OSDN Git Service

2005-11-14 Robert Dewar <dewar@adacore.com>
[pf3gnuchains/gcc-fork.git] / gcc / ada / sem_ch4.adb
1 ------------------------------------------------------------------------------
2 --                                                                          --
3 --                         GNAT COMPILER COMPONENTS                         --
4 --                                                                          --
5 --                              S E M _ C H 4                               --
6 --                                                                          --
7 --                                 B o d y                                  --
8 --                                                                          --
9 --          Copyright (C) 1992-2005, Free Software Foundation, Inc.         --
10 --                                                                          --
11 -- GNAT is free software;  you can  redistribute it  and/or modify it under --
12 -- terms of the  GNU General Public License as published  by the Free Soft- --
13 -- ware  Foundation;  either version 2,  or (at your option) any later ver- --
14 -- sion.  GNAT is distributed in the hope that it will be useful, but WITH- --
15 -- OUT ANY WARRANTY;  without even the  implied warranty of MERCHANTABILITY --
16 -- or FITNESS FOR A PARTICULAR PURPOSE.  See the GNU General Public License --
17 -- for  more details.  You should have  received  a copy of the GNU General --
18 -- Public License  distributed with GNAT;  see file COPYING.  If not, write --
19 -- to  the  Free Software Foundation,  51  Franklin  Street,  Fifth  Floor, --
20 -- Boston, MA 02110-1301, USA.                                              --
21 --                                                                          --
22 -- GNAT was originally developed  by the GNAT team at  New York University. --
23 -- Extensive contributions were provided by Ada Core Technologies Inc.      --
24 --                                                                          --
25 ------------------------------------------------------------------------------
26
27 with Atree;    use Atree;
28 with Debug;    use Debug;
29 with Einfo;    use Einfo;
30 with Elists;   use Elists;
31 with Errout;   use Errout;
32 with Exp_Util; use Exp_Util;
33 with Fname;    use Fname;
34 with Itypes;   use Itypes;
35 with Lib;      use Lib;
36 with Lib.Xref; use Lib.Xref;
37 with Namet;    use Namet;
38 with Nlists;   use Nlists;
39 with Nmake;    use Nmake;
40 with Opt;      use Opt;
41 with Output;   use Output;
42 with Restrict; use Restrict;
43 with Rident;   use Rident;
44 with Sem;      use Sem;
45 with Sem_Cat;  use Sem_Cat;
46 with Sem_Ch3;  use Sem_Ch3;
47 with Sem_Ch8;  use Sem_Ch8;
48 with Sem_Dist; use Sem_Dist;
49 with Sem_Eval; use Sem_Eval;
50 with Sem_Res;  use Sem_Res;
51 with Sem_Util; use Sem_Util;
52 with Sem_Type; use Sem_Type;
53 with Stand;    use Stand;
54 with Sinfo;    use Sinfo;
55 with Snames;   use Snames;
56 with Tbuild;   use Tbuild;
57
58 with GNAT.Spelling_Checker; use GNAT.Spelling_Checker;
59
60 package body Sem_Ch4 is
61
62    -----------------------
63    -- Local Subprograms --
64    -----------------------
65
66    procedure Analyze_Expression (N : Node_Id);
67    --  For expressions that are not names, this is just a call to analyze.
68    --  If the expression is a name, it may be a call to a parameterless
69    --  function, and if so must be converted into an explicit call node
70    --  and analyzed as such. This deproceduring must be done during the first
71    --  pass of overload resolution, because otherwise a procedure call with
72    --  overloaded actuals may fail to resolve. See 4327-001 for an example.
73
74    procedure Analyze_Operator_Call (N : Node_Id; Op_Id : Entity_Id);
75    --  Analyze a call of the form "+"(x, y), etc. The prefix of the call
76    --  is an operator name or an expanded name whose selector is an operator
77    --  name, and one possible interpretation is as a predefined operator.
78
79    procedure Analyze_Overloaded_Selected_Component (N : Node_Id);
80    --  If the prefix of a selected_component is overloaded, the proper
81    --  interpretation that yields a record type with the proper selector
82    --  name must be selected.
83
84    procedure Analyze_User_Defined_Binary_Op (N : Node_Id; Op_Id : Entity_Id);
85    --  Procedure to analyze a user defined binary operator, which is resolved
86    --  like a function, but instead of a list of actuals it is presented
87    --  with the left and right operands of an operator node.
88
89    procedure Analyze_User_Defined_Unary_Op (N : Node_Id; Op_Id : Entity_Id);
90    --  Procedure to analyze a user defined unary operator, which is resolved
91    --  like a function, but instead of a list of actuals, it is presented with
92    --  the operand of the operator node.
93
94    procedure Ambiguous_Operands (N : Node_Id);
95    --  for equality, membership, and comparison operators with overloaded
96    --  arguments, list possible interpretations.
97
98    procedure Analyze_One_Call
99       (N          : Node_Id;
100        Nam        : Entity_Id;
101        Report     : Boolean;
102        Success    : out Boolean;
103        Skip_First : Boolean := False);
104    --  Check one interpretation of an overloaded subprogram name for
105    --  compatibility with the types of the actuals in a call. If there is a
106    --  single interpretation which does not match, post error if Report is
107    --  set to True.
108    --
109    --  Nam is the entity that provides the formals against which the actuals
110    --  are checked. Nam is either the name of a subprogram, or the internal
111    --  subprogram type constructed for an access_to_subprogram. If the actuals
112    --  are compatible with Nam, then Nam is added to the list of candidate
113    --  interpretations for N, and Success is set to True.
114    --
115    --  The flag Skip_First is used when analyzing a call that was rewritten
116    --  from object notation. In this case the first actual may have to receive
117    --  an explicit dereference, depending on the first formal of the operation
118    --  being called. The caller will have verified that the object is legal
119    --  for the call. If the remaining parameters match, the first parameter
120    --  will rewritten as a dereference if needed, prior to completing analysis.
121
122    procedure Check_Misspelled_Selector
123      (Prefix : Entity_Id;
124       Sel    : Node_Id);
125    --  Give possible misspelling diagnostic if Sel is likely to be
126    --  a misspelling of one of the selectors of the Prefix.
127    --  This is called by Analyze_Selected_Component after producing
128    --  an invalid selector error message.
129
130    function Defined_In_Scope (T : Entity_Id; S : Entity_Id) return Boolean;
131    --  Verify that type T is declared in scope S. Used to find intepretations
132    --  for operators given by expanded names. This is abstracted as a separate
133    --  function to handle extensions to System, where S is System, but T is
134    --  declared in the extension.
135
136    procedure Find_Arithmetic_Types
137      (L, R  : Node_Id;
138       Op_Id : Entity_Id;
139       N     : Node_Id);
140    --  L and R are the operands of an arithmetic operator. Find
141    --  consistent pairs of interpretations for L and R that have a
142    --  numeric type consistent with the semantics of the operator.
143
144    procedure Find_Comparison_Types
145      (L, R  : Node_Id;
146       Op_Id : Entity_Id;
147       N     : Node_Id);
148    --  L and R are operands of a comparison operator. Find consistent
149    --  pairs of interpretations for L and R.
150
151    procedure Find_Concatenation_Types
152      (L, R  : Node_Id;
153       Op_Id : Entity_Id;
154       N     : Node_Id);
155    --  For the four varieties of concatenation
156
157    procedure Find_Equality_Types
158      (L, R  : Node_Id;
159       Op_Id : Entity_Id;
160       N     : Node_Id);
161    --  Ditto for equality operators
162
163    procedure Find_Boolean_Types
164      (L, R  : Node_Id;
165       Op_Id : Entity_Id;
166       N     : Node_Id);
167    --  Ditto for binary logical operations
168
169    procedure Find_Negation_Types
170      (R     : Node_Id;
171       Op_Id : Entity_Id;
172       N     : Node_Id);
173    --  Find consistent interpretation for operand of negation operator
174
175    procedure Find_Non_Universal_Interpretations
176      (N     : Node_Id;
177       R     : Node_Id;
178       Op_Id : Entity_Id;
179       T1    : Entity_Id);
180    --  For equality and comparison operators, the result is always boolean,
181    --  and the legality of the operation is determined from the visibility
182    --  of the operand types. If one of the operands has a universal interpre-
183    --  tation,  the legality check uses some compatible non-universal
184    --  interpretation of the other operand. N can be an operator node, or
185    --  a function call whose name is an operator designator.
186
187    procedure Find_Unary_Types
188      (R     : Node_Id;
189       Op_Id : Entity_Id;
190       N     : Node_Id);
191    --  Unary arithmetic types: plus, minus, abs
192
193    procedure Check_Arithmetic_Pair
194      (T1, T2 : Entity_Id;
195       Op_Id  : Entity_Id;
196       N      : Node_Id);
197    --  Subsidiary procedure to Find_Arithmetic_Types. T1 and T2 are valid
198    --  types for left and right operand. Determine whether they constitute
199    --  a valid pair for the given operator, and record the corresponding
200    --  interpretation of the operator node. The node N may be an operator
201    --  node (the usual case) or a function call whose prefix is an operator
202    --  designator. In  both cases Op_Id is the operator name itself.
203
204    procedure Diagnose_Call (N : Node_Id; Nam : Node_Id);
205    --  Give detailed information on overloaded call where none of the
206    --  interpretations match. N is the call node, Nam the designator for
207    --  the overloaded entity being called.
208
209    function Junk_Operand (N : Node_Id) return Boolean;
210    --  Test for an operand that is an inappropriate entity (e.g. a package
211    --  name or a label). If so, issue an error message and return True. If
212    --  the operand is not an inappropriate entity kind, return False.
213
214    procedure Operator_Check (N : Node_Id);
215    --  Verify that an operator has received some valid interpretation. If none
216    --  was found, determine whether a use clause would make the operation
217    --  legal. The variable Candidate_Type (defined in Sem_Type) is set for
218    --  every type compatible with the operator, even if the operator for the
219    --  type is not directly visible. The routine uses this type to emit a more
220    --  informative message.
221
222    procedure Process_Implicit_Dereference_Prefix
223      (E : Entity_Id;
224       P : Node_Id);
225    --  Called when P is the prefix of an implicit dereference, denoting an
226    --  object E. If in semantics only mode (-gnatc or generic), record that is
227    --  a reference to E. Normally, such a reference is generated only when the
228    --  implicit dereference is expanded into an explicit one. E may be empty,
229    --  in which case this procedure does nothing.
230
231    procedure Remove_Abstract_Operations (N : Node_Id);
232    --  Ada 2005: implementation of AI-310. An abstract non-dispatching
233    --  operation is not a candidate interpretation.
234
235    function Try_Indexed_Call
236      (N   : Node_Id;
237       Nam : Entity_Id;
238       Typ : Entity_Id) return Boolean;
239    --  If a function has defaults for all its actuals, a call to it may
240    --  in fact be an indexing on the result of the call. Try_Indexed_Call
241    --  attempts the interpretation as an indexing, prior to analysis as
242    --  a call. If both are possible,  the node is overloaded with both
243    --  interpretations (same symbol but two different types).
244
245    function Try_Indirect_Call
246      (N   : Node_Id;
247       Nam : Entity_Id;
248       Typ : Entity_Id) return Boolean;
249    --  Similarly, a function F that needs no actuals can return an access
250    --  to a subprogram, and the call F (X)  interpreted as F.all (X). In
251    --  this case the call may be overloaded with both interpretations.
252
253    function Try_Object_Operation (N : Node_Id) return Boolean;
254    --  Ada 2005 (AI-252): Give support to the object operation notation
255
256    ------------------------
257    -- Ambiguous_Operands --
258    ------------------------
259
260    procedure Ambiguous_Operands (N : Node_Id) is
261       procedure List_Operand_Interps (Opnd : Node_Id);
262
263       --------------------------
264       -- List_Operand_Interps --
265       --------------------------
266
267       procedure List_Operand_Interps (Opnd : Node_Id) is
268          Nam   : Node_Id;
269          Err   : Node_Id := N;
270
271       begin
272          if Is_Overloaded (Opnd) then
273             if Nkind (Opnd) in N_Op then
274                Nam := Opnd;
275             elsif Nkind (Opnd) = N_Function_Call then
276                Nam := Name (Opnd);
277             else
278                return;
279             end if;
280
281          else
282             return;
283          end if;
284
285          if Opnd = Left_Opnd (N) then
286             Error_Msg_N
287               ("\left operand has the following interpretations", N);
288          else
289             Error_Msg_N
290               ("\right operand has the following interpretations", N);
291             Err := Opnd;
292          end if;
293
294          List_Interps (Nam, Err);
295       end List_Operand_Interps;
296
297    --  Start of processing for Ambiguous_Operands
298
299    begin
300       if Nkind (N) = N_In
301         or else Nkind (N) = N_Not_In
302       then
303          Error_Msg_N ("ambiguous operands for membership",  N);
304
305       elsif Nkind (N) = N_Op_Eq
306         or else Nkind (N) = N_Op_Ne
307       then
308          Error_Msg_N ("ambiguous operands for equality",  N);
309
310       else
311          Error_Msg_N ("ambiguous operands for comparison",  N);
312       end if;
313
314       if All_Errors_Mode then
315          List_Operand_Interps (Left_Opnd  (N));
316          List_Operand_Interps (Right_Opnd (N));
317       else
318          Error_Msg_N ("\use -gnatf switch for details", N);
319       end if;
320    end Ambiguous_Operands;
321
322    -----------------------
323    -- Analyze_Aggregate --
324    -----------------------
325
326    --  Most of the analysis of Aggregates requires that the type be known,
327    --  and is therefore put off until resolution.
328
329    procedure Analyze_Aggregate (N : Node_Id) is
330    begin
331       if No (Etype (N)) then
332          Set_Etype (N, Any_Composite);
333       end if;
334    end Analyze_Aggregate;
335
336    -----------------------
337    -- Analyze_Allocator --
338    -----------------------
339
340    procedure Analyze_Allocator (N : Node_Id) is
341       Loc      : constant Source_Ptr := Sloc (N);
342       Sav_Errs : constant Nat        := Serious_Errors_Detected;
343       E        : Node_Id            := Expression (N);
344       Acc_Type : Entity_Id;
345       Type_Id  : Entity_Id;
346
347    begin
348       Check_Restriction (No_Allocators, N);
349
350       if Nkind (E) = N_Qualified_Expression then
351          Acc_Type := Create_Itype (E_Allocator_Type, N);
352          Set_Etype (Acc_Type, Acc_Type);
353          Init_Size_Align (Acc_Type);
354          Find_Type (Subtype_Mark (E));
355          Type_Id := Entity (Subtype_Mark (E));
356          Check_Fully_Declared (Type_Id, N);
357          Set_Directly_Designated_Type (Acc_Type, Type_Id);
358
359          if Is_Limited_Type (Type_Id)
360            and then Comes_From_Source (N)
361            and then not In_Instance_Body
362          then
363             --  Ada 2005 (AI-287): Do not post an error if the expression
364             --  corresponds to a limited aggregate. Limited aggregates
365             --  are checked in sem_aggr in a per-component manner
366             --  (compare with handling of Get_Value subprogram).
367
368             if Ada_Version >= Ada_05
369               and then Nkind (Expression (E)) = N_Aggregate
370             then
371                null;
372             else
373                Error_Msg_N ("initialization not allowed for limited types", N);
374                Explain_Limited_Type (Type_Id, N);
375             end if;
376          end if;
377
378          Analyze_And_Resolve (Expression (E), Type_Id);
379
380          --  A qualified expression requires an exact match of the type,
381          --  class-wide matching is not allowed.
382
383          if Is_Class_Wide_Type (Type_Id)
384            and then Base_Type (Etype (Expression (E))) /= Base_Type (Type_Id)
385          then
386             Wrong_Type (Expression (E), Type_Id);
387          end if;
388
389          Check_Non_Static_Context (Expression (E));
390
391          --  We don't analyze the qualified expression itself because it's
392          --  part of the allocator
393
394          Set_Etype  (E, Type_Id);
395
396       --  Case where no qualified expression is present
397
398       else
399          declare
400             Def_Id   : Entity_Id;
401             Base_Typ : Entity_Id;
402
403          begin
404             --  If the allocator includes a N_Subtype_Indication then a
405             --  constraint is present, otherwise the node is a subtype mark.
406             --  Introduce an explicit subtype declaration into the tree
407             --  defining some anonymous subtype and rewrite the allocator to
408             --  use this subtype rather than the subtype indication.
409
410             --  It is important to introduce the explicit subtype declaration
411             --  so that the bounds of the subtype indication are attached to
412             --  the tree in case the allocator is inside a generic unit.
413
414             if Nkind (E) = N_Subtype_Indication then
415
416                --  A constraint is only allowed for a composite type in Ada
417                --  95. In Ada 83, a constraint is also allowed for an
418                --  access-to-composite type, but the constraint is ignored.
419
420                Find_Type (Subtype_Mark (E));
421                Base_Typ := Entity (Subtype_Mark (E));
422
423                if Is_Elementary_Type (Base_Typ) then
424                   if not (Ada_Version = Ada_83
425                            and then Is_Access_Type (Base_Typ))
426                   then
427                      Error_Msg_N ("constraint not allowed here", E);
428
429                      if Nkind (Constraint (E))
430                        = N_Index_Or_Discriminant_Constraint
431                      then
432                         Error_Msg_N
433                           ("\if qualified expression was meant, " &
434                               "use apostrophe", Constraint (E));
435                      end if;
436                   end if;
437
438                   --  Get rid of the bogus constraint:
439
440                   Rewrite (E, New_Copy_Tree (Subtype_Mark (E)));
441                   Analyze_Allocator (N);
442                   return;
443
444                --  Ada 2005, AI-363: if the designated type has a constrained
445                --  partial view, it cannot receive a discriminant constraint,
446                --  and the allocated object is unconstrained.
447
448                elsif Ada_Version >= Ada_05
449                  and then Has_Constrained_Partial_View (Base_Typ)
450                then
451                   Error_Msg_N
452                     ("constraint no allowed when type " &
453                       "has a constrained partial view", Constraint (E));
454                end if;
455
456                if Expander_Active then
457                   Def_Id :=
458                     Make_Defining_Identifier (Loc, New_Internal_Name ('S'));
459
460                   Insert_Action (E,
461                     Make_Subtype_Declaration (Loc,
462                       Defining_Identifier => Def_Id,
463                       Subtype_Indication  => Relocate_Node (E)));
464
465                   if Sav_Errs /= Serious_Errors_Detected
466                     and then Nkind (Constraint (E))
467                       = N_Index_Or_Discriminant_Constraint
468                   then
469                      Error_Msg_N
470                        ("if qualified expression was meant, " &
471                            "use apostrophe!", Constraint (E));
472                   end if;
473
474                   E := New_Occurrence_Of (Def_Id, Loc);
475                   Rewrite (Expression (N), E);
476                end if;
477             end if;
478
479             Type_Id := Process_Subtype (E, N);
480             Acc_Type := Create_Itype (E_Allocator_Type, N);
481             Set_Etype                    (Acc_Type, Acc_Type);
482             Init_Size_Align              (Acc_Type);
483             Set_Directly_Designated_Type (Acc_Type, Type_Id);
484             Check_Fully_Declared (Type_Id, N);
485
486             --  Ada 2005 (AI-231)
487
488             if Can_Never_Be_Null (Type_Id) then
489                Error_Msg_N ("(Ada 2005) qualified expression required",
490                             Expression (N));
491             end if;
492
493             --  Check restriction against dynamically allocated protected
494             --  objects. Note that when limited aggregates are supported,
495             --  a similar test should be applied to an allocator with a
496             --  qualified expression ???
497
498             if Is_Protected_Type (Type_Id) then
499                Check_Restriction (No_Protected_Type_Allocators, N);
500             end if;
501
502             --  Check for missing initialization. Skip this check if we already
503             --  had errors on analyzing the allocator, since in that case these
504             --  are probably cascaded errors
505
506             if Is_Indefinite_Subtype (Type_Id)
507               and then Serious_Errors_Detected = Sav_Errs
508             then
509                if Is_Class_Wide_Type (Type_Id) then
510                   Error_Msg_N
511                     ("initialization required in class-wide allocation", N);
512                else
513                   Error_Msg_N
514                     ("initialization required in unconstrained allocation", N);
515                end if;
516             end if;
517          end;
518       end if;
519
520       if Is_Abstract (Type_Id) then
521          Error_Msg_N ("cannot allocate abstract object", E);
522       end if;
523
524       if Has_Task (Designated_Type (Acc_Type)) then
525          Check_Restriction (No_Tasking, N);
526          Check_Restriction (Max_Tasks, N);
527          Check_Restriction (No_Task_Allocators, N);
528       end if;
529
530       --  If the No_Streams restriction is set, check that the type of the
531       --  object is not, and does not contain, any subtype derived from
532       --  Ada.Streams.Root_Stream_Type. Note that we guard the call to
533       --  Has_Stream just for efficiency reasons. There is no point in
534       --  spending time on a Has_Stream check if the restriction is not set.
535
536       if Restrictions.Set (No_Streams) then
537          if Has_Stream (Designated_Type (Acc_Type)) then
538             Check_Restriction (No_Streams, N);
539          end if;
540       end if;
541
542       Set_Etype (N, Acc_Type);
543
544       if not Is_Library_Level_Entity (Acc_Type) then
545          Check_Restriction (No_Local_Allocators, N);
546       end if;
547
548       if Serious_Errors_Detected > Sav_Errs then
549          Set_Error_Posted (N);
550          Set_Etype (N, Any_Type);
551       end if;
552    end Analyze_Allocator;
553
554    ---------------------------
555    -- Analyze_Arithmetic_Op --
556    ---------------------------
557
558    procedure Analyze_Arithmetic_Op (N : Node_Id) is
559       L     : constant Node_Id := Left_Opnd (N);
560       R     : constant Node_Id := Right_Opnd (N);
561       Op_Id : Entity_Id;
562
563    begin
564       Candidate_Type := Empty;
565       Analyze_Expression (L);
566       Analyze_Expression (R);
567
568       --  If the entity is already set, the node is the instantiation of
569       --  a generic node with a non-local reference, or was manufactured
570       --  by a call to Make_Op_xxx. In either case the entity is known to
571       --  be valid, and we do not need to collect interpretations, instead
572       --  we just get the single possible interpretation.
573
574       Op_Id := Entity (N);
575
576       if Present (Op_Id) then
577          if Ekind (Op_Id) = E_Operator then
578
579             if (Nkind (N) = N_Op_Divide   or else
580                 Nkind (N) = N_Op_Mod      or else
581                 Nkind (N) = N_Op_Multiply or else
582                 Nkind (N) = N_Op_Rem)
583               and then Treat_Fixed_As_Integer (N)
584             then
585                null;
586             else
587                Set_Etype (N, Any_Type);
588                Find_Arithmetic_Types (L, R, Op_Id, N);
589             end if;
590
591          else
592             Set_Etype (N, Any_Type);
593             Add_One_Interp (N, Op_Id, Etype (Op_Id));
594          end if;
595
596       --  Entity is not already set, so we do need to collect interpretations
597
598       else
599          Op_Id := Get_Name_Entity_Id (Chars (N));
600          Set_Etype (N, Any_Type);
601
602          while Present (Op_Id) loop
603             if Ekind (Op_Id) = E_Operator
604               and then Present (Next_Entity (First_Entity (Op_Id)))
605             then
606                Find_Arithmetic_Types (L, R, Op_Id, N);
607
608             --  The following may seem superfluous, because an operator cannot
609             --  be generic, but this ignores the cleverness of the author of
610             --  ACVC bc1013a.
611
612             elsif Is_Overloadable (Op_Id) then
613                Analyze_User_Defined_Binary_Op (N, Op_Id);
614             end if;
615
616             Op_Id := Homonym (Op_Id);
617          end loop;
618       end if;
619
620       Operator_Check (N);
621    end Analyze_Arithmetic_Op;
622
623    ------------------
624    -- Analyze_Call --
625    ------------------
626
627    --  Function, procedure, and entry calls are checked here. The Name in
628    --  the call may be overloaded. The actuals have been analyzed and may
629    --  themselves be overloaded. On exit from this procedure, the node N
630    --  may have zero, one or more interpretations. In the first case an
631    --  error message is produced. In the last case, the node is flagged
632    --  as overloaded and the interpretations are collected in All_Interp.
633
634    --  If the name is an Access_To_Subprogram, it cannot be overloaded, but
635    --  the type-checking is similar to that of other calls.
636
637    procedure Analyze_Call (N : Node_Id) is
638       Actuals : constant List_Id := Parameter_Associations (N);
639       Nam     : Node_Id          := Name (N);
640       X       : Interp_Index;
641       It      : Interp;
642       Nam_Ent : Entity_Id;
643       Success : Boolean := False;
644
645       function Name_Denotes_Function return Boolean;
646       --  If the type of the name is an access to subprogram, this may be
647       --  the type of a name, or the return type of the function being called.
648       --  If the name is not an entity then it can denote a protected function.
649       --  Until we distinguish Etype from Return_Type, we must use this
650       --  routine to resolve the meaning of the name in the call.
651
652       ---------------------------
653       -- Name_Denotes_Function --
654       ---------------------------
655
656       function Name_Denotes_Function return Boolean is
657       begin
658          if Is_Entity_Name (Nam) then
659             return Ekind (Entity (Nam)) = E_Function;
660
661          elsif Nkind (Nam) = N_Selected_Component then
662             return Ekind (Entity (Selector_Name (Nam))) = E_Function;
663
664          else
665             return False;
666          end if;
667       end Name_Denotes_Function;
668
669    --  Start of processing for Analyze_Call
670
671    begin
672       --  Initialize the type of the result of the call to the error type,
673       --  which will be reset if the type is successfully resolved.
674
675       Set_Etype (N, Any_Type);
676
677       if not Is_Overloaded (Nam) then
678
679          --  Only one interpretation to check
680
681          if Ekind (Etype (Nam)) = E_Subprogram_Type then
682             Nam_Ent := Etype (Nam);
683
684          --  If the prefix is an access_to_subprogram, this may be an indirect
685          --  call. This is the case if the name in the call is not an entity
686          --  name, or if it is a function name in the context of a procedure
687          --  call. In this latter case, we have a call to a parameterless
688          --  function that returns a pointer_to_procedure which is the entity
689          --  being called.
690
691          elsif Is_Access_Type (Etype (Nam))
692            and then Ekind (Designated_Type (Etype (Nam))) = E_Subprogram_Type
693            and then
694              (not Name_Denotes_Function
695                 or else Nkind (N) = N_Procedure_Call_Statement)
696          then
697             Nam_Ent := Designated_Type (Etype (Nam));
698             Insert_Explicit_Dereference (Nam);
699
700          --  Selected component case. Simple entry or protected operation,
701          --  where the entry name is given by the selector name.
702
703          elsif Nkind (Nam) = N_Selected_Component then
704             Nam_Ent := Entity (Selector_Name (Nam));
705
706             if Ekind (Nam_Ent) /= E_Entry
707               and then Ekind (Nam_Ent) /= E_Entry_Family
708               and then Ekind (Nam_Ent) /= E_Function
709               and then Ekind (Nam_Ent) /= E_Procedure
710             then
711                Error_Msg_N ("name in call is not a callable entity", Nam);
712                Set_Etype (N, Any_Type);
713                return;
714             end if;
715
716          --  If the name is an Indexed component, it can be a call to a member
717          --  of an entry family. The prefix must be a selected component whose
718          --  selector is the entry. Analyze_Procedure_Call normalizes several
719          --  kinds of call into this form.
720
721          elsif Nkind (Nam) = N_Indexed_Component then
722
723             if Nkind (Prefix (Nam)) = N_Selected_Component then
724                Nam_Ent := Entity (Selector_Name (Prefix (Nam)));
725             else
726                Error_Msg_N ("name in call is not a callable entity", Nam);
727                Set_Etype (N, Any_Type);
728                return;
729             end if;
730
731          elsif not Is_Entity_Name (Nam) then
732             Error_Msg_N ("name in call is not a callable entity", Nam);
733             Set_Etype (N, Any_Type);
734             return;
735
736          else
737             Nam_Ent := Entity (Nam);
738
739             --  If no interpretations, give error message
740
741             if not Is_Overloadable (Nam_Ent) then
742                declare
743                   L : constant Boolean   := Is_List_Member (N);
744                   K : constant Node_Kind := Nkind (Parent (N));
745
746                begin
747                   --  If the node is in a list whose parent is not an
748                   --  expression then it must be an attempted procedure call.
749
750                   if L and then K not in N_Subexpr then
751                      if Ekind (Entity (Nam)) = E_Generic_Procedure then
752                         Error_Msg_NE
753                           ("must instantiate generic procedure& before call",
754                            Nam, Entity (Nam));
755                      else
756                         Error_Msg_N
757                           ("procedure or entry name expected", Nam);
758                      end if;
759
760                   --  Check for tasking cases where only an entry call will do
761
762                   elsif not L
763                     and then (K = N_Entry_Call_Alternative
764                                or else K = N_Triggering_Alternative)
765                   then
766                      Error_Msg_N ("entry name expected", Nam);
767
768                   --  Otherwise give general error message
769
770                   else
771                      Error_Msg_N ("invalid prefix in call", Nam);
772                   end if;
773
774                   return;
775                end;
776             end if;
777          end if;
778
779          Analyze_One_Call (N, Nam_Ent, True, Success);
780
781          --  If this is an indirect call, the return type of the access_to
782          --  subprogram may be an incomplete type. At the point of the call,
783          --  use the full type if available, and at the same time update
784          --  the return type of the access_to_subprogram.
785
786          if Success
787            and then  Nkind (Nam) = N_Explicit_Dereference
788            and then Ekind (Etype (N)) = E_Incomplete_Type
789            and then Present (Full_View (Etype (N)))
790          then
791             Set_Etype (N, Full_View (Etype (N)));
792             Set_Etype (Nam_Ent, Etype (N));
793          end if;
794
795       else
796          --  An overloaded selected component must denote overloaded
797          --  operations of a concurrent type. The interpretations are
798          --  attached to the simple name of those operations.
799
800          if Nkind (Nam) = N_Selected_Component then
801             Nam := Selector_Name (Nam);
802          end if;
803
804          Get_First_Interp (Nam, X, It);
805
806          while Present (It.Nam) loop
807             Nam_Ent := It.Nam;
808
809             --  Name may be call that returns an access to subprogram, or more
810             --  generally an overloaded expression one of whose interpretations
811             --  yields an access to subprogram. If the name is an entity, we
812             --  do not dereference, because the node is a call that returns
813             --  the access type: note difference between f(x), where the call
814             --  may return an access subprogram type, and f(x)(y), where the
815             --  type returned by the call to f is implicitly dereferenced to
816             --  analyze the outer call.
817
818             if Is_Access_Type (Nam_Ent) then
819                Nam_Ent := Designated_Type (Nam_Ent);
820
821             elsif Is_Access_Type (Etype (Nam_Ent))
822               and then not Is_Entity_Name (Nam)
823               and then Ekind (Designated_Type (Etype (Nam_Ent)))
824                                                           = E_Subprogram_Type
825             then
826                Nam_Ent := Designated_Type (Etype (Nam_Ent));
827             end if;
828
829             Analyze_One_Call (N, Nam_Ent, False, Success);
830
831             --  If the interpretation succeeds, mark the proper type of the
832             --  prefix (any valid candidate will do). If not, remove the
833             --  candidate interpretation. This only needs to be done for
834             --  overloaded protected operations, for other entities disambi-
835             --  guation is done directly in Resolve.
836
837             if Success then
838                Set_Etype (Nam, It.Typ);
839
840             elsif Nkind (Name (N)) = N_Selected_Component
841               or else Nkind (Name (N)) = N_Function_Call
842             then
843                Remove_Interp (X);
844             end if;
845
846             Get_Next_Interp (X, It);
847          end loop;
848
849          --  If the name is the result of a function call, it can only
850          --  be a call to a function returning an access to subprogram.
851          --  Insert explicit dereference.
852
853          if Nkind (Nam) = N_Function_Call then
854             Insert_Explicit_Dereference (Nam);
855          end if;
856
857          if Etype (N) = Any_Type then
858
859             --  None of the interpretations is compatible with the actuals
860
861             Diagnose_Call (N, Nam);
862
863             --  Special checks for uninstantiated put routines
864
865             if Nkind (N) = N_Procedure_Call_Statement
866               and then Is_Entity_Name (Nam)
867               and then Chars (Nam) = Name_Put
868               and then List_Length (Actuals) = 1
869             then
870                declare
871                   Arg : constant Node_Id := First (Actuals);
872                   Typ : Entity_Id;
873
874                begin
875                   if Nkind (Arg) = N_Parameter_Association then
876                      Typ := Etype (Explicit_Actual_Parameter (Arg));
877                   else
878                      Typ := Etype (Arg);
879                   end if;
880
881                   if Is_Signed_Integer_Type (Typ) then
882                      Error_Msg_N
883                        ("possible missing instantiation of " &
884                           "'Text_'I'O.'Integer_'I'O!", Nam);
885
886                   elsif Is_Modular_Integer_Type (Typ) then
887                      Error_Msg_N
888                        ("possible missing instantiation of " &
889                           "'Text_'I'O.'Modular_'I'O!", Nam);
890
891                   elsif Is_Floating_Point_Type (Typ) then
892                      Error_Msg_N
893                        ("possible missing instantiation of " &
894                           "'Text_'I'O.'Float_'I'O!", Nam);
895
896                   elsif Is_Ordinary_Fixed_Point_Type (Typ) then
897                      Error_Msg_N
898                        ("possible missing instantiation of " &
899                           "'Text_'I'O.'Fixed_'I'O!", Nam);
900
901                   elsif Is_Decimal_Fixed_Point_Type (Typ) then
902                      Error_Msg_N
903                        ("possible missing instantiation of " &
904                           "'Text_'I'O.'Decimal_'I'O!", Nam);
905
906                   elsif Is_Enumeration_Type (Typ) then
907                      Error_Msg_N
908                        ("possible missing instantiation of " &
909                           "'Text_'I'O.'Enumeration_'I'O!", Nam);
910                   end if;
911                end;
912             end if;
913
914          elsif not Is_Overloaded (N)
915            and then Is_Entity_Name (Nam)
916          then
917             --  Resolution yields a single interpretation. Verify that
918             --  is has the proper capitalization.
919
920             Set_Entity_With_Style_Check (Nam, Entity (Nam));
921             Generate_Reference (Entity (Nam), Nam);
922
923             Set_Etype (Nam, Etype (Entity (Nam)));
924          else
925             Remove_Abstract_Operations (N);
926          end if;
927
928          End_Interp_List;
929       end if;
930    end Analyze_Call;
931
932    ---------------------------
933    -- Analyze_Comparison_Op --
934    ---------------------------
935
936    procedure Analyze_Comparison_Op (N : Node_Id) is
937       L     : constant Node_Id := Left_Opnd (N);
938       R     : constant Node_Id := Right_Opnd (N);
939       Op_Id : Entity_Id        := Entity (N);
940
941    begin
942       Set_Etype (N, Any_Type);
943       Candidate_Type := Empty;
944
945       Analyze_Expression (L);
946       Analyze_Expression (R);
947
948       if Present (Op_Id) then
949          if Ekind (Op_Id) = E_Operator then
950             Find_Comparison_Types (L, R, Op_Id, N);
951          else
952             Add_One_Interp (N, Op_Id, Etype (Op_Id));
953          end if;
954
955          if Is_Overloaded (L) then
956             Set_Etype (L, Intersect_Types (L, R));
957          end if;
958
959       else
960          Op_Id := Get_Name_Entity_Id (Chars (N));
961          while Present (Op_Id) loop
962             if Ekind (Op_Id) = E_Operator then
963                Find_Comparison_Types (L, R, Op_Id, N);
964             else
965                Analyze_User_Defined_Binary_Op (N, Op_Id);
966             end if;
967
968             Op_Id := Homonym (Op_Id);
969          end loop;
970       end if;
971
972       Operator_Check (N);
973    end Analyze_Comparison_Op;
974
975    ---------------------------
976    -- Analyze_Concatenation --
977    ---------------------------
978
979    --  If the only one-dimensional array type in scope is String,
980    --  this is the resulting type of the operation. Otherwise there
981    --  will be a concatenation operation defined for each user-defined
982    --  one-dimensional array.
983
984    procedure Analyze_Concatenation (N : Node_Id) is
985       L     : constant Node_Id := Left_Opnd (N);
986       R     : constant Node_Id := Right_Opnd (N);
987       Op_Id : Entity_Id        := Entity (N);
988       LT    : Entity_Id;
989       RT    : Entity_Id;
990
991    begin
992       Set_Etype (N, Any_Type);
993       Candidate_Type := Empty;
994
995       Analyze_Expression (L);
996       Analyze_Expression (R);
997
998       --  If the entity is present, the  node appears in an instance,
999       --  and denotes a predefined concatenation operation. The resulting
1000       --  type is obtained from the arguments when possible. If the arguments
1001       --  are aggregates, the array type and the concatenation type must be
1002       --  visible.
1003
1004       if Present (Op_Id) then
1005          if Ekind (Op_Id) = E_Operator then
1006
1007             LT := Base_Type (Etype (L));
1008             RT := Base_Type (Etype (R));
1009
1010             if Is_Array_Type (LT)
1011               and then (RT = LT or else RT = Base_Type (Component_Type (LT)))
1012             then
1013                Add_One_Interp (N, Op_Id, LT);
1014
1015             elsif Is_Array_Type (RT)
1016               and then LT = Base_Type (Component_Type (RT))
1017             then
1018                Add_One_Interp (N, Op_Id, RT);
1019
1020             --  If one operand is a string type or a user-defined array type,
1021             --  and the other is a literal, result is of the specific type.
1022
1023             elsif
1024               (Root_Type (LT) = Standard_String
1025                  or else Scope (LT) /= Standard_Standard)
1026               and then Etype (R) = Any_String
1027             then
1028                Add_One_Interp (N, Op_Id, LT);
1029
1030             elsif
1031               (Root_Type (RT) = Standard_String
1032                  or else Scope (RT) /= Standard_Standard)
1033               and then Etype (L) = Any_String
1034             then
1035                Add_One_Interp (N, Op_Id, RT);
1036
1037             elsif not Is_Generic_Type (Etype (Op_Id)) then
1038                Add_One_Interp (N, Op_Id, Etype (Op_Id));
1039
1040             else
1041                --  Type and its operations must be visible
1042
1043                Set_Entity (N, Empty);
1044                Analyze_Concatenation (N);
1045             end if;
1046
1047          else
1048             Add_One_Interp (N, Op_Id, Etype (Op_Id));
1049          end if;
1050
1051       else
1052          Op_Id := Get_Name_Entity_Id (Name_Op_Concat);
1053          while Present (Op_Id) loop
1054             if Ekind (Op_Id) = E_Operator then
1055
1056                --  Do not consider operators declared in dead code, they can
1057                --  not be part of the resolution.
1058
1059                if Is_Eliminated (Op_Id) then
1060                   null;
1061                else
1062                   Find_Concatenation_Types (L, R, Op_Id, N);
1063                end if;
1064
1065             else
1066                Analyze_User_Defined_Binary_Op (N, Op_Id);
1067             end if;
1068
1069             Op_Id := Homonym (Op_Id);
1070          end loop;
1071       end if;
1072
1073       Operator_Check (N);
1074    end Analyze_Concatenation;
1075
1076    ------------------------------------
1077    -- Analyze_Conditional_Expression --
1078    ------------------------------------
1079
1080    procedure Analyze_Conditional_Expression (N : Node_Id) is
1081       Condition : constant Node_Id := First (Expressions (N));
1082       Then_Expr : constant Node_Id := Next (Condition);
1083       Else_Expr : constant Node_Id := Next (Then_Expr);
1084    begin
1085       Analyze_Expression (Condition);
1086       Analyze_Expression (Then_Expr);
1087       Analyze_Expression (Else_Expr);
1088       Set_Etype (N, Etype (Then_Expr));
1089    end Analyze_Conditional_Expression;
1090
1091    -------------------------
1092    -- Analyze_Equality_Op --
1093    -------------------------
1094
1095    procedure Analyze_Equality_Op (N : Node_Id) is
1096       Loc   : constant Source_Ptr := Sloc (N);
1097       L     : constant Node_Id := Left_Opnd (N);
1098       R     : constant Node_Id := Right_Opnd (N);
1099       Op_Id : Entity_Id;
1100
1101    begin
1102       Set_Etype (N, Any_Type);
1103       Candidate_Type := Empty;
1104
1105       Analyze_Expression (L);
1106       Analyze_Expression (R);
1107
1108       --  If the entity is set, the node is a generic instance with a non-local
1109       --  reference to the predefined operator or to a user-defined function.
1110       --  It can also be an inequality that is expanded into the negation of a
1111       --  call to a user-defined equality operator.
1112
1113       --  For the predefined case, the result is Boolean, regardless of the
1114       --  type of the  operands. The operands may even be limited, if they are
1115       --  generic actuals. If they are overloaded, label the left argument with
1116       --  the common type that must be present, or with the type of the formal
1117       --  of the user-defined function.
1118
1119       if Present (Entity (N)) then
1120          Op_Id := Entity (N);
1121
1122          if Ekind (Op_Id) = E_Operator then
1123             Add_One_Interp (N, Op_Id, Standard_Boolean);
1124          else
1125             Add_One_Interp (N, Op_Id, Etype (Op_Id));
1126          end if;
1127
1128          if Is_Overloaded (L) then
1129             if Ekind (Op_Id) = E_Operator then
1130                Set_Etype (L, Intersect_Types (L, R));
1131             else
1132                Set_Etype (L, Etype (First_Formal (Op_Id)));
1133             end if;
1134          end if;
1135
1136       else
1137          Op_Id := Get_Name_Entity_Id (Chars (N));
1138          while Present (Op_Id) loop
1139             if Ekind (Op_Id) = E_Operator then
1140                Find_Equality_Types (L, R, Op_Id, N);
1141             else
1142                Analyze_User_Defined_Binary_Op (N, Op_Id);
1143             end if;
1144
1145             Op_Id := Homonym (Op_Id);
1146          end loop;
1147       end if;
1148
1149       --  If there was no match, and the operator is inequality, this may
1150       --  be a case where inequality has not been made explicit, as for
1151       --  tagged types. Analyze the node as the negation of an equality
1152       --  operation. This cannot be done earlier, because before analysis
1153       --  we cannot rule out the presence of an explicit inequality.
1154
1155       if Etype (N) = Any_Type
1156         and then Nkind (N) = N_Op_Ne
1157       then
1158          Op_Id := Get_Name_Entity_Id (Name_Op_Eq);
1159          while Present (Op_Id) loop
1160             if Ekind (Op_Id) = E_Operator then
1161                Find_Equality_Types (L, R, Op_Id, N);
1162             else
1163                Analyze_User_Defined_Binary_Op (N, Op_Id);
1164             end if;
1165
1166             Op_Id := Homonym (Op_Id);
1167          end loop;
1168
1169          if Etype (N) /= Any_Type then
1170             Op_Id := Entity (N);
1171
1172             Rewrite (N,
1173               Make_Op_Not (Loc,
1174                 Right_Opnd =>
1175                   Make_Op_Eq (Loc,
1176                     Left_Opnd =>  Relocate_Node (Left_Opnd (N)),
1177                     Right_Opnd => Relocate_Node (Right_Opnd (N)))));
1178
1179             Set_Entity (Right_Opnd (N), Op_Id);
1180             Analyze (N);
1181          end if;
1182       end if;
1183
1184       Operator_Check (N);
1185    end Analyze_Equality_Op;
1186
1187    ----------------------------------
1188    -- Analyze_Explicit_Dereference --
1189    ----------------------------------
1190
1191    procedure Analyze_Explicit_Dereference (N : Node_Id) is
1192       Loc   : constant Source_Ptr := Sloc (N);
1193       P     : constant Node_Id := Prefix (N);
1194       T     : Entity_Id;
1195       I     : Interp_Index;
1196       It    : Interp;
1197       New_N : Node_Id;
1198
1199       function Is_Function_Type return Boolean;
1200       --  Check whether node may be interpreted as an implicit function call
1201
1202       ----------------------
1203       -- Is_Function_Type --
1204       ----------------------
1205
1206       function Is_Function_Type return Boolean is
1207          I  : Interp_Index;
1208          It : Interp;
1209
1210       begin
1211          if not Is_Overloaded (N) then
1212             return Ekind (Base_Type (Etype (N))) = E_Subprogram_Type
1213               and then Etype (Base_Type (Etype (N))) /= Standard_Void_Type;
1214
1215          else
1216             Get_First_Interp (N, I, It);
1217             while Present (It.Nam) loop
1218                if Ekind (Base_Type (It.Typ)) /= E_Subprogram_Type
1219                  or else Etype (Base_Type (It.Typ)) = Standard_Void_Type
1220                then
1221                   return False;
1222                end if;
1223
1224                Get_Next_Interp (I, It);
1225             end loop;
1226
1227             return True;
1228          end if;
1229       end Is_Function_Type;
1230
1231    --  Start of processing for Analyze_Explicit_Dereference
1232
1233    begin
1234       Analyze (P);
1235       Set_Etype (N, Any_Type);
1236
1237       --  Test for remote access to subprogram type, and if so return
1238       --  after rewriting the original tree.
1239
1240       if Remote_AST_E_Dereference (P) then
1241          return;
1242       end if;
1243
1244       --  Normal processing for other than remote access to subprogram type
1245
1246       if not Is_Overloaded (P) then
1247          if Is_Access_Type (Etype (P)) then
1248
1249             --  Set the Etype. We need to go thru Is_For_Access_Subtypes
1250             --  to avoid other problems caused by the Private_Subtype
1251             --  and it is safe to go to the Base_Type because this is the
1252             --  same as converting the access value to its Base_Type.
1253
1254             declare
1255                DT : Entity_Id := Designated_Type (Etype (P));
1256
1257             begin
1258                if Ekind (DT) = E_Private_Subtype
1259                  and then Is_For_Access_Subtype (DT)
1260                then
1261                   DT := Base_Type (DT);
1262                end if;
1263
1264                Set_Etype (N, DT);
1265             end;
1266
1267          elsif Etype (P) /= Any_Type then
1268             Error_Msg_N ("prefix of dereference must be an access type", N);
1269             return;
1270          end if;
1271
1272       else
1273          Get_First_Interp (P, I, It);
1274          while Present (It.Nam) loop
1275             T := It.Typ;
1276
1277             if Is_Access_Type (T) then
1278                Add_One_Interp (N, Designated_Type (T), Designated_Type (T));
1279             end if;
1280
1281             Get_Next_Interp (I, It);
1282          end loop;
1283
1284          --  Error if no interpretation of the prefix has an access type
1285
1286          if Etype (N) = Any_Type then
1287             Error_Msg_N
1288               ("access type required in prefix of explicit dereference", P);
1289             Set_Etype (N, Any_Type);
1290             return;
1291          end if;
1292       end if;
1293
1294       if Is_Function_Type
1295         and then Nkind (Parent (N)) /= N_Indexed_Component
1296
1297         and then (Nkind (Parent (N)) /= N_Function_Call
1298                    or else N /= Name (Parent (N)))
1299
1300         and then (Nkind (Parent (N)) /= N_Procedure_Call_Statement
1301                    or else N /= Name (Parent (N)))
1302
1303         and then Nkind (Parent (N)) /= N_Subprogram_Renaming_Declaration
1304         and then (Nkind (Parent (N)) /= N_Attribute_Reference
1305                     or else
1306                       (Attribute_Name (Parent (N)) /= Name_Address
1307                         and then
1308                        Attribute_Name (Parent (N)) /= Name_Access))
1309       then
1310          --  Name is a function call with no actuals, in a context that
1311          --  requires deproceduring (including as an actual in an enclosing
1312          --  function or procedure call). There are some pathological cases
1313          --  where the prefix might include functions that return access to
1314          --  subprograms and others that return a regular type. Disambiguation
1315          --  of those has to take place in Resolve.
1316          --  See e.g. 7117-014 and E317-001.
1317
1318          New_N :=
1319            Make_Function_Call (Loc,
1320            Name => Make_Explicit_Dereference (Loc, P),
1321            Parameter_Associations => New_List);
1322
1323          --  If the prefix is overloaded, remove operations that have formals,
1324          --  we know that this is a parameterless call.
1325
1326          if Is_Overloaded (P) then
1327             Get_First_Interp (P, I, It);
1328             while Present (It.Nam) loop
1329                T := It.Typ;
1330
1331                if No (First_Formal (Base_Type (Designated_Type (T)))) then
1332                   Set_Etype (P, T);
1333                else
1334                   Remove_Interp (I);
1335                end if;
1336
1337                Get_Next_Interp (I, It);
1338             end loop;
1339          end if;
1340
1341          Rewrite (N, New_N);
1342          Analyze (N);
1343
1344       elsif not Is_Function_Type
1345         and then Is_Overloaded (N)
1346       then
1347          --  The prefix may include access to subprograms and other access
1348          --  types. If the context selects the interpretation that is a call,
1349          --  we cannot rewrite the node yet, but we include the result of
1350          --  the call interpretation.
1351
1352          Get_First_Interp (N, I, It);
1353          while Present (It.Nam) loop
1354             if Ekind (Base_Type (It.Typ)) = E_Subprogram_Type
1355                and then Etype (Base_Type (It.Typ)) /= Standard_Void_Type
1356             then
1357                Add_One_Interp (N, Etype (It.Typ), Etype (It.Typ));
1358             end if;
1359
1360             Get_Next_Interp (I, It);
1361          end loop;
1362       end if;
1363
1364       --  A value of remote access-to-class-wide must not be dereferenced
1365       --  (RM E.2.2(16)).
1366
1367       Validate_Remote_Access_To_Class_Wide_Type (N);
1368    end Analyze_Explicit_Dereference;
1369
1370    ------------------------
1371    -- Analyze_Expression --
1372    ------------------------
1373
1374    procedure Analyze_Expression (N : Node_Id) is
1375    begin
1376       Analyze (N);
1377       Check_Parameterless_Call (N);
1378    end Analyze_Expression;
1379
1380    ------------------------------------
1381    -- Analyze_Indexed_Component_Form --
1382    ------------------------------------
1383
1384    procedure Analyze_Indexed_Component_Form (N : Node_Id) is
1385       P     : constant Node_Id := Prefix (N);
1386       Exprs : constant List_Id := Expressions (N);
1387       Exp   : Node_Id;
1388       P_T   : Entity_Id;
1389       E     : Node_Id;
1390       U_N   : Entity_Id;
1391
1392       procedure Process_Function_Call;
1393       --  Prefix in indexed component form is an overloadable entity,
1394       --  so the node is a function call. Reformat it as such.
1395
1396       procedure Process_Indexed_Component;
1397       --  Prefix in indexed component form is actually an indexed component.
1398       --  This routine processes it, knowing that the prefix is already
1399       --  resolved.
1400
1401       procedure Process_Indexed_Component_Or_Slice;
1402       --  An indexed component with a single index may designate a slice if
1403       --  the index is a subtype mark. This routine disambiguates these two
1404       --  cases by resolving the prefix to see if it is a subtype mark.
1405
1406       procedure Process_Overloaded_Indexed_Component;
1407       --  If the prefix of an indexed component is overloaded, the proper
1408       --  interpretation is selected by the index types and the context.
1409
1410       ---------------------------
1411       -- Process_Function_Call --
1412       ---------------------------
1413
1414       procedure Process_Function_Call is
1415          Actual : Node_Id;
1416
1417       begin
1418          Change_Node (N, N_Function_Call);
1419          Set_Name (N, P);
1420          Set_Parameter_Associations (N, Exprs);
1421
1422          Actual := First (Parameter_Associations (N));
1423          while Present (Actual) loop
1424             Analyze (Actual);
1425             Check_Parameterless_Call (Actual);
1426             Next_Actual (Actual);
1427          end loop;
1428
1429          Analyze_Call (N);
1430       end Process_Function_Call;
1431
1432       -------------------------------
1433       -- Process_Indexed_Component --
1434       -------------------------------
1435
1436       procedure Process_Indexed_Component is
1437          Exp          : Node_Id;
1438          Array_Type   : Entity_Id;
1439          Index        : Node_Id;
1440          Pent         : Entity_Id := Empty;
1441
1442       begin
1443          Exp := First (Exprs);
1444
1445          if Is_Overloaded (P) then
1446             Process_Overloaded_Indexed_Component;
1447
1448          else
1449             Array_Type := Etype (P);
1450
1451             if Is_Entity_Name (P) then
1452                Pent := Entity (P);
1453             elsif Nkind (P) = N_Selected_Component
1454               and then Is_Entity_Name (Selector_Name (P))
1455             then
1456                Pent := Entity (Selector_Name (P));
1457             end if;
1458
1459             --  Prefix must be appropriate for an array type, taking into
1460             --  account a possible implicit dereference.
1461
1462             if Is_Access_Type (Array_Type) then
1463                Array_Type := Designated_Type (Array_Type);
1464                Error_Msg_NW (Warn_On_Dereference, "?implicit dereference", N);
1465                Process_Implicit_Dereference_Prefix (Pent, P);
1466             end if;
1467
1468             if Is_Array_Type (Array_Type) then
1469                null;
1470
1471             elsif Present (Pent) and then Ekind (Pent) = E_Entry_Family then
1472                Analyze (Exp);
1473                Set_Etype (N, Any_Type);
1474
1475                if not Has_Compatible_Type
1476                  (Exp, Entry_Index_Type (Pent))
1477                then
1478                   Error_Msg_N ("invalid index type in entry name", N);
1479
1480                elsif Present (Next (Exp)) then
1481                   Error_Msg_N ("too many subscripts in entry reference", N);
1482
1483                else
1484                   Set_Etype (N,  Etype (P));
1485                end if;
1486
1487                return;
1488
1489             elsif Is_Record_Type (Array_Type)
1490               and then Remote_AST_I_Dereference (P)
1491             then
1492                return;
1493
1494             elsif Array_Type = Any_Type then
1495                Set_Etype (N, Any_Type);
1496                return;
1497
1498             --  Here we definitely have a bad indexing
1499
1500             else
1501                if Nkind (Parent (N)) = N_Requeue_Statement
1502                  and then Present (Pent) and then Ekind (Pent) = E_Entry
1503                then
1504                   Error_Msg_N
1505                     ("REQUEUE does not permit parameters", First (Exprs));
1506
1507                elsif Is_Entity_Name (P)
1508                  and then Etype (P) = Standard_Void_Type
1509                then
1510                   Error_Msg_NE ("incorrect use of&", P, Entity (P));
1511
1512                else
1513                   Error_Msg_N ("array type required in indexed component", P);
1514                end if;
1515
1516                Set_Etype (N, Any_Type);
1517                return;
1518             end if;
1519
1520             Index := First_Index (Array_Type);
1521             while Present (Index) and then Present (Exp) loop
1522                if not Has_Compatible_Type (Exp, Etype (Index)) then
1523                   Wrong_Type (Exp, Etype (Index));
1524                   Set_Etype (N, Any_Type);
1525                   return;
1526                end if;
1527
1528                Next_Index (Index);
1529                Next (Exp);
1530             end loop;
1531
1532             Set_Etype (N, Component_Type (Array_Type));
1533
1534             if Present (Index) then
1535                Error_Msg_N
1536                  ("too few subscripts in array reference", First (Exprs));
1537
1538             elsif Present (Exp) then
1539                Error_Msg_N ("too many subscripts in array reference", Exp);
1540             end if;
1541          end if;
1542       end Process_Indexed_Component;
1543
1544       ----------------------------------------
1545       -- Process_Indexed_Component_Or_Slice --
1546       ----------------------------------------
1547
1548       procedure Process_Indexed_Component_Or_Slice is
1549       begin
1550          Exp := First (Exprs);
1551          while Present (Exp) loop
1552             Analyze_Expression (Exp);
1553             Next (Exp);
1554          end loop;
1555
1556          Exp := First (Exprs);
1557
1558          --  If one index is present, and it is a subtype name, then the
1559          --  node denotes a slice (note that the case of an explicit range
1560          --  for a slice was already built as an N_Slice node in the first
1561          --  place, so that case is not handled here).
1562
1563          --  We use a replace rather than a rewrite here because this is one
1564          --  of the cases in which the tree built by the parser is plain wrong.
1565
1566          if No (Next (Exp))
1567            and then Is_Entity_Name (Exp)
1568            and then Is_Type (Entity (Exp))
1569          then
1570             Replace (N,
1571                Make_Slice (Sloc (N),
1572                  Prefix => P,
1573                  Discrete_Range => New_Copy (Exp)));
1574             Analyze (N);
1575
1576          --  Otherwise (more than one index present, or single index is not
1577          --  a subtype name), then we have the indexed component case.
1578
1579          else
1580             Process_Indexed_Component;
1581          end if;
1582       end Process_Indexed_Component_Or_Slice;
1583
1584       ------------------------------------------
1585       -- Process_Overloaded_Indexed_Component --
1586       ------------------------------------------
1587
1588       procedure Process_Overloaded_Indexed_Component is
1589          Exp   : Node_Id;
1590          I     : Interp_Index;
1591          It    : Interp;
1592          Typ   : Entity_Id;
1593          Index : Node_Id;
1594          Found : Boolean;
1595
1596       begin
1597          Set_Etype (N, Any_Type);
1598
1599          Get_First_Interp (P, I, It);
1600          while Present (It.Nam) loop
1601             Typ := It.Typ;
1602
1603             if Is_Access_Type (Typ) then
1604                Typ := Designated_Type (Typ);
1605                Error_Msg_NW (Warn_On_Dereference, "?implicit dereference", N);
1606             end if;
1607
1608             if Is_Array_Type (Typ) then
1609
1610                --  Got a candidate: verify that index types are compatible
1611
1612                Index := First_Index (Typ);
1613                Found := True;
1614                Exp := First (Exprs);
1615                while Present (Index) and then Present (Exp) loop
1616                   if Has_Compatible_Type (Exp, Etype (Index)) then
1617                      null;
1618                   else
1619                      Found := False;
1620                      Remove_Interp (I);
1621                      exit;
1622                   end if;
1623
1624                   Next_Index (Index);
1625                   Next (Exp);
1626                end loop;
1627
1628                if Found and then No (Index) and then No (Exp) then
1629                   Add_One_Interp (N,
1630                      Etype (Component_Type (Typ)),
1631                      Etype (Component_Type (Typ)));
1632                end if;
1633             end if;
1634
1635             Get_Next_Interp (I, It);
1636          end loop;
1637
1638          if Etype (N) = Any_Type then
1639             Error_Msg_N ("no legal interpetation for indexed component", N);
1640             Set_Is_Overloaded (N, False);
1641          end if;
1642
1643          End_Interp_List;
1644       end Process_Overloaded_Indexed_Component;
1645
1646    --  Start of processing for Analyze_Indexed_Component_Form
1647
1648    begin
1649       --  Get name of array, function or type
1650
1651       Analyze (P);
1652       if Nkind (N) = N_Function_Call
1653         or else Nkind (N) = N_Procedure_Call_Statement
1654       then
1655          --  If P is an explicit dereference whose prefix is of a
1656          --  remote access-to-subprogram type, then N has already
1657          --  been rewritten as a subprogram call and analyzed.
1658
1659          return;
1660       end if;
1661
1662       pragma Assert (Nkind (N) = N_Indexed_Component);
1663
1664       P_T := Base_Type (Etype (P));
1665
1666       if Is_Entity_Name (P)
1667         or else Nkind (P) = N_Operator_Symbol
1668       then
1669          U_N := Entity (P);
1670
1671          if Ekind (U_N) in Type_Kind then
1672
1673             --  Reformat node as a type conversion
1674
1675             E := Remove_Head (Exprs);
1676
1677             if Present (First (Exprs)) then
1678                Error_Msg_N
1679                 ("argument of type conversion must be single expression", N);
1680             end if;
1681
1682             Change_Node (N, N_Type_Conversion);
1683             Set_Subtype_Mark (N, P);
1684             Set_Etype (N, U_N);
1685             Set_Expression (N, E);
1686
1687             --  After changing the node, call for the specific Analysis
1688             --  routine directly, to avoid a double call to the expander.
1689
1690             Analyze_Type_Conversion (N);
1691             return;
1692          end if;
1693
1694          if Is_Overloadable (U_N) then
1695             Process_Function_Call;
1696
1697          elsif Ekind (Etype (P)) = E_Subprogram_Type
1698            or else (Is_Access_Type (Etype (P))
1699                       and then
1700                     Ekind (Designated_Type (Etype (P))) = E_Subprogram_Type)
1701          then
1702             --  Call to access_to-subprogram with possible implicit dereference
1703
1704             Process_Function_Call;
1705
1706          elsif Is_Generic_Subprogram (U_N) then
1707
1708             --  A common beginner's (or C++ templates fan) error
1709
1710             Error_Msg_N ("generic subprogram cannot be called", N);
1711             Set_Etype (N, Any_Type);
1712             return;
1713
1714          else
1715             Process_Indexed_Component_Or_Slice;
1716          end if;
1717
1718       --  If not an entity name, prefix is an expression that may denote
1719       --  an array or an access-to-subprogram.
1720
1721       else
1722          if Ekind (P_T) = E_Subprogram_Type
1723            or else (Is_Access_Type (P_T)
1724                      and then
1725                     Ekind (Designated_Type (P_T)) = E_Subprogram_Type)
1726          then
1727             Process_Function_Call;
1728
1729          elsif Nkind (P) = N_Selected_Component
1730            and then Is_Overloadable (Entity (Selector_Name (P)))
1731          then
1732             Process_Function_Call;
1733
1734          else
1735             --  Indexed component, slice, or a call to a member of a family
1736             --  entry, which will be converted to an entry call later.
1737
1738             Process_Indexed_Component_Or_Slice;
1739          end if;
1740       end if;
1741    end Analyze_Indexed_Component_Form;
1742
1743    ------------------------
1744    -- Analyze_Logical_Op --
1745    ------------------------
1746
1747    procedure Analyze_Logical_Op (N : Node_Id) is
1748       L     : constant Node_Id := Left_Opnd (N);
1749       R     : constant Node_Id := Right_Opnd (N);
1750       Op_Id : Entity_Id := Entity (N);
1751
1752    begin
1753       Set_Etype (N, Any_Type);
1754       Candidate_Type := Empty;
1755
1756       Analyze_Expression (L);
1757       Analyze_Expression (R);
1758
1759       if Present (Op_Id) then
1760
1761          if Ekind (Op_Id) = E_Operator then
1762             Find_Boolean_Types (L, R, Op_Id, N);
1763          else
1764             Add_One_Interp (N, Op_Id, Etype (Op_Id));
1765          end if;
1766
1767       else
1768          Op_Id := Get_Name_Entity_Id (Chars (N));
1769          while Present (Op_Id) loop
1770             if Ekind (Op_Id) = E_Operator then
1771                Find_Boolean_Types (L, R, Op_Id, N);
1772             else
1773                Analyze_User_Defined_Binary_Op (N, Op_Id);
1774             end if;
1775
1776             Op_Id := Homonym (Op_Id);
1777          end loop;
1778       end if;
1779
1780       Operator_Check (N);
1781    end Analyze_Logical_Op;
1782
1783    ---------------------------
1784    -- Analyze_Membership_Op --
1785    ---------------------------
1786
1787    procedure Analyze_Membership_Op (N : Node_Id) is
1788       L     : constant Node_Id := Left_Opnd (N);
1789       R     : constant Node_Id := Right_Opnd (N);
1790
1791       Index : Interp_Index;
1792       It    : Interp;
1793       Found : Boolean := False;
1794       I_F   : Interp_Index;
1795       T_F   : Entity_Id;
1796
1797       procedure Try_One_Interp (T1 : Entity_Id);
1798       --  Routine to try one proposed interpretation. Note that the context
1799       --  of the operation plays no role in resolving the arguments, so that
1800       --  if there is more than one interpretation of the operands that is
1801       --  compatible with a membership test, the operation is ambiguous.
1802
1803       --------------------
1804       -- Try_One_Interp --
1805       --------------------
1806
1807       procedure Try_One_Interp (T1 : Entity_Id) is
1808       begin
1809          if Has_Compatible_Type (R, T1) then
1810             if Found
1811               and then Base_Type (T1) /= Base_Type (T_F)
1812             then
1813                It := Disambiguate (L, I_F, Index, Any_Type);
1814
1815                if It = No_Interp then
1816                   Ambiguous_Operands (N);
1817                   Set_Etype (L, Any_Type);
1818                   return;
1819
1820                else
1821                   T_F := It.Typ;
1822                end if;
1823
1824             else
1825                Found := True;
1826                T_F   := T1;
1827                I_F   := Index;
1828             end if;
1829
1830             Set_Etype (L, T_F);
1831          end if;
1832
1833       end Try_One_Interp;
1834
1835    --  Start of processing for Analyze_Membership_Op
1836
1837    begin
1838       Analyze_Expression (L);
1839
1840       if Nkind (R) = N_Range
1841         or else (Nkind (R) = N_Attribute_Reference
1842                   and then Attribute_Name (R) = Name_Range)
1843       then
1844          Analyze (R);
1845
1846          if not Is_Overloaded (L) then
1847             Try_One_Interp (Etype (L));
1848
1849          else
1850             Get_First_Interp (L, Index, It);
1851             while Present (It.Typ) loop
1852                Try_One_Interp (It.Typ);
1853                Get_Next_Interp (Index, It);
1854             end loop;
1855          end if;
1856
1857       --  If not a range, it can only be a subtype mark, or else there
1858       --  is a more basic error, to be diagnosed in Find_Type.
1859
1860       else
1861          Find_Type (R);
1862
1863          if Is_Entity_Name (R) then
1864             Check_Fully_Declared (Entity (R), R);
1865          end if;
1866       end if;
1867
1868       --  Compatibility between expression and subtype mark or range is
1869       --  checked during resolution. The result of the operation is Boolean
1870       --  in any case.
1871
1872       Set_Etype (N, Standard_Boolean);
1873    end Analyze_Membership_Op;
1874
1875    ----------------------
1876    -- Analyze_Negation --
1877    ----------------------
1878
1879    procedure Analyze_Negation (N : Node_Id) is
1880       R     : constant Node_Id := Right_Opnd (N);
1881       Op_Id : Entity_Id := Entity (N);
1882
1883    begin
1884       Set_Etype (N, Any_Type);
1885       Candidate_Type := Empty;
1886
1887       Analyze_Expression (R);
1888
1889       if Present (Op_Id) then
1890          if Ekind (Op_Id) = E_Operator then
1891             Find_Negation_Types (R, Op_Id, N);
1892          else
1893             Add_One_Interp (N, Op_Id, Etype (Op_Id));
1894          end if;
1895
1896       else
1897          Op_Id := Get_Name_Entity_Id (Chars (N));
1898          while Present (Op_Id) loop
1899             if Ekind (Op_Id) = E_Operator then
1900                Find_Negation_Types (R, Op_Id, N);
1901             else
1902                Analyze_User_Defined_Unary_Op (N, Op_Id);
1903             end if;
1904
1905             Op_Id := Homonym (Op_Id);
1906          end loop;
1907       end if;
1908
1909       Operator_Check (N);
1910    end Analyze_Negation;
1911
1912    ------------------
1913    -- Analyze_Null --
1914    ------------------
1915
1916    procedure Analyze_Null (N : Node_Id) is
1917    begin
1918       Set_Etype (N, Any_Access);
1919    end Analyze_Null;
1920
1921    ----------------------
1922    -- Analyze_One_Call --
1923    ----------------------
1924
1925    procedure Analyze_One_Call
1926       (N          : Node_Id;
1927        Nam        : Entity_Id;
1928        Report     : Boolean;
1929        Success    : out Boolean;
1930        Skip_First : Boolean := False)
1931    is
1932       Actuals    : constant List_Id   := Parameter_Associations (N);
1933       Prev_T     : constant Entity_Id := Etype (N);
1934       Formal     : Entity_Id;
1935       Actual     : Node_Id;
1936       Is_Indexed : Boolean := False;
1937       Subp_Type  : constant Entity_Id := Etype (Nam);
1938       Norm_OK    : Boolean;
1939
1940       procedure Indicate_Name_And_Type;
1941       --  If candidate interpretation matches, indicate name and type of
1942       --  result on call node.
1943
1944       ----------------------------
1945       -- Indicate_Name_And_Type --
1946       ----------------------------
1947
1948       procedure Indicate_Name_And_Type is
1949       begin
1950          Add_One_Interp (N, Nam, Etype (Nam));
1951          Success := True;
1952
1953          --  If the prefix of the call is a name, indicate the entity
1954          --  being called. If it is not a name,  it is an expression that
1955          --  denotes an access to subprogram or else an entry or family. In
1956          --  the latter case, the name is a selected component, and the entity
1957          --  being called is noted on the selector.
1958
1959          if not Is_Type (Nam) then
1960             if Is_Entity_Name (Name (N))
1961               or else Nkind (Name (N)) = N_Operator_Symbol
1962             then
1963                Set_Entity (Name (N), Nam);
1964
1965             elsif Nkind (Name (N)) = N_Selected_Component then
1966                Set_Entity (Selector_Name (Name (N)),  Nam);
1967             end if;
1968          end if;
1969
1970          if Debug_Flag_E and not Report then
1971             Write_Str (" Overloaded call ");
1972             Write_Int (Int (N));
1973             Write_Str (" compatible with ");
1974             Write_Int (Int (Nam));
1975             Write_Eol;
1976          end if;
1977       end Indicate_Name_And_Type;
1978
1979    --  Start of processing for Analyze_One_Call
1980
1981    begin
1982       Success := False;
1983
1984       --  If the subprogram has no formals, or if all the formals have
1985       --  defaults, and the return type is an array type, the node may
1986       --  denote an indexing of the result of a parameterless call.
1987
1988       if Needs_No_Actuals (Nam)
1989         and then Present (Actuals)
1990       then
1991          if Is_Array_Type (Subp_Type) then
1992             Is_Indexed := Try_Indexed_Call (N, Nam, Subp_Type);
1993
1994          elsif Is_Access_Type (Subp_Type)
1995            and then Is_Array_Type (Designated_Type (Subp_Type))
1996          then
1997             Is_Indexed :=
1998               Try_Indexed_Call (N, Nam, Designated_Type (Subp_Type));
1999
2000          --  The prefix can also be a parameterless function that returns an
2001          --  access to subprogram. in which case this is an indirect call.
2002
2003          elsif Is_Access_Type (Subp_Type)
2004            and then Ekind (Designated_Type (Subp_Type))  = E_Subprogram_Type
2005          then
2006             Is_Indexed := Try_Indirect_Call (N, Nam, Subp_Type);
2007          end if;
2008
2009       end if;
2010
2011       Normalize_Actuals (N, Nam, (Report and not Is_Indexed), Norm_OK);
2012
2013       if not Norm_OK then
2014
2015          --  Mismatch in number or names of parameters
2016
2017          if Debug_Flag_E then
2018             Write_Str (" normalization fails in call ");
2019             Write_Int (Int (N));
2020             Write_Str (" with subprogram ");
2021             Write_Int (Int (Nam));
2022             Write_Eol;
2023          end if;
2024
2025       --  If the context expects a function call, discard any interpretation
2026       --  that is a procedure. If the node is not overloaded, leave as is for
2027       --  better error reporting when type mismatch is found.
2028
2029       elsif Nkind (N) = N_Function_Call
2030         and then Is_Overloaded (Name (N))
2031         and then Ekind (Nam) = E_Procedure
2032       then
2033          return;
2034
2035       --  Ditto for function calls in a procedure context
2036
2037       elsif Nkind (N) = N_Procedure_Call_Statement
2038          and then Is_Overloaded (Name (N))
2039          and then Etype (Nam) /= Standard_Void_Type
2040       then
2041          return;
2042
2043       elsif not Present (Actuals) then
2044
2045          --  If Normalize succeeds, then there are default parameters for
2046          --  all formals.
2047
2048          Indicate_Name_And_Type;
2049
2050       elsif Ekind (Nam) = E_Operator then
2051          if Nkind (N) = N_Procedure_Call_Statement then
2052             return;
2053          end if;
2054
2055          --  This can occur when the prefix of the call is an operator
2056          --  name or an expanded name whose selector is an operator name.
2057
2058          Analyze_Operator_Call (N, Nam);
2059
2060          if Etype (N) /= Prev_T then
2061
2062             --  There may be a user-defined operator that hides the
2063             --  current interpretation. We must check for this independently
2064             --  of the analysis of the call with the user-defined operation,
2065             --  because the parameter names may be wrong and yet the hiding
2066             --  takes place. Fixes b34014o.
2067
2068             if Is_Overloaded (Name (N)) then
2069                declare
2070                   I  : Interp_Index;
2071                   It : Interp;
2072
2073                begin
2074                   Get_First_Interp (Name (N), I, It);
2075                   while Present (It.Nam) loop
2076                      if Ekind (It.Nam) /= E_Operator
2077                         and then Hides_Op (It.Nam, Nam)
2078                         and then
2079                           Has_Compatible_Type
2080                             (First_Actual (N), Etype (First_Formal (It.Nam)))
2081                         and then (No (Next_Actual (First_Actual (N)))
2082                            or else Has_Compatible_Type
2083                             (Next_Actual (First_Actual (N)),
2084                              Etype (Next_Formal (First_Formal (It.Nam)))))
2085                      then
2086                         Set_Etype (N, Prev_T);
2087                         return;
2088                      end if;
2089
2090                      Get_Next_Interp (I, It);
2091                   end loop;
2092                end;
2093             end if;
2094
2095             --  If operator matches formals, record its name on the call.
2096             --  If the operator is overloaded, Resolve will select the
2097             --  correct one from the list of interpretations. The call
2098             --  node itself carries the first candidate.
2099
2100             Set_Entity (Name (N), Nam);
2101             Success := True;
2102
2103          elsif Report and then Etype (N) = Any_Type then
2104             Error_Msg_N ("incompatible arguments for operator", N);
2105          end if;
2106
2107       else
2108          --  Normalize_Actuals has chained the named associations in the
2109          --  correct order of the formals.
2110
2111          Actual := First_Actual (N);
2112          Formal := First_Formal (Nam);
2113
2114          --  If we are analyzing a call rewritten from object notation,
2115          --  skip first actual, which may be rewritten later as an
2116          --  explicit dereference.
2117
2118          if Skip_First then
2119             Next_Actual (Actual);
2120             Next_Formal (Formal);
2121          end if;
2122
2123          while Present (Actual) and then Present (Formal) loop
2124             if Nkind (Parent (Actual)) /= N_Parameter_Association
2125               or else Chars (Selector_Name (Parent (Actual))) = Chars (Formal)
2126             then
2127                if Has_Compatible_Type (Actual, Etype (Formal)) then
2128                   Next_Actual (Actual);
2129                   Next_Formal (Formal);
2130
2131                else
2132                   if Debug_Flag_E then
2133                      Write_Str (" type checking fails in call ");
2134                      Write_Int (Int (N));
2135                      Write_Str (" with formal ");
2136                      Write_Int (Int (Formal));
2137                      Write_Str (" in subprogram ");
2138                      Write_Int (Int (Nam));
2139                      Write_Eol;
2140                   end if;
2141
2142                   if Report and not Is_Indexed then
2143
2144                      --  Ada 2005 (AI-251): Complete the error notification
2145                      --  to help new Ada 2005 users
2146
2147                      if Is_Class_Wide_Type (Etype (Formal))
2148                        and then Is_Interface (Etype (Etype (Formal)))
2149                        and then not Interface_Present_In_Ancestor
2150                                       (Typ   => Etype (Actual),
2151                                        Iface => Etype (Etype (Formal)))
2152                      then
2153                         Error_Msg_NE
2154                           ("(Ada 2005) does not implement interface }",
2155                            Actual, Etype (Etype (Formal)));
2156                      end if;
2157
2158                      Wrong_Type (Actual, Etype (Formal));
2159
2160                      if Nkind (Actual) = N_Op_Eq
2161                        and then Nkind (Left_Opnd (Actual)) = N_Identifier
2162                      then
2163                         Formal := First_Formal (Nam);
2164                         while Present (Formal) loop
2165                            if Chars (Left_Opnd (Actual)) = Chars (Formal) then
2166                               Error_Msg_N
2167                                 ("possible misspelling of `='>`!", Actual);
2168                               exit;
2169                            end if;
2170
2171                            Next_Formal (Formal);
2172                         end loop;
2173                      end if;
2174
2175                      if All_Errors_Mode then
2176                         Error_Msg_Sloc := Sloc (Nam);
2177
2178                         if Is_Overloadable (Nam)
2179                           and then Present (Alias (Nam))
2180                           and then not Comes_From_Source (Nam)
2181                         then
2182                            Error_Msg_NE
2183                              ("  =='> in call to &#(inherited)!", Actual, Nam);
2184
2185                         elsif Ekind (Nam) = E_Subprogram_Type then
2186                            declare
2187                               Access_To_Subprogram_Typ :
2188                                 constant Entity_Id :=
2189                                   Defining_Identifier
2190                                     (Associated_Node_For_Itype (Nam));
2191                            begin
2192                               Error_Msg_NE (
2193                                 "  =='> in call to dereference of &#!",
2194                                 Actual, Access_To_Subprogram_Typ);
2195                            end;
2196
2197                         else
2198                            Error_Msg_NE ("  =='> in call to &#!", Actual, Nam);
2199
2200                         end if;
2201                      end if;
2202                   end if;
2203
2204                   return;
2205                end if;
2206
2207             else
2208                --  Normalize_Actuals has verified that a default value exists
2209                --  for this formal. Current actual names a subsequent formal.
2210
2211                Next_Formal (Formal);
2212             end if;
2213          end loop;
2214
2215          --  On exit, all actuals match
2216
2217          Indicate_Name_And_Type;
2218       end if;
2219    end Analyze_One_Call;
2220
2221    ---------------------------
2222    -- Analyze_Operator_Call --
2223    ---------------------------
2224
2225    procedure Analyze_Operator_Call (N : Node_Id; Op_Id : Entity_Id) is
2226       Op_Name : constant Name_Id := Chars (Op_Id);
2227       Act1    : constant Node_Id := First_Actual (N);
2228       Act2    : constant Node_Id := Next_Actual (Act1);
2229
2230    begin
2231       --  Binary operator case
2232
2233       if Present (Act2) then
2234
2235          --  If more than two operands, then not binary operator after all
2236
2237          if Present (Next_Actual (Act2)) then
2238             return;
2239
2240          elsif     Op_Name = Name_Op_Add
2241            or else Op_Name = Name_Op_Subtract
2242            or else Op_Name = Name_Op_Multiply
2243            or else Op_Name = Name_Op_Divide
2244            or else Op_Name = Name_Op_Mod
2245            or else Op_Name = Name_Op_Rem
2246            or else Op_Name = Name_Op_Expon
2247          then
2248             Find_Arithmetic_Types (Act1, Act2, Op_Id, N);
2249
2250          elsif     Op_Name =  Name_Op_And
2251            or else Op_Name = Name_Op_Or
2252            or else Op_Name = Name_Op_Xor
2253          then
2254             Find_Boolean_Types (Act1, Act2, Op_Id, N);
2255
2256          elsif     Op_Name = Name_Op_Lt
2257            or else Op_Name = Name_Op_Le
2258            or else Op_Name = Name_Op_Gt
2259            or else Op_Name = Name_Op_Ge
2260          then
2261             Find_Comparison_Types (Act1, Act2, Op_Id,  N);
2262
2263          elsif     Op_Name = Name_Op_Eq
2264            or else Op_Name = Name_Op_Ne
2265          then
2266             Find_Equality_Types (Act1, Act2, Op_Id,  N);
2267
2268          elsif     Op_Name = Name_Op_Concat then
2269             Find_Concatenation_Types (Act1, Act2, Op_Id, N);
2270
2271          --  Is this else null correct, or should it be an abort???
2272
2273          else
2274             null;
2275          end if;
2276
2277       --  Unary operator case
2278
2279       else
2280          if Op_Name = Name_Op_Subtract or else
2281             Op_Name = Name_Op_Add      or else
2282             Op_Name = Name_Op_Abs
2283          then
2284             Find_Unary_Types (Act1, Op_Id, N);
2285
2286          elsif
2287             Op_Name = Name_Op_Not
2288          then
2289             Find_Negation_Types (Act1, Op_Id, N);
2290
2291          --  Is this else null correct, or should it be an abort???
2292
2293          else
2294             null;
2295          end if;
2296       end if;
2297    end Analyze_Operator_Call;
2298
2299    -------------------------------------------
2300    -- Analyze_Overloaded_Selected_Component --
2301    -------------------------------------------
2302
2303    procedure Analyze_Overloaded_Selected_Component (N : Node_Id) is
2304       Nam   : constant Node_Id := Prefix (N);
2305       Sel   : constant Node_Id := Selector_Name (N);
2306       Comp  : Entity_Id;
2307       I     : Interp_Index;
2308       It    : Interp;
2309       T     : Entity_Id;
2310
2311    begin
2312       Set_Etype (Sel, Any_Type);
2313
2314       Get_First_Interp (Nam, I, It);
2315       while Present (It.Typ) loop
2316          if Is_Access_Type (It.Typ) then
2317             T := Designated_Type (It.Typ);
2318             Error_Msg_NW (Warn_On_Dereference, "?implicit dereference", N);
2319          else
2320             T := It.Typ;
2321          end if;
2322
2323          if Is_Record_Type (T) then
2324             Comp := First_Entity (T);
2325             while Present (Comp) loop
2326                if Chars (Comp) = Chars (Sel)
2327                  and then Is_Visible_Component (Comp)
2328                then
2329                   Set_Entity_With_Style_Check (Sel, Comp);
2330                   Generate_Reference (Comp, Sel);
2331
2332                   Set_Etype (Sel, Etype (Comp));
2333                   Add_One_Interp (N, Etype (Comp), Etype (Comp));
2334
2335                   --  This also specifies a candidate to resolve the name.
2336                   --  Further overloading will be resolved from context.
2337
2338                   Set_Etype (Nam, It.Typ);
2339                end if;
2340
2341                Next_Entity (Comp);
2342             end loop;
2343
2344          elsif Is_Concurrent_Type (T) then
2345             Comp := First_Entity (T);
2346             while Present (Comp)
2347               and then Comp /= First_Private_Entity (T)
2348             loop
2349                if Chars (Comp) = Chars (Sel) then
2350                   if Is_Overloadable (Comp) then
2351                      Add_One_Interp (Sel, Comp, Etype (Comp));
2352                   else
2353                      Set_Entity_With_Style_Check (Sel, Comp);
2354                      Generate_Reference (Comp, Sel);
2355                   end if;
2356
2357                   Set_Etype (Sel, Etype (Comp));
2358                   Set_Etype (N,   Etype (Comp));
2359                   Set_Etype (Nam, It.Typ);
2360
2361                   --  For access type case, introduce explicit deference for
2362                   --  more uniform treatment of entry calls.
2363
2364                   if Is_Access_Type (Etype (Nam)) then
2365                      Insert_Explicit_Dereference (Nam);
2366                      Error_Msg_NW
2367                        (Warn_On_Dereference, "?implicit dereference", N);
2368                   end if;
2369                end if;
2370
2371                Next_Entity (Comp);
2372             end loop;
2373
2374             Set_Is_Overloaded (N, Is_Overloaded (Sel));
2375          end if;
2376
2377          Get_Next_Interp (I, It);
2378       end loop;
2379
2380       if Etype (N) = Any_Type then
2381          Error_Msg_NE ("undefined selector& for overloaded prefix", N, Sel);
2382          Set_Entity (Sel, Any_Id);
2383          Set_Etype  (Sel, Any_Type);
2384       end if;
2385    end Analyze_Overloaded_Selected_Component;
2386
2387    ----------------------------------
2388    -- Analyze_Qualified_Expression --
2389    ----------------------------------
2390
2391    procedure Analyze_Qualified_Expression (N : Node_Id) is
2392       Mark : constant Entity_Id := Subtype_Mark (N);
2393       T    : Entity_Id;
2394
2395    begin
2396       Set_Etype (N, Any_Type);
2397       Find_Type (Mark);
2398       T := Entity (Mark);
2399
2400       if T = Any_Type then
2401          return;
2402       end if;
2403
2404       Check_Fully_Declared (T, N);
2405       Analyze_Expression (Expression (N));
2406       Set_Etype  (N, T);
2407    end Analyze_Qualified_Expression;
2408
2409    -------------------
2410    -- Analyze_Range --
2411    -------------------
2412
2413    procedure Analyze_Range (N : Node_Id) is
2414       L        : constant Node_Id := Low_Bound (N);
2415       H        : constant Node_Id := High_Bound (N);
2416       I1, I2   : Interp_Index;
2417       It1, It2 : Interp;
2418
2419       procedure Check_Common_Type (T1, T2 : Entity_Id);
2420       --  Verify the compatibility of two types,  and choose the
2421       --  non universal one if the other is universal.
2422
2423       procedure Check_High_Bound (T : Entity_Id);
2424       --  Test one interpretation of the low bound against all those
2425       --  of the high bound.
2426
2427       procedure Check_Universal_Expression (N : Node_Id);
2428       --  In Ada83, reject bounds of a universal range that are not
2429       --  literals or entity names.
2430
2431       -----------------------
2432       -- Check_Common_Type --
2433       -----------------------
2434
2435       procedure Check_Common_Type (T1, T2 : Entity_Id) is
2436       begin
2437          if Covers (T1, T2) or else Covers (T2, T1) then
2438             if T1 = Universal_Integer
2439               or else T1 = Universal_Real
2440               or else T1 = Any_Character
2441             then
2442                Add_One_Interp (N, Base_Type (T2), Base_Type (T2));
2443
2444             elsif T1 = T2 then
2445                Add_One_Interp (N, T1, T1);
2446
2447             else
2448                Add_One_Interp (N, Base_Type (T1), Base_Type (T1));
2449             end if;
2450          end if;
2451       end Check_Common_Type;
2452
2453       ----------------------
2454       -- Check_High_Bound --
2455       ----------------------
2456
2457       procedure Check_High_Bound (T : Entity_Id) is
2458       begin
2459          if not Is_Overloaded (H) then
2460             Check_Common_Type (T, Etype (H));
2461          else
2462             Get_First_Interp (H, I2, It2);
2463             while Present (It2.Typ) loop
2464                Check_Common_Type (T, It2.Typ);
2465                Get_Next_Interp (I2, It2);
2466             end loop;
2467          end if;
2468       end Check_High_Bound;
2469
2470       -----------------------------
2471       -- Is_Universal_Expression --
2472       -----------------------------
2473
2474       procedure Check_Universal_Expression (N : Node_Id) is
2475       begin
2476          if Etype (N) = Universal_Integer
2477            and then Nkind (N) /= N_Integer_Literal
2478            and then not Is_Entity_Name (N)
2479            and then Nkind (N) /= N_Attribute_Reference
2480          then
2481             Error_Msg_N ("illegal bound in discrete range", N);
2482          end if;
2483       end Check_Universal_Expression;
2484
2485    --  Start of processing for Analyze_Range
2486
2487    begin
2488       Set_Etype (N, Any_Type);
2489       Analyze_Expression (L);
2490       Analyze_Expression (H);
2491
2492       if Etype (L) = Any_Type or else Etype (H) = Any_Type then
2493          return;
2494
2495       else
2496          if not Is_Overloaded (L) then
2497             Check_High_Bound (Etype (L));
2498          else
2499             Get_First_Interp (L, I1, It1);
2500             while Present (It1.Typ) loop
2501                Check_High_Bound (It1.Typ);
2502                Get_Next_Interp (I1, It1);
2503             end loop;
2504          end if;
2505
2506          --  If result is Any_Type, then we did not find a compatible pair
2507
2508          if Etype (N) = Any_Type then
2509             Error_Msg_N ("incompatible types in range ", N);
2510          end if;
2511       end if;
2512
2513       if Ada_Version = Ada_83
2514         and then
2515           (Nkind (Parent (N)) = N_Loop_Parameter_Specification
2516              or else Nkind (Parent (N)) = N_Constrained_Array_Definition)
2517       then
2518          Check_Universal_Expression (L);
2519          Check_Universal_Expression (H);
2520       end if;
2521    end Analyze_Range;
2522
2523    -----------------------
2524    -- Analyze_Reference --
2525    -----------------------
2526
2527    procedure Analyze_Reference (N : Node_Id) is
2528       P        : constant Node_Id := Prefix (N);
2529       Acc_Type : Entity_Id;
2530    begin
2531       Analyze (P);
2532       Acc_Type := Create_Itype (E_Allocator_Type, N);
2533       Set_Etype                    (Acc_Type,  Acc_Type);
2534       Init_Size_Align              (Acc_Type);
2535       Set_Directly_Designated_Type (Acc_Type, Etype (P));
2536       Set_Etype (N, Acc_Type);
2537    end Analyze_Reference;
2538
2539    --------------------------------
2540    -- Analyze_Selected_Component --
2541    --------------------------------
2542
2543    --  Prefix is a record type or a task or protected type. In the
2544    --  later case, the selector must denote a visible entry.
2545
2546    procedure Analyze_Selected_Component (N : Node_Id) is
2547       Name        : constant Node_Id := Prefix (N);
2548       Sel         : constant Node_Id := Selector_Name (N);
2549       Comp        : Entity_Id;
2550       Entity_List : Entity_Id;
2551       Prefix_Type : Entity_Id;
2552       Pent        : Entity_Id := Empty;
2553       Act_Decl    : Node_Id;
2554       In_Scope    : Boolean;
2555       Parent_N    : Node_Id;
2556
2557    --  Start of processing for Analyze_Selected_Component
2558
2559    begin
2560       Set_Etype (N, Any_Type);
2561
2562       if Is_Overloaded (Name) then
2563          Analyze_Overloaded_Selected_Component (N);
2564          return;
2565
2566       elsif Etype (Name) = Any_Type then
2567          Set_Entity (Sel, Any_Id);
2568          Set_Etype (Sel, Any_Type);
2569          return;
2570
2571       else
2572          Prefix_Type := Etype (Name);
2573       end if;
2574
2575       if Is_Access_Type (Prefix_Type) then
2576
2577          --  A RACW object can never be used as prefix of a selected
2578          --  component since that means it is dereferenced without
2579          --  being a controlling operand of a dispatching operation
2580          --  (RM E.2.2(15)).
2581
2582          if Is_Remote_Access_To_Class_Wide_Type (Prefix_Type)
2583            and then Comes_From_Source (N)
2584          then
2585             Error_Msg_N
2586               ("invalid dereference of a remote access to class-wide value",
2587                N);
2588
2589          --  Normal case of selected component applied to access type
2590
2591          else
2592             Error_Msg_NW (Warn_On_Dereference, "?implicit dereference", N);
2593
2594             if Is_Entity_Name (Name) then
2595                Pent := Entity (Name);
2596             elsif Nkind (Name) = N_Selected_Component
2597               and then Is_Entity_Name (Selector_Name (Name))
2598             then
2599                Pent := Entity (Selector_Name (Name));
2600             end if;
2601
2602             Process_Implicit_Dereference_Prefix (Pent, Name);
2603          end if;
2604
2605          Prefix_Type := Designated_Type (Prefix_Type);
2606       end if;
2607
2608       if Ekind (Prefix_Type) = E_Private_Subtype then
2609          Prefix_Type := Base_Type (Prefix_Type);
2610       end if;
2611
2612       Entity_List := Prefix_Type;
2613
2614       --  For class-wide types, use the entity list of the root type. This
2615       --  indirection is specially important for private extensions because
2616       --  only the root type get switched (not the class-wide type).
2617
2618       if Is_Class_Wide_Type (Prefix_Type) then
2619          Entity_List := Root_Type (Prefix_Type);
2620       end if;
2621
2622       Comp := First_Entity (Entity_List);
2623
2624       --  If the selector has an original discriminant, the node appears in
2625       --  an instance. Replace the discriminant with the corresponding one
2626       --  in the current discriminated type. For nested generics, this must
2627       --  be done transitively, so note the new original discriminant.
2628
2629       if Nkind (Sel) = N_Identifier
2630         and then Present (Original_Discriminant (Sel))
2631       then
2632          Comp := Find_Corresponding_Discriminant (Sel, Prefix_Type);
2633
2634          --  Mark entity before rewriting, for completeness and because
2635          --  subsequent semantic checks might examine the original node.
2636
2637          Set_Entity (Sel, Comp);
2638          Rewrite (Selector_Name (N),
2639            New_Occurrence_Of (Comp, Sloc (N)));
2640          Set_Original_Discriminant (Selector_Name (N), Comp);
2641          Set_Etype (N, Etype (Comp));
2642
2643          if Is_Access_Type (Etype (Name)) then
2644             Insert_Explicit_Dereference (Name);
2645             Error_Msg_NW (Warn_On_Dereference, "?implicit dereference", N);
2646          end if;
2647
2648       elsif Is_Record_Type (Prefix_Type) then
2649
2650          --  Find component with given name
2651
2652          while Present (Comp) loop
2653             if Chars (Comp) = Chars (Sel)
2654               and then Is_Visible_Component (Comp)
2655             then
2656                Set_Entity_With_Style_Check (Sel, Comp);
2657                Generate_Reference (Comp, Sel);
2658
2659                Set_Etype (Sel, Etype (Comp));
2660
2661                if Ekind (Comp) = E_Discriminant then
2662                   if Is_Unchecked_Union (Base_Type (Prefix_Type)) then
2663                      Error_Msg_N
2664                        ("cannot reference discriminant of Unchecked_Union",
2665                         Sel);
2666                   end if;
2667
2668                   if Is_Generic_Type (Prefix_Type)
2669                        or else
2670                      Is_Generic_Type (Root_Type (Prefix_Type))
2671                   then
2672                      Set_Original_Discriminant (Sel, Comp);
2673                   end if;
2674                end if;
2675
2676                --  Resolve the prefix early otherwise it is not possible to
2677                --  build the actual subtype of the component: it may need
2678                --  to duplicate this prefix and duplication is only allowed
2679                --  on fully resolved expressions.
2680
2681                Resolve (Name);
2682
2683                --  Ada 2005 (AI-50217): Check wrong use of incomplete type.
2684                --  Example:
2685
2686                --    limited with Pkg;
2687                --    package Pkg is
2688                --       type Acc_Inc is access Pkg.T;
2689                --       X : Acc_Inc;
2690                --       N : Natural := X.all.Comp; -- ERROR
2691                --    end Pkg;
2692
2693                if Nkind (Name) = N_Explicit_Dereference
2694                  and then From_With_Type (Etype (Prefix (Name)))
2695                  and then not Is_Potentially_Use_Visible (Etype (Name))
2696                then
2697                   Error_Msg_NE
2698                     ("premature usage of incomplete}", Prefix (Name),
2699                      Etype (Prefix (Name)));
2700                end if;
2701
2702                --  We never need an actual subtype for the case of a selection
2703                --  for a indexed component of a non-packed array, since in
2704                --  this case gigi generates all the checks and can find the
2705                --  necessary bounds information.
2706
2707                --  We also do not need an actual subtype for the case of
2708                --  a first, last, length, or range attribute applied to a
2709                --  non-packed array, since gigi can again get the bounds in
2710                --  these cases (gigi cannot handle the packed case, since it
2711                --  has the bounds of the packed array type, not the original
2712                --  bounds of the type). However, if the prefix is itself a
2713                --  selected component, as in a.b.c (i), gigi may regard a.b.c
2714                --  as a dynamic-sized temporary, so we do generate an actual
2715                --  subtype for this case.
2716
2717                Parent_N := Parent (N);
2718
2719                if not Is_Packed (Etype (Comp))
2720                  and then
2721                    ((Nkind (Parent_N) = N_Indexed_Component
2722                       and then Nkind (Name) /= N_Selected_Component)
2723                      or else
2724                       (Nkind (Parent_N) = N_Attribute_Reference
2725                          and then (Attribute_Name (Parent_N) = Name_First
2726                                      or else
2727                                    Attribute_Name (Parent_N) = Name_Last
2728                                      or else
2729                                    Attribute_Name (Parent_N) = Name_Length
2730                                      or else
2731                                    Attribute_Name (Parent_N) = Name_Range)))
2732                then
2733                   Set_Etype (N, Etype (Comp));
2734
2735                --  If full analysis is not enabled, we do not generate an
2736                --  actual subtype, because in the absence of expansion
2737                --  reference to a formal of a protected type, for example,
2738                --  will not be properly transformed, and will lead to
2739                --  out-of-scope references in gigi.
2740
2741                --  In all other cases, we currently build an actual subtype.
2742                --  It seems likely that many of these cases can be avoided,
2743                --  but right now, the front end makes direct references to the
2744                --  bounds (e.g. in generating a length check), and if we do
2745                --  not make an actual subtype, we end up getting a direct
2746                --  reference to a discriminant, which will not do.
2747
2748                elsif Full_Analysis then
2749                   Act_Decl :=
2750                     Build_Actual_Subtype_Of_Component (Etype (Comp), N);
2751                   Insert_Action (N, Act_Decl);
2752
2753                   if No (Act_Decl) then
2754                      Set_Etype (N, Etype (Comp));
2755
2756                   else
2757                      --  Component type depends on discriminants. Enter the
2758                      --  main attributes of the subtype.
2759
2760                      declare
2761                         Subt : constant Entity_Id :=
2762                                  Defining_Identifier (Act_Decl);
2763
2764                      begin
2765                         Set_Etype (Subt, Base_Type (Etype (Comp)));
2766                         Set_Ekind (Subt, Ekind (Etype (Comp)));
2767                         Set_Etype (N, Subt);
2768                      end;
2769                   end if;
2770
2771                --  If Full_Analysis not enabled, just set the Etype
2772
2773                else
2774                   Set_Etype (N, Etype (Comp));
2775                end if;
2776
2777                return;
2778             end if;
2779
2780             Next_Entity (Comp);
2781          end loop;
2782
2783          --  Ada 2005 (AI-252)
2784
2785          if Ada_Version >= Ada_05
2786            and then Is_Tagged_Type (Prefix_Type)
2787            and then Try_Object_Operation (N)
2788          then
2789             return;
2790
2791             --  If the transformation fails, it will be necessary to redo the
2792             --  analysis with all errors enabled, to indicate candidate
2793             --  interpretations and reasons for each failure ???
2794
2795          end if;
2796
2797       elsif Is_Private_Type (Prefix_Type) then
2798
2799          --  Allow access only to discriminants of the type. If the type has
2800          --  no full view, gigi uses the parent type for the components, so we
2801          --  do the same here.
2802
2803          if No (Full_View (Prefix_Type)) then
2804             Entity_List := Root_Type (Base_Type (Prefix_Type));
2805             Comp := First_Entity (Entity_List);
2806          end if;
2807
2808          while Present (Comp) loop
2809             if Chars (Comp) = Chars (Sel) then
2810                if Ekind (Comp) = E_Discriminant then
2811                   Set_Entity_With_Style_Check (Sel, Comp);
2812                   Generate_Reference (Comp, Sel);
2813
2814                   Set_Etype (Sel, Etype (Comp));
2815                   Set_Etype (N,   Etype (Comp));
2816
2817                   if Is_Generic_Type (Prefix_Type)
2818                     or else
2819                      Is_Generic_Type (Root_Type (Prefix_Type))
2820                   then
2821                      Set_Original_Discriminant (Sel, Comp);
2822                   end if;
2823
2824                else
2825                   Error_Msg_NE
2826                     ("invisible selector for }",
2827                      N, First_Subtype (Prefix_Type));
2828                   Set_Entity (Sel, Any_Id);
2829                   Set_Etype (N, Any_Type);
2830                end if;
2831
2832                return;
2833             end if;
2834
2835             Next_Entity (Comp);
2836          end loop;
2837
2838       elsif Is_Concurrent_Type (Prefix_Type) then
2839
2840          --  Prefix is concurrent type. Find visible operation with given name
2841          --  For a task, this can only include entries or discriminants if the
2842          --  task type is not an enclosing scope. If it is an enclosing scope
2843          --  (e.g. in an inner task) then all entities are visible, but the
2844          --  prefix must denote the enclosing scope, i.e. can only be a direct
2845          --  name or an expanded name.
2846
2847          Set_Etype (Sel,  Any_Type);
2848          In_Scope := In_Open_Scopes (Prefix_Type);
2849
2850          while Present (Comp) loop
2851             if Chars (Comp) = Chars (Sel) then
2852                if Is_Overloadable (Comp) then
2853                   Add_One_Interp (Sel, Comp, Etype (Comp));
2854
2855                elsif Ekind (Comp) = E_Discriminant
2856                  or else Ekind (Comp) = E_Entry_Family
2857                  or else (In_Scope
2858                    and then Is_Entity_Name (Name))
2859                then
2860                   Set_Entity_With_Style_Check (Sel, Comp);
2861                   Generate_Reference (Comp, Sel);
2862
2863                else
2864                   goto Next_Comp;
2865                end if;
2866
2867                Set_Etype (Sel, Etype (Comp));
2868                Set_Etype (N,   Etype (Comp));
2869
2870                if Ekind (Comp) = E_Discriminant then
2871                   Set_Original_Discriminant (Sel, Comp);
2872                end if;
2873
2874                --  For access type case, introduce explicit deference for more
2875                --  uniform treatment of entry calls.
2876
2877                if Is_Access_Type (Etype (Name)) then
2878                   Insert_Explicit_Dereference (Name);
2879                   Error_Msg_NW
2880                     (Warn_On_Dereference, "?implicit dereference", N);
2881                end if;
2882             end if;
2883
2884             <<Next_Comp>>
2885                Next_Entity (Comp);
2886                exit when not In_Scope
2887                  and then
2888                    Comp = First_Private_Entity (Base_Type (Prefix_Type));
2889          end loop;
2890
2891          Set_Is_Overloaded (N, Is_Overloaded (Sel));
2892
2893       else
2894          --  Invalid prefix
2895
2896          Error_Msg_NE ("invalid prefix in selected component&", N, Sel);
2897       end if;
2898
2899       --  If N still has no type, the component is not defined in the prefix
2900
2901       if Etype (N) = Any_Type then
2902
2903          --  If the prefix is a single concurrent object, use its name in the
2904          --  error message, rather than that of its anonymous type.
2905
2906          if Is_Concurrent_Type (Prefix_Type)
2907            and then Is_Internal_Name (Chars (Prefix_Type))
2908            and then not Is_Derived_Type (Prefix_Type)
2909            and then Is_Entity_Name (Name)
2910          then
2911
2912             Error_Msg_Node_2 := Entity (Name);
2913             Error_Msg_NE ("no selector& for&", N, Sel);
2914
2915             Check_Misspelled_Selector (Entity_List, Sel);
2916
2917          elsif Is_Generic_Type (Prefix_Type)
2918            and then Ekind (Prefix_Type) = E_Record_Type_With_Private
2919            and then Prefix_Type /= Etype (Prefix_Type)
2920            and then Is_Record_Type (Etype (Prefix_Type))
2921          then
2922             --  If this is a derived formal type, the parent may have
2923             --  different visibility at this point. Try for an inherited
2924             --  component before reporting an error.
2925
2926             Set_Etype (Prefix (N), Etype (Prefix_Type));
2927             Analyze_Selected_Component (N);
2928             return;
2929
2930          elsif Ekind (Prefix_Type) = E_Record_Subtype_With_Private
2931            and then Is_Generic_Actual_Type (Prefix_Type)
2932            and then Present (Full_View (Prefix_Type))
2933          then
2934             --  Similarly, if this the actual for a formal derived type, the
2935             --  component inherited from the generic parent may not be visible
2936             --  in the actual, but the selected component is legal.
2937
2938             declare
2939                Comp : Entity_Id;
2940
2941             begin
2942                Comp :=
2943                  First_Component (Generic_Parent_Type (Parent (Prefix_Type)));
2944                while Present (Comp) loop
2945                   if Chars (Comp) = Chars (Sel) then
2946                      Set_Entity_With_Style_Check (Sel, Comp);
2947                      Set_Etype (Sel, Etype (Comp));
2948                      Set_Etype (N,   Etype (Comp));
2949                      exit;
2950                   end if;
2951
2952                   Next_Component (Comp);
2953                end loop;
2954
2955                pragma Assert (Etype (N) /= Any_Type);
2956             end;
2957
2958          else
2959             if Ekind (Prefix_Type) = E_Record_Subtype then
2960
2961                --  Check whether this is a component of the base type
2962                --  which is absent from a statically constrained subtype.
2963                --  This will raise constraint error at run-time, but is
2964                --  not a compile-time error. When the selector is illegal
2965                --  for base type as well fall through and generate a
2966                --  compilation error anyway.
2967
2968                Comp := First_Component (Base_Type (Prefix_Type));
2969                while Present (Comp) loop
2970                   if Chars (Comp) = Chars (Sel)
2971                     and then Is_Visible_Component (Comp)
2972                   then
2973                      Set_Entity_With_Style_Check (Sel, Comp);
2974                      Generate_Reference (Comp, Sel);
2975                      Set_Etype (Sel, Etype (Comp));
2976                      Set_Etype (N,   Etype (Comp));
2977
2978                      --  Emit appropriate message. Gigi will replace the
2979                      --  node subsequently with the appropriate Raise.
2980
2981                      Apply_Compile_Time_Constraint_Error
2982                        (N, "component not present in }?",
2983                         CE_Discriminant_Check_Failed,
2984                         Ent => Prefix_Type, Rep => False);
2985                      Set_Raises_Constraint_Error (N);
2986                      return;
2987                   end if;
2988
2989                   Next_Component (Comp);
2990                end loop;
2991
2992             end if;
2993
2994             Error_Msg_Node_2 := First_Subtype (Prefix_Type);
2995             Error_Msg_NE ("no selector& for}", N, Sel);
2996
2997             Check_Misspelled_Selector (Entity_List, Sel);
2998
2999          end if;
3000
3001          Set_Entity (Sel, Any_Id);
3002          Set_Etype (Sel, Any_Type);
3003       end if;
3004    end Analyze_Selected_Component;
3005
3006    ---------------------------
3007    -- Analyze_Short_Circuit --
3008    ---------------------------
3009
3010    procedure Analyze_Short_Circuit (N : Node_Id) is
3011       L   : constant Node_Id := Left_Opnd  (N);
3012       R   : constant Node_Id := Right_Opnd (N);
3013       Ind : Interp_Index;
3014       It  : Interp;
3015
3016    begin
3017       Analyze_Expression (L);
3018       Analyze_Expression (R);
3019       Set_Etype (N, Any_Type);
3020
3021       if not Is_Overloaded (L) then
3022
3023          if Root_Type (Etype (L)) = Standard_Boolean
3024            and then Has_Compatible_Type (R, Etype (L))
3025          then
3026             Add_One_Interp (N, Etype (L), Etype (L));
3027          end if;
3028
3029       else
3030          Get_First_Interp (L, Ind, It);
3031          while Present (It.Typ) loop
3032             if Root_Type (It.Typ) = Standard_Boolean
3033               and then Has_Compatible_Type (R, It.Typ)
3034             then
3035                Add_One_Interp (N, It.Typ, It.Typ);
3036             end if;
3037
3038             Get_Next_Interp (Ind, It);
3039          end loop;
3040       end if;
3041
3042       --  Here we have failed to find an interpretation. Clearly we
3043       --  know that it is not the case that both operands can have
3044       --  an interpretation of Boolean, but this is by far the most
3045       --  likely intended interpretation. So we simply resolve both
3046       --  operands as Booleans, and at least one of these resolutions
3047       --  will generate an error message, and we do not need to give
3048       --  a further error message on the short circuit operation itself.
3049
3050       if Etype (N) = Any_Type then
3051          Resolve (L, Standard_Boolean);
3052          Resolve (R, Standard_Boolean);
3053          Set_Etype (N, Standard_Boolean);
3054       end if;
3055    end Analyze_Short_Circuit;
3056
3057    -------------------
3058    -- Analyze_Slice --
3059    -------------------
3060
3061    procedure Analyze_Slice (N : Node_Id) is
3062       P          : constant Node_Id := Prefix (N);
3063       D          : constant Node_Id := Discrete_Range (N);
3064       Array_Type : Entity_Id;
3065
3066       procedure Analyze_Overloaded_Slice;
3067       --  If the prefix is overloaded, select those interpretations that
3068       --  yield a one-dimensional array type.
3069
3070       ------------------------------
3071       -- Analyze_Overloaded_Slice --
3072       ------------------------------
3073
3074       procedure Analyze_Overloaded_Slice is
3075          I   : Interp_Index;
3076          It  : Interp;
3077          Typ : Entity_Id;
3078
3079       begin
3080          Set_Etype (N, Any_Type);
3081
3082          Get_First_Interp (P, I, It);
3083          while Present (It.Nam) loop
3084             Typ := It.Typ;
3085
3086             if Is_Access_Type (Typ) then
3087                Typ := Designated_Type (Typ);
3088                Error_Msg_NW (Warn_On_Dereference, "?implicit dereference", N);
3089             end if;
3090
3091             if Is_Array_Type (Typ)
3092               and then Number_Dimensions (Typ) = 1
3093               and then Has_Compatible_Type (D, Etype (First_Index (Typ)))
3094             then
3095                Add_One_Interp (N, Typ, Typ);
3096             end if;
3097
3098             Get_Next_Interp (I, It);
3099          end loop;
3100
3101          if Etype (N) = Any_Type then
3102             Error_Msg_N ("expect array type in prefix of slice",  N);
3103          end if;
3104       end Analyze_Overloaded_Slice;
3105
3106    --  Start of processing for Analyze_Slice
3107
3108    begin
3109       Analyze (P);
3110       Analyze (D);
3111
3112       if Is_Overloaded (P) then
3113          Analyze_Overloaded_Slice;
3114
3115       else
3116          Array_Type := Etype (P);
3117          Set_Etype (N, Any_Type);
3118
3119          if Is_Access_Type (Array_Type) then
3120             Array_Type := Designated_Type (Array_Type);
3121             Error_Msg_NW (Warn_On_Dereference, "?implicit dereference", N);
3122          end if;
3123
3124          if not Is_Array_Type (Array_Type) then
3125             Wrong_Type (P, Any_Array);
3126
3127          elsif Number_Dimensions (Array_Type) > 1 then
3128             Error_Msg_N
3129               ("type is not one-dimensional array in slice prefix", N);
3130
3131          elsif not
3132            Has_Compatible_Type (D, Etype (First_Index (Array_Type)))
3133          then
3134             Wrong_Type (D, Etype (First_Index (Array_Type)));
3135
3136          else
3137             Set_Etype (N, Array_Type);
3138          end if;
3139       end if;
3140    end Analyze_Slice;
3141
3142    -----------------------------
3143    -- Analyze_Type_Conversion --
3144    -----------------------------
3145
3146    procedure Analyze_Type_Conversion (N : Node_Id) is
3147       Expr : constant Node_Id := Expression (N);
3148       T    : Entity_Id;
3149
3150    begin
3151       --  If Conversion_OK is set, then the Etype is already set, and the
3152       --  only processing required is to analyze the expression. This is
3153       --  used to construct certain "illegal" conversions which are not
3154       --  allowed by Ada semantics, but can be handled OK by Gigi, see
3155       --  Sinfo for further details.
3156
3157       if Conversion_OK (N) then
3158          Analyze (Expr);
3159          return;
3160       end if;
3161
3162       --  Otherwise full type analysis is required, as well as some semantic
3163       --  checks to make sure the argument of the conversion is appropriate.
3164
3165       Find_Type (Subtype_Mark (N));
3166       T := Entity (Subtype_Mark (N));
3167       Set_Etype (N, T);
3168       Check_Fully_Declared (T, N);
3169       Analyze_Expression (Expr);
3170       Validate_Remote_Type_Type_Conversion (N);
3171
3172       --  Only remaining step is validity checks on the argument. These
3173       --  are skipped if the conversion does not come from the source.
3174
3175       if not Comes_From_Source (N) then
3176          return;
3177
3178       elsif Nkind (Expr) = N_Null then
3179          Error_Msg_N ("argument of conversion cannot be null", N);
3180          Error_Msg_N ("\use qualified expression instead", N);
3181          Set_Etype (N, Any_Type);
3182
3183       elsif Nkind (Expr) = N_Aggregate then
3184          Error_Msg_N ("argument of conversion cannot be aggregate", N);
3185          Error_Msg_N ("\use qualified expression instead", N);
3186
3187       elsif Nkind (Expr) = N_Allocator then
3188          Error_Msg_N ("argument of conversion cannot be an allocator", N);
3189          Error_Msg_N ("\use qualified expression instead", N);
3190
3191       elsif Nkind (Expr) = N_String_Literal then
3192          Error_Msg_N ("argument of conversion cannot be string literal", N);
3193          Error_Msg_N ("\use qualified expression instead", N);
3194
3195       elsif Nkind (Expr) = N_Character_Literal then
3196          if Ada_Version = Ada_83 then
3197             Resolve (Expr, T);
3198          else
3199             Error_Msg_N ("argument of conversion cannot be character literal",
3200               N);
3201             Error_Msg_N ("\use qualified expression instead", N);
3202          end if;
3203
3204       elsif Nkind (Expr) = N_Attribute_Reference
3205         and then
3206           (Attribute_Name (Expr) = Name_Access            or else
3207            Attribute_Name (Expr) = Name_Unchecked_Access  or else
3208            Attribute_Name (Expr) = Name_Unrestricted_Access)
3209       then
3210          Error_Msg_N ("argument of conversion cannot be access", N);
3211          Error_Msg_N ("\use qualified expression instead", N);
3212       end if;
3213    end Analyze_Type_Conversion;
3214
3215    ----------------------
3216    -- Analyze_Unary_Op --
3217    ----------------------
3218
3219    procedure Analyze_Unary_Op (N : Node_Id) is
3220       R     : constant Node_Id := Right_Opnd (N);
3221       Op_Id : Entity_Id := Entity (N);
3222
3223    begin
3224       Set_Etype (N, Any_Type);
3225       Candidate_Type := Empty;
3226
3227       Analyze_Expression (R);
3228
3229       if Present (Op_Id) then
3230          if Ekind (Op_Id) = E_Operator then
3231             Find_Unary_Types (R, Op_Id,  N);
3232          else
3233             Add_One_Interp (N, Op_Id, Etype (Op_Id));
3234          end if;
3235
3236       else
3237          Op_Id := Get_Name_Entity_Id (Chars (N));
3238          while Present (Op_Id) loop
3239             if Ekind (Op_Id) = E_Operator then
3240                if No (Next_Entity (First_Entity (Op_Id))) then
3241                   Find_Unary_Types (R, Op_Id,  N);
3242                end if;
3243
3244             elsif Is_Overloadable (Op_Id) then
3245                Analyze_User_Defined_Unary_Op (N, Op_Id);
3246             end if;
3247
3248             Op_Id := Homonym (Op_Id);
3249          end loop;
3250       end if;
3251
3252       Operator_Check (N);
3253    end Analyze_Unary_Op;
3254
3255    ----------------------------------
3256    -- Analyze_Unchecked_Expression --
3257    ----------------------------------
3258
3259    procedure Analyze_Unchecked_Expression (N : Node_Id) is
3260    begin
3261       Analyze (Expression (N), Suppress => All_Checks);
3262       Set_Etype (N, Etype (Expression (N)));
3263       Save_Interps (Expression (N), N);
3264    end Analyze_Unchecked_Expression;
3265
3266    ---------------------------------------
3267    -- Analyze_Unchecked_Type_Conversion --
3268    ---------------------------------------
3269
3270    procedure Analyze_Unchecked_Type_Conversion (N : Node_Id) is
3271    begin
3272       Find_Type (Subtype_Mark (N));
3273       Analyze_Expression (Expression (N));
3274       Set_Etype (N, Entity (Subtype_Mark (N)));
3275    end Analyze_Unchecked_Type_Conversion;
3276
3277    ------------------------------------
3278    -- Analyze_User_Defined_Binary_Op --
3279    ------------------------------------
3280
3281    procedure Analyze_User_Defined_Binary_Op
3282      (N     : Node_Id;
3283       Op_Id : Entity_Id)
3284    is
3285    begin
3286       --  Only do analysis if the operator Comes_From_Source, since otherwise
3287       --  the operator was generated by the expander, and all such operators
3288       --  always refer to the operators in package Standard.
3289
3290       if Comes_From_Source (N) then
3291          declare
3292             F1 : constant Entity_Id := First_Formal (Op_Id);
3293             F2 : constant Entity_Id := Next_Formal (F1);
3294
3295          begin
3296             --  Verify that Op_Id is a visible binary function. Note that since
3297             --  we know Op_Id is overloaded, potentially use visible means use
3298             --  visible for sure (RM 9.4(11)).
3299
3300             if Ekind (Op_Id) = E_Function
3301               and then Present (F2)
3302               and then (Is_Immediately_Visible (Op_Id)
3303                          or else Is_Potentially_Use_Visible (Op_Id))
3304               and then Has_Compatible_Type (Left_Opnd (N), Etype (F1))
3305               and then Has_Compatible_Type (Right_Opnd (N), Etype (F2))
3306             then
3307                Add_One_Interp (N, Op_Id, Etype (Op_Id));
3308
3309                if Debug_Flag_E then
3310                   Write_Str ("user defined operator ");
3311                   Write_Name (Chars (Op_Id));
3312                   Write_Str (" on node ");
3313                   Write_Int (Int (N));
3314                   Write_Eol;
3315                end if;
3316             end if;
3317          end;
3318       end if;
3319    end Analyze_User_Defined_Binary_Op;
3320
3321    -----------------------------------
3322    -- Analyze_User_Defined_Unary_Op --
3323    -----------------------------------
3324
3325    procedure Analyze_User_Defined_Unary_Op
3326      (N     : Node_Id;
3327       Op_Id : Entity_Id)
3328    is
3329    begin
3330       --  Only do analysis if the operator Comes_From_Source, since otherwise
3331       --  the operator was generated by the expander, and all such operators
3332       --  always refer to the operators in package Standard.
3333
3334       if Comes_From_Source (N) then
3335          declare
3336             F : constant Entity_Id := First_Formal (Op_Id);
3337
3338          begin
3339             --  Verify that Op_Id is a visible unary function. Note that since
3340             --  we know Op_Id is overloaded, potentially use visible means use
3341             --  visible for sure (RM 9.4(11)).
3342
3343             if Ekind (Op_Id) = E_Function
3344               and then No (Next_Formal (F))
3345               and then (Is_Immediately_Visible (Op_Id)
3346                          or else Is_Potentially_Use_Visible (Op_Id))
3347               and then Has_Compatible_Type (Right_Opnd (N), Etype (F))
3348             then
3349                Add_One_Interp (N, Op_Id, Etype (Op_Id));
3350             end if;
3351          end;
3352       end if;
3353    end Analyze_User_Defined_Unary_Op;
3354
3355    ---------------------------
3356    -- Check_Arithmetic_Pair --
3357    ---------------------------
3358
3359    procedure Check_Arithmetic_Pair
3360      (T1, T2 : Entity_Id;
3361       Op_Id  : Entity_Id;
3362       N      : Node_Id)
3363    is
3364       Op_Name : constant Name_Id   := Chars (Op_Id);
3365
3366       function Has_Fixed_Op (Typ : Entity_Id; Op : Entity_Id) return Boolean;
3367       --  Check whether the fixed-point type Typ has a user-defined operator
3368       --  (multiplication or division) that should hide the corresponding
3369       --  predefined operator. Used to implement Ada 2005 AI-264, to make
3370       --  such operators more visible and therefore useful.
3371
3372       function Specific_Type (T1, T2 : Entity_Id) return Entity_Id;
3373       --  Get specific type (i.e. non-universal type if there is one)
3374
3375       ------------------
3376       -- Has_Fixed_Op --
3377       ------------------
3378
3379       function Has_Fixed_Op (Typ : Entity_Id; Op : Entity_Id) return Boolean is
3380          Ent : Entity_Id;
3381          F1  : Entity_Id;
3382          F2  : Entity_Id;
3383
3384       begin
3385          --  The operation is treated as primitive if it is declared in the
3386          --  same scope as the type, and therefore on the same entity chain.
3387
3388          Ent := Next_Entity (Typ);
3389          while Present (Ent) loop
3390             if Chars (Ent) = Chars (Op) then
3391                F1 := First_Formal (Ent);
3392                F2 := Next_Formal (F1);
3393
3394                --  The operation counts as primitive if either operand or
3395                --  result are of the given type, and both operands are fixed
3396                --  point types.
3397
3398                if (Etype (F1) = Typ
3399                     and then Is_Fixed_Point_Type (Etype (F2)))
3400
3401                  or else
3402                    (Etype (F2) = Typ
3403                      and then Is_Fixed_Point_Type (Etype (F1)))
3404
3405                  or else
3406                    (Etype (Ent) = Typ
3407                      and then Is_Fixed_Point_Type (Etype (F1))
3408                      and then Is_Fixed_Point_Type (Etype (F2)))
3409                then
3410                   return True;
3411                end if;
3412             end if;
3413
3414             Next_Entity (Ent);
3415          end loop;
3416
3417          return False;
3418       end Has_Fixed_Op;
3419
3420       -------------------
3421       -- Specific_Type --
3422       -------------------
3423
3424       function Specific_Type (T1, T2 : Entity_Id) return Entity_Id is
3425       begin
3426          if T1 = Universal_Integer or else T1 = Universal_Real then
3427             return Base_Type (T2);
3428          else
3429             return Base_Type (T1);
3430          end if;
3431       end Specific_Type;
3432
3433    --  Start of processing for Check_Arithmetic_Pair
3434
3435    begin
3436       if Op_Name = Name_Op_Add or else Op_Name = Name_Op_Subtract then
3437
3438          if Is_Numeric_Type (T1)
3439            and then Is_Numeric_Type (T2)
3440            and then (Covers (T1, T2) or else Covers (T2, T1))
3441          then
3442             Add_One_Interp (N, Op_Id, Specific_Type (T1, T2));
3443          end if;
3444
3445       elsif Op_Name = Name_Op_Multiply or else Op_Name = Name_Op_Divide then
3446
3447          if Is_Fixed_Point_Type (T1)
3448            and then (Is_Fixed_Point_Type (T2)
3449                        or else T2 = Universal_Real)
3450          then
3451             --  If Treat_Fixed_As_Integer is set then the Etype is already set
3452             --  and no further processing is required (this is the case of an
3453             --  operator constructed by Exp_Fixd for a fixed point operation)
3454             --  Otherwise add one interpretation with universal fixed result
3455             --  If the operator is given in  functional notation, it comes
3456             --  from source and Fixed_As_Integer cannot apply.
3457
3458             if (Nkind (N) not in N_Op
3459                  or else not Treat_Fixed_As_Integer (N))
3460               and then
3461                 (not (Ada_Version >= Ada_05 and then Has_Fixed_Op (T1, Op_Id))
3462                   or else Nkind (Parent (N)) = N_Type_Conversion)
3463             then
3464                Add_One_Interp (N, Op_Id, Universal_Fixed);
3465             end if;
3466
3467          elsif Is_Fixed_Point_Type (T2)
3468            and then (Nkind (N) not in N_Op
3469                       or else not Treat_Fixed_As_Integer (N))
3470            and then T1 = Universal_Real
3471            and then
3472              (not (Ada_Version >= Ada_05 and then Has_Fixed_Op (T1, Op_Id))
3473                or else Nkind (Parent (N)) = N_Type_Conversion)
3474          then
3475             Add_One_Interp (N, Op_Id, Universal_Fixed);
3476
3477          elsif Is_Numeric_Type (T1)
3478            and then Is_Numeric_Type (T2)
3479            and then (Covers (T1, T2) or else Covers (T2, T1))
3480          then
3481             Add_One_Interp (N, Op_Id, Specific_Type (T1, T2));
3482
3483          elsif Is_Fixed_Point_Type (T1)
3484            and then (Base_Type (T2) = Base_Type (Standard_Integer)
3485                        or else T2 = Universal_Integer)
3486          then
3487             Add_One_Interp (N, Op_Id, T1);
3488
3489          elsif T2 = Universal_Real
3490            and then Base_Type (T1) = Base_Type (Standard_Integer)
3491            and then Op_Name = Name_Op_Multiply
3492          then
3493             Add_One_Interp (N, Op_Id, Any_Fixed);
3494
3495          elsif T1 = Universal_Real
3496            and then Base_Type (T2) = Base_Type (Standard_Integer)
3497          then
3498             Add_One_Interp (N, Op_Id, Any_Fixed);
3499
3500          elsif Is_Fixed_Point_Type (T2)
3501            and then (Base_Type (T1) = Base_Type (Standard_Integer)
3502                        or else T1 = Universal_Integer)
3503            and then Op_Name = Name_Op_Multiply
3504          then
3505             Add_One_Interp (N, Op_Id, T2);
3506
3507          elsif T1 = Universal_Real and then T2 = Universal_Integer then
3508             Add_One_Interp (N, Op_Id, T1);
3509
3510          elsif T2 = Universal_Real
3511            and then T1 = Universal_Integer
3512            and then Op_Name = Name_Op_Multiply
3513          then
3514             Add_One_Interp (N, Op_Id, T2);
3515          end if;
3516
3517       elsif Op_Name = Name_Op_Mod or else Op_Name = Name_Op_Rem then
3518
3519          --  Note: The fixed-point operands case with Treat_Fixed_As_Integer
3520          --  set does not require any special processing, since the Etype is
3521          --  already set (case of operation constructed by Exp_Fixed).
3522
3523          if Is_Integer_Type (T1)
3524            and then (Covers (T1, T2) or else Covers (T2, T1))
3525          then
3526             Add_One_Interp (N, Op_Id, Specific_Type (T1, T2));
3527          end if;
3528
3529       elsif Op_Name = Name_Op_Expon then
3530          if Is_Numeric_Type (T1)
3531            and then not Is_Fixed_Point_Type (T1)
3532            and then (Base_Type (T2) = Base_Type (Standard_Integer)
3533                       or else T2 = Universal_Integer)
3534          then
3535             Add_One_Interp (N, Op_Id, Base_Type (T1));
3536          end if;
3537
3538       else pragma Assert (Nkind (N) in N_Op_Shift);
3539
3540          --  If not one of the predefined operators, the node may be one
3541          --  of the intrinsic functions. Its kind is always specific, and
3542          --  we can use it directly, rather than the name of the operation.
3543
3544          if Is_Integer_Type (T1)
3545            and then (Base_Type (T2) = Base_Type (Standard_Integer)
3546                       or else T2 = Universal_Integer)
3547          then
3548             Add_One_Interp (N, Op_Id, Base_Type (T1));
3549          end if;
3550       end if;
3551    end Check_Arithmetic_Pair;
3552
3553    -------------------------------
3554    -- Check_Misspelled_Selector --
3555    -------------------------------
3556
3557    procedure Check_Misspelled_Selector
3558      (Prefix : Entity_Id;
3559       Sel    : Node_Id)
3560    is
3561       Max_Suggestions   : constant := 2;
3562       Nr_Of_Suggestions : Natural := 0;
3563
3564       Suggestion_1 : Entity_Id := Empty;
3565       Suggestion_2 : Entity_Id := Empty;
3566
3567       Comp : Entity_Id;
3568
3569    begin
3570       --  All the components of the prefix of selector Sel are matched
3571       --  against  Sel and a count is maintained of possible misspellings.
3572       --  When at the end of the analysis there are one or two (not more!)
3573       --  possible misspellings, these misspellings will be suggested as
3574       --  possible correction.
3575
3576       if not (Is_Private_Type (Prefix) or else Is_Record_Type (Prefix)) then
3577
3578          --  Concurrent types should be handled as well ???
3579
3580          return;
3581       end if;
3582
3583       Get_Name_String (Chars (Sel));
3584
3585       declare
3586          S  : constant String (1 .. Name_Len) := Name_Buffer (1 .. Name_Len);
3587
3588       begin
3589          Comp  := First_Entity (Prefix);
3590          while Nr_Of_Suggestions <= Max_Suggestions
3591             and then Present (Comp)
3592          loop
3593             if Is_Visible_Component (Comp) then
3594                Get_Name_String (Chars (Comp));
3595
3596                if Is_Bad_Spelling_Of (Name_Buffer (1 .. Name_Len), S) then
3597                   Nr_Of_Suggestions := Nr_Of_Suggestions + 1;
3598
3599                   case Nr_Of_Suggestions is
3600                      when 1      => Suggestion_1 := Comp;
3601                      when 2      => Suggestion_2 := Comp;
3602                      when others => exit;
3603                   end case;
3604                end if;
3605             end if;
3606
3607             Comp := Next_Entity (Comp);
3608          end loop;
3609
3610          --  Report at most two suggestions
3611
3612          if Nr_Of_Suggestions = 1 then
3613             Error_Msg_NE ("\possible misspelling of&", Sel, Suggestion_1);
3614
3615          elsif Nr_Of_Suggestions = 2 then
3616             Error_Msg_Node_2 := Suggestion_2;
3617             Error_Msg_NE ("\possible misspelling of& or&",
3618               Sel, Suggestion_1);
3619          end if;
3620       end;
3621    end Check_Misspelled_Selector;
3622
3623    ----------------------
3624    -- Defined_In_Scope --
3625    ----------------------
3626
3627    function Defined_In_Scope (T : Entity_Id; S : Entity_Id) return Boolean
3628    is
3629       S1 : constant Entity_Id := Scope (Base_Type (T));
3630    begin
3631       return S1 = S
3632         or else (S1 = System_Aux_Id and then S = Scope (S1));
3633    end Defined_In_Scope;
3634
3635    -------------------
3636    -- Diagnose_Call --
3637    -------------------
3638
3639    procedure Diagnose_Call (N : Node_Id; Nam : Node_Id) is
3640       Actual           : Node_Id;
3641       X                : Interp_Index;
3642       It               : Interp;
3643       Success          : Boolean;
3644       Err_Mode         : Boolean;
3645       New_Nam          : Node_Id;
3646       Void_Interp_Seen : Boolean := False;
3647
3648    begin
3649       if Ada_Version >= Ada_05 then
3650          Actual := First_Actual (N);
3651          while Present (Actual) loop
3652
3653             --  Ada 2005 (AI-50217): Post an error in case of premature
3654             --  usage of an entity from the limited view.
3655
3656             if not Analyzed (Etype (Actual))
3657              and then From_With_Type (Etype (Actual))
3658             then
3659                Error_Msg_Qual_Level := 1;
3660                Error_Msg_NE
3661                 ("missing with_clause for scope of imported type&",
3662                   Actual, Etype (Actual));
3663                Error_Msg_Qual_Level := 0;
3664             end if;
3665
3666             Next_Actual (Actual);
3667          end loop;
3668       end if;
3669
3670       --   Analyze each candidate call again, with full error reporting
3671       --   for each.
3672
3673       Error_Msg_N
3674         ("no candidate interpretations match the actuals:!", Nam);
3675       Err_Mode := All_Errors_Mode;
3676       All_Errors_Mode := True;
3677
3678       --  If this is a call to an operation of a concurrent type,
3679       --  the failed interpretations have been removed from the
3680       --  name. Recover them to provide full diagnostics.
3681
3682       if Nkind (Parent (Nam)) = N_Selected_Component then
3683          Set_Entity (Nam, Empty);
3684          New_Nam := New_Copy_Tree (Parent (Nam));
3685          Set_Is_Overloaded (New_Nam, False);
3686          Set_Is_Overloaded (Selector_Name (New_Nam), False);
3687          Set_Parent (New_Nam, Parent (Parent (Nam)));
3688          Analyze_Selected_Component (New_Nam);
3689          Get_First_Interp (Selector_Name (New_Nam), X, It);
3690       else
3691          Get_First_Interp (Nam, X, It);
3692       end if;
3693
3694       while Present (It.Nam) loop
3695          if Etype (It.Nam) = Standard_Void_Type then
3696             Void_Interp_Seen := True;
3697          end if;
3698
3699          Analyze_One_Call (N, It.Nam, True, Success);
3700          Get_Next_Interp (X, It);
3701       end loop;
3702
3703       if Nkind (N) = N_Function_Call then
3704          Get_First_Interp (Nam, X, It);
3705          while Present (It.Nam) loop
3706             if Ekind (It.Nam) = E_Function
3707               or else Ekind (It.Nam) = E_Operator
3708             then
3709                return;
3710             else
3711                Get_Next_Interp (X, It);
3712             end if;
3713          end loop;
3714
3715          --  If all interpretations are procedures, this deserves a
3716          --  more precise message. Ditto if this appears as the prefix
3717          --  of a selected component, which may be a lexical error.
3718
3719          Error_Msg_N
3720            ("\context requires function call, found procedure name", Nam);
3721
3722          if Nkind (Parent (N)) = N_Selected_Component
3723            and then N = Prefix (Parent (N))
3724          then
3725             Error_Msg_N (
3726               "\period should probably be semicolon", Parent (N));
3727          end if;
3728
3729       elsif Nkind (N) = N_Procedure_Call_Statement
3730         and then not Void_Interp_Seen
3731       then
3732          Error_Msg_N (
3733          "\function name found in procedure call", Nam);
3734       end if;
3735
3736       All_Errors_Mode := Err_Mode;
3737    end Diagnose_Call;
3738
3739    ---------------------------
3740    -- Find_Arithmetic_Types --
3741    ---------------------------
3742
3743    procedure Find_Arithmetic_Types
3744      (L, R  : Node_Id;
3745       Op_Id : Entity_Id;
3746       N     : Node_Id)
3747    is
3748       Index1 : Interp_Index;
3749       Index2 : Interp_Index;
3750       It1    : Interp;
3751       It2    : Interp;
3752
3753       procedure Check_Right_Argument (T : Entity_Id);
3754       --  Check right operand of operator
3755
3756       --------------------------
3757       -- Check_Right_Argument --
3758       --------------------------
3759
3760       procedure Check_Right_Argument (T : Entity_Id) is
3761       begin
3762          if not Is_Overloaded (R) then
3763             Check_Arithmetic_Pair (T, Etype (R), Op_Id,  N);
3764          else
3765             Get_First_Interp (R, Index2, It2);
3766             while Present (It2.Typ) loop
3767                Check_Arithmetic_Pair (T, It2.Typ, Op_Id, N);
3768                Get_Next_Interp (Index2, It2);
3769             end loop;
3770          end if;
3771       end Check_Right_Argument;
3772
3773    --  Start processing for Find_Arithmetic_Types
3774
3775    begin
3776       if not Is_Overloaded (L) then
3777          Check_Right_Argument (Etype (L));
3778
3779       else
3780          Get_First_Interp (L, Index1, It1);
3781          while Present (It1.Typ) loop
3782             Check_Right_Argument (It1.Typ);
3783             Get_Next_Interp (Index1, It1);
3784          end loop;
3785       end if;
3786
3787    end Find_Arithmetic_Types;
3788
3789    ------------------------
3790    -- Find_Boolean_Types --
3791    ------------------------
3792
3793    procedure Find_Boolean_Types
3794      (L, R  : Node_Id;
3795       Op_Id : Entity_Id;
3796       N     : Node_Id)
3797    is
3798       Index : Interp_Index;
3799       It    : Interp;
3800
3801       procedure Check_Numeric_Argument (T : Entity_Id);
3802       --  Special case for logical operations one of whose operands is an
3803       --  integer literal. If both are literal the result is any modular type.
3804
3805       ----------------------------
3806       -- Check_Numeric_Argument --
3807       ----------------------------
3808
3809       procedure Check_Numeric_Argument (T : Entity_Id) is
3810       begin
3811          if T = Universal_Integer then
3812             Add_One_Interp (N, Op_Id, Any_Modular);
3813
3814          elsif Is_Modular_Integer_Type (T) then
3815             Add_One_Interp (N, Op_Id, T);
3816          end if;
3817       end Check_Numeric_Argument;
3818
3819    --  Start of processing for Find_Boolean_Types
3820
3821    begin
3822       if not Is_Overloaded (L) then
3823          if Etype (L) = Universal_Integer
3824            or else Etype (L) = Any_Modular
3825          then
3826             if not Is_Overloaded (R) then
3827                Check_Numeric_Argument (Etype (R));
3828
3829             else
3830                Get_First_Interp (R, Index, It);
3831                while Present (It.Typ) loop
3832                   Check_Numeric_Argument (It.Typ);
3833                   Get_Next_Interp (Index, It);
3834                end loop;
3835             end if;
3836
3837          elsif Valid_Boolean_Arg (Etype (L))
3838            and then Has_Compatible_Type (R, Etype (L))
3839          then
3840             Add_One_Interp (N, Op_Id, Etype (L));
3841          end if;
3842
3843       else
3844          Get_First_Interp (L, Index, It);
3845          while Present (It.Typ) loop
3846             if Valid_Boolean_Arg (It.Typ)
3847               and then Has_Compatible_Type (R, It.Typ)
3848             then
3849                Add_One_Interp (N, Op_Id, It.Typ);
3850             end if;
3851
3852             Get_Next_Interp (Index, It);
3853          end loop;
3854       end if;
3855    end Find_Boolean_Types;
3856
3857    ---------------------------
3858    -- Find_Comparison_Types --
3859    ---------------------------
3860
3861    procedure Find_Comparison_Types
3862      (L, R  : Node_Id;
3863       Op_Id : Entity_Id;
3864       N     : Node_Id)
3865    is
3866       Index : Interp_Index;
3867       It    : Interp;
3868       Found : Boolean := False;
3869       I_F   : Interp_Index;
3870       T_F   : Entity_Id;
3871       Scop  : Entity_Id := Empty;
3872
3873       procedure Try_One_Interp (T1 : Entity_Id);
3874       --  Routine to try one proposed interpretation. Note that the context
3875       --  of the operator plays no role in resolving the arguments, so that
3876       --  if there is more than one interpretation of the operands that is
3877       --  compatible with comparison, the operation is ambiguous.
3878
3879       --------------------
3880       -- Try_One_Interp --
3881       --------------------
3882
3883       procedure Try_One_Interp (T1 : Entity_Id) is
3884       begin
3885
3886          --  If the operator is an expanded name, then the type of the operand
3887          --  must be defined in the corresponding scope. If the type is
3888          --  universal, the context will impose the correct type.
3889
3890          if Present (Scop)
3891             and then not Defined_In_Scope (T1, Scop)
3892             and then T1 /= Universal_Integer
3893             and then T1 /= Universal_Real
3894             and then T1 /= Any_String
3895             and then T1 /= Any_Composite
3896          then
3897             return;
3898          end if;
3899
3900          if Valid_Comparison_Arg (T1)
3901            and then Has_Compatible_Type (R, T1)
3902          then
3903             if Found
3904               and then Base_Type (T1) /= Base_Type (T_F)
3905             then
3906                It := Disambiguate (L, I_F, Index, Any_Type);
3907
3908                if It = No_Interp then
3909                   Ambiguous_Operands (N);
3910                   Set_Etype (L, Any_Type);
3911                   return;
3912
3913                else
3914                   T_F := It.Typ;
3915                end if;
3916
3917             else
3918                Found := True;
3919                T_F   := T1;
3920                I_F   := Index;
3921             end if;
3922
3923             Set_Etype (L, T_F);
3924             Find_Non_Universal_Interpretations (N, R, Op_Id, T1);
3925
3926          end if;
3927       end Try_One_Interp;
3928
3929    --  Start processing for Find_Comparison_Types
3930
3931    begin
3932       --  If left operand is aggregate, the right operand has to
3933       --  provide a usable type for it.
3934
3935       if Nkind (L) = N_Aggregate
3936         and then Nkind (R) /= N_Aggregate
3937       then
3938          Find_Comparison_Types (R, L, Op_Id, N);
3939          return;
3940       end if;
3941
3942       if Nkind (N) = N_Function_Call
3943          and then Nkind (Name (N)) = N_Expanded_Name
3944       then
3945          Scop := Entity (Prefix (Name (N)));
3946
3947          --  The prefix may be a package renaming, and the subsequent test
3948          --  requires the original package.
3949
3950          if Ekind (Scop) = E_Package
3951            and then Present (Renamed_Entity (Scop))
3952          then
3953             Scop := Renamed_Entity (Scop);
3954             Set_Entity (Prefix (Name (N)), Scop);
3955          end if;
3956       end if;
3957
3958       if not Is_Overloaded (L) then
3959          Try_One_Interp (Etype (L));
3960
3961       else
3962          Get_First_Interp (L, Index, It);
3963          while Present (It.Typ) loop
3964             Try_One_Interp (It.Typ);
3965             Get_Next_Interp (Index, It);
3966          end loop;
3967       end if;
3968    end Find_Comparison_Types;
3969
3970    ----------------------------------------
3971    -- Find_Non_Universal_Interpretations --
3972    ----------------------------------------
3973
3974    procedure Find_Non_Universal_Interpretations
3975      (N     : Node_Id;
3976       R     : Node_Id;
3977       Op_Id : Entity_Id;
3978       T1    : Entity_Id)
3979    is
3980       Index : Interp_Index;
3981       It    : Interp;
3982
3983    begin
3984       if T1 = Universal_Integer
3985         or else T1 = Universal_Real
3986       then
3987          if not Is_Overloaded (R) then
3988             Add_One_Interp
3989               (N, Op_Id, Standard_Boolean, Base_Type (Etype (R)));
3990          else
3991             Get_First_Interp (R, Index, It);
3992             while Present (It.Typ) loop
3993                if Covers (It.Typ, T1) then
3994                   Add_One_Interp
3995                     (N, Op_Id, Standard_Boolean, Base_Type (It.Typ));
3996                end if;
3997
3998                Get_Next_Interp (Index, It);
3999             end loop;
4000          end if;
4001       else
4002          Add_One_Interp (N, Op_Id, Standard_Boolean, Base_Type (T1));
4003       end if;
4004    end Find_Non_Universal_Interpretations;
4005
4006    ------------------------------
4007    -- Find_Concatenation_Types --
4008    ------------------------------
4009
4010    procedure Find_Concatenation_Types
4011      (L, R  : Node_Id;
4012       Op_Id : Entity_Id;
4013       N     : Node_Id)
4014    is
4015       Op_Type : constant Entity_Id := Etype (Op_Id);
4016
4017    begin
4018       if Is_Array_Type (Op_Type)
4019         and then not Is_Limited_Type (Op_Type)
4020
4021         and then (Has_Compatible_Type (L, Op_Type)
4022                     or else
4023                   Has_Compatible_Type (L, Component_Type (Op_Type)))
4024
4025         and then (Has_Compatible_Type (R, Op_Type)
4026                     or else
4027                   Has_Compatible_Type (R, Component_Type (Op_Type)))
4028       then
4029          Add_One_Interp (N, Op_Id, Op_Type);
4030       end if;
4031    end Find_Concatenation_Types;
4032
4033    -------------------------
4034    -- Find_Equality_Types --
4035    -------------------------
4036
4037    procedure Find_Equality_Types
4038      (L, R  : Node_Id;
4039       Op_Id : Entity_Id;
4040       N     : Node_Id)
4041    is
4042       Index : Interp_Index;
4043       It    : Interp;
4044       Found : Boolean := False;
4045       I_F   : Interp_Index;
4046       T_F   : Entity_Id;
4047       Scop  : Entity_Id := Empty;
4048
4049       procedure Try_One_Interp (T1 : Entity_Id);
4050       --  The context of the operator plays no role in resolving the
4051       --  arguments,  so that if there is more than one interpretation
4052       --  of the operands that is compatible with equality, the construct
4053       --  is ambiguous and an error can be emitted now, after trying to
4054       --  disambiguate, i.e. applying preference rules.
4055
4056       --------------------
4057       -- Try_One_Interp --
4058       --------------------
4059
4060       procedure Try_One_Interp (T1 : Entity_Id) is
4061       begin
4062          --  If the operator is an expanded name, then the type of the operand
4063          --  must be defined in the corresponding scope. If the type is
4064          --  universal, the context will impose the correct type. An anonymous
4065          --  type for a 'Access reference is also universal in this sense, as
4066          --  the actual type is obtained from context.
4067
4068          if Present (Scop)
4069             and then not Defined_In_Scope (T1, Scop)
4070             and then T1 /= Universal_Integer
4071             and then T1 /= Universal_Real
4072             and then T1 /= Any_Access
4073             and then T1 /= Any_String
4074             and then T1 /= Any_Composite
4075             and then (Ekind (T1) /= E_Access_Subprogram_Type
4076                         or else Comes_From_Source (T1))
4077          then
4078             return;
4079          end if;
4080
4081          --  Ada 2005 (AI-230): Keep restriction imposed by Ada 83 and 95:
4082          --  Do not allow anonymous access types in equality operators.
4083
4084          if Ada_Version < Ada_05
4085            and then Ekind (T1) = E_Anonymous_Access_Type
4086          then
4087             return;
4088          end if;
4089
4090          if T1 /= Standard_Void_Type
4091            and then not Is_Limited_Type (T1)
4092            and then not Is_Limited_Composite (T1)
4093            and then Has_Compatible_Type (R, T1)
4094          then
4095             if Found
4096               and then Base_Type (T1) /= Base_Type (T_F)
4097             then
4098                It := Disambiguate (L, I_F, Index, Any_Type);
4099
4100                if It = No_Interp then
4101                   Ambiguous_Operands (N);
4102                   Set_Etype (L, Any_Type);
4103                   return;
4104
4105                else
4106                   T_F := It.Typ;
4107                end if;
4108
4109             else
4110                Found := True;
4111                T_F   := T1;
4112                I_F   := Index;
4113             end if;
4114
4115             if not Analyzed (L) then
4116                Set_Etype (L, T_F);
4117             end if;
4118
4119             Find_Non_Universal_Interpretations (N, R, Op_Id, T1);
4120
4121             --  Case of operator was not visible, Etype still set to Any_Type
4122
4123             if Etype (N) = Any_Type then
4124                Found := False;
4125             end if;
4126          end if;
4127       end Try_One_Interp;
4128
4129    --  Start of processing for Find_Equality_Types
4130
4131    begin
4132       --  If left operand is aggregate, the right operand has to
4133       --  provide a usable type for it.
4134
4135       if Nkind (L) = N_Aggregate
4136         and then Nkind (R) /= N_Aggregate
4137       then
4138          Find_Equality_Types (R, L, Op_Id, N);
4139          return;
4140       end if;
4141
4142       if Nkind (N) = N_Function_Call
4143          and then Nkind (Name (N)) = N_Expanded_Name
4144       then
4145          Scop := Entity (Prefix (Name (N)));
4146
4147          --  The prefix may be a package renaming, and the subsequent test
4148          --  requires the original package.
4149
4150          if Ekind (Scop) = E_Package
4151            and then Present (Renamed_Entity (Scop))
4152          then
4153             Scop := Renamed_Entity (Scop);
4154             Set_Entity (Prefix (Name (N)), Scop);
4155          end if;
4156       end if;
4157
4158       if not Is_Overloaded (L) then
4159          Try_One_Interp (Etype (L));
4160
4161       else
4162          Get_First_Interp (L, Index, It);
4163          while Present (It.Typ) loop
4164             Try_One_Interp (It.Typ);
4165             Get_Next_Interp (Index, It);
4166          end loop;
4167       end if;
4168    end Find_Equality_Types;
4169
4170    -------------------------
4171    -- Find_Negation_Types --
4172    -------------------------
4173
4174    procedure Find_Negation_Types
4175      (R     : Node_Id;
4176       Op_Id : Entity_Id;
4177       N     : Node_Id)
4178    is
4179       Index : Interp_Index;
4180       It    : Interp;
4181
4182    begin
4183       if not Is_Overloaded (R) then
4184          if Etype (R) = Universal_Integer then
4185             Add_One_Interp (N, Op_Id, Any_Modular);
4186          elsif Valid_Boolean_Arg (Etype (R)) then
4187             Add_One_Interp (N, Op_Id, Etype (R));
4188          end if;
4189
4190       else
4191          Get_First_Interp (R, Index, It);
4192          while Present (It.Typ) loop
4193             if Valid_Boolean_Arg (It.Typ) then
4194                Add_One_Interp (N, Op_Id, It.Typ);
4195             end if;
4196
4197             Get_Next_Interp (Index, It);
4198          end loop;
4199       end if;
4200    end Find_Negation_Types;
4201
4202    ----------------------
4203    -- Find_Unary_Types --
4204    ----------------------
4205
4206    procedure Find_Unary_Types
4207      (R     : Node_Id;
4208       Op_Id : Entity_Id;
4209       N     : Node_Id)
4210    is
4211       Index : Interp_Index;
4212       It    : Interp;
4213
4214    begin
4215       if not Is_Overloaded (R) then
4216          if Is_Numeric_Type (Etype (R)) then
4217             Add_One_Interp (N, Op_Id, Base_Type (Etype (R)));
4218          end if;
4219
4220       else
4221          Get_First_Interp (R, Index, It);
4222          while Present (It.Typ) loop
4223             if Is_Numeric_Type (It.Typ) then
4224                Add_One_Interp (N, Op_Id, Base_Type (It.Typ));
4225             end if;
4226
4227             Get_Next_Interp (Index, It);
4228          end loop;
4229       end if;
4230    end Find_Unary_Types;
4231
4232    ------------------
4233    -- Junk_Operand --
4234    ------------------
4235
4236    function Junk_Operand (N : Node_Id) return Boolean is
4237       Enode : Node_Id;
4238
4239    begin
4240       if Error_Posted (N) then
4241          return False;
4242       end if;
4243
4244       --  Get entity to be tested
4245
4246       if Is_Entity_Name (N)
4247         and then Present (Entity (N))
4248       then
4249          Enode := N;
4250
4251       --  An odd case, a procedure name gets converted to a very peculiar
4252       --  function call, and here is where we detect this happening.
4253
4254       elsif Nkind (N) = N_Function_Call
4255         and then Is_Entity_Name (Name (N))
4256         and then Present (Entity (Name (N)))
4257       then
4258          Enode := Name (N);
4259
4260       --  Another odd case, there are at least some cases of selected
4261       --  components where the selected component is not marked as having
4262       --  an entity, even though the selector does have an entity
4263
4264       elsif Nkind (N) = N_Selected_Component
4265         and then Present (Entity (Selector_Name (N)))
4266       then
4267          Enode := Selector_Name (N);
4268
4269       else
4270          return False;
4271       end if;
4272
4273       --  Now test the entity we got to see if it is a bad case
4274
4275       case Ekind (Entity (Enode)) is
4276
4277          when E_Package =>
4278             Error_Msg_N
4279               ("package name cannot be used as operand", Enode);
4280
4281          when Generic_Unit_Kind =>
4282             Error_Msg_N
4283               ("generic unit name cannot be used as operand", Enode);
4284
4285          when Type_Kind =>
4286             Error_Msg_N
4287               ("subtype name cannot be used as operand", Enode);
4288
4289          when Entry_Kind =>
4290             Error_Msg_N
4291               ("entry name cannot be used as operand", Enode);
4292
4293          when E_Procedure =>
4294             Error_Msg_N
4295               ("procedure name cannot be used as operand", Enode);
4296
4297          when E_Exception =>
4298             Error_Msg_N
4299               ("exception name cannot be used as operand", Enode);
4300
4301          when E_Block | E_Label | E_Loop =>
4302             Error_Msg_N
4303               ("label name cannot be used as operand", Enode);
4304
4305          when others =>
4306             return False;
4307
4308       end case;
4309
4310       return True;
4311    end Junk_Operand;
4312
4313    --------------------
4314    -- Operator_Check --
4315    --------------------
4316
4317    procedure Operator_Check (N : Node_Id) is
4318    begin
4319       Remove_Abstract_Operations (N);
4320
4321       --  Test for case of no interpretation found for operator
4322
4323       if Etype (N) = Any_Type then
4324          declare
4325             L : Node_Id;
4326             R : Node_Id;
4327
4328          begin
4329             R := Right_Opnd (N);
4330
4331             if Nkind (N) in N_Binary_Op then
4332                L := Left_Opnd (N);
4333             else
4334                L := Empty;
4335             end if;
4336
4337             --  If either operand has no type, then don't complain further,
4338             --  since this simply means that we have a propagated error.
4339
4340             if R = Error
4341               or else Etype (R) = Any_Type
4342               or else (Nkind (N) in N_Binary_Op and then Etype (L) = Any_Type)
4343             then
4344                return;
4345
4346             --  We explicitly check for the case of concatenation of component
4347             --  with component to avoid reporting spurious matching array types
4348             --  that might happen to be lurking in distant packages (such as
4349             --  run-time packages). This also prevents inconsistencies in the
4350             --  messages for certain ACVC B tests, which can vary depending on
4351             --  types declared in run-time interfaces. Another improvement when
4352             --  aggregates are present is to look for a well-typed operand.
4353
4354             elsif Present (Candidate_Type)
4355               and then (Nkind (N) /= N_Op_Concat
4356                          or else Is_Array_Type (Etype (L))
4357                          or else Is_Array_Type (Etype (R)))
4358             then
4359
4360                if Nkind (N) = N_Op_Concat then
4361                   if Etype (L) /= Any_Composite
4362                     and then Is_Array_Type (Etype (L))
4363                   then
4364                      Candidate_Type := Etype (L);
4365
4366                   elsif Etype (R) /= Any_Composite
4367                     and then Is_Array_Type (Etype (R))
4368                   then
4369                      Candidate_Type := Etype (R);
4370                   end if;
4371                end if;
4372
4373                Error_Msg_NE
4374                  ("operator for} is not directly visible!",
4375                   N, First_Subtype (Candidate_Type));
4376                Error_Msg_N ("use clause would make operation legal!",  N);
4377                return;
4378
4379             --  If either operand is a junk operand (e.g. package name), then
4380             --  post appropriate error messages, but do not complain further.
4381
4382             --  Note that the use of OR in this test instead of OR ELSE
4383             --  is quite deliberate, we may as well check both operands
4384             --  in the binary operator case.
4385
4386             elsif Junk_Operand (R)
4387               or (Nkind (N) in N_Binary_Op and then Junk_Operand (L))
4388             then
4389                return;
4390
4391             --  If we have a logical operator, one of whose operands is
4392             --  Boolean, then we know that the other operand cannot resolve
4393             --  to Boolean (since we got no interpretations), but in that
4394             --  case we pretty much know that the other operand should be
4395             --  Boolean, so resolve it that way (generating an error)
4396
4397             elsif Nkind (N) = N_Op_And
4398                     or else
4399                   Nkind (N) = N_Op_Or
4400                     or else
4401                   Nkind (N) = N_Op_Xor
4402             then
4403                if Etype (L) = Standard_Boolean then
4404                   Resolve (R, Standard_Boolean);
4405                   return;
4406                elsif Etype (R) = Standard_Boolean then
4407                   Resolve (L, Standard_Boolean);
4408                   return;
4409                end if;
4410
4411             --  For an arithmetic operator or comparison operator, if one
4412             --  of the operands is numeric, then we know the other operand
4413             --  is not the same numeric type. If it is a non-numeric type,
4414             --  then probably it is intended to match the other operand.
4415
4416             elsif Nkind (N) = N_Op_Add      or else
4417                   Nkind (N) = N_Op_Divide   or else
4418                   Nkind (N) = N_Op_Ge       or else
4419                   Nkind (N) = N_Op_Gt       or else
4420                   Nkind (N) = N_Op_Le       or else
4421                   Nkind (N) = N_Op_Lt       or else
4422                   Nkind (N) = N_Op_Mod      or else
4423                   Nkind (N) = N_Op_Multiply or else
4424                   Nkind (N) = N_Op_Rem      or else
4425                   Nkind (N) = N_Op_Subtract
4426             then
4427                if Is_Numeric_Type (Etype (L))
4428                  and then not Is_Numeric_Type (Etype (R))
4429                then
4430                   Resolve (R, Etype (L));
4431                   return;
4432
4433                elsif Is_Numeric_Type (Etype (R))
4434                  and then not Is_Numeric_Type (Etype (L))
4435                then
4436                   Resolve (L, Etype (R));
4437                   return;
4438                end if;
4439
4440             --  Comparisons on A'Access are common enough to deserve a
4441             --  special message.
4442
4443             elsif (Nkind (N) = N_Op_Eq  or else
4444                    Nkind (N) = N_Op_Ne)
4445                and then Ekind (Etype (L)) = E_Access_Attribute_Type
4446                and then Ekind (Etype (R)) = E_Access_Attribute_Type
4447             then
4448                Error_Msg_N
4449                  ("two access attributes cannot be compared directly", N);
4450                Error_Msg_N
4451                  ("\they must be converted to an explicit type for comparison",
4452                    N);
4453                return;
4454
4455             --  Another one for C programmers
4456
4457             elsif Nkind (N) = N_Op_Concat
4458               and then Valid_Boolean_Arg (Etype (L))
4459               and then Valid_Boolean_Arg (Etype (R))
4460             then
4461                Error_Msg_N ("invalid operands for concatenation", N);
4462                Error_Msg_N ("\maybe AND was meant", N);
4463                return;
4464
4465             --  A special case for comparison of access parameter with null
4466
4467             elsif Nkind (N) = N_Op_Eq
4468               and then Is_Entity_Name (L)
4469               and then Nkind (Parent (Entity (L))) = N_Parameter_Specification
4470               and then Nkind (Parameter_Type (Parent (Entity (L)))) =
4471                                                   N_Access_Definition
4472               and then Nkind (R) = N_Null
4473             then
4474                Error_Msg_N ("access parameter is not allowed to be null", L);
4475                Error_Msg_N ("\(call would raise Constraint_Error)", L);
4476                return;
4477             end if;
4478
4479             --  If we fall through then just give general message. Note
4480             --  that in the following messages, if the operand is overloaded
4481             --  we choose an arbitrary type to complain about, but that is
4482             --  probably more useful than not giving a type at all.
4483
4484             if Nkind (N) in N_Unary_Op then
4485                Error_Msg_Node_2 := Etype (R);
4486                Error_Msg_N ("operator& not defined for}", N);
4487                return;
4488
4489             else
4490                if Nkind (N) in N_Binary_Op then
4491                   if not Is_Overloaded (L)
4492                     and then not Is_Overloaded (R)
4493                     and then Base_Type (Etype (L)) = Base_Type (Etype (R))
4494                   then
4495                      Error_Msg_Node_2 := First_Subtype (Etype (R));
4496                      Error_Msg_N ("there is no applicable operator& for}", N);
4497
4498                   else
4499                      Error_Msg_N ("invalid operand types for operator&", N);
4500
4501                      if Nkind (N) /= N_Op_Concat then
4502                         Error_Msg_NE ("\left operand has}!",  N, Etype (L));
4503                         Error_Msg_NE ("\right operand has}!", N, Etype (R));
4504                      end if;
4505                   end if;
4506                end if;
4507             end if;
4508          end;
4509       end if;
4510    end Operator_Check;
4511
4512    -----------------------------------------
4513    -- Process_Implicit_Dereference_Prefix --
4514    -----------------------------------------
4515
4516    procedure Process_Implicit_Dereference_Prefix
4517      (E : Entity_Id;
4518       P : Entity_Id)
4519    is
4520       Ref : Node_Id;
4521
4522    begin
4523       if Present (E)
4524         and then (Operating_Mode = Check_Semantics or else not Expander_Active)
4525       then
4526          --  We create a dummy reference to E to ensure that the reference
4527          --  is not considered as part of an assignment (an implicit
4528          --  dereference can never assign to its prefix). The Comes_From_Source
4529          --  attribute needs to be propagated for accurate warnings.
4530
4531          Ref := New_Reference_To (E, Sloc (P));
4532          Set_Comes_From_Source (Ref, Comes_From_Source (P));
4533          Generate_Reference (E, Ref);
4534       end if;
4535    end Process_Implicit_Dereference_Prefix;
4536
4537    --------------------------------
4538    -- Remove_Abstract_Operations --
4539    --------------------------------
4540
4541    procedure Remove_Abstract_Operations (N : Node_Id) is
4542       I            : Interp_Index;
4543       It           : Interp;
4544       Abstract_Op  : Entity_Id := Empty;
4545
4546       --  AI-310: If overloaded, remove abstract non-dispatching
4547       --  operations. We activate this if either extensions are
4548       --  enabled, or if the abstract operation in question comes
4549       --  from a predefined file. This latter test allows us to
4550       --  use abstract to make operations invisible to users. In
4551       --  particular, if type Address is non-private and abstract
4552       --  subprograms are used to hide its operators, they will be
4553       --  truly hidden.
4554
4555       type Operand_Position is (First_Op, Second_Op);
4556       Univ_Type : constant Entity_Id := Universal_Interpretation (N);
4557
4558       procedure Remove_Address_Interpretations (Op : Operand_Position);
4559       --  Ambiguities may arise when the operands are literal and the
4560       --  address operations in s-auxdec are visible. In that case, remove
4561       --  the interpretation of a literal as Address, to retain the semantics
4562       --  of Address as a private type.
4563
4564       ------------------------------------
4565       -- Remove_Address_Interpretations --
4566       ------------------------------------
4567
4568       procedure Remove_Address_Interpretations (Op : Operand_Position) is
4569          Formal : Entity_Id;
4570
4571       begin
4572          if Is_Overloaded (N) then
4573             Get_First_Interp (N, I, It);
4574             while Present (It.Nam) loop
4575                Formal := First_Entity (It.Nam);
4576
4577                if Op = Second_Op then
4578                   Formal := Next_Entity (Formal);
4579                end if;
4580
4581                if Is_Descendent_Of_Address (Etype (Formal)) then
4582                   Remove_Interp (I);
4583                end if;
4584
4585                Get_Next_Interp (I, It);
4586             end loop;
4587          end if;
4588       end Remove_Address_Interpretations;
4589
4590    --  Start of processing for Remove_Abstract_Operations
4591
4592    begin
4593       if Is_Overloaded (N) then
4594          Get_First_Interp (N, I, It);
4595
4596          while Present (It.Nam) loop
4597             if not Is_Type (It.Nam)
4598               and then Is_Abstract (It.Nam)
4599               and then not Is_Dispatching_Operation (It.Nam)
4600               and then
4601                 (Ada_Version >= Ada_05
4602                    or else Is_Predefined_File_Name
4603                              (Unit_File_Name (Get_Source_Unit (It.Nam))))
4604
4605             then
4606                Abstract_Op := It.Nam;
4607                Remove_Interp (I);
4608                exit;
4609             end if;
4610
4611             Get_Next_Interp (I, It);
4612          end loop;
4613
4614          if No (Abstract_Op) then
4615             return;
4616
4617          elsif Nkind (N) in N_Op then
4618
4619             --  Remove interpretations that treat literals as addresses.
4620             --  This is never appropriate.
4621
4622             if Nkind (N) in N_Binary_Op then
4623                declare
4624                   U1 : constant Boolean :=
4625                      Present (Universal_Interpretation (Right_Opnd (N)));
4626                   U2 : constant Boolean :=
4627                      Present (Universal_Interpretation (Left_Opnd (N)));
4628
4629                begin
4630                   if U1 and then not U2 then
4631                      Remove_Address_Interpretations (Second_Op);
4632
4633                   elsif U2 and then not U1 then
4634                      Remove_Address_Interpretations (First_Op);
4635                   end if;
4636
4637                   if not (U1 and U2) then
4638
4639                      --  Remove corresponding predefined operator, which is
4640                      --  always added to the overload set.
4641
4642                      Get_First_Interp (N, I, It);
4643                      while Present (It.Nam) loop
4644                         if Scope (It.Nam) = Standard_Standard
4645                           and then Base_Type (It.Typ) =
4646                                    Base_Type (Etype (Abstract_Op))
4647                         then
4648                            Remove_Interp (I);
4649                         end if;
4650
4651                         Get_Next_Interp (I, It);
4652                      end loop;
4653
4654                   elsif Is_Overloaded (N)
4655                     and then Present (Univ_Type)
4656                   then
4657                      --  If both operands have a universal interpretation,
4658                      --  select the predefined operator and discard others.
4659
4660                      Get_First_Interp (N, I, It);
4661                      while Present (It.Nam) loop
4662                         if Scope (It.Nam) = Standard_Standard then
4663                            Set_Etype (N, Univ_Type);
4664                            Set_Entity (N, It.Nam);
4665                            Set_Is_Overloaded (N, False);
4666                            exit;
4667                         end if;
4668
4669                         Get_Next_Interp (I, It);
4670                      end loop;
4671                   end if;
4672                end;
4673             end if;
4674
4675          elsif Nkind (N) = N_Function_Call
4676            and then
4677              (Nkind (Name (N)) = N_Operator_Symbol
4678                 or else
4679                   (Nkind (Name (N)) = N_Expanded_Name
4680                      and then
4681                        Nkind (Selector_Name (Name (N))) = N_Operator_Symbol))
4682          then
4683
4684             declare
4685                Arg1 : constant Node_Id := First (Parameter_Associations (N));
4686                U1   : constant Boolean :=
4687                         Present (Universal_Interpretation (Arg1));
4688                U2   : constant Boolean :=
4689                         Present (Next (Arg1)) and then
4690                         Present (Universal_Interpretation (Next (Arg1)));
4691
4692             begin
4693                if U1 and then not U2 then
4694                   Remove_Address_Interpretations (First_Op);
4695
4696                elsif U2 and then not U1 then
4697                   Remove_Address_Interpretations (Second_Op);
4698                end if;
4699
4700                if not (U1 and U2) then
4701                   Get_First_Interp (N, I, It);
4702                   while Present (It.Nam) loop
4703                      if Scope (It.Nam) = Standard_Standard
4704                        and then It.Typ = Base_Type (Etype (Abstract_Op))
4705                      then
4706                         Remove_Interp (I);
4707                      end if;
4708
4709                      Get_Next_Interp (I, It);
4710                   end loop;
4711                end if;
4712             end;
4713          end if;
4714
4715          --  If the removal has left no valid interpretations, emit
4716          --  error message now and label node as illegal.
4717
4718          if Present (Abstract_Op) then
4719             Get_First_Interp (N, I, It);
4720
4721             if No (It.Nam) then
4722
4723                --  Removal of abstract operation left no viable candidate
4724
4725                Set_Etype (N, Any_Type);
4726                Error_Msg_Sloc := Sloc (Abstract_Op);
4727                Error_Msg_NE
4728                  ("cannot call abstract operation& declared#", N, Abstract_Op);
4729             end if;
4730          end if;
4731       end if;
4732    end Remove_Abstract_Operations;
4733
4734    -----------------------
4735    -- Try_Indirect_Call --
4736    -----------------------
4737
4738    function Try_Indirect_Call
4739      (N   : Node_Id;
4740       Nam : Entity_Id;
4741       Typ : Entity_Id) return Boolean
4742    is
4743       Actual  : Node_Id;
4744       Formal  : Entity_Id;
4745       Call_OK : Boolean;
4746
4747    begin
4748       Normalize_Actuals (N, Designated_Type (Typ), False, Call_OK);
4749
4750       Actual := First_Actual (N);
4751       Formal := First_Formal (Designated_Type (Typ));
4752       while Present (Actual) and then Present (Formal) loop
4753          if not Has_Compatible_Type (Actual, Etype (Formal)) then
4754             return False;
4755          end if;
4756
4757          Next (Actual);
4758          Next_Formal (Formal);
4759       end loop;
4760
4761       if No (Actual) and then No (Formal) then
4762          Add_One_Interp (N, Nam, Etype (Designated_Type (Typ)));
4763
4764          --  Nam is a candidate interpretation for the name in the call,
4765          --  if it is not an indirect call.
4766
4767          if not Is_Type (Nam)
4768             and then Is_Entity_Name (Name (N))
4769          then
4770             Set_Entity (Name (N), Nam);
4771          end if;
4772
4773          return True;
4774       else
4775          return False;
4776       end if;
4777    end Try_Indirect_Call;
4778
4779    ----------------------
4780    -- Try_Indexed_Call --
4781    ----------------------
4782
4783    function Try_Indexed_Call
4784      (N   : Node_Id;
4785       Nam : Entity_Id;
4786       Typ : Entity_Id) return Boolean
4787    is
4788       Actuals : constant List_Id   := Parameter_Associations (N);
4789       Actual : Node_Id;
4790       Index  : Entity_Id;
4791
4792    begin
4793       Actual := First (Actuals);
4794       Index := First_Index (Typ);
4795       while Present (Actual) and then Present (Index) loop
4796
4797          --  If the parameter list has a named association, the expression
4798          --  is definitely a call and not an indexed component.
4799
4800          if Nkind (Actual) = N_Parameter_Association then
4801             return False;
4802          end if;
4803
4804          if not Has_Compatible_Type (Actual, Etype (Index)) then
4805             return False;
4806          end if;
4807
4808          Next (Actual);
4809          Next_Index (Index);
4810       end loop;
4811
4812       if No (Actual) and then No (Index) then
4813          Add_One_Interp (N, Nam, Component_Type (Typ));
4814
4815          --  Nam is a candidate interpretation for the name in the call,
4816          --  if it is not an indirect call.
4817
4818          if not Is_Type (Nam)
4819             and then Is_Entity_Name (Name (N))
4820          then
4821             Set_Entity (Name (N), Nam);
4822          end if;
4823
4824          return True;
4825       else
4826          return False;
4827       end if;
4828    end Try_Indexed_Call;
4829
4830    --------------------------
4831    -- Try_Object_Operation --
4832    --------------------------
4833
4834    function Try_Object_Operation (N : Node_Id) return Boolean is
4835       K               : constant Node_Kind  := Nkind (Parent (N));
4836       Loc             : constant Source_Ptr := Sloc (N);
4837       Is_Subprg_Call  : constant Boolean    := K = N_Procedure_Call_Statement
4838                                                 or else K = N_Function_Call;
4839       Obj             : constant Node_Id    := Prefix (N);
4840       Subprog         : constant Node_Id    := Selector_Name (N);
4841
4842       Actual          : Node_Id;
4843       New_Call_Node  :  Node_Id := Empty;
4844       Node_To_Replace : Node_Id;
4845       Obj_Type        : Entity_Id := Etype (Obj);
4846
4847       procedure Complete_Object_Operation
4848         (Call_Node       : Node_Id;
4849          Node_To_Replace : Node_Id;
4850          Subprog         : Node_Id);
4851       --  Make Subprog the name of Call_Node, replace Node_To_Replace with
4852       --  Call_Node, insert the object (or its dereference) as the first actual
4853       --  in the call, and complete the analysis of the call.
4854
4855       procedure Transform_Object_Operation
4856         (Call_Node       : out Node_Id;
4857          Node_To_Replace : out Node_Id;
4858          Subprog         : Node_Id);
4859       --  Transform Obj.Operation (X, Y,,) into Operation (Obj, X, Y ..)
4860       --  Call_Node is the resulting subprogram call,
4861       --  Node_To_Replace is either N or the parent of N, and Subprog
4862       --  is a reference to the subprogram we are trying to match.
4863
4864       function Try_Class_Wide_Operation
4865         (Call_Node       : Node_Id;
4866          Node_To_Replace : Node_Id) return Boolean;
4867       --  Traverse all ancestor types looking for a class-wide subprogram
4868       --  for which the current operation is a valid non-dispatching call.
4869
4870       function Try_Primitive_Operation
4871         (Call_Node       : Node_Id;
4872          Node_To_Replace : Node_Id) return Boolean;
4873       --  Traverse the list of primitive subprograms looking for a dispatching
4874       --  operation for which the current node is a valid call .
4875
4876       -------------------------------
4877       -- Complete_Object_Operation --
4878       -------------------------------
4879
4880       procedure Complete_Object_Operation
4881         (Call_Node       : Node_Id;
4882          Node_To_Replace : Node_Id;
4883          Subprog         : Node_Id)
4884       is
4885          First_Actual : Node_Id;
4886
4887       begin
4888          First_Actual := First (Parameter_Associations (Call_Node));
4889          Set_Name (Call_Node, Subprog);
4890
4891          if Nkind (N) = N_Selected_Component
4892            and then not Inside_A_Generic
4893          then
4894             Set_Entity (Selector_Name (N), Entity (Subprog));
4895          end if;
4896
4897          --  If need be, rewrite first actual as an explicit dereference
4898
4899          if not Is_Access_Type (Etype (First_Formal (Entity (Subprog))))
4900            and then Is_Access_Type (Etype (Obj))
4901          then
4902             Rewrite (First_Actual,
4903               Make_Explicit_Dereference (Sloc (Obj), Obj));
4904             Analyze (First_Actual);
4905          else
4906             Rewrite (First_Actual, Obj);
4907          end if;
4908
4909          Rewrite (Node_To_Replace, Call_Node);
4910          Analyze (Node_To_Replace);
4911       end Complete_Object_Operation;
4912
4913       --------------------------------
4914       -- Transform_Object_Operation --
4915       --------------------------------
4916
4917       procedure Transform_Object_Operation
4918         (Call_Node       : out Node_Id;
4919          Node_To_Replace : out Node_Id;
4920          Subprog         : Node_Id)
4921       is
4922          Parent_Node : constant Node_Id := Parent (N);
4923
4924          Dummy : constant Node_Id := New_Copy (Obj);
4925          --  Placeholder used as a first parameter in the call, replaced
4926          --  eventually by the proper object.
4927
4928          Actuals : List_Id;
4929          Actual  : Node_Id;
4930
4931       begin
4932          --  Common case covering 1) Call to a procedure and 2) Call to a
4933          --  function that has some additional actuals.
4934
4935          if (Nkind (Parent_Node) = N_Function_Call
4936                or else
4937              Nkind (Parent_Node) = N_Procedure_Call_Statement)
4938
4939             --  N is a selected component node containing the name of the
4940             --  subprogram. If N is not the name of the parent node we must
4941             --  not replace the parent node by the new construct. This case
4942             --  occurs when N is a parameterless call to a subprogram that
4943             --  is an actual parameter of a call to another subprogram. For
4944             --  example:
4945             --            Some_Subprogram (..., Obj.Operation, ...)
4946
4947             and then Name (Parent_Node) = N
4948          then
4949             Node_To_Replace := Parent_Node;
4950
4951             Actuals := Parameter_Associations (Parent_Node);
4952
4953             if Present (Actuals) then
4954                Prepend (Dummy, Actuals);
4955             else
4956                Actuals := New_List (Dummy);
4957             end if;
4958
4959             if Nkind (Parent_Node) = N_Procedure_Call_Statement then
4960                Call_Node :=
4961                  Make_Procedure_Call_Statement (Loc,
4962                    Name => New_Copy_Tree (Subprog),
4963                    Parameter_Associations => Actuals);
4964
4965             else
4966                Call_Node :=
4967                  Make_Function_Call (Loc,
4968                    Name => New_Copy_Tree (Subprog),
4969                    Parameter_Associations => Actuals);
4970
4971             end if;
4972
4973          --  Before analysis, the function call appears as an indexed component
4974          --  if there are no named associations.
4975
4976          elsif Nkind (Parent_Node) =  N_Indexed_Component
4977            and then N = Prefix (Parent_Node)
4978          then
4979             Node_To_Replace := Parent_Node;
4980
4981             Actuals := Expressions (Parent_Node);
4982
4983             Actual := First (Actuals);
4984             while Present (Actual) loop
4985                Analyze (Actual);
4986                Next (Actual);
4987             end loop;
4988
4989             Prepend (Dummy, Actuals);
4990
4991             Call_Node :=
4992                Make_Function_Call (Loc,
4993                  Name => New_Copy_Tree (Subprog),
4994                  Parameter_Associations => Actuals);
4995
4996          --  Parameterless call:  Obj.F is rewritten as F (Obj)
4997
4998          else
4999             Node_To_Replace := N;
5000
5001             Call_Node :=
5002                Make_Function_Call (Loc,
5003                  Name => New_Copy_Tree (Subprog),
5004                  Parameter_Associations => New_List (Dummy));
5005          end if;
5006       end Transform_Object_Operation;
5007
5008       ------------------------------
5009       -- Try_Class_Wide_Operation --
5010       ------------------------------
5011
5012       function Try_Class_Wide_Operation
5013         (Call_Node       : Node_Id;
5014          Node_To_Replace : Node_Id) return Boolean
5015       is
5016          Anc_Type : Entity_Id;
5017          Hom      : Entity_Id;
5018          Hom_Ref  : Node_Id;
5019          Success  : Boolean;
5020
5021       begin
5022          --  Loop through ancestor types, traverse the homonym chain of the
5023          --  subprogram, and try out those homonyms whose first formal has the
5024          --  class-wide type of the ancestor.
5025
5026          --  Should we verify that it is declared in the same package as the
5027          --  ancestor type ???
5028
5029          Anc_Type := Obj_Type;
5030
5031          loop
5032             Hom := Current_Entity (Subprog);
5033             while Present (Hom) loop
5034                if (Ekind (Hom) = E_Procedure
5035                      or else
5036                    Ekind (Hom) = E_Function)
5037                  and then Present (First_Formal (Hom))
5038                  and then Etype (First_Formal (Hom)) =
5039                             Class_Wide_Type (Anc_Type)
5040                then
5041                   Hom_Ref := New_Reference_To (Hom, Loc);
5042
5043                   Set_Etype (Call_Node, Any_Type);
5044                   Set_Parent (Call_Node, Parent (Node_To_Replace));
5045
5046                   Set_Name (Call_Node, Hom_Ref);
5047
5048                   Analyze_One_Call
5049                     (N          => Call_Node,
5050                      Nam        => Hom,
5051                      Report     => False,
5052                      Success    => Success,
5053                      Skip_First => True);
5054
5055                   if Success then
5056
5057                      --  Reformat into the proper call
5058
5059                      Complete_Object_Operation
5060                        (Call_Node       => Call_Node,
5061                         Node_To_Replace => Node_To_Replace,
5062                         Subprog         => Hom_Ref);
5063
5064                      return True;
5065                   end if;
5066                end if;
5067
5068                Hom := Homonym (Hom);
5069             end loop;
5070
5071             --  Examine other ancestor types
5072
5073             exit when Etype (Anc_Type) = Anc_Type;
5074             Anc_Type := Etype (Anc_Type);
5075          end loop;
5076
5077          --  Nothing matched
5078
5079          return False;
5080       end Try_Class_Wide_Operation;
5081
5082       -----------------------------
5083       -- Try_Primitive_Operation --
5084       -----------------------------
5085
5086       function Try_Primitive_Operation
5087         (Call_Node       : Node_Id;
5088          Node_To_Replace : Node_Id) return Boolean
5089       is
5090          Elmt        : Elmt_Id;
5091          Prim_Op     : Entity_Id;
5092          Prim_Op_Ref : Node_Id;
5093          Success     : Boolean;
5094
5095          function Valid_First_Argument_Of (Op : Entity_Id) return Boolean;
5096          --  Verify that the prefix, dereferenced if need be, is a valid
5097          --  controlling argument in a call to Op. The remaining actuals
5098          --  are checked in the subsequent call to Analyze_One_Call.
5099
5100          -----------------------------
5101          -- Valid_First_Argument_Of --
5102          -----------------------------
5103
5104          function Valid_First_Argument_Of (Op : Entity_Id) return Boolean is
5105             Typ : constant Entity_Id := Etype (First_Formal (Op));
5106
5107          begin
5108             --  Simple case
5109
5110             return Base_Type (Obj_Type) = Typ
5111
5112             --  Prefix can be dereferenced
5113
5114               or else
5115                 (Is_Access_Type (Obj_Type)
5116                   and then Designated_Type (Obj_Type) = Typ)
5117
5118             --  Formal is an access parameter, for which the object
5119             --  can provide an access.
5120
5121               or else
5122                 (Ekind (Typ) = E_Anonymous_Access_Type
5123                   and then Designated_Type (Typ) = Obj_Type);
5124          end Valid_First_Argument_Of;
5125
5126       --  Start of processing for Try_Primitive_Operation
5127
5128       begin
5129          --  Look for the subprogram in the list of primitive operations
5130
5131          Elmt := First_Elmt (Primitive_Operations (Obj_Type));
5132          while Present (Elmt) loop
5133             Prim_Op := Node (Elmt);
5134
5135             if Chars (Prim_Op) = Chars (Subprog)
5136               and then Present (First_Formal (Prim_Op))
5137               and then Valid_First_Argument_Of (Prim_Op)
5138             then
5139                Prim_Op_Ref := New_Reference_To (Prim_Op, Loc);
5140
5141                Set_Etype (Call_Node, Any_Type);
5142                Set_Parent (Call_Node, Parent (Node_To_Replace));
5143
5144                Set_Name (Call_Node, Prim_Op_Ref);
5145
5146                Analyze_One_Call
5147                  (N          => Call_Node,
5148                   Nam        => Prim_Op,
5149                   Report     => False,
5150                   Success    => Success,
5151                   Skip_First => True);
5152
5153                if Success then
5154                   Complete_Object_Operation
5155                     (Call_Node       => Call_Node,
5156                      Node_To_Replace => Node_To_Replace,
5157                      Subprog         => Prim_Op_Ref);
5158
5159                   return True;
5160                end if;
5161             end if;
5162
5163             Next_Elmt (Elmt);
5164          end loop;
5165
5166          return False;
5167       end Try_Primitive_Operation;
5168
5169    --  Start of processing for Try_Object_Operation
5170
5171    begin
5172       if Is_Access_Type (Obj_Type) then
5173          Obj_Type := Designated_Type (Obj_Type);
5174       end if;
5175
5176       if Ekind (Obj_Type) = E_Private_Subtype then
5177          Obj_Type := Base_Type (Obj_Type);
5178       end if;
5179
5180       if Is_Class_Wide_Type (Obj_Type) then
5181          Obj_Type := Etype (Class_Wide_Type (Obj_Type));
5182       end if;
5183
5184       --  The type may have be obtained through a limited_with clause,
5185       --  in which case the primitive operations are available on its
5186       --  non-limited view.
5187
5188       if Ekind (Obj_Type) = E_Incomplete_Type
5189         and then From_With_Type (Obj_Type)
5190       then
5191          Obj_Type := Non_Limited_View (Obj_Type);
5192       end if;
5193
5194       if not Is_Tagged_Type (Obj_Type) then
5195          return False;
5196       end if;
5197
5198       --  Analyze the actuals if node is know to be a subprogram call
5199
5200       if Is_Subprg_Call and then N = Name (Parent (N)) then
5201          Actual := First (Parameter_Associations (Parent (N)));
5202          while Present (Actual) loop
5203             Analyze_Expression (Actual);
5204             Next (Actual);
5205          end loop;
5206       end if;
5207
5208       Analyze_Expression (Obj);
5209
5210       --  Build a subprogram call node, using a copy of Obj as its first
5211       --  actual. This is a placeholder, to be replaced by an explicit
5212       --  dereference when needed.
5213
5214       Transform_Object_Operation
5215         (Call_Node       => New_Call_Node,
5216          Node_To_Replace => Node_To_Replace,
5217          Subprog         => Subprog);
5218
5219       Set_Etype (New_Call_Node, Any_Type);
5220       Set_Parent (New_Call_Node, Parent (Node_To_Replace));
5221
5222       return
5223          Try_Primitive_Operation
5224            (Call_Node       => New_Call_Node,
5225             Node_To_Replace => Node_To_Replace)
5226
5227         or else
5228          Try_Class_Wide_Operation
5229            (Call_Node       => New_Call_Node,
5230             Node_To_Replace => Node_To_Replace);
5231    end Try_Object_Operation;
5232
5233 end Sem_Ch4;