* c-common.c (get_priority): Add check for
[official-gcc.git] / gcc / ada / sem_ch13.adb
blob6a49bd565ca8c1b1479a6471f7a1d50cfd7b7aca
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 Sem_Warn; use Sem_Warn;
47 with Snames; use Snames;
48 with Stand; use Stand;
49 with Sinfo; use Sinfo;
50 with Table;
51 with Targparm; use Targparm;
52 with Ttypes; use Ttypes;
53 with Tbuild; use Tbuild;
54 with Urealp; use Urealp;
56 with GNAT.Heap_Sort_A; use GNAT.Heap_Sort_A;
58 package body Sem_Ch13 is
60 SSU : constant Pos := System_Storage_Unit;
61 -- Convenient short hand for commonly used constant
63 -----------------------
64 -- Local Subprograms --
65 -----------------------
67 procedure Alignment_Check_For_Esize_Change (Typ : Entity_Id);
68 -- This routine is called after setting the Esize of type entity Typ.
69 -- The purpose is to deal with the situation where an aligment has been
70 -- inherited from a derived type that is no longer appropriate for the
71 -- new Esize value. In this case, we reset the Alignment to unknown.
73 procedure Check_Component_Overlap (C1_Ent, C2_Ent : Entity_Id);
74 -- Given two entities for record components or discriminants, checks
75 -- if they hav overlapping component clauses and issues errors if so.
77 function Get_Alignment_Value (Expr : Node_Id) return Uint;
78 -- Given the expression for an alignment value, returns the corresponding
79 -- Uint value. If the value is inappropriate, then error messages are
80 -- posted as required, and a value of No_Uint is returned.
82 function Is_Operational_Item (N : Node_Id) return Boolean;
83 -- A specification for a stream attribute is allowed before the full
84 -- type is declared, as explained in AI-00137 and the corrigendum.
85 -- Attributes that do not specify a representation characteristic are
86 -- operational attributes.
88 function Address_Aliased_Entity (N : Node_Id) return Entity_Id;
89 -- If expression N is of the form E'Address, return E
91 procedure Mark_Aliased_Address_As_Volatile (N : Node_Id);
92 -- This is used for processing of an address representation clause. If
93 -- the expression N is of the form of K'Address, then the entity that
94 -- is associated with K is marked as volatile.
96 procedure New_Stream_Subprogram
97 (N : Node_Id;
98 Ent : Entity_Id;
99 Subp : Entity_Id;
100 Nam : TSS_Name_Type);
101 -- Create a subprogram renaming of a given stream attribute to the
102 -- designated subprogram and then in the tagged case, provide this as a
103 -- primitive operation, or in the non-tagged case make an appropriate TSS
104 -- entry. This is more properly an expansion activity than just semantics,
105 -- but the presence of user-defined stream functions for limited types is a
106 -- legality check, which is why this takes place here rather than in
107 -- exp_ch13, where it was previously. Nam indicates the name of the TSS
108 -- function to be generated.
110 -- To avoid elaboration anomalies with freeze nodes, for untagged types
111 -- we generate both a subprogram declaration and a subprogram renaming
112 -- declaration, so that the attribute specification is handled as a
113 -- renaming_as_body. For tagged types, the specification is one of the
114 -- primitive specs.
116 ----------------------------------------------
117 -- Table for Validate_Unchecked_Conversions --
118 ----------------------------------------------
120 -- The following table collects unchecked conversions for validation.
121 -- Entries are made by Validate_Unchecked_Conversion and then the
122 -- call to Validate_Unchecked_Conversions does the actual error
123 -- checking and posting of warnings. The reason for this delayed
124 -- processing is to take advantage of back-annotations of size and
125 -- alignment values peformed by the back end.
127 type UC_Entry is record
128 Enode : Node_Id; -- node used for posting warnings
129 Source : Entity_Id; -- source type for unchecked conversion
130 Target : Entity_Id; -- target type for unchecked conversion
131 end record;
133 package Unchecked_Conversions is new Table.Table (
134 Table_Component_Type => UC_Entry,
135 Table_Index_Type => Int,
136 Table_Low_Bound => 1,
137 Table_Initial => 50,
138 Table_Increment => 200,
139 Table_Name => "Unchecked_Conversions");
141 ----------------------------
142 -- Address_Aliased_Entity --
143 ----------------------------
145 function Address_Aliased_Entity (N : Node_Id) return Entity_Id is
146 begin
147 if Nkind (N) = N_Attribute_Reference
148 and then Attribute_Name (N) = Name_Address
149 then
150 declare
151 Nam : Node_Id := Prefix (N);
152 begin
153 while False
154 or else Nkind (Nam) = N_Selected_Component
155 or else Nkind (Nam) = N_Indexed_Component
156 loop
157 Nam := Prefix (Nam);
158 end loop;
160 if Is_Entity_Name (Nam) then
161 return Entity (Nam);
162 end if;
163 end;
164 end if;
166 return Empty;
167 end Address_Aliased_Entity;
169 --------------------------------------
170 -- Alignment_Check_For_Esize_Change --
171 --------------------------------------
173 procedure Alignment_Check_For_Esize_Change (Typ : Entity_Id) is
174 begin
175 -- If the alignment is known, and not set by a rep clause, and is
176 -- inconsistent with the size being set, then reset it to unknown,
177 -- we assume in this case that the size overrides the inherited
178 -- alignment, and that the alignment must be recomputed.
180 if Known_Alignment (Typ)
181 and then not Has_Alignment_Clause (Typ)
182 and then Esize (Typ) mod (Alignment (Typ) * SSU) /= 0
183 then
184 Init_Alignment (Typ);
185 end if;
186 end Alignment_Check_For_Esize_Change;
188 -----------------------
189 -- Analyze_At_Clause --
190 -----------------------
192 -- An at clause is replaced by the corresponding Address attribute
193 -- definition clause that is the preferred approach in Ada 95.
195 procedure Analyze_At_Clause (N : Node_Id) is
196 begin
197 Check_Restriction (No_Obsolescent_Features, N);
199 if Warn_On_Obsolescent_Feature then
200 Error_Msg_N
201 ("at clause is an obsolescent feature ('R'M 'J.7(2))?", N);
202 Error_Msg_N
203 ("\use address attribute definition clause instead?", N);
204 end if;
206 Rewrite (N,
207 Make_Attribute_Definition_Clause (Sloc (N),
208 Name => Identifier (N),
209 Chars => Name_Address,
210 Expression => Expression (N)));
211 Analyze_Attribute_Definition_Clause (N);
212 end Analyze_At_Clause;
214 -----------------------------------------
215 -- Analyze_Attribute_Definition_Clause --
216 -----------------------------------------
218 procedure Analyze_Attribute_Definition_Clause (N : Node_Id) is
219 Loc : constant Source_Ptr := Sloc (N);
220 Nam : constant Node_Id := Name (N);
221 Attr : constant Name_Id := Chars (N);
222 Expr : constant Node_Id := Expression (N);
223 Id : constant Attribute_Id := Get_Attribute_Id (Attr);
224 Ent : Entity_Id;
225 U_Ent : Entity_Id;
227 FOnly : Boolean := False;
228 -- Reset to True for subtype specific attribute (Alignment, Size)
229 -- and for stream attributes, i.e. those cases where in the call
230 -- to Rep_Item_Too_Late, FOnly is set True so that only the freezing
231 -- rules are checked. Note that the case of stream attributes is not
232 -- clear from the RM, but see AI95-00137. Also, the RM seems to
233 -- disallow Storage_Size for derived task types, but that is also
234 -- clearly unintentional.
236 procedure Analyze_Stream_TSS_Definition (TSS_Nam : TSS_Name_Type);
237 -- Common processing for 'Read, 'Write, 'Input and 'Output attribute
238 -- definition clauses.
240 procedure Analyze_Stream_TSS_Definition (TSS_Nam : TSS_Name_Type) is
241 Subp : Entity_Id := Empty;
242 I : Interp_Index;
243 It : Interp;
244 Pnam : Entity_Id;
246 Is_Read : constant Boolean := (TSS_Nam = TSS_Stream_Read);
248 function Has_Good_Profile (Subp : Entity_Id) return Boolean;
249 -- Return true if the entity is a subprogram with an appropriate
250 -- profile for the attribute being defined.
252 ----------------------
253 -- Has_Good_Profile --
254 ----------------------
256 function Has_Good_Profile (Subp : Entity_Id) return Boolean is
257 F : Entity_Id;
258 Is_Function : constant Boolean := (TSS_Nam = TSS_Stream_Input);
259 Expected_Ekind : constant array (Boolean) of Entity_Kind :=
260 (False => E_Procedure, True => E_Function);
261 Typ : Entity_Id;
263 begin
264 if Ekind (Subp) /= Expected_Ekind (Is_Function) then
265 return False;
266 end if;
268 F := First_Formal (Subp);
270 if No (F)
271 or else Ekind (Etype (F)) /= E_Anonymous_Access_Type
272 or else Designated_Type (Etype (F)) /=
273 Class_Wide_Type (RTE (RE_Root_Stream_Type))
274 then
275 return False;
276 end if;
278 if not Is_Function then
279 Next_Formal (F);
281 declare
282 Expected_Mode : constant array (Boolean) of Entity_Kind :=
283 (False => E_In_Parameter,
284 True => E_Out_Parameter);
285 begin
286 if Parameter_Mode (F) /= Expected_Mode (Is_Read) then
287 return False;
288 end if;
289 end;
291 Typ := Etype (F);
293 else
294 Typ := Etype (Subp);
295 end if;
297 return Base_Type (Typ) = Base_Type (Ent)
298 and then No (Next_Formal (F));
300 end Has_Good_Profile;
302 -- Start of processing for Analyze_Stream_TSS_Definition
304 begin
305 FOnly := True;
307 if not Is_Type (U_Ent) then
308 Error_Msg_N ("local name must be a subtype", Nam);
309 return;
310 end if;
312 Pnam := TSS (Base_Type (U_Ent), TSS_Nam);
314 -- If Pnam is present, it can be either inherited from an ancestor
315 -- type (in which case it is legal to redefine it for this type), or
316 -- be a previous definition of the attribute for the same type (in
317 -- which case it is illegal).
319 -- In the first case, it will have been analyzed already, and we
320 -- can check that its profile does not match the expected profile
321 -- for a stream attribute of U_Ent. In the second case, either Pnam
322 -- has been analyzed (and has the expected profile), or it has not
323 -- been analyzed yet (case of a type that has not been frozen yet
324 -- and for which the stream attribute has been set using Set_TSS).
326 if Present (Pnam)
327 and then (No (First_Entity (Pnam)) or else Has_Good_Profile (Pnam))
328 then
329 Error_Msg_Sloc := Sloc (Pnam);
330 Error_Msg_Name_1 := Attr;
331 Error_Msg_N ("% attribute already defined #", Nam);
332 return;
333 end if;
335 Analyze (Expr);
337 if Is_Entity_Name (Expr) then
338 if not Is_Overloaded (Expr) then
339 if Has_Good_Profile (Entity (Expr)) then
340 Subp := Entity (Expr);
341 end if;
343 else
344 Get_First_Interp (Expr, I, It);
346 while Present (It.Nam) loop
347 if Has_Good_Profile (It.Nam) then
348 Subp := It.Nam;
349 exit;
350 end if;
352 Get_Next_Interp (I, It);
353 end loop;
354 end if;
355 end if;
357 if Present (Subp) then
358 if Is_Abstract (Subp) then
359 Error_Msg_N ("stream subprogram must not be abstract", Expr);
360 return;
361 end if;
363 Set_Entity (Expr, Subp);
364 Set_Etype (Expr, Etype (Subp));
366 New_Stream_Subprogram (N, U_Ent, Subp, TSS_Nam);
368 else
369 Error_Msg_Name_1 := Attr;
370 Error_Msg_N ("incorrect expression for% attribute", Expr);
371 end if;
372 end Analyze_Stream_TSS_Definition;
374 -- Start of processing for Analyze_Attribute_Definition_Clause
376 begin
377 Analyze (Nam);
378 Ent := Entity (Nam);
380 if Rep_Item_Too_Early (Ent, N) then
381 return;
382 end if;
384 -- Rep clause applies to full view of incomplete type or private type if
385 -- we have one (if not, this is a premature use of the type). However,
386 -- certain semantic checks need to be done on the specified entity (i.e.
387 -- the private view), so we save it in Ent.
389 if Is_Private_Type (Ent)
390 and then Is_Derived_Type (Ent)
391 and then not Is_Tagged_Type (Ent)
392 and then No (Full_View (Ent))
393 then
394 -- If this is a private type whose completion is a derivation from
395 -- another private type, there is no full view, and the attribute
396 -- belongs to the type itself, not its underlying parent.
398 U_Ent := Ent;
400 elsif Ekind (Ent) = E_Incomplete_Type then
402 -- The attribute applies to the full view, set the entity of the
403 -- attribute definition accordingly.
405 Ent := Underlying_Type (Ent);
406 U_Ent := Ent;
407 Set_Entity (Nam, Ent);
409 else
410 U_Ent := Underlying_Type (Ent);
411 end if;
413 -- Complete other routine error checks
415 if Etype (Nam) = Any_Type then
416 return;
418 elsif Scope (Ent) /= Current_Scope then
419 Error_Msg_N ("entity must be declared in this scope", Nam);
420 return;
422 elsif No (U_Ent) then
423 U_Ent := Ent;
425 elsif Is_Type (U_Ent)
426 and then not Is_First_Subtype (U_Ent)
427 and then Id /= Attribute_Object_Size
428 and then Id /= Attribute_Value_Size
429 and then not From_At_Mod (N)
430 then
431 Error_Msg_N ("cannot specify attribute for subtype", Nam);
432 return;
433 end if;
435 -- Switch on particular attribute
437 case Id is
439 -------------
440 -- Address --
441 -------------
443 -- Address attribute definition clause
445 when Attribute_Address => Address : begin
446 Analyze_And_Resolve (Expr, RTE (RE_Address));
448 if Present (Address_Clause (U_Ent)) then
449 Error_Msg_N ("address already given for &", Nam);
451 -- Case of address clause for subprogram
453 elsif Is_Subprogram (U_Ent) then
454 if Has_Homonym (U_Ent) then
455 Error_Msg_N
456 ("address clause cannot be given " &
457 "for overloaded subprogram",
458 Nam);
459 end if;
461 -- For subprograms, all address clauses are permitted,
462 -- and we mark the subprogram as having a deferred freeze
463 -- so that Gigi will not elaborate it too soon.
465 -- Above needs more comments, what is too soon about???
467 Set_Has_Delayed_Freeze (U_Ent);
469 -- Case of address clause for entry
471 elsif Ekind (U_Ent) = E_Entry then
472 if Nkind (Parent (N)) = N_Task_Body then
473 Error_Msg_N
474 ("entry address must be specified in task spec", Nam);
475 end if;
477 -- For entries, we require a constant address
479 Check_Constant_Address_Clause (Expr, U_Ent);
481 if Is_Task_Type (Scope (U_Ent))
482 and then Comes_From_Source (Scope (U_Ent))
483 then
484 Error_Msg_N
485 ("?entry address declared for entry in task type", N);
486 Error_Msg_N
487 ("\?only one task can be declared of this type", N);
488 end if;
490 Check_Restriction (No_Obsolescent_Features, N);
492 if Warn_On_Obsolescent_Feature then
493 Error_Msg_N
494 ("attaching interrupt to task entry is an " &
495 "obsolescent feature ('R'M 'J.7.1)?", N);
496 Error_Msg_N
497 ("\use interrupt procedure instead?", N);
498 end if;
500 -- Case of an address clause for a controlled object:
501 -- erroneous execution.
503 elsif Is_Controlled (Etype (U_Ent)) then
504 Error_Msg_NE
505 ("?controlled object& must not be overlaid", Nam, U_Ent);
506 Error_Msg_N
507 ("\?Program_Error will be raised at run time", Nam);
508 Insert_Action (Declaration_Node (U_Ent),
509 Make_Raise_Program_Error (Loc,
510 Reason => PE_Overlaid_Controlled_Object));
512 -- Case of address clause for a (non-controlled) object
514 elsif
515 Ekind (U_Ent) = E_Variable
516 or else
517 Ekind (U_Ent) = E_Constant
518 then
519 declare
520 Expr : constant Node_Id := Expression (N);
521 Aent : constant Entity_Id := Address_Aliased_Entity (Expr);
523 begin
524 -- Exported variables cannot have an address clause,
525 -- because this cancels the effect of the pragma Export
527 if Is_Exported (U_Ent) then
528 Error_Msg_N
529 ("cannot export object with address clause", Nam);
531 -- Overlaying controlled objects is erroneous
533 elsif Present (Aent)
534 and then Is_Controlled (Etype (Aent))
535 then
536 Error_Msg_N
537 ("?controlled object must not be overlaid", Expr);
538 Error_Msg_N
539 ("\?Program_Error will be raised at run time", Expr);
540 Insert_Action (Declaration_Node (U_Ent),
541 Make_Raise_Program_Error (Loc,
542 Reason => PE_Overlaid_Controlled_Object));
544 elsif Present (Aent)
545 and then Ekind (U_Ent) = E_Constant
546 and then Ekind (Aent) /= E_Constant
547 then
548 Error_Msg_N ("constant overlays a variable?", Expr);
550 elsif Present (Renamed_Object (U_Ent)) then
551 Error_Msg_N
552 ("address clause not allowed"
553 & " for a renaming declaration ('R'M 13.1(6))", Nam);
555 -- Imported variables can have an address clause, but then
556 -- the import is pretty meaningless except to suppress
557 -- initializations, so we do not need such variables to
558 -- be statically allocated (and in fact it causes trouble
559 -- if the address clause is a local value).
561 elsif Is_Imported (U_Ent) then
562 Set_Is_Statically_Allocated (U_Ent, False);
563 end if;
565 -- We mark a possible modification of a variable with an
566 -- address clause, since it is likely aliasing is occurring.
568 Note_Possible_Modification (Nam);
570 -- Here we are checking for explicit overlap of one
571 -- variable by another, and if we find this, then we
572 -- mark the overlapped variable as also being aliased.
574 -- First case is where we have an explicit
576 -- for J'Address use K'Address;
578 -- In this case, we mark K as volatile
580 Mark_Aliased_Address_As_Volatile (Expr);
582 -- Second case is where we have a constant whose
583 -- definition is of the form of an address as in:
585 -- A : constant Address := K'Address;
586 -- ...
587 -- for B'Address use A;
589 -- In this case we also mark K as volatile
591 if Is_Entity_Name (Expr) then
592 declare
593 Ent : constant Entity_Id := Entity (Expr);
594 Decl : constant Node_Id := Declaration_Node (Ent);
596 begin
597 if Ekind (Ent) = E_Constant
598 and then Nkind (Decl) = N_Object_Declaration
599 and then Present (Expression (Decl))
600 then
601 Mark_Aliased_Address_As_Volatile
602 (Expression (Decl));
603 end if;
604 end;
605 end if;
607 -- Legality checks on the address clause for initialized
608 -- objects is deferred until the freeze point, because
609 -- a subsequent pragma might indicate that the object is
610 -- imported and thus not initialized.
612 Set_Has_Delayed_Freeze (U_Ent);
614 if Is_Exported (U_Ent) then
615 Error_Msg_N
616 ("& cannot be exported if an address clause is given",
617 Nam);
618 Error_Msg_N
619 ("\define and export a variable " &
620 "that holds its address instead",
621 Nam);
622 end if;
624 -- Entity has delayed freeze, so we will generate an
625 -- alignment check at the freeze point unless suppressed.
627 if not Range_Checks_Suppressed (U_Ent)
628 and then not Alignment_Checks_Suppressed (U_Ent)
629 then
630 Set_Check_Address_Alignment (N);
631 end if;
633 -- Kill the size check code, since we are not allocating
634 -- the variable, it is somewhere else.
636 Kill_Size_Check_Code (U_Ent);
637 end;
639 -- Not a valid entity for an address clause
641 else
642 Error_Msg_N ("address cannot be given for &", Nam);
643 end if;
644 end Address;
646 ---------------
647 -- Alignment --
648 ---------------
650 -- Alignment attribute definition clause
652 when Attribute_Alignment => Alignment_Block : declare
653 Align : constant Uint := Get_Alignment_Value (Expr);
655 begin
656 FOnly := True;
658 if not Is_Type (U_Ent)
659 and then Ekind (U_Ent) /= E_Variable
660 and then Ekind (U_Ent) /= E_Constant
661 then
662 Error_Msg_N ("alignment cannot be given for &", Nam);
664 elsif Has_Alignment_Clause (U_Ent) then
665 Error_Msg_Sloc := Sloc (Alignment_Clause (U_Ent));
666 Error_Msg_N ("alignment clause previously given#", N);
668 elsif Align /= No_Uint then
669 Set_Has_Alignment_Clause (U_Ent);
670 Set_Alignment (U_Ent, Align);
671 end if;
672 end Alignment_Block;
674 ---------------
675 -- Bit_Order --
676 ---------------
678 -- Bit_Order attribute definition clause
680 when Attribute_Bit_Order => Bit_Order : declare
681 begin
682 if not Is_Record_Type (U_Ent) then
683 Error_Msg_N
684 ("Bit_Order can only be defined for record type", Nam);
686 else
687 Analyze_And_Resolve (Expr, RTE (RE_Bit_Order));
689 if Etype (Expr) = Any_Type then
690 return;
692 elsif not Is_Static_Expression (Expr) then
693 Flag_Non_Static_Expr
694 ("Bit_Order requires static expression!", Expr);
696 else
697 if (Expr_Value (Expr) = 0) /= Bytes_Big_Endian then
698 Set_Reverse_Bit_Order (U_Ent, True);
699 end if;
700 end if;
701 end if;
702 end Bit_Order;
704 --------------------
705 -- Component_Size --
706 --------------------
708 -- Component_Size attribute definition clause
710 when Attribute_Component_Size => Component_Size_Case : declare
711 Csize : constant Uint := Static_Integer (Expr);
712 Btype : Entity_Id;
713 Biased : Boolean;
714 New_Ctyp : Entity_Id;
715 Decl : Node_Id;
717 begin
718 if not Is_Array_Type (U_Ent) then
719 Error_Msg_N ("component size requires array type", Nam);
720 return;
721 end if;
723 Btype := Base_Type (U_Ent);
725 if Has_Component_Size_Clause (Btype) then
726 Error_Msg_N
727 ("component size clase for& previously given", Nam);
729 elsif Csize /= No_Uint then
730 Check_Size (Expr, Component_Type (Btype), Csize, Biased);
732 if Has_Aliased_Components (Btype)
733 and then Csize < 32
734 and then Csize /= 8
735 and then Csize /= 16
736 then
737 Error_Msg_N
738 ("component size incorrect for aliased components", N);
739 return;
740 end if;
742 -- For the biased case, build a declaration for a subtype
743 -- that will be used to represent the biased subtype that
744 -- reflects the biased representation of components. We need
745 -- this subtype to get proper conversions on referencing
746 -- elements of the array.
748 if Biased then
749 New_Ctyp :=
750 Make_Defining_Identifier (Loc,
751 Chars => New_External_Name (Chars (U_Ent), 'C', 0, 'T'));
753 Decl :=
754 Make_Subtype_Declaration (Loc,
755 Defining_Identifier => New_Ctyp,
756 Subtype_Indication =>
757 New_Occurrence_Of (Component_Type (Btype), Loc));
759 Set_Parent (Decl, N);
760 Analyze (Decl, Suppress => All_Checks);
762 Set_Has_Delayed_Freeze (New_Ctyp, False);
763 Set_Esize (New_Ctyp, Csize);
764 Set_RM_Size (New_Ctyp, Csize);
765 Init_Alignment (New_Ctyp);
766 Set_Has_Biased_Representation (New_Ctyp, True);
767 Set_Is_Itype (New_Ctyp, True);
768 Set_Associated_Node_For_Itype (New_Ctyp, U_Ent);
770 Set_Component_Type (Btype, New_Ctyp);
771 end if;
773 Set_Component_Size (Btype, Csize);
774 Set_Has_Component_Size_Clause (Btype, True);
775 Set_Has_Non_Standard_Rep (Btype, True);
776 end if;
777 end Component_Size_Case;
779 ------------------
780 -- External_Tag --
781 ------------------
783 when Attribute_External_Tag => External_Tag :
784 begin
785 if not Is_Tagged_Type (U_Ent) then
786 Error_Msg_N ("should be a tagged type", Nam);
787 end if;
789 Analyze_And_Resolve (Expr, Standard_String);
791 if not Is_Static_Expression (Expr) then
792 Flag_Non_Static_Expr
793 ("static string required for tag name!", Nam);
794 end if;
796 Set_Has_External_Tag_Rep_Clause (U_Ent);
797 end External_Tag;
799 -----------
800 -- Input --
801 -----------
803 when Attribute_Input =>
804 Analyze_Stream_TSS_Definition (TSS_Stream_Input);
805 Set_Has_Specified_Stream_Input (Ent);
807 -------------------
808 -- Machine_Radix --
809 -------------------
811 -- Machine radix attribute definition clause
813 when Attribute_Machine_Radix => Machine_Radix : declare
814 Radix : constant Uint := Static_Integer (Expr);
816 begin
817 if not Is_Decimal_Fixed_Point_Type (U_Ent) then
818 Error_Msg_N ("decimal fixed-point type expected for &", Nam);
820 elsif Has_Machine_Radix_Clause (U_Ent) then
821 Error_Msg_Sloc := Sloc (Alignment_Clause (U_Ent));
822 Error_Msg_N ("machine radix clause previously given#", N);
824 elsif Radix /= No_Uint then
825 Set_Has_Machine_Radix_Clause (U_Ent);
826 Set_Has_Non_Standard_Rep (Base_Type (U_Ent));
828 if Radix = 2 then
829 null;
830 elsif Radix = 10 then
831 Set_Machine_Radix_10 (U_Ent);
832 else
833 Error_Msg_N ("machine radix value must be 2 or 10", Expr);
834 end if;
835 end if;
836 end Machine_Radix;
838 -----------------
839 -- Object_Size --
840 -----------------
842 -- Object_Size attribute definition clause
844 when Attribute_Object_Size => Object_Size : declare
845 Size : constant Uint := Static_Integer (Expr);
846 Biased : Boolean;
848 begin
849 if not Is_Type (U_Ent) then
850 Error_Msg_N ("Object_Size cannot be given for &", Nam);
852 elsif Has_Object_Size_Clause (U_Ent) then
853 Error_Msg_N ("Object_Size already given for &", Nam);
855 else
856 Check_Size (Expr, U_Ent, Size, Biased);
858 if Size /= 8
859 and then
860 Size /= 16
861 and then
862 Size /= 32
863 and then
864 UI_Mod (Size, 64) /= 0
865 then
866 Error_Msg_N
867 ("Object_Size must be 8, 16, 32, or multiple of 64",
868 Expr);
869 end if;
871 Set_Esize (U_Ent, Size);
872 Set_Has_Object_Size_Clause (U_Ent);
873 Alignment_Check_For_Esize_Change (U_Ent);
874 end if;
875 end Object_Size;
877 ------------
878 -- Output --
879 ------------
881 when Attribute_Output =>
882 Analyze_Stream_TSS_Definition (TSS_Stream_Output);
883 Set_Has_Specified_Stream_Output (Ent);
885 ----------
886 -- Read --
887 ----------
889 when Attribute_Read =>
890 Analyze_Stream_TSS_Definition (TSS_Stream_Read);
891 Set_Has_Specified_Stream_Read (Ent);
893 ----------
894 -- Size --
895 ----------
897 -- Size attribute definition clause
899 when Attribute_Size => Size : declare
900 Size : constant Uint := Static_Integer (Expr);
901 Etyp : Entity_Id;
902 Biased : Boolean;
904 begin
905 FOnly := True;
907 if Has_Size_Clause (U_Ent) then
908 Error_Msg_N ("size already given for &", Nam);
910 elsif not Is_Type (U_Ent)
911 and then Ekind (U_Ent) /= E_Variable
912 and then Ekind (U_Ent) /= E_Constant
913 then
914 Error_Msg_N ("size cannot be given for &", Nam);
916 elsif Is_Array_Type (U_Ent)
917 and then not Is_Constrained (U_Ent)
918 then
919 Error_Msg_N
920 ("size cannot be given for unconstrained array", Nam);
922 elsif Size /= No_Uint then
923 if Is_Type (U_Ent) then
924 Etyp := U_Ent;
925 else
926 Etyp := Etype (U_Ent);
927 end if;
929 -- Check size, note that Gigi is in charge of checking
930 -- that the size of an array or record type is OK. Also
931 -- we do not check the size in the ordinary fixed-point
932 -- case, since it is too early to do so (there may be a
933 -- subsequent small clause that affects the size). We can
934 -- check the size if a small clause has already been given.
936 if not Is_Ordinary_Fixed_Point_Type (U_Ent)
937 or else Has_Small_Clause (U_Ent)
938 then
939 Check_Size (Expr, Etyp, Size, Biased);
940 Set_Has_Biased_Representation (U_Ent, Biased);
941 end if;
943 -- For types set RM_Size and Esize if possible
945 if Is_Type (U_Ent) then
946 Set_RM_Size (U_Ent, Size);
948 -- For scalar types, increase Object_Size to power of 2,
949 -- but not less than a storage unit in any case (i.e.,
950 -- normally this means it will be byte addressable).
952 if Is_Scalar_Type (U_Ent) then
953 if Size <= System_Storage_Unit then
954 Init_Esize (U_Ent, System_Storage_Unit);
955 elsif Size <= 16 then
956 Init_Esize (U_Ent, 16);
957 elsif Size <= 32 then
958 Init_Esize (U_Ent, 32);
959 else
960 Set_Esize (U_Ent, (Size + 63) / 64 * 64);
961 end if;
963 -- For all other types, object size = value size. The
964 -- backend will adjust as needed.
966 else
967 Set_Esize (U_Ent, Size);
968 end if;
970 Alignment_Check_For_Esize_Change (U_Ent);
972 -- For objects, set Esize only
974 else
975 if Is_Elementary_Type (Etyp) then
976 if Size /= System_Storage_Unit
977 and then
978 Size /= System_Storage_Unit * 2
979 and then
980 Size /= System_Storage_Unit * 4
981 and then
982 Size /= System_Storage_Unit * 8
983 then
984 Error_Msg_Uint_1 := UI_From_Int (System_Storage_Unit);
985 Error_Msg_Uint_2 := Error_Msg_Uint_1 * 8;
986 Error_Msg_N
987 ("size for primitive object must be a power of 2"
988 & " in the range ^-^", N);
989 end if;
990 end if;
992 Set_Esize (U_Ent, Size);
993 end if;
995 Set_Has_Size_Clause (U_Ent);
996 end if;
997 end Size;
999 -----------
1000 -- Small --
1001 -----------
1003 -- Small attribute definition clause
1005 when Attribute_Small => Small : declare
1006 Implicit_Base : constant Entity_Id := Base_Type (U_Ent);
1007 Small : Ureal;
1009 begin
1010 Analyze_And_Resolve (Expr, Any_Real);
1012 if Etype (Expr) = Any_Type then
1013 return;
1015 elsif not Is_Static_Expression (Expr) then
1016 Flag_Non_Static_Expr
1017 ("small requires static expression!", Expr);
1018 return;
1020 else
1021 Small := Expr_Value_R (Expr);
1023 if Small <= Ureal_0 then
1024 Error_Msg_N ("small value must be greater than zero", Expr);
1025 return;
1026 end if;
1028 end if;
1030 if not Is_Ordinary_Fixed_Point_Type (U_Ent) then
1031 Error_Msg_N
1032 ("small requires an ordinary fixed point type", Nam);
1034 elsif Has_Small_Clause (U_Ent) then
1035 Error_Msg_N ("small already given for &", Nam);
1037 elsif Small > Delta_Value (U_Ent) then
1038 Error_Msg_N
1039 ("small value must not be greater then delta value", Nam);
1041 else
1042 Set_Small_Value (U_Ent, Small);
1043 Set_Small_Value (Implicit_Base, Small);
1044 Set_Has_Small_Clause (U_Ent);
1045 Set_Has_Small_Clause (Implicit_Base);
1046 Set_Has_Non_Standard_Rep (Implicit_Base);
1047 end if;
1048 end Small;
1050 ------------------
1051 -- Storage_Pool --
1052 ------------------
1054 -- Storage_Pool attribute definition clause
1056 when Attribute_Storage_Pool => Storage_Pool : declare
1057 Pool : Entity_Id;
1058 T : Entity_Id;
1060 begin
1061 if Ekind (U_Ent) = E_Access_Subprogram_Type then
1062 Error_Msg_N
1063 ("storage pool cannot be given for access-to-subprogram type",
1064 Nam);
1065 return;
1067 elsif Ekind (U_Ent) /= E_Access_Type
1068 and then Ekind (U_Ent) /= E_General_Access_Type
1069 then
1070 Error_Msg_N
1071 ("storage pool can only be given for access types", Nam);
1072 return;
1074 elsif Is_Derived_Type (U_Ent) then
1075 Error_Msg_N
1076 ("storage pool cannot be given for a derived access type",
1077 Nam);
1079 elsif Has_Storage_Size_Clause (U_Ent) then
1080 Error_Msg_N ("storage size already given for &", Nam);
1081 return;
1083 elsif Present (Associated_Storage_Pool (U_Ent)) then
1084 Error_Msg_N ("storage pool already given for &", Nam);
1085 return;
1086 end if;
1088 Analyze_And_Resolve
1089 (Expr, Class_Wide_Type (RTE (RE_Root_Storage_Pool)));
1091 if Nkind (Expr) = N_Type_Conversion then
1092 T := Etype (Expression (Expr));
1093 else
1094 T := Etype (Expr);
1095 end if;
1097 -- The Stack_Bounded_Pool is used internally for implementing
1098 -- access types with a Storage_Size. Since it only work
1099 -- properly when used on one specific type, we need to check
1100 -- that it is not highjacked improperly:
1101 -- type T is access Integer;
1102 -- for T'Storage_Size use n;
1103 -- type Q is access Float;
1104 -- for Q'Storage_Size use T'Storage_Size; -- incorrect
1106 if Base_Type (T) = RTE (RE_Stack_Bounded_Pool) then
1107 Error_Msg_N ("non-sharable internal Pool", Expr);
1108 return;
1109 end if;
1111 -- If the argument is a name that is not an entity name, then
1112 -- we construct a renaming operation to define an entity of
1113 -- type storage pool.
1115 if not Is_Entity_Name (Expr)
1116 and then Is_Object_Reference (Expr)
1117 then
1118 Pool :=
1119 Make_Defining_Identifier (Loc,
1120 Chars => New_Internal_Name ('P'));
1122 declare
1123 Rnode : constant Node_Id :=
1124 Make_Object_Renaming_Declaration (Loc,
1125 Defining_Identifier => Pool,
1126 Subtype_Mark =>
1127 New_Occurrence_Of (Etype (Expr), Loc),
1128 Name => Expr);
1130 begin
1131 Insert_Before (N, Rnode);
1132 Analyze (Rnode);
1133 Set_Associated_Storage_Pool (U_Ent, Pool);
1134 end;
1136 elsif Is_Entity_Name (Expr) then
1137 Pool := Entity (Expr);
1139 -- If pool is a renamed object, get original one. This can
1140 -- happen with an explicit renaming, and within instances.
1142 while Present (Renamed_Object (Pool))
1143 and then Is_Entity_Name (Renamed_Object (Pool))
1144 loop
1145 Pool := Entity (Renamed_Object (Pool));
1146 end loop;
1148 if Present (Renamed_Object (Pool))
1149 and then Nkind (Renamed_Object (Pool)) = N_Type_Conversion
1150 and then Is_Entity_Name (Expression (Renamed_Object (Pool)))
1151 then
1152 Pool := Entity (Expression (Renamed_Object (Pool)));
1153 end if;
1155 Set_Associated_Storage_Pool (U_Ent, Pool);
1157 elsif Nkind (Expr) = N_Type_Conversion
1158 and then Is_Entity_Name (Expression (Expr))
1159 and then Nkind (Original_Node (Expr)) = N_Attribute_Reference
1160 then
1161 Pool := Entity (Expression (Expr));
1162 Set_Associated_Storage_Pool (U_Ent, Pool);
1164 else
1165 Error_Msg_N ("incorrect reference to a Storage Pool", Expr);
1166 return;
1167 end if;
1168 end Storage_Pool;
1170 ------------------
1171 -- Storage_Size --
1172 ------------------
1174 -- Storage_Size attribute definition clause
1176 when Attribute_Storage_Size => Storage_Size : declare
1177 Btype : constant Entity_Id := Base_Type (U_Ent);
1178 Sprag : Node_Id;
1180 begin
1181 if Is_Task_Type (U_Ent) then
1182 Check_Restriction (No_Obsolescent_Features, N);
1184 if Warn_On_Obsolescent_Feature then
1185 Error_Msg_N
1186 ("storage size clause for task is an " &
1187 "obsolescent feature ('R'M 'J.9)?", N);
1188 Error_Msg_N
1189 ("\use Storage_Size pragma instead?", N);
1190 end if;
1192 FOnly := True;
1193 end if;
1195 if not Is_Access_Type (U_Ent)
1196 and then Ekind (U_Ent) /= E_Task_Type
1197 then
1198 Error_Msg_N ("storage size cannot be given for &", Nam);
1200 elsif Is_Access_Type (U_Ent) and Is_Derived_Type (U_Ent) then
1201 Error_Msg_N
1202 ("storage size cannot be given for a derived access type",
1203 Nam);
1205 elsif Has_Storage_Size_Clause (Btype) then
1206 Error_Msg_N ("storage size already given for &", Nam);
1208 else
1209 Analyze_And_Resolve (Expr, Any_Integer);
1211 if Is_Access_Type (U_Ent) then
1212 if Present (Associated_Storage_Pool (U_Ent)) then
1213 Error_Msg_N ("storage pool already given for &", Nam);
1214 return;
1215 end if;
1217 if Compile_Time_Known_Value (Expr)
1218 and then Expr_Value (Expr) = 0
1219 then
1220 Set_No_Pool_Assigned (Btype);
1221 end if;
1223 else -- Is_Task_Type (U_Ent)
1224 Sprag := Get_Rep_Pragma (Btype, Name_Storage_Size);
1226 if Present (Sprag) then
1227 Error_Msg_Sloc := Sloc (Sprag);
1228 Error_Msg_N
1229 ("Storage_Size already specified#", Nam);
1230 return;
1231 end if;
1232 end if;
1234 Set_Has_Storage_Size_Clause (Btype);
1235 end if;
1236 end Storage_Size;
1238 -----------------
1239 -- Stream_Size --
1240 -----------------
1242 when Attribute_Stream_Size => Stream_Size : declare
1243 Size : constant Uint := Static_Integer (Expr);
1245 begin
1246 if Has_Stream_Size_Clause (U_Ent) then
1247 Error_Msg_N ("Stream_Size already given for &", Nam);
1249 elsif Is_Elementary_Type (U_Ent) then
1250 if Size /= System_Storage_Unit
1251 and then
1252 Size /= System_Storage_Unit * 2
1253 and then
1254 Size /= System_Storage_Unit * 4
1255 and then
1256 Size /= System_Storage_Unit * 8
1257 then
1258 Error_Msg_Uint_1 := UI_From_Int (System_Storage_Unit);
1259 Error_Msg_N
1260 ("stream size for elementary type must be a"
1261 & " power of 2 and at least ^", N);
1263 elsif RM_Size (U_Ent) > Size then
1264 Error_Msg_Uint_1 := RM_Size (U_Ent);
1265 Error_Msg_N
1266 ("stream size for elementary type must be a"
1267 & " power of 2 and at least ^", N);
1268 end if;
1270 Set_Has_Stream_Size_Clause (U_Ent);
1272 else
1273 Error_Msg_N ("Stream_Size cannot be given for &", Nam);
1274 end if;
1275 end Stream_Size;
1277 ----------------
1278 -- Value_Size --
1279 ----------------
1281 -- Value_Size attribute definition clause
1283 when Attribute_Value_Size => Value_Size : declare
1284 Size : constant Uint := Static_Integer (Expr);
1285 Biased : Boolean;
1287 begin
1288 if not Is_Type (U_Ent) then
1289 Error_Msg_N ("Value_Size cannot be given for &", Nam);
1291 elsif Present
1292 (Get_Attribute_Definition_Clause
1293 (U_Ent, Attribute_Value_Size))
1294 then
1295 Error_Msg_N ("Value_Size already given for &", Nam);
1297 else
1298 if Is_Elementary_Type (U_Ent) then
1299 Check_Size (Expr, U_Ent, Size, Biased);
1300 Set_Has_Biased_Representation (U_Ent, Biased);
1301 end if;
1303 Set_RM_Size (U_Ent, Size);
1304 end if;
1305 end Value_Size;
1307 -----------
1308 -- Write --
1309 -----------
1311 when Attribute_Write =>
1312 Analyze_Stream_TSS_Definition (TSS_Stream_Write);
1313 Set_Has_Specified_Stream_Write (Ent);
1315 -- All other attributes cannot be set
1317 when others =>
1318 Error_Msg_N
1319 ("attribute& cannot be set with definition clause", N);
1320 end case;
1322 -- The test for the type being frozen must be performed after
1323 -- any expression the clause has been analyzed since the expression
1324 -- itself might cause freezing that makes the clause illegal.
1326 if Rep_Item_Too_Late (U_Ent, N, FOnly) then
1327 return;
1328 end if;
1329 end Analyze_Attribute_Definition_Clause;
1331 ----------------------------
1332 -- Analyze_Code_Statement --
1333 ----------------------------
1335 procedure Analyze_Code_Statement (N : Node_Id) is
1336 HSS : constant Node_Id := Parent (N);
1337 SBody : constant Node_Id := Parent (HSS);
1338 Subp : constant Entity_Id := Current_Scope;
1339 Stmt : Node_Id;
1340 Decl : Node_Id;
1341 StmtO : Node_Id;
1342 DeclO : Node_Id;
1344 begin
1345 -- Analyze and check we get right type, note that this implements the
1346 -- requirement (RM 13.8(1)) that Machine_Code be with'ed, since that
1347 -- is the only way that Asm_Insn could possibly be visible.
1349 Analyze_And_Resolve (Expression (N));
1351 if Etype (Expression (N)) = Any_Type then
1352 return;
1353 elsif Etype (Expression (N)) /= RTE (RE_Asm_Insn) then
1354 Error_Msg_N ("incorrect type for code statement", N);
1355 return;
1356 end if;
1358 Check_Code_Statement (N);
1360 -- Make sure we appear in the handled statement sequence of a
1361 -- subprogram (RM 13.8(3)).
1363 if Nkind (HSS) /= N_Handled_Sequence_Of_Statements
1364 or else Nkind (SBody) /= N_Subprogram_Body
1365 then
1366 Error_Msg_N
1367 ("code statement can only appear in body of subprogram", N);
1368 return;
1369 end if;
1371 -- Do remaining checks (RM 13.8(3)) if not already done
1373 if not Is_Machine_Code_Subprogram (Subp) then
1374 Set_Is_Machine_Code_Subprogram (Subp);
1376 -- No exception handlers allowed
1378 if Present (Exception_Handlers (HSS)) then
1379 Error_Msg_N
1380 ("exception handlers not permitted in machine code subprogram",
1381 First (Exception_Handlers (HSS)));
1382 end if;
1384 -- No declarations other than use clauses and pragmas (we allow
1385 -- certain internally generated declarations as well).
1387 Decl := First (Declarations (SBody));
1388 while Present (Decl) loop
1389 DeclO := Original_Node (Decl);
1390 if Comes_From_Source (DeclO)
1391 and then Nkind (DeclO) /= N_Pragma
1392 and then Nkind (DeclO) /= N_Use_Package_Clause
1393 and then Nkind (DeclO) /= N_Use_Type_Clause
1394 and then Nkind (DeclO) /= N_Implicit_Label_Declaration
1395 then
1396 Error_Msg_N
1397 ("this declaration not allowed in machine code subprogram",
1398 DeclO);
1399 end if;
1401 Next (Decl);
1402 end loop;
1404 -- No statements other than code statements, pragmas, and labels.
1405 -- Again we allow certain internally generated statements.
1407 Stmt := First (Statements (HSS));
1408 while Present (Stmt) loop
1409 StmtO := Original_Node (Stmt);
1410 if Comes_From_Source (StmtO)
1411 and then Nkind (StmtO) /= N_Pragma
1412 and then Nkind (StmtO) /= N_Label
1413 and then Nkind (StmtO) /= N_Code_Statement
1414 then
1415 Error_Msg_N
1416 ("this statement is not allowed in machine code subprogram",
1417 StmtO);
1418 end if;
1420 Next (Stmt);
1421 end loop;
1422 end if;
1423 end Analyze_Code_Statement;
1425 -----------------------------------------------
1426 -- Analyze_Enumeration_Representation_Clause --
1427 -----------------------------------------------
1429 procedure Analyze_Enumeration_Representation_Clause (N : Node_Id) is
1430 Ident : constant Node_Id := Identifier (N);
1431 Aggr : constant Node_Id := Array_Aggregate (N);
1432 Enumtype : Entity_Id;
1433 Elit : Entity_Id;
1434 Expr : Node_Id;
1435 Assoc : Node_Id;
1436 Choice : Node_Id;
1437 Val : Uint;
1438 Err : Boolean := False;
1440 Lo : constant Uint := Expr_Value (Type_Low_Bound (Universal_Integer));
1441 Hi : constant Uint := Expr_Value (Type_High_Bound (Universal_Integer));
1442 Min : Uint;
1443 Max : Uint;
1445 begin
1446 -- First some basic error checks
1448 Find_Type (Ident);
1449 Enumtype := Entity (Ident);
1451 if Enumtype = Any_Type
1452 or else Rep_Item_Too_Early (Enumtype, N)
1453 then
1454 return;
1455 else
1456 Enumtype := Underlying_Type (Enumtype);
1457 end if;
1459 if not Is_Enumeration_Type (Enumtype) then
1460 Error_Msg_NE
1461 ("enumeration type required, found}",
1462 Ident, First_Subtype (Enumtype));
1463 return;
1464 end if;
1466 -- Ignore rep clause on generic actual type. This will already have
1467 -- been flagged on the template as an error, and this is the safest
1468 -- way to ensure we don't get a junk cascaded message in the instance.
1470 if Is_Generic_Actual_Type (Enumtype) then
1471 return;
1473 -- Type must be in current scope
1475 elsif Scope (Enumtype) /= Current_Scope then
1476 Error_Msg_N ("type must be declared in this scope", Ident);
1477 return;
1479 -- Type must be a first subtype
1481 elsif not Is_First_Subtype (Enumtype) then
1482 Error_Msg_N ("cannot give enumeration rep clause for subtype", N);
1483 return;
1485 -- Ignore duplicate rep clause
1487 elsif Has_Enumeration_Rep_Clause (Enumtype) then
1488 Error_Msg_N ("duplicate enumeration rep clause ignored", N);
1489 return;
1491 -- Don't allow rep clause for standard [wide_[wide_]]character
1493 elsif Root_Type (Enumtype) = Standard_Character
1494 or else Root_Type (Enumtype) = Standard_Wide_Character
1495 or else Root_Type (Enumtype) = Standard_Wide_Wide_Character
1496 then
1497 Error_Msg_N ("enumeration rep clause not allowed for this type", N);
1498 return;
1500 -- Check that the expression is a proper aggregate (no parentheses)
1502 elsif Paren_Count (Aggr) /= 0 then
1503 Error_Msg
1504 ("extra parentheses surrounding aggregate not allowed",
1505 First_Sloc (Aggr));
1506 return;
1508 -- All tests passed, so set rep clause in place
1510 else
1511 Set_Has_Enumeration_Rep_Clause (Enumtype);
1512 Set_Has_Enumeration_Rep_Clause (Base_Type (Enumtype));
1513 end if;
1515 -- Now we process the aggregate. Note that we don't use the normal
1516 -- aggregate code for this purpose, because we don't want any of the
1517 -- normal expansion activities, and a number of special semantic
1518 -- rules apply (including the component type being any integer type)
1520 Elit := First_Literal (Enumtype);
1522 -- First the positional entries if any
1524 if Present (Expressions (Aggr)) then
1525 Expr := First (Expressions (Aggr));
1526 while Present (Expr) loop
1527 if No (Elit) then
1528 Error_Msg_N ("too many entries in aggregate", Expr);
1529 return;
1530 end if;
1532 Val := Static_Integer (Expr);
1534 -- Err signals that we found some incorrect entries processing
1535 -- the list. The final checks for completeness and ordering are
1536 -- skipped in this case.
1538 if Val = No_Uint then
1539 Err := True;
1540 elsif Val < Lo or else Hi < Val then
1541 Error_Msg_N ("value outside permitted range", Expr);
1542 Err := True;
1543 end if;
1545 Set_Enumeration_Rep (Elit, Val);
1546 Set_Enumeration_Rep_Expr (Elit, Expr);
1547 Next (Expr);
1548 Next (Elit);
1549 end loop;
1550 end if;
1552 -- Now process the named entries if present
1554 if Present (Component_Associations (Aggr)) then
1555 Assoc := First (Component_Associations (Aggr));
1556 while Present (Assoc) loop
1557 Choice := First (Choices (Assoc));
1559 if Present (Next (Choice)) then
1560 Error_Msg_N
1561 ("multiple choice not allowed here", Next (Choice));
1562 Err := True;
1563 end if;
1565 if Nkind (Choice) = N_Others_Choice then
1566 Error_Msg_N ("others choice not allowed here", Choice);
1567 Err := True;
1569 elsif Nkind (Choice) = N_Range then
1570 -- ??? should allow zero/one element range here
1571 Error_Msg_N ("range not allowed here", Choice);
1572 Err := True;
1574 else
1575 Analyze_And_Resolve (Choice, Enumtype);
1577 if Is_Entity_Name (Choice)
1578 and then Is_Type (Entity (Choice))
1579 then
1580 Error_Msg_N ("subtype name not allowed here", Choice);
1581 Err := True;
1582 -- ??? should allow static subtype with zero/one entry
1584 elsif Etype (Choice) = Base_Type (Enumtype) then
1585 if not Is_Static_Expression (Choice) then
1586 Flag_Non_Static_Expr
1587 ("non-static expression used for choice!", Choice);
1588 Err := True;
1590 else
1591 Elit := Expr_Value_E (Choice);
1593 if Present (Enumeration_Rep_Expr (Elit)) then
1594 Error_Msg_Sloc := Sloc (Enumeration_Rep_Expr (Elit));
1595 Error_Msg_NE
1596 ("representation for& previously given#",
1597 Choice, Elit);
1598 Err := True;
1599 end if;
1601 Set_Enumeration_Rep_Expr (Elit, Choice);
1603 Expr := Expression (Assoc);
1604 Val := Static_Integer (Expr);
1606 if Val = No_Uint then
1607 Err := True;
1609 elsif Val < Lo or else Hi < Val then
1610 Error_Msg_N ("value outside permitted range", Expr);
1611 Err := True;
1612 end if;
1614 Set_Enumeration_Rep (Elit, Val);
1615 end if;
1616 end if;
1617 end if;
1619 Next (Assoc);
1620 end loop;
1621 end if;
1623 -- Aggregate is fully processed. Now we check that a full set of
1624 -- representations was given, and that they are in range and in order.
1625 -- These checks are only done if no other errors occurred.
1627 if not Err then
1628 Min := No_Uint;
1629 Max := No_Uint;
1631 Elit := First_Literal (Enumtype);
1632 while Present (Elit) loop
1633 if No (Enumeration_Rep_Expr (Elit)) then
1634 Error_Msg_NE ("missing representation for&!", N, Elit);
1636 else
1637 Val := Enumeration_Rep (Elit);
1639 if Min = No_Uint then
1640 Min := Val;
1641 end if;
1643 if Val /= No_Uint then
1644 if Max /= No_Uint and then Val <= Max then
1645 Error_Msg_NE
1646 ("enumeration value for& not ordered!",
1647 Enumeration_Rep_Expr (Elit), Elit);
1648 end if;
1650 Max := Val;
1651 end if;
1653 -- If there is at least one literal whose representation
1654 -- is not equal to the Pos value, then note that this
1655 -- enumeration type has a non-standard representation.
1657 if Val /= Enumeration_Pos (Elit) then
1658 Set_Has_Non_Standard_Rep (Base_Type (Enumtype));
1659 end if;
1660 end if;
1662 Next (Elit);
1663 end loop;
1665 -- Now set proper size information
1667 declare
1668 Minsize : Uint := UI_From_Int (Minimum_Size (Enumtype));
1670 begin
1671 if Has_Size_Clause (Enumtype) then
1672 if Esize (Enumtype) >= Minsize then
1673 null;
1675 else
1676 Minsize :=
1677 UI_From_Int (Minimum_Size (Enumtype, Biased => True));
1679 if Esize (Enumtype) < Minsize then
1680 Error_Msg_N ("previously given size is too small", N);
1682 else
1683 Set_Has_Biased_Representation (Enumtype);
1684 end if;
1685 end if;
1687 else
1688 Set_RM_Size (Enumtype, Minsize);
1689 Set_Enum_Esize (Enumtype);
1690 end if;
1692 Set_RM_Size (Base_Type (Enumtype), RM_Size (Enumtype));
1693 Set_Esize (Base_Type (Enumtype), Esize (Enumtype));
1694 Set_Alignment (Base_Type (Enumtype), Alignment (Enumtype));
1695 end;
1696 end if;
1698 -- We repeat the too late test in case it froze itself!
1700 if Rep_Item_Too_Late (Enumtype, N) then
1701 null;
1702 end if;
1703 end Analyze_Enumeration_Representation_Clause;
1705 ----------------------------
1706 -- Analyze_Free_Statement --
1707 ----------------------------
1709 procedure Analyze_Free_Statement (N : Node_Id) is
1710 begin
1711 Analyze (Expression (N));
1712 end Analyze_Free_Statement;
1714 ------------------------------------------
1715 -- Analyze_Record_Representation_Clause --
1716 ------------------------------------------
1718 procedure Analyze_Record_Representation_Clause (N : Node_Id) is
1719 Loc : constant Source_Ptr := Sloc (N);
1720 Ident : constant Node_Id := Identifier (N);
1721 Rectype : Entity_Id;
1722 Fent : Entity_Id;
1723 CC : Node_Id;
1724 Posit : Uint;
1725 Fbit : Uint;
1726 Lbit : Uint;
1727 Hbit : Uint := Uint_0;
1728 Comp : Entity_Id;
1729 Ocomp : Entity_Id;
1730 Biased : Boolean;
1732 Max_Bit_So_Far : Uint;
1733 -- Records the maximum bit position so far. If all field positions
1734 -- are monotonically increasing, then we can skip the circuit for
1735 -- checking for overlap, since no overlap is possible.
1737 Overlap_Check_Required : Boolean;
1738 -- Used to keep track of whether or not an overlap check is required
1740 Ccount : Natural := 0;
1741 -- Number of component clauses in record rep clause
1743 CR_Pragma : Node_Id := Empty;
1744 -- Points to N_Pragma node if Complete_Representation pragma present
1746 begin
1747 Find_Type (Ident);
1748 Rectype := Entity (Ident);
1750 if Rectype = Any_Type
1751 or else Rep_Item_Too_Early (Rectype, N)
1752 then
1753 return;
1754 else
1755 Rectype := Underlying_Type (Rectype);
1756 end if;
1758 -- First some basic error checks
1760 if not Is_Record_Type (Rectype) then
1761 Error_Msg_NE
1762 ("record type required, found}", Ident, First_Subtype (Rectype));
1763 return;
1765 elsif Is_Unchecked_Union (Rectype) then
1766 Error_Msg_N
1767 ("record rep clause not allowed for Unchecked_Union", N);
1769 elsif Scope (Rectype) /= Current_Scope then
1770 Error_Msg_N ("type must be declared in this scope", N);
1771 return;
1773 elsif not Is_First_Subtype (Rectype) then
1774 Error_Msg_N ("cannot give record rep clause for subtype", N);
1775 return;
1777 elsif Has_Record_Rep_Clause (Rectype) then
1778 Error_Msg_N ("duplicate record rep clause ignored", N);
1779 return;
1781 elsif Rep_Item_Too_Late (Rectype, N) then
1782 return;
1783 end if;
1785 if Present (Mod_Clause (N)) then
1786 declare
1787 Loc : constant Source_Ptr := Sloc (N);
1788 M : constant Node_Id := Mod_Clause (N);
1789 P : constant List_Id := Pragmas_Before (M);
1790 AtM_Nod : Node_Id;
1792 Mod_Val : Uint;
1793 pragma Warnings (Off, Mod_Val);
1795 begin
1796 Check_Restriction (No_Obsolescent_Features, Mod_Clause (N));
1798 if Warn_On_Obsolescent_Feature then
1799 Error_Msg_N
1800 ("mod clause is an obsolescent feature ('R'M 'J.8)?", N);
1801 Error_Msg_N
1802 ("\use alignment attribute definition clause instead?", N);
1803 end if;
1805 if Present (P) then
1806 Analyze_List (P);
1807 end if;
1809 -- In ASIS_Mode mode, expansion is disabled, but we must
1810 -- convert the Mod clause into an alignment clause anyway, so
1811 -- that the back-end can compute and back-annotate properly the
1812 -- size and alignment of types that may include this record.
1814 if Operating_Mode = Check_Semantics
1815 and then ASIS_Mode
1816 then
1817 AtM_Nod :=
1818 Make_Attribute_Definition_Clause (Loc,
1819 Name => New_Reference_To (Base_Type (Rectype), Loc),
1820 Chars => Name_Alignment,
1821 Expression => Relocate_Node (Expression (M)));
1823 Set_From_At_Mod (AtM_Nod);
1824 Insert_After (N, AtM_Nod);
1825 Mod_Val := Get_Alignment_Value (Expression (AtM_Nod));
1826 Set_Mod_Clause (N, Empty);
1828 else
1829 -- Get the alignment value to perform error checking
1831 Mod_Val := Get_Alignment_Value (Expression (M));
1833 end if;
1834 end;
1835 end if;
1837 -- Clear any existing component clauses for the type (this happens
1838 -- with derived types, where we are now overriding the original)
1840 Fent := First_Entity (Rectype);
1842 Comp := Fent;
1843 while Present (Comp) loop
1844 if Ekind (Comp) = E_Component
1845 or else Ekind (Comp) = E_Discriminant
1846 then
1847 Set_Component_Clause (Comp, Empty);
1848 end if;
1850 Next_Entity (Comp);
1851 end loop;
1853 -- All done if no component clauses
1855 CC := First (Component_Clauses (N));
1857 if No (CC) then
1858 return;
1859 end if;
1861 -- If a tag is present, then create a component clause that places
1862 -- it at the start of the record (otherwise gigi may place it after
1863 -- other fields that have rep clauses).
1865 if Nkind (Fent) = N_Defining_Identifier
1866 and then Chars (Fent) = Name_uTag
1867 then
1868 Set_Component_Bit_Offset (Fent, Uint_0);
1869 Set_Normalized_Position (Fent, Uint_0);
1870 Set_Normalized_First_Bit (Fent, Uint_0);
1871 Set_Normalized_Position_Max (Fent, Uint_0);
1872 Init_Esize (Fent, System_Address_Size);
1874 Set_Component_Clause (Fent,
1875 Make_Component_Clause (Loc,
1876 Component_Name =>
1877 Make_Identifier (Loc,
1878 Chars => Name_uTag),
1880 Position =>
1881 Make_Integer_Literal (Loc,
1882 Intval => Uint_0),
1884 First_Bit =>
1885 Make_Integer_Literal (Loc,
1886 Intval => Uint_0),
1888 Last_Bit =>
1889 Make_Integer_Literal (Loc,
1890 UI_From_Int (System_Address_Size))));
1892 Ccount := Ccount + 1;
1893 end if;
1895 -- A representation like this applies to the base type
1897 Set_Has_Record_Rep_Clause (Base_Type (Rectype));
1898 Set_Has_Non_Standard_Rep (Base_Type (Rectype));
1899 Set_Has_Specified_Layout (Base_Type (Rectype));
1901 Max_Bit_So_Far := Uint_Minus_1;
1902 Overlap_Check_Required := False;
1904 -- Process the component clauses
1906 while Present (CC) loop
1908 -- Pragma
1910 if Nkind (CC) = N_Pragma then
1911 Analyze (CC);
1913 -- The only pragma of interest is Complete_Representation
1915 if Chars (CC) = Name_Complete_Representation then
1916 CR_Pragma := CC;
1917 end if;
1919 -- Processing for real component clause
1921 else
1922 Ccount := Ccount + 1;
1923 Posit := Static_Integer (Position (CC));
1924 Fbit := Static_Integer (First_Bit (CC));
1925 Lbit := Static_Integer (Last_Bit (CC));
1927 if Posit /= No_Uint
1928 and then Fbit /= No_Uint
1929 and then Lbit /= No_Uint
1930 then
1931 if Posit < 0 then
1932 Error_Msg_N
1933 ("position cannot be negative", Position (CC));
1935 elsif Fbit < 0 then
1936 Error_Msg_N
1937 ("first bit cannot be negative", First_Bit (CC));
1939 -- Values look OK, so find the corresponding record component
1940 -- Even though the syntax allows an attribute reference for
1941 -- implementation-defined components, GNAT does not allow the
1942 -- tag to get an explicit position.
1944 elsif Nkind (Component_Name (CC)) = N_Attribute_Reference then
1945 if Attribute_Name (Component_Name (CC)) = Name_Tag then
1946 Error_Msg_N ("position of tag cannot be specified", CC);
1947 else
1948 Error_Msg_N ("illegal component name", CC);
1949 end if;
1951 else
1952 Comp := First_Entity (Rectype);
1953 while Present (Comp) loop
1954 exit when Chars (Comp) = Chars (Component_Name (CC));
1955 Next_Entity (Comp);
1956 end loop;
1958 if No (Comp) then
1960 -- Maybe component of base type that is absent from
1961 -- statically constrained first subtype.
1963 Comp := First_Entity (Base_Type (Rectype));
1964 while Present (Comp) loop
1965 exit when Chars (Comp) = Chars (Component_Name (CC));
1966 Next_Entity (Comp);
1967 end loop;
1968 end if;
1970 if No (Comp) then
1971 Error_Msg_N
1972 ("component clause is for non-existent field", CC);
1974 elsif Present (Component_Clause (Comp)) then
1975 Error_Msg_Sloc := Sloc (Component_Clause (Comp));
1976 Error_Msg_N
1977 ("component clause previously given#", CC);
1979 else
1980 -- Update Fbit and Lbit to the actual bit number
1982 Fbit := Fbit + UI_From_Int (SSU) * Posit;
1983 Lbit := Lbit + UI_From_Int (SSU) * Posit;
1985 if Fbit <= Max_Bit_So_Far then
1986 Overlap_Check_Required := True;
1987 else
1988 Max_Bit_So_Far := Lbit;
1989 end if;
1991 if Has_Size_Clause (Rectype)
1992 and then Esize (Rectype) <= Lbit
1993 then
1994 Error_Msg_N
1995 ("bit number out of range of specified size",
1996 Last_Bit (CC));
1997 else
1998 Set_Component_Clause (Comp, CC);
1999 Set_Component_Bit_Offset (Comp, Fbit);
2000 Set_Esize (Comp, 1 + (Lbit - Fbit));
2001 Set_Normalized_First_Bit (Comp, Fbit mod SSU);
2002 Set_Normalized_Position (Comp, Fbit / SSU);
2004 Set_Normalized_Position_Max
2005 (Fent, Normalized_Position (Fent));
2007 if Is_Tagged_Type (Rectype)
2008 and then Fbit < System_Address_Size
2009 then
2010 Error_Msg_NE
2011 ("component overlaps tag field of&",
2012 CC, Rectype);
2013 end if;
2015 -- This information is also set in the corresponding
2016 -- component of the base type, found by accessing the
2017 -- Original_Record_Component link if it is present.
2019 Ocomp := Original_Record_Component (Comp);
2021 if Hbit < Lbit then
2022 Hbit := Lbit;
2023 end if;
2025 Check_Size
2026 (Component_Name (CC),
2027 Etype (Comp),
2028 Esize (Comp),
2029 Biased);
2031 Set_Has_Biased_Representation (Comp, Biased);
2033 if Present (Ocomp) then
2034 Set_Component_Clause (Ocomp, CC);
2035 Set_Component_Bit_Offset (Ocomp, Fbit);
2036 Set_Normalized_First_Bit (Ocomp, Fbit mod SSU);
2037 Set_Normalized_Position (Ocomp, Fbit / SSU);
2038 Set_Esize (Ocomp, 1 + (Lbit - Fbit));
2040 Set_Normalized_Position_Max
2041 (Ocomp, Normalized_Position (Ocomp));
2043 Set_Has_Biased_Representation
2044 (Ocomp, Has_Biased_Representation (Comp));
2045 end if;
2047 if Esize (Comp) < 0 then
2048 Error_Msg_N ("component size is negative", CC);
2049 end if;
2050 end if;
2051 end if;
2052 end if;
2053 end if;
2054 end if;
2056 Next (CC);
2057 end loop;
2059 -- Now that we have processed all the component clauses, check for
2060 -- overlap. We have to leave this till last, since the components
2061 -- can appear in any arbitrary order in the representation clause.
2063 -- We do not need this check if all specified ranges were monotonic,
2064 -- as recorded by Overlap_Check_Required being False at this stage.
2066 -- This first section checks if there are any overlapping entries
2067 -- at all. It does this by sorting all entries and then seeing if
2068 -- there are any overlaps. If there are none, then that is decisive,
2069 -- but if there are overlaps, they may still be OK (they may result
2070 -- from fields in different variants).
2072 if Overlap_Check_Required then
2073 Overlap_Check1 : declare
2075 OC_Fbit : array (0 .. Ccount) of Uint;
2076 -- First-bit values for component clauses, the value is the
2077 -- offset of the first bit of the field from start of record.
2078 -- The zero entry is for use in sorting.
2080 OC_Lbit : array (0 .. Ccount) of Uint;
2081 -- Last-bit values for component clauses, the value is the
2082 -- offset of the last bit of the field from start of record.
2083 -- The zero entry is for use in sorting.
2085 OC_Count : Natural := 0;
2086 -- Count of entries in OC_Fbit and OC_Lbit
2088 function OC_Lt (Op1, Op2 : Natural) return Boolean;
2089 -- Compare routine for Sort (See GNAT.Heap_Sort_A)
2091 procedure OC_Move (From : Natural; To : Natural);
2092 -- Move routine for Sort (see GNAT.Heap_Sort_A)
2094 function OC_Lt (Op1, Op2 : Natural) return Boolean is
2095 begin
2096 return OC_Fbit (Op1) < OC_Fbit (Op2);
2097 end OC_Lt;
2099 procedure OC_Move (From : Natural; To : Natural) is
2100 begin
2101 OC_Fbit (To) := OC_Fbit (From);
2102 OC_Lbit (To) := OC_Lbit (From);
2103 end OC_Move;
2105 begin
2106 CC := First (Component_Clauses (N));
2107 while Present (CC) loop
2108 if Nkind (CC) /= N_Pragma then
2109 Posit := Static_Integer (Position (CC));
2110 Fbit := Static_Integer (First_Bit (CC));
2111 Lbit := Static_Integer (Last_Bit (CC));
2113 if Posit /= No_Uint
2114 and then Fbit /= No_Uint
2115 and then Lbit /= No_Uint
2116 then
2117 OC_Count := OC_Count + 1;
2118 Posit := Posit * SSU;
2119 OC_Fbit (OC_Count) := Fbit + Posit;
2120 OC_Lbit (OC_Count) := Lbit + Posit;
2121 end if;
2122 end if;
2124 Next (CC);
2125 end loop;
2127 Sort
2128 (OC_Count,
2129 OC_Move'Unrestricted_Access,
2130 OC_Lt'Unrestricted_Access);
2132 Overlap_Check_Required := False;
2133 for J in 1 .. OC_Count - 1 loop
2134 if OC_Lbit (J) >= OC_Fbit (J + 1) then
2135 Overlap_Check_Required := True;
2136 exit;
2137 end if;
2138 end loop;
2139 end Overlap_Check1;
2140 end if;
2142 -- If Overlap_Check_Required is still True, then we have to do
2143 -- the full scale overlap check, since we have at least two fields
2144 -- that do overlap, and we need to know if that is OK since they
2145 -- are in the same variant, or whether we have a definite problem
2147 if Overlap_Check_Required then
2148 Overlap_Check2 : declare
2149 C1_Ent, C2_Ent : Entity_Id;
2150 -- Entities of components being checked for overlap
2152 Clist : Node_Id;
2153 -- Component_List node whose Component_Items are being checked
2155 Citem : Node_Id;
2156 -- Component declaration for component being checked
2158 begin
2159 C1_Ent := First_Entity (Base_Type (Rectype));
2161 -- Loop through all components in record. For each component check
2162 -- for overlap with any of the preceding elements on the component
2163 -- list containing the component, and also, if the component is in
2164 -- a variant, check against components outside the case structure.
2165 -- This latter test is repeated recursively up the variant tree.
2167 Main_Component_Loop : while Present (C1_Ent) loop
2168 if Ekind (C1_Ent) /= E_Component
2169 and then Ekind (C1_Ent) /= E_Discriminant
2170 then
2171 goto Continue_Main_Component_Loop;
2172 end if;
2174 -- Skip overlap check if entity has no declaration node. This
2175 -- happens with discriminants in constrained derived types.
2176 -- Probably we are missing some checks as a result, but that
2177 -- does not seem terribly serious ???
2179 if No (Declaration_Node (C1_Ent)) then
2180 goto Continue_Main_Component_Loop;
2181 end if;
2183 Clist := Parent (List_Containing (Declaration_Node (C1_Ent)));
2185 -- Loop through component lists that need checking. Check the
2186 -- current component list and all lists in variants above us.
2188 Component_List_Loop : loop
2190 -- If derived type definition, go to full declaration
2191 -- If at outer level, check discriminants if there are any
2193 if Nkind (Clist) = N_Derived_Type_Definition then
2194 Clist := Parent (Clist);
2195 end if;
2197 -- Outer level of record definition, check discriminants
2199 if Nkind (Clist) = N_Full_Type_Declaration
2200 or else Nkind (Clist) = N_Private_Type_Declaration
2201 then
2202 if Has_Discriminants (Defining_Identifier (Clist)) then
2203 C2_Ent :=
2204 First_Discriminant (Defining_Identifier (Clist));
2206 while Present (C2_Ent) loop
2207 exit when C1_Ent = C2_Ent;
2208 Check_Component_Overlap (C1_Ent, C2_Ent);
2209 Next_Discriminant (C2_Ent);
2210 end loop;
2211 end if;
2213 -- Record extension case
2215 elsif Nkind (Clist) = N_Derived_Type_Definition then
2216 Clist := Empty;
2218 -- Otherwise check one component list
2220 else
2221 Citem := First (Component_Items (Clist));
2223 while Present (Citem) loop
2224 if Nkind (Citem) = N_Component_Declaration then
2225 C2_Ent := Defining_Identifier (Citem);
2226 exit when C1_Ent = C2_Ent;
2227 Check_Component_Overlap (C1_Ent, C2_Ent);
2228 end if;
2230 Next (Citem);
2231 end loop;
2232 end if;
2234 -- Check for variants above us (the parent of the Clist can
2235 -- be a variant, in which case its parent is a variant part,
2236 -- and the parent of the variant part is a component list
2237 -- whose components must all be checked against the current
2238 -- component for overlap.
2240 if Nkind (Parent (Clist)) = N_Variant then
2241 Clist := Parent (Parent (Parent (Clist)));
2243 -- Check for possible discriminant part in record, this is
2244 -- treated essentially as another level in the recursion.
2245 -- For this case we have the parent of the component list
2246 -- is the record definition, and its parent is the full
2247 -- type declaration which contains the discriminant
2248 -- specifications.
2250 elsif Nkind (Parent (Clist)) = N_Record_Definition then
2251 Clist := Parent (Parent ((Clist)));
2253 -- If neither of these two cases, we are at the top of
2254 -- the tree
2256 else
2257 exit Component_List_Loop;
2258 end if;
2259 end loop Component_List_Loop;
2261 <<Continue_Main_Component_Loop>>
2262 Next_Entity (C1_Ent);
2264 end loop Main_Component_Loop;
2265 end Overlap_Check2;
2266 end if;
2268 -- For records that have component clauses for all components, and
2269 -- whose size is less than or equal to 32, we need to know the size
2270 -- in the front end to activate possible packed array processing
2271 -- where the component type is a record.
2273 -- At this stage Hbit + 1 represents the first unused bit from all
2274 -- the component clauses processed, so if the component clauses are
2275 -- complete, then this is the length of the record.
2277 -- For records longer than System.Storage_Unit, and for those where
2278 -- not all components have component clauses, the back end determines
2279 -- the length (it may for example be appopriate to round up the size
2280 -- to some convenient boundary, based on alignment considerations etc).
2282 if Unknown_RM_Size (Rectype)
2283 and then Hbit + 1 <= 32
2284 then
2285 -- Nothing to do if at least one component with no component clause
2287 Comp := First_Entity (Rectype);
2288 while Present (Comp) loop
2289 if Ekind (Comp) = E_Component
2290 or else Ekind (Comp) = E_Discriminant
2291 then
2292 exit when No (Component_Clause (Comp));
2293 end if;
2295 Next_Entity (Comp);
2296 end loop;
2298 -- If we fall out of loop, all components have component clauses
2299 -- and so we can set the size to the maximum value.
2301 if No (Comp) then
2302 Set_RM_Size (Rectype, Hbit + 1);
2303 end if;
2304 end if;
2306 -- Check missing components if Complete_Representation pragma appeared
2308 if Present (CR_Pragma) then
2309 Comp := First_Entity (Rectype);
2310 while Present (Comp) loop
2311 if Ekind (Comp) = E_Component
2312 or else
2313 Ekind (Comp) = E_Discriminant
2314 then
2315 if No (Component_Clause (Comp)) then
2316 Error_Msg_NE
2317 ("missing component clause for &", CR_Pragma, Comp);
2318 end if;
2319 end if;
2321 Next_Entity (Comp);
2322 end loop;
2323 end if;
2324 end Analyze_Record_Representation_Clause;
2326 -----------------------------
2327 -- Check_Component_Overlap --
2328 -----------------------------
2330 procedure Check_Component_Overlap (C1_Ent, C2_Ent : Entity_Id) is
2331 begin
2332 if Present (Component_Clause (C1_Ent))
2333 and then Present (Component_Clause (C2_Ent))
2334 then
2335 -- Exclude odd case where we have two tag fields in the same
2336 -- record, both at location zero. This seems a bit strange,
2337 -- but it seems to happen in some circumstances ???
2339 if Chars (C1_Ent) = Name_uTag
2340 and then Chars (C2_Ent) = Name_uTag
2341 then
2342 return;
2343 end if;
2345 -- Here we check if the two fields overlap
2347 declare
2348 S1 : constant Uint := Component_Bit_Offset (C1_Ent);
2349 S2 : constant Uint := Component_Bit_Offset (C2_Ent);
2350 E1 : constant Uint := S1 + Esize (C1_Ent);
2351 E2 : constant Uint := S2 + Esize (C2_Ent);
2353 begin
2354 if E2 <= S1 or else E1 <= S2 then
2355 null;
2356 else
2357 Error_Msg_Node_2 :=
2358 Component_Name (Component_Clause (C2_Ent));
2359 Error_Msg_Sloc := Sloc (Error_Msg_Node_2);
2360 Error_Msg_Node_1 :=
2361 Component_Name (Component_Clause (C1_Ent));
2362 Error_Msg_N
2363 ("component& overlaps & #",
2364 Component_Name (Component_Clause (C1_Ent)));
2365 end if;
2366 end;
2367 end if;
2368 end Check_Component_Overlap;
2370 -----------------------------------
2371 -- Check_Constant_Address_Clause --
2372 -----------------------------------
2374 procedure Check_Constant_Address_Clause
2375 (Expr : Node_Id;
2376 U_Ent : Entity_Id)
2378 procedure Check_At_Constant_Address (Nod : Node_Id);
2379 -- Checks that the given node N represents a name whose 'Address
2380 -- is constant (in the same sense as OK_Constant_Address_Clause,
2381 -- i.e. the address value is the same at the point of declaration
2382 -- of U_Ent and at the time of elaboration of the address clause.
2384 procedure Check_Expr_Constants (Nod : Node_Id);
2385 -- Checks that Nod meets the requirements for a constant address
2386 -- clause in the sense of the enclosing procedure.
2388 procedure Check_List_Constants (Lst : List_Id);
2389 -- Check that all elements of list Lst meet the requirements for a
2390 -- constant address clause in the sense of the enclosing procedure.
2392 -------------------------------
2393 -- Check_At_Constant_Address --
2394 -------------------------------
2396 procedure Check_At_Constant_Address (Nod : Node_Id) is
2397 begin
2398 if Is_Entity_Name (Nod) then
2399 if Present (Address_Clause (Entity ((Nod)))) then
2400 Error_Msg_NE
2401 ("invalid address clause for initialized object &!",
2402 Nod, U_Ent);
2403 Error_Msg_NE
2404 ("address for& cannot" &
2405 " depend on another address clause! ('R'M 13.1(22))!",
2406 Nod, U_Ent);
2408 elsif In_Same_Source_Unit (Entity (Nod), U_Ent)
2409 and then Sloc (U_Ent) < Sloc (Entity (Nod))
2410 then
2411 Error_Msg_NE
2412 ("invalid address clause for initialized object &!",
2413 Nod, U_Ent);
2414 Error_Msg_Name_1 := Chars (Entity (Nod));
2415 Error_Msg_Name_2 := Chars (U_Ent);
2416 Error_Msg_N
2417 ("\% must be defined before % ('R'M 13.1(22))!",
2418 Nod);
2419 end if;
2421 elsif Nkind (Nod) = N_Selected_Component then
2422 declare
2423 T : constant Entity_Id := Etype (Prefix (Nod));
2425 begin
2426 if (Is_Record_Type (T)
2427 and then Has_Discriminants (T))
2428 or else
2429 (Is_Access_Type (T)
2430 and then Is_Record_Type (Designated_Type (T))
2431 and then Has_Discriminants (Designated_Type (T)))
2432 then
2433 Error_Msg_NE
2434 ("invalid address clause for initialized object &!",
2435 Nod, U_Ent);
2436 Error_Msg_N
2437 ("\address cannot depend on component" &
2438 " of discriminated record ('R'M 13.1(22))!",
2439 Nod);
2440 else
2441 Check_At_Constant_Address (Prefix (Nod));
2442 end if;
2443 end;
2445 elsif Nkind (Nod) = N_Indexed_Component then
2446 Check_At_Constant_Address (Prefix (Nod));
2447 Check_List_Constants (Expressions (Nod));
2449 else
2450 Check_Expr_Constants (Nod);
2451 end if;
2452 end Check_At_Constant_Address;
2454 --------------------------
2455 -- Check_Expr_Constants --
2456 --------------------------
2458 procedure Check_Expr_Constants (Nod : Node_Id) is
2459 Loc_U_Ent : constant Source_Ptr := Sloc (U_Ent);
2460 Ent : Entity_Id := Empty;
2462 begin
2463 if Nkind (Nod) in N_Has_Etype
2464 and then Etype (Nod) = Any_Type
2465 then
2466 return;
2467 end if;
2469 case Nkind (Nod) is
2470 when N_Empty | N_Error =>
2471 return;
2473 when N_Identifier | N_Expanded_Name =>
2474 Ent := Entity (Nod);
2476 -- We need to look at the original node if it is different
2477 -- from the node, since we may have rewritten things and
2478 -- substituted an identifier representing the rewrite.
2480 if Original_Node (Nod) /= Nod then
2481 Check_Expr_Constants (Original_Node (Nod));
2483 -- If the node is an object declaration without initial
2484 -- value, some code has been expanded, and the expression
2485 -- is not constant, even if the constituents might be
2486 -- acceptable, as in A'Address + offset.
2488 if Ekind (Ent) = E_Variable
2489 and then Nkind (Declaration_Node (Ent))
2490 = N_Object_Declaration
2491 and then
2492 No (Expression (Declaration_Node (Ent)))
2493 then
2494 Error_Msg_NE
2495 ("invalid address clause for initialized object &!",
2496 Nod, U_Ent);
2498 -- If entity is constant, it may be the result of expanding
2499 -- a check. We must verify that its declaration appears
2500 -- before the object in question, else we also reject the
2501 -- address clause.
2503 elsif Ekind (Ent) = E_Constant
2504 and then In_Same_Source_Unit (Ent, U_Ent)
2505 and then Sloc (Ent) > Loc_U_Ent
2506 then
2507 Error_Msg_NE
2508 ("invalid address clause for initialized object &!",
2509 Nod, U_Ent);
2510 end if;
2512 return;
2513 end if;
2515 -- Otherwise look at the identifier and see if it is OK
2517 if Ekind (Ent) = E_Named_Integer
2518 or else
2519 Ekind (Ent) = E_Named_Real
2520 or else
2521 Is_Type (Ent)
2522 then
2523 return;
2525 elsif
2526 Ekind (Ent) = E_Constant
2527 or else
2528 Ekind (Ent) = E_In_Parameter
2529 then
2530 -- This is the case where we must have Ent defined
2531 -- before U_Ent. Clearly if they are in different
2532 -- units this requirement is met since the unit
2533 -- containing Ent is already processed.
2535 if not In_Same_Source_Unit (Ent, U_Ent) then
2536 return;
2538 -- Otherwise location of Ent must be before the
2539 -- location of U_Ent, that's what prior defined means.
2541 elsif Sloc (Ent) < Loc_U_Ent then
2542 return;
2544 else
2545 Error_Msg_NE
2546 ("invalid address clause for initialized object &!",
2547 Nod, U_Ent);
2548 Error_Msg_Name_1 := Chars (Ent);
2549 Error_Msg_Name_2 := Chars (U_Ent);
2550 Error_Msg_N
2551 ("\% must be defined before % ('R'M 13.1(22))!",
2552 Nod);
2553 end if;
2555 elsif Nkind (Original_Node (Nod)) = N_Function_Call then
2556 Check_Expr_Constants (Original_Node (Nod));
2558 else
2559 Error_Msg_NE
2560 ("invalid address clause for initialized object &!",
2561 Nod, U_Ent);
2563 if Comes_From_Source (Ent) then
2564 Error_Msg_Name_1 := Chars (Ent);
2565 Error_Msg_N
2566 ("\reference to variable% not allowed"
2567 & " ('R'M 13.1(22))!", Nod);
2568 else
2569 Error_Msg_N
2570 ("non-static expression not allowed"
2571 & " ('R'M 13.1(22))!", Nod);
2572 end if;
2573 end if;
2575 when N_Integer_Literal =>
2577 -- If this is a rewritten unchecked conversion, in a system
2578 -- where Address is an integer type, always use the base type
2579 -- for a literal value. This is user-friendly and prevents
2580 -- order-of-elaboration issues with instances of unchecked
2581 -- conversion.
2583 if Nkind (Original_Node (Nod)) = N_Function_Call then
2584 Set_Etype (Nod, Base_Type (Etype (Nod)));
2585 end if;
2587 when N_Real_Literal |
2588 N_String_Literal |
2589 N_Character_Literal =>
2590 return;
2592 when N_Range =>
2593 Check_Expr_Constants (Low_Bound (Nod));
2594 Check_Expr_Constants (High_Bound (Nod));
2596 when N_Explicit_Dereference =>
2597 Check_Expr_Constants (Prefix (Nod));
2599 when N_Indexed_Component =>
2600 Check_Expr_Constants (Prefix (Nod));
2601 Check_List_Constants (Expressions (Nod));
2603 when N_Slice =>
2604 Check_Expr_Constants (Prefix (Nod));
2605 Check_Expr_Constants (Discrete_Range (Nod));
2607 when N_Selected_Component =>
2608 Check_Expr_Constants (Prefix (Nod));
2610 when N_Attribute_Reference =>
2611 if Attribute_Name (Nod) = Name_Address
2612 or else
2613 Attribute_Name (Nod) = Name_Access
2614 or else
2615 Attribute_Name (Nod) = Name_Unchecked_Access
2616 or else
2617 Attribute_Name (Nod) = Name_Unrestricted_Access
2618 then
2619 Check_At_Constant_Address (Prefix (Nod));
2621 else
2622 Check_Expr_Constants (Prefix (Nod));
2623 Check_List_Constants (Expressions (Nod));
2624 end if;
2626 when N_Aggregate =>
2627 Check_List_Constants (Component_Associations (Nod));
2628 Check_List_Constants (Expressions (Nod));
2630 when N_Component_Association =>
2631 Check_Expr_Constants (Expression (Nod));
2633 when N_Extension_Aggregate =>
2634 Check_Expr_Constants (Ancestor_Part (Nod));
2635 Check_List_Constants (Component_Associations (Nod));
2636 Check_List_Constants (Expressions (Nod));
2638 when N_Null =>
2639 return;
2641 when N_Binary_Op | N_And_Then | N_Or_Else | N_Membership_Test =>
2642 Check_Expr_Constants (Left_Opnd (Nod));
2643 Check_Expr_Constants (Right_Opnd (Nod));
2645 when N_Unary_Op =>
2646 Check_Expr_Constants (Right_Opnd (Nod));
2648 when N_Type_Conversion |
2649 N_Qualified_Expression |
2650 N_Allocator =>
2651 Check_Expr_Constants (Expression (Nod));
2653 when N_Unchecked_Type_Conversion =>
2654 Check_Expr_Constants (Expression (Nod));
2656 -- If this is a rewritten unchecked conversion, subtypes
2657 -- in this node are those created within the instance.
2658 -- To avoid order of elaboration issues, replace them
2659 -- with their base types. Note that address clauses can
2660 -- cause order of elaboration problems because they are
2661 -- elaborated by the back-end at the point of definition,
2662 -- and may mention entities declared in between (as long
2663 -- as everything is static). It is user-friendly to allow
2664 -- unchecked conversions in this context.
2666 if Nkind (Original_Node (Nod)) = N_Function_Call then
2667 Set_Etype (Expression (Nod),
2668 Base_Type (Etype (Expression (Nod))));
2669 Set_Etype (Nod, Base_Type (Etype (Nod)));
2670 end if;
2672 when N_Function_Call =>
2673 if not Is_Pure (Entity (Name (Nod))) then
2674 Error_Msg_NE
2675 ("invalid address clause for initialized object &!",
2676 Nod, U_Ent);
2678 Error_Msg_NE
2679 ("\function & is not pure ('R'M 13.1(22))!",
2680 Nod, Entity (Name (Nod)));
2682 else
2683 Check_List_Constants (Parameter_Associations (Nod));
2684 end if;
2686 when N_Parameter_Association =>
2687 Check_Expr_Constants (Explicit_Actual_Parameter (Nod));
2689 when others =>
2690 Error_Msg_NE
2691 ("invalid address clause for initialized object &!",
2692 Nod, U_Ent);
2693 Error_Msg_NE
2694 ("\must be constant defined before& ('R'M 13.1(22))!",
2695 Nod, U_Ent);
2696 end case;
2697 end Check_Expr_Constants;
2699 --------------------------
2700 -- Check_List_Constants --
2701 --------------------------
2703 procedure Check_List_Constants (Lst : List_Id) is
2704 Nod1 : Node_Id;
2706 begin
2707 if Present (Lst) then
2708 Nod1 := First (Lst);
2709 while Present (Nod1) loop
2710 Check_Expr_Constants (Nod1);
2711 Next (Nod1);
2712 end loop;
2713 end if;
2714 end Check_List_Constants;
2716 -- Start of processing for Check_Constant_Address_Clause
2718 begin
2719 Check_Expr_Constants (Expr);
2720 end Check_Constant_Address_Clause;
2722 ----------------
2723 -- Check_Size --
2724 ----------------
2726 procedure Check_Size
2727 (N : Node_Id;
2728 T : Entity_Id;
2729 Siz : Uint;
2730 Biased : out Boolean)
2732 UT : constant Entity_Id := Underlying_Type (T);
2733 M : Uint;
2735 begin
2736 Biased := False;
2738 -- Dismiss cases for generic types or types with previous errors
2740 if No (UT)
2741 or else UT = Any_Type
2742 or else Is_Generic_Type (UT)
2743 or else Is_Generic_Type (Root_Type (UT))
2744 then
2745 return;
2747 -- Check case of bit packed array
2749 elsif Is_Array_Type (UT)
2750 and then Known_Static_Component_Size (UT)
2751 and then Is_Bit_Packed_Array (UT)
2752 then
2753 declare
2754 Asiz : Uint;
2755 Indx : Node_Id;
2756 Ityp : Entity_Id;
2758 begin
2759 Asiz := Component_Size (UT);
2760 Indx := First_Index (UT);
2761 loop
2762 Ityp := Etype (Indx);
2764 -- If non-static bound, then we are not in the business of
2765 -- trying to check the length, and indeed an error will be
2766 -- issued elsewhere, since sizes of non-static array types
2767 -- cannot be set implicitly or explicitly.
2769 if not Is_Static_Subtype (Ityp) then
2770 return;
2771 end if;
2773 -- Otherwise accumulate next dimension
2775 Asiz := Asiz * (Expr_Value (Type_High_Bound (Ityp)) -
2776 Expr_Value (Type_Low_Bound (Ityp)) +
2777 Uint_1);
2779 Next_Index (Indx);
2780 exit when No (Indx);
2781 end loop;
2783 if Asiz <= Siz then
2784 return;
2785 else
2786 Error_Msg_Uint_1 := Asiz;
2787 Error_Msg_NE
2788 ("size for& too small, minimum allowed is ^", N, T);
2789 Set_Esize (T, Asiz);
2790 Set_RM_Size (T, Asiz);
2791 end if;
2792 end;
2794 -- All other composite types are ignored
2796 elsif Is_Composite_Type (UT) then
2797 return;
2799 -- For fixed-point types, don't check minimum if type is not frozen,
2800 -- since we don't know all the characteristics of the type that can
2801 -- affect the size (e.g. a specified small) till freeze time.
2803 elsif Is_Fixed_Point_Type (UT)
2804 and then not Is_Frozen (UT)
2805 then
2806 null;
2808 -- Cases for which a minimum check is required
2810 else
2811 -- Ignore if specified size is correct for the type
2813 if Known_Esize (UT) and then Siz = Esize (UT) then
2814 return;
2815 end if;
2817 -- Otherwise get minimum size
2819 M := UI_From_Int (Minimum_Size (UT));
2821 if Siz < M then
2823 -- Size is less than minimum size, but one possibility remains
2824 -- that we can manage with the new size if we bias the type
2826 M := UI_From_Int (Minimum_Size (UT, Biased => True));
2828 if Siz < M then
2829 Error_Msg_Uint_1 := M;
2830 Error_Msg_NE
2831 ("size for& too small, minimum allowed is ^", N, T);
2832 Set_Esize (T, M);
2833 Set_RM_Size (T, M);
2834 else
2835 Biased := True;
2836 end if;
2837 end if;
2838 end if;
2839 end Check_Size;
2841 -------------------------
2842 -- Get_Alignment_Value --
2843 -------------------------
2845 function Get_Alignment_Value (Expr : Node_Id) return Uint is
2846 Align : constant Uint := Static_Integer (Expr);
2848 begin
2849 if Align = No_Uint then
2850 return No_Uint;
2852 elsif Align <= 0 then
2853 Error_Msg_N ("alignment value must be positive", Expr);
2854 return No_Uint;
2856 else
2857 for J in Int range 0 .. 64 loop
2858 declare
2859 M : constant Uint := Uint_2 ** J;
2861 begin
2862 exit when M = Align;
2864 if M > Align then
2865 Error_Msg_N
2866 ("alignment value must be power of 2", Expr);
2867 return No_Uint;
2868 end if;
2869 end;
2870 end loop;
2872 return Align;
2873 end if;
2874 end Get_Alignment_Value;
2876 ----------------
2877 -- Initialize --
2878 ----------------
2880 procedure Initialize is
2881 begin
2882 Unchecked_Conversions.Init;
2883 end Initialize;
2885 -------------------------
2886 -- Is_Operational_Item --
2887 -------------------------
2889 function Is_Operational_Item (N : Node_Id) return Boolean is
2890 begin
2891 if Nkind (N) /= N_Attribute_Definition_Clause then
2892 return False;
2893 else
2894 declare
2895 Id : constant Attribute_Id := Get_Attribute_Id (Chars (N));
2897 begin
2898 return Id = Attribute_Input
2899 or else Id = Attribute_Output
2900 or else Id = Attribute_Read
2901 or else Id = Attribute_Write
2902 or else Id = Attribute_External_Tag;
2903 end;
2904 end if;
2905 end Is_Operational_Item;
2907 --------------------------------------
2908 -- Mark_Aliased_Address_As_Volatile --
2909 --------------------------------------
2911 procedure Mark_Aliased_Address_As_Volatile (N : Node_Id) is
2912 Ent : constant Entity_Id := Address_Aliased_Entity (N);
2914 begin
2915 if Present (Ent) then
2916 Set_Treat_As_Volatile (Ent);
2917 end if;
2918 end Mark_Aliased_Address_As_Volatile;
2920 ------------------
2921 -- Minimum_Size --
2922 ------------------
2924 function Minimum_Size
2925 (T : Entity_Id;
2926 Biased : Boolean := False) return Nat
2928 Lo : Uint := No_Uint;
2929 Hi : Uint := No_Uint;
2930 LoR : Ureal := No_Ureal;
2931 HiR : Ureal := No_Ureal;
2932 LoSet : Boolean := False;
2933 HiSet : Boolean := False;
2934 B : Uint;
2935 S : Nat;
2936 Ancest : Entity_Id;
2937 R_Typ : constant Entity_Id := Root_Type (T);
2939 begin
2940 -- If bad type, return 0
2942 if T = Any_Type then
2943 return 0;
2945 -- For generic types, just return zero. There cannot be any legitimate
2946 -- need to know such a size, but this routine may be called with a
2947 -- generic type as part of normal processing.
2949 elsif Is_Generic_Type (R_Typ)
2950 or else R_Typ = Any_Type
2951 then
2952 return 0;
2954 -- Access types. Normally an access type cannot have a size smaller
2955 -- than the size of System.Address. The exception is on VMS, where
2956 -- we have short and long addresses, and it is possible for an access
2957 -- type to have a short address size (and thus be less than the size
2958 -- of System.Address itself). We simply skip the check for VMS, and
2959 -- leave the back end to do the check.
2961 elsif Is_Access_Type (T) then
2962 if OpenVMS_On_Target then
2963 return 0;
2964 else
2965 return System_Address_Size;
2966 end if;
2968 -- Floating-point types
2970 elsif Is_Floating_Point_Type (T) then
2971 return UI_To_Int (Esize (R_Typ));
2973 -- Discrete types
2975 elsif Is_Discrete_Type (T) then
2977 -- The following loop is looking for the nearest compile time
2978 -- known bounds following the ancestor subtype chain. The idea
2979 -- is to find the most restrictive known bounds information.
2981 Ancest := T;
2982 loop
2983 if Ancest = Any_Type or else Etype (Ancest) = Any_Type then
2984 return 0;
2985 end if;
2987 if not LoSet then
2988 if Compile_Time_Known_Value (Type_Low_Bound (Ancest)) then
2989 Lo := Expr_Rep_Value (Type_Low_Bound (Ancest));
2990 LoSet := True;
2991 exit when HiSet;
2992 end if;
2993 end if;
2995 if not HiSet then
2996 if Compile_Time_Known_Value (Type_High_Bound (Ancest)) then
2997 Hi := Expr_Rep_Value (Type_High_Bound (Ancest));
2998 HiSet := True;
2999 exit when LoSet;
3000 end if;
3001 end if;
3003 Ancest := Ancestor_Subtype (Ancest);
3005 if No (Ancest) then
3006 Ancest := Base_Type (T);
3008 if Is_Generic_Type (Ancest) then
3009 return 0;
3010 end if;
3011 end if;
3012 end loop;
3014 -- Fixed-point types. We can't simply use Expr_Value to get the
3015 -- Corresponding_Integer_Value values of the bounds, since these
3016 -- do not get set till the type is frozen, and this routine can
3017 -- be called before the type is frozen. Similarly the test for
3018 -- bounds being static needs to include the case where we have
3019 -- unanalyzed real literals for the same reason.
3021 elsif Is_Fixed_Point_Type (T) then
3023 -- The following loop is looking for the nearest compile time
3024 -- known bounds following the ancestor subtype chain. The idea
3025 -- is to find the most restrictive known bounds information.
3027 Ancest := T;
3028 loop
3029 if Ancest = Any_Type or else Etype (Ancest) = Any_Type then
3030 return 0;
3031 end if;
3033 if not LoSet then
3034 if Nkind (Type_Low_Bound (Ancest)) = N_Real_Literal
3035 or else Compile_Time_Known_Value (Type_Low_Bound (Ancest))
3036 then
3037 LoR := Expr_Value_R (Type_Low_Bound (Ancest));
3038 LoSet := True;
3039 exit when HiSet;
3040 end if;
3041 end if;
3043 if not HiSet then
3044 if Nkind (Type_High_Bound (Ancest)) = N_Real_Literal
3045 or else Compile_Time_Known_Value (Type_High_Bound (Ancest))
3046 then
3047 HiR := Expr_Value_R (Type_High_Bound (Ancest));
3048 HiSet := True;
3049 exit when LoSet;
3050 end if;
3051 end if;
3053 Ancest := Ancestor_Subtype (Ancest);
3055 if No (Ancest) then
3056 Ancest := Base_Type (T);
3058 if Is_Generic_Type (Ancest) then
3059 return 0;
3060 end if;
3061 end if;
3062 end loop;
3064 Lo := UR_To_Uint (LoR / Small_Value (T));
3065 Hi := UR_To_Uint (HiR / Small_Value (T));
3067 -- No other types allowed
3069 else
3070 raise Program_Error;
3071 end if;
3073 -- Fall through with Hi and Lo set. Deal with biased case
3075 if (Biased and then not Is_Fixed_Point_Type (T))
3076 or else Has_Biased_Representation (T)
3077 then
3078 Hi := Hi - Lo;
3079 Lo := Uint_0;
3080 end if;
3082 -- Signed case. Note that we consider types like range 1 .. -1 to be
3083 -- signed for the purpose of computing the size, since the bounds
3084 -- have to be accomodated in the base type.
3086 if Lo < 0 or else Hi < 0 then
3087 S := 1;
3088 B := Uint_1;
3090 -- S = size, B = 2 ** (size - 1) (can accommodate -B .. +(B - 1))
3091 -- Note that we accommodate the case where the bounds cross. This
3092 -- can happen either because of the way the bounds are declared
3093 -- or because of the algorithm in Freeze_Fixed_Point_Type.
3095 while Lo < -B
3096 or else Hi < -B
3097 or else Lo >= B
3098 or else Hi >= B
3099 loop
3100 B := Uint_2 ** S;
3101 S := S + 1;
3102 end loop;
3104 -- Unsigned case
3106 else
3107 -- If both bounds are positive, make sure that both are represen-
3108 -- table in the case where the bounds are crossed. This can happen
3109 -- either because of the way the bounds are declared, or because of
3110 -- the algorithm in Freeze_Fixed_Point_Type.
3112 if Lo > Hi then
3113 Hi := Lo;
3114 end if;
3116 -- S = size, (can accommodate 0 .. (2**size - 1))
3118 S := 0;
3119 while Hi >= Uint_2 ** S loop
3120 S := S + 1;
3121 end loop;
3122 end if;
3124 return S;
3125 end Minimum_Size;
3127 ---------------------------
3128 -- New_Stream_Subprogram --
3129 ---------------------------
3131 procedure New_Stream_Subprogram
3132 (N : Node_Id;
3133 Ent : Entity_Id;
3134 Subp : Entity_Id;
3135 Nam : TSS_Name_Type)
3137 Loc : constant Source_Ptr := Sloc (N);
3138 Sname : constant Name_Id := Make_TSS_Name (Base_Type (Ent), Nam);
3139 Subp_Id : Entity_Id;
3140 Subp_Decl : Node_Id;
3141 F : Entity_Id;
3142 Etyp : Entity_Id;
3144 Defer_Declaration : constant Boolean :=
3145 Is_Tagged_Type (Ent) or else Is_Private_Type (Ent);
3146 -- For a tagged type, there is a declaration for each stream attribute
3147 -- at the freeze point, and we must generate only a completion of this
3148 -- declaration. We do the same for private types, because the full view
3149 -- might be tagged. Otherwise we generate a declaration at the point of
3150 -- the attribute definition clause.
3152 function Build_Spec return Node_Id;
3153 -- Used for declaration and renaming declaration, so that this is
3154 -- treated as a renaming_as_body.
3156 ----------------
3157 -- Build_Spec --
3158 ----------------
3160 function Build_Spec return Node_Id is
3161 Out_P : constant Boolean := (Nam = TSS_Stream_Read);
3162 Formals : List_Id;
3163 Spec : Node_Id;
3164 T_Ref : constant Node_Id := New_Reference_To (Etyp, Loc);
3166 begin
3167 Subp_Id := Make_Defining_Identifier (Loc, Sname);
3169 -- S : access Root_Stream_Type'Class
3171 Formals := New_List (
3172 Make_Parameter_Specification (Loc,
3173 Defining_Identifier =>
3174 Make_Defining_Identifier (Loc, Name_S),
3175 Parameter_Type =>
3176 Make_Access_Definition (Loc,
3177 Subtype_Mark =>
3178 New_Reference_To (
3179 Designated_Type (Etype (F)), Loc))));
3181 if Nam = TSS_Stream_Input then
3182 Spec := Make_Function_Specification (Loc,
3183 Defining_Unit_Name => Subp_Id,
3184 Parameter_Specifications => Formals,
3185 Result_Definition => T_Ref);
3186 else
3187 -- V : [out] T
3189 Append_To (Formals,
3190 Make_Parameter_Specification (Loc,
3191 Defining_Identifier => Make_Defining_Identifier (Loc, Name_V),
3192 Out_Present => Out_P,
3193 Parameter_Type => T_Ref));
3195 Spec := Make_Procedure_Specification (Loc,
3196 Defining_Unit_Name => Subp_Id,
3197 Parameter_Specifications => Formals);
3198 end if;
3200 return Spec;
3201 end Build_Spec;
3203 -- Start of processing for New_Stream_Subprogram
3205 begin
3206 F := First_Formal (Subp);
3208 if Ekind (Subp) = E_Procedure then
3209 Etyp := Etype (Next_Formal (F));
3210 else
3211 Etyp := Etype (Subp);
3212 end if;
3214 -- Prepare subprogram declaration and insert it as an action on the
3215 -- clause node. The visibility for this entity is used to test for
3216 -- visibility of the attribute definition clause (in the sense of
3217 -- 8.3(23) as amended by AI-195).
3219 if not Defer_Declaration then
3220 Subp_Decl :=
3221 Make_Subprogram_Declaration (Loc,
3222 Specification => Build_Spec);
3224 -- For a tagged type, there is always a visible declaration for each
3225 -- stream TSS (it is a predefined primitive operation), and the for the
3226 -- completion of this declaration occurs at the freeze point, which is
3227 -- not always visible at places where the attribute definition clause is
3228 -- visible. So, we create a dummy entity here for the purpose of
3229 -- tracking the visibility of the attribute definition clause itself.
3231 else
3232 Subp_Id :=
3233 Make_Defining_Identifier (Loc,
3234 Chars => New_External_Name (Sname, 'V'));
3235 Subp_Decl :=
3236 Make_Object_Declaration (Loc,
3237 Defining_Identifier => Subp_Id,
3238 Object_Definition => New_Occurrence_Of (Standard_Boolean, Loc));
3239 end if;
3241 Insert_Action (N, Subp_Decl);
3242 Set_Entity (N, Subp_Id);
3244 Subp_Decl :=
3245 Make_Subprogram_Renaming_Declaration (Loc,
3246 Specification => Build_Spec,
3247 Name => New_Reference_To (Subp, Loc));
3249 if Defer_Declaration then
3250 Set_TSS (Base_Type (Ent), Subp_Id);
3251 else
3252 Insert_Action (N, Subp_Decl);
3253 Copy_TSS (Subp_Id, Base_Type (Ent));
3254 end if;
3255 end New_Stream_Subprogram;
3257 ------------------------
3258 -- Rep_Item_Too_Early --
3259 ------------------------
3261 function Rep_Item_Too_Early (T : Entity_Id; N : Node_Id) return Boolean is
3262 begin
3263 -- Cannot apply non-operational rep items to generic types
3265 if Is_Operational_Item (N) then
3266 return False;
3268 elsif Is_Type (T)
3269 and then Is_Generic_Type (Root_Type (T))
3270 then
3271 Error_Msg_N
3272 ("representation item not allowed for generic type", N);
3273 return True;
3274 end if;
3276 -- Otherwise check for incompleted type
3278 if Is_Incomplete_Or_Private_Type (T)
3279 and then No (Underlying_Type (T))
3280 then
3281 Error_Msg_N
3282 ("representation item must be after full type declaration", N);
3283 return True;
3285 -- If the type has incompleted components, a representation clause is
3286 -- illegal but stream attributes and Convention pragmas are correct.
3288 elsif Has_Private_Component (T) then
3289 if Nkind (N) = N_Pragma then
3290 return False;
3291 else
3292 Error_Msg_N
3293 ("representation item must appear after type is fully defined",
3295 return True;
3296 end if;
3297 else
3298 return False;
3299 end if;
3300 end Rep_Item_Too_Early;
3302 -----------------------
3303 -- Rep_Item_Too_Late --
3304 -----------------------
3306 function Rep_Item_Too_Late
3307 (T : Entity_Id;
3308 N : Node_Id;
3309 FOnly : Boolean := False) return Boolean
3311 S : Entity_Id;
3312 Parent_Type : Entity_Id;
3314 procedure Too_Late;
3315 -- Output the too late message. Note that this is not considered a
3316 -- serious error, since the effect is simply that we ignore the
3317 -- representation clause in this case.
3319 --------------
3320 -- Too_Late --
3321 --------------
3323 procedure Too_Late is
3324 begin
3325 Error_Msg_N ("|representation item appears too late!", N);
3326 end Too_Late;
3328 -- Start of processing for Rep_Item_Too_Late
3330 begin
3331 -- First make sure entity is not frozen (RM 13.1(9)). Exclude imported
3332 -- types, which may be frozen if they appear in a representation clause
3333 -- for a local type.
3335 if Is_Frozen (T)
3336 and then not From_With_Type (T)
3337 then
3338 Too_Late;
3339 S := First_Subtype (T);
3341 if Present (Freeze_Node (S)) then
3342 Error_Msg_NE
3343 ("?no more representation items for }", Freeze_Node (S), S);
3344 end if;
3346 return True;
3348 -- Check for case of non-tagged derived type whose parent either has
3349 -- primitive operations, or is a by reference type (RM 13.1(10)).
3351 elsif Is_Type (T)
3352 and then not FOnly
3353 and then Is_Derived_Type (T)
3354 and then not Is_Tagged_Type (T)
3355 then
3356 Parent_Type := Etype (Base_Type (T));
3358 if Has_Primitive_Operations (Parent_Type) then
3359 Too_Late;
3360 Error_Msg_NE
3361 ("primitive operations already defined for&!", N, Parent_Type);
3362 return True;
3364 elsif Is_By_Reference_Type (Parent_Type) then
3365 Too_Late;
3366 Error_Msg_NE
3367 ("parent type & is a by reference type!", N, Parent_Type);
3368 return True;
3369 end if;
3370 end if;
3372 -- No error, link item into head of chain of rep items for the entity
3374 Record_Rep_Item (T, N);
3375 return False;
3376 end Rep_Item_Too_Late;
3378 -------------------------
3379 -- Same_Representation --
3380 -------------------------
3382 function Same_Representation (Typ1, Typ2 : Entity_Id) return Boolean is
3383 T1 : constant Entity_Id := Underlying_Type (Typ1);
3384 T2 : constant Entity_Id := Underlying_Type (Typ2);
3386 begin
3387 -- A quick check, if base types are the same, then we definitely have
3388 -- the same representation, because the subtype specific representation
3389 -- attributes (Size and Alignment) do not affect representation from
3390 -- the point of view of this test.
3392 if Base_Type (T1) = Base_Type (T2) then
3393 return True;
3395 elsif Is_Private_Type (Base_Type (T2))
3396 and then Base_Type (T1) = Full_View (Base_Type (T2))
3397 then
3398 return True;
3399 end if;
3401 -- Tagged types never have differing representations
3403 if Is_Tagged_Type (T1) then
3404 return True;
3405 end if;
3407 -- Representations are definitely different if conventions differ
3409 if Convention (T1) /= Convention (T2) then
3410 return False;
3411 end if;
3413 -- Representations are different if component alignments differ
3415 if (Is_Record_Type (T1) or else Is_Array_Type (T1))
3416 and then
3417 (Is_Record_Type (T2) or else Is_Array_Type (T2))
3418 and then Component_Alignment (T1) /= Component_Alignment (T2)
3419 then
3420 return False;
3421 end if;
3423 -- For arrays, the only real issue is component size. If we know the
3424 -- component size for both arrays, and it is the same, then that's
3425 -- good enough to know we don't have a change of representation.
3427 if Is_Array_Type (T1) then
3428 if Known_Component_Size (T1)
3429 and then Known_Component_Size (T2)
3430 and then Component_Size (T1) = Component_Size (T2)
3431 then
3432 return True;
3433 end if;
3434 end if;
3436 -- Types definitely have same representation if neither has non-standard
3437 -- representation since default representations are always consistent.
3438 -- If only one has non-standard representation, and the other does not,
3439 -- then we consider that they do not have the same representation. They
3440 -- might, but there is no way of telling early enough.
3442 if Has_Non_Standard_Rep (T1) then
3443 if not Has_Non_Standard_Rep (T2) then
3444 return False;
3445 end if;
3446 else
3447 return not Has_Non_Standard_Rep (T2);
3448 end if;
3450 -- Here the two types both have non-standard representation, and we
3451 -- need to determine if they have the same non-standard representation
3453 -- For arrays, we simply need to test if the component sizes are the
3454 -- same. Pragma Pack is reflected in modified component sizes, so this
3455 -- check also deals with pragma Pack.
3457 if Is_Array_Type (T1) then
3458 return Component_Size (T1) = Component_Size (T2);
3460 -- Tagged types always have the same representation, because it is not
3461 -- possible to specify different representations for common fields.
3463 elsif Is_Tagged_Type (T1) then
3464 return True;
3466 -- Case of record types
3468 elsif Is_Record_Type (T1) then
3470 -- Packed status must conform
3472 if Is_Packed (T1) /= Is_Packed (T2) then
3473 return False;
3475 -- Otherwise we must check components. Typ2 maybe a constrained
3476 -- subtype with fewer components, so we compare the components
3477 -- of the base types.
3479 else
3480 Record_Case : declare
3481 CD1, CD2 : Entity_Id;
3483 function Same_Rep return Boolean;
3484 -- CD1 and CD2 are either components or discriminants. This
3485 -- function tests whether the two have the same representation
3487 --------------
3488 -- Same_Rep --
3489 --------------
3491 function Same_Rep return Boolean is
3492 begin
3493 if No (Component_Clause (CD1)) then
3494 return No (Component_Clause (CD2));
3496 else
3497 return
3498 Present (Component_Clause (CD2))
3499 and then
3500 Component_Bit_Offset (CD1) = Component_Bit_Offset (CD2)
3501 and then
3502 Esize (CD1) = Esize (CD2);
3503 end if;
3504 end Same_Rep;
3506 -- Start processing for Record_Case
3508 begin
3509 if Has_Discriminants (T1) then
3510 CD1 := First_Discriminant (T1);
3511 CD2 := First_Discriminant (T2);
3513 -- The number of discriminants may be different if the
3514 -- derived type has fewer (constrained by values). The
3515 -- invisible discriminants retain the representation of
3516 -- the original, so the discrepancy does not per se
3517 -- indicate a different representation.
3519 while Present (CD1)
3520 and then Present (CD2)
3521 loop
3522 if not Same_Rep then
3523 return False;
3524 else
3525 Next_Discriminant (CD1);
3526 Next_Discriminant (CD2);
3527 end if;
3528 end loop;
3529 end if;
3531 CD1 := First_Component (Underlying_Type (Base_Type (T1)));
3532 CD2 := First_Component (Underlying_Type (Base_Type (T2)));
3534 while Present (CD1) loop
3535 if not Same_Rep then
3536 return False;
3537 else
3538 Next_Component (CD1);
3539 Next_Component (CD2);
3540 end if;
3541 end loop;
3543 return True;
3544 end Record_Case;
3545 end if;
3547 -- For enumeration types, we must check each literal to see if the
3548 -- representation is the same. Note that we do not permit enumeration
3549 -- reprsentation clauses for Character and Wide_Character, so these
3550 -- cases were already dealt with.
3552 elsif Is_Enumeration_Type (T1) then
3554 Enumeration_Case : declare
3555 L1, L2 : Entity_Id;
3557 begin
3558 L1 := First_Literal (T1);
3559 L2 := First_Literal (T2);
3561 while Present (L1) loop
3562 if Enumeration_Rep (L1) /= Enumeration_Rep (L2) then
3563 return False;
3564 else
3565 Next_Literal (L1);
3566 Next_Literal (L2);
3567 end if;
3568 end loop;
3570 return True;
3572 end Enumeration_Case;
3574 -- Any other types have the same representation for these purposes
3576 else
3577 return True;
3578 end if;
3579 end Same_Representation;
3581 --------------------
3582 -- Set_Enum_Esize --
3583 --------------------
3585 procedure Set_Enum_Esize (T : Entity_Id) is
3586 Lo : Uint;
3587 Hi : Uint;
3588 Sz : Nat;
3590 begin
3591 Init_Alignment (T);
3593 -- Find the minimum standard size (8,16,32,64) that fits
3595 Lo := Enumeration_Rep (Entity (Type_Low_Bound (T)));
3596 Hi := Enumeration_Rep (Entity (Type_High_Bound (T)));
3598 if Lo < 0 then
3599 if Lo >= -Uint_2**07 and then Hi < Uint_2**07 then
3600 Sz := Standard_Character_Size; -- May be > 8 on some targets
3602 elsif Lo >= -Uint_2**15 and then Hi < Uint_2**15 then
3603 Sz := 16;
3605 elsif Lo >= -Uint_2**31 and then Hi < Uint_2**31 then
3606 Sz := 32;
3608 else pragma Assert (Lo >= -Uint_2**63 and then Hi < Uint_2**63);
3609 Sz := 64;
3610 end if;
3612 else
3613 if Hi < Uint_2**08 then
3614 Sz := Standard_Character_Size; -- May be > 8 on some targets
3616 elsif Hi < Uint_2**16 then
3617 Sz := 16;
3619 elsif Hi < Uint_2**32 then
3620 Sz := 32;
3622 else pragma Assert (Hi < Uint_2**63);
3623 Sz := 64;
3624 end if;
3625 end if;
3627 -- That minimum is the proper size unless we have a foreign convention
3628 -- and the size required is 32 or less, in which case we bump the size
3629 -- up to 32. This is required for C and C++ and seems reasonable for
3630 -- all other foreign conventions.
3632 if Has_Foreign_Convention (T)
3633 and then Esize (T) < Standard_Integer_Size
3634 then
3635 Init_Esize (T, Standard_Integer_Size);
3637 else
3638 Init_Esize (T, Sz);
3639 end if;
3640 end Set_Enum_Esize;
3642 -----------------------------------
3643 -- Validate_Unchecked_Conversion --
3644 -----------------------------------
3646 procedure Validate_Unchecked_Conversion
3647 (N : Node_Id;
3648 Act_Unit : Entity_Id)
3650 Source : Entity_Id;
3651 Target : Entity_Id;
3652 Vnode : Node_Id;
3654 begin
3655 -- Obtain source and target types. Note that we call Ancestor_Subtype
3656 -- here because the processing for generic instantiation always makes
3657 -- subtypes, and we want the original frozen actual types.
3659 -- If we are dealing with private types, then do the check on their
3660 -- fully declared counterparts if the full declarations have been
3661 -- encountered (they don't have to be visible, but they must exist!)
3663 Source := Ancestor_Subtype (Etype (First_Formal (Act_Unit)));
3665 if Is_Private_Type (Source)
3666 and then Present (Underlying_Type (Source))
3667 then
3668 Source := Underlying_Type (Source);
3669 end if;
3671 Target := Ancestor_Subtype (Etype (Act_Unit));
3673 -- If either type is generic, the instantiation happens within a
3674 -- generic unit, and there is nothing to check. The proper check
3675 -- will happen when the enclosing generic is instantiated.
3677 if Is_Generic_Type (Source) or else Is_Generic_Type (Target) then
3678 return;
3679 end if;
3681 if Is_Private_Type (Target)
3682 and then Present (Underlying_Type (Target))
3683 then
3684 Target := Underlying_Type (Target);
3685 end if;
3687 -- Source may be unconstrained array, but not target
3689 if Is_Array_Type (Target)
3690 and then not Is_Constrained (Target)
3691 then
3692 Error_Msg_N
3693 ("unchecked conversion to unconstrained array not allowed", N);
3694 return;
3695 end if;
3697 -- Make entry in unchecked conversion table for later processing
3698 -- by Validate_Unchecked_Conversions, which will check sizes and
3699 -- alignments (using values set by the back-end where possible).
3700 -- This is only done if the appropriate warning is active
3702 if Warn_On_Unchecked_Conversion then
3703 Unchecked_Conversions.Append
3704 (New_Val => UC_Entry'
3705 (Enode => N,
3706 Source => Source,
3707 Target => Target));
3709 -- If both sizes are known statically now, then back end annotation
3710 -- is not required to do a proper check but if either size is not
3711 -- known statically, then we need the annotation.
3713 if Known_Static_RM_Size (Source)
3714 and then Known_Static_RM_Size (Target)
3715 then
3716 null;
3717 else
3718 Back_Annotate_Rep_Info := True;
3719 end if;
3720 end if;
3722 -- If unchecked conversion to access type, and access type is
3723 -- declared in the same unit as the unchecked conversion, then
3724 -- set the No_Strict_Aliasing flag (no strict aliasing is
3725 -- implicit in this situation).
3727 if Is_Access_Type (Target) and then
3728 In_Same_Source_Unit (Target, N)
3729 then
3730 Set_No_Strict_Aliasing (Implementation_Base_Type (Target));
3731 end if;
3733 -- Generate N_Validate_Unchecked_Conversion node for back end in
3734 -- case the back end needs to perform special validation checks.
3736 -- Shouldn't this be in exp_ch13, since the check only gets done
3737 -- if we have full expansion and the back end is called ???
3739 Vnode :=
3740 Make_Validate_Unchecked_Conversion (Sloc (N));
3741 Set_Source_Type (Vnode, Source);
3742 Set_Target_Type (Vnode, Target);
3744 -- If the unchecked conversion node is in a list, just insert before
3745 -- it. If not we have some strange case, not worth bothering about.
3747 if Is_List_Member (N) then
3748 Insert_After (N, Vnode);
3749 end if;
3750 end Validate_Unchecked_Conversion;
3752 ------------------------------------
3753 -- Validate_Unchecked_Conversions --
3754 ------------------------------------
3756 procedure Validate_Unchecked_Conversions is
3757 begin
3758 for N in Unchecked_Conversions.First .. Unchecked_Conversions.Last loop
3759 declare
3760 T : UC_Entry renames Unchecked_Conversions.Table (N);
3762 Enode : constant Node_Id := T.Enode;
3763 Source : constant Entity_Id := T.Source;
3764 Target : constant Entity_Id := T.Target;
3766 Source_Siz : Uint;
3767 Target_Siz : Uint;
3769 begin
3770 -- This validation check, which warns if we have unequal sizes
3771 -- for unchecked conversion, and thus potentially implementation
3772 -- dependent semantics, is one of the few occasions on which we
3773 -- use the official RM size instead of Esize. See description
3774 -- in Einfo "Handling of Type'Size Values" for details.
3776 if Serious_Errors_Detected = 0
3777 and then Known_Static_RM_Size (Source)
3778 and then Known_Static_RM_Size (Target)
3779 then
3780 Source_Siz := RM_Size (Source);
3781 Target_Siz := RM_Size (Target);
3783 if Source_Siz /= Target_Siz then
3784 Error_Msg_N
3785 ("types for unchecked conversion have different sizes?",
3786 Enode);
3788 if All_Errors_Mode then
3789 Error_Msg_Name_1 := Chars (Source);
3790 Error_Msg_Uint_1 := Source_Siz;
3791 Error_Msg_Name_2 := Chars (Target);
3792 Error_Msg_Uint_2 := Target_Siz;
3793 Error_Msg_N
3794 ("\size of % is ^, size of % is ^?", Enode);
3796 Error_Msg_Uint_1 := UI_Abs (Source_Siz - Target_Siz);
3798 if Is_Discrete_Type (Source)
3799 and then Is_Discrete_Type (Target)
3800 then
3801 if Source_Siz > Target_Siz then
3802 Error_Msg_N
3803 ("\^ high order bits of source will be ignored?",
3804 Enode);
3806 elsif Is_Unsigned_Type (Source) then
3807 Error_Msg_N
3808 ("\source will be extended with ^ high order " &
3809 "zero bits?", Enode);
3811 else
3812 Error_Msg_N
3813 ("\source will be extended with ^ high order " &
3814 "sign bits?",
3815 Enode);
3816 end if;
3818 elsif Source_Siz < Target_Siz then
3819 if Is_Discrete_Type (Target) then
3820 if Bytes_Big_Endian then
3821 Error_Msg_N
3822 ("\target value will include ^ undefined " &
3823 "low order bits?",
3824 Enode);
3825 else
3826 Error_Msg_N
3827 ("\target value will include ^ undefined " &
3828 "high order bits?",
3829 Enode);
3830 end if;
3832 else
3833 Error_Msg_N
3834 ("\^ trailing bits of target value will be " &
3835 "undefined?", Enode);
3836 end if;
3838 else pragma Assert (Source_Siz > Target_Siz);
3839 Error_Msg_N
3840 ("\^ trailing bits of source will be ignored?",
3841 Enode);
3842 end if;
3843 end if;
3844 end if;
3845 end if;
3847 -- If both types are access types, we need to check the alignment.
3848 -- If the alignment of both is specified, we can do it here.
3850 if Serious_Errors_Detected = 0
3851 and then Ekind (Source) in Access_Kind
3852 and then Ekind (Target) in Access_Kind
3853 and then Target_Strict_Alignment
3854 and then Present (Designated_Type (Source))
3855 and then Present (Designated_Type (Target))
3856 then
3857 declare
3858 D_Source : constant Entity_Id := Designated_Type (Source);
3859 D_Target : constant Entity_Id := Designated_Type (Target);
3861 begin
3862 if Known_Alignment (D_Source)
3863 and then Known_Alignment (D_Target)
3864 then
3865 declare
3866 Source_Align : constant Uint := Alignment (D_Source);
3867 Target_Align : constant Uint := Alignment (D_Target);
3869 begin
3870 if Source_Align < Target_Align
3871 and then not Is_Tagged_Type (D_Source)
3872 then
3873 Error_Msg_Uint_1 := Target_Align;
3874 Error_Msg_Uint_2 := Source_Align;
3875 Error_Msg_Node_2 := D_Source;
3876 Error_Msg_NE
3877 ("alignment of & (^) is stricter than " &
3878 "alignment of & (^)?", Enode, D_Target);
3880 if All_Errors_Mode then
3881 Error_Msg_N
3882 ("\resulting access value may have invalid " &
3883 "alignment?", Enode);
3884 end if;
3885 end if;
3886 end;
3887 end if;
3888 end;
3889 end if;
3890 end;
3891 end loop;
3892 end Validate_Unchecked_Conversions;
3894 end Sem_Ch13;