Merge from mainline
[official-gcc.git] / gcc / ada / sem_ch13.adb
blob00505e6d866139fc6854657e199685c47eb4e3a7
1 ------------------------------------------------------------------------------
2 -- --
3 -- GNAT COMPILER COMPONENTS --
4 -- --
5 -- S E M _ C H 1 3 --
6 -- --
7 -- B o d y --
8 -- --
9 -- Copyright (C) 1992-2006, 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 2, 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 COPYING. If not, write --
19 -- to the Free Software Foundation, 51 Franklin Street, Fifth Floor, --
20 -- Boston, MA 02110-1301, USA. --
21 -- --
22 -- GNAT was originally developed by the GNAT team at New York University. --
23 -- Extensive contributions were provided by Ada Core Technologies Inc. --
24 -- --
25 ------------------------------------------------------------------------------
27 with Atree; use Atree;
28 with Checks; use Checks;
29 with Einfo; use Einfo;
30 with Errout; use Errout;
31 with Exp_Tss; use Exp_Tss;
32 with Exp_Util; use Exp_Util;
33 with Lib; use Lib;
34 with Nlists; use Nlists;
35 with Nmake; use Nmake;
36 with Opt; use Opt;
37 with Restrict; use Restrict;
38 with Rident; use Rident;
39 with Rtsfind; use Rtsfind;
40 with Sem; use Sem;
41 with Sem_Ch8; use Sem_Ch8;
42 with Sem_Eval; use Sem_Eval;
43 with Sem_Res; use Sem_Res;
44 with Sem_Type; use Sem_Type;
45 with Sem_Util; use Sem_Util;
46 with Snames; use Snames;
47 with Stand; use Stand;
48 with Sinfo; use Sinfo;
49 with Table;
50 with Targparm; use Targparm;
51 with Ttypes; use Ttypes;
52 with Tbuild; use Tbuild;
53 with Urealp; use Urealp;
55 with GNAT.Heap_Sort_A; use GNAT.Heap_Sort_A;
57 package body Sem_Ch13 is
59 SSU : constant Pos := System_Storage_Unit;
60 -- Convenient short hand for commonly used constant
62 -----------------------
63 -- Local Subprograms --
64 -----------------------
66 procedure Alignment_Check_For_Esize_Change (Typ : Entity_Id);
67 -- This routine is called after setting the Esize of type entity Typ.
68 -- The purpose is to deal with the situation where an aligment has been
69 -- inherited from a derived type that is no longer appropriate for the
70 -- new Esize value. In this case, we reset the Alignment to unknown.
72 procedure Check_Component_Overlap (C1_Ent, C2_Ent : Entity_Id);
73 -- Given two entities for record components or discriminants, checks
74 -- if they hav overlapping component clauses and issues errors if so.
76 function Get_Alignment_Value (Expr : Node_Id) return Uint;
77 -- Given the expression for an alignment value, returns the corresponding
78 -- Uint value. If the value is inappropriate, then error messages are
79 -- posted as required, and a value of No_Uint is returned.
81 function Is_Operational_Item (N : Node_Id) return Boolean;
82 -- A specification for a stream attribute is allowed before the full
83 -- type is declared, as explained in AI-00137 and the corrigendum.
84 -- Attributes that do not specify a representation characteristic are
85 -- operational attributes.
87 function Address_Aliased_Entity (N : Node_Id) return Entity_Id;
88 -- If expression N is of the form E'Address, return E
90 procedure Mark_Aliased_Address_As_Volatile (N : Node_Id);
91 -- This is used for processing of an address representation clause. If
92 -- the expression N is of the form of K'Address, then the entity that
93 -- is associated with K is marked as volatile.
95 procedure New_Stream_Function
96 (N : Node_Id;
97 Ent : Entity_Id;
98 Subp : Entity_Id;
99 Nam : TSS_Name_Type);
100 -- Create a function renaming of a given stream attribute to the
101 -- designated subprogram and then in the tagged case, provide this as
102 -- a primitive operation, or in the non-tagged case make an appropriate
103 -- TSS entry. Used for Input. This is more properly an expansion activity
104 -- than just semantics, but the presence of user-defined stream functions
105 -- for limited types is a legality check, which is why this takes place
106 -- here rather than in exp_ch13, where it was previously. Nam indicates
107 -- the name of the TSS function to be generated.
109 -- To avoid elaboration anomalies with freeze nodes, for untagged types
110 -- we generate both a subprogram declaration and a subprogram renaming
111 -- declaration, so that the attribute specification is handled as a
112 -- renaming_as_body. For tagged types, the specification is one of the
113 -- primitive specs.
115 procedure New_Stream_Procedure
116 (N : Node_Id;
117 Ent : Entity_Id;
118 Subp : Entity_Id;
119 Nam : TSS_Name_Type;
120 Out_P : Boolean := False);
121 -- Create a procedure renaming of a given stream attribute to the
122 -- designated subprogram and then in the tagged case, provide this as
123 -- a primitive operation, or in the non-tagged case make an appropriate
124 -- TSS entry. Used for Read, Output, Write. Nam indicates the name of
125 -- the TSS procedure to be generated.
127 ----------------------------------------------
128 -- Table for Validate_Unchecked_Conversions --
129 ----------------------------------------------
131 -- The following table collects unchecked conversions for validation.
132 -- Entries are made by Validate_Unchecked_Conversion and then the
133 -- call to Validate_Unchecked_Conversions does the actual error
134 -- checking and posting of warnings. The reason for this delayed
135 -- processing is to take advantage of back-annotations of size and
136 -- alignment values peformed by the back end.
138 type UC_Entry is record
139 Enode : Node_Id; -- node used for posting warnings
140 Source : Entity_Id; -- source type for unchecked conversion
141 Target : Entity_Id; -- target type for unchecked conversion
142 end record;
144 package Unchecked_Conversions is new Table.Table (
145 Table_Component_Type => UC_Entry,
146 Table_Index_Type => Int,
147 Table_Low_Bound => 1,
148 Table_Initial => 50,
149 Table_Increment => 200,
150 Table_Name => "Unchecked_Conversions");
152 ----------------------------
153 -- Address_Aliased_Entity --
154 ----------------------------
156 function Address_Aliased_Entity (N : Node_Id) return Entity_Id is
157 begin
158 if Nkind (N) = N_Attribute_Reference
159 and then Attribute_Name (N) = Name_Address
160 then
161 declare
162 Nam : Node_Id := Prefix (N);
163 begin
164 while False
165 or else Nkind (Nam) = N_Selected_Component
166 or else Nkind (Nam) = N_Indexed_Component
167 loop
168 Nam := Prefix (Nam);
169 end loop;
171 if Is_Entity_Name (Nam) then
172 return Entity (Nam);
173 end if;
174 end;
175 end if;
177 return Empty;
178 end Address_Aliased_Entity;
180 --------------------------------------
181 -- Alignment_Check_For_Esize_Change --
182 --------------------------------------
184 procedure Alignment_Check_For_Esize_Change (Typ : Entity_Id) is
185 begin
186 -- If the alignment is known, and not set by a rep clause, and is
187 -- inconsistent with the size being set, then reset it to unknown,
188 -- we assume in this case that the size overrides the inherited
189 -- alignment, and that the alignment must be recomputed.
191 if Known_Alignment (Typ)
192 and then not Has_Alignment_Clause (Typ)
193 and then Esize (Typ) mod (Alignment (Typ) * SSU) /= 0
194 then
195 Init_Alignment (Typ);
196 end if;
197 end Alignment_Check_For_Esize_Change;
199 -----------------------
200 -- Analyze_At_Clause --
201 -----------------------
203 -- An at clause is replaced by the corresponding Address attribute
204 -- definition clause that is the preferred approach in Ada 95.
206 procedure Analyze_At_Clause (N : Node_Id) is
207 begin
208 Check_Restriction (No_Obsolescent_Features, N);
210 if Warn_On_Obsolescent_Feature then
211 Error_Msg_N
212 ("at clause is an obsolescent feature ('R'M 'J.7(2))?", N);
213 Error_Msg_N
214 ("\use address attribute definition clause instead?", N);
215 end if;
217 Rewrite (N,
218 Make_Attribute_Definition_Clause (Sloc (N),
219 Name => Identifier (N),
220 Chars => Name_Address,
221 Expression => Expression (N)));
222 Analyze_Attribute_Definition_Clause (N);
223 end Analyze_At_Clause;
225 -----------------------------------------
226 -- Analyze_Attribute_Definition_Clause --
227 -----------------------------------------
229 procedure Analyze_Attribute_Definition_Clause (N : Node_Id) is
230 Loc : constant Source_Ptr := Sloc (N);
231 Nam : constant Node_Id := Name (N);
232 Attr : constant Name_Id := Chars (N);
233 Expr : constant Node_Id := Expression (N);
234 Id : constant Attribute_Id := Get_Attribute_Id (Attr);
235 Ent : Entity_Id;
236 U_Ent : Entity_Id;
238 FOnly : Boolean := False;
239 -- Reset to True for subtype specific attribute (Alignment, Size)
240 -- and for stream attributes, i.e. those cases where in the call
241 -- to Rep_Item_Too_Late, FOnly is set True so that only the freezing
242 -- rules are checked. Note that the case of stream attributes is not
243 -- clear from the RM, but see AI95-00137. Also, the RM seems to
244 -- disallow Storage_Size for derived task types, but that is also
245 -- clearly unintentional.
247 procedure Analyze_Stream_TSS_Definition (TSS_Nam : TSS_Name_Type);
248 -- Common processing for 'Read, 'Write, 'Input and 'Output attribute
249 -- definition clauses.
251 procedure Analyze_Stream_TSS_Definition (TSS_Nam : TSS_Name_Type) is
252 Subp : Entity_Id := Empty;
253 I : Interp_Index;
254 It : Interp;
255 Pnam : Entity_Id;
257 Is_Read : constant Boolean := (TSS_Nam = TSS_Stream_Read);
259 function Has_Good_Profile (Subp : Entity_Id) return Boolean;
260 -- Return true if the entity is a subprogram with an appropriate
261 -- profile for the attribute being defined.
263 ----------------------
264 -- Has_Good_Profile --
265 ----------------------
267 function Has_Good_Profile (Subp : Entity_Id) return Boolean is
268 F : Entity_Id;
269 Is_Function : constant Boolean := (TSS_Nam = TSS_Stream_Input);
270 Expected_Ekind : constant array (Boolean) of Entity_Kind :=
271 (False => E_Procedure, True => E_Function);
272 Typ : Entity_Id;
274 begin
275 if Ekind (Subp) /= Expected_Ekind (Is_Function) then
276 return False;
277 end if;
279 F := First_Formal (Subp);
281 if No (F)
282 or else Ekind (Etype (F)) /= E_Anonymous_Access_Type
283 or else Designated_Type (Etype (F)) /=
284 Class_Wide_Type (RTE (RE_Root_Stream_Type))
285 then
286 return False;
287 end if;
289 if not Is_Function then
290 Next_Formal (F);
292 declare
293 Expected_Mode : constant array (Boolean) of Entity_Kind :=
294 (False => E_In_Parameter,
295 True => E_Out_Parameter);
296 begin
297 if Parameter_Mode (F) /= Expected_Mode (Is_Read) then
298 return False;
299 end if;
300 end;
302 Typ := Etype (F);
304 else
305 Typ := Etype (Subp);
306 end if;
308 return Base_Type (Typ) = Base_Type (Ent)
309 and then No (Next_Formal (F));
311 end Has_Good_Profile;
313 -- Start of processing for Analyze_Stream_TSS_Definition
315 begin
316 FOnly := True;
318 if not Is_Type (U_Ent) then
319 Error_Msg_N ("local name must be a subtype", Nam);
320 return;
321 end if;
323 Pnam := TSS (Base_Type (U_Ent), TSS_Nam);
325 if Present (Pnam) and then Has_Good_Profile (Pnam) then
326 Error_Msg_Sloc := Sloc (Pnam);
327 Error_Msg_Name_1 := Attr;
328 Error_Msg_N ("% attribute already defined #", Nam);
329 return;
330 end if;
332 Analyze (Expr);
334 if Is_Entity_Name (Expr) then
335 if not Is_Overloaded (Expr) then
336 if Has_Good_Profile (Entity (Expr)) then
337 Subp := Entity (Expr);
338 end if;
340 else
341 Get_First_Interp (Expr, I, It);
343 while Present (It.Nam) loop
344 if Has_Good_Profile (It.Nam) then
345 Subp := It.Nam;
346 exit;
347 end if;
349 Get_Next_Interp (I, It);
350 end loop;
351 end if;
352 end if;
354 if Present (Subp) then
355 if Is_Abstract (Subp) then
356 Error_Msg_N ("stream subprogram must not be abstract", Expr);
357 return;
358 end if;
360 Set_Entity (Expr, Subp);
361 Set_Etype (Expr, Etype (Subp));
363 if TSS_Nam = TSS_Stream_Input then
364 New_Stream_Function (N, U_Ent, Subp, TSS_Nam);
365 else
366 New_Stream_Procedure (N, U_Ent, Subp, TSS_Nam,
367 Out_P => Is_Read);
368 end if;
370 else
371 Error_Msg_Name_1 := Attr;
372 Error_Msg_N ("incorrect expression for% attribute", Expr);
373 end if;
374 end Analyze_Stream_TSS_Definition;
376 -- Start of processing for Analyze_Attribute_Definition_Clause
378 begin
379 Analyze (Nam);
380 Ent := Entity (Nam);
382 if Rep_Item_Too_Early (Ent, N) then
383 return;
384 end if;
386 -- Rep clause applies to full view of incomplete type or private type if
387 -- we have one (if not, this is a premature use of the type). However,
388 -- certain semantic checks need to be done on the specified entity (i.e.
389 -- the private view), so we save it in Ent.
391 if Is_Private_Type (Ent)
392 and then Is_Derived_Type (Ent)
393 and then not Is_Tagged_Type (Ent)
394 and then No (Full_View (Ent))
395 then
396 -- If this is a private type whose completion is a derivation from
397 -- another private type, there is no full view, and the attribute
398 -- belongs to the type itself, not its underlying parent.
400 U_Ent := Ent;
402 elsif Ekind (Ent) = E_Incomplete_Type then
404 -- The attribute applies to the full view, set the entity of the
405 -- attribute definition accordingly.
407 Ent := Underlying_Type (Ent);
408 U_Ent := Ent;
409 Set_Entity (Nam, Ent);
411 else
412 U_Ent := Underlying_Type (Ent);
413 end if;
415 -- Complete other routine error checks
417 if Etype (Nam) = Any_Type then
418 return;
420 elsif Scope (Ent) /= Current_Scope then
421 Error_Msg_N ("entity must be declared in this scope", Nam);
422 return;
424 elsif No (U_Ent) then
425 U_Ent := Ent;
427 elsif Is_Type (U_Ent)
428 and then not Is_First_Subtype (U_Ent)
429 and then Id /= Attribute_Object_Size
430 and then Id /= Attribute_Value_Size
431 and then not From_At_Mod (N)
432 then
433 Error_Msg_N ("cannot specify attribute for subtype", Nam);
434 return;
435 end if;
437 -- Switch on particular attribute
439 case Id is
441 -------------
442 -- Address --
443 -------------
445 -- Address attribute definition clause
447 when Attribute_Address => Address : begin
448 Analyze_And_Resolve (Expr, RTE (RE_Address));
450 if Present (Address_Clause (U_Ent)) then
451 Error_Msg_N ("address already given for &", Nam);
453 -- Case of address clause for subprogram
455 elsif Is_Subprogram (U_Ent) then
456 if Has_Homonym (U_Ent) then
457 Error_Msg_N
458 ("address clause cannot be given " &
459 "for overloaded subprogram",
460 Nam);
461 end if;
463 -- For subprograms, all address clauses are permitted,
464 -- and we mark the subprogram as having a deferred freeze
465 -- so that Gigi will not elaborate it too soon.
467 -- Above needs more comments, what is too soon about???
469 Set_Has_Delayed_Freeze (U_Ent);
471 -- Case of address clause for entry
473 elsif Ekind (U_Ent) = E_Entry then
474 if Nkind (Parent (N)) = N_Task_Body then
475 Error_Msg_N
476 ("entry address must be specified in task spec", Nam);
477 end if;
479 -- For entries, we require a constant address
481 Check_Constant_Address_Clause (Expr, U_Ent);
483 if Is_Task_Type (Scope (U_Ent))
484 and then Comes_From_Source (Scope (U_Ent))
485 then
486 Error_Msg_N
487 ("?entry address declared for entry in task type", N);
488 Error_Msg_N
489 ("\?only one task can be declared of this type", N);
490 end if;
492 Check_Restriction (No_Obsolescent_Features, N);
494 if Warn_On_Obsolescent_Feature then
495 Error_Msg_N
496 ("attaching interrupt to task entry is an " &
497 "obsolescent feature ('R'M 'J.7.1)?", N);
498 Error_Msg_N
499 ("\use interrupt procedure instead?", N);
500 end if;
502 -- Case of an address clause for a controlled object:
503 -- erroneous execution.
505 elsif Is_Controlled (Etype (U_Ent)) then
506 Error_Msg_NE
507 ("?controlled object& must not be overlaid", Nam, U_Ent);
508 Error_Msg_N
509 ("\?Program_Error will be raised at run time", Nam);
510 Insert_Action (Declaration_Node (U_Ent),
511 Make_Raise_Program_Error (Loc,
512 Reason => PE_Overlaid_Controlled_Object));
514 -- Case of address clause for a (non-controlled) object
516 elsif
517 Ekind (U_Ent) = E_Variable
518 or else
519 Ekind (U_Ent) = E_Constant
520 then
521 declare
522 Expr : constant Node_Id := Expression (N);
523 Aent : constant Entity_Id := Address_Aliased_Entity (Expr);
525 begin
526 -- Exported variables cannot have an address clause,
527 -- because this cancels the effect of the pragma Export
529 if Is_Exported (U_Ent) then
530 Error_Msg_N
531 ("cannot export object with address clause", Nam);
533 -- Overlaying controlled objects is erroneous
535 elsif Present (Aent)
536 and then Is_Controlled (Etype (Aent))
537 then
538 Error_Msg_N
539 ("?controlled object must not be overlaid", Expr);
540 Error_Msg_N
541 ("\?Program_Error will be raised at run time", Expr);
542 Insert_Action (Declaration_Node (U_Ent),
543 Make_Raise_Program_Error (Loc,
544 Reason => PE_Overlaid_Controlled_Object));
546 elsif Present (Aent)
547 and then Ekind (U_Ent) = E_Constant
548 and then Ekind (Aent) /= E_Constant
549 then
550 Error_Msg_N ("constant overlays a variable?", Expr);
552 elsif Present (Renamed_Object (U_Ent)) then
553 Error_Msg_N
554 ("address clause not allowed"
555 & " for a renaming declaration ('R'M 13.1(6))", Nam);
557 -- Imported variables can have an address clause, but then
558 -- the import is pretty meaningless except to suppress
559 -- initializations, so we do not need such variables to
560 -- be statically allocated (and in fact it causes trouble
561 -- if the address clause is a local value).
563 elsif Is_Imported (U_Ent) then
564 Set_Is_Statically_Allocated (U_Ent, False);
565 end if;
567 -- We mark a possible modification of a variable with an
568 -- address clause, since it is likely aliasing is occurring.
570 Note_Possible_Modification (Nam);
572 -- Here we are checking for explicit overlap of one
573 -- variable by another, and if we find this, then we
574 -- mark the overlapped variable as also being aliased.
576 -- First case is where we have an explicit
578 -- for J'Address use K'Address;
580 -- In this case, we mark K as volatile
582 Mark_Aliased_Address_As_Volatile (Expr);
584 -- Second case is where we have a constant whose
585 -- definition is of the form of an adress as in:
587 -- A : constant Address := K'Address;
588 -- ...
589 -- for B'Address use A;
591 -- In this case we also mark K as volatile
593 if Is_Entity_Name (Expr) then
594 declare
595 Ent : constant Entity_Id := Entity (Expr);
596 Decl : constant Node_Id := Declaration_Node (Ent);
598 begin
599 if Ekind (Ent) = E_Constant
600 and then Nkind (Decl) = N_Object_Declaration
601 and then Present (Expression (Decl))
602 then
603 Mark_Aliased_Address_As_Volatile
604 (Expression (Decl));
605 end if;
606 end;
607 end if;
609 -- Legality checks on the address clause for initialized
610 -- objects is deferred until the freeze point, because
611 -- a subsequent pragma might indicate that the object is
612 -- imported and thus not initialized.
614 Set_Has_Delayed_Freeze (U_Ent);
616 if Is_Exported (U_Ent) then
617 Error_Msg_N
618 ("& cannot be exported if an address clause is given",
619 Nam);
620 Error_Msg_N
621 ("\define and export a variable " &
622 "that holds its address instead",
623 Nam);
624 end if;
626 -- Entity has delayed freeze, so we will generate
627 -- an alignment check at the freeze point.
629 Set_Check_Address_Alignment
630 (N, not Range_Checks_Suppressed (U_Ent));
632 -- Kill the size check code, since we are not allocating
633 -- the variable, it is somewhere else.
635 Kill_Size_Check_Code (U_Ent);
636 end;
638 -- Not a valid entity for an address clause
640 else
641 Error_Msg_N ("address cannot be given for &", Nam);
642 end if;
643 end Address;
645 ---------------
646 -- Alignment --
647 ---------------
649 -- Alignment attribute definition clause
651 when Attribute_Alignment => Alignment_Block : declare
652 Align : constant Uint := Get_Alignment_Value (Expr);
654 begin
655 FOnly := True;
657 if not Is_Type (U_Ent)
658 and then Ekind (U_Ent) /= E_Variable
659 and then Ekind (U_Ent) /= E_Constant
660 then
661 Error_Msg_N ("alignment cannot be given for &", Nam);
663 elsif Has_Alignment_Clause (U_Ent) then
664 Error_Msg_Sloc := Sloc (Alignment_Clause (U_Ent));
665 Error_Msg_N ("alignment clause previously given#", N);
667 elsif Align /= No_Uint then
668 Set_Has_Alignment_Clause (U_Ent);
669 Set_Alignment (U_Ent, Align);
670 end if;
671 end Alignment_Block;
673 ---------------
674 -- Bit_Order --
675 ---------------
677 -- Bit_Order attribute definition clause
679 when Attribute_Bit_Order => Bit_Order : declare
680 begin
681 if not Is_Record_Type (U_Ent) then
682 Error_Msg_N
683 ("Bit_Order can only be defined for record type", Nam);
685 else
686 Analyze_And_Resolve (Expr, RTE (RE_Bit_Order));
688 if Etype (Expr) = Any_Type then
689 return;
691 elsif not Is_Static_Expression (Expr) then
692 Flag_Non_Static_Expr
693 ("Bit_Order requires static expression!", Expr);
695 else
696 if (Expr_Value (Expr) = 0) /= Bytes_Big_Endian then
697 Set_Reverse_Bit_Order (U_Ent, True);
698 end if;
699 end if;
700 end if;
701 end Bit_Order;
703 --------------------
704 -- Component_Size --
705 --------------------
707 -- Component_Size attribute definition clause
709 when Attribute_Component_Size => Component_Size_Case : declare
710 Csize : constant Uint := Static_Integer (Expr);
711 Btype : Entity_Id;
712 Biased : Boolean;
713 New_Ctyp : Entity_Id;
714 Decl : Node_Id;
716 begin
717 if not Is_Array_Type (U_Ent) then
718 Error_Msg_N ("component size requires array type", Nam);
719 return;
720 end if;
722 Btype := Base_Type (U_Ent);
724 if Has_Component_Size_Clause (Btype) then
725 Error_Msg_N
726 ("component size clase for& previously given", Nam);
728 elsif Csize /= No_Uint then
729 Check_Size (Expr, Component_Type (Btype), Csize, Biased);
731 if Has_Aliased_Components (Btype)
732 and then Csize < 32
733 and then Csize /= 8
734 and then Csize /= 16
735 then
736 Error_Msg_N
737 ("component size incorrect for aliased components", N);
738 return;
739 end if;
741 -- For the biased case, build a declaration for a subtype
742 -- that will be used to represent the biased subtype that
743 -- reflects the biased representation of components. We need
744 -- this subtype to get proper conversions on referencing
745 -- elements of the array.
747 if Biased then
748 New_Ctyp :=
749 Make_Defining_Identifier (Loc,
750 Chars => New_External_Name (Chars (U_Ent), 'C', 0, 'T'));
752 Decl :=
753 Make_Subtype_Declaration (Loc,
754 Defining_Identifier => New_Ctyp,
755 Subtype_Indication =>
756 New_Occurrence_Of (Component_Type (Btype), Loc));
758 Set_Parent (Decl, N);
759 Analyze (Decl, Suppress => All_Checks);
761 Set_Has_Delayed_Freeze (New_Ctyp, False);
762 Set_Esize (New_Ctyp, Csize);
763 Set_RM_Size (New_Ctyp, Csize);
764 Init_Alignment (New_Ctyp);
765 Set_Has_Biased_Representation (New_Ctyp, True);
766 Set_Is_Itype (New_Ctyp, True);
767 Set_Associated_Node_For_Itype (New_Ctyp, U_Ent);
769 Set_Component_Type (Btype, New_Ctyp);
770 end if;
772 Set_Component_Size (Btype, Csize);
773 Set_Has_Component_Size_Clause (Btype, True);
774 Set_Has_Non_Standard_Rep (Btype, True);
775 end if;
776 end Component_Size_Case;
778 ------------------
779 -- External_Tag --
780 ------------------
782 when Attribute_External_Tag => External_Tag :
783 begin
784 if not Is_Tagged_Type (U_Ent) then
785 Error_Msg_N ("should be a tagged type", Nam);
786 end if;
788 Analyze_And_Resolve (Expr, Standard_String);
790 if not Is_Static_Expression (Expr) then
791 Flag_Non_Static_Expr
792 ("static string required for tag name!", Nam);
793 end if;
795 Set_Has_External_Tag_Rep_Clause (U_Ent);
796 end External_Tag;
798 -----------
799 -- Input --
800 -----------
802 when Attribute_Input =>
803 Analyze_Stream_TSS_Definition (TSS_Stream_Input);
804 Set_Has_Specified_Stream_Input (Ent);
806 -------------------
807 -- Machine_Radix --
808 -------------------
810 -- Machine radix attribute definition clause
812 when Attribute_Machine_Radix => Machine_Radix : declare
813 Radix : constant Uint := Static_Integer (Expr);
815 begin
816 if not Is_Decimal_Fixed_Point_Type (U_Ent) then
817 Error_Msg_N ("decimal fixed-point type expected for &", Nam);
819 elsif Has_Machine_Radix_Clause (U_Ent) then
820 Error_Msg_Sloc := Sloc (Alignment_Clause (U_Ent));
821 Error_Msg_N ("machine radix clause previously given#", N);
823 elsif Radix /= No_Uint then
824 Set_Has_Machine_Radix_Clause (U_Ent);
825 Set_Has_Non_Standard_Rep (Base_Type (U_Ent));
827 if Radix = 2 then
828 null;
829 elsif Radix = 10 then
830 Set_Machine_Radix_10 (U_Ent);
831 else
832 Error_Msg_N ("machine radix value must be 2 or 10", Expr);
833 end if;
834 end if;
835 end Machine_Radix;
837 -----------------
838 -- Object_Size --
839 -----------------
841 -- Object_Size attribute definition clause
843 when Attribute_Object_Size => Object_Size : declare
844 Size : constant Uint := Static_Integer (Expr);
845 Biased : Boolean;
847 begin
848 if not Is_Type (U_Ent) then
849 Error_Msg_N ("Object_Size cannot be given for &", Nam);
851 elsif Has_Object_Size_Clause (U_Ent) then
852 Error_Msg_N ("Object_Size already given for &", Nam);
854 else
855 Check_Size (Expr, U_Ent, Size, Biased);
857 if Size /= 8
858 and then
859 Size /= 16
860 and then
861 Size /= 32
862 and then
863 UI_Mod (Size, 64) /= 0
864 then
865 Error_Msg_N
866 ("Object_Size must be 8, 16, 32, or multiple of 64",
867 Expr);
868 end if;
870 Set_Esize (U_Ent, Size);
871 Set_Has_Object_Size_Clause (U_Ent);
872 Alignment_Check_For_Esize_Change (U_Ent);
873 end if;
874 end Object_Size;
876 ------------
877 -- Output --
878 ------------
880 when Attribute_Output =>
881 Analyze_Stream_TSS_Definition (TSS_Stream_Output);
882 Set_Has_Specified_Stream_Output (Ent);
884 ----------
885 -- Read --
886 ----------
888 when Attribute_Read =>
889 Analyze_Stream_TSS_Definition (TSS_Stream_Read);
890 Set_Has_Specified_Stream_Read (Ent);
892 ----------
893 -- Size --
894 ----------
896 -- Size attribute definition clause
898 when Attribute_Size => Size : declare
899 Size : constant Uint := Static_Integer (Expr);
900 Etyp : Entity_Id;
901 Biased : Boolean;
903 begin
904 FOnly := True;
906 if Has_Size_Clause (U_Ent) then
907 Error_Msg_N ("size already given for &", Nam);
909 elsif not Is_Type (U_Ent)
910 and then Ekind (U_Ent) /= E_Variable
911 and then Ekind (U_Ent) /= E_Constant
912 then
913 Error_Msg_N ("size cannot be given for &", Nam);
915 elsif Is_Array_Type (U_Ent)
916 and then not Is_Constrained (U_Ent)
917 then
918 Error_Msg_N
919 ("size cannot be given for unconstrained array", Nam);
921 elsif Size /= No_Uint then
922 if Is_Type (U_Ent) then
923 Etyp := U_Ent;
924 else
925 Etyp := Etype (U_Ent);
926 end if;
928 -- Check size, note that Gigi is in charge of checking
929 -- that the size of an array or record type is OK. Also
930 -- we do not check the size in the ordinary fixed-point
931 -- case, since it is too early to do so (there may be a
932 -- subsequent small clause that affects the size). We can
933 -- check the size if a small clause has already been given.
935 if not Is_Ordinary_Fixed_Point_Type (U_Ent)
936 or else Has_Small_Clause (U_Ent)
937 then
938 Check_Size (Expr, Etyp, Size, Biased);
939 Set_Has_Biased_Representation (U_Ent, Biased);
940 end if;
942 -- For types set RM_Size and Esize if possible
944 if Is_Type (U_Ent) then
945 Set_RM_Size (U_Ent, Size);
947 -- For scalar types, increase Object_Size to power of 2,
948 -- but not less than a storage unit in any case (i.e.,
949 -- normally this means it will be byte addressable).
951 if Is_Scalar_Type (U_Ent) then
952 if Size <= System_Storage_Unit then
953 Init_Esize (U_Ent, System_Storage_Unit);
954 elsif Size <= 16 then
955 Init_Esize (U_Ent, 16);
956 elsif Size <= 32 then
957 Init_Esize (U_Ent, 32);
958 else
959 Set_Esize (U_Ent, (Size + 63) / 64 * 64);
960 end if;
962 -- For all other types, object size = value size. The
963 -- backend will adjust as needed.
965 else
966 Set_Esize (U_Ent, Size);
967 end if;
969 Alignment_Check_For_Esize_Change (U_Ent);
971 -- For objects, set Esize only
973 else
974 if Is_Elementary_Type (Etyp) then
975 if Size /= System_Storage_Unit
976 and then
977 Size /= System_Storage_Unit * 2
978 and then
979 Size /= System_Storage_Unit * 4
980 and then
981 Size /= System_Storage_Unit * 8
982 then
983 Error_Msg_Uint_1 := UI_From_Int (System_Storage_Unit);
984 Error_Msg_Uint_2 := Error_Msg_Uint_1 * 8;
985 Error_Msg_N
986 ("size for primitive object must be a power of 2"
987 & " in the range ^-^", N);
988 end if;
989 end if;
991 Set_Esize (U_Ent, Size);
992 end if;
994 Set_Has_Size_Clause (U_Ent);
995 end if;
996 end Size;
998 -----------
999 -- Small --
1000 -----------
1002 -- Small attribute definition clause
1004 when Attribute_Small => Small : declare
1005 Implicit_Base : constant Entity_Id := Base_Type (U_Ent);
1006 Small : Ureal;
1008 begin
1009 Analyze_And_Resolve (Expr, Any_Real);
1011 if Etype (Expr) = Any_Type then
1012 return;
1014 elsif not Is_Static_Expression (Expr) then
1015 Flag_Non_Static_Expr
1016 ("small requires static expression!", Expr);
1017 return;
1019 else
1020 Small := Expr_Value_R (Expr);
1022 if Small <= Ureal_0 then
1023 Error_Msg_N ("small value must be greater than zero", Expr);
1024 return;
1025 end if;
1027 end if;
1029 if not Is_Ordinary_Fixed_Point_Type (U_Ent) then
1030 Error_Msg_N
1031 ("small requires an ordinary fixed point type", Nam);
1033 elsif Has_Small_Clause (U_Ent) then
1034 Error_Msg_N ("small already given for &", Nam);
1036 elsif Small > Delta_Value (U_Ent) then
1037 Error_Msg_N
1038 ("small value must not be greater then delta value", Nam);
1040 else
1041 Set_Small_Value (U_Ent, Small);
1042 Set_Small_Value (Implicit_Base, Small);
1043 Set_Has_Small_Clause (U_Ent);
1044 Set_Has_Small_Clause (Implicit_Base);
1045 Set_Has_Non_Standard_Rep (Implicit_Base);
1046 end if;
1047 end Small;
1049 ------------------
1050 -- Storage_Size --
1051 ------------------
1053 -- Storage_Size attribute definition clause
1055 when Attribute_Storage_Size => Storage_Size : declare
1056 Btype : constant Entity_Id := Base_Type (U_Ent);
1057 Sprag : Node_Id;
1059 begin
1060 if Is_Task_Type (U_Ent) then
1061 Check_Restriction (No_Obsolescent_Features, N);
1063 if Warn_On_Obsolescent_Feature then
1064 Error_Msg_N
1065 ("storage size clause for task is an " &
1066 "obsolescent feature ('R'M 'J.9)?", N);
1067 Error_Msg_N
1068 ("\use Storage_Size pragma instead?", N);
1069 end if;
1071 FOnly := True;
1072 end if;
1074 if not Is_Access_Type (U_Ent)
1075 and then Ekind (U_Ent) /= E_Task_Type
1076 then
1077 Error_Msg_N ("storage size cannot be given for &", Nam);
1079 elsif Is_Access_Type (U_Ent) and Is_Derived_Type (U_Ent) then
1080 Error_Msg_N
1081 ("storage size cannot be given for a derived access type",
1082 Nam);
1084 elsif Has_Storage_Size_Clause (Btype) then
1085 Error_Msg_N ("storage size already given for &", Nam);
1087 else
1088 Analyze_And_Resolve (Expr, Any_Integer);
1090 if Is_Access_Type (U_Ent) then
1092 if Present (Associated_Storage_Pool (U_Ent)) then
1093 Error_Msg_N ("storage pool already given for &", Nam);
1094 return;
1095 end if;
1097 if Compile_Time_Known_Value (Expr)
1098 and then Expr_Value (Expr) = 0
1099 then
1100 Set_No_Pool_Assigned (Btype);
1101 end if;
1103 else -- Is_Task_Type (U_Ent)
1104 Sprag := Get_Rep_Pragma (Btype, Name_Storage_Size);
1106 if Present (Sprag) then
1107 Error_Msg_Sloc := Sloc (Sprag);
1108 Error_Msg_N
1109 ("Storage_Size already specified#", Nam);
1110 return;
1111 end if;
1112 end if;
1114 Set_Has_Storage_Size_Clause (Btype);
1115 end if;
1116 end Storage_Size;
1118 ------------------
1119 -- Storage_Pool --
1120 ------------------
1122 -- Storage_Pool attribute definition clause
1124 when Attribute_Storage_Pool => Storage_Pool : declare
1125 Pool : Entity_Id;
1126 T : Entity_Id;
1128 begin
1129 if Ekind (U_Ent) /= E_Access_Type
1130 and then Ekind (U_Ent) /= E_General_Access_Type
1131 then
1132 Error_Msg_N (
1133 "storage pool can only be given for access types", Nam);
1134 return;
1136 elsif Is_Derived_Type (U_Ent) then
1137 Error_Msg_N
1138 ("storage pool cannot be given for a derived access type",
1139 Nam);
1141 elsif Has_Storage_Size_Clause (U_Ent) then
1142 Error_Msg_N ("storage size already given for &", Nam);
1143 return;
1145 elsif Present (Associated_Storage_Pool (U_Ent)) then
1146 Error_Msg_N ("storage pool already given for &", Nam);
1147 return;
1148 end if;
1150 Analyze_And_Resolve
1151 (Expr, Class_Wide_Type (RTE (RE_Root_Storage_Pool)));
1153 if Nkind (Expr) = N_Type_Conversion then
1154 T := Etype (Expression (Expr));
1155 else
1156 T := Etype (Expr);
1157 end if;
1159 -- The Stack_Bounded_Pool is used internally for implementing
1160 -- access types with a Storage_Size. Since it only work
1161 -- properly when used on one specific type, we need to check
1162 -- that it is not highjacked improperly:
1163 -- type T is access Integer;
1164 -- for T'Storage_Size use n;
1165 -- type Q is access Float;
1166 -- for Q'Storage_Size use T'Storage_Size; -- incorrect
1168 if Base_Type (T) = RTE (RE_Stack_Bounded_Pool) then
1169 Error_Msg_N ("non-sharable internal Pool", Expr);
1170 return;
1171 end if;
1173 -- If the argument is a name that is not an entity name, then
1174 -- we construct a renaming operation to define an entity of
1175 -- type storage pool.
1177 if not Is_Entity_Name (Expr)
1178 and then Is_Object_Reference (Expr)
1179 then
1180 Pool :=
1181 Make_Defining_Identifier (Loc,
1182 Chars => New_Internal_Name ('P'));
1184 declare
1185 Rnode : constant Node_Id :=
1186 Make_Object_Renaming_Declaration (Loc,
1187 Defining_Identifier => Pool,
1188 Subtype_Mark =>
1189 New_Occurrence_Of (Etype (Expr), Loc),
1190 Name => Expr);
1192 begin
1193 Insert_Before (N, Rnode);
1194 Analyze (Rnode);
1195 Set_Associated_Storage_Pool (U_Ent, Pool);
1196 end;
1198 elsif Is_Entity_Name (Expr) then
1199 Pool := Entity (Expr);
1201 -- If pool is a renamed object, get original one. This can
1202 -- happen with an explicit renaming, and within instances.
1204 while Present (Renamed_Object (Pool))
1205 and then Is_Entity_Name (Renamed_Object (Pool))
1206 loop
1207 Pool := Entity (Renamed_Object (Pool));
1208 end loop;
1210 if Present (Renamed_Object (Pool))
1211 and then Nkind (Renamed_Object (Pool)) = N_Type_Conversion
1212 and then Is_Entity_Name (Expression (Renamed_Object (Pool)))
1213 then
1214 Pool := Entity (Expression (Renamed_Object (Pool)));
1215 end if;
1217 Set_Associated_Storage_Pool (U_Ent, Pool);
1219 elsif Nkind (Expr) = N_Type_Conversion
1220 and then Is_Entity_Name (Expression (Expr))
1221 and then Nkind (Original_Node (Expr)) = N_Attribute_Reference
1222 then
1223 Pool := Entity (Expression (Expr));
1224 Set_Associated_Storage_Pool (U_Ent, Pool);
1226 else
1227 Error_Msg_N ("incorrect reference to a Storage Pool", Expr);
1228 return;
1229 end if;
1230 end Storage_Pool;
1232 -----------------
1233 -- Stream_Size --
1234 -----------------
1236 when Attribute_Stream_Size => Stream_Size : declare
1237 Size : constant Uint := Static_Integer (Expr);
1239 begin
1240 if Has_Stream_Size_Clause (U_Ent) then
1241 Error_Msg_N ("Stream_Size already given for &", Nam);
1243 elsif Is_Elementary_Type (U_Ent) then
1244 if Size /= System_Storage_Unit
1245 and then
1246 Size /= System_Storage_Unit * 2
1247 and then
1248 Size /= System_Storage_Unit * 4
1249 and then
1250 Size /= System_Storage_Unit * 8
1251 then
1252 Error_Msg_Uint_1 := UI_From_Int (System_Storage_Unit);
1253 Error_Msg_N
1254 ("stream size for elementary type must be a"
1255 & " power of 2 and at least ^", N);
1257 elsif RM_Size (U_Ent) > Size then
1258 Error_Msg_Uint_1 := RM_Size (U_Ent);
1259 Error_Msg_N
1260 ("stream size for elementary type must be a"
1261 & " power of 2 and at least ^", N);
1262 end if;
1264 Set_Has_Stream_Size_Clause (U_Ent);
1266 else
1267 Error_Msg_N ("Stream_Size cannot be given for &", Nam);
1268 end if;
1269 end Stream_Size;
1271 ----------------
1272 -- Value_Size --
1273 ----------------
1275 -- Value_Size attribute definition clause
1277 when Attribute_Value_Size => Value_Size : declare
1278 Size : constant Uint := Static_Integer (Expr);
1279 Biased : Boolean;
1281 begin
1282 if not Is_Type (U_Ent) then
1283 Error_Msg_N ("Value_Size cannot be given for &", Nam);
1285 elsif Present
1286 (Get_Attribute_Definition_Clause
1287 (U_Ent, Attribute_Value_Size))
1288 then
1289 Error_Msg_N ("Value_Size already given for &", Nam);
1291 else
1292 if Is_Elementary_Type (U_Ent) then
1293 Check_Size (Expr, U_Ent, Size, Biased);
1294 Set_Has_Biased_Representation (U_Ent, Biased);
1295 end if;
1297 Set_RM_Size (U_Ent, Size);
1298 end if;
1299 end Value_Size;
1301 -----------
1302 -- Write --
1303 -----------
1305 when Attribute_Write =>
1306 Analyze_Stream_TSS_Definition (TSS_Stream_Write);
1307 Set_Has_Specified_Stream_Write (Ent);
1309 -- All other attributes cannot be set
1311 when others =>
1312 Error_Msg_N
1313 ("attribute& cannot be set with definition clause", N);
1314 end case;
1316 -- The test for the type being frozen must be performed after
1317 -- any expression the clause has been analyzed since the expression
1318 -- itself might cause freezing that makes the clause illegal.
1320 if Rep_Item_Too_Late (U_Ent, N, FOnly) then
1321 return;
1322 end if;
1323 end Analyze_Attribute_Definition_Clause;
1325 ----------------------------
1326 -- Analyze_Code_Statement --
1327 ----------------------------
1329 procedure Analyze_Code_Statement (N : Node_Id) is
1330 HSS : constant Node_Id := Parent (N);
1331 SBody : constant Node_Id := Parent (HSS);
1332 Subp : constant Entity_Id := Current_Scope;
1333 Stmt : Node_Id;
1334 Decl : Node_Id;
1335 StmtO : Node_Id;
1336 DeclO : Node_Id;
1338 begin
1339 -- Analyze and check we get right type, note that this implements the
1340 -- requirement (RM 13.8(1)) that Machine_Code be with'ed, since that
1341 -- is the only way that Asm_Insn could possibly be visible.
1343 Analyze_And_Resolve (Expression (N));
1345 if Etype (Expression (N)) = Any_Type then
1346 return;
1347 elsif Etype (Expression (N)) /= RTE (RE_Asm_Insn) then
1348 Error_Msg_N ("incorrect type for code statement", N);
1349 return;
1350 end if;
1352 -- Make sure we appear in the handled statement sequence of a
1353 -- subprogram (RM 13.8(3)).
1355 if Nkind (HSS) /= N_Handled_Sequence_Of_Statements
1356 or else Nkind (SBody) /= N_Subprogram_Body
1357 then
1358 Error_Msg_N
1359 ("code statement can only appear in body of subprogram", N);
1360 return;
1361 end if;
1363 -- Do remaining checks (RM 13.8(3)) if not already done
1365 if not Is_Machine_Code_Subprogram (Subp) then
1366 Set_Is_Machine_Code_Subprogram (Subp);
1368 -- No exception handlers allowed
1370 if Present (Exception_Handlers (HSS)) then
1371 Error_Msg_N
1372 ("exception handlers not permitted in machine code subprogram",
1373 First (Exception_Handlers (HSS)));
1374 end if;
1376 -- No declarations other than use clauses and pragmas (we allow
1377 -- certain internally generated declarations as well).
1379 Decl := First (Declarations (SBody));
1380 while Present (Decl) loop
1381 DeclO := Original_Node (Decl);
1382 if Comes_From_Source (DeclO)
1383 and then Nkind (DeclO) /= N_Pragma
1384 and then Nkind (DeclO) /= N_Use_Package_Clause
1385 and then Nkind (DeclO) /= N_Use_Type_Clause
1386 and then Nkind (DeclO) /= N_Implicit_Label_Declaration
1387 then
1388 Error_Msg_N
1389 ("this declaration not allowed in machine code subprogram",
1390 DeclO);
1391 end if;
1393 Next (Decl);
1394 end loop;
1396 -- No statements other than code statements, pragmas, and labels.
1397 -- Again we allow certain internally generated statements.
1399 Stmt := First (Statements (HSS));
1400 while Present (Stmt) loop
1401 StmtO := Original_Node (Stmt);
1402 if Comes_From_Source (StmtO)
1403 and then Nkind (StmtO) /= N_Pragma
1404 and then Nkind (StmtO) /= N_Label
1405 and then Nkind (StmtO) /= N_Code_Statement
1406 then
1407 Error_Msg_N
1408 ("this statement is not allowed in machine code subprogram",
1409 StmtO);
1410 end if;
1412 Next (Stmt);
1413 end loop;
1414 end if;
1415 end Analyze_Code_Statement;
1417 -----------------------------------------------
1418 -- Analyze_Enumeration_Representation_Clause --
1419 -----------------------------------------------
1421 procedure Analyze_Enumeration_Representation_Clause (N : Node_Id) is
1422 Ident : constant Node_Id := Identifier (N);
1423 Aggr : constant Node_Id := Array_Aggregate (N);
1424 Enumtype : Entity_Id;
1425 Elit : Entity_Id;
1426 Expr : Node_Id;
1427 Assoc : Node_Id;
1428 Choice : Node_Id;
1429 Val : Uint;
1430 Err : Boolean := False;
1432 Lo : constant Uint := Expr_Value (Type_Low_Bound (Universal_Integer));
1433 Hi : constant Uint := Expr_Value (Type_High_Bound (Universal_Integer));
1434 Min : Uint;
1435 Max : Uint;
1437 begin
1438 -- First some basic error checks
1440 Find_Type (Ident);
1441 Enumtype := Entity (Ident);
1443 if Enumtype = Any_Type
1444 or else Rep_Item_Too_Early (Enumtype, N)
1445 then
1446 return;
1447 else
1448 Enumtype := Underlying_Type (Enumtype);
1449 end if;
1451 if not Is_Enumeration_Type (Enumtype) then
1452 Error_Msg_NE
1453 ("enumeration type required, found}",
1454 Ident, First_Subtype (Enumtype));
1455 return;
1456 end if;
1458 -- Ignore rep clause on generic actual type. This will already have
1459 -- been flagged on the template as an error, and this is the safest
1460 -- way to ensure we don't get a junk cascaded message in the instance.
1462 if Is_Generic_Actual_Type (Enumtype) then
1463 return;
1465 -- Type must be in current scope
1467 elsif Scope (Enumtype) /= Current_Scope then
1468 Error_Msg_N ("type must be declared in this scope", Ident);
1469 return;
1471 -- Type must be a first subtype
1473 elsif not Is_First_Subtype (Enumtype) then
1474 Error_Msg_N ("cannot give enumeration rep clause for subtype", N);
1475 return;
1477 -- Ignore duplicate rep clause
1479 elsif Has_Enumeration_Rep_Clause (Enumtype) then
1480 Error_Msg_N ("duplicate enumeration rep clause ignored", N);
1481 return;
1483 -- Don't allow rep clause for standard [wide_[wide_]]character
1485 elsif Root_Type (Enumtype) = Standard_Character
1486 or else Root_Type (Enumtype) = Standard_Wide_Character
1487 or else Root_Type (Enumtype) = Standard_Wide_Wide_Character
1488 then
1489 Error_Msg_N ("enumeration rep clause not allowed for this type", N);
1490 return;
1492 -- Check that the expression is a proper aggregate (no parentheses)
1494 elsif Paren_Count (Aggr) /= 0 then
1495 Error_Msg
1496 ("extra parentheses surrounding aggregate not allowed",
1497 First_Sloc (Aggr));
1498 return;
1500 -- All tests passed, so set rep clause in place
1502 else
1503 Set_Has_Enumeration_Rep_Clause (Enumtype);
1504 Set_Has_Enumeration_Rep_Clause (Base_Type (Enumtype));
1505 end if;
1507 -- Now we process the aggregate. Note that we don't use the normal
1508 -- aggregate code for this purpose, because we don't want any of the
1509 -- normal expansion activities, and a number of special semantic
1510 -- rules apply (including the component type being any integer type)
1512 Elit := First_Literal (Enumtype);
1514 -- First the positional entries if any
1516 if Present (Expressions (Aggr)) then
1517 Expr := First (Expressions (Aggr));
1518 while Present (Expr) loop
1519 if No (Elit) then
1520 Error_Msg_N ("too many entries in aggregate", Expr);
1521 return;
1522 end if;
1524 Val := Static_Integer (Expr);
1526 -- Err signals that we found some incorrect entries processing
1527 -- the list. The final checks for completeness and ordering are
1528 -- skipped in this case.
1530 if Val = No_Uint then
1531 Err := True;
1532 elsif Val < Lo or else Hi < Val then
1533 Error_Msg_N ("value outside permitted range", Expr);
1534 Err := True;
1535 end if;
1537 Set_Enumeration_Rep (Elit, Val);
1538 Set_Enumeration_Rep_Expr (Elit, Expr);
1539 Next (Expr);
1540 Next (Elit);
1541 end loop;
1542 end if;
1544 -- Now process the named entries if present
1546 if Present (Component_Associations (Aggr)) then
1547 Assoc := First (Component_Associations (Aggr));
1548 while Present (Assoc) loop
1549 Choice := First (Choices (Assoc));
1551 if Present (Next (Choice)) then
1552 Error_Msg_N
1553 ("multiple choice not allowed here", Next (Choice));
1554 Err := True;
1555 end if;
1557 if Nkind (Choice) = N_Others_Choice then
1558 Error_Msg_N ("others choice not allowed here", Choice);
1559 Err := True;
1561 elsif Nkind (Choice) = N_Range then
1562 -- ??? should allow zero/one element range here
1563 Error_Msg_N ("range not allowed here", Choice);
1564 Err := True;
1566 else
1567 Analyze_And_Resolve (Choice, Enumtype);
1569 if Is_Entity_Name (Choice)
1570 and then Is_Type (Entity (Choice))
1571 then
1572 Error_Msg_N ("subtype name not allowed here", Choice);
1573 Err := True;
1574 -- ??? should allow static subtype with zero/one entry
1576 elsif Etype (Choice) = Base_Type (Enumtype) then
1577 if not Is_Static_Expression (Choice) then
1578 Flag_Non_Static_Expr
1579 ("non-static expression used for choice!", Choice);
1580 Err := True;
1582 else
1583 Elit := Expr_Value_E (Choice);
1585 if Present (Enumeration_Rep_Expr (Elit)) then
1586 Error_Msg_Sloc := Sloc (Enumeration_Rep_Expr (Elit));
1587 Error_Msg_NE
1588 ("representation for& previously given#",
1589 Choice, Elit);
1590 Err := True;
1591 end if;
1593 Set_Enumeration_Rep_Expr (Elit, Choice);
1595 Expr := Expression (Assoc);
1596 Val := Static_Integer (Expr);
1598 if Val = No_Uint then
1599 Err := True;
1601 elsif Val < Lo or else Hi < Val then
1602 Error_Msg_N ("value outside permitted range", Expr);
1603 Err := True;
1604 end if;
1606 Set_Enumeration_Rep (Elit, Val);
1607 end if;
1608 end if;
1609 end if;
1611 Next (Assoc);
1612 end loop;
1613 end if;
1615 -- Aggregate is fully processed. Now we check that a full set of
1616 -- representations was given, and that they are in range and in order.
1617 -- These checks are only done if no other errors occurred.
1619 if not Err then
1620 Min := No_Uint;
1621 Max := No_Uint;
1623 Elit := First_Literal (Enumtype);
1624 while Present (Elit) loop
1625 if No (Enumeration_Rep_Expr (Elit)) then
1626 Error_Msg_NE ("missing representation for&!", N, Elit);
1628 else
1629 Val := Enumeration_Rep (Elit);
1631 if Min = No_Uint then
1632 Min := Val;
1633 end if;
1635 if Val /= No_Uint then
1636 if Max /= No_Uint and then Val <= Max then
1637 Error_Msg_NE
1638 ("enumeration value for& not ordered!",
1639 Enumeration_Rep_Expr (Elit), Elit);
1640 end if;
1642 Max := Val;
1643 end if;
1645 -- If there is at least one literal whose representation
1646 -- is not equal to the Pos value, then note that this
1647 -- enumeration type has a non-standard representation.
1649 if Val /= Enumeration_Pos (Elit) then
1650 Set_Has_Non_Standard_Rep (Base_Type (Enumtype));
1651 end if;
1652 end if;
1654 Next (Elit);
1655 end loop;
1657 -- Now set proper size information
1659 declare
1660 Minsize : Uint := UI_From_Int (Minimum_Size (Enumtype));
1662 begin
1663 if Has_Size_Clause (Enumtype) then
1664 if Esize (Enumtype) >= Minsize then
1665 null;
1667 else
1668 Minsize :=
1669 UI_From_Int (Minimum_Size (Enumtype, Biased => True));
1671 if Esize (Enumtype) < Minsize then
1672 Error_Msg_N ("previously given size is too small", N);
1674 else
1675 Set_Has_Biased_Representation (Enumtype);
1676 end if;
1677 end if;
1679 else
1680 Set_RM_Size (Enumtype, Minsize);
1681 Set_Enum_Esize (Enumtype);
1682 end if;
1684 Set_RM_Size (Base_Type (Enumtype), RM_Size (Enumtype));
1685 Set_Esize (Base_Type (Enumtype), Esize (Enumtype));
1686 Set_Alignment (Base_Type (Enumtype), Alignment (Enumtype));
1687 end;
1688 end if;
1690 -- We repeat the too late test in case it froze itself!
1692 if Rep_Item_Too_Late (Enumtype, N) then
1693 null;
1694 end if;
1695 end Analyze_Enumeration_Representation_Clause;
1697 ----------------------------
1698 -- Analyze_Free_Statement --
1699 ----------------------------
1701 procedure Analyze_Free_Statement (N : Node_Id) is
1702 begin
1703 Analyze (Expression (N));
1704 end Analyze_Free_Statement;
1706 ------------------------------------------
1707 -- Analyze_Record_Representation_Clause --
1708 ------------------------------------------
1710 procedure Analyze_Record_Representation_Clause (N : Node_Id) is
1711 Loc : constant Source_Ptr := Sloc (N);
1712 Ident : constant Node_Id := Identifier (N);
1713 Rectype : Entity_Id;
1714 Fent : Entity_Id;
1715 CC : Node_Id;
1716 Posit : Uint;
1717 Fbit : Uint;
1718 Lbit : Uint;
1719 Hbit : Uint := Uint_0;
1720 Comp : Entity_Id;
1721 Ocomp : Entity_Id;
1722 Biased : Boolean;
1724 Max_Bit_So_Far : Uint;
1725 -- Records the maximum bit position so far. If all field positions
1726 -- are monotonically increasing, then we can skip the circuit for
1727 -- checking for overlap, since no overlap is possible.
1729 Overlap_Check_Required : Boolean;
1730 -- Used to keep track of whether or not an overlap check is required
1732 Ccount : Natural := 0;
1733 -- Number of component clauses in record rep clause
1735 CR_Pragma : Node_Id := Empty;
1736 -- Points to N_Pragma node if Complete_Representation pragma present
1738 begin
1739 Find_Type (Ident);
1740 Rectype := Entity (Ident);
1742 if Rectype = Any_Type
1743 or else Rep_Item_Too_Early (Rectype, N)
1744 then
1745 return;
1746 else
1747 Rectype := Underlying_Type (Rectype);
1748 end if;
1750 -- First some basic error checks
1752 if not Is_Record_Type (Rectype) then
1753 Error_Msg_NE
1754 ("record type required, found}", Ident, First_Subtype (Rectype));
1755 return;
1757 elsif Is_Unchecked_Union (Rectype) then
1758 Error_Msg_N
1759 ("record rep clause not allowed for Unchecked_Union", N);
1761 elsif Scope (Rectype) /= Current_Scope then
1762 Error_Msg_N ("type must be declared in this scope", N);
1763 return;
1765 elsif not Is_First_Subtype (Rectype) then
1766 Error_Msg_N ("cannot give record rep clause for subtype", N);
1767 return;
1769 elsif Has_Record_Rep_Clause (Rectype) then
1770 Error_Msg_N ("duplicate record rep clause ignored", N);
1771 return;
1773 elsif Rep_Item_Too_Late (Rectype, N) then
1774 return;
1775 end if;
1777 if Present (Mod_Clause (N)) then
1778 declare
1779 Loc : constant Source_Ptr := Sloc (N);
1780 M : constant Node_Id := Mod_Clause (N);
1781 P : constant List_Id := Pragmas_Before (M);
1782 AtM_Nod : Node_Id;
1784 Mod_Val : Uint;
1785 pragma Warnings (Off, Mod_Val);
1787 begin
1788 Check_Restriction (No_Obsolescent_Features, Mod_Clause (N));
1790 if Warn_On_Obsolescent_Feature then
1791 Error_Msg_N
1792 ("mod clause is an obsolescent feature ('R'M 'J.8)?", N);
1793 Error_Msg_N
1794 ("\use alignment attribute definition clause instead?", N);
1795 end if;
1797 if Present (P) then
1798 Analyze_List (P);
1799 end if;
1801 -- In ASIS_Mode mode, expansion is disabled, but we must
1802 -- convert the Mod clause into an alignment clause anyway, so
1803 -- that the back-end can compute and back-annotate properly the
1804 -- size and alignment of types that may include this record.
1806 if Operating_Mode = Check_Semantics
1807 and then ASIS_Mode
1808 then
1809 AtM_Nod :=
1810 Make_Attribute_Definition_Clause (Loc,
1811 Name => New_Reference_To (Base_Type (Rectype), Loc),
1812 Chars => Name_Alignment,
1813 Expression => Relocate_Node (Expression (M)));
1815 Set_From_At_Mod (AtM_Nod);
1816 Insert_After (N, AtM_Nod);
1817 Mod_Val := Get_Alignment_Value (Expression (AtM_Nod));
1818 Set_Mod_Clause (N, Empty);
1820 else
1821 -- Get the alignment value to perform error checking
1823 Mod_Val := Get_Alignment_Value (Expression (M));
1825 end if;
1826 end;
1827 end if;
1829 -- Clear any existing component clauses for the type (this happens
1830 -- with derived types, where we are now overriding the original)
1832 Fent := First_Entity (Rectype);
1834 Comp := Fent;
1835 while Present (Comp) loop
1836 if Ekind (Comp) = E_Component
1837 or else Ekind (Comp) = E_Discriminant
1838 then
1839 Set_Component_Clause (Comp, Empty);
1840 end if;
1842 Next_Entity (Comp);
1843 end loop;
1845 -- All done if no component clauses
1847 CC := First (Component_Clauses (N));
1849 if No (CC) then
1850 return;
1851 end if;
1853 -- If a tag is present, then create a component clause that places
1854 -- it at the start of the record (otherwise gigi may place it after
1855 -- other fields that have rep clauses).
1857 if Nkind (Fent) = N_Defining_Identifier
1858 and then Chars (Fent) = Name_uTag
1859 then
1860 Set_Component_Bit_Offset (Fent, Uint_0);
1861 Set_Normalized_Position (Fent, Uint_0);
1862 Set_Normalized_First_Bit (Fent, Uint_0);
1863 Set_Normalized_Position_Max (Fent, Uint_0);
1864 Init_Esize (Fent, System_Address_Size);
1866 Set_Component_Clause (Fent,
1867 Make_Component_Clause (Loc,
1868 Component_Name =>
1869 Make_Identifier (Loc,
1870 Chars => Name_uTag),
1872 Position =>
1873 Make_Integer_Literal (Loc,
1874 Intval => Uint_0),
1876 First_Bit =>
1877 Make_Integer_Literal (Loc,
1878 Intval => Uint_0),
1880 Last_Bit =>
1881 Make_Integer_Literal (Loc,
1882 UI_From_Int (System_Address_Size))));
1884 Ccount := Ccount + 1;
1885 end if;
1887 -- A representation like this applies to the base type
1889 Set_Has_Record_Rep_Clause (Base_Type (Rectype));
1890 Set_Has_Non_Standard_Rep (Base_Type (Rectype));
1891 Set_Has_Specified_Layout (Base_Type (Rectype));
1893 Max_Bit_So_Far := Uint_Minus_1;
1894 Overlap_Check_Required := False;
1896 -- Process the component clauses
1898 while Present (CC) loop
1900 -- Pragma
1902 if Nkind (CC) = N_Pragma then
1903 Analyze (CC);
1905 -- The only pragma of interest is Complete_Representation
1907 if Chars (CC) = Name_Complete_Representation then
1908 CR_Pragma := CC;
1909 end if;
1911 -- Processing for real component clause
1913 else
1914 Ccount := Ccount + 1;
1915 Posit := Static_Integer (Position (CC));
1916 Fbit := Static_Integer (First_Bit (CC));
1917 Lbit := Static_Integer (Last_Bit (CC));
1919 if Posit /= No_Uint
1920 and then Fbit /= No_Uint
1921 and then Lbit /= No_Uint
1922 then
1923 if Posit < 0 then
1924 Error_Msg_N
1925 ("position cannot be negative", Position (CC));
1927 elsif Fbit < 0 then
1928 Error_Msg_N
1929 ("first bit cannot be negative", First_Bit (CC));
1931 -- Values look OK, so find the corresponding record component
1932 -- Even though the syntax allows an attribute reference for
1933 -- implementation-defined components, GNAT does not allow the
1934 -- tag to get an explicit position.
1936 elsif Nkind (Component_Name (CC)) = N_Attribute_Reference then
1937 if Attribute_Name (Component_Name (CC)) = Name_Tag then
1938 Error_Msg_N ("position of tag cannot be specified", CC);
1939 else
1940 Error_Msg_N ("illegal component name", CC);
1941 end if;
1943 else
1944 Comp := First_Entity (Rectype);
1945 while Present (Comp) loop
1946 exit when Chars (Comp) = Chars (Component_Name (CC));
1947 Next_Entity (Comp);
1948 end loop;
1950 if No (Comp) then
1952 -- Maybe component of base type that is absent from
1953 -- statically constrained first subtype.
1955 Comp := First_Entity (Base_Type (Rectype));
1956 while Present (Comp) loop
1957 exit when Chars (Comp) = Chars (Component_Name (CC));
1958 Next_Entity (Comp);
1959 end loop;
1960 end if;
1962 if No (Comp) then
1963 Error_Msg_N
1964 ("component clause is for non-existent field", CC);
1966 elsif Present (Component_Clause (Comp)) then
1967 Error_Msg_Sloc := Sloc (Component_Clause (Comp));
1968 Error_Msg_N
1969 ("component clause previously given#", CC);
1971 else
1972 -- Update Fbit and Lbit to the actual bit number
1974 Fbit := Fbit + UI_From_Int (SSU) * Posit;
1975 Lbit := Lbit + UI_From_Int (SSU) * Posit;
1977 if Fbit <= Max_Bit_So_Far then
1978 Overlap_Check_Required := True;
1979 else
1980 Max_Bit_So_Far := Lbit;
1981 end if;
1983 if Has_Size_Clause (Rectype)
1984 and then Esize (Rectype) <= Lbit
1985 then
1986 Error_Msg_N
1987 ("bit number out of range of specified size",
1988 Last_Bit (CC));
1989 else
1990 Set_Component_Clause (Comp, CC);
1991 Set_Component_Bit_Offset (Comp, Fbit);
1992 Set_Esize (Comp, 1 + (Lbit - Fbit));
1993 Set_Normalized_First_Bit (Comp, Fbit mod SSU);
1994 Set_Normalized_Position (Comp, Fbit / SSU);
1996 Set_Normalized_Position_Max
1997 (Fent, Normalized_Position (Fent));
1999 if Is_Tagged_Type (Rectype)
2000 and then Fbit < System_Address_Size
2001 then
2002 Error_Msg_NE
2003 ("component overlaps tag field of&",
2004 CC, Rectype);
2005 end if;
2007 -- This information is also set in the corresponding
2008 -- component of the base type, found by accessing the
2009 -- Original_Record_Component link if it is present.
2011 Ocomp := Original_Record_Component (Comp);
2013 if Hbit < Lbit then
2014 Hbit := Lbit;
2015 end if;
2017 Check_Size
2018 (Component_Name (CC),
2019 Etype (Comp),
2020 Esize (Comp),
2021 Biased);
2023 Set_Has_Biased_Representation (Comp, Biased);
2025 if Present (Ocomp) then
2026 Set_Component_Clause (Ocomp, CC);
2027 Set_Component_Bit_Offset (Ocomp, Fbit);
2028 Set_Normalized_First_Bit (Ocomp, Fbit mod SSU);
2029 Set_Normalized_Position (Ocomp, Fbit / SSU);
2030 Set_Esize (Ocomp, 1 + (Lbit - Fbit));
2032 Set_Normalized_Position_Max
2033 (Ocomp, Normalized_Position (Ocomp));
2035 Set_Has_Biased_Representation
2036 (Ocomp, Has_Biased_Representation (Comp));
2037 end if;
2039 if Esize (Comp) < 0 then
2040 Error_Msg_N ("component size is negative", CC);
2041 end if;
2042 end if;
2043 end if;
2044 end if;
2045 end if;
2046 end if;
2048 Next (CC);
2049 end loop;
2051 -- Now that we have processed all the component clauses, check for
2052 -- overlap. We have to leave this till last, since the components
2053 -- can appear in any arbitrary order in the representation clause.
2055 -- We do not need this check if all specified ranges were monotonic,
2056 -- as recorded by Overlap_Check_Required being False at this stage.
2058 -- This first section checks if there are any overlapping entries
2059 -- at all. It does this by sorting all entries and then seeing if
2060 -- there are any overlaps. If there are none, then that is decisive,
2061 -- but if there are overlaps, they may still be OK (they may result
2062 -- from fields in different variants).
2064 if Overlap_Check_Required then
2065 Overlap_Check1 : declare
2067 OC_Fbit : array (0 .. Ccount) of Uint;
2068 -- First-bit values for component clauses, the value is the
2069 -- offset of the first bit of the field from start of record.
2070 -- The zero entry is for use in sorting.
2072 OC_Lbit : array (0 .. Ccount) of Uint;
2073 -- Last-bit values for component clauses, the value is the
2074 -- offset of the last bit of the field from start of record.
2075 -- The zero entry is for use in sorting.
2077 OC_Count : Natural := 0;
2078 -- Count of entries in OC_Fbit and OC_Lbit
2080 function OC_Lt (Op1, Op2 : Natural) return Boolean;
2081 -- Compare routine for Sort (See GNAT.Heap_Sort_A)
2083 procedure OC_Move (From : Natural; To : Natural);
2084 -- Move routine for Sort (see GNAT.Heap_Sort_A)
2086 function OC_Lt (Op1, Op2 : Natural) return Boolean is
2087 begin
2088 return OC_Fbit (Op1) < OC_Fbit (Op2);
2089 end OC_Lt;
2091 procedure OC_Move (From : Natural; To : Natural) is
2092 begin
2093 OC_Fbit (To) := OC_Fbit (From);
2094 OC_Lbit (To) := OC_Lbit (From);
2095 end OC_Move;
2097 begin
2098 CC := First (Component_Clauses (N));
2099 while Present (CC) loop
2100 if Nkind (CC) /= N_Pragma then
2101 Posit := Static_Integer (Position (CC));
2102 Fbit := Static_Integer (First_Bit (CC));
2103 Lbit := Static_Integer (Last_Bit (CC));
2105 if Posit /= No_Uint
2106 and then Fbit /= No_Uint
2107 and then Lbit /= No_Uint
2108 then
2109 OC_Count := OC_Count + 1;
2110 Posit := Posit * SSU;
2111 OC_Fbit (OC_Count) := Fbit + Posit;
2112 OC_Lbit (OC_Count) := Lbit + Posit;
2113 end if;
2114 end if;
2116 Next (CC);
2117 end loop;
2119 Sort
2120 (OC_Count,
2121 OC_Move'Unrestricted_Access,
2122 OC_Lt'Unrestricted_Access);
2124 Overlap_Check_Required := False;
2125 for J in 1 .. OC_Count - 1 loop
2126 if OC_Lbit (J) >= OC_Fbit (J + 1) then
2127 Overlap_Check_Required := True;
2128 exit;
2129 end if;
2130 end loop;
2131 end Overlap_Check1;
2132 end if;
2134 -- If Overlap_Check_Required is still True, then we have to do
2135 -- the full scale overlap check, since we have at least two fields
2136 -- that do overlap, and we need to know if that is OK since they
2137 -- are in the same variant, or whether we have a definite problem
2139 if Overlap_Check_Required then
2140 Overlap_Check2 : declare
2141 C1_Ent, C2_Ent : Entity_Id;
2142 -- Entities of components being checked for overlap
2144 Clist : Node_Id;
2145 -- Component_List node whose Component_Items are being checked
2147 Citem : Node_Id;
2148 -- Component declaration for component being checked
2150 begin
2151 C1_Ent := First_Entity (Base_Type (Rectype));
2153 -- Loop through all components in record. For each component check
2154 -- for overlap with any of the preceding elements on the component
2155 -- list containing the component, and also, if the component is in
2156 -- a variant, check against components outside the case structure.
2157 -- This latter test is repeated recursively up the variant tree.
2159 Main_Component_Loop : while Present (C1_Ent) loop
2160 if Ekind (C1_Ent) /= E_Component
2161 and then Ekind (C1_Ent) /= E_Discriminant
2162 then
2163 goto Continue_Main_Component_Loop;
2164 end if;
2166 -- Skip overlap check if entity has no declaration node. This
2167 -- happens with discriminants in constrained derived types.
2168 -- Probably we are missing some checks as a result, but that
2169 -- does not seem terribly serious ???
2171 if No (Declaration_Node (C1_Ent)) then
2172 goto Continue_Main_Component_Loop;
2173 end if;
2175 Clist := Parent (List_Containing (Declaration_Node (C1_Ent)));
2177 -- Loop through component lists that need checking. Check the
2178 -- current component list and all lists in variants above us.
2180 Component_List_Loop : loop
2182 -- If derived type definition, go to full declaration
2183 -- If at outer level, check discriminants if there are any
2185 if Nkind (Clist) = N_Derived_Type_Definition then
2186 Clist := Parent (Clist);
2187 end if;
2189 -- Outer level of record definition, check discriminants
2191 if Nkind (Clist) = N_Full_Type_Declaration
2192 or else Nkind (Clist) = N_Private_Type_Declaration
2193 then
2194 if Has_Discriminants (Defining_Identifier (Clist)) then
2195 C2_Ent :=
2196 First_Discriminant (Defining_Identifier (Clist));
2198 while Present (C2_Ent) loop
2199 exit when C1_Ent = C2_Ent;
2200 Check_Component_Overlap (C1_Ent, C2_Ent);
2201 Next_Discriminant (C2_Ent);
2202 end loop;
2203 end if;
2205 -- Record extension case
2207 elsif Nkind (Clist) = N_Derived_Type_Definition then
2208 Clist := Empty;
2210 -- Otherwise check one component list
2212 else
2213 Citem := First (Component_Items (Clist));
2215 while Present (Citem) loop
2216 if Nkind (Citem) = N_Component_Declaration then
2217 C2_Ent := Defining_Identifier (Citem);
2218 exit when C1_Ent = C2_Ent;
2219 Check_Component_Overlap (C1_Ent, C2_Ent);
2220 end if;
2222 Next (Citem);
2223 end loop;
2224 end if;
2226 -- Check for variants above us (the parent of the Clist can
2227 -- be a variant, in which case its parent is a variant part,
2228 -- and the parent of the variant part is a component list
2229 -- whose components must all be checked against the current
2230 -- component for overlap.
2232 if Nkind (Parent (Clist)) = N_Variant then
2233 Clist := Parent (Parent (Parent (Clist)));
2235 -- Check for possible discriminant part in record, this is
2236 -- treated essentially as another level in the recursion.
2237 -- For this case we have the parent of the component list
2238 -- is the record definition, and its parent is the full
2239 -- type declaration which contains the discriminant
2240 -- specifications.
2242 elsif Nkind (Parent (Clist)) = N_Record_Definition then
2243 Clist := Parent (Parent ((Clist)));
2245 -- If neither of these two cases, we are at the top of
2246 -- the tree
2248 else
2249 exit Component_List_Loop;
2250 end if;
2251 end loop Component_List_Loop;
2253 <<Continue_Main_Component_Loop>>
2254 Next_Entity (C1_Ent);
2256 end loop Main_Component_Loop;
2257 end Overlap_Check2;
2258 end if;
2260 -- For records that have component clauses for all components, and
2261 -- whose size is less than or equal to 32, we need to know the size
2262 -- in the front end to activate possible packed array processing
2263 -- where the component type is a record.
2265 -- At this stage Hbit + 1 represents the first unused bit from all
2266 -- the component clauses processed, so if the component clauses are
2267 -- complete, then this is the length of the record.
2269 -- For records longer than System.Storage_Unit, and for those where
2270 -- not all components have component clauses, the back end determines
2271 -- the length (it may for example be appopriate to round up the size
2272 -- to some convenient boundary, based on alignment considerations etc).
2274 if Unknown_RM_Size (Rectype)
2275 and then Hbit + 1 <= 32
2276 then
2277 -- Nothing to do if at least one component with no component clause
2279 Comp := First_Entity (Rectype);
2280 while Present (Comp) loop
2281 if Ekind (Comp) = E_Component
2282 or else Ekind (Comp) = E_Discriminant
2283 then
2284 exit when No (Component_Clause (Comp));
2285 end if;
2287 Next_Entity (Comp);
2288 end loop;
2290 -- If we fall out of loop, all components have component clauses
2291 -- and so we can set the size to the maximum value.
2293 if No (Comp) then
2294 Set_RM_Size (Rectype, Hbit + 1);
2295 end if;
2296 end if;
2298 -- Check missing components if Complete_Representation pragma appeared
2300 if Present (CR_Pragma) then
2301 Comp := First_Entity (Rectype);
2302 while Present (Comp) loop
2303 if Ekind (Comp) = E_Component
2304 or else
2305 Ekind (Comp) = E_Discriminant
2306 then
2307 if No (Component_Clause (Comp)) then
2308 Error_Msg_NE
2309 ("missing component clause for &", CR_Pragma, Comp);
2310 end if;
2311 end if;
2313 Next_Entity (Comp);
2314 end loop;
2315 end if;
2316 end Analyze_Record_Representation_Clause;
2318 -----------------------------
2319 -- Check_Component_Overlap --
2320 -----------------------------
2322 procedure Check_Component_Overlap (C1_Ent, C2_Ent : Entity_Id) is
2323 begin
2324 if Present (Component_Clause (C1_Ent))
2325 and then Present (Component_Clause (C2_Ent))
2326 then
2327 -- Exclude odd case where we have two tag fields in the same
2328 -- record, both at location zero. This seems a bit strange,
2329 -- but it seems to happen in some circumstances ???
2331 if Chars (C1_Ent) = Name_uTag
2332 and then Chars (C2_Ent) = Name_uTag
2333 then
2334 return;
2335 end if;
2337 -- Here we check if the two fields overlap
2339 declare
2340 S1 : constant Uint := Component_Bit_Offset (C1_Ent);
2341 S2 : constant Uint := Component_Bit_Offset (C2_Ent);
2342 E1 : constant Uint := S1 + Esize (C1_Ent);
2343 E2 : constant Uint := S2 + Esize (C2_Ent);
2345 begin
2346 if E2 <= S1 or else E1 <= S2 then
2347 null;
2348 else
2349 Error_Msg_Node_2 :=
2350 Component_Name (Component_Clause (C2_Ent));
2351 Error_Msg_Sloc := Sloc (Error_Msg_Node_2);
2352 Error_Msg_Node_1 :=
2353 Component_Name (Component_Clause (C1_Ent));
2354 Error_Msg_N
2355 ("component& overlaps & #",
2356 Component_Name (Component_Clause (C1_Ent)));
2357 end if;
2358 end;
2359 end if;
2360 end Check_Component_Overlap;
2362 -----------------------------------
2363 -- Check_Constant_Address_Clause --
2364 -----------------------------------
2366 procedure Check_Constant_Address_Clause
2367 (Expr : Node_Id;
2368 U_Ent : Entity_Id)
2370 procedure Check_At_Constant_Address (Nod : Node_Id);
2371 -- Checks that the given node N represents a name whose 'Address
2372 -- is constant (in the same sense as OK_Constant_Address_Clause,
2373 -- i.e. the address value is the same at the point of declaration
2374 -- of U_Ent and at the time of elaboration of the address clause.
2376 procedure Check_Expr_Constants (Nod : Node_Id);
2377 -- Checks that Nod meets the requirements for a constant address
2378 -- clause in the sense of the enclosing procedure.
2380 procedure Check_List_Constants (Lst : List_Id);
2381 -- Check that all elements of list Lst meet the requirements for a
2382 -- constant address clause in the sense of the enclosing procedure.
2384 -------------------------------
2385 -- Check_At_Constant_Address --
2386 -------------------------------
2388 procedure Check_At_Constant_Address (Nod : Node_Id) is
2389 begin
2390 if Is_Entity_Name (Nod) then
2391 if Present (Address_Clause (Entity ((Nod)))) then
2392 Error_Msg_NE
2393 ("invalid address clause for initialized object &!",
2394 Nod, U_Ent);
2395 Error_Msg_NE
2396 ("address for& cannot" &
2397 " depend on another address clause! ('R'M 13.1(22))!",
2398 Nod, U_Ent);
2400 elsif In_Same_Source_Unit (Entity (Nod), U_Ent)
2401 and then Sloc (U_Ent) < Sloc (Entity (Nod))
2402 then
2403 Error_Msg_NE
2404 ("invalid address clause for initialized object &!",
2405 Nod, U_Ent);
2406 Error_Msg_Name_1 := Chars (Entity (Nod));
2407 Error_Msg_Name_2 := Chars (U_Ent);
2408 Error_Msg_N
2409 ("\% must be defined before % ('R'M 13.1(22))!",
2410 Nod);
2411 end if;
2413 elsif Nkind (Nod) = N_Selected_Component then
2414 declare
2415 T : constant Entity_Id := Etype (Prefix (Nod));
2417 begin
2418 if (Is_Record_Type (T)
2419 and then Has_Discriminants (T))
2420 or else
2421 (Is_Access_Type (T)
2422 and then Is_Record_Type (Designated_Type (T))
2423 and then Has_Discriminants (Designated_Type (T)))
2424 then
2425 Error_Msg_NE
2426 ("invalid address clause for initialized object &!",
2427 Nod, U_Ent);
2428 Error_Msg_N
2429 ("\address cannot depend on component" &
2430 " of discriminated record ('R'M 13.1(22))!",
2431 Nod);
2432 else
2433 Check_At_Constant_Address (Prefix (Nod));
2434 end if;
2435 end;
2437 elsif Nkind (Nod) = N_Indexed_Component then
2438 Check_At_Constant_Address (Prefix (Nod));
2439 Check_List_Constants (Expressions (Nod));
2441 else
2442 Check_Expr_Constants (Nod);
2443 end if;
2444 end Check_At_Constant_Address;
2446 --------------------------
2447 -- Check_Expr_Constants --
2448 --------------------------
2450 procedure Check_Expr_Constants (Nod : Node_Id) is
2451 Loc_U_Ent : constant Source_Ptr := Sloc (U_Ent);
2452 Ent : Entity_Id := Empty;
2454 begin
2455 if Nkind (Nod) in N_Has_Etype
2456 and then Etype (Nod) = Any_Type
2457 then
2458 return;
2459 end if;
2461 case Nkind (Nod) is
2462 when N_Empty | N_Error =>
2463 return;
2465 when N_Identifier | N_Expanded_Name =>
2466 Ent := Entity (Nod);
2468 -- We need to look at the original node if it is different
2469 -- from the node, since we may have rewritten things and
2470 -- substituted an identifier representing the rewrite.
2472 if Original_Node (Nod) /= Nod then
2473 Check_Expr_Constants (Original_Node (Nod));
2475 -- If the node is an object declaration without initial
2476 -- value, some code has been expanded, and the expression
2477 -- is not constant, even if the constituents might be
2478 -- acceptable, as in A'Address + offset.
2480 if Ekind (Ent) = E_Variable
2481 and then Nkind (Declaration_Node (Ent))
2482 = N_Object_Declaration
2483 and then
2484 No (Expression (Declaration_Node (Ent)))
2485 then
2486 Error_Msg_NE
2487 ("invalid address clause for initialized object &!",
2488 Nod, U_Ent);
2490 -- If entity is constant, it may be the result of expanding
2491 -- a check. We must verify that its declaration appears
2492 -- before the object in question, else we also reject the
2493 -- address clause.
2495 elsif Ekind (Ent) = E_Constant
2496 and then In_Same_Source_Unit (Ent, U_Ent)
2497 and then Sloc (Ent) > Loc_U_Ent
2498 then
2499 Error_Msg_NE
2500 ("invalid address clause for initialized object &!",
2501 Nod, U_Ent);
2502 end if;
2504 return;
2505 end if;
2507 -- Otherwise look at the identifier and see if it is OK
2509 if Ekind (Ent) = E_Named_Integer
2510 or else
2511 Ekind (Ent) = E_Named_Real
2512 or else
2513 Is_Type (Ent)
2514 then
2515 return;
2517 elsif
2518 Ekind (Ent) = E_Constant
2519 or else
2520 Ekind (Ent) = E_In_Parameter
2521 then
2522 -- This is the case where we must have Ent defined
2523 -- before U_Ent. Clearly if they are in different
2524 -- units this requirement is met since the unit
2525 -- containing Ent is already processed.
2527 if not In_Same_Source_Unit (Ent, U_Ent) then
2528 return;
2530 -- Otherwise location of Ent must be before the
2531 -- location of U_Ent, that's what prior defined means.
2533 elsif Sloc (Ent) < Loc_U_Ent then
2534 return;
2536 else
2537 Error_Msg_NE
2538 ("invalid address clause for initialized object &!",
2539 Nod, U_Ent);
2540 Error_Msg_Name_1 := Chars (Ent);
2541 Error_Msg_Name_2 := Chars (U_Ent);
2542 Error_Msg_N
2543 ("\% must be defined before % ('R'M 13.1(22))!",
2544 Nod);
2545 end if;
2547 elsif Nkind (Original_Node (Nod)) = N_Function_Call then
2548 Check_Expr_Constants (Original_Node (Nod));
2550 else
2551 Error_Msg_NE
2552 ("invalid address clause for initialized object &!",
2553 Nod, U_Ent);
2555 if Comes_From_Source (Ent) then
2556 Error_Msg_Name_1 := Chars (Ent);
2557 Error_Msg_N
2558 ("\reference to variable% not allowed"
2559 & " ('R'M 13.1(22))!", Nod);
2560 else
2561 Error_Msg_N
2562 ("non-static expression not allowed"
2563 & " ('R'M 13.1(22))!", Nod);
2564 end if;
2565 end if;
2567 when N_Integer_Literal =>
2569 -- If this is a rewritten unchecked conversion, in a system
2570 -- where Address is an integer type, always use the base type
2571 -- for a literal value. This is user-friendly and prevents
2572 -- order-of-elaboration issues with instances of unchecked
2573 -- conversion.
2575 if Nkind (Original_Node (Nod)) = N_Function_Call then
2576 Set_Etype (Nod, Base_Type (Etype (Nod)));
2577 end if;
2579 when N_Real_Literal |
2580 N_String_Literal |
2581 N_Character_Literal =>
2582 return;
2584 when N_Range =>
2585 Check_Expr_Constants (Low_Bound (Nod));
2586 Check_Expr_Constants (High_Bound (Nod));
2588 when N_Explicit_Dereference =>
2589 Check_Expr_Constants (Prefix (Nod));
2591 when N_Indexed_Component =>
2592 Check_Expr_Constants (Prefix (Nod));
2593 Check_List_Constants (Expressions (Nod));
2595 when N_Slice =>
2596 Check_Expr_Constants (Prefix (Nod));
2597 Check_Expr_Constants (Discrete_Range (Nod));
2599 when N_Selected_Component =>
2600 Check_Expr_Constants (Prefix (Nod));
2602 when N_Attribute_Reference =>
2603 if Attribute_Name (Nod) = Name_Address
2604 or else
2605 Attribute_Name (Nod) = Name_Access
2606 or else
2607 Attribute_Name (Nod) = Name_Unchecked_Access
2608 or else
2609 Attribute_Name (Nod) = Name_Unrestricted_Access
2610 then
2611 Check_At_Constant_Address (Prefix (Nod));
2613 else
2614 Check_Expr_Constants (Prefix (Nod));
2615 Check_List_Constants (Expressions (Nod));
2616 end if;
2618 when N_Aggregate =>
2619 Check_List_Constants (Component_Associations (Nod));
2620 Check_List_Constants (Expressions (Nod));
2622 when N_Component_Association =>
2623 Check_Expr_Constants (Expression (Nod));
2625 when N_Extension_Aggregate =>
2626 Check_Expr_Constants (Ancestor_Part (Nod));
2627 Check_List_Constants (Component_Associations (Nod));
2628 Check_List_Constants (Expressions (Nod));
2630 when N_Null =>
2631 return;
2633 when N_Binary_Op | N_And_Then | N_Or_Else | N_In | N_Not_In =>
2634 Check_Expr_Constants (Left_Opnd (Nod));
2635 Check_Expr_Constants (Right_Opnd (Nod));
2637 when N_Unary_Op =>
2638 Check_Expr_Constants (Right_Opnd (Nod));
2640 when N_Type_Conversion |
2641 N_Qualified_Expression |
2642 N_Allocator =>
2643 Check_Expr_Constants (Expression (Nod));
2645 when N_Unchecked_Type_Conversion =>
2646 Check_Expr_Constants (Expression (Nod));
2648 -- If this is a rewritten unchecked conversion, subtypes
2649 -- in this node are those created within the instance.
2650 -- To avoid order of elaboration issues, replace them
2651 -- with their base types. Note that address clauses can
2652 -- cause order of elaboration problems because they are
2653 -- elaborated by the back-end at the point of definition,
2654 -- and may mention entities declared in between (as long
2655 -- as everything is static). It is user-friendly to allow
2656 -- unchecked conversions in this context.
2658 if Nkind (Original_Node (Nod)) = N_Function_Call then
2659 Set_Etype (Expression (Nod),
2660 Base_Type (Etype (Expression (Nod))));
2661 Set_Etype (Nod, Base_Type (Etype (Nod)));
2662 end if;
2664 when N_Function_Call =>
2665 if not Is_Pure (Entity (Name (Nod))) then
2666 Error_Msg_NE
2667 ("invalid address clause for initialized object &!",
2668 Nod, U_Ent);
2670 Error_Msg_NE
2671 ("\function & is not pure ('R'M 13.1(22))!",
2672 Nod, Entity (Name (Nod)));
2674 else
2675 Check_List_Constants (Parameter_Associations (Nod));
2676 end if;
2678 when N_Parameter_Association =>
2679 Check_Expr_Constants (Explicit_Actual_Parameter (Nod));
2681 when others =>
2682 Error_Msg_NE
2683 ("invalid address clause for initialized object &!",
2684 Nod, U_Ent);
2685 Error_Msg_NE
2686 ("\must be constant defined before& ('R'M 13.1(22))!",
2687 Nod, U_Ent);
2688 end case;
2689 end Check_Expr_Constants;
2691 --------------------------
2692 -- Check_List_Constants --
2693 --------------------------
2695 procedure Check_List_Constants (Lst : List_Id) is
2696 Nod1 : Node_Id;
2698 begin
2699 if Present (Lst) then
2700 Nod1 := First (Lst);
2701 while Present (Nod1) loop
2702 Check_Expr_Constants (Nod1);
2703 Next (Nod1);
2704 end loop;
2705 end if;
2706 end Check_List_Constants;
2708 -- Start of processing for Check_Constant_Address_Clause
2710 begin
2711 Check_Expr_Constants (Expr);
2712 end Check_Constant_Address_Clause;
2714 ----------------
2715 -- Check_Size --
2716 ----------------
2718 procedure Check_Size
2719 (N : Node_Id;
2720 T : Entity_Id;
2721 Siz : Uint;
2722 Biased : out Boolean)
2724 UT : constant Entity_Id := Underlying_Type (T);
2725 M : Uint;
2727 begin
2728 Biased := False;
2730 -- Dismiss cases for generic types or types with previous errors
2732 if No (UT)
2733 or else UT = Any_Type
2734 or else Is_Generic_Type (UT)
2735 or else Is_Generic_Type (Root_Type (UT))
2736 then
2737 return;
2739 -- Check case of bit packed array
2741 elsif Is_Array_Type (UT)
2742 and then Known_Static_Component_Size (UT)
2743 and then Is_Bit_Packed_Array (UT)
2744 then
2745 declare
2746 Asiz : Uint;
2747 Indx : Node_Id;
2748 Ityp : Entity_Id;
2750 begin
2751 Asiz := Component_Size (UT);
2752 Indx := First_Index (UT);
2753 loop
2754 Ityp := Etype (Indx);
2756 -- If non-static bound, then we are not in the business of
2757 -- trying to check the length, and indeed an error will be
2758 -- issued elsewhere, since sizes of non-static array types
2759 -- cannot be set implicitly or explicitly.
2761 if not Is_Static_Subtype (Ityp) then
2762 return;
2763 end if;
2765 -- Otherwise accumulate next dimension
2767 Asiz := Asiz * (Expr_Value (Type_High_Bound (Ityp)) -
2768 Expr_Value (Type_Low_Bound (Ityp)) +
2769 Uint_1);
2771 Next_Index (Indx);
2772 exit when No (Indx);
2773 end loop;
2775 if Asiz <= Siz then
2776 return;
2777 else
2778 Error_Msg_Uint_1 := Asiz;
2779 Error_Msg_NE
2780 ("size for& too small, minimum allowed is ^", N, T);
2781 Set_Esize (T, Asiz);
2782 Set_RM_Size (T, Asiz);
2783 end if;
2784 end;
2786 -- All other composite types are ignored
2788 elsif Is_Composite_Type (UT) then
2789 return;
2791 -- For fixed-point types, don't check minimum if type is not frozen,
2792 -- since we don't know all the characteristics of the type that can
2793 -- affect the size (e.g. a specified small) till freeze time.
2795 elsif Is_Fixed_Point_Type (UT)
2796 and then not Is_Frozen (UT)
2797 then
2798 null;
2800 -- Cases for which a minimum check is required
2802 else
2803 -- Ignore if specified size is correct for the type
2805 if Known_Esize (UT) and then Siz = Esize (UT) then
2806 return;
2807 end if;
2809 -- Otherwise get minimum size
2811 M := UI_From_Int (Minimum_Size (UT));
2813 if Siz < M then
2815 -- Size is less than minimum size, but one possibility remains
2816 -- that we can manage with the new size if we bias the type
2818 M := UI_From_Int (Minimum_Size (UT, Biased => True));
2820 if Siz < M then
2821 Error_Msg_Uint_1 := M;
2822 Error_Msg_NE
2823 ("size for& too small, minimum allowed is ^", N, T);
2824 Set_Esize (T, M);
2825 Set_RM_Size (T, M);
2826 else
2827 Biased := True;
2828 end if;
2829 end if;
2830 end if;
2831 end Check_Size;
2833 -------------------------
2834 -- Get_Alignment_Value --
2835 -------------------------
2837 function Get_Alignment_Value (Expr : Node_Id) return Uint is
2838 Align : constant Uint := Static_Integer (Expr);
2840 begin
2841 if Align = No_Uint then
2842 return No_Uint;
2844 elsif Align <= 0 then
2845 Error_Msg_N ("alignment value must be positive", Expr);
2846 return No_Uint;
2848 else
2849 for J in Int range 0 .. 64 loop
2850 declare
2851 M : constant Uint := Uint_2 ** J;
2853 begin
2854 exit when M = Align;
2856 if M > Align then
2857 Error_Msg_N
2858 ("alignment value must be power of 2", Expr);
2859 return No_Uint;
2860 end if;
2861 end;
2862 end loop;
2864 return Align;
2865 end if;
2866 end Get_Alignment_Value;
2868 ----------------
2869 -- Initialize --
2870 ----------------
2872 procedure Initialize is
2873 begin
2874 Unchecked_Conversions.Init;
2875 end Initialize;
2877 -------------------------
2878 -- Is_Operational_Item --
2879 -------------------------
2881 function Is_Operational_Item (N : Node_Id) return Boolean is
2882 begin
2883 if Nkind (N) /= N_Attribute_Definition_Clause then
2884 return False;
2885 else
2886 declare
2887 Id : constant Attribute_Id := Get_Attribute_Id (Chars (N));
2889 begin
2890 return Id = Attribute_Input
2891 or else Id = Attribute_Output
2892 or else Id = Attribute_Read
2893 or else Id = Attribute_Write
2894 or else Id = Attribute_External_Tag;
2895 end;
2896 end if;
2897 end Is_Operational_Item;
2899 --------------------------------------
2900 -- Mark_Aliased_Address_As_Volatile --
2901 --------------------------------------
2903 procedure Mark_Aliased_Address_As_Volatile (N : Node_Id) is
2904 Ent : constant Entity_Id := Address_Aliased_Entity (N);
2906 begin
2907 if Present (Ent) then
2908 Set_Treat_As_Volatile (Ent);
2909 end if;
2910 end Mark_Aliased_Address_As_Volatile;
2912 ------------------
2913 -- Minimum_Size --
2914 ------------------
2916 function Minimum_Size
2917 (T : Entity_Id;
2918 Biased : Boolean := False) return Nat
2920 Lo : Uint := No_Uint;
2921 Hi : Uint := No_Uint;
2922 LoR : Ureal := No_Ureal;
2923 HiR : Ureal := No_Ureal;
2924 LoSet : Boolean := False;
2925 HiSet : Boolean := False;
2926 B : Uint;
2927 S : Nat;
2928 Ancest : Entity_Id;
2929 R_Typ : constant Entity_Id := Root_Type (T);
2931 begin
2932 -- If bad type, return 0
2934 if T = Any_Type then
2935 return 0;
2937 -- For generic types, just return zero. There cannot be any legitimate
2938 -- need to know such a size, but this routine may be called with a
2939 -- generic type as part of normal processing.
2941 elsif Is_Generic_Type (R_Typ)
2942 or else R_Typ = Any_Type
2943 then
2944 return 0;
2946 -- Access types. Normally an access type cannot have a size smaller
2947 -- than the size of System.Address. The exception is on VMS, where
2948 -- we have short and long addresses, and it is possible for an access
2949 -- type to have a short address size (and thus be less than the size
2950 -- of System.Address itself). We simply skip the check for VMS, and
2951 -- leave the back end to do the check.
2953 elsif Is_Access_Type (T) then
2954 if OpenVMS_On_Target then
2955 return 0;
2956 else
2957 return System_Address_Size;
2958 end if;
2960 -- Floating-point types
2962 elsif Is_Floating_Point_Type (T) then
2963 return UI_To_Int (Esize (R_Typ));
2965 -- Discrete types
2967 elsif Is_Discrete_Type (T) then
2969 -- The following loop is looking for the nearest compile time
2970 -- known bounds following the ancestor subtype chain. The idea
2971 -- is to find the most restrictive known bounds information.
2973 Ancest := T;
2974 loop
2975 if Ancest = Any_Type or else Etype (Ancest) = Any_Type then
2976 return 0;
2977 end if;
2979 if not LoSet then
2980 if Compile_Time_Known_Value (Type_Low_Bound (Ancest)) then
2981 Lo := Expr_Rep_Value (Type_Low_Bound (Ancest));
2982 LoSet := True;
2983 exit when HiSet;
2984 end if;
2985 end if;
2987 if not HiSet then
2988 if Compile_Time_Known_Value (Type_High_Bound (Ancest)) then
2989 Hi := Expr_Rep_Value (Type_High_Bound (Ancest));
2990 HiSet := True;
2991 exit when LoSet;
2992 end if;
2993 end if;
2995 Ancest := Ancestor_Subtype (Ancest);
2997 if No (Ancest) then
2998 Ancest := Base_Type (T);
3000 if Is_Generic_Type (Ancest) then
3001 return 0;
3002 end if;
3003 end if;
3004 end loop;
3006 -- Fixed-point types. We can't simply use Expr_Value to get the
3007 -- Corresponding_Integer_Value values of the bounds, since these
3008 -- do not get set till the type is frozen, and this routine can
3009 -- be called before the type is frozen. Similarly the test for
3010 -- bounds being static needs to include the case where we have
3011 -- unanalyzed real literals for the same reason.
3013 elsif Is_Fixed_Point_Type (T) then
3015 -- The following loop is looking for the nearest compile time
3016 -- known bounds following the ancestor subtype chain. The idea
3017 -- is to find the most restrictive known bounds information.
3019 Ancest := T;
3020 loop
3021 if Ancest = Any_Type or else Etype (Ancest) = Any_Type then
3022 return 0;
3023 end if;
3025 if not LoSet then
3026 if Nkind (Type_Low_Bound (Ancest)) = N_Real_Literal
3027 or else Compile_Time_Known_Value (Type_Low_Bound (Ancest))
3028 then
3029 LoR := Expr_Value_R (Type_Low_Bound (Ancest));
3030 LoSet := True;
3031 exit when HiSet;
3032 end if;
3033 end if;
3035 if not HiSet then
3036 if Nkind (Type_High_Bound (Ancest)) = N_Real_Literal
3037 or else Compile_Time_Known_Value (Type_High_Bound (Ancest))
3038 then
3039 HiR := Expr_Value_R (Type_High_Bound (Ancest));
3040 HiSet := True;
3041 exit when LoSet;
3042 end if;
3043 end if;
3045 Ancest := Ancestor_Subtype (Ancest);
3047 if No (Ancest) then
3048 Ancest := Base_Type (T);
3050 if Is_Generic_Type (Ancest) then
3051 return 0;
3052 end if;
3053 end if;
3054 end loop;
3056 Lo := UR_To_Uint (LoR / Small_Value (T));
3057 Hi := UR_To_Uint (HiR / Small_Value (T));
3059 -- No other types allowed
3061 else
3062 raise Program_Error;
3063 end if;
3065 -- Fall through with Hi and Lo set. Deal with biased case
3067 if (Biased and then not Is_Fixed_Point_Type (T))
3068 or else Has_Biased_Representation (T)
3069 then
3070 Hi := Hi - Lo;
3071 Lo := Uint_0;
3072 end if;
3074 -- Signed case. Note that we consider types like range 1 .. -1 to be
3075 -- signed for the purpose of computing the size, since the bounds
3076 -- have to be accomodated in the base type.
3078 if Lo < 0 or else Hi < 0 then
3079 S := 1;
3080 B := Uint_1;
3082 -- S = size, B = 2 ** (size - 1) (can accommodate -B .. +(B - 1))
3083 -- Note that we accommodate the case where the bounds cross. This
3084 -- can happen either because of the way the bounds are declared
3085 -- or because of the algorithm in Freeze_Fixed_Point_Type.
3087 while Lo < -B
3088 or else Hi < -B
3089 or else Lo >= B
3090 or else Hi >= B
3091 loop
3092 B := Uint_2 ** S;
3093 S := S + 1;
3094 end loop;
3096 -- Unsigned case
3098 else
3099 -- If both bounds are positive, make sure that both are represen-
3100 -- table in the case where the bounds are crossed. This can happen
3101 -- either because of the way the bounds are declared, or because of
3102 -- the algorithm in Freeze_Fixed_Point_Type.
3104 if Lo > Hi then
3105 Hi := Lo;
3106 end if;
3108 -- S = size, (can accommodate 0 .. (2**size - 1))
3110 S := 0;
3111 while Hi >= Uint_2 ** S loop
3112 S := S + 1;
3113 end loop;
3114 end if;
3116 return S;
3117 end Minimum_Size;
3119 -------------------------
3120 -- New_Stream_Function --
3121 -------------------------
3123 procedure New_Stream_Function
3124 (N : Node_Id;
3125 Ent : Entity_Id;
3126 Subp : Entity_Id;
3127 Nam : TSS_Name_Type)
3129 Loc : constant Source_Ptr := Sloc (N);
3130 Sname : constant Name_Id := Make_TSS_Name (Base_Type (Ent), Nam);
3131 Subp_Id : Entity_Id;
3132 Subp_Decl : Node_Id;
3133 F : Entity_Id;
3134 Etyp : Entity_Id;
3136 function Build_Spec return Node_Id;
3137 -- Used for declaration and renaming declaration, so that this is
3138 -- treated as a renaming_as_body.
3140 ----------------
3141 -- Build_Spec --
3142 ----------------
3144 function Build_Spec return Node_Id is
3145 begin
3146 Subp_Id := Make_Defining_Identifier (Loc, Sname);
3148 return
3149 Make_Function_Specification (Loc,
3150 Defining_Unit_Name => Subp_Id,
3151 Parameter_Specifications =>
3152 New_List (
3153 Make_Parameter_Specification (Loc,
3154 Defining_Identifier =>
3155 Make_Defining_Identifier (Loc, Name_S),
3156 Parameter_Type =>
3157 Make_Access_Definition (Loc,
3158 Subtype_Mark =>
3159 New_Reference_To (
3160 Designated_Type (Etype (F)), Loc)))),
3162 Result_Definition =>
3163 New_Reference_To (Etyp, Loc));
3164 end Build_Spec;
3166 -- Start of processing for New_Stream_Function
3168 begin
3169 F := First_Formal (Subp);
3170 Etyp := Etype (Subp);
3172 if not Is_Tagged_Type (Ent) then
3173 Subp_Decl :=
3174 Make_Subprogram_Declaration (Loc,
3175 Specification => Build_Spec);
3176 Insert_Action (N, Subp_Decl);
3177 end if;
3179 Subp_Decl :=
3180 Make_Subprogram_Renaming_Declaration (Loc,
3181 Specification => Build_Spec,
3182 Name => New_Reference_To (Subp, Loc));
3184 if Is_Tagged_Type (Ent) then
3185 Set_TSS (Base_Type (Ent), Subp_Id);
3186 else
3187 Insert_Action (N, Subp_Decl);
3188 Copy_TSS (Subp_Id, Base_Type (Ent));
3189 end if;
3190 end New_Stream_Function;
3192 --------------------------
3193 -- New_Stream_Procedure --
3194 --------------------------
3196 procedure New_Stream_Procedure
3197 (N : Node_Id;
3198 Ent : Entity_Id;
3199 Subp : Entity_Id;
3200 Nam : TSS_Name_Type;
3201 Out_P : Boolean := False)
3203 Loc : constant Source_Ptr := Sloc (N);
3204 Sname : constant Name_Id := Make_TSS_Name (Base_Type (Ent), Nam);
3205 Subp_Id : Entity_Id;
3206 Subp_Decl : Node_Id;
3207 F : Entity_Id;
3208 Etyp : Entity_Id;
3210 function Build_Spec return Node_Id;
3211 -- Used for declaration and renaming declaration, so that this is
3212 -- treated as a renaming_as_body.
3214 ----------------
3215 -- Build_Spec --
3216 ----------------
3218 function Build_Spec return Node_Id is
3219 begin
3220 Subp_Id := Make_Defining_Identifier (Loc, Sname);
3222 return
3223 Make_Procedure_Specification (Loc,
3224 Defining_Unit_Name => Subp_Id,
3225 Parameter_Specifications =>
3226 New_List (
3227 Make_Parameter_Specification (Loc,
3228 Defining_Identifier =>
3229 Make_Defining_Identifier (Loc, Name_S),
3230 Parameter_Type =>
3231 Make_Access_Definition (Loc,
3232 Subtype_Mark =>
3233 New_Reference_To (
3234 Designated_Type (Etype (F)), Loc))),
3236 Make_Parameter_Specification (Loc,
3237 Defining_Identifier =>
3238 Make_Defining_Identifier (Loc, Name_V),
3239 Out_Present => Out_P,
3240 Parameter_Type =>
3241 New_Reference_To (Etyp, Loc))));
3242 end Build_Spec;
3244 -- Start of processing for New_Stream_Procedure
3246 begin
3247 F := First_Formal (Subp);
3248 Etyp := Etype (Next_Formal (F));
3250 if not Is_Tagged_Type (Ent) then
3251 Subp_Decl :=
3252 Make_Subprogram_Declaration (Loc,
3253 Specification => Build_Spec);
3254 Insert_Action (N, Subp_Decl);
3255 end if;
3257 Subp_Decl :=
3258 Make_Subprogram_Renaming_Declaration (Loc,
3259 Specification => Build_Spec,
3260 Name => New_Reference_To (Subp, Loc));
3262 if Is_Tagged_Type (Ent) then
3263 Set_TSS (Base_Type (Ent), Subp_Id);
3264 else
3265 Insert_Action (N, Subp_Decl);
3266 Copy_TSS (Subp_Id, Base_Type (Ent));
3267 end if;
3268 end New_Stream_Procedure;
3270 ------------------------
3271 -- Rep_Item_Too_Early --
3272 ------------------------
3274 function Rep_Item_Too_Early (T : Entity_Id; N : Node_Id) return Boolean is
3275 begin
3276 -- Cannot apply rep items that are not operational items
3277 -- to generic types
3279 if Is_Operational_Item (N) then
3280 return False;
3282 elsif Is_Type (T)
3283 and then Is_Generic_Type (Root_Type (T))
3284 then
3285 Error_Msg_N
3286 ("representation item not allowed for generic type", N);
3287 return True;
3288 end if;
3290 -- Otherwise check for incompleted type
3292 if Is_Incomplete_Or_Private_Type (T)
3293 and then No (Underlying_Type (T))
3294 then
3295 Error_Msg_N
3296 ("representation item must be after full type declaration", N);
3297 return True;
3299 -- If the type has incompleted components, a representation clause is
3300 -- illegal but stream attributes and Convention pragmas are correct.
3302 elsif Has_Private_Component (T) then
3303 if Nkind (N) = N_Pragma then
3304 return False;
3305 else
3306 Error_Msg_N
3307 ("representation item must appear after type is fully defined",
3309 return True;
3310 end if;
3311 else
3312 return False;
3313 end if;
3314 end Rep_Item_Too_Early;
3316 -----------------------
3317 -- Rep_Item_Too_Late --
3318 -----------------------
3320 function Rep_Item_Too_Late
3321 (T : Entity_Id;
3322 N : Node_Id;
3323 FOnly : Boolean := False) return Boolean
3325 S : Entity_Id;
3326 Parent_Type : Entity_Id;
3328 procedure Too_Late;
3329 -- Output the too late message. Note that this is not considered a
3330 -- serious error, since the effect is simply that we ignore the
3331 -- representation clause in this case.
3333 --------------
3334 -- Too_Late --
3335 --------------
3337 procedure Too_Late is
3338 begin
3339 Error_Msg_N ("|representation item appears too late!", N);
3340 end Too_Late;
3342 -- Start of processing for Rep_Item_Too_Late
3344 begin
3345 -- First make sure entity is not frozen (RM 13.1(9)). Exclude imported
3346 -- types, which may be frozen if they appear in a representation clause
3347 -- for a local type.
3349 if Is_Frozen (T)
3350 and then not From_With_Type (T)
3351 then
3352 Too_Late;
3353 S := First_Subtype (T);
3355 if Present (Freeze_Node (S)) then
3356 Error_Msg_NE
3357 ("?no more representation items for }", Freeze_Node (S), S);
3358 end if;
3360 return True;
3362 -- Check for case of non-tagged derived type whose parent either has
3363 -- primitive operations, or is a by reference type (RM 13.1(10)).
3365 elsif Is_Type (T)
3366 and then not FOnly
3367 and then Is_Derived_Type (T)
3368 and then not Is_Tagged_Type (T)
3369 then
3370 Parent_Type := Etype (Base_Type (T));
3372 if Has_Primitive_Operations (Parent_Type) then
3373 Too_Late;
3374 Error_Msg_NE
3375 ("primitive operations already defined for&!", N, Parent_Type);
3376 return True;
3378 elsif Is_By_Reference_Type (Parent_Type) then
3379 Too_Late;
3380 Error_Msg_NE
3381 ("parent type & is a by reference type!", N, Parent_Type);
3382 return True;
3383 end if;
3384 end if;
3386 -- No error, link item into head of chain of rep items for the entity
3388 Record_Rep_Item (T, N);
3389 return False;
3390 end Rep_Item_Too_Late;
3392 -------------------------
3393 -- Same_Representation --
3394 -------------------------
3396 function Same_Representation (Typ1, Typ2 : Entity_Id) return Boolean is
3397 T1 : constant Entity_Id := Underlying_Type (Typ1);
3398 T2 : constant Entity_Id := Underlying_Type (Typ2);
3400 begin
3401 -- A quick check, if base types are the same, then we definitely have
3402 -- the same representation, because the subtype specific representation
3403 -- attributes (Size and Alignment) do not affect representation from
3404 -- the point of view of this test.
3406 if Base_Type (T1) = Base_Type (T2) then
3407 return True;
3409 elsif Is_Private_Type (Base_Type (T2))
3410 and then Base_Type (T1) = Full_View (Base_Type (T2))
3411 then
3412 return True;
3413 end if;
3415 -- Tagged types never have differing representations
3417 if Is_Tagged_Type (T1) then
3418 return True;
3419 end if;
3421 -- Representations are definitely different if conventions differ
3423 if Convention (T1) /= Convention (T2) then
3424 return False;
3425 end if;
3427 -- Representations are different if component alignments differ
3429 if (Is_Record_Type (T1) or else Is_Array_Type (T1))
3430 and then
3431 (Is_Record_Type (T2) or else Is_Array_Type (T2))
3432 and then Component_Alignment (T1) /= Component_Alignment (T2)
3433 then
3434 return False;
3435 end if;
3437 -- For arrays, the only real issue is component size. If we know the
3438 -- component size for both arrays, and it is the same, then that's
3439 -- good enough to know we don't have a change of representation.
3441 if Is_Array_Type (T1) then
3442 if Known_Component_Size (T1)
3443 and then Known_Component_Size (T2)
3444 and then Component_Size (T1) = Component_Size (T2)
3445 then
3446 return True;
3447 end if;
3448 end if;
3450 -- Types definitely have same representation if neither has non-standard
3451 -- representation since default representations are always consistent.
3452 -- If only one has non-standard representation, and the other does not,
3453 -- then we consider that they do not have the same representation. They
3454 -- might, but there is no way of telling early enough.
3456 if Has_Non_Standard_Rep (T1) then
3457 if not Has_Non_Standard_Rep (T2) then
3458 return False;
3459 end if;
3460 else
3461 return not Has_Non_Standard_Rep (T2);
3462 end if;
3464 -- Here the two types both have non-standard representation, and we
3465 -- need to determine if they have the same non-standard representation
3467 -- For arrays, we simply need to test if the component sizes are the
3468 -- same. Pragma Pack is reflected in modified component sizes, so this
3469 -- check also deals with pragma Pack.
3471 if Is_Array_Type (T1) then
3472 return Component_Size (T1) = Component_Size (T2);
3474 -- Tagged types always have the same representation, because it is not
3475 -- possible to specify different representations for common fields.
3477 elsif Is_Tagged_Type (T1) then
3478 return True;
3480 -- Case of record types
3482 elsif Is_Record_Type (T1) then
3484 -- Packed status must conform
3486 if Is_Packed (T1) /= Is_Packed (T2) then
3487 return False;
3489 -- Otherwise we must check components. Typ2 maybe a constrained
3490 -- subtype with fewer components, so we compare the components
3491 -- of the base types.
3493 else
3494 Record_Case : declare
3495 CD1, CD2 : Entity_Id;
3497 function Same_Rep return Boolean;
3498 -- CD1 and CD2 are either components or discriminants. This
3499 -- function tests whether the two have the same representation
3501 --------------
3502 -- Same_Rep --
3503 --------------
3505 function Same_Rep return Boolean is
3506 begin
3507 if No (Component_Clause (CD1)) then
3508 return No (Component_Clause (CD2));
3510 else
3511 return
3512 Present (Component_Clause (CD2))
3513 and then
3514 Component_Bit_Offset (CD1) = Component_Bit_Offset (CD2)
3515 and then
3516 Esize (CD1) = Esize (CD2);
3517 end if;
3518 end Same_Rep;
3520 -- Start processing for Record_Case
3522 begin
3523 if Has_Discriminants (T1) then
3524 CD1 := First_Discriminant (T1);
3525 CD2 := First_Discriminant (T2);
3527 -- The number of discriminants may be different if the
3528 -- derived type has fewer (constrained by values). The
3529 -- invisible discriminants retain the representation of
3530 -- the original, so the discrepancy does not per se
3531 -- indicate a different representation.
3533 while Present (CD1)
3534 and then Present (CD2)
3535 loop
3536 if not Same_Rep then
3537 return False;
3538 else
3539 Next_Discriminant (CD1);
3540 Next_Discriminant (CD2);
3541 end if;
3542 end loop;
3543 end if;
3545 CD1 := First_Component (Underlying_Type (Base_Type (T1)));
3546 CD2 := First_Component (Underlying_Type (Base_Type (T2)));
3548 while Present (CD1) loop
3549 if not Same_Rep then
3550 return False;
3551 else
3552 Next_Component (CD1);
3553 Next_Component (CD2);
3554 end if;
3555 end loop;
3557 return True;
3558 end Record_Case;
3559 end if;
3561 -- For enumeration types, we must check each literal to see if the
3562 -- representation is the same. Note that we do not permit enumeration
3563 -- reprsentation clauses for Character and Wide_Character, so these
3564 -- cases were already dealt with.
3566 elsif Is_Enumeration_Type (T1) then
3568 Enumeration_Case : declare
3569 L1, L2 : Entity_Id;
3571 begin
3572 L1 := First_Literal (T1);
3573 L2 := First_Literal (T2);
3575 while Present (L1) loop
3576 if Enumeration_Rep (L1) /= Enumeration_Rep (L2) then
3577 return False;
3578 else
3579 Next_Literal (L1);
3580 Next_Literal (L2);
3581 end if;
3582 end loop;
3584 return True;
3586 end Enumeration_Case;
3588 -- Any other types have the same representation for these purposes
3590 else
3591 return True;
3592 end if;
3593 end Same_Representation;
3595 --------------------
3596 -- Set_Enum_Esize --
3597 --------------------
3599 procedure Set_Enum_Esize (T : Entity_Id) is
3600 Lo : Uint;
3601 Hi : Uint;
3602 Sz : Nat;
3604 begin
3605 Init_Alignment (T);
3607 -- Find the minimum standard size (8,16,32,64) that fits
3609 Lo := Enumeration_Rep (Entity (Type_Low_Bound (T)));
3610 Hi := Enumeration_Rep (Entity (Type_High_Bound (T)));
3612 if Lo < 0 then
3613 if Lo >= -Uint_2**07 and then Hi < Uint_2**07 then
3614 Sz := Standard_Character_Size; -- May be > 8 on some targets
3616 elsif Lo >= -Uint_2**15 and then Hi < Uint_2**15 then
3617 Sz := 16;
3619 elsif Lo >= -Uint_2**31 and then Hi < Uint_2**31 then
3620 Sz := 32;
3622 else pragma Assert (Lo >= -Uint_2**63 and then Hi < Uint_2**63);
3623 Sz := 64;
3624 end if;
3626 else
3627 if Hi < Uint_2**08 then
3628 Sz := Standard_Character_Size; -- May be > 8 on some targets
3630 elsif Hi < Uint_2**16 then
3631 Sz := 16;
3633 elsif Hi < Uint_2**32 then
3634 Sz := 32;
3636 else pragma Assert (Hi < Uint_2**63);
3637 Sz := 64;
3638 end if;
3639 end if;
3641 -- That minimum is the proper size unless we have a foreign convention
3642 -- and the size required is 32 or less, in which case we bump the size
3643 -- up to 32. This is required for C and C++ and seems reasonable for
3644 -- all other foreign conventions.
3646 if Has_Foreign_Convention (T)
3647 and then Esize (T) < Standard_Integer_Size
3648 then
3649 Init_Esize (T, Standard_Integer_Size);
3651 else
3652 Init_Esize (T, Sz);
3653 end if;
3654 end Set_Enum_Esize;
3656 -----------------------------------
3657 -- Validate_Unchecked_Conversion --
3658 -----------------------------------
3660 procedure Validate_Unchecked_Conversion
3661 (N : Node_Id;
3662 Act_Unit : Entity_Id)
3664 Source : Entity_Id;
3665 Target : Entity_Id;
3666 Vnode : Node_Id;
3668 begin
3669 -- Obtain source and target types. Note that we call Ancestor_Subtype
3670 -- here because the processing for generic instantiation always makes
3671 -- subtypes, and we want the original frozen actual types.
3673 -- If we are dealing with private types, then do the check on their
3674 -- fully declared counterparts if the full declarations have been
3675 -- encountered (they don't have to be visible, but they must exist!)
3677 Source := Ancestor_Subtype (Etype (First_Formal (Act_Unit)));
3679 if Is_Private_Type (Source)
3680 and then Present (Underlying_Type (Source))
3681 then
3682 Source := Underlying_Type (Source);
3683 end if;
3685 Target := Ancestor_Subtype (Etype (Act_Unit));
3687 -- If either type is generic, the instantiation happens within a
3688 -- generic unit, and there is nothing to check. The proper check
3689 -- will happen when the enclosing generic is instantiated.
3691 if Is_Generic_Type (Source) or else Is_Generic_Type (Target) then
3692 return;
3693 end if;
3695 if Is_Private_Type (Target)
3696 and then Present (Underlying_Type (Target))
3697 then
3698 Target := Underlying_Type (Target);
3699 end if;
3701 -- Source may be unconstrained array, but not target
3703 if Is_Array_Type (Target)
3704 and then not Is_Constrained (Target)
3705 then
3706 Error_Msg_N
3707 ("unchecked conversion to unconstrained array not allowed", N);
3708 return;
3709 end if;
3711 -- Make entry in unchecked conversion table for later processing
3712 -- by Validate_Unchecked_Conversions, which will check sizes and
3713 -- alignments (using values set by the back-end where possible).
3714 -- This is only done if the appropriate warning is active
3716 if Warn_On_Unchecked_Conversion then
3717 Unchecked_Conversions.Append
3718 (New_Val => UC_Entry'
3719 (Enode => N,
3720 Source => Source,
3721 Target => Target));
3723 -- If both sizes are known statically now, then back end annotation
3724 -- is not required to do a proper check but if either size is not
3725 -- known statically, then we need the annotation.
3727 if Known_Static_RM_Size (Source)
3728 and then Known_Static_RM_Size (Target)
3729 then
3730 null;
3731 else
3732 Back_Annotate_Rep_Info := True;
3733 end if;
3734 end if;
3736 -- If unchecked conversion to access type, and access type is
3737 -- declared in the same unit as the unchecked conversion, then
3738 -- set the No_Strict_Aliasing flag (no strict aliasing is
3739 -- implicit in this situation).
3741 if Is_Access_Type (Target) and then
3742 In_Same_Source_Unit (Target, N)
3743 then
3744 Set_No_Strict_Aliasing (Implementation_Base_Type (Target));
3745 end if;
3747 -- Generate N_Validate_Unchecked_Conversion node for back end in
3748 -- case the back end needs to perform special validation checks.
3750 -- Shouldn't this be in exp_ch13, since the check only gets done
3751 -- if we have full expansion and the back end is called ???
3753 Vnode :=
3754 Make_Validate_Unchecked_Conversion (Sloc (N));
3755 Set_Source_Type (Vnode, Source);
3756 Set_Target_Type (Vnode, Target);
3758 -- If the unchecked conversion node is in a list, just insert before
3759 -- it. If not we have some strange case, not worth bothering about.
3761 if Is_List_Member (N) then
3762 Insert_After (N, Vnode);
3763 end if;
3764 end Validate_Unchecked_Conversion;
3766 ------------------------------------
3767 -- Validate_Unchecked_Conversions --
3768 ------------------------------------
3770 procedure Validate_Unchecked_Conversions is
3771 begin
3772 for N in Unchecked_Conversions.First .. Unchecked_Conversions.Last loop
3773 declare
3774 T : UC_Entry renames Unchecked_Conversions.Table (N);
3776 Enode : constant Node_Id := T.Enode;
3777 Source : constant Entity_Id := T.Source;
3778 Target : constant Entity_Id := T.Target;
3780 Source_Siz : Uint;
3781 Target_Siz : Uint;
3783 begin
3784 -- This validation check, which warns if we have unequal sizes
3785 -- for unchecked conversion, and thus potentially implementation
3786 -- dependent semantics, is one of the few occasions on which we
3787 -- use the official RM size instead of Esize. See description
3788 -- in Einfo "Handling of Type'Size Values" for details.
3790 if Serious_Errors_Detected = 0
3791 and then Known_Static_RM_Size (Source)
3792 and then Known_Static_RM_Size (Target)
3793 then
3794 Source_Siz := RM_Size (Source);
3795 Target_Siz := RM_Size (Target);
3797 if Source_Siz /= Target_Siz then
3798 Error_Msg_N
3799 ("types for unchecked conversion have different sizes?",
3800 Enode);
3802 if All_Errors_Mode then
3803 Error_Msg_Name_1 := Chars (Source);
3804 Error_Msg_Uint_1 := Source_Siz;
3805 Error_Msg_Name_2 := Chars (Target);
3806 Error_Msg_Uint_2 := Target_Siz;
3807 Error_Msg_N
3808 ("\size of % is ^, size of % is ^?", Enode);
3810 Error_Msg_Uint_1 := UI_Abs (Source_Siz - Target_Siz);
3812 if Is_Discrete_Type (Source)
3813 and then Is_Discrete_Type (Target)
3814 then
3815 if Source_Siz > Target_Siz then
3816 Error_Msg_N
3817 ("\^ high order bits of source will be ignored?",
3818 Enode);
3820 elsif Is_Unsigned_Type (Source) then
3821 Error_Msg_N
3822 ("\source will be extended with ^ high order " &
3823 "zero bits?", Enode);
3825 else
3826 Error_Msg_N
3827 ("\source will be extended with ^ high order " &
3828 "sign bits?",
3829 Enode);
3830 end if;
3832 elsif Source_Siz < Target_Siz then
3833 if Is_Discrete_Type (Target) then
3834 if Bytes_Big_Endian then
3835 Error_Msg_N
3836 ("\target value will include ^ undefined " &
3837 "low order bits?",
3838 Enode);
3839 else
3840 Error_Msg_N
3841 ("\target value will include ^ undefined " &
3842 "high order bits?",
3843 Enode);
3844 end if;
3846 else
3847 Error_Msg_N
3848 ("\^ trailing bits of target value will be " &
3849 "undefined?", Enode);
3850 end if;
3852 else pragma Assert (Source_Siz > Target_Siz);
3853 Error_Msg_N
3854 ("\^ trailing bits of source will be ignored?",
3855 Enode);
3856 end if;
3857 end if;
3858 end if;
3859 end if;
3861 -- If both types are access types, we need to check the alignment.
3862 -- If the alignment of both is specified, we can do it here.
3864 if Serious_Errors_Detected = 0
3865 and then Ekind (Source) in Access_Kind
3866 and then Ekind (Target) in Access_Kind
3867 and then Target_Strict_Alignment
3868 and then Present (Designated_Type (Source))
3869 and then Present (Designated_Type (Target))
3870 then
3871 declare
3872 D_Source : constant Entity_Id := Designated_Type (Source);
3873 D_Target : constant Entity_Id := Designated_Type (Target);
3875 begin
3876 if Known_Alignment (D_Source)
3877 and then Known_Alignment (D_Target)
3878 then
3879 declare
3880 Source_Align : constant Uint := Alignment (D_Source);
3881 Target_Align : constant Uint := Alignment (D_Target);
3883 begin
3884 if Source_Align < Target_Align
3885 and then not Is_Tagged_Type (D_Source)
3886 then
3887 Error_Msg_Uint_1 := Target_Align;
3888 Error_Msg_Uint_2 := Source_Align;
3889 Error_Msg_Node_2 := D_Source;
3890 Error_Msg_NE
3891 ("alignment of & (^) is stricter than " &
3892 "alignment of & (^)?", Enode, D_Target);
3894 if All_Errors_Mode then
3895 Error_Msg_N
3896 ("\resulting access value may have invalid " &
3897 "alignment?", Enode);
3898 end if;
3899 end if;
3900 end;
3901 end if;
3902 end;
3903 end if;
3904 end;
3905 end loop;
3906 end Validate_Unchecked_Conversions;
3908 end Sem_Ch13;