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