[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-2013, 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 Debug; use Debug;
30 with Einfo; use Einfo;
31 with Elists; use Elists;
32 with Errout; use Errout;
33 with Exp_Disp; use Exp_Disp;
34 with Exp_Tss; use Exp_Tss;
35 with Exp_Util; use Exp_Util;
36 with Lib; use Lib;
37 with Lib.Xref; use Lib.Xref;
38 with Namet; use Namet;
39 with Nlists; use Nlists;
40 with Nmake; use Nmake;
41 with Opt; use Opt;
42 with Restrict; use Restrict;
43 with Rident; use Rident;
44 with Rtsfind; use Rtsfind;
45 with Sem; use Sem;
46 with Sem_Aux; use Sem_Aux;
47 with Sem_Case; use Sem_Case;
48 with Sem_Ch3; use Sem_Ch3;
49 with Sem_Ch6; use Sem_Ch6;
50 with Sem_Ch8; use Sem_Ch8;
51 with Sem_Ch9; use Sem_Ch9;
52 with Sem_Dim; use Sem_Dim;
53 with Sem_Disp; use Sem_Disp;
54 with Sem_Eval; use Sem_Eval;
55 with Sem_Prag; use Sem_Prag;
56 with Sem_Res; use Sem_Res;
57 with Sem_Type; use Sem_Type;
58 with Sem_Util; use Sem_Util;
59 with Sem_Warn; use Sem_Warn;
60 with Sinput; use Sinput;
61 with Snames; use Snames;
62 with Stand; use Stand;
63 with Sinfo; use Sinfo;
64 with Stringt; use Stringt;
65 with Targparm; use Targparm;
66 with Ttypes; use Ttypes;
67 with Tbuild; use Tbuild;
68 with Urealp; use Urealp;
69 with Warnsw; use Warnsw;
70
71 with GNAT.Heap_Sort_G;
72
73 package body Sem_Ch13 is
74
75 SSU : constant Pos := System_Storage_Unit;
76 -- Convenient short hand for commonly used constant
77
78 -----------------------
79 -- Local Subprograms --
80 -----------------------
81
82 procedure Alignment_Check_For_Size_Change (Typ : Entity_Id; Size : Uint);
83 -- This routine is called after setting one of the sizes of type entity
84 -- Typ to Size. The purpose is to deal with the situation of a derived
85 -- type whose inherited alignment is no longer appropriate for the new
86 -- size value. In this case, we reset the Alignment to unknown.
87
88 procedure Build_Predicate_Functions (Typ : Entity_Id; N : Node_Id);
89 -- If Typ has predicates (indicated by Has_Predicates being set for Typ,
90 -- then either there are pragma Predicate entries on the rep chain for the
91 -- type (note that Predicate aspects are converted to pragma Predicate), or
92 -- there are inherited aspects from a parent type, or ancestor subtypes.
93 -- This procedure builds the spec and body for the Predicate function that
94 -- tests these predicates. N is the freeze node for the type. The spec of
95 -- the function is inserted before the freeze node, and the body of the
96 -- function is inserted after the freeze node. If the predicate expression
97 -- has at least one Raise_Expression, then this procedure also builds the
98 -- M version of the predicate function for use in membership tests.
99
100 procedure Build_Static_Predicate
101 (Typ : Entity_Id;
102 Expr : Node_Id;
103 Nam : Name_Id);
104 -- Given a predicated type Typ, where Typ is a discrete static subtype,
105 -- whose predicate expression is Expr, tests if Expr is a static predicate,
106 -- and if so, builds the predicate range list. Nam is the name of the one
107 -- argument to the predicate function. Occurrences of the type name in the
108 -- predicate expression have been replaced by identifier references to this
109 -- name, which is unique, so any identifier with Chars matching Nam must be
110 -- a reference to the type. If the predicate is non-static, this procedure
111 -- returns doing nothing. If the predicate is static, then the predicate
112 -- list is stored in Static_Predicate (Typ), and the Expr is rewritten as
113 -- a canonicalized membership operation.
114
115 function Get_Alignment_Value (Expr : Node_Id) return Uint;
116 -- Given the expression for an alignment value, returns the corresponding
117 -- Uint value. If the value is inappropriate, then error messages are
118 -- posted as required, and a value of No_Uint is returned.
119
120 function Is_Operational_Item (N : Node_Id) return Boolean;
121 -- A specification for a stream attribute is allowed before the full type
122 -- is declared, as explained in AI-00137 and the corrigendum. Attributes
123 -- that do not specify a representation characteristic are operational
124 -- attributes.
125
126 procedure New_Stream_Subprogram
127 (N : Node_Id;
128 Ent : Entity_Id;
129 Subp : Entity_Id;
130 Nam : TSS_Name_Type);
131 -- Create a subprogram renaming of a given stream attribute to the
132 -- designated subprogram and then in the tagged case, provide this as a
133 -- primitive operation, or in the non-tagged case make an appropriate TSS
134 -- entry. This is more properly an expansion activity than just semantics,
135 -- but the presence of user-defined stream functions for limited types is a
136 -- legality check, which is why this takes place here rather than in
137 -- exp_ch13, where it was previously. Nam indicates the name of the TSS
138 -- function to be generated.
139 --
140 -- To avoid elaboration anomalies with freeze nodes, for untagged types
141 -- we generate both a subprogram declaration and a subprogram renaming
142 -- declaration, so that the attribute specification is handled as a
143 -- renaming_as_body. For tagged types, the specification is one of the
144 -- primitive specs.
145
146 generic
147 with procedure Replace_Type_Reference (N : Node_Id);
148 procedure Replace_Type_References_Generic (N : Node_Id; TName : Name_Id);
149 -- This is used to scan an expression for a predicate or invariant aspect
150 -- replacing occurrences of the name TName (the name of the subtype to
151 -- which the aspect applies) with appropriate references to the parameter
152 -- of the predicate function or invariant procedure. The procedure passed
153 -- as a generic parameter does the actual replacement of node N, which is
154 -- either a simple direct reference to TName, or a selected component that
155 -- represents an appropriately qualified occurrence of TName.
156
157 procedure Set_Biased
158 (E : Entity_Id;
159 N : Node_Id;
160 Msg : String;
161 Biased : Boolean := True);
162 -- If Biased is True, sets Has_Biased_Representation flag for E, and
163 -- outputs a warning message at node N if Warn_On_Biased_Representation is
164 -- is True. This warning inserts the string Msg to describe the construct
165 -- causing biasing.
166
167 ----------------------------------------------
168 -- Table for Validate_Unchecked_Conversions --
169 ----------------------------------------------
170
171 -- The following table collects unchecked conversions for validation.
172 -- Entries are made by Validate_Unchecked_Conversion and then the call
173 -- to Validate_Unchecked_Conversions does the actual error checking and
174 -- posting of warnings. The reason for this delayed processing is to take
175 -- advantage of back-annotations of size and alignment values performed by
176 -- the back end.
177
178 -- Note: the reason we store a Source_Ptr value instead of a Node_Id is
179 -- that by the time Validate_Unchecked_Conversions is called, Sprint will
180 -- already have modified all Sloc values if the -gnatD option is set.
181
182 type UC_Entry is record
183 Eloc : Source_Ptr; -- node used for posting warnings
184 Source : Entity_Id; -- source type for unchecked conversion
185 Target : Entity_Id; -- target type for unchecked conversion
186 end record;
187
188 package Unchecked_Conversions is new Table.Table (
189 Table_Component_Type => UC_Entry,
190 Table_Index_Type => Int,
191 Table_Low_Bound => 1,
192 Table_Initial => 50,
193 Table_Increment => 200,
194 Table_Name => "Unchecked_Conversions");
195
196 ----------------------------------------
197 -- Table for Validate_Address_Clauses --
198 ----------------------------------------
199
200 -- If an address clause has the form
201
202 -- for X'Address use Expr
203
204 -- where Expr is of the form Y'Address or recursively is a reference to a
205 -- constant of either of these forms, and X and Y are entities of objects,
206 -- then if Y has a smaller alignment than X, that merits a warning about
207 -- possible bad alignment. The following table collects address clauses of
208 -- this kind. We put these in a table so that they can be checked after the
209 -- back end has completed annotation of the alignments of objects, since we
210 -- can catch more cases that way.
211
212 type Address_Clause_Check_Record is record
213 N : Node_Id;
214 -- The address clause
215
216 X : Entity_Id;
217 -- The entity of the object overlaying Y
218
219 Y : Entity_Id;
220 -- The entity of the object being overlaid
221
222 Off : Boolean;
223 -- Whether the address is offset within Y
224 end record;
225
226 package Address_Clause_Checks is new Table.Table (
227 Table_Component_Type => Address_Clause_Check_Record,
228 Table_Index_Type => Int,
229 Table_Low_Bound => 1,
230 Table_Initial => 20,
231 Table_Increment => 200,
232 Table_Name => "Address_Clause_Checks");
233
234 -----------------------------------------
235 -- Adjust_Record_For_Reverse_Bit_Order --
236 -----------------------------------------
237
238 procedure Adjust_Record_For_Reverse_Bit_Order (R : Entity_Id) is
239 Comp : Node_Id;
240 CC : Node_Id;
241
242 begin
243 -- Processing depends on version of Ada
244
245 -- For Ada 95, we just renumber bits within a storage unit. We do the
246 -- same for Ada 83 mode, since we recognize the Bit_Order attribute in
247 -- Ada 83, and are free to add this extension.
248
249 if Ada_Version < Ada_2005 then
250 Comp := First_Component_Or_Discriminant (R);
251 while Present (Comp) loop
252 CC := Component_Clause (Comp);
253
254 -- If component clause is present, then deal with the non-default
255 -- bit order case for Ada 95 mode.
256
257 -- We only do this processing for the base type, and in fact that
258 -- is important, since otherwise if there are record subtypes, we
259 -- could reverse the bits once for each subtype, which is wrong.
260
261 if Present (CC) and then Ekind (R) = E_Record_Type then
262 declare
263 CFB : constant Uint := Component_Bit_Offset (Comp);
264 CSZ : constant Uint := Esize (Comp);
265 CLC : constant Node_Id := Component_Clause (Comp);
266 Pos : constant Node_Id := Position (CLC);
267 FB : constant Node_Id := First_Bit (CLC);
268
269 Storage_Unit_Offset : constant Uint :=
270 CFB / System_Storage_Unit;
271
272 Start_Bit : constant Uint :=
273 CFB mod System_Storage_Unit;
274
275 begin
276 -- Cases where field goes over storage unit boundary
277
278 if Start_Bit + CSZ > System_Storage_Unit then
279
280 -- Allow multi-byte field but generate warning
281
282 if Start_Bit mod System_Storage_Unit = 0
283 and then CSZ mod System_Storage_Unit = 0
284 then
285 Error_Msg_N
286 ("multi-byte field specified with non-standard"
287 & " Bit_Order??", CLC);
288
289 if Bytes_Big_Endian then
290 Error_Msg_N
291 ("bytes are not reversed "
292 & "(component is big-endian)??", CLC);
293 else
294 Error_Msg_N
295 ("bytes are not reversed "
296 & "(component is little-endian)??", CLC);
297 end if;
298
299 -- Do not allow non-contiguous field
300
301 else
302 Error_Msg_N
303 ("attempt to specify non-contiguous field "
304 & "not permitted", CLC);
305 Error_Msg_N
306 ("\caused by non-standard Bit_Order "
307 & "specified", CLC);
308 Error_Msg_N
309 ("\consider possibility of using "
310 & "Ada 2005 mode here", CLC);
311 end if;
312
313 -- Case where field fits in one storage unit
314
315 else
316 -- Give warning if suspicious component clause
317
318 if Intval (FB) >= System_Storage_Unit
319 and then Warn_On_Reverse_Bit_Order
320 then
321 Error_Msg_N
322 ("Bit_Order clause does not affect " &
323 "byte ordering?V?", Pos);
324 Error_Msg_Uint_1 :=
325 Intval (Pos) + Intval (FB) /
326 System_Storage_Unit;
327 Error_Msg_N
328 ("position normalized to ^ before bit " &
329 "order interpreted?V?", Pos);
330 end if;
331
332 -- Here is where we fix up the Component_Bit_Offset value
333 -- to account for the reverse bit order. Some examples of
334 -- what needs to be done are:
335
336 -- First_Bit .. Last_Bit Component_Bit_Offset
337 -- old new old new
338
339 -- 0 .. 0 7 .. 7 0 7
340 -- 0 .. 1 6 .. 7 0 6
341 -- 0 .. 2 5 .. 7 0 5
342 -- 0 .. 7 0 .. 7 0 4
343
344 -- 1 .. 1 6 .. 6 1 6
345 -- 1 .. 4 3 .. 6 1 3
346 -- 4 .. 7 0 .. 3 4 0
347
348 -- The rule is that the first bit is is obtained by
349 -- subtracting the old ending bit from storage_unit - 1.
350
351 Set_Component_Bit_Offset
352 (Comp,
353 (Storage_Unit_Offset * System_Storage_Unit) +
354 (System_Storage_Unit - 1) -
355 (Start_Bit + CSZ - 1));
356
357 Set_Normalized_First_Bit
358 (Comp,
359 Component_Bit_Offset (Comp) mod
360 System_Storage_Unit);
361 end if;
362 end;
363 end if;
364
365 Next_Component_Or_Discriminant (Comp);
366 end loop;
367
368 -- For Ada 2005, we do machine scalar processing, as fully described In
369 -- AI-133. This involves gathering all components which start at the
370 -- same byte offset and processing them together. Same approach is still
371 -- valid in later versions including Ada 2012.
372
373 else
374 declare
375 Max_Machine_Scalar_Size : constant Uint :=
376 UI_From_Int
377 (Standard_Long_Long_Integer_Size);
378 -- We use this as the maximum machine scalar size
379
380 Num_CC : Natural;
381 SSU : constant Uint := UI_From_Int (System_Storage_Unit);
382
383 begin
384 -- This first loop through components does two things. First it
385 -- deals with the case of components with component clauses whose
386 -- length is greater than the maximum machine scalar size (either
387 -- accepting them or rejecting as needed). Second, it counts the
388 -- number of components with component clauses whose length does
389 -- not exceed this maximum for later processing.
390
391 Num_CC := 0;
392 Comp := First_Component_Or_Discriminant (R);
393 while Present (Comp) loop
394 CC := Component_Clause (Comp);
395
396 if Present (CC) then
397 declare
398 Fbit : constant Uint := Static_Integer (First_Bit (CC));
399 Lbit : constant Uint := Static_Integer (Last_Bit (CC));
400
401 begin
402 -- Case of component with last bit >= max machine scalar
403
404 if Lbit >= Max_Machine_Scalar_Size then
405
406 -- This is allowed only if first bit is zero, and
407 -- last bit + 1 is a multiple of storage unit size.
408
409 if Fbit = 0 and then (Lbit + 1) mod SSU = 0 then
410
411 -- This is the case to give a warning if enabled
412
413 if Warn_On_Reverse_Bit_Order then
414 Error_Msg_N
415 ("multi-byte field specified with "
416 & " non-standard Bit_Order?V?", CC);
417
418 if Bytes_Big_Endian then
419 Error_Msg_N
420 ("\bytes are not reversed "
421 & "(component is big-endian)?V?", CC);
422 else
423 Error_Msg_N
424 ("\bytes are not reversed "
425 & "(component is little-endian)?V?", CC);
426 end if;
427 end if;
428
429 -- Give error message for RM 13.5.1(10) violation
430
431 else
432 Error_Msg_FE
433 ("machine scalar rules not followed for&",
434 First_Bit (CC), Comp);
435
436 Error_Msg_Uint_1 := Lbit;
437 Error_Msg_Uint_2 := Max_Machine_Scalar_Size;
438 Error_Msg_F
439 ("\last bit (^) exceeds maximum machine "
440 & "scalar size (^)",
441 First_Bit (CC));
442
443 if (Lbit + 1) mod SSU /= 0 then
444 Error_Msg_Uint_1 := SSU;
445 Error_Msg_F
446 ("\and is not a multiple of Storage_Unit (^) "
447 & "(RM 13.4.1(10))",
448 First_Bit (CC));
449
450 else
451 Error_Msg_Uint_1 := Fbit;
452 Error_Msg_F
453 ("\and first bit (^) is non-zero "
454 & "(RM 13.4.1(10))",
455 First_Bit (CC));
456 end if;
457 end if;
458
459 -- OK case of machine scalar related component clause,
460 -- For now, just count them.
461
462 else
463 Num_CC := Num_CC + 1;
464 end if;
465 end;
466 end if;
467
468 Next_Component_Or_Discriminant (Comp);
469 end loop;
470
471 -- We need to sort the component clauses on the basis of the
472 -- Position values in the clause, so we can group clauses with
473 -- the same Position. together to determine the relevant machine
474 -- scalar size.
475
476 Sort_CC : declare
477 Comps : array (0 .. Num_CC) of Entity_Id;
478 -- Array to collect component and discriminant entities. The
479 -- data starts at index 1, the 0'th entry is for the sort
480 -- routine.
481
482 function CP_Lt (Op1, Op2 : Natural) return Boolean;
483 -- Compare routine for Sort
484
485 procedure CP_Move (From : Natural; To : Natural);
486 -- Move routine for Sort
487
488 package Sorting is new GNAT.Heap_Sort_G (CP_Move, CP_Lt);
489
490 Start : Natural;
491 Stop : Natural;
492 -- Start and stop positions in the component list of the set of
493 -- components with the same starting position (that constitute
494 -- components in a single machine scalar).
495
496 MaxL : Uint;
497 -- Maximum last bit value of any component in this set
498
499 MSS : Uint;
500 -- Corresponding machine scalar size
501
502 -----------
503 -- CP_Lt --
504 -----------
505
506 function CP_Lt (Op1, Op2 : Natural) return Boolean is
507 begin
508 return Position (Component_Clause (Comps (Op1))) <
509 Position (Component_Clause (Comps (Op2)));
510 end CP_Lt;
511
512 -------------
513 -- CP_Move --
514 -------------
515
516 procedure CP_Move (From : Natural; To : Natural) is
517 begin
518 Comps (To) := Comps (From);
519 end CP_Move;
520
521 -- Start of processing for Sort_CC
522
523 begin
524 -- Collect the machine scalar relevant component clauses
525
526 Num_CC := 0;
527 Comp := First_Component_Or_Discriminant (R);
528 while Present (Comp) loop
529 declare
530 CC : constant Node_Id := Component_Clause (Comp);
531
532 begin
533 -- Collect only component clauses whose last bit is less
534 -- than machine scalar size. Any component clause whose
535 -- last bit exceeds this value does not take part in
536 -- machine scalar layout considerations. The test for
537 -- Error_Posted makes sure we exclude component clauses
538 -- for which we already posted an error.
539
540 if Present (CC)
541 and then not Error_Posted (Last_Bit (CC))
542 and then Static_Integer (Last_Bit (CC)) <
543 Max_Machine_Scalar_Size
544 then
545 Num_CC := Num_CC + 1;
546 Comps (Num_CC) := Comp;
547 end if;
548 end;
549
550 Next_Component_Or_Discriminant (Comp);
551 end loop;
552
553 -- Sort by ascending position number
554
555 Sorting.Sort (Num_CC);
556
557 -- We now have all the components whose size does not exceed
558 -- the max machine scalar value, sorted by starting position.
559 -- In this loop we gather groups of clauses starting at the
560 -- same position, to process them in accordance with AI-133.
561
562 Stop := 0;
563 while Stop < Num_CC loop
564 Start := Stop + 1;
565 Stop := Start;
566 MaxL :=
567 Static_Integer
568 (Last_Bit (Component_Clause (Comps (Start))));
569 while Stop < Num_CC loop
570 if Static_Integer
571 (Position (Component_Clause (Comps (Stop + 1)))) =
572 Static_Integer
573 (Position (Component_Clause (Comps (Stop))))
574 then
575 Stop := Stop + 1;
576 MaxL :=
577 UI_Max
578 (MaxL,
579 Static_Integer
580 (Last_Bit
581 (Component_Clause (Comps (Stop)))));
582 else
583 exit;
584 end if;
585 end loop;
586
587 -- Now we have a group of component clauses from Start to
588 -- Stop whose positions are identical, and MaxL is the
589 -- maximum last bit value of any of these components.
590
591 -- We need to determine the corresponding machine scalar
592 -- size. This loop assumes that machine scalar sizes are
593 -- even, and that each possible machine scalar has twice
594 -- as many bits as the next smaller one.
595
596 MSS := Max_Machine_Scalar_Size;
597 while MSS mod 2 = 0
598 and then (MSS / 2) >= SSU
599 and then (MSS / 2) > MaxL
600 loop
601 MSS := MSS / 2;
602 end loop;
603
604 -- Here is where we fix up the Component_Bit_Offset value
605 -- to account for the reverse bit order. Some examples of
606 -- what needs to be done for the case of a machine scalar
607 -- size of 8 are:
608
609 -- First_Bit .. Last_Bit Component_Bit_Offset
610 -- old new old new
611
612 -- 0 .. 0 7 .. 7 0 7
613 -- 0 .. 1 6 .. 7 0 6
614 -- 0 .. 2 5 .. 7 0 5
615 -- 0 .. 7 0 .. 7 0 4
616
617 -- 1 .. 1 6 .. 6 1 6
618 -- 1 .. 4 3 .. 6 1 3
619 -- 4 .. 7 0 .. 3 4 0
620
621 -- The rule is that the first bit is obtained by subtracting
622 -- the old ending bit from machine scalar size - 1.
623
624 for C in Start .. Stop loop
625 declare
626 Comp : constant Entity_Id := Comps (C);
627 CC : constant Node_Id := Component_Clause (Comp);
628
629 LB : constant Uint := Static_Integer (Last_Bit (CC));
630 NFB : constant Uint := MSS - Uint_1 - LB;
631 NLB : constant Uint := NFB + Esize (Comp) - 1;
632 Pos : constant Uint := Static_Integer (Position (CC));
633
634 begin
635 if Warn_On_Reverse_Bit_Order then
636 Error_Msg_Uint_1 := MSS;
637 Error_Msg_N
638 ("info: reverse bit order in machine " &
639 "scalar of length^?V?", First_Bit (CC));
640 Error_Msg_Uint_1 := NFB;
641 Error_Msg_Uint_2 := NLB;
642
643 if Bytes_Big_Endian then
644 Error_Msg_NE
645 ("\info: big-endian range for "
646 & "component & is ^ .. ^?V?",
647 First_Bit (CC), Comp);
648 else
649 Error_Msg_NE
650 ("\info: little-endian range "
651 & "for component & is ^ .. ^?V?",
652 First_Bit (CC), Comp);
653 end if;
654 end if;
655
656 Set_Component_Bit_Offset (Comp, Pos * SSU + NFB);
657 Set_Normalized_First_Bit (Comp, NFB mod SSU);
658 end;
659 end loop;
660 end loop;
661 end Sort_CC;
662 end;
663 end if;
664 end Adjust_Record_For_Reverse_Bit_Order;
665
666 -------------------------------------
667 -- Alignment_Check_For_Size_Change --
668 -------------------------------------
669
670 procedure Alignment_Check_For_Size_Change (Typ : Entity_Id; Size : Uint) is
671 begin
672 -- If the alignment is known, and not set by a rep clause, and is
673 -- inconsistent with the size being set, then reset it to unknown,
674 -- we assume in this case that the size overrides the inherited
675 -- alignment, and that the alignment must be recomputed.
676
677 if Known_Alignment (Typ)
678 and then not Has_Alignment_Clause (Typ)
679 and then Size mod (Alignment (Typ) * SSU) /= 0
680 then
681 Init_Alignment (Typ);
682 end if;
683 end Alignment_Check_For_Size_Change;
684
685 -------------------------------------
686 -- Analyze_Aspects_At_Freeze_Point --
687 -------------------------------------
688
689 procedure Analyze_Aspects_At_Freeze_Point (E : Entity_Id) is
690 ASN : Node_Id;
691 A_Id : Aspect_Id;
692 Ritem : Node_Id;
693
694 procedure Analyze_Aspect_Default_Value (ASN : Node_Id);
695 -- This routine analyzes an Aspect_Default_[Component_]Value denoted by
696 -- the aspect specification node ASN.
697
698 procedure Inherit_Delayed_Rep_Aspects (ASN : Node_Id);
699 -- As discussed in the spec of Aspects (see Aspect_Delay declaration),
700 -- a derived type can inherit aspects from its parent which have been
701 -- specified at the time of the derivation using an aspect, as in:
702 --
703 -- type A is range 1 .. 10
704 -- with Size => Not_Defined_Yet;
705 -- ..
706 -- type B is new A;
707 -- ..
708 -- Not_Defined_Yet : constant := 64;
709 --
710 -- In this example, the Size of A is considered to be specified prior
711 -- to the derivation, and thus inherited, even though the value is not
712 -- known at the time of derivation. To deal with this, we use two entity
713 -- flags. The flag Has_Derived_Rep_Aspects is set in the parent type (A
714 -- here), and then the flag May_Inherit_Delayed_Rep_Aspects is set in
715 -- the derived type (B here). If this flag is set when the derived type
716 -- is frozen, then this procedure is called to ensure proper inheritance
717 -- of all delayed aspects from the parent type. The derived type is E,
718 -- the argument to Analyze_Aspects_At_Freeze_Point. ASN is the first
719 -- aspect specification node in the Rep_Item chain for the parent type.
720
721 procedure Make_Pragma_From_Boolean_Aspect (ASN : Node_Id);
722 -- Given an aspect specification node ASN whose expression is an
723 -- optional Boolean, this routines creates the corresponding pragma
724 -- at the freezing point.
725
726 ----------------------------------
727 -- Analyze_Aspect_Default_Value --
728 ----------------------------------
729
730 procedure Analyze_Aspect_Default_Value (ASN : Node_Id) is
731 Ent : constant Entity_Id := Entity (ASN);
732 Expr : constant Node_Id := Expression (ASN);
733 Id : constant Node_Id := Identifier (ASN);
734
735 begin
736 Error_Msg_Name_1 := Chars (Id);
737
738 if not Is_Type (Ent) then
739 Error_Msg_N ("aspect% can only apply to a type", Id);
740 return;
741
742 elsif not Is_First_Subtype (Ent) then
743 Error_Msg_N ("aspect% cannot apply to subtype", Id);
744 return;
745
746 elsif A_Id = Aspect_Default_Value
747 and then not Is_Scalar_Type (Ent)
748 then
749 Error_Msg_N ("aspect% can only be applied to scalar type", Id);
750 return;
751
752 elsif A_Id = Aspect_Default_Component_Value then
753 if not Is_Array_Type (Ent) then
754 Error_Msg_N ("aspect% can only be applied to array type", Id);
755 return;
756
757 elsif not Is_Scalar_Type (Component_Type (Ent)) then
758 Error_Msg_N ("aspect% requires scalar components", Id);
759 return;
760 end if;
761 end if;
762
763 Set_Has_Default_Aspect (Base_Type (Ent));
764
765 if Is_Scalar_Type (Ent) then
766 Set_Default_Aspect_Value (Ent, Expr);
767
768 -- Place default value of base type as well, because that is
769 -- the semantics of the aspect. It is convenient to link the
770 -- aspect to both the (possibly anonymous) base type and to
771 -- the given first subtype.
772
773 Set_Default_Aspect_Value (Base_Type (Ent), Expr);
774
775 else
776 Set_Default_Aspect_Component_Value (Ent, Expr);
777 end if;
778 end Analyze_Aspect_Default_Value;
779
780 ---------------------------------
781 -- Inherit_Delayed_Rep_Aspects --
782 ---------------------------------
783
784 procedure Inherit_Delayed_Rep_Aspects (ASN : Node_Id) is
785 P : constant Entity_Id := Entity (ASN);
786 -- Entithy for parent type
787
788 N : Node_Id;
789 -- Item from Rep_Item chain
790
791 A : Aspect_Id;
792
793 begin
794 -- Loop through delayed aspects for the parent type
795
796 N := ASN;
797 while Present (N) loop
798 if Nkind (N) = N_Aspect_Specification then
799 exit when Entity (N) /= P;
800
801 if Is_Delayed_Aspect (N) then
802 A := Get_Aspect_Id (Chars (Identifier (N)));
803
804 -- Process delayed rep aspect. For Boolean attributes it is
805 -- not possible to cancel an attribute once set (the attempt
806 -- to use an aspect with xxx => False is an error) for a
807 -- derived type. So for those cases, we do not have to check
808 -- if a clause has been given for the derived type, since it
809 -- is harmless to set it again if it is already set.
810
811 case A is
812
813 -- Alignment
814
815 when Aspect_Alignment =>
816 if not Has_Alignment_Clause (E) then
817 Set_Alignment (E, Alignment (P));
818 end if;
819
820 -- Atomic
821
822 when Aspect_Atomic =>
823 if Is_Atomic (P) then
824 Set_Is_Atomic (E);
825 end if;
826
827 -- Atomic_Components
828
829 when Aspect_Atomic_Components =>
830 if Has_Atomic_Components (P) then
831 Set_Has_Atomic_Components (Base_Type (E));
832 end if;
833
834 -- Bit_Order
835
836 when Aspect_Bit_Order =>
837 if Is_Record_Type (E)
838 and then No (Get_Attribute_Definition_Clause
839 (E, Attribute_Bit_Order))
840 and then Reverse_Bit_Order (P)
841 then
842 Set_Reverse_Bit_Order (Base_Type (E));
843 end if;
844
845 -- Component_Size
846
847 when Aspect_Component_Size =>
848 if Is_Array_Type (E)
849 and then not Has_Component_Size_Clause (E)
850 then
851 Set_Component_Size
852 (Base_Type (E), Component_Size (P));
853 end if;
854
855 -- Machine_Radix
856
857 when Aspect_Machine_Radix =>
858 if Is_Decimal_Fixed_Point_Type (E)
859 and then not Has_Machine_Radix_Clause (E)
860 then
861 Set_Machine_Radix_10 (E, Machine_Radix_10 (P));
862 end if;
863
864 -- Object_Size (also Size which also sets Object_Size)
865
866 when Aspect_Object_Size | Aspect_Size =>
867 if not Has_Size_Clause (E)
868 and then
869 No (Get_Attribute_Definition_Clause
870 (E, Attribute_Object_Size))
871 then
872 Set_Esize (E, Esize (P));
873 end if;
874
875 -- Pack
876
877 when Aspect_Pack =>
878 if not Is_Packed (E) then
879 Set_Is_Packed (Base_Type (E));
880
881 if Is_Bit_Packed_Array (P) then
882 Set_Is_Bit_Packed_Array (Base_Type (E));
883 Set_Packed_Array_Type (E, Packed_Array_Type (P));
884 end if;
885 end if;
886
887 -- Scalar_Storage_Order
888
889 when Aspect_Scalar_Storage_Order =>
890 if (Is_Record_Type (E) or else Is_Array_Type (E))
891 and then No (Get_Attribute_Definition_Clause
892 (E, Attribute_Scalar_Storage_Order))
893 and then Reverse_Storage_Order (P)
894 then
895 Set_Reverse_Storage_Order (Base_Type (E));
896 end if;
897
898 -- Small
899
900 when Aspect_Small =>
901 if Is_Fixed_Point_Type (E)
902 and then not Has_Small_Clause (E)
903 then
904 Set_Small_Value (E, Small_Value (P));
905 end if;
906
907 -- Storage_Size
908
909 when Aspect_Storage_Size =>
910 if (Is_Access_Type (E) or else Is_Task_Type (E))
911 and then not Has_Storage_Size_Clause (E)
912 then
913 Set_Storage_Size_Variable
914 (Base_Type (E), Storage_Size_Variable (P));
915 end if;
916
917 -- Value_Size
918
919 when Aspect_Value_Size =>
920
921 -- Value_Size is never inherited, it is either set by
922 -- default, or it is explicitly set for the derived
923 -- type. So nothing to do here.
924
925 null;
926
927 -- Volatile
928
929 when Aspect_Volatile =>
930 if Is_Volatile (P) then
931 Set_Is_Volatile (E);
932 end if;
933
934 -- Volatile_Components
935
936 when Aspect_Volatile_Components =>
937 if Has_Volatile_Components (P) then
938 Set_Has_Volatile_Components (Base_Type (E));
939 end if;
940
941 -- That should be all the Rep Aspects
942
943 when others =>
944 pragma Assert (Aspect_Delay (A_Id) /= Rep_Aspect);
945 null;
946
947 end case;
948 end if;
949 end if;
950
951 N := Next_Rep_Item (N);
952 end loop;
953 end Inherit_Delayed_Rep_Aspects;
954
955 -------------------------------------
956 -- Make_Pragma_From_Boolean_Aspect --
957 -------------------------------------
958
959 procedure Make_Pragma_From_Boolean_Aspect (ASN : Node_Id) is
960 Ident : constant Node_Id := Identifier (ASN);
961 A_Name : constant Name_Id := Chars (Ident);
962 A_Id : constant Aspect_Id := Get_Aspect_Id (A_Name);
963 Ent : constant Entity_Id := Entity (ASN);
964 Expr : constant Node_Id := Expression (ASN);
965 Loc : constant Source_Ptr := Sloc (ASN);
966
967 Prag : Node_Id;
968
969 procedure Check_False_Aspect_For_Derived_Type;
970 -- This procedure checks for the case of a false aspect for a derived
971 -- type, which improperly tries to cancel an aspect inherited from
972 -- the parent.
973
974 -----------------------------------------
975 -- Check_False_Aspect_For_Derived_Type --
976 -----------------------------------------
977
978 procedure Check_False_Aspect_For_Derived_Type is
979 Par : Node_Id;
980
981 begin
982 -- We are only checking derived types
983
984 if not Is_Derived_Type (E) then
985 return;
986 end if;
987
988 Par := Nearest_Ancestor (E);
989
990 case A_Id is
991 when Aspect_Atomic | Aspect_Shared =>
992 if not Is_Atomic (Par) then
993 return;
994 end if;
995
996 when Aspect_Atomic_Components =>
997 if not Has_Atomic_Components (Par) then
998 return;
999 end if;
1000
1001 when Aspect_Discard_Names =>
1002 if not Discard_Names (Par) then
1003 return;
1004 end if;
1005
1006 when Aspect_Pack =>
1007 if not Is_Packed (Par) then
1008 return;
1009 end if;
1010
1011 when Aspect_Unchecked_Union =>
1012 if not Is_Unchecked_Union (Par) then
1013 return;
1014 end if;
1015
1016 when Aspect_Volatile =>
1017 if not Is_Volatile (Par) then
1018 return;
1019 end if;
1020
1021 when Aspect_Volatile_Components =>
1022 if not Has_Volatile_Components (Par) then
1023 return;
1024 end if;
1025
1026 when others =>
1027 return;
1028 end case;
1029
1030 -- Fall through means we are canceling an inherited aspect
1031
1032 Error_Msg_Name_1 := A_Name;
1033 Error_Msg_NE
1034 ("derived type& inherits aspect%, cannot cancel", Expr, E);
1035
1036 end Check_False_Aspect_For_Derived_Type;
1037
1038 -- Start of processing for Make_Pragma_From_Boolean_Aspect
1039
1040 begin
1041 -- Note that we know Expr is present, because for a missing Expr
1042 -- argument, we knew it was True and did not need to delay the
1043 -- evaluation to the freeze point.
1044
1045 if Is_False (Static_Boolean (Expr)) then
1046 Check_False_Aspect_For_Derived_Type;
1047
1048 else
1049 Prag :=
1050 Make_Pragma (Loc,
1051 Pragma_Argument_Associations => New_List (
1052 Make_Pragma_Argument_Association (Sloc (Ident),
1053 Expression => New_Occurrence_Of (Ent, Sloc (Ident)))),
1054
1055 Pragma_Identifier =>
1056 Make_Identifier (Sloc (Ident), Chars (Ident)));
1057
1058 Set_From_Aspect_Specification (Prag, True);
1059 Set_Corresponding_Aspect (Prag, ASN);
1060 Set_Aspect_Rep_Item (ASN, Prag);
1061 Set_Is_Delayed_Aspect (Prag);
1062 Set_Parent (Prag, ASN);
1063 end if;
1064 end Make_Pragma_From_Boolean_Aspect;
1065
1066 -- Start of processing for Analyze_Aspects_At_Freeze_Point
1067
1068 begin
1069 -- Must be visible in current scope
1070
1071 if not Scope_Within_Or_Same (Current_Scope, Scope (E)) then
1072 return;
1073 end if;
1074
1075 -- Look for aspect specification entries for this entity
1076
1077 ASN := First_Rep_Item (E);
1078 while Present (ASN) loop
1079 if Nkind (ASN) = N_Aspect_Specification then
1080 exit when Entity (ASN) /= E;
1081
1082 if Is_Delayed_Aspect (ASN) then
1083 A_Id := Get_Aspect_Id (ASN);
1084
1085 case A_Id is
1086
1087 -- For aspects whose expression is an optional Boolean, make
1088 -- the corresponding pragma at the freezing point.
1089
1090 when Boolean_Aspects |
1091 Library_Unit_Aspects =>
1092 Make_Pragma_From_Boolean_Aspect (ASN);
1093
1094 -- Special handling for aspects that don't correspond to
1095 -- pragmas/attributes.
1096
1097 when Aspect_Default_Value |
1098 Aspect_Default_Component_Value =>
1099 Analyze_Aspect_Default_Value (ASN);
1100
1101 -- Ditto for iterator aspects, because the corresponding
1102 -- attributes may not have been analyzed yet.
1103
1104 when Aspect_Constant_Indexing |
1105 Aspect_Variable_Indexing |
1106 Aspect_Default_Iterator |
1107 Aspect_Iterator_Element =>
1108 Analyze (Expression (ASN));
1109
1110 when others =>
1111 null;
1112 end case;
1113
1114 Ritem := Aspect_Rep_Item (ASN);
1115
1116 if Present (Ritem) then
1117 Analyze (Ritem);
1118 end if;
1119 end if;
1120 end if;
1121
1122 Next_Rep_Item (ASN);
1123 end loop;
1124
1125 -- This is where we inherit delayed rep aspects from our parent. Note
1126 -- that if we fell out of the above loop with ASN non-empty, it means
1127 -- we hit an aspect for an entity other than E, and it must be the
1128 -- type from which we were derived.
1129
1130 if May_Inherit_Delayed_Rep_Aspects (E) then
1131 Inherit_Delayed_Rep_Aspects (ASN);
1132 end if;
1133 end Analyze_Aspects_At_Freeze_Point;
1134
1135 -----------------------------------
1136 -- Analyze_Aspect_Specifications --
1137 -----------------------------------
1138
1139 procedure Analyze_Aspect_Specifications (N : Node_Id; E : Entity_Id) is
1140 procedure Decorate_Delayed_Aspect_And_Pragma
1141 (Asp : Node_Id;
1142 Prag : Node_Id);
1143 -- Establish the linkages between a delayed aspect and its corresponding
1144 -- pragma. Set all delay-related flags on both constructs.
1145
1146 procedure Insert_Delayed_Pragma (Prag : Node_Id);
1147 -- Insert a postcondition-like pragma into the tree depending on the
1148 -- context. Prag must denote one of the following: Pre, Post, Depends,
1149 -- Global or Contract_Cases.
1150
1151 ----------------------------------------
1152 -- Decorate_Delayed_Aspect_And_Pragma --
1153 ----------------------------------------
1154
1155 procedure Decorate_Delayed_Aspect_And_Pragma
1156 (Asp : Node_Id;
1157 Prag : Node_Id)
1158 is
1159 begin
1160 Set_Aspect_Rep_Item (Asp, Prag);
1161 Set_Corresponding_Aspect (Prag, Asp);
1162 Set_From_Aspect_Specification (Prag);
1163 Set_Is_Delayed_Aspect (Prag);
1164 Set_Is_Delayed_Aspect (Asp);
1165 Set_Parent (Prag, Asp);
1166 end Decorate_Delayed_Aspect_And_Pragma;
1167
1168 ---------------------------
1169 -- Insert_Delayed_Pragma --
1170 ---------------------------
1171
1172 procedure Insert_Delayed_Pragma (Prag : Node_Id) is
1173 Aux : Node_Id;
1174
1175 begin
1176 -- When the context is a library unit, the pragma is added to the
1177 -- Pragmas_After list.
1178
1179 if Nkind (Parent (N)) = N_Compilation_Unit then
1180 Aux := Aux_Decls_Node (Parent (N));
1181
1182 if No (Pragmas_After (Aux)) then
1183 Set_Pragmas_After (Aux, New_List);
1184 end if;
1185
1186 Prepend (Prag, Pragmas_After (Aux));
1187
1188 -- Pragmas associated with subprogram bodies are inserted in the
1189 -- declarative part.
1190
1191 elsif Nkind (N) = N_Subprogram_Body then
1192 if No (Declarations (N)) then
1193 Set_Declarations (N, New_List (Prag));
1194 else
1195 declare
1196 D : Node_Id;
1197 begin
1198
1199 -- There may be several aspects associated with the body;
1200 -- preserve the ordering of the corresponding pragmas.
1201
1202 D := First (Declarations (N));
1203 while Present (D) loop
1204 exit when Nkind (D) /= N_Pragma
1205 or else not From_Aspect_Specification (D);
1206 Next (D);
1207 end loop;
1208
1209 if No (D) then
1210 Append (Prag, Declarations (N));
1211 else
1212 Insert_Before (D, Prag);
1213 end if;
1214 end;
1215 end if;
1216
1217 -- Default
1218
1219 else
1220 Insert_After (N, Prag);
1221
1222 -- Analyze the pragma before analyzing the proper body of a stub.
1223 -- This ensures that the pragma will appear on the proper contract
1224 -- list (see N_Contract).
1225
1226 if Nkind (N) = N_Subprogram_Body_Stub then
1227 Analyze (Prag);
1228 end if;
1229 end if;
1230 end Insert_Delayed_Pragma;
1231
1232 -- Local variables
1233
1234 Aspect : Node_Id;
1235 Aitem : Node_Id;
1236 Ent : Node_Id;
1237
1238 L : constant List_Id := Aspect_Specifications (N);
1239
1240 Ins_Node : Node_Id := N;
1241 -- Insert pragmas/attribute definition clause after this node when no
1242 -- delayed analysis is required.
1243
1244 -- Start of processing for Analyze_Aspect_Specifications
1245
1246 -- The general processing involves building an attribute definition
1247 -- clause or a pragma node that corresponds to the aspect. Then in order
1248 -- to delay the evaluation of this aspect to the freeze point, we attach
1249 -- the corresponding pragma/attribute definition clause to the aspect
1250 -- specification node, which is then placed in the Rep Item chain. In
1251 -- this case we mark the entity by setting the flag Has_Delayed_Aspects
1252 -- and we evaluate the rep item at the freeze point. When the aspect
1253 -- doesn't have a corresponding pragma/attribute definition clause, then
1254 -- its analysis is simply delayed at the freeze point.
1255
1256 -- Some special cases don't require delay analysis, thus the aspect is
1257 -- analyzed right now.
1258
1259 -- Note that there is a special handling for Pre, Post, Test_Case,
1260 -- Contract_Cases aspects. In these cases, we do not have to worry
1261 -- about delay issues, since the pragmas themselves deal with delay
1262 -- of visibility for the expression analysis. Thus, we just insert
1263 -- the pragma after the node N.
1264
1265 begin
1266 pragma Assert (Present (L));
1267
1268 -- Loop through aspects
1269
1270 Aspect := First (L);
1271 Aspect_Loop : while Present (Aspect) loop
1272 Analyze_One_Aspect : declare
1273 Expr : constant Node_Id := Expression (Aspect);
1274 Id : constant Node_Id := Identifier (Aspect);
1275 Loc : constant Source_Ptr := Sloc (Aspect);
1276 Nam : constant Name_Id := Chars (Id);
1277 A_Id : constant Aspect_Id := Get_Aspect_Id (Nam);
1278 Anod : Node_Id;
1279
1280 Delay_Required : Boolean;
1281 -- Set False if delay is not required
1282
1283 Eloc : Source_Ptr := No_Location;
1284 -- Source location of expression, modified when we split PPC's. It
1285 -- is set below when Expr is present.
1286
1287 procedure Analyze_Aspect_External_Or_Link_Name;
1288 -- Perform analysis of the External_Name or Link_Name aspects
1289
1290 procedure Analyze_Aspect_Implicit_Dereference;
1291 -- Perform analysis of the Implicit_Dereference aspects
1292
1293 procedure Make_Aitem_Pragma
1294 (Pragma_Argument_Associations : List_Id;
1295 Pragma_Name : Name_Id);
1296 -- This is a wrapper for Make_Pragma used for converting aspects
1297 -- to pragmas. It takes care of Sloc (set from Loc) and building
1298 -- the pragma identifier from the given name. In addition the
1299 -- flags Class_Present and Split_PPC are set from the aspect
1300 -- node, as well as Is_Ignored. This routine also sets the
1301 -- From_Aspect_Specification in the resulting pragma node to
1302 -- True, and sets Corresponding_Aspect to point to the aspect.
1303 -- The resulting pragma is assigned to Aitem.
1304
1305 ------------------------------------------
1306 -- Analyze_Aspect_External_Or_Link_Name --
1307 ------------------------------------------
1308
1309 procedure Analyze_Aspect_External_Or_Link_Name is
1310 begin
1311 -- Verify that there is an Import/Export aspect defined for the
1312 -- entity. The processing of that aspect in turn checks that
1313 -- there is a Convention aspect declared. The pragma is
1314 -- constructed when processing the Convention aspect.
1315
1316 declare
1317 A : Node_Id;
1318
1319 begin
1320 A := First (L);
1321 while Present (A) loop
1322 exit when Nam_In (Chars (Identifier (A)), Name_Export,
1323 Name_Import);
1324 Next (A);
1325 end loop;
1326
1327 if No (A) then
1328 Error_Msg_N
1329 ("missing Import/Export for Link/External name",
1330 Aspect);
1331 end if;
1332 end;
1333 end Analyze_Aspect_External_Or_Link_Name;
1334
1335 -----------------------------------------
1336 -- Analyze_Aspect_Implicit_Dereference --
1337 -----------------------------------------
1338
1339 procedure Analyze_Aspect_Implicit_Dereference is
1340 begin
1341 if not Is_Type (E) or else not Has_Discriminants (E) then
1342 Error_Msg_N
1343 ("aspect must apply to a type with discriminants", N);
1344
1345 else
1346 declare
1347 Disc : Entity_Id;
1348
1349 begin
1350 Disc := First_Discriminant (E);
1351 while Present (Disc) loop
1352 if Chars (Expr) = Chars (Disc)
1353 and then Ekind (Etype (Disc)) =
1354 E_Anonymous_Access_Type
1355 then
1356 Set_Has_Implicit_Dereference (E);
1357 Set_Has_Implicit_Dereference (Disc);
1358 return;
1359 end if;
1360
1361 Next_Discriminant (Disc);
1362 end loop;
1363
1364 -- Error if no proper access discriminant.
1365
1366 Error_Msg_NE
1367 ("not an access discriminant of&", Expr, E);
1368 end;
1369 end if;
1370 end Analyze_Aspect_Implicit_Dereference;
1371
1372 -----------------------
1373 -- Make_Aitem_Pragma --
1374 -----------------------
1375
1376 procedure Make_Aitem_Pragma
1377 (Pragma_Argument_Associations : List_Id;
1378 Pragma_Name : Name_Id)
1379 is
1380 Args : List_Id := Pragma_Argument_Associations;
1381
1382 begin
1383 -- We should never get here if aspect was disabled
1384
1385 pragma Assert (not Is_Disabled (Aspect));
1386
1387 -- Certain aspects allow for an optional name or expression. Do
1388 -- not generate a pragma with empty argument association list.
1389
1390 if No (Args) or else No (Expression (First (Args))) then
1391 Args := No_List;
1392 end if;
1393
1394 -- Build the pragma
1395
1396 Aitem :=
1397 Make_Pragma (Loc,
1398 Pragma_Argument_Associations => Args,
1399 Pragma_Identifier =>
1400 Make_Identifier (Sloc (Id), Pragma_Name),
1401 Class_Present => Class_Present (Aspect),
1402 Split_PPC => Split_PPC (Aspect));
1403
1404 -- Set additional semantic fields
1405
1406 if Is_Ignored (Aspect) then
1407 Set_Is_Ignored (Aitem);
1408 elsif Is_Checked (Aspect) then
1409 Set_Is_Checked (Aitem);
1410 end if;
1411
1412 Set_Corresponding_Aspect (Aitem, Aspect);
1413 Set_From_Aspect_Specification (Aitem, True);
1414 end Make_Aitem_Pragma;
1415
1416 -- Start of processing for Analyze_One_Aspect
1417
1418 begin
1419 -- Skip aspect if already analyzed (not clear if this is needed)
1420
1421 if Analyzed (Aspect) then
1422 goto Continue;
1423 end if;
1424
1425 -- Skip looking at aspect if it is totally disabled. Just mark
1426 -- it as such for later reference in the tree. This also sets
1427 -- the Is_Ignored and Is_Checked flags appropriately.
1428
1429 Check_Applicable_Policy (Aspect);
1430
1431 if Is_Disabled (Aspect) then
1432 goto Continue;
1433 end if;
1434
1435 -- Set the source location of expression, used in the case of
1436 -- a failed precondition/postcondition or invariant. Note that
1437 -- the source location of the expression is not usually the best
1438 -- choice here. For example, it gets located on the last AND
1439 -- keyword in a chain of boolean expressiond AND'ed together.
1440 -- It is best to put the message on the first character of the
1441 -- assertion, which is the effect of the First_Node call here.
1442
1443 if Present (Expr) then
1444 Eloc := Sloc (First_Node (Expr));
1445 end if;
1446
1447 -- Check restriction No_Implementation_Aspect_Specifications
1448
1449 if Implementation_Defined_Aspect (A_Id) then
1450 Check_Restriction
1451 (No_Implementation_Aspect_Specifications, Aspect);
1452 end if;
1453
1454 -- Check restriction No_Specification_Of_Aspect
1455
1456 Check_Restriction_No_Specification_Of_Aspect (Aspect);
1457
1458 -- Analyze this aspect (actual analysis is delayed till later)
1459
1460 Set_Analyzed (Aspect);
1461 Set_Entity (Aspect, E);
1462 Ent := New_Occurrence_Of (E, Sloc (Id));
1463
1464 -- Check for duplicate aspect. Note that the Comes_From_Source
1465 -- test allows duplicate Pre/Post's that we generate internally
1466 -- to escape being flagged here.
1467
1468 if No_Duplicates_Allowed (A_Id) then
1469 Anod := First (L);
1470 while Anod /= Aspect loop
1471 if Comes_From_Source (Aspect)
1472 and then Same_Aspect (A_Id, Get_Aspect_Id (Anod))
1473 then
1474 Error_Msg_Name_1 := Nam;
1475 Error_Msg_Sloc := Sloc (Anod);
1476
1477 -- Case of same aspect specified twice
1478
1479 if Class_Present (Anod) = Class_Present (Aspect) then
1480 if not Class_Present (Anod) then
1481 Error_Msg_NE
1482 ("aspect% for & previously given#",
1483 Id, E);
1484 else
1485 Error_Msg_NE
1486 ("aspect `%''Class` for & previously given#",
1487 Id, E);
1488 end if;
1489 end if;
1490 end if;
1491
1492 Next (Anod);
1493 end loop;
1494 end if;
1495
1496 -- Check some general restrictions on language defined aspects
1497
1498 if not Implementation_Defined_Aspect (A_Id) then
1499 Error_Msg_Name_1 := Nam;
1500
1501 -- Not allowed for renaming declarations
1502
1503 if Nkind (N) in N_Renaming_Declaration then
1504 Error_Msg_N
1505 ("aspect % not allowed for renaming declaration",
1506 Aspect);
1507 end if;
1508
1509 -- Not allowed for formal type declarations
1510
1511 if Nkind (N) = N_Formal_Type_Declaration then
1512 Error_Msg_N
1513 ("aspect % not allowed for formal type declaration",
1514 Aspect);
1515 end if;
1516 end if;
1517
1518 -- Copy expression for later processing by the procedures
1519 -- Check_Aspect_At_[Freeze_Point | End_Of_Declarations]
1520
1521 Set_Entity (Id, New_Copy_Tree (Expr));
1522
1523 -- Set Delay_Required as appropriate to aspect
1524
1525 case Aspect_Delay (A_Id) is
1526 when Always_Delay =>
1527 Delay_Required := True;
1528
1529 when Never_Delay =>
1530 Delay_Required := False;
1531
1532 when Rep_Aspect =>
1533
1534 -- If expression has the form of an integer literal, then
1535 -- do not delay, since we know the value cannot change.
1536 -- This optimization catches most rep clause cases.
1537
1538 if (Present (Expr) and then Nkind (Expr) = N_Integer_Literal)
1539 or else (A_Id in Boolean_Aspects and then No (Expr))
1540 then
1541 Delay_Required := False;
1542 else
1543 Delay_Required := True;
1544 Set_Has_Delayed_Rep_Aspects (E);
1545 end if;
1546 end case;
1547
1548 -- Processing based on specific aspect
1549
1550 case A_Id is
1551
1552 -- No_Aspect should be impossible
1553
1554 when No_Aspect =>
1555 raise Program_Error;
1556
1557 -- Case 1: Aspects corresponding to attribute definition
1558 -- clauses.
1559
1560 when Aspect_Address |
1561 Aspect_Alignment |
1562 Aspect_Bit_Order |
1563 Aspect_Component_Size |
1564 Aspect_Constant_Indexing |
1565 Aspect_Default_Iterator |
1566 Aspect_Dispatching_Domain |
1567 Aspect_External_Tag |
1568 Aspect_Input |
1569 Aspect_Iterator_Element |
1570 Aspect_Machine_Radix |
1571 Aspect_Object_Size |
1572 Aspect_Output |
1573 Aspect_Read |
1574 Aspect_Scalar_Storage_Order |
1575 Aspect_Size |
1576 Aspect_Small |
1577 Aspect_Simple_Storage_Pool |
1578 Aspect_Storage_Pool |
1579 Aspect_Stream_Size |
1580 Aspect_Value_Size |
1581 Aspect_Variable_Indexing |
1582 Aspect_Write =>
1583
1584 -- Indexing aspects apply only to tagged type
1585
1586 if (A_Id = Aspect_Constant_Indexing
1587 or else
1588 A_Id = Aspect_Variable_Indexing)
1589 and then not (Is_Type (E)
1590 and then Is_Tagged_Type (E))
1591 then
1592 Error_Msg_N ("indexing applies to a tagged type", N);
1593 goto Continue;
1594 end if;
1595
1596 -- For case of address aspect, we don't consider that we
1597 -- know the entity is never set in the source, since it is
1598 -- is likely aliasing is occurring.
1599
1600 -- Note: one might think that the analysis of the resulting
1601 -- attribute definition clause would take care of that, but
1602 -- that's not the case since it won't be from source.
1603
1604 if A_Id = Aspect_Address then
1605 Set_Never_Set_In_Source (E, False);
1606 end if;
1607
1608 -- Construct the attribute definition clause
1609
1610 Aitem :=
1611 Make_Attribute_Definition_Clause (Loc,
1612 Name => Ent,
1613 Chars => Chars (Id),
1614 Expression => Relocate_Node (Expr));
1615
1616 -- If the address is specified, then we treat the entity as
1617 -- referenced, to avoid spurious warnings. This is analogous
1618 -- to what is done with an attribute definition clause, but
1619 -- here we don't want to generate a reference because this
1620 -- is the point of definition of the entity.
1621
1622 if A_Id = Aspect_Address then
1623 Set_Referenced (E);
1624 end if;
1625
1626 -- Case 2: Aspects corresponding to pragmas
1627
1628 -- Case 2a: Aspects corresponding to pragmas with two
1629 -- arguments, where the first argument is a local name
1630 -- referring to the entity, and the second argument is the
1631 -- aspect definition expression.
1632
1633 -- Suppress/Unsuppress
1634
1635 when Aspect_Suppress |
1636 Aspect_Unsuppress =>
1637
1638 Make_Aitem_Pragma
1639 (Pragma_Argument_Associations => New_List (
1640 Make_Pragma_Argument_Association (Loc,
1641 Expression => New_Occurrence_Of (E, Loc)),
1642 Make_Pragma_Argument_Association (Sloc (Expr),
1643 Expression => Relocate_Node (Expr))),
1644 Pragma_Name => Chars (Id));
1645
1646 -- Synchronization
1647
1648 -- Corresponds to pragma Implemented, construct the pragma
1649
1650 when Aspect_Synchronization =>
1651
1652 Make_Aitem_Pragma
1653 (Pragma_Argument_Associations => New_List (
1654 Make_Pragma_Argument_Association (Loc,
1655 Expression => New_Occurrence_Of (E, Loc)),
1656 Make_Pragma_Argument_Association (Sloc (Expr),
1657 Expression => Relocate_Node (Expr))),
1658 Pragma_Name => Name_Implemented);
1659
1660 -- Attach Handler
1661
1662 when Aspect_Attach_Handler =>
1663 Make_Aitem_Pragma
1664 (Pragma_Argument_Associations => New_List (
1665 Make_Pragma_Argument_Association (Sloc (Ent),
1666 Expression => Ent),
1667 Make_Pragma_Argument_Association (Sloc (Expr),
1668 Expression => Relocate_Node (Expr))),
1669 Pragma_Name => Name_Attach_Handler);
1670
1671 -- Dynamic_Predicate, Predicate, Static_Predicate
1672
1673 when Aspect_Dynamic_Predicate |
1674 Aspect_Predicate |
1675 Aspect_Static_Predicate =>
1676
1677 -- Construct the pragma (always a pragma Predicate, with
1678 -- flags recording whether it is static/dynamic). We also
1679 -- set flags recording this in the type itself.
1680
1681 Make_Aitem_Pragma
1682 (Pragma_Argument_Associations => New_List (
1683 Make_Pragma_Argument_Association (Sloc (Ent),
1684 Expression => Ent),
1685 Make_Pragma_Argument_Association (Sloc (Expr),
1686 Expression => Relocate_Node (Expr))),
1687 Pragma_Name => Name_Predicate);
1688
1689 -- Mark type has predicates, and remember what kind of
1690 -- aspect lead to this predicate (we need this to access
1691 -- the right set of check policies later on).
1692
1693 Set_Has_Predicates (E);
1694
1695 if A_Id = Aspect_Dynamic_Predicate then
1696 Set_Has_Dynamic_Predicate_Aspect (E);
1697 elsif A_Id = Aspect_Static_Predicate then
1698 Set_Has_Static_Predicate_Aspect (E);
1699 end if;
1700
1701 -- If the type is private, indicate that its completion
1702 -- has a freeze node, because that is the one that will be
1703 -- visible at freeze time.
1704
1705 if Is_Private_Type (E) and then Present (Full_View (E)) then
1706 Set_Has_Predicates (Full_View (E));
1707
1708 if A_Id = Aspect_Dynamic_Predicate then
1709 Set_Has_Dynamic_Predicate_Aspect (Full_View (E));
1710 elsif A_Id = Aspect_Static_Predicate then
1711 Set_Has_Static_Predicate_Aspect (Full_View (E));
1712 end if;
1713
1714 Set_Has_Delayed_Aspects (Full_View (E));
1715 Ensure_Freeze_Node (Full_View (E));
1716 end if;
1717
1718 -- Case 2b: Aspects corresponding to pragmas with two
1719 -- arguments, where the second argument is a local name
1720 -- referring to the entity, and the first argument is the
1721 -- aspect definition expression.
1722
1723 -- Convention
1724
1725 when Aspect_Convention =>
1726
1727 -- The aspect may be part of the specification of an import
1728 -- or export pragma. Scan the aspect list to gather the
1729 -- other components, if any. The name of the generated
1730 -- pragma is one of Convention/Import/Export.
1731
1732 declare
1733 P_Name : Name_Id;
1734 A_Name : Name_Id;
1735 A : Node_Id;
1736 Arg_List : List_Id;
1737 Found : Boolean;
1738 L_Assoc : Node_Id;
1739 E_Assoc : Node_Id;
1740
1741 begin
1742 P_Name := Chars (Id);
1743 Found := False;
1744 Arg_List := New_List;
1745 L_Assoc := Empty;
1746 E_Assoc := Empty;
1747
1748 A := First (L);
1749 while Present (A) loop
1750 A_Name := Chars (Identifier (A));
1751
1752 if Nam_In (A_Name, Name_Import, Name_Export) then
1753 if Found then
1754 Error_Msg_N ("conflicting", A);
1755 else
1756 Found := True;
1757 end if;
1758
1759 P_Name := A_Name;
1760
1761 elsif A_Name = Name_Link_Name then
1762 L_Assoc :=
1763 Make_Pragma_Argument_Association (Loc,
1764 Chars => A_Name,
1765 Expression => Relocate_Node (Expression (A)));
1766
1767 elsif A_Name = Name_External_Name then
1768 E_Assoc :=
1769 Make_Pragma_Argument_Association (Loc,
1770 Chars => A_Name,
1771 Expression => Relocate_Node (Expression (A)));
1772 end if;
1773
1774 Next (A);
1775 end loop;
1776
1777 Arg_List := New_List (
1778 Make_Pragma_Argument_Association (Sloc (Expr),
1779 Expression => Relocate_Node (Expr)),
1780 Make_Pragma_Argument_Association (Sloc (Ent),
1781 Expression => Ent));
1782
1783 if Present (L_Assoc) then
1784 Append_To (Arg_List, L_Assoc);
1785 end if;
1786
1787 if Present (E_Assoc) then
1788 Append_To (Arg_List, E_Assoc);
1789 end if;
1790
1791 Make_Aitem_Pragma
1792 (Pragma_Argument_Associations => Arg_List,
1793 Pragma_Name => P_Name);
1794 end;
1795
1796 -- CPU, Interrupt_Priority, Priority
1797
1798 -- These three aspects can be specified for a subprogram body,
1799 -- in which case we generate pragmas for them and insert them
1800 -- ahead of local declarations, rather than after the body.
1801
1802 when Aspect_CPU |
1803 Aspect_Interrupt_Priority |
1804 Aspect_Priority =>
1805
1806 if Nkind (N) = N_Subprogram_Body then
1807 Make_Aitem_Pragma
1808 (Pragma_Argument_Associations => New_List (
1809 Make_Pragma_Argument_Association (Sloc (Expr),
1810 Expression => Relocate_Node (Expr))),
1811 Pragma_Name => Chars (Id));
1812
1813 else
1814 Aitem :=
1815 Make_Attribute_Definition_Clause (Loc,
1816 Name => Ent,
1817 Chars => Chars (Id),
1818 Expression => Relocate_Node (Expr));
1819 end if;
1820
1821 -- Warnings
1822
1823 when Aspect_Warnings =>
1824 Make_Aitem_Pragma
1825 (Pragma_Argument_Associations => New_List (
1826 Make_Pragma_Argument_Association (Sloc (Expr),
1827 Expression => Relocate_Node (Expr)),
1828 Make_Pragma_Argument_Association (Loc,
1829 Expression => New_Occurrence_Of (E, Loc))),
1830 Pragma_Name => Chars (Id));
1831
1832 -- Case 2c: Aspects corresponding to pragmas with three
1833 -- arguments.
1834
1835 -- Invariant aspects have a first argument that references the
1836 -- entity, a second argument that is the expression and a third
1837 -- argument that is an appropriate message.
1838
1839 -- Invariant, Type_Invariant
1840
1841 when Aspect_Invariant |
1842 Aspect_Type_Invariant =>
1843
1844 -- Analysis of the pragma will verify placement legality:
1845 -- an invariant must apply to a private type, or appear in
1846 -- the private part of a spec and apply to a completion.
1847
1848 Make_Aitem_Pragma
1849 (Pragma_Argument_Associations => New_List (
1850 Make_Pragma_Argument_Association (Sloc (Ent),
1851 Expression => Ent),
1852 Make_Pragma_Argument_Association (Sloc (Expr),
1853 Expression => Relocate_Node (Expr))),
1854 Pragma_Name => Name_Invariant);
1855
1856 -- Add message unless exception messages are suppressed
1857
1858 if not Opt.Exception_Locations_Suppressed then
1859 Append_To (Pragma_Argument_Associations (Aitem),
1860 Make_Pragma_Argument_Association (Eloc,
1861 Chars => Name_Message,
1862 Expression =>
1863 Make_String_Literal (Eloc,
1864 Strval => "failed invariant from "
1865 & Build_Location_String (Eloc))));
1866 end if;
1867
1868 -- For Invariant case, insert immediately after the entity
1869 -- declaration. We do not have to worry about delay issues
1870 -- since the pragma processing takes care of this.
1871
1872 Delay_Required := False;
1873
1874 -- Case 2d : Aspects that correspond to a pragma with one
1875 -- argument.
1876
1877 -- Abstract_State
1878
1879 when Aspect_Abstract_State =>
1880 Make_Aitem_Pragma
1881 (Pragma_Argument_Associations => New_List (
1882 Make_Pragma_Argument_Association (Loc,
1883 Expression => Relocate_Node (Expr))),
1884 Pragma_Name => Name_Abstract_State);
1885
1886 -- Depends
1887
1888 -- Aspect Depends must be delayed because it mentions names
1889 -- of inputs and output that are classified by aspect Global.
1890 -- The aspect and pragma are treated the same way as a post
1891 -- condition.
1892
1893 when Aspect_Depends =>
1894 Make_Aitem_Pragma
1895 (Pragma_Argument_Associations => New_List (
1896 Make_Pragma_Argument_Association (Loc,
1897 Expression => Relocate_Node (Expr))),
1898 Pragma_Name => Name_Depends);
1899
1900 Decorate_Delayed_Aspect_And_Pragma (Aspect, Aitem);
1901 Insert_Delayed_Pragma (Aitem);
1902 goto Continue;
1903
1904 -- Global
1905
1906 -- Aspect Global must be delayed because it can mention names
1907 -- and benefit from the forward visibility rules applicable to
1908 -- aspects of subprograms. The aspect and pragma are treated
1909 -- the same way as a post condition.
1910
1911 when Aspect_Global =>
1912 Make_Aitem_Pragma
1913 (Pragma_Argument_Associations => New_List (
1914 Make_Pragma_Argument_Association (Loc,
1915 Expression => Relocate_Node (Expr))),
1916 Pragma_Name => Name_Global);
1917
1918 Decorate_Delayed_Aspect_And_Pragma (Aspect, Aitem);
1919 Insert_Delayed_Pragma (Aitem);
1920 goto Continue;
1921
1922 -- SPARK_Mode
1923
1924 when Aspect_SPARK_Mode =>
1925 Make_Aitem_Pragma
1926 (Pragma_Argument_Associations => New_List (
1927 Make_Pragma_Argument_Association (Loc,
1928 Expression => Relocate_Node (Expr))),
1929 Pragma_Name => Name_SPARK_Mode);
1930
1931 -- Refined_Depends
1932
1933 -- ??? To be implemented
1934
1935 when Aspect_Refined_Depends =>
1936 null;
1937
1938 -- Refined_Global
1939
1940 -- ??? To be implemented
1941
1942 when Aspect_Refined_Global =>
1943 null;
1944
1945 -- Refined_Post
1946
1947 when Aspect_Refined_Post =>
1948 Make_Aitem_Pragma
1949 (Pragma_Argument_Associations => New_List (
1950 Make_Pragma_Argument_Association (Loc,
1951 Expression => Relocate_Node (Expr))),
1952 Pragma_Name => Name_Refined_Post);
1953
1954 -- Refined_Pre
1955
1956 when Aspect_Refined_Pre =>
1957 Make_Aitem_Pragma
1958 (Pragma_Argument_Associations => New_List (
1959 Make_Pragma_Argument_Association (Loc,
1960 Expression => Relocate_Node (Expr))),
1961 Pragma_Name => Name_Refined_Pre);
1962
1963 -- Relative_Deadline
1964
1965 when Aspect_Relative_Deadline =>
1966 Make_Aitem_Pragma
1967 (Pragma_Argument_Associations => New_List (
1968 Make_Pragma_Argument_Association (Loc,
1969 Expression => Relocate_Node (Expr))),
1970 Pragma_Name => Name_Relative_Deadline);
1971
1972 -- If the aspect applies to a task, the corresponding pragma
1973 -- must appear within its declarations, not after.
1974
1975 if Nkind (N) = N_Task_Type_Declaration then
1976 declare
1977 Def : Node_Id;
1978 V : List_Id;
1979
1980 begin
1981 if No (Task_Definition (N)) then
1982 Set_Task_Definition (N,
1983 Make_Task_Definition (Loc,
1984 Visible_Declarations => New_List,
1985 End_Label => Empty));
1986 end if;
1987
1988 Def := Task_Definition (N);
1989 V := Visible_Declarations (Def);
1990 if not Is_Empty_List (V) then
1991 Insert_Before (First (V), Aitem);
1992
1993 else
1994 Set_Visible_Declarations (Def, New_List (Aitem));
1995 end if;
1996
1997 goto Continue;
1998 end;
1999 end if;
2000
2001 -- Case 3 : Aspects that don't correspond to pragma/attribute
2002 -- definition clause.
2003
2004 -- Case 3a: The aspects listed below don't correspond to
2005 -- pragmas/attributes but do require delayed analysis.
2006
2007 -- Default_Value, Default_Component_Value
2008
2009 when Aspect_Default_Value |
2010 Aspect_Default_Component_Value =>
2011 Aitem := Empty;
2012
2013 -- Case 3b: The aspects listed below don't correspond to
2014 -- pragmas/attributes and don't need delayed analysis.
2015
2016 -- Implicit_Dereference
2017
2018 -- For Implicit_Dereference, External_Name and Link_Name, only
2019 -- the legality checks are done during the analysis, thus no
2020 -- delay is required.
2021
2022 when Aspect_Implicit_Dereference =>
2023 Analyze_Aspect_Implicit_Dereference;
2024 goto Continue;
2025
2026 -- External_Name, Link_Name
2027
2028 when Aspect_External_Name |
2029 Aspect_Link_Name =>
2030 Analyze_Aspect_External_Or_Link_Name;
2031 goto Continue;
2032
2033 -- Dimension
2034
2035 when Aspect_Dimension =>
2036 Analyze_Aspect_Dimension (N, Id, Expr);
2037 goto Continue;
2038
2039 -- Dimension_System
2040
2041 when Aspect_Dimension_System =>
2042 Analyze_Aspect_Dimension_System (N, Id, Expr);
2043 goto Continue;
2044
2045 -- Case 4: Aspects requiring special handling
2046
2047 -- Pre/Post/Test_Case/Contract_Cases whose corresponding
2048 -- pragmas take care of the delay.
2049
2050 -- Pre/Post
2051
2052 -- Aspects Pre/Post generate Precondition/Postcondition pragmas
2053 -- with a first argument that is the expression, and a second
2054 -- argument that is an informative message if the test fails.
2055 -- This is inserted right after the declaration, to get the
2056 -- required pragma placement. The processing for the pragmas
2057 -- takes care of the required delay.
2058
2059 when Pre_Post_Aspects => Pre_Post : declare
2060 Pname : Name_Id;
2061
2062 begin
2063 if A_Id = Aspect_Pre or else A_Id = Aspect_Precondition then
2064 Pname := Name_Precondition;
2065 else
2066 Pname := Name_Postcondition;
2067 end if;
2068
2069 -- If the expressions is of the form A and then B, then
2070 -- we generate separate Pre/Post aspects for the separate
2071 -- clauses. Since we allow multiple pragmas, there is no
2072 -- problem in allowing multiple Pre/Post aspects internally.
2073 -- These should be treated in reverse order (B first and
2074 -- A second) since they are later inserted just after N in
2075 -- the order they are treated. This way, the pragma for A
2076 -- ends up preceding the pragma for B, which may have an
2077 -- importance for the error raised (either constraint error
2078 -- or precondition error).
2079
2080 -- We do not do this for Pre'Class, since we have to put
2081 -- these conditions together in a complex OR expression
2082
2083 -- We do not do this in ASIS mode, as ASIS relies on the
2084 -- original node representing the complete expression, when
2085 -- retrieving it through the source aspect table.
2086
2087 if not ASIS_Mode
2088 and then (Pname = Name_Postcondition
2089 or else not Class_Present (Aspect))
2090 then
2091 while Nkind (Expr) = N_And_Then loop
2092 Insert_After (Aspect,
2093 Make_Aspect_Specification (Sloc (Left_Opnd (Expr)),
2094 Identifier => Identifier (Aspect),
2095 Expression => Relocate_Node (Left_Opnd (Expr)),
2096 Class_Present => Class_Present (Aspect),
2097 Split_PPC => True));
2098 Rewrite (Expr, Relocate_Node (Right_Opnd (Expr)));
2099 Eloc := Sloc (Expr);
2100 end loop;
2101 end if;
2102
2103 -- Build the precondition/postcondition pragma
2104
2105 -- Add note about why we do NOT need Copy_Tree here ???
2106
2107 Make_Aitem_Pragma
2108 (Pragma_Argument_Associations => New_List (
2109 Make_Pragma_Argument_Association (Eloc,
2110 Chars => Name_Check,
2111 Expression => Relocate_Node (Expr))),
2112 Pragma_Name => Pname);
2113
2114 -- Add message unless exception messages are suppressed
2115
2116 if not Opt.Exception_Locations_Suppressed then
2117 Append_To (Pragma_Argument_Associations (Aitem),
2118 Make_Pragma_Argument_Association (Eloc,
2119 Chars => Name_Message,
2120 Expression =>
2121 Make_String_Literal (Eloc,
2122 Strval => "failed "
2123 & Get_Name_String (Pname)
2124 & " from "
2125 & Build_Location_String (Eloc))));
2126 end if;
2127
2128 Set_Is_Delayed_Aspect (Aspect);
2129
2130 -- For Pre/Post cases, insert immediately after the entity
2131 -- declaration, since that is the required pragma placement.
2132 -- Note that for these aspects, we do not have to worry
2133 -- about delay issues, since the pragmas themselves deal
2134 -- with delay of visibility for the expression analysis.
2135
2136 Insert_Delayed_Pragma (Aitem);
2137 goto Continue;
2138 end Pre_Post;
2139
2140 -- Test_Case
2141
2142 when Aspect_Test_Case => Test_Case : declare
2143 Args : List_Id;
2144 Comp_Expr : Node_Id;
2145 Comp_Assn : Node_Id;
2146 New_Expr : Node_Id;
2147
2148 begin
2149 Args := New_List;
2150
2151 if Nkind (Parent (N)) = N_Compilation_Unit then
2152 Error_Msg_Name_1 := Nam;
2153 Error_Msg_N ("incorrect placement of aspect `%`", E);
2154 goto Continue;
2155 end if;
2156
2157 if Nkind (Expr) /= N_Aggregate then
2158 Error_Msg_Name_1 := Nam;
2159 Error_Msg_NE
2160 ("wrong syntax for aspect `%` for &", Id, E);
2161 goto Continue;
2162 end if;
2163
2164 -- Make pragma expressions refer to the original aspect
2165 -- expressions through the Original_Node link. This is
2166 -- used in semantic analysis for ASIS mode, so that the
2167 -- original expression also gets analyzed.
2168
2169 Comp_Expr := First (Expressions (Expr));
2170 while Present (Comp_Expr) loop
2171 New_Expr := Relocate_Node (Comp_Expr);
2172 Set_Original_Node (New_Expr, Comp_Expr);
2173 Append_To (Args,
2174 Make_Pragma_Argument_Association (Sloc (Comp_Expr),
2175 Expression => New_Expr));
2176 Next (Comp_Expr);
2177 end loop;
2178
2179 Comp_Assn := First (Component_Associations (Expr));
2180 while Present (Comp_Assn) loop
2181 if List_Length (Choices (Comp_Assn)) /= 1
2182 or else
2183 Nkind (First (Choices (Comp_Assn))) /= N_Identifier
2184 then
2185 Error_Msg_Name_1 := Nam;
2186 Error_Msg_NE
2187 ("wrong syntax for aspect `%` for &", Id, E);
2188 goto Continue;
2189 end if;
2190
2191 New_Expr := Relocate_Node (Expression (Comp_Assn));
2192 Set_Original_Node (New_Expr, Expression (Comp_Assn));
2193 Append_To (Args,
2194 Make_Pragma_Argument_Association (Sloc (Comp_Assn),
2195 Chars => Chars (First (Choices (Comp_Assn))),
2196 Expression => New_Expr));
2197 Next (Comp_Assn);
2198 end loop;
2199
2200 -- Build the test-case pragma
2201
2202 Make_Aitem_Pragma
2203 (Pragma_Argument_Associations => Args,
2204 Pragma_Name => Nam);
2205 end Test_Case;
2206
2207 -- Contract_Cases
2208
2209 when Aspect_Contract_Cases =>
2210 Make_Aitem_Pragma
2211 (Pragma_Argument_Associations => New_List (
2212 Make_Pragma_Argument_Association (Loc,
2213 Expression => Relocate_Node (Expr))),
2214 Pragma_Name => Nam);
2215
2216 Decorate_Delayed_Aspect_And_Pragma (Aspect, Aitem);
2217 Insert_Delayed_Pragma (Aitem);
2218 goto Continue;
2219
2220 -- Case 5: Special handling for aspects with an optional
2221 -- boolean argument.
2222
2223 -- In the general case, the corresponding pragma cannot be
2224 -- generated yet because the evaluation of the boolean needs
2225 -- to be delayed till the freeze point.
2226
2227 when Boolean_Aspects |
2228 Library_Unit_Aspects =>
2229
2230 Set_Is_Boolean_Aspect (Aspect);
2231
2232 -- Lock_Free aspect only apply to protected objects
2233
2234 if A_Id = Aspect_Lock_Free then
2235 if Ekind (E) /= E_Protected_Type then
2236 Error_Msg_Name_1 := Nam;
2237 Error_Msg_N
2238 ("aspect % only applies to a protected object",
2239 Aspect);
2240
2241 else
2242 -- Set the Uses_Lock_Free flag to True if there is no
2243 -- expression or if the expression is True. The
2244 -- evaluation of this aspect should be delayed to the
2245 -- freeze point (why???)
2246
2247 if No (Expr)
2248 or else Is_True (Static_Boolean (Expr))
2249 then
2250 Set_Uses_Lock_Free (E);
2251 end if;
2252
2253 Record_Rep_Item (E, Aspect);
2254 end if;
2255
2256 goto Continue;
2257
2258 elsif A_Id = Aspect_Import or else A_Id = Aspect_Export then
2259
2260 -- Verify that there is an aspect Convention that will
2261 -- incorporate the Import/Export aspect, and eventual
2262 -- Link/External names.
2263
2264 declare
2265 A : Node_Id;
2266
2267 begin
2268 A := First (L);
2269 while Present (A) loop
2270 exit when Chars (Identifier (A)) = Name_Convention;
2271 Next (A);
2272 end loop;
2273
2274 -- It is legal to specify Import for a variable, in
2275 -- order to suppress initialization for it, without
2276 -- specifying explicitly its convention. However this
2277 -- is only legal if the convention of the object type
2278 -- is Ada or similar.
2279
2280 if No (A) then
2281 if Ekind (E) = E_Variable
2282 and then A_Id = Aspect_Import
2283 then
2284 declare
2285 C : constant Convention_Id :=
2286 Convention (Etype (E));
2287 begin
2288 if C = Convention_Ada or else
2289 C = Convention_Ada_Pass_By_Copy or else
2290 C = Convention_Ada_Pass_By_Reference
2291 then
2292 goto Continue;
2293 end if;
2294 end;
2295 end if;
2296
2297 -- Otherwise, Convention must be specified
2298
2299 Error_Msg_N
2300 ("missing Convention aspect for Export/Import",
2301 Aspect);
2302 end if;
2303 end;
2304
2305 goto Continue;
2306 end if;
2307
2308 -- Library unit aspects require special handling in the case
2309 -- of a package declaration, the pragma needs to be inserted
2310 -- in the list of declarations for the associated package.
2311 -- There is no issue of visibility delay for these aspects.
2312
2313 if A_Id in Library_Unit_Aspects
2314 and then
2315 Nkind_In (N, N_Package_Declaration,
2316 N_Generic_Package_Declaration)
2317 and then Nkind (Parent (N)) /= N_Compilation_Unit
2318 then
2319 Error_Msg_N
2320 ("incorrect context for library unit aspect&", Id);
2321 goto Continue;
2322 end if;
2323
2324 -- Cases where we do not delay, includes all cases where
2325 -- the expression is missing other than the above cases.
2326
2327 if not Delay_Required or else No (Expr) then
2328 Make_Aitem_Pragma
2329 (Pragma_Argument_Associations => New_List (
2330 Make_Pragma_Argument_Association (Sloc (Ent),
2331 Expression => Ent)),
2332 Pragma_Name => Chars (Id));
2333 Delay_Required := False;
2334
2335 -- In general cases, the corresponding pragma/attribute
2336 -- definition clause will be inserted later at the freezing
2337 -- point, and we do not need to build it now
2338
2339 else
2340 Aitem := Empty;
2341 end if;
2342
2343 -- Storage_Size
2344
2345 -- This is special because for access types we need to generate
2346 -- an attribute definition clause. This also works for single
2347 -- task declarations, but it does not work for task type
2348 -- declarations, because we have the case where the expression
2349 -- references a discriminant of the task type. That can't use
2350 -- an attribute definition clause because we would not have
2351 -- visibility on the discriminant. For that case we must
2352 -- generate a pragma in the task definition.
2353
2354 when Aspect_Storage_Size =>
2355
2356 -- Task type case
2357
2358 if Ekind (E) = E_Task_Type then
2359 declare
2360 Decl : constant Node_Id := Declaration_Node (E);
2361
2362 begin
2363 pragma Assert (Nkind (Decl) = N_Task_Type_Declaration);
2364
2365 -- If no task definition, create one
2366
2367 if No (Task_Definition (Decl)) then
2368 Set_Task_Definition (Decl,
2369 Make_Task_Definition (Loc,
2370 Visible_Declarations => Empty_List,
2371 End_Label => Empty));
2372 end if;
2373
2374 -- Create a pragma and put it at the start of the
2375 -- task definition for the task type declaration.
2376
2377 Make_Aitem_Pragma
2378 (Pragma_Argument_Associations => New_List (
2379 Make_Pragma_Argument_Association (Loc,
2380 Expression => Relocate_Node (Expr))),
2381 Pragma_Name => Name_Storage_Size);
2382
2383 Prepend
2384 (Aitem,
2385 Visible_Declarations (Task_Definition (Decl)));
2386 goto Continue;
2387 end;
2388
2389 -- All other cases, generate attribute definition
2390
2391 else
2392 Aitem :=
2393 Make_Attribute_Definition_Clause (Loc,
2394 Name => Ent,
2395 Chars => Chars (Id),
2396 Expression => Relocate_Node (Expr));
2397 end if;
2398 end case;
2399
2400 -- Attach the corresponding pragma/attribute definition clause to
2401 -- the aspect specification node.
2402
2403 if Present (Aitem) then
2404 Set_From_Aspect_Specification (Aitem, True);
2405 end if;
2406
2407 -- Aspect Abstract_State introduces implicit declarations for all
2408 -- state abstraction entities it defines. To emulate this behavior
2409 -- insert the pragma at the start of the visible declarations of
2410 -- the related package.
2411
2412 if Nam = Name_Abstract_State
2413 and then Nkind (N) = N_Package_Declaration
2414 then
2415 if No (Visible_Declarations (Specification (N))) then
2416 Set_Visible_Declarations (Specification (N), New_List);
2417 end if;
2418
2419 Prepend (Aitem, Visible_Declarations (Specification (N)));
2420 goto Continue;
2421
2422 -- In the context of a compilation unit, we directly put the
2423 -- pragma in the Pragmas_After list of the N_Compilation_Unit_Aux
2424 -- node (no delay is required here) except for aspects on a
2425 -- subprogram body (see below) and a generic package, for which
2426 -- we need to introduce the pragma before building the generic
2427 -- copy (see sem_ch12), and for package instantiations, where
2428 -- the library unit pragmas are better handled early.
2429
2430 elsif Nkind (Parent (N)) = N_Compilation_Unit
2431 and then (Present (Aitem) or else Is_Boolean_Aspect (Aspect))
2432 then
2433 declare
2434 Aux : constant Node_Id := Aux_Decls_Node (Parent (N));
2435
2436 begin
2437 pragma Assert (Nkind (Aux) = N_Compilation_Unit_Aux);
2438
2439 -- For a Boolean aspect, create the corresponding pragma if
2440 -- no expression or if the value is True.
2441
2442 if Is_Boolean_Aspect (Aspect) and then No (Aitem) then
2443 if Is_True (Static_Boolean (Expr)) then
2444 Make_Aitem_Pragma
2445 (Pragma_Argument_Associations => New_List (
2446 Make_Pragma_Argument_Association (Sloc (Ent),
2447 Expression => Ent)),
2448 Pragma_Name => Chars (Id));
2449
2450 Set_From_Aspect_Specification (Aitem, True);
2451 Set_Corresponding_Aspect (Aitem, Aspect);
2452
2453 else
2454 goto Continue;
2455 end if;
2456 end if;
2457
2458 -- If the aspect is on a subprogram body (relevant aspects
2459 -- are Inline and Priority), add the pragma in front of
2460 -- the declarations.
2461
2462 if Nkind (N) = N_Subprogram_Body then
2463 if No (Declarations (N)) then
2464 Set_Declarations (N, New_List);
2465 end if;
2466
2467 Prepend (Aitem, Declarations (N));
2468
2469 elsif Nkind (N) = N_Generic_Package_Declaration then
2470 if No (Visible_Declarations (Specification (N))) then
2471 Set_Visible_Declarations (Specification (N), New_List);
2472 end if;
2473
2474 Prepend (Aitem,
2475 Visible_Declarations (Specification (N)));
2476
2477 elsif Nkind (N) = N_Package_Instantiation then
2478 declare
2479 Spec : constant Node_Id :=
2480 Specification (Instance_Spec (N));
2481 begin
2482 if No (Visible_Declarations (Spec)) then
2483 Set_Visible_Declarations (Spec, New_List);
2484 end if;
2485
2486 Prepend (Aitem, Visible_Declarations (Spec));
2487 end;
2488
2489 else
2490 if No (Pragmas_After (Aux)) then
2491 Set_Pragmas_After (Aux, New_List);
2492 end if;
2493
2494 Append (Aitem, Pragmas_After (Aux));
2495 end if;
2496
2497 goto Continue;
2498 end;
2499 end if;
2500
2501 -- The evaluation of the aspect is delayed to the freezing point.
2502 -- The pragma or attribute clause if there is one is then attached
2503 -- to the aspect specification which is put in the rep item list.
2504
2505 if Delay_Required then
2506 if Present (Aitem) then
2507 Set_Is_Delayed_Aspect (Aitem);
2508 Set_Aspect_Rep_Item (Aspect, Aitem);
2509 Set_Parent (Aitem, Aspect);
2510 end if;
2511
2512 Set_Is_Delayed_Aspect (Aspect);
2513
2514 -- In the case of Default_Value, link the aspect to base type
2515 -- as well, even though it appears on a first subtype. This is
2516 -- mandated by the semantics of the aspect. Do not establish
2517 -- the link when processing the base type itself as this leads
2518 -- to a rep item circularity. Verify that we are dealing with
2519 -- a scalar type to prevent cascaded errors.
2520
2521 if A_Id = Aspect_Default_Value
2522 and then Is_Scalar_Type (E)
2523 and then Base_Type (E) /= E
2524 then
2525 Set_Has_Delayed_Aspects (Base_Type (E));
2526 Record_Rep_Item (Base_Type (E), Aspect);
2527 end if;
2528
2529 Set_Has_Delayed_Aspects (E);
2530 Record_Rep_Item (E, Aspect);
2531
2532 -- When delay is not required and the context is a package or a
2533 -- subprogram body, insert the pragma in the body declarations.
2534
2535 elsif Nkind_In (N, N_Package_Body, N_Subprogram_Body) then
2536 if No (Declarations (N)) then
2537 Set_Declarations (N, New_List);
2538 end if;
2539
2540 -- The pragma is added before source declarations
2541
2542 Prepend_To (Declarations (N), Aitem);
2543
2544 -- When delay is not required and the context is not a compilation
2545 -- unit, we simply insert the pragma/attribute definition clause
2546 -- in sequence.
2547
2548 else
2549 Insert_After (Ins_Node, Aitem);
2550 Ins_Node := Aitem;
2551 end if;
2552 end Analyze_One_Aspect;
2553
2554 <<Continue>>
2555 Next (Aspect);
2556 end loop Aspect_Loop;
2557
2558 if Has_Delayed_Aspects (E) then
2559 Ensure_Freeze_Node (E);
2560 end if;
2561 end Analyze_Aspect_Specifications;
2562
2563 -----------------------
2564 -- Analyze_At_Clause --
2565 -----------------------
2566
2567 -- An at clause is replaced by the corresponding Address attribute
2568 -- definition clause that is the preferred approach in Ada 95.
2569
2570 procedure Analyze_At_Clause (N : Node_Id) is
2571 CS : constant Boolean := Comes_From_Source (N);
2572
2573 begin
2574 -- This is an obsolescent feature
2575
2576 Check_Restriction (No_Obsolescent_Features, N);
2577
2578 if Warn_On_Obsolescent_Feature then
2579 Error_Msg_N
2580 ("?j?at clause is an obsolescent feature (RM J.7(2))", N);
2581 Error_Msg_N
2582 ("\?j?use address attribute definition clause instead", N);
2583 end if;
2584
2585 -- Rewrite as address clause
2586
2587 Rewrite (N,
2588 Make_Attribute_Definition_Clause (Sloc (N),
2589 Name => Identifier (N),
2590 Chars => Name_Address,
2591 Expression => Expression (N)));
2592
2593 -- We preserve Comes_From_Source, since logically the clause still comes
2594 -- from the source program even though it is changed in form.
2595
2596 Set_Comes_From_Source (N, CS);
2597
2598 -- Analyze rewritten clause
2599
2600 Analyze_Attribute_Definition_Clause (N);
2601 end Analyze_At_Clause;
2602
2603 -----------------------------------------
2604 -- Analyze_Attribute_Definition_Clause --
2605 -----------------------------------------
2606
2607 procedure Analyze_Attribute_Definition_Clause (N : Node_Id) is
2608 Loc : constant Source_Ptr := Sloc (N);
2609 Nam : constant Node_Id := Name (N);
2610 Attr : constant Name_Id := Chars (N);
2611 Expr : constant Node_Id := Expression (N);
2612 Id : constant Attribute_Id := Get_Attribute_Id (Attr);
2613
2614 Ent : Entity_Id;
2615 -- The entity of Nam after it is analyzed. In the case of an incomplete
2616 -- type, this is the underlying type.
2617
2618 U_Ent : Entity_Id;
2619 -- The underlying entity to which the attribute applies. Generally this
2620 -- is the Underlying_Type of Ent, except in the case where the clause
2621 -- applies to full view of incomplete type or private type in which case
2622 -- U_Ent is just a copy of Ent.
2623
2624 FOnly : Boolean := False;
2625 -- Reset to True for subtype specific attribute (Alignment, Size)
2626 -- and for stream attributes, i.e. those cases where in the call
2627 -- to Rep_Item_Too_Late, FOnly is set True so that only the freezing
2628 -- rules are checked. Note that the case of stream attributes is not
2629 -- clear from the RM, but see AI95-00137. Also, the RM seems to
2630 -- disallow Storage_Size for derived task types, but that is also
2631 -- clearly unintentional.
2632
2633 procedure Analyze_Stream_TSS_Definition (TSS_Nam : TSS_Name_Type);
2634 -- Common processing for 'Read, 'Write, 'Input and 'Output attribute
2635 -- definition clauses.
2636
2637 function Duplicate_Clause return Boolean;
2638 -- This routine checks if the aspect for U_Ent being given by attribute
2639 -- definition clause N is for an aspect that has already been specified,
2640 -- and if so gives an error message. If there is a duplicate, True is
2641 -- returned, otherwise if there is no error, False is returned.
2642
2643 procedure Check_Indexing_Functions;
2644 -- Check that the function in Constant_Indexing or Variable_Indexing
2645 -- attribute has the proper type structure. If the name is overloaded,
2646 -- check that some interpretation is legal.
2647
2648 procedure Check_Iterator_Functions;
2649 -- Check that there is a single function in Default_Iterator attribute
2650 -- has the proper type structure.
2651
2652 function Check_Primitive_Function (Subp : Entity_Id) return Boolean;
2653 -- Common legality check for the previous two
2654
2655 -----------------------------------
2656 -- Analyze_Stream_TSS_Definition --
2657 -----------------------------------
2658
2659 procedure Analyze_Stream_TSS_Definition (TSS_Nam : TSS_Name_Type) is
2660 Subp : Entity_Id := Empty;
2661 I : Interp_Index;
2662 It : Interp;
2663 Pnam : Entity_Id;
2664
2665 Is_Read : constant Boolean := (TSS_Nam = TSS_Stream_Read);
2666 -- True for Read attribute, false for other attributes
2667
2668 function Has_Good_Profile (Subp : Entity_Id) return Boolean;
2669 -- Return true if the entity is a subprogram with an appropriate
2670 -- profile for the attribute being defined.
2671
2672 ----------------------
2673 -- Has_Good_Profile --
2674 ----------------------
2675
2676 function Has_Good_Profile (Subp : Entity_Id) return Boolean is
2677 F : Entity_Id;
2678 Is_Function : constant Boolean := (TSS_Nam = TSS_Stream_Input);
2679 Expected_Ekind : constant array (Boolean) of Entity_Kind :=
2680 (False => E_Procedure, True => E_Function);
2681 Typ : Entity_Id;
2682
2683 begin
2684 if Ekind (Subp) /= Expected_Ekind (Is_Function) then
2685 return False;
2686 end if;
2687
2688 F := First_Formal (Subp);
2689
2690 if No (F)
2691 or else Ekind (Etype (F)) /= E_Anonymous_Access_Type
2692 or else Designated_Type (Etype (F)) /=
2693 Class_Wide_Type (RTE (RE_Root_Stream_Type))
2694 then
2695 return False;
2696 end if;
2697
2698 if not Is_Function then
2699 Next_Formal (F);
2700
2701 declare
2702 Expected_Mode : constant array (Boolean) of Entity_Kind :=
2703 (False => E_In_Parameter,
2704 True => E_Out_Parameter);
2705 begin
2706 if Parameter_Mode (F) /= Expected_Mode (Is_Read) then
2707 return False;
2708 end if;
2709 end;
2710
2711 Typ := Etype (F);
2712
2713 else
2714 Typ := Etype (Subp);
2715 end if;
2716
2717 return Base_Type (Typ) = Base_Type (Ent)
2718 and then No (Next_Formal (F));
2719 end Has_Good_Profile;
2720
2721 -- Start of processing for Analyze_Stream_TSS_Definition
2722
2723 begin
2724 FOnly := True;
2725
2726 if not Is_Type (U_Ent) then
2727 Error_Msg_N ("local name must be a subtype", Nam);
2728 return;
2729 end if;
2730
2731 Pnam := TSS (Base_Type (U_Ent), TSS_Nam);
2732
2733 -- If Pnam is present, it can be either inherited from an ancestor
2734 -- type (in which case it is legal to redefine it for this type), or
2735 -- be a previous definition of the attribute for the same type (in
2736 -- which case it is illegal).
2737
2738 -- In the first case, it will have been analyzed already, and we
2739 -- can check that its profile does not match the expected profile
2740 -- for a stream attribute of U_Ent. In the second case, either Pnam
2741 -- has been analyzed (and has the expected profile), or it has not
2742 -- been analyzed yet (case of a type that has not been frozen yet
2743 -- and for which the stream attribute has been set using Set_TSS).
2744
2745 if Present (Pnam)
2746 and then (No (First_Entity (Pnam)) or else Has_Good_Profile (Pnam))
2747 then
2748 Error_Msg_Sloc := Sloc (Pnam);
2749 Error_Msg_Name_1 := Attr;
2750 Error_Msg_N ("% attribute already defined #", Nam);
2751 return;
2752 end if;
2753
2754 Analyze (Expr);
2755
2756 if Is_Entity_Name (Expr) then
2757 if not Is_Overloaded (Expr) then
2758 if Has_Good_Profile (Entity (Expr)) then
2759 Subp := Entity (Expr);
2760 end if;
2761
2762 else
2763 Get_First_Interp (Expr, I, It);
2764 while Present (It.Nam) loop
2765 if Has_Good_Profile (It.Nam) then
2766 Subp := It.Nam;
2767 exit;
2768 end if;
2769
2770 Get_Next_Interp (I, It);
2771 end loop;
2772 end if;
2773 end if;
2774
2775 if Present (Subp) then
2776 if Is_Abstract_Subprogram (Subp) then
2777 Error_Msg_N ("stream subprogram must not be abstract", Expr);
2778 return;
2779 end if;
2780
2781 Set_Entity (Expr, Subp);
2782 Set_Etype (Expr, Etype (Subp));
2783
2784 New_Stream_Subprogram (N, U_Ent, Subp, TSS_Nam);
2785
2786 else
2787 Error_Msg_Name_1 := Attr;
2788 Error_Msg_N ("incorrect expression for% attribute", Expr);
2789 end if;
2790 end Analyze_Stream_TSS_Definition;
2791
2792 ------------------------------
2793 -- Check_Indexing_Functions --
2794 ------------------------------
2795
2796 procedure Check_Indexing_Functions is
2797 Indexing_Found : Boolean;
2798
2799 procedure Check_One_Function (Subp : Entity_Id);
2800 -- Check one possible interpretation. Sets Indexing_Found True if an
2801 -- indexing function is found.
2802
2803 ------------------------
2804 -- Check_One_Function --
2805 ------------------------
2806
2807 procedure Check_One_Function (Subp : Entity_Id) is
2808 Default_Element : constant Node_Id :=
2809 Find_Value_Of_Aspect
2810 (Etype (First_Formal (Subp)),
2811 Aspect_Iterator_Element);
2812
2813 begin
2814 if not Check_Primitive_Function (Subp)
2815 and then not Is_Overloaded (Expr)
2816 then
2817 Error_Msg_NE
2818 ("aspect Indexing requires a function that applies to type&",
2819 Subp, Ent);
2820 end if;
2821
2822 -- An indexing function must return either the default element of
2823 -- the container, or a reference type. For variable indexing it
2824 -- must be the latter.
2825
2826 if Present (Default_Element) then
2827 Analyze (Default_Element);
2828
2829 if Is_Entity_Name (Default_Element)
2830 and then Covers (Entity (Default_Element), Etype (Subp))
2831 then
2832 Indexing_Found := True;
2833 return;
2834 end if;
2835 end if;
2836
2837 -- For variable_indexing the return type must be a reference type
2838
2839 if Attr = Name_Variable_Indexing
2840 and then not Has_Implicit_Dereference (Etype (Subp))
2841 then
2842 Error_Msg_N
2843 ("function for indexing must return a reference type", Subp);
2844
2845 else
2846 Indexing_Found := True;
2847 end if;
2848 end Check_One_Function;
2849
2850 -- Start of processing for Check_Indexing_Functions
2851
2852 begin
2853 if In_Instance then
2854 return;
2855 end if;
2856
2857 Analyze (Expr);
2858
2859 if not Is_Overloaded (Expr) then
2860 Check_One_Function (Entity (Expr));
2861
2862 else
2863 declare
2864 I : Interp_Index;
2865 It : Interp;
2866
2867 begin
2868 Indexing_Found := False;
2869 Get_First_Interp (Expr, I, It);
2870 while Present (It.Nam) loop
2871
2872 -- Note that analysis will have added the interpretation
2873 -- that corresponds to the dereference. We only check the
2874 -- subprogram itself.
2875
2876 if Is_Overloadable (It.Nam) then
2877 Check_One_Function (It.Nam);
2878 end if;
2879
2880 Get_Next_Interp (I, It);
2881 end loop;
2882
2883 if not Indexing_Found then
2884 Error_Msg_NE
2885 ("aspect Indexing requires a function that "
2886 & "applies to type&", Expr, Ent);
2887 end if;
2888 end;
2889 end if;
2890 end Check_Indexing_Functions;
2891
2892 ------------------------------
2893 -- Check_Iterator_Functions --
2894 ------------------------------
2895
2896 procedure Check_Iterator_Functions is
2897 Default : Entity_Id;
2898
2899 function Valid_Default_Iterator (Subp : Entity_Id) return Boolean;
2900 -- Check one possible interpretation for validity
2901
2902 ----------------------------
2903 -- Valid_Default_Iterator --
2904 ----------------------------
2905
2906 function Valid_Default_Iterator (Subp : Entity_Id) return Boolean is
2907 Formal : Entity_Id;
2908
2909 begin
2910 if not Check_Primitive_Function (Subp) then
2911 return False;
2912 else
2913 Formal := First_Formal (Subp);
2914 end if;
2915
2916 -- False if any subsequent formal has no default expression
2917
2918 Formal := Next_Formal (Formal);
2919 while Present (Formal) loop
2920 if No (Expression (Parent (Formal))) then
2921 return False;
2922 end if;
2923
2924 Next_Formal (Formal);
2925 end loop;
2926
2927 -- True if all subsequent formals have default expressions
2928
2929 return True;
2930 end Valid_Default_Iterator;
2931
2932 -- Start of processing for Check_Iterator_Functions
2933
2934 begin
2935 Analyze (Expr);
2936
2937 if not Is_Entity_Name (Expr) then
2938 Error_Msg_N ("aspect Iterator must be a function name", Expr);
2939 end if;
2940
2941 if not Is_Overloaded (Expr) then
2942 if not Check_Primitive_Function (Entity (Expr)) then
2943 Error_Msg_NE
2944 ("aspect Indexing requires a function that applies to type&",
2945 Entity (Expr), Ent);
2946 end if;
2947
2948 if not Valid_Default_Iterator (Entity (Expr)) then
2949 Error_Msg_N ("improper function for default iterator", Expr);
2950 end if;
2951
2952 else
2953 Default := Empty;
2954 declare
2955 I : Interp_Index;
2956 It : Interp;
2957
2958 begin
2959 Get_First_Interp (Expr, I, It);
2960 while Present (It.Nam) loop
2961 if not Check_Primitive_Function (It.Nam)
2962 or else not Valid_Default_Iterator (It.Nam)
2963 then
2964 Remove_Interp (I);
2965
2966 elsif Present (Default) then
2967 Error_Msg_N ("default iterator must be unique", Expr);
2968
2969 else
2970 Default := It.Nam;
2971 end if;
2972
2973 Get_Next_Interp (I, It);
2974 end loop;
2975 end;
2976
2977 if Present (Default) then
2978 Set_Entity (Expr, Default);
2979 Set_Is_Overloaded (Expr, False);
2980 end if;
2981 end if;
2982 end Check_Iterator_Functions;
2983
2984 -------------------------------
2985 -- Check_Primitive_Function --
2986 -------------------------------
2987
2988 function Check_Primitive_Function (Subp : Entity_Id) return Boolean is
2989 Ctrl : Entity_Id;
2990
2991 begin
2992 if Ekind (Subp) /= E_Function then
2993 return False;
2994 end if;
2995
2996 if No (First_Formal (Subp)) then
2997 return False;
2998 else
2999 Ctrl := Etype (First_Formal (Subp));
3000 end if;
3001
3002 if Ctrl = Ent
3003 or else Ctrl = Class_Wide_Type (Ent)
3004 or else
3005 (Ekind (Ctrl) = E_Anonymous_Access_Type
3006 and then
3007 (Designated_Type (Ctrl) = Ent
3008 or else Designated_Type (Ctrl) = Class_Wide_Type (Ent)))
3009 then
3010 null;
3011
3012 else
3013 return False;
3014 end if;
3015
3016 return True;
3017 end Check_Primitive_Function;
3018
3019 ----------------------
3020 -- Duplicate_Clause --
3021 ----------------------
3022
3023 function Duplicate_Clause return Boolean is
3024 A : Node_Id;
3025
3026 begin
3027 -- Nothing to do if this attribute definition clause comes from
3028 -- an aspect specification, since we could not be duplicating an
3029 -- explicit clause, and we dealt with the case of duplicated aspects
3030 -- in Analyze_Aspect_Specifications.
3031
3032 if From_Aspect_Specification (N) then
3033 return False;
3034 end if;
3035
3036 -- Otherwise current clause may duplicate previous clause, or a
3037 -- previously given pragma or aspect specification for the same
3038 -- aspect.
3039
3040 A := Get_Rep_Item (U_Ent, Chars (N), Check_Parents => False);
3041
3042 if Present (A) then
3043 Error_Msg_Name_1 := Chars (N);
3044 Error_Msg_Sloc := Sloc (A);
3045
3046 Error_Msg_NE ("aspect% for & previously given#", N, U_Ent);
3047 return True;
3048 end if;
3049
3050 return False;
3051 end Duplicate_Clause;
3052
3053 -- Start of processing for Analyze_Attribute_Definition_Clause
3054
3055 begin
3056 -- The following code is a defense against recursion. Not clear that
3057 -- this can happen legitimately, but perhaps some error situations
3058 -- can cause it, and we did see this recursion during testing.
3059
3060 if Analyzed (N) then
3061 return;
3062 else
3063 Set_Analyzed (N, True);
3064 end if;
3065
3066 -- Ignore some selected attributes in CodePeer mode since they are not
3067 -- relevant in this context.
3068
3069 if CodePeer_Mode then
3070 case Id is
3071
3072 -- Ignore Component_Size in CodePeer mode, to avoid changing the
3073 -- internal representation of types by implicitly packing them.
3074
3075 when Attribute_Component_Size =>
3076 Rewrite (N, Make_Null_Statement (Sloc (N)));
3077 return;
3078
3079 when others =>
3080 null;
3081 end case;
3082 end if;
3083
3084 -- Process Ignore_Rep_Clauses option
3085
3086 if Ignore_Rep_Clauses then
3087 case Id is
3088
3089 -- The following should be ignored. They do not affect legality
3090 -- and may be target dependent. The basic idea of -gnatI is to
3091 -- ignore any rep clauses that may be target dependent but do not
3092 -- affect legality (except possibly to be rejected because they
3093 -- are incompatible with the compilation target).
3094
3095 when Attribute_Alignment |
3096 Attribute_Bit_Order |
3097 Attribute_Component_Size |
3098 Attribute_Machine_Radix |
3099 Attribute_Object_Size |
3100 Attribute_Size |
3101 Attribute_Stream_Size |
3102 Attribute_Value_Size =>
3103 Rewrite (N, Make_Null_Statement (Sloc (N)));
3104 return;
3105
3106 -- Perhaps 'Small should not be ignored by Ignore_Rep_Clauses ???
3107
3108 when Attribute_Small =>
3109 if Ignore_Rep_Clauses then
3110 Rewrite (N, Make_Null_Statement (Sloc (N)));
3111 return;
3112 end if;
3113
3114 -- The following should not be ignored, because in the first place
3115 -- they are reasonably portable, and should not cause problems in
3116 -- compiling code from another target, and also they do affect
3117 -- legality, e.g. failing to provide a stream attribute for a
3118 -- type may make a program illegal.
3119
3120 when Attribute_External_Tag |
3121 Attribute_Input |
3122 Attribute_Output |
3123 Attribute_Read |
3124 Attribute_Simple_Storage_Pool |
3125 Attribute_Storage_Pool |
3126 Attribute_Storage_Size |
3127 Attribute_Write =>
3128 null;
3129
3130 -- Other cases are errors ("attribute& cannot be set with
3131 -- definition clause"), which will be caught below.
3132
3133 when others =>
3134 null;
3135 end case;
3136 end if;
3137
3138 Analyze (Nam);
3139 Ent := Entity (Nam);
3140
3141 if Rep_Item_Too_Early (Ent, N) then
3142 return;
3143 end if;
3144
3145 -- Rep clause applies to full view of incomplete type or private type if
3146 -- we have one (if not, this is a premature use of the type). However,
3147 -- certain semantic checks need to be done on the specified entity (i.e.
3148 -- the private view), so we save it in Ent.
3149
3150 if Is_Private_Type (Ent)
3151 and then Is_Derived_Type (Ent)
3152 and then not Is_Tagged_Type (Ent)
3153 and then No (Full_View (Ent))
3154 then
3155 -- If this is a private type whose completion is a derivation from
3156 -- another private type, there is no full view, and the attribute
3157 -- belongs to the type itself, not its underlying parent.
3158
3159 U_Ent := Ent;
3160
3161 elsif Ekind (Ent) = E_Incomplete_Type then
3162
3163 -- The attribute applies to the full view, set the entity of the
3164 -- attribute definition accordingly.
3165
3166 Ent := Underlying_Type (Ent);
3167 U_Ent := Ent;
3168 Set_Entity (Nam, Ent);
3169
3170 else
3171 U_Ent := Underlying_Type (Ent);
3172 end if;
3173
3174 -- Avoid cascaded error
3175
3176 if Etype (Nam) = Any_Type then
3177 return;
3178
3179 -- Must be declared in current scope or in case of an aspect
3180 -- specification, must be visible in current scope.
3181
3182 elsif Scope (Ent) /= Current_Scope
3183 and then
3184 not (From_Aspect_Specification (N)
3185 and then Scope_Within_Or_Same (Current_Scope, Scope (Ent)))
3186 then
3187 Error_Msg_N ("entity must be declared in this scope", Nam);
3188 return;
3189
3190 -- Must not be a source renaming (we do have some cases where the
3191 -- expander generates a renaming, and those cases are OK, in such
3192 -- cases any attribute applies to the renamed object as well).
3193
3194 elsif Is_Object (Ent)
3195 and then Present (Renamed_Object (Ent))
3196 then
3197 -- Case of renamed object from source, this is an error
3198
3199 if Comes_From_Source (Renamed_Object (Ent)) then
3200 Get_Name_String (Chars (N));
3201 Error_Msg_Strlen := Name_Len;
3202 Error_Msg_String (1 .. Name_Len) := Name_Buffer (1 .. Name_Len);
3203 Error_Msg_N
3204 ("~ clause not allowed for a renaming declaration "
3205 & "(RM 13.1(6))", Nam);
3206 return;
3207
3208 -- For the case of a compiler generated renaming, the attribute
3209 -- definition clause applies to the renamed object created by the
3210 -- expander. The easiest general way to handle this is to create a
3211 -- copy of the attribute definition clause for this object.
3212
3213 else
3214 Insert_Action (N,
3215 Make_Attribute_Definition_Clause (Loc,
3216 Name =>
3217 New_Occurrence_Of (Entity (Renamed_Object (Ent)), Loc),
3218 Chars => Chars (N),
3219 Expression => Duplicate_Subexpr (Expression (N))));
3220 end if;
3221
3222 -- If no underlying entity, use entity itself, applies to some
3223 -- previously detected error cases ???
3224
3225 elsif No (U_Ent) then
3226 U_Ent := Ent;
3227
3228 -- Cannot specify for a subtype (exception Object/Value_Size)
3229
3230 elsif Is_Type (U_Ent)
3231 and then not Is_First_Subtype (U_Ent)
3232 and then Id /= Attribute_Object_Size
3233 and then Id /= Attribute_Value_Size
3234 and then not From_At_Mod (N)
3235 then
3236 Error_Msg_N ("cannot specify attribute for subtype", Nam);
3237 return;
3238 end if;
3239
3240 Set_Entity (N, U_Ent);
3241 Check_Restriction_No_Use_Of_Attribute (N);
3242
3243 -- Switch on particular attribute
3244
3245 case Id is
3246
3247 -------------
3248 -- Address --
3249 -------------
3250
3251 -- Address attribute definition clause
3252
3253 when Attribute_Address => Address : begin
3254
3255 -- A little error check, catch for X'Address use X'Address;
3256
3257 if Nkind (Nam) = N_Identifier
3258 and then Nkind (Expr) = N_Attribute_Reference
3259 and then Attribute_Name (Expr) = Name_Address
3260 and then Nkind (Prefix (Expr)) = N_Identifier
3261 and then Chars (Nam) = Chars (Prefix (Expr))
3262 then
3263 Error_Msg_NE
3264 ("address for & is self-referencing", Prefix (Expr), Ent);
3265 return;
3266 end if;
3267
3268 -- Not that special case, carry on with analysis of expression
3269
3270 Analyze_And_Resolve (Expr, RTE (RE_Address));
3271
3272 -- Even when ignoring rep clauses we need to indicate that the
3273 -- entity has an address clause and thus it is legal to declare
3274 -- it imported.
3275
3276 if Ignore_Rep_Clauses then
3277 if Ekind_In (U_Ent, E_Variable, E_Constant) then
3278 Record_Rep_Item (U_Ent, N);
3279 end if;
3280
3281 return;
3282 end if;
3283
3284 if Duplicate_Clause then
3285 null;
3286
3287 -- Case of address clause for subprogram
3288
3289 elsif Is_Subprogram (U_Ent) then
3290 if Has_Homonym (U_Ent) then
3291 Error_Msg_N
3292 ("address clause cannot be given " &
3293 "for overloaded subprogram",
3294 Nam);
3295 return;
3296 end if;
3297
3298 -- For subprograms, all address clauses are permitted, and we
3299 -- mark the subprogram as having a deferred freeze so that Gigi
3300 -- will not elaborate it too soon.
3301
3302 -- Above needs more comments, what is too soon about???
3303
3304 Set_Has_Delayed_Freeze (U_Ent);
3305
3306 -- Case of address clause for entry
3307
3308 elsif Ekind (U_Ent) = E_Entry then
3309 if Nkind (Parent (N)) = N_Task_Body then
3310 Error_Msg_N
3311 ("entry address must be specified in task spec", Nam);
3312 return;
3313 end if;
3314
3315 -- For entries, we require a constant address
3316
3317 Check_Constant_Address_Clause (Expr, U_Ent);
3318
3319 -- Special checks for task types
3320
3321 if Is_Task_Type (Scope (U_Ent))
3322 and then Comes_From_Source (Scope (U_Ent))
3323 then
3324 Error_Msg_N
3325 ("??entry address declared for entry in task type", N);
3326 Error_Msg_N
3327 ("\??only one task can be declared of this type", N);
3328 end if;
3329
3330 -- Entry address clauses are obsolescent
3331
3332 Check_Restriction (No_Obsolescent_Features, N);
3333
3334 if Warn_On_Obsolescent_Feature then
3335 Error_Msg_N
3336 ("?j?attaching interrupt to task entry is an " &
3337 "obsolescent feature (RM J.7.1)", N);
3338 Error_Msg_N
3339 ("\?j?use interrupt procedure instead", N);
3340 end if;
3341
3342 -- Case of an address clause for a controlled object which we
3343 -- consider to be erroneous.
3344
3345 elsif Is_Controlled (Etype (U_Ent))
3346 or else Has_Controlled_Component (Etype (U_Ent))
3347 then
3348 Error_Msg_NE
3349 ("??controlled object& must not be overlaid", Nam, U_Ent);
3350 Error_Msg_N
3351 ("\??Program_Error will be raised at run time", Nam);
3352 Insert_Action (Declaration_Node (U_Ent),
3353 Make_Raise_Program_Error (Loc,
3354 Reason => PE_Overlaid_Controlled_Object));
3355 return;
3356
3357 -- Case of address clause for a (non-controlled) object
3358
3359 elsif
3360 Ekind (U_Ent) = E_Variable
3361 or else
3362 Ekind (U_Ent) = E_Constant
3363 then
3364 declare
3365 Expr : constant Node_Id := Expression (N);
3366 O_Ent : Entity_Id;
3367 Off : Boolean;
3368
3369 begin
3370 -- Exported variables cannot have an address clause, because
3371 -- this cancels the effect of the pragma Export.
3372
3373 if Is_Exported (U_Ent) then
3374 Error_Msg_N
3375 ("cannot export object with address clause", Nam);
3376 return;
3377 end if;
3378
3379 Find_Overlaid_Entity (N, O_Ent, Off);
3380
3381 -- Overlaying controlled objects is erroneous
3382
3383 if Present (O_Ent)
3384 and then (Has_Controlled_Component (Etype (O_Ent))
3385 or else Is_Controlled (Etype (O_Ent)))
3386 then
3387 Error_Msg_N
3388 ("??cannot overlay with controlled object", Expr);
3389 Error_Msg_N
3390 ("\??Program_Error will be raised at run time", Expr);
3391 Insert_Action (Declaration_Node (U_Ent),
3392 Make_Raise_Program_Error (Loc,
3393 Reason => PE_Overlaid_Controlled_Object));
3394 return;
3395
3396 elsif Present (O_Ent)
3397 and then Ekind (U_Ent) = E_Constant
3398 and then not Is_Constant_Object (O_Ent)
3399 then
3400 Error_Msg_N ("??constant overlays a variable", Expr);
3401
3402 -- Imported variables can have an address clause, but then
3403 -- the import is pretty meaningless except to suppress
3404 -- initializations, so we do not need such variables to
3405 -- be statically allocated (and in fact it causes trouble
3406 -- if the address clause is a local value).
3407
3408 elsif Is_Imported (U_Ent) then
3409 Set_Is_Statically_Allocated (U_Ent, False);
3410 end if;
3411
3412 -- We mark a possible modification of a variable with an
3413 -- address clause, since it is likely aliasing is occurring.
3414
3415 Note_Possible_Modification (Nam, Sure => False);
3416
3417 -- Here we are checking for explicit overlap of one variable
3418 -- by another, and if we find this then mark the overlapped
3419 -- variable as also being volatile to prevent unwanted
3420 -- optimizations. This is a significant pessimization so
3421 -- avoid it when there is an offset, i.e. when the object
3422 -- is composite; they cannot be optimized easily anyway.
3423
3424 if Present (O_Ent)
3425 and then Is_Object (O_Ent)
3426 and then not Off
3427
3428 -- The following test is an expedient solution to what
3429 -- is really a problem in CodePeer. Suppressing the
3430 -- Set_Treat_As_Volatile call here prevents later
3431 -- generation (in some cases) of trees that CodePeer
3432 -- should, but currently does not, handle correctly.
3433 -- This test should probably be removed when CodePeer
3434 -- is improved, just because we want the tree CodePeer
3435 -- analyzes to match the tree for which we generate code
3436 -- as closely as is practical. ???
3437
3438 and then not CodePeer_Mode
3439 then
3440 -- ??? O_Ent might not be in current unit
3441
3442 Set_Treat_As_Volatile (O_Ent);
3443 end if;
3444
3445 -- Legality checks on the address clause for initialized
3446 -- objects is deferred until the freeze point, because
3447 -- a subsequent pragma might indicate that the object
3448 -- is imported and thus not initialized. Also, the address
3449 -- clause might involve entities that have yet to be
3450 -- elaborated.
3451
3452 Set_Has_Delayed_Freeze (U_Ent);
3453
3454 -- If an initialization call has been generated for this
3455 -- object, it needs to be deferred to after the freeze node
3456 -- we have just now added, otherwise GIGI will see a
3457 -- reference to the variable (as actual to the IP call)
3458 -- before its definition.
3459
3460 declare
3461 Init_Call : constant Node_Id :=
3462 Remove_Init_Call (U_Ent, N);
3463
3464 begin
3465 if Present (Init_Call) then
3466
3467 -- If the init call is an expression with actions with
3468 -- null expression, just extract the actions.
3469
3470 if Nkind (Init_Call) = N_Expression_With_Actions
3471 and then
3472 Nkind (Expression (Init_Call)) = N_Null_Statement
3473 then
3474 Append_Freeze_Actions (U_Ent, Actions (Init_Call));
3475
3476 -- General case: move Init_Call to freeze actions
3477
3478 else
3479 Append_Freeze_Action (U_Ent, Init_Call);
3480 end if;
3481 end if;
3482 end;
3483
3484 if Is_Exported (U_Ent) then
3485 Error_Msg_N
3486 ("& cannot be exported if an address clause is given",
3487 Nam);
3488 Error_Msg_N
3489 ("\define and export a variable "
3490 & "that holds its address instead", Nam);
3491 end if;
3492
3493 -- Entity has delayed freeze, so we will generate an
3494 -- alignment check at the freeze point unless suppressed.
3495
3496 if not Range_Checks_Suppressed (U_Ent)
3497 and then not Alignment_Checks_Suppressed (U_Ent)
3498 then
3499 Set_Check_Address_Alignment (N);
3500 end if;
3501
3502 -- Kill the size check code, since we are not allocating
3503 -- the variable, it is somewhere else.
3504
3505 Kill_Size_Check_Code (U_Ent);
3506
3507 -- If the address clause is of the form:
3508
3509 -- for Y'Address use X'Address
3510
3511 -- or
3512
3513 -- Const : constant Address := X'Address;
3514 -- ...
3515 -- for Y'Address use Const;
3516
3517 -- then we make an entry in the table for checking the size
3518 -- and alignment of the overlaying variable. We defer this
3519 -- check till after code generation to take full advantage
3520 -- of the annotation done by the back end.
3521
3522 -- If the entity has a generic type, the check will be
3523 -- performed in the instance if the actual type justifies
3524 -- it, and we do not insert the clause in the table to
3525 -- prevent spurious warnings.
3526
3527 -- Note: we used to test Comes_From_Source and only give
3528 -- this warning for source entities, but we have removed
3529 -- this test. It really seems bogus to generate overlays
3530 -- that would trigger this warning in generated code.
3531 -- Furthermore, by removing the test, we handle the
3532 -- aspect case properly.
3533
3534 if Address_Clause_Overlay_Warnings
3535 and then Present (O_Ent)
3536 and then Is_Object (O_Ent)
3537 then
3538 if not Is_Generic_Type (Etype (U_Ent)) then
3539 Address_Clause_Checks.Append ((N, U_Ent, O_Ent, Off));
3540 end if;
3541
3542 -- If variable overlays a constant view, and we are
3543 -- warning on overlays, then mark the variable as
3544 -- overlaying a constant (we will give warnings later
3545 -- if this variable is assigned).
3546
3547 if Is_Constant_Object (O_Ent)
3548 and then Ekind (U_Ent) = E_Variable
3549 then
3550 Set_Overlays_Constant (U_Ent);
3551 end if;
3552 end if;
3553 end;
3554
3555 -- Not a valid entity for an address clause
3556
3557 else
3558 Error_Msg_N ("address cannot be given for &", Nam);
3559 end if;
3560 end Address;
3561
3562 ---------------
3563 -- Alignment --
3564 ---------------
3565
3566 -- Alignment attribute definition clause
3567
3568 when Attribute_Alignment => Alignment : declare
3569 Align : constant Uint := Get_Alignment_Value (Expr);
3570 Max_Align : constant Uint := UI_From_Int (Maximum_Alignment);
3571
3572 begin
3573 FOnly := True;
3574
3575 if not Is_Type (U_Ent)
3576 and then Ekind (U_Ent) /= E_Variable
3577 and then Ekind (U_Ent) /= E_Constant
3578 then
3579 Error_Msg_N ("alignment cannot be given for &", Nam);
3580
3581 elsif Duplicate_Clause then
3582 null;
3583
3584 elsif Align /= No_Uint then
3585 Set_Has_Alignment_Clause (U_Ent);
3586
3587 -- Tagged type case, check for attempt to set alignment to a
3588 -- value greater than Max_Align, and reset if so.
3589
3590 if Is_Tagged_Type (U_Ent) and then Align > Max_Align then
3591 Error_Msg_N
3592 ("alignment for & set to Maximum_Aligment??", Nam);
3593 Set_Alignment (U_Ent, Max_Align);
3594
3595 -- All other cases
3596
3597 else
3598 Set_Alignment (U_Ent, Align);
3599 end if;
3600
3601 -- For an array type, U_Ent is the first subtype. In that case,
3602 -- also set the alignment of the anonymous base type so that
3603 -- other subtypes (such as the itypes for aggregates of the
3604 -- type) also receive the expected alignment.
3605
3606 if Is_Array_Type (U_Ent) then
3607 Set_Alignment (Base_Type (U_Ent), Align);
3608 end if;
3609 end if;
3610 end Alignment;
3611
3612 ---------------
3613 -- Bit_Order --
3614 ---------------
3615
3616 -- Bit_Order attribute definition clause
3617
3618 when Attribute_Bit_Order => Bit_Order : declare
3619 begin
3620 if not Is_Record_Type (U_Ent) then
3621 Error_Msg_N
3622 ("Bit_Order can only be defined for record type", Nam);
3623
3624 elsif Duplicate_Clause then
3625 null;
3626
3627 else
3628 Analyze_And_Resolve (Expr, RTE (RE_Bit_Order));
3629
3630 if Etype (Expr) = Any_Type then
3631 return;
3632
3633 elsif not Is_Static_Expression (Expr) then
3634 Flag_Non_Static_Expr
3635 ("Bit_Order requires static expression!", Expr);
3636
3637 else
3638 if (Expr_Value (Expr) = 0) /= Bytes_Big_Endian then
3639 Set_Reverse_Bit_Order (U_Ent, True);
3640 end if;
3641 end if;
3642 end if;
3643 end Bit_Order;
3644
3645 --------------------
3646 -- Component_Size --
3647 --------------------
3648
3649 -- Component_Size attribute definition clause
3650
3651 when Attribute_Component_Size => Component_Size_Case : declare
3652 Csize : constant Uint := Static_Integer (Expr);
3653 Ctyp : Entity_Id;
3654 Btype : Entity_Id;
3655 Biased : Boolean;
3656 New_Ctyp : Entity_Id;
3657 Decl : Node_Id;
3658
3659 begin
3660 if not Is_Array_Type (U_Ent) then
3661 Error_Msg_N ("component size requires array type", Nam);
3662 return;
3663 end if;
3664
3665 Btype := Base_Type (U_Ent);
3666 Ctyp := Component_Type (Btype);
3667
3668 if Duplicate_Clause then
3669 null;
3670
3671 elsif Rep_Item_Too_Early (Btype, N) then
3672 null;
3673
3674 elsif Csize /= No_Uint then
3675 Check_Size (Expr, Ctyp, Csize, Biased);
3676
3677 -- For the biased case, build a declaration for a subtype that
3678 -- will be used to represent the biased subtype that reflects
3679 -- the biased representation of components. We need the subtype
3680 -- to get proper conversions on referencing elements of the
3681 -- array. Note: component size clauses are ignored in VM mode.
3682
3683 if VM_Target = No_VM then
3684 if Biased then
3685 New_Ctyp :=
3686 Make_Defining_Identifier (Loc,
3687 Chars =>
3688 New_External_Name (Chars (U_Ent), 'C', 0, 'T'));
3689
3690 Decl :=
3691 Make_Subtype_Declaration (Loc,
3692 Defining_Identifier => New_Ctyp,
3693 Subtype_Indication =>
3694 New_Occurrence_Of (Component_Type (Btype), Loc));
3695
3696 Set_Parent (Decl, N);
3697 Analyze (Decl, Suppress => All_Checks);
3698
3699 Set_Has_Delayed_Freeze (New_Ctyp, False);
3700 Set_Esize (New_Ctyp, Csize);
3701 Set_RM_Size (New_Ctyp, Csize);
3702 Init_Alignment (New_Ctyp);
3703 Set_Is_Itype (New_Ctyp, True);
3704 Set_Associated_Node_For_Itype (New_Ctyp, U_Ent);
3705
3706 Set_Component_Type (Btype, New_Ctyp);
3707 Set_Biased (New_Ctyp, N, "component size clause");
3708 end if;
3709
3710 Set_Component_Size (Btype, Csize);
3711
3712 -- For VM case, we ignore component size clauses
3713
3714 else
3715 -- Give a warning unless we are in GNAT mode, in which case
3716 -- the warning is suppressed since it is not useful.
3717
3718 if not GNAT_Mode then
3719 Error_Msg_N
3720 ("component size ignored in this configuration??", N);
3721 end if;
3722 end if;
3723
3724 -- Deal with warning on overridden size
3725
3726 if Warn_On_Overridden_Size
3727 and then Has_Size_Clause (Ctyp)
3728 and then RM_Size (Ctyp) /= Csize
3729 then
3730 Error_Msg_NE
3731 ("component size overrides size clause for&?S?", N, Ctyp);
3732 end if;
3733
3734 Set_Has_Component_Size_Clause (Btype, True);
3735 Set_Has_Non_Standard_Rep (Btype, True);
3736 end if;
3737 end Component_Size_Case;
3738
3739 -----------------------
3740 -- Constant_Indexing --
3741 -----------------------
3742
3743 when Attribute_Constant_Indexing =>
3744 Check_Indexing_Functions;
3745
3746 ---------
3747 -- CPU --
3748 ---------
3749
3750 when Attribute_CPU => CPU :
3751 begin
3752 -- CPU attribute definition clause not allowed except from aspect
3753 -- specification.
3754
3755 if From_Aspect_Specification (N) then
3756 if not Is_Task_Type (U_Ent) then
3757 Error_Msg_N ("CPU can only be defined for task", Nam);
3758
3759 elsif Duplicate_Clause then
3760 null;
3761
3762 else
3763 -- The expression must be analyzed in the special manner
3764 -- described in "Handling of Default and Per-Object
3765 -- Expressions" in sem.ads.
3766
3767 -- The visibility to the discriminants must be restored
3768
3769 Push_Scope_And_Install_Discriminants (U_Ent);
3770 Preanalyze_Spec_Expression (Expr, RTE (RE_CPU_Range));
3771 Uninstall_Discriminants_And_Pop_Scope (U_Ent);
3772
3773 if not Is_Static_Expression (Expr) then
3774 Check_Restriction (Static_Priorities, Expr);
3775 end if;
3776 end if;
3777
3778 else
3779 Error_Msg_N
3780 ("attribute& cannot be set with definition clause", N);
3781 end if;
3782 end CPU;
3783
3784 ----------------------
3785 -- Default_Iterator --
3786 ----------------------
3787
3788 when Attribute_Default_Iterator => Default_Iterator : declare
3789 Func : Entity_Id;
3790
3791 begin
3792 if not Is_Tagged_Type (U_Ent) then
3793 Error_Msg_N
3794 ("aspect Default_Iterator applies to tagged type", Nam);
3795 end if;
3796
3797 Check_Iterator_Functions;
3798
3799 Analyze (Expr);
3800
3801 if not Is_Entity_Name (Expr)
3802 or else Ekind (Entity (Expr)) /= E_Function
3803 then
3804 Error_Msg_N ("aspect Iterator must be a function", Expr);
3805 else
3806 Func := Entity (Expr);
3807 end if;
3808
3809 if No (First_Formal (Func))
3810 or else Etype (First_Formal (Func)) /= U_Ent
3811 then
3812 Error_Msg_NE
3813 ("Default Iterator must be a primitive of&", Func, U_Ent);
3814 end if;
3815 end Default_Iterator;
3816
3817 ------------------------
3818 -- Dispatching_Domain --
3819 ------------------------
3820
3821 when Attribute_Dispatching_Domain => Dispatching_Domain :
3822 begin
3823 -- Dispatching_Domain attribute definition clause not allowed
3824 -- except from aspect specification.
3825
3826 if From_Aspect_Specification (N) then
3827 if not Is_Task_Type (U_Ent) then
3828 Error_Msg_N ("Dispatching_Domain can only be defined" &
3829 "for task",
3830 Nam);
3831
3832 elsif Duplicate_Clause then
3833 null;
3834
3835 else
3836 -- The expression must be analyzed in the special manner
3837 -- described in "Handling of Default and Per-Object
3838 -- Expressions" in sem.ads.
3839
3840 -- The visibility to the discriminants must be restored
3841
3842 Push_Scope_And_Install_Discriminants (U_Ent);
3843
3844 Preanalyze_Spec_Expression
3845 (Expr, RTE (RE_Dispatching_Domain));
3846
3847 Uninstall_Discriminants_And_Pop_Scope (U_Ent);
3848 end if;
3849
3850 else
3851 Error_Msg_N
3852 ("attribute& cannot be set with definition clause", N);
3853 end if;
3854 end Dispatching_Domain;
3855
3856 ------------------
3857 -- External_Tag --
3858 ------------------
3859
3860 when Attribute_External_Tag => External_Tag :
3861 begin
3862 if not Is_Tagged_Type (U_Ent) then
3863 Error_Msg_N ("should be a tagged type", Nam);
3864 end if;
3865
3866 if Duplicate_Clause then
3867 null;
3868
3869 else
3870 Analyze_And_Resolve (Expr, Standard_String);
3871
3872 if not Is_Static_Expression (Expr) then
3873 Flag_Non_Static_Expr
3874 ("static string required for tag name!", Nam);
3875 end if;
3876
3877 if VM_Target = No_VM then
3878 Set_Has_External_Tag_Rep_Clause (U_Ent);
3879 else
3880 Error_Msg_Name_1 := Attr;
3881 Error_Msg_N
3882 ("% attribute unsupported in this configuration", Nam);
3883 end if;
3884
3885 if not Is_Library_Level_Entity (U_Ent) then
3886 Error_Msg_NE
3887 ("??non-unique external tag supplied for &", N, U_Ent);
3888 Error_Msg_N
3889 ("\??same external tag applies to all "
3890 & "subprogram calls", N);
3891 Error_Msg_N
3892 ("\??corresponding internal tag cannot be obtained", N);
3893 end if;
3894 end if;
3895 end External_Tag;
3896
3897 --------------------------
3898 -- Implicit_Dereference --
3899 --------------------------
3900
3901 when Attribute_Implicit_Dereference =>
3902
3903 -- Legality checks already performed at the point of the type
3904 -- declaration, aspect is not delayed.
3905
3906 null;
3907
3908 -----------
3909 -- Input --
3910 -----------
3911
3912 when Attribute_Input =>
3913 Analyze_Stream_TSS_Definition (TSS_Stream_Input);
3914 Set_Has_Specified_Stream_Input (Ent);
3915
3916 ------------------------
3917 -- Interrupt_Priority --
3918 ------------------------
3919
3920 when Attribute_Interrupt_Priority => Interrupt_Priority :
3921 begin
3922 -- Interrupt_Priority attribute definition clause not allowed
3923 -- except from aspect specification.
3924
3925 if From_Aspect_Specification (N) then
3926 if not (Is_Protected_Type (U_Ent)
3927 or else Is_Task_Type (U_Ent))
3928 then
3929 Error_Msg_N
3930 ("Interrupt_Priority can only be defined for task" &
3931 "and protected object",
3932 Nam);
3933
3934 elsif Duplicate_Clause then
3935 null;
3936
3937 else
3938 -- The expression must be analyzed in the special manner
3939 -- described in "Handling of Default and Per-Object
3940 -- Expressions" in sem.ads.
3941
3942 -- The visibility to the discriminants must be restored
3943
3944 Push_Scope_And_Install_Discriminants (U_Ent);
3945
3946 Preanalyze_Spec_Expression
3947 (Expr, RTE (RE_Interrupt_Priority));
3948
3949 Uninstall_Discriminants_And_Pop_Scope (U_Ent);
3950 end if;
3951
3952 else
3953 Error_Msg_N
3954 ("attribute& cannot be set with definition clause", N);
3955 end if;
3956 end Interrupt_Priority;
3957
3958 ----------------------
3959 -- Iterator_Element --
3960 ----------------------
3961
3962 when Attribute_Iterator_Element =>
3963 Analyze (Expr);
3964
3965 if not Is_Entity_Name (Expr)
3966 or else not Is_Type (Entity (Expr))
3967 then
3968 Error_Msg_N ("aspect Iterator_Element must be a type", Expr);
3969 end if;
3970
3971 -------------------
3972 -- Machine_Radix --
3973 -------------------
3974
3975 -- Machine radix attribute definition clause
3976
3977 when Attribute_Machine_Radix => Machine_Radix : declare
3978 Radix : constant Uint := Static_Integer (Expr);
3979
3980 begin
3981 if not Is_Decimal_Fixed_Point_Type (U_Ent) then
3982 Error_Msg_N ("decimal fixed-point type expected for &", Nam);
3983
3984 elsif Duplicate_Clause then
3985 null;
3986
3987 elsif Radix /= No_Uint then
3988 Set_Has_Machine_Radix_Clause (U_Ent);
3989 Set_Has_Non_Standard_Rep (Base_Type (U_Ent));
3990
3991 if Radix = 2 then
3992 null;
3993 elsif Radix = 10 then
3994 Set_Machine_Radix_10 (U_Ent);
3995 else
3996 Error_Msg_N ("machine radix value must be 2 or 10", Expr);
3997 end if;
3998 end if;
3999 end Machine_Radix;
4000
4001 -----------------
4002 -- Object_Size --
4003 -----------------
4004
4005 -- Object_Size attribute definition clause
4006
4007 when Attribute_Object_Size => Object_Size : declare
4008 Size : constant Uint := Static_Integer (Expr);
4009
4010 Biased : Boolean;
4011 pragma Warnings (Off, Biased);
4012
4013 begin
4014 if not Is_Type (U_Ent) then
4015 Error_Msg_N ("Object_Size cannot be given for &", Nam);
4016
4017 elsif Duplicate_Clause then
4018 null;
4019
4020 else
4021 Check_Size (Expr, U_Ent, Size, Biased);
4022
4023 if Size /= 8
4024 and then
4025 Size /= 16
4026 and then
4027 Size /= 32
4028 and then
4029 UI_Mod (Size, 64) /= 0
4030 then
4031 Error_Msg_N
4032 ("Object_Size must be 8, 16, 32, or multiple of 64",
4033 Expr);
4034 end if;
4035
4036 Set_Esize (U_Ent, Size);
4037 Set_Has_Object_Size_Clause (U_Ent);
4038 Alignment_Check_For_Size_Change (U_Ent, Size);
4039 end if;
4040 end Object_Size;
4041
4042 ------------
4043 -- Output --
4044 ------------
4045
4046 when Attribute_Output =>
4047 Analyze_Stream_TSS_Definition (TSS_Stream_Output);
4048 Set_Has_Specified_Stream_Output (Ent);
4049
4050 --------------
4051 -- Priority --
4052 --------------
4053
4054 when Attribute_Priority => Priority :
4055 begin
4056 -- Priority attribute definition clause not allowed except from
4057 -- aspect specification.
4058
4059 if From_Aspect_Specification (N) then
4060 if not (Is_Protected_Type (U_Ent)
4061 or else Is_Task_Type (U_Ent)
4062 or else Ekind (U_Ent) = E_Procedure)
4063 then
4064 Error_Msg_N
4065 ("Priority can only be defined for task and protected " &
4066 "object",
4067 Nam);
4068
4069 elsif Duplicate_Clause then
4070 null;
4071
4072 else
4073 -- The expression must be analyzed in the special manner
4074 -- described in "Handling of Default and Per-Object
4075 -- Expressions" in sem.ads.
4076
4077 -- The visibility to the discriminants must be restored
4078
4079 Push_Scope_And_Install_Discriminants (U_Ent);
4080 Preanalyze_Spec_Expression (Expr, Standard_Integer);
4081 Uninstall_Discriminants_And_Pop_Scope (U_Ent);
4082
4083 if not Is_Static_Expression (Expr) then
4084 Check_Restriction (Static_Priorities, Expr);
4085 end if;
4086 end if;
4087
4088 else
4089 Error_Msg_N
4090 ("attribute& cannot be set with definition clause", N);
4091 end if;
4092 end Priority;
4093
4094 ----------
4095 -- Read --
4096 ----------
4097
4098 when Attribute_Read =>
4099 Analyze_Stream_TSS_Definition (TSS_Stream_Read);
4100 Set_Has_Specified_Stream_Read (Ent);
4101
4102 --------------------------
4103 -- Scalar_Storage_Order --
4104 --------------------------
4105
4106 -- Scalar_Storage_Order attribute definition clause
4107
4108 when Attribute_Scalar_Storage_Order => Scalar_Storage_Order : declare
4109 begin
4110 if not (Is_Record_Type (U_Ent) or else Is_Array_Type (U_Ent)) then
4111 Error_Msg_N
4112 ("Scalar_Storage_Order can only be defined for "
4113 & "record or array type", Nam);
4114
4115 elsif Duplicate_Clause then
4116 null;
4117
4118 else
4119 Analyze_And_Resolve (Expr, RTE (RE_Bit_Order));
4120
4121 if Etype (Expr) = Any_Type then
4122 return;
4123
4124 elsif not Is_Static_Expression (Expr) then
4125 Flag_Non_Static_Expr
4126 ("Scalar_Storage_Order requires static expression!", Expr);
4127
4128 elsif (Expr_Value (Expr) = 0) /= Bytes_Big_Endian then
4129
4130 -- Here for the case of a non-default (i.e. non-confirming)
4131 -- Scalar_Storage_Order attribute definition.
4132
4133 if Support_Nondefault_SSO_On_Target then
4134 Set_Reverse_Storage_Order (Base_Type (U_Ent), True);
4135 else
4136 Error_Msg_N
4137 ("non-default Scalar_Storage_Order "
4138 & "not supported on target", Expr);
4139 end if;
4140 end if;
4141 end if;
4142 end Scalar_Storage_Order;
4143
4144 ----------
4145 -- Size --
4146 ----------
4147
4148 -- Size attribute definition clause
4149
4150 when Attribute_Size => Size : declare
4151 Size : constant Uint := Static_Integer (Expr);
4152 Etyp : Entity_Id;
4153 Biased : Boolean;
4154
4155 begin
4156 FOnly := True;
4157
4158 if Duplicate_Clause then
4159 null;
4160
4161 elsif not Is_Type (U_Ent)
4162 and then Ekind (U_Ent) /= E_Variable
4163 and then Ekind (U_Ent) /= E_Constant
4164 then
4165 Error_Msg_N ("size cannot be given for &", Nam);
4166
4167 elsif Is_Array_Type (U_Ent)
4168 and then not Is_Constrained (U_Ent)
4169 then
4170 Error_Msg_N
4171 ("size cannot be given for unconstrained array", Nam);
4172
4173 elsif Size /= No_Uint then
4174 if VM_Target /= No_VM and then not GNAT_Mode then
4175
4176 -- Size clause is not handled properly on VM targets.
4177 -- Display a warning unless we are in GNAT mode, in which
4178 -- case this is useless.
4179
4180 Error_Msg_N
4181 ("size clauses are ignored in this configuration??", N);
4182 end if;
4183
4184 if Is_Type (U_Ent) then
4185 Etyp := U_Ent;
4186 else
4187 Etyp := Etype (U_Ent);
4188 end if;
4189
4190 -- Check size, note that Gigi is in charge of checking that the
4191 -- size of an array or record type is OK. Also we do not check
4192 -- the size in the ordinary fixed-point case, since it is too
4193 -- early to do so (there may be subsequent small clause that
4194 -- affects the size). We can check the size if a small clause
4195 -- has already been given.
4196
4197 if not Is_Ordinary_Fixed_Point_Type (U_Ent)
4198 or else Has_Small_Clause (U_Ent)
4199 then
4200 Check_Size (Expr, Etyp, Size, Biased);
4201 Set_Biased (U_Ent, N, "size clause", Biased);
4202 end if;
4203
4204 -- For types set RM_Size and Esize if possible
4205
4206 if Is_Type (U_Ent) then
4207 Set_RM_Size (U_Ent, Size);
4208
4209 -- For elementary types, increase Object_Size to power of 2,
4210 -- but not less than a storage unit in any case (normally
4211 -- this means it will be byte addressable).
4212
4213 -- For all other types, nothing else to do, we leave Esize
4214 -- (object size) unset, the back end will set it from the
4215 -- size and alignment in an appropriate manner.
4216
4217 -- In both cases, we check whether the alignment must be
4218 -- reset in the wake of the size change.
4219
4220 if Is_Elementary_Type (U_Ent) then
4221 if Size <= System_Storage_Unit then
4222 Init_Esize (U_Ent, System_Storage_Unit);
4223 elsif Size <= 16 then
4224 Init_Esize (U_Ent, 16);
4225 elsif Size <= 32 then
4226 Init_Esize (U_Ent, 32);
4227 else
4228 Set_Esize (U_Ent, (Size + 63) / 64 * 64);
4229 end if;
4230
4231 Alignment_Check_For_Size_Change (U_Ent, Esize (U_Ent));
4232 else
4233 Alignment_Check_For_Size_Change (U_Ent, Size);
4234 end if;
4235
4236 -- For objects, set Esize only
4237
4238 else
4239 if Is_Elementary_Type (Etyp) then
4240 if Size /= System_Storage_Unit
4241 and then
4242 Size /= System_Storage_Unit * 2
4243 and then
4244 Size /= System_Storage_Unit * 4
4245 and then
4246 Size /= System_Storage_Unit * 8
4247 then
4248 Error_Msg_Uint_1 := UI_From_Int (System_Storage_Unit);
4249 Error_Msg_Uint_2 := Error_Msg_Uint_1 * 8;
4250 Error_Msg_N
4251 ("size for primitive object must be a power of 2"
4252 & " in the range ^-^", N);
4253 end if;
4254 end if;
4255
4256 Set_Esize (U_Ent, Size);
4257 end if;
4258
4259 Set_Has_Size_Clause (U_Ent);
4260 end if;
4261 end Size;
4262
4263 -----------
4264 -- Small --
4265 -----------
4266
4267 -- Small attribute definition clause
4268
4269 when Attribute_Small => Small : declare
4270 Implicit_Base : constant Entity_Id := Base_Type (U_Ent);
4271 Small : Ureal;
4272
4273 begin
4274 Analyze_And_Resolve (Expr, Any_Real);
4275
4276 if Etype (Expr) = Any_Type then
4277 return;
4278
4279 elsif not Is_Static_Expression (Expr) then
4280 Flag_Non_Static_Expr
4281 ("small requires static expression!", Expr);
4282 return;
4283
4284 else
4285 Small := Expr_Value_R (Expr);
4286
4287 if Small <= Ureal_0 then
4288 Error_Msg_N ("small value must be greater than zero", Expr);
4289 return;
4290 end if;
4291
4292 end if;
4293
4294 if not Is_Ordinary_Fixed_Point_Type (U_Ent) then
4295 Error_Msg_N
4296 ("small requires an ordinary fixed point type", Nam);
4297
4298 elsif Has_Small_Clause (U_Ent) then
4299 Error_Msg_N ("small already given for &", Nam);
4300
4301 elsif Small > Delta_Value (U_Ent) then
4302 Error_Msg_N
4303 ("small value must not be greater than delta value", Nam);
4304
4305 else
4306 Set_Small_Value (U_Ent, Small);
4307 Set_Small_Value (Implicit_Base, Small);
4308 Set_Has_Small_Clause (U_Ent);
4309 Set_Has_Small_Clause (Implicit_Base);
4310 Set_Has_Non_Standard_Rep (Implicit_Base);
4311 end if;
4312 end Small;
4313
4314 ------------------
4315 -- Storage_Pool --
4316 ------------------
4317
4318 -- Storage_Pool attribute definition clause
4319
4320 when Attribute_Storage_Pool | Attribute_Simple_Storage_Pool => declare
4321 Pool : Entity_Id;
4322 T : Entity_Id;
4323
4324 begin
4325 if Ekind (U_Ent) = E_Access_Subprogram_Type then
4326 Error_Msg_N
4327 ("storage pool cannot be given for access-to-subprogram type",
4328 Nam);
4329 return;
4330
4331 elsif not
4332 Ekind_In (U_Ent, E_Access_Type, E_General_Access_Type)
4333 then
4334 Error_Msg_N
4335 ("storage pool can only be given for access types", Nam);
4336 return;
4337
4338 elsif Is_Derived_Type (U_Ent) then
4339 Error_Msg_N
4340 ("storage pool cannot be given for a derived access type",
4341 Nam);
4342
4343 elsif Duplicate_Clause then
4344 return;
4345
4346 elsif Present (Associated_Storage_Pool (U_Ent)) then
4347 Error_Msg_N ("storage pool already given for &", Nam);
4348 return;
4349 end if;
4350
4351 if Id = Attribute_Storage_Pool then
4352 Analyze_And_Resolve
4353 (Expr, Class_Wide_Type (RTE (RE_Root_Storage_Pool)));
4354
4355 -- In the Simple_Storage_Pool case, we allow a variable of any
4356 -- simple storage pool type, so we Resolve without imposing an
4357 -- expected type.
4358
4359 else
4360 Analyze_And_Resolve (Expr);
4361
4362 if not Present (Get_Rep_Pragma
4363 (Etype (Expr), Name_Simple_Storage_Pool_Type))
4364 then
4365 Error_Msg_N
4366 ("expression must be of a simple storage pool type", Expr);
4367 end if;
4368 end if;
4369
4370 if not Denotes_Variable (Expr) then
4371 Error_Msg_N ("storage pool must be a variable", Expr);
4372 return;
4373 end if;
4374
4375 if Nkind (Expr) = N_Type_Conversion then
4376 T := Etype (Expression (Expr));
4377 else
4378 T := Etype (Expr);
4379 end if;
4380
4381 -- The Stack_Bounded_Pool is used internally for implementing
4382 -- access types with a Storage_Size. Since it only work properly
4383 -- when used on one specific type, we need to check that it is not
4384 -- hijacked improperly:
4385
4386 -- type T is access Integer;
4387 -- for T'Storage_Size use n;
4388 -- type Q is access Float;
4389 -- for Q'Storage_Size use T'Storage_Size; -- incorrect
4390
4391 if RTE_Available (RE_Stack_Bounded_Pool)
4392 and then Base_Type (T) = RTE (RE_Stack_Bounded_Pool)
4393 then
4394 Error_Msg_N ("non-shareable internal Pool", Expr);
4395 return;
4396 end if;
4397
4398 -- If the argument is a name that is not an entity name, then
4399 -- we construct a renaming operation to define an entity of
4400 -- type storage pool.
4401
4402 if not Is_Entity_Name (Expr)
4403 and then Is_Object_Reference (Expr)
4404 then
4405 Pool := Make_Temporary (Loc, 'P', Expr);
4406
4407 declare
4408 Rnode : constant Node_Id :=
4409 Make_Object_Renaming_Declaration (Loc,
4410 Defining_Identifier => Pool,
4411 Subtype_Mark =>
4412 New_Occurrence_Of (Etype (Expr), Loc),
4413 Name => Expr);
4414
4415 begin
4416 -- If the attribute definition clause comes from an aspect
4417 -- clause, then insert the renaming before the associated
4418 -- entity's declaration, since the attribute clause has
4419 -- not yet been appended to the declaration list.
4420
4421 if From_Aspect_Specification (N) then
4422 Insert_Before (Parent (Entity (N)), Rnode);
4423 else
4424 Insert_Before (N, Rnode);
4425 end if;
4426
4427 Analyze (Rnode);
4428 Set_Associated_Storage_Pool (U_Ent, Pool);
4429 end;
4430
4431 elsif Is_Entity_Name (Expr) then
4432 Pool := Entity (Expr);
4433
4434 -- If pool is a renamed object, get original one. This can
4435 -- happen with an explicit renaming, and within instances.
4436
4437 while Present (Renamed_Object (Pool))
4438 and then Is_Entity_Name (Renamed_Object (Pool))
4439 loop
4440 Pool := Entity (Renamed_Object (Pool));
4441 end loop;
4442
4443 if Present (Renamed_Object (Pool))
4444 and then Nkind (Renamed_Object (Pool)) = N_Type_Conversion
4445 and then Is_Entity_Name (Expression (Renamed_Object (Pool)))
4446 then
4447 Pool := Entity (Expression (Renamed_Object (Pool)));
4448 end if;
4449
4450 Set_Associated_Storage_Pool (U_Ent, Pool);
4451
4452 elsif Nkind (Expr) = N_Type_Conversion
4453 and then Is_Entity_Name (Expression (Expr))
4454 and then Nkind (Original_Node (Expr)) = N_Attribute_Reference
4455 then
4456 Pool := Entity (Expression (Expr));
4457 Set_Associated_Storage_Pool (U_Ent, Pool);
4458
4459 else
4460 Error_Msg_N ("incorrect reference to a Storage Pool", Expr);
4461 return;
4462 end if;
4463 end;
4464
4465 ------------------
4466 -- Storage_Size --
4467 ------------------
4468
4469 -- Storage_Size attribute definition clause
4470
4471 when Attribute_Storage_Size => Storage_Size : declare
4472 Btype : constant Entity_Id := Base_Type (U_Ent);
4473
4474 begin
4475 if Is_Task_Type (U_Ent) then
4476
4477 -- Check obsolescent (but never obsolescent if from aspect!)
4478
4479 if not From_Aspect_Specification (N) then
4480 Check_Restriction (No_Obsolescent_Features, N);
4481
4482 if Warn_On_Obsolescent_Feature then
4483 Error_Msg_N
4484 ("?j?storage size clause for task is an " &
4485 "obsolescent feature (RM J.9)", N);
4486 Error_Msg_N ("\?j?use Storage_Size pragma instead", N);
4487 end if;
4488 end if;
4489
4490 FOnly := True;
4491 end if;
4492
4493 if not Is_Access_Type (U_Ent)
4494 and then Ekind (U_Ent) /= E_Task_Type
4495 then
4496 Error_Msg_N ("storage size cannot be given for &", Nam);
4497
4498 elsif Is_Access_Type (U_Ent) and Is_Derived_Type (U_Ent) then
4499 Error_Msg_N
4500 ("storage size cannot be given for a derived access type",
4501 Nam);
4502
4503 elsif Duplicate_Clause then
4504 null;
4505
4506 else
4507 Analyze_And_Resolve (Expr, Any_Integer);
4508
4509 if Is_Access_Type (U_Ent) then
4510 if Present (Associated_Storage_Pool (U_Ent)) then
4511 Error_Msg_N ("storage pool already given for &", Nam);
4512 return;
4513 end if;
4514
4515 if Is_OK_Static_Expression (Expr)
4516 and then Expr_Value (Expr) = 0
4517 then
4518 Set_No_Pool_Assigned (Btype);
4519 end if;
4520 end if;
4521
4522 Set_Has_Storage_Size_Clause (Btype);
4523 end if;
4524 end Storage_Size;
4525
4526 -----------------
4527 -- Stream_Size --
4528 -----------------
4529
4530 when Attribute_Stream_Size => Stream_Size : declare
4531 Size : constant Uint := Static_Integer (Expr);
4532
4533 begin
4534 if Ada_Version <= Ada_95 then
4535 Check_Restriction (No_Implementation_Attributes, N);
4536 end if;
4537
4538 if Duplicate_Clause then
4539 null;
4540
4541 elsif Is_Elementary_Type (U_Ent) then
4542 if Size /= System_Storage_Unit
4543 and then
4544 Size /= System_Storage_Unit * 2
4545 and then
4546 Size /= System_Storage_Unit * 4
4547 and then
4548 Size /= System_Storage_Unit * 8
4549 then
4550 Error_Msg_Uint_1 := UI_From_Int (System_Storage_Unit);
4551 Error_Msg_N
4552 ("stream size for elementary type must be a"
4553 & " power of 2 and at least ^", N);
4554
4555 elsif RM_Size (U_Ent) > Size then
4556 Error_Msg_Uint_1 := RM_Size (U_Ent);
4557 Error_Msg_N
4558 ("stream size for elementary type must be a"
4559 & " power of 2 and at least ^", N);
4560 end if;
4561
4562 Set_Has_Stream_Size_Clause (U_Ent);
4563
4564 else
4565 Error_Msg_N ("Stream_Size cannot be given for &", Nam);
4566 end if;
4567 end Stream_Size;
4568
4569 ----------------
4570 -- Value_Size --
4571 ----------------
4572
4573 -- Value_Size attribute definition clause
4574
4575 when Attribute_Value_Size => Value_Size : declare
4576 Size : constant Uint := Static_Integer (Expr);
4577 Biased : Boolean;
4578
4579 begin
4580 if not Is_Type (U_Ent) then
4581 Error_Msg_N ("Value_Size cannot be given for &", Nam);
4582
4583 elsif Duplicate_Clause then
4584 null;
4585
4586 elsif Is_Array_Type (U_Ent)
4587 and then not Is_Constrained (U_Ent)
4588 then
4589 Error_Msg_N
4590 ("Value_Size cannot be given for unconstrained array", Nam);
4591
4592 else
4593 if Is_Elementary_Type (U_Ent) then
4594 Check_Size (Expr, U_Ent, Size, Biased);
4595 Set_Biased (U_Ent, N, "value size clause", Biased);
4596 end if;
4597
4598 Set_RM_Size (U_Ent, Size);
4599 end if;
4600 end Value_Size;
4601
4602 -----------------------
4603 -- Variable_Indexing --
4604 -----------------------
4605
4606 when Attribute_Variable_Indexing =>
4607 Check_Indexing_Functions;
4608
4609 -----------
4610 -- Write --
4611 -----------
4612
4613 when Attribute_Write =>
4614 Analyze_Stream_TSS_Definition (TSS_Stream_Write);
4615 Set_Has_Specified_Stream_Write (Ent);
4616
4617 -- All other attributes cannot be set
4618
4619 when others =>
4620 Error_Msg_N
4621 ("attribute& cannot be set with definition clause", N);
4622 end case;
4623
4624 -- The test for the type being frozen must be performed after any
4625 -- expression the clause has been analyzed since the expression itself
4626 -- might cause freezing that makes the clause illegal.
4627
4628 if Rep_Item_Too_Late (U_Ent, N, FOnly) then
4629 return;
4630 end if;
4631 end Analyze_Attribute_Definition_Clause;
4632
4633 ----------------------------
4634 -- Analyze_Code_Statement --
4635 ----------------------------
4636
4637 procedure Analyze_Code_Statement (N : Node_Id) is
4638 HSS : constant Node_Id := Parent (N);
4639 SBody : constant Node_Id := Parent (HSS);
4640 Subp : constant Entity_Id := Current_Scope;
4641 Stmt : Node_Id;
4642 Decl : Node_Id;
4643 StmtO : Node_Id;
4644 DeclO : Node_Id;
4645
4646 begin
4647 -- Analyze and check we get right type, note that this implements the
4648 -- requirement (RM 13.8(1)) that Machine_Code be with'ed, since that
4649 -- is the only way that Asm_Insn could possibly be visible.
4650
4651 Analyze_And_Resolve (Expression (N));
4652
4653 if Etype (Expression (N)) = Any_Type then
4654 return;
4655 elsif Etype (Expression (N)) /= RTE (RE_Asm_Insn) then
4656 Error_Msg_N ("incorrect type for code statement", N);
4657 return;
4658 end if;
4659
4660 Check_Code_Statement (N);
4661
4662 -- Make sure we appear in the handled statement sequence of a
4663 -- subprogram (RM 13.8(3)).
4664
4665 if Nkind (HSS) /= N_Handled_Sequence_Of_Statements
4666 or else Nkind (SBody) /= N_Subprogram_Body
4667 then
4668 Error_Msg_N
4669 ("code statement can only appear in body of subprogram", N);
4670 return;
4671 end if;
4672
4673 -- Do remaining checks (RM 13.8(3)) if not already done
4674
4675 if not Is_Machine_Code_Subprogram (Subp) then
4676 Set_Is_Machine_Code_Subprogram (Subp);
4677
4678 -- No exception handlers allowed
4679
4680 if Present (Exception_Handlers (HSS)) then
4681 Error_Msg_N
4682 ("exception handlers not permitted in machine code subprogram",
4683 First (Exception_Handlers (HSS)));
4684 end if;
4685
4686 -- No declarations other than use clauses and pragmas (we allow
4687 -- certain internally generated declarations as well).
4688
4689 Decl := First (Declarations (SBody));
4690 while Present (Decl) loop
4691 DeclO := Original_Node (Decl);
4692 if Comes_From_Source (DeclO)
4693 and not Nkind_In (DeclO, N_Pragma,
4694 N_Use_Package_Clause,
4695 N_Use_Type_Clause,
4696 N_Implicit_Label_Declaration)
4697 then
4698 Error_Msg_N
4699 ("this declaration not allowed in machine code subprogram",
4700 DeclO);
4701 end if;
4702
4703 Next (Decl);
4704 end loop;
4705
4706 -- No statements other than code statements, pragmas, and labels.
4707 -- Again we allow certain internally generated statements.
4708
4709 -- In Ada 2012, qualified expressions are names, and the code
4710 -- statement is initially parsed as a procedure call.
4711
4712 Stmt := First (Statements (HSS));
4713 while Present (Stmt) loop
4714 StmtO := Original_Node (Stmt);
4715
4716 -- A procedure call transformed into a code statement is OK.
4717
4718 if Ada_Version >= Ada_2012
4719 and then Nkind (StmtO) = N_Procedure_Call_Statement
4720 and then Nkind (Name (StmtO)) = N_Qualified_Expression
4721 then
4722 null;
4723
4724 elsif Comes_From_Source (StmtO)
4725 and then not Nkind_In (StmtO, N_Pragma,
4726 N_Label,
4727 N_Code_Statement)
4728 then
4729 Error_Msg_N
4730 ("this statement is not allowed in machine code subprogram",
4731 StmtO);
4732 end if;
4733
4734 Next (Stmt);
4735 end loop;
4736 end if;
4737 end Analyze_Code_Statement;
4738
4739 -----------------------------------------------
4740 -- Analyze_Enumeration_Representation_Clause --
4741 -----------------------------------------------
4742
4743 procedure Analyze_Enumeration_Representation_Clause (N : Node_Id) is
4744 Ident : constant Node_Id := Identifier (N);
4745 Aggr : constant Node_Id := Array_Aggregate (N);
4746 Enumtype : Entity_Id;
4747 Elit : Entity_Id;
4748 Expr : Node_Id;
4749 Assoc : Node_Id;
4750 Choice : Node_Id;
4751 Val : Uint;
4752
4753 Err : Boolean := False;
4754 -- Set True to avoid cascade errors and crashes on incorrect source code
4755
4756 Lo : constant Uint := Expr_Value (Type_Low_Bound (Universal_Integer));
4757 Hi : constant Uint := Expr_Value (Type_High_Bound (Universal_Integer));
4758 -- Allowed range of universal integer (= allowed range of enum lit vals)
4759
4760 Min : Uint;
4761 Max : Uint;
4762 -- Minimum and maximum values of entries
4763
4764 Max_Node : Node_Id;
4765 -- Pointer to node for literal providing max value
4766
4767 begin
4768 if Ignore_Rep_Clauses then
4769 return;
4770 end if;
4771
4772 -- Ignore enumeration rep clauses by default in CodePeer mode,
4773 -- unless -gnatd.I is specified, as a work around for potential false
4774 -- positive messages.
4775
4776 if CodePeer_Mode and not Debug_Flag_Dot_II then
4777 return;
4778 end if;
4779
4780 -- First some basic error checks
4781
4782 Find_Type (Ident);
4783 Enumtype := Entity (Ident);
4784
4785 if Enumtype = Any_Type
4786 or else Rep_Item_Too_Early (Enumtype, N)
4787 then
4788 return;
4789 else
4790 Enumtype := Underlying_Type (Enumtype);
4791 end if;
4792
4793 if not Is_Enumeration_Type (Enumtype) then
4794 Error_Msg_NE
4795 ("enumeration type required, found}",
4796 Ident, First_Subtype (Enumtype));
4797 return;
4798 end if;
4799
4800 -- Ignore rep clause on generic actual type. This will already have
4801 -- been flagged on the template as an error, and this is the safest
4802 -- way to ensure we don't get a junk cascaded message in the instance.
4803
4804 if Is_Generic_Actual_Type (Enumtype) then
4805 return;
4806
4807 -- Type must be in current scope
4808
4809 elsif Scope (Enumtype) /= Current_Scope then
4810 Error_Msg_N ("type must be declared in this scope", Ident);
4811 return;
4812
4813 -- Type must be a first subtype
4814
4815 elsif not Is_First_Subtype (Enumtype) then
4816 Error_Msg_N ("cannot give enumeration rep clause for subtype", N);
4817 return;
4818
4819 -- Ignore duplicate rep clause
4820
4821 elsif Has_Enumeration_Rep_Clause (Enumtype) then
4822 Error_Msg_N ("duplicate enumeration rep clause ignored", N);
4823 return;
4824
4825 -- Don't allow rep clause for standard [wide_[wide_]]character
4826
4827 elsif Is_Standard_Character_Type (Enumtype) then
4828 Error_Msg_N ("enumeration rep clause not allowed for this type", N);
4829 return;
4830
4831 -- Check that the expression is a proper aggregate (no parentheses)
4832
4833 elsif Paren_Count (Aggr) /= 0 then
4834 Error_Msg
4835 ("extra parentheses surrounding aggregate not allowed",
4836 First_Sloc (Aggr));
4837 return;
4838
4839 -- All tests passed, so set rep clause in place
4840
4841 else
4842 Set_Has_Enumeration_Rep_Clause (Enumtype);
4843 Set_Has_Enumeration_Rep_Clause (Base_Type (Enumtype));
4844 end if;
4845
4846 -- Now we process the aggregate. Note that we don't use the normal
4847 -- aggregate code for this purpose, because we don't want any of the
4848 -- normal expansion activities, and a number of special semantic
4849 -- rules apply (including the component type being any integer type)
4850
4851 Elit := First_Literal (Enumtype);
4852
4853 -- First the positional entries if any
4854
4855 if Present (Expressions (Aggr)) then
4856 Expr := First (Expressions (Aggr));
4857 while Present (Expr) loop
4858 if No (Elit) then
4859 Error_Msg_N ("too many entries in aggregate", Expr);
4860 return;
4861 end if;
4862
4863 Val := Static_Integer (Expr);
4864
4865 -- Err signals that we found some incorrect entries processing
4866 -- the list. The final checks for completeness and ordering are
4867 -- skipped in this case.
4868
4869 if Val = No_Uint then
4870 Err := True;
4871 elsif Val < Lo or else Hi < Val then
4872 Error_Msg_N ("value outside permitted range", Expr);
4873 Err := True;
4874 end if;
4875
4876 Set_Enumeration_Rep (Elit, Val);
4877 Set_Enumeration_Rep_Expr (Elit, Expr);
4878 Next (Expr);
4879 Next (Elit);
4880 end loop;
4881 end if;
4882
4883 -- Now process the named entries if present
4884
4885 if Present (Component_Associations (Aggr)) then
4886 Assoc := First (Component_Associations (Aggr));
4887 while Present (Assoc) loop
4888 Choice := First (Choices (Assoc));
4889
4890 if Present (Next (Choice)) then
4891 Error_Msg_N
4892 ("multiple choice not allowed here", Next (Choice));
4893 Err := True;
4894 end if;
4895
4896 if Nkind (Choice) = N_Others_Choice then
4897 Error_Msg_N ("others choice not allowed here", Choice);
4898 Err := True;
4899
4900 elsif Nkind (Choice) = N_Range then
4901
4902 -- ??? should allow zero/one element range here
4903
4904 Error_Msg_N ("range not allowed here", Choice);
4905 Err := True;
4906
4907 else
4908 Analyze_And_Resolve (Choice, Enumtype);
4909
4910 if Error_Posted (Choice) then
4911 Err := True;
4912 end if;
4913
4914 if not Err then
4915 if Is_Entity_Name (Choice)
4916 and then Is_Type (Entity (Choice))
4917 then
4918 Error_Msg_N ("subtype name not allowed here", Choice);
4919 Err := True;
4920
4921 -- ??? should allow static subtype with zero/one entry
4922
4923 elsif Etype (Choice) = Base_Type (Enumtype) then
4924 if not Is_Static_Expression (Choice) then
4925 Flag_Non_Static_Expr
4926 ("non-static expression used for choice!", Choice);
4927 Err := True;
4928
4929 else
4930 Elit := Expr_Value_E (Choice);
4931
4932 if Present (Enumeration_Rep_Expr (Elit)) then
4933 Error_Msg_Sloc :=
4934 Sloc (Enumeration_Rep_Expr (Elit));
4935 Error_Msg_NE
4936 ("representation for& previously given#",
4937 Choice, Elit);
4938 Err := True;
4939 end if;
4940
4941 Set_Enumeration_Rep_Expr (Elit, Expression (Assoc));
4942
4943 Expr := Expression (Assoc);
4944 Val := Static_Integer (Expr);
4945
4946 if Val = No_Uint then
4947 Err := True;
4948
4949 elsif Val < Lo or else Hi < Val then
4950 Error_Msg_N ("value outside permitted range", Expr);
4951 Err := True;
4952 end if;
4953
4954 Set_Enumeration_Rep (Elit, Val);
4955 end if;
4956 end if;
4957 end if;
4958 end if;
4959
4960 Next (Assoc);
4961 end loop;
4962 end if;
4963
4964 -- Aggregate is fully processed. Now we check that a full set of
4965 -- representations was given, and that they are in range and in order.
4966 -- These checks are only done if no other errors occurred.
4967
4968 if not Err then
4969 Min := No_Uint;
4970 Max := No_Uint;
4971
4972 Elit := First_Literal (Enumtype);
4973 while Present (Elit) loop
4974 if No (Enumeration_Rep_Expr (Elit)) then
4975 Error_Msg_NE ("missing representation for&!", N, Elit);
4976
4977 else
4978 Val := Enumeration_Rep (Elit);
4979
4980 if Min = No_Uint then
4981 Min := Val;
4982 end if;
4983
4984 if Val /= No_Uint then
4985 if Max /= No_Uint and then Val <= Max then
4986 Error_Msg_NE
4987 ("enumeration value for& not ordered!",
4988 Enumeration_Rep_Expr (Elit), Elit);
4989 end if;
4990
4991 Max_Node := Enumeration_Rep_Expr (Elit);
4992 Max := Val;
4993 end if;
4994
4995 -- If there is at least one literal whose representation is not
4996 -- equal to the Pos value, then note that this enumeration type
4997 -- has a non-standard representation.
4998
4999 if Val /= Enumeration_Pos (Elit) then
5000 Set_Has_Non_Standard_Rep (Base_Type (Enumtype));
5001 end if;
5002 end if;
5003
5004 Next (Elit);
5005 end loop;
5006
5007 -- Now set proper size information
5008
5009 declare
5010 Minsize : Uint := UI_From_Int (Minimum_Size (Enumtype));
5011
5012 begin
5013 if Has_Size_Clause (Enumtype) then
5014
5015 -- All OK, if size is OK now
5016
5017 if RM_Size (Enumtype) >= Minsize then
5018 null;
5019
5020 else
5021 -- Try if we can get by with biasing
5022
5023 Minsize :=
5024 UI_From_Int (Minimum_Size (Enumtype, Biased => True));
5025
5026 -- Error message if even biasing does not work
5027
5028 if RM_Size (Enumtype) < Minsize then
5029 Error_Msg_Uint_1 := RM_Size (Enumtype);
5030 Error_Msg_Uint_2 := Max;
5031 Error_Msg_N
5032 ("previously given size (^) is too small "
5033 & "for this value (^)", Max_Node);
5034
5035 -- If biasing worked, indicate that we now have biased rep
5036
5037 else
5038 Set_Biased
5039 (Enumtype, Size_Clause (Enumtype), "size clause");
5040 end if;
5041 end if;
5042
5043 else
5044 Set_RM_Size (Enumtype, Minsize);
5045 Set_Enum_Esize (Enumtype);
5046 end if;
5047
5048 Set_RM_Size (Base_Type (Enumtype), RM_Size (Enumtype));
5049 Set_Esize (Base_Type (Enumtype), Esize (Enumtype));
5050 Set_Alignment (Base_Type (Enumtype), Alignment (Enumtype));
5051 end;
5052 end if;
5053
5054 -- We repeat the too late test in case it froze itself!
5055
5056 if Rep_Item_Too_Late (Enumtype, N) then
5057 null;
5058 end if;
5059 end Analyze_Enumeration_Representation_Clause;
5060
5061 ----------------------------
5062 -- Analyze_Free_Statement --
5063 ----------------------------
5064
5065 procedure Analyze_Free_Statement (N : Node_Id) is
5066 begin
5067 Analyze (Expression (N));
5068 end Analyze_Free_Statement;
5069
5070 ---------------------------
5071 -- Analyze_Freeze_Entity --
5072 ---------------------------
5073
5074 procedure Analyze_Freeze_Entity (N : Node_Id) is
5075 E : constant Entity_Id := Entity (N);
5076
5077 begin
5078 -- Remember that we are processing a freezing entity. Required to
5079 -- ensure correct decoration of internal entities associated with
5080 -- interfaces (see New_Overloaded_Entity).
5081
5082 Inside_Freezing_Actions := Inside_Freezing_Actions + 1;
5083
5084 -- For tagged types covering interfaces add internal entities that link
5085 -- the primitives of the interfaces with the primitives that cover them.
5086 -- Note: These entities were originally generated only when generating
5087 -- code because their main purpose was to provide support to initialize
5088 -- the secondary dispatch tables. They are now generated also when
5089 -- compiling with no code generation to provide ASIS the relationship
5090 -- between interface primitives and tagged type primitives. They are
5091 -- also used to locate primitives covering interfaces when processing
5092 -- generics (see Derive_Subprograms).
5093
5094 if Ada_Version >= Ada_2005
5095 and then Ekind (E) = E_Record_Type
5096 and then Is_Tagged_Type (E)
5097 and then not Is_Interface (E)
5098 and then Has_Interfaces (E)
5099 then
5100 -- This would be a good common place to call the routine that checks
5101 -- overriding of interface primitives (and thus factorize calls to
5102 -- Check_Abstract_Overriding located at different contexts in the
5103 -- compiler). However, this is not possible because it causes
5104 -- spurious errors in case of late overriding.
5105
5106 Add_Internal_Interface_Entities (E);
5107 end if;
5108
5109 -- Check CPP types
5110
5111 if Ekind (E) = E_Record_Type
5112 and then Is_CPP_Class (E)
5113 and then Is_Tagged_Type (E)
5114 and then Tagged_Type_Expansion
5115 and then Expander_Active
5116 then
5117 if CPP_Num_Prims (E) = 0 then
5118
5119 -- If the CPP type has user defined components then it must import
5120 -- primitives from C++. This is required because if the C++ class
5121 -- has no primitives then the C++ compiler does not added the _tag
5122 -- component to the type.
5123
5124 pragma Assert (Chars (First_Entity (E)) = Name_uTag);
5125
5126 if First_Entity (E) /= Last_Entity (E) then
5127 Error_Msg_N
5128 ("'C'P'P type must import at least one primitive from C++??",
5129 E);
5130 end if;
5131 end if;
5132
5133 -- Check that all its primitives are abstract or imported from C++.
5134 -- Check also availability of the C++ constructor.
5135
5136 declare
5137 Has_Constructors : constant Boolean := Has_CPP_Constructors (E);
5138 Elmt : Elmt_Id;
5139 Error_Reported : Boolean := False;
5140 Prim : Node_Id;
5141
5142 begin
5143 Elmt := First_Elmt (Primitive_Operations (E));
5144 while Present (Elmt) loop
5145 Prim := Node (Elmt);
5146
5147 if Comes_From_Source (Prim) then
5148 if Is_Abstract_Subprogram (Prim) then
5149 null;
5150
5151 elsif not Is_Imported (Prim)
5152 or else Convention (Prim) /= Convention_CPP
5153 then
5154 Error_Msg_N
5155 ("primitives of 'C'P'P types must be imported from C++ "
5156 & "or abstract??", Prim);
5157
5158 elsif not Has_Constructors
5159 and then not Error_Reported
5160 then
5161 Error_Msg_Name_1 := Chars (E);
5162 Error_Msg_N
5163 ("??'C'P'P constructor required for type %", Prim);
5164 Error_Reported := True;
5165 end if;
5166 end if;
5167
5168 Next_Elmt (Elmt);
5169 end loop;
5170 end;
5171 end if;
5172
5173 -- Check Ada derivation of CPP type
5174
5175 if Expander_Active
5176 and then Tagged_Type_Expansion
5177 and then Ekind (E) = E_Record_Type
5178 and then Etype (E) /= E
5179 and then Is_CPP_Class (Etype (E))
5180 and then CPP_Num_Prims (Etype (E)) > 0
5181 and then not Is_CPP_Class (E)
5182 and then not Has_CPP_Constructors (Etype (E))
5183 then
5184 -- If the parent has C++ primitives but it has no constructor then
5185 -- check that all the primitives are overridden in this derivation;
5186 -- otherwise the constructor of the parent is needed to build the
5187 -- dispatch table.
5188
5189 declare
5190 Elmt : Elmt_Id;
5191 Prim : Node_Id;
5192
5193 begin
5194 Elmt := First_Elmt (Primitive_Operations (E));
5195 while Present (Elmt) loop
5196 Prim := Node (Elmt);
5197
5198 if not Is_Abstract_Subprogram (Prim)
5199 and then No (Interface_Alias (Prim))
5200 and then Find_Dispatching_Type (Ultimate_Alias (Prim)) /= E
5201 then
5202 Error_Msg_Name_1 := Chars (Etype (E));
5203 Error_Msg_N
5204 ("'C'P'P constructor required for parent type %", E);
5205 exit;
5206 end if;
5207
5208 Next_Elmt (Elmt);
5209 end loop;
5210 end;
5211 end if;
5212
5213 Inside_Freezing_Actions := Inside_Freezing_Actions - 1;
5214
5215 -- If we have a type with predicates, build predicate function
5216
5217 if Is_Type (E) and then Has_Predicates (E) then
5218 Build_Predicate_Functions (E, N);
5219 end if;
5220
5221 -- If type has delayed aspects, this is where we do the preanalysis at
5222 -- the freeze point, as part of the consistent visibility check. Note
5223 -- that this must be done after calling Build_Predicate_Functions or
5224 -- Build_Invariant_Procedure since these subprograms fix occurrences of
5225 -- the subtype name in the saved expression so that they will not cause
5226 -- trouble in the preanalysis.
5227
5228 if Has_Delayed_Aspects (E)
5229 and then Scope (E) = Current_Scope
5230 then
5231 -- Retrieve the visibility to the discriminants in order to properly
5232 -- analyze the aspects.
5233
5234 Push_Scope_And_Install_Discriminants (E);
5235
5236 declare
5237 Ritem : Node_Id;
5238
5239 begin
5240 -- Look for aspect specification entries for this entity
5241
5242 Ritem := First_Rep_Item (E);
5243 while Present (Ritem) loop
5244 if Nkind (Ritem) = N_Aspect_Specification
5245 and then Entity (Ritem) = E
5246 and then Is_Delayed_Aspect (Ritem)
5247 then
5248 Check_Aspect_At_Freeze_Point (Ritem);
5249 end if;
5250
5251 Next_Rep_Item (Ritem);
5252 end loop;
5253 end;
5254
5255 Uninstall_Discriminants_And_Pop_Scope (E);
5256 end if;
5257
5258 -- For a record type, deal with variant parts. This has to be delayed
5259 -- to this point, because of the issue of statically precicated
5260 -- subtypes, which we have to ensure are frozen before checking
5261 -- choices, since we need to have the static choice list set.
5262
5263 if Is_Record_Type (E) then
5264 Check_Variant_Part : declare
5265 D : constant Node_Id := Declaration_Node (E);
5266 T : Node_Id;
5267 C : Node_Id;
5268 VP : Node_Id;
5269
5270 Others_Present : Boolean;
5271 pragma Warnings (Off, Others_Present);
5272 -- Indicates others present, not used in this case
5273
5274 procedure Non_Static_Choice_Error (Choice : Node_Id);
5275 -- Error routine invoked by the generic instantiation below when
5276 -- the variant part has a non static choice.
5277
5278 procedure Process_Declarations (Variant : Node_Id);
5279 -- Processes declarations associated with a variant. We analyzed
5280 -- the declarations earlier (in Sem_Ch3.Analyze_Variant_Part),
5281 -- but we still need the recursive call to Check_Choices for any
5282 -- nested variant to get its choices properly processed. This is
5283 -- also where we expand out the choices if expansion is active.
5284
5285 package Variant_Choices_Processing is new
5286 Generic_Check_Choices
5287 (Process_Empty_Choice => No_OP,
5288 Process_Non_Static_Choice => Non_Static_Choice_Error,
5289 Process_Associated_Node => Process_Declarations);
5290 use Variant_Choices_Processing;
5291
5292 -----------------------------
5293 -- Non_Static_Choice_Error --
5294 -----------------------------
5295
5296 procedure Non_Static_Choice_Error (Choice : Node_Id) is
5297 begin
5298 Flag_Non_Static_Expr
5299 ("choice given in variant part is not static!", Choice);
5300 end Non_Static_Choice_Error;
5301
5302 --------------------------
5303 -- Process_Declarations --
5304 --------------------------
5305
5306 procedure Process_Declarations (Variant : Node_Id) is
5307 CL : constant Node_Id := Component_List (Variant);
5308 VP : Node_Id;
5309
5310 begin
5311 -- Check for static predicate present in this variant
5312
5313 if Has_SP_Choice (Variant) then
5314
5315 -- Here we expand. You might expect to find this call in
5316 -- Expand_N_Variant_Part, but that is called when we first
5317 -- see the variant part, and we cannot do this expansion
5318 -- earlier than the freeze point, since for statically
5319 -- predicated subtypes, the predicate is not known till
5320 -- the freeze point.
5321
5322 -- Furthermore, we do this expansion even if the expander
5323 -- is not active, because other semantic processing, e.g.
5324 -- for aggregates, requires the expanded list of choices.
5325
5326 -- If the expander is not active, then we can't just clobber
5327 -- the list since it would invalidate the ASIS -gnatct tree.
5328 -- So we have to rewrite the variant part with a Rewrite
5329 -- call that replaces it with a copy and clobber the copy.
5330
5331 if not Expander_Active then
5332 declare
5333 NewV : constant Node_Id := New_Copy (Variant);
5334 begin
5335 Set_Discrete_Choices
5336 (NewV, New_Copy_List (Discrete_Choices (Variant)));
5337 Rewrite (Variant, NewV);
5338 end;
5339 end if;
5340
5341 Expand_Static_Predicates_In_Choices (Variant);
5342 end if;
5343
5344 -- We don't need to worry about the declarations in the variant
5345 -- (since they were analyzed by Analyze_Choices when we first
5346 -- encountered the variant), but we do need to take care of
5347 -- expansion of any nested variants.
5348
5349 if not Null_Present (CL) then
5350 VP := Variant_Part (CL);
5351
5352 if Present (VP) then
5353 Check_Choices
5354 (VP, Variants (VP), Etype (Name (VP)), Others_Present);
5355 end if;
5356 end if;
5357 end Process_Declarations;
5358
5359 -- Start of processing for Check_Variant_Part
5360
5361 begin
5362 -- Find component list
5363
5364 C := Empty;
5365
5366 if Nkind (D) = N_Full_Type_Declaration then
5367 T := Type_Definition (D);
5368
5369 if Nkind (T) = N_Record_Definition then
5370 C := Component_List (T);
5371
5372 elsif Nkind (T) = N_Derived_Type_Definition
5373 and then Present (Record_Extension_Part (T))
5374 then
5375 C := Component_List (Record_Extension_Part (T));
5376 end if;
5377 end if;
5378
5379 -- Case of variant part present
5380
5381 if Present (C) and then Present (Variant_Part (C)) then
5382 VP := Variant_Part (C);
5383
5384 -- Check choices
5385
5386 Check_Choices
5387 (VP, Variants (VP), Etype (Name (VP)), Others_Present);
5388
5389 -- If the last variant does not contain the Others choice,
5390 -- replace it with an N_Others_Choice node since Gigi always
5391 -- wants an Others. Note that we do not bother to call Analyze
5392 -- on the modified variant part, since its only effect would be
5393 -- to compute the Others_Discrete_Choices node laboriously, and
5394 -- of course we already know the list of choices corresponding
5395 -- to the others choice (it's the list we're replacing!)
5396
5397 -- We only want to do this if the expander is active, since
5398 -- we do not want to clobber the ASIS tree!
5399
5400 if Expander_Active then
5401 declare
5402 Last_Var : constant Node_Id :=
5403 Last_Non_Pragma (Variants (VP));
5404
5405 Others_Node : Node_Id;
5406
5407 begin
5408 if Nkind (First (Discrete_Choices (Last_Var))) /=
5409 N_Others_Choice
5410 then
5411 Others_Node := Make_Others_Choice (Sloc (Last_Var));
5412 Set_Others_Discrete_Choices
5413 (Others_Node, Discrete_Choices (Last_Var));
5414 Set_Discrete_Choices
5415 (Last_Var, New_List (Others_Node));
5416 end if;
5417 end;
5418 end if;
5419 end if;
5420 end Check_Variant_Part;
5421 end if;
5422 end Analyze_Freeze_Entity;
5423
5424 ------------------------------------------
5425 -- Analyze_Record_Representation_Clause --
5426 ------------------------------------------
5427
5428 -- Note: we check as much as we can here, but we can't do any checks
5429 -- based on the position values (e.g. overlap checks) until freeze time
5430 -- because especially in Ada 2005 (machine scalar mode), the processing
5431 -- for non-standard bit order can substantially change the positions.
5432 -- See procedure Check_Record_Representation_Clause (called from Freeze)
5433 -- for the remainder of this processing.
5434
5435 procedure Analyze_Record_Representation_Clause (N : Node_Id) is
5436 Ident : constant Node_Id := Identifier (N);
5437 Biased : Boolean;
5438 CC : Node_Id;
5439 Comp : Entity_Id;
5440 Fbit : Uint;
5441 Hbit : Uint := Uint_0;
5442 Lbit : Uint;
5443 Ocomp : Entity_Id;
5444 Posit : Uint;
5445 Rectype : Entity_Id;
5446 Recdef : Node_Id;
5447
5448 function Is_Inherited (Comp : Entity_Id) return Boolean;
5449 -- True if Comp is an inherited component in a record extension
5450
5451 ------------------
5452 -- Is_Inherited --
5453 ------------------
5454
5455 function Is_Inherited (Comp : Entity_Id) return Boolean is
5456 Comp_Base : Entity_Id;
5457
5458 begin
5459 if Ekind (Rectype) = E_Record_Subtype then
5460 Comp_Base := Original_Record_Component (Comp);
5461 else
5462 Comp_Base := Comp;
5463 end if;
5464
5465 return Comp_Base /= Original_Record_Component (Comp_Base);
5466 end Is_Inherited;
5467
5468 -- Local variables
5469
5470 Is_Record_Extension : Boolean;
5471 -- True if Rectype is a record extension
5472
5473 CR_Pragma : Node_Id := Empty;
5474 -- Points to N_Pragma node if Complete_Representation pragma present
5475
5476 -- Start of processing for Analyze_Record_Representation_Clause
5477
5478 begin
5479 if Ignore_Rep_Clauses then
5480 return;
5481 end if;
5482
5483 Find_Type (Ident);
5484 Rectype := Entity (Ident);
5485
5486 if Rectype = Any_Type or else Rep_Item_Too_Early (Rectype, N) then
5487 return;
5488 else
5489 Rectype := Underlying_Type (Rectype);
5490 end if;
5491
5492 -- First some basic error checks
5493
5494 if not Is_Record_Type (Rectype) then
5495 Error_Msg_NE
5496 ("record type required, found}", Ident, First_Subtype (Rectype));
5497 return;
5498
5499 elsif Scope (Rectype) /= Current_Scope then
5500 Error_Msg_N ("type must be declared in this scope", N);
5501 return;
5502
5503 elsif not Is_First_Subtype (Rectype) then
5504 Error_Msg_N ("cannot give record rep clause for subtype", N);
5505 return;
5506
5507 elsif Has_Record_Rep_Clause (Rectype) then
5508 Error_Msg_N ("duplicate record rep clause ignored", N);
5509 return;
5510
5511 elsif Rep_Item_Too_Late (Rectype, N) then
5512 return;
5513 end if;
5514
5515 -- We know we have a first subtype, now possibly go the the anonymous
5516 -- base type to determine whether Rectype is a record extension.
5517
5518 Recdef := Type_Definition (Declaration_Node (Base_Type (Rectype)));
5519 Is_Record_Extension :=
5520 Nkind (Recdef) = N_Derived_Type_Definition
5521 and then Present (Record_Extension_Part (Recdef));
5522
5523 if Present (Mod_Clause (N)) then
5524 declare
5525 Loc : constant Source_Ptr := Sloc (N);
5526 M : constant Node_Id := Mod_Clause (N);
5527 P : constant List_Id := Pragmas_Before (M);
5528 AtM_Nod : Node_Id;
5529
5530 Mod_Val : Uint;
5531 pragma Warnings (Off, Mod_Val);
5532
5533 begin
5534 Check_Restriction (No_Obsolescent_Features, Mod_Clause (N));
5535
5536 if Warn_On_Obsolescent_Feature then
5537 Error_Msg_N
5538 ("?j?mod clause is an obsolescent feature (RM J.8)", N);
5539 Error_Msg_N
5540 ("\?j?use alignment attribute definition clause instead", N);
5541 end if;
5542
5543 if Present (P) then
5544 Analyze_List (P);
5545 end if;
5546
5547 -- In ASIS_Mode mode, expansion is disabled, but we must convert
5548 -- the Mod clause into an alignment clause anyway, so that the
5549 -- back-end can compute and back-annotate properly the size and
5550 -- alignment of types that may include this record.
5551
5552 -- This seems dubious, this destroys the source tree in a manner
5553 -- not detectable by ASIS ???
5554
5555 if Operating_Mode = Check_Semantics and then ASIS_Mode then
5556 AtM_Nod :=
5557 Make_Attribute_Definition_Clause (Loc,
5558 Name => New_Reference_To (Base_Type (Rectype), Loc),
5559 Chars => Name_Alignment,
5560 Expression => Relocate_Node (Expression (M)));
5561
5562 Set_From_At_Mod (AtM_Nod);
5563 Insert_After (N, AtM_Nod);
5564 Mod_Val := Get_Alignment_Value (Expression (AtM_Nod));
5565 Set_Mod_Clause (N, Empty);
5566
5567 else
5568 -- Get the alignment value to perform error checking
5569
5570 Mod_Val := Get_Alignment_Value (Expression (M));
5571 end if;
5572 end;
5573 end if;
5574
5575 -- For untagged types, clear any existing component clauses for the
5576 -- type. If the type is derived, this is what allows us to override
5577 -- a rep clause for the parent. For type extensions, the representation
5578 -- of the inherited components is inherited, so we want to keep previous
5579 -- component clauses for completeness.
5580
5581 if not Is_Tagged_Type (Rectype) then
5582 Comp := First_Component_Or_Discriminant (Rectype);
5583 while Present (Comp) loop
5584 Set_Component_Clause (Comp, Empty);
5585 Next_Component_Or_Discriminant (Comp);
5586 end loop;
5587 end if;
5588
5589 -- All done if no component clauses
5590
5591 CC := First (Component_Clauses (N));
5592
5593 if No (CC) then
5594 return;
5595 end if;
5596
5597 -- A representation like this applies to the base type
5598
5599 Set_Has_Record_Rep_Clause (Base_Type (Rectype));
5600 Set_Has_Non_Standard_Rep (Base_Type (Rectype));
5601 Set_Has_Specified_Layout (Base_Type (Rectype));
5602
5603 -- Process the component clauses
5604
5605 while Present (CC) loop
5606
5607 -- Pragma
5608
5609 if Nkind (CC) = N_Pragma then
5610 Analyze (CC);
5611
5612 -- The only pragma of interest is Complete_Representation
5613
5614 if Pragma_Name (CC) = Name_Complete_Representation then
5615 CR_Pragma := CC;
5616 end if;
5617
5618 -- Processing for real component clause
5619
5620 else
5621 Posit := Static_Integer (Position (CC));
5622 Fbit := Static_Integer (First_Bit (CC));
5623 Lbit := Static_Integer (Last_Bit (CC));
5624
5625 if Posit /= No_Uint
5626 and then Fbit /= No_Uint
5627 and then Lbit /= No_Uint
5628 then
5629 if Posit < 0 then
5630 Error_Msg_N
5631 ("position cannot be negative", Position (CC));
5632
5633 elsif Fbit < 0 then
5634 Error_Msg_N
5635 ("first bit cannot be negative", First_Bit (CC));
5636
5637 -- The Last_Bit specified in a component clause must not be
5638 -- less than the First_Bit minus one (RM-13.5.1(10)).
5639
5640 elsif Lbit < Fbit - 1 then
5641 Error_Msg_N
5642 ("last bit cannot be less than first bit minus one",
5643 Last_Bit (CC));
5644
5645 -- Values look OK, so find the corresponding record component
5646 -- Even though the syntax allows an attribute reference for
5647 -- implementation-defined components, GNAT does not allow the
5648 -- tag to get an explicit position.
5649
5650 elsif Nkind (Component_Name (CC)) = N_Attribute_Reference then
5651 if Attribute_Name (Component_Name (CC)) = Name_Tag then
5652 Error_Msg_N ("position of tag cannot be specified", CC);
5653 else
5654 Error_Msg_N ("illegal component name", CC);
5655 end if;
5656
5657 else
5658 Comp := First_Entity (Rectype);
5659 while Present (Comp) loop
5660 exit when Chars (Comp) = Chars (Component_Name (CC));
5661 Next_Entity (Comp);
5662 end loop;
5663
5664 if No (Comp) then
5665
5666 -- Maybe component of base type that is absent from
5667 -- statically constrained first subtype.
5668
5669 Comp := First_Entity (Base_Type (Rectype));
5670 while Present (Comp) loop
5671 exit when Chars (Comp) = Chars (Component_Name (CC));
5672 Next_Entity (Comp);
5673 end loop;
5674 end if;
5675
5676 if No (Comp) then
5677 Error_Msg_N
5678 ("component clause is for non-existent field", CC);
5679
5680 -- Ada 2012 (AI05-0026): Any name that denotes a
5681 -- discriminant of an object of an unchecked union type
5682 -- shall not occur within a record_representation_clause.
5683
5684 -- The general restriction of using record rep clauses on
5685 -- Unchecked_Union types has now been lifted. Since it is
5686 -- possible to introduce a record rep clause which mentions
5687 -- the discriminant of an Unchecked_Union in non-Ada 2012
5688 -- code, this check is applied to all versions of the
5689 -- language.
5690
5691 elsif Ekind (Comp) = E_Discriminant
5692 and then Is_Unchecked_Union (Rectype)
5693 then
5694 Error_Msg_N
5695 ("cannot reference discriminant of unchecked union",
5696 Component_Name (CC));
5697
5698 elsif Is_Record_Extension and then Is_Inherited (Comp) then
5699 Error_Msg_NE
5700 ("component clause not allowed for inherited "
5701 & "component&", CC, Comp);
5702
5703 elsif Present (Component_Clause (Comp)) then
5704
5705 -- Diagnose duplicate rep clause, or check consistency
5706 -- if this is an inherited component. In a double fault,
5707 -- there may be a duplicate inconsistent clause for an
5708 -- inherited component.
5709
5710 if Scope (Original_Record_Component (Comp)) = Rectype
5711 or else Parent (Component_Clause (Comp)) = N
5712 then
5713 Error_Msg_Sloc := Sloc (Component_Clause (Comp));
5714 Error_Msg_N ("component clause previously given#", CC);
5715
5716 else
5717 declare
5718 Rep1 : constant Node_Id := Component_Clause (Comp);
5719 begin
5720 if Intval (Position (Rep1)) /=
5721 Intval (Position (CC))
5722 or else Intval (First_Bit (Rep1)) /=
5723 Intval (First_Bit (CC))
5724 or else Intval (Last_Bit (Rep1)) /=
5725 Intval (Last_Bit (CC))
5726 then
5727 Error_Msg_N
5728 ("component clause inconsistent "
5729 & "with representation of ancestor", CC);
5730
5731 elsif Warn_On_Redundant_Constructs then
5732 Error_Msg_N
5733 ("?r?redundant confirming component clause "
5734 & "for component!", CC);
5735 end if;
5736 end;
5737 end if;
5738
5739 -- Normal case where this is the first component clause we
5740 -- have seen for this entity, so set it up properly.
5741
5742 else
5743 -- Make reference for field in record rep clause and set
5744 -- appropriate entity field in the field identifier.
5745
5746 Generate_Reference
5747 (Comp, Component_Name (CC), Set_Ref => False);
5748 Set_Entity (Component_Name (CC), Comp);
5749
5750 -- Update Fbit and Lbit to the actual bit number
5751
5752 Fbit := Fbit + UI_From_Int (SSU) * Posit;
5753 Lbit := Lbit + UI_From_Int (SSU) * Posit;
5754
5755 if Has_Size_Clause (Rectype)
5756 and then RM_Size (Rectype) <= Lbit
5757 then
5758 Error_Msg_N
5759 ("bit number out of range of specified size",
5760 Last_Bit (CC));
5761 else
5762 Set_Component_Clause (Comp, CC);
5763 Set_Component_Bit_Offset (Comp, Fbit);
5764 Set_Esize (Comp, 1 + (Lbit - Fbit));
5765 Set_Normalized_First_Bit (Comp, Fbit mod SSU);
5766 Set_Normalized_Position (Comp, Fbit / SSU);
5767
5768 if Warn_On_Overridden_Size
5769 and then Has_Size_Clause (Etype (Comp))
5770 and then RM_Size (Etype (Comp)) /= Esize (Comp)
5771 then
5772 Error_Msg_NE
5773 ("?S?component size overrides size clause for&",
5774 Component_Name (CC), Etype (Comp));
5775 end if;
5776
5777 -- This information is also set in the corresponding
5778 -- component of the base type, found by accessing the
5779 -- Original_Record_Component link if it is present.
5780
5781 Ocomp := Original_Record_Component (Comp);
5782
5783 if Hbit < Lbit then
5784 Hbit := Lbit;
5785 end if;
5786
5787 Check_Size
5788 (Component_Name (CC),
5789 Etype (Comp),
5790 Esize (Comp),
5791 Biased);
5792
5793 Set_Biased
5794 (Comp, First_Node (CC), "component clause", Biased);
5795
5796 if Present (Ocomp) then
5797 Set_Component_Clause (Ocomp, CC);
5798 Set_Component_Bit_Offset (Ocomp, Fbit);
5799 Set_Normalized_First_Bit (Ocomp, Fbit mod SSU);
5800 Set_Normalized_Position (Ocomp, Fbit / SSU);
5801 Set_Esize (Ocomp, 1 + (Lbit - Fbit));
5802
5803 Set_Normalized_Position_Max
5804 (Ocomp, Normalized_Position (Ocomp));
5805
5806 -- Note: we don't use Set_Biased here, because we
5807 -- already gave a warning above if needed, and we
5808 -- would get a duplicate for the same name here.
5809
5810 Set_Has_Biased_Representation
5811 (Ocomp, Has_Biased_Representation (Comp));
5812 end if;
5813
5814 if Esize (Comp) < 0 then
5815 Error_Msg_N ("component size is negative", CC);
5816 end if;
5817 end if;
5818 end if;
5819 end if;
5820 end if;
5821 end if;
5822
5823 Next (CC);
5824 end loop;
5825
5826 -- Check missing components if Complete_Representation pragma appeared
5827
5828 if Present (CR_Pragma) then
5829 Comp := First_Component_Or_Discriminant (Rectype);
5830 while Present (Comp) loop
5831 if No (Component_Clause (Comp)) then
5832 Error_Msg_NE
5833 ("missing component clause for &", CR_Pragma, Comp);
5834 end if;
5835
5836 Next_Component_Or_Discriminant (Comp);
5837 end loop;
5838
5839 -- Give missing components warning if required
5840
5841 elsif Warn_On_Unrepped_Components then
5842 declare
5843 Num_Repped_Components : Nat := 0;
5844 Num_Unrepped_Components : Nat := 0;
5845
5846 begin
5847 -- First count number of repped and unrepped components
5848
5849 Comp := First_Component_Or_Discriminant (Rectype);
5850 while Present (Comp) loop
5851 if Present (Component_Clause (Comp)) then
5852 Num_Repped_Components := Num_Repped_Components + 1;
5853 else
5854 Num_Unrepped_Components := Num_Unrepped_Components + 1;
5855 end if;
5856
5857 Next_Component_Or_Discriminant (Comp);
5858 end loop;
5859
5860 -- We are only interested in the case where there is at least one
5861 -- unrepped component, and at least half the components have rep
5862 -- clauses. We figure that if less than half have them, then the
5863 -- partial rep clause is really intentional. If the component
5864 -- type has no underlying type set at this point (as for a generic
5865 -- formal type), we don't know enough to give a warning on the
5866 -- component.
5867
5868 if Num_Unrepped_Components > 0
5869 and then Num_Unrepped_Components < Num_Repped_Components
5870 then
5871 Comp := First_Component_Or_Discriminant (Rectype);
5872 while Present (Comp) loop
5873 if No (Component_Clause (Comp))
5874 and then Comes_From_Source (Comp)
5875 and then Present (Underlying_Type (Etype (Comp)))
5876 and then (Is_Scalar_Type (Underlying_Type (Etype (Comp)))
5877 or else Size_Known_At_Compile_Time
5878 (Underlying_Type (Etype (Comp))))
5879 and then not Has_Warnings_Off (Rectype)
5880 then
5881 Error_Msg_Sloc := Sloc (Comp);
5882 Error_Msg_NE
5883 ("?C?no component clause given for & declared #",
5884 N, Comp);
5885 end if;
5886
5887 Next_Component_Or_Discriminant (Comp);
5888 end loop;
5889 end if;
5890 end;
5891 end if;
5892 end Analyze_Record_Representation_Clause;
5893
5894 -------------------------------------------
5895 -- Build_Invariant_Procedure_Declaration --
5896 -------------------------------------------
5897
5898 function Build_Invariant_Procedure_Declaration
5899 (Typ : Entity_Id) return Node_Id
5900 is
5901 Loc : constant Source_Ptr := Sloc (Typ);
5902 Object_Entity : constant Entity_Id :=
5903 Make_Defining_Identifier (Loc, New_Internal_Name ('I'));
5904 Spec : Node_Id;
5905 SId : Entity_Id;
5906
5907 begin
5908 Set_Etype (Object_Entity, Typ);
5909
5910 -- Check for duplicate definiations.
5911
5912 if Has_Invariants (Typ) and then Present (Invariant_Procedure (Typ)) then
5913 return Empty;
5914 end if;
5915
5916 SId :=
5917 Make_Defining_Identifier (Loc,
5918 Chars => New_External_Name (Chars (Typ), "Invariant"));
5919 Set_Has_Invariants (Typ);
5920 Set_Ekind (SId, E_Procedure);
5921 Set_Is_Invariant_Procedure (SId);
5922 Set_Invariant_Procedure (Typ, SId);
5923
5924 Spec :=
5925 Make_Procedure_Specification (Loc,
5926 Defining_Unit_Name => SId,
5927 Parameter_Specifications => New_List (
5928 Make_Parameter_Specification (Loc,
5929 Defining_Identifier => Object_Entity,
5930 Parameter_Type => New_Occurrence_Of (Typ, Loc))));
5931
5932 return Make_Subprogram_Declaration (Loc, Specification => Spec);
5933 end Build_Invariant_Procedure_Declaration;
5934
5935 -------------------------------
5936 -- Build_Invariant_Procedure --
5937 -------------------------------
5938
5939 -- The procedure that is constructed here has the form
5940
5941 -- procedure typInvariant (Ixxx : typ) is
5942 -- begin
5943 -- pragma Check (Invariant, exp, "failed invariant from xxx");
5944 -- pragma Check (Invariant, exp, "failed invariant from xxx");
5945 -- ...
5946 -- pragma Check (Invariant, exp, "failed inherited invariant from xxx");
5947 -- ...
5948 -- end typInvariant;
5949
5950 procedure Build_Invariant_Procedure (Typ : Entity_Id; N : Node_Id) is
5951 Loc : constant Source_Ptr := Sloc (Typ);
5952 Stmts : List_Id;
5953 Spec : Node_Id;
5954 SId : Entity_Id;
5955 PDecl : Node_Id;
5956 PBody : Node_Id;
5957
5958 Visible_Decls : constant List_Id := Visible_Declarations (N);
5959 Private_Decls : constant List_Id := Private_Declarations (N);
5960
5961 procedure Add_Invariants (T : Entity_Id; Inherit : Boolean);
5962 -- Appends statements to Stmts for any invariants in the rep item chain
5963 -- of the given type. If Inherit is False, then we only process entries
5964 -- on the chain for the type Typ. If Inherit is True, then we ignore any
5965 -- Invariant aspects, but we process all Invariant'Class aspects, adding
5966 -- "inherited" to the exception message and generating an informational
5967 -- message about the inheritance of an invariant.
5968
5969 Object_Name : Name_Id;
5970 -- Name for argument of invariant procedure
5971
5972 Object_Entity : Node_Id;
5973 -- The entity of the formal for the procedure
5974
5975 --------------------
5976 -- Add_Invariants --
5977 --------------------
5978
5979 procedure Add_Invariants (T : Entity_Id; Inherit : Boolean) is
5980 Ritem : Node_Id;
5981 Arg1 : Node_Id;
5982 Arg2 : Node_Id;
5983 Arg3 : Node_Id;
5984 Exp : Node_Id;
5985 Loc : Source_Ptr;
5986 Assoc : List_Id;
5987 Str : String_Id;
5988
5989 procedure Replace_Type_Reference (N : Node_Id);
5990 -- Replace a single occurrence N of the subtype name with a reference
5991 -- to the formal of the predicate function. N can be an identifier
5992 -- referencing the subtype, or a selected component, representing an
5993 -- appropriately qualified occurrence of the subtype name.
5994
5995 procedure Replace_Type_References is
5996 new Replace_Type_References_Generic (Replace_Type_Reference);
5997 -- Traverse an expression replacing all occurrences of the subtype
5998 -- name with appropriate references to the object that is the formal
5999 -- parameter of the predicate function. Note that we must ensure
6000 -- that the type and entity information is properly set in the
6001 -- replacement node, since we will do a Preanalyze call of this
6002 -- expression without proper visibility of the procedure argument.
6003
6004 ----------------------------
6005 -- Replace_Type_Reference --
6006 ----------------------------
6007
6008 -- Note: See comments in Add_Predicates.Replace_Type_Reference
6009 -- regarding handling of Sloc and Comes_From_Source.
6010
6011 procedure Replace_Type_Reference (N : Node_Id) is
6012 begin
6013 -- Invariant'Class, replace with T'Class (obj)
6014
6015 if Class_Present (Ritem) then
6016 Rewrite (N,
6017 Make_Type_Conversion (Sloc (N),
6018 Subtype_Mark =>
6019 Make_Attribute_Reference (Sloc (N),
6020 Prefix => New_Occurrence_Of (T, Sloc (N)),
6021 Attribute_Name => Name_Class),
6022 Expression => Make_Identifier (Sloc (N), Object_Name)));
6023
6024 Set_Entity (Expression (N), Object_Entity);
6025 Set_Etype (Expression (N), Typ);
6026
6027 -- Invariant, replace with obj
6028
6029 else
6030 Rewrite (N, Make_Identifier (Sloc (N), Object_Name));
6031 Set_Entity (N, Object_Entity);
6032 Set_Etype (N, Typ);
6033 end if;
6034
6035 Set_Comes_From_Source (N, True);
6036 end Replace_Type_Reference;
6037
6038 -- Start of processing for Add_Invariants
6039
6040 begin
6041 Ritem := First_Rep_Item (T);
6042 while Present (Ritem) loop
6043 if Nkind (Ritem) = N_Pragma
6044 and then Pragma_Name (Ritem) = Name_Invariant
6045 then
6046 Arg1 := First (Pragma_Argument_Associations (Ritem));
6047 Arg2 := Next (Arg1);
6048 Arg3 := Next (Arg2);
6049
6050 Arg1 := Get_Pragma_Arg (Arg1);
6051 Arg2 := Get_Pragma_Arg (Arg2);
6052
6053 -- For Inherit case, ignore Invariant, process only Class case
6054
6055 if Inherit then
6056 if not Class_Present (Ritem) then
6057 goto Continue;
6058 end if;
6059
6060 -- For Inherit false, process only item for right type
6061
6062 else
6063 if Entity (Arg1) /= Typ then
6064 goto Continue;
6065 end if;
6066 end if;
6067
6068 if No (Stmts) then
6069 Stmts := Empty_List;
6070 end if;
6071
6072 Exp := New_Copy_Tree (Arg2);
6073
6074 -- Preserve sloc of original pragma Invariant
6075
6076 Loc := Sloc (Ritem);
6077
6078 -- We need to replace any occurrences of the name of the type
6079 -- with references to the object, converted to type'Class in
6080 -- the case of Invariant'Class aspects.
6081
6082 Replace_Type_References (Exp, Chars (T));
6083
6084 -- If this invariant comes from an aspect, find the aspect
6085 -- specification, and replace the saved expression because
6086 -- we need the subtype references replaced for the calls to
6087 -- Preanalyze_Spec_Expressin in Check_Aspect_At_Freeze_Point
6088 -- and Check_Aspect_At_End_Of_Declarations.
6089
6090 if From_Aspect_Specification (Ritem) then
6091 declare
6092 Aitem : Node_Id;
6093
6094 begin
6095 -- Loop to find corresponding aspect, note that this
6096 -- must be present given the pragma is marked delayed.
6097
6098 Aitem := Next_Rep_Item (Ritem);
6099 while Present (Aitem) loop
6100 if Nkind (Aitem) = N_Aspect_Specification
6101 and then Aspect_Rep_Item (Aitem) = Ritem
6102 then
6103 Set_Entity
6104 (Identifier (Aitem), New_Copy_Tree (Exp));
6105 exit;
6106 end if;
6107
6108 Aitem := Next_Rep_Item (Aitem);
6109 end loop;
6110 end;
6111 end if;
6112
6113 -- Now we need to preanalyze the expression to properly capture
6114 -- the visibility in the visible part. The expression will not
6115 -- be analyzed for real until the body is analyzed, but that is
6116 -- at the end of the private part and has the wrong visibility.
6117
6118 Set_Parent (Exp, N);
6119 Preanalyze_Assert_Expression (Exp, Standard_Boolean);
6120
6121 -- Build first two arguments for Check pragma
6122
6123 Assoc := New_List (
6124 Make_Pragma_Argument_Association (Loc,
6125 Expression => Make_Identifier (Loc, Name_Invariant)),
6126 Make_Pragma_Argument_Association (Loc,
6127 Expression => Exp));
6128
6129 -- Add message if present in Invariant pragma
6130
6131 if Present (Arg3) then
6132 Str := Strval (Get_Pragma_Arg (Arg3));
6133
6134 -- If inherited case, and message starts "failed invariant",
6135 -- change it to be "failed inherited invariant".
6136
6137 if Inherit then
6138 String_To_Name_Buffer (Str);
6139
6140 if Name_Buffer (1 .. 16) = "failed invariant" then
6141 Insert_Str_In_Name_Buffer ("inherited ", 8);
6142 Str := String_From_Name_Buffer;
6143 end if;
6144 end if;
6145
6146 Append_To (Assoc,
6147 Make_Pragma_Argument_Association (Loc,
6148 Expression => Make_String_Literal (Loc, Str)));
6149 end if;
6150
6151 -- Add Check pragma to list of statements
6152
6153 Append_To (Stmts,
6154 Make_Pragma (Loc,
6155 Pragma_Identifier =>
6156 Make_Identifier (Loc, Name_Check),
6157 Pragma_Argument_Associations => Assoc));
6158
6159 -- If Inherited case and option enabled, output info msg. Note
6160 -- that we know this is a case of Invariant'Class.
6161
6162 if Inherit and Opt.List_Inherited_Aspects then
6163 Error_Msg_Sloc := Sloc (Ritem);
6164 Error_Msg_N
6165 ("?L?info: & inherits `Invariant''Class` aspect from #",
6166 Typ);
6167 end if;
6168 end if;
6169
6170 <<Continue>>
6171 Next_Rep_Item (Ritem);
6172 end loop;
6173 end Add_Invariants;
6174
6175 -- Start of processing for Build_Invariant_Procedure
6176
6177 begin
6178 Stmts := No_List;
6179 PDecl := Empty;
6180 PBody := Empty;
6181 SId := Empty;
6182
6183 -- If the aspect specification exists for some view of the type, the
6184 -- declaration for the procedure has been created.
6185
6186 if Has_Invariants (Typ) then
6187 SId := Invariant_Procedure (Typ);
6188 end if;
6189
6190 if Present (SId) then
6191 PDecl := Unit_Declaration_Node (SId);
6192
6193 else
6194 PDecl := Build_Invariant_Procedure_Declaration (Typ);
6195 end if;
6196
6197 -- Recover formal of procedure, for use in the calls to invariant
6198 -- functions (including inherited ones).
6199
6200 Object_Entity :=
6201 Defining_Identifier
6202 (First (Parameter_Specifications (Specification (PDecl))));
6203 Object_Name := Chars (Object_Entity);
6204
6205 -- Add invariants for the current type
6206
6207 Add_Invariants (Typ, Inherit => False);
6208
6209 -- Add invariants for parent types
6210
6211 declare
6212 Current_Typ : Entity_Id;
6213 Parent_Typ : Entity_Id;
6214
6215 begin
6216 Current_Typ := Typ;
6217 loop
6218 Parent_Typ := Etype (Current_Typ);
6219
6220 if Is_Private_Type (Parent_Typ)
6221 and then Present (Full_View (Base_Type (Parent_Typ)))
6222 then
6223 Parent_Typ := Full_View (Base_Type (Parent_Typ));
6224 end if;
6225
6226 exit when Parent_Typ = Current_Typ;
6227
6228 Current_Typ := Parent_Typ;
6229 Add_Invariants (Current_Typ, Inherit => True);
6230 end loop;
6231 end;
6232
6233 -- Build the procedure if we generated at least one Check pragma
6234
6235 if Stmts /= No_List then
6236 Spec := Copy_Separate_Tree (Specification (PDecl));
6237
6238 PBody :=
6239 Make_Subprogram_Body (Loc,
6240 Specification => Spec,
6241 Declarations => Empty_List,
6242 Handled_Statement_Sequence =>
6243 Make_Handled_Sequence_Of_Statements (Loc,
6244 Statements => Stmts));
6245
6246 -- Insert procedure declaration and spec at the appropriate points.
6247 -- If declaration is already analyzed, it was processed by the
6248 -- generated pragma.
6249
6250 if Present (Private_Decls) then
6251
6252 -- The spec goes at the end of visible declarations, but they have
6253 -- already been analyzed, so we need to explicitly do the analyze.
6254
6255 if not Analyzed (PDecl) then
6256 Append_To (Visible_Decls, PDecl);
6257 Analyze (PDecl);
6258 end if;
6259
6260 -- The body goes at the end of the private declarations, which we
6261 -- have not analyzed yet, so we do not need to perform an explicit
6262 -- analyze call. We skip this if there are no private declarations
6263 -- (this is an error that will be caught elsewhere);
6264
6265 Append_To (Private_Decls, PBody);
6266
6267 -- If the invariant appears on the full view of a type, the
6268 -- analysis of the private part is complete, and we must
6269 -- analyze the new body explicitly.
6270
6271 if In_Private_Part (Current_Scope) then
6272 Analyze (PBody);
6273 end if;
6274
6275 -- If there are no private declarations this may be an error that
6276 -- will be diagnosed elsewhere. However, if this is a non-private
6277 -- type that inherits invariants, it needs no completion and there
6278 -- may be no private part. In this case insert invariant procedure
6279 -- at end of current declarative list, and analyze at once, given
6280 -- that the type is about to be frozen.
6281
6282 elsif not Is_Private_Type (Typ) then
6283 Append_To (Visible_Decls, PDecl);
6284 Append_To (Visible_Decls, PBody);
6285 Analyze (PDecl);
6286 Analyze (PBody);
6287 end if;
6288 end if;
6289 end Build_Invariant_Procedure;
6290
6291 -------------------------------
6292 -- Build_Predicate_Functions --
6293 -------------------------------
6294
6295 -- The procedures that are constructed here have the form:
6296
6297 -- function typPredicate (Ixxx : typ) return Boolean is
6298 -- begin
6299 -- return
6300 -- exp1 and then exp2 and then ...
6301 -- and then typ1Predicate (typ1 (Ixxx))
6302 -- and then typ2Predicate (typ2 (Ixxx))
6303 -- and then ...;
6304 -- end typPredicate;
6305
6306 -- Here exp1, and exp2 are expressions from Predicate pragmas. Note that
6307 -- this is the point at which these expressions get analyzed, providing the
6308 -- required delay, and typ1, typ2, are entities from which predicates are
6309 -- inherited. Note that we do NOT generate Check pragmas, that's because we
6310 -- use this function even if checks are off, e.g. for membership tests.
6311
6312 -- If the expression has at least one Raise_Expression, then we also build
6313 -- the typPredicateM version of the function, in which any occurrence of a
6314 -- Raise_Expression is converted to "return False".
6315
6316 procedure Build_Predicate_Functions (Typ : Entity_Id; N : Node_Id) is
6317 Loc : constant Source_Ptr := Sloc (Typ);
6318
6319 Expr : Node_Id;
6320 -- This is the expression for the result of the function. It is
6321 -- is build by connecting the component predicates with AND THEN.
6322
6323 Expr_M : Node_Id;
6324 -- This is the corresponding return expression for the Predicate_M
6325 -- function. It differs in that raise expressions are marked for
6326 -- special expansion (see Process_REs).
6327
6328 Object_Name : constant Name_Id := New_Internal_Name ('I');
6329 -- Name for argument of Predicate procedure. Note that we use the same
6330 -- name for both predicate procedure. That way the reference within the
6331 -- predicate expression is the same in both functions.
6332
6333 Object_Entity : constant Entity_Id :=
6334 Make_Defining_Identifier (Loc, Chars => Object_Name);
6335 -- Entity for argument of Predicate procedure
6336
6337 Object_Entity_M : constant Entity_Id :=
6338 Make_Defining_Identifier (Loc, Chars => Object_Name);
6339 -- Entity for argument of Predicate_M procedure
6340
6341 Raise_Expression_Present : Boolean := False;
6342 -- Set True if Expr has at least one Raise_Expression
6343
6344 Static_Predic : Node_Id := Empty;
6345 -- Set to N_Pragma node for a static predicate if one is encountered
6346
6347 procedure Add_Call (T : Entity_Id);
6348 -- Includes a call to the predicate function for type T in Expr if T
6349 -- has predicates and Predicate_Function (T) is non-empty.
6350
6351 procedure Add_Predicates;
6352 -- Appends expressions for any Predicate pragmas in the rep item chain
6353 -- Typ to Expr. Note that we look only at items for this exact entity.
6354 -- Inheritance of predicates for the parent type is done by calling the
6355 -- Predicate_Function of the parent type, using Add_Call above.
6356
6357 function Test_RE (N : Node_Id) return Traverse_Result;
6358 -- Used in Test_REs, tests one node for being a raise expression, and if
6359 -- so sets Raise_Expression_Present True.
6360
6361 procedure Test_REs is new Traverse_Proc (Test_RE);
6362 -- Tests to see if Expr contains any raise expressions
6363
6364 function Process_RE (N : Node_Id) return Traverse_Result;
6365 -- Used in Process REs, tests if node N is a raise expression, and if
6366 -- so, marks it to be converted to return False.
6367
6368 procedure Process_REs is new Traverse_Proc (Process_RE);
6369 -- Marks any raise expressions in Expr_M to return False
6370
6371 --------------
6372 -- Add_Call --
6373 --------------
6374
6375 procedure Add_Call (T : Entity_Id) is
6376 Exp : Node_Id;
6377
6378 begin
6379 if Present (T) and then Present (Predicate_Function (T)) then
6380 Set_Has_Predicates (Typ);
6381
6382 -- Build the call to the predicate function of T
6383
6384 Exp :=
6385 Make_Predicate_Call
6386 (T, Convert_To (T, Make_Identifier (Loc, Object_Name)));
6387
6388 -- Add call to evolving expression, using AND THEN if needed
6389
6390 if No (Expr) then
6391 Expr := Exp;
6392 else
6393 Expr :=
6394 Make_And_Then (Loc,
6395 Left_Opnd => Relocate_Node (Expr),
6396 Right_Opnd => Exp);
6397 end if;
6398
6399 -- Output info message on inheritance if required. Note we do not
6400 -- give this information for generic actual types, since it is
6401 -- unwelcome noise in that case in instantiations. We also
6402 -- generally suppress the message in instantiations, and also
6403 -- if it involves internal names.
6404
6405 if Opt.List_Inherited_Aspects
6406 and then not Is_Generic_Actual_Type (Typ)
6407 and then Instantiation_Depth (Sloc (Typ)) = 0
6408 and then not Is_Internal_Name (Chars (T))
6409 and then not Is_Internal_Name (Chars (Typ))
6410 then
6411 Error_Msg_Sloc := Sloc (Predicate_Function (T));
6412 Error_Msg_Node_2 := T;
6413 Error_Msg_N ("info: & inherits predicate from & #?L?", Typ);
6414 end if;
6415 end if;
6416 end Add_Call;
6417
6418 --------------------
6419 -- Add_Predicates --
6420 --------------------
6421
6422 procedure Add_Predicates is
6423 Ritem : Node_Id;
6424 Arg1 : Node_Id;
6425 Arg2 : Node_Id;
6426
6427 procedure Replace_Type_Reference (N : Node_Id);
6428 -- Replace a single occurrence N of the subtype name with a reference
6429 -- to the formal of the predicate function. N can be an identifier
6430 -- referencing the subtype, or a selected component, representing an
6431 -- appropriately qualified occurrence of the subtype name.
6432
6433 procedure Replace_Type_References is
6434 new Replace_Type_References_Generic (Replace_Type_Reference);
6435 -- Traverse an expression changing every occurrence of an identifier
6436 -- whose name matches the name of the subtype with a reference to
6437 -- the formal parameter of the predicate function.
6438
6439 ----------------------------
6440 -- Replace_Type_Reference --
6441 ----------------------------
6442
6443 procedure Replace_Type_Reference (N : Node_Id) is
6444 begin
6445 Rewrite (N, Make_Identifier (Sloc (N), Object_Name));
6446 -- Use the Sloc of the usage name, not the defining name
6447
6448 Set_Etype (N, Typ);
6449 Set_Entity (N, Object_Entity);
6450
6451 -- We want to treat the node as if it comes from source, so that
6452 -- ASIS will not ignore it
6453
6454 Set_Comes_From_Source (N, True);
6455 end Replace_Type_Reference;
6456
6457 -- Start of processing for Add_Predicates
6458
6459 begin
6460 Ritem := First_Rep_Item (Typ);
6461 while Present (Ritem) loop
6462 if Nkind (Ritem) = N_Pragma
6463 and then Pragma_Name (Ritem) = Name_Predicate
6464 then
6465 -- Save the static predicate of the type for diagnostics and
6466 -- error reporting purposes.
6467
6468 if Present (Corresponding_Aspect (Ritem))
6469 and then Chars (Identifier (Corresponding_Aspect (Ritem))) =
6470 Name_Static_Predicate
6471 then
6472 Static_Predic := Ritem;
6473 end if;
6474
6475 -- Acquire arguments
6476
6477 Arg1 := First (Pragma_Argument_Associations (Ritem));
6478 Arg2 := Next (Arg1);
6479
6480 Arg1 := Get_Pragma_Arg (Arg1);
6481 Arg2 := Get_Pragma_Arg (Arg2);
6482
6483 -- See if this predicate pragma is for the current type or for
6484 -- its full view. A predicate on a private completion is placed
6485 -- on the partial view beause this is the visible entity that
6486 -- is frozen.
6487
6488 if Entity (Arg1) = Typ
6489 or else Full_View (Entity (Arg1)) = Typ
6490 then
6491 -- We have a match, this entry is for our subtype
6492
6493 -- We need to replace any occurrences of the name of the
6494 -- type with references to the object.
6495
6496 Replace_Type_References (Arg2, Chars (Typ));
6497
6498 -- If this predicate comes from an aspect, find the aspect
6499 -- specification, and replace the saved expression because
6500 -- we need the subtype references replaced for the calls to
6501 -- Preanalyze_Spec_Expressin in Check_Aspect_At_Freeze_Point
6502 -- and Check_Aspect_At_End_Of_Declarations.
6503
6504 if From_Aspect_Specification (Ritem) then
6505 declare
6506 Aitem : Node_Id;
6507
6508 begin
6509 -- Loop to find corresponding aspect, note that this
6510 -- must be present given the pragma is marked delayed.
6511
6512 Aitem := Next_Rep_Item (Ritem);
6513 loop
6514 if Nkind (Aitem) = N_Aspect_Specification
6515 and then Aspect_Rep_Item (Aitem) = Ritem
6516 then
6517 Set_Entity
6518 (Identifier (Aitem), New_Copy_Tree (Arg2));
6519 exit;
6520 end if;
6521
6522 Aitem := Next_Rep_Item (Aitem);
6523 end loop;
6524 end;
6525 end if;
6526
6527 -- Now we can add the expression
6528
6529 if No (Expr) then
6530 Expr := Relocate_Node (Arg2);
6531
6532 -- There already was a predicate, so add to it
6533
6534 else
6535 Expr :=
6536 Make_And_Then (Loc,
6537 Left_Opnd => Relocate_Node (Expr),
6538 Right_Opnd => Relocate_Node (Arg2));
6539 end if;
6540 end if;
6541 end if;
6542
6543 Next_Rep_Item (Ritem);
6544 end loop;
6545 end Add_Predicates;
6546
6547 ----------------
6548 -- Process_RE --
6549 ----------------
6550
6551 function Process_RE (N : Node_Id) return Traverse_Result is
6552 begin
6553 if Nkind (N) = N_Raise_Expression then
6554 Set_Convert_To_Return_False (N);
6555 return Skip;
6556 else
6557 return OK;
6558 end if;
6559 end Process_RE;
6560
6561 -------------
6562 -- Test_RE --
6563 -------------
6564
6565 function Test_RE (N : Node_Id) return Traverse_Result is
6566 begin
6567 if Nkind (N) = N_Raise_Expression then
6568 Raise_Expression_Present := True;
6569 return Abandon;
6570 else
6571 return OK;
6572 end if;
6573 end Test_RE;
6574
6575 -- Start of processing for Build_Predicate_Functions
6576
6577 begin
6578 -- Return if already built or if type does not have predicates
6579
6580 if not Has_Predicates (Typ)
6581 or else Present (Predicate_Function (Typ))
6582 then
6583 return;
6584 end if;
6585
6586 -- Prepare to construct predicate expression
6587
6588 Expr := Empty;
6589
6590 -- Add Predicates for the current type
6591
6592 Add_Predicates;
6593
6594 -- Add predicates for ancestor if present
6595
6596 declare
6597 Atyp : constant Entity_Id := Nearest_Ancestor (Typ);
6598 begin
6599 if Present (Atyp) then
6600 Add_Call (Atyp);
6601 end if;
6602 end;
6603
6604 -- Case where predicates are present
6605
6606 if Present (Expr) then
6607
6608 -- Test for raise expression present
6609
6610 Test_REs (Expr);
6611
6612 -- If raise expression is present, capture a copy of Expr for use
6613 -- in building the predicateM function version later on. For this
6614 -- copy we replace references to Object_Entity by Object_Entity_M.
6615
6616 if Raise_Expression_Present then
6617 declare
6618 Map : constant Elist_Id := New_Elmt_List;
6619 begin
6620 Append_Elmt (Object_Entity, Map);
6621 Append_Elmt (Object_Entity_M, Map);
6622 Expr_M := New_Copy_Tree (Expr, Map => Map);
6623 end;
6624 end if;
6625
6626 -- Build the main predicate function
6627
6628 declare
6629 SId : constant Entity_Id :=
6630 Make_Defining_Identifier (Loc,
6631 Chars => New_External_Name (Chars (Typ), "Predicate"));
6632 -- The entity for the the function spec
6633
6634 SIdB : constant Entity_Id :=
6635 Make_Defining_Identifier (Loc,
6636 Chars => New_External_Name (Chars (Typ), "Predicate"));
6637 -- The entity for the function body
6638
6639 Spec : Node_Id;
6640 FDecl : Node_Id;
6641 FBody : Node_Id;
6642
6643 begin
6644 -- Build function declaration
6645
6646 Set_Ekind (SId, E_Function);
6647 Set_Is_Predicate_Function (SId);
6648 Set_Predicate_Function (Typ, SId);
6649
6650 -- The predicate function is shared between views of a type
6651
6652 if Is_Private_Type (Typ) and then Present (Full_View (Typ)) then
6653 Set_Predicate_Function (Full_View (Typ), SId);
6654 end if;
6655
6656 Spec :=
6657 Make_Function_Specification (Loc,
6658 Defining_Unit_Name => SId,
6659 Parameter_Specifications => New_List (
6660 Make_Parameter_Specification (Loc,
6661 Defining_Identifier => Object_Entity,
6662 Parameter_Type => New_Occurrence_Of (Typ, Loc))),
6663 Result_Definition =>
6664 New_Occurrence_Of (Standard_Boolean, Loc));
6665
6666 FDecl :=
6667 Make_Subprogram_Declaration (Loc,
6668 Specification => Spec);
6669
6670 -- Build function body
6671
6672 Spec :=
6673 Make_Function_Specification (Loc,
6674 Defining_Unit_Name => SIdB,
6675 Parameter_Specifications => New_List (
6676 Make_Parameter_Specification (Loc,
6677 Defining_Identifier =>
6678 Make_Defining_Identifier (Loc, Object_Name),
6679 Parameter_Type =>
6680 New_Occurrence_Of (Typ, Loc))),
6681 Result_Definition =>
6682 New_Occurrence_Of (Standard_Boolean, Loc));
6683
6684 FBody :=
6685 Make_Subprogram_Body (Loc,
6686 Specification => Spec,
6687 Declarations => Empty_List,
6688 Handled_Statement_Sequence =>
6689 Make_Handled_Sequence_Of_Statements (Loc,
6690 Statements => New_List (
6691 Make_Simple_Return_Statement (Loc,
6692 Expression => Expr))));
6693
6694 -- Insert declaration before freeze node and body after
6695
6696 Insert_Before_And_Analyze (N, FDecl);
6697 Insert_After_And_Analyze (N, FBody);
6698 end;
6699
6700 -- Test for raise expressions present and if so build M version
6701
6702 if Raise_Expression_Present then
6703 declare
6704 SId : constant Entity_Id :=
6705 Make_Defining_Identifier (Loc,
6706 Chars => New_External_Name (Chars (Typ), "PredicateM"));
6707 -- The entity for the the function spec
6708
6709 SIdB : constant Entity_Id :=
6710 Make_Defining_Identifier (Loc,
6711 Chars => New_External_Name (Chars (Typ), "PredicateM"));
6712 -- The entity for the function body
6713
6714 Spec : Node_Id;
6715 FDecl : Node_Id;
6716 FBody : Node_Id;
6717 BTemp : Entity_Id;
6718
6719 begin
6720 -- Mark any raise expressions for special expansion
6721
6722 Process_REs (Expr_M);
6723
6724 -- Build function declaration
6725
6726 Set_Ekind (SId, E_Function);
6727 Set_Is_Predicate_Function_M (SId);
6728 Set_Predicate_Function_M (Typ, SId);
6729
6730 -- The predicate function is shared between views of a type
6731
6732 if Is_Private_Type (Typ) and then Present (Full_View (Typ)) then
6733 Set_Predicate_Function_M (Full_View (Typ), SId);
6734 end if;
6735
6736 Spec :=
6737 Make_Function_Specification (Loc,
6738 Defining_Unit_Name => SId,
6739 Parameter_Specifications => New_List (
6740 Make_Parameter_Specification (Loc,
6741 Defining_Identifier => Object_Entity_M,
6742 Parameter_Type => New_Occurrence_Of (Typ, Loc))),
6743 Result_Definition =>
6744 New_Occurrence_Of (Standard_Boolean, Loc));
6745
6746 FDecl :=
6747 Make_Subprogram_Declaration (Loc,
6748 Specification => Spec);
6749
6750 -- Build function body
6751
6752 Spec :=
6753 Make_Function_Specification (Loc,
6754 Defining_Unit_Name => SIdB,
6755 Parameter_Specifications => New_List (
6756 Make_Parameter_Specification (Loc,
6757 Defining_Identifier =>
6758 Make_Defining_Identifier (Loc, Object_Name),
6759 Parameter_Type =>
6760 New_Occurrence_Of (Typ, Loc))),
6761 Result_Definition =>
6762 New_Occurrence_Of (Standard_Boolean, Loc));
6763
6764 -- Build the body, we declare the boolean expression before
6765 -- doing the return, because we are not really confident of
6766 -- what happens if a return appears within a return!
6767
6768 BTemp :=
6769 Make_Defining_Identifier (Loc,
6770 Chars => New_Internal_Name ('B'));
6771
6772 FBody :=
6773 Make_Subprogram_Body (Loc,
6774 Specification => Spec,
6775
6776 Declarations => New_List (
6777 Make_Object_Declaration (Loc,
6778 Defining_Identifier => BTemp,
6779 Constant_Present => True,
6780 Object_Definition =>
6781 New_Reference_To (Standard_Boolean, Loc),
6782 Expression => Expr_M)),
6783
6784 Handled_Statement_Sequence =>
6785 Make_Handled_Sequence_Of_Statements (Loc,
6786 Statements => New_List (
6787 Make_Simple_Return_Statement (Loc,
6788 Expression => New_Reference_To (BTemp, Loc)))));
6789
6790 -- Insert declaration before freeze node and body after
6791
6792 Insert_Before_And_Analyze (N, FDecl);
6793 Insert_After_And_Analyze (N, FBody);
6794 end;
6795 end if;
6796
6797 if Is_Scalar_Type (Typ) then
6798
6799 -- Attempt to build a static predicate for a discrete or a real
6800 -- subtype. This action may fail because the actual expression may
6801 -- not be static. Note that the presence of an inherited or
6802 -- explicitly declared dynamic predicate is orthogonal to this
6803 -- check because we are only interested in the static predicate.
6804
6805 if Ekind_In (Typ, E_Decimal_Fixed_Point_Subtype,
6806 E_Enumeration_Subtype,
6807 E_Floating_Point_Subtype,
6808 E_Modular_Integer_Subtype,
6809 E_Ordinary_Fixed_Point_Subtype,
6810 E_Signed_Integer_Subtype)
6811 then
6812 Build_Static_Predicate (Typ, Expr, Object_Name);
6813
6814 -- Emit an error when the predicate is categorized as static
6815 -- but its expression is dynamic.
6816
6817 if Present (Static_Predic)
6818 and then No (Static_Predicate (Typ))
6819 then
6820 Error_Msg_F
6821 ("expression does not have required form for "
6822 & "static predicate",
6823 Next (First (Pragma_Argument_Associations
6824 (Static_Predic))));
6825 end if;
6826 end if;
6827
6828 -- If a static predicate applies on other types, that's an error:
6829 -- either the type is scalar but non-static, or it's not even a
6830 -- scalar type. We do not issue an error on generated types, as
6831 -- these may be duplicates of the same error on a source type.
6832
6833 elsif Present (Static_Predic) and then Comes_From_Source (Typ) then
6834 if Is_Scalar_Type (Typ) then
6835 Error_Msg_FE
6836 ("static predicate not allowed for non-static type&",
6837 Typ, Typ);
6838 else
6839 Error_Msg_FE
6840 ("static predicate not allowed for non-scalar type&",
6841 Typ, Typ);
6842 end if;
6843 end if;
6844 end if;
6845 end Build_Predicate_Functions;
6846
6847 ----------------------------
6848 -- Build_Static_Predicate --
6849 ----------------------------
6850
6851 procedure Build_Static_Predicate
6852 (Typ : Entity_Id;
6853 Expr : Node_Id;
6854 Nam : Name_Id)
6855 is
6856 Loc : constant Source_Ptr := Sloc (Expr);
6857
6858 Non_Static : exception;
6859 -- Raised if something non-static is found
6860
6861 Btyp : constant Entity_Id := Base_Type (Typ);
6862
6863 BLo : constant Uint := Expr_Value (Type_Low_Bound (Btyp));
6864 BHi : constant Uint := Expr_Value (Type_High_Bound (Btyp));
6865 -- Low bound and high bound value of base type of Typ
6866
6867 TLo : constant Uint := Expr_Value (Type_Low_Bound (Typ));
6868 THi : constant Uint := Expr_Value (Type_High_Bound (Typ));
6869 -- Low bound and high bound values of static subtype Typ
6870
6871 type REnt is record
6872 Lo, Hi : Uint;
6873 end record;
6874 -- One entry in a Rlist value, a single REnt (range entry) value denotes
6875 -- one range from Lo to Hi. To represent a single value range Lo = Hi =
6876 -- value.
6877
6878 type RList is array (Nat range <>) of REnt;
6879 -- A list of ranges. The ranges are sorted in increasing order, and are
6880 -- disjoint (there is a gap of at least one value between each range in
6881 -- the table). A value is in the set of ranges in Rlist if it lies
6882 -- within one of these ranges.
6883
6884 False_Range : constant RList :=
6885 RList'(1 .. 0 => REnt'(No_Uint, No_Uint));
6886 -- An empty set of ranges represents a range list that can never be
6887 -- satisfied, since there are no ranges in which the value could lie,
6888 -- so it does not lie in any of them. False_Range is a canonical value
6889 -- for this empty set, but general processing should test for an Rlist
6890 -- with length zero (see Is_False predicate), since other null ranges
6891 -- may appear which must be treated as False.
6892
6893 True_Range : constant RList := RList'(1 => REnt'(BLo, BHi));
6894 -- Range representing True, value must be in the base range
6895
6896 function "and" (Left : RList; Right : RList) return RList;
6897 -- And's together two range lists, returning a range list. This is a set
6898 -- intersection operation.
6899
6900 function "or" (Left : RList; Right : RList) return RList;
6901 -- Or's together two range lists, returning a range list. This is a set
6902 -- union operation.
6903
6904 function "not" (Right : RList) return RList;
6905 -- Returns complement of a given range list, i.e. a range list
6906 -- representing all the values in TLo .. THi that are not in the input
6907 -- operand Right.
6908
6909 function Build_Val (V : Uint) return Node_Id;
6910 -- Return an analyzed N_Identifier node referencing this value, suitable
6911 -- for use as an entry in the Static_Predicate list. This node is typed
6912 -- with the base type.
6913
6914 function Build_Range (Lo : Uint; Hi : Uint) return Node_Id;
6915 -- Return an analyzed N_Range node referencing this range, suitable for
6916 -- use as an entry in the Static_Predicate list. This node is typed with
6917 -- the base type.
6918
6919 function Get_RList (Exp : Node_Id) return RList;
6920 -- This is a recursive routine that converts the given expression into a
6921 -- list of ranges, suitable for use in building the static predicate.
6922
6923 function Is_False (R : RList) return Boolean;
6924 pragma Inline (Is_False);
6925 -- Returns True if the given range list is empty, and thus represents a
6926 -- False list of ranges that can never be satisfied.
6927
6928 function Is_True (R : RList) return Boolean;
6929 -- Returns True if R trivially represents the True predicate by having a
6930 -- single range from BLo to BHi.
6931
6932 function Is_Type_Ref (N : Node_Id) return Boolean;
6933 pragma Inline (Is_Type_Ref);
6934 -- Returns if True if N is a reference to the type for the predicate in
6935 -- the expression (i.e. if it is an identifier whose Chars field matches
6936 -- the Nam given in the call).
6937
6938 function Lo_Val (N : Node_Id) return Uint;
6939 -- Given static expression or static range from a Static_Predicate list,
6940 -- gets expression value or low bound of range.
6941
6942 function Hi_Val (N : Node_Id) return Uint;
6943 -- Given static expression or static range from a Static_Predicate list,
6944 -- gets expression value of high bound of range.
6945
6946 function Membership_Entry (N : Node_Id) return RList;
6947 -- Given a single membership entry (range, value, or subtype), returns
6948 -- the corresponding range list. Raises Static_Error if not static.
6949
6950 function Membership_Entries (N : Node_Id) return RList;
6951 -- Given an element on an alternatives list of a membership operation,
6952 -- returns the range list corresponding to this entry and all following
6953 -- entries (i.e. returns the "or" of this list of values).
6954
6955 function Stat_Pred (Typ : Entity_Id) return RList;
6956 -- Given a type, if it has a static predicate, then return the predicate
6957 -- as a range list, otherwise raise Non_Static.
6958
6959 -----------
6960 -- "and" --
6961 -----------
6962
6963 function "and" (Left : RList; Right : RList) return RList is
6964 FEnt : REnt;
6965 -- First range of result
6966
6967 SLeft : Nat := Left'First;
6968 -- Start of rest of left entries
6969
6970 SRight : Nat := Right'First;
6971 -- Start of rest of right entries
6972
6973 begin
6974 -- If either range is True, return the other
6975
6976 if Is_True (Left) then
6977 return Right;
6978 elsif Is_True (Right) then
6979 return Left;
6980 end if;
6981
6982 -- If either range is False, return False
6983
6984 if Is_False (Left) or else Is_False (Right) then
6985 return False_Range;
6986 end if;
6987
6988 -- Loop to remove entries at start that are disjoint, and thus just
6989 -- get discarded from the result entirely.
6990
6991 loop
6992 -- If no operands left in either operand, result is false
6993
6994 if SLeft > Left'Last or else SRight > Right'Last then
6995 return False_Range;
6996
6997 -- Discard first left operand entry if disjoint with right
6998
6999 elsif Left (SLeft).Hi < Right (SRight).Lo then
7000 SLeft := SLeft + 1;
7001
7002 -- Discard first right operand entry if disjoint with left
7003
7004 elsif Right (SRight).Hi < Left (SLeft).Lo then
7005 SRight := SRight + 1;
7006
7007 -- Otherwise we have an overlapping entry
7008
7009 else
7010 exit;
7011 end if;
7012 end loop;
7013
7014 -- Now we have two non-null operands, and first entries overlap. The
7015 -- first entry in the result will be the overlapping part of these
7016 -- two entries.
7017
7018 FEnt := REnt'(Lo => UI_Max (Left (SLeft).Lo, Right (SRight).Lo),
7019 Hi => UI_Min (Left (SLeft).Hi, Right (SRight).Hi));
7020
7021 -- Now we can remove the entry that ended at a lower value, since its
7022 -- contribution is entirely contained in Fent.
7023
7024 if Left (SLeft).Hi <= Right (SRight).Hi then
7025 SLeft := SLeft + 1;
7026 else
7027 SRight := SRight + 1;
7028 end if;
7029
7030 -- Compute result by concatenating this first entry with the "and" of
7031 -- the remaining parts of the left and right operands. Note that if
7032 -- either of these is empty, "and" will yield empty, so that we will
7033 -- end up with just Fent, which is what we want in that case.
7034
7035 return
7036 FEnt & (Left (SLeft .. Left'Last) and Right (SRight .. Right'Last));
7037 end "and";
7038
7039 -----------
7040 -- "not" --
7041 -----------
7042
7043 function "not" (Right : RList) return RList is
7044 begin
7045 -- Return True if False range
7046
7047 if Is_False (Right) then
7048 return True_Range;
7049 end if;
7050
7051 -- Return False if True range
7052
7053 if Is_True (Right) then
7054 return False_Range;
7055 end if;
7056
7057 -- Here if not trivial case
7058
7059 declare
7060 Result : RList (1 .. Right'Length + 1);
7061 -- May need one more entry for gap at beginning and end
7062
7063 Count : Nat := 0;
7064 -- Number of entries stored in Result
7065
7066 begin
7067 -- Gap at start
7068
7069 if Right (Right'First).Lo > TLo then
7070 Count := Count + 1;
7071 Result (Count) := REnt'(TLo, Right (Right'First).Lo - 1);
7072 end if;
7073
7074 -- Gaps between ranges
7075
7076 for J in Right'First .. Right'Last - 1 loop
7077 Count := Count + 1;
7078 Result (Count) :=
7079 REnt'(Right (J).Hi + 1, Right (J + 1).Lo - 1);
7080 end loop;
7081
7082 -- Gap at end
7083
7084 if Right (Right'Last).Hi < THi then
7085 Count := Count + 1;
7086 Result (Count) := REnt'(Right (Right'Last).Hi + 1, THi);
7087 end if;
7088
7089 return Result (1 .. Count);
7090 end;
7091 end "not";
7092
7093 ----------
7094 -- "or" --
7095 ----------
7096
7097 function "or" (Left : RList; Right : RList) return RList is
7098 FEnt : REnt;
7099 -- First range of result
7100
7101 SLeft : Nat := Left'First;
7102 -- Start of rest of left entries
7103
7104 SRight : Nat := Right'First;
7105 -- Start of rest of right entries
7106
7107 begin
7108 -- If either range is True, return True
7109
7110 if Is_True (Left) or else Is_True (Right) then
7111 return True_Range;
7112 end if;
7113
7114 -- If either range is False (empty), return the other
7115
7116 if Is_False (Left) then
7117 return Right;
7118 elsif Is_False (Right) then
7119 return Left;
7120 end if;
7121
7122 -- Initialize result first entry from left or right operand depending
7123 -- on which starts with the lower range.
7124
7125 if Left (SLeft).Lo < Right (SRight).Lo then
7126 FEnt := Left (SLeft);
7127 SLeft := SLeft + 1;
7128 else
7129 FEnt := Right (SRight);
7130 SRight := SRight + 1;
7131 end if;
7132
7133 -- This loop eats ranges from left and right operands that are
7134 -- contiguous with the first range we are gathering.
7135
7136 loop
7137 -- Eat first entry in left operand if contiguous or overlapped by
7138 -- gathered first operand of result.
7139
7140 if SLeft <= Left'Last
7141 and then Left (SLeft).Lo <= FEnt.Hi + 1
7142 then
7143 FEnt.Hi := UI_Max (FEnt.Hi, Left (SLeft).Hi);
7144 SLeft := SLeft + 1;
7145
7146 -- Eat first entry in right operand if contiguous or overlapped by
7147 -- gathered right operand of result.
7148
7149 elsif SRight <= Right'Last
7150 and then Right (SRight).Lo <= FEnt.Hi + 1
7151 then
7152 FEnt.Hi := UI_Max (FEnt.Hi, Right (SRight).Hi);
7153 SRight := SRight + 1;
7154
7155 -- All done if no more entries to eat
7156
7157 else
7158 exit;
7159 end if;
7160 end loop;
7161
7162 -- Obtain result as the first entry we just computed, concatenated
7163 -- to the "or" of the remaining results (if one operand is empty,
7164 -- this will just concatenate with the other
7165
7166 return
7167 FEnt & (Left (SLeft .. Left'Last) or Right (SRight .. Right'Last));
7168 end "or";
7169
7170 -----------------
7171 -- Build_Range --
7172 -----------------
7173
7174 function Build_Range (Lo : Uint; Hi : Uint) return Node_Id is
7175 Result : Node_Id;
7176
7177 begin
7178 Result :=
7179 Make_Range (Loc,
7180 Low_Bound => Build_Val (Lo),
7181 High_Bound => Build_Val (Hi));
7182 Set_Etype (Result, Btyp);
7183 Set_Analyzed (Result);
7184
7185 return Result;
7186 end Build_Range;
7187
7188 ---------------
7189 -- Build_Val --
7190 ---------------
7191
7192 function Build_Val (V : Uint) return Node_Id is
7193 Result : Node_Id;
7194
7195 begin
7196 if Is_Enumeration_Type (Typ) then
7197 Result := Get_Enum_Lit_From_Pos (Typ, V, Loc);
7198 else
7199 Result := Make_Integer_Literal (Loc, V);
7200 end if;
7201
7202 Set_Etype (Result, Btyp);
7203 Set_Is_Static_Expression (Result);
7204 Set_Analyzed (Result);
7205 return Result;
7206 end Build_Val;
7207
7208 ---------------
7209 -- Get_RList --
7210 ---------------
7211
7212 function Get_RList (Exp : Node_Id) return RList is
7213 Op : Node_Kind;
7214 Val : Uint;
7215
7216 begin
7217 -- Static expression can only be true or false
7218
7219 if Is_OK_Static_Expression (Exp) then
7220
7221 -- For False
7222
7223 if Expr_Value (Exp) = 0 then
7224 return False_Range;
7225 else
7226 return True_Range;
7227 end if;
7228 end if;
7229
7230 -- Otherwise test node type
7231
7232 Op := Nkind (Exp);
7233
7234 case Op is
7235
7236 -- And
7237
7238 when N_Op_And | N_And_Then =>
7239 return Get_RList (Left_Opnd (Exp))
7240 and
7241 Get_RList (Right_Opnd (Exp));
7242
7243 -- Or
7244
7245 when N_Op_Or | N_Or_Else =>
7246 return Get_RList (Left_Opnd (Exp))
7247 or
7248 Get_RList (Right_Opnd (Exp));
7249
7250 -- Not
7251
7252 when N_Op_Not =>
7253 return not Get_RList (Right_Opnd (Exp));
7254
7255 -- Comparisons of type with static value
7256
7257 when N_Op_Compare =>
7258
7259 -- Type is left operand
7260
7261 if Is_Type_Ref (Left_Opnd (Exp))
7262 and then Is_OK_Static_Expression (Right_Opnd (Exp))
7263 then
7264 Val := Expr_Value (Right_Opnd (Exp));
7265
7266 -- Typ is right operand
7267
7268 elsif Is_Type_Ref (Right_Opnd (Exp))
7269 and then Is_OK_Static_Expression (Left_Opnd (Exp))
7270 then
7271 Val := Expr_Value (Left_Opnd (Exp));
7272
7273 -- Invert sense of comparison
7274
7275 case Op is
7276 when N_Op_Gt => Op := N_Op_Lt;
7277 when N_Op_Lt => Op := N_Op_Gt;
7278 when N_Op_Ge => Op := N_Op_Le;
7279 when N_Op_Le => Op := N_Op_Ge;
7280 when others => null;
7281 end case;
7282
7283 -- Other cases are non-static
7284
7285 else
7286 raise Non_Static;
7287 end if;
7288
7289 -- Construct range according to comparison operation
7290
7291 case Op is
7292 when N_Op_Eq =>
7293 return RList'(1 => REnt'(Val, Val));
7294
7295 when N_Op_Ge =>
7296 return RList'(1 => REnt'(Val, BHi));
7297
7298 when N_Op_Gt =>
7299 return RList'(1 => REnt'(Val + 1, BHi));
7300
7301 when N_Op_Le =>
7302 return RList'(1 => REnt'(BLo, Val));
7303
7304 when N_Op_Lt =>
7305 return RList'(1 => REnt'(BLo, Val - 1));
7306
7307 when N_Op_Ne =>
7308 return RList'(REnt'(BLo, Val - 1),
7309 REnt'(Val + 1, BHi));
7310
7311 when others =>
7312 raise Program_Error;
7313 end case;
7314
7315 -- Membership (IN)
7316
7317 when N_In =>
7318 if not Is_Type_Ref (Left_Opnd (Exp)) then
7319 raise Non_Static;
7320 end if;
7321
7322 if Present (Right_Opnd (Exp)) then
7323 return Membership_Entry (Right_Opnd (Exp));
7324 else
7325 return Membership_Entries (First (Alternatives (Exp)));
7326 end if;
7327
7328 -- Negative membership (NOT IN)
7329
7330 when N_Not_In =>
7331 if not Is_Type_Ref (Left_Opnd (Exp)) then
7332 raise Non_Static;
7333 end if;
7334
7335 if Present (Right_Opnd (Exp)) then
7336 return not Membership_Entry (Right_Opnd (Exp));
7337 else
7338 return not Membership_Entries (First (Alternatives (Exp)));
7339 end if;
7340
7341 -- Function call, may be call to static predicate
7342
7343 when N_Function_Call =>
7344 if Is_Entity_Name (Name (Exp)) then
7345 declare
7346 Ent : constant Entity_Id := Entity (Name (Exp));
7347 begin
7348 if Is_Predicate_Function (Ent)
7349 or else
7350 Is_Predicate_Function_M (Ent)
7351 then
7352 return Stat_Pred (Etype (First_Formal (Ent)));
7353 end if;
7354 end;
7355 end if;
7356
7357 -- Other function call cases are non-static
7358
7359 raise Non_Static;
7360
7361 -- Qualified expression, dig out the expression
7362
7363 when N_Qualified_Expression =>
7364 return Get_RList (Expression (Exp));
7365
7366 -- Xor operator
7367
7368 when N_Op_Xor =>
7369 return (Get_RList (Left_Opnd (Exp))
7370 and not Get_RList (Right_Opnd (Exp)))
7371 or (Get_RList (Right_Opnd (Exp))
7372 and not Get_RList (Left_Opnd (Exp)));
7373
7374 -- Any other node type is non-static
7375
7376 when others =>
7377 raise Non_Static;
7378 end case;
7379 end Get_RList;
7380
7381 ------------
7382 -- Hi_Val --
7383 ------------
7384
7385 function Hi_Val (N : Node_Id) return Uint is
7386 begin
7387 if Is_Static_Expression (N) then
7388 return Expr_Value (N);
7389 else
7390 pragma Assert (Nkind (N) = N_Range);
7391 return Expr_Value (High_Bound (N));
7392 end if;
7393 end Hi_Val;
7394
7395 --------------
7396 -- Is_False --
7397 --------------
7398
7399 function Is_False (R : RList) return Boolean is
7400 begin
7401 return R'Length = 0;
7402 end Is_False;
7403
7404 -------------
7405 -- Is_True --
7406 -------------
7407
7408 function Is_True (R : RList) return Boolean is
7409 begin
7410 return R'Length = 1
7411 and then R (R'First).Lo = BLo
7412 and then R (R'First).Hi = BHi;
7413 end Is_True;
7414
7415 -----------------
7416 -- Is_Type_Ref --
7417 -----------------
7418
7419 function Is_Type_Ref (N : Node_Id) return Boolean is
7420 begin
7421 return Nkind (N) = N_Identifier and then Chars (N) = Nam;
7422 end Is_Type_Ref;
7423
7424 ------------
7425 -- Lo_Val --
7426 ------------
7427
7428 function Lo_Val (N : Node_Id) return Uint is
7429 begin
7430 if Is_Static_Expression (N) then
7431 return Expr_Value (N);
7432 else
7433 pragma Assert (Nkind (N) = N_Range);
7434 return Expr_Value (Low_Bound (N));
7435 end if;
7436 end Lo_Val;
7437
7438 ------------------------
7439 -- Membership_Entries --
7440 ------------------------
7441
7442 function Membership_Entries (N : Node_Id) return RList is
7443 begin
7444 if No (Next (N)) then
7445 return Membership_Entry (N);
7446 else
7447 return Membership_Entry (N) or Membership_Entries (Next (N));
7448 end if;
7449 end Membership_Entries;
7450
7451 ----------------------
7452 -- Membership_Entry --
7453 ----------------------
7454
7455 function Membership_Entry (N : Node_Id) return RList is
7456 Val : Uint;
7457 SLo : Uint;
7458 SHi : Uint;
7459
7460 begin
7461 -- Range case
7462
7463 if Nkind (N) = N_Range then
7464 if not Is_Static_Expression (Low_Bound (N))
7465 or else
7466 not Is_Static_Expression (High_Bound (N))
7467 then
7468 raise Non_Static;
7469 else
7470 SLo := Expr_Value (Low_Bound (N));
7471 SHi := Expr_Value (High_Bound (N));
7472 return RList'(1 => REnt'(SLo, SHi));
7473 end if;
7474
7475 -- Static expression case
7476
7477 elsif Is_Static_Expression (N) then
7478 Val := Expr_Value (N);
7479 return RList'(1 => REnt'(Val, Val));
7480
7481 -- Identifier (other than static expression) case
7482
7483 else pragma Assert (Nkind (N) = N_Identifier);
7484
7485 -- Type case
7486
7487 if Is_Type (Entity (N)) then
7488
7489 -- If type has predicates, process them
7490
7491 if Has_Predicates (Entity (N)) then
7492 return Stat_Pred (Entity (N));
7493
7494 -- For static subtype without predicates, get range
7495
7496 elsif Is_Static_Subtype (Entity (N)) then
7497 SLo := Expr_Value (Type_Low_Bound (Entity (N)));
7498 SHi := Expr_Value (Type_High_Bound (Entity (N)));
7499 return RList'(1 => REnt'(SLo, SHi));
7500
7501 -- Any other type makes us non-static
7502
7503 else
7504 raise Non_Static;
7505 end if;
7506
7507 -- Any other kind of identifier in predicate (e.g. a non-static
7508 -- expression value) means this is not a static predicate.
7509
7510 else
7511 raise Non_Static;
7512 end if;
7513 end if;
7514 end Membership_Entry;
7515
7516 ---------------
7517 -- Stat_Pred --
7518 ---------------
7519
7520 function Stat_Pred (Typ : Entity_Id) return RList is
7521 begin
7522 -- Not static if type does not have static predicates
7523
7524 if not Has_Predicates (Typ) or else No (Static_Predicate (Typ)) then
7525 raise Non_Static;
7526 end if;
7527
7528 -- Otherwise we convert the predicate list to a range list
7529
7530 declare
7531 Result : RList (1 .. List_Length (Static_Predicate (Typ)));
7532 P : Node_Id;
7533
7534 begin
7535 P := First (Static_Predicate (Typ));
7536 for J in Result'Range loop
7537 Result (J) := REnt'(Lo_Val (P), Hi_Val (P));
7538 Next (P);
7539 end loop;
7540
7541 return Result;
7542 end;
7543 end Stat_Pred;
7544
7545 -- Start of processing for Build_Static_Predicate
7546
7547 begin
7548 -- Now analyze the expression to see if it is a static predicate
7549
7550 declare
7551 Ranges : constant RList := Get_RList (Expr);
7552 -- Range list from expression if it is static
7553
7554 Plist : List_Id;
7555
7556 begin
7557 -- Convert range list into a form for the static predicate. In the
7558 -- Ranges array, we just have raw ranges, these must be converted
7559 -- to properly typed and analyzed static expressions or range nodes.
7560
7561 -- Note: here we limit ranges to the ranges of the subtype, so that
7562 -- a predicate is always false for values outside the subtype. That
7563 -- seems fine, such values are invalid anyway, and considering them
7564 -- to fail the predicate seems allowed and friendly, and furthermore
7565 -- simplifies processing for case statements and loops.
7566
7567 Plist := New_List;
7568
7569 for J in Ranges'Range loop
7570 declare
7571 Lo : Uint := Ranges (J).Lo;
7572 Hi : Uint := Ranges (J).Hi;
7573
7574 begin
7575 -- Ignore completely out of range entry
7576
7577 if Hi < TLo or else Lo > THi then
7578 null;
7579
7580 -- Otherwise process entry
7581
7582 else
7583 -- Adjust out of range value to subtype range
7584
7585 if Lo < TLo then
7586 Lo := TLo;
7587 end if;
7588
7589 if Hi > THi then
7590 Hi := THi;
7591 end if;
7592
7593 -- Convert range into required form
7594
7595 Append_To (Plist, Build_Range (Lo, Hi));
7596 end if;
7597 end;
7598 end loop;
7599
7600 -- Processing was successful and all entries were static, so now we
7601 -- can store the result as the predicate list.
7602
7603 Set_Static_Predicate (Typ, Plist);
7604
7605 -- The processing for static predicates put the expression into
7606 -- canonical form as a series of ranges. It also eliminated
7607 -- duplicates and collapsed and combined ranges. We might as well
7608 -- replace the alternatives list of the right operand of the
7609 -- membership test with the static predicate list, which will
7610 -- usually be more efficient.
7611
7612 declare
7613 New_Alts : constant List_Id := New_List;
7614 Old_Node : Node_Id;
7615 New_Node : Node_Id;
7616
7617 begin
7618 Old_Node := First (Plist);
7619 while Present (Old_Node) loop
7620 New_Node := New_Copy (Old_Node);
7621
7622 if Nkind (New_Node) = N_Range then
7623 Set_Low_Bound (New_Node, New_Copy (Low_Bound (Old_Node)));
7624 Set_High_Bound (New_Node, New_Copy (High_Bound (Old_Node)));
7625 end if;
7626
7627 Append_To (New_Alts, New_Node);
7628 Next (Old_Node);
7629 end loop;
7630
7631 -- If empty list, replace by False
7632
7633 if Is_Empty_List (New_Alts) then
7634 Rewrite (Expr, New_Occurrence_Of (Standard_False, Loc));
7635
7636 -- Else replace by set membership test
7637
7638 else
7639 Rewrite (Expr,
7640 Make_In (Loc,
7641 Left_Opnd => Make_Identifier (Loc, Nam),
7642 Right_Opnd => Empty,
7643 Alternatives => New_Alts));
7644
7645 -- Resolve new expression in function context
7646
7647 Install_Formals (Predicate_Function (Typ));
7648 Push_Scope (Predicate_Function (Typ));
7649 Analyze_And_Resolve (Expr, Standard_Boolean);
7650 Pop_Scope;
7651 end if;
7652 end;
7653 end;
7654
7655 -- If non-static, return doing nothing
7656
7657 exception
7658 when Non_Static =>
7659 return;
7660 end Build_Static_Predicate;
7661
7662 -----------------------------------------
7663 -- Check_Aspect_At_End_Of_Declarations --
7664 -----------------------------------------
7665
7666 procedure Check_Aspect_At_End_Of_Declarations (ASN : Node_Id) is
7667 Ent : constant Entity_Id := Entity (ASN);
7668 Ident : constant Node_Id := Identifier (ASN);
7669 A_Id : constant Aspect_Id := Get_Aspect_Id (Chars (Ident));
7670
7671 End_Decl_Expr : constant Node_Id := Entity (Ident);
7672 -- Expression to be analyzed at end of declarations
7673
7674 Freeze_Expr : constant Node_Id := Expression (ASN);
7675 -- Expression from call to Check_Aspect_At_Freeze_Point
7676
7677 T : constant Entity_Id := Etype (Freeze_Expr);
7678 -- Type required for preanalyze call
7679
7680 Err : Boolean;
7681 -- Set False if error
7682
7683 -- On entry to this procedure, Entity (Ident) contains a copy of the
7684 -- original expression from the aspect, saved for this purpose, and
7685 -- but Expression (Ident) is a preanalyzed copy of the expression,
7686 -- preanalyzed just after the freeze point.
7687
7688 procedure Check_Overloaded_Name;
7689 -- For aspects whose expression is simply a name, this routine checks if
7690 -- the name is overloaded or not. If so, it verifies there is an
7691 -- interpretation that matches the entity obtained at the freeze point,
7692 -- otherwise the compiler complains.
7693
7694 ---------------------------
7695 -- Check_Overloaded_Name --
7696 ---------------------------
7697
7698 procedure Check_Overloaded_Name is
7699 begin
7700 if not Is_Overloaded (End_Decl_Expr) then
7701 Err := Entity (End_Decl_Expr) /= Entity (Freeze_Expr);
7702
7703 else
7704 Err := True;
7705
7706 declare
7707 Index : Interp_Index;
7708 It : Interp;
7709
7710 begin
7711 Get_First_Interp (End_Decl_Expr, Index, It);
7712 while Present (It.Typ) loop
7713 if It.Nam = Entity (Freeze_Expr) then
7714 Err := False;
7715 exit;
7716 end if;
7717
7718 Get_Next_Interp (Index, It);
7719 end loop;
7720 end;
7721 end if;
7722 end Check_Overloaded_Name;
7723
7724 -- Start of processing for Check_Aspect_At_End_Of_Declarations
7725
7726 begin
7727 -- Case of aspects Dimension, Dimension_System and Synchronization
7728
7729 if A_Id = Aspect_Synchronization then
7730 return;
7731
7732 -- Case of stream attributes, just have to compare entities. However,
7733 -- the expression is just a name (possibly overloaded), and there may
7734 -- be stream operations declared for unrelated types, so we just need
7735 -- to verify that one of these interpretations is the one available at
7736 -- at the freeze point.
7737
7738 elsif A_Id = Aspect_Input or else
7739 A_Id = Aspect_Output or else
7740 A_Id = Aspect_Read or else
7741 A_Id = Aspect_Write
7742 then
7743 Analyze (End_Decl_Expr);
7744 Check_Overloaded_Name;
7745
7746 elsif A_Id = Aspect_Variable_Indexing or else
7747 A_Id = Aspect_Constant_Indexing or else
7748 A_Id = Aspect_Default_Iterator or else
7749 A_Id = Aspect_Iterator_Element
7750 then
7751 -- Make type unfrozen before analysis, to prevent spurious errors
7752 -- about late attributes.
7753
7754 Set_Is_Frozen (Ent, False);
7755 Analyze (End_Decl_Expr);
7756 Set_Is_Frozen (Ent, True);
7757
7758 -- If the end of declarations comes before any other freeze
7759 -- point, the Freeze_Expr is not analyzed: no check needed.
7760
7761 if Analyzed (Freeze_Expr) and then not In_Instance then
7762 Check_Overloaded_Name;
7763 else
7764 Err := False;
7765 end if;
7766
7767 -- All other cases
7768
7769 else
7770 -- In a generic context the aspect expressions have not been
7771 -- preanalyzed, so do it now. There are no conformance checks
7772 -- to perform in this case.
7773
7774 if No (T) then
7775 Check_Aspect_At_Freeze_Point (ASN);
7776 return;
7777
7778 -- The default values attributes may be defined in the private part,
7779 -- and the analysis of the expression may take place when only the
7780 -- partial view is visible. The expression must be scalar, so use
7781 -- the full view to resolve.
7782
7783 elsif (A_Id = Aspect_Default_Value
7784 or else
7785 A_Id = Aspect_Default_Component_Value)
7786 and then Is_Private_Type (T)
7787 then
7788 Preanalyze_Spec_Expression (End_Decl_Expr, Full_View (T));
7789 else
7790 Preanalyze_Spec_Expression (End_Decl_Expr, T);
7791 end if;
7792
7793 Err := not Fully_Conformant_Expressions (End_Decl_Expr, Freeze_Expr);
7794 end if;
7795
7796 -- Output error message if error
7797
7798 if Err then
7799 Error_Msg_NE
7800 ("visibility of aspect for& changes after freeze point",
7801 ASN, Ent);
7802 Error_Msg_NE
7803 ("info: & is frozen here, aspects evaluated at this point??",
7804 Freeze_Node (Ent), Ent);
7805 end if;
7806 end Check_Aspect_At_End_Of_Declarations;
7807
7808 ----------------------------------
7809 -- Check_Aspect_At_Freeze_Point --
7810 ----------------------------------
7811
7812 procedure Check_Aspect_At_Freeze_Point (ASN : Node_Id) is
7813 Ident : constant Node_Id := Identifier (ASN);
7814 -- Identifier (use Entity field to save expression)
7815
7816 A_Id : constant Aspect_Id := Get_Aspect_Id (Chars (Ident));
7817
7818 T : Entity_Id := Empty;
7819 -- Type required for preanalyze call
7820
7821 begin
7822 -- On entry to this procedure, Entity (Ident) contains a copy of the
7823 -- original expression from the aspect, saved for this purpose.
7824
7825 -- On exit from this procedure Entity (Ident) is unchanged, still
7826 -- containing that copy, but Expression (Ident) is a preanalyzed copy
7827 -- of the expression, preanalyzed just after the freeze point.
7828
7829 -- Make a copy of the expression to be preanalyzed
7830
7831 Set_Expression (ASN, New_Copy_Tree (Entity (Ident)));
7832
7833 -- Find type for preanalyze call
7834
7835 case A_Id is
7836
7837 -- No_Aspect should be impossible
7838
7839 when No_Aspect =>
7840 raise Program_Error;
7841
7842 -- Aspects taking an optional boolean argument
7843
7844 when Boolean_Aspects |
7845 Library_Unit_Aspects =>
7846
7847 T := Standard_Boolean;
7848
7849 -- Aspects corresponding to attribute definition clauses
7850
7851 when Aspect_Address =>
7852 T := RTE (RE_Address);
7853
7854 when Aspect_Attach_Handler =>
7855 T := RTE (RE_Interrupt_ID);
7856
7857 when Aspect_Bit_Order | Aspect_Scalar_Storage_Order =>
7858 T := RTE (RE_Bit_Order);
7859
7860 when Aspect_Convention =>
7861 return;
7862
7863 when Aspect_CPU =>
7864 T := RTE (RE_CPU_Range);
7865
7866 -- Default_Component_Value is resolved with the component type
7867
7868 when Aspect_Default_Component_Value =>
7869 T := Component_Type (Entity (ASN));
7870
7871 -- Default_Value is resolved with the type entity in question
7872
7873 when Aspect_Default_Value =>
7874 T := Entity (ASN);
7875
7876 -- Depends is a delayed aspect because it mentiones names first
7877 -- introduced by aspect Global which is already delayed. There is
7878 -- no action to be taken with respect to the aspect itself as the
7879 -- analysis is done by the corresponding pragma.
7880
7881 when Aspect_Depends =>
7882 return;
7883
7884 when Aspect_Dispatching_Domain =>
7885 T := RTE (RE_Dispatching_Domain);
7886
7887 when Aspect_External_Tag =>
7888 T := Standard_String;
7889
7890 when Aspect_External_Name =>
7891 T := Standard_String;
7892
7893 -- Global is a delayed aspect because it may reference names that
7894 -- have not been declared yet. There is no action to be taken with
7895 -- respect to the aspect itself as the reference checking is done
7896 -- on the corresponding pragma.
7897
7898 when Aspect_Global =>
7899 return;
7900
7901 when Aspect_Link_Name =>
7902 T := Standard_String;
7903
7904 when Aspect_Priority | Aspect_Interrupt_Priority =>
7905 T := Standard_Integer;
7906
7907 when Aspect_Relative_Deadline =>
7908 T := RTE (RE_Time_Span);
7909
7910 when Aspect_Small =>
7911 T := Universal_Real;
7912
7913 -- For a simple storage pool, we have to retrieve the type of the
7914 -- pool object associated with the aspect's corresponding attribute
7915 -- definition clause.
7916
7917 when Aspect_Simple_Storage_Pool =>
7918 T := Etype (Expression (Aspect_Rep_Item (ASN)));
7919
7920 when Aspect_Storage_Pool =>
7921 T := Class_Wide_Type (RTE (RE_Root_Storage_Pool));
7922
7923 when Aspect_Alignment |
7924 Aspect_Component_Size |
7925 Aspect_Machine_Radix |
7926 Aspect_Object_Size |
7927 Aspect_Size |
7928 Aspect_Storage_Size |
7929 Aspect_Stream_Size |
7930 Aspect_Value_Size =>
7931 T := Any_Integer;
7932
7933 when Aspect_Synchronization =>
7934 return;
7935
7936 -- Special case, the expression of these aspects is just an entity
7937 -- that does not need any resolution, so just analyze.
7938
7939 when Aspect_Input |
7940 Aspect_Output |
7941 Aspect_Read |
7942 Aspect_Suppress |
7943 Aspect_Unsuppress |
7944 Aspect_Warnings |
7945 Aspect_Write =>
7946 Analyze (Expression (ASN));
7947 return;
7948
7949 -- Same for Iterator aspects, where the expression is a function
7950 -- name. Legality rules are checked separately.
7951
7952 when Aspect_Constant_Indexing |
7953 Aspect_Default_Iterator |
7954 Aspect_Iterator_Element |
7955 Aspect_Variable_Indexing =>
7956 Analyze (Expression (ASN));
7957 return;
7958
7959 -- Invariant/Predicate take boolean expressions
7960
7961 when Aspect_Dynamic_Predicate |
7962 Aspect_Invariant |
7963 Aspect_Predicate |
7964 Aspect_Static_Predicate |
7965 Aspect_Type_Invariant =>
7966 T := Standard_Boolean;
7967
7968 -- Here is the list of aspects that don't require delay analysis
7969
7970 when Aspect_Abstract_State |
7971 Aspect_Contract_Cases |
7972 Aspect_Dimension |
7973 Aspect_Dimension_System |
7974 Aspect_Implicit_Dereference |
7975 Aspect_Post |
7976 Aspect_Postcondition |
7977 Aspect_Pre |
7978 Aspect_Precondition |
7979 Aspect_Refined_Depends |
7980 Aspect_Refined_Global |
7981 Aspect_Refined_Post |
7982 Aspect_Refined_Pre |
7983 Aspect_SPARK_Mode |
7984 Aspect_Test_Case =>
7985 raise Program_Error;
7986
7987 end case;
7988
7989 -- Do the preanalyze call
7990
7991 Preanalyze_Spec_Expression (Expression (ASN), T);
7992 end Check_Aspect_At_Freeze_Point;
7993
7994 -----------------------------------
7995 -- Check_Constant_Address_Clause --
7996 -----------------------------------
7997
7998 procedure Check_Constant_Address_Clause
7999 (Expr : Node_Id;
8000 U_Ent : Entity_Id)
8001 is
8002 procedure Check_At_Constant_Address (Nod : Node_Id);
8003 -- Checks that the given node N represents a name whose 'Address is
8004 -- constant (in the same sense as OK_Constant_Address_Clause, i.e. the
8005 -- address value is the same at the point of declaration of U_Ent and at
8006 -- the time of elaboration of the address clause.
8007
8008 procedure Check_Expr_Constants (Nod : Node_Id);
8009 -- Checks that Nod meets the requirements for a constant address clause
8010 -- in the sense of the enclosing procedure.
8011
8012 procedure Check_List_Constants (Lst : List_Id);
8013 -- Check that all elements of list Lst meet the requirements for a
8014 -- constant address clause in the sense of the enclosing procedure.
8015
8016 -------------------------------
8017 -- Check_At_Constant_Address --
8018 -------------------------------
8019
8020 procedure Check_At_Constant_Address (Nod : Node_Id) is
8021 begin
8022 if Is_Entity_Name (Nod) then
8023 if Present (Address_Clause (Entity ((Nod)))) then
8024 Error_Msg_NE
8025 ("invalid address clause for initialized object &!",
8026 Nod, U_Ent);
8027 Error_Msg_NE
8028 ("address for& cannot" &
8029 " depend on another address clause! (RM 13.1(22))!",
8030 Nod, U_Ent);
8031
8032 elsif In_Same_Source_Unit (Entity (Nod), U_Ent)
8033 and then Sloc (U_Ent) < Sloc (Entity (Nod))
8034 then
8035 Error_Msg_NE
8036 ("invalid address clause for initialized object &!",
8037 Nod, U_Ent);
8038 Error_Msg_Node_2 := U_Ent;
8039 Error_Msg_NE
8040 ("\& must be defined before & (RM 13.1(22))!",
8041 Nod, Entity (Nod));
8042 end if;
8043
8044 elsif Nkind (Nod) = N_Selected_Component then
8045 declare
8046 T : constant Entity_Id := Etype (Prefix (Nod));
8047
8048 begin
8049 if (Is_Record_Type (T)
8050 and then Has_Discriminants (T))
8051 or else
8052 (Is_Access_Type (T)
8053 and then Is_Record_Type (Designated_Type (T))
8054 and then Has_Discriminants (Designated_Type (T)))
8055 then
8056 Error_Msg_NE
8057 ("invalid address clause for initialized object &!",
8058 Nod, U_Ent);
8059 Error_Msg_N
8060 ("\address cannot depend on component" &
8061 " of discriminated record (RM 13.1(22))!",
8062 Nod);
8063 else
8064 Check_At_Constant_Address (Prefix (Nod));
8065 end if;
8066 end;
8067
8068 elsif Nkind (Nod) = N_Indexed_Component then
8069 Check_At_Constant_Address (Prefix (Nod));
8070 Check_List_Constants (Expressions (Nod));
8071
8072 else
8073 Check_Expr_Constants (Nod);
8074 end if;
8075 end Check_At_Constant_Address;
8076
8077 --------------------------
8078 -- Check_Expr_Constants --
8079 --------------------------
8080
8081 procedure Check_Expr_Constants (Nod : Node_Id) is
8082 Loc_U_Ent : constant Source_Ptr := Sloc (U_Ent);
8083 Ent : Entity_Id := Empty;
8084
8085 begin
8086 if Nkind (Nod) in N_Has_Etype
8087 and then Etype (Nod) = Any_Type
8088 then
8089 return;
8090 end if;
8091
8092 case Nkind (Nod) is
8093 when N_Empty | N_Error =>
8094 return;
8095
8096 when N_Identifier | N_Expanded_Name =>
8097 Ent := Entity (Nod);
8098
8099 -- We need to look at the original node if it is different
8100 -- from the node, since we may have rewritten things and
8101 -- substituted an identifier representing the rewrite.
8102
8103 if Original_Node (Nod) /= Nod then
8104 Check_Expr_Constants (Original_Node (Nod));
8105
8106 -- If the node is an object declaration without initial
8107 -- value, some code has been expanded, and the expression
8108 -- is not constant, even if the constituents might be
8109 -- acceptable, as in A'Address + offset.
8110
8111 if Ekind (Ent) = E_Variable
8112 and then
8113 Nkind (Declaration_Node (Ent)) = N_Object_Declaration
8114 and then
8115 No (Expression (Declaration_Node (Ent)))
8116 then
8117 Error_Msg_NE
8118 ("invalid address clause for initialized object &!",
8119 Nod, U_Ent);
8120
8121 -- If entity is constant, it may be the result of expanding
8122 -- a check. We must verify that its declaration appears
8123 -- before the object in question, else we also reject the
8124 -- address clause.
8125
8126 elsif Ekind (Ent) = E_Constant
8127 and then In_Same_Source_Unit (Ent, U_Ent)
8128 and then Sloc (Ent) > Loc_U_Ent
8129 then
8130 Error_Msg_NE
8131 ("invalid address clause for initialized object &!",
8132 Nod, U_Ent);
8133 end if;
8134
8135 return;
8136 end if;
8137
8138 -- Otherwise look at the identifier and see if it is OK
8139
8140 if Ekind_In (Ent, E_Named_Integer, E_Named_Real)
8141 or else Is_Type (Ent)
8142 then
8143 return;
8144
8145 elsif
8146 Ekind (Ent) = E_Constant
8147 or else
8148 Ekind (Ent) = E_In_Parameter
8149 then
8150 -- This is the case where we must have Ent defined before
8151 -- U_Ent. Clearly if they are in different units this
8152 -- requirement is met since the unit containing Ent is
8153 -- already processed.
8154
8155 if not In_Same_Source_Unit (Ent, U_Ent) then
8156 return;
8157
8158 -- Otherwise location of Ent must be before the location
8159 -- of U_Ent, that's what prior defined means.
8160
8161 elsif Sloc (Ent) < Loc_U_Ent then
8162 return;
8163
8164 else
8165 Error_Msg_NE
8166 ("invalid address clause for initialized object &!",
8167 Nod, U_Ent);
8168 Error_Msg_Node_2 := U_Ent;
8169 Error_Msg_NE
8170 ("\& must be defined before & (RM 13.1(22))!",
8171 Nod, Ent);
8172 end if;
8173
8174 elsif Nkind (Original_Node (Nod)) = N_Function_Call then
8175 Check_Expr_Constants (Original_Node (Nod));
8176
8177 else
8178 Error_Msg_NE
8179 ("invalid address clause for initialized object &!",
8180 Nod, U_Ent);
8181
8182 if Comes_From_Source (Ent) then
8183 Error_Msg_NE
8184 ("\reference to variable& not allowed"
8185 & " (RM 13.1(22))!", Nod, Ent);
8186 else
8187 Error_Msg_N
8188 ("non-static expression not allowed"
8189 & " (RM 13.1(22))!", Nod);
8190 end if;
8191 end if;
8192
8193 when N_Integer_Literal =>
8194
8195 -- If this is a rewritten unchecked conversion, in a system
8196 -- where Address is an integer type, always use the base type
8197 -- for a literal value. This is user-friendly and prevents
8198 -- order-of-elaboration issues with instances of unchecked
8199 -- conversion.
8200
8201 if Nkind (Original_Node (Nod)) = N_Function_Call then
8202 Set_Etype (Nod, Base_Type (Etype (Nod)));
8203 end if;
8204
8205 when N_Real_Literal |
8206 N_String_Literal |
8207 N_Character_Literal =>
8208 return;
8209
8210 when N_Range =>
8211 Check_Expr_Constants (Low_Bound (Nod));
8212 Check_Expr_Constants (High_Bound (Nod));
8213
8214 when N_Explicit_Dereference =>
8215 Check_Expr_Constants (Prefix (Nod));
8216
8217 when N_Indexed_Component =>
8218 Check_Expr_Constants (Prefix (Nod));
8219 Check_List_Constants (Expressions (Nod));
8220
8221 when N_Slice =>
8222 Check_Expr_Constants (Prefix (Nod));
8223 Check_Expr_Constants (Discrete_Range (Nod));
8224
8225 when N_Selected_Component =>
8226 Check_Expr_Constants (Prefix (Nod));
8227
8228 when N_Attribute_Reference =>
8229 if Nam_In (Attribute_Name (Nod), Name_Address,
8230 Name_Access,
8231 Name_Unchecked_Access,
8232 Name_Unrestricted_Access)
8233 then
8234 Check_At_Constant_Address (Prefix (Nod));
8235
8236 else
8237 Check_Expr_Constants (Prefix (Nod));
8238 Check_List_Constants (Expressions (Nod));
8239 end if;
8240
8241 when N_Aggregate =>
8242 Check_List_Constants (Component_Associations (Nod));
8243 Check_List_Constants (Expressions (Nod));
8244
8245 when N_Component_Association =>
8246 Check_Expr_Constants (Expression (Nod));
8247
8248 when N_Extension_Aggregate =>
8249 Check_Expr_Constants (Ancestor_Part (Nod));
8250 Check_List_Constants (Component_Associations (Nod));
8251 Check_List_Constants (Expressions (Nod));
8252
8253 when N_Null =>
8254 return;
8255
8256 when N_Binary_Op | N_Short_Circuit | N_Membership_Test =>
8257 Check_Expr_Constants (Left_Opnd (Nod));
8258 Check_Expr_Constants (Right_Opnd (Nod));
8259
8260 when N_Unary_Op =>
8261 Check_Expr_Constants (Right_Opnd (Nod));
8262
8263 when N_Type_Conversion |
8264 N_Qualified_Expression |
8265 N_Allocator |
8266 N_Unchecked_Type_Conversion =>
8267 Check_Expr_Constants (Expression (Nod));
8268
8269 when N_Function_Call =>
8270 if not Is_Pure (Entity (Name (Nod))) then
8271 Error_Msg_NE
8272 ("invalid address clause for initialized object &!",
8273 Nod, U_Ent);
8274
8275 Error_Msg_NE
8276 ("\function & is not pure (RM 13.1(22))!",
8277 Nod, Entity (Name (Nod)));
8278
8279 else
8280 Check_List_Constants (Parameter_Associations (Nod));
8281 end if;
8282
8283 when N_Parameter_Association =>
8284 Check_Expr_Constants (Explicit_Actual_Parameter (Nod));
8285
8286 when others =>
8287 Error_Msg_NE
8288 ("invalid address clause for initialized object &!",
8289 Nod, U_Ent);
8290 Error_Msg_NE
8291 ("\must be constant defined before& (RM 13.1(22))!",
8292 Nod, U_Ent);
8293 end case;
8294 end Check_Expr_Constants;
8295
8296 --------------------------
8297 -- Check_List_Constants --
8298 --------------------------
8299
8300 procedure Check_List_Constants (Lst : List_Id) is
8301 Nod1 : Node_Id;
8302
8303 begin
8304 if Present (Lst) then
8305 Nod1 := First (Lst);
8306 while Present (Nod1) loop
8307 Check_Expr_Constants (Nod1);
8308 Next (Nod1);
8309 end loop;
8310 end if;
8311 end Check_List_Constants;
8312
8313 -- Start of processing for Check_Constant_Address_Clause
8314
8315 begin
8316 -- If rep_clauses are to be ignored, no need for legality checks. In
8317 -- particular, no need to pester user about rep clauses that violate
8318 -- the rule on constant addresses, given that these clauses will be
8319 -- removed by Freeze before they reach the back end.
8320
8321 if not Ignore_Rep_Clauses then
8322 Check_Expr_Constants (Expr);
8323 end if;
8324 end Check_Constant_Address_Clause;
8325
8326 ----------------------------------------
8327 -- Check_Record_Representation_Clause --
8328 ----------------------------------------
8329
8330 procedure Check_Record_Representation_Clause (N : Node_Id) is
8331 Loc : constant Source_Ptr := Sloc (N);
8332 Ident : constant Node_Id := Identifier (N);
8333 Rectype : Entity_Id;
8334 Fent : Entity_Id;
8335 CC : Node_Id;
8336 Fbit : Uint;
8337 Lbit : Uint;
8338 Hbit : Uint := Uint_0;
8339 Comp : Entity_Id;
8340 Pcomp : Entity_Id;
8341
8342 Max_Bit_So_Far : Uint;
8343 -- Records the maximum bit position so far. If all field positions
8344 -- are monotonically increasing, then we can skip the circuit for
8345 -- checking for overlap, since no overlap is possible.
8346
8347 Tagged_Parent : Entity_Id := Empty;
8348 -- This is set in the case of a derived tagged type for which we have
8349 -- Is_Fully_Repped_Tagged_Type True (indicating that all components are
8350 -- positioned by record representation clauses). In this case we must
8351 -- check for overlap between components of this tagged type, and the
8352 -- components of its parent. Tagged_Parent will point to this parent
8353 -- type. For all other cases Tagged_Parent is left set to Empty.
8354
8355 Parent_Last_Bit : Uint;
8356 -- Relevant only if Tagged_Parent is set, Parent_Last_Bit indicates the
8357 -- last bit position for any field in the parent type. We only need to
8358 -- check overlap for fields starting below this point.
8359
8360 Overlap_Check_Required : Boolean;
8361 -- Used to keep track of whether or not an overlap check is required
8362
8363 Overlap_Detected : Boolean := False;
8364 -- Set True if an overlap is detected
8365
8366 Ccount : Natural := 0;
8367 -- Number of component clauses in record rep clause
8368
8369 procedure Check_Component_Overlap (C1_Ent, C2_Ent : Entity_Id);
8370 -- Given two entities for record components or discriminants, checks
8371 -- if they have overlapping component clauses and issues errors if so.
8372
8373 procedure Find_Component;
8374 -- Finds component entity corresponding to current component clause (in
8375 -- CC), and sets Comp to the entity, and Fbit/Lbit to the zero origin
8376 -- start/stop bits for the field. If there is no matching component or
8377 -- if the matching component does not have a component clause, then
8378 -- that's an error and Comp is set to Empty, but no error message is
8379 -- issued, since the message was already given. Comp is also set to
8380 -- Empty if the current "component clause" is in fact a pragma.
8381
8382 -----------------------------
8383 -- Check_Component_Overlap --
8384 -----------------------------
8385
8386 procedure Check_Component_Overlap (C1_Ent, C2_Ent : Entity_Id) is
8387 CC1 : constant Node_Id := Component_Clause (C1_Ent);
8388 CC2 : constant Node_Id := Component_Clause (C2_Ent);
8389
8390 begin
8391 if Present (CC1) and then Present (CC2) then
8392
8393 -- Exclude odd case where we have two tag components in the same
8394 -- record, both at location zero. This seems a bit strange, but
8395 -- it seems to happen in some circumstances, perhaps on an error.
8396
8397 if Nam_In (Chars (C1_Ent), Name_uTag, Name_uTag) then
8398 return;
8399 end if;
8400
8401 -- Here we check if the two fields overlap
8402
8403 declare
8404 S1 : constant Uint := Component_Bit_Offset (C1_Ent);
8405 S2 : constant Uint := Component_Bit_Offset (C2_Ent);
8406 E1 : constant Uint := S1 + Esize (C1_Ent);
8407 E2 : constant Uint := S2 + Esize (C2_Ent);
8408
8409 begin
8410 if E2 <= S1 or else E1 <= S2 then
8411 null;
8412 else
8413 Error_Msg_Node_2 := Component_Name (CC2);
8414 Error_Msg_Sloc := Sloc (Error_Msg_Node_2);
8415 Error_Msg_Node_1 := Component_Name (CC1);
8416 Error_Msg_N
8417 ("component& overlaps & #", Component_Name (CC1));
8418 Overlap_Detected := True;
8419 end if;
8420 end;
8421 end if;
8422 end Check_Component_Overlap;
8423
8424 --------------------
8425 -- Find_Component --
8426 --------------------
8427
8428 procedure Find_Component is
8429
8430 procedure Search_Component (R : Entity_Id);
8431 -- Search components of R for a match. If found, Comp is set
8432
8433 ----------------------
8434 -- Search_Component --
8435 ----------------------
8436
8437 procedure Search_Component (R : Entity_Id) is
8438 begin
8439 Comp := First_Component_Or_Discriminant (R);
8440 while Present (Comp) loop
8441
8442 -- Ignore error of attribute name for component name (we
8443 -- already gave an error message for this, so no need to
8444 -- complain here)
8445
8446 if Nkind (Component_Name (CC)) = N_Attribute_Reference then
8447 null;
8448 else
8449 exit when Chars (Comp) = Chars (Component_Name (CC));
8450 end if;
8451
8452 Next_Component_Or_Discriminant (Comp);
8453 end loop;
8454 end Search_Component;
8455
8456 -- Start of processing for Find_Component
8457
8458 begin
8459 -- Return with Comp set to Empty if we have a pragma
8460
8461 if Nkind (CC) = N_Pragma then
8462 Comp := Empty;
8463 return;
8464 end if;
8465
8466 -- Search current record for matching component
8467
8468 Search_Component (Rectype);
8469
8470 -- If not found, maybe component of base type discriminant that is
8471 -- absent from statically constrained first subtype.
8472
8473 if No (Comp) then
8474 Search_Component (Base_Type (Rectype));
8475 end if;
8476
8477 -- If no component, or the component does not reference the component
8478 -- clause in question, then there was some previous error for which
8479 -- we already gave a message, so just return with Comp Empty.
8480
8481 if No (Comp) or else Component_Clause (Comp) /= CC then
8482 Check_Error_Detected;
8483 Comp := Empty;
8484
8485 -- Normal case where we have a component clause
8486
8487 else
8488 Fbit := Component_Bit_Offset (Comp);
8489 Lbit := Fbit + Esize (Comp) - 1;
8490 end if;
8491 end Find_Component;
8492
8493 -- Start of processing for Check_Record_Representation_Clause
8494
8495 begin
8496 Find_Type (Ident);
8497 Rectype := Entity (Ident);
8498
8499 if Rectype = Any_Type then
8500 return;
8501 else
8502 Rectype := Underlying_Type (Rectype);
8503 end if;
8504
8505 -- See if we have a fully repped derived tagged type
8506
8507 declare
8508 PS : constant Entity_Id := Parent_Subtype (Rectype);
8509
8510 begin
8511 if Present (PS) and then Is_Fully_Repped_Tagged_Type (PS) then
8512 Tagged_Parent := PS;
8513
8514 -- Find maximum bit of any component of the parent type
8515
8516 Parent_Last_Bit := UI_From_Int (System_Address_Size - 1);
8517 Pcomp := First_Entity (Tagged_Parent);
8518 while Present (Pcomp) loop
8519 if Ekind_In (Pcomp, E_Discriminant, E_Component) then
8520 if Component_Bit_Offset (Pcomp) /= No_Uint
8521 and then Known_Static_Esize (Pcomp)
8522 then
8523 Parent_Last_Bit :=
8524 UI_Max
8525 (Parent_Last_Bit,
8526 Component_Bit_Offset (Pcomp) + Esize (Pcomp) - 1);
8527 end if;
8528
8529 Next_Entity (Pcomp);
8530 end if;
8531 end loop;
8532 end if;
8533 end;
8534
8535 -- All done if no component clauses
8536
8537 CC := First (Component_Clauses (N));
8538
8539 if No (CC) then
8540 return;
8541 end if;
8542
8543 -- If a tag is present, then create a component clause that places it
8544 -- at the start of the record (otherwise gigi may place it after other
8545 -- fields that have rep clauses).
8546
8547 Fent := First_Entity (Rectype);
8548
8549 if Nkind (Fent) = N_Defining_Identifier
8550 and then Chars (Fent) = Name_uTag
8551 then
8552 Set_Component_Bit_Offset (Fent, Uint_0);
8553 Set_Normalized_Position (Fent, Uint_0);
8554 Set_Normalized_First_Bit (Fent, Uint_0);
8555 Set_Normalized_Position_Max (Fent, Uint_0);
8556 Init_Esize (Fent, System_Address_Size);
8557
8558 Set_Component_Clause (Fent,
8559 Make_Component_Clause (Loc,
8560 Component_Name => Make_Identifier (Loc, Name_uTag),
8561
8562 Position => Make_Integer_Literal (Loc, Uint_0),
8563 First_Bit => Make_Integer_Literal (Loc, Uint_0),
8564 Last_Bit =>
8565 Make_Integer_Literal (Loc,
8566 UI_From_Int (System_Address_Size))));
8567
8568 Ccount := Ccount + 1;
8569 end if;
8570
8571 Max_Bit_So_Far := Uint_Minus_1;
8572 Overlap_Check_Required := False;
8573
8574 -- Process the component clauses
8575
8576 while Present (CC) loop
8577 Find_Component;
8578
8579 if Present (Comp) then
8580 Ccount := Ccount + 1;
8581
8582 -- We need a full overlap check if record positions non-monotonic
8583
8584 if Fbit <= Max_Bit_So_Far then
8585 Overlap_Check_Required := True;
8586 end if;
8587
8588 Max_Bit_So_Far := Lbit;
8589
8590 -- Check bit position out of range of specified size
8591
8592 if Has_Size_Clause (Rectype)
8593 and then RM_Size (Rectype) <= Lbit
8594 then
8595 Error_Msg_N
8596 ("bit number out of range of specified size",
8597 Last_Bit (CC));
8598
8599 -- Check for overlap with tag component
8600
8601 else
8602 if Is_Tagged_Type (Rectype)
8603 and then Fbit < System_Address_Size
8604 then
8605 Error_Msg_NE
8606 ("component overlaps tag field of&",
8607 Component_Name (CC), Rectype);
8608 Overlap_Detected := True;
8609 end if;
8610
8611 if Hbit < Lbit then
8612 Hbit := Lbit;
8613 end if;
8614 end if;
8615
8616 -- Check parent overlap if component might overlap parent field
8617
8618 if Present (Tagged_Parent) and then Fbit <= Parent_Last_Bit then
8619 Pcomp := First_Component_Or_Discriminant (Tagged_Parent);
8620 while Present (Pcomp) loop
8621 if not Is_Tag (Pcomp)
8622 and then Chars (Pcomp) /= Name_uParent
8623 then
8624 Check_Component_Overlap (Comp, Pcomp);
8625 end if;
8626
8627 Next_Component_Or_Discriminant (Pcomp);
8628 end loop;
8629 end if;
8630 end if;
8631
8632 Next (CC);
8633 end loop;
8634
8635 -- Now that we have processed all the component clauses, check for
8636 -- overlap. We have to leave this till last, since the components can
8637 -- appear in any arbitrary order in the representation clause.
8638
8639 -- We do not need this check if all specified ranges were monotonic,
8640 -- as recorded by Overlap_Check_Required being False at this stage.
8641
8642 -- This first section checks if there are any overlapping entries at
8643 -- all. It does this by sorting all entries and then seeing if there are
8644 -- any overlaps. If there are none, then that is decisive, but if there
8645 -- are overlaps, they may still be OK (they may result from fields in
8646 -- different variants).
8647
8648 if Overlap_Check_Required then
8649 Overlap_Check1 : declare
8650
8651 OC_Fbit : array (0 .. Ccount) of Uint;
8652 -- First-bit values for component clauses, the value is the offset
8653 -- of the first bit of the field from start of record. The zero
8654 -- entry is for use in sorting.
8655
8656 OC_Lbit : array (0 .. Ccount) of Uint;
8657 -- Last-bit values for component clauses, the value is the offset
8658 -- of the last bit of the field from start of record. The zero
8659 -- entry is for use in sorting.
8660
8661 OC_Count : Natural := 0;
8662 -- Count of entries in OC_Fbit and OC_Lbit
8663
8664 function OC_Lt (Op1, Op2 : Natural) return Boolean;
8665 -- Compare routine for Sort
8666
8667 procedure OC_Move (From : Natural; To : Natural);
8668 -- Move routine for Sort
8669
8670 package Sorting is new GNAT.Heap_Sort_G (OC_Move, OC_Lt);
8671
8672 -----------
8673 -- OC_Lt --
8674 -----------
8675
8676 function OC_Lt (Op1, Op2 : Natural) return Boolean is
8677 begin
8678 return OC_Fbit (Op1) < OC_Fbit (Op2);
8679 end OC_Lt;
8680
8681 -------------
8682 -- OC_Move --
8683 -------------
8684
8685 procedure OC_Move (From : Natural; To : Natural) is
8686 begin
8687 OC_Fbit (To) := OC_Fbit (From);
8688 OC_Lbit (To) := OC_Lbit (From);
8689 end OC_Move;
8690
8691 -- Start of processing for Overlap_Check
8692
8693 begin
8694 CC := First (Component_Clauses (N));
8695 while Present (CC) loop
8696
8697 -- Exclude component clause already marked in error
8698
8699 if not Error_Posted (CC) then
8700 Find_Component;
8701
8702 if Present (Comp) then
8703 OC_Count := OC_Count + 1;
8704 OC_Fbit (OC_Count) := Fbit;
8705 OC_Lbit (OC_Count) := Lbit;
8706 end if;
8707 end if;
8708
8709 Next (CC);
8710 end loop;
8711
8712 Sorting.Sort (OC_Count);
8713
8714 Overlap_Check_Required := False;
8715 for J in 1 .. OC_Count - 1 loop
8716 if OC_Lbit (J) >= OC_Fbit (J + 1) then
8717 Overlap_Check_Required := True;
8718 exit;
8719 end if;
8720 end loop;
8721 end Overlap_Check1;
8722 end if;
8723
8724 -- If Overlap_Check_Required is still True, then we have to do the full
8725 -- scale overlap check, since we have at least two fields that do
8726 -- overlap, and we need to know if that is OK since they are in
8727 -- different variant, or whether we have a definite problem.
8728
8729 if Overlap_Check_Required then
8730 Overlap_Check2 : declare
8731 C1_Ent, C2_Ent : Entity_Id;
8732 -- Entities of components being checked for overlap
8733
8734 Clist : Node_Id;
8735 -- Component_List node whose Component_Items are being checked
8736
8737 Citem : Node_Id;
8738 -- Component declaration for component being checked
8739
8740 begin
8741 C1_Ent := First_Entity (Base_Type (Rectype));
8742
8743 -- Loop through all components in record. For each component check
8744 -- for overlap with any of the preceding elements on the component
8745 -- list containing the component and also, if the component is in
8746 -- a variant, check against components outside the case structure.
8747 -- This latter test is repeated recursively up the variant tree.
8748
8749 Main_Component_Loop : while Present (C1_Ent) loop
8750 if not Ekind_In (C1_Ent, E_Component, E_Discriminant) then
8751 goto Continue_Main_Component_Loop;
8752 end if;
8753
8754 -- Skip overlap check if entity has no declaration node. This
8755 -- happens with discriminants in constrained derived types.
8756 -- Possibly we are missing some checks as a result, but that
8757 -- does not seem terribly serious.
8758
8759 if No (Declaration_Node (C1_Ent)) then
8760 goto Continue_Main_Component_Loop;
8761 end if;
8762
8763 Clist := Parent (List_Containing (Declaration_Node (C1_Ent)));
8764
8765 -- Loop through component lists that need checking. Check the
8766 -- current component list and all lists in variants above us.
8767
8768 Component_List_Loop : loop
8769
8770 -- If derived type definition, go to full declaration
8771 -- If at outer level, check discriminants if there are any.
8772
8773 if Nkind (Clist) = N_Derived_Type_Definition then
8774 Clist := Parent (Clist);
8775 end if;
8776
8777 -- Outer level of record definition, check discriminants
8778
8779 if Nkind_In (Clist, N_Full_Type_Declaration,
8780 N_Private_Type_Declaration)
8781 then
8782 if Has_Discriminants (Defining_Identifier (Clist)) then
8783 C2_Ent :=
8784 First_Discriminant (Defining_Identifier (Clist));
8785 while Present (C2_Ent) loop
8786 exit when C1_Ent = C2_Ent;
8787 Check_Component_Overlap (C1_Ent, C2_Ent);
8788 Next_Discriminant (C2_Ent);
8789 end loop;
8790 end if;
8791
8792 -- Record extension case
8793
8794 elsif Nkind (Clist) = N_Derived_Type_Definition then
8795 Clist := Empty;
8796
8797 -- Otherwise check one component list
8798
8799 else
8800 Citem := First (Component_Items (Clist));
8801 while Present (Citem) loop
8802 if Nkind (Citem) = N_Component_Declaration then
8803 C2_Ent := Defining_Identifier (Citem);
8804 exit when C1_Ent = C2_Ent;
8805 Check_Component_Overlap (C1_Ent, C2_Ent);
8806 end if;
8807
8808 Next (Citem);
8809 end loop;
8810 end if;
8811
8812 -- Check for variants above us (the parent of the Clist can
8813 -- be a variant, in which case its parent is a variant part,
8814 -- and the parent of the variant part is a component list
8815 -- whose components must all be checked against the current
8816 -- component for overlap).
8817
8818 if Nkind (Parent (Clist)) = N_Variant then
8819 Clist := Parent (Parent (Parent (Clist)));
8820
8821 -- Check for possible discriminant part in record, this
8822 -- is treated essentially as another level in the
8823 -- recursion. For this case the parent of the component
8824 -- list is the record definition, and its parent is the
8825 -- full type declaration containing the discriminant
8826 -- specifications.
8827
8828 elsif Nkind (Parent (Clist)) = N_Record_Definition then
8829 Clist := Parent (Parent ((Clist)));
8830
8831 -- If neither of these two cases, we are at the top of
8832 -- the tree.
8833
8834 else
8835 exit Component_List_Loop;
8836 end if;
8837 end loop Component_List_Loop;
8838
8839 <<Continue_Main_Component_Loop>>
8840 Next_Entity (C1_Ent);
8841
8842 end loop Main_Component_Loop;
8843 end Overlap_Check2;
8844 end if;
8845
8846 -- The following circuit deals with warning on record holes (gaps). We
8847 -- skip this check if overlap was detected, since it makes sense for the
8848 -- programmer to fix this illegality before worrying about warnings.
8849
8850 if not Overlap_Detected and Warn_On_Record_Holes then
8851 Record_Hole_Check : declare
8852 Decl : constant Node_Id := Declaration_Node (Base_Type (Rectype));
8853 -- Full declaration of record type
8854
8855 procedure Check_Component_List
8856 (CL : Node_Id;
8857 Sbit : Uint;
8858 DS : List_Id);
8859 -- Check component list CL for holes. The starting bit should be
8860 -- Sbit. which is zero for the main record component list and set
8861 -- appropriately for recursive calls for variants. DS is set to
8862 -- a list of discriminant specifications to be included in the
8863 -- consideration of components. It is No_List if none to consider.
8864
8865 --------------------------
8866 -- Check_Component_List --
8867 --------------------------
8868
8869 procedure Check_Component_List
8870 (CL : Node_Id;
8871 Sbit : Uint;
8872 DS : List_Id)
8873 is
8874 Compl : Integer;
8875
8876 begin
8877 Compl := Integer (List_Length (Component_Items (CL)));
8878
8879 if DS /= No_List then
8880 Compl := Compl + Integer (List_Length (DS));
8881 end if;
8882
8883 declare
8884 Comps : array (Natural range 0 .. Compl) of Entity_Id;
8885 -- Gather components (zero entry is for sort routine)
8886
8887 Ncomps : Natural := 0;
8888 -- Number of entries stored in Comps (starting at Comps (1))
8889
8890 Citem : Node_Id;
8891 -- One component item or discriminant specification
8892
8893 Nbit : Uint;
8894 -- Starting bit for next component
8895
8896 CEnt : Entity_Id;
8897 -- Component entity
8898
8899 Variant : Node_Id;
8900 -- One variant
8901
8902 function Lt (Op1, Op2 : Natural) return Boolean;
8903 -- Compare routine for Sort
8904
8905 procedure Move (From : Natural; To : Natural);
8906 -- Move routine for Sort
8907
8908 package Sorting is new GNAT.Heap_Sort_G (Move, Lt);
8909
8910 --------
8911 -- Lt --
8912 --------
8913
8914 function Lt (Op1, Op2 : Natural) return Boolean is
8915 begin
8916 return Component_Bit_Offset (Comps (Op1))
8917 <
8918 Component_Bit_Offset (Comps (Op2));
8919 end Lt;
8920
8921 ----------
8922 -- Move --
8923 ----------
8924
8925 procedure Move (From : Natural; To : Natural) is
8926 begin
8927 Comps (To) := Comps (From);
8928 end Move;
8929
8930 begin
8931 -- Gather discriminants into Comp
8932
8933 if DS /= No_List then
8934 Citem := First (DS);
8935 while Present (Citem) loop
8936 if Nkind (Citem) = N_Discriminant_Specification then
8937 declare
8938 Ent : constant Entity_Id :=
8939 Defining_Identifier (Citem);
8940 begin
8941 if Ekind (Ent) = E_Discriminant then
8942 Ncomps := Ncomps + 1;
8943 Comps (Ncomps) := Ent;
8944 end if;
8945 end;
8946 end if;
8947
8948 Next (Citem);
8949 end loop;
8950 end if;
8951
8952 -- Gather component entities into Comp
8953
8954 Citem := First (Component_Items (CL));
8955 while Present (Citem) loop
8956 if Nkind (Citem) = N_Component_Declaration then
8957 Ncomps := Ncomps + 1;
8958 Comps (Ncomps) := Defining_Identifier (Citem);
8959 end if;
8960
8961 Next (Citem);
8962 end loop;
8963
8964 -- Now sort the component entities based on the first bit.
8965 -- Note we already know there are no overlapping components.
8966
8967 Sorting.Sort (Ncomps);
8968
8969 -- Loop through entries checking for holes
8970
8971 Nbit := Sbit;
8972 for J in 1 .. Ncomps loop
8973 CEnt := Comps (J);
8974 Error_Msg_Uint_1 := Component_Bit_Offset (CEnt) - Nbit;
8975
8976 if Error_Msg_Uint_1 > 0 then
8977 Error_Msg_NE
8978 ("?H?^-bit gap before component&",
8979 Component_Name (Component_Clause (CEnt)), CEnt);
8980 end if;
8981
8982 Nbit := Component_Bit_Offset (CEnt) + Esize (CEnt);
8983 end loop;
8984
8985 -- Process variant parts recursively if present
8986
8987 if Present (Variant_Part (CL)) then
8988 Variant := First (Variants (Variant_Part (CL)));
8989 while Present (Variant) loop
8990 Check_Component_List
8991 (Component_List (Variant), Nbit, No_List);
8992 Next (Variant);
8993 end loop;
8994 end if;
8995 end;
8996 end Check_Component_List;
8997
8998 -- Start of processing for Record_Hole_Check
8999
9000 begin
9001 declare
9002 Sbit : Uint;
9003
9004 begin
9005 if Is_Tagged_Type (Rectype) then
9006 Sbit := UI_From_Int (System_Address_Size);
9007 else
9008 Sbit := Uint_0;
9009 end if;
9010
9011 if Nkind (Decl) = N_Full_Type_Declaration
9012 and then Nkind (Type_Definition (Decl)) = N_Record_Definition
9013 then
9014 Check_Component_List
9015 (Component_List (Type_Definition (Decl)),
9016 Sbit,
9017 Discriminant_Specifications (Decl));
9018 end if;
9019 end;
9020 end Record_Hole_Check;
9021 end if;
9022
9023 -- For records that have component clauses for all components, and whose
9024 -- size is less than or equal to 32, we need to know the size in the
9025 -- front end to activate possible packed array processing where the
9026 -- component type is a record.
9027
9028 -- At this stage Hbit + 1 represents the first unused bit from all the
9029 -- component clauses processed, so if the component clauses are
9030 -- complete, then this is the length of the record.
9031
9032 -- For records longer than System.Storage_Unit, and for those where not
9033 -- all components have component clauses, the back end determines the
9034 -- length (it may for example be appropriate to round up the size
9035 -- to some convenient boundary, based on alignment considerations, etc).
9036
9037 if Unknown_RM_Size (Rectype) and then Hbit + 1 <= 32 then
9038
9039 -- Nothing to do if at least one component has no component clause
9040
9041 Comp := First_Component_Or_Discriminant (Rectype);
9042 while Present (Comp) loop
9043 exit when No (Component_Clause (Comp));
9044 Next_Component_Or_Discriminant (Comp);
9045 end loop;
9046
9047 -- If we fall out of loop, all components have component clauses
9048 -- and so we can set the size to the maximum value.
9049
9050 if No (Comp) then
9051 Set_RM_Size (Rectype, Hbit + 1);
9052 end if;
9053 end if;
9054 end Check_Record_Representation_Clause;
9055
9056 ----------------
9057 -- Check_Size --
9058 ----------------
9059
9060 procedure Check_Size
9061 (N : Node_Id;
9062 T : Entity_Id;
9063 Siz : Uint;
9064 Biased : out Boolean)
9065 is
9066 UT : constant Entity_Id := Underlying_Type (T);
9067 M : Uint;
9068
9069 begin
9070 Biased := False;
9071
9072 -- Reject patently improper size values.
9073
9074 if Is_Elementary_Type (T)
9075 and then Siz > UI_From_Int (Int'Last)
9076 then
9077 Error_Msg_N ("Size value too large for elementary type", N);
9078
9079 if Nkind (Original_Node (N)) = N_Op_Expon then
9080 Error_Msg_N
9081 ("\maybe '* was meant, rather than '*'*", Original_Node (N));
9082 end if;
9083 end if;
9084
9085 -- Dismiss generic types
9086
9087 if Is_Generic_Type (T)
9088 or else
9089 Is_Generic_Type (UT)
9090 or else
9091 Is_Generic_Type (Root_Type (UT))
9092 then
9093 return;
9094
9095 -- Guard against previous errors
9096
9097 elsif No (UT) or else UT = Any_Type then
9098 Check_Error_Detected;
9099 return;
9100
9101 -- Check case of bit packed array
9102
9103 elsif Is_Array_Type (UT)
9104 and then Known_Static_Component_Size (UT)
9105 and then Is_Bit_Packed_Array (UT)
9106 then
9107 declare
9108 Asiz : Uint;
9109 Indx : Node_Id;
9110 Ityp : Entity_Id;
9111
9112 begin
9113 Asiz := Component_Size (UT);
9114 Indx := First_Index (UT);
9115 loop
9116 Ityp := Etype (Indx);
9117
9118 -- If non-static bound, then we are not in the business of
9119 -- trying to check the length, and indeed an error will be
9120 -- issued elsewhere, since sizes of non-static array types
9121 -- cannot be set implicitly or explicitly.
9122
9123 if not Is_Static_Subtype (Ityp) then
9124 return;
9125 end if;
9126
9127 -- Otherwise accumulate next dimension
9128
9129 Asiz := Asiz * (Expr_Value (Type_High_Bound (Ityp)) -
9130 Expr_Value (Type_Low_Bound (Ityp)) +
9131 Uint_1);
9132
9133 Next_Index (Indx);
9134 exit when No (Indx);
9135 end loop;
9136
9137 if Asiz <= Siz then
9138 return;
9139
9140 else
9141 Error_Msg_Uint_1 := Asiz;
9142 Error_Msg_NE
9143 ("size for& too small, minimum allowed is ^", N, T);
9144 Set_Esize (T, Asiz);
9145 Set_RM_Size (T, Asiz);
9146 end if;
9147 end;
9148
9149 -- All other composite types are ignored
9150
9151 elsif Is_Composite_Type (UT) then
9152 return;
9153
9154 -- For fixed-point types, don't check minimum if type is not frozen,
9155 -- since we don't know all the characteristics of the type that can
9156 -- affect the size (e.g. a specified small) till freeze time.
9157
9158 elsif Is_Fixed_Point_Type (UT)
9159 and then not Is_Frozen (UT)
9160 then
9161 null;
9162
9163 -- Cases for which a minimum check is required
9164
9165 else
9166 -- Ignore if specified size is correct for the type
9167
9168 if Known_Esize (UT) and then Siz = Esize (UT) then
9169 return;
9170 end if;
9171
9172 -- Otherwise get minimum size
9173
9174 M := UI_From_Int (Minimum_Size (UT));
9175
9176 if Siz < M then
9177
9178 -- Size is less than minimum size, but one possibility remains
9179 -- that we can manage with the new size if we bias the type.
9180
9181 M := UI_From_Int (Minimum_Size (UT, Biased => True));
9182
9183 if Siz < M then
9184 Error_Msg_Uint_1 := M;
9185 Error_Msg_NE
9186 ("size for& too small, minimum allowed is ^", N, T);
9187 Set_Esize (T, M);
9188 Set_RM_Size (T, M);
9189 else
9190 Biased := True;
9191 end if;
9192 end if;
9193 end if;
9194 end Check_Size;
9195
9196 -------------------------
9197 -- Get_Alignment_Value --
9198 -------------------------
9199
9200 function Get_Alignment_Value (Expr : Node_Id) return Uint is
9201 Align : constant Uint := Static_Integer (Expr);
9202
9203 begin
9204 if Align = No_Uint then
9205 return No_Uint;
9206
9207 elsif Align <= 0 then
9208 Error_Msg_N ("alignment value must be positive", Expr);
9209 return No_Uint;
9210
9211 else
9212 for J in Int range 0 .. 64 loop
9213 declare
9214 M : constant Uint := Uint_2 ** J;
9215
9216 begin
9217 exit when M = Align;
9218
9219 if M > Align then
9220 Error_Msg_N
9221 ("alignment value must be power of 2", Expr);
9222 return No_Uint;
9223 end if;
9224 end;
9225 end loop;
9226
9227 return Align;
9228 end if;
9229 end Get_Alignment_Value;
9230
9231 -------------------------------------
9232 -- Inherit_Aspects_At_Freeze_Point --
9233 -------------------------------------
9234
9235 procedure Inherit_Aspects_At_Freeze_Point (Typ : Entity_Id) is
9236
9237 function Is_Pragma_Or_Corr_Pragma_Present_In_Rep_Item
9238 (Rep_Item : Node_Id) return Boolean;
9239 -- This routine checks if Rep_Item is either a pragma or an aspect
9240 -- specification node whose correponding pragma (if any) is present in
9241 -- the Rep Item chain of the entity it has been specified to.
9242
9243 --------------------------------------------------
9244 -- Is_Pragma_Or_Corr_Pragma_Present_In_Rep_Item --
9245 --------------------------------------------------
9246
9247 function Is_Pragma_Or_Corr_Pragma_Present_In_Rep_Item
9248 (Rep_Item : Node_Id) return Boolean
9249 is
9250 begin
9251 return Nkind (Rep_Item) = N_Pragma
9252 or else Present_In_Rep_Item
9253 (Entity (Rep_Item), Aspect_Rep_Item (Rep_Item));
9254 end Is_Pragma_Or_Corr_Pragma_Present_In_Rep_Item;
9255
9256 -- Start of processing for Inherit_Aspects_At_Freeze_Point
9257
9258 begin
9259 -- A representation item is either subtype-specific (Size and Alignment
9260 -- clauses) or type-related (all others). Subtype-specific aspects may
9261 -- differ for different subtypes of the same type (RM 13.1.8).
9262
9263 -- A derived type inherits each type-related representation aspect of
9264 -- its parent type that was directly specified before the declaration of
9265 -- the derived type (RM 13.1.15).
9266
9267 -- A derived subtype inherits each subtype-specific representation
9268 -- aspect of its parent subtype that was directly specified before the
9269 -- declaration of the derived type (RM 13.1.15).
9270
9271 -- The general processing involves inheriting a representation aspect
9272 -- from a parent type whenever the first rep item (aspect specification,
9273 -- attribute definition clause, pragma) corresponding to the given
9274 -- representation aspect in the rep item chain of Typ, if any, isn't
9275 -- directly specified to Typ but to one of its parents.
9276
9277 -- ??? Note that, for now, just a limited number of representation
9278 -- aspects have been inherited here so far. Many of them are
9279 -- still inherited in Sem_Ch3. This will be fixed soon. Here is
9280 -- a non- exhaustive list of aspects that likely also need to
9281 -- be moved to this routine: Alignment, Component_Alignment,
9282 -- Component_Size, Machine_Radix, Object_Size, Pack, Predicates,
9283 -- Preelaborable_Initialization, RM_Size and Small.
9284
9285 if Nkind (Parent (Typ)) = N_Private_Extension_Declaration then
9286 return;
9287 end if;
9288
9289 -- Ada_05/Ada_2005
9290
9291 if not Has_Rep_Item (Typ, Name_Ada_05, Name_Ada_2005, False)
9292 and then Has_Rep_Item (Typ, Name_Ada_05, Name_Ada_2005)
9293 and then Is_Pragma_Or_Corr_Pragma_Present_In_Rep_Item
9294 (Get_Rep_Item (Typ, Name_Ada_05, Name_Ada_2005))
9295 then
9296 Set_Is_Ada_2005_Only (Typ);
9297 end if;
9298
9299 -- Ada_12/Ada_2012
9300
9301 if not Has_Rep_Item (Typ, Name_Ada_12, Name_Ada_2012, False)
9302 and then Has_Rep_Item (Typ, Name_Ada_12, Name_Ada_2012)
9303 and then Is_Pragma_Or_Corr_Pragma_Present_In_Rep_Item
9304 (Get_Rep_Item (Typ, Name_Ada_12, Name_Ada_2012))
9305 then
9306 Set_Is_Ada_2012_Only (Typ);
9307 end if;
9308
9309 -- Atomic/Shared
9310
9311 if not Has_Rep_Item (Typ, Name_Atomic, Name_Shared, False)
9312 and then Has_Rep_Pragma (Typ, Name_Atomic, Name_Shared)
9313 and then Is_Pragma_Or_Corr_Pragma_Present_In_Rep_Item
9314 (Get_Rep_Item (Typ, Name_Atomic, Name_Shared))
9315 then
9316 Set_Is_Atomic (Typ);
9317 Set_Treat_As_Volatile (Typ);
9318 Set_Is_Volatile (Typ);
9319 end if;
9320
9321 -- Default_Component_Value
9322
9323 if Is_Array_Type (Typ)
9324 and then Has_Rep_Item (Typ, Name_Default_Component_Value, False)
9325 and then Has_Rep_Item (Typ, Name_Default_Component_Value)
9326 then
9327 Set_Default_Aspect_Component_Value (Typ,
9328 Default_Aspect_Component_Value
9329 (Entity (Get_Rep_Item (Typ, Name_Default_Component_Value))));
9330 end if;
9331
9332 -- Default_Value
9333
9334 if Is_Scalar_Type (Typ)
9335 and then Has_Rep_Item (Typ, Name_Default_Value, False)
9336 and then Has_Rep_Item (Typ, Name_Default_Value)
9337 then
9338 Set_Default_Aspect_Value (Typ,
9339 Default_Aspect_Value
9340 (Entity (Get_Rep_Item (Typ, Name_Default_Value))));
9341 end if;
9342
9343 -- Discard_Names
9344
9345 if not Has_Rep_Item (Typ, Name_Discard_Names, False)
9346 and then Has_Rep_Item (Typ, Name_Discard_Names)
9347 and then Is_Pragma_Or_Corr_Pragma_Present_In_Rep_Item
9348 (Get_Rep_Item (Typ, Name_Discard_Names))
9349 then
9350 Set_Discard_Names (Typ);
9351 end if;
9352
9353 -- Invariants
9354
9355 if not Has_Rep_Item (Typ, Name_Invariant, False)
9356 and then Has_Rep_Item (Typ, Name_Invariant)
9357 and then Is_Pragma_Or_Corr_Pragma_Present_In_Rep_Item
9358 (Get_Rep_Item (Typ, Name_Invariant))
9359 then
9360 Set_Has_Invariants (Typ);
9361
9362 if Class_Present (Get_Rep_Item (Typ, Name_Invariant)) then
9363 Set_Has_Inheritable_Invariants (Typ);
9364 end if;
9365 end if;
9366
9367 -- Volatile
9368
9369 if not Has_Rep_Item (Typ, Name_Volatile, False)
9370 and then Has_Rep_Item (Typ, Name_Volatile)
9371 and then Is_Pragma_Or_Corr_Pragma_Present_In_Rep_Item
9372 (Get_Rep_Item (Typ, Name_Volatile))
9373 then
9374 Set_Treat_As_Volatile (Typ);
9375 Set_Is_Volatile (Typ);
9376 end if;
9377
9378 -- Inheritance for derived types only
9379
9380 if Is_Derived_Type (Typ) then
9381 declare
9382 Bas_Typ : constant Entity_Id := Base_Type (Typ);
9383 Imp_Bas_Typ : constant Entity_Id := Implementation_Base_Type (Typ);
9384
9385 begin
9386 -- Atomic_Components
9387
9388 if not Has_Rep_Item (Typ, Name_Atomic_Components, False)
9389 and then Has_Rep_Item (Typ, Name_Atomic_Components)
9390 and then Is_Pragma_Or_Corr_Pragma_Present_In_Rep_Item
9391 (Get_Rep_Item (Typ, Name_Atomic_Components))
9392 then
9393 Set_Has_Atomic_Components (Imp_Bas_Typ);
9394 end if;
9395
9396 -- Volatile_Components
9397
9398 if not Has_Rep_Item (Typ, Name_Volatile_Components, False)
9399 and then Has_Rep_Item (Typ, Name_Volatile_Components)
9400 and then Is_Pragma_Or_Corr_Pragma_Present_In_Rep_Item
9401 (Get_Rep_Item (Typ, Name_Volatile_Components))
9402 then
9403 Set_Has_Volatile_Components (Imp_Bas_Typ);
9404 end if;
9405
9406 -- Finalize_Storage_Only.
9407
9408 if not Has_Rep_Pragma (Typ, Name_Finalize_Storage_Only, False)
9409 and then Has_Rep_Pragma (Typ, Name_Finalize_Storage_Only)
9410 then
9411 Set_Finalize_Storage_Only (Bas_Typ);
9412 end if;
9413
9414 -- Universal_Aliasing
9415
9416 if not Has_Rep_Item (Typ, Name_Universal_Aliasing, False)
9417 and then Has_Rep_Item (Typ, Name_Universal_Aliasing)
9418 and then Is_Pragma_Or_Corr_Pragma_Present_In_Rep_Item
9419 (Get_Rep_Item (Typ, Name_Universal_Aliasing))
9420 then
9421 Set_Universal_Aliasing (Imp_Bas_Typ);
9422 end if;
9423
9424 -- Record type specific aspects
9425
9426 if Is_Record_Type (Typ) then
9427
9428 -- Bit_Order
9429
9430 if not Has_Rep_Item (Typ, Name_Bit_Order, False)
9431 and then Has_Rep_Item (Typ, Name_Bit_Order)
9432 then
9433 Set_Reverse_Bit_Order (Bas_Typ,
9434 Reverse_Bit_Order (Entity (Name
9435 (Get_Rep_Item (Typ, Name_Bit_Order)))));
9436 end if;
9437
9438 -- Scalar_Storage_Order
9439
9440 if not Has_Rep_Item (Typ, Name_Scalar_Storage_Order, False)
9441 and then Has_Rep_Item (Typ, Name_Scalar_Storage_Order)
9442 then
9443 Set_Reverse_Storage_Order (Bas_Typ,
9444 Reverse_Storage_Order (Entity (Name
9445 (Get_Rep_Item (Typ, Name_Scalar_Storage_Order)))));
9446 end if;
9447 end if;
9448 end;
9449 end if;
9450 end Inherit_Aspects_At_Freeze_Point;
9451
9452 ----------------
9453 -- Initialize --
9454 ----------------
9455
9456 procedure Initialize is
9457 begin
9458 Address_Clause_Checks.Init;
9459 Independence_Checks.Init;
9460 Unchecked_Conversions.Init;
9461 end Initialize;
9462
9463 -------------------------
9464 -- Is_Operational_Item --
9465 -------------------------
9466
9467 function Is_Operational_Item (N : Node_Id) return Boolean is
9468 begin
9469 if Nkind (N) /= N_Attribute_Definition_Clause then
9470 return False;
9471
9472 else
9473 declare
9474 Id : constant Attribute_Id := Get_Attribute_Id (Chars (N));
9475 begin
9476 return Id = Attribute_Input
9477 or else Id = Attribute_Output
9478 or else Id = Attribute_Read
9479 or else Id = Attribute_Write
9480 or else Id = Attribute_External_Tag;
9481 end;
9482 end if;
9483 end Is_Operational_Item;
9484
9485 ------------------
9486 -- Minimum_Size --
9487 ------------------
9488
9489 function Minimum_Size
9490 (T : Entity_Id;
9491 Biased : Boolean := False) return Nat
9492 is
9493 Lo : Uint := No_Uint;
9494 Hi : Uint := No_Uint;
9495 LoR : Ureal := No_Ureal;
9496 HiR : Ureal := No_Ureal;
9497 LoSet : Boolean := False;
9498 HiSet : Boolean := False;
9499 B : Uint;
9500 S : Nat;
9501 Ancest : Entity_Id;
9502 R_Typ : constant Entity_Id := Root_Type (T);
9503
9504 begin
9505 -- If bad type, return 0
9506
9507 if T = Any_Type then
9508 return 0;
9509
9510 -- For generic types, just return zero. There cannot be any legitimate
9511 -- need to know such a size, but this routine may be called with a
9512 -- generic type as part of normal processing.
9513
9514 elsif Is_Generic_Type (R_Typ)
9515 or else R_Typ = Any_Type
9516 then
9517 return 0;
9518
9519 -- Access types. Normally an access type cannot have a size smaller
9520 -- than the size of System.Address. The exception is on VMS, where
9521 -- we have short and long addresses, and it is possible for an access
9522 -- type to have a short address size (and thus be less than the size
9523 -- of System.Address itself). We simply skip the check for VMS, and
9524 -- leave it to the back end to do the check.
9525
9526 elsif Is_Access_Type (T) then
9527 if OpenVMS_On_Target then
9528 return 0;
9529 else
9530 return System_Address_Size;
9531 end if;
9532
9533 -- Floating-point types
9534
9535 elsif Is_Floating_Point_Type (T) then
9536 return UI_To_Int (Esize (R_Typ));
9537
9538 -- Discrete types
9539
9540 elsif Is_Discrete_Type (T) then
9541
9542 -- The following loop is looking for the nearest compile time known
9543 -- bounds following the ancestor subtype chain. The idea is to find
9544 -- the most restrictive known bounds information.
9545
9546 Ancest := T;
9547 loop
9548 if Ancest = Any_Type or else Etype (Ancest) = Any_Type then
9549 return 0;
9550 end if;
9551
9552 if not LoSet then
9553 if Compile_Time_Known_Value (Type_Low_Bound (Ancest)) then
9554 Lo := Expr_Rep_Value (Type_Low_Bound (Ancest));
9555 LoSet := True;
9556 exit when HiSet;
9557 end if;
9558 end if;
9559
9560 if not HiSet then
9561 if Compile_Time_Known_Value (Type_High_Bound (Ancest)) then
9562 Hi := Expr_Rep_Value (Type_High_Bound (Ancest));
9563 HiSet := True;
9564 exit when LoSet;
9565 end if;
9566 end if;
9567
9568 Ancest := Ancestor_Subtype (Ancest);
9569
9570 if No (Ancest) then
9571 Ancest := Base_Type (T);
9572
9573 if Is_Generic_Type (Ancest) then
9574 return 0;
9575 end if;
9576 end if;
9577 end loop;
9578
9579 -- Fixed-point types. We can't simply use Expr_Value to get the
9580 -- Corresponding_Integer_Value values of the bounds, since these do not
9581 -- get set till the type is frozen, and this routine can be called
9582 -- before the type is frozen. Similarly the test for bounds being static
9583 -- needs to include the case where we have unanalyzed real literals for
9584 -- the same reason.
9585
9586 elsif Is_Fixed_Point_Type (T) then
9587
9588 -- The following loop is looking for the nearest compile time known
9589 -- bounds following the ancestor subtype chain. The idea is to find
9590 -- the most restrictive known bounds information.
9591
9592 Ancest := T;
9593 loop
9594 if Ancest = Any_Type or else Etype (Ancest) = Any_Type then
9595 return 0;
9596 end if;
9597
9598 -- Note: In the following two tests for LoSet and HiSet, it may
9599 -- seem redundant to test for N_Real_Literal here since normally
9600 -- one would assume that the test for the value being known at
9601 -- compile time includes this case. However, there is a glitch.
9602 -- If the real literal comes from folding a non-static expression,
9603 -- then we don't consider any non- static expression to be known
9604 -- at compile time if we are in configurable run time mode (needed
9605 -- in some cases to give a clearer definition of what is and what
9606 -- is not accepted). So the test is indeed needed. Without it, we
9607 -- would set neither Lo_Set nor Hi_Set and get an infinite loop.
9608
9609 if not LoSet then
9610 if Nkind (Type_Low_Bound (Ancest)) = N_Real_Literal
9611 or else Compile_Time_Known_Value (Type_Low_Bound (Ancest))
9612 then
9613 LoR := Expr_Value_R (Type_Low_Bound (Ancest));
9614 LoSet := True;
9615 exit when HiSet;
9616 end if;
9617 end if;
9618
9619 if not HiSet then
9620 if Nkind (Type_High_Bound (Ancest)) = N_Real_Literal
9621 or else Compile_Time_Known_Value (Type_High_Bound (Ancest))
9622 then
9623 HiR := Expr_Value_R (Type_High_Bound (Ancest));
9624 HiSet := True;
9625 exit when LoSet;
9626 end if;
9627 end if;
9628
9629 Ancest := Ancestor_Subtype (Ancest);
9630
9631 if No (Ancest) then
9632 Ancest := Base_Type (T);
9633
9634 if Is_Generic_Type (Ancest) then
9635 return 0;
9636 end if;
9637 end if;
9638 end loop;
9639
9640 Lo := UR_To_Uint (LoR / Small_Value (T));
9641 Hi := UR_To_Uint (HiR / Small_Value (T));
9642
9643 -- No other types allowed
9644
9645 else
9646 raise Program_Error;
9647 end if;
9648
9649 -- Fall through with Hi and Lo set. Deal with biased case
9650
9651 if (Biased
9652 and then not Is_Fixed_Point_Type (T)
9653 and then not (Is_Enumeration_Type (T)
9654 and then Has_Non_Standard_Rep (T)))
9655 or else Has_Biased_Representation (T)
9656 then
9657 Hi := Hi - Lo;
9658 Lo := Uint_0;
9659 end if;
9660
9661 -- Signed case. Note that we consider types like range 1 .. -1 to be
9662 -- signed for the purpose of computing the size, since the bounds have
9663 -- to be accommodated in the base type.
9664
9665 if Lo < 0 or else Hi < 0 then
9666 S := 1;
9667 B := Uint_1;
9668
9669 -- S = size, B = 2 ** (size - 1) (can accommodate -B .. +(B - 1))
9670 -- Note that we accommodate the case where the bounds cross. This
9671 -- can happen either because of the way the bounds are declared
9672 -- or because of the algorithm in Freeze_Fixed_Point_Type.
9673
9674 while Lo < -B
9675 or else Hi < -B
9676 or else Lo >= B
9677 or else Hi >= B
9678 loop
9679 B := Uint_2 ** S;
9680 S := S + 1;
9681 end loop;
9682
9683 -- Unsigned case
9684
9685 else
9686 -- If both bounds are positive, make sure that both are represen-
9687 -- table in the case where the bounds are crossed. This can happen
9688 -- either because of the way the bounds are declared, or because of
9689 -- the algorithm in Freeze_Fixed_Point_Type.
9690
9691 if Lo > Hi then
9692 Hi := Lo;
9693 end if;
9694
9695 -- S = size, (can accommodate 0 .. (2**size - 1))
9696
9697 S := 0;
9698 while Hi >= Uint_2 ** S loop
9699 S := S + 1;
9700 end loop;
9701 end if;
9702
9703 return S;
9704 end Minimum_Size;
9705
9706 ---------------------------
9707 -- New_Stream_Subprogram --
9708 ---------------------------
9709
9710 procedure New_Stream_Subprogram
9711 (N : Node_Id;
9712 Ent : Entity_Id;
9713 Subp : Entity_Id;
9714 Nam : TSS_Name_Type)
9715 is
9716 Loc : constant Source_Ptr := Sloc (N);
9717 Sname : constant Name_Id := Make_TSS_Name (Base_Type (Ent), Nam);
9718 Subp_Id : Entity_Id;
9719 Subp_Decl : Node_Id;
9720 F : Entity_Id;
9721 Etyp : Entity_Id;
9722
9723 Defer_Declaration : constant Boolean :=
9724 Is_Tagged_Type (Ent) or else Is_Private_Type (Ent);
9725 -- For a tagged type, there is a declaration for each stream attribute
9726 -- at the freeze point, and we must generate only a completion of this
9727 -- declaration. We do the same for private types, because the full view
9728 -- might be tagged. Otherwise we generate a declaration at the point of
9729 -- the attribute definition clause.
9730
9731 function Build_Spec return Node_Id;
9732 -- Used for declaration and renaming declaration, so that this is
9733 -- treated as a renaming_as_body.
9734
9735 ----------------
9736 -- Build_Spec --
9737 ----------------
9738
9739 function Build_Spec return Node_Id is
9740 Out_P : constant Boolean := (Nam = TSS_Stream_Read);
9741 Formals : List_Id;
9742 Spec : Node_Id;
9743 T_Ref : constant Node_Id := New_Reference_To (Etyp, Loc);
9744
9745 begin
9746 Subp_Id := Make_Defining_Identifier (Loc, Sname);
9747
9748 -- S : access Root_Stream_Type'Class
9749
9750 Formals := New_List (
9751 Make_Parameter_Specification (Loc,
9752 Defining_Identifier =>
9753 Make_Defining_Identifier (Loc, Name_S),
9754 Parameter_Type =>
9755 Make_Access_Definition (Loc,
9756 Subtype_Mark =>
9757 New_Reference_To (
9758 Designated_Type (Etype (F)), Loc))));
9759
9760 if Nam = TSS_Stream_Input then
9761 Spec :=
9762 Make_Function_Specification (Loc,
9763 Defining_Unit_Name => Subp_Id,
9764 Parameter_Specifications => Formals,
9765 Result_Definition => T_Ref);
9766 else
9767 -- V : [out] T
9768
9769 Append_To (Formals,
9770 Make_Parameter_Specification (Loc,
9771 Defining_Identifier => Make_Defining_Identifier (Loc, Name_V),
9772 Out_Present => Out_P,
9773 Parameter_Type => T_Ref));
9774
9775 Spec :=
9776 Make_Procedure_Specification (Loc,
9777 Defining_Unit_Name => Subp_Id,
9778 Parameter_Specifications => Formals);
9779 end if;
9780
9781 return Spec;
9782 end Build_Spec;
9783
9784 -- Start of processing for New_Stream_Subprogram
9785
9786 begin
9787 F := First_Formal (Subp);
9788
9789 if Ekind (Subp) = E_Procedure then
9790 Etyp := Etype (Next_Formal (F));
9791 else
9792 Etyp := Etype (Subp);
9793 end if;
9794
9795 -- Prepare subprogram declaration and insert it as an action on the
9796 -- clause node. The visibility for this entity is used to test for
9797 -- visibility of the attribute definition clause (in the sense of
9798 -- 8.3(23) as amended by AI-195).
9799
9800 if not Defer_Declaration then
9801 Subp_Decl :=
9802 Make_Subprogram_Declaration (Loc,
9803 Specification => Build_Spec);
9804
9805 -- For a tagged type, there is always a visible declaration for each
9806 -- stream TSS (it is a predefined primitive operation), and the
9807 -- completion of this declaration occurs at the freeze point, which is
9808 -- not always visible at places where the attribute definition clause is
9809 -- visible. So, we create a dummy entity here for the purpose of
9810 -- tracking the visibility of the attribute definition clause itself.
9811
9812 else
9813 Subp_Id :=
9814 Make_Defining_Identifier (Loc, New_External_Name (Sname, 'V'));
9815 Subp_Decl :=
9816 Make_Object_Declaration (Loc,
9817 Defining_Identifier => Subp_Id,
9818 Object_Definition => New_Occurrence_Of (Standard_Boolean, Loc));
9819 end if;
9820
9821 Insert_Action (N, Subp_Decl);
9822 Set_Entity (N, Subp_Id);
9823
9824 Subp_Decl :=
9825 Make_Subprogram_Renaming_Declaration (Loc,
9826 Specification => Build_Spec,
9827 Name => New_Reference_To (Subp, Loc));
9828
9829 if Defer_Declaration then
9830 Set_TSS (Base_Type (Ent), Subp_Id);
9831 else
9832 Insert_Action (N, Subp_Decl);
9833 Copy_TSS (Subp_Id, Base_Type (Ent));
9834 end if;
9835 end New_Stream_Subprogram;
9836
9837 ------------------------
9838 -- Rep_Item_Too_Early --
9839 ------------------------
9840
9841 function Rep_Item_Too_Early (T : Entity_Id; N : Node_Id) return Boolean is
9842 begin
9843 -- Cannot apply non-operational rep items to generic types
9844
9845 if Is_Operational_Item (N) then
9846 return False;
9847
9848 elsif Is_Type (T)
9849 and then Is_Generic_Type (Root_Type (T))
9850 then
9851 Error_Msg_N ("representation item not allowed for generic type", N);
9852 return True;
9853 end if;
9854
9855 -- Otherwise check for incomplete type
9856
9857 if Is_Incomplete_Or_Private_Type (T)
9858 and then No (Underlying_Type (T))
9859 and then
9860 (Nkind (N) /= N_Pragma
9861 or else Get_Pragma_Id (N) /= Pragma_Import)
9862 then
9863 Error_Msg_N
9864 ("representation item must be after full type declaration", N);
9865 return True;
9866
9867 -- If the type has incomplete components, a representation clause is
9868 -- illegal but stream attributes and Convention pragmas are correct.
9869
9870 elsif Has_Private_Component (T) then
9871 if Nkind (N) = N_Pragma then
9872 return False;
9873
9874 else
9875 Error_Msg_N
9876 ("representation item must appear after type is fully defined",
9877 N);
9878 return True;
9879 end if;
9880 else
9881 return False;
9882 end if;
9883 end Rep_Item_Too_Early;
9884
9885 -----------------------
9886 -- Rep_Item_Too_Late --
9887 -----------------------
9888
9889 function Rep_Item_Too_Late
9890 (T : Entity_Id;
9891 N : Node_Id;
9892 FOnly : Boolean := False) return Boolean
9893 is
9894 S : Entity_Id;
9895 Parent_Type : Entity_Id;
9896
9897 procedure Too_Late;
9898 -- Output the too late message. Note that this is not considered a
9899 -- serious error, since the effect is simply that we ignore the
9900 -- representation clause in this case.
9901
9902 --------------
9903 -- Too_Late --
9904 --------------
9905
9906 procedure Too_Late is
9907 begin
9908 -- Other compilers seem more relaxed about rep items appearing too
9909 -- late. Since analysis tools typically don't care about rep items
9910 -- anyway, no reason to be too strict about this.
9911
9912 if not Relaxed_RM_Semantics then
9913 Error_Msg_N ("|representation item appears too late!", N);
9914 end if;
9915 end Too_Late;
9916
9917 -- Start of processing for Rep_Item_Too_Late
9918
9919 begin
9920 -- First make sure entity is not frozen (RM 13.1(9))
9921
9922 if Is_Frozen (T)
9923
9924 -- Exclude imported types, which may be frozen if they appear in a
9925 -- representation clause for a local type.
9926
9927 and then not From_With_Type (T)
9928
9929 -- Exclude generated entities (not coming from source). The common
9930 -- case is when we generate a renaming which prematurely freezes the
9931 -- renamed internal entity, but we still want to be able to set copies
9932 -- of attribute values such as Size/Alignment.
9933
9934 and then Comes_From_Source (T)
9935 then
9936 Too_Late;
9937 S := First_Subtype (T);
9938
9939 if Present (Freeze_Node (S)) then
9940 Error_Msg_NE
9941 ("??no more representation items for }", Freeze_Node (S), S);
9942 end if;
9943
9944 return True;
9945
9946 -- Check for case of non-tagged derived type whose parent either has
9947 -- primitive operations, or is a by reference type (RM 13.1(10)).
9948
9949 elsif Is_Type (T)
9950 and then not FOnly
9951 and then Is_Derived_Type (T)
9952 and then not Is_Tagged_Type (T)
9953 then
9954 Parent_Type := Etype (Base_Type (T));
9955
9956 if Has_Primitive_Operations (Parent_Type) then
9957 Too_Late;
9958 Error_Msg_NE
9959 ("primitive operations already defined for&!", N, Parent_Type);
9960 return True;
9961
9962 elsif Is_By_Reference_Type (Parent_Type) then
9963 Too_Late;
9964 Error_Msg_NE
9965 ("parent type & is a by reference type!", N, Parent_Type);
9966 return True;
9967 end if;
9968 end if;
9969
9970 -- No error, link item into head of chain of rep items for the entity,
9971 -- but avoid chaining if we have an overloadable entity, and the pragma
9972 -- is one that can apply to multiple overloaded entities.
9973
9974 if Is_Overloadable (T) and then Nkind (N) = N_Pragma then
9975 declare
9976 Pname : constant Name_Id := Pragma_Name (N);
9977 begin
9978 if Nam_In (Pname, Name_Convention, Name_Import, Name_Export,
9979 Name_External, Name_Interface)
9980 then
9981 return False;
9982 end if;
9983 end;
9984 end if;
9985
9986 Record_Rep_Item (T, N);
9987 return False;
9988 end Rep_Item_Too_Late;
9989
9990 -------------------------------------
9991 -- Replace_Type_References_Generic --
9992 -------------------------------------
9993
9994 procedure Replace_Type_References_Generic (N : Node_Id; TName : Name_Id) is
9995
9996 function Replace_Node (N : Node_Id) return Traverse_Result;
9997 -- Processes a single node in the traversal procedure below, checking
9998 -- if node N should be replaced, and if so, doing the replacement.
9999
10000 procedure Replace_Type_Refs is new Traverse_Proc (Replace_Node);
10001 -- This instantiation provides the body of Replace_Type_References
10002
10003 ------------------
10004 -- Replace_Node --
10005 ------------------
10006
10007 function Replace_Node (N : Node_Id) return Traverse_Result is
10008 S : Entity_Id;
10009 P : Node_Id;
10010
10011 begin
10012 -- Case of identifier
10013
10014 if Nkind (N) = N_Identifier then
10015
10016 -- If not the type name, all done with this node
10017
10018 if Chars (N) /= TName then
10019 return Skip;
10020
10021 -- Otherwise do the replacement and we are done with this node
10022
10023 else
10024 Replace_Type_Reference (N);
10025 return Skip;
10026 end if;
10027
10028 -- Case of selected component (which is what a qualification
10029 -- looks like in the unanalyzed tree, which is what we have.
10030
10031 elsif Nkind (N) = N_Selected_Component then
10032
10033 -- If selector name is not our type, keeping going (we might
10034 -- still have an occurrence of the type in the prefix).
10035
10036 if Nkind (Selector_Name (N)) /= N_Identifier
10037 or else Chars (Selector_Name (N)) /= TName
10038 then
10039 return OK;
10040
10041 -- Selector name is our type, check qualification
10042
10043 else
10044 -- Loop through scopes and prefixes, doing comparison
10045
10046 S := Current_Scope;
10047 P := Prefix (N);
10048 loop
10049 -- Continue if no more scopes or scope with no name
10050
10051 if No (S) or else Nkind (S) not in N_Has_Chars then
10052 return OK;
10053 end if;
10054
10055 -- Do replace if prefix is an identifier matching the
10056 -- scope that we are currently looking at.
10057
10058 if Nkind (P) = N_Identifier
10059 and then Chars (P) = Chars (S)
10060 then
10061 Replace_Type_Reference (N);
10062 return Skip;
10063 end if;
10064
10065 -- Go check scope above us if prefix is itself of the
10066 -- form of a selected component, whose selector matches
10067 -- the scope we are currently looking at.
10068
10069 if Nkind (P) = N_Selected_Component
10070 and then Nkind (Selector_Name (P)) = N_Identifier
10071 and then Chars (Selector_Name (P)) = Chars (S)
10072 then
10073 S := Scope (S);
10074 P := Prefix (P);
10075
10076 -- For anything else, we don't have a match, so keep on
10077 -- going, there are still some weird cases where we may
10078 -- still have a replacement within the prefix.
10079
10080 else
10081 return OK;
10082 end if;
10083 end loop;
10084 end if;
10085
10086 -- Continue for any other node kind
10087
10088 else
10089 return OK;
10090 end if;
10091 end Replace_Node;
10092
10093 begin
10094 Replace_Type_Refs (N);
10095 end Replace_Type_References_Generic;
10096
10097 -------------------------
10098 -- Same_Representation --
10099 -------------------------
10100
10101 function Same_Representation (Typ1, Typ2 : Entity_Id) return Boolean is
10102 T1 : constant Entity_Id := Underlying_Type (Typ1);
10103 T2 : constant Entity_Id := Underlying_Type (Typ2);
10104
10105 begin
10106 -- A quick check, if base types are the same, then we definitely have
10107 -- the same representation, because the subtype specific representation
10108 -- attributes (Size and Alignment) do not affect representation from
10109 -- the point of view of this test.
10110
10111 if Base_Type (T1) = Base_Type (T2) then
10112 return True;
10113
10114 elsif Is_Private_Type (Base_Type (T2))
10115 and then Base_Type (T1) = Full_View (Base_Type (T2))
10116 then
10117 return True;
10118 end if;
10119
10120 -- Tagged types never have differing representations
10121
10122 if Is_Tagged_Type (T1) then
10123 return True;
10124 end if;
10125
10126 -- Representations are definitely different if conventions differ
10127
10128 if Convention (T1) /= Convention (T2) then
10129 return False;
10130 end if;
10131
10132 -- Representations are different if component alignments or scalar
10133 -- storage orders differ.
10134
10135 if (Is_Record_Type (T1) or else Is_Array_Type (T1))
10136 and then
10137 (Is_Record_Type (T2) or else Is_Array_Type (T2))
10138 and then
10139 (Component_Alignment (T1) /= Component_Alignment (T2)
10140 or else
10141 Reverse_Storage_Order (T1) /= Reverse_Storage_Order (T2))
10142 then
10143 return False;
10144 end if;
10145
10146 -- For arrays, the only real issue is component size. If we know the
10147 -- component size for both arrays, and it is the same, then that's
10148 -- good enough to know we don't have a change of representation.
10149
10150 if Is_Array_Type (T1) then
10151 if Known_Component_Size (T1)
10152 and then Known_Component_Size (T2)
10153 and then Component_Size (T1) = Component_Size (T2)
10154 then
10155 if VM_Target = No_VM then
10156 return True;
10157
10158 -- In VM targets the representation of arrays with aliased
10159 -- components differs from arrays with non-aliased components
10160
10161 else
10162 return Has_Aliased_Components (Base_Type (T1))
10163 =
10164 Has_Aliased_Components (Base_Type (T2));
10165 end if;
10166 end if;
10167 end if;
10168
10169 -- Types definitely have same representation if neither has non-standard
10170 -- representation since default representations are always consistent.
10171 -- If only one has non-standard representation, and the other does not,
10172 -- then we consider that they do not have the same representation. They
10173 -- might, but there is no way of telling early enough.
10174
10175 if Has_Non_Standard_Rep (T1) then
10176 if not Has_Non_Standard_Rep (T2) then
10177 return False;
10178 end if;
10179 else
10180 return not Has_Non_Standard_Rep (T2);
10181 end if;
10182
10183 -- Here the two types both have non-standard representation, and we need
10184 -- to determine if they have the same non-standard representation.
10185
10186 -- For arrays, we simply need to test if the component sizes are the
10187 -- same. Pragma Pack is reflected in modified component sizes, so this
10188 -- check also deals with pragma Pack.
10189
10190 if Is_Array_Type (T1) then
10191 return Component_Size (T1) = Component_Size (T2);
10192
10193 -- Tagged types always have the same representation, because it is not
10194 -- possible to specify different representations for common fields.
10195
10196 elsif Is_Tagged_Type (T1) then
10197 return True;
10198
10199 -- Case of record types
10200
10201 elsif Is_Record_Type (T1) then
10202
10203 -- Packed status must conform
10204
10205 if Is_Packed (T1) /= Is_Packed (T2) then
10206 return False;
10207
10208 -- Otherwise we must check components. Typ2 maybe a constrained
10209 -- subtype with fewer components, so we compare the components
10210 -- of the base types.
10211
10212 else
10213 Record_Case : declare
10214 CD1, CD2 : Entity_Id;
10215
10216 function Same_Rep return Boolean;
10217 -- CD1 and CD2 are either components or discriminants. This
10218 -- function tests whether they have the same representation.
10219
10220 --------------
10221 -- Same_Rep --
10222 --------------
10223
10224 function Same_Rep return Boolean is
10225 begin
10226 if No (Component_Clause (CD1)) then
10227 return No (Component_Clause (CD2));
10228 else
10229 -- Note: at this point, component clauses have been
10230 -- normalized to the default bit order, so that the
10231 -- comparison of Component_Bit_Offsets is meaningful.
10232
10233 return
10234 Present (Component_Clause (CD2))
10235 and then
10236 Component_Bit_Offset (CD1) = Component_Bit_Offset (CD2)
10237 and then
10238 Esize (CD1) = Esize (CD2);
10239 end if;
10240 end Same_Rep;
10241
10242 -- Start of processing for Record_Case
10243
10244 begin
10245 if Has_Discriminants (T1) then
10246
10247 -- The number of discriminants may be different if the
10248 -- derived type has fewer (constrained by values). The
10249 -- invisible discriminants retain the representation of
10250 -- the original, so the discrepancy does not per se
10251 -- indicate a different representation.
10252
10253 CD1 := First_Discriminant (T1);
10254 CD2 := First_Discriminant (T2);
10255 while Present (CD1) and then Present (CD2) loop
10256 if not Same_Rep then
10257 return False;
10258 else
10259 Next_Discriminant (CD1);
10260 Next_Discriminant (CD2);
10261 end if;
10262 end loop;
10263 end if;
10264
10265 CD1 := First_Component (Underlying_Type (Base_Type (T1)));
10266 CD2 := First_Component (Underlying_Type (Base_Type (T2)));
10267 while Present (CD1) loop
10268 if not Same_Rep then
10269 return False;
10270 else
10271 Next_Component (CD1);
10272 Next_Component (CD2);
10273 end if;
10274 end loop;
10275
10276 return True;
10277 end Record_Case;
10278 end if;
10279
10280 -- For enumeration types, we must check each literal to see if the
10281 -- representation is the same. Note that we do not permit enumeration
10282 -- representation clauses for Character and Wide_Character, so these
10283 -- cases were already dealt with.
10284
10285 elsif Is_Enumeration_Type (T1) then
10286 Enumeration_Case : declare
10287 L1, L2 : Entity_Id;
10288
10289 begin
10290 L1 := First_Literal (T1);
10291 L2 := First_Literal (T2);
10292 while Present (L1) loop
10293 if Enumeration_Rep (L1) /= Enumeration_Rep (L2) then
10294 return False;
10295 else
10296 Next_Literal (L1);
10297 Next_Literal (L2);
10298 end if;
10299 end loop;
10300
10301 return True;
10302 end Enumeration_Case;
10303
10304 -- Any other types have the same representation for these purposes
10305
10306 else
10307 return True;
10308 end if;
10309 end Same_Representation;
10310
10311 ----------------
10312 -- Set_Biased --
10313 ----------------
10314
10315 procedure Set_Biased
10316 (E : Entity_Id;
10317 N : Node_Id;
10318 Msg : String;
10319 Biased : Boolean := True)
10320 is
10321 begin
10322 if Biased then
10323 Set_Has_Biased_Representation (E);
10324
10325 if Warn_On_Biased_Representation then
10326 Error_Msg_NE
10327 ("?B?" & Msg & " forces biased representation for&", N, E);
10328 end if;
10329 end if;
10330 end Set_Biased;
10331
10332 --------------------
10333 -- Set_Enum_Esize --
10334 --------------------
10335
10336 procedure Set_Enum_Esize (T : Entity_Id) is
10337 Lo : Uint;
10338 Hi : Uint;
10339 Sz : Nat;
10340
10341 begin
10342 Init_Alignment (T);
10343
10344 -- Find the minimum standard size (8,16,32,64) that fits
10345
10346 Lo := Enumeration_Rep (Entity (Type_Low_Bound (T)));
10347 Hi := Enumeration_Rep (Entity (Type_High_Bound (T)));
10348
10349 if Lo < 0 then
10350 if Lo >= -Uint_2**07 and then Hi < Uint_2**07 then
10351 Sz := Standard_Character_Size; -- May be > 8 on some targets
10352
10353 elsif Lo >= -Uint_2**15 and then Hi < Uint_2**15 then
10354 Sz := 16;
10355
10356 elsif Lo >= -Uint_2**31 and then Hi < Uint_2**31 then
10357 Sz := 32;
10358
10359 else pragma Assert (Lo >= -Uint_2**63 and then Hi < Uint_2**63);
10360 Sz := 64;
10361 end if;
10362
10363 else
10364 if Hi < Uint_2**08 then
10365 Sz := Standard_Character_Size; -- May be > 8 on some targets
10366
10367 elsif Hi < Uint_2**16 then
10368 Sz := 16;
10369
10370 elsif Hi < Uint_2**32 then
10371 Sz := 32;
10372
10373 else pragma Assert (Hi < Uint_2**63);
10374 Sz := 64;
10375 end if;
10376 end if;
10377
10378 -- That minimum is the proper size unless we have a foreign convention
10379 -- and the size required is 32 or less, in which case we bump the size
10380 -- up to 32. This is required for C and C++ and seems reasonable for
10381 -- all other foreign conventions.
10382
10383 if Has_Foreign_Convention (T)
10384 and then Esize (T) < Standard_Integer_Size
10385 then
10386 Init_Esize (T, Standard_Integer_Size);
10387 else
10388 Init_Esize (T, Sz);
10389 end if;
10390 end Set_Enum_Esize;
10391
10392 ------------------------------
10393 -- Validate_Address_Clauses --
10394 ------------------------------
10395
10396 procedure Validate_Address_Clauses is
10397 begin
10398 for J in Address_Clause_Checks.First .. Address_Clause_Checks.Last loop
10399 declare
10400 ACCR : Address_Clause_Check_Record
10401 renames Address_Clause_Checks.Table (J);
10402
10403 Expr : Node_Id;
10404
10405 X_Alignment : Uint;
10406 Y_Alignment : Uint;
10407
10408 X_Size : Uint;
10409 Y_Size : Uint;
10410
10411 begin
10412 -- Skip processing of this entry if warning already posted
10413
10414 if not Address_Warning_Posted (ACCR.N) then
10415 Expr := Original_Node (Expression (ACCR.N));
10416
10417 -- Get alignments
10418
10419 X_Alignment := Alignment (ACCR.X);
10420 Y_Alignment := Alignment (ACCR.Y);
10421
10422 -- Similarly obtain sizes
10423
10424 X_Size := Esize (ACCR.X);
10425 Y_Size := Esize (ACCR.Y);
10426
10427 -- Check for large object overlaying smaller one
10428
10429 if Y_Size > Uint_0
10430 and then X_Size > Uint_0
10431 and then X_Size > Y_Size
10432 then
10433 Error_Msg_NE
10434 ("?& overlays smaller object", ACCR.N, ACCR.X);
10435 Error_Msg_N
10436 ("\??program execution may be erroneous", ACCR.N);
10437 Error_Msg_Uint_1 := X_Size;
10438 Error_Msg_NE
10439 ("\??size of & is ^", ACCR.N, ACCR.X);
10440 Error_Msg_Uint_1 := Y_Size;
10441 Error_Msg_NE
10442 ("\??size of & is ^", ACCR.N, ACCR.Y);
10443
10444 -- Check for inadequate alignment, both of the base object
10445 -- and of the offset, if any.
10446
10447 -- Note: we do not check the alignment if we gave a size
10448 -- warning, since it would likely be redundant.
10449
10450 elsif Y_Alignment /= Uint_0
10451 and then (Y_Alignment < X_Alignment
10452 or else (ACCR.Off
10453 and then
10454 Nkind (Expr) = N_Attribute_Reference
10455 and then
10456 Attribute_Name (Expr) = Name_Address
10457 and then
10458 Has_Compatible_Alignment
10459 (ACCR.X, Prefix (Expr))
10460 /= Known_Compatible))
10461 then
10462 Error_Msg_NE
10463 ("??specified address for& may be inconsistent "
10464 & "with alignment", ACCR.N, ACCR.X);
10465 Error_Msg_N
10466 ("\??program execution may be erroneous (RM 13.3(27))",
10467 ACCR.N);
10468 Error_Msg_Uint_1 := X_Alignment;
10469 Error_Msg_NE
10470 ("\??alignment of & is ^", ACCR.N, ACCR.X);
10471 Error_Msg_Uint_1 := Y_Alignment;
10472 Error_Msg_NE
10473 ("\??alignment of & is ^", ACCR.N, ACCR.Y);
10474 if Y_Alignment >= X_Alignment then
10475 Error_Msg_N
10476 ("\??but offset is not multiple of alignment", ACCR.N);
10477 end if;
10478 end if;
10479 end if;
10480 end;
10481 end loop;
10482 end Validate_Address_Clauses;
10483
10484 ---------------------------
10485 -- Validate_Independence --
10486 ---------------------------
10487
10488 procedure Validate_Independence is
10489 SU : constant Uint := UI_From_Int (System_Storage_Unit);
10490 N : Node_Id;
10491 E : Entity_Id;
10492 IC : Boolean;
10493 Comp : Entity_Id;
10494 Addr : Node_Id;
10495 P : Node_Id;
10496
10497 procedure Check_Array_Type (Atyp : Entity_Id);
10498 -- Checks if the array type Atyp has independent components, and
10499 -- if not, outputs an appropriate set of error messages.
10500
10501 procedure No_Independence;
10502 -- Output message that independence cannot be guaranteed
10503
10504 function OK_Component (C : Entity_Id) return Boolean;
10505 -- Checks one component to see if it is independently accessible, and
10506 -- if so yields True, otherwise yields False if independent access
10507 -- cannot be guaranteed. This is a conservative routine, it only
10508 -- returns True if it knows for sure, it returns False if it knows
10509 -- there is a problem, or it cannot be sure there is no problem.
10510
10511 procedure Reason_Bad_Component (C : Entity_Id);
10512 -- Outputs continuation message if a reason can be determined for
10513 -- the component C being bad.
10514
10515 ----------------------
10516 -- Check_Array_Type --
10517 ----------------------
10518
10519 procedure Check_Array_Type (Atyp : Entity_Id) is
10520 Ctyp : constant Entity_Id := Component_Type (Atyp);
10521
10522 begin
10523 -- OK if no alignment clause, no pack, and no component size
10524
10525 if not Has_Component_Size_Clause (Atyp)
10526 and then not Has_Alignment_Clause (Atyp)
10527 and then not Is_Packed (Atyp)
10528 then
10529 return;
10530 end if;
10531
10532 -- Check actual component size
10533
10534 if not Known_Component_Size (Atyp)
10535 or else not (Addressable (Component_Size (Atyp))
10536 and then Component_Size (Atyp) < 64)
10537 or else Component_Size (Atyp) mod Esize (Ctyp) /= 0
10538 then
10539 No_Independence;
10540
10541 -- Bad component size, check reason
10542
10543 if Has_Component_Size_Clause (Atyp) then
10544 P := Get_Attribute_Definition_Clause
10545 (Atyp, Attribute_Component_Size);
10546
10547 if Present (P) then
10548 Error_Msg_Sloc := Sloc (P);
10549 Error_Msg_N ("\because of Component_Size clause#", N);
10550 return;
10551 end if;
10552 end if;
10553
10554 if Is_Packed (Atyp) then
10555 P := Get_Rep_Pragma (Atyp, Name_Pack);
10556
10557 if Present (P) then
10558 Error_Msg_Sloc := Sloc (P);
10559 Error_Msg_N ("\because of pragma Pack#", N);
10560 return;
10561 end if;
10562 end if;
10563
10564 -- No reason found, just return
10565
10566 return;
10567 end if;
10568
10569 -- Array type is OK independence-wise
10570
10571 return;
10572 end Check_Array_Type;
10573
10574 ---------------------
10575 -- No_Independence --
10576 ---------------------
10577
10578 procedure No_Independence is
10579 begin
10580 if Pragma_Name (N) = Name_Independent then
10581 Error_Msg_NE ("independence cannot be guaranteed for&", N, E);
10582 else
10583 Error_Msg_NE
10584 ("independent components cannot be guaranteed for&", N, E);
10585 end if;
10586 end No_Independence;
10587
10588 ------------------
10589 -- OK_Component --
10590 ------------------
10591
10592 function OK_Component (C : Entity_Id) return Boolean is
10593 Rec : constant Entity_Id := Scope (C);
10594 Ctyp : constant Entity_Id := Etype (C);
10595
10596 begin
10597 -- OK if no component clause, no Pack, and no alignment clause
10598
10599 if No (Component_Clause (C))
10600 and then not Is_Packed (Rec)
10601 and then not Has_Alignment_Clause (Rec)
10602 then
10603 return True;
10604 end if;
10605
10606 -- Here we look at the actual component layout. A component is
10607 -- addressable if its size is a multiple of the Esize of the
10608 -- component type, and its starting position in the record has
10609 -- appropriate alignment, and the record itself has appropriate
10610 -- alignment to guarantee the component alignment.
10611
10612 -- Make sure sizes are static, always assume the worst for any
10613 -- cases where we cannot check static values.
10614
10615 if not (Known_Static_Esize (C)
10616 and then
10617 Known_Static_Esize (Ctyp))
10618 then
10619 return False;
10620 end if;
10621
10622 -- Size of component must be addressable or greater than 64 bits
10623 -- and a multiple of bytes.
10624
10625 if not Addressable (Esize (C)) and then Esize (C) < Uint_64 then
10626 return False;
10627 end if;
10628
10629 -- Check size is proper multiple
10630
10631 if Esize (C) mod Esize (Ctyp) /= 0 then
10632 return False;
10633 end if;
10634
10635 -- Check alignment of component is OK
10636
10637 if not Known_Component_Bit_Offset (C)
10638 or else Component_Bit_Offset (C) < Uint_0
10639 or else Component_Bit_Offset (C) mod Esize (Ctyp) /= 0
10640 then
10641 return False;
10642 end if;
10643
10644 -- Check alignment of record type is OK
10645
10646 if not Known_Alignment (Rec)
10647 or else (Alignment (Rec) * SU) mod Esize (Ctyp) /= 0
10648 then
10649 return False;
10650 end if;
10651
10652 -- All tests passed, component is addressable
10653
10654 return True;
10655 end OK_Component;
10656
10657 --------------------------
10658 -- Reason_Bad_Component --
10659 --------------------------
10660
10661 procedure Reason_Bad_Component (C : Entity_Id) is
10662 Rec : constant Entity_Id := Scope (C);
10663 Ctyp : constant Entity_Id := Etype (C);
10664
10665 begin
10666 -- If component clause present assume that's the problem
10667
10668 if Present (Component_Clause (C)) then
10669 Error_Msg_Sloc := Sloc (Component_Clause (C));
10670 Error_Msg_N ("\because of Component_Clause#", N);
10671 return;
10672 end if;
10673
10674 -- If pragma Pack clause present, assume that's the problem
10675
10676 if Is_Packed (Rec) then
10677 P := Get_Rep_Pragma (Rec, Name_Pack);
10678
10679 if Present (P) then
10680 Error_Msg_Sloc := Sloc (P);
10681 Error_Msg_N ("\because of pragma Pack#", N);
10682 return;
10683 end if;
10684 end if;
10685
10686 -- See if record has bad alignment clause
10687
10688 if Has_Alignment_Clause (Rec)
10689 and then Known_Alignment (Rec)
10690 and then (Alignment (Rec) * SU) mod Esize (Ctyp) /= 0
10691 then
10692 P := Get_Attribute_Definition_Clause (Rec, Attribute_Alignment);
10693
10694 if Present (P) then
10695 Error_Msg_Sloc := Sloc (P);
10696 Error_Msg_N ("\because of Alignment clause#", N);
10697 end if;
10698 end if;
10699
10700 -- Couldn't find a reason, so return without a message
10701
10702 return;
10703 end Reason_Bad_Component;
10704
10705 -- Start of processing for Validate_Independence
10706
10707 begin
10708 for J in Independence_Checks.First .. Independence_Checks.Last loop
10709 N := Independence_Checks.Table (J).N;
10710 E := Independence_Checks.Table (J).E;
10711 IC := Pragma_Name (N) = Name_Independent_Components;
10712
10713 -- Deal with component case
10714
10715 if Ekind (E) = E_Discriminant or else Ekind (E) = E_Component then
10716 if not OK_Component (E) then
10717 No_Independence;
10718 Reason_Bad_Component (E);
10719 goto Continue;
10720 end if;
10721 end if;
10722
10723 -- Deal with record with Independent_Components
10724
10725 if IC and then Is_Record_Type (E) then
10726 Comp := First_Component_Or_Discriminant (E);
10727 while Present (Comp) loop
10728 if not OK_Component (Comp) then
10729 No_Independence;
10730 Reason_Bad_Component (Comp);
10731 goto Continue;
10732 end if;
10733
10734 Next_Component_Or_Discriminant (Comp);
10735 end loop;
10736 end if;
10737
10738 -- Deal with address clause case
10739
10740 if Is_Object (E) then
10741 Addr := Address_Clause (E);
10742
10743 if Present (Addr) then
10744 No_Independence;
10745 Error_Msg_Sloc := Sloc (Addr);
10746 Error_Msg_N ("\because of Address clause#", N);
10747 goto Continue;
10748 end if;
10749 end if;
10750
10751 -- Deal with independent components for array type
10752
10753 if IC and then Is_Array_Type (E) then
10754 Check_Array_Type (E);
10755 end if;
10756
10757 -- Deal with independent components for array object
10758
10759 if IC and then Is_Object (E) and then Is_Array_Type (Etype (E)) then
10760 Check_Array_Type (Etype (E));
10761 end if;
10762
10763 <<Continue>> null;
10764 end loop;
10765 end Validate_Independence;
10766
10767 -----------------------------------
10768 -- Validate_Unchecked_Conversion --
10769 -----------------------------------
10770
10771 procedure Validate_Unchecked_Conversion
10772 (N : Node_Id;
10773 Act_Unit : Entity_Id)
10774 is
10775 Source : Entity_Id;
10776 Target : Entity_Id;
10777 Vnode : Node_Id;
10778
10779 begin
10780 -- Obtain source and target types. Note that we call Ancestor_Subtype
10781 -- here because the processing for generic instantiation always makes
10782 -- subtypes, and we want the original frozen actual types.
10783
10784 -- If we are dealing with private types, then do the check on their
10785 -- fully declared counterparts if the full declarations have been
10786 -- encountered (they don't have to be visible, but they must exist!)
10787
10788 Source := Ancestor_Subtype (Etype (First_Formal (Act_Unit)));
10789
10790 if Is_Private_Type (Source)
10791 and then Present (Underlying_Type (Source))
10792 then
10793 Source := Underlying_Type (Source);
10794 end if;
10795
10796 Target := Ancestor_Subtype (Etype (Act_Unit));
10797
10798 -- If either type is generic, the instantiation happens within a generic
10799 -- unit, and there is nothing to check. The proper check will happen
10800 -- when the enclosing generic is instantiated.
10801
10802 if Is_Generic_Type (Source) or else Is_Generic_Type (Target) then
10803 return;
10804 end if;
10805
10806 if Is_Private_Type (Target)
10807 and then Present (Underlying_Type (Target))
10808 then
10809 Target := Underlying_Type (Target);
10810 end if;
10811
10812 -- Source may be unconstrained array, but not target
10813
10814 if Is_Array_Type (Target) and then not Is_Constrained (Target) then
10815 Error_Msg_N
10816 ("unchecked conversion to unconstrained array not allowed", N);
10817 return;
10818 end if;
10819
10820 -- Warn if conversion between two different convention pointers
10821
10822 if Is_Access_Type (Target)
10823 and then Is_Access_Type (Source)
10824 and then Convention (Target) /= Convention (Source)
10825 and then Warn_On_Unchecked_Conversion
10826 then
10827 -- Give warnings for subprogram pointers only on most targets. The
10828 -- exception is VMS, where data pointers can have different lengths
10829 -- depending on the pointer convention.
10830
10831 if Is_Access_Subprogram_Type (Target)
10832 or else Is_Access_Subprogram_Type (Source)
10833 or else OpenVMS_On_Target
10834 then
10835 Error_Msg_N
10836 ("?z?conversion between pointers with different conventions!",
10837 N);
10838 end if;
10839 end if;
10840
10841 -- Warn if one of the operands is Ada.Calendar.Time. Do not emit a
10842 -- warning when compiling GNAT-related sources.
10843
10844 if Warn_On_Unchecked_Conversion
10845 and then not In_Predefined_Unit (N)
10846 and then RTU_Loaded (Ada_Calendar)
10847 and then
10848 (Chars (Source) = Name_Time
10849 or else
10850 Chars (Target) = Name_Time)
10851 then
10852 -- If Ada.Calendar is loaded and the name of one of the operands is
10853 -- Time, there is a good chance that this is Ada.Calendar.Time.
10854
10855 declare
10856 Calendar_Time : constant Entity_Id :=
10857 Full_View (RTE (RO_CA_Time));
10858 begin
10859 pragma Assert (Present (Calendar_Time));
10860
10861 if Source = Calendar_Time or else Target = Calendar_Time then
10862 Error_Msg_N
10863 ("?z?representation of 'Time values may change between " &
10864 "'G'N'A'T versions", N);
10865 end if;
10866 end;
10867 end if;
10868
10869 -- Make entry in unchecked conversion table for later processing by
10870 -- Validate_Unchecked_Conversions, which will check sizes and alignments
10871 -- (using values set by the back-end where possible). This is only done
10872 -- if the appropriate warning is active.
10873
10874 if Warn_On_Unchecked_Conversion then
10875 Unchecked_Conversions.Append
10876 (New_Val => UC_Entry'(Eloc => Sloc (N),
10877 Source => Source,
10878 Target => Target));
10879
10880 -- If both sizes are known statically now, then back end annotation
10881 -- is not required to do a proper check but if either size is not
10882 -- known statically, then we need the annotation.
10883
10884 if Known_Static_RM_Size (Source)
10885 and then
10886 Known_Static_RM_Size (Target)
10887 then
10888 null;
10889 else
10890 Back_Annotate_Rep_Info := True;
10891 end if;
10892 end if;
10893
10894 -- If unchecked conversion to access type, and access type is declared
10895 -- in the same unit as the unchecked conversion, then set the flag
10896 -- No_Strict_Aliasing (no strict aliasing is implicit here)
10897
10898 if Is_Access_Type (Target) and then
10899 In_Same_Source_Unit (Target, N)
10900 then
10901 Set_No_Strict_Aliasing (Implementation_Base_Type (Target));
10902 end if;
10903
10904 -- Generate N_Validate_Unchecked_Conversion node for back end in case
10905 -- the back end needs to perform special validation checks.
10906
10907 -- Shouldn't this be in Exp_Ch13, since the check only gets done if we
10908 -- have full expansion and the back end is called ???
10909
10910 Vnode :=
10911 Make_Validate_Unchecked_Conversion (Sloc (N));
10912 Set_Source_Type (Vnode, Source);
10913 Set_Target_Type (Vnode, Target);
10914
10915 -- If the unchecked conversion node is in a list, just insert before it.
10916 -- If not we have some strange case, not worth bothering about.
10917
10918 if Is_List_Member (N) then
10919 Insert_After (N, Vnode);
10920 end if;
10921 end Validate_Unchecked_Conversion;
10922
10923 ------------------------------------
10924 -- Validate_Unchecked_Conversions --
10925 ------------------------------------
10926
10927 procedure Validate_Unchecked_Conversions is
10928 begin
10929 for N in Unchecked_Conversions.First .. Unchecked_Conversions.Last loop
10930 declare
10931 T : UC_Entry renames Unchecked_Conversions.Table (N);
10932
10933 Eloc : constant Source_Ptr := T.Eloc;
10934 Source : constant Entity_Id := T.Source;
10935 Target : constant Entity_Id := T.Target;
10936
10937 Source_Siz : Uint;
10938 Target_Siz : Uint;
10939
10940 begin
10941 -- This validation check, which warns if we have unequal sizes for
10942 -- unchecked conversion, and thus potentially implementation
10943 -- dependent semantics, is one of the few occasions on which we
10944 -- use the official RM size instead of Esize. See description in
10945 -- Einfo "Handling of Type'Size Values" for details.
10946
10947 if Serious_Errors_Detected = 0
10948 and then Known_Static_RM_Size (Source)
10949 and then Known_Static_RM_Size (Target)
10950
10951 -- Don't do the check if warnings off for either type, note the
10952 -- deliberate use of OR here instead of OR ELSE to get the flag
10953 -- Warnings_Off_Used set for both types if appropriate.
10954
10955 and then not (Has_Warnings_Off (Source)
10956 or
10957 Has_Warnings_Off (Target))
10958 then
10959 Source_Siz := RM_Size (Source);
10960 Target_Siz := RM_Size (Target);
10961
10962 if Source_Siz /= Target_Siz then
10963 Error_Msg
10964 ("?z?types for unchecked conversion have different sizes!",
10965 Eloc);
10966
10967 if All_Errors_Mode then
10968 Error_Msg_Name_1 := Chars (Source);
10969 Error_Msg_Uint_1 := Source_Siz;
10970 Error_Msg_Name_2 := Chars (Target);
10971 Error_Msg_Uint_2 := Target_Siz;
10972 Error_Msg ("\size of % is ^, size of % is ^?z?", Eloc);
10973
10974 Error_Msg_Uint_1 := UI_Abs (Source_Siz - Target_Siz);
10975
10976 if Is_Discrete_Type (Source)
10977 and then
10978 Is_Discrete_Type (Target)
10979 then
10980 if Source_Siz > Target_Siz then
10981 Error_Msg
10982 ("\?z?^ high order bits of source will "
10983 & "be ignored!", Eloc);
10984
10985 elsif Is_Unsigned_Type (Source) then
10986 Error_Msg
10987 ("\?z?source will be extended with ^ high order "
10988 & "zero bits?!", Eloc);
10989
10990 else
10991 Error_Msg
10992 ("\?z?source will be extended with ^ high order "
10993 & "sign bits!", Eloc);
10994 end if;
10995
10996 elsif Source_Siz < Target_Siz then
10997 if Is_Discrete_Type (Target) then
10998 if Bytes_Big_Endian then
10999 Error_Msg
11000 ("\?z?target value will include ^ undefined "
11001 & "low order bits!", Eloc);
11002 else
11003 Error_Msg
11004 ("\?z?target value will include ^ undefined "
11005 & "high order bits!", Eloc);
11006 end if;
11007
11008 else
11009 Error_Msg
11010 ("\?z?^ trailing bits of target value will be "
11011 & "undefined!", Eloc);
11012 end if;
11013
11014 else pragma Assert (Source_Siz > Target_Siz);
11015 Error_Msg
11016 ("\?z?^ trailing bits of source will be ignored!",
11017 Eloc);
11018 end if;
11019 end if;
11020 end if;
11021 end if;
11022
11023 -- If both types are access types, we need to check the alignment.
11024 -- If the alignment of both is specified, we can do it here.
11025
11026 if Serious_Errors_Detected = 0
11027 and then Ekind (Source) in Access_Kind
11028 and then Ekind (Target) in Access_Kind
11029 and then Target_Strict_Alignment
11030 and then Present (Designated_Type (Source))
11031 and then Present (Designated_Type (Target))
11032 then
11033 declare
11034 D_Source : constant Entity_Id := Designated_Type (Source);
11035 D_Target : constant Entity_Id := Designated_Type (Target);
11036
11037 begin
11038 if Known_Alignment (D_Source)
11039 and then
11040 Known_Alignment (D_Target)
11041 then
11042 declare
11043 Source_Align : constant Uint := Alignment (D_Source);
11044 Target_Align : constant Uint := Alignment (D_Target);
11045
11046 begin
11047 if Source_Align < Target_Align
11048 and then not Is_Tagged_Type (D_Source)
11049
11050 -- Suppress warning if warnings suppressed on either
11051 -- type or either designated type. Note the use of
11052 -- OR here instead of OR ELSE. That is intentional,
11053 -- we would like to set flag Warnings_Off_Used in
11054 -- all types for which warnings are suppressed.
11055
11056 and then not (Has_Warnings_Off (D_Source)
11057 or
11058 Has_Warnings_Off (D_Target)
11059 or
11060 Has_Warnings_Off (Source)
11061 or
11062 Has_Warnings_Off (Target))
11063 then
11064 Error_Msg_Uint_1 := Target_Align;
11065 Error_Msg_Uint_2 := Source_Align;
11066 Error_Msg_Node_1 := D_Target;
11067 Error_Msg_Node_2 := D_Source;
11068 Error_Msg
11069 ("?z?alignment of & (^) is stricter than "
11070 & "alignment of & (^)!", Eloc);
11071 Error_Msg
11072 ("\?z?resulting access value may have invalid "
11073 & "alignment!", Eloc);
11074 end if;
11075 end;
11076 end if;
11077 end;
11078 end if;
11079 end;
11080 end loop;
11081 end Validate_Unchecked_Conversions;
11082
11083 end Sem_Ch13;