OSDN Git Service

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