Merge from mainline (160224:163495).
[official-gcc/graphite-test-results.git] / gcc / ada / sem_ch13.adb
blob67a913919e3c9721cf690806daeb4d6dbc48d7ad
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-2010, Free Software Foundation, Inc. --
10 -- --
11 -- GNAT is free software; you can redistribute it and/or modify it under --
12 -- terms of the GNU General Public License as published by the Free Soft- --
13 -- ware Foundation; either version 3, or (at your option) any later ver- --
14 -- sion. GNAT is distributed in the hope that it will be useful, but WITH- --
15 -- OUT ANY WARRANTY; without even the implied warranty of MERCHANTABILITY --
16 -- or FITNESS FOR A PARTICULAR PURPOSE. See the GNU General Public License --
17 -- for more details. You should have received a copy of the GNU General --
18 -- Public License distributed with GNAT; see file COPYING3. If not, go to --
19 -- http://www.gnu.org/licenses for a complete copy of the license. --
20 -- --
21 -- GNAT was originally developed by the GNAT team at New York University. --
22 -- Extensive contributions were provided by Ada Core Technologies Inc. --
23 -- --
24 ------------------------------------------------------------------------------
26 with Atree; use Atree;
27 with Checks; use Checks;
28 with Einfo; use Einfo;
29 with Elists; use Elists;
30 with Errout; use Errout;
31 with Exp_Disp; use Exp_Disp;
32 with Exp_Tss; use Exp_Tss;
33 with Exp_Util; use Exp_Util;
34 with Lib; use Lib;
35 with Lib.Xref; use Lib.Xref;
36 with Namet; use Namet;
37 with Nlists; use Nlists;
38 with Nmake; use Nmake;
39 with Opt; use Opt;
40 with Restrict; use Restrict;
41 with Rident; use Rident;
42 with Rtsfind; use Rtsfind;
43 with Sem; use Sem;
44 with Sem_Aux; use Sem_Aux;
45 with Sem_Ch3; use Sem_Ch3;
46 with Sem_Ch8; use Sem_Ch8;
47 with Sem_Eval; use Sem_Eval;
48 with Sem_Res; use Sem_Res;
49 with Sem_Type; use Sem_Type;
50 with Sem_Util; use Sem_Util;
51 with Sem_Warn; use Sem_Warn;
52 with Snames; use Snames;
53 with Stand; use Stand;
54 with Sinfo; use Sinfo;
55 with Table;
56 with Targparm; use Targparm;
57 with Ttypes; use Ttypes;
58 with Tbuild; use Tbuild;
59 with Urealp; use Urealp;
61 with GNAT.Heap_Sort_G;
63 package body Sem_Ch13 is
65 SSU : constant Pos := System_Storage_Unit;
66 -- Convenient short hand for commonly used constant
68 -----------------------
69 -- Local Subprograms --
70 -----------------------
72 procedure Alignment_Check_For_Esize_Change (Typ : Entity_Id);
73 -- This routine is called after setting the Esize of type entity Typ.
74 -- The purpose is to deal with the situation where an alignment has been
75 -- inherited from a derived type that is no longer appropriate for the
76 -- new Esize value. In this case, we reset the Alignment to unknown.
78 function Get_Alignment_Value (Expr : Node_Id) return Uint;
79 -- Given the expression for an alignment value, returns the corresponding
80 -- Uint value. If the value is inappropriate, then error messages are
81 -- posted as required, and a value of No_Uint is returned.
83 function Is_Operational_Item (N : Node_Id) return Boolean;
84 -- A specification for a stream attribute is allowed before the full
85 -- type is declared, as explained in AI-00137 and the corrigendum.
86 -- Attributes that do not specify a representation characteristic are
87 -- operational attributes.
89 procedure New_Stream_Subprogram
90 (N : Node_Id;
91 Ent : Entity_Id;
92 Subp : Entity_Id;
93 Nam : TSS_Name_Type);
94 -- Create a subprogram renaming of a given stream attribute to the
95 -- designated subprogram and then in the tagged case, provide this as a
96 -- primitive operation, or in the non-tagged case make an appropriate TSS
97 -- entry. This is more properly an expansion activity than just semantics,
98 -- but the presence of user-defined stream functions for limited types is a
99 -- legality check, which is why this takes place here rather than in
100 -- exp_ch13, where it was previously. Nam indicates the name of the TSS
101 -- function to be generated.
103 -- To avoid elaboration anomalies with freeze nodes, for untagged types
104 -- we generate both a subprogram declaration and a subprogram renaming
105 -- declaration, so that the attribute specification is handled as a
106 -- renaming_as_body. For tagged types, the specification is one of the
107 -- primitive specs.
109 ----------------------------------------------
110 -- Table for Validate_Unchecked_Conversions --
111 ----------------------------------------------
113 -- The following table collects unchecked conversions for validation.
114 -- Entries are made by Validate_Unchecked_Conversion and then the
115 -- call to Validate_Unchecked_Conversions does the actual error
116 -- checking and posting of warnings. The reason for this delayed
117 -- processing is to take advantage of back-annotations of size and
118 -- alignment values performed by the back end.
120 -- Note: the reason we store a Source_Ptr value instead of a Node_Id
121 -- is that by the time Validate_Unchecked_Conversions is called, Sprint
122 -- will already have modified all Sloc values if the -gnatD option is set.
124 type UC_Entry is record
125 Eloc : Source_Ptr; -- node used for posting warnings
126 Source : Entity_Id; -- source type for unchecked conversion
127 Target : Entity_Id; -- target type for unchecked conversion
128 end record;
130 package Unchecked_Conversions is new Table.Table (
131 Table_Component_Type => UC_Entry,
132 Table_Index_Type => Int,
133 Table_Low_Bound => 1,
134 Table_Initial => 50,
135 Table_Increment => 200,
136 Table_Name => "Unchecked_Conversions");
138 ----------------------------------------
139 -- Table for Validate_Address_Clauses --
140 ----------------------------------------
142 -- If an address clause has the form
144 -- for X'Address use Expr
146 -- where Expr is of the form Y'Address or recursively is a reference
147 -- to a constant of either of these forms, and X and Y are entities of
148 -- objects, then if Y has a smaller alignment than X, that merits a
149 -- warning about possible bad alignment. The following table collects
150 -- address clauses of this kind. We put these in a table so that they
151 -- can be checked after the back end has completed annotation of the
152 -- alignments of objects, since we can catch more cases that way.
154 type Address_Clause_Check_Record is record
155 N : Node_Id;
156 -- The address clause
158 X : Entity_Id;
159 -- The entity of the object overlaying Y
161 Y : Entity_Id;
162 -- The entity of the object being overlaid
164 Off : Boolean;
165 -- Whether the address is offseted within Y
166 end record;
168 package Address_Clause_Checks is new Table.Table (
169 Table_Component_Type => Address_Clause_Check_Record,
170 Table_Index_Type => Int,
171 Table_Low_Bound => 1,
172 Table_Initial => 20,
173 Table_Increment => 200,
174 Table_Name => "Address_Clause_Checks");
176 -----------------------------------------
177 -- Adjust_Record_For_Reverse_Bit_Order --
178 -----------------------------------------
180 procedure Adjust_Record_For_Reverse_Bit_Order (R : Entity_Id) is
181 Comp : Node_Id;
182 CC : Node_Id;
184 begin
185 -- Processing depends on version of Ada
187 case Ada_Version is
189 -- For Ada 95, we just renumber bits within a storage unit. We do
190 -- the same for Ada 83 mode, since we recognize pragma Bit_Order
191 -- in Ada 83, and are free to add this extension.
193 when Ada_83 | Ada_95 =>
194 Comp := First_Component_Or_Discriminant (R);
195 while Present (Comp) loop
196 CC := Component_Clause (Comp);
198 -- If component clause is present, then deal with the non-
199 -- default bit order case for Ada 95 mode.
201 -- We only do this processing for the base type, and in
202 -- fact that's important, since otherwise if there are
203 -- record subtypes, we could reverse the bits once for
204 -- each subtype, which would be incorrect.
206 if Present (CC)
207 and then Ekind (R) = E_Record_Type
208 then
209 declare
210 CFB : constant Uint := Component_Bit_Offset (Comp);
211 CSZ : constant Uint := Esize (Comp);
212 CLC : constant Node_Id := Component_Clause (Comp);
213 Pos : constant Node_Id := Position (CLC);
214 FB : constant Node_Id := First_Bit (CLC);
216 Storage_Unit_Offset : constant Uint :=
217 CFB / System_Storage_Unit;
219 Start_Bit : constant Uint :=
220 CFB mod System_Storage_Unit;
222 begin
223 -- Cases where field goes over storage unit boundary
225 if Start_Bit + CSZ > System_Storage_Unit then
227 -- Allow multi-byte field but generate warning
229 if Start_Bit mod System_Storage_Unit = 0
230 and then CSZ mod System_Storage_Unit = 0
231 then
232 Error_Msg_N
233 ("multi-byte field specified with non-standard"
234 & " Bit_Order?", CLC);
236 if Bytes_Big_Endian then
237 Error_Msg_N
238 ("bytes are not reversed "
239 & "(component is big-endian)?", CLC);
240 else
241 Error_Msg_N
242 ("bytes are not reversed "
243 & "(component is little-endian)?", CLC);
244 end if;
246 -- Do not allow non-contiguous field
248 else
249 Error_Msg_N
250 ("attempt to specify non-contiguous field "
251 & "not permitted", CLC);
252 Error_Msg_N
253 ("\caused by non-standard Bit_Order "
254 & "specified", CLC);
255 Error_Msg_N
256 ("\consider possibility of using "
257 & "Ada 2005 mode here", CLC);
258 end if;
260 -- Case where field fits in one storage unit
262 else
263 -- Give warning if suspicious component clause
265 if Intval (FB) >= System_Storage_Unit
266 and then Warn_On_Reverse_Bit_Order
267 then
268 Error_Msg_N
269 ("?Bit_Order clause does not affect " &
270 "byte ordering", Pos);
271 Error_Msg_Uint_1 :=
272 Intval (Pos) + Intval (FB) /
273 System_Storage_Unit;
274 Error_Msg_N
275 ("?position normalized to ^ before bit " &
276 "order interpreted", Pos);
277 end if;
279 -- Here is where we fix up the Component_Bit_Offset
280 -- value to account for the reverse bit order.
281 -- Some examples of what needs to be done are:
283 -- First_Bit .. Last_Bit Component_Bit_Offset
284 -- old new old new
286 -- 0 .. 0 7 .. 7 0 7
287 -- 0 .. 1 6 .. 7 0 6
288 -- 0 .. 2 5 .. 7 0 5
289 -- 0 .. 7 0 .. 7 0 4
291 -- 1 .. 1 6 .. 6 1 6
292 -- 1 .. 4 3 .. 6 1 3
293 -- 4 .. 7 0 .. 3 4 0
295 -- The general rule is that the first bit is
296 -- is obtained by subtracting the old ending bit
297 -- from storage_unit - 1.
299 Set_Component_Bit_Offset
300 (Comp,
301 (Storage_Unit_Offset * System_Storage_Unit) +
302 (System_Storage_Unit - 1) -
303 (Start_Bit + CSZ - 1));
305 Set_Normalized_First_Bit
306 (Comp,
307 Component_Bit_Offset (Comp) mod
308 System_Storage_Unit);
309 end if;
310 end;
311 end if;
313 Next_Component_Or_Discriminant (Comp);
314 end loop;
316 -- For Ada 2005, we do machine scalar processing, as fully described
317 -- In AI-133. This involves gathering all components which start at
318 -- the same byte offset and processing them together
320 when Ada_05 .. Ada_Version_Type'Last =>
321 declare
322 Max_Machine_Scalar_Size : constant Uint :=
323 UI_From_Int
324 (Standard_Long_Long_Integer_Size);
325 -- We use this as the maximum machine scalar size
327 Num_CC : Natural;
328 SSU : constant Uint := UI_From_Int (System_Storage_Unit);
330 begin
331 -- This first loop through components does two things. First it
332 -- deals with the case of components with component clauses
333 -- whose length is greater than the maximum machine scalar size
334 -- (either accepting them or rejecting as needed). Second, it
335 -- counts the number of components with component clauses whose
336 -- length does not exceed this maximum for later processing.
338 Num_CC := 0;
339 Comp := First_Component_Or_Discriminant (R);
340 while Present (Comp) loop
341 CC := Component_Clause (Comp);
343 if Present (CC) then
344 declare
345 Fbit : constant Uint :=
346 Static_Integer (First_Bit (CC));
348 begin
349 -- Case of component with size > max machine scalar
351 if Esize (Comp) > Max_Machine_Scalar_Size then
353 -- Must begin on byte boundary
355 if Fbit mod SSU /= 0 then
356 Error_Msg_N
357 ("illegal first bit value for "
358 & "reverse bit order",
359 First_Bit (CC));
360 Error_Msg_Uint_1 := SSU;
361 Error_Msg_Uint_2 := Max_Machine_Scalar_Size;
363 Error_Msg_N
364 ("\must be a multiple of ^ "
365 & "if size greater than ^",
366 First_Bit (CC));
368 -- Must end on byte boundary
370 elsif Esize (Comp) mod SSU /= 0 then
371 Error_Msg_N
372 ("illegal last bit value for "
373 & "reverse bit order",
374 Last_Bit (CC));
375 Error_Msg_Uint_1 := SSU;
376 Error_Msg_Uint_2 := Max_Machine_Scalar_Size;
378 Error_Msg_N
379 ("\must be a multiple of ^ if size "
380 & "greater than ^",
381 Last_Bit (CC));
383 -- OK, give warning if enabled
385 elsif Warn_On_Reverse_Bit_Order then
386 Error_Msg_N
387 ("multi-byte field specified with "
388 & " non-standard Bit_Order?", CC);
390 if Bytes_Big_Endian then
391 Error_Msg_N
392 ("\bytes are not reversed "
393 & "(component is big-endian)?", CC);
394 else
395 Error_Msg_N
396 ("\bytes are not reversed "
397 & "(component is little-endian)?", CC);
398 end if;
399 end if;
401 -- Case where size is not greater than max machine
402 -- scalar. For now, we just count these.
404 else
405 Num_CC := Num_CC + 1;
406 end if;
407 end;
408 end if;
410 Next_Component_Or_Discriminant (Comp);
411 end loop;
413 -- We need to sort the component clauses on the basis of the
414 -- Position values in the clause, so we can group clauses with
415 -- the same Position. together to determine the relevant
416 -- machine scalar size.
418 Sort_CC : declare
419 Comps : array (0 .. Num_CC) of Entity_Id;
420 -- Array to collect component and discriminant entities. The
421 -- data starts at index 1, the 0'th entry is for the sort
422 -- routine.
424 function CP_Lt (Op1, Op2 : Natural) return Boolean;
425 -- Compare routine for Sort
427 procedure CP_Move (From : Natural; To : Natural);
428 -- Move routine for Sort
430 package Sorting is new GNAT.Heap_Sort_G (CP_Move, CP_Lt);
432 Start : Natural;
433 Stop : Natural;
434 -- Start and stop positions in component list of set of
435 -- components with the same starting position (that
436 -- constitute components in a single machine scalar).
438 MaxL : Uint;
439 -- Maximum last bit value of any component in this set
441 MSS : Uint;
442 -- Corresponding machine scalar size
444 -----------
445 -- CP_Lt --
446 -----------
448 function CP_Lt (Op1, Op2 : Natural) return Boolean is
449 begin
450 return Position (Component_Clause (Comps (Op1))) <
451 Position (Component_Clause (Comps (Op2)));
452 end CP_Lt;
454 -------------
455 -- CP_Move --
456 -------------
458 procedure CP_Move (From : Natural; To : Natural) is
459 begin
460 Comps (To) := Comps (From);
461 end CP_Move;
463 -- Start of processing for Sort_CC
465 begin
466 -- Collect the component clauses
468 Num_CC := 0;
469 Comp := First_Component_Or_Discriminant (R);
470 while Present (Comp) loop
471 if Present (Component_Clause (Comp))
472 and then Esize (Comp) <= Max_Machine_Scalar_Size
473 then
474 Num_CC := Num_CC + 1;
475 Comps (Num_CC) := Comp;
476 end if;
478 Next_Component_Or_Discriminant (Comp);
479 end loop;
481 -- Sort by ascending position number
483 Sorting.Sort (Num_CC);
485 -- We now have all the components whose size does not exceed
486 -- the max machine scalar value, sorted by starting
487 -- position. In this loop we gather groups of clauses
488 -- starting at the same position, to process them in
489 -- accordance with Ada 2005 AI-133.
491 Stop := 0;
492 while Stop < Num_CC loop
493 Start := Stop + 1;
494 Stop := Start;
495 MaxL :=
496 Static_Integer
497 (Last_Bit (Component_Clause (Comps (Start))));
498 while Stop < Num_CC loop
499 if Static_Integer
500 (Position (Component_Clause (Comps (Stop + 1)))) =
501 Static_Integer
502 (Position (Component_Clause (Comps (Stop))))
503 then
504 Stop := Stop + 1;
505 MaxL :=
506 UI_Max
507 (MaxL,
508 Static_Integer
509 (Last_Bit
510 (Component_Clause (Comps (Stop)))));
511 else
512 exit;
513 end if;
514 end loop;
516 -- Now we have a group of component clauses from Start to
517 -- Stop whose positions are identical, and MaxL is the
518 -- maximum last bit value of any of these components.
520 -- We need to determine the corresponding machine scalar
521 -- size. This loop assumes that machine scalar sizes are
522 -- even, and that each possible machine scalar has twice
523 -- as many bits as the next smaller one.
525 MSS := Max_Machine_Scalar_Size;
526 while MSS mod 2 = 0
527 and then (MSS / 2) >= SSU
528 and then (MSS / 2) > MaxL
529 loop
530 MSS := MSS / 2;
531 end loop;
533 -- Here is where we fix up the Component_Bit_Offset value
534 -- to account for the reverse bit order. Some examples of
535 -- what needs to be done for the case of a machine scalar
536 -- size of 8 are:
538 -- First_Bit .. Last_Bit Component_Bit_Offset
539 -- old new old new
541 -- 0 .. 0 7 .. 7 0 7
542 -- 0 .. 1 6 .. 7 0 6
543 -- 0 .. 2 5 .. 7 0 5
544 -- 0 .. 7 0 .. 7 0 4
546 -- 1 .. 1 6 .. 6 1 6
547 -- 1 .. 4 3 .. 6 1 3
548 -- 4 .. 7 0 .. 3 4 0
550 -- The general rule is that the first bit is obtained by
551 -- subtracting the old ending bit from machine scalar
552 -- size - 1.
554 for C in Start .. Stop loop
555 declare
556 Comp : constant Entity_Id := Comps (C);
557 CC : constant Node_Id :=
558 Component_Clause (Comp);
559 LB : constant Uint :=
560 Static_Integer (Last_Bit (CC));
561 NFB : constant Uint := MSS - Uint_1 - LB;
562 NLB : constant Uint := NFB + Esize (Comp) - 1;
563 Pos : constant Uint :=
564 Static_Integer (Position (CC));
566 begin
567 if Warn_On_Reverse_Bit_Order then
568 Error_Msg_Uint_1 := MSS;
569 Error_Msg_N
570 ("info: reverse bit order in machine " &
571 "scalar of length^?", First_Bit (CC));
572 Error_Msg_Uint_1 := NFB;
573 Error_Msg_Uint_2 := NLB;
575 if Bytes_Big_Endian then
576 Error_Msg_NE
577 ("?\info: big-endian range for "
578 & "component & is ^ .. ^",
579 First_Bit (CC), Comp);
580 else
581 Error_Msg_NE
582 ("?\info: little-endian range "
583 & "for component & is ^ .. ^",
584 First_Bit (CC), Comp);
585 end if;
586 end if;
588 Set_Component_Bit_Offset (Comp, Pos * SSU + NFB);
589 Set_Normalized_First_Bit (Comp, NFB mod SSU);
590 end;
591 end loop;
592 end loop;
593 end Sort_CC;
594 end;
595 end case;
596 end Adjust_Record_For_Reverse_Bit_Order;
598 --------------------------------------
599 -- Alignment_Check_For_Esize_Change --
600 --------------------------------------
602 procedure Alignment_Check_For_Esize_Change (Typ : Entity_Id) is
603 begin
604 -- If the alignment is known, and not set by a rep clause, and is
605 -- inconsistent with the size being set, then reset it to unknown,
606 -- we assume in this case that the size overrides the inherited
607 -- alignment, and that the alignment must be recomputed.
609 if Known_Alignment (Typ)
610 and then not Has_Alignment_Clause (Typ)
611 and then Esize (Typ) mod (Alignment (Typ) * SSU) /= 0
612 then
613 Init_Alignment (Typ);
614 end if;
615 end Alignment_Check_For_Esize_Change;
617 -----------------------
618 -- Analyze_At_Clause --
619 -----------------------
621 -- An at clause is replaced by the corresponding Address attribute
622 -- definition clause that is the preferred approach in Ada 95.
624 procedure Analyze_At_Clause (N : Node_Id) is
625 CS : constant Boolean := Comes_From_Source (N);
627 begin
628 -- This is an obsolescent feature
630 Check_Restriction (No_Obsolescent_Features, N);
632 if Warn_On_Obsolescent_Feature then
633 Error_Msg_N
634 ("at clause is an obsolescent feature (RM J.7(2))?", N);
635 Error_Msg_N
636 ("\use address attribute definition clause instead?", N);
637 end if;
639 -- Rewrite as address clause
641 Rewrite (N,
642 Make_Attribute_Definition_Clause (Sloc (N),
643 Name => Identifier (N),
644 Chars => Name_Address,
645 Expression => Expression (N)));
647 -- We preserve Comes_From_Source, since logically the clause still
648 -- comes from the source program even though it is changed in form.
650 Set_Comes_From_Source (N, CS);
652 -- Analyze rewritten clause
654 Analyze_Attribute_Definition_Clause (N);
655 end Analyze_At_Clause;
657 -----------------------------------------
658 -- Analyze_Attribute_Definition_Clause --
659 -----------------------------------------
661 procedure Analyze_Attribute_Definition_Clause (N : Node_Id) is
662 Loc : constant Source_Ptr := Sloc (N);
663 Nam : constant Node_Id := Name (N);
664 Attr : constant Name_Id := Chars (N);
665 Expr : constant Node_Id := Expression (N);
666 Id : constant Attribute_Id := Get_Attribute_Id (Attr);
667 Ent : Entity_Id;
668 U_Ent : Entity_Id;
670 FOnly : Boolean := False;
671 -- Reset to True for subtype specific attribute (Alignment, Size)
672 -- and for stream attributes, i.e. those cases where in the call
673 -- to Rep_Item_Too_Late, FOnly is set True so that only the freezing
674 -- rules are checked. Note that the case of stream attributes is not
675 -- clear from the RM, but see AI95-00137. Also, the RM seems to
676 -- disallow Storage_Size for derived task types, but that is also
677 -- clearly unintentional.
679 procedure Analyze_Stream_TSS_Definition (TSS_Nam : TSS_Name_Type);
680 -- Common processing for 'Read, 'Write, 'Input and 'Output attribute
681 -- definition clauses.
683 -----------------------------------
684 -- Analyze_Stream_TSS_Definition --
685 -----------------------------------
687 procedure Analyze_Stream_TSS_Definition (TSS_Nam : TSS_Name_Type) is
688 Subp : Entity_Id := Empty;
689 I : Interp_Index;
690 It : Interp;
691 Pnam : Entity_Id;
693 Is_Read : constant Boolean := (TSS_Nam = TSS_Stream_Read);
695 function Has_Good_Profile (Subp : Entity_Id) return Boolean;
696 -- Return true if the entity is a subprogram with an appropriate
697 -- profile for the attribute being defined.
699 ----------------------
700 -- Has_Good_Profile --
701 ----------------------
703 function Has_Good_Profile (Subp : Entity_Id) return Boolean is
704 F : Entity_Id;
705 Is_Function : constant Boolean := (TSS_Nam = TSS_Stream_Input);
706 Expected_Ekind : constant array (Boolean) of Entity_Kind :=
707 (False => E_Procedure, True => E_Function);
708 Typ : Entity_Id;
710 begin
711 if Ekind (Subp) /= Expected_Ekind (Is_Function) then
712 return False;
713 end if;
715 F := First_Formal (Subp);
717 if No (F)
718 or else Ekind (Etype (F)) /= E_Anonymous_Access_Type
719 or else Designated_Type (Etype (F)) /=
720 Class_Wide_Type (RTE (RE_Root_Stream_Type))
721 then
722 return False;
723 end if;
725 if not Is_Function then
726 Next_Formal (F);
728 declare
729 Expected_Mode : constant array (Boolean) of Entity_Kind :=
730 (False => E_In_Parameter,
731 True => E_Out_Parameter);
732 begin
733 if Parameter_Mode (F) /= Expected_Mode (Is_Read) then
734 return False;
735 end if;
736 end;
738 Typ := Etype (F);
740 else
741 Typ := Etype (Subp);
742 end if;
744 return Base_Type (Typ) = Base_Type (Ent)
745 and then No (Next_Formal (F));
746 end Has_Good_Profile;
748 -- Start of processing for Analyze_Stream_TSS_Definition
750 begin
751 FOnly := True;
753 if not Is_Type (U_Ent) then
754 Error_Msg_N ("local name must be a subtype", Nam);
755 return;
756 end if;
758 Pnam := TSS (Base_Type (U_Ent), TSS_Nam);
760 -- If Pnam is present, it can be either inherited from an ancestor
761 -- type (in which case it is legal to redefine it for this type), or
762 -- be a previous definition of the attribute for the same type (in
763 -- which case it is illegal).
765 -- In the first case, it will have been analyzed already, and we
766 -- can check that its profile does not match the expected profile
767 -- for a stream attribute of U_Ent. In the second case, either Pnam
768 -- has been analyzed (and has the expected profile), or it has not
769 -- been analyzed yet (case of a type that has not been frozen yet
770 -- and for which the stream attribute has been set using Set_TSS).
772 if Present (Pnam)
773 and then (No (First_Entity (Pnam)) or else Has_Good_Profile (Pnam))
774 then
775 Error_Msg_Sloc := Sloc (Pnam);
776 Error_Msg_Name_1 := Attr;
777 Error_Msg_N ("% attribute already defined #", Nam);
778 return;
779 end if;
781 Analyze (Expr);
783 if Is_Entity_Name (Expr) then
784 if not Is_Overloaded (Expr) then
785 if Has_Good_Profile (Entity (Expr)) then
786 Subp := Entity (Expr);
787 end if;
789 else
790 Get_First_Interp (Expr, I, It);
791 while Present (It.Nam) loop
792 if Has_Good_Profile (It.Nam) then
793 Subp := It.Nam;
794 exit;
795 end if;
797 Get_Next_Interp (I, It);
798 end loop;
799 end if;
800 end if;
802 if Present (Subp) then
803 if Is_Abstract_Subprogram (Subp) then
804 Error_Msg_N ("stream subprogram must not be abstract", Expr);
805 return;
806 end if;
808 Set_Entity (Expr, Subp);
809 Set_Etype (Expr, Etype (Subp));
811 New_Stream_Subprogram (N, U_Ent, Subp, TSS_Nam);
813 else
814 Error_Msg_Name_1 := Attr;
815 Error_Msg_N ("incorrect expression for% attribute", Expr);
816 end if;
817 end Analyze_Stream_TSS_Definition;
819 -- Start of processing for Analyze_Attribute_Definition_Clause
821 begin
822 -- Process Ignore_Rep_Clauses option
824 if Ignore_Rep_Clauses then
825 case Id is
827 -- The following should be ignored. They do not affect legality
828 -- and may be target dependent. The basic idea of -gnatI is to
829 -- ignore any rep clauses that may be target dependent but do not
830 -- affect legality (except possibly to be rejected because they
831 -- are incompatible with the compilation target).
833 when Attribute_Alignment |
834 Attribute_Bit_Order |
835 Attribute_Component_Size |
836 Attribute_Machine_Radix |
837 Attribute_Object_Size |
838 Attribute_Size |
839 Attribute_Small |
840 Attribute_Stream_Size |
841 Attribute_Value_Size =>
843 Rewrite (N, Make_Null_Statement (Sloc (N)));
844 return;
846 -- The following should not be ignored, because in the first place
847 -- they are reasonably portable, and should not cause problems in
848 -- compiling code from another target, and also they do affect
849 -- legality, e.g. failing to provide a stream attribute for a
850 -- type may make a program illegal.
852 when Attribute_External_Tag |
853 Attribute_Input |
854 Attribute_Output |
855 Attribute_Read |
856 Attribute_Storage_Pool |
857 Attribute_Storage_Size |
858 Attribute_Write =>
859 null;
861 -- Other cases are errors ("attribute& cannot be set with
862 -- definition clause"), which will be caught below.
864 when others =>
865 null;
866 end case;
867 end if;
869 Analyze (Nam);
870 Ent := Entity (Nam);
872 if Rep_Item_Too_Early (Ent, N) then
873 return;
874 end if;
876 -- Rep clause applies to full view of incomplete type or private type if
877 -- we have one (if not, this is a premature use of the type). However,
878 -- certain semantic checks need to be done on the specified entity (i.e.
879 -- the private view), so we save it in Ent.
881 if Is_Private_Type (Ent)
882 and then Is_Derived_Type (Ent)
883 and then not Is_Tagged_Type (Ent)
884 and then No (Full_View (Ent))
885 then
886 -- If this is a private type whose completion is a derivation from
887 -- another private type, there is no full view, and the attribute
888 -- belongs to the type itself, not its underlying parent.
890 U_Ent := Ent;
892 elsif Ekind (Ent) = E_Incomplete_Type then
894 -- The attribute applies to the full view, set the entity of the
895 -- attribute definition accordingly.
897 Ent := Underlying_Type (Ent);
898 U_Ent := Ent;
899 Set_Entity (Nam, Ent);
901 else
902 U_Ent := Underlying_Type (Ent);
903 end if;
905 -- Complete other routine error checks
907 if Etype (Nam) = Any_Type then
908 return;
910 elsif Scope (Ent) /= Current_Scope then
911 Error_Msg_N ("entity must be declared in this scope", Nam);
912 return;
914 elsif No (U_Ent) then
915 U_Ent := Ent;
917 elsif Is_Type (U_Ent)
918 and then not Is_First_Subtype (U_Ent)
919 and then Id /= Attribute_Object_Size
920 and then Id /= Attribute_Value_Size
921 and then not From_At_Mod (N)
922 then
923 Error_Msg_N ("cannot specify attribute for subtype", Nam);
924 return;
925 end if;
927 -- Switch on particular attribute
929 case Id is
931 -------------
932 -- Address --
933 -------------
935 -- Address attribute definition clause
937 when Attribute_Address => Address : begin
939 -- A little error check, catch for X'Address use X'Address;
941 if Nkind (Nam) = N_Identifier
942 and then Nkind (Expr) = N_Attribute_Reference
943 and then Attribute_Name (Expr) = Name_Address
944 and then Nkind (Prefix (Expr)) = N_Identifier
945 and then Chars (Nam) = Chars (Prefix (Expr))
946 then
947 Error_Msg_NE
948 ("address for & is self-referencing", Prefix (Expr), Ent);
949 return;
950 end if;
952 -- Not that special case, carry on with analysis of expression
954 Analyze_And_Resolve (Expr, RTE (RE_Address));
956 -- Even when ignoring rep clauses we need to indicate that the
957 -- entity has an address clause and thus it is legal to declare
958 -- it imported.
960 if Ignore_Rep_Clauses then
961 if Ekind_In (U_Ent, E_Variable, E_Constant) then
962 Record_Rep_Item (U_Ent, N);
963 end if;
965 return;
966 end if;
968 if Present (Address_Clause (U_Ent)) then
969 Error_Msg_N ("address already given for &", Nam);
971 -- Case of address clause for subprogram
973 elsif Is_Subprogram (U_Ent) then
974 if Has_Homonym (U_Ent) then
975 Error_Msg_N
976 ("address clause cannot be given " &
977 "for overloaded subprogram",
978 Nam);
979 return;
980 end if;
982 -- For subprograms, all address clauses are permitted, and we
983 -- mark the subprogram as having a deferred freeze so that Gigi
984 -- will not elaborate it too soon.
986 -- Above needs more comments, what is too soon about???
988 Set_Has_Delayed_Freeze (U_Ent);
990 -- Case of address clause for entry
992 elsif Ekind (U_Ent) = E_Entry then
993 if Nkind (Parent (N)) = N_Task_Body then
994 Error_Msg_N
995 ("entry address must be specified in task spec", Nam);
996 return;
997 end if;
999 -- For entries, we require a constant address
1001 Check_Constant_Address_Clause (Expr, U_Ent);
1003 -- Special checks for task types
1005 if Is_Task_Type (Scope (U_Ent))
1006 and then Comes_From_Source (Scope (U_Ent))
1007 then
1008 Error_Msg_N
1009 ("?entry address declared for entry in task type", N);
1010 Error_Msg_N
1011 ("\?only one task can be declared of this type", N);
1012 end if;
1014 -- Entry address clauses are obsolescent
1016 Check_Restriction (No_Obsolescent_Features, N);
1018 if Warn_On_Obsolescent_Feature then
1019 Error_Msg_N
1020 ("attaching interrupt to task entry is an " &
1021 "obsolescent feature (RM J.7.1)?", N);
1022 Error_Msg_N
1023 ("\use interrupt procedure instead?", N);
1024 end if;
1026 -- Case of an address clause for a controlled object which we
1027 -- consider to be erroneous.
1029 elsif Is_Controlled (Etype (U_Ent))
1030 or else Has_Controlled_Component (Etype (U_Ent))
1031 then
1032 Error_Msg_NE
1033 ("?controlled object& must not be overlaid", Nam, U_Ent);
1034 Error_Msg_N
1035 ("\?Program_Error will be raised at run time", Nam);
1036 Insert_Action (Declaration_Node (U_Ent),
1037 Make_Raise_Program_Error (Loc,
1038 Reason => PE_Overlaid_Controlled_Object));
1039 return;
1041 -- Case of address clause for a (non-controlled) object
1043 elsif
1044 Ekind (U_Ent) = E_Variable
1045 or else
1046 Ekind (U_Ent) = E_Constant
1047 then
1048 declare
1049 Expr : constant Node_Id := Expression (N);
1050 O_Ent : Entity_Id;
1051 Off : Boolean;
1053 begin
1054 -- Exported variables cannot have an address clause, because
1055 -- this cancels the effect of the pragma Export.
1057 if Is_Exported (U_Ent) then
1058 Error_Msg_N
1059 ("cannot export object with address clause", Nam);
1060 return;
1061 end if;
1063 Find_Overlaid_Entity (N, O_Ent, Off);
1065 -- Overlaying controlled objects is erroneous
1067 if Present (O_Ent)
1068 and then (Has_Controlled_Component (Etype (O_Ent))
1069 or else Is_Controlled (Etype (O_Ent)))
1070 then
1071 Error_Msg_N
1072 ("?cannot overlay with controlled object", Expr);
1073 Error_Msg_N
1074 ("\?Program_Error will be raised at run time", Expr);
1075 Insert_Action (Declaration_Node (U_Ent),
1076 Make_Raise_Program_Error (Loc,
1077 Reason => PE_Overlaid_Controlled_Object));
1078 return;
1080 elsif Present (O_Ent)
1081 and then Ekind (U_Ent) = E_Constant
1082 and then not Is_Constant_Object (O_Ent)
1083 then
1084 Error_Msg_N ("constant overlays a variable?", Expr);
1086 elsif Present (Renamed_Object (U_Ent)) then
1087 Error_Msg_N
1088 ("address clause not allowed"
1089 & " for a renaming declaration (RM 13.1(6))", Nam);
1090 return;
1092 -- Imported variables can have an address clause, but then
1093 -- the import is pretty meaningless except to suppress
1094 -- initializations, so we do not need such variables to
1095 -- be statically allocated (and in fact it causes trouble
1096 -- if the address clause is a local value).
1098 elsif Is_Imported (U_Ent) then
1099 Set_Is_Statically_Allocated (U_Ent, False);
1100 end if;
1102 -- We mark a possible modification of a variable with an
1103 -- address clause, since it is likely aliasing is occurring.
1105 Note_Possible_Modification (Nam, Sure => False);
1107 -- Here we are checking for explicit overlap of one variable
1108 -- by another, and if we find this then mark the overlapped
1109 -- variable as also being volatile to prevent unwanted
1110 -- optimizations. This is a significant pessimization so
1111 -- avoid it when there is an offset, i.e. when the object
1112 -- is composite; they cannot be optimized easily anyway.
1114 if Present (O_Ent)
1115 and then Is_Object (O_Ent)
1116 and then not Off
1117 then
1118 Set_Treat_As_Volatile (O_Ent);
1119 end if;
1121 -- Legality checks on the address clause for initialized
1122 -- objects is deferred until the freeze point, because
1123 -- a subsequent pragma might indicate that the object is
1124 -- imported and thus not initialized.
1126 Set_Has_Delayed_Freeze (U_Ent);
1128 -- If an initialization call has been generated for this
1129 -- object, it needs to be deferred to after the freeze node
1130 -- we have just now added, otherwise GIGI will see a
1131 -- reference to the variable (as actual to the IP call)
1132 -- before its definition.
1134 declare
1135 Init_Call : constant Node_Id := Find_Init_Call (U_Ent, N);
1136 begin
1137 if Present (Init_Call) then
1138 Remove (Init_Call);
1139 Append_Freeze_Action (U_Ent, Init_Call);
1140 end if;
1141 end;
1143 if Is_Exported (U_Ent) then
1144 Error_Msg_N
1145 ("& cannot be exported if an address clause is given",
1146 Nam);
1147 Error_Msg_N
1148 ("\define and export a variable " &
1149 "that holds its address instead",
1150 Nam);
1151 end if;
1153 -- Entity has delayed freeze, so we will generate an
1154 -- alignment check at the freeze point unless suppressed.
1156 if not Range_Checks_Suppressed (U_Ent)
1157 and then not Alignment_Checks_Suppressed (U_Ent)
1158 then
1159 Set_Check_Address_Alignment (N);
1160 end if;
1162 -- Kill the size check code, since we are not allocating
1163 -- the variable, it is somewhere else.
1165 Kill_Size_Check_Code (U_Ent);
1167 -- If the address clause is of the form:
1169 -- for Y'Address use X'Address
1171 -- or
1173 -- Const : constant Address := X'Address;
1174 -- ...
1175 -- for Y'Address use Const;
1177 -- then we make an entry in the table for checking the size
1178 -- and alignment of the overlaying variable. We defer this
1179 -- check till after code generation to take full advantage
1180 -- of the annotation done by the back end. This entry is
1181 -- only made if the address clause comes from source.
1182 -- If the entity has a generic type, the check will be
1183 -- performed in the instance if the actual type justifies
1184 -- it, and we do not insert the clause in the table to
1185 -- prevent spurious warnings.
1187 if Address_Clause_Overlay_Warnings
1188 and then Comes_From_Source (N)
1189 and then Present (O_Ent)
1190 and then Is_Object (O_Ent)
1191 then
1192 if not Is_Generic_Type (Etype (U_Ent)) then
1193 Address_Clause_Checks.Append ((N, U_Ent, O_Ent, Off));
1194 end if;
1196 -- If variable overlays a constant view, and we are
1197 -- warning on overlays, then mark the variable as
1198 -- overlaying a constant (we will give warnings later
1199 -- if this variable is assigned).
1201 if Is_Constant_Object (O_Ent)
1202 and then Ekind (U_Ent) = E_Variable
1203 then
1204 Set_Overlays_Constant (U_Ent);
1205 end if;
1206 end if;
1207 end;
1209 -- Not a valid entity for an address clause
1211 else
1212 Error_Msg_N ("address cannot be given for &", Nam);
1213 end if;
1214 end Address;
1216 ---------------
1217 -- Alignment --
1218 ---------------
1220 -- Alignment attribute definition clause
1222 when Attribute_Alignment => Alignment : declare
1223 Align : constant Uint := Get_Alignment_Value (Expr);
1225 begin
1226 FOnly := True;
1228 if not Is_Type (U_Ent)
1229 and then Ekind (U_Ent) /= E_Variable
1230 and then Ekind (U_Ent) /= E_Constant
1231 then
1232 Error_Msg_N ("alignment cannot be given for &", Nam);
1234 elsif Has_Alignment_Clause (U_Ent) then
1235 Error_Msg_Sloc := Sloc (Alignment_Clause (U_Ent));
1236 Error_Msg_N ("alignment clause previously given#", N);
1238 elsif Align /= No_Uint then
1239 Set_Has_Alignment_Clause (U_Ent);
1240 Set_Alignment (U_Ent, Align);
1242 -- For an array type, U_Ent is the first subtype. In that case,
1243 -- also set the alignment of the anonymous base type so that
1244 -- other subtypes (such as the itypes for aggregates of the
1245 -- type) also receive the expected alignment.
1247 if Is_Array_Type (U_Ent) then
1248 Set_Alignment (Base_Type (U_Ent), Align);
1249 end if;
1250 end if;
1251 end Alignment;
1253 ---------------
1254 -- Bit_Order --
1255 ---------------
1257 -- Bit_Order attribute definition clause
1259 when Attribute_Bit_Order => Bit_Order : declare
1260 begin
1261 if not Is_Record_Type (U_Ent) then
1262 Error_Msg_N
1263 ("Bit_Order can only be defined for record type", Nam);
1265 else
1266 Analyze_And_Resolve (Expr, RTE (RE_Bit_Order));
1268 if Etype (Expr) = Any_Type then
1269 return;
1271 elsif not Is_Static_Expression (Expr) then
1272 Flag_Non_Static_Expr
1273 ("Bit_Order requires static expression!", Expr);
1275 else
1276 if (Expr_Value (Expr) = 0) /= Bytes_Big_Endian then
1277 Set_Reverse_Bit_Order (U_Ent, True);
1278 end if;
1279 end if;
1280 end if;
1281 end Bit_Order;
1283 --------------------
1284 -- Component_Size --
1285 --------------------
1287 -- Component_Size attribute definition clause
1289 when Attribute_Component_Size => Component_Size_Case : declare
1290 Csize : constant Uint := Static_Integer (Expr);
1291 Btype : Entity_Id;
1292 Biased : Boolean;
1293 New_Ctyp : Entity_Id;
1294 Decl : Node_Id;
1296 begin
1297 if not Is_Array_Type (U_Ent) then
1298 Error_Msg_N ("component size requires array type", Nam);
1299 return;
1300 end if;
1302 Btype := Base_Type (U_Ent);
1304 if Has_Component_Size_Clause (Btype) then
1305 Error_Msg_N
1306 ("component size clause for& previously given", Nam);
1308 elsif Csize /= No_Uint then
1309 Check_Size (Expr, Component_Type (Btype), Csize, Biased);
1311 if Has_Aliased_Components (Btype)
1312 and then Csize < 32
1313 and then Csize /= 8
1314 and then Csize /= 16
1315 then
1316 Error_Msg_N
1317 ("component size incorrect for aliased components", N);
1318 return;
1319 end if;
1321 -- For the biased case, build a declaration for a subtype
1322 -- that will be used to represent the biased subtype that
1323 -- reflects the biased representation of components. We need
1324 -- this subtype to get proper conversions on referencing
1325 -- elements of the array. Note that component size clauses
1326 -- are ignored in VM mode.
1328 if VM_Target = No_VM then
1329 if Biased then
1330 New_Ctyp :=
1331 Make_Defining_Identifier (Loc,
1332 Chars =>
1333 New_External_Name (Chars (U_Ent), 'C', 0, 'T'));
1335 Decl :=
1336 Make_Subtype_Declaration (Loc,
1337 Defining_Identifier => New_Ctyp,
1338 Subtype_Indication =>
1339 New_Occurrence_Of (Component_Type (Btype), Loc));
1341 Set_Parent (Decl, N);
1342 Analyze (Decl, Suppress => All_Checks);
1344 Set_Has_Delayed_Freeze (New_Ctyp, False);
1345 Set_Esize (New_Ctyp, Csize);
1346 Set_RM_Size (New_Ctyp, Csize);
1347 Init_Alignment (New_Ctyp);
1348 Set_Has_Biased_Representation (New_Ctyp, True);
1349 Set_Is_Itype (New_Ctyp, True);
1350 Set_Associated_Node_For_Itype (New_Ctyp, U_Ent);
1352 Set_Component_Type (Btype, New_Ctyp);
1354 if Warn_On_Biased_Representation then
1355 Error_Msg_N
1356 ("?component size clause forces biased "
1357 & "representation", N);
1358 end if;
1359 end if;
1361 Set_Component_Size (Btype, Csize);
1363 -- For VM case, we ignore component size clauses
1365 else
1366 -- Give a warning unless we are in GNAT mode, in which case
1367 -- the warning is suppressed since it is not useful.
1369 if not GNAT_Mode then
1370 Error_Msg_N
1371 ("?component size ignored in this configuration", N);
1372 end if;
1373 end if;
1375 Set_Has_Component_Size_Clause (Btype, True);
1376 Set_Has_Non_Standard_Rep (Btype, True);
1377 end if;
1378 end Component_Size_Case;
1380 ------------------
1381 -- External_Tag --
1382 ------------------
1384 when Attribute_External_Tag => External_Tag :
1385 begin
1386 if not Is_Tagged_Type (U_Ent) then
1387 Error_Msg_N ("should be a tagged type", Nam);
1388 end if;
1390 Analyze_And_Resolve (Expr, Standard_String);
1392 if not Is_Static_Expression (Expr) then
1393 Flag_Non_Static_Expr
1394 ("static string required for tag name!", Nam);
1395 end if;
1397 if VM_Target = No_VM then
1398 Set_Has_External_Tag_Rep_Clause (U_Ent);
1399 else
1400 Error_Msg_Name_1 := Attr;
1401 Error_Msg_N
1402 ("% attribute unsupported in this configuration", Nam);
1403 end if;
1405 if not Is_Library_Level_Entity (U_Ent) then
1406 Error_Msg_NE
1407 ("?non-unique external tag supplied for &", N, U_Ent);
1408 Error_Msg_N
1409 ("?\same external tag applies to all subprogram calls", N);
1410 Error_Msg_N
1411 ("?\corresponding internal tag cannot be obtained", N);
1412 end if;
1413 end External_Tag;
1415 -----------
1416 -- Input --
1417 -----------
1419 when Attribute_Input =>
1420 Analyze_Stream_TSS_Definition (TSS_Stream_Input);
1421 Set_Has_Specified_Stream_Input (Ent);
1423 -------------------
1424 -- Machine_Radix --
1425 -------------------
1427 -- Machine radix attribute definition clause
1429 when Attribute_Machine_Radix => Machine_Radix : declare
1430 Radix : constant Uint := Static_Integer (Expr);
1432 begin
1433 if not Is_Decimal_Fixed_Point_Type (U_Ent) then
1434 Error_Msg_N ("decimal fixed-point type expected for &", Nam);
1436 elsif Has_Machine_Radix_Clause (U_Ent) then
1437 Error_Msg_Sloc := Sloc (Alignment_Clause (U_Ent));
1438 Error_Msg_N ("machine radix clause previously given#", N);
1440 elsif Radix /= No_Uint then
1441 Set_Has_Machine_Radix_Clause (U_Ent);
1442 Set_Has_Non_Standard_Rep (Base_Type (U_Ent));
1444 if Radix = 2 then
1445 null;
1446 elsif Radix = 10 then
1447 Set_Machine_Radix_10 (U_Ent);
1448 else
1449 Error_Msg_N ("machine radix value must be 2 or 10", Expr);
1450 end if;
1451 end if;
1452 end Machine_Radix;
1454 -----------------
1455 -- Object_Size --
1456 -----------------
1458 -- Object_Size attribute definition clause
1460 when Attribute_Object_Size => Object_Size : declare
1461 Size : constant Uint := Static_Integer (Expr);
1463 Biased : Boolean;
1464 pragma Warnings (Off, Biased);
1466 begin
1467 if not Is_Type (U_Ent) then
1468 Error_Msg_N ("Object_Size cannot be given for &", Nam);
1470 elsif Has_Object_Size_Clause (U_Ent) then
1471 Error_Msg_N ("Object_Size already given for &", Nam);
1473 else
1474 Check_Size (Expr, U_Ent, Size, Biased);
1476 if Size /= 8
1477 and then
1478 Size /= 16
1479 and then
1480 Size /= 32
1481 and then
1482 UI_Mod (Size, 64) /= 0
1483 then
1484 Error_Msg_N
1485 ("Object_Size must be 8, 16, 32, or multiple of 64",
1486 Expr);
1487 end if;
1489 Set_Esize (U_Ent, Size);
1490 Set_Has_Object_Size_Clause (U_Ent);
1491 Alignment_Check_For_Esize_Change (U_Ent);
1492 end if;
1493 end Object_Size;
1495 ------------
1496 -- Output --
1497 ------------
1499 when Attribute_Output =>
1500 Analyze_Stream_TSS_Definition (TSS_Stream_Output);
1501 Set_Has_Specified_Stream_Output (Ent);
1503 ----------
1504 -- Read --
1505 ----------
1507 when Attribute_Read =>
1508 Analyze_Stream_TSS_Definition (TSS_Stream_Read);
1509 Set_Has_Specified_Stream_Read (Ent);
1511 ----------
1512 -- Size --
1513 ----------
1515 -- Size attribute definition clause
1517 when Attribute_Size => Size : declare
1518 Size : constant Uint := Static_Integer (Expr);
1519 Etyp : Entity_Id;
1520 Biased : Boolean;
1522 begin
1523 FOnly := True;
1525 if Has_Size_Clause (U_Ent) then
1526 Error_Msg_N ("size already given for &", Nam);
1528 elsif not Is_Type (U_Ent)
1529 and then Ekind (U_Ent) /= E_Variable
1530 and then Ekind (U_Ent) /= E_Constant
1531 then
1532 Error_Msg_N ("size cannot be given for &", Nam);
1534 elsif Is_Array_Type (U_Ent)
1535 and then not Is_Constrained (U_Ent)
1536 then
1537 Error_Msg_N
1538 ("size cannot be given for unconstrained array", Nam);
1540 elsif Size /= No_Uint then
1541 if Is_Type (U_Ent) then
1542 Etyp := U_Ent;
1543 else
1544 Etyp := Etype (U_Ent);
1545 end if;
1547 -- Check size, note that Gigi is in charge of checking that the
1548 -- size of an array or record type is OK. Also we do not check
1549 -- the size in the ordinary fixed-point case, since it is too
1550 -- early to do so (there may be subsequent small clause that
1551 -- affects the size). We can check the size if a small clause
1552 -- has already been given.
1554 if not Is_Ordinary_Fixed_Point_Type (U_Ent)
1555 or else Has_Small_Clause (U_Ent)
1556 then
1557 Check_Size (Expr, Etyp, Size, Biased);
1558 Set_Has_Biased_Representation (U_Ent, Biased);
1560 if Biased and Warn_On_Biased_Representation then
1561 Error_Msg_N
1562 ("?size clause forces biased representation", N);
1563 end if;
1564 end if;
1566 -- For types set RM_Size and Esize if possible
1568 if Is_Type (U_Ent) then
1569 Set_RM_Size (U_Ent, Size);
1571 -- For scalar types, increase Object_Size to power of 2, but
1572 -- not less than a storage unit in any case (i.e., normally
1573 -- this means it will be byte addressable).
1575 if Is_Scalar_Type (U_Ent) then
1576 if Size <= System_Storage_Unit then
1577 Init_Esize (U_Ent, System_Storage_Unit);
1578 elsif Size <= 16 then
1579 Init_Esize (U_Ent, 16);
1580 elsif Size <= 32 then
1581 Init_Esize (U_Ent, 32);
1582 else
1583 Set_Esize (U_Ent, (Size + 63) / 64 * 64);
1584 end if;
1586 -- For all other types, object size = value size. The
1587 -- backend will adjust as needed.
1589 else
1590 Set_Esize (U_Ent, Size);
1591 end if;
1593 Alignment_Check_For_Esize_Change (U_Ent);
1595 -- For objects, set Esize only
1597 else
1598 if Is_Elementary_Type (Etyp) then
1599 if Size /= System_Storage_Unit
1600 and then
1601 Size /= System_Storage_Unit * 2
1602 and then
1603 Size /= System_Storage_Unit * 4
1604 and then
1605 Size /= System_Storage_Unit * 8
1606 then
1607 Error_Msg_Uint_1 := UI_From_Int (System_Storage_Unit);
1608 Error_Msg_Uint_2 := Error_Msg_Uint_1 * 8;
1609 Error_Msg_N
1610 ("size for primitive object must be a power of 2"
1611 & " in the range ^-^", N);
1612 end if;
1613 end if;
1615 Set_Esize (U_Ent, Size);
1616 end if;
1618 Set_Has_Size_Clause (U_Ent);
1619 end if;
1620 end Size;
1622 -----------
1623 -- Small --
1624 -----------
1626 -- Small attribute definition clause
1628 when Attribute_Small => Small : declare
1629 Implicit_Base : constant Entity_Id := Base_Type (U_Ent);
1630 Small : Ureal;
1632 begin
1633 Analyze_And_Resolve (Expr, Any_Real);
1635 if Etype (Expr) = Any_Type then
1636 return;
1638 elsif not Is_Static_Expression (Expr) then
1639 Flag_Non_Static_Expr
1640 ("small requires static expression!", Expr);
1641 return;
1643 else
1644 Small := Expr_Value_R (Expr);
1646 if Small <= Ureal_0 then
1647 Error_Msg_N ("small value must be greater than zero", Expr);
1648 return;
1649 end if;
1651 end if;
1653 if not Is_Ordinary_Fixed_Point_Type (U_Ent) then
1654 Error_Msg_N
1655 ("small requires an ordinary fixed point type", Nam);
1657 elsif Has_Small_Clause (U_Ent) then
1658 Error_Msg_N ("small already given for &", Nam);
1660 elsif Small > Delta_Value (U_Ent) then
1661 Error_Msg_N
1662 ("small value must not be greater then delta value", Nam);
1664 else
1665 Set_Small_Value (U_Ent, Small);
1666 Set_Small_Value (Implicit_Base, Small);
1667 Set_Has_Small_Clause (U_Ent);
1668 Set_Has_Small_Clause (Implicit_Base);
1669 Set_Has_Non_Standard_Rep (Implicit_Base);
1670 end if;
1671 end Small;
1673 ------------------
1674 -- Storage_Pool --
1675 ------------------
1677 -- Storage_Pool attribute definition clause
1679 when Attribute_Storage_Pool => Storage_Pool : declare
1680 Pool : Entity_Id;
1681 T : Entity_Id;
1683 begin
1684 if Ekind (U_Ent) = E_Access_Subprogram_Type then
1685 Error_Msg_N
1686 ("storage pool cannot be given for access-to-subprogram type",
1687 Nam);
1688 return;
1690 elsif not
1691 Ekind_In (U_Ent, E_Access_Type, E_General_Access_Type)
1692 then
1693 Error_Msg_N
1694 ("storage pool can only be given for access types", Nam);
1695 return;
1697 elsif Is_Derived_Type (U_Ent) then
1698 Error_Msg_N
1699 ("storage pool cannot be given for a derived access type",
1700 Nam);
1702 elsif Has_Storage_Size_Clause (U_Ent) then
1703 Error_Msg_N ("storage size already given for &", Nam);
1704 return;
1706 elsif Present (Associated_Storage_Pool (U_Ent)) then
1707 Error_Msg_N ("storage pool already given for &", Nam);
1708 return;
1709 end if;
1711 Analyze_And_Resolve
1712 (Expr, Class_Wide_Type (RTE (RE_Root_Storage_Pool)));
1714 if not Denotes_Variable (Expr) then
1715 Error_Msg_N ("storage pool must be a variable", Expr);
1716 return;
1717 end if;
1719 if Nkind (Expr) = N_Type_Conversion then
1720 T := Etype (Expression (Expr));
1721 else
1722 T := Etype (Expr);
1723 end if;
1725 -- The Stack_Bounded_Pool is used internally for implementing
1726 -- access types with a Storage_Size. Since it only work
1727 -- properly when used on one specific type, we need to check
1728 -- that it is not hijacked improperly:
1729 -- type T is access Integer;
1730 -- for T'Storage_Size use n;
1731 -- type Q is access Float;
1732 -- for Q'Storage_Size use T'Storage_Size; -- incorrect
1734 if RTE_Available (RE_Stack_Bounded_Pool)
1735 and then Base_Type (T) = RTE (RE_Stack_Bounded_Pool)
1736 then
1737 Error_Msg_N ("non-shareable internal Pool", Expr);
1738 return;
1739 end if;
1741 -- If the argument is a name that is not an entity name, then
1742 -- we construct a renaming operation to define an entity of
1743 -- type storage pool.
1745 if not Is_Entity_Name (Expr)
1746 and then Is_Object_Reference (Expr)
1747 then
1748 Pool := Make_Temporary (Loc, 'P', Expr);
1750 declare
1751 Rnode : constant Node_Id :=
1752 Make_Object_Renaming_Declaration (Loc,
1753 Defining_Identifier => Pool,
1754 Subtype_Mark =>
1755 New_Occurrence_Of (Etype (Expr), Loc),
1756 Name => Expr);
1758 begin
1759 Insert_Before (N, Rnode);
1760 Analyze (Rnode);
1761 Set_Associated_Storage_Pool (U_Ent, Pool);
1762 end;
1764 elsif Is_Entity_Name (Expr) then
1765 Pool := Entity (Expr);
1767 -- If pool is a renamed object, get original one. This can
1768 -- happen with an explicit renaming, and within instances.
1770 while Present (Renamed_Object (Pool))
1771 and then Is_Entity_Name (Renamed_Object (Pool))
1772 loop
1773 Pool := Entity (Renamed_Object (Pool));
1774 end loop;
1776 if Present (Renamed_Object (Pool))
1777 and then Nkind (Renamed_Object (Pool)) = N_Type_Conversion
1778 and then Is_Entity_Name (Expression (Renamed_Object (Pool)))
1779 then
1780 Pool := Entity (Expression (Renamed_Object (Pool)));
1781 end if;
1783 Set_Associated_Storage_Pool (U_Ent, Pool);
1785 elsif Nkind (Expr) = N_Type_Conversion
1786 and then Is_Entity_Name (Expression (Expr))
1787 and then Nkind (Original_Node (Expr)) = N_Attribute_Reference
1788 then
1789 Pool := Entity (Expression (Expr));
1790 Set_Associated_Storage_Pool (U_Ent, Pool);
1792 else
1793 Error_Msg_N ("incorrect reference to a Storage Pool", Expr);
1794 return;
1795 end if;
1796 end Storage_Pool;
1798 ------------------
1799 -- Storage_Size --
1800 ------------------
1802 -- Storage_Size attribute definition clause
1804 when Attribute_Storage_Size => Storage_Size : declare
1805 Btype : constant Entity_Id := Base_Type (U_Ent);
1806 Sprag : Node_Id;
1808 begin
1809 if Is_Task_Type (U_Ent) then
1810 Check_Restriction (No_Obsolescent_Features, N);
1812 if Warn_On_Obsolescent_Feature then
1813 Error_Msg_N
1814 ("storage size clause for task is an " &
1815 "obsolescent feature (RM J.9)?", N);
1816 Error_Msg_N ("\use Storage_Size pragma instead?", N);
1817 end if;
1819 FOnly := True;
1820 end if;
1822 if not Is_Access_Type (U_Ent)
1823 and then Ekind (U_Ent) /= E_Task_Type
1824 then
1825 Error_Msg_N ("storage size cannot be given for &", Nam);
1827 elsif Is_Access_Type (U_Ent) and Is_Derived_Type (U_Ent) then
1828 Error_Msg_N
1829 ("storage size cannot be given for a derived access type",
1830 Nam);
1832 elsif Has_Storage_Size_Clause (Btype) then
1833 Error_Msg_N ("storage size already given for &", Nam);
1835 else
1836 Analyze_And_Resolve (Expr, Any_Integer);
1838 if Is_Access_Type (U_Ent) then
1839 if Present (Associated_Storage_Pool (U_Ent)) then
1840 Error_Msg_N ("storage pool already given for &", Nam);
1841 return;
1842 end if;
1844 if Compile_Time_Known_Value (Expr)
1845 and then Expr_Value (Expr) = 0
1846 then
1847 Set_No_Pool_Assigned (Btype);
1848 end if;
1850 else -- Is_Task_Type (U_Ent)
1851 Sprag := Get_Rep_Pragma (Btype, Name_Storage_Size);
1853 if Present (Sprag) then
1854 Error_Msg_Sloc := Sloc (Sprag);
1855 Error_Msg_N
1856 ("Storage_Size already specified#", Nam);
1857 return;
1858 end if;
1859 end if;
1861 Set_Has_Storage_Size_Clause (Btype);
1862 end if;
1863 end Storage_Size;
1865 -----------------
1866 -- Stream_Size --
1867 -----------------
1869 when Attribute_Stream_Size => Stream_Size : declare
1870 Size : constant Uint := Static_Integer (Expr);
1872 begin
1873 if Ada_Version <= Ada_95 then
1874 Check_Restriction (No_Implementation_Attributes, N);
1875 end if;
1877 if Has_Stream_Size_Clause (U_Ent) then
1878 Error_Msg_N ("Stream_Size already given for &", Nam);
1880 elsif Is_Elementary_Type (U_Ent) then
1881 if Size /= System_Storage_Unit
1882 and then
1883 Size /= System_Storage_Unit * 2
1884 and then
1885 Size /= System_Storage_Unit * 4
1886 and then
1887 Size /= System_Storage_Unit * 8
1888 then
1889 Error_Msg_Uint_1 := UI_From_Int (System_Storage_Unit);
1890 Error_Msg_N
1891 ("stream size for elementary type must be a"
1892 & " power of 2 and at least ^", N);
1894 elsif RM_Size (U_Ent) > Size then
1895 Error_Msg_Uint_1 := RM_Size (U_Ent);
1896 Error_Msg_N
1897 ("stream size for elementary type must be a"
1898 & " power of 2 and at least ^", N);
1899 end if;
1901 Set_Has_Stream_Size_Clause (U_Ent);
1903 else
1904 Error_Msg_N ("Stream_Size cannot be given for &", Nam);
1905 end if;
1906 end Stream_Size;
1908 ----------------
1909 -- Value_Size --
1910 ----------------
1912 -- Value_Size attribute definition clause
1914 when Attribute_Value_Size => Value_Size : declare
1915 Size : constant Uint := Static_Integer (Expr);
1916 Biased : Boolean;
1918 begin
1919 if not Is_Type (U_Ent) then
1920 Error_Msg_N ("Value_Size cannot be given for &", Nam);
1922 elsif Present
1923 (Get_Attribute_Definition_Clause
1924 (U_Ent, Attribute_Value_Size))
1925 then
1926 Error_Msg_N ("Value_Size already given for &", Nam);
1928 elsif Is_Array_Type (U_Ent)
1929 and then not Is_Constrained (U_Ent)
1930 then
1931 Error_Msg_N
1932 ("Value_Size cannot be given for unconstrained array", Nam);
1934 else
1935 if Is_Elementary_Type (U_Ent) then
1936 Check_Size (Expr, U_Ent, Size, Biased);
1937 Set_Has_Biased_Representation (U_Ent, Biased);
1939 if Biased and Warn_On_Biased_Representation then
1940 Error_Msg_N
1941 ("?value size clause forces biased representation", N);
1942 end if;
1943 end if;
1945 Set_RM_Size (U_Ent, Size);
1946 end if;
1947 end Value_Size;
1949 -----------
1950 -- Write --
1951 -----------
1953 when Attribute_Write =>
1954 Analyze_Stream_TSS_Definition (TSS_Stream_Write);
1955 Set_Has_Specified_Stream_Write (Ent);
1957 -- All other attributes cannot be set
1959 when others =>
1960 Error_Msg_N
1961 ("attribute& cannot be set with definition clause", N);
1962 end case;
1964 -- The test for the type being frozen must be performed after
1965 -- any expression the clause has been analyzed since the expression
1966 -- itself might cause freezing that makes the clause illegal.
1968 if Rep_Item_Too_Late (U_Ent, N, FOnly) then
1969 return;
1970 end if;
1971 end Analyze_Attribute_Definition_Clause;
1973 ----------------------------
1974 -- Analyze_Code_Statement --
1975 ----------------------------
1977 procedure Analyze_Code_Statement (N : Node_Id) is
1978 HSS : constant Node_Id := Parent (N);
1979 SBody : constant Node_Id := Parent (HSS);
1980 Subp : constant Entity_Id := Current_Scope;
1981 Stmt : Node_Id;
1982 Decl : Node_Id;
1983 StmtO : Node_Id;
1984 DeclO : Node_Id;
1986 begin
1987 -- Analyze and check we get right type, note that this implements the
1988 -- requirement (RM 13.8(1)) that Machine_Code be with'ed, since that
1989 -- is the only way that Asm_Insn could possibly be visible.
1991 Analyze_And_Resolve (Expression (N));
1993 if Etype (Expression (N)) = Any_Type then
1994 return;
1995 elsif Etype (Expression (N)) /= RTE (RE_Asm_Insn) then
1996 Error_Msg_N ("incorrect type for code statement", N);
1997 return;
1998 end if;
2000 Check_Code_Statement (N);
2002 -- Make sure we appear in the handled statement sequence of a
2003 -- subprogram (RM 13.8(3)).
2005 if Nkind (HSS) /= N_Handled_Sequence_Of_Statements
2006 or else Nkind (SBody) /= N_Subprogram_Body
2007 then
2008 Error_Msg_N
2009 ("code statement can only appear in body of subprogram", N);
2010 return;
2011 end if;
2013 -- Do remaining checks (RM 13.8(3)) if not already done
2015 if not Is_Machine_Code_Subprogram (Subp) then
2016 Set_Is_Machine_Code_Subprogram (Subp);
2018 -- No exception handlers allowed
2020 if Present (Exception_Handlers (HSS)) then
2021 Error_Msg_N
2022 ("exception handlers not permitted in machine code subprogram",
2023 First (Exception_Handlers (HSS)));
2024 end if;
2026 -- No declarations other than use clauses and pragmas (we allow
2027 -- certain internally generated declarations as well).
2029 Decl := First (Declarations (SBody));
2030 while Present (Decl) loop
2031 DeclO := Original_Node (Decl);
2032 if Comes_From_Source (DeclO)
2033 and not Nkind_In (DeclO, N_Pragma,
2034 N_Use_Package_Clause,
2035 N_Use_Type_Clause,
2036 N_Implicit_Label_Declaration)
2037 then
2038 Error_Msg_N
2039 ("this declaration not allowed in machine code subprogram",
2040 DeclO);
2041 end if;
2043 Next (Decl);
2044 end loop;
2046 -- No statements other than code statements, pragmas, and labels.
2047 -- Again we allow certain internally generated statements.
2049 Stmt := First (Statements (HSS));
2050 while Present (Stmt) loop
2051 StmtO := Original_Node (Stmt);
2052 if Comes_From_Source (StmtO)
2053 and then not Nkind_In (StmtO, N_Pragma,
2054 N_Label,
2055 N_Code_Statement)
2056 then
2057 Error_Msg_N
2058 ("this statement is not allowed in machine code subprogram",
2059 StmtO);
2060 end if;
2062 Next (Stmt);
2063 end loop;
2064 end if;
2065 end Analyze_Code_Statement;
2067 -----------------------------------------------
2068 -- Analyze_Enumeration_Representation_Clause --
2069 -----------------------------------------------
2071 procedure Analyze_Enumeration_Representation_Clause (N : Node_Id) is
2072 Ident : constant Node_Id := Identifier (N);
2073 Aggr : constant Node_Id := Array_Aggregate (N);
2074 Enumtype : Entity_Id;
2075 Elit : Entity_Id;
2076 Expr : Node_Id;
2077 Assoc : Node_Id;
2078 Choice : Node_Id;
2079 Val : Uint;
2080 Err : Boolean := False;
2082 Lo : constant Uint := Expr_Value (Type_Low_Bound (Universal_Integer));
2083 Hi : constant Uint := Expr_Value (Type_High_Bound (Universal_Integer));
2084 Min : Uint;
2085 Max : Uint;
2087 begin
2088 if Ignore_Rep_Clauses then
2089 return;
2090 end if;
2092 -- First some basic error checks
2094 Find_Type (Ident);
2095 Enumtype := Entity (Ident);
2097 if Enumtype = Any_Type
2098 or else Rep_Item_Too_Early (Enumtype, N)
2099 then
2100 return;
2101 else
2102 Enumtype := Underlying_Type (Enumtype);
2103 end if;
2105 if not Is_Enumeration_Type (Enumtype) then
2106 Error_Msg_NE
2107 ("enumeration type required, found}",
2108 Ident, First_Subtype (Enumtype));
2109 return;
2110 end if;
2112 -- Ignore rep clause on generic actual type. This will already have
2113 -- been flagged on the template as an error, and this is the safest
2114 -- way to ensure we don't get a junk cascaded message in the instance.
2116 if Is_Generic_Actual_Type (Enumtype) then
2117 return;
2119 -- Type must be in current scope
2121 elsif Scope (Enumtype) /= Current_Scope then
2122 Error_Msg_N ("type must be declared in this scope", Ident);
2123 return;
2125 -- Type must be a first subtype
2127 elsif not Is_First_Subtype (Enumtype) then
2128 Error_Msg_N ("cannot give enumeration rep clause for subtype", N);
2129 return;
2131 -- Ignore duplicate rep clause
2133 elsif Has_Enumeration_Rep_Clause (Enumtype) then
2134 Error_Msg_N ("duplicate enumeration rep clause ignored", N);
2135 return;
2137 -- Don't allow rep clause for standard [wide_[wide_]]character
2139 elsif Is_Standard_Character_Type (Enumtype) then
2140 Error_Msg_N ("enumeration rep clause not allowed for this type", N);
2141 return;
2143 -- Check that the expression is a proper aggregate (no parentheses)
2145 elsif Paren_Count (Aggr) /= 0 then
2146 Error_Msg
2147 ("extra parentheses surrounding aggregate not allowed",
2148 First_Sloc (Aggr));
2149 return;
2151 -- All tests passed, so set rep clause in place
2153 else
2154 Set_Has_Enumeration_Rep_Clause (Enumtype);
2155 Set_Has_Enumeration_Rep_Clause (Base_Type (Enumtype));
2156 end if;
2158 -- Now we process the aggregate. Note that we don't use the normal
2159 -- aggregate code for this purpose, because we don't want any of the
2160 -- normal expansion activities, and a number of special semantic
2161 -- rules apply (including the component type being any integer type)
2163 Elit := First_Literal (Enumtype);
2165 -- First the positional entries if any
2167 if Present (Expressions (Aggr)) then
2168 Expr := First (Expressions (Aggr));
2169 while Present (Expr) loop
2170 if No (Elit) then
2171 Error_Msg_N ("too many entries in aggregate", Expr);
2172 return;
2173 end if;
2175 Val := Static_Integer (Expr);
2177 -- Err signals that we found some incorrect entries processing
2178 -- the list. The final checks for completeness and ordering are
2179 -- skipped in this case.
2181 if Val = No_Uint then
2182 Err := True;
2183 elsif Val < Lo or else Hi < Val then
2184 Error_Msg_N ("value outside permitted range", Expr);
2185 Err := True;
2186 end if;
2188 Set_Enumeration_Rep (Elit, Val);
2189 Set_Enumeration_Rep_Expr (Elit, Expr);
2190 Next (Expr);
2191 Next (Elit);
2192 end loop;
2193 end if;
2195 -- Now process the named entries if present
2197 if Present (Component_Associations (Aggr)) then
2198 Assoc := First (Component_Associations (Aggr));
2199 while Present (Assoc) loop
2200 Choice := First (Choices (Assoc));
2202 if Present (Next (Choice)) then
2203 Error_Msg_N
2204 ("multiple choice not allowed here", Next (Choice));
2205 Err := True;
2206 end if;
2208 if Nkind (Choice) = N_Others_Choice then
2209 Error_Msg_N ("others choice not allowed here", Choice);
2210 Err := True;
2212 elsif Nkind (Choice) = N_Range then
2213 -- ??? should allow zero/one element range here
2214 Error_Msg_N ("range not allowed here", Choice);
2215 Err := True;
2217 else
2218 Analyze_And_Resolve (Choice, Enumtype);
2220 if Is_Entity_Name (Choice)
2221 and then Is_Type (Entity (Choice))
2222 then
2223 Error_Msg_N ("subtype name not allowed here", Choice);
2224 Err := True;
2225 -- ??? should allow static subtype with zero/one entry
2227 elsif Etype (Choice) = Base_Type (Enumtype) then
2228 if not Is_Static_Expression (Choice) then
2229 Flag_Non_Static_Expr
2230 ("non-static expression used for choice!", Choice);
2231 Err := True;
2233 else
2234 Elit := Expr_Value_E (Choice);
2236 if Present (Enumeration_Rep_Expr (Elit)) then
2237 Error_Msg_Sloc := Sloc (Enumeration_Rep_Expr (Elit));
2238 Error_Msg_NE
2239 ("representation for& previously given#",
2240 Choice, Elit);
2241 Err := True;
2242 end if;
2244 Set_Enumeration_Rep_Expr (Elit, Choice);
2246 Expr := Expression (Assoc);
2247 Val := Static_Integer (Expr);
2249 if Val = No_Uint then
2250 Err := True;
2252 elsif Val < Lo or else Hi < Val then
2253 Error_Msg_N ("value outside permitted range", Expr);
2254 Err := True;
2255 end if;
2257 Set_Enumeration_Rep (Elit, Val);
2258 end if;
2259 end if;
2260 end if;
2262 Next (Assoc);
2263 end loop;
2264 end if;
2266 -- Aggregate is fully processed. Now we check that a full set of
2267 -- representations was given, and that they are in range and in order.
2268 -- These checks are only done if no other errors occurred.
2270 if not Err then
2271 Min := No_Uint;
2272 Max := No_Uint;
2274 Elit := First_Literal (Enumtype);
2275 while Present (Elit) loop
2276 if No (Enumeration_Rep_Expr (Elit)) then
2277 Error_Msg_NE ("missing representation for&!", N, Elit);
2279 else
2280 Val := Enumeration_Rep (Elit);
2282 if Min = No_Uint then
2283 Min := Val;
2284 end if;
2286 if Val /= No_Uint then
2287 if Max /= No_Uint and then Val <= Max then
2288 Error_Msg_NE
2289 ("enumeration value for& not ordered!",
2290 Enumeration_Rep_Expr (Elit), Elit);
2291 end if;
2293 Max := Val;
2294 end if;
2296 -- If there is at least one literal whose representation
2297 -- is not equal to the Pos value, then note that this
2298 -- enumeration type has a non-standard representation.
2300 if Val /= Enumeration_Pos (Elit) then
2301 Set_Has_Non_Standard_Rep (Base_Type (Enumtype));
2302 end if;
2303 end if;
2305 Next (Elit);
2306 end loop;
2308 -- Now set proper size information
2310 declare
2311 Minsize : Uint := UI_From_Int (Minimum_Size (Enumtype));
2313 begin
2314 if Has_Size_Clause (Enumtype) then
2315 if Esize (Enumtype) >= Minsize then
2316 null;
2318 else
2319 Minsize :=
2320 UI_From_Int (Minimum_Size (Enumtype, Biased => True));
2322 if Esize (Enumtype) < Minsize then
2323 Error_Msg_N ("previously given size is too small", N);
2325 else
2326 Set_Has_Biased_Representation (Enumtype);
2327 end if;
2328 end if;
2330 else
2331 Set_RM_Size (Enumtype, Minsize);
2332 Set_Enum_Esize (Enumtype);
2333 end if;
2335 Set_RM_Size (Base_Type (Enumtype), RM_Size (Enumtype));
2336 Set_Esize (Base_Type (Enumtype), Esize (Enumtype));
2337 Set_Alignment (Base_Type (Enumtype), Alignment (Enumtype));
2338 end;
2339 end if;
2341 -- We repeat the too late test in case it froze itself!
2343 if Rep_Item_Too_Late (Enumtype, N) then
2344 null;
2345 end if;
2346 end Analyze_Enumeration_Representation_Clause;
2348 ----------------------------
2349 -- Analyze_Free_Statement --
2350 ----------------------------
2352 procedure Analyze_Free_Statement (N : Node_Id) is
2353 begin
2354 Analyze (Expression (N));
2355 end Analyze_Free_Statement;
2357 ---------------------------
2358 -- Analyze_Freeze_Entity --
2359 ---------------------------
2361 procedure Analyze_Freeze_Entity (N : Node_Id) is
2362 E : constant Entity_Id := Entity (N);
2364 begin
2365 -- For tagged types covering interfaces add internal entities that link
2366 -- the primitives of the interfaces with the primitives that cover them.
2368 -- Note: These entities were originally generated only when generating
2369 -- code because their main purpose was to provide support to initialize
2370 -- the secondary dispatch tables. They are now generated also when
2371 -- compiling with no code generation to provide ASIS the relationship
2372 -- between interface primitives and tagged type primitives. They are
2373 -- also used to locate primitives covering interfaces when processing
2374 -- generics (see Derive_Subprograms).
2376 if Ada_Version >= Ada_05
2377 and then Ekind (E) = E_Record_Type
2378 and then Is_Tagged_Type (E)
2379 and then not Is_Interface (E)
2380 and then Has_Interfaces (E)
2381 then
2382 -- This would be a good common place to call the routine that checks
2383 -- overriding of interface primitives (and thus factorize calls to
2384 -- Check_Abstract_Overriding located at different contexts in the
2385 -- compiler). However, this is not possible because it causes
2386 -- spurious errors in case of late overriding.
2388 Add_Internal_Interface_Entities (E);
2389 end if;
2391 -- Check CPP types
2393 if Ekind (E) = E_Record_Type
2394 and then Is_CPP_Class (E)
2395 and then Is_Tagged_Type (E)
2396 and then Tagged_Type_Expansion
2397 and then Expander_Active
2398 then
2399 if CPP_Num_Prims (E) = 0 then
2401 -- If the CPP type has user defined components then it must import
2402 -- primitives from C++. This is required because if the C++ class
2403 -- has no primitives then the C++ compiler does not added the _tag
2404 -- component to the type.
2406 pragma Assert (Chars (First_Entity (E)) = Name_uTag);
2408 if First_Entity (E) /= Last_Entity (E) then
2409 Error_Msg_N
2410 ("?'C'P'P type must import at least one primitive from C++",
2412 end if;
2413 end if;
2415 -- Check that all its primitives are abstract or imported from C++.
2416 -- Check also availability of the C++ constructor.
2418 declare
2419 Has_Constructors : constant Boolean := Has_CPP_Constructors (E);
2420 Elmt : Elmt_Id;
2421 Error_Reported : Boolean := False;
2422 Prim : Node_Id;
2424 begin
2425 Elmt := First_Elmt (Primitive_Operations (E));
2426 while Present (Elmt) loop
2427 Prim := Node (Elmt);
2429 if Comes_From_Source (Prim) then
2430 if Is_Abstract_Subprogram (Prim) then
2431 null;
2433 elsif not Is_Imported (Prim)
2434 or else Convention (Prim) /= Convention_CPP
2435 then
2436 Error_Msg_N
2437 ("?primitives of 'C'P'P types must be imported from C++"
2438 & " or abstract", Prim);
2440 elsif not Has_Constructors
2441 and then not Error_Reported
2442 then
2443 Error_Msg_Name_1 := Chars (E);
2444 Error_Msg_N
2445 ("?'C'P'P constructor required for type %", Prim);
2446 Error_Reported := True;
2447 end if;
2448 end if;
2450 Next_Elmt (Elmt);
2451 end loop;
2452 end;
2453 end if;
2454 end Analyze_Freeze_Entity;
2456 ------------------------------------------
2457 -- Analyze_Record_Representation_Clause --
2458 ------------------------------------------
2460 -- Note: we check as much as we can here, but we can't do any checks
2461 -- based on the position values (e.g. overlap checks) until freeze time
2462 -- because especially in Ada 2005 (machine scalar mode), the processing
2463 -- for non-standard bit order can substantially change the positions.
2464 -- See procedure Check_Record_Representation_Clause (called from Freeze)
2465 -- for the remainder of this processing.
2467 procedure Analyze_Record_Representation_Clause (N : Node_Id) is
2468 Ident : constant Node_Id := Identifier (N);
2469 Rectype : Entity_Id;
2470 CC : Node_Id;
2471 Posit : Uint;
2472 Fbit : Uint;
2473 Lbit : Uint;
2474 Hbit : Uint := Uint_0;
2475 Comp : Entity_Id;
2476 Ocomp : Entity_Id;
2477 Biased : Boolean;
2479 CR_Pragma : Node_Id := Empty;
2480 -- Points to N_Pragma node if Complete_Representation pragma present
2482 begin
2483 if Ignore_Rep_Clauses then
2484 return;
2485 end if;
2487 Find_Type (Ident);
2488 Rectype := Entity (Ident);
2490 if Rectype = Any_Type
2491 or else Rep_Item_Too_Early (Rectype, N)
2492 then
2493 return;
2494 else
2495 Rectype := Underlying_Type (Rectype);
2496 end if;
2498 -- First some basic error checks
2500 if not Is_Record_Type (Rectype) then
2501 Error_Msg_NE
2502 ("record type required, found}", Ident, First_Subtype (Rectype));
2503 return;
2505 elsif Is_Unchecked_Union (Rectype) then
2506 Error_Msg_N
2507 ("record rep clause not allowed for Unchecked_Union", N);
2509 elsif Scope (Rectype) /= Current_Scope then
2510 Error_Msg_N ("type must be declared in this scope", N);
2511 return;
2513 elsif not Is_First_Subtype (Rectype) then
2514 Error_Msg_N ("cannot give record rep clause for subtype", N);
2515 return;
2517 elsif Has_Record_Rep_Clause (Rectype) then
2518 Error_Msg_N ("duplicate record rep clause ignored", N);
2519 return;
2521 elsif Rep_Item_Too_Late (Rectype, N) then
2522 return;
2523 end if;
2525 if Present (Mod_Clause (N)) then
2526 declare
2527 Loc : constant Source_Ptr := Sloc (N);
2528 M : constant Node_Id := Mod_Clause (N);
2529 P : constant List_Id := Pragmas_Before (M);
2530 AtM_Nod : Node_Id;
2532 Mod_Val : Uint;
2533 pragma Warnings (Off, Mod_Val);
2535 begin
2536 Check_Restriction (No_Obsolescent_Features, Mod_Clause (N));
2538 if Warn_On_Obsolescent_Feature then
2539 Error_Msg_N
2540 ("mod clause is an obsolescent feature (RM J.8)?", N);
2541 Error_Msg_N
2542 ("\use alignment attribute definition clause instead?", N);
2543 end if;
2545 if Present (P) then
2546 Analyze_List (P);
2547 end if;
2549 -- In ASIS_Mode mode, expansion is disabled, but we must convert
2550 -- the Mod clause into an alignment clause anyway, so that the
2551 -- back-end can compute and back-annotate properly the size and
2552 -- alignment of types that may include this record.
2554 -- This seems dubious, this destroys the source tree in a manner
2555 -- not detectable by ASIS ???
2557 if Operating_Mode = Check_Semantics
2558 and then ASIS_Mode
2559 then
2560 AtM_Nod :=
2561 Make_Attribute_Definition_Clause (Loc,
2562 Name => New_Reference_To (Base_Type (Rectype), Loc),
2563 Chars => Name_Alignment,
2564 Expression => Relocate_Node (Expression (M)));
2566 Set_From_At_Mod (AtM_Nod);
2567 Insert_After (N, AtM_Nod);
2568 Mod_Val := Get_Alignment_Value (Expression (AtM_Nod));
2569 Set_Mod_Clause (N, Empty);
2571 else
2572 -- Get the alignment value to perform error checking
2574 Mod_Val := Get_Alignment_Value (Expression (M));
2575 end if;
2576 end;
2577 end if;
2579 -- For untagged types, clear any existing component clauses for the
2580 -- type. If the type is derived, this is what allows us to override
2581 -- a rep clause for the parent. For type extensions, the representation
2582 -- of the inherited components is inherited, so we want to keep previous
2583 -- component clauses for completeness.
2585 if not Is_Tagged_Type (Rectype) then
2586 Comp := First_Component_Or_Discriminant (Rectype);
2587 while Present (Comp) loop
2588 Set_Component_Clause (Comp, Empty);
2589 Next_Component_Or_Discriminant (Comp);
2590 end loop;
2591 end if;
2593 -- All done if no component clauses
2595 CC := First (Component_Clauses (N));
2597 if No (CC) then
2598 return;
2599 end if;
2601 -- A representation like this applies to the base type
2603 Set_Has_Record_Rep_Clause (Base_Type (Rectype));
2604 Set_Has_Non_Standard_Rep (Base_Type (Rectype));
2605 Set_Has_Specified_Layout (Base_Type (Rectype));
2607 -- Process the component clauses
2609 while Present (CC) loop
2611 -- Pragma
2613 if Nkind (CC) = N_Pragma then
2614 Analyze (CC);
2616 -- The only pragma of interest is Complete_Representation
2618 if Pragma_Name (CC) = Name_Complete_Representation then
2619 CR_Pragma := CC;
2620 end if;
2622 -- Processing for real component clause
2624 else
2625 Posit := Static_Integer (Position (CC));
2626 Fbit := Static_Integer (First_Bit (CC));
2627 Lbit := Static_Integer (Last_Bit (CC));
2629 if Posit /= No_Uint
2630 and then Fbit /= No_Uint
2631 and then Lbit /= No_Uint
2632 then
2633 if Posit < 0 then
2634 Error_Msg_N
2635 ("position cannot be negative", Position (CC));
2637 elsif Fbit < 0 then
2638 Error_Msg_N
2639 ("first bit cannot be negative", First_Bit (CC));
2641 -- The Last_Bit specified in a component clause must not be
2642 -- less than the First_Bit minus one (RM-13.5.1(10)).
2644 elsif Lbit < Fbit - 1 then
2645 Error_Msg_N
2646 ("last bit cannot be less than first bit minus one",
2647 Last_Bit (CC));
2649 -- Values look OK, so find the corresponding record component
2650 -- Even though the syntax allows an attribute reference for
2651 -- implementation-defined components, GNAT does not allow the
2652 -- tag to get an explicit position.
2654 elsif Nkind (Component_Name (CC)) = N_Attribute_Reference then
2655 if Attribute_Name (Component_Name (CC)) = Name_Tag then
2656 Error_Msg_N ("position of tag cannot be specified", CC);
2657 else
2658 Error_Msg_N ("illegal component name", CC);
2659 end if;
2661 else
2662 Comp := First_Entity (Rectype);
2663 while Present (Comp) loop
2664 exit when Chars (Comp) = Chars (Component_Name (CC));
2665 Next_Entity (Comp);
2666 end loop;
2668 if No (Comp) then
2670 -- Maybe component of base type that is absent from
2671 -- statically constrained first subtype.
2673 Comp := First_Entity (Base_Type (Rectype));
2674 while Present (Comp) loop
2675 exit when Chars (Comp) = Chars (Component_Name (CC));
2676 Next_Entity (Comp);
2677 end loop;
2678 end if;
2680 if No (Comp) then
2681 Error_Msg_N
2682 ("component clause is for non-existent field", CC);
2684 elsif Present (Component_Clause (Comp)) then
2686 -- Diagnose duplicate rep clause, or check consistency
2687 -- if this is an inherited component. In a double fault,
2688 -- there may be a duplicate inconsistent clause for an
2689 -- inherited component.
2691 if Scope (Original_Record_Component (Comp)) = Rectype
2692 or else Parent (Component_Clause (Comp)) = N
2693 then
2694 Error_Msg_Sloc := Sloc (Component_Clause (Comp));
2695 Error_Msg_N ("component clause previously given#", CC);
2697 else
2698 declare
2699 Rep1 : constant Node_Id := Component_Clause (Comp);
2700 begin
2701 if Intval (Position (Rep1)) /=
2702 Intval (Position (CC))
2703 or else Intval (First_Bit (Rep1)) /=
2704 Intval (First_Bit (CC))
2705 or else Intval (Last_Bit (Rep1)) /=
2706 Intval (Last_Bit (CC))
2707 then
2708 Error_Msg_N ("component clause inconsistent "
2709 & "with representation of ancestor", CC);
2710 elsif Warn_On_Redundant_Constructs then
2711 Error_Msg_N ("?redundant component clause "
2712 & "for inherited component!", CC);
2713 end if;
2714 end;
2715 end if;
2717 -- Normal case where this is the first component clause we
2718 -- have seen for this entity, so set it up properly.
2720 else
2721 -- Make reference for field in record rep clause and set
2722 -- appropriate entity field in the field identifier.
2724 Generate_Reference
2725 (Comp, Component_Name (CC), Set_Ref => False);
2726 Set_Entity (Component_Name (CC), Comp);
2728 -- Update Fbit and Lbit to the actual bit number
2730 Fbit := Fbit + UI_From_Int (SSU) * Posit;
2731 Lbit := Lbit + UI_From_Int (SSU) * Posit;
2733 if Has_Size_Clause (Rectype)
2734 and then Esize (Rectype) <= Lbit
2735 then
2736 Error_Msg_N
2737 ("bit number out of range of specified size",
2738 Last_Bit (CC));
2739 else
2740 Set_Component_Clause (Comp, CC);
2741 Set_Component_Bit_Offset (Comp, Fbit);
2742 Set_Esize (Comp, 1 + (Lbit - Fbit));
2743 Set_Normalized_First_Bit (Comp, Fbit mod SSU);
2744 Set_Normalized_Position (Comp, Fbit / SSU);
2746 -- This information is also set in the corresponding
2747 -- component of the base type, found by accessing the
2748 -- Original_Record_Component link if it is present.
2750 Ocomp := Original_Record_Component (Comp);
2752 if Hbit < Lbit then
2753 Hbit := Lbit;
2754 end if;
2756 Check_Size
2757 (Component_Name (CC),
2758 Etype (Comp),
2759 Esize (Comp),
2760 Biased);
2762 Set_Has_Biased_Representation (Comp, Biased);
2764 if Biased and Warn_On_Biased_Representation then
2765 Error_Msg_F
2766 ("?component clause forces biased "
2767 & "representation", CC);
2768 end if;
2770 if Present (Ocomp) then
2771 Set_Component_Clause (Ocomp, CC);
2772 Set_Component_Bit_Offset (Ocomp, Fbit);
2773 Set_Normalized_First_Bit (Ocomp, Fbit mod SSU);
2774 Set_Normalized_Position (Ocomp, Fbit / SSU);
2775 Set_Esize (Ocomp, 1 + (Lbit - Fbit));
2777 Set_Normalized_Position_Max
2778 (Ocomp, Normalized_Position (Ocomp));
2780 Set_Has_Biased_Representation
2781 (Ocomp, Has_Biased_Representation (Comp));
2782 end if;
2784 if Esize (Comp) < 0 then
2785 Error_Msg_N ("component size is negative", CC);
2786 end if;
2787 end if;
2788 end if;
2789 end if;
2790 end if;
2791 end if;
2793 Next (CC);
2794 end loop;
2796 -- Check missing components if Complete_Representation pragma appeared
2798 if Present (CR_Pragma) then
2799 Comp := First_Component_Or_Discriminant (Rectype);
2800 while Present (Comp) loop
2801 if No (Component_Clause (Comp)) then
2802 Error_Msg_NE
2803 ("missing component clause for &", CR_Pragma, Comp);
2804 end if;
2806 Next_Component_Or_Discriminant (Comp);
2807 end loop;
2809 -- If no Complete_Representation pragma, warn if missing components
2811 elsif Warn_On_Unrepped_Components then
2812 declare
2813 Num_Repped_Components : Nat := 0;
2814 Num_Unrepped_Components : Nat := 0;
2816 begin
2817 -- First count number of repped and unrepped components
2819 Comp := First_Component_Or_Discriminant (Rectype);
2820 while Present (Comp) loop
2821 if Present (Component_Clause (Comp)) then
2822 Num_Repped_Components := Num_Repped_Components + 1;
2823 else
2824 Num_Unrepped_Components := Num_Unrepped_Components + 1;
2825 end if;
2827 Next_Component_Or_Discriminant (Comp);
2828 end loop;
2830 -- We are only interested in the case where there is at least one
2831 -- unrepped component, and at least half the components have rep
2832 -- clauses. We figure that if less than half have them, then the
2833 -- partial rep clause is really intentional. If the component
2834 -- type has no underlying type set at this point (as for a generic
2835 -- formal type), we don't know enough to give a warning on the
2836 -- component.
2838 if Num_Unrepped_Components > 0
2839 and then Num_Unrepped_Components < Num_Repped_Components
2840 then
2841 Comp := First_Component_Or_Discriminant (Rectype);
2842 while Present (Comp) loop
2843 if No (Component_Clause (Comp))
2844 and then Comes_From_Source (Comp)
2845 and then Present (Underlying_Type (Etype (Comp)))
2846 and then (Is_Scalar_Type (Underlying_Type (Etype (Comp)))
2847 or else Size_Known_At_Compile_Time
2848 (Underlying_Type (Etype (Comp))))
2849 and then not Has_Warnings_Off (Rectype)
2850 then
2851 Error_Msg_Sloc := Sloc (Comp);
2852 Error_Msg_NE
2853 ("?no component clause given for & declared #",
2854 N, Comp);
2855 end if;
2857 Next_Component_Or_Discriminant (Comp);
2858 end loop;
2859 end if;
2860 end;
2861 end if;
2862 end Analyze_Record_Representation_Clause;
2864 -----------------------------------
2865 -- Check_Constant_Address_Clause --
2866 -----------------------------------
2868 procedure Check_Constant_Address_Clause
2869 (Expr : Node_Id;
2870 U_Ent : Entity_Id)
2872 procedure Check_At_Constant_Address (Nod : Node_Id);
2873 -- Checks that the given node N represents a name whose 'Address is
2874 -- constant (in the same sense as OK_Constant_Address_Clause, i.e. the
2875 -- address value is the same at the point of declaration of U_Ent and at
2876 -- the time of elaboration of the address clause.
2878 procedure Check_Expr_Constants (Nod : Node_Id);
2879 -- Checks that Nod meets the requirements for a constant address clause
2880 -- in the sense of the enclosing procedure.
2882 procedure Check_List_Constants (Lst : List_Id);
2883 -- Check that all elements of list Lst meet the requirements for a
2884 -- constant address clause in the sense of the enclosing procedure.
2886 -------------------------------
2887 -- Check_At_Constant_Address --
2888 -------------------------------
2890 procedure Check_At_Constant_Address (Nod : Node_Id) is
2891 begin
2892 if Is_Entity_Name (Nod) then
2893 if Present (Address_Clause (Entity ((Nod)))) then
2894 Error_Msg_NE
2895 ("invalid address clause for initialized object &!",
2896 Nod, U_Ent);
2897 Error_Msg_NE
2898 ("address for& cannot" &
2899 " depend on another address clause! (RM 13.1(22))!",
2900 Nod, U_Ent);
2902 elsif In_Same_Source_Unit (Entity (Nod), U_Ent)
2903 and then Sloc (U_Ent) < Sloc (Entity (Nod))
2904 then
2905 Error_Msg_NE
2906 ("invalid address clause for initialized object &!",
2907 Nod, U_Ent);
2908 Error_Msg_Node_2 := U_Ent;
2909 Error_Msg_NE
2910 ("\& must be defined before & (RM 13.1(22))!",
2911 Nod, Entity (Nod));
2912 end if;
2914 elsif Nkind (Nod) = N_Selected_Component then
2915 declare
2916 T : constant Entity_Id := Etype (Prefix (Nod));
2918 begin
2919 if (Is_Record_Type (T)
2920 and then Has_Discriminants (T))
2921 or else
2922 (Is_Access_Type (T)
2923 and then Is_Record_Type (Designated_Type (T))
2924 and then Has_Discriminants (Designated_Type (T)))
2925 then
2926 Error_Msg_NE
2927 ("invalid address clause for initialized object &!",
2928 Nod, U_Ent);
2929 Error_Msg_N
2930 ("\address cannot depend on component" &
2931 " of discriminated record (RM 13.1(22))!",
2932 Nod);
2933 else
2934 Check_At_Constant_Address (Prefix (Nod));
2935 end if;
2936 end;
2938 elsif Nkind (Nod) = N_Indexed_Component then
2939 Check_At_Constant_Address (Prefix (Nod));
2940 Check_List_Constants (Expressions (Nod));
2942 else
2943 Check_Expr_Constants (Nod);
2944 end if;
2945 end Check_At_Constant_Address;
2947 --------------------------
2948 -- Check_Expr_Constants --
2949 --------------------------
2951 procedure Check_Expr_Constants (Nod : Node_Id) is
2952 Loc_U_Ent : constant Source_Ptr := Sloc (U_Ent);
2953 Ent : Entity_Id := Empty;
2955 begin
2956 if Nkind (Nod) in N_Has_Etype
2957 and then Etype (Nod) = Any_Type
2958 then
2959 return;
2960 end if;
2962 case Nkind (Nod) is
2963 when N_Empty | N_Error =>
2964 return;
2966 when N_Identifier | N_Expanded_Name =>
2967 Ent := Entity (Nod);
2969 -- We need to look at the original node if it is different
2970 -- from the node, since we may have rewritten things and
2971 -- substituted an identifier representing the rewrite.
2973 if Original_Node (Nod) /= Nod then
2974 Check_Expr_Constants (Original_Node (Nod));
2976 -- If the node is an object declaration without initial
2977 -- value, some code has been expanded, and the expression
2978 -- is not constant, even if the constituents might be
2979 -- acceptable, as in A'Address + offset.
2981 if Ekind (Ent) = E_Variable
2982 and then
2983 Nkind (Declaration_Node (Ent)) = N_Object_Declaration
2984 and then
2985 No (Expression (Declaration_Node (Ent)))
2986 then
2987 Error_Msg_NE
2988 ("invalid address clause for initialized object &!",
2989 Nod, U_Ent);
2991 -- If entity is constant, it may be the result of expanding
2992 -- a check. We must verify that its declaration appears
2993 -- before the object in question, else we also reject the
2994 -- address clause.
2996 elsif Ekind (Ent) = E_Constant
2997 and then In_Same_Source_Unit (Ent, U_Ent)
2998 and then Sloc (Ent) > Loc_U_Ent
2999 then
3000 Error_Msg_NE
3001 ("invalid address clause for initialized object &!",
3002 Nod, U_Ent);
3003 end if;
3005 return;
3006 end if;
3008 -- Otherwise look at the identifier and see if it is OK
3010 if Ekind_In (Ent, E_Named_Integer, E_Named_Real)
3011 or else Is_Type (Ent)
3012 then
3013 return;
3015 elsif
3016 Ekind (Ent) = E_Constant
3017 or else
3018 Ekind (Ent) = E_In_Parameter
3019 then
3020 -- This is the case where we must have Ent defined before
3021 -- U_Ent. Clearly if they are in different units this
3022 -- requirement is met since the unit containing Ent is
3023 -- already processed.
3025 if not In_Same_Source_Unit (Ent, U_Ent) then
3026 return;
3028 -- Otherwise location of Ent must be before the location
3029 -- of U_Ent, that's what prior defined means.
3031 elsif Sloc (Ent) < Loc_U_Ent then
3032 return;
3034 else
3035 Error_Msg_NE
3036 ("invalid address clause for initialized object &!",
3037 Nod, U_Ent);
3038 Error_Msg_Node_2 := U_Ent;
3039 Error_Msg_NE
3040 ("\& must be defined before & (RM 13.1(22))!",
3041 Nod, Ent);
3042 end if;
3044 elsif Nkind (Original_Node (Nod)) = N_Function_Call then
3045 Check_Expr_Constants (Original_Node (Nod));
3047 else
3048 Error_Msg_NE
3049 ("invalid address clause for initialized object &!",
3050 Nod, U_Ent);
3052 if Comes_From_Source (Ent) then
3053 Error_Msg_NE
3054 ("\reference to variable& not allowed"
3055 & " (RM 13.1(22))!", Nod, Ent);
3056 else
3057 Error_Msg_N
3058 ("non-static expression not allowed"
3059 & " (RM 13.1(22))!", Nod);
3060 end if;
3061 end if;
3063 when N_Integer_Literal =>
3065 -- If this is a rewritten unchecked conversion, in a system
3066 -- where Address is an integer type, always use the base type
3067 -- for a literal value. This is user-friendly and prevents
3068 -- order-of-elaboration issues with instances of unchecked
3069 -- conversion.
3071 if Nkind (Original_Node (Nod)) = N_Function_Call then
3072 Set_Etype (Nod, Base_Type (Etype (Nod)));
3073 end if;
3075 when N_Real_Literal |
3076 N_String_Literal |
3077 N_Character_Literal =>
3078 return;
3080 when N_Range =>
3081 Check_Expr_Constants (Low_Bound (Nod));
3082 Check_Expr_Constants (High_Bound (Nod));
3084 when N_Explicit_Dereference =>
3085 Check_Expr_Constants (Prefix (Nod));
3087 when N_Indexed_Component =>
3088 Check_Expr_Constants (Prefix (Nod));
3089 Check_List_Constants (Expressions (Nod));
3091 when N_Slice =>
3092 Check_Expr_Constants (Prefix (Nod));
3093 Check_Expr_Constants (Discrete_Range (Nod));
3095 when N_Selected_Component =>
3096 Check_Expr_Constants (Prefix (Nod));
3098 when N_Attribute_Reference =>
3099 if Attribute_Name (Nod) = Name_Address
3100 or else
3101 Attribute_Name (Nod) = Name_Access
3102 or else
3103 Attribute_Name (Nod) = Name_Unchecked_Access
3104 or else
3105 Attribute_Name (Nod) = Name_Unrestricted_Access
3106 then
3107 Check_At_Constant_Address (Prefix (Nod));
3109 else
3110 Check_Expr_Constants (Prefix (Nod));
3111 Check_List_Constants (Expressions (Nod));
3112 end if;
3114 when N_Aggregate =>
3115 Check_List_Constants (Component_Associations (Nod));
3116 Check_List_Constants (Expressions (Nod));
3118 when N_Component_Association =>
3119 Check_Expr_Constants (Expression (Nod));
3121 when N_Extension_Aggregate =>
3122 Check_Expr_Constants (Ancestor_Part (Nod));
3123 Check_List_Constants (Component_Associations (Nod));
3124 Check_List_Constants (Expressions (Nod));
3126 when N_Null =>
3127 return;
3129 when N_Binary_Op | N_Short_Circuit | N_Membership_Test =>
3130 Check_Expr_Constants (Left_Opnd (Nod));
3131 Check_Expr_Constants (Right_Opnd (Nod));
3133 when N_Unary_Op =>
3134 Check_Expr_Constants (Right_Opnd (Nod));
3136 when N_Type_Conversion |
3137 N_Qualified_Expression |
3138 N_Allocator =>
3139 Check_Expr_Constants (Expression (Nod));
3141 when N_Unchecked_Type_Conversion =>
3142 Check_Expr_Constants (Expression (Nod));
3144 -- If this is a rewritten unchecked conversion, subtypes in
3145 -- this node are those created within the instance. To avoid
3146 -- order of elaboration issues, replace them with their base
3147 -- types. Note that address clauses can cause order of
3148 -- elaboration problems because they are elaborated by the
3149 -- back-end at the point of definition, and may mention
3150 -- entities declared in between (as long as everything is
3151 -- static). It is user-friendly to allow unchecked conversions
3152 -- in this context.
3154 if Nkind (Original_Node (Nod)) = N_Function_Call then
3155 Set_Etype (Expression (Nod),
3156 Base_Type (Etype (Expression (Nod))));
3157 Set_Etype (Nod, Base_Type (Etype (Nod)));
3158 end if;
3160 when N_Function_Call =>
3161 if not Is_Pure (Entity (Name (Nod))) then
3162 Error_Msg_NE
3163 ("invalid address clause for initialized object &!",
3164 Nod, U_Ent);
3166 Error_Msg_NE
3167 ("\function & is not pure (RM 13.1(22))!",
3168 Nod, Entity (Name (Nod)));
3170 else
3171 Check_List_Constants (Parameter_Associations (Nod));
3172 end if;
3174 when N_Parameter_Association =>
3175 Check_Expr_Constants (Explicit_Actual_Parameter (Nod));
3177 when others =>
3178 Error_Msg_NE
3179 ("invalid address clause for initialized object &!",
3180 Nod, U_Ent);
3181 Error_Msg_NE
3182 ("\must be constant defined before& (RM 13.1(22))!",
3183 Nod, U_Ent);
3184 end case;
3185 end Check_Expr_Constants;
3187 --------------------------
3188 -- Check_List_Constants --
3189 --------------------------
3191 procedure Check_List_Constants (Lst : List_Id) is
3192 Nod1 : Node_Id;
3194 begin
3195 if Present (Lst) then
3196 Nod1 := First (Lst);
3197 while Present (Nod1) loop
3198 Check_Expr_Constants (Nod1);
3199 Next (Nod1);
3200 end loop;
3201 end if;
3202 end Check_List_Constants;
3204 -- Start of processing for Check_Constant_Address_Clause
3206 begin
3207 -- If rep_clauses are to be ignored, no need for legality checks. In
3208 -- particular, no need to pester user about rep clauses that violate
3209 -- the rule on constant addresses, given that these clauses will be
3210 -- removed by Freeze before they reach the back end.
3212 if not Ignore_Rep_Clauses then
3213 Check_Expr_Constants (Expr);
3214 end if;
3215 end Check_Constant_Address_Clause;
3217 ----------------------------------------
3218 -- Check_Record_Representation_Clause --
3219 ----------------------------------------
3221 procedure Check_Record_Representation_Clause (N : Node_Id) is
3222 Loc : constant Source_Ptr := Sloc (N);
3223 Ident : constant Node_Id := Identifier (N);
3224 Rectype : Entity_Id;
3225 Fent : Entity_Id;
3226 CC : Node_Id;
3227 Fbit : Uint;
3228 Lbit : Uint;
3229 Hbit : Uint := Uint_0;
3230 Comp : Entity_Id;
3231 Pcomp : Entity_Id;
3233 Max_Bit_So_Far : Uint;
3234 -- Records the maximum bit position so far. If all field positions
3235 -- are monotonically increasing, then we can skip the circuit for
3236 -- checking for overlap, since no overlap is possible.
3238 Tagged_Parent : Entity_Id := Empty;
3239 -- This is set in the case of a derived tagged type for which we have
3240 -- Is_Fully_Repped_Tagged_Type True (indicating that all components are
3241 -- positioned by record representation clauses). In this case we must
3242 -- check for overlap between components of this tagged type, and the
3243 -- components of its parent. Tagged_Parent will point to this parent
3244 -- type. For all other cases Tagged_Parent is left set to Empty.
3246 Parent_Last_Bit : Uint;
3247 -- Relevant only if Tagged_Parent is set, Parent_Last_Bit indicates the
3248 -- last bit position for any field in the parent type. We only need to
3249 -- check overlap for fields starting below this point.
3251 Overlap_Check_Required : Boolean;
3252 -- Used to keep track of whether or not an overlap check is required
3254 Ccount : Natural := 0;
3255 -- Number of component clauses in record rep clause
3257 procedure Check_Component_Overlap (C1_Ent, C2_Ent : Entity_Id);
3258 -- Given two entities for record components or discriminants, checks
3259 -- if they have overlapping component clauses and issues errors if so.
3261 procedure Find_Component;
3262 -- Finds component entity corresponding to current component clause (in
3263 -- CC), and sets Comp to the entity, and Fbit/Lbit to the zero origin
3264 -- start/stop bits for the field. If there is no matching component or
3265 -- if the matching component does not have a component clause, then
3266 -- that's an error and Comp is set to Empty, but no error message is
3267 -- issued, since the message was already given. Comp is also set to
3268 -- Empty if the current "component clause" is in fact a pragma.
3270 -----------------------------
3271 -- Check_Component_Overlap --
3272 -----------------------------
3274 procedure Check_Component_Overlap (C1_Ent, C2_Ent : Entity_Id) is
3275 CC1 : constant Node_Id := Component_Clause (C1_Ent);
3276 CC2 : constant Node_Id := Component_Clause (C2_Ent);
3277 begin
3278 if Present (CC1) and then Present (CC2) then
3280 -- Exclude odd case where we have two tag fields in the same
3281 -- record, both at location zero. This seems a bit strange, but
3282 -- it seems to happen in some circumstances, perhaps on an error.
3284 if Chars (C1_Ent) = Name_uTag
3285 and then
3286 Chars (C2_Ent) = Name_uTag
3287 then
3288 return;
3289 end if;
3291 -- Here we check if the two fields overlap
3293 declare
3294 S1 : constant Uint := Component_Bit_Offset (C1_Ent);
3295 S2 : constant Uint := Component_Bit_Offset (C2_Ent);
3296 E1 : constant Uint := S1 + Esize (C1_Ent);
3297 E2 : constant Uint := S2 + Esize (C2_Ent);
3299 begin
3300 if E2 <= S1 or else E1 <= S2 then
3301 null;
3302 else
3303 Error_Msg_Node_2 := Component_Name (CC2);
3304 Error_Msg_Sloc := Sloc (Error_Msg_Node_2);
3305 Error_Msg_Node_1 := Component_Name (CC1);
3306 Error_Msg_N
3307 ("component& overlaps & #", Component_Name (CC1));
3308 end if;
3309 end;
3310 end if;
3311 end Check_Component_Overlap;
3313 --------------------
3314 -- Find_Component --
3315 --------------------
3317 procedure Find_Component is
3319 procedure Search_Component (R : Entity_Id);
3320 -- Search components of R for a match. If found, Comp is set.
3322 ----------------------
3323 -- Search_Component --
3324 ----------------------
3326 procedure Search_Component (R : Entity_Id) is
3327 begin
3328 Comp := First_Component_Or_Discriminant (R);
3329 while Present (Comp) loop
3331 -- Ignore error of attribute name for component name (we
3332 -- already gave an error message for this, so no need to
3333 -- complain here)
3335 if Nkind (Component_Name (CC)) = N_Attribute_Reference then
3336 null;
3337 else
3338 exit when Chars (Comp) = Chars (Component_Name (CC));
3339 end if;
3341 Next_Component_Or_Discriminant (Comp);
3342 end loop;
3343 end Search_Component;
3345 -- Start of processing for Find_Component
3347 begin
3348 -- Return with Comp set to Empty if we have a pragma
3350 if Nkind (CC) = N_Pragma then
3351 Comp := Empty;
3352 return;
3353 end if;
3355 -- Search current record for matching component
3357 Search_Component (Rectype);
3359 -- If not found, maybe component of base type that is absent from
3360 -- statically constrained first subtype.
3362 if No (Comp) then
3363 Search_Component (Base_Type (Rectype));
3364 end if;
3366 -- If no component, or the component does not reference the component
3367 -- clause in question, then there was some previous error for which
3368 -- we already gave a message, so just return with Comp Empty.
3370 if No (Comp)
3371 or else Component_Clause (Comp) /= CC
3372 then
3373 Comp := Empty;
3375 -- Normal case where we have a component clause
3377 else
3378 Fbit := Component_Bit_Offset (Comp);
3379 Lbit := Fbit + Esize (Comp) - 1;
3380 end if;
3381 end Find_Component;
3383 -- Start of processing for Check_Record_Representation_Clause
3385 begin
3386 Find_Type (Ident);
3387 Rectype := Entity (Ident);
3389 if Rectype = Any_Type then
3390 return;
3391 else
3392 Rectype := Underlying_Type (Rectype);
3393 end if;
3395 -- See if we have a fully repped derived tagged type
3397 declare
3398 PS : constant Entity_Id := Parent_Subtype (Rectype);
3400 begin
3401 if Present (PS) and then Is_Fully_Repped_Tagged_Type (PS) then
3402 Tagged_Parent := PS;
3404 -- Find maximum bit of any component of the parent type
3406 Parent_Last_Bit := UI_From_Int (System_Address_Size - 1);
3407 Pcomp := First_Entity (Tagged_Parent);
3408 while Present (Pcomp) loop
3409 if Ekind_In (Pcomp, E_Discriminant, E_Component) then
3410 if Component_Bit_Offset (Pcomp) /= No_Uint
3411 and then Known_Static_Esize (Pcomp)
3412 then
3413 Parent_Last_Bit :=
3414 UI_Max
3415 (Parent_Last_Bit,
3416 Component_Bit_Offset (Pcomp) + Esize (Pcomp) - 1);
3417 end if;
3419 Next_Entity (Pcomp);
3420 end if;
3421 end loop;
3422 end if;
3423 end;
3425 -- All done if no component clauses
3427 CC := First (Component_Clauses (N));
3429 if No (CC) then
3430 return;
3431 end if;
3433 -- If a tag is present, then create a component clause that places it
3434 -- at the start of the record (otherwise gigi may place it after other
3435 -- fields that have rep clauses).
3437 Fent := First_Entity (Rectype);
3439 if Nkind (Fent) = N_Defining_Identifier
3440 and then Chars (Fent) = Name_uTag
3441 then
3442 Set_Component_Bit_Offset (Fent, Uint_0);
3443 Set_Normalized_Position (Fent, Uint_0);
3444 Set_Normalized_First_Bit (Fent, Uint_0);
3445 Set_Normalized_Position_Max (Fent, Uint_0);
3446 Init_Esize (Fent, System_Address_Size);
3448 Set_Component_Clause (Fent,
3449 Make_Component_Clause (Loc,
3450 Component_Name =>
3451 Make_Identifier (Loc,
3452 Chars => Name_uTag),
3454 Position =>
3455 Make_Integer_Literal (Loc,
3456 Intval => Uint_0),
3458 First_Bit =>
3459 Make_Integer_Literal (Loc,
3460 Intval => Uint_0),
3462 Last_Bit =>
3463 Make_Integer_Literal (Loc,
3464 UI_From_Int (System_Address_Size))));
3466 Ccount := Ccount + 1;
3467 end if;
3469 Max_Bit_So_Far := Uint_Minus_1;
3470 Overlap_Check_Required := False;
3472 -- Process the component clauses
3474 while Present (CC) loop
3475 Find_Component;
3477 if Present (Comp) then
3478 Ccount := Ccount + 1;
3480 if Fbit <= Max_Bit_So_Far then
3481 Overlap_Check_Required := True;
3482 else
3483 Max_Bit_So_Far := Lbit;
3484 end if;
3486 -- Check bit position out of range of specified size
3488 if Has_Size_Clause (Rectype)
3489 and then Esize (Rectype) <= Lbit
3490 then
3491 Error_Msg_N
3492 ("bit number out of range of specified size",
3493 Last_Bit (CC));
3495 -- Check for overlap with tag field
3497 else
3498 if Is_Tagged_Type (Rectype)
3499 and then Fbit < System_Address_Size
3500 then
3501 Error_Msg_NE
3502 ("component overlaps tag field of&",
3503 Component_Name (CC), Rectype);
3504 end if;
3506 if Hbit < Lbit then
3507 Hbit := Lbit;
3508 end if;
3509 end if;
3511 -- Check parent overlap if component might overlap parent field
3513 if Present (Tagged_Parent)
3514 and then Fbit <= Parent_Last_Bit
3515 then
3516 Pcomp := First_Component_Or_Discriminant (Tagged_Parent);
3517 while Present (Pcomp) loop
3518 if not Is_Tag (Pcomp)
3519 and then Chars (Pcomp) /= Name_uParent
3520 then
3521 Check_Component_Overlap (Comp, Pcomp);
3522 end if;
3524 Next_Component_Or_Discriminant (Pcomp);
3525 end loop;
3526 end if;
3527 end if;
3529 Next (CC);
3530 end loop;
3532 -- Now that we have processed all the component clauses, check for
3533 -- overlap. We have to leave this till last, since the components can
3534 -- appear in any arbitrary order in the representation clause.
3536 -- We do not need this check if all specified ranges were monotonic,
3537 -- as recorded by Overlap_Check_Required being False at this stage.
3539 -- This first section checks if there are any overlapping entries at
3540 -- all. It does this by sorting all entries and then seeing if there are
3541 -- any overlaps. If there are none, then that is decisive, but if there
3542 -- are overlaps, they may still be OK (they may result from fields in
3543 -- different variants).
3545 if Overlap_Check_Required then
3546 Overlap_Check1 : declare
3548 OC_Fbit : array (0 .. Ccount) of Uint;
3549 -- First-bit values for component clauses, the value is the offset
3550 -- of the first bit of the field from start of record. The zero
3551 -- entry is for use in sorting.
3553 OC_Lbit : array (0 .. Ccount) of Uint;
3554 -- Last-bit values for component clauses, the value is the offset
3555 -- of the last bit of the field from start of record. The zero
3556 -- entry is for use in sorting.
3558 OC_Count : Natural := 0;
3559 -- Count of entries in OC_Fbit and OC_Lbit
3561 function OC_Lt (Op1, Op2 : Natural) return Boolean;
3562 -- Compare routine for Sort
3564 procedure OC_Move (From : Natural; To : Natural);
3565 -- Move routine for Sort
3567 package Sorting is new GNAT.Heap_Sort_G (OC_Move, OC_Lt);
3569 -----------
3570 -- OC_Lt --
3571 -----------
3573 function OC_Lt (Op1, Op2 : Natural) return Boolean is
3574 begin
3575 return OC_Fbit (Op1) < OC_Fbit (Op2);
3576 end OC_Lt;
3578 -------------
3579 -- OC_Move --
3580 -------------
3582 procedure OC_Move (From : Natural; To : Natural) is
3583 begin
3584 OC_Fbit (To) := OC_Fbit (From);
3585 OC_Lbit (To) := OC_Lbit (From);
3586 end OC_Move;
3588 -- Start of processing for Overlap_Check
3590 begin
3591 CC := First (Component_Clauses (N));
3592 while Present (CC) loop
3594 -- Exclude component clause already marked in error
3596 if not Error_Posted (CC) then
3597 Find_Component;
3599 if Present (Comp) then
3600 OC_Count := OC_Count + 1;
3601 OC_Fbit (OC_Count) := Fbit;
3602 OC_Lbit (OC_Count) := Lbit;
3603 end if;
3604 end if;
3606 Next (CC);
3607 end loop;
3609 Sorting.Sort (OC_Count);
3611 Overlap_Check_Required := False;
3612 for J in 1 .. OC_Count - 1 loop
3613 if OC_Lbit (J) >= OC_Fbit (J + 1) then
3614 Overlap_Check_Required := True;
3615 exit;
3616 end if;
3617 end loop;
3618 end Overlap_Check1;
3619 end if;
3621 -- If Overlap_Check_Required is still True, then we have to do the full
3622 -- scale overlap check, since we have at least two fields that do
3623 -- overlap, and we need to know if that is OK since they are in
3624 -- different variant, or whether we have a definite problem.
3626 if Overlap_Check_Required then
3627 Overlap_Check2 : declare
3628 C1_Ent, C2_Ent : Entity_Id;
3629 -- Entities of components being checked for overlap
3631 Clist : Node_Id;
3632 -- Component_List node whose Component_Items are being checked
3634 Citem : Node_Id;
3635 -- Component declaration for component being checked
3637 begin
3638 C1_Ent := First_Entity (Base_Type (Rectype));
3640 -- Loop through all components in record. For each component check
3641 -- for overlap with any of the preceding elements on the component
3642 -- list containing the component and also, if the component is in
3643 -- a variant, check against components outside the case structure.
3644 -- This latter test is repeated recursively up the variant tree.
3646 Main_Component_Loop : while Present (C1_Ent) loop
3647 if not Ekind_In (C1_Ent, E_Component, E_Discriminant) then
3648 goto Continue_Main_Component_Loop;
3649 end if;
3651 -- Skip overlap check if entity has no declaration node. This
3652 -- happens with discriminants in constrained derived types.
3653 -- Probably we are missing some checks as a result, but that
3654 -- does not seem terribly serious ???
3656 if No (Declaration_Node (C1_Ent)) then
3657 goto Continue_Main_Component_Loop;
3658 end if;
3660 Clist := Parent (List_Containing (Declaration_Node (C1_Ent)));
3662 -- Loop through component lists that need checking. Check the
3663 -- current component list and all lists in variants above us.
3665 Component_List_Loop : loop
3667 -- If derived type definition, go to full declaration
3668 -- If at outer level, check discriminants if there are any.
3670 if Nkind (Clist) = N_Derived_Type_Definition then
3671 Clist := Parent (Clist);
3672 end if;
3674 -- Outer level of record definition, check discriminants
3676 if Nkind_In (Clist, N_Full_Type_Declaration,
3677 N_Private_Type_Declaration)
3678 then
3679 if Has_Discriminants (Defining_Identifier (Clist)) then
3680 C2_Ent :=
3681 First_Discriminant (Defining_Identifier (Clist));
3682 while Present (C2_Ent) loop
3683 exit when C1_Ent = C2_Ent;
3684 Check_Component_Overlap (C1_Ent, C2_Ent);
3685 Next_Discriminant (C2_Ent);
3686 end loop;
3687 end if;
3689 -- Record extension case
3691 elsif Nkind (Clist) = N_Derived_Type_Definition then
3692 Clist := Empty;
3694 -- Otherwise check one component list
3696 else
3697 Citem := First (Component_Items (Clist));
3699 while Present (Citem) loop
3700 if Nkind (Citem) = N_Component_Declaration then
3701 C2_Ent := Defining_Identifier (Citem);
3702 exit when C1_Ent = C2_Ent;
3703 Check_Component_Overlap (C1_Ent, C2_Ent);
3704 end if;
3706 Next (Citem);
3707 end loop;
3708 end if;
3710 -- Check for variants above us (the parent of the Clist can
3711 -- be a variant, in which case its parent is a variant part,
3712 -- and the parent of the variant part is a component list
3713 -- whose components must all be checked against the current
3714 -- component for overlap).
3716 if Nkind (Parent (Clist)) = N_Variant then
3717 Clist := Parent (Parent (Parent (Clist)));
3719 -- Check for possible discriminant part in record, this
3720 -- is treated essentially as another level in the
3721 -- recursion. For this case the parent of the component
3722 -- list is the record definition, and its parent is the
3723 -- full type declaration containing the discriminant
3724 -- specifications.
3726 elsif Nkind (Parent (Clist)) = N_Record_Definition then
3727 Clist := Parent (Parent ((Clist)));
3729 -- If neither of these two cases, we are at the top of
3730 -- the tree.
3732 else
3733 exit Component_List_Loop;
3734 end if;
3735 end loop Component_List_Loop;
3737 <<Continue_Main_Component_Loop>>
3738 Next_Entity (C1_Ent);
3740 end loop Main_Component_Loop;
3741 end Overlap_Check2;
3742 end if;
3744 -- For records that have component clauses for all components, and whose
3745 -- size is less than or equal to 32, we need to know the size in the
3746 -- front end to activate possible packed array processing where the
3747 -- component type is a record.
3749 -- At this stage Hbit + 1 represents the first unused bit from all the
3750 -- component clauses processed, so if the component clauses are
3751 -- complete, then this is the length of the record.
3753 -- For records longer than System.Storage_Unit, and for those where not
3754 -- all components have component clauses, the back end determines the
3755 -- length (it may for example be appropriate to round up the size
3756 -- to some convenient boundary, based on alignment considerations, etc).
3758 if Unknown_RM_Size (Rectype) and then Hbit + 1 <= 32 then
3760 -- Nothing to do if at least one component has no component clause
3762 Comp := First_Component_Or_Discriminant (Rectype);
3763 while Present (Comp) loop
3764 exit when No (Component_Clause (Comp));
3765 Next_Component_Or_Discriminant (Comp);
3766 end loop;
3768 -- If we fall out of loop, all components have component clauses
3769 -- and so we can set the size to the maximum value.
3771 if No (Comp) then
3772 Set_RM_Size (Rectype, Hbit + 1);
3773 end if;
3774 end if;
3775 end Check_Record_Representation_Clause;
3777 ----------------
3778 -- Check_Size --
3779 ----------------
3781 procedure Check_Size
3782 (N : Node_Id;
3783 T : Entity_Id;
3784 Siz : Uint;
3785 Biased : out Boolean)
3787 UT : constant Entity_Id := Underlying_Type (T);
3788 M : Uint;
3790 begin
3791 Biased := False;
3793 -- Dismiss cases for generic types or types with previous errors
3795 if No (UT)
3796 or else UT = Any_Type
3797 or else Is_Generic_Type (UT)
3798 or else Is_Generic_Type (Root_Type (UT))
3799 then
3800 return;
3802 -- Check case of bit packed array
3804 elsif Is_Array_Type (UT)
3805 and then Known_Static_Component_Size (UT)
3806 and then Is_Bit_Packed_Array (UT)
3807 then
3808 declare
3809 Asiz : Uint;
3810 Indx : Node_Id;
3811 Ityp : Entity_Id;
3813 begin
3814 Asiz := Component_Size (UT);
3815 Indx := First_Index (UT);
3816 loop
3817 Ityp := Etype (Indx);
3819 -- If non-static bound, then we are not in the business of
3820 -- trying to check the length, and indeed an error will be
3821 -- issued elsewhere, since sizes of non-static array types
3822 -- cannot be set implicitly or explicitly.
3824 if not Is_Static_Subtype (Ityp) then
3825 return;
3826 end if;
3828 -- Otherwise accumulate next dimension
3830 Asiz := Asiz * (Expr_Value (Type_High_Bound (Ityp)) -
3831 Expr_Value (Type_Low_Bound (Ityp)) +
3832 Uint_1);
3834 Next_Index (Indx);
3835 exit when No (Indx);
3836 end loop;
3838 if Asiz <= Siz then
3839 return;
3840 else
3841 Error_Msg_Uint_1 := Asiz;
3842 Error_Msg_NE
3843 ("size for& too small, minimum allowed is ^", N, T);
3844 Set_Esize (T, Asiz);
3845 Set_RM_Size (T, Asiz);
3846 end if;
3847 end;
3849 -- All other composite types are ignored
3851 elsif Is_Composite_Type (UT) then
3852 return;
3854 -- For fixed-point types, don't check minimum if type is not frozen,
3855 -- since we don't know all the characteristics of the type that can
3856 -- affect the size (e.g. a specified small) till freeze time.
3858 elsif Is_Fixed_Point_Type (UT)
3859 and then not Is_Frozen (UT)
3860 then
3861 null;
3863 -- Cases for which a minimum check is required
3865 else
3866 -- Ignore if specified size is correct for the type
3868 if Known_Esize (UT) and then Siz = Esize (UT) then
3869 return;
3870 end if;
3872 -- Otherwise get minimum size
3874 M := UI_From_Int (Minimum_Size (UT));
3876 if Siz < M then
3878 -- Size is less than minimum size, but one possibility remains
3879 -- that we can manage with the new size if we bias the type.
3881 M := UI_From_Int (Minimum_Size (UT, Biased => True));
3883 if Siz < M then
3884 Error_Msg_Uint_1 := M;
3885 Error_Msg_NE
3886 ("size for& too small, minimum allowed is ^", N, T);
3887 Set_Esize (T, M);
3888 Set_RM_Size (T, M);
3889 else
3890 Biased := True;
3891 end if;
3892 end if;
3893 end if;
3894 end Check_Size;
3896 -------------------------
3897 -- Get_Alignment_Value --
3898 -------------------------
3900 function Get_Alignment_Value (Expr : Node_Id) return Uint is
3901 Align : constant Uint := Static_Integer (Expr);
3903 begin
3904 if Align = No_Uint then
3905 return No_Uint;
3907 elsif Align <= 0 then
3908 Error_Msg_N ("alignment value must be positive", Expr);
3909 return No_Uint;
3911 else
3912 for J in Int range 0 .. 64 loop
3913 declare
3914 M : constant Uint := Uint_2 ** J;
3916 begin
3917 exit when M = Align;
3919 if M > Align then
3920 Error_Msg_N
3921 ("alignment value must be power of 2", Expr);
3922 return No_Uint;
3923 end if;
3924 end;
3925 end loop;
3927 return Align;
3928 end if;
3929 end Get_Alignment_Value;
3931 ----------------
3932 -- Initialize --
3933 ----------------
3935 procedure Initialize is
3936 begin
3937 Unchecked_Conversions.Init;
3938 end Initialize;
3940 -------------------------
3941 -- Is_Operational_Item --
3942 -------------------------
3944 function Is_Operational_Item (N : Node_Id) return Boolean is
3945 begin
3946 if Nkind (N) /= N_Attribute_Definition_Clause then
3947 return False;
3948 else
3949 declare
3950 Id : constant Attribute_Id := Get_Attribute_Id (Chars (N));
3951 begin
3952 return Id = Attribute_Input
3953 or else Id = Attribute_Output
3954 or else Id = Attribute_Read
3955 or else Id = Attribute_Write
3956 or else Id = Attribute_External_Tag;
3957 end;
3958 end if;
3959 end Is_Operational_Item;
3961 ------------------
3962 -- Minimum_Size --
3963 ------------------
3965 function Minimum_Size
3966 (T : Entity_Id;
3967 Biased : Boolean := False) return Nat
3969 Lo : Uint := No_Uint;
3970 Hi : Uint := No_Uint;
3971 LoR : Ureal := No_Ureal;
3972 HiR : Ureal := No_Ureal;
3973 LoSet : Boolean := False;
3974 HiSet : Boolean := False;
3975 B : Uint;
3976 S : Nat;
3977 Ancest : Entity_Id;
3978 R_Typ : constant Entity_Id := Root_Type (T);
3980 begin
3981 -- If bad type, return 0
3983 if T = Any_Type then
3984 return 0;
3986 -- For generic types, just return zero. There cannot be any legitimate
3987 -- need to know such a size, but this routine may be called with a
3988 -- generic type as part of normal processing.
3990 elsif Is_Generic_Type (R_Typ)
3991 or else R_Typ = Any_Type
3992 then
3993 return 0;
3995 -- Access types. Normally an access type cannot have a size smaller
3996 -- than the size of System.Address. The exception is on VMS, where
3997 -- we have short and long addresses, and it is possible for an access
3998 -- type to have a short address size (and thus be less than the size
3999 -- of System.Address itself). We simply skip the check for VMS, and
4000 -- leave it to the back end to do the check.
4002 elsif Is_Access_Type (T) then
4003 if OpenVMS_On_Target then
4004 return 0;
4005 else
4006 return System_Address_Size;
4007 end if;
4009 -- Floating-point types
4011 elsif Is_Floating_Point_Type (T) then
4012 return UI_To_Int (Esize (R_Typ));
4014 -- Discrete types
4016 elsif Is_Discrete_Type (T) then
4018 -- The following loop is looking for the nearest compile time known
4019 -- bounds following the ancestor subtype chain. The idea is to find
4020 -- the most restrictive known bounds information.
4022 Ancest := T;
4023 loop
4024 if Ancest = Any_Type or else Etype (Ancest) = Any_Type then
4025 return 0;
4026 end if;
4028 if not LoSet then
4029 if Compile_Time_Known_Value (Type_Low_Bound (Ancest)) then
4030 Lo := Expr_Rep_Value (Type_Low_Bound (Ancest));
4031 LoSet := True;
4032 exit when HiSet;
4033 end if;
4034 end if;
4036 if not HiSet then
4037 if Compile_Time_Known_Value (Type_High_Bound (Ancest)) then
4038 Hi := Expr_Rep_Value (Type_High_Bound (Ancest));
4039 HiSet := True;
4040 exit when LoSet;
4041 end if;
4042 end if;
4044 Ancest := Ancestor_Subtype (Ancest);
4046 if No (Ancest) then
4047 Ancest := Base_Type (T);
4049 if Is_Generic_Type (Ancest) then
4050 return 0;
4051 end if;
4052 end if;
4053 end loop;
4055 -- Fixed-point types. We can't simply use Expr_Value to get the
4056 -- Corresponding_Integer_Value values of the bounds, since these do not
4057 -- get set till the type is frozen, and this routine can be called
4058 -- before the type is frozen. Similarly the test for bounds being static
4059 -- needs to include the case where we have unanalyzed real literals for
4060 -- the same reason.
4062 elsif Is_Fixed_Point_Type (T) then
4064 -- The following loop is looking for the nearest compile time known
4065 -- bounds following the ancestor subtype chain. The idea is to find
4066 -- the most restrictive known bounds information.
4068 Ancest := T;
4069 loop
4070 if Ancest = Any_Type or else Etype (Ancest) = Any_Type then
4071 return 0;
4072 end if;
4074 -- Note: In the following two tests for LoSet and HiSet, it may
4075 -- seem redundant to test for N_Real_Literal here since normally
4076 -- one would assume that the test for the value being known at
4077 -- compile time includes this case. However, there is a glitch.
4078 -- If the real literal comes from folding a non-static expression,
4079 -- then we don't consider any non- static expression to be known
4080 -- at compile time if we are in configurable run time mode (needed
4081 -- in some cases to give a clearer definition of what is and what
4082 -- is not accepted). So the test is indeed needed. Without it, we
4083 -- would set neither Lo_Set nor Hi_Set and get an infinite loop.
4085 if not LoSet then
4086 if Nkind (Type_Low_Bound (Ancest)) = N_Real_Literal
4087 or else Compile_Time_Known_Value (Type_Low_Bound (Ancest))
4088 then
4089 LoR := Expr_Value_R (Type_Low_Bound (Ancest));
4090 LoSet := True;
4091 exit when HiSet;
4092 end if;
4093 end if;
4095 if not HiSet then
4096 if Nkind (Type_High_Bound (Ancest)) = N_Real_Literal
4097 or else Compile_Time_Known_Value (Type_High_Bound (Ancest))
4098 then
4099 HiR := Expr_Value_R (Type_High_Bound (Ancest));
4100 HiSet := True;
4101 exit when LoSet;
4102 end if;
4103 end if;
4105 Ancest := Ancestor_Subtype (Ancest);
4107 if No (Ancest) then
4108 Ancest := Base_Type (T);
4110 if Is_Generic_Type (Ancest) then
4111 return 0;
4112 end if;
4113 end if;
4114 end loop;
4116 Lo := UR_To_Uint (LoR / Small_Value (T));
4117 Hi := UR_To_Uint (HiR / Small_Value (T));
4119 -- No other types allowed
4121 else
4122 raise Program_Error;
4123 end if;
4125 -- Fall through with Hi and Lo set. Deal with biased case
4127 if (Biased
4128 and then not Is_Fixed_Point_Type (T)
4129 and then not (Is_Enumeration_Type (T)
4130 and then Has_Non_Standard_Rep (T)))
4131 or else Has_Biased_Representation (T)
4132 then
4133 Hi := Hi - Lo;
4134 Lo := Uint_0;
4135 end if;
4137 -- Signed case. Note that we consider types like range 1 .. -1 to be
4138 -- signed for the purpose of computing the size, since the bounds have
4139 -- to be accommodated in the base type.
4141 if Lo < 0 or else Hi < 0 then
4142 S := 1;
4143 B := Uint_1;
4145 -- S = size, B = 2 ** (size - 1) (can accommodate -B .. +(B - 1))
4146 -- Note that we accommodate the case where the bounds cross. This
4147 -- can happen either because of the way the bounds are declared
4148 -- or because of the algorithm in Freeze_Fixed_Point_Type.
4150 while Lo < -B
4151 or else Hi < -B
4152 or else Lo >= B
4153 or else Hi >= B
4154 loop
4155 B := Uint_2 ** S;
4156 S := S + 1;
4157 end loop;
4159 -- Unsigned case
4161 else
4162 -- If both bounds are positive, make sure that both are represen-
4163 -- table in the case where the bounds are crossed. This can happen
4164 -- either because of the way the bounds are declared, or because of
4165 -- the algorithm in Freeze_Fixed_Point_Type.
4167 if Lo > Hi then
4168 Hi := Lo;
4169 end if;
4171 -- S = size, (can accommodate 0 .. (2**size - 1))
4173 S := 0;
4174 while Hi >= Uint_2 ** S loop
4175 S := S + 1;
4176 end loop;
4177 end if;
4179 return S;
4180 end Minimum_Size;
4182 ---------------------------
4183 -- New_Stream_Subprogram --
4184 ---------------------------
4186 procedure New_Stream_Subprogram
4187 (N : Node_Id;
4188 Ent : Entity_Id;
4189 Subp : Entity_Id;
4190 Nam : TSS_Name_Type)
4192 Loc : constant Source_Ptr := Sloc (N);
4193 Sname : constant Name_Id := Make_TSS_Name (Base_Type (Ent), Nam);
4194 Subp_Id : Entity_Id;
4195 Subp_Decl : Node_Id;
4196 F : Entity_Id;
4197 Etyp : Entity_Id;
4199 Defer_Declaration : constant Boolean :=
4200 Is_Tagged_Type (Ent) or else Is_Private_Type (Ent);
4201 -- For a tagged type, there is a declaration for each stream attribute
4202 -- at the freeze point, and we must generate only a completion of this
4203 -- declaration. We do the same for private types, because the full view
4204 -- might be tagged. Otherwise we generate a declaration at the point of
4205 -- the attribute definition clause.
4207 function Build_Spec return Node_Id;
4208 -- Used for declaration and renaming declaration, so that this is
4209 -- treated as a renaming_as_body.
4211 ----------------
4212 -- Build_Spec --
4213 ----------------
4215 function Build_Spec return Node_Id is
4216 Out_P : constant Boolean := (Nam = TSS_Stream_Read);
4217 Formals : List_Id;
4218 Spec : Node_Id;
4219 T_Ref : constant Node_Id := New_Reference_To (Etyp, Loc);
4221 begin
4222 Subp_Id := Make_Defining_Identifier (Loc, Sname);
4224 -- S : access Root_Stream_Type'Class
4226 Formals := New_List (
4227 Make_Parameter_Specification (Loc,
4228 Defining_Identifier =>
4229 Make_Defining_Identifier (Loc, Name_S),
4230 Parameter_Type =>
4231 Make_Access_Definition (Loc,
4232 Subtype_Mark =>
4233 New_Reference_To (
4234 Designated_Type (Etype (F)), Loc))));
4236 if Nam = TSS_Stream_Input then
4237 Spec := Make_Function_Specification (Loc,
4238 Defining_Unit_Name => Subp_Id,
4239 Parameter_Specifications => Formals,
4240 Result_Definition => T_Ref);
4241 else
4242 -- V : [out] T
4244 Append_To (Formals,
4245 Make_Parameter_Specification (Loc,
4246 Defining_Identifier => Make_Defining_Identifier (Loc, Name_V),
4247 Out_Present => Out_P,
4248 Parameter_Type => T_Ref));
4250 Spec :=
4251 Make_Procedure_Specification (Loc,
4252 Defining_Unit_Name => Subp_Id,
4253 Parameter_Specifications => Formals);
4254 end if;
4256 return Spec;
4257 end Build_Spec;
4259 -- Start of processing for New_Stream_Subprogram
4261 begin
4262 F := First_Formal (Subp);
4264 if Ekind (Subp) = E_Procedure then
4265 Etyp := Etype (Next_Formal (F));
4266 else
4267 Etyp := Etype (Subp);
4268 end if;
4270 -- Prepare subprogram declaration and insert it as an action on the
4271 -- clause node. The visibility for this entity is used to test for
4272 -- visibility of the attribute definition clause (in the sense of
4273 -- 8.3(23) as amended by AI-195).
4275 if not Defer_Declaration then
4276 Subp_Decl :=
4277 Make_Subprogram_Declaration (Loc,
4278 Specification => Build_Spec);
4280 -- For a tagged type, there is always a visible declaration for each
4281 -- stream TSS (it is a predefined primitive operation), and the
4282 -- completion of this declaration occurs at the freeze point, which is
4283 -- not always visible at places where the attribute definition clause is
4284 -- visible. So, we create a dummy entity here for the purpose of
4285 -- tracking the visibility of the attribute definition clause itself.
4287 else
4288 Subp_Id :=
4289 Make_Defining_Identifier (Loc,
4290 Chars => New_External_Name (Sname, 'V'));
4291 Subp_Decl :=
4292 Make_Object_Declaration (Loc,
4293 Defining_Identifier => Subp_Id,
4294 Object_Definition => New_Occurrence_Of (Standard_Boolean, Loc));
4295 end if;
4297 Insert_Action (N, Subp_Decl);
4298 Set_Entity (N, Subp_Id);
4300 Subp_Decl :=
4301 Make_Subprogram_Renaming_Declaration (Loc,
4302 Specification => Build_Spec,
4303 Name => New_Reference_To (Subp, Loc));
4305 if Defer_Declaration then
4306 Set_TSS (Base_Type (Ent), Subp_Id);
4307 else
4308 Insert_Action (N, Subp_Decl);
4309 Copy_TSS (Subp_Id, Base_Type (Ent));
4310 end if;
4311 end New_Stream_Subprogram;
4313 ------------------------
4314 -- Rep_Item_Too_Early --
4315 ------------------------
4317 function Rep_Item_Too_Early (T : Entity_Id; N : Node_Id) return Boolean is
4318 begin
4319 -- Cannot apply non-operational rep items to generic types
4321 if Is_Operational_Item (N) then
4322 return False;
4324 elsif Is_Type (T)
4325 and then Is_Generic_Type (Root_Type (T))
4326 then
4327 Error_Msg_N ("representation item not allowed for generic type", N);
4328 return True;
4329 end if;
4331 -- Otherwise check for incomplete type
4333 if Is_Incomplete_Or_Private_Type (T)
4334 and then No (Underlying_Type (T))
4335 then
4336 Error_Msg_N
4337 ("representation item must be after full type declaration", N);
4338 return True;
4340 -- If the type has incomplete components, a representation clause is
4341 -- illegal but stream attributes and Convention pragmas are correct.
4343 elsif Has_Private_Component (T) then
4344 if Nkind (N) = N_Pragma then
4345 return False;
4346 else
4347 Error_Msg_N
4348 ("representation item must appear after type is fully defined",
4350 return True;
4351 end if;
4352 else
4353 return False;
4354 end if;
4355 end Rep_Item_Too_Early;
4357 -----------------------
4358 -- Rep_Item_Too_Late --
4359 -----------------------
4361 function Rep_Item_Too_Late
4362 (T : Entity_Id;
4363 N : Node_Id;
4364 FOnly : Boolean := False) return Boolean
4366 S : Entity_Id;
4367 Parent_Type : Entity_Id;
4369 procedure Too_Late;
4370 -- Output the too late message. Note that this is not considered a
4371 -- serious error, since the effect is simply that we ignore the
4372 -- representation clause in this case.
4374 --------------
4375 -- Too_Late --
4376 --------------
4378 procedure Too_Late is
4379 begin
4380 Error_Msg_N ("|representation item appears too late!", N);
4381 end Too_Late;
4383 -- Start of processing for Rep_Item_Too_Late
4385 begin
4386 -- First make sure entity is not frozen (RM 13.1(9)). Exclude imported
4387 -- types, which may be frozen if they appear in a representation clause
4388 -- for a local type.
4390 if Is_Frozen (T)
4391 and then not From_With_Type (T)
4392 then
4393 Too_Late;
4394 S := First_Subtype (T);
4396 if Present (Freeze_Node (S)) then
4397 Error_Msg_NE
4398 ("?no more representation items for }", Freeze_Node (S), S);
4399 end if;
4401 return True;
4403 -- Check for case of non-tagged derived type whose parent either has
4404 -- primitive operations, or is a by reference type (RM 13.1(10)).
4406 elsif Is_Type (T)
4407 and then not FOnly
4408 and then Is_Derived_Type (T)
4409 and then not Is_Tagged_Type (T)
4410 then
4411 Parent_Type := Etype (Base_Type (T));
4413 if Has_Primitive_Operations (Parent_Type) then
4414 Too_Late;
4415 Error_Msg_NE
4416 ("primitive operations already defined for&!", N, Parent_Type);
4417 return True;
4419 elsif Is_By_Reference_Type (Parent_Type) then
4420 Too_Late;
4421 Error_Msg_NE
4422 ("parent type & is a by reference type!", N, Parent_Type);
4423 return True;
4424 end if;
4425 end if;
4427 -- No error, link item into head of chain of rep items for the entity,
4428 -- but avoid chaining if we have an overloadable entity, and the pragma
4429 -- is one that can apply to multiple overloaded entities.
4431 if Is_Overloadable (T)
4432 and then Nkind (N) = N_Pragma
4433 then
4434 declare
4435 Pname : constant Name_Id := Pragma_Name (N);
4436 begin
4437 if Pname = Name_Convention or else
4438 Pname = Name_Import or else
4439 Pname = Name_Export or else
4440 Pname = Name_External or else
4441 Pname = Name_Interface
4442 then
4443 return False;
4444 end if;
4445 end;
4446 end if;
4448 Record_Rep_Item (T, N);
4449 return False;
4450 end Rep_Item_Too_Late;
4452 -------------------------
4453 -- Same_Representation --
4454 -------------------------
4456 function Same_Representation (Typ1, Typ2 : Entity_Id) return Boolean is
4457 T1 : constant Entity_Id := Underlying_Type (Typ1);
4458 T2 : constant Entity_Id := Underlying_Type (Typ2);
4460 begin
4461 -- A quick check, if base types are the same, then we definitely have
4462 -- the same representation, because the subtype specific representation
4463 -- attributes (Size and Alignment) do not affect representation from
4464 -- the point of view of this test.
4466 if Base_Type (T1) = Base_Type (T2) then
4467 return True;
4469 elsif Is_Private_Type (Base_Type (T2))
4470 and then Base_Type (T1) = Full_View (Base_Type (T2))
4471 then
4472 return True;
4473 end if;
4475 -- Tagged types never have differing representations
4477 if Is_Tagged_Type (T1) then
4478 return True;
4479 end if;
4481 -- Representations are definitely different if conventions differ
4483 if Convention (T1) /= Convention (T2) then
4484 return False;
4485 end if;
4487 -- Representations are different if component alignments differ
4489 if (Is_Record_Type (T1) or else Is_Array_Type (T1))
4490 and then
4491 (Is_Record_Type (T2) or else Is_Array_Type (T2))
4492 and then Component_Alignment (T1) /= Component_Alignment (T2)
4493 then
4494 return False;
4495 end if;
4497 -- For arrays, the only real issue is component size. If we know the
4498 -- component size for both arrays, and it is the same, then that's
4499 -- good enough to know we don't have a change of representation.
4501 if Is_Array_Type (T1) then
4502 if Known_Component_Size (T1)
4503 and then Known_Component_Size (T2)
4504 and then Component_Size (T1) = Component_Size (T2)
4505 then
4506 return True;
4507 end if;
4508 end if;
4510 -- Types definitely have same representation if neither has non-standard
4511 -- representation since default representations are always consistent.
4512 -- If only one has non-standard representation, and the other does not,
4513 -- then we consider that they do not have the same representation. They
4514 -- might, but there is no way of telling early enough.
4516 if Has_Non_Standard_Rep (T1) then
4517 if not Has_Non_Standard_Rep (T2) then
4518 return False;
4519 end if;
4520 else
4521 return not Has_Non_Standard_Rep (T2);
4522 end if;
4524 -- Here the two types both have non-standard representation, and we need
4525 -- to determine if they have the same non-standard representation.
4527 -- For arrays, we simply need to test if the component sizes are the
4528 -- same. Pragma Pack is reflected in modified component sizes, so this
4529 -- check also deals with pragma Pack.
4531 if Is_Array_Type (T1) then
4532 return Component_Size (T1) = Component_Size (T2);
4534 -- Tagged types always have the same representation, because it is not
4535 -- possible to specify different representations for common fields.
4537 elsif Is_Tagged_Type (T1) then
4538 return True;
4540 -- Case of record types
4542 elsif Is_Record_Type (T1) then
4544 -- Packed status must conform
4546 if Is_Packed (T1) /= Is_Packed (T2) then
4547 return False;
4549 -- Otherwise we must check components. Typ2 maybe a constrained
4550 -- subtype with fewer components, so we compare the components
4551 -- of the base types.
4553 else
4554 Record_Case : declare
4555 CD1, CD2 : Entity_Id;
4557 function Same_Rep return Boolean;
4558 -- CD1 and CD2 are either components or discriminants. This
4559 -- function tests whether the two have the same representation
4561 --------------
4562 -- Same_Rep --
4563 --------------
4565 function Same_Rep return Boolean is
4566 begin
4567 if No (Component_Clause (CD1)) then
4568 return No (Component_Clause (CD2));
4570 else
4571 return
4572 Present (Component_Clause (CD2))
4573 and then
4574 Component_Bit_Offset (CD1) = Component_Bit_Offset (CD2)
4575 and then
4576 Esize (CD1) = Esize (CD2);
4577 end if;
4578 end Same_Rep;
4580 -- Start of processing for Record_Case
4582 begin
4583 if Has_Discriminants (T1) then
4584 CD1 := First_Discriminant (T1);
4585 CD2 := First_Discriminant (T2);
4587 -- The number of discriminants may be different if the
4588 -- derived type has fewer (constrained by values). The
4589 -- invisible discriminants retain the representation of
4590 -- the original, so the discrepancy does not per se
4591 -- indicate a different representation.
4593 while Present (CD1)
4594 and then Present (CD2)
4595 loop
4596 if not Same_Rep then
4597 return False;
4598 else
4599 Next_Discriminant (CD1);
4600 Next_Discriminant (CD2);
4601 end if;
4602 end loop;
4603 end if;
4605 CD1 := First_Component (Underlying_Type (Base_Type (T1)));
4606 CD2 := First_Component (Underlying_Type (Base_Type (T2)));
4608 while Present (CD1) loop
4609 if not Same_Rep then
4610 return False;
4611 else
4612 Next_Component (CD1);
4613 Next_Component (CD2);
4614 end if;
4615 end loop;
4617 return True;
4618 end Record_Case;
4619 end if;
4621 -- For enumeration types, we must check each literal to see if the
4622 -- representation is the same. Note that we do not permit enumeration
4623 -- representation clauses for Character and Wide_Character, so these
4624 -- cases were already dealt with.
4626 elsif Is_Enumeration_Type (T1) then
4628 Enumeration_Case : declare
4629 L1, L2 : Entity_Id;
4631 begin
4632 L1 := First_Literal (T1);
4633 L2 := First_Literal (T2);
4635 while Present (L1) loop
4636 if Enumeration_Rep (L1) /= Enumeration_Rep (L2) then
4637 return False;
4638 else
4639 Next_Literal (L1);
4640 Next_Literal (L2);
4641 end if;
4642 end loop;
4644 return True;
4646 end Enumeration_Case;
4648 -- Any other types have the same representation for these purposes
4650 else
4651 return True;
4652 end if;
4653 end Same_Representation;
4655 --------------------
4656 -- Set_Enum_Esize --
4657 --------------------
4659 procedure Set_Enum_Esize (T : Entity_Id) is
4660 Lo : Uint;
4661 Hi : Uint;
4662 Sz : Nat;
4664 begin
4665 Init_Alignment (T);
4667 -- Find the minimum standard size (8,16,32,64) that fits
4669 Lo := Enumeration_Rep (Entity (Type_Low_Bound (T)));
4670 Hi := Enumeration_Rep (Entity (Type_High_Bound (T)));
4672 if Lo < 0 then
4673 if Lo >= -Uint_2**07 and then Hi < Uint_2**07 then
4674 Sz := Standard_Character_Size; -- May be > 8 on some targets
4676 elsif Lo >= -Uint_2**15 and then Hi < Uint_2**15 then
4677 Sz := 16;
4679 elsif Lo >= -Uint_2**31 and then Hi < Uint_2**31 then
4680 Sz := 32;
4682 else pragma Assert (Lo >= -Uint_2**63 and then Hi < Uint_2**63);
4683 Sz := 64;
4684 end if;
4686 else
4687 if Hi < Uint_2**08 then
4688 Sz := Standard_Character_Size; -- May be > 8 on some targets
4690 elsif Hi < Uint_2**16 then
4691 Sz := 16;
4693 elsif Hi < Uint_2**32 then
4694 Sz := 32;
4696 else pragma Assert (Hi < Uint_2**63);
4697 Sz := 64;
4698 end if;
4699 end if;
4701 -- That minimum is the proper size unless we have a foreign convention
4702 -- and the size required is 32 or less, in which case we bump the size
4703 -- up to 32. This is required for C and C++ and seems reasonable for
4704 -- all other foreign conventions.
4706 if Has_Foreign_Convention (T)
4707 and then Esize (T) < Standard_Integer_Size
4708 then
4709 Init_Esize (T, Standard_Integer_Size);
4710 else
4711 Init_Esize (T, Sz);
4712 end if;
4713 end Set_Enum_Esize;
4715 ------------------------------
4716 -- Validate_Address_Clauses --
4717 ------------------------------
4719 procedure Validate_Address_Clauses is
4720 begin
4721 for J in Address_Clause_Checks.First .. Address_Clause_Checks.Last loop
4722 declare
4723 ACCR : Address_Clause_Check_Record
4724 renames Address_Clause_Checks.Table (J);
4726 Expr : Node_Id;
4728 X_Alignment : Uint;
4729 Y_Alignment : Uint;
4731 X_Size : Uint;
4732 Y_Size : Uint;
4734 begin
4735 -- Skip processing of this entry if warning already posted
4737 if not Address_Warning_Posted (ACCR.N) then
4739 Expr := Original_Node (Expression (ACCR.N));
4741 -- Get alignments
4743 X_Alignment := Alignment (ACCR.X);
4744 Y_Alignment := Alignment (ACCR.Y);
4746 -- Similarly obtain sizes
4748 X_Size := Esize (ACCR.X);
4749 Y_Size := Esize (ACCR.Y);
4751 -- Check for large object overlaying smaller one
4753 if Y_Size > Uint_0
4754 and then X_Size > Uint_0
4755 and then X_Size > Y_Size
4756 then
4757 Error_Msg_NE
4758 ("?& overlays smaller object", ACCR.N, ACCR.X);
4759 Error_Msg_N
4760 ("\?program execution may be erroneous", ACCR.N);
4761 Error_Msg_Uint_1 := X_Size;
4762 Error_Msg_NE
4763 ("\?size of & is ^", ACCR.N, ACCR.X);
4764 Error_Msg_Uint_1 := Y_Size;
4765 Error_Msg_NE
4766 ("\?size of & is ^", ACCR.N, ACCR.Y);
4768 -- Check for inadequate alignment, both of the base object
4769 -- and of the offset, if any.
4771 -- Note: we do not check the alignment if we gave a size
4772 -- warning, since it would likely be redundant.
4774 elsif Y_Alignment /= Uint_0
4775 and then (Y_Alignment < X_Alignment
4776 or else (ACCR.Off
4777 and then
4778 Nkind (Expr) = N_Attribute_Reference
4779 and then
4780 Attribute_Name (Expr) = Name_Address
4781 and then
4782 Has_Compatible_Alignment
4783 (ACCR.X, Prefix (Expr))
4784 /= Known_Compatible))
4785 then
4786 Error_Msg_NE
4787 ("?specified address for& may be inconsistent "
4788 & "with alignment",
4789 ACCR.N, ACCR.X);
4790 Error_Msg_N
4791 ("\?program execution may be erroneous (RM 13.3(27))",
4792 ACCR.N);
4793 Error_Msg_Uint_1 := X_Alignment;
4794 Error_Msg_NE
4795 ("\?alignment of & is ^",
4796 ACCR.N, ACCR.X);
4797 Error_Msg_Uint_1 := Y_Alignment;
4798 Error_Msg_NE
4799 ("\?alignment of & is ^",
4800 ACCR.N, ACCR.Y);
4801 if Y_Alignment >= X_Alignment then
4802 Error_Msg_N
4803 ("\?but offset is not multiple of alignment",
4804 ACCR.N);
4805 end if;
4806 end if;
4807 end if;
4808 end;
4809 end loop;
4810 end Validate_Address_Clauses;
4812 -----------------------------------
4813 -- Validate_Unchecked_Conversion --
4814 -----------------------------------
4816 procedure Validate_Unchecked_Conversion
4817 (N : Node_Id;
4818 Act_Unit : Entity_Id)
4820 Source : Entity_Id;
4821 Target : Entity_Id;
4822 Vnode : Node_Id;
4824 begin
4825 -- Obtain source and target types. Note that we call Ancestor_Subtype
4826 -- here because the processing for generic instantiation always makes
4827 -- subtypes, and we want the original frozen actual types.
4829 -- If we are dealing with private types, then do the check on their
4830 -- fully declared counterparts if the full declarations have been
4831 -- encountered (they don't have to be visible, but they must exist!)
4833 Source := Ancestor_Subtype (Etype (First_Formal (Act_Unit)));
4835 if Is_Private_Type (Source)
4836 and then Present (Underlying_Type (Source))
4837 then
4838 Source := Underlying_Type (Source);
4839 end if;
4841 Target := Ancestor_Subtype (Etype (Act_Unit));
4843 -- If either type is generic, the instantiation happens within a generic
4844 -- unit, and there is nothing to check. The proper check
4845 -- will happen when the enclosing generic is instantiated.
4847 if Is_Generic_Type (Source) or else Is_Generic_Type (Target) then
4848 return;
4849 end if;
4851 if Is_Private_Type (Target)
4852 and then Present (Underlying_Type (Target))
4853 then
4854 Target := Underlying_Type (Target);
4855 end if;
4857 -- Source may be unconstrained array, but not target
4859 if Is_Array_Type (Target)
4860 and then not Is_Constrained (Target)
4861 then
4862 Error_Msg_N
4863 ("unchecked conversion to unconstrained array not allowed", N);
4864 return;
4865 end if;
4867 -- Warn if conversion between two different convention pointers
4869 if Is_Access_Type (Target)
4870 and then Is_Access_Type (Source)
4871 and then Convention (Target) /= Convention (Source)
4872 and then Warn_On_Unchecked_Conversion
4873 then
4874 -- Give warnings for subprogram pointers only on most targets. The
4875 -- exception is VMS, where data pointers can have different lengths
4876 -- depending on the pointer convention.
4878 if Is_Access_Subprogram_Type (Target)
4879 or else Is_Access_Subprogram_Type (Source)
4880 or else OpenVMS_On_Target
4881 then
4882 Error_Msg_N
4883 ("?conversion between pointers with different conventions!", N);
4884 end if;
4885 end if;
4887 -- Warn if one of the operands is Ada.Calendar.Time. Do not emit a
4888 -- warning when compiling GNAT-related sources.
4890 if Warn_On_Unchecked_Conversion
4891 and then not In_Predefined_Unit (N)
4892 and then RTU_Loaded (Ada_Calendar)
4893 and then
4894 (Chars (Source) = Name_Time
4895 or else
4896 Chars (Target) = Name_Time)
4897 then
4898 -- If Ada.Calendar is loaded and the name of one of the operands is
4899 -- Time, there is a good chance that this is Ada.Calendar.Time.
4901 declare
4902 Calendar_Time : constant Entity_Id :=
4903 Full_View (RTE (RO_CA_Time));
4904 begin
4905 pragma Assert (Present (Calendar_Time));
4907 if Source = Calendar_Time
4908 or else Target = Calendar_Time
4909 then
4910 Error_Msg_N
4911 ("?representation of 'Time values may change between " &
4912 "'G'N'A'T versions", N);
4913 end if;
4914 end;
4915 end if;
4917 -- Make entry in unchecked conversion table for later processing by
4918 -- Validate_Unchecked_Conversions, which will check sizes and alignments
4919 -- (using values set by the back-end where possible). This is only done
4920 -- if the appropriate warning is active.
4922 if Warn_On_Unchecked_Conversion then
4923 Unchecked_Conversions.Append
4924 (New_Val => UC_Entry'
4925 (Eloc => Sloc (N),
4926 Source => Source,
4927 Target => Target));
4929 -- If both sizes are known statically now, then back end annotation
4930 -- is not required to do a proper check but if either size is not
4931 -- known statically, then we need the annotation.
4933 if Known_Static_RM_Size (Source)
4934 and then Known_Static_RM_Size (Target)
4935 then
4936 null;
4937 else
4938 Back_Annotate_Rep_Info := True;
4939 end if;
4940 end if;
4942 -- If unchecked conversion to access type, and access type is declared
4943 -- in the same unit as the unchecked conversion, then set the
4944 -- No_Strict_Aliasing flag (no strict aliasing is implicit in this
4945 -- situation).
4947 if Is_Access_Type (Target) and then
4948 In_Same_Source_Unit (Target, N)
4949 then
4950 Set_No_Strict_Aliasing (Implementation_Base_Type (Target));
4951 end if;
4953 -- Generate N_Validate_Unchecked_Conversion node for back end in
4954 -- case the back end needs to perform special validation checks.
4956 -- Shouldn't this be in Exp_Ch13, since the check only gets done
4957 -- if we have full expansion and the back end is called ???
4959 Vnode :=
4960 Make_Validate_Unchecked_Conversion (Sloc (N));
4961 Set_Source_Type (Vnode, Source);
4962 Set_Target_Type (Vnode, Target);
4964 -- If the unchecked conversion node is in a list, just insert before it.
4965 -- If not we have some strange case, not worth bothering about.
4967 if Is_List_Member (N) then
4968 Insert_After (N, Vnode);
4969 end if;
4970 end Validate_Unchecked_Conversion;
4972 ------------------------------------
4973 -- Validate_Unchecked_Conversions --
4974 ------------------------------------
4976 procedure Validate_Unchecked_Conversions is
4977 begin
4978 for N in Unchecked_Conversions.First .. Unchecked_Conversions.Last loop
4979 declare
4980 T : UC_Entry renames Unchecked_Conversions.Table (N);
4982 Eloc : constant Source_Ptr := T.Eloc;
4983 Source : constant Entity_Id := T.Source;
4984 Target : constant Entity_Id := T.Target;
4986 Source_Siz : Uint;
4987 Target_Siz : Uint;
4989 begin
4990 -- This validation check, which warns if we have unequal sizes for
4991 -- unchecked conversion, and thus potentially implementation
4992 -- dependent semantics, is one of the few occasions on which we
4993 -- use the official RM size instead of Esize. See description in
4994 -- Einfo "Handling of Type'Size Values" for details.
4996 if Serious_Errors_Detected = 0
4997 and then Known_Static_RM_Size (Source)
4998 and then Known_Static_RM_Size (Target)
5000 -- Don't do the check if warnings off for either type, note the
5001 -- deliberate use of OR here instead of OR ELSE to get the flag
5002 -- Warnings_Off_Used set for both types if appropriate.
5004 and then not (Has_Warnings_Off (Source)
5006 Has_Warnings_Off (Target))
5007 then
5008 Source_Siz := RM_Size (Source);
5009 Target_Siz := RM_Size (Target);
5011 if Source_Siz /= Target_Siz then
5012 Error_Msg
5013 ("?types for unchecked conversion have different sizes!",
5014 Eloc);
5016 if All_Errors_Mode then
5017 Error_Msg_Name_1 := Chars (Source);
5018 Error_Msg_Uint_1 := Source_Siz;
5019 Error_Msg_Name_2 := Chars (Target);
5020 Error_Msg_Uint_2 := Target_Siz;
5021 Error_Msg ("\size of % is ^, size of % is ^?", Eloc);
5023 Error_Msg_Uint_1 := UI_Abs (Source_Siz - Target_Siz);
5025 if Is_Discrete_Type (Source)
5026 and then Is_Discrete_Type (Target)
5027 then
5028 if Source_Siz > Target_Siz then
5029 Error_Msg
5030 ("\?^ high order bits of source will be ignored!",
5031 Eloc);
5033 elsif Is_Unsigned_Type (Source) then
5034 Error_Msg
5035 ("\?source will be extended with ^ high order " &
5036 "zero bits?!", Eloc);
5038 else
5039 Error_Msg
5040 ("\?source will be extended with ^ high order " &
5041 "sign bits!",
5042 Eloc);
5043 end if;
5045 elsif Source_Siz < Target_Siz then
5046 if Is_Discrete_Type (Target) then
5047 if Bytes_Big_Endian then
5048 Error_Msg
5049 ("\?target value will include ^ undefined " &
5050 "low order bits!",
5051 Eloc);
5052 else
5053 Error_Msg
5054 ("\?target value will include ^ undefined " &
5055 "high order bits!",
5056 Eloc);
5057 end if;
5059 else
5060 Error_Msg
5061 ("\?^ trailing bits of target value will be " &
5062 "undefined!", Eloc);
5063 end if;
5065 else pragma Assert (Source_Siz > Target_Siz);
5066 Error_Msg
5067 ("\?^ trailing bits of source will be ignored!",
5068 Eloc);
5069 end if;
5070 end if;
5071 end if;
5072 end if;
5074 -- If both types are access types, we need to check the alignment.
5075 -- If the alignment of both is specified, we can do it here.
5077 if Serious_Errors_Detected = 0
5078 and then Ekind (Source) in Access_Kind
5079 and then Ekind (Target) in Access_Kind
5080 and then Target_Strict_Alignment
5081 and then Present (Designated_Type (Source))
5082 and then Present (Designated_Type (Target))
5083 then
5084 declare
5085 D_Source : constant Entity_Id := Designated_Type (Source);
5086 D_Target : constant Entity_Id := Designated_Type (Target);
5088 begin
5089 if Known_Alignment (D_Source)
5090 and then Known_Alignment (D_Target)
5091 then
5092 declare
5093 Source_Align : constant Uint := Alignment (D_Source);
5094 Target_Align : constant Uint := Alignment (D_Target);
5096 begin
5097 if Source_Align < Target_Align
5098 and then not Is_Tagged_Type (D_Source)
5100 -- Suppress warning if warnings suppressed on either
5101 -- type or either designated type. Note the use of
5102 -- OR here instead of OR ELSE. That is intentional,
5103 -- we would like to set flag Warnings_Off_Used in
5104 -- all types for which warnings are suppressed.
5106 and then not (Has_Warnings_Off (D_Source)
5108 Has_Warnings_Off (D_Target)
5110 Has_Warnings_Off (Source)
5112 Has_Warnings_Off (Target))
5113 then
5114 Error_Msg_Uint_1 := Target_Align;
5115 Error_Msg_Uint_2 := Source_Align;
5116 Error_Msg_Node_1 := D_Target;
5117 Error_Msg_Node_2 := D_Source;
5118 Error_Msg
5119 ("?alignment of & (^) is stricter than " &
5120 "alignment of & (^)!", Eloc);
5121 Error_Msg
5122 ("\?resulting access value may have invalid " &
5123 "alignment!", Eloc);
5124 end if;
5125 end;
5126 end if;
5127 end;
5128 end if;
5129 end;
5130 end loop;
5131 end Validate_Unchecked_Conversions;
5133 end Sem_Ch13;