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