OSDN Git Service

2008-03-26 Javier Miranda <miranda@adacore.com>
[pf3gnuchains/gcc-fork.git] / gcc / ada / sem_case.adb
1 ------------------------------------------------------------------------------
2 --                                                                          --
3 --                         GNAT COMPILER COMPONENTS                         --
4 --                                                                          --
5 --                             S E M _ C A S E                              --
6 --                                                                          --
7 --                                 B o d y                                  --
8 --                                                                          --
9 --          Copyright (C) 1996-2007, 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 Einfo;    use Einfo;
28 with Errout;   use Errout;
29 with Namet;    use Namet;
30 with Nlists;   use Nlists;
31 with Nmake;    use Nmake;
32 with Opt;      use Opt;
33 with Sem;      use Sem;
34 with Sem_Eval; use Sem_Eval;
35 with Sem_Res;  use Sem_Res;
36 with Sem_Util; use Sem_Util;
37 with Sem_Type; use Sem_Type;
38 with Snames;   use Snames;
39 with Stand;    use Stand;
40 with Sinfo;    use Sinfo;
41 with Tbuild;   use Tbuild;
42 with Uintp;    use Uintp;
43
44 with GNAT.Heap_Sort_G;
45
46 package body Sem_Case is
47
48    -----------------------
49    -- Local Subprograms --
50    -----------------------
51
52    type Sort_Choice_Table_Type is array (Nat range <>) of Choice_Bounds;
53    --  This new array type is used as the actual table type for sorting
54    --  discrete choices. The reason for not using Choice_Table_Type, is that
55    --  in Sort_Choice_Table_Type we reserve entry 0 for the sorting algortim
56    --  (this is not absolutely necessary but it makes the code more
57    --  efficient).
58
59    procedure Check_Choices
60      (Choice_Table   : in out Sort_Choice_Table_Type;
61       Bounds_Type    : Entity_Id;
62       Others_Present : Boolean;
63       Msg_Sloc       : Source_Ptr);
64    --  This is the procedure which verifies that a set of case alternatives
65    --  or record variant choices has no duplicates, and covers the range
66    --  specified by Bounds_Type. Choice_Table contains the discrete choices
67    --  to check. These must start at position 1.
68    --  Furthermore Choice_Table (0) must exist. This element is used by
69    --  the sorting algorithm as a temporary. Others_Present is a flag
70    --  indicating whether or not an Others choice is present. Finally
71    --  Msg_Sloc gives the source location of the construct containing the
72    --  choices in the Choice_Table.
73
74    function Choice_Image (Value : Uint; Ctype : Entity_Id) return Name_Id;
75    --  Given a Pos value of enumeration type Ctype, returns the name
76    --  ID of an appropriate string to be used in error message output.
77
78    procedure Expand_Others_Choice
79      (Case_Table     : Choice_Table_Type;
80       Others_Choice  : Node_Id;
81       Choice_Type    : Entity_Id);
82    --  The case table is the table generated by a call to Analyze_Choices
83    --  (with just 1 .. Last_Choice entries present). Others_Choice is a
84    --  pointer to the N_Others_Choice node (this routine is only called if
85    --  an others choice is present), and Choice_Type is the discrete type
86    --  of the bounds. The effect of this call is to analyze the cases and
87    --  determine the set of values covered by others. This choice list is
88    --  set in the Others_Discrete_Choices field of the N_Others_Choice node.
89
90    -------------------
91    -- Check_Choices --
92    -------------------
93
94    procedure Check_Choices
95      (Choice_Table   : in out Sort_Choice_Table_Type;
96       Bounds_Type    : Entity_Id;
97       Others_Present : Boolean;
98       Msg_Sloc       : Source_Ptr)
99    is
100       function Lt_Choice (C1, C2 : Natural) return Boolean;
101       --  Comparison routine for comparing Choice_Table entries. Use the lower
102       --  bound of each Choice as the key.
103
104       procedure Move_Choice (From : Natural; To : Natural);
105       --  Move routine for sorting the Choice_Table
106
107       package Sorting is new GNAT.Heap_Sort_G (Move_Choice, Lt_Choice);
108
109       procedure Issue_Msg (Value1 : Node_Id; Value2 : Node_Id);
110       procedure Issue_Msg (Value1 : Node_Id; Value2 : Uint);
111       procedure Issue_Msg (Value1 : Uint;    Value2 : Node_Id);
112       procedure Issue_Msg (Value1 : Uint;    Value2 : Uint);
113       --  Issue an error message indicating that there are missing choices,
114       --  followed by the image of the missing choices themselves which lie
115       --  between Value1 and Value2 inclusive.
116
117       ---------------
118       -- Issue_Msg --
119       ---------------
120
121       procedure Issue_Msg (Value1 : Node_Id; Value2 : Node_Id) is
122       begin
123          Issue_Msg (Expr_Value (Value1), Expr_Value (Value2));
124       end Issue_Msg;
125
126       procedure Issue_Msg (Value1 : Node_Id; Value2 : Uint) is
127       begin
128          Issue_Msg (Expr_Value (Value1), Value2);
129       end Issue_Msg;
130
131       procedure Issue_Msg (Value1 : Uint; Value2 : Node_Id) is
132       begin
133          Issue_Msg (Value1, Expr_Value (Value2));
134       end Issue_Msg;
135
136       procedure Issue_Msg (Value1 : Uint; Value2 : Uint) is
137       begin
138          --  In some situations, we call this with a null range, and
139          --  obviously we don't want to complain in this case!
140
141          if Value1 > Value2 then
142             return;
143          end if;
144
145          --  Case of only one value that is missing
146
147          if Value1 = Value2 then
148             if Is_Integer_Type (Bounds_Type) then
149                Error_Msg_Uint_1 := Value1;
150                Error_Msg ("missing case value: ^!", Msg_Sloc);
151             else
152                Error_Msg_Name_1 := Choice_Image (Value1, Bounds_Type);
153                Error_Msg ("missing case value: %!", Msg_Sloc);
154             end if;
155
156          --  More than one choice value, so print range of values
157
158          else
159             if Is_Integer_Type (Bounds_Type) then
160                Error_Msg_Uint_1 := Value1;
161                Error_Msg_Uint_2 := Value2;
162                Error_Msg ("missing case values: ^ .. ^!", Msg_Sloc);
163             else
164                Error_Msg_Name_1 := Choice_Image (Value1, Bounds_Type);
165                Error_Msg_Name_2 := Choice_Image (Value2, Bounds_Type);
166                Error_Msg ("missing case values: % .. %!", Msg_Sloc);
167             end if;
168          end if;
169       end Issue_Msg;
170
171       ---------------
172       -- Lt_Choice --
173       ---------------
174
175       function Lt_Choice (C1, C2 : Natural) return Boolean is
176       begin
177          return
178            Expr_Value (Choice_Table (Nat (C1)).Lo)
179              <
180            Expr_Value (Choice_Table (Nat (C2)).Lo);
181       end Lt_Choice;
182
183       -----------------
184       -- Move_Choice --
185       -----------------
186
187       procedure Move_Choice (From : Natural; To : Natural) is
188       begin
189          Choice_Table (Nat (To)) := Choice_Table (Nat (From));
190       end Move_Choice;
191
192       --  Variables local to Check_Choices
193
194       Choice      : Node_Id;
195       Bounds_Lo   : constant Node_Id := Type_Low_Bound (Bounds_Type);
196       Bounds_Hi   : constant Node_Id := Type_High_Bound (Bounds_Type);
197
198       Prev_Choice : Node_Id;
199
200       Hi       : Uint;
201       Lo       : Uint;
202       Prev_Hi  : Uint;
203
204    --  Start processing for Check_Choices
205
206    begin
207       --  Choice_Table must start at 0 which is an unused location used
208       --  by the sorting algorithm. However the first valid position for
209       --  a discrete choice is 1.
210
211       pragma Assert (Choice_Table'First = 0);
212
213       if Choice_Table'Last = 0 then
214          if not Others_Present then
215             Issue_Msg (Bounds_Lo, Bounds_Hi);
216          end if;
217          return;
218       end if;
219
220       Sorting.Sort (Positive (Choice_Table'Last));
221
222       Lo      := Expr_Value (Choice_Table (1).Lo);
223       Hi      := Expr_Value (Choice_Table (1).Hi);
224       Prev_Hi := Hi;
225
226       if not Others_Present and then Expr_Value (Bounds_Lo) < Lo then
227          Issue_Msg (Bounds_Lo, Lo - 1);
228       end if;
229
230       for J in 2 .. Choice_Table'Last loop
231          Lo := Expr_Value (Choice_Table (J).Lo);
232          Hi := Expr_Value (Choice_Table (J).Hi);
233
234          if Lo <= Prev_Hi then
235             Prev_Choice := Choice_Table (J - 1).Node;
236             Choice      := Choice_Table (J).Node;
237
238             if Sloc (Prev_Choice) <= Sloc (Choice) then
239                Error_Msg_Sloc := Sloc (Prev_Choice);
240                Error_Msg_N ("duplication of choice value#", Choice);
241             else
242                Error_Msg_Sloc := Sloc (Choice);
243                Error_Msg_N ("duplication of choice value#", Prev_Choice);
244             end if;
245
246          elsif not Others_Present and then Lo /= Prev_Hi + 1 then
247             Issue_Msg (Prev_Hi + 1, Lo - 1);
248          end if;
249
250          Prev_Hi := Hi;
251       end loop;
252
253       if not Others_Present and then Expr_Value (Bounds_Hi) > Hi then
254          Issue_Msg (Hi + 1, Bounds_Hi);
255       end if;
256    end Check_Choices;
257
258    ------------------
259    -- Choice_Image --
260    ------------------
261
262    function Choice_Image (Value : Uint; Ctype : Entity_Id) return Name_Id is
263       Rtp : constant Entity_Id := Root_Type (Ctype);
264       Lit : Entity_Id;
265       C   : Int;
266
267    begin
268       --  For character, or wide [wide] character. If 7-bit ASCII graphic
269       --  range, then build and return appropriate character literal name
270
271       if Rtp = Standard_Character
272         or else Rtp = Standard_Wide_Character
273         or else Rtp = Standard_Wide_Wide_Character
274       then
275          C := UI_To_Int (Value);
276
277          if C in 16#20# .. 16#7E# then
278             Set_Character_Literal_Name (Char_Code (UI_To_Int (Value)));
279             return Name_Find;
280          end if;
281
282       --  For user defined enumeration type, find enum/char literal
283
284       else
285          Lit := First_Literal (Rtp);
286
287          for J in 1 .. UI_To_Int (Value) loop
288             Next_Literal (Lit);
289          end loop;
290
291          --  If enumeration literal, just return its value
292
293          if Nkind (Lit) = N_Defining_Identifier then
294             return Chars (Lit);
295
296          --  For character literal, get the name and use it if it is
297          --  for a 7-bit ASCII graphic character in 16#20#..16#7E#.
298
299          else
300             Get_Decoded_Name_String (Chars (Lit));
301
302             if Name_Len = 3
303               and then Name_Buffer (2) in
304                 Character'Val (16#20#) .. Character'Val (16#7E#)
305             then
306                return Chars (Lit);
307             end if;
308          end if;
309       end if;
310
311       --  If we fall through, we have a character literal which is not in
312       --  the 7-bit ASCII graphic set. For such cases, we construct the
313       --  name "type'val(nnn)" where type is the choice type, and nnn is
314       --  the pos value passed as an argument to Choice_Image.
315
316       Get_Name_String (Chars (First_Subtype (Ctype)));
317       Name_Len := Name_Len + 1;
318       Name_Buffer (Name_Len) := ''';
319       Name_Len := Name_Len + 1;
320       Name_Buffer (Name_Len) := 'v';
321       Name_Len := Name_Len + 1;
322       Name_Buffer (Name_Len) := 'a';
323       Name_Len := Name_Len + 1;
324       Name_Buffer (Name_Len) := 'l';
325       Name_Len := Name_Len + 1;
326       Name_Buffer (Name_Len) := '(';
327
328       UI_Image (Value);
329
330       for J in 1 .. UI_Image_Length loop
331          Name_Len := Name_Len + 1;
332          Name_Buffer (Name_Len) := UI_Image_Buffer (J);
333       end loop;
334
335       Name_Len := Name_Len + 1;
336       Name_Buffer (Name_Len) := ')';
337       return Name_Find;
338    end Choice_Image;
339
340    --------------------------
341    -- Expand_Others_Choice --
342    --------------------------
343
344    procedure Expand_Others_Choice
345      (Case_Table    : Choice_Table_Type;
346       Others_Choice : Node_Id;
347       Choice_Type   : Entity_Id)
348    is
349       Loc         : constant Source_Ptr := Sloc (Others_Choice);
350       Choice_List : constant List_Id    := New_List;
351       Choice      : Node_Id;
352       Exp_Lo      : Node_Id;
353       Exp_Hi      : Node_Id;
354       Hi          : Uint;
355       Lo          : Uint;
356       Previous_Hi : Uint;
357
358       function Build_Choice (Value1, Value2 : Uint) return Node_Id;
359       --  Builds a node representing the missing choices given by the
360       --  Value1 and Value2. A N_Range node is built if there is more than
361       --  one literal value missing. Otherwise a single N_Integer_Literal,
362       --  N_Identifier or N_Character_Literal is built depending on what
363       --  Choice_Type is.
364
365       function Lit_Of (Value : Uint) return Node_Id;
366       --  Returns the Node_Id for the enumeration literal corresponding to the
367       --  position given by Value within the enumeration type Choice_Type.
368
369       ------------------
370       -- Build_Choice --
371       ------------------
372
373       function Build_Choice (Value1, Value2 : Uint) return Node_Id is
374          Lit_Node : Node_Id;
375          Lo, Hi   : Node_Id;
376
377       begin
378          --  If there is only one choice value missing between Value1 and
379          --  Value2, build an integer or enumeration literal to represent it.
380
381          if (Value2 - Value1) = 0 then
382             if Is_Integer_Type (Choice_Type) then
383                Lit_Node := Make_Integer_Literal (Loc, Value1);
384                Set_Etype (Lit_Node, Choice_Type);
385             else
386                Lit_Node := Lit_Of (Value1);
387             end if;
388
389          --  Otherwise is more that one choice value that is missing between
390          --  Value1 and Value2, therefore build a N_Range node of either
391          --  integer or enumeration literals.
392
393          else
394             if Is_Integer_Type (Choice_Type) then
395                Lo := Make_Integer_Literal (Loc, Value1);
396                Set_Etype (Lo, Choice_Type);
397                Hi := Make_Integer_Literal (Loc, Value2);
398                Set_Etype (Hi, Choice_Type);
399                Lit_Node :=
400                  Make_Range (Loc,
401                    Low_Bound  => Lo,
402                    High_Bound => Hi);
403
404             else
405                Lit_Node :=
406                  Make_Range (Loc,
407                    Low_Bound  => Lit_Of (Value1),
408                    High_Bound => Lit_Of (Value2));
409             end if;
410          end if;
411
412          return Lit_Node;
413       end Build_Choice;
414
415       ------------
416       -- Lit_Of --
417       ------------
418
419       function Lit_Of (Value : Uint) return Node_Id is
420          Lit : Entity_Id;
421
422       begin
423          --  In the case where the literal is of type Character, there needs
424          --  to be some special handling since there is no explicit chain
425          --  of literals to search. Instead, a N_Character_Literal node
426          --  is created with the appropriate Char_Code and Chars fields.
427
428          if Root_Type (Choice_Type) = Standard_Character
429               or else
430             Root_Type (Choice_Type) = Standard_Wide_Character
431               or else
432             Root_Type (Choice_Type) = Standard_Wide_Wide_Character
433          then
434             Set_Character_Literal_Name (Char_Code (UI_To_Int (Value)));
435             Lit := New_Node (N_Character_Literal, Loc);
436             Set_Chars (Lit, Name_Find);
437             Set_Char_Literal_Value (Lit, Value);
438             Set_Etype (Lit, Choice_Type);
439             Set_Is_Static_Expression (Lit, True);
440             return Lit;
441
442          --  Otherwise, iterate through the literals list of Choice_Type
443          --  "Value" number of times until the desired literal is reached
444          --  and then return an occurrence of it.
445
446          else
447             Lit := First_Literal (Choice_Type);
448             for J in 1 .. UI_To_Int (Value) loop
449                Next_Literal (Lit);
450             end loop;
451
452             return New_Occurrence_Of (Lit, Loc);
453          end if;
454       end Lit_Of;
455
456    --  Start of processing for Expand_Others_Choice
457
458    begin
459       if Case_Table'Length = 0 then
460
461          --  Special case: only an others case is present.
462          --  The others case covers the full range of the type.
463
464          if Is_Static_Subtype (Choice_Type) then
465             Choice := New_Occurrence_Of (Choice_Type, Loc);
466          else
467             Choice := New_Occurrence_Of (Base_Type (Choice_Type), Loc);
468          end if;
469
470          Set_Others_Discrete_Choices (Others_Choice, New_List (Choice));
471          return;
472       end if;
473
474       --  Establish the bound values for the choice depending upon whether
475       --  the type of the case statement is static or not.
476
477       if Is_OK_Static_Subtype (Choice_Type) then
478          Exp_Lo := Type_Low_Bound (Choice_Type);
479          Exp_Hi := Type_High_Bound (Choice_Type);
480       else
481          Exp_Lo := Type_Low_Bound (Base_Type (Choice_Type));
482          Exp_Hi := Type_High_Bound (Base_Type (Choice_Type));
483       end if;
484
485       Lo := Expr_Value (Case_Table (Case_Table'First).Lo);
486       Hi := Expr_Value (Case_Table (Case_Table'First).Hi);
487       Previous_Hi := Expr_Value (Case_Table (Case_Table'First).Hi);
488
489       --  Build the node for any missing choices that are smaller than any
490       --  explicit choices given in the case.
491
492       if Expr_Value (Exp_Lo) < Lo then
493          Append (Build_Choice (Expr_Value (Exp_Lo), Lo - 1), Choice_List);
494       end if;
495
496       --  Build the nodes representing any missing choices that lie between
497       --  the explicit ones given in the case.
498
499       for J in Case_Table'First + 1 .. Case_Table'Last loop
500          Lo := Expr_Value (Case_Table (J).Lo);
501          Hi := Expr_Value (Case_Table (J).Hi);
502
503          if Lo /= (Previous_Hi + 1) then
504             Append_To (Choice_List, Build_Choice (Previous_Hi + 1, Lo - 1));
505          end if;
506
507          Previous_Hi := Hi;
508       end loop;
509
510       --  Build the node for any missing choices that are greater than any
511       --  explicit choices given in the case.
512
513       if Expr_Value (Exp_Hi) > Hi then
514          Append (Build_Choice (Hi + 1, Expr_Value (Exp_Hi)), Choice_List);
515       end if;
516
517       Set_Others_Discrete_Choices (Others_Choice, Choice_List);
518
519       --  Warn on null others list if warning option set
520
521       if Warn_On_Redundant_Constructs
522         and then Comes_From_Source (Others_Choice)
523         and then Is_Empty_List (Choice_List)
524       then
525          Error_Msg_N ("?OTHERS choice is redundant", Others_Choice);
526          Error_Msg_N ("\previous choices cover all values", Others_Choice);
527       end if;
528    end Expand_Others_Choice;
529
530    -----------
531    -- No_OP --
532    -----------
533
534    procedure No_OP (C : Node_Id) is
535       pragma Warnings (Off, C);
536
537    begin
538       null;
539    end No_OP;
540
541    --------------------------------
542    -- Generic_Choices_Processing --
543    --------------------------------
544
545    package body Generic_Choices_Processing is
546
547       ---------------------
548       -- Analyze_Choices --
549       ---------------------
550
551       procedure Analyze_Choices
552         (N              : Node_Id;
553          Subtyp         : Entity_Id;
554          Choice_Table   : out Choice_Table_Type;
555          Last_Choice    : out Nat;
556          Raises_CE      : out Boolean;
557          Others_Present : out Boolean)
558       is
559          pragma Assert (Choice_Table'First = 1);
560
561          E : Entity_Id;
562
563          Enode : Node_Id;
564          --  This is where we post error messages for bounds out of range
565
566          Nb_Choices        : constant Nat := Choice_Table'Length;
567          Sort_Choice_Table : Sort_Choice_Table_Type (0 .. Nb_Choices);
568
569          Choice_Type : constant Entity_Id := Base_Type (Subtyp);
570          --  The actual type against which the discrete choices are
571          --  resolved.  Note that this type is always the base type not the
572          --  subtype of the ruling expression, index or discriminant.
573
574          Bounds_Type : Entity_Id;
575          --  The type from which are derived the bounds of the values
576          --  covered by the discrete choices (see 3.8.1 (4)). If a discrete
577          --  choice specifies a value outside of these bounds we have an error.
578
579          Bounds_Lo : Uint;
580          Bounds_Hi : Uint;
581          --  The actual bounds of the above type
582
583          Expected_Type : Entity_Id;
584          --  The expected type of each choice. Equal to Choice_Type, except
585          --  if the expression is universal,  in which case the choices can
586          --  be of any integer type.
587
588          Alt : Node_Id;
589          --  A case statement alternative or a variant in a record type
590          --  declaration
591
592          Choice : Node_Id;
593          Kind   : Node_Kind;
594          --  The node kind of the current Choice
595
596          Others_Choice : Node_Id := Empty;
597          --  Remember others choice if it is present (empty otherwise)
598
599          procedure Check (Choice : Node_Id; Lo, Hi : Node_Id);
600          --  Checks the validity of the bounds of a choice.  When the bounds
601          --  are static and no error occurred the bounds are entered into
602          --  the choices table so that they can be sorted later on.
603
604          -----------
605          -- Check --
606          -----------
607
608          procedure Check (Choice : Node_Id; Lo, Hi : Node_Id) is
609             Lo_Val : Uint;
610             Hi_Val : Uint;
611
612          begin
613             --  First check if an error was already detected on either bounds
614
615             if Etype (Lo) = Any_Type or else Etype (Hi) = Any_Type then
616                return;
617
618             --  Do not insert non static choices in the table to be sorted
619
620             elsif not Is_Static_Expression (Lo)
621               or else not Is_Static_Expression (Hi)
622             then
623                Process_Non_Static_Choice (Choice);
624                return;
625
626             --  Ignore range which raise constraint error
627
628             elsif Raises_Constraint_Error (Lo)
629               or else Raises_Constraint_Error (Hi)
630             then
631                Raises_CE := True;
632                return;
633
634             --  Otherwise we have an OK static choice
635
636             else
637                Lo_Val := Expr_Value (Lo);
638                Hi_Val := Expr_Value (Hi);
639
640                --  Do not insert null ranges in the choices table
641
642                if Lo_Val > Hi_Val then
643                   Process_Empty_Choice (Choice);
644                   return;
645                end if;
646             end if;
647
648             --  Check for low bound out of range
649
650             if Lo_Val < Bounds_Lo then
651
652                --  If the choice is an entity name, then it is a type, and
653                --  we want to post the message on the reference to this
654                --  entity. Otherwise we want to post it on the lower bound
655                --  of the range.
656
657                if Is_Entity_Name (Choice) then
658                   Enode := Choice;
659                else
660                   Enode := Lo;
661                end if;
662
663                --  Specialize message for integer/enum type
664
665                if Is_Integer_Type (Bounds_Type) then
666                   Error_Msg_Uint_1 := Bounds_Lo;
667                   Error_Msg_N ("minimum allowed choice value is^", Enode);
668                else
669                   Error_Msg_Name_1 := Choice_Image (Bounds_Lo, Bounds_Type);
670                   Error_Msg_N ("minimum allowed choice value is%", Enode);
671                end if;
672             end if;
673
674             --  Check for high bound out of range
675
676             if Hi_Val > Bounds_Hi then
677
678                --  If the choice is an entity name, then it is a type, and
679                --  we want to post the message on the reference to this
680                --  entity. Otherwise we want to post it on the upper bound
681                --  of the range.
682
683                if Is_Entity_Name (Choice) then
684                   Enode := Choice;
685                else
686                   Enode := Hi;
687                end if;
688
689                --  Specialize message for integer/enum type
690
691                if Is_Integer_Type (Bounds_Type) then
692                   Error_Msg_Uint_1 := Bounds_Hi;
693                   Error_Msg_N ("maximum allowed choice value is^", Enode);
694                else
695                   Error_Msg_Name_1 := Choice_Image (Bounds_Hi, Bounds_Type);
696                   Error_Msg_N ("maximum allowed choice value is%", Enode);
697                end if;
698             end if;
699
700             --  Store bounds in the table
701
702             --  Note: we still store the bounds, even if they are out of
703             --  range, since this may prevent unnecessary cascaded errors
704             --  for values that are covered by such an excessive range.
705
706             Last_Choice := Last_Choice + 1;
707             Sort_Choice_Table (Last_Choice).Lo   := Lo;
708             Sort_Choice_Table (Last_Choice).Hi   := Hi;
709             Sort_Choice_Table (Last_Choice).Node := Choice;
710          end Check;
711
712       --  Start of processing for Analyze_Choices
713
714       begin
715          Last_Choice    := 0;
716          Raises_CE      := False;
717          Others_Present := False;
718
719          --  If Subtyp is not a static subtype Ada 95 requires then we use
720          --  the bounds of its base type to determine the values covered by
721          --  the discrete choices.
722
723          if Is_OK_Static_Subtype (Subtyp) then
724             Bounds_Type := Subtyp;
725          else
726             Bounds_Type := Choice_Type;
727          end if;
728
729          --  Obtain static bounds of type, unless this is a generic formal
730          --  discrete type for which all choices will be non-static.
731
732          if not Is_Generic_Type (Root_Type (Bounds_Type))
733            or else Ekind (Bounds_Type) /= E_Enumeration_Type
734          then
735             Bounds_Lo := Expr_Value (Type_Low_Bound (Bounds_Type));
736             Bounds_Hi := Expr_Value (Type_High_Bound (Bounds_Type));
737          end if;
738
739          if Choice_Type = Universal_Integer then
740             Expected_Type := Any_Integer;
741          else
742             Expected_Type := Choice_Type;
743          end if;
744
745          --  Now loop through the case alternatives or record variants
746
747          Alt := First (Get_Alternatives (N));
748          while Present (Alt) loop
749
750             --  If pragma, just analyze it
751
752             if Nkind (Alt) = N_Pragma then
753                Analyze (Alt);
754
755             --  Otherwise check each choice against its base type
756
757             else
758                Choice := First (Get_Choices (Alt));
759                while Present (Choice) loop
760                   Analyze (Choice);
761                   Kind := Nkind (Choice);
762
763                   --  Choice is a Range
764
765                   if Kind = N_Range
766                     or else (Kind = N_Attribute_Reference
767                               and then Attribute_Name (Choice) = Name_Range)
768                   then
769                      Resolve (Choice, Expected_Type);
770                      Check (Choice, Low_Bound (Choice), High_Bound (Choice));
771
772                   --  Choice is a subtype name
773
774                   elsif Is_Entity_Name (Choice)
775                     and then Is_Type (Entity (Choice))
776                   then
777                      if not Covers (Expected_Type, Etype (Choice)) then
778                         Wrong_Type (Choice, Choice_Type);
779
780                      else
781                         E := Entity (Choice);
782
783                         if not Is_Static_Subtype (E) then
784                            Process_Non_Static_Choice (Choice);
785                         else
786                            Check
787                              (Choice, Type_Low_Bound (E), Type_High_Bound (E));
788                         end if;
789                      end if;
790
791                   --  Choice is a subtype indication
792
793                   elsif Kind = N_Subtype_Indication then
794                      Resolve_Discrete_Subtype_Indication
795                        (Choice, Expected_Type);
796
797                      if Etype (Choice) /= Any_Type then
798                         declare
799                            C : constant Node_Id := Constraint (Choice);
800                            R : constant Node_Id := Range_Expression (C);
801                            L : constant Node_Id := Low_Bound (R);
802                            H : constant Node_Id := High_Bound (R);
803
804                         begin
805                            E := Entity (Subtype_Mark (Choice));
806
807                            if not Is_Static_Subtype (E) then
808                               Process_Non_Static_Choice (Choice);
809
810                            else
811                               if Is_OK_Static_Expression (L)
812                                 and then Is_OK_Static_Expression (H)
813                               then
814                                  if Expr_Value (L) > Expr_Value (H) then
815                                     Process_Empty_Choice (Choice);
816                                  else
817                                     if Is_Out_Of_Range (L, E) then
818                                        Apply_Compile_Time_Constraint_Error
819                                          (L, "static value out of range",
820                                           CE_Range_Check_Failed);
821                                     end if;
822
823                                     if Is_Out_Of_Range (H, E) then
824                                        Apply_Compile_Time_Constraint_Error
825                                          (H, "static value out of range",
826                                           CE_Range_Check_Failed);
827                                     end if;
828                                  end if;
829                               end if;
830
831                               Check (Choice, L, H);
832                            end if;
833                         end;
834                      end if;
835
836                   --  The others choice is only allowed for the last
837                   --  alternative and as its only choice.
838
839                   elsif Kind = N_Others_Choice then
840                      if not (Choice = First (Get_Choices (Alt))
841                              and then Choice = Last (Get_Choices (Alt))
842                              and then Alt = Last (Get_Alternatives (N)))
843                      then
844                         Error_Msg_N
845                           ("the choice OTHERS must appear alone and last",
846                            Choice);
847                         return;
848                      end if;
849
850                      Others_Present := True;
851                      Others_Choice  := Choice;
852
853                   --  Only other possibility is an expression
854
855                   else
856                      Resolve (Choice, Expected_Type);
857                      Check (Choice, Choice, Choice);
858                   end if;
859
860                   Next (Choice);
861                end loop;
862
863                Process_Associated_Node (Alt);
864             end if;
865
866             Next (Alt);
867          end loop;
868
869          Check_Choices
870            (Sort_Choice_Table (0 .. Last_Choice),
871             Bounds_Type,
872             Others_Present or else (Choice_Type = Universal_Integer),
873             Sloc (N));
874
875          --  Now copy the sorted discrete choices
876
877          for J in 1 .. Last_Choice loop
878             Choice_Table (Choice_Table'First - 1 + J) := Sort_Choice_Table (J);
879          end loop;
880
881          --  If no others choice we are all done, otherwise we have one more
882          --  step, which is to set the Others_Discrete_Choices field of the
883          --  others choice (to contain all otherwise unspecified choices).
884          --  Skip this if CE is known to be raised.
885
886          if Others_Present and not Raises_CE then
887             Expand_Others_Choice
888               (Case_Table    => Choice_Table (1 .. Last_Choice),
889                Others_Choice => Others_Choice,
890                Choice_Type   => Bounds_Type);
891          end if;
892       end Analyze_Choices;
893
894       -----------------------
895       -- Number_Of_Choices --
896       -----------------------
897
898       function Number_Of_Choices (N : Node_Id) return Nat is
899          Alt : Node_Id;
900          --  A case statement alternative or a record variant
901
902          Choice : Node_Id;
903          Count  : Nat := 0;
904
905       begin
906          if No (Get_Alternatives (N)) then
907             return 0;
908          end if;
909
910          Alt := First_Non_Pragma (Get_Alternatives (N));
911          while Present (Alt) loop
912
913             Choice := First (Get_Choices (Alt));
914             while Present (Choice) loop
915                if Nkind (Choice) /= N_Others_Choice then
916                   Count := Count + 1;
917                end if;
918
919                Next (Choice);
920             end loop;
921
922             Next_Non_Pragma (Alt);
923          end loop;
924
925          return Count;
926       end Number_Of_Choices;
927
928    end Generic_Choices_Processing;
929
930 end Sem_Case;