OSDN Git Service

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