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