OSDN Git Service

2007-09-26 Thomas Quinot <quinot@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          if Is_Access_Protected_Subprogram_Type (Btyp) then
610             Expand_Access_To_Protected_Op (N, Pref, Typ);
611
612          --  If the prefix is a type name, this is a reference to the current
613          --  instance of the type, within its initialization procedure.
614
615          elsif Is_Entity_Name (Pref)
616            and then Is_Type (Entity (Pref))
617          then
618             declare
619                Par    : Node_Id;
620                Formal : Entity_Id;
621
622             begin
623                --  If the current instance name denotes a task type, then the
624                --  access attribute is rewritten to be the name of the "_task"
625                --  parameter associated with the task type's task procedure.
626                --  An unchecked conversion is applied to ensure a type match in
627                --  cases of expander-generated calls (e.g., init procs).
628
629                if Is_Task_Type (Entity (Pref)) then
630                   Formal :=
631                     First_Entity (Get_Task_Body_Procedure (Entity (Pref)));
632                   while Present (Formal) loop
633                      exit when Chars (Formal) = Name_uTask;
634                      Next_Entity (Formal);
635                   end loop;
636
637                   pragma Assert (Present (Formal));
638
639                   Rewrite (N,
640                     Unchecked_Convert_To
641                       (Typ, New_Occurrence_Of (Formal, Loc)));
642                   Set_Etype (N, Typ);
643
644                   return;
645
646                --  The expression must appear in a default expression, (which
647                --  in the initialization procedure is the right-hand side of an
648                --  assignment), and not in a discriminant constraint.
649
650                else
651                   Par := Parent (N);
652                   while Present (Par) loop
653                      exit when Nkind (Par) = N_Assignment_Statement;
654
655                      if Nkind (Par) = N_Component_Declaration then
656                         return;
657                      end if;
658
659                      Par := Parent (Par);
660                   end loop;
661
662                   if Present (Par) then
663                      Rewrite (N,
664                        Make_Attribute_Reference (Loc,
665                          Prefix => Make_Identifier (Loc, Name_uInit),
666                          Attribute_Name  => Attribute_Name (N)));
667
668                      Analyze_And_Resolve (N, Typ);
669                   end if;
670
671                   return;
672                end if;
673             end;
674
675          --  The following handles cases involving interfaces and when the
676          --  prefix of an access attribute is an explicit dereference. In the
677          --  case where the access attribute is specifically Attribute_Access,
678          --  we only do this when the context type is E_General_Access_Type,
679          --  and not for anonymous access types. It seems that this code should
680          --  be used for anonymous contexts as well, but that causes various
681          --  regressions, such as on prefix-notation calls to dispatching
682          --  operations and back-end errors on access type conversions. ???
683
684          elsif Id /= Attribute_Access
685            or else Ekind (Btyp) = E_General_Access_Type
686          then
687             declare
688                Ref_Object : constant Node_Id := Get_Referenced_Object (Pref);
689                Parm_Ent   : Entity_Id;
690                Conversion : Node_Id;
691
692             begin
693                --  If the prefix of an Access attribute is a dereference of an
694                --  access parameter (or a renaming of such a dereference) and
695                --  the context is a general access type (but not an anonymous
696                --  access type), then rewrite the attribute as a conversion of
697                --  the access parameter to the context access type. This will
698                --  result in an accessibility check being performed, if needed.
699
700                --    (X.all'Access => Acc_Type (X))
701
702                --  Note: Limit the expansion of an attribute applied to a
703                --  dereference of an access parameter so that it's only done
704                --  for 'Access. This fixes a problem with 'Unrestricted_Access
705                --  that leads to errors in the case where the attribute
706                --  type is access-to-variable and the access parameter is
707                --  access-to-constant. The conversion is only done to get
708                --  accessibility checks, so it makes sense to limit it to
709                --  'Access (and consistent with existing comment).
710
711                if Nkind (Ref_Object) = N_Explicit_Dereference
712                  and then Is_Entity_Name (Prefix (Ref_Object))
713                  and then Id = Attribute_Access
714                then
715                   Parm_Ent := Entity (Prefix (Ref_Object));
716
717                   if Ekind (Parm_Ent) in Formal_Kind
718                     and then Ekind (Etype (Parm_Ent)) = E_Anonymous_Access_Type
719                     and then Present (Extra_Accessibility (Parm_Ent))
720                   then
721                      Conversion :=
722                        Convert_To (Typ, New_Copy_Tree (Prefix (Ref_Object)));
723
724                      Rewrite (N, Conversion);
725                      Analyze_And_Resolve (N, Typ);
726
727                      return;
728                   end if;
729                end if;
730
731                --  Ada 2005 (AI-251): If the designated type is an interface,
732                --  then rewrite the referenced object as a conversion, to force
733                --  the displacement of the pointer to the secondary dispatch
734                --  table.
735
736                if Is_Interface (Directly_Designated_Type (Btyp)) then
737
738                   --  When the object is an explicit dereference, just convert
739                   --  the dereference's prefix.
740
741                   if Nkind (Ref_Object) = N_Explicit_Dereference then
742                      Conversion :=
743                        Convert_To (Typ, New_Copy_Tree (Prefix (Ref_Object)));
744
745                   --  It seems rather bizarre that we generate a conversion of
746                   --  a tagged object to an access type, since such conversions
747                   --  are not normally permitted, but Expand_N_Type_Conversion
748                   --  (actually Expand_Interface_Conversion) is designed to
749                   --  handle them in the interface case. Do we really want to
750                   --  create such odd conversions???
751
752                   else
753                      Conversion :=
754                        Convert_To (Typ, New_Copy_Tree (Ref_Object));
755                   end if;
756
757                   Rewrite (N, Conversion);
758                   Analyze_And_Resolve (N, Typ);
759                end if;
760             end;
761          end if;
762
763       --------------
764       -- Adjacent --
765       --------------
766
767       --  Transforms 'Adjacent into a call to the floating-point attribute
768       --  function Adjacent in Fat_xxx (where xxx is the root type)
769
770       when Attribute_Adjacent =>
771          Expand_Fpt_Attribute_RR (N);
772
773       -------------
774       -- Address --
775       -------------
776
777       when Attribute_Address => Address : declare
778          Task_Proc : Entity_Id;
779
780       begin
781          --  If the prefix is a task or a task type, the useful address is that
782          --  of the procedure for the task body, i.e. the actual program unit.
783          --  We replace the original entity with that of the procedure.
784
785          if Is_Entity_Name (Pref)
786            and then Is_Task_Type (Entity (Pref))
787          then
788             Task_Proc := Next_Entity (Root_Type (Etype (Pref)));
789
790             while Present (Task_Proc) loop
791                exit when Ekind (Task_Proc) = E_Procedure
792                  and then Etype (First_Formal (Task_Proc)) =
793                                   Corresponding_Record_Type (Etype (Pref));
794                Next_Entity (Task_Proc);
795             end loop;
796
797             if Present (Task_Proc) then
798                Set_Entity (Pref, Task_Proc);
799                Set_Etype  (Pref, Etype (Task_Proc));
800             end if;
801
802          --  Similarly, the address of a protected operation is the address
803          --  of the corresponding protected body, regardless of the protected
804          --  object from which it is selected.
805
806          elsif Nkind (Pref) = N_Selected_Component
807            and then Is_Subprogram (Entity (Selector_Name (Pref)))
808            and then Is_Protected_Type (Scope (Entity (Selector_Name (Pref))))
809          then
810             Rewrite (Pref,
811               New_Occurrence_Of (
812                 External_Subprogram (Entity (Selector_Name (Pref))), Loc));
813
814          elsif Nkind (Pref) = N_Explicit_Dereference
815            and then Ekind (Etype (Pref)) = E_Subprogram_Type
816            and then Convention (Etype (Pref)) = Convention_Protected
817          then
818             --  The prefix is be a dereference of an access_to_protected_
819             --  subprogram. The desired address is the second component of
820             --  the record that represents the access.
821
822             declare
823                Addr : constant Entity_Id := Etype (N);
824                Ptr  : constant Node_Id   := Prefix (Pref);
825                T    : constant Entity_Id :=
826                         Equivalent_Type (Base_Type (Etype (Ptr)));
827
828             begin
829                Rewrite (N,
830                  Unchecked_Convert_To (Addr,
831                    Make_Selected_Component (Loc,
832                      Prefix => Unchecked_Convert_To (T, Ptr),
833                      Selector_Name => New_Occurrence_Of (
834                        Next_Entity (First_Entity (T)), Loc))));
835
836                Analyze_And_Resolve (N, Addr);
837             end;
838
839          --  Ada 2005 (AI-251): Class-wide interface objects are always
840          --  "displaced" to reference the tag associated with the interface
841          --  type. In order to obtain the real address of such objects we
842          --  generate a call to a run-time subprogram that returns the base
843          --  address of the object.
844
845          elsif Is_Class_Wide_Type (Etype (Pref))
846            and then Is_Interface (Etype (Pref))
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             Rewrite (N,
1931               Unchecked_Convert_To (Id_Kind, Concurrent_Ref (Pref)));
1932          end if;
1933
1934          Analyze_And_Resolve (N, Id_Kind);
1935       end Identity;
1936
1937       -----------
1938       -- Image --
1939       -----------
1940
1941       --  Image attribute is handled in separate unit Exp_Imgv
1942
1943       when Attribute_Image =>
1944          Exp_Imgv.Expand_Image_Attribute (N);
1945
1946       ---------
1947       -- Img --
1948       ---------
1949
1950       --  X'Img is expanded to typ'Image (X), where typ is the type of X
1951
1952       when Attribute_Img => Img :
1953       begin
1954          Rewrite (N,
1955            Make_Attribute_Reference (Loc,
1956              Prefix => New_Reference_To (Etype (Pref), Loc),
1957              Attribute_Name => Name_Image,
1958              Expressions => New_List (Relocate_Node (Pref))));
1959
1960          Analyze_And_Resolve (N, Standard_String);
1961       end Img;
1962
1963       -----------
1964       -- Input --
1965       -----------
1966
1967       when Attribute_Input => Input : declare
1968          P_Type : constant Entity_Id := Entity (Pref);
1969          B_Type : constant Entity_Id := Base_Type (P_Type);
1970          U_Type : constant Entity_Id := Underlying_Type (P_Type);
1971          Strm   : constant Node_Id   := First (Exprs);
1972          Fname  : Entity_Id;
1973          Decl   : Node_Id;
1974          Call   : Node_Id;
1975          Prag   : Node_Id;
1976          Arg2   : Node_Id;
1977          Rfunc  : Node_Id;
1978
1979          Cntrl  : Node_Id := Empty;
1980          --  Value for controlling argument in call. Always Empty except in
1981          --  the dispatching (class-wide type) case, where it is a reference
1982          --  to the dummy object initialized to the right internal tag.
1983
1984          procedure Freeze_Stream_Subprogram (F : Entity_Id);
1985          --  The expansion of the attribute reference may generate a call to
1986          --  a user-defined stream subprogram that is frozen by the call. This
1987          --  can lead to access-before-elaboration problem if the reference
1988          --  appears in an object declaration and the subprogram body has not
1989          --  been seen. The freezing of the subprogram requires special code
1990          --  because it appears in an expanded context where expressions do
1991          --  not freeze their constituents.
1992
1993          ------------------------------
1994          -- Freeze_Stream_Subprogram --
1995          ------------------------------
1996
1997          procedure Freeze_Stream_Subprogram (F : Entity_Id) is
1998             Decl : constant Node_Id := Unit_Declaration_Node (F);
1999             Bod  : Node_Id;
2000
2001          begin
2002             --  If this is user-defined subprogram, the corresponding
2003             --  stream function appears as a renaming-as-body, and the
2004             --  user subprogram must be retrieved by tree traversal.
2005
2006             if Present (Decl)
2007               and then Nkind (Decl) = N_Subprogram_Declaration
2008               and then Present (Corresponding_Body (Decl))
2009             then
2010                Bod := Corresponding_Body (Decl);
2011
2012                if Nkind (Unit_Declaration_Node (Bod)) =
2013                  N_Subprogram_Renaming_Declaration
2014                then
2015                   Set_Is_Frozen (Entity (Name (Unit_Declaration_Node (Bod))));
2016                end if;
2017             end if;
2018          end Freeze_Stream_Subprogram;
2019
2020       --  Start of processing for Input
2021
2022       begin
2023          --  If no underlying type, we have an error that will be diagnosed
2024          --  elsewhere, so here we just completely ignore the expansion.
2025
2026          if No (U_Type) then
2027             return;
2028          end if;
2029
2030          --  If there is a TSS for Input, just call it
2031
2032          Fname := Find_Stream_Subprogram (P_Type, TSS_Stream_Input);
2033
2034          if Present (Fname) then
2035             null;
2036
2037          else
2038             --  If there is a Stream_Convert pragma, use it, we rewrite
2039
2040             --     sourcetyp'Input (stream)
2041
2042             --  as
2043
2044             --     sourcetyp (streamread (strmtyp'Input (stream)));
2045
2046             --  where stmrearead is the given Read function that converts
2047             --  an argument of type strmtyp to type sourcetyp or a type
2048             --  from which it is derived. The extra conversion is required
2049             --  for the derived case.
2050
2051             Prag := Get_Stream_Convert_Pragma (P_Type);
2052
2053             if Present (Prag) then
2054                Arg2  := Next (First (Pragma_Argument_Associations (Prag)));
2055                Rfunc := Entity (Expression (Arg2));
2056
2057                Rewrite (N,
2058                  Convert_To (B_Type,
2059                    Make_Function_Call (Loc,
2060                      Name => New_Occurrence_Of (Rfunc, Loc),
2061                      Parameter_Associations => New_List (
2062                        Make_Attribute_Reference (Loc,
2063                          Prefix =>
2064                            New_Occurrence_Of
2065                              (Etype (First_Formal (Rfunc)), Loc),
2066                          Attribute_Name => Name_Input,
2067                          Expressions => Exprs)))));
2068
2069                Analyze_And_Resolve (N, B_Type);
2070                return;
2071
2072             --  Elementary types
2073
2074             elsif Is_Elementary_Type (U_Type) then
2075
2076                --  A special case arises if we have a defined _Read routine,
2077                --  since in this case we are required to call this routine.
2078
2079                if Present (TSS (Base_Type (U_Type), TSS_Stream_Read)) then
2080                   Build_Record_Or_Elementary_Input_Function
2081                     (Loc, U_Type, Decl, Fname);
2082                   Insert_Action (N, Decl);
2083
2084                --  For normal cases, we call the I_xxx routine directly
2085
2086                else
2087                   Rewrite (N, Build_Elementary_Input_Call (N));
2088                   Analyze_And_Resolve (N, P_Type);
2089                   return;
2090                end if;
2091
2092             --  Array type case
2093
2094             elsif Is_Array_Type (U_Type) then
2095                Build_Array_Input_Function (Loc, U_Type, Decl, Fname);
2096                Compile_Stream_Body_In_Scope (N, Decl, U_Type, Check => False);
2097
2098             --  Dispatching case with class-wide type
2099
2100             elsif Is_Class_Wide_Type (P_Type) then
2101
2102                --  No need to do anything else compiling under restriction
2103                --  No_Dispatching_Calls. During the semantic analysis we
2104                --  already notified such violation.
2105
2106                if Restriction_Active (No_Dispatching_Calls) then
2107                   return;
2108                end if;
2109
2110                declare
2111                   Rtyp : constant Entity_Id := Root_Type (P_Type);
2112                   Dnn  : Entity_Id;
2113                   Decl : Node_Id;
2114
2115                begin
2116                   --  Read the internal tag (RM 13.13.2(34)) and use it to
2117                   --  initialize a dummy tag object:
2118
2119                   --    Dnn : Ada.Tags.Tag
2120                   --           := Descendant_Tag (String'Input (Strm), P_Type);
2121
2122                   --  This dummy object is used only to provide a controlling
2123                   --  argument for the eventual _Input call. Descendant_Tag is
2124                   --  called rather than Internal_Tag to ensure that we have a
2125                   --  tag for a type that is descended from the prefix type and
2126                   --  declared at the same accessibility level (the exception
2127                   --  Tag_Error will be raised otherwise). The level check is
2128                   --  required for Ada 2005 because tagged types can be
2129                   --  extended in nested scopes (AI-344).
2130
2131                   Dnn :=
2132                     Make_Defining_Identifier (Loc,
2133                       Chars => New_Internal_Name ('D'));
2134
2135                   Decl :=
2136                     Make_Object_Declaration (Loc,
2137                       Defining_Identifier => Dnn,
2138                       Object_Definition =>
2139                         New_Occurrence_Of (RTE (RE_Tag), Loc),
2140                       Expression =>
2141                         Make_Function_Call (Loc,
2142                           Name =>
2143                             New_Occurrence_Of (RTE (RE_Descendant_Tag), Loc),
2144                           Parameter_Associations => New_List (
2145                             Make_Attribute_Reference (Loc,
2146                               Prefix =>
2147                                 New_Occurrence_Of (Standard_String, Loc),
2148                               Attribute_Name => Name_Input,
2149                               Expressions => New_List (
2150                                 Relocate_Node
2151                                   (Duplicate_Subexpr (Strm)))),
2152                             Make_Attribute_Reference (Loc,
2153                               Prefix => New_Reference_To (P_Type, Loc),
2154                               Attribute_Name => Name_Tag))));
2155
2156                   Insert_Action (N, Decl);
2157
2158                   --  Now we need to get the entity for the call, and construct
2159                   --  a function call node, where we preset a reference to Dnn
2160                   --  as the controlling argument (doing an unchecked convert
2161                   --  to the class-wide tagged type to make it look like a real
2162                   --  tagged object).
2163
2164                   Fname := Find_Prim_Op (Rtyp, TSS_Stream_Input);
2165                   Cntrl := Unchecked_Convert_To (P_Type,
2166                              New_Occurrence_Of (Dnn, Loc));
2167                   Set_Etype (Cntrl, P_Type);
2168                   Set_Parent (Cntrl, N);
2169                end;
2170
2171             --  For tagged types, use the primitive Input function
2172
2173             elsif Is_Tagged_Type (U_Type) then
2174                Fname := Find_Prim_Op (U_Type, TSS_Stream_Input);
2175
2176             --  All other record type cases, including protected records. The
2177             --  latter only arise for expander generated code for handling
2178             --  shared passive partition access.
2179
2180             else
2181                pragma Assert
2182                  (Is_Record_Type (U_Type) or else Is_Protected_Type (U_Type));
2183
2184                --  Ada 2005 (AI-216): Program_Error is raised when executing
2185                --  the default implementation of the Input attribute of an
2186                --  unchecked union type if the type lacks default discriminant
2187                --  values.
2188
2189                if Is_Unchecked_Union (Base_Type (U_Type))
2190                  and then No (Discriminant_Constraint (U_Type))
2191                then
2192                   Insert_Action (N,
2193                     Make_Raise_Program_Error (Loc,
2194                       Reason => PE_Unchecked_Union_Restriction));
2195
2196                   return;
2197                end if;
2198
2199                Build_Record_Or_Elementary_Input_Function
2200                  (Loc, Base_Type (U_Type), Decl, Fname);
2201                Insert_Action (N, Decl);
2202
2203                if Nkind (Parent (N)) = N_Object_Declaration
2204                  and then Is_Record_Type (U_Type)
2205                then
2206                   --  The stream function may contain calls to user-defined
2207                   --  Read procedures for individual components.
2208
2209                   declare
2210                      Comp : Entity_Id;
2211                      Func : Entity_Id;
2212
2213                   begin
2214                      Comp := First_Component (U_Type);
2215                      while Present (Comp) loop
2216                         Func :=
2217                           Find_Stream_Subprogram
2218                             (Etype (Comp), TSS_Stream_Read);
2219
2220                         if Present (Func) then
2221                            Freeze_Stream_Subprogram (Func);
2222                         end if;
2223
2224                         Next_Component (Comp);
2225                      end loop;
2226                   end;
2227                end if;
2228             end if;
2229          end if;
2230
2231          --  If we fall through, Fname is the function to be called. The result
2232          --  is obtained by calling the appropriate function, then converting
2233          --  the result. The conversion does a subtype check.
2234
2235          Call :=
2236            Make_Function_Call (Loc,
2237              Name => New_Occurrence_Of (Fname, Loc),
2238              Parameter_Associations => New_List (
2239                 Relocate_Node (Strm)));
2240
2241          Set_Controlling_Argument (Call, Cntrl);
2242          Rewrite (N, Unchecked_Convert_To (P_Type, Call));
2243          Analyze_And_Resolve (N, P_Type);
2244
2245          if Nkind (Parent (N)) = N_Object_Declaration then
2246             Freeze_Stream_Subprogram (Fname);
2247          end if;
2248       end Input;
2249
2250       -------------------
2251       -- Integer_Value --
2252       -------------------
2253
2254       --  We transform
2255
2256       --    inttype'Fixed_Value (fixed-value)
2257
2258       --  into
2259
2260       --    inttype(integer-value))
2261
2262       --  we do all the required analysis of the conversion here, because
2263       --  we do not want this to go through the fixed-point conversion
2264       --  circuits. Note that gigi always treats fixed-point as equivalent
2265       --  to the corresponding integer type anyway.
2266
2267       when Attribute_Integer_Value => Integer_Value :
2268       begin
2269          Rewrite (N,
2270            Make_Type_Conversion (Loc,
2271              Subtype_Mark => New_Occurrence_Of (Entity (Pref), Loc),
2272              Expression   => Relocate_Node (First (Exprs))));
2273          Set_Etype (N, Entity (Pref));
2274          Set_Analyzed (N);
2275
2276       --  Note: it might appear that a properly analyzed unchecked conversion
2277       --  would be just fine here, but that's not the case, since the full
2278       --  range checks performed by the following call are critical!
2279
2280          Apply_Type_Conversion_Checks (N);
2281       end Integer_Value;
2282
2283       ----------
2284       -- Last --
2285       ----------
2286
2287       when Attribute_Last => declare
2288          Ptyp : constant Entity_Id := Etype (Pref);
2289
2290       begin
2291          --  If the prefix type is a constrained packed array type which
2292          --  already has a Packed_Array_Type representation defined, then
2293          --  replace this attribute with a direct reference to 'Last of the
2294          --  appropriate index subtype (since otherwise Gigi will try to give
2295          --  us the value of 'Last for this implementation type).
2296
2297          if Is_Constrained_Packed_Array (Ptyp) then
2298             Rewrite (N,
2299               Make_Attribute_Reference (Loc,
2300                 Attribute_Name => Name_Last,
2301                 Prefix => New_Reference_To (Get_Index_Subtype (N), Loc)));
2302             Analyze_And_Resolve (N, Typ);
2303
2304          elsif Is_Access_Type (Ptyp) then
2305             Apply_Access_Check (N);
2306          end if;
2307       end;
2308
2309       --------------
2310       -- Last_Bit --
2311       --------------
2312
2313       --  We compute this if a component clause was present, otherwise
2314       --  we leave the computation up to Gigi, since we don't know what
2315       --  layout will be chosen.
2316
2317       when Attribute_Last_Bit => Last_Bit :
2318       declare
2319          CE : constant Entity_Id := Entity (Selector_Name (Pref));
2320
2321       begin
2322          if Known_Static_Component_Bit_Offset (CE)
2323            and then Known_Static_Esize (CE)
2324          then
2325             Rewrite (N,
2326               Make_Integer_Literal (Loc,
2327                Intval => (Component_Bit_Offset (CE) mod System_Storage_Unit)
2328                                 + Esize (CE) - 1));
2329
2330             Analyze_And_Resolve (N, Typ);
2331
2332          else
2333             Apply_Universal_Integer_Attribute_Checks (N);
2334          end if;
2335       end Last_Bit;
2336
2337       ------------------
2338       -- Leading_Part --
2339       ------------------
2340
2341       --  Transforms 'Leading_Part into a call to the floating-point attribute
2342       --  function Leading_Part in Fat_xxx (where xxx is the root type)
2343
2344       --  Note: strictly, we should have special case code to deal with
2345       --  absurdly large positive arguments (greater than Integer'Last), which
2346       --  result in returning the first argument unchanged, but it hardly seems
2347       --  worth the effort. We raise constraint error for absurdly negative
2348       --  arguments which is fine.
2349
2350       when Attribute_Leading_Part =>
2351          Expand_Fpt_Attribute_RI (N);
2352
2353       ------------
2354       -- Length --
2355       ------------
2356
2357       when Attribute_Length => declare
2358          Ptyp : constant Entity_Id := Etype (Pref);
2359          Ityp : Entity_Id;
2360          Xnum : Uint;
2361
2362       begin
2363          --  Processing for packed array types
2364
2365          if Is_Array_Type (Ptyp) and then Is_Packed (Ptyp) then
2366             Ityp := Get_Index_Subtype (N);
2367
2368             --  If the index type, Ityp, is an enumeration type with
2369             --  holes, then we calculate X'Length explicitly using
2370
2371             --     Typ'Max
2372             --       (0, Ityp'Pos (X'Last  (N)) -
2373             --           Ityp'Pos (X'First (N)) + 1);
2374
2375             --  Since the bounds in the template are the representation
2376             --  values and gigi would get the wrong value.
2377
2378             if Is_Enumeration_Type (Ityp)
2379               and then Present (Enum_Pos_To_Rep (Base_Type (Ityp)))
2380             then
2381                if No (Exprs) then
2382                   Xnum := Uint_1;
2383                else
2384                   Xnum := Expr_Value (First (Expressions (N)));
2385                end if;
2386
2387                Rewrite (N,
2388                  Make_Attribute_Reference (Loc,
2389                    Prefix         => New_Occurrence_Of (Typ, Loc),
2390                    Attribute_Name => Name_Max,
2391                    Expressions    => New_List
2392                      (Make_Integer_Literal (Loc, 0),
2393
2394                       Make_Op_Add (Loc,
2395                         Left_Opnd =>
2396                           Make_Op_Subtract (Loc,
2397                             Left_Opnd =>
2398                               Make_Attribute_Reference (Loc,
2399                                 Prefix => New_Occurrence_Of (Ityp, Loc),
2400                                 Attribute_Name => Name_Pos,
2401
2402                                 Expressions => New_List (
2403                                   Make_Attribute_Reference (Loc,
2404                                     Prefix => Duplicate_Subexpr (Pref),
2405                                    Attribute_Name => Name_Last,
2406                                     Expressions => New_List (
2407                                       Make_Integer_Literal (Loc, Xnum))))),
2408
2409                             Right_Opnd =>
2410                               Make_Attribute_Reference (Loc,
2411                                 Prefix => New_Occurrence_Of (Ityp, Loc),
2412                                 Attribute_Name => Name_Pos,
2413
2414                                 Expressions => New_List (
2415                                   Make_Attribute_Reference (Loc,
2416                                     Prefix =>
2417                                       Duplicate_Subexpr_No_Checks (Pref),
2418                                    Attribute_Name => Name_First,
2419                                     Expressions => New_List (
2420                                       Make_Integer_Literal (Loc, Xnum)))))),
2421
2422                         Right_Opnd => Make_Integer_Literal (Loc, 1)))));
2423
2424                Analyze_And_Resolve (N, Typ, Suppress => All_Checks);
2425                return;
2426
2427             --  If the prefix type is a constrained packed array type which
2428             --  already has a Packed_Array_Type representation defined, then
2429             --  replace this attribute with a direct reference to 'Range_Length
2430             --  of the appropriate index subtype (since otherwise Gigi will try
2431             --  to give us the value of 'Length for this implementation type).
2432
2433             elsif Is_Constrained (Ptyp) then
2434                Rewrite (N,
2435                  Make_Attribute_Reference (Loc,
2436                    Attribute_Name => Name_Range_Length,
2437                    Prefix => New_Reference_To (Ityp, Loc)));
2438                Analyze_And_Resolve (N, Typ);
2439             end if;
2440
2441          --  If we have a packed array that is not bit packed, which was
2442
2443          --  Access type case
2444
2445          elsif Is_Access_Type (Ptyp) then
2446             Apply_Access_Check (N);
2447
2448             --  If the designated type is a packed array type, then we
2449             --  convert the reference to:
2450
2451             --    typ'Max (0, 1 +
2452             --                xtyp'Pos (Pref'Last (Expr)) -
2453             --                xtyp'Pos (Pref'First (Expr)));
2454
2455             --  This is a bit complex, but it is the easiest thing to do
2456             --  that works in all cases including enum types with holes
2457             --  xtyp here is the appropriate index type.
2458
2459             declare
2460                Dtyp : constant Entity_Id := Designated_Type (Ptyp);
2461                Xtyp : Entity_Id;
2462
2463             begin
2464                if Is_Array_Type (Dtyp) and then Is_Packed (Dtyp) then
2465                   Xtyp := Get_Index_Subtype (N);
2466
2467                   Rewrite (N,
2468                     Make_Attribute_Reference (Loc,
2469                       Prefix         => New_Occurrence_Of (Typ, Loc),
2470                       Attribute_Name => Name_Max,
2471                       Expressions    => New_List (
2472                         Make_Integer_Literal (Loc, 0),
2473
2474                         Make_Op_Add (Loc,
2475                           Make_Integer_Literal (Loc, 1),
2476                           Make_Op_Subtract (Loc,
2477                             Left_Opnd =>
2478                               Make_Attribute_Reference (Loc,
2479                                 Prefix => New_Occurrence_Of (Xtyp, Loc),
2480                                 Attribute_Name => Name_Pos,
2481                                 Expressions    => New_List (
2482                                   Make_Attribute_Reference (Loc,
2483                                     Prefix => Duplicate_Subexpr (Pref),
2484                                     Attribute_Name => Name_Last,
2485                                     Expressions =>
2486                                       New_Copy_List (Exprs)))),
2487
2488                             Right_Opnd =>
2489                               Make_Attribute_Reference (Loc,
2490                                 Prefix => New_Occurrence_Of (Xtyp, Loc),
2491                                 Attribute_Name => Name_Pos,
2492                                 Expressions    => New_List (
2493                                   Make_Attribute_Reference (Loc,
2494                                     Prefix =>
2495                                       Duplicate_Subexpr_No_Checks (Pref),
2496                                     Attribute_Name => Name_First,
2497                                     Expressions =>
2498                                       New_Copy_List (Exprs)))))))));
2499
2500                   Analyze_And_Resolve (N, Typ);
2501                end if;
2502             end;
2503
2504          --  Otherwise leave it to gigi
2505
2506          else
2507             Apply_Universal_Integer_Attribute_Checks (N);
2508          end if;
2509       end;
2510
2511       -------------
2512       -- Machine --
2513       -------------
2514
2515       --  Transforms 'Machine into a call to the floating-point attribute
2516       --  function Machine in Fat_xxx (where xxx is the root type)
2517
2518       when Attribute_Machine =>
2519          Expand_Fpt_Attribute_R (N);
2520
2521       ----------------------
2522       -- Machine_Rounding --
2523       ----------------------
2524
2525       --  Transforms 'Machine_Rounding into a call to the floating-point
2526       --  attribute function Machine_Rounding in Fat_xxx (where xxx is the root
2527       --  type). Expansion is avoided for cases the back end can handle
2528       --  directly.
2529
2530       when Attribute_Machine_Rounding =>
2531          if not Is_Inline_Floating_Point_Attribute (N) then
2532             Expand_Fpt_Attribute_R (N);
2533          end if;
2534
2535       ------------------
2536       -- Machine_Size --
2537       ------------------
2538
2539       --  Machine_Size is equivalent to Object_Size, so transform it into
2540       --  Object_Size and that way Gigi never sees Machine_Size.
2541
2542       when Attribute_Machine_Size =>
2543          Rewrite (N,
2544            Make_Attribute_Reference (Loc,
2545              Prefix => Prefix (N),
2546              Attribute_Name => Name_Object_Size));
2547
2548          Analyze_And_Resolve (N, Typ);
2549
2550       --------------
2551       -- Mantissa --
2552       --------------
2553
2554       --  The only case that can get this far is the dynamic case of the old
2555       --  Ada 83 Mantissa attribute for the fixed-point case. For this case, we
2556       --  expand:
2557
2558       --    typ'Mantissa
2559
2560       --  into
2561
2562       --    ityp (System.Mantissa.Mantissa_Value
2563       --           (Integer'Integer_Value (typ'First),
2564       --            Integer'Integer_Value (typ'Last)));
2565
2566       when Attribute_Mantissa => Mantissa : declare
2567          Ptyp : constant Entity_Id := Etype (Pref);
2568
2569       begin
2570          Rewrite (N,
2571            Convert_To (Typ,
2572              Make_Function_Call (Loc,
2573                Name => New_Occurrence_Of (RTE (RE_Mantissa_Value), Loc),
2574
2575                Parameter_Associations => New_List (
2576
2577                  Make_Attribute_Reference (Loc,
2578                    Prefix => New_Occurrence_Of (Standard_Integer, Loc),
2579                    Attribute_Name => Name_Integer_Value,
2580                    Expressions => New_List (
2581
2582                      Make_Attribute_Reference (Loc,
2583                        Prefix => New_Occurrence_Of (Ptyp, Loc),
2584                        Attribute_Name => Name_First))),
2585
2586                  Make_Attribute_Reference (Loc,
2587                    Prefix => New_Occurrence_Of (Standard_Integer, Loc),
2588                    Attribute_Name => Name_Integer_Value,
2589                    Expressions => New_List (
2590
2591                      Make_Attribute_Reference (Loc,
2592                        Prefix => New_Occurrence_Of (Ptyp, Loc),
2593                        Attribute_Name => Name_Last)))))));
2594
2595          Analyze_And_Resolve (N, Typ);
2596       end Mantissa;
2597
2598       --------------------
2599       -- Mechanism_Code --
2600       --------------------
2601
2602       when Attribute_Mechanism_Code =>
2603
2604          --  We must replace the prefix in the renamed case
2605
2606          if Is_Entity_Name (Pref)
2607            and then Present (Alias (Entity (Pref)))
2608          then
2609             Set_Renamed_Subprogram (Pref, Alias (Entity (Pref)));
2610          end if;
2611
2612       ---------
2613       -- Mod --
2614       ---------
2615
2616       when Attribute_Mod => Mod_Case : declare
2617          Arg  : constant Node_Id := Relocate_Node (First (Exprs));
2618          Hi   : constant Node_Id := Type_High_Bound (Etype (Arg));
2619          Modv : constant Uint    := Modulus (Btyp);
2620
2621       begin
2622
2623          --  This is not so simple. The issue is what type to use for the
2624          --  computation of the modular value.
2625
2626          --  The easy case is when the modulus value is within the bounds
2627          --  of the signed integer type of the argument. In this case we can
2628          --  just do the computation in that signed integer type, and then
2629          --  do an ordinary conversion to the target type.
2630
2631          if Modv <= Expr_Value (Hi) then
2632             Rewrite (N,
2633               Convert_To (Btyp,
2634                 Make_Op_Mod (Loc,
2635                   Left_Opnd  => Arg,
2636                   Right_Opnd => Make_Integer_Literal (Loc, Modv))));
2637
2638          --  Here we know that the modulus is larger than type'Last of the
2639          --  integer type. There are two cases to consider:
2640
2641          --    a) The integer value is non-negative. In this case, it is
2642          --    returned as the result (since it is less than the modulus).
2643
2644          --    b) The integer value is negative. In this case, we know that the
2645          --    result is modulus + value, where the value might be as small as
2646          --    -modulus. The trouble is what type do we use to do the subtract.
2647          --    No type will do, since modulus can be as big as 2**64, and no
2648          --    integer type accomodates this value. Let's do bit of algebra
2649
2650          --         modulus + value
2651          --      =  modulus - (-value)
2652          --      =  (modulus - 1) - (-value - 1)
2653
2654          --    Now modulus - 1 is certainly in range of the modular type.
2655          --    -value is in the range 1 .. modulus, so -value -1 is in the
2656          --    range 0 .. modulus-1 which is in range of the modular type.
2657          --    Furthermore, (-value - 1) can be expressed as -(value + 1)
2658          --    which we can compute using the integer base type.
2659
2660          --  Once this is done we analyze the conditional expression without
2661          --  range checks, because we know everything is in range, and we
2662          --  want to prevent spurious warnings on either branch.
2663
2664          else
2665             Rewrite (N,
2666               Make_Conditional_Expression (Loc,
2667                 Expressions => New_List (
2668                   Make_Op_Ge (Loc,
2669                     Left_Opnd  => Duplicate_Subexpr (Arg),
2670                     Right_Opnd => Make_Integer_Literal (Loc, 0)),
2671
2672                   Convert_To (Btyp,
2673                     Duplicate_Subexpr_No_Checks (Arg)),
2674
2675                   Make_Op_Subtract (Loc,
2676                     Left_Opnd =>
2677                       Make_Integer_Literal (Loc,
2678                         Intval => Modv - 1),
2679                     Right_Opnd =>
2680                       Convert_To (Btyp,
2681                         Make_Op_Minus (Loc,
2682                           Right_Opnd =>
2683                             Make_Op_Add (Loc,
2684                               Left_Opnd  => Duplicate_Subexpr_No_Checks (Arg),
2685                               Right_Opnd =>
2686                                 Make_Integer_Literal (Loc,
2687                                   Intval => 1))))))));
2688
2689          end if;
2690
2691          Analyze_And_Resolve (N, Btyp, Suppress => All_Checks);
2692       end Mod_Case;
2693
2694       -----------
2695       -- Model --
2696       -----------
2697
2698       --  Transforms 'Model into a call to the floating-point attribute
2699       --  function Model in Fat_xxx (where xxx is the root type)
2700
2701       when Attribute_Model =>
2702          Expand_Fpt_Attribute_R (N);
2703
2704       -----------------
2705       -- Object_Size --
2706       -----------------
2707
2708       --  The processing for Object_Size shares the processing for Size
2709
2710       ------------
2711       -- Output --
2712       ------------
2713
2714       when Attribute_Output => Output : declare
2715          P_Type : constant Entity_Id := Entity (Pref);
2716          U_Type : constant Entity_Id := Underlying_Type (P_Type);
2717          Pname  : Entity_Id;
2718          Decl   : Node_Id;
2719          Prag   : Node_Id;
2720          Arg3   : Node_Id;
2721          Wfunc  : Node_Id;
2722
2723       begin
2724          --  If no underlying type, we have an error that will be diagnosed
2725          --  elsewhere, so here we just completely ignore the expansion.
2726
2727          if No (U_Type) then
2728             return;
2729          end if;
2730
2731          --  If TSS for Output is present, just call it
2732
2733          Pname := Find_Stream_Subprogram (P_Type, TSS_Stream_Output);
2734
2735          if Present (Pname) then
2736             null;
2737
2738          else
2739             --  If there is a Stream_Convert pragma, use it, we rewrite
2740
2741             --     sourcetyp'Output (stream, Item)
2742
2743             --  as
2744
2745             --     strmtyp'Output (Stream, strmwrite (acttyp (Item)));
2746
2747             --  where strmwrite is the given Write function that converts an
2748             --  argument of type sourcetyp or a type acctyp, from which it is
2749             --  derived to type strmtyp. The conversion to acttyp is required
2750             --  for the derived case.
2751
2752             Prag := Get_Stream_Convert_Pragma (P_Type);
2753
2754             if Present (Prag) then
2755                Arg3 :=
2756                  Next (Next (First (Pragma_Argument_Associations (Prag))));
2757                Wfunc := Entity (Expression (Arg3));
2758
2759                Rewrite (N,
2760                  Make_Attribute_Reference (Loc,
2761                    Prefix => New_Occurrence_Of (Etype (Wfunc), Loc),
2762                    Attribute_Name => Name_Output,
2763                    Expressions => New_List (
2764                    Relocate_Node (First (Exprs)),
2765                      Make_Function_Call (Loc,
2766                        Name => New_Occurrence_Of (Wfunc, Loc),
2767                        Parameter_Associations => New_List (
2768                          OK_Convert_To (Etype (First_Formal (Wfunc)),
2769                            Relocate_Node (Next (First (Exprs)))))))));
2770
2771                Analyze (N);
2772                return;
2773
2774             --  For elementary types, we call the W_xxx routine directly.
2775             --  Note that the effect of Write and Output is identical for
2776             --  the case of an elementary type, since there are no
2777             --  discriminants or bounds.
2778
2779             elsif Is_Elementary_Type (U_Type) then
2780
2781                --  A special case arises if we have a defined _Write routine,
2782                --  since in this case we are required to call this routine.
2783
2784                if Present (TSS (Base_Type (U_Type), TSS_Stream_Write)) then
2785                   Build_Record_Or_Elementary_Output_Procedure
2786                     (Loc, U_Type, Decl, Pname);
2787                   Insert_Action (N, Decl);
2788
2789                --  For normal cases, we call the W_xxx routine directly
2790
2791                else
2792                   Rewrite (N, Build_Elementary_Write_Call (N));
2793                   Analyze (N);
2794                   return;
2795                end if;
2796
2797             --  Array type case
2798
2799             elsif Is_Array_Type (U_Type) then
2800                Build_Array_Output_Procedure (Loc, U_Type, Decl, Pname);
2801                Compile_Stream_Body_In_Scope (N, Decl, U_Type, Check => False);
2802
2803             --  Class-wide case, first output external tag, then dispatch
2804             --  to the appropriate primitive Output function (RM 13.13.2(31)).
2805
2806             elsif Is_Class_Wide_Type (P_Type) then
2807
2808                --  No need to do anything else compiling under restriction
2809                --  No_Dispatching_Calls. During the semantic analysis we
2810                --  already notified such violation.
2811
2812                if Restriction_Active (No_Dispatching_Calls) then
2813                   return;
2814                end if;
2815
2816                Tag_Write : declare
2817                   Strm : constant Node_Id := First (Exprs);
2818                   Item : constant Node_Id := Next (Strm);
2819
2820                begin
2821                   --  Ada 2005 (AI-344): Check that the accessibility level
2822                   --  of the type of the output object is not deeper than
2823                   --  that of the attribute's prefix type.
2824
2825                   --  if Get_Access_Level (Item'Tag)
2826                   --       /= Get_Access_Level (P_Type'Tag)
2827                   --  then
2828                   --     raise Tag_Error;
2829                   --  end if;
2830
2831                   --  String'Output (Strm, External_Tag (Item'Tag));
2832
2833                   --  We cannot figure out a practical way to implement this
2834                   --  accessibility check on virtual machines, so we omit it.
2835
2836                   if Ada_Version >= Ada_05
2837                     and then VM_Target = No_VM
2838                   then
2839                      Insert_Action (N,
2840                        Make_Implicit_If_Statement (N,
2841                          Condition =>
2842                            Make_Op_Ne (Loc,
2843                              Left_Opnd  =>
2844                                Build_Get_Access_Level (Loc,
2845                                  Make_Attribute_Reference (Loc,
2846                                    Prefix         =>
2847                                      Relocate_Node (
2848                                        Duplicate_Subexpr (Item,
2849                                          Name_Req => True)),
2850                                    Attribute_Name => Name_Tag)),
2851
2852                              Right_Opnd =>
2853                                Make_Integer_Literal (Loc,
2854                                  Type_Access_Level (P_Type))),
2855
2856                          Then_Statements =>
2857                            New_List (Make_Raise_Statement (Loc,
2858                                        New_Occurrence_Of (
2859                                          RTE (RE_Tag_Error), Loc)))));
2860                   end if;
2861
2862                   Insert_Action (N,
2863                     Make_Attribute_Reference (Loc,
2864                       Prefix => New_Occurrence_Of (Standard_String, Loc),
2865                       Attribute_Name => Name_Output,
2866                       Expressions => New_List (
2867                         Relocate_Node (Duplicate_Subexpr (Strm)),
2868                         Make_Function_Call (Loc,
2869                           Name =>
2870                             New_Occurrence_Of (RTE (RE_External_Tag), Loc),
2871                           Parameter_Associations => New_List (
2872                            Make_Attribute_Reference (Loc,
2873                              Prefix =>
2874                                Relocate_Node
2875                                  (Duplicate_Subexpr (Item, Name_Req => True)),
2876                              Attribute_Name => Name_Tag))))));
2877                end Tag_Write;
2878
2879                Pname := Find_Prim_Op (U_Type, TSS_Stream_Output);
2880
2881             --  Tagged type case, use the primitive Output function
2882
2883             elsif Is_Tagged_Type (U_Type) then
2884                Pname := Find_Prim_Op (U_Type, TSS_Stream_Output);
2885
2886             --  All other record type cases, including protected records.
2887             --  The latter only arise for expander generated code for
2888             --  handling shared passive partition access.
2889
2890             else
2891                pragma Assert
2892                  (Is_Record_Type (U_Type) or else Is_Protected_Type (U_Type));
2893
2894                --  Ada 2005 (AI-216): Program_Error is raised when executing
2895                --  the default implementation of the Output attribute of an
2896                --  unchecked union type if the type lacks default discriminant
2897                --  values.
2898
2899                if Is_Unchecked_Union (Base_Type (U_Type))
2900                  and then No (Discriminant_Constraint (U_Type))
2901                then
2902                   Insert_Action (N,
2903                     Make_Raise_Program_Error (Loc,
2904                       Reason => PE_Unchecked_Union_Restriction));
2905
2906                   return;
2907                end if;
2908
2909                Build_Record_Or_Elementary_Output_Procedure
2910                  (Loc, Base_Type (U_Type), Decl, Pname);
2911                Insert_Action (N, Decl);
2912             end if;
2913          end if;
2914
2915          --  If we fall through, Pname is the name of the procedure to call
2916
2917          Rewrite_Stream_Proc_Call (Pname);
2918       end Output;
2919
2920       ---------
2921       -- Pos --
2922       ---------
2923
2924       --  For enumeration types with a standard representation, Pos is
2925       --  handled by Gigi.
2926
2927       --  For enumeration types, with a non-standard representation we
2928       --  generate a call to the _Rep_To_Pos function created when the
2929       --  type was frozen. The call has the form
2930
2931       --    _rep_to_pos (expr, flag)
2932
2933       --  The parameter flag is True if range checks are enabled, causing
2934       --  Program_Error to be raised if the expression has an invalid
2935       --  representation, and False if range checks are suppressed.
2936
2937       --  For integer types, Pos is equivalent to a simple integer
2938       --  conversion and we rewrite it as such
2939
2940       when Attribute_Pos => Pos :
2941       declare
2942          Etyp : Entity_Id := Base_Type (Entity (Pref));
2943
2944       begin
2945          --  Deal with zero/non-zero boolean values
2946
2947          if Is_Boolean_Type (Etyp) then
2948             Adjust_Condition (First (Exprs));
2949             Etyp := Standard_Boolean;
2950             Set_Prefix (N, New_Occurrence_Of (Standard_Boolean, Loc));
2951          end if;
2952
2953          --  Case of enumeration type
2954
2955          if Is_Enumeration_Type (Etyp) then
2956
2957             --  Non-standard enumeration type (generate call)
2958
2959             if Present (Enum_Pos_To_Rep (Etyp)) then
2960                Append_To (Exprs, Rep_To_Pos_Flag (Etyp, Loc));
2961                Rewrite (N,
2962                  Convert_To (Typ,
2963                    Make_Function_Call (Loc,
2964                      Name =>
2965                        New_Reference_To (TSS (Etyp, TSS_Rep_To_Pos), Loc),
2966                      Parameter_Associations => Exprs)));
2967
2968                Analyze_And_Resolve (N, Typ);
2969
2970             --  Standard enumeration type (do universal integer check)
2971
2972             else
2973                Apply_Universal_Integer_Attribute_Checks (N);
2974             end if;
2975
2976          --  Deal with integer types (replace by conversion)
2977
2978          elsif Is_Integer_Type (Etyp) then
2979             Rewrite (N, Convert_To (Typ, First (Exprs)));
2980             Analyze_And_Resolve (N, Typ);
2981          end if;
2982
2983       end Pos;
2984
2985       --------------
2986       -- Position --
2987       --------------
2988
2989       --  We compute this if a component clause was present, otherwise
2990       --  we leave the computation up to Gigi, since we don't know what
2991       --  layout will be chosen.
2992
2993       when Attribute_Position => Position :
2994       declare
2995          CE : constant Entity_Id := Entity (Selector_Name (Pref));
2996
2997       begin
2998          if Present (Component_Clause (CE)) then
2999             Rewrite (N,
3000               Make_Integer_Literal (Loc,
3001                 Intval => Component_Bit_Offset (CE) / System_Storage_Unit));
3002             Analyze_And_Resolve (N, Typ);
3003
3004          else
3005             Apply_Universal_Integer_Attribute_Checks (N);
3006          end if;
3007       end Position;
3008
3009       ----------
3010       -- Pred --
3011       ----------
3012
3013       --  1. Deal with enumeration types with holes
3014       --  2. For floating-point, generate call to attribute function
3015       --  3. For other cases, deal with constraint checking
3016
3017       when Attribute_Pred => Pred :
3018       declare
3019          Ptyp : constant Entity_Id := Base_Type (Etype (Pref));
3020
3021       begin
3022          --  For enumeration types with non-standard representations, we
3023          --  expand typ'Pred (x) into
3024
3025          --    Pos_To_Rep (Rep_To_Pos (x) - 1)
3026
3027          --    If the representation is contiguous, we compute instead
3028          --    Lit1 + Rep_to_Pos (x -1), to catch invalid representations.
3029
3030          if Is_Enumeration_Type (Ptyp)
3031            and then Present (Enum_Pos_To_Rep (Ptyp))
3032          then
3033             if Has_Contiguous_Rep (Ptyp) then
3034                Rewrite (N,
3035                   Unchecked_Convert_To (Ptyp,
3036                      Make_Op_Add (Loc,
3037                         Left_Opnd  =>
3038                          Make_Integer_Literal (Loc,
3039                            Enumeration_Rep (First_Literal (Ptyp))),
3040                         Right_Opnd =>
3041                           Make_Function_Call (Loc,
3042                             Name =>
3043                               New_Reference_To
3044                                (TSS (Ptyp, TSS_Rep_To_Pos), Loc),
3045
3046                             Parameter_Associations =>
3047                               New_List (
3048                                 Unchecked_Convert_To (Ptyp,
3049                                   Make_Op_Subtract (Loc,
3050                                     Left_Opnd =>
3051                                      Unchecked_Convert_To (Standard_Integer,
3052                                        Relocate_Node (First (Exprs))),
3053                                     Right_Opnd =>
3054                                       Make_Integer_Literal (Loc, 1))),
3055                                 Rep_To_Pos_Flag (Ptyp, Loc))))));
3056
3057             else
3058                --  Add Boolean parameter True, to request program errror if
3059                --  we have a bad representation on our hands. If checks are
3060                --  suppressed, then add False instead
3061
3062                Append_To (Exprs, Rep_To_Pos_Flag (Ptyp, Loc));
3063                Rewrite (N,
3064                  Make_Indexed_Component (Loc,
3065                    Prefix => New_Reference_To (Enum_Pos_To_Rep (Ptyp), Loc),
3066                    Expressions => New_List (
3067                      Make_Op_Subtract (Loc,
3068                     Left_Opnd =>
3069                       Make_Function_Call (Loc,
3070                         Name =>
3071                           New_Reference_To (TSS (Ptyp, TSS_Rep_To_Pos), Loc),
3072                           Parameter_Associations => Exprs),
3073                     Right_Opnd => Make_Integer_Literal (Loc, 1)))));
3074             end if;
3075
3076             Analyze_And_Resolve (N, Typ);
3077
3078          --  For floating-point, we transform 'Pred into a call to the Pred
3079          --  floating-point attribute function in Fat_xxx (xxx is root type)
3080
3081          elsif Is_Floating_Point_Type (Ptyp) then
3082             Expand_Fpt_Attribute_R (N);
3083             Analyze_And_Resolve (N, Typ);
3084
3085          --  For modular types, nothing to do (no overflow, since wraps)
3086
3087          elsif Is_Modular_Integer_Type (Ptyp) then
3088             null;
3089
3090          --  For other types, if range checking is enabled, we must generate
3091          --  a check if overflow checking is enabled.
3092
3093          elsif not Overflow_Checks_Suppressed (Ptyp) then
3094             Expand_Pred_Succ (N);
3095          end if;
3096       end Pred;
3097
3098       --------------
3099       -- Priority --
3100       --------------
3101
3102       --  Ada 2005 (AI-327): Dynamic ceiling priorities
3103
3104       --  We rewrite X'Priority as the following run-time call:
3105
3106       --     Get_Ceiling (X._Object)
3107
3108       --  Note that although X'Priority is notionally an object, it is quite
3109       --  deliberately not defined as an aliased object in the RM. This means
3110       --  that it works fine to rewrite it as a call, without having to worry
3111       --  about complications that would other arise from X'Priority'Access,
3112       --  which is illegal, because of the lack of aliasing.
3113
3114       when Attribute_Priority =>
3115          declare
3116             Call           : Node_Id;
3117             Conctyp        : Entity_Id;
3118             Object_Parm    : Node_Id;
3119             Subprg         : Entity_Id;
3120             RT_Subprg_Name : Node_Id;
3121
3122          begin
3123             --  Look for the enclosing concurrent type
3124
3125             Conctyp := Current_Scope;
3126             while not Is_Concurrent_Type (Conctyp) loop
3127                Conctyp := Scope (Conctyp);
3128             end loop;
3129
3130             pragma Assert (Is_Protected_Type (Conctyp));
3131
3132             --  Generate the actual of the call
3133
3134             Subprg := Current_Scope;
3135             while not Present (Protected_Body_Subprogram (Subprg)) loop
3136                Subprg := Scope (Subprg);
3137             end loop;
3138
3139             --  Use of 'Priority inside protected entries and barriers (in
3140             --  both cases the type of the first formal of their expanded
3141             --  subprogram is Address)
3142
3143             if Etype (First_Entity (Protected_Body_Subprogram (Subprg)))
3144               = RTE (RE_Address)
3145             then
3146                declare
3147                   New_Itype : Entity_Id;
3148
3149                begin
3150                   --  In the expansion of protected entries the type of the
3151                   --  first formal of the Protected_Body_Subprogram is an
3152                   --  Address. In order to reference the _object component
3153                   --  we generate:
3154
3155                   --    type T is access p__ptTV;
3156                   --    freeze T []
3157
3158                   New_Itype := Create_Itype (E_Access_Type, N);
3159                   Set_Etype (New_Itype, New_Itype);
3160                   Init_Esize (New_Itype);
3161                   Init_Size_Align (New_Itype);
3162                   Set_Directly_Designated_Type (New_Itype,
3163                     Corresponding_Record_Type (Conctyp));
3164                   Freeze_Itype (New_Itype, N);
3165
3166                   --  Generate:
3167                   --    T!(O)._object'unchecked_access
3168
3169                   Object_Parm :=
3170                     Make_Attribute_Reference (Loc,
3171                        Prefix =>
3172                          Make_Selected_Component (Loc,
3173                            Prefix =>
3174                              Unchecked_Convert_To (New_Itype,
3175                                New_Reference_To
3176                                  (First_Entity
3177                                    (Protected_Body_Subprogram (Subprg)),
3178                                   Loc)),
3179                            Selector_Name =>
3180                              Make_Identifier (Loc, Name_uObject)),
3181                        Attribute_Name => Name_Unchecked_Access);
3182                end;
3183
3184             --  Use of 'Priority inside a protected subprogram
3185
3186             else
3187                Object_Parm :=
3188                  Make_Attribute_Reference (Loc,
3189                     Prefix =>
3190                       Make_Selected_Component (Loc,
3191                         Prefix => New_Reference_To
3192                                     (First_Entity
3193                                       (Protected_Body_Subprogram (Subprg)),
3194                                        Loc),
3195                         Selector_Name =>
3196                           Make_Identifier (Loc, Name_uObject)),
3197                     Attribute_Name => Name_Unchecked_Access);
3198             end if;
3199
3200             --  Select the appropriate run-time subprogram
3201
3202             if Number_Entries (Conctyp) = 0 then
3203                RT_Subprg_Name :=
3204                  New_Reference_To (RTE (RE_Get_Ceiling), Loc);
3205             else
3206                RT_Subprg_Name :=
3207                  New_Reference_To (RTE (RO_PE_Get_Ceiling), Loc);
3208             end if;
3209
3210             Call :=
3211               Make_Function_Call (Loc,
3212                 Name => RT_Subprg_Name,
3213                 Parameter_Associations => New_List (Object_Parm));
3214
3215             Rewrite (N, Call);
3216
3217             --  Avoid the generation of extra checks on the pointer to the
3218             --  protected object.
3219
3220             Analyze_And_Resolve (N, Typ, Suppress => Access_Check);
3221          end;
3222
3223       ------------------
3224       -- Range_Length --
3225       ------------------
3226
3227       when Attribute_Range_Length => Range_Length : declare
3228          P_Type : constant Entity_Id := Etype (Pref);
3229
3230       begin
3231          --  The only special processing required is for the case where
3232          --  Range_Length is applied to an enumeration type with holes.
3233          --  In this case we transform
3234
3235          --     X'Range_Length
3236
3237          --  to
3238
3239          --     X'Pos (X'Last) - X'Pos (X'First) + 1
3240
3241          --  So that the result reflects the proper Pos values instead
3242          --  of the underlying representations.
3243
3244          if Is_Enumeration_Type (P_Type)
3245            and then Has_Non_Standard_Rep (P_Type)
3246          then
3247             Rewrite (N,
3248               Make_Op_Add (Loc,
3249                 Left_Opnd =>
3250                   Make_Op_Subtract (Loc,
3251                     Left_Opnd =>
3252                       Make_Attribute_Reference (Loc,
3253                         Attribute_Name => Name_Pos,
3254                         Prefix => New_Occurrence_Of (P_Type, Loc),
3255                         Expressions => New_List (
3256                           Make_Attribute_Reference (Loc,
3257                             Attribute_Name => Name_Last,
3258                             Prefix => New_Occurrence_Of (P_Type, Loc)))),
3259
3260                     Right_Opnd =>
3261                       Make_Attribute_Reference (Loc,
3262                         Attribute_Name => Name_Pos,
3263                         Prefix => New_Occurrence_Of (P_Type, Loc),
3264                         Expressions => New_List (
3265                           Make_Attribute_Reference (Loc,
3266                             Attribute_Name => Name_First,
3267                             Prefix => New_Occurrence_Of (P_Type, Loc))))),
3268
3269                 Right_Opnd =>
3270                   Make_Integer_Literal (Loc, 1)));
3271
3272             Analyze_And_Resolve (N, Typ);
3273
3274          --  For all other cases, attribute is handled by Gigi, but we need
3275          --  to deal with the case of the range check on a universal integer.
3276
3277          else
3278             Apply_Universal_Integer_Attribute_Checks (N);
3279          end if;
3280       end Range_Length;
3281
3282       ----------
3283       -- Read --
3284       ----------
3285
3286       when Attribute_Read => Read : declare
3287          P_Type : constant Entity_Id := Entity (Pref);
3288          B_Type : constant Entity_Id := Base_Type (P_Type);
3289          U_Type : constant Entity_Id := Underlying_Type (P_Type);
3290          Pname  : Entity_Id;
3291          Decl   : Node_Id;
3292          Prag   : Node_Id;
3293          Arg2   : Node_Id;
3294          Rfunc  : Node_Id;
3295          Lhs    : Node_Id;
3296          Rhs    : Node_Id;
3297
3298       begin
3299          --  If no underlying type, we have an error that will be diagnosed
3300          --  elsewhere, so here we just completely ignore the expansion.
3301
3302          if No (U_Type) then
3303             return;
3304          end if;
3305
3306          --  The simple case, if there is a TSS for Read, just call it
3307
3308          Pname := Find_Stream_Subprogram (P_Type, TSS_Stream_Read);
3309
3310          if Present (Pname) then
3311             null;
3312
3313          else
3314             --  If there is a Stream_Convert pragma, use it, we rewrite
3315
3316             --     sourcetyp'Read (stream, Item)
3317
3318             --  as
3319
3320             --     Item := sourcetyp (strmread (strmtyp'Input (Stream)));
3321
3322             --  where strmread is the given Read function that converts an
3323             --  argument of type strmtyp to type sourcetyp or a type from which
3324             --  it is derived. The conversion to sourcetyp is required in the
3325             --  latter case.
3326
3327             --  A special case arises if Item is a type conversion in which
3328             --  case, we have to expand to:
3329
3330             --     Itemx := typex (strmread (strmtyp'Input (Stream)));
3331
3332             --  where Itemx is the expression of the type conversion (i.e.
3333             --  the actual object), and typex is the type of Itemx.
3334
3335             Prag := Get_Stream_Convert_Pragma (P_Type);
3336
3337             if Present (Prag) then
3338                Arg2  := Next (First (Pragma_Argument_Associations (Prag)));
3339                Rfunc := Entity (Expression (Arg2));
3340                Lhs := Relocate_Node (Next (First (Exprs)));
3341                Rhs :=
3342                  OK_Convert_To (B_Type,
3343                    Make_Function_Call (Loc,
3344                      Name => New_Occurrence_Of (Rfunc, Loc),
3345                      Parameter_Associations => New_List (
3346                        Make_Attribute_Reference (Loc,
3347                          Prefix =>
3348                            New_Occurrence_Of
3349                              (Etype (First_Formal (Rfunc)), Loc),
3350                          Attribute_Name => Name_Input,
3351                          Expressions => New_List (
3352                            Relocate_Node (First (Exprs)))))));
3353
3354                if Nkind (Lhs) = N_Type_Conversion then
3355                   Lhs := Expression (Lhs);
3356                   Rhs := Convert_To (Etype (Lhs), Rhs);
3357                end if;
3358
3359                Rewrite (N,
3360                  Make_Assignment_Statement (Loc,
3361                    Name       => Lhs,
3362                    Expression => Rhs));
3363                Set_Assignment_OK (Lhs);
3364                Analyze (N);
3365                return;
3366
3367             --  For elementary types, we call the I_xxx routine using the first
3368             --  parameter and then assign the result into the second parameter.
3369             --  We set Assignment_OK to deal with the conversion case.
3370
3371             elsif Is_Elementary_Type (U_Type) then
3372                declare
3373                   Lhs : Node_Id;
3374                   Rhs : Node_Id;
3375
3376                begin
3377                   Lhs := Relocate_Node (Next (First (Exprs)));
3378                   Rhs := Build_Elementary_Input_Call (N);
3379
3380                   if Nkind (Lhs) = N_Type_Conversion then
3381                      Lhs := Expression (Lhs);
3382                      Rhs := Convert_To (Etype (Lhs), Rhs);
3383                   end if;
3384
3385                   Set_Assignment_OK (Lhs);
3386
3387                   Rewrite (N,
3388                     Make_Assignment_Statement (Loc,
3389                       Name => Lhs,
3390                       Expression => Rhs));
3391
3392                   Analyze (N);
3393                   return;
3394                end;
3395
3396             --  Array type case
3397
3398             elsif Is_Array_Type (U_Type) then
3399                Build_Array_Read_Procedure (N, U_Type, Decl, Pname);
3400                Compile_Stream_Body_In_Scope (N, Decl, U_Type, Check => False);
3401
3402             --  Tagged type case, use the primitive Read function. Note that
3403             --  this will dispatch in the class-wide case which is what we want
3404
3405             elsif Is_Tagged_Type (U_Type) then
3406                Pname := Find_Prim_Op (U_Type, TSS_Stream_Read);
3407
3408             --  All other record type cases, including protected records. The
3409             --  latter only arise for expander generated code for handling
3410             --  shared passive partition access.
3411
3412             else
3413                pragma Assert
3414                  (Is_Record_Type (U_Type) or else Is_Protected_Type (U_Type));
3415
3416                --  Ada 2005 (AI-216): Program_Error is raised when executing
3417                --  the default implementation of the Read attribute of an
3418                --  Unchecked_Union type.
3419
3420                if Is_Unchecked_Union (Base_Type (U_Type)) then
3421                   Insert_Action (N,
3422                     Make_Raise_Program_Error (Loc,
3423                       Reason => PE_Unchecked_Union_Restriction));
3424                end if;
3425
3426                if Has_Discriminants (U_Type)
3427                  and then Present
3428                    (Discriminant_Default_Value (First_Discriminant (U_Type)))
3429                then
3430                   Build_Mutable_Record_Read_Procedure
3431                     (Loc, Base_Type (U_Type), Decl, Pname);
3432                else
3433                   Build_Record_Read_Procedure
3434                     (Loc, Base_Type (U_Type), Decl, Pname);
3435                end if;
3436
3437                --  Suppress checks, uninitialized or otherwise invalid
3438                --  data does not cause constraint errors to be raised for
3439                --  a complete record read.
3440
3441                Insert_Action (N, Decl, All_Checks);
3442             end if;
3443          end if;
3444
3445          Rewrite_Stream_Proc_Call (Pname);
3446       end Read;
3447
3448       ---------------
3449       -- Remainder --
3450       ---------------
3451
3452       --  Transforms 'Remainder into a call to the floating-point attribute
3453       --  function Remainder in Fat_xxx (where xxx is the root type)
3454
3455       when Attribute_Remainder =>
3456          Expand_Fpt_Attribute_RR (N);
3457
3458       -----------
3459       -- Round --
3460       -----------
3461
3462       --  The handling of the Round attribute is quite delicate. The processing
3463       --  in Sem_Attr introduced a conversion to universal real, reflecting the
3464       --  semantics of Round, but we do not want anything to do with universal
3465       --  real at runtime, since this corresponds to using floating-point
3466       --  arithmetic.
3467
3468       --  What we have now is that the Etype of the Round attribute correctly
3469       --  indicates the final result type. The operand of the Round is the
3470       --  conversion to universal real, described above, and the operand of
3471       --  this conversion is the actual operand of Round, which may be the
3472       --  special case of a fixed point multiplication or division (Etype =
3473       --  universal fixed)
3474
3475       --  The exapander will expand first the operand of the conversion, then
3476       --  the conversion, and finally the round attribute itself, since we
3477       --  always work inside out. But we cannot simply process naively in this
3478       --  order. In the semantic world where universal fixed and real really
3479       --  exist and have infinite precision, there is no problem, but in the
3480       --  implementation world, where universal real is a floating-point type,
3481       --  we would get the wrong result.
3482
3483       --  So the approach is as follows. First, when expanding a multiply or
3484       --  divide whose type is universal fixed, we do nothing at all, instead
3485       --  deferring the operation till later.
3486
3487       --  The actual processing is done in Expand_N_Type_Conversion which
3488       --  handles the special case of Round by looking at its parent to see if
3489       --  it is a Round attribute, and if it is, handling the conversion (or
3490       --  its fixed multiply/divide child) in an appropriate manner.
3491
3492       --  This means that by the time we get to expanding the Round attribute
3493       --  itself, the Round is nothing more than a type conversion (and will
3494       --  often be a null type conversion), so we just replace it with the
3495       --  appropriate conversion operation.
3496
3497       when Attribute_Round =>
3498          Rewrite (N,
3499            Convert_To (Etype (N), Relocate_Node (First (Exprs))));
3500          Analyze_And_Resolve (N);
3501
3502       --------------
3503       -- Rounding --
3504       --------------
3505
3506       --  Transforms 'Rounding into a call to the floating-point attribute
3507       --  function Rounding in Fat_xxx (where xxx is the root type)
3508
3509       when Attribute_Rounding =>
3510          Expand_Fpt_Attribute_R (N);
3511
3512       -------------
3513       -- Scaling --
3514       -------------
3515
3516       --  Transforms 'Scaling into a call to the floating-point attribute
3517       --  function Scaling in Fat_xxx (where xxx is the root type)
3518
3519       when Attribute_Scaling =>
3520          Expand_Fpt_Attribute_RI (N);
3521
3522       ----------
3523       -- Size --
3524       ----------
3525
3526       when Attribute_Size        |
3527            Attribute_Object_Size |
3528            Attribute_Value_Size  |
3529            Attribute_VADS_Size   => Size :
3530
3531       declare
3532          Ptyp     : constant Entity_Id := Etype (Pref);
3533          Siz      : Uint;
3534          New_Node : Node_Id;
3535
3536       begin
3537          --  Processing for VADS_Size case. Note that this processing removes
3538          --  all traces of VADS_Size from the tree, and completes all required
3539          --  processing for VADS_Size by translating the attribute reference
3540          --  to an appropriate Size or Object_Size reference.
3541
3542          if Id = Attribute_VADS_Size
3543            or else (Use_VADS_Size and then Id = Attribute_Size)
3544          then
3545             --  If the size is specified, then we simply use the specified
3546             --  size. This applies to both types and objects. The size of an
3547             --  object can be specified in the following ways:
3548
3549             --    An explicit size object is given for an object
3550             --    A component size is specified for an indexed component
3551             --    A component clause is specified for a selected component
3552             --    The object is a component of a packed composite object
3553
3554             --  If the size is specified, then VADS_Size of an object
3555
3556             if (Is_Entity_Name (Pref)
3557                  and then Present (Size_Clause (Entity (Pref))))
3558               or else
3559                 (Nkind (Pref) = N_Component_Clause
3560                   and then (Present (Component_Clause
3561                                      (Entity (Selector_Name (Pref))))
3562                              or else Is_Packed (Etype (Prefix (Pref)))))
3563               or else
3564                 (Nkind (Pref) = N_Indexed_Component
3565                   and then (Component_Size (Etype (Prefix (Pref))) /= 0
3566                              or else Is_Packed (Etype (Prefix (Pref)))))
3567             then
3568                Set_Attribute_Name (N, Name_Size);
3569
3570             --  Otherwise if we have an object rather than a type, then the
3571             --  VADS_Size attribute applies to the type of the object, rather
3572             --  than the object itself. This is one of the respects in which
3573             --  VADS_Size differs from Size.
3574
3575             else
3576                if (not Is_Entity_Name (Pref)
3577                     or else not Is_Type (Entity (Pref)))
3578                  and then (Is_Scalar_Type (Etype (Pref))
3579                             or else Is_Constrained (Etype (Pref)))
3580                then
3581                   Rewrite (Pref, New_Occurrence_Of (Etype (Pref), Loc));
3582                end if;
3583
3584                --  For a scalar type for which no size was explicitly given,
3585                --  VADS_Size means Object_Size. This is the other respect in
3586                --  which VADS_Size differs from Size.
3587
3588                if Is_Scalar_Type (Etype (Pref))
3589                  and then No (Size_Clause (Etype (Pref)))
3590                then
3591                   Set_Attribute_Name (N, Name_Object_Size);
3592
3593                --  In all other cases, Size and VADS_Size are the sane
3594
3595                else
3596                   Set_Attribute_Name (N, Name_Size);
3597                end if;
3598             end if;
3599          end if;
3600
3601          --  For class-wide types,  X'Class'Size is transformed into a
3602          --  direct reference to the Size of the class type, so that gigi
3603          --  does not have to deal with the X'Class'Size reference.
3604
3605          if Is_Entity_Name (Pref)
3606            and then Is_Class_Wide_Type (Entity (Pref))
3607          then
3608             Rewrite (Prefix (N), New_Occurrence_Of (Entity (Pref), Loc));
3609             return;
3610
3611          --  For X'Size applied to an object of a class-wide type, transform
3612          --  X'Size into a call to the primitive operation _Size applied to X.
3613
3614          elsif Is_Class_Wide_Type (Ptyp) then
3615
3616             --  No need to do anything else compiling under restriction
3617             --  No_Dispatching_Calls. During the semantic analysis we
3618             --  already notified such violation.
3619
3620             if Restriction_Active (No_Dispatching_Calls) then
3621                return;
3622             end if;
3623
3624             New_Node :=
3625               Make_Function_Call (Loc,
3626                 Name => New_Reference_To
3627                   (Find_Prim_Op (Ptyp, Name_uSize), Loc),
3628                 Parameter_Associations => New_List (Pref));
3629
3630             if Typ /= Standard_Long_Long_Integer then
3631
3632                --  The context is a specific integer type with which the
3633                --  original attribute was compatible. The function has a
3634                --  specific type as well, so to preserve the compatibility
3635                --  we must convert explicitly.
3636
3637                New_Node := Convert_To (Typ, New_Node);
3638             end if;
3639
3640             Rewrite (N, New_Node);
3641             Analyze_And_Resolve (N, Typ);
3642                return;
3643
3644          --  Case of known RM_Size of a type
3645
3646          elsif (Id = Attribute_Size or else Id = Attribute_Value_Size)
3647            and then Is_Entity_Name (Pref)
3648            and then Is_Type (Entity (Pref))
3649            and then Known_Static_RM_Size (Entity (Pref))
3650          then
3651             Siz := RM_Size (Entity (Pref));
3652
3653          --  Case of known Esize of a type
3654
3655          elsif Id = Attribute_Object_Size
3656            and then Is_Entity_Name (Pref)
3657            and then Is_Type (Entity (Pref))
3658            and then Known_Static_Esize (Entity (Pref))
3659          then
3660             Siz := Esize (Entity (Pref));
3661
3662          --  Case of known size of object
3663
3664          elsif Id = Attribute_Size
3665            and then Is_Entity_Name (Pref)
3666            and then Is_Object (Entity (Pref))
3667            and then Known_Esize (Entity (Pref))
3668            and then Known_Static_Esize (Entity (Pref))
3669          then
3670             Siz := Esize (Entity (Pref));
3671
3672          --  For an array component, we can do Size in the front end
3673          --  if the component_size of the array is set.
3674
3675          elsif Nkind (Pref) = N_Indexed_Component then
3676             Siz := Component_Size (Etype (Prefix (Pref)));
3677
3678          --  For a record component, we can do Size in the front end if there
3679          --  is a component clause, or if the record is packed and the
3680          --  component's size is known at compile time.
3681
3682          elsif Nkind (Pref) = N_Selected_Component then
3683             declare
3684                Rec  : constant Entity_Id := Etype (Prefix (Pref));
3685                Comp : constant Entity_Id := Entity (Selector_Name (Pref));
3686
3687             begin
3688                if Present (Component_Clause (Comp)) then
3689                   Siz := Esize (Comp);
3690
3691                elsif Is_Packed (Rec) then
3692                   Siz := RM_Size (Ptyp);
3693
3694                else
3695                   Apply_Universal_Integer_Attribute_Checks (N);
3696                   return;
3697                end if;
3698             end;
3699
3700          --  All other cases are handled by Gigi
3701
3702          else
3703             Apply_Universal_Integer_Attribute_Checks (N);
3704
3705             --  If Size is applied to a formal parameter that is of a packed
3706             --  array subtype, then apply Size to the actual subtype.
3707
3708             if Is_Entity_Name (Pref)
3709               and then Is_Formal (Entity (Pref))
3710               and then Is_Array_Type (Etype (Pref))
3711               and then Is_Packed (Etype (Pref))
3712             then
3713                Rewrite (N,
3714                  Make_Attribute_Reference (Loc,
3715                    Prefix =>
3716                      New_Occurrence_Of (Get_Actual_Subtype (Pref), Loc),
3717                    Attribute_Name => Name_Size));
3718                Analyze_And_Resolve (N, Typ);
3719             end if;
3720
3721             --  If Size applies to a dereference of an access to unconstrained
3722             --  packed array, GIGI needs to see its unconstrained nominal type,
3723             --  but also a hint to the actual constrained type.
3724
3725             if Nkind (Pref) = N_Explicit_Dereference
3726               and then Is_Array_Type (Etype (Pref))
3727               and then not Is_Constrained (Etype (Pref))
3728               and then Is_Packed (Etype (Pref))
3729             then
3730                Set_Actual_Designated_Subtype (Pref,
3731                  Get_Actual_Subtype (Pref));
3732             end if;
3733
3734             return;
3735          end if;
3736
3737          --  Common processing for record and array component case
3738
3739          if Siz /= No_Uint and then Siz /= 0 then
3740             Rewrite (N, Make_Integer_Literal (Loc, Siz));
3741
3742             Analyze_And_Resolve (N, Typ);
3743
3744             --  The result is not a static expression
3745
3746             Set_Is_Static_Expression (N, False);
3747          end if;
3748       end Size;
3749
3750       ------------------
3751       -- Storage_Pool --
3752       ------------------
3753
3754       when Attribute_Storage_Pool =>
3755          Rewrite (N,
3756            Make_Type_Conversion (Loc,
3757              Subtype_Mark => New_Reference_To (Etype (N), Loc),
3758              Expression   => New_Reference_To (Entity (N), Loc)));
3759          Analyze_And_Resolve (N, Typ);
3760
3761       ------------------
3762       -- Storage_Size --
3763       ------------------
3764
3765       when Attribute_Storage_Size => Storage_Size :
3766       declare
3767          Ptyp : constant Entity_Id := Etype (Pref);
3768
3769       begin
3770          --  Access type case, always go to the root type
3771
3772          --  The case of access types results in a value of zero for the case
3773          --  where no storage size attribute clause has been given. If a
3774          --  storage size has been given, then the attribute is converted
3775          --  to a reference to the variable used to hold this value.
3776
3777          if Is_Access_Type (Ptyp) then
3778             if Present (Storage_Size_Variable (Root_Type (Ptyp))) then
3779                Rewrite (N,
3780                  Make_Attribute_Reference (Loc,
3781                    Prefix => New_Reference_To (Typ, Loc),
3782                    Attribute_Name => Name_Max,
3783                    Expressions => New_List (
3784                      Make_Integer_Literal (Loc, 0),
3785                      Convert_To (Typ,
3786                        New_Reference_To
3787                          (Storage_Size_Variable (Root_Type (Ptyp)), Loc)))));
3788
3789             elsif Present (Associated_Storage_Pool (Root_Type (Ptyp))) then
3790                Rewrite (N,
3791                  OK_Convert_To (Typ,
3792                    Make_Function_Call (Loc,
3793                      Name =>
3794                        New_Reference_To
3795                          (Find_Prim_Op
3796                            (Etype (Associated_Storage_Pool (Root_Type (Ptyp))),
3797                             Attribute_Name (N)),
3798                           Loc),
3799
3800                      Parameter_Associations => New_List (
3801                        New_Reference_To
3802                          (Associated_Storage_Pool (Root_Type (Ptyp)), Loc)))));
3803
3804             else
3805                Rewrite (N, Make_Integer_Literal (Loc, 0));
3806             end if;
3807
3808             Analyze_And_Resolve (N, Typ);
3809
3810          --  For tasks, we retrieve the size directly from the TCB. The
3811          --  size may depend on a discriminant of the type, and therefore
3812          --  can be a per-object expression, so type-level information is
3813          --  not sufficient in general. There are four cases to consider:
3814
3815          --  a) If the attribute appears within a task body, the designated
3816          --    TCB is obtained by a call to Self.
3817
3818          --  b) If the prefix of the attribute is the name of a task object,
3819          --  the designated TCB is the one stored in the corresponding record.
3820
3821          --  c) If the prefix is a task type, the size is obtained from the
3822          --  size variable created for each task type
3823
3824          --  d) If no storage_size was specified for the type , there is no
3825          --  size variable, and the value is a system-specific default.
3826
3827          else
3828             if In_Open_Scopes (Ptyp) then
3829
3830                --  Storage_Size (Self)
3831
3832                Rewrite (N,
3833                  Convert_To (Typ,
3834                    Make_Function_Call (Loc,
3835                      Name =>
3836                        New_Occurrence_Of (RTE (RE_Storage_Size), Loc),
3837                      Parameter_Associations =>
3838                        New_List (
3839                          Make_Function_Call (Loc,
3840                            Name =>
3841                              New_Reference_To (RTE (RE_Self), Loc))))));
3842
3843             elsif not Is_Entity_Name (Pref)
3844               or else not Is_Type (Entity (Pref))
3845             then
3846                --  Storage_Size (Rec (Obj).Size)
3847
3848                Rewrite (N,
3849                  Convert_To (Typ,
3850                    Make_Function_Call (Loc,
3851                      Name =>
3852                        New_Occurrence_Of (RTE (RE_Storage_Size), Loc),
3853                        Parameter_Associations =>
3854                           New_List (
3855                             Make_Selected_Component (Loc,
3856                               Prefix =>
3857                                 Unchecked_Convert_To (
3858                                   Corresponding_Record_Type (Ptyp),
3859                                     New_Copy_Tree (Pref)),
3860                               Selector_Name =>
3861                                  Make_Identifier (Loc, Name_uTask_Id))))));
3862
3863             elsif Present (Storage_Size_Variable (Ptyp)) then
3864
3865                --  Static storage size pragma given for type: retrieve value
3866                --  from its allocated storage variable.
3867
3868                Rewrite (N,
3869                  Convert_To (Typ,
3870                    Make_Function_Call (Loc,
3871                      Name => New_Occurrence_Of (
3872                        RTE (RE_Adjust_Storage_Size), Loc),
3873                      Parameter_Associations =>
3874                        New_List (
3875                          New_Reference_To (
3876                            Storage_Size_Variable (Ptyp), Loc)))));
3877             else
3878                --  Get system default
3879
3880                Rewrite (N,
3881                  Convert_To (Typ,
3882                    Make_Function_Call (Loc,
3883                      Name =>
3884                        New_Occurrence_Of (
3885                         RTE (RE_Default_Stack_Size), Loc))));
3886             end if;
3887
3888             Analyze_And_Resolve (N, Typ);
3889          end if;
3890       end Storage_Size;
3891
3892       -----------------
3893       -- Stream_Size --
3894       -----------------
3895
3896       when Attribute_Stream_Size => Stream_Size : declare
3897          Ptyp : constant Entity_Id := Etype (Pref);
3898          Size : Int;
3899
3900       begin
3901          --  If we have a Stream_Size clause for this type use it, otherwise
3902          --  the Stream_Size if the size of the type.
3903
3904          if Has_Stream_Size_Clause (Ptyp) then
3905             Size :=
3906               UI_To_Int
3907                 (Static_Integer (Expression (Stream_Size_Clause (Ptyp))));
3908          else
3909             Size := UI_To_Int (Esize (Ptyp));
3910          end if;
3911
3912          Rewrite (N, Make_Integer_Literal (Loc, Intval => Size));
3913          Analyze_And_Resolve (N, Typ);
3914       end Stream_Size;
3915
3916       ----------
3917       -- Succ --
3918       ----------
3919
3920       --  1. Deal with enumeration types with holes
3921       --  2. For floating-point, generate call to attribute function
3922       --  3. For other cases, deal with constraint checking
3923
3924       when Attribute_Succ => Succ :
3925       declare
3926          Ptyp : constant Entity_Id := Base_Type (Etype (Pref));
3927
3928       begin
3929          --  For enumeration types with non-standard representations, we
3930          --  expand typ'Succ (x) into
3931
3932          --    Pos_To_Rep (Rep_To_Pos (x) + 1)
3933
3934          --    If the representation is contiguous, we compute instead
3935          --    Lit1 + Rep_to_Pos (x+1), to catch invalid representations.
3936
3937          if Is_Enumeration_Type (Ptyp)
3938            and then Present (Enum_Pos_To_Rep (Ptyp))
3939          then
3940             if Has_Contiguous_Rep (Ptyp) then
3941                Rewrite (N,
3942                   Unchecked_Convert_To (Ptyp,
3943                      Make_Op_Add (Loc,
3944                         Left_Opnd  =>
3945                          Make_Integer_Literal (Loc,
3946                            Enumeration_Rep (First_Literal (Ptyp))),
3947                         Right_Opnd =>
3948                           Make_Function_Call (Loc,
3949                             Name =>
3950                               New_Reference_To
3951                                (TSS (Ptyp, TSS_Rep_To_Pos), Loc),
3952
3953                             Parameter_Associations =>
3954                               New_List (
3955                                 Unchecked_Convert_To (Ptyp,
3956                                   Make_Op_Add (Loc,
3957                                   Left_Opnd =>
3958                                     Unchecked_Convert_To (Standard_Integer,
3959                                       Relocate_Node (First (Exprs))),
3960                                   Right_Opnd =>
3961                                     Make_Integer_Literal (Loc, 1))),
3962                                 Rep_To_Pos_Flag (Ptyp, Loc))))));
3963             else
3964                --  Add Boolean parameter True, to request program errror if
3965                --  we have a bad representation on our hands. Add False if
3966                --  checks are suppressed.
3967
3968                Append_To (Exprs, Rep_To_Pos_Flag (Ptyp, Loc));
3969                Rewrite (N,
3970                  Make_Indexed_Component (Loc,
3971                    Prefix => New_Reference_To (Enum_Pos_To_Rep (Ptyp), Loc),
3972                    Expressions => New_List (
3973                      Make_Op_Add (Loc,
3974                        Left_Opnd =>
3975                          Make_Function_Call (Loc,
3976                            Name =>
3977                              New_Reference_To
3978                                (TSS (Ptyp, TSS_Rep_To_Pos), Loc),
3979                            Parameter_Associations => Exprs),
3980                        Right_Opnd => Make_Integer_Literal (Loc, 1)))));
3981             end if;
3982
3983             Analyze_And_Resolve (N, Typ);
3984
3985          --  For floating-point, we transform 'Succ into a call to the Succ
3986          --  floating-point attribute function in Fat_xxx (xxx is root type)
3987
3988          elsif Is_Floating_Point_Type (Ptyp) then
3989             Expand_Fpt_Attribute_R (N);
3990             Analyze_And_Resolve (N, Typ);
3991
3992          --  For modular types, nothing to do (no overflow, since wraps)
3993
3994          elsif Is_Modular_Integer_Type (Ptyp) then
3995             null;
3996
3997          --  For other types, if range checking is enabled, we must generate
3998          --  a check if overflow checking is enabled.
3999
4000          elsif not Overflow_Checks_Suppressed (Ptyp) then
4001             Expand_Pred_Succ (N);
4002          end if;
4003       end Succ;
4004
4005       ---------
4006       -- Tag --
4007       ---------
4008
4009       --  Transforms X'Tag into a direct reference to the tag of X
4010
4011       when Attribute_Tag => Tag :
4012       declare
4013          Ttyp           : Entity_Id;
4014          Prefix_Is_Type : Boolean;
4015
4016       begin
4017          if Is_Entity_Name (Pref) and then Is_Type (Entity (Pref)) then
4018             Ttyp := Entity (Pref);
4019             Prefix_Is_Type := True;
4020          else
4021             Ttyp := Etype (Pref);
4022             Prefix_Is_Type := False;
4023          end if;
4024
4025          if Is_Class_Wide_Type (Ttyp) then
4026             Ttyp := Root_Type (Ttyp);
4027          end if;
4028
4029          Ttyp := Underlying_Type (Ttyp);
4030
4031          if Prefix_Is_Type then
4032
4033             --  For VMs we leave the type attribute unexpanded because
4034             --  there's not a dispatching table to reference.
4035
4036             if VM_Target = No_VM then
4037                Rewrite (N,
4038                  Unchecked_Convert_To (RTE (RE_Tag),
4039                    New_Reference_To
4040                      (Node (First_Elmt (Access_Disp_Table (Ttyp))), Loc)));
4041                Analyze_And_Resolve (N, RTE (RE_Tag));
4042             end if;
4043
4044          --  (Ada 2005 (AI-251): The use of 'Tag in the sources always
4045          --  references the primary tag of the actual object. If 'Tag is
4046          --  applied to class-wide interface objects we generate code that
4047          --  displaces "this" to reference the base of the object.
4048
4049          elsif Comes_From_Source (N)
4050             and then Is_Class_Wide_Type (Etype (Prefix (N)))
4051             and then Is_Interface (Etype (Prefix (N)))
4052          then
4053             --  Generate:
4054             --    (To_Tag_Ptr (Prefix'Address)).all
4055
4056             --  Note that Prefix'Address is recursively expanded into a call
4057             --  to Base_Address (Obj.Tag)
4058
4059             Rewrite (N,
4060               Make_Explicit_Dereference (Loc,
4061                 Unchecked_Convert_To (RTE (RE_Tag_Ptr),
4062                   Make_Attribute_Reference (Loc,
4063                     Prefix => Relocate_Node (Pref),
4064                     Attribute_Name => Name_Address))));
4065             Analyze_And_Resolve (N, RTE (RE_Tag));
4066
4067          else
4068             Rewrite (N,
4069               Make_Selected_Component (Loc,
4070                 Prefix => Relocate_Node (Pref),
4071                 Selector_Name =>
4072                   New_Reference_To (First_Tag_Component (Ttyp), Loc)));
4073             Analyze_And_Resolve (N, RTE (RE_Tag));
4074          end if;
4075       end Tag;
4076
4077       ----------------
4078       -- Terminated --
4079       ----------------
4080
4081       --  Transforms 'Terminated attribute into a call to Terminated function
4082
4083       when Attribute_Terminated => Terminated :
4084       begin
4085          --  The prefix of Terminated is of a task interface class-wide type.
4086          --  Generate:
4087
4088          --    terminated (Task_Id (Pref._disp_get_task_id));
4089
4090          if Ada_Version >= Ada_05
4091            and then Ekind (Etype (Pref)) = E_Class_Wide_Type
4092            and then Is_Interface (Etype (Pref))
4093            and then Is_Task_Interface (Etype (Pref))
4094          then
4095             Rewrite (N,
4096               Make_Function_Call (Loc,
4097                 Name =>
4098                   New_Reference_To (RTE (RE_Terminated), Loc),
4099                 Parameter_Associations => New_List (
4100                   Make_Unchecked_Type_Conversion (Loc,
4101                     Subtype_Mark =>
4102                       New_Reference_To (RTE (RO_ST_Task_Id), Loc),
4103                     Expression =>
4104                       Make_Selected_Component (Loc,
4105                         Prefix =>
4106                           New_Copy_Tree (Pref),
4107                         Selector_Name =>
4108                           Make_Identifier (Loc, Name_uDisp_Get_Task_Id))))));
4109
4110          elsif Restricted_Profile then
4111             Rewrite (N,
4112               Build_Call_With_Task (Pref, RTE (RE_Restricted_Terminated)));
4113
4114          else
4115             Rewrite (N,
4116               Build_Call_With_Task (Pref, RTE (RE_Terminated)));
4117          end if;
4118
4119          Analyze_And_Resolve (N, Standard_Boolean);
4120       end Terminated;
4121
4122       ----------------
4123       -- To_Address --
4124       ----------------
4125
4126       --  Transforms System'To_Address (X) into unchecked conversion
4127       --  from (integral) type of X to type address.
4128
4129       when Attribute_To_Address =>
4130          Rewrite (N,
4131            Unchecked_Convert_To (RTE (RE_Address),
4132              Relocate_Node (First (Exprs))));
4133          Analyze_And_Resolve (N, RTE (RE_Address));
4134
4135       ----------------
4136       -- Truncation --
4137       ----------------
4138
4139       --  Transforms 'Truncation into a call to the floating-point attribute
4140       --  function Truncation in Fat_xxx (where xxx is the root type).
4141       --  Expansion is avoided for cases the back end can handle directly.
4142
4143       when Attribute_Truncation =>
4144          if not Is_Inline_Floating_Point_Attribute (N) then
4145             Expand_Fpt_Attribute_R (N);
4146          end if;
4147
4148       -----------------------
4149       -- Unbiased_Rounding --
4150       -----------------------
4151
4152       --  Transforms 'Unbiased_Rounding into a call to the floating-point
4153       --  attribute function Unbiased_Rounding in Fat_xxx (where xxx is the
4154       --  root type). Expansion is avoided for cases the back end can handle
4155       --  directly.
4156
4157       when Attribute_Unbiased_Rounding =>
4158          if not Is_Inline_Floating_Point_Attribute (N) then
4159             Expand_Fpt_Attribute_R (N);
4160          end if;
4161
4162       -----------------
4163       -- UET_Address --
4164       -----------------
4165
4166       when Attribute_UET_Address => UET_Address : declare
4167          Ent : constant Entity_Id :=
4168                  Make_Defining_Identifier (Loc, New_Internal_Name ('T'));
4169
4170       begin
4171          Insert_Action (N,
4172            Make_Object_Declaration (Loc,
4173              Defining_Identifier => Ent,
4174              Aliased_Present     => True,
4175              Object_Definition   =>
4176                New_Occurrence_Of (RTE (RE_Address), Loc)));
4177
4178          --  Construct name __gnat_xxx__SDP, where xxx is the unit name
4179          --  in normal external form.
4180
4181          Get_External_Unit_Name_String (Get_Unit_Name (Pref));
4182          Name_Buffer (1 + 7 .. Name_Len + 7) := Name_Buffer (1 .. Name_Len);
4183          Name_Len := Name_Len + 7;
4184          Name_Buffer (1 .. 7) := "__gnat_";
4185          Name_Buffer (Name_Len + 1 .. Name_Len + 5) := "__SDP";
4186          Name_Len := Name_Len + 5;
4187
4188          Set_Is_Imported (Ent);
4189          Set_Interface_Name (Ent,
4190            Make_String_Literal (Loc,
4191              Strval => String_From_Name_Buffer));
4192
4193          --  Set entity as internal to ensure proper Sprint output of its
4194          --  implicit importation.
4195
4196          Set_Is_Internal (Ent);
4197
4198          Rewrite (N,
4199            Make_Attribute_Reference (Loc,
4200              Prefix => New_Occurrence_Of (Ent, Loc),
4201              Attribute_Name => Name_Address));
4202
4203          Analyze_And_Resolve (N, Typ);
4204       end UET_Address;
4205
4206       ---------------
4207       -- VADS_Size --
4208       ---------------
4209
4210       --  The processing for VADS_Size is shared with Size
4211
4212       ---------
4213       -- Val --
4214       ---------
4215
4216       --  For enumeration types with a standard representation, and for all
4217       --  other types, Val is handled by Gigi. For enumeration types with
4218       --  a non-standard representation we use the _Pos_To_Rep array that
4219       --  was created when the type was frozen.
4220
4221       when Attribute_Val => Val :
4222       declare
4223          Etyp : constant Entity_Id := Base_Type (Entity (Pref));
4224
4225       begin
4226          if Is_Enumeration_Type (Etyp)
4227            and then Present (Enum_Pos_To_Rep (Etyp))
4228          then
4229             if Has_Contiguous_Rep (Etyp) then
4230                declare
4231                   Rep_Node : constant Node_Id :=
4232                     Unchecked_Convert_To (Etyp,
4233                        Make_Op_Add (Loc,
4234                          Left_Opnd =>
4235                             Make_Integer_Literal (Loc,
4236                               Enumeration_Rep (First_Literal (Etyp))),
4237                          Right_Opnd =>
4238                           (Convert_To (Standard_Integer,
4239                              Relocate_Node (First (Exprs))))));
4240
4241                begin
4242                   Rewrite (N,
4243                      Unchecked_Convert_To (Etyp,
4244                          Make_Op_Add (Loc,
4245                            Left_Opnd =>
4246                              Make_Integer_Literal (Loc,
4247                                Enumeration_Rep (First_Literal (Etyp))),
4248                            Right_Opnd =>
4249                              Make_Function_Call (Loc,
4250                                Name =>
4251                                  New_Reference_To
4252                                    (TSS (Etyp, TSS_Rep_To_Pos), Loc),
4253                                Parameter_Associations => New_List (
4254                                  Rep_Node,
4255                                  Rep_To_Pos_Flag (Etyp, Loc))))));
4256                end;
4257
4258             else
4259                Rewrite (N,
4260                  Make_Indexed_Component (Loc,
4261                    Prefix => New_Reference_To (Enum_Pos_To_Rep (Etyp), Loc),
4262                    Expressions => New_List (
4263                      Convert_To (Standard_Integer,
4264                        Relocate_Node (First (Exprs))))));
4265             end if;
4266
4267             Analyze_And_Resolve (N, Typ);
4268          end if;
4269       end Val;
4270
4271       -----------
4272       -- Valid --
4273       -----------
4274
4275       --  The code for valid is dependent on the particular types involved.
4276       --  See separate sections below for the generated code in each case.
4277
4278       when Attribute_Valid => Valid :
4279       declare
4280          Ptyp : constant Entity_Id  := Etype (Pref);
4281          Btyp : Entity_Id           := Base_Type (Ptyp);
4282          Tst  : Node_Id;
4283
4284          Save_Validity_Checks_On : constant Boolean := Validity_Checks_On;
4285          --  Save the validity checking mode. We always turn off validity
4286          --  checking during process of 'Valid since this is one place
4287          --  where we do not want the implicit validity checks to intefere
4288          --  with the explicit validity check that the programmer is doing.
4289
4290          function Make_Range_Test return Node_Id;
4291          --  Build the code for a range test of the form
4292          --    Btyp!(Pref) >= Btyp!(Ptyp'First)
4293          --      and then
4294          --    Btyp!(Pref) <= Btyp!(Ptyp'Last)
4295
4296          ---------------------
4297          -- Make_Range_Test --
4298          ---------------------
4299
4300          function Make_Range_Test return Node_Id is
4301          begin
4302             return
4303               Make_And_Then (Loc,
4304                 Left_Opnd =>
4305                   Make_Op_Ge (Loc,
4306                     Left_Opnd =>
4307                       Unchecked_Convert_To (Btyp, Duplicate_Subexpr (Pref)),
4308
4309                     Right_Opnd =>
4310                       Unchecked_Convert_To (Btyp,
4311                         Make_Attribute_Reference (Loc,
4312                           Prefix => New_Occurrence_Of (Ptyp, Loc),
4313                           Attribute_Name => Name_First))),
4314
4315                 Right_Opnd =>
4316                   Make_Op_Le (Loc,
4317                     Left_Opnd =>
4318                       Unchecked_Convert_To (Btyp,
4319                         Duplicate_Subexpr_No_Checks (Pref)),
4320
4321                     Right_Opnd =>
4322                       Unchecked_Convert_To (Btyp,
4323                         Make_Attribute_Reference (Loc,
4324                           Prefix => New_Occurrence_Of (Ptyp, Loc),
4325                           Attribute_Name => Name_Last))));
4326          end Make_Range_Test;
4327
4328       --  Start of processing for Attribute_Valid
4329
4330       begin
4331          --  Turn off validity checks. We do not want any implicit validity
4332          --  checks to intefere with the explicit check from the attribute
4333
4334          Validity_Checks_On := False;
4335
4336          --  Floating-point case. This case is handled by the Valid attribute
4337          --  code in the floating-point attribute run-time library.
4338
4339          if Is_Floating_Point_Type (Ptyp) then
4340             declare
4341                Pkg : RE_Id;
4342                Ftp : Entity_Id;
4343
4344             begin
4345                --  For vax fpt types, call appropriate routine in special vax
4346                --  floating point unit. We do not have to worry about loads in
4347                --  this case, since these types have no signalling NaN's.
4348
4349                if Vax_Float (Btyp) then
4350                   Expand_Vax_Valid (N);
4351
4352                --  The AAMP back end handles Valid for floating-point types
4353
4354                elsif Is_AAMP_Float (Btyp) then
4355                   Analyze_And_Resolve (Pref, Ptyp);
4356                   Set_Etype (N, Standard_Boolean);
4357                   Set_Analyzed (N);
4358
4359                --  Non VAX float case
4360
4361                else
4362                   Find_Fat_Info (Etype (Pref), Ftp, Pkg);
4363
4364                   --  If the floating-point object might be unaligned, we need
4365                   --  to call the special routine Unaligned_Valid, which makes
4366                   --  the needed copy, being careful not to load the value into
4367                   --  any floating-point register. The argument in this case is
4368                   --  obj'Address (see Unaligned_Valid routine in Fat_Gen).
4369
4370                   if Is_Possibly_Unaligned_Object (Pref) then
4371                      Expand_Fpt_Attribute
4372                        (N, Pkg, Name_Unaligned_Valid,
4373                         New_List (
4374                           Make_Attribute_Reference (Loc,
4375                             Prefix => Relocate_Node (Pref),
4376                             Attribute_Name => Name_Address)));
4377
4378                   --  In the normal case where we are sure the object is
4379                   --  aligned, we generate a call to Valid, and the argument in
4380                   --  this case is obj'Unrestricted_Access (after converting
4381                   --  obj to the right floating-point type).
4382
4383                   else
4384                      Expand_Fpt_Attribute
4385                        (N, Pkg, Name_Valid,
4386                         New_List (
4387                           Make_Attribute_Reference (Loc,
4388                             Prefix => Unchecked_Convert_To (Ftp, Pref),
4389                             Attribute_Name => Name_Unrestricted_Access)));
4390                   end if;
4391                end if;
4392
4393                --  One more task, we still need a range check. Required
4394                --  only if we have a constraint, since the Valid routine
4395                --  catches infinities properly (infinities are never valid).
4396
4397                --  The way we do the range check is simply to create the
4398                --  expression: Valid (N) and then Base_Type(Pref) in Typ.
4399
4400                if not Subtypes_Statically_Match (Ptyp, Btyp) then
4401                   Rewrite (N,
4402                     Make_And_Then (Loc,
4403                       Left_Opnd  => Relocate_Node (N),
4404                       Right_Opnd =>
4405                         Make_In (Loc,
4406                           Left_Opnd => Convert_To (Btyp, Pref),
4407                           Right_Opnd => New_Occurrence_Of (Ptyp, Loc))));
4408                end if;
4409             end;
4410
4411          --  Enumeration type with holes
4412
4413          --  For enumeration types with holes, the Pos value constructed by
4414          --  the Enum_Rep_To_Pos function built in Exp_Ch3 called with a
4415          --  second argument of False returns minus one for an invalid value,
4416          --  and the non-negative pos value for a valid value, so the
4417          --  expansion of X'Valid is simply:
4418
4419          --     type(X)'Pos (X) >= 0
4420
4421          --  We can't quite generate it that way because of the requirement
4422          --  for the non-standard second argument of False in the resulting
4423          --  rep_to_pos call, so we have to explicitly create:
4424
4425          --     _rep_to_pos (X, False) >= 0
4426
4427          --  If we have an enumeration subtype, we also check that the
4428          --  value is in range:
4429
4430          --    _rep_to_pos (X, False) >= 0
4431          --      and then
4432          --       (X >= type(X)'First and then type(X)'Last <= X)
4433
4434          elsif Is_Enumeration_Type (Ptyp)
4435            and then Present (Enum_Pos_To_Rep (Base_Type (Ptyp)))
4436          then
4437             Tst :=
4438               Make_Op_Ge (Loc,
4439                 Left_Opnd =>
4440                   Make_Function_Call (Loc,
4441                     Name =>
4442                       New_Reference_To
4443                         (TSS (Base_Type (Ptyp), TSS_Rep_To_Pos), Loc),
4444                     Parameter_Associations => New_List (
4445                       Pref,
4446                       New_Occurrence_Of (Standard_False, Loc))),
4447                 Right_Opnd => Make_Integer_Literal (Loc, 0));
4448
4449             if Ptyp /= Btyp
4450               and then
4451                 (Type_Low_Bound (Ptyp) /= Type_Low_Bound (Btyp)
4452                   or else
4453                  Type_High_Bound (Ptyp) /= Type_High_Bound (Btyp))
4454             then
4455                --  The call to Make_Range_Test will create declarations
4456                --  that need a proper insertion point, but Pref is now
4457                --  attached to a node with no ancestor. Attach to tree
4458                --  even if it is to be rewritten below.
4459
4460                Set_Parent (Tst, Parent (N));
4461
4462                Tst :=
4463                  Make_And_Then (Loc,
4464                    Left_Opnd  => Make_Range_Test,
4465                    Right_Opnd => Tst);
4466             end if;
4467
4468             Rewrite (N, Tst);
4469
4470          --  Fortran convention booleans
4471
4472          --  For the very special case of Fortran convention booleans, the
4473          --  value is always valid, since it is an integer with the semantics
4474          --  that non-zero is true, and any value is permissible.
4475
4476          elsif Is_Boolean_Type (Ptyp)
4477            and then Convention (Ptyp) = Convention_Fortran
4478          then
4479             Rewrite (N, New_Occurrence_Of (Standard_True, Loc));
4480
4481          --  For biased representations, we will be doing an unchecked
4482          --  conversion without unbiasing the result. That means that the range
4483          --  test has to take this into account, and the proper form of the
4484          --  test is:
4485
4486          --    Btyp!(Pref) < Btyp!(Ptyp'Range_Length)
4487
4488          elsif Has_Biased_Representation (Ptyp) then
4489             Btyp := RTE (RE_Unsigned_32);
4490             Rewrite (N,
4491               Make_Op_Lt (Loc,
4492                 Left_Opnd =>
4493                   Unchecked_Convert_To (Btyp, Duplicate_Subexpr (Pref)),
4494                 Right_Opnd =>
4495                   Unchecked_Convert_To (Btyp,
4496                     Make_Attribute_Reference (Loc,
4497                       Prefix => New_Occurrence_Of (Ptyp, Loc),
4498                       Attribute_Name => Name_Range_Length))));
4499
4500          --  For all other scalar types, what we want logically is a
4501          --  range test:
4502
4503          --     X in type(X)'First .. type(X)'Last
4504
4505          --  But that's precisely what won't work because of possible
4506          --  unwanted optimization (and indeed the basic motivation for
4507          --  the Valid attribute is exactly that this test does not work!)
4508          --  What will work is:
4509
4510          --     Btyp!(X) >= Btyp!(type(X)'First)
4511          --       and then
4512          --     Btyp!(X) <= Btyp!(type(X)'Last)
4513
4514          --  where Btyp is an integer type large enough to cover the full
4515          --  range of possible stored values (i.e. it is chosen on the basis
4516          --  of the size of the type, not the range of the values). We write
4517          --  this as two tests, rather than a range check, so that static
4518          --  evaluation will easily remove either or both of the checks if
4519          --  they can be -statically determined to be true (this happens
4520          --  when the type of X is static and the range extends to the full
4521          --  range of stored values).
4522
4523          --  Unsigned types. Note: it is safe to consider only whether the
4524          --  subtype is unsigned, since we will in that case be doing all
4525          --  unsigned comparisons based on the subtype range. Since we use the
4526          --  actual subtype object size, this is appropriate.
4527
4528          --  For example, if we have
4529
4530          --    subtype x is integer range 1 .. 200;
4531          --    for x'Object_Size use 8;
4532
4533          --  Now the base type is signed, but objects of this type are bits
4534          --  unsigned, and doing an unsigned test of the range 1 to 200 is
4535          --  correct, even though a value greater than 127 looks signed to a
4536          --  signed comparison.
4537
4538          elsif Is_Unsigned_Type (Ptyp) then
4539             if Esize (Ptyp) <= 32 then
4540                Btyp := RTE (RE_Unsigned_32);
4541             else
4542                Btyp := RTE (RE_Unsigned_64);
4543             end if;
4544
4545             Rewrite (N, Make_Range_Test);
4546
4547          --  Signed types
4548
4549          else
4550             if Esize (Ptyp) <= Esize (Standard_Integer) then
4551                Btyp := Standard_Integer;
4552             else
4553                Btyp := Universal_Integer;
4554             end if;
4555
4556             Rewrite (N, Make_Range_Test);
4557          end if;
4558
4559          Analyze_And_Resolve (N, Standard_Boolean);
4560          Validity_Checks_On := Save_Validity_Checks_On;
4561       end Valid;
4562
4563       -----------
4564       -- Value --
4565       -----------
4566
4567       --  Value attribute is handled in separate unti Exp_Imgv
4568
4569       when Attribute_Value =>
4570          Exp_Imgv.Expand_Value_Attribute (N);
4571
4572       -----------------
4573       -- Value_Size --
4574       -----------------
4575
4576       --  The processing for Value_Size shares the processing for Size
4577
4578       -------------
4579       -- Version --
4580       -------------
4581
4582       --  The processing for Version shares the processing for Body_Version
4583
4584       ----------------
4585       -- Wide_Image --
4586       ----------------
4587
4588       --  We expand typ'Wide_Image (X) into
4589
4590       --    String_To_Wide_String
4591       --      (typ'Image (X), Wide_Character_Encoding_Method)
4592
4593       --  This works in all cases because String_To_Wide_String converts any
4594       --  wide character escape sequences resulting from the Image call to the
4595       --  proper Wide_Character equivalent
4596
4597       --  not quite right for typ = Wide_Character ???
4598
4599       when Attribute_Wide_Image => Wide_Image :
4600       begin
4601          Rewrite (N,
4602            Make_Function_Call (Loc,
4603              Name => New_Reference_To (RTE (RE_String_To_Wide_String), Loc),
4604              Parameter_Associations => New_List (
4605                Make_Attribute_Reference (Loc,
4606                  Prefix         => Pref,
4607                  Attribute_Name => Name_Image,
4608                  Expressions    => Exprs),
4609
4610                Make_Integer_Literal (Loc,
4611                  Intval => Int (Wide_Character_Encoding_Method)))));
4612
4613          Analyze_And_Resolve (N, Standard_Wide_String);
4614       end Wide_Image;
4615
4616       ---------------------
4617       -- Wide_Wide_Image --
4618       ---------------------
4619
4620       --  We expand typ'Wide_Wide_Image (X) into
4621
4622       --    String_To_Wide_Wide_String
4623       --      (typ'Image (X), Wide_Character_Encoding_Method)
4624
4625       --  This works in all cases because String_To_Wide_Wide_String converts
4626       --  any wide character escape sequences resulting from the Image call to
4627       --  the proper Wide_Character equivalent
4628
4629       --  not quite right for typ = Wide_Wide_Character ???
4630
4631       when Attribute_Wide_Wide_Image => Wide_Wide_Image :
4632       begin
4633          Rewrite (N,
4634            Make_Function_Call (Loc,
4635              Name => New_Reference_To
4636                (RTE (RE_String_To_Wide_Wide_String), Loc),
4637              Parameter_Associations => New_List (
4638                Make_Attribute_Reference (Loc,
4639                  Prefix         => Pref,
4640                  Attribute_Name => Name_Image,
4641                  Expressions    => Exprs),
4642
4643                Make_Integer_Literal (Loc,
4644                  Intval => Int (Wide_Character_Encoding_Method)))));
4645
4646          Analyze_And_Resolve (N, Standard_Wide_Wide_String);
4647       end Wide_Wide_Image;
4648
4649       ----------------
4650       -- Wide_Value --
4651       ----------------
4652
4653       --  We expand typ'Wide_Value (X) into
4654
4655       --    typ'Value
4656       --      (Wide_String_To_String (X, Wide_Character_Encoding_Method))
4657
4658       --  Wide_String_To_String is a runtime function that converts its wide
4659       --  string argument to String, converting any non-translatable characters
4660       --  into appropriate escape sequences. This preserves the required
4661       --  semantics of Wide_Value in all cases, and results in a very simple
4662       --  implementation approach.
4663
4664       --  Note: for this approach to be fully standard compliant for the cases
4665       --  where typ is Wide_Character and Wide_Wide_Character, the encoding
4666       --  method must cover the entire character range (e.g. UTF-8). But that
4667       --  is a reasonable requirement when dealing with encoded character
4668       --  sequences. Presumably if one of the restrictive encoding mechanisms
4669       --  is in use such as Shift-JIS, then characters that cannot be
4670       --  represented using this encoding will not appear in any case.
4671
4672       when Attribute_Wide_Value => Wide_Value :
4673       begin
4674          Rewrite (N,
4675            Make_Attribute_Reference (Loc,
4676              Prefix         => Pref,
4677              Attribute_Name => Name_Value,
4678
4679              Expressions    => New_List (
4680                Make_Function_Call (Loc,
4681                  Name =>
4682                    New_Reference_To (RTE (RE_Wide_String_To_String), Loc),
4683
4684                  Parameter_Associations => New_List (
4685                    Relocate_Node (First (Exprs)),
4686                    Make_Integer_Literal (Loc,
4687                      Intval => Int (Wide_Character_Encoding_Method)))))));
4688
4689          Analyze_And_Resolve (N, Typ);
4690       end Wide_Value;
4691
4692       ---------------------
4693       -- Wide_Wide_Value --
4694       ---------------------
4695
4696       --  We expand typ'Wide_Value_Value (X) into
4697
4698       --    typ'Value
4699       --      (Wide_Wide_String_To_String (X, Wide_Character_Encoding_Method))
4700
4701       --  Wide_Wide_String_To_String is a runtime function that converts its
4702       --  wide string argument to String, converting any non-translatable
4703       --  characters into appropriate escape sequences. This preserves the
4704       --  required semantics of Wide_Wide_Value in all cases, and results in a
4705       --  very simple implementation approach.
4706
4707       --  It's not quite right where typ = Wide_Wide_Character, because the
4708       --  encoding method may not cover the whole character type ???
4709
4710       when Attribute_Wide_Wide_Value => Wide_Wide_Value :
4711       begin
4712          Rewrite (N,
4713            Make_Attribute_Reference (Loc,
4714              Prefix         => Pref,
4715              Attribute_Name => Name_Value,
4716
4717              Expressions    => New_List (
4718                Make_Function_Call (Loc,
4719                  Name =>
4720                    New_Reference_To (RTE (RE_Wide_Wide_String_To_String), Loc),
4721
4722                  Parameter_Associations => New_List (
4723                    Relocate_Node (First (Exprs)),
4724                    Make_Integer_Literal (Loc,
4725                      Intval => Int (Wide_Character_Encoding_Method)))))));
4726
4727          Analyze_And_Resolve (N, Typ);
4728       end Wide_Wide_Value;
4729
4730       ---------------------
4731       -- Wide_Wide_Width --
4732       ---------------------
4733
4734       --  Wide_Wide_Width attribute is handled in separate unit Exp_Imgv
4735
4736       when Attribute_Wide_Wide_Width =>
4737          Exp_Imgv.Expand_Width_Attribute (N, Wide_Wide);
4738
4739       ----------------
4740       -- Wide_Width --
4741       ----------------
4742
4743       --  Wide_Width attribute is handled in separate unit Exp_Imgv
4744
4745       when Attribute_Wide_Width =>
4746          Exp_Imgv.Expand_Width_Attribute (N, Wide);
4747
4748       -----------
4749       -- Width --
4750       -----------
4751
4752       --  Width attribute is handled in separate unit Exp_Imgv
4753
4754       when Attribute_Width =>
4755          Exp_Imgv.Expand_Width_Attribute (N, Normal);
4756
4757       -----------
4758       -- Write --
4759       -----------
4760
4761       when Attribute_Write => Write : declare
4762          P_Type : constant Entity_Id := Entity (Pref);
4763          U_Type : constant Entity_Id := Underlying_Type (P_Type);
4764          Pname  : Entity_Id;
4765          Decl   : Node_Id;
4766          Prag   : Node_Id;
4767          Arg3   : Node_Id;
4768          Wfunc  : Node_Id;
4769
4770       begin
4771          --  If no underlying type, we have an error that will be diagnosed
4772          --  elsewhere, so here we just completely ignore the expansion.
4773
4774          if No (U_Type) then
4775             return;
4776          end if;
4777
4778          --  The simple case, if there is a TSS for Write, just call it
4779
4780          Pname := Find_Stream_Subprogram (P_Type, TSS_Stream_Write);
4781
4782          if Present (Pname) then
4783             null;
4784
4785          else
4786             --  If there is a Stream_Convert pragma, use it, we rewrite
4787
4788             --     sourcetyp'Output (stream, Item)
4789
4790             --  as
4791
4792             --     strmtyp'Output (Stream, strmwrite (acttyp (Item)));
4793
4794             --  where strmwrite is the given Write function that converts an
4795             --  argument of type sourcetyp or a type acctyp, from which it is
4796             --  derived to type strmtyp. The conversion to acttyp is required
4797             --  for the derived case.
4798
4799             Prag := Get_Stream_Convert_Pragma (P_Type);
4800
4801             if Present (Prag) then
4802                Arg3 :=
4803                  Next (Next (First (Pragma_Argument_Associations (Prag))));
4804                Wfunc := Entity (Expression (Arg3));
4805
4806                Rewrite (N,
4807                  Make_Attribute_Reference (Loc,
4808                    Prefix => New_Occurrence_Of (Etype (Wfunc), Loc),
4809                    Attribute_Name => Name_Output,
4810                    Expressions => New_List (
4811                      Relocate_Node (First (Exprs)),
4812                      Make_Function_Call (Loc,
4813                        Name => New_Occurrence_Of (Wfunc, Loc),
4814                        Parameter_Associations => New_List (
4815                          OK_Convert_To (Etype (First_Formal (Wfunc)),
4816                            Relocate_Node (Next (First (Exprs)))))))));
4817
4818                Analyze (N);
4819                return;
4820
4821             --  For elementary types, we call the W_xxx routine directly
4822
4823             elsif Is_Elementary_Type (U_Type) then
4824                Rewrite (N, Build_Elementary_Write_Call (N));
4825                Analyze (N);
4826                return;
4827
4828             --  Array type case
4829
4830             elsif Is_Array_Type (U_Type) then
4831                Build_Array_Write_Procedure (N, U_Type, Decl, Pname);
4832                Compile_Stream_Body_In_Scope (N, Decl, U_Type, Check => False);
4833
4834             --  Tagged type case, use the primitive Write function. Note that
4835             --  this will dispatch in the class-wide case which is what we want
4836
4837             elsif Is_Tagged_Type (U_Type) then
4838                Pname := Find_Prim_Op (U_Type, TSS_Stream_Write);
4839
4840             --  All other record type cases, including protected records.
4841             --  The latter only arise for expander generated code for
4842             --  handling shared passive partition access.
4843
4844             else
4845                pragma Assert
4846                  (Is_Record_Type (U_Type) or else Is_Protected_Type (U_Type));
4847
4848                --  Ada 2005 (AI-216): Program_Error is raised when executing
4849                --  the default implementation of the Write attribute of an
4850                --  Unchecked_Union type. However, if the 'Write reference is
4851                --  within the generated Output stream procedure, Write outputs
4852                --  the components, and the default values of the discriminant
4853                --  are streamed by the Output procedure itself.
4854
4855                if Is_Unchecked_Union (Base_Type (U_Type))
4856                  and not Is_TSS (Current_Scope, TSS_Stream_Output)
4857                then
4858                   Insert_Action (N,
4859                     Make_Raise_Program_Error (Loc,
4860                       Reason => PE_Unchecked_Union_Restriction));
4861                end if;
4862
4863                if Has_Discriminants (U_Type)
4864                  and then Present
4865                    (Discriminant_Default_Value (First_Discriminant (U_Type)))
4866                then
4867                   Build_Mutable_Record_Write_Procedure
4868                     (Loc, Base_Type (U_Type), Decl, Pname);
4869                else
4870                   Build_Record_Write_Procedure
4871                     (Loc, Base_Type (U_Type), Decl, Pname);
4872                end if;
4873
4874                Insert_Action (N, Decl);
4875             end if;
4876          end if;
4877
4878          --  If we fall through, Pname is the procedure to be called
4879
4880          Rewrite_Stream_Proc_Call (Pname);
4881       end Write;
4882
4883       --  Component_Size is handled by Gigi, unless the component size is known
4884       --  at compile time, which is always true in the packed array case. It is
4885       --  important that the packed array case is handled in the front end (see
4886       --  Eval_Attribute) since Gigi would otherwise get confused by the
4887       --  equivalent packed array type.
4888
4889       when Attribute_Component_Size =>
4890          null;
4891
4892       --  The following attributes are handled by the back end (except that
4893       --  static cases have already been evaluated during semantic processing,
4894       --  but in any case the back end should not count on this). The one bit
4895       --  of special processing required is that these attributes typically
4896       --  generate conditionals in the code, so we need to check the relevant
4897       --  restriction.
4898
4899       when Attribute_Max                          |
4900            Attribute_Min                          =>
4901          Check_Restriction (No_Implicit_Conditionals, N);
4902
4903       --  The following attributes are handled by the back end (except that
4904       --  static cases have already been evaluated during semantic processing,
4905       --  but in any case the back end should not count on this).
4906
4907       --  Gigi also handles the non-class-wide cases of Size
4908
4909       when Attribute_Bit_Order                    |
4910            Attribute_Code_Address                 |
4911            Attribute_Definite                     |
4912            Attribute_Null_Parameter               |
4913            Attribute_Passed_By_Reference          |
4914            Attribute_Pool_Address                 =>
4915          null;
4916
4917       --  The following attributes are also handled by Gigi, but return a
4918       --  universal integer result, so may need a conversion for checking
4919       --  that the result is in range.
4920
4921       when Attribute_Aft                          |
4922            Attribute_Bit                          |
4923            Attribute_Max_Size_In_Storage_Elements
4924       =>
4925          Apply_Universal_Integer_Attribute_Checks (N);
4926
4927       --  The following attributes should not appear at this stage, since they
4928       --  have already been handled by the analyzer (and properly rewritten
4929       --  with corresponding values or entities to represent the right values)
4930
4931       when Attribute_Abort_Signal                 |
4932            Attribute_Address_Size                 |
4933            Attribute_Base                         |
4934            Attribute_Class                        |
4935            Attribute_Default_Bit_Order            |
4936            Attribute_Delta                        |
4937            Attribute_Denorm                       |
4938            Attribute_Digits                       |
4939            Attribute_Emax                         |
4940            Attribute_Enabled                      |
4941            Attribute_Epsilon                      |
4942            Attribute_Has_Access_Values            |
4943            Attribute_Has_Discriminants            |
4944            Attribute_Large                        |
4945            Attribute_Machine_Emax                 |
4946            Attribute_Machine_Emin                 |
4947            Attribute_Machine_Mantissa             |
4948            Attribute_Machine_Overflows            |
4949            Attribute_Machine_Radix                |
4950            Attribute_Machine_Rounds               |
4951            Attribute_Maximum_Alignment            |
4952            Attribute_Model_Emin                   |
4953            Attribute_Model_Epsilon                |
4954            Attribute_Model_Mantissa               |
4955            Attribute_Model_Small                  |
4956            Attribute_Modulus                      |
4957            Attribute_Partition_ID                 |
4958            Attribute_Range                        |
4959            Attribute_Safe_Emax                    |
4960            Attribute_Safe_First                   |
4961            Attribute_Safe_Large                   |
4962            Attribute_Safe_Last                    |
4963            Attribute_Safe_Small                   |
4964            Attribute_Scale                        |
4965            Attribute_Signed_Zeros                 |
4966            Attribute_Small                        |
4967            Attribute_Storage_Unit                 |
4968            Attribute_Stub_Type                    |
4969            Attribute_Target_Name                  |
4970            Attribute_Type_Class                   |
4971            Attribute_Unconstrained_Array          |
4972            Attribute_Universal_Literal_String     |
4973            Attribute_Wchar_T_Size                 |
4974            Attribute_Word_Size                    =>
4975
4976          raise Program_Error;
4977
4978       --  The Asm_Input and Asm_Output attributes are not expanded at this
4979       --  stage, but will be eliminated in the expansion of the Asm call,
4980       --  see Exp_Intr for details. So Gigi will never see these either.
4981
4982       when Attribute_Asm_Input                    |
4983            Attribute_Asm_Output                   =>
4984
4985          null;
4986
4987       end case;
4988
4989    exception
4990       when RE_Not_Available =>
4991          return;
4992    end Expand_N_Attribute_Reference;
4993
4994    ----------------------
4995    -- Expand_Pred_Succ --
4996    ----------------------
4997
4998    --  For typ'Pred (exp), we generate the check
4999
5000    --    [constraint_error when exp = typ'Base'First]
5001
5002    --  Similarly, for typ'Succ (exp), we generate the check
5003
5004    --    [constraint_error when exp = typ'Base'Last]
5005
5006    --  These checks are not generated for modular types, since the proper
5007    --  semantics for Succ and Pred on modular types is to wrap, not raise CE.
5008
5009    procedure Expand_Pred_Succ (N : Node_Id) is
5010       Loc  : constant Source_Ptr := Sloc (N);
5011       Cnam : Name_Id;
5012
5013    begin
5014       if Attribute_Name (N) = Name_Pred then
5015          Cnam := Name_First;
5016       else
5017          Cnam := Name_Last;
5018       end if;
5019
5020       Insert_Action (N,
5021         Make_Raise_Constraint_Error (Loc,
5022           Condition =>
5023             Make_Op_Eq (Loc,
5024               Left_Opnd =>
5025                 Duplicate_Subexpr_Move_Checks (First (Expressions (N))),
5026               Right_Opnd =>
5027                 Make_Attribute_Reference (Loc,
5028                   Prefix =>
5029                     New_Reference_To (Base_Type (Etype (Prefix (N))), Loc),
5030                   Attribute_Name => Cnam)),
5031           Reason => CE_Overflow_Check_Failed));
5032    end Expand_Pred_Succ;
5033
5034    -------------------
5035    -- Find_Fat_Info --
5036    -------------------
5037
5038    procedure Find_Fat_Info
5039      (T        : Entity_Id;
5040       Fat_Type : out Entity_Id;
5041       Fat_Pkg  : out RE_Id)
5042    is
5043       Btyp : constant Entity_Id := Base_Type (T);
5044       Rtyp : constant Entity_Id := Root_Type (T);
5045       Digs : constant Nat       := UI_To_Int (Digits_Value (Btyp));
5046
5047    begin
5048       --  If the base type is VAX float, then get appropriate VAX float type
5049
5050       if Vax_Float (Btyp) then
5051          case Digs is
5052             when 6 =>
5053                Fat_Type := RTE (RE_Fat_VAX_F);
5054                Fat_Pkg  := RE_Attr_VAX_F_Float;
5055
5056             when 9 =>
5057                Fat_Type := RTE (RE_Fat_VAX_D);
5058                Fat_Pkg  := RE_Attr_VAX_D_Float;
5059
5060             when 15 =>
5061                Fat_Type := RTE (RE_Fat_VAX_G);
5062                Fat_Pkg  := RE_Attr_VAX_G_Float;
5063
5064             when others =>
5065                raise Program_Error;
5066          end case;
5067
5068       --  If root type is VAX float, this is the case where the library has
5069       --  been recompiled in VAX float mode, and we have an IEEE float type.
5070       --  This is when we use the special IEEE Fat packages.
5071
5072       elsif Vax_Float (Rtyp) then
5073          case Digs is
5074             when 6 =>
5075                Fat_Type := RTE (RE_Fat_IEEE_Short);
5076                Fat_Pkg  := RE_Attr_IEEE_Short;
5077
5078             when 15 =>
5079                Fat_Type := RTE (RE_Fat_IEEE_Long);
5080                Fat_Pkg  := RE_Attr_IEEE_Long;
5081
5082             when others =>
5083                raise Program_Error;
5084          end case;
5085
5086       --  If neither the base type nor the root type is VAX_Float then VAX
5087       --  float is out of the picture, and we can just use the root type.
5088
5089       else
5090          Fat_Type := Rtyp;
5091
5092          if Fat_Type = Standard_Short_Float then
5093             Fat_Pkg := RE_Attr_Short_Float;
5094
5095          elsif Fat_Type = Standard_Float then
5096             Fat_Pkg := RE_Attr_Float;
5097
5098          elsif Fat_Type = Standard_Long_Float then
5099             Fat_Pkg := RE_Attr_Long_Float;
5100
5101          elsif Fat_Type = Standard_Long_Long_Float then
5102             Fat_Pkg := RE_Attr_Long_Long_Float;
5103
5104          --  Universal real (which is its own root type) is treated as being
5105          --  equivalent to Standard.Long_Long_Float, since it is defined to
5106          --  have the same precision as the longest Float type.
5107
5108          elsif Fat_Type = Universal_Real then
5109             Fat_Type := Standard_Long_Long_Float;
5110             Fat_Pkg := RE_Attr_Long_Long_Float;
5111
5112          else
5113             raise Program_Error;
5114          end if;
5115       end if;
5116    end Find_Fat_Info;
5117
5118    ----------------------------
5119    -- Find_Stream_Subprogram --
5120    ----------------------------
5121
5122    function Find_Stream_Subprogram
5123      (Typ : Entity_Id;
5124       Nam : TSS_Name_Type) return Entity_Id
5125    is
5126       Ent : constant Entity_Id := TSS (Typ, Nam);
5127    begin
5128       if Present (Ent) then
5129          return Ent;
5130       end if;
5131
5132       if Is_Tagged_Type (Typ)
5133         and then Is_Derived_Type (Typ)
5134       then
5135          return Find_Prim_Op (Typ, Nam);
5136       else
5137          return Find_Inherited_TSS (Typ, Nam);
5138       end if;
5139    end Find_Stream_Subprogram;
5140
5141    -----------------------
5142    -- Get_Index_Subtype --
5143    -----------------------
5144
5145    function Get_Index_Subtype (N : Node_Id) return Node_Id is
5146       P_Type : Entity_Id := Etype (Prefix (N));
5147       Indx   : Node_Id;
5148       J      : Int;
5149
5150    begin
5151       if Is_Access_Type (P_Type) then
5152          P_Type := Designated_Type (P_Type);
5153       end if;
5154
5155       if No (Expressions (N)) then
5156          J := 1;
5157       else
5158          J := UI_To_Int (Expr_Value (First (Expressions (N))));
5159       end if;
5160
5161       Indx := First_Index (P_Type);
5162       while J > 1 loop
5163          Next_Index (Indx);
5164          J := J - 1;
5165       end loop;
5166
5167       return Etype (Indx);
5168    end Get_Index_Subtype;
5169
5170    -------------------------------
5171    -- Get_Stream_Convert_Pragma --
5172    -------------------------------
5173
5174    function Get_Stream_Convert_Pragma (T : Entity_Id) return Node_Id is
5175       Typ : Entity_Id;
5176       N   : Node_Id;
5177
5178    begin
5179       --  Note: we cannot use Get_Rep_Pragma here because of the peculiarity
5180       --  that a stream convert pragma for a tagged type is not inherited from
5181       --  its parent. Probably what is wrong here is that it is basically
5182       --  incorrect to consider a stream convert pragma to be a representation
5183       --  pragma at all ???
5184
5185       N := First_Rep_Item (Implementation_Base_Type (T));
5186       while Present (N) loop
5187          if Nkind (N) = N_Pragma and then Chars (N) = Name_Stream_Convert then
5188
5189             --  For tagged types this pragma is not inherited, so we
5190             --  must verify that it is defined for the given type and
5191             --  not an ancestor.
5192
5193             Typ :=
5194               Entity (Expression (First (Pragma_Argument_Associations (N))));
5195
5196             if not Is_Tagged_Type (T)
5197               or else T = Typ
5198               or else (Is_Private_Type (Typ) and then T = Full_View (Typ))
5199             then
5200                return N;
5201             end if;
5202          end if;
5203
5204          Next_Rep_Item (N);
5205       end loop;
5206
5207       return Empty;
5208    end Get_Stream_Convert_Pragma;
5209
5210    ---------------------------------
5211    -- Is_Constrained_Packed_Array --
5212    ---------------------------------
5213
5214    function Is_Constrained_Packed_Array (Typ : Entity_Id) return Boolean is
5215       Arr : Entity_Id := Typ;
5216
5217    begin
5218       if Is_Access_Type (Arr) then
5219          Arr := Designated_Type (Arr);
5220       end if;
5221
5222       return Is_Array_Type (Arr)
5223         and then Is_Constrained (Arr)
5224         and then Present (Packed_Array_Type (Arr));
5225    end Is_Constrained_Packed_Array;
5226
5227    ----------------------------------------
5228    -- Is_Inline_Floating_Point_Attribute --
5229    ----------------------------------------
5230
5231    function Is_Inline_Floating_Point_Attribute (N : Node_Id) return Boolean is
5232       Id : constant Attribute_Id := Get_Attribute_Id (Attribute_Name (N));
5233
5234    begin
5235       if Nkind (Parent (N)) /= N_Type_Conversion
5236         or else not Is_Integer_Type (Etype (Parent (N)))
5237       then
5238          return False;
5239       end if;
5240
5241       --  Should also support 'Machine_Rounding and 'Unbiased_Rounding, but
5242       --  required back end support has not been implemented yet ???
5243
5244       return Id = Attribute_Truncation;
5245    end Is_Inline_Floating_Point_Attribute;
5246
5247 end Exp_Attr;