OSDN Git Service

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