OSDN Git Service

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