OSDN Git Service

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