[multiple changes]
[gcc.git] / gcc / ada / sem_ch13.adb
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 ------------------------------------------------------------------------------
25
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;
60
61 with GNAT.Heap_Sort_G;
62
63 package body Sem_Ch13 is
64
65 SSU : constant Pos := System_Storage_Unit;
66 -- Convenient short hand for commonly used constant
67
68 -----------------------
69 -- Local Subprograms --
70 -----------------------
71
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.
77
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.
82
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.
88
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.
102 --
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.
108
109 ----------------------------------------------
110 -- Table for Validate_Unchecked_Conversions --
111 ----------------------------------------------
112
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.
119
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.
123
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;
129
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");
137
138 ----------------------------------------
139 -- Table for Validate_Address_Clauses --
140 ----------------------------------------
141
142 -- If an address clause has the form
143
144 -- for X'Address use Expr
145
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.
153
154 type Address_Clause_Check_Record is record
155 N : Node_Id;
156 -- The address clause
157
158 X : Entity_Id;
159 -- The entity of the object overlaying Y
160
161 Y : Entity_Id;
162 -- The entity of the object being overlaid
163
164 Off : Boolean;
165 -- Whether the address is offseted within Y
166 end record;
167
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");
175
176 -----------------------------------------
177 -- Adjust_Record_For_Reverse_Bit_Order --
178 -----------------------------------------
179
180 procedure Adjust_Record_For_Reverse_Bit_Order (R : Entity_Id) is
181 Comp : Node_Id;
182 CC : Node_Id;
183
184 begin
185 -- Processing depends on version of Ada
186
187 -- For Ada 95, we just renumber bits within a storage unit. We do the
188 -- same for Ada 83 mode, since we recognize pragma Bit_Order in Ada 83,
189 -- and are free to add this extension.
190
191 if Ada_Version < Ada_2005 then
192 Comp := First_Component_Or_Discriminant (R);
193 while Present (Comp) loop
194 CC := Component_Clause (Comp);
195
196 -- If component clause is present, then deal with the non-default
197 -- bit order case for Ada 95 mode.
198
199 -- We only do this processing for the base type, and in fact that
200 -- is important, since otherwise if there are record subtypes, we
201 -- could reverse the bits once for each subtype, which is wrong.
202
203 if Present (CC)
204 and then Ekind (R) = E_Record_Type
205 then
206 declare
207 CFB : constant Uint := Component_Bit_Offset (Comp);
208 CSZ : constant Uint := Esize (Comp);
209 CLC : constant Node_Id := Component_Clause (Comp);
210 Pos : constant Node_Id := Position (CLC);
211 FB : constant Node_Id := First_Bit (CLC);
212
213 Storage_Unit_Offset : constant Uint :=
214 CFB / System_Storage_Unit;
215
216 Start_Bit : constant Uint :=
217 CFB mod System_Storage_Unit;
218
219 begin
220 -- Cases where field goes over storage unit boundary
221
222 if Start_Bit + CSZ > System_Storage_Unit then
223
224 -- Allow multi-byte field but generate warning
225
226 if Start_Bit mod System_Storage_Unit = 0
227 and then CSZ mod System_Storage_Unit = 0
228 then
229 Error_Msg_N
230 ("multi-byte field specified with non-standard"
231 & " Bit_Order?", CLC);
232
233 if Bytes_Big_Endian then
234 Error_Msg_N
235 ("bytes are not reversed "
236 & "(component is big-endian)?", CLC);
237 else
238 Error_Msg_N
239 ("bytes are not reversed "
240 & "(component is little-endian)?", CLC);
241 end if;
242
243 -- Do not allow non-contiguous field
244
245 else
246 Error_Msg_N
247 ("attempt to specify non-contiguous field "
248 & "not permitted", CLC);
249 Error_Msg_N
250 ("\caused by non-standard Bit_Order "
251 & "specified", CLC);
252 Error_Msg_N
253 ("\consider possibility of using "
254 & "Ada 2005 mode here", CLC);
255 end if;
256
257 -- Case where field fits in one storage unit
258
259 else
260 -- Give warning if suspicious component clause
261
262 if Intval (FB) >= System_Storage_Unit
263 and then Warn_On_Reverse_Bit_Order
264 then
265 Error_Msg_N
266 ("?Bit_Order clause does not affect " &
267 "byte ordering", Pos);
268 Error_Msg_Uint_1 :=
269 Intval (Pos) + Intval (FB) /
270 System_Storage_Unit;
271 Error_Msg_N
272 ("?position normalized to ^ before bit " &
273 "order interpreted", Pos);
274 end if;
275
276 -- Here is where we fix up the Component_Bit_Offset value
277 -- to account for the reverse bit order. Some examples of
278 -- what needs to be done are:
279
280 -- First_Bit .. Last_Bit Component_Bit_Offset
281 -- old new old new
282
283 -- 0 .. 0 7 .. 7 0 7
284 -- 0 .. 1 6 .. 7 0 6
285 -- 0 .. 2 5 .. 7 0 5
286 -- 0 .. 7 0 .. 7 0 4
287
288 -- 1 .. 1 6 .. 6 1 6
289 -- 1 .. 4 3 .. 6 1 3
290 -- 4 .. 7 0 .. 3 4 0
291
292 -- The rule is that the first bit is is obtained by
293 -- subtracting the old ending bit from storage_unit - 1.
294
295 Set_Component_Bit_Offset
296 (Comp,
297 (Storage_Unit_Offset * System_Storage_Unit) +
298 (System_Storage_Unit - 1) -
299 (Start_Bit + CSZ - 1));
300
301 Set_Normalized_First_Bit
302 (Comp,
303 Component_Bit_Offset (Comp) mod
304 System_Storage_Unit);
305 end if;
306 end;
307 end if;
308
309 Next_Component_Or_Discriminant (Comp);
310 end loop;
311
312 -- For Ada 2005, we do machine scalar processing, as fully described In
313 -- AI-133. This involves gathering all components which start at the
314 -- same byte offset and processing them together. Same approach is still
315 -- valid in later versions including Ada 2012.
316
317 else
318 declare
319 Max_Machine_Scalar_Size : constant Uint :=
320 UI_From_Int
321 (Standard_Long_Long_Integer_Size);
322 -- We use this as the maximum machine scalar size
323
324 Num_CC : Natural;
325 SSU : constant Uint := UI_From_Int (System_Storage_Unit);
326
327 begin
328 -- This first loop through components does two things. First it
329 -- deals with the case of components with component clauses whose
330 -- length is greater than the maximum machine scalar size (either
331 -- accepting them or rejecting as needed). Second, it counts the
332 -- number of components with component clauses whose length does
333 -- not exceed this maximum for later processing.
334
335 Num_CC := 0;
336 Comp := First_Component_Or_Discriminant (R);
337 while Present (Comp) loop
338 CC := Component_Clause (Comp);
339
340 if Present (CC) then
341 declare
342 Fbit : constant Uint :=
343 Static_Integer (First_Bit (CC));
344
345 begin
346 -- Case of component with size > max machine scalar
347
348 if Esize (Comp) > Max_Machine_Scalar_Size then
349
350 -- Must begin on byte boundary
351
352 if Fbit mod SSU /= 0 then
353 Error_Msg_N
354 ("illegal first bit value for "
355 & "reverse bit order",
356 First_Bit (CC));
357 Error_Msg_Uint_1 := SSU;
358 Error_Msg_Uint_2 := Max_Machine_Scalar_Size;
359
360 Error_Msg_N
361 ("\must be a multiple of ^ "
362 & "if size greater than ^",
363 First_Bit (CC));
364
365 -- Must end on byte boundary
366
367 elsif Esize (Comp) mod SSU /= 0 then
368 Error_Msg_N
369 ("illegal last bit value for "
370 & "reverse bit order",
371 Last_Bit (CC));
372 Error_Msg_Uint_1 := SSU;
373 Error_Msg_Uint_2 := Max_Machine_Scalar_Size;
374
375 Error_Msg_N
376 ("\must be a multiple of ^ if size "
377 & "greater than ^",
378 Last_Bit (CC));
379
380 -- OK, give warning if enabled
381
382 elsif Warn_On_Reverse_Bit_Order then
383 Error_Msg_N
384 ("multi-byte field specified with "
385 & " non-standard Bit_Order?", CC);
386
387 if Bytes_Big_Endian then
388 Error_Msg_N
389 ("\bytes are not reversed "
390 & "(component is big-endian)?", CC);
391 else
392 Error_Msg_N
393 ("\bytes are not reversed "
394 & "(component is little-endian)?", CC);
395 end if;
396 end if;
397
398 -- Case where size is not greater than max machine
399 -- scalar. For now, we just count these.
400
401 else
402 Num_CC := Num_CC + 1;
403 end if;
404 end;
405 end if;
406
407 Next_Component_Or_Discriminant (Comp);
408 end loop;
409
410 -- We need to sort the component clauses on the basis of the
411 -- Position values in the clause, so we can group clauses with
412 -- the same Position. together to determine the relevant machine
413 -- scalar size.
414
415 Sort_CC : declare
416 Comps : array (0 .. Num_CC) of Entity_Id;
417 -- Array to collect component and discriminant entities. The
418 -- data starts at index 1, the 0'th entry is for the sort
419 -- routine.
420
421 function CP_Lt (Op1, Op2 : Natural) return Boolean;
422 -- Compare routine for Sort
423
424 procedure CP_Move (From : Natural; To : Natural);
425 -- Move routine for Sort
426
427 package Sorting is new GNAT.Heap_Sort_G (CP_Move, CP_Lt);
428
429 Start : Natural;
430 Stop : Natural;
431 -- Start and stop positions in the component list of the set of
432 -- components with the same starting position (that constitute
433 -- components in a single machine scalar).
434
435 MaxL : Uint;
436 -- Maximum last bit value of any component in this set
437
438 MSS : Uint;
439 -- Corresponding machine scalar size
440
441 -----------
442 -- CP_Lt --
443 -----------
444
445 function CP_Lt (Op1, Op2 : Natural) return Boolean is
446 begin
447 return Position (Component_Clause (Comps (Op1))) <
448 Position (Component_Clause (Comps (Op2)));
449 end CP_Lt;
450
451 -------------
452 -- CP_Move --
453 -------------
454
455 procedure CP_Move (From : Natural; To : Natural) is
456 begin
457 Comps (To) := Comps (From);
458 end CP_Move;
459
460 -- Start of processing for Sort_CC
461
462 begin
463 -- Collect the component clauses
464
465 Num_CC := 0;
466 Comp := First_Component_Or_Discriminant (R);
467 while Present (Comp) loop
468 if Present (Component_Clause (Comp))
469 and then Esize (Comp) <= Max_Machine_Scalar_Size
470 then
471 Num_CC := Num_CC + 1;
472 Comps (Num_CC) := Comp;
473 end if;
474
475 Next_Component_Or_Discriminant (Comp);
476 end loop;
477
478 -- Sort by ascending position number
479
480 Sorting.Sort (Num_CC);
481
482 -- We now have all the components whose size does not exceed
483 -- the max machine scalar value, sorted by starting position.
484 -- In this loop we gather groups of clauses starting at the
485 -- same position, to process them in accordance with AI-133.
486
487 Stop := 0;
488 while Stop < Num_CC loop
489 Start := Stop + 1;
490 Stop := Start;
491 MaxL :=
492 Static_Integer
493 (Last_Bit (Component_Clause (Comps (Start))));
494 while Stop < Num_CC loop
495 if Static_Integer
496 (Position (Component_Clause (Comps (Stop + 1)))) =
497 Static_Integer
498 (Position (Component_Clause (Comps (Stop))))
499 then
500 Stop := Stop + 1;
501 MaxL :=
502 UI_Max
503 (MaxL,
504 Static_Integer
505 (Last_Bit
506 (Component_Clause (Comps (Stop)))));
507 else
508 exit;
509 end if;
510 end loop;
511
512 -- Now we have a group of component clauses from Start to
513 -- Stop whose positions are identical, and MaxL is the
514 -- maximum last bit value of any of these components.
515
516 -- We need to determine the corresponding machine scalar
517 -- size. This loop assumes that machine scalar sizes are
518 -- even, and that each possible machine scalar has twice
519 -- as many bits as the next smaller one.
520
521 MSS := Max_Machine_Scalar_Size;
522 while MSS mod 2 = 0
523 and then (MSS / 2) >= SSU
524 and then (MSS / 2) > MaxL
525 loop
526 MSS := MSS / 2;
527 end loop;
528
529 -- Here is where we fix up the Component_Bit_Offset value
530 -- to account for the reverse bit order. Some examples of
531 -- what needs to be done for the case of a machine scalar
532 -- size of 8 are:
533
534 -- First_Bit .. Last_Bit Component_Bit_Offset
535 -- old new old new
536
537 -- 0 .. 0 7 .. 7 0 7
538 -- 0 .. 1 6 .. 7 0 6
539 -- 0 .. 2 5 .. 7 0 5
540 -- 0 .. 7 0 .. 7 0 4
541
542 -- 1 .. 1 6 .. 6 1 6
543 -- 1 .. 4 3 .. 6 1 3
544 -- 4 .. 7 0 .. 3 4 0
545
546 -- The rule is that the first bit is obtained by subtracting
547 -- the old ending bit from machine scalar size - 1.
548
549 for C in Start .. Stop loop
550 declare
551 Comp : constant Entity_Id := Comps (C);
552 CC : constant Node_Id :=
553 Component_Clause (Comp);
554 LB : constant Uint :=
555 Static_Integer (Last_Bit (CC));
556 NFB : constant Uint := MSS - Uint_1 - LB;
557 NLB : constant Uint := NFB + Esize (Comp) - 1;
558 Pos : constant Uint :=
559 Static_Integer (Position (CC));
560
561 begin
562 if Warn_On_Reverse_Bit_Order then
563 Error_Msg_Uint_1 := MSS;
564 Error_Msg_N
565 ("info: reverse bit order in machine " &
566 "scalar of length^?", First_Bit (CC));
567 Error_Msg_Uint_1 := NFB;
568 Error_Msg_Uint_2 := NLB;
569
570 if Bytes_Big_Endian then
571 Error_Msg_NE
572 ("?\info: big-endian range for "
573 & "component & is ^ .. ^",
574 First_Bit (CC), Comp);
575 else
576 Error_Msg_NE
577 ("?\info: little-endian range "
578 & "for component & is ^ .. ^",
579 First_Bit (CC), Comp);
580 end if;
581 end if;
582
583 Set_Component_Bit_Offset (Comp, Pos * SSU + NFB);
584 Set_Normalized_First_Bit (Comp, NFB mod SSU);
585 end;
586 end loop;
587 end loop;
588 end Sort_CC;
589 end;
590 end if;
591 end Adjust_Record_For_Reverse_Bit_Order;
592
593 --------------------------------------
594 -- Alignment_Check_For_Esize_Change --
595 --------------------------------------
596
597 procedure Alignment_Check_For_Esize_Change (Typ : Entity_Id) is
598 begin
599 -- If the alignment is known, and not set by a rep clause, and is
600 -- inconsistent with the size being set, then reset it to unknown,
601 -- we assume in this case that the size overrides the inherited
602 -- alignment, and that the alignment must be recomputed.
603
604 if Known_Alignment (Typ)
605 and then not Has_Alignment_Clause (Typ)
606 and then Esize (Typ) mod (Alignment (Typ) * SSU) /= 0
607 then
608 Init_Alignment (Typ);
609 end if;
610 end Alignment_Check_For_Esize_Change;
611
612 -----------------------
613 -- Analyze_At_Clause --
614 -----------------------
615
616 -- An at clause is replaced by the corresponding Address attribute
617 -- definition clause that is the preferred approach in Ada 95.
618
619 procedure Analyze_At_Clause (N : Node_Id) is
620 CS : constant Boolean := Comes_From_Source (N);
621
622 begin
623 -- This is an obsolescent feature
624
625 Check_Restriction (No_Obsolescent_Features, N);
626
627 if Warn_On_Obsolescent_Feature then
628 Error_Msg_N
629 ("at clause is an obsolescent feature (RM J.7(2))?", N);
630 Error_Msg_N
631 ("\use address attribute definition clause instead?", N);
632 end if;
633
634 -- Rewrite as address clause
635
636 Rewrite (N,
637 Make_Attribute_Definition_Clause (Sloc (N),
638 Name => Identifier (N),
639 Chars => Name_Address,
640 Expression => Expression (N)));
641
642 -- We preserve Comes_From_Source, since logically the clause still
643 -- comes from the source program even though it is changed in form.
644
645 Set_Comes_From_Source (N, CS);
646
647 -- Analyze rewritten clause
648
649 Analyze_Attribute_Definition_Clause (N);
650 end Analyze_At_Clause;
651
652 -----------------------------------------
653 -- Analyze_Attribute_Definition_Clause --
654 -----------------------------------------
655
656 procedure Analyze_Attribute_Definition_Clause (N : Node_Id) is
657 Loc : constant Source_Ptr := Sloc (N);
658 Nam : constant Node_Id := Name (N);
659 Attr : constant Name_Id := Chars (N);
660 Expr : constant Node_Id := Expression (N);
661 Id : constant Attribute_Id := Get_Attribute_Id (Attr);
662 Ent : Entity_Id;
663 U_Ent : Entity_Id;
664
665 FOnly : Boolean := False;
666 -- Reset to True for subtype specific attribute (Alignment, Size)
667 -- and for stream attributes, i.e. those cases where in the call
668 -- to Rep_Item_Too_Late, FOnly is set True so that only the freezing
669 -- rules are checked. Note that the case of stream attributes is not
670 -- clear from the RM, but see AI95-00137. Also, the RM seems to
671 -- disallow Storage_Size for derived task types, but that is also
672 -- clearly unintentional.
673
674 procedure Analyze_Stream_TSS_Definition (TSS_Nam : TSS_Name_Type);
675 -- Common processing for 'Read, 'Write, 'Input and 'Output attribute
676 -- definition clauses.
677
678 -----------------------------------
679 -- Analyze_Stream_TSS_Definition --
680 -----------------------------------
681
682 procedure Analyze_Stream_TSS_Definition (TSS_Nam : TSS_Name_Type) is
683 Subp : Entity_Id := Empty;
684 I : Interp_Index;
685 It : Interp;
686 Pnam : Entity_Id;
687
688 Is_Read : constant Boolean := (TSS_Nam = TSS_Stream_Read);
689
690 function Has_Good_Profile (Subp : Entity_Id) return Boolean;
691 -- Return true if the entity is a subprogram with an appropriate
692 -- profile for the attribute being defined.
693
694 ----------------------
695 -- Has_Good_Profile --
696 ----------------------
697
698 function Has_Good_Profile (Subp : Entity_Id) return Boolean is
699 F : Entity_Id;
700 Is_Function : constant Boolean := (TSS_Nam = TSS_Stream_Input);
701 Expected_Ekind : constant array (Boolean) of Entity_Kind :=
702 (False => E_Procedure, True => E_Function);
703 Typ : Entity_Id;
704
705 begin
706 if Ekind (Subp) /= Expected_Ekind (Is_Function) then
707 return False;
708 end if;
709
710 F := First_Formal (Subp);
711
712 if No (F)
713 or else Ekind (Etype (F)) /= E_Anonymous_Access_Type
714 or else Designated_Type (Etype (F)) /=
715 Class_Wide_Type (RTE (RE_Root_Stream_Type))
716 then
717 return False;
718 end if;
719
720 if not Is_Function then
721 Next_Formal (F);
722
723 declare
724 Expected_Mode : constant array (Boolean) of Entity_Kind :=
725 (False => E_In_Parameter,
726 True => E_Out_Parameter);
727 begin
728 if Parameter_Mode (F) /= Expected_Mode (Is_Read) then
729 return False;
730 end if;
731 end;
732
733 Typ := Etype (F);
734
735 else
736 Typ := Etype (Subp);
737 end if;
738
739 return Base_Type (Typ) = Base_Type (Ent)
740 and then No (Next_Formal (F));
741 end Has_Good_Profile;
742
743 -- Start of processing for Analyze_Stream_TSS_Definition
744
745 begin
746 FOnly := True;
747
748 if not Is_Type (U_Ent) then
749 Error_Msg_N ("local name must be a subtype", Nam);
750 return;
751 end if;
752
753 Pnam := TSS (Base_Type (U_Ent), TSS_Nam);
754
755 -- If Pnam is present, it can be either inherited from an ancestor
756 -- type (in which case it is legal to redefine it for this type), or
757 -- be a previous definition of the attribute for the same type (in
758 -- which case it is illegal).
759
760 -- In the first case, it will have been analyzed already, and we
761 -- can check that its profile does not match the expected profile
762 -- for a stream attribute of U_Ent. In the second case, either Pnam
763 -- has been analyzed (and has the expected profile), or it has not
764 -- been analyzed yet (case of a type that has not been frozen yet
765 -- and for which the stream attribute has been set using Set_TSS).
766
767 if Present (Pnam)
768 and then (No (First_Entity (Pnam)) or else Has_Good_Profile (Pnam))
769 then
770 Error_Msg_Sloc := Sloc (Pnam);
771 Error_Msg_Name_1 := Attr;
772 Error_Msg_N ("% attribute already defined #", Nam);
773 return;
774 end if;
775
776 Analyze (Expr);
777
778 if Is_Entity_Name (Expr) then
779 if not Is_Overloaded (Expr) then
780 if Has_Good_Profile (Entity (Expr)) then
781 Subp := Entity (Expr);
782 end if;
783
784 else
785 Get_First_Interp (Expr, I, It);
786 while Present (It.Nam) loop
787 if Has_Good_Profile (It.Nam) then
788 Subp := It.Nam;
789 exit;
790 end if;
791
792 Get_Next_Interp (I, It);
793 end loop;
794 end if;
795 end if;
796
797 if Present (Subp) then
798 if Is_Abstract_Subprogram (Subp) then
799 Error_Msg_N ("stream subprogram must not be abstract", Expr);
800 return;
801 end if;
802
803 Set_Entity (Expr, Subp);
804 Set_Etype (Expr, Etype (Subp));
805
806 New_Stream_Subprogram (N, U_Ent, Subp, TSS_Nam);
807
808 else
809 Error_Msg_Name_1 := Attr;
810 Error_Msg_N ("incorrect expression for% attribute", Expr);
811 end if;
812 end Analyze_Stream_TSS_Definition;
813
814 -- Start of processing for Analyze_Attribute_Definition_Clause
815
816 begin
817 -- Process Ignore_Rep_Clauses option
818
819 if Ignore_Rep_Clauses then
820 case Id is
821
822 -- The following should be ignored. They do not affect legality
823 -- and may be target dependent. The basic idea of -gnatI is to
824 -- ignore any rep clauses that may be target dependent but do not
825 -- affect legality (except possibly to be rejected because they
826 -- are incompatible with the compilation target).
827
828 when Attribute_Alignment |
829 Attribute_Bit_Order |
830 Attribute_Component_Size |
831 Attribute_Machine_Radix |
832 Attribute_Object_Size |
833 Attribute_Size |
834 Attribute_Small |
835 Attribute_Stream_Size |
836 Attribute_Value_Size =>
837
838 Rewrite (N, Make_Null_Statement (Sloc (N)));
839 return;
840
841 -- The following should not be ignored, because in the first place
842 -- they are reasonably portable, and should not cause problems in
843 -- compiling code from another target, and also they do affect
844 -- legality, e.g. failing to provide a stream attribute for a
845 -- type may make a program illegal.
846
847 when Attribute_External_Tag |
848 Attribute_Input |
849 Attribute_Output |
850 Attribute_Read |
851 Attribute_Storage_Pool |
852 Attribute_Storage_Size |
853 Attribute_Write =>
854 null;
855
856 -- Other cases are errors ("attribute& cannot be set with
857 -- definition clause"), which will be caught below.
858
859 when others =>
860 null;
861 end case;
862 end if;
863
864 Analyze (Nam);
865 Ent := Entity (Nam);
866
867 if Rep_Item_Too_Early (Ent, N) then
868 return;
869 end if;
870
871 -- Rep clause applies to full view of incomplete type or private type if
872 -- we have one (if not, this is a premature use of the type). However,
873 -- certain semantic checks need to be done on the specified entity (i.e.
874 -- the private view), so we save it in Ent.
875
876 if Is_Private_Type (Ent)
877 and then Is_Derived_Type (Ent)
878 and then not Is_Tagged_Type (Ent)
879 and then No (Full_View (Ent))
880 then
881 -- If this is a private type whose completion is a derivation from
882 -- another private type, there is no full view, and the attribute
883 -- belongs to the type itself, not its underlying parent.
884
885 U_Ent := Ent;
886
887 elsif Ekind (Ent) = E_Incomplete_Type then
888
889 -- The attribute applies to the full view, set the entity of the
890 -- attribute definition accordingly.
891
892 Ent := Underlying_Type (Ent);
893 U_Ent := Ent;
894 Set_Entity (Nam, Ent);
895
896 else
897 U_Ent := Underlying_Type (Ent);
898 end if;
899
900 -- Complete other routine error checks
901
902 if Etype (Nam) = Any_Type then
903 return;
904
905 elsif Scope (Ent) /= Current_Scope then
906 Error_Msg_N ("entity must be declared in this scope", Nam);
907 return;
908
909 elsif No (U_Ent) then
910 U_Ent := Ent;
911
912 elsif Is_Type (U_Ent)
913 and then not Is_First_Subtype (U_Ent)
914 and then Id /= Attribute_Object_Size
915 and then Id /= Attribute_Value_Size
916 and then not From_At_Mod (N)
917 then
918 Error_Msg_N ("cannot specify attribute for subtype", Nam);
919 return;
920 end if;
921
922 -- Switch on particular attribute
923
924 case Id is
925
926 -------------
927 -- Address --
928 -------------
929
930 -- Address attribute definition clause
931
932 when Attribute_Address => Address : begin
933
934 -- A little error check, catch for X'Address use X'Address;
935
936 if Nkind (Nam) = N_Identifier
937 and then Nkind (Expr) = N_Attribute_Reference
938 and then Attribute_Name (Expr) = Name_Address
939 and then Nkind (Prefix (Expr)) = N_Identifier
940 and then Chars (Nam) = Chars (Prefix (Expr))
941 then
942 Error_Msg_NE
943 ("address for & is self-referencing", Prefix (Expr), Ent);
944 return;
945 end if;
946
947 -- Not that special case, carry on with analysis of expression
948
949 Analyze_And_Resolve (Expr, RTE (RE_Address));
950
951 -- Even when ignoring rep clauses we need to indicate that the
952 -- entity has an address clause and thus it is legal to declare
953 -- it imported.
954
955 if Ignore_Rep_Clauses then
956 if Ekind_In (U_Ent, E_Variable, E_Constant) then
957 Record_Rep_Item (U_Ent, N);
958 end if;
959
960 return;
961 end if;
962
963 if Present (Address_Clause (U_Ent)) then
964 Error_Msg_N ("address already given for &", Nam);
965
966 -- Case of address clause for subprogram
967
968 elsif Is_Subprogram (U_Ent) then
969 if Has_Homonym (U_Ent) then
970 Error_Msg_N
971 ("address clause cannot be given " &
972 "for overloaded subprogram",
973 Nam);
974 return;
975 end if;
976
977 -- For subprograms, all address clauses are permitted, and we
978 -- mark the subprogram as having a deferred freeze so that Gigi
979 -- will not elaborate it too soon.
980
981 -- Above needs more comments, what is too soon about???
982
983 Set_Has_Delayed_Freeze (U_Ent);
984
985 -- Case of address clause for entry
986
987 elsif Ekind (U_Ent) = E_Entry then
988 if Nkind (Parent (N)) = N_Task_Body then
989 Error_Msg_N
990 ("entry address must be specified in task spec", Nam);
991 return;
992 end if;
993
994 -- For entries, we require a constant address
995
996 Check_Constant_Address_Clause (Expr, U_Ent);
997
998 -- Special checks for task types
999
1000 if Is_Task_Type (Scope (U_Ent))
1001 and then Comes_From_Source (Scope (U_Ent))
1002 then
1003 Error_Msg_N
1004 ("?entry address declared for entry in task type", N);
1005 Error_Msg_N
1006 ("\?only one task can be declared of this type", N);
1007 end if;
1008
1009 -- Entry address clauses are obsolescent
1010
1011 Check_Restriction (No_Obsolescent_Features, N);
1012
1013 if Warn_On_Obsolescent_Feature then
1014 Error_Msg_N
1015 ("attaching interrupt to task entry is an " &
1016 "obsolescent feature (RM J.7.1)?", N);
1017 Error_Msg_N
1018 ("\use interrupt procedure instead?", N);
1019 end if;
1020
1021 -- Case of an address clause for a controlled object which we
1022 -- consider to be erroneous.
1023
1024 elsif Is_Controlled (Etype (U_Ent))
1025 or else Has_Controlled_Component (Etype (U_Ent))
1026 then
1027 Error_Msg_NE
1028 ("?controlled object& must not be overlaid", Nam, U_Ent);
1029 Error_Msg_N
1030 ("\?Program_Error will be raised at run time", Nam);
1031 Insert_Action (Declaration_Node (U_Ent),
1032 Make_Raise_Program_Error (Loc,
1033 Reason => PE_Overlaid_Controlled_Object));
1034 return;
1035
1036 -- Case of address clause for a (non-controlled) object
1037
1038 elsif
1039 Ekind (U_Ent) = E_Variable
1040 or else
1041 Ekind (U_Ent) = E_Constant
1042 then
1043 declare
1044 Expr : constant Node_Id := Expression (N);
1045 O_Ent : Entity_Id;
1046 Off : Boolean;
1047
1048 begin
1049 -- Exported variables cannot have an address clause, because
1050 -- this cancels the effect of the pragma Export.
1051
1052 if Is_Exported (U_Ent) then
1053 Error_Msg_N
1054 ("cannot export object with address clause", Nam);
1055 return;
1056 end if;
1057
1058 Find_Overlaid_Entity (N, O_Ent, Off);
1059
1060 -- Overlaying controlled objects is erroneous
1061
1062 if Present (O_Ent)
1063 and then (Has_Controlled_Component (Etype (O_Ent))
1064 or else Is_Controlled (Etype (O_Ent)))
1065 then
1066 Error_Msg_N
1067 ("?cannot overlay with controlled object", Expr);
1068 Error_Msg_N
1069 ("\?Program_Error will be raised at run time", Expr);
1070 Insert_Action (Declaration_Node (U_Ent),
1071 Make_Raise_Program_Error (Loc,
1072 Reason => PE_Overlaid_Controlled_Object));
1073 return;
1074
1075 elsif Present (O_Ent)
1076 and then Ekind (U_Ent) = E_Constant
1077 and then not Is_Constant_Object (O_Ent)
1078 then
1079 Error_Msg_N ("constant overlays a variable?", Expr);
1080
1081 elsif Present (Renamed_Object (U_Ent)) then
1082 Error_Msg_N
1083 ("address clause not allowed"
1084 & " for a renaming declaration (RM 13.1(6))", Nam);
1085 return;
1086
1087 -- Imported variables can have an address clause, but then
1088 -- the import is pretty meaningless except to suppress
1089 -- initializations, so we do not need such variables to
1090 -- be statically allocated (and in fact it causes trouble
1091 -- if the address clause is a local value).
1092
1093 elsif Is_Imported (U_Ent) then
1094 Set_Is_Statically_Allocated (U_Ent, False);
1095 end if;
1096
1097 -- We mark a possible modification of a variable with an
1098 -- address clause, since it is likely aliasing is occurring.
1099
1100 Note_Possible_Modification (Nam, Sure => False);
1101
1102 -- Here we are checking for explicit overlap of one variable
1103 -- by another, and if we find this then mark the overlapped
1104 -- variable as also being volatile to prevent unwanted
1105 -- optimizations. This is a significant pessimization so
1106 -- avoid it when there is an offset, i.e. when the object
1107 -- is composite; they cannot be optimized easily anyway.
1108
1109 if Present (O_Ent)
1110 and then Is_Object (O_Ent)
1111 and then not Off
1112 then
1113 Set_Treat_As_Volatile (O_Ent);
1114 end if;
1115
1116 -- Legality checks on the address clause for initialized
1117 -- objects is deferred until the freeze point, because
1118 -- a subsequent pragma might indicate that the object is
1119 -- imported and thus not initialized.
1120
1121 Set_Has_Delayed_Freeze (U_Ent);
1122
1123 -- If an initialization call has been generated for this
1124 -- object, it needs to be deferred to after the freeze node
1125 -- we have just now added, otherwise GIGI will see a
1126 -- reference to the variable (as actual to the IP call)
1127 -- before its definition.
1128
1129 declare
1130 Init_Call : constant Node_Id := Find_Init_Call (U_Ent, N);
1131 begin
1132 if Present (Init_Call) then
1133 Remove (Init_Call);
1134 Append_Freeze_Action (U_Ent, Init_Call);
1135 end if;
1136 end;
1137
1138 if Is_Exported (U_Ent) then
1139 Error_Msg_N
1140 ("& cannot be exported if an address clause is given",
1141 Nam);
1142 Error_Msg_N
1143 ("\define and export a variable " &
1144 "that holds its address instead",
1145 Nam);
1146 end if;
1147
1148 -- Entity has delayed freeze, so we will generate an
1149 -- alignment check at the freeze point unless suppressed.
1150
1151 if not Range_Checks_Suppressed (U_Ent)
1152 and then not Alignment_Checks_Suppressed (U_Ent)
1153 then
1154 Set_Check_Address_Alignment (N);
1155 end if;
1156
1157 -- Kill the size check code, since we are not allocating
1158 -- the variable, it is somewhere else.
1159
1160 Kill_Size_Check_Code (U_Ent);
1161
1162 -- If the address clause is of the form:
1163
1164 -- for Y'Address use X'Address
1165
1166 -- or
1167
1168 -- Const : constant Address := X'Address;
1169 -- ...
1170 -- for Y'Address use Const;
1171
1172 -- then we make an entry in the table for checking the size
1173 -- and alignment of the overlaying variable. We defer this
1174 -- check till after code generation to take full advantage
1175 -- of the annotation done by the back end. This entry is
1176 -- only made if the address clause comes from source.
1177 -- If the entity has a generic type, the check will be
1178 -- performed in the instance if the actual type justifies
1179 -- it, and we do not insert the clause in the table to
1180 -- prevent spurious warnings.
1181
1182 if Address_Clause_Overlay_Warnings
1183 and then Comes_From_Source (N)
1184 and then Present (O_Ent)
1185 and then Is_Object (O_Ent)
1186 then
1187 if not Is_Generic_Type (Etype (U_Ent)) then
1188 Address_Clause_Checks.Append ((N, U_Ent, O_Ent, Off));
1189 end if;
1190
1191 -- If variable overlays a constant view, and we are
1192 -- warning on overlays, then mark the variable as
1193 -- overlaying a constant (we will give warnings later
1194 -- if this variable is assigned).
1195
1196 if Is_Constant_Object (O_Ent)
1197 and then Ekind (U_Ent) = E_Variable
1198 then
1199 Set_Overlays_Constant (U_Ent);
1200 end if;
1201 end if;
1202 end;
1203
1204 -- Not a valid entity for an address clause
1205
1206 else
1207 Error_Msg_N ("address cannot be given for &", Nam);
1208 end if;
1209 end Address;
1210
1211 ---------------
1212 -- Alignment --
1213 ---------------
1214
1215 -- Alignment attribute definition clause
1216
1217 when Attribute_Alignment => Alignment : declare
1218 Align : constant Uint := Get_Alignment_Value (Expr);
1219
1220 begin
1221 FOnly := True;
1222
1223 if not Is_Type (U_Ent)
1224 and then Ekind (U_Ent) /= E_Variable
1225 and then Ekind (U_Ent) /= E_Constant
1226 then
1227 Error_Msg_N ("alignment cannot be given for &", Nam);
1228
1229 elsif Has_Alignment_Clause (U_Ent) then
1230 Error_Msg_Sloc := Sloc (Alignment_Clause (U_Ent));
1231 Error_Msg_N ("alignment clause previously given#", N);
1232
1233 elsif Align /= No_Uint then
1234 Set_Has_Alignment_Clause (U_Ent);
1235 Set_Alignment (U_Ent, Align);
1236
1237 -- For an array type, U_Ent is the first subtype. In that case,
1238 -- also set the alignment of the anonymous base type so that
1239 -- other subtypes (such as the itypes for aggregates of the
1240 -- type) also receive the expected alignment.
1241
1242 if Is_Array_Type (U_Ent) then
1243 Set_Alignment (Base_Type (U_Ent), Align);
1244 end if;
1245 end if;
1246 end Alignment;
1247
1248 ---------------
1249 -- Bit_Order --
1250 ---------------
1251
1252 -- Bit_Order attribute definition clause
1253
1254 when Attribute_Bit_Order => Bit_Order : declare
1255 begin
1256 if not Is_Record_Type (U_Ent) then
1257 Error_Msg_N
1258 ("Bit_Order can only be defined for record type", Nam);
1259
1260 else
1261 Analyze_And_Resolve (Expr, RTE (RE_Bit_Order));
1262
1263 if Etype (Expr) = Any_Type then
1264 return;
1265
1266 elsif not Is_Static_Expression (Expr) then
1267 Flag_Non_Static_Expr
1268 ("Bit_Order requires static expression!", Expr);
1269
1270 else
1271 if (Expr_Value (Expr) = 0) /= Bytes_Big_Endian then
1272 Set_Reverse_Bit_Order (U_Ent, True);
1273 end if;
1274 end if;
1275 end if;
1276 end Bit_Order;
1277
1278 --------------------
1279 -- Component_Size --
1280 --------------------
1281
1282 -- Component_Size attribute definition clause
1283
1284 when Attribute_Component_Size => Component_Size_Case : declare
1285 Csize : constant Uint := Static_Integer (Expr);
1286 Ctyp : Entity_Id;
1287 Btype : Entity_Id;
1288 Biased : Boolean;
1289 New_Ctyp : Entity_Id;
1290 Decl : Node_Id;
1291
1292 begin
1293 if not Is_Array_Type (U_Ent) then
1294 Error_Msg_N ("component size requires array type", Nam);
1295 return;
1296 end if;
1297
1298 Btype := Base_Type (U_Ent);
1299 Ctyp := Component_Type (Btype);
1300
1301 if Has_Component_Size_Clause (Btype) then
1302 Error_Msg_N
1303 ("component size clause for& previously given", Nam);
1304
1305 elsif Csize /= No_Uint then
1306 Check_Size (Expr, Ctyp, Csize, Biased);
1307
1308 if Has_Aliased_Components (Btype)
1309 and then Csize < 32
1310 and then Csize /= 8
1311 and then Csize /= 16
1312 then
1313 Error_Msg_N
1314 ("component size incorrect for aliased components", N);
1315 return;
1316 end if;
1317
1318 -- For the biased case, build a declaration for a subtype
1319 -- that will be used to represent the biased subtype that
1320 -- reflects the biased representation of components. We need
1321 -- this subtype to get proper conversions on referencing
1322 -- elements of the array. Note that component size clauses
1323 -- are ignored in VM mode.
1324
1325 if VM_Target = No_VM then
1326 if Biased then
1327 New_Ctyp :=
1328 Make_Defining_Identifier (Loc,
1329 Chars =>
1330 New_External_Name (Chars (U_Ent), 'C', 0, 'T'));
1331
1332 Decl :=
1333 Make_Subtype_Declaration (Loc,
1334 Defining_Identifier => New_Ctyp,
1335 Subtype_Indication =>
1336 New_Occurrence_Of (Component_Type (Btype), Loc));
1337
1338 Set_Parent (Decl, N);
1339 Analyze (Decl, Suppress => All_Checks);
1340
1341 Set_Has_Delayed_Freeze (New_Ctyp, False);
1342 Set_Esize (New_Ctyp, Csize);
1343 Set_RM_Size (New_Ctyp, Csize);
1344 Init_Alignment (New_Ctyp);
1345 Set_Has_Biased_Representation (New_Ctyp, True);
1346 Set_Is_Itype (New_Ctyp, True);
1347 Set_Associated_Node_For_Itype (New_Ctyp, U_Ent);
1348
1349 Set_Component_Type (Btype, New_Ctyp);
1350
1351 if Warn_On_Biased_Representation then
1352 Error_Msg_N
1353 ("?component size clause forces biased "
1354 & "representation", N);
1355 end if;
1356 end if;
1357
1358 Set_Component_Size (Btype, Csize);
1359
1360 -- For VM case, we ignore component size clauses
1361
1362 else
1363 -- Give a warning unless we are in GNAT mode, in which case
1364 -- the warning is suppressed since it is not useful.
1365
1366 if not GNAT_Mode then
1367 Error_Msg_N
1368 ("?component size ignored in this configuration", N);
1369 end if;
1370 end if;
1371
1372 -- Deal with warning on overridden size
1373
1374 if Warn_On_Overridden_Size
1375 and then Has_Size_Clause (Ctyp)
1376 and then RM_Size (Ctyp) /= Csize
1377 then
1378 Error_Msg_NE
1379 ("?component size overrides size clause for&",
1380 N, Ctyp);
1381 end if;
1382
1383 Set_Has_Component_Size_Clause (Btype, True);
1384 Set_Has_Non_Standard_Rep (Btype, True);
1385 end if;
1386 end Component_Size_Case;
1387
1388 ------------------
1389 -- External_Tag --
1390 ------------------
1391
1392 when Attribute_External_Tag => External_Tag :
1393 begin
1394 if not Is_Tagged_Type (U_Ent) then
1395 Error_Msg_N ("should be a tagged type", Nam);
1396 end if;
1397
1398 Analyze_And_Resolve (Expr, Standard_String);
1399
1400 if not Is_Static_Expression (Expr) then
1401 Flag_Non_Static_Expr
1402 ("static string required for tag name!", Nam);
1403 end if;
1404
1405 if VM_Target = No_VM then
1406 Set_Has_External_Tag_Rep_Clause (U_Ent);
1407 else
1408 Error_Msg_Name_1 := Attr;
1409 Error_Msg_N
1410 ("% attribute unsupported in this configuration", Nam);
1411 end if;
1412
1413 if not Is_Library_Level_Entity (U_Ent) then
1414 Error_Msg_NE
1415 ("?non-unique external tag supplied for &", N, U_Ent);
1416 Error_Msg_N
1417 ("?\same external tag applies to all subprogram calls", N);
1418 Error_Msg_N
1419 ("?\corresponding internal tag cannot be obtained", N);
1420 end if;
1421 end External_Tag;
1422
1423 -----------
1424 -- Input --
1425 -----------
1426
1427 when Attribute_Input =>
1428 Analyze_Stream_TSS_Definition (TSS_Stream_Input);
1429 Set_Has_Specified_Stream_Input (Ent);
1430
1431 -------------------
1432 -- Machine_Radix --
1433 -------------------
1434
1435 -- Machine radix attribute definition clause
1436
1437 when Attribute_Machine_Radix => Machine_Radix : declare
1438 Radix : constant Uint := Static_Integer (Expr);
1439
1440 begin
1441 if not Is_Decimal_Fixed_Point_Type (U_Ent) then
1442 Error_Msg_N ("decimal fixed-point type expected for &", Nam);
1443
1444 elsif Has_Machine_Radix_Clause (U_Ent) then
1445 Error_Msg_Sloc := Sloc (Alignment_Clause (U_Ent));
1446 Error_Msg_N ("machine radix clause previously given#", N);
1447
1448 elsif Radix /= No_Uint then
1449 Set_Has_Machine_Radix_Clause (U_Ent);
1450 Set_Has_Non_Standard_Rep (Base_Type (U_Ent));
1451
1452 if Radix = 2 then
1453 null;
1454 elsif Radix = 10 then
1455 Set_Machine_Radix_10 (U_Ent);
1456 else
1457 Error_Msg_N ("machine radix value must be 2 or 10", Expr);
1458 end if;
1459 end if;
1460 end Machine_Radix;
1461
1462 -----------------
1463 -- Object_Size --
1464 -----------------
1465
1466 -- Object_Size attribute definition clause
1467
1468 when Attribute_Object_Size => Object_Size : declare
1469 Size : constant Uint := Static_Integer (Expr);
1470
1471 Biased : Boolean;
1472 pragma Warnings (Off, Biased);
1473
1474 begin
1475 if not Is_Type (U_Ent) then
1476 Error_Msg_N ("Object_Size cannot be given for &", Nam);
1477
1478 elsif Has_Object_Size_Clause (U_Ent) then
1479 Error_Msg_N ("Object_Size already given for &", Nam);
1480
1481 else
1482 Check_Size (Expr, U_Ent, Size, Biased);
1483
1484 if Size /= 8
1485 and then
1486 Size /= 16
1487 and then
1488 Size /= 32
1489 and then
1490 UI_Mod (Size, 64) /= 0
1491 then
1492 Error_Msg_N
1493 ("Object_Size must be 8, 16, 32, or multiple of 64",
1494 Expr);
1495 end if;
1496
1497 Set_Esize (U_Ent, Size);
1498 Set_Has_Object_Size_Clause (U_Ent);
1499 Alignment_Check_For_Esize_Change (U_Ent);
1500 end if;
1501 end Object_Size;
1502
1503 ------------
1504 -- Output --
1505 ------------
1506
1507 when Attribute_Output =>
1508 Analyze_Stream_TSS_Definition (TSS_Stream_Output);
1509 Set_Has_Specified_Stream_Output (Ent);
1510
1511 ----------
1512 -- Read --
1513 ----------
1514
1515 when Attribute_Read =>
1516 Analyze_Stream_TSS_Definition (TSS_Stream_Read);
1517 Set_Has_Specified_Stream_Read (Ent);
1518
1519 ----------
1520 -- Size --
1521 ----------
1522
1523 -- Size attribute definition clause
1524
1525 when Attribute_Size => Size : declare
1526 Size : constant Uint := Static_Integer (Expr);
1527 Etyp : Entity_Id;
1528 Biased : Boolean;
1529
1530 begin
1531 FOnly := True;
1532
1533 if Has_Size_Clause (U_Ent) then
1534 Error_Msg_N ("size already given for &", Nam);
1535
1536 elsif not Is_Type (U_Ent)
1537 and then Ekind (U_Ent) /= E_Variable
1538 and then Ekind (U_Ent) /= E_Constant
1539 then
1540 Error_Msg_N ("size cannot be given for &", Nam);
1541
1542 elsif Is_Array_Type (U_Ent)
1543 and then not Is_Constrained (U_Ent)
1544 then
1545 Error_Msg_N
1546 ("size cannot be given for unconstrained array", Nam);
1547
1548 elsif Size /= No_Uint then
1549
1550 if VM_Target /= No_VM and then not GNAT_Mode then
1551
1552 -- Size clause is not handled properly on VM targets.
1553 -- Display a warning unless we are in GNAT mode, in which
1554 -- case this is useless.
1555
1556 Error_Msg_N
1557 ("?size clauses are ignored in this configuration", N);
1558 end if;
1559
1560 if Is_Type (U_Ent) then
1561 Etyp := U_Ent;
1562 else
1563 Etyp := Etype (U_Ent);
1564 end if;
1565
1566 -- Check size, note that Gigi is in charge of checking that the
1567 -- size of an array or record type is OK. Also we do not check
1568 -- the size in the ordinary fixed-point case, since it is too
1569 -- early to do so (there may be subsequent small clause that
1570 -- affects the size). We can check the size if a small clause
1571 -- has already been given.
1572
1573 if not Is_Ordinary_Fixed_Point_Type (U_Ent)
1574 or else Has_Small_Clause (U_Ent)
1575 then
1576 Check_Size (Expr, Etyp, Size, Biased);
1577 Set_Has_Biased_Representation (U_Ent, Biased);
1578
1579 if Biased and Warn_On_Biased_Representation then
1580 Error_Msg_N
1581 ("?size clause forces biased representation", N);
1582 end if;
1583 end if;
1584
1585 -- For types set RM_Size and Esize if possible
1586
1587 if Is_Type (U_Ent) then
1588 Set_RM_Size (U_Ent, Size);
1589
1590 -- For scalar types, increase Object_Size to power of 2, but
1591 -- not less than a storage unit in any case (i.e., normally
1592 -- this means it will be byte addressable).
1593
1594 if Is_Scalar_Type (U_Ent) then
1595 if Size <= System_Storage_Unit then
1596 Init_Esize (U_Ent, System_Storage_Unit);
1597 elsif Size <= 16 then
1598 Init_Esize (U_Ent, 16);
1599 elsif Size <= 32 then
1600 Init_Esize (U_Ent, 32);
1601 else
1602 Set_Esize (U_Ent, (Size + 63) / 64 * 64);
1603 end if;
1604
1605 -- For all other types, object size = value size. The
1606 -- backend will adjust as needed.
1607
1608 else
1609 Set_Esize (U_Ent, Size);
1610 end if;
1611
1612 Alignment_Check_For_Esize_Change (U_Ent);
1613
1614 -- For objects, set Esize only
1615
1616 else
1617 if Is_Elementary_Type (Etyp) then
1618 if Size /= System_Storage_Unit
1619 and then
1620 Size /= System_Storage_Unit * 2
1621 and then
1622 Size /= System_Storage_Unit * 4
1623 and then
1624 Size /= System_Storage_Unit * 8
1625 then
1626 Error_Msg_Uint_1 := UI_From_Int (System_Storage_Unit);
1627 Error_Msg_Uint_2 := Error_Msg_Uint_1 * 8;
1628 Error_Msg_N
1629 ("size for primitive object must be a power of 2"
1630 & " in the range ^-^", N);
1631 end if;
1632 end if;
1633
1634 Set_Esize (U_Ent, Size);
1635 end if;
1636
1637 Set_Has_Size_Clause (U_Ent);
1638 end if;
1639 end Size;
1640
1641 -----------
1642 -- Small --
1643 -----------
1644
1645 -- Small attribute definition clause
1646
1647 when Attribute_Small => Small : declare
1648 Implicit_Base : constant Entity_Id := Base_Type (U_Ent);
1649 Small : Ureal;
1650
1651 begin
1652 Analyze_And_Resolve (Expr, Any_Real);
1653
1654 if Etype (Expr) = Any_Type then
1655 return;
1656
1657 elsif not Is_Static_Expression (Expr) then
1658 Flag_Non_Static_Expr
1659 ("small requires static expression!", Expr);
1660 return;
1661
1662 else
1663 Small := Expr_Value_R (Expr);
1664
1665 if Small <= Ureal_0 then
1666 Error_Msg_N ("small value must be greater than zero", Expr);
1667 return;
1668 end if;
1669
1670 end if;
1671
1672 if not Is_Ordinary_Fixed_Point_Type (U_Ent) then
1673 Error_Msg_N
1674 ("small requires an ordinary fixed point type", Nam);
1675
1676 elsif Has_Small_Clause (U_Ent) then
1677 Error_Msg_N ("small already given for &", Nam);
1678
1679 elsif Small > Delta_Value (U_Ent) then
1680 Error_Msg_N
1681 ("small value must not be greater then delta value", Nam);
1682
1683 else
1684 Set_Small_Value (U_Ent, Small);
1685 Set_Small_Value (Implicit_Base, Small);
1686 Set_Has_Small_Clause (U_Ent);
1687 Set_Has_Small_Clause (Implicit_Base);
1688 Set_Has_Non_Standard_Rep (Implicit_Base);
1689 end if;
1690 end Small;
1691
1692 ------------------
1693 -- Storage_Pool --
1694 ------------------
1695
1696 -- Storage_Pool attribute definition clause
1697
1698 when Attribute_Storage_Pool => Storage_Pool : declare
1699 Pool : Entity_Id;
1700 T : Entity_Id;
1701
1702 begin
1703 if Ekind (U_Ent) = E_Access_Subprogram_Type then
1704 Error_Msg_N
1705 ("storage pool cannot be given for access-to-subprogram type",
1706 Nam);
1707 return;
1708
1709 elsif not
1710 Ekind_In (U_Ent, E_Access_Type, E_General_Access_Type)
1711 then
1712 Error_Msg_N
1713 ("storage pool can only be given for access types", Nam);
1714 return;
1715
1716 elsif Is_Derived_Type (U_Ent) then
1717 Error_Msg_N
1718 ("storage pool cannot be given for a derived access type",
1719 Nam);
1720
1721 elsif Has_Storage_Size_Clause (U_Ent) then
1722 Error_Msg_N ("storage size already given for &", Nam);
1723 return;
1724
1725 elsif Present (Associated_Storage_Pool (U_Ent)) then
1726 Error_Msg_N ("storage pool already given for &", Nam);
1727 return;
1728 end if;
1729
1730 Analyze_And_Resolve
1731 (Expr, Class_Wide_Type (RTE (RE_Root_Storage_Pool)));
1732
1733 if not Denotes_Variable (Expr) then
1734 Error_Msg_N ("storage pool must be a variable", Expr);
1735 return;
1736 end if;
1737
1738 if Nkind (Expr) = N_Type_Conversion then
1739 T := Etype (Expression (Expr));
1740 else
1741 T := Etype (Expr);
1742 end if;
1743
1744 -- The Stack_Bounded_Pool is used internally for implementing
1745 -- access types with a Storage_Size. Since it only work
1746 -- properly when used on one specific type, we need to check
1747 -- that it is not hijacked improperly:
1748 -- type T is access Integer;
1749 -- for T'Storage_Size use n;
1750 -- type Q is access Float;
1751 -- for Q'Storage_Size use T'Storage_Size; -- incorrect
1752
1753 if RTE_Available (RE_Stack_Bounded_Pool)
1754 and then Base_Type (T) = RTE (RE_Stack_Bounded_Pool)
1755 then
1756 Error_Msg_N ("non-shareable internal Pool", Expr);
1757 return;
1758 end if;
1759
1760 -- If the argument is a name that is not an entity name, then
1761 -- we construct a renaming operation to define an entity of
1762 -- type storage pool.
1763
1764 if not Is_Entity_Name (Expr)
1765 and then Is_Object_Reference (Expr)
1766 then
1767 Pool := Make_Temporary (Loc, 'P', Expr);
1768
1769 declare
1770 Rnode : constant Node_Id :=
1771 Make_Object_Renaming_Declaration (Loc,
1772 Defining_Identifier => Pool,
1773 Subtype_Mark =>
1774 New_Occurrence_Of (Etype (Expr), Loc),
1775 Name => Expr);
1776
1777 begin
1778 Insert_Before (N, Rnode);
1779 Analyze (Rnode);
1780 Set_Associated_Storage_Pool (U_Ent, Pool);
1781 end;
1782
1783 elsif Is_Entity_Name (Expr) then
1784 Pool := Entity (Expr);
1785
1786 -- If pool is a renamed object, get original one. This can
1787 -- happen with an explicit renaming, and within instances.
1788
1789 while Present (Renamed_Object (Pool))
1790 and then Is_Entity_Name (Renamed_Object (Pool))
1791 loop
1792 Pool := Entity (Renamed_Object (Pool));
1793 end loop;
1794
1795 if Present (Renamed_Object (Pool))
1796 and then Nkind (Renamed_Object (Pool)) = N_Type_Conversion
1797 and then Is_Entity_Name (Expression (Renamed_Object (Pool)))
1798 then
1799 Pool := Entity (Expression (Renamed_Object (Pool)));
1800 end if;
1801
1802 Set_Associated_Storage_Pool (U_Ent, Pool);
1803
1804 elsif Nkind (Expr) = N_Type_Conversion
1805 and then Is_Entity_Name (Expression (Expr))
1806 and then Nkind (Original_Node (Expr)) = N_Attribute_Reference
1807 then
1808 Pool := Entity (Expression (Expr));
1809 Set_Associated_Storage_Pool (U_Ent, Pool);
1810
1811 else
1812 Error_Msg_N ("incorrect reference to a Storage Pool", Expr);
1813 return;
1814 end if;
1815 end Storage_Pool;
1816
1817 ------------------
1818 -- Storage_Size --
1819 ------------------
1820
1821 -- Storage_Size attribute definition clause
1822
1823 when Attribute_Storage_Size => Storage_Size : declare
1824 Btype : constant Entity_Id := Base_Type (U_Ent);
1825 Sprag : Node_Id;
1826
1827 begin
1828 if Is_Task_Type (U_Ent) then
1829 Check_Restriction (No_Obsolescent_Features, N);
1830
1831 if Warn_On_Obsolescent_Feature then
1832 Error_Msg_N
1833 ("storage size clause for task is an " &
1834 "obsolescent feature (RM J.9)?", N);
1835 Error_Msg_N ("\use Storage_Size pragma instead?", N);
1836 end if;
1837
1838 FOnly := True;
1839 end if;
1840
1841 if not Is_Access_Type (U_Ent)
1842 and then Ekind (U_Ent) /= E_Task_Type
1843 then
1844 Error_Msg_N ("storage size cannot be given for &", Nam);
1845
1846 elsif Is_Access_Type (U_Ent) and Is_Derived_Type (U_Ent) then
1847 Error_Msg_N
1848 ("storage size cannot be given for a derived access type",
1849 Nam);
1850
1851 elsif Has_Storage_Size_Clause (Btype) then
1852 Error_Msg_N ("storage size already given for &", Nam);
1853
1854 else
1855 Analyze_And_Resolve (Expr, Any_Integer);
1856
1857 if Is_Access_Type (U_Ent) then
1858 if Present (Associated_Storage_Pool (U_Ent)) then
1859 Error_Msg_N ("storage pool already given for &", Nam);
1860 return;
1861 end if;
1862
1863 if Compile_Time_Known_Value (Expr)
1864 and then Expr_Value (Expr) = 0
1865 then
1866 Set_No_Pool_Assigned (Btype);
1867 end if;
1868
1869 else -- Is_Task_Type (U_Ent)
1870 Sprag := Get_Rep_Pragma (Btype, Name_Storage_Size);
1871
1872 if Present (Sprag) then
1873 Error_Msg_Sloc := Sloc (Sprag);
1874 Error_Msg_N
1875 ("Storage_Size already specified#", Nam);
1876 return;
1877 end if;
1878 end if;
1879
1880 Set_Has_Storage_Size_Clause (Btype);
1881 end if;
1882 end Storage_Size;
1883
1884 -----------------
1885 -- Stream_Size --
1886 -----------------
1887
1888 when Attribute_Stream_Size => Stream_Size : declare
1889 Size : constant Uint := Static_Integer (Expr);
1890
1891 begin
1892 if Ada_Version <= Ada_95 then
1893 Check_Restriction (No_Implementation_Attributes, N);
1894 end if;
1895
1896 if Has_Stream_Size_Clause (U_Ent) then
1897 Error_Msg_N ("Stream_Size already given for &", Nam);
1898
1899 elsif Is_Elementary_Type (U_Ent) then
1900 if Size /= System_Storage_Unit
1901 and then
1902 Size /= System_Storage_Unit * 2
1903 and then
1904 Size /= System_Storage_Unit * 4
1905 and then
1906 Size /= System_Storage_Unit * 8
1907 then
1908 Error_Msg_Uint_1 := UI_From_Int (System_Storage_Unit);
1909 Error_Msg_N
1910 ("stream size for elementary type must be a"
1911 & " power of 2 and at least ^", N);
1912
1913 elsif RM_Size (U_Ent) > Size then
1914 Error_Msg_Uint_1 := RM_Size (U_Ent);
1915 Error_Msg_N
1916 ("stream size for elementary type must be a"
1917 & " power of 2 and at least ^", N);
1918 end if;
1919
1920 Set_Has_Stream_Size_Clause (U_Ent);
1921
1922 else
1923 Error_Msg_N ("Stream_Size cannot be given for &", Nam);
1924 end if;
1925 end Stream_Size;
1926
1927 ----------------
1928 -- Value_Size --
1929 ----------------
1930
1931 -- Value_Size attribute definition clause
1932
1933 when Attribute_Value_Size => Value_Size : declare
1934 Size : constant Uint := Static_Integer (Expr);
1935 Biased : Boolean;
1936
1937 begin
1938 if not Is_Type (U_Ent) then
1939 Error_Msg_N ("Value_Size cannot be given for &", Nam);
1940
1941 elsif Present
1942 (Get_Attribute_Definition_Clause
1943 (U_Ent, Attribute_Value_Size))
1944 then
1945 Error_Msg_N ("Value_Size already given for &", Nam);
1946
1947 elsif Is_Array_Type (U_Ent)
1948 and then not Is_Constrained (U_Ent)
1949 then
1950 Error_Msg_N
1951 ("Value_Size cannot be given for unconstrained array", Nam);
1952
1953 else
1954 if Is_Elementary_Type (U_Ent) then
1955 Check_Size (Expr, U_Ent, Size, Biased);
1956 Set_Has_Biased_Representation (U_Ent, Biased);
1957
1958 if Biased and Warn_On_Biased_Representation then
1959 Error_Msg_N
1960 ("?value size clause forces biased representation", N);
1961 end if;
1962 end if;
1963
1964 Set_RM_Size (U_Ent, Size);
1965 end if;
1966 end Value_Size;
1967
1968 -----------
1969 -- Write --
1970 -----------
1971
1972 when Attribute_Write =>
1973 Analyze_Stream_TSS_Definition (TSS_Stream_Write);
1974 Set_Has_Specified_Stream_Write (Ent);
1975
1976 -- All other attributes cannot be set
1977
1978 when others =>
1979 Error_Msg_N
1980 ("attribute& cannot be set with definition clause", N);
1981 end case;
1982
1983 -- The test for the type being frozen must be performed after
1984 -- any expression the clause has been analyzed since the expression
1985 -- itself might cause freezing that makes the clause illegal.
1986
1987 if Rep_Item_Too_Late (U_Ent, N, FOnly) then
1988 return;
1989 end if;
1990 end Analyze_Attribute_Definition_Clause;
1991
1992 ----------------------------
1993 -- Analyze_Code_Statement --
1994 ----------------------------
1995
1996 procedure Analyze_Code_Statement (N : Node_Id) is
1997 HSS : constant Node_Id := Parent (N);
1998 SBody : constant Node_Id := Parent (HSS);
1999 Subp : constant Entity_Id := Current_Scope;
2000 Stmt : Node_Id;
2001 Decl : Node_Id;
2002 StmtO : Node_Id;
2003 DeclO : Node_Id;
2004
2005 begin
2006 -- Analyze and check we get right type, note that this implements the
2007 -- requirement (RM 13.8(1)) that Machine_Code be with'ed, since that
2008 -- is the only way that Asm_Insn could possibly be visible.
2009
2010 Analyze_And_Resolve (Expression (N));
2011
2012 if Etype (Expression (N)) = Any_Type then
2013 return;
2014 elsif Etype (Expression (N)) /= RTE (RE_Asm_Insn) then
2015 Error_Msg_N ("incorrect type for code statement", N);
2016 return;
2017 end if;
2018
2019 Check_Code_Statement (N);
2020
2021 -- Make sure we appear in the handled statement sequence of a
2022 -- subprogram (RM 13.8(3)).
2023
2024 if Nkind (HSS) /= N_Handled_Sequence_Of_Statements
2025 or else Nkind (SBody) /= N_Subprogram_Body
2026 then
2027 Error_Msg_N
2028 ("code statement can only appear in body of subprogram", N);
2029 return;
2030 end if;
2031
2032 -- Do remaining checks (RM 13.8(3)) if not already done
2033
2034 if not Is_Machine_Code_Subprogram (Subp) then
2035 Set_Is_Machine_Code_Subprogram (Subp);
2036
2037 -- No exception handlers allowed
2038
2039 if Present (Exception_Handlers (HSS)) then
2040 Error_Msg_N
2041 ("exception handlers not permitted in machine code subprogram",
2042 First (Exception_Handlers (HSS)));
2043 end if;
2044
2045 -- No declarations other than use clauses and pragmas (we allow
2046 -- certain internally generated declarations as well).
2047
2048 Decl := First (Declarations (SBody));
2049 while Present (Decl) loop
2050 DeclO := Original_Node (Decl);
2051 if Comes_From_Source (DeclO)
2052 and not Nkind_In (DeclO, N_Pragma,
2053 N_Use_Package_Clause,
2054 N_Use_Type_Clause,
2055 N_Implicit_Label_Declaration)
2056 then
2057 Error_Msg_N
2058 ("this declaration not allowed in machine code subprogram",
2059 DeclO);
2060 end if;
2061
2062 Next (Decl);
2063 end loop;
2064
2065 -- No statements other than code statements, pragmas, and labels.
2066 -- Again we allow certain internally generated statements.
2067
2068 Stmt := First (Statements (HSS));
2069 while Present (Stmt) loop
2070 StmtO := Original_Node (Stmt);
2071 if Comes_From_Source (StmtO)
2072 and then not Nkind_In (StmtO, N_Pragma,
2073 N_Label,
2074 N_Code_Statement)
2075 then
2076 Error_Msg_N
2077 ("this statement is not allowed in machine code subprogram",
2078 StmtO);
2079 end if;
2080
2081 Next (Stmt);
2082 end loop;
2083 end if;
2084 end Analyze_Code_Statement;
2085
2086 -----------------------------------------------
2087 -- Analyze_Enumeration_Representation_Clause --
2088 -----------------------------------------------
2089
2090 procedure Analyze_Enumeration_Representation_Clause (N : Node_Id) is
2091 Ident : constant Node_Id := Identifier (N);
2092 Aggr : constant Node_Id := Array_Aggregate (N);
2093 Enumtype : Entity_Id;
2094 Elit : Entity_Id;
2095 Expr : Node_Id;
2096 Assoc : Node_Id;
2097 Choice : Node_Id;
2098 Val : Uint;
2099 Err : Boolean := False;
2100
2101 Lo : constant Uint := Expr_Value (Type_Low_Bound (Universal_Integer));
2102 Hi : constant Uint := Expr_Value (Type_High_Bound (Universal_Integer));
2103 Min : Uint;
2104 Max : Uint;
2105
2106 begin
2107 if Ignore_Rep_Clauses then
2108 return;
2109 end if;
2110
2111 -- First some basic error checks
2112
2113 Find_Type (Ident);
2114 Enumtype := Entity (Ident);
2115
2116 if Enumtype = Any_Type
2117 or else Rep_Item_Too_Early (Enumtype, N)
2118 then
2119 return;
2120 else
2121 Enumtype := Underlying_Type (Enumtype);
2122 end if;
2123
2124 if not Is_Enumeration_Type (Enumtype) then
2125 Error_Msg_NE
2126 ("enumeration type required, found}",
2127 Ident, First_Subtype (Enumtype));
2128 return;
2129 end if;
2130
2131 -- Ignore rep clause on generic actual type. This will already have
2132 -- been flagged on the template as an error, and this is the safest
2133 -- way to ensure we don't get a junk cascaded message in the instance.
2134
2135 if Is_Generic_Actual_Type (Enumtype) then
2136 return;
2137
2138 -- Type must be in current scope
2139
2140 elsif Scope (Enumtype) /= Current_Scope then
2141 Error_Msg_N ("type must be declared in this scope", Ident);
2142 return;
2143
2144 -- Type must be a first subtype
2145
2146 elsif not Is_First_Subtype (Enumtype) then
2147 Error_Msg_N ("cannot give enumeration rep clause for subtype", N);
2148 return;
2149
2150 -- Ignore duplicate rep clause
2151
2152 elsif Has_Enumeration_Rep_Clause (Enumtype) then
2153 Error_Msg_N ("duplicate enumeration rep clause ignored", N);
2154 return;
2155
2156 -- Don't allow rep clause for standard [wide_[wide_]]character
2157
2158 elsif Is_Standard_Character_Type (Enumtype) then
2159 Error_Msg_N ("enumeration rep clause not allowed for this type", N);
2160 return;
2161
2162 -- Check that the expression is a proper aggregate (no parentheses)
2163
2164 elsif Paren_Count (Aggr) /= 0 then
2165 Error_Msg
2166 ("extra parentheses surrounding aggregate not allowed",
2167 First_Sloc (Aggr));
2168 return;
2169
2170 -- All tests passed, so set rep clause in place
2171
2172 else
2173 Set_Has_Enumeration_Rep_Clause (Enumtype);
2174 Set_Has_Enumeration_Rep_Clause (Base_Type (Enumtype));
2175 end if;
2176
2177 -- Now we process the aggregate. Note that we don't use the normal
2178 -- aggregate code for this purpose, because we don't want any of the
2179 -- normal expansion activities, and a number of special semantic
2180 -- rules apply (including the component type being any integer type)
2181
2182 Elit := First_Literal (Enumtype);
2183
2184 -- First the positional entries if any
2185
2186 if Present (Expressions (Aggr)) then
2187 Expr := First (Expressions (Aggr));
2188 while Present (Expr) loop
2189 if No (Elit) then
2190 Error_Msg_N ("too many entries in aggregate", Expr);
2191 return;
2192 end if;
2193
2194 Val := Static_Integer (Expr);
2195
2196 -- Err signals that we found some incorrect entries processing
2197 -- the list. The final checks for completeness and ordering are
2198 -- skipped in this case.
2199
2200 if Val = No_Uint then
2201 Err := True;
2202 elsif Val < Lo or else Hi < Val then
2203 Error_Msg_N ("value outside permitted range", Expr);
2204 Err := True;
2205 end if;
2206
2207 Set_Enumeration_Rep (Elit, Val);
2208 Set_Enumeration_Rep_Expr (Elit, Expr);
2209 Next (Expr);
2210 Next (Elit);
2211 end loop;
2212 end if;
2213
2214 -- Now process the named entries if present
2215
2216 if Present (Component_Associations (Aggr)) then
2217 Assoc := First (Component_Associations (Aggr));
2218 while Present (Assoc) loop
2219 Choice := First (Choices (Assoc));
2220
2221 if Present (Next (Choice)) then
2222 Error_Msg_N
2223 ("multiple choice not allowed here", Next (Choice));
2224 Err := True;
2225 end if;
2226
2227 if Nkind (Choice) = N_Others_Choice then
2228 Error_Msg_N ("others choice not allowed here", Choice);
2229 Err := True;
2230
2231 elsif Nkind (Choice) = N_Range then
2232 -- ??? should allow zero/one element range here
2233 Error_Msg_N ("range not allowed here", Choice);
2234 Err := True;
2235
2236 else
2237 Analyze_And_Resolve (Choice, Enumtype);
2238
2239 if Is_Entity_Name (Choice)
2240 and then Is_Type (Entity (Choice))
2241 then
2242 Error_Msg_N ("subtype name not allowed here", Choice);
2243 Err := True;
2244 -- ??? should allow static subtype with zero/one entry
2245
2246 elsif Etype (Choice) = Base_Type (Enumtype) then
2247 if not Is_Static_Expression (Choice) then
2248 Flag_Non_Static_Expr
2249 ("non-static expression used for choice!", Choice);
2250 Err := True;
2251
2252 else
2253 Elit := Expr_Value_E (Choice);
2254
2255 if Present (Enumeration_Rep_Expr (Elit)) then
2256 Error_Msg_Sloc := Sloc (Enumeration_Rep_Expr (Elit));
2257 Error_Msg_NE
2258 ("representation for& previously given#",
2259 Choice, Elit);
2260 Err := True;
2261 end if;
2262
2263 Set_Enumeration_Rep_Expr (Elit, Choice);
2264
2265 Expr := Expression (Assoc);
2266 Val := Static_Integer (Expr);
2267
2268 if Val = No_Uint then
2269 Err := True;
2270
2271 elsif Val < Lo or else Hi < Val then
2272 Error_Msg_N ("value outside permitted range", Expr);
2273 Err := True;
2274 end if;
2275
2276 Set_Enumeration_Rep (Elit, Val);
2277 end if;
2278 end if;
2279 end if;
2280
2281 Next (Assoc);
2282 end loop;
2283 end if;
2284
2285 -- Aggregate is fully processed. Now we check that a full set of
2286 -- representations was given, and that they are in range and in order.
2287 -- These checks are only done if no other errors occurred.
2288
2289 if not Err then
2290 Min := No_Uint;
2291 Max := No_Uint;
2292
2293 Elit := First_Literal (Enumtype);
2294 while Present (Elit) loop
2295 if No (Enumeration_Rep_Expr (Elit)) then
2296 Error_Msg_NE ("missing representation for&!", N, Elit);
2297
2298 else
2299 Val := Enumeration_Rep (Elit);
2300
2301 if Min = No_Uint then
2302 Min := Val;
2303 end if;
2304
2305 if Val /= No_Uint then
2306 if Max /= No_Uint and then Val <= Max then
2307 Error_Msg_NE
2308 ("enumeration value for& not ordered!",
2309 Enumeration_Rep_Expr (Elit), Elit);
2310 end if;
2311
2312 Max := Val;
2313 end if;
2314
2315 -- If there is at least one literal whose representation
2316 -- is not equal to the Pos value, then note that this
2317 -- enumeration type has a non-standard representation.
2318
2319 if Val /= Enumeration_Pos (Elit) then
2320 Set_Has_Non_Standard_Rep (Base_Type (Enumtype));
2321 end if;
2322 end if;
2323
2324 Next (Elit);
2325 end loop;
2326
2327 -- Now set proper size information
2328
2329 declare
2330 Minsize : Uint := UI_From_Int (Minimum_Size (Enumtype));
2331
2332 begin
2333 if Has_Size_Clause (Enumtype) then
2334 if Esize (Enumtype) >= Minsize then
2335 null;
2336
2337 else
2338 Minsize :=
2339 UI_From_Int (Minimum_Size (Enumtype, Biased => True));
2340
2341 if Esize (Enumtype) < Minsize then
2342 Error_Msg_N ("previously given size is too small", N);
2343
2344 else
2345 Set_Has_Biased_Representation (Enumtype);
2346 end if;
2347 end if;
2348
2349 else
2350 Set_RM_Size (Enumtype, Minsize);
2351 Set_Enum_Esize (Enumtype);
2352 end if;
2353
2354 Set_RM_Size (Base_Type (Enumtype), RM_Size (Enumtype));
2355 Set_Esize (Base_Type (Enumtype), Esize (Enumtype));
2356 Set_Alignment (Base_Type (Enumtype), Alignment (Enumtype));
2357 end;
2358 end if;
2359
2360 -- We repeat the too late test in case it froze itself!
2361
2362 if Rep_Item_Too_Late (Enumtype, N) then
2363 null;
2364 end if;
2365 end Analyze_Enumeration_Representation_Clause;
2366
2367 ----------------------------
2368 -- Analyze_Free_Statement --
2369 ----------------------------
2370
2371 procedure Analyze_Free_Statement (N : Node_Id) is
2372 begin
2373 Analyze (Expression (N));
2374 end Analyze_Free_Statement;
2375
2376 ---------------------------
2377 -- Analyze_Freeze_Entity --
2378 ---------------------------
2379
2380 procedure Analyze_Freeze_Entity (N : Node_Id) is
2381 E : constant Entity_Id := Entity (N);
2382
2383 begin
2384 -- For tagged types covering interfaces add internal entities that link
2385 -- the primitives of the interfaces with the primitives that cover them.
2386
2387 -- Note: These entities were originally generated only when generating
2388 -- code because their main purpose was to provide support to initialize
2389 -- the secondary dispatch tables. They are now generated also when
2390 -- compiling with no code generation to provide ASIS the relationship
2391 -- between interface primitives and tagged type primitives. They are
2392 -- also used to locate primitives covering interfaces when processing
2393 -- generics (see Derive_Subprograms).
2394
2395 if Ada_Version >= Ada_05
2396 and then Ekind (E) = E_Record_Type
2397 and then Is_Tagged_Type (E)
2398 and then not Is_Interface (E)
2399 and then Has_Interfaces (E)
2400 then
2401 -- This would be a good common place to call the routine that checks
2402 -- overriding of interface primitives (and thus factorize calls to
2403 -- Check_Abstract_Overriding located at different contexts in the
2404 -- compiler). However, this is not possible because it causes
2405 -- spurious errors in case of late overriding.
2406
2407 Add_Internal_Interface_Entities (E);
2408 end if;
2409
2410 -- Check CPP types
2411
2412 if Ekind (E) = E_Record_Type
2413 and then Is_CPP_Class (E)
2414 and then Is_Tagged_Type (E)
2415 and then Tagged_Type_Expansion
2416 and then Expander_Active
2417 then
2418 if CPP_Num_Prims (E) = 0 then
2419
2420 -- If the CPP type has user defined components then it must import
2421 -- primitives from C++. This is required because if the C++ class
2422 -- has no primitives then the C++ compiler does not added the _tag
2423 -- component to the type.
2424
2425 pragma Assert (Chars (First_Entity (E)) = Name_uTag);
2426
2427 if First_Entity (E) /= Last_Entity (E) then
2428 Error_Msg_N
2429 ("?'C'P'P type must import at least one primitive from C++",
2430 E);
2431 end if;
2432 end if;
2433
2434 -- Check that all its primitives are abstract or imported from C++.
2435 -- Check also availability of the C++ constructor.
2436
2437 declare
2438 Has_Constructors : constant Boolean := Has_CPP_Constructors (E);
2439 Elmt : Elmt_Id;
2440 Error_Reported : Boolean := False;
2441 Prim : Node_Id;
2442
2443 begin
2444 Elmt := First_Elmt (Primitive_Operations (E));
2445 while Present (Elmt) loop
2446 Prim := Node (Elmt);
2447
2448 if Comes_From_Source (Prim) then
2449 if Is_Abstract_Subprogram (Prim) then
2450 null;
2451
2452 elsif not Is_Imported (Prim)
2453 or else Convention (Prim) /= Convention_CPP
2454 then
2455 Error_Msg_N
2456 ("?primitives of 'C'P'P types must be imported from C++"
2457 & " or abstract", Prim);
2458
2459 elsif not Has_Constructors
2460 and then not Error_Reported
2461 then
2462 Error_Msg_Name_1 := Chars (E);
2463 Error_Msg_N
2464 ("?'C'P'P constructor required for type %", Prim);
2465 Error_Reported := True;
2466 end if;
2467 end if;
2468
2469 Next_Elmt (Elmt);
2470 end loop;
2471 end;
2472 end if;
2473 end Analyze_Freeze_Entity;
2474
2475 ------------------------------------------
2476 -- Analyze_Record_Representation_Clause --
2477 ------------------------------------------
2478
2479 -- Note: we check as much as we can here, but we can't do any checks
2480 -- based on the position values (e.g. overlap checks) until freeze time
2481 -- because especially in Ada 2005 (machine scalar mode), the processing
2482 -- for non-standard bit order can substantially change the positions.
2483 -- See procedure Check_Record_Representation_Clause (called from Freeze)
2484 -- for the remainder of this processing.
2485
2486 procedure Analyze_Record_Representation_Clause (N : Node_Id) is
2487 Ident : constant Node_Id := Identifier (N);
2488 Rectype : Entity_Id;
2489 CC : Node_Id;
2490 Posit : Uint;
2491 Fbit : Uint;
2492 Lbit : Uint;
2493 Hbit : Uint := Uint_0;
2494 Comp : Entity_Id;
2495 Ocomp : Entity_Id;
2496 Biased : Boolean;
2497
2498 CR_Pragma : Node_Id := Empty;
2499 -- Points to N_Pragma node if Complete_Representation pragma present
2500
2501 begin
2502 if Ignore_Rep_Clauses then
2503 return;
2504 end if;
2505
2506 Find_Type (Ident);
2507 Rectype := Entity (Ident);
2508
2509 if Rectype = Any_Type
2510 or else Rep_Item_Too_Early (Rectype, N)
2511 then
2512 return;
2513 else
2514 Rectype := Underlying_Type (Rectype);
2515 end if;
2516
2517 -- First some basic error checks
2518
2519 if not Is_Record_Type (Rectype) then
2520 Error_Msg_NE
2521 ("record type required, found}", Ident, First_Subtype (Rectype));
2522 return;
2523
2524 elsif Is_Unchecked_Union (Rectype) then
2525 Error_Msg_N
2526 ("record rep clause not allowed for Unchecked_Union", N);
2527
2528 elsif Scope (Rectype) /= Current_Scope then
2529 Error_Msg_N ("type must be declared in this scope", N);
2530 return;
2531
2532 elsif not Is_First_Subtype (Rectype) then
2533 Error_Msg_N ("cannot give record rep clause for subtype", N);
2534 return;
2535
2536 elsif Has_Record_Rep_Clause (Rectype) then
2537 Error_Msg_N ("duplicate record rep clause ignored", N);
2538 return;
2539
2540 elsif Rep_Item_Too_Late (Rectype, N) then
2541 return;
2542 end if;
2543
2544 if Present (Mod_Clause (N)) then
2545 declare
2546 Loc : constant Source_Ptr := Sloc (N);
2547 M : constant Node_Id := Mod_Clause (N);
2548 P : constant List_Id := Pragmas_Before (M);
2549 AtM_Nod : Node_Id;
2550
2551 Mod_Val : Uint;
2552 pragma Warnings (Off, Mod_Val);
2553
2554 begin
2555 Check_Restriction (No_Obsolescent_Features, Mod_Clause (N));
2556
2557 if Warn_On_Obsolescent_Feature then
2558 Error_Msg_N
2559 ("mod clause is an obsolescent feature (RM J.8)?", N);
2560 Error_Msg_N
2561 ("\use alignment attribute definition clause instead?", N);
2562 end if;
2563
2564 if Present (P) then
2565 Analyze_List (P);
2566 end if;
2567
2568 -- In ASIS_Mode mode, expansion is disabled, but we must convert
2569 -- the Mod clause into an alignment clause anyway, so that the
2570 -- back-end can compute and back-annotate properly the size and
2571 -- alignment of types that may include this record.
2572
2573 -- This seems dubious, this destroys the source tree in a manner
2574 -- not detectable by ASIS ???
2575
2576 if Operating_Mode = Check_Semantics
2577 and then ASIS_Mode
2578 then
2579 AtM_Nod :=
2580 Make_Attribute_Definition_Clause (Loc,
2581 Name => New_Reference_To (Base_Type (Rectype), Loc),
2582 Chars => Name_Alignment,
2583 Expression => Relocate_Node (Expression (M)));
2584
2585 Set_From_At_Mod (AtM_Nod);
2586 Insert_After (N, AtM_Nod);
2587 Mod_Val := Get_Alignment_Value (Expression (AtM_Nod));
2588 Set_Mod_Clause (N, Empty);
2589
2590 else
2591 -- Get the alignment value to perform error checking
2592
2593 Mod_Val := Get_Alignment_Value (Expression (M));
2594 end if;
2595 end;
2596 end if;
2597
2598 -- For untagged types, clear any existing component clauses for the
2599 -- type. If the type is derived, this is what allows us to override
2600 -- a rep clause for the parent. For type extensions, the representation
2601 -- of the inherited components is inherited, so we want to keep previous
2602 -- component clauses for completeness.
2603
2604 if not Is_Tagged_Type (Rectype) then
2605 Comp := First_Component_Or_Discriminant (Rectype);
2606 while Present (Comp) loop
2607 Set_Component_Clause (Comp, Empty);
2608 Next_Component_Or_Discriminant (Comp);
2609 end loop;
2610 end if;
2611
2612 -- All done if no component clauses
2613
2614 CC := First (Component_Clauses (N));
2615
2616 if No (CC) then
2617 return;
2618 end if;
2619
2620 -- A representation like this applies to the base type
2621
2622 Set_Has_Record_Rep_Clause (Base_Type (Rectype));
2623 Set_Has_Non_Standard_Rep (Base_Type (Rectype));
2624 Set_Has_Specified_Layout (Base_Type (Rectype));
2625
2626 -- Process the component clauses
2627
2628 while Present (CC) loop
2629
2630 -- Pragma
2631
2632 if Nkind (CC) = N_Pragma then
2633 Analyze (CC);
2634
2635 -- The only pragma of interest is Complete_Representation
2636
2637 if Pragma_Name (CC) = Name_Complete_Representation then
2638 CR_Pragma := CC;
2639 end if;
2640
2641 -- Processing for real component clause
2642
2643 else
2644 Posit := Static_Integer (Position (CC));
2645 Fbit := Static_Integer (First_Bit (CC));
2646 Lbit := Static_Integer (Last_Bit (CC));
2647
2648 if Posit /= No_Uint
2649 and then Fbit /= No_Uint
2650 and then Lbit /= No_Uint
2651 then
2652 if Posit < 0 then
2653 Error_Msg_N
2654 ("position cannot be negative", Position (CC));
2655
2656 elsif Fbit < 0 then
2657 Error_Msg_N
2658 ("first bit cannot be negative", First_Bit (CC));
2659
2660 -- The Last_Bit specified in a component clause must not be
2661 -- less than the First_Bit minus one (RM-13.5.1(10)).
2662
2663 elsif Lbit < Fbit - 1 then
2664 Error_Msg_N
2665 ("last bit cannot be less than first bit minus one",
2666 Last_Bit (CC));
2667
2668 -- Values look OK, so find the corresponding record component
2669 -- Even though the syntax allows an attribute reference for
2670 -- implementation-defined components, GNAT does not allow the
2671 -- tag to get an explicit position.
2672
2673 elsif Nkind (Component_Name (CC)) = N_Attribute_Reference then
2674 if Attribute_Name (Component_Name (CC)) = Name_Tag then
2675 Error_Msg_N ("position of tag cannot be specified", CC);
2676 else
2677 Error_Msg_N ("illegal component name", CC);
2678 end if;
2679
2680 else
2681 Comp := First_Entity (Rectype);
2682 while Present (Comp) loop
2683 exit when Chars (Comp) = Chars (Component_Name (CC));
2684 Next_Entity (Comp);
2685 end loop;
2686
2687 if No (Comp) then
2688
2689 -- Maybe component of base type that is absent from
2690 -- statically constrained first subtype.
2691
2692 Comp := First_Entity (Base_Type (Rectype));
2693 while Present (Comp) loop
2694 exit when Chars (Comp) = Chars (Component_Name (CC));
2695 Next_Entity (Comp);
2696 end loop;
2697 end if;
2698
2699 if No (Comp) then
2700 Error_Msg_N
2701 ("component clause is for non-existent field", CC);
2702
2703 elsif Present (Component_Clause (Comp)) then
2704
2705 -- Diagnose duplicate rep clause, or check consistency
2706 -- if this is an inherited component. In a double fault,
2707 -- there may be a duplicate inconsistent clause for an
2708 -- inherited component.
2709
2710 if Scope (Original_Record_Component (Comp)) = Rectype
2711 or else Parent (Component_Clause (Comp)) = N
2712 then
2713 Error_Msg_Sloc := Sloc (Component_Clause (Comp));
2714 Error_Msg_N ("component clause previously given#", CC);
2715
2716 else
2717 declare
2718 Rep1 : constant Node_Id := Component_Clause (Comp);
2719 begin
2720 if Intval (Position (Rep1)) /=
2721 Intval (Position (CC))
2722 or else Intval (First_Bit (Rep1)) /=
2723 Intval (First_Bit (CC))
2724 or else Intval (Last_Bit (Rep1)) /=
2725 Intval (Last_Bit (CC))
2726 then
2727 Error_Msg_N ("component clause inconsistent "
2728 & "with representation of ancestor", CC);
2729 elsif Warn_On_Redundant_Constructs then
2730 Error_Msg_N ("?redundant component clause "
2731 & "for inherited component!", CC);
2732 end if;
2733 end;
2734 end if;
2735
2736 -- Normal case where this is the first component clause we
2737 -- have seen for this entity, so set it up properly.
2738
2739 else
2740 -- Make reference for field in record rep clause and set
2741 -- appropriate entity field in the field identifier.
2742
2743 Generate_Reference
2744 (Comp, Component_Name (CC), Set_Ref => False);
2745 Set_Entity (Component_Name (CC), Comp);
2746
2747 -- Update Fbit and Lbit to the actual bit number
2748
2749 Fbit := Fbit + UI_From_Int (SSU) * Posit;
2750 Lbit := Lbit + UI_From_Int (SSU) * Posit;
2751
2752 if Has_Size_Clause (Rectype)
2753 and then Esize (Rectype) <= Lbit
2754 then
2755 Error_Msg_N
2756 ("bit number out of range of specified size",
2757 Last_Bit (CC));
2758 else
2759 Set_Component_Clause (Comp, CC);
2760 Set_Component_Bit_Offset (Comp, Fbit);
2761 Set_Esize (Comp, 1 + (Lbit - Fbit));
2762 Set_Normalized_First_Bit (Comp, Fbit mod SSU);
2763 Set_Normalized_Position (Comp, Fbit / SSU);
2764
2765 if Warn_On_Overridden_Size
2766 and then Has_Size_Clause (Etype (Comp))
2767 and then RM_Size (Etype (Comp)) /= Esize (Comp)
2768 then
2769 Error_Msg_NE
2770 ("?component size overrides size clause for&",
2771 Component_Name (CC), Etype (Comp));
2772 end if;
2773
2774 -- This information is also set in the corresponding
2775 -- component of the base type, found by accessing the
2776 -- Original_Record_Component link if it is present.
2777
2778 Ocomp := Original_Record_Component (Comp);
2779
2780 if Hbit < Lbit then
2781 Hbit := Lbit;
2782 end if;
2783
2784 Check_Size
2785 (Component_Name (CC),
2786 Etype (Comp),
2787 Esize (Comp),
2788 Biased);
2789
2790 Set_Has_Biased_Representation (Comp, Biased);
2791
2792 if Biased and Warn_On_Biased_Representation then
2793 Error_Msg_F
2794 ("?component clause forces biased "
2795 & "representation", CC);
2796 end if;
2797
2798 if Present (Ocomp) then
2799 Set_Component_Clause (Ocomp, CC);
2800 Set_Component_Bit_Offset (Ocomp, Fbit);
2801 Set_Normalized_First_Bit (Ocomp, Fbit mod SSU);
2802 Set_Normalized_Position (Ocomp, Fbit / SSU);
2803 Set_Esize (Ocomp, 1 + (Lbit - Fbit));
2804
2805 Set_Normalized_Position_Max
2806 (Ocomp, Normalized_Position (Ocomp));
2807
2808 Set_Has_Biased_Representation
2809 (Ocomp, Has_Biased_Representation (Comp));
2810 end if;
2811
2812 if Esize (Comp) < 0 then
2813 Error_Msg_N ("component size is negative", CC);
2814 end if;
2815 end if;
2816 end if;
2817 end if;
2818 end if;
2819 end if;
2820
2821 Next (CC);
2822 end loop;
2823
2824 -- Check missing components if Complete_Representation pragma appeared
2825
2826 if Present (CR_Pragma) then
2827 Comp := First_Component_Or_Discriminant (Rectype);
2828 while Present (Comp) loop
2829 if No (Component_Clause (Comp)) then
2830 Error_Msg_NE
2831 ("missing component clause for &", CR_Pragma, Comp);
2832 end if;
2833
2834 Next_Component_Or_Discriminant (Comp);
2835 end loop;
2836
2837 -- If no Complete_Representation pragma, warn if missing components
2838
2839 elsif Warn_On_Unrepped_Components then
2840 declare
2841 Num_Repped_Components : Nat := 0;
2842 Num_Unrepped_Components : Nat := 0;
2843
2844 begin
2845 -- First count number of repped and unrepped components
2846
2847 Comp := First_Component_Or_Discriminant (Rectype);
2848 while Present (Comp) loop
2849 if Present (Component_Clause (Comp)) then
2850 Num_Repped_Components := Num_Repped_Components + 1;
2851 else
2852 Num_Unrepped_Components := Num_Unrepped_Components + 1;
2853 end if;
2854
2855 Next_Component_Or_Discriminant (Comp);
2856 end loop;
2857
2858 -- We are only interested in the case where there is at least one
2859 -- unrepped component, and at least half the components have rep
2860 -- clauses. We figure that if less than half have them, then the
2861 -- partial rep clause is really intentional. If the component
2862 -- type has no underlying type set at this point (as for a generic
2863 -- formal type), we don't know enough to give a warning on the
2864 -- component.
2865
2866 if Num_Unrepped_Components > 0
2867 and then Num_Unrepped_Components < Num_Repped_Components
2868 then
2869 Comp := First_Component_Or_Discriminant (Rectype);
2870 while Present (Comp) loop
2871 if No (Component_Clause (Comp))
2872 and then Comes_From_Source (Comp)
2873 and then Present (Underlying_Type (Etype (Comp)))
2874 and then (Is_Scalar_Type (Underlying_Type (Etype (Comp)))
2875 or else Size_Known_At_Compile_Time
2876 (Underlying_Type (Etype (Comp))))
2877 and then not Has_Warnings_Off (Rectype)
2878 then
2879 Error_Msg_Sloc := Sloc (Comp);
2880 Error_Msg_NE
2881 ("?no component clause given for & declared #",
2882 N, Comp);
2883 end if;
2884
2885 Next_Component_Or_Discriminant (Comp);
2886 end loop;
2887 end if;
2888 end;
2889 end if;
2890 end Analyze_Record_Representation_Clause;
2891
2892 -----------------------------------
2893 -- Check_Constant_Address_Clause --
2894 -----------------------------------
2895
2896 procedure Check_Constant_Address_Clause
2897 (Expr : Node_Id;
2898 U_Ent : Entity_Id)
2899 is
2900 procedure Check_At_Constant_Address (Nod : Node_Id);
2901 -- Checks that the given node N represents a name whose 'Address is
2902 -- constant (in the same sense as OK_Constant_Address_Clause, i.e. the
2903 -- address value is the same at the point of declaration of U_Ent and at
2904 -- the time of elaboration of the address clause.
2905
2906 procedure Check_Expr_Constants (Nod : Node_Id);
2907 -- Checks that Nod meets the requirements for a constant address clause
2908 -- in the sense of the enclosing procedure.
2909
2910 procedure Check_List_Constants (Lst : List_Id);
2911 -- Check that all elements of list Lst meet the requirements for a
2912 -- constant address clause in the sense of the enclosing procedure.
2913
2914 -------------------------------
2915 -- Check_At_Constant_Address --
2916 -------------------------------
2917
2918 procedure Check_At_Constant_Address (Nod : Node_Id) is
2919 begin
2920 if Is_Entity_Name (Nod) then
2921 if Present (Address_Clause (Entity ((Nod)))) then
2922 Error_Msg_NE
2923 ("invalid address clause for initialized object &!",
2924 Nod, U_Ent);
2925 Error_Msg_NE
2926 ("address for& cannot" &
2927 " depend on another address clause! (RM 13.1(22))!",
2928 Nod, U_Ent);
2929
2930 elsif In_Same_Source_Unit (Entity (Nod), U_Ent)
2931 and then Sloc (U_Ent) < Sloc (Entity (Nod))
2932 then
2933 Error_Msg_NE
2934 ("invalid address clause for initialized object &!",
2935 Nod, U_Ent);
2936 Error_Msg_Node_2 := U_Ent;
2937 Error_Msg_NE
2938 ("\& must be defined before & (RM 13.1(22))!",
2939 Nod, Entity (Nod));
2940 end if;
2941
2942 elsif Nkind (Nod) = N_Selected_Component then
2943 declare
2944 T : constant Entity_Id := Etype (Prefix (Nod));
2945
2946 begin
2947 if (Is_Record_Type (T)
2948 and then Has_Discriminants (T))
2949 or else
2950 (Is_Access_Type (T)
2951 and then Is_Record_Type (Designated_Type (T))
2952 and then Has_Discriminants (Designated_Type (T)))
2953 then
2954 Error_Msg_NE
2955 ("invalid address clause for initialized object &!",
2956 Nod, U_Ent);
2957 Error_Msg_N
2958 ("\address cannot depend on component" &
2959 " of discriminated record (RM 13.1(22))!",
2960 Nod);
2961 else
2962 Check_At_Constant_Address (Prefix (Nod));
2963 end if;
2964 end;
2965
2966 elsif Nkind (Nod) = N_Indexed_Component then
2967 Check_At_Constant_Address (Prefix (Nod));
2968 Check_List_Constants (Expressions (Nod));
2969
2970 else
2971 Check_Expr_Constants (Nod);
2972 end if;
2973 end Check_At_Constant_Address;
2974
2975 --------------------------
2976 -- Check_Expr_Constants --
2977 --------------------------
2978
2979 procedure Check_Expr_Constants (Nod : Node_Id) is
2980 Loc_U_Ent : constant Source_Ptr := Sloc (U_Ent);
2981 Ent : Entity_Id := Empty;
2982
2983 begin
2984 if Nkind (Nod) in N_Has_Etype
2985 and then Etype (Nod) = Any_Type
2986 then
2987 return;
2988 end if;
2989
2990 case Nkind (Nod) is
2991 when N_Empty | N_Error =>
2992 return;
2993
2994 when N_Identifier | N_Expanded_Name =>
2995 Ent := Entity (Nod);
2996
2997 -- We need to look at the original node if it is different
2998 -- from the node, since we may have rewritten things and
2999 -- substituted an identifier representing the rewrite.
3000
3001 if Original_Node (Nod) /= Nod then
3002 Check_Expr_Constants (Original_Node (Nod));
3003
3004 -- If the node is an object declaration without initial
3005 -- value, some code has been expanded, and the expression
3006 -- is not constant, even if the constituents might be
3007 -- acceptable, as in A'Address + offset.
3008
3009 if Ekind (Ent) = E_Variable
3010 and then
3011 Nkind (Declaration_Node (Ent)) = N_Object_Declaration
3012 and then
3013 No (Expression (Declaration_Node (Ent)))
3014 then
3015 Error_Msg_NE
3016 ("invalid address clause for initialized object &!",
3017 Nod, U_Ent);
3018
3019 -- If entity is constant, it may be the result of expanding
3020 -- a check. We must verify that its declaration appears
3021 -- before the object in question, else we also reject the
3022 -- address clause.
3023
3024 elsif Ekind (Ent) = E_Constant
3025 and then In_Same_Source_Unit (Ent, U_Ent)
3026 and then Sloc (Ent) > Loc_U_Ent
3027 then
3028 Error_Msg_NE
3029 ("invalid address clause for initialized object &!",
3030 Nod, U_Ent);
3031 end if;
3032
3033 return;
3034 end if;
3035
3036 -- Otherwise look at the identifier and see if it is OK
3037
3038 if Ekind_In (Ent, E_Named_Integer, E_Named_Real)
3039 or else Is_Type (Ent)
3040 then
3041 return;
3042
3043 elsif
3044 Ekind (Ent) = E_Constant
3045 or else
3046 Ekind (Ent) = E_In_Parameter
3047 then
3048 -- This is the case where we must have Ent defined before
3049 -- U_Ent. Clearly if they are in different units this
3050 -- requirement is met since the unit containing Ent is
3051 -- already processed.
3052
3053 if not In_Same_Source_Unit (Ent, U_Ent) then
3054 return;
3055
3056 -- Otherwise location of Ent must be before the location
3057 -- of U_Ent, that's what prior defined means.
3058
3059 elsif Sloc (Ent) < Loc_U_Ent then
3060 return;
3061
3062 else
3063 Error_Msg_NE
3064 ("invalid address clause for initialized object &!",
3065 Nod, U_Ent);
3066 Error_Msg_Node_2 := U_Ent;
3067 Error_Msg_NE
3068 ("\& must be defined before & (RM 13.1(22))!",
3069 Nod, Ent);
3070 end if;
3071
3072 elsif Nkind (Original_Node (Nod)) = N_Function_Call then
3073 Check_Expr_Constants (Original_Node (Nod));
3074
3075 else
3076 Error_Msg_NE
3077 ("invalid address clause for initialized object &!",
3078 Nod, U_Ent);
3079
3080 if Comes_From_Source (Ent) then
3081 Error_Msg_NE
3082 ("\reference to variable& not allowed"
3083 & " (RM 13.1(22))!", Nod, Ent);
3084 else
3085 Error_Msg_N
3086 ("non-static expression not allowed"
3087 & " (RM 13.1(22))!", Nod);
3088 end if;
3089 end if;
3090
3091 when N_Integer_Literal =>
3092
3093 -- If this is a rewritten unchecked conversion, in a system
3094 -- where Address is an integer type, always use the base type
3095 -- for a literal value. This is user-friendly and prevents
3096 -- order-of-elaboration issues with instances of unchecked
3097 -- conversion.
3098
3099 if Nkind (Original_Node (Nod)) = N_Function_Call then
3100 Set_Etype (Nod, Base_Type (Etype (Nod)));
3101 end if;
3102
3103 when N_Real_Literal |
3104 N_String_Literal |
3105 N_Character_Literal =>
3106 return;
3107
3108 when N_Range =>
3109 Check_Expr_Constants (Low_Bound (Nod));
3110 Check_Expr_Constants (High_Bound (Nod));
3111
3112 when N_Explicit_Dereference =>
3113 Check_Expr_Constants (Prefix (Nod));
3114
3115 when N_Indexed_Component =>
3116 Check_Expr_Constants (Prefix (Nod));
3117 Check_List_Constants (Expressions (Nod));
3118
3119 when N_Slice =>
3120 Check_Expr_Constants (Prefix (Nod));
3121 Check_Expr_Constants (Discrete_Range (Nod));
3122
3123 when N_Selected_Component =>
3124 Check_Expr_Constants (Prefix (Nod));
3125
3126 when N_Attribute_Reference =>
3127 if Attribute_Name (Nod) = Name_Address
3128 or else
3129 Attribute_Name (Nod) = Name_Access
3130 or else
3131 Attribute_Name (Nod) = Name_Unchecked_Access
3132 or else
3133 Attribute_Name (Nod) = Name_Unrestricted_Access
3134 then
3135 Check_At_Constant_Address (Prefix (Nod));
3136
3137 else
3138 Check_Expr_Constants (Prefix (Nod));
3139 Check_List_Constants (Expressions (Nod));
3140 end if;
3141
3142 when N_Aggregate =>
3143 Check_List_Constants (Component_Associations (Nod));
3144 Check_List_Constants (Expressions (Nod));
3145
3146 when N_Component_Association =>
3147 Check_Expr_Constants (Expression (Nod));
3148
3149 when N_Extension_Aggregate =>
3150 Check_Expr_Constants (Ancestor_Part (Nod));
3151 Check_List_Constants (Component_Associations (Nod));
3152 Check_List_Constants (Expressions (Nod));
3153
3154 when N_Null =>
3155 return;
3156
3157 when N_Binary_Op | N_Short_Circuit | N_Membership_Test =>
3158 Check_Expr_Constants (Left_Opnd (Nod));
3159 Check_Expr_Constants (Right_Opnd (Nod));
3160
3161 when N_Unary_Op =>
3162 Check_Expr_Constants (Right_Opnd (Nod));
3163
3164 when N_Type_Conversion |
3165 N_Qualified_Expression |
3166 N_Allocator =>
3167 Check_Expr_Constants (Expression (Nod));
3168
3169 when N_Unchecked_Type_Conversion =>
3170 Check_Expr_Constants (Expression (Nod));
3171
3172 -- If this is a rewritten unchecked conversion, subtypes in
3173 -- this node are those created within the instance. To avoid
3174 -- order of elaboration issues, replace them with their base
3175 -- types. Note that address clauses can cause order of
3176 -- elaboration problems because they are elaborated by the
3177 -- back-end at the point of definition, and may mention
3178 -- entities declared in between (as long as everything is
3179 -- static). It is user-friendly to allow unchecked conversions
3180 -- in this context.
3181
3182 if Nkind (Original_Node (Nod)) = N_Function_Call then
3183 Set_Etype (Expression (Nod),
3184 Base_Type (Etype (Expression (Nod))));
3185 Set_Etype (Nod, Base_Type (Etype (Nod)));
3186 end if;
3187
3188 when N_Function_Call =>
3189 if not Is_Pure (Entity (Name (Nod))) then
3190 Error_Msg_NE
3191 ("invalid address clause for initialized object &!",
3192 Nod, U_Ent);
3193
3194 Error_Msg_NE
3195 ("\function & is not pure (RM 13.1(22))!",
3196 Nod, Entity (Name (Nod)));
3197
3198 else
3199 Check_List_Constants (Parameter_Associations (Nod));
3200 end if;
3201
3202 when N_Parameter_Association =>
3203 Check_Expr_Constants (Explicit_Actual_Parameter (Nod));
3204
3205 when others =>
3206 Error_Msg_NE
3207 ("invalid address clause for initialized object &!",
3208 Nod, U_Ent);
3209 Error_Msg_NE
3210 ("\must be constant defined before& (RM 13.1(22))!",
3211 Nod, U_Ent);
3212 end case;
3213 end Check_Expr_Constants;
3214
3215 --------------------------
3216 -- Check_List_Constants --
3217 --------------------------
3218
3219 procedure Check_List_Constants (Lst : List_Id) is
3220 Nod1 : Node_Id;
3221
3222 begin
3223 if Present (Lst) then
3224 Nod1 := First (Lst);
3225 while Present (Nod1) loop
3226 Check_Expr_Constants (Nod1);
3227 Next (Nod1);
3228 end loop;
3229 end if;
3230 end Check_List_Constants;
3231
3232 -- Start of processing for Check_Constant_Address_Clause
3233
3234 begin
3235 -- If rep_clauses are to be ignored, no need for legality checks. In
3236 -- particular, no need to pester user about rep clauses that violate
3237 -- the rule on constant addresses, given that these clauses will be
3238 -- removed by Freeze before they reach the back end.
3239
3240 if not Ignore_Rep_Clauses then
3241 Check_Expr_Constants (Expr);
3242 end if;
3243 end Check_Constant_Address_Clause;
3244
3245 ----------------------------------------
3246 -- Check_Record_Representation_Clause --
3247 ----------------------------------------
3248
3249 procedure Check_Record_Representation_Clause (N : Node_Id) is
3250 Loc : constant Source_Ptr := Sloc (N);
3251 Ident : constant Node_Id := Identifier (N);
3252 Rectype : Entity_Id;
3253 Fent : Entity_Id;
3254 CC : Node_Id;
3255 Fbit : Uint;
3256 Lbit : Uint;
3257 Hbit : Uint := Uint_0;
3258 Comp : Entity_Id;
3259 Pcomp : Entity_Id;
3260
3261 Max_Bit_So_Far : Uint;
3262 -- Records the maximum bit position so far. If all field positions
3263 -- are monotonically increasing, then we can skip the circuit for
3264 -- checking for overlap, since no overlap is possible.
3265
3266 Tagged_Parent : Entity_Id := Empty;
3267 -- This is set in the case of a derived tagged type for which we have
3268 -- Is_Fully_Repped_Tagged_Type True (indicating that all components are
3269 -- positioned by record representation clauses). In this case we must
3270 -- check for overlap between components of this tagged type, and the
3271 -- components of its parent. Tagged_Parent will point to this parent
3272 -- type. For all other cases Tagged_Parent is left set to Empty.
3273
3274 Parent_Last_Bit : Uint;
3275 -- Relevant only if Tagged_Parent is set, Parent_Last_Bit indicates the
3276 -- last bit position for any field in the parent type. We only need to
3277 -- check overlap for fields starting below this point.
3278
3279 Overlap_Check_Required : Boolean;
3280 -- Used to keep track of whether or not an overlap check is required
3281
3282 Overlap_Detected : Boolean := False;
3283 -- Set True if an overlap is detected
3284
3285 Ccount : Natural := 0;
3286 -- Number of component clauses in record rep clause
3287
3288 procedure Check_Component_Overlap (C1_Ent, C2_Ent : Entity_Id);
3289 -- Given two entities for record components or discriminants, checks
3290 -- if they have overlapping component clauses and issues errors if so.
3291
3292 procedure Find_Component;
3293 -- Finds component entity corresponding to current component clause (in
3294 -- CC), and sets Comp to the entity, and Fbit/Lbit to the zero origin
3295 -- start/stop bits for the field. If there is no matching component or
3296 -- if the matching component does not have a component clause, then
3297 -- that's an error and Comp is set to Empty, but no error message is
3298 -- issued, since the message was already given. Comp is also set to
3299 -- Empty if the current "component clause" is in fact a pragma.
3300
3301 -----------------------------
3302 -- Check_Component_Overlap --
3303 -----------------------------
3304
3305 procedure Check_Component_Overlap (C1_Ent, C2_Ent : Entity_Id) is
3306 CC1 : constant Node_Id := Component_Clause (C1_Ent);
3307 CC2 : constant Node_Id := Component_Clause (C2_Ent);
3308
3309 begin
3310 if Present (CC1) and then Present (CC2) then
3311
3312 -- Exclude odd case where we have two tag fields in the same
3313 -- record, both at location zero. This seems a bit strange, but
3314 -- it seems to happen in some circumstances, perhaps on an error.
3315
3316 if Chars (C1_Ent) = Name_uTag
3317 and then
3318 Chars (C2_Ent) = Name_uTag
3319 then
3320 return;
3321 end if;
3322
3323 -- Here we check if the two fields overlap
3324
3325 declare
3326 S1 : constant Uint := Component_Bit_Offset (C1_Ent);
3327 S2 : constant Uint := Component_Bit_Offset (C2_Ent);
3328 E1 : constant Uint := S1 + Esize (C1_Ent);
3329 E2 : constant Uint := S2 + Esize (C2_Ent);
3330
3331 begin
3332 if E2 <= S1 or else E1 <= S2 then
3333 null;
3334 else
3335 Error_Msg_Node_2 := Component_Name (CC2);
3336 Error_Msg_Sloc := Sloc (Error_Msg_Node_2);
3337 Error_Msg_Node_1 := Component_Name (CC1);
3338 Error_Msg_N
3339 ("component& overlaps & #", Component_Name (CC1));
3340 Overlap_Detected := True;
3341 end if;
3342 end;
3343 end if;
3344 end Check_Component_Overlap;
3345
3346 --------------------
3347 -- Find_Component --
3348 --------------------
3349
3350 procedure Find_Component is
3351
3352 procedure Search_Component (R : Entity_Id);
3353 -- Search components of R for a match. If found, Comp is set.
3354
3355 ----------------------
3356 -- Search_Component --
3357 ----------------------
3358
3359 procedure Search_Component (R : Entity_Id) is
3360 begin
3361 Comp := First_Component_Or_Discriminant (R);
3362 while Present (Comp) loop
3363
3364 -- Ignore error of attribute name for component name (we
3365 -- already gave an error message for this, so no need to
3366 -- complain here)
3367
3368 if Nkind (Component_Name (CC)) = N_Attribute_Reference then
3369 null;
3370 else
3371 exit when Chars (Comp) = Chars (Component_Name (CC));
3372 end if;
3373
3374 Next_Component_Or_Discriminant (Comp);
3375 end loop;
3376 end Search_Component;
3377
3378 -- Start of processing for Find_Component
3379
3380 begin
3381 -- Return with Comp set to Empty if we have a pragma
3382
3383 if Nkind (CC) = N_Pragma then
3384 Comp := Empty;
3385 return;
3386 end if;
3387
3388 -- Search current record for matching component
3389
3390 Search_Component (Rectype);
3391
3392 -- If not found, maybe component of base type that is absent from
3393 -- statically constrained first subtype.
3394
3395 if No (Comp) then
3396 Search_Component (Base_Type (Rectype));
3397 end if;
3398
3399 -- If no component, or the component does not reference the component
3400 -- clause in question, then there was some previous error for which
3401 -- we already gave a message, so just return with Comp Empty.
3402
3403 if No (Comp)
3404 or else Component_Clause (Comp) /= CC
3405 then
3406 Comp := Empty;
3407
3408 -- Normal case where we have a component clause
3409
3410 else
3411 Fbit := Component_Bit_Offset (Comp);
3412 Lbit := Fbit + Esize (Comp) - 1;
3413 end if;
3414 end Find_Component;
3415
3416 -- Start of processing for Check_Record_Representation_Clause
3417
3418 begin
3419 Find_Type (Ident);
3420 Rectype := Entity (Ident);
3421
3422 if Rectype = Any_Type then
3423 return;
3424 else
3425 Rectype := Underlying_Type (Rectype);
3426 end if;
3427
3428 -- See if we have a fully repped derived tagged type
3429
3430 declare
3431 PS : constant Entity_Id := Parent_Subtype (Rectype);
3432
3433 begin
3434 if Present (PS) and then Is_Fully_Repped_Tagged_Type (PS) then
3435 Tagged_Parent := PS;
3436
3437 -- Find maximum bit of any component of the parent type
3438
3439 Parent_Last_Bit := UI_From_Int (System_Address_Size - 1);
3440 Pcomp := First_Entity (Tagged_Parent);
3441 while Present (Pcomp) loop
3442 if Ekind_In (Pcomp, E_Discriminant, E_Component) then
3443 if Component_Bit_Offset (Pcomp) /= No_Uint
3444 and then Known_Static_Esize (Pcomp)
3445 then
3446 Parent_Last_Bit :=
3447 UI_Max
3448 (Parent_Last_Bit,
3449 Component_Bit_Offset (Pcomp) + Esize (Pcomp) - 1);
3450 end if;
3451
3452 Next_Entity (Pcomp);
3453 end if;
3454 end loop;
3455 end if;
3456 end;
3457
3458 -- All done if no component clauses
3459
3460 CC := First (Component_Clauses (N));
3461
3462 if No (CC) then
3463 return;
3464 end if;
3465
3466 -- If a tag is present, then create a component clause that places it
3467 -- at the start of the record (otherwise gigi may place it after other
3468 -- fields that have rep clauses).
3469
3470 Fent := First_Entity (Rectype);
3471
3472 if Nkind (Fent) = N_Defining_Identifier
3473 and then Chars (Fent) = Name_uTag
3474 then
3475 Set_Component_Bit_Offset (Fent, Uint_0);
3476 Set_Normalized_Position (Fent, Uint_0);
3477 Set_Normalized_First_Bit (Fent, Uint_0);
3478 Set_Normalized_Position_Max (Fent, Uint_0);
3479 Init_Esize (Fent, System_Address_Size);
3480
3481 Set_Component_Clause (Fent,
3482 Make_Component_Clause (Loc,
3483 Component_Name =>
3484 Make_Identifier (Loc,
3485 Chars => Name_uTag),
3486
3487 Position =>
3488 Make_Integer_Literal (Loc,
3489 Intval => Uint_0),
3490
3491 First_Bit =>
3492 Make_Integer_Literal (Loc,
3493 Intval => Uint_0),
3494
3495 Last_Bit =>
3496 Make_Integer_Literal (Loc,
3497 UI_From_Int (System_Address_Size))));
3498
3499 Ccount := Ccount + 1;
3500 end if;
3501
3502 Max_Bit_So_Far := Uint_Minus_1;
3503 Overlap_Check_Required := False;
3504
3505 -- Process the component clauses
3506
3507 while Present (CC) loop
3508 Find_Component;
3509
3510 if Present (Comp) then
3511 Ccount := Ccount + 1;
3512
3513 -- We need a full overlap check if record positions non-monotonic
3514
3515 if Fbit <= Max_Bit_So_Far then
3516 Overlap_Check_Required := True;
3517 end if;
3518
3519 Max_Bit_So_Far := Lbit;
3520
3521 -- Check bit position out of range of specified size
3522
3523 if Has_Size_Clause (Rectype)
3524 and then Esize (Rectype) <= Lbit
3525 then
3526 Error_Msg_N
3527 ("bit number out of range of specified size",
3528 Last_Bit (CC));
3529
3530 -- Check for overlap with tag field
3531
3532 else
3533 if Is_Tagged_Type (Rectype)
3534 and then Fbit < System_Address_Size
3535 then
3536 Error_Msg_NE
3537 ("component overlaps tag field of&",
3538 Component_Name (CC), Rectype);
3539 Overlap_Detected := True;
3540 end if;
3541
3542 if Hbit < Lbit then
3543 Hbit := Lbit;
3544 end if;
3545 end if;
3546
3547 -- Check parent overlap if component might overlap parent field
3548
3549 if Present (Tagged_Parent)
3550 and then Fbit <= Parent_Last_Bit
3551 then
3552 Pcomp := First_Component_Or_Discriminant (Tagged_Parent);
3553 while Present (Pcomp) loop
3554 if not Is_Tag (Pcomp)
3555 and then Chars (Pcomp) /= Name_uParent
3556 then
3557 Check_Component_Overlap (Comp, Pcomp);
3558 end if;
3559
3560 Next_Component_Or_Discriminant (Pcomp);
3561 end loop;
3562 end if;
3563 end if;
3564
3565 Next (CC);
3566 end loop;
3567
3568 -- Now that we have processed all the component clauses, check for
3569 -- overlap. We have to leave this till last, since the components can
3570 -- appear in any arbitrary order in the representation clause.
3571
3572 -- We do not need this check if all specified ranges were monotonic,
3573 -- as recorded by Overlap_Check_Required being False at this stage.
3574
3575 -- This first section checks if there are any overlapping entries at
3576 -- all. It does this by sorting all entries and then seeing if there are
3577 -- any overlaps. If there are none, then that is decisive, but if there
3578 -- are overlaps, they may still be OK (they may result from fields in
3579 -- different variants).
3580
3581 if Overlap_Check_Required then
3582 Overlap_Check1 : declare
3583
3584 OC_Fbit : array (0 .. Ccount) of Uint;
3585 -- First-bit values for component clauses, the value is the offset
3586 -- of the first bit of the field from start of record. The zero
3587 -- entry is for use in sorting.
3588
3589 OC_Lbit : array (0 .. Ccount) of Uint;
3590 -- Last-bit values for component clauses, the value is the offset
3591 -- of the last bit of the field from start of record. The zero
3592 -- entry is for use in sorting.
3593
3594 OC_Count : Natural := 0;
3595 -- Count of entries in OC_Fbit and OC_Lbit
3596
3597 function OC_Lt (Op1, Op2 : Natural) return Boolean;
3598 -- Compare routine for Sort
3599
3600 procedure OC_Move (From : Natural; To : Natural);
3601 -- Move routine for Sort
3602
3603 package Sorting is new GNAT.Heap_Sort_G (OC_Move, OC_Lt);
3604
3605 -----------
3606 -- OC_Lt --
3607 -----------
3608
3609 function OC_Lt (Op1, Op2 : Natural) return Boolean is
3610 begin
3611 return OC_Fbit (Op1) < OC_Fbit (Op2);
3612 end OC_Lt;
3613
3614 -------------
3615 -- OC_Move --
3616 -------------
3617
3618 procedure OC_Move (From : Natural; To : Natural) is
3619 begin
3620 OC_Fbit (To) := OC_Fbit (From);
3621 OC_Lbit (To) := OC_Lbit (From);
3622 end OC_Move;
3623
3624 -- Start of processing for Overlap_Check
3625
3626 begin
3627 CC := First (Component_Clauses (N));
3628 while Present (CC) loop
3629
3630 -- Exclude component clause already marked in error
3631
3632 if not Error_Posted (CC) then
3633 Find_Component;
3634
3635 if Present (Comp) then
3636 OC_Count := OC_Count + 1;
3637 OC_Fbit (OC_Count) := Fbit;
3638 OC_Lbit (OC_Count) := Lbit;
3639 end if;
3640 end if;
3641
3642 Next (CC);
3643 end loop;
3644
3645 Sorting.Sort (OC_Count);
3646
3647 Overlap_Check_Required := False;
3648 for J in 1 .. OC_Count - 1 loop
3649 if OC_Lbit (J) >= OC_Fbit (J + 1) then
3650 Overlap_Check_Required := True;
3651 exit;
3652 end if;
3653 end loop;
3654 end Overlap_Check1;
3655 end if;
3656
3657 -- If Overlap_Check_Required is still True, then we have to do the full
3658 -- scale overlap check, since we have at least two fields that do
3659 -- overlap, and we need to know if that is OK since they are in
3660 -- different variant, or whether we have a definite problem.
3661
3662 if Overlap_Check_Required then
3663 Overlap_Check2 : declare
3664 C1_Ent, C2_Ent : Entity_Id;
3665 -- Entities of components being checked for overlap
3666
3667 Clist : Node_Id;
3668 -- Component_List node whose Component_Items are being checked
3669
3670 Citem : Node_Id;
3671 -- Component declaration for component being checked
3672
3673 begin
3674 C1_Ent := First_Entity (Base_Type (Rectype));
3675
3676 -- Loop through all components in record. For each component check
3677 -- for overlap with any of the preceding elements on the component
3678 -- list containing the component and also, if the component is in
3679 -- a variant, check against components outside the case structure.
3680 -- This latter test is repeated recursively up the variant tree.
3681
3682 Main_Component_Loop : while Present (C1_Ent) loop
3683 if not Ekind_In (C1_Ent, E_Component, E_Discriminant) then
3684 goto Continue_Main_Component_Loop;
3685 end if;
3686
3687 -- Skip overlap check if entity has no declaration node. This
3688 -- happens with discriminants in constrained derived types.
3689 -- Possibly we are missing some checks as a result, but that
3690 -- does not seem terribly serious.
3691
3692 if No (Declaration_Node (C1_Ent)) then
3693 goto Continue_Main_Component_Loop;
3694 end if;
3695
3696 Clist := Parent (List_Containing (Declaration_Node (C1_Ent)));
3697
3698 -- Loop through component lists that need checking. Check the
3699 -- current component list and all lists in variants above us.
3700
3701 Component_List_Loop : loop
3702
3703 -- If derived type definition, go to full declaration
3704 -- If at outer level, check discriminants if there are any.
3705
3706 if Nkind (Clist) = N_Derived_Type_Definition then
3707 Clist := Parent (Clist);
3708 end if;
3709
3710 -- Outer level of record definition, check discriminants
3711
3712 if Nkind_In (Clist, N_Full_Type_Declaration,
3713 N_Private_Type_Declaration)
3714 then
3715 if Has_Discriminants (Defining_Identifier (Clist)) then
3716 C2_Ent :=
3717 First_Discriminant (Defining_Identifier (Clist));
3718 while Present (C2_Ent) loop
3719 exit when C1_Ent = C2_Ent;
3720 Check_Component_Overlap (C1_Ent, C2_Ent);
3721 Next_Discriminant (C2_Ent);
3722 end loop;
3723 end if;
3724
3725 -- Record extension case
3726
3727 elsif Nkind (Clist) = N_Derived_Type_Definition then
3728 Clist := Empty;
3729
3730 -- Otherwise check one component list
3731
3732 else
3733 Citem := First (Component_Items (Clist));
3734 while Present (Citem) loop
3735 if Nkind (Citem) = N_Component_Declaration then
3736 C2_Ent := Defining_Identifier (Citem);
3737 exit when C1_Ent = C2_Ent;
3738 Check_Component_Overlap (C1_Ent, C2_Ent);
3739 end if;
3740
3741 Next (Citem);
3742 end loop;
3743 end if;
3744
3745 -- Check for variants above us (the parent of the Clist can
3746 -- be a variant, in which case its parent is a variant part,
3747 -- and the parent of the variant part is a component list
3748 -- whose components must all be checked against the current
3749 -- component for overlap).
3750
3751 if Nkind (Parent (Clist)) = N_Variant then
3752 Clist := Parent (Parent (Parent (Clist)));
3753
3754 -- Check for possible discriminant part in record, this
3755 -- is treated essentially as another level in the
3756 -- recursion. For this case the parent of the component
3757 -- list is the record definition, and its parent is the
3758 -- full type declaration containing the discriminant
3759 -- specifications.
3760
3761 elsif Nkind (Parent (Clist)) = N_Record_Definition then
3762 Clist := Parent (Parent ((Clist)));
3763
3764 -- If neither of these two cases, we are at the top of
3765 -- the tree.
3766
3767 else
3768 exit Component_List_Loop;
3769 end if;
3770 end loop Component_List_Loop;
3771
3772 <<Continue_Main_Component_Loop>>
3773 Next_Entity (C1_Ent);
3774
3775 end loop Main_Component_Loop;
3776 end Overlap_Check2;
3777 end if;
3778
3779 -- The following circuit deals with warning on record holes (gaps). We
3780 -- skip this check if overlap was detected, since it makes sense for the
3781 -- programmer to fix this illegality before worrying about warnings.
3782
3783 if not Overlap_Detected and Warn_On_Record_Holes then
3784 Record_Hole_Check : declare
3785 Decl : constant Node_Id := Declaration_Node (Base_Type (Rectype));
3786 -- Full declaration of record type
3787
3788 procedure Check_Component_List
3789 (CL : Node_Id;
3790 Sbit : Uint;
3791 DS : List_Id);
3792 -- Check component list CL for holes. The starting bit should be
3793 -- Sbit. which is zero for the main record component list and set
3794 -- appropriately for recursive calls for variants. DS is set to
3795 -- a list of discriminant specifications to be included in the
3796 -- consideration of components. It is No_List if none to consider.
3797
3798 --------------------------
3799 -- Check_Component_List --
3800 --------------------------
3801
3802 procedure Check_Component_List
3803 (CL : Node_Id;
3804 Sbit : Uint;
3805 DS : List_Id)
3806 is
3807 Compl : Integer;
3808
3809 begin
3810 Compl := Integer (List_Length (Component_Items (CL)));
3811
3812 if DS /= No_List then
3813 Compl := Compl + Integer (List_Length (DS));
3814 end if;
3815
3816 declare
3817 Comps : array (Natural range 0 .. Compl) of Entity_Id;
3818 -- Gather components (zero entry is for sort routine)
3819
3820 Ncomps : Natural := 0;
3821 -- Number of entries stored in Comps (starting at Comps (1))
3822
3823 Citem : Node_Id;
3824 -- One component item or discriminant specification
3825
3826 Nbit : Uint;
3827 -- Starting bit for next component
3828
3829 CEnt : Entity_Id;
3830 -- Component entity
3831
3832 Variant : Node_Id;
3833 -- One variant
3834
3835 function Lt (Op1, Op2 : Natural) return Boolean;
3836 -- Compare routine for Sort
3837
3838 procedure Move (From : Natural; To : Natural);
3839 -- Move routine for Sort
3840
3841 package Sorting is new GNAT.Heap_Sort_G (Move, Lt);
3842
3843 --------
3844 -- Lt --
3845 --------
3846
3847 function Lt (Op1, Op2 : Natural) return Boolean is
3848 begin
3849 return Component_Bit_Offset (Comps (Op1))
3850 <
3851 Component_Bit_Offset (Comps (Op2));
3852 end Lt;
3853
3854 ----------
3855 -- Move --
3856 ----------
3857
3858 procedure Move (From : Natural; To : Natural) is
3859 begin
3860 Comps (To) := Comps (From);
3861 end Move;
3862
3863 begin
3864 -- Gather discriminants into Comp
3865
3866 if DS /= No_List then
3867 Citem := First (DS);
3868 while Present (Citem) loop
3869 if Nkind (Citem) = N_Discriminant_Specification then
3870 declare
3871 Ent : constant Entity_Id :=
3872 Defining_Identifier (Citem);
3873 begin
3874 if Ekind (Ent) = E_Discriminant then
3875 Ncomps := Ncomps + 1;
3876 Comps (Ncomps) := Ent;
3877 end if;
3878 end;
3879 end if;
3880
3881 Next (Citem);
3882 end loop;
3883 end if;
3884
3885 -- Gather component entities into Comp
3886
3887 Citem := First (Component_Items (CL));
3888 while Present (Citem) loop
3889 if Nkind (Citem) = N_Component_Declaration then
3890 Ncomps := Ncomps + 1;
3891 Comps (Ncomps) := Defining_Identifier (Citem);
3892 end if;
3893
3894 Next (Citem);
3895 end loop;
3896
3897 -- Now sort the component entities based on the first bit.
3898 -- Note we already know there are no overlapping components.
3899
3900 Sorting.Sort (Ncomps);
3901
3902 -- Loop through entries checking for holes
3903
3904 Nbit := Sbit;
3905 for J in 1 .. Ncomps loop
3906 CEnt := Comps (J);
3907 Error_Msg_Uint_1 := Component_Bit_Offset (CEnt) - Nbit;
3908
3909 if Error_Msg_Uint_1 > 0 then
3910 Error_Msg_NE
3911 ("?^-bit gap before component&",
3912 Component_Name (Component_Clause (CEnt)), CEnt);
3913 end if;
3914
3915 Nbit := Component_Bit_Offset (CEnt) + Esize (CEnt);
3916 end loop;
3917
3918 -- Process variant parts recursively if present
3919
3920 if Present (Variant_Part (CL)) then
3921 Variant := First (Variants (Variant_Part (CL)));
3922 while Present (Variant) loop
3923 Check_Component_List
3924 (Component_List (Variant), Nbit, No_List);
3925 Next (Variant);
3926 end loop;
3927 end if;
3928 end;
3929 end Check_Component_List;
3930
3931 -- Start of processing for Record_Hole_Check
3932
3933 begin
3934 declare
3935 Sbit : Uint;
3936
3937 begin
3938 if Is_Tagged_Type (Rectype) then
3939 Sbit := UI_From_Int (System_Address_Size);
3940 else
3941 Sbit := Uint_0;
3942 end if;
3943
3944 if Nkind (Decl) = N_Full_Type_Declaration
3945 and then Nkind (Type_Definition (Decl)) = N_Record_Definition
3946 then
3947 Check_Component_List
3948 (Component_List (Type_Definition (Decl)),
3949 Sbit,
3950 Discriminant_Specifications (Decl));
3951 end if;
3952 end;
3953 end Record_Hole_Check;
3954 end if;
3955
3956 -- For records that have component clauses for all components, and whose
3957 -- size is less than or equal to 32, we need to know the size in the
3958 -- front end to activate possible packed array processing where the
3959 -- component type is a record.
3960
3961 -- At this stage Hbit + 1 represents the first unused bit from all the
3962 -- component clauses processed, so if the component clauses are
3963 -- complete, then this is the length of the record.
3964
3965 -- For records longer than System.Storage_Unit, and for those where not
3966 -- all components have component clauses, the back end determines the
3967 -- length (it may for example be appropriate to round up the size
3968 -- to some convenient boundary, based on alignment considerations, etc).
3969
3970 if Unknown_RM_Size (Rectype) and then Hbit + 1 <= 32 then
3971
3972 -- Nothing to do if at least one component has no component clause
3973
3974 Comp := First_Component_Or_Discriminant (Rectype);
3975 while Present (Comp) loop
3976 exit when No (Component_Clause (Comp));
3977 Next_Component_Or_Discriminant (Comp);
3978 end loop;
3979
3980 -- If we fall out of loop, all components have component clauses
3981 -- and so we can set the size to the maximum value.
3982
3983 if No (Comp) then
3984 Set_RM_Size (Rectype, Hbit + 1);
3985 end if;
3986 end if;
3987 end Check_Record_Representation_Clause;
3988
3989 ----------------
3990 -- Check_Size --
3991 ----------------
3992
3993 procedure Check_Size
3994 (N : Node_Id;
3995 T : Entity_Id;
3996 Siz : Uint;
3997 Biased : out Boolean)
3998 is
3999 UT : constant Entity_Id := Underlying_Type (T);
4000 M : Uint;
4001
4002 begin
4003 Biased := False;
4004
4005 -- Dismiss cases for generic types or types with previous errors
4006
4007 if No (UT)
4008 or else UT = Any_Type
4009 or else Is_Generic_Type (UT)
4010 or else Is_Generic_Type (Root_Type (UT))
4011 then
4012 return;
4013
4014 -- Check case of bit packed array
4015
4016 elsif Is_Array_Type (UT)
4017 and then Known_Static_Component_Size (UT)
4018 and then Is_Bit_Packed_Array (UT)
4019 then
4020 declare
4021 Asiz : Uint;
4022 Indx : Node_Id;
4023 Ityp : Entity_Id;
4024
4025 begin
4026 Asiz := Component_Size (UT);
4027 Indx := First_Index (UT);
4028 loop
4029 Ityp := Etype (Indx);
4030
4031 -- If non-static bound, then we are not in the business of
4032 -- trying to check the length, and indeed an error will be
4033 -- issued elsewhere, since sizes of non-static array types
4034 -- cannot be set implicitly or explicitly.
4035
4036 if not Is_Static_Subtype (Ityp) then
4037 return;
4038 end if;
4039
4040 -- Otherwise accumulate next dimension
4041
4042 Asiz := Asiz * (Expr_Value (Type_High_Bound (Ityp)) -
4043 Expr_Value (Type_Low_Bound (Ityp)) +
4044 Uint_1);
4045
4046 Next_Index (Indx);
4047 exit when No (Indx);
4048 end loop;
4049
4050 if Asiz <= Siz then
4051 return;
4052 else
4053 Error_Msg_Uint_1 := Asiz;
4054 Error_Msg_NE
4055 ("size for& too small, minimum allowed is ^", N, T);
4056 Set_Esize (T, Asiz);
4057 Set_RM_Size (T, Asiz);
4058 end if;
4059 end;
4060
4061 -- All other composite types are ignored
4062
4063 elsif Is_Composite_Type (UT) then
4064 return;
4065
4066 -- For fixed-point types, don't check minimum if type is not frozen,
4067 -- since we don't know all the characteristics of the type that can
4068 -- affect the size (e.g. a specified small) till freeze time.
4069
4070 elsif Is_Fixed_Point_Type (UT)
4071 and then not Is_Frozen (UT)
4072 then
4073 null;
4074
4075 -- Cases for which a minimum check is required
4076
4077 else
4078 -- Ignore if specified size is correct for the type
4079
4080 if Known_Esize (UT) and then Siz = Esize (UT) then
4081 return;
4082 end if;
4083
4084 -- Otherwise get minimum size
4085
4086 M := UI_From_Int (Minimum_Size (UT));
4087
4088 if Siz < M then
4089
4090 -- Size is less than minimum size, but one possibility remains
4091 -- that we can manage with the new size if we bias the type.
4092
4093 M := UI_From_Int (Minimum_Size (UT, Biased => True));
4094
4095 if Siz < M then
4096 Error_Msg_Uint_1 := M;
4097 Error_Msg_NE
4098 ("size for& too small, minimum allowed is ^", N, T);
4099 Set_Esize (T, M);
4100 Set_RM_Size (T, M);
4101 else
4102 Biased := True;
4103 end if;
4104 end if;
4105 end if;
4106 end Check_Size;
4107
4108 -------------------------
4109 -- Get_Alignment_Value --
4110 -------------------------
4111
4112 function Get_Alignment_Value (Expr : Node_Id) return Uint is
4113 Align : constant Uint := Static_Integer (Expr);
4114
4115 begin
4116 if Align = No_Uint then
4117 return No_Uint;
4118
4119 elsif Align <= 0 then
4120 Error_Msg_N ("alignment value must be positive", Expr);
4121 return No_Uint;
4122
4123 else
4124 for J in Int range 0 .. 64 loop
4125 declare
4126 M : constant Uint := Uint_2 ** J;
4127
4128 begin
4129 exit when M = Align;
4130
4131 if M > Align then
4132 Error_Msg_N
4133 ("alignment value must be power of 2", Expr);
4134 return No_Uint;
4135 end if;
4136 end;
4137 end loop;
4138
4139 return Align;
4140 end if;
4141 end Get_Alignment_Value;
4142
4143 ----------------
4144 -- Initialize --
4145 ----------------
4146
4147 procedure Initialize is
4148 begin
4149 Unchecked_Conversions.Init;
4150 end Initialize;
4151
4152 -------------------------
4153 -- Is_Operational_Item --
4154 -------------------------
4155
4156 function Is_Operational_Item (N : Node_Id) return Boolean is
4157 begin
4158 if Nkind (N) /= N_Attribute_Definition_Clause then
4159 return False;
4160 else
4161 declare
4162 Id : constant Attribute_Id := Get_Attribute_Id (Chars (N));
4163 begin
4164 return Id = Attribute_Input
4165 or else Id = Attribute_Output
4166 or else Id = Attribute_Read
4167 or else Id = Attribute_Write
4168 or else Id = Attribute_External_Tag;
4169 end;
4170 end if;
4171 end Is_Operational_Item;
4172
4173 ------------------
4174 -- Minimum_Size --
4175 ------------------
4176
4177 function Minimum_Size
4178 (T : Entity_Id;
4179 Biased : Boolean := False) return Nat
4180 is
4181 Lo : Uint := No_Uint;
4182 Hi : Uint := No_Uint;
4183 LoR : Ureal := No_Ureal;
4184 HiR : Ureal := No_Ureal;
4185 LoSet : Boolean := False;
4186 HiSet : Boolean := False;
4187 B : Uint;
4188 S : Nat;
4189 Ancest : Entity_Id;
4190 R_Typ : constant Entity_Id := Root_Type (T);
4191
4192 begin
4193 -- If bad type, return 0
4194
4195 if T = Any_Type then
4196 return 0;
4197
4198 -- For generic types, just return zero. There cannot be any legitimate
4199 -- need to know such a size, but this routine may be called with a
4200 -- generic type as part of normal processing.
4201
4202 elsif Is_Generic_Type (R_Typ)
4203 or else R_Typ = Any_Type
4204 then
4205 return 0;
4206
4207 -- Access types. Normally an access type cannot have a size smaller
4208 -- than the size of System.Address. The exception is on VMS, where
4209 -- we have short and long addresses, and it is possible for an access
4210 -- type to have a short address size (and thus be less than the size
4211 -- of System.Address itself). We simply skip the check for VMS, and
4212 -- leave it to the back end to do the check.
4213
4214 elsif Is_Access_Type (T) then
4215 if OpenVMS_On_Target then
4216 return 0;
4217 else
4218 return System_Address_Size;
4219 end if;
4220
4221 -- Floating-point types
4222
4223 elsif Is_Floating_Point_Type (T) then
4224 return UI_To_Int (Esize (R_Typ));
4225
4226 -- Discrete types
4227
4228 elsif Is_Discrete_Type (T) then
4229
4230 -- The following loop is looking for the nearest compile time known
4231 -- bounds following the ancestor subtype chain. The idea is to find
4232 -- the most restrictive known bounds information.
4233
4234 Ancest := T;
4235 loop
4236 if Ancest = Any_Type or else Etype (Ancest) = Any_Type then
4237 return 0;
4238 end if;
4239
4240 if not LoSet then
4241 if Compile_Time_Known_Value (Type_Low_Bound (Ancest)) then
4242 Lo := Expr_Rep_Value (Type_Low_Bound (Ancest));
4243 LoSet := True;
4244 exit when HiSet;
4245 end if;
4246 end if;
4247
4248 if not HiSet then
4249 if Compile_Time_Known_Value (Type_High_Bound (Ancest)) then
4250 Hi := Expr_Rep_Value (Type_High_Bound (Ancest));
4251 HiSet := True;
4252 exit when LoSet;
4253 end if;
4254 end if;
4255
4256 Ancest := Ancestor_Subtype (Ancest);
4257
4258 if No (Ancest) then
4259 Ancest := Base_Type (T);
4260
4261 if Is_Generic_Type (Ancest) then
4262 return 0;
4263 end if;
4264 end if;
4265 end loop;
4266
4267 -- Fixed-point types. We can't simply use Expr_Value to get the
4268 -- Corresponding_Integer_Value values of the bounds, since these do not
4269 -- get set till the type is frozen, and this routine can be called
4270 -- before the type is frozen. Similarly the test for bounds being static
4271 -- needs to include the case where we have unanalyzed real literals for
4272 -- the same reason.
4273
4274 elsif Is_Fixed_Point_Type (T) then
4275
4276 -- The following loop is looking for the nearest compile time known
4277 -- bounds following the ancestor subtype chain. The idea is to find
4278 -- the most restrictive known bounds information.
4279
4280 Ancest := T;
4281 loop
4282 if Ancest = Any_Type or else Etype (Ancest) = Any_Type then
4283 return 0;
4284 end if;
4285
4286 -- Note: In the following two tests for LoSet and HiSet, it may
4287 -- seem redundant to test for N_Real_Literal here since normally
4288 -- one would assume that the test for the value being known at
4289 -- compile time includes this case. However, there is a glitch.
4290 -- If the real literal comes from folding a non-static expression,
4291 -- then we don't consider any non- static expression to be known
4292 -- at compile time if we are in configurable run time mode (needed
4293 -- in some cases to give a clearer definition of what is and what
4294 -- is not accepted). So the test is indeed needed. Without it, we
4295 -- would set neither Lo_Set nor Hi_Set and get an infinite loop.
4296
4297 if not LoSet then
4298 if Nkind (Type_Low_Bound (Ancest)) = N_Real_Literal
4299 or else Compile_Time_Known_Value (Type_Low_Bound (Ancest))
4300 then
4301 LoR := Expr_Value_R (Type_Low_Bound (Ancest));
4302 LoSet := True;
4303 exit when HiSet;
4304 end if;
4305 end if;
4306
4307 if not HiSet then
4308 if Nkind (Type_High_Bound (Ancest)) = N_Real_Literal
4309 or else Compile_Time_Known_Value (Type_High_Bound (Ancest))
4310 then
4311 HiR := Expr_Value_R (Type_High_Bound (Ancest));
4312 HiSet := True;
4313 exit when LoSet;
4314 end if;
4315 end if;
4316
4317 Ancest := Ancestor_Subtype (Ancest);
4318
4319 if No (Ancest) then
4320 Ancest := Base_Type (T);
4321
4322 if Is_Generic_Type (Ancest) then
4323 return 0;
4324 end if;
4325 end if;
4326 end loop;
4327
4328 Lo := UR_To_Uint (LoR / Small_Value (T));
4329 Hi := UR_To_Uint (HiR / Small_Value (T));
4330
4331 -- No other types allowed
4332
4333 else
4334 raise Program_Error;
4335 end if;
4336
4337 -- Fall through with Hi and Lo set. Deal with biased case
4338
4339 if (Biased
4340 and then not Is_Fixed_Point_Type (T)
4341 and then not (Is_Enumeration_Type (T)
4342 and then Has_Non_Standard_Rep (T)))
4343 or else Has_Biased_Representation (T)
4344 then
4345 Hi := Hi - Lo;
4346 Lo := Uint_0;
4347 end if;
4348
4349 -- Signed case. Note that we consider types like range 1 .. -1 to be
4350 -- signed for the purpose of computing the size, since the bounds have
4351 -- to be accommodated in the base type.
4352
4353 if Lo < 0 or else Hi < 0 then
4354 S := 1;
4355 B := Uint_1;
4356
4357 -- S = size, B = 2 ** (size - 1) (can accommodate -B .. +(B - 1))
4358 -- Note that we accommodate the case where the bounds cross. This
4359 -- can happen either because of the way the bounds are declared
4360 -- or because of the algorithm in Freeze_Fixed_Point_Type.
4361
4362 while Lo < -B
4363 or else Hi < -B
4364 or else Lo >= B
4365 or else Hi >= B
4366 loop
4367 B := Uint_2 ** S;
4368 S := S + 1;
4369 end loop;
4370
4371 -- Unsigned case
4372
4373 else
4374 -- If both bounds are positive, make sure that both are represen-
4375 -- table in the case where the bounds are crossed. This can happen
4376 -- either because of the way the bounds are declared, or because of
4377 -- the algorithm in Freeze_Fixed_Point_Type.
4378
4379 if Lo > Hi then
4380 Hi := Lo;
4381 end if;
4382
4383 -- S = size, (can accommodate 0 .. (2**size - 1))
4384
4385 S := 0;
4386 while Hi >= Uint_2 ** S loop
4387 S := S + 1;
4388 end loop;
4389 end if;
4390
4391 return S;
4392 end Minimum_Size;
4393
4394 ---------------------------
4395 -- New_Stream_Subprogram --
4396 ---------------------------
4397
4398 procedure New_Stream_Subprogram
4399 (N : Node_Id;
4400 Ent : Entity_Id;
4401 Subp : Entity_Id;
4402 Nam : TSS_Name_Type)
4403 is
4404 Loc : constant Source_Ptr := Sloc (N);
4405 Sname : constant Name_Id := Make_TSS_Name (Base_Type (Ent), Nam);
4406 Subp_Id : Entity_Id;
4407 Subp_Decl : Node_Id;
4408 F : Entity_Id;
4409 Etyp : Entity_Id;
4410
4411 Defer_Declaration : constant Boolean :=
4412 Is_Tagged_Type (Ent) or else Is_Private_Type (Ent);
4413 -- For a tagged type, there is a declaration for each stream attribute
4414 -- at the freeze point, and we must generate only a completion of this
4415 -- declaration. We do the same for private types, because the full view
4416 -- might be tagged. Otherwise we generate a declaration at the point of
4417 -- the attribute definition clause.
4418
4419 function Build_Spec return Node_Id;
4420 -- Used for declaration and renaming declaration, so that this is
4421 -- treated as a renaming_as_body.
4422
4423 ----------------
4424 -- Build_Spec --
4425 ----------------
4426
4427 function Build_Spec return Node_Id is
4428 Out_P : constant Boolean := (Nam = TSS_Stream_Read);
4429 Formals : List_Id;
4430 Spec : Node_Id;
4431 T_Ref : constant Node_Id := New_Reference_To (Etyp, Loc);
4432
4433 begin
4434 Subp_Id := Make_Defining_Identifier (Loc, Sname);
4435
4436 -- S : access Root_Stream_Type'Class
4437
4438 Formals := New_List (
4439 Make_Parameter_Specification (Loc,
4440 Defining_Identifier =>
4441 Make_Defining_Identifier (Loc, Name_S),
4442 Parameter_Type =>
4443 Make_Access_Definition (Loc,
4444 Subtype_Mark =>
4445 New_Reference_To (
4446 Designated_Type (Etype (F)), Loc))));
4447
4448 if Nam = TSS_Stream_Input then
4449 Spec := Make_Function_Specification (Loc,
4450 Defining_Unit_Name => Subp_Id,
4451 Parameter_Specifications => Formals,
4452 Result_Definition => T_Ref);
4453 else
4454 -- V : [out] T
4455
4456 Append_To (Formals,
4457 Make_Parameter_Specification (Loc,
4458 Defining_Identifier => Make_Defining_Identifier (Loc, Name_V),
4459 Out_Present => Out_P,
4460 Parameter_Type => T_Ref));
4461
4462 Spec :=
4463 Make_Procedure_Specification (Loc,
4464 Defining_Unit_Name => Subp_Id,
4465 Parameter_Specifications => Formals);
4466 end if;
4467
4468 return Spec;
4469 end Build_Spec;
4470
4471 -- Start of processing for New_Stream_Subprogram
4472
4473 begin
4474 F := First_Formal (Subp);
4475
4476 if Ekind (Subp) = E_Procedure then
4477 Etyp := Etype (Next_Formal (F));
4478 else
4479 Etyp := Etype (Subp);
4480 end if;
4481
4482 -- Prepare subprogram declaration and insert it as an action on the
4483 -- clause node. The visibility for this entity is used to test for
4484 -- visibility of the attribute definition clause (in the sense of
4485 -- 8.3(23) as amended by AI-195).
4486
4487 if not Defer_Declaration then
4488 Subp_Decl :=
4489 Make_Subprogram_Declaration (Loc,
4490 Specification => Build_Spec);
4491
4492 -- For a tagged type, there is always a visible declaration for each
4493 -- stream TSS (it is a predefined primitive operation), and the
4494 -- completion of this declaration occurs at the freeze point, which is
4495 -- not always visible at places where the attribute definition clause is
4496 -- visible. So, we create a dummy entity here for the purpose of
4497 -- tracking the visibility of the attribute definition clause itself.
4498
4499 else
4500 Subp_Id :=
4501 Make_Defining_Identifier (Loc,
4502 Chars => New_External_Name (Sname, 'V'));
4503 Subp_Decl :=
4504 Make_Object_Declaration (Loc,
4505 Defining_Identifier => Subp_Id,
4506 Object_Definition => New_Occurrence_Of (Standard_Boolean, Loc));
4507 end if;
4508
4509 Insert_Action (N, Subp_Decl);
4510 Set_Entity (N, Subp_Id);
4511
4512 Subp_Decl :=
4513 Make_Subprogram_Renaming_Declaration (Loc,
4514 Specification => Build_Spec,
4515 Name => New_Reference_To (Subp, Loc));
4516
4517 if Defer_Declaration then
4518 Set_TSS (Base_Type (Ent), Subp_Id);
4519 else
4520 Insert_Action (N, Subp_Decl);
4521 Copy_TSS (Subp_Id, Base_Type (Ent));
4522 end if;
4523 end New_Stream_Subprogram;
4524
4525 ------------------------
4526 -- Rep_Item_Too_Early --
4527 ------------------------
4528
4529 function Rep_Item_Too_Early (T : Entity_Id; N : Node_Id) return Boolean is
4530 begin
4531 -- Cannot apply non-operational rep items to generic types
4532
4533 if Is_Operational_Item (N) then
4534 return False;
4535
4536 elsif Is_Type (T)
4537 and then Is_Generic_Type (Root_Type (T))
4538 then
4539 Error_Msg_N ("representation item not allowed for generic type", N);
4540 return True;
4541 end if;
4542
4543 -- Otherwise check for incomplete type
4544
4545 if Is_Incomplete_Or_Private_Type (T)
4546 and then No (Underlying_Type (T))
4547 then
4548 Error_Msg_N
4549 ("representation item must be after full type declaration", N);
4550 return True;
4551
4552 -- If the type has incomplete components, a representation clause is
4553 -- illegal but stream attributes and Convention pragmas are correct.
4554
4555 elsif Has_Private_Component (T) then
4556 if Nkind (N) = N_Pragma then
4557 return False;
4558 else
4559 Error_Msg_N
4560 ("representation item must appear after type is fully defined",
4561 N);
4562 return True;
4563 end if;
4564 else
4565 return False;
4566 end if;
4567 end Rep_Item_Too_Early;
4568
4569 -----------------------
4570 -- Rep_Item_Too_Late --
4571 -----------------------
4572
4573 function Rep_Item_Too_Late
4574 (T : Entity_Id;
4575 N : Node_Id;
4576 FOnly : Boolean := False) return Boolean
4577 is
4578 S : Entity_Id;
4579 Parent_Type : Entity_Id;
4580
4581 procedure Too_Late;
4582 -- Output the too late message. Note that this is not considered a
4583 -- serious error, since the effect is simply that we ignore the
4584 -- representation clause in this case.
4585
4586 --------------
4587 -- Too_Late --
4588 --------------
4589
4590 procedure Too_Late is
4591 begin
4592 Error_Msg_N ("|representation item appears too late!", N);
4593 end Too_Late;
4594
4595 -- Start of processing for Rep_Item_Too_Late
4596
4597 begin
4598 -- First make sure entity is not frozen (RM 13.1(9)). Exclude imported
4599 -- types, which may be frozen if they appear in a representation clause
4600 -- for a local type.
4601
4602 if Is_Frozen (T)
4603 and then not From_With_Type (T)
4604 then
4605 Too_Late;
4606 S := First_Subtype (T);
4607
4608 if Present (Freeze_Node (S)) then
4609 Error_Msg_NE
4610 ("?no more representation items for }", Freeze_Node (S), S);
4611 end if;
4612
4613 return True;
4614
4615 -- Check for case of non-tagged derived type whose parent either has
4616 -- primitive operations, or is a by reference type (RM 13.1(10)).
4617
4618 elsif Is_Type (T)
4619 and then not FOnly
4620 and then Is_Derived_Type (T)
4621 and then not Is_Tagged_Type (T)
4622 then
4623 Parent_Type := Etype (Base_Type (T));
4624
4625 if Has_Primitive_Operations (Parent_Type) then
4626 Too_Late;
4627 Error_Msg_NE
4628 ("primitive operations already defined for&!", N, Parent_Type);
4629 return True;
4630
4631 elsif Is_By_Reference_Type (Parent_Type) then
4632 Too_Late;
4633 Error_Msg_NE
4634 ("parent type & is a by reference type!", N, Parent_Type);
4635 return True;
4636 end if;
4637 end if;
4638
4639 -- No error, link item into head of chain of rep items for the entity,
4640 -- but avoid chaining if we have an overloadable entity, and the pragma
4641 -- is one that can apply to multiple overloaded entities.
4642
4643 if Is_Overloadable (T)
4644 and then Nkind (N) = N_Pragma
4645 then
4646 declare
4647 Pname : constant Name_Id := Pragma_Name (N);
4648 begin
4649 if Pname = Name_Convention or else
4650 Pname = Name_Import or else
4651 Pname = Name_Export or else
4652 Pname = Name_External or else
4653 Pname = Name_Interface
4654 then
4655 return False;
4656 end if;
4657 end;
4658 end if;
4659
4660 Record_Rep_Item (T, N);
4661 return False;
4662 end Rep_Item_Too_Late;
4663
4664 -------------------------
4665 -- Same_Representation --
4666 -------------------------
4667
4668 function Same_Representation (Typ1, Typ2 : Entity_Id) return Boolean is
4669 T1 : constant Entity_Id := Underlying_Type (Typ1);
4670 T2 : constant Entity_Id := Underlying_Type (Typ2);
4671
4672 begin
4673 -- A quick check, if base types are the same, then we definitely have
4674 -- the same representation, because the subtype specific representation
4675 -- attributes (Size and Alignment) do not affect representation from
4676 -- the point of view of this test.
4677
4678 if Base_Type (T1) = Base_Type (T2) then
4679 return True;
4680
4681 elsif Is_Private_Type (Base_Type (T2))
4682 and then Base_Type (T1) = Full_View (Base_Type (T2))
4683 then
4684 return True;
4685 end if;
4686
4687 -- Tagged types never have differing representations
4688
4689 if Is_Tagged_Type (T1) then
4690 return True;
4691 end if;
4692
4693 -- Representations are definitely different if conventions differ
4694
4695 if Convention (T1) /= Convention (T2) then
4696 return False;
4697 end if;
4698
4699 -- Representations are different if component alignments differ
4700
4701 if (Is_Record_Type (T1) or else Is_Array_Type (T1))
4702 and then
4703 (Is_Record_Type (T2) or else Is_Array_Type (T2))
4704 and then Component_Alignment (T1) /= Component_Alignment (T2)
4705 then
4706 return False;
4707 end if;
4708
4709 -- For arrays, the only real issue is component size. If we know the
4710 -- component size for both arrays, and it is the same, then that's
4711 -- good enough to know we don't have a change of representation.
4712
4713 if Is_Array_Type (T1) then
4714 if Known_Component_Size (T1)
4715 and then Known_Component_Size (T2)
4716 and then Component_Size (T1) = Component_Size (T2)
4717 then
4718 return True;
4719 end if;
4720 end if;
4721
4722 -- Types definitely have same representation if neither has non-standard
4723 -- representation since default representations are always consistent.
4724 -- If only one has non-standard representation, and the other does not,
4725 -- then we consider that they do not have the same representation. They
4726 -- might, but there is no way of telling early enough.
4727
4728 if Has_Non_Standard_Rep (T1) then
4729 if not Has_Non_Standard_Rep (T2) then
4730 return False;
4731 end if;
4732 else
4733 return not Has_Non_Standard_Rep (T2);
4734 end if;
4735
4736 -- Here the two types both have non-standard representation, and we need
4737 -- to determine if they have the same non-standard representation.
4738
4739 -- For arrays, we simply need to test if the component sizes are the
4740 -- same. Pragma Pack is reflected in modified component sizes, so this
4741 -- check also deals with pragma Pack.
4742
4743 if Is_Array_Type (T1) then
4744 return Component_Size (T1) = Component_Size (T2);
4745
4746 -- Tagged types always have the same representation, because it is not
4747 -- possible to specify different representations for common fields.
4748
4749 elsif Is_Tagged_Type (T1) then
4750 return True;
4751
4752 -- Case of record types
4753
4754 elsif Is_Record_Type (T1) then
4755
4756 -- Packed status must conform
4757
4758 if Is_Packed (T1) /= Is_Packed (T2) then
4759 return False;
4760
4761 -- Otherwise we must check components. Typ2 maybe a constrained
4762 -- subtype with fewer components, so we compare the components
4763 -- of the base types.
4764
4765 else
4766 Record_Case : declare
4767 CD1, CD2 : Entity_Id;
4768
4769 function Same_Rep return Boolean;
4770 -- CD1 and CD2 are either components or discriminants. This
4771 -- function tests whether the two have the same representation
4772
4773 --------------
4774 -- Same_Rep --
4775 --------------
4776
4777 function Same_Rep return Boolean is
4778 begin
4779 if No (Component_Clause (CD1)) then
4780 return No (Component_Clause (CD2));
4781
4782 else
4783 return
4784 Present (Component_Clause (CD2))
4785 and then
4786 Component_Bit_Offset (CD1) = Component_Bit_Offset (CD2)
4787 and then
4788 Esize (CD1) = Esize (CD2);
4789 end if;
4790 end Same_Rep;
4791
4792 -- Start of processing for Record_Case
4793
4794 begin
4795 if Has_Discriminants (T1) then
4796 CD1 := First_Discriminant (T1);
4797 CD2 := First_Discriminant (T2);
4798
4799 -- The number of discriminants may be different if the
4800 -- derived type has fewer (constrained by values). The
4801 -- invisible discriminants retain the representation of
4802 -- the original, so the discrepancy does not per se
4803 -- indicate a different representation.
4804
4805 while Present (CD1)
4806 and then Present (CD2)
4807 loop
4808 if not Same_Rep then
4809 return False;
4810 else
4811 Next_Discriminant (CD1);
4812 Next_Discriminant (CD2);
4813 end if;
4814 end loop;
4815 end if;
4816
4817 CD1 := First_Component (Underlying_Type (Base_Type (T1)));
4818 CD2 := First_Component (Underlying_Type (Base_Type (T2)));
4819
4820 while Present (CD1) loop
4821 if not Same_Rep then
4822 return False;
4823 else
4824 Next_Component (CD1);
4825 Next_Component (CD2);
4826 end if;
4827 end loop;
4828
4829 return True;
4830 end Record_Case;
4831 end if;
4832
4833 -- For enumeration types, we must check each literal to see if the
4834 -- representation is the same. Note that we do not permit enumeration
4835 -- representation clauses for Character and Wide_Character, so these
4836 -- cases were already dealt with.
4837
4838 elsif Is_Enumeration_Type (T1) then
4839
4840 Enumeration_Case : declare
4841 L1, L2 : Entity_Id;
4842
4843 begin
4844 L1 := First_Literal (T1);
4845 L2 := First_Literal (T2);
4846
4847 while Present (L1) loop
4848 if Enumeration_Rep (L1) /= Enumeration_Rep (L2) then
4849 return False;
4850 else
4851 Next_Literal (L1);
4852 Next_Literal (L2);
4853 end if;
4854 end loop;
4855
4856 return True;
4857
4858 end Enumeration_Case;
4859
4860 -- Any other types have the same representation for these purposes
4861
4862 else
4863 return True;
4864 end if;
4865 end Same_Representation;
4866
4867 --------------------
4868 -- Set_Enum_Esize --
4869 --------------------
4870
4871 procedure Set_Enum_Esize (T : Entity_Id) is
4872 Lo : Uint;
4873 Hi : Uint;
4874 Sz : Nat;
4875
4876 begin
4877 Init_Alignment (T);
4878
4879 -- Find the minimum standard size (8,16,32,64) that fits
4880
4881 Lo := Enumeration_Rep (Entity (Type_Low_Bound (T)));
4882 Hi := Enumeration_Rep (Entity (Type_High_Bound (T)));
4883
4884 if Lo < 0 then
4885 if Lo >= -Uint_2**07 and then Hi < Uint_2**07 then
4886 Sz := Standard_Character_Size; -- May be > 8 on some targets
4887
4888 elsif Lo >= -Uint_2**15 and then Hi < Uint_2**15 then
4889 Sz := 16;
4890
4891 elsif Lo >= -Uint_2**31 and then Hi < Uint_2**31 then
4892 Sz := 32;
4893
4894 else pragma Assert (Lo >= -Uint_2**63 and then Hi < Uint_2**63);
4895 Sz := 64;
4896 end if;
4897
4898 else
4899 if Hi < Uint_2**08 then
4900 Sz := Standard_Character_Size; -- May be > 8 on some targets
4901
4902 elsif Hi < Uint_2**16 then
4903 Sz := 16;
4904
4905 elsif Hi < Uint_2**32 then
4906 Sz := 32;
4907
4908 else pragma Assert (Hi < Uint_2**63);
4909 Sz := 64;
4910 end if;
4911 end if;
4912
4913 -- That minimum is the proper size unless we have a foreign convention
4914 -- and the size required is 32 or less, in which case we bump the size
4915 -- up to 32. This is required for C and C++ and seems reasonable for
4916 -- all other foreign conventions.
4917
4918 if Has_Foreign_Convention (T)
4919 and then Esize (T) < Standard_Integer_Size
4920 then
4921 Init_Esize (T, Standard_Integer_Size);
4922 else
4923 Init_Esize (T, Sz);
4924 end if;
4925 end Set_Enum_Esize;
4926
4927 ------------------------------
4928 -- Validate_Address_Clauses --
4929 ------------------------------
4930
4931 procedure Validate_Address_Clauses is
4932 begin
4933 for J in Address_Clause_Checks.First .. Address_Clause_Checks.Last loop
4934 declare
4935 ACCR : Address_Clause_Check_Record
4936 renames Address_Clause_Checks.Table (J);
4937
4938 Expr : Node_Id;
4939
4940 X_Alignment : Uint;
4941 Y_Alignment : Uint;
4942
4943 X_Size : Uint;
4944 Y_Size : Uint;
4945
4946 begin
4947 -- Skip processing of this entry if warning already posted
4948
4949 if not Address_Warning_Posted (ACCR.N) then
4950
4951 Expr := Original_Node (Expression (ACCR.N));
4952
4953 -- Get alignments
4954
4955 X_Alignment := Alignment (ACCR.X);
4956 Y_Alignment := Alignment (ACCR.Y);
4957
4958 -- Similarly obtain sizes
4959
4960 X_Size := Esize (ACCR.X);
4961 Y_Size := Esize (ACCR.Y);
4962
4963 -- Check for large object overlaying smaller one
4964
4965 if Y_Size > Uint_0
4966 and then X_Size > Uint_0
4967 and then X_Size > Y_Size
4968 then
4969 Error_Msg_NE
4970 ("?& overlays smaller object", ACCR.N, ACCR.X);
4971 Error_Msg_N
4972 ("\?program execution may be erroneous", ACCR.N);
4973 Error_Msg_Uint_1 := X_Size;
4974 Error_Msg_NE
4975 ("\?size of & is ^", ACCR.N, ACCR.X);
4976 Error_Msg_Uint_1 := Y_Size;
4977 Error_Msg_NE
4978 ("\?size of & is ^", ACCR.N, ACCR.Y);
4979
4980 -- Check for inadequate alignment, both of the base object
4981 -- and of the offset, if any.
4982
4983 -- Note: we do not check the alignment if we gave a size
4984 -- warning, since it would likely be redundant.
4985
4986 elsif Y_Alignment /= Uint_0
4987 and then (Y_Alignment < X_Alignment
4988 or else (ACCR.Off
4989 and then
4990 Nkind (Expr) = N_Attribute_Reference
4991 and then
4992 Attribute_Name (Expr) = Name_Address
4993 and then
4994 Has_Compatible_Alignment
4995 (ACCR.X, Prefix (Expr))
4996 /= Known_Compatible))
4997 then
4998 Error_Msg_NE
4999 ("?specified address for& may be inconsistent "
5000 & "with alignment",
5001 ACCR.N, ACCR.X);
5002 Error_Msg_N
5003 ("\?program execution may be erroneous (RM 13.3(27))",
5004 ACCR.N);
5005 Error_Msg_Uint_1 := X_Alignment;
5006 Error_Msg_NE
5007 ("\?alignment of & is ^",
5008 ACCR.N, ACCR.X);
5009 Error_Msg_Uint_1 := Y_Alignment;
5010 Error_Msg_NE
5011 ("\?alignment of & is ^",
5012 ACCR.N, ACCR.Y);
5013 if Y_Alignment >= X_Alignment then
5014 Error_Msg_N
5015 ("\?but offset is not multiple of alignment",
5016 ACCR.N);
5017 end if;
5018 end if;
5019 end if;
5020 end;
5021 end loop;
5022 end Validate_Address_Clauses;
5023
5024 -----------------------------------
5025 -- Validate_Unchecked_Conversion --
5026 -----------------------------------
5027
5028 procedure Validate_Unchecked_Conversion
5029 (N : Node_Id;
5030 Act_Unit : Entity_Id)
5031 is
5032 Source : Entity_Id;
5033 Target : Entity_Id;
5034 Vnode : Node_Id;
5035
5036 begin
5037 -- Obtain source and target types. Note that we call Ancestor_Subtype
5038 -- here because the processing for generic instantiation always makes
5039 -- subtypes, and we want the original frozen actual types.
5040
5041 -- If we are dealing with private types, then do the check on their
5042 -- fully declared counterparts if the full declarations have been
5043 -- encountered (they don't have to be visible, but they must exist!)
5044
5045 Source := Ancestor_Subtype (Etype (First_Formal (Act_Unit)));
5046
5047 if Is_Private_Type (Source)
5048 and then Present (Underlying_Type (Source))
5049 then
5050 Source := Underlying_Type (Source);
5051 end if;
5052
5053 Target := Ancestor_Subtype (Etype (Act_Unit));
5054
5055 -- If either type is generic, the instantiation happens within a generic
5056 -- unit, and there is nothing to check. The proper check
5057 -- will happen when the enclosing generic is instantiated.
5058
5059 if Is_Generic_Type (Source) or else Is_Generic_Type (Target) then
5060 return;
5061 end if;
5062
5063 if Is_Private_Type (Target)
5064 and then Present (Underlying_Type (Target))
5065 then
5066 Target := Underlying_Type (Target);
5067 end if;
5068
5069 -- Source may be unconstrained array, but not target
5070
5071 if Is_Array_Type (Target)
5072 and then not Is_Constrained (Target)
5073 then
5074 Error_Msg_N
5075 ("unchecked conversion to unconstrained array not allowed", N);
5076 return;
5077 end if;
5078
5079 -- Warn if conversion between two different convention pointers
5080
5081 if Is_Access_Type (Target)
5082 and then Is_Access_Type (Source)
5083 and then Convention (Target) /= Convention (Source)
5084 and then Warn_On_Unchecked_Conversion
5085 then
5086 -- Give warnings for subprogram pointers only on most targets. The
5087 -- exception is VMS, where data pointers can have different lengths
5088 -- depending on the pointer convention.
5089
5090 if Is_Access_Subprogram_Type (Target)
5091 or else Is_Access_Subprogram_Type (Source)
5092 or else OpenVMS_On_Target
5093 then
5094 Error_Msg_N
5095 ("?conversion between pointers with different conventions!", N);
5096 end if;
5097 end if;
5098
5099 -- Warn if one of the operands is Ada.Calendar.Time. Do not emit a
5100 -- warning when compiling GNAT-related sources.
5101
5102 if Warn_On_Unchecked_Conversion
5103 and then not In_Predefined_Unit (N)
5104 and then RTU_Loaded (Ada_Calendar)
5105 and then
5106 (Chars (Source) = Name_Time
5107 or else
5108 Chars (Target) = Name_Time)
5109 then
5110 -- If Ada.Calendar is loaded and the name of one of the operands is
5111 -- Time, there is a good chance that this is Ada.Calendar.Time.
5112
5113 declare
5114 Calendar_Time : constant Entity_Id :=
5115 Full_View (RTE (RO_CA_Time));
5116 begin
5117 pragma Assert (Present (Calendar_Time));
5118
5119 if Source = Calendar_Time
5120 or else Target = Calendar_Time
5121 then
5122 Error_Msg_N
5123 ("?representation of 'Time values may change between " &
5124 "'G'N'A'T versions", N);
5125 end if;
5126 end;
5127 end if;
5128
5129 -- Make entry in unchecked conversion table for later processing by
5130 -- Validate_Unchecked_Conversions, which will check sizes and alignments
5131 -- (using values set by the back-end where possible). This is only done
5132 -- if the appropriate warning is active.
5133
5134 if Warn_On_Unchecked_Conversion then
5135 Unchecked_Conversions.Append
5136 (New_Val => UC_Entry'
5137 (Eloc => Sloc (N),
5138 Source => Source,
5139 Target => Target));
5140
5141 -- If both sizes are known statically now, then back end annotation
5142 -- is not required to do a proper check but if either size is not
5143 -- known statically, then we need the annotation.
5144
5145 if Known_Static_RM_Size (Source)
5146 and then Known_Static_RM_Size (Target)
5147 then
5148 null;
5149 else
5150 Back_Annotate_Rep_Info := True;
5151 end if;
5152 end if;
5153
5154 -- If unchecked conversion to access type, and access type is declared
5155 -- in the same unit as the unchecked conversion, then set the
5156 -- No_Strict_Aliasing flag (no strict aliasing is implicit in this
5157 -- situation).
5158
5159 if Is_Access_Type (Target) and then
5160 In_Same_Source_Unit (Target, N)
5161 then
5162 Set_No_Strict_Aliasing (Implementation_Base_Type (Target));
5163 end if;
5164
5165 -- Generate N_Validate_Unchecked_Conversion node for back end in
5166 -- case the back end needs to perform special validation checks.
5167
5168 -- Shouldn't this be in Exp_Ch13, since the check only gets done
5169 -- if we have full expansion and the back end is called ???
5170
5171 Vnode :=
5172 Make_Validate_Unchecked_Conversion (Sloc (N));
5173 Set_Source_Type (Vnode, Source);
5174 Set_Target_Type (Vnode, Target);
5175
5176 -- If the unchecked conversion node is in a list, just insert before it.
5177 -- If not we have some strange case, not worth bothering about.
5178
5179 if Is_List_Member (N) then
5180 Insert_After (N, Vnode);
5181 end if;
5182 end Validate_Unchecked_Conversion;
5183
5184 ------------------------------------
5185 -- Validate_Unchecked_Conversions --
5186 ------------------------------------
5187
5188 procedure Validate_Unchecked_Conversions is
5189 begin
5190 for N in Unchecked_Conversions.First .. Unchecked_Conversions.Last loop
5191 declare
5192 T : UC_Entry renames Unchecked_Conversions.Table (N);
5193
5194 Eloc : constant Source_Ptr := T.Eloc;
5195 Source : constant Entity_Id := T.Source;
5196 Target : constant Entity_Id := T.Target;
5197
5198 Source_Siz : Uint;
5199 Target_Siz : Uint;
5200
5201 begin
5202 -- This validation check, which warns if we have unequal sizes for
5203 -- unchecked conversion, and thus potentially implementation
5204 -- dependent semantics, is one of the few occasions on which we
5205 -- use the official RM size instead of Esize. See description in
5206 -- Einfo "Handling of Type'Size Values" for details.
5207
5208 if Serious_Errors_Detected = 0
5209 and then Known_Static_RM_Size (Source)
5210 and then Known_Static_RM_Size (Target)
5211
5212 -- Don't do the check if warnings off for either type, note the
5213 -- deliberate use of OR here instead of OR ELSE to get the flag
5214 -- Warnings_Off_Used set for both types if appropriate.
5215
5216 and then not (Has_Warnings_Off (Source)
5217 or
5218 Has_Warnings_Off (Target))
5219 then
5220 Source_Siz := RM_Size (Source);
5221 Target_Siz := RM_Size (Target);
5222
5223 if Source_Siz /= Target_Siz then
5224 Error_Msg
5225 ("?types for unchecked conversion have different sizes!",
5226 Eloc);
5227
5228 if All_Errors_Mode then
5229 Error_Msg_Name_1 := Chars (Source);
5230 Error_Msg_Uint_1 := Source_Siz;
5231 Error_Msg_Name_2 := Chars (Target);
5232 Error_Msg_Uint_2 := Target_Siz;
5233 Error_Msg ("\size of % is ^, size of % is ^?", Eloc);
5234
5235 Error_Msg_Uint_1 := UI_Abs (Source_Siz - Target_Siz);
5236
5237 if Is_Discrete_Type (Source)
5238 and then Is_Discrete_Type (Target)
5239 then
5240 if Source_Siz > Target_Siz then
5241 Error_Msg
5242 ("\?^ high order bits of source will be ignored!",
5243 Eloc);
5244
5245 elsif Is_Unsigned_Type (Source) then
5246 Error_Msg
5247 ("\?source will be extended with ^ high order " &
5248 "zero bits?!", Eloc);
5249
5250 else
5251 Error_Msg
5252 ("\?source will be extended with ^ high order " &
5253 "sign bits!",
5254 Eloc);
5255 end if;
5256
5257 elsif Source_Siz < Target_Siz then
5258 if Is_Discrete_Type (Target) then
5259 if Bytes_Big_Endian then
5260 Error_Msg
5261 ("\?target value will include ^ undefined " &
5262 "low order bits!",
5263 Eloc);
5264 else
5265 Error_Msg
5266 ("\?target value will include ^ undefined " &
5267 "high order bits!",
5268 Eloc);
5269 end if;
5270
5271 else
5272 Error_Msg
5273 ("\?^ trailing bits of target value will be " &
5274 "undefined!", Eloc);
5275 end if;
5276
5277 else pragma Assert (Source_Siz > Target_Siz);
5278 Error_Msg
5279 ("\?^ trailing bits of source will be ignored!",
5280 Eloc);
5281 end if;
5282 end if;
5283 end if;
5284 end if;
5285
5286 -- If both types are access types, we need to check the alignment.
5287 -- If the alignment of both is specified, we can do it here.
5288
5289 if Serious_Errors_Detected = 0
5290 and then Ekind (Source) in Access_Kind
5291 and then Ekind (Target) in Access_Kind
5292 and then Target_Strict_Alignment
5293 and then Present (Designated_Type (Source))
5294 and then Present (Designated_Type (Target))
5295 then
5296 declare
5297 D_Source : constant Entity_Id := Designated_Type (Source);
5298 D_Target : constant Entity_Id := Designated_Type (Target);
5299
5300 begin
5301 if Known_Alignment (D_Source)
5302 and then Known_Alignment (D_Target)
5303 then
5304 declare
5305 Source_Align : constant Uint := Alignment (D_Source);
5306 Target_Align : constant Uint := Alignment (D_Target);
5307
5308 begin
5309 if Source_Align < Target_Align
5310 and then not Is_Tagged_Type (D_Source)
5311
5312 -- Suppress warning if warnings suppressed on either
5313 -- type or either designated type. Note the use of
5314 -- OR here instead of OR ELSE. That is intentional,
5315 -- we would like to set flag Warnings_Off_Used in
5316 -- all types for which warnings are suppressed.
5317
5318 and then not (Has_Warnings_Off (D_Source)
5319 or
5320 Has_Warnings_Off (D_Target)
5321 or
5322 Has_Warnings_Off (Source)
5323 or
5324 Has_Warnings_Off (Target))
5325 then
5326 Error_Msg_Uint_1 := Target_Align;
5327 Error_Msg_Uint_2 := Source_Align;
5328 Error_Msg_Node_1 := D_Target;
5329 Error_Msg_Node_2 := D_Source;
5330 Error_Msg
5331 ("?alignment of & (^) is stricter than " &
5332 "alignment of & (^)!", Eloc);
5333 Error_Msg
5334 ("\?resulting access value may have invalid " &
5335 "alignment!", Eloc);
5336 end if;
5337 end;
5338 end if;
5339 end;
5340 end if;
5341 end;
5342 end loop;
5343 end Validate_Unchecked_Conversions;
5344
5345 end Sem_Ch13;