OSDN Git Service

2011-08-05 Robert Dewar <dewar@adacore.com>
[pf3gnuchains/gcc-fork.git] / gcc / ada / sem_res.adb
1 ------------------------------------------------------------------------------
2 --                                                                          --
3 --                         GNAT COMPILER COMPONENTS                         --
4 --                                                                          --
5 --                              S E M _ R E S                               --
6 --                                                                          --
7 --                                 B o d y                                  --
8 --                                                                          --
9 --          Copyright (C) 1992-2011, Free Software Foundation, Inc.         --
10 --                                                                          --
11 -- GNAT is free software;  you can  redistribute it  and/or modify it under --
12 -- terms of the  GNU General Public License as published  by the Free Soft- --
13 -- ware  Foundation;  either version 3,  or (at your option) any later ver- --
14 -- sion.  GNAT is distributed in the hope that it will be useful, but WITH- --
15 -- OUT ANY WARRANTY;  without even the  implied warranty of MERCHANTABILITY --
16 -- or FITNESS FOR A PARTICULAR PURPOSE.  See the GNU General Public License --
17 -- for  more details.  You should have  received  a copy of the GNU General --
18 -- Public License  distributed with GNAT; see file COPYING3.  If not, go to --
19 -- http://www.gnu.org/licenses for a complete copy of the license.          --
20 --                                                                          --
21 -- GNAT was originally developed  by the GNAT team at  New York University. --
22 -- Extensive contributions were provided by Ada Core Technologies Inc.      --
23 --                                                                          --
24 ------------------------------------------------------------------------------
25
26 with Atree;    use Atree;
27 with Checks;   use Checks;
28 with Debug;    use Debug;
29 with Debug_A;  use Debug_A;
30 with Einfo;    use Einfo;
31 with Errout;   use Errout;
32 with Expander; use Expander;
33 with Exp_Disp; use Exp_Disp;
34 with Exp_Ch6;  use Exp_Ch6;
35 with Exp_Ch7;  use Exp_Ch7;
36 with Exp_Tss;  use Exp_Tss;
37 with Exp_Util; use Exp_Util;
38 with Fname;    use Fname;
39 with Freeze;   use Freeze;
40 with Itypes;   use Itypes;
41 with Lib;      use Lib;
42 with Lib.Xref; use Lib.Xref;
43 with Namet;    use Namet;
44 with Nmake;    use Nmake;
45 with Nlists;   use Nlists;
46 with Opt;      use Opt;
47 with Output;   use Output;
48 with Restrict; use Restrict;
49 with Rident;   use Rident;
50 with Rtsfind;  use Rtsfind;
51 with Sem;      use Sem;
52 with Sem_Aux;  use Sem_Aux;
53 with Sem_Aggr; use Sem_Aggr;
54 with Sem_Attr; use Sem_Attr;
55 with Sem_Cat;  use Sem_Cat;
56 with Sem_Ch4;  use Sem_Ch4;
57 with Sem_Ch6;  use Sem_Ch6;
58 with Sem_Ch8;  use Sem_Ch8;
59 with Sem_Ch13; use Sem_Ch13;
60 with Sem_Disp; use Sem_Disp;
61 with Sem_Dist; use Sem_Dist;
62 with Sem_Elim; use Sem_Elim;
63 with Sem_Elab; use Sem_Elab;
64 with Sem_Eval; use Sem_Eval;
65 with Sem_Intr; use Sem_Intr;
66 with Sem_Util; use Sem_Util;
67 with Sem_Type; use Sem_Type;
68 with Sem_Warn; use Sem_Warn;
69 with Sinfo;    use Sinfo;
70 with Sinfo.CN; use Sinfo.CN;
71 with Snames;   use Snames;
72 with Stand;    use Stand;
73 with Stringt;  use Stringt;
74 with Style;    use Style;
75 with Tbuild;   use Tbuild;
76 with Uintp;    use Uintp;
77 with Urealp;   use Urealp;
78
79 package body Sem_Res is
80
81    -----------------------
82    -- Local Subprograms --
83    -----------------------
84
85    --  Second pass (top-down) type checking and overload resolution procedures
86    --  Typ is the type required by context. These procedures propagate the type
87    --  information recursively to the descendants of N. If the node is not
88    --  overloaded, its Etype is established in the first pass. If overloaded,
89    --  the Resolve routines set the correct type. For arith. operators, the
90    --  Etype is the base type of the context.
91
92    --  Note that Resolve_Attribute is separated off in Sem_Attr
93
94    function Bad_Unordered_Enumeration_Reference
95      (N : Node_Id;
96       T : Entity_Id) return Boolean;
97    --  Node N contains a potentially dubious reference to type T, either an
98    --  explicit comparison, or an explicit range. This function returns True
99    --  if the type T is an enumeration type for which No pragma Order has been
100    --  given, and the reference N is not in the same extended source unit as
101    --  the declaration of T.
102
103    procedure Check_Discriminant_Use (N : Node_Id);
104    --  Enforce the restrictions on the use of discriminants when constraining
105    --  a component of a discriminated type (record or concurrent type).
106
107    procedure Check_For_Visible_Operator (N : Node_Id; T : Entity_Id);
108    --  Given a node for an operator associated with type T, check that
109    --  the operator is visible. Operators all of whose operands are
110    --  universal must be checked for visibility during resolution
111    --  because their type is not determinable based on their operands.
112
113    procedure Check_Fully_Declared_Prefix
114      (Typ  : Entity_Id;
115       Pref : Node_Id);
116    --  Check that the type of the prefix of a dereference is not incomplete
117
118    function Check_Infinite_Recursion (N : Node_Id) return Boolean;
119    --  Given a call node, N, which is known to occur immediately within the
120    --  subprogram being called, determines whether it is a detectable case of
121    --  an infinite recursion, and if so, outputs appropriate messages. Returns
122    --  True if an infinite recursion is detected, and False otherwise.
123
124    procedure Check_Initialization_Call (N : Entity_Id; Nam : Entity_Id);
125    --  If the type of the object being initialized uses the secondary stack
126    --  directly or indirectly, create a transient scope for the call to the
127    --  init proc. This is because we do not create transient scopes for the
128    --  initialization of individual components within the init proc itself.
129    --  Could be optimized away perhaps?
130
131    procedure Check_No_Direct_Boolean_Operators (N : Node_Id);
132    --  N is the node for a logical operator. If the operator is predefined, and
133    --  the root type of the operands is Standard.Boolean, then a check is made
134    --  for restriction No_Direct_Boolean_Operators. This procedure also handles
135    --  the style check for Style_Check_Boolean_And_Or.
136
137    function Is_Definite_Access_Type (E : Entity_Id) return Boolean;
138    --  Determine whether E is an access type declared by an access declaration,
139    --  and not an (anonymous) allocator type.
140
141    function Is_Predefined_Op (Nam : Entity_Id) return Boolean;
142    --  Utility to check whether the entity for an operator is a predefined
143    --  operator, in which case the expression is left as an operator in the
144    --  tree (else it is rewritten into a call). An instance of an intrinsic
145    --  conversion operation may be given an operator name, but is not treated
146    --  like an operator. Note that an operator that is an imported back-end
147    --  builtin has convention Intrinsic, but is expected to be rewritten into
148    --  a call, so such an operator is not treated as predefined by this
149    --  predicate.
150
151    procedure Replace_Actual_Discriminants (N : Node_Id; Default : Node_Id);
152    --  If a default expression in entry call N depends on the discriminants
153    --  of the task, it must be replaced with a reference to the discriminant
154    --  of the task being called.
155
156    procedure Resolve_Op_Concat_Arg
157      (N       : Node_Id;
158       Arg     : Node_Id;
159       Typ     : Entity_Id;
160       Is_Comp : Boolean);
161    --  Internal procedure for Resolve_Op_Concat to resolve one operand of
162    --  concatenation operator.  The operand is either of the array type or of
163    --  the component type. If the operand is an aggregate, and the component
164    --  type is composite, this is ambiguous if component type has aggregates.
165
166    procedure Resolve_Op_Concat_First (N : Node_Id; Typ : Entity_Id);
167    --  Does the first part of the work of Resolve_Op_Concat
168
169    procedure Resolve_Op_Concat_Rest (N : Node_Id; Typ : Entity_Id);
170    --  Does the "rest" of the work of Resolve_Op_Concat, after the left operand
171    --  has been resolved. See Resolve_Op_Concat for details.
172
173    procedure Resolve_Allocator                 (N : Node_Id; Typ : Entity_Id);
174    procedure Resolve_Arithmetic_Op             (N : Node_Id; Typ : Entity_Id);
175    procedure Resolve_Call                      (N : Node_Id; Typ : Entity_Id);
176    procedure Resolve_Case_Expression           (N : Node_Id; Typ : Entity_Id);
177    procedure Resolve_Character_Literal         (N : Node_Id; Typ : Entity_Id);
178    procedure Resolve_Comparison_Op             (N : Node_Id; Typ : Entity_Id);
179    procedure Resolve_Conditional_Expression    (N : Node_Id; Typ : Entity_Id);
180    procedure Resolve_Entity_Name               (N : Node_Id; Typ : Entity_Id);
181    procedure Resolve_Equality_Op               (N : Node_Id; Typ : Entity_Id);
182    procedure Resolve_Explicit_Dereference      (N : Node_Id; Typ : Entity_Id);
183    procedure Resolve_Expression_With_Actions   (N : Node_Id; Typ : Entity_Id);
184    procedure Resolve_Indexed_Component         (N : Node_Id; Typ : Entity_Id);
185    procedure Resolve_Integer_Literal           (N : Node_Id; Typ : Entity_Id);
186    procedure Resolve_Logical_Op                (N : Node_Id; Typ : Entity_Id);
187    procedure Resolve_Membership_Op             (N : Node_Id; Typ : Entity_Id);
188    procedure Resolve_Null                      (N : Node_Id; Typ : Entity_Id);
189    procedure Resolve_Operator_Symbol           (N : Node_Id; Typ : Entity_Id);
190    procedure Resolve_Op_Concat                 (N : Node_Id; Typ : Entity_Id);
191    procedure Resolve_Op_Expon                  (N : Node_Id; Typ : Entity_Id);
192    procedure Resolve_Op_Not                    (N : Node_Id; Typ : Entity_Id);
193    procedure Resolve_Qualified_Expression      (N : Node_Id; Typ : Entity_Id);
194    procedure Resolve_Quantified_Expression     (N : Node_Id; Typ : Entity_Id);
195    procedure Resolve_Range                     (N : Node_Id; Typ : Entity_Id);
196    procedure Resolve_Real_Literal              (N : Node_Id; Typ : Entity_Id);
197    procedure Resolve_Reference                 (N : Node_Id; Typ : Entity_Id);
198    procedure Resolve_Selected_Component        (N : Node_Id; Typ : Entity_Id);
199    procedure Resolve_Shift                     (N : Node_Id; Typ : Entity_Id);
200    procedure Resolve_Short_Circuit             (N : Node_Id; Typ : Entity_Id);
201    procedure Resolve_Slice                     (N : Node_Id; Typ : Entity_Id);
202    procedure Resolve_String_Literal            (N : Node_Id; Typ : Entity_Id);
203    procedure Resolve_Subprogram_Info           (N : Node_Id; Typ : Entity_Id);
204    procedure Resolve_Type_Conversion           (N : Node_Id; Typ : Entity_Id);
205    procedure Resolve_Unary_Op                  (N : Node_Id; Typ : Entity_Id);
206    procedure Resolve_Unchecked_Expression      (N : Node_Id; Typ : Entity_Id);
207    procedure Resolve_Unchecked_Type_Conversion (N : Node_Id; Typ : Entity_Id);
208
209    function Operator_Kind
210      (Op_Name   : Name_Id;
211       Is_Binary : Boolean) return Node_Kind;
212    --  Utility to map the name of an operator into the corresponding Node. Used
213    --  by other node rewriting procedures.
214
215    procedure Resolve_Actuals (N : Node_Id; Nam : Entity_Id);
216    --  Resolve actuals of call, and add default expressions for missing ones.
217    --  N is the Node_Id for the subprogram call, and Nam is the entity of the
218    --  called subprogram.
219
220    procedure Resolve_Entry_Call (N : Node_Id; Typ : Entity_Id);
221    --  Called from Resolve_Call, when the prefix denotes an entry or element
222    --  of entry family. Actuals are resolved as for subprograms, and the node
223    --  is rebuilt as an entry call. Also called for protected operations. Typ
224    --  is the context type, which is used when the operation is a protected
225    --  function with no arguments, and the return value is indexed.
226
227    procedure Resolve_Intrinsic_Operator (N : Node_Id; Typ : Entity_Id);
228    --  A call to a user-defined intrinsic operator is rewritten as a call to
229    --  the corresponding predefined operator, with suitable conversions. Note
230    --  that this applies only for intrinsic operators that denote predefined
231    --  operators, not ones that are intrinsic imports of back-end builtins.
232
233    procedure Resolve_Intrinsic_Unary_Operator (N : Node_Id; Typ : Entity_Id);
234    --  Ditto, for unary operators (arithmetic ones and "not" on signed
235    --  integer types for VMS).
236
237    procedure Rewrite_Operator_As_Call (N : Node_Id; Nam : Entity_Id);
238    --  If an operator node resolves to a call to a user-defined operator,
239    --  rewrite the node as a function call.
240
241    procedure Make_Call_Into_Operator
242      (N     : Node_Id;
243       Typ   : Entity_Id;
244       Op_Id : Entity_Id);
245    --  Inverse transformation: if an operator is given in functional notation,
246    --  then after resolving the node, transform into an operator node, so
247    --  that operands are resolved properly. Recall that predefined operators
248    --  do not have a full signature and special resolution rules apply.
249
250    procedure Rewrite_Renamed_Operator
251      (N   : Node_Id;
252       Op  : Entity_Id;
253       Typ : Entity_Id);
254    --  An operator can rename another, e.g. in  an instantiation. In that
255    --  case, the proper operator node must be constructed and resolved.
256
257    procedure Set_String_Literal_Subtype (N : Node_Id; Typ : Entity_Id);
258    --  The String_Literal_Subtype is built for all strings that are not
259    --  operands of a static concatenation operation. If the argument is
260    --  not a N_String_Literal node, then the call has no effect.
261
262    procedure Set_Slice_Subtype (N : Node_Id);
263    --  Build subtype of array type, with the range specified by the slice
264
265    procedure Simplify_Type_Conversion (N : Node_Id);
266    --  Called after N has been resolved and evaluated, but before range checks
267    --  have been applied. Currently simplifies a combination of floating-point
268    --  to integer conversion and Truncation attribute.
269
270    function Unique_Fixed_Point_Type (N : Node_Id) return Entity_Id;
271    --  A universal_fixed expression in an universal context is unambiguous if
272    --  there is only one applicable fixed point type. Determining whether there
273    --  is only one requires a search over all visible entities, and happens
274    --  only in very pathological cases (see 6115-006).
275
276    function Valid_Conversion
277      (N       : Node_Id;
278       Target  : Entity_Id;
279       Operand : Node_Id) return Boolean;
280    --  Verify legality rules given in 4.6 (8-23). Target is the target type
281    --  of the conversion, which may be an implicit conversion of an actual
282    --  parameter to an anonymous access type (in which case N denotes the
283    --  actual parameter and N = Operand).
284
285    -------------------------
286    -- Ambiguous_Character --
287    -------------------------
288
289    procedure Ambiguous_Character (C : Node_Id) is
290       E : Entity_Id;
291
292    begin
293       if Nkind (C) = N_Character_Literal then
294          Error_Msg_N ("ambiguous character literal", C);
295
296          --  First the ones in Standard
297
298          Error_Msg_N ("\\possible interpretation: Character!", C);
299          Error_Msg_N ("\\possible interpretation: Wide_Character!", C);
300
301          --  Include Wide_Wide_Character in Ada 2005 mode
302
303          if Ada_Version >= Ada_2005 then
304             Error_Msg_N ("\\possible interpretation: Wide_Wide_Character!", C);
305          end if;
306
307          --  Now any other types that match
308
309          E := Current_Entity (C);
310          while Present (E) loop
311             Error_Msg_NE ("\\possible interpretation:}!", C, Etype (E));
312             E := Homonym (E);
313          end loop;
314       end if;
315    end Ambiguous_Character;
316
317    -------------------------
318    -- Analyze_And_Resolve --
319    -------------------------
320
321    procedure Analyze_And_Resolve (N : Node_Id) is
322    begin
323       Analyze (N);
324       Resolve (N);
325    end Analyze_And_Resolve;
326
327    procedure Analyze_And_Resolve (N : Node_Id; Typ : Entity_Id) is
328    begin
329       Analyze (N);
330       Resolve (N, Typ);
331    end Analyze_And_Resolve;
332
333    --  Version withs check(s) suppressed
334
335    procedure Analyze_And_Resolve
336      (N        : Node_Id;
337       Typ      : Entity_Id;
338       Suppress : Check_Id)
339    is
340       Scop : constant Entity_Id := Current_Scope;
341
342    begin
343       if Suppress = All_Checks then
344          declare
345             Svg : constant Suppress_Array := Scope_Suppress;
346          begin
347             Scope_Suppress := (others => True);
348             Analyze_And_Resolve (N, Typ);
349             Scope_Suppress := Svg;
350          end;
351
352       else
353          declare
354             Svg : constant Boolean := Scope_Suppress (Suppress);
355
356          begin
357             Scope_Suppress (Suppress) := True;
358             Analyze_And_Resolve (N, Typ);
359             Scope_Suppress (Suppress) := Svg;
360          end;
361       end if;
362
363       if Current_Scope /= Scop
364         and then Scope_Is_Transient
365       then
366          --  This can only happen if a transient scope was created for an inner
367          --  expression, which will be removed upon completion of the analysis
368          --  of an enclosing construct. The transient scope must have the
369          --  suppress status of the enclosing environment, not of this Analyze
370          --  call.
371
372          Scope_Stack.Table (Scope_Stack.Last).Save_Scope_Suppress :=
373            Scope_Suppress;
374       end if;
375    end Analyze_And_Resolve;
376
377    procedure Analyze_And_Resolve
378      (N        : Node_Id;
379       Suppress : Check_Id)
380    is
381       Scop : constant Entity_Id := Current_Scope;
382
383    begin
384       if Suppress = All_Checks then
385          declare
386             Svg : constant Suppress_Array := Scope_Suppress;
387          begin
388             Scope_Suppress := (others => True);
389             Analyze_And_Resolve (N);
390             Scope_Suppress := Svg;
391          end;
392
393       else
394          declare
395             Svg : constant Boolean := Scope_Suppress (Suppress);
396
397          begin
398             Scope_Suppress (Suppress) := True;
399             Analyze_And_Resolve (N);
400             Scope_Suppress (Suppress) := Svg;
401          end;
402       end if;
403
404       if Current_Scope /= Scop
405         and then Scope_Is_Transient
406       then
407          Scope_Stack.Table (Scope_Stack.Last).Save_Scope_Suppress :=
408            Scope_Suppress;
409       end if;
410    end Analyze_And_Resolve;
411
412    ----------------------------------------
413    -- Bad_Unordered_Enumeration_Reference --
414    ----------------------------------------
415
416    function Bad_Unordered_Enumeration_Reference
417      (N : Node_Id;
418       T : Entity_Id) return Boolean
419    is
420    begin
421       return Is_Enumeration_Type (T)
422         and then Comes_From_Source (N)
423         and then Warn_On_Unordered_Enumeration_Type
424         and then not Has_Pragma_Ordered (T)
425         and then not In_Same_Extended_Unit (N, T);
426    end Bad_Unordered_Enumeration_Reference;
427
428    ----------------------------
429    -- Check_Discriminant_Use --
430    ----------------------------
431
432    procedure Check_Discriminant_Use (N : Node_Id) is
433       PN   : constant Node_Id   := Parent (N);
434       Disc : constant Entity_Id := Entity (N);
435       P    : Node_Id;
436       D    : Node_Id;
437
438    begin
439       --  Any use in a spec-expression is legal
440
441       if In_Spec_Expression then
442          null;
443
444       elsif Nkind (PN) = N_Range then
445
446          --  Discriminant cannot be used to constrain a scalar type
447
448          P := Parent (PN);
449
450          if Nkind (P) = N_Range_Constraint
451            and then Nkind (Parent (P)) = N_Subtype_Indication
452            and then Nkind (Parent (Parent (P))) = N_Component_Definition
453          then
454             Error_Msg_N ("discriminant cannot constrain scalar type", N);
455
456          elsif Nkind (P) = N_Index_Or_Discriminant_Constraint then
457
458             --  The following check catches the unusual case where a
459             --  discriminant appears within an index constraint that is part of
460             --  a larger expression within a constraint on a component, e.g. "C
461             --  : Int range 1 .. F (new A(1 .. D))". For now we only check case
462             --  of record components, and note that a similar check should also
463             --  apply in the case of discriminant constraints below. ???
464
465             --  Note that the check for N_Subtype_Declaration below is to
466             --  detect the valid use of discriminants in the constraints of a
467             --  subtype declaration when this subtype declaration appears
468             --  inside the scope of a record type (which is syntactically
469             --  illegal, but which may be created as part of derived type
470             --  processing for records). See Sem_Ch3.Build_Derived_Record_Type
471             --  for more info.
472
473             if Ekind (Current_Scope) = E_Record_Type
474               and then Scope (Disc) = Current_Scope
475               and then not
476                 (Nkind (Parent (P)) = N_Subtype_Indication
477                   and then
478                     Nkind_In (Parent (Parent (P)), N_Component_Definition,
479                                                    N_Subtype_Declaration)
480                   and then Paren_Count (N) = 0)
481             then
482                Error_Msg_N
483                  ("discriminant must appear alone in component constraint", N);
484                return;
485             end if;
486
487             --   Detect a common error:
488
489             --   type R (D : Positive := 100) is record
490             --     Name : String (1 .. D);
491             --   end record;
492
493             --  The default value causes an object of type R to be allocated
494             --  with room for Positive'Last characters. The RM does not mandate
495             --  the allocation of the maximum size, but that is what GNAT does
496             --  so we should warn the programmer that there is a problem.
497
498             Check_Large : declare
499                SI : Node_Id;
500                T  : Entity_Id;
501                TB : Node_Id;
502                CB : Entity_Id;
503
504                function Large_Storage_Type (T : Entity_Id) return Boolean;
505                --  Return True if type T has a large enough range that any
506                --  array whose index type covered the whole range of the type
507                --  would likely raise Storage_Error.
508
509                ------------------------
510                -- Large_Storage_Type --
511                ------------------------
512
513                function Large_Storage_Type (T : Entity_Id) return Boolean is
514                begin
515                   --  The type is considered large if its bounds are known at
516                   --  compile time and if it requires at least as many bits as
517                   --  a Positive to store the possible values.
518
519                   return Compile_Time_Known_Value (Type_Low_Bound (T))
520                     and then Compile_Time_Known_Value (Type_High_Bound (T))
521                     and then
522                       Minimum_Size (T, Biased => True) >=
523                         RM_Size (Standard_Positive);
524                end Large_Storage_Type;
525
526             --  Start of processing for Check_Large
527
528             begin
529                --  Check that the Disc has a large range
530
531                if not Large_Storage_Type (Etype (Disc)) then
532                   goto No_Danger;
533                end if;
534
535                --  If the enclosing type is limited, we allocate only the
536                --  default value, not the maximum, and there is no need for
537                --  a warning.
538
539                if Is_Limited_Type (Scope (Disc)) then
540                   goto No_Danger;
541                end if;
542
543                --  Check that it is the high bound
544
545                if N /= High_Bound (PN)
546                  or else No (Discriminant_Default_Value (Disc))
547                then
548                   goto No_Danger;
549                end if;
550
551                --  Check the array allows a large range at this bound. First
552                --  find the array
553
554                SI := Parent (P);
555
556                if Nkind (SI) /= N_Subtype_Indication then
557                   goto No_Danger;
558                end if;
559
560                T := Entity (Subtype_Mark (SI));
561
562                if not Is_Array_Type (T) then
563                   goto No_Danger;
564                end if;
565
566                --  Next, find the dimension
567
568                TB := First_Index (T);
569                CB := First (Constraints (P));
570                while True
571                  and then Present (TB)
572                  and then Present (CB)
573                  and then CB /= PN
574                loop
575                   Next_Index (TB);
576                   Next (CB);
577                end loop;
578
579                if CB /= PN then
580                   goto No_Danger;
581                end if;
582
583                --  Now, check the dimension has a large range
584
585                if not Large_Storage_Type (Etype (TB)) then
586                   goto No_Danger;
587                end if;
588
589                --  Warn about the danger
590
591                Error_Msg_N
592                  ("?creation of & object may raise Storage_Error!",
593                   Scope (Disc));
594
595                <<No_Danger>>
596                   null;
597
598             end Check_Large;
599          end if;
600
601       --  Legal case is in index or discriminant constraint
602
603       elsif Nkind_In (PN, N_Index_Or_Discriminant_Constraint,
604                           N_Discriminant_Association)
605       then
606          if Paren_Count (N) > 0 then
607             Error_Msg_N
608               ("discriminant in constraint must appear alone",  N);
609
610          elsif Nkind (N) = N_Expanded_Name
611            and then Comes_From_Source (N)
612          then
613             Error_Msg_N
614               ("discriminant must appear alone as a direct name", N);
615          end if;
616
617          return;
618
619       --  Otherwise, context is an expression. It should not be within (i.e. a
620       --  subexpression of) a constraint for a component.
621
622       else
623          D := PN;
624          P := Parent (PN);
625          while not Nkind_In (P, N_Component_Declaration,
626                                 N_Subtype_Indication,
627                                 N_Entry_Declaration)
628          loop
629             D := P;
630             P := Parent (P);
631             exit when No (P);
632          end loop;
633
634          --  If the discriminant is used in an expression that is a bound of a
635          --  scalar type, an Itype is created and the bounds are attached to
636          --  its range, not to the original subtype indication. Such use is of
637          --  course a double fault.
638
639          if (Nkind (P) = N_Subtype_Indication
640               and then Nkind_In (Parent (P), N_Component_Definition,
641                                              N_Derived_Type_Definition)
642               and then D = Constraint (P))
643
644            --  The constraint itself may be given by a subtype indication,
645            --  rather than by a more common discrete range.
646
647            or else (Nkind (P) = N_Subtype_Indication
648                       and then
649                     Nkind (Parent (P)) = N_Index_Or_Discriminant_Constraint)
650            or else Nkind (P) = N_Entry_Declaration
651            or else Nkind (D) = N_Defining_Identifier
652          then
653             Error_Msg_N
654               ("discriminant in constraint must appear alone",  N);
655          end if;
656       end if;
657    end Check_Discriminant_Use;
658
659    --------------------------------
660    -- Check_For_Visible_Operator --
661    --------------------------------
662
663    procedure Check_For_Visible_Operator (N : Node_Id; T : Entity_Id) is
664    begin
665       if Is_Invisible_Operator (N, T) then
666          Error_Msg_NE -- CODEFIX
667            ("operator for} is not directly visible!", N, First_Subtype (T));
668          Error_Msg_N -- CODEFIX
669            ("use clause would make operation legal!", N);
670       end if;
671    end Check_For_Visible_Operator;
672
673    ----------------------------------
674    --  Check_Fully_Declared_Prefix --
675    ----------------------------------
676
677    procedure Check_Fully_Declared_Prefix
678      (Typ  : Entity_Id;
679       Pref : Node_Id)
680    is
681    begin
682       --  Check that the designated type of the prefix of a dereference is
683       --  not an incomplete type. This cannot be done unconditionally, because
684       --  dereferences of private types are legal in default expressions. This
685       --  case is taken care of in Check_Fully_Declared, called below. There
686       --  are also 2005 cases where it is legal for the prefix to be unfrozen.
687
688       --  This consideration also applies to similar checks for allocators,
689       --  qualified expressions, and type conversions.
690
691       --  An additional exception concerns other per-object expressions that
692       --  are not directly related to component declarations, in particular
693       --  representation pragmas for tasks. These will be per-object
694       --  expressions if they depend on discriminants or some global entity.
695       --  If the task has access discriminants, the designated type may be
696       --  incomplete at the point the expression is resolved. This resolution
697       --  takes place within the body of the initialization procedure, where
698       --  the discriminant is replaced by its discriminal.
699
700       if Is_Entity_Name (Pref)
701         and then Ekind (Entity (Pref)) = E_In_Parameter
702       then
703          null;
704
705       --  Ada 2005 (AI-326): Tagged incomplete types allowed. The wrong usages
706       --  are handled by Analyze_Access_Attribute, Analyze_Assignment,
707       --  Analyze_Object_Renaming, and Freeze_Entity.
708
709       elsif Ada_Version >= Ada_2005
710         and then Is_Entity_Name (Pref)
711         and then Is_Access_Type (Etype (Pref))
712         and then Ekind (Directly_Designated_Type (Etype (Pref))) =
713                                                        E_Incomplete_Type
714         and then Is_Tagged_Type (Directly_Designated_Type (Etype (Pref)))
715       then
716          null;
717       else
718          Check_Fully_Declared (Typ, Parent (Pref));
719       end if;
720    end Check_Fully_Declared_Prefix;
721
722    ------------------------------
723    -- Check_Infinite_Recursion --
724    ------------------------------
725
726    function Check_Infinite_Recursion (N : Node_Id) return Boolean is
727       P : Node_Id;
728       C : Node_Id;
729
730       function Same_Argument_List return Boolean;
731       --  Check whether list of actuals is identical to list of formals of
732       --  called function (which is also the enclosing scope).
733
734       ------------------------
735       -- Same_Argument_List --
736       ------------------------
737
738       function Same_Argument_List return Boolean is
739          A    : Node_Id;
740          F    : Entity_Id;
741          Subp : Entity_Id;
742
743       begin
744          if not Is_Entity_Name (Name (N)) then
745             return False;
746          else
747             Subp := Entity (Name (N));
748          end if;
749
750          F := First_Formal (Subp);
751          A := First_Actual (N);
752          while Present (F) and then Present (A) loop
753             if not Is_Entity_Name (A)
754               or else Entity (A) /= F
755             then
756                return False;
757             end if;
758
759             Next_Actual (A);
760             Next_Formal (F);
761          end loop;
762
763          return True;
764       end Same_Argument_List;
765
766    --  Start of processing for Check_Infinite_Recursion
767
768    begin
769       --  Special case, if this is a procedure call and is a call to the
770       --  current procedure with the same argument list, then this is for
771       --  sure an infinite recursion and we insert a call to raise SE.
772
773       if Is_List_Member (N)
774         and then List_Length (List_Containing (N)) = 1
775         and then Same_Argument_List
776       then
777          declare
778             P : constant Node_Id := Parent (N);
779          begin
780             if Nkind (P) = N_Handled_Sequence_Of_Statements
781               and then Nkind (Parent (P)) = N_Subprogram_Body
782               and then Is_Empty_List (Declarations (Parent (P)))
783             then
784                Error_Msg_N ("!?infinite recursion", N);
785                Error_Msg_N ("\!?Storage_Error will be raised at run time", N);
786                Insert_Action (N,
787                  Make_Raise_Storage_Error (Sloc (N),
788                    Reason => SE_Infinite_Recursion));
789                return True;
790             end if;
791          end;
792       end if;
793
794       --  If not that special case, search up tree, quitting if we reach a
795       --  construct (e.g. a conditional) that tells us that this is not a
796       --  case for an infinite recursion warning.
797
798       C := N;
799       loop
800          P := Parent (C);
801
802          --  If no parent, then we were not inside a subprogram, this can for
803          --  example happen when processing certain pragmas in a spec. Just
804          --  return False in this case.
805
806          if No (P) then
807             return False;
808          end if;
809
810          --  Done if we get to subprogram body, this is definitely an infinite
811          --  recursion case if we did not find anything to stop us.
812
813          exit when Nkind (P) = N_Subprogram_Body;
814
815          --  If appearing in conditional, result is false
816
817          if Nkind_In (P, N_Or_Else,
818                          N_And_Then,
819                          N_Case_Expression,
820                          N_Case_Statement,
821                          N_Conditional_Expression,
822                          N_If_Statement)
823          then
824             return False;
825
826          elsif Nkind (P) = N_Handled_Sequence_Of_Statements
827            and then C /= First (Statements (P))
828          then
829             --  If the call is the expression of a return statement and the
830             --  actuals are identical to the formals, it's worth a warning.
831             --  However, we skip this if there is an immediately preceding
832             --  raise statement, since the call is never executed.
833
834             --  Furthermore, this corresponds to a common idiom:
835
836             --    function F (L : Thing) return Boolean is
837             --    begin
838             --       raise Program_Error;
839             --       return F (L);
840             --    end F;
841
842             --  for generating a stub function
843
844             if Nkind (Parent (N)) = N_Simple_Return_Statement
845               and then Same_Argument_List
846             then
847                exit when not Is_List_Member (Parent (N));
848
849                --  OK, return statement is in a statement list, look for raise
850
851                declare
852                   Nod : Node_Id;
853
854                begin
855                   --  Skip past N_Freeze_Entity nodes generated by expansion
856
857                   Nod := Prev (Parent (N));
858                   while Present (Nod)
859                     and then Nkind (Nod) = N_Freeze_Entity
860                   loop
861                      Prev (Nod);
862                   end loop;
863
864                   --  If no raise statement, give warning
865
866                   exit when Nkind (Nod) /= N_Raise_Statement
867                     and then
868                       (Nkind (Nod) not in N_Raise_xxx_Error
869                         or else Present (Condition (Nod)));
870                end;
871             end if;
872
873             return False;
874
875          else
876             C := P;
877          end if;
878       end loop;
879
880       Error_Msg_N ("!?possible infinite recursion", N);
881       Error_Msg_N ("\!?Storage_Error may be raised at run time", N);
882
883       return True;
884    end Check_Infinite_Recursion;
885
886    -------------------------------
887    -- Check_Initialization_Call --
888    -------------------------------
889
890    procedure Check_Initialization_Call (N : Entity_Id; Nam : Entity_Id) is
891       Typ : constant Entity_Id := Etype (First_Formal (Nam));
892
893       function Uses_SS (T : Entity_Id) return Boolean;
894       --  Check whether the creation of an object of the type will involve
895       --  use of the secondary stack. If T is a record type, this is true
896       --  if the expression for some component uses the secondary stack, e.g.
897       --  through a call to a function that returns an unconstrained value.
898       --  False if T is controlled, because cleanups occur elsewhere.
899
900       -------------
901       -- Uses_SS --
902       -------------
903
904       function Uses_SS (T : Entity_Id) return Boolean is
905          Comp      : Entity_Id;
906          Expr      : Node_Id;
907          Full_Type : Entity_Id := Underlying_Type (T);
908
909       begin
910          --  Normally we want to use the underlying type, but if it's not set
911          --  then continue with T.
912
913          if not Present (Full_Type) then
914             Full_Type := T;
915          end if;
916
917          if Is_Controlled (Full_Type) then
918             return False;
919
920          elsif Is_Array_Type (Full_Type) then
921             return Uses_SS (Component_Type (Full_Type));
922
923          elsif Is_Record_Type (Full_Type) then
924             Comp := First_Component (Full_Type);
925             while Present (Comp) loop
926                if Ekind (Comp) = E_Component
927                  and then Nkind (Parent (Comp)) = N_Component_Declaration
928                then
929                   --  The expression for a dynamic component may be rewritten
930                   --  as a dereference, so retrieve original node.
931
932                   Expr := Original_Node (Expression (Parent (Comp)));
933
934                   --  Return True if the expression is a call to a function
935                   --  (including an attribute function such as Image, or a
936                   --  user-defined operator) with a result that requires a
937                   --  transient scope.
938
939                   if (Nkind (Expr) = N_Function_Call
940                        or else Nkind (Expr) in N_Op
941                        or else (Nkind (Expr) = N_Attribute_Reference
942                                  and then Present (Expressions (Expr))))
943                     and then Requires_Transient_Scope (Etype (Expr))
944                   then
945                      return True;
946
947                   elsif Uses_SS (Etype (Comp)) then
948                      return True;
949                   end if;
950                end if;
951
952                Next_Component (Comp);
953             end loop;
954
955             return False;
956
957          else
958             return False;
959          end if;
960       end Uses_SS;
961
962    --  Start of processing for Check_Initialization_Call
963
964    begin
965       --  Establish a transient scope if the type needs it
966
967       if Uses_SS (Typ) then
968          Establish_Transient_Scope (First_Actual (N), Sec_Stack => True);
969       end if;
970    end Check_Initialization_Call;
971
972    ---------------------------------------
973    -- Check_No_Direct_Boolean_Operators --
974    ---------------------------------------
975
976    procedure Check_No_Direct_Boolean_Operators (N : Node_Id) is
977    begin
978       if Scope (Entity (N)) = Standard_Standard
979         and then Root_Type (Etype (Left_Opnd (N))) = Standard_Boolean
980       then
981          --  Restriction only applies to original source code
982
983          if Comes_From_Source (N) then
984             Check_Restriction (No_Direct_Boolean_Operators, N);
985          end if;
986       end if;
987
988       if Style_Check then
989          Check_Boolean_Operator (N);
990       end if;
991    end Check_No_Direct_Boolean_Operators;
992
993    ------------------------------
994    -- Check_Parameterless_Call --
995    ------------------------------
996
997    procedure Check_Parameterless_Call (N : Node_Id) is
998       Nam : Node_Id;
999
1000       function Prefix_Is_Access_Subp return Boolean;
1001       --  If the prefix is of an access_to_subprogram type, the node must be
1002       --  rewritten as a call. Ditto if the prefix is overloaded and all its
1003       --  interpretations are access to subprograms.
1004
1005       ---------------------------
1006       -- Prefix_Is_Access_Subp --
1007       ---------------------------
1008
1009       function Prefix_Is_Access_Subp return Boolean is
1010          I   : Interp_Index;
1011          It  : Interp;
1012
1013       begin
1014          --  If the context is an attribute reference that can apply to
1015          --  functions, this is never a parameterless call (RM 4.1.4(6)).
1016
1017          if Nkind (Parent (N)) = N_Attribute_Reference
1018             and then (Attribute_Name (Parent (N)) = Name_Address      or else
1019                       Attribute_Name (Parent (N)) = Name_Code_Address or else
1020                       Attribute_Name (Parent (N)) = Name_Access)
1021          then
1022             return False;
1023          end if;
1024
1025          if not Is_Overloaded (N) then
1026             return
1027               Ekind (Etype (N)) = E_Subprogram_Type
1028                 and then Base_Type (Etype (Etype (N))) /= Standard_Void_Type;
1029          else
1030             Get_First_Interp (N, I, It);
1031             while Present (It.Typ) loop
1032                if Ekind (It.Typ) /= E_Subprogram_Type
1033                  or else Base_Type (Etype (It.Typ)) = Standard_Void_Type
1034                then
1035                   return False;
1036                end if;
1037
1038                Get_Next_Interp (I, It);
1039             end loop;
1040
1041             return True;
1042          end if;
1043       end Prefix_Is_Access_Subp;
1044
1045    --  Start of processing for Check_Parameterless_Call
1046
1047    begin
1048       --  Defend against junk stuff if errors already detected
1049
1050       if Total_Errors_Detected /= 0 then
1051          if Nkind (N) in N_Has_Etype and then Etype (N) = Any_Type then
1052             return;
1053          elsif Nkind (N) in N_Has_Chars
1054            and then Chars (N) in Error_Name_Or_No_Name
1055          then
1056             return;
1057          end if;
1058
1059          Require_Entity (N);
1060       end if;
1061
1062       --  If the context expects a value, and the name is a procedure, this is
1063       --  most likely a missing 'Access. Don't try to resolve the parameterless
1064       --  call, error will be caught when the outer call is analyzed.
1065
1066       if Is_Entity_Name (N)
1067         and then Ekind (Entity (N)) = E_Procedure
1068         and then not Is_Overloaded (N)
1069         and then
1070          Nkind_In (Parent (N), N_Parameter_Association,
1071                                N_Function_Call,
1072                                N_Procedure_Call_Statement)
1073       then
1074          return;
1075       end if;
1076
1077       --  Rewrite as call if overloadable entity that is (or could be, in the
1078       --  overloaded case) a function call. If we know for sure that the entity
1079       --  is an enumeration literal, we do not rewrite it.
1080
1081       --  If the entity is the name of an operator, it cannot be a call because
1082       --  operators cannot have default parameters. In this case, this must be
1083       --  a string whose contents coincide with an operator name. Set the kind
1084       --  of the node appropriately.
1085
1086       if (Is_Entity_Name (N)
1087             and then Nkind (N) /= N_Operator_Symbol
1088             and then Is_Overloadable (Entity (N))
1089             and then (Ekind (Entity (N)) /= E_Enumeration_Literal
1090                        or else Is_Overloaded (N)))
1091
1092       --  Rewrite as call if it is an explicit dereference of an expression of
1093       --  a subprogram access type, and the subprogram type is not that of a
1094       --  procedure or entry.
1095
1096       or else
1097         (Nkind (N) = N_Explicit_Dereference and then Prefix_Is_Access_Subp)
1098
1099       --  Rewrite as call if it is a selected component which is a function,
1100       --  this is the case of a call to a protected function (which may be
1101       --  overloaded with other protected operations).
1102
1103       or else
1104         (Nkind (N) = N_Selected_Component
1105           and then (Ekind (Entity (Selector_Name (N))) = E_Function
1106                      or else
1107                        (Ekind_In (Entity (Selector_Name (N)), E_Entry,
1108                                                               E_Procedure)
1109                          and then Is_Overloaded (Selector_Name (N)))))
1110
1111       --  If one of the above three conditions is met, rewrite as call. Apply
1112       --  the rewriting only once.
1113
1114       then
1115          if Nkind (Parent (N)) /= N_Function_Call
1116            or else N /= Name (Parent (N))
1117          then
1118             Nam := New_Copy (N);
1119
1120             --  If overloaded, overload set belongs to new copy
1121
1122             Save_Interps (N, Nam);
1123
1124             --  Change node to parameterless function call (note that the
1125             --  Parameter_Associations associations field is left set to Empty,
1126             --  its normal default value since there are no parameters)
1127
1128             Change_Node (N, N_Function_Call);
1129             Set_Name (N, Nam);
1130             Set_Sloc (N, Sloc (Nam));
1131             Analyze_Call (N);
1132          end if;
1133
1134       elsif Nkind (N) = N_Parameter_Association then
1135          Check_Parameterless_Call (Explicit_Actual_Parameter (N));
1136
1137       elsif Nkind (N) = N_Operator_Symbol then
1138          Change_Operator_Symbol_To_String_Literal (N);
1139          Set_Is_Overloaded (N, False);
1140          Set_Etype (N, Any_String);
1141       end if;
1142    end Check_Parameterless_Call;
1143
1144    -----------------------------
1145    -- Is_Definite_Access_Type --
1146    -----------------------------
1147
1148    function Is_Definite_Access_Type (E : Entity_Id) return Boolean is
1149       Btyp : constant Entity_Id := Base_Type (E);
1150    begin
1151       return Ekind (Btyp) = E_Access_Type
1152         or else (Ekind (Btyp) = E_Access_Subprogram_Type
1153                   and then Comes_From_Source (Btyp));
1154    end Is_Definite_Access_Type;
1155
1156    ----------------------
1157    -- Is_Predefined_Op --
1158    ----------------------
1159
1160    function Is_Predefined_Op (Nam : Entity_Id) return Boolean is
1161    begin
1162       --  Predefined operators are intrinsic subprograms
1163
1164       if not Is_Intrinsic_Subprogram (Nam) then
1165          return False;
1166       end if;
1167
1168       --  A call to a back-end builtin is never a predefined operator
1169
1170       if Is_Imported (Nam) and then Present (Interface_Name (Nam)) then
1171          return False;
1172       end if;
1173
1174       return not Is_Generic_Instance (Nam)
1175         and then Chars (Nam) in Any_Operator_Name
1176         and then (No (Alias (Nam)) or else Is_Predefined_Op (Alias (Nam)));
1177    end Is_Predefined_Op;
1178
1179    -----------------------------
1180    -- Make_Call_Into_Operator --
1181    -----------------------------
1182
1183    procedure Make_Call_Into_Operator
1184      (N     : Node_Id;
1185       Typ   : Entity_Id;
1186       Op_Id : Entity_Id)
1187    is
1188       Op_Name   : constant Name_Id := Chars (Op_Id);
1189       Act1      : Node_Id := First_Actual (N);
1190       Act2      : Node_Id := Next_Actual (Act1);
1191       Error     : Boolean := False;
1192       Func      : constant Entity_Id := Entity (Name (N));
1193       Is_Binary : constant Boolean   := Present (Act2);
1194       Op_Node   : Node_Id;
1195       Opnd_Type : Entity_Id;
1196       Orig_Type : Entity_Id := Empty;
1197       Pack      : Entity_Id;
1198
1199       type Kind_Test is access function (E : Entity_Id) return Boolean;
1200
1201       function Operand_Type_In_Scope (S : Entity_Id) return Boolean;
1202       --  If the operand is not universal, and the operator is given by an
1203       --  expanded name, verify that the operand has an interpretation with a
1204       --  type defined in the given scope of the operator.
1205
1206       function Type_In_P (Test : Kind_Test) return Entity_Id;
1207       --  Find a type of the given class in package Pack that contains the
1208       --  operator.
1209
1210       ---------------------------
1211       -- Operand_Type_In_Scope --
1212       ---------------------------
1213
1214       function Operand_Type_In_Scope (S : Entity_Id) return Boolean is
1215          Nod : constant Node_Id := Right_Opnd (Op_Node);
1216          I   : Interp_Index;
1217          It  : Interp;
1218
1219       begin
1220          if not Is_Overloaded (Nod) then
1221             return Scope (Base_Type (Etype (Nod))) = S;
1222
1223          else
1224             Get_First_Interp (Nod, I, It);
1225             while Present (It.Typ) loop
1226                if Scope (Base_Type (It.Typ)) = S then
1227                   return True;
1228                end if;
1229
1230                Get_Next_Interp (I, It);
1231             end loop;
1232
1233             return False;
1234          end if;
1235       end Operand_Type_In_Scope;
1236
1237       ---------------
1238       -- Type_In_P --
1239       ---------------
1240
1241       function Type_In_P (Test : Kind_Test) return Entity_Id is
1242          E : Entity_Id;
1243
1244          function In_Decl return Boolean;
1245          --  Verify that node is not part of the type declaration for the
1246          --  candidate type, which would otherwise be invisible.
1247
1248          -------------
1249          -- In_Decl --
1250          -------------
1251
1252          function In_Decl return Boolean is
1253             Decl_Node : constant Node_Id := Parent (E);
1254             N2        : Node_Id;
1255
1256          begin
1257             N2 := N;
1258
1259             if Etype (E) = Any_Type then
1260                return True;
1261
1262             elsif No (Decl_Node) then
1263                return False;
1264
1265             else
1266                while Present (N2)
1267                  and then Nkind (N2) /= N_Compilation_Unit
1268                loop
1269                   if N2 = Decl_Node then
1270                      return True;
1271                   else
1272                      N2 := Parent (N2);
1273                   end if;
1274                end loop;
1275
1276                return False;
1277             end if;
1278          end In_Decl;
1279
1280       --  Start of processing for Type_In_P
1281
1282       begin
1283          --  If the context type is declared in the prefix package, this is the
1284          --  desired base type.
1285
1286          if Scope (Base_Type (Typ)) = Pack and then Test (Typ) then
1287             return Base_Type (Typ);
1288
1289          else
1290             E := First_Entity (Pack);
1291             while Present (E) loop
1292                if Test (E)
1293                  and then not In_Decl
1294                then
1295                   return E;
1296                end if;
1297
1298                Next_Entity (E);
1299             end loop;
1300
1301             return Empty;
1302          end if;
1303       end Type_In_P;
1304
1305    --  Start of processing for Make_Call_Into_Operator
1306
1307    begin
1308       Op_Node := New_Node (Operator_Kind (Op_Name, Is_Binary), Sloc (N));
1309
1310       --  Binary operator
1311
1312       if Is_Binary then
1313          Set_Left_Opnd  (Op_Node, Relocate_Node (Act1));
1314          Set_Right_Opnd (Op_Node, Relocate_Node (Act2));
1315          Save_Interps (Act1, Left_Opnd  (Op_Node));
1316          Save_Interps (Act2, Right_Opnd (Op_Node));
1317          Act1 := Left_Opnd (Op_Node);
1318          Act2 := Right_Opnd (Op_Node);
1319
1320       --  Unary operator
1321
1322       else
1323          Set_Right_Opnd (Op_Node, Relocate_Node (Act1));
1324          Save_Interps (Act1, Right_Opnd (Op_Node));
1325          Act1 := Right_Opnd (Op_Node);
1326       end if;
1327
1328       --  If the operator is denoted by an expanded name, and the prefix is
1329       --  not Standard, but the operator is a predefined one whose scope is
1330       --  Standard, then this is an implicit_operator, inserted as an
1331       --  interpretation by the procedure of the same name. This procedure
1332       --  overestimates the presence of implicit operators, because it does
1333       --  not examine the type of the operands. Verify now that the operand
1334       --  type appears in the given scope. If right operand is universal,
1335       --  check the other operand. In the case of concatenation, either
1336       --  argument can be the component type, so check the type of the result.
1337       --  If both arguments are literals, look for a type of the right kind
1338       --  defined in the given scope. This elaborate nonsense is brought to
1339       --  you courtesy of b33302a. The type itself must be frozen, so we must
1340       --  find the type of the proper class in the given scope.
1341
1342       --  A final wrinkle is the multiplication operator for fixed point types,
1343       --  which is defined in Standard only, and not in the scope of the
1344       --  fixed point type itself.
1345
1346       if Nkind (Name (N)) = N_Expanded_Name then
1347          Pack := Entity (Prefix (Name (N)));
1348
1349          --  If the entity being called is defined in the given package, it is
1350          --  a renaming of a predefined operator, and known to be legal.
1351
1352          if Scope (Entity (Name (N))) = Pack
1353             and then Pack /= Standard_Standard
1354          then
1355             null;
1356
1357          --  Visibility does not need to be checked in an instance: if the
1358          --  operator was not visible in the generic it has been diagnosed
1359          --  already, else there is an implicit copy of it in the instance.
1360
1361          elsif In_Instance then
1362             null;
1363
1364          elsif (Op_Name = Name_Op_Multiply or else Op_Name = Name_Op_Divide)
1365            and then Is_Fixed_Point_Type (Etype (Left_Opnd  (Op_Node)))
1366            and then Is_Fixed_Point_Type (Etype (Right_Opnd (Op_Node)))
1367          then
1368             if Pack /= Standard_Standard then
1369                Error := True;
1370             end if;
1371
1372          --  Ada 2005 AI-420: Predefined equality on Universal_Access is
1373          --  available.
1374
1375          elsif Ada_Version >= Ada_2005
1376            and then (Op_Name = Name_Op_Eq or else Op_Name = Name_Op_Ne)
1377            and then Ekind (Etype (Act1)) = E_Anonymous_Access_Type
1378          then
1379             null;
1380
1381          else
1382             Opnd_Type := Base_Type (Etype (Right_Opnd (Op_Node)));
1383
1384             if Op_Name = Name_Op_Concat then
1385                Opnd_Type := Base_Type (Typ);
1386
1387             elsif (Scope (Opnd_Type) = Standard_Standard
1388                      and then Is_Binary)
1389               or else (Nkind (Right_Opnd (Op_Node)) = N_Attribute_Reference
1390                         and then Is_Binary
1391                         and then not Comes_From_Source (Opnd_Type))
1392             then
1393                Opnd_Type := Base_Type (Etype (Left_Opnd (Op_Node)));
1394             end if;
1395
1396             if Scope (Opnd_Type) = Standard_Standard then
1397
1398                --  Verify that the scope contains a type that corresponds to
1399                --  the given literal. Optimize the case where Pack is Standard.
1400
1401                if Pack /= Standard_Standard then
1402
1403                   if Opnd_Type = Universal_Integer then
1404                      Orig_Type := Type_In_P (Is_Integer_Type'Access);
1405
1406                   elsif Opnd_Type = Universal_Real then
1407                      Orig_Type := Type_In_P (Is_Real_Type'Access);
1408
1409                   elsif Opnd_Type = Any_String then
1410                      Orig_Type := Type_In_P (Is_String_Type'Access);
1411
1412                   elsif Opnd_Type = Any_Access then
1413                      Orig_Type := Type_In_P (Is_Definite_Access_Type'Access);
1414
1415                   elsif Opnd_Type = Any_Composite then
1416                      Orig_Type := Type_In_P (Is_Composite_Type'Access);
1417
1418                      if Present (Orig_Type) then
1419                         if Has_Private_Component (Orig_Type) then
1420                            Orig_Type := Empty;
1421                         else
1422                            Set_Etype (Act1, Orig_Type);
1423
1424                            if Is_Binary then
1425                               Set_Etype (Act2, Orig_Type);
1426                            end if;
1427                         end if;
1428                      end if;
1429
1430                   else
1431                      Orig_Type := Empty;
1432                   end if;
1433
1434                   Error := No (Orig_Type);
1435                end if;
1436
1437             elsif Ekind (Opnd_Type) = E_Allocator_Type
1438                and then No (Type_In_P (Is_Definite_Access_Type'Access))
1439             then
1440                Error := True;
1441
1442             --  If the type is defined elsewhere, and the operator is not
1443             --  defined in the given scope (by a renaming declaration, e.g.)
1444             --  then this is an error as well. If an extension of System is
1445             --  present, and the type may be defined there, Pack must be
1446             --  System itself.
1447
1448             elsif Scope (Opnd_Type) /= Pack
1449               and then Scope (Op_Id) /= Pack
1450               and then (No (System_Aux_Id)
1451                          or else Scope (Opnd_Type) /= System_Aux_Id
1452                          or else Pack /= Scope (System_Aux_Id))
1453             then
1454                if not Is_Overloaded (Right_Opnd (Op_Node)) then
1455                   Error := True;
1456                else
1457                   Error := not Operand_Type_In_Scope (Pack);
1458                end if;
1459
1460             elsif Pack = Standard_Standard
1461               and then not Operand_Type_In_Scope (Standard_Standard)
1462             then
1463                Error := True;
1464             end if;
1465          end if;
1466
1467          if Error then
1468             Error_Msg_Node_2 := Pack;
1469             Error_Msg_NE
1470               ("& not declared in&", N, Selector_Name (Name (N)));
1471             Set_Etype (N, Any_Type);
1472             return;
1473
1474          --  Detect a mismatch between the context type and the result type
1475          --  in the named package, which is otherwise not detected if the
1476          --  operands are universal. Check is only needed if source entity is
1477          --  an operator, not a function that renames an operator.
1478
1479          elsif Nkind (Parent (N)) /= N_Type_Conversion
1480            and then Ekind (Entity (Name (N))) = E_Operator
1481            and then Is_Numeric_Type (Typ)
1482            and then not Is_Universal_Numeric_Type (Typ)
1483            and then Scope (Base_Type (Typ)) /= Pack
1484            and then not In_Instance
1485          then
1486             if Is_Fixed_Point_Type (Typ)
1487               and then (Op_Name = Name_Op_Multiply
1488                           or else
1489                         Op_Name = Name_Op_Divide)
1490             then
1491                --  Already checked above
1492
1493                null;
1494
1495             --  Operator may be defined in an extension of System
1496
1497             elsif Present (System_Aux_Id)
1498               and then Scope (Opnd_Type) = System_Aux_Id
1499             then
1500                null;
1501
1502             else
1503                --  Could we use Wrong_Type here??? (this would require setting
1504                --  Etype (N) to the actual type found where Typ was expected).
1505
1506                Error_Msg_NE ("expect }", N, Typ);
1507             end if;
1508          end if;
1509       end if;
1510
1511       Set_Chars  (Op_Node, Op_Name);
1512
1513       if not Is_Private_Type (Etype (N)) then
1514          Set_Etype (Op_Node, Base_Type (Etype (N)));
1515       else
1516          Set_Etype (Op_Node, Etype (N));
1517       end if;
1518
1519       --  If this is a call to a function that renames a predefined equality,
1520       --  the renaming declaration provides a type that must be used to
1521       --  resolve the operands. This must be done now because resolution of
1522       --  the equality node will not resolve any remaining ambiguity, and it
1523       --  assumes that the first operand is not overloaded.
1524
1525       if (Op_Name = Name_Op_Eq or else Op_Name = Name_Op_Ne)
1526         and then Ekind (Func) = E_Function
1527         and then Is_Overloaded (Act1)
1528       then
1529          Resolve (Act1, Base_Type (Etype (First_Formal (Func))));
1530          Resolve (Act2, Base_Type (Etype (First_Formal (Func))));
1531       end if;
1532
1533       Set_Entity (Op_Node, Op_Id);
1534       Generate_Reference (Op_Id, N, ' ');
1535
1536       --  Do rewrite setting Comes_From_Source on the result if the original
1537       --  call came from source. Although it is not strictly the case that the
1538       --  operator as such comes from the source, logically it corresponds
1539       --  exactly to the function call in the source, so it should be marked
1540       --  this way (e.g. to make sure that validity checks work fine).
1541
1542       declare
1543          CS : constant Boolean := Comes_From_Source (N);
1544       begin
1545          Rewrite (N, Op_Node);
1546          Set_Comes_From_Source (N, CS);
1547       end;
1548
1549       --  If this is an arithmetic operator and the result type is private,
1550       --  the operands and the result must be wrapped in conversion to
1551       --  expose the underlying numeric type and expand the proper checks,
1552       --  e.g. on division.
1553
1554       if Is_Private_Type (Typ) then
1555          case Nkind (N) is
1556             when N_Op_Add   | N_Op_Subtract | N_Op_Multiply | N_Op_Divide |
1557                  N_Op_Expon | N_Op_Mod      | N_Op_Rem      =>
1558                Resolve_Intrinsic_Operator (N, Typ);
1559
1560             when N_Op_Plus  | N_Op_Minus    | N_Op_Abs      =>
1561                Resolve_Intrinsic_Unary_Operator (N, Typ);
1562
1563             when others =>
1564                Resolve (N, Typ);
1565          end case;
1566       else
1567          Resolve (N, Typ);
1568       end if;
1569    end Make_Call_Into_Operator;
1570
1571    -------------------
1572    -- Operator_Kind --
1573    -------------------
1574
1575    function Operator_Kind
1576      (Op_Name   : Name_Id;
1577       Is_Binary : Boolean) return Node_Kind
1578    is
1579       Kind : Node_Kind;
1580
1581    begin
1582       --  Use CASE statement or array???
1583
1584       if Is_Binary then
1585          if    Op_Name =  Name_Op_And      then
1586             Kind := N_Op_And;
1587          elsif Op_Name =  Name_Op_Or       then
1588             Kind := N_Op_Or;
1589          elsif Op_Name =  Name_Op_Xor      then
1590             Kind := N_Op_Xor;
1591          elsif Op_Name =  Name_Op_Eq       then
1592             Kind := N_Op_Eq;
1593          elsif Op_Name =  Name_Op_Ne       then
1594             Kind := N_Op_Ne;
1595          elsif Op_Name =  Name_Op_Lt       then
1596             Kind := N_Op_Lt;
1597          elsif Op_Name =  Name_Op_Le       then
1598             Kind := N_Op_Le;
1599          elsif Op_Name =  Name_Op_Gt       then
1600             Kind := N_Op_Gt;
1601          elsif Op_Name =  Name_Op_Ge       then
1602             Kind := N_Op_Ge;
1603          elsif Op_Name =  Name_Op_Add      then
1604             Kind := N_Op_Add;
1605          elsif Op_Name =  Name_Op_Subtract then
1606             Kind := N_Op_Subtract;
1607          elsif Op_Name =  Name_Op_Concat   then
1608             Kind := N_Op_Concat;
1609          elsif Op_Name =  Name_Op_Multiply then
1610             Kind := N_Op_Multiply;
1611          elsif Op_Name =  Name_Op_Divide   then
1612             Kind := N_Op_Divide;
1613          elsif Op_Name =  Name_Op_Mod      then
1614             Kind := N_Op_Mod;
1615          elsif Op_Name =  Name_Op_Rem      then
1616             Kind := N_Op_Rem;
1617          elsif Op_Name =  Name_Op_Expon    then
1618             Kind := N_Op_Expon;
1619          else
1620             raise Program_Error;
1621          end if;
1622
1623       --  Unary operators
1624
1625       else
1626          if    Op_Name =  Name_Op_Add      then
1627             Kind := N_Op_Plus;
1628          elsif Op_Name =  Name_Op_Subtract then
1629             Kind := N_Op_Minus;
1630          elsif Op_Name =  Name_Op_Abs      then
1631             Kind := N_Op_Abs;
1632          elsif Op_Name =  Name_Op_Not      then
1633             Kind := N_Op_Not;
1634          else
1635             raise Program_Error;
1636          end if;
1637       end if;
1638
1639       return Kind;
1640    end Operator_Kind;
1641
1642    ----------------------------
1643    -- Preanalyze_And_Resolve --
1644    ----------------------------
1645
1646    procedure Preanalyze_And_Resolve (N : Node_Id; T : Entity_Id) is
1647       Save_Full_Analysis : constant Boolean := Full_Analysis;
1648
1649    begin
1650       Full_Analysis := False;
1651       Expander_Mode_Save_And_Set (False);
1652
1653       --  We suppress all checks for this analysis, since the checks will
1654       --  be applied properly, and in the right location, when the default
1655       --  expression is reanalyzed and reexpanded later on.
1656
1657       Analyze_And_Resolve (N, T, Suppress => All_Checks);
1658
1659       Expander_Mode_Restore;
1660       Full_Analysis := Save_Full_Analysis;
1661    end Preanalyze_And_Resolve;
1662
1663    --  Version without context type
1664
1665    procedure Preanalyze_And_Resolve (N : Node_Id) is
1666       Save_Full_Analysis : constant Boolean := Full_Analysis;
1667
1668    begin
1669       Full_Analysis := False;
1670       Expander_Mode_Save_And_Set (False);
1671
1672       Analyze (N);
1673       Resolve (N, Etype (N), Suppress => All_Checks);
1674
1675       Expander_Mode_Restore;
1676       Full_Analysis := Save_Full_Analysis;
1677    end Preanalyze_And_Resolve;
1678
1679    ----------------------------------
1680    -- Replace_Actual_Discriminants --
1681    ----------------------------------
1682
1683    procedure Replace_Actual_Discriminants (N : Node_Id; Default : Node_Id) is
1684       Loc : constant Source_Ptr := Sloc (N);
1685       Tsk : Node_Id := Empty;
1686
1687       function Process_Discr (Nod : Node_Id) return Traverse_Result;
1688
1689       -------------------
1690       -- Process_Discr --
1691       -------------------
1692
1693       function Process_Discr (Nod : Node_Id) return Traverse_Result is
1694          Ent : Entity_Id;
1695
1696       begin
1697          if Nkind (Nod) = N_Identifier then
1698             Ent := Entity (Nod);
1699
1700             if Present (Ent)
1701               and then Ekind (Ent) = E_Discriminant
1702             then
1703                Rewrite (Nod,
1704                  Make_Selected_Component (Loc,
1705                    Prefix        => New_Copy_Tree (Tsk, New_Sloc => Loc),
1706                    Selector_Name => Make_Identifier (Loc, Chars (Ent))));
1707
1708                Set_Etype (Nod, Etype (Ent));
1709             end if;
1710
1711          end if;
1712
1713          return OK;
1714       end Process_Discr;
1715
1716       procedure Replace_Discrs is new Traverse_Proc (Process_Discr);
1717
1718    --  Start of processing for Replace_Actual_Discriminants
1719
1720    begin
1721       if not Expander_Active then
1722          return;
1723       end if;
1724
1725       if Nkind (Name (N)) = N_Selected_Component then
1726          Tsk := Prefix (Name (N));
1727
1728       elsif Nkind (Name (N)) = N_Indexed_Component then
1729          Tsk := Prefix (Prefix (Name (N)));
1730       end if;
1731
1732       if No (Tsk) then
1733          return;
1734       else
1735          Replace_Discrs (Default);
1736       end if;
1737    end Replace_Actual_Discriminants;
1738
1739    -------------
1740    -- Resolve --
1741    -------------
1742
1743    procedure Resolve (N : Node_Id; Typ : Entity_Id) is
1744       Ambiguous : Boolean   := False;
1745       Ctx_Type  : Entity_Id := Typ;
1746       Expr_Type : Entity_Id := Empty; -- prevent junk warning
1747       Err_Type  : Entity_Id := Empty;
1748       Found     : Boolean   := False;
1749       From_Lib  : Boolean;
1750       I         : Interp_Index;
1751       I1        : Interp_Index := 0;  -- prevent junk warning
1752       It        : Interp;
1753       It1       : Interp;
1754       Seen      : Entity_Id := Empty; -- prevent junk warning
1755
1756       procedure Build_Explicit_Dereference
1757         (Expr : Node_Id;
1758          Disc : Entity_Id);
1759       --  AI05-139: Names with implicit dereference. If the expression N is a
1760       --  reference type and the context imposes the corresponding designated
1761       --  type, convert N into N.Disc.all. Such expressions are always over-
1762       --  loaded with both interpretations, and the dereference interpretation
1763       --  carries the name of the reference discriminant.
1764
1765       function Comes_From_Predefined_Lib_Unit (Nod : Node_Id) return Boolean;
1766       --  Determine whether a node comes from a predefined library unit or
1767       --  Standard.
1768
1769       procedure Patch_Up_Value (N : Node_Id; Typ : Entity_Id);
1770       --  Try and fix up a literal so that it matches its expected type. New
1771       --  literals are manufactured if necessary to avoid cascaded errors.
1772
1773       procedure Report_Ambiguous_Argument;
1774       --  Additional diagnostics when an ambiguous call has an ambiguous
1775       --  argument (typically a controlling actual).
1776
1777       procedure Resolution_Failed;
1778       --  Called when attempt at resolving current expression fails
1779
1780       --------------------------------
1781       -- Build_Explicit_Dereference --
1782       --------------------------------
1783
1784       procedure Build_Explicit_Dereference
1785         (Expr : Node_Id;
1786          Disc : Entity_Id)
1787       is
1788          Loc : constant Source_Ptr := Sloc (Expr);
1789
1790       begin
1791          Set_Is_Overloaded (Expr, False);
1792          Rewrite (Expr,
1793            Make_Explicit_Dereference (Loc,
1794              Prefix =>
1795                Make_Selected_Component (Loc,
1796                  Prefix => Relocate_Node (Expr),
1797                  Selector_Name =>
1798                New_Occurrence_Of (Disc, Loc))));
1799
1800          Set_Etype (Prefix (Expr), Etype (Disc));
1801          Set_Etype (Expr, Typ);
1802       end Build_Explicit_Dereference;
1803
1804       ------------------------------------
1805       -- Comes_From_Predefined_Lib_Unit --
1806       -------------------------------------
1807
1808       function Comes_From_Predefined_Lib_Unit (Nod : Node_Id) return Boolean is
1809       begin
1810          return
1811            Sloc (Nod) = Standard_Location
1812              or else Is_Predefined_File_Name
1813                        (Unit_File_Name (Get_Source_Unit (Sloc (Nod))));
1814       end Comes_From_Predefined_Lib_Unit;
1815
1816       --------------------
1817       -- Patch_Up_Value --
1818       --------------------
1819
1820       procedure Patch_Up_Value (N : Node_Id; Typ : Entity_Id) is
1821       begin
1822          if Nkind (N) = N_Integer_Literal
1823            and then Is_Real_Type (Typ)
1824          then
1825             Rewrite (N,
1826               Make_Real_Literal (Sloc (N),
1827                 Realval => UR_From_Uint (Intval (N))));
1828             Set_Etype (N, Universal_Real);
1829             Set_Is_Static_Expression (N);
1830
1831          elsif Nkind (N) = N_Real_Literal
1832            and then Is_Integer_Type (Typ)
1833          then
1834             Rewrite (N,
1835               Make_Integer_Literal (Sloc (N),
1836                 Intval => UR_To_Uint (Realval (N))));
1837             Set_Etype (N, Universal_Integer);
1838             Set_Is_Static_Expression (N);
1839
1840          elsif Nkind (N) = N_String_Literal
1841            and then Is_Character_Type (Typ)
1842          then
1843             Set_Character_Literal_Name (Char_Code (Character'Pos ('A')));
1844             Rewrite (N,
1845               Make_Character_Literal (Sloc (N),
1846                 Chars => Name_Find,
1847                 Char_Literal_Value =>
1848                   UI_From_Int (Character'Pos ('A'))));
1849             Set_Etype (N, Any_Character);
1850             Set_Is_Static_Expression (N);
1851
1852          elsif Nkind (N) /= N_String_Literal
1853            and then Is_String_Type (Typ)
1854          then
1855             Rewrite (N,
1856               Make_String_Literal (Sloc (N),
1857                 Strval => End_String));
1858
1859          elsif Nkind (N) = N_Range then
1860             Patch_Up_Value (Low_Bound (N), Typ);
1861             Patch_Up_Value (High_Bound (N), Typ);
1862          end if;
1863       end Patch_Up_Value;
1864
1865       -------------------------------
1866       -- Report_Ambiguous_Argument --
1867       -------------------------------
1868
1869       procedure Report_Ambiguous_Argument is
1870          Arg : constant Node_Id := First (Parameter_Associations (N));
1871          I   : Interp_Index;
1872          It  : Interp;
1873
1874       begin
1875          if Nkind (Arg) = N_Function_Call
1876            and then Is_Entity_Name (Name (Arg))
1877            and then Is_Overloaded (Name (Arg))
1878          then
1879             Error_Msg_NE ("ambiguous call to&", Arg, Name (Arg));
1880
1881             --  Could use comments on what is going on here ???
1882
1883             Get_First_Interp (Name (Arg), I, It);
1884             while Present (It.Nam) loop
1885                Error_Msg_Sloc := Sloc (It.Nam);
1886
1887                if Nkind (Parent (It.Nam)) = N_Full_Type_Declaration then
1888                   Error_Msg_N ("interpretation (inherited) #!", Arg);
1889                else
1890                   Error_Msg_N ("interpretation #!", Arg);
1891                end if;
1892
1893                Get_Next_Interp (I, It);
1894             end loop;
1895          end if;
1896       end Report_Ambiguous_Argument;
1897
1898       -----------------------
1899       -- Resolution_Failed --
1900       -----------------------
1901
1902       procedure Resolution_Failed is
1903       begin
1904          Patch_Up_Value (N, Typ);
1905          Set_Etype (N, Typ);
1906          Debug_A_Exit ("resolving  ", N, " (done, resolution failed)");
1907          Set_Is_Overloaded (N, False);
1908
1909          --  The caller will return without calling the expander, so we need
1910          --  to set the analyzed flag. Note that it is fine to set Analyzed
1911          --  to True even if we are in the middle of a shallow analysis,
1912          --  (see the spec of sem for more details) since this is an error
1913          --  situation anyway, and there is no point in repeating the
1914          --  analysis later (indeed it won't work to repeat it later, since
1915          --  we haven't got a clear resolution of which entity is being
1916          --  referenced.)
1917
1918          Set_Analyzed (N, True);
1919          return;
1920       end Resolution_Failed;
1921
1922    --  Start of processing for Resolve
1923
1924    begin
1925       if N = Error then
1926          return;
1927       end if;
1928
1929       --  Access attribute on remote subprogram cannot be used for
1930       --  a non-remote access-to-subprogram type.
1931
1932       if Nkind (N) = N_Attribute_Reference
1933         and then (Attribute_Name (N) = Name_Access              or else
1934                   Attribute_Name (N) = Name_Unrestricted_Access or else
1935                   Attribute_Name (N) = Name_Unchecked_Access)
1936         and then Comes_From_Source (N)
1937         and then Is_Entity_Name (Prefix (N))
1938         and then Is_Subprogram (Entity (Prefix (N)))
1939         and then Is_Remote_Call_Interface (Entity (Prefix (N)))
1940         and then not Is_Remote_Access_To_Subprogram_Type (Typ)
1941       then
1942          Error_Msg_N
1943            ("prefix must statically denote a non-remote subprogram", N);
1944       end if;
1945
1946       From_Lib := Comes_From_Predefined_Lib_Unit (N);
1947
1948       --  If the context is a Remote_Access_To_Subprogram, access attributes
1949       --  must be resolved with the corresponding fat pointer. There is no need
1950       --  to check for the attribute name since the return type of an
1951       --  attribute is never a remote type.
1952
1953       if Nkind (N) = N_Attribute_Reference
1954         and then Comes_From_Source (N)
1955         and then (Is_Remote_Call_Interface (Typ) or else Is_Remote_Types (Typ))
1956       then
1957          declare
1958             Attr      : constant Attribute_Id :=
1959                           Get_Attribute_Id (Attribute_Name (N));
1960             Pref      : constant Node_Id      := Prefix (N);
1961             Decl      : Node_Id;
1962             Spec      : Node_Id;
1963             Is_Remote : Boolean := True;
1964
1965          begin
1966             --  Check that Typ is a remote access-to-subprogram type
1967
1968             if Is_Remote_Access_To_Subprogram_Type (Typ) then
1969
1970                --  Prefix (N) must statically denote a remote subprogram
1971                --  declared in a package specification.
1972
1973                if Attr = Attribute_Access then
1974                   Decl := Unit_Declaration_Node (Entity (Pref));
1975
1976                   if Nkind (Decl) = N_Subprogram_Body then
1977                      Spec := Corresponding_Spec (Decl);
1978
1979                      if not No (Spec) then
1980                         Decl := Unit_Declaration_Node (Spec);
1981                      end if;
1982                   end if;
1983
1984                   Spec := Parent (Decl);
1985
1986                   if not Is_Entity_Name (Prefix (N))
1987                     or else Nkind (Spec) /= N_Package_Specification
1988                     or else
1989                       not Is_Remote_Call_Interface (Defining_Entity (Spec))
1990                   then
1991                      Is_Remote := False;
1992                      Error_Msg_N
1993                        ("prefix must statically denote a remote subprogram ",
1994                         N);
1995                   end if;
1996                end if;
1997
1998                --   If we are generating code for a distributed program.
1999                --   perform semantic checks against the corresponding
2000                --   remote entities.
2001
2002                if (Attr = Attribute_Access           or else
2003                    Attr = Attribute_Unchecked_Access or else
2004                    Attr = Attribute_Unrestricted_Access)
2005                  and then Expander_Active
2006                  and then Get_PCS_Name /= Name_No_DSA
2007                then
2008                   Check_Subtype_Conformant
2009                     (New_Id  => Entity (Prefix (N)),
2010                      Old_Id  => Designated_Type
2011                                   (Corresponding_Remote_Type (Typ)),
2012                      Err_Loc => N);
2013
2014                   if Is_Remote then
2015                      Process_Remote_AST_Attribute (N, Typ);
2016                   end if;
2017                end if;
2018             end if;
2019          end;
2020       end if;
2021
2022       Debug_A_Entry ("resolving  ", N);
2023
2024       if Comes_From_Source (N) then
2025          if Is_Fixed_Point_Type (Typ) then
2026             Check_Restriction (No_Fixed_Point, N);
2027
2028          elsif Is_Floating_Point_Type (Typ)
2029            and then Typ /= Universal_Real
2030            and then Typ /= Any_Real
2031          then
2032             Check_Restriction (No_Floating_Point, N);
2033          end if;
2034       end if;
2035
2036       --  Return if already analyzed
2037
2038       if Analyzed (N) then
2039          Debug_A_Exit ("resolving  ", N, "  (done, already analyzed)");
2040          return;
2041
2042       --  Return if type = Any_Type (previous error encountered)
2043
2044       elsif Etype (N) = Any_Type then
2045          Debug_A_Exit ("resolving  ", N, "  (done, Etype = Any_Type)");
2046          return;
2047       end if;
2048
2049       Check_Parameterless_Call (N);
2050
2051       --  If not overloaded, then we know the type, and all that needs doing
2052       --  is to check that this type is compatible with the context.
2053
2054       if not Is_Overloaded (N) then
2055          Found := Covers (Typ, Etype (N));
2056          Expr_Type := Etype (N);
2057
2058       --  In the overloaded case, we must select the interpretation that
2059       --  is compatible with the context (i.e. the type passed to Resolve)
2060
2061       else
2062          --  Loop through possible interpretations
2063
2064          Get_First_Interp (N, I, It);
2065          Interp_Loop : while Present (It.Typ) loop
2066
2067             --  We are only interested in interpretations that are compatible
2068             --  with the expected type, any other interpretations are ignored.
2069
2070             if not Covers (Typ, It.Typ) then
2071                if Debug_Flag_V then
2072                   Write_Str ("    interpretation incompatible with context");
2073                   Write_Eol;
2074                end if;
2075
2076             else
2077                --  Skip the current interpretation if it is disabled by an
2078                --  abstract operator. This action is performed only when the
2079                --  type against which we are resolving is the same as the
2080                --  type of the interpretation.
2081
2082                if Ada_Version >= Ada_2005
2083                  and then It.Typ = Typ
2084                  and then Typ /= Universal_Integer
2085                  and then Typ /= Universal_Real
2086                  and then Present (It.Abstract_Op)
2087                then
2088                   goto Continue;
2089                end if;
2090
2091                --  First matching interpretation
2092
2093                if not Found then
2094                   Found := True;
2095                   I1    := I;
2096                   Seen  := It.Nam;
2097                   Expr_Type := It.Typ;
2098
2099                --  Matching interpretation that is not the first, maybe an
2100                --  error, but there are some cases where preference rules are
2101                --  used to choose between the two possibilities. These and
2102                --  some more obscure cases are handled in Disambiguate.
2103
2104                else
2105                   --  If the current statement is part of a predefined library
2106                   --  unit, then all interpretations which come from user level
2107                   --  packages should not be considered.
2108
2109                   if From_Lib
2110                     and then not Comes_From_Predefined_Lib_Unit (It.Nam)
2111                   then
2112                      goto Continue;
2113                   end if;
2114
2115                   Error_Msg_Sloc := Sloc (Seen);
2116                   It1 := Disambiguate (N, I1, I, Typ);
2117
2118                   --  Disambiguation has succeeded. Skip the remaining
2119                   --  interpretations.
2120
2121                   if It1 /= No_Interp then
2122                      Seen := It1.Nam;
2123                      Expr_Type := It1.Typ;
2124
2125                      while Present (It.Typ) loop
2126                         Get_Next_Interp (I, It);
2127                      end loop;
2128
2129                   else
2130                      --  Before we issue an ambiguity complaint, check for
2131                      --  the case of a subprogram call where at least one
2132                      --  of the arguments is Any_Type, and if so, suppress
2133                      --  the message, since it is a cascaded error.
2134
2135                      if Nkind_In (N, N_Function_Call,
2136                                      N_Procedure_Call_Statement)
2137                      then
2138                         declare
2139                            A : Node_Id;
2140                            E : Node_Id;
2141
2142                         begin
2143                            A := First_Actual (N);
2144                            while Present (A) loop
2145                               E := A;
2146
2147                               if Nkind (E) = N_Parameter_Association then
2148                                  E := Explicit_Actual_Parameter (E);
2149                               end if;
2150
2151                               if Etype (E) = Any_Type then
2152                                  if Debug_Flag_V then
2153                                     Write_Str ("Any_Type in call");
2154                                     Write_Eol;
2155                                  end if;
2156
2157                                  exit Interp_Loop;
2158                               end if;
2159
2160                               Next_Actual (A);
2161                            end loop;
2162                         end;
2163
2164                      elsif Nkind (N) in N_Binary_Op
2165                        and then (Etype (Left_Opnd (N)) = Any_Type
2166                                   or else Etype (Right_Opnd (N)) = Any_Type)
2167                      then
2168                         exit Interp_Loop;
2169
2170                      elsif Nkind (N) in  N_Unary_Op
2171                        and then Etype (Right_Opnd (N)) = Any_Type
2172                      then
2173                         exit Interp_Loop;
2174                      end if;
2175
2176                      --  Not that special case, so issue message using the
2177                      --  flag Ambiguous to control printing of the header
2178                      --  message only at the start of an ambiguous set.
2179
2180                      if not Ambiguous then
2181                         if Nkind (N) = N_Function_Call
2182                           and then Nkind (Name (N)) = N_Explicit_Dereference
2183                         then
2184                            Error_Msg_N
2185                              ("ambiguous expression "
2186                                & "(cannot resolve indirect call)!", N);
2187                         else
2188                            Error_Msg_NE -- CODEFIX
2189                              ("ambiguous expression (cannot resolve&)!",
2190                               N, It.Nam);
2191                         end if;
2192
2193                         Ambiguous := True;
2194
2195                         if Nkind (Parent (Seen)) = N_Full_Type_Declaration then
2196                            Error_Msg_N
2197                              ("\\possible interpretation (inherited)#!", N);
2198                         else
2199                            Error_Msg_N -- CODEFIX
2200                              ("\\possible interpretation#!", N);
2201                         end if;
2202
2203                         if Nkind_In
2204                              (N, N_Procedure_Call_Statement, N_Function_Call)
2205                           and then Present (Parameter_Associations (N))
2206                         then
2207                            Report_Ambiguous_Argument;
2208                         end if;
2209                      end if;
2210
2211                      Error_Msg_Sloc := Sloc (It.Nam);
2212
2213                      --  By default, the error message refers to the candidate
2214                      --  interpretation. But if it is a predefined operator, it
2215                      --  is implicitly declared at the declaration of the type
2216                      --  of the operand. Recover the sloc of that declaration
2217                      --  for the error message.
2218
2219                      if Nkind (N) in N_Op
2220                        and then Scope (It.Nam) = Standard_Standard
2221                        and then not Is_Overloaded (Right_Opnd (N))
2222                        and then Scope (Base_Type (Etype (Right_Opnd (N)))) /=
2223                                                              Standard_Standard
2224                      then
2225                         Err_Type := First_Subtype (Etype (Right_Opnd (N)));
2226
2227                         if Comes_From_Source (Err_Type)
2228                           and then Present (Parent (Err_Type))
2229                         then
2230                            Error_Msg_Sloc := Sloc (Parent (Err_Type));
2231                         end if;
2232
2233                      elsif Nkind (N) in N_Binary_Op
2234                        and then Scope (It.Nam) = Standard_Standard
2235                        and then not Is_Overloaded (Left_Opnd (N))
2236                        and then Scope (Base_Type (Etype (Left_Opnd (N)))) /=
2237                                                              Standard_Standard
2238                      then
2239                         Err_Type := First_Subtype (Etype (Left_Opnd (N)));
2240
2241                         if Comes_From_Source (Err_Type)
2242                           and then Present (Parent (Err_Type))
2243                         then
2244                            Error_Msg_Sloc := Sloc (Parent (Err_Type));
2245                         end if;
2246
2247                      --  If this is an indirect call, use the subprogram_type
2248                      --  in the message, to have a meaningful location. Also
2249                      --  indicate if this is an inherited operation, created
2250                      --  by a type declaration.
2251
2252                      elsif Nkind (N) = N_Function_Call
2253                        and then Nkind (Name (N)) = N_Explicit_Dereference
2254                        and then Is_Type (It.Nam)
2255                      then
2256                         Err_Type := It.Nam;
2257                         Error_Msg_Sloc :=
2258                           Sloc (Associated_Node_For_Itype (Err_Type));
2259                      else
2260                         Err_Type := Empty;
2261                      end if;
2262
2263                      if Nkind (N) in N_Op
2264                        and then Scope (It.Nam) = Standard_Standard
2265                        and then Present (Err_Type)
2266                      then
2267                         --  Special-case the message for universal_fixed
2268                         --  operators, which are not declared with the type
2269                         --  of the operand, but appear forever in Standard.
2270
2271                         if  It.Typ = Universal_Fixed
2272                           and then Scope (It.Nam) = Standard_Standard
2273                         then
2274                            Error_Msg_N
2275                              ("\\possible interpretation as " &
2276                                 "universal_fixed operation " &
2277                                   "(RM 4.5.5 (19))", N);
2278                         else
2279                            Error_Msg_N
2280                              ("\\possible interpretation (predefined)#!", N);
2281                         end if;
2282
2283                      elsif
2284                        Nkind (Parent (It.Nam)) = N_Full_Type_Declaration
2285                      then
2286                         Error_Msg_N
2287                           ("\\possible interpretation (inherited)#!", N);
2288                      else
2289                         Error_Msg_N -- CODEFIX
2290                           ("\\possible interpretation#!", N);
2291                      end if;
2292
2293                   end if;
2294                end if;
2295
2296                --  We have a matching interpretation, Expr_Type is the type
2297                --  from this interpretation, and Seen is the entity.
2298
2299                --  For an operator, just set the entity name. The type will be
2300                --  set by the specific operator resolution routine.
2301
2302                if Nkind (N) in N_Op then
2303                   Set_Entity (N, Seen);
2304                   Generate_Reference (Seen, N);
2305
2306                elsif Nkind (N) = N_Case_Expression then
2307                   Set_Etype (N, Expr_Type);
2308
2309                elsif Nkind (N) = N_Character_Literal then
2310                   Set_Etype (N, Expr_Type);
2311
2312                elsif Nkind (N) = N_Conditional_Expression then
2313                   Set_Etype (N, Expr_Type);
2314
2315                --  AI05-0139-2: Expression is overloaded because type has
2316                --  implicit dereference. If type matches context, no implicit
2317                --  dereference is involved.
2318
2319                elsif Has_Implicit_Dereference (Expr_Type) then
2320                   Set_Etype (N, Expr_Type);
2321                   Set_Is_Overloaded (N, False);
2322                   exit Interp_Loop;
2323
2324                elsif Is_Overloaded (N)
2325                  and then Present (It.Nam)
2326                  and then Ekind (It.Nam) = E_Discriminant
2327                  and then Has_Implicit_Dereference (It.Nam)
2328                then
2329                   Build_Explicit_Dereference (N, It.Nam);
2330
2331                --  For an explicit dereference, attribute reference, range,
2332                --  short-circuit form (which is not an operator node), or call
2333                --  with a name that is an explicit dereference, there is
2334                --  nothing to be done at this point.
2335
2336                elsif Nkind_In (N, N_Explicit_Dereference,
2337                                   N_Attribute_Reference,
2338                                   N_And_Then,
2339                                   N_Indexed_Component,
2340                                   N_Or_Else,
2341                                   N_Range,
2342                                   N_Selected_Component,
2343                                   N_Slice)
2344                  or else Nkind (Name (N)) = N_Explicit_Dereference
2345                then
2346                   null;
2347
2348                --  For procedure or function calls, set the type of the name,
2349                --  and also the entity pointer for the prefix.
2350
2351                elsif Nkind_In (N, N_Procedure_Call_Statement, N_Function_Call)
2352                  and then Is_Entity_Name (Name (N))
2353                then
2354                   Set_Etype  (Name (N), Expr_Type);
2355                   Set_Entity (Name (N), Seen);
2356                   Generate_Reference (Seen, Name (N));
2357
2358                elsif Nkind (N) = N_Function_Call
2359                  and then Nkind (Name (N)) = N_Selected_Component
2360                then
2361                   Set_Etype (Name (N), Expr_Type);
2362                   Set_Entity (Selector_Name (Name (N)), Seen);
2363                   Generate_Reference (Seen, Selector_Name (Name (N)));
2364
2365                --  For all other cases, just set the type of the Name
2366
2367                else
2368                   Set_Etype (Name (N), Expr_Type);
2369                end if;
2370
2371             end if;
2372
2373             <<Continue>>
2374
2375             --  Move to next interpretation
2376
2377             exit Interp_Loop when No (It.Typ);
2378
2379             Get_Next_Interp (I, It);
2380          end loop Interp_Loop;
2381       end if;
2382
2383       --  At this stage Found indicates whether or not an acceptable
2384       --  interpretation exists. If not, then we have an error, except that if
2385       --  the context is Any_Type as a result of some other error, then we
2386       --  suppress the error report.
2387
2388       if not Found then
2389          if Typ /= Any_Type then
2390
2391             --  If type we are looking for is Void, then this is the procedure
2392             --  call case, and the error is simply that what we gave is not a
2393             --  procedure name (we think of procedure calls as expressions with
2394             --  types internally, but the user doesn't think of them this way!)
2395
2396             if Typ = Standard_Void_Type then
2397
2398                --  Special case message if function used as a procedure
2399
2400                if Nkind (N) = N_Procedure_Call_Statement
2401                  and then Is_Entity_Name (Name (N))
2402                  and then Ekind (Entity (Name (N))) = E_Function
2403                then
2404                   Error_Msg_NE
2405                     ("cannot use function & in a procedure call",
2406                      Name (N), Entity (Name (N)));
2407
2408                --  Otherwise give general message (not clear what cases this
2409                --  covers, but no harm in providing for them!)
2410
2411                else
2412                   Error_Msg_N ("expect procedure name in procedure call", N);
2413                end if;
2414
2415                Found := True;
2416
2417             --  Otherwise we do have a subexpression with the wrong type
2418
2419             --  Check for the case of an allocator which uses an access type
2420             --  instead of the designated type. This is a common error and we
2421             --  specialize the message, posting an error on the operand of the
2422             --  allocator, complaining that we expected the designated type of
2423             --  the allocator.
2424
2425             elsif Nkind (N) = N_Allocator
2426               and then Ekind (Typ) in Access_Kind
2427               and then Ekind (Etype (N)) in Access_Kind
2428               and then Designated_Type (Etype (N)) = Typ
2429             then
2430                Wrong_Type (Expression (N), Designated_Type (Typ));
2431                Found := True;
2432
2433             --  Check for view mismatch on Null in instances, for which the
2434             --  view-swapping mechanism has no identifier.
2435
2436             elsif (In_Instance or else In_Inlined_Body)
2437               and then (Nkind (N) = N_Null)
2438               and then Is_Private_Type (Typ)
2439               and then Is_Access_Type (Full_View (Typ))
2440             then
2441                Resolve (N, Full_View (Typ));
2442                Set_Etype (N, Typ);
2443                return;
2444
2445             --  Check for an aggregate. Sometimes we can get bogus aggregates
2446             --  from misuse of parentheses, and we are about to complain about
2447             --  the aggregate without even looking inside it.
2448
2449             --  Instead, if we have an aggregate of type Any_Composite, then
2450             --  analyze and resolve the component fields, and then only issue
2451             --  another message if we get no errors doing this (otherwise
2452             --  assume that the errors in the aggregate caused the problem).
2453
2454             elsif Nkind (N) = N_Aggregate
2455               and then Etype (N) = Any_Composite
2456             then
2457                --  Disable expansion in any case. If there is a type mismatch
2458                --  it may be fatal to try to expand the aggregate. The flag
2459                --  would otherwise be set to false when the error is posted.
2460
2461                Expander_Active := False;
2462
2463                declare
2464                   procedure Check_Aggr (Aggr : Node_Id);
2465                   --  Check one aggregate, and set Found to True if we have a
2466                   --  definite error in any of its elements
2467
2468                   procedure Check_Elmt (Aelmt : Node_Id);
2469                   --  Check one element of aggregate and set Found to True if
2470                   --  we definitely have an error in the element.
2471
2472                   ----------------
2473                   -- Check_Aggr --
2474                   ----------------
2475
2476                   procedure Check_Aggr (Aggr : Node_Id) is
2477                      Elmt : Node_Id;
2478
2479                   begin
2480                      if Present (Expressions (Aggr)) then
2481                         Elmt := First (Expressions (Aggr));
2482                         while Present (Elmt) loop
2483                            Check_Elmt (Elmt);
2484                            Next (Elmt);
2485                         end loop;
2486                      end if;
2487
2488                      if Present (Component_Associations (Aggr)) then
2489                         Elmt := First (Component_Associations (Aggr));
2490                         while Present (Elmt) loop
2491
2492                            --  If this is a default-initialized component, then
2493                            --  there is nothing to check. The box will be
2494                            --  replaced by the appropriate call during late
2495                            --  expansion.
2496
2497                            if not Box_Present (Elmt) then
2498                               Check_Elmt (Expression (Elmt));
2499                            end if;
2500
2501                            Next (Elmt);
2502                         end loop;
2503                      end if;
2504                   end Check_Aggr;
2505
2506                   ----------------
2507                   -- Check_Elmt --
2508                   ----------------
2509
2510                   procedure Check_Elmt (Aelmt : Node_Id) is
2511                   begin
2512                      --  If we have a nested aggregate, go inside it (to
2513                      --  attempt a naked analyze-resolve of the aggregate can
2514                      --  cause undesirable cascaded errors). Do not resolve
2515                      --  expression if it needs a type from context, as for
2516                      --  integer * fixed expression.
2517
2518                      if Nkind (Aelmt) = N_Aggregate then
2519                         Check_Aggr (Aelmt);
2520
2521                      else
2522                         Analyze (Aelmt);
2523
2524                         if not Is_Overloaded (Aelmt)
2525                           and then Etype (Aelmt) /= Any_Fixed
2526                         then
2527                            Resolve (Aelmt);
2528                         end if;
2529
2530                         if Etype (Aelmt) = Any_Type then
2531                            Found := True;
2532                         end if;
2533                      end if;
2534                   end Check_Elmt;
2535
2536                begin
2537                   Check_Aggr (N);
2538                end;
2539             end if;
2540
2541             --  If an error message was issued already, Found got reset to
2542             --  True, so if it is still False, issue standard Wrong_Type msg.
2543
2544             if not Found then
2545                if Is_Overloaded (N)
2546                  and then Nkind (N) = N_Function_Call
2547                then
2548                   declare
2549                      Subp_Name : Node_Id;
2550                   begin
2551                      if Is_Entity_Name (Name (N)) then
2552                         Subp_Name := Name (N);
2553
2554                      elsif Nkind (Name (N)) = N_Selected_Component then
2555
2556                         --  Protected operation: retrieve operation name
2557
2558                         Subp_Name := Selector_Name (Name (N));
2559
2560                      else
2561                         raise Program_Error;
2562                      end if;
2563
2564                      Error_Msg_Node_2 := Typ;
2565                      Error_Msg_NE ("no visible interpretation of&" &
2566                        " matches expected type&", N, Subp_Name);
2567                   end;
2568
2569                   if All_Errors_Mode then
2570                      declare
2571                         Index : Interp_Index;
2572                         It    : Interp;
2573
2574                      begin
2575                         Error_Msg_N ("\\possible interpretations:", N);
2576
2577                         Get_First_Interp (Name (N), Index, It);
2578                         while Present (It.Nam) loop
2579                            Error_Msg_Sloc := Sloc (It.Nam);
2580                            Error_Msg_Node_2 := It.Nam;
2581                            Error_Msg_NE
2582                              ("\\  type& for & declared#", N, It.Typ);
2583                            Get_Next_Interp (Index, It);
2584                         end loop;
2585                      end;
2586
2587                   else
2588                      Error_Msg_N ("\use -gnatf for details", N);
2589                   end if;
2590
2591                else
2592                   Wrong_Type (N, Typ);
2593                end if;
2594             end if;
2595          end if;
2596
2597          Resolution_Failed;
2598          return;
2599
2600       --  Test if we have more than one interpretation for the context
2601
2602       elsif Ambiguous then
2603          Resolution_Failed;
2604          return;
2605
2606       --  Here we have an acceptable interpretation for the context
2607
2608       else
2609          --  Propagate type information and normalize tree for various
2610          --  predefined operations. If the context only imposes a class of
2611          --  types, rather than a specific type, propagate the actual type
2612          --  downward.
2613
2614          if Typ = Any_Integer or else
2615             Typ = Any_Boolean or else
2616             Typ = Any_Modular or else
2617             Typ = Any_Real    or else
2618             Typ = Any_Discrete
2619          then
2620             Ctx_Type := Expr_Type;
2621
2622             --  Any_Fixed is legal in a real context only if a specific fixed-
2623             --  point type is imposed. If Norman Cohen can be confused by this,
2624             --  it deserves a separate message.
2625
2626             if Typ = Any_Real
2627               and then Expr_Type = Any_Fixed
2628             then
2629                Error_Msg_N ("illegal context for mixed mode operation", N);
2630                Set_Etype (N, Universal_Real);
2631                Ctx_Type := Universal_Real;
2632             end if;
2633          end if;
2634
2635          --  A user-defined operator is transformed into a function call at
2636          --  this point, so that further processing knows that operators are
2637          --  really operators (i.e. are predefined operators). User-defined
2638          --  operators that are intrinsic are just renamings of the predefined
2639          --  ones, and need not be turned into calls either, but if they rename
2640          --  a different operator, we must transform the node accordingly.
2641          --  Instantiations of Unchecked_Conversion are intrinsic but are
2642          --  treated as functions, even if given an operator designator.
2643
2644          if Nkind (N) in N_Op
2645            and then Present (Entity (N))
2646            and then Ekind (Entity (N)) /= E_Operator
2647          then
2648
2649             if not Is_Predefined_Op (Entity (N)) then
2650                Rewrite_Operator_As_Call (N, Entity (N));
2651
2652             elsif Present (Alias (Entity (N)))
2653               and then
2654                 Nkind (Parent (Parent (Entity (N)))) =
2655                                     N_Subprogram_Renaming_Declaration
2656             then
2657                Rewrite_Renamed_Operator (N, Alias (Entity (N)), Typ);
2658
2659                --  If the node is rewritten, it will be fully resolved in
2660                --  Rewrite_Renamed_Operator.
2661
2662                if Analyzed (N) then
2663                   return;
2664                end if;
2665             end if;
2666          end if;
2667
2668          case N_Subexpr'(Nkind (N)) is
2669
2670             when N_Aggregate => Resolve_Aggregate                (N, Ctx_Type);
2671
2672             when N_Allocator => Resolve_Allocator                (N, Ctx_Type);
2673
2674             when N_Short_Circuit
2675                              => Resolve_Short_Circuit            (N, Ctx_Type);
2676
2677             when N_Attribute_Reference
2678                              => Resolve_Attribute                (N, Ctx_Type);
2679
2680             when N_Case_Expression
2681                              => Resolve_Case_Expression          (N, Ctx_Type);
2682
2683             when N_Character_Literal
2684                              => Resolve_Character_Literal        (N, Ctx_Type);
2685
2686             when N_Conditional_Expression
2687                              => Resolve_Conditional_Expression   (N, Ctx_Type);
2688
2689             when N_Expanded_Name
2690                              => Resolve_Entity_Name              (N, Ctx_Type);
2691
2692             when N_Explicit_Dereference
2693                              => Resolve_Explicit_Dereference     (N, Ctx_Type);
2694
2695             when N_Expression_With_Actions
2696                              => Resolve_Expression_With_Actions  (N, Ctx_Type);
2697
2698             when N_Extension_Aggregate
2699                              => Resolve_Extension_Aggregate      (N, Ctx_Type);
2700
2701             when N_Function_Call
2702                              => Resolve_Call                     (N, Ctx_Type);
2703
2704             when N_Identifier
2705                              => Resolve_Entity_Name              (N, Ctx_Type);
2706
2707             when N_Indexed_Component
2708                              => Resolve_Indexed_Component        (N, Ctx_Type);
2709
2710             when N_Integer_Literal
2711                              => Resolve_Integer_Literal          (N, Ctx_Type);
2712
2713             when N_Membership_Test
2714                              => Resolve_Membership_Op            (N, Ctx_Type);
2715
2716             when N_Null      => Resolve_Null                     (N, Ctx_Type);
2717
2718             when N_Op_And | N_Op_Or | N_Op_Xor
2719                              => Resolve_Logical_Op               (N, Ctx_Type);
2720
2721             when N_Op_Eq | N_Op_Ne
2722                              => Resolve_Equality_Op              (N, Ctx_Type);
2723
2724             when N_Op_Lt | N_Op_Le | N_Op_Gt | N_Op_Ge
2725                              => Resolve_Comparison_Op            (N, Ctx_Type);
2726
2727             when N_Op_Not    => Resolve_Op_Not                   (N, Ctx_Type);
2728
2729             when N_Op_Add    | N_Op_Subtract | N_Op_Multiply |
2730                  N_Op_Divide | N_Op_Mod      | N_Op_Rem
2731
2732                              => Resolve_Arithmetic_Op            (N, Ctx_Type);
2733
2734             when N_Op_Concat => Resolve_Op_Concat                (N, Ctx_Type);
2735
2736             when N_Op_Expon  => Resolve_Op_Expon                 (N, Ctx_Type);
2737
2738             when N_Op_Plus | N_Op_Minus  | N_Op_Abs
2739                              => Resolve_Unary_Op                 (N, Ctx_Type);
2740
2741             when N_Op_Shift  => Resolve_Shift                    (N, Ctx_Type);
2742
2743             when N_Procedure_Call_Statement
2744                              => Resolve_Call                     (N, Ctx_Type);
2745
2746             when N_Operator_Symbol
2747                              => Resolve_Operator_Symbol          (N, Ctx_Type);
2748
2749             when N_Qualified_Expression
2750                              => Resolve_Qualified_Expression     (N, Ctx_Type);
2751
2752             when N_Quantified_Expression
2753                              => Resolve_Quantified_Expression    (N, Ctx_Type);
2754
2755             when N_Raise_xxx_Error
2756                              => Set_Etype (N, Ctx_Type);
2757
2758             when N_Range     => Resolve_Range                    (N, Ctx_Type);
2759
2760             when N_Real_Literal
2761                              => Resolve_Real_Literal             (N, Ctx_Type);
2762
2763             when N_Reference => Resolve_Reference                (N, Ctx_Type);
2764
2765             when N_Selected_Component
2766                              => Resolve_Selected_Component       (N, Ctx_Type);
2767
2768             when N_Slice     => Resolve_Slice                    (N, Ctx_Type);
2769
2770             when N_String_Literal
2771                              => Resolve_String_Literal           (N, Ctx_Type);
2772
2773             when N_Subprogram_Info
2774                              => Resolve_Subprogram_Info          (N, Ctx_Type);
2775
2776             when N_Type_Conversion
2777                              => Resolve_Type_Conversion          (N, Ctx_Type);
2778
2779             when N_Unchecked_Expression =>
2780                Resolve_Unchecked_Expression                      (N, Ctx_Type);
2781
2782             when N_Unchecked_Type_Conversion =>
2783                Resolve_Unchecked_Type_Conversion                 (N, Ctx_Type);
2784          end case;
2785
2786          --  If the subexpression was replaced by a non-subexpression, then
2787          --  all we do is to expand it. The only legitimate case we know of
2788          --  is converting procedure call statement to entry call statements,
2789          --  but there may be others, so we are making this test general.
2790
2791          if Nkind (N) not in N_Subexpr then
2792             Debug_A_Exit ("resolving  ", N, "  (done)");
2793             Expand (N);
2794             return;
2795          end if;
2796
2797          --  AI05-144-2: Check dangerous order dependence within an expression
2798          --  that is not a subexpression. Exclude RHS of an assignment, because
2799          --  both sides may have side-effects and the check must be performed
2800          --  over the statement.
2801
2802          if Nkind (Parent (N)) not in N_Subexpr
2803            and then Nkind (Parent (N)) /= N_Assignment_Statement
2804            and then Nkind (Parent (N)) /= N_Procedure_Call_Statement
2805          then
2806             Check_Order_Dependence;
2807          end if;
2808
2809          --  The expression is definitely NOT overloaded at this point, so
2810          --  we reset the Is_Overloaded flag to avoid any confusion when
2811          --  reanalyzing the node.
2812
2813          Set_Is_Overloaded (N, False);
2814
2815          --  Freeze expression type, entity if it is a name, and designated
2816          --  type if it is an allocator (RM 13.14(10,11,13)).
2817
2818          --  Now that the resolution of the type of the node is complete, and
2819          --  we did not detect an error, we can expand this node. We skip the
2820          --  expand call if we are in a default expression, see section
2821          --  "Handling of Default Expressions" in Sem spec.
2822
2823          Debug_A_Exit ("resolving  ", N, "  (done)");
2824
2825          --  We unconditionally freeze the expression, even if we are in
2826          --  default expression mode (the Freeze_Expression routine tests this
2827          --  flag and only freezes static types if it is set).
2828
2829          Freeze_Expression (N);
2830
2831          --  Now we can do the expansion
2832
2833          Expand (N);
2834       end if;
2835    end Resolve;
2836
2837    -------------
2838    -- Resolve --
2839    -------------
2840
2841    --  Version with check(s) suppressed
2842
2843    procedure Resolve (N : Node_Id; Typ : Entity_Id; Suppress : Check_Id) is
2844    begin
2845       if Suppress = All_Checks then
2846          declare
2847             Svg : constant Suppress_Array := Scope_Suppress;
2848          begin
2849             Scope_Suppress := (others => True);
2850             Resolve (N, Typ);
2851             Scope_Suppress := Svg;
2852          end;
2853
2854       else
2855          declare
2856             Svg : constant Boolean := Scope_Suppress (Suppress);
2857          begin
2858             Scope_Suppress (Suppress) := True;
2859             Resolve (N, Typ);
2860             Scope_Suppress (Suppress) := Svg;
2861          end;
2862       end if;
2863    end Resolve;
2864
2865    -------------
2866    -- Resolve --
2867    -------------
2868
2869    --  Version with implicit type
2870
2871    procedure Resolve (N : Node_Id) is
2872    begin
2873       Resolve (N, Etype (N));
2874    end Resolve;
2875
2876    ---------------------
2877    -- Resolve_Actuals --
2878    ---------------------
2879
2880    procedure Resolve_Actuals (N : Node_Id; Nam : Entity_Id) is
2881       Loc    : constant Source_Ptr := Sloc (N);
2882       A      : Node_Id;
2883       F      : Entity_Id;
2884       A_Typ  : Entity_Id;
2885       F_Typ  : Entity_Id;
2886       Prev   : Node_Id := Empty;
2887       Orig_A : Node_Id;
2888
2889       procedure Check_Argument_Order;
2890       --  Performs a check for the case where the actuals are all simple
2891       --  identifiers that correspond to the formal names, but in the wrong
2892       --  order, which is considered suspicious and cause for a warning.
2893
2894       procedure Check_Prefixed_Call;
2895       --  If the original node is an overloaded call in prefix notation,
2896       --  insert an 'Access or a dereference as needed over the first actual.
2897       --  Try_Object_Operation has already verified that there is a valid
2898       --  interpretation, but the form of the actual can only be determined
2899       --  once the primitive operation is identified.
2900
2901       procedure Insert_Default;
2902       --  If the actual is missing in a call, insert in the actuals list
2903       --  an instance of the default expression. The insertion is always
2904       --  a named association.
2905
2906       function Same_Ancestor (T1, T2 : Entity_Id) return Boolean;
2907       --  Check whether T1 and T2, or their full views, are derived from a
2908       --  common type. Used to enforce the restrictions on array conversions
2909       --  of AI95-00246.
2910
2911       function Static_Concatenation (N : Node_Id) return Boolean;
2912       --  Predicate to determine whether an actual that is a concatenation
2913       --  will be evaluated statically and does not need a transient scope.
2914       --  This must be determined before the actual is resolved and expanded
2915       --  because if needed the transient scope must be introduced earlier.
2916
2917       --------------------------
2918       -- Check_Argument_Order --
2919       --------------------------
2920
2921       procedure Check_Argument_Order is
2922       begin
2923          --  Nothing to do if no parameters, or original node is neither a
2924          --  function call nor a procedure call statement (happens in the
2925          --  operator-transformed-to-function call case), or the call does
2926          --  not come from source, or this warning is off.
2927
2928          if not Warn_On_Parameter_Order
2929            or else No (Parameter_Associations (N))
2930            or else not Nkind_In (Original_Node (N), N_Procedure_Call_Statement,
2931                                                     N_Function_Call)
2932            or else not Comes_From_Source (N)
2933          then
2934             return;
2935          end if;
2936
2937          declare
2938             Nargs : constant Nat := List_Length (Parameter_Associations (N));
2939
2940          begin
2941             --  Nothing to do if only one parameter
2942
2943             if Nargs < 2 then
2944                return;
2945             end if;
2946
2947             --  Here if at least two arguments
2948
2949             declare
2950                Actuals : array (1 .. Nargs) of Node_Id;
2951                Actual  : Node_Id;
2952                Formal  : Node_Id;
2953
2954                Wrong_Order : Boolean := False;
2955                --  Set True if an out of order case is found
2956
2957             begin
2958                --  Collect identifier names of actuals, fail if any actual is
2959                --  not a simple identifier, and record max length of name.
2960
2961                Actual := First (Parameter_Associations (N));
2962                for J in Actuals'Range loop
2963                   if Nkind (Actual) /= N_Identifier then
2964                      return;
2965                   else
2966                      Actuals (J) := Actual;
2967                      Next (Actual);
2968                   end if;
2969                end loop;
2970
2971                --  If we got this far, all actuals are identifiers and the list
2972                --  of their names is stored in the Actuals array.
2973
2974                Formal := First_Formal (Nam);
2975                for J in Actuals'Range loop
2976
2977                   --  If we ran out of formals, that's odd, probably an error
2978                   --  which will be detected elsewhere, but abandon the search.
2979
2980                   if No (Formal) then
2981                      return;
2982                   end if;
2983
2984                   --  If name matches and is in order OK
2985
2986                   if Chars (Formal) = Chars (Actuals (J)) then
2987                      null;
2988
2989                   else
2990                      --  If no match, see if it is elsewhere in list and if so
2991                      --  flag potential wrong order if type is compatible.
2992
2993                      for K in Actuals'Range loop
2994                         if Chars (Formal) = Chars (Actuals (K))
2995                           and then
2996                             Has_Compatible_Type (Actuals (K), Etype (Formal))
2997                         then
2998                            Wrong_Order := True;
2999                            goto Continue;
3000                         end if;
3001                      end loop;
3002
3003                      --  No match
3004
3005                      return;
3006                   end if;
3007
3008                   <<Continue>> Next_Formal (Formal);
3009                end loop;
3010
3011                --  If Formals left over, also probably an error, skip warning
3012
3013                if Present (Formal) then
3014                   return;
3015                end if;
3016
3017                --  Here we give the warning if something was out of order
3018
3019                if Wrong_Order then
3020                   Error_Msg_N
3021                     ("actuals for this call may be in wrong order?", N);
3022                end if;
3023             end;
3024          end;
3025       end Check_Argument_Order;
3026
3027       -------------------------
3028       -- Check_Prefixed_Call --
3029       -------------------------
3030
3031       procedure Check_Prefixed_Call is
3032          Act    : constant Node_Id   := First_Actual (N);
3033          A_Type : constant Entity_Id := Etype (Act);
3034          F_Type : constant Entity_Id := Etype (First_Formal (Nam));
3035          Orig   : constant Node_Id := Original_Node (N);
3036          New_A  : Node_Id;
3037
3038       begin
3039          --  Check whether the call is a prefixed call, with or without
3040          --  additional actuals.
3041
3042          if Nkind (Orig) = N_Selected_Component
3043            or else
3044              (Nkind (Orig) = N_Indexed_Component
3045                and then Nkind (Prefix (Orig)) = N_Selected_Component
3046                and then Is_Entity_Name (Prefix (Prefix (Orig)))
3047                and then Is_Entity_Name (Act)
3048                and then Chars (Act) = Chars (Prefix (Prefix (Orig))))
3049          then
3050             if Is_Access_Type (A_Type)
3051               and then not Is_Access_Type (F_Type)
3052             then
3053                --  Introduce dereference on object in prefix
3054
3055                New_A :=
3056                  Make_Explicit_Dereference (Sloc (Act),
3057                    Prefix => Relocate_Node (Act));
3058                Rewrite (Act, New_A);
3059                Analyze (Act);
3060
3061             elsif Is_Access_Type (F_Type)
3062               and then not Is_Access_Type (A_Type)
3063             then
3064                --  Introduce an implicit 'Access in prefix
3065
3066                if not Is_Aliased_View (Act) then
3067                   Error_Msg_NE
3068                     ("object in prefixed call to& must be aliased"
3069                          & " (RM-2005 4.3.1 (13))",
3070                     Prefix (Act), Nam);
3071                end if;
3072
3073                Rewrite (Act,
3074                  Make_Attribute_Reference (Loc,
3075                    Attribute_Name => Name_Access,
3076                    Prefix         => Relocate_Node (Act)));
3077             end if;
3078
3079             Analyze (Act);
3080          end if;
3081       end Check_Prefixed_Call;
3082
3083       --------------------
3084       -- Insert_Default --
3085       --------------------
3086
3087       procedure Insert_Default is
3088          Actval : Node_Id;
3089          Assoc  : Node_Id;
3090
3091       begin
3092          --  Missing argument in call, nothing to insert
3093
3094          if No (Default_Value (F)) then
3095             return;
3096
3097          else
3098             --  Note that we do a full New_Copy_Tree, so that any associated
3099             --  Itypes are properly copied. This may not be needed any more,
3100             --  but it does no harm as a safety measure! Defaults of a generic
3101             --  formal may be out of bounds of the corresponding actual (see
3102             --  cc1311b) and an additional check may be required.
3103
3104             Actval :=
3105               New_Copy_Tree
3106                 (Default_Value (F),
3107                  New_Scope => Current_Scope,
3108                  New_Sloc  => Loc);
3109
3110             if Is_Concurrent_Type (Scope (Nam))
3111               and then Has_Discriminants (Scope (Nam))
3112             then
3113                Replace_Actual_Discriminants (N, Actval);
3114             end if;
3115
3116             if Is_Overloadable (Nam)
3117               and then Present (Alias (Nam))
3118             then
3119                if Base_Type (Etype (F)) /= Base_Type (Etype (Actval))
3120                  and then not Is_Tagged_Type (Etype (F))
3121                then
3122                   --  If default is a real literal, do not introduce a
3123                   --  conversion whose effect may depend on the run-time
3124                   --  size of universal real.
3125
3126                   if Nkind (Actval) = N_Real_Literal then
3127                      Set_Etype (Actval, Base_Type (Etype (F)));
3128                   else
3129                      Actval := Unchecked_Convert_To (Etype (F), Actval);
3130                   end if;
3131                end if;
3132
3133                if Is_Scalar_Type (Etype (F)) then
3134                   Enable_Range_Check (Actval);
3135                end if;
3136
3137                Set_Parent (Actval, N);
3138
3139                --  Resolve aggregates with their base type, to avoid scope
3140                --  anomalies: the subtype was first built in the subprogram
3141                --  declaration, and the current call may be nested.
3142
3143                if Nkind (Actval) = N_Aggregate then
3144                   Analyze_And_Resolve (Actval, Etype (F));
3145                else
3146                   Analyze_And_Resolve (Actval, Etype (Actval));
3147                end if;
3148
3149             else
3150                Set_Parent (Actval, N);
3151
3152                --  See note above concerning aggregates
3153
3154                if Nkind (Actval) = N_Aggregate
3155                  and then Has_Discriminants (Etype (Actval))
3156                then
3157                   Analyze_And_Resolve (Actval, Base_Type (Etype (Actval)));
3158
3159                --  Resolve entities with their own type, which may differ from
3160                --  the type of a reference in a generic context (the view
3161                --  swapping mechanism did not anticipate the re-analysis of
3162                --  default values in calls).
3163
3164                elsif Is_Entity_Name (Actval) then
3165                   Analyze_And_Resolve (Actval, Etype (Entity (Actval)));
3166
3167                else
3168                   Analyze_And_Resolve (Actval, Etype (Actval));
3169                end if;
3170             end if;
3171
3172             --  If default is a tag indeterminate function call, propagate tag
3173             --  to obtain proper dispatching.
3174
3175             if Is_Controlling_Formal (F)
3176               and then Nkind (Default_Value (F)) = N_Function_Call
3177             then
3178                Set_Is_Controlling_Actual (Actval);
3179             end if;
3180
3181          end if;
3182
3183          --  If the default expression raises constraint error, then just
3184          --  silently replace it with an N_Raise_Constraint_Error node, since
3185          --  we already gave the warning on the subprogram spec. If node is
3186          --  already a Raise_Constraint_Error leave as is, to prevent loops in
3187          --  the warnings removal machinery.
3188
3189          if Raises_Constraint_Error (Actval)
3190            and then Nkind (Actval) /= N_Raise_Constraint_Error
3191          then
3192             Rewrite (Actval,
3193               Make_Raise_Constraint_Error (Loc,
3194                 Reason => CE_Range_Check_Failed));
3195             Set_Raises_Constraint_Error (Actval);
3196             Set_Etype (Actval, Etype (F));
3197          end if;
3198
3199          Assoc :=
3200            Make_Parameter_Association (Loc,
3201              Explicit_Actual_Parameter => Actval,
3202              Selector_Name => Make_Identifier (Loc, Chars (F)));
3203
3204          --  Case of insertion is first named actual
3205
3206          if No (Prev) or else
3207             Nkind (Parent (Prev)) /= N_Parameter_Association
3208          then
3209             Set_Next_Named_Actual (Assoc, First_Named_Actual (N));
3210             Set_First_Named_Actual (N, Actval);
3211
3212             if No (Prev) then
3213                if No (Parameter_Associations (N)) then
3214                   Set_Parameter_Associations (N, New_List (Assoc));
3215                else
3216                   Append (Assoc, Parameter_Associations (N));
3217                end if;
3218
3219             else
3220                Insert_After (Prev, Assoc);
3221             end if;
3222
3223          --  Case of insertion is not first named actual
3224
3225          else
3226             Set_Next_Named_Actual
3227               (Assoc, Next_Named_Actual (Parent (Prev)));
3228             Set_Next_Named_Actual (Parent (Prev), Actval);
3229             Append (Assoc, Parameter_Associations (N));
3230          end if;
3231
3232          Mark_Rewrite_Insertion (Assoc);
3233          Mark_Rewrite_Insertion (Actval);
3234
3235          Prev := Actval;
3236       end Insert_Default;
3237
3238       -------------------
3239       -- Same_Ancestor --
3240       -------------------
3241
3242       function Same_Ancestor (T1, T2 : Entity_Id) return Boolean is
3243          FT1 : Entity_Id := T1;
3244          FT2 : Entity_Id := T2;
3245
3246       begin
3247          if Is_Private_Type (T1)
3248            and then Present (Full_View (T1))
3249          then
3250             FT1 := Full_View (T1);
3251          end if;
3252
3253          if Is_Private_Type (T2)
3254            and then Present (Full_View (T2))
3255          then
3256             FT2 := Full_View (T2);
3257          end if;
3258
3259          return Root_Type (Base_Type (FT1)) = Root_Type (Base_Type (FT2));
3260       end Same_Ancestor;
3261
3262       --------------------------
3263       -- Static_Concatenation --
3264       --------------------------
3265
3266       function Static_Concatenation (N : Node_Id) return Boolean is
3267       begin
3268          case Nkind (N) is
3269             when N_String_Literal =>
3270                return True;
3271
3272             when N_Op_Concat =>
3273
3274                --  Concatenation is static when both operands are static and
3275                --  the concatenation operator is a predefined one.
3276
3277                return Scope (Entity (N)) = Standard_Standard
3278                         and then
3279                       Static_Concatenation (Left_Opnd (N))
3280                         and then
3281                       Static_Concatenation (Right_Opnd (N));
3282
3283             when others =>
3284                if Is_Entity_Name (N) then
3285                   declare
3286                      Ent : constant Entity_Id := Entity (N);
3287                   begin
3288                      return Ekind (Ent) = E_Constant
3289                               and then Present (Constant_Value (Ent))
3290                               and then
3291                                 Is_Static_Expression (Constant_Value (Ent));
3292                   end;
3293
3294                else
3295                   return False;
3296                end if;
3297          end case;
3298       end Static_Concatenation;
3299
3300    --  Start of processing for Resolve_Actuals
3301
3302    begin
3303       Check_Argument_Order;
3304
3305       if Present (First_Actual (N)) then
3306          Check_Prefixed_Call;
3307       end if;
3308
3309       A := First_Actual (N);
3310       F := First_Formal (Nam);
3311       while Present (F) loop
3312          if No (A) and then Needs_No_Actuals (Nam) then
3313             null;
3314
3315          --  If we have an error in any actual or formal, indicated by a type
3316          --  of Any_Type, then abandon resolution attempt, and set result type
3317          --  to Any_Type.
3318
3319          elsif (Present (A) and then Etype (A) = Any_Type)
3320            or else Etype (F) = Any_Type
3321          then
3322             Set_Etype (N, Any_Type);
3323             return;
3324          end if;
3325
3326          --  Case where actual is present
3327
3328          --  If the actual is an entity, generate a reference to it now. We
3329          --  do this before the actual is resolved, because a formal of some
3330          --  protected subprogram, or a task discriminant, will be rewritten
3331          --  during expansion, and the source entity reference may be lost.
3332
3333          if Present (A)
3334            and then Is_Entity_Name (A)
3335            and then Comes_From_Source (N)
3336          then
3337             Orig_A := Entity (A);
3338
3339             if Present (Orig_A) then
3340                if Is_Formal (Orig_A)
3341                  and then Ekind (F) /= E_In_Parameter
3342                then
3343                   Generate_Reference (Orig_A, A, 'm');
3344
3345                elsif not Is_Overloaded (A) then
3346                   Generate_Reference (Orig_A, A);
3347                end if;
3348             end if;
3349          end if;
3350
3351          if Present (A)
3352            and then (Nkind (Parent (A)) /= N_Parameter_Association
3353                       or else Chars (Selector_Name (Parent (A))) = Chars (F))
3354          then
3355             --  If style checking mode on, check match of formal name
3356
3357             if Style_Check then
3358                if Nkind (Parent (A)) = N_Parameter_Association then
3359                   Check_Identifier (Selector_Name (Parent (A)), F);
3360                end if;
3361             end if;
3362
3363             --  If the formal is Out or In_Out, do not resolve and expand the
3364             --  conversion, because it is subsequently expanded into explicit
3365             --  temporaries and assignments. However, the object of the
3366             --  conversion can be resolved. An exception is the case of tagged
3367             --  type conversion with a class-wide actual. In that case we want
3368             --  the tag check to occur and no temporary will be needed (no
3369             --  representation change can occur) and the parameter is passed by
3370             --  reference, so we go ahead and resolve the type conversion.
3371             --  Another exception is the case of reference to component or
3372             --  subcomponent of a bit-packed array, in which case we want to
3373             --  defer expansion to the point the in and out assignments are
3374             --  performed.
3375
3376             if Ekind (F) /= E_In_Parameter
3377               and then Nkind (A) = N_Type_Conversion
3378               and then not Is_Class_Wide_Type (Etype (Expression (A)))
3379             then
3380                if Ekind (F) = E_In_Out_Parameter
3381                  and then Is_Array_Type (Etype (F))
3382                then
3383                   --  In a view conversion, the conversion must be legal in
3384                   --  both directions, and thus both component types must be
3385                   --  aliased, or neither (4.6 (8)).
3386
3387                   --  The extra rule in 4.6 (24.9.2) seems unduly restrictive:
3388                   --  the privacy requirement should not apply to generic
3389                   --  types, and should be checked in an instance. ARG query
3390                   --  is in order ???
3391
3392                   if Has_Aliased_Components (Etype (Expression (A))) /=
3393                      Has_Aliased_Components (Etype (F))
3394                   then
3395                      Error_Msg_N
3396                        ("both component types in a view conversion must be"
3397                          & " aliased, or neither", A);
3398
3399                   --  Comment here??? what set of cases???
3400
3401                   elsif
3402                      not Same_Ancestor (Etype (F), Etype (Expression (A)))
3403                   then
3404                      --  Check view conv between unrelated by ref array types
3405
3406                      if Is_By_Reference_Type (Etype (F))
3407                         or else Is_By_Reference_Type (Etype (Expression (A)))
3408                      then
3409                         Error_Msg_N
3410                           ("view conversion between unrelated by reference " &
3411                            "array types not allowed (\'A'I-00246)", A);
3412
3413                      --  In Ada 2005 mode, check view conversion component
3414                      --  type cannot be private, tagged, or volatile. Note
3415                      --  that we only apply this to source conversions. The
3416                      --  generated code can contain conversions which are
3417                      --  not subject to this test, and we cannot extract the
3418                      --  component type in such cases since it is not present.
3419
3420                      elsif Comes_From_Source (A)
3421                        and then Ada_Version >= Ada_2005
3422                      then
3423                         declare
3424                            Comp_Type : constant Entity_Id :=
3425                                          Component_Type
3426                                            (Etype (Expression (A)));
3427                         begin
3428                            if (Is_Private_Type (Comp_Type)
3429                                  and then not Is_Generic_Type (Comp_Type))
3430                              or else Is_Tagged_Type (Comp_Type)
3431                              or else Is_Volatile (Comp_Type)
3432                            then
3433                               Error_Msg_N
3434                                 ("component type of a view conversion cannot"
3435                                    & " be private, tagged, or volatile"
3436                                    & " (RM 4.6 (24))",
3437                                    Expression (A));
3438                            end if;
3439                         end;
3440                      end if;
3441                   end if;
3442                end if;
3443
3444                --  Resolve expression if conversion is all OK
3445
3446                if (Conversion_OK (A)
3447                     or else Valid_Conversion (A, Etype (A), Expression (A)))
3448                  and then not Is_Ref_To_Bit_Packed_Array (Expression (A))
3449                then
3450                   Resolve (Expression (A));
3451                end if;
3452
3453             --  If the actual is a function call that returns a limited
3454             --  unconstrained object that needs finalization, create a
3455             --  transient scope for it, so that it can receive the proper
3456             --  finalization list.
3457
3458             elsif Nkind (A) = N_Function_Call
3459               and then Is_Limited_Record (Etype (F))
3460               and then not Is_Constrained (Etype (F))
3461               and then Expander_Active
3462               and then (Is_Controlled (Etype (F)) or else Has_Task (Etype (F)))
3463             then
3464                Establish_Transient_Scope (A, False);
3465
3466             --  A small optimization: if one of the actuals is a concatenation
3467             --  create a block around a procedure call to recover stack space.
3468             --  This alleviates stack usage when several procedure calls in
3469             --  the same statement list use concatenation. We do not perform
3470             --  this wrapping for code statements, where the argument is a
3471             --  static string, and we want to preserve warnings involving
3472             --  sequences of such statements.
3473
3474             elsif Nkind (A) = N_Op_Concat
3475               and then Nkind (N) = N_Procedure_Call_Statement
3476               and then Expander_Active
3477               and then
3478                 not (Is_Intrinsic_Subprogram (Nam)
3479                       and then Chars (Nam) = Name_Asm)
3480               and then not Static_Concatenation (A)
3481             then
3482                Establish_Transient_Scope (A, False);
3483                Resolve (A, Etype (F));
3484
3485             else
3486                if Nkind (A) = N_Type_Conversion
3487                  and then Is_Array_Type (Etype (F))
3488                  and then not Same_Ancestor (Etype (F), Etype (Expression (A)))
3489                  and then
3490                   (Is_Limited_Type (Etype (F))
3491                      or else Is_Limited_Type (Etype (Expression (A))))
3492                then
3493                   Error_Msg_N
3494                     ("conversion between unrelated limited array types " &
3495                      "not allowed (\A\I-00246)", A);
3496
3497                   if Is_Limited_Type (Etype (F)) then
3498                      Explain_Limited_Type (Etype (F), A);
3499                   end if;
3500
3501                   if Is_Limited_Type (Etype (Expression (A))) then
3502                      Explain_Limited_Type (Etype (Expression (A)), A);
3503                   end if;
3504                end if;
3505
3506                --  (Ada 2005: AI-251): If the actual is an allocator whose
3507                --  directly designated type is a class-wide interface, we build
3508                --  an anonymous access type to use it as the type of the
3509                --  allocator. Later, when the subprogram call is expanded, if
3510                --  the interface has a secondary dispatch table the expander
3511                --  will add a type conversion to force the correct displacement
3512                --  of the pointer.
3513
3514                if Nkind (A) = N_Allocator then
3515                   declare
3516                      DDT : constant Entity_Id :=
3517                              Directly_Designated_Type (Base_Type (Etype (F)));
3518
3519                      New_Itype : Entity_Id;
3520
3521                   begin
3522                      if Is_Class_Wide_Type (DDT)
3523                        and then Is_Interface (DDT)
3524                      then
3525                         New_Itype := Create_Itype (E_Anonymous_Access_Type, A);
3526                         Set_Etype (New_Itype, Etype (A));
3527                         Set_Directly_Designated_Type (New_Itype,
3528                           Directly_Designated_Type (Etype (A)));
3529                         Set_Etype (A, New_Itype);
3530                      end if;
3531
3532                      --  Ada 2005, AI-162:If the actual is an allocator, the
3533                      --  innermost enclosing statement is the master of the
3534                      --  created object. This needs to be done with expansion
3535                      --  enabled only, otherwise the transient scope will not
3536                      --  be removed in the expansion of the wrapped construct.
3537
3538                      if (Is_Controlled (DDT) or else Has_Task (DDT))
3539                        and then Expander_Active
3540                      then
3541                         Establish_Transient_Scope (A, False);
3542                      end if;
3543                   end;
3544                end if;
3545
3546                --  (Ada 2005): The call may be to a primitive operation of
3547                --   a tagged synchronized type, declared outside of the type.
3548                --   In this case the controlling actual must be converted to
3549                --   its corresponding record type, which is the formal type.
3550                --   The actual may be a subtype, either because of a constraint
3551                --   or because it is a generic actual, so use base type to
3552                --   locate concurrent type.
3553
3554                F_Typ := Base_Type (Etype (F));
3555
3556                if Is_Tagged_Type (F_Typ)
3557                  and then (Is_Concurrent_Type (F_Typ)
3558                              or else Is_Concurrent_Record_Type (F_Typ))
3559                then
3560                   --  If the actual is overloaded, look for an interpretation
3561                   --  that has a synchronized type.
3562
3563                   if not Is_Overloaded (A) then
3564                      A_Typ := Base_Type (Etype (A));
3565
3566                   else
3567                      declare
3568                         Index : Interp_Index;
3569                         It    : Interp;
3570
3571                      begin
3572                         Get_First_Interp (A, Index, It);
3573                         while Present (It.Typ) loop
3574                            if Is_Concurrent_Type (It.Typ)
3575                              or else Is_Concurrent_Record_Type (It.Typ)
3576                            then
3577                               A_Typ := Base_Type (It.Typ);
3578                               exit;
3579                            end if;
3580
3581                            Get_Next_Interp (Index, It);
3582                         end loop;
3583                      end;
3584                   end if;
3585
3586                   declare
3587                      Full_A_Typ : Entity_Id;
3588
3589                   begin
3590                      if Present (Full_View (A_Typ)) then
3591                         Full_A_Typ := Base_Type (Full_View (A_Typ));
3592                      else
3593                         Full_A_Typ := A_Typ;
3594                      end if;
3595
3596                      --  Tagged synchronized type (case 1): the actual is a
3597                      --  concurrent type.
3598
3599                      if Is_Concurrent_Type (A_Typ)
3600                        and then Corresponding_Record_Type (A_Typ) = F_Typ
3601                      then
3602                         Rewrite (A,
3603                           Unchecked_Convert_To
3604                             (Corresponding_Record_Type (A_Typ), A));
3605                         Resolve (A, Etype (F));
3606
3607                      --  Tagged synchronized type (case 2): the formal is a
3608                      --  concurrent type.
3609
3610                      elsif Ekind (Full_A_Typ) = E_Record_Type
3611                        and then Present
3612                                (Corresponding_Concurrent_Type (Full_A_Typ))
3613                        and then Is_Concurrent_Type (F_Typ)
3614                        and then Present (Corresponding_Record_Type (F_Typ))
3615                        and then Full_A_Typ = Corresponding_Record_Type (F_Typ)
3616                      then
3617                         Resolve (A, Corresponding_Record_Type (F_Typ));
3618
3619                      --  Common case
3620
3621                      else
3622                         Resolve (A, Etype (F));
3623                      end if;
3624                   end;
3625                else
3626
3627                   --  not a synchronized operation.
3628
3629                   Resolve (A, Etype (F));
3630                end if;
3631             end if;
3632
3633             A_Typ := Etype (A);
3634             F_Typ := Etype (F);
3635
3636             if Comes_From_Source (Original_Node (N))
3637               and then Nkind_In (Original_Node (N), N_Function_Call,
3638                                                     N_Procedure_Call_Statement)
3639             then
3640                --  In formal mode, check that actual parameters matching
3641                --  formals of tagged types are objects (or ancestor type
3642                --  conversions of objects), not general expressions.
3643
3644                if Is_Actual_Tagged_Parameter (A) then
3645                   if Is_SPARK_Object_Reference (A) then
3646                      null;
3647
3648                   elsif Nkind (A) = N_Type_Conversion then
3649                      declare
3650                         Operand     : constant Node_Id   := Expression (A);
3651                         Operand_Typ : constant Entity_Id := Etype (Operand);
3652                         Target_Typ  : constant Entity_Id := A_Typ;
3653
3654                      begin
3655                         if not Is_SPARK_Object_Reference (Operand) then
3656                            Check_SPARK_Restriction
3657                              ("object required", Operand);
3658
3659                         --  In formal mode, the only view conversions are those
3660                         --  involving ancestor conversion of an extended type.
3661
3662                         elsif not
3663                           (Is_Tagged_Type (Target_Typ)
3664                            and then not Is_Class_Wide_Type (Target_Typ)
3665                            and then Is_Tagged_Type (Operand_Typ)
3666                            and then not Is_Class_Wide_Type (Operand_Typ)
3667                            and then Is_Ancestor (Target_Typ, Operand_Typ))
3668                         then
3669                            if Ekind_In
3670                              (F, E_Out_Parameter, E_In_Out_Parameter)
3671                            then
3672                               Check_SPARK_Restriction
3673                                 ("ancestor conversion is the only permitted "
3674                                  & "view conversion", A);
3675                            else
3676                               Check_SPARK_Restriction
3677                                 ("ancestor conversion required", A);
3678                            end if;
3679
3680                         else
3681                            null;
3682                         end if;
3683                      end;
3684
3685                   else
3686                      Check_SPARK_Restriction ("object required", A);
3687                   end if;
3688
3689                --  In formal mode, the only view conversions are those
3690                --  involving ancestor conversion of an extended type.
3691
3692                elsif Nkind (A) = N_Type_Conversion
3693                  and then Ekind_In (F, E_Out_Parameter, E_In_Out_Parameter)
3694                then
3695                   Check_SPARK_Restriction
3696                     ("ancestor conversion is the only permitted view "
3697                      & "conversion", A);
3698                end if;
3699             end if;
3700
3701             --  Save actual for subsequent check on order dependence, and
3702             --  indicate whether actual is modifiable. For AI05-0144-2.
3703
3704             Save_Actual (A, Ekind (F) /= E_In_Parameter);
3705
3706             --  For mode IN, if actual is an entity, and the type of the formal
3707             --  has warnings suppressed, then we reset Never_Set_In_Source for
3708             --  the calling entity. The reason for this is to catch cases like
3709             --  GNAT.Spitbol.Patterns.Vstring_Var where the called subprogram
3710             --  uses trickery to modify an IN parameter.
3711
3712             if Ekind (F) = E_In_Parameter
3713               and then Is_Entity_Name (A)
3714               and then Present (Entity (A))
3715               and then Ekind (Entity (A)) = E_Variable
3716               and then Has_Warnings_Off (F_Typ)
3717             then
3718                Set_Never_Set_In_Source (Entity (A), False);
3719             end if;
3720
3721             --  Perform error checks for IN and IN OUT parameters
3722
3723             if Ekind (F) /= E_Out_Parameter then
3724
3725                --  Check unset reference. For scalar parameters, it is clearly
3726                --  wrong to pass an uninitialized value as either an IN or
3727                --  IN-OUT parameter. For composites, it is also clearly an
3728                --  error to pass a completely uninitialized value as an IN
3729                --  parameter, but the case of IN OUT is trickier. We prefer
3730                --  not to give a warning here. For example, suppose there is
3731                --  a routine that sets some component of a record to False.
3732                --  It is perfectly reasonable to make this IN-OUT and allow
3733                --  either initialized or uninitialized records to be passed
3734                --  in this case.
3735
3736                --  For partially initialized composite values, we also avoid
3737                --  warnings, since it is quite likely that we are passing a
3738                --  partially initialized value and only the initialized fields
3739                --  will in fact be read in the subprogram.
3740
3741                if Is_Scalar_Type (A_Typ)
3742                  or else (Ekind (F) = E_In_Parameter
3743                            and then not Is_Partially_Initialized_Type (A_Typ))
3744                then
3745                   Check_Unset_Reference (A);
3746                end if;
3747
3748                --  In Ada 83 we cannot pass an OUT parameter as an IN or IN OUT
3749                --  actual to a nested call, since this is case of reading an
3750                --  out parameter, which is not allowed.
3751
3752                if Ada_Version = Ada_83
3753                  and then Is_Entity_Name (A)
3754                  and then Ekind (Entity (A)) = E_Out_Parameter
3755                then
3756                   Error_Msg_N ("(Ada 83) illegal reading of out parameter", A);
3757                end if;
3758             end if;
3759
3760             --  Case of OUT or IN OUT parameter
3761
3762             if Ekind (F) /= E_In_Parameter then
3763
3764                --  For an Out parameter, check for useless assignment. Note
3765                --  that we can't set Last_Assignment this early, because we may
3766                --  kill current values in Resolve_Call, and that call would
3767                --  clobber the Last_Assignment field.
3768
3769                --  Note: call Warn_On_Useless_Assignment before doing the check
3770                --  below for Is_OK_Variable_For_Out_Formal so that the setting
3771                --  of Referenced_As_LHS/Referenced_As_Out_Formal properly
3772                --  reflects the last assignment, not this one!
3773
3774                if Ekind (F) = E_Out_Parameter then
3775                   if Warn_On_Modified_As_Out_Parameter (F)
3776                     and then Is_Entity_Name (A)
3777                     and then Present (Entity (A))
3778                     and then Comes_From_Source (N)
3779                   then
3780                      Warn_On_Useless_Assignment (Entity (A), A);
3781                   end if;
3782                end if;
3783
3784                --  Validate the form of the actual. Note that the call to
3785                --  Is_OK_Variable_For_Out_Formal generates the required
3786                --  reference in this case.
3787
3788                --  A call to an initialization procedure for an aggregate
3789                --  component may initialize a nested component of a constant
3790                --  designated object. In this context the object is variable.
3791
3792                if not Is_OK_Variable_For_Out_Formal (A)
3793                  and then not Is_Init_Proc (Nam)
3794                then
3795                   Error_Msg_NE ("actual for& must be a variable", A, F);
3796                end if;
3797
3798                --  What's the following about???
3799
3800                if Is_Entity_Name (A) then
3801                   Kill_Checks (Entity (A));
3802                else
3803                   Kill_All_Checks;
3804                end if;
3805             end if;
3806
3807             if Etype (A) = Any_Type then
3808                Set_Etype (N, Any_Type);
3809                return;
3810             end if;
3811
3812             --  Apply appropriate range checks for in, out, and in-out
3813             --  parameters. Out and in-out parameters also need a separate
3814             --  check, if there is a type conversion, to make sure the return
3815             --  value meets the constraints of the variable before the
3816             --  conversion.
3817
3818             --  Gigi looks at the check flag and uses the appropriate types.
3819             --  For now since one flag is used there is an optimization which
3820             --  might not be done in the In Out case since Gigi does not do
3821             --  any analysis. More thought required about this ???
3822
3823             if Ekind_In (F, E_In_Parameter, E_In_Out_Parameter) then
3824
3825                --  Apply predicate checks, unless this is a call to the
3826                --  predicate check function itself, which would cause an
3827                --  infinite recursion.
3828
3829                if not (Ekind (Nam) = E_Function
3830                         and then Has_Predicates (Nam))
3831                then
3832                   Apply_Predicate_Check (A, F_Typ);
3833                end if;
3834
3835                --  Apply required constraint checks
3836
3837                if Is_Scalar_Type (Etype (A)) then
3838                   Apply_Scalar_Range_Check (A, F_Typ);
3839
3840                elsif Is_Array_Type (Etype (A)) then
3841                   Apply_Length_Check (A, F_Typ);
3842
3843                elsif Is_Record_Type (F_Typ)
3844                  and then Has_Discriminants (F_Typ)
3845                  and then Is_Constrained (F_Typ)
3846                  and then (not Is_Derived_Type (F_Typ)
3847                             or else Comes_From_Source (Nam))
3848                then
3849                   Apply_Discriminant_Check (A, F_Typ);
3850
3851                elsif Is_Access_Type (F_Typ)
3852                  and then Is_Array_Type (Designated_Type (F_Typ))
3853                  and then Is_Constrained (Designated_Type (F_Typ))
3854                then
3855                   Apply_Length_Check (A, F_Typ);
3856
3857                elsif Is_Access_Type (F_Typ)
3858                  and then Has_Discriminants (Designated_Type (F_Typ))
3859                  and then Is_Constrained (Designated_Type (F_Typ))
3860                then
3861                   Apply_Discriminant_Check (A, F_Typ);
3862
3863                else
3864                   Apply_Range_Check (A, F_Typ);
3865                end if;
3866
3867                --  Ada 2005 (AI-231): Note that the controlling parameter case
3868                --  already existed in Ada 95, which is partially checked
3869                --  elsewhere (see Checks), and we don't want the warning
3870                --  message to differ.
3871
3872                if Is_Access_Type (F_Typ)
3873                  and then Can_Never_Be_Null (F_Typ)
3874                  and then Known_Null (A)
3875                then
3876                   if Is_Controlling_Formal (F) then
3877                      Apply_Compile_Time_Constraint_Error
3878                        (N      => A,
3879                         Msg    => "null value not allowed here?",
3880                         Reason => CE_Access_Check_Failed);
3881
3882                   elsif Ada_Version >= Ada_2005 then
3883                      Apply_Compile_Time_Constraint_Error
3884                        (N      => A,
3885                         Msg    => "(Ada 2005) null not allowed in "
3886                                   & "null-excluding formal?",
3887                         Reason => CE_Null_Not_Allowed);
3888                   end if;
3889                end if;
3890             end if;
3891
3892             if Ekind_In (F, E_Out_Parameter, E_In_Out_Parameter) then
3893                if Nkind (A) = N_Type_Conversion then
3894                   if Is_Scalar_Type (A_Typ) then
3895                      Apply_Scalar_Range_Check
3896                        (Expression (A), Etype (Expression (A)), A_Typ);
3897                   else
3898                      Apply_Range_Check
3899                        (Expression (A), Etype (Expression (A)), A_Typ);
3900                   end if;
3901
3902                else
3903                   if Is_Scalar_Type (F_Typ) then
3904                      Apply_Scalar_Range_Check (A, A_Typ, F_Typ);
3905                   elsif Is_Array_Type (F_Typ)
3906                     and then Ekind (F) = E_Out_Parameter
3907                   then
3908                      Apply_Length_Check (A, F_Typ);
3909                   else
3910                      Apply_Range_Check (A, A_Typ, F_Typ);
3911                   end if;
3912                end if;
3913             end if;
3914
3915             --  An actual associated with an access parameter is implicitly
3916             --  converted to the anonymous access type of the formal and must
3917             --  satisfy the legality checks for access conversions.
3918
3919             if Ekind (F_Typ) = E_Anonymous_Access_Type then
3920                if not Valid_Conversion (A, F_Typ, A) then
3921                   Error_Msg_N
3922                     ("invalid implicit conversion for access parameter", A);
3923                end if;
3924             end if;
3925
3926             --  Check bad case of atomic/volatile argument (RM C.6(12))
3927
3928             if Is_By_Reference_Type (Etype (F))
3929               and then Comes_From_Source (N)
3930             then
3931                if Is_Atomic_Object (A)
3932                  and then not Is_Atomic (Etype (F))
3933                then
3934                   Error_Msg_N
3935                     ("cannot pass atomic argument to non-atomic formal",
3936                      N);
3937
3938                elsif Is_Volatile_Object (A)
3939                  and then not Is_Volatile (Etype (F))
3940                then
3941                   Error_Msg_N
3942                     ("cannot pass volatile argument to non-volatile formal",
3943                      N);
3944                end if;
3945             end if;
3946
3947             --  Check that subprograms don't have improper controlling
3948             --  arguments (RM 3.9.2 (9)).
3949
3950             --  A primitive operation may have an access parameter of an
3951             --  incomplete tagged type, but a dispatching call is illegal
3952             --  if the type is still incomplete.
3953
3954             if Is_Controlling_Formal (F) then
3955                Set_Is_Controlling_Actual (A);
3956
3957                if Ekind (Etype (F)) = E_Anonymous_Access_Type then
3958                   declare
3959                      Desig : constant Entity_Id := Designated_Type (Etype (F));
3960                   begin
3961                      if Ekind (Desig) = E_Incomplete_Type
3962                        and then No (Full_View (Desig))
3963                        and then No (Non_Limited_View (Desig))
3964                      then
3965                         Error_Msg_NE
3966                           ("premature use of incomplete type& " &
3967                            "in dispatching call", A, Desig);
3968                      end if;
3969                   end;
3970                end if;
3971
3972             elsif Nkind (A) = N_Explicit_Dereference then
3973                Validate_Remote_Access_To_Class_Wide_Type (A);
3974             end if;
3975
3976             if (Is_Class_Wide_Type (A_Typ) or else Is_Dynamically_Tagged (A))
3977               and then not Is_Class_Wide_Type (F_Typ)
3978               and then not Is_Controlling_Formal (F)
3979             then
3980                Error_Msg_N ("class-wide argument not allowed here!", A);
3981
3982                if Is_Subprogram (Nam)
3983                  and then Comes_From_Source (Nam)
3984                then
3985                   Error_Msg_Node_2 := F_Typ;
3986                   Error_Msg_NE
3987                     ("& is not a dispatching operation of &!", A, Nam);
3988                end if;
3989
3990             elsif Is_Access_Type (A_Typ)
3991               and then Is_Access_Type (F_Typ)
3992               and then Ekind (F_Typ) /= E_Access_Subprogram_Type
3993               and then Ekind (F_Typ) /= E_Anonymous_Access_Subprogram_Type
3994               and then (Is_Class_Wide_Type (Designated_Type (A_Typ))
3995                          or else (Nkind (A) = N_Attribute_Reference
3996                                    and then
3997                                      Is_Class_Wide_Type (Etype (Prefix (A)))))
3998               and then not Is_Class_Wide_Type (Designated_Type (F_Typ))
3999               and then not Is_Controlling_Formal (F)
4000
4001               --  Disable these checks for call to imported C++ subprograms
4002
4003               and then not
4004                 (Is_Entity_Name (Name (N))
4005                   and then Is_Imported (Entity (Name (N)))
4006                   and then Convention (Entity (Name (N))) = Convention_CPP)
4007             then
4008                Error_Msg_N
4009                  ("access to class-wide argument not allowed here!", A);
4010
4011                if Is_Subprogram (Nam)
4012                  and then Comes_From_Source (Nam)
4013                then
4014                   Error_Msg_Node_2 := Designated_Type (F_Typ);
4015                   Error_Msg_NE
4016                     ("& is not a dispatching operation of &!", A, Nam);
4017                end if;
4018             end if;
4019
4020             Eval_Actual (A);
4021
4022             --  If it is a named association, treat the selector_name as a
4023             --  proper identifier, and mark the corresponding entity. Ignore
4024             --  this reference in ALFA mode, as it refers to an entity not in
4025             --  scope at the point of reference, so the reference should be
4026             --  ignored for computing effects of subprograms.
4027
4028             if Nkind (Parent (A)) = N_Parameter_Association
4029               and then not ALFA_Mode
4030             then
4031                Set_Entity (Selector_Name (Parent (A)), F);
4032                Generate_Reference (F, Selector_Name (Parent (A)));
4033                Set_Etype (Selector_Name (Parent (A)), F_Typ);
4034                Generate_Reference (F_Typ, N, ' ');
4035             end if;
4036
4037             Prev := A;
4038
4039             if Ekind (F) /= E_Out_Parameter then
4040                Check_Unset_Reference (A);
4041             end if;
4042
4043             Next_Actual (A);
4044
4045          --  Case where actual is not present
4046
4047          else
4048             Insert_Default;
4049          end if;
4050
4051          Next_Formal (F);
4052       end loop;
4053    end Resolve_Actuals;
4054
4055    -----------------------
4056    -- Resolve_Allocator --
4057    -----------------------
4058
4059    procedure Resolve_Allocator (N : Node_Id; Typ : Entity_Id) is
4060       E        : constant Node_Id := Expression (N);
4061       Subtyp   : Entity_Id;
4062       Discrim  : Entity_Id;
4063       Constr   : Node_Id;
4064       Aggr     : Node_Id;
4065       Assoc    : Node_Id := Empty;
4066       Disc_Exp : Node_Id;
4067
4068       procedure Check_Allocator_Discrim_Accessibility
4069         (Disc_Exp  : Node_Id;
4070          Alloc_Typ : Entity_Id);
4071       --  Check that accessibility level associated with an access discriminant
4072       --  initialized in an allocator by the expression Disc_Exp is not deeper
4073       --  than the level of the allocator type Alloc_Typ. An error message is
4074       --  issued if this condition is violated. Specialized checks are done for
4075       --  the cases of a constraint expression which is an access attribute or
4076       --  an access discriminant.
4077
4078       function In_Dispatching_Context return Boolean;
4079       --  If the allocator is an actual in a call, it is allowed to be class-
4080       --  wide when the context is not because it is a controlling actual.
4081
4082       -------------------------------------------
4083       -- Check_Allocator_Discrim_Accessibility --
4084       -------------------------------------------
4085
4086       procedure Check_Allocator_Discrim_Accessibility
4087         (Disc_Exp  : Node_Id;
4088          Alloc_Typ : Entity_Id)
4089       is
4090       begin
4091          if Type_Access_Level (Etype (Disc_Exp)) >
4092             Type_Access_Level (Alloc_Typ)
4093          then
4094             Error_Msg_N
4095               ("operand type has deeper level than allocator type", Disc_Exp);
4096
4097          --  When the expression is an Access attribute the level of the prefix
4098          --  object must not be deeper than that of the allocator's type.
4099
4100          elsif Nkind (Disc_Exp) = N_Attribute_Reference
4101            and then Get_Attribute_Id (Attribute_Name (Disc_Exp))
4102                       = Attribute_Access
4103            and then Object_Access_Level (Prefix (Disc_Exp))
4104                       > Type_Access_Level (Alloc_Typ)
4105          then
4106             Error_Msg_N
4107               ("prefix of attribute has deeper level than allocator type",
4108                Disc_Exp);
4109
4110          --  When the expression is an access discriminant the check is against
4111          --  the level of the prefix object.
4112
4113          elsif Ekind (Etype (Disc_Exp)) = E_Anonymous_Access_Type
4114            and then Nkind (Disc_Exp) = N_Selected_Component
4115            and then Object_Access_Level (Prefix (Disc_Exp))
4116                       > Type_Access_Level (Alloc_Typ)
4117          then
4118             Error_Msg_N
4119               ("access discriminant has deeper level than allocator type",
4120                Disc_Exp);
4121
4122          --  All other cases are legal
4123
4124          else
4125             null;
4126          end if;
4127       end Check_Allocator_Discrim_Accessibility;
4128
4129       ----------------------------
4130       -- In_Dispatching_Context --
4131       ----------------------------
4132
4133       function In_Dispatching_Context return Boolean is
4134          Par : constant Node_Id := Parent (N);
4135
4136       begin
4137          return
4138            Nkind_In (Par, N_Function_Call,
4139                           N_Procedure_Call_Statement)
4140              and then Is_Entity_Name (Name (Par))
4141              and then Is_Dispatching_Operation (Entity (Name (Par)));
4142       end In_Dispatching_Context;
4143
4144    --  Start of processing for Resolve_Allocator
4145
4146    begin
4147       --  Replace general access with specific type
4148
4149       if Ekind (Etype (N)) = E_Allocator_Type then
4150          Set_Etype (N, Base_Type (Typ));
4151       end if;
4152
4153       if Is_Abstract_Type (Typ) then
4154          Error_Msg_N ("type of allocator cannot be abstract",  N);
4155       end if;
4156
4157       --  For qualified expression, resolve the expression using the
4158       --  given subtype (nothing to do for type mark, subtype indication)
4159
4160       if Nkind (E) = N_Qualified_Expression then
4161          if Is_Class_Wide_Type (Etype (E))
4162            and then not Is_Class_Wide_Type (Designated_Type (Typ))
4163            and then not In_Dispatching_Context
4164          then
4165             Error_Msg_N
4166               ("class-wide allocator not allowed for this access type", N);
4167          end if;
4168
4169          Resolve (Expression (E), Etype (E));
4170          Check_Unset_Reference (Expression (E));
4171
4172          --  A qualified expression requires an exact match of the type,
4173          --  class-wide matching is not allowed.
4174
4175          if (Is_Class_Wide_Type (Etype (Expression (E)))
4176               or else Is_Class_Wide_Type (Etype (E)))
4177            and then Base_Type (Etype (Expression (E))) /= Base_Type (Etype (E))
4178          then
4179             Wrong_Type (Expression (E), Etype (E));
4180          end if;
4181
4182          --  A special accessibility check is needed for allocators that
4183          --  constrain access discriminants. The level of the type of the
4184          --  expression used to constrain an access discriminant cannot be
4185          --  deeper than the type of the allocator (in contrast to access
4186          --  parameters, where the level of the actual can be arbitrary).
4187
4188          --  We can't use Valid_Conversion to perform this check because
4189          --  in general the type of the allocator is unrelated to the type
4190          --  of the access discriminant.
4191
4192          if Ekind (Typ) /= E_Anonymous_Access_Type
4193            or else Is_Local_Anonymous_Access (Typ)
4194          then
4195             Subtyp := Entity (Subtype_Mark (E));
4196
4197             Aggr := Original_Node (Expression (E));
4198
4199             if Has_Discriminants (Subtyp)
4200               and then Nkind_In (Aggr, N_Aggregate, N_Extension_Aggregate)
4201             then
4202                Discrim := First_Discriminant (Base_Type (Subtyp));
4203
4204                --  Get the first component expression of the aggregate
4205
4206                if Present (Expressions (Aggr)) then
4207                   Disc_Exp := First (Expressions (Aggr));
4208
4209                elsif Present (Component_Associations (Aggr)) then
4210                   Assoc := First (Component_Associations (Aggr));
4211
4212                   if Present (Assoc) then
4213                      Disc_Exp := Expression (Assoc);
4214                   else
4215                      Disc_Exp := Empty;
4216                   end if;
4217
4218                else
4219                   Disc_Exp := Empty;
4220                end if;
4221
4222                while Present (Discrim) and then Present (Disc_Exp) loop
4223                   if Ekind (Etype (Discrim)) = E_Anonymous_Access_Type then
4224                      Check_Allocator_Discrim_Accessibility (Disc_Exp, Typ);
4225                   end if;
4226
4227                   Next_Discriminant (Discrim);
4228
4229                   if Present (Discrim) then
4230                      if Present (Assoc) then
4231                         Next (Assoc);
4232                         Disc_Exp := Expression (Assoc);
4233
4234                      elsif Present (Next (Disc_Exp)) then
4235                         Next (Disc_Exp);
4236
4237                      else
4238                         Assoc := First (Component_Associations (Aggr));
4239
4240                         if Present (Assoc) then
4241                            Disc_Exp := Expression (Assoc);
4242                         else
4243                            Disc_Exp := Empty;
4244                         end if;
4245                      end if;
4246                   end if;
4247                end loop;
4248             end if;
4249          end if;
4250
4251       --  For a subtype mark or subtype indication, freeze the subtype
4252
4253       else
4254          Freeze_Expression (E);
4255
4256          if Is_Access_Constant (Typ) and then not No_Initialization (N) then
4257             Error_Msg_N
4258               ("initialization required for access-to-constant allocator", N);
4259          end if;
4260
4261          --  A special accessibility check is needed for allocators that
4262          --  constrain access discriminants. The level of the type of the
4263          --  expression used to constrain an access discriminant cannot be
4264          --  deeper than the type of the allocator (in contrast to access
4265          --  parameters, where the level of the actual can be arbitrary).
4266          --  We can't use Valid_Conversion to perform this check because
4267          --  in general the type of the allocator is unrelated to the type
4268          --  of the access discriminant.
4269
4270          if Nkind (Original_Node (E)) = N_Subtype_Indication
4271            and then (Ekind (Typ) /= E_Anonymous_Access_Type
4272                       or else Is_Local_Anonymous_Access (Typ))
4273          then
4274             Subtyp := Entity (Subtype_Mark (Original_Node (E)));
4275
4276             if Has_Discriminants (Subtyp) then
4277                Discrim := First_Discriminant (Base_Type (Subtyp));
4278                Constr := First (Constraints (Constraint (Original_Node (E))));
4279                while Present (Discrim) and then Present (Constr) loop
4280                   if Ekind (Etype (Discrim)) = E_Anonymous_Access_Type then
4281                      if Nkind (Constr) = N_Discriminant_Association then
4282                         Disc_Exp := Original_Node (Expression (Constr));
4283                      else
4284                         Disc_Exp := Original_Node (Constr);
4285                      end if;
4286
4287                      Check_Allocator_Discrim_Accessibility (Disc_Exp, Typ);
4288                   end if;
4289
4290                   Next_Discriminant (Discrim);
4291                   Next (Constr);
4292                end loop;
4293             end if;
4294          end if;
4295       end if;
4296
4297       --  Ada 2005 (AI-344): A class-wide allocator requires an accessibility
4298       --  check that the level of the type of the created object is not deeper
4299       --  than the level of the allocator's access type, since extensions can
4300       --  now occur at deeper levels than their ancestor types. This is a
4301       --  static accessibility level check; a run-time check is also needed in
4302       --  the case of an initialized allocator with a class-wide argument (see
4303       --  Expand_Allocator_Expression).
4304
4305       if Ada_Version >= Ada_2005
4306         and then Is_Class_Wide_Type (Designated_Type (Typ))
4307       then
4308          declare
4309             Exp_Typ : Entity_Id;
4310
4311          begin
4312             if Nkind (E) = N_Qualified_Expression then
4313                Exp_Typ := Etype (E);
4314             elsif Nkind (E) = N_Subtype_Indication then
4315                Exp_Typ := Entity (Subtype_Mark (Original_Node (E)));
4316             else
4317                Exp_Typ := Entity (E);
4318             end if;
4319
4320             if Type_Access_Level (Exp_Typ) > Type_Access_Level (Typ) then
4321                if In_Instance_Body then
4322                   Error_Msg_N ("?type in allocator has deeper level than" &
4323                                " designated class-wide type", E);
4324                   Error_Msg_N ("\?Program_Error will be raised at run time",
4325                                E);
4326                   Rewrite (N,
4327                     Make_Raise_Program_Error (Sloc (N),
4328                       Reason => PE_Accessibility_Check_Failed));
4329                   Set_Etype (N, Typ);
4330
4331                --  Do not apply Ada 2005 accessibility checks on a class-wide
4332                --  allocator if the type given in the allocator is a formal
4333                --  type. A run-time check will be performed in the instance.
4334
4335                elsif not Is_Generic_Type (Exp_Typ) then
4336                   Error_Msg_N ("type in allocator has deeper level than" &
4337                                " designated class-wide type", E);
4338                end if;
4339             end if;
4340          end;
4341       end if;
4342
4343       --  Check for allocation from an empty storage pool
4344
4345       if No_Pool_Assigned (Typ) then
4346          Error_Msg_N ("allocation from empty storage pool!", N);
4347
4348       --  If the context is an unchecked conversion, as may happen within an
4349       --  inlined subprogram, the allocator is being resolved with its own
4350       --  anonymous type. In that case, if the target type has a specific
4351       --  storage pool, it must be inherited explicitly by the allocator type.
4352
4353       elsif Nkind (Parent (N)) = N_Unchecked_Type_Conversion
4354         and then No (Associated_Storage_Pool (Typ))
4355       then
4356          Set_Associated_Storage_Pool
4357            (Typ, Associated_Storage_Pool (Etype (Parent (N))));
4358       end if;
4359
4360       if Ekind (Etype (N)) = E_Anonymous_Access_Type then
4361          Check_Restriction (No_Anonymous_Allocators, N);
4362       end if;
4363
4364       --  Check that an allocator with task parts isn't for a nested access
4365       --  type when restriction No_Task_Hierarchy applies.
4366
4367       if not Is_Library_Level_Entity (Base_Type (Typ))
4368         and then Has_Task (Base_Type (Designated_Type (Typ)))
4369       then
4370          Check_Restriction (No_Task_Hierarchy, N);
4371       end if;
4372
4373       --  An erroneous allocator may be rewritten as a raise Program_Error
4374       --  statement.
4375
4376       if Nkind (N) = N_Allocator then
4377
4378          --  An anonymous access discriminant is the definition of a
4379          --  coextension.
4380
4381          if Ekind (Typ) = E_Anonymous_Access_Type
4382            and then Nkind (Associated_Node_For_Itype (Typ)) =
4383                       N_Discriminant_Specification
4384          then
4385             --  Avoid marking an allocator as a dynamic coextension if it is
4386             --  within a static construct.
4387
4388             if not Is_Static_Coextension (N) then
4389                Set_Is_Dynamic_Coextension (N);
4390             end if;
4391
4392          --  Cleanup for potential static coextensions
4393
4394          else
4395             Set_Is_Dynamic_Coextension (N, False);
4396             Set_Is_Static_Coextension  (N, False);
4397          end if;
4398       end if;
4399
4400       --  Report a simple error:  if the designated object is a local task,
4401       --  its body has not been seen yet, and its activation will fail
4402       --  an elaboration check.
4403
4404       if Is_Task_Type (Designated_Type (Typ))
4405         and then Scope (Base_Type (Designated_Type (Typ))) = Current_Scope
4406         and then Is_Compilation_Unit (Current_Scope)
4407         and then Ekind (Current_Scope) = E_Package
4408         and then not In_Package_Body (Current_Scope)
4409       then
4410          Error_Msg_N
4411            ("cannot activate task before body seen?", N);
4412          Error_Msg_N ("\Program_Error will be raised at run time?", N);
4413       end if;
4414    end Resolve_Allocator;
4415
4416    ---------------------------
4417    -- Resolve_Arithmetic_Op --
4418    ---------------------------
4419
4420    --  Used for resolving all arithmetic operators except exponentiation
4421
4422    procedure Resolve_Arithmetic_Op (N : Node_Id; Typ : Entity_Id) is
4423       L   : constant Node_Id := Left_Opnd (N);
4424       R   : constant Node_Id := Right_Opnd (N);
4425       TL  : constant Entity_Id := Base_Type (Etype (L));
4426       TR  : constant Entity_Id := Base_Type (Etype (R));
4427       T   : Entity_Id;
4428       Rop : Node_Id;
4429
4430       B_Typ : constant Entity_Id := Base_Type (Typ);
4431       --  We do the resolution using the base type, because intermediate values
4432       --  in expressions always are of the base type, not a subtype of it.
4433
4434       function Expected_Type_Is_Any_Real (N : Node_Id) return Boolean;
4435       --  Returns True if N is in a context that expects "any real type"
4436
4437       function Is_Integer_Or_Universal (N : Node_Id) return Boolean;
4438       --  Return True iff given type is Integer or universal real/integer
4439
4440       procedure Set_Mixed_Mode_Operand (N : Node_Id; T : Entity_Id);
4441       --  Choose type of integer literal in fixed-point operation to conform
4442       --  to available fixed-point type. T is the type of the other operand,
4443       --  which is needed to determine the expected type of N.
4444
4445       procedure Set_Operand_Type (N : Node_Id);
4446       --  Set operand type to T if universal
4447
4448       -------------------------------
4449       -- Expected_Type_Is_Any_Real --
4450       -------------------------------
4451
4452       function Expected_Type_Is_Any_Real (N : Node_Id) return Boolean is
4453       begin
4454          --  N is the expression after "delta" in a fixed_point_definition;
4455          --  see RM-3.5.9(6):
4456
4457          return Nkind_In (Parent (N), N_Ordinary_Fixed_Point_Definition,
4458                                       N_Decimal_Fixed_Point_Definition,
4459
4460          --  N is one of the bounds in a real_range_specification;
4461          --  see RM-3.5.7(5):
4462
4463                                       N_Real_Range_Specification,
4464
4465          --  N is the expression of a delta_constraint;
4466          --  see RM-J.3(3):
4467
4468                                       N_Delta_Constraint);
4469       end Expected_Type_Is_Any_Real;
4470
4471       -----------------------------
4472       -- Is_Integer_Or_Universal --
4473       -----------------------------
4474
4475       function Is_Integer_Or_Universal (N : Node_Id) return Boolean is
4476          T     : Entity_Id;
4477          Index : Interp_Index;
4478          It    : Interp;
4479
4480       begin
4481          if not Is_Overloaded (N) then
4482             T := Etype (N);
4483             return Base_Type (T) = Base_Type (Standard_Integer)
4484               or else T = Universal_Integer
4485               or else T = Universal_Real;
4486          else
4487             Get_First_Interp (N, Index, It);
4488             while Present (It.Typ) loop
4489                if Base_Type (It.Typ) = Base_Type (Standard_Integer)
4490                  or else It.Typ = Universal_Integer
4491                  or else It.Typ = Universal_Real
4492                then
4493                   return True;
4494                end if;
4495
4496                Get_Next_Interp (Index, It);
4497             end loop;
4498          end if;
4499
4500          return False;
4501       end Is_Integer_Or_Universal;
4502
4503       ----------------------------
4504       -- Set_Mixed_Mode_Operand --
4505       ----------------------------
4506
4507       procedure Set_Mixed_Mode_Operand (N : Node_Id; T : Entity_Id) is
4508          Index : Interp_Index;
4509          It    : Interp;
4510
4511       begin
4512          if Universal_Interpretation (N) = Universal_Integer then
4513
4514             --  A universal integer literal is resolved as standard integer
4515             --  except in the case of a fixed-point result, where we leave it
4516             --  as universal (to be handled by Exp_Fixd later on)
4517
4518             if Is_Fixed_Point_Type (T) then
4519                Resolve (N, Universal_Integer);
4520             else
4521                Resolve (N, Standard_Integer);
4522             end if;
4523
4524          elsif Universal_Interpretation (N) = Universal_Real
4525            and then (T = Base_Type (Standard_Integer)
4526                       or else T = Universal_Integer
4527                       or else T = Universal_Real)
4528          then
4529             --  A universal real can appear in a fixed-type context. We resolve
4530             --  the literal with that context, even though this might raise an
4531             --  exception prematurely (the other operand may be zero).
4532
4533             Resolve (N, B_Typ);
4534
4535          elsif Etype (N) = Base_Type (Standard_Integer)
4536            and then T = Universal_Real
4537            and then Is_Overloaded (N)
4538          then
4539             --  Integer arg in mixed-mode operation. Resolve with universal
4540             --  type, in case preference rule must be applied.
4541
4542             Resolve (N, Universal_Integer);
4543
4544          elsif Etype (N) = T
4545            and then B_Typ /= Universal_Fixed
4546          then
4547             --  Not a mixed-mode operation, resolve with context
4548
4549             Resolve (N, B_Typ);
4550
4551          elsif Etype (N) = Any_Fixed then
4552
4553             --  N may itself be a mixed-mode operation, so use context type
4554
4555             Resolve (N, B_Typ);
4556
4557          elsif Is_Fixed_Point_Type (T)
4558            and then B_Typ = Universal_Fixed
4559            and then Is_Overloaded (N)
4560          then
4561             --  Must be (fixed * fixed) operation, operand must have one
4562             --  compatible interpretation.
4563
4564             Resolve (N, Any_Fixed);
4565
4566          elsif Is_Fixed_Point_Type (B_Typ)
4567            and then (T = Universal_Real
4568                       or else Is_Fixed_Point_Type (T))
4569            and then Is_Overloaded (N)
4570          then
4571             --  C * F(X) in a fixed context, where C is a real literal or a
4572             --  fixed-point expression. F must have either a fixed type
4573             --  interpretation or an integer interpretation, but not both.
4574
4575             Get_First_Interp (N, Index, It);
4576             while Present (It.Typ) loop
4577                if Base_Type (It.Typ) = Base_Type (Standard_Integer) then
4578                   if Analyzed (N) then
4579                      Error_Msg_N ("ambiguous operand in fixed operation", N);
4580                   else
4581                      Resolve (N, Standard_Integer);
4582                   end if;
4583
4584                elsif Is_Fixed_Point_Type (It.Typ) then
4585                   if Analyzed (N) then
4586                      Error_Msg_N ("ambiguous operand in fixed operation", N);
4587                   else
4588                      Resolve (N, It.Typ);
4589                   end if;
4590                end if;
4591
4592                Get_Next_Interp (Index, It);
4593             end loop;
4594
4595             --  Reanalyze the literal with the fixed type of the context. If
4596             --  context is Universal_Fixed, we are within a conversion, leave
4597             --  the literal as a universal real because there is no usable
4598             --  fixed type, and the target of the conversion plays no role in
4599             --  the resolution.
4600
4601             declare
4602                Op2 : Node_Id;
4603                T2  : Entity_Id;
4604
4605             begin
4606                if N = L then
4607                   Op2 := R;
4608                else
4609                   Op2 := L;
4610                end if;
4611
4612                if B_Typ = Universal_Fixed
4613                   and then Nkind (Op2) = N_Real_Literal
4614                then
4615                   T2 := Universal_Real;
4616                else
4617                   T2 := B_Typ;
4618                end if;
4619
4620                Set_Analyzed (Op2, False);
4621                Resolve (Op2, T2);
4622             end;
4623
4624          else
4625             Resolve (N);
4626          end if;
4627       end Set_Mixed_Mode_Operand;
4628
4629       ----------------------
4630       -- Set_Operand_Type --
4631       ----------------------
4632
4633       procedure Set_Operand_Type (N : Node_Id) is
4634       begin
4635          if Etype (N) = Universal_Integer
4636            or else Etype (N) = Universal_Real
4637          then
4638             Set_Etype (N, T);
4639          end if;
4640       end Set_Operand_Type;
4641
4642    --  Start of processing for Resolve_Arithmetic_Op
4643
4644    begin
4645       if Comes_From_Source (N)
4646         and then Ekind (Entity (N)) = E_Function
4647         and then Is_Imported (Entity (N))
4648         and then Is_Intrinsic_Subprogram (Entity (N))
4649       then
4650          Resolve_Intrinsic_Operator (N, Typ);
4651          return;
4652
4653       --  Special-case for mixed-mode universal expressions or fixed point type
4654       --  operation: each argument is resolved separately. The same treatment
4655       --  is required if one of the operands of a fixed point operation is
4656       --  universal real, since in this case we don't do a conversion to a
4657       --  specific fixed-point type (instead the expander handles the case).
4658
4659       elsif (B_Typ = Universal_Integer or else B_Typ = Universal_Real)
4660         and then Present (Universal_Interpretation (L))
4661         and then Present (Universal_Interpretation (R))
4662       then
4663          Resolve (L, Universal_Interpretation (L));
4664          Resolve (R, Universal_Interpretation (R));
4665          Set_Etype (N, B_Typ);
4666
4667       elsif (B_Typ = Universal_Real
4668               or else Etype (N) = Universal_Fixed
4669               or else (Etype (N) = Any_Fixed
4670                         and then Is_Fixed_Point_Type (B_Typ))
4671               or else (Is_Fixed_Point_Type (B_Typ)
4672                         and then (Is_Integer_Or_Universal (L)
4673                                    or else
4674                                   Is_Integer_Or_Universal (R))))
4675         and then Nkind_In (N, N_Op_Multiply, N_Op_Divide)
4676       then
4677          if TL = Universal_Integer or else TR = Universal_Integer then
4678             Check_For_Visible_Operator (N, B_Typ);
4679          end if;
4680
4681          --  If context is a fixed type and one operand is integer, the other
4682          --  is resolved with the type of the context.
4683
4684          if Is_Fixed_Point_Type (B_Typ)
4685            and then (Base_Type (TL) = Base_Type (Standard_Integer)
4686                       or else TL = Universal_Integer)
4687          then
4688             Resolve (R, B_Typ);
4689             Resolve (L, TL);
4690
4691          elsif Is_Fixed_Point_Type (B_Typ)
4692            and then (Base_Type (TR) = Base_Type (Standard_Integer)
4693                       or else TR = Universal_Integer)
4694          then
4695             Resolve (L, B_Typ);
4696             Resolve (R, TR);
4697
4698          else
4699             Set_Mixed_Mode_Operand (L, TR);
4700             Set_Mixed_Mode_Operand (R, TL);
4701          end if;
4702
4703          --  Check the rule in RM05-4.5.5(19.1/2) disallowing universal_fixed
4704          --  multiplying operators from being used when the expected type is
4705          --  also universal_fixed. Note that B_Typ will be Universal_Fixed in
4706          --  some cases where the expected type is actually Any_Real;
4707          --  Expected_Type_Is_Any_Real takes care of that case.
4708
4709          if Etype (N) = Universal_Fixed
4710            or else Etype (N) = Any_Fixed
4711          then
4712             if B_Typ = Universal_Fixed
4713               and then not Expected_Type_Is_Any_Real (N)
4714               and then not Nkind_In (Parent (N), N_Type_Conversion,
4715                                                  N_Unchecked_Type_Conversion)
4716             then
4717                Error_Msg_N ("type cannot be determined from context!", N);
4718                Error_Msg_N ("\explicit conversion to result type required", N);
4719
4720                Set_Etype (L, Any_Type);
4721                Set_Etype (R, Any_Type);
4722
4723             else
4724                if Ada_Version = Ada_83
4725                  and then Etype (N) = Universal_Fixed
4726                  and then not
4727                    Nkind_In (Parent (N), N_Type_Conversion,
4728                                          N_Unchecked_Type_Conversion)
4729                then
4730                   Error_Msg_N
4731                     ("(Ada 83) fixed-point operation "
4732                      & "needs explicit conversion", N);
4733                end if;
4734
4735                --  The expected type is "any real type" in contexts like
4736
4737                --    type T is delta <universal_fixed-expression> ...
4738
4739                --  in which case we need to set the type to Universal_Real
4740                --  so that static expression evaluation will work properly.
4741
4742                if Expected_Type_Is_Any_Real (N) then
4743                   Set_Etype (N, Universal_Real);
4744                else
4745                   Set_Etype (N, B_Typ);
4746                end if;
4747             end if;
4748
4749          elsif Is_Fixed_Point_Type (B_Typ)
4750            and then (Is_Integer_Or_Universal (L)
4751                        or else Nkind (L) = N_Real_Literal
4752                        or else Nkind (R) = N_Real_Literal
4753                        or else Is_Integer_Or_Universal (R))
4754          then
4755             Set_Etype (N, B_Typ);
4756
4757          elsif Etype (N) = Any_Fixed then
4758
4759             --  If no previous errors, this is only possible if one operand is
4760             --  overloaded and the context is universal. Resolve as such.
4761
4762             Set_Etype (N, B_Typ);
4763          end if;
4764
4765       else
4766          if (TL = Universal_Integer or else TL = Universal_Real)
4767               and then
4768             (TR = Universal_Integer or else TR = Universal_Real)
4769          then
4770             Check_For_Visible_Operator (N, B_Typ);
4771          end if;
4772
4773          --  If the context is Universal_Fixed and the operands are also
4774          --  universal fixed, this is an error, unless there is only one
4775          --  applicable fixed_point type (usually Duration).
4776
4777          if B_Typ = Universal_Fixed and then Etype (L) = Universal_Fixed then
4778             T := Unique_Fixed_Point_Type (N);
4779
4780             if T  = Any_Type then
4781                Set_Etype (N, T);
4782                return;
4783             else
4784                Resolve (L, T);
4785                Resolve (R, T);
4786             end if;
4787
4788          else
4789             Resolve (L, B_Typ);
4790             Resolve (R, B_Typ);
4791          end if;
4792
4793          --  If one of the arguments was resolved to a non-universal type.
4794          --  label the result of the operation itself with the same type.
4795          --  Do the same for the universal argument, if any.
4796
4797          T := Intersect_Types (L, R);
4798          Set_Etype (N, Base_Type (T));
4799          Set_Operand_Type (L);
4800          Set_Operand_Type (R);
4801       end if;
4802
4803       Generate_Operator_Reference (N, Typ);
4804       Eval_Arithmetic_Op (N);
4805
4806       --  In SPARK, a multiplication or division with operands of fixed point
4807       --  types shall be qualified or explicitly converted to identify the
4808       --  result type.
4809
4810       if (Is_Fixed_Point_Type (Etype (L))
4811            or else Is_Fixed_Point_Type (Etype (R)))
4812         and then Nkind_In (N, N_Op_Multiply, N_Op_Divide)
4813         and then
4814           not Nkind_In (Parent (N), N_Qualified_Expression, N_Type_Conversion)
4815       then
4816          Check_SPARK_Restriction
4817            ("operation should be qualified or explicitly converted", N);
4818       end if;
4819
4820       --  Set overflow and division checking bit. Much cleverer code needed
4821       --  here eventually and perhaps the Resolve routines should be separated
4822       --  for the various arithmetic operations, since they will need
4823       --  different processing. ???
4824
4825       if Nkind (N) in N_Op then
4826          if not Overflow_Checks_Suppressed (Etype (N)) then
4827             Enable_Overflow_Check (N);
4828          end if;
4829
4830          --  Give warning if explicit division by zero
4831
4832          if Nkind_In (N, N_Op_Divide, N_Op_Rem, N_Op_Mod)
4833            and then not Division_Checks_Suppressed (Etype (N))
4834          then
4835             Rop := Right_Opnd (N);
4836
4837             if Compile_Time_Known_Value (Rop)
4838               and then ((Is_Integer_Type (Etype (Rop))
4839                           and then Expr_Value (Rop) = Uint_0)
4840                          or else
4841                            (Is_Real_Type (Etype (Rop))
4842                              and then Expr_Value_R (Rop) = Ureal_0))
4843             then
4844                --  Specialize the warning message according to the operation
4845
4846                case Nkind (N) is
4847                   when N_Op_Divide =>
4848                      Apply_Compile_Time_Constraint_Error
4849                        (N, "division by zero?", CE_Divide_By_Zero,
4850                         Loc => Sloc (Right_Opnd (N)));
4851
4852                   when N_Op_Rem =>
4853                      Apply_Compile_Time_Constraint_Error
4854                        (N, "rem with zero divisor?", CE_Divide_By_Zero,
4855                         Loc => Sloc (Right_Opnd (N)));
4856
4857                   when N_Op_Mod =>
4858                      Apply_Compile_Time_Constraint_Error
4859                        (N, "mod with zero divisor?", CE_Divide_By_Zero,
4860                         Loc => Sloc (Right_Opnd (N)));
4861
4862                   --  Division by zero can only happen with division, rem,
4863                   --  and mod operations.
4864
4865                   when others =>
4866                      raise Program_Error;
4867                end case;
4868
4869             --  Otherwise just set the flag to check at run time
4870
4871             else
4872                Activate_Division_Check (N);
4873             end if;
4874          end if;
4875
4876          --  If Restriction No_Implicit_Conditionals is active, then it is
4877          --  violated if either operand can be negative for mod, or for rem
4878          --  if both operands can be negative.
4879
4880          if Restriction_Check_Required (No_Implicit_Conditionals)
4881            and then Nkind_In (N, N_Op_Rem, N_Op_Mod)
4882          then
4883             declare
4884                Lo : Uint;
4885                Hi : Uint;
4886                OK : Boolean;
4887
4888                LNeg : Boolean;
4889                RNeg : Boolean;
4890                --  Set if corresponding operand might be negative
4891
4892             begin
4893                Determine_Range
4894                  (Left_Opnd (N), OK, Lo, Hi, Assume_Valid => True);
4895                LNeg := (not OK) or else Lo < 0;
4896
4897                Determine_Range
4898                  (Right_Opnd (N), OK, Lo, Hi, Assume_Valid => True);
4899                RNeg := (not OK) or else Lo < 0;
4900
4901                --  Check if we will be generating conditionals. There are two
4902                --  cases where that can happen, first for REM, the only case
4903                --  is largest negative integer mod -1, where the division can
4904                --  overflow, but we still have to give the right result. The
4905                --  front end generates a test for this annoying case. Here we
4906                --  just test if both operands can be negative (that's what the
4907                --  expander does, so we match its logic here).
4908
4909                --  The second case is mod where either operand can be negative.
4910                --  In this case, the back end has to generate additional tests.
4911
4912                if (Nkind (N) = N_Op_Rem and then (LNeg and RNeg))
4913                     or else
4914                   (Nkind (N) = N_Op_Mod and then (LNeg or RNeg))
4915                then
4916                   Check_Restriction (No_Implicit_Conditionals, N);
4917                end if;
4918             end;
4919          end if;
4920       end if;
4921
4922       Check_Unset_Reference (L);
4923       Check_Unset_Reference (R);
4924    end Resolve_Arithmetic_Op;
4925
4926    ------------------
4927    -- Resolve_Call --
4928    ------------------
4929
4930    procedure Resolve_Call (N : Node_Id; Typ : Entity_Id) is
4931       Loc     : constant Source_Ptr := Sloc (N);
4932       Subp    : constant Node_Id    := Name (N);
4933       Nam     : Entity_Id;
4934       I       : Interp_Index;
4935       It      : Interp;
4936       Norm_OK : Boolean;
4937       Scop    : Entity_Id;
4938       Rtype   : Entity_Id;
4939
4940       function Same_Or_Aliased_Subprograms
4941         (S : Entity_Id;
4942          E : Entity_Id) return Boolean;
4943       --  Returns True if the subprogram entity S is the same as E or else
4944       --  S is an alias of E.
4945
4946       ---------------------------------
4947       -- Same_Or_Aliased_Subprograms --
4948       ---------------------------------
4949
4950       function Same_Or_Aliased_Subprograms
4951         (S : Entity_Id;
4952          E : Entity_Id) return Boolean
4953       is
4954          Subp_Alias : constant Entity_Id := Alias (S);
4955       begin
4956          return S = E
4957            or else (Present (Subp_Alias) and then Subp_Alias = E);
4958       end Same_Or_Aliased_Subprograms;
4959
4960    --  Start of processing for Resolve_Call
4961
4962    begin
4963       --  The context imposes a unique interpretation with type Typ on a
4964       --  procedure or function call. Find the entity of the subprogram that
4965       --  yields the expected type, and propagate the corresponding formal
4966       --  constraints on the actuals. The caller has established that an
4967       --  interpretation exists, and emitted an error if not unique.
4968
4969       --  First deal with the case of a call to an access-to-subprogram,
4970       --  dereference made explicit in Analyze_Call.
4971
4972       if Ekind (Etype (Subp)) = E_Subprogram_Type then
4973          if not Is_Overloaded (Subp) then
4974             Nam := Etype (Subp);
4975
4976          else
4977             --  Find the interpretation whose type (a subprogram type) has a
4978             --  return type that is compatible with the context. Analysis of
4979             --  the node has established that one exists.
4980
4981             Nam := Empty;
4982
4983             Get_First_Interp (Subp,  I, It);
4984             while Present (It.Typ) loop
4985                if Covers (Typ, Etype (It.Typ)) then
4986                   Nam := It.Typ;
4987                   exit;
4988                end if;
4989
4990                Get_Next_Interp (I, It);
4991             end loop;
4992
4993             if No (Nam) then
4994                raise Program_Error;
4995             end if;
4996          end if;
4997
4998          --  If the prefix is not an entity, then resolve it
4999
5000          if not Is_Entity_Name (Subp) then
5001             Resolve (Subp, Nam);
5002          end if;
5003
5004          --  For an indirect call, we always invalidate checks, since we do not
5005          --  know whether the subprogram is local or global. Yes we could do
5006          --  better here, e.g. by knowing that there are no local subprograms,
5007          --  but it does not seem worth the effort. Similarly, we kill all
5008          --  knowledge of current constant values.
5009
5010          Kill_Current_Values;
5011
5012       --  If this is a procedure call which is really an entry call, do
5013       --  the conversion of the procedure call to an entry call. Protected
5014       --  operations use the same circuitry because the name in the call
5015       --  can be an arbitrary expression with special resolution rules.
5016
5017       elsif Nkind_In (Subp, N_Selected_Component, N_Indexed_Component)
5018         or else (Is_Entity_Name (Subp)
5019                   and then Ekind (Entity (Subp)) = E_Entry)
5020       then
5021          Resolve_Entry_Call (N, Typ);
5022          Check_Elab_Call (N);
5023
5024          --  Kill checks and constant values, as above for indirect case
5025          --  Who knows what happens when another task is activated?
5026
5027          Kill_Current_Values;
5028          return;
5029
5030       --  Normal subprogram call with name established in Resolve
5031
5032       elsif not (Is_Type (Entity (Subp))) then
5033          Nam := Entity (Subp);
5034          Set_Entity_With_Style_Check (Subp, Nam);
5035
5036       --  Otherwise we must have the case of an overloaded call
5037
5038       else
5039          pragma Assert (Is_Overloaded (Subp));
5040
5041          --  Initialize Nam to prevent warning (we know it will be assigned
5042          --  in the loop below, but the compiler does not know that).
5043
5044          Nam := Empty;
5045
5046          Get_First_Interp (Subp,  I, It);
5047          while Present (It.Typ) loop
5048             if Covers (Typ, It.Typ) then
5049                Nam := It.Nam;
5050                Set_Entity_With_Style_Check (Subp, Nam);
5051                exit;
5052             end if;
5053
5054             Get_Next_Interp (I, It);
5055          end loop;
5056       end if;
5057
5058       if Is_Access_Subprogram_Type (Base_Type (Etype (Nam)))
5059          and then not Is_Access_Subprogram_Type (Base_Type (Typ))
5060          and then Nkind (Subp) /= N_Explicit_Dereference
5061          and then Present (Parameter_Associations (N))
5062       then
5063          --  The prefix is a parameterless function call that returns an access
5064          --  to subprogram. If parameters are present in the current call, add
5065          --  add an explicit dereference. We use the base type here because
5066          --  within an instance these may be subtypes.
5067
5068          --  The dereference is added either in Analyze_Call or here. Should
5069          --  be consolidated ???
5070
5071          Set_Is_Overloaded (Subp, False);
5072          Set_Etype (Subp, Etype (Nam));
5073          Insert_Explicit_Dereference (Subp);
5074          Nam := Designated_Type (Etype (Nam));
5075          Resolve (Subp, Nam);
5076       end if;
5077
5078       --  Check that a call to Current_Task does not occur in an entry body
5079
5080       if Is_RTE (Nam, RE_Current_Task) then
5081          declare
5082             P : Node_Id;
5083
5084          begin
5085             P := N;
5086             loop
5087                P := Parent (P);
5088
5089                --  Exclude calls that occur within the default of a formal
5090                --  parameter of the entry, since those are evaluated outside
5091                --  of the body.
5092
5093                exit when No (P) or else Nkind (P) = N_Parameter_Specification;
5094
5095                if Nkind (P) = N_Entry_Body
5096                  or else (Nkind (P) = N_Subprogram_Body
5097                            and then Is_Entry_Barrier_Function (P))
5098                then
5099                   Rtype := Etype (N);
5100                   Error_Msg_NE
5101                     ("?& should not be used in entry body (RM C.7(17))",
5102                      N, Nam);
5103                   Error_Msg_NE
5104                     ("\Program_Error will be raised at run time?", N, Nam);
5105                   Rewrite (N,
5106                     Make_Raise_Program_Error (Loc,
5107                       Reason => PE_Current_Task_In_Entry_Body));
5108                   Set_Etype (N, Rtype);
5109                   return;
5110                end if;
5111             end loop;
5112          end;
5113       end if;
5114
5115       --  Check that a procedure call does not occur in the context of the
5116       --  entry call statement of a conditional or timed entry call. Note that
5117       --  the case of a call to a subprogram renaming of an entry will also be
5118       --  rejected. The test for N not being an N_Entry_Call_Statement is
5119       --  defensive, covering the possibility that the processing of entry
5120       --  calls might reach this point due to later modifications of the code
5121       --  above.
5122
5123       if Nkind (Parent (N)) = N_Entry_Call_Alternative
5124         and then Nkind (N) /= N_Entry_Call_Statement
5125         and then Entry_Call_Statement (Parent (N)) = N
5126       then
5127          if Ada_Version < Ada_2005 then
5128             Error_Msg_N ("entry call required in select statement", N);
5129
5130          --  Ada 2005 (AI-345): If a procedure_call_statement is used
5131          --  for a procedure_or_entry_call, the procedure_name or
5132          --  procedure_prefix of the procedure_call_statement shall denote
5133          --  an entry renamed by a procedure, or (a view of) a primitive
5134          --  subprogram of a limited interface whose first parameter is
5135          --  a controlling parameter.
5136
5137          elsif Nkind (N) = N_Procedure_Call_Statement
5138            and then not Is_Renamed_Entry (Nam)
5139            and then not Is_Controlling_Limited_Procedure (Nam)
5140          then
5141             Error_Msg_N
5142              ("entry call or dispatching primitive of interface required", N);
5143          end if;
5144       end if;
5145
5146       --  Check that this is not a call to a protected procedure or entry from
5147       --  within a protected function.
5148
5149       if Ekind (Current_Scope) = E_Function
5150         and then Ekind (Scope (Current_Scope)) = E_Protected_Type
5151         and then Ekind (Nam) /= E_Function
5152         and then Scope (Nam) = Scope (Current_Scope)
5153       then
5154          Error_Msg_N ("within protected function, protected " &
5155            "object is constant", N);
5156          Error_Msg_N ("\cannot call operation that may modify it", N);
5157       end if;
5158
5159       --  Freeze the subprogram name if not in a spec-expression. Note that we
5160       --  freeze procedure calls as well as function calls. Procedure calls are
5161       --  not frozen according to the rules (RM 13.14(14)) because it is
5162       --  impossible to have a procedure call to a non-frozen procedure in pure
5163       --  Ada, but in the code that we generate in the expander, this rule
5164       --  needs extending because we can generate procedure calls that need
5165       --  freezing.
5166
5167       if Is_Entity_Name (Subp) and then not In_Spec_Expression then
5168          Freeze_Expression (Subp);
5169       end if;
5170
5171       --  For a predefined operator, the type of the result is the type imposed
5172       --  by context, except for a predefined operation on universal fixed.
5173       --  Otherwise The type of the call is the type returned by the subprogram
5174       --  being called.
5175
5176       if Is_Predefined_Op (Nam) then
5177          if Etype (N) /= Universal_Fixed then
5178             Set_Etype (N, Typ);
5179          end if;
5180
5181       --  If the subprogram returns an array type, and the context requires the
5182       --  component type of that array type, the node is really an indexing of
5183       --  the parameterless call. Resolve as such. A pathological case occurs
5184       --  when the type of the component is an access to the array type. In
5185       --  this case the call is truly ambiguous.
5186
5187       elsif (Needs_No_Actuals (Nam) or else Needs_One_Actual (Nam))
5188         and then
5189           ((Is_Array_Type (Etype (Nam))
5190              and then Covers (Typ, Component_Type (Etype (Nam))))
5191              or else (Is_Access_Type (Etype (Nam))
5192                        and then Is_Array_Type (Designated_Type (Etype (Nam)))
5193                        and then
5194                          Covers
5195                           (Typ,
5196                            Component_Type (Designated_Type (Etype (Nam))))))
5197       then
5198          declare
5199             Index_Node : Node_Id;
5200             New_Subp   : Node_Id;
5201             Ret_Type   : constant Entity_Id := Etype (Nam);
5202
5203          begin
5204             if Is_Access_Type (Ret_Type)
5205               and then Ret_Type = Component_Type (Designated_Type (Ret_Type))
5206             then
5207                Error_Msg_N
5208                  ("cannot disambiguate function call and indexing", N);
5209             else
5210                New_Subp := Relocate_Node (Subp);
5211                Set_Entity (Subp, Nam);
5212
5213                if (Is_Array_Type (Ret_Type)
5214                     and then Component_Type (Ret_Type) /= Any_Type)
5215                  or else
5216                   (Is_Access_Type (Ret_Type)
5217                     and then
5218                       Component_Type (Designated_Type (Ret_Type)) /= Any_Type)
5219                then
5220                   if Needs_No_Actuals (Nam) then
5221
5222                      --  Indexed call to a parameterless function
5223
5224                      Index_Node :=
5225                        Make_Indexed_Component (Loc,
5226                          Prefix =>
5227                            Make_Function_Call (Loc,
5228                              Name => New_Subp),
5229                          Expressions => Parameter_Associations (N));
5230                   else
5231                      --  An Ada 2005 prefixed call to a primitive operation
5232                      --  whose first parameter is the prefix. This prefix was
5233                      --  prepended to the parameter list, which is actually a
5234                      --  list of indexes. Remove the prefix in order to build
5235                      --  the proper indexed component.
5236
5237                      Index_Node :=
5238                         Make_Indexed_Component (Loc,
5239                           Prefix =>
5240                             Make_Function_Call (Loc,
5241                                Name => New_Subp,
5242                                Parameter_Associations =>
5243                                  New_List
5244                                    (Remove_Head (Parameter_Associations (N)))),
5245                            Expressions => Parameter_Associations (N));
5246                   end if;
5247
5248                   --  Preserve the parenthesis count of the node
5249
5250                   Set_Paren_Count (Index_Node, Paren_Count (N));
5251
5252                   --  Since we are correcting a node classification error made
5253                   --  by the parser, we call Replace rather than Rewrite.
5254
5255                   Replace (N, Index_Node);
5256
5257                   Set_Etype (Prefix (N), Ret_Type);
5258                   Set_Etype (N, Typ);
5259                   Resolve_Indexed_Component (N, Typ);
5260                   Check_Elab_Call (Prefix (N));
5261                end if;
5262             end if;
5263
5264             return;
5265          end;
5266
5267       else
5268          Set_Etype (N, Etype (Nam));
5269       end if;
5270
5271       --  In the case where the call is to an overloaded subprogram, Analyze
5272       --  calls Normalize_Actuals once per overloaded subprogram. Therefore in
5273       --  such a case Normalize_Actuals needs to be called once more to order
5274       --  the actuals correctly. Otherwise the call will have the ordering
5275       --  given by the last overloaded subprogram whether this is the correct
5276       --  one being called or not.
5277
5278       if Is_Overloaded (Subp) then
5279          Normalize_Actuals (N, Nam, False, Norm_OK);
5280          pragma Assert (Norm_OK);
5281       end if;
5282
5283       --  In any case, call is fully resolved now. Reset Overload flag, to
5284       --  prevent subsequent overload resolution if node is analyzed again
5285
5286       Set_Is_Overloaded (Subp, False);
5287       Set_Is_Overloaded (N, False);
5288
5289       --  If we are calling the current subprogram from immediately within its
5290       --  body, then that is the case where we can sometimes detect cases of
5291       --  infinite recursion statically. Do not try this in case restriction
5292       --  No_Recursion is in effect anyway, and do it only for source calls.
5293
5294       if Comes_From_Source (N) then
5295          Scop := Current_Scope;
5296
5297          --  Issue warning for possible infinite recursion in the absence
5298          --  of the No_Recursion restriction.
5299
5300          if Same_Or_Aliased_Subprograms (Nam, Scop)
5301            and then not Restriction_Active (No_Recursion)
5302            and then Check_Infinite_Recursion (N)
5303          then
5304             --  Here we detected and flagged an infinite recursion, so we do
5305             --  not need to test the case below for further warnings. Also we
5306             --  are all done if we now have a raise SE node.
5307
5308             if Nkind (N) = N_Raise_Storage_Error then
5309                return;
5310             end if;
5311
5312          --  If call is to immediately containing subprogram, then check for
5313          --  the case of a possible run-time detectable infinite recursion.
5314
5315          else
5316             Scope_Loop : while Scop /= Standard_Standard loop
5317                if Same_Or_Aliased_Subprograms (Nam, Scop) then
5318
5319                   --  Although in general case, recursion is not statically
5320                   --  checkable, the case of calling an immediately containing
5321                   --  subprogram is easy to catch.
5322
5323                   Check_Restriction (No_Recursion, N);
5324
5325                   --  If the recursive call is to a parameterless subprogram,
5326                   --  then even if we can't statically detect infinite
5327                   --  recursion, this is pretty suspicious, and we output a
5328                   --  warning. Furthermore, we will try later to detect some
5329                   --  cases here at run time by expanding checking code (see
5330                   --  Detect_Infinite_Recursion in package Exp_Ch6).
5331
5332                   --  If the recursive call is within a handler, do not emit a
5333                   --  warning, because this is a common idiom: loop until input
5334                   --  is correct, catch illegal input in handler and restart.
5335
5336                   if No (First_Formal (Nam))
5337                     and then Etype (Nam) = Standard_Void_Type
5338                     and then not Error_Posted (N)
5339                     and then Nkind (Parent (N)) /= N_Exception_Handler
5340                   then
5341                      --  For the case of a procedure call. We give the message
5342                      --  only if the call is the first statement in a sequence
5343                      --  of statements, or if all previous statements are
5344                      --  simple assignments. This is simply a heuristic to
5345                      --  decrease false positives, without losing too many good
5346                      --  warnings. The idea is that these previous statements
5347                      --  may affect global variables the procedure depends on.
5348                      --  We also exclude raise statements, that may arise from
5349                      --  constraint checks and are probably unrelated to the
5350                      --  intended control flow.
5351
5352                      if Nkind (N) = N_Procedure_Call_Statement
5353                        and then Is_List_Member (N)
5354                      then
5355                         declare
5356                            P : Node_Id;
5357                         begin
5358                            P := Prev (N);
5359                            while Present (P) loop
5360                               if not Nkind_In (P,
5361                                 N_Assignment_Statement,
5362                                 N_Raise_Constraint_Error)
5363                               then
5364                                  exit Scope_Loop;
5365                               end if;
5366
5367                               Prev (P);
5368                            end loop;
5369                         end;
5370                      end if;
5371
5372                      --  Do not give warning if we are in a conditional context
5373
5374                      declare
5375                         K : constant Node_Kind := Nkind (Parent (N));
5376                      begin
5377                         if (K = N_Loop_Statement
5378                              and then Present (Iteration_Scheme (Parent (N))))
5379                           or else K = N_If_Statement
5380                           or else K = N_Elsif_Part
5381                           or else K = N_Case_Statement_Alternative
5382                         then
5383                            exit Scope_Loop;
5384                         end if;
5385                      end;
5386
5387                      --  Here warning is to be issued
5388
5389                      Set_Has_Recursive_Call (Nam);
5390                      Error_Msg_N
5391                        ("?possible infinite recursion!", N);
5392                      Error_Msg_N
5393                        ("\?Storage_Error may be raised at run time!", N);
5394                   end if;
5395
5396                   exit Scope_Loop;
5397                end if;
5398
5399                Scop := Scope (Scop);
5400             end loop Scope_Loop;
5401          end if;
5402       end if;
5403
5404       --  Check obsolescent reference to Ada.Characters.Handling subprogram
5405
5406       Check_Obsolescent_2005_Entity (Nam, Subp);
5407
5408       --  If subprogram name is a predefined operator, it was given in
5409       --  functional notation. Replace call node with operator node, so
5410       --  that actuals can be resolved appropriately.
5411
5412       if Is_Predefined_Op (Nam) or else Ekind (Nam) = E_Operator then
5413          Make_Call_Into_Operator (N, Typ, Entity (Name (N)));
5414          return;
5415
5416       elsif Present (Alias (Nam))
5417         and then Is_Predefined_Op (Alias (Nam))
5418       then
5419          Resolve_Actuals (N, Nam);
5420          Make_Call_Into_Operator (N, Typ, Alias (Nam));
5421          return;
5422       end if;
5423
5424       --  Create a transient scope if the resulting type requires it
5425
5426       --  There are several notable exceptions:
5427
5428       --  a) In init procs, the transient scope overhead is not needed, and is
5429       --  even incorrect when the call is a nested initialization call for a
5430       --  component whose expansion may generate adjust calls. However, if the
5431       --  call is some other procedure call within an initialization procedure
5432       --  (for example a call to Create_Task in the init_proc of the task
5433       --  run-time record) a transient scope must be created around this call.
5434
5435       --  b) Enumeration literal pseudo-calls need no transient scope
5436
5437       --  c) Intrinsic subprograms (Unchecked_Conversion and source info
5438       --  functions) do not use the secondary stack even though the return
5439       --  type may be unconstrained.
5440
5441       --  d) Calls to a build-in-place function, since such functions may
5442       --  allocate their result directly in a target object, and cases where
5443       --  the result does get allocated in the secondary stack are checked for
5444       --  within the specialized Exp_Ch6 procedures for expanding those
5445       --  build-in-place calls.
5446
5447       --  e) If the subprogram is marked Inline_Always, then even if it returns
5448       --  an unconstrained type the call does not require use of the secondary
5449       --  stack. However, inlining will only take place if the body to inline
5450       --  is already present. It may not be available if e.g. the subprogram is
5451       --  declared in a child instance.
5452
5453       --  If this is an initialization call for a type whose construction
5454       --  uses the secondary stack, and it is not a nested call to initialize
5455       --  a component, we do need to create a transient scope for it. We
5456       --  check for this by traversing the type in Check_Initialization_Call.
5457
5458       if Is_Inlined (Nam)
5459         and then Has_Pragma_Inline_Always (Nam)
5460         and then Nkind (Unit_Declaration_Node (Nam)) = N_Subprogram_Declaration
5461         and then Present (Body_To_Inline (Unit_Declaration_Node (Nam)))
5462       then
5463          null;
5464
5465       elsif Ekind (Nam) = E_Enumeration_Literal
5466         or else Is_Build_In_Place_Function (Nam)
5467         or else Is_Intrinsic_Subprogram (Nam)
5468       then
5469          null;
5470
5471       elsif Expander_Active
5472         and then Is_Type (Etype (Nam))
5473         and then Requires_Transient_Scope (Etype (Nam))
5474         and then
5475           (not Within_Init_Proc
5476             or else
5477               (not Is_Init_Proc (Nam) and then Ekind (Nam) /= E_Function))
5478       then
5479          Establish_Transient_Scope (N, Sec_Stack => True);
5480
5481          --  If the call appears within the bounds of a loop, it will
5482          --  be rewritten and reanalyzed, nothing left to do here.
5483
5484          if Nkind (N) /= N_Function_Call then
5485             return;
5486          end if;
5487
5488       elsif Is_Init_Proc (Nam)
5489         and then not Within_Init_Proc
5490       then
5491          Check_Initialization_Call (N, Nam);
5492       end if;
5493
5494       --  A protected function cannot be called within the definition of the
5495       --  enclosing protected type.
5496
5497       if Is_Protected_Type (Scope (Nam))
5498         and then In_Open_Scopes (Scope (Nam))
5499         and then not Has_Completion (Scope (Nam))
5500       then
5501          Error_Msg_NE
5502            ("& cannot be called before end of protected definition", N, Nam);
5503       end if;
5504
5505       --  Propagate interpretation to actuals, and add default expressions
5506       --  where needed.
5507
5508       if Present (First_Formal (Nam)) then
5509          Resolve_Actuals (N, Nam);
5510
5511       --  Overloaded literals are rewritten as function calls, for purpose of
5512       --  resolution. After resolution, we can replace the call with the
5513       --  literal itself.
5514
5515       elsif Ekind (Nam) = E_Enumeration_Literal then
5516          Copy_Node (Subp, N);
5517          Resolve_Entity_Name (N, Typ);
5518
5519          --  Avoid validation, since it is a static function call
5520
5521          Generate_Reference (Nam, Subp);
5522          return;
5523       end if;
5524
5525       --  If the subprogram is not global, then kill all saved values and
5526       --  checks. This is a bit conservative, since in many cases we could do
5527       --  better, but it is not worth the effort. Similarly, we kill constant
5528       --  values. However we do not need to do this for internal entities
5529       --  (unless they are inherited user-defined subprograms), since they
5530       --  are not in the business of molesting local values.
5531
5532       --  If the flag Suppress_Value_Tracking_On_Calls is set, then we also
5533       --  kill all checks and values for calls to global subprograms. This
5534       --  takes care of the case where an access to a local subprogram is
5535       --  taken, and could be passed directly or indirectly and then called
5536       --  from almost any context.
5537
5538       --  Note: we do not do this step till after resolving the actuals. That
5539       --  way we still take advantage of the current value information while
5540       --  scanning the actuals.
5541
5542       --  We suppress killing values if we are processing the nodes associated
5543       --  with N_Freeze_Entity nodes. Otherwise the declaration of a tagged
5544       --  type kills all the values as part of analyzing the code that
5545       --  initializes the dispatch tables.
5546
5547       if Inside_Freezing_Actions = 0
5548         and then (not Is_Library_Level_Entity (Nam)
5549                    or else Suppress_Value_Tracking_On_Call
5550                              (Nearest_Dynamic_Scope (Current_Scope)))
5551         and then (Comes_From_Source (Nam)
5552                    or else (Present (Alias (Nam))
5553                              and then Comes_From_Source (Alias (Nam))))
5554       then
5555          Kill_Current_Values;
5556       end if;
5557
5558       --  If we are warning about unread OUT parameters, this is the place to
5559       --  set Last_Assignment for OUT and IN OUT parameters. We have to do this
5560       --  after the above call to Kill_Current_Values (since that call clears
5561       --  the Last_Assignment field of all local variables).
5562
5563       if (Warn_On_Modified_Unread or Warn_On_All_Unread_Out_Parameters)
5564         and then Comes_From_Source (N)
5565         and then In_Extended_Main_Source_Unit (N)
5566       then
5567          declare
5568             F : Entity_Id;
5569             A : Node_Id;
5570
5571          begin
5572             F := First_Formal (Nam);
5573             A := First_Actual (N);
5574             while Present (F) and then Present (A) loop
5575                if Ekind_In (F, E_Out_Parameter, E_In_Out_Parameter)
5576                  and then Warn_On_Modified_As_Out_Parameter (F)
5577                  and then Is_Entity_Name (A)
5578                  and then Present (Entity (A))
5579                  and then Comes_From_Source (N)
5580                  and then Safe_To_Capture_Value (N, Entity (A))
5581                then
5582                   Set_Last_Assignment (Entity (A), A);
5583                end if;
5584
5585                Next_Formal (F);
5586                Next_Actual (A);
5587             end loop;
5588          end;
5589       end if;
5590
5591       --  If the subprogram is a primitive operation, check whether or not
5592       --  it is a correct dispatching call.
5593
5594       if Is_Overloadable (Nam)
5595         and then Is_Dispatching_Operation (Nam)
5596       then
5597          Check_Dispatching_Call (N);
5598
5599       elsif Ekind (Nam) /= E_Subprogram_Type
5600         and then Is_Abstract_Subprogram (Nam)
5601         and then not In_Instance
5602       then
5603          Error_Msg_NE ("cannot call abstract subprogram &!", N, Nam);
5604       end if;
5605
5606       --  If this is a dispatching call, generate the appropriate reference,
5607       --  for better source navigation in GPS.
5608
5609       if Is_Overloadable (Nam)
5610         and then Present (Controlling_Argument (N))
5611       then
5612          Generate_Reference (Nam, Subp, 'R');
5613
5614       --  Normal case, not a dispatching call: generate a call reference
5615
5616       else
5617          Generate_Reference (Nam, Subp, 's');
5618       end if;
5619
5620       if Is_Intrinsic_Subprogram (Nam) then
5621          Check_Intrinsic_Call (N);
5622       end if;
5623
5624       --  Check for violation of restriction No_Specific_Termination_Handlers
5625       --  and warn on a potentially blocking call to Abort_Task.
5626
5627       if Restriction_Check_Required (No_Specific_Termination_Handlers)
5628         and then (Is_RTE (Nam, RE_Set_Specific_Handler)
5629                     or else
5630                   Is_RTE (Nam, RE_Specific_Handler))
5631       then
5632          Check_Restriction (No_Specific_Termination_Handlers, N);
5633
5634       elsif Is_RTE (Nam, RE_Abort_Task) then
5635          Check_Potentially_Blocking_Operation (N);
5636       end if;
5637
5638       --  A call to Ada.Real_Time.Timing_Events.Set_Handler to set a relative
5639       --  timing event violates restriction No_Relative_Delay (AI-0211). We
5640       --  need to check the second argument to determine whether it is an
5641       --  absolute or relative timing event.
5642
5643       if Restriction_Check_Required (No_Relative_Delay)
5644         and then Is_RTE (Nam, RE_Set_Handler)
5645         and then Is_RTE (Etype (Next_Actual (First_Actual (N))), RE_Time_Span)
5646       then
5647          Check_Restriction (No_Relative_Delay, N);
5648       end if;
5649
5650       --  Issue an error for a call to an eliminated subprogram. We skip this
5651       --  in a spec expression, e.g. a call in a default parameter value, since
5652       --  we are not really doing a call at this time. That's important because
5653       --  the spec expression may itself belong to an eliminated subprogram.
5654
5655       if not In_Spec_Expression then
5656          Check_For_Eliminated_Subprogram (Subp, Nam);
5657       end if;
5658
5659       --  In formal mode, the primitive operations of a tagged type or type
5660       --  extension do not include functions that return the tagged type.
5661
5662       --  Commented out as the call to Is_Inherited_Operation_For_Type may
5663       --  cause an error because the type entity of the parent node of
5664       --  Entity (Name (N) may not be set. ???
5665       --  So why not just add a guard ???
5666
5667 --      if Nkind (N) = N_Function_Call
5668 --        and then Is_Tagged_Type (Etype (N))
5669 --        and then Is_Entity_Name (Name (N))
5670 --        and then Is_Inherited_Operation_For_Type
5671 --                   (Entity (Name (N)), Etype (N))
5672 --      then
5673 --         Check_SPARK_Restriction ("function not inherited", N);
5674 --      end if;
5675
5676       --  Implement rule in 12.5.1 (23.3/2): In an instance, if the actual is
5677       --  class-wide and the call dispatches on result in a context that does
5678       --  not provide a tag, the call raises Program_Error.
5679
5680       if Nkind (N) = N_Function_Call
5681         and then In_Instance
5682         and then Is_Generic_Actual_Type (Typ)
5683         and then Is_Class_Wide_Type (Typ)
5684         and then Has_Controlling_Result (Nam)
5685         and then Nkind (Parent (N)) = N_Object_Declaration
5686       then
5687          --  Verify that none of the formals are controlling
5688
5689          declare
5690             Call_OK : Boolean := False;
5691             F       : Entity_Id;
5692
5693          begin
5694             F := First_Formal (Nam);
5695             while Present (F) loop
5696                if Is_Controlling_Formal (F) then
5697                   Call_OK := True;
5698                   exit;
5699                end if;
5700
5701                Next_Formal (F);
5702             end loop;
5703
5704             if not Call_OK then
5705                Error_Msg_N ("!? cannot determine tag of result", N);
5706                Error_Msg_N ("!? Program_Error will be raised", N);
5707                Insert_Action (N,
5708                  Make_Raise_Program_Error (Sloc (N),
5709                     Reason => PE_Explicit_Raise));
5710             end if;
5711          end;
5712       end if;
5713
5714       --  All done, evaluate call and deal with elaboration issues
5715
5716       Eval_Call (N);
5717       Check_Elab_Call (N);
5718       Warn_On_Overlapping_Actuals (Nam, N);
5719    end Resolve_Call;
5720
5721    -----------------------------
5722    -- Resolve_Case_Expression --
5723    -----------------------------
5724
5725    procedure Resolve_Case_Expression (N : Node_Id; Typ : Entity_Id) is
5726       Alt : Node_Id;
5727
5728    begin
5729       Alt := First (Alternatives (N));
5730       while Present (Alt) loop
5731          Resolve (Expression (Alt), Typ);
5732          Next (Alt);
5733       end loop;
5734
5735       Set_Etype (N, Typ);
5736       Eval_Case_Expression (N);
5737    end Resolve_Case_Expression;
5738
5739    -------------------------------
5740    -- Resolve_Character_Literal --
5741    -------------------------------
5742
5743    procedure Resolve_Character_Literal (N : Node_Id; Typ : Entity_Id) is
5744       B_Typ : constant Entity_Id := Base_Type (Typ);
5745       C     : Entity_Id;
5746
5747    begin
5748       --  Verify that the character does belong to the type of the context
5749
5750       Set_Etype (N, B_Typ);
5751       Eval_Character_Literal (N);
5752
5753       --  Wide_Wide_Character literals must always be defined, since the set
5754       --  of wide wide character literals is complete, i.e. if a character
5755       --  literal is accepted by the parser, then it is OK for wide wide
5756       --  character (out of range character literals are rejected).
5757
5758       if Root_Type (B_Typ) = Standard_Wide_Wide_Character then
5759          return;
5760
5761       --  Always accept character literal for type Any_Character, which
5762       --  occurs in error situations and in comparisons of literals, both
5763       --  of which should accept all literals.
5764
5765       elsif B_Typ = Any_Character then
5766          return;
5767
5768       --  For Standard.Character or a type derived from it, check that the
5769       --  literal is in range.
5770
5771       elsif Root_Type (B_Typ) = Standard_Character then
5772          if In_Character_Range (UI_To_CC (Char_Literal_Value (N))) then
5773             return;
5774          end if;
5775
5776       --  For Standard.Wide_Character or a type derived from it, check that the
5777       --  literal is in range.
5778
5779       elsif Root_Type (B_Typ) = Standard_Wide_Character then
5780          if In_Wide_Character_Range (UI_To_CC (Char_Literal_Value (N))) then
5781             return;
5782          end if;
5783
5784       --  For Standard.Wide_Wide_Character or a type derived from it, we
5785       --  know the literal is in range, since the parser checked!
5786
5787       elsif Root_Type (B_Typ) = Standard_Wide_Wide_Character then
5788          return;
5789
5790       --  If the entity is already set, this has already been resolved in a
5791       --  generic context, or comes from expansion. Nothing else to do.
5792
5793       elsif Present (Entity (N)) then
5794          return;
5795
5796       --  Otherwise we have a user defined character type, and we can use the
5797       --  standard visibility mechanisms to locate the referenced entity.
5798
5799       else
5800          C := Current_Entity (N);
5801          while Present (C) loop
5802             if Etype (C) = B_Typ then
5803                Set_Entity_With_Style_Check (N, C);
5804                Generate_Reference (C, N);
5805                return;
5806             end if;
5807
5808             C := Homonym (C);
5809          end loop;
5810       end if;
5811
5812       --  If we fall through, then the literal does not match any of the
5813       --  entries of the enumeration type. This isn't just a constraint error
5814       --  situation, it is an illegality (see RM 4.2).
5815
5816       Error_Msg_NE
5817         ("character not defined for }", N, First_Subtype (B_Typ));
5818    end Resolve_Character_Literal;
5819
5820    ---------------------------
5821    -- Resolve_Comparison_Op --
5822    ---------------------------
5823
5824    --  Context requires a boolean type, and plays no role in resolution.
5825    --  Processing identical to that for equality operators. The result type is
5826    --  the base type, which matters when pathological subtypes of booleans with
5827    --  limited ranges are used.
5828
5829    procedure Resolve_Comparison_Op (N : Node_Id; Typ : Entity_Id) is
5830       L : constant Node_Id := Left_Opnd (N);
5831       R : constant Node_Id := Right_Opnd (N);
5832       T : Entity_Id;
5833
5834    begin
5835       --  If this is an intrinsic operation which is not predefined, use the
5836       --  types of its declared arguments to resolve the possibly overloaded
5837       --  operands. Otherwise the operands are unambiguous and specify the
5838       --  expected type.
5839
5840       if Scope (Entity (N)) /= Standard_Standard then
5841          T := Etype (First_Entity (Entity (N)));
5842
5843       else
5844          T := Find_Unique_Type (L, R);
5845
5846          if T = Any_Fixed then
5847             T := Unique_Fixed_Point_Type (L);
5848          end if;
5849       end if;
5850
5851       Set_Etype (N, Base_Type (Typ));
5852       Generate_Reference (T, N, ' ');
5853
5854       --  Skip remaining processing if already set to Any_Type
5855
5856       if T = Any_Type then
5857          return;
5858       end if;
5859
5860       --  Deal with other error cases
5861
5862       if T = Any_String    or else
5863          T = Any_Composite or else
5864          T = Any_Character
5865       then
5866          if T = Any_Character then
5867             Ambiguous_Character (L);
5868          else
5869             Error_Msg_N ("ambiguous operands for comparison", N);
5870          end if;
5871
5872          Set_Etype (N, Any_Type);
5873          return;
5874       end if;
5875
5876       --  Resolve the operands if types OK
5877
5878       Resolve (L, T);
5879       Resolve (R, T);
5880       Check_Unset_Reference (L);
5881       Check_Unset_Reference (R);
5882       Generate_Operator_Reference (N, T);
5883       Check_Low_Bound_Tested (N);
5884
5885       --  In SPARK, ordering operators <, <=, >, >= are not defined for Boolean
5886       --  types or array types except String.
5887
5888       if Is_Boolean_Type (T) then
5889          Check_SPARK_Restriction
5890            ("comparison is not defined on Boolean type", N);
5891
5892       elsif Is_Array_Type (T)
5893         and then Base_Type (T) /= Standard_String
5894       then
5895          Check_SPARK_Restriction
5896            ("comparison is not defined on array types other than String", N);
5897       end if;
5898
5899       --  Check comparison on unordered enumeration
5900
5901       if Comes_From_Source (N)
5902         and then Bad_Unordered_Enumeration_Reference (N, Etype (L))
5903       then
5904          Error_Msg_N ("comparison on unordered enumeration type?", N);
5905       end if;
5906
5907       --  Evaluate the relation (note we do this after the above check since
5908       --  this Eval call may change N to True/False.
5909
5910       Eval_Relational_Op (N);
5911    end Resolve_Comparison_Op;
5912
5913    ------------------------------------
5914    -- Resolve_Conditional_Expression --
5915    ------------------------------------
5916
5917    procedure Resolve_Conditional_Expression (N : Node_Id; Typ : Entity_Id) is
5918       Condition : constant Node_Id := First (Expressions (N));
5919       Then_Expr : constant Node_Id := Next (Condition);
5920       Else_Expr : Node_Id          := Next (Then_Expr);
5921
5922    begin
5923       Resolve (Condition, Any_Boolean);
5924       Resolve (Then_Expr, Typ);
5925
5926       --  If ELSE expression present, just resolve using the determined type
5927
5928       if Present (Else_Expr) then
5929          Resolve (Else_Expr, Typ);
5930
5931       --  If no ELSE expression is present, root type must be Standard.Boolean
5932       --  and we provide a Standard.True result converted to the appropriate
5933       --  Boolean type (in case it is a derived boolean type).
5934
5935       elsif Root_Type (Typ) = Standard_Boolean then
5936          Else_Expr :=
5937            Convert_To (Typ, New_Occurrence_Of (Standard_True, Sloc (N)));
5938          Analyze_And_Resolve (Else_Expr, Typ);
5939          Append_To (Expressions (N), Else_Expr);
5940
5941       else
5942          Error_Msg_N ("can only omit ELSE expression in Boolean case", N);
5943          Append_To (Expressions (N), Error);
5944       end if;
5945
5946       Set_Etype (N, Typ);
5947       Eval_Conditional_Expression (N);
5948    end Resolve_Conditional_Expression;
5949
5950    -----------------------------------------
5951    -- Resolve_Discrete_Subtype_Indication --
5952    -----------------------------------------
5953
5954    procedure Resolve_Discrete_Subtype_Indication
5955      (N   : Node_Id;
5956       Typ : Entity_Id)
5957    is
5958       R : Node_Id;
5959       S : Entity_Id;
5960
5961    begin
5962       Analyze (Subtype_Mark (N));
5963       S := Entity (Subtype_Mark (N));
5964
5965       if Nkind (Constraint (N)) /= N_Range_Constraint then
5966          Error_Msg_N ("expect range constraint for discrete type", N);
5967          Set_Etype (N, Any_Type);
5968
5969       else
5970          R := Range_Expression (Constraint (N));
5971
5972          if R = Error then
5973             return;
5974          end if;
5975
5976          Analyze (R);
5977
5978          if Base_Type (S) /= Base_Type (Typ) then
5979             Error_Msg_NE
5980               ("expect subtype of }", N, First_Subtype (Typ));
5981
5982             --  Rewrite the constraint as a range of Typ
5983             --  to allow compilation to proceed further.
5984
5985             Set_Etype (N, Typ);
5986             Rewrite (Low_Bound (R),
5987               Make_Attribute_Reference (Sloc (Low_Bound (R)),
5988                 Prefix         => New_Occurrence_Of (Typ, Sloc (R)),
5989                 Attribute_Name => Name_First));
5990             Rewrite (High_Bound (R),
5991               Make_Attribute_Reference (Sloc (High_Bound (R)),
5992                 Prefix         => New_Occurrence_Of (Typ, Sloc (R)),
5993                 Attribute_Name => Name_First));
5994
5995          else
5996             Resolve (R, Typ);
5997             Set_Etype (N, Etype (R));
5998
5999             --  Additionally, we must check that the bounds are compatible
6000             --  with the given subtype, which might be different from the
6001             --  type of the context.
6002
6003             Apply_Range_Check (R, S);
6004
6005             --  ??? If the above check statically detects a Constraint_Error
6006             --  it replaces the offending bound(s) of the range R with a
6007             --  Constraint_Error node. When the itype which uses these bounds
6008             --  is frozen the resulting call to Duplicate_Subexpr generates
6009             --  a new temporary for the bounds.
6010
6011             --  Unfortunately there are other itypes that are also made depend
6012             --  on these bounds, so when Duplicate_Subexpr is called they get
6013             --  a forward reference to the newly created temporaries and Gigi
6014             --  aborts on such forward references. This is probably sign of a
6015             --  more fundamental problem somewhere else in either the order of
6016             --  itype freezing or the way certain itypes are constructed.
6017
6018             --  To get around this problem we call Remove_Side_Effects right
6019             --  away if either bounds of R are a Constraint_Error.
6020
6021             declare
6022                L : constant Node_Id := Low_Bound (R);
6023                H : constant Node_Id := High_Bound (R);
6024
6025             begin
6026                if Nkind (L) = N_Raise_Constraint_Error then
6027                   Remove_Side_Effects (L);
6028                end if;
6029
6030                if Nkind (H) = N_Raise_Constraint_Error then
6031                   Remove_Side_Effects (H);
6032                end if;
6033             end;
6034
6035             Check_Unset_Reference (Low_Bound  (R));
6036             Check_Unset_Reference (High_Bound (R));
6037          end if;
6038       end if;
6039    end Resolve_Discrete_Subtype_Indication;
6040
6041    -------------------------
6042    -- Resolve_Entity_Name --
6043    -------------------------
6044
6045    --  Used to resolve identifiers and expanded names
6046
6047    procedure Resolve_Entity_Name (N : Node_Id; Typ : Entity_Id) is
6048       E : constant Entity_Id := Entity (N);
6049
6050    begin
6051       --  If garbage from errors, set to Any_Type and return
6052
6053       if No (E) and then Total_Errors_Detected /= 0 then
6054          Set_Etype (N, Any_Type);
6055          return;
6056       end if;
6057
6058       --  Replace named numbers by corresponding literals. Note that this is
6059       --  the one case where Resolve_Entity_Name must reset the Etype, since
6060       --  it is currently marked as universal.
6061
6062       if Ekind (E) = E_Named_Integer then
6063          Set_Etype (N, Typ);
6064          Eval_Named_Integer (N);
6065
6066       elsif Ekind (E) = E_Named_Real then
6067          Set_Etype (N, Typ);
6068          Eval_Named_Real (N);
6069
6070       --  For enumeration literals, we need to make sure that a proper style
6071       --  check is done, since such literals are overloaded, and thus we did
6072       --  not do a style check during the first phase of analysis.
6073
6074       elsif Ekind (E) = E_Enumeration_Literal then
6075          Set_Entity_With_Style_Check (N, E);
6076          Eval_Entity_Name (N);
6077
6078       --  Case of subtype name appearing as an operand in expression
6079
6080       elsif Is_Type (E) then
6081
6082          --  Allow use of subtype if it is a concurrent type where we are
6083          --  currently inside the body. This will eventually be expanded into a
6084          --  call to Self (for tasks) or _object (for protected objects). Any
6085          --  other use of a subtype is invalid.
6086
6087          if Is_Concurrent_Type (E)
6088            and then In_Open_Scopes (E)
6089          then
6090             null;
6091
6092          --  Any other use is an error
6093
6094          else
6095             Error_Msg_N
6096                ("invalid use of subtype mark in expression or call", N);
6097          end if;
6098
6099       --  Check discriminant use if entity is discriminant in current scope,
6100       --  i.e. discriminant of record or concurrent type currently being
6101       --  analyzed. Uses in corresponding body are unrestricted.
6102
6103       elsif Ekind (E) = E_Discriminant
6104         and then Scope (E) = Current_Scope
6105         and then not Has_Completion (Current_Scope)
6106       then
6107          Check_Discriminant_Use (N);
6108
6109       --  A parameterless generic function cannot appear in a context that
6110       --  requires resolution.
6111
6112       elsif Ekind (E) = E_Generic_Function then
6113          Error_Msg_N ("illegal use of generic function", N);
6114
6115       elsif Ekind (E) = E_Out_Parameter
6116         and then Ada_Version = Ada_83
6117         and then (Nkind (Parent (N)) in N_Op
6118                    or else (Nkind (Parent (N)) = N_Assignment_Statement
6119                              and then N = Expression (Parent (N)))
6120                    or else Nkind (Parent (N)) = N_Explicit_Dereference)
6121       then
6122          Error_Msg_N ("(Ada 83) illegal reading of out parameter", N);
6123
6124       --  In all other cases, just do the possible static evaluation
6125
6126       else
6127          --  A deferred constant that appears in an expression must have a
6128          --  completion, unless it has been removed by in-place expansion of
6129          --  an aggregate.
6130
6131          if Ekind (E) = E_Constant
6132            and then Comes_From_Source (E)
6133            and then No (Constant_Value (E))
6134            and then Is_Frozen (Etype (E))
6135            and then not In_Spec_Expression
6136            and then not Is_Imported (E)
6137          then
6138             if No_Initialization (Parent (E))
6139               or else (Present (Full_View (E))
6140                         and then No_Initialization (Parent (Full_View (E))))
6141             then
6142                null;
6143             else
6144                Error_Msg_N (
6145                  "deferred constant is frozen before completion", N);
6146             end if;
6147          end if;
6148
6149          Eval_Entity_Name (N);
6150       end if;
6151    end Resolve_Entity_Name;
6152
6153    -------------------
6154    -- Resolve_Entry --
6155    -------------------
6156
6157    procedure Resolve_Entry (Entry_Name : Node_Id) is
6158       Loc    : constant Source_Ptr := Sloc (Entry_Name);
6159       Nam    : Entity_Id;
6160       New_N  : Node_Id;
6161       S      : Entity_Id;
6162       Tsk    : Entity_Id;
6163       E_Name : Node_Id;
6164       Index  : Node_Id;
6165
6166       function Actual_Index_Type (E : Entity_Id) return Entity_Id;
6167       --  If the bounds of the entry family being called depend on task
6168       --  discriminants, build a new index subtype where a discriminant is
6169       --  replaced with the value of the discriminant of the target task.
6170       --  The target task is the prefix of the entry name in the call.
6171
6172       -----------------------
6173       -- Actual_Index_Type --
6174       -----------------------
6175
6176       function Actual_Index_Type (E : Entity_Id) return Entity_Id is
6177          Typ   : constant Entity_Id := Entry_Index_Type (E);
6178          Tsk   : constant Entity_Id := Scope (E);
6179          Lo    : constant Node_Id   := Type_Low_Bound  (Typ);
6180          Hi    : constant Node_Id   := Type_High_Bound (Typ);
6181          New_T : Entity_Id;
6182
6183          function Actual_Discriminant_Ref (Bound : Node_Id) return Node_Id;
6184          --  If the bound is given by a discriminant, replace with a reference
6185          --  to the discriminant of the same name in the target task. If the
6186          --  entry name is the target of a requeue statement and the entry is
6187          --  in the current protected object, the bound to be used is the
6188          --  discriminal of the object (see Apply_Range_Checks for details of
6189          --  the transformation).
6190
6191          -----------------------------
6192          -- Actual_Discriminant_Ref --
6193          -----------------------------
6194
6195          function Actual_Discriminant_Ref (Bound : Node_Id) return Node_Id is
6196             Typ : constant Entity_Id := Etype (Bound);
6197             Ref : Node_Id;
6198
6199          begin
6200             Remove_Side_Effects (Bound);
6201
6202             if not Is_Entity_Name (Bound)
6203               or else Ekind (Entity (Bound)) /= E_Discriminant
6204             then
6205                return Bound;
6206
6207             elsif Is_Protected_Type (Tsk)
6208               and then In_Open_Scopes (Tsk)
6209               and then Nkind (Parent (Entry_Name)) = N_Requeue_Statement
6210             then
6211                --  Note: here Bound denotes a discriminant of the corresponding
6212                --  record type tskV, whose discriminal is a formal of the
6213                --  init-proc tskVIP. What we want is the body discriminal,
6214                --  which is associated to the discriminant of the original
6215                --  concurrent type tsk.
6216
6217                return New_Occurrence_Of
6218                         (Find_Body_Discriminal (Entity (Bound)), Loc);
6219
6220             else
6221                Ref :=
6222                  Make_Selected_Component (Loc,
6223                    Prefix => New_Copy_Tree (Prefix (Prefix (Entry_Name))),
6224                    Selector_Name => New_Occurrence_Of (Entity (Bound), Loc));
6225                Analyze (Ref);
6226                Resolve (Ref, Typ);
6227                return Ref;
6228             end if;
6229          end Actual_Discriminant_Ref;
6230
6231       --  Start of processing for Actual_Index_Type
6232
6233       begin
6234          if not Has_Discriminants (Tsk)
6235            or else (not Is_Entity_Name (Lo) and then not Is_Entity_Name (Hi))
6236          then
6237             return Entry_Index_Type (E);
6238
6239          else
6240             New_T := Create_Itype (Ekind (Typ), Parent (Entry_Name));
6241             Set_Etype        (New_T, Base_Type (Typ));
6242             Set_Size_Info    (New_T, Typ);
6243             Set_RM_Size      (New_T, RM_Size (Typ));
6244             Set_Scalar_Range (New_T,
6245               Make_Range (Sloc (Entry_Name),
6246                 Low_Bound  => Actual_Discriminant_Ref (Lo),
6247                 High_Bound => Actual_Discriminant_Ref (Hi)));
6248
6249             return New_T;
6250          end if;
6251       end Actual_Index_Type;
6252
6253    --  Start of processing of Resolve_Entry
6254
6255    begin
6256       --  Find name of entry being called, and resolve prefix of name with its
6257       --  own type. The prefix can be overloaded, and the name and signature of
6258       --  the entry must be taken into account.
6259
6260       if Nkind (Entry_Name) = N_Indexed_Component then
6261
6262          --  Case of dealing with entry family within the current tasks
6263
6264          E_Name := Prefix (Entry_Name);
6265
6266       else
6267          E_Name := Entry_Name;
6268       end if;
6269
6270       if Is_Entity_Name (E_Name) then
6271
6272          --  Entry call to an entry (or entry family) in the current task. This
6273          --  is legal even though the task will deadlock. Rewrite as call to
6274          --  current task.
6275
6276          --  This can also be a call to an entry in an enclosing task. If this
6277          --  is a single task, we have to retrieve its name, because the scope
6278          --  of the entry is the task type, not the object. If the enclosing
6279          --  task is a task type, the identity of the task is given by its own
6280          --  self variable.
6281
6282          --  Finally this can be a requeue on an entry of the same task or
6283          --  protected object.
6284
6285          S := Scope (Entity (E_Name));
6286
6287          for J in reverse 0 .. Scope_Stack.Last loop
6288             if Is_Task_Type (Scope_Stack.Table (J).Entity)
6289               and then not Comes_From_Source (S)
6290             then
6291                --  S is an enclosing task or protected object. The concurrent
6292                --  declaration has been converted into a type declaration, and
6293                --  the object itself has an object declaration that follows
6294                --  the type in the same declarative part.
6295
6296                Tsk := Next_Entity (S);
6297                while Etype (Tsk) /= S loop
6298                   Next_Entity (Tsk);
6299                end loop;
6300
6301                S := Tsk;
6302                exit;
6303
6304             elsif S = Scope_Stack.Table (J).Entity then
6305
6306                --  Call to current task. Will be transformed into call to Self
6307
6308                exit;
6309
6310             end if;
6311          end loop;
6312
6313          New_N :=
6314            Make_Selected_Component (Loc,
6315              Prefix => New_Occurrence_Of (S, Loc),
6316              Selector_Name =>
6317                New_Occurrence_Of (Entity (E_Name), Loc));
6318          Rewrite (E_Name, New_N);
6319          Analyze (E_Name);
6320
6321       elsif Nkind (Entry_Name) = N_Selected_Component
6322         and then Is_Overloaded (Prefix (Entry_Name))
6323       then
6324          --  Use the entry name (which must be unique at this point) to find
6325          --  the prefix that returns the corresponding task/protected type.
6326
6327          declare
6328             Pref : constant Node_Id := Prefix (Entry_Name);
6329             Ent  : constant Entity_Id :=  Entity (Selector_Name (Entry_Name));
6330             I    : Interp_Index;
6331             It   : Interp;
6332
6333          begin
6334             Get_First_Interp (Pref, I, It);
6335             while Present (It.Typ) loop
6336                if Scope (Ent) = It.Typ then
6337                   Set_Etype (Pref, It.Typ);
6338                   exit;
6339                end if;
6340
6341                Get_Next_Interp (I, It);
6342             end loop;
6343          end;
6344       end if;
6345
6346       if Nkind (Entry_Name) = N_Selected_Component then
6347          Resolve (Prefix (Entry_Name));
6348
6349       else pragma Assert (Nkind (Entry_Name) = N_Indexed_Component);
6350          Nam := Entity (Selector_Name (Prefix (Entry_Name)));
6351          Resolve (Prefix (Prefix (Entry_Name)));
6352          Index :=  First (Expressions (Entry_Name));
6353          Resolve (Index, Entry_Index_Type (Nam));
6354
6355          --  Up to this point the expression could have been the actual in a
6356          --  simple entry call, and be given by a named association.
6357
6358          if Nkind (Index) = N_Parameter_Association then
6359             Error_Msg_N ("expect expression for entry index", Index);
6360          else
6361             Apply_Range_Check (Index, Actual_Index_Type (Nam));
6362          end if;
6363       end if;
6364    end Resolve_Entry;
6365
6366    ------------------------
6367    -- Resolve_Entry_Call --
6368    ------------------------
6369
6370    procedure Resolve_Entry_Call (N : Node_Id; Typ : Entity_Id) is
6371       Entry_Name  : constant Node_Id    := Name (N);
6372       Loc         : constant Source_Ptr := Sloc (Entry_Name);
6373       Actuals     : List_Id;
6374       First_Named : Node_Id;
6375       Nam         : Entity_Id;
6376       Norm_OK     : Boolean;
6377       Obj         : Node_Id;
6378       Was_Over    : Boolean;
6379
6380    begin
6381       --  We kill all checks here, because it does not seem worth the effort to
6382       --  do anything better, an entry call is a big operation.
6383
6384       Kill_All_Checks;
6385
6386       --  Processing of the name is similar for entry calls and protected
6387       --  operation calls. Once the entity is determined, we can complete
6388       --  the resolution of the actuals.
6389
6390       --  The selector may be overloaded, in the case of a protected object
6391       --  with overloaded functions. The type of the context is used for
6392       --  resolution.
6393
6394       if Nkind (Entry_Name) = N_Selected_Component
6395         and then Is_Overloaded (Selector_Name (Entry_Name))
6396         and then Typ /= Standard_Void_Type
6397       then
6398          declare
6399             I  : Interp_Index;
6400             It : Interp;
6401
6402          begin
6403             Get_First_Interp (Selector_Name (Entry_Name), I, It);
6404             while Present (It.Typ) loop
6405                if Covers (Typ, It.Typ) then
6406                   Set_Entity (Selector_Name (Entry_Name), It.Nam);
6407                   Set_Etype  (Entry_Name, It.Typ);
6408
6409                   Generate_Reference (It.Typ, N, ' ');
6410                end if;
6411
6412                Get_Next_Interp (I, It);
6413             end loop;
6414          end;
6415       end if;
6416
6417       Resolve_Entry (Entry_Name);
6418
6419       if Nkind (Entry_Name) = N_Selected_Component then
6420
6421          --  Simple entry call
6422
6423          Nam := Entity (Selector_Name (Entry_Name));
6424          Obj := Prefix (Entry_Name);
6425          Was_Over := Is_Overloaded (Selector_Name (Entry_Name));
6426
6427       else pragma Assert (Nkind (Entry_Name) = N_Indexed_Component);
6428
6429          --  Call to member of entry family
6430
6431          Nam := Entity (Selector_Name (Prefix (Entry_Name)));
6432          Obj := Prefix (Prefix (Entry_Name));
6433          Was_Over := Is_Overloaded (Selector_Name (Prefix (Entry_Name)));
6434       end if;
6435
6436       --  We cannot in general check the maximum depth of protected entry calls
6437       --  at compile time. But we can tell that any protected entry call at all
6438       --  violates a specified nesting depth of zero.
6439
6440       if Is_Protected_Type (Scope (Nam)) then
6441          Check_Restriction (Max_Entry_Queue_Length, N);
6442       end if;
6443
6444       --  Use context type to disambiguate a protected function that can be
6445       --  called without actuals and that returns an array type, and where the
6446       --  argument list may be an indexing of the returned value.
6447
6448       if Ekind (Nam) = E_Function
6449         and then Needs_No_Actuals (Nam)
6450         and then Present (Parameter_Associations (N))
6451         and then
6452           ((Is_Array_Type (Etype (Nam))
6453              and then Covers (Typ, Component_Type (Etype (Nam))))
6454
6455             or else (Is_Access_Type (Etype (Nam))
6456                       and then Is_Array_Type (Designated_Type (Etype (Nam)))
6457                       and then
6458                         Covers
6459                          (Typ,
6460                           Component_Type (Designated_Type (Etype (Nam))))))
6461       then
6462          declare
6463             Index_Node : Node_Id;
6464
6465          begin
6466             Index_Node :=
6467               Make_Indexed_Component (Loc,
6468                 Prefix =>
6469                   Make_Function_Call (Loc, Name => Relocate_Node (Entry_Name)),
6470                 Expressions => Parameter_Associations (N));
6471
6472             --  Since we are correcting a node classification error made by the
6473             --  parser, we call Replace rather than Rewrite.
6474
6475             Replace (N, Index_Node);
6476             Set_Etype (Prefix (N), Etype (Nam));
6477             Set_Etype (N, Typ);
6478             Resolve_Indexed_Component (N, Typ);
6479             return;
6480          end;
6481       end if;
6482
6483       if Ekind_In (Nam, E_Entry, E_Entry_Family)
6484         and then Present (PPC_Wrapper (Nam))
6485         and then Current_Scope /= PPC_Wrapper (Nam)
6486       then
6487          --  Rewrite as call to the precondition wrapper, adding the task
6488          --  object to the list of actuals. If the call is to a member of an
6489          --  entry family, include the index as well.
6490
6491          declare
6492             New_Call    : Node_Id;
6493             New_Actuals : List_Id;
6494
6495          begin
6496             New_Actuals := New_List (Obj);
6497
6498             if  Nkind (Entry_Name) = N_Indexed_Component then
6499                Append_To (New_Actuals,
6500                  New_Copy_Tree (First (Expressions (Entry_Name))));
6501             end if;
6502
6503             Append_List (Parameter_Associations (N), New_Actuals);
6504             New_Call :=
6505               Make_Procedure_Call_Statement (Loc,
6506                 Name                   =>
6507                   New_Occurrence_Of (PPC_Wrapper (Nam), Loc),
6508                 Parameter_Associations => New_Actuals);
6509             Rewrite (N, New_Call);
6510             Analyze_And_Resolve (N);
6511             return;
6512          end;
6513       end if;
6514
6515       --  The operation name may have been overloaded. Order the actuals
6516       --  according to the formals of the resolved entity, and set the return
6517       --  type to that of the operation.
6518
6519       if Was_Over then
6520          Normalize_Actuals (N, Nam, False, Norm_OK);
6521          pragma Assert (Norm_OK);
6522          Set_Etype (N, Etype (Nam));
6523       end if;
6524
6525       Resolve_Actuals (N, Nam);
6526
6527       --  Create a call reference to the entry
6528
6529       Generate_Reference (Nam, Entry_Name, 's');
6530
6531       if Ekind_In (Nam, E_Entry, E_Entry_Family) then
6532          Check_Potentially_Blocking_Operation (N);
6533       end if;
6534
6535       --  Verify that a procedure call cannot masquerade as an entry
6536       --  call where an entry call is expected.
6537
6538       if Ekind (Nam) = E_Procedure then
6539          if Nkind (Parent (N)) = N_Entry_Call_Alternative
6540            and then N = Entry_Call_Statement (Parent (N))
6541          then
6542             Error_Msg_N ("entry call required in select statement", N);
6543
6544          elsif Nkind (Parent (N)) = N_Triggering_Alternative
6545            and then N = Triggering_Statement (Parent (N))
6546          then
6547             Error_Msg_N ("triggering statement cannot be procedure call", N);
6548
6549          elsif Ekind (Scope (Nam)) = E_Task_Type
6550            and then not In_Open_Scopes (Scope (Nam))
6551          then
6552             Error_Msg_N ("task has no entry with this name", Entry_Name);
6553          end if;
6554       end if;
6555
6556       --  After resolution, entry calls and protected procedure calls are
6557       --  changed into entry calls, for expansion. The structure of the node
6558       --  does not change, so it can safely be done in place. Protected
6559       --  function calls must keep their structure because they are
6560       --  subexpressions.
6561
6562       if Ekind (Nam) /= E_Function then
6563
6564          --  A protected operation that is not a function may modify the
6565          --  corresponding object, and cannot apply to a constant. If this
6566          --  is an internal call, the prefix is the type itself.
6567
6568          if Is_Protected_Type (Scope (Nam))
6569            and then not Is_Variable (Obj)
6570            and then (not Is_Entity_Name (Obj)
6571                        or else not Is_Type (Entity (Obj)))
6572          then
6573             Error_Msg_N
6574               ("prefix of protected procedure or entry call must be variable",
6575                Entry_Name);
6576          end if;
6577
6578          Actuals := Parameter_Associations (N);
6579          First_Named := First_Named_Actual (N);
6580
6581          Rewrite (N,
6582            Make_Entry_Call_Statement (Loc,
6583              Name                   => Entry_Name,
6584              Parameter_Associations => Actuals));
6585
6586          Set_First_Named_Actual (N, First_Named);
6587          Set_Analyzed (N, True);
6588
6589       --  Protected functions can return on the secondary stack, in which
6590       --  case we must trigger the transient scope mechanism.
6591
6592       elsif Expander_Active
6593         and then Requires_Transient_Scope (Etype (Nam))
6594       then
6595          Establish_Transient_Scope (N, Sec_Stack => True);
6596       end if;
6597    end Resolve_Entry_Call;
6598
6599    -------------------------
6600    -- Resolve_Equality_Op --
6601    -------------------------
6602
6603    --  Both arguments must have the same type, and the boolean context does
6604    --  not participate in the resolution. The first pass verifies that the
6605    --  interpretation is not ambiguous, and the type of the left argument is
6606    --  correctly set, or is Any_Type in case of ambiguity. If both arguments
6607    --  are strings or aggregates, allocators, or Null, they are ambiguous even
6608    --  though they carry a single (universal) type. Diagnose this case here.
6609
6610    procedure Resolve_Equality_Op (N : Node_Id; Typ : Entity_Id) is
6611       L : constant Node_Id   := Left_Opnd (N);
6612       R : constant Node_Id   := Right_Opnd (N);
6613       T : Entity_Id := Find_Unique_Type (L, R);
6614
6615       procedure Check_Conditional_Expression (Cond : Node_Id);
6616       --  The resolution rule for conditional expressions requires that each
6617       --  such must have a unique type. This means that if several dependent
6618       --  expressions are of a non-null anonymous access type, and the context
6619       --  does not impose an expected type (as can be the case in an equality
6620       --  operation) the expression must be rejected.
6621
6622       function Find_Unique_Access_Type return Entity_Id;
6623       --  In the case of allocators, make a last-ditch attempt to find a single
6624       --  access type with the right designated type. This is semantically
6625       --  dubious, and of no interest to any real code, but c48008a makes it
6626       --  all worthwhile.
6627
6628       ----------------------------------
6629       -- Check_Conditional_Expression --
6630       ----------------------------------
6631
6632       procedure Check_Conditional_Expression (Cond : Node_Id) is
6633          Then_Expr : Node_Id;
6634          Else_Expr : Node_Id;
6635
6636       begin
6637          if Nkind (Cond) = N_Conditional_Expression then
6638             Then_Expr := Next (First (Expressions (Cond)));
6639             Else_Expr := Next (Then_Expr);
6640
6641             if Nkind (Then_Expr) /= N_Null
6642               and then Nkind (Else_Expr) /= N_Null
6643             then
6644                Error_Msg_N
6645                  ("cannot determine type of conditional expression", Cond);
6646             end if;
6647          end if;
6648       end Check_Conditional_Expression;
6649
6650       -----------------------------
6651       -- Find_Unique_Access_Type --
6652       -----------------------------
6653
6654       function Find_Unique_Access_Type return Entity_Id is
6655          Acc : Entity_Id;
6656          E   : Entity_Id;
6657          S   : Entity_Id;
6658
6659       begin
6660          if Ekind (Etype (R)) =  E_Allocator_Type then
6661             Acc := Designated_Type (Etype (R));
6662          elsif Ekind (Etype (L)) =  E_Allocator_Type then
6663             Acc := Designated_Type (Etype (L));
6664          else
6665             return Empty;
6666          end if;
6667
6668          S := Current_Scope;
6669          while S /= Standard_Standard loop
6670             E := First_Entity (S);
6671             while Present (E) loop
6672                if Is_Type (E)
6673                  and then Is_Access_Type (E)
6674                  and then Ekind (E) /= E_Allocator_Type
6675                  and then Designated_Type (E) = Base_Type (Acc)
6676                then
6677                   return E;
6678                end if;
6679
6680                Next_Entity (E);
6681             end loop;
6682
6683             S := Scope (S);
6684          end loop;
6685
6686          return Empty;
6687       end Find_Unique_Access_Type;
6688
6689    --  Start of processing for Resolve_Equality_Op
6690
6691    begin
6692       Set_Etype (N, Base_Type (Typ));
6693       Generate_Reference (T, N, ' ');
6694
6695       if T = Any_Fixed then
6696          T := Unique_Fixed_Point_Type (L);
6697       end if;
6698
6699       if T /= Any_Type then
6700          if T = Any_String    or else
6701             T = Any_Composite or else
6702             T = Any_Character
6703          then
6704             if T = Any_Character then
6705                Ambiguous_Character (L);
6706             else
6707                Error_Msg_N ("ambiguous operands for equality", N);
6708             end if;
6709
6710             Set_Etype (N, Any_Type);
6711             return;
6712
6713          elsif T = Any_Access
6714            or else Ekind_In (T, E_Allocator_Type, E_Access_Attribute_Type)
6715          then
6716             T := Find_Unique_Access_Type;
6717
6718             if No (T) then
6719                Error_Msg_N ("ambiguous operands for equality", N);
6720                Set_Etype (N, Any_Type);
6721                return;
6722             end if;
6723
6724          --  Conditional expressions must have a single type, and if the
6725          --  context does not impose one the dependent expressions cannot
6726          --  be anonymous access types.
6727
6728          elsif Ada_Version >= Ada_2012
6729            and then Ekind_In (Etype (L), E_Anonymous_Access_Type,
6730                                          E_Anonymous_Access_Subprogram_Type)
6731            and then Ekind_In (Etype (R), E_Anonymous_Access_Type,
6732                                          E_Anonymous_Access_Subprogram_Type)
6733          then
6734             Check_Conditional_Expression (L);
6735             Check_Conditional_Expression (R);
6736          end if;
6737
6738          Resolve (L, T);
6739          Resolve (R, T);
6740
6741          --  In SPARK, equality operators = and /= for array types other than
6742          --  String are only defined when, for each index position, the
6743          --  operands have equal static bounds.
6744
6745          if Is_Array_Type (T) then
6746             --  Protect call to Matching_Static_Array_Bounds to avoid costly
6747             --  operation if not needed.
6748
6749             if Restriction_Check_Required (SPARK)
6750               and then Base_Type (T) /= Standard_String
6751               and then Base_Type (Etype (L)) = Base_Type (Etype (R))
6752               and then Etype (L) /= Any_Composite  --  or else L in error
6753               and then Etype (R) /= Any_Composite  --  or else R in error
6754               and then not Matching_Static_Array_Bounds (Etype (L), Etype (R))
6755             then
6756                Check_SPARK_Restriction
6757                  ("array types should have matching static bounds", N);
6758             end if;
6759          end if;
6760
6761          --  If the unique type is a class-wide type then it will be expanded
6762          --  into a dispatching call to the predefined primitive. Therefore we
6763          --  check here for potential violation of such restriction.
6764
6765          if Is_Class_Wide_Type (T) then
6766             Check_Restriction (No_Dispatching_Calls, N);
6767          end if;
6768
6769          if Warn_On_Redundant_Constructs
6770            and then Comes_From_Source (N)
6771            and then Is_Entity_Name (R)
6772            and then Entity (R) = Standard_True
6773            and then Comes_From_Source (R)
6774          then
6775             Error_Msg_N -- CODEFIX
6776               ("?comparison with True is redundant!", R);
6777          end if;
6778
6779          Check_Unset_Reference (L);
6780          Check_Unset_Reference (R);
6781          Generate_Operator_Reference (N, T);
6782          Check_Low_Bound_Tested (N);
6783
6784          --  If this is an inequality, it may be the implicit inequality
6785          --  created for a user-defined operation, in which case the corres-
6786          --  ponding equality operation is not intrinsic, and the operation
6787          --  cannot be constant-folded. Else fold.
6788
6789          if Nkind (N) = N_Op_Eq
6790            or else Comes_From_Source (Entity (N))
6791            or else Ekind (Entity (N)) = E_Operator
6792            or else Is_Intrinsic_Subprogram
6793                      (Corresponding_Equality (Entity (N)))
6794          then
6795             Eval_Relational_Op (N);
6796
6797          elsif Nkind (N) = N_Op_Ne
6798            and then Is_Abstract_Subprogram (Entity (N))
6799          then
6800             Error_Msg_NE ("cannot call abstract subprogram &!", N, Entity (N));
6801          end if;
6802
6803          --  Ada 2005: If one operand is an anonymous access type, convert the
6804          --  other operand to it, to ensure that the underlying types match in
6805          --  the back-end. Same for access_to_subprogram, and the conversion
6806          --  verifies that the types are subtype conformant.
6807
6808          --  We apply the same conversion in the case one of the operands is a
6809          --  private subtype of the type of the other.
6810
6811          --  Why the Expander_Active test here ???
6812
6813          if Expander_Active
6814            and then
6815              (Ekind_In (T, E_Anonymous_Access_Type,
6816                            E_Anonymous_Access_Subprogram_Type)
6817                or else Is_Private_Type (T))
6818          then
6819             if Etype (L) /= T then
6820                Rewrite (L,
6821                  Make_Unchecked_Type_Conversion (Sloc (L),
6822                    Subtype_Mark => New_Occurrence_Of (T, Sloc (L)),
6823                    Expression   => Relocate_Node (L)));
6824                Analyze_And_Resolve (L, T);
6825             end if;
6826
6827             if (Etype (R)) /= T then
6828                Rewrite (R,
6829                   Make_Unchecked_Type_Conversion (Sloc (R),
6830                     Subtype_Mark => New_Occurrence_Of (Etype (L), Sloc (R)),
6831                     Expression   => Relocate_Node (R)));
6832                Analyze_And_Resolve (R, T);
6833             end if;
6834          end if;
6835       end if;
6836    end Resolve_Equality_Op;
6837
6838    ----------------------------------
6839    -- Resolve_Explicit_Dereference --
6840    ----------------------------------
6841
6842    procedure Resolve_Explicit_Dereference (N : Node_Id; Typ : Entity_Id) is
6843       Loc   : constant Source_Ptr := Sloc (N);
6844       New_N : Node_Id;
6845       P     : constant Node_Id := Prefix (N);
6846       I     : Interp_Index;
6847       It    : Interp;
6848
6849    begin
6850       Check_Fully_Declared_Prefix (Typ, P);
6851
6852       if Is_Overloaded (P) then
6853
6854          --  Use the context type to select the prefix that has the correct
6855          --  designated type.
6856
6857          Get_First_Interp (P, I, It);
6858          while Present (It.Typ) loop
6859             exit when Is_Access_Type (It.Typ)
6860               and then Covers (Typ, Designated_Type (It.Typ));
6861             Get_Next_Interp (I, It);
6862          end loop;
6863
6864          if Present (It.Typ) then
6865             Resolve (P, It.Typ);
6866          else
6867             --  If no interpretation covers the designated type of the prefix,
6868             --  this is the pathological case where not all implementations of
6869             --  the prefix allow the interpretation of the node as a call. Now
6870             --  that the expected type is known, Remove other interpretations
6871             --  from prefix, rewrite it as a call, and resolve again, so that
6872             --  the proper call node is generated.
6873
6874             Get_First_Interp (P, I, It);
6875             while Present (It.Typ) loop
6876                if Ekind (It.Typ) /= E_Access_Subprogram_Type then
6877                   Remove_Interp (I);
6878                end if;
6879
6880                Get_Next_Interp (I, It);
6881             end loop;
6882
6883             New_N :=
6884               Make_Function_Call (Loc,
6885                 Name =>
6886                   Make_Explicit_Dereference (Loc,
6887                     Prefix => P),
6888                 Parameter_Associations => New_List);
6889
6890             Save_Interps (N, New_N);
6891             Rewrite (N, New_N);
6892             Analyze_And_Resolve (N, Typ);
6893             return;
6894          end if;
6895
6896          Set_Etype (N, Designated_Type (It.Typ));
6897
6898       else
6899          Resolve (P);
6900       end if;
6901
6902       if Is_Access_Type (Etype (P)) then
6903          Apply_Access_Check (N);
6904       end if;
6905
6906       --  If the designated type is a packed unconstrained array type, and the
6907       --  explicit dereference is not in the context of an attribute reference,
6908       --  then we must compute and set the actual subtype, since it is needed
6909       --  by Gigi. The reason we exclude the attribute case is that this is
6910       --  handled fine by Gigi, and in fact we use such attributes to build the
6911       --  actual subtype. We also exclude generated code (which builds actual
6912       --  subtypes directly if they are needed).
6913
6914       if Is_Array_Type (Etype (N))
6915         and then Is_Packed (Etype (N))
6916         and then not Is_Constrained (Etype (N))
6917         and then Nkind (Parent (N)) /= N_Attribute_Reference
6918         and then Comes_From_Source (N)
6919       then
6920          Set_Etype (N, Get_Actual_Subtype (N));
6921       end if;
6922
6923       --  Note: No Eval processing is required for an explicit dereference,
6924       --  because such a name can never be static.
6925
6926    end Resolve_Explicit_Dereference;
6927
6928    -------------------------------------
6929    -- Resolve_Expression_With_Actions --
6930    -------------------------------------
6931
6932    procedure Resolve_Expression_With_Actions (N : Node_Id; Typ : Entity_Id) is
6933    begin
6934       Set_Etype (N, Typ);
6935    end Resolve_Expression_With_Actions;
6936
6937    -------------------------------
6938    -- Resolve_Indexed_Component --
6939    -------------------------------
6940
6941    procedure Resolve_Indexed_Component (N : Node_Id; Typ : Entity_Id) is
6942       Name       : constant Node_Id := Prefix  (N);
6943       Expr       : Node_Id;
6944       Array_Type : Entity_Id := Empty; -- to prevent junk warning
6945       Index      : Node_Id;
6946
6947    begin
6948       if Is_Overloaded (Name) then
6949
6950          --  Use the context type to select the prefix that yields the correct
6951          --  component type.
6952
6953          declare
6954             I     : Interp_Index;
6955             It    : Interp;
6956             I1    : Interp_Index := 0;
6957             P     : constant Node_Id := Prefix (N);
6958             Found : Boolean := False;
6959
6960          begin
6961             Get_First_Interp (P, I, It);
6962             while Present (It.Typ) loop
6963                if (Is_Array_Type (It.Typ)
6964                      and then Covers (Typ, Component_Type (It.Typ)))
6965                  or else (Is_Access_Type (It.Typ)
6966                             and then Is_Array_Type (Designated_Type (It.Typ))
6967                             and then
6968                               Covers
6969                                 (Typ,
6970                                  Component_Type (Designated_Type (It.Typ))))
6971                then
6972                   if Found then
6973                      It := Disambiguate (P, I1, I, Any_Type);
6974
6975                      if It = No_Interp then
6976                         Error_Msg_N ("ambiguous prefix for indexing",  N);
6977                         Set_Etype (N, Typ);
6978                         return;
6979
6980                      else
6981                         Found := True;
6982                         Array_Type := It.Typ;
6983                         I1 := I;
6984                      end if;
6985
6986                   else
6987                      Found := True;
6988                      Array_Type := It.Typ;
6989                      I1 := I;
6990                   end if;
6991                end if;
6992
6993                Get_Next_Interp (I, It);
6994             end loop;
6995          end;
6996
6997       else
6998          Array_Type := Etype (Name);
6999       end if;
7000
7001       Resolve (Name, Array_Type);
7002       Array_Type := Get_Actual_Subtype_If_Available (Name);
7003
7004       --  If prefix is access type, dereference to get real array type.
7005       --  Note: we do not apply an access check because the expander always
7006       --  introduces an explicit dereference, and the check will happen there.
7007
7008       if Is_Access_Type (Array_Type) then
7009          Array_Type := Designated_Type (Array_Type);
7010       end if;
7011
7012       --  If name was overloaded, set component type correctly now
7013       --  If a misplaced call to an entry family (which has no index types)
7014       --  return. Error will be diagnosed from calling context.
7015
7016       if Is_Array_Type (Array_Type) then
7017          Set_Etype (N, Component_Type (Array_Type));
7018       else
7019          return;
7020       end if;
7021
7022       Index := First_Index (Array_Type);
7023       Expr  := First (Expressions (N));
7024
7025       --  The prefix may have resolved to a string literal, in which case its
7026       --  etype has a special representation. This is only possible currently
7027       --  if the prefix is a static concatenation, written in functional
7028       --  notation.
7029
7030       if Ekind (Array_Type) = E_String_Literal_Subtype then
7031          Resolve (Expr, Standard_Positive);
7032
7033       else
7034          while Present (Index) and Present (Expr) loop
7035             Resolve (Expr, Etype (Index));
7036             Check_Unset_Reference (Expr);
7037
7038             if Is_Scalar_Type (Etype (Expr)) then
7039                Apply_Scalar_Range_Check (Expr, Etype (Index));
7040             else
7041                Apply_Range_Check (Expr, Get_Actual_Subtype (Index));
7042             end if;
7043
7044             Next_Index (Index);
7045             Next (Expr);
7046          end loop;
7047       end if;
7048
7049       --  Do not generate the warning on suspicious index if we are analyzing
7050       --  package Ada.Tags; otherwise we will report the warning with the
7051       --  Prims_Ptr field of the dispatch table.
7052
7053       if Scope (Etype (Prefix (N))) = Standard_Standard
7054         or else not
7055           Is_RTU (Cunit_Entity (Get_Source_Unit (Etype (Prefix (N)))),
7056                   Ada_Tags)
7057       then
7058          Warn_On_Suspicious_Index (Name, First (Expressions (N)));
7059          Eval_Indexed_Component (N);
7060       end if;
7061
7062       --  If the array type is atomic, and is packed, and we are in a left side
7063       --  context, then this is worth a warning, since we have a situation
7064       --  where the access to the component may cause extra read/writes of
7065       --  the atomic array object, which could be considered unexpected.
7066
7067       if Nkind (N) = N_Indexed_Component
7068         and then (Is_Atomic (Array_Type)
7069                    or else (Is_Entity_Name (Prefix (N))
7070                              and then Is_Atomic (Entity (Prefix (N)))))
7071         and then Is_Bit_Packed_Array (Array_Type)
7072         and then Is_LHS (N)
7073       then
7074          Error_Msg_N ("?assignment to component of packed atomic array",
7075                       Prefix (N));
7076          Error_Msg_N ("?\may cause unexpected accesses to atomic object",
7077                       Prefix (N));
7078       end if;
7079    end Resolve_Indexed_Component;
7080
7081    -----------------------------
7082    -- Resolve_Integer_Literal --
7083    -----------------------------
7084
7085    procedure Resolve_Integer_Literal (N : Node_Id; Typ : Entity_Id) is
7086    begin
7087       Set_Etype (N, Typ);
7088       Eval_Integer_Literal (N);
7089    end Resolve_Integer_Literal;
7090
7091    --------------------------------
7092    -- Resolve_Intrinsic_Operator --
7093    --------------------------------
7094
7095    procedure Resolve_Intrinsic_Operator  (N : Node_Id; Typ : Entity_Id) is
7096       Btyp    : constant Entity_Id := Base_Type (Underlying_Type (Typ));
7097       Op      : Entity_Id;
7098       Orig_Op : constant Entity_Id := Entity (N);
7099       Arg1    : Node_Id;
7100       Arg2    : Node_Id;
7101
7102       function Convert_Operand (Opnd : Node_Id) return Node_Id;
7103       --  If the operand is a literal, it cannot be the expression in a
7104       --  conversion. Use a qualified expression instead.
7105
7106       function Convert_Operand (Opnd : Node_Id) return Node_Id is
7107          Loc : constant Source_Ptr := Sloc (Opnd);
7108          Res : Node_Id;
7109       begin
7110          if Nkind_In (Opnd, N_Integer_Literal, N_Real_Literal) then
7111             Res :=
7112               Make_Qualified_Expression (Loc,
7113                 Subtype_Mark => New_Occurrence_Of (Btyp, Loc),
7114                 Expression   => Relocate_Node (Opnd));
7115             Analyze (Res);
7116
7117          else
7118             Res := Unchecked_Convert_To (Btyp, Opnd);
7119          end if;
7120
7121          return Res;
7122       end Convert_Operand;
7123
7124    begin
7125       --  We must preserve the original entity in a generic setting, so that
7126       --  the legality of the operation can be verified in an instance.
7127
7128       if not Expander_Active then
7129          return;
7130       end if;
7131
7132       Op := Entity (N);
7133       while Scope (Op) /= Standard_Standard loop
7134          Op := Homonym (Op);
7135          pragma Assert (Present (Op));
7136       end loop;
7137
7138       Set_Entity (N, Op);
7139       Set_Is_Overloaded (N, False);
7140
7141       --  If the operand type is private, rewrite with suitable conversions on
7142       --  the operands and the result, to expose the proper underlying numeric
7143       --  type.
7144
7145       if Is_Private_Type (Typ) then
7146          Arg1 := Convert_Operand (Left_Opnd (N));
7147          --  Unchecked_Convert_To (Btyp, Left_Opnd  (N));
7148
7149          if Nkind (N) = N_Op_Expon then
7150             Arg2 := Unchecked_Convert_To (Standard_Integer, Right_Opnd (N));
7151          else
7152             Arg2 := Convert_Operand (Right_Opnd (N));
7153          end if;
7154
7155          if Nkind (Arg1) = N_Type_Conversion then
7156             Save_Interps (Left_Opnd (N),  Expression (Arg1));
7157          end if;
7158
7159          if Nkind (Arg2) = N_Type_Conversion then
7160             Save_Interps (Right_Opnd (N), Expression (Arg2));
7161          end if;
7162
7163          Set_Left_Opnd  (N, Arg1);
7164          Set_Right_Opnd (N, Arg2);
7165
7166          Set_Etype (N, Btyp);
7167          Rewrite (N, Unchecked_Convert_To (Typ, N));
7168          Resolve (N, Typ);
7169
7170       elsif Typ /= Etype (Left_Opnd (N))
7171         or else Typ /= Etype (Right_Opnd (N))
7172       then
7173          --  Add explicit conversion where needed, and save interpretations in
7174          --  case operands are overloaded. If the context is a VMS operation,
7175          --  assert that the conversion is legal (the operands have the proper
7176          --  types to select the VMS intrinsic). Note that in rare cases the
7177          --  VMS operators may be visible, but the default System is being used
7178          --  and Address is a private type.
7179
7180          Arg1 := Convert_To (Typ, Left_Opnd  (N));
7181          Arg2 := Convert_To (Typ, Right_Opnd (N));
7182
7183          if Nkind (Arg1) = N_Type_Conversion then
7184             Save_Interps (Left_Opnd (N), Expression (Arg1));
7185
7186             if Is_VMS_Operator (Orig_Op) then
7187                Set_Conversion_OK (Arg1);
7188             end if;
7189          else
7190             Save_Interps (Left_Opnd (N), Arg1);
7191          end if;
7192
7193          if Nkind (Arg2) = N_Type_Conversion then
7194             Save_Interps (Right_Opnd (N), Expression (Arg2));
7195
7196             if Is_VMS_Operator (Orig_Op) then
7197                Set_Conversion_OK (Arg2);
7198             end if;
7199          else
7200             Save_Interps (Right_Opnd (N), Arg2);
7201          end if;
7202
7203          Rewrite (Left_Opnd  (N), Arg1);
7204          Rewrite (Right_Opnd (N), Arg2);
7205          Analyze (Arg1);
7206          Analyze (Arg2);
7207          Resolve_Arithmetic_Op (N, Typ);
7208
7209       else
7210          Resolve_Arithmetic_Op (N, Typ);
7211       end if;
7212    end Resolve_Intrinsic_Operator;
7213
7214    --------------------------------------
7215    -- Resolve_Intrinsic_Unary_Operator --
7216    --------------------------------------
7217
7218    procedure Resolve_Intrinsic_Unary_Operator
7219      (N   : Node_Id;
7220       Typ : Entity_Id)
7221    is
7222       Btyp : constant Entity_Id := Base_Type (Underlying_Type (Typ));
7223       Op   : Entity_Id;
7224       Arg2 : Node_Id;
7225
7226    begin
7227       Op := Entity (N);
7228       while Scope (Op) /= Standard_Standard loop
7229          Op := Homonym (Op);
7230          pragma Assert (Present (Op));
7231       end loop;
7232
7233       Set_Entity (N, Op);
7234
7235       if Is_Private_Type (Typ) then
7236          Arg2 := Unchecked_Convert_To (Btyp, Right_Opnd (N));
7237          Save_Interps (Right_Opnd (N), Expression (Arg2));
7238
7239          Set_Right_Opnd (N, Arg2);
7240
7241          Set_Etype (N, Btyp);
7242          Rewrite (N, Unchecked_Convert_To (Typ, N));
7243          Resolve (N, Typ);
7244
7245       else
7246          Resolve_Unary_Op (N, Typ);
7247       end if;
7248    end Resolve_Intrinsic_Unary_Operator;
7249
7250    ------------------------
7251    -- Resolve_Logical_Op --
7252    ------------------------
7253
7254    procedure Resolve_Logical_Op (N : Node_Id; Typ : Entity_Id) is
7255       B_Typ : Entity_Id;
7256
7257    begin
7258       Check_No_Direct_Boolean_Operators (N);
7259
7260       --  Predefined operations on scalar types yield the base type. On the
7261       --  other hand, logical operations on arrays yield the type of the
7262       --  arguments (and the context).
7263
7264       if Is_Array_Type (Typ) then
7265          B_Typ := Typ;
7266       else
7267          B_Typ := Base_Type (Typ);
7268       end if;
7269
7270       --  OK if this is a VMS-specific intrinsic operation
7271
7272       if Is_VMS_Operator (Entity (N)) then
7273          null;
7274
7275       --  The following test is required because the operands of the operation
7276       --  may be literals, in which case the resulting type appears to be
7277       --  compatible with a signed integer type, when in fact it is compatible
7278       --  only with modular types. If the context itself is universal, the
7279       --  operation is illegal.
7280
7281       elsif not Valid_Boolean_Arg (Typ) then
7282          Error_Msg_N ("invalid context for logical operation", N);
7283          Set_Etype (N, Any_Type);
7284          return;
7285
7286       elsif Typ = Any_Modular then
7287          Error_Msg_N
7288            ("no modular type available in this context", N);
7289          Set_Etype (N, Any_Type);
7290          return;
7291
7292       elsif Is_Modular_Integer_Type (Typ)
7293         and then Etype (Left_Opnd (N)) = Universal_Integer
7294         and then Etype (Right_Opnd (N)) = Universal_Integer
7295       then
7296          Check_For_Visible_Operator (N, B_Typ);
7297       end if;
7298
7299       Resolve (Left_Opnd (N), B_Typ);
7300       Resolve (Right_Opnd (N), B_Typ);
7301
7302       Check_Unset_Reference (Left_Opnd  (N));
7303       Check_Unset_Reference (Right_Opnd (N));
7304
7305       Set_Etype (N, B_Typ);
7306       Generate_Operator_Reference (N, B_Typ);
7307       Eval_Logical_Op (N);
7308
7309       --  In SPARK, logical operations AND, OR and XOR for arrays are defined
7310       --  only when both operands have same static lower and higher bounds. Of
7311       --  course the types have to match, so only check if operands are
7312       --  compatible and the node itself has no errors.
7313
7314       if Is_Array_Type (B_Typ)
7315         and then Nkind (N) in N_Binary_Op
7316       then
7317          declare
7318             Left_Typ  : constant Node_Id := Etype (Left_Opnd (N));
7319             Right_Typ : constant Node_Id := Etype (Right_Opnd (N));
7320
7321          begin
7322             --  Protect call to Matching_Static_Array_Bounds to avoid costly
7323             --  operation if not needed.
7324
7325             if Restriction_Check_Required (SPARK)
7326               and then Base_Type (Left_Typ) = Base_Type (Right_Typ)
7327               and then Left_Typ /= Any_Composite  --  or Left_Opnd in error
7328               and then Right_Typ /= Any_Composite  --  or Right_Opnd in error
7329               and then not Matching_Static_Array_Bounds (Left_Typ, Right_Typ)
7330             then
7331                Check_SPARK_Restriction
7332                  ("array types should have matching static bounds", N);
7333             end if;
7334          end;
7335       end if;
7336    end Resolve_Logical_Op;
7337
7338    ---------------------------
7339    -- Resolve_Membership_Op --
7340    ---------------------------
7341
7342    --  The context can only be a boolean type, and does not determine the
7343    --  arguments. Arguments should be unambiguous, but the preference rule for
7344    --  universal types applies.
7345
7346    procedure Resolve_Membership_Op (N : Node_Id; Typ : Entity_Id) is
7347       pragma Warnings (Off, Typ);
7348
7349       L : constant Node_Id := Left_Opnd  (N);
7350       R : constant Node_Id := Right_Opnd (N);
7351       T : Entity_Id;
7352
7353       procedure Resolve_Set_Membership;
7354       --  Analysis has determined a unique type for the left operand. Use it to
7355       --  resolve the disjuncts.
7356
7357       ----------------------------
7358       -- Resolve_Set_Membership --
7359       ----------------------------
7360
7361       procedure Resolve_Set_Membership is
7362          Alt : Node_Id;
7363
7364       begin
7365          Resolve (L, Etype (L));
7366
7367          Alt := First (Alternatives (N));
7368          while Present (Alt) loop
7369
7370             --  Alternative is an expression, a range
7371             --  or a subtype mark.
7372
7373             if not Is_Entity_Name (Alt)
7374               or else not Is_Type (Entity (Alt))
7375             then
7376                Resolve (Alt, Etype (L));
7377             end if;
7378
7379             Next (Alt);
7380          end loop;
7381       end Resolve_Set_Membership;
7382
7383    --  Start of processing for Resolve_Membership_Op
7384
7385    begin
7386       if L = Error or else R = Error then
7387          return;
7388       end if;
7389
7390       if Present (Alternatives (N)) then
7391          Resolve_Set_Membership;
7392          return;
7393
7394       elsif not Is_Overloaded (R)
7395         and then
7396           (Etype (R) = Universal_Integer
7397              or else
7398            Etype (R) = Universal_Real)
7399         and then Is_Overloaded (L)
7400       then
7401          T := Etype (R);
7402
7403       --  Ada 2005 (AI-251): Support the following case:
7404
7405       --      type I is interface;
7406       --      type T is tagged ...
7407
7408       --      function Test (O : I'Class) is
7409       --      begin
7410       --         return O in T'Class.
7411       --      end Test;
7412
7413       --  In this case we have nothing else to do. The membership test will be
7414       --  done at run time.
7415
7416       elsif Ada_Version >= Ada_2005
7417         and then Is_Class_Wide_Type (Etype (L))
7418         and then Is_Interface (Etype (L))
7419         and then Is_Class_Wide_Type (Etype (R))
7420         and then not Is_Interface (Etype (R))
7421       then
7422          return;
7423       else
7424          T := Intersect_Types (L, R);
7425       end if;
7426
7427       --  If mixed-mode operations are present and operands are all literal,
7428       --  the only interpretation involves Duration, which is probably not
7429       --  the intention of the programmer.
7430
7431       if T = Any_Fixed then
7432          T := Unique_Fixed_Point_Type (N);
7433
7434          if T = Any_Type then
7435             return;
7436          end if;
7437       end if;
7438
7439       Resolve (L, T);
7440       Check_Unset_Reference (L);
7441
7442       if Nkind (R) = N_Range
7443         and then not Is_Scalar_Type (T)
7444       then
7445          Error_Msg_N ("scalar type required for range", R);
7446       end if;
7447
7448       if Is_Entity_Name (R) then
7449          Freeze_Expression (R);
7450       else
7451          Resolve (R, T);
7452          Check_Unset_Reference (R);
7453       end if;
7454
7455       Eval_Membership_Op (N);
7456    end Resolve_Membership_Op;
7457
7458    ------------------
7459    -- Resolve_Null --
7460    ------------------
7461
7462    procedure Resolve_Null (N : Node_Id; Typ : Entity_Id) is
7463       Loc : constant Source_Ptr := Sloc (N);
7464
7465    begin
7466       --  Handle restriction against anonymous null access values This
7467       --  restriction can be turned off using -gnatdj.
7468
7469       --  Ada 2005 (AI-231): Remove restriction
7470
7471       if Ada_Version < Ada_2005
7472         and then not Debug_Flag_J
7473         and then Ekind (Typ) = E_Anonymous_Access_Type
7474         and then Comes_From_Source (N)
7475       then
7476          --  In the common case of a call which uses an explicitly null value
7477          --  for an access parameter, give specialized error message.
7478
7479          if Nkind_In (Parent (N), N_Procedure_Call_Statement,
7480                                   N_Function_Call)
7481          then
7482             Error_Msg_N
7483               ("null is not allowed as argument for an access parameter", N);
7484
7485          --  Standard message for all other cases (are there any?)
7486
7487          else
7488             Error_Msg_N
7489               ("null cannot be of an anonymous access type", N);
7490          end if;
7491       end if;
7492
7493       --  Ada 2005 (AI-231): Generate the null-excluding check in case of
7494       --  assignment to a null-excluding object
7495
7496       if Ada_Version >= Ada_2005
7497         and then Can_Never_Be_Null (Typ)
7498         and then Nkind (Parent (N)) = N_Assignment_Statement
7499       then
7500          if not Inside_Init_Proc then
7501             Insert_Action
7502               (Compile_Time_Constraint_Error (N,
7503                  "(Ada 2005) null not allowed in null-excluding objects?"),
7504                Make_Raise_Constraint_Error (Loc,
7505                  Reason => CE_Access_Check_Failed));
7506          else
7507             Insert_Action (N,
7508               Make_Raise_Constraint_Error (Loc,
7509                 Reason => CE_Access_Check_Failed));
7510          end if;
7511       end if;
7512
7513       --  In a distributed context, null for a remote access to subprogram may
7514       --  need to be replaced with a special record aggregate. In this case,
7515       --  return after having done the transformation.
7516
7517       if (Ekind (Typ) = E_Record_Type
7518            or else Is_Remote_Access_To_Subprogram_Type (Typ))
7519         and then Remote_AST_Null_Value (N, Typ)
7520       then
7521          return;
7522       end if;
7523
7524       --  The null literal takes its type from the context
7525
7526       Set_Etype (N, Typ);
7527    end Resolve_Null;
7528
7529    -----------------------
7530    -- Resolve_Op_Concat --
7531    -----------------------
7532
7533    procedure Resolve_Op_Concat (N : Node_Id; Typ : Entity_Id) is
7534
7535       --  We wish to avoid deep recursion, because concatenations are often
7536       --  deeply nested, as in A&B&...&Z. Therefore, we walk down the left
7537       --  operands nonrecursively until we find something that is not a simple
7538       --  concatenation (A in this case). We resolve that, and then walk back
7539       --  up the tree following Parent pointers, calling Resolve_Op_Concat_Rest
7540       --  to do the rest of the work at each level. The Parent pointers allow
7541       --  us to avoid recursion, and thus avoid running out of memory. See also
7542       --  Sem_Ch4.Analyze_Concatenation, where a similar approach is used.
7543
7544       NN  : Node_Id := N;
7545       Op1 : Node_Id;
7546
7547    begin
7548       --  The following code is equivalent to:
7549
7550       --    Resolve_Op_Concat_First (NN, Typ);
7551       --    Resolve_Op_Concat_Arg (N, ...);
7552       --    Resolve_Op_Concat_Rest (N, Typ);
7553
7554       --  where the Resolve_Op_Concat_Arg call recurses back here if the left
7555       --  operand is a concatenation.
7556
7557       --  Walk down left operands
7558
7559       loop
7560          Resolve_Op_Concat_First (NN, Typ);
7561          Op1 := Left_Opnd (NN);
7562          exit when not (Nkind (Op1) = N_Op_Concat
7563                          and then not Is_Array_Type (Component_Type (Typ))
7564                          and then Entity (Op1) = Entity (NN));
7565          NN := Op1;
7566       end loop;
7567
7568       --  Now (given the above example) NN is A&B and Op1 is A
7569
7570       --  First resolve Op1 ...
7571
7572       Resolve_Op_Concat_Arg (NN, Op1, Typ, Is_Component_Left_Opnd  (NN));
7573
7574       --  ... then walk NN back up until we reach N (where we started), calling
7575       --  Resolve_Op_Concat_Rest along the way.
7576
7577       loop
7578          Resolve_Op_Concat_Rest (NN, Typ);
7579          exit when NN = N;
7580          NN := Parent (NN);
7581       end loop;
7582
7583       if Base_Type (Etype (N)) /= Standard_String then
7584          Check_SPARK_Restriction
7585            ("result of concatenation should have type String", N);
7586       end if;
7587    end Resolve_Op_Concat;
7588
7589    ---------------------------
7590    -- Resolve_Op_Concat_Arg --
7591    ---------------------------
7592
7593    procedure Resolve_Op_Concat_Arg
7594      (N       : Node_Id;
7595       Arg     : Node_Id;
7596       Typ     : Entity_Id;
7597       Is_Comp : Boolean)
7598    is
7599       Btyp : constant Entity_Id := Base_Type (Typ);
7600       Ctyp : constant Entity_Id := Component_Type (Typ);
7601
7602    begin
7603       if In_Instance then
7604          if Is_Comp
7605            or else (not Is_Overloaded (Arg)
7606                      and then Etype (Arg) /= Any_Composite
7607                      and then Covers (Ctyp, Etype (Arg)))
7608          then
7609             Resolve (Arg, Ctyp);
7610          else
7611             Resolve (Arg, Btyp);
7612          end if;
7613
7614       --  If both Array & Array and Array & Component are visible, there is a
7615       --  potential ambiguity that must be reported.
7616
7617       elsif Has_Compatible_Type (Arg, Ctyp) then
7618          if Nkind (Arg) = N_Aggregate
7619            and then Is_Composite_Type (Ctyp)
7620          then
7621             if Is_Private_Type (Ctyp) then
7622                Resolve (Arg, Btyp);
7623
7624             --  If the operation is user-defined and not overloaded use its
7625             --  profile. The operation may be a renaming, in which case it has
7626             --  been rewritten, and we want the original profile.
7627
7628             elsif not Is_Overloaded (N)
7629               and then Comes_From_Source (Entity (Original_Node (N)))
7630               and then Ekind (Entity (Original_Node (N))) = E_Function
7631             then
7632                Resolve (Arg,
7633                  Etype
7634                    (Next_Formal (First_Formal (Entity (Original_Node (N))))));
7635                return;
7636
7637             --  Otherwise an aggregate may match both the array type and the
7638             --  component type.
7639
7640             else
7641                Error_Msg_N ("ambiguous aggregate must be qualified", Arg);
7642                Set_Etype (Arg, Any_Type);
7643             end if;
7644
7645          else
7646             if Is_Overloaded (Arg)
7647               and then Has_Compatible_Type (Arg, Typ)
7648               and then Etype (Arg) /= Any_Type
7649             then
7650                declare
7651                   I    : Interp_Index;
7652                   It   : Interp;
7653                   Func : Entity_Id;
7654
7655                begin
7656                   Get_First_Interp (Arg, I, It);
7657                   Func := It.Nam;
7658                   Get_Next_Interp (I, It);
7659
7660                   --  Special-case the error message when the overloading is
7661                   --  caused by a function that yields an array and can be
7662                   --  called without parameters.
7663
7664                   if It.Nam = Func then
7665                      Error_Msg_Sloc := Sloc (Func);
7666                      Error_Msg_N ("ambiguous call to function#", Arg);
7667                      Error_Msg_NE
7668                        ("\\interpretation as call yields&", Arg, Typ);
7669                      Error_Msg_NE
7670                        ("\\interpretation as indexing of call yields&",
7671                          Arg, Component_Type (Typ));
7672
7673                   else
7674                      Error_Msg_N ("ambiguous operand for concatenation!", Arg);
7675
7676                      Get_First_Interp (Arg, I, It);
7677                      while Present (It.Nam) loop
7678                         Error_Msg_Sloc := Sloc (It.Nam);
7679
7680                         if Base_Type (It.Typ) = Btyp
7681                              or else
7682                            Base_Type (It.Typ) = Base_Type (Ctyp)
7683                         then
7684                            Error_Msg_N -- CODEFIX
7685                              ("\\possible interpretation#", Arg);
7686                         end if;
7687
7688                         Get_Next_Interp (I, It);
7689                      end loop;
7690                   end if;
7691                end;
7692             end if;
7693
7694             Resolve (Arg, Component_Type (Typ));
7695
7696             if Nkind (Arg) = N_String_Literal then
7697                Set_Etype (Arg, Component_Type (Typ));
7698             end if;
7699
7700             if Arg = Left_Opnd (N) then
7701                Set_Is_Component_Left_Opnd (N);
7702             else
7703                Set_Is_Component_Right_Opnd (N);
7704             end if;
7705          end if;
7706
7707       else
7708          Resolve (Arg, Btyp);
7709       end if;
7710
7711       --  Concatenation is restricted in SPARK: each operand must be either a
7712       --  string literal, the name of a string constant, a static character or
7713       --  string expression, or another concatenation. Arg cannot be a
7714       --  concatenation here as callers of Resolve_Op_Concat_Arg call it
7715       --  separately on each final operand, past concatenation operations.
7716
7717       if Is_Character_Type (Etype (Arg)) then
7718          if not Is_Static_Expression (Arg) then
7719             Check_SPARK_Restriction
7720               ("character operand for concatenation should be static", N);
7721          end if;
7722
7723       elsif Is_String_Type (Etype (Arg)) then
7724          if not (Nkind_In (Arg, N_Identifier, N_Expanded_Name)
7725                   and then Is_Constant_Object (Entity (Arg)))
7726            and then not Is_Static_Expression (Arg)
7727          then
7728             Check_SPARK_Restriction
7729               ("string operand for concatenation should be static", N);
7730          end if;
7731
7732       --  Do not issue error on an operand that is neither a character nor a
7733       --  string, as the error is issued in Resolve_Op_Concat.
7734
7735       else
7736          null;
7737       end if;
7738
7739       Check_Unset_Reference (Arg);
7740    end Resolve_Op_Concat_Arg;
7741
7742    -----------------------------
7743    -- Resolve_Op_Concat_First --
7744    -----------------------------
7745
7746    procedure Resolve_Op_Concat_First (N : Node_Id; Typ : Entity_Id) is
7747       Btyp : constant Entity_Id := Base_Type (Typ);
7748       Op1  : constant Node_Id := Left_Opnd (N);
7749       Op2  : constant Node_Id := Right_Opnd (N);
7750
7751    begin
7752       --  The parser folds an enormous sequence of concatenations of string
7753       --  literals into "" & "...", where the Is_Folded_In_Parser flag is set
7754       --  in the right operand. If the expression resolves to a predefined "&"
7755       --  operator, all is well. Otherwise, the parser's folding is wrong, so
7756       --  we give an error. See P_Simple_Expression in Par.Ch4.
7757
7758       if Nkind (Op2) = N_String_Literal
7759         and then Is_Folded_In_Parser (Op2)
7760         and then Ekind (Entity (N)) = E_Function
7761       then
7762          pragma Assert (Nkind (Op1) = N_String_Literal  --  should be ""
7763                and then String_Length (Strval (Op1)) = 0);
7764          Error_Msg_N ("too many user-defined concatenations", N);
7765          return;
7766       end if;
7767
7768       Set_Etype (N, Btyp);
7769
7770       if Is_Limited_Composite (Btyp) then
7771          Error_Msg_N ("concatenation not available for limited array", N);
7772          Explain_Limited_Type (Btyp, N);
7773       end if;
7774    end Resolve_Op_Concat_First;
7775
7776    ----------------------------
7777    -- Resolve_Op_Concat_Rest --
7778    ----------------------------
7779
7780    procedure Resolve_Op_Concat_Rest (N : Node_Id; Typ : Entity_Id) is
7781       Op1  : constant Node_Id := Left_Opnd (N);
7782       Op2  : constant Node_Id := Right_Opnd (N);
7783
7784    begin
7785       Resolve_Op_Concat_Arg (N, Op2, Typ, Is_Component_Right_Opnd  (N));
7786
7787       Generate_Operator_Reference (N, Typ);
7788
7789       if Is_String_Type (Typ) then
7790          Eval_Concatenation (N);
7791       end if;
7792
7793       --  If this is not a static concatenation, but the result is a string
7794       --  type (and not an array of strings) ensure that static string operands
7795       --  have their subtypes properly constructed.
7796
7797       if Nkind (N) /= N_String_Literal
7798         and then Is_Character_Type (Component_Type (Typ))
7799       then
7800          Set_String_Literal_Subtype (Op1, Typ);
7801          Set_String_Literal_Subtype (Op2, Typ);
7802       end if;
7803    end Resolve_Op_Concat_Rest;
7804
7805    ----------------------
7806    -- Resolve_Op_Expon --
7807    ----------------------
7808
7809    procedure Resolve_Op_Expon (N : Node_Id; Typ : Entity_Id) is
7810       B_Typ : constant Entity_Id := Base_Type (Typ);
7811
7812    begin
7813       --  Catch attempts to do fixed-point exponentiation with universal
7814       --  operands, which is a case where the illegality is not caught during
7815       --  normal operator analysis.
7816
7817       if Is_Fixed_Point_Type (Typ) and then Comes_From_Source (N) then
7818          Error_Msg_N ("exponentiation not available for fixed point", N);
7819          return;
7820       end if;
7821
7822       if Comes_From_Source (N)
7823         and then Ekind (Entity (N)) = E_Function
7824         and then Is_Imported (Entity (N))
7825         and then Is_Intrinsic_Subprogram (Entity (N))
7826       then
7827          Resolve_Intrinsic_Operator (N, Typ);
7828          return;
7829       end if;
7830
7831       if Etype (Left_Opnd (N)) = Universal_Integer
7832         or else Etype (Left_Opnd (N)) = Universal_Real
7833       then
7834          Check_For_Visible_Operator (N, B_Typ);
7835       end if;
7836
7837       --  We do the resolution using the base type, because intermediate values
7838       --  in expressions always are of the base type, not a subtype of it.
7839
7840       Resolve (Left_Opnd (N), B_Typ);
7841       Resolve (Right_Opnd (N), Standard_Integer);
7842
7843       Check_Unset_Reference (Left_Opnd  (N));
7844       Check_Unset_Reference (Right_Opnd (N));
7845
7846       Set_Etype (N, B_Typ);
7847       Generate_Operator_Reference (N, B_Typ);
7848       Eval_Op_Expon (N);
7849
7850       --  Set overflow checking bit. Much cleverer code needed here eventually
7851       --  and perhaps the Resolve routines should be separated for the various
7852       --  arithmetic operations, since they will need different processing. ???
7853
7854       if Nkind (N) in N_Op then
7855          if not Overflow_Checks_Suppressed (Etype (N)) then
7856             Enable_Overflow_Check (N);
7857          end if;
7858       end if;
7859    end Resolve_Op_Expon;
7860
7861    --------------------
7862    -- Resolve_Op_Not --
7863    --------------------
7864
7865    procedure Resolve_Op_Not (N : Node_Id; Typ : Entity_Id) is
7866       B_Typ : Entity_Id;
7867
7868       function Parent_Is_Boolean return Boolean;
7869       --  This function determines if the parent node is a boolean operator or
7870       --  operation (comparison op, membership test, or short circuit form) and
7871       --  the not in question is the left operand of this operation. Note that
7872       --  if the not is in parens, then false is returned.
7873
7874       -----------------------
7875       -- Parent_Is_Boolean --
7876       -----------------------
7877
7878       function Parent_Is_Boolean return Boolean is
7879       begin
7880          if Paren_Count (N) /= 0 then
7881             return False;
7882
7883          else
7884             case Nkind (Parent (N)) is
7885                when N_Op_And   |
7886                     N_Op_Eq    |
7887                     N_Op_Ge    |
7888                     N_Op_Gt    |
7889                     N_Op_Le    |
7890                     N_Op_Lt    |
7891                     N_Op_Ne    |
7892                     N_Op_Or    |
7893                     N_Op_Xor   |
7894                     N_In       |
7895                     N_Not_In   |
7896                     N_And_Then |
7897                     N_Or_Else  =>
7898
7899                   return Left_Opnd (Parent (N)) = N;
7900
7901                when others =>
7902                   return False;
7903             end case;
7904          end if;
7905       end Parent_Is_Boolean;
7906
7907    --  Start of processing for Resolve_Op_Not
7908
7909    begin
7910       --  Predefined operations on scalar types yield the base type. On the
7911       --  other hand, logical operations on arrays yield the type of the
7912       --  arguments (and the context).
7913
7914       if Is_Array_Type (Typ) then
7915          B_Typ := Typ;
7916       else
7917          B_Typ := Base_Type (Typ);
7918       end if;
7919
7920       if Is_VMS_Operator (Entity (N)) then
7921          null;
7922
7923       --  Straightforward case of incorrect arguments
7924
7925       elsif not Valid_Boolean_Arg (Typ) then
7926          Error_Msg_N ("invalid operand type for operator&", N);
7927          Set_Etype (N, Any_Type);
7928          return;
7929
7930       --  Special case of probable missing parens
7931
7932       elsif Typ = Universal_Integer or else Typ = Any_Modular then
7933          if Parent_Is_Boolean then
7934             Error_Msg_N
7935               ("operand of not must be enclosed in parentheses",
7936                Right_Opnd (N));
7937          else
7938             Error_Msg_N
7939               ("no modular type available in this context", N);
7940          end if;
7941
7942          Set_Etype (N, Any_Type);
7943          return;
7944
7945       --  OK resolution of NOT
7946
7947       else
7948          --  Warn if non-boolean types involved. This is a case like not a < b
7949          --  where a and b are modular, where we will get (not a) < b and most
7950          --  likely not (a < b) was intended.
7951
7952          if Warn_On_Questionable_Missing_Parens
7953            and then not Is_Boolean_Type (Typ)
7954            and then Parent_Is_Boolean
7955          then
7956             Error_Msg_N ("?not expression should be parenthesized here!", N);
7957          end if;
7958
7959          --  Warn on double negation if checking redundant constructs
7960
7961          if Warn_On_Redundant_Constructs
7962            and then Comes_From_Source (N)
7963            and then Comes_From_Source (Right_Opnd (N))
7964            and then Root_Type (Typ) = Standard_Boolean
7965            and then Nkind (Right_Opnd (N)) = N_Op_Not
7966          then
7967             Error_Msg_N ("redundant double negation?", N);
7968          end if;
7969
7970          --  Complete resolution and evaluation of NOT
7971
7972          Resolve (Right_Opnd (N), B_Typ);
7973          Check_Unset_Reference (Right_Opnd (N));
7974          Set_Etype (N, B_Typ);
7975          Generate_Operator_Reference (N, B_Typ);
7976          Eval_Op_Not (N);
7977       end if;
7978    end Resolve_Op_Not;
7979
7980    -----------------------------
7981    -- Resolve_Operator_Symbol --
7982    -----------------------------
7983
7984    --  Nothing to be done, all resolved already
7985
7986    procedure Resolve_Operator_Symbol (N : Node_Id; Typ : Entity_Id) is
7987       pragma Warnings (Off, N);
7988       pragma Warnings (Off, Typ);
7989
7990    begin
7991       null;
7992    end Resolve_Operator_Symbol;
7993
7994    ----------------------------------
7995    -- Resolve_Qualified_Expression --
7996    ----------------------------------
7997
7998    procedure Resolve_Qualified_Expression (N : Node_Id; Typ : Entity_Id) is
7999       pragma Warnings (Off, Typ);
8000
8001       Target_Typ : constant Entity_Id := Entity (Subtype_Mark (N));
8002       Expr       : constant Node_Id   := Expression (N);
8003
8004    begin
8005       Resolve (Expr, Target_Typ);
8006
8007       --  Protect call to Matching_Static_Array_Bounds to avoid costly
8008       --  operation if not needed.
8009
8010       if Restriction_Check_Required (SPARK)
8011         and then Is_Array_Type (Target_Typ)
8012         and then Is_Array_Type (Etype (Expr))
8013         and then Etype (Expr) /= Any_Composite  --  or else Expr in error
8014         and then not Matching_Static_Array_Bounds (Target_Typ, Etype (Expr))
8015       then
8016          Check_SPARK_Restriction
8017            ("array types should have matching static bounds", N);
8018       end if;
8019
8020       --  A qualified expression requires an exact match of the type, class-
8021       --  wide matching is not allowed. However, if the qualifying type is
8022       --  specific and the expression has a class-wide type, it may still be
8023       --  okay, since it can be the result of the expansion of a call to a
8024       --  dispatching function, so we also have to check class-wideness of the
8025       --  type of the expression's original node.
8026
8027       if (Is_Class_Wide_Type (Target_Typ)
8028            or else
8029              (Is_Class_Wide_Type (Etype (Expr))
8030                and then Is_Class_Wide_Type (Etype (Original_Node (Expr)))))
8031         and then Base_Type (Etype (Expr)) /= Base_Type (Target_Typ)
8032       then
8033          Wrong_Type (Expr, Target_Typ);
8034       end if;
8035
8036       --  If the target type is unconstrained, then we reset the type of the
8037       --  result from the type of the expression. For other cases, the actual
8038       --  subtype of the expression is the target type.
8039
8040       if Is_Composite_Type (Target_Typ)
8041         and then not Is_Constrained (Target_Typ)
8042       then
8043          Set_Etype (N, Etype (Expr));
8044       end if;
8045
8046       Eval_Qualified_Expression (N);
8047    end Resolve_Qualified_Expression;
8048
8049    -----------------------------------
8050    -- Resolve_Quantified_Expression --
8051    -----------------------------------
8052
8053    procedure Resolve_Quantified_Expression (N : Node_Id; Typ : Entity_Id) is
8054    begin
8055       --  The loop structure is already resolved during its analysis, only the
8056       --  resolution of the condition needs to be done. Expansion is disabled
8057       --  so that checks and other generated code are inserted in the tree
8058       --  after expression has been rewritten as a loop.
8059
8060       Expander_Mode_Save_And_Set (False);
8061       Resolve (Condition (N), Typ);
8062       Expander_Mode_Restore;
8063    end Resolve_Quantified_Expression;
8064
8065    -------------------
8066    -- Resolve_Range --
8067    -------------------
8068
8069    procedure Resolve_Range (N : Node_Id; Typ : Entity_Id) is
8070       L : constant Node_Id := Low_Bound (N);
8071       H : constant Node_Id := High_Bound (N);
8072
8073       function First_Last_Ref return Boolean;
8074       --  Returns True if N is of the form X'First .. X'Last where X is the
8075       --  same entity for both attributes.
8076
8077       --------------------
8078       -- First_Last_Ref --
8079       --------------------
8080
8081       function First_Last_Ref return Boolean is
8082          Lorig : constant Node_Id := Original_Node (L);
8083          Horig : constant Node_Id := Original_Node (H);
8084
8085       begin
8086          if Nkind (Lorig) = N_Attribute_Reference
8087            and then Nkind (Horig) = N_Attribute_Reference
8088            and then Attribute_Name (Lorig) = Name_First
8089            and then Attribute_Name (Horig) = Name_Last
8090          then
8091             declare
8092                PL : constant Node_Id := Prefix (Lorig);
8093                PH : constant Node_Id := Prefix (Horig);
8094             begin
8095                if Is_Entity_Name (PL)
8096                  and then Is_Entity_Name (PH)
8097                  and then Entity (PL) = Entity (PH)
8098                then
8099                   return True;
8100                end if;
8101             end;
8102          end if;
8103
8104          return False;
8105       end First_Last_Ref;
8106
8107    --  Start of processing for Resolve_Range
8108
8109    begin
8110       Set_Etype (N, Typ);
8111       Resolve (L, Typ);
8112       Resolve (H, Typ);
8113
8114       --  Check for inappropriate range on unordered enumeration type
8115
8116       if Bad_Unordered_Enumeration_Reference (N, Typ)
8117
8118         --  Exclude X'First .. X'Last if X is the same entity for both
8119
8120         and then not First_Last_Ref
8121       then
8122          Error_Msg ("subrange of unordered enumeration type?", Sloc (N));
8123       end if;
8124
8125       Check_Unset_Reference (L);
8126       Check_Unset_Reference (H);
8127
8128       --  We have to check the bounds for being within the base range as
8129       --  required for a non-static context. Normally this is automatic and
8130       --  done as part of evaluating expressions, but the N_Range node is an
8131       --  exception, since in GNAT we consider this node to be a subexpression,
8132       --  even though in Ada it is not. The circuit in Sem_Eval could check for
8133       --  this, but that would put the test on the main evaluation path for
8134       --  expressions.
8135
8136       Check_Non_Static_Context (L);
8137       Check_Non_Static_Context (H);
8138
8139       --  Check for an ambiguous range over character literals. This will
8140       --  happen with a membership test involving only literals.
8141
8142       if Typ = Any_Character then
8143          Ambiguous_Character (L);
8144          Set_Etype (N, Any_Type);
8145          return;
8146       end if;
8147
8148       --  If bounds are static, constant-fold them, so size computations are
8149       --  identical between front-end and back-end. Do not perform this
8150       --  transformation while analyzing generic units, as type information
8151       --  would be lost when reanalyzing the constant node in the instance.
8152
8153       if Is_Discrete_Type (Typ) and then Expander_Active then
8154          if Is_OK_Static_Expression (L) then
8155             Fold_Uint  (L, Expr_Value (L), Is_Static_Expression (L));
8156          end if;
8157
8158          if Is_OK_Static_Expression (H) then
8159             Fold_Uint  (H, Expr_Value (H), Is_Static_Expression (H));
8160          end if;
8161       end if;
8162    end Resolve_Range;
8163
8164    --------------------------
8165    -- Resolve_Real_Literal --
8166    --------------------------
8167
8168    procedure Resolve_Real_Literal (N : Node_Id; Typ : Entity_Id) is
8169       Actual_Typ : constant Entity_Id := Etype (N);
8170
8171    begin
8172       --  Special processing for fixed-point literals to make sure that the
8173       --  value is an exact multiple of small where this is required. We skip
8174       --  this for the universal real case, and also for generic types.
8175
8176       if Is_Fixed_Point_Type (Typ)
8177         and then Typ /= Universal_Fixed
8178         and then Typ /= Any_Fixed
8179         and then not Is_Generic_Type (Typ)
8180       then
8181          declare
8182             Val   : constant Ureal := Realval (N);
8183             Cintr : constant Ureal := Val / Small_Value (Typ);
8184             Cint  : constant Uint  := UR_Trunc (Cintr);
8185             Den   : constant Uint  := Norm_Den (Cintr);
8186             Stat  : Boolean;
8187
8188          begin
8189             --  Case of literal is not an exact multiple of the Small
8190
8191             if Den /= 1 then
8192
8193                --  For a source program literal for a decimal fixed-point type,
8194                --  this is statically illegal (RM 4.9(36)).
8195
8196                if Is_Decimal_Fixed_Point_Type (Typ)
8197                  and then Actual_Typ = Universal_Real
8198                  and then Comes_From_Source (N)
8199                then
8200                   Error_Msg_N ("value has extraneous low order digits", N);
8201                end if;
8202
8203                --  Generate a warning if literal from source
8204
8205                if Is_Static_Expression (N)
8206                  and then Warn_On_Bad_Fixed_Value
8207                then
8208                   Error_Msg_N
8209                     ("?static fixed-point value is not a multiple of Small!",
8210                      N);
8211                end if;
8212
8213                --  Replace literal by a value that is the exact representation
8214                --  of a value of the type, i.e. a multiple of the small value,
8215                --  by truncation, since Machine_Rounds is false for all GNAT
8216                --  fixed-point types (RM 4.9(38)).
8217
8218                Stat := Is_Static_Expression (N);
8219                Rewrite (N,
8220                  Make_Real_Literal (Sloc (N),
8221                    Realval => Small_Value (Typ) * Cint));
8222
8223                Set_Is_Static_Expression (N, Stat);
8224             end if;
8225
8226             --  In all cases, set the corresponding integer field
8227
8228             Set_Corresponding_Integer_Value (N, Cint);
8229          end;
8230       end if;
8231
8232       --  Now replace the actual type by the expected type as usual
8233
8234       Set_Etype (N, Typ);
8235       Eval_Real_Literal (N);
8236    end Resolve_Real_Literal;
8237
8238    -----------------------
8239    -- Resolve_Reference --
8240    -----------------------
8241
8242    procedure Resolve_Reference (N : Node_Id; Typ : Entity_Id) is
8243       P : constant Node_Id := Prefix (N);
8244
8245    begin
8246       --  Replace general access with specific type
8247
8248       if Ekind (Etype (N)) = E_Allocator_Type then
8249          Set_Etype (N, Base_Type (Typ));
8250       end if;
8251
8252       Resolve (P, Designated_Type (Etype (N)));
8253
8254       --  If we are taking the reference of a volatile entity, then treat it as
8255       --  a potential modification of this entity. This is too conservative,
8256       --  but necessary because remove side effects can cause transformations
8257       --  of normal assignments into reference sequences that otherwise fail to
8258       --  notice the modification.
8259
8260       if Is_Entity_Name (P) and then Treat_As_Volatile (Entity (P)) then
8261          Note_Possible_Modification (P, Sure => False);
8262       end if;
8263    end Resolve_Reference;
8264
8265    --------------------------------
8266    -- Resolve_Selected_Component --
8267    --------------------------------
8268
8269    procedure Resolve_Selected_Component (N : Node_Id; Typ : Entity_Id) is
8270       Comp  : Entity_Id;
8271       Comp1 : Entity_Id        := Empty; -- prevent junk warning
8272       P     : constant Node_Id := Prefix  (N);
8273       S     : constant Node_Id := Selector_Name (N);
8274       T     : Entity_Id        := Etype (P);
8275       I     : Interp_Index;
8276       I1    : Interp_Index := 0; -- prevent junk warning
8277       It    : Interp;
8278       It1   : Interp;
8279       Found : Boolean;
8280
8281       function Init_Component return Boolean;
8282       --  Check whether this is the initialization of a component within an
8283       --  init proc (by assignment or call to another init proc). If true,
8284       --  there is no need for a discriminant check.
8285
8286       --------------------
8287       -- Init_Component --
8288       --------------------
8289
8290       function Init_Component return Boolean is
8291       begin
8292          return Inside_Init_Proc
8293            and then Nkind (Prefix (N)) = N_Identifier
8294            and then Chars (Prefix (N)) = Name_uInit
8295            and then Nkind (Parent (Parent (N))) = N_Case_Statement_Alternative;
8296       end Init_Component;
8297
8298    --  Start of processing for Resolve_Selected_Component
8299
8300    begin
8301       if Is_Overloaded (P) then
8302
8303          --  Use the context type to select the prefix that has a selector
8304          --  of the correct name and type.
8305
8306          Found := False;
8307          Get_First_Interp (P, I, It);
8308
8309          Search : while Present (It.Typ) loop
8310             if Is_Access_Type (It.Typ) then
8311                T := Designated_Type (It.Typ);
8312             else
8313                T := It.Typ;
8314             end if;
8315
8316             --  Locate selected component. For a private prefix the selector
8317             --  can denote a discriminant.
8318
8319             if Is_Record_Type (T) or else Is_Private_Type (T) then
8320
8321                --  The visible components of a class-wide type are those of
8322                --  the root type.
8323
8324                if Is_Class_Wide_Type (T) then
8325                   T := Etype (T);
8326                end if;
8327
8328                Comp := First_Entity (T);
8329                while Present (Comp) loop
8330                   if Chars (Comp) = Chars (S)
8331                     and then Covers (Etype (Comp), Typ)
8332                   then
8333                      if not Found then
8334                         Found := True;
8335                         I1  := I;
8336                         It1 := It;
8337                         Comp1 := Comp;
8338
8339                      else
8340                         It := Disambiguate (P, I1, I, Any_Type);
8341
8342                         if It = No_Interp then
8343                            Error_Msg_N
8344                              ("ambiguous prefix for selected component",  N);
8345                            Set_Etype (N, Typ);
8346                            return;
8347
8348                         else
8349                            It1 := It;
8350
8351                            --  There may be an implicit dereference. Retrieve
8352                            --  designated record type.
8353
8354                            if Is_Access_Type (It1.Typ) then
8355                               T := Designated_Type (It1.Typ);
8356                            else
8357                               T := It1.Typ;
8358                            end if;
8359
8360                            if Scope (Comp1) /= T then
8361
8362                               --  Resolution chooses the new interpretation.
8363                               --  Find the component with the right name.
8364
8365                               Comp1 := First_Entity (T);
8366                               while Present (Comp1)
8367                                 and then Chars (Comp1) /= Chars (S)
8368                               loop
8369                                  Comp1 := Next_Entity (Comp1);
8370                               end loop;
8371                            end if;
8372
8373                            exit Search;
8374                         end if;
8375                      end if;
8376                   end if;
8377
8378                   Comp := Next_Entity (Comp);
8379                end loop;
8380             end if;
8381
8382             Get_Next_Interp (I, It);
8383          end loop Search;
8384
8385          Resolve (P, It1.Typ);
8386          Set_Etype (N, Typ);
8387          Set_Entity_With_Style_Check (S, Comp1);
8388
8389       else
8390          --  Resolve prefix with its type
8391
8392          Resolve (P, T);
8393       end if;
8394
8395       --  Generate cross-reference. We needed to wait until full overloading
8396       --  resolution was complete to do this, since otherwise we can't tell if
8397       --  we are an lvalue or not.
8398
8399       if May_Be_Lvalue (N) then
8400          Generate_Reference (Entity (S), S, 'm');
8401       else
8402          Generate_Reference (Entity (S), S, 'r');
8403       end if;
8404
8405       --  If prefix is an access type, the node will be transformed into an
8406       --  explicit dereference during expansion. The type of the node is the
8407       --  designated type of that of the prefix.
8408
8409       if Is_Access_Type (Etype (P)) then
8410          T := Designated_Type (Etype (P));
8411          Check_Fully_Declared_Prefix (T, P);
8412       else
8413          T := Etype (P);
8414       end if;
8415
8416       if Has_Discriminants (T)
8417         and then Ekind_In (Entity (S), E_Component, E_Discriminant)
8418         and then Present (Original_Record_Component (Entity (S)))
8419         and then Ekind (Original_Record_Component (Entity (S))) = E_Component
8420         and then Present (Discriminant_Checking_Func
8421                            (Original_Record_Component (Entity (S))))
8422         and then not Discriminant_Checks_Suppressed (T)
8423         and then not Init_Component
8424       then
8425          Set_Do_Discriminant_Check (N);
8426       end if;
8427
8428       if Ekind (Entity (S)) = E_Void then
8429          Error_Msg_N ("premature use of component", S);
8430       end if;
8431
8432       --  If the prefix is a record conversion, this may be a renamed
8433       --  discriminant whose bounds differ from those of the original
8434       --  one, so we must ensure that a range check is performed.
8435
8436       if Nkind (P) = N_Type_Conversion
8437         and then Ekind (Entity (S)) = E_Discriminant
8438         and then Is_Discrete_Type (Typ)
8439       then
8440          Set_Etype (N, Base_Type (Typ));
8441       end if;
8442
8443       --  Note: No Eval processing is required, because the prefix is of a
8444       --  record type, or protected type, and neither can possibly be static.
8445
8446       --  If the array type is atomic, and is packed, and we are in a left side
8447       --  context, then this is worth a warning, since we have a situation
8448       --  where the access to the component may cause extra read/writes of the
8449       --  atomic array object, which could be considered unexpected.
8450
8451       if Nkind (N) = N_Selected_Component
8452         and then (Is_Atomic (T)
8453                    or else (Is_Entity_Name (Prefix (N))
8454                              and then Is_Atomic (Entity (Prefix (N)))))
8455         and then Is_Packed (T)
8456         and then Is_LHS (N)
8457       then
8458          Error_Msg_N ("?assignment to component of packed atomic record",
8459                       Prefix (N));
8460          Error_Msg_N ("?\may cause unexpected accesses to atomic object",
8461                       Prefix (N));
8462       end if;
8463    end Resolve_Selected_Component;
8464
8465    -------------------
8466    -- Resolve_Shift --
8467    -------------------
8468
8469    procedure Resolve_Shift (N : Node_Id; Typ : Entity_Id) is
8470       B_Typ : constant Entity_Id := Base_Type (Typ);
8471       L     : constant Node_Id   := Left_Opnd  (N);
8472       R     : constant Node_Id   := Right_Opnd (N);
8473
8474    begin
8475       --  We do the resolution using the base type, because intermediate values
8476       --  in expressions always are of the base type, not a subtype of it.
8477
8478       Resolve (L, B_Typ);
8479       Resolve (R, Standard_Natural);
8480
8481       Check_Unset_Reference (L);
8482       Check_Unset_Reference (R);
8483
8484       Set_Etype (N, B_Typ);
8485       Generate_Operator_Reference (N, B_Typ);
8486       Eval_Shift (N);
8487    end Resolve_Shift;
8488
8489    ---------------------------
8490    -- Resolve_Short_Circuit --
8491    ---------------------------
8492
8493    procedure Resolve_Short_Circuit (N : Node_Id; Typ : Entity_Id) is
8494       B_Typ : constant Entity_Id := Base_Type (Typ);
8495       L     : constant Node_Id   := Left_Opnd  (N);
8496       R     : constant Node_Id   := Right_Opnd (N);
8497
8498    begin
8499       Resolve (L, B_Typ);
8500       Resolve (R, B_Typ);
8501
8502       --  Check for issuing warning for always False assert/check, this happens
8503       --  when assertions are turned off, in which case the pragma Assert/Check
8504       --  was transformed into:
8505
8506       --     if False and then <condition> then ...
8507
8508       --  and we detect this pattern
8509
8510       if Warn_On_Assertion_Failure
8511         and then Is_Entity_Name (R)
8512         and then Entity (R) = Standard_False
8513         and then Nkind (Parent (N)) = N_If_Statement
8514         and then Nkind (N) = N_And_Then
8515         and then Is_Entity_Name (L)
8516         and then Entity (L) = Standard_False
8517       then
8518          declare
8519             Orig : constant Node_Id := Original_Node (Parent (N));
8520
8521          begin
8522             if Nkind (Orig) = N_Pragma
8523               and then Pragma_Name (Orig) = Name_Assert
8524             then
8525                --  Don't want to warn if original condition is explicit False
8526
8527                declare
8528                   Expr : constant Node_Id :=
8529                            Original_Node
8530                              (Expression
8531                                (First (Pragma_Argument_Associations (Orig))));
8532                begin
8533                   if Is_Entity_Name (Expr)
8534                     and then Entity (Expr) = Standard_False
8535                   then
8536                      null;
8537                   else
8538                      --  Issue warning. We do not want the deletion of the
8539                      --  IF/AND-THEN to take this message with it. We achieve
8540                      --  this by making sure that the expanded code points to
8541                      --  the Sloc of the expression, not the original pragma.
8542
8543                      Error_Msg_N
8544                        ("?assertion would fail at run time!",
8545                         Expression
8546                           (First (Pragma_Argument_Associations (Orig))));
8547                   end if;
8548                end;
8549
8550             --  Similar processing for Check pragma
8551
8552             elsif Nkind (Orig) = N_Pragma
8553               and then Pragma_Name (Orig) = Name_Check
8554             then
8555                --  Don't want to warn if original condition is explicit False
8556
8557                declare
8558                   Expr : constant Node_Id :=
8559                            Original_Node
8560                              (Expression
8561                                 (Next (First
8562                                   (Pragma_Argument_Associations (Orig)))));
8563                begin
8564                   if Is_Entity_Name (Expr)
8565                     and then Entity (Expr) = Standard_False
8566                   then
8567                      null;
8568                   else
8569                      Error_Msg_N
8570                        ("?check would fail at run time!",
8571                         Expression
8572                           (Last (Pragma_Argument_Associations (Orig))));
8573                   end if;
8574                end;
8575             end if;
8576          end;
8577       end if;
8578
8579       --  Continue with processing of short circuit
8580
8581       Check_Unset_Reference (L);
8582       Check_Unset_Reference (R);
8583
8584       Set_Etype (N, B_Typ);
8585       Eval_Short_Circuit (N);
8586    end Resolve_Short_Circuit;
8587
8588    -------------------
8589    -- Resolve_Slice --
8590    -------------------
8591
8592    procedure Resolve_Slice (N : Node_Id; Typ : Entity_Id) is
8593       Name       : constant Node_Id := Prefix (N);
8594       Drange     : constant Node_Id := Discrete_Range (N);
8595       Array_Type : Entity_Id        := Empty;
8596       Index      : Node_Id;
8597
8598    begin
8599       if Is_Overloaded (Name) then
8600
8601          --  Use the context type to select the prefix that yields the correct
8602          --  array type.
8603
8604          declare
8605             I      : Interp_Index;
8606             I1     : Interp_Index := 0;
8607             It     : Interp;
8608             P      : constant Node_Id := Prefix (N);
8609             Found  : Boolean := False;
8610
8611          begin
8612             Get_First_Interp (P, I,  It);
8613             while Present (It.Typ) loop
8614                if (Is_Array_Type (It.Typ)
8615                     and then Covers (Typ,  It.Typ))
8616                  or else (Is_Access_Type (It.Typ)
8617                            and then Is_Array_Type (Designated_Type (It.Typ))
8618                            and then Covers (Typ, Designated_Type (It.Typ)))
8619                then
8620                   if Found then
8621                      It := Disambiguate (P, I1, I, Any_Type);
8622
8623                      if It = No_Interp then
8624                         Error_Msg_N ("ambiguous prefix for slicing",  N);
8625                         Set_Etype (N, Typ);
8626                         return;
8627                      else
8628                         Found := True;
8629                         Array_Type := It.Typ;
8630                         I1 := I;
8631                      end if;
8632                   else
8633                      Found := True;
8634                      Array_Type := It.Typ;
8635                      I1 := I;
8636                   end if;
8637                end if;
8638
8639                Get_Next_Interp (I, It);
8640             end loop;
8641          end;
8642
8643       else
8644          Array_Type := Etype (Name);
8645       end if;
8646
8647       Resolve (Name, Array_Type);
8648
8649       if Is_Access_Type (Array_Type) then
8650          Apply_Access_Check (N);
8651          Array_Type := Designated_Type (Array_Type);
8652
8653          --  If the prefix is an access to an unconstrained array, we must use
8654          --  the actual subtype of the object to perform the index checks. The
8655          --  object denoted by the prefix is implicit in the node, so we build
8656          --  an explicit representation for it in order to compute the actual
8657          --  subtype.
8658
8659          if not Is_Constrained (Array_Type) then
8660             Remove_Side_Effects (Prefix (N));
8661
8662             declare
8663                Obj : constant Node_Id :=
8664                        Make_Explicit_Dereference (Sloc (N),
8665                          Prefix => New_Copy_Tree (Prefix (N)));
8666             begin
8667                Set_Etype (Obj, Array_Type);
8668                Set_Parent (Obj, Parent (N));
8669                Array_Type := Get_Actual_Subtype (Obj);
8670             end;
8671          end if;
8672
8673       elsif Is_Entity_Name (Name)
8674         or else Nkind (Name) = N_Explicit_Dereference
8675         or else (Nkind (Name) = N_Function_Call
8676                   and then not Is_Constrained (Etype (Name)))
8677       then
8678          Array_Type := Get_Actual_Subtype (Name);
8679
8680       --  If the name is a selected component that depends on discriminants,
8681       --  build an actual subtype for it. This can happen only when the name
8682       --  itself is overloaded; otherwise the actual subtype is created when
8683       --  the selected component is analyzed.
8684
8685       elsif Nkind (Name) = N_Selected_Component
8686         and then Full_Analysis
8687         and then Depends_On_Discriminant (First_Index (Array_Type))
8688       then
8689          declare
8690             Act_Decl : constant Node_Id :=
8691                          Build_Actual_Subtype_Of_Component (Array_Type, Name);
8692          begin
8693             Insert_Action (N, Act_Decl);
8694             Array_Type := Defining_Identifier (Act_Decl);
8695          end;
8696
8697       --  Maybe this should just be "else", instead of checking for the
8698       --  specific case of slice??? This is needed for the case where the
8699       --  prefix is an Image attribute, which gets expanded to a slice, and so
8700       --  has a constrained subtype which we want to use for the slice range
8701       --  check applied below (the range check won't get done if the
8702       --  unconstrained subtype of the 'Image is used).
8703
8704       elsif Nkind (Name) = N_Slice then
8705          Array_Type := Etype (Name);
8706       end if;
8707
8708       --  If name was overloaded, set slice type correctly now
8709
8710       Set_Etype (N, Array_Type);
8711
8712       --  If the range is specified by a subtype mark, no resolution is
8713       --  necessary. Else resolve the bounds, and apply needed checks.
8714
8715       if not Is_Entity_Name (Drange) then
8716          Index := First_Index (Array_Type);
8717          Resolve (Drange, Base_Type (Etype (Index)));
8718
8719          if Nkind (Drange) = N_Range then
8720
8721             --  Ensure that side effects in the bounds are properly handled
8722
8723             Force_Evaluation (Low_Bound (Drange));
8724             Force_Evaluation (High_Bound (Drange));
8725
8726             --  Do not apply the range check to nodes associated with the
8727             --  frontend expansion of the dispatch table. We first check
8728             --  if Ada.Tags is already loaded to avoid the addition of an
8729             --  undesired dependence on such run-time unit.
8730
8731             if not Tagged_Type_Expansion
8732               or else not
8733                 (RTU_Loaded (Ada_Tags)
8734                   and then Nkind (Prefix (N)) = N_Selected_Component
8735                   and then Present (Entity (Selector_Name (Prefix (N))))
8736                   and then Entity (Selector_Name (Prefix (N))) =
8737                                          RTE_Record_Component (RE_Prims_Ptr))
8738             then
8739                Apply_Range_Check (Drange, Etype (Index));
8740             end if;
8741          end if;
8742       end if;
8743
8744       Set_Slice_Subtype (N);
8745
8746       --  Check bad use of type with predicates
8747
8748       if Has_Predicates (Etype (Drange)) then
8749          Bad_Predicated_Subtype_Use
8750            ("subtype& has predicate, not allowed in slice",
8751             Drange, Etype (Drange));
8752
8753       --  Otherwise here is where we check suspicious indexes
8754
8755       elsif Nkind (Drange) = N_Range then
8756          Warn_On_Suspicious_Index (Name, Low_Bound  (Drange));
8757          Warn_On_Suspicious_Index (Name, High_Bound (Drange));
8758       end if;
8759
8760       Eval_Slice (N);
8761    end Resolve_Slice;
8762
8763    ----------------------------
8764    -- Resolve_String_Literal --
8765    ----------------------------
8766
8767    procedure Resolve_String_Literal (N : Node_Id; Typ : Entity_Id) is
8768       C_Typ      : constant Entity_Id  := Component_Type (Typ);
8769       R_Typ      : constant Entity_Id  := Root_Type (C_Typ);
8770       Loc        : constant Source_Ptr := Sloc (N);
8771       Str        : constant String_Id  := Strval (N);
8772       Strlen     : constant Nat        := String_Length (Str);
8773       Subtype_Id : Entity_Id;
8774       Need_Check : Boolean;
8775
8776    begin
8777       --  For a string appearing in a concatenation, defer creation of the
8778       --  string_literal_subtype until the end of the resolution of the
8779       --  concatenation, because the literal may be constant-folded away. This
8780       --  is a useful optimization for long concatenation expressions.
8781
8782       --  If the string is an aggregate built for a single character (which
8783       --  happens in a non-static context) or a is null string to which special
8784       --  checks may apply, we build the subtype. Wide strings must also get a
8785       --  string subtype if they come from a one character aggregate. Strings
8786       --  generated by attributes might be static, but it is often hard to
8787       --  determine whether the enclosing context is static, so we generate
8788       --  subtypes for them as well, thus losing some rarer optimizations ???
8789       --  Same for strings that come from a static conversion.
8790
8791       Need_Check :=
8792         (Strlen = 0 and then Typ /= Standard_String)
8793           or else Nkind (Parent (N)) /= N_Op_Concat
8794           or else (N /= Left_Opnd (Parent (N))
8795                     and then N /= Right_Opnd (Parent (N)))
8796           or else ((Typ = Standard_Wide_String
8797                       or else Typ = Standard_Wide_Wide_String)
8798                     and then Nkind (Original_Node (N)) /= N_String_Literal);
8799
8800       --  If the resolving type is itself a string literal subtype, we can just
8801       --  reuse it, since there is no point in creating another.
8802
8803       if Ekind (Typ) = E_String_Literal_Subtype then
8804          Subtype_Id := Typ;
8805
8806       elsif Nkind (Parent (N)) = N_Op_Concat
8807         and then not Need_Check
8808         and then not Nkind_In (Original_Node (N), N_Character_Literal,
8809                                                   N_Attribute_Reference,
8810                                                   N_Qualified_Expression,
8811                                                   N_Type_Conversion)
8812       then
8813          Subtype_Id := Typ;
8814
8815       --  Otherwise we must create a string literal subtype. Note that the
8816       --  whole idea of string literal subtypes is simply to avoid the need
8817       --  for building a full fledged array subtype for each literal.
8818
8819       else
8820          Set_String_Literal_Subtype (N, Typ);
8821          Subtype_Id := Etype (N);
8822       end if;
8823
8824       if Nkind (Parent (N)) /= N_Op_Concat
8825         or else Need_Check
8826       then
8827          Set_Etype (N, Subtype_Id);
8828          Eval_String_Literal (N);
8829       end if;
8830
8831       if Is_Limited_Composite (Typ)
8832         or else Is_Private_Composite (Typ)
8833       then
8834          Error_Msg_N ("string literal not available for private array", N);
8835          Set_Etype (N, Any_Type);
8836          return;
8837       end if;
8838
8839       --  The validity of a null string has been checked in the call to
8840       --  Eval_String_Literal.
8841
8842       if Strlen = 0 then
8843          return;
8844
8845       --  Always accept string literal with component type Any_Character, which
8846       --  occurs in error situations and in comparisons of literals, both of
8847       --  which should accept all literals.
8848
8849       elsif R_Typ = Any_Character then
8850          return;
8851
8852       --  If the type is bit-packed, then we always transform the string
8853       --  literal into a full fledged aggregate.
8854
8855       elsif Is_Bit_Packed_Array (Typ) then
8856          null;
8857
8858       --  Deal with cases of Wide_Wide_String, Wide_String, and String
8859
8860       else
8861          --  For Standard.Wide_Wide_String, or any other type whose component
8862          --  type is Standard.Wide_Wide_Character, we know that all the
8863          --  characters in the string must be acceptable, since the parser
8864          --  accepted the characters as valid character literals.
8865
8866          if R_Typ = Standard_Wide_Wide_Character then
8867             null;
8868
8869          --  For the case of Standard.String, or any other type whose component
8870          --  type is Standard.Character, we must make sure that there are no
8871          --  wide characters in the string, i.e. that it is entirely composed
8872          --  of characters in range of type Character.
8873
8874          --  If the string literal is the result of a static concatenation, the
8875          --  test has already been performed on the components, and need not be
8876          --  repeated.
8877
8878          elsif R_Typ = Standard_Character
8879            and then Nkind (Original_Node (N)) /= N_Op_Concat
8880          then
8881             for J in 1 .. Strlen loop
8882                if not In_Character_Range (Get_String_Char (Str, J)) then
8883
8884                   --  If we are out of range, post error. This is one of the
8885                   --  very few places that we place the flag in the middle of
8886                   --  a token, right under the offending wide character. Not
8887                   --  quite clear if this is right wrt wide character encoding
8888                   --  sequences, but it's only an error message!
8889
8890                   Error_Msg
8891                     ("literal out of range of type Standard.Character",
8892                      Source_Ptr (Int (Loc) + J));
8893                   return;
8894                end if;
8895             end loop;
8896
8897          --  For the case of Standard.Wide_String, or any other type whose
8898          --  component type is Standard.Wide_Character, we must make sure that
8899          --  there are no wide characters in the string, i.e. that it is
8900          --  entirely composed of characters in range of type Wide_Character.
8901
8902          --  If the string literal is the result of a static concatenation,
8903          --  the test has already been performed on the components, and need
8904          --  not be repeated.
8905
8906          elsif R_Typ = Standard_Wide_Character
8907            and then Nkind (Original_Node (N)) /= N_Op_Concat
8908          then
8909             for J in 1 .. Strlen loop
8910                if not In_Wide_Character_Range (Get_String_Char (Str, J)) then
8911
8912                   --  If we are out of range, post error. This is one of the
8913                   --  very few places that we place the flag in the middle of
8914                   --  a token, right under the offending wide character.
8915
8916                   --  This is not quite right, because characters in general
8917                   --  will take more than one character position ???
8918
8919                   Error_Msg
8920                     ("literal out of range of type Standard.Wide_Character",
8921                      Source_Ptr (Int (Loc) + J));
8922                   return;
8923                end if;
8924             end loop;
8925
8926          --  If the root type is not a standard character, then we will convert
8927          --  the string into an aggregate and will let the aggregate code do
8928          --  the checking. Standard Wide_Wide_Character is also OK here.
8929
8930          else
8931             null;
8932          end if;
8933
8934          --  See if the component type of the array corresponding to the string
8935          --  has compile time known bounds. If yes we can directly check
8936          --  whether the evaluation of the string will raise constraint error.
8937          --  Otherwise we need to transform the string literal into the
8938          --  corresponding character aggregate and let the aggregate code do
8939          --  the checking.
8940
8941          if Is_Standard_Character_Type (R_Typ) then
8942
8943             --  Check for the case of full range, where we are definitely OK
8944
8945             if Component_Type (Typ) = Base_Type (Component_Type (Typ)) then
8946                return;
8947             end if;
8948
8949             --  Here the range is not the complete base type range, so check
8950
8951             declare
8952                Comp_Typ_Lo : constant Node_Id :=
8953                                Type_Low_Bound (Component_Type (Typ));
8954                Comp_Typ_Hi : constant Node_Id :=
8955                                Type_High_Bound (Component_Type (Typ));
8956
8957                Char_Val : Uint;
8958
8959             begin
8960                if Compile_Time_Known_Value (Comp_Typ_Lo)
8961                  and then Compile_Time_Known_Value (Comp_Typ_Hi)
8962                then
8963                   for J in 1 .. Strlen loop
8964                      Char_Val := UI_From_Int (Int (Get_String_Char (Str, J)));
8965
8966                      if Char_Val < Expr_Value (Comp_Typ_Lo)
8967                        or else Char_Val > Expr_Value (Comp_Typ_Hi)
8968                      then
8969                         Apply_Compile_Time_Constraint_Error
8970                           (N, "character out of range?", CE_Range_Check_Failed,
8971                            Loc => Source_Ptr (Int (Loc) + J));
8972                      end if;
8973                   end loop;
8974
8975                   return;
8976                end if;
8977             end;
8978          end if;
8979       end if;
8980
8981       --  If we got here we meed to transform the string literal into the
8982       --  equivalent qualified positional array aggregate. This is rather
8983       --  heavy artillery for this situation, but it is hard work to avoid.
8984
8985       declare
8986          Lits : constant List_Id    := New_List;
8987          P    : Source_Ptr := Loc + 1;
8988          C    : Char_Code;
8989
8990       begin
8991          --  Build the character literals, we give them source locations that
8992          --  correspond to the string positions, which is a bit tricky given
8993          --  the possible presence of wide character escape sequences.
8994
8995          for J in 1 .. Strlen loop
8996             C := Get_String_Char (Str, J);
8997             Set_Character_Literal_Name (C);
8998
8999             Append_To (Lits,
9000               Make_Character_Literal (P,
9001                 Chars              => Name_Find,
9002                 Char_Literal_Value => UI_From_CC (C)));
9003
9004             if In_Character_Range (C) then
9005                P := P + 1;
9006
9007             --  Should we have a call to Skip_Wide here ???
9008
9009             --  ???     else
9010             --             Skip_Wide (P);
9011
9012             end if;
9013          end loop;
9014
9015          Rewrite (N,
9016            Make_Qualified_Expression (Loc,
9017              Subtype_Mark => New_Reference_To (Typ, Loc),
9018              Expression   =>
9019                Make_Aggregate (Loc, Expressions => Lits)));
9020
9021          Analyze_And_Resolve (N, Typ);
9022       end;
9023    end Resolve_String_Literal;
9024
9025    -----------------------------
9026    -- Resolve_Subprogram_Info --
9027    -----------------------------
9028
9029    procedure Resolve_Subprogram_Info (N : Node_Id; Typ : Entity_Id) is
9030    begin
9031       Set_Etype (N, Typ);
9032    end Resolve_Subprogram_Info;
9033
9034    -----------------------------
9035    -- Resolve_Type_Conversion --
9036    -----------------------------
9037
9038    procedure Resolve_Type_Conversion (N : Node_Id; Typ : Entity_Id) is
9039       Conv_OK     : constant Boolean   := Conversion_OK (N);
9040       Operand     : constant Node_Id   := Expression (N);
9041       Operand_Typ : constant Entity_Id := Etype (Operand);
9042       Target_Typ  : constant Entity_Id := Etype (N);
9043       Rop         : Node_Id;
9044       Orig_N      : Node_Id;
9045       Orig_T      : Node_Id;
9046
9047       Test_Redundant : Boolean := Warn_On_Redundant_Constructs;
9048       --  Set to False to suppress cases where we want to suppress the test
9049       --  for redundancy to avoid possible false positives on this warning.
9050
9051    begin
9052       if not Conv_OK
9053         and then not Valid_Conversion (N, Target_Typ, Operand)
9054       then
9055          return;
9056       end if;
9057
9058       --  If the Operand Etype is Universal_Fixed, then the conversion is
9059       --  never redundant. We need this check because by the time we have
9060       --  finished the rather complex transformation, the conversion looks
9061       --  redundant when it is not.
9062
9063       if Operand_Typ = Universal_Fixed then
9064          Test_Redundant := False;
9065
9066       --  If the operand is marked as Any_Fixed, then special processing is
9067       --  required. This is also a case where we suppress the test for a
9068       --  redundant conversion, since most certainly it is not redundant.
9069
9070       elsif Operand_Typ = Any_Fixed then
9071          Test_Redundant := False;
9072
9073          --  Mixed-mode operation involving a literal. Context must be a fixed
9074          --  type which is applied to the literal subsequently.
9075
9076          if Is_Fixed_Point_Type (Typ) then
9077             Set_Etype (Operand, Universal_Real);
9078
9079          elsif Is_Numeric_Type (Typ)
9080            and then Nkind_In (Operand, N_Op_Multiply, N_Op_Divide)
9081            and then (Etype (Right_Opnd (Operand)) = Universal_Real
9082                        or else
9083                      Etype (Left_Opnd  (Operand)) = Universal_Real)
9084          then
9085             --  Return if expression is ambiguous
9086
9087             if Unique_Fixed_Point_Type (N) = Any_Type then
9088                return;
9089
9090             --  If nothing else, the available fixed type is Duration
9091
9092             else
9093                Set_Etype (Operand, Standard_Duration);
9094             end if;
9095
9096             --  Resolve the real operand with largest available precision
9097
9098             if Etype (Right_Opnd (Operand)) = Universal_Real then
9099                Rop := New_Copy_Tree (Right_Opnd (Operand));
9100             else
9101                Rop := New_Copy_Tree (Left_Opnd (Operand));
9102             end if;
9103
9104             Resolve (Rop, Universal_Real);
9105
9106             --  If the operand is a literal (it could be a non-static and
9107             --  illegal exponentiation) check whether the use of Duration
9108             --  is potentially inaccurate.
9109
9110             if Nkind (Rop) = N_Real_Literal
9111               and then Realval (Rop) /= Ureal_0
9112               and then abs (Realval (Rop)) < Delta_Value (Standard_Duration)
9113             then
9114                Error_Msg_N
9115                  ("?universal real operand can only " &
9116                   "be interpreted as Duration!",
9117                   Rop);
9118                Error_Msg_N
9119                  ("\?precision will be lost in the conversion!", Rop);
9120             end if;
9121
9122          elsif Is_Numeric_Type (Typ)
9123            and then Nkind (Operand) in N_Op
9124            and then Unique_Fixed_Point_Type (N) /= Any_Type
9125          then
9126             Set_Etype (Operand, Standard_Duration);
9127
9128          else
9129             Error_Msg_N ("invalid context for mixed mode operation", N);
9130             Set_Etype (Operand, Any_Type);
9131             return;
9132          end if;
9133       end if;
9134
9135       Resolve (Operand);
9136
9137       --  In SPARK, a type conversion between array types should be restricted
9138       --  to types which have matching static bounds.
9139
9140       --  Protect call to Matching_Static_Array_Bounds to avoid costly
9141       --  operation if not needed.
9142
9143       if Restriction_Check_Required (SPARK)
9144         and then Is_Array_Type (Target_Typ)
9145         and then Is_Array_Type (Operand_Typ)
9146         and then Operand_Typ /= Any_Composite  --  or else Operand in error
9147         and then not Matching_Static_Array_Bounds (Target_Typ, Operand_Typ)
9148       then
9149          Check_SPARK_Restriction
9150            ("array types should have matching static bounds", N);
9151       end if;
9152
9153       --  In formal mode, the operand of an ancestor type conversion must be an
9154       --  object (not an expression).
9155
9156       if Is_Tagged_Type (Target_Typ)
9157         and then not Is_Class_Wide_Type (Target_Typ)
9158         and then Is_Tagged_Type (Operand_Typ)
9159         and then not Is_Class_Wide_Type (Operand_Typ)
9160         and then Is_Ancestor (Target_Typ, Operand_Typ)
9161         and then not Is_SPARK_Object_Reference (Operand)
9162       then
9163          Check_SPARK_Restriction ("object required", Operand);
9164       end if;
9165
9166       --  Note: we do the Eval_Type_Conversion call before applying the
9167       --  required checks for a subtype conversion. This is important, since
9168       --  both are prepared under certain circumstances to change the type
9169       --  conversion to a constraint error node, but in the case of
9170       --  Eval_Type_Conversion this may reflect an illegality in the static
9171       --  case, and we would miss the illegality (getting only a warning
9172       --  message), if we applied the type conversion checks first.
9173
9174       Eval_Type_Conversion (N);
9175
9176       --  Even when evaluation is not possible, we may be able to simplify the
9177       --  conversion or its expression. This needs to be done before applying
9178       --  checks, since otherwise the checks may use the original expression
9179       --  and defeat the simplifications. This is specifically the case for
9180       --  elimination of the floating-point Truncation attribute in
9181       --  float-to-int conversions.
9182
9183       Simplify_Type_Conversion (N);
9184
9185       --  If after evaluation we still have a type conversion, then we may need
9186       --  to apply checks required for a subtype conversion.
9187
9188       --  Skip these type conversion checks if universal fixed operands
9189       --  operands involved, since range checks are handled separately for
9190       --  these cases (in the appropriate Expand routines in unit Exp_Fixd).
9191
9192       if Nkind (N) = N_Type_Conversion
9193         and then not Is_Generic_Type (Root_Type (Target_Typ))
9194         and then Target_Typ  /= Universal_Fixed
9195         and then Operand_Typ /= Universal_Fixed
9196       then
9197          Apply_Type_Conversion_Checks (N);
9198       end if;
9199
9200       --  Issue warning for conversion of simple object to its own type. We
9201       --  have to test the original nodes, since they may have been rewritten
9202       --  by various optimizations.
9203
9204       Orig_N := Original_Node (N);
9205
9206       --  Here we test for a redundant conversion if the warning mode is
9207       --  active (and was not locally reset), and we have a type conversion
9208       --  from source not appearing in a generic instance.
9209
9210       if Test_Redundant
9211         and then Nkind (Orig_N) = N_Type_Conversion
9212         and then Comes_From_Source (Orig_N)
9213         and then not In_Instance
9214       then
9215          Orig_N := Original_Node (Expression (Orig_N));
9216          Orig_T := Target_Typ;
9217
9218          --  If the node is part of a larger expression, the Target_Type
9219          --  may not be the original type of the node if the context is a
9220          --  condition. Recover original type to see if conversion is needed.
9221
9222          if Is_Boolean_Type (Orig_T)
9223           and then Nkind (Parent (N)) in N_Op
9224          then
9225             Orig_T := Etype (Parent (N));
9226          end if;
9227
9228          --  If we have an entity name, then give the warning if the entity
9229          --  is the right type, or if it is a loop parameter covered by the
9230          --  original type (that's needed because loop parameters have an
9231          --  odd subtype coming from the bounds).
9232
9233          if (Is_Entity_Name (Orig_N)
9234                and then
9235                  (Etype (Entity (Orig_N)) = Orig_T
9236                    or else
9237                      (Ekind (Entity (Orig_N)) = E_Loop_Parameter
9238                        and then Covers (Orig_T, Etype (Entity (Orig_N))))))
9239
9240            --  If not an entity, then type of expression must match
9241
9242            or else Etype (Orig_N) = Orig_T
9243          then
9244             --  One more check, do not give warning if the analyzed conversion
9245             --  has an expression with non-static bounds, and the bounds of the
9246             --  target are static. This avoids junk warnings in cases where the
9247             --  conversion is necessary to establish staticness, for example in
9248             --  a case statement.
9249
9250             if not Is_OK_Static_Subtype (Operand_Typ)
9251               and then Is_OK_Static_Subtype (Target_Typ)
9252             then
9253                null;
9254
9255             --  Finally, if this type conversion occurs in a context requiring
9256             --  a prefix, and the expression is a qualified expression then the
9257             --  type conversion is not redundant, since a qualified expression
9258             --  is not a prefix, whereas a type conversion is. For example, "X
9259             --  := T'(Funx(...)).Y;" is illegal because a selected component
9260             --  requires a prefix, but a type conversion makes it legal: "X :=
9261             --  T(T'(Funx(...))).Y;"
9262
9263             --  In Ada 2012, a qualified expression is a name, so this idiom is
9264             --  no longer needed, but we still suppress the warning because it
9265             --  seems unfriendly for warnings to pop up when you switch to the
9266             --  newer language version.
9267
9268             elsif Nkind (Orig_N) = N_Qualified_Expression
9269               and then Nkind_In (Parent (N), N_Attribute_Reference,
9270                                              N_Indexed_Component,
9271                                              N_Selected_Component,
9272                                              N_Slice,
9273                                              N_Explicit_Dereference)
9274             then
9275                null;
9276
9277             --  Here we give the redundant conversion warning. If it is an
9278             --  entity, give the name of the entity in the message. If not,
9279             --  just mention the expression.
9280
9281             else
9282                if Is_Entity_Name (Orig_N) then
9283                   Error_Msg_Node_2 := Orig_T;
9284                   Error_Msg_NE -- CODEFIX
9285                     ("?redundant conversion, & is of type &!",
9286                      N, Entity (Orig_N));
9287                else
9288                   Error_Msg_NE
9289                     ("?redundant conversion, expression is of type&!",
9290                      N, Orig_T);
9291                end if;
9292             end if;
9293          end if;
9294       end if;
9295
9296       --  Ada 2005 (AI-251): Handle class-wide interface type conversions.
9297       --  No need to perform any interface conversion if the type of the
9298       --  expression coincides with the target type.
9299
9300       if Ada_Version >= Ada_2005
9301         and then Expander_Active
9302         and then Operand_Typ /= Target_Typ
9303       then
9304          declare
9305             Opnd   : Entity_Id := Operand_Typ;
9306             Target : Entity_Id := Target_Typ;
9307
9308          begin
9309             if Is_Access_Type (Opnd) then
9310                Opnd := Designated_Type (Opnd);
9311             end if;
9312
9313             if Is_Access_Type (Target_Typ) then
9314                Target := Designated_Type (Target);
9315             end if;
9316
9317             if Opnd = Target then
9318                null;
9319
9320             --  Conversion from interface type
9321
9322             elsif Is_Interface (Opnd) then
9323
9324                --  Ada 2005 (AI-217): Handle entities from limited views
9325
9326                if From_With_Type (Opnd) then
9327                   Error_Msg_Qual_Level := 99;
9328                   Error_Msg_NE -- CODEFIX
9329                     ("missing WITH clause on package &", N,
9330                     Cunit_Entity (Get_Source_Unit (Base_Type (Opnd))));
9331                   Error_Msg_N
9332                     ("type conversions require visibility of the full view",
9333                      N);
9334
9335                elsif From_With_Type (Target)
9336                  and then not
9337                    (Is_Access_Type (Target_Typ)
9338                       and then Present (Non_Limited_View (Etype (Target))))
9339                then
9340                   Error_Msg_Qual_Level := 99;
9341                   Error_Msg_NE -- CODEFIX
9342                     ("missing WITH clause on package &", N,
9343                     Cunit_Entity (Get_Source_Unit (Base_Type (Target))));
9344                   Error_Msg_N
9345                     ("type conversions require visibility of the full view",
9346                      N);
9347
9348                else
9349                   Expand_Interface_Conversion (N, Is_Static => False);
9350                end if;
9351
9352             --  Conversion to interface type
9353
9354             elsif Is_Interface (Target) then
9355
9356                --  Handle subtypes
9357
9358                if Ekind_In (Opnd, E_Protected_Subtype, E_Task_Subtype) then
9359                   Opnd := Etype (Opnd);
9360                end if;
9361
9362                if not Interface_Present_In_Ancestor
9363                         (Typ   => Opnd,
9364                          Iface => Target)
9365                then
9366                   if Is_Class_Wide_Type (Opnd) then
9367
9368                      --  The static analysis is not enough to know if the
9369                      --  interface is implemented or not. Hence we must pass
9370                      --  the work to the expander to generate code to evaluate
9371                      --  the conversion at run time.
9372
9373                      Expand_Interface_Conversion (N, Is_Static => False);
9374
9375                   else
9376                      Error_Msg_Name_1 := Chars (Etype (Target));
9377                      Error_Msg_Name_2 := Chars (Opnd);
9378                      Error_Msg_N
9379                        ("wrong interface conversion (% is not a progenitor " &
9380                         "of %)", N);
9381                   end if;
9382
9383                else
9384                   Expand_Interface_Conversion (N);
9385                end if;
9386             end if;
9387          end;
9388       end if;
9389    end Resolve_Type_Conversion;
9390
9391    ----------------------
9392    -- Resolve_Unary_Op --
9393    ----------------------
9394
9395    procedure Resolve_Unary_Op (N : Node_Id; Typ : Entity_Id) is
9396       B_Typ : constant Entity_Id := Base_Type (Typ);
9397       R     : constant Node_Id   := Right_Opnd (N);
9398       OK    : Boolean;
9399       Lo    : Uint;
9400       Hi    : Uint;
9401
9402    begin
9403       if Is_Modular_Integer_Type (Typ) and then Nkind (N) /= N_Op_Not then
9404          Error_Msg_Name_1 := Chars (Typ);
9405          Check_SPARK_Restriction
9406            ("unary operator not defined for modular type%", N);
9407       end if;
9408
9409       --  Deal with intrinsic unary operators
9410
9411       if Comes_From_Source (N)
9412         and then Ekind (Entity (N)) = E_Function
9413         and then Is_Imported (Entity (N))
9414         and then Is_Intrinsic_Subprogram (Entity (N))
9415       then
9416          Resolve_Intrinsic_Unary_Operator (N, Typ);
9417          return;
9418       end if;
9419
9420       --  Deal with universal cases
9421
9422       if Etype (R) = Universal_Integer
9423            or else
9424          Etype (R) = Universal_Real
9425       then
9426          Check_For_Visible_Operator (N, B_Typ);
9427       end if;
9428
9429       Set_Etype (N, B_Typ);
9430       Resolve (R, B_Typ);
9431
9432       --  Generate warning for expressions like abs (x mod 2)
9433
9434       if Warn_On_Redundant_Constructs
9435         and then Nkind (N) = N_Op_Abs
9436       then
9437          Determine_Range (Right_Opnd (N), OK, Lo, Hi);
9438
9439          if OK and then Hi >= Lo and then Lo >= 0 then
9440             Error_Msg_N -- CODEFIX
9441              ("?abs applied to known non-negative value has no effect", N);
9442          end if;
9443       end if;
9444
9445       --  Deal with reference generation
9446
9447       Check_Unset_Reference (R);
9448       Generate_Operator_Reference (N, B_Typ);
9449       Eval_Unary_Op (N);
9450
9451       --  Set overflow checking bit. Much cleverer code needed here eventually
9452       --  and perhaps the Resolve routines should be separated for the various
9453       --  arithmetic operations, since they will need different processing ???
9454
9455       if Nkind (N) in N_Op then
9456          if not Overflow_Checks_Suppressed (Etype (N)) then
9457             Enable_Overflow_Check (N);
9458          end if;
9459       end if;
9460
9461       --  Generate warning for expressions like -5 mod 3 for integers. No need
9462       --  to worry in the floating-point case, since parens do not affect the
9463       --  result so there is no point in giving in a warning.
9464
9465       declare
9466          Norig : constant Node_Id := Original_Node (N);
9467          Rorig : Node_Id;
9468          Val   : Uint;
9469          HB    : Uint;
9470          LB    : Uint;
9471          Lval  : Uint;
9472          Opnd  : Node_Id;
9473
9474       begin
9475          if Warn_On_Questionable_Missing_Parens
9476            and then Comes_From_Source (Norig)
9477            and then Is_Integer_Type (Typ)
9478            and then Nkind (Norig) = N_Op_Minus
9479          then
9480             Rorig := Original_Node (Right_Opnd (Norig));
9481
9482             --  We are looking for cases where the right operand is not
9483             --  parenthesized, and is a binary operator, multiply, divide, or
9484             --  mod. These are the cases where the grouping can affect results.
9485
9486             if Paren_Count (Rorig) = 0
9487               and then Nkind_In (Rorig, N_Op_Mod, N_Op_Multiply, N_Op_Divide)
9488             then
9489                --  For mod, we always give the warning, since the value is
9490                --  affected by the parenthesization (e.g. (-5) mod 315 /=
9491                --  -(5 mod 315)). But for the other cases, the only concern is
9492                --  overflow, e.g. for the case of 8 big signed (-(2 * 64)
9493                --  overflows, but (-2) * 64 does not). So we try to give the
9494                --  message only when overflow is possible.
9495
9496                if Nkind (Rorig) /= N_Op_Mod
9497                  and then Compile_Time_Known_Value (R)
9498                then
9499                   Val := Expr_Value (R);
9500
9501                   if Compile_Time_Known_Value (Type_High_Bound (Typ)) then
9502                      HB := Expr_Value (Type_High_Bound (Typ));
9503                   else
9504                      HB := Expr_Value (Type_High_Bound (Base_Type (Typ)));
9505                   end if;
9506
9507                   if Compile_Time_Known_Value (Type_Low_Bound (Typ)) then
9508                      LB := Expr_Value (Type_Low_Bound (Typ));
9509                   else
9510                      LB := Expr_Value (Type_Low_Bound (Base_Type (Typ)));
9511                   end if;
9512
9513                   --  Note that the test below is deliberately excluding the
9514                   --  largest negative number, since that is a potentially
9515                   --  troublesome case (e.g. -2 * x, where the result is the
9516                   --  largest negative integer has an overflow with 2 * x).
9517
9518                   if Val > LB and then Val <= HB then
9519                      return;
9520                   end if;
9521                end if;
9522
9523                --  For the multiplication case, the only case we have to worry
9524                --  about is when (-a)*b is exactly the largest negative number
9525                --  so that -(a*b) can cause overflow. This can only happen if
9526                --  a is a power of 2, and more generally if any operand is a
9527                --  constant that is not a power of 2, then the parentheses
9528                --  cannot affect whether overflow occurs. We only bother to
9529                --  test the left most operand
9530
9531                --  Loop looking at left operands for one that has known value
9532
9533                Opnd := Rorig;
9534                Opnd_Loop : while Nkind (Opnd) = N_Op_Multiply loop
9535                   if Compile_Time_Known_Value (Left_Opnd (Opnd)) then
9536                      Lval := UI_Abs (Expr_Value (Left_Opnd (Opnd)));
9537
9538                      --  Operand value of 0 or 1 skips warning
9539
9540                      if Lval <= 1 then
9541                         return;
9542
9543                      --  Otherwise check power of 2, if power of 2, warn, if
9544                      --  anything else, skip warning.
9545
9546                      else
9547                         while Lval /= 2 loop
9548                            if Lval mod 2 = 1 then
9549                               return;
9550                            else
9551                               Lval := Lval / 2;
9552                            end if;
9553                         end loop;
9554
9555                         exit Opnd_Loop;
9556                      end if;
9557                   end if;
9558
9559                   --  Keep looking at left operands
9560
9561                   Opnd := Left_Opnd (Opnd);
9562                end loop Opnd_Loop;
9563
9564                --  For rem or "/" we can only have a problematic situation
9565                --  if the divisor has a value of minus one or one. Otherwise
9566                --  overflow is impossible (divisor > 1) or we have a case of
9567                --  division by zero in any case.
9568
9569                if Nkind_In (Rorig, N_Op_Divide, N_Op_Rem)
9570                  and then Compile_Time_Known_Value (Right_Opnd (Rorig))
9571                  and then UI_Abs (Expr_Value (Right_Opnd (Rorig))) /= 1
9572                then
9573                   return;
9574                end if;
9575
9576                --  If we fall through warning should be issued
9577
9578                Error_Msg_N
9579                  ("?unary minus expression should be parenthesized here!", N);
9580             end if;
9581          end if;
9582       end;
9583    end Resolve_Unary_Op;
9584
9585    ----------------------------------
9586    -- Resolve_Unchecked_Expression --
9587    ----------------------------------
9588
9589    procedure Resolve_Unchecked_Expression
9590      (N   : Node_Id;
9591       Typ : Entity_Id)
9592    is
9593    begin
9594       Resolve (Expression (N), Typ, Suppress => All_Checks);
9595       Set_Etype (N, Typ);
9596    end Resolve_Unchecked_Expression;
9597
9598    ---------------------------------------
9599    -- Resolve_Unchecked_Type_Conversion --
9600    ---------------------------------------
9601
9602    procedure Resolve_Unchecked_Type_Conversion
9603      (N   : Node_Id;
9604       Typ : Entity_Id)
9605    is
9606       pragma Warnings (Off, Typ);
9607
9608       Operand   : constant Node_Id   := Expression (N);
9609       Opnd_Type : constant Entity_Id := Etype (Operand);
9610
9611    begin
9612       --  Resolve operand using its own type
9613
9614       Resolve (Operand, Opnd_Type);
9615       Eval_Unchecked_Conversion (N);
9616    end Resolve_Unchecked_Type_Conversion;
9617
9618    ------------------------------
9619    -- Rewrite_Operator_As_Call --
9620    ------------------------------
9621
9622    procedure Rewrite_Operator_As_Call (N : Node_Id; Nam : Entity_Id) is
9623       Loc     : constant Source_Ptr := Sloc (N);
9624       Actuals : constant List_Id    := New_List;
9625       New_N   : Node_Id;
9626
9627    begin
9628       if Nkind (N) in  N_Binary_Op then
9629          Append (Left_Opnd (N), Actuals);
9630       end if;
9631
9632       Append (Right_Opnd (N), Actuals);
9633
9634       New_N :=
9635         Make_Function_Call (Sloc => Loc,
9636           Name => New_Occurrence_Of (Nam, Loc),
9637           Parameter_Associations => Actuals);
9638
9639       Preserve_Comes_From_Source (New_N, N);
9640       Preserve_Comes_From_Source (Name (New_N), N);
9641       Rewrite (N, New_N);
9642       Set_Etype (N, Etype (Nam));
9643    end Rewrite_Operator_As_Call;
9644
9645    ------------------------------
9646    -- Rewrite_Renamed_Operator --
9647    ------------------------------
9648
9649    procedure Rewrite_Renamed_Operator
9650      (N   : Node_Id;
9651       Op  : Entity_Id;
9652       Typ : Entity_Id)
9653    is
9654       Nam       : constant Name_Id := Chars (Op);
9655       Is_Binary : constant Boolean := Nkind (N) in N_Binary_Op;
9656       Op_Node   : Node_Id;
9657
9658    begin
9659       --  Rewrite the operator node using the real operator, not its renaming.
9660       --  Exclude user-defined intrinsic operations of the same name, which are
9661       --  treated separately and rewritten as calls.
9662
9663       if Ekind (Op) /= E_Function or else Chars (N) /= Nam then
9664          Op_Node := New_Node (Operator_Kind (Nam, Is_Binary), Sloc (N));
9665          Set_Chars      (Op_Node, Nam);
9666          Set_Etype      (Op_Node, Etype (N));
9667          Set_Entity     (Op_Node, Op);
9668          Set_Right_Opnd (Op_Node, Right_Opnd (N));
9669
9670          --  Indicate that both the original entity and its renaming are
9671          --  referenced at this point.
9672
9673          Generate_Reference (Entity (N), N);
9674          Generate_Reference (Op, N);
9675
9676          if Is_Binary then
9677             Set_Left_Opnd  (Op_Node, Left_Opnd  (N));
9678          end if;
9679
9680          Rewrite (N, Op_Node);
9681
9682          --  If the context type is private, add the appropriate conversions so
9683          --  that the operator is applied to the full view. This is done in the
9684          --  routines that resolve intrinsic operators.
9685
9686          if Is_Intrinsic_Subprogram (Op)
9687            and then Is_Private_Type (Typ)
9688          then
9689             case Nkind (N) is
9690                when N_Op_Add   | N_Op_Subtract | N_Op_Multiply | N_Op_Divide |
9691                     N_Op_Expon | N_Op_Mod      | N_Op_Rem      =>
9692                   Resolve_Intrinsic_Operator (N, Typ);
9693
9694                when N_Op_Plus  | N_Op_Minus    | N_Op_Abs      =>
9695                   Resolve_Intrinsic_Unary_Operator (N, Typ);
9696
9697                when others =>
9698                   Resolve (N, Typ);
9699             end case;
9700          end if;
9701
9702       elsif Ekind (Op) = E_Function and then Is_Intrinsic_Subprogram (Op) then
9703
9704          --  Operator renames a user-defined operator of the same name. Use the
9705          --  original operator in the node, which is the one Gigi knows about.
9706
9707          Set_Entity (N, Op);
9708          Set_Is_Overloaded (N, False);
9709       end if;
9710    end Rewrite_Renamed_Operator;
9711
9712    -----------------------
9713    -- Set_Slice_Subtype --
9714    -----------------------
9715
9716    --  Build an implicit subtype declaration to represent the type delivered by
9717    --  the slice. This is an abbreviated version of an array subtype. We define
9718    --  an index subtype for the slice, using either the subtype name or the
9719    --  discrete range of the slice. To be consistent with index usage elsewhere
9720    --  we create a list header to hold the single index. This list is not
9721    --  otherwise attached to the syntax tree.
9722
9723    procedure Set_Slice_Subtype (N : Node_Id) is
9724       Loc           : constant Source_Ptr := Sloc (N);
9725       Index_List    : constant List_Id    := New_List;
9726       Index         : Node_Id;
9727       Index_Subtype : Entity_Id;
9728       Index_Type    : Entity_Id;
9729       Slice_Subtype : Entity_Id;
9730       Drange        : constant Node_Id := Discrete_Range (N);
9731
9732    begin
9733       if Is_Entity_Name (Drange) then
9734          Index_Subtype := Entity (Drange);
9735
9736       else
9737          --  We force the evaluation of a range. This is definitely needed in
9738          --  the renamed case, and seems safer to do unconditionally. Note in
9739          --  any case that since we will create and insert an Itype referring
9740          --  to this range, we must make sure any side effect removal actions
9741          --  are inserted before the Itype definition.
9742
9743          if Nkind (Drange) = N_Range then
9744             Force_Evaluation (Low_Bound (Drange));
9745             Force_Evaluation (High_Bound (Drange));
9746          end if;
9747
9748          Index_Type := Base_Type (Etype (Drange));
9749
9750          Index_Subtype := Create_Itype (Subtype_Kind (Ekind (Index_Type)), N);
9751
9752          --  Take a new copy of Drange (where bounds have been rewritten to
9753          --  reference side-effect-free names). Using a separate tree ensures
9754          --  that further expansion (e.g. while rewriting a slice assignment
9755          --  into a FOR loop) does not attempt to remove side effects on the
9756          --  bounds again (which would cause the bounds in the index subtype
9757          --  definition to refer to temporaries before they are defined) (the
9758          --  reason is that some names are considered side effect free here
9759          --  for the subtype, but not in the context of a loop iteration
9760          --  scheme).
9761
9762          Set_Scalar_Range (Index_Subtype, New_Copy_Tree (Drange));
9763          Set_Parent       (Scalar_Range (Index_Subtype), Index_Subtype);
9764          Set_Etype        (Index_Subtype, Index_Type);
9765          Set_Size_Info    (Index_Subtype, Index_Type);
9766          Set_RM_Size      (Index_Subtype, RM_Size (Index_Type));
9767       end if;
9768
9769       Slice_Subtype := Create_Itype (E_Array_Subtype, N);
9770
9771       Index := New_Occurrence_Of (Index_Subtype, Loc);
9772       Set_Etype (Index, Index_Subtype);
9773       Append (Index, Index_List);
9774
9775       Set_First_Index    (Slice_Subtype, Index);
9776       Set_Etype          (Slice_Subtype, Base_Type (Etype (N)));
9777       Set_Is_Constrained (Slice_Subtype, True);
9778
9779       Check_Compile_Time_Size (Slice_Subtype);
9780
9781       --  The Etype of the existing Slice node is reset to this slice subtype.
9782       --  Its bounds are obtained from its first index.
9783
9784       Set_Etype (N, Slice_Subtype);
9785
9786       --  For packed slice subtypes, freeze immediately (except in the case of
9787       --  being in a "spec expression" where we never freeze when we first see
9788       --  the expression).
9789
9790       if Is_Packed (Slice_Subtype) and not In_Spec_Expression then
9791          Freeze_Itype (Slice_Subtype, N);
9792
9793       --  For all other cases insert an itype reference in the slice's actions
9794       --  so that the itype is frozen at the proper place in the tree (i.e. at
9795       --  the point where actions for the slice are analyzed). Note that this
9796       --  is different from freezing the itype immediately, which might be
9797       --  premature (e.g. if the slice is within a transient scope). This needs
9798       --  to be done only if expansion is enabled.
9799
9800       elsif Expander_Active then
9801          Ensure_Defined (Typ => Slice_Subtype, N => N);
9802       end if;
9803    end Set_Slice_Subtype;
9804
9805    --------------------------------
9806    -- Set_String_Literal_Subtype --
9807    --------------------------------
9808
9809    procedure Set_String_Literal_Subtype (N : Node_Id; Typ : Entity_Id) is
9810       Loc        : constant Source_Ptr := Sloc (N);
9811       Low_Bound  : constant Node_Id :=
9812                      Type_Low_Bound (Etype (First_Index (Typ)));
9813       Subtype_Id : Entity_Id;
9814
9815    begin
9816       if Nkind (N) /= N_String_Literal then
9817          return;
9818       end if;
9819
9820       Subtype_Id := Create_Itype (E_String_Literal_Subtype, N);
9821       Set_String_Literal_Length (Subtype_Id, UI_From_Int
9822                                                (String_Length (Strval (N))));
9823       Set_Etype          (Subtype_Id, Base_Type (Typ));
9824       Set_Is_Constrained (Subtype_Id);
9825       Set_Etype          (N, Subtype_Id);
9826
9827       if Is_OK_Static_Expression (Low_Bound) then
9828
9829       --  The low bound is set from the low bound of the corresponding index
9830       --  type. Note that we do not store the high bound in the string literal
9831       --  subtype, but it can be deduced if necessary from the length and the
9832       --  low bound.
9833
9834          Set_String_Literal_Low_Bound (Subtype_Id, Low_Bound);
9835
9836       else
9837          --  If the lower bound is not static we create a range for the string
9838          --  literal, using the index type and the known length of the literal.
9839          --  The index type is not necessarily Positive, so the upper bound is
9840          --  computed as  T'Val (T'Pos (Low_Bound) + L - 1)
9841
9842          declare
9843             Index_List    : constant List_Id    := New_List;
9844             Index_Type    : constant Entity_Id := Etype (First_Index (Typ));
9845
9846             High_Bound : constant Node_Id :=
9847                            Make_Attribute_Reference (Loc,
9848                              Attribute_Name => Name_Val,
9849                              Prefix         =>
9850                                New_Occurrence_Of (Index_Type, Loc),
9851                              Expressions    => New_List (
9852                                Make_Op_Add (Loc,
9853                                  Left_Opnd  =>
9854                                    Make_Attribute_Reference (Loc,
9855                                      Attribute_Name => Name_Pos,
9856                                      Prefix         =>
9857                                        New_Occurrence_Of (Index_Type, Loc),
9858                                      Expressions    =>
9859                                        New_List (New_Copy_Tree (Low_Bound))),
9860                                  Right_Opnd =>
9861                                    Make_Integer_Literal (Loc,
9862                                      String_Length (Strval (N)) - 1))));
9863
9864             Array_Subtype : Entity_Id;
9865             Index_Subtype : Entity_Id;
9866             Drange        : Node_Id;
9867             Index         : Node_Id;
9868
9869          begin
9870             if Is_Integer_Type (Index_Type) then
9871                Set_String_Literal_Low_Bound
9872                  (Subtype_Id, Make_Integer_Literal (Loc, 1));
9873
9874             else
9875                --  If the index type is an enumeration type, build bounds
9876                --  expression with attributes.
9877
9878                Set_String_Literal_Low_Bound
9879                  (Subtype_Id,
9880                   Make_Attribute_Reference (Loc,
9881                     Attribute_Name => Name_First,
9882                     Prefix         =>
9883                       New_Occurrence_Of (Base_Type (Index_Type), Loc)));
9884                Set_Etype (String_Literal_Low_Bound (Subtype_Id), Index_Type);
9885             end if;
9886
9887             Analyze_And_Resolve (String_Literal_Low_Bound (Subtype_Id));
9888
9889             --  Build bona fide subtype for the string, and wrap it in an
9890             --  unchecked conversion, because the backend expects the
9891             --  String_Literal_Subtype to have a static lower bound.
9892
9893             Index_Subtype :=
9894               Create_Itype (Subtype_Kind (Ekind (Index_Type)), N);
9895             Drange := Make_Range (Loc, New_Copy_Tree (Low_Bound), High_Bound);
9896             Set_Scalar_Range (Index_Subtype, Drange);
9897             Set_Parent (Drange, N);
9898             Analyze_And_Resolve (Drange, Index_Type);
9899
9900             --  In the context, the Index_Type may already have a constraint,
9901             --  so use common base type on string subtype. The base type may
9902             --  be used when generating attributes of the string, for example
9903             --  in the context of a slice assignment.
9904
9905             Set_Etype     (Index_Subtype, Base_Type (Index_Type));
9906             Set_Size_Info (Index_Subtype, Index_Type);
9907             Set_RM_Size   (Index_Subtype, RM_Size (Index_Type));
9908
9909             Array_Subtype := Create_Itype (E_Array_Subtype, N);
9910
9911             Index := New_Occurrence_Of (Index_Subtype, Loc);
9912             Set_Etype (Index, Index_Subtype);
9913             Append (Index, Index_List);
9914
9915             Set_First_Index    (Array_Subtype, Index);
9916             Set_Etype          (Array_Subtype, Base_Type (Typ));
9917             Set_Is_Constrained (Array_Subtype, True);
9918
9919             Rewrite (N,
9920               Make_Unchecked_Type_Conversion (Loc,
9921                 Subtype_Mark => New_Occurrence_Of (Array_Subtype, Loc),
9922                 Expression => Relocate_Node (N)));
9923             Set_Etype (N, Array_Subtype);
9924          end;
9925       end if;
9926    end Set_String_Literal_Subtype;
9927
9928    ------------------------------
9929    -- Simplify_Type_Conversion --
9930    ------------------------------
9931
9932    procedure Simplify_Type_Conversion (N : Node_Id) is
9933    begin
9934       if Nkind (N) = N_Type_Conversion then
9935          declare
9936             Operand    : constant Node_Id   := Expression (N);
9937             Target_Typ : constant Entity_Id := Etype (N);
9938             Opnd_Typ   : constant Entity_Id := Etype (Operand);
9939
9940          begin
9941             if Is_Floating_Point_Type (Opnd_Typ)
9942               and then
9943                 (Is_Integer_Type (Target_Typ)
9944                    or else (Is_Fixed_Point_Type (Target_Typ)
9945                               and then Conversion_OK (N)))
9946               and then Nkind (Operand) = N_Attribute_Reference
9947               and then Attribute_Name (Operand) = Name_Truncation
9948
9949             --  Special processing required if the conversion is the expression
9950             --  of a Truncation attribute reference. In this case we replace:
9951
9952             --     ityp (ftyp'Truncation (x))
9953
9954             --  by
9955
9956             --     ityp (x)
9957
9958             --  with the Float_Truncate flag set, which is more efficient.
9959
9960             then
9961                Rewrite (Operand,
9962                  Relocate_Node (First (Expressions (Operand))));
9963                Set_Float_Truncate (N, True);
9964             end if;
9965          end;
9966       end if;
9967    end Simplify_Type_Conversion;
9968
9969    -----------------------------
9970    -- Unique_Fixed_Point_Type --
9971    -----------------------------
9972
9973    function Unique_Fixed_Point_Type (N : Node_Id) return Entity_Id is
9974       T1   : Entity_Id := Empty;
9975       T2   : Entity_Id;
9976       Item : Node_Id;
9977       Scop : Entity_Id;
9978
9979       procedure Fixed_Point_Error;
9980       --  Give error messages for true ambiguity. Messages are posted on node
9981       --  N, and entities T1, T2 are the possible interpretations.
9982
9983       -----------------------
9984       -- Fixed_Point_Error --
9985       -----------------------
9986
9987       procedure Fixed_Point_Error is
9988       begin
9989          Error_Msg_N ("ambiguous universal_fixed_expression", N);
9990          Error_Msg_NE ("\\possible interpretation as}", N, T1);
9991          Error_Msg_NE ("\\possible interpretation as}", N, T2);
9992       end Fixed_Point_Error;
9993
9994    --  Start of processing for Unique_Fixed_Point_Type
9995
9996    begin
9997       --  The operations on Duration are visible, so Duration is always a
9998       --  possible interpretation.
9999
10000       T1 := Standard_Duration;
10001
10002       --  Look for fixed-point types in enclosing scopes
10003
10004       Scop := Current_Scope;
10005       while Scop /= Standard_Standard loop
10006          T2 := First_Entity (Scop);
10007          while Present (T2) loop
10008             if Is_Fixed_Point_Type (T2)
10009               and then Current_Entity (T2) = T2
10010               and then Scope (Base_Type (T2)) = Scop
10011             then
10012                if Present (T1) then
10013                   Fixed_Point_Error;
10014                   return Any_Type;
10015                else
10016                   T1 := T2;
10017                end if;
10018             end if;
10019
10020             Next_Entity (T2);
10021          end loop;
10022
10023          Scop := Scope (Scop);
10024       end loop;
10025
10026       --  Look for visible fixed type declarations in the context
10027
10028       Item := First (Context_Items (Cunit (Current_Sem_Unit)));
10029       while Present (Item) loop
10030          if Nkind (Item) = N_With_Clause then
10031             Scop := Entity (Name (Item));
10032             T2 := First_Entity (Scop);
10033             while Present (T2) loop
10034                if Is_Fixed_Point_Type (T2)
10035                  and then Scope (Base_Type (T2)) = Scop
10036                  and then (Is_Potentially_Use_Visible (T2) or else In_Use (T2))
10037                then
10038                   if Present (T1) then
10039                      Fixed_Point_Error;
10040                      return Any_Type;
10041                   else
10042                      T1 := T2;
10043                   end if;
10044                end if;
10045
10046                Next_Entity (T2);
10047             end loop;
10048          end if;
10049
10050          Next (Item);
10051       end loop;
10052
10053       if Nkind (N) = N_Real_Literal then
10054          Error_Msg_NE ("?real literal interpreted as }!", N, T1);
10055       else
10056          Error_Msg_NE ("?universal_fixed expression interpreted as }!", N, T1);
10057       end if;
10058
10059       return T1;
10060    end Unique_Fixed_Point_Type;
10061
10062    ----------------------
10063    -- Valid_Conversion --
10064    ----------------------
10065
10066    function Valid_Conversion
10067      (N       : Node_Id;
10068       Target  : Entity_Id;
10069       Operand : Node_Id) return Boolean
10070    is
10071       Target_Type : constant Entity_Id := Base_Type (Target);
10072       Opnd_Type   : Entity_Id := Etype (Operand);
10073
10074       function Conversion_Check
10075         (Valid : Boolean;
10076          Msg   : String) return Boolean;
10077       --  Little routine to post Msg if Valid is False, returns Valid value
10078
10079       function Valid_Tagged_Conversion
10080         (Target_Type : Entity_Id;
10081          Opnd_Type   : Entity_Id) return Boolean;
10082       --  Specifically test for validity of tagged conversions
10083
10084       function Valid_Array_Conversion return Boolean;
10085       --  Check index and component conformance, and accessibility levels if
10086       --  the component types are anonymous access types (Ada 2005).
10087
10088       ----------------------
10089       -- Conversion_Check --
10090       ----------------------
10091
10092       function Conversion_Check
10093         (Valid : Boolean;
10094          Msg   : String) return Boolean
10095       is
10096       begin
10097          if not Valid then
10098             Error_Msg_N (Msg, Operand);
10099          end if;
10100
10101          return Valid;
10102       end Conversion_Check;
10103
10104       ----------------------------
10105       -- Valid_Array_Conversion --
10106       ----------------------------
10107
10108       function Valid_Array_Conversion return Boolean
10109       is
10110          Opnd_Comp_Type : constant Entity_Id := Component_Type (Opnd_Type);
10111          Opnd_Comp_Base : constant Entity_Id := Base_Type (Opnd_Comp_Type);
10112
10113          Opnd_Index      : Node_Id;
10114          Opnd_Index_Type : Entity_Id;
10115
10116          Target_Comp_Type : constant Entity_Id :=
10117                               Component_Type (Target_Type);
10118          Target_Comp_Base : constant Entity_Id :=
10119                               Base_Type (Target_Comp_Type);
10120
10121          Target_Index      : Node_Id;
10122          Target_Index_Type : Entity_Id;
10123
10124       begin
10125          --  Error if wrong number of dimensions
10126
10127          if
10128            Number_Dimensions (Target_Type) /= Number_Dimensions (Opnd_Type)
10129          then
10130             Error_Msg_N
10131               ("incompatible number of dimensions for conversion", Operand);
10132             return False;
10133
10134          --  Number of dimensions matches
10135
10136          else
10137             --  Loop through indexes of the two arrays
10138
10139             Target_Index := First_Index (Target_Type);
10140             Opnd_Index   := First_Index (Opnd_Type);
10141             while Present (Target_Index) and then Present (Opnd_Index) loop
10142                Target_Index_Type := Etype (Target_Index);
10143                Opnd_Index_Type   := Etype (Opnd_Index);
10144
10145                --  Error if index types are incompatible
10146
10147                if not (Is_Integer_Type (Target_Index_Type)
10148                        and then Is_Integer_Type (Opnd_Index_Type))
10149                  and then (Root_Type (Target_Index_Type)
10150                            /= Root_Type (Opnd_Index_Type))
10151                then
10152                   Error_Msg_N
10153                     ("incompatible index types for array conversion",
10154                      Operand);
10155                   return False;
10156                end if;
10157
10158                Next_Index (Target_Index);
10159                Next_Index (Opnd_Index);
10160             end loop;
10161
10162             --  If component types have same base type, all set
10163
10164             if Target_Comp_Base  = Opnd_Comp_Base then
10165                null;
10166
10167                --  Here if base types of components are not the same. The only
10168                --  time this is allowed is if we have anonymous access types.
10169
10170                --  The conversion of arrays of anonymous access types can lead
10171                --  to dangling pointers. AI-392 formalizes the accessibility
10172                --  checks that must be applied to such conversions to prevent
10173                --  out-of-scope references.
10174
10175             elsif Ekind_In
10176                     (Target_Comp_Base, E_Anonymous_Access_Type,
10177                                        E_Anonymous_Access_Subprogram_Type)
10178               and then Ekind (Opnd_Comp_Base) = Ekind (Target_Comp_Base)
10179               and then
10180                 Subtypes_Statically_Match (Target_Comp_Type, Opnd_Comp_Type)
10181             then
10182                if Type_Access_Level (Target_Type) <
10183                    Type_Access_Level (Opnd_Type)
10184                then
10185                   if In_Instance_Body then
10186                      Error_Msg_N ("?source array type " &
10187                        "has deeper accessibility level than target", Operand);
10188                      Error_Msg_N ("\?Program_Error will be raised at run time",
10189                          Operand);
10190                      Rewrite (N,
10191                        Make_Raise_Program_Error (Sloc (N),
10192                          Reason => PE_Accessibility_Check_Failed));
10193                      Set_Etype (N, Target_Type);
10194                      return False;
10195
10196                   --  Conversion not allowed because of accessibility levels
10197
10198                   else
10199                      Error_Msg_N ("source array type " &
10200                        "has deeper accessibility level than target", Operand);
10201                      return False;
10202                   end if;
10203
10204                else
10205                   null;
10206                end if;
10207
10208             --  All other cases where component base types do not match
10209
10210             else
10211                Error_Msg_N
10212                  ("incompatible component types for array conversion",
10213                   Operand);
10214                return False;
10215             end if;
10216
10217             --  Check that component subtypes statically match. For numeric
10218             --  types this means that both must be either constrained or
10219             --  unconstrained. For enumeration types the bounds must match.
10220             --  All of this is checked in Subtypes_Statically_Match.
10221
10222             if not Subtypes_Statically_Match
10223                             (Target_Comp_Type, Opnd_Comp_Type)
10224             then
10225                Error_Msg_N
10226                  ("component subtypes must statically match", Operand);
10227                return False;
10228             end if;
10229          end if;
10230
10231          return True;
10232       end Valid_Array_Conversion;
10233
10234       -----------------------------
10235       -- Valid_Tagged_Conversion --
10236       -----------------------------
10237
10238       function Valid_Tagged_Conversion
10239         (Target_Type : Entity_Id;
10240          Opnd_Type   : Entity_Id) return Boolean
10241       is
10242       begin
10243          --  Upward conversions are allowed (RM 4.6(22))
10244
10245          if Covers (Target_Type, Opnd_Type)
10246            or else Is_Ancestor (Target_Type, Opnd_Type)
10247          then
10248             return True;
10249
10250          --  Downward conversion are allowed if the operand is class-wide
10251          --  (RM 4.6(23)).
10252
10253          elsif Is_Class_Wide_Type (Opnd_Type)
10254            and then Covers (Opnd_Type, Target_Type)
10255          then
10256             return True;
10257
10258          elsif Covers (Opnd_Type, Target_Type)
10259            or else Is_Ancestor (Opnd_Type, Target_Type)
10260          then
10261             return
10262               Conversion_Check (False,
10263                 "downward conversion of tagged objects not allowed");
10264
10265          --  Ada 2005 (AI-251): The conversion to/from interface types is
10266          --  always valid
10267
10268          elsif Is_Interface (Target_Type) or else Is_Interface (Opnd_Type) then
10269             return True;
10270
10271          --  If the operand is a class-wide type obtained through a limited_
10272          --  with clause, and the context includes the non-limited view, use
10273          --  it to determine whether the conversion is legal.
10274
10275          elsif Is_Class_Wide_Type (Opnd_Type)
10276            and then From_With_Type (Opnd_Type)
10277            and then Present (Non_Limited_View (Etype (Opnd_Type)))
10278            and then Is_Interface (Non_Limited_View (Etype (Opnd_Type)))
10279          then
10280             return True;
10281
10282          elsif Is_Access_Type (Opnd_Type)
10283            and then Is_Interface (Directly_Designated_Type (Opnd_Type))
10284          then
10285             return True;
10286
10287          else
10288             Error_Msg_NE
10289               ("invalid tagged conversion, not compatible with}",
10290                N, First_Subtype (Opnd_Type));
10291             return False;
10292          end if;
10293       end Valid_Tagged_Conversion;
10294
10295    --  Start of processing for Valid_Conversion
10296
10297    begin
10298       Check_Parameterless_Call (Operand);
10299
10300       if Is_Overloaded (Operand) then
10301          declare
10302             I   : Interp_Index;
10303             I1  : Interp_Index;
10304             It  : Interp;
10305             It1 : Interp;
10306             N1  : Entity_Id;
10307             T1  : Entity_Id;
10308
10309          begin
10310             --  Remove procedure calls, which syntactically cannot appear in
10311             --  this context, but which cannot be removed by type checking,
10312             --  because the context does not impose a type.
10313
10314             --  When compiling for VMS, spurious ambiguities can be produced
10315             --  when arithmetic operations have a literal operand and return
10316             --  System.Address or a descendant of it. These ambiguities are
10317             --  otherwise resolved by the context, but for conversions there
10318             --  is no context type and the removal of the spurious operations
10319             --  must be done explicitly here.
10320
10321             --  The node may be labelled overloaded, but still contain only one
10322             --  interpretation because others were discarded earlier. If this
10323             --  is the case, retain the single interpretation if legal.
10324
10325             Get_First_Interp (Operand, I, It);
10326             Opnd_Type := It.Typ;
10327             Get_Next_Interp (I, It);
10328
10329             if Present (It.Typ)
10330               and then Opnd_Type /= Standard_Void_Type
10331             then
10332                --  More than one candidate interpretation is available
10333
10334                Get_First_Interp (Operand, I, It);
10335                while Present (It.Typ) loop
10336                   if It.Typ = Standard_Void_Type then
10337                      Remove_Interp (I);
10338                   end if;
10339
10340                   if Present (System_Aux_Id)
10341                     and then Is_Descendent_Of_Address (It.Typ)
10342                   then
10343                      Remove_Interp (I);
10344                   end if;
10345
10346                   Get_Next_Interp (I, It);
10347                end loop;
10348             end if;
10349
10350             Get_First_Interp (Operand, I, It);
10351             I1  := I;
10352             It1 := It;
10353
10354             if No (It.Typ) then
10355                Error_Msg_N ("illegal operand in conversion", Operand);
10356                return False;
10357             end if;
10358
10359             Get_Next_Interp (I, It);
10360
10361             if Present (It.Typ) then
10362                N1  := It1.Nam;
10363                T1  := It1.Typ;
10364                It1 :=  Disambiguate (Operand, I1, I, Any_Type);
10365
10366                if It1 = No_Interp then
10367                   Error_Msg_N ("ambiguous operand in conversion", Operand);
10368
10369                   --  If the interpretation involves a standard operator, use
10370                   --  the location of the type, which may be user-defined.
10371
10372                   if Sloc (It.Nam) = Standard_Location then
10373                      Error_Msg_Sloc := Sloc (It.Typ);
10374                   else
10375                      Error_Msg_Sloc := Sloc (It.Nam);
10376                   end if;
10377
10378                   Error_Msg_N -- CODEFIX
10379                     ("\\possible interpretation#!", Operand);
10380
10381                   if Sloc (N1) = Standard_Location then
10382                      Error_Msg_Sloc := Sloc (T1);
10383                   else
10384                      Error_Msg_Sloc := Sloc (N1);
10385                   end if;
10386
10387                   Error_Msg_N -- CODEFIX
10388                     ("\\possible interpretation#!", Operand);
10389
10390                   return False;
10391                end if;
10392             end if;
10393
10394             Set_Etype (Operand, It1.Typ);
10395             Opnd_Type := It1.Typ;
10396          end;
10397       end if;
10398
10399       --  Numeric types
10400
10401       if Is_Numeric_Type (Target_Type)  then
10402
10403          --  A universal fixed expression can be converted to any numeric type
10404
10405          if Opnd_Type = Universal_Fixed then
10406             return True;
10407
10408          --  Also no need to check when in an instance or inlined body, because
10409          --  the legality has been established when the template was analyzed.
10410          --  Furthermore, numeric conversions may occur where only a private
10411          --  view of the operand type is visible at the instantiation point.
10412          --  This results in a spurious error if we check that the operand type
10413          --  is a numeric type.
10414
10415          --  Note: in a previous version of this unit, the following tests were
10416          --  applied only for generated code (Comes_From_Source set to False),
10417          --  but in fact the test is required for source code as well, since
10418          --  this situation can arise in source code.
10419
10420          elsif In_Instance or else In_Inlined_Body then
10421             return True;
10422
10423          --  Otherwise we need the conversion check
10424
10425          else
10426             return Conversion_Check
10427                     (Is_Numeric_Type (Opnd_Type),
10428                      "illegal operand for numeric conversion");
10429          end if;
10430
10431       --  Array types
10432
10433       elsif Is_Array_Type (Target_Type) then
10434          if not Is_Array_Type (Opnd_Type)
10435            or else Opnd_Type = Any_Composite
10436            or else Opnd_Type = Any_String
10437          then
10438             Error_Msg_N ("illegal operand for array conversion", Operand);
10439             return False;
10440          else
10441             return Valid_Array_Conversion;
10442          end if;
10443
10444       --  Ada 2005 (AI-251): Anonymous access types where target references an
10445       --  interface type.
10446
10447       elsif Ekind_In (Target_Type, E_General_Access_Type,
10448                                    E_Anonymous_Access_Type)
10449         and then Is_Interface (Directly_Designated_Type (Target_Type))
10450       then
10451          --  Check the static accessibility rule of 4.6(17). Note that the
10452          --  check is not enforced when within an instance body, since the
10453          --  RM requires such cases to be caught at run time.
10454
10455          if Ekind (Target_Type) /= E_Anonymous_Access_Type then
10456             if Type_Access_Level (Opnd_Type) >
10457                Type_Access_Level (Target_Type)
10458             then
10459                --  In an instance, this is a run-time check, but one we know
10460                --  will fail, so generate an appropriate warning. The raise
10461                --  will be generated by Expand_N_Type_Conversion.
10462
10463                if In_Instance_Body then
10464                   Error_Msg_N
10465                     ("?cannot convert local pointer to non-local access type",
10466                      Operand);
10467                   Error_Msg_N
10468                     ("\?Program_Error will be raised at run time", Operand);
10469                else
10470                   Error_Msg_N
10471                     ("cannot convert local pointer to non-local access type",
10472                      Operand);
10473                   return False;
10474                end if;
10475
10476             --  Special accessibility checks are needed in the case of access
10477             --  discriminants declared for a limited type.
10478
10479             elsif Ekind (Opnd_Type) = E_Anonymous_Access_Type
10480               and then not Is_Local_Anonymous_Access (Opnd_Type)
10481             then
10482                --  When the operand is a selected access discriminant the check
10483                --  needs to be made against the level of the object denoted by
10484                --  the prefix of the selected name (Object_Access_Level handles
10485                --  checking the prefix of the operand for this case).
10486
10487                if Nkind (Operand) = N_Selected_Component
10488                  and then Object_Access_Level (Operand) >
10489                           Type_Access_Level (Target_Type)
10490                then
10491                   --  In an instance, this is a run-time check, but one we know
10492                   --  will fail, so generate an appropriate warning. The raise
10493                   --  will be generated by Expand_N_Type_Conversion.
10494
10495                   if In_Instance_Body then
10496                      Error_Msg_N
10497                        ("?cannot convert access discriminant to non-local" &
10498                         " access type", Operand);
10499                      Error_Msg_N
10500                        ("\?Program_Error will be raised at run time", Operand);
10501                   else
10502                      Error_Msg_N
10503                        ("cannot convert access discriminant to non-local" &
10504                         " access type", Operand);
10505                      return False;
10506                   end if;
10507                end if;
10508
10509                --  The case of a reference to an access discriminant from
10510                --  within a limited type declaration (which will appear as
10511                --  a discriminal) is always illegal because the level of the
10512                --  discriminant is considered to be deeper than any (nameable)
10513                --  access type.
10514
10515                if Is_Entity_Name (Operand)
10516                  and then not Is_Local_Anonymous_Access (Opnd_Type)
10517                  and then
10518                    Ekind_In (Entity (Operand), E_In_Parameter, E_Constant)
10519                  and then Present (Discriminal_Link (Entity (Operand)))
10520                then
10521                   Error_Msg_N
10522                     ("discriminant has deeper accessibility level than target",
10523                      Operand);
10524                   return False;
10525                end if;
10526             end if;
10527          end if;
10528
10529          return True;
10530
10531       --  General and anonymous access types
10532
10533       elsif Ekind_In (Target_Type, E_General_Access_Type,
10534                                    E_Anonymous_Access_Type)
10535           and then
10536             Conversion_Check
10537               (Is_Access_Type (Opnd_Type)
10538                 and then not
10539                   Ekind_In (Opnd_Type, E_Access_Subprogram_Type,
10540                                        E_Access_Protected_Subprogram_Type),
10541                "must be an access-to-object type")
10542       then
10543          if Is_Access_Constant (Opnd_Type)
10544            and then not Is_Access_Constant (Target_Type)
10545          then
10546             Error_Msg_N
10547               ("access-to-constant operand type not allowed", Operand);
10548             return False;
10549          end if;
10550
10551          --  Check the static accessibility rule of 4.6(17). Note that the
10552          --  check is not enforced when within an instance body, since the RM
10553          --  requires such cases to be caught at run time.
10554
10555          if Ekind (Target_Type) /= E_Anonymous_Access_Type
10556            or else Is_Local_Anonymous_Access (Target_Type)
10557          then
10558             if Type_Access_Level (Opnd_Type)
10559               > Type_Access_Level (Target_Type)
10560             then
10561                --  In an instance, this is a run-time check, but one we know
10562                --  will fail, so generate an appropriate warning. The raise
10563                --  will be generated by Expand_N_Type_Conversion.
10564
10565                if In_Instance_Body then
10566                   Error_Msg_N
10567                     ("?cannot convert local pointer to non-local access type",
10568                      Operand);
10569                   Error_Msg_N
10570                     ("\?Program_Error will be raised at run time", Operand);
10571
10572                else
10573                   --  Avoid generation of spurious error message
10574
10575                   if not Error_Posted (N) then
10576                      Error_Msg_N
10577                       ("cannot convert local pointer to non-local access type",
10578                        Operand);
10579                   end if;
10580
10581                   return False;
10582                end if;
10583
10584             --  Special accessibility checks are needed in the case of access
10585             --  discriminants declared for a limited type.
10586
10587             elsif Ekind (Opnd_Type) = E_Anonymous_Access_Type
10588               and then not Is_Local_Anonymous_Access (Opnd_Type)
10589             then
10590                --  When the operand is a selected access discriminant the check
10591                --  needs to be made against the level of the object denoted by
10592                --  the prefix of the selected name (Object_Access_Level handles
10593                --  checking the prefix of the operand for this case).
10594
10595                if Nkind (Operand) = N_Selected_Component
10596                  and then Object_Access_Level (Operand) >
10597                           Type_Access_Level (Target_Type)
10598                then
10599                   --  In an instance, this is a run-time check, but one we know
10600                   --  will fail, so generate an appropriate warning. The raise
10601                   --  will be generated by Expand_N_Type_Conversion.
10602
10603                   if In_Instance_Body then
10604                      Error_Msg_N
10605                        ("?cannot convert access discriminant to non-local" &
10606                         " access type", Operand);
10607                      Error_Msg_N
10608                        ("\?Program_Error will be raised at run time",
10609                         Operand);
10610
10611                   else
10612                      Error_Msg_N
10613                        ("cannot convert access discriminant to non-local" &
10614                         " access type", Operand);
10615                      return False;
10616                   end if;
10617                end if;
10618
10619                --  The case of a reference to an access discriminant from
10620                --  within a limited type declaration (which will appear as
10621                --  a discriminal) is always illegal because the level of the
10622                --  discriminant is considered to be deeper than any (nameable)
10623                --  access type.
10624
10625                if Is_Entity_Name (Operand)
10626                  and then
10627                    Ekind_In (Entity (Operand), E_In_Parameter, E_Constant)
10628                  and then Present (Discriminal_Link (Entity (Operand)))
10629                then
10630                   Error_Msg_N
10631                     ("discriminant has deeper accessibility level than target",
10632                      Operand);
10633                   return False;
10634                end if;
10635             end if;
10636          end if;
10637
10638          --  In the presence of limited_with clauses we have to use non-limited
10639          --  views, if available.
10640
10641          Check_Limited : declare
10642             function Full_Designated_Type (T : Entity_Id) return Entity_Id;
10643             --  Helper function to handle limited views
10644
10645             --------------------------
10646             -- Full_Designated_Type --
10647             --------------------------
10648
10649             function Full_Designated_Type (T : Entity_Id) return Entity_Id is
10650                Desig : constant Entity_Id := Designated_Type (T);
10651
10652             begin
10653                --  Handle the limited view of a type
10654
10655                if Is_Incomplete_Type (Desig)
10656                  and then From_With_Type (Desig)
10657                  and then Present (Non_Limited_View (Desig))
10658                then
10659                   return Available_View (Desig);
10660                else
10661                   return Desig;
10662                end if;
10663             end Full_Designated_Type;
10664
10665             --  Local Declarations
10666
10667             Target : constant Entity_Id := Full_Designated_Type (Target_Type);
10668             Opnd   : constant Entity_Id := Full_Designated_Type (Opnd_Type);
10669
10670             Same_Base : constant Boolean :=
10671                           Base_Type (Target) = Base_Type (Opnd);
10672
10673          --  Start of processing for Check_Limited
10674
10675          begin
10676             if Is_Tagged_Type (Target) then
10677                return Valid_Tagged_Conversion (Target, Opnd);
10678
10679             else
10680                if not Same_Base then
10681                   Error_Msg_NE
10682                     ("target designated type not compatible with }",
10683                      N, Base_Type (Opnd));
10684                   return False;
10685
10686                --  Ada 2005 AI-384: legality rule is symmetric in both
10687                --  designated types. The conversion is legal (with possible
10688                --  constraint check) if either designated type is
10689                --  unconstrained.
10690
10691                elsif Subtypes_Statically_Match (Target, Opnd)
10692                  or else
10693                    (Has_Discriminants (Target)
10694                      and then
10695                       (not Is_Constrained (Opnd)
10696                         or else not Is_Constrained (Target)))
10697                then
10698                   --  Special case, if Value_Size has been used to make the
10699                   --  sizes different, the conversion is not allowed even
10700                   --  though the subtypes statically match.
10701
10702                   if Known_Static_RM_Size (Target)
10703                     and then Known_Static_RM_Size (Opnd)
10704                     and then RM_Size (Target) /= RM_Size (Opnd)
10705                   then
10706                      Error_Msg_NE
10707                        ("target designated subtype not compatible with }",
10708                         N, Opnd);
10709                      Error_Msg_NE
10710                        ("\because sizes of the two designated subtypes differ",
10711                         N, Opnd);
10712                      return False;
10713
10714                   --  Normal case where conversion is allowed
10715
10716                   else
10717                      return True;
10718                   end if;
10719
10720                else
10721                   Error_Msg_NE
10722                     ("target designated subtype not compatible with }",
10723                      N, Opnd);
10724                   return False;
10725                end if;
10726             end if;
10727          end Check_Limited;
10728
10729       --  Access to subprogram types. If the operand is an access parameter,
10730       --  the type has a deeper accessibility that any master, and cannot be
10731       --  assigned. We must make an exception if the conversion is part of an
10732       --  assignment and the target is the return object of an extended return
10733       --  statement, because in that case the accessibility check takes place
10734       --  after the return.
10735
10736       elsif Is_Access_Subprogram_Type (Target_Type)
10737         and then No (Corresponding_Remote_Type (Opnd_Type))
10738       then
10739          if Ekind (Base_Type (Opnd_Type)) = E_Anonymous_Access_Subprogram_Type
10740            and then Is_Entity_Name (Operand)
10741            and then Ekind (Entity (Operand)) = E_In_Parameter
10742            and then
10743              (Nkind (Parent (N)) /= N_Assignment_Statement
10744                or else not Is_Entity_Name (Name (Parent (N)))
10745                or else not Is_Return_Object (Entity (Name (Parent (N)))))
10746          then
10747             Error_Msg_N
10748               ("illegal attempt to store anonymous access to subprogram",
10749                Operand);
10750             Error_Msg_N
10751               ("\value has deeper accessibility than any master " &
10752                "(RM 3.10.2 (13))",
10753                Operand);
10754
10755             Error_Msg_NE
10756              ("\use named access type for& instead of access parameter",
10757                Operand, Entity (Operand));
10758          end if;
10759
10760          --  Check that the designated types are subtype conformant
10761
10762          Check_Subtype_Conformant (New_Id  => Designated_Type (Target_Type),
10763                                    Old_Id  => Designated_Type (Opnd_Type),
10764                                    Err_Loc => N);
10765
10766          --  Check the static accessibility rule of 4.6(20)
10767
10768          if Type_Access_Level (Opnd_Type) >
10769             Type_Access_Level (Target_Type)
10770          then
10771             Error_Msg_N
10772               ("operand type has deeper accessibility level than target",
10773                Operand);
10774
10775          --  Check that if the operand type is declared in a generic body,
10776          --  then the target type must be declared within that same body
10777          --  (enforces last sentence of 4.6(20)).
10778
10779          elsif Present (Enclosing_Generic_Body (Opnd_Type)) then
10780             declare
10781                O_Gen : constant Node_Id :=
10782                          Enclosing_Generic_Body (Opnd_Type);
10783
10784                T_Gen : Node_Id;
10785
10786             begin
10787                T_Gen := Enclosing_Generic_Body (Target_Type);
10788                while Present (T_Gen) and then T_Gen /= O_Gen loop
10789                   T_Gen := Enclosing_Generic_Body (T_Gen);
10790                end loop;
10791
10792                if T_Gen /= O_Gen then
10793                   Error_Msg_N
10794                     ("target type must be declared in same generic body"
10795                      & " as operand type", N);
10796                end if;
10797             end;
10798          end if;
10799
10800          return True;
10801
10802       --  Remote subprogram access types
10803
10804       elsif Is_Remote_Access_To_Subprogram_Type (Target_Type)
10805         and then Is_Remote_Access_To_Subprogram_Type (Opnd_Type)
10806       then
10807          --  It is valid to convert from one RAS type to another provided
10808          --  that their specification statically match.
10809
10810          Check_Subtype_Conformant
10811            (New_Id  =>
10812               Designated_Type (Corresponding_Remote_Type (Target_Type)),
10813             Old_Id  =>
10814               Designated_Type (Corresponding_Remote_Type (Opnd_Type)),
10815             Err_Loc =>
10816               N);
10817          return True;
10818
10819       --  If both are tagged types, check legality of view conversions
10820
10821       elsif Is_Tagged_Type (Target_Type)
10822               and then
10823             Is_Tagged_Type (Opnd_Type)
10824       then
10825          return Valid_Tagged_Conversion (Target_Type, Opnd_Type);
10826
10827       --  Types derived from the same root type are convertible
10828
10829       elsif Root_Type (Target_Type) = Root_Type (Opnd_Type) then
10830          return True;
10831
10832       --  In an instance or an inlined body, there may be inconsistent views of
10833       --  the same type, or of types derived from a common root.
10834
10835       elsif (In_Instance or In_Inlined_Body)
10836         and then
10837           Root_Type (Underlying_Type (Target_Type)) =
10838           Root_Type (Underlying_Type (Opnd_Type))
10839       then
10840          return True;
10841
10842       --  Special check for common access type error case
10843
10844       elsif Ekind (Target_Type) = E_Access_Type
10845          and then Is_Access_Type (Opnd_Type)
10846       then
10847          Error_Msg_N ("target type must be general access type!", N);
10848          Error_Msg_NE -- CODEFIX
10849             ("add ALL to }!", N, Target_Type);
10850          return False;
10851
10852       else
10853          Error_Msg_NE ("invalid conversion, not compatible with }",
10854            N, Opnd_Type);
10855          return False;
10856       end if;
10857    end Valid_Conversion;
10858
10859 end Sem_Res;