[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-2011, 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 Aspects; use Aspects;
27 with Atree; use Atree;
28 with Checks; use Checks;
29 with Einfo; use Einfo;
30 with Elists; use Elists;
31 with Errout; use Errout;
32 with Exp_Disp; use Exp_Disp;
33 with Exp_Tss; use Exp_Tss;
34 with Exp_Util; use Exp_Util;
35 with Lib; use Lib;
36 with Lib.Xref; use Lib.Xref;
37 with Namet; use Namet;
38 with Nlists; use Nlists;
39 with Nmake; use Nmake;
40 with Opt; use Opt;
41 with Restrict; use Restrict;
42 with Rident; use Rident;
43 with Rtsfind; use Rtsfind;
44 with Sem; use Sem;
45 with Sem_Aux; use Sem_Aux;
46 with Sem_Ch3; use Sem_Ch3;
47 with Sem_Ch6; use Sem_Ch6;
48 with Sem_Ch8; use Sem_Ch8;
49 with Sem_Eval; use Sem_Eval;
50 with Sem_Res; use Sem_Res;
51 with Sem_Type; use Sem_Type;
52 with Sem_Util; use Sem_Util;
53 with Sem_Warn; use Sem_Warn;
54 with Sinput; use Sinput;
55 with Snames; use Snames;
56 with Stand; use Stand;
57 with Sinfo; use Sinfo;
58 with Stringt; use Stringt;
59 with Targparm; use Targparm;
60 with Ttypes; use Ttypes;
61 with Tbuild; use Tbuild;
62 with Urealp; use Urealp;
63 with Warnsw; use Warnsw;
64
65 with GNAT.Heap_Sort_G;
66
67 package body Sem_Ch13 is
68
69 SSU : constant Pos := System_Storage_Unit;
70 -- Convenient short hand for commonly used constant
71
72 -----------------------
73 -- Local Subprograms --
74 -----------------------
75
76 procedure Alignment_Check_For_Size_Change (Typ : Entity_Id; Size : Uint);
77 -- This routine is called after setting one of the sizes of type entity
78 -- Typ to Size. The purpose is to deal with the situation of a derived
79 -- type whose inherited alignment is no longer appropriate for the new
80 -- size value. In this case, we reset the Alignment to unknown.
81
82 procedure Build_Predicate_Function (Typ : Entity_Id; N : Node_Id);
83 -- If Typ has predicates (indicated by Has_Predicates being set for Typ,
84 -- then either there are pragma Invariant entries on the rep chain for the
85 -- type (note that Predicate aspects are converted to pragma Predicate), or
86 -- there are inherited aspects from a parent type, or ancestor subtypes.
87 -- This procedure builds the spec and body for the Predicate function that
88 -- tests these predicates. N is the freeze node for the type. The spec of
89 -- the function is inserted before the freeze node, and the body of the
90 -- function is inserted after the freeze node.
91
92 procedure Build_Static_Predicate
93 (Typ : Entity_Id;
94 Expr : Node_Id;
95 Nam : Name_Id);
96 -- Given a predicated type Typ, where Typ is a discrete static subtype,
97 -- whose predicate expression is Expr, tests if Expr is a static predicate,
98 -- and if so, builds the predicate range list. Nam is the name of the one
99 -- argument to the predicate function. Occurrences of the type name in the
100 -- predicate expression have been replaced by identifier references to this
101 -- name, which is unique, so any identifier with Chars matching Nam must be
102 -- a reference to the type. If the predicate is non-static, this procedure
103 -- returns doing nothing. If the predicate is static, then the predicate
104 -- list is stored in Static_Predicate (Typ), and the Expr is rewritten as
105 -- a canonicalized membership operation.
106
107 function Get_Alignment_Value (Expr : Node_Id) return Uint;
108 -- Given the expression for an alignment value, returns the corresponding
109 -- Uint value. If the value is inappropriate, then error messages are
110 -- posted as required, and a value of No_Uint is returned.
111
112 function Is_Operational_Item (N : Node_Id) return Boolean;
113 -- A specification for a stream attribute is allowed before the full type
114 -- is declared, as explained in AI-00137 and the corrigendum. Attributes
115 -- that do not specify a representation characteristic are operational
116 -- attributes.
117
118 procedure New_Stream_Subprogram
119 (N : Node_Id;
120 Ent : Entity_Id;
121 Subp : Entity_Id;
122 Nam : TSS_Name_Type);
123 -- Create a subprogram renaming of a given stream attribute to the
124 -- designated subprogram and then in the tagged case, provide this as a
125 -- primitive operation, or in the non-tagged case make an appropriate TSS
126 -- entry. This is more properly an expansion activity than just semantics,
127 -- but the presence of user-defined stream functions for limited types is a
128 -- legality check, which is why this takes place here rather than in
129 -- exp_ch13, where it was previously. Nam indicates the name of the TSS
130 -- function to be generated.
131 --
132 -- To avoid elaboration anomalies with freeze nodes, for untagged types
133 -- we generate both a subprogram declaration and a subprogram renaming
134 -- declaration, so that the attribute specification is handled as a
135 -- renaming_as_body. For tagged types, the specification is one of the
136 -- primitive specs.
137
138 generic
139 with procedure Replace_Type_Reference (N : Node_Id);
140 procedure Replace_Type_References_Generic (N : Node_Id; TName : Name_Id);
141 -- This is used to scan an expression for a predicate or invariant aspect
142 -- replacing occurrences of the name TName (the name of the subtype to
143 -- which the aspect applies) with appropriate references to the parameter
144 -- of the predicate function or invariant procedure. The procedure passed
145 -- as a generic parameter does the actual replacement of node N, which is
146 -- either a simple direct reference to TName, or a selected component that
147 -- represents an appropriately qualified occurrence of TName.
148
149 procedure Set_Biased
150 (E : Entity_Id;
151 N : Node_Id;
152 Msg : String;
153 Biased : Boolean := True);
154 -- If Biased is True, sets Has_Biased_Representation flag for E, and
155 -- outputs a warning message at node N if Warn_On_Biased_Representation is
156 -- is True. This warning inserts the string Msg to describe the construct
157 -- causing biasing.
158
159 ----------------------------------------------
160 -- Table for Validate_Unchecked_Conversions --
161 ----------------------------------------------
162
163 -- The following table collects unchecked conversions for validation.
164 -- Entries are made by Validate_Unchecked_Conversion and then the
165 -- call to Validate_Unchecked_Conversions does the actual error
166 -- checking and posting of warnings. The reason for this delayed
167 -- processing is to take advantage of back-annotations of size and
168 -- alignment values performed by the back end.
169
170 -- Note: the reason we store a Source_Ptr value instead of a Node_Id
171 -- is that by the time Validate_Unchecked_Conversions is called, Sprint
172 -- will already have modified all Sloc values if the -gnatD option is set.
173
174 type UC_Entry is record
175 Eloc : Source_Ptr; -- node used for posting warnings
176 Source : Entity_Id; -- source type for unchecked conversion
177 Target : Entity_Id; -- target type for unchecked conversion
178 end record;
179
180 package Unchecked_Conversions is new Table.Table (
181 Table_Component_Type => UC_Entry,
182 Table_Index_Type => Int,
183 Table_Low_Bound => 1,
184 Table_Initial => 50,
185 Table_Increment => 200,
186 Table_Name => "Unchecked_Conversions");
187
188 ----------------------------------------
189 -- Table for Validate_Address_Clauses --
190 ----------------------------------------
191
192 -- If an address clause has the form
193
194 -- for X'Address use Expr
195
196 -- where Expr is of the form Y'Address or recursively is a reference
197 -- to a constant of either of these forms, and X and Y are entities of
198 -- objects, then if Y has a smaller alignment than X, that merits a
199 -- warning about possible bad alignment. The following table collects
200 -- address clauses of this kind. We put these in a table so that they
201 -- can be checked after the back end has completed annotation of the
202 -- alignments of objects, since we can catch more cases that way.
203
204 type Address_Clause_Check_Record is record
205 N : Node_Id;
206 -- The address clause
207
208 X : Entity_Id;
209 -- The entity of the object overlaying Y
210
211 Y : Entity_Id;
212 -- The entity of the object being overlaid
213
214 Off : Boolean;
215 -- Whether the address is offset within Y
216 end record;
217
218 package Address_Clause_Checks is new Table.Table (
219 Table_Component_Type => Address_Clause_Check_Record,
220 Table_Index_Type => Int,
221 Table_Low_Bound => 1,
222 Table_Initial => 20,
223 Table_Increment => 200,
224 Table_Name => "Address_Clause_Checks");
225
226 -----------------------------------------
227 -- Adjust_Record_For_Reverse_Bit_Order --
228 -----------------------------------------
229
230 procedure Adjust_Record_For_Reverse_Bit_Order (R : Entity_Id) is
231 Comp : Node_Id;
232 CC : Node_Id;
233
234 begin
235 -- Processing depends on version of Ada
236
237 -- For Ada 95, we just renumber bits within a storage unit. We do the
238 -- same for Ada 83 mode, since we recognize the Bit_Order attribute in
239 -- Ada 83, and are free to add this extension.
240
241 if Ada_Version < Ada_2005 then
242 Comp := First_Component_Or_Discriminant (R);
243 while Present (Comp) loop
244 CC := Component_Clause (Comp);
245
246 -- If component clause is present, then deal with the non-default
247 -- bit order case for Ada 95 mode.
248
249 -- We only do this processing for the base type, and in fact that
250 -- is important, since otherwise if there are record subtypes, we
251 -- could reverse the bits once for each subtype, which is wrong.
252
253 if Present (CC)
254 and then Ekind (R) = E_Record_Type
255 then
256 declare
257 CFB : constant Uint := Component_Bit_Offset (Comp);
258 CSZ : constant Uint := Esize (Comp);
259 CLC : constant Node_Id := Component_Clause (Comp);
260 Pos : constant Node_Id := Position (CLC);
261 FB : constant Node_Id := First_Bit (CLC);
262
263 Storage_Unit_Offset : constant Uint :=
264 CFB / System_Storage_Unit;
265
266 Start_Bit : constant Uint :=
267 CFB mod System_Storage_Unit;
268
269 begin
270 -- Cases where field goes over storage unit boundary
271
272 if Start_Bit + CSZ > System_Storage_Unit then
273
274 -- Allow multi-byte field but generate warning
275
276 if Start_Bit mod System_Storage_Unit = 0
277 and then CSZ mod System_Storage_Unit = 0
278 then
279 Error_Msg_N
280 ("multi-byte field specified with non-standard"
281 & " Bit_Order?", CLC);
282
283 if Bytes_Big_Endian then
284 Error_Msg_N
285 ("bytes are not reversed "
286 & "(component is big-endian)?", CLC);
287 else
288 Error_Msg_N
289 ("bytes are not reversed "
290 & "(component is little-endian)?", CLC);
291 end if;
292
293 -- Do not allow non-contiguous field
294
295 else
296 Error_Msg_N
297 ("attempt to specify non-contiguous field "
298 & "not permitted", CLC);
299 Error_Msg_N
300 ("\caused by non-standard Bit_Order "
301 & "specified", CLC);
302 Error_Msg_N
303 ("\consider possibility of using "
304 & "Ada 2005 mode here", CLC);
305 end if;
306
307 -- Case where field fits in one storage unit
308
309 else
310 -- Give warning if suspicious component clause
311
312 if Intval (FB) >= System_Storage_Unit
313 and then Warn_On_Reverse_Bit_Order
314 then
315 Error_Msg_N
316 ("?Bit_Order clause does not affect " &
317 "byte ordering", Pos);
318 Error_Msg_Uint_1 :=
319 Intval (Pos) + Intval (FB) /
320 System_Storage_Unit;
321 Error_Msg_N
322 ("?position normalized to ^ before bit " &
323 "order interpreted", Pos);
324 end if;
325
326 -- Here is where we fix up the Component_Bit_Offset value
327 -- to account for the reverse bit order. Some examples of
328 -- what needs to be done are:
329
330 -- First_Bit .. Last_Bit Component_Bit_Offset
331 -- old new old new
332
333 -- 0 .. 0 7 .. 7 0 7
334 -- 0 .. 1 6 .. 7 0 6
335 -- 0 .. 2 5 .. 7 0 5
336 -- 0 .. 7 0 .. 7 0 4
337
338 -- 1 .. 1 6 .. 6 1 6
339 -- 1 .. 4 3 .. 6 1 3
340 -- 4 .. 7 0 .. 3 4 0
341
342 -- The rule is that the first bit is is obtained by
343 -- subtracting the old ending bit from storage_unit - 1.
344
345 Set_Component_Bit_Offset
346 (Comp,
347 (Storage_Unit_Offset * System_Storage_Unit) +
348 (System_Storage_Unit - 1) -
349 (Start_Bit + CSZ - 1));
350
351 Set_Normalized_First_Bit
352 (Comp,
353 Component_Bit_Offset (Comp) mod
354 System_Storage_Unit);
355 end if;
356 end;
357 end if;
358
359 Next_Component_Or_Discriminant (Comp);
360 end loop;
361
362 -- For Ada 2005, we do machine scalar processing, as fully described In
363 -- AI-133. This involves gathering all components which start at the
364 -- same byte offset and processing them together. Same approach is still
365 -- valid in later versions including Ada 2012.
366
367 else
368 declare
369 Max_Machine_Scalar_Size : constant Uint :=
370 UI_From_Int
371 (Standard_Long_Long_Integer_Size);
372 -- We use this as the maximum machine scalar size
373
374 Num_CC : Natural;
375 SSU : constant Uint := UI_From_Int (System_Storage_Unit);
376
377 begin
378 -- This first loop through components does two things. First it
379 -- deals with the case of components with component clauses whose
380 -- length is greater than the maximum machine scalar size (either
381 -- accepting them or rejecting as needed). Second, it counts the
382 -- number of components with component clauses whose length does
383 -- not exceed this maximum for later processing.
384
385 Num_CC := 0;
386 Comp := First_Component_Or_Discriminant (R);
387 while Present (Comp) loop
388 CC := Component_Clause (Comp);
389
390 if Present (CC) then
391 declare
392 Fbit : constant Uint :=
393 Static_Integer (First_Bit (CC));
394 Lbit : constant Uint :=
395 Static_Integer (Last_Bit (CC));
396
397 begin
398 -- Case of component with last bit >= max machine scalar
399
400 if Lbit >= Max_Machine_Scalar_Size then
401
402 -- This is allowed only if first bit is zero, and
403 -- last bit + 1 is a multiple of storage unit size.
404
405 if Fbit = 0 and then (Lbit + 1) mod SSU = 0 then
406
407 -- This is the case to give a warning if enabled
408
409 if Warn_On_Reverse_Bit_Order then
410 Error_Msg_N
411 ("multi-byte field specified with "
412 & " non-standard Bit_Order?", CC);
413
414 if Bytes_Big_Endian then
415 Error_Msg_N
416 ("\bytes are not reversed "
417 & "(component is big-endian)?", CC);
418 else
419 Error_Msg_N
420 ("\bytes are not reversed "
421 & "(component is little-endian)?", CC);
422 end if;
423 end if;
424
425 -- Give error message for RM 13.4.1(10) violation
426
427 else
428 Error_Msg_FE
429 ("machine scalar rules not followed for&",
430 First_Bit (CC), Comp);
431
432 Error_Msg_Uint_1 := Lbit;
433 Error_Msg_Uint_2 := Max_Machine_Scalar_Size;
434 Error_Msg_F
435 ("\last bit (^) exceeds maximum machine "
436 & "scalar size (^)",
437 First_Bit (CC));
438
439 if (Lbit + 1) mod SSU /= 0 then
440 Error_Msg_Uint_1 := SSU;
441 Error_Msg_F
442 ("\and is not a multiple of Storage_Unit (^) "
443 & "(RM 13.4.1(10))",
444 First_Bit (CC));
445
446 else
447 Error_Msg_Uint_1 := Fbit;
448 Error_Msg_F
449 ("\and first bit (^) is non-zero "
450 & "(RM 13.4.1(10))",
451 First_Bit (CC));
452 end if;
453 end if;
454
455 -- OK case of machine scalar related component clause,
456 -- For now, just count them.
457
458 else
459 Num_CC := Num_CC + 1;
460 end if;
461 end;
462 end if;
463
464 Next_Component_Or_Discriminant (Comp);
465 end loop;
466
467 -- We need to sort the component clauses on the basis of the
468 -- Position values in the clause, so we can group clauses with
469 -- the same Position. together to determine the relevant machine
470 -- scalar size.
471
472 Sort_CC : declare
473 Comps : array (0 .. Num_CC) of Entity_Id;
474 -- Array to collect component and discriminant entities. The
475 -- data starts at index 1, the 0'th entry is for the sort
476 -- routine.
477
478 function CP_Lt (Op1, Op2 : Natural) return Boolean;
479 -- Compare routine for Sort
480
481 procedure CP_Move (From : Natural; To : Natural);
482 -- Move routine for Sort
483
484 package Sorting is new GNAT.Heap_Sort_G (CP_Move, CP_Lt);
485
486 Start : Natural;
487 Stop : Natural;
488 -- Start and stop positions in the component list of the set of
489 -- components with the same starting position (that constitute
490 -- components in a single machine scalar).
491
492 MaxL : Uint;
493 -- Maximum last bit value of any component in this set
494
495 MSS : Uint;
496 -- Corresponding machine scalar size
497
498 -----------
499 -- CP_Lt --
500 -----------
501
502 function CP_Lt (Op1, Op2 : Natural) return Boolean is
503 begin
504 return Position (Component_Clause (Comps (Op1))) <
505 Position (Component_Clause (Comps (Op2)));
506 end CP_Lt;
507
508 -------------
509 -- CP_Move --
510 -------------
511
512 procedure CP_Move (From : Natural; To : Natural) is
513 begin
514 Comps (To) := Comps (From);
515 end CP_Move;
516
517 -- Start of processing for Sort_CC
518
519 begin
520 -- Collect the machine scalar relevant component clauses
521
522 Num_CC := 0;
523 Comp := First_Component_Or_Discriminant (R);
524 while Present (Comp) loop
525 declare
526 CC : constant Node_Id := Component_Clause (Comp);
527
528 begin
529 -- Collect only component clauses whose last bit is less
530 -- than machine scalar size. Any component clause whose
531 -- last bit exceeds this value does not take part in
532 -- machine scalar layout considerations. The test for
533 -- Error_Posted makes sure we exclude component clauses
534 -- for which we already posted an error.
535
536 if Present (CC)
537 and then not Error_Posted (Last_Bit (CC))
538 and then Static_Integer (Last_Bit (CC)) <
539 Max_Machine_Scalar_Size
540 then
541 Num_CC := Num_CC + 1;
542 Comps (Num_CC) := Comp;
543 end if;
544 end;
545
546 Next_Component_Or_Discriminant (Comp);
547 end loop;
548
549 -- Sort by ascending position number
550
551 Sorting.Sort (Num_CC);
552
553 -- We now have all the components whose size does not exceed
554 -- the max machine scalar value, sorted by starting position.
555 -- In this loop we gather groups of clauses starting at the
556 -- same position, to process them in accordance with AI-133.
557
558 Stop := 0;
559 while Stop < Num_CC loop
560 Start := Stop + 1;
561 Stop := Start;
562 MaxL :=
563 Static_Integer
564 (Last_Bit (Component_Clause (Comps (Start))));
565 while Stop < Num_CC loop
566 if Static_Integer
567 (Position (Component_Clause (Comps (Stop + 1)))) =
568 Static_Integer
569 (Position (Component_Clause (Comps (Stop))))
570 then
571 Stop := Stop + 1;
572 MaxL :=
573 UI_Max
574 (MaxL,
575 Static_Integer
576 (Last_Bit
577 (Component_Clause (Comps (Stop)))));
578 else
579 exit;
580 end if;
581 end loop;
582
583 -- Now we have a group of component clauses from Start to
584 -- Stop whose positions are identical, and MaxL is the
585 -- maximum last bit value of any of these components.
586
587 -- We need to determine the corresponding machine scalar
588 -- size. This loop assumes that machine scalar sizes are
589 -- even, and that each possible machine scalar has twice
590 -- as many bits as the next smaller one.
591
592 MSS := Max_Machine_Scalar_Size;
593 while MSS mod 2 = 0
594 and then (MSS / 2) >= SSU
595 and then (MSS / 2) > MaxL
596 loop
597 MSS := MSS / 2;
598 end loop;
599
600 -- Here is where we fix up the Component_Bit_Offset value
601 -- to account for the reverse bit order. Some examples of
602 -- what needs to be done for the case of a machine scalar
603 -- size of 8 are:
604
605 -- First_Bit .. Last_Bit Component_Bit_Offset
606 -- old new old new
607
608 -- 0 .. 0 7 .. 7 0 7
609 -- 0 .. 1 6 .. 7 0 6
610 -- 0 .. 2 5 .. 7 0 5
611 -- 0 .. 7 0 .. 7 0 4
612
613 -- 1 .. 1 6 .. 6 1 6
614 -- 1 .. 4 3 .. 6 1 3
615 -- 4 .. 7 0 .. 3 4 0
616
617 -- The rule is that the first bit is obtained by subtracting
618 -- the old ending bit from machine scalar size - 1.
619
620 for C in Start .. Stop loop
621 declare
622 Comp : constant Entity_Id := Comps (C);
623 CC : constant Node_Id :=
624 Component_Clause (Comp);
625 LB : constant Uint :=
626 Static_Integer (Last_Bit (CC));
627 NFB : constant Uint := MSS - Uint_1 - LB;
628 NLB : constant Uint := NFB + Esize (Comp) - 1;
629 Pos : constant Uint :=
630 Static_Integer (Position (CC));
631
632 begin
633 if Warn_On_Reverse_Bit_Order then
634 Error_Msg_Uint_1 := MSS;
635 Error_Msg_N
636 ("info: reverse bit order in machine " &
637 "scalar of length^?", First_Bit (CC));
638 Error_Msg_Uint_1 := NFB;
639 Error_Msg_Uint_2 := NLB;
640
641 if Bytes_Big_Endian then
642 Error_Msg_NE
643 ("?\info: big-endian range for "
644 & "component & is ^ .. ^",
645 First_Bit (CC), Comp);
646 else
647 Error_Msg_NE
648 ("?\info: little-endian range "
649 & "for component & is ^ .. ^",
650 First_Bit (CC), Comp);
651 end if;
652 end if;
653
654 Set_Component_Bit_Offset (Comp, Pos * SSU + NFB);
655 Set_Normalized_First_Bit (Comp, NFB mod SSU);
656 end;
657 end loop;
658 end loop;
659 end Sort_CC;
660 end;
661 end if;
662 end Adjust_Record_For_Reverse_Bit_Order;
663
664 -------------------------------------
665 -- Alignment_Check_For_Size_Change --
666 -------------------------------------
667
668 procedure Alignment_Check_For_Size_Change (Typ : Entity_Id; Size : Uint) is
669 begin
670 -- If the alignment is known, and not set by a rep clause, and is
671 -- inconsistent with the size being set, then reset it to unknown,
672 -- we assume in this case that the size overrides the inherited
673 -- alignment, and that the alignment must be recomputed.
674
675 if Known_Alignment (Typ)
676 and then not Has_Alignment_Clause (Typ)
677 and then Size mod (Alignment (Typ) * SSU) /= 0
678 then
679 Init_Alignment (Typ);
680 end if;
681 end Alignment_Check_For_Size_Change;
682
683 -----------------------------------
684 -- Analyze_Aspect_Specifications --
685 -----------------------------------
686
687 procedure Analyze_Aspect_Specifications (N : Node_Id; E : Entity_Id) is
688 Aspect : Node_Id;
689 Aitem : Node_Id;
690 Ent : Node_Id;
691
692 L : constant List_Id := Aspect_Specifications (N);
693
694 Ins_Node : Node_Id := N;
695 -- Insert pragmas (except Pre/Post/Invariant/Predicate) after this node
696
697 -- The general processing involves building an attribute definition
698 -- clause or a pragma node that corresponds to the aspect. Then one
699 -- of two things happens:
700
701 -- If we are required to delay the evaluation of this aspect to the
702 -- freeze point, we attach the corresponding pragma/attribute definition
703 -- clause to the aspect specification node, which is then placed in the
704 -- Rep Item chain. In this case we mark the entity by setting the flag
705 -- Has_Delayed_Aspects and we evaluate the rep item at the freeze point.
706
707 -- If no delay is required, we just insert the pragma or attribute
708 -- after the declaration, and it will get processed by the normal
709 -- circuit. The From_Aspect_Specification flag is set on the pragma
710 -- or attribute definition node in either case to activate special
711 -- processing (e.g. not traversing the list of homonyms for inline).
712
713 Delay_Required : Boolean;
714 -- Set True if delay is required
715
716 begin
717 pragma Assert (Present (L));
718
719 -- Loop through aspects
720
721 Aspect := First (L);
722 Aspect_Loop : while Present (Aspect) loop
723 declare
724 Loc : constant Source_Ptr := Sloc (Aspect);
725 Id : constant Node_Id := Identifier (Aspect);
726 Expr : constant Node_Id := Expression (Aspect);
727 Nam : constant Name_Id := Chars (Id);
728 A_Id : constant Aspect_Id := Get_Aspect_Id (Nam);
729 Anod : Node_Id;
730
731 Eloc : Source_Ptr := Sloc (Expr);
732 -- Source location of expression, modified when we split PPC's
733
734 procedure Check_False_Aspect_For_Derived_Type;
735 -- This procedure checks for the case of a false aspect for a
736 -- derived type, which improperly tries to cancel an aspect
737 -- inherited from the parent;
738
739 -----------------------------------------
740 -- Check_False_Aspect_For_Derived_Type --
741 -----------------------------------------
742
743 procedure Check_False_Aspect_For_Derived_Type is
744 begin
745 -- We are only checking derived types
746
747 if not Is_Derived_Type (E) then
748 return;
749 end if;
750
751 case A_Id is
752 when Aspect_Atomic | Aspect_Shared =>
753 if not Is_Atomic (E) then
754 return;
755 end if;
756
757 when Aspect_Atomic_Components =>
758 if not Has_Atomic_Components (E) then
759 return;
760 end if;
761
762 when Aspect_Discard_Names =>
763 if not Discard_Names (E) then
764 return;
765 end if;
766
767 when Aspect_Pack =>
768 if not Is_Packed (E) then
769 return;
770 end if;
771
772 when Aspect_Unchecked_Union =>
773 if not Is_Unchecked_Union (E) then
774 return;
775 end if;
776
777 when Aspect_Volatile =>
778 if not Is_Volatile (E) then
779 return;
780 end if;
781
782 when Aspect_Volatile_Components =>
783 if not Has_Volatile_Components (E) then
784 return;
785 end if;
786
787 when others =>
788 return;
789 end case;
790
791 -- Fall through means we are canceling an inherited aspect
792
793 Error_Msg_Name_1 := Nam;
794 Error_Msg_NE
795 ("derived type& inherits aspect%, cannot cancel", Expr, E);
796 end Check_False_Aspect_For_Derived_Type;
797
798 -- Start of processing for Aspect_Loop
799
800 begin
801 -- Skip aspect if already analyzed (not clear if this is needed)
802
803 if Analyzed (Aspect) then
804 goto Continue;
805 end if;
806
807 Set_Analyzed (Aspect);
808 Set_Entity (Aspect, E);
809 Ent := New_Occurrence_Of (E, Sloc (Id));
810
811 -- Check for duplicate aspect. Note that the Comes_From_Source
812 -- test allows duplicate Pre/Post's that we generate internally
813 -- to escape being flagged here.
814
815 if No_Duplicates_Allowed (A_Id) then
816 Anod := First (L);
817 while Anod /= Aspect loop
818 if Same_Aspect
819 (A_Id, Get_Aspect_Id (Chars (Identifier (Anod))))
820 and then Comes_From_Source (Aspect)
821 then
822 Error_Msg_Name_1 := Nam;
823 Error_Msg_Sloc := Sloc (Anod);
824
825 -- Case of same aspect specified twice
826
827 if Class_Present (Anod) = Class_Present (Aspect) then
828 if not Class_Present (Anod) then
829 Error_Msg_NE
830 ("aspect% for & previously given#",
831 Id, E);
832 else
833 Error_Msg_NE
834 ("aspect `%''Class` for & previously given#",
835 Id, E);
836 end if;
837
838 -- Case of Pre and Pre'Class both specified
839
840 elsif Nam = Name_Pre then
841 if Class_Present (Aspect) then
842 Error_Msg_NE
843 ("aspect `Pre''Class` for & is not allowed here",
844 Id, E);
845 Error_Msg_NE
846 ("\since aspect `Pre` previously given#",
847 Id, E);
848
849 else
850 Error_Msg_NE
851 ("aspect `Pre` for & is not allowed here",
852 Id, E);
853 Error_Msg_NE
854 ("\since aspect `Pre''Class` previously given#",
855 Id, E);
856 end if;
857 end if;
858
859 -- Allowed case of X and X'Class both specified
860 end if;
861
862 Next (Anod);
863 end loop;
864 end if;
865
866 -- Copy expression for later processing by the procedures
867 -- Check_Aspect_At_[Freeze_Point | End_Of_Declarations]
868
869 Set_Entity (Id, New_Copy_Tree (Expr));
870
871 -- Processing based on specific aspect
872
873 case A_Id is
874
875 -- No_Aspect should be impossible
876
877 when No_Aspect =>
878 raise Program_Error;
879
880 -- Aspects taking an optional boolean argument. For all of
881 -- these we just create a matching pragma and insert it, if
882 -- the expression is missing or set to True. If the expression
883 -- is False, we can ignore the aspect with the exception that
884 -- in the case of a derived type, we must check for an illegal
885 -- attempt to cancel an inherited aspect.
886
887 when Boolean_Aspects =>
888 Set_Is_Boolean_Aspect (Aspect);
889
890 if Present (Expr)
891 and then Is_False (Static_Boolean (Expr))
892 then
893 Check_False_Aspect_For_Derived_Type;
894 goto Continue;
895 end if;
896
897 -- If True, build corresponding pragma node
898
899 Aitem :=
900 Make_Pragma (Loc,
901 Pragma_Argument_Associations => New_List (Ent),
902 Pragma_Identifier =>
903 Make_Identifier (Sloc (Id), Chars (Id)));
904
905 -- Never need to delay for boolean aspects
906
907 Delay_Required := False;
908
909 -- Library unit aspects. These are boolean aspects, but we
910 -- have to do special things with the insertion, since the
911 -- pragma belongs inside the declarations of a package.
912
913 when Library_Unit_Aspects =>
914 if Present (Expr)
915 and then Is_False (Static_Boolean (Expr))
916 then
917 goto Continue;
918 end if;
919
920 -- Build corresponding pragma node
921
922 Aitem :=
923 Make_Pragma (Loc,
924 Pragma_Argument_Associations => New_List (Ent),
925 Pragma_Identifier =>
926 Make_Identifier (Sloc (Id), Chars (Id)));
927
928 -- This requires special handling in the case of a package
929 -- declaration, the pragma needs to be inserted in the list
930 -- of declarations for the associated package. There is no
931 -- issue of visibility delay for these aspects.
932
933 if Nkind (N) = N_Package_Declaration then
934 if Nkind (Parent (N)) /= N_Compilation_Unit then
935 Error_Msg_N
936 ("incorrect context for library unit aspect&", Id);
937 else
938 Prepend
939 (Aitem, Visible_Declarations (Specification (N)));
940 end if;
941
942 goto Continue;
943 end if;
944
945 -- If not package declaration, no delay is required
946
947 Delay_Required := False;
948
949 -- Aspects related to container iterators. These aspects denote
950 -- subprograms, and thus must be delayed.
951
952 when Aspect_Constant_Indexing |
953 Aspect_Variable_Indexing =>
954
955 if not Is_Type (E) or else not Is_Tagged_Type (E) then
956 Error_Msg_N ("indexing applies to a tagged type", N);
957 end if;
958
959 Aitem :=
960 Make_Attribute_Definition_Clause (Loc,
961 Name => Ent,
962 Chars => Chars (Id),
963 Expression => Relocate_Node (Expr));
964
965 Delay_Required := True;
966 Set_Is_Delayed_Aspect (Aspect);
967
968 when Aspect_Default_Iterator |
969 Aspect_Iterator_Element =>
970
971 Aitem :=
972 Make_Attribute_Definition_Clause (Loc,
973 Name => Ent,
974 Chars => Chars (Id),
975 Expression => Relocate_Node (Expr));
976
977 Delay_Required := True;
978 Set_Is_Delayed_Aspect (Aspect);
979
980 when Aspect_Implicit_Dereference =>
981 if not Is_Type (E)
982 or else not Has_Discriminants (E)
983 then
984 Error_Msg_N
985 ("Aspect must apply to a type with discriminants", N);
986 goto Continue;
987
988 else
989 declare
990 Disc : Entity_Id;
991
992 begin
993 Disc := First_Discriminant (E);
994 while Present (Disc) loop
995 if Chars (Expr) = Chars (Disc)
996 and then Ekind (Etype (Disc)) =
997 E_Anonymous_Access_Type
998 then
999 Set_Has_Implicit_Dereference (E);
1000 Set_Has_Implicit_Dereference (Disc);
1001 goto Continue;
1002 end if;
1003
1004 Next_Discriminant (Disc);
1005 end loop;
1006
1007 -- Error if no proper access discriminant.
1008
1009 Error_Msg_NE
1010 ("not an access discriminant of&", Expr, E);
1011 end;
1012
1013 goto Continue;
1014 end if;
1015
1016 -- Aspects corresponding to attribute definition clauses
1017
1018 when Aspect_Address |
1019 Aspect_Alignment |
1020 Aspect_Bit_Order |
1021 Aspect_Component_Size |
1022 Aspect_External_Tag |
1023 Aspect_Input |
1024 Aspect_Machine_Radix |
1025 Aspect_Object_Size |
1026 Aspect_Output |
1027 Aspect_Read |
1028 Aspect_Size |
1029 Aspect_Storage_Pool |
1030 Aspect_Storage_Size |
1031 Aspect_Stream_Size |
1032 Aspect_Value_Size |
1033 Aspect_Write =>
1034
1035 -- Construct the attribute definition clause
1036
1037 Aitem :=
1038 Make_Attribute_Definition_Clause (Loc,
1039 Name => Ent,
1040 Chars => Chars (Id),
1041 Expression => Relocate_Node (Expr));
1042
1043 -- A delay is required except in the common case where
1044 -- the expression is a literal, in which case it is fine
1045 -- to take care of it right away.
1046
1047 if Nkind_In (Expr, N_Integer_Literal, N_String_Literal) then
1048 Delay_Required := False;
1049 else
1050 Delay_Required := True;
1051 Set_Is_Delayed_Aspect (Aspect);
1052 end if;
1053
1054 -- Aspects corresponding to pragmas with two arguments, where
1055 -- the first argument is a local name referring to the entity,
1056 -- and the second argument is the aspect definition expression
1057 -- which is an expression that does not get analyzed.
1058
1059 when Aspect_Suppress |
1060 Aspect_Unsuppress =>
1061
1062 -- Construct the pragma
1063
1064 Aitem :=
1065 Make_Pragma (Loc,
1066 Pragma_Argument_Associations => New_List (
1067 New_Occurrence_Of (E, Loc),
1068 Relocate_Node (Expr)),
1069 Pragma_Identifier =>
1070 Make_Identifier (Sloc (Id), Chars (Id)));
1071
1072 -- We don't have to play the delay game here, since the only
1073 -- values are check names which don't get analyzed anyway.
1074
1075 Delay_Required := False;
1076
1077 -- Aspects corresponding to pragmas with two arguments, where
1078 -- the second argument is a local name referring to the entity,
1079 -- and the first argument is the aspect definition expression.
1080
1081 when Aspect_Warnings =>
1082
1083 -- Construct the pragma
1084
1085 Aitem :=
1086 Make_Pragma (Loc,
1087 Pragma_Argument_Associations => New_List (
1088 Relocate_Node (Expr),
1089 New_Occurrence_Of (E, Loc)),
1090 Pragma_Identifier =>
1091 Make_Identifier (Sloc (Id), Chars (Id)),
1092 Class_Present => Class_Present (Aspect));
1093
1094 -- We don't have to play the delay game here, since the only
1095 -- values are ON/OFF which don't get analyzed anyway.
1096
1097 Delay_Required := False;
1098
1099 -- Default_Value and Default_Component_Value aspects. These
1100 -- are specially handled because they have no corresponding
1101 -- pragmas or attributes.
1102
1103 when Aspect_Default_Value | Aspect_Default_Component_Value =>
1104 Error_Msg_Name_1 := Chars (Id);
1105
1106 if not Is_Type (E) then
1107 Error_Msg_N ("aspect% can only apply to a type", Id);
1108 goto Continue;
1109
1110 elsif not Is_First_Subtype (E) then
1111 Error_Msg_N ("aspect% cannot apply to subtype", Id);
1112 goto Continue;
1113
1114 elsif A_Id = Aspect_Default_Value
1115 and then not Is_Scalar_Type (E)
1116 then
1117 Error_Msg_N
1118 ("aspect% can only be applied to scalar type", Id);
1119 goto Continue;
1120
1121 elsif A_Id = Aspect_Default_Component_Value then
1122 if not Is_Array_Type (E) then
1123 Error_Msg_N
1124 ("aspect% can only be applied to array type", Id);
1125 goto Continue;
1126 elsif not Is_Scalar_Type (Component_Type (E)) then
1127 Error_Msg_N
1128 ("aspect% requires scalar components", Id);
1129 goto Continue;
1130 end if;
1131 end if;
1132
1133 Aitem := Empty;
1134 Delay_Required := True;
1135 Set_Is_Delayed_Aspect (Aspect);
1136 Set_Has_Default_Aspect (Base_Type (Entity (Ent)));
1137
1138 -- Aspects Pre/Post generate Precondition/Postcondition pragmas
1139 -- with a first argument that is the expression, and a second
1140 -- argument that is an informative message if the test fails.
1141 -- This is inserted right after the declaration, to get the
1142 -- required pragma placement. The processing for the pragmas
1143 -- takes care of the required delay.
1144
1145 when Pre_Post_Aspects => declare
1146 Pname : Name_Id;
1147
1148 begin
1149 if A_Id = Aspect_Pre or else A_Id = Aspect_Precondition then
1150 Pname := Name_Precondition;
1151 else
1152 Pname := Name_Postcondition;
1153 end if;
1154
1155 -- If the expressions is of the form A and then B, then
1156 -- we generate separate Pre/Post aspects for the separate
1157 -- clauses. Since we allow multiple pragmas, there is no
1158 -- problem in allowing multiple Pre/Post aspects internally.
1159 -- These should be treated in reverse order (B first and
1160 -- A second) since they are later inserted just after N in
1161 -- the order they are treated. This way, the pragma for A
1162 -- ends up preceding the pragma for B, which may have an
1163 -- importance for the error raised (either constraint error
1164 -- or precondition error).
1165
1166 -- We do not do this for Pre'Class, since we have to put
1167 -- these conditions together in a complex OR expression
1168
1169 if Pname = Name_Postcondition
1170 or else not Class_Present (Aspect)
1171 then
1172 while Nkind (Expr) = N_And_Then loop
1173 Insert_After (Aspect,
1174 Make_Aspect_Specification (Sloc (Left_Opnd (Expr)),
1175 Identifier => Identifier (Aspect),
1176 Expression => Relocate_Node (Left_Opnd (Expr)),
1177 Class_Present => Class_Present (Aspect),
1178 Split_PPC => True));
1179 Rewrite (Expr, Relocate_Node (Right_Opnd (Expr)));
1180 Eloc := Sloc (Expr);
1181 end loop;
1182 end if;
1183
1184 -- Build the precondition/postcondition pragma
1185
1186 Aitem :=
1187 Make_Pragma (Loc,
1188 Pragma_Identifier =>
1189 Make_Identifier (Sloc (Id), Pname),
1190 Class_Present => Class_Present (Aspect),
1191 Split_PPC => Split_PPC (Aspect),
1192 Pragma_Argument_Associations => New_List (
1193 Make_Pragma_Argument_Association (Eloc,
1194 Chars => Name_Check,
1195 Expression => Relocate_Node (Expr))));
1196
1197 -- Add message unless exception messages are suppressed
1198
1199 if not Opt.Exception_Locations_Suppressed then
1200 Append_To (Pragma_Argument_Associations (Aitem),
1201 Make_Pragma_Argument_Association (Eloc,
1202 Chars => Name_Message,
1203 Expression =>
1204 Make_String_Literal (Eloc,
1205 Strval => "failed "
1206 & Get_Name_String (Pname)
1207 & " from "
1208 & Build_Location_String (Eloc))));
1209 end if;
1210
1211 Set_From_Aspect_Specification (Aitem, True);
1212 Set_Is_Delayed_Aspect (Aspect);
1213
1214 -- For Pre/Post cases, insert immediately after the entity
1215 -- declaration, since that is the required pragma placement.
1216 -- Note that for these aspects, we do not have to worry
1217 -- about delay issues, since the pragmas themselves deal
1218 -- with delay of visibility for the expression analysis.
1219
1220 -- If the entity is a library-level subprogram, the pre/
1221 -- postconditions must be treated as late pragmas.
1222
1223 if Nkind (Parent (N)) = N_Compilation_Unit then
1224 Add_Global_Declaration (Aitem);
1225 else
1226 Insert_After (N, Aitem);
1227 end if;
1228
1229 goto Continue;
1230 end;
1231
1232 -- Invariant aspects generate a corresponding pragma with a
1233 -- first argument that is the entity, a second argument that is
1234 -- the expression and a third argument that is an appropriate
1235 -- message. This is inserted right after the declaration, to
1236 -- get the required pragma placement. The pragma processing
1237 -- takes care of the required delay.
1238
1239 when Aspect_Invariant |
1240 Aspect_Type_Invariant =>
1241
1242 -- Check placement legality
1243
1244 if not Nkind_In (N, N_Private_Type_Declaration,
1245 N_Private_Extension_Declaration)
1246 then
1247 Error_Msg_N
1248 ("invariant aspect must apply to a private type", N);
1249 end if;
1250
1251 -- Construct the pragma
1252
1253 Aitem :=
1254 Make_Pragma (Loc,
1255 Pragma_Argument_Associations =>
1256 New_List (Ent, Relocate_Node (Expr)),
1257 Class_Present => Class_Present (Aspect),
1258 Pragma_Identifier =>
1259 Make_Identifier (Sloc (Id), Name_Invariant));
1260
1261 -- Add message unless exception messages are suppressed
1262
1263 if not Opt.Exception_Locations_Suppressed then
1264 Append_To (Pragma_Argument_Associations (Aitem),
1265 Make_Pragma_Argument_Association (Eloc,
1266 Chars => Name_Message,
1267 Expression =>
1268 Make_String_Literal (Eloc,
1269 Strval => "failed invariant from "
1270 & Build_Location_String (Eloc))));
1271 end if;
1272
1273 Set_From_Aspect_Specification (Aitem, True);
1274 Set_Is_Delayed_Aspect (Aspect);
1275
1276 -- For Invariant case, insert immediately after the entity
1277 -- declaration. We do not have to worry about delay issues
1278 -- since the pragma processing takes care of this.
1279
1280 Insert_After (N, Aitem);
1281 goto Continue;
1282
1283 -- Predicate aspects generate a corresponding pragma with a
1284 -- first argument that is the entity, and the second argument
1285 -- is the expression.
1286
1287 when Aspect_Dynamic_Predicate |
1288 Aspect_Predicate |
1289 Aspect_Static_Predicate =>
1290
1291 -- Construct the pragma (always a pragma Predicate, with
1292 -- flags recording whether it is static/dynamic).
1293
1294 Aitem :=
1295 Make_Pragma (Loc,
1296 Pragma_Argument_Associations =>
1297 New_List (Ent, Relocate_Node (Expr)),
1298 Class_Present => Class_Present (Aspect),
1299 Pragma_Identifier =>
1300 Make_Identifier (Sloc (Id), Name_Predicate));
1301
1302 Set_From_Aspect_Specification (Aitem, True);
1303
1304 -- Set special flags for dynamic/static cases
1305
1306 if A_Id = Aspect_Dynamic_Predicate then
1307 Set_From_Dynamic_Predicate (Aitem);
1308 elsif A_Id = Aspect_Static_Predicate then
1309 Set_From_Static_Predicate (Aitem);
1310 end if;
1311
1312 -- Make sure we have a freeze node (it might otherwise be
1313 -- missing in cases like subtype X is Y, and we would not
1314 -- have a place to build the predicate function).
1315
1316 Set_Has_Predicates (E);
1317
1318 if Is_Private_Type (E)
1319 and then Present (Full_View (E))
1320 then
1321 Set_Has_Predicates (Full_View (E));
1322 Set_Has_Delayed_Aspects (Full_View (E));
1323 end if;
1324
1325 Ensure_Freeze_Node (E);
1326 Set_Is_Delayed_Aspect (Aspect);
1327 Delay_Required := True;
1328
1329 when Aspect_Test_Case => declare
1330 Args : List_Id;
1331 Comp_Expr : Node_Id;
1332 Comp_Assn : Node_Id;
1333
1334 begin
1335 Args := New_List;
1336
1337 if Nkind (Expr) /= N_Aggregate then
1338 Error_Msg_NE
1339 ("wrong syntax for aspect `Test_Case` for &", Id, E);
1340 goto Continue;
1341 end if;
1342
1343 Comp_Expr := First (Expressions (Expr));
1344 while Present (Comp_Expr) loop
1345 Append (Relocate_Node (Comp_Expr), Args);
1346 Next (Comp_Expr);
1347 end loop;
1348
1349 Comp_Assn := First (Component_Associations (Expr));
1350 while Present (Comp_Assn) loop
1351 if List_Length (Choices (Comp_Assn)) /= 1
1352 or else
1353 Nkind (First (Choices (Comp_Assn))) /= N_Identifier
1354 then
1355 Error_Msg_NE
1356 ("wrong syntax for aspect `Test_Case` for &", Id, E);
1357 goto Continue;
1358 end if;
1359
1360 Append (Make_Pragma_Argument_Association (
1361 Sloc => Sloc (Comp_Assn),
1362 Chars => Chars (First (Choices (Comp_Assn))),
1363 Expression => Relocate_Node (Expression (Comp_Assn))),
1364 Args);
1365 Next (Comp_Assn);
1366 end loop;
1367
1368 -- Build the test-case pragma
1369
1370 Aitem :=
1371 Make_Pragma (Loc,
1372 Pragma_Identifier =>
1373 Make_Identifier (Sloc (Id), Name_Test_Case),
1374 Pragma_Argument_Associations =>
1375 Args);
1376
1377 Set_From_Aspect_Specification (Aitem, True);
1378 Set_Is_Delayed_Aspect (Aspect);
1379
1380 -- Insert immediately after the entity declaration
1381
1382 Insert_After (N, Aitem);
1383
1384 goto Continue;
1385 end;
1386 end case;
1387
1388 -- If a delay is required, we delay the freeze (not much point in
1389 -- delaying the aspect if we don't delay the freeze!). The pragma
1390 -- or attribute clause if there is one is then attached to the
1391 -- aspect specification which is placed in the rep item list.
1392
1393 if Delay_Required then
1394 if Present (Aitem) then
1395 Set_From_Aspect_Specification (Aitem, True);
1396 Set_Is_Delayed_Aspect (Aitem);
1397 Set_Aspect_Rep_Item (Aspect, Aitem);
1398 end if;
1399
1400 Ensure_Freeze_Node (E);
1401 Set_Has_Delayed_Aspects (E);
1402 Record_Rep_Item (E, Aspect);
1403
1404 -- If no delay required, insert the pragma/clause in the tree
1405
1406 else
1407 Set_From_Aspect_Specification (Aitem, True);
1408
1409 -- If this is a compilation unit, we will put the pragma in
1410 -- the Pragmas_After list of the N_Compilation_Unit_Aux node.
1411
1412 if Nkind (Parent (Ins_Node)) = N_Compilation_Unit then
1413 declare
1414 Aux : constant Node_Id :=
1415 Aux_Decls_Node (Parent (Ins_Node));
1416
1417 begin
1418 pragma Assert (Nkind (Aux) = N_Compilation_Unit_Aux);
1419
1420 if No (Pragmas_After (Aux)) then
1421 Set_Pragmas_After (Aux, Empty_List);
1422 end if;
1423
1424 -- For Pre_Post put at start of list, otherwise at end
1425
1426 if A_Id in Pre_Post_Aspects then
1427 Prepend (Aitem, Pragmas_After (Aux));
1428 else
1429 Append (Aitem, Pragmas_After (Aux));
1430 end if;
1431 end;
1432
1433 -- Here if not compilation unit case
1434
1435 else
1436 -- For Pre/Post cases, insert immediately after the entity
1437 -- declaration, since that is the required pragma placement.
1438
1439 if A_Id in Pre_Post_Aspects then
1440 Insert_After (N, Aitem);
1441
1442 -- For all other cases, insert in sequence
1443
1444 else
1445 Insert_After (Ins_Node, Aitem);
1446 Ins_Node := Aitem;
1447 end if;
1448 end if;
1449 end if;
1450 end;
1451
1452 <<Continue>>
1453 Next (Aspect);
1454 end loop Aspect_Loop;
1455 end Analyze_Aspect_Specifications;
1456
1457 -----------------------
1458 -- Analyze_At_Clause --
1459 -----------------------
1460
1461 -- An at clause is replaced by the corresponding Address attribute
1462 -- definition clause that is the preferred approach in Ada 95.
1463
1464 procedure Analyze_At_Clause (N : Node_Id) is
1465 CS : constant Boolean := Comes_From_Source (N);
1466
1467 begin
1468 -- This is an obsolescent feature
1469
1470 Check_Restriction (No_Obsolescent_Features, N);
1471
1472 if Warn_On_Obsolescent_Feature then
1473 Error_Msg_N
1474 ("at clause is an obsolescent feature (RM J.7(2))?", N);
1475 Error_Msg_N
1476 ("\use address attribute definition clause instead?", N);
1477 end if;
1478
1479 -- Rewrite as address clause
1480
1481 Rewrite (N,
1482 Make_Attribute_Definition_Clause (Sloc (N),
1483 Name => Identifier (N),
1484 Chars => Name_Address,
1485 Expression => Expression (N)));
1486
1487 -- We preserve Comes_From_Source, since logically the clause still
1488 -- comes from the source program even though it is changed in form.
1489
1490 Set_Comes_From_Source (N, CS);
1491
1492 -- Analyze rewritten clause
1493
1494 Analyze_Attribute_Definition_Clause (N);
1495 end Analyze_At_Clause;
1496
1497 -----------------------------------------
1498 -- Analyze_Attribute_Definition_Clause --
1499 -----------------------------------------
1500
1501 procedure Analyze_Attribute_Definition_Clause (N : Node_Id) is
1502 Loc : constant Source_Ptr := Sloc (N);
1503 Nam : constant Node_Id := Name (N);
1504 Attr : constant Name_Id := Chars (N);
1505 Expr : constant Node_Id := Expression (N);
1506 Id : constant Attribute_Id := Get_Attribute_Id (Attr);
1507
1508 Ent : Entity_Id;
1509 -- The entity of Nam after it is analyzed. In the case of an incomplete
1510 -- type, this is the underlying type.
1511
1512 U_Ent : Entity_Id;
1513 -- The underlying entity to which the attribute applies. Generally this
1514 -- is the Underlying_Type of Ent, except in the case where the clause
1515 -- applies to full view of incomplete type or private type in which case
1516 -- U_Ent is just a copy of Ent.
1517
1518 FOnly : Boolean := False;
1519 -- Reset to True for subtype specific attribute (Alignment, Size)
1520 -- and for stream attributes, i.e. those cases where in the call
1521 -- to Rep_Item_Too_Late, FOnly is set True so that only the freezing
1522 -- rules are checked. Note that the case of stream attributes is not
1523 -- clear from the RM, but see AI95-00137. Also, the RM seems to
1524 -- disallow Storage_Size for derived task types, but that is also
1525 -- clearly unintentional.
1526
1527 procedure Analyze_Stream_TSS_Definition (TSS_Nam : TSS_Name_Type);
1528 -- Common processing for 'Read, 'Write, 'Input and 'Output attribute
1529 -- definition clauses.
1530
1531 function Duplicate_Clause return Boolean;
1532 -- This routine checks if the aspect for U_Ent being given by attribute
1533 -- definition clause N is for an aspect that has already been specified,
1534 -- and if so gives an error message. If there is a duplicate, True is
1535 -- returned, otherwise if there is no error, False is returned.
1536
1537 procedure Check_Indexing_Functions;
1538 -- Check that the function in Constant_Indexing or Variable_Indexing
1539 -- attribute has the proper type structure. If the name is overloaded,
1540 -- check that all interpretations are legal.
1541
1542 procedure Check_Iterator_Functions;
1543 -- Check that there is a single function in Default_Iterator attribute
1544 -- that has the proper type structure.
1545
1546 function Check_Primitive_Function (Subp : Entity_Id) return Boolean;
1547 -- Common legality check for the previoous two.
1548
1549 -----------------------------------
1550 -- Analyze_Stream_TSS_Definition --
1551 -----------------------------------
1552
1553 procedure Analyze_Stream_TSS_Definition (TSS_Nam : TSS_Name_Type) is
1554 Subp : Entity_Id := Empty;
1555 I : Interp_Index;
1556 It : Interp;
1557 Pnam : Entity_Id;
1558
1559 Is_Read : constant Boolean := (TSS_Nam = TSS_Stream_Read);
1560 -- True for Read attribute, false for other attributes
1561
1562 function Has_Good_Profile (Subp : Entity_Id) return Boolean;
1563 -- Return true if the entity is a subprogram with an appropriate
1564 -- profile for the attribute being defined.
1565
1566 ----------------------
1567 -- Has_Good_Profile --
1568 ----------------------
1569
1570 function Has_Good_Profile (Subp : Entity_Id) return Boolean is
1571 F : Entity_Id;
1572 Is_Function : constant Boolean := (TSS_Nam = TSS_Stream_Input);
1573 Expected_Ekind : constant array (Boolean) of Entity_Kind :=
1574 (False => E_Procedure, True => E_Function);
1575 Typ : Entity_Id;
1576
1577 begin
1578 if Ekind (Subp) /= Expected_Ekind (Is_Function) then
1579 return False;
1580 end if;
1581
1582 F := First_Formal (Subp);
1583
1584 if No (F)
1585 or else Ekind (Etype (F)) /= E_Anonymous_Access_Type
1586 or else Designated_Type (Etype (F)) /=
1587 Class_Wide_Type (RTE (RE_Root_Stream_Type))
1588 then
1589 return False;
1590 end if;
1591
1592 if not Is_Function then
1593 Next_Formal (F);
1594
1595 declare
1596 Expected_Mode : constant array (Boolean) of Entity_Kind :=
1597 (False => E_In_Parameter,
1598 True => E_Out_Parameter);
1599 begin
1600 if Parameter_Mode (F) /= Expected_Mode (Is_Read) then
1601 return False;
1602 end if;
1603 end;
1604
1605 Typ := Etype (F);
1606
1607 else
1608 Typ := Etype (Subp);
1609 end if;
1610
1611 return Base_Type (Typ) = Base_Type (Ent)
1612 and then No (Next_Formal (F));
1613 end Has_Good_Profile;
1614
1615 -- Start of processing for Analyze_Stream_TSS_Definition
1616
1617 begin
1618 FOnly := True;
1619
1620 if not Is_Type (U_Ent) then
1621 Error_Msg_N ("local name must be a subtype", Nam);
1622 return;
1623 end if;
1624
1625 Pnam := TSS (Base_Type (U_Ent), TSS_Nam);
1626
1627 -- If Pnam is present, it can be either inherited from an ancestor
1628 -- type (in which case it is legal to redefine it for this type), or
1629 -- be a previous definition of the attribute for the same type (in
1630 -- which case it is illegal).
1631
1632 -- In the first case, it will have been analyzed already, and we
1633 -- can check that its profile does not match the expected profile
1634 -- for a stream attribute of U_Ent. In the second case, either Pnam
1635 -- has been analyzed (and has the expected profile), or it has not
1636 -- been analyzed yet (case of a type that has not been frozen yet
1637 -- and for which the stream attribute has been set using Set_TSS).
1638
1639 if Present (Pnam)
1640 and then (No (First_Entity (Pnam)) or else Has_Good_Profile (Pnam))
1641 then
1642 Error_Msg_Sloc := Sloc (Pnam);
1643 Error_Msg_Name_1 := Attr;
1644 Error_Msg_N ("% attribute already defined #", Nam);
1645 return;
1646 end if;
1647
1648 Analyze (Expr);
1649
1650 if Is_Entity_Name (Expr) then
1651 if not Is_Overloaded (Expr) then
1652 if Has_Good_Profile (Entity (Expr)) then
1653 Subp := Entity (Expr);
1654 end if;
1655
1656 else
1657 Get_First_Interp (Expr, I, It);
1658 while Present (It.Nam) loop
1659 if Has_Good_Profile (It.Nam) then
1660 Subp := It.Nam;
1661 exit;
1662 end if;
1663
1664 Get_Next_Interp (I, It);
1665 end loop;
1666 end if;
1667 end if;
1668
1669 if Present (Subp) then
1670 if Is_Abstract_Subprogram (Subp) then
1671 Error_Msg_N ("stream subprogram must not be abstract", Expr);
1672 return;
1673 end if;
1674
1675 Set_Entity (Expr, Subp);
1676 Set_Etype (Expr, Etype (Subp));
1677
1678 New_Stream_Subprogram (N, U_Ent, Subp, TSS_Nam);
1679
1680 else
1681 Error_Msg_Name_1 := Attr;
1682 Error_Msg_N ("incorrect expression for% attribute", Expr);
1683 end if;
1684 end Analyze_Stream_TSS_Definition;
1685
1686 ------------------------------
1687 -- Check_Indexing_Functions --
1688 ------------------------------
1689
1690 procedure Check_Indexing_Functions is
1691 procedure Check_One_Function (Subp : Entity_Id);
1692 -- Check one possible interpretation
1693
1694 ------------------------
1695 -- Check_One_Function --
1696 ------------------------
1697
1698 procedure Check_One_Function (Subp : Entity_Id) is
1699 begin
1700 if not Check_Primitive_Function (Subp) then
1701 Error_Msg_NE
1702 ("aspect Indexing requires a function that applies to type&",
1703 Subp, Ent);
1704 end if;
1705
1706 if not Has_Implicit_Dereference (Etype (Subp)) then
1707 Error_Msg_N
1708 ("function for indexing must return a reference type", Subp);
1709 end if;
1710 end Check_One_Function;
1711
1712 -- Start of processing for Check_Indexing_Functions
1713
1714 begin
1715 if In_Instance then
1716 return;
1717 end if;
1718
1719 Analyze (Expr);
1720
1721 if not Is_Overloaded (Expr) then
1722 Check_One_Function (Entity (Expr));
1723
1724 else
1725 declare
1726 I : Interp_Index;
1727 It : Interp;
1728
1729 begin
1730 Get_First_Interp (Expr, I, It);
1731 while Present (It.Nam) loop
1732
1733 -- Note that analysis will have added the interpretation
1734 -- that corresponds to the dereference. We only check the
1735 -- subprogram itself.
1736
1737 if Is_Overloadable (It.Nam) then
1738 Check_One_Function (It.Nam);
1739 end if;
1740
1741 Get_Next_Interp (I, It);
1742 end loop;
1743 end;
1744 end if;
1745 end Check_Indexing_Functions;
1746
1747 ------------------------------
1748 -- Check_Iterator_Functions --
1749 ------------------------------
1750
1751 procedure Check_Iterator_Functions is
1752 Default : Entity_Id;
1753
1754 function Valid_Default_Iterator (Subp : Entity_Id) return Boolean;
1755 -- Check one possible interpretation.
1756
1757 ----------------------------
1758 -- Valid_Default_Iterator --
1759 ----------------------------
1760
1761 function Valid_Default_Iterator (Subp : Entity_Id) return Boolean is
1762 Formal : Entity_Id;
1763
1764 begin
1765 if not Check_Primitive_Function (Subp) then
1766 return False;
1767 else
1768 Formal := First_Formal (Subp);
1769 end if;
1770
1771 Formal := Next_Formal (Formal);
1772
1773 -- I don't see why the if is required here, we will return
1774 -- True anyway if Present (Formal) is false on first loop ???
1775
1776 if No (Formal) then
1777 return True;
1778
1779 else
1780 while Present (Formal) loop
1781 if No (Expression (Parent (Formal))) then
1782 return False;
1783 end if;
1784
1785 Next_Formal (Formal);
1786 end loop;
1787 end if;
1788
1789 return True;
1790 end Valid_Default_Iterator;
1791
1792 -- Start of processing for Check_Iterator_Functions
1793
1794 begin
1795 Analyze (Expr);
1796
1797 if not Is_Entity_Name (Expr) then
1798 Error_Msg_N ("aspect Iterator must be a function name", Expr);
1799 end if;
1800
1801 if not Is_Overloaded (Expr) then
1802 if not Check_Primitive_Function (Entity (Expr)) then
1803 Error_Msg_NE
1804 ("aspect Indexing requires a function that applies to type&",
1805 Entity (Expr), Ent);
1806 end if;
1807
1808 if not Valid_Default_Iterator (Entity (Expr)) then
1809 Error_Msg_N ("improper function for default iterator", Expr);
1810 end if;
1811
1812 else
1813 Default := Empty;
1814 declare
1815 I : Interp_Index;
1816 It : Interp;
1817
1818 begin
1819 Get_First_Interp (Expr, I, It);
1820 while Present (It.Nam) loop
1821 if not Check_Primitive_Function (It.Nam)
1822 or else Valid_Default_Iterator (It.Nam)
1823 then
1824 Remove_Interp (I);
1825
1826 elsif Present (Default) then
1827 Error_Msg_N ("default iterator must be unique", Expr);
1828
1829 else
1830 Default := It.Nam;
1831 end if;
1832
1833 Get_Next_Interp (I, It);
1834 end loop;
1835 end;
1836
1837 if Present (Default) then
1838 Set_Entity (Expr, Default);
1839 Set_Is_Overloaded (Expr, False);
1840 end if;
1841 end if;
1842 end Check_Iterator_Functions;
1843
1844 -------------------------------
1845 -- Check_Primitive_Function --
1846 -------------------------------
1847
1848 function Check_Primitive_Function (Subp : Entity_Id) return Boolean is
1849 Ctrl : Entity_Id;
1850
1851 begin
1852 if Ekind (Subp) /= E_Function then
1853 return False;
1854 end if;
1855
1856 if No (First_Formal (Subp)) then
1857 return False;
1858 else
1859 Ctrl := Etype (First_Formal (Subp));
1860 end if;
1861
1862 if Ctrl = Ent
1863 or else Ctrl = Class_Wide_Type (Ent)
1864 or else
1865 (Ekind (Ctrl) = E_Anonymous_Access_Type
1866 and then
1867 (Designated_Type (Ctrl) = Ent
1868 or else Designated_Type (Ctrl) = Class_Wide_Type (Ent)))
1869 then
1870 null;
1871
1872 else
1873 return False;
1874 end if;
1875
1876 return True;
1877 end Check_Primitive_Function;
1878
1879 ----------------------
1880 -- Duplicate_Clause --
1881 ----------------------
1882
1883 function Duplicate_Clause return Boolean is
1884 A : Node_Id;
1885
1886 begin
1887 -- Nothing to do if this attribute definition clause comes from
1888 -- an aspect specification, since we could not be duplicating an
1889 -- explicit clause, and we dealt with the case of duplicated aspects
1890 -- in Analyze_Aspect_Specifications.
1891
1892 if From_Aspect_Specification (N) then
1893 return False;
1894 end if;
1895
1896 -- Otherwise current clause may duplicate previous clause or a
1897 -- previously given aspect specification for the same aspect.
1898
1899 A := Get_Rep_Item_For_Entity (U_Ent, Chars (N));
1900
1901 if Present (A) then
1902 if Entity (A) = U_Ent then
1903 Error_Msg_Name_1 := Chars (N);
1904 Error_Msg_Sloc := Sloc (A);
1905 Error_Msg_NE ("aspect% for & previously given#", N, U_Ent);
1906 return True;
1907 end if;
1908 end if;
1909
1910 return False;
1911 end Duplicate_Clause;
1912
1913 -- Start of processing for Analyze_Attribute_Definition_Clause
1914
1915 begin
1916 -- The following code is a defense against recursion. Not clear that
1917 -- this can happen legitimately, but perhaps some error situations
1918 -- can cause it, and we did see this recursion during testing.
1919
1920 if Analyzed (N) then
1921 return;
1922 else
1923 Set_Analyzed (N, True);
1924 end if;
1925
1926 -- Process Ignore_Rep_Clauses option (we also ignore rep clauses in
1927 -- CodePeer mode, since they are not relevant in that context).
1928
1929 if Ignore_Rep_Clauses or CodePeer_Mode then
1930 case Id is
1931
1932 -- The following should be ignored. They do not affect legality
1933 -- and may be target dependent. The basic idea of -gnatI is to
1934 -- ignore any rep clauses that may be target dependent but do not
1935 -- affect legality (except possibly to be rejected because they
1936 -- are incompatible with the compilation target).
1937
1938 when Attribute_Alignment |
1939 Attribute_Bit_Order |
1940 Attribute_Component_Size |
1941 Attribute_Machine_Radix |
1942 Attribute_Object_Size |
1943 Attribute_Size |
1944 Attribute_Stream_Size |
1945 Attribute_Value_Size =>
1946 Rewrite (N, Make_Null_Statement (Sloc (N)));
1947 return;
1948
1949 -- We do not want too ignore 'Small in CodePeer_Mode, since it
1950 -- has an impact on the exact computations performed.
1951
1952 -- Perhaps 'Small should also not be ignored by
1953 -- Ignore_Rep_Clauses ???
1954
1955 when Attribute_Small =>
1956 if Ignore_Rep_Clauses then
1957 Rewrite (N, Make_Null_Statement (Sloc (N)));
1958 return;
1959 end if;
1960
1961 -- The following should not be ignored, because in the first place
1962 -- they are reasonably portable, and should not cause problems in
1963 -- compiling code from another target, and also they do affect
1964 -- legality, e.g. failing to provide a stream attribute for a
1965 -- type may make a program illegal.
1966
1967 when Attribute_External_Tag |
1968 Attribute_Input |
1969 Attribute_Output |
1970 Attribute_Read |
1971 Attribute_Storage_Pool |
1972 Attribute_Storage_Size |
1973 Attribute_Write =>
1974 null;
1975
1976 -- Other cases are errors ("attribute& cannot be set with
1977 -- definition clause"), which will be caught below.
1978
1979 when others =>
1980 null;
1981 end case;
1982 end if;
1983
1984 Analyze (Nam);
1985 Ent := Entity (Nam);
1986
1987 if Rep_Item_Too_Early (Ent, N) then
1988 return;
1989 end if;
1990
1991 -- Rep clause applies to full view of incomplete type or private type if
1992 -- we have one (if not, this is a premature use of the type). However,
1993 -- certain semantic checks need to be done on the specified entity (i.e.
1994 -- the private view), so we save it in Ent.
1995
1996 if Is_Private_Type (Ent)
1997 and then Is_Derived_Type (Ent)
1998 and then not Is_Tagged_Type (Ent)
1999 and then No (Full_View (Ent))
2000 then
2001 -- If this is a private type whose completion is a derivation from
2002 -- another private type, there is no full view, and the attribute
2003 -- belongs to the type itself, not its underlying parent.
2004
2005 U_Ent := Ent;
2006
2007 elsif Ekind (Ent) = E_Incomplete_Type then
2008
2009 -- The attribute applies to the full view, set the entity of the
2010 -- attribute definition accordingly.
2011
2012 Ent := Underlying_Type (Ent);
2013 U_Ent := Ent;
2014 Set_Entity (Nam, Ent);
2015
2016 else
2017 U_Ent := Underlying_Type (Ent);
2018 end if;
2019
2020 -- Complete other routine error checks
2021
2022 if Etype (Nam) = Any_Type then
2023 return;
2024
2025 elsif Scope (Ent) /= Current_Scope then
2026 Error_Msg_N ("entity must be declared in this scope", Nam);
2027 return;
2028
2029 elsif No (U_Ent) then
2030 U_Ent := Ent;
2031
2032 elsif Is_Type (U_Ent)
2033 and then not Is_First_Subtype (U_Ent)
2034 and then Id /= Attribute_Object_Size
2035 and then Id /= Attribute_Value_Size
2036 and then not From_At_Mod (N)
2037 then
2038 Error_Msg_N ("cannot specify attribute for subtype", Nam);
2039 return;
2040 end if;
2041
2042 Set_Entity (N, U_Ent);
2043
2044 -- Switch on particular attribute
2045
2046 case Id is
2047
2048 -------------
2049 -- Address --
2050 -------------
2051
2052 -- Address attribute definition clause
2053
2054 when Attribute_Address => Address : begin
2055
2056 -- A little error check, catch for X'Address use X'Address;
2057
2058 if Nkind (Nam) = N_Identifier
2059 and then Nkind (Expr) = N_Attribute_Reference
2060 and then Attribute_Name (Expr) = Name_Address
2061 and then Nkind (Prefix (Expr)) = N_Identifier
2062 and then Chars (Nam) = Chars (Prefix (Expr))
2063 then
2064 Error_Msg_NE
2065 ("address for & is self-referencing", Prefix (Expr), Ent);
2066 return;
2067 end if;
2068
2069 -- Not that special case, carry on with analysis of expression
2070
2071 Analyze_And_Resolve (Expr, RTE (RE_Address));
2072
2073 -- Even when ignoring rep clauses we need to indicate that the
2074 -- entity has an address clause and thus it is legal to declare
2075 -- it imported.
2076
2077 if Ignore_Rep_Clauses then
2078 if Ekind_In (U_Ent, E_Variable, E_Constant) then
2079 Record_Rep_Item (U_Ent, N);
2080 end if;
2081
2082 return;
2083 end if;
2084
2085 if Duplicate_Clause then
2086 null;
2087
2088 -- Case of address clause for subprogram
2089
2090 elsif Is_Subprogram (U_Ent) then
2091 if Has_Homonym (U_Ent) then
2092 Error_Msg_N
2093 ("address clause cannot be given " &
2094 "for overloaded subprogram",
2095 Nam);
2096 return;
2097 end if;
2098
2099 -- For subprograms, all address clauses are permitted, and we
2100 -- mark the subprogram as having a deferred freeze so that Gigi
2101 -- will not elaborate it too soon.
2102
2103 -- Above needs more comments, what is too soon about???
2104
2105 Set_Has_Delayed_Freeze (U_Ent);
2106
2107 -- Case of address clause for entry
2108
2109 elsif Ekind (U_Ent) = E_Entry then
2110 if Nkind (Parent (N)) = N_Task_Body then
2111 Error_Msg_N
2112 ("entry address must be specified in task spec", Nam);
2113 return;
2114 end if;
2115
2116 -- For entries, we require a constant address
2117
2118 Check_Constant_Address_Clause (Expr, U_Ent);
2119
2120 -- Special checks for task types
2121
2122 if Is_Task_Type (Scope (U_Ent))
2123 and then Comes_From_Source (Scope (U_Ent))
2124 then
2125 Error_Msg_N
2126 ("?entry address declared for entry in task type", N);
2127 Error_Msg_N
2128 ("\?only one task can be declared of this type", N);
2129 end if;
2130
2131 -- Entry address clauses are obsolescent
2132
2133 Check_Restriction (No_Obsolescent_Features, N);
2134
2135 if Warn_On_Obsolescent_Feature then
2136 Error_Msg_N
2137 ("attaching interrupt to task entry is an " &
2138 "obsolescent feature (RM J.7.1)?", N);
2139 Error_Msg_N
2140 ("\use interrupt procedure instead?", N);
2141 end if;
2142
2143 -- Case of an address clause for a controlled object which we
2144 -- consider to be erroneous.
2145
2146 elsif Is_Controlled (Etype (U_Ent))
2147 or else Has_Controlled_Component (Etype (U_Ent))
2148 then
2149 Error_Msg_NE
2150 ("?controlled object& must not be overlaid", Nam, U_Ent);
2151 Error_Msg_N
2152 ("\?Program_Error will be raised at run time", Nam);
2153 Insert_Action (Declaration_Node (U_Ent),
2154 Make_Raise_Program_Error (Loc,
2155 Reason => PE_Overlaid_Controlled_Object));
2156 return;
2157
2158 -- Case of address clause for a (non-controlled) object
2159
2160 elsif
2161 Ekind (U_Ent) = E_Variable
2162 or else
2163 Ekind (U_Ent) = E_Constant
2164 then
2165 declare
2166 Expr : constant Node_Id := Expression (N);
2167 O_Ent : Entity_Id;
2168 Off : Boolean;
2169
2170 begin
2171 -- Exported variables cannot have an address clause, because
2172 -- this cancels the effect of the pragma Export.
2173
2174 if Is_Exported (U_Ent) then
2175 Error_Msg_N
2176 ("cannot export object with address clause", Nam);
2177 return;
2178 end if;
2179
2180 Find_Overlaid_Entity (N, O_Ent, Off);
2181
2182 -- Overlaying controlled objects is erroneous
2183
2184 if Present (O_Ent)
2185 and then (Has_Controlled_Component (Etype (O_Ent))
2186 or else Is_Controlled (Etype (O_Ent)))
2187 then
2188 Error_Msg_N
2189 ("?cannot overlay with controlled object", Expr);
2190 Error_Msg_N
2191 ("\?Program_Error will be raised at run time", Expr);
2192 Insert_Action (Declaration_Node (U_Ent),
2193 Make_Raise_Program_Error (Loc,
2194 Reason => PE_Overlaid_Controlled_Object));
2195 return;
2196
2197 elsif Present (O_Ent)
2198 and then Ekind (U_Ent) = E_Constant
2199 and then not Is_Constant_Object (O_Ent)
2200 then
2201 Error_Msg_N ("constant overlays a variable?", Expr);
2202
2203 elsif Present (Renamed_Object (U_Ent)) then
2204 Error_Msg_N
2205 ("address clause not allowed"
2206 & " for a renaming declaration (RM 13.1(6))", Nam);
2207 return;
2208
2209 -- Imported variables can have an address clause, but then
2210 -- the import is pretty meaningless except to suppress
2211 -- initializations, so we do not need such variables to
2212 -- be statically allocated (and in fact it causes trouble
2213 -- if the address clause is a local value).
2214
2215 elsif Is_Imported (U_Ent) then
2216 Set_Is_Statically_Allocated (U_Ent, False);
2217 end if;
2218
2219 -- We mark a possible modification of a variable with an
2220 -- address clause, since it is likely aliasing is occurring.
2221
2222 Note_Possible_Modification (Nam, Sure => False);
2223
2224 -- Here we are checking for explicit overlap of one variable
2225 -- by another, and if we find this then mark the overlapped
2226 -- variable as also being volatile to prevent unwanted
2227 -- optimizations. This is a significant pessimization so
2228 -- avoid it when there is an offset, i.e. when the object
2229 -- is composite; they cannot be optimized easily anyway.
2230
2231 if Present (O_Ent)
2232 and then Is_Object (O_Ent)
2233 and then not Off
2234 then
2235 Set_Treat_As_Volatile (O_Ent);
2236 end if;
2237
2238 -- Legality checks on the address clause for initialized
2239 -- objects is deferred until the freeze point, because
2240 -- a subsequent pragma might indicate that the object is
2241 -- imported and thus not initialized.
2242
2243 Set_Has_Delayed_Freeze (U_Ent);
2244
2245 -- If an initialization call has been generated for this
2246 -- object, it needs to be deferred to after the freeze node
2247 -- we have just now added, otherwise GIGI will see a
2248 -- reference to the variable (as actual to the IP call)
2249 -- before its definition.
2250
2251 declare
2252 Init_Call : constant Node_Id := Find_Init_Call (U_Ent, N);
2253 begin
2254 if Present (Init_Call) then
2255 Remove (Init_Call);
2256 Append_Freeze_Action (U_Ent, Init_Call);
2257 end if;
2258 end;
2259
2260 if Is_Exported (U_Ent) then
2261 Error_Msg_N
2262 ("& cannot be exported if an address clause is given",
2263 Nam);
2264 Error_Msg_N
2265 ("\define and export a variable " &
2266 "that holds its address instead",
2267 Nam);
2268 end if;
2269
2270 -- Entity has delayed freeze, so we will generate an
2271 -- alignment check at the freeze point unless suppressed.
2272
2273 if not Range_Checks_Suppressed (U_Ent)
2274 and then not Alignment_Checks_Suppressed (U_Ent)
2275 then
2276 Set_Check_Address_Alignment (N);
2277 end if;
2278
2279 -- Kill the size check code, since we are not allocating
2280 -- the variable, it is somewhere else.
2281
2282 Kill_Size_Check_Code (U_Ent);
2283
2284 -- If the address clause is of the form:
2285
2286 -- for Y'Address use X'Address
2287
2288 -- or
2289
2290 -- Const : constant Address := X'Address;
2291 -- ...
2292 -- for Y'Address use Const;
2293
2294 -- then we make an entry in the table for checking the size
2295 -- and alignment of the overlaying variable. We defer this
2296 -- check till after code generation to take full advantage
2297 -- of the annotation done by the back end. This entry is
2298 -- only made if the address clause comes from source.
2299
2300 -- If the entity has a generic type, the check will be
2301 -- performed in the instance if the actual type justifies
2302 -- it, and we do not insert the clause in the table to
2303 -- prevent spurious warnings.
2304
2305 if Address_Clause_Overlay_Warnings
2306 and then Comes_From_Source (N)
2307 and then Present (O_Ent)
2308 and then Is_Object (O_Ent)
2309 then
2310 if not Is_Generic_Type (Etype (U_Ent)) then
2311 Address_Clause_Checks.Append ((N, U_Ent, O_Ent, Off));
2312 end if;
2313
2314 -- If variable overlays a constant view, and we are
2315 -- warning on overlays, then mark the variable as
2316 -- overlaying a constant (we will give warnings later
2317 -- if this variable is assigned).
2318
2319 if Is_Constant_Object (O_Ent)
2320 and then Ekind (U_Ent) = E_Variable
2321 then
2322 Set_Overlays_Constant (U_Ent);
2323 end if;
2324 end if;
2325 end;
2326
2327 -- Not a valid entity for an address clause
2328
2329 else
2330 Error_Msg_N ("address cannot be given for &", Nam);
2331 end if;
2332 end Address;
2333
2334 ---------------
2335 -- Alignment --
2336 ---------------
2337
2338 -- Alignment attribute definition clause
2339
2340 when Attribute_Alignment => Alignment : declare
2341 Align : constant Uint := Get_Alignment_Value (Expr);
2342
2343 begin
2344 FOnly := True;
2345
2346 if not Is_Type (U_Ent)
2347 and then Ekind (U_Ent) /= E_Variable
2348 and then Ekind (U_Ent) /= E_Constant
2349 then
2350 Error_Msg_N ("alignment cannot be given for &", Nam);
2351
2352 elsif Duplicate_Clause then
2353 null;
2354
2355 elsif Align /= No_Uint then
2356 Set_Has_Alignment_Clause (U_Ent);
2357 Set_Alignment (U_Ent, Align);
2358
2359 -- For an array type, U_Ent is the first subtype. In that case,
2360 -- also set the alignment of the anonymous base type so that
2361 -- other subtypes (such as the itypes for aggregates of the
2362 -- type) also receive the expected alignment.
2363
2364 if Is_Array_Type (U_Ent) then
2365 Set_Alignment (Base_Type (U_Ent), Align);
2366 end if;
2367 end if;
2368 end Alignment;
2369
2370 ---------------
2371 -- Bit_Order --
2372 ---------------
2373
2374 -- Bit_Order attribute definition clause
2375
2376 when Attribute_Bit_Order => Bit_Order : declare
2377 begin
2378 if not Is_Record_Type (U_Ent) then
2379 Error_Msg_N
2380 ("Bit_Order can only be defined for record type", Nam);
2381
2382 elsif Duplicate_Clause then
2383 null;
2384
2385 else
2386 Analyze_And_Resolve (Expr, RTE (RE_Bit_Order));
2387
2388 if Etype (Expr) = Any_Type then
2389 return;
2390
2391 elsif not Is_Static_Expression (Expr) then
2392 Flag_Non_Static_Expr
2393 ("Bit_Order requires static expression!", Expr);
2394
2395 else
2396 if (Expr_Value (Expr) = 0) /= Bytes_Big_Endian then
2397 Set_Reverse_Bit_Order (U_Ent, True);
2398 end if;
2399 end if;
2400 end if;
2401 end Bit_Order;
2402
2403 --------------------
2404 -- Component_Size --
2405 --------------------
2406
2407 -- Component_Size attribute definition clause
2408
2409 when Attribute_Component_Size => Component_Size_Case : declare
2410 Csize : constant Uint := Static_Integer (Expr);
2411 Ctyp : Entity_Id;
2412 Btype : Entity_Id;
2413 Biased : Boolean;
2414 New_Ctyp : Entity_Id;
2415 Decl : Node_Id;
2416
2417 begin
2418 if not Is_Array_Type (U_Ent) then
2419 Error_Msg_N ("component size requires array type", Nam);
2420 return;
2421 end if;
2422
2423 Btype := Base_Type (U_Ent);
2424 Ctyp := Component_Type (Btype);
2425
2426 if Duplicate_Clause then
2427 null;
2428
2429 elsif Rep_Item_Too_Early (Btype, N) then
2430 null;
2431
2432 elsif Csize /= No_Uint then
2433 Check_Size (Expr, Ctyp, Csize, Biased);
2434
2435 -- For the biased case, build a declaration for a subtype that
2436 -- will be used to represent the biased subtype that reflects
2437 -- the biased representation of components. We need the subtype
2438 -- to get proper conversions on referencing elements of the
2439 -- array. Note: component size clauses are ignored in VM mode.
2440
2441 if VM_Target = No_VM then
2442 if Biased then
2443 New_Ctyp :=
2444 Make_Defining_Identifier (Loc,
2445 Chars =>
2446 New_External_Name (Chars (U_Ent), 'C', 0, 'T'));
2447
2448 Decl :=
2449 Make_Subtype_Declaration (Loc,
2450 Defining_Identifier => New_Ctyp,
2451 Subtype_Indication =>
2452 New_Occurrence_Of (Component_Type (Btype), Loc));
2453
2454 Set_Parent (Decl, N);
2455 Analyze (Decl, Suppress => All_Checks);
2456
2457 Set_Has_Delayed_Freeze (New_Ctyp, False);
2458 Set_Esize (New_Ctyp, Csize);
2459 Set_RM_Size (New_Ctyp, Csize);
2460 Init_Alignment (New_Ctyp);
2461 Set_Is_Itype (New_Ctyp, True);
2462 Set_Associated_Node_For_Itype (New_Ctyp, U_Ent);
2463
2464 Set_Component_Type (Btype, New_Ctyp);
2465 Set_Biased (New_Ctyp, N, "component size clause");
2466 end if;
2467
2468 Set_Component_Size (Btype, Csize);
2469
2470 -- For VM case, we ignore component size clauses
2471
2472 else
2473 -- Give a warning unless we are in GNAT mode, in which case
2474 -- the warning is suppressed since it is not useful.
2475
2476 if not GNAT_Mode then
2477 Error_Msg_N
2478 ("?component size ignored in this configuration", N);
2479 end if;
2480 end if;
2481
2482 -- Deal with warning on overridden size
2483
2484 if Warn_On_Overridden_Size
2485 and then Has_Size_Clause (Ctyp)
2486 and then RM_Size (Ctyp) /= Csize
2487 then
2488 Error_Msg_NE
2489 ("?component size overrides size clause for&",
2490 N, Ctyp);
2491 end if;
2492
2493 Set_Has_Component_Size_Clause (Btype, True);
2494 Set_Has_Non_Standard_Rep (Btype, True);
2495 end if;
2496 end Component_Size_Case;
2497
2498 -----------------------
2499 -- Constant_Indexing --
2500 -----------------------
2501
2502 when Attribute_Constant_Indexing =>
2503 Check_Indexing_Functions;
2504
2505 ----------------------
2506 -- Default_Iterator --
2507 ----------------------
2508
2509 when Attribute_Default_Iterator => Default_Iterator : declare
2510 Func : Entity_Id;
2511
2512 begin
2513 if not Is_Tagged_Type (U_Ent) then
2514 Error_Msg_N
2515 ("aspect Default_Iterator applies to tagged type", Nam);
2516 end if;
2517
2518 Check_Iterator_Functions;
2519
2520 Analyze (Expr);
2521
2522 if not Is_Entity_Name (Expr)
2523 or else Ekind (Entity (Expr)) /= E_Function
2524 then
2525 Error_Msg_N ("aspect Iterator must be a function", Expr);
2526 else
2527 Func := Entity (Expr);
2528 end if;
2529
2530 if No (First_Formal (Func))
2531 or else Etype (First_Formal (Func)) /= U_Ent
2532 then
2533 Error_Msg_NE
2534 ("Default Iterator must be a primitive of&", Func, U_Ent);
2535 end if;
2536 end Default_Iterator;
2537
2538 ------------------
2539 -- External_Tag --
2540 ------------------
2541
2542 when Attribute_External_Tag => External_Tag :
2543 begin
2544 if not Is_Tagged_Type (U_Ent) then
2545 Error_Msg_N ("should be a tagged type", Nam);
2546 end if;
2547
2548 if Duplicate_Clause then
2549 null;
2550
2551 else
2552 Analyze_And_Resolve (Expr, Standard_String);
2553
2554 if not Is_Static_Expression (Expr) then
2555 Flag_Non_Static_Expr
2556 ("static string required for tag name!", Nam);
2557 end if;
2558
2559 if VM_Target = No_VM then
2560 Set_Has_External_Tag_Rep_Clause (U_Ent);
2561 else
2562 Error_Msg_Name_1 := Attr;
2563 Error_Msg_N
2564 ("% attribute unsupported in this configuration", Nam);
2565 end if;
2566
2567 if not Is_Library_Level_Entity (U_Ent) then
2568 Error_Msg_NE
2569 ("?non-unique external tag supplied for &", N, U_Ent);
2570 Error_Msg_N
2571 ("?\same external tag applies to all subprogram calls", N);
2572 Error_Msg_N
2573 ("?\corresponding internal tag cannot be obtained", N);
2574 end if;
2575 end if;
2576 end External_Tag;
2577
2578 --------------------------
2579 -- Implicit_Dereference --
2580 --------------------------
2581
2582 when Attribute_Implicit_Dereference =>
2583
2584 -- Legality checks already performed at the point of
2585 -- the type declaration, aspect is not delayed.
2586
2587 null;
2588
2589 -----------
2590 -- Input --
2591 -----------
2592
2593 when Attribute_Input =>
2594 Analyze_Stream_TSS_Definition (TSS_Stream_Input);
2595 Set_Has_Specified_Stream_Input (Ent);
2596
2597 ----------------------
2598 -- Iterator_Element --
2599 ----------------------
2600
2601 when Attribute_Iterator_Element =>
2602 Analyze (Expr);
2603
2604 if not Is_Entity_Name (Expr)
2605 or else not Is_Type (Entity (Expr))
2606 then
2607 Error_Msg_N ("aspect Iterator_Element must be a type", Expr);
2608 end if;
2609
2610 -------------------
2611 -- Machine_Radix --
2612 -------------------
2613
2614 -- Machine radix attribute definition clause
2615
2616 when Attribute_Machine_Radix => Machine_Radix : declare
2617 Radix : constant Uint := Static_Integer (Expr);
2618
2619 begin
2620 if not Is_Decimal_Fixed_Point_Type (U_Ent) then
2621 Error_Msg_N ("decimal fixed-point type expected for &", Nam);
2622
2623 elsif Duplicate_Clause then
2624 null;
2625
2626 elsif Radix /= No_Uint then
2627 Set_Has_Machine_Radix_Clause (U_Ent);
2628 Set_Has_Non_Standard_Rep (Base_Type (U_Ent));
2629
2630 if Radix = 2 then
2631 null;
2632 elsif Radix = 10 then
2633 Set_Machine_Radix_10 (U_Ent);
2634 else
2635 Error_Msg_N ("machine radix value must be 2 or 10", Expr);
2636 end if;
2637 end if;
2638 end Machine_Radix;
2639
2640 -----------------
2641 -- Object_Size --
2642 -----------------
2643
2644 -- Object_Size attribute definition clause
2645
2646 when Attribute_Object_Size => Object_Size : declare
2647 Size : constant Uint := Static_Integer (Expr);
2648
2649 Biased : Boolean;
2650 pragma Warnings (Off, Biased);
2651
2652 begin
2653 if not Is_Type (U_Ent) then
2654 Error_Msg_N ("Object_Size cannot be given for &", Nam);
2655
2656 elsif Duplicate_Clause then
2657 null;
2658
2659 else
2660 Check_Size (Expr, U_Ent, Size, Biased);
2661
2662 if Size /= 8
2663 and then
2664 Size /= 16
2665 and then
2666 Size /= 32
2667 and then
2668 UI_Mod (Size, 64) /= 0
2669 then
2670 Error_Msg_N
2671 ("Object_Size must be 8, 16, 32, or multiple of 64",
2672 Expr);
2673 end if;
2674
2675 Set_Esize (U_Ent, Size);
2676 Set_Has_Object_Size_Clause (U_Ent);
2677 Alignment_Check_For_Size_Change (U_Ent, Size);
2678 end if;
2679 end Object_Size;
2680
2681 ------------
2682 -- Output --
2683 ------------
2684
2685 when Attribute_Output =>
2686 Analyze_Stream_TSS_Definition (TSS_Stream_Output);
2687 Set_Has_Specified_Stream_Output (Ent);
2688
2689 ----------
2690 -- Read --
2691 ----------
2692
2693 when Attribute_Read =>
2694 Analyze_Stream_TSS_Definition (TSS_Stream_Read);
2695 Set_Has_Specified_Stream_Read (Ent);
2696
2697 ----------
2698 -- Size --
2699 ----------
2700
2701 -- Size attribute definition clause
2702
2703 when Attribute_Size => Size : declare
2704 Size : constant Uint := Static_Integer (Expr);
2705 Etyp : Entity_Id;
2706 Biased : Boolean;
2707
2708 begin
2709 FOnly := True;
2710
2711 if Duplicate_Clause then
2712 null;
2713
2714 elsif not Is_Type (U_Ent)
2715 and then Ekind (U_Ent) /= E_Variable
2716 and then Ekind (U_Ent) /= E_Constant
2717 then
2718 Error_Msg_N ("size cannot be given for &", Nam);
2719
2720 elsif Is_Array_Type (U_Ent)
2721 and then not Is_Constrained (U_Ent)
2722 then
2723 Error_Msg_N
2724 ("size cannot be given for unconstrained array", Nam);
2725
2726 elsif Size /= No_Uint then
2727 if VM_Target /= No_VM and then not GNAT_Mode then
2728
2729 -- Size clause is not handled properly on VM targets.
2730 -- Display a warning unless we are in GNAT mode, in which
2731 -- case this is useless.
2732
2733 Error_Msg_N
2734 ("?size clauses are ignored in this configuration", N);
2735 end if;
2736
2737 if Is_Type (U_Ent) then
2738 Etyp := U_Ent;
2739 else
2740 Etyp := Etype (U_Ent);
2741 end if;
2742
2743 -- Check size, note that Gigi is in charge of checking that the
2744 -- size of an array or record type is OK. Also we do not check
2745 -- the size in the ordinary fixed-point case, since it is too
2746 -- early to do so (there may be subsequent small clause that
2747 -- affects the size). We can check the size if a small clause
2748 -- has already been given.
2749
2750 if not Is_Ordinary_Fixed_Point_Type (U_Ent)
2751 or else Has_Small_Clause (U_Ent)
2752 then
2753 Check_Size (Expr, Etyp, Size, Biased);
2754 Set_Biased (U_Ent, N, "size clause", Biased);
2755 end if;
2756
2757 -- For types set RM_Size and Esize if possible
2758
2759 if Is_Type (U_Ent) then
2760 Set_RM_Size (U_Ent, Size);
2761
2762 -- For elementary types, increase Object_Size to power of 2,
2763 -- but not less than a storage unit in any case (normally
2764 -- this means it will be byte addressable).
2765
2766 -- For all other types, nothing else to do, we leave Esize
2767 -- (object size) unset, the back end will set it from the
2768 -- size and alignment in an appropriate manner.
2769
2770 -- In both cases, we check whether the alignment must be
2771 -- reset in the wake of the size change.
2772
2773 if Is_Elementary_Type (U_Ent) then
2774 if Size <= System_Storage_Unit then
2775 Init_Esize (U_Ent, System_Storage_Unit);
2776 elsif Size <= 16 then
2777 Init_Esize (U_Ent, 16);
2778 elsif Size <= 32 then
2779 Init_Esize (U_Ent, 32);
2780 else
2781 Set_Esize (U_Ent, (Size + 63) / 64 * 64);
2782 end if;
2783
2784 Alignment_Check_For_Size_Change (U_Ent, Esize (U_Ent));
2785 else
2786 Alignment_Check_For_Size_Change (U_Ent, Size);
2787 end if;
2788
2789 -- For objects, set Esize only
2790
2791 else
2792 if Is_Elementary_Type (Etyp) then
2793 if Size /= System_Storage_Unit
2794 and then
2795 Size /= System_Storage_Unit * 2
2796 and then
2797 Size /= System_Storage_Unit * 4
2798 and then
2799 Size /= System_Storage_Unit * 8
2800 then
2801 Error_Msg_Uint_1 := UI_From_Int (System_Storage_Unit);
2802 Error_Msg_Uint_2 := Error_Msg_Uint_1 * 8;
2803 Error_Msg_N
2804 ("size for primitive object must be a power of 2"
2805 & " in the range ^-^", N);
2806 end if;
2807 end if;
2808
2809 Set_Esize (U_Ent, Size);
2810 end if;
2811
2812 Set_Has_Size_Clause (U_Ent);
2813 end if;
2814 end Size;
2815
2816 -----------
2817 -- Small --
2818 -----------
2819
2820 -- Small attribute definition clause
2821
2822 when Attribute_Small => Small : declare
2823 Implicit_Base : constant Entity_Id := Base_Type (U_Ent);
2824 Small : Ureal;
2825
2826 begin
2827 Analyze_And_Resolve (Expr, Any_Real);
2828
2829 if Etype (Expr) = Any_Type then
2830 return;
2831
2832 elsif not Is_Static_Expression (Expr) then
2833 Flag_Non_Static_Expr
2834 ("small requires static expression!", Expr);
2835 return;
2836
2837 else
2838 Small := Expr_Value_R (Expr);
2839
2840 if Small <= Ureal_0 then
2841 Error_Msg_N ("small value must be greater than zero", Expr);
2842 return;
2843 end if;
2844
2845 end if;
2846
2847 if not Is_Ordinary_Fixed_Point_Type (U_Ent) then
2848 Error_Msg_N
2849 ("small requires an ordinary fixed point type", Nam);
2850
2851 elsif Has_Small_Clause (U_Ent) then
2852 Error_Msg_N ("small already given for &", Nam);
2853
2854 elsif Small > Delta_Value (U_Ent) then
2855 Error_Msg_N
2856 ("small value must not be greater then delta value", Nam);
2857
2858 else
2859 Set_Small_Value (U_Ent, Small);
2860 Set_Small_Value (Implicit_Base, Small);
2861 Set_Has_Small_Clause (U_Ent);
2862 Set_Has_Small_Clause (Implicit_Base);
2863 Set_Has_Non_Standard_Rep (Implicit_Base);
2864 end if;
2865 end Small;
2866
2867 ------------------
2868 -- Storage_Pool --
2869 ------------------
2870
2871 -- Storage_Pool attribute definition clause
2872
2873 when Attribute_Storage_Pool => Storage_Pool : declare
2874 Pool : Entity_Id;
2875 T : Entity_Id;
2876
2877 begin
2878 if Ekind (U_Ent) = E_Access_Subprogram_Type then
2879 Error_Msg_N
2880 ("storage pool cannot be given for access-to-subprogram type",
2881 Nam);
2882 return;
2883
2884 elsif not
2885 Ekind_In (U_Ent, E_Access_Type, E_General_Access_Type)
2886 then
2887 Error_Msg_N
2888 ("storage pool can only be given for access types", Nam);
2889 return;
2890
2891 elsif Is_Derived_Type (U_Ent) then
2892 Error_Msg_N
2893 ("storage pool cannot be given for a derived access type",
2894 Nam);
2895
2896 elsif Duplicate_Clause then
2897 return;
2898
2899 elsif Present (Associated_Storage_Pool (U_Ent)) then
2900 Error_Msg_N ("storage pool already given for &", Nam);
2901 return;
2902 end if;
2903
2904 Analyze_And_Resolve
2905 (Expr, Class_Wide_Type (RTE (RE_Root_Storage_Pool)));
2906
2907 if not Denotes_Variable (Expr) then
2908 Error_Msg_N ("storage pool must be a variable", Expr);
2909 return;
2910 end if;
2911
2912 if Nkind (Expr) = N_Type_Conversion then
2913 T := Etype (Expression (Expr));
2914 else
2915 T := Etype (Expr);
2916 end if;
2917
2918 -- The Stack_Bounded_Pool is used internally for implementing
2919 -- access types with a Storage_Size. Since it only work properly
2920 -- when used on one specific type, we need to check that it is not
2921 -- hijacked improperly:
2922
2923 -- type T is access Integer;
2924 -- for T'Storage_Size use n;
2925 -- type Q is access Float;
2926 -- for Q'Storage_Size use T'Storage_Size; -- incorrect
2927
2928 if RTE_Available (RE_Stack_Bounded_Pool)
2929 and then Base_Type (T) = RTE (RE_Stack_Bounded_Pool)
2930 then
2931 Error_Msg_N ("non-shareable internal Pool", Expr);
2932 return;
2933 end if;
2934
2935 -- If the argument is a name that is not an entity name, then
2936 -- we construct a renaming operation to define an entity of
2937 -- type storage pool.
2938
2939 if not Is_Entity_Name (Expr)
2940 and then Is_Object_Reference (Expr)
2941 then
2942 Pool := Make_Temporary (Loc, 'P', Expr);
2943
2944 declare
2945 Rnode : constant Node_Id :=
2946 Make_Object_Renaming_Declaration (Loc,
2947 Defining_Identifier => Pool,
2948 Subtype_Mark =>
2949 New_Occurrence_Of (Etype (Expr), Loc),
2950 Name => Expr);
2951
2952 begin
2953 Insert_Before (N, Rnode);
2954 Analyze (Rnode);
2955 Set_Associated_Storage_Pool (U_Ent, Pool);
2956 end;
2957
2958 elsif Is_Entity_Name (Expr) then
2959 Pool := Entity (Expr);
2960
2961 -- If pool is a renamed object, get original one. This can
2962 -- happen with an explicit renaming, and within instances.
2963
2964 while Present (Renamed_Object (Pool))
2965 and then Is_Entity_Name (Renamed_Object (Pool))
2966 loop
2967 Pool := Entity (Renamed_Object (Pool));
2968 end loop;
2969
2970 if Present (Renamed_Object (Pool))
2971 and then Nkind (Renamed_Object (Pool)) = N_Type_Conversion
2972 and then Is_Entity_Name (Expression (Renamed_Object (Pool)))
2973 then
2974 Pool := Entity (Expression (Renamed_Object (Pool)));
2975 end if;
2976
2977 Set_Associated_Storage_Pool (U_Ent, Pool);
2978
2979 elsif Nkind (Expr) = N_Type_Conversion
2980 and then Is_Entity_Name (Expression (Expr))
2981 and then Nkind (Original_Node (Expr)) = N_Attribute_Reference
2982 then
2983 Pool := Entity (Expression (Expr));
2984 Set_Associated_Storage_Pool (U_Ent, Pool);
2985
2986 else
2987 Error_Msg_N ("incorrect reference to a Storage Pool", Expr);
2988 return;
2989 end if;
2990 end Storage_Pool;
2991
2992 ------------------
2993 -- Storage_Size --
2994 ------------------
2995
2996 -- Storage_Size attribute definition clause
2997
2998 when Attribute_Storage_Size => Storage_Size : declare
2999 Btype : constant Entity_Id := Base_Type (U_Ent);
3000 Sprag : Node_Id;
3001
3002 begin
3003 if Is_Task_Type (U_Ent) then
3004 Check_Restriction (No_Obsolescent_Features, N);
3005
3006 if Warn_On_Obsolescent_Feature then
3007 Error_Msg_N
3008 ("storage size clause for task is an " &
3009 "obsolescent feature (RM J.9)?", N);
3010 Error_Msg_N ("\use Storage_Size pragma instead?", N);
3011 end if;
3012
3013 FOnly := True;
3014 end if;
3015
3016 if not Is_Access_Type (U_Ent)
3017 and then Ekind (U_Ent) /= E_Task_Type
3018 then
3019 Error_Msg_N ("storage size cannot be given for &", Nam);
3020
3021 elsif Is_Access_Type (U_Ent) and Is_Derived_Type (U_Ent) then
3022 Error_Msg_N
3023 ("storage size cannot be given for a derived access type",
3024 Nam);
3025
3026 elsif Duplicate_Clause then
3027 null;
3028
3029 else
3030 Analyze_And_Resolve (Expr, Any_Integer);
3031
3032 if Is_Access_Type (U_Ent) then
3033 if Present (Associated_Storage_Pool (U_Ent)) then
3034 Error_Msg_N ("storage pool already given for &", Nam);
3035 return;
3036 end if;
3037
3038 if Is_OK_Static_Expression (Expr)
3039 and then Expr_Value (Expr) = 0
3040 then
3041 Set_No_Pool_Assigned (Btype);
3042 end if;
3043
3044 else -- Is_Task_Type (U_Ent)
3045 Sprag := Get_Rep_Pragma (Btype, Name_Storage_Size);
3046
3047 if Present (Sprag) then
3048 Error_Msg_Sloc := Sloc (Sprag);
3049 Error_Msg_N
3050 ("Storage_Size already specified#", Nam);
3051 return;
3052 end if;
3053 end if;
3054
3055 Set_Has_Storage_Size_Clause (Btype);
3056 end if;
3057 end Storage_Size;
3058
3059 -----------------
3060 -- Stream_Size --
3061 -----------------
3062
3063 when Attribute_Stream_Size => Stream_Size : declare
3064 Size : constant Uint := Static_Integer (Expr);
3065
3066 begin
3067 if Ada_Version <= Ada_95 then
3068 Check_Restriction (No_Implementation_Attributes, N);
3069 end if;
3070
3071 if Duplicate_Clause then
3072 null;
3073
3074 elsif Is_Elementary_Type (U_Ent) then
3075 if Size /= System_Storage_Unit
3076 and then
3077 Size /= System_Storage_Unit * 2
3078 and then
3079 Size /= System_Storage_Unit * 4
3080 and then
3081 Size /= System_Storage_Unit * 8
3082 then
3083 Error_Msg_Uint_1 := UI_From_Int (System_Storage_Unit);
3084 Error_Msg_N
3085 ("stream size for elementary type must be a"
3086 & " power of 2 and at least ^", N);
3087
3088 elsif RM_Size (U_Ent) > Size then
3089 Error_Msg_Uint_1 := RM_Size (U_Ent);
3090 Error_Msg_N
3091 ("stream size for elementary type must be a"
3092 & " power of 2 and at least ^", N);
3093 end if;
3094
3095 Set_Has_Stream_Size_Clause (U_Ent);
3096
3097 else
3098 Error_Msg_N ("Stream_Size cannot be given for &", Nam);
3099 end if;
3100 end Stream_Size;
3101
3102 ----------------
3103 -- Value_Size --
3104 ----------------
3105
3106 -- Value_Size attribute definition clause
3107
3108 when Attribute_Value_Size => Value_Size : declare
3109 Size : constant Uint := Static_Integer (Expr);
3110 Biased : Boolean;
3111
3112 begin
3113 if not Is_Type (U_Ent) then
3114 Error_Msg_N ("Value_Size cannot be given for &", Nam);
3115
3116 elsif Duplicate_Clause then
3117 null;
3118
3119 elsif Is_Array_Type (U_Ent)
3120 and then not Is_Constrained (U_Ent)
3121 then
3122 Error_Msg_N
3123 ("Value_Size cannot be given for unconstrained array", Nam);
3124
3125 else
3126 if Is_Elementary_Type (U_Ent) then
3127 Check_Size (Expr, U_Ent, Size, Biased);
3128 Set_Biased (U_Ent, N, "value size clause", Biased);
3129 end if;
3130
3131 Set_RM_Size (U_Ent, Size);
3132 end if;
3133 end Value_Size;
3134
3135 -----------------------
3136 -- Variable_Indexing --
3137 -----------------------
3138
3139 when Attribute_Variable_Indexing =>
3140 Check_Indexing_Functions;
3141
3142 -----------
3143 -- Write --
3144 -----------
3145
3146 when Attribute_Write =>
3147 Analyze_Stream_TSS_Definition (TSS_Stream_Write);
3148 Set_Has_Specified_Stream_Write (Ent);
3149
3150 -- All other attributes cannot be set
3151
3152 when others =>
3153 Error_Msg_N
3154 ("attribute& cannot be set with definition clause", N);
3155 end case;
3156
3157 -- The test for the type being frozen must be performed after any
3158 -- expression the clause has been analyzed since the expression itself
3159 -- might cause freezing that makes the clause illegal.
3160
3161 if Rep_Item_Too_Late (U_Ent, N, FOnly) then
3162 return;
3163 end if;
3164 end Analyze_Attribute_Definition_Clause;
3165
3166 ----------------------------
3167 -- Analyze_Code_Statement --
3168 ----------------------------
3169
3170 procedure Analyze_Code_Statement (N : Node_Id) is
3171 HSS : constant Node_Id := Parent (N);
3172 SBody : constant Node_Id := Parent (HSS);
3173 Subp : constant Entity_Id := Current_Scope;
3174 Stmt : Node_Id;
3175 Decl : Node_Id;
3176 StmtO : Node_Id;
3177 DeclO : Node_Id;
3178
3179 begin
3180 -- Analyze and check we get right type, note that this implements the
3181 -- requirement (RM 13.8(1)) that Machine_Code be with'ed, since that
3182 -- is the only way that Asm_Insn could possibly be visible.
3183
3184 Analyze_And_Resolve (Expression (N));
3185
3186 if Etype (Expression (N)) = Any_Type then
3187 return;
3188 elsif Etype (Expression (N)) /= RTE (RE_Asm_Insn) then
3189 Error_Msg_N ("incorrect type for code statement", N);
3190 return;
3191 end if;
3192
3193 Check_Code_Statement (N);
3194
3195 -- Make sure we appear in the handled statement sequence of a
3196 -- subprogram (RM 13.8(3)).
3197
3198 if Nkind (HSS) /= N_Handled_Sequence_Of_Statements
3199 or else Nkind (SBody) /= N_Subprogram_Body
3200 then
3201 Error_Msg_N
3202 ("code statement can only appear in body of subprogram", N);
3203 return;
3204 end if;
3205
3206 -- Do remaining checks (RM 13.8(3)) if not already done
3207
3208 if not Is_Machine_Code_Subprogram (Subp) then
3209 Set_Is_Machine_Code_Subprogram (Subp);
3210
3211 -- No exception handlers allowed
3212
3213 if Present (Exception_Handlers (HSS)) then
3214 Error_Msg_N
3215 ("exception handlers not permitted in machine code subprogram",
3216 First (Exception_Handlers (HSS)));
3217 end if;
3218
3219 -- No declarations other than use clauses and pragmas (we allow
3220 -- certain internally generated declarations as well).
3221
3222 Decl := First (Declarations (SBody));
3223 while Present (Decl) loop
3224 DeclO := Original_Node (Decl);
3225 if Comes_From_Source (DeclO)
3226 and not Nkind_In (DeclO, N_Pragma,
3227 N_Use_Package_Clause,
3228 N_Use_Type_Clause,
3229 N_Implicit_Label_Declaration)
3230 then
3231 Error_Msg_N
3232 ("this declaration not allowed in machine code subprogram",
3233 DeclO);
3234 end if;
3235
3236 Next (Decl);
3237 end loop;
3238
3239 -- No statements other than code statements, pragmas, and labels.
3240 -- Again we allow certain internally generated statements.
3241
3242 Stmt := First (Statements (HSS));
3243 while Present (Stmt) loop
3244 StmtO := Original_Node (Stmt);
3245 if Comes_From_Source (StmtO)
3246 and then not Nkind_In (StmtO, N_Pragma,
3247 N_Label,
3248 N_Code_Statement)
3249 then
3250 Error_Msg_N
3251 ("this statement is not allowed in machine code subprogram",
3252 StmtO);
3253 end if;
3254
3255 Next (Stmt);
3256 end loop;
3257 end if;
3258 end Analyze_Code_Statement;
3259
3260 -----------------------------------------------
3261 -- Analyze_Enumeration_Representation_Clause --
3262 -----------------------------------------------
3263
3264 procedure Analyze_Enumeration_Representation_Clause (N : Node_Id) is
3265 Ident : constant Node_Id := Identifier (N);
3266 Aggr : constant Node_Id := Array_Aggregate (N);
3267 Enumtype : Entity_Id;
3268 Elit : Entity_Id;
3269 Expr : Node_Id;
3270 Assoc : Node_Id;
3271 Choice : Node_Id;
3272 Val : Uint;
3273
3274 Err : Boolean := False;
3275 -- Set True to avoid cascade errors and crashes on incorrect source code
3276
3277 Lo : constant Uint := Expr_Value (Type_Low_Bound (Universal_Integer));
3278 Hi : constant Uint := Expr_Value (Type_High_Bound (Universal_Integer));
3279 -- Allowed range of universal integer (= allowed range of enum lit vals)
3280
3281 Min : Uint;
3282 Max : Uint;
3283 -- Minimum and maximum values of entries
3284
3285 Max_Node : Node_Id;
3286 -- Pointer to node for literal providing max value
3287
3288 begin
3289 if Ignore_Rep_Clauses then
3290 return;
3291 end if;
3292
3293 -- First some basic error checks
3294
3295 Find_Type (Ident);
3296 Enumtype := Entity (Ident);
3297
3298 if Enumtype = Any_Type
3299 or else Rep_Item_Too_Early (Enumtype, N)
3300 then
3301 return;
3302 else
3303 Enumtype := Underlying_Type (Enumtype);
3304 end if;
3305
3306 if not Is_Enumeration_Type (Enumtype) then
3307 Error_Msg_NE
3308 ("enumeration type required, found}",
3309 Ident, First_Subtype (Enumtype));
3310 return;
3311 end if;
3312
3313 -- Ignore rep clause on generic actual type. This will already have
3314 -- been flagged on the template as an error, and this is the safest
3315 -- way to ensure we don't get a junk cascaded message in the instance.
3316
3317 if Is_Generic_Actual_Type (Enumtype) then
3318 return;
3319
3320 -- Type must be in current scope
3321
3322 elsif Scope (Enumtype) /= Current_Scope then
3323 Error_Msg_N ("type must be declared in this scope", Ident);
3324 return;
3325
3326 -- Type must be a first subtype
3327
3328 elsif not Is_First_Subtype (Enumtype) then
3329 Error_Msg_N ("cannot give enumeration rep clause for subtype", N);
3330 return;
3331
3332 -- Ignore duplicate rep clause
3333
3334 elsif Has_Enumeration_Rep_Clause (Enumtype) then
3335 Error_Msg_N ("duplicate enumeration rep clause ignored", N);
3336 return;
3337
3338 -- Don't allow rep clause for standard [wide_[wide_]]character
3339
3340 elsif Is_Standard_Character_Type (Enumtype) then
3341 Error_Msg_N ("enumeration rep clause not allowed for this type", N);
3342 return;
3343
3344 -- Check that the expression is a proper aggregate (no parentheses)
3345
3346 elsif Paren_Count (Aggr) /= 0 then
3347 Error_Msg
3348 ("extra parentheses surrounding aggregate not allowed",
3349 First_Sloc (Aggr));
3350 return;
3351
3352 -- All tests passed, so set rep clause in place
3353
3354 else
3355 Set_Has_Enumeration_Rep_Clause (Enumtype);
3356 Set_Has_Enumeration_Rep_Clause (Base_Type (Enumtype));
3357 end if;
3358
3359 -- Now we process the aggregate. Note that we don't use the normal
3360 -- aggregate code for this purpose, because we don't want any of the
3361 -- normal expansion activities, and a number of special semantic
3362 -- rules apply (including the component type being any integer type)
3363
3364 Elit := First_Literal (Enumtype);
3365
3366 -- First the positional entries if any
3367
3368 if Present (Expressions (Aggr)) then
3369 Expr := First (Expressions (Aggr));
3370 while Present (Expr) loop
3371 if No (Elit) then
3372 Error_Msg_N ("too many entries in aggregate", Expr);
3373 return;
3374 end if;
3375
3376 Val := Static_Integer (Expr);
3377
3378 -- Err signals that we found some incorrect entries processing
3379 -- the list. The final checks for completeness and ordering are
3380 -- skipped in this case.
3381
3382 if Val = No_Uint then
3383 Err := True;
3384 elsif Val < Lo or else Hi < Val then
3385 Error_Msg_N ("value outside permitted range", Expr);
3386 Err := True;
3387 end if;
3388
3389 Set_Enumeration_Rep (Elit, Val);
3390 Set_Enumeration_Rep_Expr (Elit, Expr);
3391 Next (Expr);
3392 Next (Elit);
3393 end loop;
3394 end if;
3395
3396 -- Now process the named entries if present
3397
3398 if Present (Component_Associations (Aggr)) then
3399 Assoc := First (Component_Associations (Aggr));
3400 while Present (Assoc) loop
3401 Choice := First (Choices (Assoc));
3402
3403 if Present (Next (Choice)) then
3404 Error_Msg_N
3405 ("multiple choice not allowed here", Next (Choice));
3406 Err := True;
3407 end if;
3408
3409 if Nkind (Choice) = N_Others_Choice then
3410 Error_Msg_N ("others choice not allowed here", Choice);
3411 Err := True;
3412
3413 elsif Nkind (Choice) = N_Range then
3414
3415 -- ??? should allow zero/one element range here
3416
3417 Error_Msg_N ("range not allowed here", Choice);
3418 Err := True;
3419
3420 else
3421 Analyze_And_Resolve (Choice, Enumtype);
3422
3423 if Error_Posted (Choice) then
3424 Err := True;
3425 end if;
3426
3427 if not Err then
3428 if Is_Entity_Name (Choice)
3429 and then Is_Type (Entity (Choice))
3430 then
3431 Error_Msg_N ("subtype name not allowed here", Choice);
3432 Err := True;
3433
3434 -- ??? should allow static subtype with zero/one entry
3435
3436 elsif Etype (Choice) = Base_Type (Enumtype) then
3437 if not Is_Static_Expression (Choice) then
3438 Flag_Non_Static_Expr
3439 ("non-static expression used for choice!", Choice);
3440 Err := True;
3441
3442 else
3443 Elit := Expr_Value_E (Choice);
3444
3445 if Present (Enumeration_Rep_Expr (Elit)) then
3446 Error_Msg_Sloc :=
3447 Sloc (Enumeration_Rep_Expr (Elit));
3448 Error_Msg_NE
3449 ("representation for& previously given#",
3450 Choice, Elit);
3451 Err := True;
3452 end if;
3453
3454 Set_Enumeration_Rep_Expr (Elit, Expression (Assoc));
3455
3456 Expr := Expression (Assoc);
3457 Val := Static_Integer (Expr);
3458
3459 if Val = No_Uint then
3460 Err := True;
3461
3462 elsif Val < Lo or else Hi < Val then
3463 Error_Msg_N ("value outside permitted range", Expr);
3464 Err := True;
3465 end if;
3466
3467 Set_Enumeration_Rep (Elit, Val);
3468 end if;
3469 end if;
3470 end if;
3471 end if;
3472
3473 Next (Assoc);
3474 end loop;
3475 end if;
3476
3477 -- Aggregate is fully processed. Now we check that a full set of
3478 -- representations was given, and that they are in range and in order.
3479 -- These checks are only done if no other errors occurred.
3480
3481 if not Err then
3482 Min := No_Uint;
3483 Max := No_Uint;
3484
3485 Elit := First_Literal (Enumtype);
3486 while Present (Elit) loop
3487 if No (Enumeration_Rep_Expr (Elit)) then
3488 Error_Msg_NE ("missing representation for&!", N, Elit);
3489
3490 else
3491 Val := Enumeration_Rep (Elit);
3492
3493 if Min = No_Uint then
3494 Min := Val;
3495 end if;
3496
3497 if Val /= No_Uint then
3498 if Max /= No_Uint and then Val <= Max then
3499 Error_Msg_NE
3500 ("enumeration value for& not ordered!",
3501 Enumeration_Rep_Expr (Elit), Elit);
3502 end if;
3503
3504 Max_Node := Enumeration_Rep_Expr (Elit);
3505 Max := Val;
3506 end if;
3507
3508 -- If there is at least one literal whose representation is not
3509 -- equal to the Pos value, then note that this enumeration type
3510 -- has a non-standard representation.
3511
3512 if Val /= Enumeration_Pos (Elit) then
3513 Set_Has_Non_Standard_Rep (Base_Type (Enumtype));
3514 end if;
3515 end if;
3516
3517 Next (Elit);
3518 end loop;
3519
3520 -- Now set proper size information
3521
3522 declare
3523 Minsize : Uint := UI_From_Int (Minimum_Size (Enumtype));
3524
3525 begin
3526 if Has_Size_Clause (Enumtype) then
3527
3528 -- All OK, if size is OK now
3529
3530 if RM_Size (Enumtype) >= Minsize then
3531 null;
3532
3533 else
3534 -- Try if we can get by with biasing
3535
3536 Minsize :=
3537 UI_From_Int (Minimum_Size (Enumtype, Biased => True));
3538
3539 -- Error message if even biasing does not work
3540
3541 if RM_Size (Enumtype) < Minsize then
3542 Error_Msg_Uint_1 := RM_Size (Enumtype);
3543 Error_Msg_Uint_2 := Max;
3544 Error_Msg_N
3545 ("previously given size (^) is too small "
3546 & "for this value (^)", Max_Node);
3547
3548 -- If biasing worked, indicate that we now have biased rep
3549
3550 else
3551 Set_Biased
3552 (Enumtype, Size_Clause (Enumtype), "size clause");
3553 end if;
3554 end if;
3555
3556 else
3557 Set_RM_Size (Enumtype, Minsize);
3558 Set_Enum_Esize (Enumtype);
3559 end if;
3560
3561 Set_RM_Size (Base_Type (Enumtype), RM_Size (Enumtype));
3562 Set_Esize (Base_Type (Enumtype), Esize (Enumtype));
3563 Set_Alignment (Base_Type (Enumtype), Alignment (Enumtype));
3564 end;
3565 end if;
3566
3567 -- We repeat the too late test in case it froze itself!
3568
3569 if Rep_Item_Too_Late (Enumtype, N) then
3570 null;
3571 end if;
3572 end Analyze_Enumeration_Representation_Clause;
3573
3574 ----------------------------
3575 -- Analyze_Free_Statement --
3576 ----------------------------
3577
3578 procedure Analyze_Free_Statement (N : Node_Id) is
3579 begin
3580 Analyze (Expression (N));
3581 end Analyze_Free_Statement;
3582
3583 ---------------------------
3584 -- Analyze_Freeze_Entity --
3585 ---------------------------
3586
3587 procedure Analyze_Freeze_Entity (N : Node_Id) is
3588 E : constant Entity_Id := Entity (N);
3589
3590 begin
3591 -- Remember that we are processing a freezing entity. Required to
3592 -- ensure correct decoration of internal entities associated with
3593 -- interfaces (see New_Overloaded_Entity).
3594
3595 Inside_Freezing_Actions := Inside_Freezing_Actions + 1;
3596
3597 -- For tagged types covering interfaces add internal entities that link
3598 -- the primitives of the interfaces with the primitives that cover them.
3599 -- Note: These entities were originally generated only when generating
3600 -- code because their main purpose was to provide support to initialize
3601 -- the secondary dispatch tables. They are now generated also when
3602 -- compiling with no code generation to provide ASIS the relationship
3603 -- between interface primitives and tagged type primitives. They are
3604 -- also used to locate primitives covering interfaces when processing
3605 -- generics (see Derive_Subprograms).
3606
3607 if Ada_Version >= Ada_2005
3608 and then Ekind (E) = E_Record_Type
3609 and then Is_Tagged_Type (E)
3610 and then not Is_Interface (E)
3611 and then Has_Interfaces (E)
3612 then
3613 -- This would be a good common place to call the routine that checks
3614 -- overriding of interface primitives (and thus factorize calls to
3615 -- Check_Abstract_Overriding located at different contexts in the
3616 -- compiler). However, this is not possible because it causes
3617 -- spurious errors in case of late overriding.
3618
3619 Add_Internal_Interface_Entities (E);
3620 end if;
3621
3622 -- Check CPP types
3623
3624 if Ekind (E) = E_Record_Type
3625 and then Is_CPP_Class (E)
3626 and then Is_Tagged_Type (E)
3627 and then Tagged_Type_Expansion
3628 and then Expander_Active
3629 then
3630 if CPP_Num_Prims (E) = 0 then
3631
3632 -- If the CPP type has user defined components then it must import
3633 -- primitives from C++. This is required because if the C++ class
3634 -- has no primitives then the C++ compiler does not added the _tag
3635 -- component to the type.
3636
3637 pragma Assert (Chars (First_Entity (E)) = Name_uTag);
3638
3639 if First_Entity (E) /= Last_Entity (E) then
3640 Error_Msg_N
3641 ("?'C'P'P type must import at least one primitive from C++",
3642 E);
3643 end if;
3644 end if;
3645
3646 -- Check that all its primitives are abstract or imported from C++.
3647 -- Check also availability of the C++ constructor.
3648
3649 declare
3650 Has_Constructors : constant Boolean := Has_CPP_Constructors (E);
3651 Elmt : Elmt_Id;
3652 Error_Reported : Boolean := False;
3653 Prim : Node_Id;
3654
3655 begin
3656 Elmt := First_Elmt (Primitive_Operations (E));
3657 while Present (Elmt) loop
3658 Prim := Node (Elmt);
3659
3660 if Comes_From_Source (Prim) then
3661 if Is_Abstract_Subprogram (Prim) then
3662 null;
3663
3664 elsif not Is_Imported (Prim)
3665 or else Convention (Prim) /= Convention_CPP
3666 then
3667 Error_Msg_N
3668 ("?primitives of 'C'P'P types must be imported from C++"
3669 & " or abstract", Prim);
3670
3671 elsif not Has_Constructors
3672 and then not Error_Reported
3673 then
3674 Error_Msg_Name_1 := Chars (E);
3675 Error_Msg_N
3676 ("?'C'P'P constructor required for type %", Prim);
3677 Error_Reported := True;
3678 end if;
3679 end if;
3680
3681 Next_Elmt (Elmt);
3682 end loop;
3683 end;
3684 end if;
3685
3686 Inside_Freezing_Actions := Inside_Freezing_Actions - 1;
3687
3688 -- If we have a type with predicates, build predicate function
3689
3690 if Is_Type (E) and then Has_Predicates (E) then
3691 Build_Predicate_Function (E, N);
3692 end if;
3693
3694 -- If type has delayed aspects, this is where we do the preanalysis at
3695 -- the freeze point, as part of the consistent visibility check. Note
3696 -- that this must be done after calling Build_Predicate_Function or
3697 -- Build_Invariant_Procedure since these subprograms fix occurrences of
3698 -- the subtype name in the saved expression so that they will not cause
3699 -- trouble in the preanalysis.
3700
3701 if Has_Delayed_Aspects (E) then
3702 declare
3703 Ritem : Node_Id;
3704
3705 begin
3706 -- Look for aspect specification entries for this entity
3707
3708 Ritem := First_Rep_Item (E);
3709 while Present (Ritem) loop
3710 if Nkind (Ritem) = N_Aspect_Specification
3711 and then Entity (Ritem) = E
3712 and then Is_Delayed_Aspect (Ritem)
3713 and then Scope (E) = Current_Scope
3714 then
3715 Check_Aspect_At_Freeze_Point (Ritem);
3716 end if;
3717
3718 Next_Rep_Item (Ritem);
3719 end loop;
3720 end;
3721 end if;
3722 end Analyze_Freeze_Entity;
3723
3724 ------------------------------------------
3725 -- Analyze_Record_Representation_Clause --
3726 ------------------------------------------
3727
3728 -- Note: we check as much as we can here, but we can't do any checks
3729 -- based on the position values (e.g. overlap checks) until freeze time
3730 -- because especially in Ada 2005 (machine scalar mode), the processing
3731 -- for non-standard bit order can substantially change the positions.
3732 -- See procedure Check_Record_Representation_Clause (called from Freeze)
3733 -- for the remainder of this processing.
3734
3735 procedure Analyze_Record_Representation_Clause (N : Node_Id) is
3736 Ident : constant Node_Id := Identifier (N);
3737 Biased : Boolean;
3738 CC : Node_Id;
3739 Comp : Entity_Id;
3740 Fbit : Uint;
3741 Hbit : Uint := Uint_0;
3742 Lbit : Uint;
3743 Ocomp : Entity_Id;
3744 Posit : Uint;
3745 Rectype : Entity_Id;
3746
3747 CR_Pragma : Node_Id := Empty;
3748 -- Points to N_Pragma node if Complete_Representation pragma present
3749
3750 begin
3751 if Ignore_Rep_Clauses then
3752 return;
3753 end if;
3754
3755 Find_Type (Ident);
3756 Rectype := Entity (Ident);
3757
3758 if Rectype = Any_Type
3759 or else Rep_Item_Too_Early (Rectype, N)
3760 then
3761 return;
3762 else
3763 Rectype := Underlying_Type (Rectype);
3764 end if;
3765
3766 -- First some basic error checks
3767
3768 if not Is_Record_Type (Rectype) then
3769 Error_Msg_NE
3770 ("record type required, found}", Ident, First_Subtype (Rectype));
3771 return;
3772
3773 elsif Scope (Rectype) /= Current_Scope then
3774 Error_Msg_N ("type must be declared in this scope", N);
3775 return;
3776
3777 elsif not Is_First_Subtype (Rectype) then
3778 Error_Msg_N ("cannot give record rep clause for subtype", N);
3779 return;
3780
3781 elsif Has_Record_Rep_Clause (Rectype) then
3782 Error_Msg_N ("duplicate record rep clause ignored", N);
3783 return;
3784
3785 elsif Rep_Item_Too_Late (Rectype, N) then
3786 return;
3787 end if;
3788
3789 if Present (Mod_Clause (N)) then
3790 declare
3791 Loc : constant Source_Ptr := Sloc (N);
3792 M : constant Node_Id := Mod_Clause (N);
3793 P : constant List_Id := Pragmas_Before (M);
3794 AtM_Nod : Node_Id;
3795
3796 Mod_Val : Uint;
3797 pragma Warnings (Off, Mod_Val);
3798
3799 begin
3800 Check_Restriction (No_Obsolescent_Features, Mod_Clause (N));
3801
3802 if Warn_On_Obsolescent_Feature then
3803 Error_Msg_N
3804 ("mod clause is an obsolescent feature (RM J.8)?", N);
3805 Error_Msg_N
3806 ("\use alignment attribute definition clause instead?", N);
3807 end if;
3808
3809 if Present (P) then
3810 Analyze_List (P);
3811 end if;
3812
3813 -- In ASIS_Mode mode, expansion is disabled, but we must convert
3814 -- the Mod clause into an alignment clause anyway, so that the
3815 -- back-end can compute and back-annotate properly the size and
3816 -- alignment of types that may include this record.
3817
3818 -- This seems dubious, this destroys the source tree in a manner
3819 -- not detectable by ASIS ???
3820
3821 if Operating_Mode = Check_Semantics
3822 and then ASIS_Mode
3823 then
3824 AtM_Nod :=
3825 Make_Attribute_Definition_Clause (Loc,
3826 Name => New_Reference_To (Base_Type (Rectype), Loc),
3827 Chars => Name_Alignment,
3828 Expression => Relocate_Node (Expression (M)));
3829
3830 Set_From_At_Mod (AtM_Nod);
3831 Insert_After (N, AtM_Nod);
3832 Mod_Val := Get_Alignment_Value (Expression (AtM_Nod));
3833 Set_Mod_Clause (N, Empty);
3834
3835 else
3836 -- Get the alignment value to perform error checking
3837
3838 Mod_Val := Get_Alignment_Value (Expression (M));
3839 end if;
3840 end;
3841 end if;
3842
3843 -- For untagged types, clear any existing component clauses for the
3844 -- type. If the type is derived, this is what allows us to override
3845 -- a rep clause for the parent. For type extensions, the representation
3846 -- of the inherited components is inherited, so we want to keep previous
3847 -- component clauses for completeness.
3848
3849 if not Is_Tagged_Type (Rectype) then
3850 Comp := First_Component_Or_Discriminant (Rectype);
3851 while Present (Comp) loop
3852 Set_Component_Clause (Comp, Empty);
3853 Next_Component_Or_Discriminant (Comp);
3854 end loop;
3855 end if;
3856
3857 -- All done if no component clauses
3858
3859 CC := First (Component_Clauses (N));
3860
3861 if No (CC) then
3862 return;
3863 end if;
3864
3865 -- A representation like this applies to the base type
3866
3867 Set_Has_Record_Rep_Clause (Base_Type (Rectype));
3868 Set_Has_Non_Standard_Rep (Base_Type (Rectype));
3869 Set_Has_Specified_Layout (Base_Type (Rectype));
3870
3871 -- Process the component clauses
3872
3873 while Present (CC) loop
3874
3875 -- Pragma
3876
3877 if Nkind (CC) = N_Pragma then
3878 Analyze (CC);
3879
3880 -- The only pragma of interest is Complete_Representation
3881
3882 if Pragma_Name (CC) = Name_Complete_Representation then
3883 CR_Pragma := CC;
3884 end if;
3885
3886 -- Processing for real component clause
3887
3888 else
3889 Posit := Static_Integer (Position (CC));
3890 Fbit := Static_Integer (First_Bit (CC));
3891 Lbit := Static_Integer (Last_Bit (CC));
3892
3893 if Posit /= No_Uint
3894 and then Fbit /= No_Uint
3895 and then Lbit /= No_Uint
3896 then
3897 if Posit < 0 then
3898 Error_Msg_N
3899 ("position cannot be negative", Position (CC));
3900
3901 elsif Fbit < 0 then
3902 Error_Msg_N
3903 ("first bit cannot be negative", First_Bit (CC));
3904
3905 -- The Last_Bit specified in a component clause must not be
3906 -- less than the First_Bit minus one (RM-13.5.1(10)).
3907
3908 elsif Lbit < Fbit - 1 then
3909 Error_Msg_N
3910 ("last bit cannot be less than first bit minus one",
3911 Last_Bit (CC));
3912
3913 -- Values look OK, so find the corresponding record component
3914 -- Even though the syntax allows an attribute reference for
3915 -- implementation-defined components, GNAT does not allow the
3916 -- tag to get an explicit position.
3917
3918 elsif Nkind (Component_Name (CC)) = N_Attribute_Reference then
3919 if Attribute_Name (Component_Name (CC)) = Name_Tag then
3920 Error_Msg_N ("position of tag cannot be specified", CC);
3921 else
3922 Error_Msg_N ("illegal component name", CC);
3923 end if;
3924
3925 else
3926 Comp := First_Entity (Rectype);
3927 while Present (Comp) loop
3928 exit when Chars (Comp) = Chars (Component_Name (CC));
3929 Next_Entity (Comp);
3930 end loop;
3931
3932 if No (Comp) then
3933
3934 -- Maybe component of base type that is absent from
3935 -- statically constrained first subtype.
3936
3937 Comp := First_Entity (Base_Type (Rectype));
3938 while Present (Comp) loop
3939 exit when Chars (Comp) = Chars (Component_Name (CC));
3940 Next_Entity (Comp);
3941 end loop;
3942 end if;
3943
3944 if No (Comp) then
3945 Error_Msg_N
3946 ("component clause is for non-existent field", CC);
3947
3948 -- Ada 2012 (AI05-0026): Any name that denotes a
3949 -- discriminant of an object of an unchecked union type
3950 -- shall not occur within a record_representation_clause.
3951
3952 -- The general restriction of using record rep clauses on
3953 -- Unchecked_Union types has now been lifted. Since it is
3954 -- possible to introduce a record rep clause which mentions
3955 -- the discriminant of an Unchecked_Union in non-Ada 2012
3956 -- code, this check is applied to all versions of the
3957 -- language.
3958
3959 elsif Ekind (Comp) = E_Discriminant
3960 and then Is_Unchecked_Union (Rectype)
3961 then
3962 Error_Msg_N
3963 ("cannot reference discriminant of Unchecked_Union",
3964 Component_Name (CC));
3965
3966 elsif Present (Component_Clause (Comp)) then
3967
3968 -- Diagnose duplicate rep clause, or check consistency
3969 -- if this is an inherited component. In a double fault,
3970 -- there may be a duplicate inconsistent clause for an
3971 -- inherited component.
3972
3973 if Scope (Original_Record_Component (Comp)) = Rectype
3974 or else Parent (Component_Clause (Comp)) = N
3975 then
3976 Error_Msg_Sloc := Sloc (Component_Clause (Comp));
3977 Error_Msg_N ("component clause previously given#", CC);
3978
3979 else
3980 declare
3981 Rep1 : constant Node_Id := Component_Clause (Comp);
3982 begin
3983 if Intval (Position (Rep1)) /=
3984 Intval (Position (CC))
3985 or else Intval (First_Bit (Rep1)) /=
3986 Intval (First_Bit (CC))
3987 or else Intval (Last_Bit (Rep1)) /=
3988 Intval (Last_Bit (CC))
3989 then
3990 Error_Msg_N ("component clause inconsistent "
3991 & "with representation of ancestor", CC);
3992 elsif Warn_On_Redundant_Constructs then
3993 Error_Msg_N ("?redundant component clause "
3994 & "for inherited component!", CC);
3995 end if;
3996 end;
3997 end if;
3998
3999 -- Normal case where this is the first component clause we
4000 -- have seen for this entity, so set it up properly.
4001
4002 else
4003 -- Make reference for field in record rep clause and set
4004 -- appropriate entity field in the field identifier.
4005
4006 Generate_Reference
4007 (Comp, Component_Name (CC), Set_Ref => False);
4008 Set_Entity (Component_Name (CC), Comp);
4009
4010 -- Update Fbit and Lbit to the actual bit number
4011
4012 Fbit := Fbit + UI_From_Int (SSU) * Posit;
4013 Lbit := Lbit + UI_From_Int (SSU) * Posit;
4014
4015 if Has_Size_Clause (Rectype)
4016 and then RM_Size (Rectype) <= Lbit
4017 then
4018 Error_Msg_N
4019 ("bit number out of range of specified size",
4020 Last_Bit (CC));
4021 else
4022 Set_Component_Clause (Comp, CC);
4023 Set_Component_Bit_Offset (Comp, Fbit);
4024 Set_Esize (Comp, 1 + (Lbit - Fbit));
4025 Set_Normalized_First_Bit (Comp, Fbit mod SSU);
4026 Set_Normalized_Position (Comp, Fbit / SSU);
4027
4028 if Warn_On_Overridden_Size
4029 and then Has_Size_Clause (Etype (Comp))
4030 and then RM_Size (Etype (Comp)) /= Esize (Comp)
4031 then
4032 Error_Msg_NE
4033 ("?component size overrides size clause for&",
4034 Component_Name (CC), Etype (Comp));
4035 end if;
4036
4037 -- This information is also set in the corresponding
4038 -- component of the base type, found by accessing the
4039 -- Original_Record_Component link if it is present.
4040
4041 Ocomp := Original_Record_Component (Comp);
4042
4043 if Hbit < Lbit then
4044 Hbit := Lbit;
4045 end if;
4046
4047 Check_Size
4048 (Component_Name (CC),
4049 Etype (Comp),
4050 Esize (Comp),
4051 Biased);
4052
4053 Set_Biased
4054 (Comp, First_Node (CC), "component clause", Biased);
4055
4056 if Present (Ocomp) then
4057 Set_Component_Clause (Ocomp, CC);
4058 Set_Component_Bit_Offset (Ocomp, Fbit);
4059 Set_Normalized_First_Bit (Ocomp, Fbit mod SSU);
4060 Set_Normalized_Position (Ocomp, Fbit / SSU);
4061 Set_Esize (Ocomp, 1 + (Lbit - Fbit));
4062
4063 Set_Normalized_Position_Max
4064 (Ocomp, Normalized_Position (Ocomp));
4065
4066 -- Note: we don't use Set_Biased here, because we
4067 -- already gave a warning above if needed, and we
4068 -- would get a duplicate for the same name here.
4069
4070 Set_Has_Biased_Representation
4071 (Ocomp, Has_Biased_Representation (Comp));
4072 end if;
4073
4074 if Esize (Comp) < 0 then
4075 Error_Msg_N ("component size is negative", CC);
4076 end if;
4077 end if;
4078 end if;
4079 end if;
4080 end if;
4081 end if;
4082
4083 Next (CC);
4084 end loop;
4085
4086 -- Check missing components if Complete_Representation pragma appeared
4087
4088 if Present (CR_Pragma) then
4089 Comp := First_Component_Or_Discriminant (Rectype);
4090 while Present (Comp) loop
4091 if No (Component_Clause (Comp)) then
4092 Error_Msg_NE
4093 ("missing component clause for &", CR_Pragma, Comp);
4094 end if;
4095
4096 Next_Component_Or_Discriminant (Comp);
4097 end loop;
4098
4099 -- If no Complete_Representation pragma, warn if missing components
4100
4101 elsif Warn_On_Unrepped_Components then
4102 declare
4103 Num_Repped_Components : Nat := 0;
4104 Num_Unrepped_Components : Nat := 0;
4105
4106 begin
4107 -- First count number of repped and unrepped components
4108
4109 Comp := First_Component_Or_Discriminant (Rectype);
4110 while Present (Comp) loop
4111 if Present (Component_Clause (Comp)) then
4112 Num_Repped_Components := Num_Repped_Components + 1;
4113 else
4114 Num_Unrepped_Components := Num_Unrepped_Components + 1;
4115 end if;
4116
4117 Next_Component_Or_Discriminant (Comp);
4118 end loop;
4119
4120 -- We are only interested in the case where there is at least one
4121 -- unrepped component, and at least half the components have rep
4122 -- clauses. We figure that if less than half have them, then the
4123 -- partial rep clause is really intentional. If the component
4124 -- type has no underlying type set at this point (as for a generic
4125 -- formal type), we don't know enough to give a warning on the
4126 -- component.
4127
4128 if Num_Unrepped_Components > 0
4129 and then Num_Unrepped_Components < Num_Repped_Components
4130 then
4131 Comp := First_Component_Or_Discriminant (Rectype);
4132 while Present (Comp) loop
4133 if No (Component_Clause (Comp))
4134 and then Comes_From_Source (Comp)
4135 and then Present (Underlying_Type (Etype (Comp)))
4136 and then (Is_Scalar_Type (Underlying_Type (Etype (Comp)))
4137 or else Size_Known_At_Compile_Time
4138 (Underlying_Type (Etype (Comp))))
4139 and then not Has_Warnings_Off (Rectype)
4140 then
4141 Error_Msg_Sloc := Sloc (Comp);
4142 Error_Msg_NE
4143 ("?no component clause given for & declared #",
4144 N, Comp);
4145 end if;
4146
4147 Next_Component_Or_Discriminant (Comp);
4148 end loop;
4149 end if;
4150 end;
4151 end if;
4152 end Analyze_Record_Representation_Clause;
4153
4154 -------------------------------
4155 -- Build_Invariant_Procedure --
4156 -------------------------------
4157
4158 -- The procedure that is constructed here has the form
4159
4160 -- procedure typInvariant (Ixxx : typ) is
4161 -- begin
4162 -- pragma Check (Invariant, exp, "failed invariant from xxx");
4163 -- pragma Check (Invariant, exp, "failed invariant from xxx");
4164 -- ...
4165 -- pragma Check (Invariant, exp, "failed inherited invariant from xxx");
4166 -- ...
4167 -- end typInvariant;
4168
4169 procedure Build_Invariant_Procedure (Typ : Entity_Id; N : Node_Id) is
4170 Loc : constant Source_Ptr := Sloc (Typ);
4171 Stmts : List_Id;
4172 Spec : Node_Id;
4173 SId : Entity_Id;
4174 PDecl : Node_Id;
4175 PBody : Node_Id;
4176
4177 Visible_Decls : constant List_Id := Visible_Declarations (N);
4178 Private_Decls : constant List_Id := Private_Declarations (N);
4179
4180 procedure Add_Invariants (T : Entity_Id; Inherit : Boolean);
4181 -- Appends statements to Stmts for any invariants in the rep item chain
4182 -- of the given type. If Inherit is False, then we only process entries
4183 -- on the chain for the type Typ. If Inherit is True, then we ignore any
4184 -- Invariant aspects, but we process all Invariant'Class aspects, adding
4185 -- "inherited" to the exception message and generating an informational
4186 -- message about the inheritance of an invariant.
4187
4188 Object_Name : constant Name_Id := New_Internal_Name ('I');
4189 -- Name for argument of invariant procedure
4190
4191 Object_Entity : constant Node_Id :=
4192 Make_Defining_Identifier (Loc, Object_Name);
4193 -- The procedure declaration entity for the argument
4194
4195 --------------------
4196 -- Add_Invariants --
4197 --------------------
4198
4199 procedure Add_Invariants (T : Entity_Id; Inherit : Boolean) is
4200 Ritem : Node_Id;
4201 Arg1 : Node_Id;
4202 Arg2 : Node_Id;
4203 Arg3 : Node_Id;
4204 Exp : Node_Id;
4205 Loc : Source_Ptr;
4206 Assoc : List_Id;
4207 Str : String_Id;
4208
4209 procedure Replace_Type_Reference (N : Node_Id);
4210 -- Replace a single occurrence N of the subtype name with a reference
4211 -- to the formal of the predicate function. N can be an identifier
4212 -- referencing the subtype, or a selected component, representing an
4213 -- appropriately qualified occurrence of the subtype name.
4214
4215 procedure Replace_Type_References is
4216 new Replace_Type_References_Generic (Replace_Type_Reference);
4217 -- Traverse an expression replacing all occurrences of the subtype
4218 -- name with appropriate references to the object that is the formal
4219 -- parameter of the predicate function. Note that we must ensure
4220 -- that the type and entity information is properly set in the
4221 -- replacement node, since we will do a Preanalyze call of this
4222 -- expression without proper visibility of the procedure argument.
4223
4224 ----------------------------
4225 -- Replace_Type_Reference --
4226 ----------------------------
4227
4228 procedure Replace_Type_Reference (N : Node_Id) is
4229 begin
4230 -- Invariant'Class, replace with T'Class (obj)
4231
4232 if Class_Present (Ritem) then
4233 Rewrite (N,
4234 Make_Type_Conversion (Loc,
4235 Subtype_Mark =>
4236 Make_Attribute_Reference (Loc,
4237 Prefix => New_Occurrence_Of (T, Loc),
4238 Attribute_Name => Name_Class),
4239 Expression => Make_Identifier (Loc, Object_Name)));
4240
4241 Set_Entity (Expression (N), Object_Entity);
4242 Set_Etype (Expression (N), Typ);
4243
4244 -- Invariant, replace with obj
4245
4246 else
4247 Rewrite (N, Make_Identifier (Loc, Object_Name));
4248 Set_Entity (N, Object_Entity);
4249 Set_Etype (N, Typ);
4250 end if;
4251 end Replace_Type_Reference;
4252
4253 -- Start of processing for Add_Invariants
4254
4255 begin
4256 Ritem := First_Rep_Item (T);
4257 while Present (Ritem) loop
4258 if Nkind (Ritem) = N_Pragma
4259 and then Pragma_Name (Ritem) = Name_Invariant
4260 then
4261 Arg1 := First (Pragma_Argument_Associations (Ritem));
4262 Arg2 := Next (Arg1);
4263 Arg3 := Next (Arg2);
4264
4265 Arg1 := Get_Pragma_Arg (Arg1);
4266 Arg2 := Get_Pragma_Arg (Arg2);
4267
4268 -- For Inherit case, ignore Invariant, process only Class case
4269
4270 if Inherit then
4271 if not Class_Present (Ritem) then
4272 goto Continue;
4273 end if;
4274
4275 -- For Inherit false, process only item for right type
4276
4277 else
4278 if Entity (Arg1) /= Typ then
4279 goto Continue;
4280 end if;
4281 end if;
4282
4283 if No (Stmts) then
4284 Stmts := Empty_List;
4285 end if;
4286
4287 Exp := New_Copy_Tree (Arg2);
4288 Loc := Sloc (Exp);
4289
4290 -- We need to replace any occurrences of the name of the type
4291 -- with references to the object, converted to type'Class in
4292 -- the case of Invariant'Class aspects.
4293
4294 Replace_Type_References (Exp, Chars (T));
4295
4296 -- If this invariant comes from an aspect, find the aspect
4297 -- specification, and replace the saved expression because
4298 -- we need the subtype references replaced for the calls to
4299 -- Preanalyze_Spec_Expressin in Check_Aspect_At_Freeze_Point
4300 -- and Check_Aspect_At_End_Of_Declarations.
4301
4302 if From_Aspect_Specification (Ritem) then
4303 declare
4304 Aitem : Node_Id;
4305
4306 begin
4307 -- Loop to find corresponding aspect, note that this
4308 -- must be present given the pragma is marked delayed.
4309
4310 Aitem := Next_Rep_Item (Ritem);
4311 while Present (Aitem) loop
4312 if Nkind (Aitem) = N_Aspect_Specification
4313 and then Aspect_Rep_Item (Aitem) = Ritem
4314 then
4315 Set_Entity
4316 (Identifier (Aitem), New_Copy_Tree (Exp));
4317 exit;
4318 end if;
4319
4320 Aitem := Next_Rep_Item (Aitem);
4321 end loop;
4322 end;
4323 end if;
4324
4325 -- Now we need to preanalyze the expression to properly capture
4326 -- the visibility in the visible part. The expression will not
4327 -- be analyzed for real until the body is analyzed, but that is
4328 -- at the end of the private part and has the wrong visibility.
4329
4330 Set_Parent (Exp, N);
4331 Preanalyze_Spec_Expression (Exp, Standard_Boolean);
4332
4333 -- Build first two arguments for Check pragma
4334
4335 Assoc := New_List (
4336 Make_Pragma_Argument_Association (Loc,
4337 Expression => Make_Identifier (Loc, Name_Invariant)),
4338 Make_Pragma_Argument_Association (Loc, Expression => Exp));
4339
4340 -- Add message if present in Invariant pragma
4341
4342 if Present (Arg3) then
4343 Str := Strval (Get_Pragma_Arg (Arg3));
4344
4345 -- If inherited case, and message starts "failed invariant",
4346 -- change it to be "failed inherited invariant".
4347
4348 if Inherit then
4349 String_To_Name_Buffer (Str);
4350
4351 if Name_Buffer (1 .. 16) = "failed invariant" then
4352 Insert_Str_In_Name_Buffer ("inherited ", 8);
4353 Str := String_From_Name_Buffer;
4354 end if;
4355 end if;
4356
4357 Append_To (Assoc,
4358 Make_Pragma_Argument_Association (Loc,
4359 Expression => Make_String_Literal (Loc, Str)));
4360 end if;
4361
4362 -- Add Check pragma to list of statements
4363
4364 Append_To (Stmts,
4365 Make_Pragma (Loc,
4366 Pragma_Identifier =>
4367 Make_Identifier (Loc, Name_Check),
4368 Pragma_Argument_Associations => Assoc));
4369
4370 -- If Inherited case and option enabled, output info msg. Note
4371 -- that we know this is a case of Invariant'Class.
4372
4373 if Inherit and Opt.List_Inherited_Aspects then
4374 Error_Msg_Sloc := Sloc (Ritem);
4375 Error_Msg_N
4376 ("?info: & inherits `Invariant''Class` aspect from #",
4377 Typ);
4378 end if;
4379 end if;
4380
4381 <<Continue>>
4382 Next_Rep_Item (Ritem);
4383 end loop;
4384 end Add_Invariants;
4385
4386 -- Start of processing for Build_Invariant_Procedure
4387
4388 begin
4389 Stmts := No_List;
4390 PDecl := Empty;
4391 PBody := Empty;
4392 Set_Etype (Object_Entity, Typ);
4393
4394 -- Add invariants for the current type
4395
4396 Add_Invariants (Typ, Inherit => False);
4397
4398 -- Add invariants for parent types
4399
4400 declare
4401 Current_Typ : Entity_Id;
4402 Parent_Typ : Entity_Id;
4403
4404 begin
4405 Current_Typ := Typ;
4406 loop
4407 Parent_Typ := Etype (Current_Typ);
4408
4409 if Is_Private_Type (Parent_Typ)
4410 and then Present (Full_View (Base_Type (Parent_Typ)))
4411 then
4412 Parent_Typ := Full_View (Base_Type (Parent_Typ));
4413 end if;
4414
4415 exit when Parent_Typ = Current_Typ;
4416
4417 Current_Typ := Parent_Typ;
4418 Add_Invariants (Current_Typ, Inherit => True);
4419 end loop;
4420 end;
4421
4422 -- Build the procedure if we generated at least one Check pragma
4423
4424 if Stmts /= No_List then
4425
4426 -- Build procedure declaration
4427
4428 SId :=
4429 Make_Defining_Identifier (Loc,
4430 Chars => New_External_Name (Chars (Typ), "Invariant"));
4431 Set_Has_Invariants (SId);
4432 Set_Invariant_Procedure (Typ, SId);
4433
4434 Spec :=
4435 Make_Procedure_Specification (Loc,
4436 Defining_Unit_Name => SId,
4437 Parameter_Specifications => New_List (
4438 Make_Parameter_Specification (Loc,
4439 Defining_Identifier => Object_Entity,
4440 Parameter_Type => New_Occurrence_Of (Typ, Loc))));
4441
4442 PDecl := Make_Subprogram_Declaration (Loc, Specification => Spec);
4443
4444 -- Build procedure body
4445
4446 SId :=
4447 Make_Defining_Identifier (Loc,
4448 Chars => New_External_Name (Chars (Typ), "Invariant"));
4449
4450 Spec :=
4451 Make_Procedure_Specification (Loc,
4452 Defining_Unit_Name => SId,
4453 Parameter_Specifications => New_List (
4454 Make_Parameter_Specification (Loc,
4455 Defining_Identifier =>
4456 Make_Defining_Identifier (Loc, Object_Name),
4457 Parameter_Type => New_Occurrence_Of (Typ, Loc))));
4458
4459 PBody :=
4460 Make_Subprogram_Body (Loc,
4461 Specification => Spec,
4462 Declarations => Empty_List,
4463 Handled_Statement_Sequence =>
4464 Make_Handled_Sequence_Of_Statements (Loc,
4465 Statements => Stmts));
4466
4467 -- Insert procedure declaration and spec at the appropriate points.
4468 -- Skip this if there are no private declarations (that's an error
4469 -- that will be diagnosed elsewhere, and there is no point in having
4470 -- an invariant procedure set if the full declaration is missing).
4471
4472 if Present (Private_Decls) then
4473
4474 -- The spec goes at the end of visible declarations, but they have
4475 -- already been analyzed, so we need to explicitly do the analyze.
4476
4477 Append_To (Visible_Decls, PDecl);
4478 Analyze (PDecl);
4479
4480 -- The body goes at the end of the private declarations, which we
4481 -- have not analyzed yet, so we do not need to perform an explicit
4482 -- analyze call. We skip this if there are no private declarations
4483 -- (this is an error that will be caught elsewhere);
4484
4485 Append_To (Private_Decls, PBody);
4486 end if;
4487 end if;
4488 end Build_Invariant_Procedure;
4489
4490 ------------------------------
4491 -- Build_Predicate_Function --
4492 ------------------------------
4493
4494 -- The procedure that is constructed here has the form
4495
4496 -- function typPredicate (Ixxx : typ) return Boolean is
4497 -- begin
4498 -- return
4499 -- exp1 and then exp2 and then ...
4500 -- and then typ1Predicate (typ1 (Ixxx))
4501 -- and then typ2Predicate (typ2 (Ixxx))
4502 -- and then ...;
4503 -- end typPredicate;
4504
4505 -- Here exp1, and exp2 are expressions from Predicate pragmas. Note that
4506 -- this is the point at which these expressions get analyzed, providing the
4507 -- required delay, and typ1, typ2, are entities from which predicates are
4508 -- inherited. Note that we do NOT generate Check pragmas, that's because we
4509 -- use this function even if checks are off, e.g. for membership tests.
4510
4511 procedure Build_Predicate_Function (Typ : Entity_Id; N : Node_Id) is
4512 Loc : constant Source_Ptr := Sloc (Typ);
4513 Spec : Node_Id;
4514 SId : Entity_Id;
4515 FDecl : Node_Id;
4516 FBody : Node_Id;
4517
4518 Expr : Node_Id;
4519 -- This is the expression for the return statement in the function. It
4520 -- is build by connecting the component predicates with AND THEN.
4521
4522 procedure Add_Call (T : Entity_Id);
4523 -- Includes a call to the predicate function for type T in Expr if T
4524 -- has predicates and Predicate_Function (T) is non-empty.
4525
4526 procedure Add_Predicates;
4527 -- Appends expressions for any Predicate pragmas in the rep item chain
4528 -- Typ to Expr. Note that we look only at items for this exact entity.
4529 -- Inheritance of predicates for the parent type is done by calling the
4530 -- Predicate_Function of the parent type, using Add_Call above.
4531
4532 Object_Name : constant Name_Id := New_Internal_Name ('I');
4533 -- Name for argument of Predicate procedure
4534
4535 Object_Entity : constant Entity_Id :=
4536 Make_Defining_Identifier (Loc, Object_Name);
4537 -- The entity for the spec entity for the argument
4538
4539 Dynamic_Predicate_Present : Boolean := False;
4540 -- Set True if a dynamic predicate is present, results in the entire
4541 -- predicate being considered dynamic even if it looks static
4542
4543 Static_Predicate_Present : Node_Id := Empty;
4544 -- Set to N_Pragma node for a static predicate if one is encountered.
4545
4546 --------------
4547 -- Add_Call --
4548 --------------
4549
4550 procedure Add_Call (T : Entity_Id) is
4551 Exp : Node_Id;
4552
4553 begin
4554 if Present (T) and then Present (Predicate_Function (T)) then
4555 Set_Has_Predicates (Typ);
4556
4557 -- Build the call to the predicate function of T
4558
4559 Exp :=
4560 Make_Predicate_Call
4561 (T, Convert_To (T, Make_Identifier (Loc, Object_Name)));
4562
4563 -- Add call to evolving expression, using AND THEN if needed
4564
4565 if No (Expr) then
4566 Expr := Exp;
4567 else
4568 Expr :=
4569 Make_And_Then (Loc,
4570 Left_Opnd => Relocate_Node (Expr),
4571 Right_Opnd => Exp);
4572 end if;
4573
4574 -- Output info message on inheritance if required. Note we do not
4575 -- give this information for generic actual types, since it is
4576 -- unwelcome noise in that case in instantiations. We also
4577 -- generally suppress the message in instantiations, and also
4578 -- if it involves internal names.
4579
4580 if Opt.List_Inherited_Aspects
4581 and then not Is_Generic_Actual_Type (Typ)
4582 and then Instantiation_Depth (Sloc (Typ)) = 0
4583 and then not Is_Internal_Name (Chars (T))
4584 and then not Is_Internal_Name (Chars (Typ))
4585 then
4586 Error_Msg_Sloc := Sloc (Predicate_Function (T));
4587 Error_Msg_Node_2 := T;
4588 Error_Msg_N ("?info: & inherits predicate from & #", Typ);
4589 end if;
4590 end if;
4591 end Add_Call;
4592
4593 --------------------
4594 -- Add_Predicates --
4595 --------------------
4596
4597 procedure Add_Predicates is
4598 Ritem : Node_Id;
4599 Arg1 : Node_Id;
4600 Arg2 : Node_Id;
4601
4602 procedure Replace_Type_Reference (N : Node_Id);
4603 -- Replace a single occurrence N of the subtype name with a reference
4604 -- to the formal of the predicate function. N can be an identifier
4605 -- referencing the subtype, or a selected component, representing an
4606 -- appropriately qualified occurrence of the subtype name.
4607
4608 procedure Replace_Type_References is
4609 new Replace_Type_References_Generic (Replace_Type_Reference);
4610 -- Traverse an expression changing every occurrence of an identifier
4611 -- whose name matches the name of the subtype with a reference to
4612 -- the formal parameter of the predicate function.
4613
4614 ----------------------------
4615 -- Replace_Type_Reference --
4616 ----------------------------
4617
4618 procedure Replace_Type_Reference (N : Node_Id) is
4619 begin
4620 Rewrite (N, Make_Identifier (Loc, Object_Name));
4621 Set_Entity (N, Object_Entity);
4622 Set_Etype (N, Typ);
4623 end Replace_Type_Reference;
4624
4625 -- Start of processing for Add_Predicates
4626
4627 begin
4628 Ritem := First_Rep_Item (Typ);
4629 while Present (Ritem) loop
4630 if Nkind (Ritem) = N_Pragma
4631 and then Pragma_Name (Ritem) = Name_Predicate
4632 then
4633 if From_Dynamic_Predicate (Ritem) then
4634 Dynamic_Predicate_Present := True;
4635 elsif From_Static_Predicate (Ritem) then
4636 Static_Predicate_Present := Ritem;
4637 end if;
4638
4639 -- Acquire arguments
4640
4641 Arg1 := First (Pragma_Argument_Associations (Ritem));
4642 Arg2 := Next (Arg1);
4643
4644 Arg1 := Get_Pragma_Arg (Arg1);
4645 Arg2 := Get_Pragma_Arg (Arg2);
4646
4647 -- See if this predicate pragma is for the current type or for
4648 -- its full view. A predicate on a private completion is placed
4649 -- on the partial view beause this is the visible entity that
4650 -- is frozen.
4651
4652 if Entity (Arg1) = Typ
4653 or else Full_View (Entity (Arg1)) = Typ
4654 then
4655
4656 -- We have a match, this entry is for our subtype
4657
4658 -- We need to replace any occurrences of the name of the
4659 -- type with references to the object.
4660
4661 Replace_Type_References (Arg2, Chars (Typ));
4662
4663 -- If this predicate comes from an aspect, find the aspect
4664 -- specification, and replace the saved expression because
4665 -- we need the subtype references replaced for the calls to
4666 -- Preanalyze_Spec_Expressin in Check_Aspect_At_Freeze_Point
4667 -- and Check_Aspect_At_End_Of_Declarations.
4668
4669 if From_Aspect_Specification (Ritem) then
4670 declare
4671 Aitem : Node_Id;
4672
4673 begin
4674 -- Loop to find corresponding aspect, note that this
4675 -- must be present given the pragma is marked delayed.
4676
4677 Aitem := Next_Rep_Item (Ritem);
4678 loop
4679 if Nkind (Aitem) = N_Aspect_Specification
4680 and then Aspect_Rep_Item (Aitem) = Ritem
4681 then
4682 Set_Entity
4683 (Identifier (Aitem), New_Copy_Tree (Arg2));
4684 exit;
4685 end if;
4686
4687 Aitem := Next_Rep_Item (Aitem);
4688 end loop;
4689 end;
4690 end if;
4691
4692 -- Now we can add the expression
4693
4694 if No (Expr) then
4695 Expr := Relocate_Node (Arg2);
4696
4697 -- There already was a predicate, so add to it
4698
4699 else
4700 Expr :=
4701 Make_And_Then (Loc,
4702 Left_Opnd => Relocate_Node (Expr),
4703 Right_Opnd => Relocate_Node (Arg2));
4704 end if;
4705 end if;
4706 end if;
4707
4708 Next_Rep_Item (Ritem);
4709 end loop;
4710 end Add_Predicates;
4711
4712 -- Start of processing for Build_Predicate_Function
4713
4714 begin
4715 -- Initialize for construction of statement list
4716
4717 Expr := Empty;
4718
4719 -- Return if already built or if type does not have predicates
4720
4721 if not Has_Predicates (Typ)
4722 or else Present (Predicate_Function (Typ))
4723 then
4724 return;
4725 end if;
4726
4727 -- Add Predicates for the current type
4728
4729 Add_Predicates;
4730
4731 -- Add predicates for ancestor if present
4732
4733 declare
4734 Atyp : constant Entity_Id := Nearest_Ancestor (Typ);
4735 begin
4736 if Present (Atyp) then
4737 Add_Call (Atyp);
4738 end if;
4739 end;
4740
4741 -- If we have predicates, build the function
4742
4743 if Present (Expr) then
4744
4745 -- Build function declaration
4746
4747 pragma Assert (Has_Predicates (Typ));
4748 SId :=
4749 Make_Defining_Identifier (Loc,
4750 Chars => New_External_Name (Chars (Typ), "Predicate"));
4751 Set_Has_Predicates (SId);
4752 Set_Predicate_Function (Typ, SId);
4753
4754 Spec :=
4755 Make_Function_Specification (Loc,
4756 Defining_Unit_Name => SId,
4757 Parameter_Specifications => New_List (
4758 Make_Parameter_Specification (Loc,
4759 Defining_Identifier => Object_Entity,
4760 Parameter_Type => New_Occurrence_Of (Typ, Loc))),
4761 Result_Definition =>
4762 New_Occurrence_Of (Standard_Boolean, Loc));
4763
4764 FDecl := Make_Subprogram_Declaration (Loc, Specification => Spec);
4765
4766 -- Build function body
4767
4768 SId :=
4769 Make_Defining_Identifier (Loc,
4770 Chars => New_External_Name (Chars (Typ), "Predicate"));
4771
4772 Spec :=
4773 Make_Function_Specification (Loc,
4774 Defining_Unit_Name => SId,
4775 Parameter_Specifications => New_List (
4776 Make_Parameter_Specification (Loc,
4777 Defining_Identifier =>
4778 Make_Defining_Identifier (Loc, Object_Name),
4779 Parameter_Type =>
4780 New_Occurrence_Of (Typ, Loc))),
4781 Result_Definition =>
4782 New_Occurrence_Of (Standard_Boolean, Loc));
4783
4784 FBody :=
4785 Make_Subprogram_Body (Loc,
4786 Specification => Spec,
4787 Declarations => Empty_List,
4788 Handled_Statement_Sequence =>
4789 Make_Handled_Sequence_Of_Statements (Loc,
4790 Statements => New_List (
4791 Make_Simple_Return_Statement (Loc,
4792 Expression => Expr))));
4793
4794 -- Insert declaration before freeze node and body after
4795
4796 Insert_Before_And_Analyze (N, FDecl);
4797 Insert_After_And_Analyze (N, FBody);
4798
4799 -- Deal with static predicate case
4800
4801 if Ekind_In (Typ, E_Enumeration_Subtype,
4802 E_Modular_Integer_Subtype,
4803 E_Signed_Integer_Subtype)
4804 and then Is_Static_Subtype (Typ)
4805 and then not Dynamic_Predicate_Present
4806 then
4807 Build_Static_Predicate (Typ, Expr, Object_Name);
4808
4809 if Present (Static_Predicate_Present)
4810 and No (Static_Predicate (Typ))
4811 then
4812 Error_Msg_F
4813 ("expression does not have required form for "
4814 & "static predicate",
4815 Next (First (Pragma_Argument_Associations
4816 (Static_Predicate_Present))));
4817 end if;
4818 end if;
4819 end if;
4820 end Build_Predicate_Function;
4821
4822 ----------------------------
4823 -- Build_Static_Predicate --
4824 ----------------------------
4825
4826 procedure Build_Static_Predicate
4827 (Typ : Entity_Id;
4828 Expr : Node_Id;
4829 Nam : Name_Id)
4830 is
4831 Loc : constant Source_Ptr := Sloc (Expr);
4832
4833 Non_Static : exception;
4834 -- Raised if something non-static is found
4835
4836 Btyp : constant Entity_Id := Base_Type (Typ);
4837
4838 BLo : constant Uint := Expr_Value (Type_Low_Bound (Btyp));
4839 BHi : constant Uint := Expr_Value (Type_High_Bound (Btyp));
4840 -- Low bound and high bound value of base type of Typ
4841
4842 TLo : constant Uint := Expr_Value (Type_Low_Bound (Typ));
4843 THi : constant Uint := Expr_Value (Type_High_Bound (Typ));
4844 -- Low bound and high bound values of static subtype Typ
4845
4846 type REnt is record
4847 Lo, Hi : Uint;
4848 end record;
4849 -- One entry in a Rlist value, a single REnt (range entry) value
4850 -- denotes one range from Lo to Hi. To represent a single value
4851 -- range Lo = Hi = value.
4852
4853 type RList is array (Nat range <>) of REnt;
4854 -- A list of ranges. The ranges are sorted in increasing order,
4855 -- and are disjoint (there is a gap of at least one value between
4856 -- each range in the table). A value is in the set of ranges in
4857 -- Rlist if it lies within one of these ranges
4858
4859 False_Range : constant RList :=
4860 RList'(1 .. 0 => REnt'(No_Uint, No_Uint));
4861 -- An empty set of ranges represents a range list that can never be
4862 -- satisfied, since there are no ranges in which the value could lie,
4863 -- so it does not lie in any of them. False_Range is a canonical value
4864 -- for this empty set, but general processing should test for an Rlist
4865 -- with length zero (see Is_False predicate), since other null ranges
4866 -- may appear which must be treated as False.
4867
4868 True_Range : constant RList := RList'(1 => REnt'(BLo, BHi));
4869 -- Range representing True, value must be in the base range
4870
4871 function "and" (Left, Right : RList) return RList;
4872 -- And's together two range lists, returning a range list. This is
4873 -- a set intersection operation.
4874
4875 function "or" (Left, Right : RList) return RList;
4876 -- Or's together two range lists, returning a range list. This is a
4877 -- set union operation.
4878
4879 function "not" (Right : RList) return RList;
4880 -- Returns complement of a given range list, i.e. a range list
4881 -- representing all the values in TLo .. THi that are not in the
4882 -- input operand Right.
4883
4884 function Build_Val (V : Uint) return Node_Id;
4885 -- Return an analyzed N_Identifier node referencing this value, suitable
4886 -- for use as an entry in the Static_Predicate list. This node is typed
4887 -- with the base type.
4888
4889 function Build_Range (Lo, Hi : Uint) return Node_Id;
4890 -- Return an analyzed N_Range node referencing this range, suitable
4891 -- for use as an entry in the Static_Predicate list. This node is typed
4892 -- with the base type.
4893
4894 function Get_RList (Exp : Node_Id) return RList;
4895 -- This is a recursive routine that converts the given expression into
4896 -- a list of ranges, suitable for use in building the static predicate.
4897
4898 function Is_False (R : RList) return Boolean;
4899 pragma Inline (Is_False);
4900 -- Returns True if the given range list is empty, and thus represents
4901 -- a False list of ranges that can never be satisfied.
4902
4903 function Is_True (R : RList) return Boolean;
4904 -- Returns True if R trivially represents the True predicate by having
4905 -- a single range from BLo to BHi.
4906
4907 function Is_Type_Ref (N : Node_Id) return Boolean;
4908 pragma Inline (Is_Type_Ref);
4909 -- Returns if True if N is a reference to the type for the predicate in
4910 -- the expression (i.e. if it is an identifier whose Chars field matches
4911 -- the Nam given in the call).
4912
4913 function Lo_Val (N : Node_Id) return Uint;
4914 -- Given static expression or static range from a Static_Predicate list,
4915 -- gets expression value or low bound of range.
4916
4917 function Hi_Val (N : Node_Id) return Uint;
4918 -- Given static expression or static range from a Static_Predicate list,
4919 -- gets expression value of high bound of range.
4920
4921 function Membership_Entry (N : Node_Id) return RList;
4922 -- Given a single membership entry (range, value, or subtype), returns
4923 -- the corresponding range list. Raises Static_Error if not static.
4924
4925 function Membership_Entries (N : Node_Id) return RList;
4926 -- Given an element on an alternatives list of a membership operation,
4927 -- returns the range list corresponding to this entry and all following
4928 -- entries (i.e. returns the "or" of this list of values).
4929
4930 function Stat_Pred (Typ : Entity_Id) return RList;
4931 -- Given a type, if it has a static predicate, then return the predicate
4932 -- as a range list, otherwise raise Non_Static.
4933
4934 -----------
4935 -- "and" --
4936 -----------
4937
4938 function "and" (Left, Right : RList) return RList is
4939 FEnt : REnt;
4940 -- First range of result
4941
4942 SLeft : Nat := Left'First;
4943 -- Start of rest of left entries
4944
4945 SRight : Nat := Right'First;
4946 -- Start of rest of right entries
4947
4948 begin
4949 -- If either range is True, return the other
4950
4951 if Is_True (Left) then
4952 return Right;
4953 elsif Is_True (Right) then
4954 return Left;
4955 end if;
4956
4957 -- If either range is False, return False
4958
4959 if Is_False (Left) or else Is_False (Right) then
4960 return False_Range;
4961 end if;
4962
4963 -- Loop to remove entries at start that are disjoint, and thus
4964 -- just get discarded from the result entirely.
4965
4966 loop
4967 -- If no operands left in either operand, result is false
4968
4969 if SLeft > Left'Last or else SRight > Right'Last then
4970 return False_Range;
4971
4972 -- Discard first left operand entry if disjoint with right
4973
4974 elsif Left (SLeft).Hi < Right (SRight).Lo then
4975 SLeft := SLeft + 1;
4976
4977 -- Discard first right operand entry if disjoint with left
4978
4979 elsif Right (SRight).Hi < Left (SLeft).Lo then
4980 SRight := SRight + 1;
4981
4982 -- Otherwise we have an overlapping entry
4983
4984 else
4985 exit;
4986 end if;
4987 end loop;
4988
4989 -- Now we have two non-null operands, and first entries overlap.
4990 -- The first entry in the result will be the overlapping part of
4991 -- these two entries.
4992
4993 FEnt := REnt'(Lo => UI_Max (Left (SLeft).Lo, Right (SRight).Lo),
4994 Hi => UI_Min (Left (SLeft).Hi, Right (SRight).Hi));
4995
4996 -- Now we can remove the entry that ended at a lower value, since
4997 -- its contribution is entirely contained in Fent.
4998
4999 if Left (SLeft).Hi <= Right (SRight).Hi then
5000 SLeft := SLeft + 1;
5001 else
5002 SRight := SRight + 1;
5003 end if;
5004
5005 -- Compute result by concatenating this first entry with the "and"
5006 -- of the remaining parts of the left and right operands. Note that
5007 -- if either of these is empty, "and" will yield empty, so that we
5008 -- will end up with just Fent, which is what we want in that case.
5009
5010 return
5011 FEnt & (Left (SLeft .. Left'Last) and Right (SRight .. Right'Last));
5012 end "and";
5013
5014 -----------
5015 -- "not" --
5016 -----------
5017
5018 function "not" (Right : RList) return RList is
5019 begin
5020 -- Return True if False range
5021
5022 if Is_False (Right) then
5023 return True_Range;
5024 end if;
5025
5026 -- Return False if True range
5027
5028 if Is_True (Right) then
5029 return False_Range;
5030 end if;
5031
5032 -- Here if not trivial case
5033
5034 declare
5035 Result : RList (1 .. Right'Length + 1);
5036 -- May need one more entry for gap at beginning and end
5037
5038 Count : Nat := 0;
5039 -- Number of entries stored in Result
5040
5041 begin
5042 -- Gap at start
5043
5044 if Right (Right'First).Lo > TLo then
5045 Count := Count + 1;
5046 Result (Count) := REnt'(TLo, Right (Right'First).Lo - 1);
5047 end if;
5048
5049 -- Gaps between ranges
5050
5051 for J in Right'First .. Right'Last - 1 loop
5052 Count := Count + 1;
5053 Result (Count) :=
5054 REnt'(Right (J).Hi + 1, Right (J + 1).Lo - 1);
5055 end loop;
5056
5057 -- Gap at end
5058
5059 if Right (Right'Last).Hi < THi then
5060 Count := Count + 1;
5061 Result (Count) := REnt'(Right (Right'Last).Hi + 1, THi);
5062 end if;
5063
5064 return Result (1 .. Count);
5065 end;
5066 end "not";
5067
5068 ----------
5069 -- "or" --
5070 ----------
5071
5072 function "or" (Left, Right : RList) return RList is
5073 FEnt : REnt;
5074 -- First range of result
5075
5076 SLeft : Nat := Left'First;
5077 -- Start of rest of left entries
5078
5079 SRight : Nat := Right'First;
5080 -- Start of rest of right entries
5081
5082 begin
5083 -- If either range is True, return True
5084
5085 if Is_True (Left) or else Is_True (Right) then
5086 return True_Range;
5087 end if;
5088
5089 -- If either range is False (empty), return the other
5090
5091 if Is_False (Left) then
5092 return Right;
5093 elsif Is_False (Right) then
5094 return Left;
5095 end if;
5096
5097 -- Initialize result first entry from left or right operand
5098 -- depending on which starts with the lower range.
5099
5100 if Left (SLeft).Lo < Right (SRight).Lo then
5101 FEnt := Left (SLeft);
5102 SLeft := SLeft + 1;
5103 else
5104 FEnt := Right (SRight);
5105 SRight := SRight + 1;
5106 end if;
5107
5108 -- This loop eats ranges from left and right operands that
5109 -- are contiguous with the first range we are gathering.
5110
5111 loop
5112 -- Eat first entry in left operand if contiguous or
5113 -- overlapped by gathered first operand of result.
5114
5115 if SLeft <= Left'Last
5116 and then Left (SLeft).Lo <= FEnt.Hi + 1
5117 then
5118 FEnt.Hi := UI_Max (FEnt.Hi, Left (SLeft).Hi);
5119 SLeft := SLeft + 1;
5120
5121 -- Eat first entry in right operand if contiguous or
5122 -- overlapped by gathered right operand of result.
5123
5124 elsif SRight <= Right'Last
5125 and then Right (SRight).Lo <= FEnt.Hi + 1
5126 then
5127 FEnt.Hi := UI_Max (FEnt.Hi, Right (SRight).Hi);
5128 SRight := SRight + 1;
5129
5130 -- All done if no more entries to eat!
5131
5132 else
5133 exit;
5134 end if;
5135 end loop;
5136
5137 -- Obtain result as the first entry we just computed, concatenated
5138 -- to the "or" of the remaining results (if one operand is empty,
5139 -- this will just concatenate with the other
5140
5141 return
5142 FEnt & (Left (SLeft .. Left'Last) or Right (SRight .. Right'Last));
5143 end "or";
5144
5145 -----------------
5146 -- Build_Range --
5147 -----------------
5148
5149 function Build_Range (Lo, Hi : Uint) return Node_Id is
5150 Result : Node_Id;
5151 begin
5152 if Lo = Hi then
5153 return Build_Val (Hi);
5154 else
5155 Result :=
5156 Make_Range (Loc,
5157 Low_Bound => Build_Val (Lo),
5158 High_Bound => Build_Val (Hi));
5159 Set_Etype (Result, Btyp);
5160 Set_Analyzed (Result);
5161 return Result;
5162 end if;
5163 end Build_Range;
5164
5165 ---------------
5166 -- Build_Val --
5167 ---------------
5168
5169 function Build_Val (V : Uint) return Node_Id is
5170 Result : Node_Id;
5171
5172 begin
5173 if Is_Enumeration_Type (Typ) then
5174 Result := Get_Enum_Lit_From_Pos (Typ, V, Loc);
5175 else
5176 Result := Make_Integer_Literal (Loc, V);
5177 end if;
5178
5179 Set_Etype (Result, Btyp);
5180 Set_Is_Static_Expression (Result);
5181 Set_Analyzed (Result);
5182 return Result;
5183 end Build_Val;
5184
5185 ---------------
5186 -- Get_RList --
5187 ---------------
5188
5189 function Get_RList (Exp : Node_Id) return RList is
5190 Op : Node_Kind;
5191 Val : Uint;
5192
5193 begin
5194 -- Static expression can only be true or false
5195
5196 if Is_OK_Static_Expression (Exp) then
5197
5198 -- For False
5199
5200 if Expr_Value (Exp) = 0 then
5201 return False_Range;
5202 else
5203 return True_Range;
5204 end if;
5205 end if;
5206
5207 -- Otherwise test node type
5208
5209 Op := Nkind (Exp);
5210
5211 case Op is
5212
5213 -- And
5214
5215 when N_Op_And | N_And_Then =>
5216 return Get_RList (Left_Opnd (Exp))
5217 and
5218 Get_RList (Right_Opnd (Exp));
5219
5220 -- Or
5221
5222 when N_Op_Or | N_Or_Else =>
5223 return Get_RList (Left_Opnd (Exp))
5224 or
5225 Get_RList (Right_Opnd (Exp));
5226
5227 -- Not
5228
5229 when N_Op_Not =>
5230 return not Get_RList (Right_Opnd (Exp));
5231
5232 -- Comparisons of type with static value
5233
5234 when N_Op_Compare =>
5235 -- Type is left operand
5236
5237 if Is_Type_Ref (Left_Opnd (Exp))
5238 and then Is_OK_Static_Expression (Right_Opnd (Exp))
5239 then
5240 Val := Expr_Value (Right_Opnd (Exp));
5241
5242 -- Typ is right operand
5243
5244 elsif Is_Type_Ref (Right_Opnd (Exp))
5245 and then Is_OK_Static_Expression (Left_Opnd (Exp))
5246 then
5247 Val := Expr_Value (Left_Opnd (Exp));
5248
5249 -- Invert sense of comparison
5250
5251 case Op is
5252 when N_Op_Gt => Op := N_Op_Lt;
5253 when N_Op_Lt => Op := N_Op_Gt;
5254 when N_Op_Ge => Op := N_Op_Le;
5255 when N_Op_Le => Op := N_Op_Ge;
5256 when others => null;
5257 end case;
5258
5259 -- Other cases are non-static
5260
5261 else
5262 raise Non_Static;
5263 end if;
5264
5265 -- Construct range according to comparison operation
5266
5267 case Op is
5268 when N_Op_Eq =>
5269 return RList'(1 => REnt'(Val, Val));
5270
5271 when N_Op_Ge =>
5272 return RList'(1 => REnt'(Val, BHi));
5273
5274 when N_Op_Gt =>
5275 return RList'(1 => REnt'(Val + 1, BHi));
5276
5277 when N_Op_Le =>
5278 return RList'(1 => REnt'(BLo, Val));
5279
5280 when N_Op_Lt =>
5281 return RList'(1 => REnt'(BLo, Val - 1));
5282
5283 when N_Op_Ne =>
5284 return RList'(REnt'(BLo, Val - 1),
5285 REnt'(Val + 1, BHi));
5286
5287 when others =>
5288 raise Program_Error;
5289 end case;
5290
5291 -- Membership (IN)
5292
5293 when N_In =>
5294 if not Is_Type_Ref (Left_Opnd (Exp)) then
5295 raise Non_Static;
5296 end if;
5297
5298 if Present (Right_Opnd (Exp)) then
5299 return Membership_Entry (Right_Opnd (Exp));
5300 else
5301 return Membership_Entries (First (Alternatives (Exp)));
5302 end if;
5303
5304 -- Negative membership (NOT IN)
5305
5306 when N_Not_In =>
5307 if not Is_Type_Ref (Left_Opnd (Exp)) then
5308 raise Non_Static;
5309 end if;
5310
5311 if Present (Right_Opnd (Exp)) then
5312 return not Membership_Entry (Right_Opnd (Exp));
5313 else
5314 return not Membership_Entries (First (Alternatives (Exp)));
5315 end if;
5316
5317 -- Function call, may be call to static predicate
5318
5319 when N_Function_Call =>
5320 if Is_Entity_Name (Name (Exp)) then
5321 declare
5322 Ent : constant Entity_Id := Entity (Name (Exp));
5323 begin
5324 if Has_Predicates (Ent) then
5325 return Stat_Pred (Etype (First_Formal (Ent)));
5326 end if;
5327 end;
5328 end if;
5329
5330 -- Other function call cases are non-static
5331
5332 raise Non_Static;
5333
5334 -- Qualified expression, dig out the expression
5335
5336 when N_Qualified_Expression =>
5337 return Get_RList (Expression (Exp));
5338
5339 -- Xor operator
5340
5341 when N_Op_Xor =>
5342 return (Get_RList (Left_Opnd (Exp))
5343 and not Get_RList (Right_Opnd (Exp)))
5344 or (Get_RList (Right_Opnd (Exp))
5345 and not Get_RList (Left_Opnd (Exp)));
5346
5347 -- Any other node type is non-static
5348
5349 when others =>
5350 raise Non_Static;
5351 end case;
5352 end Get_RList;
5353
5354 ------------
5355 -- Hi_Val --
5356 ------------
5357
5358 function Hi_Val (N : Node_Id) return Uint is
5359 begin
5360 if Is_Static_Expression (N) then
5361 return Expr_Value (N);
5362 else
5363 pragma Assert (Nkind (N) = N_Range);
5364 return Expr_Value (High_Bound (N));
5365 end if;
5366 end Hi_Val;
5367
5368 --------------
5369 -- Is_False --
5370 --------------
5371
5372 function Is_False (R : RList) return Boolean is
5373 begin
5374 return R'Length = 0;
5375 end Is_False;
5376
5377 -------------
5378 -- Is_True --
5379 -------------
5380
5381 function Is_True (R : RList) return Boolean is
5382 begin
5383 return R'Length = 1
5384 and then R (R'First).Lo = BLo
5385 and then R (R'First).Hi = BHi;
5386 end Is_True;
5387
5388 -----------------
5389 -- Is_Type_Ref --
5390 -----------------
5391
5392 function Is_Type_Ref (N : Node_Id) return Boolean is
5393 begin
5394 return Nkind (N) = N_Identifier and then Chars (N) = Nam;
5395 end Is_Type_Ref;
5396
5397 ------------
5398 -- Lo_Val --
5399 ------------
5400
5401 function Lo_Val (N : Node_Id) return Uint is
5402 begin
5403 if Is_Static_Expression (N) then
5404 return Expr_Value (N);
5405 else
5406 pragma Assert (Nkind (N) = N_Range);
5407 return Expr_Value (Low_Bound (N));
5408 end if;
5409 end Lo_Val;
5410
5411 ------------------------
5412 -- Membership_Entries --
5413 ------------------------
5414
5415 function Membership_Entries (N : Node_Id) return RList is
5416 begin
5417 if No (Next (N)) then
5418 return Membership_Entry (N);
5419 else
5420 return Membership_Entry (N) or Membership_Entries (Next (N));
5421 end if;
5422 end Membership_Entries;
5423
5424 ----------------------
5425 -- Membership_Entry --
5426 ----------------------
5427
5428 function Membership_Entry (N : Node_Id) return RList is
5429 Val : Uint;
5430 SLo : Uint;
5431 SHi : Uint;
5432
5433 begin
5434 -- Range case
5435
5436 if Nkind (N) = N_Range then
5437 if not Is_Static_Expression (Low_Bound (N))
5438 or else
5439 not Is_Static_Expression (High_Bound (N))
5440 then
5441 raise Non_Static;
5442 else
5443 SLo := Expr_Value (Low_Bound (N));
5444 SHi := Expr_Value (High_Bound (N));
5445 return RList'(1 => REnt'(SLo, SHi));
5446 end if;
5447
5448 -- Static expression case
5449
5450 elsif Is_Static_Expression (N) then
5451 Val := Expr_Value (N);
5452 return RList'(1 => REnt'(Val, Val));
5453
5454 -- Identifier (other than static expression) case
5455
5456 else pragma Assert (Nkind (N) = N_Identifier);
5457
5458 -- Type case
5459
5460 if Is_Type (Entity (N)) then
5461
5462 -- If type has predicates, process them
5463
5464 if Has_Predicates (Entity (N)) then
5465 return Stat_Pred (Entity (N));
5466
5467 -- For static subtype without predicates, get range
5468
5469 elsif Is_Static_Subtype (Entity (N)) then
5470 SLo := Expr_Value (Type_Low_Bound (Entity (N)));
5471 SHi := Expr_Value (Type_High_Bound (Entity (N)));
5472 return RList'(1 => REnt'(SLo, SHi));
5473
5474 -- Any other type makes us non-static
5475
5476 else
5477 raise Non_Static;
5478 end if;
5479
5480 -- Any other kind of identifier in predicate (e.g. a non-static
5481 -- expression value) means this is not a static predicate.
5482
5483 else
5484 raise Non_Static;
5485 end if;
5486 end if;
5487 end Membership_Entry;
5488
5489 ---------------
5490 -- Stat_Pred --
5491 ---------------
5492
5493 function Stat_Pred (Typ : Entity_Id) return RList is
5494 begin
5495 -- Not static if type does not have static predicates
5496
5497 if not Has_Predicates (Typ)
5498 or else No (Static_Predicate (Typ))
5499 then
5500 raise Non_Static;
5501 end if;
5502
5503 -- Otherwise we convert the predicate list to a range list
5504
5505 declare
5506 Result : RList (1 .. List_Length (Static_Predicate (Typ)));
5507 P : Node_Id;
5508
5509 begin
5510 P := First (Static_Predicate (Typ));
5511 for J in Result'Range loop
5512 Result (J) := REnt'(Lo_Val (P), Hi_Val (P));
5513 Next (P);
5514 end loop;
5515
5516 return Result;
5517 end;
5518 end Stat_Pred;
5519
5520 -- Start of processing for Build_Static_Predicate
5521
5522 begin
5523 -- Now analyze the expression to see if it is a static predicate
5524
5525 declare
5526 Ranges : constant RList := Get_RList (Expr);
5527 -- Range list from expression if it is static
5528
5529 Plist : List_Id;
5530
5531 begin
5532 -- Convert range list into a form for the static predicate. In the
5533 -- Ranges array, we just have raw ranges, these must be converted
5534 -- to properly typed and analyzed static expressions or range nodes.
5535
5536 -- Note: here we limit ranges to the ranges of the subtype, so that
5537 -- a predicate is always false for values outside the subtype. That
5538 -- seems fine, such values are invalid anyway, and considering them
5539 -- to fail the predicate seems allowed and friendly, and furthermore
5540 -- simplifies processing for case statements and loops.
5541
5542 Plist := New_List;
5543
5544 for J in Ranges'Range loop
5545 declare
5546 Lo : Uint := Ranges (J).Lo;
5547 Hi : Uint := Ranges (J).Hi;
5548
5549 begin
5550 -- Ignore completely out of range entry
5551
5552 if Hi < TLo or else Lo > THi then
5553 null;
5554
5555 -- Otherwise process entry
5556
5557 else
5558 -- Adjust out of range value to subtype range
5559
5560 if Lo < TLo then
5561 Lo := TLo;
5562 end if;
5563
5564 if Hi > THi then
5565 Hi := THi;
5566 end if;
5567
5568 -- Convert range into required form
5569
5570 if Lo = Hi then
5571 Append_To (Plist, Build_Val (Lo));
5572 else
5573 Append_To (Plist, Build_Range (Lo, Hi));
5574 end if;
5575 end if;
5576 end;
5577 end loop;
5578
5579 -- Processing was successful and all entries were static, so now we
5580 -- can store the result as the predicate list.
5581
5582 Set_Static_Predicate (Typ, Plist);
5583
5584 -- The processing for static predicates put the expression into
5585 -- canonical form as a series of ranges. It also eliminated
5586 -- duplicates and collapsed and combined ranges. We might as well
5587 -- replace the alternatives list of the right operand of the
5588 -- membership test with the static predicate list, which will
5589 -- usually be more efficient.
5590
5591 declare
5592 New_Alts : constant List_Id := New_List;
5593 Old_Node : Node_Id;
5594 New_Node : Node_Id;
5595
5596 begin
5597 Old_Node := First (Plist);
5598 while Present (Old_Node) loop
5599 New_Node := New_Copy (Old_Node);
5600
5601 if Nkind (New_Node) = N_Range then
5602 Set_Low_Bound (New_Node, New_Copy (Low_Bound (Old_Node)));
5603 Set_High_Bound (New_Node, New_Copy (High_Bound (Old_Node)));
5604 end if;
5605
5606 Append_To (New_Alts, New_Node);
5607 Next (Old_Node);
5608 end loop;
5609
5610 -- If empty list, replace by False
5611
5612 if Is_Empty_List (New_Alts) then
5613 Rewrite (Expr, New_Occurrence_Of (Standard_False, Loc));
5614
5615 -- Else replace by set membership test
5616
5617 else
5618 Rewrite (Expr,
5619 Make_In (Loc,
5620 Left_Opnd => Make_Identifier (Loc, Nam),
5621 Right_Opnd => Empty,
5622 Alternatives => New_Alts));
5623
5624 -- Resolve new expression in function context
5625
5626 Install_Formals (Predicate_Function (Typ));
5627 Push_Scope (Predicate_Function (Typ));
5628 Analyze_And_Resolve (Expr, Standard_Boolean);
5629 Pop_Scope;
5630 end if;
5631 end;
5632 end;
5633
5634 -- If non-static, return doing nothing
5635
5636 exception
5637 when Non_Static =>
5638 return;
5639 end Build_Static_Predicate;
5640
5641 -----------------------------------------
5642 -- Check_Aspect_At_End_Of_Declarations --
5643 -----------------------------------------
5644
5645 procedure Check_Aspect_At_End_Of_Declarations (ASN : Node_Id) is
5646 Ent : constant Entity_Id := Entity (ASN);
5647 Ident : constant Node_Id := Identifier (ASN);
5648
5649 Freeze_Expr : constant Node_Id := Expression (ASN);
5650 -- Expression from call to Check_Aspect_At_Freeze_Point
5651
5652 End_Decl_Expr : constant Node_Id := Entity (Ident);
5653 -- Expression to be analyzed at end of declarations
5654
5655 T : constant Entity_Id := Etype (Freeze_Expr);
5656 -- Type required for preanalyze call
5657
5658 A_Id : constant Aspect_Id := Get_Aspect_Id (Chars (Ident));
5659
5660 Err : Boolean;
5661 -- Set False if error
5662
5663 -- On entry to this procedure, Entity (Ident) contains a copy of the
5664 -- original expression from the aspect, saved for this purpose, and
5665 -- but Expression (Ident) is a preanalyzed copy of the expression,
5666 -- preanalyzed just after the freeze point.
5667
5668 begin
5669 -- Case of stream attributes, just have to compare entities
5670
5671 if A_Id = Aspect_Input or else
5672 A_Id = Aspect_Output or else
5673 A_Id = Aspect_Read or else
5674 A_Id = Aspect_Write
5675 then
5676 Analyze (End_Decl_Expr);
5677 Err := Entity (End_Decl_Expr) /= Entity (Freeze_Expr);
5678
5679 elsif A_Id = Aspect_Variable_Indexing or else
5680 A_Id = Aspect_Constant_Indexing or else
5681 A_Id = Aspect_Default_Iterator or else
5682 A_Id = Aspect_Iterator_Element
5683 then
5684 Analyze (End_Decl_Expr);
5685 Analyze (Aspect_Rep_Item (ASN));
5686
5687 -- If the end of declarations comes before any other freeze
5688 -- point, the Freeze_Expr is not analyzed: no check needed.
5689
5690 Err :=
5691 Analyzed (Freeze_Expr)
5692 and then not In_Instance
5693 and then Entity (End_Decl_Expr) /= Entity (Freeze_Expr);
5694
5695 -- All other cases
5696
5697 else
5698 Preanalyze_Spec_Expression (End_Decl_Expr, T);
5699 Err := not Fully_Conformant_Expressions (End_Decl_Expr, Freeze_Expr);
5700 end if;
5701
5702 -- Output error message if error
5703
5704 if Err then
5705 Error_Msg_NE
5706 ("visibility of aspect for& changes after freeze point",
5707 ASN, Ent);
5708 Error_Msg_NE
5709 ("?info: & is frozen here, aspects evaluated at this point",
5710 Freeze_Node (Ent), Ent);
5711 end if;
5712 end Check_Aspect_At_End_Of_Declarations;
5713
5714 ----------------------------------
5715 -- Check_Aspect_At_Freeze_Point --
5716 ----------------------------------
5717
5718 procedure Check_Aspect_At_Freeze_Point (ASN : Node_Id) is
5719 Ident : constant Node_Id := Identifier (ASN);
5720 -- Identifier (use Entity field to save expression)
5721
5722 T : Entity_Id;
5723 -- Type required for preanalyze call
5724
5725 A_Id : constant Aspect_Id := Get_Aspect_Id (Chars (Ident));
5726
5727 begin
5728 -- On entry to this procedure, Entity (Ident) contains a copy of the
5729 -- original expression from the aspect, saved for this purpose.
5730
5731 -- On exit from this procedure Entity (Ident) is unchanged, still
5732 -- containing that copy, but Expression (Ident) is a preanalyzed copy
5733 -- of the expression, preanalyzed just after the freeze point.
5734
5735 -- Make a copy of the expression to be preanalyed
5736
5737 Set_Expression (ASN, New_Copy_Tree (Entity (Ident)));
5738
5739 -- Find type for preanalyze call
5740
5741 case A_Id is
5742
5743 -- No_Aspect should be impossible
5744
5745 when No_Aspect =>
5746 raise Program_Error;
5747
5748 -- Library unit aspects should be impossible (never delayed)
5749
5750 when Library_Unit_Aspects =>
5751 raise Program_Error;
5752
5753 -- Aspects taking an optional boolean argument. Should be impossible
5754 -- since these are never delayed.
5755
5756 when Boolean_Aspects =>
5757 raise Program_Error;
5758
5759 -- Test_Case aspect applies to entries and subprograms, hence should
5760 -- never be delayed.
5761
5762 when Aspect_Test_Case =>
5763 raise Program_Error;
5764
5765 -- Default_Value is resolved with the type entity in question
5766
5767 when Aspect_Default_Value =>
5768 T := Entity (ASN);
5769
5770 -- Default_Component_Value is resolved with the component type
5771
5772 when Aspect_Default_Component_Value =>
5773 T := Component_Type (Entity (ASN));
5774
5775 -- Aspects corresponding to attribute definition clauses
5776
5777 when Aspect_Address =>
5778 T := RTE (RE_Address);
5779
5780 when Aspect_Bit_Order =>
5781 T := RTE (RE_Bit_Order);
5782
5783 when Aspect_External_Tag =>
5784 T := Standard_String;
5785
5786 when Aspect_Storage_Pool =>
5787 T := Class_Wide_Type (RTE (RE_Root_Storage_Pool));
5788
5789 when Aspect_Alignment |
5790 Aspect_Component_Size |
5791 Aspect_Machine_Radix |
5792 Aspect_Object_Size |
5793 Aspect_Size |
5794 Aspect_Storage_Size |
5795 Aspect_Stream_Size |
5796 Aspect_Value_Size =>
5797 T := Any_Integer;
5798
5799 -- Stream attribute. Special case, the expression is just an entity
5800 -- that does not need any resolution, so just analyze.
5801
5802 when Aspect_Input |
5803 Aspect_Output |
5804 Aspect_Read |
5805 Aspect_Write =>
5806 Analyze (Expression (ASN));
5807 return;
5808
5809 -- Same for Iterator aspects, where the expression is a function
5810 -- name. Legality rules are checked separately.
5811
5812 when Aspect_Constant_Indexing |
5813 Aspect_Default_Iterator |
5814 Aspect_Iterator_Element |
5815 Aspect_Implicit_Dereference |
5816 Aspect_Variable_Indexing =>
5817 Analyze (Expression (ASN));
5818 return;
5819
5820 -- Suppress/Unsuppress/Warnings should never be delayed
5821
5822 when Aspect_Suppress |
5823 Aspect_Unsuppress |
5824 Aspect_Warnings =>
5825 raise Program_Error;
5826
5827 -- Pre/Post/Invariant/Predicate take boolean expressions
5828
5829 when Aspect_Dynamic_Predicate |
5830 Aspect_Invariant |
5831 Aspect_Pre |
5832 Aspect_Precondition |
5833 Aspect_Post |
5834 Aspect_Postcondition |
5835 Aspect_Predicate |
5836 Aspect_Static_Predicate |
5837 Aspect_Type_Invariant =>
5838 T := Standard_Boolean;
5839 end case;
5840
5841 -- Do the preanalyze call
5842
5843 Preanalyze_Spec_Expression (Expression (ASN), T);
5844 end Check_Aspect_At_Freeze_Point;
5845
5846 -----------------------------------
5847 -- Check_Constant_Address_Clause --
5848 -----------------------------------
5849
5850 procedure Check_Constant_Address_Clause
5851 (Expr : Node_Id;
5852 U_Ent : Entity_Id)
5853 is
5854 procedure Check_At_Constant_Address (Nod : Node_Id);
5855 -- Checks that the given node N represents a name whose 'Address is
5856 -- constant (in the same sense as OK_Constant_Address_Clause, i.e. the
5857 -- address value is the same at the point of declaration of U_Ent and at
5858 -- the time of elaboration of the address clause.
5859
5860 procedure Check_Expr_Constants (Nod : Node_Id);
5861 -- Checks that Nod meets the requirements for a constant address clause
5862 -- in the sense of the enclosing procedure.
5863
5864 procedure Check_List_Constants (Lst : List_Id);
5865 -- Check that all elements of list Lst meet the requirements for a
5866 -- constant address clause in the sense of the enclosing procedure.
5867
5868 -------------------------------
5869 -- Check_At_Constant_Address --
5870 -------------------------------
5871
5872 procedure Check_At_Constant_Address (Nod : Node_Id) is
5873 begin
5874 if Is_Entity_Name (Nod) then
5875 if Present (Address_Clause (Entity ((Nod)))) then
5876 Error_Msg_NE
5877 ("invalid address clause for initialized object &!",
5878 Nod, U_Ent);
5879 Error_Msg_NE
5880 ("address for& cannot" &
5881 " depend on another address clause! (RM 13.1(22))!",
5882 Nod, U_Ent);
5883
5884 elsif In_Same_Source_Unit (Entity (Nod), U_Ent)
5885 and then Sloc (U_Ent) < Sloc (Entity (Nod))
5886 then
5887 Error_Msg_NE
5888 ("invalid address clause for initialized object &!",
5889 Nod, U_Ent);
5890 Error_Msg_Node_2 := U_Ent;
5891 Error_Msg_NE
5892 ("\& must be defined before & (RM 13.1(22))!",
5893 Nod, Entity (Nod));
5894 end if;
5895
5896 elsif Nkind (Nod) = N_Selected_Component then
5897 declare
5898 T : constant Entity_Id := Etype (Prefix (Nod));
5899
5900 begin
5901 if (Is_Record_Type (T)
5902 and then Has_Discriminants (T))
5903 or else
5904 (Is_Access_Type (T)
5905 and then Is_Record_Type (Designated_Type (T))
5906 and then Has_Discriminants (Designated_Type (T)))
5907 then
5908 Error_Msg_NE
5909 ("invalid address clause for initialized object &!",
5910 Nod, U_Ent);
5911 Error_Msg_N
5912 ("\address cannot depend on component" &
5913 " of discriminated record (RM 13.1(22))!",
5914 Nod);
5915 else
5916 Check_At_Constant_Address (Prefix (Nod));
5917 end if;
5918 end;
5919
5920 elsif Nkind (Nod) = N_Indexed_Component then
5921 Check_At_Constant_Address (Prefix (Nod));
5922 Check_List_Constants (Expressions (Nod));
5923
5924 else
5925 Check_Expr_Constants (Nod);
5926 end if;
5927 end Check_At_Constant_Address;
5928
5929 --------------------------
5930 -- Check_Expr_Constants --
5931 --------------------------
5932
5933 procedure Check_Expr_Constants (Nod : Node_Id) is
5934 Loc_U_Ent : constant Source_Ptr := Sloc (U_Ent);
5935 Ent : Entity_Id := Empty;
5936
5937 begin
5938 if Nkind (Nod) in N_Has_Etype
5939 and then Etype (Nod) = Any_Type
5940 then
5941 return;
5942 end if;
5943
5944 case Nkind (Nod) is
5945 when N_Empty | N_Error =>
5946 return;
5947
5948 when N_Identifier | N_Expanded_Name =>
5949 Ent := Entity (Nod);
5950
5951 -- We need to look at the original node if it is different
5952 -- from the node, since we may have rewritten things and
5953 -- substituted an identifier representing the rewrite.
5954
5955 if Original_Node (Nod) /= Nod then
5956 Check_Expr_Constants (Original_Node (Nod));
5957
5958 -- If the node is an object declaration without initial
5959 -- value, some code has been expanded, and the expression
5960 -- is not constant, even if the constituents might be
5961 -- acceptable, as in A'Address + offset.
5962
5963 if Ekind (Ent) = E_Variable
5964 and then
5965 Nkind (Declaration_Node (Ent)) = N_Object_Declaration
5966 and then
5967 No (Expression (Declaration_Node (Ent)))
5968 then
5969 Error_Msg_NE
5970 ("invalid address clause for initialized object &!",
5971 Nod, U_Ent);
5972
5973 -- If entity is constant, it may be the result of expanding
5974 -- a check. We must verify that its declaration appears
5975 -- before the object in question, else we also reject the
5976 -- address clause.
5977
5978 elsif Ekind (Ent) = E_Constant
5979 and then In_Same_Source_Unit (Ent, U_Ent)
5980 and then Sloc (Ent) > Loc_U_Ent
5981 then
5982 Error_Msg_NE
5983 ("invalid address clause for initialized object &!",
5984 Nod, U_Ent);
5985 end if;
5986
5987 return;
5988 end if;
5989
5990 -- Otherwise look at the identifier and see if it is OK
5991
5992 if Ekind_In (Ent, E_Named_Integer, E_Named_Real)
5993 or else Is_Type (Ent)
5994 then
5995 return;
5996
5997 elsif
5998 Ekind (Ent) = E_Constant
5999 or else
6000 Ekind (Ent) = E_In_Parameter
6001 then
6002 -- This is the case where we must have Ent defined before
6003 -- U_Ent. Clearly if they are in different units this
6004 -- requirement is met since the unit containing Ent is
6005 -- already processed.
6006
6007 if not In_Same_Source_Unit (Ent, U_Ent) then
6008 return;
6009
6010 -- Otherwise location of Ent must be before the location
6011 -- of U_Ent, that's what prior defined means.
6012
6013 elsif Sloc (Ent) < Loc_U_Ent then
6014 return;
6015
6016 else
6017 Error_Msg_NE
6018 ("invalid address clause for initialized object &!",
6019 Nod, U_Ent);
6020 Error_Msg_Node_2 := U_Ent;
6021 Error_Msg_NE
6022 ("\& must be defined before & (RM 13.1(22))!",
6023 Nod, Ent);
6024 end if;
6025
6026 elsif Nkind (Original_Node (Nod)) = N_Function_Call then
6027 Check_Expr_Constants (Original_Node (Nod));
6028
6029 else
6030 Error_Msg_NE
6031 ("invalid address clause for initialized object &!",
6032 Nod, U_Ent);
6033
6034 if Comes_From_Source (Ent) then
6035 Error_Msg_NE
6036 ("\reference to variable& not allowed"
6037 & " (RM 13.1(22))!", Nod, Ent);
6038 else
6039 Error_Msg_N
6040 ("non-static expression not allowed"
6041 & " (RM 13.1(22))!", Nod);
6042 end if;
6043 end if;
6044
6045 when N_Integer_Literal =>
6046
6047 -- If this is a rewritten unchecked conversion, in a system
6048 -- where Address is an integer type, always use the base type
6049 -- for a literal value. This is user-friendly and prevents
6050 -- order-of-elaboration issues with instances of unchecked
6051 -- conversion.
6052
6053 if Nkind (Original_Node (Nod)) = N_Function_Call then
6054 Set_Etype (Nod, Base_Type (Etype (Nod)));
6055 end if;
6056
6057 when N_Real_Literal |
6058 N_String_Literal |
6059 N_Character_Literal =>
6060 return;
6061
6062 when N_Range =>
6063 Check_Expr_Constants (Low_Bound (Nod));
6064 Check_Expr_Constants (High_Bound (Nod));
6065
6066 when N_Explicit_Dereference =>
6067 Check_Expr_Constants (Prefix (Nod));
6068
6069 when N_Indexed_Component =>
6070 Check_Expr_Constants (Prefix (Nod));
6071 Check_List_Constants (Expressions (Nod));
6072
6073 when N_Slice =>
6074 Check_Expr_Constants (Prefix (Nod));
6075 Check_Expr_Constants (Discrete_Range (Nod));
6076
6077 when N_Selected_Component =>
6078 Check_Expr_Constants (Prefix (Nod));
6079
6080 when N_Attribute_Reference =>
6081 if Attribute_Name (Nod) = Name_Address
6082 or else
6083 Attribute_Name (Nod) = Name_Access
6084 or else
6085 Attribute_Name (Nod) = Name_Unchecked_Access
6086 or else
6087 Attribute_Name (Nod) = Name_Unrestricted_Access
6088 then
6089 Check_At_Constant_Address (Prefix (Nod));
6090
6091 else
6092 Check_Expr_Constants (Prefix (Nod));
6093 Check_List_Constants (Expressions (Nod));
6094 end if;
6095
6096 when N_Aggregate =>
6097 Check_List_Constants (Component_Associations (Nod));
6098 Check_List_Constants (Expressions (Nod));
6099
6100 when N_Component_Association =>
6101 Check_Expr_Constants (Expression (Nod));
6102
6103 when N_Extension_Aggregate =>
6104 Check_Expr_Constants (Ancestor_Part (Nod));
6105 Check_List_Constants (Component_Associations (Nod));
6106 Check_List_Constants (Expressions (Nod));
6107
6108 when N_Null =>
6109 return;
6110
6111 when N_Binary_Op | N_Short_Circuit | N_Membership_Test =>
6112 Check_Expr_Constants (Left_Opnd (Nod));
6113 Check_Expr_Constants (Right_Opnd (Nod));
6114
6115 when N_Unary_Op =>
6116 Check_Expr_Constants (Right_Opnd (Nod));
6117
6118 when N_Type_Conversion |
6119 N_Qualified_Expression |
6120 N_Allocator =>
6121 Check_Expr_Constants (Expression (Nod));
6122
6123 when N_Unchecked_Type_Conversion =>
6124 Check_Expr_Constants (Expression (Nod));
6125
6126 -- If this is a rewritten unchecked conversion, subtypes in
6127 -- this node are those created within the instance. To avoid
6128 -- order of elaboration issues, replace them with their base
6129 -- types. Note that address clauses can cause order of
6130 -- elaboration problems because they are elaborated by the
6131 -- back-end at the point of definition, and may mention
6132 -- entities declared in between (as long as everything is
6133 -- static). It is user-friendly to allow unchecked conversions
6134 -- in this context.
6135
6136 if Nkind (Original_Node (Nod)) = N_Function_Call then
6137 Set_Etype (Expression (Nod),
6138 Base_Type (Etype (Expression (Nod))));
6139 Set_Etype (Nod, Base_Type (Etype (Nod)));
6140 end if;
6141
6142 when N_Function_Call =>
6143 if not Is_Pure (Entity (Name (Nod))) then
6144 Error_Msg_NE
6145 ("invalid address clause for initialized object &!",
6146 Nod, U_Ent);
6147
6148 Error_Msg_NE
6149 ("\function & is not pure (RM 13.1(22))!",
6150 Nod, Entity (Name (Nod)));
6151
6152 else
6153 Check_List_Constants (Parameter_Associations (Nod));
6154 end if;
6155
6156 when N_Parameter_Association =>
6157 Check_Expr_Constants (Explicit_Actual_Parameter (Nod));
6158
6159 when others =>
6160 Error_Msg_NE
6161 ("invalid address clause for initialized object &!",
6162 Nod, U_Ent);
6163 Error_Msg_NE
6164 ("\must be constant defined before& (RM 13.1(22))!",
6165 Nod, U_Ent);
6166 end case;
6167 end Check_Expr_Constants;
6168
6169 --------------------------
6170 -- Check_List_Constants --
6171 --------------------------
6172
6173 procedure Check_List_Constants (Lst : List_Id) is
6174 Nod1 : Node_Id;
6175
6176 begin
6177 if Present (Lst) then
6178 Nod1 := First (Lst);
6179 while Present (Nod1) loop
6180 Check_Expr_Constants (Nod1);
6181 Next (Nod1);
6182 end loop;
6183 end if;
6184 end Check_List_Constants;
6185
6186 -- Start of processing for Check_Constant_Address_Clause
6187
6188 begin
6189 -- If rep_clauses are to be ignored, no need for legality checks. In
6190 -- particular, no need to pester user about rep clauses that violate
6191 -- the rule on constant addresses, given that these clauses will be
6192 -- removed by Freeze before they reach the back end.
6193
6194 if not Ignore_Rep_Clauses then
6195 Check_Expr_Constants (Expr);
6196 end if;
6197 end Check_Constant_Address_Clause;
6198
6199 ----------------------------------------
6200 -- Check_Record_Representation_Clause --
6201 ----------------------------------------
6202
6203 procedure Check_Record_Representation_Clause (N : Node_Id) is
6204 Loc : constant Source_Ptr := Sloc (N);
6205 Ident : constant Node_Id := Identifier (N);
6206 Rectype : Entity_Id;
6207 Fent : Entity_Id;
6208 CC : Node_Id;
6209 Fbit : Uint;
6210 Lbit : Uint;
6211 Hbit : Uint := Uint_0;
6212 Comp : Entity_Id;
6213 Pcomp : Entity_Id;
6214
6215 Max_Bit_So_Far : Uint;
6216 -- Records the maximum bit position so far. If all field positions
6217 -- are monotonically increasing, then we can skip the circuit for
6218 -- checking for overlap, since no overlap is possible.
6219
6220 Tagged_Parent : Entity_Id := Empty;
6221 -- This is set in the case of a derived tagged type for which we have
6222 -- Is_Fully_Repped_Tagged_Type True (indicating that all components are
6223 -- positioned by record representation clauses). In this case we must
6224 -- check for overlap between components of this tagged type, and the
6225 -- components of its parent. Tagged_Parent will point to this parent
6226 -- type. For all other cases Tagged_Parent is left set to Empty.
6227
6228 Parent_Last_Bit : Uint;
6229 -- Relevant only if Tagged_Parent is set, Parent_Last_Bit indicates the
6230 -- last bit position for any field in the parent type. We only need to
6231 -- check overlap for fields starting below this point.
6232
6233 Overlap_Check_Required : Boolean;
6234 -- Used to keep track of whether or not an overlap check is required
6235
6236 Overlap_Detected : Boolean := False;
6237 -- Set True if an overlap is detected
6238
6239 Ccount : Natural := 0;
6240 -- Number of component clauses in record rep clause
6241
6242 procedure Check_Component_Overlap (C1_Ent, C2_Ent : Entity_Id);
6243 -- Given two entities for record components or discriminants, checks
6244 -- if they have overlapping component clauses and issues errors if so.
6245
6246 procedure Find_Component;
6247 -- Finds component entity corresponding to current component clause (in
6248 -- CC), and sets Comp to the entity, and Fbit/Lbit to the zero origin
6249 -- start/stop bits for the field. If there is no matching component or
6250 -- if the matching component does not have a component clause, then
6251 -- that's an error and Comp is set to Empty, but no error message is
6252 -- issued, since the message was already given. Comp is also set to
6253 -- Empty if the current "component clause" is in fact a pragma.
6254
6255 -----------------------------
6256 -- Check_Component_Overlap --
6257 -----------------------------
6258
6259 procedure Check_Component_Overlap (C1_Ent, C2_Ent : Entity_Id) is
6260 CC1 : constant Node_Id := Component_Clause (C1_Ent);
6261 CC2 : constant Node_Id := Component_Clause (C2_Ent);
6262
6263 begin
6264 if Present (CC1) and then Present (CC2) then
6265
6266 -- Exclude odd case where we have two tag fields in the same
6267 -- record, both at location zero. This seems a bit strange, but
6268 -- it seems to happen in some circumstances, perhaps on an error.
6269
6270 if Chars (C1_Ent) = Name_uTag
6271 and then
6272 Chars (C2_Ent) = Name_uTag
6273 then
6274 return;
6275 end if;
6276
6277 -- Here we check if the two fields overlap
6278
6279 declare
6280 S1 : constant Uint := Component_Bit_Offset (C1_Ent);
6281 S2 : constant Uint := Component_Bit_Offset (C2_Ent);
6282 E1 : constant Uint := S1 + Esize (C1_Ent);
6283 E2 : constant Uint := S2 + Esize (C2_Ent);
6284
6285 begin
6286 if E2 <= S1 or else E1 <= S2 then
6287 null;
6288 else
6289 Error_Msg_Node_2 := Component_Name (CC2);
6290 Error_Msg_Sloc := Sloc (Error_Msg_Node_2);
6291 Error_Msg_Node_1 := Component_Name (CC1);
6292 Error_Msg_N
6293 ("component& overlaps & #", Component_Name (CC1));
6294 Overlap_Detected := True;
6295 end if;
6296 end;
6297 end if;
6298 end Check_Component_Overlap;
6299
6300 --------------------
6301 -- Find_Component --
6302 --------------------
6303
6304 procedure Find_Component is
6305
6306 procedure Search_Component (R : Entity_Id);
6307 -- Search components of R for a match. If found, Comp is set.
6308
6309 ----------------------
6310 -- Search_Component --
6311 ----------------------
6312
6313 procedure Search_Component (R : Entity_Id) is
6314 begin
6315 Comp := First_Component_Or_Discriminant (R);
6316 while Present (Comp) loop
6317
6318 -- Ignore error of attribute name for component name (we
6319 -- already gave an error message for this, so no need to
6320 -- complain here)
6321
6322 if Nkind (Component_Name (CC)) = N_Attribute_Reference then
6323 null;
6324 else
6325 exit when Chars (Comp) = Chars (Component_Name (CC));
6326 end if;
6327
6328 Next_Component_Or_Discriminant (Comp);
6329 end loop;
6330 end Search_Component;
6331
6332 -- Start of processing for Find_Component
6333
6334 begin
6335 -- Return with Comp set to Empty if we have a pragma
6336
6337 if Nkind (CC) = N_Pragma then
6338 Comp := Empty;
6339 return;
6340 end if;
6341
6342 -- Search current record for matching component
6343
6344 Search_Component (Rectype);
6345
6346 -- If not found, maybe component of base type that is absent from
6347 -- statically constrained first subtype.
6348
6349 if No (Comp) then
6350 Search_Component (Base_Type (Rectype));
6351 end if;
6352
6353 -- If no component, or the component does not reference the component
6354 -- clause in question, then there was some previous error for which
6355 -- we already gave a message, so just return with Comp Empty.
6356
6357 if No (Comp)
6358 or else Component_Clause (Comp) /= CC
6359 then
6360 Comp := Empty;
6361
6362 -- Normal case where we have a component clause
6363
6364 else
6365 Fbit := Component_Bit_Offset (Comp);
6366 Lbit := Fbit + Esize (Comp) - 1;
6367 end if;
6368 end Find_Component;
6369
6370 -- Start of processing for Check_Record_Representation_Clause
6371
6372 begin
6373 Find_Type (Ident);
6374 Rectype := Entity (Ident);
6375
6376 if Rectype = Any_Type then
6377 return;
6378 else
6379 Rectype := Underlying_Type (Rectype);
6380 end if;
6381
6382 -- See if we have a fully repped derived tagged type
6383
6384 declare
6385 PS : constant Entity_Id := Parent_Subtype (Rectype);
6386
6387 begin
6388 if Present (PS) and then Is_Fully_Repped_Tagged_Type (PS) then
6389 Tagged_Parent := PS;
6390
6391 -- Find maximum bit of any component of the parent type
6392
6393 Parent_Last_Bit := UI_From_Int (System_Address_Size - 1);
6394 Pcomp := First_Entity (Tagged_Parent);
6395 while Present (Pcomp) loop
6396 if Ekind_In (Pcomp, E_Discriminant, E_Component) then
6397 if Component_Bit_Offset (Pcomp) /= No_Uint
6398 and then Known_Static_Esize (Pcomp)
6399 then
6400 Parent_Last_Bit :=
6401 UI_Max
6402 (Parent_Last_Bit,
6403 Component_Bit_Offset (Pcomp) + Esize (Pcomp) - 1);
6404 end if;
6405
6406 Next_Entity (Pcomp);
6407 end if;
6408 end loop;
6409 end if;
6410 end;
6411
6412 -- All done if no component clauses
6413
6414 CC := First (Component_Clauses (N));
6415
6416 if No (CC) then
6417 return;
6418 end if;
6419
6420 -- If a tag is present, then create a component clause that places it
6421 -- at the start of the record (otherwise gigi may place it after other
6422 -- fields that have rep clauses).
6423
6424 Fent := First_Entity (Rectype);
6425
6426 if Nkind (Fent) = N_Defining_Identifier
6427 and then Chars (Fent) = Name_uTag
6428 then
6429 Set_Component_Bit_Offset (Fent, Uint_0);
6430 Set_Normalized_Position (Fent, Uint_0);
6431 Set_Normalized_First_Bit (Fent, Uint_0);
6432 Set_Normalized_Position_Max (Fent, Uint_0);
6433 Init_Esize (Fent, System_Address_Size);
6434
6435 Set_Component_Clause (Fent,
6436 Make_Component_Clause (Loc,
6437 Component_Name => Make_Identifier (Loc, Name_uTag),
6438
6439 Position => Make_Integer_Literal (Loc, Uint_0),
6440 First_Bit => Make_Integer_Literal (Loc, Uint_0),
6441 Last_Bit =>
6442 Make_Integer_Literal (Loc,
6443 UI_From_Int (System_Address_Size))));
6444
6445 Ccount := Ccount + 1;
6446 end if;
6447
6448 Max_Bit_So_Far := Uint_Minus_1;
6449 Overlap_Check_Required := False;
6450
6451 -- Process the component clauses
6452
6453 while Present (CC) loop
6454 Find_Component;
6455
6456 if Present (Comp) then
6457 Ccount := Ccount + 1;
6458
6459 -- We need a full overlap check if record positions non-monotonic
6460
6461 if Fbit <= Max_Bit_So_Far then
6462 Overlap_Check_Required := True;
6463 end if;
6464
6465 Max_Bit_So_Far := Lbit;
6466
6467 -- Check bit position out of range of specified size
6468
6469 if Has_Size_Clause (Rectype)
6470 and then RM_Size (Rectype) <= Lbit
6471 then
6472 Error_Msg_N
6473 ("bit number out of range of specified size",
6474 Last_Bit (CC));
6475
6476 -- Check for overlap with tag field
6477
6478 else
6479 if Is_Tagged_Type (Rectype)
6480 and then Fbit < System_Address_Size
6481 then
6482 Error_Msg_NE
6483 ("component overlaps tag field of&",
6484 Component_Name (CC), Rectype);
6485 Overlap_Detected := True;
6486 end if;
6487
6488 if Hbit < Lbit then
6489 Hbit := Lbit;
6490 end if;
6491 end if;
6492
6493 -- Check parent overlap if component might overlap parent field
6494
6495 if Present (Tagged_Parent)
6496 and then Fbit <= Parent_Last_Bit
6497 then
6498 Pcomp := First_Component_Or_Discriminant (Tagged_Parent);
6499 while Present (Pcomp) loop
6500 if not Is_Tag (Pcomp)
6501 and then Chars (Pcomp) /= Name_uParent
6502 then
6503 Check_Component_Overlap (Comp, Pcomp);
6504 end if;
6505
6506 Next_Component_Or_Discriminant (Pcomp);
6507 end loop;
6508 end if;
6509 end if;
6510
6511 Next (CC);
6512 end loop;
6513
6514 -- Now that we have processed all the component clauses, check for
6515 -- overlap. We have to leave this till last, since the components can
6516 -- appear in any arbitrary order in the representation clause.
6517
6518 -- We do not need this check if all specified ranges were monotonic,
6519 -- as recorded by Overlap_Check_Required being False at this stage.
6520
6521 -- This first section checks if there are any overlapping entries at
6522 -- all. It does this by sorting all entries and then seeing if there are
6523 -- any overlaps. If there are none, then that is decisive, but if there
6524 -- are overlaps, they may still be OK (they may result from fields in
6525 -- different variants).
6526
6527 if Overlap_Check_Required then
6528 Overlap_Check1 : declare
6529
6530 OC_Fbit : array (0 .. Ccount) of Uint;
6531 -- First-bit values for component clauses, the value is the offset
6532 -- of the first bit of the field from start of record. The zero
6533 -- entry is for use in sorting.
6534
6535 OC_Lbit : array (0 .. Ccount) of Uint;
6536 -- Last-bit values for component clauses, the value is the offset
6537 -- of the last bit of the field from start of record. The zero
6538 -- entry is for use in sorting.
6539
6540 OC_Count : Natural := 0;
6541 -- Count of entries in OC_Fbit and OC_Lbit
6542
6543 function OC_Lt (Op1, Op2 : Natural) return Boolean;
6544 -- Compare routine for Sort
6545
6546 procedure OC_Move (From : Natural; To : Natural);
6547 -- Move routine for Sort
6548
6549 package Sorting is new GNAT.Heap_Sort_G (OC_Move, OC_Lt);
6550
6551 -----------
6552 -- OC_Lt --
6553 -----------
6554
6555 function OC_Lt (Op1, Op2 : Natural) return Boolean is
6556 begin
6557 return OC_Fbit (Op1) < OC_Fbit (Op2);
6558 end OC_Lt;
6559
6560 -------------
6561 -- OC_Move --
6562 -------------
6563
6564 procedure OC_Move (From : Natural; To : Natural) is
6565 begin
6566 OC_Fbit (To) := OC_Fbit (From);
6567 OC_Lbit (To) := OC_Lbit (From);
6568 end OC_Move;
6569
6570 -- Start of processing for Overlap_Check
6571
6572 begin
6573 CC := First (Component_Clauses (N));
6574 while Present (CC) loop
6575
6576 -- Exclude component clause already marked in error
6577
6578 if not Error_Posted (CC) then
6579 Find_Component;
6580
6581 if Present (Comp) then
6582 OC_Count := OC_Count + 1;
6583 OC_Fbit (OC_Count) := Fbit;
6584 OC_Lbit (OC_Count) := Lbit;
6585 end if;
6586 end if;
6587
6588 Next (CC);
6589 end loop;
6590
6591 Sorting.Sort (OC_Count);
6592
6593 Overlap_Check_Required := False;
6594 for J in 1 .. OC_Count - 1 loop
6595 if OC_Lbit (J) >= OC_Fbit (J + 1) then
6596 Overlap_Check_Required := True;
6597 exit;
6598 end if;
6599 end loop;
6600 end Overlap_Check1;
6601 end if;
6602
6603 -- If Overlap_Check_Required is still True, then we have to do the full
6604 -- scale overlap check, since we have at least two fields that do
6605 -- overlap, and we need to know if that is OK since they are in
6606 -- different variant, or whether we have a definite problem.
6607
6608 if Overlap_Check_Required then
6609 Overlap_Check2 : declare
6610 C1_Ent, C2_Ent : Entity_Id;
6611 -- Entities of components being checked for overlap
6612
6613 Clist : Node_Id;
6614 -- Component_List node whose Component_Items are being checked
6615
6616 Citem : Node_Id;
6617 -- Component declaration for component being checked
6618
6619 begin
6620 C1_Ent := First_Entity (Base_Type (Rectype));
6621
6622 -- Loop through all components in record. For each component check
6623 -- for overlap with any of the preceding elements on the component
6624 -- list containing the component and also, if the component is in
6625 -- a variant, check against components outside the case structure.
6626 -- This latter test is repeated recursively up the variant tree.
6627
6628 Main_Component_Loop : while Present (C1_Ent) loop
6629 if not Ekind_In (C1_Ent, E_Component, E_Discriminant) then
6630 goto Continue_Main_Component_Loop;
6631 end if;
6632
6633 -- Skip overlap check if entity has no declaration node. This
6634 -- happens with discriminants in constrained derived types.
6635 -- Possibly we are missing some checks as a result, but that
6636 -- does not seem terribly serious.
6637
6638 if No (Declaration_Node (C1_Ent)) then
6639 goto Continue_Main_Component_Loop;
6640 end if;
6641
6642 Clist := Parent (List_Containing (Declaration_Node (C1_Ent)));
6643
6644 -- Loop through component lists that need checking. Check the
6645 -- current component list and all lists in variants above us.
6646
6647 Component_List_Loop : loop
6648
6649 -- If derived type definition, go to full declaration
6650 -- If at outer level, check discriminants if there are any.
6651
6652 if Nkind (Clist) = N_Derived_Type_Definition then
6653 Clist := Parent (Clist);
6654 end if;
6655
6656 -- Outer level of record definition, check discriminants
6657
6658 if Nkind_In (Clist, N_Full_Type_Declaration,
6659 N_Private_Type_Declaration)
6660 then
6661 if Has_Discriminants (Defining_Identifier (Clist)) then
6662 C2_Ent :=
6663 First_Discriminant (Defining_Identifier (Clist));
6664 while Present (C2_Ent) loop
6665 exit when C1_Ent = C2_Ent;
6666 Check_Component_Overlap (C1_Ent, C2_Ent);
6667 Next_Discriminant (C2_Ent);
6668 end loop;
6669 end if;
6670
6671 -- Record extension case
6672
6673 elsif Nkind (Clist) = N_Derived_Type_Definition then
6674 Clist := Empty;
6675
6676 -- Otherwise check one component list
6677
6678 else
6679 Citem := First (Component_Items (Clist));
6680 while Present (Citem) loop
6681 if Nkind (Citem) = N_Component_Declaration then
6682 C2_Ent := Defining_Identifier (Citem);
6683 exit when C1_Ent = C2_Ent;
6684 Check_Component_Overlap (C1_Ent, C2_Ent);
6685 end if;
6686
6687 Next (Citem);
6688 end loop;
6689 end if;
6690
6691 -- Check for variants above us (the parent of the Clist can
6692 -- be a variant, in which case its parent is a variant part,
6693 -- and the parent of the variant part is a component list
6694 -- whose components must all be checked against the current
6695 -- component for overlap).
6696
6697 if Nkind (Parent (Clist)) = N_Variant then
6698 Clist := Parent (Parent (Parent (Clist)));
6699
6700 -- Check for possible discriminant part in record, this
6701 -- is treated essentially as another level in the
6702 -- recursion. For this case the parent of the component
6703 -- list is the record definition, and its parent is the
6704 -- full type declaration containing the discriminant
6705 -- specifications.
6706
6707 elsif Nkind (Parent (Clist)) = N_Record_Definition then
6708 Clist := Parent (Parent ((Clist)));
6709
6710 -- If neither of these two cases, we are at the top of
6711 -- the tree.
6712
6713 else
6714 exit Component_List_Loop;
6715 end if;
6716 end loop Component_List_Loop;
6717
6718 <<Continue_Main_Component_Loop>>
6719 Next_Entity (C1_Ent);
6720
6721 end loop Main_Component_Loop;
6722 end Overlap_Check2;
6723 end if;
6724
6725 -- The following circuit deals with warning on record holes (gaps). We
6726 -- skip this check if overlap was detected, since it makes sense for the
6727 -- programmer to fix this illegality before worrying about warnings.
6728
6729 if not Overlap_Detected and Warn_On_Record_Holes then
6730 Record_Hole_Check : declare
6731 Decl : constant Node_Id := Declaration_Node (Base_Type (Rectype));
6732 -- Full declaration of record type
6733
6734 procedure Check_Component_List
6735 (CL : Node_Id;
6736 Sbit : Uint;
6737 DS : List_Id);
6738 -- Check component list CL for holes. The starting bit should be
6739 -- Sbit. which is zero for the main record component list and set
6740 -- appropriately for recursive calls for variants. DS is set to
6741 -- a list of discriminant specifications to be included in the
6742 -- consideration of components. It is No_List if none to consider.
6743
6744 --------------------------
6745 -- Check_Component_List --
6746 --------------------------
6747
6748 procedure Check_Component_List
6749 (CL : Node_Id;
6750 Sbit : Uint;
6751 DS : List_Id)
6752 is
6753 Compl : Integer;
6754
6755 begin
6756 Compl := Integer (List_Length (Component_Items (CL)));
6757
6758 if DS /= No_List then
6759 Compl := Compl + Integer (List_Length (DS));
6760 end if;
6761
6762 declare
6763 Comps : array (Natural range 0 .. Compl) of Entity_Id;
6764 -- Gather components (zero entry is for sort routine)
6765
6766 Ncomps : Natural := 0;
6767 -- Number of entries stored in Comps (starting at Comps (1))
6768
6769 Citem : Node_Id;
6770 -- One component item or discriminant specification
6771
6772 Nbit : Uint;
6773 -- Starting bit for next component
6774
6775 CEnt : Entity_Id;
6776 -- Component entity
6777
6778 Variant : Node_Id;
6779 -- One variant
6780
6781 function Lt (Op1, Op2 : Natural) return Boolean;
6782 -- Compare routine for Sort
6783
6784 procedure Move (From : Natural; To : Natural);
6785 -- Move routine for Sort
6786
6787 package Sorting is new GNAT.Heap_Sort_G (Move, Lt);
6788
6789 --------
6790 -- Lt --
6791 --------
6792
6793 function Lt (Op1, Op2 : Natural) return Boolean is
6794 begin
6795 return Component_Bit_Offset (Comps (Op1))
6796 <
6797 Component_Bit_Offset (Comps (Op2));
6798 end Lt;
6799
6800 ----------
6801 -- Move --
6802 ----------
6803
6804 procedure Move (From : Natural; To : Natural) is
6805 begin
6806 Comps (To) := Comps (From);
6807 end Move;
6808
6809 begin
6810 -- Gather discriminants into Comp
6811
6812 if DS /= No_List then
6813 Citem := First (DS);
6814 while Present (Citem) loop
6815 if Nkind (Citem) = N_Discriminant_Specification then
6816 declare
6817 Ent : constant Entity_Id :=
6818 Defining_Identifier (Citem);
6819 begin
6820 if Ekind (Ent) = E_Discriminant then
6821 Ncomps := Ncomps + 1;
6822 Comps (Ncomps) := Ent;
6823 end if;
6824 end;
6825 end if;
6826
6827 Next (Citem);
6828 end loop;
6829 end if;
6830
6831 -- Gather component entities into Comp
6832
6833 Citem := First (Component_Items (CL));
6834 while Present (Citem) loop
6835 if Nkind (Citem) = N_Component_Declaration then
6836 Ncomps := Ncomps + 1;
6837 Comps (Ncomps) := Defining_Identifier (Citem);
6838 end if;
6839
6840 Next (Citem);
6841 end loop;
6842
6843 -- Now sort the component entities based on the first bit.
6844 -- Note we already know there are no overlapping components.
6845
6846 Sorting.Sort (Ncomps);
6847
6848 -- Loop through entries checking for holes
6849
6850 Nbit := Sbit;
6851 for J in 1 .. Ncomps loop
6852 CEnt := Comps (J);
6853 Error_Msg_Uint_1 := Component_Bit_Offset (CEnt) - Nbit;
6854
6855 if Error_Msg_Uint_1 > 0 then
6856 Error_Msg_NE
6857 ("?^-bit gap before component&",
6858 Component_Name (Component_Clause (CEnt)), CEnt);
6859 end if;
6860
6861 Nbit := Component_Bit_Offset (CEnt) + Esize (CEnt);
6862 end loop;
6863
6864 -- Process variant parts recursively if present
6865
6866 if Present (Variant_Part (CL)) then
6867 Variant := First (Variants (Variant_Part (CL)));
6868 while Present (Variant) loop
6869 Check_Component_List
6870 (Component_List (Variant), Nbit, No_List);
6871 Next (Variant);
6872 end loop;
6873 end if;
6874 end;
6875 end Check_Component_List;
6876
6877 -- Start of processing for Record_Hole_Check
6878
6879 begin
6880 declare
6881 Sbit : Uint;
6882
6883 begin
6884 if Is_Tagged_Type (Rectype) then
6885 Sbit := UI_From_Int (System_Address_Size);
6886 else
6887 Sbit := Uint_0;
6888 end if;
6889
6890 if Nkind (Decl) = N_Full_Type_Declaration
6891 and then Nkind (Type_Definition (Decl)) = N_Record_Definition
6892 then
6893 Check_Component_List
6894 (Component_List (Type_Definition (Decl)),
6895 Sbit,
6896 Discriminant_Specifications (Decl));
6897 end if;
6898 end;
6899 end Record_Hole_Check;
6900 end if;
6901
6902 -- For records that have component clauses for all components, and whose
6903 -- size is less than or equal to 32, we need to know the size in the
6904 -- front end to activate possible packed array processing where the
6905 -- component type is a record.
6906
6907 -- At this stage Hbit + 1 represents the first unused bit from all the
6908 -- component clauses processed, so if the component clauses are
6909 -- complete, then this is the length of the record.
6910
6911 -- For records longer than System.Storage_Unit, and for those where not
6912 -- all components have component clauses, the back end determines the
6913 -- length (it may for example be appropriate to round up the size
6914 -- to some convenient boundary, based on alignment considerations, etc).
6915
6916 if Unknown_RM_Size (Rectype) and then Hbit + 1 <= 32 then
6917
6918 -- Nothing to do if at least one component has no component clause
6919
6920 Comp := First_Component_Or_Discriminant (Rectype);
6921 while Present (Comp) loop
6922 exit when No (Component_Clause (Comp));
6923 Next_Component_Or_Discriminant (Comp);
6924 end loop;
6925
6926 -- If we fall out of loop, all components have component clauses
6927 -- and so we can set the size to the maximum value.
6928
6929 if No (Comp) then
6930 Set_RM_Size (Rectype, Hbit + 1);
6931 end if;
6932 end if;
6933 end Check_Record_Representation_Clause;
6934
6935 ----------------
6936 -- Check_Size --
6937 ----------------
6938
6939 procedure Check_Size
6940 (N : Node_Id;
6941 T : Entity_Id;
6942 Siz : Uint;
6943 Biased : out Boolean)
6944 is
6945 UT : constant Entity_Id := Underlying_Type (T);
6946 M : Uint;
6947
6948 begin
6949 Biased := False;
6950
6951 -- Dismiss cases for generic types or types with previous errors
6952
6953 if No (UT)
6954 or else UT = Any_Type
6955 or else Is_Generic_Type (UT)
6956 or else Is_Generic_Type (Root_Type (UT))
6957 then
6958 return;
6959
6960 -- Check case of bit packed array
6961
6962 elsif Is_Array_Type (UT)
6963 and then Known_Static_Component_Size (UT)
6964 and then Is_Bit_Packed_Array (UT)
6965 then
6966 declare
6967 Asiz : Uint;
6968 Indx : Node_Id;
6969 Ityp : Entity_Id;
6970
6971 begin
6972 Asiz := Component_Size (UT);
6973 Indx := First_Index (UT);
6974 loop
6975 Ityp := Etype (Indx);
6976
6977 -- If non-static bound, then we are not in the business of
6978 -- trying to check the length, and indeed an error will be
6979 -- issued elsewhere, since sizes of non-static array types
6980 -- cannot be set implicitly or explicitly.
6981
6982 if not Is_Static_Subtype (Ityp) then
6983 return;
6984 end if;
6985
6986 -- Otherwise accumulate next dimension
6987
6988 Asiz := Asiz * (Expr_Value (Type_High_Bound (Ityp)) -
6989 Expr_Value (Type_Low_Bound (Ityp)) +
6990 Uint_1);
6991
6992 Next_Index (Indx);
6993 exit when No (Indx);
6994 end loop;
6995
6996 if Asiz <= Siz then
6997 return;
6998 else
6999 Error_Msg_Uint_1 := Asiz;
7000 Error_Msg_NE
7001 ("size for& too small, minimum allowed is ^", N, T);
7002 Set_Esize (T, Asiz);
7003 Set_RM_Size (T, Asiz);
7004 end if;
7005 end;
7006
7007 -- All other composite types are ignored
7008
7009 elsif Is_Composite_Type (UT) then
7010 return;
7011
7012 -- For fixed-point types, don't check minimum if type is not frozen,
7013 -- since we don't know all the characteristics of the type that can
7014 -- affect the size (e.g. a specified small) till freeze time.
7015
7016 elsif Is_Fixed_Point_Type (UT)
7017 and then not Is_Frozen (UT)
7018 then
7019 null;
7020
7021 -- Cases for which a minimum check is required
7022
7023 else
7024 -- Ignore if specified size is correct for the type
7025
7026 if Known_Esize (UT) and then Siz = Esize (UT) then
7027 return;
7028 end if;
7029
7030 -- Otherwise get minimum size
7031
7032 M := UI_From_Int (Minimum_Size (UT));
7033
7034 if Siz < M then
7035
7036 -- Size is less than minimum size, but one possibility remains
7037 -- that we can manage with the new size if we bias the type.
7038
7039 M := UI_From_Int (Minimum_Size (UT, Biased => True));
7040
7041 if Siz < M then
7042 Error_Msg_Uint_1 := M;
7043 Error_Msg_NE
7044 ("size for& too small, minimum allowed is ^", N, T);
7045 Set_Esize (T, M);
7046 Set_RM_Size (T, M);
7047 else
7048 Biased := True;
7049 end if;
7050 end if;
7051 end if;
7052 end Check_Size;
7053
7054 -------------------------
7055 -- Get_Alignment_Value --
7056 -------------------------
7057
7058 function Get_Alignment_Value (Expr : Node_Id) return Uint is
7059 Align : constant Uint := Static_Integer (Expr);
7060
7061 begin
7062 if Align = No_Uint then
7063 return No_Uint;
7064
7065 elsif Align <= 0 then
7066 Error_Msg_N ("alignment value must be positive", Expr);
7067 return No_Uint;
7068
7069 else
7070 for J in Int range 0 .. 64 loop
7071 declare
7072 M : constant Uint := Uint_2 ** J;
7073
7074 begin
7075 exit when M = Align;
7076
7077 if M > Align then
7078 Error_Msg_N
7079 ("alignment value must be power of 2", Expr);
7080 return No_Uint;
7081 end if;
7082 end;
7083 end loop;
7084
7085 return Align;
7086 end if;
7087 end Get_Alignment_Value;
7088
7089 ----------------
7090 -- Initialize --
7091 ----------------
7092
7093 procedure Initialize is
7094 begin
7095 Address_Clause_Checks.Init;
7096 Independence_Checks.Init;
7097 Unchecked_Conversions.Init;
7098 end Initialize;
7099
7100 -------------------------
7101 -- Is_Operational_Item --
7102 -------------------------
7103
7104 function Is_Operational_Item (N : Node_Id) return Boolean is
7105 begin
7106 if Nkind (N) /= N_Attribute_Definition_Clause then
7107 return False;
7108 else
7109 declare
7110 Id : constant Attribute_Id := Get_Attribute_Id (Chars (N));
7111 begin
7112 return Id = Attribute_Input
7113 or else Id = Attribute_Output
7114 or else Id = Attribute_Read
7115 or else Id = Attribute_Write
7116 or else Id = Attribute_External_Tag;
7117 end;
7118 end if;
7119 end Is_Operational_Item;
7120
7121 ------------------
7122 -- Minimum_Size --
7123 ------------------
7124
7125 function Minimum_Size
7126 (T : Entity_Id;
7127 Biased : Boolean := False) return Nat
7128 is
7129 Lo : Uint := No_Uint;
7130 Hi : Uint := No_Uint;
7131 LoR : Ureal := No_Ureal;
7132 HiR : Ureal := No_Ureal;
7133 LoSet : Boolean := False;
7134 HiSet : Boolean := False;
7135 B : Uint;
7136 S : Nat;
7137 Ancest : Entity_Id;
7138 R_Typ : constant Entity_Id := Root_Type (T);
7139
7140 begin
7141 -- If bad type, return 0
7142
7143 if T = Any_Type then
7144 return 0;
7145
7146 -- For generic types, just return zero. There cannot be any legitimate
7147 -- need to know such a size, but this routine may be called with a
7148 -- generic type as part of normal processing.
7149
7150 elsif Is_Generic_Type (R_Typ)
7151 or else R_Typ = Any_Type
7152 then
7153 return 0;
7154
7155 -- Access types. Normally an access type cannot have a size smaller
7156 -- than the size of System.Address. The exception is on VMS, where
7157 -- we have short and long addresses, and it is possible for an access
7158 -- type to have a short address size (and thus be less than the size
7159 -- of System.Address itself). We simply skip the check for VMS, and
7160 -- leave it to the back end to do the check.
7161
7162 elsif Is_Access_Type (T) then
7163 if OpenVMS_On_Target then
7164 return 0;
7165 else
7166 return System_Address_Size;
7167 end if;
7168
7169 -- Floating-point types
7170
7171 elsif Is_Floating_Point_Type (T) then
7172 return UI_To_Int (Esize (R_Typ));
7173
7174 -- Discrete types
7175
7176 elsif Is_Discrete_Type (T) then
7177
7178 -- The following loop is looking for the nearest compile time known
7179 -- bounds following the ancestor subtype chain. The idea is to find
7180 -- the most restrictive known bounds information.
7181
7182 Ancest := T;
7183 loop
7184 if Ancest = Any_Type or else Etype (Ancest) = Any_Type then
7185 return 0;
7186 end if;
7187
7188 if not LoSet then
7189 if Compile_Time_Known_Value (Type_Low_Bound (Ancest)) then
7190 Lo := Expr_Rep_Value (Type_Low_Bound (Ancest));
7191 LoSet := True;
7192 exit when HiSet;
7193 end if;
7194 end if;
7195
7196 if not HiSet then
7197 if Compile_Time_Known_Value (Type_High_Bound (Ancest)) then
7198 Hi := Expr_Rep_Value (Type_High_Bound (Ancest));
7199 HiSet := True;
7200 exit when LoSet;
7201 end if;
7202 end if;
7203
7204 Ancest := Ancestor_Subtype (Ancest);
7205
7206 if No (Ancest) then
7207 Ancest := Base_Type (T);
7208
7209 if Is_Generic_Type (Ancest) then
7210 return 0;
7211 end if;
7212 end if;
7213 end loop;
7214
7215 -- Fixed-point types. We can't simply use Expr_Value to get the
7216 -- Corresponding_Integer_Value values of the bounds, since these do not
7217 -- get set till the type is frozen, and this routine can be called
7218 -- before the type is frozen. Similarly the test for bounds being static
7219 -- needs to include the case where we have unanalyzed real literals for
7220 -- the same reason.
7221
7222 elsif Is_Fixed_Point_Type (T) then
7223
7224 -- The following loop is looking for the nearest compile time known
7225 -- bounds following the ancestor subtype chain. The idea is to find
7226 -- the most restrictive known bounds information.
7227
7228 Ancest := T;
7229 loop
7230 if Ancest = Any_Type or else Etype (Ancest) = Any_Type then
7231 return 0;
7232 end if;
7233
7234 -- Note: In the following two tests for LoSet and HiSet, it may
7235 -- seem redundant to test for N_Real_Literal here since normally
7236 -- one would assume that the test for the value being known at
7237 -- compile time includes this case. However, there is a glitch.
7238 -- If the real literal comes from folding a non-static expression,
7239 -- then we don't consider any non- static expression to be known
7240 -- at compile time if we are in configurable run time mode (needed
7241 -- in some cases to give a clearer definition of what is and what
7242 -- is not accepted). So the test is indeed needed. Without it, we
7243 -- would set neither Lo_Set nor Hi_Set and get an infinite loop.
7244
7245 if not LoSet then
7246 if Nkind (Type_Low_Bound (Ancest)) = N_Real_Literal
7247 or else Compile_Time_Known_Value (Type_Low_Bound (Ancest))
7248 then
7249 LoR := Expr_Value_R (Type_Low_Bound (Ancest));
7250 LoSet := True;
7251 exit when HiSet;
7252 end if;
7253 end if;
7254
7255 if not HiSet then
7256 if Nkind (Type_High_Bound (Ancest)) = N_Real_Literal
7257 or else Compile_Time_Known_Value (Type_High_Bound (Ancest))
7258 then
7259 HiR := Expr_Value_R (Type_High_Bound (Ancest));
7260 HiSet := True;
7261 exit when LoSet;
7262 end if;
7263 end if;
7264
7265 Ancest := Ancestor_Subtype (Ancest);
7266
7267 if No (Ancest) then
7268 Ancest := Base_Type (T);
7269
7270 if Is_Generic_Type (Ancest) then
7271 return 0;
7272 end if;
7273 end if;
7274 end loop;
7275
7276 Lo := UR_To_Uint (LoR / Small_Value (T));
7277 Hi := UR_To_Uint (HiR / Small_Value (T));
7278
7279 -- No other types allowed
7280
7281 else
7282 raise Program_Error;
7283 end if;
7284
7285 -- Fall through with Hi and Lo set. Deal with biased case
7286
7287 if (Biased
7288 and then not Is_Fixed_Point_Type (T)
7289 and then not (Is_Enumeration_Type (T)
7290 and then Has_Non_Standard_Rep (T)))
7291 or else Has_Biased_Representation (T)
7292 then
7293 Hi := Hi - Lo;
7294 Lo := Uint_0;
7295 end if;
7296
7297 -- Signed case. Note that we consider types like range 1 .. -1 to be
7298 -- signed for the purpose of computing the size, since the bounds have
7299 -- to be accommodated in the base type.
7300
7301 if Lo < 0 or else Hi < 0 then
7302 S := 1;
7303 B := Uint_1;
7304
7305 -- S = size, B = 2 ** (size - 1) (can accommodate -B .. +(B - 1))
7306 -- Note that we accommodate the case where the bounds cross. This
7307 -- can happen either because of the way the bounds are declared
7308 -- or because of the algorithm in Freeze_Fixed_Point_Type.
7309
7310 while Lo < -B
7311 or else Hi < -B
7312 or else Lo >= B
7313 or else Hi >= B
7314 loop
7315 B := Uint_2 ** S;
7316 S := S + 1;
7317 end loop;
7318
7319 -- Unsigned case
7320
7321 else
7322 -- If both bounds are positive, make sure that both are represen-
7323 -- table in the case where the bounds are crossed. This can happen
7324 -- either because of the way the bounds are declared, or because of
7325 -- the algorithm in Freeze_Fixed_Point_Type.
7326
7327 if Lo > Hi then
7328 Hi := Lo;
7329 end if;
7330
7331 -- S = size, (can accommodate 0 .. (2**size - 1))
7332
7333 S := 0;
7334 while Hi >= Uint_2 ** S loop
7335 S := S + 1;
7336 end loop;
7337 end if;
7338
7339 return S;
7340 end Minimum_Size;
7341
7342 ---------------------------
7343 -- New_Stream_Subprogram --
7344 ---------------------------
7345
7346 procedure New_Stream_Subprogram
7347 (N : Node_Id;
7348 Ent : Entity_Id;
7349 Subp : Entity_Id;
7350 Nam : TSS_Name_Type)
7351 is
7352 Loc : constant Source_Ptr := Sloc (N);
7353 Sname : constant Name_Id := Make_TSS_Name (Base_Type (Ent), Nam);
7354 Subp_Id : Entity_Id;
7355 Subp_Decl : Node_Id;
7356 F : Entity_Id;
7357 Etyp : Entity_Id;
7358
7359 Defer_Declaration : constant Boolean :=
7360 Is_Tagged_Type (Ent) or else Is_Private_Type (Ent);
7361 -- For a tagged type, there is a declaration for each stream attribute
7362 -- at the freeze point, and we must generate only a completion of this
7363 -- declaration. We do the same for private types, because the full view
7364 -- might be tagged. Otherwise we generate a declaration at the point of
7365 -- the attribute definition clause.
7366
7367 function Build_Spec return Node_Id;
7368 -- Used for declaration and renaming declaration, so that this is
7369 -- treated as a renaming_as_body.
7370
7371 ----------------
7372 -- Build_Spec --
7373 ----------------
7374
7375 function Build_Spec return Node_Id is
7376 Out_P : constant Boolean := (Nam = TSS_Stream_Read);
7377 Formals : List_Id;
7378 Spec : Node_Id;
7379 T_Ref : constant Node_Id := New_Reference_To (Etyp, Loc);
7380
7381 begin
7382 Subp_Id := Make_Defining_Identifier (Loc, Sname);
7383
7384 -- S : access Root_Stream_Type'Class
7385
7386 Formals := New_List (
7387 Make_Parameter_Specification (Loc,
7388 Defining_Identifier =>
7389 Make_Defining_Identifier (Loc, Name_S),
7390 Parameter_Type =>
7391 Make_Access_Definition (Loc,
7392 Subtype_Mark =>
7393 New_Reference_To (
7394 Designated_Type (Etype (F)), Loc))));
7395
7396 if Nam = TSS_Stream_Input then
7397 Spec := Make_Function_Specification (Loc,
7398 Defining_Unit_Name => Subp_Id,
7399 Parameter_Specifications => Formals,
7400 Result_Definition => T_Ref);
7401 else
7402 -- V : [out] T
7403
7404 Append_To (Formals,
7405 Make_Parameter_Specification (Loc,
7406 Defining_Identifier => Make_Defining_Identifier (Loc, Name_V),
7407 Out_Present => Out_P,
7408 Parameter_Type => T_Ref));
7409
7410 Spec :=
7411 Make_Procedure_Specification (Loc,
7412 Defining_Unit_Name => Subp_Id,
7413 Parameter_Specifications => Formals);
7414 end if;
7415
7416 return Spec;
7417 end Build_Spec;
7418
7419 -- Start of processing for New_Stream_Subprogram
7420
7421 begin
7422 F := First_Formal (Subp);
7423
7424 if Ekind (Subp) = E_Procedure then
7425 Etyp := Etype (Next_Formal (F));
7426 else
7427 Etyp := Etype (Subp);
7428 end if;
7429
7430 -- Prepare subprogram declaration and insert it as an action on the
7431 -- clause node. The visibility for this entity is used to test for
7432 -- visibility of the attribute definition clause (in the sense of
7433 -- 8.3(23) as amended by AI-195).
7434
7435 if not Defer_Declaration then
7436 Subp_Decl :=
7437 Make_Subprogram_Declaration (Loc,
7438 Specification => Build_Spec);
7439
7440 -- For a tagged type, there is always a visible declaration for each
7441 -- stream TSS (it is a predefined primitive operation), and the
7442 -- completion of this declaration occurs at the freeze point, which is
7443 -- not always visible at places where the attribute definition clause is
7444 -- visible. So, we create a dummy entity here for the purpose of
7445 -- tracking the visibility of the attribute definition clause itself.
7446
7447 else
7448 Subp_Id :=
7449 Make_Defining_Identifier (Loc, New_External_Name (Sname, 'V'));
7450 Subp_Decl :=
7451 Make_Object_Declaration (Loc,
7452 Defining_Identifier => Subp_Id,
7453 Object_Definition => New_Occurrence_Of (Standard_Boolean, Loc));
7454 end if;
7455
7456 Insert_Action (N, Subp_Decl);
7457 Set_Entity (N, Subp_Id);
7458
7459 Subp_Decl :=
7460 Make_Subprogram_Renaming_Declaration (Loc,
7461 Specification => Build_Spec,
7462 Name => New_Reference_To (Subp, Loc));
7463
7464 if Defer_Declaration then
7465 Set_TSS (Base_Type (Ent), Subp_Id);
7466 else
7467 Insert_Action (N, Subp_Decl);
7468 Copy_TSS (Subp_Id, Base_Type (Ent));
7469 end if;
7470 end New_Stream_Subprogram;
7471
7472 ------------------------
7473 -- Rep_Item_Too_Early --
7474 ------------------------
7475
7476 function Rep_Item_Too_Early (T : Entity_Id; N : Node_Id) return Boolean is
7477 begin
7478 -- Cannot apply non-operational rep items to generic types
7479
7480 if Is_Operational_Item (N) then
7481 return False;
7482
7483 elsif Is_Type (T)
7484 and then Is_Generic_Type (Root_Type (T))
7485 then
7486 Error_Msg_N ("representation item not allowed for generic type", N);
7487 return True;
7488 end if;
7489
7490 -- Otherwise check for incomplete type
7491
7492 if Is_Incomplete_Or_Private_Type (T)
7493 and then No (Underlying_Type (T))
7494 and then
7495 (Nkind (N) /= N_Pragma
7496 or else Get_Pragma_Id (N) /= Pragma_Import)
7497 then
7498 Error_Msg_N
7499 ("representation item must be after full type declaration", N);
7500 return True;
7501
7502 -- If the type has incomplete components, a representation clause is
7503 -- illegal but stream attributes and Convention pragmas are correct.
7504
7505 elsif Has_Private_Component (T) then
7506 if Nkind (N) = N_Pragma then
7507 return False;
7508 else
7509 Error_Msg_N
7510 ("representation item must appear after type is fully defined",
7511 N);
7512 return True;
7513 end if;
7514 else
7515 return False;
7516 end if;
7517 end Rep_Item_Too_Early;
7518
7519 -----------------------
7520 -- Rep_Item_Too_Late --
7521 -----------------------
7522
7523 function Rep_Item_Too_Late
7524 (T : Entity_Id;
7525 N : Node_Id;
7526 FOnly : Boolean := False) return Boolean
7527 is
7528 S : Entity_Id;
7529 Parent_Type : Entity_Id;
7530
7531 procedure Too_Late;
7532 -- Output the too late message. Note that this is not considered a
7533 -- serious error, since the effect is simply that we ignore the
7534 -- representation clause in this case.
7535
7536 --------------
7537 -- Too_Late --
7538 --------------
7539
7540 procedure Too_Late is
7541 begin
7542 Error_Msg_N ("|representation item appears too late!", N);
7543 end Too_Late;
7544
7545 -- Start of processing for Rep_Item_Too_Late
7546
7547 begin
7548 -- First make sure entity is not frozen (RM 13.1(9)). Exclude imported
7549 -- types, which may be frozen if they appear in a representation clause
7550 -- for a local type.
7551
7552 if Is_Frozen (T)
7553 and then not From_With_Type (T)
7554 then
7555 Too_Late;
7556 S := First_Subtype (T);
7557
7558 if Present (Freeze_Node (S)) then
7559 Error_Msg_NE
7560 ("?no more representation items for }", Freeze_Node (S), S);
7561 end if;
7562
7563 return True;
7564
7565 -- Check for case of non-tagged derived type whose parent either has
7566 -- primitive operations, or is a by reference type (RM 13.1(10)).
7567
7568 elsif Is_Type (T)
7569 and then not FOnly
7570 and then Is_Derived_Type (T)
7571 and then not Is_Tagged_Type (T)
7572 then
7573 Parent_Type := Etype (Base_Type (T));
7574
7575 if Has_Primitive_Operations (Parent_Type) then
7576 Too_Late;
7577 Error_Msg_NE
7578 ("primitive operations already defined for&!", N, Parent_Type);
7579 return True;
7580
7581 elsif Is_By_Reference_Type (Parent_Type) then
7582 Too_Late;
7583 Error_Msg_NE
7584 ("parent type & is a by reference type!", N, Parent_Type);
7585 return True;
7586 end if;
7587 end if;
7588
7589 -- No error, link item into head of chain of rep items for the entity,
7590 -- but avoid chaining if we have an overloadable entity, and the pragma
7591 -- is one that can apply to multiple overloaded entities.
7592
7593 if Is_Overloadable (T)
7594 and then Nkind (N) = N_Pragma
7595 then
7596 declare
7597 Pname : constant Name_Id := Pragma_Name (N);
7598 begin
7599 if Pname = Name_Convention or else
7600 Pname = Name_Import or else
7601 Pname = Name_Export or else
7602 Pname = Name_External or else
7603 Pname = Name_Interface
7604 then
7605 return False;
7606 end if;
7607 end;
7608 end if;
7609
7610 Record_Rep_Item (T, N);
7611 return False;
7612 end Rep_Item_Too_Late;
7613
7614 -------------------------------------
7615 -- Replace_Type_References_Generic --
7616 -------------------------------------
7617
7618 procedure Replace_Type_References_Generic (N : Node_Id; TName : Name_Id) is
7619
7620 function Replace_Node (N : Node_Id) return Traverse_Result;
7621 -- Processes a single node in the traversal procedure below, checking
7622 -- if node N should be replaced, and if so, doing the replacement.
7623
7624 procedure Replace_Type_Refs is new Traverse_Proc (Replace_Node);
7625 -- This instantiation provides the body of Replace_Type_References
7626
7627 ------------------
7628 -- Replace_Node --
7629 ------------------
7630
7631 function Replace_Node (N : Node_Id) return Traverse_Result is
7632 S : Entity_Id;
7633 P : Node_Id;
7634
7635 begin
7636 -- Case of identifier
7637
7638 if Nkind (N) = N_Identifier then
7639
7640 -- If not the type name, all done with this node
7641
7642 if Chars (N) /= TName then
7643 return Skip;
7644
7645 -- Otherwise do the replacement and we are done with this node
7646
7647 else
7648 Replace_Type_Reference (N);
7649 return Skip;
7650 end if;
7651
7652 -- Case of selected component (which is what a qualification
7653 -- looks like in the unanalyzed tree, which is what we have.
7654
7655 elsif Nkind (N) = N_Selected_Component then
7656
7657 -- If selector name is not our type, keeping going (we might
7658 -- still have an occurrence of the type in the prefix).
7659
7660 if Nkind (Selector_Name (N)) /= N_Identifier
7661 or else Chars (Selector_Name (N)) /= TName
7662 then
7663 return OK;
7664
7665 -- Selector name is our type, check qualification
7666
7667 else
7668 -- Loop through scopes and prefixes, doing comparison
7669
7670 S := Current_Scope;
7671 P := Prefix (N);
7672 loop
7673 -- Continue if no more scopes or scope with no name
7674
7675 if No (S) or else Nkind (S) not in N_Has_Chars then
7676 return OK;
7677 end if;
7678
7679 -- Do replace if prefix is an identifier matching the
7680 -- scope that we are currently looking at.
7681
7682 if Nkind (P) = N_Identifier
7683 and then Chars (P) = Chars (S)
7684 then
7685 Replace_Type_Reference (N);
7686 return Skip;
7687 end if;
7688
7689 -- Go check scope above us if prefix is itself of the
7690 -- form of a selected component, whose selector matches
7691 -- the scope we are currently looking at.
7692
7693 if Nkind (P) = N_Selected_Component
7694 and then Nkind (Selector_Name (P)) = N_Identifier
7695 and then Chars (Selector_Name (P)) = Chars (S)
7696 then
7697 S := Scope (S);
7698 P := Prefix (P);
7699
7700 -- For anything else, we don't have a match, so keep on
7701 -- going, there are still some weird cases where we may
7702 -- still have a replacement within the prefix.
7703
7704 else
7705 return OK;
7706 end if;
7707 end loop;
7708 end if;
7709
7710 -- Continue for any other node kind
7711
7712 else
7713 return OK;
7714 end if;
7715 end Replace_Node;
7716
7717 begin
7718 Replace_Type_Refs (N);
7719 end Replace_Type_References_Generic;
7720
7721 -------------------------
7722 -- Same_Representation --
7723 -------------------------
7724
7725 function Same_Representation (Typ1, Typ2 : Entity_Id) return Boolean is
7726 T1 : constant Entity_Id := Underlying_Type (Typ1);
7727 T2 : constant Entity_Id := Underlying_Type (Typ2);
7728
7729 begin
7730 -- A quick check, if base types are the same, then we definitely have
7731 -- the same representation, because the subtype specific representation
7732 -- attributes (Size and Alignment) do not affect representation from
7733 -- the point of view of this test.
7734
7735 if Base_Type (T1) = Base_Type (T2) then
7736 return True;
7737
7738 elsif Is_Private_Type (Base_Type (T2))
7739 and then Base_Type (T1) = Full_View (Base_Type (T2))
7740 then
7741 return True;
7742 end if;
7743
7744 -- Tagged types never have differing representations
7745
7746 if Is_Tagged_Type (T1) then
7747 return True;
7748 end if;
7749
7750 -- Representations are definitely different if conventions differ
7751
7752 if Convention (T1) /= Convention (T2) then
7753 return False;
7754 end if;
7755
7756 -- Representations are different if component alignments differ
7757
7758 if (Is_Record_Type (T1) or else Is_Array_Type (T1))
7759 and then
7760 (Is_Record_Type (T2) or else Is_Array_Type (T2))
7761 and then Component_Alignment (T1) /= Component_Alignment (T2)
7762 then
7763 return False;
7764 end if;
7765
7766 -- For arrays, the only real issue is component size. If we know the
7767 -- component size for both arrays, and it is the same, then that's
7768 -- good enough to know we don't have a change of representation.
7769
7770 if Is_Array_Type (T1) then
7771 if Known_Component_Size (T1)
7772 and then Known_Component_Size (T2)
7773 and then Component_Size (T1) = Component_Size (T2)
7774 then
7775 if VM_Target = No_VM then
7776 return True;
7777
7778 -- In VM targets the representation of arrays with aliased
7779 -- components differs from arrays with non-aliased components
7780
7781 else
7782 return Has_Aliased_Components (Base_Type (T1))
7783 =
7784 Has_Aliased_Components (Base_Type (T2));
7785 end if;
7786 end if;
7787 end if;
7788
7789 -- Types definitely have same representation if neither has non-standard
7790 -- representation since default representations are always consistent.
7791 -- If only one has non-standard representation, and the other does not,
7792 -- then we consider that they do not have the same representation. They
7793 -- might, but there is no way of telling early enough.
7794
7795 if Has_Non_Standard_Rep (T1) then
7796 if not Has_Non_Standard_Rep (T2) then
7797 return False;
7798 end if;
7799 else
7800 return not Has_Non_Standard_Rep (T2);
7801 end if;
7802
7803 -- Here the two types both have non-standard representation, and we need
7804 -- to determine if they have the same non-standard representation.
7805
7806 -- For arrays, we simply need to test if the component sizes are the
7807 -- same. Pragma Pack is reflected in modified component sizes, so this
7808 -- check also deals with pragma Pack.
7809
7810 if Is_Array_Type (T1) then
7811 return Component_Size (T1) = Component_Size (T2);
7812
7813 -- Tagged types always have the same representation, because it is not
7814 -- possible to specify different representations for common fields.
7815
7816 elsif Is_Tagged_Type (T1) then
7817 return True;
7818
7819 -- Case of record types
7820
7821 elsif Is_Record_Type (T1) then
7822
7823 -- Packed status must conform
7824
7825 if Is_Packed (T1) /= Is_Packed (T2) then
7826 return False;
7827
7828 -- Otherwise we must check components. Typ2 maybe a constrained
7829 -- subtype with fewer components, so we compare the components
7830 -- of the base types.
7831
7832 else
7833 Record_Case : declare
7834 CD1, CD2 : Entity_Id;
7835
7836 function Same_Rep return Boolean;
7837 -- CD1 and CD2 are either components or discriminants. This
7838 -- function tests whether the two have the same representation
7839
7840 --------------
7841 -- Same_Rep --
7842 --------------
7843
7844 function Same_Rep return Boolean is
7845 begin
7846 if No (Component_Clause (CD1)) then
7847 return No (Component_Clause (CD2));
7848
7849 else
7850 return
7851 Present (Component_Clause (CD2))
7852 and then
7853 Component_Bit_Offset (CD1) = Component_Bit_Offset (CD2)
7854 and then
7855 Esize (CD1) = Esize (CD2);
7856 end if;
7857 end Same_Rep;
7858
7859 -- Start of processing for Record_Case
7860
7861 begin
7862 if Has_Discriminants (T1) then
7863 CD1 := First_Discriminant (T1);
7864 CD2 := First_Discriminant (T2);
7865
7866 -- The number of discriminants may be different if the
7867 -- derived type has fewer (constrained by values). The
7868 -- invisible discriminants retain the representation of
7869 -- the original, so the discrepancy does not per se
7870 -- indicate a different representation.
7871
7872 while Present (CD1)
7873 and then Present (CD2)
7874 loop
7875 if not Same_Rep then
7876 return False;
7877 else
7878 Next_Discriminant (CD1);
7879 Next_Discriminant (CD2);
7880 end if;
7881 end loop;
7882 end if;
7883
7884 CD1 := First_Component (Underlying_Type (Base_Type (T1)));
7885 CD2 := First_Component (Underlying_Type (Base_Type (T2)));
7886
7887 while Present (CD1) loop
7888 if not Same_Rep then
7889 return False;
7890 else
7891 Next_Component (CD1);
7892 Next_Component (CD2);
7893 end if;
7894 end loop;
7895
7896 return True;
7897 end Record_Case;
7898 end if;
7899
7900 -- For enumeration types, we must check each literal to see if the
7901 -- representation is the same. Note that we do not permit enumeration
7902 -- representation clauses for Character and Wide_Character, so these
7903 -- cases were already dealt with.
7904
7905 elsif Is_Enumeration_Type (T1) then
7906 Enumeration_Case : declare
7907 L1, L2 : Entity_Id;
7908
7909 begin
7910 L1 := First_Literal (T1);
7911 L2 := First_Literal (T2);
7912
7913 while Present (L1) loop
7914 if Enumeration_Rep (L1) /= Enumeration_Rep (L2) then
7915 return False;
7916 else
7917 Next_Literal (L1);
7918 Next_Literal (L2);
7919 end if;
7920 end loop;
7921
7922 return True;
7923
7924 end Enumeration_Case;
7925
7926 -- Any other types have the same representation for these purposes
7927
7928 else
7929 return True;
7930 end if;
7931 end Same_Representation;
7932
7933 ----------------
7934 -- Set_Biased --
7935 ----------------
7936
7937 procedure Set_Biased
7938 (E : Entity_Id;
7939 N : Node_Id;
7940 Msg : String;
7941 Biased : Boolean := True)
7942 is
7943 begin
7944 if Biased then
7945 Set_Has_Biased_Representation (E);
7946
7947 if Warn_On_Biased_Representation then
7948 Error_Msg_NE
7949 ("?" & Msg & " forces biased representation for&", N, E);
7950 end if;
7951 end if;
7952 end Set_Biased;
7953
7954 --------------------
7955 -- Set_Enum_Esize --
7956 --------------------
7957
7958 procedure Set_Enum_Esize (T : Entity_Id) is
7959 Lo : Uint;
7960 Hi : Uint;
7961 Sz : Nat;
7962
7963 begin
7964 Init_Alignment (T);
7965
7966 -- Find the minimum standard size (8,16,32,64) that fits
7967
7968 Lo := Enumeration_Rep (Entity (Type_Low_Bound (T)));
7969 Hi := Enumeration_Rep (Entity (Type_High_Bound (T)));
7970
7971 if Lo < 0 then
7972 if Lo >= -Uint_2**07 and then Hi < Uint_2**07 then
7973 Sz := Standard_Character_Size; -- May be > 8 on some targets
7974
7975 elsif Lo >= -Uint_2**15 and then Hi < Uint_2**15 then
7976 Sz := 16;
7977
7978 elsif Lo >= -Uint_2**31 and then Hi < Uint_2**31 then
7979 Sz := 32;
7980
7981 else pragma Assert (Lo >= -Uint_2**63 and then Hi < Uint_2**63);
7982 Sz := 64;
7983 end if;
7984
7985 else
7986 if Hi < Uint_2**08 then
7987 Sz := Standard_Character_Size; -- May be > 8 on some targets
7988
7989 elsif Hi < Uint_2**16 then
7990 Sz := 16;
7991
7992 elsif Hi < Uint_2**32 then
7993 Sz := 32;
7994
7995 else pragma Assert (Hi < Uint_2**63);
7996 Sz := 64;
7997 end if;
7998 end if;
7999
8000 -- That minimum is the proper size unless we have a foreign convention
8001 -- and the size required is 32 or less, in which case we bump the size
8002 -- up to 32. This is required for C and C++ and seems reasonable for
8003 -- all other foreign conventions.
8004
8005 if Has_Foreign_Convention (T)
8006 and then Esize (T) < Standard_Integer_Size
8007 then
8008 Init_Esize (T, Standard_Integer_Size);
8009 else
8010 Init_Esize (T, Sz);
8011 end if;
8012 end Set_Enum_Esize;
8013
8014 ------------------------------
8015 -- Validate_Address_Clauses --
8016 ------------------------------
8017
8018 procedure Validate_Address_Clauses is
8019 begin
8020 for J in Address_Clause_Checks.First .. Address_Clause_Checks.Last loop
8021 declare
8022 ACCR : Address_Clause_Check_Record
8023 renames Address_Clause_Checks.Table (J);
8024
8025 Expr : Node_Id;
8026
8027 X_Alignment : Uint;
8028 Y_Alignment : Uint;
8029
8030 X_Size : Uint;
8031 Y_Size : Uint;
8032
8033 begin
8034 -- Skip processing of this entry if warning already posted
8035
8036 if not Address_Warning_Posted (ACCR.N) then
8037
8038 Expr := Original_Node (Expression (ACCR.N));
8039
8040 -- Get alignments
8041
8042 X_Alignment := Alignment (ACCR.X);
8043 Y_Alignment := Alignment (ACCR.Y);
8044
8045 -- Similarly obtain sizes
8046
8047 X_Size := Esize (ACCR.X);
8048 Y_Size := Esize (ACCR.Y);
8049
8050 -- Check for large object overlaying smaller one
8051
8052 if Y_Size > Uint_0
8053 and then X_Size > Uint_0
8054 and then X_Size > Y_Size
8055 then
8056 Error_Msg_NE
8057 ("?& overlays smaller object", ACCR.N, ACCR.X);
8058 Error_Msg_N
8059 ("\?program execution may be erroneous", ACCR.N);
8060 Error_Msg_Uint_1 := X_Size;
8061 Error_Msg_NE
8062 ("\?size of & is ^", ACCR.N, ACCR.X);
8063 Error_Msg_Uint_1 := Y_Size;
8064 Error_Msg_NE
8065 ("\?size of & is ^", ACCR.N, ACCR.Y);
8066
8067 -- Check for inadequate alignment, both of the base object
8068 -- and of the offset, if any.
8069
8070 -- Note: we do not check the alignment if we gave a size
8071 -- warning, since it would likely be redundant.
8072
8073 elsif Y_Alignment /= Uint_0
8074 and then (Y_Alignment < X_Alignment
8075 or else (ACCR.Off
8076 and then
8077 Nkind (Expr) = N_Attribute_Reference
8078 and then
8079 Attribute_Name (Expr) = Name_Address
8080 and then
8081 Has_Compatible_Alignment
8082 (ACCR.X, Prefix (Expr))
8083 /= Known_Compatible))
8084 then
8085 Error_Msg_NE
8086 ("?specified address for& may be inconsistent "
8087 & "with alignment",
8088 ACCR.N, ACCR.X);
8089 Error_Msg_N
8090 ("\?program execution may be erroneous (RM 13.3(27))",
8091 ACCR.N);
8092 Error_Msg_Uint_1 := X_Alignment;
8093 Error_Msg_NE
8094 ("\?alignment of & is ^",
8095 ACCR.N, ACCR.X);
8096 Error_Msg_Uint_1 := Y_Alignment;
8097 Error_Msg_NE
8098 ("\?alignment of & is ^",
8099 ACCR.N, ACCR.Y);
8100 if Y_Alignment >= X_Alignment then
8101 Error_Msg_N
8102 ("\?but offset is not multiple of alignment",
8103 ACCR.N);
8104 end if;
8105 end if;
8106 end if;
8107 end;
8108 end loop;
8109 end Validate_Address_Clauses;
8110
8111 ---------------------------
8112 -- Validate_Independence --
8113 ---------------------------
8114
8115 procedure Validate_Independence is
8116 SU : constant Uint := UI_From_Int (System_Storage_Unit);
8117 N : Node_Id;
8118 E : Entity_Id;
8119 IC : Boolean;
8120 Comp : Entity_Id;
8121 Addr : Node_Id;
8122 P : Node_Id;
8123
8124 procedure Check_Array_Type (Atyp : Entity_Id);
8125 -- Checks if the array type Atyp has independent components, and
8126 -- if not, outputs an appropriate set of error messages.
8127
8128 procedure No_Independence;
8129 -- Output message that independence cannot be guaranteed
8130
8131 function OK_Component (C : Entity_Id) return Boolean;
8132 -- Checks one component to see if it is independently accessible, and
8133 -- if so yields True, otherwise yields False if independent access
8134 -- cannot be guaranteed. This is a conservative routine, it only
8135 -- returns True if it knows for sure, it returns False if it knows
8136 -- there is a problem, or it cannot be sure there is no problem.
8137
8138 procedure Reason_Bad_Component (C : Entity_Id);
8139 -- Outputs continuation message if a reason can be determined for
8140 -- the component C being bad.
8141
8142 ----------------------
8143 -- Check_Array_Type --
8144 ----------------------
8145
8146 procedure Check_Array_Type (Atyp : Entity_Id) is
8147 Ctyp : constant Entity_Id := Component_Type (Atyp);
8148
8149 begin
8150 -- OK if no alignment clause, no pack, and no component size
8151
8152 if not Has_Component_Size_Clause (Atyp)
8153 and then not Has_Alignment_Clause (Atyp)
8154 and then not Is_Packed (Atyp)
8155 then
8156 return;
8157 end if;
8158
8159 -- Check actual component size
8160
8161 if not Known_Component_Size (Atyp)
8162 or else not (Addressable (Component_Size (Atyp))
8163 and then Component_Size (Atyp) < 64)
8164 or else Component_Size (Atyp) mod Esize (Ctyp) /= 0
8165 then
8166 No_Independence;
8167
8168 -- Bad component size, check reason
8169
8170 if Has_Component_Size_Clause (Atyp) then
8171 P :=
8172 Get_Attribute_Definition_Clause
8173 (Atyp, Attribute_Component_Size);
8174
8175 if Present (P) then
8176 Error_Msg_Sloc := Sloc (P);
8177 Error_Msg_N ("\because of Component_Size clause#", N);
8178 return;
8179 end if;
8180 end if;
8181
8182 if Is_Packed (Atyp) then
8183 P := Get_Rep_Pragma (Atyp, Name_Pack);
8184
8185 if Present (P) then
8186 Error_Msg_Sloc := Sloc (P);
8187 Error_Msg_N ("\because of pragma Pack#", N);
8188 return;
8189 end if;
8190 end if;
8191
8192 -- No reason found, just return
8193
8194 return;
8195 end if;
8196
8197 -- Array type is OK independence-wise
8198
8199 return;
8200 end Check_Array_Type;
8201
8202 ---------------------
8203 -- No_Independence --
8204 ---------------------
8205
8206 procedure No_Independence is
8207 begin
8208 if Pragma_Name (N) = Name_Independent then
8209 Error_Msg_NE
8210 ("independence cannot be guaranteed for&", N, E);
8211 else
8212 Error_Msg_NE
8213 ("independent components cannot be guaranteed for&", N, E);
8214 end if;
8215 end No_Independence;
8216
8217 ------------------
8218 -- OK_Component --
8219 ------------------
8220
8221 function OK_Component (C : Entity_Id) return Boolean is
8222 Rec : constant Entity_Id := Scope (C);
8223 Ctyp : constant Entity_Id := Etype (C);
8224
8225 begin
8226 -- OK if no component clause, no Pack, and no alignment clause
8227
8228 if No (Component_Clause (C))
8229 and then not Is_Packed (Rec)
8230 and then not Has_Alignment_Clause (Rec)
8231 then
8232 return True;
8233 end if;
8234
8235 -- Here we look at the actual component layout. A component is
8236 -- addressable if its size is a multiple of the Esize of the
8237 -- component type, and its starting position in the record has
8238 -- appropriate alignment, and the record itself has appropriate
8239 -- alignment to guarantee the component alignment.
8240
8241 -- Make sure sizes are static, always assume the worst for any
8242 -- cases where we cannot check static values.
8243
8244 if not (Known_Static_Esize (C)
8245 and then Known_Static_Esize (Ctyp))
8246 then
8247 return False;
8248 end if;
8249
8250 -- Size of component must be addressable or greater than 64 bits
8251 -- and a multiple of bytes.
8252
8253 if not Addressable (Esize (C))
8254 and then Esize (C) < Uint_64
8255 then
8256 return False;
8257 end if;
8258
8259 -- Check size is proper multiple
8260
8261 if Esize (C) mod Esize (Ctyp) /= 0 then
8262 return False;
8263 end if;
8264
8265 -- Check alignment of component is OK
8266
8267 if not Known_Component_Bit_Offset (C)
8268 or else Component_Bit_Offset (C) < Uint_0
8269 or else Component_Bit_Offset (C) mod Esize (Ctyp) /= 0
8270 then
8271 return False;
8272 end if;
8273
8274 -- Check alignment of record type is OK
8275
8276 if not Known_Alignment (Rec)
8277 or else (Alignment (Rec) * SU) mod Esize (Ctyp) /= 0
8278 then
8279 return False;
8280 end if;
8281
8282 -- All tests passed, component is addressable
8283
8284 return True;
8285 end OK_Component;
8286
8287 --------------------------
8288 -- Reason_Bad_Component --
8289 --------------------------
8290
8291 procedure Reason_Bad_Component (C : Entity_Id) is
8292 Rec : constant Entity_Id := Scope (C);
8293 Ctyp : constant Entity_Id := Etype (C);
8294
8295 begin
8296 -- If component clause present assume that's the problem
8297
8298 if Present (Component_Clause (C)) then
8299 Error_Msg_Sloc := Sloc (Component_Clause (C));
8300 Error_Msg_N ("\because of Component_Clause#", N);
8301 return;
8302 end if;
8303
8304 -- If pragma Pack clause present, assume that's the problem
8305
8306 if Is_Packed (Rec) then
8307 P := Get_Rep_Pragma (Rec, Name_Pack);
8308
8309 if Present (P) then
8310 Error_Msg_Sloc := Sloc (P);
8311 Error_Msg_N ("\because of pragma Pack#", N);
8312 return;
8313 end if;
8314 end if;
8315
8316 -- See if record has bad alignment clause
8317
8318 if Has_Alignment_Clause (Rec)
8319 and then Known_Alignment (Rec)
8320 and then (Alignment (Rec) * SU) mod Esize (Ctyp) /= 0
8321 then
8322 P := Get_Attribute_Definition_Clause (Rec, Attribute_Alignment);
8323
8324 if Present (P) then
8325 Error_Msg_Sloc := Sloc (P);
8326 Error_Msg_N ("\because of Alignment clause#", N);
8327 end if;
8328 end if;
8329
8330 -- Couldn't find a reason, so return without a message
8331
8332 return;
8333 end Reason_Bad_Component;
8334
8335 -- Start of processing for Validate_Independence
8336
8337 begin
8338 for J in Independence_Checks.First .. Independence_Checks.Last loop
8339 N := Independence_Checks.Table (J).N;
8340 E := Independence_Checks.Table (J).E;
8341 IC := Pragma_Name (N) = Name_Independent_Components;
8342
8343 -- Deal with component case
8344
8345 if Ekind (E) = E_Discriminant or else Ekind (E) = E_Component then
8346 if not OK_Component (E) then
8347 No_Independence;
8348 Reason_Bad_Component (E);
8349 goto Continue;
8350 end if;
8351 end if;
8352
8353 -- Deal with record with Independent_Components
8354
8355 if IC and then Is_Record_Type (E) then
8356 Comp := First_Component_Or_Discriminant (E);
8357 while Present (Comp) loop
8358 if not OK_Component (Comp) then
8359 No_Independence;
8360 Reason_Bad_Component (Comp);
8361 goto Continue;
8362 end if;
8363
8364 Next_Component_Or_Discriminant (Comp);
8365 end loop;
8366 end if;
8367
8368 -- Deal with address clause case
8369
8370 if Is_Object (E) then
8371 Addr := Address_Clause (E);
8372
8373 if Present (Addr) then
8374 No_Independence;
8375 Error_Msg_Sloc := Sloc (Addr);
8376 Error_Msg_N ("\because of Address clause#", N);
8377 goto Continue;
8378 end if;
8379 end if;
8380
8381 -- Deal with independent components for array type
8382
8383 if IC and then Is_Array_Type (E) then
8384 Check_Array_Type (E);
8385 end if;
8386
8387 -- Deal with independent components for array object
8388
8389 if IC and then Is_Object (E) and then Is_Array_Type (Etype (E)) then
8390 Check_Array_Type (Etype (E));
8391 end if;
8392
8393 <<Continue>> null;
8394 end loop;
8395 end Validate_Independence;
8396
8397 -----------------------------------
8398 -- Validate_Unchecked_Conversion --
8399 -----------------------------------
8400
8401 procedure Validate_Unchecked_Conversion
8402 (N : Node_Id;
8403 Act_Unit : Entity_Id)
8404 is
8405 Source : Entity_Id;
8406 Target : Entity_Id;
8407 Vnode : Node_Id;
8408
8409 begin
8410 -- Obtain source and target types. Note that we call Ancestor_Subtype
8411 -- here because the processing for generic instantiation always makes
8412 -- subtypes, and we want the original frozen actual types.
8413
8414 -- If we are dealing with private types, then do the check on their
8415 -- fully declared counterparts if the full declarations have been
8416 -- encountered (they don't have to be visible, but they must exist!)
8417
8418 Source := Ancestor_Subtype (Etype (First_Formal (Act_Unit)));
8419
8420 if Is_Private_Type (Source)
8421 and then Present (Underlying_Type (Source))
8422 then
8423 Source := Underlying_Type (Source);
8424 end if;
8425
8426 Target := Ancestor_Subtype (Etype (Act_Unit));
8427
8428 -- If either type is generic, the instantiation happens within a generic
8429 -- unit, and there is nothing to check. The proper check
8430 -- will happen when the enclosing generic is instantiated.
8431
8432 if Is_Generic_Type (Source) or else Is_Generic_Type (Target) then
8433 return;
8434 end if;
8435
8436 if Is_Private_Type (Target)
8437 and then Present (Underlying_Type (Target))
8438 then
8439 Target := Underlying_Type (Target);
8440 end if;
8441
8442 -- Source may be unconstrained array, but not target
8443
8444 if Is_Array_Type (Target)
8445 and then not Is_Constrained (Target)
8446 then
8447 Error_Msg_N
8448 ("unchecked conversion to unconstrained array not allowed", N);
8449 return;
8450 end if;
8451
8452 -- Warn if conversion between two different convention pointers
8453
8454 if Is_Access_Type (Target)
8455 and then Is_Access_Type (Source)
8456 and then Convention (Target) /= Convention (Source)
8457 and then Warn_On_Unchecked_Conversion
8458 then
8459 -- Give warnings for subprogram pointers only on most targets. The
8460 -- exception is VMS, where data pointers can have different lengths
8461 -- depending on the pointer convention.
8462
8463 if Is_Access_Subprogram_Type (Target)
8464 or else Is_Access_Subprogram_Type (Source)
8465 or else OpenVMS_On_Target
8466 then
8467 Error_Msg_N
8468 ("?conversion between pointers with different conventions!", N);
8469 end if;
8470 end if;
8471
8472 -- Warn if one of the operands is Ada.Calendar.Time. Do not emit a
8473 -- warning when compiling GNAT-related sources.
8474
8475 if Warn_On_Unchecked_Conversion
8476 and then not In_Predefined_Unit (N)
8477 and then RTU_Loaded (Ada_Calendar)
8478 and then
8479 (Chars (Source) = Name_Time
8480 or else
8481 Chars (Target) = Name_Time)
8482 then
8483 -- If Ada.Calendar is loaded and the name of one of the operands is
8484 -- Time, there is a good chance that this is Ada.Calendar.Time.
8485
8486 declare
8487 Calendar_Time : constant Entity_Id :=
8488 Full_View (RTE (RO_CA_Time));
8489 begin
8490 pragma Assert (Present (Calendar_Time));
8491
8492 if Source = Calendar_Time
8493 or else Target = Calendar_Time
8494 then
8495 Error_Msg_N
8496 ("?representation of 'Time values may change between " &
8497 "'G'N'A'T versions", N);
8498 end if;
8499 end;
8500 end if;
8501
8502 -- Make entry in unchecked conversion table for later processing by
8503 -- Validate_Unchecked_Conversions, which will check sizes and alignments
8504 -- (using values set by the back-end where possible). This is only done
8505 -- if the appropriate warning is active.
8506
8507 if Warn_On_Unchecked_Conversion then
8508 Unchecked_Conversions.Append
8509 (New_Val => UC_Entry'
8510 (Eloc => Sloc (N),
8511 Source => Source,
8512 Target => Target));
8513
8514 -- If both sizes are known statically now, then back end annotation
8515 -- is not required to do a proper check but if either size is not
8516 -- known statically, then we need the annotation.
8517
8518 if Known_Static_RM_Size (Source)
8519 and then Known_Static_RM_Size (Target)
8520 then
8521 null;
8522 else
8523 Back_Annotate_Rep_Info := True;
8524 end if;
8525 end if;
8526
8527 -- If unchecked conversion to access type, and access type is declared
8528 -- in the same unit as the unchecked conversion, then set the
8529 -- No_Strict_Aliasing flag (no strict aliasing is implicit in this
8530 -- situation).
8531
8532 if Is_Access_Type (Target) and then
8533 In_Same_Source_Unit (Target, N)
8534 then
8535 Set_No_Strict_Aliasing (Implementation_Base_Type (Target));
8536 end if;
8537
8538 -- Generate N_Validate_Unchecked_Conversion node for back end in
8539 -- case the back end needs to perform special validation checks.
8540
8541 -- Shouldn't this be in Exp_Ch13, since the check only gets done
8542 -- if we have full expansion and the back end is called ???
8543
8544 Vnode :=
8545 Make_Validate_Unchecked_Conversion (Sloc (N));
8546 Set_Source_Type (Vnode, Source);
8547 Set_Target_Type (Vnode, Target);
8548
8549 -- If the unchecked conversion node is in a list, just insert before it.
8550 -- If not we have some strange case, not worth bothering about.
8551
8552 if Is_List_Member (N) then
8553 Insert_After (N, Vnode);
8554 end if;
8555 end Validate_Unchecked_Conversion;
8556
8557 ------------------------------------
8558 -- Validate_Unchecked_Conversions --
8559 ------------------------------------
8560
8561 procedure Validate_Unchecked_Conversions is
8562 begin
8563 for N in Unchecked_Conversions.First .. Unchecked_Conversions.Last loop
8564 declare
8565 T : UC_Entry renames Unchecked_Conversions.Table (N);
8566
8567 Eloc : constant Source_Ptr := T.Eloc;
8568 Source : constant Entity_Id := T.Source;
8569 Target : constant Entity_Id := T.Target;
8570
8571 Source_Siz : Uint;
8572 Target_Siz : Uint;
8573
8574 begin
8575 -- This validation check, which warns if we have unequal sizes for
8576 -- unchecked conversion, and thus potentially implementation
8577 -- dependent semantics, is one of the few occasions on which we
8578 -- use the official RM size instead of Esize. See description in
8579 -- Einfo "Handling of Type'Size Values" for details.
8580
8581 if Serious_Errors_Detected = 0
8582 and then Known_Static_RM_Size (Source)
8583 and then Known_Static_RM_Size (Target)
8584
8585 -- Don't do the check if warnings off for either type, note the
8586 -- deliberate use of OR here instead of OR ELSE to get the flag
8587 -- Warnings_Off_Used set for both types if appropriate.
8588
8589 and then not (Has_Warnings_Off (Source)
8590 or
8591 Has_Warnings_Off (Target))
8592 then
8593 Source_Siz := RM_Size (Source);
8594 Target_Siz := RM_Size (Target);
8595
8596 if Source_Siz /= Target_Siz then
8597 Error_Msg
8598 ("?types for unchecked conversion have different sizes!",
8599 Eloc);
8600
8601 if All_Errors_Mode then
8602 Error_Msg_Name_1 := Chars (Source);
8603 Error_Msg_Uint_1 := Source_Siz;
8604 Error_Msg_Name_2 := Chars (Target);
8605 Error_Msg_Uint_2 := Target_Siz;
8606 Error_Msg ("\size of % is ^, size of % is ^?", Eloc);
8607
8608 Error_Msg_Uint_1 := UI_Abs (Source_Siz - Target_Siz);
8609
8610 if Is_Discrete_Type (Source)
8611 and then Is_Discrete_Type (Target)
8612 then
8613 if Source_Siz > Target_Siz then
8614 Error_Msg
8615 ("\?^ high order bits of source will be ignored!",
8616 Eloc);
8617
8618 elsif Is_Unsigned_Type (Source) then
8619 Error_Msg
8620 ("\?source will be extended with ^ high order " &
8621 "zero bits?!", Eloc);
8622
8623 else
8624 Error_Msg
8625 ("\?source will be extended with ^ high order " &
8626 "sign bits!",
8627 Eloc);
8628 end if;
8629
8630 elsif Source_Siz < Target_Siz then
8631 if Is_Discrete_Type (Target) then
8632 if Bytes_Big_Endian then
8633 Error_Msg
8634 ("\?target value will include ^ undefined " &
8635 "low order bits!",
8636 Eloc);
8637 else
8638 Error_Msg
8639 ("\?target value will include ^ undefined " &
8640 "high order bits!",
8641 Eloc);
8642 end if;
8643
8644 else
8645 Error_Msg
8646 ("\?^ trailing bits of target value will be " &
8647 "undefined!", Eloc);
8648 end if;
8649
8650 else pragma Assert (Source_Siz > Target_Siz);
8651 Error_Msg
8652 ("\?^ trailing bits of source will be ignored!",
8653 Eloc);
8654 end if;
8655 end if;
8656 end if;
8657 end if;
8658
8659 -- If both types are access types, we need to check the alignment.
8660 -- If the alignment of both is specified, we can do it here.
8661
8662 if Serious_Errors_Detected = 0
8663 and then Ekind (Source) in Access_Kind
8664 and then Ekind (Target) in Access_Kind
8665 and then Target_Strict_Alignment
8666 and then Present (Designated_Type (Source))
8667 and then Present (Designated_Type (Target))
8668 then
8669 declare
8670 D_Source : constant Entity_Id := Designated_Type (Source);
8671 D_Target : constant Entity_Id := Designated_Type (Target);
8672
8673 begin
8674 if Known_Alignment (D_Source)
8675 and then Known_Alignment (D_Target)
8676 then
8677 declare
8678 Source_Align : constant Uint := Alignment (D_Source);
8679 Target_Align : constant Uint := Alignment (D_Target);
8680
8681 begin
8682 if Source_Align < Target_Align
8683 and then not Is_Tagged_Type (D_Source)
8684
8685 -- Suppress warning if warnings suppressed on either
8686 -- type or either designated type. Note the use of
8687 -- OR here instead of OR ELSE. That is intentional,
8688 -- we would like to set flag Warnings_Off_Used in
8689 -- all types for which warnings are suppressed.
8690
8691 and then not (Has_Warnings_Off (D_Source)
8692 or
8693 Has_Warnings_Off (D_Target)
8694 or
8695 Has_Warnings_Off (Source)
8696 or
8697 Has_Warnings_Off (Target))
8698 then
8699 Error_Msg_Uint_1 := Target_Align;
8700 Error_Msg_Uint_2 := Source_Align;
8701 Error_Msg_Node_1 := D_Target;
8702 Error_Msg_Node_2 := D_Source;
8703 Error_Msg
8704 ("?alignment of & (^) is stricter than " &
8705 "alignment of & (^)!", Eloc);
8706 Error_Msg
8707 ("\?resulting access value may have invalid " &
8708 "alignment!", Eloc);
8709 end if;
8710 end;
8711 end if;
8712 end;
8713 end if;
8714 end;
8715 end loop;
8716 end Validate_Unchecked_Conversions;
8717
8718 end Sem_Ch13;