Commit 0503c53a by Robert Dewar Committed by Arnaud Charlet

itypes.adb (Create_Itype): Use new name Access_Subprogram_Kind

2008-03-26  Robert Dewar  <dewar@adacore.com>

	* itypes.adb (Create_Itype): Use new name Access_Subprogram_Kind

	* sem_ch13.adb (Validate_Unchecked_Conversion): Give warning for
	unchecked conversion for different conventions only for subprogram
	pointers or on VMS.

From-SVN: r133570
parent f88ecba0
...@@ -68,7 +68,7 @@ package body Itypes is ...@@ -68,7 +68,7 @@ package body Itypes is
Set_Is_Frozen (Typ); Set_Is_Frozen (Typ);
end if; end if;
if Ekind in Access_Subprogram_Type_Kind then if Ekind in Access_Subprogram_Kind then
Set_Can_Use_Internal_Rep (Typ, not Always_Compatible_Rep_On_Target); Set_Can_Use_Internal_Rep (Typ, not Always_Compatible_Rep_On_Target);
end if; end if;
......
...@@ -6,7 +6,7 @@ ...@@ -6,7 +6,7 @@
-- -- -- --
-- B o d y -- -- B o d y --
-- -- -- --
-- Copyright (C) 1992-2007, Free Software Foundation, Inc. -- -- Copyright (C) 1992-2008, Free Software Foundation, Inc. --
-- -- -- --
-- GNAT is free software; you can redistribute it and/or modify it under -- -- 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- -- -- terms of the GNU General Public License as published by the Free Soft- --
...@@ -180,17 +180,16 @@ package body Sem_Ch13 is ...@@ -180,17 +180,16 @@ package body Sem_Ch13 is
and then Attribute_Name (N) = Name_Address and then Attribute_Name (N) = Name_Address
then then
declare declare
Nam : Node_Id := Prefix (N); P : Node_Id;
begin begin
while False P := Prefix (N);
or else Nkind (Nam) = N_Selected_Component while Nkind_In (P, N_Selected_Component, N_Indexed_Component) loop
or else Nkind (Nam) = N_Indexed_Component P := Prefix (P);
loop
Nam := Prefix (Nam);
end loop; end loop;
if Is_Entity_Name (Nam) then if Is_Entity_Name (P) then
return Entity (Nam); return Entity (P);
end if; end if;
end; end;
end if; end if;
...@@ -1392,6 +1391,9 @@ package body Sem_Ch13 is ...@@ -1392,6 +1391,9 @@ package body Sem_Ch13 is
Set_Has_Small_Clause (U_Ent); Set_Has_Small_Clause (U_Ent);
Set_Has_Small_Clause (Implicit_Base); Set_Has_Small_Clause (Implicit_Base);
Set_Has_Non_Standard_Rep (Implicit_Base); Set_Has_Non_Standard_Rep (Implicit_Base);
-- Recompute RM_Size, but shouldn't this be done in Freeze???
Set_Discrete_RM_Size (U_Ent); Set_Discrete_RM_Size (U_Ent);
end if; end if;
end Small; end Small;
...@@ -1749,10 +1751,10 @@ package body Sem_Ch13 is ...@@ -1749,10 +1751,10 @@ package body Sem_Ch13 is
while Present (Decl) loop while Present (Decl) loop
DeclO := Original_Node (Decl); DeclO := Original_Node (Decl);
if Comes_From_Source (DeclO) if Comes_From_Source (DeclO)
and then Nkind (DeclO) /= N_Pragma and not Nkind_In (DeclO, N_Pragma,
and then Nkind (DeclO) /= N_Use_Package_Clause N_Use_Package_Clause,
and then Nkind (DeclO) /= N_Use_Type_Clause N_Use_Type_Clause,
and then Nkind (DeclO) /= N_Implicit_Label_Declaration N_Implicit_Label_Declaration)
then then
Error_Msg_N Error_Msg_N
("this declaration not allowed in machine code subprogram", ("this declaration not allowed in machine code subprogram",
...@@ -1769,9 +1771,9 @@ package body Sem_Ch13 is ...@@ -1769,9 +1771,9 @@ package body Sem_Ch13 is
while Present (Stmt) loop while Present (Stmt) loop
StmtO := Original_Node (Stmt); StmtO := Original_Node (Stmt);
if Comes_From_Source (StmtO) if Comes_From_Source (StmtO)
and then Nkind (StmtO) /= N_Pragma and then not Nkind_In (StmtO, N_Pragma,
and then Nkind (StmtO) /= N_Label N_Label,
and then Nkind (StmtO) /= N_Code_Statement N_Code_Statement)
then then
Error_Msg_N Error_Msg_N
("this statement is not allowed in machine code subprogram", ("this statement is not allowed in machine code subprogram",
...@@ -2284,7 +2286,7 @@ package body Sem_Ch13 is ...@@ -2284,7 +2286,7 @@ package body Sem_Ch13 is
-- The only pragma of interest is Complete_Representation -- The only pragma of interest is Complete_Representation
if Chars (CC) = Name_Complete_Representation then if Pragma_Name (CC) = Name_Complete_Representation then
CR_Pragma := CC; CR_Pragma := CC;
end if; end if;
...@@ -2346,13 +2348,12 @@ package body Sem_Ch13 is ...@@ -2346,13 +2348,12 @@ package body Sem_Ch13 is
elsif Present (Component_Clause (Comp)) then elsif Present (Component_Clause (Comp)) then
-- Diagose duplicate rep clause, or check consistency -- Diagose duplicate rep clause, or check consistency
-- if this is inherited component. In a double fault, -- if this is an inherited component. In a double fault,
-- there may be a duplicate inconsistent clause for an -- there may be a duplicate inconsistent clause for an
-- inherited component. -- inherited component.
if if Scope (Original_Record_Component (Comp)) = Rectype
Scope (Original_Record_Component (Comp)) = Rectype or else Parent (Component_Clause (Comp)) = N
or else Parent (Component_Clause (Comp)) = N
then then
Error_Msg_Sloc := Sloc (Component_Clause (Comp)); Error_Msg_Sloc := Sloc (Component_Clause (Comp));
Error_Msg_N ("component clause previously given#", CC); Error_Msg_N ("component clause previously given#", CC);
...@@ -2360,7 +2361,6 @@ package body Sem_Ch13 is ...@@ -2360,7 +2361,6 @@ package body Sem_Ch13 is
else else
declare declare
Rep1 : constant Node_Id := Component_Clause (Comp); Rep1 : constant Node_Id := Component_Clause (Comp);
begin begin
if Intval (Position (Rep1)) /= if Intval (Position (Rep1)) /=
Intval (Position (CC)) Intval (Position (CC))
...@@ -2371,7 +2371,6 @@ package body Sem_Ch13 is ...@@ -2371,7 +2371,6 @@ package body Sem_Ch13 is
then then
Error_Msg_N ("component clause inconsistent " Error_Msg_N ("component clause inconsistent "
& "with representation of ancestor", CC); & "with representation of ancestor", CC);
elsif Warn_On_Redundant_Constructs then elsif Warn_On_Redundant_Constructs then
Error_Msg_N ("?redundant component clause " Error_Msg_N ("?redundant component clause "
& "for inherited component!", CC); & "for inherited component!", CC);
...@@ -2467,30 +2466,30 @@ package body Sem_Ch13 is ...@@ -2467,30 +2466,30 @@ package body Sem_Ch13 is
end loop; end loop;
-- Now that we have processed all the component clauses, check for -- Now that we have processed all the component clauses, check for
-- overlap. We have to leave this till last, since the components -- overlap. We have to leave this till last, since the components can
-- can appear in any arbitrary order in the representation clause. -- appear in any arbitrary order in the representation clause.
-- We do not need this check if all specified ranges were monotonic, -- We do not need this check if all specified ranges were monotonic,
-- as recorded by Overlap_Check_Required being False at this stage. -- as recorded by Overlap_Check_Required being False at this stage.
-- This first section checks if there are any overlapping entries -- This first section checks if there are any overlapping entries at
-- at all. It does this by sorting all entries and then seeing if -- all. It does this by sorting all entries and then seeing if there are
-- there are any overlaps. If there are none, then that is decisive, -- any overlaps. If there are none, then that is decisive, but if there
-- but if there are overlaps, they may still be OK (they may result -- are overlaps, they may still be OK (they may result from fields in
-- from fields in different variants). -- different variants).
if Overlap_Check_Required then if Overlap_Check_Required then
Overlap_Check1 : declare Overlap_Check1 : declare
OC_Fbit : array (0 .. Ccount) of Uint; OC_Fbit : array (0 .. Ccount) of Uint;
-- First-bit values for component clauses, the value is the -- First-bit values for component clauses, the value is the offset
-- offset of the first bit of the field from start of record. -- of the first bit of the field from start of record. The zero
-- The zero entry is for use in sorting. -- entry is for use in sorting.
OC_Lbit : array (0 .. Ccount) of Uint; OC_Lbit : array (0 .. Ccount) of Uint;
-- Last-bit values for component clauses, the value is the -- Last-bit values for component clauses, the value is the offset
-- offset of the last bit of the field from start of record. -- of the last bit of the field from start of record. The zero
-- The zero entry is for use in sorting. -- entry is for use in sorting.
OC_Count : Natural := 0; OC_Count : Natural := 0;
-- Count of entries in OC_Fbit and OC_Lbit -- Count of entries in OC_Fbit and OC_Lbit
...@@ -2548,10 +2547,10 @@ package body Sem_Ch13 is ...@@ -2548,10 +2547,10 @@ package body Sem_Ch13 is
end Overlap_Check1; end Overlap_Check1;
end if; end if;
-- If Overlap_Check_Required is still True, then we have to do -- If Overlap_Check_Required is still True, then we have to do the full
-- the full scale overlap check, since we have at least two fields -- scale overlap check, since we have at least two fields that do
-- that do overlap, and we need to know if that is OK since they -- overlap, and we need to know if that is OK since they are in
-- are in the same variant, or whether we have a definite problem -- different variant, or whether we have a definite problem.
if Overlap_Check_Required then if Overlap_Check_Required then
Overlap_Check2 : declare Overlap_Check2 : declare
...@@ -2569,7 +2568,7 @@ package body Sem_Ch13 is ...@@ -2569,7 +2568,7 @@ package body Sem_Ch13 is
-- Loop through all components in record. For each component check -- Loop through all components in record. For each component check
-- for overlap with any of the preceding elements on the component -- for overlap with any of the preceding elements on the component
-- list containing the component, and also, if the component is in -- list containing the component and also, if the component is in
-- a variant, check against components outside the case structure. -- a variant, check against components outside the case structure.
-- This latter test is repeated recursively up the variant tree. -- This latter test is repeated recursively up the variant tree.
...@@ -2597,7 +2596,7 @@ package body Sem_Ch13 is ...@@ -2597,7 +2596,7 @@ package body Sem_Ch13 is
Component_List_Loop : loop Component_List_Loop : loop
-- If derived type definition, go to full declaration -- If derived type definition, go to full declaration
-- If at outer level, check discriminants if there are any -- If at outer level, check discriminants if there are any.
if Nkind (Clist) = N_Derived_Type_Definition then if Nkind (Clist) = N_Derived_Type_Definition then
Clist := Parent (Clist); Clist := Parent (Clist);
...@@ -2605,8 +2604,8 @@ package body Sem_Ch13 is ...@@ -2605,8 +2604,8 @@ package body Sem_Ch13 is
-- Outer level of record definition, check discriminants -- Outer level of record definition, check discriminants
if Nkind (Clist) = N_Full_Type_Declaration if Nkind_In (Clist, N_Full_Type_Declaration,
or else Nkind (Clist) = N_Private_Type_Declaration N_Private_Type_Declaration)
then then
if Has_Discriminants (Defining_Identifier (Clist)) then if Has_Discriminants (Defining_Identifier (Clist)) then
C2_Ent := C2_Ent :=
...@@ -2644,23 +2643,22 @@ package body Sem_Ch13 is ...@@ -2644,23 +2643,22 @@ package body Sem_Ch13 is
-- be a variant, in which case its parent is a variant part, -- be a variant, in which case its parent is a variant part,
-- and the parent of the variant part is a component list -- and the parent of the variant part is a component list
-- whose components must all be checked against the current -- whose components must all be checked against the current
-- component for overlap. -- component for overlap).
if Nkind (Parent (Clist)) = N_Variant then if Nkind (Parent (Clist)) = N_Variant then
Clist := Parent (Parent (Parent (Clist))); Clist := Parent (Parent (Parent (Clist)));
-- Check for possible discriminant part in record, this is -- Check for possible discriminant part in record, this is
-- treated essentially as another level in the recursion. -- treated essentially as another level in the recursion.
-- For this case we have the parent of the component list -- For this case the parent of the component list is the
-- is the record definition, and its parent is the full -- record definition, and its parent is the full type
-- type declaration which contains the discriminant -- declaration containing the discriminant specifications.
-- specifications.
elsif Nkind (Parent (Clist)) = N_Record_Definition then elsif Nkind (Parent (Clist)) = N_Record_Definition then
Clist := Parent (Parent ((Clist))); Clist := Parent (Parent ((Clist)));
-- If neither of these two cases, we are at the top of -- If neither of these two cases, we are at the top of
-- the tree -- the tree.
else else
exit Component_List_Loop; exit Component_List_Loop;
...@@ -2674,24 +2672,23 @@ package body Sem_Ch13 is ...@@ -2674,24 +2672,23 @@ package body Sem_Ch13 is
end Overlap_Check2; end Overlap_Check2;
end if; end if;
-- For records that have component clauses for all components, and -- For records that have component clauses for all components, and whose
-- whose size is less than or equal to 32, we need to know the size -- size is less than or equal to 32, we need to know the size in the
-- in the front end to activate possible packed array processing -- front end to activate possible packed array processing where the
-- where the component type is a record. -- component type is a record.
-- At this stage Hbit + 1 represents the first unused bit from all -- At this stage Hbit + 1 represents the first unused bit from all the
-- the component clauses processed, so if the component clauses are -- component clauses processed, so if the component clauses are
-- complete, then this is the length of the record. -- complete, then this is the length of the record.
-- For records longer than System.Storage_Unit, and for those where -- For records longer than System.Storage_Unit, and for those where not
-- not all components have component clauses, the back end determines -- all components have component clauses, the back end determines the
-- the length (it may for example be appopriate to round up the size -- length (it may for example be appopriate to round up the size
-- to some convenient boundary, based on alignment considerations etc). -- to some convenient boundary, based on alignment considerations, etc).
if Unknown_RM_Size (Rectype) if Unknown_RM_Size (Rectype) and then Hbit + 1 <= 32 then
and then Hbit + 1 <= 32
then -- Nothing to do if at least one component has no component clause
-- Nothing to do if at least one component with no component clause
Comp := First_Component_Or_Discriminant (Rectype); Comp := First_Component_Or_Discriminant (Rectype);
while Present (Comp) loop while Present (Comp) loop
...@@ -2722,9 +2719,7 @@ package body Sem_Ch13 is ...@@ -2722,9 +2719,7 @@ package body Sem_Ch13 is
-- If no Complete_Representation pragma, warn if missing components -- If no Complete_Representation pragma, warn if missing components
elsif Warn_On_Unrepped_Components elsif Warn_On_Unrepped_Components then
and then not Warnings_Off (Rectype)
then
declare declare
Num_Repped_Components : Nat := 0; Num_Repped_Components : Nat := 0;
Num_Unrepped_Components : Nat := 0; Num_Unrepped_Components : Nat := 0;
...@@ -2736,7 +2731,6 @@ package body Sem_Ch13 is ...@@ -2736,7 +2731,6 @@ package body Sem_Ch13 is
while Present (Comp) loop while Present (Comp) loop
if Present (Component_Clause (Comp)) then if Present (Component_Clause (Comp)) then
Num_Repped_Components := Num_Repped_Components + 1; Num_Repped_Components := Num_Repped_Components + 1;
else else
Num_Unrepped_Components := Num_Unrepped_Components + 1; Num_Unrepped_Components := Num_Unrepped_Components + 1;
end if; end if;
...@@ -2763,6 +2757,7 @@ package body Sem_Ch13 is ...@@ -2763,6 +2757,7 @@ package body Sem_Ch13 is
and then (Is_Scalar_Type (Underlying_Type (Etype (Comp))) and then (Is_Scalar_Type (Underlying_Type (Etype (Comp)))
or else Size_Known_At_Compile_Time or else Size_Known_At_Compile_Time
(Underlying_Type (Etype (Comp)))) (Underlying_Type (Etype (Comp))))
and then not Has_Warnings_Off (Rectype)
then then
Error_Msg_Sloc := Sloc (Comp); Error_Msg_Sloc := Sloc (Comp);
Error_Msg_NE Error_Msg_NE
...@@ -2786,9 +2781,9 @@ package body Sem_Ch13 is ...@@ -2786,9 +2781,9 @@ package body Sem_Ch13 is
if Present (Component_Clause (C1_Ent)) if Present (Component_Clause (C1_Ent))
and then Present (Component_Clause (C2_Ent)) and then Present (Component_Clause (C2_Ent))
then then
-- Exclude odd case where we have two tag fields in the same -- Exclude odd case where we have two tag fields in the same record,
-- record, both at location zero. This seems a bit strange, -- both at location zero. This seems a bit strange, but it seems to
-- but it seems to happen in some circumstances ??? -- happen in some circumstances ???
if Chars (C1_Ent) = Name_uTag if Chars (C1_Ent) = Name_uTag
and then Chars (C2_Ent) = Name_uTag and then Chars (C2_Ent) = Name_uTag
...@@ -2830,14 +2825,14 @@ package body Sem_Ch13 is ...@@ -2830,14 +2825,14 @@ package body Sem_Ch13 is
U_Ent : Entity_Id) U_Ent : Entity_Id)
is is
procedure Check_At_Constant_Address (Nod : Node_Id); procedure Check_At_Constant_Address (Nod : Node_Id);
-- Checks that the given node N represents a name whose 'Address -- Checks that the given node N represents a name whose 'Address is
-- is constant (in the same sense as OK_Constant_Address_Clause, -- constant (in the same sense as OK_Constant_Address_Clause, i.e. the
-- i.e. the address value is the same at the point of declaration -- address value is the same at the point of declaration of U_Ent and at
-- of U_Ent and at the time of elaboration of the address clause. -- the time of elaboration of the address clause.
procedure Check_Expr_Constants (Nod : Node_Id); procedure Check_Expr_Constants (Nod : Node_Id);
-- Checks that Nod meets the requirements for a constant address -- Checks that Nod meets the requirements for a constant address clause
-- clause in the sense of the enclosing procedure. -- in the sense of the enclosing procedure.
procedure Check_List_Constants (Lst : List_Id); procedure Check_List_Constants (Lst : List_Id);
-- Check that all elements of list Lst meet the requirements for a -- Check that all elements of list Lst meet the requirements for a
...@@ -2937,11 +2932,11 @@ package body Sem_Ch13 is ...@@ -2937,11 +2932,11 @@ package body Sem_Ch13 is
-- If the node is an object declaration without initial -- If the node is an object declaration without initial
-- value, some code has been expanded, and the expression -- value, some code has been expanded, and the expression
-- is not constant, even if the constituents might be -- is not constant, even if the constituents might be
-- acceptable, as in A'Address + offset. -- acceptable, as in A'Address + offset.
if Ekind (Ent) = E_Variable if Ekind (Ent) = E_Variable
and then Nkind (Declaration_Node (Ent)) and then
= N_Object_Declaration Nkind (Declaration_Node (Ent)) = N_Object_Declaration
and then and then
No (Expression (Declaration_Node (Ent))) No (Expression (Declaration_Node (Ent)))
then then
...@@ -2981,16 +2976,16 @@ package body Sem_Ch13 is ...@@ -2981,16 +2976,16 @@ package body Sem_Ch13 is
or else or else
Ekind (Ent) = E_In_Parameter Ekind (Ent) = E_In_Parameter
then then
-- This is the case where we must have Ent defined -- This is the case where we must have Ent defined before
-- before U_Ent. Clearly if they are in different -- U_Ent. Clearly if they are in different units this
-- units this requirement is met since the unit -- requirement is met since the unit containing Ent is
-- containing Ent is already processed. -- already processed.
if not In_Same_Source_Unit (Ent, U_Ent) then if not In_Same_Source_Unit (Ent, U_Ent) then
return; return;
-- Otherwise location of Ent must be before the -- Otherwise location of Ent must be before the location
-- location of U_Ent, that's what prior defined means. -- of U_Ent, that's what prior defined means.
elsif Sloc (Ent) < Loc_U_Ent then elsif Sloc (Ent) < Loc_U_Ent then
return; return;
...@@ -3107,15 +3102,15 @@ package body Sem_Ch13 is ...@@ -3107,15 +3102,15 @@ package body Sem_Ch13 is
when N_Unchecked_Type_Conversion => when N_Unchecked_Type_Conversion =>
Check_Expr_Constants (Expression (Nod)); Check_Expr_Constants (Expression (Nod));
-- If this is a rewritten unchecked conversion, subtypes -- If this is a rewritten unchecked conversion, subtypes in
-- in this node are those created within the instance. -- this node are those created within the instance. To avoid
-- To avoid order of elaboration issues, replace them -- order of elaboration issues, replace them with their base
-- with their base types. Note that address clauses can -- types. Note that address clauses can cause order of
-- cause order of elaboration problems because they are -- elaboration problems because they are elaborated by the
-- elaborated by the back-end at the point of definition, -- back-end at the point of definition, and may mention
-- and may mention entities declared in between (as long -- entities declared in between (as long as everything is
-- as everything is static). It is user-friendly to allow -- static). It is user-friendly to allow unchecked conversions
-- unchecked conversions in this context. -- in this context.
if Nkind (Original_Node (Nod)) = N_Function_Call then if Nkind (Original_Node (Nod)) = N_Function_Call then
Set_Etype (Expression (Nod), Set_Etype (Expression (Nod),
...@@ -3275,7 +3270,7 @@ package body Sem_Ch13 is ...@@ -3275,7 +3270,7 @@ package body Sem_Ch13 is
if Siz < M then if Siz < M then
-- Size is less than minimum size, but one possibility remains -- Size is less than minimum size, but one possibility remains
-- that we can manage with the new size if we bias the type -- that we can manage with the new size if we bias the type.
M := UI_From_Int (Minimum_Size (UT, Biased => True)); M := UI_From_Int (Minimum_Size (UT, Biased => True));
...@@ -3347,9 +3342,8 @@ package body Sem_Ch13 is ...@@ -3347,9 +3342,8 @@ package body Sem_Ch13 is
else else
declare declare
Id : constant Attribute_Id := Get_Attribute_Id (Chars (N)); Id : constant Attribute_Id := Get_Attribute_Id (Chars (N));
begin begin
return Id = Attribute_Input return Id = Attribute_Input
or else Id = Attribute_Output or else Id = Attribute_Output
or else Id = Attribute_Read or else Id = Attribute_Read
or else Id = Attribute_Write or else Id = Attribute_Write
...@@ -3397,7 +3391,7 @@ package body Sem_Ch13 is ...@@ -3397,7 +3391,7 @@ package body Sem_Ch13 is
-- we have short and long addresses, and it is possible for an access -- we have short and long addresses, and it is possible for an access
-- type to have a short address size (and thus be less than the size -- type to have a short address size (and thus be less than the size
-- of System.Address itself). We simply skip the check for VMS, and -- of System.Address itself). We simply skip the check for VMS, and
-- leave the back end to do the check. -- leave it to the back end to do the check.
elsif Is_Access_Type (T) then elsif Is_Access_Type (T) then
if OpenVMS_On_Target then if OpenVMS_On_Target then
...@@ -3415,9 +3409,9 @@ package body Sem_Ch13 is ...@@ -3415,9 +3409,9 @@ package body Sem_Ch13 is
elsif Is_Discrete_Type (T) then elsif Is_Discrete_Type (T) then
-- The following loop is looking for the nearest compile time -- The following loop is looking for the nearest compile time known
-- known bounds following the ancestor subtype chain. The idea -- bounds following the ancestor subtype chain. The idea is to find
-- is to find the most restrictive known bounds information. -- the most restrictive known bounds information.
Ancest := T; Ancest := T;
loop loop
...@@ -3453,17 +3447,17 @@ package body Sem_Ch13 is ...@@ -3453,17 +3447,17 @@ package body Sem_Ch13 is
end loop; end loop;
-- Fixed-point types. We can't simply use Expr_Value to get the -- Fixed-point types. We can't simply use Expr_Value to get the
-- Corresponding_Integer_Value values of the bounds, since these -- Corresponding_Integer_Value values of the bounds, since these do not
-- do not get set till the type is frozen, and this routine can -- get set till the type is frozen, and this routine can be called
-- be called before the type is frozen. Similarly the test for -- before the type is frozen. Similarly the test for bounds being static
-- bounds being static needs to include the case where we have -- needs to include the case where we have unanalyzed real literals for
-- unanalyzed real literals for the same reason. -- the same reason.
elsif Is_Fixed_Point_Type (T) then elsif Is_Fixed_Point_Type (T) then
-- The following loop is looking for the nearest compile time -- The following loop is looking for the nearest compile time known
-- known bounds following the ancestor subtype chain. The idea -- bounds following the ancestor subtype chain. The idea is to find
-- is to find the most restrictive known bounds information. -- the most restrictive known bounds information.
Ancest := T; Ancest := T;
loop loop
...@@ -3532,8 +3526,8 @@ package body Sem_Ch13 is ...@@ -3532,8 +3526,8 @@ package body Sem_Ch13 is
end if; end if;
-- Signed case. Note that we consider types like range 1 .. -1 to be -- Signed case. Note that we consider types like range 1 .. -1 to be
-- signed for the purpose of computing the size, since the bounds -- signed for the purpose of computing the size, since the bounds have
-- have to be accomodated in the base type. -- to be accomodated in the base type.
if Lo < 0 or else Hi < 0 then if Lo < 0 or else Hi < 0 then
S := 1; S := 1;
...@@ -3725,7 +3719,7 @@ package body Sem_Ch13 is ...@@ -3725,7 +3719,7 @@ package body Sem_Ch13 is
return True; return True;
end if; end if;
-- Otherwise check for incompleted type -- Otherwise check for incomplete type
if Is_Incomplete_Or_Private_Type (T) if Is_Incomplete_Or_Private_Type (T)
and then No (Underlying_Type (T)) and then No (Underlying_Type (T))
...@@ -3827,23 +3821,22 @@ package body Sem_Ch13 is ...@@ -3827,23 +3821,22 @@ package body Sem_Ch13 is
if Is_Overloadable (T) if Is_Overloadable (T)
and then Nkind (N) = N_Pragma and then Nkind (N) = N_Pragma
and then (Chars (N) = Name_Convention
or else
Chars (N) = Name_Import
or else
Chars (N) = Name_Export
or else
Chars (N) = Name_External
or else
Chars (N) = Name_Interface)
then then
null; declare
else Pname : constant Name_Id := Pragma_Name (N);
Record_Rep_Item (T, N); begin
if Pname = Name_Convention or else
Pname = Name_Import or else
Pname = Name_Export or else
Pname = Name_External or else
Pname = Name_Interface
then
return False;
end if;
end;
end if; end if;
-- Rep item was OK, not too late Record_Rep_Item (T, N);
return False; return False;
end Rep_Item_Too_Late; end Rep_Item_Too_Late;
...@@ -3919,8 +3912,8 @@ package body Sem_Ch13 is ...@@ -3919,8 +3912,8 @@ package body Sem_Ch13 is
return not Has_Non_Standard_Rep (T2); return not Has_Non_Standard_Rep (T2);
end if; end if;
-- Here the two types both have non-standard representation, and we -- Here the two types both have non-standard representation, and we need
-- need to determine if they have the same non-standard representation -- to determine if they have the same non-standard representation.
-- For arrays, we simply need to test if the component sizes are the -- For arrays, we simply need to test if the component sizes are the
-- same. Pragma Pack is reflected in modified component sizes, so this -- same. Pragma Pack is reflected in modified component sizes, so this
...@@ -4240,8 +4233,8 @@ package body Sem_Ch13 is ...@@ -4240,8 +4233,8 @@ package body Sem_Ch13 is
Target := Ancestor_Subtype (Etype (Act_Unit)); Target := Ancestor_Subtype (Etype (Act_Unit));
-- If either type is generic, the instantiation happens within a -- If either type is generic, the instantiation happens within a generic
-- generic unit, and there is nothing to check. The proper check -- unit, and there is nothing to check. The proper check
-- will happen when the enclosing generic is instantiated. -- will happen when the enclosing generic is instantiated.
if Is_Generic_Type (Source) or else Is_Generic_Type (Target) then if Is_Generic_Type (Source) or else Is_Generic_Type (Target) then
...@@ -4271,8 +4264,17 @@ package body Sem_Ch13 is ...@@ -4271,8 +4264,17 @@ package body Sem_Ch13 is
and then Convention (Target) /= Convention (Source) and then Convention (Target) /= Convention (Source)
and then Warn_On_Unchecked_Conversion and then Warn_On_Unchecked_Conversion
then then
Error_Msg_N -- Give warnings for subprogram pointers only on most targets. The
("?conversion between pointers with different conventions!", N); -- exception is VMS, where data pointers can have different lengths
-- depending on the pointer convention.
if Is_Access_Subprogram_Type (Target)
or else Is_Access_Subprogram_Type (Source)
or else OpenVMS_On_Target
then
Error_Msg_N
("?conversion between pointers with different conventions!", N);
end if;
end if; end if;
-- Warn if one of the operands is Ada.Calendar.Time. Do not emit a -- Warn if one of the operands is Ada.Calendar.Time. Do not emit a
...@@ -4305,10 +4307,10 @@ package body Sem_Ch13 is ...@@ -4305,10 +4307,10 @@ package body Sem_Ch13 is
end; end;
end if; end if;
-- Make entry in unchecked conversion table for later processing -- Make entry in unchecked conversion table for later processing by
-- by Validate_Unchecked_Conversions, which will check sizes and -- Validate_Unchecked_Conversions, which will check sizes and alignments
-- alignments (using values set by the back-end where possible). -- (using values set by the back-end where possible). This is only done
-- This is only done if the appropriate warning is active -- if the appropriate warning is active.
if Warn_On_Unchecked_Conversion then if Warn_On_Unchecked_Conversion then
Unchecked_Conversions.Append Unchecked_Conversions.Append
...@@ -4330,10 +4332,10 @@ package body Sem_Ch13 is ...@@ -4330,10 +4332,10 @@ package body Sem_Ch13 is
end if; end if;
end if; end if;
-- If unchecked conversion to access type, and access type is -- If unchecked conversion to access type, and access type is declared
-- declared in the same unit as the unchecked conversion, then -- in the same unit as the unchecked conversion, then set the
-- set the No_Strict_Aliasing flag (no strict aliasing is -- No_Strict_Aliasing flag (no strict aliasing is implicit in this
-- implicit in this situation). -- situation).
if Is_Access_Type (Target) and then if Is_Access_Type (Target) and then
In_Same_Source_Unit (Target, N) In_Same_Source_Unit (Target, N)
...@@ -4344,7 +4346,7 @@ package body Sem_Ch13 is ...@@ -4344,7 +4346,7 @@ package body Sem_Ch13 is
-- Generate N_Validate_Unchecked_Conversion node for back end in -- Generate N_Validate_Unchecked_Conversion node for back end in
-- case the back end needs to perform special validation checks. -- case the back end needs to perform special validation checks.
-- Shouldn't this be in exp_ch13, since the check only gets done -- Shouldn't this be in Exp_Ch13, since the check only gets done
-- if we have full expansion and the back end is called ??? -- if we have full expansion and the back end is called ???
Vnode := Vnode :=
...@@ -4352,8 +4354,8 @@ package body Sem_Ch13 is ...@@ -4352,8 +4354,8 @@ package body Sem_Ch13 is
Set_Source_Type (Vnode, Source); Set_Source_Type (Vnode, Source);
Set_Target_Type (Vnode, Target); Set_Target_Type (Vnode, Target);
-- If the unchecked conversion node is in a list, just insert before -- If the unchecked conversion node is in a list, just insert before it.
-- it. If not we have some strange case, not worth bothering about. -- If not we have some strange case, not worth bothering about.
if Is_List_Member (N) then if Is_List_Member (N) then
Insert_After (N, Vnode); Insert_After (N, Vnode);
...@@ -4378,11 +4380,11 @@ package body Sem_Ch13 is ...@@ -4378,11 +4380,11 @@ package body Sem_Ch13 is
Target_Siz : Uint; Target_Siz : Uint;
begin begin
-- This validation check, which warns if we have unequal sizes -- This validation check, which warns if we have unequal sizes for
-- for unchecked conversion, and thus potentially implementation -- unchecked conversion, and thus potentially implementation
-- dependent semantics, is one of the few occasions on which we -- dependent semantics, is one of the few occasions on which we
-- use the official RM size instead of Esize. See description -- use the official RM size instead of Esize. See description in
-- in Einfo "Handling of Type'Size Values" for details. -- Einfo "Handling of Type'Size Values" for details.
if Serious_Errors_Detected = 0 if Serious_Errors_Detected = 0
and then Known_Static_RM_Size (Source) and then Known_Static_RM_Size (Source)
......
Markdown is supported
0% or
You are about to add 0 people to the discussion. Proceed with caution.
Finish editing this message first!
Please register or to comment