OSDN Git Service

* double-int.c (mpz_set_double_int): Moved from
[pf3gnuchains/gcc-fork.git] / gcc / ada / sem_res.adb
1 ------------------------------------------------------------------------------
2 --                                                                          --
3 --                         GNAT COMPILER COMPONENTS                         --
4 --                                                                          --
5 --                              S E M _ R E S                               --
6 --                                                                          --
7 --                                 B o d y                                  --
8 --                                                                          --
9 --          Copyright (C) 1992-2006, 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 Debug;    use Debug;
30 with Debug_A;  use Debug_A;
31 with Einfo;    use Einfo;
32 with Errout;   use Errout;
33 with Expander; use Expander;
34 with Exp_Disp; use Exp_Disp;
35 with Exp_Ch6;  use Exp_Ch6;
36 with Exp_Ch7;  use Exp_Ch7;
37 with Exp_Tss;  use Exp_Tss;
38 with Exp_Util; use Exp_Util;
39 with Freeze;   use Freeze;
40 with Itypes;   use Itypes;
41 with Lib;      use Lib;
42 with Lib.Xref; use Lib.Xref;
43 with Namet;    use Namet;
44 with Nmake;    use Nmake;
45 with Nlists;   use Nlists;
46 with Opt;      use Opt;
47 with Output;   use Output;
48 with Restrict; use Restrict;
49 with Rident;   use Rident;
50 with Rtsfind;  use Rtsfind;
51 with Sem;      use Sem;
52 with Sem_Aggr; use Sem_Aggr;
53 with Sem_Attr; use Sem_Attr;
54 with Sem_Cat;  use Sem_Cat;
55 with Sem_Ch4;  use Sem_Ch4;
56 with Sem_Ch6;  use Sem_Ch6;
57 with Sem_Ch8;  use Sem_Ch8;
58 with Sem_Disp; use Sem_Disp;
59 with Sem_Dist; use Sem_Dist;
60 with Sem_Elab; use Sem_Elab;
61 with Sem_Eval; use Sem_Eval;
62 with Sem_Intr; use Sem_Intr;
63 with Sem_Util; use Sem_Util;
64 with Sem_Type; use Sem_Type;
65 with Sem_Warn; use Sem_Warn;
66 with Sinfo;    use Sinfo;
67 with Snames;   use Snames;
68 with Stand;    use Stand;
69 with Stringt;  use Stringt;
70 with Tbuild;   use Tbuild;
71 with Uintp;    use Uintp;
72 with Urealp;   use Urealp;
73
74 package body Sem_Res is
75
76    -----------------------
77    -- Local Subprograms --
78    -----------------------
79
80    --  Second pass (top-down) type checking and overload resolution procedures
81    --  Typ is the type required by context. These procedures propagate the
82    --  type information recursively to the descendants of N. If the node
83    --  is not overloaded, its Etype is established in the first pass. If
84    --  overloaded,  the Resolve routines set the correct type. For arith.
85    --  operators, the Etype is the base type of the context.
86
87    --  Note that Resolve_Attribute is separated off in Sem_Attr
88
89    procedure Ambiguous_Character (C : Node_Id);
90    --  Give list of candidate interpretations when a character literal cannot
91    --  be resolved.
92
93    procedure Check_Discriminant_Use (N : Node_Id);
94    --  Enforce the restrictions on the use of discriminants when constraining
95    --  a component of a discriminated type (record or concurrent type).
96
97    procedure Check_For_Visible_Operator (N : Node_Id; T : Entity_Id);
98    --  Given a node for an operator associated with type T, check that
99    --  the operator is visible. Operators all of whose operands are
100    --  universal must be checked for visibility during resolution
101    --  because their type is not determinable based on their operands.
102
103    procedure Check_Fully_Declared_Prefix
104      (Typ  : Entity_Id;
105       Pref : Node_Id);
106    --  Check that the type of the prefix of a dereference is not incomplete
107
108    function Check_Infinite_Recursion (N : Node_Id) return Boolean;
109    --  Given a call node, N, which is known to occur immediately within the
110    --  subprogram being called, determines whether it is a detectable case of
111    --  an infinite recursion, and if so, outputs appropriate messages. Returns
112    --  True if an infinite recursion is detected, and False otherwise.
113
114    procedure Check_Initialization_Call (N : Entity_Id; Nam : Entity_Id);
115    --  If the type of the object being initialized uses the secondary stack
116    --  directly or indirectly, create a transient scope for the call to the
117    --  init proc. This is because we do not create transient scopes for the
118    --  initialization of individual components within the init proc itself.
119    --  Could be optimized away perhaps?
120
121    function Is_Predefined_Op (Nam : Entity_Id) return Boolean;
122    --  Utility to check whether the name in the call is a predefined
123    --  operator, in which case the call is made into an operator node.
124    --  An instance of an intrinsic conversion operation may be given
125    --  an operator name, but is not treated like an operator.
126
127    procedure Replace_Actual_Discriminants (N : Node_Id; Default : Node_Id);
128    --  If a default expression in entry call N depends on the discriminants
129    --  of the task, it must be replaced with a reference to the discriminant
130    --  of the task being called.
131
132    procedure Resolve_Allocator                 (N : Node_Id; Typ : Entity_Id);
133    procedure Resolve_Arithmetic_Op             (N : Node_Id; Typ : Entity_Id);
134    procedure Resolve_Call                      (N : Node_Id; Typ : Entity_Id);
135    procedure Resolve_Character_Literal         (N : Node_Id; Typ : Entity_Id);
136    procedure Resolve_Comparison_Op             (N : Node_Id; Typ : Entity_Id);
137    procedure Resolve_Conditional_Expression    (N : Node_Id; Typ : Entity_Id);
138    procedure Resolve_Equality_Op               (N : Node_Id; Typ : Entity_Id);
139    procedure Resolve_Explicit_Dereference      (N : Node_Id; Typ : Entity_Id);
140    procedure Resolve_Entity_Name               (N : Node_Id; Typ : Entity_Id);
141    procedure Resolve_Indexed_Component         (N : Node_Id; Typ : Entity_Id);
142    procedure Resolve_Integer_Literal           (N : Node_Id; Typ : Entity_Id);
143    procedure Resolve_Logical_Op                (N : Node_Id; Typ : Entity_Id);
144    procedure Resolve_Membership_Op             (N : Node_Id; Typ : Entity_Id);
145    procedure Resolve_Null                      (N : Node_Id; Typ : Entity_Id);
146    procedure Resolve_Operator_Symbol           (N : Node_Id; Typ : Entity_Id);
147    procedure Resolve_Op_Concat                 (N : Node_Id; Typ : Entity_Id);
148    procedure Resolve_Op_Expon                  (N : Node_Id; Typ : Entity_Id);
149    procedure Resolve_Op_Not                    (N : Node_Id; Typ : Entity_Id);
150    procedure Resolve_Qualified_Expression      (N : Node_Id; Typ : Entity_Id);
151    procedure Resolve_Range                     (N : Node_Id; Typ : Entity_Id);
152    procedure Resolve_Real_Literal              (N : Node_Id; Typ : Entity_Id);
153    procedure Resolve_Reference                 (N : Node_Id; Typ : Entity_Id);
154    procedure Resolve_Selected_Component        (N : Node_Id; Typ : Entity_Id);
155    procedure Resolve_Shift                     (N : Node_Id; Typ : Entity_Id);
156    procedure Resolve_Short_Circuit             (N : Node_Id; Typ : Entity_Id);
157    procedure Resolve_Slice                     (N : Node_Id; Typ : Entity_Id);
158    procedure Resolve_String_Literal            (N : Node_Id; Typ : Entity_Id);
159    procedure Resolve_Subprogram_Info           (N : Node_Id; Typ : Entity_Id);
160    procedure Resolve_Type_Conversion           (N : Node_Id; Typ : Entity_Id);
161    procedure Resolve_Unary_Op                  (N : Node_Id; Typ : Entity_Id);
162    procedure Resolve_Unchecked_Expression      (N : Node_Id; Typ : Entity_Id);
163    procedure Resolve_Unchecked_Type_Conversion (N : Node_Id; Typ : Entity_Id);
164
165    function Operator_Kind
166      (Op_Name   : Name_Id;
167       Is_Binary : Boolean) return Node_Kind;
168    --  Utility to map the name of an operator into the corresponding Node. Used
169    --  by other node rewriting procedures.
170
171    procedure Resolve_Actuals (N : Node_Id; Nam : Entity_Id);
172    --  Resolve actuals of call, and add default expressions for missing ones.
173    --  N is the Node_Id for the subprogram call, and Nam is the entity of the
174    --  called subprogram.
175
176    procedure Resolve_Entry_Call (N : Node_Id; Typ : Entity_Id);
177    --  Called from Resolve_Call, when the prefix denotes an entry or element
178    --  of entry family. Actuals are resolved as for subprograms, and the node
179    --  is rebuilt as an entry call. Also called for protected operations. Typ
180    --  is the context type, which is used when the operation is a protected
181    --  function with no arguments, and the return value is indexed.
182
183    procedure Resolve_Intrinsic_Operator (N : Node_Id; Typ : Entity_Id);
184    --  A call to a user-defined intrinsic operator is rewritten as a call
185    --  to the corresponding predefined operator, with suitable conversions.
186
187    procedure Resolve_Intrinsic_Unary_Operator (N : Node_Id; Typ : Entity_Id);
188    --  Ditto, for unary operators (only arithmetic ones)
189
190    procedure Rewrite_Operator_As_Call (N : Node_Id; Nam : Entity_Id);
191    --  If an operator node resolves to a call to a user-defined operator,
192    --  rewrite the node as a function call.
193
194    procedure Make_Call_Into_Operator
195      (N     : Node_Id;
196       Typ   : Entity_Id;
197       Op_Id : Entity_Id);
198    --  Inverse transformation: if an operator is given in functional notation,
199    --  then after resolving the node, transform into an operator node, so
200    --  that operands are resolved properly. Recall that predefined operators
201    --  do not have a full signature and special resolution rules apply.
202
203    procedure Rewrite_Renamed_Operator
204      (N   : Node_Id;
205       Op  : Entity_Id;
206       Typ : Entity_Id);
207    --  An operator can rename another, e.g. in  an instantiation. In that
208    --  case, the proper operator node must be constructed and resolved.
209
210    procedure Set_String_Literal_Subtype (N : Node_Id; Typ : Entity_Id);
211    --  The String_Literal_Subtype is built for all strings that are not
212    --  operands of a static concatenation operation. If the argument is
213    --  not a N_String_Literal node, then the call has no effect.
214
215    procedure Set_Slice_Subtype (N : Node_Id);
216    --  Build subtype of array type, with the range specified by the slice
217
218    procedure Simplify_Type_Conversion (N : Node_Id);
219    --  Called after N has been resolved and evaluated, but before range checks
220    --  have been applied. Currently simplifies a combination of floating-point
221    --  to integer conversion and Truncation attribute.
222
223    function Unique_Fixed_Point_Type (N : Node_Id) return Entity_Id;
224    --  A universal_fixed expression in an universal context is unambiguous
225    --  if there is only one applicable fixed point type. Determining whether
226    --  there is only one requires a search over all visible entities, and
227    --  happens only in very pathological cases (see 6115-006).
228
229    function Valid_Conversion
230      (N       : Node_Id;
231       Target  : Entity_Id;
232       Operand : Node_Id) return Boolean;
233    --  Verify legality rules given in 4.6 (8-23). Target is the target
234    --  type of the conversion, which may be an implicit conversion of
235    --  an actual parameter to an anonymous access type (in which case
236    --  N denotes the actual parameter and N = Operand).
237
238    -------------------------
239    -- Ambiguous_Character --
240    -------------------------
241
242    procedure Ambiguous_Character (C : Node_Id) is
243       E : Entity_Id;
244
245    begin
246       if Nkind (C) = N_Character_Literal then
247          Error_Msg_N ("ambiguous character literal", C);
248          Error_Msg_N
249            ("\\possible interpretations: Character, Wide_Character!", C);
250
251          E := Current_Entity (C);
252          while Present (E) loop
253             Error_Msg_NE ("\\possible interpretation:}!", C, Etype (E));
254             E := Homonym (E);
255          end loop;
256       end if;
257    end Ambiguous_Character;
258
259    -------------------------
260    -- Analyze_And_Resolve --
261    -------------------------
262
263    procedure Analyze_And_Resolve (N : Node_Id) is
264    begin
265       Analyze (N);
266       Resolve (N);
267    end Analyze_And_Resolve;
268
269    procedure Analyze_And_Resolve (N : Node_Id; Typ : Entity_Id) is
270    begin
271       Analyze (N);
272       Resolve (N, Typ);
273    end Analyze_And_Resolve;
274
275    --  Version withs check(s) suppressed
276
277    procedure Analyze_And_Resolve
278      (N        : Node_Id;
279       Typ      : Entity_Id;
280       Suppress : Check_Id)
281    is
282       Scop : constant Entity_Id := Current_Scope;
283
284    begin
285       if Suppress = All_Checks then
286          declare
287             Svg : constant Suppress_Array := Scope_Suppress;
288          begin
289             Scope_Suppress := (others => True);
290             Analyze_And_Resolve (N, Typ);
291             Scope_Suppress := Svg;
292          end;
293
294       else
295          declare
296             Svg : constant Boolean := Scope_Suppress (Suppress);
297
298          begin
299             Scope_Suppress (Suppress) := True;
300             Analyze_And_Resolve (N, Typ);
301             Scope_Suppress (Suppress) := Svg;
302          end;
303       end if;
304
305       if Current_Scope /= Scop
306         and then Scope_Is_Transient
307       then
308          --  This can only happen if a transient scope was created
309          --  for an inner expression, which will be removed upon
310          --  completion of the analysis of an enclosing construct.
311          --  The transient scope must have the suppress status of
312          --  the enclosing environment, not of this Analyze call.
313
314          Scope_Stack.Table (Scope_Stack.Last).Save_Scope_Suppress :=
315            Scope_Suppress;
316       end if;
317    end Analyze_And_Resolve;
318
319    procedure Analyze_And_Resolve
320      (N        : Node_Id;
321       Suppress : Check_Id)
322    is
323       Scop : constant Entity_Id := Current_Scope;
324
325    begin
326       if Suppress = All_Checks then
327          declare
328             Svg : constant Suppress_Array := Scope_Suppress;
329          begin
330             Scope_Suppress := (others => True);
331             Analyze_And_Resolve (N);
332             Scope_Suppress := Svg;
333          end;
334
335       else
336          declare
337             Svg : constant Boolean := Scope_Suppress (Suppress);
338
339          begin
340             Scope_Suppress (Suppress) := True;
341             Analyze_And_Resolve (N);
342             Scope_Suppress (Suppress) := Svg;
343          end;
344       end if;
345
346       if Current_Scope /= Scop
347         and then Scope_Is_Transient
348       then
349          Scope_Stack.Table (Scope_Stack.Last).Save_Scope_Suppress :=
350            Scope_Suppress;
351       end if;
352    end Analyze_And_Resolve;
353
354    ----------------------------
355    -- Check_Discriminant_Use --
356    ----------------------------
357
358    procedure Check_Discriminant_Use (N : Node_Id) is
359       PN   : constant Node_Id   := Parent (N);
360       Disc : constant Entity_Id := Entity (N);
361       P    : Node_Id;
362       D    : Node_Id;
363
364    begin
365       --  Any use in a default expression is legal
366
367       if In_Default_Expression then
368          null;
369
370       elsif Nkind (PN) = N_Range then
371
372          --  Discriminant cannot be used to constrain a scalar type
373
374          P := Parent (PN);
375
376          if Nkind (P) = N_Range_Constraint
377            and then Nkind (Parent (P)) = N_Subtype_Indication
378            and then Nkind (Parent (Parent (P))) = N_Component_Definition
379          then
380             Error_Msg_N ("discriminant cannot constrain scalar type", N);
381
382          elsif Nkind (P) = N_Index_Or_Discriminant_Constraint then
383
384             --  The following check catches the unusual case where
385             --  a discriminant appears within an index constraint
386             --  that is part of a larger expression within a constraint
387             --  on a component, e.g. "C : Int range 1 .. F (new A(1 .. D))".
388             --  For now we only check case of record components, and
389             --  note that a similar check should also apply in the
390             --  case of discriminant constraints below. ???
391
392             --  Note that the check for N_Subtype_Declaration below is to
393             --  detect the valid use of discriminants in the constraints of a
394             --  subtype declaration when this subtype declaration appears
395             --  inside the scope of a record type (which is syntactically
396             --  illegal, but which may be created as part of derived type
397             --  processing for records). See Sem_Ch3.Build_Derived_Record_Type
398             --  for more info.
399
400             if Ekind (Current_Scope) = E_Record_Type
401               and then Scope (Disc) = Current_Scope
402               and then not
403                 (Nkind (Parent (P)) = N_Subtype_Indication
404                    and then
405                     (Nkind (Parent (Parent (P))) = N_Component_Definition
406                        or else
407                      Nkind (Parent (Parent (P))) = N_Subtype_Declaration)
408                   and then Paren_Count (N) = 0)
409             then
410                Error_Msg_N
411                  ("discriminant must appear alone in component constraint", N);
412                return;
413             end if;
414
415             --   Detect a common beginner error:
416
417             --   type R (D : Positive := 100) is record
418             --     Name : String (1 .. D);
419             --   end record;
420
421             --  The default value causes an object of type R to be
422             --  allocated with room for Positive'Last characters.
423
424             declare
425                SI : Node_Id;
426                T  : Entity_Id;
427                TB : Node_Id;
428                CB : Entity_Id;
429
430                function Large_Storage_Type (T : Entity_Id) return Boolean;
431                --  Return True if type T has a large enough range that
432                --  any array whose index type covered the whole range of
433                --  the type would likely raise Storage_Error.
434
435                ------------------------
436                -- Large_Storage_Type --
437                ------------------------
438
439                function Large_Storage_Type (T : Entity_Id) return Boolean is
440                begin
441                   return
442                     T = Standard_Integer
443                       or else
444                     T = Standard_Positive
445                       or else
446                     T = Standard_Natural;
447                end Large_Storage_Type;
448
449             begin
450                --  Check that the Disc has a large range
451
452                if not Large_Storage_Type (Etype (Disc)) then
453                   goto No_Danger;
454                end if;
455
456                --  If the enclosing type is limited, we allocate only the
457                --  default value, not the maximum, and there is no need for
458                --  a warning.
459
460                if Is_Limited_Type (Scope (Disc)) then
461                   goto No_Danger;
462                end if;
463
464                --  Check that it is the high bound
465
466                if N /= High_Bound (PN)
467                  or else No (Discriminant_Default_Value (Disc))
468                then
469                   goto No_Danger;
470                end if;
471
472                --  Check the array allows a large range at this bound.
473                --  First find the array
474
475                SI := Parent (P);
476
477                if Nkind (SI) /= N_Subtype_Indication then
478                   goto No_Danger;
479                end if;
480
481                T := Entity (Subtype_Mark (SI));
482
483                if not Is_Array_Type (T) then
484                   goto No_Danger;
485                end if;
486
487                --  Next, find the dimension
488
489                TB := First_Index (T);
490                CB := First (Constraints (P));
491                while True
492                  and then Present (TB)
493                  and then Present (CB)
494                  and then CB /= PN
495                loop
496                   Next_Index (TB);
497                   Next (CB);
498                end loop;
499
500                if CB /= PN then
501                   goto No_Danger;
502                end if;
503
504                --  Now, check the dimension has a large range
505
506                if not Large_Storage_Type (Etype (TB)) then
507                   goto No_Danger;
508                end if;
509
510                --  Warn about the danger
511
512                Error_Msg_N
513                  ("creation of & object may raise Storage_Error?",
514                   Scope (Disc));
515
516                <<No_Danger>>
517                   null;
518
519             end;
520          end if;
521
522       --  Legal case is in index or discriminant constraint
523
524       elsif Nkind (PN) = N_Index_Or_Discriminant_Constraint
525         or else Nkind (PN) = N_Discriminant_Association
526       then
527          if Paren_Count (N) > 0 then
528             Error_Msg_N
529               ("discriminant in constraint must appear alone",  N);
530
531          elsif Nkind (N) = N_Expanded_Name
532            and then Comes_From_Source (N)
533          then
534             Error_Msg_N
535               ("discriminant must appear alone as a direct name", N);
536          end if;
537
538          return;
539
540       --  Otherwise, context is an expression. It should not be within
541       --  (i.e. a subexpression of) a constraint for a component.
542
543       else
544          D := PN;
545          P := Parent (PN);
546          while Nkind (P) /= N_Component_Declaration
547            and then Nkind (P) /= N_Subtype_Indication
548            and then Nkind (P) /= N_Entry_Declaration
549          loop
550             D := P;
551             P := Parent (P);
552             exit when No (P);
553          end loop;
554
555          --  If the discriminant is used in an expression that is a bound
556          --  of a scalar type, an Itype is created and the bounds are attached
557          --  to its range,  not to the original subtype indication. Such use
558          --  is of course a double fault.
559
560          if (Nkind (P) = N_Subtype_Indication
561               and then
562                 (Nkind (Parent (P)) = N_Component_Definition
563                    or else
564                  Nkind (Parent (P)) = N_Derived_Type_Definition)
565               and then D = Constraint (P))
566
567          --  The constraint itself may be given by a subtype indication,
568          --  rather than by a more common discrete range.
569
570            or else (Nkind (P) = N_Subtype_Indication
571                       and then
572                     Nkind (Parent (P)) = N_Index_Or_Discriminant_Constraint)
573            or else Nkind (P) = N_Entry_Declaration
574            or else Nkind (D) = N_Defining_Identifier
575          then
576             Error_Msg_N
577               ("discriminant in constraint must appear alone",  N);
578          end if;
579       end if;
580    end Check_Discriminant_Use;
581
582    --------------------------------
583    -- Check_For_Visible_Operator --
584    --------------------------------
585
586    procedure Check_For_Visible_Operator (N : Node_Id; T : Entity_Id) is
587    begin
588       if Is_Invisible_Operator (N, T) then
589          Error_Msg_NE
590            ("operator for} is not directly visible!", N, First_Subtype (T));
591          Error_Msg_N ("use clause would make operation legal!", N);
592       end if;
593    end Check_For_Visible_Operator;
594
595    ----------------------------------
596    --  Check_Fully_Declared_Prefix --
597    ----------------------------------
598
599    procedure Check_Fully_Declared_Prefix
600      (Typ  : Entity_Id;
601       Pref : Node_Id)
602    is
603    begin
604       --  Check that the designated type of the prefix of a dereference is
605       --  not an incomplete type. This cannot be done unconditionally, because
606       --  dereferences of private types are legal in default expressions. This
607       --  case is taken care of in Check_Fully_Declared, called below. There
608       --  are also 2005 cases where it is legal for the prefix to be unfrozen.
609
610       --  This consideration also applies to similar checks for allocators,
611       --  qualified expressions, and type conversions.
612
613       --  An additional exception concerns other per-object expressions that
614       --  are not directly related to component declarations, in particular
615       --  representation pragmas for tasks. These will be per-object
616       --  expressions if they depend on discriminants or some global entity.
617       --  If the task has access discriminants, the designated type may be
618       --  incomplete at the point the expression is resolved. This resolution
619       --  takes place within the body of the initialization procedure, where
620       --  the discriminant is replaced by its discriminal.
621
622       if Is_Entity_Name (Pref)
623         and then Ekind (Entity (Pref)) = E_In_Parameter
624       then
625          null;
626
627       --  Ada 2005 (AI-326): Tagged incomplete types allowed. The wrong usages
628       --  are handled by Analyze_Access_Attribute, Analyze_Assignment,
629       --  Analyze_Object_Renaming, and Freeze_Entity.
630
631       elsif Ada_Version >= Ada_05
632         and then Is_Entity_Name (Pref)
633         and then Ekind (Directly_Designated_Type (Etype (Pref))) =
634                                                        E_Incomplete_Type
635         and then Is_Tagged_Type (Directly_Designated_Type (Etype (Pref)))
636       then
637          null;
638       else
639          Check_Fully_Declared (Typ, Parent (Pref));
640       end if;
641    end Check_Fully_Declared_Prefix;
642
643    ------------------------------
644    -- Check_Infinite_Recursion --
645    ------------------------------
646
647    function Check_Infinite_Recursion (N : Node_Id) return Boolean is
648       P : Node_Id;
649       C : Node_Id;
650
651       function Same_Argument_List return Boolean;
652       --  Check whether list of actuals is identical to list of formals
653       --  of called function (which is also the enclosing scope).
654
655       ------------------------
656       -- Same_Argument_List --
657       ------------------------
658
659       function Same_Argument_List return Boolean is
660          A    : Node_Id;
661          F    : Entity_Id;
662          Subp : Entity_Id;
663
664       begin
665          if not Is_Entity_Name (Name (N)) then
666             return False;
667          else
668             Subp := Entity (Name (N));
669          end if;
670
671          F := First_Formal (Subp);
672          A := First_Actual (N);
673          while Present (F) and then Present (A) loop
674             if not Is_Entity_Name (A)
675               or else Entity (A) /= F
676             then
677                return False;
678             end if;
679
680             Next_Actual (A);
681             Next_Formal (F);
682          end loop;
683
684          return True;
685       end Same_Argument_List;
686
687    --  Start of processing for Check_Infinite_Recursion
688
689    begin
690       --  Loop moving up tree, quitting if something tells us we are
691       --  definitely not in an infinite recursion situation.
692
693       C := N;
694       loop
695          P := Parent (C);
696          exit when Nkind (P) = N_Subprogram_Body;
697
698          if Nkind (P) = N_Or_Else        or else
699             Nkind (P) = N_And_Then       or else
700             Nkind (P) = N_If_Statement   or else
701             Nkind (P) = N_Case_Statement
702          then
703             return False;
704
705          elsif Nkind (P) = N_Handled_Sequence_Of_Statements
706            and then C /= First (Statements (P))
707          then
708             --  If the call is the expression of a return statement and
709             --  the actuals are identical to the formals, it's worth a
710             --  warning. However, we skip this if there is an immediately
711             --  preceding raise statement, since the call is never executed.
712
713             --  Furthermore, this corresponds to a common idiom:
714
715             --    function F (L : Thing) return Boolean is
716             --    begin
717             --       raise Program_Error;
718             --       return F (L);
719             --    end F;
720
721             --  for generating a stub function
722
723             if Nkind (Parent (N)) = N_Return_Statement
724               and then Same_Argument_List
725             then
726                exit when not Is_List_Member (Parent (N));
727
728                --  OK, return statement is in a statement list, look for raise
729
730                declare
731                   Nod : Node_Id;
732
733                begin
734                   --  Skip past N_Freeze_Entity nodes generated by expansion
735
736                   Nod := Prev (Parent (N));
737                   while Present (Nod)
738                     and then Nkind (Nod) = N_Freeze_Entity
739                   loop
740                      Prev (Nod);
741                   end loop;
742
743                   --  If no raise statement, give warning
744
745                   exit when Nkind (Nod) /= N_Raise_Statement
746                     and then
747                       (Nkind (Nod) not in N_Raise_xxx_Error
748                          or else Present (Condition (Nod)));
749                end;
750             end if;
751
752             return False;
753
754          else
755             C := P;
756          end if;
757       end loop;
758
759       Error_Msg_N ("possible infinite recursion?", N);
760       Error_Msg_N ("\Storage_Error may be raised at run time?", N);
761
762       return True;
763    end Check_Infinite_Recursion;
764
765    -------------------------------
766    -- Check_Initialization_Call --
767    -------------------------------
768
769    procedure Check_Initialization_Call (N : Entity_Id; Nam : Entity_Id) is
770       Typ : constant Entity_Id := Etype (First_Formal (Nam));
771
772       function Uses_SS (T : Entity_Id) return Boolean;
773       --  Check whether the creation of an object of the type will involve
774       --  use of the secondary stack. If T is a record type, this is true
775       --  if the expression for some component uses the secondary stack, eg.
776       --  through a call to a function that returns an unconstrained value.
777       --  False if T is controlled, because cleanups occur elsewhere.
778
779       -------------
780       -- Uses_SS --
781       -------------
782
783       function Uses_SS (T : Entity_Id) return Boolean is
784          Comp : Entity_Id;
785          Expr : Node_Id;
786
787       begin
788          if Is_Controlled (T) then
789             return False;
790
791          elsif Is_Array_Type (T) then
792             return Uses_SS (Component_Type (T));
793
794          elsif Is_Record_Type (T) then
795             Comp := First_Component (T);
796             while Present (Comp) loop
797                if Ekind (Comp) = E_Component
798                  and then Nkind (Parent (Comp)) = N_Component_Declaration
799                then
800                   Expr := Expression (Parent (Comp));
801
802                   --  The expression for a dynamic component may be
803                   --  rewritten as a dereference. Retrieve original
804                   --  call.
805
806                   if Nkind (Original_Node (Expr)) = N_Function_Call
807                     and then Requires_Transient_Scope (Etype (Expr))
808                   then
809                      return True;
810
811                   elsif Uses_SS (Etype (Comp)) then
812                      return True;
813                   end if;
814                end if;
815
816                Next_Component (Comp);
817             end loop;
818
819             return False;
820
821          else
822             return False;
823          end if;
824       end Uses_SS;
825
826    --  Start of processing for Check_Initialization_Call
827
828    begin
829       --  Establish a transient scope if the type needs it
830
831       if Uses_SS (Typ) then
832          Establish_Transient_Scope (First_Actual (N), Sec_Stack => True);
833       end if;
834    end Check_Initialization_Call;
835
836    ------------------------------
837    -- Check_Parameterless_Call --
838    ------------------------------
839
840    procedure Check_Parameterless_Call (N : Node_Id) is
841       Nam : Node_Id;
842
843       function Prefix_Is_Access_Subp return Boolean;
844       --  If the prefix is of an access_to_subprogram type, the node must be
845       --  rewritten as a call. Ditto if the prefix is overloaded and all its
846       --  interpretations are access to subprograms.
847
848       ---------------------------
849       -- Prefix_Is_Access_Subp --
850       ---------------------------
851
852       function Prefix_Is_Access_Subp return Boolean is
853          I   : Interp_Index;
854          It  : Interp;
855
856       begin
857          if not Is_Overloaded (N) then
858             return
859               Ekind (Etype (N)) = E_Subprogram_Type
860                 and then Base_Type (Etype (Etype (N))) /= Standard_Void_Type;
861          else
862             Get_First_Interp (N, I, It);
863             while Present (It.Typ) loop
864                if Ekind (It.Typ) /= E_Subprogram_Type
865                  or else Base_Type (Etype (It.Typ)) = Standard_Void_Type
866                then
867                   return False;
868                end if;
869
870                Get_Next_Interp (I, It);
871             end loop;
872
873             return True;
874          end if;
875       end Prefix_Is_Access_Subp;
876
877    --  Start of processing for Check_Parameterless_Call
878
879    begin
880       --  Defend against junk stuff if errors already detected
881
882       if Total_Errors_Detected /= 0 then
883          if Nkind (N) in N_Has_Etype and then Etype (N) = Any_Type then
884             return;
885          elsif Nkind (N) in N_Has_Chars
886            and then Chars (N) in Error_Name_Or_No_Name
887          then
888             return;
889          end if;
890
891          Require_Entity (N);
892       end if;
893
894       --  If the context expects a value, and the name is a procedure,
895       --  this is most likely a missing 'Access. Do not try to resolve
896       --  the parameterless call, error will be caught when the outer
897       --  call is analyzed.
898
899       if Is_Entity_Name (N)
900         and then Ekind (Entity (N)) = E_Procedure
901         and then not Is_Overloaded (N)
902         and then
903          (Nkind (Parent (N)) = N_Parameter_Association
904             or else Nkind (Parent (N)) = N_Function_Call
905             or else Nkind (Parent (N)) = N_Procedure_Call_Statement)
906       then
907          return;
908       end if;
909
910       --  Rewrite as call if overloadable entity that is (or could be, in
911       --  the overloaded case) a function call. If we know for sure that
912       --  the entity is an enumeration literal, we do not rewrite it.
913
914       if (Is_Entity_Name (N)
915             and then Is_Overloadable (Entity (N))
916             and then (Ekind (Entity (N)) /= E_Enumeration_Literal
917                         or else Is_Overloaded (N)))
918
919       --  Rewrite as call if it is an explicit deference of an expression of
920       --  a subprogram access type, and the suprogram type is not that of a
921       --  procedure or entry.
922
923       or else
924         (Nkind (N) = N_Explicit_Dereference and then Prefix_Is_Access_Subp)
925
926       --  Rewrite as call if it is a selected component which is a function,
927       --  this is the case of a call to a protected function (which may be
928       --  overloaded with other protected operations).
929
930       or else
931         (Nkind (N) = N_Selected_Component
932           and then (Ekind (Entity (Selector_Name (N))) = E_Function
933                       or else
934                         ((Ekind (Entity (Selector_Name (N))) = E_Entry
935                             or else
936                           Ekind (Entity (Selector_Name (N))) = E_Procedure)
937                             and then Is_Overloaded (Selector_Name (N)))))
938
939       --  If one of the above three conditions is met, rewrite as call.
940       --  Apply the rewriting only once.
941
942       then
943          if Nkind (Parent (N)) /= N_Function_Call
944            or else N /= Name (Parent (N))
945          then
946             Nam := New_Copy (N);
947
948             --  If overloaded, overload set belongs to new copy
949
950             Save_Interps (N, Nam);
951
952             --  Change node to parameterless function call (note that the
953             --  Parameter_Associations associations field is left set to Empty,
954             --  its normal default value since there are no parameters)
955
956             Change_Node (N, N_Function_Call);
957             Set_Name (N, Nam);
958             Set_Sloc (N, Sloc (Nam));
959             Analyze_Call (N);
960          end if;
961
962       elsif Nkind (N) = N_Parameter_Association then
963          Check_Parameterless_Call (Explicit_Actual_Parameter (N));
964       end if;
965    end Check_Parameterless_Call;
966
967    ----------------------
968    -- Is_Predefined_Op --
969    ----------------------
970
971    function Is_Predefined_Op (Nam : Entity_Id) return Boolean is
972    begin
973       return Is_Intrinsic_Subprogram (Nam)
974         and then not Is_Generic_Instance (Nam)
975         and then Chars (Nam) in Any_Operator_Name
976         and then (No (Alias (Nam))
977                    or else Is_Predefined_Op (Alias (Nam)));
978    end Is_Predefined_Op;
979
980    -----------------------------
981    -- Make_Call_Into_Operator --
982    -----------------------------
983
984    procedure Make_Call_Into_Operator
985      (N     : Node_Id;
986       Typ   : Entity_Id;
987       Op_Id : Entity_Id)
988    is
989       Op_Name   : constant Name_Id := Chars (Op_Id);
990       Act1      : Node_Id := First_Actual (N);
991       Act2      : Node_Id := Next_Actual (Act1);
992       Error     : Boolean := False;
993       Func      : constant Entity_Id := Entity (Name (N));
994       Is_Binary : constant Boolean   := Present (Act2);
995       Op_Node   : Node_Id;
996       Opnd_Type : Entity_Id;
997       Orig_Type : Entity_Id := Empty;
998       Pack      : Entity_Id;
999
1000       type Kind_Test is access function (E : Entity_Id) return Boolean;
1001
1002       function Is_Definite_Access_Type (E : Entity_Id) return Boolean;
1003       --  Determine whether E is an access type declared by an access decla-
1004       --  ration, and  not an (anonymous) allocator type.
1005
1006       function Operand_Type_In_Scope (S : Entity_Id) return Boolean;
1007       --  If the operand is not universal, and the operator is given by a
1008       --  expanded name,  verify that the operand has an interpretation with
1009       --  a type defined in the given scope of the operator.
1010
1011       function Type_In_P (Test : Kind_Test) return Entity_Id;
1012       --  Find a type of the given class in the package Pack that contains
1013       --  the operator.
1014
1015       -----------------------------
1016       -- Is_Definite_Access_Type --
1017       -----------------------------
1018
1019       function Is_Definite_Access_Type (E : Entity_Id) return Boolean is
1020          Btyp : constant Entity_Id := Base_Type (E);
1021       begin
1022          return Ekind (Btyp) = E_Access_Type
1023            or else (Ekind (Btyp) = E_Access_Subprogram_Type
1024                      and then Comes_From_Source (Btyp));
1025       end Is_Definite_Access_Type;
1026
1027       ---------------------------
1028       -- Operand_Type_In_Scope --
1029       ---------------------------
1030
1031       function Operand_Type_In_Scope (S : Entity_Id) return Boolean is
1032          Nod : constant Node_Id := Right_Opnd (Op_Node);
1033          I   : Interp_Index;
1034          It  : Interp;
1035
1036       begin
1037          if not Is_Overloaded (Nod) then
1038             return Scope (Base_Type (Etype (Nod))) = S;
1039
1040          else
1041             Get_First_Interp (Nod, I, It);
1042             while Present (It.Typ) loop
1043                if Scope (Base_Type (It.Typ)) = S then
1044                   return True;
1045                end if;
1046
1047                Get_Next_Interp (I, It);
1048             end loop;
1049
1050             return False;
1051          end if;
1052       end Operand_Type_In_Scope;
1053
1054       ---------------
1055       -- Type_In_P --
1056       ---------------
1057
1058       function Type_In_P (Test : Kind_Test) return Entity_Id is
1059          E : Entity_Id;
1060
1061          function In_Decl return Boolean;
1062          --  Verify that node is not part of the type declaration for the
1063          --  candidate type, which would otherwise be invisible.
1064
1065          -------------
1066          -- In_Decl --
1067          -------------
1068
1069          function In_Decl return Boolean is
1070             Decl_Node : constant Node_Id := Parent (E);
1071             N2        : Node_Id;
1072
1073          begin
1074             N2 := N;
1075
1076             if Etype (E) = Any_Type then
1077                return True;
1078
1079             elsif No (Decl_Node) then
1080                return False;
1081
1082             else
1083                while Present (N2)
1084                  and then Nkind (N2) /= N_Compilation_Unit
1085                loop
1086                   if N2 = Decl_Node then
1087                      return True;
1088                   else
1089                      N2 := Parent (N2);
1090                   end if;
1091                end loop;
1092
1093                return False;
1094             end if;
1095          end In_Decl;
1096
1097       --  Start of processing for Type_In_P
1098
1099       begin
1100          --  If the context type is declared in the prefix package, this
1101          --  is the desired base type.
1102
1103          if Scope (Base_Type (Typ)) = Pack
1104            and then Test (Typ)
1105          then
1106             return Base_Type (Typ);
1107
1108          else
1109             E := First_Entity (Pack);
1110             while Present (E) loop
1111                if Test (E)
1112                  and then not In_Decl
1113                then
1114                   return E;
1115                end if;
1116
1117                Next_Entity (E);
1118             end loop;
1119
1120             return Empty;
1121          end if;
1122       end Type_In_P;
1123
1124    --  Start of processing for Make_Call_Into_Operator
1125
1126    begin
1127       Op_Node := New_Node (Operator_Kind (Op_Name, Is_Binary), Sloc (N));
1128
1129       --  Binary operator
1130
1131       if Is_Binary then
1132          Set_Left_Opnd  (Op_Node, Relocate_Node (Act1));
1133          Set_Right_Opnd (Op_Node, Relocate_Node (Act2));
1134          Save_Interps (Act1, Left_Opnd  (Op_Node));
1135          Save_Interps (Act2, Right_Opnd (Op_Node));
1136          Act1 := Left_Opnd (Op_Node);
1137          Act2 := Right_Opnd (Op_Node);
1138
1139       --  Unary operator
1140
1141       else
1142          Set_Right_Opnd (Op_Node, Relocate_Node (Act1));
1143          Save_Interps (Act1, Right_Opnd (Op_Node));
1144          Act1 := Right_Opnd (Op_Node);
1145       end if;
1146
1147       --  If the operator is denoted by an expanded name, and the prefix is
1148       --  not Standard, but the operator is a predefined one whose scope is
1149       --  Standard, then this is an implicit_operator, inserted as an
1150       --  interpretation by the procedure of the same name. This procedure
1151       --  overestimates the presence of implicit operators, because it does
1152       --  not examine the type of the operands. Verify now that the operand
1153       --  type appears in the given scope. If right operand is universal,
1154       --  check the other operand. In the case of concatenation, either
1155       --  argument can be the component type, so check the type of the result.
1156       --  If both arguments are literals, look for a type of the right kind
1157       --  defined in the given scope. This elaborate nonsense is brought to
1158       --  you courtesy of b33302a. The type itself must be frozen, so we must
1159       --  find the type of the proper class in the given scope.
1160
1161       --  A final wrinkle is the multiplication operator for fixed point
1162       --  types, which is defined in Standard only, and not in the scope of
1163       --  the fixed_point type itself.
1164
1165       if Nkind (Name (N)) = N_Expanded_Name then
1166          Pack := Entity (Prefix (Name (N)));
1167
1168          --  If the entity being called is defined in the given package,
1169          --  it is a renaming of a predefined operator, and known to be
1170          --  legal.
1171
1172          if Scope (Entity (Name (N))) = Pack
1173             and then Pack /= Standard_Standard
1174          then
1175             null;
1176
1177          --  Visibility does not need to be checked in an instance: if the
1178          --  operator was not visible in the generic it has been diagnosed
1179          --  already, else there is an implicit copy of it in the instance.
1180
1181          elsif In_Instance then
1182             null;
1183
1184          elsif (Op_Name =  Name_Op_Multiply
1185               or else Op_Name = Name_Op_Divide)
1186            and then Is_Fixed_Point_Type (Etype (Left_Opnd  (Op_Node)))
1187            and then Is_Fixed_Point_Type (Etype (Right_Opnd (Op_Node)))
1188          then
1189             if Pack /= Standard_Standard then
1190                Error := True;
1191             end if;
1192
1193          --  Ada 2005, AI-420:  Predefined equality on Universal_Access
1194          --  is available.
1195
1196          elsif Ada_Version >= Ada_05
1197            and then (Op_Name = Name_Op_Eq or else Op_Name = Name_Op_Ne)
1198            and then Ekind (Etype (Act1)) = E_Anonymous_Access_Type
1199          then
1200             null;
1201
1202          else
1203             Opnd_Type := Base_Type (Etype (Right_Opnd (Op_Node)));
1204
1205             if Op_Name = Name_Op_Concat then
1206                Opnd_Type := Base_Type (Typ);
1207
1208             elsif (Scope (Opnd_Type) = Standard_Standard
1209                      and then Is_Binary)
1210               or else (Nkind (Right_Opnd (Op_Node)) = N_Attribute_Reference
1211                         and then Is_Binary
1212                         and then not Comes_From_Source (Opnd_Type))
1213             then
1214                Opnd_Type := Base_Type (Etype (Left_Opnd (Op_Node)));
1215             end if;
1216
1217             if Scope (Opnd_Type) = Standard_Standard then
1218
1219                --  Verify that the scope contains a type that corresponds to
1220                --  the given literal. Optimize the case where Pack is Standard.
1221
1222                if Pack /= Standard_Standard then
1223
1224                   if Opnd_Type = Universal_Integer then
1225                      Orig_Type :=  Type_In_P (Is_Integer_Type'Access);
1226
1227                   elsif Opnd_Type = Universal_Real then
1228                      Orig_Type := Type_In_P (Is_Real_Type'Access);
1229
1230                   elsif Opnd_Type = Any_String then
1231                      Orig_Type := Type_In_P (Is_String_Type'Access);
1232
1233                   elsif Opnd_Type = Any_Access then
1234                      Orig_Type :=  Type_In_P (Is_Definite_Access_Type'Access);
1235
1236                   elsif Opnd_Type = Any_Composite then
1237                      Orig_Type := Type_In_P (Is_Composite_Type'Access);
1238
1239                      if Present (Orig_Type) then
1240                         if Has_Private_Component (Orig_Type) then
1241                            Orig_Type := Empty;
1242                         else
1243                            Set_Etype (Act1, Orig_Type);
1244
1245                            if Is_Binary then
1246                               Set_Etype (Act2, Orig_Type);
1247                            end if;
1248                         end if;
1249                      end if;
1250
1251                   else
1252                      Orig_Type := Empty;
1253                   end if;
1254
1255                   Error := No (Orig_Type);
1256                end if;
1257
1258             elsif Ekind (Opnd_Type) = E_Allocator_Type
1259                and then No (Type_In_P (Is_Definite_Access_Type'Access))
1260             then
1261                Error := True;
1262
1263             --  If the type is defined elsewhere, and the operator is not
1264             --  defined in the given scope (by a renaming declaration, e.g.)
1265             --  then this is an error as well. If an extension of System is
1266             --  present, and the type may be defined there, Pack must be
1267             --  System itself.
1268
1269             elsif Scope (Opnd_Type) /= Pack
1270               and then Scope (Op_Id) /= Pack
1271               and then (No (System_Aux_Id)
1272                          or else Scope (Opnd_Type) /= System_Aux_Id
1273                          or else Pack /= Scope (System_Aux_Id))
1274             then
1275                if not Is_Overloaded (Right_Opnd (Op_Node)) then
1276                   Error := True;
1277                else
1278                   Error := not Operand_Type_In_Scope (Pack);
1279                end if;
1280
1281             elsif Pack = Standard_Standard
1282               and then not Operand_Type_In_Scope (Standard_Standard)
1283             then
1284                Error := True;
1285             end if;
1286          end if;
1287
1288          if Error then
1289             Error_Msg_Node_2 := Pack;
1290             Error_Msg_NE
1291               ("& not declared in&", N, Selector_Name (Name (N)));
1292             Set_Etype (N, Any_Type);
1293             return;
1294          end if;
1295       end if;
1296
1297       Set_Chars  (Op_Node, Op_Name);
1298
1299       if not Is_Private_Type (Etype (N)) then
1300          Set_Etype (Op_Node, Base_Type (Etype (N)));
1301       else
1302          Set_Etype (Op_Node, Etype (N));
1303       end if;
1304
1305       --  If this is a call to a function that renames a predefined equality,
1306       --  the renaming declaration provides a type that must be used to
1307       --  resolve the operands. This must be done now because resolution of
1308       --  the equality node will not resolve any remaining ambiguity, and it
1309       --  assumes that the first operand is not overloaded.
1310
1311       if (Op_Name = Name_Op_Eq or else Op_Name = Name_Op_Ne)
1312         and then Ekind (Func) = E_Function
1313         and then Is_Overloaded (Act1)
1314       then
1315          Resolve (Act1, Base_Type (Etype (First_Formal (Func))));
1316          Resolve (Act2, Base_Type (Etype (First_Formal (Func))));
1317       end if;
1318
1319       Set_Entity (Op_Node, Op_Id);
1320       Generate_Reference (Op_Id, N, ' ');
1321       Rewrite (N,  Op_Node);
1322
1323       --  If this is an arithmetic operator and the result type is private,
1324       --  the operands and the result must be wrapped in conversion to
1325       --  expose the underlying numeric type and expand the proper checks,
1326       --  e.g. on division.
1327
1328       if Is_Private_Type (Typ) then
1329          case Nkind (N) is
1330             when N_Op_Add  | N_Op_Subtract | N_Op_Multiply | N_Op_Divide |
1331             N_Op_Expon     | N_Op_Mod      | N_Op_Rem      =>
1332                Resolve_Intrinsic_Operator (N, Typ);
1333
1334             when N_Op_Plus | N_Op_Minus    | N_Op_Abs      =>
1335                Resolve_Intrinsic_Unary_Operator (N, Typ);
1336
1337             when others =>
1338                Resolve (N, Typ);
1339          end case;
1340       else
1341          Resolve (N, Typ);
1342       end if;
1343
1344       --  For predefined operators on literals, the operation freezes
1345       --  their type.
1346
1347       if Present (Orig_Type) then
1348          Set_Etype (Act1, Orig_Type);
1349          Freeze_Expression (Act1);
1350       end if;
1351    end Make_Call_Into_Operator;
1352
1353    -------------------
1354    -- Operator_Kind --
1355    -------------------
1356
1357    function Operator_Kind
1358      (Op_Name   : Name_Id;
1359       Is_Binary : Boolean) return Node_Kind
1360    is
1361       Kind : Node_Kind;
1362
1363    begin
1364       if Is_Binary then
1365          if    Op_Name =  Name_Op_And      then Kind := N_Op_And;
1366          elsif Op_Name =  Name_Op_Or       then Kind := N_Op_Or;
1367          elsif Op_Name =  Name_Op_Xor      then Kind := N_Op_Xor;
1368          elsif Op_Name =  Name_Op_Eq       then Kind := N_Op_Eq;
1369          elsif Op_Name =  Name_Op_Ne       then Kind := N_Op_Ne;
1370          elsif Op_Name =  Name_Op_Lt       then Kind := N_Op_Lt;
1371          elsif Op_Name =  Name_Op_Le       then Kind := N_Op_Le;
1372          elsif Op_Name =  Name_Op_Gt       then Kind := N_Op_Gt;
1373          elsif Op_Name =  Name_Op_Ge       then Kind := N_Op_Ge;
1374          elsif Op_Name =  Name_Op_Add      then Kind := N_Op_Add;
1375          elsif Op_Name =  Name_Op_Subtract then Kind := N_Op_Subtract;
1376          elsif Op_Name =  Name_Op_Concat   then Kind := N_Op_Concat;
1377          elsif Op_Name =  Name_Op_Multiply then Kind := N_Op_Multiply;
1378          elsif Op_Name =  Name_Op_Divide   then Kind := N_Op_Divide;
1379          elsif Op_Name =  Name_Op_Mod      then Kind := N_Op_Mod;
1380          elsif Op_Name =  Name_Op_Rem      then Kind := N_Op_Rem;
1381          elsif Op_Name =  Name_Op_Expon    then Kind := N_Op_Expon;
1382          else
1383             raise Program_Error;
1384          end if;
1385
1386       --  Unary operators
1387
1388       else
1389          if    Op_Name =  Name_Op_Add      then Kind := N_Op_Plus;
1390          elsif Op_Name =  Name_Op_Subtract then Kind := N_Op_Minus;
1391          elsif Op_Name =  Name_Op_Abs      then Kind := N_Op_Abs;
1392          elsif Op_Name =  Name_Op_Not      then Kind := N_Op_Not;
1393          else
1394             raise Program_Error;
1395          end if;
1396       end if;
1397
1398       return Kind;
1399    end Operator_Kind;
1400
1401    -----------------------------
1402    -- Pre_Analyze_And_Resolve --
1403    -----------------------------
1404
1405    procedure Pre_Analyze_And_Resolve (N : Node_Id; T : Entity_Id) is
1406       Save_Full_Analysis : constant Boolean := Full_Analysis;
1407
1408    begin
1409       Full_Analysis := False;
1410       Expander_Mode_Save_And_Set (False);
1411
1412       --  We suppress all checks for this analysis, since the checks will
1413       --  be applied properly, and in the right location, when the default
1414       --  expression is reanalyzed and reexpanded later on.
1415
1416       Analyze_And_Resolve (N, T, Suppress => All_Checks);
1417
1418       Expander_Mode_Restore;
1419       Full_Analysis := Save_Full_Analysis;
1420    end Pre_Analyze_And_Resolve;
1421
1422    --  Version without context type
1423
1424    procedure Pre_Analyze_And_Resolve (N : Node_Id) is
1425       Save_Full_Analysis : constant Boolean := Full_Analysis;
1426
1427    begin
1428       Full_Analysis := False;
1429       Expander_Mode_Save_And_Set (False);
1430
1431       Analyze (N);
1432       Resolve (N, Etype (N), Suppress => All_Checks);
1433
1434       Expander_Mode_Restore;
1435       Full_Analysis := Save_Full_Analysis;
1436    end Pre_Analyze_And_Resolve;
1437
1438    ----------------------------------
1439    -- Replace_Actual_Discriminants --
1440    ----------------------------------
1441
1442    procedure Replace_Actual_Discriminants (N : Node_Id; Default : Node_Id) is
1443       Loc : constant Source_Ptr := Sloc (N);
1444       Tsk : Node_Id := Empty;
1445
1446       function Process_Discr (Nod : Node_Id) return Traverse_Result;
1447
1448       -------------------
1449       -- Process_Discr --
1450       -------------------
1451
1452       function Process_Discr (Nod : Node_Id) return Traverse_Result is
1453          Ent : Entity_Id;
1454
1455       begin
1456          if Nkind (Nod) = N_Identifier then
1457             Ent := Entity (Nod);
1458
1459             if Present (Ent)
1460               and then Ekind (Ent) = E_Discriminant
1461             then
1462                Rewrite (Nod,
1463                  Make_Selected_Component (Loc,
1464                    Prefix        => New_Copy_Tree (Tsk, New_Sloc => Loc),
1465                    Selector_Name => Make_Identifier (Loc, Chars (Ent))));
1466
1467                Set_Etype (Nod, Etype (Ent));
1468             end if;
1469
1470          end if;
1471
1472          return OK;
1473       end Process_Discr;
1474
1475       procedure Replace_Discrs is new Traverse_Proc (Process_Discr);
1476
1477    --  Start of processing for Replace_Actual_Discriminants
1478
1479    begin
1480       if not Expander_Active then
1481          return;
1482       end if;
1483
1484       if Nkind (Name (N)) = N_Selected_Component then
1485          Tsk := Prefix (Name (N));
1486
1487       elsif Nkind (Name (N)) = N_Indexed_Component then
1488          Tsk := Prefix (Prefix (Name (N)));
1489       end if;
1490
1491       if No (Tsk) then
1492          return;
1493       else
1494          Replace_Discrs (Default);
1495       end if;
1496    end Replace_Actual_Discriminants;
1497
1498    -------------
1499    -- Resolve --
1500    -------------
1501
1502    procedure Resolve (N : Node_Id; Typ : Entity_Id) is
1503       I         : Interp_Index;
1504       I1        : Interp_Index := 0; -- prevent junk warning
1505       It        : Interp;
1506       It1       : Interp;
1507       Found     : Boolean   := False;
1508       Seen      : Entity_Id := Empty; -- prevent junk warning
1509       Ctx_Type  : Entity_Id := Typ;
1510       Expr_Type : Entity_Id := Empty; -- prevent junk warning
1511       Err_Type  : Entity_Id := Empty;
1512       Ambiguous : Boolean   := False;
1513
1514       procedure Patch_Up_Value (N : Node_Id; Typ : Entity_Id);
1515       --  Try and fix up a literal so that it matches its expected type. New
1516       --  literals are manufactured if necessary to avoid cascaded errors.
1517
1518       procedure Resolution_Failed;
1519       --  Called when attempt at resolving current expression fails
1520
1521       --------------------
1522       -- Patch_Up_Value --
1523       --------------------
1524
1525       procedure Patch_Up_Value (N : Node_Id; Typ : Entity_Id) is
1526       begin
1527          if Nkind (N) = N_Integer_Literal
1528            and then Is_Real_Type (Typ)
1529          then
1530             Rewrite (N,
1531               Make_Real_Literal (Sloc (N),
1532                 Realval => UR_From_Uint (Intval (N))));
1533             Set_Etype (N, Universal_Real);
1534             Set_Is_Static_Expression (N);
1535
1536          elsif Nkind (N) = N_Real_Literal
1537            and then Is_Integer_Type (Typ)
1538          then
1539             Rewrite (N,
1540               Make_Integer_Literal (Sloc (N),
1541                 Intval => UR_To_Uint (Realval (N))));
1542             Set_Etype (N, Universal_Integer);
1543             Set_Is_Static_Expression (N);
1544          elsif Nkind (N) = N_String_Literal
1545            and then Is_Character_Type (Typ)
1546          then
1547             Set_Character_Literal_Name (Char_Code (Character'Pos ('A')));
1548             Rewrite (N,
1549               Make_Character_Literal (Sloc (N),
1550                 Chars => Name_Find,
1551                 Char_Literal_Value =>
1552                   UI_From_Int (Character'Pos ('A'))));
1553             Set_Etype (N, Any_Character);
1554             Set_Is_Static_Expression (N);
1555
1556          elsif Nkind (N) /= N_String_Literal
1557            and then Is_String_Type (Typ)
1558          then
1559             Rewrite (N,
1560               Make_String_Literal (Sloc (N),
1561                 Strval => End_String));
1562
1563          elsif Nkind (N) = N_Range then
1564             Patch_Up_Value (Low_Bound (N), Typ);
1565             Patch_Up_Value (High_Bound (N), Typ);
1566          end if;
1567       end Patch_Up_Value;
1568
1569       -----------------------
1570       -- Resolution_Failed --
1571       -----------------------
1572
1573       procedure Resolution_Failed is
1574       begin
1575          Patch_Up_Value (N, Typ);
1576          Set_Etype (N, Typ);
1577          Debug_A_Exit ("resolving  ", N, " (done, resolution failed)");
1578          Set_Is_Overloaded (N, False);
1579
1580          --  The caller will return without calling the expander, so we need
1581          --  to set the analyzed flag. Note that it is fine to set Analyzed
1582          --  to True even if we are in the middle of a shallow analysis,
1583          --  (see the spec of sem for more details) since this is an error
1584          --  situation anyway, and there is no point in repeating the
1585          --  analysis later (indeed it won't work to repeat it later, since
1586          --  we haven't got a clear resolution of which entity is being
1587          --  referenced.)
1588
1589          Set_Analyzed (N, True);
1590          return;
1591       end Resolution_Failed;
1592
1593    --  Start of processing for Resolve
1594
1595    begin
1596       if N = Error then
1597          return;
1598       end if;
1599
1600       --  Access attribute on remote subprogram cannot be used for
1601       --  a non-remote access-to-subprogram type.
1602
1603       if Nkind (N) = N_Attribute_Reference
1604         and then (Attribute_Name (N) = Name_Access
1605                     or else Attribute_Name (N) = Name_Unrestricted_Access
1606                     or else Attribute_Name (N) = Name_Unchecked_Access)
1607         and then Comes_From_Source (N)
1608         and then Is_Entity_Name (Prefix (N))
1609         and then Is_Subprogram (Entity (Prefix (N)))
1610         and then Is_Remote_Call_Interface (Entity (Prefix (N)))
1611         and then not Is_Remote_Access_To_Subprogram_Type (Typ)
1612       then
1613          Error_Msg_N
1614            ("prefix must statically denote a non-remote subprogram", N);
1615       end if;
1616
1617       --  If the context is a Remote_Access_To_Subprogram, access attributes
1618       --  must be resolved with the corresponding fat pointer. There is no need
1619       --  to check for the attribute name since the return type of an
1620       --  attribute is never a remote type.
1621
1622       if Nkind (N) = N_Attribute_Reference
1623         and then Comes_From_Source (N)
1624         and then (Is_Remote_Call_Interface (Typ)
1625                     or else Is_Remote_Types (Typ))
1626       then
1627          declare
1628             Attr      : constant Attribute_Id :=
1629                           Get_Attribute_Id (Attribute_Name (N));
1630             Pref      : constant Node_Id      := Prefix (N);
1631             Decl      : Node_Id;
1632             Spec      : Node_Id;
1633             Is_Remote : Boolean := True;
1634
1635          begin
1636             --  Check that Typ is a remote access-to-subprogram type
1637
1638             if Is_Remote_Access_To_Subprogram_Type (Typ) then
1639                --  Prefix (N) must statically denote a remote subprogram
1640                --  declared in a package specification.
1641
1642                if Attr = Attribute_Access then
1643                   Decl := Unit_Declaration_Node (Entity (Pref));
1644
1645                   if Nkind (Decl) = N_Subprogram_Body then
1646                      Spec := Corresponding_Spec (Decl);
1647
1648                      if not No (Spec) then
1649                         Decl := Unit_Declaration_Node (Spec);
1650                      end if;
1651                   end if;
1652
1653                   Spec := Parent (Decl);
1654
1655                   if not Is_Entity_Name (Prefix (N))
1656                     or else Nkind (Spec) /= N_Package_Specification
1657                     or else
1658                       not Is_Remote_Call_Interface (Defining_Entity (Spec))
1659                   then
1660                      Is_Remote := False;
1661                      Error_Msg_N
1662                        ("prefix must statically denote a remote subprogram ",
1663                         N);
1664                   end if;
1665                end if;
1666
1667                --   If we are generating code for a distributed program.
1668                --   perform semantic checks against the corresponding
1669                --   remote entities.
1670
1671                if (Attr = Attribute_Access
1672                     or else Attr = Attribute_Unchecked_Access
1673                     or else Attr = Attribute_Unrestricted_Access)
1674                  and then Expander_Active
1675                  and then Get_PCS_Name /= Name_No_DSA
1676                then
1677                   Check_Subtype_Conformant
1678                     (New_Id  => Entity (Prefix (N)),
1679                      Old_Id  => Designated_Type
1680                        (Corresponding_Remote_Type (Typ)),
1681                      Err_Loc => N);
1682                   if Is_Remote then
1683                      Process_Remote_AST_Attribute (N, Typ);
1684                   end if;
1685                end if;
1686             end if;
1687          end;
1688       end if;
1689
1690       Debug_A_Entry ("resolving  ", N);
1691
1692       if Comes_From_Source (N) then
1693          if Is_Fixed_Point_Type (Typ) then
1694             Check_Restriction (No_Fixed_Point, N);
1695
1696          elsif Is_Floating_Point_Type (Typ)
1697            and then Typ /= Universal_Real
1698            and then Typ /= Any_Real
1699          then
1700             Check_Restriction (No_Floating_Point, N);
1701          end if;
1702       end if;
1703
1704       --  Return if already analyzed
1705
1706       if Analyzed (N) then
1707          Debug_A_Exit ("resolving  ", N, "  (done, already analyzed)");
1708          return;
1709
1710       --  Return if type = Any_Type (previous error encountered)
1711
1712       elsif Etype (N) = Any_Type then
1713          Debug_A_Exit ("resolving  ", N, "  (done, Etype = Any_Type)");
1714          return;
1715       end if;
1716
1717       Check_Parameterless_Call (N);
1718
1719       --  If not overloaded, then we know the type, and all that needs doing
1720       --  is to check that this type is compatible with the context.
1721
1722       if not Is_Overloaded (N) then
1723          Found := Covers (Typ, Etype (N));
1724          Expr_Type := Etype (N);
1725
1726       --  In the overloaded case, we must select the interpretation that
1727       --  is compatible with the context (i.e. the type passed to Resolve)
1728
1729       else
1730          --  Loop through possible interpretations
1731
1732          Get_First_Interp (N, I, It);
1733          Interp_Loop : while Present (It.Typ) loop
1734
1735             --  We are only interested in interpretations that are compatible
1736             --  with the expected type, any other interpretations are ignored
1737
1738             if not Covers (Typ, It.Typ) then
1739                if Debug_Flag_V then
1740                   Write_Str ("    interpretation incompatible with context");
1741                   Write_Eol;
1742                end if;
1743
1744             else
1745                --  First matching interpretation
1746
1747                if not Found then
1748                   Found := True;
1749                   I1    := I;
1750                   Seen  := It.Nam;
1751                   Expr_Type := It.Typ;
1752
1753                --  Matching interpretation that is not the first, maybe an
1754                --  error, but there are some cases where preference rules are
1755                --  used to choose between the two possibilities. These and
1756                --  some more obscure cases are handled in Disambiguate.
1757
1758                else
1759                   Error_Msg_Sloc := Sloc (Seen);
1760                   It1 := Disambiguate (N, I1, I, Typ);
1761
1762                   --  Disambiguation has succeeded. Skip the remaining
1763                   --  interpretations.
1764
1765                   if It1 /= No_Interp then
1766                      Seen := It1.Nam;
1767                      Expr_Type := It1.Typ;
1768
1769                      while Present (It.Typ) loop
1770                         Get_Next_Interp (I, It);
1771                      end loop;
1772
1773                   else
1774                      --  Before we issue an ambiguity complaint, check for
1775                      --  the case of a subprogram call where at least one
1776                      --  of the arguments is Any_Type, and if so, suppress
1777                      --  the message, since it is a cascaded error.
1778
1779                      if Nkind (N) = N_Function_Call
1780                        or else Nkind (N) = N_Procedure_Call_Statement
1781                      then
1782                         declare
1783                            A : Node_Id;
1784                            E : Node_Id;
1785
1786                         begin
1787                            A := First_Actual (N);
1788                            while Present (A) loop
1789                               E := A;
1790
1791                               if Nkind (E) = N_Parameter_Association then
1792                                  E := Explicit_Actual_Parameter (E);
1793                               end if;
1794
1795                               if Etype (E) = Any_Type then
1796                                  if Debug_Flag_V then
1797                                     Write_Str ("Any_Type in call");
1798                                     Write_Eol;
1799                                  end if;
1800
1801                                  exit Interp_Loop;
1802                               end if;
1803
1804                               Next_Actual (A);
1805                            end loop;
1806                         end;
1807
1808                      elsif Nkind (N) in  N_Binary_Op
1809                        and then (Etype (Left_Opnd (N)) = Any_Type
1810                                   or else Etype (Right_Opnd (N)) = Any_Type)
1811                      then
1812                         exit Interp_Loop;
1813
1814                      elsif Nkind (N) in  N_Unary_Op
1815                        and then Etype (Right_Opnd (N)) = Any_Type
1816                      then
1817                         exit Interp_Loop;
1818                      end if;
1819
1820                      --  Not that special case, so issue message using the
1821                      --  flag Ambiguous to control printing of the header
1822                      --  message only at the start of an ambiguous set.
1823
1824                      if not Ambiguous then
1825                         if Nkind (N) = N_Function_Call
1826                           and then Nkind (Name (N)) = N_Explicit_Dereference
1827                         then
1828                            Error_Msg_N
1829                              ("ambiguous expression "
1830                                & "(cannot resolve indirect call)!", N);
1831                         else
1832                            Error_Msg_NE
1833                              ("ambiguous expression (cannot resolve&)!",
1834                               N, It.Nam);
1835                         end if;
1836
1837                         Ambiguous := True;
1838
1839                         if Nkind (Parent (Seen)) = N_Full_Type_Declaration then
1840                            Error_Msg_N
1841                              ("\\possible interpretation (inherited)#!", N);
1842                         else
1843                            Error_Msg_N ("\\possible interpretation#!", N);
1844                         end if;
1845                      end if;
1846
1847                      Error_Msg_Sloc := Sloc (It.Nam);
1848
1849                      --  By default, the error message refers to the candidate
1850                      --  interpretation. But if it is a predefined operator, it
1851                      --  is implicitly declared at the declaration of the type
1852                      --  of the operand. Recover the sloc of that declaration
1853                      --  for the error message.
1854
1855                      if Nkind (N) in N_Op
1856                        and then Scope (It.Nam) = Standard_Standard
1857                        and then not Is_Overloaded (Right_Opnd (N))
1858                        and then Scope (Base_Type (Etype (Right_Opnd (N)))) /=
1859                                                              Standard_Standard
1860                      then
1861                         Err_Type := First_Subtype (Etype (Right_Opnd (N)));
1862
1863                         if Comes_From_Source (Err_Type)
1864                           and then Present (Parent (Err_Type))
1865                         then
1866                            Error_Msg_Sloc := Sloc (Parent (Err_Type));
1867                         end if;
1868
1869                      elsif Nkind (N) in N_Binary_Op
1870                        and then Scope (It.Nam) = Standard_Standard
1871                        and then not Is_Overloaded (Left_Opnd (N))
1872                        and then Scope (Base_Type (Etype (Left_Opnd (N)))) /=
1873                                                              Standard_Standard
1874                      then
1875                         Err_Type := First_Subtype (Etype (Left_Opnd (N)));
1876
1877                         if Comes_From_Source (Err_Type)
1878                           and then Present (Parent (Err_Type))
1879                         then
1880                            Error_Msg_Sloc := Sloc (Parent (Err_Type));
1881                         end if;
1882
1883                      --  If this is an indirect call, use the subprogram_type
1884                      --  in the message, to have a meaningful location.
1885                      --  Indicate as well if this is an inherited operation,
1886                      --  created by a type declaration.
1887
1888                      elsif Nkind (N) = N_Function_Call
1889                        and then Nkind (Name (N)) = N_Explicit_Dereference
1890                        and then Is_Type (It.Nam)
1891                      then
1892                         Err_Type := It.Nam;
1893                         Error_Msg_Sloc :=
1894                           Sloc (Associated_Node_For_Itype (Err_Type));
1895                      else
1896                         Err_Type := Empty;
1897                      end if;
1898
1899                      if Nkind (N) in N_Op
1900                        and then Scope (It.Nam) = Standard_Standard
1901                        and then Present (Err_Type)
1902                      then
1903                         Error_Msg_N
1904                           ("\\possible interpretation (predefined)#!", N);
1905
1906                      elsif
1907                        Nkind (Parent (It.Nam)) = N_Full_Type_Declaration
1908                      then
1909                         Error_Msg_N
1910                           ("\\possible interpretation (inherited)#!", N);
1911                      else
1912                         Error_Msg_N ("\\possible interpretation#!", N);
1913                      end if;
1914
1915                   end if;
1916                end if;
1917
1918                --  We have a matching interpretation, Expr_Type is the type
1919                --  from this interpretation, and Seen is the entity.
1920
1921                --  For an operator, just set the entity name. The type will be
1922                --  set by the specific operator resolution routine.
1923
1924                if Nkind (N) in N_Op then
1925                   Set_Entity (N, Seen);
1926                   Generate_Reference (Seen, N);
1927
1928                elsif Nkind (N) = N_Character_Literal then
1929                   Set_Etype (N, Expr_Type);
1930
1931                --  For an explicit dereference, attribute reference, range,
1932                --  short-circuit form (which is not an operator node), or call
1933                --  with a name that is an explicit dereference, there is
1934                --  nothing to be done at this point.
1935
1936                elsif     Nkind (N) = N_Explicit_Dereference
1937                  or else Nkind (N) = N_Attribute_Reference
1938                  or else Nkind (N) = N_And_Then
1939                  or else Nkind (N) = N_Indexed_Component
1940                  or else Nkind (N) = N_Or_Else
1941                  or else Nkind (N) = N_Range
1942                  or else Nkind (N) = N_Selected_Component
1943                  or else Nkind (N) = N_Slice
1944                  or else Nkind (Name (N)) = N_Explicit_Dereference
1945                then
1946                   null;
1947
1948                --  For procedure or function calls, set the type of the name,
1949                --  and also the entity pointer for the prefix
1950
1951                elsif (Nkind (N) = N_Procedure_Call_Statement
1952                        or else Nkind (N) = N_Function_Call)
1953                  and then (Is_Entity_Name (Name (N))
1954                             or else Nkind (Name (N)) = N_Operator_Symbol)
1955                then
1956                   Set_Etype  (Name (N), Expr_Type);
1957                   Set_Entity (Name (N), Seen);
1958                   Generate_Reference (Seen, Name (N));
1959
1960                elsif Nkind (N) = N_Function_Call
1961                  and then Nkind (Name (N)) = N_Selected_Component
1962                then
1963                   Set_Etype (Name (N), Expr_Type);
1964                   Set_Entity (Selector_Name (Name (N)), Seen);
1965                   Generate_Reference (Seen, Selector_Name (Name (N)));
1966
1967                --  For all other cases, just set the type of the Name
1968
1969                else
1970                   Set_Etype (Name (N), Expr_Type);
1971                end if;
1972
1973             end if;
1974
1975             --  Move to next interpretation
1976
1977             exit Interp_Loop when No (It.Typ);
1978
1979             Get_Next_Interp (I, It);
1980          end loop Interp_Loop;
1981       end if;
1982
1983       --  At this stage Found indicates whether or not an acceptable
1984       --  interpretation exists. If not, then we have an error, except
1985       --  that if the context is Any_Type as a result of some other error,
1986       --  then we suppress the error report.
1987
1988       if not Found then
1989          if Typ /= Any_Type then
1990
1991             --  If type we are looking for is Void, then this is the procedure
1992             --  call case, and the error is simply that what we gave is not a
1993             --  procedure name (we think of procedure calls as expressions with
1994             --  types internally, but the user doesn't think of them this way!)
1995
1996             if Typ = Standard_Void_Type then
1997
1998                --  Special case message if function used as a procedure
1999
2000                if Nkind (N) = N_Procedure_Call_Statement
2001                  and then Is_Entity_Name (Name (N))
2002                  and then Ekind (Entity (Name (N))) = E_Function
2003                then
2004                   Error_Msg_NE
2005                     ("cannot use function & in a procedure call",
2006                      Name (N), Entity (Name (N)));
2007
2008                --  Otherwise give general message (not clear what cases this
2009                --  covers, but no harm in providing for them!)
2010
2011                else
2012                   Error_Msg_N ("expect procedure name in procedure call", N);
2013                end if;
2014
2015                Found := True;
2016
2017             --  Otherwise we do have a subexpression with the wrong type
2018
2019             --  Check for the case of an allocator which uses an access type
2020             --  instead of the designated type. This is a common error and we
2021             --  specialize the message, posting an error on the operand of the
2022             --  allocator, complaining that we expected the designated type of
2023             --  the allocator.
2024
2025             elsif Nkind (N) = N_Allocator
2026               and then Ekind (Typ) in Access_Kind
2027               and then Ekind (Etype (N)) in Access_Kind
2028               and then Designated_Type (Etype (N)) = Typ
2029             then
2030                Wrong_Type (Expression (N), Designated_Type (Typ));
2031                Found := True;
2032
2033             --  Check for view mismatch on Null in instances, for which the
2034             --  view-swapping mechanism has no identifier.
2035
2036             elsif (In_Instance or else In_Inlined_Body)
2037               and then (Nkind (N) = N_Null)
2038               and then Is_Private_Type (Typ)
2039               and then Is_Access_Type (Full_View (Typ))
2040             then
2041                Resolve (N, Full_View (Typ));
2042                Set_Etype (N, Typ);
2043                return;
2044
2045             --  Check for an aggregate. Sometimes we can get bogus aggregates
2046             --  from misuse of parentheses, and we are about to complain about
2047             --  the aggregate without even looking inside it.
2048
2049             --  Instead, if we have an aggregate of type Any_Composite, then
2050             --  analyze and resolve the component fields, and then only issue
2051             --  another message if we get no errors doing this (otherwise
2052             --  assume that the errors in the aggregate caused the problem).
2053
2054             elsif Nkind (N) = N_Aggregate
2055               and then Etype (N) = Any_Composite
2056             then
2057                --  Disable expansion in any case. If there is a type mismatch
2058                --  it may be fatal to try to expand the aggregate. The flag
2059                --  would otherwise be set to false when the error is posted.
2060
2061                Expander_Active := False;
2062
2063                declare
2064                   procedure Check_Aggr (Aggr : Node_Id);
2065                   --  Check one aggregate, and set Found to True if we have a
2066                   --  definite error in any of its elements
2067
2068                   procedure Check_Elmt (Aelmt : Node_Id);
2069                   --  Check one element of aggregate and set Found to True if
2070                   --  we definitely have an error in the element.
2071
2072                   ----------------
2073                   -- Check_Aggr --
2074                   ----------------
2075
2076                   procedure Check_Aggr (Aggr : Node_Id) is
2077                      Elmt : Node_Id;
2078
2079                   begin
2080                      if Present (Expressions (Aggr)) then
2081                         Elmt := First (Expressions (Aggr));
2082                         while Present (Elmt) loop
2083                            Check_Elmt (Elmt);
2084                            Next (Elmt);
2085                         end loop;
2086                      end if;
2087
2088                      if Present (Component_Associations (Aggr)) then
2089                         Elmt := First (Component_Associations (Aggr));
2090                         while Present (Elmt) loop
2091
2092                            --  If this is a default-initialized component, then
2093                            --  there is nothing to check. The box will be
2094                            --  replaced by the appropriate call during late
2095                            --  expansion.
2096
2097                            if not Box_Present (Elmt) then
2098                               Check_Elmt (Expression (Elmt));
2099                            end if;
2100
2101                            Next (Elmt);
2102                         end loop;
2103                      end if;
2104                   end Check_Aggr;
2105
2106                   ----------------
2107                   -- Check_Elmt --
2108                   ----------------
2109
2110                   procedure Check_Elmt (Aelmt : Node_Id) is
2111                   begin
2112                      --  If we have a nested aggregate, go inside it (to
2113                      --  attempt a naked analyze-resolve of the aggregate
2114                      --  can cause undesirable cascaded errors). Do not
2115                      --  resolve expression if it needs a type from context,
2116                      --  as for integer * fixed expression.
2117
2118                      if Nkind (Aelmt) = N_Aggregate then
2119                         Check_Aggr (Aelmt);
2120
2121                      else
2122                         Analyze (Aelmt);
2123
2124                         if not Is_Overloaded (Aelmt)
2125                           and then Etype (Aelmt) /= Any_Fixed
2126                         then
2127                            Resolve (Aelmt);
2128                         end if;
2129
2130                         if Etype (Aelmt) = Any_Type then
2131                            Found := True;
2132                         end if;
2133                      end if;
2134                   end Check_Elmt;
2135
2136                begin
2137                   Check_Aggr (N);
2138                end;
2139             end if;
2140
2141             --  If an error message was issued already, Found got reset
2142             --  to True, so if it is still False, issue the standard
2143             --  Wrong_Type message.
2144
2145             if not Found then
2146                if Is_Overloaded (N)
2147                  and then Nkind (N) = N_Function_Call
2148                then
2149                   declare
2150                      Subp_Name : Node_Id;
2151                   begin
2152                      if Is_Entity_Name (Name (N)) then
2153                         Subp_Name := Name (N);
2154
2155                      elsif Nkind (Name (N)) = N_Selected_Component then
2156
2157                         --  Protected operation: retrieve operation name
2158
2159                         Subp_Name := Selector_Name (Name (N));
2160                      else
2161                         raise Program_Error;
2162                      end if;
2163
2164                      Error_Msg_Node_2 := Typ;
2165                      Error_Msg_NE ("no visible interpretation of&" &
2166                        " matches expected type&", N, Subp_Name);
2167                   end;
2168
2169                   if All_Errors_Mode then
2170                      declare
2171                         Index : Interp_Index;
2172                         It    : Interp;
2173
2174                      begin
2175                         Error_Msg_N ("\\possible interpretations:", N);
2176
2177                         Get_First_Interp (Name (N), Index, It);
2178                         while Present (It.Nam) loop
2179                            Error_Msg_Sloc := Sloc (It.Nam);
2180                            Error_Msg_Node_2 := It.Typ;
2181                            Error_Msg_NE ("\&  declared#, type&", N, It.Nam);
2182                            Get_Next_Interp (Index, It);
2183                         end loop;
2184                      end;
2185                   else
2186                      Error_Msg_N ("\use -gnatf for details", N);
2187                   end if;
2188                else
2189                   Wrong_Type (N, Typ);
2190                end if;
2191             end if;
2192          end if;
2193
2194          Resolution_Failed;
2195          return;
2196
2197       --  Test if we have more than one interpretation for the context
2198
2199       elsif Ambiguous then
2200          Resolution_Failed;
2201          return;
2202
2203       --  Here we have an acceptable interpretation for the context
2204
2205       else
2206          --  Propagate type information and normalize tree for various
2207          --  predefined operations. If the context only imposes a class of
2208          --  types, rather than a specific type, propagate the actual type
2209          --  downward.
2210
2211          if Typ = Any_Integer
2212            or else Typ = Any_Boolean
2213            or else Typ = Any_Modular
2214            or else Typ = Any_Real
2215            or else Typ = Any_Discrete
2216          then
2217             Ctx_Type := Expr_Type;
2218
2219             --  Any_Fixed is legal in a real context only if a specific
2220             --  fixed point type is imposed. If Norman Cohen can be
2221             --  confused by this, it deserves a separate message.
2222
2223             if Typ = Any_Real
2224               and then Expr_Type = Any_Fixed
2225             then
2226                Error_Msg_N ("illegal context for mixed mode operation", N);
2227                Set_Etype (N, Universal_Real);
2228                Ctx_Type := Universal_Real;
2229             end if;
2230          end if;
2231
2232          --  A user-defined operator is tranformed into a function call at
2233          --  this point, so that further processing knows that operators are
2234          --  really operators (i.e. are predefined operators). User-defined
2235          --  operators that are intrinsic are just renamings of the predefined
2236          --  ones, and need not be turned into calls either, but if they rename
2237          --  a different operator, we must transform the node accordingly.
2238          --  Instantiations of Unchecked_Conversion are intrinsic but are
2239          --  treated as functions, even if given an operator designator.
2240
2241          if Nkind (N) in N_Op
2242            and then Present (Entity (N))
2243            and then Ekind (Entity (N)) /= E_Operator
2244          then
2245
2246             if not Is_Predefined_Op (Entity (N)) then
2247                Rewrite_Operator_As_Call (N, Entity (N));
2248
2249             elsif Present (Alias (Entity (N)))
2250               and then
2251                 Nkind (Parent (Parent (Entity (N))))
2252                   = N_Subprogram_Renaming_Declaration
2253             then
2254                Rewrite_Renamed_Operator (N, Alias (Entity (N)), Typ);
2255
2256                --  If the node is rewritten, it will be fully resolved in
2257                --  Rewrite_Renamed_Operator.
2258
2259                if Analyzed (N) then
2260                   return;
2261                end if;
2262             end if;
2263          end if;
2264
2265          case N_Subexpr'(Nkind (N)) is
2266
2267             when N_Aggregate => Resolve_Aggregate                (N, Ctx_Type);
2268
2269             when N_Allocator => Resolve_Allocator                (N, Ctx_Type);
2270
2271             when N_And_Then | N_Or_Else
2272                              => Resolve_Short_Circuit            (N, Ctx_Type);
2273
2274             when N_Attribute_Reference
2275                              => Resolve_Attribute                (N, Ctx_Type);
2276
2277             when N_Character_Literal
2278                              => Resolve_Character_Literal        (N, Ctx_Type);
2279
2280             when N_Conditional_Expression
2281                              => Resolve_Conditional_Expression   (N, Ctx_Type);
2282
2283             when N_Expanded_Name
2284                              => Resolve_Entity_Name              (N, Ctx_Type);
2285
2286             when N_Extension_Aggregate
2287                              => Resolve_Extension_Aggregate      (N, Ctx_Type);
2288
2289             when N_Explicit_Dereference
2290                              => Resolve_Explicit_Dereference     (N, Ctx_Type);
2291
2292             when N_Function_Call
2293                              => Resolve_Call                     (N, Ctx_Type);
2294
2295             when N_Identifier
2296                              => Resolve_Entity_Name              (N, Ctx_Type);
2297
2298             when N_Indexed_Component
2299                              => Resolve_Indexed_Component        (N, Ctx_Type);
2300
2301             when N_Integer_Literal
2302                              => Resolve_Integer_Literal          (N, Ctx_Type);
2303
2304             when N_Membership_Test
2305                              => Resolve_Membership_Op            (N, Ctx_Type);
2306
2307             when N_Null      => Resolve_Null                     (N, Ctx_Type);
2308
2309             when N_Op_And | N_Op_Or | N_Op_Xor
2310                              => Resolve_Logical_Op               (N, Ctx_Type);
2311
2312             when N_Op_Eq | N_Op_Ne
2313                              => Resolve_Equality_Op              (N, Ctx_Type);
2314
2315             when N_Op_Lt | N_Op_Le | N_Op_Gt | N_Op_Ge
2316                              => Resolve_Comparison_Op            (N, Ctx_Type);
2317
2318             when N_Op_Not    => Resolve_Op_Not                   (N, Ctx_Type);
2319
2320             when N_Op_Add    | N_Op_Subtract | N_Op_Multiply |
2321                  N_Op_Divide | N_Op_Mod      | N_Op_Rem
2322
2323                              => Resolve_Arithmetic_Op            (N, Ctx_Type);
2324
2325             when N_Op_Concat => Resolve_Op_Concat                (N, Ctx_Type);
2326
2327             when N_Op_Expon  => Resolve_Op_Expon                 (N, Ctx_Type);
2328
2329             when N_Op_Plus | N_Op_Minus  | N_Op_Abs
2330                              => Resolve_Unary_Op                 (N, Ctx_Type);
2331
2332             when N_Op_Shift  => Resolve_Shift                    (N, Ctx_Type);
2333
2334             when N_Procedure_Call_Statement
2335                              => Resolve_Call                     (N, Ctx_Type);
2336
2337             when N_Operator_Symbol
2338                              => Resolve_Operator_Symbol          (N, Ctx_Type);
2339
2340             when N_Qualified_Expression
2341                              => Resolve_Qualified_Expression     (N, Ctx_Type);
2342
2343             when N_Raise_xxx_Error
2344                              => Set_Etype (N, Ctx_Type);
2345
2346             when N_Range     => Resolve_Range                    (N, Ctx_Type);
2347
2348             when N_Real_Literal
2349                              => Resolve_Real_Literal             (N, Ctx_Type);
2350
2351             when N_Reference => Resolve_Reference                (N, Ctx_Type);
2352
2353             when N_Selected_Component
2354                              => Resolve_Selected_Component       (N, Ctx_Type);
2355
2356             when N_Slice     => Resolve_Slice                    (N, Ctx_Type);
2357
2358             when N_String_Literal
2359                              => Resolve_String_Literal           (N, Ctx_Type);
2360
2361             when N_Subprogram_Info
2362                              => Resolve_Subprogram_Info          (N, Ctx_Type);
2363
2364             when N_Type_Conversion
2365                              => Resolve_Type_Conversion          (N, Ctx_Type);
2366
2367             when N_Unchecked_Expression =>
2368                Resolve_Unchecked_Expression                      (N, Ctx_Type);
2369
2370             when N_Unchecked_Type_Conversion =>
2371                Resolve_Unchecked_Type_Conversion                 (N, Ctx_Type);
2372
2373          end case;
2374
2375          --  If the subexpression was replaced by a non-subexpression, then
2376          --  all we do is to expand it. The only legitimate case we know of
2377          --  is converting procedure call statement to entry call statements,
2378          --  but there may be others, so we are making this test general.
2379
2380          if Nkind (N) not in N_Subexpr then
2381             Debug_A_Exit ("resolving  ", N, "  (done)");
2382             Expand (N);
2383             return;
2384          end if;
2385
2386          --  The expression is definitely NOT overloaded at this point, so
2387          --  we reset the Is_Overloaded flag to avoid any confusion when
2388          --  reanalyzing the node.
2389
2390          Set_Is_Overloaded (N, False);
2391
2392          --  Freeze expression type, entity if it is a name, and designated
2393          --  type if it is an allocator (RM 13.14(10,11,13)).
2394
2395          --  Now that the resolution of the type of the node is complete,
2396          --  and we did not detect an error, we can expand this node. We
2397          --  skip the expand call if we are in a default expression, see
2398          --  section "Handling of Default Expressions" in Sem spec.
2399
2400          Debug_A_Exit ("resolving  ", N, "  (done)");
2401
2402          --  We unconditionally freeze the expression, even if we are in
2403          --  default expression mode (the Freeze_Expression routine tests
2404          --  this flag and only freezes static types if it is set).
2405
2406          Freeze_Expression (N);
2407
2408          --  Now we can do the expansion
2409
2410          Expand (N);
2411       end if;
2412    end Resolve;
2413
2414    -------------
2415    -- Resolve --
2416    -------------
2417
2418    --  Version with check(s) suppressed
2419
2420    procedure Resolve (N : Node_Id; Typ : Entity_Id; Suppress : Check_Id) is
2421    begin
2422       if Suppress = All_Checks then
2423          declare
2424             Svg : constant Suppress_Array := Scope_Suppress;
2425          begin
2426             Scope_Suppress := (others => True);
2427             Resolve (N, Typ);
2428             Scope_Suppress := Svg;
2429          end;
2430
2431       else
2432          declare
2433             Svg : constant Boolean := Scope_Suppress (Suppress);
2434          begin
2435             Scope_Suppress (Suppress) := True;
2436             Resolve (N, Typ);
2437             Scope_Suppress (Suppress) := Svg;
2438          end;
2439       end if;
2440    end Resolve;
2441
2442    -------------
2443    -- Resolve --
2444    -------------
2445
2446    --  Version with implicit type
2447
2448    procedure Resolve (N : Node_Id) is
2449    begin
2450       Resolve (N, Etype (N));
2451    end Resolve;
2452
2453    ---------------------
2454    -- Resolve_Actuals --
2455    ---------------------
2456
2457    procedure Resolve_Actuals (N : Node_Id; Nam : Entity_Id) is
2458       Loc    : constant Source_Ptr := Sloc (N);
2459       A      : Node_Id;
2460       F      : Entity_Id;
2461       A_Typ  : Entity_Id;
2462       F_Typ  : Entity_Id;
2463       Prev   : Node_Id := Empty;
2464
2465       procedure Insert_Default;
2466       --  If the actual is missing in a call, insert in the actuals list
2467       --  an instance of the default expression. The insertion is always
2468       --  a named association.
2469
2470       function Same_Ancestor (T1, T2 : Entity_Id) return Boolean;
2471       --  Check whether T1 and T2, or their full views, are derived from a
2472       --  common type. Used to enforce the restrictions on array conversions
2473       --  of AI95-00246.
2474
2475       --------------------
2476       -- Insert_Default --
2477       --------------------
2478
2479       procedure Insert_Default is
2480          Actval : Node_Id;
2481          Assoc  : Node_Id;
2482
2483       begin
2484          --  Missing argument in call, nothing to insert
2485
2486          if No (Default_Value (F)) then
2487             return;
2488
2489          else
2490             --  Note that we do a full New_Copy_Tree, so that any associated
2491             --  Itypes are properly copied. This may not be needed any more,
2492             --  but it does no harm as a safety measure! Defaults of a generic
2493             --  formal may be out of bounds of the corresponding actual (see
2494             --  cc1311b) and an additional check may be required.
2495
2496             Actval := New_Copy_Tree (Default_Value (F),
2497                         New_Scope => Current_Scope, New_Sloc => Loc);
2498
2499             if Is_Concurrent_Type (Scope (Nam))
2500               and then Has_Discriminants (Scope (Nam))
2501             then
2502                Replace_Actual_Discriminants (N, Actval);
2503             end if;
2504
2505             if Is_Overloadable (Nam)
2506               and then Present (Alias (Nam))
2507             then
2508                if Base_Type (Etype (F)) /= Base_Type (Etype (Actval))
2509                  and then not Is_Tagged_Type (Etype (F))
2510                then
2511                   --  If default is a real literal, do not introduce a
2512                   --  conversion whose effect may depend on the run-time
2513                   --  size of universal real.
2514
2515                   if Nkind (Actval) = N_Real_Literal then
2516                      Set_Etype (Actval, Base_Type (Etype (F)));
2517                   else
2518                      Actval := Unchecked_Convert_To (Etype (F), Actval);
2519                   end if;
2520                end if;
2521
2522                if Is_Scalar_Type (Etype (F)) then
2523                   Enable_Range_Check (Actval);
2524                end if;
2525
2526                Set_Parent (Actval, N);
2527
2528                --  Resolve aggregates with their base type, to avoid scope
2529                --  anomalies: the subtype was first built in the suprogram
2530                --  declaration, and the current call may be nested.
2531
2532                if Nkind (Actval) = N_Aggregate
2533                  and then Has_Discriminants (Etype (Actval))
2534                then
2535                   Analyze_And_Resolve (Actval, Base_Type (Etype (Actval)));
2536                else
2537                   Analyze_And_Resolve (Actval, Etype (Actval));
2538                end if;
2539
2540             else
2541                Set_Parent (Actval, N);
2542
2543                --  See note above concerning aggregates
2544
2545                if Nkind (Actval) = N_Aggregate
2546                  and then Has_Discriminants (Etype (Actval))
2547                then
2548                   Analyze_And_Resolve (Actval, Base_Type (Etype (Actval)));
2549
2550                --  Resolve entities with their own type, which may differ
2551                --  from the type of a reference in a generic context (the
2552                --  view swapping mechanism did not anticipate the re-analysis
2553                --  of default values in calls).
2554
2555                elsif Is_Entity_Name (Actval) then
2556                   Analyze_And_Resolve (Actval, Etype (Entity (Actval)));
2557
2558                else
2559                   Analyze_And_Resolve (Actval, Etype (Actval));
2560                end if;
2561             end if;
2562
2563             --  If default is a tag indeterminate function call, propagate
2564             --  tag to obtain proper dispatching.
2565
2566             if Is_Controlling_Formal (F)
2567               and then Nkind (Default_Value (F)) = N_Function_Call
2568             then
2569                Set_Is_Controlling_Actual (Actval);
2570             end if;
2571
2572          end if;
2573
2574          --  If the default expression raises constraint error, then just
2575          --  silently replace it with an N_Raise_Constraint_Error node,
2576          --  since we already gave the warning on the subprogram spec.
2577
2578          if Raises_Constraint_Error (Actval) then
2579             Rewrite (Actval,
2580               Make_Raise_Constraint_Error (Loc,
2581                 Reason => CE_Range_Check_Failed));
2582             Set_Raises_Constraint_Error (Actval);
2583             Set_Etype (Actval, Etype (F));
2584          end if;
2585
2586          Assoc :=
2587            Make_Parameter_Association (Loc,
2588              Explicit_Actual_Parameter => Actval,
2589              Selector_Name => Make_Identifier (Loc, Chars (F)));
2590
2591          --  Case of insertion is first named actual
2592
2593          if No (Prev) or else
2594             Nkind (Parent (Prev)) /= N_Parameter_Association
2595          then
2596             Set_Next_Named_Actual (Assoc, First_Named_Actual (N));
2597             Set_First_Named_Actual (N, Actval);
2598
2599             if No (Prev) then
2600                if No (Parameter_Associations (N)) then
2601                   Set_Parameter_Associations (N, New_List (Assoc));
2602                else
2603                   Append (Assoc, Parameter_Associations (N));
2604                end if;
2605
2606             else
2607                Insert_After (Prev, Assoc);
2608             end if;
2609
2610          --  Case of insertion is not first named actual
2611
2612          else
2613             Set_Next_Named_Actual
2614               (Assoc, Next_Named_Actual (Parent (Prev)));
2615             Set_Next_Named_Actual (Parent (Prev), Actval);
2616             Append (Assoc, Parameter_Associations (N));
2617          end if;
2618
2619          Mark_Rewrite_Insertion (Assoc);
2620          Mark_Rewrite_Insertion (Actval);
2621
2622          Prev := Actval;
2623       end Insert_Default;
2624
2625       -------------------
2626       -- Same_Ancestor --
2627       -------------------
2628
2629       function Same_Ancestor (T1, T2 : Entity_Id) return Boolean is
2630          FT1 : Entity_Id := T1;
2631          FT2 : Entity_Id := T2;
2632
2633       begin
2634          if Is_Private_Type (T1)
2635            and then Present (Full_View (T1))
2636          then
2637             FT1 := Full_View (T1);
2638          end if;
2639
2640          if Is_Private_Type (T2)
2641            and then Present (Full_View (T2))
2642          then
2643             FT2 := Full_View (T2);
2644          end if;
2645
2646          return Root_Type (Base_Type (FT1)) = Root_Type (Base_Type (FT2));
2647       end Same_Ancestor;
2648
2649    --  Start of processing for Resolve_Actuals
2650
2651    begin
2652       A := First_Actual (N);
2653       F := First_Formal (Nam);
2654       while Present (F) loop
2655          if No (A) and then Needs_No_Actuals (Nam) then
2656             null;
2657
2658          --  If we have an error in any actual or formal, indicated by
2659          --  a type of Any_Type, then abandon resolution attempt, and
2660          --  set result type to Any_Type.
2661
2662          elsif (Present (A) and then Etype (A) = Any_Type)
2663            or else Etype (F) = Any_Type
2664          then
2665             Set_Etype (N, Any_Type);
2666             return;
2667          end if;
2668
2669          if Present (A)
2670            and then (Nkind (Parent (A)) /= N_Parameter_Association
2671                        or else
2672                      Chars (Selector_Name (Parent (A))) = Chars (F))
2673          then
2674             --  If the formal is Out or In_Out, do not resolve and expand the
2675             --  conversion, because it is subsequently expanded into explicit
2676             --  temporaries and assignments. However, the object of the
2677             --  conversion can be resolved. An exception is the case of tagged
2678             --  type conversion with a class-wide actual. In that case we want
2679             --  the tag check to occur and no temporary will be needed (no
2680             --  representation change can occur) and the parameter is passed by
2681             --  reference, so we go ahead and resolve the type conversion.
2682             --  Another exception is the case of reference to component or
2683             --  subcomponent of a bit-packed array, in which case we want to
2684             --  defer expansion to the point the in and out assignments are
2685             --  performed.
2686
2687             if Ekind (F) /= E_In_Parameter
2688               and then Nkind (A) = N_Type_Conversion
2689               and then not Is_Class_Wide_Type (Etype (Expression (A)))
2690             then
2691                if Ekind (F) = E_In_Out_Parameter
2692                  and then Is_Array_Type (Etype (F))
2693                then
2694                   if Has_Aliased_Components (Etype (Expression (A)))
2695                     /= Has_Aliased_Components (Etype (F))
2696                   then
2697                      if Ada_Version < Ada_05 then
2698                         Error_Msg_N
2699                           ("both component types in a view conversion must be"
2700                             & " aliased, or neither", A);
2701
2702                      --  Ada 2005: rule is relaxed (see AI-363)
2703
2704                      elsif Has_Aliased_Components (Etype (F))
2705                        and then
2706                          not Has_Aliased_Components (Etype (Expression (A)))
2707                      then
2708                         Error_Msg_N
2709                           ("view conversion operand must have aliased " &
2710                            "components", N);
2711                         Error_Msg_N
2712                           ("\since target type has aliased components", N);
2713                      end if;
2714
2715                   elsif not Same_Ancestor (Etype (F), Etype (Expression (A)))
2716                     and then
2717                      (Is_By_Reference_Type (Etype (F))
2718                         or else Is_By_Reference_Type (Etype (Expression (A))))
2719                   then
2720                      Error_Msg_N
2721                        ("view conversion between unrelated by reference " &
2722                         "array types not allowed (\'A'I-00246)", A);
2723                   end if;
2724                end if;
2725
2726                if (Conversion_OK (A)
2727                      or else Valid_Conversion (A, Etype (A), Expression (A)))
2728                  and then not Is_Ref_To_Bit_Packed_Array (Expression (A))
2729                then
2730                   Resolve (Expression (A));
2731                end if;
2732
2733             else
2734                if Nkind (A) = N_Type_Conversion
2735                  and then Is_Array_Type (Etype (F))
2736                  and then not Same_Ancestor (Etype (F), Etype (Expression (A)))
2737                  and then
2738                   (Is_Limited_Type (Etype (F))
2739                      or else Is_Limited_Type (Etype (Expression (A))))
2740                then
2741                   Error_Msg_N
2742                     ("conversion between unrelated limited array types " &
2743                      "not allowed (\A\I-00246)", A);
2744
2745                   if Is_Limited_Type (Etype (F)) then
2746                      Explain_Limited_Type (Etype (F), A);
2747                   end if;
2748
2749                   if Is_Limited_Type (Etype (Expression (A))) then
2750                      Explain_Limited_Type (Etype (Expression (A)), A);
2751                   end if;
2752                end if;
2753
2754                --  (Ada 2005: AI-251): If the actual is an allocator whose
2755                --  directly designated type is a class-wide interface, we build
2756                --  an anonymous access type to use it as the type of the
2757                --  allocator. Later, when the subprogram call is expanded, if
2758                --  the interface has a secondary dispatch table the expander
2759                --  will add a type conversion to force the correct displacement
2760                --  of the pointer.
2761
2762                if Nkind (A) = N_Allocator then
2763                   declare
2764                      DDT : constant Entity_Id :=
2765                              Directly_Designated_Type (Base_Type (Etype (F)));
2766                      New_Itype : Entity_Id;
2767                   begin
2768                      if Is_Class_Wide_Type (DDT)
2769                        and then Is_Interface (DDT)
2770                      then
2771                         New_Itype := Create_Itype (E_Anonymous_Access_Type, A);
2772                         Set_Etype       (New_Itype, Etype (A));
2773                         Init_Size_Align (New_Itype);
2774                         Set_Directly_Designated_Type (New_Itype,
2775                           Directly_Designated_Type (Etype (A)));
2776                         Set_Etype (A, New_Itype);
2777                      end if;
2778
2779                      --  Ada 2005, AI-162:If the actual is an allocator, the
2780                      --  innermost enclosing statement is the master of the
2781                      --  created object.
2782
2783                      if Is_Controlled (DDT)
2784                        or else Has_Task (DDT)
2785                      then
2786                         Establish_Transient_Scope (A, False);
2787                      end if;
2788                   end;
2789                end if;
2790
2791                Resolve (A, Etype (F));
2792             end if;
2793
2794             A_Typ := Etype (A);
2795             F_Typ := Etype (F);
2796
2797             --  Perform error checks for IN and IN OUT parameters
2798
2799             if Ekind (F) /= E_Out_Parameter then
2800
2801                --  Check unset reference. For scalar parameters, it is clearly
2802                --  wrong to pass an uninitialized value as either an IN or
2803                --  IN-OUT parameter. For composites, it is also clearly an
2804                --  error to pass a completely uninitialized value as an IN
2805                --  parameter, but the case of IN OUT is trickier. We prefer
2806                --  not to give a warning here. For example, suppose there is
2807                --  a routine that sets some component of a record to False.
2808                --  It is perfectly reasonable to make this IN-OUT and allow
2809                --  either initialized or uninitialized records to be passed
2810                --  in this case.
2811
2812                --  For partially initialized composite values, we also avoid
2813                --  warnings, since it is quite likely that we are passing a
2814                --  partially initialized value and only the initialized fields
2815                --  will in fact be read in the subprogram.
2816
2817                if Is_Scalar_Type (A_Typ)
2818                  or else (Ekind (F) = E_In_Parameter
2819                             and then not Is_Partially_Initialized_Type (A_Typ))
2820                then
2821                   Check_Unset_Reference (A);
2822                end if;
2823
2824                --  In Ada 83 we cannot pass an OUT parameter as an IN or IN OUT
2825                --  actual to a nested call, since this is case of reading an
2826                --  out parameter, which is not allowed.
2827
2828                if Ada_Version = Ada_83
2829                  and then Is_Entity_Name (A)
2830                  and then Ekind (Entity (A)) = E_Out_Parameter
2831                then
2832                   Error_Msg_N ("(Ada 83) illegal reading of out parameter", A);
2833                end if;
2834             end if;
2835
2836             if Ekind (F) /= E_In_Parameter
2837               and then not Is_OK_Variable_For_Out_Formal (A)
2838             then
2839                Error_Msg_NE ("actual for& must be a variable", A, F);
2840
2841                if Is_Entity_Name (A) then
2842                   Kill_Checks (Entity (A));
2843                else
2844                   Kill_All_Checks;
2845                end if;
2846             end if;
2847
2848             if Etype (A) = Any_Type then
2849                Set_Etype (N, Any_Type);
2850                return;
2851             end if;
2852
2853             --  Apply appropriate range checks for in, out, and in-out
2854             --  parameters. Out and in-out parameters also need a separate
2855             --  check, if there is a type conversion, to make sure the return
2856             --  value meets the constraints of the variable before the
2857             --  conversion.
2858
2859             --  Gigi looks at the check flag and uses the appropriate types.
2860             --  For now since one flag is used there is an optimization which
2861             --  might not be done in the In Out case since Gigi does not do
2862             --  any analysis. More thought required about this ???
2863
2864             if Ekind (F) = E_In_Parameter
2865               or else Ekind (F) = E_In_Out_Parameter
2866             then
2867                if Is_Scalar_Type (Etype (A)) then
2868                   Apply_Scalar_Range_Check (A, F_Typ);
2869
2870                elsif Is_Array_Type (Etype (A)) then
2871                   Apply_Length_Check (A, F_Typ);
2872
2873                elsif Is_Record_Type (F_Typ)
2874                  and then Has_Discriminants (F_Typ)
2875                  and then Is_Constrained (F_Typ)
2876                  and then (not Is_Derived_Type (F_Typ)
2877                              or else Comes_From_Source (Nam))
2878                then
2879                   Apply_Discriminant_Check (A, F_Typ);
2880
2881                elsif Is_Access_Type (F_Typ)
2882                  and then Is_Array_Type (Designated_Type (F_Typ))
2883                  and then Is_Constrained (Designated_Type (F_Typ))
2884                then
2885                   Apply_Length_Check (A, F_Typ);
2886
2887                elsif Is_Access_Type (F_Typ)
2888                  and then Has_Discriminants (Designated_Type (F_Typ))
2889                  and then Is_Constrained (Designated_Type (F_Typ))
2890                then
2891                   Apply_Discriminant_Check (A, F_Typ);
2892
2893                else
2894                   Apply_Range_Check (A, F_Typ);
2895                end if;
2896
2897                --  Ada 2005 (AI-231)
2898
2899                if Ada_Version >= Ada_05
2900                  and then Is_Access_Type (F_Typ)
2901                  and then Can_Never_Be_Null (F_Typ)
2902                  and then Nkind (A) = N_Null
2903                then
2904                   Apply_Compile_Time_Constraint_Error
2905                     (N      => A,
2906                      Msg    => "(Ada 2005) NULL not allowed in "
2907                                & "null-excluding formal?",
2908                      Reason => CE_Null_Not_Allowed);
2909                end if;
2910             end if;
2911
2912             if Ekind (F) = E_Out_Parameter
2913               or else Ekind (F) = E_In_Out_Parameter
2914             then
2915                if Nkind (A) = N_Type_Conversion then
2916                   if Is_Scalar_Type (A_Typ) then
2917                      Apply_Scalar_Range_Check
2918                        (Expression (A), Etype (Expression (A)), A_Typ);
2919                   else
2920                      Apply_Range_Check
2921                        (Expression (A), Etype (Expression (A)), A_Typ);
2922                   end if;
2923
2924                else
2925                   if Is_Scalar_Type (F_Typ) then
2926                      Apply_Scalar_Range_Check (A, A_Typ, F_Typ);
2927
2928                   elsif Is_Array_Type (F_Typ)
2929                     and then Ekind (F) = E_Out_Parameter
2930                   then
2931                      Apply_Length_Check (A, F_Typ);
2932
2933                   else
2934                      Apply_Range_Check (A, A_Typ, F_Typ);
2935                   end if;
2936                end if;
2937             end if;
2938
2939             --  An actual associated with an access parameter is implicitly
2940             --  converted to the anonymous access type of the formal and
2941             --  must satisfy the legality checks for access conversions.
2942
2943             if Ekind (F_Typ) = E_Anonymous_Access_Type then
2944                if not Valid_Conversion (A, F_Typ, A) then
2945                   Error_Msg_N
2946                     ("invalid implicit conversion for access parameter", A);
2947                end if;
2948             end if;
2949
2950             --  Check bad case of atomic/volatile argument (RM C.6(12))
2951
2952             if Is_By_Reference_Type (Etype (F))
2953               and then Comes_From_Source (N)
2954             then
2955                if Is_Atomic_Object (A)
2956                  and then not Is_Atomic (Etype (F))
2957                then
2958                   Error_Msg_N
2959                     ("cannot pass atomic argument to non-atomic formal",
2960                      N);
2961
2962                elsif Is_Volatile_Object (A)
2963                  and then not Is_Volatile (Etype (F))
2964                then
2965                   Error_Msg_N
2966                     ("cannot pass volatile argument to non-volatile formal",
2967                      N);
2968                end if;
2969             end if;
2970
2971             --  Check that subprograms don't have improper controlling
2972             --  arguments (RM 3.9.2 (9))
2973
2974             --  A primitive operation may have an access parameter of an
2975             --  incomplete tagged type, but a dispatching call is illegal
2976             --  if the type is still incomplete.
2977
2978             if Is_Controlling_Formal (F) then
2979                Set_Is_Controlling_Actual (A);
2980
2981                if Ekind (Etype (F)) = E_Anonymous_Access_Type then
2982                   declare
2983                      Desig : constant Entity_Id := Designated_Type (Etype (F));
2984                   begin
2985                      if Ekind (Desig) = E_Incomplete_Type
2986                        and then No (Full_View (Desig))
2987                        and then No (Non_Limited_View (Desig))
2988                      then
2989                         Error_Msg_NE
2990                           ("premature use of incomplete type& " &
2991                            "in dispatching call", A, Desig);
2992                      end if;
2993                   end;
2994                end if;
2995
2996             elsif Nkind (A) = N_Explicit_Dereference then
2997                Validate_Remote_Access_To_Class_Wide_Type (A);
2998             end if;
2999
3000             if (Is_Class_Wide_Type (A_Typ) or else Is_Dynamically_Tagged (A))
3001               and then not Is_Class_Wide_Type (F_Typ)
3002               and then not Is_Controlling_Formal (F)
3003             then
3004                Error_Msg_N ("class-wide argument not allowed here!", A);
3005
3006                if Is_Subprogram (Nam)
3007                  and then Comes_From_Source (Nam)
3008                then
3009                   Error_Msg_Node_2 := F_Typ;
3010                   Error_Msg_NE
3011                     ("& is not a dispatching operation of &!", A, Nam);
3012                end if;
3013
3014             elsif Is_Access_Type (A_Typ)
3015               and then Is_Access_Type (F_Typ)
3016               and then Ekind (F_Typ) /= E_Access_Subprogram_Type
3017               and then (Is_Class_Wide_Type (Designated_Type (A_Typ))
3018                          or else (Nkind (A) = N_Attribute_Reference
3019                                    and then
3020                                   Is_Class_Wide_Type (Etype (Prefix (A)))))
3021               and then not Is_Class_Wide_Type (Designated_Type (F_Typ))
3022               and then not Is_Controlling_Formal (F)
3023             then
3024                Error_Msg_N
3025                  ("access to class-wide argument not allowed here!", A);
3026
3027                if Is_Subprogram (Nam)
3028                  and then Comes_From_Source (Nam)
3029                then
3030                   Error_Msg_Node_2 := Designated_Type (F_Typ);
3031                   Error_Msg_NE
3032                     ("& is not a dispatching operation of &!", A, Nam);
3033                end if;
3034             end if;
3035
3036             Eval_Actual (A);
3037
3038             --  If it is a named association, treat the selector_name as
3039             --  a proper identifier, and mark the corresponding entity.
3040
3041             if Nkind (Parent (A)) = N_Parameter_Association then
3042                Set_Entity (Selector_Name (Parent (A)), F);
3043                Generate_Reference (F, Selector_Name (Parent (A)));
3044                Set_Etype (Selector_Name (Parent (A)), F_Typ);
3045                Generate_Reference (F_Typ, N, ' ');
3046             end if;
3047
3048             Prev := A;
3049
3050             if Ekind (F) /= E_Out_Parameter then
3051                Check_Unset_Reference (A);
3052             end if;
3053
3054             Next_Actual (A);
3055
3056          --  Case where actual is not present
3057
3058          else
3059             Insert_Default;
3060          end if;
3061
3062          Next_Formal (F);
3063       end loop;
3064    end Resolve_Actuals;
3065
3066    -----------------------
3067    -- Resolve_Allocator --
3068    -----------------------
3069
3070    procedure Resolve_Allocator (N : Node_Id; Typ : Entity_Id) is
3071       E        : constant Node_Id := Expression (N);
3072       Subtyp   : Entity_Id;
3073       Discrim  : Entity_Id;
3074       Constr   : Node_Id;
3075       Disc_Exp : Node_Id;
3076
3077       function In_Dispatching_Context return Boolean;
3078       --  If the allocator is an actual in a call, it is allowed to be
3079       --  class-wide when the context is not because it is a controlling
3080       --  actual.
3081
3082       ----------------------------
3083       -- In_Dispatching_Context --
3084       ----------------------------
3085
3086       function In_Dispatching_Context return Boolean is
3087          Par : constant Node_Id := Parent (N);
3088
3089       begin
3090          return (Nkind (Par) = N_Function_Call
3091                    or else Nkind (Par) = N_Procedure_Call_Statement)
3092            and then Is_Entity_Name (Name (Par))
3093            and then Is_Dispatching_Operation (Entity (Name (Par)));
3094       end In_Dispatching_Context;
3095
3096    --  Start of processing for Resolve_Allocator
3097
3098    begin
3099       --  Replace general access with specific type
3100
3101       if Ekind (Etype (N)) = E_Allocator_Type then
3102          Set_Etype (N, Base_Type (Typ));
3103       end if;
3104
3105       if Is_Abstract_Type (Typ) then
3106          Error_Msg_N ("type of allocator cannot be abstract",  N);
3107       end if;
3108
3109       --  For qualified expression, resolve the expression using the
3110       --  given subtype (nothing to do for type mark, subtype indication)
3111
3112       if Nkind (E) = N_Qualified_Expression then
3113          if Is_Class_Wide_Type (Etype (E))
3114            and then not Is_Class_Wide_Type (Designated_Type (Typ))
3115            and then not In_Dispatching_Context
3116          then
3117             Error_Msg_N
3118               ("class-wide allocator not allowed for this access type", N);
3119          end if;
3120
3121          Resolve (Expression (E), Etype (E));
3122          Check_Unset_Reference (Expression (E));
3123
3124          --  A qualified expression requires an exact match of the type,
3125          --  class-wide matching is not allowed.
3126
3127          if (Is_Class_Wide_Type (Etype (Expression (E)))
3128               or else Is_Class_Wide_Type (Etype (E)))
3129            and then Base_Type (Etype (Expression (E))) /= Base_Type (Etype (E))
3130          then
3131             Wrong_Type (Expression (E), Etype (E));
3132          end if;
3133
3134       --  For a subtype mark or subtype indication, freeze the subtype
3135
3136       else
3137          Freeze_Expression (E);
3138
3139          if Is_Access_Constant (Typ) and then not No_Initialization (N) then
3140             Error_Msg_N
3141               ("initialization required for access-to-constant allocator", N);
3142          end if;
3143
3144          --  A special accessibility check is needed for allocators that
3145          --  constrain access discriminants. The level of the type of the
3146          --  expression used to contrain an access discriminant cannot be
3147          --  deeper than the type of the allocator (in constrast to access
3148          --  parameters, where the level of the actual can be arbitrary).
3149          --  We can't use Valid_Conversion to perform this check because
3150          --  in general the type of the allocator is unrelated to the type
3151          --  of the access discriminant. Note that specialized checks are
3152          --  needed for the cases of a constraint expression which is an
3153          --  access attribute or an access discriminant.
3154
3155          if Nkind (Original_Node (E)) = N_Subtype_Indication
3156            and then Ekind (Typ) /= E_Anonymous_Access_Type
3157          then
3158             Subtyp := Entity (Subtype_Mark (Original_Node (E)));
3159
3160             if Has_Discriminants (Subtyp) then
3161                Discrim := First_Discriminant (Base_Type (Subtyp));
3162                Constr := First (Constraints (Constraint (Original_Node (E))));
3163                while Present (Discrim) and then Present (Constr) loop
3164                   if Ekind (Etype (Discrim)) = E_Anonymous_Access_Type then
3165                      if Nkind (Constr) = N_Discriminant_Association then
3166                         Disc_Exp := Original_Node (Expression (Constr));
3167                      else
3168                         Disc_Exp := Original_Node (Constr);
3169                      end if;
3170
3171                      if Type_Access_Level (Etype (Disc_Exp))
3172                        > Type_Access_Level (Typ)
3173                      then
3174                         Error_Msg_N
3175                           ("operand type has deeper level than allocator type",
3176                            Disc_Exp);
3177
3178                      elsif Nkind (Disc_Exp) = N_Attribute_Reference
3179                        and then Get_Attribute_Id (Attribute_Name (Disc_Exp))
3180                                   = Attribute_Access
3181                        and then Object_Access_Level (Prefix (Disc_Exp))
3182                                   > Type_Access_Level (Typ)
3183                      then
3184                         Error_Msg_N
3185                           ("prefix of attribute has deeper level than"
3186                               & " allocator type", Disc_Exp);
3187
3188                      --  When the operand is an access discriminant the check
3189                      --  is against the level of the prefix object.
3190
3191                      elsif Ekind (Etype (Disc_Exp)) = E_Anonymous_Access_Type
3192                        and then Nkind (Disc_Exp) = N_Selected_Component
3193                        and then Object_Access_Level (Prefix (Disc_Exp))
3194                                   > Type_Access_Level (Typ)
3195                      then
3196                         Error_Msg_N
3197                           ("access discriminant has deeper level than"
3198                               & " allocator type", Disc_Exp);
3199                      end if;
3200                   end if;
3201                   Next_Discriminant (Discrim);
3202                   Next (Constr);
3203                end loop;
3204             end if;
3205          end if;
3206       end if;
3207
3208       --  Ada 2005 (AI-344): A class-wide allocator requires an accessibility
3209       --  check that the level of the type of the created object is not deeper
3210       --  than the level of the allocator's access type, since extensions can
3211       --  now occur at deeper levels than their ancestor types. This is a
3212       --  static accessibility level check; a run-time check is also needed in
3213       --  the case of an initialized allocator with a class-wide argument (see
3214       --  Expand_Allocator_Expression).
3215
3216       if Ada_Version >= Ada_05
3217         and then Is_Class_Wide_Type (Designated_Type (Typ))
3218       then
3219          declare
3220             Exp_Typ   : Entity_Id;
3221
3222          begin
3223             if Nkind (E) = N_Qualified_Expression then
3224                Exp_Typ := Etype (E);
3225             elsif Nkind (E) = N_Subtype_Indication then
3226                Exp_Typ := Entity (Subtype_Mark (Original_Node (E)));
3227             else
3228                Exp_Typ := Entity (E);
3229             end if;
3230
3231             if Type_Access_Level (Exp_Typ) > Type_Access_Level (Typ) then
3232                if In_Instance_Body then
3233                   Error_Msg_N ("?type in allocator has deeper level than" &
3234                                " designated class-wide type", E);
3235                   Error_Msg_N ("\?Program_Error will be raised at run time",
3236                                E);
3237                   Rewrite (N,
3238                     Make_Raise_Program_Error (Sloc (N),
3239                       Reason => PE_Accessibility_Check_Failed));
3240                   Set_Etype (N, Typ);
3241
3242                --  Do not apply Ada 2005 accessibility checks on a class-wide
3243                --  allocator if the type given in the allocator is a formal
3244                --  type. A run-time check will be performed in the instance.
3245
3246                elsif not Is_Generic_Type (Exp_Typ) then
3247                   Error_Msg_N ("type in allocator has deeper level than" &
3248                                " designated class-wide type", E);
3249                end if;
3250             end if;
3251          end;
3252       end if;
3253
3254       --  Check for allocation from an empty storage pool
3255
3256       if No_Pool_Assigned (Typ) then
3257          declare
3258             Loc : constant Source_Ptr := Sloc (N);
3259          begin
3260             Error_Msg_N ("?allocation from empty storage pool", N);
3261             Error_Msg_N ("\?Storage_Error will be raised at run time", N);
3262             Insert_Action (N,
3263               Make_Raise_Storage_Error (Loc,
3264                 Reason => SE_Empty_Storage_Pool));
3265          end;
3266
3267       --  If the context is an unchecked conversion, as may happen within
3268       --  an inlined subprogram, the allocator is being resolved with its
3269       --  own anonymous type. In that case, if the target type has a specific
3270       --  storage pool, it must be inherited explicitly by the allocator type.
3271
3272       elsif Nkind (Parent (N)) = N_Unchecked_Type_Conversion
3273         and then No (Associated_Storage_Pool (Typ))
3274       then
3275          Set_Associated_Storage_Pool
3276            (Typ, Associated_Storage_Pool (Etype (Parent (N))));
3277       end if;
3278    end Resolve_Allocator;
3279
3280    ---------------------------
3281    -- Resolve_Arithmetic_Op --
3282    ---------------------------
3283
3284    --  Used for resolving all arithmetic operators except exponentiation
3285
3286    procedure Resolve_Arithmetic_Op (N : Node_Id; Typ : Entity_Id) is
3287       L   : constant Node_Id := Left_Opnd (N);
3288       R   : constant Node_Id := Right_Opnd (N);
3289       TL  : constant Entity_Id := Base_Type (Etype (L));
3290       TR  : constant Entity_Id := Base_Type (Etype (R));
3291       T   : Entity_Id;
3292       Rop : Node_Id;
3293
3294       B_Typ : constant Entity_Id := Base_Type (Typ);
3295       --  We do the resolution using the base type, because intermediate values
3296       --  in expressions always are of the base type, not a subtype of it.
3297
3298       function Expected_Type_Is_Any_Real (N : Node_Id) return Boolean;
3299       --  Returns True if N is in a context that expects "any real type"
3300
3301       function Is_Integer_Or_Universal (N : Node_Id) return Boolean;
3302       --  Return True iff given type is Integer or universal real/integer
3303
3304       procedure Set_Mixed_Mode_Operand (N : Node_Id; T : Entity_Id);
3305       --  Choose type of integer literal in fixed-point operation to conform
3306       --  to available fixed-point type. T is the type of the other operand,
3307       --  which is needed to determine the expected type of N.
3308
3309       procedure Set_Operand_Type (N : Node_Id);
3310       --  Set operand type to T if universal
3311
3312       -------------------------------
3313       -- Expected_Type_Is_Any_Real --
3314       -------------------------------
3315
3316       function Expected_Type_Is_Any_Real (N : Node_Id) return Boolean is
3317       begin
3318          --  N is the expression after "delta" in a fixed_point_definition;
3319          --  see RM-3.5.9(6):
3320
3321          return    Nkind (Parent (N)) = N_Ordinary_Fixed_Point_Definition
3322            or else Nkind (Parent (N)) = N_Decimal_Fixed_Point_Definition
3323
3324          --  N is one of the bounds in a real_range_specification;
3325          --  see RM-3.5.7(5):
3326
3327            or else Nkind (Parent (N)) = N_Real_Range_Specification
3328
3329          --  N is the expression of a delta_constraint;
3330          --  see RM-J.3(3):
3331
3332            or else Nkind (Parent (N)) = N_Delta_Constraint;
3333       end Expected_Type_Is_Any_Real;
3334
3335       -----------------------------
3336       -- Is_Integer_Or_Universal --
3337       -----------------------------
3338
3339       function Is_Integer_Or_Universal (N : Node_Id) return Boolean is
3340          T     : Entity_Id;
3341          Index : Interp_Index;
3342          It    : Interp;
3343
3344       begin
3345          if not Is_Overloaded (N) then
3346             T := Etype (N);
3347             return Base_Type (T) = Base_Type (Standard_Integer)
3348               or else T = Universal_Integer
3349               or else T = Universal_Real;
3350          else
3351             Get_First_Interp (N, Index, It);
3352             while Present (It.Typ) loop
3353                if Base_Type (It.Typ) = Base_Type (Standard_Integer)
3354                  or else It.Typ = Universal_Integer
3355                  or else It.Typ = Universal_Real
3356                then
3357                   return True;
3358                end if;
3359
3360                Get_Next_Interp (Index, It);
3361             end loop;
3362          end if;
3363
3364          return False;
3365       end Is_Integer_Or_Universal;
3366
3367       ----------------------------
3368       -- Set_Mixed_Mode_Operand --
3369       ----------------------------
3370
3371       procedure Set_Mixed_Mode_Operand (N : Node_Id; T : Entity_Id) is
3372          Index : Interp_Index;
3373          It    : Interp;
3374
3375       begin
3376          if Universal_Interpretation (N) = Universal_Integer then
3377
3378             --  A universal integer literal is resolved as standard integer
3379             --  except in the case of a fixed-point result, where we leave it
3380             --  as universal (to be handled by Exp_Fixd later on)
3381
3382             if Is_Fixed_Point_Type (T) then
3383                Resolve (N, Universal_Integer);
3384             else
3385                Resolve (N, Standard_Integer);
3386             end if;
3387
3388          elsif Universal_Interpretation (N) = Universal_Real
3389            and then (T = Base_Type (Standard_Integer)
3390                       or else T = Universal_Integer
3391                       or else T = Universal_Real)
3392          then
3393             --  A universal real can appear in a fixed-type context. We resolve
3394             --  the literal with that context, even though this might raise an
3395             --  exception prematurely (the other operand may be zero).
3396
3397             Resolve (N, B_Typ);
3398
3399          elsif Etype (N) = Base_Type (Standard_Integer)
3400            and then T = Universal_Real
3401            and then Is_Overloaded (N)
3402          then
3403             --  Integer arg in mixed-mode operation. Resolve with universal
3404             --  type, in case preference rule must be applied.
3405
3406             Resolve (N, Universal_Integer);
3407
3408          elsif Etype (N) = T
3409            and then B_Typ /= Universal_Fixed
3410          then
3411             --  Not a mixed-mode operation, resolve with context
3412
3413             Resolve (N, B_Typ);
3414
3415          elsif Etype (N) = Any_Fixed then
3416
3417             --  N may itself be a mixed-mode operation, so use context type
3418
3419             Resolve (N, B_Typ);
3420
3421          elsif Is_Fixed_Point_Type (T)
3422            and then B_Typ = Universal_Fixed
3423            and then Is_Overloaded (N)
3424          then
3425             --  Must be (fixed * fixed) operation, operand must have one
3426             --  compatible interpretation.
3427
3428             Resolve (N, Any_Fixed);
3429
3430          elsif Is_Fixed_Point_Type (B_Typ)
3431            and then (T = Universal_Real
3432                       or else Is_Fixed_Point_Type (T))
3433            and then Is_Overloaded (N)
3434          then
3435             --  C * F(X) in a fixed context, where C is a real literal or a
3436             --  fixed-point expression. F must have either a fixed type
3437             --  interpretation or an integer interpretation, but not both.
3438
3439             Get_First_Interp (N, Index, It);
3440             while Present (It.Typ) loop
3441                if Base_Type (It.Typ) = Base_Type (Standard_Integer) then
3442
3443                   if Analyzed (N) then
3444                      Error_Msg_N ("ambiguous operand in fixed operation", N);
3445                   else
3446                      Resolve (N, Standard_Integer);
3447                   end if;
3448
3449                elsif Is_Fixed_Point_Type (It.Typ) then
3450
3451                   if Analyzed (N) then
3452                      Error_Msg_N ("ambiguous operand in fixed operation", N);
3453                   else
3454                      Resolve (N, It.Typ);
3455                   end if;
3456                end if;
3457
3458                Get_Next_Interp (Index, It);
3459             end loop;
3460
3461             --  Reanalyze the literal with the fixed type of the context. If
3462             --  context is Universal_Fixed, we are within a conversion, leave
3463             --  the literal as a universal real because there is no usable
3464             --  fixed type, and the target of the conversion plays no role in
3465             --  the resolution.
3466
3467             declare
3468                Op2 : Node_Id;
3469                T2  : Entity_Id;
3470
3471             begin
3472                if N = L then
3473                   Op2 := R;
3474                else
3475                   Op2 := L;
3476                end if;
3477
3478                if B_Typ = Universal_Fixed
3479                   and then Nkind (Op2) = N_Real_Literal
3480                then
3481                   T2 := Universal_Real;
3482                else
3483                   T2 := B_Typ;
3484                end if;
3485
3486                Set_Analyzed (Op2, False);
3487                Resolve (Op2, T2);
3488             end;
3489
3490          else
3491             Resolve (N);
3492          end if;
3493       end Set_Mixed_Mode_Operand;
3494
3495       ----------------------
3496       -- Set_Operand_Type --
3497       ----------------------
3498
3499       procedure Set_Operand_Type (N : Node_Id) is
3500       begin
3501          if Etype (N) = Universal_Integer
3502            or else Etype (N) = Universal_Real
3503          then
3504             Set_Etype (N, T);
3505          end if;
3506       end Set_Operand_Type;
3507
3508    --  Start of processing for Resolve_Arithmetic_Op
3509
3510    begin
3511       if Comes_From_Source (N)
3512         and then Ekind (Entity (N)) = E_Function
3513         and then Is_Imported (Entity (N))
3514         and then Is_Intrinsic_Subprogram (Entity (N))
3515       then
3516          Resolve_Intrinsic_Operator (N, Typ);
3517          return;
3518
3519       --  Special-case for mixed-mode universal expressions or fixed point
3520       --  type operation: each argument is resolved separately. The same
3521       --  treatment is required if one of the operands of a fixed point
3522       --  operation is universal real, since in this case we don't do a
3523       --  conversion to a specific fixed-point type (instead the expander
3524       --  takes care of the case).
3525
3526       elsif (B_Typ = Universal_Integer
3527            or else B_Typ = Universal_Real)
3528         and then Present (Universal_Interpretation (L))
3529         and then Present (Universal_Interpretation (R))
3530       then
3531          Resolve (L, Universal_Interpretation (L));
3532          Resolve (R, Universal_Interpretation (R));
3533          Set_Etype (N, B_Typ);
3534
3535       elsif (B_Typ = Universal_Real
3536            or else Etype (N) = Universal_Fixed
3537            or else (Etype (N) = Any_Fixed
3538                      and then Is_Fixed_Point_Type (B_Typ))
3539            or else (Is_Fixed_Point_Type (B_Typ)
3540                      and then (Is_Integer_Or_Universal (L)
3541                                  or else
3542                                Is_Integer_Or_Universal (R))))
3543         and then (Nkind (N) = N_Op_Multiply or else
3544                   Nkind (N) = N_Op_Divide)
3545       then
3546          if TL = Universal_Integer or else TR = Universal_Integer then
3547             Check_For_Visible_Operator (N, B_Typ);
3548          end if;
3549
3550          --  If context is a fixed type and one operand is integer, the
3551          --  other is resolved with the type of the context.
3552
3553          if Is_Fixed_Point_Type (B_Typ)
3554            and then (Base_Type (TL) = Base_Type (Standard_Integer)
3555                       or else TL = Universal_Integer)
3556          then
3557             Resolve (R, B_Typ);
3558             Resolve (L, TL);
3559
3560          elsif Is_Fixed_Point_Type (B_Typ)
3561            and then (Base_Type (TR) = Base_Type (Standard_Integer)
3562                       or else TR = Universal_Integer)
3563          then
3564             Resolve (L, B_Typ);
3565             Resolve (R, TR);
3566
3567          else
3568             Set_Mixed_Mode_Operand (L, TR);
3569             Set_Mixed_Mode_Operand (R, TL);
3570          end if;
3571
3572          --  Check the rule in RM05-4.5.5(19.1/2) disallowing the
3573          --  universal_fixed multiplying operators from being used when the
3574          --  expected type is also universal_fixed. Note that B_Typ will be
3575          --  Universal_Fixed in some cases where the expected type is actually
3576          --  Any_Real; Expected_Type_Is_Any_Real takes care of that case.
3577
3578          if Etype (N) = Universal_Fixed
3579            or else Etype (N) = Any_Fixed
3580          then
3581             if B_Typ = Universal_Fixed
3582               and then not Expected_Type_Is_Any_Real (N)
3583               and then Nkind (Parent (N)) /= N_Type_Conversion
3584               and then Nkind (Parent (N)) /= N_Unchecked_Type_Conversion
3585             then
3586                Error_Msg_N
3587                  ("type cannot be determined from context!", N);
3588                Error_Msg_N
3589                  ("\explicit conversion to result type required", N);
3590
3591                Set_Etype (L, Any_Type);
3592                Set_Etype (R, Any_Type);
3593
3594             else
3595                if Ada_Version = Ada_83
3596                   and then Etype (N) = Universal_Fixed
3597                   and then Nkind (Parent (N)) /= N_Type_Conversion
3598                   and then Nkind (Parent (N)) /= N_Unchecked_Type_Conversion
3599                then
3600                   Error_Msg_N
3601                     ("(Ada 83) fixed-point operation " &
3602                      "needs explicit conversion",
3603                      N);
3604                end if;
3605
3606                --  The expected type is "any real type" in contexts like
3607                --    type T is delta <universal_fixed-expression> ...
3608                --  in which case we need to set the type to Universal_Real
3609                --  so that static expression evaluation will work properly.
3610
3611                if Expected_Type_Is_Any_Real (N) then
3612                   Set_Etype (N, Universal_Real);
3613                else
3614                   Set_Etype (N, B_Typ);
3615                end if;
3616             end if;
3617
3618          elsif Is_Fixed_Point_Type (B_Typ)
3619            and then (Is_Integer_Or_Universal (L)
3620                        or else Nkind (L) = N_Real_Literal
3621                        or else Nkind (R) = N_Real_Literal
3622                        or else
3623                      Is_Integer_Or_Universal (R))
3624          then
3625             Set_Etype (N, B_Typ);
3626
3627          elsif Etype (N) = Any_Fixed then
3628
3629             --  If no previous errors, this is only possible if one operand
3630             --  is overloaded and the context is universal. Resolve as such.
3631
3632             Set_Etype (N, B_Typ);
3633          end if;
3634
3635       else
3636          if (TL = Universal_Integer or else TL = Universal_Real)
3637            and then (TR = Universal_Integer or else TR = Universal_Real)
3638          then
3639             Check_For_Visible_Operator (N, B_Typ);
3640          end if;
3641
3642          --  If the context is Universal_Fixed and the operands are also
3643          --  universal fixed, this is an error, unless there is only one
3644          --  applicable fixed_point type (usually duration).
3645
3646          if B_Typ = Universal_Fixed
3647            and then Etype (L) = Universal_Fixed
3648          then
3649             T := Unique_Fixed_Point_Type (N);
3650
3651             if T  = Any_Type then
3652                Set_Etype (N, T);
3653                return;
3654             else
3655                Resolve (L, T);
3656                Resolve (R, T);
3657             end if;
3658
3659          else
3660             Resolve (L, B_Typ);
3661             Resolve (R, B_Typ);
3662          end if;
3663
3664          --  If one of the arguments was resolved to a non-universal type.
3665          --  label the result of the operation itself with the same type.
3666          --  Do the same for the universal argument, if any.
3667
3668          T := Intersect_Types (L, R);
3669          Set_Etype (N, Base_Type (T));
3670          Set_Operand_Type (L);
3671          Set_Operand_Type (R);
3672       end if;
3673
3674       Generate_Operator_Reference (N, Typ);
3675       Eval_Arithmetic_Op (N);
3676
3677       --  Set overflow and division checking bit. Much cleverer code needed
3678       --  here eventually and perhaps the Resolve routines should be separated
3679       --  for the various arithmetic operations, since they will need
3680       --  different processing. ???
3681
3682       if Nkind (N) in N_Op then
3683          if not Overflow_Checks_Suppressed (Etype (N)) then
3684             Enable_Overflow_Check (N);
3685          end if;
3686
3687          --  Give warning if explicit division by zero
3688
3689          if (Nkind (N) = N_Op_Divide
3690              or else Nkind (N) = N_Op_Rem
3691              or else Nkind (N) = N_Op_Mod)
3692            and then not Division_Checks_Suppressed (Etype (N))
3693          then
3694             Rop := Right_Opnd (N);
3695
3696             if Compile_Time_Known_Value (Rop)
3697               and then ((Is_Integer_Type (Etype (Rop))
3698                                 and then Expr_Value (Rop) = Uint_0)
3699                           or else
3700                         (Is_Real_Type (Etype (Rop))
3701                                 and then Expr_Value_R (Rop) = Ureal_0))
3702             then
3703                --  Specialize the warning message according to the operation
3704
3705                case Nkind (N) is
3706                   when N_Op_Divide =>
3707                      Apply_Compile_Time_Constraint_Error
3708                        (N, "division by zero?", CE_Divide_By_Zero,
3709                         Loc => Sloc (Right_Opnd (N)));
3710
3711                   when N_Op_Rem =>
3712                      Apply_Compile_Time_Constraint_Error
3713                        (N, "rem with zero divisor?", CE_Divide_By_Zero,
3714                         Loc => Sloc (Right_Opnd (N)));
3715
3716                   when N_Op_Mod =>
3717                      Apply_Compile_Time_Constraint_Error
3718                        (N, "mod with zero divisor?", CE_Divide_By_Zero,
3719                         Loc => Sloc (Right_Opnd (N)));
3720
3721                   --  Division by zero can only happen with division, rem,
3722                   --  and mod operations.
3723
3724                   when others =>
3725                      raise Program_Error;
3726                end case;
3727
3728             --  Otherwise just set the flag to check at run time
3729
3730             else
3731                Set_Do_Division_Check (N);
3732             end if;
3733          end if;
3734       end if;
3735
3736       Check_Unset_Reference (L);
3737       Check_Unset_Reference (R);
3738    end Resolve_Arithmetic_Op;
3739
3740    ------------------
3741    -- Resolve_Call --
3742    ------------------
3743
3744    procedure Resolve_Call (N : Node_Id; Typ : Entity_Id) is
3745       Loc     : constant Source_Ptr := Sloc (N);
3746       Subp    : constant Node_Id    := Name (N);
3747       Nam     : Entity_Id;
3748       I       : Interp_Index;
3749       It      : Interp;
3750       Norm_OK : Boolean;
3751       Scop    : Entity_Id;
3752       Rtype   : Entity_Id;
3753
3754    begin
3755       --  The context imposes a unique interpretation with type Typ on a
3756       --  procedure or function call. Find the entity of the subprogram that
3757       --  yields the expected type, and propagate the corresponding formal
3758       --  constraints on the actuals. The caller has established that an
3759       --  interpretation exists, and emitted an error if not unique.
3760
3761       --  First deal with the case of a call to an access-to-subprogram,
3762       --  dereference made explicit in Analyze_Call.
3763
3764       if Ekind (Etype (Subp)) = E_Subprogram_Type then
3765          if not Is_Overloaded (Subp) then
3766             Nam := Etype (Subp);
3767
3768          else
3769             --  Find the interpretation whose type (a subprogram type) has a
3770             --  return type that is compatible with the context. Analysis of
3771             --  the node has established that one exists.
3772
3773             Nam := Empty;
3774
3775             Get_First_Interp (Subp,  I, It);
3776             while Present (It.Typ) loop
3777                if Covers (Typ, Etype (It.Typ)) then
3778                   Nam := It.Typ;
3779                   exit;
3780                end if;
3781
3782                Get_Next_Interp (I, It);
3783             end loop;
3784
3785             if No (Nam) then
3786                raise Program_Error;
3787             end if;
3788          end if;
3789
3790          --  If the prefix is not an entity, then resolve it
3791
3792          if not Is_Entity_Name (Subp) then
3793             Resolve (Subp, Nam);
3794          end if;
3795
3796          --  For an indirect call, we always invalidate checks, since we do not
3797          --  know whether the subprogram is local or global. Yes we could do
3798          --  better here, e.g. by knowing that there are no local subprograms,
3799          --  but it does not seem worth the effort. Similarly, we kill all
3800          --  knowledge of current constant values.
3801
3802          Kill_Current_Values;
3803
3804       --  If this is a procedure call which is really an entry call, do the
3805       --  conversion of the procedure call to an entry call. Protected
3806       --  operations use the same circuitry because the name in the call can be
3807       --  an arbitrary expression with special resolution rules.
3808
3809       elsif Nkind (Subp) = N_Selected_Component
3810         or else Nkind (Subp) = N_Indexed_Component
3811         or else (Is_Entity_Name (Subp)
3812                   and then Ekind (Entity (Subp)) = E_Entry)
3813       then
3814          Resolve_Entry_Call (N, Typ);
3815          Check_Elab_Call (N);
3816
3817          --  Kill checks and constant values, as above for indirect case
3818          --  Who knows what happens when another task is activated?
3819
3820          Kill_Current_Values;
3821          return;
3822
3823       --  Normal subprogram call with name established in Resolve
3824
3825       elsif not (Is_Type (Entity (Subp))) then
3826          Nam := Entity (Subp);
3827          Set_Entity_With_Style_Check (Subp, Nam);
3828          Generate_Reference (Nam, Subp);
3829
3830       --  Otherwise we must have the case of an overloaded call
3831
3832       else
3833          pragma Assert (Is_Overloaded (Subp));
3834          Nam := Empty;  --  We know that it will be assigned in loop below
3835
3836          Get_First_Interp (Subp,  I, It);
3837          while Present (It.Typ) loop
3838             if Covers (Typ, It.Typ) then
3839                Nam := It.Nam;
3840                Set_Entity_With_Style_Check (Subp, Nam);
3841                Generate_Reference (Nam, Subp);
3842                exit;
3843             end if;
3844
3845             Get_Next_Interp (I, It);
3846          end loop;
3847       end if;
3848
3849       --  Check that a call to Current_Task does not occur in an entry body
3850
3851       if Is_RTE (Nam, RE_Current_Task) then
3852          declare
3853             P : Node_Id;
3854
3855          begin
3856             P := N;
3857             loop
3858                P := Parent (P);
3859                exit when No (P);
3860
3861                if Nkind (P) = N_Entry_Body
3862                  or else (Nkind (P) = N_Subprogram_Body
3863                             and then Is_Entry_Barrier_Function (P))
3864                then
3865                   Rtype := Etype (N);
3866                   Error_Msg_NE
3867                     ("& should not be used in entry body ('R'M C.7(17))?",
3868                      N, Nam);
3869                   Error_Msg_NE
3870                     ("\Program_Error will be raised at run time?", N, Nam);
3871                   Rewrite (N,
3872                     Make_Raise_Program_Error (Loc,
3873                       Reason => PE_Current_Task_In_Entry_Body));
3874                   Set_Etype (N, Rtype);
3875                   exit;
3876                end if;
3877             end loop;
3878          end;
3879       end if;
3880
3881       --  Cannot call thread body directly
3882
3883       if Is_Thread_Body (Nam) then
3884          Error_Msg_N ("cannot call thread body directly", N);
3885       end if;
3886
3887       --  Check that a procedure call does not occur in the context of the
3888       --  entry call statement of a conditional or timed entry call. Note that
3889       --  the case of a call to a subprogram renaming of an entry will also be
3890       --  rejected. The test for N not being an N_Entry_Call_Statement is
3891       --  defensive, covering the possibility that the processing of entry
3892       --  calls might reach this point due to later modifications of the code
3893       --  above.
3894
3895       if Nkind (Parent (N)) = N_Entry_Call_Alternative
3896         and then Nkind (N) /= N_Entry_Call_Statement
3897         and then Entry_Call_Statement (Parent (N)) = N
3898       then
3899          if Ada_Version < Ada_05 then
3900             Error_Msg_N ("entry call required in select statement", N);
3901
3902          --  Ada 2005 (AI-345): If a procedure_call_statement is used
3903          --  for a procedure_or_entry_call, the procedure_name or pro-
3904          --  cedure_prefix of the procedure_call_statement shall denote
3905          --  an entry renamed by a procedure, or (a view of) a primitive
3906          --  subprogram of a limited interface whose first parameter is
3907          --  a controlling parameter.
3908
3909          elsif Nkind (N) = N_Procedure_Call_Statement
3910            and then not Is_Renamed_Entry (Nam)
3911            and then not Is_Controlling_Limited_Procedure (Nam)
3912          then
3913             Error_Msg_N
3914              ("entry call or dispatching primitive of interface required", N);
3915          end if;
3916       end if;
3917
3918       --  Check that this is not a call to a protected procedure or
3919       --  entry from within a protected function.
3920
3921       if Ekind (Current_Scope) = E_Function
3922         and then Ekind (Scope (Current_Scope)) = E_Protected_Type
3923         and then Ekind (Nam) /= E_Function
3924         and then Scope (Nam) = Scope (Current_Scope)
3925       then
3926          Error_Msg_N ("within protected function, protected " &
3927            "object is constant", N);
3928          Error_Msg_N ("\cannot call operation that may modify it", N);
3929       end if;
3930
3931       --  Freeze the subprogram name if not in default expression. Note that we
3932       --  freeze procedure calls as well as function calls. Procedure calls are
3933       --  not frozen according to the rules (RM 13.14(14)) because it is
3934       --  impossible to have a procedure call to a non-frozen procedure in pure
3935       --  Ada, but in the code that we generate in the expander, this rule
3936       --  needs extending because we can generate procedure calls that need
3937       --  freezing.
3938
3939       if Is_Entity_Name (Subp) and then not In_Default_Expression then
3940          Freeze_Expression (Subp);
3941       end if;
3942
3943       --  For a predefined operator, the type of the result is the type imposed
3944       --  by context, except for a predefined operation on universal fixed.
3945       --  Otherwise The type of the call is the type returned by the subprogram
3946       --  being called.
3947
3948       if Is_Predefined_Op (Nam) then
3949          if Etype (N) /= Universal_Fixed then
3950             Set_Etype (N, Typ);
3951          end if;
3952
3953       --  If the subprogram returns an array type, and the context requires the
3954       --  component type of that array type, the node is really an indexing of
3955       --  the parameterless call. Resolve as such. A pathological case occurs
3956       --  when the type of the component is an access to the array type. In
3957       --  this case the call is truly ambiguous.
3958
3959       elsif (Needs_No_Actuals (Nam) or else Needs_One_Actual (Nam))
3960         and then
3961           ((Is_Array_Type (Etype (Nam))
3962                    and then Covers (Typ, Component_Type (Etype (Nam))))
3963              or else (Is_Access_Type (Etype (Nam))
3964                         and then Is_Array_Type (Designated_Type (Etype (Nam)))
3965                         and then
3966                           Covers (Typ,
3967                             Component_Type (Designated_Type (Etype (Nam))))))
3968       then
3969          declare
3970             Index_Node : Node_Id;
3971             New_Subp   : Node_Id;
3972             Ret_Type   : constant Entity_Id := Etype (Nam);
3973
3974          begin
3975             if Is_Access_Type (Ret_Type)
3976               and then Ret_Type = Component_Type (Designated_Type (Ret_Type))
3977             then
3978                Error_Msg_N
3979                  ("cannot disambiguate function call and indexing", N);
3980             else
3981                New_Subp := Relocate_Node (Subp);
3982                Set_Entity (Subp, Nam);
3983
3984                if Component_Type (Ret_Type) /= Any_Type then
3985                   if Needs_No_Actuals (Nam) then
3986
3987                      --  Indexed call to a parameterless function
3988
3989                      Index_Node :=
3990                        Make_Indexed_Component (Loc,
3991                          Prefix =>
3992                            Make_Function_Call (Loc,
3993                              Name => New_Subp),
3994                          Expressions => Parameter_Associations (N));
3995                   else
3996                      --  An Ada 2005 prefixed call to a primitive operation
3997                      --  whose first parameter is the prefix. This prefix was
3998                      --  prepended to the parameter list, which is actually a
3999                      --  list of indices. Remove the prefix in order to build
4000                      --  the proper indexed component.
4001
4002                      Index_Node :=
4003                         Make_Indexed_Component (Loc,
4004                           Prefix =>
4005                             Make_Function_Call (Loc,
4006                                Name => New_Subp,
4007                                Parameter_Associations =>
4008                                  New_List
4009                                    (Remove_Head (Parameter_Associations (N)))),
4010                            Expressions => Parameter_Associations (N));
4011                   end if;
4012
4013                   --  Since we are correcting a node classification error made
4014                   --  by the parser, we call Replace rather than Rewrite.
4015
4016                   Replace (N, Index_Node);
4017                   Set_Etype (Prefix (N), Ret_Type);
4018                   Set_Etype (N, Typ);
4019                   Resolve_Indexed_Component (N, Typ);
4020                   Check_Elab_Call (Prefix (N));
4021                end if;
4022             end if;
4023
4024             return;
4025          end;
4026
4027       else
4028          Set_Etype (N, Etype (Nam));
4029       end if;
4030
4031       --  In the case where the call is to an overloaded subprogram, Analyze
4032       --  calls Normalize_Actuals once per overloaded subprogram. Therefore in
4033       --  such a case Normalize_Actuals needs to be called once more to order
4034       --  the actuals correctly. Otherwise the call will have the ordering
4035       --  given by the last overloaded subprogram whether this is the correct
4036       --  one being called or not.
4037
4038       if Is_Overloaded (Subp) then
4039          Normalize_Actuals (N, Nam, False, Norm_OK);
4040          pragma Assert (Norm_OK);
4041       end if;
4042
4043       --  In any case, call is fully resolved now. Reset Overload flag, to
4044       --  prevent subsequent overload resolution if node is analyzed again
4045
4046       Set_Is_Overloaded (Subp, False);
4047       Set_Is_Overloaded (N, False);
4048
4049       --  If we are calling the current subprogram from immediately within its
4050       --  body, then that is the case where we can sometimes detect cases of
4051       --  infinite recursion statically. Do not try this in case restriction
4052       --  No_Recursion is in effect anyway.
4053
4054       Scop := Current_Scope;
4055
4056       if Nam = Scop
4057         and then not Restriction_Active (No_Recursion)
4058         and then Check_Infinite_Recursion (N)
4059       then
4060          --  Here we detected and flagged an infinite recursion, so we do
4061          --  not need to test the case below for further warnings.
4062
4063          null;
4064
4065       --  If call is to immediately containing subprogram, then check for
4066       --  the case of a possible run-time detectable infinite recursion.
4067
4068       else
4069          Scope_Loop : while Scop /= Standard_Standard loop
4070             if Nam = Scop then
4071
4072                --  Although in general recursion is not statically checkable,
4073                --  the case of calling an immediately containing subprogram
4074                --  is easy to catch.
4075
4076                Check_Restriction (No_Recursion, N);
4077
4078                --  If the recursive call is to a parameterless subprogram, then
4079                --  even if we can't statically detect infinite recursion, this
4080                --  is pretty suspicious, and we output a warning. Furthermore,
4081                --  we will try later to detect some cases here at run time by
4082                --  expanding checking code (see Detect_Infinite_Recursion in
4083                --  package Exp_Ch6).
4084
4085                --  If the recursive call is within a handler we do not emit a
4086                --  warning, because this is a common idiom: loop until input
4087                --  is correct, catch illegal input in handler and restart.
4088
4089                if No (First_Formal (Nam))
4090                  and then Etype (Nam) = Standard_Void_Type
4091                  and then not Error_Posted (N)
4092                  and then Nkind (Parent (N)) /= N_Exception_Handler
4093                then
4094                   --  For the case of a procedure call. We give the message
4095                   --  only if the call is the first statement in a sequence of
4096                   --  statements, or if all previous statements are simple
4097                   --  assignments. This is simply a heuristic to decrease false
4098                   --  positives, without losing too many good warnings. The
4099                   --  idea is that these previous statements may affect global
4100                   --  variables the procedure depends on.
4101
4102                   if Nkind (N) = N_Procedure_Call_Statement
4103                     and then Is_List_Member (N)
4104                   then
4105                      declare
4106                         P : Node_Id;
4107                      begin
4108                         P := Prev (N);
4109                         while Present (P) loop
4110                            if Nkind (P) /= N_Assignment_Statement then
4111                               exit Scope_Loop;
4112                            end if;
4113
4114                            Prev (P);
4115                         end loop;
4116                      end;
4117                   end if;
4118
4119                   --  Do not give warning if we are in a conditional context
4120
4121                   declare
4122                      K : constant Node_Kind := Nkind (Parent (N));
4123                   begin
4124                      if (K = N_Loop_Statement
4125                           and then Present (Iteration_Scheme (Parent (N))))
4126                        or else K = N_If_Statement
4127                        or else K = N_Elsif_Part
4128                        or else K = N_Case_Statement_Alternative
4129                      then
4130                         exit Scope_Loop;
4131                      end if;
4132                   end;
4133
4134                   --  Here warning is to be issued
4135
4136                   Set_Has_Recursive_Call (Nam);
4137                   Error_Msg_N ("possible infinite recursion?", N);
4138                   Error_Msg_N ("\Storage_Error may be raised at run time?", N);
4139                end if;
4140
4141                exit Scope_Loop;
4142             end if;
4143
4144             Scop := Scope (Scop);
4145          end loop Scope_Loop;
4146       end if;
4147
4148       --  If subprogram name is a predefined operator, it was given in
4149       --  functional notation. Replace call node with operator node, so
4150       --  that actuals can be resolved appropriately.
4151
4152       if Is_Predefined_Op (Nam) or else Ekind (Nam) = E_Operator then
4153          Make_Call_Into_Operator (N, Typ, Entity (Name (N)));
4154          return;
4155
4156       elsif Present (Alias (Nam))
4157         and then Is_Predefined_Op (Alias (Nam))
4158       then
4159          Resolve_Actuals (N, Nam);
4160          Make_Call_Into_Operator (N, Typ, Alias (Nam));
4161          return;
4162       end if;
4163
4164       --  Create a transient scope if the resulting type requires it
4165
4166       --  There are 4 notable exceptions: in init procs, the transient scope
4167       --  overhead is not needed and even incorrect due to the actual expansion
4168       --  of adjust calls; the second case is enumeration literal pseudo calls;
4169       --  the third case is intrinsic subprograms (Unchecked_Conversion and
4170       --  source information functions) that do not use the secondary stack
4171       --  even though the return type is unconstrained; the fourth case is a
4172       --  call to a build-in-place function, since such functions may allocate
4173       --  their result directly in a target object, and cases where the result
4174       --  does get allocated in the secondary stack are checked for within the
4175       --  specialized Exp_Ch6 procedures for expanding build-in-place calls.
4176
4177       --  If this is an initialization call for a type whose initialization
4178       --  uses the secondary stack, we also need to create a transient scope
4179       --  for it, precisely because we will not do it within the init proc
4180       --  itself.
4181
4182       --  If the subprogram is marked Inlined_Always, then even if it returns
4183       --  an unconstrained type the call does not require use of the secondary
4184       --  stack.
4185
4186       if Is_Inlined (Nam)
4187         and then Present (First_Rep_Item (Nam))
4188         and then Nkind (First_Rep_Item (Nam)) = N_Pragma
4189         and then Chars (First_Rep_Item (Nam)) = Name_Inline_Always
4190       then
4191          null;
4192
4193       elsif Expander_Active
4194         and then Is_Type (Etype (Nam))
4195         and then Requires_Transient_Scope (Etype (Nam))
4196         and then not Is_Build_In_Place_Function (Nam)
4197         and then Ekind (Nam) /= E_Enumeration_Literal
4198         and then not Within_Init_Proc
4199         and then not Is_Intrinsic_Subprogram (Nam)
4200       then
4201          Establish_Transient_Scope (N, Sec_Stack => True);
4202
4203          --  If the call appears within the bounds of a loop, it will
4204          --  be rewritten and reanalyzed, nothing left to do here.
4205
4206          if Nkind (N) /= N_Function_Call then
4207             return;
4208          end if;
4209
4210       elsif Is_Init_Proc (Nam)
4211         and then not Within_Init_Proc
4212       then
4213          Check_Initialization_Call (N, Nam);
4214       end if;
4215
4216       --  A protected function cannot be called within the definition of the
4217       --  enclosing protected type.
4218
4219       if Is_Protected_Type (Scope (Nam))
4220         and then In_Open_Scopes (Scope (Nam))
4221         and then not Has_Completion (Scope (Nam))
4222       then
4223          Error_Msg_NE
4224            ("& cannot be called before end of protected definition", N, Nam);
4225       end if;
4226
4227       --  Propagate interpretation to actuals, and add default expressions
4228       --  where needed.
4229
4230       if Present (First_Formal (Nam)) then
4231          Resolve_Actuals (N, Nam);
4232
4233          --  Overloaded literals are rewritten as function calls, for
4234          --  purpose of resolution. After resolution, we can replace
4235          --  the call with the literal itself.
4236
4237       elsif Ekind (Nam) = E_Enumeration_Literal then
4238          Copy_Node (Subp, N);
4239          Resolve_Entity_Name (N, Typ);
4240
4241          --  Avoid validation, since it is a static function call
4242
4243          return;
4244       end if;
4245
4246       --  If the subprogram is not global, then kill all checks. This is a bit
4247       --  conservative, since in many cases we could do better, but it is not
4248       --  worth the effort. Similarly, we kill constant values. However we do
4249       --  not need to do this for internal entities (unless they are inherited
4250       --  user-defined subprograms), since they are not in the business of
4251       --  molesting global values.
4252
4253       --  Note: we do not do this step till after resolving the actuals. That
4254       --  way we still take advantage of the current value information while
4255       --  scanning the actuals.
4256
4257       if not Is_Library_Level_Entity (Nam)
4258         and then (Comes_From_Source (Nam)
4259                    or else (Present (Alias (Nam))
4260                              and then Comes_From_Source (Alias (Nam))))
4261       then
4262          Kill_Current_Values;
4263       end if;
4264
4265       --  If the subprogram is a primitive operation, check whether or not
4266       --  it is a correct dispatching call.
4267
4268       if Is_Overloadable (Nam)
4269         and then Is_Dispatching_Operation (Nam)
4270       then
4271          Check_Dispatching_Call (N);
4272
4273       elsif Ekind (Nam) /= E_Subprogram_Type
4274         and then Is_Abstract_Subprogram (Nam)
4275         and then not In_Instance
4276       then
4277          Error_Msg_NE ("cannot call abstract subprogram &!", N, Nam);
4278       end if;
4279
4280       if Is_Intrinsic_Subprogram (Nam) then
4281          Check_Intrinsic_Call (N);
4282       end if;
4283
4284       Eval_Call (N);
4285       Check_Elab_Call (N);
4286    end Resolve_Call;
4287
4288    -------------------------------
4289    -- Resolve_Character_Literal --
4290    -------------------------------
4291
4292    procedure Resolve_Character_Literal (N : Node_Id; Typ : Entity_Id) is
4293       B_Typ : constant Entity_Id := Base_Type (Typ);
4294       C     : Entity_Id;
4295
4296    begin
4297       --  Verify that the character does belong to the type of the context
4298
4299       Set_Etype (N, B_Typ);
4300       Eval_Character_Literal (N);
4301
4302       --  Wide_Wide_Character literals must always be defined, since the set
4303       --  of wide wide character literals is complete, i.e. if a character
4304       --  literal is accepted by the parser, then it is OK for wide wide
4305       --  character (out of range character literals are rejected).
4306
4307       if Root_Type (B_Typ) = Standard_Wide_Wide_Character then
4308          return;
4309
4310       --  Always accept character literal for type Any_Character, which
4311       --  occurs in error situations and in comparisons of literals, both
4312       --  of which should accept all literals.
4313
4314       elsif B_Typ = Any_Character then
4315          return;
4316
4317       --  For Standard.Character or a type derived from it, check that
4318       --  the literal is in range
4319
4320       elsif Root_Type (B_Typ) = Standard_Character then
4321          if In_Character_Range (UI_To_CC (Char_Literal_Value (N))) then
4322             return;
4323          end if;
4324
4325       --  For Standard.Wide_Character or a type derived from it, check
4326       --  that the literal is in range
4327
4328       elsif Root_Type (B_Typ) = Standard_Wide_Character then
4329          if In_Wide_Character_Range (UI_To_CC (Char_Literal_Value (N))) then
4330             return;
4331          end if;
4332
4333       --  For Standard.Wide_Wide_Character or a type derived from it, we
4334       --  know the literal is in range, since the parser checked!
4335
4336       elsif Root_Type (B_Typ) = Standard_Wide_Wide_Character then
4337          return;
4338
4339       --  If the entity is already set, this has already been resolved in
4340       --  a generic context, or comes from expansion. Nothing else to do.
4341
4342       elsif Present (Entity (N)) then
4343          return;
4344
4345       --  Otherwise we have a user defined character type, and we can use
4346       --  the standard visibility mechanisms to locate the referenced entity
4347
4348       else
4349          C := Current_Entity (N);
4350          while Present (C) loop
4351             if Etype (C) = B_Typ then
4352                Set_Entity_With_Style_Check (N, C);
4353                Generate_Reference (C, N);
4354                return;
4355             end if;
4356
4357             C := Homonym (C);
4358          end loop;
4359       end if;
4360
4361       --  If we fall through, then the literal does not match any of the
4362       --  entries of the enumeration type. This isn't just a constraint
4363       --  error situation, it is an illegality (see RM 4.2).
4364
4365       Error_Msg_NE
4366         ("character not defined for }", N, First_Subtype (B_Typ));
4367    end Resolve_Character_Literal;
4368
4369    ---------------------------
4370    -- Resolve_Comparison_Op --
4371    ---------------------------
4372
4373    --  Context requires a boolean type, and plays no role in resolution.
4374    --  Processing identical to that for equality operators. The result
4375    --  type is the base type, which matters when pathological subtypes of
4376    --  booleans with limited ranges are used.
4377
4378    procedure Resolve_Comparison_Op (N : Node_Id; Typ : Entity_Id) is
4379       L : constant Node_Id := Left_Opnd (N);
4380       R : constant Node_Id := Right_Opnd (N);
4381       T : Entity_Id;
4382
4383    begin
4384       --  If this is an intrinsic operation which is not predefined, use
4385       --  the types of its declared arguments to resolve the possibly
4386       --  overloaded operands. Otherwise the operands are unambiguous and
4387       --  specify the expected type.
4388
4389       if Scope (Entity (N)) /= Standard_Standard then
4390          T := Etype (First_Entity (Entity (N)));
4391
4392       else
4393          T := Find_Unique_Type (L, R);
4394
4395          if T = Any_Fixed then
4396             T := Unique_Fixed_Point_Type (L);
4397          end if;
4398       end if;
4399
4400       Set_Etype (N, Base_Type (Typ));
4401       Generate_Reference (T, N, ' ');
4402
4403       if T /= Any_Type then
4404          if T = Any_String
4405            or else T = Any_Composite
4406            or else T = Any_Character
4407          then
4408             if T = Any_Character then
4409                Ambiguous_Character (L);
4410             else
4411                Error_Msg_N ("ambiguous operands for comparison", N);
4412             end if;
4413
4414             Set_Etype (N, Any_Type);
4415             return;
4416
4417          else
4418             Resolve (L, T);
4419             Resolve (R, T);
4420             Check_Unset_Reference (L);
4421             Check_Unset_Reference (R);
4422             Generate_Operator_Reference (N, T);
4423             Eval_Relational_Op (N);
4424          end if;
4425       end if;
4426    end Resolve_Comparison_Op;
4427
4428    ------------------------------------
4429    -- Resolve_Conditional_Expression --
4430    ------------------------------------
4431
4432    procedure Resolve_Conditional_Expression (N : Node_Id; Typ : Entity_Id) is
4433       Condition : constant Node_Id := First (Expressions (N));
4434       Then_Expr : constant Node_Id := Next (Condition);
4435       Else_Expr : constant Node_Id := Next (Then_Expr);
4436
4437    begin
4438       Resolve (Condition, Standard_Boolean);
4439       Resolve (Then_Expr, Typ);
4440       Resolve (Else_Expr, Typ);
4441
4442       Set_Etype (N, Typ);
4443       Eval_Conditional_Expression (N);
4444    end Resolve_Conditional_Expression;
4445
4446    -----------------------------------------
4447    -- Resolve_Discrete_Subtype_Indication --
4448    -----------------------------------------
4449
4450    procedure Resolve_Discrete_Subtype_Indication
4451      (N   : Node_Id;
4452       Typ : Entity_Id)
4453    is
4454       R : Node_Id;
4455       S : Entity_Id;
4456
4457    begin
4458       Analyze (Subtype_Mark (N));
4459       S := Entity (Subtype_Mark (N));
4460
4461       if Nkind (Constraint (N)) /= N_Range_Constraint then
4462          Error_Msg_N ("expect range constraint for discrete type", N);
4463          Set_Etype (N, Any_Type);
4464
4465       else
4466          R := Range_Expression (Constraint (N));
4467
4468          if R = Error then
4469             return;
4470          end if;
4471
4472          Analyze (R);
4473
4474          if Base_Type (S) /= Base_Type (Typ) then
4475             Error_Msg_NE
4476               ("expect subtype of }", N, First_Subtype (Typ));
4477
4478             --  Rewrite the constraint as a range of Typ
4479             --  to allow compilation to proceed further.
4480
4481             Set_Etype (N, Typ);
4482             Rewrite (Low_Bound (R),
4483               Make_Attribute_Reference (Sloc (Low_Bound (R)),
4484                 Prefix =>         New_Occurrence_Of (Typ, Sloc (R)),
4485                 Attribute_Name => Name_First));
4486             Rewrite (High_Bound (R),
4487               Make_Attribute_Reference (Sloc (High_Bound (R)),
4488                 Prefix =>         New_Occurrence_Of (Typ, Sloc (R)),
4489                 Attribute_Name => Name_First));
4490
4491          else
4492             Resolve (R, Typ);
4493             Set_Etype (N, Etype (R));
4494
4495             --  Additionally, we must check that the bounds are compatible
4496             --  with the given subtype, which might be different from the
4497             --  type of the context.
4498
4499             Apply_Range_Check (R, S);
4500
4501             --  ??? If the above check statically detects a Constraint_Error
4502             --  it replaces the offending bound(s) of the range R with a
4503             --  Constraint_Error node. When the itype which uses these bounds
4504             --  is frozen the resulting call to Duplicate_Subexpr generates
4505             --  a new temporary for the bounds.
4506
4507             --  Unfortunately there are other itypes that are also made depend
4508             --  on these bounds, so when Duplicate_Subexpr is called they get
4509             --  a forward reference to the newly created temporaries and Gigi
4510             --  aborts on such forward references. This is probably sign of a
4511             --  more fundamental problem somewhere else in either the order of
4512             --  itype freezing or the way certain itypes are constructed.
4513
4514             --  To get around this problem we call Remove_Side_Effects right
4515             --  away if either bounds of R are a Constraint_Error.
4516
4517             declare
4518                L : constant Node_Id := Low_Bound (R);
4519                H : constant Node_Id := High_Bound (R);
4520
4521             begin
4522                if Nkind (L) = N_Raise_Constraint_Error then
4523                   Remove_Side_Effects (L);
4524                end if;
4525
4526                if Nkind (H) = N_Raise_Constraint_Error then
4527                   Remove_Side_Effects (H);
4528                end if;
4529             end;
4530
4531             Check_Unset_Reference (Low_Bound  (R));
4532             Check_Unset_Reference (High_Bound (R));
4533          end if;
4534       end if;
4535    end Resolve_Discrete_Subtype_Indication;
4536
4537    -------------------------
4538    -- Resolve_Entity_Name --
4539    -------------------------
4540
4541    --  Used to resolve identifiers and expanded names
4542
4543    procedure Resolve_Entity_Name (N : Node_Id; Typ : Entity_Id) is
4544       E : constant Entity_Id := Entity (N);
4545
4546    begin
4547       --  If garbage from errors, set to Any_Type and return
4548
4549       if No (E) and then Total_Errors_Detected /= 0 then
4550          Set_Etype (N, Any_Type);
4551          return;
4552       end if;
4553
4554       --  Replace named numbers by corresponding literals. Note that this is
4555       --  the one case where Resolve_Entity_Name must reset the Etype, since
4556       --  it is currently marked as universal.
4557
4558       if Ekind (E) = E_Named_Integer then
4559          Set_Etype (N, Typ);
4560          Eval_Named_Integer (N);
4561
4562       elsif Ekind (E) = E_Named_Real then
4563          Set_Etype (N, Typ);
4564          Eval_Named_Real (N);
4565
4566       --  Allow use of subtype only if it is a concurrent type where we are
4567       --  currently inside the body. This will eventually be expanded
4568       --  into a call to Self (for tasks) or _object (for protected
4569       --  objects). Any other use of a subtype is invalid.
4570
4571       elsif Is_Type (E) then
4572          if Is_Concurrent_Type (E)
4573            and then In_Open_Scopes (E)
4574          then
4575             null;
4576          else
4577             Error_Msg_N
4578                ("invalid use of subtype mark in expression or call", N);
4579          end if;
4580
4581       --  Check discriminant use if entity is discriminant in current scope,
4582       --  i.e. discriminant of record or concurrent type currently being
4583       --  analyzed. Uses in corresponding body are unrestricted.
4584
4585       elsif Ekind (E) = E_Discriminant
4586         and then Scope (E) = Current_Scope
4587         and then not Has_Completion (Current_Scope)
4588       then
4589          Check_Discriminant_Use (N);
4590
4591       --  A parameterless generic function cannot appear in a context that
4592       --  requires resolution.
4593
4594       elsif Ekind (E) = E_Generic_Function then
4595          Error_Msg_N ("illegal use of generic function", N);
4596
4597       elsif Ekind (E) = E_Out_Parameter
4598         and then Ada_Version = Ada_83
4599         and then (Nkind (Parent (N)) in N_Op
4600                     or else (Nkind (Parent (N)) = N_Assignment_Statement
4601                               and then N = Expression (Parent (N)))
4602                     or else Nkind (Parent (N)) = N_Explicit_Dereference)
4603       then
4604          Error_Msg_N ("(Ada 83) illegal reading of out parameter", N);
4605
4606       --  In all other cases, just do the possible static evaluation
4607
4608       else
4609          --  A deferred constant that appears in an expression must have
4610          --  a completion, unless it has been removed by in-place expansion
4611          --  of an aggregate.
4612
4613          if Ekind (E) = E_Constant
4614            and then Comes_From_Source (E)
4615            and then No (Constant_Value (E))
4616            and then Is_Frozen (Etype (E))
4617            and then not In_Default_Expression
4618            and then not Is_Imported (E)
4619          then
4620
4621             if No_Initialization (Parent (E))
4622               or else (Present (Full_View (E))
4623                         and then No_Initialization (Parent (Full_View (E))))
4624             then
4625                null;
4626             else
4627                Error_Msg_N (
4628                  "deferred constant is frozen before completion", N);
4629             end if;
4630          end if;
4631
4632          Eval_Entity_Name (N);
4633       end if;
4634    end Resolve_Entity_Name;
4635
4636    -------------------
4637    -- Resolve_Entry --
4638    -------------------
4639
4640    procedure Resolve_Entry (Entry_Name : Node_Id) is
4641       Loc    : constant Source_Ptr := Sloc (Entry_Name);
4642       Nam    : Entity_Id;
4643       New_N  : Node_Id;
4644       S      : Entity_Id;
4645       Tsk    : Entity_Id;
4646       E_Name : Node_Id;
4647       Index  : Node_Id;
4648
4649       function Actual_Index_Type (E : Entity_Id) return Entity_Id;
4650       --  If the bounds of the entry family being called depend on task
4651       --  discriminants, build a new index subtype where a discriminant is
4652       --  replaced with the value of the discriminant of the target task.
4653       --  The target task is the prefix of the entry name in the call.
4654
4655       -----------------------
4656       -- Actual_Index_Type --
4657       -----------------------
4658
4659       function Actual_Index_Type (E : Entity_Id) return Entity_Id is
4660          Typ   : constant Entity_Id := Entry_Index_Type (E);
4661          Tsk   : constant Entity_Id := Scope (E);
4662          Lo    : constant Node_Id   := Type_Low_Bound  (Typ);
4663          Hi    : constant Node_Id   := Type_High_Bound (Typ);
4664          New_T : Entity_Id;
4665
4666          function Actual_Discriminant_Ref (Bound : Node_Id) return Node_Id;
4667          --  If the bound is given by a discriminant, replace with a reference
4668          --  to the discriminant of the same name in the target task.
4669          --  If the entry name is the target of a requeue statement and the
4670          --  entry is in the current protected object, the bound to be used
4671          --  is the discriminal of the object (see apply_range_checks for
4672          --  details of the transformation).
4673
4674          -----------------------------
4675          -- Actual_Discriminant_Ref --
4676          -----------------------------
4677
4678          function Actual_Discriminant_Ref (Bound : Node_Id) return Node_Id is
4679             Typ : constant Entity_Id := Etype (Bound);
4680             Ref : Node_Id;
4681
4682          begin
4683             Remove_Side_Effects (Bound);
4684
4685             if not Is_Entity_Name (Bound)
4686               or else Ekind (Entity (Bound)) /= E_Discriminant
4687             then
4688                return Bound;
4689
4690             elsif Is_Protected_Type (Tsk)
4691               and then In_Open_Scopes (Tsk)
4692               and then Nkind (Parent (Entry_Name)) = N_Requeue_Statement
4693             then
4694                return New_Occurrence_Of (Discriminal (Entity (Bound)), Loc);
4695
4696             else
4697                Ref :=
4698                  Make_Selected_Component (Loc,
4699                    Prefix => New_Copy_Tree (Prefix (Prefix (Entry_Name))),
4700                    Selector_Name => New_Occurrence_Of (Entity (Bound), Loc));
4701                Analyze (Ref);
4702                Resolve (Ref, Typ);
4703                return Ref;
4704             end if;
4705          end Actual_Discriminant_Ref;
4706
4707       --  Start of processing for Actual_Index_Type
4708
4709       begin
4710          if not Has_Discriminants (Tsk)
4711            or else (not Is_Entity_Name (Lo)
4712                      and then not Is_Entity_Name (Hi))
4713          then
4714             return Entry_Index_Type (E);
4715
4716          else
4717             New_T := Create_Itype (Ekind (Typ), Parent (Entry_Name));
4718             Set_Etype        (New_T, Base_Type (Typ));
4719             Set_Size_Info    (New_T, Typ);
4720             Set_RM_Size      (New_T, RM_Size (Typ));
4721             Set_Scalar_Range (New_T,
4722               Make_Range (Sloc (Entry_Name),
4723                 Low_Bound  => Actual_Discriminant_Ref (Lo),
4724                 High_Bound => Actual_Discriminant_Ref (Hi)));
4725
4726             return New_T;
4727          end if;
4728       end Actual_Index_Type;
4729
4730    --  Start of processing of Resolve_Entry
4731
4732    begin
4733       --  Find name of entry being called, and resolve prefix of name
4734       --  with its own type. The prefix can be overloaded, and the name
4735       --  and signature of the entry must be taken into account.
4736
4737       if Nkind (Entry_Name) = N_Indexed_Component then
4738
4739          --  Case of dealing with entry family within the current tasks
4740
4741          E_Name := Prefix (Entry_Name);
4742
4743       else
4744          E_Name := Entry_Name;
4745       end if;
4746
4747       if Is_Entity_Name (E_Name) then
4748          --  Entry call to an entry (or entry family) in the current task.
4749          --  This is legal even though the task will deadlock. Rewrite as
4750          --  call to current task.
4751
4752          --  This can also be a call to an entry in  an enclosing task.
4753          --  If this is a single task, we have to retrieve its name,
4754          --  because the scope of the entry is the task type, not the
4755          --  object. If the enclosing task is a task type, the identity
4756          --  of the task is given by its own self variable.
4757
4758          --  Finally this can be a requeue on an entry of the same task
4759          --  or protected object.
4760
4761          S := Scope (Entity (E_Name));
4762
4763          for J in reverse 0 .. Scope_Stack.Last loop
4764
4765             if Is_Task_Type (Scope_Stack.Table (J).Entity)
4766               and then not Comes_From_Source (S)
4767             then
4768                --  S is an enclosing task or protected object. The concurrent
4769                --  declaration has been converted into a type declaration, and
4770                --  the object itself has an object declaration that follows
4771                --  the type in the same declarative part.
4772
4773                Tsk := Next_Entity (S);
4774                while Etype (Tsk) /= S loop
4775                   Next_Entity (Tsk);
4776                end loop;
4777
4778                S := Tsk;
4779                exit;
4780
4781             elsif S = Scope_Stack.Table (J).Entity then
4782
4783                --  Call to current task. Will be transformed into call to Self
4784
4785                exit;
4786
4787             end if;
4788          end loop;
4789
4790          New_N :=
4791            Make_Selected_Component (Loc,
4792              Prefix => New_Occurrence_Of (S, Loc),
4793              Selector_Name =>
4794                New_Occurrence_Of (Entity (E_Name), Loc));
4795          Rewrite (E_Name, New_N);
4796          Analyze (E_Name);
4797
4798       elsif Nkind (Entry_Name) = N_Selected_Component
4799         and then Is_Overloaded (Prefix (Entry_Name))
4800       then
4801          --  Use the entry name (which must be unique at this point) to
4802          --  find the prefix that returns the corresponding task type or
4803          --  protected type.
4804
4805          declare
4806             Pref : constant Node_Id := Prefix (Entry_Name);
4807             Ent  : constant Entity_Id :=  Entity (Selector_Name (Entry_Name));
4808             I    : Interp_Index;
4809             It   : Interp;
4810
4811          begin
4812             Get_First_Interp (Pref, I, It);
4813             while Present (It.Typ) loop
4814                if Scope (Ent) = It.Typ then
4815                   Set_Etype (Pref, It.Typ);
4816                   exit;
4817                end if;
4818
4819                Get_Next_Interp (I, It);
4820             end loop;
4821          end;
4822       end if;
4823
4824       if Nkind (Entry_Name) = N_Selected_Component then
4825          Resolve (Prefix (Entry_Name));
4826
4827       else pragma Assert (Nkind (Entry_Name) = N_Indexed_Component);
4828          Nam := Entity (Selector_Name (Prefix (Entry_Name)));
4829          Resolve (Prefix (Prefix (Entry_Name)));
4830          Index :=  First (Expressions (Entry_Name));
4831          Resolve (Index, Entry_Index_Type (Nam));
4832
4833          --  Up to this point the expression could have been the actual
4834          --  in a simple entry call, and be given by a named association.
4835
4836          if Nkind (Index) = N_Parameter_Association then
4837             Error_Msg_N ("expect expression for entry index", Index);
4838          else
4839             Apply_Range_Check (Index, Actual_Index_Type (Nam));
4840          end if;
4841       end if;
4842    end Resolve_Entry;
4843
4844    ------------------------
4845    -- Resolve_Entry_Call --
4846    ------------------------
4847
4848    procedure Resolve_Entry_Call (N : Node_Id; Typ : Entity_Id) is
4849       Entry_Name  : constant Node_Id    := Name (N);
4850       Loc         : constant Source_Ptr := Sloc (Entry_Name);
4851       Actuals     : List_Id;
4852       First_Named : Node_Id;
4853       Nam         : Entity_Id;
4854       Norm_OK     : Boolean;
4855       Obj         : Node_Id;
4856       Was_Over    : Boolean;
4857
4858    begin
4859       --  We kill all checks here, because it does not seem worth the
4860       --  effort to do anything better, an entry call is a big operation.
4861
4862       Kill_All_Checks;
4863
4864       --  Processing of the name is similar for entry calls and protected
4865       --  operation calls. Once the entity is determined, we can complete
4866       --  the resolution of the actuals.
4867
4868       --  The selector may be overloaded, in the case of a protected object
4869       --  with overloaded functions. The type of the context is used for
4870       --  resolution.
4871
4872       if Nkind (Entry_Name) = N_Selected_Component
4873         and then Is_Overloaded (Selector_Name (Entry_Name))
4874         and then Typ /= Standard_Void_Type
4875       then
4876          declare
4877             I  : Interp_Index;
4878             It : Interp;
4879
4880          begin
4881             Get_First_Interp (Selector_Name (Entry_Name), I, It);
4882             while Present (It.Typ) loop
4883                if Covers (Typ, It.Typ) then
4884                   Set_Entity (Selector_Name (Entry_Name), It.Nam);
4885                   Set_Etype  (Entry_Name, It.Typ);
4886
4887                   Generate_Reference (It.Typ, N, ' ');
4888                end if;
4889
4890                Get_Next_Interp (I, It);
4891             end loop;
4892          end;
4893       end if;
4894
4895       Resolve_Entry (Entry_Name);
4896
4897       if Nkind (Entry_Name) = N_Selected_Component then
4898
4899          --  Simple entry call
4900
4901          Nam := Entity (Selector_Name (Entry_Name));
4902          Obj := Prefix (Entry_Name);
4903          Was_Over := Is_Overloaded (Selector_Name (Entry_Name));
4904
4905       else pragma Assert (Nkind (Entry_Name) = N_Indexed_Component);
4906
4907          --  Call to member of entry family
4908
4909          Nam := Entity (Selector_Name (Prefix (Entry_Name)));
4910          Obj := Prefix (Prefix (Entry_Name));
4911          Was_Over := Is_Overloaded (Selector_Name (Prefix (Entry_Name)));
4912       end if;
4913
4914       --  We cannot in general check the maximum depth of protected entry
4915       --  calls at compile time. But we can tell that any protected entry
4916       --  call at all violates a specified nesting depth of zero.
4917
4918       if Is_Protected_Type (Scope (Nam)) then
4919          Check_Restriction (Max_Entry_Queue_Length, N);
4920       end if;
4921
4922       --  Use context type to disambiguate a protected function that can be
4923       --  called without actuals and that returns an array type, and where
4924       --  the argument list may be an indexing of the returned value.
4925
4926       if Ekind (Nam) = E_Function
4927         and then Needs_No_Actuals (Nam)
4928         and then Present (Parameter_Associations (N))
4929         and then
4930           ((Is_Array_Type (Etype (Nam))
4931              and then Covers (Typ, Component_Type (Etype (Nam))))
4932
4933             or else (Is_Access_Type (Etype (Nam))
4934                       and then Is_Array_Type (Designated_Type (Etype (Nam)))
4935                       and then Covers (Typ,
4936                         Component_Type (Designated_Type (Etype (Nam))))))
4937       then
4938          declare
4939             Index_Node : Node_Id;
4940
4941          begin
4942             Index_Node :=
4943               Make_Indexed_Component (Loc,
4944                 Prefix =>
4945                   Make_Function_Call (Loc,
4946                     Name => Relocate_Node (Entry_Name)),
4947                 Expressions => Parameter_Associations (N));
4948
4949             --  Since we are correcting a node classification error made by
4950             --  the parser, we call Replace rather than Rewrite.
4951
4952             Replace (N, Index_Node);
4953             Set_Etype (Prefix (N), Etype (Nam));
4954             Set_Etype (N, Typ);
4955             Resolve_Indexed_Component (N, Typ);
4956             return;
4957          end;
4958       end if;
4959
4960       --  The operation name may have been overloaded. Order the actuals
4961       --  according to the formals of the resolved entity, and set the
4962       --  return type to that of the operation.
4963
4964       if Was_Over then
4965          Normalize_Actuals (N, Nam, False, Norm_OK);
4966          pragma Assert (Norm_OK);
4967          Set_Etype (N, Etype (Nam));
4968       end if;
4969
4970       Resolve_Actuals (N, Nam);
4971       Generate_Reference (Nam, Entry_Name);
4972
4973       if Ekind (Nam) = E_Entry
4974         or else Ekind (Nam) = E_Entry_Family
4975       then
4976          Check_Potentially_Blocking_Operation (N);
4977       end if;
4978
4979       --  Verify that a procedure call cannot masquerade as an entry
4980       --  call where an entry call is expected.
4981
4982       if Ekind (Nam) = E_Procedure then
4983          if Nkind (Parent (N)) = N_Entry_Call_Alternative
4984            and then N = Entry_Call_Statement (Parent (N))
4985          then
4986             Error_Msg_N ("entry call required in select statement", N);
4987
4988          elsif Nkind (Parent (N)) = N_Triggering_Alternative
4989            and then N = Triggering_Statement (Parent (N))
4990          then
4991             Error_Msg_N ("triggering statement cannot be procedure call", N);
4992
4993          elsif Ekind (Scope (Nam)) = E_Task_Type
4994            and then not In_Open_Scopes (Scope (Nam))
4995          then
4996             Error_Msg_N ("task has no entry with this name", Entry_Name);
4997          end if;
4998       end if;
4999
5000       --  After resolution, entry calls and protected procedure calls
5001       --  are changed into entry calls, for expansion. The structure
5002       --  of the node does not change, so it can safely be done in place.
5003       --  Protected function calls must keep their structure because they
5004       --  are subexpressions.
5005
5006       if Ekind (Nam) /= E_Function then
5007
5008          --  A protected operation that is not a function may modify the
5009          --  corresponding object, and cannot apply to a constant.
5010          --  If this is an internal call, the prefix is the type itself.
5011
5012          if Is_Protected_Type (Scope (Nam))
5013            and then not Is_Variable (Obj)
5014            and then (not Is_Entity_Name (Obj)
5015                        or else not Is_Type (Entity (Obj)))
5016          then
5017             Error_Msg_N
5018               ("prefix of protected procedure or entry call must be variable",
5019                Entry_Name);
5020          end if;
5021
5022          Actuals := Parameter_Associations (N);
5023          First_Named := First_Named_Actual (N);
5024
5025          Rewrite (N,
5026            Make_Entry_Call_Statement (Loc,
5027              Name                   => Entry_Name,
5028              Parameter_Associations => Actuals));
5029
5030          Set_First_Named_Actual (N, First_Named);
5031          Set_Analyzed (N, True);
5032
5033       --  Protected functions can return on the secondary stack, in which
5034       --  case we must trigger the transient scope mechanism.
5035
5036       elsif Expander_Active
5037         and then Requires_Transient_Scope (Etype (Nam))
5038       then
5039          Establish_Transient_Scope (N, Sec_Stack => True);
5040       end if;
5041    end Resolve_Entry_Call;
5042
5043    -------------------------
5044    -- Resolve_Equality_Op --
5045    -------------------------
5046
5047    --  Both arguments must have the same type, and the boolean context
5048    --  does not participate in the resolution. The first pass verifies
5049    --  that the interpretation is not ambiguous, and the type of the left
5050    --  argument is correctly set, or is Any_Type in case of ambiguity.
5051    --  If both arguments are strings or aggregates, allocators, or Null,
5052    --  they are ambiguous even though they carry a single (universal) type.
5053    --  Diagnose this case here.
5054
5055    procedure Resolve_Equality_Op (N : Node_Id; Typ : Entity_Id) is
5056       L : constant Node_Id   := Left_Opnd (N);
5057       R : constant Node_Id   := Right_Opnd (N);
5058       T : Entity_Id := Find_Unique_Type (L, R);
5059
5060       function Find_Unique_Access_Type return Entity_Id;
5061       --  In the case of allocators, make a last-ditch attempt to find a single
5062       --  access type with the right designated type. This is semantically
5063       --  dubious, and of no interest to any real code, but c48008a makes it
5064       --  all worthwhile.
5065
5066       -----------------------------
5067       -- Find_Unique_Access_Type --
5068       -----------------------------
5069
5070       function Find_Unique_Access_Type return Entity_Id is
5071          Acc : Entity_Id;
5072          E   : Entity_Id;
5073          S   : Entity_Id;
5074
5075       begin
5076          if Ekind (Etype (R)) =  E_Allocator_Type then
5077             Acc := Designated_Type (Etype (R));
5078
5079          elsif Ekind (Etype (L)) =  E_Allocator_Type then
5080             Acc := Designated_Type (Etype (L));
5081
5082          else
5083             return Empty;
5084          end if;
5085
5086          S := Current_Scope;
5087          while S /= Standard_Standard loop
5088             E := First_Entity (S);
5089             while Present (E) loop
5090                if Is_Type (E)
5091                  and then Is_Access_Type (E)
5092                  and then Ekind (E) /= E_Allocator_Type
5093                  and then Designated_Type (E) = Base_Type (Acc)
5094                then
5095                   return E;
5096                end if;
5097
5098                Next_Entity (E);
5099             end loop;
5100
5101             S := Scope (S);
5102          end loop;
5103
5104          return Empty;
5105       end Find_Unique_Access_Type;
5106
5107    --  Start of processing for Resolve_Equality_Op
5108
5109    begin
5110       Set_Etype (N, Base_Type (Typ));
5111       Generate_Reference (T, N, ' ');
5112
5113       if T = Any_Fixed then
5114          T := Unique_Fixed_Point_Type (L);
5115       end if;
5116
5117       if T /= Any_Type then
5118          if T = Any_String
5119            or else T = Any_Composite
5120            or else T = Any_Character
5121          then
5122             if T = Any_Character then
5123                Ambiguous_Character (L);
5124             else
5125                Error_Msg_N ("ambiguous operands for equality", N);
5126             end if;
5127
5128             Set_Etype (N, Any_Type);
5129             return;
5130
5131          elsif T = Any_Access
5132            or else Ekind (T) = E_Allocator_Type
5133            or else Ekind (T) = E_Access_Attribute_Type
5134          then
5135             T := Find_Unique_Access_Type;
5136
5137             if No (T) then
5138                Error_Msg_N ("ambiguous operands for equality", N);
5139                Set_Etype (N, Any_Type);
5140                return;
5141             end if;
5142          end if;
5143
5144          Resolve (L, T);
5145          Resolve (R, T);
5146
5147          --  If the unique type is a class-wide type then it will be expanded
5148          --  into a dispatching call to the predefined primitive. Therefore we
5149          --  check here for potential violation of such restriction.
5150
5151          if Is_Class_Wide_Type (T) then
5152             Check_Restriction (No_Dispatching_Calls, N);
5153          end if;
5154
5155          if Warn_On_Redundant_Constructs
5156            and then Comes_From_Source (N)
5157            and then Is_Entity_Name (R)
5158            and then Entity (R) = Standard_True
5159            and then Comes_From_Source (R)
5160          then
5161             Error_Msg_N ("comparison with True is redundant?", R);
5162          end if;
5163
5164          Check_Unset_Reference (L);
5165          Check_Unset_Reference (R);
5166          Generate_Operator_Reference (N, T);
5167
5168          --  If this is an inequality, it may be the implicit inequality
5169          --  created for a user-defined operation, in which case the corres-
5170          --  ponding equality operation is not intrinsic, and the operation
5171          --  cannot be constant-folded. Else fold.
5172
5173          if Nkind (N) = N_Op_Eq
5174            or else Comes_From_Source (Entity (N))
5175            or else Ekind (Entity (N)) = E_Operator
5176            or else Is_Intrinsic_Subprogram
5177              (Corresponding_Equality (Entity (N)))
5178          then
5179             Eval_Relational_Op (N);
5180          elsif Nkind (N) = N_Op_Ne
5181            and then Is_Abstract_Subprogram (Entity (N))
5182          then
5183             Error_Msg_NE ("cannot call abstract subprogram &!", N, Entity (N));
5184          end if;
5185
5186          --  Ada 2005:  If one operand is an anonymous access type, convert
5187          --  the other operand to it, to ensure that the underlying types
5188          --  match in the back-end.
5189          --  We apply the same conversion in the case one of the operands is
5190          --  a private subtype of the type of the other.
5191
5192          if Expander_Active
5193            and then (Ekind (T) =  E_Anonymous_Access_Type
5194                        or else Is_Private_Type (T))
5195          then
5196             if Etype (L) /= T then
5197                Rewrite (L,
5198                  Make_Unchecked_Type_Conversion (Sloc (L),
5199                    Subtype_Mark => New_Occurrence_Of (T, Sloc (L)),
5200                    Expression   => Relocate_Node (L)));
5201                Analyze_And_Resolve (L, T);
5202             end if;
5203
5204             if (Etype (R)) /= T then
5205                Rewrite (R,
5206                   Make_Unchecked_Type_Conversion (Sloc (R),
5207                     Subtype_Mark => New_Occurrence_Of (Etype (L), Sloc (R)),
5208                     Expression   => Relocate_Node (R)));
5209                Analyze_And_Resolve (R, T);
5210             end if;
5211          end if;
5212       end if;
5213    end Resolve_Equality_Op;
5214
5215    ----------------------------------
5216    -- Resolve_Explicit_Dereference --
5217    ----------------------------------
5218
5219    procedure Resolve_Explicit_Dereference (N : Node_Id; Typ : Entity_Id) is
5220       Loc   : constant Source_Ptr := Sloc (N);
5221       New_N : Node_Id;
5222       P     : constant Node_Id := Prefix (N);
5223       I     : Interp_Index;
5224       It    : Interp;
5225
5226    begin
5227       Check_Fully_Declared_Prefix (Typ, P);
5228
5229       if Is_Overloaded (P) then
5230
5231          --  Use the context type to select the prefix that has the correct
5232          --  designated type.
5233
5234          Get_First_Interp (P, I, It);
5235          while Present (It.Typ) loop
5236             exit when Is_Access_Type (It.Typ)
5237               and then Covers (Typ, Designated_Type (It.Typ));
5238             Get_Next_Interp (I, It);
5239          end loop;
5240
5241          if Present (It.Typ) then
5242             Resolve (P, It.Typ);
5243          else
5244             --  If no interpretation covers the designated type of the prefix,
5245             --  this is the pathological case where not all implementations of
5246             --  the prefix allow the interpretation of the node as a call. Now
5247             --  that the expected type is known, Remove other interpretations
5248             --  from prefix, rewrite it as a call, and resolve again, so that
5249             --  the proper call node is generated.
5250
5251             Get_First_Interp (P, I, It);
5252             while Present (It.Typ) loop
5253                if Ekind (It.Typ) /= E_Access_Subprogram_Type then
5254                   Remove_Interp (I);
5255                end if;
5256
5257                Get_Next_Interp (I, It);
5258             end loop;
5259
5260             New_N :=
5261               Make_Function_Call (Loc,
5262                 Name =>
5263                   Make_Explicit_Dereference (Loc,
5264                     Prefix => P),
5265                 Parameter_Associations => New_List);
5266
5267             Save_Interps (N, New_N);
5268             Rewrite (N, New_N);
5269             Analyze_And_Resolve (N, Typ);
5270             return;
5271          end if;
5272
5273          Set_Etype (N, Designated_Type (It.Typ));
5274
5275       else
5276          Resolve (P);
5277       end if;
5278
5279       if Is_Access_Type (Etype (P)) then
5280          Apply_Access_Check (N);
5281       end if;
5282
5283       --  If the designated type is a packed unconstrained array type, and the
5284       --  explicit dereference is not in the context of an attribute reference,
5285       --  then we must compute and set the actual subtype, since it is needed
5286       --  by Gigi. The reason we exclude the attribute case is that this is
5287       --  handled fine by Gigi, and in fact we use such attributes to build the
5288       --  actual subtype. We also exclude generated code (which builds actual
5289       --  subtypes directly if they are needed).
5290
5291       if Is_Array_Type (Etype (N))
5292         and then Is_Packed (Etype (N))
5293         and then not Is_Constrained (Etype (N))
5294         and then Nkind (Parent (N)) /= N_Attribute_Reference
5295         and then Comes_From_Source (N)
5296       then
5297          Set_Etype (N, Get_Actual_Subtype (N));
5298       end if;
5299
5300       --  Note: there is no Eval processing required for an explicit deference,
5301       --  because the type is known to be an allocators, and allocator
5302       --  expressions can never be static.
5303
5304    end Resolve_Explicit_Dereference;
5305
5306    -------------------------------
5307    -- Resolve_Indexed_Component --
5308    -------------------------------
5309
5310    procedure Resolve_Indexed_Component (N : Node_Id; Typ : Entity_Id) is
5311       Name       : constant Node_Id := Prefix  (N);
5312       Expr       : Node_Id;
5313       Array_Type : Entity_Id := Empty; -- to prevent junk warning
5314       Index      : Node_Id;
5315
5316    begin
5317       if Is_Overloaded (Name) then
5318
5319          --  Use the context type to select the prefix that yields the correct
5320          --  component type.
5321
5322          declare
5323             I     : Interp_Index;
5324             It    : Interp;
5325             I1    : Interp_Index := 0;
5326             P     : constant Node_Id := Prefix (N);
5327             Found : Boolean := False;
5328
5329          begin
5330             Get_First_Interp (P, I, It);
5331             while Present (It.Typ) loop
5332                if (Is_Array_Type (It.Typ)
5333                      and then Covers (Typ, Component_Type (It.Typ)))
5334                  or else (Is_Access_Type (It.Typ)
5335                             and then Is_Array_Type (Designated_Type (It.Typ))
5336                             and then Covers
5337                               (Typ, Component_Type (Designated_Type (It.Typ))))
5338                then
5339                   if Found then
5340                      It := Disambiguate (P, I1, I, Any_Type);
5341
5342                      if It = No_Interp then
5343                         Error_Msg_N ("ambiguous prefix for indexing",  N);
5344                         Set_Etype (N, Typ);
5345                         return;
5346
5347                      else
5348                         Found := True;
5349                         Array_Type := It.Typ;
5350                         I1 := I;
5351                      end if;
5352
5353                   else
5354                      Found := True;
5355                      Array_Type := It.Typ;
5356                      I1 := I;
5357                   end if;
5358                end if;
5359
5360                Get_Next_Interp (I, It);
5361             end loop;
5362          end;
5363
5364       else
5365          Array_Type := Etype (Name);
5366       end if;
5367
5368       Resolve (Name, Array_Type);
5369       Array_Type := Get_Actual_Subtype_If_Available (Name);
5370
5371       --  If prefix is access type, dereference to get real array type.
5372       --  Note: we do not apply an access check because the expander always
5373       --  introduces an explicit dereference, and the check will happen there.
5374
5375       if Is_Access_Type (Array_Type) then
5376          Array_Type := Designated_Type (Array_Type);
5377       end if;
5378
5379       --  If name was overloaded, set component type correctly now
5380
5381       Set_Etype (N, Component_Type (Array_Type));
5382
5383       Index := First_Index (Array_Type);
5384       Expr  := First (Expressions (N));
5385
5386       --  The prefix may have resolved to a string literal, in which case its
5387       --  etype has a special representation. This is only possible currently
5388       --  if the prefix is a static concatenation, written in functional
5389       --  notation.
5390
5391       if Ekind (Array_Type) = E_String_Literal_Subtype then
5392          Resolve (Expr, Standard_Positive);
5393
5394       else
5395          while Present (Index) and Present (Expr) loop
5396             Resolve (Expr, Etype (Index));
5397             Check_Unset_Reference (Expr);
5398
5399             if Is_Scalar_Type (Etype (Expr)) then
5400                Apply_Scalar_Range_Check (Expr, Etype (Index));
5401             else
5402                Apply_Range_Check (Expr, Get_Actual_Subtype (Index));
5403             end if;
5404
5405             Next_Index (Index);
5406             Next (Expr);
5407          end loop;
5408       end if;
5409
5410       --  Do not generate the warning on suspicious index if we are analyzing
5411       --  package Ada.Tags; otherwise we will report the warning with the
5412       --  Prims_Ptr field of the dispatch table.
5413
5414       if Scope (Etype (Prefix (N))) = Standard_Standard
5415         or else not
5416           Is_RTU (Cunit_Entity (Get_Source_Unit (Etype (Prefix (N)))),
5417                   Ada_Tags)
5418       then
5419          Warn_On_Suspicious_Index (Name, First (Expressions (N)));
5420          Eval_Indexed_Component (N);
5421       end if;
5422    end Resolve_Indexed_Component;
5423
5424    -----------------------------
5425    -- Resolve_Integer_Literal --
5426    -----------------------------
5427
5428    procedure Resolve_Integer_Literal (N : Node_Id; Typ : Entity_Id) is
5429    begin
5430       Set_Etype (N, Typ);
5431       Eval_Integer_Literal (N);
5432    end Resolve_Integer_Literal;
5433
5434    --------------------------------
5435    -- Resolve_Intrinsic_Operator --
5436    --------------------------------
5437
5438    procedure Resolve_Intrinsic_Operator  (N : Node_Id; Typ : Entity_Id) is
5439       Btyp : constant Entity_Id := Base_Type (Underlying_Type (Typ));
5440       Op   : Entity_Id;
5441       Arg1 : Node_Id;
5442       Arg2 : Node_Id;
5443
5444    begin
5445       Op := Entity (N);
5446       while Scope (Op) /= Standard_Standard loop
5447          Op := Homonym (Op);
5448          pragma Assert (Present (Op));
5449       end loop;
5450
5451       Set_Entity (N, Op);
5452       Set_Is_Overloaded (N, False);
5453
5454       --  If the operand type is private, rewrite with suitable conversions on
5455       --  the operands and the result, to expose the proper underlying numeric
5456       --  type.
5457
5458       if Is_Private_Type (Typ) then
5459          Arg1 := Unchecked_Convert_To (Btyp, Left_Opnd  (N));
5460
5461          if Nkind (N) = N_Op_Expon then
5462             Arg2 := Unchecked_Convert_To (Standard_Integer, Right_Opnd (N));
5463          else
5464             Arg2 := Unchecked_Convert_To (Btyp, Right_Opnd (N));
5465          end if;
5466
5467          Save_Interps (Left_Opnd (N),  Expression (Arg1));
5468          Save_Interps (Right_Opnd (N), Expression (Arg2));
5469
5470          Set_Left_Opnd  (N, Arg1);
5471          Set_Right_Opnd (N, Arg2);
5472
5473          Set_Etype (N, Btyp);
5474          Rewrite (N, Unchecked_Convert_To (Typ, N));
5475          Resolve (N, Typ);
5476
5477       elsif Typ /= Etype (Left_Opnd (N))
5478         or else Typ /= Etype (Right_Opnd (N))
5479       then
5480          --  Add explicit conversion where needed, and save interpretations
5481          --  in case operands are overloaded.
5482
5483          Arg1 := Convert_To (Typ, Left_Opnd  (N));
5484          Arg2 := Convert_To (Typ, Right_Opnd (N));
5485
5486          if Nkind (Arg1) = N_Type_Conversion then
5487             Save_Interps (Left_Opnd (N), Expression (Arg1));
5488          else
5489             Save_Interps (Left_Opnd (N), Arg1);
5490          end if;
5491
5492          if Nkind (Arg2) = N_Type_Conversion then
5493             Save_Interps (Right_Opnd (N), Expression (Arg2));
5494          else
5495             Save_Interps (Right_Opnd (N), Arg2);
5496          end if;
5497
5498          Rewrite (Left_Opnd  (N), Arg1);
5499          Rewrite (Right_Opnd (N), Arg2);
5500          Analyze (Arg1);
5501          Analyze (Arg2);
5502          Resolve_Arithmetic_Op (N, Typ);
5503
5504       else
5505          Resolve_Arithmetic_Op (N, Typ);
5506       end if;
5507    end Resolve_Intrinsic_Operator;
5508
5509    --------------------------------------
5510    -- Resolve_Intrinsic_Unary_Operator --
5511    --------------------------------------
5512
5513    procedure Resolve_Intrinsic_Unary_Operator
5514      (N   : Node_Id;
5515       Typ : Entity_Id)
5516    is
5517       Btyp : constant Entity_Id := Base_Type (Underlying_Type (Typ));
5518       Op   : Entity_Id;
5519       Arg2 : Node_Id;
5520
5521    begin
5522       Op := Entity (N);
5523       while Scope (Op) /= Standard_Standard loop
5524          Op := Homonym (Op);
5525          pragma Assert (Present (Op));
5526       end loop;
5527
5528       Set_Entity (N, Op);
5529
5530       if Is_Private_Type (Typ) then
5531          Arg2 := Unchecked_Convert_To (Btyp, Right_Opnd (N));
5532          Save_Interps (Right_Opnd (N), Expression (Arg2));
5533
5534          Set_Right_Opnd (N, Arg2);
5535
5536          Set_Etype (N, Btyp);
5537          Rewrite (N, Unchecked_Convert_To (Typ, N));
5538          Resolve (N, Typ);
5539
5540       else
5541          Resolve_Unary_Op (N, Typ);
5542       end if;
5543    end Resolve_Intrinsic_Unary_Operator;
5544
5545    ------------------------
5546    -- Resolve_Logical_Op --
5547    ------------------------
5548
5549    procedure Resolve_Logical_Op (N : Node_Id; Typ : Entity_Id) is
5550       B_Typ : Entity_Id;
5551       N_Opr : constant Node_Kind := Nkind (N);
5552
5553    begin
5554       --  Predefined operations on scalar types yield the base type. On the
5555       --  other hand, logical operations on arrays yield the type of the
5556       --  arguments (and the context).
5557
5558       if Is_Array_Type (Typ) then
5559          B_Typ := Typ;
5560       else
5561          B_Typ := Base_Type (Typ);
5562       end if;
5563
5564       --  The following test is required because the operands of the operation
5565       --  may be literals, in which case the resulting type appears to be
5566       --  compatible with a signed integer type, when in fact it is compatible
5567       --  only with modular types. If the context itself is universal, the
5568       --  operation is illegal.
5569
5570       if not Valid_Boolean_Arg (Typ) then
5571          Error_Msg_N ("invalid context for logical operation", N);
5572          Set_Etype (N, Any_Type);
5573          return;
5574
5575       elsif Typ = Any_Modular then
5576          Error_Msg_N
5577            ("no modular type available in this context", N);
5578          Set_Etype (N, Any_Type);
5579          return;
5580       elsif Is_Modular_Integer_Type (Typ)
5581         and then Etype (Left_Opnd (N)) = Universal_Integer
5582         and then Etype (Right_Opnd (N)) = Universal_Integer
5583       then
5584          Check_For_Visible_Operator (N, B_Typ);
5585       end if;
5586
5587       Resolve (Left_Opnd (N), B_Typ);
5588       Resolve (Right_Opnd (N), B_Typ);
5589
5590       Check_Unset_Reference (Left_Opnd  (N));
5591       Check_Unset_Reference (Right_Opnd (N));
5592
5593       Set_Etype (N, B_Typ);
5594       Generate_Operator_Reference (N, B_Typ);
5595       Eval_Logical_Op (N);
5596
5597       --  Check for violation of restriction No_Direct_Boolean_Operators
5598       --  if the operator was not eliminated by the Eval_Logical_Op call.
5599
5600       if Nkind (N) = N_Opr
5601         and then Root_Type (Etype (Left_Opnd (N))) = Standard_Boolean
5602       then
5603          Check_Restriction (No_Direct_Boolean_Operators, N);
5604       end if;
5605    end Resolve_Logical_Op;
5606
5607    ---------------------------
5608    -- Resolve_Membership_Op --
5609    ---------------------------
5610
5611    --  The context can only be a boolean type, and does not determine
5612    --  the arguments. Arguments should be unambiguous, but the preference
5613    --  rule for universal types applies.
5614
5615    procedure Resolve_Membership_Op (N : Node_Id; Typ : Entity_Id) is
5616       pragma Warnings (Off, Typ);
5617
5618       L : constant Node_Id   := Left_Opnd (N);
5619       R : constant Node_Id   := Right_Opnd (N);
5620       T : Entity_Id;
5621
5622    begin
5623       if L = Error or else R = Error then
5624          return;
5625       end if;
5626
5627       if not Is_Overloaded (R)
5628         and then
5629           (Etype (R) = Universal_Integer or else
5630            Etype (R) = Universal_Real)
5631         and then Is_Overloaded (L)
5632       then
5633          T := Etype (R);
5634
5635       --  Ada 2005 (AI-251): Give support to the following case:
5636
5637       --      type I is interface;
5638       --      type T is tagged ...
5639
5640       --      function Test (O : I'Class) is
5641       --      begin
5642       --         return O in T'Class.
5643       --      end Test;
5644
5645       --  In this case we have nothing else to do; the membership test will be
5646       --  done at run-time.
5647
5648       elsif Ada_Version >= Ada_05
5649         and then Is_Class_Wide_Type (Etype (L))
5650         and then Is_Interface (Etype (L))
5651         and then Is_Class_Wide_Type (Etype (R))
5652         and then not Is_Interface (Etype (R))
5653       then
5654          return;
5655
5656       else
5657          T := Intersect_Types (L, R);
5658       end if;
5659
5660       Resolve (L, T);
5661       Check_Unset_Reference (L);
5662
5663       if Nkind (R) = N_Range
5664         and then not Is_Scalar_Type (T)
5665       then
5666          Error_Msg_N ("scalar type required for range", R);
5667       end if;
5668
5669       if Is_Entity_Name (R) then
5670          Freeze_Expression (R);
5671       else
5672          Resolve (R, T);
5673          Check_Unset_Reference (R);
5674       end if;
5675
5676       Eval_Membership_Op (N);
5677    end Resolve_Membership_Op;
5678
5679    ------------------
5680    -- Resolve_Null --
5681    ------------------
5682
5683    procedure Resolve_Null (N : Node_Id; Typ : Entity_Id) is
5684    begin
5685       --  Handle restriction against anonymous null access values This
5686       --  restriction can be turned off using -gnatdh.
5687
5688       --  Ada 2005 (AI-231): Remove restriction
5689
5690       if Ada_Version < Ada_05
5691         and then not Debug_Flag_J
5692         and then Ekind (Typ) = E_Anonymous_Access_Type
5693         and then Comes_From_Source (N)
5694       then
5695          --  In the common case of a call which uses an explicitly null
5696          --  value for an access parameter, give specialized error msg
5697
5698          if Nkind (Parent (N)) = N_Procedure_Call_Statement
5699               or else
5700             Nkind (Parent (N)) = N_Function_Call
5701          then
5702             Error_Msg_N
5703               ("null is not allowed as argument for an access parameter", N);
5704
5705          --  Standard message for all other cases (are there any?)
5706
5707          else
5708             Error_Msg_N
5709               ("null cannot be of an anonymous access type", N);
5710          end if;
5711       end if;
5712
5713       --  In a distributed context, null for a remote access to subprogram
5714       --  may need to be replaced with a special record aggregate. In this
5715       --  case, return after having done the transformation.
5716
5717       if (Ekind (Typ) = E_Record_Type
5718            or else Is_Remote_Access_To_Subprogram_Type (Typ))
5719         and then Remote_AST_Null_Value (N, Typ)
5720       then
5721          return;
5722       end if;
5723
5724       --  The null literal takes its type from the context
5725
5726       Set_Etype (N, Typ);
5727    end Resolve_Null;
5728
5729    -----------------------
5730    -- Resolve_Op_Concat --
5731    -----------------------
5732
5733    procedure Resolve_Op_Concat (N : Node_Id; Typ : Entity_Id) is
5734       Btyp : constant Entity_Id := Base_Type (Typ);
5735       Op1  : constant Node_Id := Left_Opnd (N);
5736       Op2  : constant Node_Id := Right_Opnd (N);
5737
5738       procedure Resolve_Concatenation_Arg (Arg : Node_Id; Is_Comp : Boolean);
5739       --  Internal procedure to resolve one operand of concatenation operator.
5740       --  The operand is either of the array type or of the component type.
5741       --  If the operand is an aggregate, and the component type is composite,
5742       --  this is ambiguous if component type has aggregates.
5743
5744       -------------------------------
5745       -- Resolve_Concatenation_Arg --
5746       -------------------------------
5747
5748       procedure Resolve_Concatenation_Arg (Arg : Node_Id; Is_Comp : Boolean) is
5749       begin
5750          if In_Instance then
5751             if Is_Comp
5752               or else (not Is_Overloaded (Arg)
5753                and then Etype (Arg) /= Any_Composite
5754                and then Covers (Component_Type (Typ), Etype (Arg)))
5755             then
5756                Resolve (Arg, Component_Type (Typ));
5757             else
5758                Resolve (Arg, Btyp);
5759             end if;
5760
5761          elsif Has_Compatible_Type (Arg, Component_Type (Typ)) then
5762
5763             if Nkind (Arg) = N_Aggregate
5764               and then Is_Composite_Type (Component_Type (Typ))
5765             then
5766                if Is_Private_Type (Component_Type (Typ)) then
5767                   Resolve (Arg, Btyp);
5768
5769                else
5770                   Error_Msg_N ("ambiguous aggregate must be qualified", Arg);
5771                   Set_Etype (Arg, Any_Type);
5772                end if;
5773
5774             else
5775                if Is_Overloaded (Arg)
5776                  and then Has_Compatible_Type (Arg, Typ)
5777                  and then Etype (Arg) /= Any_Type
5778                then
5779
5780                   declare
5781                      I    : Interp_Index;
5782                      It   : Interp;
5783                      Func : Entity_Id;
5784
5785                   begin
5786                      Get_First_Interp (Arg, I, It);
5787                      Func := It.Nam;
5788                      Get_Next_Interp (I, It);
5789
5790                      --  Special-case the error message when the overloading
5791                      --  is caused by a function that yields and array and
5792                      --  can be called without parameters.
5793
5794                      if It.Nam = Func then
5795                         Error_Msg_Sloc := Sloc (Func);
5796                         Error_Msg_N ("\ambiguous call to function#", Arg);
5797                         Error_Msg_NE
5798                           ("\\interpretation as call yields&", Arg, Typ);
5799                         Error_Msg_NE
5800                           ("\\interpretation as indexing of call yields&",
5801                             Arg, Component_Type (Typ));
5802
5803                      else
5804                         Error_Msg_N
5805                           ("ambiguous operand for concatenation!", Arg);
5806                         Get_First_Interp (Arg, I, It);
5807                         while Present (It.Nam) loop
5808                            Error_Msg_Sloc := Sloc (It.Nam);
5809
5810                            if Base_Type (It.Typ) = Base_Type (Typ)
5811                              or else Base_Type (It.Typ) =
5812                                Base_Type (Component_Type (Typ))
5813                            then
5814                               Error_Msg_N ("\\possible interpretation#", Arg);
5815                            end if;
5816
5817                            Get_Next_Interp (I, It);
5818                         end loop;
5819                      end if;
5820                   end;
5821                end if;
5822
5823                Resolve (Arg, Component_Type (Typ));
5824
5825                if Nkind (Arg) = N_String_Literal then
5826                   Set_Etype (Arg, Component_Type (Typ));
5827                end if;
5828
5829                if Arg = Left_Opnd (N) then
5830                   Set_Is_Component_Left_Opnd (N);
5831                else
5832                   Set_Is_Component_Right_Opnd (N);
5833                end if;
5834             end if;
5835
5836          else
5837             Resolve (Arg, Btyp);
5838          end if;
5839
5840          Check_Unset_Reference (Arg);
5841       end Resolve_Concatenation_Arg;
5842
5843    --  Start of processing for Resolve_Op_Concat
5844
5845    begin
5846       Set_Etype (N, Btyp);
5847
5848       if Is_Limited_Composite (Btyp) then
5849          Error_Msg_N ("concatenation not available for limited array", N);
5850          Explain_Limited_Type (Btyp, N);
5851       end if;
5852
5853       --  If the operands are themselves concatenations, resolve them as such
5854       --  directly. This removes several layers of recursion and allows GNAT to
5855       --  handle larger multiple concatenations.
5856
5857       if Nkind (Op1) = N_Op_Concat
5858         and then not Is_Array_Type (Component_Type (Typ))
5859         and then Entity (Op1) = Entity (N)
5860       then
5861          Resolve_Op_Concat (Op1, Typ);
5862       else
5863          Resolve_Concatenation_Arg
5864            (Op1,  Is_Component_Left_Opnd  (N));
5865       end if;
5866
5867       if Nkind (Op2) = N_Op_Concat
5868         and then not Is_Array_Type (Component_Type (Typ))
5869         and then Entity (Op2) = Entity (N)
5870       then
5871          Resolve_Op_Concat (Op2, Typ);
5872       else
5873          Resolve_Concatenation_Arg
5874            (Op2, Is_Component_Right_Opnd  (N));
5875       end if;
5876
5877       Generate_Operator_Reference (N, Typ);
5878
5879       if Is_String_Type (Typ) then
5880          Eval_Concatenation (N);
5881       end if;
5882
5883       --  If this is not a static concatenation, but the result is a
5884       --  string type (and not an array of strings) insure that static
5885       --  string operands have their subtypes properly constructed.
5886
5887       if Nkind (N) /= N_String_Literal
5888         and then Is_Character_Type (Component_Type (Typ))
5889       then
5890          Set_String_Literal_Subtype (Op1, Typ);
5891          Set_String_Literal_Subtype (Op2, Typ);
5892       end if;
5893    end Resolve_Op_Concat;
5894
5895    ----------------------
5896    -- Resolve_Op_Expon --
5897    ----------------------
5898
5899    procedure Resolve_Op_Expon (N : Node_Id; Typ : Entity_Id) is
5900       B_Typ : constant Entity_Id := Base_Type (Typ);
5901
5902    begin
5903       --  Catch attempts to do fixed-point exponentation with universal
5904       --  operands, which is a case where the illegality is not caught during
5905       --  normal operator analysis.
5906
5907       if Is_Fixed_Point_Type (Typ) and then Comes_From_Source (N) then
5908          Error_Msg_N ("exponentiation not available for fixed point", N);
5909          return;
5910       end if;
5911
5912       if Comes_From_Source (N)
5913         and then Ekind (Entity (N)) = E_Function
5914         and then Is_Imported (Entity (N))
5915         and then Is_Intrinsic_Subprogram (Entity (N))
5916       then
5917          Resolve_Intrinsic_Operator (N, Typ);
5918          return;
5919       end if;
5920
5921       if Etype (Left_Opnd (N)) = Universal_Integer
5922         or else Etype (Left_Opnd (N)) = Universal_Real
5923       then
5924          Check_For_Visible_Operator (N, B_Typ);
5925       end if;
5926
5927       --  We do the resolution using the base type, because intermediate values
5928       --  in expressions always are of the base type, not a subtype of it.
5929
5930       Resolve (Left_Opnd (N), B_Typ);
5931       Resolve (Right_Opnd (N), Standard_Integer);
5932
5933       Check_Unset_Reference (Left_Opnd  (N));
5934       Check_Unset_Reference (Right_Opnd (N));
5935
5936       Set_Etype (N, B_Typ);
5937       Generate_Operator_Reference (N, B_Typ);
5938       Eval_Op_Expon (N);
5939
5940       --  Set overflow checking bit. Much cleverer code needed here eventually
5941       --  and perhaps the Resolve routines should be separated for the various
5942       --  arithmetic operations, since they will need different processing. ???
5943
5944       if Nkind (N) in N_Op then
5945          if not Overflow_Checks_Suppressed (Etype (N)) then
5946             Enable_Overflow_Check (N);
5947          end if;
5948       end if;
5949    end Resolve_Op_Expon;
5950
5951    --------------------
5952    -- Resolve_Op_Not --
5953    --------------------
5954
5955    procedure Resolve_Op_Not (N : Node_Id; Typ : Entity_Id) is
5956       B_Typ : Entity_Id;
5957
5958       function Parent_Is_Boolean return Boolean;
5959       --  This function determines if the parent node is a boolean operator
5960       --  or operation (comparison op, membership test, or short circuit form)
5961       --  and the not in question is the left operand of this operation.
5962       --  Note that if the not is in parens, then false is returned.
5963
5964       -----------------------
5965       -- Parent_Is_Boolean --
5966       -----------------------
5967
5968       function Parent_Is_Boolean return Boolean is
5969       begin
5970          if Paren_Count (N) /= 0 then
5971             return False;
5972
5973          else
5974             case Nkind (Parent (N)) is
5975                when N_Op_And   |
5976                     N_Op_Eq    |
5977                     N_Op_Ge    |
5978                     N_Op_Gt    |
5979                     N_Op_Le    |
5980                     N_Op_Lt    |
5981                     N_Op_Ne    |
5982                     N_Op_Or    |
5983                     N_Op_Xor   |
5984                     N_In       |
5985                     N_Not_In   |
5986                     N_And_Then |
5987                     N_Or_Else  =>
5988
5989                   return Left_Opnd (Parent (N)) = N;
5990
5991                when others =>
5992                   return False;
5993             end case;
5994          end if;
5995       end Parent_Is_Boolean;
5996
5997    --  Start of processing for Resolve_Op_Not
5998
5999    begin
6000       --  Predefined operations on scalar types yield the base type. On the
6001       --  other hand, logical operations on arrays yield the type of the
6002       --  arguments (and the context).
6003
6004       if Is_Array_Type (Typ) then
6005          B_Typ := Typ;
6006       else
6007          B_Typ := Base_Type (Typ);
6008       end if;
6009
6010       --  Straigtforward case of incorrect arguments
6011
6012       if not Valid_Boolean_Arg (Typ) then
6013          Error_Msg_N ("invalid operand type for operator&", N);
6014          Set_Etype (N, Any_Type);
6015          return;
6016
6017       --  Special case of probable missing parens
6018
6019       elsif Typ = Universal_Integer or else Typ = Any_Modular then
6020          if Parent_Is_Boolean then
6021             Error_Msg_N
6022               ("operand of not must be enclosed in parentheses",
6023                Right_Opnd (N));
6024          else
6025             Error_Msg_N
6026               ("no modular type available in this context", N);
6027          end if;
6028
6029          Set_Etype (N, Any_Type);
6030          return;
6031
6032       --  OK resolution of not
6033
6034       else
6035          --  Warn if non-boolean types involved. This is a case like not a < b
6036          --  where a and b are modular, where we will get (not a) < b and most
6037          --  likely not (a < b) was intended.
6038
6039          if Warn_On_Questionable_Missing_Parens
6040            and then not Is_Boolean_Type (Typ)
6041            and then Parent_Is_Boolean
6042          then
6043             Error_Msg_N ("?not expression should be parenthesized here", N);
6044          end if;
6045
6046          Resolve (Right_Opnd (N), B_Typ);
6047          Check_Unset_Reference (Right_Opnd (N));
6048          Set_Etype (N, B_Typ);
6049          Generate_Operator_Reference (N, B_Typ);
6050          Eval_Op_Not (N);
6051       end if;
6052    end Resolve_Op_Not;
6053
6054    -----------------------------
6055    -- Resolve_Operator_Symbol --
6056    -----------------------------
6057
6058    --  Nothing to be done, all resolved already
6059
6060    procedure Resolve_Operator_Symbol (N : Node_Id; Typ : Entity_Id) is
6061       pragma Warnings (Off, N);
6062       pragma Warnings (Off, Typ);
6063
6064    begin
6065       null;
6066    end Resolve_Operator_Symbol;
6067
6068    ----------------------------------
6069    -- Resolve_Qualified_Expression --
6070    ----------------------------------
6071
6072    procedure Resolve_Qualified_Expression (N : Node_Id; Typ : Entity_Id) is
6073       pragma Warnings (Off, Typ);
6074
6075       Target_Typ : constant Entity_Id := Entity (Subtype_Mark (N));
6076       Expr       : constant Node_Id   := Expression (N);
6077
6078    begin
6079       Resolve (Expr, Target_Typ);
6080
6081       --  A qualified expression requires an exact match of the type,
6082       --  class-wide matching is not allowed. However, if the qualifying
6083       --  type is specific and the expression has a class-wide type, it
6084       --  may still be okay, since it can be the result of the expansion
6085       --  of a call to a dispatching function, so we also have to check
6086       --  class-wideness of the type of the expression's original node.
6087
6088       if (Is_Class_Wide_Type (Target_Typ)
6089            or else
6090              (Is_Class_Wide_Type (Etype (Expr))
6091                and then Is_Class_Wide_Type (Etype (Original_Node (Expr)))))
6092         and then Base_Type (Etype (Expr)) /= Base_Type (Target_Typ)
6093       then
6094          Wrong_Type (Expr, Target_Typ);
6095       end if;
6096
6097       --  If the target type is unconstrained, then we reset the type of
6098       --  the result from the type of the expression. For other cases, the
6099       --  actual subtype of the expression is the target type.
6100
6101       if Is_Composite_Type (Target_Typ)
6102         and then not Is_Constrained (Target_Typ)
6103       then
6104          Set_Etype (N, Etype (Expr));
6105       end if;
6106
6107       Eval_Qualified_Expression (N);
6108    end Resolve_Qualified_Expression;
6109
6110    -------------------
6111    -- Resolve_Range --
6112    -------------------
6113
6114    procedure Resolve_Range (N : Node_Id; Typ : Entity_Id) is
6115       L : constant Node_Id := Low_Bound (N);
6116       H : constant Node_Id := High_Bound (N);
6117
6118    begin
6119       Set_Etype (N, Typ);
6120       Resolve (L, Typ);
6121       Resolve (H, Typ);
6122
6123       Check_Unset_Reference (L);
6124       Check_Unset_Reference (H);
6125
6126       --  We have to check the bounds for being within the base range as
6127       --  required for a non-static context. Normally this is automatic and
6128       --  done as part of evaluating expressions, but the N_Range node is an
6129       --  exception, since in GNAT we consider this node to be a subexpression,
6130       --  even though in Ada it is not. The circuit in Sem_Eval could check for
6131       --  this, but that would put the test on the main evaluation path for
6132       --  expressions.
6133
6134       Check_Non_Static_Context (L);
6135       Check_Non_Static_Context (H);
6136
6137       --  If bounds are static, constant-fold them, so size computations
6138       --  are identical between front-end and back-end. Do not perform this
6139       --  transformation while analyzing generic units, as type information
6140       --  would then be lost when reanalyzing the constant node in the
6141       --  instance.
6142
6143       if Is_Discrete_Type (Typ) and then Expander_Active then
6144          if Is_OK_Static_Expression (L) then
6145             Fold_Uint  (L, Expr_Value (L), Is_Static_Expression (L));
6146          end if;
6147
6148          if Is_OK_Static_Expression (H) then
6149             Fold_Uint  (H, Expr_Value (H), Is_Static_Expression (H));
6150          end if;
6151       end if;
6152    end Resolve_Range;
6153
6154    --------------------------
6155    -- Resolve_Real_Literal --
6156    --------------------------
6157
6158    procedure Resolve_Real_Literal (N : Node_Id; Typ : Entity_Id) is
6159       Actual_Typ : constant Entity_Id := Etype (N);
6160
6161    begin
6162       --  Special processing for fixed-point literals to make sure that the
6163       --  value is an exact multiple of small where this is required. We
6164       --  skip this for the universal real case, and also for generic types.
6165
6166       if Is_Fixed_Point_Type (Typ)
6167         and then Typ /= Universal_Fixed
6168         and then Typ /= Any_Fixed
6169         and then not Is_Generic_Type (Typ)
6170       then
6171          declare
6172             Val   : constant Ureal := Realval (N);
6173             Cintr : constant Ureal := Val / Small_Value (Typ);
6174             Cint  : constant Uint  := UR_Trunc (Cintr);
6175             Den   : constant Uint  := Norm_Den (Cintr);
6176             Stat  : Boolean;
6177
6178          begin
6179             --  Case of literal is not an exact multiple of the Small
6180
6181             if Den /= 1 then
6182
6183                --  For a source program literal for a decimal fixed-point
6184                --  type, this is statically illegal (RM 4.9(36)).
6185
6186                if Is_Decimal_Fixed_Point_Type (Typ)
6187                  and then Actual_Typ = Universal_Real
6188                  and then Comes_From_Source (N)
6189                then
6190                   Error_Msg_N ("value has extraneous low order digits", N);
6191                end if;
6192
6193                --  Generate a warning if literal from source
6194
6195                if Is_Static_Expression (N)
6196                  and then Warn_On_Bad_Fixed_Value
6197                then
6198                   Error_Msg_N
6199                     ("static fixed-point value is not a multiple of Small?",
6200                      N);
6201                end if;
6202
6203                --  Replace literal by a value that is the exact representation
6204                --  of a value of the type, i.e. a multiple of the small value,
6205                --  by truncation, since Machine_Rounds is false for all GNAT
6206                --  fixed-point types (RM 4.9(38)).
6207
6208                Stat := Is_Static_Expression (N);
6209                Rewrite (N,
6210                  Make_Real_Literal (Sloc (N),
6211                    Realval => Small_Value (Typ) * Cint));
6212
6213                Set_Is_Static_Expression (N, Stat);
6214             end if;
6215
6216             --  In all cases, set the corresponding integer field
6217
6218             Set_Corresponding_Integer_Value (N, Cint);
6219          end;
6220       end if;
6221
6222       --  Now replace the actual type by the expected type as usual
6223
6224       Set_Etype (N, Typ);
6225       Eval_Real_Literal (N);
6226    end Resolve_Real_Literal;
6227
6228    -----------------------
6229    -- Resolve_Reference --
6230    -----------------------
6231
6232    procedure Resolve_Reference (N : Node_Id; Typ : Entity_Id) is
6233       P : constant Node_Id := Prefix (N);
6234
6235    begin
6236       --  Replace general access with specific type
6237
6238       if Ekind (Etype (N)) = E_Allocator_Type then
6239          Set_Etype (N, Base_Type (Typ));
6240       end if;
6241
6242       Resolve (P, Designated_Type (Etype (N)));
6243
6244       --  If we are taking the reference of a volatile entity, then treat
6245       --  it as a potential modification of this entity. This is much too
6246       --  conservative, but is necessary because remove side effects can
6247       --  result in transformations of normal assignments into reference
6248       --  sequences that otherwise fail to notice the modification.
6249
6250       if Is_Entity_Name (P) and then Treat_As_Volatile (Entity (P)) then
6251          Note_Possible_Modification (P);
6252       end if;
6253    end Resolve_Reference;
6254
6255    --------------------------------
6256    -- Resolve_Selected_Component --
6257    --------------------------------
6258
6259    procedure Resolve_Selected_Component (N : Node_Id; Typ : Entity_Id) is
6260       Comp  : Entity_Id;
6261       Comp1 : Entity_Id        := Empty; -- prevent junk warning
6262       P     : constant Node_Id := Prefix  (N);
6263       S     : constant Node_Id := Selector_Name (N);
6264       T     : Entity_Id        := Etype (P);
6265       I     : Interp_Index;
6266       I1    : Interp_Index := 0; -- prevent junk warning
6267       It    : Interp;
6268       It1   : Interp;
6269       Found : Boolean;
6270
6271       function Init_Component return Boolean;
6272       --  Check whether this is the initialization of a component within an
6273       --  init proc (by assignment or call to another init proc). If true,
6274       --  there is no need for a discriminant check.
6275
6276       --------------------
6277       -- Init_Component --
6278       --------------------
6279
6280       function Init_Component return Boolean is
6281       begin
6282          return Inside_Init_Proc
6283            and then Nkind (Prefix (N)) = N_Identifier
6284            and then Chars (Prefix (N)) = Name_uInit
6285            and then Nkind (Parent (Parent (N))) = N_Case_Statement_Alternative;
6286       end Init_Component;
6287
6288    --  Start of processing for Resolve_Selected_Component
6289
6290    begin
6291       if Is_Overloaded (P) then
6292
6293          --  Use the context type to select the prefix that has a selector
6294          --  of the correct name and type.
6295
6296          Found := False;
6297          Get_First_Interp (P, I, It);
6298
6299          Search : while Present (It.Typ) loop
6300             if Is_Access_Type (It.Typ) then
6301                T := Designated_Type (It.Typ);
6302             else
6303                T := It.Typ;
6304             end if;
6305
6306             if Is_Record_Type (T) then
6307                Comp := First_Entity (T);
6308                while Present (Comp) loop
6309                   if Chars (Comp) = Chars (S)
6310                     and then Covers (Etype (Comp), Typ)
6311                   then
6312                      if not Found then
6313                         Found := True;
6314                         I1  := I;
6315                         It1 := It;
6316                         Comp1 := Comp;
6317
6318                      else
6319                         It := Disambiguate (P, I1, I, Any_Type);
6320
6321                         if It = No_Interp then
6322                            Error_Msg_N
6323                              ("ambiguous prefix for selected component",  N);
6324                            Set_Etype (N, Typ);
6325                            return;
6326
6327                         else
6328                            It1 := It;
6329
6330                            --  There may be an implicit dereference. Retrieve
6331                            --  designated record type.
6332
6333                            if Is_Access_Type (It1.Typ) then
6334                               T := Designated_Type (It1.Typ);
6335                            else
6336                               T := It1.Typ;
6337                            end if;
6338
6339                            if Scope (Comp1) /= T then
6340
6341                               --  Resolution chooses the new interpretation.
6342                               --  Find the component with the right name.
6343
6344                               Comp1 := First_Entity (T);
6345                               while Present (Comp1)
6346                                 and then Chars (Comp1) /= Chars (S)
6347                               loop
6348                                  Comp1 := Next_Entity (Comp1);
6349                               end loop;
6350                            end if;
6351
6352                            exit Search;
6353                         end if;
6354                      end if;
6355                   end if;
6356
6357                   Comp := Next_Entity (Comp);
6358                end loop;
6359
6360             end if;
6361
6362             Get_Next_Interp (I, It);
6363          end loop Search;
6364
6365          Resolve (P, It1.Typ);
6366          Set_Etype (N, Typ);
6367          Set_Entity_With_Style_Check (S, Comp1);
6368
6369       else
6370          --  Resolve prefix with its type
6371
6372          Resolve (P, T);
6373       end if;
6374
6375       --  Generate cross-reference. We needed to wait until full overloading
6376       --  resolution was complete to do this, since otherwise we can't tell if
6377       --  we are an Lvalue of not.
6378
6379       if May_Be_Lvalue (N) then
6380          Generate_Reference (Entity (S), S, 'm');
6381       else
6382          Generate_Reference (Entity (S), S, 'r');
6383       end if;
6384
6385       --  If prefix is an access type, the node will be transformed into an
6386       --  explicit dereference during expansion. The type of the node is the
6387       --  designated type of that of the prefix.
6388
6389       if Is_Access_Type (Etype (P)) then
6390          T := Designated_Type (Etype (P));
6391          Check_Fully_Declared_Prefix (T, P);
6392       else
6393          T := Etype (P);
6394       end if;
6395
6396       if Has_Discriminants (T)
6397         and then (Ekind (Entity (S)) = E_Component
6398                    or else
6399                   Ekind (Entity (S)) = E_Discriminant)
6400         and then Present (Original_Record_Component (Entity (S)))
6401         and then Ekind (Original_Record_Component (Entity (S))) = E_Component
6402         and then Present (Discriminant_Checking_Func
6403                            (Original_Record_Component (Entity (S))))
6404         and then not Discriminant_Checks_Suppressed (T)
6405         and then not Init_Component
6406       then
6407          Set_Do_Discriminant_Check (N);
6408       end if;
6409
6410       if Ekind (Entity (S)) = E_Void then
6411          Error_Msg_N ("premature use of component", S);
6412       end if;
6413
6414       --  If the prefix is a record conversion, this may be a renamed
6415       --  discriminant whose bounds differ from those of the original
6416       --  one, so we must ensure that a range check is performed.
6417
6418       if Nkind (P) = N_Type_Conversion
6419         and then Ekind (Entity (S)) = E_Discriminant
6420         and then Is_Discrete_Type (Typ)
6421       then
6422          Set_Etype (N, Base_Type (Typ));
6423       end if;
6424
6425       --  Note: No Eval processing is required, because the prefix is of a
6426       --  record type, or protected type, and neither can possibly be static.
6427
6428    end Resolve_Selected_Component;
6429
6430    -------------------
6431    -- Resolve_Shift --
6432    -------------------
6433
6434    procedure Resolve_Shift (N : Node_Id; Typ : Entity_Id) is
6435       B_Typ : constant Entity_Id := Base_Type (Typ);
6436       L     : constant Node_Id   := Left_Opnd  (N);
6437       R     : constant Node_Id   := Right_Opnd (N);
6438
6439    begin
6440       --  We do the resolution using the base type, because intermediate values
6441       --  in expressions always are of the base type, not a subtype of it.
6442
6443       Resolve (L, B_Typ);
6444       Resolve (R, Standard_Natural);
6445
6446       Check_Unset_Reference (L);
6447       Check_Unset_Reference (R);
6448
6449       Set_Etype (N, B_Typ);
6450       Generate_Operator_Reference (N, B_Typ);
6451       Eval_Shift (N);
6452    end Resolve_Shift;
6453
6454    ---------------------------
6455    -- Resolve_Short_Circuit --
6456    ---------------------------
6457
6458    procedure Resolve_Short_Circuit (N : Node_Id; Typ : Entity_Id) is
6459       B_Typ : constant Entity_Id := Base_Type (Typ);
6460       L     : constant Node_Id   := Left_Opnd  (N);
6461       R     : constant Node_Id   := Right_Opnd (N);
6462
6463    begin
6464       Resolve (L, B_Typ);
6465       Resolve (R, B_Typ);
6466
6467       Check_Unset_Reference (L);
6468       Check_Unset_Reference (R);
6469
6470       Set_Etype (N, B_Typ);
6471       Eval_Short_Circuit (N);
6472    end Resolve_Short_Circuit;
6473
6474    -------------------
6475    -- Resolve_Slice --
6476    -------------------
6477
6478    procedure Resolve_Slice (N : Node_Id; Typ : Entity_Id) is
6479       Name       : constant Node_Id := Prefix (N);
6480       Drange     : constant Node_Id := Discrete_Range (N);
6481       Array_Type : Entity_Id        := Empty;
6482       Index      : Node_Id;
6483
6484    begin
6485       if Is_Overloaded (Name) then
6486
6487          --  Use the context type to select the prefix that yields the
6488          --  correct array type.
6489
6490          declare
6491             I      : Interp_Index;
6492             I1     : Interp_Index := 0;
6493             It     : Interp;
6494             P      : constant Node_Id := Prefix (N);
6495             Found  : Boolean := False;
6496
6497          begin
6498             Get_First_Interp (P, I,  It);
6499             while Present (It.Typ) loop
6500                if (Is_Array_Type (It.Typ)
6501                     and then Covers (Typ,  It.Typ))
6502                  or else (Is_Access_Type (It.Typ)
6503                            and then Is_Array_Type (Designated_Type (It.Typ))
6504                            and then Covers (Typ, Designated_Type (It.Typ)))
6505                then
6506                   if Found then
6507                      It := Disambiguate (P, I1, I, Any_Type);
6508
6509                      if It = No_Interp then
6510                         Error_Msg_N ("ambiguous prefix for slicing",  N);
6511                         Set_Etype (N, Typ);
6512                         return;
6513                      else
6514                         Found := True;
6515                         Array_Type := It.Typ;
6516                         I1 := I;
6517                      end if;
6518                   else
6519                      Found := True;
6520                      Array_Type := It.Typ;
6521                      I1 := I;
6522                   end if;
6523                end if;
6524
6525                Get_Next_Interp (I, It);
6526             end loop;
6527          end;
6528
6529       else
6530          Array_Type := Etype (Name);
6531       end if;
6532
6533       Resolve (Name, Array_Type);
6534
6535       if Is_Access_Type (Array_Type) then
6536          Apply_Access_Check (N);
6537          Array_Type := Designated_Type (Array_Type);
6538
6539          --  If the prefix is an access to an unconstrained array, we must use
6540          --  the actual subtype of the object to perform the index checks. The
6541          --  object denoted by the prefix is implicit in the node, so we build
6542          --  an explicit representation for it in order to compute the actual
6543          --  subtype.
6544
6545          if not Is_Constrained (Array_Type) then
6546             Remove_Side_Effects (Prefix (N));
6547
6548             declare
6549                Obj : constant Node_Id :=
6550                        Make_Explicit_Dereference (Sloc (N),
6551                          Prefix => New_Copy_Tree (Prefix (N)));
6552             begin
6553                Set_Etype (Obj, Array_Type);
6554                Set_Parent (Obj, Parent (N));
6555                Array_Type := Get_Actual_Subtype (Obj);
6556             end;
6557          end if;
6558
6559       elsif Is_Entity_Name (Name)
6560         or else (Nkind (Name) = N_Function_Call
6561                   and then not Is_Constrained (Etype (Name)))
6562       then
6563          Array_Type := Get_Actual_Subtype (Name);
6564       end if;
6565
6566       --  If name was overloaded, set slice type correctly now
6567
6568       Set_Etype (N, Array_Type);
6569
6570       --  If the range is specified by a subtype mark, no resolution is
6571       --  necessary. Else resolve the bounds, and apply needed checks.
6572
6573       if not Is_Entity_Name (Drange) then
6574          Index := First_Index (Array_Type);
6575          Resolve (Drange, Base_Type (Etype (Index)));
6576
6577          if Nkind (Drange) = N_Range
6578
6579             --  Do not apply the range check to nodes associated with the
6580             --  frontend expansion of the dispatch table. We first check
6581             --  if Ada.Tags is already loaded to void the addition of an
6582             --  undesired dependence on such run-time unit.
6583
6584            and then not
6585              (RTU_Loaded (Ada_Tags)
6586               and then Nkind (Prefix (N)) = N_Selected_Component
6587               and then Present (Entity (Selector_Name (Prefix (N))))
6588               and then Entity (Selector_Name (Prefix (N)))
6589                          = RTE_Record_Component (RE_Prims_Ptr))
6590          then
6591             Apply_Range_Check (Drange, Etype (Index));
6592          end if;
6593       end if;
6594
6595       Set_Slice_Subtype (N);
6596
6597       if Nkind (Drange) = N_Range then
6598          Warn_On_Suspicious_Index (Name, Low_Bound  (Drange));
6599          Warn_On_Suspicious_Index (Name, High_Bound (Drange));
6600       end if;
6601
6602       Eval_Slice (N);
6603    end Resolve_Slice;
6604
6605    ----------------------------
6606    -- Resolve_String_Literal --
6607    ----------------------------
6608
6609    procedure Resolve_String_Literal (N : Node_Id; Typ : Entity_Id) is
6610       C_Typ      : constant Entity_Id  := Component_Type (Typ);
6611       R_Typ      : constant Entity_Id  := Root_Type (C_Typ);
6612       Loc        : constant Source_Ptr := Sloc (N);
6613       Str        : constant String_Id  := Strval (N);
6614       Strlen     : constant Nat        := String_Length (Str);
6615       Subtype_Id : Entity_Id;
6616       Need_Check : Boolean;
6617
6618    begin
6619       --  For a string appearing in a concatenation, defer creation of the
6620       --  string_literal_subtype until the end of the resolution of the
6621       --  concatenation, because the literal may be constant-folded away. This
6622       --  is a useful optimization for long concatenation expressions.
6623
6624       --  If the string is an aggregate built for a single character (which
6625       --  happens in a non-static context) or a is null string to which special
6626       --  checks may apply, we build the subtype. Wide strings must also get a
6627       --  string subtype if they come from a one character aggregate. Strings
6628       --  generated by attributes might be static, but it is often hard to
6629       --  determine whether the enclosing context is static, so we generate
6630       --  subtypes for them as well, thus losing some rarer optimizations ???
6631       --  Same for strings that come from a static conversion.
6632
6633       Need_Check :=
6634         (Strlen = 0 and then Typ /= Standard_String)
6635           or else Nkind (Parent (N)) /= N_Op_Concat
6636           or else (N /= Left_Opnd (Parent (N))
6637                     and then N /= Right_Opnd (Parent (N)))
6638           or else ((Typ = Standard_Wide_String
6639                       or else Typ = Standard_Wide_Wide_String)
6640                     and then Nkind (Original_Node (N)) /= N_String_Literal);
6641
6642       --  If the resolving type is itself a string literal subtype, we
6643       --  can just reuse it, since there is no point in creating another.
6644
6645       if Ekind (Typ) = E_String_Literal_Subtype then
6646          Subtype_Id := Typ;
6647
6648       elsif Nkind (Parent (N)) = N_Op_Concat
6649         and then not Need_Check
6650         and then Nkind (Original_Node (N)) /= N_Character_Literal
6651         and then Nkind (Original_Node (N)) /= N_Attribute_Reference
6652         and then Nkind (Original_Node (N)) /= N_Qualified_Expression
6653         and then Nkind (Original_Node (N)) /= N_Type_Conversion
6654       then
6655          Subtype_Id := Typ;
6656
6657       --  Otherwise we must create a string literal subtype. Note that the
6658       --  whole idea of string literal subtypes is simply to avoid the need
6659       --  for building a full fledged array subtype for each literal.
6660       else
6661          Set_String_Literal_Subtype (N, Typ);
6662          Subtype_Id := Etype (N);
6663       end if;
6664
6665       if Nkind (Parent (N)) /= N_Op_Concat
6666         or else Need_Check
6667       then
6668          Set_Etype (N, Subtype_Id);
6669          Eval_String_Literal (N);
6670       end if;
6671
6672       if Is_Limited_Composite (Typ)
6673         or else Is_Private_Composite (Typ)
6674       then
6675          Error_Msg_N ("string literal not available for private array", N);
6676          Set_Etype (N, Any_Type);
6677          return;
6678       end if;
6679
6680       --  The validity of a null string has been checked in the
6681       --  call to  Eval_String_Literal.
6682
6683       if Strlen = 0 then
6684          return;
6685
6686       --  Always accept string literal with component type Any_Character, which
6687       --  occurs in error situations and in comparisons of literals, both of
6688       --  which should accept all literals.
6689
6690       elsif R_Typ = Any_Character then
6691          return;
6692
6693       --  If the type is bit-packed, then we always tranform the string literal
6694       --  into a full fledged aggregate.
6695
6696       elsif Is_Bit_Packed_Array (Typ) then
6697          null;
6698
6699       --  Deal with cases of Wide_Wide_String, Wide_String, and String
6700
6701       else
6702          --  For Standard.Wide_Wide_String, or any other type whose component
6703          --  type is Standard.Wide_Wide_Character, we know that all the
6704          --  characters in the string must be acceptable, since the parser
6705          --  accepted the characters as valid character literals.
6706
6707          if R_Typ = Standard_Wide_Wide_Character then
6708             null;
6709
6710          --  For the case of Standard.String, or any other type whose component
6711          --  type is Standard.Character, we must make sure that there are no
6712          --  wide characters in the string, i.e. that it is entirely composed
6713          --  of characters in range of type Character.
6714
6715          --  If the string literal is the result of a static concatenation, the
6716          --  test has already been performed on the components, and need not be
6717          --  repeated.
6718
6719          elsif R_Typ = Standard_Character
6720            and then Nkind (Original_Node (N)) /= N_Op_Concat
6721          then
6722             for J in 1 .. Strlen loop
6723                if not In_Character_Range (Get_String_Char (Str, J)) then
6724
6725                   --  If we are out of range, post error. This is one of the
6726                   --  very few places that we place the flag in the middle of
6727                   --  a token, right under the offending wide character.
6728
6729                   Error_Msg
6730                     ("literal out of range of type Standard.Character",
6731                      Source_Ptr (Int (Loc) + J));
6732                   return;
6733                end if;
6734             end loop;
6735
6736          --  For the case of Standard.Wide_String, or any other type whose
6737          --  component type is Standard.Wide_Character, we must make sure that
6738          --  there are no wide characters in the string, i.e. that it is
6739          --  entirely composed of characters in range of type Wide_Character.
6740
6741          --  If the string literal is the result of a static concatenation,
6742          --  the test has already been performed on the components, and need
6743          --  not be repeated.
6744
6745          elsif R_Typ = Standard_Wide_Character
6746            and then Nkind (Original_Node (N)) /= N_Op_Concat
6747          then
6748             for J in 1 .. Strlen loop
6749                if not In_Wide_Character_Range (Get_String_Char (Str, J)) then
6750
6751                   --  If we are out of range, post error. This is one of the
6752                   --  very few places that we place the flag in the middle of
6753                   --  a token, right under the offending wide character.
6754
6755                   --  This is not quite right, because characters in general
6756                   --  will take more than one character position ???
6757
6758                   Error_Msg
6759                     ("literal out of range of type Standard.Wide_Character",
6760                      Source_Ptr (Int (Loc) + J));
6761                   return;
6762                end if;
6763             end loop;
6764
6765          --  If the root type is not a standard character, then we will convert
6766          --  the string into an aggregate and will let the aggregate code do
6767          --  the checking. Standard Wide_Wide_Character is also OK here.
6768
6769          else
6770             null;
6771          end if;
6772
6773          --  See if the component type of the array corresponding to the string
6774          --  has compile time known bounds. If yes we can directly check
6775          --  whether the evaluation of the string will raise constraint error.
6776          --  Otherwise we need to transform the string literal into the
6777          --  corresponding character aggregate and let the aggregate
6778          --  code do the checking.
6779
6780          if R_Typ = Standard_Character
6781            or else R_Typ = Standard_Wide_Character
6782            or else R_Typ = Standard_Wide_Wide_Character
6783          then
6784             --  Check for the case of full range, where we are definitely OK
6785
6786             if Component_Type (Typ) = Base_Type (Component_Type (Typ)) then
6787                return;
6788             end if;
6789
6790             --  Here the range is not the complete base type range, so check
6791
6792             declare
6793                Comp_Typ_Lo : constant Node_Id :=
6794                                Type_Low_Bound (Component_Type (Typ));
6795                Comp_Typ_Hi : constant Node_Id :=
6796                                Type_High_Bound (Component_Type (Typ));
6797
6798                Char_Val : Uint;
6799
6800             begin
6801                if Compile_Time_Known_Value (Comp_Typ_Lo)
6802                  and then Compile_Time_Known_Value (Comp_Typ_Hi)
6803                then
6804                   for J in 1 .. Strlen loop
6805                      Char_Val := UI_From_Int (Int (Get_String_Char (Str, J)));
6806
6807                      if Char_Val < Expr_Value (Comp_Typ_Lo)
6808                        or else Char_Val > Expr_Value (Comp_Typ_Hi)
6809                      then
6810                         Apply_Compile_Time_Constraint_Error
6811                           (N, "character out of range?", CE_Range_Check_Failed,
6812                            Loc => Source_Ptr (Int (Loc) + J));
6813                      end if;
6814                   end loop;
6815
6816                   return;
6817                end if;
6818             end;
6819          end if;
6820       end if;
6821
6822       --  If we got here we meed to transform the string literal into the
6823       --  equivalent qualified positional array aggregate. This is rather
6824       --  heavy artillery for this situation, but it is hard work to avoid.
6825
6826       declare
6827          Lits : constant List_Id    := New_List;
6828          P    : Source_Ptr := Loc + 1;
6829          C    : Char_Code;
6830
6831       begin
6832          --  Build the character literals, we give them source locations that
6833          --  correspond to the string positions, which is a bit tricky given
6834          --  the possible presence of wide character escape sequences.
6835
6836          for J in 1 .. Strlen loop
6837             C := Get_String_Char (Str, J);
6838             Set_Character_Literal_Name (C);
6839
6840             Append_To (Lits,
6841               Make_Character_Literal (P,
6842                 Chars              => Name_Find,
6843                 Char_Literal_Value => UI_From_CC (C)));
6844
6845             if In_Character_Range (C) then
6846                P := P + 1;
6847
6848             --  Should we have a call to Skip_Wide here ???
6849             --  ???     else
6850             --             Skip_Wide (P);
6851
6852             end if;
6853          end loop;
6854
6855          Rewrite (N,
6856            Make_Qualified_Expression (Loc,
6857              Subtype_Mark => New_Reference_To (Typ, Loc),
6858              Expression   =>
6859                Make_Aggregate (Loc, Expressions => Lits)));
6860
6861          Analyze_And_Resolve (N, Typ);
6862       end;
6863    end Resolve_String_Literal;
6864
6865    -----------------------------
6866    -- Resolve_Subprogram_Info --
6867    -----------------------------
6868
6869    procedure Resolve_Subprogram_Info (N : Node_Id; Typ : Entity_Id) is
6870    begin
6871       Set_Etype (N, Typ);
6872    end Resolve_Subprogram_Info;
6873
6874    -----------------------------
6875    -- Resolve_Type_Conversion --
6876    -----------------------------
6877
6878    procedure Resolve_Type_Conversion (N : Node_Id; Typ : Entity_Id) is
6879       Conv_OK     : constant Boolean := Conversion_OK (N);
6880       Target_Type : Entity_Id := Etype (N);
6881       Operand     : Node_Id;
6882       Opnd_Type   : Entity_Id;
6883       Rop         : Node_Id;
6884       Orig_N      : Node_Id;
6885       Orig_T      : Node_Id;
6886
6887    begin
6888       Operand := Expression (N);
6889
6890       if not Conv_OK
6891         and then not Valid_Conversion (N, Target_Type, Operand)
6892       then
6893          return;
6894       end if;
6895
6896       if Etype (Operand) = Any_Fixed then
6897
6898          --  Mixed-mode operation involving a literal. Context must be a fixed
6899          --  type which is applied to the literal subsequently.
6900
6901          if Is_Fixed_Point_Type (Typ) then
6902             Set_Etype (Operand, Universal_Real);
6903
6904          elsif Is_Numeric_Type (Typ)
6905            and then (Nkind (Operand) = N_Op_Multiply
6906                       or else Nkind (Operand) = N_Op_Divide)
6907            and then (Etype (Right_Opnd (Operand)) = Universal_Real
6908                      or else Etype (Left_Opnd (Operand)) = Universal_Real)
6909          then
6910             --  Return if expression is ambiguous
6911
6912             if Unique_Fixed_Point_Type (N) = Any_Type then
6913                return;
6914
6915             --  If nothing else, the available fixed type is Duration
6916
6917             else
6918                Set_Etype (Operand, Standard_Duration);
6919             end if;
6920
6921             --  Resolve the real operand with largest available precision
6922
6923             if Etype (Right_Opnd (Operand)) = Universal_Real then
6924                Rop := New_Copy_Tree (Right_Opnd (Operand));
6925             else
6926                Rop := New_Copy_Tree (Left_Opnd (Operand));
6927             end if;
6928
6929             Resolve (Rop, Universal_Real);
6930
6931             --  If the operand is a literal (it could be a non-static and
6932             --  illegal exponentiation) check whether the use of Duration
6933             --  is potentially inaccurate.
6934
6935             if Nkind (Rop) = N_Real_Literal
6936               and then Realval (Rop) /= Ureal_0
6937               and then abs (Realval (Rop)) < Delta_Value (Standard_Duration)
6938             then
6939                Error_Msg_N
6940                  ("universal real operand can only " &
6941                   "be interpreted as Duration?",
6942                   Rop);
6943                Error_Msg_N
6944                  ("\precision will be lost in the conversion", Rop);
6945             end if;
6946
6947          elsif Is_Numeric_Type (Typ)
6948            and then Nkind (Operand) in N_Op
6949            and then Unique_Fixed_Point_Type (N) /= Any_Type
6950          then
6951             Set_Etype (Operand, Standard_Duration);
6952
6953          else
6954             Error_Msg_N ("invalid context for mixed mode operation", N);
6955             Set_Etype (Operand, Any_Type);
6956             return;
6957          end if;
6958       end if;
6959
6960       Opnd_Type := Etype (Operand);
6961       Resolve (Operand);
6962
6963       --  Note: we do the Eval_Type_Conversion call before applying the
6964       --  required checks for a subtype conversion. This is important,
6965       --  since both are prepared under certain circumstances to change
6966       --  the type conversion to a constraint error node, but in the case
6967       --  of Eval_Type_Conversion this may reflect an illegality in the
6968       --  static case, and we would miss the illegality (getting only a
6969       --  warning message), if we applied the type conversion checks first.
6970
6971       Eval_Type_Conversion (N);
6972
6973       --  Even when evaluation is not possible, we may be able to simplify
6974       --  the conversion or its expression. This needs to be done before
6975       --  applying checks, since otherwise the checks may use the original
6976       --  expression and defeat the simplifications. The is specifically
6977       --  the case for elimination of the floating-point Truncation
6978       --  attribute in float-to-int conversions.
6979
6980       Simplify_Type_Conversion (N);
6981
6982       --  If after evaluation, we still have a type conversion, then we
6983       --  may need to apply checks required for a subtype conversion.
6984
6985       --  Skip these type conversion checks if universal fixed operands
6986       --  operands involved, since range checks are handled separately for
6987       --  these cases (in the appropriate Expand routines in unit Exp_Fixd).
6988
6989       if Nkind (N) = N_Type_Conversion
6990         and then not Is_Generic_Type (Root_Type (Target_Type))
6991         and then Target_Type /= Universal_Fixed
6992         and then Opnd_Type /= Universal_Fixed
6993       then
6994          Apply_Type_Conversion_Checks (N);
6995       end if;
6996
6997       --  Issue warning for conversion of simple object to its own type
6998       --  We have to test the original nodes, since they may have been
6999       --  rewritten by various optimizations.
7000
7001       Orig_N := Original_Node (N);
7002
7003       if Warn_On_Redundant_Constructs
7004         and then Comes_From_Source (Orig_N)
7005         and then Nkind (Orig_N) = N_Type_Conversion
7006         and then not In_Instance
7007       then
7008          Orig_N := Original_Node (Expression (Orig_N));
7009          Orig_T := Target_Type;
7010
7011          --  If the node is part of a larger expression, the Target_Type
7012          --  may not be the original type of the node if the context is a
7013          --  condition. Recover original type to see if conversion is needed.
7014
7015          if Is_Boolean_Type (Orig_T)
7016           and then Nkind (Parent (N)) in N_Op
7017          then
7018             Orig_T := Etype (Parent (N));
7019          end if;
7020
7021          if Is_Entity_Name (Orig_N)
7022            and then Etype (Entity (Orig_N)) = Orig_T
7023          then
7024             Error_Msg_NE
7025               ("?useless conversion, & has this type", N, Entity (Orig_N));
7026          end if;
7027       end if;
7028
7029       --  Ada 2005 (AI-251): Handle conversions to abstract interface types
7030       --  No need to perform any interface conversion if the type of the
7031       --  expression coincides with the target type.
7032
7033       if Ada_Version >= Ada_05
7034         and then Expander_Active
7035         and then Opnd_Type /= Target_Type
7036       then
7037          if Is_Access_Type (Target_Type) then
7038             Target_Type := Directly_Designated_Type (Target_Type);
7039          end if;
7040
7041          if Is_Class_Wide_Type (Target_Type) then
7042             Target_Type := Etype (Target_Type);
7043          end if;
7044
7045          if Is_Interface (Target_Type) then
7046             if Is_Access_Type (Opnd_Type) then
7047                Opnd_Type := Directly_Designated_Type (Opnd_Type);
7048             end if;
7049
7050             if Is_Class_Wide_Type (Opnd_Type) then
7051                Opnd_Type := Etype (Opnd_Type);
7052             end if;
7053
7054             --  Handle subtypes
7055
7056             if Ekind (Opnd_Type) = E_Protected_Subtype
7057               or else Ekind (Opnd_Type) = E_Task_Subtype
7058             then
7059                Opnd_Type := Etype (Opnd_Type);
7060             end if;
7061
7062             if not Interface_Present_In_Ancestor
7063                      (Typ   => Opnd_Type,
7064                       Iface => Target_Type)
7065             then
7066                --  The static analysis is not enough to know if the interface
7067                --  is implemented or not. Hence we must pass the work to the
7068                --  expander to generate the required code to evaluate the
7069                --  conversion at run-time.
7070
7071                Expand_Interface_Conversion (N, Is_Static => False);
7072
7073             else
7074                Expand_Interface_Conversion (N);
7075             end if;
7076
7077          --  Ada 2005 (AI-251): Conversion from a class-wide interface to a
7078          --  tagged type
7079
7080          elsif Is_Class_Wide_Type (Opnd_Type)
7081             and then Is_Interface (Opnd_Type)
7082          then
7083             Expand_Interface_Conversion (N, Is_Static => False);
7084          end if;
7085       end if;
7086    end Resolve_Type_Conversion;
7087
7088    ----------------------
7089    -- Resolve_Unary_Op --
7090    ----------------------
7091
7092    procedure Resolve_Unary_Op (N : Node_Id; Typ : Entity_Id) is
7093       B_Typ : constant Entity_Id := Base_Type (Typ);
7094       R     : constant Node_Id   := Right_Opnd (N);
7095       OK    : Boolean;
7096       Lo    : Uint;
7097       Hi    : Uint;
7098
7099    begin
7100       --  Deal with intrincis unary operators
7101
7102       if Comes_From_Source (N)
7103         and then Ekind (Entity (N)) = E_Function
7104         and then Is_Imported (Entity (N))
7105         and then Is_Intrinsic_Subprogram (Entity (N))
7106       then
7107          Resolve_Intrinsic_Unary_Operator (N, Typ);
7108          return;
7109       end if;
7110
7111       --  Deal with universal cases
7112
7113       if Etype (R) = Universal_Integer
7114            or else
7115          Etype (R) = Universal_Real
7116       then
7117          Check_For_Visible_Operator (N, B_Typ);
7118       end if;
7119
7120       Set_Etype (N, B_Typ);
7121       Resolve (R, B_Typ);
7122
7123       --  Generate warning for expressions like abs (x mod 2)
7124
7125       if Warn_On_Redundant_Constructs
7126         and then Nkind (N) = N_Op_Abs
7127       then
7128          Determine_Range (Right_Opnd (N), OK, Lo, Hi);
7129
7130          if OK and then Hi >= Lo and then Lo >= 0 then
7131             Error_Msg_N
7132              ("?abs applied to known non-negative value has no effect", N);
7133          end if;
7134       end if;
7135
7136       --  Deal with reference generation
7137
7138       Check_Unset_Reference (R);
7139       Generate_Operator_Reference (N, B_Typ);
7140       Eval_Unary_Op (N);
7141
7142       --  Set overflow checking bit. Much cleverer code needed here eventually
7143       --  and perhaps the Resolve routines should be separated for the various
7144       --  arithmetic operations, since they will need different processing ???
7145
7146       if Nkind (N) in N_Op then
7147          if not Overflow_Checks_Suppressed (Etype (N)) then
7148             Enable_Overflow_Check (N);
7149          end if;
7150       end if;
7151
7152       --  Generate warning for expressions like -5 mod 3 for integers. No
7153       --  need to worry in the floating-point case, since parens do not affect
7154       --  the result so there is no point in giving in a warning.
7155
7156       declare
7157          Norig : constant Node_Id := Original_Node (N);
7158          Rorig : Node_Id;
7159          Val   : Uint;
7160          HB    : Uint;
7161          LB    : Uint;
7162          Lval  : Uint;
7163          Opnd  : Node_Id;
7164
7165       begin
7166          if Warn_On_Questionable_Missing_Parens
7167            and then Comes_From_Source (Norig)
7168            and then Is_Integer_Type (Typ)
7169            and then Nkind (Norig) = N_Op_Minus
7170          then
7171             Rorig := Original_Node (Right_Opnd (Norig));
7172
7173             --  We are looking for cases where the right operand is not
7174             --  parenthesized, and is a bianry operator, multiply, divide, or
7175             --  mod. These are the cases where the grouping can affect results.
7176
7177             if Paren_Count (Rorig) = 0
7178               and then (Nkind (Rorig) = N_Op_Mod
7179                           or else
7180                         Nkind (Rorig) = N_Op_Multiply
7181                           or else
7182                         Nkind (Rorig) = N_Op_Divide)
7183             then
7184                --  For mod, we always give the warning, since the value is
7185                --  affected by the parenthesization (e.g. (-5) mod 315 /=
7186                --  (5 mod 315)). But for the other cases, the only concern is
7187                --  overflow, e.g. for the case of 8 big signed (-(2 * 64)
7188                --  overflows, but (-2) * 64 does not). So we try to give the
7189                --  message only when overflow is possible.
7190
7191                if Nkind (Rorig) /= N_Op_Mod
7192                  and then Compile_Time_Known_Value (R)
7193                then
7194                   Val := Expr_Value (R);
7195
7196                   if Compile_Time_Known_Value (Type_High_Bound (Typ)) then
7197                      HB := Expr_Value (Type_High_Bound (Typ));
7198                   else
7199                      HB := Expr_Value (Type_High_Bound (Base_Type (Typ)));
7200                   end if;
7201
7202                   if Compile_Time_Known_Value (Type_Low_Bound (Typ)) then
7203                      LB := Expr_Value (Type_Low_Bound (Typ));
7204                   else
7205                      LB := Expr_Value (Type_Low_Bound (Base_Type (Typ)));
7206                   end if;
7207
7208                   --  Note that the test below is deliberately excluding
7209                   --  the largest negative number, since that is a potentially
7210                   --  troublesome case (e.g. -2 * x, where the result is the
7211                   --  largest negative integer has an overflow with 2 * x).
7212
7213                   if Val > LB and then Val <= HB then
7214                      return;
7215                   end if;
7216                end if;
7217
7218                --  For the multiplication case, the only case we have to worry
7219                --  about is when (-a)*b is exactly the largest negative number
7220                --  so that -(a*b) can cause overflow. This can only happen if
7221                --  a is a power of 2, and more generally if any operand is a
7222                --  constant that is not a power of 2, then the parentheses
7223                --  cannot affect whether overflow occurs. We only bother to
7224                --  test the left most operand
7225
7226                --  Loop looking at left operands for one that has known value
7227
7228                Opnd := Rorig;
7229                Opnd_Loop : while Nkind (Opnd) = N_Op_Multiply loop
7230                   if Compile_Time_Known_Value (Left_Opnd (Opnd)) then
7231                      Lval := UI_Abs (Expr_Value (Left_Opnd (Opnd)));
7232
7233                      --  Operand value of 0 or 1 skips warning
7234
7235                      if Lval <= 1 then
7236                         return;
7237
7238                      --  Otherwise check power of 2, if power of 2, warn, if
7239                      --  anything else, skip warning.
7240
7241                      else
7242                         while Lval /= 2 loop
7243                            if Lval mod 2 = 1 then
7244                               return;
7245                            else
7246                               Lval := Lval / 2;
7247                            end if;
7248                         end loop;
7249
7250                         exit Opnd_Loop;
7251                      end if;
7252                   end if;
7253
7254                   --  Keep looking at left operands
7255
7256                   Opnd := Left_Opnd (Opnd);
7257                end loop Opnd_Loop;
7258
7259                --  For rem or "/" we can only have a problematic situation
7260                --  if the divisor has a value of minus one or one. Otherwise
7261                --  overflow is impossible (divisor > 1) or we have a case of
7262                --  division by zero in any case.
7263
7264                if (Nkind (Rorig) = N_Op_Divide
7265                     or else
7266                    Nkind (Rorig) = N_Op_Rem)
7267                  and then Compile_Time_Known_Value (Right_Opnd (Rorig))
7268                  and then UI_Abs (Expr_Value (Right_Opnd (Rorig))) /= 1
7269                then
7270                   return;
7271                end if;
7272
7273                --  If we fall through warning should be issued
7274
7275                Error_Msg_N
7276                  ("?unary minus expression should be parenthesized here", N);
7277             end if;
7278          end if;
7279       end;
7280    end Resolve_Unary_Op;
7281
7282    ----------------------------------
7283    -- Resolve_Unchecked_Expression --
7284    ----------------------------------
7285
7286    procedure Resolve_Unchecked_Expression
7287      (N   : Node_Id;
7288       Typ : Entity_Id)
7289    is
7290    begin
7291       Resolve (Expression (N), Typ, Suppress => All_Checks);
7292       Set_Etype (N, Typ);
7293    end Resolve_Unchecked_Expression;
7294
7295    ---------------------------------------
7296    -- Resolve_Unchecked_Type_Conversion --
7297    ---------------------------------------
7298
7299    procedure Resolve_Unchecked_Type_Conversion
7300      (N   : Node_Id;
7301       Typ : Entity_Id)
7302    is
7303       pragma Warnings (Off, Typ);
7304
7305       Operand   : constant Node_Id   := Expression (N);
7306       Opnd_Type : constant Entity_Id := Etype (Operand);
7307
7308    begin
7309       --  Resolve operand using its own type
7310
7311       Resolve (Operand, Opnd_Type);
7312       Eval_Unchecked_Conversion (N);
7313
7314    end Resolve_Unchecked_Type_Conversion;
7315
7316    ------------------------------
7317    -- Rewrite_Operator_As_Call --
7318    ------------------------------
7319
7320    procedure Rewrite_Operator_As_Call (N : Node_Id; Nam : Entity_Id) is
7321       Loc     : constant Source_Ptr := Sloc (N);
7322       Actuals : constant List_Id    := New_List;
7323       New_N   : Node_Id;
7324
7325    begin
7326       if Nkind (N) in  N_Binary_Op then
7327          Append (Left_Opnd (N), Actuals);
7328       end if;
7329
7330       Append (Right_Opnd (N), Actuals);
7331
7332       New_N :=
7333         Make_Function_Call (Sloc => Loc,
7334           Name => New_Occurrence_Of (Nam, Loc),
7335           Parameter_Associations => Actuals);
7336
7337       Preserve_Comes_From_Source (New_N, N);
7338       Preserve_Comes_From_Source (Name (New_N), N);
7339       Rewrite (N, New_N);
7340       Set_Etype (N, Etype (Nam));
7341    end Rewrite_Operator_As_Call;
7342
7343    ------------------------------
7344    -- Rewrite_Renamed_Operator --
7345    ------------------------------
7346
7347    procedure Rewrite_Renamed_Operator
7348      (N   : Node_Id;
7349       Op  : Entity_Id;
7350       Typ : Entity_Id)
7351    is
7352       Nam       : constant Name_Id := Chars (Op);
7353       Is_Binary : constant Boolean := Nkind (N) in N_Binary_Op;
7354       Op_Node   : Node_Id;
7355
7356    begin
7357       --  Rewrite the operator node using the real operator, not its
7358       --  renaming. Exclude user-defined intrinsic operations of the same
7359       --  name, which are treated separately and rewritten as calls.
7360
7361       if Ekind (Op) /= E_Function
7362         or else Chars (N) /= Nam
7363       then
7364          Op_Node := New_Node (Operator_Kind (Nam, Is_Binary), Sloc (N));
7365          Set_Chars      (Op_Node, Nam);
7366          Set_Etype      (Op_Node, Etype (N));
7367          Set_Entity     (Op_Node, Op);
7368          Set_Right_Opnd (Op_Node, Right_Opnd (N));
7369
7370          --  Indicate that both the original entity and its renaming
7371          --  are referenced at this point.
7372
7373          Generate_Reference (Entity (N), N);
7374          Generate_Reference (Op, N);
7375
7376          if Is_Binary then
7377             Set_Left_Opnd  (Op_Node, Left_Opnd  (N));
7378          end if;
7379
7380          Rewrite (N, Op_Node);
7381
7382          --  If the context type is private, add the appropriate conversions
7383          --  so that the operator is applied to the full view. This is done
7384          --  in the routines that resolve intrinsic operators,
7385
7386          if Is_Intrinsic_Subprogram (Op)
7387            and then Is_Private_Type (Typ)
7388          then
7389             case Nkind (N) is
7390                when N_Op_Add   | N_Op_Subtract | N_Op_Multiply | N_Op_Divide |
7391                     N_Op_Expon | N_Op_Mod      | N_Op_Rem      =>
7392                   Resolve_Intrinsic_Operator (N, Typ);
7393
7394                when N_Op_Plus | N_Op_Minus    | N_Op_Abs      =>
7395                   Resolve_Intrinsic_Unary_Operator (N, Typ);
7396
7397                when others =>
7398                   Resolve (N, Typ);
7399             end case;
7400          end if;
7401
7402       elsif Ekind (Op) = E_Function
7403         and then Is_Intrinsic_Subprogram (Op)
7404       then
7405          --  Operator renames a user-defined operator of the same name. Use
7406          --  the original operator in the node, which is the one that gigi
7407          --  knows about.
7408
7409          Set_Entity (N, Op);
7410          Set_Is_Overloaded (N, False);
7411       end if;
7412    end Rewrite_Renamed_Operator;
7413
7414    -----------------------
7415    -- Set_Slice_Subtype --
7416    -----------------------
7417
7418    --  Build an implicit subtype declaration to represent the type delivered
7419    --  by the slice. This is an abbreviated version of an array subtype. We
7420    --  define an index subtype for the slice,  using either the subtype name
7421    --  or the discrete range of the slice. To be consistent with index usage
7422    --  elsewhere, we create a list header to hold the single index. This list
7423    --  is not otherwise attached to the syntax tree.
7424
7425    procedure Set_Slice_Subtype (N : Node_Id) is
7426       Loc           : constant Source_Ptr := Sloc (N);
7427       Index_List    : constant List_Id    := New_List;
7428       Index         : Node_Id;
7429       Index_Subtype : Entity_Id;
7430       Index_Type    : Entity_Id;
7431       Slice_Subtype : Entity_Id;
7432       Drange        : constant Node_Id := Discrete_Range (N);
7433
7434    begin
7435       if Is_Entity_Name (Drange) then
7436          Index_Subtype := Entity (Drange);
7437
7438       else
7439          --  We force the evaluation of a range. This is definitely needed in
7440          --  the renamed case, and seems safer to do unconditionally. Note in
7441          --  any case that since we will create and insert an Itype referring
7442          --  to this range, we must make sure any side effect removal actions
7443          --  are inserted before the Itype definition.
7444
7445          if Nkind (Drange) = N_Range then
7446             Force_Evaluation (Low_Bound (Drange));
7447             Force_Evaluation (High_Bound (Drange));
7448          end if;
7449
7450          Index_Type := Base_Type (Etype (Drange));
7451
7452          Index_Subtype := Create_Itype (Subtype_Kind (Ekind (Index_Type)), N);
7453
7454          Set_Scalar_Range (Index_Subtype, Drange);
7455          Set_Etype        (Index_Subtype, Index_Type);
7456          Set_Size_Info    (Index_Subtype, Index_Type);
7457          Set_RM_Size      (Index_Subtype, RM_Size (Index_Type));
7458       end if;
7459
7460       Slice_Subtype := Create_Itype (E_Array_Subtype, N);
7461
7462       Index := New_Occurrence_Of (Index_Subtype, Loc);
7463       Set_Etype (Index, Index_Subtype);
7464       Append (Index, Index_List);
7465
7466       Set_First_Index    (Slice_Subtype, Index);
7467       Set_Etype          (Slice_Subtype, Base_Type (Etype (N)));
7468       Set_Is_Constrained (Slice_Subtype, True);
7469       Init_Size_Align    (Slice_Subtype);
7470
7471       Check_Compile_Time_Size (Slice_Subtype);
7472
7473       --  The Etype of the existing Slice node is reset to this slice
7474       --  subtype. Its bounds are obtained from its first index.
7475
7476       Set_Etype (N, Slice_Subtype);
7477
7478       --  In the packed case, this must be immediately frozen
7479
7480       --  Couldn't we always freeze here??? and if we did, then the above
7481       --  call to Check_Compile_Time_Size could be eliminated, which would
7482       --  be nice, because then that routine could be made private to Freeze.
7483
7484       if Is_Packed (Slice_Subtype) and not In_Default_Expression then
7485          Freeze_Itype (Slice_Subtype, N);
7486       end if;
7487
7488    end Set_Slice_Subtype;
7489
7490    --------------------------------
7491    -- Set_String_Literal_Subtype --
7492    --------------------------------
7493
7494    procedure Set_String_Literal_Subtype (N : Node_Id; Typ : Entity_Id) is
7495       Loc        : constant Source_Ptr := Sloc (N);
7496       Low_Bound  : constant Node_Id :=
7497                         Type_Low_Bound (Etype (First_Index (Typ)));
7498       Subtype_Id : Entity_Id;
7499
7500    begin
7501       if Nkind (N) /= N_String_Literal then
7502          return;
7503       end if;
7504
7505       Subtype_Id := Create_Itype (E_String_Literal_Subtype, N);
7506       Set_String_Literal_Length (Subtype_Id, UI_From_Int
7507                                                (String_Length (Strval (N))));
7508       Set_Etype          (Subtype_Id, Base_Type (Typ));
7509       Set_Is_Constrained (Subtype_Id);
7510       Set_Etype          (N, Subtype_Id);
7511
7512       if Is_OK_Static_Expression (Low_Bound) then
7513
7514       --  The low bound is set from the low bound of the corresponding
7515       --  index type. Note that we do not store the high bound in the
7516       --  string literal subtype, but it can be deduced if necessary
7517       --  from the length and the low bound.
7518
7519          Set_String_Literal_Low_Bound (Subtype_Id, Low_Bound);
7520
7521       else
7522          Set_String_Literal_Low_Bound
7523            (Subtype_Id, Make_Integer_Literal (Loc, 1));
7524          Set_Etype (String_Literal_Low_Bound (Subtype_Id), Standard_Positive);
7525
7526          --  Build bona fide subtypes for the string, and wrap it in an
7527          --  unchecked conversion, because the backend expects  the
7528          --  String_Literal_Subtype to have a static lower bound.
7529
7530          declare
7531             Index_List    : constant List_Id    := New_List;
7532             Index_Type    : constant Entity_Id := Etype (First_Index (Typ));
7533             High_Bound    : constant Node_Id :=
7534                                Make_Op_Add (Loc,
7535                                   Left_Opnd => New_Copy_Tree (Low_Bound),
7536                                   Right_Opnd =>
7537                                     Make_Integer_Literal (Loc,
7538                                       String_Length (Strval (N)) - 1));
7539             Array_Subtype : Entity_Id;
7540             Index_Subtype : Entity_Id;
7541             Drange        : Node_Id;
7542             Index         : Node_Id;
7543
7544          begin
7545             Index_Subtype :=
7546               Create_Itype (Subtype_Kind (Ekind (Index_Type)), N);
7547             Drange := Make_Range (Loc, New_Copy_Tree (Low_Bound), High_Bound);
7548             Set_Scalar_Range (Index_Subtype, Drange);
7549             Set_Parent (Drange, N);
7550             Analyze_And_Resolve (Drange, Index_Type);
7551
7552             Set_Etype        (Index_Subtype, Index_Type);
7553             Set_Size_Info    (Index_Subtype, Index_Type);
7554             Set_RM_Size      (Index_Subtype, RM_Size (Index_Type));
7555
7556             Array_Subtype := Create_Itype (E_Array_Subtype, N);
7557
7558             Index := New_Occurrence_Of (Index_Subtype, Loc);
7559             Set_Etype (Index, Index_Subtype);
7560             Append (Index, Index_List);
7561
7562             Set_First_Index    (Array_Subtype, Index);
7563             Set_Etype          (Array_Subtype, Base_Type (Typ));
7564             Set_Is_Constrained (Array_Subtype, True);
7565             Init_Size_Align    (Array_Subtype);
7566
7567             Rewrite (N,
7568               Make_Unchecked_Type_Conversion (Loc,
7569                 Subtype_Mark => New_Occurrence_Of (Array_Subtype, Loc),
7570                 Expression => Relocate_Node (N)));
7571             Set_Etype (N, Array_Subtype);
7572          end;
7573       end if;
7574    end Set_String_Literal_Subtype;
7575
7576    ------------------------------
7577    -- Simplify_Type_Conversion --
7578    ------------------------------
7579
7580    procedure Simplify_Type_Conversion (N : Node_Id) is
7581    begin
7582       if Nkind (N) = N_Type_Conversion then
7583          declare
7584             Operand    : constant Node_Id   := Expression (N);
7585             Target_Typ : constant Entity_Id := Etype (N);
7586             Opnd_Typ   : constant Entity_Id := Etype (Operand);
7587
7588          begin
7589             if Is_Floating_Point_Type (Opnd_Typ)
7590               and then
7591                 (Is_Integer_Type (Target_Typ)
7592                    or else (Is_Fixed_Point_Type (Target_Typ)
7593                               and then Conversion_OK (N)))
7594               and then Nkind (Operand) = N_Attribute_Reference
7595               and then Attribute_Name (Operand) = Name_Truncation
7596
7597             --  Special processing required if the conversion is the expression
7598             --  of a Truncation attribute reference. In this case we replace:
7599
7600             --     ityp (ftyp'Truncation (x))
7601
7602             --  by
7603
7604             --     ityp (x)
7605
7606             --  with the Float_Truncate flag set, which is more efficient
7607
7608             then
7609                Rewrite (Operand,
7610                  Relocate_Node (First (Expressions (Operand))));
7611                Set_Float_Truncate (N, True);
7612             end if;
7613          end;
7614       end if;
7615    end Simplify_Type_Conversion;
7616
7617    -----------------------------
7618    -- Unique_Fixed_Point_Type --
7619    -----------------------------
7620
7621    function Unique_Fixed_Point_Type (N : Node_Id) return Entity_Id is
7622       T1   : Entity_Id := Empty;
7623       T2   : Entity_Id;
7624       Item : Node_Id;
7625       Scop : Entity_Id;
7626
7627       procedure Fixed_Point_Error;
7628       --  If true ambiguity, give details
7629
7630       -----------------------
7631       -- Fixed_Point_Error --
7632       -----------------------
7633
7634       procedure Fixed_Point_Error is
7635       begin
7636          Error_Msg_N ("ambiguous universal_fixed_expression", N);
7637          Error_Msg_NE ("\\possible interpretation as}", N, T1);
7638          Error_Msg_NE ("\\possible interpretation as}", N, T2);
7639       end Fixed_Point_Error;
7640
7641    --  Start of processing for Unique_Fixed_Point_Type
7642
7643    begin
7644       --  The operations on Duration are visible, so Duration is always a
7645       --  possible interpretation.
7646
7647       T1 := Standard_Duration;
7648
7649       --  Look for fixed-point types in enclosing scopes
7650
7651       Scop := Current_Scope;
7652       while Scop /= Standard_Standard loop
7653          T2 := First_Entity (Scop);
7654          while Present (T2) loop
7655             if Is_Fixed_Point_Type (T2)
7656               and then Current_Entity (T2) = T2
7657               and then Scope (Base_Type (T2)) = Scop
7658             then
7659                if Present (T1) then
7660                   Fixed_Point_Error;
7661                   return Any_Type;
7662                else
7663                   T1 := T2;
7664                end if;
7665             end if;
7666
7667             Next_Entity (T2);
7668          end loop;
7669
7670          Scop := Scope (Scop);
7671       end loop;
7672
7673       --  Look for visible fixed type declarations in the context
7674
7675       Item := First (Context_Items (Cunit (Current_Sem_Unit)));
7676       while Present (Item) loop
7677          if Nkind (Item) = N_With_Clause then
7678             Scop := Entity (Name (Item));
7679             T2 := First_Entity (Scop);
7680             while Present (T2) loop
7681                if Is_Fixed_Point_Type (T2)
7682                  and then Scope (Base_Type (T2)) = Scop
7683                  and then (Is_Potentially_Use_Visible (T2)
7684                              or else In_Use (T2))
7685                then
7686                   if Present (T1) then
7687                      Fixed_Point_Error;
7688                      return Any_Type;
7689                   else
7690                      T1 := T2;
7691                   end if;
7692                end if;
7693
7694                Next_Entity (T2);
7695             end loop;
7696          end if;
7697
7698          Next (Item);
7699       end loop;
7700
7701       if Nkind (N) = N_Real_Literal then
7702          Error_Msg_NE ("real literal interpreted as }?", N, T1);
7703
7704       else
7705          Error_Msg_NE ("universal_fixed expression interpreted as }?", N, T1);
7706       end if;
7707
7708       return T1;
7709    end Unique_Fixed_Point_Type;
7710
7711    ----------------------
7712    -- Valid_Conversion --
7713    ----------------------
7714
7715    function Valid_Conversion
7716      (N       : Node_Id;
7717       Target  : Entity_Id;
7718       Operand : Node_Id) return Boolean
7719    is
7720       Target_Type : constant Entity_Id := Base_Type (Target);
7721       Opnd_Type   : Entity_Id := Etype (Operand);
7722
7723       function Conversion_Check
7724         (Valid : Boolean;
7725          Msg   : String) return Boolean;
7726       --  Little routine to post Msg if Valid is False, returns Valid value
7727
7728       function Valid_Tagged_Conversion
7729         (Target_Type : Entity_Id;
7730          Opnd_Type   : Entity_Id) return Boolean;
7731       --  Specifically test for validity of tagged conversions
7732
7733       function Valid_Array_Conversion return Boolean;
7734       --  Check index and component conformance, and accessibility levels
7735       --  if the component types are anonymous access types (Ada 2005)
7736
7737       ----------------------
7738       -- Conversion_Check --
7739       ----------------------
7740
7741       function Conversion_Check
7742         (Valid : Boolean;
7743          Msg   : String) return Boolean
7744       is
7745       begin
7746          if not Valid then
7747             Error_Msg_N (Msg, Operand);
7748          end if;
7749
7750          return Valid;
7751       end Conversion_Check;
7752
7753       ----------------------------
7754       -- Valid_Array_Conversion --
7755       ----------------------------
7756
7757       function Valid_Array_Conversion return Boolean
7758       is
7759          Opnd_Comp_Type : constant Entity_Id := Component_Type (Opnd_Type);
7760          Opnd_Comp_Base : constant Entity_Id := Base_Type (Opnd_Comp_Type);
7761
7762          Opnd_Index      : Node_Id;
7763          Opnd_Index_Type : Entity_Id;
7764
7765          Target_Comp_Type : constant Entity_Id :=
7766                               Component_Type (Target_Type);
7767          Target_Comp_Base : constant Entity_Id :=
7768                               Base_Type (Target_Comp_Type);
7769
7770          Target_Index      : Node_Id;
7771          Target_Index_Type : Entity_Id;
7772
7773       begin
7774          --  Error if wrong number of dimensions
7775
7776          if
7777            Number_Dimensions (Target_Type) /= Number_Dimensions (Opnd_Type)
7778          then
7779             Error_Msg_N
7780               ("incompatible number of dimensions for conversion", Operand);
7781             return False;
7782
7783          --  Number of dimensions matches
7784
7785          else
7786             --  Loop through indexes of the two arrays
7787
7788             Target_Index := First_Index (Target_Type);
7789             Opnd_Index   := First_Index (Opnd_Type);
7790             while Present (Target_Index) and then Present (Opnd_Index) loop
7791                Target_Index_Type := Etype (Target_Index);
7792                Opnd_Index_Type   := Etype (Opnd_Index);
7793
7794                --  Error if index types are incompatible
7795
7796                if not (Is_Integer_Type (Target_Index_Type)
7797                        and then Is_Integer_Type (Opnd_Index_Type))
7798                  and then (Root_Type (Target_Index_Type)
7799                            /= Root_Type (Opnd_Index_Type))
7800                then
7801                   Error_Msg_N
7802                     ("incompatible index types for array conversion",
7803                      Operand);
7804                   return False;
7805                end if;
7806
7807                Next_Index (Target_Index);
7808                Next_Index (Opnd_Index);
7809             end loop;
7810
7811             --  If component types have same base type, all set
7812
7813             if Target_Comp_Base  = Opnd_Comp_Base then
7814                null;
7815
7816                --  Here if base types of components are not the same. The only
7817                --  time this is allowed is if we have anonymous access types.
7818
7819                --  The conversion of arrays of anonymous access types can lead
7820                --  to dangling pointers. AI-392 formalizes the accessibility
7821                --  checks that must be applied to such conversions to prevent
7822                --  out-of-scope references.
7823
7824             elsif
7825               (Ekind (Target_Comp_Base) = E_Anonymous_Access_Type
7826                  or else
7827                Ekind (Target_Comp_Base) = E_Anonymous_Access_Subprogram_Type)
7828               and then Ekind (Opnd_Comp_Base) = Ekind (Target_Comp_Base)
7829               and then
7830                 Subtypes_Statically_Match (Target_Comp_Type, Opnd_Comp_Type)
7831             then
7832                if Type_Access_Level (Target_Type) <
7833                    Type_Access_Level (Opnd_Type)
7834                then
7835                   if In_Instance_Body then
7836                      Error_Msg_N ("?source array type " &
7837                        "has deeper accessibility level than target", Operand);
7838                      Error_Msg_N ("\?Program_Error will be raised at run time",
7839                          Operand);
7840                      Rewrite (N,
7841                        Make_Raise_Program_Error (Sloc (N),
7842                          Reason => PE_Accessibility_Check_Failed));
7843                      Set_Etype (N, Target_Type);
7844                      return False;
7845
7846                   --  Conversion not allowed because of accessibility levels
7847
7848                   else
7849                      Error_Msg_N ("source array type " &
7850                        "has deeper accessibility level than target", Operand);
7851                      return False;
7852                   end if;
7853                else
7854                   null;
7855                end if;
7856
7857             --  All other cases where component base types do not match
7858
7859             else
7860                Error_Msg_N
7861                  ("incompatible component types for array conversion",
7862                   Operand);
7863                return False;
7864             end if;
7865
7866             --  Check that component subtypes statically match
7867
7868             if Is_Constrained (Target_Comp_Type) /=
7869                  Is_Constrained (Opnd_Comp_Type)
7870               or else not Subtypes_Statically_Match
7871                             (Target_Comp_Type, Opnd_Comp_Type)
7872             then
7873                Error_Msg_N
7874                  ("component subtypes must statically match", Operand);
7875                return False;
7876             end if;
7877          end if;
7878
7879          return True;
7880       end Valid_Array_Conversion;
7881
7882       -----------------------------
7883       -- Valid_Tagged_Conversion --
7884       -----------------------------
7885
7886       function Valid_Tagged_Conversion
7887         (Target_Type : Entity_Id;
7888          Opnd_Type   : Entity_Id) return Boolean
7889       is
7890       begin
7891          --  Upward conversions are allowed (RM 4.6(22))
7892
7893          if Covers (Target_Type, Opnd_Type)
7894            or else Is_Ancestor (Target_Type, Opnd_Type)
7895          then
7896             return True;
7897
7898          --  Downward conversion are allowed if the operand is class-wide
7899          --  (RM 4.6(23)).
7900
7901          elsif Is_Class_Wide_Type (Opnd_Type)
7902               and then Covers (Opnd_Type, Target_Type)
7903          then
7904             return True;
7905
7906          elsif Covers (Opnd_Type, Target_Type)
7907            or else Is_Ancestor (Opnd_Type, Target_Type)
7908          then
7909             return
7910               Conversion_Check (False,
7911                 "downward conversion of tagged objects not allowed");
7912
7913          --  Ada 2005 (AI-251): The conversion to/from interface types is
7914          --  always valid
7915
7916          elsif Is_Interface (Target_Type) or else Is_Interface (Opnd_Type) then
7917             return True;
7918
7919          elsif Is_Access_Type (Opnd_Type)
7920            and then Is_Interface (Directly_Designated_Type (Opnd_Type))
7921          then
7922             return True;
7923
7924          else
7925             Error_Msg_NE
7926               ("invalid tagged conversion, not compatible with}",
7927                N, First_Subtype (Opnd_Type));
7928             return False;
7929          end if;
7930       end Valid_Tagged_Conversion;
7931
7932    --  Start of processing for Valid_Conversion
7933
7934    begin
7935       Check_Parameterless_Call (Operand);
7936
7937       if Is_Overloaded (Operand) then
7938          declare
7939             I   : Interp_Index;
7940             I1  : Interp_Index;
7941             It  : Interp;
7942             It1 : Interp;
7943             N1  : Entity_Id;
7944
7945          begin
7946             --  Remove procedure calls, which syntactically cannot appear
7947             --  in this context, but which cannot be removed by type checking,
7948             --  because the context does not impose a type.
7949
7950             --  When compiling for VMS, spurious ambiguities can be produced
7951             --  when arithmetic operations have a literal operand and return
7952             --  System.Address or a descendant of it. These ambiguities are
7953             --  otherwise resolved by the context, but for conversions there
7954             --  is no context type and the removal of the spurious operations
7955             --  must be done explicitly here.
7956
7957             --  The node may be labelled overloaded, but still contain only
7958             --  one interpretation because others were discarded in previous
7959             --  filters. If this is the case, retain the single interpretation
7960             --  if legal.
7961
7962             Get_First_Interp (Operand, I, It);
7963             Opnd_Type := It.Typ;
7964             Get_Next_Interp (I, It);
7965
7966             if Present (It.Typ)
7967               and then Opnd_Type /= Standard_Void_Type
7968             then
7969                --  More than one candidate interpretation is available
7970
7971                Get_First_Interp (Operand, I, It);
7972                while Present (It.Typ) loop
7973                   if It.Typ = Standard_Void_Type then
7974                      Remove_Interp (I);
7975                   end if;
7976
7977                   if Present (System_Aux_Id)
7978                     and then Is_Descendent_Of_Address (It.Typ)
7979                   then
7980                      Remove_Interp (I);
7981                   end if;
7982
7983                   Get_Next_Interp (I, It);
7984                end loop;
7985             end if;
7986
7987             Get_First_Interp (Operand, I, It);
7988             I1  := I;
7989             It1 := It;
7990
7991             if No (It.Typ) then
7992                Error_Msg_N ("illegal operand in conversion", Operand);
7993                return False;
7994             end if;
7995
7996             Get_Next_Interp (I, It);
7997
7998             if Present (It.Typ) then
7999                N1  := It1.Nam;
8000                It1 :=  Disambiguate (Operand, I1, I, Any_Type);
8001
8002                if It1 = No_Interp then
8003                   Error_Msg_N ("ambiguous operand in conversion", Operand);
8004
8005                   Error_Msg_Sloc := Sloc (It.Nam);
8006                   Error_Msg_N ("\\possible interpretation#!", Operand);
8007
8008                   Error_Msg_Sloc := Sloc (N1);
8009                   Error_Msg_N ("\\possible interpretation#!", Operand);
8010
8011                   return False;
8012                end if;
8013             end if;
8014
8015             Set_Etype (Operand, It1.Typ);
8016             Opnd_Type := It1.Typ;
8017          end;
8018       end if;
8019
8020       --  Numeric types
8021
8022       if Is_Numeric_Type (Target_Type)  then
8023
8024          --  A universal fixed expression can be converted to any numeric type
8025
8026          if Opnd_Type = Universal_Fixed then
8027             return True;
8028
8029          --  Also no need to check when in an instance or inlined body, because
8030          --  the legality has been established when the template was analyzed.
8031          --  Furthermore, numeric conversions may occur where only a private
8032          --  view of the operand type is visible at the instanciation point.
8033          --  This results in a spurious error if we check that the operand type
8034          --  is a numeric type.
8035
8036          --  Note: in a previous version of this unit, the following tests were
8037          --  applied only for generated code (Comes_From_Source set to False),
8038          --  but in fact the test is required for source code as well, since
8039          --  this situation can arise in source code.
8040
8041          elsif In_Instance or else In_Inlined_Body then
8042                return True;
8043
8044          --  Otherwise we need the conversion check
8045
8046          else
8047             return Conversion_Check
8048                     (Is_Numeric_Type (Opnd_Type),
8049                      "illegal operand for numeric conversion");
8050          end if;
8051
8052       --  Array types
8053
8054       elsif Is_Array_Type (Target_Type) then
8055          if not Is_Array_Type (Opnd_Type)
8056            or else Opnd_Type = Any_Composite
8057            or else Opnd_Type = Any_String
8058          then
8059             Error_Msg_N
8060               ("illegal operand for array conversion", Operand);
8061             return False;
8062          else
8063             return Valid_Array_Conversion;
8064          end if;
8065
8066       --  Anonymous access types where target references an interface
8067
8068       elsif (Ekind (Target_Type) = E_General_Access_Type
8069               or else
8070              Ekind (Target_Type) = E_Anonymous_Access_Type)
8071         and then Is_Interface (Directly_Designated_Type (Target_Type))
8072       then
8073          --  Check the static accessibility rule of 4.6(17). Note that the
8074          --  check is not enforced when within an instance body, since the RM
8075          --  requires such cases to be caught at run time.
8076
8077          if Ekind (Target_Type) /= E_Anonymous_Access_Type then
8078             if Type_Access_Level (Opnd_Type) >
8079                Type_Access_Level (Target_Type)
8080             then
8081                --  In an instance, this is a run-time check, but one we know
8082                --  will fail, so generate an appropriate warning. The raise
8083                --  will be generated by Expand_N_Type_Conversion.
8084
8085                if In_Instance_Body then
8086                   Error_Msg_N
8087                     ("?cannot convert local pointer to non-local access type",
8088                      Operand);
8089                   Error_Msg_N
8090                     ("\?Program_Error will be raised at run time", Operand);
8091                else
8092                   Error_Msg_N
8093                     ("cannot convert local pointer to non-local access type",
8094                      Operand);
8095                   return False;
8096                end if;
8097
8098             --  Special accessibility checks are needed in the case of access
8099             --  discriminants declared for a limited type.
8100
8101             elsif Ekind (Opnd_Type) = E_Anonymous_Access_Type
8102               and then not Is_Local_Anonymous_Access (Opnd_Type)
8103             then
8104                --  When the operand is a selected access discriminant the check
8105                --  needs to be made against the level of the object denoted by
8106                --  the prefix of the selected name. (Object_Access_Level
8107                --  handles checking the prefix of the operand for this case.)
8108
8109                if Nkind (Operand) = N_Selected_Component
8110                  and then Object_Access_Level (Operand) >
8111                             Type_Access_Level (Target_Type)
8112                then
8113                   --  In an instance, this is a run-time check, but one we
8114                   --  know will fail, so generate an appropriate warning.
8115                   --  The raise will be generated by Expand_N_Type_Conversion.
8116
8117                   if In_Instance_Body then
8118                      Error_Msg_N
8119                        ("?cannot convert access discriminant to non-local" &
8120                         " access type", Operand);
8121                      Error_Msg_N
8122                        ("\?Program_Error will be raised at run time", Operand);
8123                   else
8124                      Error_Msg_N
8125                        ("cannot convert access discriminant to non-local" &
8126                         " access type", Operand);
8127                      return False;
8128                   end if;
8129                end if;
8130
8131                --  The case of a reference to an access discriminant from
8132                --  within a limited type declaration (which will appear as
8133                --  a discriminal) is always illegal because the level of the
8134                --  discriminant is considered to be deeper than any (namable)
8135                --  access type.
8136
8137                if Is_Entity_Name (Operand)
8138                  and then not Is_Local_Anonymous_Access (Opnd_Type)
8139                  and then (Ekind (Entity (Operand)) = E_In_Parameter
8140                             or else Ekind (Entity (Operand)) = E_Constant)
8141                  and then Present (Discriminal_Link (Entity (Operand)))
8142                then
8143                   Error_Msg_N
8144                     ("discriminant has deeper accessibility level than target",
8145                      Operand);
8146                   return False;
8147                end if;
8148             end if;
8149          end if;
8150
8151          return True;
8152
8153       --  General and anonymous access types
8154
8155       elsif (Ekind (Target_Type) = E_General_Access_Type
8156         or else Ekind (Target_Type) = E_Anonymous_Access_Type)
8157           and then
8158             Conversion_Check
8159               (Is_Access_Type (Opnd_Type)
8160                  and then Ekind (Opnd_Type) /=
8161                    E_Access_Subprogram_Type
8162                  and then Ekind (Opnd_Type) /=
8163                    E_Access_Protected_Subprogram_Type,
8164                "must be an access-to-object type")
8165       then
8166          if Is_Access_Constant (Opnd_Type)
8167            and then not Is_Access_Constant (Target_Type)
8168          then
8169             Error_Msg_N
8170               ("access-to-constant operand type not allowed", Operand);
8171             return False;
8172          end if;
8173
8174          --  Check the static accessibility rule of 4.6(17). Note that the
8175          --  check is not enforced when within an instance body, since the RM
8176          --  requires such cases to be caught at run time.
8177
8178          if Ekind (Target_Type) /= E_Anonymous_Access_Type
8179            or else Is_Local_Anonymous_Access (Target_Type)
8180          then
8181             if Type_Access_Level (Opnd_Type)
8182               > Type_Access_Level (Target_Type)
8183             then
8184                --  In an instance, this is a run-time check, but one we
8185                --  know will fail, so generate an appropriate warning.
8186                --  The raise will be generated by Expand_N_Type_Conversion.
8187
8188                if In_Instance_Body then
8189                   Error_Msg_N
8190                     ("?cannot convert local pointer to non-local access type",
8191                      Operand);
8192                   Error_Msg_N
8193                     ("\?Program_Error will be raised at run time", Operand);
8194
8195                else
8196                   Error_Msg_N
8197                     ("cannot convert local pointer to non-local access type",
8198                      Operand);
8199                   return False;
8200                end if;
8201
8202             --  Special accessibility checks are needed in the case of access
8203             --  discriminants declared for a limited type.
8204
8205             elsif Ekind (Opnd_Type) = E_Anonymous_Access_Type
8206               and then not Is_Local_Anonymous_Access (Opnd_Type)
8207             then
8208
8209                --  When the operand is a selected access discriminant the check
8210                --  needs to be made against the level of the object denoted by
8211                --  the prefix of the selected name. (Object_Access_Level
8212                --  handles checking the prefix of the operand for this case.)
8213
8214                if Nkind (Operand) = N_Selected_Component
8215                  and then Object_Access_Level (Operand)
8216                    > Type_Access_Level (Target_Type)
8217                then
8218                   --  In an instance, this is a run-time check, but one we
8219                   --  know will fail, so generate an appropriate warning.
8220                   --  The raise will be generated by Expand_N_Type_Conversion.
8221
8222                   if In_Instance_Body then
8223                      Error_Msg_N
8224                        ("?cannot convert access discriminant to non-local" &
8225                         " access type", Operand);
8226                      Error_Msg_N
8227                        ("\?Program_Error will be raised at run time",
8228                         Operand);
8229
8230                   else
8231                      Error_Msg_N
8232                        ("cannot convert access discriminant to non-local" &
8233                         " access type", Operand);
8234                      return False;
8235                   end if;
8236                end if;
8237
8238                --  The case of a reference to an access discriminant from
8239                --  within a limited type declaration (which will appear as
8240                --  a discriminal) is always illegal because the level of the
8241                --  discriminant is considered to be deeper than any (namable)
8242                --  access type.
8243
8244                if Is_Entity_Name (Operand)
8245                  and then (Ekind (Entity (Operand)) = E_In_Parameter
8246                             or else Ekind (Entity (Operand)) = E_Constant)
8247                  and then Present (Discriminal_Link (Entity (Operand)))
8248                then
8249                   Error_Msg_N
8250                     ("discriminant has deeper accessibility level than target",
8251                      Operand);
8252                   return False;
8253                end if;
8254             end if;
8255          end if;
8256
8257          declare
8258             function Full_Designated_Type (T : Entity_Id) return Entity_Id;
8259             --  Helper function to handle limited views
8260
8261             --------------------------
8262             -- Full_Designated_Type --
8263             --------------------------
8264
8265             function Full_Designated_Type (T : Entity_Id) return Entity_Id is
8266                Desig : constant Entity_Id := Designated_Type (T);
8267             begin
8268                if From_With_Type (Desig)
8269                  and then Is_Incomplete_Type (Desig)
8270                  and then Present (Non_Limited_View (Desig))
8271                then
8272                   return Non_Limited_View (Desig);
8273                else
8274                   return Desig;
8275                end if;
8276             end Full_Designated_Type;
8277
8278             Target : constant Entity_Id := Full_Designated_Type (Target_Type);
8279             Opnd   : constant Entity_Id := Full_Designated_Type (Opnd_Type);
8280
8281             Same_Base : constant Boolean :=
8282                           Base_Type (Target) = Base_Type (Opnd);
8283
8284          begin
8285             if Is_Tagged_Type (Target) then
8286                return Valid_Tagged_Conversion (Target, Opnd);
8287
8288             else
8289                if not Same_Base then
8290                   Error_Msg_NE
8291                     ("target designated type not compatible with }",
8292                      N, Base_Type (Opnd));
8293                   return False;
8294
8295                --  Ada 2005 AI-384: legality rule is symmetric in both
8296                --  designated types. The conversion is legal (with possible
8297                --  constraint check) if either designated type is
8298                --  unconstrained.
8299
8300                elsif Subtypes_Statically_Match (Target, Opnd)
8301                  or else
8302                    (Has_Discriminants (Target)
8303                      and then
8304                       (not Is_Constrained (Opnd)
8305                         or else not Is_Constrained (Target)))
8306                then
8307                   return True;
8308
8309                else
8310                   Error_Msg_NE
8311                     ("target designated subtype not compatible with }",
8312                      N, Opnd);
8313                   return False;
8314                end if;
8315             end if;
8316          end;
8317
8318       --  Subprogram access types
8319
8320       elsif (Ekind (Target_Type) = E_Access_Subprogram_Type
8321                or else
8322              Ekind (Target_Type) = E_Anonymous_Access_Subprogram_Type)
8323         and then No (Corresponding_Remote_Type (Opnd_Type))
8324       then
8325          if
8326            Ekind (Base_Type (Opnd_Type)) = E_Anonymous_Access_Subprogram_Type
8327          then
8328             Error_Msg_N
8329               ("illegal attempt to store anonymous access to subprogram",
8330                Operand);
8331             Error_Msg_N
8332               ("\value has deeper accessibility than any master " &
8333                "('R'M 3.10.2 (13))",
8334                Operand);
8335
8336             if Is_Entity_Name (Operand)
8337               and then Ekind (Entity (Operand)) = E_In_Parameter
8338             then
8339                Error_Msg_NE
8340                  ("\use named access type for& instead of access parameter",
8341                   Operand, Entity (Operand));
8342             end if;
8343          end if;
8344
8345          --  Check that the designated types are subtype conformant
8346
8347          Check_Subtype_Conformant (New_Id  => Designated_Type (Target_Type),
8348                                    Old_Id  => Designated_Type (Opnd_Type),
8349                                    Err_Loc => N);
8350
8351          --  Check the static accessibility rule of 4.6(20)
8352
8353          if Type_Access_Level (Opnd_Type) >
8354             Type_Access_Level (Target_Type)
8355          then
8356             Error_Msg_N
8357               ("operand type has deeper accessibility level than target",
8358                Operand);
8359
8360          --  Check that if the operand type is declared in a generic body,
8361          --  then the target type must be declared within that same body
8362          --  (enforces last sentence of 4.6(20)).
8363
8364          elsif Present (Enclosing_Generic_Body (Opnd_Type)) then
8365             declare
8366                O_Gen : constant Node_Id :=
8367                          Enclosing_Generic_Body (Opnd_Type);
8368
8369                T_Gen : Node_Id;
8370
8371             begin
8372                T_Gen := Enclosing_Generic_Body (Target_Type);
8373                while Present (T_Gen) and then T_Gen /= O_Gen loop
8374                   T_Gen := Enclosing_Generic_Body (T_Gen);
8375                end loop;
8376
8377                if T_Gen /= O_Gen then
8378                   Error_Msg_N
8379                     ("target type must be declared in same generic body"
8380                      & " as operand type", N);
8381                end if;
8382             end;
8383          end if;
8384
8385          return True;
8386
8387       --  Remote subprogram access types
8388
8389       elsif Is_Remote_Access_To_Subprogram_Type (Target_Type)
8390         and then Is_Remote_Access_To_Subprogram_Type (Opnd_Type)
8391       then
8392          --  It is valid to convert from one RAS type to another provided
8393          --  that their specification statically match.
8394
8395          Check_Subtype_Conformant
8396            (New_Id  =>
8397               Designated_Type (Corresponding_Remote_Type (Target_Type)),
8398             Old_Id  =>
8399               Designated_Type (Corresponding_Remote_Type (Opnd_Type)),
8400             Err_Loc =>
8401               N);
8402          return True;
8403
8404       --  Tagged types
8405
8406       elsif Is_Tagged_Type (Target_Type) then
8407          return Valid_Tagged_Conversion (Target_Type, Opnd_Type);
8408
8409       --  Types derived from the same root type are convertible
8410
8411       elsif Root_Type (Target_Type) = Root_Type (Opnd_Type) then
8412          return True;
8413
8414       --  In an instance, there may be inconsistent views of the same
8415       --  type, or types derived from the same type.
8416
8417       elsif In_Instance
8418         and then Underlying_Type (Target_Type) = Underlying_Type (Opnd_Type)
8419       then
8420          return True;
8421
8422       --  Special check for common access type error case
8423
8424       elsif Ekind (Target_Type) = E_Access_Type
8425          and then Is_Access_Type (Opnd_Type)
8426       then
8427          Error_Msg_N ("target type must be general access type!", N);
8428          Error_Msg_NE ("add ALL to }!", N, Target_Type);
8429
8430          return False;
8431
8432       else
8433          Error_Msg_NE ("invalid conversion, not compatible with }",
8434            N, Opnd_Type);
8435
8436          return False;
8437       end if;
8438    end Valid_Conversion;
8439
8440 end Sem_Res;