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