OSDN Git Service

2009-04-10 Ed Schonberg <schonberg@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
1350          --    callable (Task_Id (Pref._disp_get_task_id));
1351
1352          if Ada_Version >= Ada_05
1353            and then Ekind (Ptyp) = E_Class_Wide_Type
1354            and then Is_Interface (Ptyp)
1355            and then Is_Task_Interface (Ptyp)
1356          then
1357             Rewrite (N,
1358               Make_Function_Call (Loc,
1359                 Name =>
1360                   New_Reference_To (RTE (RE_Callable), Loc),
1361                 Parameter_Associations => New_List (
1362                   Make_Unchecked_Type_Conversion (Loc,
1363                     Subtype_Mark =>
1364                       New_Reference_To (RTE (RO_ST_Task_Id), Loc),
1365                     Expression =>
1366                       Make_Selected_Component (Loc,
1367                         Prefix =>
1368                           New_Copy_Tree (Pref),
1369                         Selector_Name =>
1370                           Make_Identifier (Loc, Name_uDisp_Get_Task_Id))))));
1371
1372          else
1373             Rewrite (N,
1374               Build_Call_With_Task (Pref, RTE (RE_Callable)));
1375          end if;
1376
1377          Analyze_And_Resolve (N, Standard_Boolean);
1378       end Callable;
1379
1380       ------------
1381       -- Caller --
1382       ------------
1383
1384       --  Transforms 'Caller attribute into a call to either the
1385       --  Task_Entry_Caller or the Protected_Entry_Caller function.
1386
1387       when Attribute_Caller => Caller : declare
1388          Id_Kind    : constant Entity_Id := RTE (RO_AT_Task_Id);
1389          Ent        : constant Entity_Id := Entity (Pref);
1390          Conctype   : constant Entity_Id := Scope (Ent);
1391          Nest_Depth : Integer := 0;
1392          Name       : Node_Id;
1393          S          : Entity_Id;
1394
1395       begin
1396          --  Protected case
1397
1398          if Is_Protected_Type (Conctype) then
1399             case Corresponding_Runtime_Package (Conctype) is
1400                when System_Tasking_Protected_Objects_Entries =>
1401                   Name :=
1402                     New_Reference_To
1403                       (RTE (RE_Protected_Entry_Caller), Loc);
1404
1405                when System_Tasking_Protected_Objects_Single_Entry =>
1406                   Name :=
1407                     New_Reference_To
1408                       (RTE (RE_Protected_Single_Entry_Caller), Loc);
1409
1410                when others =>
1411                   raise Program_Error;
1412             end case;
1413
1414             Rewrite (N,
1415               Unchecked_Convert_To (Id_Kind,
1416                 Make_Function_Call (Loc,
1417                   Name => Name,
1418                   Parameter_Associations => New_List (
1419                     New_Reference_To
1420                       (Find_Protection_Object (Current_Scope), Loc)))));
1421
1422          --  Task case
1423
1424          else
1425             --  Determine the nesting depth of the E'Caller attribute, that
1426             --  is, how many accept statements are nested within the accept
1427             --  statement for E at the point of E'Caller. The runtime uses
1428             --  this depth to find the specified entry call.
1429
1430             for J in reverse 0 .. Scope_Stack.Last loop
1431                S := Scope_Stack.Table (J).Entity;
1432
1433                --  We should not reach the scope of the entry, as it should
1434                --  already have been checked in Sem_Attr that this attribute
1435                --  reference is within a matching accept statement.
1436
1437                pragma Assert (S /= Conctype);
1438
1439                if S = Ent then
1440                   exit;
1441
1442                elsif Is_Entry (S) then
1443                   Nest_Depth := Nest_Depth + 1;
1444                end if;
1445             end loop;
1446
1447             Rewrite (N,
1448               Unchecked_Convert_To (Id_Kind,
1449                 Make_Function_Call (Loc,
1450                   Name =>
1451                     New_Reference_To (RTE (RE_Task_Entry_Caller), Loc),
1452                   Parameter_Associations => New_List (
1453                     Make_Integer_Literal (Loc,
1454                       Intval => Int (Nest_Depth))))));
1455          end if;
1456
1457          Analyze_And_Resolve (N, Id_Kind);
1458       end Caller;
1459
1460       -------------
1461       -- Compose --
1462       -------------
1463
1464       --  Transforms 'Compose into a call to the floating-point attribute
1465       --  function Compose in Fat_xxx (where xxx is the root type)
1466
1467       --  Note: we strictly should have special code here to deal with the
1468       --  case of absurdly negative arguments (less than Integer'First)
1469       --  which will return a (signed) zero value, but it hardly seems
1470       --  worth the effort. Absurdly large positive arguments will raise
1471       --  constraint error which is fine.
1472
1473       when Attribute_Compose =>
1474          Expand_Fpt_Attribute_RI (N);
1475
1476       -----------------
1477       -- Constrained --
1478       -----------------
1479
1480       when Attribute_Constrained => Constrained : declare
1481          Formal_Ent : constant Entity_Id := Param_Entity (Pref);
1482
1483          function Is_Constrained_Aliased_View (Obj : Node_Id) return Boolean;
1484          --  Ada 2005 (AI-363): Returns True if the object name Obj denotes a
1485          --  view of an aliased object whose subtype is constrained.
1486
1487          ---------------------------------
1488          -- Is_Constrained_Aliased_View --
1489          ---------------------------------
1490
1491          function Is_Constrained_Aliased_View (Obj : Node_Id) return Boolean is
1492             E : Entity_Id;
1493
1494          begin
1495             if Is_Entity_Name (Obj) then
1496                E := Entity (Obj);
1497
1498                if Present (Renamed_Object (E)) then
1499                   return Is_Constrained_Aliased_View (Renamed_Object (E));
1500                else
1501                   return Is_Aliased (E) and then Is_Constrained (Etype (E));
1502                end if;
1503
1504             else
1505                return Is_Aliased_View (Obj)
1506                         and then
1507                       (Is_Constrained (Etype (Obj))
1508                          or else (Nkind (Obj) = N_Explicit_Dereference
1509                                     and then
1510                                       not Has_Constrained_Partial_View
1511                                             (Base_Type (Etype (Obj)))));
1512             end if;
1513          end Is_Constrained_Aliased_View;
1514
1515       --  Start of processing for Constrained
1516
1517       begin
1518          --  Reference to a parameter where the value is passed as an extra
1519          --  actual, corresponding to the extra formal referenced by the
1520          --  Extra_Constrained field of the corresponding formal. If this
1521          --  is an entry in-parameter, it is replaced by a constant renaming
1522          --  for which Extra_Constrained is never created.
1523
1524          if Present (Formal_Ent)
1525            and then Ekind (Formal_Ent) /= E_Constant
1526            and then Present (Extra_Constrained (Formal_Ent))
1527          then
1528             Rewrite (N,
1529               New_Occurrence_Of
1530                 (Extra_Constrained (Formal_Ent), Sloc (N)));
1531
1532          --  For variables with a Extra_Constrained field, we use the
1533          --  corresponding entity.
1534
1535          elsif Nkind (Pref) = N_Identifier
1536            and then Ekind (Entity (Pref)) = E_Variable
1537            and then Present (Extra_Constrained (Entity (Pref)))
1538          then
1539             Rewrite (N,
1540               New_Occurrence_Of
1541                 (Extra_Constrained (Entity (Pref)), Sloc (N)));
1542
1543          --  For all other entity names, we can tell at compile time
1544
1545          elsif Is_Entity_Name (Pref) then
1546             declare
1547                Ent : constant Entity_Id   := Entity (Pref);
1548                Res : Boolean;
1549
1550             begin
1551                --  (RM J.4) obsolescent cases
1552
1553                if Is_Type (Ent) then
1554
1555                   --  Private type
1556
1557                   if Is_Private_Type (Ent) then
1558                      Res := not Has_Discriminants (Ent)
1559                               or else Is_Constrained (Ent);
1560
1561                   --  It not a private type, must be a generic actual type
1562                   --  that corresponded to a private type. We know that this
1563                   --  correspondence holds, since otherwise the reference
1564                   --  within the generic template would have been illegal.
1565
1566                   else
1567                      if Is_Composite_Type (Underlying_Type (Ent)) then
1568                         Res := Is_Constrained (Ent);
1569                      else
1570                         Res := True;
1571                      end if;
1572                   end if;
1573
1574                --  If the prefix is not a variable or is aliased, then
1575                --  definitely true; if it's a formal parameter without an
1576                --  associated extra formal, then treat it as constrained.
1577
1578                --  Ada 2005 (AI-363): An aliased prefix must be known to be
1579                --  constrained in order to set the attribute to True.
1580
1581                elsif not Is_Variable (Pref)
1582                  or else Present (Formal_Ent)
1583                  or else (Ada_Version < Ada_05
1584                             and then Is_Aliased_View (Pref))
1585                  or else (Ada_Version >= Ada_05
1586                             and then Is_Constrained_Aliased_View (Pref))
1587                then
1588                   Res := True;
1589
1590                --  Variable case, look at type to see if it is constrained.
1591                --  Note that the one case where this is not accurate (the
1592                --  procedure formal case), has been handled above.
1593
1594                --  We use the Underlying_Type here (and below) in case the
1595                --  type is private without discriminants, but the full type
1596                --  has discriminants. This case is illegal, but we generate it
1597                --  internally for passing to the Extra_Constrained parameter.
1598
1599                else
1600                   Res := Is_Constrained (Underlying_Type (Etype (Ent)));
1601                end if;
1602
1603                Rewrite (N,
1604                  New_Reference_To (Boolean_Literals (Res), Loc));
1605             end;
1606
1607          --  Prefix is not an entity name. These are also cases where we can
1608          --  always tell at compile time by looking at the form and type of the
1609          --  prefix. If an explicit dereference of an object with constrained
1610          --  partial view, this is unconstrained (Ada 2005 AI-363).
1611
1612          else
1613             Rewrite (N,
1614               New_Reference_To (
1615                 Boolean_Literals (
1616                   not Is_Variable (Pref)
1617                     or else
1618                      (Nkind (Pref) = N_Explicit_Dereference
1619                         and then
1620                           not Has_Constrained_Partial_View (Base_Type (Ptyp)))
1621                     or else Is_Constrained (Underlying_Type (Ptyp))),
1622                 Loc));
1623          end if;
1624
1625          Analyze_And_Resolve (N, Standard_Boolean);
1626       end Constrained;
1627
1628       ---------------
1629       -- Copy_Sign --
1630       ---------------
1631
1632       --  Transforms 'Copy_Sign into a call to the floating-point attribute
1633       --  function Copy_Sign in Fat_xxx (where xxx is the root type)
1634
1635       when Attribute_Copy_Sign =>
1636          Expand_Fpt_Attribute_RR (N);
1637
1638       -----------
1639       -- Count --
1640       -----------
1641
1642       --  Transforms 'Count attribute into a call to the Count function
1643
1644       when Attribute_Count => Count : declare
1645          Call     : Node_Id;
1646          Conctyp  : Entity_Id;
1647          Entnam   : Node_Id;
1648          Entry_Id : Entity_Id;
1649          Index    : Node_Id;
1650          Name     : Node_Id;
1651
1652       begin
1653          --  If the prefix is a member of an entry family, retrieve both
1654          --  entry name and index. For a simple entry there is no index.
1655
1656          if Nkind (Pref) = N_Indexed_Component then
1657             Entnam := Prefix (Pref);
1658             Index := First (Expressions (Pref));
1659          else
1660             Entnam := Pref;
1661             Index := Empty;
1662          end if;
1663
1664          Entry_Id := Entity (Entnam);
1665
1666          --  Find the concurrent type in which this attribute is referenced
1667          --  (there had better be one).
1668
1669          Conctyp := Current_Scope;
1670          while not Is_Concurrent_Type (Conctyp) loop
1671             Conctyp := Scope (Conctyp);
1672          end loop;
1673
1674          --  Protected case
1675
1676          if Is_Protected_Type (Conctyp) then
1677             case Corresponding_Runtime_Package (Conctyp) is
1678                when System_Tasking_Protected_Objects_Entries =>
1679                   Name := New_Reference_To (RTE (RE_Protected_Count), Loc);
1680
1681                   Call :=
1682                     Make_Function_Call (Loc,
1683                       Name => Name,
1684                       Parameter_Associations => New_List (
1685                         New_Reference_To
1686                           (Find_Protection_Object (Current_Scope), Loc),
1687                         Entry_Index_Expression
1688                           (Loc, Entry_Id, Index, Scope (Entry_Id))));
1689
1690                when System_Tasking_Protected_Objects_Single_Entry =>
1691                   Name :=
1692                     New_Reference_To (RTE (RE_Protected_Count_Entry), Loc);
1693
1694                   Call :=
1695                     Make_Function_Call (Loc,
1696                       Name => Name,
1697                       Parameter_Associations => New_List (
1698                         New_Reference_To
1699                           (Find_Protection_Object (Current_Scope), Loc)));
1700
1701                when others =>
1702                   raise Program_Error;
1703             end case;
1704
1705          --  Task case
1706
1707          else
1708             Call :=
1709               Make_Function_Call (Loc,
1710                 Name => New_Reference_To (RTE (RE_Task_Count), Loc),
1711                 Parameter_Associations => New_List (
1712                   Entry_Index_Expression (Loc,
1713                     Entry_Id, Index, Scope (Entry_Id))));
1714          end if;
1715
1716          --  The call returns type Natural but the context is universal integer
1717          --  so any integer type is allowed. The attribute was already resolved
1718          --  so its Etype is the required result type. If the base type of the
1719          --  context type is other than Standard.Integer we put in a conversion
1720          --  to the required type. This can be a normal typed conversion since
1721          --  both input and output types of the conversion are integer types
1722
1723          if Base_Type (Typ) /= Base_Type (Standard_Integer) then
1724             Rewrite (N, Convert_To (Typ, Call));
1725          else
1726             Rewrite (N, Call);
1727          end if;
1728
1729          Analyze_And_Resolve (N, Typ);
1730       end Count;
1731
1732       ---------------
1733       -- Elab_Body --
1734       ---------------
1735
1736       --  This processing is shared by Elab_Spec
1737
1738       --  What we do is to insert the following declarations
1739
1740       --     procedure tnn;
1741       --     pragma Import (C, enn, "name___elabb/s");
1742
1743       --  and then the Elab_Body/Spec attribute is replaced by a reference
1744       --  to this defining identifier.
1745
1746       when Attribute_Elab_Body |
1747            Attribute_Elab_Spec =>
1748
1749          Elab_Body : declare
1750             Ent  : constant Entity_Id :=
1751                      Make_Defining_Identifier (Loc,
1752                        New_Internal_Name ('E'));
1753             Str  : String_Id;
1754             Lang : Node_Id;
1755
1756             procedure Make_Elab_String (Nod : Node_Id);
1757             --  Given Nod, an identifier, or a selected component, put the
1758             --  image into the current string literal, with double underline
1759             --  between components.
1760
1761             ----------------------
1762             -- Make_Elab_String --
1763             ----------------------
1764
1765             procedure Make_Elab_String (Nod : Node_Id) is
1766             begin
1767                if Nkind (Nod) = N_Selected_Component then
1768                   Make_Elab_String (Prefix (Nod));
1769
1770                   case VM_Target is
1771                      when JVM_Target =>
1772                         Store_String_Char ('$');
1773                      when CLI_Target =>
1774                         Store_String_Char ('.');
1775                      when No_VM =>
1776                         Store_String_Char ('_');
1777                         Store_String_Char ('_');
1778                   end case;
1779
1780                   Get_Name_String (Chars (Selector_Name (Nod)));
1781
1782                else
1783                   pragma Assert (Nkind (Nod) = N_Identifier);
1784                   Get_Name_String (Chars (Nod));
1785                end if;
1786
1787                Store_String_Chars (Name_Buffer (1 .. Name_Len));
1788             end Make_Elab_String;
1789
1790          --  Start of processing for Elab_Body/Elab_Spec
1791
1792          begin
1793             --  First we need to prepare the string literal for the name of
1794             --  the elaboration routine to be referenced.
1795
1796             Start_String;
1797             Make_Elab_String (Pref);
1798
1799             if VM_Target = No_VM then
1800                Store_String_Chars ("___elab");
1801                Lang := Make_Identifier (Loc, Name_C);
1802             else
1803                Store_String_Chars ("._elab");
1804                Lang := Make_Identifier (Loc, Name_Ada);
1805             end if;
1806
1807             if Id = Attribute_Elab_Body then
1808                Store_String_Char ('b');
1809             else
1810                Store_String_Char ('s');
1811             end if;
1812
1813             Str := End_String;
1814
1815             Insert_Actions (N, New_List (
1816               Make_Subprogram_Declaration (Loc,
1817                 Specification =>
1818                   Make_Procedure_Specification (Loc,
1819                     Defining_Unit_Name => Ent)),
1820
1821               Make_Pragma (Loc,
1822                 Chars => Name_Import,
1823                 Pragma_Argument_Associations => New_List (
1824                   Make_Pragma_Argument_Association (Loc,
1825                     Expression => Lang),
1826
1827                   Make_Pragma_Argument_Association (Loc,
1828                     Expression =>
1829                       Make_Identifier (Loc, Chars (Ent))),
1830
1831                   Make_Pragma_Argument_Association (Loc,
1832                     Expression =>
1833                       Make_String_Literal (Loc, Str))))));
1834
1835             Set_Entity (N, Ent);
1836             Rewrite (N, New_Occurrence_Of (Ent, Loc));
1837          end Elab_Body;
1838
1839       ----------------
1840       -- Elaborated --
1841       ----------------
1842
1843       --  Elaborated is always True for preelaborated units, predefined units,
1844       --  pure units and units which have Elaborate_Body pragmas. These units
1845       --  have no elaboration entity.
1846
1847       --  Note: The Elaborated attribute is never passed to the back end
1848
1849       when Attribute_Elaborated => Elaborated : declare
1850          Ent : constant Entity_Id := Entity (Pref);
1851
1852       begin
1853          if Present (Elaboration_Entity (Ent)) then
1854             Rewrite (N,
1855               New_Occurrence_Of (Elaboration_Entity (Ent), Loc));
1856          else
1857             Rewrite (N, New_Occurrence_Of (Standard_True, Loc));
1858          end if;
1859       end Elaborated;
1860
1861       --------------
1862       -- Enum_Rep --
1863       --------------
1864
1865       when Attribute_Enum_Rep => Enum_Rep :
1866       begin
1867          --  X'Enum_Rep (Y) expands to
1868
1869          --    target-type (Y)
1870
1871          --  This is simply a direct conversion from the enumeration type to
1872          --  the target integer type, which is treated by the back end as a
1873          --  normal integer conversion, treating the enumeration type as an
1874          --  integer, which is exactly what we want! We set Conversion_OK to
1875          --  make sure that the analyzer does not complain about what otherwise
1876          --  might be an illegal conversion.
1877
1878          if Is_Non_Empty_List (Exprs) then
1879             Rewrite (N,
1880               OK_Convert_To (Typ, Relocate_Node (First (Exprs))));
1881
1882          --  X'Enum_Rep where X is an enumeration literal is replaced by
1883          --  the literal value.
1884
1885          elsif Ekind (Entity (Pref)) = E_Enumeration_Literal then
1886             Rewrite (N,
1887               Make_Integer_Literal (Loc, Enumeration_Rep (Entity (Pref))));
1888
1889          --  If this is a renaming of a literal, recover the representation
1890          --  of the original.
1891
1892          elsif Ekind (Entity (Pref)) = E_Constant
1893            and then Present (Renamed_Object (Entity (Pref)))
1894            and then
1895              Ekind (Entity (Renamed_Object (Entity (Pref))))
1896                = E_Enumeration_Literal
1897          then
1898             Rewrite (N,
1899               Make_Integer_Literal (Loc,
1900                 Enumeration_Rep (Entity (Renamed_Object (Entity (Pref))))));
1901
1902          --  X'Enum_Rep where X is an object does a direct unchecked conversion
1903          --  of the object value, as described for the type case above.
1904
1905          else
1906             Rewrite (N,
1907               OK_Convert_To (Typ, Relocate_Node (Pref)));
1908          end if;
1909
1910          Set_Etype (N, Typ);
1911          Analyze_And_Resolve (N, Typ);
1912       end Enum_Rep;
1913
1914       --------------
1915       -- Enum_Val --
1916       --------------
1917
1918       when Attribute_Enum_Val => Enum_Val : declare
1919          Expr : Node_Id;
1920          Btyp : constant Entity_Id  := Base_Type (Ptyp);
1921
1922       begin
1923          --  X'Enum_Val (Y) expands to
1924
1925          --    [constraint_error when _rep_to_pos (Y, False) = -1, msg]
1926          --    X!(Y);
1927
1928          Expr := Unchecked_Convert_To (Ptyp, First (Exprs));
1929
1930          Insert_Action (N,
1931            Make_Raise_Constraint_Error (Loc,
1932              Condition =>
1933                Make_Op_Eq (Loc,
1934                  Left_Opnd =>
1935                    Make_Function_Call (Loc,
1936                      Name =>
1937                        New_Reference_To (TSS (Btyp, TSS_Rep_To_Pos), Loc),
1938                      Parameter_Associations => New_List (
1939                        Relocate_Node (Duplicate_Subexpr (Expr)),
1940                          New_Occurrence_Of (Standard_False, Loc))),
1941
1942                  Right_Opnd => Make_Integer_Literal (Loc, -1)),
1943              Reason => CE_Range_Check_Failed));
1944
1945          Rewrite (N, Expr);
1946          Analyze_And_Resolve (N, Ptyp);
1947       end Enum_Val;
1948
1949       --------------
1950       -- Exponent --
1951       --------------
1952
1953       --  Transforms 'Exponent into a call to the floating-point attribute
1954       --  function Exponent in Fat_xxx (where xxx is the root type)
1955
1956       when Attribute_Exponent =>
1957          Expand_Fpt_Attribute_R (N);
1958
1959       ------------------
1960       -- External_Tag --
1961       ------------------
1962
1963       --  transforme X'External_Tag into Ada.Tags.External_Tag (X'tag)
1964
1965       when Attribute_External_Tag => External_Tag :
1966       begin
1967          Rewrite (N,
1968            Make_Function_Call (Loc,
1969              Name => New_Reference_To (RTE (RE_External_Tag), Loc),
1970              Parameter_Associations => New_List (
1971                Make_Attribute_Reference (Loc,
1972                  Attribute_Name => Name_Tag,
1973                  Prefix => Prefix (N)))));
1974
1975          Analyze_And_Resolve (N, Standard_String);
1976       end External_Tag;
1977
1978       -----------
1979       -- First --
1980       -----------
1981
1982       when Attribute_First =>
1983
1984          --  If the prefix type is a constrained packed array type which
1985          --  already has a Packed_Array_Type representation defined, then
1986          --  replace this attribute with a direct reference to 'First of the
1987          --  appropriate index subtype (since otherwise the back end will try
1988          --  to give us the value of 'First for this implementation type).
1989
1990          if Is_Constrained_Packed_Array (Ptyp) then
1991             Rewrite (N,
1992               Make_Attribute_Reference (Loc,
1993                 Attribute_Name => Name_First,
1994                 Prefix => New_Reference_To (Get_Index_Subtype (N), Loc)));
1995             Analyze_And_Resolve (N, Typ);
1996
1997          elsif Is_Access_Type (Ptyp) then
1998             Apply_Access_Check (N);
1999          end if;
2000
2001       ---------------
2002       -- First_Bit --
2003       ---------------
2004
2005       --  Compute this if component clause was present, otherwise we leave the
2006       --  computation to be completed in the back-end, since we don't know what
2007       --  layout will be chosen.
2008
2009       when Attribute_First_Bit => First_Bit : declare
2010          CE : constant Entity_Id := Entity (Selector_Name (Pref));
2011
2012       begin
2013          if Known_Static_Component_Bit_Offset (CE) then
2014             Rewrite (N,
2015               Make_Integer_Literal (Loc,
2016                 Component_Bit_Offset (CE) mod System_Storage_Unit));
2017
2018             Analyze_And_Resolve (N, Typ);
2019
2020          else
2021             Apply_Universal_Integer_Attribute_Checks (N);
2022          end if;
2023       end First_Bit;
2024
2025       -----------------
2026       -- Fixed_Value --
2027       -----------------
2028
2029       --  We transform:
2030
2031       --     fixtype'Fixed_Value (integer-value)
2032
2033       --  into
2034
2035       --     fixtype(integer-value)
2036
2037       --  We do all the required analysis of the conversion here, because we do
2038       --  not want this to go through the fixed-point conversion circuits. Note
2039       --  that the back end always treats fixed-point as equivalent to the
2040       --  corresponding integer type anyway.
2041
2042       when Attribute_Fixed_Value => Fixed_Value :
2043       begin
2044          Rewrite (N,
2045            Make_Type_Conversion (Loc,
2046              Subtype_Mark => New_Occurrence_Of (Entity (Pref), Loc),
2047              Expression   => Relocate_Node (First (Exprs))));
2048          Set_Etype (N, Entity (Pref));
2049          Set_Analyzed (N);
2050
2051       --  Note: it might appear that a properly analyzed unchecked conversion
2052       --  would be just fine here, but that's not the case, since the full
2053       --  range checks performed by the following call are critical!
2054
2055          Apply_Type_Conversion_Checks (N);
2056       end Fixed_Value;
2057
2058       -----------
2059       -- Floor --
2060       -----------
2061
2062       --  Transforms 'Floor into a call to the floating-point attribute
2063       --  function Floor in Fat_xxx (where xxx is the root type)
2064
2065       when Attribute_Floor =>
2066          Expand_Fpt_Attribute_R (N);
2067
2068       ----------
2069       -- Fore --
2070       ----------
2071
2072       --  For the fixed-point type Typ:
2073
2074       --    Typ'Fore
2075
2076       --  expands into
2077
2078       --    Result_Type (System.Fore (Universal_Real (Type'First)),
2079       --                              Universal_Real (Type'Last))
2080
2081       --  Note that we know that the type is a non-static subtype, or Fore
2082       --  would have itself been computed dynamically in Eval_Attribute.
2083
2084       when Attribute_Fore => Fore : begin
2085          Rewrite (N,
2086            Convert_To (Typ,
2087              Make_Function_Call (Loc,
2088                Name => New_Reference_To (RTE (RE_Fore), Loc),
2089
2090                Parameter_Associations => New_List (
2091                  Convert_To (Universal_Real,
2092                    Make_Attribute_Reference (Loc,
2093                      Prefix => New_Reference_To (Ptyp, Loc),
2094                      Attribute_Name => Name_First)),
2095
2096                  Convert_To (Universal_Real,
2097                    Make_Attribute_Reference (Loc,
2098                      Prefix => New_Reference_To (Ptyp, Loc),
2099                      Attribute_Name => Name_Last))))));
2100
2101          Analyze_And_Resolve (N, Typ);
2102       end Fore;
2103
2104       --------------
2105       -- Fraction --
2106       --------------
2107
2108       --  Transforms 'Fraction into a call to the floating-point attribute
2109       --  function Fraction in Fat_xxx (where xxx is the root type)
2110
2111       when Attribute_Fraction =>
2112          Expand_Fpt_Attribute_R (N);
2113
2114       --------------
2115       -- From_Any --
2116       --------------
2117
2118       when Attribute_From_Any => From_Any : declare
2119          P_Type : constant Entity_Id := Etype (Pref);
2120          Decls  : constant List_Id   := New_List;
2121       begin
2122          Rewrite (N,
2123            Build_From_Any_Call (P_Type,
2124              Relocate_Node (First (Exprs)),
2125              Decls));
2126          Insert_Actions (N, Decls);
2127          Analyze_And_Resolve (N, P_Type);
2128       end From_Any;
2129
2130       --------------
2131       -- Identity --
2132       --------------
2133
2134       --  For an exception returns a reference to the exception data:
2135       --      Exception_Id!(Prefix'Reference)
2136
2137       --  For a task it returns a reference to the _task_id component of
2138       --  corresponding record:
2139
2140       --    taskV!(Prefix)._Task_Id, converted to the type Task_Id defined
2141
2142       --  in Ada.Task_Identification
2143
2144       when Attribute_Identity => Identity : declare
2145          Id_Kind : Entity_Id;
2146
2147       begin
2148          if Ptyp = Standard_Exception_Type then
2149             Id_Kind := RTE (RE_Exception_Id);
2150
2151             if Present (Renamed_Object (Entity (Pref))) then
2152                Set_Entity (Pref, Renamed_Object (Entity (Pref)));
2153             end if;
2154
2155             Rewrite (N,
2156               Unchecked_Convert_To (Id_Kind, Make_Reference (Loc, Pref)));
2157          else
2158             Id_Kind := RTE (RO_AT_Task_Id);
2159
2160             --  If the prefix is a task interface, the Task_Id is obtained
2161             --  dynamically through a dispatching call, as for other task
2162             --  attributes applied to interfaces.
2163
2164             if Ada_Version >= Ada_05
2165               and then Ekind (Ptyp) = E_Class_Wide_Type
2166               and then Is_Interface (Ptyp)
2167               and then Is_Task_Interface (Ptyp)
2168             then
2169                Rewrite (N,
2170                  Unchecked_Convert_To (Id_Kind,
2171                    Make_Selected_Component (Loc,
2172                      Prefix =>
2173                        New_Copy_Tree (Pref),
2174                      Selector_Name =>
2175                        Make_Identifier (Loc, Name_uDisp_Get_Task_Id))));
2176
2177             else
2178                Rewrite (N,
2179                  Unchecked_Convert_To (Id_Kind, Concurrent_Ref (Pref)));
2180             end if;
2181          end if;
2182
2183          Analyze_And_Resolve (N, Id_Kind);
2184       end Identity;
2185
2186       -----------
2187       -- Image --
2188       -----------
2189
2190       --  Image attribute is handled in separate unit Exp_Imgv
2191
2192       when Attribute_Image =>
2193          Exp_Imgv.Expand_Image_Attribute (N);
2194
2195       ---------
2196       -- Img --
2197       ---------
2198
2199       --  X'Img is expanded to typ'Image (X), where typ is the type of X
2200
2201       when Attribute_Img => Img :
2202       begin
2203          Rewrite (N,
2204            Make_Attribute_Reference (Loc,
2205              Prefix => New_Reference_To (Ptyp, Loc),
2206              Attribute_Name => Name_Image,
2207              Expressions => New_List (Relocate_Node (Pref))));
2208
2209          Analyze_And_Resolve (N, Standard_String);
2210       end Img;
2211
2212       -----------
2213       -- Input --
2214       -----------
2215
2216       when Attribute_Input => Input : declare
2217          P_Type : constant Entity_Id := Entity (Pref);
2218          B_Type : constant Entity_Id := Base_Type (P_Type);
2219          U_Type : constant Entity_Id := Underlying_Type (P_Type);
2220          Strm   : constant Node_Id   := First (Exprs);
2221          Fname  : Entity_Id;
2222          Decl   : Node_Id;
2223          Call   : Node_Id;
2224          Prag   : Node_Id;
2225          Arg2   : Node_Id;
2226          Rfunc  : Node_Id;
2227
2228          Cntrl  : Node_Id := Empty;
2229          --  Value for controlling argument in call. Always Empty except in
2230          --  the dispatching (class-wide type) case, where it is a reference
2231          --  to the dummy object initialized to the right internal tag.
2232
2233          procedure Freeze_Stream_Subprogram (F : Entity_Id);
2234          --  The expansion of the attribute reference may generate a call to
2235          --  a user-defined stream subprogram that is frozen by the call. This
2236          --  can lead to access-before-elaboration problem if the reference
2237          --  appears in an object declaration and the subprogram body has not
2238          --  been seen. The freezing of the subprogram requires special code
2239          --  because it appears in an expanded context where expressions do
2240          --  not freeze their constituents.
2241
2242          ------------------------------
2243          -- Freeze_Stream_Subprogram --
2244          ------------------------------
2245
2246          procedure Freeze_Stream_Subprogram (F : Entity_Id) is
2247             Decl : constant Node_Id := Unit_Declaration_Node (F);
2248             Bod  : Node_Id;
2249
2250          begin
2251             --  If this is user-defined subprogram, the corresponding
2252             --  stream function appears as a renaming-as-body, and the
2253             --  user subprogram must be retrieved by tree traversal.
2254
2255             if Present (Decl)
2256               and then Nkind (Decl) = N_Subprogram_Declaration
2257               and then Present (Corresponding_Body (Decl))
2258             then
2259                Bod := Corresponding_Body (Decl);
2260
2261                if Nkind (Unit_Declaration_Node (Bod)) =
2262                  N_Subprogram_Renaming_Declaration
2263                then
2264                   Set_Is_Frozen (Entity (Name (Unit_Declaration_Node (Bod))));
2265                end if;
2266             end if;
2267          end Freeze_Stream_Subprogram;
2268
2269       --  Start of processing for Input
2270
2271       begin
2272          --  If no underlying type, we have an error that will be diagnosed
2273          --  elsewhere, so here we just completely ignore the expansion.
2274
2275          if No (U_Type) then
2276             return;
2277          end if;
2278
2279          --  If there is a TSS for Input, just call it
2280
2281          Fname := Find_Stream_Subprogram (P_Type, TSS_Stream_Input);
2282
2283          if Present (Fname) then
2284             null;
2285
2286          else
2287             --  If there is a Stream_Convert pragma, use it, we rewrite
2288
2289             --     sourcetyp'Input (stream)
2290
2291             --  as
2292
2293             --     sourcetyp (streamread (strmtyp'Input (stream)));
2294
2295             --  where streamread is the given Read function that converts an
2296             --  argument of type strmtyp to type sourcetyp or a type from which
2297             --  it is derived (extra conversion required for the derived case).
2298
2299             Prag := Get_Stream_Convert_Pragma (P_Type);
2300
2301             if Present (Prag) then
2302                Arg2  := Next (First (Pragma_Argument_Associations (Prag)));
2303                Rfunc := Entity (Expression (Arg2));
2304
2305                Rewrite (N,
2306                  Convert_To (B_Type,
2307                    Make_Function_Call (Loc,
2308                      Name => New_Occurrence_Of (Rfunc, Loc),
2309                      Parameter_Associations => New_List (
2310                        Make_Attribute_Reference (Loc,
2311                          Prefix =>
2312                            New_Occurrence_Of
2313                              (Etype (First_Formal (Rfunc)), Loc),
2314                          Attribute_Name => Name_Input,
2315                          Expressions => Exprs)))));
2316
2317                Analyze_And_Resolve (N, B_Type);
2318                return;
2319
2320             --  Elementary types
2321
2322             elsif Is_Elementary_Type (U_Type) then
2323
2324                --  A special case arises if we have a defined _Read routine,
2325                --  since in this case we are required to call this routine.
2326
2327                if Present (TSS (Base_Type (U_Type), TSS_Stream_Read)) then
2328                   Build_Record_Or_Elementary_Input_Function
2329                     (Loc, U_Type, Decl, Fname);
2330                   Insert_Action (N, Decl);
2331
2332                --  For normal cases, we call the I_xxx routine directly
2333
2334                else
2335                   Rewrite (N, Build_Elementary_Input_Call (N));
2336                   Analyze_And_Resolve (N, P_Type);
2337                   return;
2338                end if;
2339
2340             --  Array type case
2341
2342             elsif Is_Array_Type (U_Type) then
2343                Build_Array_Input_Function (Loc, U_Type, Decl, Fname);
2344                Compile_Stream_Body_In_Scope (N, Decl, U_Type, Check => False);
2345
2346             --  Dispatching case with class-wide type
2347
2348             elsif Is_Class_Wide_Type (P_Type) then
2349
2350                --  No need to do anything else compiling under restriction
2351                --  No_Dispatching_Calls. During the semantic analysis we
2352                --  already notified such violation.
2353
2354                if Restriction_Active (No_Dispatching_Calls) then
2355                   return;
2356                end if;
2357
2358                declare
2359                   Rtyp : constant Entity_Id := Root_Type (P_Type);
2360                   Dnn  : Entity_Id;
2361                   Decl : Node_Id;
2362
2363                begin
2364                   --  Read the internal tag (RM 13.13.2(34)) and use it to
2365                   --  initialize a dummy tag object:
2366
2367                   --    Dnn : Ada.Tags.Tag
2368                   --           := Descendant_Tag (String'Input (Strm), P_Type);
2369
2370                   --  This dummy object is used only to provide a controlling
2371                   --  argument for the eventual _Input call. Descendant_Tag is
2372                   --  called rather than Internal_Tag to ensure that we have a
2373                   --  tag for a type that is descended from the prefix type and
2374                   --  declared at the same accessibility level (the exception
2375                   --  Tag_Error will be raised otherwise). The level check is
2376                   --  required for Ada 2005 because tagged types can be
2377                   --  extended in nested scopes (AI-344).
2378
2379                   Dnn :=
2380                     Make_Defining_Identifier (Loc,
2381                       Chars => New_Internal_Name ('D'));
2382
2383                   Decl :=
2384                     Make_Object_Declaration (Loc,
2385                       Defining_Identifier => Dnn,
2386                       Object_Definition =>
2387                         New_Occurrence_Of (RTE (RE_Tag), Loc),
2388                       Expression =>
2389                         Make_Function_Call (Loc,
2390                           Name =>
2391                             New_Occurrence_Of (RTE (RE_Descendant_Tag), Loc),
2392                           Parameter_Associations => New_List (
2393                             Make_Attribute_Reference (Loc,
2394                               Prefix =>
2395                                 New_Occurrence_Of (Standard_String, Loc),
2396                               Attribute_Name => Name_Input,
2397                               Expressions => New_List (
2398                                 Relocate_Node
2399                                   (Duplicate_Subexpr (Strm)))),
2400                             Make_Attribute_Reference (Loc,
2401                               Prefix => New_Reference_To (P_Type, Loc),
2402                               Attribute_Name => Name_Tag))));
2403
2404                   Insert_Action (N, Decl);
2405
2406                   --  Now we need to get the entity for the call, and construct
2407                   --  a function call node, where we preset a reference to Dnn
2408                   --  as the controlling argument (doing an unchecked convert
2409                   --  to the class-wide tagged type to make it look like a real
2410                   --  tagged object).
2411
2412                   Fname := Find_Prim_Op (Rtyp, TSS_Stream_Input);
2413                   Cntrl := Unchecked_Convert_To (P_Type,
2414                              New_Occurrence_Of (Dnn, Loc));
2415                   Set_Etype (Cntrl, P_Type);
2416                   Set_Parent (Cntrl, N);
2417                end;
2418
2419             --  For tagged types, use the primitive Input function
2420
2421             elsif Is_Tagged_Type (U_Type) then
2422                Fname := Find_Prim_Op (U_Type, TSS_Stream_Input);
2423
2424             --  All other record type cases, including protected records. The
2425             --  latter only arise for expander generated code for handling
2426             --  shared passive partition access.
2427
2428             else
2429                pragma Assert
2430                  (Is_Record_Type (U_Type) or else Is_Protected_Type (U_Type));
2431
2432                --  Ada 2005 (AI-216): Program_Error is raised executing default
2433                --  implementation of the Input attribute of an unchecked union
2434                --  type if the type lacks default discriminant values.
2435
2436                if Is_Unchecked_Union (Base_Type (U_Type))
2437                  and then No (Discriminant_Constraint (U_Type))
2438                then
2439                   Insert_Action (N,
2440                     Make_Raise_Program_Error (Loc,
2441                       Reason => PE_Unchecked_Union_Restriction));
2442
2443                   return;
2444                end if;
2445
2446                Build_Record_Or_Elementary_Input_Function
2447                  (Loc, Base_Type (U_Type), Decl, Fname);
2448                Insert_Action (N, Decl);
2449
2450                if Nkind (Parent (N)) = N_Object_Declaration
2451                  and then Is_Record_Type (U_Type)
2452                then
2453                   --  The stream function may contain calls to user-defined
2454                   --  Read procedures for individual components.
2455
2456                   declare
2457                      Comp : Entity_Id;
2458                      Func : Entity_Id;
2459
2460                   begin
2461                      Comp := First_Component (U_Type);
2462                      while Present (Comp) loop
2463                         Func :=
2464                           Find_Stream_Subprogram
2465                             (Etype (Comp), TSS_Stream_Read);
2466
2467                         if Present (Func) then
2468                            Freeze_Stream_Subprogram (Func);
2469                         end if;
2470
2471                         Next_Component (Comp);
2472                      end loop;
2473                   end;
2474                end if;
2475             end if;
2476          end if;
2477
2478          --  If we fall through, Fname is the function to be called. The result
2479          --  is obtained by calling the appropriate function, then converting
2480          --  the result. The conversion does a subtype check.
2481
2482          Call :=
2483            Make_Function_Call (Loc,
2484              Name => New_Occurrence_Of (Fname, Loc),
2485              Parameter_Associations => New_List (
2486                 Relocate_Node (Strm)));
2487
2488          Set_Controlling_Argument (Call, Cntrl);
2489          Rewrite (N, Unchecked_Convert_To (P_Type, Call));
2490          Analyze_And_Resolve (N, P_Type);
2491
2492          if Nkind (Parent (N)) = N_Object_Declaration then
2493             Freeze_Stream_Subprogram (Fname);
2494          end if;
2495       end Input;
2496
2497       -------------------
2498       -- Integer_Value --
2499       -------------------
2500
2501       --  We transform
2502
2503       --    inttype'Fixed_Value (fixed-value)
2504
2505       --  into
2506
2507       --    inttype(integer-value))
2508
2509       --  we do all the required analysis of the conversion here, because we do
2510       --  not want this to go through the fixed-point conversion circuits. Note
2511       --  that the back end always treats fixed-point as equivalent to the
2512       --  corresponding integer type anyway.
2513
2514       when Attribute_Integer_Value => Integer_Value :
2515       begin
2516          Rewrite (N,
2517            Make_Type_Conversion (Loc,
2518              Subtype_Mark => New_Occurrence_Of (Entity (Pref), Loc),
2519              Expression   => Relocate_Node (First (Exprs))));
2520          Set_Etype (N, Entity (Pref));
2521          Set_Analyzed (N);
2522
2523       --  Note: it might appear that a properly analyzed unchecked conversion
2524       --  would be just fine here, but that's not the case, since the full
2525       --  range checks performed by the following call are critical!
2526
2527          Apply_Type_Conversion_Checks (N);
2528       end Integer_Value;
2529
2530       -------------------
2531       -- Invalid_Value --
2532       -------------------
2533
2534       when Attribute_Invalid_Value =>
2535          Rewrite (N, Get_Simple_Init_Val (Ptyp, N));
2536
2537       ----------
2538       -- Last --
2539       ----------
2540
2541       when Attribute_Last =>
2542
2543          --  If the prefix type is a constrained packed array type which
2544          --  already has a Packed_Array_Type representation defined, then
2545          --  replace this attribute with a direct reference to 'Last of the
2546          --  appropriate index subtype (since otherwise the back end will try
2547          --  to give us the value of 'Last for this implementation type).
2548
2549          if Is_Constrained_Packed_Array (Ptyp) then
2550             Rewrite (N,
2551               Make_Attribute_Reference (Loc,
2552                 Attribute_Name => Name_Last,
2553                 Prefix => New_Reference_To (Get_Index_Subtype (N), Loc)));
2554             Analyze_And_Resolve (N, Typ);
2555
2556          elsif Is_Access_Type (Ptyp) then
2557             Apply_Access_Check (N);
2558          end if;
2559
2560       --------------
2561       -- Last_Bit --
2562       --------------
2563
2564       --  We compute this if a component clause was present, otherwise we leave
2565       --  the computation up to the back end, since we don't know what layout
2566       --  will be chosen.
2567
2568       when Attribute_Last_Bit => Last_Bit : declare
2569          CE : constant Entity_Id := Entity (Selector_Name (Pref));
2570
2571       begin
2572          if Known_Static_Component_Bit_Offset (CE)
2573            and then Known_Static_Esize (CE)
2574          then
2575             Rewrite (N,
2576               Make_Integer_Literal (Loc,
2577                Intval => (Component_Bit_Offset (CE) mod System_Storage_Unit)
2578                                 + Esize (CE) - 1));
2579
2580             Analyze_And_Resolve (N, Typ);
2581
2582          else
2583             Apply_Universal_Integer_Attribute_Checks (N);
2584          end if;
2585       end Last_Bit;
2586
2587       ------------------
2588       -- Leading_Part --
2589       ------------------
2590
2591       --  Transforms 'Leading_Part into a call to the floating-point attribute
2592       --  function Leading_Part in Fat_xxx (where xxx is the root type)
2593
2594       --  Note: strictly, we should generate special case code to deal with
2595       --  absurdly large positive arguments (greater than Integer'Last), which
2596       --  result in returning the first argument unchanged, but it hardly seems
2597       --  worth the effort. We raise constraint error for absurdly negative
2598       --  arguments which is fine.
2599
2600       when Attribute_Leading_Part =>
2601          Expand_Fpt_Attribute_RI (N);
2602
2603       ------------
2604       -- Length --
2605       ------------
2606
2607       when Attribute_Length => declare
2608          Ityp : Entity_Id;
2609          Xnum : Uint;
2610
2611       begin
2612          --  Processing for packed array types
2613
2614          if Is_Array_Type (Ptyp) and then Is_Packed (Ptyp) then
2615             Ityp := Get_Index_Subtype (N);
2616
2617             --  If the index type, Ityp, is an enumeration type with holes,
2618             --  then we calculate X'Length explicitly using
2619
2620             --     Typ'Max
2621             --       (0, Ityp'Pos (X'Last  (N)) -
2622             --           Ityp'Pos (X'First (N)) + 1);
2623
2624             --  Since the bounds in the template are the representation values
2625             --  and the back end would get the wrong value.
2626
2627             if Is_Enumeration_Type (Ityp)
2628               and then Present (Enum_Pos_To_Rep (Base_Type (Ityp)))
2629             then
2630                if No (Exprs) then
2631                   Xnum := Uint_1;
2632                else
2633                   Xnum := Expr_Value (First (Expressions (N)));
2634                end if;
2635
2636                Rewrite (N,
2637                  Make_Attribute_Reference (Loc,
2638                    Prefix         => New_Occurrence_Of (Typ, Loc),
2639                    Attribute_Name => Name_Max,
2640                    Expressions    => New_List
2641                      (Make_Integer_Literal (Loc, 0),
2642
2643                       Make_Op_Add (Loc,
2644                         Left_Opnd =>
2645                           Make_Op_Subtract (Loc,
2646                             Left_Opnd =>
2647                               Make_Attribute_Reference (Loc,
2648                                 Prefix => New_Occurrence_Of (Ityp, Loc),
2649                                 Attribute_Name => Name_Pos,
2650
2651                                 Expressions => New_List (
2652                                   Make_Attribute_Reference (Loc,
2653                                     Prefix => Duplicate_Subexpr (Pref),
2654                                    Attribute_Name => Name_Last,
2655                                     Expressions => New_List (
2656                                       Make_Integer_Literal (Loc, Xnum))))),
2657
2658                             Right_Opnd =>
2659                               Make_Attribute_Reference (Loc,
2660                                 Prefix => New_Occurrence_Of (Ityp, Loc),
2661                                 Attribute_Name => Name_Pos,
2662
2663                                 Expressions => New_List (
2664                                   Make_Attribute_Reference (Loc,
2665                                     Prefix =>
2666                                       Duplicate_Subexpr_No_Checks (Pref),
2667                                    Attribute_Name => Name_First,
2668                                     Expressions => New_List (
2669                                       Make_Integer_Literal (Loc, Xnum)))))),
2670
2671                         Right_Opnd => Make_Integer_Literal (Loc, 1)))));
2672
2673                Analyze_And_Resolve (N, Typ, Suppress => All_Checks);
2674                return;
2675
2676             --  If the prefix type is a constrained packed array type which
2677             --  already has a Packed_Array_Type representation defined, then
2678             --  replace this attribute with a direct reference to 'Range_Length
2679             --  of the appropriate index subtype (since otherwise the back end
2680             --  will try to give us the value of 'Length for this
2681             --  implementation type).
2682
2683             elsif Is_Constrained (Ptyp) then
2684                Rewrite (N,
2685                  Make_Attribute_Reference (Loc,
2686                    Attribute_Name => Name_Range_Length,
2687                    Prefix => New_Reference_To (Ityp, Loc)));
2688                Analyze_And_Resolve (N, Typ);
2689             end if;
2690
2691          --  Access type case
2692
2693          elsif Is_Access_Type (Ptyp) then
2694             Apply_Access_Check (N);
2695
2696             --  If the designated type is a packed array type, then we convert
2697             --  the reference to:
2698
2699             --    typ'Max (0, 1 +
2700             --                xtyp'Pos (Pref'Last (Expr)) -
2701             --                xtyp'Pos (Pref'First (Expr)));
2702
2703             --  This is a bit complex, but it is the easiest thing to do that
2704             --  works in all cases including enum types with holes xtyp here
2705             --  is the appropriate index type.
2706
2707             declare
2708                Dtyp : constant Entity_Id := Designated_Type (Ptyp);
2709                Xtyp : Entity_Id;
2710
2711             begin
2712                if Is_Array_Type (Dtyp) and then Is_Packed (Dtyp) then
2713                   Xtyp := Get_Index_Subtype (N);
2714
2715                   Rewrite (N,
2716                     Make_Attribute_Reference (Loc,
2717                       Prefix         => New_Occurrence_Of (Typ, Loc),
2718                       Attribute_Name => Name_Max,
2719                       Expressions    => New_List (
2720                         Make_Integer_Literal (Loc, 0),
2721
2722                         Make_Op_Add (Loc,
2723                           Make_Integer_Literal (Loc, 1),
2724                           Make_Op_Subtract (Loc,
2725                             Left_Opnd =>
2726                               Make_Attribute_Reference (Loc,
2727                                 Prefix => New_Occurrence_Of (Xtyp, Loc),
2728                                 Attribute_Name => Name_Pos,
2729                                 Expressions    => New_List (
2730                                   Make_Attribute_Reference (Loc,
2731                                     Prefix => Duplicate_Subexpr (Pref),
2732                                     Attribute_Name => Name_Last,
2733                                     Expressions =>
2734                                       New_Copy_List (Exprs)))),
2735
2736                             Right_Opnd =>
2737                               Make_Attribute_Reference (Loc,
2738                                 Prefix => New_Occurrence_Of (Xtyp, Loc),
2739                                 Attribute_Name => Name_Pos,
2740                                 Expressions    => New_List (
2741                                   Make_Attribute_Reference (Loc,
2742                                     Prefix =>
2743                                       Duplicate_Subexpr_No_Checks (Pref),
2744                                     Attribute_Name => Name_First,
2745                                     Expressions =>
2746                                       New_Copy_List (Exprs)))))))));
2747
2748                   Analyze_And_Resolve (N, Typ);
2749                end if;
2750             end;
2751
2752          --  Otherwise leave it to the back end
2753
2754          else
2755             Apply_Universal_Integer_Attribute_Checks (N);
2756          end if;
2757       end;
2758
2759       -------------
2760       -- Machine --
2761       -------------
2762
2763       --  Transforms 'Machine into a call to the floating-point attribute
2764       --  function Machine in Fat_xxx (where xxx is the root type)
2765
2766       when Attribute_Machine =>
2767          Expand_Fpt_Attribute_R (N);
2768
2769       ----------------------
2770       -- Machine_Rounding --
2771       ----------------------
2772
2773       --  Transforms 'Machine_Rounding into a call to the floating-point
2774       --  attribute function Machine_Rounding in Fat_xxx (where xxx is the root
2775       --  type). Expansion is avoided for cases the back end can handle
2776       --  directly.
2777
2778       when Attribute_Machine_Rounding =>
2779          if not Is_Inline_Floating_Point_Attribute (N) then
2780             Expand_Fpt_Attribute_R (N);
2781          end if;
2782
2783       ------------------
2784       -- Machine_Size --
2785       ------------------
2786
2787       --  Machine_Size is equivalent to Object_Size, so transform it into
2788       --  Object_Size and that way the back end never sees Machine_Size.
2789
2790       when Attribute_Machine_Size =>
2791          Rewrite (N,
2792            Make_Attribute_Reference (Loc,
2793              Prefix => Prefix (N),
2794              Attribute_Name => Name_Object_Size));
2795
2796          Analyze_And_Resolve (N, Typ);
2797
2798       --------------
2799       -- Mantissa --
2800       --------------
2801
2802       --  The only case that can get this far is the dynamic case of the old
2803       --  Ada 83 Mantissa attribute for the fixed-point case. For this case,
2804       --  we expand:
2805
2806       --    typ'Mantissa
2807
2808       --  into
2809
2810       --    ityp (System.Mantissa.Mantissa_Value
2811       --           (Integer'Integer_Value (typ'First),
2812       --            Integer'Integer_Value (typ'Last)));
2813
2814       when Attribute_Mantissa => Mantissa : begin
2815          Rewrite (N,
2816            Convert_To (Typ,
2817              Make_Function_Call (Loc,
2818                Name => New_Occurrence_Of (RTE (RE_Mantissa_Value), Loc),
2819
2820                Parameter_Associations => New_List (
2821
2822                  Make_Attribute_Reference (Loc,
2823                    Prefix => New_Occurrence_Of (Standard_Integer, Loc),
2824                    Attribute_Name => Name_Integer_Value,
2825                    Expressions => New_List (
2826
2827                      Make_Attribute_Reference (Loc,
2828                        Prefix => New_Occurrence_Of (Ptyp, Loc),
2829                        Attribute_Name => Name_First))),
2830
2831                  Make_Attribute_Reference (Loc,
2832                    Prefix => New_Occurrence_Of (Standard_Integer, Loc),
2833                    Attribute_Name => Name_Integer_Value,
2834                    Expressions => New_List (
2835
2836                      Make_Attribute_Reference (Loc,
2837                        Prefix => New_Occurrence_Of (Ptyp, Loc),
2838                        Attribute_Name => Name_Last)))))));
2839
2840          Analyze_And_Resolve (N, Typ);
2841       end Mantissa;
2842
2843       --------------------
2844       -- Mechanism_Code --
2845       --------------------
2846
2847       when Attribute_Mechanism_Code =>
2848
2849          --  We must replace the prefix in the renamed case
2850
2851          if Is_Entity_Name (Pref)
2852            and then Present (Alias (Entity (Pref)))
2853          then
2854             Set_Renamed_Subprogram (Pref, Alias (Entity (Pref)));
2855          end if;
2856
2857       ---------
2858       -- Mod --
2859       ---------
2860
2861       when Attribute_Mod => Mod_Case : declare
2862          Arg  : constant Node_Id := Relocate_Node (First (Exprs));
2863          Hi   : constant Node_Id := Type_High_Bound (Etype (Arg));
2864          Modv : constant Uint    := Modulus (Btyp);
2865
2866       begin
2867
2868          --  This is not so simple. The issue is what type to use for the
2869          --  computation of the modular value.
2870
2871          --  The easy case is when the modulus value is within the bounds
2872          --  of the signed integer type of the argument. In this case we can
2873          --  just do the computation in that signed integer type, and then
2874          --  do an ordinary conversion to the target type.
2875
2876          if Modv <= Expr_Value (Hi) then
2877             Rewrite (N,
2878               Convert_To (Btyp,
2879                 Make_Op_Mod (Loc,
2880                   Left_Opnd  => Arg,
2881                   Right_Opnd => Make_Integer_Literal (Loc, Modv))));
2882
2883          --  Here we know that the modulus is larger than type'Last of the
2884          --  integer type. There are two cases to consider:
2885
2886          --    a) The integer value is non-negative. In this case, it is
2887          --    returned as the result (since it is less than the modulus).
2888
2889          --    b) The integer value is negative. In this case, we know that the
2890          --    result is modulus + value, where the value might be as small as
2891          --    -modulus. The trouble is what type do we use to do the subtract.
2892          --    No type will do, since modulus can be as big as 2**64, and no
2893          --    integer type accommodates this value. Let's do bit of algebra
2894
2895          --         modulus + value
2896          --      =  modulus - (-value)
2897          --      =  (modulus - 1) - (-value - 1)
2898
2899          --    Now modulus - 1 is certainly in range of the modular type.
2900          --    -value is in the range 1 .. modulus, so -value -1 is in the
2901          --    range 0 .. modulus-1 which is in range of the modular type.
2902          --    Furthermore, (-value - 1) can be expressed as -(value + 1)
2903          --    which we can compute using the integer base type.
2904
2905          --  Once this is done we analyze the conditional expression without
2906          --  range checks, because we know everything is in range, and we
2907          --  want to prevent spurious warnings on either branch.
2908
2909          else
2910             Rewrite (N,
2911               Make_Conditional_Expression (Loc,
2912                 Expressions => New_List (
2913                   Make_Op_Ge (Loc,
2914                     Left_Opnd  => Duplicate_Subexpr (Arg),
2915                     Right_Opnd => Make_Integer_Literal (Loc, 0)),
2916
2917                   Convert_To (Btyp,
2918                     Duplicate_Subexpr_No_Checks (Arg)),
2919
2920                   Make_Op_Subtract (Loc,
2921                     Left_Opnd =>
2922                       Make_Integer_Literal (Loc,
2923                         Intval => Modv - 1),
2924                     Right_Opnd =>
2925                       Convert_To (Btyp,
2926                         Make_Op_Minus (Loc,
2927                           Right_Opnd =>
2928                             Make_Op_Add (Loc,
2929                               Left_Opnd  => Duplicate_Subexpr_No_Checks (Arg),
2930                               Right_Opnd =>
2931                                 Make_Integer_Literal (Loc,
2932                                   Intval => 1))))))));
2933
2934          end if;
2935
2936          Analyze_And_Resolve (N, Btyp, Suppress => All_Checks);
2937       end Mod_Case;
2938
2939       -----------
2940       -- Model --
2941       -----------
2942
2943       --  Transforms 'Model into a call to the floating-point attribute
2944       --  function Model in Fat_xxx (where xxx is the root type)
2945
2946       when Attribute_Model =>
2947          Expand_Fpt_Attribute_R (N);
2948
2949       -----------------
2950       -- Object_Size --
2951       -----------------
2952
2953       --  The processing for Object_Size shares the processing for Size
2954
2955       ---------
2956       -- Old --
2957       ---------
2958
2959       when Attribute_Old => Old : declare
2960          Tnn     : constant Entity_Id :=
2961                      Make_Defining_Identifier (Loc,
2962                        Chars => New_Internal_Name ('T'));
2963          Subp    : Node_Id;
2964          Asn_Stm : Node_Id;
2965
2966       begin
2967          --  Find the nearest subprogram body, ignoring _Preconditions
2968
2969          Subp := N;
2970          loop
2971             Subp := Parent (Subp);
2972             exit when Nkind (Subp) = N_Subprogram_Body
2973               and then Chars (Defining_Entity (Subp)) /= Name_uPostconditions;
2974          end loop;
2975
2976          --  Insert the assignment at the start of the declarations
2977
2978          Asn_Stm :=
2979            Make_Object_Declaration (Loc,
2980              Defining_Identifier => Tnn,
2981              Constant_Present    => True,
2982              Object_Definition   => New_Occurrence_Of (Etype (N), Loc),
2983              Expression          => Pref);
2984
2985          if Is_Empty_List (Declarations (Subp)) then
2986             Set_Declarations (Subp, New_List (Asn_Stm));
2987             Analyze (Asn_Stm);
2988          else
2989             Insert_Action (First (Declarations (Subp)), Asn_Stm);
2990          end if;
2991
2992          Rewrite (N, New_Occurrence_Of (Tnn, Loc));
2993       end Old;
2994
2995       ------------
2996       -- Output --
2997       ------------
2998
2999       when Attribute_Output => Output : declare
3000          P_Type : constant Entity_Id := Entity (Pref);
3001          U_Type : constant Entity_Id := Underlying_Type (P_Type);
3002          Pname  : Entity_Id;
3003          Decl   : Node_Id;
3004          Prag   : Node_Id;
3005          Arg3   : Node_Id;
3006          Wfunc  : Node_Id;
3007
3008       begin
3009          --  If no underlying type, we have an error that will be diagnosed
3010          --  elsewhere, so here we just completely ignore the expansion.
3011
3012          if No (U_Type) then
3013             return;
3014          end if;
3015
3016          --  If TSS for Output is present, just call it
3017
3018          Pname := Find_Stream_Subprogram (P_Type, TSS_Stream_Output);
3019
3020          if Present (Pname) then
3021             null;
3022
3023          else
3024             --  If there is a Stream_Convert pragma, use it, we rewrite
3025
3026             --     sourcetyp'Output (stream, Item)
3027
3028             --  as
3029
3030             --     strmtyp'Output (Stream, strmwrite (acttyp (Item)));
3031
3032             --  where strmwrite is the given Write function that converts an
3033             --  argument of type sourcetyp or a type acctyp, from which it is
3034             --  derived to type strmtyp. The conversion to acttyp is required
3035             --  for the derived case.
3036
3037             Prag := Get_Stream_Convert_Pragma (P_Type);
3038
3039             if Present (Prag) then
3040                Arg3 :=
3041                  Next (Next (First (Pragma_Argument_Associations (Prag))));
3042                Wfunc := Entity (Expression (Arg3));
3043
3044                Rewrite (N,
3045                  Make_Attribute_Reference (Loc,
3046                    Prefix => New_Occurrence_Of (Etype (Wfunc), Loc),
3047                    Attribute_Name => Name_Output,
3048                    Expressions => New_List (
3049                    Relocate_Node (First (Exprs)),
3050                      Make_Function_Call (Loc,
3051                        Name => New_Occurrence_Of (Wfunc, Loc),
3052                        Parameter_Associations => New_List (
3053                          OK_Convert_To (Etype (First_Formal (Wfunc)),
3054                            Relocate_Node (Next (First (Exprs)))))))));
3055
3056                Analyze (N);
3057                return;
3058
3059             --  For elementary types, we call the W_xxx routine directly.
3060             --  Note that the effect of Write and Output is identical for
3061             --  the case of an elementary type, since there are no
3062             --  discriminants or bounds.
3063
3064             elsif Is_Elementary_Type (U_Type) then
3065
3066                --  A special case arises if we have a defined _Write routine,
3067                --  since in this case we are required to call this routine.
3068
3069                if Present (TSS (Base_Type (U_Type), TSS_Stream_Write)) then
3070                   Build_Record_Or_Elementary_Output_Procedure
3071                     (Loc, U_Type, Decl, Pname);
3072                   Insert_Action (N, Decl);
3073
3074                --  For normal cases, we call the W_xxx routine directly
3075
3076                else
3077                   Rewrite (N, Build_Elementary_Write_Call (N));
3078                   Analyze (N);
3079                   return;
3080                end if;
3081
3082             --  Array type case
3083
3084             elsif Is_Array_Type (U_Type) then
3085                Build_Array_Output_Procedure (Loc, U_Type, Decl, Pname);
3086                Compile_Stream_Body_In_Scope (N, Decl, U_Type, Check => False);
3087
3088             --  Class-wide case, first output external tag, then dispatch
3089             --  to the appropriate primitive Output function (RM 13.13.2(31)).
3090
3091             elsif Is_Class_Wide_Type (P_Type) then
3092
3093                --  No need to do anything else compiling under restriction
3094                --  No_Dispatching_Calls. During the semantic analysis we
3095                --  already notified such violation.
3096
3097                if Restriction_Active (No_Dispatching_Calls) then
3098                   return;
3099                end if;
3100
3101                Tag_Write : declare
3102                   Strm : constant Node_Id := First (Exprs);
3103                   Item : constant Node_Id := Next (Strm);
3104
3105                begin
3106                   --  Ada 2005 (AI-344): Check that the accessibility level
3107                   --  of the type of the output object is not deeper than
3108                   --  that of the attribute's prefix type.
3109
3110                   --  if Get_Access_Level (Item'Tag)
3111                   --       /= Get_Access_Level (P_Type'Tag)
3112                   --  then
3113                   --     raise Tag_Error;
3114                   --  end if;
3115
3116                   --  String'Output (Strm, External_Tag (Item'Tag));
3117
3118                   --  We cannot figure out a practical way to implement this
3119                   --  accessibility check on virtual machines, so we omit it.
3120
3121                   if Ada_Version >= Ada_05
3122                     and then VM_Target = No_VM
3123                   then
3124                      Insert_Action (N,
3125                        Make_Implicit_If_Statement (N,
3126                          Condition =>
3127                            Make_Op_Ne (Loc,
3128                              Left_Opnd  =>
3129                                Build_Get_Access_Level (Loc,
3130                                  Make_Attribute_Reference (Loc,
3131                                    Prefix         =>
3132                                      Relocate_Node (
3133                                        Duplicate_Subexpr (Item,
3134                                          Name_Req => True)),
3135                                    Attribute_Name => Name_Tag)),
3136
3137                              Right_Opnd =>
3138                                Make_Integer_Literal (Loc,
3139                                  Type_Access_Level (P_Type))),
3140
3141                          Then_Statements =>
3142                            New_List (Make_Raise_Statement (Loc,
3143                                        New_Occurrence_Of (
3144                                          RTE (RE_Tag_Error), Loc)))));
3145                   end if;
3146
3147                   Insert_Action (N,
3148                     Make_Attribute_Reference (Loc,
3149                       Prefix => New_Occurrence_Of (Standard_String, Loc),
3150                       Attribute_Name => Name_Output,
3151                       Expressions => New_List (
3152                         Relocate_Node (Duplicate_Subexpr (Strm)),
3153                         Make_Function_Call (Loc,
3154                           Name =>
3155                             New_Occurrence_Of (RTE (RE_External_Tag), Loc),
3156                           Parameter_Associations => New_List (
3157                            Make_Attribute_Reference (Loc,
3158                              Prefix =>
3159                                Relocate_Node
3160                                  (Duplicate_Subexpr (Item, Name_Req => True)),
3161                              Attribute_Name => Name_Tag))))));
3162                end Tag_Write;
3163
3164                Pname := Find_Prim_Op (U_Type, TSS_Stream_Output);
3165
3166             --  Tagged type case, use the primitive Output function
3167
3168             elsif Is_Tagged_Type (U_Type) then
3169                Pname := Find_Prim_Op (U_Type, TSS_Stream_Output);
3170
3171             --  All other record type cases, including protected records.
3172             --  The latter only arise for expander generated code for
3173             --  handling shared passive partition access.
3174
3175             else
3176                pragma Assert
3177                  (Is_Record_Type (U_Type) or else Is_Protected_Type (U_Type));
3178
3179                --  Ada 2005 (AI-216): Program_Error is raised when executing
3180                --  the default implementation of the Output attribute of an
3181                --  unchecked union type if the type lacks default discriminant
3182                --  values.
3183
3184                if Is_Unchecked_Union (Base_Type (U_Type))
3185                  and then No (Discriminant_Constraint (U_Type))
3186                then
3187                   Insert_Action (N,
3188                     Make_Raise_Program_Error (Loc,
3189                       Reason => PE_Unchecked_Union_Restriction));
3190
3191                   return;
3192                end if;
3193
3194                Build_Record_Or_Elementary_Output_Procedure
3195                  (Loc, Base_Type (U_Type), Decl, Pname);
3196                Insert_Action (N, Decl);
3197             end if;
3198          end if;
3199
3200          --  If we fall through, Pname is the name of the procedure to call
3201
3202          Rewrite_Stream_Proc_Call (Pname);
3203       end Output;
3204
3205       ---------
3206       -- Pos --
3207       ---------
3208
3209       --  For enumeration types with a standard representation, Pos is
3210       --  handled by the back end.
3211
3212       --  For enumeration types, with a non-standard representation we
3213       --  generate a call to the _Rep_To_Pos function created when the
3214       --  type was frozen. The call has the form
3215
3216       --    _rep_to_pos (expr, flag)
3217
3218       --  The parameter flag is True if range checks are enabled, causing
3219       --  Program_Error to be raised if the expression has an invalid
3220       --  representation, and False if range checks are suppressed.
3221
3222       --  For integer types, Pos is equivalent to a simple integer
3223       --  conversion and we rewrite it as such
3224
3225       when Attribute_Pos => Pos :
3226       declare
3227          Etyp : Entity_Id := Base_Type (Entity (Pref));
3228
3229       begin
3230          --  Deal with zero/non-zero boolean values
3231
3232          if Is_Boolean_Type (Etyp) then
3233             Adjust_Condition (First (Exprs));
3234             Etyp := Standard_Boolean;
3235             Set_Prefix (N, New_Occurrence_Of (Standard_Boolean, Loc));
3236          end if;
3237
3238          --  Case of enumeration type
3239
3240          if Is_Enumeration_Type (Etyp) then
3241
3242             --  Non-standard enumeration type (generate call)
3243
3244             if Present (Enum_Pos_To_Rep (Etyp)) then
3245                Append_To (Exprs, Rep_To_Pos_Flag (Etyp, Loc));
3246                Rewrite (N,
3247                  Convert_To (Typ,
3248                    Make_Function_Call (Loc,
3249                      Name =>
3250                        New_Reference_To (TSS (Etyp, TSS_Rep_To_Pos), Loc),
3251                      Parameter_Associations => Exprs)));
3252
3253                Analyze_And_Resolve (N, Typ);
3254
3255             --  Standard enumeration type (do universal integer check)
3256
3257             else
3258                Apply_Universal_Integer_Attribute_Checks (N);
3259             end if;
3260
3261          --  Deal with integer types (replace by conversion)
3262
3263          elsif Is_Integer_Type (Etyp) then
3264             Rewrite (N, Convert_To (Typ, First (Exprs)));
3265             Analyze_And_Resolve (N, Typ);
3266          end if;
3267
3268       end Pos;
3269
3270       --------------
3271       -- Position --
3272       --------------
3273
3274       --  We compute this if a component clause was present, otherwise we leave
3275       --  the computation up to the back end, since we don't know what layout
3276       --  will be chosen.
3277
3278       when Attribute_Position => Position :
3279       declare
3280          CE : constant Entity_Id := Entity (Selector_Name (Pref));
3281
3282       begin
3283          if Present (Component_Clause (CE)) then
3284             Rewrite (N,
3285               Make_Integer_Literal (Loc,
3286                 Intval => Component_Bit_Offset (CE) / System_Storage_Unit));
3287             Analyze_And_Resolve (N, Typ);
3288
3289          else
3290             Apply_Universal_Integer_Attribute_Checks (N);
3291          end if;
3292       end Position;
3293
3294       ----------
3295       -- Pred --
3296       ----------
3297
3298       --  1. Deal with enumeration types with holes
3299       --  2. For floating-point, generate call to attribute function
3300       --  3. For other cases, deal with constraint checking
3301
3302       when Attribute_Pred => Pred :
3303       declare
3304          Etyp : constant Entity_Id := Base_Type (Ptyp);
3305
3306       begin
3307
3308          --  For enumeration types with non-standard representations, we
3309          --  expand typ'Pred (x) into
3310
3311          --    Pos_To_Rep (Rep_To_Pos (x) - 1)
3312
3313          --    If the representation is contiguous, we compute instead
3314          --    Lit1 + Rep_to_Pos (x -1), to catch invalid representations.
3315          --    The conversion function Enum_Pos_To_Rep is defined on the
3316          --    base type, not the subtype, so we have to use the base type
3317          --    explicitly for this and other enumeration attributes.
3318
3319          if Is_Enumeration_Type (Ptyp)
3320            and then Present (Enum_Pos_To_Rep (Etyp))
3321          then
3322             if Has_Contiguous_Rep (Etyp) then
3323                Rewrite (N,
3324                   Unchecked_Convert_To (Ptyp,
3325                      Make_Op_Add (Loc,
3326                         Left_Opnd  =>
3327                          Make_Integer_Literal (Loc,
3328                            Enumeration_Rep (First_Literal (Ptyp))),
3329                         Right_Opnd =>
3330                           Make_Function_Call (Loc,
3331                             Name =>
3332                               New_Reference_To
3333                                (TSS (Etyp, TSS_Rep_To_Pos), Loc),
3334
3335                             Parameter_Associations =>
3336                               New_List (
3337                                 Unchecked_Convert_To (Ptyp,
3338                                   Make_Op_Subtract (Loc,
3339                                     Left_Opnd =>
3340                                      Unchecked_Convert_To (Standard_Integer,
3341                                        Relocate_Node (First (Exprs))),
3342                                     Right_Opnd =>
3343                                       Make_Integer_Literal (Loc, 1))),
3344                                 Rep_To_Pos_Flag (Ptyp, Loc))))));
3345
3346             else
3347                --  Add Boolean parameter True, to request program errror if
3348                --  we have a bad representation on our hands. If checks are
3349                --  suppressed, then add False instead
3350
3351                Append_To (Exprs, Rep_To_Pos_Flag (Ptyp, Loc));
3352                Rewrite (N,
3353                  Make_Indexed_Component (Loc,
3354                    Prefix =>
3355                      New_Reference_To
3356                        (Enum_Pos_To_Rep (Etyp), Loc),
3357                    Expressions => New_List (
3358                      Make_Op_Subtract (Loc,
3359                     Left_Opnd =>
3360                       Make_Function_Call (Loc,
3361                         Name =>
3362                           New_Reference_To
3363                             (TSS (Etyp, TSS_Rep_To_Pos), Loc),
3364                           Parameter_Associations => Exprs),
3365                     Right_Opnd => Make_Integer_Literal (Loc, 1)))));
3366             end if;
3367
3368             Analyze_And_Resolve (N, Typ);
3369
3370          --  For floating-point, we transform 'Pred into a call to the Pred
3371          --  floating-point attribute function in Fat_xxx (xxx is root type)
3372
3373          elsif Is_Floating_Point_Type (Ptyp) then
3374             Expand_Fpt_Attribute_R (N);
3375             Analyze_And_Resolve (N, Typ);
3376
3377          --  For modular types, nothing to do (no overflow, since wraps)
3378
3379          elsif Is_Modular_Integer_Type (Ptyp) then
3380             null;
3381
3382          --  For other types, if range checking is enabled, we must generate
3383          --  a check if overflow checking is enabled.
3384
3385          elsif not Overflow_Checks_Suppressed (Ptyp) then
3386             Expand_Pred_Succ (N);
3387          end if;
3388       end Pred;
3389
3390       --------------
3391       -- Priority --
3392       --------------
3393
3394       --  Ada 2005 (AI-327): Dynamic ceiling priorities
3395
3396       --  We rewrite X'Priority as the following run-time call:
3397
3398       --     Get_Ceiling (X._Object)
3399
3400       --  Note that although X'Priority is notionally an object, it is quite
3401       --  deliberately not defined as an aliased object in the RM. This means
3402       --  that it works fine to rewrite it as a call, without having to worry
3403       --  about complications that would other arise from X'Priority'Access,
3404       --  which is illegal, because of the lack of aliasing.
3405
3406       when Attribute_Priority =>
3407          declare
3408             Call           : Node_Id;
3409             Conctyp        : Entity_Id;
3410             Object_Parm    : Node_Id;
3411             Subprg         : Entity_Id;
3412             RT_Subprg_Name : Node_Id;
3413
3414          begin
3415             --  Look for the enclosing concurrent type
3416
3417             Conctyp := Current_Scope;
3418             while not Is_Concurrent_Type (Conctyp) loop
3419                Conctyp := Scope (Conctyp);
3420             end loop;
3421
3422             pragma Assert (Is_Protected_Type (Conctyp));
3423
3424             --  Generate the actual of the call
3425
3426             Subprg := Current_Scope;
3427             while not Present (Protected_Body_Subprogram (Subprg)) loop
3428                Subprg := Scope (Subprg);
3429             end loop;
3430
3431             --  Use of 'Priority inside protected entries and barriers (in
3432             --  both cases the type of the first formal of their expanded
3433             --  subprogram is Address)
3434
3435             if Etype (First_Entity (Protected_Body_Subprogram (Subprg)))
3436               = RTE (RE_Address)
3437             then
3438                declare
3439                   New_Itype : Entity_Id;
3440
3441                begin
3442                   --  In the expansion of protected entries the type of the
3443                   --  first formal of the Protected_Body_Subprogram is an
3444                   --  Address. In order to reference the _object component
3445                   --  we generate:
3446
3447                   --    type T is access p__ptTV;
3448                   --    freeze T []
3449
3450                   New_Itype := Create_Itype (E_Access_Type, N);
3451                   Set_Etype (New_Itype, New_Itype);
3452                   Set_Directly_Designated_Type (New_Itype,
3453                     Corresponding_Record_Type (Conctyp));
3454                   Freeze_Itype (New_Itype, N);
3455
3456                   --  Generate:
3457                   --    T!(O)._object'unchecked_access
3458
3459                   Object_Parm :=
3460                     Make_Attribute_Reference (Loc,
3461                        Prefix =>
3462                          Make_Selected_Component (Loc,
3463                            Prefix =>
3464                              Unchecked_Convert_To (New_Itype,
3465                                New_Reference_To
3466                                  (First_Entity
3467                                    (Protected_Body_Subprogram (Subprg)),
3468                                   Loc)),
3469                            Selector_Name =>
3470                              Make_Identifier (Loc, Name_uObject)),
3471                        Attribute_Name => Name_Unchecked_Access);
3472                end;
3473
3474             --  Use of 'Priority inside a protected subprogram
3475
3476             else
3477                Object_Parm :=
3478                  Make_Attribute_Reference (Loc,
3479                     Prefix =>
3480                       Make_Selected_Component (Loc,
3481                         Prefix => New_Reference_To
3482                                     (First_Entity
3483                                       (Protected_Body_Subprogram (Subprg)),
3484                                        Loc),
3485                         Selector_Name =>
3486                           Make_Identifier (Loc, Name_uObject)),
3487                     Attribute_Name => Name_Unchecked_Access);
3488             end if;
3489
3490             --  Select the appropriate run-time subprogram
3491
3492             if Number_Entries (Conctyp) = 0 then
3493                RT_Subprg_Name :=
3494                  New_Reference_To (RTE (RE_Get_Ceiling), Loc);
3495             else
3496                RT_Subprg_Name :=
3497                  New_Reference_To (RTE (RO_PE_Get_Ceiling), Loc);
3498             end if;
3499
3500             Call :=
3501               Make_Function_Call (Loc,
3502                 Name => RT_Subprg_Name,
3503                 Parameter_Associations => New_List (Object_Parm));
3504
3505             Rewrite (N, Call);
3506
3507             --  Avoid the generation of extra checks on the pointer to the
3508             --  protected object.
3509
3510             Analyze_And_Resolve (N, Typ, Suppress => Access_Check);
3511          end;
3512
3513       ------------------
3514       -- Range_Length --
3515       ------------------
3516
3517       when Attribute_Range_Length => Range_Length : begin
3518          --  The only special processing required is for the case where
3519          --  Range_Length is applied to an enumeration type with holes.
3520          --  In this case we transform
3521
3522          --     X'Range_Length
3523
3524          --  to
3525
3526          --     X'Pos (X'Last) - X'Pos (X'First) + 1
3527
3528          --  So that the result reflects the proper Pos values instead
3529          --  of the underlying representations.
3530
3531          if Is_Enumeration_Type (Ptyp)
3532            and then Has_Non_Standard_Rep (Ptyp)
3533          then
3534             Rewrite (N,
3535               Make_Op_Add (Loc,
3536                 Left_Opnd =>
3537                   Make_Op_Subtract (Loc,
3538                     Left_Opnd =>
3539                       Make_Attribute_Reference (Loc,
3540                         Attribute_Name => Name_Pos,
3541                         Prefix => New_Occurrence_Of (Ptyp, Loc),
3542                         Expressions => New_List (
3543                           Make_Attribute_Reference (Loc,
3544                             Attribute_Name => Name_Last,
3545                             Prefix => New_Occurrence_Of (Ptyp, Loc)))),
3546
3547                     Right_Opnd =>
3548                       Make_Attribute_Reference (Loc,
3549                         Attribute_Name => Name_Pos,
3550                         Prefix => New_Occurrence_Of (Ptyp, Loc),
3551                         Expressions => New_List (
3552                           Make_Attribute_Reference (Loc,
3553                             Attribute_Name => Name_First,
3554                             Prefix => New_Occurrence_Of (Ptyp, Loc))))),
3555
3556                 Right_Opnd =>
3557                   Make_Integer_Literal (Loc, 1)));
3558
3559             Analyze_And_Resolve (N, Typ);
3560
3561          --  For all other cases, the attribute is handled by the back end, but
3562          --  we need to deal with the case of the range check on a universal
3563          --  integer.
3564
3565          else
3566             Apply_Universal_Integer_Attribute_Checks (N);
3567          end if;
3568       end Range_Length;
3569
3570       ----------
3571       -- Read --
3572       ----------
3573
3574       when Attribute_Read => Read : declare
3575          P_Type : constant Entity_Id := Entity (Pref);
3576          B_Type : constant Entity_Id := Base_Type (P_Type);
3577          U_Type : constant Entity_Id := Underlying_Type (P_Type);
3578          Pname  : Entity_Id;
3579          Decl   : Node_Id;
3580          Prag   : Node_Id;
3581          Arg2   : Node_Id;
3582          Rfunc  : Node_Id;
3583          Lhs    : Node_Id;
3584          Rhs    : Node_Id;
3585
3586       begin
3587          --  If no underlying type, we have an error that will be diagnosed
3588          --  elsewhere, so here we just completely ignore the expansion.
3589
3590          if No (U_Type) then
3591             return;
3592          end if;
3593
3594          --  The simple case, if there is a TSS for Read, just call it
3595
3596          Pname := Find_Stream_Subprogram (P_Type, TSS_Stream_Read);
3597
3598          if Present (Pname) then
3599             null;
3600
3601          else
3602             --  If there is a Stream_Convert pragma, use it, we rewrite
3603
3604             --     sourcetyp'Read (stream, Item)
3605
3606             --  as
3607
3608             --     Item := sourcetyp (strmread (strmtyp'Input (Stream)));
3609
3610             --  where strmread is the given Read function that converts an
3611             --  argument of type strmtyp to type sourcetyp or a type from which
3612             --  it is derived. The conversion to sourcetyp is required in the
3613             --  latter case.
3614
3615             --  A special case arises if Item is a type conversion in which
3616             --  case, we have to expand to:
3617
3618             --     Itemx := typex (strmread (strmtyp'Input (Stream)));
3619
3620             --  where Itemx is the expression of the type conversion (i.e.
3621             --  the actual object), and typex is the type of Itemx.
3622
3623             Prag := Get_Stream_Convert_Pragma (P_Type);
3624
3625             if Present (Prag) then
3626                Arg2  := Next (First (Pragma_Argument_Associations (Prag)));
3627                Rfunc := Entity (Expression (Arg2));
3628                Lhs := Relocate_Node (Next (First (Exprs)));
3629                Rhs :=
3630                  OK_Convert_To (B_Type,
3631                    Make_Function_Call (Loc,
3632                      Name => New_Occurrence_Of (Rfunc, Loc),
3633                      Parameter_Associations => New_List (
3634                        Make_Attribute_Reference (Loc,
3635                          Prefix =>
3636                            New_Occurrence_Of
3637                              (Etype (First_Formal (Rfunc)), Loc),
3638                          Attribute_Name => Name_Input,
3639                          Expressions => New_List (
3640                            Relocate_Node (First (Exprs)))))));
3641
3642                if Nkind (Lhs) = N_Type_Conversion then
3643                   Lhs := Expression (Lhs);
3644                   Rhs := Convert_To (Etype (Lhs), Rhs);
3645                end if;
3646
3647                Rewrite (N,
3648                  Make_Assignment_Statement (Loc,
3649                    Name       => Lhs,
3650                    Expression => Rhs));
3651                Set_Assignment_OK (Lhs);
3652                Analyze (N);
3653                return;
3654
3655             --  For elementary types, we call the I_xxx routine using the first
3656             --  parameter and then assign the result into the second parameter.
3657             --  We set Assignment_OK to deal with the conversion case.
3658
3659             elsif Is_Elementary_Type (U_Type) then
3660                declare
3661                   Lhs : Node_Id;
3662                   Rhs : Node_Id;
3663
3664                begin
3665                   Lhs := Relocate_Node (Next (First (Exprs)));
3666                   Rhs := Build_Elementary_Input_Call (N);
3667
3668                   if Nkind (Lhs) = N_Type_Conversion then
3669                      Lhs := Expression (Lhs);
3670                      Rhs := Convert_To (Etype (Lhs), Rhs);
3671                   end if;
3672
3673                   Set_Assignment_OK (Lhs);
3674
3675                   Rewrite (N,
3676                     Make_Assignment_Statement (Loc,
3677                       Name => Lhs,
3678                       Expression => Rhs));
3679
3680                   Analyze (N);
3681                   return;
3682                end;
3683
3684             --  Array type case
3685
3686             elsif Is_Array_Type (U_Type) then
3687                Build_Array_Read_Procedure (N, U_Type, Decl, Pname);
3688                Compile_Stream_Body_In_Scope (N, Decl, U_Type, Check => False);
3689
3690             --  Tagged type case, use the primitive Read function. Note that
3691             --  this will dispatch in the class-wide case which is what we want
3692
3693             elsif Is_Tagged_Type (U_Type) then
3694                Pname := Find_Prim_Op (U_Type, TSS_Stream_Read);
3695
3696             --  All other record type cases, including protected records. The
3697             --  latter only arise for expander generated code for handling
3698             --  shared passive partition access.
3699
3700             else
3701                pragma Assert
3702                  (Is_Record_Type (U_Type) or else Is_Protected_Type (U_Type));
3703
3704                --  Ada 2005 (AI-216): Program_Error is raised when executing
3705                --  the default implementation of the Read attribute of an
3706                --  Unchecked_Union type.
3707
3708                if Is_Unchecked_Union (Base_Type (U_Type)) then
3709                   Insert_Action (N,
3710                     Make_Raise_Program_Error (Loc,
3711                       Reason => PE_Unchecked_Union_Restriction));
3712                end if;
3713
3714                if Has_Discriminants (U_Type)
3715                  and then Present
3716                    (Discriminant_Default_Value (First_Discriminant (U_Type)))
3717                then
3718                   Build_Mutable_Record_Read_Procedure
3719                     (Loc, Base_Type (U_Type), Decl, Pname);
3720                else
3721                   Build_Record_Read_Procedure
3722                     (Loc, Base_Type (U_Type), Decl, Pname);
3723                end if;
3724
3725                --  Suppress checks, uninitialized or otherwise invalid
3726                --  data does not cause constraint errors to be raised for
3727                --  a complete record read.
3728
3729                Insert_Action (N, Decl, All_Checks);
3730             end if;
3731          end if;
3732
3733          Rewrite_Stream_Proc_Call (Pname);
3734       end Read;
3735
3736       ---------------
3737       -- Remainder --
3738       ---------------
3739
3740       --  Transforms 'Remainder into a call to the floating-point attribute
3741       --  function Remainder in Fat_xxx (where xxx is the root type)
3742
3743       when Attribute_Remainder =>
3744          Expand_Fpt_Attribute_RR (N);
3745
3746       ------------
3747       -- Result --
3748       ------------
3749
3750       --  Transform 'Result into reference to _Result formal. At the point
3751       --  where a legal 'Result attribute is expanded, we know that we are in
3752       --  the context of a _Postcondition function with a _Result parameter.
3753
3754       when Attribute_Result =>
3755          Rewrite (N,
3756            Make_Identifier (Loc,
3757             Chars => Name_uResult));
3758          Analyze_And_Resolve (N, Typ);
3759
3760       -----------
3761       -- Round --
3762       -----------
3763
3764       --  The handling of the Round attribute is quite delicate. The processing
3765       --  in Sem_Attr introduced a conversion to universal real, reflecting the
3766       --  semantics of Round, but we do not want anything to do with universal
3767       --  real at runtime, since this corresponds to using floating-point
3768       --  arithmetic.
3769
3770       --  What we have now is that the Etype of the Round attribute correctly
3771       --  indicates the final result type. The operand of the Round is the
3772       --  conversion to universal real, described above, and the operand of
3773       --  this conversion is the actual operand of Round, which may be the
3774       --  special case of a fixed point multiplication or division (Etype =
3775       --  universal fixed)
3776
3777       --  The exapander will expand first the operand of the conversion, then
3778       --  the conversion, and finally the round attribute itself, since we
3779       --  always work inside out. But we cannot simply process naively in this
3780       --  order. In the semantic world where universal fixed and real really
3781       --  exist and have infinite precision, there is no problem, but in the
3782       --  implementation world, where universal real is a floating-point type,
3783       --  we would get the wrong result.
3784
3785       --  So the approach is as follows. First, when expanding a multiply or
3786       --  divide whose type is universal fixed, we do nothing at all, instead
3787       --  deferring the operation till later.
3788
3789       --  The actual processing is done in Expand_N_Type_Conversion which
3790       --  handles the special case of Round by looking at its parent to see if
3791       --  it is a Round attribute, and if it is, handling the conversion (or
3792       --  its fixed multiply/divide child) in an appropriate manner.
3793
3794       --  This means that by the time we get to expanding the Round attribute
3795       --  itself, the Round is nothing more than a type conversion (and will
3796       --  often be a null type conversion), so we just replace it with the
3797       --  appropriate conversion operation.
3798
3799       when Attribute_Round =>
3800          Rewrite (N,
3801            Convert_To (Etype (N), Relocate_Node (First (Exprs))));
3802          Analyze_And_Resolve (N);
3803
3804       --------------
3805       -- Rounding --
3806       --------------
3807
3808       --  Transforms 'Rounding into a call to the floating-point attribute
3809       --  function Rounding in Fat_xxx (where xxx is the root type)
3810
3811       when Attribute_Rounding =>
3812          Expand_Fpt_Attribute_R (N);
3813
3814       -------------
3815       -- Scaling --
3816       -------------
3817
3818       --  Transforms 'Scaling into a call to the floating-point attribute
3819       --  function Scaling in Fat_xxx (where xxx is the root type)
3820
3821       when Attribute_Scaling =>
3822          Expand_Fpt_Attribute_RI (N);
3823
3824       ----------
3825       -- Size --
3826       ----------
3827
3828       when Attribute_Size        |
3829            Attribute_Object_Size |
3830            Attribute_Value_Size  |
3831            Attribute_VADS_Size   => Size :
3832
3833       declare
3834          Siz      : Uint;
3835          New_Node : Node_Id;
3836
3837       begin
3838          --  Processing for VADS_Size case. Note that this processing removes
3839          --  all traces of VADS_Size from the tree, and completes all required
3840          --  processing for VADS_Size by translating the attribute reference
3841          --  to an appropriate Size or Object_Size reference.
3842
3843          if Id = Attribute_VADS_Size
3844            or else (Use_VADS_Size and then Id = Attribute_Size)
3845          then
3846             --  If the size is specified, then we simply use the specified
3847             --  size. This applies to both types and objects. The size of an
3848             --  object can be specified in the following ways:
3849
3850             --    An explicit size object is given for an object
3851             --    A component size is specified for an indexed component
3852             --    A component clause is specified for a selected component
3853             --    The object is a component of a packed composite object
3854
3855             --  If the size is specified, then VADS_Size of an object
3856
3857             if (Is_Entity_Name (Pref)
3858                  and then Present (Size_Clause (Entity (Pref))))
3859               or else
3860                 (Nkind (Pref) = N_Component_Clause
3861                   and then (Present (Component_Clause
3862                                      (Entity (Selector_Name (Pref))))
3863                              or else Is_Packed (Etype (Prefix (Pref)))))
3864               or else
3865                 (Nkind (Pref) = N_Indexed_Component
3866                   and then (Component_Size (Etype (Prefix (Pref))) /= 0
3867                              or else Is_Packed (Etype (Prefix (Pref)))))
3868             then
3869                Set_Attribute_Name (N, Name_Size);
3870
3871             --  Otherwise if we have an object rather than a type, then the
3872             --  VADS_Size attribute applies to the type of the object, rather
3873             --  than the object itself. This is one of the respects in which
3874             --  VADS_Size differs from Size.
3875
3876             else
3877                if (not Is_Entity_Name (Pref)
3878                     or else not Is_Type (Entity (Pref)))
3879                  and then (Is_Scalar_Type (Ptyp) or else Is_Constrained (Ptyp))
3880                then
3881                   Rewrite (Pref, New_Occurrence_Of (Ptyp, Loc));
3882                end if;
3883
3884                --  For a scalar type for which no size was explicitly given,
3885                --  VADS_Size means Object_Size. This is the other respect in
3886                --  which VADS_Size differs from Size.
3887
3888                if Is_Scalar_Type (Ptyp) and then No (Size_Clause (Ptyp)) then
3889                   Set_Attribute_Name (N, Name_Object_Size);
3890
3891                --  In all other cases, Size and VADS_Size are the sane
3892
3893                else
3894                   Set_Attribute_Name (N, Name_Size);
3895                end if;
3896             end if;
3897          end if;
3898
3899          --  For class-wide types, X'Class'Size is transformed into a direct
3900          --  reference to the Size of the class type, so that the back end does
3901          --  not have to deal with the X'Class'Size reference.
3902
3903          if Is_Entity_Name (Pref)
3904            and then Is_Class_Wide_Type (Entity (Pref))
3905          then
3906             Rewrite (Prefix (N), New_Occurrence_Of (Entity (Pref), Loc));
3907             return;
3908
3909          --  For X'Size applied to an object of a class-wide type, transform
3910          --  X'Size into a call to the primitive operation _Size applied to X.
3911
3912          elsif Is_Class_Wide_Type (Ptyp) then
3913
3914             --  No need to do anything else compiling under restriction
3915             --  No_Dispatching_Calls. During the semantic analysis we
3916             --  already notified such violation.
3917
3918             if Restriction_Active (No_Dispatching_Calls) then
3919                return;
3920             end if;
3921
3922             New_Node :=
3923               Make_Function_Call (Loc,
3924                 Name => New_Reference_To
3925                   (Find_Prim_Op (Ptyp, Name_uSize), Loc),
3926                 Parameter_Associations => New_List (Pref));
3927
3928             if Typ /= Standard_Long_Long_Integer then
3929
3930                --  The context is a specific integer type with which the
3931                --  original attribute was compatible. The function has a
3932                --  specific type as well, so to preserve the compatibility
3933                --  we must convert explicitly.
3934
3935                New_Node := Convert_To (Typ, New_Node);
3936             end if;
3937
3938             Rewrite (N, New_Node);
3939             Analyze_And_Resolve (N, Typ);
3940                return;
3941
3942          --  Case of known RM_Size of a type
3943
3944          elsif (Id = Attribute_Size or else Id = Attribute_Value_Size)
3945            and then Is_Entity_Name (Pref)
3946            and then Is_Type (Entity (Pref))
3947            and then Known_Static_RM_Size (Entity (Pref))
3948          then
3949             Siz := RM_Size (Entity (Pref));
3950
3951          --  Case of known Esize of a type
3952
3953          elsif Id = Attribute_Object_Size
3954            and then Is_Entity_Name (Pref)
3955            and then Is_Type (Entity (Pref))
3956            and then Known_Static_Esize (Entity (Pref))
3957          then
3958             Siz := Esize (Entity (Pref));
3959
3960          --  Case of known size of object
3961
3962          elsif Id = Attribute_Size
3963            and then Is_Entity_Name (Pref)
3964            and then Is_Object (Entity (Pref))
3965            and then Known_Esize (Entity (Pref))
3966            and then Known_Static_Esize (Entity (Pref))
3967          then
3968             Siz := Esize (Entity (Pref));
3969
3970          --  For an array component, we can do Size in the front end
3971          --  if the component_size of the array is set.
3972
3973          elsif Nkind (Pref) = N_Indexed_Component then
3974             Siz := Component_Size (Etype (Prefix (Pref)));
3975
3976          --  For a record component, we can do Size in the front end if there
3977          --  is a component clause, or if the record is packed and the
3978          --  component's size is known at compile time.
3979
3980          elsif Nkind (Pref) = N_Selected_Component then
3981             declare
3982                Rec  : constant Entity_Id := Etype (Prefix (Pref));
3983                Comp : constant Entity_Id := Entity (Selector_Name (Pref));
3984
3985             begin
3986                if Present (Component_Clause (Comp)) then
3987                   Siz := Esize (Comp);
3988
3989                elsif Is_Packed (Rec) then
3990                   Siz := RM_Size (Ptyp);
3991
3992                else
3993                   Apply_Universal_Integer_Attribute_Checks (N);
3994                   return;
3995                end if;
3996             end;
3997
3998          --  All other cases are handled by the back end
3999
4000          else
4001             Apply_Universal_Integer_Attribute_Checks (N);
4002
4003             --  If Size is applied to a formal parameter that is of a packed
4004             --  array subtype, then apply Size to the actual subtype.
4005
4006             if Is_Entity_Name (Pref)
4007               and then Is_Formal (Entity (Pref))
4008               and then Is_Array_Type (Ptyp)
4009               and then Is_Packed (Ptyp)
4010             then
4011                Rewrite (N,
4012                  Make_Attribute_Reference (Loc,
4013                    Prefix =>
4014                      New_Occurrence_Of (Get_Actual_Subtype (Pref), Loc),
4015                    Attribute_Name => Name_Size));
4016                Analyze_And_Resolve (N, Typ);
4017             end if;
4018
4019             --  If Size applies to a dereference of an access to unconstrained
4020             --  packed array, the back end needs to see its unconstrained
4021             --  nominal type, but also a hint to the actual constrained type.
4022
4023             if Nkind (Pref) = N_Explicit_Dereference
4024               and then Is_Array_Type (Ptyp)
4025               and then not Is_Constrained (Ptyp)
4026               and then Is_Packed (Ptyp)
4027             then
4028                Set_Actual_Designated_Subtype (Pref,
4029                  Get_Actual_Subtype (Pref));
4030             end if;
4031
4032             return;
4033          end if;
4034
4035          --  Common processing for record and array component case
4036
4037          if Siz /= No_Uint and then Siz /= 0 then
4038             declare
4039                CS : constant Boolean := Comes_From_Source (N);
4040
4041             begin
4042                Rewrite (N, Make_Integer_Literal (Loc, Siz));
4043
4044                --  This integer literal is not a static expression. We do not
4045                --  call Analyze_And_Resolve here, because this would activate
4046                --  the circuit for deciding that a static value was out of
4047                --  range, and we don't want that.
4048
4049                --  So just manually set the type, mark the expression as non-
4050                --  static, and then ensure that the result is checked properly
4051                --  if the attribute comes from source (if it was internally
4052                --  generated, we never need a constraint check).
4053
4054                Set_Etype (N, Typ);
4055                Set_Is_Static_Expression (N, False);
4056
4057                if CS then
4058                   Apply_Constraint_Check (N, Typ);
4059                end if;
4060             end;
4061          end if;
4062       end Size;
4063
4064       ------------------
4065       -- Storage_Pool --
4066       ------------------
4067
4068       when Attribute_Storage_Pool =>
4069          Rewrite (N,
4070            Make_Type_Conversion (Loc,
4071              Subtype_Mark => New_Reference_To (Etype (N), Loc),
4072              Expression   => New_Reference_To (Entity (N), Loc)));
4073          Analyze_And_Resolve (N, Typ);
4074
4075       ------------------
4076       -- Storage_Size --
4077       ------------------
4078
4079       when Attribute_Storage_Size => Storage_Size : begin
4080
4081          --  Access type case, always go to the root type
4082
4083          --  The case of access types results in a value of zero for the case
4084          --  where no storage size attribute clause has been given. If a
4085          --  storage size has been given, then the attribute is converted
4086          --  to a reference to the variable used to hold this value.
4087
4088          if Is_Access_Type (Ptyp) then
4089             if Present (Storage_Size_Variable (Root_Type (Ptyp))) then
4090                Rewrite (N,
4091                  Make_Attribute_Reference (Loc,
4092                    Prefix => New_Reference_To (Typ, Loc),
4093                    Attribute_Name => Name_Max,
4094                    Expressions => New_List (
4095                      Make_Integer_Literal (Loc, 0),
4096                      Convert_To (Typ,
4097                        New_Reference_To
4098                          (Storage_Size_Variable (Root_Type (Ptyp)), Loc)))));
4099
4100             elsif Present (Associated_Storage_Pool (Root_Type (Ptyp))) then
4101                Rewrite (N,
4102                  OK_Convert_To (Typ,
4103                    Make_Function_Call (Loc,
4104                      Name =>
4105                        New_Reference_To
4106                          (Find_Prim_Op
4107                            (Etype (Associated_Storage_Pool (Root_Type (Ptyp))),
4108                             Attribute_Name (N)),
4109                           Loc),
4110
4111                      Parameter_Associations => New_List (
4112                        New_Reference_To
4113                          (Associated_Storage_Pool (Root_Type (Ptyp)), Loc)))));
4114
4115             else
4116                Rewrite (N, Make_Integer_Literal (Loc, 0));
4117             end if;
4118
4119             Analyze_And_Resolve (N, Typ);
4120
4121          --  For tasks, we retrieve the size directly from the TCB. The
4122          --  size may depend on a discriminant of the type, and therefore
4123          --  can be a per-object expression, so type-level information is
4124          --  not sufficient in general. There are four cases to consider:
4125
4126          --  a) If the attribute appears within a task body, the designated
4127          --    TCB is obtained by a call to Self.
4128
4129          --  b) If the prefix of the attribute is the name of a task object,
4130          --  the designated TCB is the one stored in the corresponding record.
4131
4132          --  c) If the prefix is a task type, the size is obtained from the
4133          --  size variable created for each task type
4134
4135          --  d) If no storage_size was specified for the type , there is no
4136          --  size variable, and the value is a system-specific default.
4137
4138          else
4139             if In_Open_Scopes (Ptyp) then
4140
4141                --  Storage_Size (Self)
4142
4143                Rewrite (N,
4144                  Convert_To (Typ,
4145                    Make_Function_Call (Loc,
4146                      Name =>
4147                        New_Occurrence_Of (RTE (RE_Storage_Size), Loc),
4148                      Parameter_Associations =>
4149                        New_List (
4150                          Make_Function_Call (Loc,
4151                            Name =>
4152                              New_Reference_To (RTE (RE_Self), Loc))))));
4153
4154             elsif not Is_Entity_Name (Pref)
4155               or else not Is_Type (Entity (Pref))
4156             then
4157                --  Storage_Size (Rec (Obj).Size)
4158
4159                Rewrite (N,
4160                  Convert_To (Typ,
4161                    Make_Function_Call (Loc,
4162                      Name =>
4163                        New_Occurrence_Of (RTE (RE_Storage_Size), Loc),
4164                        Parameter_Associations =>
4165                           New_List (
4166                             Make_Selected_Component (Loc,
4167                               Prefix =>
4168                                 Unchecked_Convert_To (
4169                                   Corresponding_Record_Type (Ptyp),
4170                                     New_Copy_Tree (Pref)),
4171                               Selector_Name =>
4172                                  Make_Identifier (Loc, Name_uTask_Id))))));
4173
4174             elsif Present (Storage_Size_Variable (Ptyp)) then
4175
4176                --  Static storage size pragma given for type: retrieve value
4177                --  from its allocated storage variable.
4178
4179                Rewrite (N,
4180                  Convert_To (Typ,
4181                    Make_Function_Call (Loc,
4182                      Name => New_Occurrence_Of (
4183                        RTE (RE_Adjust_Storage_Size), Loc),
4184                      Parameter_Associations =>
4185                        New_List (
4186                          New_Reference_To (
4187                            Storage_Size_Variable (Ptyp), Loc)))));
4188             else
4189                --  Get system default
4190
4191                Rewrite (N,
4192                  Convert_To (Typ,
4193                    Make_Function_Call (Loc,
4194                      Name =>
4195                        New_Occurrence_Of (
4196                         RTE (RE_Default_Stack_Size), Loc))));
4197             end if;
4198
4199             Analyze_And_Resolve (N, Typ);
4200          end if;
4201       end Storage_Size;
4202
4203       -----------------
4204       -- Stream_Size --
4205       -----------------
4206
4207       when Attribute_Stream_Size => Stream_Size : declare
4208          Size : Int;
4209
4210       begin
4211          --  If we have a Stream_Size clause for this type use it, otherwise
4212          --  the Stream_Size if the size of the type.
4213
4214          if Has_Stream_Size_Clause (Ptyp) then
4215             Size :=
4216               UI_To_Int
4217                 (Static_Integer (Expression (Stream_Size_Clause (Ptyp))));
4218          else
4219             Size := UI_To_Int (Esize (Ptyp));
4220          end if;
4221
4222          Rewrite (N, Make_Integer_Literal (Loc, Intval => Size));
4223          Analyze_And_Resolve (N, Typ);
4224       end Stream_Size;
4225
4226       ----------
4227       -- Succ --
4228       ----------
4229
4230       --  1. Deal with enumeration types with holes
4231       --  2. For floating-point, generate call to attribute function
4232       --  3. For other cases, deal with constraint checking
4233
4234       when Attribute_Succ => Succ :
4235       declare
4236          Etyp : constant Entity_Id := Base_Type (Ptyp);
4237
4238       begin
4239
4240          --  For enumeration types with non-standard representations, we
4241          --  expand typ'Succ (x) into
4242
4243          --    Pos_To_Rep (Rep_To_Pos (x) + 1)
4244
4245          --    If the representation is contiguous, we compute instead
4246          --    Lit1 + Rep_to_Pos (x+1), to catch invalid representations.
4247
4248          if Is_Enumeration_Type (Ptyp)
4249            and then Present (Enum_Pos_To_Rep (Etyp))
4250          then
4251             if Has_Contiguous_Rep (Etyp) then
4252                Rewrite (N,
4253                   Unchecked_Convert_To (Ptyp,
4254                      Make_Op_Add (Loc,
4255                         Left_Opnd  =>
4256                          Make_Integer_Literal (Loc,
4257                            Enumeration_Rep (First_Literal (Ptyp))),
4258                         Right_Opnd =>
4259                           Make_Function_Call (Loc,
4260                             Name =>
4261                               New_Reference_To
4262                                (TSS (Etyp, TSS_Rep_To_Pos), Loc),
4263
4264                             Parameter_Associations =>
4265                               New_List (
4266                                 Unchecked_Convert_To (Ptyp,
4267                                   Make_Op_Add (Loc,
4268                                   Left_Opnd =>
4269                                     Unchecked_Convert_To (Standard_Integer,
4270                                       Relocate_Node (First (Exprs))),
4271                                   Right_Opnd =>
4272                                     Make_Integer_Literal (Loc, 1))),
4273                                 Rep_To_Pos_Flag (Ptyp, Loc))))));
4274             else
4275                --  Add Boolean parameter True, to request program errror if
4276                --  we have a bad representation on our hands. Add False if
4277                --  checks are suppressed.
4278
4279                Append_To (Exprs, Rep_To_Pos_Flag (Ptyp, Loc));
4280                Rewrite (N,
4281                  Make_Indexed_Component (Loc,
4282                    Prefix =>
4283                      New_Reference_To
4284                        (Enum_Pos_To_Rep (Etyp), Loc),
4285                    Expressions => New_List (
4286                      Make_Op_Add (Loc,
4287                        Left_Opnd =>
4288                          Make_Function_Call (Loc,
4289                            Name =>
4290                              New_Reference_To
4291                                (TSS (Etyp, TSS_Rep_To_Pos), Loc),
4292                            Parameter_Associations => Exprs),
4293                        Right_Opnd => Make_Integer_Literal (Loc, 1)))));
4294             end if;
4295
4296             Analyze_And_Resolve (N, Typ);
4297
4298          --  For floating-point, we transform 'Succ into a call to the Succ
4299          --  floating-point attribute function in Fat_xxx (xxx is root type)
4300
4301          elsif Is_Floating_Point_Type (Ptyp) then
4302             Expand_Fpt_Attribute_R (N);
4303             Analyze_And_Resolve (N, Typ);
4304
4305          --  For modular types, nothing to do (no overflow, since wraps)
4306
4307          elsif Is_Modular_Integer_Type (Ptyp) then
4308             null;
4309
4310          --  For other types, if range checking is enabled, we must generate
4311          --  a check if overflow checking is enabled.
4312
4313          elsif not Overflow_Checks_Suppressed (Ptyp) then
4314             Expand_Pred_Succ (N);
4315          end if;
4316       end Succ;
4317
4318       ---------
4319       -- Tag --
4320       ---------
4321
4322       --  Transforms X'Tag into a direct reference to the tag of X
4323
4324       when Attribute_Tag => Tag :
4325       declare
4326          Ttyp           : Entity_Id;
4327          Prefix_Is_Type : Boolean;
4328
4329       begin
4330          if Is_Entity_Name (Pref) and then Is_Type (Entity (Pref)) then
4331             Ttyp := Entity (Pref);
4332             Prefix_Is_Type := True;
4333          else
4334             Ttyp := Ptyp;
4335             Prefix_Is_Type := False;
4336          end if;
4337
4338          if Is_Class_Wide_Type (Ttyp) then
4339             Ttyp := Root_Type (Ttyp);
4340          end if;
4341
4342          Ttyp := Underlying_Type (Ttyp);
4343
4344          --  Ada 2005: The type may be a synchronized tagged type, in which
4345          --  case the tag information is stored in the corresponding record.
4346
4347          if Is_Concurrent_Type (Ttyp) then
4348             Ttyp := Corresponding_Record_Type (Ttyp);
4349          end if;
4350
4351          if Prefix_Is_Type then
4352
4353             --  For VMs we leave the type attribute unexpanded because
4354             --  there's not a dispatching table to reference.
4355
4356             if VM_Target = No_VM then
4357                Rewrite (N,
4358                  Unchecked_Convert_To (RTE (RE_Tag),
4359                    New_Reference_To
4360                      (Node (First_Elmt (Access_Disp_Table (Ttyp))), Loc)));
4361                Analyze_And_Resolve (N, RTE (RE_Tag));
4362             end if;
4363
4364          --  (Ada 2005 (AI-251): The use of 'Tag in the sources always
4365          --  references the primary tag of the actual object. If 'Tag is
4366          --  applied to class-wide interface objects we generate code that
4367          --  displaces "this" to reference the base of the object.
4368
4369          elsif Comes_From_Source (N)
4370             and then Is_Class_Wide_Type (Etype (Prefix (N)))
4371             and then Is_Interface (Etype (Prefix (N)))
4372          then
4373             --  Generate:
4374             --    (To_Tag_Ptr (Prefix'Address)).all
4375
4376             --  Note that Prefix'Address is recursively expanded into a call
4377             --  to Base_Address (Obj.Tag)
4378
4379             --  Not needed for VM targets, since all handled by the VM
4380
4381             if VM_Target = No_VM then
4382                Rewrite (N,
4383                  Make_Explicit_Dereference (Loc,
4384                    Unchecked_Convert_To (RTE (RE_Tag_Ptr),
4385                      Make_Attribute_Reference (Loc,
4386                        Prefix => Relocate_Node (Pref),
4387                        Attribute_Name => Name_Address))));
4388                Analyze_And_Resolve (N, RTE (RE_Tag));
4389             end if;
4390
4391          else
4392             Rewrite (N,
4393               Make_Selected_Component (Loc,
4394                 Prefix => Relocate_Node (Pref),
4395                 Selector_Name =>
4396                   New_Reference_To (First_Tag_Component (Ttyp), Loc)));
4397             Analyze_And_Resolve (N, RTE (RE_Tag));
4398          end if;
4399       end Tag;
4400
4401       ----------------
4402       -- Terminated --
4403       ----------------
4404
4405       --  Transforms 'Terminated attribute into a call to Terminated function
4406
4407       when Attribute_Terminated => Terminated :
4408       begin
4409          --  The prefix of Terminated is of a task interface class-wide type.
4410          --  Generate:
4411
4412          --    terminated (Task_Id (Pref._disp_get_task_id));
4413
4414          if Ada_Version >= Ada_05
4415            and then Ekind (Ptyp) = E_Class_Wide_Type
4416            and then Is_Interface (Ptyp)
4417            and then Is_Task_Interface (Ptyp)
4418          then
4419             Rewrite (N,
4420               Make_Function_Call (Loc,
4421                 Name =>
4422                   New_Reference_To (RTE (RE_Terminated), Loc),
4423                 Parameter_Associations => New_List (
4424                   Make_Unchecked_Type_Conversion (Loc,
4425                     Subtype_Mark =>
4426                       New_Reference_To (RTE (RO_ST_Task_Id), Loc),
4427                     Expression =>
4428                       Make_Selected_Component (Loc,
4429                         Prefix =>
4430                           New_Copy_Tree (Pref),
4431                         Selector_Name =>
4432                           Make_Identifier (Loc, Name_uDisp_Get_Task_Id))))));
4433
4434          elsif Restricted_Profile then
4435             Rewrite (N,
4436               Build_Call_With_Task (Pref, RTE (RE_Restricted_Terminated)));
4437
4438          else
4439             Rewrite (N,
4440               Build_Call_With_Task (Pref, RTE (RE_Terminated)));
4441          end if;
4442
4443          Analyze_And_Resolve (N, Standard_Boolean);
4444       end Terminated;
4445
4446       ----------------
4447       -- To_Address --
4448       ----------------
4449
4450       --  Transforms System'To_Address (X) into unchecked conversion
4451       --  from (integral) type of X to type address.
4452
4453       when Attribute_To_Address =>
4454          Rewrite (N,
4455            Unchecked_Convert_To (RTE (RE_Address),
4456              Relocate_Node (First (Exprs))));
4457          Analyze_And_Resolve (N, RTE (RE_Address));
4458
4459       ------------
4460       -- To_Any --
4461       ------------
4462
4463       when Attribute_To_Any => To_Any : declare
4464          P_Type : constant Entity_Id := Etype (Pref);
4465          Decls  : constant List_Id   := New_List;
4466       begin
4467          Rewrite (N,
4468            Build_To_Any_Call
4469              (Convert_To (P_Type,
4470               Relocate_Node (First (Exprs))), Decls));
4471          Insert_Actions (N, Decls);
4472          Analyze_And_Resolve (N, RTE (RE_Any));
4473       end To_Any;
4474
4475       ----------------
4476       -- Truncation --
4477       ----------------
4478
4479       --  Transforms 'Truncation into a call to the floating-point attribute
4480       --  function Truncation in Fat_xxx (where xxx is the root type).
4481       --  Expansion is avoided for cases the back end can handle directly.
4482
4483       when Attribute_Truncation =>
4484          if not Is_Inline_Floating_Point_Attribute (N) then
4485             Expand_Fpt_Attribute_R (N);
4486          end if;
4487
4488       --------------
4489       -- TypeCode --
4490       --------------
4491
4492       when Attribute_TypeCode => TypeCode : declare
4493          P_Type : constant Entity_Id := Etype (Pref);
4494          Decls  : constant List_Id   := New_List;
4495       begin
4496          Rewrite (N, Build_TypeCode_Call (Loc, P_Type, Decls));
4497          Insert_Actions (N, Decls);
4498          Analyze_And_Resolve (N, RTE (RE_TypeCode));
4499       end TypeCode;
4500
4501       -----------------------
4502       -- Unbiased_Rounding --
4503       -----------------------
4504
4505       --  Transforms 'Unbiased_Rounding into a call to the floating-point
4506       --  attribute function Unbiased_Rounding in Fat_xxx (where xxx is the
4507       --  root type). Expansion is avoided for cases the back end can handle
4508       --  directly.
4509
4510       when Attribute_Unbiased_Rounding =>
4511          if not Is_Inline_Floating_Point_Attribute (N) then
4512             Expand_Fpt_Attribute_R (N);
4513          end if;
4514
4515       -----------------
4516       -- UET_Address --
4517       -----------------
4518
4519       when Attribute_UET_Address => UET_Address : declare
4520          Ent : constant Entity_Id :=
4521                  Make_Defining_Identifier (Loc, New_Internal_Name ('T'));
4522
4523       begin
4524          Insert_Action (N,
4525            Make_Object_Declaration (Loc,
4526              Defining_Identifier => Ent,
4527              Aliased_Present     => True,
4528              Object_Definition   =>
4529                New_Occurrence_Of (RTE (RE_Address), Loc)));
4530
4531          --  Construct name __gnat_xxx__SDP, where xxx is the unit name
4532          --  in normal external form.
4533
4534          Get_External_Unit_Name_String (Get_Unit_Name (Pref));
4535          Name_Buffer (1 + 7 .. Name_Len + 7) := Name_Buffer (1 .. Name_Len);
4536          Name_Len := Name_Len + 7;
4537          Name_Buffer (1 .. 7) := "__gnat_";
4538          Name_Buffer (Name_Len + 1 .. Name_Len + 5) := "__SDP";
4539          Name_Len := Name_Len + 5;
4540
4541          Set_Is_Imported (Ent);
4542          Set_Interface_Name (Ent,
4543            Make_String_Literal (Loc,
4544              Strval => String_From_Name_Buffer));
4545
4546          --  Set entity as internal to ensure proper Sprint output of its
4547          --  implicit importation.
4548
4549          Set_Is_Internal (Ent);
4550
4551          Rewrite (N,
4552            Make_Attribute_Reference (Loc,
4553              Prefix => New_Occurrence_Of (Ent, Loc),
4554              Attribute_Name => Name_Address));
4555
4556          Analyze_And_Resolve (N, Typ);
4557       end UET_Address;
4558
4559       ---------------
4560       -- VADS_Size --
4561       ---------------
4562
4563       --  The processing for VADS_Size is shared with Size
4564
4565       ---------
4566       -- Val --
4567       ---------
4568
4569       --  For enumeration types with a standard representation, and for all
4570       --  other types, Val is handled by the back end. For enumeration types
4571       --  with a non-standard representation we use the _Pos_To_Rep array that
4572       --  was created when the type was frozen.
4573
4574       when Attribute_Val => Val :
4575       declare
4576          Etyp : constant Entity_Id := Base_Type (Entity (Pref));
4577
4578       begin
4579          if Is_Enumeration_Type (Etyp)
4580            and then Present (Enum_Pos_To_Rep (Etyp))
4581          then
4582             if Has_Contiguous_Rep (Etyp) then
4583                declare
4584                   Rep_Node : constant Node_Id :=
4585                     Unchecked_Convert_To (Etyp,
4586                        Make_Op_Add (Loc,
4587                          Left_Opnd =>
4588                             Make_Integer_Literal (Loc,
4589                               Enumeration_Rep (First_Literal (Etyp))),
4590                          Right_Opnd =>
4591                           (Convert_To (Standard_Integer,
4592                              Relocate_Node (First (Exprs))))));
4593
4594                begin
4595                   Rewrite (N,
4596                      Unchecked_Convert_To (Etyp,
4597                          Make_Op_Add (Loc,
4598                            Left_Opnd =>
4599                              Make_Integer_Literal (Loc,
4600                                Enumeration_Rep (First_Literal (Etyp))),
4601                            Right_Opnd =>
4602                              Make_Function_Call (Loc,
4603                                Name =>
4604                                  New_Reference_To
4605                                    (TSS (Etyp, TSS_Rep_To_Pos), Loc),
4606                                Parameter_Associations => New_List (
4607                                  Rep_Node,
4608                                  Rep_To_Pos_Flag (Etyp, Loc))))));
4609                end;
4610
4611             else
4612                Rewrite (N,
4613                  Make_Indexed_Component (Loc,
4614                    Prefix => New_Reference_To (Enum_Pos_To_Rep (Etyp), Loc),
4615                    Expressions => New_List (
4616                      Convert_To (Standard_Integer,
4617                        Relocate_Node (First (Exprs))))));
4618             end if;
4619
4620             Analyze_And_Resolve (N, Typ);
4621          end if;
4622       end Val;
4623
4624       -----------
4625       -- Valid --
4626       -----------
4627
4628       --  The code for valid is dependent on the particular types involved.
4629       --  See separate sections below for the generated code in each case.
4630
4631       when Attribute_Valid => Valid :
4632       declare
4633          Btyp : Entity_Id := Base_Type (Ptyp);
4634          Tst  : Node_Id;
4635
4636          Save_Validity_Checks_On : constant Boolean := Validity_Checks_On;
4637          --  Save the validity checking mode. We always turn off validity
4638          --  checking during process of 'Valid since this is one place
4639          --  where we do not want the implicit validity checks to intefere
4640          --  with the explicit validity check that the programmer is doing.
4641
4642          function Make_Range_Test return Node_Id;
4643          --  Build the code for a range test of the form
4644          --    Btyp!(Pref) >= Btyp!(Ptyp'First)
4645          --      and then
4646          --    Btyp!(Pref) <= Btyp!(Ptyp'Last)
4647
4648          ---------------------
4649          -- Make_Range_Test --
4650          ---------------------
4651
4652          function Make_Range_Test return Node_Id is
4653          begin
4654             return
4655               Make_And_Then (Loc,
4656                 Left_Opnd =>
4657                   Make_Op_Ge (Loc,
4658                     Left_Opnd =>
4659                       Unchecked_Convert_To (Btyp, Duplicate_Subexpr (Pref)),
4660
4661                     Right_Opnd =>
4662                       Unchecked_Convert_To (Btyp,
4663                         Make_Attribute_Reference (Loc,
4664                           Prefix => New_Occurrence_Of (Ptyp, Loc),
4665                           Attribute_Name => Name_First))),
4666
4667                 Right_Opnd =>
4668                   Make_Op_Le (Loc,
4669                     Left_Opnd =>
4670                       Unchecked_Convert_To (Btyp,
4671                         Duplicate_Subexpr_No_Checks (Pref)),
4672
4673                     Right_Opnd =>
4674                       Unchecked_Convert_To (Btyp,
4675                         Make_Attribute_Reference (Loc,
4676                           Prefix => New_Occurrence_Of (Ptyp, Loc),
4677                           Attribute_Name => Name_Last))));
4678          end Make_Range_Test;
4679
4680       --  Start of processing for Attribute_Valid
4681
4682       begin
4683          --  Turn off validity checks. We do not want any implicit validity
4684          --  checks to intefere with the explicit check from the attribute
4685
4686          Validity_Checks_On := False;
4687
4688          --  Floating-point case. This case is handled by the Valid attribute
4689          --  code in the floating-point attribute run-time library.
4690
4691          if Is_Floating_Point_Type (Ptyp) then
4692             declare
4693                Pkg : RE_Id;
4694                Ftp : Entity_Id;
4695
4696             begin
4697                --  For vax fpt types, call appropriate routine in special vax
4698                --  floating point unit. We do not have to worry about loads in
4699                --  this case, since these types have no signalling NaN's.
4700
4701                if Vax_Float (Btyp) then
4702                   Expand_Vax_Valid (N);
4703
4704                --  The AAMP back end handles Valid for floating-point types
4705
4706                elsif Is_AAMP_Float (Btyp) then
4707                   Analyze_And_Resolve (Pref, Ptyp);
4708                   Set_Etype (N, Standard_Boolean);
4709                   Set_Analyzed (N);
4710
4711                --  Non VAX float case
4712
4713                else
4714                   Find_Fat_Info (Ptyp, Ftp, Pkg);
4715
4716                   --  If the floating-point object might be unaligned, we need
4717                   --  to call the special routine Unaligned_Valid, which makes
4718                   --  the needed copy, being careful not to load the value into
4719                   --  any floating-point register. The argument in this case is
4720                   --  obj'Address (see Unaligned_Valid routine in Fat_Gen).
4721
4722                   if Is_Possibly_Unaligned_Object (Pref) then
4723                      Expand_Fpt_Attribute
4724                        (N, Pkg, Name_Unaligned_Valid,
4725                         New_List (
4726                           Make_Attribute_Reference (Loc,
4727                             Prefix => Relocate_Node (Pref),
4728                             Attribute_Name => Name_Address)));
4729
4730                   --  In the normal case where we are sure the object is
4731                   --  aligned, we generate a call to Valid, and the argument in
4732                   --  this case is obj'Unrestricted_Access (after converting
4733                   --  obj to the right floating-point type).
4734
4735                   else
4736                      Expand_Fpt_Attribute
4737                        (N, Pkg, Name_Valid,
4738                         New_List (
4739                           Make_Attribute_Reference (Loc,
4740                             Prefix => Unchecked_Convert_To (Ftp, Pref),
4741                             Attribute_Name => Name_Unrestricted_Access)));
4742                   end if;
4743                end if;
4744
4745                --  One more task, we still need a range check. Required
4746                --  only if we have a constraint, since the Valid routine
4747                --  catches infinities properly (infinities are never valid).
4748
4749                --  The way we do the range check is simply to create the
4750                --  expression: Valid (N) and then Base_Type(Pref) in Typ.
4751
4752                if not Subtypes_Statically_Match (Ptyp, Btyp) then
4753                   Rewrite (N,
4754                     Make_And_Then (Loc,
4755                       Left_Opnd  => Relocate_Node (N),
4756                       Right_Opnd =>
4757                         Make_In (Loc,
4758                           Left_Opnd => Convert_To (Btyp, Pref),
4759                           Right_Opnd => New_Occurrence_Of (Ptyp, Loc))));
4760                end if;
4761             end;
4762
4763          --  Enumeration type with holes
4764
4765          --  For enumeration types with holes, the Pos value constructed by
4766          --  the Enum_Rep_To_Pos function built in Exp_Ch3 called with a
4767          --  second argument of False returns minus one for an invalid value,
4768          --  and the non-negative pos value for a valid value, so the
4769          --  expansion of X'Valid is simply:
4770
4771          --     type(X)'Pos (X) >= 0
4772
4773          --  We can't quite generate it that way because of the requirement
4774          --  for the non-standard second argument of False in the resulting
4775          --  rep_to_pos call, so we have to explicitly create:
4776
4777          --     _rep_to_pos (X, False) >= 0
4778
4779          --  If we have an enumeration subtype, we also check that the
4780          --  value is in range:
4781
4782          --    _rep_to_pos (X, False) >= 0
4783          --      and then
4784          --       (X >= type(X)'First and then type(X)'Last <= X)
4785
4786          elsif Is_Enumeration_Type (Ptyp)
4787            and then Present (Enum_Pos_To_Rep (Base_Type (Ptyp)))
4788          then
4789             Tst :=
4790               Make_Op_Ge (Loc,
4791                 Left_Opnd =>
4792                   Make_Function_Call (Loc,
4793                     Name =>
4794                       New_Reference_To
4795                         (TSS (Base_Type (Ptyp), TSS_Rep_To_Pos), Loc),
4796                     Parameter_Associations => New_List (
4797                       Pref,
4798                       New_Occurrence_Of (Standard_False, Loc))),
4799                 Right_Opnd => Make_Integer_Literal (Loc, 0));
4800
4801             if Ptyp /= Btyp
4802               and then
4803                 (Type_Low_Bound (Ptyp) /= Type_Low_Bound (Btyp)
4804                   or else
4805                  Type_High_Bound (Ptyp) /= Type_High_Bound (Btyp))
4806             then
4807                --  The call to Make_Range_Test will create declarations
4808                --  that need a proper insertion point, but Pref is now
4809                --  attached to a node with no ancestor. Attach to tree
4810                --  even if it is to be rewritten below.
4811
4812                Set_Parent (Tst, Parent (N));
4813
4814                Tst :=
4815                  Make_And_Then (Loc,
4816                    Left_Opnd  => Make_Range_Test,
4817                    Right_Opnd => Tst);
4818             end if;
4819
4820             Rewrite (N, Tst);
4821
4822          --  Fortran convention booleans
4823
4824          --  For the very special case of Fortran convention booleans, the
4825          --  value is always valid, since it is an integer with the semantics
4826          --  that non-zero is true, and any value is permissible.
4827
4828          elsif Is_Boolean_Type (Ptyp)
4829            and then Convention (Ptyp) = Convention_Fortran
4830          then
4831             Rewrite (N, New_Occurrence_Of (Standard_True, Loc));
4832
4833          --  For biased representations, we will be doing an unchecked
4834          --  conversion without unbiasing the result. That means that the range
4835          --  test has to take this into account, and the proper form of the
4836          --  test is:
4837
4838          --    Btyp!(Pref) < Btyp!(Ptyp'Range_Length)
4839
4840          elsif Has_Biased_Representation (Ptyp) then
4841             Btyp := RTE (RE_Unsigned_32);
4842             Rewrite (N,
4843               Make_Op_Lt (Loc,
4844                 Left_Opnd =>
4845                   Unchecked_Convert_To (Btyp, Duplicate_Subexpr (Pref)),
4846                 Right_Opnd =>
4847                   Unchecked_Convert_To (Btyp,
4848                     Make_Attribute_Reference (Loc,
4849                       Prefix => New_Occurrence_Of (Ptyp, Loc),
4850                       Attribute_Name => Name_Range_Length))));
4851
4852          --  For all other scalar types, what we want logically is a
4853          --  range test:
4854
4855          --     X in type(X)'First .. type(X)'Last
4856
4857          --  But that's precisely what won't work because of possible
4858          --  unwanted optimization (and indeed the basic motivation for
4859          --  the Valid attribute is exactly that this test does not work!)
4860          --  What will work is:
4861
4862          --     Btyp!(X) >= Btyp!(type(X)'First)
4863          --       and then
4864          --     Btyp!(X) <= Btyp!(type(X)'Last)
4865
4866          --  where Btyp is an integer type large enough to cover the full
4867          --  range of possible stored values (i.e. it is chosen on the basis
4868          --  of the size of the type, not the range of the values). We write
4869          --  this as two tests, rather than a range check, so that static
4870          --  evaluation will easily remove either or both of the checks if
4871          --  they can be -statically determined to be true (this happens
4872          --  when the type of X is static and the range extends to the full
4873          --  range of stored values).
4874
4875          --  Unsigned types. Note: it is safe to consider only whether the
4876          --  subtype is unsigned, since we will in that case be doing all
4877          --  unsigned comparisons based on the subtype range. Since we use the
4878          --  actual subtype object size, this is appropriate.
4879
4880          --  For example, if we have
4881
4882          --    subtype x is integer range 1 .. 200;
4883          --    for x'Object_Size use 8;
4884
4885          --  Now the base type is signed, but objects of this type are bits
4886          --  unsigned, and doing an unsigned test of the range 1 to 200 is
4887          --  correct, even though a value greater than 127 looks signed to a
4888          --  signed comparison.
4889
4890          elsif Is_Unsigned_Type (Ptyp) then
4891             if Esize (Ptyp) <= 32 then
4892                Btyp := RTE (RE_Unsigned_32);
4893             else
4894                Btyp := RTE (RE_Unsigned_64);
4895             end if;
4896
4897             Rewrite (N, Make_Range_Test);
4898
4899          --  Signed types
4900
4901          else
4902             if Esize (Ptyp) <= Esize (Standard_Integer) then
4903                Btyp := Standard_Integer;
4904             else
4905                Btyp := Universal_Integer;
4906             end if;
4907
4908             Rewrite (N, Make_Range_Test);
4909          end if;
4910
4911          Analyze_And_Resolve (N, Standard_Boolean);
4912          Validity_Checks_On := Save_Validity_Checks_On;
4913       end Valid;
4914
4915       -----------
4916       -- Value --
4917       -----------
4918
4919       --  Value attribute is handled in separate unti Exp_Imgv
4920
4921       when Attribute_Value =>
4922          Exp_Imgv.Expand_Value_Attribute (N);
4923
4924       -----------------
4925       -- Value_Size --
4926       -----------------
4927
4928       --  The processing for Value_Size shares the processing for Size
4929
4930       -------------
4931       -- Version --
4932       -------------
4933
4934       --  The processing for Version shares the processing for Body_Version
4935
4936       ----------------
4937       -- Wide_Image --
4938       ----------------
4939
4940       --  Wide_Image attribute is handled in separate unit Exp_Imgv
4941
4942       when Attribute_Wide_Image =>
4943          Exp_Imgv.Expand_Wide_Image_Attribute (N);
4944
4945       ---------------------
4946       -- Wide_Wide_Image --
4947       ---------------------
4948
4949       --  Wide_Wide_Image attribute is handled in separate unit Exp_Imgv
4950
4951       when Attribute_Wide_Wide_Image =>
4952          Exp_Imgv.Expand_Wide_Wide_Image_Attribute (N);
4953
4954       ----------------
4955       -- Wide_Value --
4956       ----------------
4957
4958       --  We expand typ'Wide_Value (X) into
4959
4960       --    typ'Value
4961       --      (Wide_String_To_String (X, Wide_Character_Encoding_Method))
4962
4963       --  Wide_String_To_String is a runtime function that converts its wide
4964       --  string argument to String, converting any non-translatable characters
4965       --  into appropriate escape sequences. This preserves the required
4966       --  semantics of Wide_Value in all cases, and results in a very simple
4967       --  implementation approach.
4968
4969       --  Note: for this approach to be fully standard compliant for the cases
4970       --  where typ is Wide_Character and Wide_Wide_Character, the encoding
4971       --  method must cover the entire character range (e.g. UTF-8). But that
4972       --  is a reasonable requirement when dealing with encoded character
4973       --  sequences. Presumably if one of the restrictive encoding mechanisms
4974       --  is in use such as Shift-JIS, then characters that cannot be
4975       --  represented using this encoding will not appear in any case.
4976
4977       when Attribute_Wide_Value => Wide_Value :
4978       begin
4979          Rewrite (N,
4980            Make_Attribute_Reference (Loc,
4981              Prefix         => Pref,
4982              Attribute_Name => Name_Value,
4983
4984              Expressions    => New_List (
4985                Make_Function_Call (Loc,
4986                  Name =>
4987                    New_Reference_To (RTE (RE_Wide_String_To_String), Loc),
4988
4989                  Parameter_Associations => New_List (
4990                    Relocate_Node (First (Exprs)),
4991                    Make_Integer_Literal (Loc,
4992                      Intval => Int (Wide_Character_Encoding_Method)))))));
4993
4994          Analyze_And_Resolve (N, Typ);
4995       end Wide_Value;
4996
4997       ---------------------
4998       -- Wide_Wide_Value --
4999       ---------------------
5000
5001       --  We expand typ'Wide_Value_Value (X) into
5002
5003       --    typ'Value
5004       --      (Wide_Wide_String_To_String (X, Wide_Character_Encoding_Method))
5005
5006       --  Wide_Wide_String_To_String is a runtime function that converts its
5007       --  wide string argument to String, converting any non-translatable
5008       --  characters into appropriate escape sequences. This preserves the
5009       --  required semantics of Wide_Wide_Value in all cases, and results in a
5010       --  very simple implementation approach.
5011
5012       --  It's not quite right where typ = Wide_Wide_Character, because the
5013       --  encoding method may not cover the whole character type ???
5014
5015       when Attribute_Wide_Wide_Value => Wide_Wide_Value :
5016       begin
5017          Rewrite (N,
5018            Make_Attribute_Reference (Loc,
5019              Prefix         => Pref,
5020              Attribute_Name => Name_Value,
5021
5022              Expressions    => New_List (
5023                Make_Function_Call (Loc,
5024                  Name =>
5025                    New_Reference_To (RTE (RE_Wide_Wide_String_To_String), Loc),
5026
5027                  Parameter_Associations => New_List (
5028                    Relocate_Node (First (Exprs)),
5029                    Make_Integer_Literal (Loc,
5030                      Intval => Int (Wide_Character_Encoding_Method)))))));
5031
5032          Analyze_And_Resolve (N, Typ);
5033       end Wide_Wide_Value;
5034
5035       ---------------------
5036       -- Wide_Wide_Width --
5037       ---------------------
5038
5039       --  Wide_Wide_Width attribute is handled in separate unit Exp_Imgv
5040
5041       when Attribute_Wide_Wide_Width =>
5042          Exp_Imgv.Expand_Width_Attribute (N, Wide_Wide);
5043
5044       ----------------
5045       -- Wide_Width --
5046       ----------------
5047
5048       --  Wide_Width attribute is handled in separate unit Exp_Imgv
5049
5050       when Attribute_Wide_Width =>
5051          Exp_Imgv.Expand_Width_Attribute (N, Wide);
5052
5053       -----------
5054       -- Width --
5055       -----------
5056
5057       --  Width attribute is handled in separate unit Exp_Imgv
5058
5059       when Attribute_Width =>
5060          Exp_Imgv.Expand_Width_Attribute (N, Normal);
5061
5062       -----------
5063       -- Write --
5064       -----------
5065
5066       when Attribute_Write => Write : declare
5067          P_Type : constant Entity_Id := Entity (Pref);
5068          U_Type : constant Entity_Id := Underlying_Type (P_Type);
5069          Pname  : Entity_Id;
5070          Decl   : Node_Id;
5071          Prag   : Node_Id;
5072          Arg3   : Node_Id;
5073          Wfunc  : Node_Id;
5074
5075       begin
5076          --  If no underlying type, we have an error that will be diagnosed
5077          --  elsewhere, so here we just completely ignore the expansion.
5078
5079          if No (U_Type) then
5080             return;
5081          end if;
5082
5083          --  The simple case, if there is a TSS for Write, just call it
5084
5085          Pname := Find_Stream_Subprogram (P_Type, TSS_Stream_Write);
5086
5087          if Present (Pname) then
5088             null;
5089
5090          else
5091             --  If there is a Stream_Convert pragma, use it, we rewrite
5092
5093             --     sourcetyp'Output (stream, Item)
5094
5095             --  as
5096
5097             --     strmtyp'Output (Stream, strmwrite (acttyp (Item)));
5098
5099             --  where strmwrite is the given Write function that converts an
5100             --  argument of type sourcetyp or a type acctyp, from which it is
5101             --  derived to type strmtyp. The conversion to acttyp is required
5102             --  for the derived case.
5103
5104             Prag := Get_Stream_Convert_Pragma (P_Type);
5105
5106             if Present (Prag) then
5107                Arg3 :=
5108                  Next (Next (First (Pragma_Argument_Associations (Prag))));
5109                Wfunc := Entity (Expression (Arg3));
5110
5111                Rewrite (N,
5112                  Make_Attribute_Reference (Loc,
5113                    Prefix => New_Occurrence_Of (Etype (Wfunc), Loc),
5114                    Attribute_Name => Name_Output,
5115                    Expressions => New_List (
5116                      Relocate_Node (First (Exprs)),
5117                      Make_Function_Call (Loc,
5118                        Name => New_Occurrence_Of (Wfunc, Loc),
5119                        Parameter_Associations => New_List (
5120                          OK_Convert_To (Etype (First_Formal (Wfunc)),
5121                            Relocate_Node (Next (First (Exprs)))))))));
5122
5123                Analyze (N);
5124                return;
5125
5126             --  For elementary types, we call the W_xxx routine directly
5127
5128             elsif Is_Elementary_Type (U_Type) then
5129                Rewrite (N, Build_Elementary_Write_Call (N));
5130                Analyze (N);
5131                return;
5132
5133             --  Array type case
5134
5135             elsif Is_Array_Type (U_Type) then
5136                Build_Array_Write_Procedure (N, U_Type, Decl, Pname);
5137                Compile_Stream_Body_In_Scope (N, Decl, U_Type, Check => False);
5138
5139             --  Tagged type case, use the primitive Write function. Note that
5140             --  this will dispatch in the class-wide case which is what we want
5141
5142             elsif Is_Tagged_Type (U_Type) then
5143                Pname := Find_Prim_Op (U_Type, TSS_Stream_Write);
5144
5145             --  All other record type cases, including protected records.
5146             --  The latter only arise for expander generated code for
5147             --  handling shared passive partition access.
5148
5149             else
5150                pragma Assert
5151                  (Is_Record_Type (U_Type) or else Is_Protected_Type (U_Type));
5152
5153                --  Ada 2005 (AI-216): Program_Error is raised when executing
5154                --  the default implementation of the Write attribute of an
5155                --  Unchecked_Union type. However, if the 'Write reference is
5156                --  within the generated Output stream procedure, Write outputs
5157                --  the components, and the default values of the discriminant
5158                --  are streamed by the Output procedure itself.
5159
5160                if Is_Unchecked_Union (Base_Type (U_Type))
5161                  and not Is_TSS (Current_Scope, TSS_Stream_Output)
5162                then
5163                   Insert_Action (N,
5164                     Make_Raise_Program_Error (Loc,
5165                       Reason => PE_Unchecked_Union_Restriction));
5166                end if;
5167
5168                if Has_Discriminants (U_Type)
5169                  and then Present
5170                    (Discriminant_Default_Value (First_Discriminant (U_Type)))
5171                then
5172                   Build_Mutable_Record_Write_Procedure
5173                     (Loc, Base_Type (U_Type), Decl, Pname);
5174                else
5175                   Build_Record_Write_Procedure
5176                     (Loc, Base_Type (U_Type), Decl, Pname);
5177                end if;
5178
5179                Insert_Action (N, Decl);
5180             end if;
5181          end if;
5182
5183          --  If we fall through, Pname is the procedure to be called
5184
5185          Rewrite_Stream_Proc_Call (Pname);
5186       end Write;
5187
5188       --  Component_Size is handled by the back end, unless the component size
5189       --  is known at compile time, which is always true in the packed array
5190       --  case. It is important that the packed array case is handled in the
5191       --  front end (see Eval_Attribute) since the back end would otherwise get
5192       --  confused by the equivalent packed array type.
5193
5194       when Attribute_Component_Size =>
5195          null;
5196
5197       --  The following attributes are handled by the back end (except that
5198       --  static cases have already been evaluated during semantic processing,
5199       --  but in any case the back end should not count on this). The one bit
5200       --  of special processing required is that these attributes typically
5201       --  generate conditionals in the code, so we need to check the relevant
5202       --  restriction.
5203
5204       when Attribute_Max                          |
5205            Attribute_Min                          =>
5206          Check_Restriction (No_Implicit_Conditionals, N);
5207
5208       --  The following attributes are handled by the back end (except that
5209       --  static cases have already been evaluated during semantic processing,
5210       --  but in any case the back end should not count on this).
5211
5212       --  The back end also handles the non-class-wide cases of Size
5213
5214       when Attribute_Bit_Order                    |
5215            Attribute_Code_Address                 |
5216            Attribute_Definite                     |
5217            Attribute_Null_Parameter               |
5218            Attribute_Passed_By_Reference          |
5219            Attribute_Pool_Address                 =>
5220          null;
5221
5222       --  The following attributes are also handled by the back end, but return
5223       --  a universal integer result, so may need a conversion for checking
5224       --  that the result is in range.
5225
5226       when Attribute_Aft                          |
5227            Attribute_Bit                          |
5228            Attribute_Max_Size_In_Storage_Elements
5229       =>
5230          Apply_Universal_Integer_Attribute_Checks (N);
5231
5232       --  The following attributes should not appear at this stage, since they
5233       --  have already been handled by the analyzer (and properly rewritten
5234       --  with corresponding values or entities to represent the right values)
5235
5236       when Attribute_Abort_Signal                 |
5237            Attribute_Address_Size                 |
5238            Attribute_Base                         |
5239            Attribute_Class                        |
5240            Attribute_Default_Bit_Order            |
5241            Attribute_Delta                        |
5242            Attribute_Denorm                       |
5243            Attribute_Digits                       |
5244            Attribute_Emax                         |
5245            Attribute_Enabled                      |
5246            Attribute_Epsilon                      |
5247            Attribute_Fast_Math                    |
5248            Attribute_Has_Access_Values            |
5249            Attribute_Has_Discriminants            |
5250            Attribute_Has_Tagged_Values            |
5251            Attribute_Large                        |
5252            Attribute_Machine_Emax                 |
5253            Attribute_Machine_Emin                 |
5254            Attribute_Machine_Mantissa             |
5255            Attribute_Machine_Overflows            |
5256            Attribute_Machine_Radix                |
5257            Attribute_Machine_Rounds               |
5258            Attribute_Maximum_Alignment            |
5259            Attribute_Model_Emin                   |
5260            Attribute_Model_Epsilon                |
5261            Attribute_Model_Mantissa               |
5262            Attribute_Model_Small                  |
5263            Attribute_Modulus                      |
5264            Attribute_Partition_ID                 |
5265            Attribute_Range                        |
5266            Attribute_Safe_Emax                    |
5267            Attribute_Safe_First                   |
5268            Attribute_Safe_Large                   |
5269            Attribute_Safe_Last                    |
5270            Attribute_Safe_Small                   |
5271            Attribute_Scale                        |
5272            Attribute_Signed_Zeros                 |
5273            Attribute_Small                        |
5274            Attribute_Storage_Unit                 |
5275            Attribute_Stub_Type                    |
5276            Attribute_Target_Name                  |
5277            Attribute_Type_Class                   |
5278            Attribute_Unconstrained_Array          |
5279            Attribute_Universal_Literal_String     |
5280            Attribute_Wchar_T_Size                 |
5281            Attribute_Word_Size                    =>
5282
5283          raise Program_Error;
5284
5285       --  The Asm_Input and Asm_Output attributes are not expanded at this
5286       --  stage, but will be eliminated in the expansion of the Asm call, see
5287       --  Exp_Intr for details. So the back end will never see these either.
5288
5289       when Attribute_Asm_Input                    |
5290            Attribute_Asm_Output                   =>
5291
5292          null;
5293
5294       end case;
5295
5296    exception
5297       when RE_Not_Available =>
5298          return;
5299    end Expand_N_Attribute_Reference;
5300
5301    ----------------------
5302    -- Expand_Pred_Succ --
5303    ----------------------
5304
5305    --  For typ'Pred (exp), we generate the check
5306
5307    --    [constraint_error when exp = typ'Base'First]
5308
5309    --  Similarly, for typ'Succ (exp), we generate the check
5310
5311    --    [constraint_error when exp = typ'Base'Last]
5312
5313    --  These checks are not generated for modular types, since the proper
5314    --  semantics for Succ and Pred on modular types is to wrap, not raise CE.
5315
5316    procedure Expand_Pred_Succ (N : Node_Id) is
5317       Loc  : constant Source_Ptr := Sloc (N);
5318       Cnam : Name_Id;
5319
5320    begin
5321       if Attribute_Name (N) = Name_Pred then
5322          Cnam := Name_First;
5323       else
5324          Cnam := Name_Last;
5325       end if;
5326
5327       Insert_Action (N,
5328         Make_Raise_Constraint_Error (Loc,
5329           Condition =>
5330             Make_Op_Eq (Loc,
5331               Left_Opnd =>
5332                 Duplicate_Subexpr_Move_Checks (First (Expressions (N))),
5333               Right_Opnd =>
5334                 Make_Attribute_Reference (Loc,
5335                   Prefix =>
5336                     New_Reference_To (Base_Type (Etype (Prefix (N))), Loc),
5337                   Attribute_Name => Cnam)),
5338           Reason => CE_Overflow_Check_Failed));
5339    end Expand_Pred_Succ;
5340
5341    -------------------
5342    -- Find_Fat_Info --
5343    -------------------
5344
5345    procedure Find_Fat_Info
5346      (T        : Entity_Id;
5347       Fat_Type : out Entity_Id;
5348       Fat_Pkg  : out RE_Id)
5349    is
5350       Btyp : constant Entity_Id := Base_Type (T);
5351       Rtyp : constant Entity_Id := Root_Type (T);
5352       Digs : constant Nat       := UI_To_Int (Digits_Value (Btyp));
5353
5354    begin
5355       --  If the base type is VAX float, then get appropriate VAX float type
5356
5357       if Vax_Float (Btyp) then
5358          case Digs is
5359             when 6 =>
5360                Fat_Type := RTE (RE_Fat_VAX_F);
5361                Fat_Pkg  := RE_Attr_VAX_F_Float;
5362
5363             when 9 =>
5364                Fat_Type := RTE (RE_Fat_VAX_D);
5365                Fat_Pkg  := RE_Attr_VAX_D_Float;
5366
5367             when 15 =>
5368                Fat_Type := RTE (RE_Fat_VAX_G);
5369                Fat_Pkg  := RE_Attr_VAX_G_Float;
5370
5371             when others =>
5372                raise Program_Error;
5373          end case;
5374
5375       --  If root type is VAX float, this is the case where the library has
5376       --  been recompiled in VAX float mode, and we have an IEEE float type.
5377       --  This is when we use the special IEEE Fat packages.
5378
5379       elsif Vax_Float (Rtyp) then
5380          case Digs is
5381             when 6 =>
5382                Fat_Type := RTE (RE_Fat_IEEE_Short);
5383                Fat_Pkg  := RE_Attr_IEEE_Short;
5384
5385             when 15 =>
5386                Fat_Type := RTE (RE_Fat_IEEE_Long);
5387                Fat_Pkg  := RE_Attr_IEEE_Long;
5388
5389             when others =>
5390                raise Program_Error;
5391          end case;
5392
5393       --  If neither the base type nor the root type is VAX_Float then VAX
5394       --  float is out of the picture, and we can just use the root type.
5395
5396       else
5397          Fat_Type := Rtyp;
5398
5399          if Fat_Type = Standard_Short_Float then
5400             Fat_Pkg := RE_Attr_Short_Float;
5401
5402          elsif Fat_Type = Standard_Float then
5403             Fat_Pkg := RE_Attr_Float;
5404
5405          elsif Fat_Type = Standard_Long_Float then
5406             Fat_Pkg := RE_Attr_Long_Float;
5407
5408          elsif Fat_Type = Standard_Long_Long_Float then
5409             Fat_Pkg := RE_Attr_Long_Long_Float;
5410
5411          --  Universal real (which is its own root type) is treated as being
5412          --  equivalent to Standard.Long_Long_Float, since it is defined to
5413          --  have the same precision as the longest Float type.
5414
5415          elsif Fat_Type = Universal_Real then
5416             Fat_Type := Standard_Long_Long_Float;
5417             Fat_Pkg := RE_Attr_Long_Long_Float;
5418
5419          else
5420             raise Program_Error;
5421          end if;
5422       end if;
5423    end Find_Fat_Info;
5424
5425    ----------------------------
5426    -- Find_Stream_Subprogram --
5427    ----------------------------
5428
5429    function Find_Stream_Subprogram
5430      (Typ : Entity_Id;
5431       Nam : TSS_Name_Type) return Entity_Id
5432    is
5433       Base_Typ : constant Entity_Id := Base_Type (Typ);
5434       Ent      : constant Entity_Id := TSS (Typ, Nam);
5435
5436    begin
5437       if Present (Ent) then
5438          return Ent;
5439       end if;
5440
5441       --  Stream attributes for strings are expanded into library calls. The
5442       --  following checks are disabled when the run-time is not available or
5443       --  when compiling predefined types due to bootstrap issues. As a result,
5444       --  the compiler will generate in-place stream routines for string types
5445       --  that appear in GNAT's library, but will generate calls via rtsfind
5446       --  to library routines for user code.
5447       --  ??? For now, disable this code for JVM, since this generates a
5448       --  VerifyError exception at run-time on e.g. c330001.
5449       --  This is disabled for AAMP, to avoid making dependences on files not
5450       --  supported in the AAMP library (such as s-fileio.adb).
5451
5452       if VM_Target /= JVM_Target
5453         and then not AAMP_On_Target
5454         and then
5455           not Is_Predefined_File_Name (Unit_File_Name (Current_Sem_Unit))
5456       then
5457          --  String as defined in package Ada
5458
5459          if Base_Typ = Standard_String then
5460             if Restriction_Active (No_Stream_Optimizations) then
5461                if Nam = TSS_Stream_Input then
5462                   return RTE (RE_String_Input);
5463
5464                elsif Nam = TSS_Stream_Output then
5465                   return RTE (RE_String_Output);
5466
5467                elsif Nam = TSS_Stream_Read then
5468                   return RTE (RE_String_Read);
5469
5470                else pragma Assert (Nam = TSS_Stream_Write);
5471                   return RTE (RE_String_Write);
5472                end if;
5473
5474             else
5475                if Nam = TSS_Stream_Input then
5476                   return RTE (RE_String_Input_Blk_IO);
5477
5478                elsif Nam = TSS_Stream_Output then
5479                   return RTE (RE_String_Output_Blk_IO);
5480
5481                elsif Nam = TSS_Stream_Read then
5482                   return RTE (RE_String_Read_Blk_IO);
5483
5484                else pragma Assert (Nam = TSS_Stream_Write);
5485                   return RTE (RE_String_Write_Blk_IO);
5486                end if;
5487             end if;
5488
5489          --  Wide_String as defined in package Ada
5490
5491          elsif Base_Typ = Standard_Wide_String then
5492             if Restriction_Active (No_Stream_Optimizations) then
5493                if Nam = TSS_Stream_Input then
5494                   return RTE (RE_Wide_String_Input);
5495
5496                elsif Nam = TSS_Stream_Output then
5497                   return RTE (RE_Wide_String_Output);
5498
5499                elsif Nam = TSS_Stream_Read then
5500                   return RTE (RE_Wide_String_Read);
5501
5502                else pragma Assert (Nam = TSS_Stream_Write);
5503                   return RTE (RE_Wide_String_Write);
5504                end if;
5505
5506             else
5507                if Nam = TSS_Stream_Input then
5508                   return RTE (RE_Wide_String_Input_Blk_IO);
5509
5510                elsif Nam = TSS_Stream_Output then
5511                   return RTE (RE_Wide_String_Output_Blk_IO);
5512
5513                elsif Nam = TSS_Stream_Read then
5514                   return RTE (RE_Wide_String_Read_Blk_IO);
5515
5516                else pragma Assert (Nam = TSS_Stream_Write);
5517                   return RTE (RE_Wide_String_Write_Blk_IO);
5518                end if;
5519             end if;
5520
5521          --  Wide_Wide_String as defined in package Ada
5522
5523          elsif Base_Typ = Standard_Wide_Wide_String then
5524             if Restriction_Active (No_Stream_Optimizations) then
5525                if Nam = TSS_Stream_Input then
5526                   return RTE (RE_Wide_Wide_String_Input);
5527
5528                elsif Nam = TSS_Stream_Output then
5529                   return RTE (RE_Wide_Wide_String_Output);
5530
5531                elsif Nam = TSS_Stream_Read then
5532                   return RTE (RE_Wide_Wide_String_Read);
5533
5534                else pragma Assert (Nam = TSS_Stream_Write);
5535                   return RTE (RE_Wide_Wide_String_Write);
5536                end if;
5537
5538             else
5539                if Nam = TSS_Stream_Input then
5540                   return RTE (RE_Wide_Wide_String_Input_Blk_IO);
5541
5542                elsif Nam = TSS_Stream_Output then
5543                   return RTE (RE_Wide_Wide_String_Output_Blk_IO);
5544
5545                elsif Nam = TSS_Stream_Read then
5546                   return RTE (RE_Wide_Wide_String_Read_Blk_IO);
5547
5548                else pragma Assert (Nam = TSS_Stream_Write);
5549                   return RTE (RE_Wide_Wide_String_Write_Blk_IO);
5550                end if;
5551             end if;
5552          end if;
5553       end if;
5554
5555       if Is_Tagged_Type (Typ)
5556         and then Is_Derived_Type (Typ)
5557       then
5558          return Find_Prim_Op (Typ, Nam);
5559       else
5560          return Find_Inherited_TSS (Typ, Nam);
5561       end if;
5562    end Find_Stream_Subprogram;
5563
5564    -----------------------
5565    -- Get_Index_Subtype --
5566    -----------------------
5567
5568    function Get_Index_Subtype (N : Node_Id) return Node_Id is
5569       P_Type : Entity_Id := Etype (Prefix (N));
5570       Indx   : Node_Id;
5571       J      : Int;
5572
5573    begin
5574       if Is_Access_Type (P_Type) then
5575          P_Type := Designated_Type (P_Type);
5576       end if;
5577
5578       if No (Expressions (N)) then
5579          J := 1;
5580       else
5581          J := UI_To_Int (Expr_Value (First (Expressions (N))));
5582       end if;
5583
5584       Indx := First_Index (P_Type);
5585       while J > 1 loop
5586          Next_Index (Indx);
5587          J := J - 1;
5588       end loop;
5589
5590       return Etype (Indx);
5591    end Get_Index_Subtype;
5592
5593    -------------------------------
5594    -- Get_Stream_Convert_Pragma --
5595    -------------------------------
5596
5597    function Get_Stream_Convert_Pragma (T : Entity_Id) return Node_Id is
5598       Typ : Entity_Id;
5599       N   : Node_Id;
5600
5601    begin
5602       --  Note: we cannot use Get_Rep_Pragma here because of the peculiarity
5603       --  that a stream convert pragma for a tagged type is not inherited from
5604       --  its parent. Probably what is wrong here is that it is basically
5605       --  incorrect to consider a stream convert pragma to be a representation
5606       --  pragma at all ???
5607
5608       N := First_Rep_Item (Implementation_Base_Type (T));
5609       while Present (N) loop
5610          if Nkind (N) = N_Pragma
5611            and then Pragma_Name (N) = Name_Stream_Convert
5612          then
5613             --  For tagged types this pragma is not inherited, so we
5614             --  must verify that it is defined for the given type and
5615             --  not an ancestor.
5616
5617             Typ :=
5618               Entity (Expression (First (Pragma_Argument_Associations (N))));
5619
5620             if not Is_Tagged_Type (T)
5621               or else T = Typ
5622               or else (Is_Private_Type (Typ) and then T = Full_View (Typ))
5623             then
5624                return N;
5625             end if;
5626          end if;
5627
5628          Next_Rep_Item (N);
5629       end loop;
5630
5631       return Empty;
5632    end Get_Stream_Convert_Pragma;
5633
5634    ---------------------------------
5635    -- Is_Constrained_Packed_Array --
5636    ---------------------------------
5637
5638    function Is_Constrained_Packed_Array (Typ : Entity_Id) return Boolean is
5639       Arr : Entity_Id := Typ;
5640
5641    begin
5642       if Is_Access_Type (Arr) then
5643          Arr := Designated_Type (Arr);
5644       end if;
5645
5646       return Is_Array_Type (Arr)
5647         and then Is_Constrained (Arr)
5648         and then Present (Packed_Array_Type (Arr));
5649    end Is_Constrained_Packed_Array;
5650
5651    ----------------------------------------
5652    -- Is_Inline_Floating_Point_Attribute --
5653    ----------------------------------------
5654
5655    function Is_Inline_Floating_Point_Attribute (N : Node_Id) return Boolean is
5656       Id : constant Attribute_Id := Get_Attribute_Id (Attribute_Name (N));
5657
5658    begin
5659       if Nkind (Parent (N)) /= N_Type_Conversion
5660         or else not Is_Integer_Type (Etype (Parent (N)))
5661       then
5662          return False;
5663       end if;
5664
5665       --  Should also support 'Machine_Rounding and 'Unbiased_Rounding, but
5666       --  required back end support has not been implemented yet ???
5667
5668       return Id = Attribute_Truncation;
5669    end Is_Inline_Floating_Point_Attribute;
5670
5671 end Exp_Attr;