t-linux64: Delete the 32-bit multilib that uses software floating point emulation.
[official-gcc.git] / gcc / ada / sem_ch13.adb
blob984462a025fade309a0fa60cec91f0740d670e23
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-2012, 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 ------------------------------------------------------------------------------
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_Dim; use Sem_Dim;
50 with Sem_Eval; use Sem_Eval;
51 with Sem_Res; use Sem_Res;
52 with Sem_Type; use Sem_Type;
53 with Sem_Util; use Sem_Util;
54 with Sem_Warn; use Sem_Warn;
55 with Sinput; use Sinput;
56 with Snames; use Snames;
57 with Stand; use Stand;
58 with Sinfo; use Sinfo;
59 with Stringt; use Stringt;
60 with Targparm; use Targparm;
61 with Ttypes; use Ttypes;
62 with Tbuild; use Tbuild;
63 with Urealp; use Urealp;
64 with Warnsw; use Warnsw;
66 with GNAT.Heap_Sort_G;
68 package body Sem_Ch13 is
70 SSU : constant Pos := System_Storage_Unit;
71 -- Convenient short hand for commonly used constant
73 -----------------------
74 -- Local Subprograms --
75 -----------------------
77 procedure Alignment_Check_For_Size_Change (Typ : Entity_Id; Size : Uint);
78 -- This routine is called after setting one of the sizes of type entity
79 -- Typ to Size. The purpose is to deal with the situation of a derived
80 -- type whose inherited alignment is no longer appropriate for the new
81 -- size value. In this case, we reset the Alignment to unknown.
83 procedure Build_Predicate_Function (Typ : Entity_Id; N : Node_Id);
84 -- If Typ has predicates (indicated by Has_Predicates being set for Typ,
85 -- then either there are pragma Invariant entries on the rep chain for the
86 -- type (note that Predicate aspects are converted to pragma Predicate), or
87 -- there are inherited aspects from a parent type, or ancestor subtypes.
88 -- This procedure builds the spec and body for the Predicate function that
89 -- tests these predicates. N is the freeze node for the type. The spec of
90 -- the function is inserted before the freeze node, and the body of the
91 -- function is inserted after the freeze node.
93 procedure Build_Static_Predicate
94 (Typ : Entity_Id;
95 Expr : Node_Id;
96 Nam : Name_Id);
97 -- Given a predicated type Typ, where Typ is a discrete static subtype,
98 -- whose predicate expression is Expr, tests if Expr is a static predicate,
99 -- and if so, builds the predicate range list. Nam is the name of the one
100 -- argument to the predicate function. Occurrences of the type name in the
101 -- predicate expression have been replaced by identifier references to this
102 -- name, which is unique, so any identifier with Chars matching Nam must be
103 -- a reference to the type. If the predicate is non-static, this procedure
104 -- returns doing nothing. If the predicate is static, then the predicate
105 -- list is stored in Static_Predicate (Typ), and the Expr is rewritten as
106 -- a canonicalized membership operation.
108 function Get_Alignment_Value (Expr : Node_Id) return Uint;
109 -- Given the expression for an alignment value, returns the corresponding
110 -- Uint value. If the value is inappropriate, then error messages are
111 -- posted as required, and a value of No_Uint is returned.
113 function Is_Operational_Item (N : Node_Id) return Boolean;
114 -- A specification for a stream attribute is allowed before the full type
115 -- is declared, as explained in AI-00137 and the corrigendum. Attributes
116 -- that do not specify a representation characteristic are operational
117 -- attributes.
119 procedure New_Stream_Subprogram
120 (N : Node_Id;
121 Ent : Entity_Id;
122 Subp : Entity_Id;
123 Nam : TSS_Name_Type);
124 -- Create a subprogram renaming of a given stream attribute to the
125 -- designated subprogram and then in the tagged case, provide this as a
126 -- primitive operation, or in the non-tagged case make an appropriate TSS
127 -- entry. This is more properly an expansion activity than just semantics,
128 -- but the presence of user-defined stream functions for limited types is a
129 -- legality check, which is why this takes place here rather than in
130 -- exp_ch13, where it was previously. Nam indicates the name of the TSS
131 -- function to be generated.
133 -- To avoid elaboration anomalies with freeze nodes, for untagged types
134 -- we generate both a subprogram declaration and a subprogram renaming
135 -- declaration, so that the attribute specification is handled as a
136 -- renaming_as_body. For tagged types, the specification is one of the
137 -- primitive specs.
139 generic
140 with procedure Replace_Type_Reference (N : Node_Id);
141 procedure Replace_Type_References_Generic (N : Node_Id; TName : Name_Id);
142 -- This is used to scan an expression for a predicate or invariant aspect
143 -- replacing occurrences of the name TName (the name of the subtype to
144 -- which the aspect applies) with appropriate references to the parameter
145 -- of the predicate function or invariant procedure. The procedure passed
146 -- as a generic parameter does the actual replacement of node N, which is
147 -- either a simple direct reference to TName, or a selected component that
148 -- represents an appropriately qualified occurrence of TName.
150 procedure Set_Biased
151 (E : Entity_Id;
152 N : Node_Id;
153 Msg : String;
154 Biased : Boolean := True);
155 -- If Biased is True, sets Has_Biased_Representation flag for E, and
156 -- outputs a warning message at node N if Warn_On_Biased_Representation is
157 -- is True. This warning inserts the string Msg to describe the construct
158 -- causing biasing.
160 ----------------------------------------------
161 -- Table for Validate_Unchecked_Conversions --
162 ----------------------------------------------
164 -- The following table collects unchecked conversions for validation.
165 -- Entries are made by Validate_Unchecked_Conversion and then the call
166 -- to Validate_Unchecked_Conversions does the actual error checking and
167 -- posting of warnings. The reason for this delayed processing is to take
168 -- advantage of back-annotations of size and alignment values performed by
169 -- the back end.
171 -- Note: the reason we store a Source_Ptr value instead of a Node_Id is
172 -- that by the time Validate_Unchecked_Conversions is called, Sprint will
173 -- already have modified all Sloc values if the -gnatD option is set.
175 type UC_Entry is record
176 Eloc : Source_Ptr; -- node used for posting warnings
177 Source : Entity_Id; -- source type for unchecked conversion
178 Target : Entity_Id; -- target type for unchecked conversion
179 end record;
181 package Unchecked_Conversions is new Table.Table (
182 Table_Component_Type => UC_Entry,
183 Table_Index_Type => Int,
184 Table_Low_Bound => 1,
185 Table_Initial => 50,
186 Table_Increment => 200,
187 Table_Name => "Unchecked_Conversions");
189 ----------------------------------------
190 -- Table for Validate_Address_Clauses --
191 ----------------------------------------
193 -- If an address clause has the form
195 -- for X'Address use Expr
197 -- where Expr is of the form Y'Address or recursively is a reference to a
198 -- constant of either of these forms, and X and Y are entities of objects,
199 -- then if Y has a smaller alignment than X, that merits a warning about
200 -- possible bad alignment. The following table collects address clauses of
201 -- this kind. We put these in a table so that they can be checked after the
202 -- back end has completed annotation of the alignments of objects, since we
203 -- can catch more cases that way.
205 type Address_Clause_Check_Record is record
206 N : Node_Id;
207 -- The address clause
209 X : Entity_Id;
210 -- The entity of the object overlaying Y
212 Y : Entity_Id;
213 -- The entity of the object being overlaid
215 Off : Boolean;
216 -- Whether the address is offset within Y
217 end record;
219 package Address_Clause_Checks is new Table.Table (
220 Table_Component_Type => Address_Clause_Check_Record,
221 Table_Index_Type => Int,
222 Table_Low_Bound => 1,
223 Table_Initial => 20,
224 Table_Increment => 200,
225 Table_Name => "Address_Clause_Checks");
227 -----------------------------------------
228 -- Adjust_Record_For_Reverse_Bit_Order --
229 -----------------------------------------
231 procedure Adjust_Record_For_Reverse_Bit_Order (R : Entity_Id) is
232 Comp : Node_Id;
233 CC : Node_Id;
235 begin
236 -- Processing depends on version of Ada
238 -- For Ada 95, we just renumber bits within a storage unit. We do the
239 -- same for Ada 83 mode, since we recognize the Bit_Order attribute in
240 -- Ada 83, and are free to add this extension.
242 if Ada_Version < Ada_2005 then
243 Comp := First_Component_Or_Discriminant (R);
244 while Present (Comp) loop
245 CC := Component_Clause (Comp);
247 -- If component clause is present, then deal with the non-default
248 -- bit order case for Ada 95 mode.
250 -- We only do this processing for the base type, and in fact that
251 -- is important, since otherwise if there are record subtypes, we
252 -- could reverse the bits once for each subtype, which is wrong.
254 if Present (CC)
255 and then Ekind (R) = E_Record_Type
256 then
257 declare
258 CFB : constant Uint := Component_Bit_Offset (Comp);
259 CSZ : constant Uint := Esize (Comp);
260 CLC : constant Node_Id := Component_Clause (Comp);
261 Pos : constant Node_Id := Position (CLC);
262 FB : constant Node_Id := First_Bit (CLC);
264 Storage_Unit_Offset : constant Uint :=
265 CFB / System_Storage_Unit;
267 Start_Bit : constant Uint :=
268 CFB mod System_Storage_Unit;
270 begin
271 -- Cases where field goes over storage unit boundary
273 if Start_Bit + CSZ > System_Storage_Unit then
275 -- Allow multi-byte field but generate warning
277 if Start_Bit mod System_Storage_Unit = 0
278 and then CSZ mod System_Storage_Unit = 0
279 then
280 Error_Msg_N
281 ("multi-byte field specified with non-standard"
282 & " Bit_Order?", CLC);
284 if Bytes_Big_Endian then
285 Error_Msg_N
286 ("bytes are not reversed "
287 & "(component is big-endian)?", CLC);
288 else
289 Error_Msg_N
290 ("bytes are not reversed "
291 & "(component is little-endian)?", CLC);
292 end if;
294 -- Do not allow non-contiguous field
296 else
297 Error_Msg_N
298 ("attempt to specify non-contiguous field "
299 & "not permitted", CLC);
300 Error_Msg_N
301 ("\caused by non-standard Bit_Order "
302 & "specified", CLC);
303 Error_Msg_N
304 ("\consider possibility of using "
305 & "Ada 2005 mode here", CLC);
306 end if;
308 -- Case where field fits in one storage unit
310 else
311 -- Give warning if suspicious component clause
313 if Intval (FB) >= System_Storage_Unit
314 and then Warn_On_Reverse_Bit_Order
315 then
316 Error_Msg_N
317 ("?Bit_Order clause does not affect " &
318 "byte ordering", Pos);
319 Error_Msg_Uint_1 :=
320 Intval (Pos) + Intval (FB) /
321 System_Storage_Unit;
322 Error_Msg_N
323 ("?position normalized to ^ before bit " &
324 "order interpreted", Pos);
325 end if;
327 -- Here is where we fix up the Component_Bit_Offset value
328 -- to account for the reverse bit order. Some examples of
329 -- what needs to be done are:
331 -- First_Bit .. Last_Bit Component_Bit_Offset
332 -- old new old new
334 -- 0 .. 0 7 .. 7 0 7
335 -- 0 .. 1 6 .. 7 0 6
336 -- 0 .. 2 5 .. 7 0 5
337 -- 0 .. 7 0 .. 7 0 4
339 -- 1 .. 1 6 .. 6 1 6
340 -- 1 .. 4 3 .. 6 1 3
341 -- 4 .. 7 0 .. 3 4 0
343 -- The rule is that the first bit is is obtained by
344 -- subtracting the old ending bit from storage_unit - 1.
346 Set_Component_Bit_Offset
347 (Comp,
348 (Storage_Unit_Offset * System_Storage_Unit) +
349 (System_Storage_Unit - 1) -
350 (Start_Bit + CSZ - 1));
352 Set_Normalized_First_Bit
353 (Comp,
354 Component_Bit_Offset (Comp) mod
355 System_Storage_Unit);
356 end if;
357 end;
358 end if;
360 Next_Component_Or_Discriminant (Comp);
361 end loop;
363 -- For Ada 2005, we do machine scalar processing, as fully described In
364 -- AI-133. This involves gathering all components which start at the
365 -- same byte offset and processing them together. Same approach is still
366 -- valid in later versions including Ada 2012.
368 else
369 declare
370 Max_Machine_Scalar_Size : constant Uint :=
371 UI_From_Int
372 (Standard_Long_Long_Integer_Size);
373 -- We use this as the maximum machine scalar size
375 Num_CC : Natural;
376 SSU : constant Uint := UI_From_Int (System_Storage_Unit);
378 begin
379 -- This first loop through components does two things. First it
380 -- deals with the case of components with component clauses whose
381 -- length is greater than the maximum machine scalar size (either
382 -- accepting them or rejecting as needed). Second, it counts the
383 -- number of components with component clauses whose length does
384 -- not exceed this maximum for later processing.
386 Num_CC := 0;
387 Comp := First_Component_Or_Discriminant (R);
388 while Present (Comp) loop
389 CC := Component_Clause (Comp);
391 if Present (CC) then
392 declare
393 Fbit : constant Uint :=
394 Static_Integer (First_Bit (CC));
395 Lbit : constant Uint :=
396 Static_Integer (Last_Bit (CC));
398 begin
399 -- Case of component with last bit >= max machine scalar
401 if Lbit >= Max_Machine_Scalar_Size then
403 -- This is allowed only if first bit is zero, and
404 -- last bit + 1 is a multiple of storage unit size.
406 if Fbit = 0 and then (Lbit + 1) mod SSU = 0 then
408 -- This is the case to give a warning if enabled
410 if Warn_On_Reverse_Bit_Order then
411 Error_Msg_N
412 ("multi-byte field specified with "
413 & " non-standard Bit_Order?", CC);
415 if Bytes_Big_Endian then
416 Error_Msg_N
417 ("\bytes are not reversed "
418 & "(component is big-endian)?", CC);
419 else
420 Error_Msg_N
421 ("\bytes are not reversed "
422 & "(component is little-endian)?", CC);
423 end if;
424 end if;
426 -- Give error message for RM 13.5.1(10) violation
428 else
429 Error_Msg_FE
430 ("machine scalar rules not followed for&",
431 First_Bit (CC), Comp);
433 Error_Msg_Uint_1 := Lbit;
434 Error_Msg_Uint_2 := Max_Machine_Scalar_Size;
435 Error_Msg_F
436 ("\last bit (^) exceeds maximum machine "
437 & "scalar size (^)",
438 First_Bit (CC));
440 if (Lbit + 1) mod SSU /= 0 then
441 Error_Msg_Uint_1 := SSU;
442 Error_Msg_F
443 ("\and is not a multiple of Storage_Unit (^) "
444 & "(RM 13.4.1(10))",
445 First_Bit (CC));
447 else
448 Error_Msg_Uint_1 := Fbit;
449 Error_Msg_F
450 ("\and first bit (^) is non-zero "
451 & "(RM 13.4.1(10))",
452 First_Bit (CC));
453 end if;
454 end if;
456 -- OK case of machine scalar related component clause,
457 -- For now, just count them.
459 else
460 Num_CC := Num_CC + 1;
461 end if;
462 end;
463 end if;
465 Next_Component_Or_Discriminant (Comp);
466 end loop;
468 -- We need to sort the component clauses on the basis of the
469 -- Position values in the clause, so we can group clauses with
470 -- the same Position. together to determine the relevant machine
471 -- scalar size.
473 Sort_CC : declare
474 Comps : array (0 .. Num_CC) of Entity_Id;
475 -- Array to collect component and discriminant entities. The
476 -- data starts at index 1, the 0'th entry is for the sort
477 -- routine.
479 function CP_Lt (Op1, Op2 : Natural) return Boolean;
480 -- Compare routine for Sort
482 procedure CP_Move (From : Natural; To : Natural);
483 -- Move routine for Sort
485 package Sorting is new GNAT.Heap_Sort_G (CP_Move, CP_Lt);
487 Start : Natural;
488 Stop : Natural;
489 -- Start and stop positions in the component list of the set of
490 -- components with the same starting position (that constitute
491 -- components in a single machine scalar).
493 MaxL : Uint;
494 -- Maximum last bit value of any component in this set
496 MSS : Uint;
497 -- Corresponding machine scalar size
499 -----------
500 -- CP_Lt --
501 -----------
503 function CP_Lt (Op1, Op2 : Natural) return Boolean is
504 begin
505 return Position (Component_Clause (Comps (Op1))) <
506 Position (Component_Clause (Comps (Op2)));
507 end CP_Lt;
509 -------------
510 -- CP_Move --
511 -------------
513 procedure CP_Move (From : Natural; To : Natural) is
514 begin
515 Comps (To) := Comps (From);
516 end CP_Move;
518 -- Start of processing for Sort_CC
520 begin
521 -- Collect the machine scalar relevant component clauses
523 Num_CC := 0;
524 Comp := First_Component_Or_Discriminant (R);
525 while Present (Comp) loop
526 declare
527 CC : constant Node_Id := Component_Clause (Comp);
529 begin
530 -- Collect only component clauses whose last bit is less
531 -- than machine scalar size. Any component clause whose
532 -- last bit exceeds this value does not take part in
533 -- machine scalar layout considerations. The test for
534 -- Error_Posted makes sure we exclude component clauses
535 -- for which we already posted an error.
537 if Present (CC)
538 and then not Error_Posted (Last_Bit (CC))
539 and then Static_Integer (Last_Bit (CC)) <
540 Max_Machine_Scalar_Size
541 then
542 Num_CC := Num_CC + 1;
543 Comps (Num_CC) := Comp;
544 end if;
545 end;
547 Next_Component_Or_Discriminant (Comp);
548 end loop;
550 -- Sort by ascending position number
552 Sorting.Sort (Num_CC);
554 -- We now have all the components whose size does not exceed
555 -- the max machine scalar value, sorted by starting position.
556 -- In this loop we gather groups of clauses starting at the
557 -- same position, to process them in accordance with AI-133.
559 Stop := 0;
560 while Stop < Num_CC loop
561 Start := Stop + 1;
562 Stop := Start;
563 MaxL :=
564 Static_Integer
565 (Last_Bit (Component_Clause (Comps (Start))));
566 while Stop < Num_CC loop
567 if Static_Integer
568 (Position (Component_Clause (Comps (Stop + 1)))) =
569 Static_Integer
570 (Position (Component_Clause (Comps (Stop))))
571 then
572 Stop := Stop + 1;
573 MaxL :=
574 UI_Max
575 (MaxL,
576 Static_Integer
577 (Last_Bit
578 (Component_Clause (Comps (Stop)))));
579 else
580 exit;
581 end if;
582 end loop;
584 -- Now we have a group of component clauses from Start to
585 -- Stop whose positions are identical, and MaxL is the
586 -- maximum last bit value of any of these components.
588 -- We need to determine the corresponding machine scalar
589 -- size. This loop assumes that machine scalar sizes are
590 -- even, and that each possible machine scalar has twice
591 -- as many bits as the next smaller one.
593 MSS := Max_Machine_Scalar_Size;
594 while MSS mod 2 = 0
595 and then (MSS / 2) >= SSU
596 and then (MSS / 2) > MaxL
597 loop
598 MSS := MSS / 2;
599 end loop;
601 -- Here is where we fix up the Component_Bit_Offset value
602 -- to account for the reverse bit order. Some examples of
603 -- what needs to be done for the case of a machine scalar
604 -- size of 8 are:
606 -- First_Bit .. Last_Bit Component_Bit_Offset
607 -- old new old new
609 -- 0 .. 0 7 .. 7 0 7
610 -- 0 .. 1 6 .. 7 0 6
611 -- 0 .. 2 5 .. 7 0 5
612 -- 0 .. 7 0 .. 7 0 4
614 -- 1 .. 1 6 .. 6 1 6
615 -- 1 .. 4 3 .. 6 1 3
616 -- 4 .. 7 0 .. 3 4 0
618 -- The rule is that the first bit is obtained by subtracting
619 -- the old ending bit from machine scalar size - 1.
621 for C in Start .. Stop loop
622 declare
623 Comp : constant Entity_Id := Comps (C);
624 CC : constant Node_Id :=
625 Component_Clause (Comp);
626 LB : constant Uint :=
627 Static_Integer (Last_Bit (CC));
628 NFB : constant Uint := MSS - Uint_1 - LB;
629 NLB : constant Uint := NFB + Esize (Comp) - 1;
630 Pos : constant Uint :=
631 Static_Integer (Position (CC));
633 begin
634 if Warn_On_Reverse_Bit_Order then
635 Error_Msg_Uint_1 := MSS;
636 Error_Msg_N
637 ("info: reverse bit order in machine " &
638 "scalar of length^?", First_Bit (CC));
639 Error_Msg_Uint_1 := NFB;
640 Error_Msg_Uint_2 := NLB;
642 if Bytes_Big_Endian then
643 Error_Msg_NE
644 ("?\info: big-endian range for "
645 & "component & is ^ .. ^",
646 First_Bit (CC), Comp);
647 else
648 Error_Msg_NE
649 ("?\info: little-endian range "
650 & "for component & is ^ .. ^",
651 First_Bit (CC), Comp);
652 end if;
653 end if;
655 Set_Component_Bit_Offset (Comp, Pos * SSU + NFB);
656 Set_Normalized_First_Bit (Comp, NFB mod SSU);
657 end;
658 end loop;
659 end loop;
660 end Sort_CC;
661 end;
662 end if;
663 end Adjust_Record_For_Reverse_Bit_Order;
665 -------------------------------------
666 -- Alignment_Check_For_Size_Change --
667 -------------------------------------
669 procedure Alignment_Check_For_Size_Change (Typ : Entity_Id; Size : Uint) is
670 begin
671 -- If the alignment is known, and not set by a rep clause, and is
672 -- inconsistent with the size being set, then reset it to unknown,
673 -- we assume in this case that the size overrides the inherited
674 -- alignment, and that the alignment must be recomputed.
676 if Known_Alignment (Typ)
677 and then not Has_Alignment_Clause (Typ)
678 and then Size mod (Alignment (Typ) * SSU) /= 0
679 then
680 Init_Alignment (Typ);
681 end if;
682 end Alignment_Check_For_Size_Change;
684 -----------------------------------
685 -- Analyze_Aspect_Specifications --
686 -----------------------------------
688 procedure Analyze_Aspect_Specifications (N : Node_Id; E : Entity_Id) is
689 Aspect : Node_Id;
690 Aitem : Node_Id;
691 Ent : Node_Id;
693 L : constant List_Id := Aspect_Specifications (N);
695 Ins_Node : Node_Id := N;
696 -- Insert pragmas (except Pre/Post/Invariant/Predicate) after this node
698 -- The general processing involves building an attribute definition
699 -- clause or a pragma node that corresponds to the aspect. Then one
700 -- of two things happens:
702 -- If we are required to delay the evaluation of this aspect to the
703 -- freeze point, we attach the corresponding pragma/attribute definition
704 -- clause to the aspect specification node, which is then placed in the
705 -- Rep Item chain. In this case we mark the entity by setting the flag
706 -- Has_Delayed_Aspects and we evaluate the rep item at the freeze point.
708 -- If no delay is required, we just insert the pragma or attribute
709 -- after the declaration, and it will get processed by the normal
710 -- circuit. The From_Aspect_Specification flag is set on the pragma
711 -- or attribute definition node in either case to activate special
712 -- processing (e.g. not traversing the list of homonyms for inline).
714 Delay_Required : Boolean := False;
715 -- Set True if delay is required
717 begin
718 pragma Assert (Present (L));
720 -- Loop through aspects
722 Aspect := First (L);
723 Aspect_Loop : while Present (Aspect) loop
724 declare
725 Loc : constant Source_Ptr := Sloc (Aspect);
726 Id : constant Node_Id := Identifier (Aspect);
727 Expr : constant Node_Id := Expression (Aspect);
728 Nam : constant Name_Id := Chars (Id);
729 A_Id : constant Aspect_Id := Get_Aspect_Id (Nam);
730 Anod : Node_Id;
732 Eloc : Source_Ptr := No_Location;
733 -- Source location of expression, modified when we split PPC's. It
734 -- is set below when Expr is present.
736 procedure Check_False_Aspect_For_Derived_Type;
737 -- This procedure checks for the case of a false aspect for a
738 -- derived type, which improperly tries to cancel an aspect
739 -- inherited from the parent;
741 -----------------------------------------
742 -- Check_False_Aspect_For_Derived_Type --
743 -----------------------------------------
745 procedure Check_False_Aspect_For_Derived_Type is
746 begin
747 -- We are only checking derived types
749 if not Is_Derived_Type (E) then
750 return;
751 end if;
753 case A_Id is
754 when Aspect_Atomic | Aspect_Shared =>
755 if not Is_Atomic (E) then
756 return;
757 end if;
759 when Aspect_Atomic_Components =>
760 if not Has_Atomic_Components (E) then
761 return;
762 end if;
764 when Aspect_Discard_Names =>
765 if not Discard_Names (E) then
766 return;
767 end if;
769 when Aspect_Pack =>
770 if not Is_Packed (E) then
771 return;
772 end if;
774 when Aspect_Unchecked_Union =>
775 if not Is_Unchecked_Union (E) then
776 return;
777 end if;
779 when Aspect_Volatile =>
780 if not Is_Volatile (E) then
781 return;
782 end if;
784 when Aspect_Volatile_Components =>
785 if not Has_Volatile_Components (E) then
786 return;
787 end if;
789 when others =>
790 return;
791 end case;
793 -- Fall through means we are canceling an inherited aspect
795 Error_Msg_Name_1 := Nam;
796 Error_Msg_NE
797 ("derived type& inherits aspect%, cannot cancel", Expr, E);
798 end Check_False_Aspect_For_Derived_Type;
800 -- Start of processing for Aspect_Loop
802 begin
803 -- Skip aspect if already analyzed (not clear if this is needed)
805 if Analyzed (Aspect) then
806 goto Continue;
807 end if;
809 -- Set the source location of expression, used in the case of
810 -- a failed precondition/postcondition or invariant. Note that
811 -- the source location of the expression is not usually the best
812 -- choice here. For example, it gets located on the last AND
813 -- keyword in a chain of boolean expressiond AND'ed together.
814 -- It is best to put the message on the first character of the
815 -- assertion, which is the effect of the First_Node call here.
817 if Present (Expr) then
818 Eloc := Sloc (First_Node (Expr));
819 end if;
821 -- Check restriction No_Implementation_Aspect_Specifications
823 if Impl_Defined_Aspects (A_Id) then
824 Check_Restriction
825 (No_Implementation_Aspect_Specifications, Aspect);
826 end if;
828 -- Check restriction No_Specification_Of_Aspect
830 Check_Restriction_No_Specification_Of_Aspect (Aspect);
832 -- Analyze this aspect
834 Set_Analyzed (Aspect);
835 Set_Entity (Aspect, E);
836 Ent := New_Occurrence_Of (E, Sloc (Id));
838 -- Check for duplicate aspect. Note that the Comes_From_Source
839 -- test allows duplicate Pre/Post's that we generate internally
840 -- to escape being flagged here.
842 if No_Duplicates_Allowed (A_Id) then
843 Anod := First (L);
844 while Anod /= Aspect loop
845 if Same_Aspect
846 (A_Id, Get_Aspect_Id (Chars (Identifier (Anod))))
847 and then Comes_From_Source (Aspect)
848 then
849 Error_Msg_Name_1 := Nam;
850 Error_Msg_Sloc := Sloc (Anod);
852 -- Case of same aspect specified twice
854 if Class_Present (Anod) = Class_Present (Aspect) then
855 if not Class_Present (Anod) then
856 Error_Msg_NE
857 ("aspect% for & previously given#",
858 Id, E);
859 else
860 Error_Msg_NE
861 ("aspect `%''Class` for & previously given#",
862 Id, E);
863 end if;
865 -- Case of Pre and Pre'Class both specified
867 elsif Nam = Name_Pre then
868 if Class_Present (Aspect) then
869 Error_Msg_NE
870 ("aspect `Pre''Class` for & is not allowed here",
871 Id, E);
872 Error_Msg_NE
873 ("\since aspect `Pre` previously given#",
874 Id, E);
876 else
877 Error_Msg_NE
878 ("aspect `Pre` for & is not allowed here",
879 Id, E);
880 Error_Msg_NE
881 ("\since aspect `Pre''Class` previously given#",
882 Id, E);
883 end if;
884 end if;
886 -- Allowed case of X and X'Class both specified
887 end if;
889 Next (Anod);
890 end loop;
891 end if;
893 -- Check some general restrictions on language defined aspects
895 if not Impl_Defined_Aspects (A_Id) then
896 Error_Msg_Name_1 := Nam;
898 -- Not allowed for renaming declarations
900 if Nkind (N) in N_Renaming_Declaration then
901 Error_Msg_N
902 ("aspect % not allowed for renaming declaration",
903 Aspect);
904 end if;
906 -- Not allowed for formal type declarations
908 if Nkind (N) = N_Formal_Type_Declaration then
909 Error_Msg_N
910 ("aspect % not allowed for formal type declaration",
911 Aspect);
912 end if;
913 end if;
915 -- Copy expression for later processing by the procedures
916 -- Check_Aspect_At_[Freeze_Point | End_Of_Declarations]
918 Set_Entity (Id, New_Copy_Tree (Expr));
920 -- Processing based on specific aspect
922 case A_Id is
924 -- No_Aspect should be impossible
926 when No_Aspect =>
927 raise Program_Error;
929 -- Aspects taking an optional boolean argument
931 when Boolean_Aspects =>
932 Set_Is_Boolean_Aspect (Aspect);
934 -- Special treatment for Aspect_Lock_Free since it is the
935 -- only Boolean_Aspect that doesn't correspond to a pragma.
937 if A_Id = Aspect_Lock_Free then
938 if Ekind (E) /= E_Protected_Type then
939 Error_Msg_N
940 ("aspect % only applies to protected objects",
941 Aspect);
942 end if;
944 -- Set the Uses_Lock_Free flag to True if there is no
945 -- expression or if the expression is True.
947 if No (Expr) or else Is_True (Static_Boolean (Expr)) then
948 Set_Uses_Lock_Free (E);
949 end if;
951 goto Continue;
952 end if;
954 -- For all other aspects we just create a matching pragma
955 -- and insert it, if the expression is missing or set to
956 -- True. If the expression is False, we can ignore the
957 -- aspect with the exception that in the case of a derived
958 -- type, we must check for an illegal attempt to cancel an
959 -- inherited aspect.
961 if Present (Expr)
962 and then Is_False (Static_Boolean (Expr))
963 then
964 Check_False_Aspect_For_Derived_Type;
965 goto Continue;
966 end if;
968 -- If True, build corresponding pragma node
970 Aitem :=
971 Make_Pragma (Loc,
972 Pragma_Argument_Associations => New_List (Ent),
973 Pragma_Identifier =>
974 Make_Identifier (Sloc (Id), Chars (Id)));
976 -- Never need to delay for boolean aspects
978 pragma Assert (not Delay_Required);
980 -- Library unit aspects. These are boolean aspects, but we
981 -- have to do special things with the insertion, since the
982 -- pragma belongs inside the declarations of a package.
984 when Library_Unit_Aspects =>
985 if Present (Expr)
986 and then Is_False (Static_Boolean (Expr))
987 then
988 goto Continue;
989 end if;
991 -- Build corresponding pragma node
993 Aitem :=
994 Make_Pragma (Loc,
995 Pragma_Argument_Associations => New_List (Ent),
996 Pragma_Identifier =>
997 Make_Identifier (Sloc (Id), Chars (Id)));
999 -- This requires special handling in the case of a package
1000 -- declaration, the pragma needs to be inserted in the list
1001 -- of declarations for the associated package. There is no
1002 -- issue of visibility delay for these aspects.
1004 if Nkind (N) = N_Package_Declaration then
1005 if Nkind (Parent (N)) /= N_Compilation_Unit then
1006 Error_Msg_N
1007 ("incorrect context for library unit aspect&", Id);
1008 else
1009 Prepend
1010 (Aitem, Visible_Declarations (Specification (N)));
1011 end if;
1013 goto Continue;
1014 end if;
1016 -- If not package declaration, no delay is required
1018 pragma Assert (not Delay_Required);
1020 -- Aspects related to container iterators. These aspects denote
1021 -- subprograms, and thus must be delayed.
1023 when Aspect_Constant_Indexing |
1024 Aspect_Variable_Indexing =>
1026 if not Is_Type (E) or else not Is_Tagged_Type (E) then
1027 Error_Msg_N ("indexing applies to a tagged type", N);
1028 end if;
1030 Aitem :=
1031 Make_Attribute_Definition_Clause (Loc,
1032 Name => Ent,
1033 Chars => Chars (Id),
1034 Expression => Relocate_Node (Expr));
1036 Delay_Required := True;
1037 Set_Is_Delayed_Aspect (Aspect);
1039 when Aspect_Default_Iterator |
1040 Aspect_Iterator_Element =>
1042 Aitem :=
1043 Make_Attribute_Definition_Clause (Loc,
1044 Name => Ent,
1045 Chars => Chars (Id),
1046 Expression => Relocate_Node (Expr));
1048 Delay_Required := True;
1049 Set_Is_Delayed_Aspect (Aspect);
1051 when Aspect_Implicit_Dereference =>
1052 if not Is_Type (E)
1053 or else not Has_Discriminants (E)
1054 then
1055 Error_Msg_N
1056 ("Aspect must apply to a type with discriminants", N);
1057 goto Continue;
1059 else
1060 declare
1061 Disc : Entity_Id;
1063 begin
1064 Disc := First_Discriminant (E);
1065 while Present (Disc) loop
1066 if Chars (Expr) = Chars (Disc)
1067 and then Ekind (Etype (Disc)) =
1068 E_Anonymous_Access_Type
1069 then
1070 Set_Has_Implicit_Dereference (E);
1071 Set_Has_Implicit_Dereference (Disc);
1072 goto Continue;
1073 end if;
1075 Next_Discriminant (Disc);
1076 end loop;
1078 -- Error if no proper access discriminant.
1080 Error_Msg_NE
1081 ("not an access discriminant of&", Expr, E);
1082 end;
1084 goto Continue;
1085 end if;
1087 -- Aspects corresponding to attribute definition clauses
1089 when Aspect_Address |
1090 Aspect_Alignment |
1091 Aspect_Bit_Order |
1092 Aspect_Component_Size |
1093 Aspect_External_Tag |
1094 Aspect_Input |
1095 Aspect_Machine_Radix |
1096 Aspect_Object_Size |
1097 Aspect_Output |
1098 Aspect_Read |
1099 Aspect_Scalar_Storage_Order |
1100 Aspect_Size |
1101 Aspect_Small |
1102 Aspect_Simple_Storage_Pool |
1103 Aspect_Storage_Pool |
1104 Aspect_Storage_Size |
1105 Aspect_Stream_Size |
1106 Aspect_Value_Size |
1107 Aspect_Write =>
1109 -- Construct the attribute definition clause
1111 Aitem :=
1112 Make_Attribute_Definition_Clause (Loc,
1113 Name => Ent,
1114 Chars => Chars (Id),
1115 Expression => Relocate_Node (Expr));
1117 -- A delay is required except in the common case where
1118 -- the expression is a literal, in which case it is fine
1119 -- to take care of it right away.
1121 if Nkind_In (Expr, N_Integer_Literal, N_String_Literal) then
1122 pragma Assert (not Delay_Required);
1123 null;
1124 else
1125 Delay_Required := True;
1126 Set_Is_Delayed_Aspect (Aspect);
1127 end if;
1129 -- Aspects corresponding to pragmas with two arguments, where
1130 -- the first argument is a local name referring to the entity,
1131 -- and the second argument is the aspect definition expression
1132 -- which is an expression that does not get analyzed.
1134 when Aspect_Suppress |
1135 Aspect_Unsuppress =>
1137 -- Construct the pragma
1139 Aitem :=
1140 Make_Pragma (Loc,
1141 Pragma_Argument_Associations => New_List (
1142 New_Occurrence_Of (E, Loc),
1143 Relocate_Node (Expr)),
1144 Pragma_Identifier =>
1145 Make_Identifier (Sloc (Id), Chars (Id)));
1147 -- We don't have to play the delay game here, since the only
1148 -- values are check names which don't get analyzed anyway.
1150 pragma Assert (not Delay_Required);
1152 when Aspect_Synchronization =>
1154 -- The aspect corresponds to pragma Implemented.
1155 -- Construct the pragma
1157 Aitem :=
1158 Make_Pragma (Loc,
1159 Pragma_Argument_Associations => New_List (
1160 New_Occurrence_Of (E, Loc),
1161 Relocate_Node (Expr)),
1162 Pragma_Identifier =>
1163 Make_Identifier (Sloc (Id), Name_Implemented));
1165 pragma Assert (not Delay_Required);
1167 -- Aspects corresponding to pragmas with two arguments, where
1168 -- the second argument is a local name referring to the entity,
1169 -- and the first argument is the aspect definition expression.
1171 when Aspect_Convention =>
1172 Aitem :=
1173 Make_Pragma (Loc,
1174 Pragma_Argument_Associations =>
1175 New_List (Relocate_Node (Expr), Ent),
1176 Pragma_Identifier =>
1177 Make_Identifier (Sloc (Id), Chars (Id)));
1179 when Aspect_Warnings =>
1181 -- Construct the pragma
1183 Aitem :=
1184 Make_Pragma (Loc,
1185 Pragma_Argument_Associations => New_List (
1186 Relocate_Node (Expr),
1187 New_Occurrence_Of (E, Loc)),
1188 Pragma_Identifier =>
1189 Make_Identifier (Sloc (Id), Chars (Id)),
1190 Class_Present => Class_Present (Aspect));
1192 -- We don't have to play the delay game here, since the only
1193 -- values are ON/OFF which don't get analyzed anyway.
1195 pragma Assert (not Delay_Required);
1197 -- Default_Value and Default_Component_Value aspects. These
1198 -- are specially handled because they have no corresponding
1199 -- pragmas or attributes.
1201 when Aspect_Default_Value | Aspect_Default_Component_Value =>
1202 Error_Msg_Name_1 := Chars (Id);
1204 if not Is_Type (E) then
1205 Error_Msg_N ("aspect% can only apply to a type", Id);
1206 goto Continue;
1208 elsif not Is_First_Subtype (E) then
1209 Error_Msg_N ("aspect% cannot apply to subtype", Id);
1210 goto Continue;
1212 elsif A_Id = Aspect_Default_Value
1213 and then not Is_Scalar_Type (E)
1214 then
1215 Error_Msg_N
1216 ("aspect% can only be applied to scalar type", Id);
1217 goto Continue;
1219 elsif A_Id = Aspect_Default_Component_Value then
1220 if not Is_Array_Type (E) then
1221 Error_Msg_N
1222 ("aspect% can only be applied to array type", Id);
1223 goto Continue;
1224 elsif not Is_Scalar_Type (Component_Type (E)) then
1225 Error_Msg_N
1226 ("aspect% requires scalar components", Id);
1227 goto Continue;
1228 end if;
1229 end if;
1231 Aitem := Empty;
1232 Delay_Required := True;
1233 Set_Is_Delayed_Aspect (Aspect);
1234 Set_Has_Default_Aspect (Base_Type (Entity (Ent)));
1236 if Is_Scalar_Type (E) then
1237 Set_Default_Aspect_Value (Entity (Ent), Expr);
1238 else
1239 Set_Default_Aspect_Component_Value (Entity (Ent), Expr);
1240 end if;
1242 when Aspect_Attach_Handler =>
1243 Aitem :=
1244 Make_Pragma (Loc,
1245 Pragma_Identifier =>
1246 Make_Identifier (Sloc (Id), Name_Attach_Handler),
1247 Pragma_Argument_Associations =>
1248 New_List (Ent, Relocate_Node (Expr)));
1250 Set_From_Aspect_Specification (Aitem, True);
1251 Set_Corresponding_Aspect (Aitem, Aspect);
1253 pragma Assert (not Delay_Required);
1255 when Aspect_Priority |
1256 Aspect_Interrupt_Priority |
1257 Aspect_Dispatching_Domain |
1258 Aspect_CPU =>
1259 declare
1260 Pname : Name_Id;
1262 begin
1263 if A_Id = Aspect_Priority then
1264 Pname := Name_Priority;
1266 elsif A_Id = Aspect_Interrupt_Priority then
1267 Pname := Name_Interrupt_Priority;
1269 elsif A_Id = Aspect_CPU then
1270 Pname := Name_CPU;
1272 else
1273 Pname := Name_Dispatching_Domain;
1274 end if;
1276 Aitem :=
1277 Make_Pragma (Loc,
1278 Pragma_Identifier =>
1279 Make_Identifier (Sloc (Id), Pname),
1280 Pragma_Argument_Associations =>
1281 New_List
1282 (Make_Pragma_Argument_Association
1283 (Sloc => Sloc (Id),
1284 Expression => Relocate_Node (Expr))));
1286 Set_From_Aspect_Specification (Aitem, True);
1287 Set_Corresponding_Aspect (Aitem, Aspect);
1289 pragma Assert (not Delay_Required);
1290 end;
1292 -- Aspects Pre/Post generate Precondition/Postcondition pragmas
1293 -- with a first argument that is the expression, and a second
1294 -- argument that is an informative message if the test fails.
1295 -- This is inserted right after the declaration, to get the
1296 -- required pragma placement. The processing for the pragmas
1297 -- takes care of the required delay.
1299 when Pre_Post_Aspects => declare
1300 Pname : Name_Id;
1302 begin
1303 if A_Id = Aspect_Pre or else A_Id = Aspect_Precondition then
1304 Pname := Name_Precondition;
1305 else
1306 Pname := Name_Postcondition;
1307 end if;
1309 -- If the expressions is of the form A and then B, then
1310 -- we generate separate Pre/Post aspects for the separate
1311 -- clauses. Since we allow multiple pragmas, there is no
1312 -- problem in allowing multiple Pre/Post aspects internally.
1313 -- These should be treated in reverse order (B first and
1314 -- A second) since they are later inserted just after N in
1315 -- the order they are treated. This way, the pragma for A
1316 -- ends up preceding the pragma for B, which may have an
1317 -- importance for the error raised (either constraint error
1318 -- or precondition error).
1320 -- We do not do this for Pre'Class, since we have to put
1321 -- these conditions together in a complex OR expression
1323 -- We do not do this in ASIS mode, as ASIS relies on the
1324 -- original node representing the complete expression, when
1325 -- retrieving it through the source aspect table.
1327 if not ASIS_Mode
1328 and then (Pname = Name_Postcondition
1329 or else not Class_Present (Aspect))
1330 then
1331 while Nkind (Expr) = N_And_Then loop
1332 Insert_After (Aspect,
1333 Make_Aspect_Specification (Sloc (Left_Opnd (Expr)),
1334 Identifier => Identifier (Aspect),
1335 Expression => Relocate_Node (Left_Opnd (Expr)),
1336 Class_Present => Class_Present (Aspect),
1337 Split_PPC => True));
1338 Rewrite (Expr, Relocate_Node (Right_Opnd (Expr)));
1339 Eloc := Sloc (Expr);
1340 end loop;
1341 end if;
1343 -- Build the precondition/postcondition pragma
1345 Aitem :=
1346 Make_Pragma (Loc,
1347 Pragma_Identifier =>
1348 Make_Identifier (Sloc (Id), Pname),
1349 Class_Present => Class_Present (Aspect),
1350 Split_PPC => Split_PPC (Aspect),
1351 Pragma_Argument_Associations => New_List (
1352 Make_Pragma_Argument_Association (Eloc,
1353 Chars => Name_Check,
1354 Expression => Relocate_Node (Expr))));
1356 -- Add message unless exception messages are suppressed
1358 if not Opt.Exception_Locations_Suppressed then
1359 Append_To (Pragma_Argument_Associations (Aitem),
1360 Make_Pragma_Argument_Association (Eloc,
1361 Chars => Name_Message,
1362 Expression =>
1363 Make_String_Literal (Eloc,
1364 Strval => "failed "
1365 & Get_Name_String (Pname)
1366 & " from "
1367 & Build_Location_String (Eloc))));
1368 end if;
1370 Set_From_Aspect_Specification (Aitem, True);
1371 Set_Corresponding_Aspect (Aitem, Aspect);
1372 Set_Is_Delayed_Aspect (Aspect);
1374 -- For Pre/Post cases, insert immediately after the entity
1375 -- declaration, since that is the required pragma placement.
1376 -- Note that for these aspects, we do not have to worry
1377 -- about delay issues, since the pragmas themselves deal
1378 -- with delay of visibility for the expression analysis.
1380 -- If the entity is a library-level subprogram, the pre/
1381 -- postconditions must be treated as late pragmas.
1383 if Nkind (Parent (N)) = N_Compilation_Unit then
1384 Add_Global_Declaration (Aitem);
1385 else
1386 Insert_After (N, Aitem);
1387 end if;
1389 goto Continue;
1390 end;
1392 -- Invariant aspects generate a corresponding pragma with a
1393 -- first argument that is the entity, a second argument that is
1394 -- the expression and a third argument that is an appropriate
1395 -- message. This is inserted right after the declaration, to
1396 -- get the required pragma placement. The pragma processing
1397 -- takes care of the required delay.
1399 when Aspect_Invariant |
1400 Aspect_Type_Invariant =>
1402 -- Analysis of the pragma will verify placement legality:
1403 -- an invariant must apply to a private type, or appear in
1404 -- the private part of a spec and apply to a completion.
1406 -- Construct the pragma
1408 Aitem :=
1409 Make_Pragma (Loc,
1410 Pragma_Argument_Associations =>
1411 New_List (Ent, Relocate_Node (Expr)),
1412 Class_Present => Class_Present (Aspect),
1413 Pragma_Identifier =>
1414 Make_Identifier (Sloc (Id), Name_Invariant));
1416 -- Add message unless exception messages are suppressed
1418 if not Opt.Exception_Locations_Suppressed then
1419 Append_To (Pragma_Argument_Associations (Aitem),
1420 Make_Pragma_Argument_Association (Eloc,
1421 Chars => Name_Message,
1422 Expression =>
1423 Make_String_Literal (Eloc,
1424 Strval => "failed invariant from "
1425 & Build_Location_String (Eloc))));
1426 end if;
1428 Set_From_Aspect_Specification (Aitem, True);
1429 Set_Corresponding_Aspect (Aitem, Aspect);
1430 Set_Is_Delayed_Aspect (Aspect);
1432 -- For Invariant case, insert immediately after the entity
1433 -- declaration. We do not have to worry about delay issues
1434 -- since the pragma processing takes care of this.
1436 Insert_After (N, Aitem);
1437 goto Continue;
1439 -- Predicate aspects generate a corresponding pragma with a
1440 -- first argument that is the entity, and the second argument
1441 -- is the expression.
1443 when Aspect_Dynamic_Predicate |
1444 Aspect_Predicate |
1445 Aspect_Static_Predicate =>
1447 -- Construct the pragma (always a pragma Predicate, with
1448 -- flags recording whether it is static/dynamic).
1450 Aitem :=
1451 Make_Pragma (Loc,
1452 Pragma_Argument_Associations =>
1453 New_List (Ent, Relocate_Node (Expr)),
1454 Class_Present => Class_Present (Aspect),
1455 Pragma_Identifier =>
1456 Make_Identifier (Sloc (Id), Name_Predicate));
1458 Set_From_Aspect_Specification (Aitem, True);
1459 Set_Corresponding_Aspect (Aitem, Aspect);
1461 -- Make sure we have a freeze node (it might otherwise be
1462 -- missing in cases like subtype X is Y, and we would not
1463 -- have a place to build the predicate function).
1465 -- If the type is private, indicate that its completion
1466 -- has a freeze node, because that is the one that will be
1467 -- visible at freeze time.
1469 Set_Has_Predicates (E);
1471 if Is_Private_Type (E)
1472 and then Present (Full_View (E))
1473 then
1474 Set_Has_Predicates (Full_View (E));
1475 Set_Has_Delayed_Aspects (Full_View (E));
1476 Ensure_Freeze_Node (Full_View (E));
1477 end if;
1479 Ensure_Freeze_Node (E);
1480 Set_Is_Delayed_Aspect (Aspect);
1481 Delay_Required := True;
1483 when Aspect_Contract_Case |
1484 Aspect_Test_Case =>
1485 declare
1486 Args : List_Id;
1487 Comp_Expr : Node_Id;
1488 Comp_Assn : Node_Id;
1489 New_Expr : Node_Id;
1491 begin
1492 Args := New_List;
1494 if Nkind (Parent (N)) = N_Compilation_Unit then
1495 Error_Msg_Name_1 := Nam;
1496 Error_Msg_N ("incorrect placement of aspect `%`", E);
1497 goto Continue;
1498 end if;
1500 if Nkind (Expr) /= N_Aggregate then
1501 Error_Msg_Name_1 := Nam;
1502 Error_Msg_NE
1503 ("wrong syntax for aspect `%` for &", Id, E);
1504 goto Continue;
1505 end if;
1507 -- Make pragma expressions refer to the original aspect
1508 -- expressions through the Original_Node link. This is
1509 -- used in semantic analysis for ASIS mode, so that the
1510 -- original expression also gets analyzed.
1512 Comp_Expr := First (Expressions (Expr));
1513 while Present (Comp_Expr) loop
1514 New_Expr := Relocate_Node (Comp_Expr);
1515 Set_Original_Node (New_Expr, Comp_Expr);
1516 Append
1517 (Make_Pragma_Argument_Association (Sloc (Comp_Expr),
1518 Expression => New_Expr),
1519 Args);
1520 Next (Comp_Expr);
1521 end loop;
1523 Comp_Assn := First (Component_Associations (Expr));
1524 while Present (Comp_Assn) loop
1525 if List_Length (Choices (Comp_Assn)) /= 1
1526 or else
1527 Nkind (First (Choices (Comp_Assn))) /= N_Identifier
1528 then
1529 Error_Msg_Name_1 := Nam;
1530 Error_Msg_NE
1531 ("wrong syntax for aspect `%` for &", Id, E);
1532 goto Continue;
1533 end if;
1535 New_Expr := Relocate_Node (Expression (Comp_Assn));
1536 Set_Original_Node (New_Expr, Expression (Comp_Assn));
1537 Append (Make_Pragma_Argument_Association (
1538 Sloc => Sloc (Comp_Assn),
1539 Chars => Chars (First (Choices (Comp_Assn))),
1540 Expression => New_Expr),
1541 Args);
1542 Next (Comp_Assn);
1543 end loop;
1545 -- Build the contract-case or test-case pragma
1547 Aitem :=
1548 Make_Pragma (Loc,
1549 Pragma_Identifier =>
1550 Make_Identifier (Sloc (Id), Nam),
1551 Pragma_Argument_Associations =>
1552 Args);
1554 Set_From_Aspect_Specification (Aitem, True);
1555 Set_Corresponding_Aspect (Aitem, Aspect);
1556 Set_Is_Delayed_Aspect (Aspect);
1558 -- Insert immediately after the entity declaration
1560 Insert_After (N, Aitem);
1562 goto Continue;
1563 end;
1565 when Aspect_Dimension =>
1566 Analyze_Aspect_Dimension (N, Id, Expr);
1567 goto Continue;
1569 when Aspect_Dimension_System =>
1570 Analyze_Aspect_Dimension_System (N, Id, Expr);
1571 goto Continue;
1573 -- Placeholders for new aspects without corresponding pragmas
1575 when Aspect_External_Name =>
1576 null;
1578 when Aspect_Link_Name =>
1579 null;
1580 end case;
1582 -- If a delay is required, we delay the freeze (not much point in
1583 -- delaying the aspect if we don't delay the freeze!). The pragma
1584 -- or attribute clause if there is one is then attached to the
1585 -- aspect specification which is placed in the rep item list.
1587 if Delay_Required then
1588 if Present (Aitem) then
1589 Set_From_Aspect_Specification (Aitem, True);
1591 if Nkind (Aitem) = N_Pragma then
1592 Set_Corresponding_Aspect (Aitem, Aspect);
1593 end if;
1595 Set_Is_Delayed_Aspect (Aitem);
1596 Set_Aspect_Rep_Item (Aspect, Aitem);
1597 end if;
1599 Ensure_Freeze_Node (E);
1600 Set_Has_Delayed_Aspects (E);
1601 Record_Rep_Item (E, Aspect);
1603 -- If no delay required, insert the pragma/clause in the tree
1605 else
1606 Set_From_Aspect_Specification (Aitem, True);
1608 if Nkind (Aitem) = N_Pragma then
1609 Set_Corresponding_Aspect (Aitem, Aspect);
1610 end if;
1612 -- If this is a compilation unit, we will put the pragma in
1613 -- the Pragmas_After list of the N_Compilation_Unit_Aux node.
1615 if Nkind (Parent (Ins_Node)) = N_Compilation_Unit then
1616 declare
1617 Aux : constant Node_Id :=
1618 Aux_Decls_Node (Parent (Ins_Node));
1620 begin
1621 pragma Assert (Nkind (Aux) = N_Compilation_Unit_Aux);
1623 if No (Pragmas_After (Aux)) then
1624 Set_Pragmas_After (Aux, Empty_List);
1625 end if;
1627 -- For Pre_Post put at start of list, otherwise at end
1629 if A_Id in Pre_Post_Aspects then
1630 Prepend (Aitem, Pragmas_After (Aux));
1631 else
1632 Append (Aitem, Pragmas_After (Aux));
1633 end if;
1634 end;
1636 -- Here if not compilation unit case
1638 else
1639 case A_Id is
1641 -- For Pre/Post cases, insert immediately after the
1642 -- entity declaration, since that is the required pragma
1643 -- placement.
1645 when Pre_Post_Aspects =>
1646 Insert_After (N, Aitem);
1648 -- For Priority aspects, insert into the task or
1649 -- protected definition, which we need to create if it's
1650 -- not there. The same applies to CPU and
1651 -- Dispatching_Domain but only to tasks.
1653 when Aspect_Priority |
1654 Aspect_Interrupt_Priority |
1655 Aspect_Dispatching_Domain |
1656 Aspect_CPU =>
1657 declare
1658 T : Node_Id; -- the type declaration
1659 L : List_Id; -- list of decls of task/protected
1661 begin
1662 if Nkind (N) = N_Object_Declaration then
1663 T := Parent (Etype (Defining_Identifier (N)));
1664 else
1665 T := N;
1666 end if;
1668 if Nkind (T) = N_Protected_Type_Declaration
1669 and then A_Id /= Aspect_Dispatching_Domain
1670 and then A_Id /= Aspect_CPU
1671 then
1672 pragma Assert
1673 (Present (Protected_Definition (T)));
1675 L := Visible_Declarations
1676 (Protected_Definition (T));
1678 elsif Nkind (T) = N_Task_Type_Declaration then
1679 if No (Task_Definition (T)) then
1680 Set_Task_Definition
1682 Make_Task_Definition
1683 (Sloc (T),
1684 Visible_Declarations => New_List,
1685 End_Label => Empty));
1686 end if;
1688 L := Visible_Declarations (Task_Definition (T));
1690 else
1691 raise Program_Error;
1692 end if;
1694 Prepend (Aitem, To => L);
1696 -- Analyze rewritten pragma. Otherwise, its
1697 -- analysis is done too late, after the task or
1698 -- protected object has been created.
1700 Analyze (Aitem);
1701 end;
1703 -- For all other cases, insert in sequence
1705 when others =>
1706 Insert_After (Ins_Node, Aitem);
1707 Ins_Node := Aitem;
1708 end case;
1709 end if;
1710 end if;
1711 end;
1713 <<Continue>>
1714 Next (Aspect);
1715 end loop Aspect_Loop;
1716 end Analyze_Aspect_Specifications;
1718 -----------------------
1719 -- Analyze_At_Clause --
1720 -----------------------
1722 -- An at clause is replaced by the corresponding Address attribute
1723 -- definition clause that is the preferred approach in Ada 95.
1725 procedure Analyze_At_Clause (N : Node_Id) is
1726 CS : constant Boolean := Comes_From_Source (N);
1728 begin
1729 -- This is an obsolescent feature
1731 Check_Restriction (No_Obsolescent_Features, N);
1733 if Warn_On_Obsolescent_Feature then
1734 Error_Msg_N
1735 ("at clause is an obsolescent feature (RM J.7(2))?", N);
1736 Error_Msg_N
1737 ("\use address attribute definition clause instead?", N);
1738 end if;
1740 -- Rewrite as address clause
1742 Rewrite (N,
1743 Make_Attribute_Definition_Clause (Sloc (N),
1744 Name => Identifier (N),
1745 Chars => Name_Address,
1746 Expression => Expression (N)));
1748 -- We preserve Comes_From_Source, since logically the clause still
1749 -- comes from the source program even though it is changed in form.
1751 Set_Comes_From_Source (N, CS);
1753 -- Analyze rewritten clause
1755 Analyze_Attribute_Definition_Clause (N);
1756 end Analyze_At_Clause;
1758 -----------------------------------------
1759 -- Analyze_Attribute_Definition_Clause --
1760 -----------------------------------------
1762 procedure Analyze_Attribute_Definition_Clause (N : Node_Id) is
1763 Loc : constant Source_Ptr := Sloc (N);
1764 Nam : constant Node_Id := Name (N);
1765 Attr : constant Name_Id := Chars (N);
1766 Expr : constant Node_Id := Expression (N);
1767 Id : constant Attribute_Id := Get_Attribute_Id (Attr);
1769 Ent : Entity_Id;
1770 -- The entity of Nam after it is analyzed. In the case of an incomplete
1771 -- type, this is the underlying type.
1773 U_Ent : Entity_Id;
1774 -- The underlying entity to which the attribute applies. Generally this
1775 -- is the Underlying_Type of Ent, except in the case where the clause
1776 -- applies to full view of incomplete type or private type in which case
1777 -- U_Ent is just a copy of Ent.
1779 FOnly : Boolean := False;
1780 -- Reset to True for subtype specific attribute (Alignment, Size)
1781 -- and for stream attributes, i.e. those cases where in the call
1782 -- to Rep_Item_Too_Late, FOnly is set True so that only the freezing
1783 -- rules are checked. Note that the case of stream attributes is not
1784 -- clear from the RM, but see AI95-00137. Also, the RM seems to
1785 -- disallow Storage_Size for derived task types, but that is also
1786 -- clearly unintentional.
1788 procedure Analyze_Stream_TSS_Definition (TSS_Nam : TSS_Name_Type);
1789 -- Common processing for 'Read, 'Write, 'Input and 'Output attribute
1790 -- definition clauses.
1792 function Duplicate_Clause return Boolean;
1793 -- This routine checks if the aspect for U_Ent being given by attribute
1794 -- definition clause N is for an aspect that has already been specified,
1795 -- and if so gives an error message. If there is a duplicate, True is
1796 -- returned, otherwise if there is no error, False is returned.
1798 procedure Check_Indexing_Functions;
1799 -- Check that the function in Constant_Indexing or Variable_Indexing
1800 -- attribute has the proper type structure. If the name is overloaded,
1801 -- check that all interpretations are legal.
1803 procedure Check_Iterator_Functions;
1804 -- Check that there is a single function in Default_Iterator attribute
1805 -- has the proper type structure.
1807 function Check_Primitive_Function (Subp : Entity_Id) return Boolean;
1808 -- Common legality check for the previous two
1810 -----------------------------------
1811 -- Analyze_Stream_TSS_Definition --
1812 -----------------------------------
1814 procedure Analyze_Stream_TSS_Definition (TSS_Nam : TSS_Name_Type) is
1815 Subp : Entity_Id := Empty;
1816 I : Interp_Index;
1817 It : Interp;
1818 Pnam : Entity_Id;
1820 Is_Read : constant Boolean := (TSS_Nam = TSS_Stream_Read);
1821 -- True for Read attribute, false for other attributes
1823 function Has_Good_Profile (Subp : Entity_Id) return Boolean;
1824 -- Return true if the entity is a subprogram with an appropriate
1825 -- profile for the attribute being defined.
1827 ----------------------
1828 -- Has_Good_Profile --
1829 ----------------------
1831 function Has_Good_Profile (Subp : Entity_Id) return Boolean is
1832 F : Entity_Id;
1833 Is_Function : constant Boolean := (TSS_Nam = TSS_Stream_Input);
1834 Expected_Ekind : constant array (Boolean) of Entity_Kind :=
1835 (False => E_Procedure, True => E_Function);
1836 Typ : Entity_Id;
1838 begin
1839 if Ekind (Subp) /= Expected_Ekind (Is_Function) then
1840 return False;
1841 end if;
1843 F := First_Formal (Subp);
1845 if No (F)
1846 or else Ekind (Etype (F)) /= E_Anonymous_Access_Type
1847 or else Designated_Type (Etype (F)) /=
1848 Class_Wide_Type (RTE (RE_Root_Stream_Type))
1849 then
1850 return False;
1851 end if;
1853 if not Is_Function then
1854 Next_Formal (F);
1856 declare
1857 Expected_Mode : constant array (Boolean) of Entity_Kind :=
1858 (False => E_In_Parameter,
1859 True => E_Out_Parameter);
1860 begin
1861 if Parameter_Mode (F) /= Expected_Mode (Is_Read) then
1862 return False;
1863 end if;
1864 end;
1866 Typ := Etype (F);
1868 else
1869 Typ := Etype (Subp);
1870 end if;
1872 return Base_Type (Typ) = Base_Type (Ent)
1873 and then No (Next_Formal (F));
1874 end Has_Good_Profile;
1876 -- Start of processing for Analyze_Stream_TSS_Definition
1878 begin
1879 FOnly := True;
1881 if not Is_Type (U_Ent) then
1882 Error_Msg_N ("local name must be a subtype", Nam);
1883 return;
1884 end if;
1886 Pnam := TSS (Base_Type (U_Ent), TSS_Nam);
1888 -- If Pnam is present, it can be either inherited from an ancestor
1889 -- type (in which case it is legal to redefine it for this type), or
1890 -- be a previous definition of the attribute for the same type (in
1891 -- which case it is illegal).
1893 -- In the first case, it will have been analyzed already, and we
1894 -- can check that its profile does not match the expected profile
1895 -- for a stream attribute of U_Ent. In the second case, either Pnam
1896 -- has been analyzed (and has the expected profile), or it has not
1897 -- been analyzed yet (case of a type that has not been frozen yet
1898 -- and for which the stream attribute has been set using Set_TSS).
1900 if Present (Pnam)
1901 and then (No (First_Entity (Pnam)) or else Has_Good_Profile (Pnam))
1902 then
1903 Error_Msg_Sloc := Sloc (Pnam);
1904 Error_Msg_Name_1 := Attr;
1905 Error_Msg_N ("% attribute already defined #", Nam);
1906 return;
1907 end if;
1909 Analyze (Expr);
1911 if Is_Entity_Name (Expr) then
1912 if not Is_Overloaded (Expr) then
1913 if Has_Good_Profile (Entity (Expr)) then
1914 Subp := Entity (Expr);
1915 end if;
1917 else
1918 Get_First_Interp (Expr, I, It);
1919 while Present (It.Nam) loop
1920 if Has_Good_Profile (It.Nam) then
1921 Subp := It.Nam;
1922 exit;
1923 end if;
1925 Get_Next_Interp (I, It);
1926 end loop;
1927 end if;
1928 end if;
1930 if Present (Subp) then
1931 if Is_Abstract_Subprogram (Subp) then
1932 Error_Msg_N ("stream subprogram must not be abstract", Expr);
1933 return;
1934 end if;
1936 Set_Entity (Expr, Subp);
1937 Set_Etype (Expr, Etype (Subp));
1939 New_Stream_Subprogram (N, U_Ent, Subp, TSS_Nam);
1941 else
1942 Error_Msg_Name_1 := Attr;
1943 Error_Msg_N ("incorrect expression for% attribute", Expr);
1944 end if;
1945 end Analyze_Stream_TSS_Definition;
1947 ------------------------------
1948 -- Check_Indexing_Functions --
1949 ------------------------------
1951 procedure Check_Indexing_Functions is
1953 procedure Check_One_Function (Subp : Entity_Id);
1954 -- Check one possible interpretation
1956 ------------------------
1957 -- Check_One_Function --
1958 ------------------------
1960 procedure Check_One_Function (Subp : Entity_Id) is
1961 Default_Element : constant Node_Id :=
1962 Find_Aspect
1963 (Etype (First_Formal (Subp)),
1964 Aspect_Iterator_Element);
1966 begin
1967 if not Check_Primitive_Function (Subp) then
1968 Error_Msg_NE
1969 ("aspect Indexing requires a function that applies to type&",
1970 Subp, Ent);
1971 end if;
1973 -- An indexing function must return either the default element of
1974 -- the container, or a reference type.
1976 if Present (Default_Element) then
1977 Analyze (Default_Element);
1978 if Is_Entity_Name (Default_Element)
1979 and then Covers (Entity (Default_Element), Etype (Subp))
1980 then
1981 return;
1982 end if;
1983 end if;
1985 -- Otherwise the return type must be a reference type.
1987 if not Has_Implicit_Dereference (Etype (Subp)) then
1988 Error_Msg_N
1989 ("function for indexing must return a reference type", Subp);
1990 end if;
1991 end Check_One_Function;
1993 -- Start of processing for Check_Indexing_Functions
1995 begin
1996 if In_Instance then
1997 return;
1998 end if;
2000 Analyze (Expr);
2002 if not Is_Overloaded (Expr) then
2003 Check_One_Function (Entity (Expr));
2005 else
2006 declare
2007 I : Interp_Index;
2008 It : Interp;
2010 begin
2011 Get_First_Interp (Expr, I, It);
2012 while Present (It.Nam) loop
2014 -- Note that analysis will have added the interpretation
2015 -- that corresponds to the dereference. We only check the
2016 -- subprogram itself.
2018 if Is_Overloadable (It.Nam) then
2019 Check_One_Function (It.Nam);
2020 end if;
2022 Get_Next_Interp (I, It);
2023 end loop;
2024 end;
2025 end if;
2026 end Check_Indexing_Functions;
2028 ------------------------------
2029 -- Check_Iterator_Functions --
2030 ------------------------------
2032 procedure Check_Iterator_Functions is
2033 Default : Entity_Id;
2035 function Valid_Default_Iterator (Subp : Entity_Id) return Boolean;
2036 -- Check one possible interpretation for validity
2038 ----------------------------
2039 -- Valid_Default_Iterator --
2040 ----------------------------
2042 function Valid_Default_Iterator (Subp : Entity_Id) return Boolean is
2043 Formal : Entity_Id;
2045 begin
2046 if not Check_Primitive_Function (Subp) then
2047 return False;
2048 else
2049 Formal := First_Formal (Subp);
2050 end if;
2052 -- False if any subsequent formal has no default expression
2054 Formal := Next_Formal (Formal);
2055 while Present (Formal) loop
2056 if No (Expression (Parent (Formal))) then
2057 return False;
2058 end if;
2060 Next_Formal (Formal);
2061 end loop;
2063 -- True if all subsequent formals have default expressions
2065 return True;
2066 end Valid_Default_Iterator;
2068 -- Start of processing for Check_Iterator_Functions
2070 begin
2071 Analyze (Expr);
2073 if not Is_Entity_Name (Expr) then
2074 Error_Msg_N ("aspect Iterator must be a function name", Expr);
2075 end if;
2077 if not Is_Overloaded (Expr) then
2078 if not Check_Primitive_Function (Entity (Expr)) then
2079 Error_Msg_NE
2080 ("aspect Indexing requires a function that applies to type&",
2081 Entity (Expr), Ent);
2082 end if;
2084 if not Valid_Default_Iterator (Entity (Expr)) then
2085 Error_Msg_N ("improper function for default iterator", Expr);
2086 end if;
2088 else
2089 Default := Empty;
2090 declare
2091 I : Interp_Index;
2092 It : Interp;
2094 begin
2095 Get_First_Interp (Expr, I, It);
2096 while Present (It.Nam) loop
2097 if not Check_Primitive_Function (It.Nam)
2098 or else not Valid_Default_Iterator (It.Nam)
2099 then
2100 Remove_Interp (I);
2102 elsif Present (Default) then
2103 Error_Msg_N ("default iterator must be unique", Expr);
2105 else
2106 Default := It.Nam;
2107 end if;
2109 Get_Next_Interp (I, It);
2110 end loop;
2111 end;
2113 if Present (Default) then
2114 Set_Entity (Expr, Default);
2115 Set_Is_Overloaded (Expr, False);
2116 end if;
2117 end if;
2118 end Check_Iterator_Functions;
2120 -------------------------------
2121 -- Check_Primitive_Function --
2122 -------------------------------
2124 function Check_Primitive_Function (Subp : Entity_Id) return Boolean is
2125 Ctrl : Entity_Id;
2127 begin
2128 if Ekind (Subp) /= E_Function then
2129 return False;
2130 end if;
2132 if No (First_Formal (Subp)) then
2133 return False;
2134 else
2135 Ctrl := Etype (First_Formal (Subp));
2136 end if;
2138 if Ctrl = Ent
2139 or else Ctrl = Class_Wide_Type (Ent)
2140 or else
2141 (Ekind (Ctrl) = E_Anonymous_Access_Type
2142 and then
2143 (Designated_Type (Ctrl) = Ent
2144 or else Designated_Type (Ctrl) = Class_Wide_Type (Ent)))
2145 then
2146 null;
2148 else
2149 return False;
2150 end if;
2152 return True;
2153 end Check_Primitive_Function;
2155 ----------------------
2156 -- Duplicate_Clause --
2157 ----------------------
2159 function Duplicate_Clause return Boolean is
2160 A : Node_Id;
2162 begin
2163 -- Nothing to do if this attribute definition clause comes from
2164 -- an aspect specification, since we could not be duplicating an
2165 -- explicit clause, and we dealt with the case of duplicated aspects
2166 -- in Analyze_Aspect_Specifications.
2168 if From_Aspect_Specification (N) then
2169 return False;
2170 end if;
2172 -- Otherwise current clause may duplicate previous clause or a
2173 -- previously given aspect specification for the same aspect.
2175 A := Get_Rep_Item_For_Entity (U_Ent, Chars (N));
2177 if Present (A) then
2178 if Entity (A) = U_Ent then
2179 Error_Msg_Name_1 := Chars (N);
2180 Error_Msg_Sloc := Sloc (A);
2181 Error_Msg_NE ("aspect% for & previously given#", N, U_Ent);
2182 return True;
2183 end if;
2184 end if;
2186 return False;
2187 end Duplicate_Clause;
2189 -- Start of processing for Analyze_Attribute_Definition_Clause
2191 begin
2192 -- The following code is a defense against recursion. Not clear that
2193 -- this can happen legitimately, but perhaps some error situations
2194 -- can cause it, and we did see this recursion during testing.
2196 if Analyzed (N) then
2197 return;
2198 else
2199 Set_Analyzed (N, True);
2200 end if;
2202 -- Ignore some selected attributes in CodePeer mode since they are not
2203 -- relevant in this context.
2205 if CodePeer_Mode then
2206 case Id is
2208 -- Ignore Component_Size in CodePeer mode, to avoid changing the
2209 -- internal representation of types by implicitly packing them.
2211 when Attribute_Component_Size =>
2212 Rewrite (N, Make_Null_Statement (Sloc (N)));
2213 return;
2215 when others =>
2216 null;
2217 end case;
2218 end if;
2220 -- Process Ignore_Rep_Clauses option
2222 if Ignore_Rep_Clauses then
2223 case Id is
2225 -- The following should be ignored. They do not affect legality
2226 -- and may be target dependent. The basic idea of -gnatI is to
2227 -- ignore any rep clauses that may be target dependent but do not
2228 -- affect legality (except possibly to be rejected because they
2229 -- are incompatible with the compilation target).
2231 when Attribute_Alignment |
2232 Attribute_Bit_Order |
2233 Attribute_Component_Size |
2234 Attribute_Machine_Radix |
2235 Attribute_Object_Size |
2236 Attribute_Size |
2237 Attribute_Stream_Size |
2238 Attribute_Value_Size =>
2239 Rewrite (N, Make_Null_Statement (Sloc (N)));
2240 return;
2242 -- Perhaps 'Small should not be ignored by Ignore_Rep_Clauses ???
2244 when Attribute_Small =>
2245 if Ignore_Rep_Clauses then
2246 Rewrite (N, Make_Null_Statement (Sloc (N)));
2247 return;
2248 end if;
2250 -- The following should not be ignored, because in the first place
2251 -- they are reasonably portable, and should not cause problems in
2252 -- compiling code from another target, and also they do affect
2253 -- legality, e.g. failing to provide a stream attribute for a
2254 -- type may make a program illegal.
2256 when Attribute_External_Tag |
2257 Attribute_Input |
2258 Attribute_Output |
2259 Attribute_Read |
2260 Attribute_Simple_Storage_Pool |
2261 Attribute_Storage_Pool |
2262 Attribute_Storage_Size |
2263 Attribute_Write =>
2264 null;
2266 -- Other cases are errors ("attribute& cannot be set with
2267 -- definition clause"), which will be caught below.
2269 when others =>
2270 null;
2271 end case;
2272 end if;
2274 Analyze (Nam);
2275 Ent := Entity (Nam);
2277 if Rep_Item_Too_Early (Ent, N) then
2278 return;
2279 end if;
2281 -- Rep clause applies to full view of incomplete type or private type if
2282 -- we have one (if not, this is a premature use of the type). However,
2283 -- certain semantic checks need to be done on the specified entity (i.e.
2284 -- the private view), so we save it in Ent.
2286 if Is_Private_Type (Ent)
2287 and then Is_Derived_Type (Ent)
2288 and then not Is_Tagged_Type (Ent)
2289 and then No (Full_View (Ent))
2290 then
2291 -- If this is a private type whose completion is a derivation from
2292 -- another private type, there is no full view, and the attribute
2293 -- belongs to the type itself, not its underlying parent.
2295 U_Ent := Ent;
2297 elsif Ekind (Ent) = E_Incomplete_Type then
2299 -- The attribute applies to the full view, set the entity of the
2300 -- attribute definition accordingly.
2302 Ent := Underlying_Type (Ent);
2303 U_Ent := Ent;
2304 Set_Entity (Nam, Ent);
2306 else
2307 U_Ent := Underlying_Type (Ent);
2308 end if;
2310 -- Avoid cascaded error
2312 if Etype (Nam) = Any_Type then
2313 return;
2315 -- Must be declared in current scope
2317 elsif Scope (Ent) /= Current_Scope then
2318 Error_Msg_N ("entity must be declared in this scope", Nam);
2319 return;
2321 -- Must not be a source renaming (we do have some cases where the
2322 -- expander generates a renaming, and those cases are OK, in such
2323 -- cases any attribute applies to the renamed object as well).
2325 elsif Is_Object (Ent)
2326 and then Present (Renamed_Object (Ent))
2327 then
2328 -- Case of renamed object from source, this is an error
2330 if Comes_From_Source (Renamed_Object (Ent)) then
2331 Get_Name_String (Chars (N));
2332 Error_Msg_Strlen := Name_Len;
2333 Error_Msg_String (1 .. Name_Len) := Name_Buffer (1 .. Name_Len);
2334 Error_Msg_N
2335 ("~ clause not allowed for a renaming declaration "
2336 & "(RM 13.1(6))", Nam);
2337 return;
2339 -- For the case of a compiler generated renaming, the attribute
2340 -- definition clause applies to the renamed object created by the
2341 -- expander. The easiest general way to handle this is to create a
2342 -- copy of the attribute definition clause for this object.
2344 else
2345 Insert_Action (N,
2346 Make_Attribute_Definition_Clause (Loc,
2347 Name =>
2348 New_Occurrence_Of (Entity (Renamed_Object (Ent)), Loc),
2349 Chars => Chars (N),
2350 Expression => Duplicate_Subexpr (Expression (N))));
2351 end if;
2353 -- If no underlying entity, use entity itself, applies to some
2354 -- previously detected error cases ???
2356 elsif No (U_Ent) then
2357 U_Ent := Ent;
2359 -- Cannot specify for a subtype (exception Object/Value_Size)
2361 elsif Is_Type (U_Ent)
2362 and then not Is_First_Subtype (U_Ent)
2363 and then Id /= Attribute_Object_Size
2364 and then Id /= Attribute_Value_Size
2365 and then not From_At_Mod (N)
2366 then
2367 Error_Msg_N ("cannot specify attribute for subtype", Nam);
2368 return;
2369 end if;
2371 Set_Entity (N, U_Ent);
2373 -- Switch on particular attribute
2375 case Id is
2377 -------------
2378 -- Address --
2379 -------------
2381 -- Address attribute definition clause
2383 when Attribute_Address => Address : begin
2385 -- A little error check, catch for X'Address use X'Address;
2387 if Nkind (Nam) = N_Identifier
2388 and then Nkind (Expr) = N_Attribute_Reference
2389 and then Attribute_Name (Expr) = Name_Address
2390 and then Nkind (Prefix (Expr)) = N_Identifier
2391 and then Chars (Nam) = Chars (Prefix (Expr))
2392 then
2393 Error_Msg_NE
2394 ("address for & is self-referencing", Prefix (Expr), Ent);
2395 return;
2396 end if;
2398 -- Not that special case, carry on with analysis of expression
2400 Analyze_And_Resolve (Expr, RTE (RE_Address));
2402 -- Even when ignoring rep clauses we need to indicate that the
2403 -- entity has an address clause and thus it is legal to declare
2404 -- it imported.
2406 if Ignore_Rep_Clauses then
2407 if Ekind_In (U_Ent, E_Variable, E_Constant) then
2408 Record_Rep_Item (U_Ent, N);
2409 end if;
2411 return;
2412 end if;
2414 if Duplicate_Clause then
2415 null;
2417 -- Case of address clause for subprogram
2419 elsif Is_Subprogram (U_Ent) then
2420 if Has_Homonym (U_Ent) then
2421 Error_Msg_N
2422 ("address clause cannot be given " &
2423 "for overloaded subprogram",
2424 Nam);
2425 return;
2426 end if;
2428 -- For subprograms, all address clauses are permitted, and we
2429 -- mark the subprogram as having a deferred freeze so that Gigi
2430 -- will not elaborate it too soon.
2432 -- Above needs more comments, what is too soon about???
2434 Set_Has_Delayed_Freeze (U_Ent);
2436 -- Case of address clause for entry
2438 elsif Ekind (U_Ent) = E_Entry then
2439 if Nkind (Parent (N)) = N_Task_Body then
2440 Error_Msg_N
2441 ("entry address must be specified in task spec", Nam);
2442 return;
2443 end if;
2445 -- For entries, we require a constant address
2447 Check_Constant_Address_Clause (Expr, U_Ent);
2449 -- Special checks for task types
2451 if Is_Task_Type (Scope (U_Ent))
2452 and then Comes_From_Source (Scope (U_Ent))
2453 then
2454 Error_Msg_N
2455 ("?entry address declared for entry in task type", N);
2456 Error_Msg_N
2457 ("\?only one task can be declared of this type", N);
2458 end if;
2460 -- Entry address clauses are obsolescent
2462 Check_Restriction (No_Obsolescent_Features, N);
2464 if Warn_On_Obsolescent_Feature then
2465 Error_Msg_N
2466 ("attaching interrupt to task entry is an " &
2467 "obsolescent feature (RM J.7.1)?", N);
2468 Error_Msg_N
2469 ("\use interrupt procedure instead?", N);
2470 end if;
2472 -- Case of an address clause for a controlled object which we
2473 -- consider to be erroneous.
2475 elsif Is_Controlled (Etype (U_Ent))
2476 or else Has_Controlled_Component (Etype (U_Ent))
2477 then
2478 Error_Msg_NE
2479 ("?controlled object& must not be overlaid", Nam, U_Ent);
2480 Error_Msg_N
2481 ("\?Program_Error will be raised at run time", Nam);
2482 Insert_Action (Declaration_Node (U_Ent),
2483 Make_Raise_Program_Error (Loc,
2484 Reason => PE_Overlaid_Controlled_Object));
2485 return;
2487 -- Case of address clause for a (non-controlled) object
2489 elsif
2490 Ekind (U_Ent) = E_Variable
2491 or else
2492 Ekind (U_Ent) = E_Constant
2493 then
2494 declare
2495 Expr : constant Node_Id := Expression (N);
2496 O_Ent : Entity_Id;
2497 Off : Boolean;
2499 begin
2500 -- Exported variables cannot have an address clause, because
2501 -- this cancels the effect of the pragma Export.
2503 if Is_Exported (U_Ent) then
2504 Error_Msg_N
2505 ("cannot export object with address clause", Nam);
2506 return;
2507 end if;
2509 Find_Overlaid_Entity (N, O_Ent, Off);
2511 -- Overlaying controlled objects is erroneous
2513 if Present (O_Ent)
2514 and then (Has_Controlled_Component (Etype (O_Ent))
2515 or else Is_Controlled (Etype (O_Ent)))
2516 then
2517 Error_Msg_N
2518 ("?cannot overlay with controlled object", Expr);
2519 Error_Msg_N
2520 ("\?Program_Error will be raised at run time", Expr);
2521 Insert_Action (Declaration_Node (U_Ent),
2522 Make_Raise_Program_Error (Loc,
2523 Reason => PE_Overlaid_Controlled_Object));
2524 return;
2526 elsif Present (O_Ent)
2527 and then Ekind (U_Ent) = E_Constant
2528 and then not Is_Constant_Object (O_Ent)
2529 then
2530 Error_Msg_N ("constant overlays a variable?", Expr);
2532 -- Imported variables can have an address clause, but then
2533 -- the import is pretty meaningless except to suppress
2534 -- initializations, so we do not need such variables to
2535 -- be statically allocated (and in fact it causes trouble
2536 -- if the address clause is a local value).
2538 elsif Is_Imported (U_Ent) then
2539 Set_Is_Statically_Allocated (U_Ent, False);
2540 end if;
2542 -- We mark a possible modification of a variable with an
2543 -- address clause, since it is likely aliasing is occurring.
2545 Note_Possible_Modification (Nam, Sure => False);
2547 -- Here we are checking for explicit overlap of one variable
2548 -- by another, and if we find this then mark the overlapped
2549 -- variable as also being volatile to prevent unwanted
2550 -- optimizations. This is a significant pessimization so
2551 -- avoid it when there is an offset, i.e. when the object
2552 -- is composite; they cannot be optimized easily anyway.
2554 if Present (O_Ent)
2555 and then Is_Object (O_Ent)
2556 and then not Off
2557 then
2558 Set_Treat_As_Volatile (O_Ent);
2559 end if;
2561 -- Legality checks on the address clause for initialized
2562 -- objects is deferred until the freeze point, because
2563 -- a subsequent pragma might indicate that the object is
2564 -- imported and thus not initialized.
2566 Set_Has_Delayed_Freeze (U_Ent);
2568 -- If an initialization call has been generated for this
2569 -- object, it needs to be deferred to after the freeze node
2570 -- we have just now added, otherwise GIGI will see a
2571 -- reference to the variable (as actual to the IP call)
2572 -- before its definition.
2574 declare
2575 Init_Call : constant Node_Id := Find_Init_Call (U_Ent, N);
2576 begin
2577 if Present (Init_Call) then
2578 Remove (Init_Call);
2579 Append_Freeze_Action (U_Ent, Init_Call);
2580 end if;
2581 end;
2583 if Is_Exported (U_Ent) then
2584 Error_Msg_N
2585 ("& cannot be exported if an address clause is given",
2586 Nam);
2587 Error_Msg_N
2588 ("\define and export a variable " &
2589 "that holds its address instead",
2590 Nam);
2591 end if;
2593 -- Entity has delayed freeze, so we will generate an
2594 -- alignment check at the freeze point unless suppressed.
2596 if not Range_Checks_Suppressed (U_Ent)
2597 and then not Alignment_Checks_Suppressed (U_Ent)
2598 then
2599 Set_Check_Address_Alignment (N);
2600 end if;
2602 -- Kill the size check code, since we are not allocating
2603 -- the variable, it is somewhere else.
2605 Kill_Size_Check_Code (U_Ent);
2607 -- If the address clause is of the form:
2609 -- for Y'Address use X'Address
2611 -- or
2613 -- Const : constant Address := X'Address;
2614 -- ...
2615 -- for Y'Address use Const;
2617 -- then we make an entry in the table for checking the size
2618 -- and alignment of the overlaying variable. We defer this
2619 -- check till after code generation to take full advantage
2620 -- of the annotation done by the back end. This entry is
2621 -- only made if the address clause comes from source.
2623 -- If the entity has a generic type, the check will be
2624 -- performed in the instance if the actual type justifies
2625 -- it, and we do not insert the clause in the table to
2626 -- prevent spurious warnings.
2628 if Address_Clause_Overlay_Warnings
2629 and then Comes_From_Source (N)
2630 and then Present (O_Ent)
2631 and then Is_Object (O_Ent)
2632 then
2633 if not Is_Generic_Type (Etype (U_Ent)) then
2634 Address_Clause_Checks.Append ((N, U_Ent, O_Ent, Off));
2635 end if;
2637 -- If variable overlays a constant view, and we are
2638 -- warning on overlays, then mark the variable as
2639 -- overlaying a constant (we will give warnings later
2640 -- if this variable is assigned).
2642 if Is_Constant_Object (O_Ent)
2643 and then Ekind (U_Ent) = E_Variable
2644 then
2645 Set_Overlays_Constant (U_Ent);
2646 end if;
2647 end if;
2648 end;
2650 -- Not a valid entity for an address clause
2652 else
2653 Error_Msg_N ("address cannot be given for &", Nam);
2654 end if;
2655 end Address;
2657 ---------------
2658 -- Alignment --
2659 ---------------
2661 -- Alignment attribute definition clause
2663 when Attribute_Alignment => Alignment : declare
2664 Align : constant Uint := Get_Alignment_Value (Expr);
2665 Max_Align : constant Uint := UI_From_Int (Maximum_Alignment);
2667 begin
2668 FOnly := True;
2670 if not Is_Type (U_Ent)
2671 and then Ekind (U_Ent) /= E_Variable
2672 and then Ekind (U_Ent) /= E_Constant
2673 then
2674 Error_Msg_N ("alignment cannot be given for &", Nam);
2676 elsif Duplicate_Clause then
2677 null;
2679 elsif Align /= No_Uint then
2680 Set_Has_Alignment_Clause (U_Ent);
2682 -- Tagged type case, check for attempt to set alignment to a
2683 -- value greater than Max_Align, and reset if so.
2685 if Is_Tagged_Type (U_Ent) and then Align > Max_Align then
2686 Error_Msg_N
2687 ("?alignment for & set to Maximum_Aligment", Nam);
2688 Set_Alignment (U_Ent, Max_Align);
2690 -- All other cases
2692 else
2693 Set_Alignment (U_Ent, Align);
2694 end if;
2696 -- For an array type, U_Ent is the first subtype. In that case,
2697 -- also set the alignment of the anonymous base type so that
2698 -- other subtypes (such as the itypes for aggregates of the
2699 -- type) also receive the expected alignment.
2701 if Is_Array_Type (U_Ent) then
2702 Set_Alignment (Base_Type (U_Ent), Align);
2703 end if;
2704 end if;
2705 end Alignment;
2707 ---------------
2708 -- Bit_Order --
2709 ---------------
2711 -- Bit_Order attribute definition clause
2713 when Attribute_Bit_Order => Bit_Order : declare
2714 begin
2715 if not Is_Record_Type (U_Ent) then
2716 Error_Msg_N
2717 ("Bit_Order can only be defined for record type", Nam);
2719 elsif Duplicate_Clause then
2720 null;
2722 else
2723 Analyze_And_Resolve (Expr, RTE (RE_Bit_Order));
2725 if Etype (Expr) = Any_Type then
2726 return;
2728 elsif not Is_Static_Expression (Expr) then
2729 Flag_Non_Static_Expr
2730 ("Bit_Order requires static expression!", Expr);
2732 else
2733 if (Expr_Value (Expr) = 0) /= Bytes_Big_Endian then
2734 Set_Reverse_Bit_Order (U_Ent, True);
2735 end if;
2736 end if;
2737 end if;
2738 end Bit_Order;
2740 --------------------
2741 -- Component_Size --
2742 --------------------
2744 -- Component_Size attribute definition clause
2746 when Attribute_Component_Size => Component_Size_Case : declare
2747 Csize : constant Uint := Static_Integer (Expr);
2748 Ctyp : Entity_Id;
2749 Btype : Entity_Id;
2750 Biased : Boolean;
2751 New_Ctyp : Entity_Id;
2752 Decl : Node_Id;
2754 begin
2755 if not Is_Array_Type (U_Ent) then
2756 Error_Msg_N ("component size requires array type", Nam);
2757 return;
2758 end if;
2760 Btype := Base_Type (U_Ent);
2761 Ctyp := Component_Type (Btype);
2763 if Duplicate_Clause then
2764 null;
2766 elsif Rep_Item_Too_Early (Btype, N) then
2767 null;
2769 elsif Csize /= No_Uint then
2770 Check_Size (Expr, Ctyp, Csize, Biased);
2772 -- For the biased case, build a declaration for a subtype that
2773 -- will be used to represent the biased subtype that reflects
2774 -- the biased representation of components. We need the subtype
2775 -- to get proper conversions on referencing elements of the
2776 -- array. Note: component size clauses are ignored in VM mode.
2778 if VM_Target = No_VM then
2779 if Biased then
2780 New_Ctyp :=
2781 Make_Defining_Identifier (Loc,
2782 Chars =>
2783 New_External_Name (Chars (U_Ent), 'C', 0, 'T'));
2785 Decl :=
2786 Make_Subtype_Declaration (Loc,
2787 Defining_Identifier => New_Ctyp,
2788 Subtype_Indication =>
2789 New_Occurrence_Of (Component_Type (Btype), Loc));
2791 Set_Parent (Decl, N);
2792 Analyze (Decl, Suppress => All_Checks);
2794 Set_Has_Delayed_Freeze (New_Ctyp, False);
2795 Set_Esize (New_Ctyp, Csize);
2796 Set_RM_Size (New_Ctyp, Csize);
2797 Init_Alignment (New_Ctyp);
2798 Set_Is_Itype (New_Ctyp, True);
2799 Set_Associated_Node_For_Itype (New_Ctyp, U_Ent);
2801 Set_Component_Type (Btype, New_Ctyp);
2802 Set_Biased (New_Ctyp, N, "component size clause");
2803 end if;
2805 Set_Component_Size (Btype, Csize);
2807 -- For VM case, we ignore component size clauses
2809 else
2810 -- Give a warning unless we are in GNAT mode, in which case
2811 -- the warning is suppressed since it is not useful.
2813 if not GNAT_Mode then
2814 Error_Msg_N
2815 ("?component size ignored in this configuration", N);
2816 end if;
2817 end if;
2819 -- Deal with warning on overridden size
2821 if Warn_On_Overridden_Size
2822 and then Has_Size_Clause (Ctyp)
2823 and then RM_Size (Ctyp) /= Csize
2824 then
2825 Error_Msg_NE
2826 ("?component size overrides size clause for&",
2827 N, Ctyp);
2828 end if;
2830 Set_Has_Component_Size_Clause (Btype, True);
2831 Set_Has_Non_Standard_Rep (Btype, True);
2832 end if;
2833 end Component_Size_Case;
2835 -----------------------
2836 -- Constant_Indexing --
2837 -----------------------
2839 when Attribute_Constant_Indexing =>
2840 Check_Indexing_Functions;
2842 ----------------------
2843 -- Default_Iterator --
2844 ----------------------
2846 when Attribute_Default_Iterator => Default_Iterator : declare
2847 Func : Entity_Id;
2849 begin
2850 if not Is_Tagged_Type (U_Ent) then
2851 Error_Msg_N
2852 ("aspect Default_Iterator applies to tagged type", Nam);
2853 end if;
2855 Check_Iterator_Functions;
2857 Analyze (Expr);
2859 if not Is_Entity_Name (Expr)
2860 or else Ekind (Entity (Expr)) /= E_Function
2861 then
2862 Error_Msg_N ("aspect Iterator must be a function", Expr);
2863 else
2864 Func := Entity (Expr);
2865 end if;
2867 if No (First_Formal (Func))
2868 or else Etype (First_Formal (Func)) /= U_Ent
2869 then
2870 Error_Msg_NE
2871 ("Default Iterator must be a primitive of&", Func, U_Ent);
2872 end if;
2873 end Default_Iterator;
2875 ------------------
2876 -- External_Tag --
2877 ------------------
2879 when Attribute_External_Tag => External_Tag :
2880 begin
2881 if not Is_Tagged_Type (U_Ent) then
2882 Error_Msg_N ("should be a tagged type", Nam);
2883 end if;
2885 if Duplicate_Clause then
2886 null;
2888 else
2889 Analyze_And_Resolve (Expr, Standard_String);
2891 if not Is_Static_Expression (Expr) then
2892 Flag_Non_Static_Expr
2893 ("static string required for tag name!", Nam);
2894 end if;
2896 if VM_Target = No_VM then
2897 Set_Has_External_Tag_Rep_Clause (U_Ent);
2898 else
2899 Error_Msg_Name_1 := Attr;
2900 Error_Msg_N
2901 ("% attribute unsupported in this configuration", Nam);
2902 end if;
2904 if not Is_Library_Level_Entity (U_Ent) then
2905 Error_Msg_NE
2906 ("?non-unique external tag supplied for &", N, U_Ent);
2907 Error_Msg_N
2908 ("?\same external tag applies to all subprogram calls", N);
2909 Error_Msg_N
2910 ("?\corresponding internal tag cannot be obtained", N);
2911 end if;
2912 end if;
2913 end External_Tag;
2915 --------------------------
2916 -- Implicit_Dereference --
2917 --------------------------
2919 when Attribute_Implicit_Dereference =>
2921 -- Legality checks already performed at the point of
2922 -- the type declaration, aspect is not delayed.
2924 null;
2926 -----------
2927 -- Input --
2928 -----------
2930 when Attribute_Input =>
2931 Analyze_Stream_TSS_Definition (TSS_Stream_Input);
2932 Set_Has_Specified_Stream_Input (Ent);
2934 ----------------------
2935 -- Iterator_Element --
2936 ----------------------
2938 when Attribute_Iterator_Element =>
2939 Analyze (Expr);
2941 if not Is_Entity_Name (Expr)
2942 or else not Is_Type (Entity (Expr))
2943 then
2944 Error_Msg_N ("aspect Iterator_Element must be a type", Expr);
2945 end if;
2947 -------------------
2948 -- Machine_Radix --
2949 -------------------
2951 -- Machine radix attribute definition clause
2953 when Attribute_Machine_Radix => Machine_Radix : declare
2954 Radix : constant Uint := Static_Integer (Expr);
2956 begin
2957 if not Is_Decimal_Fixed_Point_Type (U_Ent) then
2958 Error_Msg_N ("decimal fixed-point type expected for &", Nam);
2960 elsif Duplicate_Clause then
2961 null;
2963 elsif Radix /= No_Uint then
2964 Set_Has_Machine_Radix_Clause (U_Ent);
2965 Set_Has_Non_Standard_Rep (Base_Type (U_Ent));
2967 if Radix = 2 then
2968 null;
2969 elsif Radix = 10 then
2970 Set_Machine_Radix_10 (U_Ent);
2971 else
2972 Error_Msg_N ("machine radix value must be 2 or 10", Expr);
2973 end if;
2974 end if;
2975 end Machine_Radix;
2977 -----------------
2978 -- Object_Size --
2979 -----------------
2981 -- Object_Size attribute definition clause
2983 when Attribute_Object_Size => Object_Size : declare
2984 Size : constant Uint := Static_Integer (Expr);
2986 Biased : Boolean;
2987 pragma Warnings (Off, Biased);
2989 begin
2990 if not Is_Type (U_Ent) then
2991 Error_Msg_N ("Object_Size cannot be given for &", Nam);
2993 elsif Duplicate_Clause then
2994 null;
2996 else
2997 Check_Size (Expr, U_Ent, Size, Biased);
2999 if Size /= 8
3000 and then
3001 Size /= 16
3002 and then
3003 Size /= 32
3004 and then
3005 UI_Mod (Size, 64) /= 0
3006 then
3007 Error_Msg_N
3008 ("Object_Size must be 8, 16, 32, or multiple of 64",
3009 Expr);
3010 end if;
3012 Set_Esize (U_Ent, Size);
3013 Set_Has_Object_Size_Clause (U_Ent);
3014 Alignment_Check_For_Size_Change (U_Ent, Size);
3015 end if;
3016 end Object_Size;
3018 ------------
3019 -- Output --
3020 ------------
3022 when Attribute_Output =>
3023 Analyze_Stream_TSS_Definition (TSS_Stream_Output);
3024 Set_Has_Specified_Stream_Output (Ent);
3026 ----------
3027 -- Read --
3028 ----------
3030 when Attribute_Read =>
3031 Analyze_Stream_TSS_Definition (TSS_Stream_Read);
3032 Set_Has_Specified_Stream_Read (Ent);
3034 --------------------------
3035 -- Scalar_Storage_Order --
3036 --------------------------
3038 -- Scalar_Storage_Order attribute definition clause
3040 when Attribute_Scalar_Storage_Order => Scalar_Storage_Order : declare
3041 begin
3042 if not Is_Record_Type (U_Ent) then
3043 Error_Msg_N
3044 ("Scalar_Storage_Order can only be defined for record type",
3045 Nam);
3047 elsif Duplicate_Clause then
3048 null;
3050 else
3051 Analyze_And_Resolve (Expr, RTE (RE_Bit_Order));
3053 if Etype (Expr) = Any_Type then
3054 return;
3056 elsif not Is_Static_Expression (Expr) then
3057 Flag_Non_Static_Expr
3058 ("Scalar_Storage_Order requires static expression!", Expr);
3060 else
3061 if (Expr_Value (Expr) = 0) /= Bytes_Big_Endian then
3062 Set_Reverse_Storage_Order (U_Ent, True);
3063 end if;
3064 end if;
3065 end if;
3066 end Scalar_Storage_Order;
3068 ----------
3069 -- Size --
3070 ----------
3072 -- Size attribute definition clause
3074 when Attribute_Size => Size : declare
3075 Size : constant Uint := Static_Integer (Expr);
3076 Etyp : Entity_Id;
3077 Biased : Boolean;
3079 begin
3080 FOnly := True;
3082 if Duplicate_Clause then
3083 null;
3085 elsif not Is_Type (U_Ent)
3086 and then Ekind (U_Ent) /= E_Variable
3087 and then Ekind (U_Ent) /= E_Constant
3088 then
3089 Error_Msg_N ("size cannot be given for &", Nam);
3091 elsif Is_Array_Type (U_Ent)
3092 and then not Is_Constrained (U_Ent)
3093 then
3094 Error_Msg_N
3095 ("size cannot be given for unconstrained array", Nam);
3097 elsif Size /= No_Uint then
3098 if VM_Target /= No_VM and then not GNAT_Mode then
3100 -- Size clause is not handled properly on VM targets.
3101 -- Display a warning unless we are in GNAT mode, in which
3102 -- case this is useless.
3104 Error_Msg_N
3105 ("?size clauses are ignored in this configuration", N);
3106 end if;
3108 if Is_Type (U_Ent) then
3109 Etyp := U_Ent;
3110 else
3111 Etyp := Etype (U_Ent);
3112 end if;
3114 -- Check size, note that Gigi is in charge of checking that the
3115 -- size of an array or record type is OK. Also we do not check
3116 -- the size in the ordinary fixed-point case, since it is too
3117 -- early to do so (there may be subsequent small clause that
3118 -- affects the size). We can check the size if a small clause
3119 -- has already been given.
3121 if not Is_Ordinary_Fixed_Point_Type (U_Ent)
3122 or else Has_Small_Clause (U_Ent)
3123 then
3124 Check_Size (Expr, Etyp, Size, Biased);
3125 Set_Biased (U_Ent, N, "size clause", Biased);
3126 end if;
3128 -- For types set RM_Size and Esize if possible
3130 if Is_Type (U_Ent) then
3131 Set_RM_Size (U_Ent, Size);
3133 -- For elementary types, increase Object_Size to power of 2,
3134 -- but not less than a storage unit in any case (normally
3135 -- this means it will be byte addressable).
3137 -- For all other types, nothing else to do, we leave Esize
3138 -- (object size) unset, the back end will set it from the
3139 -- size and alignment in an appropriate manner.
3141 -- In both cases, we check whether the alignment must be
3142 -- reset in the wake of the size change.
3144 if Is_Elementary_Type (U_Ent) then
3145 if Size <= System_Storage_Unit then
3146 Init_Esize (U_Ent, System_Storage_Unit);
3147 elsif Size <= 16 then
3148 Init_Esize (U_Ent, 16);
3149 elsif Size <= 32 then
3150 Init_Esize (U_Ent, 32);
3151 else
3152 Set_Esize (U_Ent, (Size + 63) / 64 * 64);
3153 end if;
3155 Alignment_Check_For_Size_Change (U_Ent, Esize (U_Ent));
3156 else
3157 Alignment_Check_For_Size_Change (U_Ent, Size);
3158 end if;
3160 -- For objects, set Esize only
3162 else
3163 if Is_Elementary_Type (Etyp) then
3164 if Size /= System_Storage_Unit
3165 and then
3166 Size /= System_Storage_Unit * 2
3167 and then
3168 Size /= System_Storage_Unit * 4
3169 and then
3170 Size /= System_Storage_Unit * 8
3171 then
3172 Error_Msg_Uint_1 := UI_From_Int (System_Storage_Unit);
3173 Error_Msg_Uint_2 := Error_Msg_Uint_1 * 8;
3174 Error_Msg_N
3175 ("size for primitive object must be a power of 2"
3176 & " in the range ^-^", N);
3177 end if;
3178 end if;
3180 Set_Esize (U_Ent, Size);
3181 end if;
3183 Set_Has_Size_Clause (U_Ent);
3184 end if;
3185 end Size;
3187 -----------
3188 -- Small --
3189 -----------
3191 -- Small attribute definition clause
3193 when Attribute_Small => Small : declare
3194 Implicit_Base : constant Entity_Id := Base_Type (U_Ent);
3195 Small : Ureal;
3197 begin
3198 Analyze_And_Resolve (Expr, Any_Real);
3200 if Etype (Expr) = Any_Type then
3201 return;
3203 elsif not Is_Static_Expression (Expr) then
3204 Flag_Non_Static_Expr
3205 ("small requires static expression!", Expr);
3206 return;
3208 else
3209 Small := Expr_Value_R (Expr);
3211 if Small <= Ureal_0 then
3212 Error_Msg_N ("small value must be greater than zero", Expr);
3213 return;
3214 end if;
3216 end if;
3218 if not Is_Ordinary_Fixed_Point_Type (U_Ent) then
3219 Error_Msg_N
3220 ("small requires an ordinary fixed point type", Nam);
3222 elsif Has_Small_Clause (U_Ent) then
3223 Error_Msg_N ("small already given for &", Nam);
3225 elsif Small > Delta_Value (U_Ent) then
3226 Error_Msg_N
3227 ("small value must not be greater than delta value", Nam);
3229 else
3230 Set_Small_Value (U_Ent, Small);
3231 Set_Small_Value (Implicit_Base, Small);
3232 Set_Has_Small_Clause (U_Ent);
3233 Set_Has_Small_Clause (Implicit_Base);
3234 Set_Has_Non_Standard_Rep (Implicit_Base);
3235 end if;
3236 end Small;
3238 ------------------
3239 -- Storage_Pool --
3240 ------------------
3242 -- Storage_Pool attribute definition clause
3244 when Attribute_Storage_Pool | Attribute_Simple_Storage_Pool => declare
3245 Pool : Entity_Id;
3246 T : Entity_Id;
3248 begin
3249 if Ekind (U_Ent) = E_Access_Subprogram_Type then
3250 Error_Msg_N
3251 ("storage pool cannot be given for access-to-subprogram type",
3252 Nam);
3253 return;
3255 elsif not
3256 Ekind_In (U_Ent, E_Access_Type, E_General_Access_Type)
3257 then
3258 Error_Msg_N
3259 ("storage pool can only be given for access types", Nam);
3260 return;
3262 elsif Is_Derived_Type (U_Ent) then
3263 Error_Msg_N
3264 ("storage pool cannot be given for a derived access type",
3265 Nam);
3267 elsif Duplicate_Clause then
3268 return;
3270 elsif Present (Associated_Storage_Pool (U_Ent)) then
3271 Error_Msg_N ("storage pool already given for &", Nam);
3272 return;
3273 end if;
3275 if Id = Attribute_Storage_Pool then
3276 Analyze_And_Resolve
3277 (Expr, Class_Wide_Type (RTE (RE_Root_Storage_Pool)));
3279 -- In the Simple_Storage_Pool case, we allow a variable of any
3280 -- simple storage pool type, so we Resolve without imposing an
3281 -- expected type.
3283 else
3284 Analyze_And_Resolve (Expr);
3286 if not Present (Get_Rep_Pragma
3287 (Etype (Expr), Name_Simple_Storage_Pool_Type))
3288 then
3289 Error_Msg_N
3290 ("expression must be of a simple storage pool type", Expr);
3291 end if;
3292 end if;
3294 if not Denotes_Variable (Expr) then
3295 Error_Msg_N ("storage pool must be a variable", Expr);
3296 return;
3297 end if;
3299 if Nkind (Expr) = N_Type_Conversion then
3300 T := Etype (Expression (Expr));
3301 else
3302 T := Etype (Expr);
3303 end if;
3305 -- The Stack_Bounded_Pool is used internally for implementing
3306 -- access types with a Storage_Size. Since it only work properly
3307 -- when used on one specific type, we need to check that it is not
3308 -- hijacked improperly:
3310 -- type T is access Integer;
3311 -- for T'Storage_Size use n;
3312 -- type Q is access Float;
3313 -- for Q'Storage_Size use T'Storage_Size; -- incorrect
3315 if RTE_Available (RE_Stack_Bounded_Pool)
3316 and then Base_Type (T) = RTE (RE_Stack_Bounded_Pool)
3317 then
3318 Error_Msg_N ("non-shareable internal Pool", Expr);
3319 return;
3320 end if;
3322 -- If the argument is a name that is not an entity name, then
3323 -- we construct a renaming operation to define an entity of
3324 -- type storage pool.
3326 if not Is_Entity_Name (Expr)
3327 and then Is_Object_Reference (Expr)
3328 then
3329 Pool := Make_Temporary (Loc, 'P', Expr);
3331 declare
3332 Rnode : constant Node_Id :=
3333 Make_Object_Renaming_Declaration (Loc,
3334 Defining_Identifier => Pool,
3335 Subtype_Mark =>
3336 New_Occurrence_Of (Etype (Expr), Loc),
3337 Name => Expr);
3339 begin
3340 Insert_Before (N, Rnode);
3341 Analyze (Rnode);
3342 Set_Associated_Storage_Pool (U_Ent, Pool);
3343 end;
3345 elsif Is_Entity_Name (Expr) then
3346 Pool := Entity (Expr);
3348 -- If pool is a renamed object, get original one. This can
3349 -- happen with an explicit renaming, and within instances.
3351 while Present (Renamed_Object (Pool))
3352 and then Is_Entity_Name (Renamed_Object (Pool))
3353 loop
3354 Pool := Entity (Renamed_Object (Pool));
3355 end loop;
3357 if Present (Renamed_Object (Pool))
3358 and then Nkind (Renamed_Object (Pool)) = N_Type_Conversion
3359 and then Is_Entity_Name (Expression (Renamed_Object (Pool)))
3360 then
3361 Pool := Entity (Expression (Renamed_Object (Pool)));
3362 end if;
3364 Set_Associated_Storage_Pool (U_Ent, Pool);
3366 elsif Nkind (Expr) = N_Type_Conversion
3367 and then Is_Entity_Name (Expression (Expr))
3368 and then Nkind (Original_Node (Expr)) = N_Attribute_Reference
3369 then
3370 Pool := Entity (Expression (Expr));
3371 Set_Associated_Storage_Pool (U_Ent, Pool);
3373 else
3374 Error_Msg_N ("incorrect reference to a Storage Pool", Expr);
3375 return;
3376 end if;
3377 end;
3379 ------------------
3380 -- Storage_Size --
3381 ------------------
3383 -- Storage_Size attribute definition clause
3385 when Attribute_Storage_Size => Storage_Size : declare
3386 Btype : constant Entity_Id := Base_Type (U_Ent);
3387 Sprag : Node_Id;
3389 begin
3390 if Is_Task_Type (U_Ent) then
3391 Check_Restriction (No_Obsolescent_Features, N);
3393 if Warn_On_Obsolescent_Feature then
3394 Error_Msg_N
3395 ("storage size clause for task is an " &
3396 "obsolescent feature (RM J.9)?", N);
3397 Error_Msg_N ("\use Storage_Size pragma instead?", N);
3398 end if;
3400 FOnly := True;
3401 end if;
3403 if not Is_Access_Type (U_Ent)
3404 and then Ekind (U_Ent) /= E_Task_Type
3405 then
3406 Error_Msg_N ("storage size cannot be given for &", Nam);
3408 elsif Is_Access_Type (U_Ent) and Is_Derived_Type (U_Ent) then
3409 Error_Msg_N
3410 ("storage size cannot be given for a derived access type",
3411 Nam);
3413 elsif Duplicate_Clause then
3414 null;
3416 else
3417 Analyze_And_Resolve (Expr, Any_Integer);
3419 if Is_Access_Type (U_Ent) then
3420 if Present (Associated_Storage_Pool (U_Ent)) then
3421 Error_Msg_N ("storage pool already given for &", Nam);
3422 return;
3423 end if;
3425 if Is_OK_Static_Expression (Expr)
3426 and then Expr_Value (Expr) = 0
3427 then
3428 Set_No_Pool_Assigned (Btype);
3429 end if;
3431 else -- Is_Task_Type (U_Ent)
3432 Sprag := Get_Rep_Pragma (Btype, Name_Storage_Size);
3434 if Present (Sprag) then
3435 Error_Msg_Sloc := Sloc (Sprag);
3436 Error_Msg_N
3437 ("Storage_Size already specified#", Nam);
3438 return;
3439 end if;
3440 end if;
3442 Set_Has_Storage_Size_Clause (Btype);
3443 end if;
3444 end Storage_Size;
3446 -----------------
3447 -- Stream_Size --
3448 -----------------
3450 when Attribute_Stream_Size => Stream_Size : declare
3451 Size : constant Uint := Static_Integer (Expr);
3453 begin
3454 if Ada_Version <= Ada_95 then
3455 Check_Restriction (No_Implementation_Attributes, N);
3456 end if;
3458 if Duplicate_Clause then
3459 null;
3461 elsif Is_Elementary_Type (U_Ent) then
3462 if Size /= System_Storage_Unit
3463 and then
3464 Size /= System_Storage_Unit * 2
3465 and then
3466 Size /= System_Storage_Unit * 4
3467 and then
3468 Size /= System_Storage_Unit * 8
3469 then
3470 Error_Msg_Uint_1 := UI_From_Int (System_Storage_Unit);
3471 Error_Msg_N
3472 ("stream size for elementary type must be a"
3473 & " power of 2 and at least ^", N);
3475 elsif RM_Size (U_Ent) > Size then
3476 Error_Msg_Uint_1 := RM_Size (U_Ent);
3477 Error_Msg_N
3478 ("stream size for elementary type must be a"
3479 & " power of 2 and at least ^", N);
3480 end if;
3482 Set_Has_Stream_Size_Clause (U_Ent);
3484 else
3485 Error_Msg_N ("Stream_Size cannot be given for &", Nam);
3486 end if;
3487 end Stream_Size;
3489 ----------------
3490 -- Value_Size --
3491 ----------------
3493 -- Value_Size attribute definition clause
3495 when Attribute_Value_Size => Value_Size : declare
3496 Size : constant Uint := Static_Integer (Expr);
3497 Biased : Boolean;
3499 begin
3500 if not Is_Type (U_Ent) then
3501 Error_Msg_N ("Value_Size cannot be given for &", Nam);
3503 elsif Duplicate_Clause then
3504 null;
3506 elsif Is_Array_Type (U_Ent)
3507 and then not Is_Constrained (U_Ent)
3508 then
3509 Error_Msg_N
3510 ("Value_Size cannot be given for unconstrained array", Nam);
3512 else
3513 if Is_Elementary_Type (U_Ent) then
3514 Check_Size (Expr, U_Ent, Size, Biased);
3515 Set_Biased (U_Ent, N, "value size clause", Biased);
3516 end if;
3518 Set_RM_Size (U_Ent, Size);
3519 end if;
3520 end Value_Size;
3522 -----------------------
3523 -- Variable_Indexing --
3524 -----------------------
3526 when Attribute_Variable_Indexing =>
3527 Check_Indexing_Functions;
3529 -----------
3530 -- Write --
3531 -----------
3533 when Attribute_Write =>
3534 Analyze_Stream_TSS_Definition (TSS_Stream_Write);
3535 Set_Has_Specified_Stream_Write (Ent);
3537 -- All other attributes cannot be set
3539 when others =>
3540 Error_Msg_N
3541 ("attribute& cannot be set with definition clause", N);
3542 end case;
3544 -- The test for the type being frozen must be performed after any
3545 -- expression the clause has been analyzed since the expression itself
3546 -- might cause freezing that makes the clause illegal.
3548 if Rep_Item_Too_Late (U_Ent, N, FOnly) then
3549 return;
3550 end if;
3551 end Analyze_Attribute_Definition_Clause;
3553 ----------------------------
3554 -- Analyze_Code_Statement --
3555 ----------------------------
3557 procedure Analyze_Code_Statement (N : Node_Id) is
3558 HSS : constant Node_Id := Parent (N);
3559 SBody : constant Node_Id := Parent (HSS);
3560 Subp : constant Entity_Id := Current_Scope;
3561 Stmt : Node_Id;
3562 Decl : Node_Id;
3563 StmtO : Node_Id;
3564 DeclO : Node_Id;
3566 begin
3567 -- Analyze and check we get right type, note that this implements the
3568 -- requirement (RM 13.8(1)) that Machine_Code be with'ed, since that
3569 -- is the only way that Asm_Insn could possibly be visible.
3571 Analyze_And_Resolve (Expression (N));
3573 if Etype (Expression (N)) = Any_Type then
3574 return;
3575 elsif Etype (Expression (N)) /= RTE (RE_Asm_Insn) then
3576 Error_Msg_N ("incorrect type for code statement", N);
3577 return;
3578 end if;
3580 Check_Code_Statement (N);
3582 -- Make sure we appear in the handled statement sequence of a
3583 -- subprogram (RM 13.8(3)).
3585 if Nkind (HSS) /= N_Handled_Sequence_Of_Statements
3586 or else Nkind (SBody) /= N_Subprogram_Body
3587 then
3588 Error_Msg_N
3589 ("code statement can only appear in body of subprogram", N);
3590 return;
3591 end if;
3593 -- Do remaining checks (RM 13.8(3)) if not already done
3595 if not Is_Machine_Code_Subprogram (Subp) then
3596 Set_Is_Machine_Code_Subprogram (Subp);
3598 -- No exception handlers allowed
3600 if Present (Exception_Handlers (HSS)) then
3601 Error_Msg_N
3602 ("exception handlers not permitted in machine code subprogram",
3603 First (Exception_Handlers (HSS)));
3604 end if;
3606 -- No declarations other than use clauses and pragmas (we allow
3607 -- certain internally generated declarations as well).
3609 Decl := First (Declarations (SBody));
3610 while Present (Decl) loop
3611 DeclO := Original_Node (Decl);
3612 if Comes_From_Source (DeclO)
3613 and not Nkind_In (DeclO, N_Pragma,
3614 N_Use_Package_Clause,
3615 N_Use_Type_Clause,
3616 N_Implicit_Label_Declaration)
3617 then
3618 Error_Msg_N
3619 ("this declaration not allowed in machine code subprogram",
3620 DeclO);
3621 end if;
3623 Next (Decl);
3624 end loop;
3626 -- No statements other than code statements, pragmas, and labels.
3627 -- Again we allow certain internally generated statements.
3629 -- In Ada 2012, qualified expressions are names, and the code
3630 -- statement is initially parsed as a procedure call.
3632 Stmt := First (Statements (HSS));
3633 while Present (Stmt) loop
3634 StmtO := Original_Node (Stmt);
3636 -- A procedure call transformed into a code statement is OK.
3638 if Ada_Version >= Ada_2012
3639 and then Nkind (StmtO) = N_Procedure_Call_Statement
3640 and then Nkind (Name (StmtO)) = N_Qualified_Expression
3641 then
3642 null;
3644 elsif Comes_From_Source (StmtO)
3645 and then not Nkind_In (StmtO, N_Pragma,
3646 N_Label,
3647 N_Code_Statement)
3648 then
3649 Error_Msg_N
3650 ("this statement is not allowed in machine code subprogram",
3651 StmtO);
3652 end if;
3654 Next (Stmt);
3655 end loop;
3656 end if;
3657 end Analyze_Code_Statement;
3659 -----------------------------------------------
3660 -- Analyze_Enumeration_Representation_Clause --
3661 -----------------------------------------------
3663 procedure Analyze_Enumeration_Representation_Clause (N : Node_Id) is
3664 Ident : constant Node_Id := Identifier (N);
3665 Aggr : constant Node_Id := Array_Aggregate (N);
3666 Enumtype : Entity_Id;
3667 Elit : Entity_Id;
3668 Expr : Node_Id;
3669 Assoc : Node_Id;
3670 Choice : Node_Id;
3671 Val : Uint;
3673 Err : Boolean := False;
3674 -- Set True to avoid cascade errors and crashes on incorrect source code
3676 Lo : constant Uint := Expr_Value (Type_Low_Bound (Universal_Integer));
3677 Hi : constant Uint := Expr_Value (Type_High_Bound (Universal_Integer));
3678 -- Allowed range of universal integer (= allowed range of enum lit vals)
3680 Min : Uint;
3681 Max : Uint;
3682 -- Minimum and maximum values of entries
3684 Max_Node : Node_Id;
3685 -- Pointer to node for literal providing max value
3687 begin
3688 if Ignore_Rep_Clauses then
3689 return;
3690 end if;
3692 -- First some basic error checks
3694 Find_Type (Ident);
3695 Enumtype := Entity (Ident);
3697 if Enumtype = Any_Type
3698 or else Rep_Item_Too_Early (Enumtype, N)
3699 then
3700 return;
3701 else
3702 Enumtype := Underlying_Type (Enumtype);
3703 end if;
3705 if not Is_Enumeration_Type (Enumtype) then
3706 Error_Msg_NE
3707 ("enumeration type required, found}",
3708 Ident, First_Subtype (Enumtype));
3709 return;
3710 end if;
3712 -- Ignore rep clause on generic actual type. This will already have
3713 -- been flagged on the template as an error, and this is the safest
3714 -- way to ensure we don't get a junk cascaded message in the instance.
3716 if Is_Generic_Actual_Type (Enumtype) then
3717 return;
3719 -- Type must be in current scope
3721 elsif Scope (Enumtype) /= Current_Scope then
3722 Error_Msg_N ("type must be declared in this scope", Ident);
3723 return;
3725 -- Type must be a first subtype
3727 elsif not Is_First_Subtype (Enumtype) then
3728 Error_Msg_N ("cannot give enumeration rep clause for subtype", N);
3729 return;
3731 -- Ignore duplicate rep clause
3733 elsif Has_Enumeration_Rep_Clause (Enumtype) then
3734 Error_Msg_N ("duplicate enumeration rep clause ignored", N);
3735 return;
3737 -- Don't allow rep clause for standard [wide_[wide_]]character
3739 elsif Is_Standard_Character_Type (Enumtype) then
3740 Error_Msg_N ("enumeration rep clause not allowed for this type", N);
3741 return;
3743 -- Check that the expression is a proper aggregate (no parentheses)
3745 elsif Paren_Count (Aggr) /= 0 then
3746 Error_Msg
3747 ("extra parentheses surrounding aggregate not allowed",
3748 First_Sloc (Aggr));
3749 return;
3751 -- All tests passed, so set rep clause in place
3753 else
3754 Set_Has_Enumeration_Rep_Clause (Enumtype);
3755 Set_Has_Enumeration_Rep_Clause (Base_Type (Enumtype));
3756 end if;
3758 -- Now we process the aggregate. Note that we don't use the normal
3759 -- aggregate code for this purpose, because we don't want any of the
3760 -- normal expansion activities, and a number of special semantic
3761 -- rules apply (including the component type being any integer type)
3763 Elit := First_Literal (Enumtype);
3765 -- First the positional entries if any
3767 if Present (Expressions (Aggr)) then
3768 Expr := First (Expressions (Aggr));
3769 while Present (Expr) loop
3770 if No (Elit) then
3771 Error_Msg_N ("too many entries in aggregate", Expr);
3772 return;
3773 end if;
3775 Val := Static_Integer (Expr);
3777 -- Err signals that we found some incorrect entries processing
3778 -- the list. The final checks for completeness and ordering are
3779 -- skipped in this case.
3781 if Val = No_Uint then
3782 Err := True;
3783 elsif Val < Lo or else Hi < Val then
3784 Error_Msg_N ("value outside permitted range", Expr);
3785 Err := True;
3786 end if;
3788 Set_Enumeration_Rep (Elit, Val);
3789 Set_Enumeration_Rep_Expr (Elit, Expr);
3790 Next (Expr);
3791 Next (Elit);
3792 end loop;
3793 end if;
3795 -- Now process the named entries if present
3797 if Present (Component_Associations (Aggr)) then
3798 Assoc := First (Component_Associations (Aggr));
3799 while Present (Assoc) loop
3800 Choice := First (Choices (Assoc));
3802 if Present (Next (Choice)) then
3803 Error_Msg_N
3804 ("multiple choice not allowed here", Next (Choice));
3805 Err := True;
3806 end if;
3808 if Nkind (Choice) = N_Others_Choice then
3809 Error_Msg_N ("others choice not allowed here", Choice);
3810 Err := True;
3812 elsif Nkind (Choice) = N_Range then
3814 -- ??? should allow zero/one element range here
3816 Error_Msg_N ("range not allowed here", Choice);
3817 Err := True;
3819 else
3820 Analyze_And_Resolve (Choice, Enumtype);
3822 if Error_Posted (Choice) then
3823 Err := True;
3824 end if;
3826 if not Err then
3827 if Is_Entity_Name (Choice)
3828 and then Is_Type (Entity (Choice))
3829 then
3830 Error_Msg_N ("subtype name not allowed here", Choice);
3831 Err := True;
3833 -- ??? should allow static subtype with zero/one entry
3835 elsif Etype (Choice) = Base_Type (Enumtype) then
3836 if not Is_Static_Expression (Choice) then
3837 Flag_Non_Static_Expr
3838 ("non-static expression used for choice!", Choice);
3839 Err := True;
3841 else
3842 Elit := Expr_Value_E (Choice);
3844 if Present (Enumeration_Rep_Expr (Elit)) then
3845 Error_Msg_Sloc :=
3846 Sloc (Enumeration_Rep_Expr (Elit));
3847 Error_Msg_NE
3848 ("representation for& previously given#",
3849 Choice, Elit);
3850 Err := True;
3851 end if;
3853 Set_Enumeration_Rep_Expr (Elit, Expression (Assoc));
3855 Expr := Expression (Assoc);
3856 Val := Static_Integer (Expr);
3858 if Val = No_Uint then
3859 Err := True;
3861 elsif Val < Lo or else Hi < Val then
3862 Error_Msg_N ("value outside permitted range", Expr);
3863 Err := True;
3864 end if;
3866 Set_Enumeration_Rep (Elit, Val);
3867 end if;
3868 end if;
3869 end if;
3870 end if;
3872 Next (Assoc);
3873 end loop;
3874 end if;
3876 -- Aggregate is fully processed. Now we check that a full set of
3877 -- representations was given, and that they are in range and in order.
3878 -- These checks are only done if no other errors occurred.
3880 if not Err then
3881 Min := No_Uint;
3882 Max := No_Uint;
3884 Elit := First_Literal (Enumtype);
3885 while Present (Elit) loop
3886 if No (Enumeration_Rep_Expr (Elit)) then
3887 Error_Msg_NE ("missing representation for&!", N, Elit);
3889 else
3890 Val := Enumeration_Rep (Elit);
3892 if Min = No_Uint then
3893 Min := Val;
3894 end if;
3896 if Val /= No_Uint then
3897 if Max /= No_Uint and then Val <= Max then
3898 Error_Msg_NE
3899 ("enumeration value for& not ordered!",
3900 Enumeration_Rep_Expr (Elit), Elit);
3901 end if;
3903 Max_Node := Enumeration_Rep_Expr (Elit);
3904 Max := Val;
3905 end if;
3907 -- If there is at least one literal whose representation is not
3908 -- equal to the Pos value, then note that this enumeration type
3909 -- has a non-standard representation.
3911 if Val /= Enumeration_Pos (Elit) then
3912 Set_Has_Non_Standard_Rep (Base_Type (Enumtype));
3913 end if;
3914 end if;
3916 Next (Elit);
3917 end loop;
3919 -- Now set proper size information
3921 declare
3922 Minsize : Uint := UI_From_Int (Minimum_Size (Enumtype));
3924 begin
3925 if Has_Size_Clause (Enumtype) then
3927 -- All OK, if size is OK now
3929 if RM_Size (Enumtype) >= Minsize then
3930 null;
3932 else
3933 -- Try if we can get by with biasing
3935 Minsize :=
3936 UI_From_Int (Minimum_Size (Enumtype, Biased => True));
3938 -- Error message if even biasing does not work
3940 if RM_Size (Enumtype) < Minsize then
3941 Error_Msg_Uint_1 := RM_Size (Enumtype);
3942 Error_Msg_Uint_2 := Max;
3943 Error_Msg_N
3944 ("previously given size (^) is too small "
3945 & "for this value (^)", Max_Node);
3947 -- If biasing worked, indicate that we now have biased rep
3949 else
3950 Set_Biased
3951 (Enumtype, Size_Clause (Enumtype), "size clause");
3952 end if;
3953 end if;
3955 else
3956 Set_RM_Size (Enumtype, Minsize);
3957 Set_Enum_Esize (Enumtype);
3958 end if;
3960 Set_RM_Size (Base_Type (Enumtype), RM_Size (Enumtype));
3961 Set_Esize (Base_Type (Enumtype), Esize (Enumtype));
3962 Set_Alignment (Base_Type (Enumtype), Alignment (Enumtype));
3963 end;
3964 end if;
3966 -- We repeat the too late test in case it froze itself!
3968 if Rep_Item_Too_Late (Enumtype, N) then
3969 null;
3970 end if;
3971 end Analyze_Enumeration_Representation_Clause;
3973 ----------------------------
3974 -- Analyze_Free_Statement --
3975 ----------------------------
3977 procedure Analyze_Free_Statement (N : Node_Id) is
3978 begin
3979 Analyze (Expression (N));
3980 end Analyze_Free_Statement;
3982 ---------------------------
3983 -- Analyze_Freeze_Entity --
3984 ---------------------------
3986 procedure Analyze_Freeze_Entity (N : Node_Id) is
3987 E : constant Entity_Id := Entity (N);
3989 begin
3990 -- Remember that we are processing a freezing entity. Required to
3991 -- ensure correct decoration of internal entities associated with
3992 -- interfaces (see New_Overloaded_Entity).
3994 Inside_Freezing_Actions := Inside_Freezing_Actions + 1;
3996 -- For tagged types covering interfaces add internal entities that link
3997 -- the primitives of the interfaces with the primitives that cover them.
3998 -- Note: These entities were originally generated only when generating
3999 -- code because their main purpose was to provide support to initialize
4000 -- the secondary dispatch tables. They are now generated also when
4001 -- compiling with no code generation to provide ASIS the relationship
4002 -- between interface primitives and tagged type primitives. They are
4003 -- also used to locate primitives covering interfaces when processing
4004 -- generics (see Derive_Subprograms).
4006 if Ada_Version >= Ada_2005
4007 and then Ekind (E) = E_Record_Type
4008 and then Is_Tagged_Type (E)
4009 and then not Is_Interface (E)
4010 and then Has_Interfaces (E)
4011 then
4012 -- This would be a good common place to call the routine that checks
4013 -- overriding of interface primitives (and thus factorize calls to
4014 -- Check_Abstract_Overriding located at different contexts in the
4015 -- compiler). However, this is not possible because it causes
4016 -- spurious errors in case of late overriding.
4018 Add_Internal_Interface_Entities (E);
4019 end if;
4021 -- Check CPP types
4023 if Ekind (E) = E_Record_Type
4024 and then Is_CPP_Class (E)
4025 and then Is_Tagged_Type (E)
4026 and then Tagged_Type_Expansion
4027 and then Expander_Active
4028 then
4029 if CPP_Num_Prims (E) = 0 then
4031 -- If the CPP type has user defined components then it must import
4032 -- primitives from C++. This is required because if the C++ class
4033 -- has no primitives then the C++ compiler does not added the _tag
4034 -- component to the type.
4036 pragma Assert (Chars (First_Entity (E)) = Name_uTag);
4038 if First_Entity (E) /= Last_Entity (E) then
4039 Error_Msg_N
4040 ("?'C'P'P type must import at least one primitive from C++",
4042 end if;
4043 end if;
4045 -- Check that all its primitives are abstract or imported from C++.
4046 -- Check also availability of the C++ constructor.
4048 declare
4049 Has_Constructors : constant Boolean := Has_CPP_Constructors (E);
4050 Elmt : Elmt_Id;
4051 Error_Reported : Boolean := False;
4052 Prim : Node_Id;
4054 begin
4055 Elmt := First_Elmt (Primitive_Operations (E));
4056 while Present (Elmt) loop
4057 Prim := Node (Elmt);
4059 if Comes_From_Source (Prim) then
4060 if Is_Abstract_Subprogram (Prim) then
4061 null;
4063 elsif not Is_Imported (Prim)
4064 or else Convention (Prim) /= Convention_CPP
4065 then
4066 Error_Msg_N
4067 ("?primitives of 'C'P'P types must be imported from C++"
4068 & " or abstract", Prim);
4070 elsif not Has_Constructors
4071 and then not Error_Reported
4072 then
4073 Error_Msg_Name_1 := Chars (E);
4074 Error_Msg_N
4075 ("?'C'P'P constructor required for type %", Prim);
4076 Error_Reported := True;
4077 end if;
4078 end if;
4080 Next_Elmt (Elmt);
4081 end loop;
4082 end;
4083 end if;
4085 Inside_Freezing_Actions := Inside_Freezing_Actions - 1;
4087 -- If we have a type with predicates, build predicate function
4089 if Is_Type (E) and then Has_Predicates (E) then
4090 Build_Predicate_Function (E, N);
4091 end if;
4093 -- If type has delayed aspects, this is where we do the preanalysis at
4094 -- the freeze point, as part of the consistent visibility check. Note
4095 -- that this must be done after calling Build_Predicate_Function or
4096 -- Build_Invariant_Procedure since these subprograms fix occurrences of
4097 -- the subtype name in the saved expression so that they will not cause
4098 -- trouble in the preanalysis.
4100 if Has_Delayed_Aspects (E) then
4101 declare
4102 Ritem : Node_Id;
4104 begin
4105 -- Look for aspect specification entries for this entity
4107 Ritem := First_Rep_Item (E);
4108 while Present (Ritem) loop
4109 if Nkind (Ritem) = N_Aspect_Specification
4110 and then Entity (Ritem) = E
4111 and then Is_Delayed_Aspect (Ritem)
4112 and then Scope (E) = Current_Scope
4113 then
4114 Check_Aspect_At_Freeze_Point (Ritem);
4115 end if;
4117 Next_Rep_Item (Ritem);
4118 end loop;
4119 end;
4120 end if;
4121 end Analyze_Freeze_Entity;
4123 ------------------------------------------
4124 -- Analyze_Record_Representation_Clause --
4125 ------------------------------------------
4127 -- Note: we check as much as we can here, but we can't do any checks
4128 -- based on the position values (e.g. overlap checks) until freeze time
4129 -- because especially in Ada 2005 (machine scalar mode), the processing
4130 -- for non-standard bit order can substantially change the positions.
4131 -- See procedure Check_Record_Representation_Clause (called from Freeze)
4132 -- for the remainder of this processing.
4134 procedure Analyze_Record_Representation_Clause (N : Node_Id) is
4135 Ident : constant Node_Id := Identifier (N);
4136 Biased : Boolean;
4137 CC : Node_Id;
4138 Comp : Entity_Id;
4139 Fbit : Uint;
4140 Hbit : Uint := Uint_0;
4141 Lbit : Uint;
4142 Ocomp : Entity_Id;
4143 Posit : Uint;
4144 Rectype : Entity_Id;
4146 CR_Pragma : Node_Id := Empty;
4147 -- Points to N_Pragma node if Complete_Representation pragma present
4149 begin
4150 if Ignore_Rep_Clauses then
4151 return;
4152 end if;
4154 Find_Type (Ident);
4155 Rectype := Entity (Ident);
4157 if Rectype = Any_Type
4158 or else Rep_Item_Too_Early (Rectype, N)
4159 then
4160 return;
4161 else
4162 Rectype := Underlying_Type (Rectype);
4163 end if;
4165 -- First some basic error checks
4167 if not Is_Record_Type (Rectype) then
4168 Error_Msg_NE
4169 ("record type required, found}", Ident, First_Subtype (Rectype));
4170 return;
4172 elsif Scope (Rectype) /= Current_Scope then
4173 Error_Msg_N ("type must be declared in this scope", N);
4174 return;
4176 elsif not Is_First_Subtype (Rectype) then
4177 Error_Msg_N ("cannot give record rep clause for subtype", N);
4178 return;
4180 elsif Has_Record_Rep_Clause (Rectype) then
4181 Error_Msg_N ("duplicate record rep clause ignored", N);
4182 return;
4184 elsif Rep_Item_Too_Late (Rectype, N) then
4185 return;
4186 end if;
4188 if Present (Mod_Clause (N)) then
4189 declare
4190 Loc : constant Source_Ptr := Sloc (N);
4191 M : constant Node_Id := Mod_Clause (N);
4192 P : constant List_Id := Pragmas_Before (M);
4193 AtM_Nod : Node_Id;
4195 Mod_Val : Uint;
4196 pragma Warnings (Off, Mod_Val);
4198 begin
4199 Check_Restriction (No_Obsolescent_Features, Mod_Clause (N));
4201 if Warn_On_Obsolescent_Feature then
4202 Error_Msg_N
4203 ("mod clause is an obsolescent feature (RM J.8)?", N);
4204 Error_Msg_N
4205 ("\use alignment attribute definition clause instead?", N);
4206 end if;
4208 if Present (P) then
4209 Analyze_List (P);
4210 end if;
4212 -- In ASIS_Mode mode, expansion is disabled, but we must convert
4213 -- the Mod clause into an alignment clause anyway, so that the
4214 -- back-end can compute and back-annotate properly the size and
4215 -- alignment of types that may include this record.
4217 -- This seems dubious, this destroys the source tree in a manner
4218 -- not detectable by ASIS ???
4220 if Operating_Mode = Check_Semantics and then ASIS_Mode then
4221 AtM_Nod :=
4222 Make_Attribute_Definition_Clause (Loc,
4223 Name => New_Reference_To (Base_Type (Rectype), Loc),
4224 Chars => Name_Alignment,
4225 Expression => Relocate_Node (Expression (M)));
4227 Set_From_At_Mod (AtM_Nod);
4228 Insert_After (N, AtM_Nod);
4229 Mod_Val := Get_Alignment_Value (Expression (AtM_Nod));
4230 Set_Mod_Clause (N, Empty);
4232 else
4233 -- Get the alignment value to perform error checking
4235 Mod_Val := Get_Alignment_Value (Expression (M));
4236 end if;
4237 end;
4238 end if;
4240 -- For untagged types, clear any existing component clauses for the
4241 -- type. If the type is derived, this is what allows us to override
4242 -- a rep clause for the parent. For type extensions, the representation
4243 -- of the inherited components is inherited, so we want to keep previous
4244 -- component clauses for completeness.
4246 if not Is_Tagged_Type (Rectype) then
4247 Comp := First_Component_Or_Discriminant (Rectype);
4248 while Present (Comp) loop
4249 Set_Component_Clause (Comp, Empty);
4250 Next_Component_Or_Discriminant (Comp);
4251 end loop;
4252 end if;
4254 -- All done if no component clauses
4256 CC := First (Component_Clauses (N));
4258 if No (CC) then
4259 return;
4260 end if;
4262 -- A representation like this applies to the base type
4264 Set_Has_Record_Rep_Clause (Base_Type (Rectype));
4265 Set_Has_Non_Standard_Rep (Base_Type (Rectype));
4266 Set_Has_Specified_Layout (Base_Type (Rectype));
4268 -- Process the component clauses
4270 while Present (CC) loop
4272 -- Pragma
4274 if Nkind (CC) = N_Pragma then
4275 Analyze (CC);
4277 -- The only pragma of interest is Complete_Representation
4279 if Pragma_Name (CC) = Name_Complete_Representation then
4280 CR_Pragma := CC;
4281 end if;
4283 -- Processing for real component clause
4285 else
4286 Posit := Static_Integer (Position (CC));
4287 Fbit := Static_Integer (First_Bit (CC));
4288 Lbit := Static_Integer (Last_Bit (CC));
4290 if Posit /= No_Uint
4291 and then Fbit /= No_Uint
4292 and then Lbit /= No_Uint
4293 then
4294 if Posit < 0 then
4295 Error_Msg_N
4296 ("position cannot be negative", Position (CC));
4298 elsif Fbit < 0 then
4299 Error_Msg_N
4300 ("first bit cannot be negative", First_Bit (CC));
4302 -- The Last_Bit specified in a component clause must not be
4303 -- less than the First_Bit minus one (RM-13.5.1(10)).
4305 elsif Lbit < Fbit - 1 then
4306 Error_Msg_N
4307 ("last bit cannot be less than first bit minus one",
4308 Last_Bit (CC));
4310 -- Values look OK, so find the corresponding record component
4311 -- Even though the syntax allows an attribute reference for
4312 -- implementation-defined components, GNAT does not allow the
4313 -- tag to get an explicit position.
4315 elsif Nkind (Component_Name (CC)) = N_Attribute_Reference then
4316 if Attribute_Name (Component_Name (CC)) = Name_Tag then
4317 Error_Msg_N ("position of tag cannot be specified", CC);
4318 else
4319 Error_Msg_N ("illegal component name", CC);
4320 end if;
4322 else
4323 Comp := First_Entity (Rectype);
4324 while Present (Comp) loop
4325 exit when Chars (Comp) = Chars (Component_Name (CC));
4326 Next_Entity (Comp);
4327 end loop;
4329 if No (Comp) then
4331 -- Maybe component of base type that is absent from
4332 -- statically constrained first subtype.
4334 Comp := First_Entity (Base_Type (Rectype));
4335 while Present (Comp) loop
4336 exit when Chars (Comp) = Chars (Component_Name (CC));
4337 Next_Entity (Comp);
4338 end loop;
4339 end if;
4341 if No (Comp) then
4342 Error_Msg_N
4343 ("component clause is for non-existent field", CC);
4345 -- Ada 2012 (AI05-0026): Any name that denotes a
4346 -- discriminant of an object of an unchecked union type
4347 -- shall not occur within a record_representation_clause.
4349 -- The general restriction of using record rep clauses on
4350 -- Unchecked_Union types has now been lifted. Since it is
4351 -- possible to introduce a record rep clause which mentions
4352 -- the discriminant of an Unchecked_Union in non-Ada 2012
4353 -- code, this check is applied to all versions of the
4354 -- language.
4356 elsif Ekind (Comp) = E_Discriminant
4357 and then Is_Unchecked_Union (Rectype)
4358 then
4359 Error_Msg_N
4360 ("cannot reference discriminant of Unchecked_Union",
4361 Component_Name (CC));
4363 elsif Present (Component_Clause (Comp)) then
4365 -- Diagnose duplicate rep clause, or check consistency
4366 -- if this is an inherited component. In a double fault,
4367 -- there may be a duplicate inconsistent clause for an
4368 -- inherited component.
4370 if Scope (Original_Record_Component (Comp)) = Rectype
4371 or else Parent (Component_Clause (Comp)) = N
4372 then
4373 Error_Msg_Sloc := Sloc (Component_Clause (Comp));
4374 Error_Msg_N ("component clause previously given#", CC);
4376 else
4377 declare
4378 Rep1 : constant Node_Id := Component_Clause (Comp);
4379 begin
4380 if Intval (Position (Rep1)) /=
4381 Intval (Position (CC))
4382 or else Intval (First_Bit (Rep1)) /=
4383 Intval (First_Bit (CC))
4384 or else Intval (Last_Bit (Rep1)) /=
4385 Intval (Last_Bit (CC))
4386 then
4387 Error_Msg_N ("component clause inconsistent "
4388 & "with representation of ancestor", CC);
4389 elsif Warn_On_Redundant_Constructs then
4390 Error_Msg_N ("?redundant component clause "
4391 & "for inherited component!", CC);
4392 end if;
4393 end;
4394 end if;
4396 -- Normal case where this is the first component clause we
4397 -- have seen for this entity, so set it up properly.
4399 else
4400 -- Make reference for field in record rep clause and set
4401 -- appropriate entity field in the field identifier.
4403 Generate_Reference
4404 (Comp, Component_Name (CC), Set_Ref => False);
4405 Set_Entity (Component_Name (CC), Comp);
4407 -- Update Fbit and Lbit to the actual bit number
4409 Fbit := Fbit + UI_From_Int (SSU) * Posit;
4410 Lbit := Lbit + UI_From_Int (SSU) * Posit;
4412 if Has_Size_Clause (Rectype)
4413 and then RM_Size (Rectype) <= Lbit
4414 then
4415 Error_Msg_N
4416 ("bit number out of range of specified size",
4417 Last_Bit (CC));
4418 else
4419 Set_Component_Clause (Comp, CC);
4420 Set_Component_Bit_Offset (Comp, Fbit);
4421 Set_Esize (Comp, 1 + (Lbit - Fbit));
4422 Set_Normalized_First_Bit (Comp, Fbit mod SSU);
4423 Set_Normalized_Position (Comp, Fbit / SSU);
4425 if Warn_On_Overridden_Size
4426 and then Has_Size_Clause (Etype (Comp))
4427 and then RM_Size (Etype (Comp)) /= Esize (Comp)
4428 then
4429 Error_Msg_NE
4430 ("?component size overrides size clause for&",
4431 Component_Name (CC), Etype (Comp));
4432 end if;
4434 -- This information is also set in the corresponding
4435 -- component of the base type, found by accessing the
4436 -- Original_Record_Component link if it is present.
4438 Ocomp := Original_Record_Component (Comp);
4440 if Hbit < Lbit then
4441 Hbit := Lbit;
4442 end if;
4444 Check_Size
4445 (Component_Name (CC),
4446 Etype (Comp),
4447 Esize (Comp),
4448 Biased);
4450 Set_Biased
4451 (Comp, First_Node (CC), "component clause", Biased);
4453 if Present (Ocomp) then
4454 Set_Component_Clause (Ocomp, CC);
4455 Set_Component_Bit_Offset (Ocomp, Fbit);
4456 Set_Normalized_First_Bit (Ocomp, Fbit mod SSU);
4457 Set_Normalized_Position (Ocomp, Fbit / SSU);
4458 Set_Esize (Ocomp, 1 + (Lbit - Fbit));
4460 Set_Normalized_Position_Max
4461 (Ocomp, Normalized_Position (Ocomp));
4463 -- Note: we don't use Set_Biased here, because we
4464 -- already gave a warning above if needed, and we
4465 -- would get a duplicate for the same name here.
4467 Set_Has_Biased_Representation
4468 (Ocomp, Has_Biased_Representation (Comp));
4469 end if;
4471 if Esize (Comp) < 0 then
4472 Error_Msg_N ("component size is negative", CC);
4473 end if;
4474 end if;
4475 end if;
4476 end if;
4477 end if;
4478 end if;
4480 Next (CC);
4481 end loop;
4483 -- Check missing components if Complete_Representation pragma appeared
4485 if Present (CR_Pragma) then
4486 Comp := First_Component_Or_Discriminant (Rectype);
4487 while Present (Comp) loop
4488 if No (Component_Clause (Comp)) then
4489 Error_Msg_NE
4490 ("missing component clause for &", CR_Pragma, Comp);
4491 end if;
4493 Next_Component_Or_Discriminant (Comp);
4494 end loop;
4496 -- If no Complete_Representation pragma, warn if missing components
4498 elsif Warn_On_Unrepped_Components then
4499 declare
4500 Num_Repped_Components : Nat := 0;
4501 Num_Unrepped_Components : Nat := 0;
4503 begin
4504 -- First count number of repped and unrepped components
4506 Comp := First_Component_Or_Discriminant (Rectype);
4507 while Present (Comp) loop
4508 if Present (Component_Clause (Comp)) then
4509 Num_Repped_Components := Num_Repped_Components + 1;
4510 else
4511 Num_Unrepped_Components := Num_Unrepped_Components + 1;
4512 end if;
4514 Next_Component_Or_Discriminant (Comp);
4515 end loop;
4517 -- We are only interested in the case where there is at least one
4518 -- unrepped component, and at least half the components have rep
4519 -- clauses. We figure that if less than half have them, then the
4520 -- partial rep clause is really intentional. If the component
4521 -- type has no underlying type set at this point (as for a generic
4522 -- formal type), we don't know enough to give a warning on the
4523 -- component.
4525 if Num_Unrepped_Components > 0
4526 and then Num_Unrepped_Components < Num_Repped_Components
4527 then
4528 Comp := First_Component_Or_Discriminant (Rectype);
4529 while Present (Comp) loop
4530 if No (Component_Clause (Comp))
4531 and then Comes_From_Source (Comp)
4532 and then Present (Underlying_Type (Etype (Comp)))
4533 and then (Is_Scalar_Type (Underlying_Type (Etype (Comp)))
4534 or else Size_Known_At_Compile_Time
4535 (Underlying_Type (Etype (Comp))))
4536 and then not Has_Warnings_Off (Rectype)
4537 then
4538 Error_Msg_Sloc := Sloc (Comp);
4539 Error_Msg_NE
4540 ("?no component clause given for & declared #",
4541 N, Comp);
4542 end if;
4544 Next_Component_Or_Discriminant (Comp);
4545 end loop;
4546 end if;
4547 end;
4548 end if;
4549 end Analyze_Record_Representation_Clause;
4551 -------------------------------
4552 -- Build_Invariant_Procedure --
4553 -------------------------------
4555 -- The procedure that is constructed here has the form
4557 -- procedure typInvariant (Ixxx : typ) is
4558 -- begin
4559 -- pragma Check (Invariant, exp, "failed invariant from xxx");
4560 -- pragma Check (Invariant, exp, "failed invariant from xxx");
4561 -- ...
4562 -- pragma Check (Invariant, exp, "failed inherited invariant from xxx");
4563 -- ...
4564 -- end typInvariant;
4566 procedure Build_Invariant_Procedure (Typ : Entity_Id; N : Node_Id) is
4567 Loc : constant Source_Ptr := Sloc (Typ);
4568 Stmts : List_Id;
4569 Spec : Node_Id;
4570 SId : Entity_Id;
4571 PDecl : Node_Id;
4572 PBody : Node_Id;
4574 Visible_Decls : constant List_Id := Visible_Declarations (N);
4575 Private_Decls : constant List_Id := Private_Declarations (N);
4577 procedure Add_Invariants (T : Entity_Id; Inherit : Boolean);
4578 -- Appends statements to Stmts for any invariants in the rep item chain
4579 -- of the given type. If Inherit is False, then we only process entries
4580 -- on the chain for the type Typ. If Inherit is True, then we ignore any
4581 -- Invariant aspects, but we process all Invariant'Class aspects, adding
4582 -- "inherited" to the exception message and generating an informational
4583 -- message about the inheritance of an invariant.
4585 Object_Name : constant Name_Id := New_Internal_Name ('I');
4586 -- Name for argument of invariant procedure
4588 Object_Entity : constant Node_Id :=
4589 Make_Defining_Identifier (Loc, Object_Name);
4590 -- The procedure declaration entity for the argument
4592 --------------------
4593 -- Add_Invariants --
4594 --------------------
4596 procedure Add_Invariants (T : Entity_Id; Inherit : Boolean) is
4597 Ritem : Node_Id;
4598 Arg1 : Node_Id;
4599 Arg2 : Node_Id;
4600 Arg3 : Node_Id;
4601 Exp : Node_Id;
4602 Loc : Source_Ptr;
4603 Assoc : List_Id;
4604 Str : String_Id;
4606 procedure Replace_Type_Reference (N : Node_Id);
4607 -- Replace a single occurrence N of the subtype name with a reference
4608 -- to the formal of the predicate function. N can be an identifier
4609 -- referencing the subtype, or a selected component, representing an
4610 -- appropriately qualified occurrence of the subtype name.
4612 procedure Replace_Type_References is
4613 new Replace_Type_References_Generic (Replace_Type_Reference);
4614 -- Traverse an expression replacing all occurrences of the subtype
4615 -- name with appropriate references to the object that is the formal
4616 -- parameter of the predicate function. Note that we must ensure
4617 -- that the type and entity information is properly set in the
4618 -- replacement node, since we will do a Preanalyze call of this
4619 -- expression without proper visibility of the procedure argument.
4621 ----------------------------
4622 -- Replace_Type_Reference --
4623 ----------------------------
4625 procedure Replace_Type_Reference (N : Node_Id) is
4626 begin
4627 -- Invariant'Class, replace with T'Class (obj)
4629 if Class_Present (Ritem) then
4630 Rewrite (N,
4631 Make_Type_Conversion (Loc,
4632 Subtype_Mark =>
4633 Make_Attribute_Reference (Loc,
4634 Prefix => New_Occurrence_Of (T, Loc),
4635 Attribute_Name => Name_Class),
4636 Expression => Make_Identifier (Loc, Object_Name)));
4638 Set_Entity (Expression (N), Object_Entity);
4639 Set_Etype (Expression (N), Typ);
4641 -- Invariant, replace with obj
4643 else
4644 Rewrite (N, Make_Identifier (Loc, Object_Name));
4645 Set_Entity (N, Object_Entity);
4646 Set_Etype (N, Typ);
4647 end if;
4648 end Replace_Type_Reference;
4650 -- Start of processing for Add_Invariants
4652 begin
4653 Ritem := First_Rep_Item (T);
4654 while Present (Ritem) loop
4655 if Nkind (Ritem) = N_Pragma
4656 and then Pragma_Name (Ritem) = Name_Invariant
4657 then
4658 Arg1 := First (Pragma_Argument_Associations (Ritem));
4659 Arg2 := Next (Arg1);
4660 Arg3 := Next (Arg2);
4662 Arg1 := Get_Pragma_Arg (Arg1);
4663 Arg2 := Get_Pragma_Arg (Arg2);
4665 -- For Inherit case, ignore Invariant, process only Class case
4667 if Inherit then
4668 if not Class_Present (Ritem) then
4669 goto Continue;
4670 end if;
4672 -- For Inherit false, process only item for right type
4674 else
4675 if Entity (Arg1) /= Typ then
4676 goto Continue;
4677 end if;
4678 end if;
4680 if No (Stmts) then
4681 Stmts := Empty_List;
4682 end if;
4684 Exp := New_Copy_Tree (Arg2);
4685 Loc := Sloc (Exp);
4687 -- We need to replace any occurrences of the name of the type
4688 -- with references to the object, converted to type'Class in
4689 -- the case of Invariant'Class aspects.
4691 Replace_Type_References (Exp, Chars (T));
4693 -- If this invariant comes from an aspect, find the aspect
4694 -- specification, and replace the saved expression because
4695 -- we need the subtype references replaced for the calls to
4696 -- Preanalyze_Spec_Expressin in Check_Aspect_At_Freeze_Point
4697 -- and Check_Aspect_At_End_Of_Declarations.
4699 if From_Aspect_Specification (Ritem) then
4700 declare
4701 Aitem : Node_Id;
4703 begin
4704 -- Loop to find corresponding aspect, note that this
4705 -- must be present given the pragma is marked delayed.
4707 Aitem := Next_Rep_Item (Ritem);
4708 while Present (Aitem) loop
4709 if Nkind (Aitem) = N_Aspect_Specification
4710 and then Aspect_Rep_Item (Aitem) = Ritem
4711 then
4712 Set_Entity
4713 (Identifier (Aitem), New_Copy_Tree (Exp));
4714 exit;
4715 end if;
4717 Aitem := Next_Rep_Item (Aitem);
4718 end loop;
4719 end;
4720 end if;
4722 -- Now we need to preanalyze the expression to properly capture
4723 -- the visibility in the visible part. The expression will not
4724 -- be analyzed for real until the body is analyzed, but that is
4725 -- at the end of the private part and has the wrong visibility.
4727 Set_Parent (Exp, N);
4728 Preanalyze_Spec_Expression (Exp, Standard_Boolean);
4730 -- Build first two arguments for Check pragma
4732 Assoc := New_List (
4733 Make_Pragma_Argument_Association (Loc,
4734 Expression => Make_Identifier (Loc, Name_Invariant)),
4735 Make_Pragma_Argument_Association (Loc, Expression => Exp));
4737 -- Add message if present in Invariant pragma
4739 if Present (Arg3) then
4740 Str := Strval (Get_Pragma_Arg (Arg3));
4742 -- If inherited case, and message starts "failed invariant",
4743 -- change it to be "failed inherited invariant".
4745 if Inherit then
4746 String_To_Name_Buffer (Str);
4748 if Name_Buffer (1 .. 16) = "failed invariant" then
4749 Insert_Str_In_Name_Buffer ("inherited ", 8);
4750 Str := String_From_Name_Buffer;
4751 end if;
4752 end if;
4754 Append_To (Assoc,
4755 Make_Pragma_Argument_Association (Loc,
4756 Expression => Make_String_Literal (Loc, Str)));
4757 end if;
4759 -- Add Check pragma to list of statements
4761 Append_To (Stmts,
4762 Make_Pragma (Loc,
4763 Pragma_Identifier =>
4764 Make_Identifier (Loc, Name_Check),
4765 Pragma_Argument_Associations => Assoc));
4767 -- If Inherited case and option enabled, output info msg. Note
4768 -- that we know this is a case of Invariant'Class.
4770 if Inherit and Opt.List_Inherited_Aspects then
4771 Error_Msg_Sloc := Sloc (Ritem);
4772 Error_Msg_N
4773 ("?info: & inherits `Invariant''Class` aspect from #",
4774 Typ);
4775 end if;
4776 end if;
4778 <<Continue>>
4779 Next_Rep_Item (Ritem);
4780 end loop;
4781 end Add_Invariants;
4783 -- Start of processing for Build_Invariant_Procedure
4785 begin
4786 Stmts := No_List;
4787 PDecl := Empty;
4788 PBody := Empty;
4789 Set_Etype (Object_Entity, Typ);
4791 -- Add invariants for the current type
4793 Add_Invariants (Typ, Inherit => False);
4795 -- Add invariants for parent types
4797 declare
4798 Current_Typ : Entity_Id;
4799 Parent_Typ : Entity_Id;
4801 begin
4802 Current_Typ := Typ;
4803 loop
4804 Parent_Typ := Etype (Current_Typ);
4806 if Is_Private_Type (Parent_Typ)
4807 and then Present (Full_View (Base_Type (Parent_Typ)))
4808 then
4809 Parent_Typ := Full_View (Base_Type (Parent_Typ));
4810 end if;
4812 exit when Parent_Typ = Current_Typ;
4814 Current_Typ := Parent_Typ;
4815 Add_Invariants (Current_Typ, Inherit => True);
4816 end loop;
4817 end;
4819 -- Build the procedure if we generated at least one Check pragma
4821 if Stmts /= No_List then
4823 -- Build procedure declaration
4825 SId :=
4826 Make_Defining_Identifier (Loc,
4827 Chars => New_External_Name (Chars (Typ), "Invariant"));
4828 Set_Has_Invariants (SId);
4829 Set_Invariant_Procedure (Typ, SId);
4831 Spec :=
4832 Make_Procedure_Specification (Loc,
4833 Defining_Unit_Name => SId,
4834 Parameter_Specifications => New_List (
4835 Make_Parameter_Specification (Loc,
4836 Defining_Identifier => Object_Entity,
4837 Parameter_Type => New_Occurrence_Of (Typ, Loc))));
4839 PDecl := Make_Subprogram_Declaration (Loc, Specification => Spec);
4841 -- Build procedure body
4843 SId :=
4844 Make_Defining_Identifier (Loc,
4845 Chars => New_External_Name (Chars (Typ), "Invariant"));
4847 Spec :=
4848 Make_Procedure_Specification (Loc,
4849 Defining_Unit_Name => SId,
4850 Parameter_Specifications => New_List (
4851 Make_Parameter_Specification (Loc,
4852 Defining_Identifier =>
4853 Make_Defining_Identifier (Loc, Object_Name),
4854 Parameter_Type => New_Occurrence_Of (Typ, Loc))));
4856 PBody :=
4857 Make_Subprogram_Body (Loc,
4858 Specification => Spec,
4859 Declarations => Empty_List,
4860 Handled_Statement_Sequence =>
4861 Make_Handled_Sequence_Of_Statements (Loc,
4862 Statements => Stmts));
4864 -- Insert procedure declaration and spec at the appropriate points.
4865 -- Skip this if there are no private declarations (that's an error
4866 -- that will be diagnosed elsewhere, and there is no point in having
4867 -- an invariant procedure set if the full declaration is missing).
4869 if Present (Private_Decls) then
4871 -- The spec goes at the end of visible declarations, but they have
4872 -- already been analyzed, so we need to explicitly do the analyze.
4874 Append_To (Visible_Decls, PDecl);
4875 Analyze (PDecl);
4877 -- The body goes at the end of the private declarations, which we
4878 -- have not analyzed yet, so we do not need to perform an explicit
4879 -- analyze call. We skip this if there are no private declarations
4880 -- (this is an error that will be caught elsewhere);
4882 Append_To (Private_Decls, PBody);
4884 -- If the invariant appears on the full view of a type, the
4885 -- analysis of the private part is complete, and we must
4886 -- analyze the new body explicitly.
4888 if In_Private_Part (Current_Scope) then
4889 Analyze (PBody);
4890 end if;
4891 end if;
4892 end if;
4893 end Build_Invariant_Procedure;
4895 ------------------------------
4896 -- Build_Predicate_Function --
4897 ------------------------------
4899 -- The procedure that is constructed here has the form
4901 -- function typPredicate (Ixxx : typ) return Boolean is
4902 -- begin
4903 -- return
4904 -- exp1 and then exp2 and then ...
4905 -- and then typ1Predicate (typ1 (Ixxx))
4906 -- and then typ2Predicate (typ2 (Ixxx))
4907 -- and then ...;
4908 -- end typPredicate;
4910 -- Here exp1, and exp2 are expressions from Predicate pragmas. Note that
4911 -- this is the point at which these expressions get analyzed, providing the
4912 -- required delay, and typ1, typ2, are entities from which predicates are
4913 -- inherited. Note that we do NOT generate Check pragmas, that's because we
4914 -- use this function even if checks are off, e.g. for membership tests.
4916 procedure Build_Predicate_Function (Typ : Entity_Id; N : Node_Id) is
4917 Loc : constant Source_Ptr := Sloc (Typ);
4918 Spec : Node_Id;
4919 SId : Entity_Id;
4920 FDecl : Node_Id;
4921 FBody : Node_Id;
4923 Expr : Node_Id;
4924 -- This is the expression for the return statement in the function. It
4925 -- is build by connecting the component predicates with AND THEN.
4927 procedure Add_Call (T : Entity_Id);
4928 -- Includes a call to the predicate function for type T in Expr if T
4929 -- has predicates and Predicate_Function (T) is non-empty.
4931 procedure Add_Predicates;
4932 -- Appends expressions for any Predicate pragmas in the rep item chain
4933 -- Typ to Expr. Note that we look only at items for this exact entity.
4934 -- Inheritance of predicates for the parent type is done by calling the
4935 -- Predicate_Function of the parent type, using Add_Call above.
4937 Object_Name : constant Name_Id := New_Internal_Name ('I');
4938 -- Name for argument of Predicate procedure
4940 Object_Entity : constant Entity_Id :=
4941 Make_Defining_Identifier (Loc, Object_Name);
4942 -- The entity for the spec entity for the argument
4944 Dynamic_Predicate_Present : Boolean := False;
4945 -- Set True if a dynamic predicate is present, results in the entire
4946 -- predicate being considered dynamic even if it looks static
4948 Static_Predicate_Present : Node_Id := Empty;
4949 -- Set to N_Pragma node for a static predicate if one is encountered.
4951 --------------
4952 -- Add_Call --
4953 --------------
4955 procedure Add_Call (T : Entity_Id) is
4956 Exp : Node_Id;
4958 begin
4959 if Present (T) and then Present (Predicate_Function (T)) then
4960 Set_Has_Predicates (Typ);
4962 -- Build the call to the predicate function of T
4964 Exp :=
4965 Make_Predicate_Call
4966 (T, Convert_To (T, Make_Identifier (Loc, Object_Name)));
4968 -- Add call to evolving expression, using AND THEN if needed
4970 if No (Expr) then
4971 Expr := Exp;
4972 else
4973 Expr :=
4974 Make_And_Then (Loc,
4975 Left_Opnd => Relocate_Node (Expr),
4976 Right_Opnd => Exp);
4977 end if;
4979 -- Output info message on inheritance if required. Note we do not
4980 -- give this information for generic actual types, since it is
4981 -- unwelcome noise in that case in instantiations. We also
4982 -- generally suppress the message in instantiations, and also
4983 -- if it involves internal names.
4985 if Opt.List_Inherited_Aspects
4986 and then not Is_Generic_Actual_Type (Typ)
4987 and then Instantiation_Depth (Sloc (Typ)) = 0
4988 and then not Is_Internal_Name (Chars (T))
4989 and then not Is_Internal_Name (Chars (Typ))
4990 then
4991 Error_Msg_Sloc := Sloc (Predicate_Function (T));
4992 Error_Msg_Node_2 := T;
4993 Error_Msg_N ("?info: & inherits predicate from & #", Typ);
4994 end if;
4995 end if;
4996 end Add_Call;
4998 --------------------
4999 -- Add_Predicates --
5000 --------------------
5002 procedure Add_Predicates is
5003 Ritem : Node_Id;
5004 Arg1 : Node_Id;
5005 Arg2 : Node_Id;
5007 procedure Replace_Type_Reference (N : Node_Id);
5008 -- Replace a single occurrence N of the subtype name with a reference
5009 -- to the formal of the predicate function. N can be an identifier
5010 -- referencing the subtype, or a selected component, representing an
5011 -- appropriately qualified occurrence of the subtype name.
5013 procedure Replace_Type_References is
5014 new Replace_Type_References_Generic (Replace_Type_Reference);
5015 -- Traverse an expression changing every occurrence of an identifier
5016 -- whose name matches the name of the subtype with a reference to
5017 -- the formal parameter of the predicate function.
5019 ----------------------------
5020 -- Replace_Type_Reference --
5021 ----------------------------
5023 procedure Replace_Type_Reference (N : Node_Id) is
5024 begin
5025 Rewrite (N, Make_Identifier (Loc, Object_Name));
5026 Set_Entity (N, Object_Entity);
5027 Set_Etype (N, Typ);
5028 end Replace_Type_Reference;
5030 -- Start of processing for Add_Predicates
5032 begin
5033 Ritem := First_Rep_Item (Typ);
5034 while Present (Ritem) loop
5035 if Nkind (Ritem) = N_Pragma
5036 and then Pragma_Name (Ritem) = Name_Predicate
5037 then
5038 if Present (Corresponding_Aspect (Ritem)) then
5039 case Chars (Identifier (Corresponding_Aspect (Ritem))) is
5040 when Name_Dynamic_Predicate =>
5041 Dynamic_Predicate_Present := True;
5042 when Name_Static_Predicate =>
5043 Static_Predicate_Present := Ritem;
5044 when others =>
5045 null;
5046 end case;
5047 end if;
5049 -- Acquire arguments
5051 Arg1 := First (Pragma_Argument_Associations (Ritem));
5052 Arg2 := Next (Arg1);
5054 Arg1 := Get_Pragma_Arg (Arg1);
5055 Arg2 := Get_Pragma_Arg (Arg2);
5057 -- See if this predicate pragma is for the current type or for
5058 -- its full view. A predicate on a private completion is placed
5059 -- on the partial view beause this is the visible entity that
5060 -- is frozen.
5062 if Entity (Arg1) = Typ
5063 or else Full_View (Entity (Arg1)) = Typ
5064 then
5066 -- We have a match, this entry is for our subtype
5068 -- We need to replace any occurrences of the name of the
5069 -- type with references to the object.
5071 Replace_Type_References (Arg2, Chars (Typ));
5073 -- If this predicate comes from an aspect, find the aspect
5074 -- specification, and replace the saved expression because
5075 -- we need the subtype references replaced for the calls to
5076 -- Preanalyze_Spec_Expressin in Check_Aspect_At_Freeze_Point
5077 -- and Check_Aspect_At_End_Of_Declarations.
5079 if From_Aspect_Specification (Ritem) then
5080 declare
5081 Aitem : Node_Id;
5083 begin
5084 -- Loop to find corresponding aspect, note that this
5085 -- must be present given the pragma is marked delayed.
5087 Aitem := Next_Rep_Item (Ritem);
5088 loop
5089 if Nkind (Aitem) = N_Aspect_Specification
5090 and then Aspect_Rep_Item (Aitem) = Ritem
5091 then
5092 Set_Entity
5093 (Identifier (Aitem), New_Copy_Tree (Arg2));
5094 exit;
5095 end if;
5097 Aitem := Next_Rep_Item (Aitem);
5098 end loop;
5099 end;
5100 end if;
5102 -- Now we can add the expression
5104 if No (Expr) then
5105 Expr := Relocate_Node (Arg2);
5107 -- There already was a predicate, so add to it
5109 else
5110 Expr :=
5111 Make_And_Then (Loc,
5112 Left_Opnd => Relocate_Node (Expr),
5113 Right_Opnd => Relocate_Node (Arg2));
5114 end if;
5115 end if;
5116 end if;
5118 Next_Rep_Item (Ritem);
5119 end loop;
5120 end Add_Predicates;
5122 -- Start of processing for Build_Predicate_Function
5124 begin
5125 -- Initialize for construction of statement list
5127 Expr := Empty;
5129 -- Return if already built or if type does not have predicates
5131 if not Has_Predicates (Typ)
5132 or else Present (Predicate_Function (Typ))
5133 then
5134 return;
5135 end if;
5137 -- Add Predicates for the current type
5139 Add_Predicates;
5141 -- Add predicates for ancestor if present
5143 declare
5144 Atyp : constant Entity_Id := Nearest_Ancestor (Typ);
5145 begin
5146 if Present (Atyp) then
5147 Add_Call (Atyp);
5148 end if;
5149 end;
5151 -- If we have predicates, build the function
5153 if Present (Expr) then
5155 -- Build function declaration
5157 pragma Assert (Has_Predicates (Typ));
5158 SId :=
5159 Make_Defining_Identifier (Loc,
5160 Chars => New_External_Name (Chars (Typ), "Predicate"));
5161 Set_Has_Predicates (SId);
5162 Set_Predicate_Function (Typ, SId);
5164 -- The predicate function is shared between views of a type.
5166 if Is_Private_Type (Typ) and then Present (Full_View (Typ)) then
5167 Set_Predicate_Function (Full_View (Typ), SId);
5168 end if;
5170 Spec :=
5171 Make_Function_Specification (Loc,
5172 Defining_Unit_Name => SId,
5173 Parameter_Specifications => New_List (
5174 Make_Parameter_Specification (Loc,
5175 Defining_Identifier => Object_Entity,
5176 Parameter_Type => New_Occurrence_Of (Typ, Loc))),
5177 Result_Definition =>
5178 New_Occurrence_Of (Standard_Boolean, Loc));
5180 FDecl := Make_Subprogram_Declaration (Loc, Specification => Spec);
5182 -- Build function body
5184 SId :=
5185 Make_Defining_Identifier (Loc,
5186 Chars => New_External_Name (Chars (Typ), "Predicate"));
5188 Spec :=
5189 Make_Function_Specification (Loc,
5190 Defining_Unit_Name => SId,
5191 Parameter_Specifications => New_List (
5192 Make_Parameter_Specification (Loc,
5193 Defining_Identifier =>
5194 Make_Defining_Identifier (Loc, Object_Name),
5195 Parameter_Type =>
5196 New_Occurrence_Of (Typ, Loc))),
5197 Result_Definition =>
5198 New_Occurrence_Of (Standard_Boolean, Loc));
5200 FBody :=
5201 Make_Subprogram_Body (Loc,
5202 Specification => Spec,
5203 Declarations => Empty_List,
5204 Handled_Statement_Sequence =>
5205 Make_Handled_Sequence_Of_Statements (Loc,
5206 Statements => New_List (
5207 Make_Simple_Return_Statement (Loc,
5208 Expression => Expr))));
5210 -- Insert declaration before freeze node and body after
5212 Insert_Before_And_Analyze (N, FDecl);
5213 Insert_After_And_Analyze (N, FBody);
5215 -- Deal with static predicate case
5217 if Ekind_In (Typ, E_Enumeration_Subtype,
5218 E_Modular_Integer_Subtype,
5219 E_Signed_Integer_Subtype)
5220 and then Is_Static_Subtype (Typ)
5221 and then not Dynamic_Predicate_Present
5222 then
5223 Build_Static_Predicate (Typ, Expr, Object_Name);
5225 if Present (Static_Predicate_Present)
5226 and No (Static_Predicate (Typ))
5227 then
5228 Error_Msg_F
5229 ("expression does not have required form for "
5230 & "static predicate",
5231 Next (First (Pragma_Argument_Associations
5232 (Static_Predicate_Present))));
5233 end if;
5234 end if;
5235 end if;
5236 end Build_Predicate_Function;
5238 ----------------------------
5239 -- Build_Static_Predicate --
5240 ----------------------------
5242 procedure Build_Static_Predicate
5243 (Typ : Entity_Id;
5244 Expr : Node_Id;
5245 Nam : Name_Id)
5247 Loc : constant Source_Ptr := Sloc (Expr);
5249 Non_Static : exception;
5250 -- Raised if something non-static is found
5252 Btyp : constant Entity_Id := Base_Type (Typ);
5254 BLo : constant Uint := Expr_Value (Type_Low_Bound (Btyp));
5255 BHi : constant Uint := Expr_Value (Type_High_Bound (Btyp));
5256 -- Low bound and high bound value of base type of Typ
5258 TLo : constant Uint := Expr_Value (Type_Low_Bound (Typ));
5259 THi : constant Uint := Expr_Value (Type_High_Bound (Typ));
5260 -- Low bound and high bound values of static subtype Typ
5262 type REnt is record
5263 Lo, Hi : Uint;
5264 end record;
5265 -- One entry in a Rlist value, a single REnt (range entry) value
5266 -- denotes one range from Lo to Hi. To represent a single value
5267 -- range Lo = Hi = value.
5269 type RList is array (Nat range <>) of REnt;
5270 -- A list of ranges. The ranges are sorted in increasing order,
5271 -- and are disjoint (there is a gap of at least one value between
5272 -- each range in the table). A value is in the set of ranges in
5273 -- Rlist if it lies within one of these ranges
5275 False_Range : constant RList :=
5276 RList'(1 .. 0 => REnt'(No_Uint, No_Uint));
5277 -- An empty set of ranges represents a range list that can never be
5278 -- satisfied, since there are no ranges in which the value could lie,
5279 -- so it does not lie in any of them. False_Range is a canonical value
5280 -- for this empty set, but general processing should test for an Rlist
5281 -- with length zero (see Is_False predicate), since other null ranges
5282 -- may appear which must be treated as False.
5284 True_Range : constant RList := RList'(1 => REnt'(BLo, BHi));
5285 -- Range representing True, value must be in the base range
5287 function "and" (Left, Right : RList) return RList;
5288 -- And's together two range lists, returning a range list. This is
5289 -- a set intersection operation.
5291 function "or" (Left, Right : RList) return RList;
5292 -- Or's together two range lists, returning a range list. This is a
5293 -- set union operation.
5295 function "not" (Right : RList) return RList;
5296 -- Returns complement of a given range list, i.e. a range list
5297 -- representing all the values in TLo .. THi that are not in the
5298 -- input operand Right.
5300 function Build_Val (V : Uint) return Node_Id;
5301 -- Return an analyzed N_Identifier node referencing this value, suitable
5302 -- for use as an entry in the Static_Predicate list. This node is typed
5303 -- with the base type.
5305 function Build_Range (Lo, Hi : Uint) return Node_Id;
5306 -- Return an analyzed N_Range node referencing this range, suitable
5307 -- for use as an entry in the Static_Predicate list. This node is typed
5308 -- with the base type.
5310 function Get_RList (Exp : Node_Id) return RList;
5311 -- This is a recursive routine that converts the given expression into
5312 -- a list of ranges, suitable for use in building the static predicate.
5314 function Is_False (R : RList) return Boolean;
5315 pragma Inline (Is_False);
5316 -- Returns True if the given range list is empty, and thus represents
5317 -- a False list of ranges that can never be satisfied.
5319 function Is_True (R : RList) return Boolean;
5320 -- Returns True if R trivially represents the True predicate by having
5321 -- a single range from BLo to BHi.
5323 function Is_Type_Ref (N : Node_Id) return Boolean;
5324 pragma Inline (Is_Type_Ref);
5325 -- Returns if True if N is a reference to the type for the predicate in
5326 -- the expression (i.e. if it is an identifier whose Chars field matches
5327 -- the Nam given in the call).
5329 function Lo_Val (N : Node_Id) return Uint;
5330 -- Given static expression or static range from a Static_Predicate list,
5331 -- gets expression value or low bound of range.
5333 function Hi_Val (N : Node_Id) return Uint;
5334 -- Given static expression or static range from a Static_Predicate list,
5335 -- gets expression value of high bound of range.
5337 function Membership_Entry (N : Node_Id) return RList;
5338 -- Given a single membership entry (range, value, or subtype), returns
5339 -- the corresponding range list. Raises Static_Error if not static.
5341 function Membership_Entries (N : Node_Id) return RList;
5342 -- Given an element on an alternatives list of a membership operation,
5343 -- returns the range list corresponding to this entry and all following
5344 -- entries (i.e. returns the "or" of this list of values).
5346 function Stat_Pred (Typ : Entity_Id) return RList;
5347 -- Given a type, if it has a static predicate, then return the predicate
5348 -- as a range list, otherwise raise Non_Static.
5350 -----------
5351 -- "and" --
5352 -----------
5354 function "and" (Left, Right : RList) return RList is
5355 FEnt : REnt;
5356 -- First range of result
5358 SLeft : Nat := Left'First;
5359 -- Start of rest of left entries
5361 SRight : Nat := Right'First;
5362 -- Start of rest of right entries
5364 begin
5365 -- If either range is True, return the other
5367 if Is_True (Left) then
5368 return Right;
5369 elsif Is_True (Right) then
5370 return Left;
5371 end if;
5373 -- If either range is False, return False
5375 if Is_False (Left) or else Is_False (Right) then
5376 return False_Range;
5377 end if;
5379 -- Loop to remove entries at start that are disjoint, and thus
5380 -- just get discarded from the result entirely.
5382 loop
5383 -- If no operands left in either operand, result is false
5385 if SLeft > Left'Last or else SRight > Right'Last then
5386 return False_Range;
5388 -- Discard first left operand entry if disjoint with right
5390 elsif Left (SLeft).Hi < Right (SRight).Lo then
5391 SLeft := SLeft + 1;
5393 -- Discard first right operand entry if disjoint with left
5395 elsif Right (SRight).Hi < Left (SLeft).Lo then
5396 SRight := SRight + 1;
5398 -- Otherwise we have an overlapping entry
5400 else
5401 exit;
5402 end if;
5403 end loop;
5405 -- Now we have two non-null operands, and first entries overlap.
5406 -- The first entry in the result will be the overlapping part of
5407 -- these two entries.
5409 FEnt := REnt'(Lo => UI_Max (Left (SLeft).Lo, Right (SRight).Lo),
5410 Hi => UI_Min (Left (SLeft).Hi, Right (SRight).Hi));
5412 -- Now we can remove the entry that ended at a lower value, since
5413 -- its contribution is entirely contained in Fent.
5415 if Left (SLeft).Hi <= Right (SRight).Hi then
5416 SLeft := SLeft + 1;
5417 else
5418 SRight := SRight + 1;
5419 end if;
5421 -- Compute result by concatenating this first entry with the "and"
5422 -- of the remaining parts of the left and right operands. Note that
5423 -- if either of these is empty, "and" will yield empty, so that we
5424 -- will end up with just Fent, which is what we want in that case.
5426 return
5427 FEnt & (Left (SLeft .. Left'Last) and Right (SRight .. Right'Last));
5428 end "and";
5430 -----------
5431 -- "not" --
5432 -----------
5434 function "not" (Right : RList) return RList is
5435 begin
5436 -- Return True if False range
5438 if Is_False (Right) then
5439 return True_Range;
5440 end if;
5442 -- Return False if True range
5444 if Is_True (Right) then
5445 return False_Range;
5446 end if;
5448 -- Here if not trivial case
5450 declare
5451 Result : RList (1 .. Right'Length + 1);
5452 -- May need one more entry for gap at beginning and end
5454 Count : Nat := 0;
5455 -- Number of entries stored in Result
5457 begin
5458 -- Gap at start
5460 if Right (Right'First).Lo > TLo then
5461 Count := Count + 1;
5462 Result (Count) := REnt'(TLo, Right (Right'First).Lo - 1);
5463 end if;
5465 -- Gaps between ranges
5467 for J in Right'First .. Right'Last - 1 loop
5468 Count := Count + 1;
5469 Result (Count) :=
5470 REnt'(Right (J).Hi + 1, Right (J + 1).Lo - 1);
5471 end loop;
5473 -- Gap at end
5475 if Right (Right'Last).Hi < THi then
5476 Count := Count + 1;
5477 Result (Count) := REnt'(Right (Right'Last).Hi + 1, THi);
5478 end if;
5480 return Result (1 .. Count);
5481 end;
5482 end "not";
5484 ----------
5485 -- "or" --
5486 ----------
5488 function "or" (Left, Right : RList) return RList is
5489 FEnt : REnt;
5490 -- First range of result
5492 SLeft : Nat := Left'First;
5493 -- Start of rest of left entries
5495 SRight : Nat := Right'First;
5496 -- Start of rest of right entries
5498 begin
5499 -- If either range is True, return True
5501 if Is_True (Left) or else Is_True (Right) then
5502 return True_Range;
5503 end if;
5505 -- If either range is False (empty), return the other
5507 if Is_False (Left) then
5508 return Right;
5509 elsif Is_False (Right) then
5510 return Left;
5511 end if;
5513 -- Initialize result first entry from left or right operand
5514 -- depending on which starts with the lower range.
5516 if Left (SLeft).Lo < Right (SRight).Lo then
5517 FEnt := Left (SLeft);
5518 SLeft := SLeft + 1;
5519 else
5520 FEnt := Right (SRight);
5521 SRight := SRight + 1;
5522 end if;
5524 -- This loop eats ranges from left and right operands that
5525 -- are contiguous with the first range we are gathering.
5527 loop
5528 -- Eat first entry in left operand if contiguous or
5529 -- overlapped by gathered first operand of result.
5531 if SLeft <= Left'Last
5532 and then Left (SLeft).Lo <= FEnt.Hi + 1
5533 then
5534 FEnt.Hi := UI_Max (FEnt.Hi, Left (SLeft).Hi);
5535 SLeft := SLeft + 1;
5537 -- Eat first entry in right operand if contiguous or
5538 -- overlapped by gathered right operand of result.
5540 elsif SRight <= Right'Last
5541 and then Right (SRight).Lo <= FEnt.Hi + 1
5542 then
5543 FEnt.Hi := UI_Max (FEnt.Hi, Right (SRight).Hi);
5544 SRight := SRight + 1;
5546 -- All done if no more entries to eat!
5548 else
5549 exit;
5550 end if;
5551 end loop;
5553 -- Obtain result as the first entry we just computed, concatenated
5554 -- to the "or" of the remaining results (if one operand is empty,
5555 -- this will just concatenate with the other
5557 return
5558 FEnt & (Left (SLeft .. Left'Last) or Right (SRight .. Right'Last));
5559 end "or";
5561 -----------------
5562 -- Build_Range --
5563 -----------------
5565 function Build_Range (Lo, Hi : Uint) return Node_Id is
5566 Result : Node_Id;
5567 begin
5568 if Lo = Hi then
5569 return Build_Val (Hi);
5570 else
5571 Result :=
5572 Make_Range (Loc,
5573 Low_Bound => Build_Val (Lo),
5574 High_Bound => Build_Val (Hi));
5575 Set_Etype (Result, Btyp);
5576 Set_Analyzed (Result);
5577 return Result;
5578 end if;
5579 end Build_Range;
5581 ---------------
5582 -- Build_Val --
5583 ---------------
5585 function Build_Val (V : Uint) return Node_Id is
5586 Result : Node_Id;
5588 begin
5589 if Is_Enumeration_Type (Typ) then
5590 Result := Get_Enum_Lit_From_Pos (Typ, V, Loc);
5591 else
5592 Result := Make_Integer_Literal (Loc, V);
5593 end if;
5595 Set_Etype (Result, Btyp);
5596 Set_Is_Static_Expression (Result);
5597 Set_Analyzed (Result);
5598 return Result;
5599 end Build_Val;
5601 ---------------
5602 -- Get_RList --
5603 ---------------
5605 function Get_RList (Exp : Node_Id) return RList is
5606 Op : Node_Kind;
5607 Val : Uint;
5609 begin
5610 -- Static expression can only be true or false
5612 if Is_OK_Static_Expression (Exp) then
5614 -- For False
5616 if Expr_Value (Exp) = 0 then
5617 return False_Range;
5618 else
5619 return True_Range;
5620 end if;
5621 end if;
5623 -- Otherwise test node type
5625 Op := Nkind (Exp);
5627 case Op is
5629 -- And
5631 when N_Op_And | N_And_Then =>
5632 return Get_RList (Left_Opnd (Exp))
5634 Get_RList (Right_Opnd (Exp));
5636 -- Or
5638 when N_Op_Or | N_Or_Else =>
5639 return Get_RList (Left_Opnd (Exp))
5641 Get_RList (Right_Opnd (Exp));
5643 -- Not
5645 when N_Op_Not =>
5646 return not Get_RList (Right_Opnd (Exp));
5648 -- Comparisons of type with static value
5650 when N_Op_Compare =>
5651 -- Type is left operand
5653 if Is_Type_Ref (Left_Opnd (Exp))
5654 and then Is_OK_Static_Expression (Right_Opnd (Exp))
5655 then
5656 Val := Expr_Value (Right_Opnd (Exp));
5658 -- Typ is right operand
5660 elsif Is_Type_Ref (Right_Opnd (Exp))
5661 and then Is_OK_Static_Expression (Left_Opnd (Exp))
5662 then
5663 Val := Expr_Value (Left_Opnd (Exp));
5665 -- Invert sense of comparison
5667 case Op is
5668 when N_Op_Gt => Op := N_Op_Lt;
5669 when N_Op_Lt => Op := N_Op_Gt;
5670 when N_Op_Ge => Op := N_Op_Le;
5671 when N_Op_Le => Op := N_Op_Ge;
5672 when others => null;
5673 end case;
5675 -- Other cases are non-static
5677 else
5678 raise Non_Static;
5679 end if;
5681 -- Construct range according to comparison operation
5683 case Op is
5684 when N_Op_Eq =>
5685 return RList'(1 => REnt'(Val, Val));
5687 when N_Op_Ge =>
5688 return RList'(1 => REnt'(Val, BHi));
5690 when N_Op_Gt =>
5691 return RList'(1 => REnt'(Val + 1, BHi));
5693 when N_Op_Le =>
5694 return RList'(1 => REnt'(BLo, Val));
5696 when N_Op_Lt =>
5697 return RList'(1 => REnt'(BLo, Val - 1));
5699 when N_Op_Ne =>
5700 return RList'(REnt'(BLo, Val - 1),
5701 REnt'(Val + 1, BHi));
5703 when others =>
5704 raise Program_Error;
5705 end case;
5707 -- Membership (IN)
5709 when N_In =>
5710 if not Is_Type_Ref (Left_Opnd (Exp)) then
5711 raise Non_Static;
5712 end if;
5714 if Present (Right_Opnd (Exp)) then
5715 return Membership_Entry (Right_Opnd (Exp));
5716 else
5717 return Membership_Entries (First (Alternatives (Exp)));
5718 end if;
5720 -- Negative membership (NOT IN)
5722 when N_Not_In =>
5723 if not Is_Type_Ref (Left_Opnd (Exp)) then
5724 raise Non_Static;
5725 end if;
5727 if Present (Right_Opnd (Exp)) then
5728 return not Membership_Entry (Right_Opnd (Exp));
5729 else
5730 return not Membership_Entries (First (Alternatives (Exp)));
5731 end if;
5733 -- Function call, may be call to static predicate
5735 when N_Function_Call =>
5736 if Is_Entity_Name (Name (Exp)) then
5737 declare
5738 Ent : constant Entity_Id := Entity (Name (Exp));
5739 begin
5740 if Has_Predicates (Ent) then
5741 return Stat_Pred (Etype (First_Formal (Ent)));
5742 end if;
5743 end;
5744 end if;
5746 -- Other function call cases are non-static
5748 raise Non_Static;
5750 -- Qualified expression, dig out the expression
5752 when N_Qualified_Expression =>
5753 return Get_RList (Expression (Exp));
5755 -- Xor operator
5757 when N_Op_Xor =>
5758 return (Get_RList (Left_Opnd (Exp))
5759 and not Get_RList (Right_Opnd (Exp)))
5760 or (Get_RList (Right_Opnd (Exp))
5761 and not Get_RList (Left_Opnd (Exp)));
5763 -- Any other node type is non-static
5765 when others =>
5766 raise Non_Static;
5767 end case;
5768 end Get_RList;
5770 ------------
5771 -- Hi_Val --
5772 ------------
5774 function Hi_Val (N : Node_Id) return Uint is
5775 begin
5776 if Is_Static_Expression (N) then
5777 return Expr_Value (N);
5778 else
5779 pragma Assert (Nkind (N) = N_Range);
5780 return Expr_Value (High_Bound (N));
5781 end if;
5782 end Hi_Val;
5784 --------------
5785 -- Is_False --
5786 --------------
5788 function Is_False (R : RList) return Boolean is
5789 begin
5790 return R'Length = 0;
5791 end Is_False;
5793 -------------
5794 -- Is_True --
5795 -------------
5797 function Is_True (R : RList) return Boolean is
5798 begin
5799 return R'Length = 1
5800 and then R (R'First).Lo = BLo
5801 and then R (R'First).Hi = BHi;
5802 end Is_True;
5804 -----------------
5805 -- Is_Type_Ref --
5806 -----------------
5808 function Is_Type_Ref (N : Node_Id) return Boolean is
5809 begin
5810 return Nkind (N) = N_Identifier and then Chars (N) = Nam;
5811 end Is_Type_Ref;
5813 ------------
5814 -- Lo_Val --
5815 ------------
5817 function Lo_Val (N : Node_Id) return Uint is
5818 begin
5819 if Is_Static_Expression (N) then
5820 return Expr_Value (N);
5821 else
5822 pragma Assert (Nkind (N) = N_Range);
5823 return Expr_Value (Low_Bound (N));
5824 end if;
5825 end Lo_Val;
5827 ------------------------
5828 -- Membership_Entries --
5829 ------------------------
5831 function Membership_Entries (N : Node_Id) return RList is
5832 begin
5833 if No (Next (N)) then
5834 return Membership_Entry (N);
5835 else
5836 return Membership_Entry (N) or Membership_Entries (Next (N));
5837 end if;
5838 end Membership_Entries;
5840 ----------------------
5841 -- Membership_Entry --
5842 ----------------------
5844 function Membership_Entry (N : Node_Id) return RList is
5845 Val : Uint;
5846 SLo : Uint;
5847 SHi : Uint;
5849 begin
5850 -- Range case
5852 if Nkind (N) = N_Range then
5853 if not Is_Static_Expression (Low_Bound (N))
5854 or else
5855 not Is_Static_Expression (High_Bound (N))
5856 then
5857 raise Non_Static;
5858 else
5859 SLo := Expr_Value (Low_Bound (N));
5860 SHi := Expr_Value (High_Bound (N));
5861 return RList'(1 => REnt'(SLo, SHi));
5862 end if;
5864 -- Static expression case
5866 elsif Is_Static_Expression (N) then
5867 Val := Expr_Value (N);
5868 return RList'(1 => REnt'(Val, Val));
5870 -- Identifier (other than static expression) case
5872 else pragma Assert (Nkind (N) = N_Identifier);
5874 -- Type case
5876 if Is_Type (Entity (N)) then
5878 -- If type has predicates, process them
5880 if Has_Predicates (Entity (N)) then
5881 return Stat_Pred (Entity (N));
5883 -- For static subtype without predicates, get range
5885 elsif Is_Static_Subtype (Entity (N)) then
5886 SLo := Expr_Value (Type_Low_Bound (Entity (N)));
5887 SHi := Expr_Value (Type_High_Bound (Entity (N)));
5888 return RList'(1 => REnt'(SLo, SHi));
5890 -- Any other type makes us non-static
5892 else
5893 raise Non_Static;
5894 end if;
5896 -- Any other kind of identifier in predicate (e.g. a non-static
5897 -- expression value) means this is not a static predicate.
5899 else
5900 raise Non_Static;
5901 end if;
5902 end if;
5903 end Membership_Entry;
5905 ---------------
5906 -- Stat_Pred --
5907 ---------------
5909 function Stat_Pred (Typ : Entity_Id) return RList is
5910 begin
5911 -- Not static if type does not have static predicates
5913 if not Has_Predicates (Typ)
5914 or else No (Static_Predicate (Typ))
5915 then
5916 raise Non_Static;
5917 end if;
5919 -- Otherwise we convert the predicate list to a range list
5921 declare
5922 Result : RList (1 .. List_Length (Static_Predicate (Typ)));
5923 P : Node_Id;
5925 begin
5926 P := First (Static_Predicate (Typ));
5927 for J in Result'Range loop
5928 Result (J) := REnt'(Lo_Val (P), Hi_Val (P));
5929 Next (P);
5930 end loop;
5932 return Result;
5933 end;
5934 end Stat_Pred;
5936 -- Start of processing for Build_Static_Predicate
5938 begin
5939 -- Now analyze the expression to see if it is a static predicate
5941 declare
5942 Ranges : constant RList := Get_RList (Expr);
5943 -- Range list from expression if it is static
5945 Plist : List_Id;
5947 begin
5948 -- Convert range list into a form for the static predicate. In the
5949 -- Ranges array, we just have raw ranges, these must be converted
5950 -- to properly typed and analyzed static expressions or range nodes.
5952 -- Note: here we limit ranges to the ranges of the subtype, so that
5953 -- a predicate is always false for values outside the subtype. That
5954 -- seems fine, such values are invalid anyway, and considering them
5955 -- to fail the predicate seems allowed and friendly, and furthermore
5956 -- simplifies processing for case statements and loops.
5958 Plist := New_List;
5960 for J in Ranges'Range loop
5961 declare
5962 Lo : Uint := Ranges (J).Lo;
5963 Hi : Uint := Ranges (J).Hi;
5965 begin
5966 -- Ignore completely out of range entry
5968 if Hi < TLo or else Lo > THi then
5969 null;
5971 -- Otherwise process entry
5973 else
5974 -- Adjust out of range value to subtype range
5976 if Lo < TLo then
5977 Lo := TLo;
5978 end if;
5980 if Hi > THi then
5981 Hi := THi;
5982 end if;
5984 -- Convert range into required form
5986 if Lo = Hi then
5987 Append_To (Plist, Build_Val (Lo));
5988 else
5989 Append_To (Plist, Build_Range (Lo, Hi));
5990 end if;
5991 end if;
5992 end;
5993 end loop;
5995 -- Processing was successful and all entries were static, so now we
5996 -- can store the result as the predicate list.
5998 Set_Static_Predicate (Typ, Plist);
6000 -- The processing for static predicates put the expression into
6001 -- canonical form as a series of ranges. It also eliminated
6002 -- duplicates and collapsed and combined ranges. We might as well
6003 -- replace the alternatives list of the right operand of the
6004 -- membership test with the static predicate list, which will
6005 -- usually be more efficient.
6007 declare
6008 New_Alts : constant List_Id := New_List;
6009 Old_Node : Node_Id;
6010 New_Node : Node_Id;
6012 begin
6013 Old_Node := First (Plist);
6014 while Present (Old_Node) loop
6015 New_Node := New_Copy (Old_Node);
6017 if Nkind (New_Node) = N_Range then
6018 Set_Low_Bound (New_Node, New_Copy (Low_Bound (Old_Node)));
6019 Set_High_Bound (New_Node, New_Copy (High_Bound (Old_Node)));
6020 end if;
6022 Append_To (New_Alts, New_Node);
6023 Next (Old_Node);
6024 end loop;
6026 -- If empty list, replace by False
6028 if Is_Empty_List (New_Alts) then
6029 Rewrite (Expr, New_Occurrence_Of (Standard_False, Loc));
6031 -- Else replace by set membership test
6033 else
6034 Rewrite (Expr,
6035 Make_In (Loc,
6036 Left_Opnd => Make_Identifier (Loc, Nam),
6037 Right_Opnd => Empty,
6038 Alternatives => New_Alts));
6040 -- Resolve new expression in function context
6042 Install_Formals (Predicate_Function (Typ));
6043 Push_Scope (Predicate_Function (Typ));
6044 Analyze_And_Resolve (Expr, Standard_Boolean);
6045 Pop_Scope;
6046 end if;
6047 end;
6048 end;
6050 -- If non-static, return doing nothing
6052 exception
6053 when Non_Static =>
6054 return;
6055 end Build_Static_Predicate;
6057 -----------------------------------------
6058 -- Check_Aspect_At_End_Of_Declarations --
6059 -----------------------------------------
6061 procedure Check_Aspect_At_End_Of_Declarations (ASN : Node_Id) is
6062 Ent : constant Entity_Id := Entity (ASN);
6063 Ident : constant Node_Id := Identifier (ASN);
6065 Freeze_Expr : constant Node_Id := Expression (ASN);
6066 -- Expression from call to Check_Aspect_At_Freeze_Point
6068 End_Decl_Expr : constant Node_Id := Entity (Ident);
6069 -- Expression to be analyzed at end of declarations
6071 T : constant Entity_Id := Etype (Freeze_Expr);
6072 -- Type required for preanalyze call
6074 A_Id : constant Aspect_Id := Get_Aspect_Id (Chars (Ident));
6076 Err : Boolean;
6077 -- Set False if error
6079 -- On entry to this procedure, Entity (Ident) contains a copy of the
6080 -- original expression from the aspect, saved for this purpose, and
6081 -- but Expression (Ident) is a preanalyzed copy of the expression,
6082 -- preanalyzed just after the freeze point.
6084 begin
6085 -- Case of stream attributes, just have to compare entities
6087 if A_Id = Aspect_Input or else
6088 A_Id = Aspect_Output or else
6089 A_Id = Aspect_Read or else
6090 A_Id = Aspect_Write
6091 then
6092 Analyze (End_Decl_Expr);
6093 Err := Entity (End_Decl_Expr) /= Entity (Freeze_Expr);
6095 elsif A_Id = Aspect_Variable_Indexing or else
6096 A_Id = Aspect_Constant_Indexing or else
6097 A_Id = Aspect_Default_Iterator or else
6098 A_Id = Aspect_Iterator_Element
6099 then
6100 -- Make type unfrozen before analysis, to prevent spurious errors
6101 -- about late attributes.
6103 Set_Is_Frozen (Ent, False);
6104 Analyze (End_Decl_Expr);
6105 Analyze (Aspect_Rep_Item (ASN));
6106 Set_Is_Frozen (Ent, True);
6108 -- If the end of declarations comes before any other freeze
6109 -- point, the Freeze_Expr is not analyzed: no check needed.
6111 Err :=
6112 Analyzed (Freeze_Expr)
6113 and then not In_Instance
6114 and then Entity (End_Decl_Expr) /= Entity (Freeze_Expr);
6116 -- All other cases
6118 else
6119 -- In a generic context the aspect expressions have not been
6120 -- preanalyzed, so do it now. There are no conformance checks
6121 -- to perform in this case.
6123 if No (T) then
6124 Check_Aspect_At_Freeze_Point (ASN);
6125 return;
6127 -- The default values attributes may be defined in the private part,
6128 -- and the analysis of the expression may take place when only the
6129 -- partial view is visible. The expression must be scalar, so use
6130 -- the full view to resolve.
6132 elsif (A_Id = Aspect_Default_Value
6133 or else
6134 A_Id = Aspect_Default_Component_Value)
6135 and then Is_Private_Type (T)
6136 then
6137 Preanalyze_Spec_Expression (End_Decl_Expr, Full_View (T));
6138 else
6139 Preanalyze_Spec_Expression (End_Decl_Expr, T);
6140 end if;
6142 Err := not Fully_Conformant_Expressions (End_Decl_Expr, Freeze_Expr);
6143 end if;
6145 -- Output error message if error
6147 if Err then
6148 Error_Msg_NE
6149 ("visibility of aspect for& changes after freeze point",
6150 ASN, Ent);
6151 Error_Msg_NE
6152 ("?info: & is frozen here, aspects evaluated at this point",
6153 Freeze_Node (Ent), Ent);
6154 end if;
6155 end Check_Aspect_At_End_Of_Declarations;
6157 ----------------------------------
6158 -- Check_Aspect_At_Freeze_Point --
6159 ----------------------------------
6161 procedure Check_Aspect_At_Freeze_Point (ASN : Node_Id) is
6162 Ident : constant Node_Id := Identifier (ASN);
6163 -- Identifier (use Entity field to save expression)
6165 T : Entity_Id;
6166 -- Type required for preanalyze call
6168 A_Id : constant Aspect_Id := Get_Aspect_Id (Chars (Ident));
6170 begin
6171 -- On entry to this procedure, Entity (Ident) contains a copy of the
6172 -- original expression from the aspect, saved for this purpose.
6174 -- On exit from this procedure Entity (Ident) is unchanged, still
6175 -- containing that copy, but Expression (Ident) is a preanalyzed copy
6176 -- of the expression, preanalyzed just after the freeze point.
6178 -- Make a copy of the expression to be preanalyed
6180 Set_Expression (ASN, New_Copy_Tree (Entity (Ident)));
6182 -- Find type for preanalyze call
6184 case A_Id is
6186 -- No_Aspect should be impossible
6188 when No_Aspect =>
6189 raise Program_Error;
6191 -- Library unit aspects should be impossible (never delayed)
6193 when Library_Unit_Aspects =>
6194 raise Program_Error;
6196 -- Aspects taking an optional boolean argument. Should be impossible
6197 -- since these are never delayed.
6199 when Boolean_Aspects =>
6200 raise Program_Error;
6202 -- Contract_Case aspects apply to subprograms, hence should never be
6203 -- delayed.
6205 when Aspect_Contract_Case =>
6206 raise Program_Error;
6208 -- Test_Case aspects apply to entries and subprograms, hence should
6209 -- never be delayed.
6211 when Aspect_Test_Case =>
6212 raise Program_Error;
6214 when Aspect_Attach_Handler =>
6215 T := RTE (RE_Interrupt_ID);
6217 when Aspect_Convention =>
6218 null;
6220 -- Default_Value is resolved with the type entity in question
6222 when Aspect_Default_Value =>
6223 T := Entity (ASN);
6225 -- Default_Component_Value is resolved with the component type
6227 when Aspect_Default_Component_Value =>
6228 T := Component_Type (Entity (ASN));
6230 -- Aspects corresponding to attribute definition clauses
6232 when Aspect_Address =>
6233 T := RTE (RE_Address);
6235 when Aspect_Bit_Order | Aspect_Scalar_Storage_Order =>
6236 T := RTE (RE_Bit_Order);
6238 when Aspect_CPU =>
6239 T := RTE (RE_CPU_Range);
6241 when Aspect_Dispatching_Domain =>
6242 T := RTE (RE_Dispatching_Domain);
6244 when Aspect_External_Tag =>
6245 T := Standard_String;
6247 when Aspect_External_Name =>
6248 T := Standard_String;
6250 when Aspect_Link_Name =>
6251 T := Standard_String;
6253 when Aspect_Priority | Aspect_Interrupt_Priority =>
6254 T := Standard_Integer;
6256 when Aspect_Small =>
6257 T := Universal_Real;
6259 -- For a simple storage pool, we have to retrieve the type of the
6260 -- pool object associated with the aspect's corresponding attribute
6261 -- definition clause.
6263 when Aspect_Simple_Storage_Pool =>
6264 T := Etype (Expression (Aspect_Rep_Item (ASN)));
6266 when Aspect_Storage_Pool =>
6267 T := Class_Wide_Type (RTE (RE_Root_Storage_Pool));
6269 when Aspect_Alignment |
6270 Aspect_Component_Size |
6271 Aspect_Machine_Radix |
6272 Aspect_Object_Size |
6273 Aspect_Size |
6274 Aspect_Storage_Size |
6275 Aspect_Stream_Size |
6276 Aspect_Value_Size =>
6277 T := Any_Integer;
6279 -- Stream attribute. Special case, the expression is just an entity
6280 -- that does not need any resolution, so just analyze.
6282 when Aspect_Input |
6283 Aspect_Output |
6284 Aspect_Read |
6285 Aspect_Write =>
6286 Analyze (Expression (ASN));
6287 return;
6289 -- Same for Iterator aspects, where the expression is a function
6290 -- name. Legality rules are checked separately.
6292 when Aspect_Constant_Indexing |
6293 Aspect_Default_Iterator |
6294 Aspect_Iterator_Element |
6295 Aspect_Implicit_Dereference |
6296 Aspect_Variable_Indexing =>
6297 Analyze (Expression (ASN));
6298 return;
6300 -- Suppress/Unsuppress/Synchronization/Warnings should not be delayed
6302 when Aspect_Suppress |
6303 Aspect_Unsuppress |
6304 Aspect_Synchronization |
6305 Aspect_Warnings =>
6306 raise Program_Error;
6308 -- Pre/Post/Invariant/Predicate take boolean expressions
6310 when Aspect_Dynamic_Predicate |
6311 Aspect_Invariant |
6312 Aspect_Pre |
6313 Aspect_Precondition |
6314 Aspect_Post |
6315 Aspect_Postcondition |
6316 Aspect_Predicate |
6317 Aspect_Static_Predicate |
6318 Aspect_Type_Invariant =>
6319 T := Standard_Boolean;
6321 when Aspect_Dimension |
6322 Aspect_Dimension_System =>
6323 raise Program_Error;
6325 end case;
6327 -- Do the preanalyze call
6329 Preanalyze_Spec_Expression (Expression (ASN), T);
6330 end Check_Aspect_At_Freeze_Point;
6332 -----------------------------------
6333 -- Check_Constant_Address_Clause --
6334 -----------------------------------
6336 procedure Check_Constant_Address_Clause
6337 (Expr : Node_Id;
6338 U_Ent : Entity_Id)
6340 procedure Check_At_Constant_Address (Nod : Node_Id);
6341 -- Checks that the given node N represents a name whose 'Address is
6342 -- constant (in the same sense as OK_Constant_Address_Clause, i.e. the
6343 -- address value is the same at the point of declaration of U_Ent and at
6344 -- the time of elaboration of the address clause.
6346 procedure Check_Expr_Constants (Nod : Node_Id);
6347 -- Checks that Nod meets the requirements for a constant address clause
6348 -- in the sense of the enclosing procedure.
6350 procedure Check_List_Constants (Lst : List_Id);
6351 -- Check that all elements of list Lst meet the requirements for a
6352 -- constant address clause in the sense of the enclosing procedure.
6354 -------------------------------
6355 -- Check_At_Constant_Address --
6356 -------------------------------
6358 procedure Check_At_Constant_Address (Nod : Node_Id) is
6359 begin
6360 if Is_Entity_Name (Nod) then
6361 if Present (Address_Clause (Entity ((Nod)))) then
6362 Error_Msg_NE
6363 ("invalid address clause for initialized object &!",
6364 Nod, U_Ent);
6365 Error_Msg_NE
6366 ("address for& cannot" &
6367 " depend on another address clause! (RM 13.1(22))!",
6368 Nod, U_Ent);
6370 elsif In_Same_Source_Unit (Entity (Nod), U_Ent)
6371 and then Sloc (U_Ent) < Sloc (Entity (Nod))
6372 then
6373 Error_Msg_NE
6374 ("invalid address clause for initialized object &!",
6375 Nod, U_Ent);
6376 Error_Msg_Node_2 := U_Ent;
6377 Error_Msg_NE
6378 ("\& must be defined before & (RM 13.1(22))!",
6379 Nod, Entity (Nod));
6380 end if;
6382 elsif Nkind (Nod) = N_Selected_Component then
6383 declare
6384 T : constant Entity_Id := Etype (Prefix (Nod));
6386 begin
6387 if (Is_Record_Type (T)
6388 and then Has_Discriminants (T))
6389 or else
6390 (Is_Access_Type (T)
6391 and then Is_Record_Type (Designated_Type (T))
6392 and then Has_Discriminants (Designated_Type (T)))
6393 then
6394 Error_Msg_NE
6395 ("invalid address clause for initialized object &!",
6396 Nod, U_Ent);
6397 Error_Msg_N
6398 ("\address cannot depend on component" &
6399 " of discriminated record (RM 13.1(22))!",
6400 Nod);
6401 else
6402 Check_At_Constant_Address (Prefix (Nod));
6403 end if;
6404 end;
6406 elsif Nkind (Nod) = N_Indexed_Component then
6407 Check_At_Constant_Address (Prefix (Nod));
6408 Check_List_Constants (Expressions (Nod));
6410 else
6411 Check_Expr_Constants (Nod);
6412 end if;
6413 end Check_At_Constant_Address;
6415 --------------------------
6416 -- Check_Expr_Constants --
6417 --------------------------
6419 procedure Check_Expr_Constants (Nod : Node_Id) is
6420 Loc_U_Ent : constant Source_Ptr := Sloc (U_Ent);
6421 Ent : Entity_Id := Empty;
6423 begin
6424 if Nkind (Nod) in N_Has_Etype
6425 and then Etype (Nod) = Any_Type
6426 then
6427 return;
6428 end if;
6430 case Nkind (Nod) is
6431 when N_Empty | N_Error =>
6432 return;
6434 when N_Identifier | N_Expanded_Name =>
6435 Ent := Entity (Nod);
6437 -- We need to look at the original node if it is different
6438 -- from the node, since we may have rewritten things and
6439 -- substituted an identifier representing the rewrite.
6441 if Original_Node (Nod) /= Nod then
6442 Check_Expr_Constants (Original_Node (Nod));
6444 -- If the node is an object declaration without initial
6445 -- value, some code has been expanded, and the expression
6446 -- is not constant, even if the constituents might be
6447 -- acceptable, as in A'Address + offset.
6449 if Ekind (Ent) = E_Variable
6450 and then
6451 Nkind (Declaration_Node (Ent)) = N_Object_Declaration
6452 and then
6453 No (Expression (Declaration_Node (Ent)))
6454 then
6455 Error_Msg_NE
6456 ("invalid address clause for initialized object &!",
6457 Nod, U_Ent);
6459 -- If entity is constant, it may be the result of expanding
6460 -- a check. We must verify that its declaration appears
6461 -- before the object in question, else we also reject the
6462 -- address clause.
6464 elsif Ekind (Ent) = E_Constant
6465 and then In_Same_Source_Unit (Ent, U_Ent)
6466 and then Sloc (Ent) > Loc_U_Ent
6467 then
6468 Error_Msg_NE
6469 ("invalid address clause for initialized object &!",
6470 Nod, U_Ent);
6471 end if;
6473 return;
6474 end if;
6476 -- Otherwise look at the identifier and see if it is OK
6478 if Ekind_In (Ent, E_Named_Integer, E_Named_Real)
6479 or else Is_Type (Ent)
6480 then
6481 return;
6483 elsif
6484 Ekind (Ent) = E_Constant
6485 or else
6486 Ekind (Ent) = E_In_Parameter
6487 then
6488 -- This is the case where we must have Ent defined before
6489 -- U_Ent. Clearly if they are in different units this
6490 -- requirement is met since the unit containing Ent is
6491 -- already processed.
6493 if not In_Same_Source_Unit (Ent, U_Ent) then
6494 return;
6496 -- Otherwise location of Ent must be before the location
6497 -- of U_Ent, that's what prior defined means.
6499 elsif Sloc (Ent) < Loc_U_Ent then
6500 return;
6502 else
6503 Error_Msg_NE
6504 ("invalid address clause for initialized object &!",
6505 Nod, U_Ent);
6506 Error_Msg_Node_2 := U_Ent;
6507 Error_Msg_NE
6508 ("\& must be defined before & (RM 13.1(22))!",
6509 Nod, Ent);
6510 end if;
6512 elsif Nkind (Original_Node (Nod)) = N_Function_Call then
6513 Check_Expr_Constants (Original_Node (Nod));
6515 else
6516 Error_Msg_NE
6517 ("invalid address clause for initialized object &!",
6518 Nod, U_Ent);
6520 if Comes_From_Source (Ent) then
6521 Error_Msg_NE
6522 ("\reference to variable& not allowed"
6523 & " (RM 13.1(22))!", Nod, Ent);
6524 else
6525 Error_Msg_N
6526 ("non-static expression not allowed"
6527 & " (RM 13.1(22))!", Nod);
6528 end if;
6529 end if;
6531 when N_Integer_Literal =>
6533 -- If this is a rewritten unchecked conversion, in a system
6534 -- where Address is an integer type, always use the base type
6535 -- for a literal value. This is user-friendly and prevents
6536 -- order-of-elaboration issues with instances of unchecked
6537 -- conversion.
6539 if Nkind (Original_Node (Nod)) = N_Function_Call then
6540 Set_Etype (Nod, Base_Type (Etype (Nod)));
6541 end if;
6543 when N_Real_Literal |
6544 N_String_Literal |
6545 N_Character_Literal =>
6546 return;
6548 when N_Range =>
6549 Check_Expr_Constants (Low_Bound (Nod));
6550 Check_Expr_Constants (High_Bound (Nod));
6552 when N_Explicit_Dereference =>
6553 Check_Expr_Constants (Prefix (Nod));
6555 when N_Indexed_Component =>
6556 Check_Expr_Constants (Prefix (Nod));
6557 Check_List_Constants (Expressions (Nod));
6559 when N_Slice =>
6560 Check_Expr_Constants (Prefix (Nod));
6561 Check_Expr_Constants (Discrete_Range (Nod));
6563 when N_Selected_Component =>
6564 Check_Expr_Constants (Prefix (Nod));
6566 when N_Attribute_Reference =>
6567 if Attribute_Name (Nod) = Name_Address
6568 or else
6569 Attribute_Name (Nod) = Name_Access
6570 or else
6571 Attribute_Name (Nod) = Name_Unchecked_Access
6572 or else
6573 Attribute_Name (Nod) = Name_Unrestricted_Access
6574 then
6575 Check_At_Constant_Address (Prefix (Nod));
6577 else
6578 Check_Expr_Constants (Prefix (Nod));
6579 Check_List_Constants (Expressions (Nod));
6580 end if;
6582 when N_Aggregate =>
6583 Check_List_Constants (Component_Associations (Nod));
6584 Check_List_Constants (Expressions (Nod));
6586 when N_Component_Association =>
6587 Check_Expr_Constants (Expression (Nod));
6589 when N_Extension_Aggregate =>
6590 Check_Expr_Constants (Ancestor_Part (Nod));
6591 Check_List_Constants (Component_Associations (Nod));
6592 Check_List_Constants (Expressions (Nod));
6594 when N_Null =>
6595 return;
6597 when N_Binary_Op | N_Short_Circuit | N_Membership_Test =>
6598 Check_Expr_Constants (Left_Opnd (Nod));
6599 Check_Expr_Constants (Right_Opnd (Nod));
6601 when N_Unary_Op =>
6602 Check_Expr_Constants (Right_Opnd (Nod));
6604 when N_Type_Conversion |
6605 N_Qualified_Expression |
6606 N_Allocator =>
6607 Check_Expr_Constants (Expression (Nod));
6609 when N_Unchecked_Type_Conversion =>
6610 Check_Expr_Constants (Expression (Nod));
6612 -- If this is a rewritten unchecked conversion, subtypes in
6613 -- this node are those created within the instance. To avoid
6614 -- order of elaboration issues, replace them with their base
6615 -- types. Note that address clauses can cause order of
6616 -- elaboration problems because they are elaborated by the
6617 -- back-end at the point of definition, and may mention
6618 -- entities declared in between (as long as everything is
6619 -- static). It is user-friendly to allow unchecked conversions
6620 -- in this context.
6622 if Nkind (Original_Node (Nod)) = N_Function_Call then
6623 Set_Etype (Expression (Nod),
6624 Base_Type (Etype (Expression (Nod))));
6625 Set_Etype (Nod, Base_Type (Etype (Nod)));
6626 end if;
6628 when N_Function_Call =>
6629 if not Is_Pure (Entity (Name (Nod))) then
6630 Error_Msg_NE
6631 ("invalid address clause for initialized object &!",
6632 Nod, U_Ent);
6634 Error_Msg_NE
6635 ("\function & is not pure (RM 13.1(22))!",
6636 Nod, Entity (Name (Nod)));
6638 else
6639 Check_List_Constants (Parameter_Associations (Nod));
6640 end if;
6642 when N_Parameter_Association =>
6643 Check_Expr_Constants (Explicit_Actual_Parameter (Nod));
6645 when others =>
6646 Error_Msg_NE
6647 ("invalid address clause for initialized object &!",
6648 Nod, U_Ent);
6649 Error_Msg_NE
6650 ("\must be constant defined before& (RM 13.1(22))!",
6651 Nod, U_Ent);
6652 end case;
6653 end Check_Expr_Constants;
6655 --------------------------
6656 -- Check_List_Constants --
6657 --------------------------
6659 procedure Check_List_Constants (Lst : List_Id) is
6660 Nod1 : Node_Id;
6662 begin
6663 if Present (Lst) then
6664 Nod1 := First (Lst);
6665 while Present (Nod1) loop
6666 Check_Expr_Constants (Nod1);
6667 Next (Nod1);
6668 end loop;
6669 end if;
6670 end Check_List_Constants;
6672 -- Start of processing for Check_Constant_Address_Clause
6674 begin
6675 -- If rep_clauses are to be ignored, no need for legality checks. In
6676 -- particular, no need to pester user about rep clauses that violate
6677 -- the rule on constant addresses, given that these clauses will be
6678 -- removed by Freeze before they reach the back end.
6680 if not Ignore_Rep_Clauses then
6681 Check_Expr_Constants (Expr);
6682 end if;
6683 end Check_Constant_Address_Clause;
6685 ----------------------------------------
6686 -- Check_Record_Representation_Clause --
6687 ----------------------------------------
6689 procedure Check_Record_Representation_Clause (N : Node_Id) is
6690 Loc : constant Source_Ptr := Sloc (N);
6691 Ident : constant Node_Id := Identifier (N);
6692 Rectype : Entity_Id;
6693 Fent : Entity_Id;
6694 CC : Node_Id;
6695 Fbit : Uint;
6696 Lbit : Uint;
6697 Hbit : Uint := Uint_0;
6698 Comp : Entity_Id;
6699 Pcomp : Entity_Id;
6701 Max_Bit_So_Far : Uint;
6702 -- Records the maximum bit position so far. If all field positions
6703 -- are monotonically increasing, then we can skip the circuit for
6704 -- checking for overlap, since no overlap is possible.
6706 Tagged_Parent : Entity_Id := Empty;
6707 -- This is set in the case of a derived tagged type for which we have
6708 -- Is_Fully_Repped_Tagged_Type True (indicating that all components are
6709 -- positioned by record representation clauses). In this case we must
6710 -- check for overlap between components of this tagged type, and the
6711 -- components of its parent. Tagged_Parent will point to this parent
6712 -- type. For all other cases Tagged_Parent is left set to Empty.
6714 Parent_Last_Bit : Uint;
6715 -- Relevant only if Tagged_Parent is set, Parent_Last_Bit indicates the
6716 -- last bit position for any field in the parent type. We only need to
6717 -- check overlap for fields starting below this point.
6719 Overlap_Check_Required : Boolean;
6720 -- Used to keep track of whether or not an overlap check is required
6722 Overlap_Detected : Boolean := False;
6723 -- Set True if an overlap is detected
6725 Ccount : Natural := 0;
6726 -- Number of component clauses in record rep clause
6728 procedure Check_Component_Overlap (C1_Ent, C2_Ent : Entity_Id);
6729 -- Given two entities for record components or discriminants, checks
6730 -- if they have overlapping component clauses and issues errors if so.
6732 procedure Find_Component;
6733 -- Finds component entity corresponding to current component clause (in
6734 -- CC), and sets Comp to the entity, and Fbit/Lbit to the zero origin
6735 -- start/stop bits for the field. If there is no matching component or
6736 -- if the matching component does not have a component clause, then
6737 -- that's an error and Comp is set to Empty, but no error message is
6738 -- issued, since the message was already given. Comp is also set to
6739 -- Empty if the current "component clause" is in fact a pragma.
6741 -----------------------------
6742 -- Check_Component_Overlap --
6743 -----------------------------
6745 procedure Check_Component_Overlap (C1_Ent, C2_Ent : Entity_Id) is
6746 CC1 : constant Node_Id := Component_Clause (C1_Ent);
6747 CC2 : constant Node_Id := Component_Clause (C2_Ent);
6749 begin
6750 if Present (CC1) and then Present (CC2) then
6752 -- Exclude odd case where we have two tag fields in the same
6753 -- record, both at location zero. This seems a bit strange, but
6754 -- it seems to happen in some circumstances, perhaps on an error.
6756 if Chars (C1_Ent) = Name_uTag
6757 and then
6758 Chars (C2_Ent) = Name_uTag
6759 then
6760 return;
6761 end if;
6763 -- Here we check if the two fields overlap
6765 declare
6766 S1 : constant Uint := Component_Bit_Offset (C1_Ent);
6767 S2 : constant Uint := Component_Bit_Offset (C2_Ent);
6768 E1 : constant Uint := S1 + Esize (C1_Ent);
6769 E2 : constant Uint := S2 + Esize (C2_Ent);
6771 begin
6772 if E2 <= S1 or else E1 <= S2 then
6773 null;
6774 else
6775 Error_Msg_Node_2 := Component_Name (CC2);
6776 Error_Msg_Sloc := Sloc (Error_Msg_Node_2);
6777 Error_Msg_Node_1 := Component_Name (CC1);
6778 Error_Msg_N
6779 ("component& overlaps & #", Component_Name (CC1));
6780 Overlap_Detected := True;
6781 end if;
6782 end;
6783 end if;
6784 end Check_Component_Overlap;
6786 --------------------
6787 -- Find_Component --
6788 --------------------
6790 procedure Find_Component is
6792 procedure Search_Component (R : Entity_Id);
6793 -- Search components of R for a match. If found, Comp is set.
6795 ----------------------
6796 -- Search_Component --
6797 ----------------------
6799 procedure Search_Component (R : Entity_Id) is
6800 begin
6801 Comp := First_Component_Or_Discriminant (R);
6802 while Present (Comp) loop
6804 -- Ignore error of attribute name for component name (we
6805 -- already gave an error message for this, so no need to
6806 -- complain here)
6808 if Nkind (Component_Name (CC)) = N_Attribute_Reference then
6809 null;
6810 else
6811 exit when Chars (Comp) = Chars (Component_Name (CC));
6812 end if;
6814 Next_Component_Or_Discriminant (Comp);
6815 end loop;
6816 end Search_Component;
6818 -- Start of processing for Find_Component
6820 begin
6821 -- Return with Comp set to Empty if we have a pragma
6823 if Nkind (CC) = N_Pragma then
6824 Comp := Empty;
6825 return;
6826 end if;
6828 -- Search current record for matching component
6830 Search_Component (Rectype);
6832 -- If not found, maybe component of base type that is absent from
6833 -- statically constrained first subtype.
6835 if No (Comp) then
6836 Search_Component (Base_Type (Rectype));
6837 end if;
6839 -- If no component, or the component does not reference the component
6840 -- clause in question, then there was some previous error for which
6841 -- we already gave a message, so just return with Comp Empty.
6843 if No (Comp)
6844 or else Component_Clause (Comp) /= CC
6845 then
6846 Comp := Empty;
6848 -- Normal case where we have a component clause
6850 else
6851 Fbit := Component_Bit_Offset (Comp);
6852 Lbit := Fbit + Esize (Comp) - 1;
6853 end if;
6854 end Find_Component;
6856 -- Start of processing for Check_Record_Representation_Clause
6858 begin
6859 Find_Type (Ident);
6860 Rectype := Entity (Ident);
6862 if Rectype = Any_Type then
6863 return;
6864 else
6865 Rectype := Underlying_Type (Rectype);
6866 end if;
6868 -- See if we have a fully repped derived tagged type
6870 declare
6871 PS : constant Entity_Id := Parent_Subtype (Rectype);
6873 begin
6874 if Present (PS) and then Is_Fully_Repped_Tagged_Type (PS) then
6875 Tagged_Parent := PS;
6877 -- Find maximum bit of any component of the parent type
6879 Parent_Last_Bit := UI_From_Int (System_Address_Size - 1);
6880 Pcomp := First_Entity (Tagged_Parent);
6881 while Present (Pcomp) loop
6882 if Ekind_In (Pcomp, E_Discriminant, E_Component) then
6883 if Component_Bit_Offset (Pcomp) /= No_Uint
6884 and then Known_Static_Esize (Pcomp)
6885 then
6886 Parent_Last_Bit :=
6887 UI_Max
6888 (Parent_Last_Bit,
6889 Component_Bit_Offset (Pcomp) + Esize (Pcomp) - 1);
6890 end if;
6892 Next_Entity (Pcomp);
6893 end if;
6894 end loop;
6895 end if;
6896 end;
6898 -- All done if no component clauses
6900 CC := First (Component_Clauses (N));
6902 if No (CC) then
6903 return;
6904 end if;
6906 -- If a tag is present, then create a component clause that places it
6907 -- at the start of the record (otherwise gigi may place it after other
6908 -- fields that have rep clauses).
6910 Fent := First_Entity (Rectype);
6912 if Nkind (Fent) = N_Defining_Identifier
6913 and then Chars (Fent) = Name_uTag
6914 then
6915 Set_Component_Bit_Offset (Fent, Uint_0);
6916 Set_Normalized_Position (Fent, Uint_0);
6917 Set_Normalized_First_Bit (Fent, Uint_0);
6918 Set_Normalized_Position_Max (Fent, Uint_0);
6919 Init_Esize (Fent, System_Address_Size);
6921 Set_Component_Clause (Fent,
6922 Make_Component_Clause (Loc,
6923 Component_Name => Make_Identifier (Loc, Name_uTag),
6925 Position => Make_Integer_Literal (Loc, Uint_0),
6926 First_Bit => Make_Integer_Literal (Loc, Uint_0),
6927 Last_Bit =>
6928 Make_Integer_Literal (Loc,
6929 UI_From_Int (System_Address_Size))));
6931 Ccount := Ccount + 1;
6932 end if;
6934 Max_Bit_So_Far := Uint_Minus_1;
6935 Overlap_Check_Required := False;
6937 -- Process the component clauses
6939 while Present (CC) loop
6940 Find_Component;
6942 if Present (Comp) then
6943 Ccount := Ccount + 1;
6945 -- We need a full overlap check if record positions non-monotonic
6947 if Fbit <= Max_Bit_So_Far then
6948 Overlap_Check_Required := True;
6949 end if;
6951 Max_Bit_So_Far := Lbit;
6953 -- Check bit position out of range of specified size
6955 if Has_Size_Clause (Rectype)
6956 and then RM_Size (Rectype) <= Lbit
6957 then
6958 Error_Msg_N
6959 ("bit number out of range of specified size",
6960 Last_Bit (CC));
6962 -- Check for overlap with tag field
6964 else
6965 if Is_Tagged_Type (Rectype)
6966 and then Fbit < System_Address_Size
6967 then
6968 Error_Msg_NE
6969 ("component overlaps tag field of&",
6970 Component_Name (CC), Rectype);
6971 Overlap_Detected := True;
6972 end if;
6974 if Hbit < Lbit then
6975 Hbit := Lbit;
6976 end if;
6977 end if;
6979 -- Check parent overlap if component might overlap parent field
6981 if Present (Tagged_Parent)
6982 and then Fbit <= Parent_Last_Bit
6983 then
6984 Pcomp := First_Component_Or_Discriminant (Tagged_Parent);
6985 while Present (Pcomp) loop
6986 if not Is_Tag (Pcomp)
6987 and then Chars (Pcomp) /= Name_uParent
6988 then
6989 Check_Component_Overlap (Comp, Pcomp);
6990 end if;
6992 Next_Component_Or_Discriminant (Pcomp);
6993 end loop;
6994 end if;
6995 end if;
6997 Next (CC);
6998 end loop;
7000 -- Now that we have processed all the component clauses, check for
7001 -- overlap. We have to leave this till last, since the components can
7002 -- appear in any arbitrary order in the representation clause.
7004 -- We do not need this check if all specified ranges were monotonic,
7005 -- as recorded by Overlap_Check_Required being False at this stage.
7007 -- This first section checks if there are any overlapping entries at
7008 -- all. It does this by sorting all entries and then seeing if there are
7009 -- any overlaps. If there are none, then that is decisive, but if there
7010 -- are overlaps, they may still be OK (they may result from fields in
7011 -- different variants).
7013 if Overlap_Check_Required then
7014 Overlap_Check1 : declare
7016 OC_Fbit : array (0 .. Ccount) of Uint;
7017 -- First-bit values for component clauses, the value is the offset
7018 -- of the first bit of the field from start of record. The zero
7019 -- entry is for use in sorting.
7021 OC_Lbit : array (0 .. Ccount) of Uint;
7022 -- Last-bit values for component clauses, the value is the offset
7023 -- of the last bit of the field from start of record. The zero
7024 -- entry is for use in sorting.
7026 OC_Count : Natural := 0;
7027 -- Count of entries in OC_Fbit and OC_Lbit
7029 function OC_Lt (Op1, Op2 : Natural) return Boolean;
7030 -- Compare routine for Sort
7032 procedure OC_Move (From : Natural; To : Natural);
7033 -- Move routine for Sort
7035 package Sorting is new GNAT.Heap_Sort_G (OC_Move, OC_Lt);
7037 -----------
7038 -- OC_Lt --
7039 -----------
7041 function OC_Lt (Op1, Op2 : Natural) return Boolean is
7042 begin
7043 return OC_Fbit (Op1) < OC_Fbit (Op2);
7044 end OC_Lt;
7046 -------------
7047 -- OC_Move --
7048 -------------
7050 procedure OC_Move (From : Natural; To : Natural) is
7051 begin
7052 OC_Fbit (To) := OC_Fbit (From);
7053 OC_Lbit (To) := OC_Lbit (From);
7054 end OC_Move;
7056 -- Start of processing for Overlap_Check
7058 begin
7059 CC := First (Component_Clauses (N));
7060 while Present (CC) loop
7062 -- Exclude component clause already marked in error
7064 if not Error_Posted (CC) then
7065 Find_Component;
7067 if Present (Comp) then
7068 OC_Count := OC_Count + 1;
7069 OC_Fbit (OC_Count) := Fbit;
7070 OC_Lbit (OC_Count) := Lbit;
7071 end if;
7072 end if;
7074 Next (CC);
7075 end loop;
7077 Sorting.Sort (OC_Count);
7079 Overlap_Check_Required := False;
7080 for J in 1 .. OC_Count - 1 loop
7081 if OC_Lbit (J) >= OC_Fbit (J + 1) then
7082 Overlap_Check_Required := True;
7083 exit;
7084 end if;
7085 end loop;
7086 end Overlap_Check1;
7087 end if;
7089 -- If Overlap_Check_Required is still True, then we have to do the full
7090 -- scale overlap check, since we have at least two fields that do
7091 -- overlap, and we need to know if that is OK since they are in
7092 -- different variant, or whether we have a definite problem.
7094 if Overlap_Check_Required then
7095 Overlap_Check2 : declare
7096 C1_Ent, C2_Ent : Entity_Id;
7097 -- Entities of components being checked for overlap
7099 Clist : Node_Id;
7100 -- Component_List node whose Component_Items are being checked
7102 Citem : Node_Id;
7103 -- Component declaration for component being checked
7105 begin
7106 C1_Ent := First_Entity (Base_Type (Rectype));
7108 -- Loop through all components in record. For each component check
7109 -- for overlap with any of the preceding elements on the component
7110 -- list containing the component and also, if the component is in
7111 -- a variant, check against components outside the case structure.
7112 -- This latter test is repeated recursively up the variant tree.
7114 Main_Component_Loop : while Present (C1_Ent) loop
7115 if not Ekind_In (C1_Ent, E_Component, E_Discriminant) then
7116 goto Continue_Main_Component_Loop;
7117 end if;
7119 -- Skip overlap check if entity has no declaration node. This
7120 -- happens with discriminants in constrained derived types.
7121 -- Possibly we are missing some checks as a result, but that
7122 -- does not seem terribly serious.
7124 if No (Declaration_Node (C1_Ent)) then
7125 goto Continue_Main_Component_Loop;
7126 end if;
7128 Clist := Parent (List_Containing (Declaration_Node (C1_Ent)));
7130 -- Loop through component lists that need checking. Check the
7131 -- current component list and all lists in variants above us.
7133 Component_List_Loop : loop
7135 -- If derived type definition, go to full declaration
7136 -- If at outer level, check discriminants if there are any.
7138 if Nkind (Clist) = N_Derived_Type_Definition then
7139 Clist := Parent (Clist);
7140 end if;
7142 -- Outer level of record definition, check discriminants
7144 if Nkind_In (Clist, N_Full_Type_Declaration,
7145 N_Private_Type_Declaration)
7146 then
7147 if Has_Discriminants (Defining_Identifier (Clist)) then
7148 C2_Ent :=
7149 First_Discriminant (Defining_Identifier (Clist));
7150 while Present (C2_Ent) loop
7151 exit when C1_Ent = C2_Ent;
7152 Check_Component_Overlap (C1_Ent, C2_Ent);
7153 Next_Discriminant (C2_Ent);
7154 end loop;
7155 end if;
7157 -- Record extension case
7159 elsif Nkind (Clist) = N_Derived_Type_Definition then
7160 Clist := Empty;
7162 -- Otherwise check one component list
7164 else
7165 Citem := First (Component_Items (Clist));
7166 while Present (Citem) loop
7167 if Nkind (Citem) = N_Component_Declaration then
7168 C2_Ent := Defining_Identifier (Citem);
7169 exit when C1_Ent = C2_Ent;
7170 Check_Component_Overlap (C1_Ent, C2_Ent);
7171 end if;
7173 Next (Citem);
7174 end loop;
7175 end if;
7177 -- Check for variants above us (the parent of the Clist can
7178 -- be a variant, in which case its parent is a variant part,
7179 -- and the parent of the variant part is a component list
7180 -- whose components must all be checked against the current
7181 -- component for overlap).
7183 if Nkind (Parent (Clist)) = N_Variant then
7184 Clist := Parent (Parent (Parent (Clist)));
7186 -- Check for possible discriminant part in record, this
7187 -- is treated essentially as another level in the
7188 -- recursion. For this case the parent of the component
7189 -- list is the record definition, and its parent is the
7190 -- full type declaration containing the discriminant
7191 -- specifications.
7193 elsif Nkind (Parent (Clist)) = N_Record_Definition then
7194 Clist := Parent (Parent ((Clist)));
7196 -- If neither of these two cases, we are at the top of
7197 -- the tree.
7199 else
7200 exit Component_List_Loop;
7201 end if;
7202 end loop Component_List_Loop;
7204 <<Continue_Main_Component_Loop>>
7205 Next_Entity (C1_Ent);
7207 end loop Main_Component_Loop;
7208 end Overlap_Check2;
7209 end if;
7211 -- The following circuit deals with warning on record holes (gaps). We
7212 -- skip this check if overlap was detected, since it makes sense for the
7213 -- programmer to fix this illegality before worrying about warnings.
7215 if not Overlap_Detected and Warn_On_Record_Holes then
7216 Record_Hole_Check : declare
7217 Decl : constant Node_Id := Declaration_Node (Base_Type (Rectype));
7218 -- Full declaration of record type
7220 procedure Check_Component_List
7221 (CL : Node_Id;
7222 Sbit : Uint;
7223 DS : List_Id);
7224 -- Check component list CL for holes. The starting bit should be
7225 -- Sbit. which is zero for the main record component list and set
7226 -- appropriately for recursive calls for variants. DS is set to
7227 -- a list of discriminant specifications to be included in the
7228 -- consideration of components. It is No_List if none to consider.
7230 --------------------------
7231 -- Check_Component_List --
7232 --------------------------
7234 procedure Check_Component_List
7235 (CL : Node_Id;
7236 Sbit : Uint;
7237 DS : List_Id)
7239 Compl : Integer;
7241 begin
7242 Compl := Integer (List_Length (Component_Items (CL)));
7244 if DS /= No_List then
7245 Compl := Compl + Integer (List_Length (DS));
7246 end if;
7248 declare
7249 Comps : array (Natural range 0 .. Compl) of Entity_Id;
7250 -- Gather components (zero entry is for sort routine)
7252 Ncomps : Natural := 0;
7253 -- Number of entries stored in Comps (starting at Comps (1))
7255 Citem : Node_Id;
7256 -- One component item or discriminant specification
7258 Nbit : Uint;
7259 -- Starting bit for next component
7261 CEnt : Entity_Id;
7262 -- Component entity
7264 Variant : Node_Id;
7265 -- One variant
7267 function Lt (Op1, Op2 : Natural) return Boolean;
7268 -- Compare routine for Sort
7270 procedure Move (From : Natural; To : Natural);
7271 -- Move routine for Sort
7273 package Sorting is new GNAT.Heap_Sort_G (Move, Lt);
7275 --------
7276 -- Lt --
7277 --------
7279 function Lt (Op1, Op2 : Natural) return Boolean is
7280 begin
7281 return Component_Bit_Offset (Comps (Op1))
7283 Component_Bit_Offset (Comps (Op2));
7284 end Lt;
7286 ----------
7287 -- Move --
7288 ----------
7290 procedure Move (From : Natural; To : Natural) is
7291 begin
7292 Comps (To) := Comps (From);
7293 end Move;
7295 begin
7296 -- Gather discriminants into Comp
7298 if DS /= No_List then
7299 Citem := First (DS);
7300 while Present (Citem) loop
7301 if Nkind (Citem) = N_Discriminant_Specification then
7302 declare
7303 Ent : constant Entity_Id :=
7304 Defining_Identifier (Citem);
7305 begin
7306 if Ekind (Ent) = E_Discriminant then
7307 Ncomps := Ncomps + 1;
7308 Comps (Ncomps) := Ent;
7309 end if;
7310 end;
7311 end if;
7313 Next (Citem);
7314 end loop;
7315 end if;
7317 -- Gather component entities into Comp
7319 Citem := First (Component_Items (CL));
7320 while Present (Citem) loop
7321 if Nkind (Citem) = N_Component_Declaration then
7322 Ncomps := Ncomps + 1;
7323 Comps (Ncomps) := Defining_Identifier (Citem);
7324 end if;
7326 Next (Citem);
7327 end loop;
7329 -- Now sort the component entities based on the first bit.
7330 -- Note we already know there are no overlapping components.
7332 Sorting.Sort (Ncomps);
7334 -- Loop through entries checking for holes
7336 Nbit := Sbit;
7337 for J in 1 .. Ncomps loop
7338 CEnt := Comps (J);
7339 Error_Msg_Uint_1 := Component_Bit_Offset (CEnt) - Nbit;
7341 if Error_Msg_Uint_1 > 0 then
7342 Error_Msg_NE
7343 ("?^-bit gap before component&",
7344 Component_Name (Component_Clause (CEnt)), CEnt);
7345 end if;
7347 Nbit := Component_Bit_Offset (CEnt) + Esize (CEnt);
7348 end loop;
7350 -- Process variant parts recursively if present
7352 if Present (Variant_Part (CL)) then
7353 Variant := First (Variants (Variant_Part (CL)));
7354 while Present (Variant) loop
7355 Check_Component_List
7356 (Component_List (Variant), Nbit, No_List);
7357 Next (Variant);
7358 end loop;
7359 end if;
7360 end;
7361 end Check_Component_List;
7363 -- Start of processing for Record_Hole_Check
7365 begin
7366 declare
7367 Sbit : Uint;
7369 begin
7370 if Is_Tagged_Type (Rectype) then
7371 Sbit := UI_From_Int (System_Address_Size);
7372 else
7373 Sbit := Uint_0;
7374 end if;
7376 if Nkind (Decl) = N_Full_Type_Declaration
7377 and then Nkind (Type_Definition (Decl)) = N_Record_Definition
7378 then
7379 Check_Component_List
7380 (Component_List (Type_Definition (Decl)),
7381 Sbit,
7382 Discriminant_Specifications (Decl));
7383 end if;
7384 end;
7385 end Record_Hole_Check;
7386 end if;
7388 -- For records that have component clauses for all components, and whose
7389 -- size is less than or equal to 32, we need to know the size in the
7390 -- front end to activate possible packed array processing where the
7391 -- component type is a record.
7393 -- At this stage Hbit + 1 represents the first unused bit from all the
7394 -- component clauses processed, so if the component clauses are
7395 -- complete, then this is the length of the record.
7397 -- For records longer than System.Storage_Unit, and for those where not
7398 -- all components have component clauses, the back end determines the
7399 -- length (it may for example be appropriate to round up the size
7400 -- to some convenient boundary, based on alignment considerations, etc).
7402 if Unknown_RM_Size (Rectype) and then Hbit + 1 <= 32 then
7404 -- Nothing to do if at least one component has no component clause
7406 Comp := First_Component_Or_Discriminant (Rectype);
7407 while Present (Comp) loop
7408 exit when No (Component_Clause (Comp));
7409 Next_Component_Or_Discriminant (Comp);
7410 end loop;
7412 -- If we fall out of loop, all components have component clauses
7413 -- and so we can set the size to the maximum value.
7415 if No (Comp) then
7416 Set_RM_Size (Rectype, Hbit + 1);
7417 end if;
7418 end if;
7419 end Check_Record_Representation_Clause;
7421 ----------------
7422 -- Check_Size --
7423 ----------------
7425 procedure Check_Size
7426 (N : Node_Id;
7427 T : Entity_Id;
7428 Siz : Uint;
7429 Biased : out Boolean)
7431 UT : constant Entity_Id := Underlying_Type (T);
7432 M : Uint;
7434 begin
7435 Biased := False;
7437 -- Dismiss cases for generic types or types with previous errors
7439 if No (UT)
7440 or else UT = Any_Type
7441 or else Is_Generic_Type (UT)
7442 or else Is_Generic_Type (Root_Type (UT))
7443 then
7444 return;
7446 -- Check case of bit packed array
7448 elsif Is_Array_Type (UT)
7449 and then Known_Static_Component_Size (UT)
7450 and then Is_Bit_Packed_Array (UT)
7451 then
7452 declare
7453 Asiz : Uint;
7454 Indx : Node_Id;
7455 Ityp : Entity_Id;
7457 begin
7458 Asiz := Component_Size (UT);
7459 Indx := First_Index (UT);
7460 loop
7461 Ityp := Etype (Indx);
7463 -- If non-static bound, then we are not in the business of
7464 -- trying to check the length, and indeed an error will be
7465 -- issued elsewhere, since sizes of non-static array types
7466 -- cannot be set implicitly or explicitly.
7468 if not Is_Static_Subtype (Ityp) then
7469 return;
7470 end if;
7472 -- Otherwise accumulate next dimension
7474 Asiz := Asiz * (Expr_Value (Type_High_Bound (Ityp)) -
7475 Expr_Value (Type_Low_Bound (Ityp)) +
7476 Uint_1);
7478 Next_Index (Indx);
7479 exit when No (Indx);
7480 end loop;
7482 if Asiz <= Siz then
7483 return;
7484 else
7485 Error_Msg_Uint_1 := Asiz;
7486 Error_Msg_NE
7487 ("size for& too small, minimum allowed is ^", N, T);
7488 Set_Esize (T, Asiz);
7489 Set_RM_Size (T, Asiz);
7490 end if;
7491 end;
7493 -- All other composite types are ignored
7495 elsif Is_Composite_Type (UT) then
7496 return;
7498 -- For fixed-point types, don't check minimum if type is not frozen,
7499 -- since we don't know all the characteristics of the type that can
7500 -- affect the size (e.g. a specified small) till freeze time.
7502 elsif Is_Fixed_Point_Type (UT)
7503 and then not Is_Frozen (UT)
7504 then
7505 null;
7507 -- Cases for which a minimum check is required
7509 else
7510 -- Ignore if specified size is correct for the type
7512 if Known_Esize (UT) and then Siz = Esize (UT) then
7513 return;
7514 end if;
7516 -- Otherwise get minimum size
7518 M := UI_From_Int (Minimum_Size (UT));
7520 if Siz < M then
7522 -- Size is less than minimum size, but one possibility remains
7523 -- that we can manage with the new size if we bias the type.
7525 M := UI_From_Int (Minimum_Size (UT, Biased => True));
7527 if Siz < M then
7528 Error_Msg_Uint_1 := M;
7529 Error_Msg_NE
7530 ("size for& too small, minimum allowed is ^", N, T);
7531 Set_Esize (T, M);
7532 Set_RM_Size (T, M);
7533 else
7534 Biased := True;
7535 end if;
7536 end if;
7537 end if;
7538 end Check_Size;
7540 -------------------------
7541 -- Get_Alignment_Value --
7542 -------------------------
7544 function Get_Alignment_Value (Expr : Node_Id) return Uint is
7545 Align : constant Uint := Static_Integer (Expr);
7547 begin
7548 if Align = No_Uint then
7549 return No_Uint;
7551 elsif Align <= 0 then
7552 Error_Msg_N ("alignment value must be positive", Expr);
7553 return No_Uint;
7555 else
7556 for J in Int range 0 .. 64 loop
7557 declare
7558 M : constant Uint := Uint_2 ** J;
7560 begin
7561 exit when M = Align;
7563 if M > Align then
7564 Error_Msg_N
7565 ("alignment value must be power of 2", Expr);
7566 return No_Uint;
7567 end if;
7568 end;
7569 end loop;
7571 return Align;
7572 end if;
7573 end Get_Alignment_Value;
7575 ----------------
7576 -- Initialize --
7577 ----------------
7579 procedure Initialize is
7580 begin
7581 Address_Clause_Checks.Init;
7582 Independence_Checks.Init;
7583 Unchecked_Conversions.Init;
7584 end Initialize;
7586 -------------------------
7587 -- Is_Operational_Item --
7588 -------------------------
7590 function Is_Operational_Item (N : Node_Id) return Boolean is
7591 begin
7592 if Nkind (N) /= N_Attribute_Definition_Clause then
7593 return False;
7594 else
7595 declare
7596 Id : constant Attribute_Id := Get_Attribute_Id (Chars (N));
7597 begin
7598 return Id = Attribute_Input
7599 or else Id = Attribute_Output
7600 or else Id = Attribute_Read
7601 or else Id = Attribute_Write
7602 or else Id = Attribute_External_Tag;
7603 end;
7604 end if;
7605 end Is_Operational_Item;
7607 ------------------
7608 -- Minimum_Size --
7609 ------------------
7611 function Minimum_Size
7612 (T : Entity_Id;
7613 Biased : Boolean := False) return Nat
7615 Lo : Uint := No_Uint;
7616 Hi : Uint := No_Uint;
7617 LoR : Ureal := No_Ureal;
7618 HiR : Ureal := No_Ureal;
7619 LoSet : Boolean := False;
7620 HiSet : Boolean := False;
7621 B : Uint;
7622 S : Nat;
7623 Ancest : Entity_Id;
7624 R_Typ : constant Entity_Id := Root_Type (T);
7626 begin
7627 -- If bad type, return 0
7629 if T = Any_Type then
7630 return 0;
7632 -- For generic types, just return zero. There cannot be any legitimate
7633 -- need to know such a size, but this routine may be called with a
7634 -- generic type as part of normal processing.
7636 elsif Is_Generic_Type (R_Typ)
7637 or else R_Typ = Any_Type
7638 then
7639 return 0;
7641 -- Access types. Normally an access type cannot have a size smaller
7642 -- than the size of System.Address. The exception is on VMS, where
7643 -- we have short and long addresses, and it is possible for an access
7644 -- type to have a short address size (and thus be less than the size
7645 -- of System.Address itself). We simply skip the check for VMS, and
7646 -- leave it to the back end to do the check.
7648 elsif Is_Access_Type (T) then
7649 if OpenVMS_On_Target then
7650 return 0;
7651 else
7652 return System_Address_Size;
7653 end if;
7655 -- Floating-point types
7657 elsif Is_Floating_Point_Type (T) then
7658 return UI_To_Int (Esize (R_Typ));
7660 -- Discrete types
7662 elsif Is_Discrete_Type (T) then
7664 -- The following loop is looking for the nearest compile time known
7665 -- bounds following the ancestor subtype chain. The idea is to find
7666 -- the most restrictive known bounds information.
7668 Ancest := T;
7669 loop
7670 if Ancest = Any_Type or else Etype (Ancest) = Any_Type then
7671 return 0;
7672 end if;
7674 if not LoSet then
7675 if Compile_Time_Known_Value (Type_Low_Bound (Ancest)) then
7676 Lo := Expr_Rep_Value (Type_Low_Bound (Ancest));
7677 LoSet := True;
7678 exit when HiSet;
7679 end if;
7680 end if;
7682 if not HiSet then
7683 if Compile_Time_Known_Value (Type_High_Bound (Ancest)) then
7684 Hi := Expr_Rep_Value (Type_High_Bound (Ancest));
7685 HiSet := True;
7686 exit when LoSet;
7687 end if;
7688 end if;
7690 Ancest := Ancestor_Subtype (Ancest);
7692 if No (Ancest) then
7693 Ancest := Base_Type (T);
7695 if Is_Generic_Type (Ancest) then
7696 return 0;
7697 end if;
7698 end if;
7699 end loop;
7701 -- Fixed-point types. We can't simply use Expr_Value to get the
7702 -- Corresponding_Integer_Value values of the bounds, since these do not
7703 -- get set till the type is frozen, and this routine can be called
7704 -- before the type is frozen. Similarly the test for bounds being static
7705 -- needs to include the case where we have unanalyzed real literals for
7706 -- the same reason.
7708 elsif Is_Fixed_Point_Type (T) then
7710 -- The following loop is looking for the nearest compile time known
7711 -- bounds following the ancestor subtype chain. The idea is to find
7712 -- the most restrictive known bounds information.
7714 Ancest := T;
7715 loop
7716 if Ancest = Any_Type or else Etype (Ancest) = Any_Type then
7717 return 0;
7718 end if;
7720 -- Note: In the following two tests for LoSet and HiSet, it may
7721 -- seem redundant to test for N_Real_Literal here since normally
7722 -- one would assume that the test for the value being known at
7723 -- compile time includes this case. However, there is a glitch.
7724 -- If the real literal comes from folding a non-static expression,
7725 -- then we don't consider any non- static expression to be known
7726 -- at compile time if we are in configurable run time mode (needed
7727 -- in some cases to give a clearer definition of what is and what
7728 -- is not accepted). So the test is indeed needed. Without it, we
7729 -- would set neither Lo_Set nor Hi_Set and get an infinite loop.
7731 if not LoSet then
7732 if Nkind (Type_Low_Bound (Ancest)) = N_Real_Literal
7733 or else Compile_Time_Known_Value (Type_Low_Bound (Ancest))
7734 then
7735 LoR := Expr_Value_R (Type_Low_Bound (Ancest));
7736 LoSet := True;
7737 exit when HiSet;
7738 end if;
7739 end if;
7741 if not HiSet then
7742 if Nkind (Type_High_Bound (Ancest)) = N_Real_Literal
7743 or else Compile_Time_Known_Value (Type_High_Bound (Ancest))
7744 then
7745 HiR := Expr_Value_R (Type_High_Bound (Ancest));
7746 HiSet := True;
7747 exit when LoSet;
7748 end if;
7749 end if;
7751 Ancest := Ancestor_Subtype (Ancest);
7753 if No (Ancest) then
7754 Ancest := Base_Type (T);
7756 if Is_Generic_Type (Ancest) then
7757 return 0;
7758 end if;
7759 end if;
7760 end loop;
7762 Lo := UR_To_Uint (LoR / Small_Value (T));
7763 Hi := UR_To_Uint (HiR / Small_Value (T));
7765 -- No other types allowed
7767 else
7768 raise Program_Error;
7769 end if;
7771 -- Fall through with Hi and Lo set. Deal with biased case
7773 if (Biased
7774 and then not Is_Fixed_Point_Type (T)
7775 and then not (Is_Enumeration_Type (T)
7776 and then Has_Non_Standard_Rep (T)))
7777 or else Has_Biased_Representation (T)
7778 then
7779 Hi := Hi - Lo;
7780 Lo := Uint_0;
7781 end if;
7783 -- Signed case. Note that we consider types like range 1 .. -1 to be
7784 -- signed for the purpose of computing the size, since the bounds have
7785 -- to be accommodated in the base type.
7787 if Lo < 0 or else Hi < 0 then
7788 S := 1;
7789 B := Uint_1;
7791 -- S = size, B = 2 ** (size - 1) (can accommodate -B .. +(B - 1))
7792 -- Note that we accommodate the case where the bounds cross. This
7793 -- can happen either because of the way the bounds are declared
7794 -- or because of the algorithm in Freeze_Fixed_Point_Type.
7796 while Lo < -B
7797 or else Hi < -B
7798 or else Lo >= B
7799 or else Hi >= B
7800 loop
7801 B := Uint_2 ** S;
7802 S := S + 1;
7803 end loop;
7805 -- Unsigned case
7807 else
7808 -- If both bounds are positive, make sure that both are represen-
7809 -- table in the case where the bounds are crossed. This can happen
7810 -- either because of the way the bounds are declared, or because of
7811 -- the algorithm in Freeze_Fixed_Point_Type.
7813 if Lo > Hi then
7814 Hi := Lo;
7815 end if;
7817 -- S = size, (can accommodate 0 .. (2**size - 1))
7819 S := 0;
7820 while Hi >= Uint_2 ** S loop
7821 S := S + 1;
7822 end loop;
7823 end if;
7825 return S;
7826 end Minimum_Size;
7828 ---------------------------
7829 -- New_Stream_Subprogram --
7830 ---------------------------
7832 procedure New_Stream_Subprogram
7833 (N : Node_Id;
7834 Ent : Entity_Id;
7835 Subp : Entity_Id;
7836 Nam : TSS_Name_Type)
7838 Loc : constant Source_Ptr := Sloc (N);
7839 Sname : constant Name_Id := Make_TSS_Name (Base_Type (Ent), Nam);
7840 Subp_Id : Entity_Id;
7841 Subp_Decl : Node_Id;
7842 F : Entity_Id;
7843 Etyp : Entity_Id;
7845 Defer_Declaration : constant Boolean :=
7846 Is_Tagged_Type (Ent) or else Is_Private_Type (Ent);
7847 -- For a tagged type, there is a declaration for each stream attribute
7848 -- at the freeze point, and we must generate only a completion of this
7849 -- declaration. We do the same for private types, because the full view
7850 -- might be tagged. Otherwise we generate a declaration at the point of
7851 -- the attribute definition clause.
7853 function Build_Spec return Node_Id;
7854 -- Used for declaration and renaming declaration, so that this is
7855 -- treated as a renaming_as_body.
7857 ----------------
7858 -- Build_Spec --
7859 ----------------
7861 function Build_Spec return Node_Id is
7862 Out_P : constant Boolean := (Nam = TSS_Stream_Read);
7863 Formals : List_Id;
7864 Spec : Node_Id;
7865 T_Ref : constant Node_Id := New_Reference_To (Etyp, Loc);
7867 begin
7868 Subp_Id := Make_Defining_Identifier (Loc, Sname);
7870 -- S : access Root_Stream_Type'Class
7872 Formals := New_List (
7873 Make_Parameter_Specification (Loc,
7874 Defining_Identifier =>
7875 Make_Defining_Identifier (Loc, Name_S),
7876 Parameter_Type =>
7877 Make_Access_Definition (Loc,
7878 Subtype_Mark =>
7879 New_Reference_To (
7880 Designated_Type (Etype (F)), Loc))));
7882 if Nam = TSS_Stream_Input then
7883 Spec := Make_Function_Specification (Loc,
7884 Defining_Unit_Name => Subp_Id,
7885 Parameter_Specifications => Formals,
7886 Result_Definition => T_Ref);
7887 else
7888 -- V : [out] T
7890 Append_To (Formals,
7891 Make_Parameter_Specification (Loc,
7892 Defining_Identifier => Make_Defining_Identifier (Loc, Name_V),
7893 Out_Present => Out_P,
7894 Parameter_Type => T_Ref));
7896 Spec :=
7897 Make_Procedure_Specification (Loc,
7898 Defining_Unit_Name => Subp_Id,
7899 Parameter_Specifications => Formals);
7900 end if;
7902 return Spec;
7903 end Build_Spec;
7905 -- Start of processing for New_Stream_Subprogram
7907 begin
7908 F := First_Formal (Subp);
7910 if Ekind (Subp) = E_Procedure then
7911 Etyp := Etype (Next_Formal (F));
7912 else
7913 Etyp := Etype (Subp);
7914 end if;
7916 -- Prepare subprogram declaration and insert it as an action on the
7917 -- clause node. The visibility for this entity is used to test for
7918 -- visibility of the attribute definition clause (in the sense of
7919 -- 8.3(23) as amended by AI-195).
7921 if not Defer_Declaration then
7922 Subp_Decl :=
7923 Make_Subprogram_Declaration (Loc,
7924 Specification => Build_Spec);
7926 -- For a tagged type, there is always a visible declaration for each
7927 -- stream TSS (it is a predefined primitive operation), and the
7928 -- completion of this declaration occurs at the freeze point, which is
7929 -- not always visible at places where the attribute definition clause is
7930 -- visible. So, we create a dummy entity here for the purpose of
7931 -- tracking the visibility of the attribute definition clause itself.
7933 else
7934 Subp_Id :=
7935 Make_Defining_Identifier (Loc, New_External_Name (Sname, 'V'));
7936 Subp_Decl :=
7937 Make_Object_Declaration (Loc,
7938 Defining_Identifier => Subp_Id,
7939 Object_Definition => New_Occurrence_Of (Standard_Boolean, Loc));
7940 end if;
7942 Insert_Action (N, Subp_Decl);
7943 Set_Entity (N, Subp_Id);
7945 Subp_Decl :=
7946 Make_Subprogram_Renaming_Declaration (Loc,
7947 Specification => Build_Spec,
7948 Name => New_Reference_To (Subp, Loc));
7950 if Defer_Declaration then
7951 Set_TSS (Base_Type (Ent), Subp_Id);
7952 else
7953 Insert_Action (N, Subp_Decl);
7954 Copy_TSS (Subp_Id, Base_Type (Ent));
7955 end if;
7956 end New_Stream_Subprogram;
7958 ------------------------
7959 -- Rep_Item_Too_Early --
7960 ------------------------
7962 function Rep_Item_Too_Early (T : Entity_Id; N : Node_Id) return Boolean is
7963 begin
7964 -- Cannot apply non-operational rep items to generic types
7966 if Is_Operational_Item (N) then
7967 return False;
7969 elsif Is_Type (T)
7970 and then Is_Generic_Type (Root_Type (T))
7971 then
7972 Error_Msg_N ("representation item not allowed for generic type", N);
7973 return True;
7974 end if;
7976 -- Otherwise check for incomplete type
7978 if Is_Incomplete_Or_Private_Type (T)
7979 and then No (Underlying_Type (T))
7980 and then
7981 (Nkind (N) /= N_Pragma
7982 or else Get_Pragma_Id (N) /= Pragma_Import)
7983 then
7984 Error_Msg_N
7985 ("representation item must be after full type declaration", N);
7986 return True;
7988 -- If the type has incomplete components, a representation clause is
7989 -- illegal but stream attributes and Convention pragmas are correct.
7991 elsif Has_Private_Component (T) then
7992 if Nkind (N) = N_Pragma then
7993 return False;
7994 else
7995 Error_Msg_N
7996 ("representation item must appear after type is fully defined",
7998 return True;
7999 end if;
8000 else
8001 return False;
8002 end if;
8003 end Rep_Item_Too_Early;
8005 -----------------------
8006 -- Rep_Item_Too_Late --
8007 -----------------------
8009 function Rep_Item_Too_Late
8010 (T : Entity_Id;
8011 N : Node_Id;
8012 FOnly : Boolean := False) return Boolean
8014 S : Entity_Id;
8015 Parent_Type : Entity_Id;
8017 procedure Too_Late;
8018 -- Output the too late message. Note that this is not considered a
8019 -- serious error, since the effect is simply that we ignore the
8020 -- representation clause in this case.
8022 --------------
8023 -- Too_Late --
8024 --------------
8026 procedure Too_Late is
8027 begin
8028 Error_Msg_N ("|representation item appears too late!", N);
8029 end Too_Late;
8031 -- Start of processing for Rep_Item_Too_Late
8033 begin
8034 -- First make sure entity is not frozen (RM 13.1(9))
8036 if Is_Frozen (T)
8038 -- Exclude imported types, which may be frozen if they appear in a
8039 -- representation clause for a local type.
8041 and then not From_With_Type (T)
8043 -- Exclude generated entitiesa (not coming from source). The common
8044 -- case is when we generate a renaming which prematurely freezes the
8045 -- renamed internal entity, but we still want to be able to set copies
8046 -- of attribute values such as Size/Alignment.
8048 and then Comes_From_Source (T)
8049 then
8050 Too_Late;
8051 S := First_Subtype (T);
8053 if Present (Freeze_Node (S)) then
8054 Error_Msg_NE
8055 ("?no more representation items for }", Freeze_Node (S), S);
8056 end if;
8058 return True;
8060 -- Check for case of non-tagged derived type whose parent either has
8061 -- primitive operations, or is a by reference type (RM 13.1(10)).
8063 elsif Is_Type (T)
8064 and then not FOnly
8065 and then Is_Derived_Type (T)
8066 and then not Is_Tagged_Type (T)
8067 then
8068 Parent_Type := Etype (Base_Type (T));
8070 if Has_Primitive_Operations (Parent_Type) then
8071 Too_Late;
8072 Error_Msg_NE
8073 ("primitive operations already defined for&!", N, Parent_Type);
8074 return True;
8076 elsif Is_By_Reference_Type (Parent_Type) then
8077 Too_Late;
8078 Error_Msg_NE
8079 ("parent type & is a by reference type!", N, Parent_Type);
8080 return True;
8081 end if;
8082 end if;
8084 -- No error, link item into head of chain of rep items for the entity,
8085 -- but avoid chaining if we have an overloadable entity, and the pragma
8086 -- is one that can apply to multiple overloaded entities.
8088 if Is_Overloadable (T)
8089 and then Nkind (N) = N_Pragma
8090 then
8091 declare
8092 Pname : constant Name_Id := Pragma_Name (N);
8093 begin
8094 if Pname = Name_Convention or else
8095 Pname = Name_Import or else
8096 Pname = Name_Export or else
8097 Pname = Name_External or else
8098 Pname = Name_Interface
8099 then
8100 return False;
8101 end if;
8102 end;
8103 end if;
8105 Record_Rep_Item (T, N);
8106 return False;
8107 end Rep_Item_Too_Late;
8109 -------------------------------------
8110 -- Replace_Type_References_Generic --
8111 -------------------------------------
8113 procedure Replace_Type_References_Generic (N : Node_Id; TName : Name_Id) is
8115 function Replace_Node (N : Node_Id) return Traverse_Result;
8116 -- Processes a single node in the traversal procedure below, checking
8117 -- if node N should be replaced, and if so, doing the replacement.
8119 procedure Replace_Type_Refs is new Traverse_Proc (Replace_Node);
8120 -- This instantiation provides the body of Replace_Type_References
8122 ------------------
8123 -- Replace_Node --
8124 ------------------
8126 function Replace_Node (N : Node_Id) return Traverse_Result is
8127 S : Entity_Id;
8128 P : Node_Id;
8130 begin
8131 -- Case of identifier
8133 if Nkind (N) = N_Identifier then
8135 -- If not the type name, all done with this node
8137 if Chars (N) /= TName then
8138 return Skip;
8140 -- Otherwise do the replacement and we are done with this node
8142 else
8143 Replace_Type_Reference (N);
8144 return Skip;
8145 end if;
8147 -- Case of selected component (which is what a qualification
8148 -- looks like in the unanalyzed tree, which is what we have.
8150 elsif Nkind (N) = N_Selected_Component then
8152 -- If selector name is not our type, keeping going (we might
8153 -- still have an occurrence of the type in the prefix).
8155 if Nkind (Selector_Name (N)) /= N_Identifier
8156 or else Chars (Selector_Name (N)) /= TName
8157 then
8158 return OK;
8160 -- Selector name is our type, check qualification
8162 else
8163 -- Loop through scopes and prefixes, doing comparison
8165 S := Current_Scope;
8166 P := Prefix (N);
8167 loop
8168 -- Continue if no more scopes or scope with no name
8170 if No (S) or else Nkind (S) not in N_Has_Chars then
8171 return OK;
8172 end if;
8174 -- Do replace if prefix is an identifier matching the
8175 -- scope that we are currently looking at.
8177 if Nkind (P) = N_Identifier
8178 and then Chars (P) = Chars (S)
8179 then
8180 Replace_Type_Reference (N);
8181 return Skip;
8182 end if;
8184 -- Go check scope above us if prefix is itself of the
8185 -- form of a selected component, whose selector matches
8186 -- the scope we are currently looking at.
8188 if Nkind (P) = N_Selected_Component
8189 and then Nkind (Selector_Name (P)) = N_Identifier
8190 and then Chars (Selector_Name (P)) = Chars (S)
8191 then
8192 S := Scope (S);
8193 P := Prefix (P);
8195 -- For anything else, we don't have a match, so keep on
8196 -- going, there are still some weird cases where we may
8197 -- still have a replacement within the prefix.
8199 else
8200 return OK;
8201 end if;
8202 end loop;
8203 end if;
8205 -- Continue for any other node kind
8207 else
8208 return OK;
8209 end if;
8210 end Replace_Node;
8212 begin
8213 Replace_Type_Refs (N);
8214 end Replace_Type_References_Generic;
8216 -------------------------
8217 -- Same_Representation --
8218 -------------------------
8220 function Same_Representation (Typ1, Typ2 : Entity_Id) return Boolean is
8221 T1 : constant Entity_Id := Underlying_Type (Typ1);
8222 T2 : constant Entity_Id := Underlying_Type (Typ2);
8224 begin
8225 -- A quick check, if base types are the same, then we definitely have
8226 -- the same representation, because the subtype specific representation
8227 -- attributes (Size and Alignment) do not affect representation from
8228 -- the point of view of this test.
8230 if Base_Type (T1) = Base_Type (T2) then
8231 return True;
8233 elsif Is_Private_Type (Base_Type (T2))
8234 and then Base_Type (T1) = Full_View (Base_Type (T2))
8235 then
8236 return True;
8237 end if;
8239 -- Tagged types never have differing representations
8241 if Is_Tagged_Type (T1) then
8242 return True;
8243 end if;
8245 -- Representations are definitely different if conventions differ
8247 if Convention (T1) /= Convention (T2) then
8248 return False;
8249 end if;
8251 -- Representations are different if component alignments differ
8253 if (Is_Record_Type (T1) or else Is_Array_Type (T1))
8254 and then
8255 (Is_Record_Type (T2) or else Is_Array_Type (T2))
8256 and then Component_Alignment (T1) /= Component_Alignment (T2)
8257 then
8258 return False;
8259 end if;
8261 -- For arrays, the only real issue is component size. If we know the
8262 -- component size for both arrays, and it is the same, then that's
8263 -- good enough to know we don't have a change of representation.
8265 if Is_Array_Type (T1) then
8266 if Known_Component_Size (T1)
8267 and then Known_Component_Size (T2)
8268 and then Component_Size (T1) = Component_Size (T2)
8269 then
8270 if VM_Target = No_VM then
8271 return True;
8273 -- In VM targets the representation of arrays with aliased
8274 -- components differs from arrays with non-aliased components
8276 else
8277 return Has_Aliased_Components (Base_Type (T1))
8279 Has_Aliased_Components (Base_Type (T2));
8280 end if;
8281 end if;
8282 end if;
8284 -- Types definitely have same representation if neither has non-standard
8285 -- representation since default representations are always consistent.
8286 -- If only one has non-standard representation, and the other does not,
8287 -- then we consider that they do not have the same representation. They
8288 -- might, but there is no way of telling early enough.
8290 if Has_Non_Standard_Rep (T1) then
8291 if not Has_Non_Standard_Rep (T2) then
8292 return False;
8293 end if;
8294 else
8295 return not Has_Non_Standard_Rep (T2);
8296 end if;
8298 -- Here the two types both have non-standard representation, and we need
8299 -- to determine if they have the same non-standard representation.
8301 -- For arrays, we simply need to test if the component sizes are the
8302 -- same. Pragma Pack is reflected in modified component sizes, so this
8303 -- check also deals with pragma Pack.
8305 if Is_Array_Type (T1) then
8306 return Component_Size (T1) = Component_Size (T2);
8308 -- Tagged types always have the same representation, because it is not
8309 -- possible to specify different representations for common fields.
8311 elsif Is_Tagged_Type (T1) then
8312 return True;
8314 -- Case of record types
8316 elsif Is_Record_Type (T1) then
8318 -- Packed status must conform
8320 if Is_Packed (T1) /= Is_Packed (T2) then
8321 return False;
8323 -- Otherwise we must check components. Typ2 maybe a constrained
8324 -- subtype with fewer components, so we compare the components
8325 -- of the base types.
8327 else
8328 Record_Case : declare
8329 CD1, CD2 : Entity_Id;
8331 function Same_Rep return Boolean;
8332 -- CD1 and CD2 are either components or discriminants. This
8333 -- function tests whether the two have the same representation
8335 --------------
8336 -- Same_Rep --
8337 --------------
8339 function Same_Rep return Boolean is
8340 begin
8341 if No (Component_Clause (CD1)) then
8342 return No (Component_Clause (CD2));
8344 else
8345 return
8346 Present (Component_Clause (CD2))
8347 and then
8348 Component_Bit_Offset (CD1) = Component_Bit_Offset (CD2)
8349 and then
8350 Esize (CD1) = Esize (CD2);
8351 end if;
8352 end Same_Rep;
8354 -- Start of processing for Record_Case
8356 begin
8357 if Has_Discriminants (T1) then
8358 CD1 := First_Discriminant (T1);
8359 CD2 := First_Discriminant (T2);
8361 -- The number of discriminants may be different if the
8362 -- derived type has fewer (constrained by values). The
8363 -- invisible discriminants retain the representation of
8364 -- the original, so the discrepancy does not per se
8365 -- indicate a different representation.
8367 while Present (CD1)
8368 and then Present (CD2)
8369 loop
8370 if not Same_Rep then
8371 return False;
8372 else
8373 Next_Discriminant (CD1);
8374 Next_Discriminant (CD2);
8375 end if;
8376 end loop;
8377 end if;
8379 CD1 := First_Component (Underlying_Type (Base_Type (T1)));
8380 CD2 := First_Component (Underlying_Type (Base_Type (T2)));
8382 while Present (CD1) loop
8383 if not Same_Rep then
8384 return False;
8385 else
8386 Next_Component (CD1);
8387 Next_Component (CD2);
8388 end if;
8389 end loop;
8391 return True;
8392 end Record_Case;
8393 end if;
8395 -- For enumeration types, we must check each literal to see if the
8396 -- representation is the same. Note that we do not permit enumeration
8397 -- representation clauses for Character and Wide_Character, so these
8398 -- cases were already dealt with.
8400 elsif Is_Enumeration_Type (T1) then
8401 Enumeration_Case : declare
8402 L1, L2 : Entity_Id;
8404 begin
8405 L1 := First_Literal (T1);
8406 L2 := First_Literal (T2);
8408 while Present (L1) loop
8409 if Enumeration_Rep (L1) /= Enumeration_Rep (L2) then
8410 return False;
8411 else
8412 Next_Literal (L1);
8413 Next_Literal (L2);
8414 end if;
8415 end loop;
8417 return True;
8419 end Enumeration_Case;
8421 -- Any other types have the same representation for these purposes
8423 else
8424 return True;
8425 end if;
8426 end Same_Representation;
8428 ----------------
8429 -- Set_Biased --
8430 ----------------
8432 procedure Set_Biased
8433 (E : Entity_Id;
8434 N : Node_Id;
8435 Msg : String;
8436 Biased : Boolean := True)
8438 begin
8439 if Biased then
8440 Set_Has_Biased_Representation (E);
8442 if Warn_On_Biased_Representation then
8443 Error_Msg_NE
8444 ("?" & Msg & " forces biased representation for&", N, E);
8445 end if;
8446 end if;
8447 end Set_Biased;
8449 --------------------
8450 -- Set_Enum_Esize --
8451 --------------------
8453 procedure Set_Enum_Esize (T : Entity_Id) is
8454 Lo : Uint;
8455 Hi : Uint;
8456 Sz : Nat;
8458 begin
8459 Init_Alignment (T);
8461 -- Find the minimum standard size (8,16,32,64) that fits
8463 Lo := Enumeration_Rep (Entity (Type_Low_Bound (T)));
8464 Hi := Enumeration_Rep (Entity (Type_High_Bound (T)));
8466 if Lo < 0 then
8467 if Lo >= -Uint_2**07 and then Hi < Uint_2**07 then
8468 Sz := Standard_Character_Size; -- May be > 8 on some targets
8470 elsif Lo >= -Uint_2**15 and then Hi < Uint_2**15 then
8471 Sz := 16;
8473 elsif Lo >= -Uint_2**31 and then Hi < Uint_2**31 then
8474 Sz := 32;
8476 else pragma Assert (Lo >= -Uint_2**63 and then Hi < Uint_2**63);
8477 Sz := 64;
8478 end if;
8480 else
8481 if Hi < Uint_2**08 then
8482 Sz := Standard_Character_Size; -- May be > 8 on some targets
8484 elsif Hi < Uint_2**16 then
8485 Sz := 16;
8487 elsif Hi < Uint_2**32 then
8488 Sz := 32;
8490 else pragma Assert (Hi < Uint_2**63);
8491 Sz := 64;
8492 end if;
8493 end if;
8495 -- That minimum is the proper size unless we have a foreign convention
8496 -- and the size required is 32 or less, in which case we bump the size
8497 -- up to 32. This is required for C and C++ and seems reasonable for
8498 -- all other foreign conventions.
8500 if Has_Foreign_Convention (T)
8501 and then Esize (T) < Standard_Integer_Size
8502 then
8503 Init_Esize (T, Standard_Integer_Size);
8504 else
8505 Init_Esize (T, Sz);
8506 end if;
8507 end Set_Enum_Esize;
8509 ------------------------------
8510 -- Validate_Address_Clauses --
8511 ------------------------------
8513 procedure Validate_Address_Clauses is
8514 begin
8515 for J in Address_Clause_Checks.First .. Address_Clause_Checks.Last loop
8516 declare
8517 ACCR : Address_Clause_Check_Record
8518 renames Address_Clause_Checks.Table (J);
8520 Expr : Node_Id;
8522 X_Alignment : Uint;
8523 Y_Alignment : Uint;
8525 X_Size : Uint;
8526 Y_Size : Uint;
8528 begin
8529 -- Skip processing of this entry if warning already posted
8531 if not Address_Warning_Posted (ACCR.N) then
8533 Expr := Original_Node (Expression (ACCR.N));
8535 -- Get alignments
8537 X_Alignment := Alignment (ACCR.X);
8538 Y_Alignment := Alignment (ACCR.Y);
8540 -- Similarly obtain sizes
8542 X_Size := Esize (ACCR.X);
8543 Y_Size := Esize (ACCR.Y);
8545 -- Check for large object overlaying smaller one
8547 if Y_Size > Uint_0
8548 and then X_Size > Uint_0
8549 and then X_Size > Y_Size
8550 then
8551 Error_Msg_NE
8552 ("?& overlays smaller object", ACCR.N, ACCR.X);
8553 Error_Msg_N
8554 ("\?program execution may be erroneous", ACCR.N);
8555 Error_Msg_Uint_1 := X_Size;
8556 Error_Msg_NE
8557 ("\?size of & is ^", ACCR.N, ACCR.X);
8558 Error_Msg_Uint_1 := Y_Size;
8559 Error_Msg_NE
8560 ("\?size of & is ^", ACCR.N, ACCR.Y);
8562 -- Check for inadequate alignment, both of the base object
8563 -- and of the offset, if any.
8565 -- Note: we do not check the alignment if we gave a size
8566 -- warning, since it would likely be redundant.
8568 elsif Y_Alignment /= Uint_0
8569 and then (Y_Alignment < X_Alignment
8570 or else (ACCR.Off
8571 and then
8572 Nkind (Expr) = N_Attribute_Reference
8573 and then
8574 Attribute_Name (Expr) = Name_Address
8575 and then
8576 Has_Compatible_Alignment
8577 (ACCR.X, Prefix (Expr))
8578 /= Known_Compatible))
8579 then
8580 Error_Msg_NE
8581 ("?specified address for& may be inconsistent "
8582 & "with alignment",
8583 ACCR.N, ACCR.X);
8584 Error_Msg_N
8585 ("\?program execution may be erroneous (RM 13.3(27))",
8586 ACCR.N);
8587 Error_Msg_Uint_1 := X_Alignment;
8588 Error_Msg_NE
8589 ("\?alignment of & is ^",
8590 ACCR.N, ACCR.X);
8591 Error_Msg_Uint_1 := Y_Alignment;
8592 Error_Msg_NE
8593 ("\?alignment of & is ^",
8594 ACCR.N, ACCR.Y);
8595 if Y_Alignment >= X_Alignment then
8596 Error_Msg_N
8597 ("\?but offset is not multiple of alignment",
8598 ACCR.N);
8599 end if;
8600 end if;
8601 end if;
8602 end;
8603 end loop;
8604 end Validate_Address_Clauses;
8606 ---------------------------
8607 -- Validate_Independence --
8608 ---------------------------
8610 procedure Validate_Independence is
8611 SU : constant Uint := UI_From_Int (System_Storage_Unit);
8612 N : Node_Id;
8613 E : Entity_Id;
8614 IC : Boolean;
8615 Comp : Entity_Id;
8616 Addr : Node_Id;
8617 P : Node_Id;
8619 procedure Check_Array_Type (Atyp : Entity_Id);
8620 -- Checks if the array type Atyp has independent components, and
8621 -- if not, outputs an appropriate set of error messages.
8623 procedure No_Independence;
8624 -- Output message that independence cannot be guaranteed
8626 function OK_Component (C : Entity_Id) return Boolean;
8627 -- Checks one component to see if it is independently accessible, and
8628 -- if so yields True, otherwise yields False if independent access
8629 -- cannot be guaranteed. This is a conservative routine, it only
8630 -- returns True if it knows for sure, it returns False if it knows
8631 -- there is a problem, or it cannot be sure there is no problem.
8633 procedure Reason_Bad_Component (C : Entity_Id);
8634 -- Outputs continuation message if a reason can be determined for
8635 -- the component C being bad.
8637 ----------------------
8638 -- Check_Array_Type --
8639 ----------------------
8641 procedure Check_Array_Type (Atyp : Entity_Id) is
8642 Ctyp : constant Entity_Id := Component_Type (Atyp);
8644 begin
8645 -- OK if no alignment clause, no pack, and no component size
8647 if not Has_Component_Size_Clause (Atyp)
8648 and then not Has_Alignment_Clause (Atyp)
8649 and then not Is_Packed (Atyp)
8650 then
8651 return;
8652 end if;
8654 -- Check actual component size
8656 if not Known_Component_Size (Atyp)
8657 or else not (Addressable (Component_Size (Atyp))
8658 and then Component_Size (Atyp) < 64)
8659 or else Component_Size (Atyp) mod Esize (Ctyp) /= 0
8660 then
8661 No_Independence;
8663 -- Bad component size, check reason
8665 if Has_Component_Size_Clause (Atyp) then
8666 P :=
8667 Get_Attribute_Definition_Clause
8668 (Atyp, Attribute_Component_Size);
8670 if Present (P) then
8671 Error_Msg_Sloc := Sloc (P);
8672 Error_Msg_N ("\because of Component_Size clause#", N);
8673 return;
8674 end if;
8675 end if;
8677 if Is_Packed (Atyp) then
8678 P := Get_Rep_Pragma (Atyp, Name_Pack);
8680 if Present (P) then
8681 Error_Msg_Sloc := Sloc (P);
8682 Error_Msg_N ("\because of pragma Pack#", N);
8683 return;
8684 end if;
8685 end if;
8687 -- No reason found, just return
8689 return;
8690 end if;
8692 -- Array type is OK independence-wise
8694 return;
8695 end Check_Array_Type;
8697 ---------------------
8698 -- No_Independence --
8699 ---------------------
8701 procedure No_Independence is
8702 begin
8703 if Pragma_Name (N) = Name_Independent then
8704 Error_Msg_NE
8705 ("independence cannot be guaranteed for&", N, E);
8706 else
8707 Error_Msg_NE
8708 ("independent components cannot be guaranteed for&", N, E);
8709 end if;
8710 end No_Independence;
8712 ------------------
8713 -- OK_Component --
8714 ------------------
8716 function OK_Component (C : Entity_Id) return Boolean is
8717 Rec : constant Entity_Id := Scope (C);
8718 Ctyp : constant Entity_Id := Etype (C);
8720 begin
8721 -- OK if no component clause, no Pack, and no alignment clause
8723 if No (Component_Clause (C))
8724 and then not Is_Packed (Rec)
8725 and then not Has_Alignment_Clause (Rec)
8726 then
8727 return True;
8728 end if;
8730 -- Here we look at the actual component layout. A component is
8731 -- addressable if its size is a multiple of the Esize of the
8732 -- component type, and its starting position in the record has
8733 -- appropriate alignment, and the record itself has appropriate
8734 -- alignment to guarantee the component alignment.
8736 -- Make sure sizes are static, always assume the worst for any
8737 -- cases where we cannot check static values.
8739 if not (Known_Static_Esize (C)
8740 and then Known_Static_Esize (Ctyp))
8741 then
8742 return False;
8743 end if;
8745 -- Size of component must be addressable or greater than 64 bits
8746 -- and a multiple of bytes.
8748 if not Addressable (Esize (C))
8749 and then Esize (C) < Uint_64
8750 then
8751 return False;
8752 end if;
8754 -- Check size is proper multiple
8756 if Esize (C) mod Esize (Ctyp) /= 0 then
8757 return False;
8758 end if;
8760 -- Check alignment of component is OK
8762 if not Known_Component_Bit_Offset (C)
8763 or else Component_Bit_Offset (C) < Uint_0
8764 or else Component_Bit_Offset (C) mod Esize (Ctyp) /= 0
8765 then
8766 return False;
8767 end if;
8769 -- Check alignment of record type is OK
8771 if not Known_Alignment (Rec)
8772 or else (Alignment (Rec) * SU) mod Esize (Ctyp) /= 0
8773 then
8774 return False;
8775 end if;
8777 -- All tests passed, component is addressable
8779 return True;
8780 end OK_Component;
8782 --------------------------
8783 -- Reason_Bad_Component --
8784 --------------------------
8786 procedure Reason_Bad_Component (C : Entity_Id) is
8787 Rec : constant Entity_Id := Scope (C);
8788 Ctyp : constant Entity_Id := Etype (C);
8790 begin
8791 -- If component clause present assume that's the problem
8793 if Present (Component_Clause (C)) then
8794 Error_Msg_Sloc := Sloc (Component_Clause (C));
8795 Error_Msg_N ("\because of Component_Clause#", N);
8796 return;
8797 end if;
8799 -- If pragma Pack clause present, assume that's the problem
8801 if Is_Packed (Rec) then
8802 P := Get_Rep_Pragma (Rec, Name_Pack);
8804 if Present (P) then
8805 Error_Msg_Sloc := Sloc (P);
8806 Error_Msg_N ("\because of pragma Pack#", N);
8807 return;
8808 end if;
8809 end if;
8811 -- See if record has bad alignment clause
8813 if Has_Alignment_Clause (Rec)
8814 and then Known_Alignment (Rec)
8815 and then (Alignment (Rec) * SU) mod Esize (Ctyp) /= 0
8816 then
8817 P := Get_Attribute_Definition_Clause (Rec, Attribute_Alignment);
8819 if Present (P) then
8820 Error_Msg_Sloc := Sloc (P);
8821 Error_Msg_N ("\because of Alignment clause#", N);
8822 end if;
8823 end if;
8825 -- Couldn't find a reason, so return without a message
8827 return;
8828 end Reason_Bad_Component;
8830 -- Start of processing for Validate_Independence
8832 begin
8833 for J in Independence_Checks.First .. Independence_Checks.Last loop
8834 N := Independence_Checks.Table (J).N;
8835 E := Independence_Checks.Table (J).E;
8836 IC := Pragma_Name (N) = Name_Independent_Components;
8838 -- Deal with component case
8840 if Ekind (E) = E_Discriminant or else Ekind (E) = E_Component then
8841 if not OK_Component (E) then
8842 No_Independence;
8843 Reason_Bad_Component (E);
8844 goto Continue;
8845 end if;
8846 end if;
8848 -- Deal with record with Independent_Components
8850 if IC and then Is_Record_Type (E) then
8851 Comp := First_Component_Or_Discriminant (E);
8852 while Present (Comp) loop
8853 if not OK_Component (Comp) then
8854 No_Independence;
8855 Reason_Bad_Component (Comp);
8856 goto Continue;
8857 end if;
8859 Next_Component_Or_Discriminant (Comp);
8860 end loop;
8861 end if;
8863 -- Deal with address clause case
8865 if Is_Object (E) then
8866 Addr := Address_Clause (E);
8868 if Present (Addr) then
8869 No_Independence;
8870 Error_Msg_Sloc := Sloc (Addr);
8871 Error_Msg_N ("\because of Address clause#", N);
8872 goto Continue;
8873 end if;
8874 end if;
8876 -- Deal with independent components for array type
8878 if IC and then Is_Array_Type (E) then
8879 Check_Array_Type (E);
8880 end if;
8882 -- Deal with independent components for array object
8884 if IC and then Is_Object (E) and then Is_Array_Type (Etype (E)) then
8885 Check_Array_Type (Etype (E));
8886 end if;
8888 <<Continue>> null;
8889 end loop;
8890 end Validate_Independence;
8892 -----------------------------------
8893 -- Validate_Unchecked_Conversion --
8894 -----------------------------------
8896 procedure Validate_Unchecked_Conversion
8897 (N : Node_Id;
8898 Act_Unit : Entity_Id)
8900 Source : Entity_Id;
8901 Target : Entity_Id;
8902 Vnode : Node_Id;
8904 begin
8905 -- Obtain source and target types. Note that we call Ancestor_Subtype
8906 -- here because the processing for generic instantiation always makes
8907 -- subtypes, and we want the original frozen actual types.
8909 -- If we are dealing with private types, then do the check on their
8910 -- fully declared counterparts if the full declarations have been
8911 -- encountered (they don't have to be visible, but they must exist!)
8913 Source := Ancestor_Subtype (Etype (First_Formal (Act_Unit)));
8915 if Is_Private_Type (Source)
8916 and then Present (Underlying_Type (Source))
8917 then
8918 Source := Underlying_Type (Source);
8919 end if;
8921 Target := Ancestor_Subtype (Etype (Act_Unit));
8923 -- If either type is generic, the instantiation happens within a generic
8924 -- unit, and there is nothing to check. The proper check will happen
8925 -- when the enclosing generic is instantiated.
8927 if Is_Generic_Type (Source) or else Is_Generic_Type (Target) then
8928 return;
8929 end if;
8931 if Is_Private_Type (Target)
8932 and then Present (Underlying_Type (Target))
8933 then
8934 Target := Underlying_Type (Target);
8935 end if;
8937 -- Source may be unconstrained array, but not target
8939 if Is_Array_Type (Target)
8940 and then not Is_Constrained (Target)
8941 then
8942 Error_Msg_N
8943 ("unchecked conversion to unconstrained array not allowed", N);
8944 return;
8945 end if;
8947 -- Warn if conversion between two different convention pointers
8949 if Is_Access_Type (Target)
8950 and then Is_Access_Type (Source)
8951 and then Convention (Target) /= Convention (Source)
8952 and then Warn_On_Unchecked_Conversion
8953 then
8954 -- Give warnings for subprogram pointers only on most targets. The
8955 -- exception is VMS, where data pointers can have different lengths
8956 -- depending on the pointer convention.
8958 if Is_Access_Subprogram_Type (Target)
8959 or else Is_Access_Subprogram_Type (Source)
8960 or else OpenVMS_On_Target
8961 then
8962 Error_Msg_N
8963 ("?conversion between pointers with different conventions!", N);
8964 end if;
8965 end if;
8967 -- Warn if one of the operands is Ada.Calendar.Time. Do not emit a
8968 -- warning when compiling GNAT-related sources.
8970 if Warn_On_Unchecked_Conversion
8971 and then not In_Predefined_Unit (N)
8972 and then RTU_Loaded (Ada_Calendar)
8973 and then
8974 (Chars (Source) = Name_Time
8975 or else
8976 Chars (Target) = Name_Time)
8977 then
8978 -- If Ada.Calendar is loaded and the name of one of the operands is
8979 -- Time, there is a good chance that this is Ada.Calendar.Time.
8981 declare
8982 Calendar_Time : constant Entity_Id :=
8983 Full_View (RTE (RO_CA_Time));
8984 begin
8985 pragma Assert (Present (Calendar_Time));
8987 if Source = Calendar_Time
8988 or else Target = Calendar_Time
8989 then
8990 Error_Msg_N
8991 ("?representation of 'Time values may change between " &
8992 "'G'N'A'T versions", N);
8993 end if;
8994 end;
8995 end if;
8997 -- Make entry in unchecked conversion table for later processing by
8998 -- Validate_Unchecked_Conversions, which will check sizes and alignments
8999 -- (using values set by the back-end where possible). This is only done
9000 -- if the appropriate warning is active.
9002 if Warn_On_Unchecked_Conversion then
9003 Unchecked_Conversions.Append
9004 (New_Val => UC_Entry'
9005 (Eloc => Sloc (N),
9006 Source => Source,
9007 Target => Target));
9009 -- If both sizes are known statically now, then back end annotation
9010 -- is not required to do a proper check but if either size is not
9011 -- known statically, then we need the annotation.
9013 if Known_Static_RM_Size (Source)
9014 and then Known_Static_RM_Size (Target)
9015 then
9016 null;
9017 else
9018 Back_Annotate_Rep_Info := True;
9019 end if;
9020 end if;
9022 -- If unchecked conversion to access type, and access type is declared
9023 -- in the same unit as the unchecked conversion, then set the flag
9024 -- No_Strict_Aliasing (no strict aliasing is implicit here)
9026 if Is_Access_Type (Target) and then
9027 In_Same_Source_Unit (Target, N)
9028 then
9029 Set_No_Strict_Aliasing (Implementation_Base_Type (Target));
9030 end if;
9032 -- Generate N_Validate_Unchecked_Conversion node for back end in case
9033 -- the back end needs to perform special validation checks.
9035 -- Shouldn't this be in Exp_Ch13, since the check only gets done if we
9036 -- have full expansion and the back end is called ???
9038 Vnode :=
9039 Make_Validate_Unchecked_Conversion (Sloc (N));
9040 Set_Source_Type (Vnode, Source);
9041 Set_Target_Type (Vnode, Target);
9043 -- If the unchecked conversion node is in a list, just insert before it.
9044 -- If not we have some strange case, not worth bothering about.
9046 if Is_List_Member (N) then
9047 Insert_After (N, Vnode);
9048 end if;
9049 end Validate_Unchecked_Conversion;
9051 ------------------------------------
9052 -- Validate_Unchecked_Conversions --
9053 ------------------------------------
9055 procedure Validate_Unchecked_Conversions is
9056 begin
9057 for N in Unchecked_Conversions.First .. Unchecked_Conversions.Last loop
9058 declare
9059 T : UC_Entry renames Unchecked_Conversions.Table (N);
9061 Eloc : constant Source_Ptr := T.Eloc;
9062 Source : constant Entity_Id := T.Source;
9063 Target : constant Entity_Id := T.Target;
9065 Source_Siz : Uint;
9066 Target_Siz : Uint;
9068 begin
9069 -- This validation check, which warns if we have unequal sizes for
9070 -- unchecked conversion, and thus potentially implementation
9071 -- dependent semantics, is one of the few occasions on which we
9072 -- use the official RM size instead of Esize. See description in
9073 -- Einfo "Handling of Type'Size Values" for details.
9075 if Serious_Errors_Detected = 0
9076 and then Known_Static_RM_Size (Source)
9077 and then Known_Static_RM_Size (Target)
9079 -- Don't do the check if warnings off for either type, note the
9080 -- deliberate use of OR here instead of OR ELSE to get the flag
9081 -- Warnings_Off_Used set for both types if appropriate.
9083 and then not (Has_Warnings_Off (Source)
9085 Has_Warnings_Off (Target))
9086 then
9087 Source_Siz := RM_Size (Source);
9088 Target_Siz := RM_Size (Target);
9090 if Source_Siz /= Target_Siz then
9091 Error_Msg
9092 ("?types for unchecked conversion have different sizes!",
9093 Eloc);
9095 if All_Errors_Mode then
9096 Error_Msg_Name_1 := Chars (Source);
9097 Error_Msg_Uint_1 := Source_Siz;
9098 Error_Msg_Name_2 := Chars (Target);
9099 Error_Msg_Uint_2 := Target_Siz;
9100 Error_Msg ("\size of % is ^, size of % is ^?", Eloc);
9102 Error_Msg_Uint_1 := UI_Abs (Source_Siz - Target_Siz);
9104 if Is_Discrete_Type (Source)
9105 and then Is_Discrete_Type (Target)
9106 then
9107 if Source_Siz > Target_Siz then
9108 Error_Msg
9109 ("\?^ high order bits of source will be ignored!",
9110 Eloc);
9112 elsif Is_Unsigned_Type (Source) then
9113 Error_Msg
9114 ("\?source will be extended with ^ high order " &
9115 "zero bits?!", Eloc);
9117 else
9118 Error_Msg
9119 ("\?source will be extended with ^ high order " &
9120 "sign bits!",
9121 Eloc);
9122 end if;
9124 elsif Source_Siz < Target_Siz then
9125 if Is_Discrete_Type (Target) then
9126 if Bytes_Big_Endian then
9127 Error_Msg
9128 ("\?target value will include ^ undefined " &
9129 "low order bits!",
9130 Eloc);
9131 else
9132 Error_Msg
9133 ("\?target value will include ^ undefined " &
9134 "high order bits!",
9135 Eloc);
9136 end if;
9138 else
9139 Error_Msg
9140 ("\?^ trailing bits of target value will be " &
9141 "undefined!", Eloc);
9142 end if;
9144 else pragma Assert (Source_Siz > Target_Siz);
9145 Error_Msg
9146 ("\?^ trailing bits of source will be ignored!",
9147 Eloc);
9148 end if;
9149 end if;
9150 end if;
9151 end if;
9153 -- If both types are access types, we need to check the alignment.
9154 -- If the alignment of both is specified, we can do it here.
9156 if Serious_Errors_Detected = 0
9157 and then Ekind (Source) in Access_Kind
9158 and then Ekind (Target) in Access_Kind
9159 and then Target_Strict_Alignment
9160 and then Present (Designated_Type (Source))
9161 and then Present (Designated_Type (Target))
9162 then
9163 declare
9164 D_Source : constant Entity_Id := Designated_Type (Source);
9165 D_Target : constant Entity_Id := Designated_Type (Target);
9167 begin
9168 if Known_Alignment (D_Source)
9169 and then Known_Alignment (D_Target)
9170 then
9171 declare
9172 Source_Align : constant Uint := Alignment (D_Source);
9173 Target_Align : constant Uint := Alignment (D_Target);
9175 begin
9176 if Source_Align < Target_Align
9177 and then not Is_Tagged_Type (D_Source)
9179 -- Suppress warning if warnings suppressed on either
9180 -- type or either designated type. Note the use of
9181 -- OR here instead of OR ELSE. That is intentional,
9182 -- we would like to set flag Warnings_Off_Used in
9183 -- all types for which warnings are suppressed.
9185 and then not (Has_Warnings_Off (D_Source)
9187 Has_Warnings_Off (D_Target)
9189 Has_Warnings_Off (Source)
9191 Has_Warnings_Off (Target))
9192 then
9193 Error_Msg_Uint_1 := Target_Align;
9194 Error_Msg_Uint_2 := Source_Align;
9195 Error_Msg_Node_1 := D_Target;
9196 Error_Msg_Node_2 := D_Source;
9197 Error_Msg
9198 ("?alignment of & (^) is stricter than " &
9199 "alignment of & (^)!", Eloc);
9200 Error_Msg
9201 ("\?resulting access value may have invalid " &
9202 "alignment!", Eloc);
9203 end if;
9204 end;
9205 end if;
9206 end;
9207 end if;
9208 end;
9209 end loop;
9210 end Validate_Unchecked_Conversions;
9212 end Sem_Ch13;