home
***
CD-ROM
|
disk
|
FTP
|
other
***
search
/
Geek Gadgets 1
/
ADE-1.bin
/
ade-dist
/
gnat-2.06-src.tgz
/
tar.out
/
fsf
/
gnat
/
ada
/
sem_ch5.adb
< prev
next >
Wrap
Text File
|
1996-09-28
|
37KB
|
1,163 lines
------------------------------------------------------------------------------
-- --
-- GNAT COMPILER COMPONENTS --
-- --
-- S E M _ C H 5 --
-- --
-- B o d y --
-- --
-- $Revision: 1.166 $ --
-- --
-- Copyright (c) 1992,1993,1994,1995 NYU, All Rights Reserved --
-- --
-- GNAT is free software; you can redistribute it and/or modify it under --
-- terms of the GNU General Public License as published by the Free Soft- --
-- ware Foundation; either version 2, or (at your option) any later ver- --
-- sion. GNAT is distributed in the hope that it will be useful, but WITH- --
-- OUT ANY WARRANTY; without even the implied warranty of MERCHANTABILITY --
-- or FITNESS FOR A PARTICULAR PURPOSE. See the GNU General Public License --
-- for more details. You should have received a copy of the GNU General --
-- Public License distributed with GNAT; see file COPYING. If not, write --
-- to the Free Software Foundation, 675 Mass Ave, Cambridge, MA 02139, USA. --
-- --
------------------------------------------------------------------------------
with Atree; use Atree;
with Checks; use Checks;
with Einfo; use Einfo;
with Errout; use Errout;
with Exp_Ch7; use Exp_Ch7;
with Itypes; use Itypes;
with Namet; use Namet;
with Nlists; use Nlists;
with Output; use Output;
with Sem; use Sem;
with Sem_Ch3; use Sem_Ch3;
with Sem_Ch8; use Sem_Ch8;
with Sem_Eval; use Sem_Eval;
with Sem_Disp; use Sem_Disp;
with Sem_Res; use Sem_Res;
with Sem_Util; use Sem_Util;
with Sem_Type; use Sem_Type;
with Stand; use Stand;
with Sinfo; use Sinfo;
with Uintp; use Uintp;
package body Sem_Ch5 is
-----------------------
-- Local Subprograms --
-----------------------
procedure Analyze_Elsif_Parts (L : List_Id);
procedure Analyze_Iteration_Scheme (N : Node_Id);
function Choice_Image (Value : Uint; Ctype : Entity_Id) return Name_Id;
-- Given a Pos value of enumeration type Ctype, returns the name
-- ID of an appropriate string to be used in error message output.
------------------------
-- Analyze_Statements --
------------------------
procedure Analyze_Statements (L : List_Id) is
S : Node_Id;
begin
-- The labels declared in the statement list are reachable from
-- statements in the list.
S := First (L);
while Present (S) loop
if Nkind (S) = N_Label then
Analyze (Identifier (S));
-- If we found a label mark it as reachable, if not ignore, since
-- it means there was a conflicting declaration which will already
-- have been diagnosed (from the explicit label declaration).
if Ekind (Entity (Identifier (S))) = E_Label then
Set_Reachable (Entity (Identifier (S)));
end if;
end if;
S := Next (S);
end loop;
-- Perform semantic analysis on all statements
S := First (L);
while Present (S) loop
if Nkind (S) /= N_Label then
Analyze (S);
end if;
S := Next (S);
end loop;
-- Make labels unreachable. Visibility is not sufficient, because
-- labels in one if-branch for example are not reachable from the
-- other branch, even though their declarations are in the enclosing
-- declarative part.
S := First (L);
while Present (S) loop
if Nkind (S) = N_Label then
Set_Reachable (Entity (Identifier (S)), False);
end if;
S := Next (S);
end loop;
end Analyze_Statements;
------------------------
-- Analyze_Assignment --
------------------------
procedure Analyze_Assignment (N : Node_Id) is
Lhs : constant Node_Id := Name (N);
Rhs : constant Node_Id := Expression (N);
T1, T2 : Entity_Id;
Decl : Node_Id;
begin
Analyze (Lhs);
Analyze (Rhs);
T1 := Etype (Lhs);
-- In the most general case, both Lhs and Rhs can be overloaded, and we
-- must compute the intersection of the possible types on each side.
if Is_Overloaded (Lhs) then
declare
I : Interp_Index;
It : Interp;
begin
T1 := Any_Type;
Get_First_Interp (Lhs, I, It);
while Present (It.Typ) loop
if Has_Compatible_Type (Rhs, It.Typ) then
if T1 /= Any_Type then
Error_Msg_N
("ambiguous left-hand side in assignment", Lhs);
exit;
else
T1 := It.Typ;
end if;
end if;
Get_Next_Interp (I, It);
end loop;
end;
if T1 = Any_Type then
Error_Msg_N
("no valid types for left-hand side for assignment", Lhs);
return;
end if;
end if;
Resolve (Lhs, T1);
-- Immediate exit with error if left side is procedure name or label,
-- since otherwise resolving the right side will generate a confusing
-- and useless error message.
if Etype (Lhs) = Standard_Void_Type then
Error_Msg_N
("left hand side of assignment must be a variable", Lhs);
return;
end if;
if not Is_Variable (Lhs) then
if Is_Entity_Name (Lhs)
and then Ekind (Entity (Lhs)) = E_In_Parameter
then
Error_Msg_N ("assignment to IN mode parameter not allowed", Lhs);
elsif Is_Entity_Name (Lhs)
and then Is_Protected_Type (Scope (Current_Scope))
and then Ekind (Current_Scope) = E_Function
then
Error_Msg_N
("within a protected function the protected object is constant",
Lhs);
else
Error_Msg_N
("left hand side of assignment must be a variable", Lhs);
end if;
return;
elsif Is_Limited_Type (T1)
and then not Assignment_OK (Lhs)
then
Error_Msg_N
("left hand of assignment must not be limited type", Lhs);
return;
end if;
-- If the nominal subtype of the left-hand side is unconstrained,
-- use the actual subtype, or construct it if not available.
if Is_Entity_Name (Lhs)
and then (Ekind (Entity (Lhs)) = E_Out_Parameter
or else Ekind (Entity (Lhs)) = E_In_Out_Parameter
or else Ekind (Entity (Lhs)) = E_Generic_In_Out_Parameter)
then
T1 := Actual_Subtype (Entity (Lhs));
-- should we be using Get_Actual_Subtype here ???
elsif Nkind (Lhs) = N_Selected_Component
or else Nkind (Lhs) = N_Explicit_Dereference
then
Decl := Build_Actual_Subtype_Of_Component (T1, Lhs);
if Present (Decl) then
Insert_Before (N, Decl);
Mark_Rewrite_Insertion (Decl);
Analyze (Decl);
T1 := Defining_Identifier (Decl);
Set_Etype (Lhs, T1);
end if;
elsif Nkind (Lhs) = N_Slice then
-- Use constrained subtype created for slice.
T1 := Etype (Lhs);
end if;
Resolve (Rhs, T1);
T2 := Etype (Rhs);
if Covers (T1, T2) then
null;
else
Wrong_Type (Rhs, Etype (Lhs));
return;
end if;
if T1 = Any_Type or else T2 = Any_Type then
return;
end if;
if Is_Class_Wide_Type (T1)
and then Is_Tag_Indeterminate (Rhs)
then
Propagate_Tag (Lhs, Rhs);
end if;
Apply_Range_Check (Rhs, Etype (Rhs), Etype (Lhs));
if not Length_Checks_Suppressed (Etype (Lhs)) then
Set_Do_Length_Check (N);
end if;
Apply_Static_Length_Check (Rhs, Etype (Rhs), Etype (Lhs));
end Analyze_Assignment;
-----------------------------
-- Analyze_Block_Statement --
-----------------------------
procedure Analyze_Block_Statement (N : Node_Id) is
Decls : constant List_Id := Declarations (N);
Id : Node_Id;
begin
Id := Identifier (N);
if Present (Id) then
Analyze (Id);
Id := Entity (Id);
Set_Ekind (Id, E_Block);
else
Id := New_Internal_Entity (E_Block, Current_Scope, Sloc (N), 'B');
end if;
Set_Etype (Id, Standard_Void_Type);
New_Scope (Id);
if Present (Decls) then
Analyze_Declarations (Decls);
Check_Completion;
end if;
Analyze (Handled_Statement_Sequence (N));
if Present (Exception_Handlers (Handled_Statement_Sequence (N))) then
declare
S : Entity_Id := Scope (Id);
begin
-- Indicate that enclosing scopes contain a block with handlers.
-- Only non-generic scopes need to be marked.
loop
Set_Has_Nested_Block_With_Handler (S);
exit when Is_Overloadable (S)
or else Ekind (S) = E_Package
or else Ekind (S) = E_Generic_Function
or else Ekind (S) = E_Generic_Package
or else Ekind (S) = E_Generic_Procedure;
S := Scope (S);
end loop;
end;
end if;
End_Scope;
end Analyze_Block_Statement;
----------------------------
-- Analyze_Case_Statement --
----------------------------
procedure Analyze_Case_Statement (N : Node_Id) is
Alt : Node_Id;
Case_Table : Case_Table_Type (1 .. Number_Of_Case_Choices (N));
Choice : Node_Id;
Choice_Count : Nat := 0;
E : Entity_Id;
Exp : Node_Id;
Exp_Btype : Entity_Id;
Exp_Type : Entity_Id;
Exp_Lo, Exp_Hi : Uint;
Hi : Node_Id;
Invalid_Case : Boolean := False;
Kind : Node_Kind;
Lo : Node_Id;
Others_Present : Boolean := False;
procedure Check_Choice (Lo, Hi : Node_Id; Choice : Node_Id);
-- Check_Choice checks whether the given bounds of a choice are
-- static and valid for the range of the discrete subtype. If not,
-- a message is issued, otherwise the bounds are entered into
-- the case table.
procedure Check_Choice (Lo, Hi : Node_Id; Choice : Node_Id) is
begin
if not Is_Static_Expression (Lo)
or else not Is_Static_Expression (Hi)
then
Error_Msg_N
("choice given in case statement is not static", Choice);
Invalid_Case := True;
return;
end if;
if Choice_In_Range (Lo, Hi, Exp_Lo, Exp_Hi, Exp_Btype) then
Choice_Count := Choice_Count + 1;
Case_Table (Choice_Count).Choice_Lo := Lo;
Case_Table (Choice_Count).Choice_Hi := Hi;
Case_Table (Choice_Count).Choice_Node := Choice;
end if;
end Check_Choice;
-- Start of processing for Analyze_Case_Statement
begin
-- Check that the case expression is of a discrete type and that
-- its range is static, and find the length of the range.
Exp := Expression (N);
Analyze (Exp);
Resolve (Exp, Any_Discrete);
Exp_Type := Etype (Exp);
-- If universal, force Standard.Integer, else use given type
if Exp_Type = Universal_Integer then
Exp_Btype := Standard_Integer;
else
Exp_Btype := Base_Type (Exp_Type);
end if;
-- The expression must be of a discrete type which must be determinable
-- independently of the context in which the expression occurs, but
-- using the fact that the expression must be of a discrete type.
-- Moreover, the type this expression must not be a generic formal type.
if not Is_Discrete_Type (Exp_Btype) then
Error_Msg_N ("case expression not of discrete type", Exp);
return;
elsif Is_Generic_Type (Exp_Btype) then
Error_Msg_N ("case expression cannot be of a generic type", Exp);
return;
end if;
if Is_OK_Static_Subtype (Exp_Type) then
Exp_Lo := Expr_Value (Type_Low_Bound (Exp_Type));
Exp_Hi := Expr_Value (Type_High_Bound (Exp_Type));
else
Exp_Lo := Expr_Value (Type_Low_Bound (Exp_Btype));
Exp_Hi := Expr_Value (Type_High_Bound (Exp_Btype));
end if;
-- The simple expressions and discrete ranges given as choices
-- in a case statement must be static (RM 5.4) and in range.
Alt := First (Alternatives (N));
while Present (Alt) loop
Choice := First (Discrete_Choices (Alt));
while Present (Choice) loop
-- Type check the choice and ensure that it is static,
-- that it is in the range for the expression subtype, and
-- that it appears no more than once as a value possibility.
Analyze (Choice);
Kind := Nkind (Choice);
if Kind = N_Range then
Resolve (Choice, Exp_Btype);
Check_Choice (Low_Bound (Choice), High_Bound (Choice), Choice);
elsif Is_Entity_Name (Choice)
and then Is_Type (Entity (Choice))
then
if not Covers (Exp_Btype, Etype (Choice)) then
Wrong_Type (Choice, Exp_Btype);
end if;
E := Entity (Choice);
Lo := Type_Low_Bound (E);
Hi := Type_High_Bound (E);
Check_Choice (Lo, Hi, Choice);
elsif Kind = N_Subtype_Indication then
Resolve_Discrete_Subtype_Indication (Choice, Exp_Btype);
if Etype (Choice) /= Any_Type then
declare
Constr : constant Node_Id := Constraint (Choice);
Rang : constant Node_Id := Range_Expression (Constr);
Subt : constant Entity_Id :=
Entity (Subtype_Mark (Choice));
begin
Lo := Low_Bound (Rang);
Hi := High_Bound (Rang);
if Is_OK_Static_Expression (Lo)
and then Is_OK_Static_Expression (Hi)
then
if Expr_Value (Lo) <= Expr_Value (Hi) then
if Is_Out_Of_Range (Lo, Subt) then
Compile_Time_Constraint_Error
(Lo, "static value out of range");
end if;
if Is_Out_Of_Range (Hi, Subt) then
Compile_Time_Constraint_Error
(Hi, "static value out of range");
end if;
end if;
end if;
Check_Choice (Lo, Hi, Choice);
end;
end if;
-- The choice others is only allowed for the last alternative and
-- as its only choice; it stands for all values (possibly none)
-- not given in the choices of previous statement alternatives.
elsif Kind = N_Others_Choice then
if not (Choice = First (Discrete_Choices (Alt))
and then Choice = Last (Discrete_Choices (Alt))
and then Alt = Last (Alternatives (N)))
then
Error_Msg_N
("the choice OTHERS must appear alone and last", Choice);
return;
end if;
Others_Present := True;
-- Only other possibility is an expression
else
Resolve (Choice, Exp_Btype);
if Etype (Choice) /= Any_Type then
Check_Choice (Choice, Choice, Choice);
end if;
end if;
Choice := Next (Choice);
end loop;
Analyze_Statements (Statements (Alt));
Alt := Next (Alt);
end loop;
if not Invalid_Case and then Choice_Count > 0 then
Check_Case_Choices
(Case_Table (1 .. Choice_Count), N, Exp_Type, Others_Present);
end if;
end Analyze_Case_Statement;
-------------------------
-- Analyze_Elsif_Parts --
-------------------------
procedure Analyze_Elsif_Parts (L : List_Id) is
N : constant Node_Id := Parent (L);
Cond : constant Node_Id := Condition (N);
E : Node_Id;
begin
E := First (L);
while Present (E) loop
declare
Cond : constant Node_Id := Condition (E);
begin
Analyze (Cond);
Resolve (Cond, Any_Boolean);
end;
Analyze_Statements (Then_Statements (E));
E := Next (E);
end loop;
end Analyze_Elsif_Parts;
----------------------------
-- Analyze_Exit_Statement --
----------------------------
-- If the exit includes a name, it must be the name of a currently open
-- loop. Otherwise there must be an innermost open loop on the stack,
-- to which the statement implicitly refers.
procedure Analyze_Exit_Statement (N : Node_Id) is
Target : constant Node_Id := Name (N);
Cond : constant Node_Id := Condition (N);
Scope_Id : Entity_Id;
U_Name : Entity_Id;
Kind : Entity_Kind;
begin
if Present (Target) then
Analyze (Target);
U_Name := Entity (Target);
if not In_Open_Scopes (U_Name) or else Ekind (U_Name) /= E_Loop then
Error_Msg_N ("invalid loop name in exit statement", N);
return;
else
Set_Has_Exit (U_Name);
end if;
end if;
for J in reverse 0 .. Scope_Stack.Last loop
Scope_Id := Scope_Stack.Table (J).Entity;
Kind := Ekind (Scope_Id);
if Kind = E_Loop and (No (Target) or Scope_Id = U_Name) then
exit;
elsif Kind = E_Block or else Kind = E_Loop then
null;
else
Error_Msg_N
("cannot exit from program unit or accept statement", N);
exit;
end if;
end loop;
-- Verify that if present the condition is a Boolean expression.
if Present (Cond) then
Analyze (Cond);
Resolve (Cond, Any_Boolean);
end if;
end Analyze_Exit_Statement;
----------------------------
-- Analyze_Goto_Statement --
----------------------------
procedure Analyze_Goto_Statement (N : Node_Id) is
Label : constant Node_Id := Name (N);
Scope_Id : Entity_Id;
Label_Scope : Entity_Id;
begin
Analyze (Label);
if Entity (Label) = Any_Id then
return;
elsif Ekind (Entity (Label)) /= E_Label then
Error_Msg_N ("target of goto statement must be a label", Label);
return;
elsif not Reachable (Entity (Label)) then
Error_Msg_N ("target of goto statement is not reachable", Label);
return;
end if;
Label_Scope := Scope (Entity (Label));
for J in reverse 0 .. Scope_Stack.Last loop
Scope_Id := Scope_Stack.Table (J).Entity;
exit when (Label_Scope = Scope_Id)
or else (Ekind (Scope_Id) /= E_Block
and then Ekind (Scope_Id) /= E_Loop);
end loop;
if Scope_Id /= Label_Scope then
Error_Msg_N
("cannot exit from program unit or accept statement", N);
end if;
end Analyze_Goto_Statement;
--------------------------
-- Analyze_If_Statement --
--------------------------
procedure Analyze_If_Statement (N : Node_Id) is
Cond : constant Node_Id := Condition (N);
begin
Analyze (Cond);
Resolve (Cond, Any_Boolean);
Analyze_Statements (Then_Statements (N));
if Present (Elsif_Parts (N)) then
Analyze_Elsif_Parts (Elsif_Parts (N));
end if;
if Present (Else_Statements (N)) then
Analyze_Statements (Else_Statements (N));
end if;
end Analyze_If_Statement;
----------------------------------------
-- Analyze_Implicit_Label_Declaration --
----------------------------------------
-- An implicit label declaration is generated in the innermost
-- enclosing declarative part. This is done for labels as well as
-- block and loop names.
procedure Analyze_Implicit_Label_Declaration (N : Node_Id) is
Id : Node_Id := Defining_Identifier (N);
begin
Enter_Name (Id);
Set_Ekind (Id, E_Label);
Set_Etype (Id, Standard_Void_Type);
end Analyze_Implicit_Label_Declaration;
------------------------------
-- Analyze_Iteration_Scheme --
------------------------------
procedure Analyze_Iteration_Scheme (N : Node_Id) is
begin
-- For an infinite loop, there is no iteration scheme
if No (N) then
return;
else
declare
Cond : constant Node_Id := Condition (N);
begin
-- For WHILE loop, verify that the condition is a Boolean
-- expression and resolve and check it.
if Present (Cond) then
Analyze (Cond);
Resolve (Cond, Any_Boolean);
-- Else we have a FOR loop
else
declare
L : constant Node_Id := Loop_Parameter_Specification (N);
Id : constant Node_Id := Defining_Identifier (L);
D : constant Node_Id := Discrete_Subtype_Definition (L);
begin
Analyze (D);
if not Is_Discrete_Type (Etype (D)) then
Wrong_Type (D, Any_Discrete);
Set_Etype (D, Any_Type);
end if;
Make_Index (D, L);
Enter_Name (Id);
Set_Ekind (Id, E_Loop_Parameter);
Set_Etype (Id, Etype (D));
end;
end if;
end;
end if;
end Analyze_Iteration_Scheme;
----------------------------
-- Analyze_Loop_Statement --
----------------------------
procedure Analyze_Loop_Statement (N : Node_Id) is
Id : Node_Id := Identifier (N);
begin
if Present (Id) then
-- Make name visible, e.g. for use in exit statements
Analyze (Id);
Id := Entity (Id);
-- If we found a label, mark it's type. If not, ignore it, since it
-- means we have a conflicting declaration, which would already have
-- been diagnosed at declaration time.
if Ekind (Id) = E_Label then
Set_Ekind (Id, E_Loop);
end if;
else
Id := New_Internal_Entity (E_Loop, Current_Scope, Sloc (N), 'L');
Set_Etype (Id, Standard_Void_Type);
end if;
New_Scope (Id);
Analyze_Iteration_Scheme (Iteration_Scheme (N));
Analyze_Statements (Statements (N));
End_Scope;
end Analyze_Loop_Statement;
----------------------------
-- Analyze_Null_Statement --
----------------------------
-- Note: the semantics of the null statement is implemented by a single
-- null statement, too bad everything isn't as simple as this!
procedure Analyze_Null_Statement (N : Node_Id) is
begin
null;
end Analyze_Null_Statement;
------------------------------
-- Analyze_Return_Statement --
------------------------------
procedure Analyze_Return_Statement (N : Node_Id) is
Expr : Node_Id;
Scope_Id : Entity_Id;
Kind : Entity_Kind;
begin
-- Find subprogram or accept statement enclosing the return statement
for J in reverse 0 .. Scope_Stack.Last loop
Scope_Id := Scope_Stack.Table (J).Entity;
exit when Ekind (Scope_Id) /= E_Block and then
Ekind (Scope_Id) /= E_Loop;
end loop;
Kind := Ekind (Scope_Id);
Expr := Expression (N);
if Kind = E_Package then
Error_Msg_N ("return not allowed in package body", N);
elsif Present (Expr) then
if Kind = E_Function or else Kind = E_Generic_Function then
Set_Return_Present (Scope_Id);
Set_Return_Type (N, Etype (Scope_Id));
Analyze (Expr);
Resolve (Expr, Etype (Scope_Id));
Apply_Range_Check (Expr, Etype (Expr), Etype (Scope_Id));
-- ??? a real static accessibility check is needed when
-- returning by reference. For now just check the most obvious
-- cases
if Is_Return_By_Reference_Type (Etype (Scope_Id))
and then Is_Entity_Name (Expr)
then
if Scope (Entity (Expr)) = Scope_Id
or else Scope (Scope (Entity (Expr))) = Scope_Id
or else Scope (Scope (Scope (Entity (Expr)))) = Scope_Id
then
Error_Msg_N ("cannot return a local value by reference", N);
end if;
end if;
elsif Kind = E_Procedure or else Kind = E_Generic_Procedure then
Error_Msg_N ("procedure cannot return value (use function)", N);
else
Error_Msg_N ("accept statement cannot return value", N);
end if;
elsif Kind = E_Function or Kind = E_Generic_Function then
Error_Msg_N ("missing expression in return from function", N);
end if;
end Analyze_Return_Statement;
---------------------
-- Choice_In_Range --
---------------------
function Choice_In_Range
(Lo, Hi : Node_Id;
Discr_Lo : Uint;
Discr_Hi : Uint;
Btype : Entity_Id)
return Boolean
is
Lo_Val, Hi_Val : Uint;
begin
-- Ignore range which raises constraint error (error already posted)
if Raises_Constraint_Error (Lo)
or else Raises_Constraint_Error (Hi)
then
return False;
-- Otherwise we have an OK static choice
else
Lo_Val := Expr_Value (Lo);
Hi_Val := Expr_Value (Hi);
end if;
-- Ignore null range
if Lo_Val > Hi_Val then
return False;
end if;
-- Check for bound out of range. Note that we still store the
-- bounds in the table, even if they are out of range, since
-- this may prevent unnecessary cascaded errors for values
-- that are covered by such an excessive range.
if Lo_Val < Discr_Lo then
if Is_Integer_Type (Btype) then
Error_Msg_Uint_1 := Discr_Lo;
Error_Msg_N ("minimum allowed choice value is^", Hi);
else
Error_Msg_Name_1 := Choice_Image (Discr_Lo, Btype);
Error_Msg_N ("minimum allowed choice value is%", Lo);
end if;
elsif Hi_Val > Discr_Hi then
if Is_Integer_Type (Btype) then
Error_Msg_Uint_1 := Discr_Hi;
Error_Msg_N ("maximum allowed choice value is^", Hi);
else
Error_Msg_Name_1 := Choice_Image (Discr_Hi, Btype);
Error_Msg_N ("maximum allowed choice value is%", Hi);
end if;
end if;
-- Will store range in table
return True;
end Choice_In_Range;
------------------------
-- Check_Case_Choices --
------------------------
procedure Check_Case_Choices
(Case_Table : in out Case_Table_Type;
N : Node_Id;
Choice_Type : Entity_Id;
Others_Present : Boolean)
is
Choice : Node_Id;
First_Msg : Boolean := True;
Exp_Lo : Node_Id;
Exp_Hi : Node_Id;
Hi : Uint;
Lo : Uint;
Msg_Sloc : Source_Ptr;
Previous_Hi : Uint;
procedure Issue_Msg (Value1, Value2 : Uint);
-- Issue an error message indicating that there are missing choices,
-- followed by the image of the missing choices themselves which lie
-- between Value1 and Value2 exclusive. If there is more than one
-- choice missing print the first and last of the range. Since this
-- can be called several times for the same case statement or variant
-- part, make sure to print the error message itself only once per
-- case statement or variant part.
procedure Issue_Msg (Value1, Value2 : Uint) is
begin
if First_Msg then
Msg_Sloc := Sloc (N);
First_Msg := False;
end if;
-- Get range of missing values
Error_Msg_Uint_1 := Value1 + 1;
Error_Msg_Uint_2 := Value2 - 1;
-- Case of only one value that is missing
if Error_Msg_Uint_1 = Error_Msg_Uint_2 then
if Is_Integer_Type (Choice_Type) then
Error_Msg ("missing case value: ^!", Msg_Sloc);
else
Error_Msg_Name_1 :=
Choice_Image (Error_Msg_Uint_1, Choice_Type);
Error_Msg ("missing case value: %!", Msg_Sloc);
end if;
-- More than one choice value, so print range of values
else
if Is_Integer_Type (Choice_Type) then
Error_Msg ("missing case values: ^ .. ^!", Msg_Sloc);
else
Error_Msg_Name_1 :=
Choice_Image (Error_Msg_Uint_1, Choice_Type);
Error_Msg_Name_2 :=
Choice_Image (Error_Msg_Uint_2, Choice_Type);
Error_Msg ("missing case values: % .. %!", Msg_Sloc);
end if;
end if;
end Issue_Msg;
-- Start processing for Check_Case_Choices
begin
Sort_Case_Table (Case_Table);
-- If the subtype of the discriminant is static, then each value of this
-- subtype must be represented once and only once in the set of choices
-- of the variant part, and no other value is allowed. Otherwise, each
-- value of the (base) type of the discriminant must be represented once
-- and only once in the set of choices. [LRM 3.7.3]
-- If the expression is the name of an object whose subtype is static,
-- then each value of this subtype must be represented once and only
-- once in the set of choices of the case statement, and no other value
-- is allowed. Otherwise, for other forms of expression, each value
-- of the (base) type of the expression must be represented once and
-- only once in the set of choices, and no other value is allowed.
if Is_OK_Static_Subtype (Choice_Type) then
Exp_Lo := Type_Low_Bound (Choice_Type);
Exp_Hi := Type_High_Bound (Choice_Type);
else
Exp_Lo := Type_Low_Bound (Base_Type (Choice_Type));
Exp_Hi := Type_High_Bound (Base_Type (Choice_Type));
end if;
Lo := Expr_Value (Case_Table (Case_Table'First).Choice_Lo);
Hi := Expr_Value (Case_Table (Case_Table'First).Choice_Hi);
Previous_Hi := Expr_Value (Case_Table (Case_Table'First).Choice_Hi);
if not Others_Present and then Expr_Value (Exp_Lo) < Lo then
Issue_Msg (Expr_Value (Exp_Lo) - 1, Lo);
end if;
for J in Case_Table'First + 1 .. Case_Table'Last loop
Lo := Expr_Value (Case_Table (J).Choice_Lo);
Hi := Expr_Value (Case_Table (J).Choice_Hi);
Choice := Case_Table (J).Choice_Node;
if Lo <= Previous_Hi then
Error_Msg_Sloc := Sloc (Case_Table (J - 1).Choice_Node);
Error_Msg_N ("duplication of choice value#", Choice);
elsif not Others_Present
and then Lo /= Previous_Hi + 1
then
Issue_Msg (Previous_Hi, Lo);
end if;
Previous_Hi := Hi;
end loop;
if not Others_Present and then Expr_Value (Exp_Hi) > Hi then
Issue_Msg (Hi, Expr_Value (Exp_Hi) + 1);
end if;
end Check_Case_Choices;
------------------
-- Choice_Image --
------------------
function Choice_Image (Value : Uint; Ctype : Entity_Id) return Name_Id is
Rtp : constant Entity_Id := Root_Type (Ctype);
Lit : Entity_Id;
C : Int;
begin
-- For character, or wide character. If we are in 7-bit ASCII graphic
-- range, then build and return appropriate character literal name
if Rtp = Standard_Character
or else Rtp = Standard_Wide_Character
then
C := UI_To_Int (Value);
if C in 16#20# .. 16#7E# then
Name_Buffer (1) := ''';
Name_Buffer (2) := Character'Val (C);
Name_Buffer (3) := ''';
Name_Len := 3;
return Name_Find;
end if;
-- For user defined enumeration type, find enum/char literal
else
Lit := First_Literal (Rtp);
for J in 1 .. UI_To_Int (Value) loop
Lit := Next_Literal (Lit);
end loop;
-- If enumeration literal, just return its value
if Nkind (Lit) = N_Defining_Identifier then
return Chars (Lit);
-- For character literal, get the name and use it if it is
-- for a 7-bit ASCII graphic character in 16#20#..16#7E#.
else
Get_Decoded_Name_String (Chars (Lit));
if Name_Len = 3
and then Name_Buffer (2) in
Character'Val (16#20#) .. Character'Val (16#7E#)
then
return Chars (Lit);
end if;
end if;
end if;
-- If we fall through, we have a character literal which is not in
-- the 7-bit ASCII graphic set. For such cases, we construct the
-- name "type'val(nnn)" where type is the choice type, and nnn is
-- the pos value passed as an argument to Choice_Image.
Get_Name_String (Chars (Ctype));
Name_Len := Name_Len + 1;
Name_Buffer (Name_Len) := ''';
Name_Len := Name_Len + 1;
Name_Buffer (Name_Len) := 'v';
Name_Len := Name_Len + 1;
Name_Buffer (Name_Len) := 'a';
Name_Len := Name_Len + 1;
Name_Buffer (Name_Len) := 'l';
Name_Len := Name_Len + 1;
Name_Buffer (Name_Len) := '(';
UI_Image (Value);
for J in 1 .. UI_Image_Length loop
Name_Len := Name_Len + 1;
Name_Buffer (Name_Len) := UI_Image_Buffer (J);
end loop;
Name_Len := Name_Len + 1;
Name_Buffer (Name_Len) := ')';
return Name_Find;
end Choice_Image;
----------------------------
-- Number_Of_Case_Choices --
----------------------------
function Number_Of_Case_Choices (N : Node_Id) return Nat is
Alt_or_Var : Node_Id;
Choice : Node_Id;
Count : Nat := 0;
begin
-- The iteration uses different access functions depending on whether
-- it is processing a case statement or a variant part here.
if Nkind (N) = N_Case_Statement then
Alt_or_Var := First (Alternatives (N));
else -- N_Variant_Part
Alt_or_Var := First (Variants (N));
end if;
while Present (Alt_or_Var) loop
Choice := First (Discrete_Choices (Alt_or_Var));
while Present (Choice) loop
if Nkind (Choice) /= N_Others_Choice then
Count := Count + 1;
end if;
Choice := Next (Choice);
end loop;
Alt_or_Var := Next (Alt_or_Var);
end loop;
return Count;
end Number_Of_Case_Choices;
---------------------
-- Sort_Case_Table --
---------------------
procedure Sort_Case_Table (Case_Table : in out Case_Table_Type) is
L : Int := Case_Table'First;
U : Int := Case_Table'Last;
K : Int;
J : Int;
T : Case_Bounds;
begin
K := L;
while K /= U loop
T := Case_Table (K + 1);
J := K + 1;
while J /= L
and then Expr_Value (Case_Table (J - 1).Choice_Lo) >
Expr_Value (T.Choice_Lo)
loop
Case_Table (J) := Case_Table (J - 1);
J := J - 1;
end loop;
Case_Table (J) := T;
K := K + 1;
end loop;
end Sort_Case_Table;
end Sem_Ch5;