* libgfortran.h (support_fpu_underflow_control,
[official-gcc.git] / gcc / ada / sem_ch13.adb
blob149826f2519e33e80e37eecb88e26a63b51135d9
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-2014, 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 Debug; use Debug;
30 with Einfo; use Einfo;
31 with Elists; use Elists;
32 with Errout; use Errout;
33 with Exp_Disp; use Exp_Disp;
34 with Exp_Tss; use Exp_Tss;
35 with Exp_Util; use Exp_Util;
36 with Lib; use Lib;
37 with Lib.Xref; use Lib.Xref;
38 with Namet; use Namet;
39 with Nlists; use Nlists;
40 with Nmake; use Nmake;
41 with Opt; use Opt;
42 with Restrict; use Restrict;
43 with Rident; use Rident;
44 with Rtsfind; use Rtsfind;
45 with Sem; use Sem;
46 with Sem_Aux; use Sem_Aux;
47 with Sem_Case; use Sem_Case;
48 with Sem_Ch3; use Sem_Ch3;
49 with Sem_Ch6; use Sem_Ch6;
50 with Sem_Ch8; use Sem_Ch8;
51 with Sem_Dim; use Sem_Dim;
52 with Sem_Disp; use Sem_Disp;
53 with Sem_Eval; use Sem_Eval;
54 with Sem_Prag; use Sem_Prag;
55 with Sem_Res; use Sem_Res;
56 with Sem_Type; use Sem_Type;
57 with Sem_Util; use Sem_Util;
58 with Sem_Warn; use Sem_Warn;
59 with Sinput; use Sinput;
60 with Snames; use Snames;
61 with Stand; use Stand;
62 with Sinfo; use Sinfo;
63 with Stringt; use Stringt;
64 with Targparm; use Targparm;
65 with Ttypes; use Ttypes;
66 with Tbuild; use Tbuild;
67 with Urealp; use Urealp;
68 with Warnsw; use Warnsw;
70 with GNAT.Heap_Sort_G;
72 package body Sem_Ch13 is
74 SSU : constant Pos := System_Storage_Unit;
75 -- Convenient short hand for commonly used constant
77 -----------------------
78 -- Local Subprograms --
79 -----------------------
81 procedure Alignment_Check_For_Size_Change (Typ : Entity_Id; Size : Uint);
82 -- This routine is called after setting one of the sizes of type entity
83 -- Typ to Size. The purpose is to deal with the situation of a derived
84 -- type whose inherited alignment is no longer appropriate for the new
85 -- size value. In this case, we reset the Alignment to unknown.
87 procedure Build_Predicate_Functions (Typ : Entity_Id; N : Node_Id);
88 -- If Typ has predicates (indicated by Has_Predicates being set for Typ),
89 -- then either there are pragma Predicate entries on the rep chain for the
90 -- type (note that Predicate aspects are converted to pragma Predicate), or
91 -- there are inherited aspects from a parent type, or ancestor subtypes.
92 -- This procedure builds the spec and body for the Predicate function that
93 -- tests these predicates. N is the freeze node for the type. The spec of
94 -- the function is inserted before the freeze node, and the body of the
95 -- function is inserted after the freeze node. If the predicate expression
96 -- has at least one Raise_Expression, then this procedure also builds the
97 -- M version of the predicate function for use in membership tests.
99 procedure Build_Static_Predicate
100 (Typ : Entity_Id;
101 Expr : Node_Id;
102 Nam : Name_Id);
103 -- Given a predicated type Typ, where Typ is a discrete static subtype,
104 -- whose predicate expression is Expr, tests if Expr is a static predicate,
105 -- and if so, builds the predicate range list. Nam is the name of the one
106 -- argument to the predicate function. Occurrences of the type name in the
107 -- predicate expression have been replaced by identifier references to this
108 -- name, which is unique, so any identifier with Chars matching Nam must be
109 -- a reference to the type. If the predicate is non-static, this procedure
110 -- returns doing nothing. If the predicate is static, then the predicate
111 -- list is stored in Static_Predicate (Typ), and the Expr is rewritten as
112 -- a canonicalized membership operation.
114 procedure Check_Pool_Size_Clash (Ent : Entity_Id; SP, SS : Node_Id);
115 -- Called if both Storage_Pool and Storage_Size attribute definition
116 -- clauses (SP and SS) are present for entity Ent. Issue error message.
118 procedure Freeze_Entity_Checks (N : Node_Id);
119 -- Called from Analyze_Freeze_Entity and Analyze_Generic_Freeze Entity
120 -- to generate appropriate semantic checks that are delayed until this
121 -- point (they had to be delayed this long for cases of delayed aspects,
122 -- e.g. analysis of statically predicated subtypes in choices, for which
123 -- we have to be sure the subtypes in question are frozen before checking.
125 function Get_Alignment_Value (Expr : Node_Id) return Uint;
126 -- Given the expression for an alignment value, returns the corresponding
127 -- Uint value. If the value is inappropriate, then error messages are
128 -- posted as required, and a value of No_Uint is returned.
130 function Is_Operational_Item (N : Node_Id) return Boolean;
131 -- A specification for a stream attribute is allowed before the full type
132 -- is declared, as explained in AI-00137 and the corrigendum. Attributes
133 -- that do not specify a representation characteristic are operational
134 -- attributes.
136 procedure New_Stream_Subprogram
137 (N : Node_Id;
138 Ent : Entity_Id;
139 Subp : Entity_Id;
140 Nam : TSS_Name_Type);
141 -- Create a subprogram renaming of a given stream attribute to the
142 -- designated subprogram and then in the tagged case, provide this as a
143 -- primitive operation, or in the non-tagged case make an appropriate TSS
144 -- entry. This is more properly an expansion activity than just semantics,
145 -- but the presence of user-defined stream functions for limited types is a
146 -- legality check, which is why this takes place here rather than in
147 -- exp_ch13, where it was previously. Nam indicates the name of the TSS
148 -- function to be generated.
150 -- To avoid elaboration anomalies with freeze nodes, for untagged types
151 -- we generate both a subprogram declaration and a subprogram renaming
152 -- declaration, so that the attribute specification is handled as a
153 -- renaming_as_body. For tagged types, the specification is one of the
154 -- primitive specs.
156 generic
157 with procedure Replace_Type_Reference (N : Node_Id);
158 procedure Replace_Type_References_Generic (N : Node_Id; TName : Name_Id);
159 -- This is used to scan an expression for a predicate or invariant aspect
160 -- replacing occurrences of the name TName (the name of the subtype to
161 -- which the aspect applies) with appropriate references to the parameter
162 -- of the predicate function or invariant procedure. The procedure passed
163 -- as a generic parameter does the actual replacement of node N, which is
164 -- either a simple direct reference to TName, or a selected component that
165 -- represents an appropriately qualified occurrence of TName.
167 procedure Resolve_Iterable_Operation
168 (N : Node_Id;
169 Cursor : Entity_Id;
170 Typ : Entity_Id;
171 Nam : Name_Id);
172 -- If the name of a primitive operation for an Iterable aspect is
173 -- overloaded, resolve according to required signature.
175 procedure Set_Biased
176 (E : Entity_Id;
177 N : Node_Id;
178 Msg : String;
179 Biased : Boolean := True);
180 -- If Biased is True, sets Has_Biased_Representation flag for E, and
181 -- outputs a warning message at node N if Warn_On_Biased_Representation is
182 -- is True. This warning inserts the string Msg to describe the construct
183 -- causing biasing.
185 ----------------------------------------------
186 -- Table for Validate_Unchecked_Conversions --
187 ----------------------------------------------
189 -- The following table collects unchecked conversions for validation.
190 -- Entries are made by Validate_Unchecked_Conversion and then the call
191 -- to Validate_Unchecked_Conversions does the actual error checking and
192 -- posting of warnings. The reason for this delayed processing is to take
193 -- advantage of back-annotations of size and alignment values performed by
194 -- the back end.
196 -- Note: the reason we store a Source_Ptr value instead of a Node_Id is
197 -- that by the time Validate_Unchecked_Conversions is called, Sprint will
198 -- already have modified all Sloc values if the -gnatD option is set.
200 type UC_Entry is record
201 Eloc : Source_Ptr; -- node used for posting warnings
202 Source : Entity_Id; -- source type for unchecked conversion
203 Target : Entity_Id; -- target type for unchecked conversion
204 Act_Unit : Entity_Id; -- actual function instantiated
205 end record;
207 package Unchecked_Conversions is new Table.Table (
208 Table_Component_Type => UC_Entry,
209 Table_Index_Type => Int,
210 Table_Low_Bound => 1,
211 Table_Initial => 50,
212 Table_Increment => 200,
213 Table_Name => "Unchecked_Conversions");
215 ----------------------------------------
216 -- Table for Validate_Address_Clauses --
217 ----------------------------------------
219 -- If an address clause has the form
221 -- for X'Address use Expr
223 -- where Expr is of the form Y'Address or recursively is a reference to a
224 -- constant of either of these forms, and X and Y are entities of objects,
225 -- then if Y has a smaller alignment than X, that merits a warning about
226 -- possible bad alignment. The following table collects address clauses of
227 -- this kind. We put these in a table so that they can be checked after the
228 -- back end has completed annotation of the alignments of objects, since we
229 -- can catch more cases that way.
231 type Address_Clause_Check_Record is record
232 N : Node_Id;
233 -- The address clause
235 X : Entity_Id;
236 -- The entity of the object overlaying Y
238 Y : Entity_Id;
239 -- The entity of the object being overlaid
241 Off : Boolean;
242 -- Whether the address is offset within Y
243 end record;
245 package Address_Clause_Checks is new Table.Table (
246 Table_Component_Type => Address_Clause_Check_Record,
247 Table_Index_Type => Int,
248 Table_Low_Bound => 1,
249 Table_Initial => 20,
250 Table_Increment => 200,
251 Table_Name => "Address_Clause_Checks");
253 -----------------------------------------
254 -- Adjust_Record_For_Reverse_Bit_Order --
255 -----------------------------------------
257 procedure Adjust_Record_For_Reverse_Bit_Order (R : Entity_Id) is
258 Comp : Node_Id;
259 CC : Node_Id;
261 begin
262 -- Processing depends on version of Ada
264 -- For Ada 95, we just renumber bits within a storage unit. We do the
265 -- same for Ada 83 mode, since we recognize the Bit_Order attribute in
266 -- Ada 83, and are free to add this extension.
268 if Ada_Version < Ada_2005 then
269 Comp := First_Component_Or_Discriminant (R);
270 while Present (Comp) loop
271 CC := Component_Clause (Comp);
273 -- If component clause is present, then deal with the non-default
274 -- bit order case for Ada 95 mode.
276 -- We only do this processing for the base type, and in fact that
277 -- is important, since otherwise if there are record subtypes, we
278 -- could reverse the bits once for each subtype, which is wrong.
280 if Present (CC) and then Ekind (R) = E_Record_Type then
281 declare
282 CFB : constant Uint := Component_Bit_Offset (Comp);
283 CSZ : constant Uint := Esize (Comp);
284 CLC : constant Node_Id := Component_Clause (Comp);
285 Pos : constant Node_Id := Position (CLC);
286 FB : constant Node_Id := First_Bit (CLC);
288 Storage_Unit_Offset : constant Uint :=
289 CFB / System_Storage_Unit;
291 Start_Bit : constant Uint :=
292 CFB mod System_Storage_Unit;
294 begin
295 -- Cases where field goes over storage unit boundary
297 if Start_Bit + CSZ > System_Storage_Unit then
299 -- Allow multi-byte field but generate warning
301 if Start_Bit mod System_Storage_Unit = 0
302 and then CSZ mod System_Storage_Unit = 0
303 then
304 Error_Msg_N
305 ("multi-byte field specified with non-standard"
306 & " Bit_Order??", CLC);
308 if Bytes_Big_Endian then
309 Error_Msg_N
310 ("bytes are not reversed "
311 & "(component is big-endian)??", CLC);
312 else
313 Error_Msg_N
314 ("bytes are not reversed "
315 & "(component is little-endian)??", CLC);
316 end if;
318 -- Do not allow non-contiguous field
320 else
321 Error_Msg_N
322 ("attempt to specify non-contiguous field "
323 & "not permitted", CLC);
324 Error_Msg_N
325 ("\caused by non-standard Bit_Order "
326 & "specified", CLC);
327 Error_Msg_N
328 ("\consider possibility of using "
329 & "Ada 2005 mode here", CLC);
330 end if;
332 -- Case where field fits in one storage unit
334 else
335 -- Give warning if suspicious component clause
337 if Intval (FB) >= System_Storage_Unit
338 and then Warn_On_Reverse_Bit_Order
339 then
340 Error_Msg_N
341 ("Bit_Order clause does not affect " &
342 "byte ordering?V?", Pos);
343 Error_Msg_Uint_1 :=
344 Intval (Pos) + Intval (FB) /
345 System_Storage_Unit;
346 Error_Msg_N
347 ("position normalized to ^ before bit " &
348 "order interpreted?V?", Pos);
349 end if;
351 -- Here is where we fix up the Component_Bit_Offset value
352 -- to account for the reverse bit order. Some examples of
353 -- what needs to be done are:
355 -- First_Bit .. Last_Bit Component_Bit_Offset
356 -- old new old new
358 -- 0 .. 0 7 .. 7 0 7
359 -- 0 .. 1 6 .. 7 0 6
360 -- 0 .. 2 5 .. 7 0 5
361 -- 0 .. 7 0 .. 7 0 4
363 -- 1 .. 1 6 .. 6 1 6
364 -- 1 .. 4 3 .. 6 1 3
365 -- 4 .. 7 0 .. 3 4 0
367 -- The rule is that the first bit is is obtained by
368 -- subtracting the old ending bit from storage_unit - 1.
370 Set_Component_Bit_Offset
371 (Comp,
372 (Storage_Unit_Offset * System_Storage_Unit) +
373 (System_Storage_Unit - 1) -
374 (Start_Bit + CSZ - 1));
376 Set_Normalized_First_Bit
377 (Comp,
378 Component_Bit_Offset (Comp) mod
379 System_Storage_Unit);
380 end if;
381 end;
382 end if;
384 Next_Component_Or_Discriminant (Comp);
385 end loop;
387 -- For Ada 2005, we do machine scalar processing, as fully described In
388 -- AI-133. This involves gathering all components which start at the
389 -- same byte offset and processing them together. Same approach is still
390 -- valid in later versions including Ada 2012.
392 else
393 declare
394 Max_Machine_Scalar_Size : constant Uint :=
395 UI_From_Int
396 (Standard_Long_Long_Integer_Size);
397 -- We use this as the maximum machine scalar size
399 Num_CC : Natural;
400 SSU : constant Uint := UI_From_Int (System_Storage_Unit);
402 begin
403 -- This first loop through components does two things. First it
404 -- deals with the case of components with component clauses whose
405 -- length is greater than the maximum machine scalar size (either
406 -- accepting them or rejecting as needed). Second, it counts the
407 -- number of components with component clauses whose length does
408 -- not exceed this maximum for later processing.
410 Num_CC := 0;
411 Comp := First_Component_Or_Discriminant (R);
412 while Present (Comp) loop
413 CC := Component_Clause (Comp);
415 if Present (CC) then
416 declare
417 Fbit : constant Uint := Static_Integer (First_Bit (CC));
418 Lbit : constant Uint := Static_Integer (Last_Bit (CC));
420 begin
421 -- Case of component with last bit >= max machine scalar
423 if Lbit >= Max_Machine_Scalar_Size then
425 -- This is allowed only if first bit is zero, and
426 -- last bit + 1 is a multiple of storage unit size.
428 if Fbit = 0 and then (Lbit + 1) mod SSU = 0 then
430 -- This is the case to give a warning if enabled
432 if Warn_On_Reverse_Bit_Order then
433 Error_Msg_N
434 ("multi-byte field specified with "
435 & " non-standard Bit_Order?V?", CC);
437 if Bytes_Big_Endian then
438 Error_Msg_N
439 ("\bytes are not reversed "
440 & "(component is big-endian)?V?", CC);
441 else
442 Error_Msg_N
443 ("\bytes are not reversed "
444 & "(component is little-endian)?V?", CC);
445 end if;
446 end if;
448 -- Give error message for RM 13.5.1(10) violation
450 else
451 Error_Msg_FE
452 ("machine scalar rules not followed for&",
453 First_Bit (CC), Comp);
455 Error_Msg_Uint_1 := Lbit;
456 Error_Msg_Uint_2 := Max_Machine_Scalar_Size;
457 Error_Msg_F
458 ("\last bit (^) exceeds maximum machine "
459 & "scalar size (^)",
460 First_Bit (CC));
462 if (Lbit + 1) mod SSU /= 0 then
463 Error_Msg_Uint_1 := SSU;
464 Error_Msg_F
465 ("\and is not a multiple of Storage_Unit (^) "
466 & "(RM 13.4.1(10))",
467 First_Bit (CC));
469 else
470 Error_Msg_Uint_1 := Fbit;
471 Error_Msg_F
472 ("\and first bit (^) is non-zero "
473 & "(RM 13.4.1(10))",
474 First_Bit (CC));
475 end if;
476 end if;
478 -- OK case of machine scalar related component clause,
479 -- For now, just count them.
481 else
482 Num_CC := Num_CC + 1;
483 end if;
484 end;
485 end if;
487 Next_Component_Or_Discriminant (Comp);
488 end loop;
490 -- We need to sort the component clauses on the basis of the
491 -- Position values in the clause, so we can group clauses with
492 -- the same Position together to determine the relevant machine
493 -- scalar size.
495 Sort_CC : declare
496 Comps : array (0 .. Num_CC) of Entity_Id;
497 -- Array to collect component and discriminant entities. The
498 -- data starts at index 1, the 0'th entry is for the sort
499 -- routine.
501 function CP_Lt (Op1, Op2 : Natural) return Boolean;
502 -- Compare routine for Sort
504 procedure CP_Move (From : Natural; To : Natural);
505 -- Move routine for Sort
507 package Sorting is new GNAT.Heap_Sort_G (CP_Move, CP_Lt);
509 Start : Natural;
510 Stop : Natural;
511 -- Start and stop positions in the component list of the set of
512 -- components with the same starting position (that constitute
513 -- components in a single machine scalar).
515 MaxL : Uint;
516 -- Maximum last bit value of any component in this set
518 MSS : Uint;
519 -- Corresponding machine scalar size
521 -----------
522 -- CP_Lt --
523 -----------
525 function CP_Lt (Op1, Op2 : Natural) return Boolean is
526 begin
527 return Position (Component_Clause (Comps (Op1))) <
528 Position (Component_Clause (Comps (Op2)));
529 end CP_Lt;
531 -------------
532 -- CP_Move --
533 -------------
535 procedure CP_Move (From : Natural; To : Natural) is
536 begin
537 Comps (To) := Comps (From);
538 end CP_Move;
540 -- Start of processing for Sort_CC
542 begin
543 -- Collect the machine scalar relevant component clauses
545 Num_CC := 0;
546 Comp := First_Component_Or_Discriminant (R);
547 while Present (Comp) loop
548 declare
549 CC : constant Node_Id := Component_Clause (Comp);
551 begin
552 -- Collect only component clauses whose last bit is less
553 -- than machine scalar size. Any component clause whose
554 -- last bit exceeds this value does not take part in
555 -- machine scalar layout considerations. The test for
556 -- Error_Posted makes sure we exclude component clauses
557 -- for which we already posted an error.
559 if Present (CC)
560 and then not Error_Posted (Last_Bit (CC))
561 and then Static_Integer (Last_Bit (CC)) <
562 Max_Machine_Scalar_Size
563 then
564 Num_CC := Num_CC + 1;
565 Comps (Num_CC) := Comp;
566 end if;
567 end;
569 Next_Component_Or_Discriminant (Comp);
570 end loop;
572 -- Sort by ascending position number
574 Sorting.Sort (Num_CC);
576 -- We now have all the components whose size does not exceed
577 -- the max machine scalar value, sorted by starting position.
578 -- In this loop we gather groups of clauses starting at the
579 -- same position, to process them in accordance with AI-133.
581 Stop := 0;
582 while Stop < Num_CC loop
583 Start := Stop + 1;
584 Stop := Start;
585 MaxL :=
586 Static_Integer
587 (Last_Bit (Component_Clause (Comps (Start))));
588 while Stop < Num_CC loop
589 if Static_Integer
590 (Position (Component_Clause (Comps (Stop + 1)))) =
591 Static_Integer
592 (Position (Component_Clause (Comps (Stop))))
593 then
594 Stop := Stop + 1;
595 MaxL :=
596 UI_Max
597 (MaxL,
598 Static_Integer
599 (Last_Bit
600 (Component_Clause (Comps (Stop)))));
601 else
602 exit;
603 end if;
604 end loop;
606 -- Now we have a group of component clauses from Start to
607 -- Stop whose positions are identical, and MaxL is the
608 -- maximum last bit value of any of these components.
610 -- We need to determine the corresponding machine scalar
611 -- size. This loop assumes that machine scalar sizes are
612 -- even, and that each possible machine scalar has twice
613 -- as many bits as the next smaller one.
615 MSS := Max_Machine_Scalar_Size;
616 while MSS mod 2 = 0
617 and then (MSS / 2) >= SSU
618 and then (MSS / 2) > MaxL
619 loop
620 MSS := MSS / 2;
621 end loop;
623 -- Here is where we fix up the Component_Bit_Offset value
624 -- to account for the reverse bit order. Some examples of
625 -- what needs to be done for the case of a machine scalar
626 -- size of 8 are:
628 -- First_Bit .. Last_Bit Component_Bit_Offset
629 -- old new old new
631 -- 0 .. 0 7 .. 7 0 7
632 -- 0 .. 1 6 .. 7 0 6
633 -- 0 .. 2 5 .. 7 0 5
634 -- 0 .. 7 0 .. 7 0 4
636 -- 1 .. 1 6 .. 6 1 6
637 -- 1 .. 4 3 .. 6 1 3
638 -- 4 .. 7 0 .. 3 4 0
640 -- The rule is that the first bit is obtained by subtracting
641 -- the old ending bit from machine scalar size - 1.
643 for C in Start .. Stop loop
644 declare
645 Comp : constant Entity_Id := Comps (C);
646 CC : constant Node_Id := Component_Clause (Comp);
648 LB : constant Uint := Static_Integer (Last_Bit (CC));
649 NFB : constant Uint := MSS - Uint_1 - LB;
650 NLB : constant Uint := NFB + Esize (Comp) - 1;
651 Pos : constant Uint := Static_Integer (Position (CC));
653 begin
654 if Warn_On_Reverse_Bit_Order then
655 Error_Msg_Uint_1 := MSS;
656 Error_Msg_N
657 ("info: reverse bit order in machine " &
658 "scalar of length^?V?", First_Bit (CC));
659 Error_Msg_Uint_1 := NFB;
660 Error_Msg_Uint_2 := NLB;
662 if Bytes_Big_Endian then
663 Error_Msg_NE
664 ("\big-endian range for "
665 & "component & is ^ .. ^?V?",
666 First_Bit (CC), Comp);
667 else
668 Error_Msg_NE
669 ("\little-endian range "
670 & "for component & is ^ .. ^?V?",
671 First_Bit (CC), Comp);
672 end if;
673 end if;
675 Set_Component_Bit_Offset (Comp, Pos * SSU + NFB);
676 Set_Normalized_First_Bit (Comp, NFB mod SSU);
677 end;
678 end loop;
679 end loop;
680 end Sort_CC;
681 end;
682 end if;
683 end Adjust_Record_For_Reverse_Bit_Order;
685 -------------------------------------
686 -- Alignment_Check_For_Size_Change --
687 -------------------------------------
689 procedure Alignment_Check_For_Size_Change (Typ : Entity_Id; Size : Uint) is
690 begin
691 -- If the alignment is known, and not set by a rep clause, and is
692 -- inconsistent with the size being set, then reset it to unknown,
693 -- we assume in this case that the size overrides the inherited
694 -- alignment, and that the alignment must be recomputed.
696 if Known_Alignment (Typ)
697 and then not Has_Alignment_Clause (Typ)
698 and then Size mod (Alignment (Typ) * SSU) /= 0
699 then
700 Init_Alignment (Typ);
701 end if;
702 end Alignment_Check_For_Size_Change;
704 -------------------------------------
705 -- Analyze_Aspects_At_Freeze_Point --
706 -------------------------------------
708 procedure Analyze_Aspects_At_Freeze_Point (E : Entity_Id) is
709 ASN : Node_Id;
710 A_Id : Aspect_Id;
711 Ritem : Node_Id;
713 procedure Analyze_Aspect_Default_Value (ASN : Node_Id);
714 -- This routine analyzes an Aspect_Default_[Component_]Value denoted by
715 -- the aspect specification node ASN.
717 procedure Inherit_Delayed_Rep_Aspects (ASN : Node_Id);
718 -- As discussed in the spec of Aspects (see Aspect_Delay declaration),
719 -- a derived type can inherit aspects from its parent which have been
720 -- specified at the time of the derivation using an aspect, as in:
722 -- type A is range 1 .. 10
723 -- with Size => Not_Defined_Yet;
724 -- ..
725 -- type B is new A;
726 -- ..
727 -- Not_Defined_Yet : constant := 64;
729 -- In this example, the Size of A is considered to be specified prior
730 -- to the derivation, and thus inherited, even though the value is not
731 -- known at the time of derivation. To deal with this, we use two entity
732 -- flags. The flag Has_Derived_Rep_Aspects is set in the parent type (A
733 -- here), and then the flag May_Inherit_Delayed_Rep_Aspects is set in
734 -- the derived type (B here). If this flag is set when the derived type
735 -- is frozen, then this procedure is called to ensure proper inheritance
736 -- of all delayed aspects from the parent type. The derived type is E,
737 -- the argument to Analyze_Aspects_At_Freeze_Point. ASN is the first
738 -- aspect specification node in the Rep_Item chain for the parent type.
740 procedure Make_Pragma_From_Boolean_Aspect (ASN : Node_Id);
741 -- Given an aspect specification node ASN whose expression is an
742 -- optional Boolean, this routines creates the corresponding pragma
743 -- at the freezing point.
745 ----------------------------------
746 -- Analyze_Aspect_Default_Value --
747 ----------------------------------
749 procedure Analyze_Aspect_Default_Value (ASN : Node_Id) is
750 Ent : constant Entity_Id := Entity (ASN);
751 Expr : constant Node_Id := Expression (ASN);
752 Id : constant Node_Id := Identifier (ASN);
754 begin
755 Error_Msg_Name_1 := Chars (Id);
757 if not Is_Type (Ent) then
758 Error_Msg_N ("aspect% can only apply to a type", Id);
759 return;
761 elsif not Is_First_Subtype (Ent) then
762 Error_Msg_N ("aspect% cannot apply to subtype", Id);
763 return;
765 elsif A_Id = Aspect_Default_Value
766 and then not Is_Scalar_Type (Ent)
767 then
768 Error_Msg_N ("aspect% can only be applied to scalar type", Id);
769 return;
771 elsif A_Id = Aspect_Default_Component_Value then
772 if not Is_Array_Type (Ent) then
773 Error_Msg_N ("aspect% can only be applied to array type", Id);
774 return;
776 elsif not Is_Scalar_Type (Component_Type (Ent)) then
777 Error_Msg_N ("aspect% requires scalar components", Id);
778 return;
779 end if;
780 end if;
782 Set_Has_Default_Aspect (Base_Type (Ent));
784 if Is_Scalar_Type (Ent) then
785 Set_Default_Aspect_Value (Base_Type (Ent), Expr);
786 else
787 Set_Default_Aspect_Component_Value (Base_Type (Ent), Expr);
788 end if;
789 end Analyze_Aspect_Default_Value;
791 ---------------------------------
792 -- Inherit_Delayed_Rep_Aspects --
793 ---------------------------------
795 procedure Inherit_Delayed_Rep_Aspects (ASN : Node_Id) is
796 P : constant Entity_Id := Entity (ASN);
797 -- Entithy for parent type
799 N : Node_Id;
800 -- Item from Rep_Item chain
802 A : Aspect_Id;
804 begin
805 -- Loop through delayed aspects for the parent type
807 N := ASN;
808 while Present (N) loop
809 if Nkind (N) = N_Aspect_Specification then
810 exit when Entity (N) /= P;
812 if Is_Delayed_Aspect (N) then
813 A := Get_Aspect_Id (Chars (Identifier (N)));
815 -- Process delayed rep aspect. For Boolean attributes it is
816 -- not possible to cancel an attribute once set (the attempt
817 -- to use an aspect with xxx => False is an error) for a
818 -- derived type. So for those cases, we do not have to check
819 -- if a clause has been given for the derived type, since it
820 -- is harmless to set it again if it is already set.
822 case A is
824 -- Alignment
826 when Aspect_Alignment =>
827 if not Has_Alignment_Clause (E) then
828 Set_Alignment (E, Alignment (P));
829 end if;
831 -- Atomic
833 when Aspect_Atomic =>
834 if Is_Atomic (P) then
835 Set_Is_Atomic (E);
836 end if;
838 -- Atomic_Components
840 when Aspect_Atomic_Components =>
841 if Has_Atomic_Components (P) then
842 Set_Has_Atomic_Components (Base_Type (E));
843 end if;
845 -- Bit_Order
847 when Aspect_Bit_Order =>
848 if Is_Record_Type (E)
849 and then No (Get_Attribute_Definition_Clause
850 (E, Attribute_Bit_Order))
851 and then Reverse_Bit_Order (P)
852 then
853 Set_Reverse_Bit_Order (Base_Type (E));
854 end if;
856 -- Component_Size
858 when Aspect_Component_Size =>
859 if Is_Array_Type (E)
860 and then not Has_Component_Size_Clause (E)
861 then
862 Set_Component_Size
863 (Base_Type (E), Component_Size (P));
864 end if;
866 -- Machine_Radix
868 when Aspect_Machine_Radix =>
869 if Is_Decimal_Fixed_Point_Type (E)
870 and then not Has_Machine_Radix_Clause (E)
871 then
872 Set_Machine_Radix_10 (E, Machine_Radix_10 (P));
873 end if;
875 -- Object_Size (also Size which also sets Object_Size)
877 when Aspect_Object_Size | Aspect_Size =>
878 if not Has_Size_Clause (E)
879 and then
880 No (Get_Attribute_Definition_Clause
881 (E, Attribute_Object_Size))
882 then
883 Set_Esize (E, Esize (P));
884 end if;
886 -- Pack
888 when Aspect_Pack =>
889 if not Is_Packed (E) then
890 Set_Is_Packed (Base_Type (E));
892 if Is_Bit_Packed_Array (P) then
893 Set_Is_Bit_Packed_Array (Base_Type (E));
894 Set_Packed_Array_Type (E, Packed_Array_Type (P));
895 end if;
896 end if;
898 -- Scalar_Storage_Order
900 when Aspect_Scalar_Storage_Order =>
901 if (Is_Record_Type (E) or else Is_Array_Type (E))
902 and then No (Get_Attribute_Definition_Clause
903 (E, Attribute_Scalar_Storage_Order))
904 and then Reverse_Storage_Order (P)
905 then
906 Set_Reverse_Storage_Order (Base_Type (E));
907 end if;
909 -- Small
911 when Aspect_Small =>
912 if Is_Fixed_Point_Type (E)
913 and then not Has_Small_Clause (E)
914 then
915 Set_Small_Value (E, Small_Value (P));
916 end if;
918 -- Storage_Size
920 when Aspect_Storage_Size =>
921 if (Is_Access_Type (E) or else Is_Task_Type (E))
922 and then not Has_Storage_Size_Clause (E)
923 then
924 Set_Storage_Size_Variable
925 (Base_Type (E), Storage_Size_Variable (P));
926 end if;
928 -- Value_Size
930 when Aspect_Value_Size =>
932 -- Value_Size is never inherited, it is either set by
933 -- default, or it is explicitly set for the derived
934 -- type. So nothing to do here.
936 null;
938 -- Volatile
940 when Aspect_Volatile =>
941 if Is_Volatile (P) then
942 Set_Is_Volatile (E);
943 end if;
945 -- Volatile_Components
947 when Aspect_Volatile_Components =>
948 if Has_Volatile_Components (P) then
949 Set_Has_Volatile_Components (Base_Type (E));
950 end if;
952 -- That should be all the Rep Aspects
954 when others =>
955 pragma Assert (Aspect_Delay (A_Id) /= Rep_Aspect);
956 null;
958 end case;
959 end if;
960 end if;
962 N := Next_Rep_Item (N);
963 end loop;
964 end Inherit_Delayed_Rep_Aspects;
966 -------------------------------------
967 -- Make_Pragma_From_Boolean_Aspect --
968 -------------------------------------
970 procedure Make_Pragma_From_Boolean_Aspect (ASN : Node_Id) is
971 Ident : constant Node_Id := Identifier (ASN);
972 A_Name : constant Name_Id := Chars (Ident);
973 A_Id : constant Aspect_Id := Get_Aspect_Id (A_Name);
974 Ent : constant Entity_Id := Entity (ASN);
975 Expr : constant Node_Id := Expression (ASN);
976 Loc : constant Source_Ptr := Sloc (ASN);
978 Prag : Node_Id;
980 procedure Check_False_Aspect_For_Derived_Type;
981 -- This procedure checks for the case of a false aspect for a derived
982 -- type, which improperly tries to cancel an aspect inherited from
983 -- the parent.
985 -----------------------------------------
986 -- Check_False_Aspect_For_Derived_Type --
987 -----------------------------------------
989 procedure Check_False_Aspect_For_Derived_Type is
990 Par : Node_Id;
992 begin
993 -- We are only checking derived types
995 if not Is_Derived_Type (E) then
996 return;
997 end if;
999 Par := Nearest_Ancestor (E);
1001 case A_Id is
1002 when Aspect_Atomic | Aspect_Shared =>
1003 if not Is_Atomic (Par) then
1004 return;
1005 end if;
1007 when Aspect_Atomic_Components =>
1008 if not Has_Atomic_Components (Par) then
1009 return;
1010 end if;
1012 when Aspect_Discard_Names =>
1013 if not Discard_Names (Par) then
1014 return;
1015 end if;
1017 when Aspect_Pack =>
1018 if not Is_Packed (Par) then
1019 return;
1020 end if;
1022 when Aspect_Unchecked_Union =>
1023 if not Is_Unchecked_Union (Par) then
1024 return;
1025 end if;
1027 when Aspect_Volatile =>
1028 if not Is_Volatile (Par) then
1029 return;
1030 end if;
1032 when Aspect_Volatile_Components =>
1033 if not Has_Volatile_Components (Par) then
1034 return;
1035 end if;
1037 when others =>
1038 return;
1039 end case;
1041 -- Fall through means we are canceling an inherited aspect
1043 Error_Msg_Name_1 := A_Name;
1044 Error_Msg_NE
1045 ("derived type& inherits aspect%, cannot cancel", Expr, E);
1047 end Check_False_Aspect_For_Derived_Type;
1049 -- Start of processing for Make_Pragma_From_Boolean_Aspect
1051 begin
1052 -- Note that we know Expr is present, because for a missing Expr
1053 -- argument, we knew it was True and did not need to delay the
1054 -- evaluation to the freeze point.
1056 if Is_False (Static_Boolean (Expr)) then
1057 Check_False_Aspect_For_Derived_Type;
1059 else
1060 Prag :=
1061 Make_Pragma (Loc,
1062 Pragma_Argument_Associations => New_List (
1063 Make_Pragma_Argument_Association (Sloc (Ident),
1064 Expression => New_Occurrence_Of (Ent, Sloc (Ident)))),
1066 Pragma_Identifier =>
1067 Make_Identifier (Sloc (Ident), Chars (Ident)));
1069 Set_From_Aspect_Specification (Prag, True);
1070 Set_Corresponding_Aspect (Prag, ASN);
1071 Set_Aspect_Rep_Item (ASN, Prag);
1072 Set_Is_Delayed_Aspect (Prag);
1073 Set_Parent (Prag, ASN);
1074 end if;
1075 end Make_Pragma_From_Boolean_Aspect;
1077 -- Start of processing for Analyze_Aspects_At_Freeze_Point
1079 begin
1080 -- Must be visible in current scope
1082 if not Scope_Within_Or_Same (Current_Scope, Scope (E)) then
1083 return;
1084 end if;
1086 -- Look for aspect specification entries for this entity
1088 ASN := First_Rep_Item (E);
1089 while Present (ASN) loop
1090 if Nkind (ASN) = N_Aspect_Specification then
1091 exit when Entity (ASN) /= E;
1093 if Is_Delayed_Aspect (ASN) then
1094 A_Id := Get_Aspect_Id (ASN);
1096 case A_Id is
1098 -- For aspects whose expression is an optional Boolean, make
1099 -- the corresponding pragma at the freezing point.
1101 when Boolean_Aspects |
1102 Library_Unit_Aspects =>
1103 Make_Pragma_From_Boolean_Aspect (ASN);
1105 -- Special handling for aspects that don't correspond to
1106 -- pragmas/attributes.
1108 when Aspect_Default_Value |
1109 Aspect_Default_Component_Value =>
1110 Analyze_Aspect_Default_Value (ASN);
1112 -- Ditto for iterator aspects, because the corresponding
1113 -- attributes may not have been analyzed yet.
1115 when Aspect_Constant_Indexing |
1116 Aspect_Variable_Indexing |
1117 Aspect_Default_Iterator |
1118 Aspect_Iterator_Element =>
1119 Analyze (Expression (ASN));
1121 when Aspect_Iterable =>
1122 Validate_Iterable_Aspect (E, ASN);
1124 when others =>
1125 null;
1126 end case;
1128 Ritem := Aspect_Rep_Item (ASN);
1130 if Present (Ritem) then
1131 Analyze (Ritem);
1132 end if;
1133 end if;
1134 end if;
1136 Next_Rep_Item (ASN);
1137 end loop;
1139 -- This is where we inherit delayed rep aspects from our parent. Note
1140 -- that if we fell out of the above loop with ASN non-empty, it means
1141 -- we hit an aspect for an entity other than E, and it must be the
1142 -- type from which we were derived.
1144 if May_Inherit_Delayed_Rep_Aspects (E) then
1145 Inherit_Delayed_Rep_Aspects (ASN);
1146 end if;
1147 end Analyze_Aspects_At_Freeze_Point;
1149 -----------------------------------
1150 -- Analyze_Aspect_Specifications --
1151 -----------------------------------
1153 procedure Analyze_Aspect_Specifications (N : Node_Id; E : Entity_Id) is
1154 procedure Decorate_Aspect_And_Pragma
1155 (Asp : Node_Id;
1156 Prag : Node_Id;
1157 Delayed : Boolean := False);
1158 -- Establish the linkages between an aspect and its corresponding
1159 -- pragma. Flag Delayed should be set when both constructs are delayed.
1161 procedure Insert_Delayed_Pragma (Prag : Node_Id);
1162 -- Insert a postcondition-like pragma into the tree depending on the
1163 -- context. Prag must denote one of the following: Pre, Post, Depends,
1164 -- Global or Contract_Cases. This procedure is also used for the case
1165 -- of Attach_Handler which has similar requirements for placement.
1167 --------------------------------
1168 -- Decorate_Aspect_And_Pragma --
1169 --------------------------------
1171 procedure Decorate_Aspect_And_Pragma
1172 (Asp : Node_Id;
1173 Prag : Node_Id;
1174 Delayed : Boolean := False)
1176 begin
1177 Set_Aspect_Rep_Item (Asp, Prag);
1178 Set_Corresponding_Aspect (Prag, Asp);
1179 Set_From_Aspect_Specification (Prag);
1180 Set_Is_Delayed_Aspect (Prag, Delayed);
1181 Set_Is_Delayed_Aspect (Asp, Delayed);
1182 Set_Parent (Prag, Asp);
1183 end Decorate_Aspect_And_Pragma;
1185 ---------------------------
1186 -- Insert_Delayed_Pragma --
1187 ---------------------------
1189 procedure Insert_Delayed_Pragma (Prag : Node_Id) is
1190 Aux : Node_Id;
1192 begin
1193 -- When the context is a library unit, the pragma is added to the
1194 -- Pragmas_After list.
1196 if Nkind (Parent (N)) = N_Compilation_Unit then
1197 Aux := Aux_Decls_Node (Parent (N));
1199 if No (Pragmas_After (Aux)) then
1200 Set_Pragmas_After (Aux, New_List);
1201 end if;
1203 Prepend (Prag, Pragmas_After (Aux));
1205 -- Pragmas associated with subprogram bodies are inserted in the
1206 -- declarative part.
1208 elsif Nkind (N) = N_Subprogram_Body then
1209 if No (Declarations (N)) then
1210 Set_Declarations (N, New_List (Prag));
1211 else
1212 declare
1213 D : Node_Id;
1214 begin
1216 -- There may be several aspects associated with the body;
1217 -- preserve the ordering of the corresponding pragmas.
1219 D := First (Declarations (N));
1220 while Present (D) loop
1221 exit when Nkind (D) /= N_Pragma
1222 or else not From_Aspect_Specification (D);
1223 Next (D);
1224 end loop;
1226 if No (D) then
1227 Append (Prag, Declarations (N));
1228 else
1229 Insert_Before (D, Prag);
1230 end if;
1231 end;
1232 end if;
1234 -- Default
1236 else
1237 Insert_After (N, Prag);
1238 end if;
1239 end Insert_Delayed_Pragma;
1241 -- Local variables
1243 Aspect : Node_Id;
1244 Aitem : Node_Id;
1245 Ent : Node_Id;
1247 L : constant List_Id := Aspect_Specifications (N);
1249 Ins_Node : Node_Id := N;
1250 -- Insert pragmas/attribute definition clause after this node when no
1251 -- delayed analysis is required.
1253 -- Start of processing for Analyze_Aspect_Specifications
1255 -- The general processing involves building an attribute definition
1256 -- clause or a pragma node that corresponds to the aspect. Then in order
1257 -- to delay the evaluation of this aspect to the freeze point, we attach
1258 -- the corresponding pragma/attribute definition clause to the aspect
1259 -- specification node, which is then placed in the Rep Item chain. In
1260 -- this case we mark the entity by setting the flag Has_Delayed_Aspects
1261 -- and we evaluate the rep item at the freeze point. When the aspect
1262 -- doesn't have a corresponding pragma/attribute definition clause, then
1263 -- its analysis is simply delayed at the freeze point.
1265 -- Some special cases don't require delay analysis, thus the aspect is
1266 -- analyzed right now.
1268 -- Note that there is a special handling for Pre, Post, Test_Case,
1269 -- Contract_Cases aspects. In these cases, we do not have to worry
1270 -- about delay issues, since the pragmas themselves deal with delay
1271 -- of visibility for the expression analysis. Thus, we just insert
1272 -- the pragma after the node N.
1274 begin
1275 pragma Assert (Present (L));
1277 -- Loop through aspects
1279 Aspect := First (L);
1280 Aspect_Loop : while Present (Aspect) loop
1281 Analyze_One_Aspect : declare
1282 Expr : constant Node_Id := Expression (Aspect);
1283 Id : constant Node_Id := Identifier (Aspect);
1284 Loc : constant Source_Ptr := Sloc (Aspect);
1285 Nam : constant Name_Id := Chars (Id);
1286 A_Id : constant Aspect_Id := Get_Aspect_Id (Nam);
1287 Anod : Node_Id;
1289 Delay_Required : Boolean;
1290 -- Set False if delay is not required
1292 Eloc : Source_Ptr := No_Location;
1293 -- Source location of expression, modified when we split PPC's. It
1294 -- is set below when Expr is present.
1296 procedure Analyze_Aspect_External_Or_Link_Name;
1297 -- Perform analysis of the External_Name or Link_Name aspects
1299 procedure Analyze_Aspect_Implicit_Dereference;
1300 -- Perform analysis of the Implicit_Dereference aspects
1302 procedure Make_Aitem_Pragma
1303 (Pragma_Argument_Associations : List_Id;
1304 Pragma_Name : Name_Id);
1305 -- This is a wrapper for Make_Pragma used for converting aspects
1306 -- to pragmas. It takes care of Sloc (set from Loc) and building
1307 -- the pragma identifier from the given name. In addition the
1308 -- flags Class_Present and Split_PPC are set from the aspect
1309 -- node, as well as Is_Ignored. This routine also sets the
1310 -- From_Aspect_Specification in the resulting pragma node to
1311 -- True, and sets Corresponding_Aspect to point to the aspect.
1312 -- The resulting pragma is assigned to Aitem.
1314 ------------------------------------------
1315 -- Analyze_Aspect_External_Or_Link_Name --
1316 ------------------------------------------
1318 procedure Analyze_Aspect_External_Or_Link_Name is
1319 begin
1320 -- Verify that there is an Import/Export aspect defined for the
1321 -- entity. The processing of that aspect in turn checks that
1322 -- there is a Convention aspect declared. The pragma is
1323 -- constructed when processing the Convention aspect.
1325 declare
1326 A : Node_Id;
1328 begin
1329 A := First (L);
1330 while Present (A) loop
1331 exit when Nam_In (Chars (Identifier (A)), Name_Export,
1332 Name_Import);
1333 Next (A);
1334 end loop;
1336 if No (A) then
1337 Error_Msg_N
1338 ("missing Import/Export for Link/External name",
1339 Aspect);
1340 end if;
1341 end;
1342 end Analyze_Aspect_External_Or_Link_Name;
1344 -----------------------------------------
1345 -- Analyze_Aspect_Implicit_Dereference --
1346 -----------------------------------------
1348 procedure Analyze_Aspect_Implicit_Dereference is
1349 begin
1350 if not Is_Type (E) or else not Has_Discriminants (E) then
1351 Error_Msg_N
1352 ("aspect must apply to a type with discriminants", N);
1354 else
1355 declare
1356 Disc : Entity_Id;
1358 begin
1359 Disc := First_Discriminant (E);
1360 while Present (Disc) loop
1361 if Chars (Expr) = Chars (Disc)
1362 and then Ekind (Etype (Disc)) =
1363 E_Anonymous_Access_Type
1364 then
1365 Set_Has_Implicit_Dereference (E);
1366 Set_Has_Implicit_Dereference (Disc);
1367 return;
1368 end if;
1370 Next_Discriminant (Disc);
1371 end loop;
1373 -- Error if no proper access discriminant.
1375 Error_Msg_NE
1376 ("not an access discriminant of&", Expr, E);
1377 end;
1378 end if;
1379 end Analyze_Aspect_Implicit_Dereference;
1381 -----------------------
1382 -- Make_Aitem_Pragma --
1383 -----------------------
1385 procedure Make_Aitem_Pragma
1386 (Pragma_Argument_Associations : List_Id;
1387 Pragma_Name : Name_Id)
1389 Args : List_Id := Pragma_Argument_Associations;
1391 begin
1392 -- We should never get here if aspect was disabled
1394 pragma Assert (not Is_Disabled (Aspect));
1396 -- Certain aspects allow for an optional name or expression. Do
1397 -- not generate a pragma with empty argument association list.
1399 if No (Args) or else No (Expression (First (Args))) then
1400 Args := No_List;
1401 end if;
1403 -- Build the pragma
1405 Aitem :=
1406 Make_Pragma (Loc,
1407 Pragma_Argument_Associations => Args,
1408 Pragma_Identifier =>
1409 Make_Identifier (Sloc (Id), Pragma_Name),
1410 Class_Present => Class_Present (Aspect),
1411 Split_PPC => Split_PPC (Aspect));
1413 -- Set additional semantic fields
1415 if Is_Ignored (Aspect) then
1416 Set_Is_Ignored (Aitem);
1417 elsif Is_Checked (Aspect) then
1418 Set_Is_Checked (Aitem);
1419 end if;
1421 Set_Corresponding_Aspect (Aitem, Aspect);
1422 Set_From_Aspect_Specification (Aitem, True);
1423 end Make_Aitem_Pragma;
1425 -- Start of processing for Analyze_One_Aspect
1427 begin
1428 -- Skip aspect if already analyzed (not clear if this is needed)
1430 if Analyzed (Aspect) then
1431 goto Continue;
1432 end if;
1434 -- Skip looking at aspect if it is totally disabled. Just mark it
1435 -- as such for later reference in the tree. This also sets the
1436 -- Is_Ignored and Is_Checked flags appropriately.
1438 Check_Applicable_Policy (Aspect);
1440 if Is_Disabled (Aspect) then
1441 goto Continue;
1442 end if;
1444 -- Set the source location of expression, used in the case of
1445 -- a failed precondition/postcondition or invariant. Note that
1446 -- the source location of the expression is not usually the best
1447 -- choice here. For example, it gets located on the last AND
1448 -- keyword in a chain of boolean expressiond AND'ed together.
1449 -- It is best to put the message on the first character of the
1450 -- assertion, which is the effect of the First_Node call here.
1452 if Present (Expr) then
1453 Eloc := Sloc (First_Node (Expr));
1454 end if;
1456 -- Check restriction No_Implementation_Aspect_Specifications
1458 if Implementation_Defined_Aspect (A_Id) then
1459 Check_Restriction
1460 (No_Implementation_Aspect_Specifications, Aspect);
1461 end if;
1463 -- Check restriction No_Specification_Of_Aspect
1465 Check_Restriction_No_Specification_Of_Aspect (Aspect);
1467 -- Mark aspect analyzed (actual analysis is delayed till later)
1469 Set_Analyzed (Aspect);
1470 Set_Entity (Aspect, E);
1471 Ent := New_Occurrence_Of (E, Sloc (Id));
1473 -- Check for duplicate aspect. Note that the Comes_From_Source
1474 -- test allows duplicate Pre/Post's that we generate internally
1475 -- to escape being flagged here.
1477 if No_Duplicates_Allowed (A_Id) then
1478 Anod := First (L);
1479 while Anod /= Aspect loop
1480 if Comes_From_Source (Aspect)
1481 and then Same_Aspect (A_Id, Get_Aspect_Id (Anod))
1482 then
1483 Error_Msg_Name_1 := Nam;
1484 Error_Msg_Sloc := Sloc (Anod);
1486 -- Case of same aspect specified twice
1488 if Class_Present (Anod) = Class_Present (Aspect) then
1489 if not Class_Present (Anod) then
1490 Error_Msg_NE
1491 ("aspect% for & previously given#",
1492 Id, E);
1493 else
1494 Error_Msg_NE
1495 ("aspect `%''Class` for & previously given#",
1496 Id, E);
1497 end if;
1498 end if;
1499 end if;
1501 Next (Anod);
1502 end loop;
1503 end if;
1505 -- Check some general restrictions on language defined aspects
1507 if not Implementation_Defined_Aspect (A_Id) then
1508 Error_Msg_Name_1 := Nam;
1510 -- Not allowed for renaming declarations
1512 if Nkind (N) in N_Renaming_Declaration then
1513 Error_Msg_N
1514 ("aspect % not allowed for renaming declaration",
1515 Aspect);
1516 end if;
1518 -- Not allowed for formal type declarations
1520 if Nkind (N) = N_Formal_Type_Declaration then
1521 Error_Msg_N
1522 ("aspect % not allowed for formal type declaration",
1523 Aspect);
1524 end if;
1525 end if;
1527 -- Copy expression for later processing by the procedures
1528 -- Check_Aspect_At_[Freeze_Point | End_Of_Declarations]
1530 Set_Entity (Id, New_Copy_Tree (Expr));
1532 -- Set Delay_Required as appropriate to aspect
1534 case Aspect_Delay (A_Id) is
1535 when Always_Delay =>
1536 Delay_Required := True;
1538 when Never_Delay =>
1539 Delay_Required := False;
1541 when Rep_Aspect =>
1543 -- If expression has the form of an integer literal, then
1544 -- do not delay, since we know the value cannot change.
1545 -- This optimization catches most rep clause cases.
1547 if (Present (Expr) and then Nkind (Expr) = N_Integer_Literal)
1548 or else (A_Id in Boolean_Aspects and then No (Expr))
1549 then
1550 Delay_Required := False;
1551 else
1552 Delay_Required := True;
1553 Set_Has_Delayed_Rep_Aspects (E);
1554 end if;
1555 end case;
1557 -- Processing based on specific aspect
1559 case A_Id is
1561 -- No_Aspect should be impossible
1563 when No_Aspect =>
1564 raise Program_Error;
1566 -- Case 1: Aspects corresponding to attribute definition
1567 -- clauses.
1569 when Aspect_Address |
1570 Aspect_Alignment |
1571 Aspect_Bit_Order |
1572 Aspect_Component_Size |
1573 Aspect_Constant_Indexing |
1574 Aspect_Default_Iterator |
1575 Aspect_Dispatching_Domain |
1576 Aspect_External_Tag |
1577 Aspect_Input |
1578 Aspect_Iterable |
1579 Aspect_Iterator_Element |
1580 Aspect_Machine_Radix |
1581 Aspect_Object_Size |
1582 Aspect_Output |
1583 Aspect_Read |
1584 Aspect_Scalar_Storage_Order |
1585 Aspect_Size |
1586 Aspect_Small |
1587 Aspect_Simple_Storage_Pool |
1588 Aspect_Storage_Pool |
1589 Aspect_Stream_Size |
1590 Aspect_Value_Size |
1591 Aspect_Variable_Indexing |
1592 Aspect_Write =>
1594 -- Indexing aspects apply only to tagged type
1596 if (A_Id = Aspect_Constant_Indexing
1597 or else
1598 A_Id = Aspect_Variable_Indexing)
1599 and then not (Is_Type (E)
1600 and then Is_Tagged_Type (E))
1601 then
1602 Error_Msg_N ("indexing applies to a tagged type", N);
1603 goto Continue;
1604 end if;
1606 -- For the case of aspect Address, we don't consider that we
1607 -- know the entity is never set in the source, since it is
1608 -- is likely aliasing is occurring.
1610 -- Note: one might think that the analysis of the resulting
1611 -- attribute definition clause would take care of that, but
1612 -- that's not the case since it won't be from source.
1614 if A_Id = Aspect_Address then
1615 Set_Never_Set_In_Source (E, False);
1616 end if;
1618 -- Construct the attribute definition clause
1620 Aitem :=
1621 Make_Attribute_Definition_Clause (Loc,
1622 Name => Ent,
1623 Chars => Chars (Id),
1624 Expression => Relocate_Node (Expr));
1626 -- If the address is specified, then we treat the entity as
1627 -- referenced, to avoid spurious warnings. This is analogous
1628 -- to what is done with an attribute definition clause, but
1629 -- here we don't want to generate a reference because this
1630 -- is the point of definition of the entity.
1632 if A_Id = Aspect_Address then
1633 Set_Referenced (E);
1634 end if;
1636 -- Case 2: Aspects corresponding to pragmas
1638 -- Case 2a: Aspects corresponding to pragmas with two
1639 -- arguments, where the first argument is a local name
1640 -- referring to the entity, and the second argument is the
1641 -- aspect definition expression.
1643 -- Linker_Section/Suppress/Unsuppress
1645 when Aspect_Linker_Section |
1646 Aspect_Suppress |
1647 Aspect_Unsuppress =>
1649 Make_Aitem_Pragma
1650 (Pragma_Argument_Associations => New_List (
1651 Make_Pragma_Argument_Association (Loc,
1652 Expression => New_Occurrence_Of (E, Loc)),
1653 Make_Pragma_Argument_Association (Sloc (Expr),
1654 Expression => Relocate_Node (Expr))),
1655 Pragma_Name => Chars (Id));
1657 -- Synchronization
1659 -- Corresponds to pragma Implemented, construct the pragma
1661 when Aspect_Synchronization =>
1663 Make_Aitem_Pragma
1664 (Pragma_Argument_Associations => New_List (
1665 Make_Pragma_Argument_Association (Loc,
1666 Expression => New_Occurrence_Of (E, Loc)),
1667 Make_Pragma_Argument_Association (Sloc (Expr),
1668 Expression => Relocate_Node (Expr))),
1669 Pragma_Name => Name_Implemented);
1671 -- Attach Handler
1673 when Aspect_Attach_Handler =>
1674 Make_Aitem_Pragma
1675 (Pragma_Argument_Associations => New_List (
1676 Make_Pragma_Argument_Association (Sloc (Ent),
1677 Expression => Ent),
1678 Make_Pragma_Argument_Association (Sloc (Expr),
1679 Expression => Relocate_Node (Expr))),
1680 Pragma_Name => Name_Attach_Handler);
1682 -- We need to insert this pragma into the tree to get proper
1683 -- processing and to look valid from a placement viewpoint.
1685 Insert_Delayed_Pragma (Aitem);
1686 goto Continue;
1688 -- Dynamic_Predicate, Predicate, Static_Predicate
1690 when Aspect_Dynamic_Predicate |
1691 Aspect_Predicate |
1692 Aspect_Static_Predicate =>
1694 -- Construct the pragma (always a pragma Predicate, with
1695 -- flags recording whether it is static/dynamic). We also
1696 -- set flags recording this in the type itself.
1698 Make_Aitem_Pragma
1699 (Pragma_Argument_Associations => New_List (
1700 Make_Pragma_Argument_Association (Sloc (Ent),
1701 Expression => Ent),
1702 Make_Pragma_Argument_Association (Sloc (Expr),
1703 Expression => Relocate_Node (Expr))),
1704 Pragma_Name => Name_Predicate);
1706 -- Mark type has predicates, and remember what kind of
1707 -- aspect lead to this predicate (we need this to access
1708 -- the right set of check policies later on).
1710 Set_Has_Predicates (E);
1712 if A_Id = Aspect_Dynamic_Predicate then
1713 Set_Has_Dynamic_Predicate_Aspect (E);
1714 elsif A_Id = Aspect_Static_Predicate then
1715 Set_Has_Static_Predicate_Aspect (E);
1716 end if;
1718 -- If the type is private, indicate that its completion
1719 -- has a freeze node, because that is the one that will
1720 -- be visible at freeze time.
1722 if Is_Private_Type (E) and then Present (Full_View (E)) then
1723 Set_Has_Predicates (Full_View (E));
1725 if A_Id = Aspect_Dynamic_Predicate then
1726 Set_Has_Dynamic_Predicate_Aspect (Full_View (E));
1727 elsif A_Id = Aspect_Static_Predicate then
1728 Set_Has_Static_Predicate_Aspect (Full_View (E));
1729 end if;
1731 Set_Has_Delayed_Aspects (Full_View (E));
1732 Ensure_Freeze_Node (Full_View (E));
1733 end if;
1735 -- Case 2b: Aspects corresponding to pragmas with two
1736 -- arguments, where the second argument is a local name
1737 -- referring to the entity, and the first argument is the
1738 -- aspect definition expression.
1740 -- Convention
1742 when Aspect_Convention =>
1744 -- The aspect may be part of the specification of an import
1745 -- or export pragma. Scan the aspect list to gather the
1746 -- other components, if any. The name of the generated
1747 -- pragma is one of Convention/Import/Export.
1749 declare
1750 P_Name : Name_Id;
1751 A_Name : Name_Id;
1752 A : Node_Id;
1753 Arg_List : List_Id;
1754 Found : Boolean;
1755 L_Assoc : Node_Id;
1756 E_Assoc : Node_Id;
1758 begin
1759 P_Name := Chars (Id);
1760 Found := False;
1761 Arg_List := New_List;
1762 L_Assoc := Empty;
1763 E_Assoc := Empty;
1765 A := First (L);
1766 while Present (A) loop
1767 A_Name := Chars (Identifier (A));
1769 if Nam_In (A_Name, Name_Import, Name_Export) then
1770 if Found then
1771 Error_Msg_N ("conflicting", A);
1772 else
1773 Found := True;
1774 end if;
1776 P_Name := A_Name;
1778 elsif A_Name = Name_Link_Name then
1779 L_Assoc :=
1780 Make_Pragma_Argument_Association (Loc,
1781 Chars => A_Name,
1782 Expression => Relocate_Node (Expression (A)));
1784 elsif A_Name = Name_External_Name then
1785 E_Assoc :=
1786 Make_Pragma_Argument_Association (Loc,
1787 Chars => A_Name,
1788 Expression => Relocate_Node (Expression (A)));
1789 end if;
1791 Next (A);
1792 end loop;
1794 Arg_List := New_List (
1795 Make_Pragma_Argument_Association (Sloc (Expr),
1796 Expression => Relocate_Node (Expr)),
1797 Make_Pragma_Argument_Association (Sloc (Ent),
1798 Expression => Ent));
1800 if Present (L_Assoc) then
1801 Append_To (Arg_List, L_Assoc);
1802 end if;
1804 if Present (E_Assoc) then
1805 Append_To (Arg_List, E_Assoc);
1806 end if;
1808 Make_Aitem_Pragma
1809 (Pragma_Argument_Associations => Arg_List,
1810 Pragma_Name => P_Name);
1811 end;
1813 -- CPU, Interrupt_Priority, Priority
1815 -- These three aspects can be specified for a subprogram spec
1816 -- or body, in which case we analyze the expression and export
1817 -- the value of the aspect.
1819 -- Previously, we generated an equivalent pragma for bodies
1820 -- (note that the specs cannot contain these pragmas). The
1821 -- pragma was inserted ahead of local declarations, rather than
1822 -- after the body. This leads to a certain duplication between
1823 -- the processing performed for the aspect and the pragma, but
1824 -- given the straightforward handling required it is simpler
1825 -- to duplicate than to translate the aspect in the spec into
1826 -- a pragma in the declarative part of the body.
1828 when Aspect_CPU |
1829 Aspect_Interrupt_Priority |
1830 Aspect_Priority =>
1832 if Nkind_In (N, N_Subprogram_Body,
1833 N_Subprogram_Declaration)
1834 then
1835 -- Analyze the aspect expression
1837 Analyze_And_Resolve (Expr, Standard_Integer);
1839 -- Interrupt_Priority aspect not allowed for main
1840 -- subprograms. ARM D.1 does not forbid this explicitly,
1841 -- but ARM J.15.11 (6/3) does not permit pragma
1842 -- Interrupt_Priority for subprograms.
1844 if A_Id = Aspect_Interrupt_Priority then
1845 Error_Msg_N
1846 ("Interrupt_Priority aspect cannot apply to "
1847 & "subprogram", Expr);
1849 -- The expression must be static
1851 elsif not Is_Static_Expression (Expr) then
1852 Flag_Non_Static_Expr
1853 ("aspect requires static expression!", Expr);
1855 -- Check whether this is the main subprogram. Issue a
1856 -- warning only if it is obviously not a main program
1857 -- (when it has parameters or when the subprogram is
1858 -- within a package).
1860 elsif Present (Parameter_Specifications
1861 (Specification (N)))
1862 or else not Is_Compilation_Unit (Defining_Entity (N))
1863 then
1864 -- See ARM D.1 (14/3) and D.16 (12/3)
1866 Error_Msg_N
1867 ("aspect applied to subprogram other than the "
1868 & "main subprogram has no effect??", Expr);
1870 -- Otherwise check in range and export the value
1872 -- For the CPU aspect
1874 elsif A_Id = Aspect_CPU then
1875 if Is_In_Range (Expr, RTE (RE_CPU_Range)) then
1877 -- Value is correct so we export the value to make
1878 -- it available at execution time.
1880 Set_Main_CPU
1881 (Main_Unit, UI_To_Int (Expr_Value (Expr)));
1883 else
1884 Error_Msg_N
1885 ("main subprogram CPU is out of range", Expr);
1886 end if;
1888 -- For the Priority aspect
1890 elsif A_Id = Aspect_Priority then
1891 if Is_In_Range (Expr, RTE (RE_Priority)) then
1893 -- Value is correct so we export the value to make
1894 -- it available at execution time.
1896 Set_Main_Priority
1897 (Main_Unit, UI_To_Int (Expr_Value (Expr)));
1899 -- Ignore pragma if Relaxed_RM_Semantics to support
1900 -- other targets/non GNAT compilers.
1902 elsif not Relaxed_RM_Semantics then
1903 Error_Msg_N
1904 ("main subprogram priority is out of range",
1905 Expr);
1906 end if;
1907 end if;
1909 -- Load an arbitrary entity from System.Tasking.Stages
1910 -- or System.Tasking.Restricted.Stages (depending on
1911 -- the supported profile) to make sure that one of these
1912 -- packages is implicitly with'ed, since we need to have
1913 -- the tasking run time active for the pragma Priority to
1914 -- have any effect. Previously with with'ed the package
1915 -- System.Tasking, but this package does not trigger the
1916 -- required initialization of the run-time library.
1918 declare
1919 Discard : Entity_Id;
1920 pragma Warnings (Off, Discard);
1921 begin
1922 if Restricted_Profile then
1923 Discard := RTE (RE_Activate_Restricted_Tasks);
1924 else
1925 Discard := RTE (RE_Activate_Tasks);
1926 end if;
1927 end;
1929 -- Handling for these Aspects in subprograms is complete
1931 goto Continue;
1933 -- For tasks
1935 else
1936 -- Pass the aspect as an attribute
1938 Aitem :=
1939 Make_Attribute_Definition_Clause (Loc,
1940 Name => Ent,
1941 Chars => Chars (Id),
1942 Expression => Relocate_Node (Expr));
1943 end if;
1945 -- Warnings
1947 when Aspect_Warnings =>
1948 Make_Aitem_Pragma
1949 (Pragma_Argument_Associations => New_List (
1950 Make_Pragma_Argument_Association (Sloc (Expr),
1951 Expression => Relocate_Node (Expr)),
1952 Make_Pragma_Argument_Association (Loc,
1953 Expression => New_Occurrence_Of (E, Loc))),
1954 Pragma_Name => Chars (Id));
1956 -- Case 2c: Aspects corresponding to pragmas with three
1957 -- arguments.
1959 -- Invariant aspects have a first argument that references the
1960 -- entity, a second argument that is the expression and a third
1961 -- argument that is an appropriate message.
1963 -- Invariant, Type_Invariant
1965 when Aspect_Invariant |
1966 Aspect_Type_Invariant =>
1968 -- Analysis of the pragma will verify placement legality:
1969 -- an invariant must apply to a private type, or appear in
1970 -- the private part of a spec and apply to a completion.
1972 Make_Aitem_Pragma
1973 (Pragma_Argument_Associations => New_List (
1974 Make_Pragma_Argument_Association (Sloc (Ent),
1975 Expression => Ent),
1976 Make_Pragma_Argument_Association (Sloc (Expr),
1977 Expression => Relocate_Node (Expr))),
1978 Pragma_Name => Name_Invariant);
1980 -- Add message unless exception messages are suppressed
1982 if not Opt.Exception_Locations_Suppressed then
1983 Append_To (Pragma_Argument_Associations (Aitem),
1984 Make_Pragma_Argument_Association (Eloc,
1985 Chars => Name_Message,
1986 Expression =>
1987 Make_String_Literal (Eloc,
1988 Strval => "failed invariant from "
1989 & Build_Location_String (Eloc))));
1990 end if;
1992 -- For Invariant case, insert immediately after the entity
1993 -- declaration. We do not have to worry about delay issues
1994 -- since the pragma processing takes care of this.
1996 Delay_Required := False;
1998 -- Case 2d : Aspects that correspond to a pragma with one
1999 -- argument.
2001 -- Abstract_State
2003 -- Aspect Abstract_State introduces implicit declarations for
2004 -- all state abstraction entities it defines. To emulate this
2005 -- behavior, insert the pragma at the beginning of the visible
2006 -- declarations of the related package so that it is analyzed
2007 -- immediately.
2009 when Aspect_Abstract_State => Abstract_State : declare
2010 procedure Insert_After_SPARK_Mode
2011 (Ins_Nod : Node_Id;
2012 Decls : List_Id);
2013 -- Insert Aitem before node Ins_Nod. If Ins_Nod denotes
2014 -- pragma SPARK_Mode, then SPARK_Mode is skipped. Decls is
2015 -- the associated declarative list where Aitem is to reside.
2017 -----------------------------
2018 -- Insert_After_SPARK_Mode --
2019 -----------------------------
2021 procedure Insert_After_SPARK_Mode
2022 (Ins_Nod : Node_Id;
2023 Decls : List_Id)
2025 Decl : Node_Id := Ins_Nod;
2027 begin
2028 -- Skip SPARK_Mode
2030 if Present (Decl)
2031 and then Nkind (Decl) = N_Pragma
2032 and then Pragma_Name (Decl) = Name_SPARK_Mode
2033 then
2034 Decl := Next (Decl);
2035 end if;
2037 if Present (Decl) then
2038 Insert_Before (Decl, Aitem);
2040 -- Aitem acts as the last declaration
2042 else
2043 Append_To (Decls, Aitem);
2044 end if;
2045 end Insert_After_SPARK_Mode;
2047 -- Local variables
2049 Context : Node_Id := N;
2050 Decl : Node_Id;
2051 Decls : List_Id;
2053 -- Start of processing for Abstract_State
2055 begin
2056 -- When aspect Abstract_State appears on a generic package,
2057 -- it is propageted to the package instance. The context in
2058 -- this case is the instance spec.
2060 if Nkind (Context) = N_Package_Instantiation then
2061 Context := Instance_Spec (Context);
2062 end if;
2064 if Nkind_In (Context, N_Generic_Package_Declaration,
2065 N_Package_Declaration)
2066 then
2067 Make_Aitem_Pragma
2068 (Pragma_Argument_Associations => New_List (
2069 Make_Pragma_Argument_Association (Loc,
2070 Expression => Relocate_Node (Expr))),
2071 Pragma_Name => Name_Abstract_State);
2072 Decorate_Aspect_And_Pragma (Aspect, Aitem);
2074 Decls := Visible_Declarations (Specification (Context));
2076 -- In general pragma Abstract_State must be at the top
2077 -- of the existing visible declarations to emulate its
2078 -- source counterpart. The only exception to this is a
2079 -- generic instance in which case the pragma must be
2080 -- inserted after the association renamings.
2082 if Present (Decls) then
2084 -- The visible declarations of a generic instance have
2085 -- the following structure:
2087 -- <renamings of generic formals>
2088 -- <renamings of internally-generated spec and body>
2089 -- <first source declaration>
2091 -- The pragma must be inserted before the first source
2092 -- declaration.
2094 if Is_Generic_Instance (Defining_Entity (Context)) then
2096 -- Skip the instance "header"
2098 Decl := First (Decls);
2099 while Present (Decl)
2100 and then not Comes_From_Source (Decl)
2101 loop
2102 Decl := Next (Decl);
2103 end loop;
2105 -- Pragma Abstract_State must be inserted after
2106 -- pragma SPARK_Mode in the tree. This ensures that
2107 -- any error messages dependent on SPARK_Mode will
2108 -- be properly enabled/suppressed.
2110 Insert_After_SPARK_Mode (Decl, Decls);
2112 -- The related package is not a generic instance, the
2113 -- corresponding pragma must be the first declaration
2114 -- except when SPARK_Mode is already in the list. In
2115 -- that case pragma Abstract_State is placed second.
2117 else
2118 Insert_After_SPARK_Mode (First (Decls), Decls);
2119 end if;
2121 -- Otherwise the pragma forms a new declarative list
2123 else
2124 Set_Visible_Declarations
2125 (Specification (Context), New_List (Aitem));
2126 end if;
2128 else
2129 Error_Msg_NE
2130 ("aspect & must apply to a package declaration",
2131 Aspect, Id);
2132 end if;
2134 goto Continue;
2135 end Abstract_State;
2137 -- Depends
2139 -- Aspect Depends must be delayed because it mentions names
2140 -- of inputs and output that are classified by aspect Global.
2141 -- The aspect and pragma are treated the same way as a post
2142 -- condition.
2144 when Aspect_Depends =>
2145 Make_Aitem_Pragma
2146 (Pragma_Argument_Associations => New_List (
2147 Make_Pragma_Argument_Association (Loc,
2148 Expression => Relocate_Node (Expr))),
2149 Pragma_Name => Name_Depends);
2151 Decorate_Aspect_And_Pragma
2152 (Aspect, Aitem, Delayed => True);
2153 Insert_Delayed_Pragma (Aitem);
2154 goto Continue;
2156 -- Global
2158 -- Aspect Global must be delayed because it can mention names
2159 -- and benefit from the forward visibility rules applicable to
2160 -- aspects of subprograms. The aspect and pragma are treated
2161 -- the same way as a post condition.
2163 when Aspect_Global =>
2164 Make_Aitem_Pragma
2165 (Pragma_Argument_Associations => New_List (
2166 Make_Pragma_Argument_Association (Loc,
2167 Expression => Relocate_Node (Expr))),
2168 Pragma_Name => Name_Global);
2170 Decorate_Aspect_And_Pragma
2171 (Aspect, Aitem, Delayed => True);
2172 Insert_Delayed_Pragma (Aitem);
2173 goto Continue;
2175 -- Initial_Condition
2177 -- Aspect Initial_Condition covers the visible declarations of
2178 -- a package and all hidden states through functions. As such,
2179 -- it must be evaluated at the end of the said declarations.
2181 when Aspect_Initial_Condition => Initial_Condition : declare
2182 Context : Node_Id := N;
2183 Decls : List_Id;
2185 begin
2186 -- When aspect Abstract_State appears on a generic package,
2187 -- it is propageted to the package instance. The context in
2188 -- this case is the instance spec.
2190 if Nkind (Context) = N_Package_Instantiation then
2191 Context := Instance_Spec (Context);
2192 end if;
2194 if Nkind_In (Context, N_Generic_Package_Declaration,
2195 N_Package_Declaration)
2196 then
2197 Decls := Visible_Declarations (Specification (Context));
2199 Make_Aitem_Pragma
2200 (Pragma_Argument_Associations => New_List (
2201 Make_Pragma_Argument_Association (Loc,
2202 Expression => Relocate_Node (Expr))),
2203 Pragma_Name =>
2204 Name_Initial_Condition);
2206 Decorate_Aspect_And_Pragma
2207 (Aspect, Aitem, Delayed => True);
2209 if No (Decls) then
2210 Decls := New_List;
2211 Set_Visible_Declarations (Context, Decls);
2212 end if;
2214 Prepend_To (Decls, Aitem);
2216 else
2217 Error_Msg_NE
2218 ("aspect & must apply to a package declaration",
2219 Aspect, Id);
2220 end if;
2222 goto Continue;
2223 end Initial_Condition;
2225 -- Initializes
2227 -- Aspect Initializes coverts the visible declarations of a
2228 -- package. As such, it must be evaluated at the end of the
2229 -- said declarations.
2231 when Aspect_Initializes => Initializes : declare
2232 Context : Node_Id := N;
2233 Decls : List_Id;
2235 begin
2236 -- When aspect Abstract_State appears on a generic package,
2237 -- it is propageted to the package instance. The context in
2238 -- this case is the instance spec.
2240 if Nkind (Context) = N_Package_Instantiation then
2241 Context := Instance_Spec (Context);
2242 end if;
2244 if Nkind_In (Context, N_Generic_Package_Declaration,
2245 N_Package_Declaration)
2246 then
2247 Decls := Visible_Declarations (Specification (Context));
2249 Make_Aitem_Pragma
2250 (Pragma_Argument_Associations => New_List (
2251 Make_Pragma_Argument_Association (Loc,
2252 Expression => Relocate_Node (Expr))),
2253 Pragma_Name => Name_Initializes);
2255 Decorate_Aspect_And_Pragma
2256 (Aspect, Aitem, Delayed => True);
2258 if No (Decls) then
2259 Decls := New_List;
2260 Set_Visible_Declarations (Context, Decls);
2261 end if;
2263 Prepend_To (Decls, Aitem);
2265 else
2266 Error_Msg_NE
2267 ("aspect & must apply to a package declaration",
2268 Aspect, Id);
2269 end if;
2271 goto Continue;
2272 end Initializes;
2274 -- Part_Of
2276 when Aspect_Part_Of =>
2277 if Nkind_In (N, N_Object_Declaration,
2278 N_Package_Instantiation)
2279 then
2280 Make_Aitem_Pragma
2281 (Pragma_Argument_Associations => New_List (
2282 Make_Pragma_Argument_Association (Loc,
2283 Expression => Relocate_Node (Expr))),
2284 Pragma_Name => Name_Part_Of);
2286 else
2287 Error_Msg_NE
2288 ("aspect & must apply to a variable or package "
2289 & "instantiation", Aspect, Id);
2290 end if;
2292 -- SPARK_Mode
2294 when Aspect_SPARK_Mode => SPARK_Mode : declare
2295 Decls : List_Id;
2297 begin
2298 Make_Aitem_Pragma
2299 (Pragma_Argument_Associations => New_List (
2300 Make_Pragma_Argument_Association (Loc,
2301 Expression => Relocate_Node (Expr))),
2302 Pragma_Name => Name_SPARK_Mode);
2304 -- When the aspect appears on a package body, insert the
2305 -- generated pragma at the top of the body declarations to
2306 -- emulate the behavior of a source pragma.
2308 if Nkind (N) = N_Package_Body then
2309 Decorate_Aspect_And_Pragma (Aspect, Aitem);
2311 Decls := Declarations (N);
2313 if No (Decls) then
2314 Decls := New_List;
2315 Set_Declarations (N, Decls);
2316 end if;
2318 Prepend_To (Decls, Aitem);
2319 goto Continue;
2321 -- When the aspect is associated with package declaration,
2322 -- insert the generated pragma at the top of the visible
2323 -- declarations to emulate the behavior of a source pragma.
2325 elsif Nkind (N) = N_Package_Declaration then
2326 Decorate_Aspect_And_Pragma (Aspect, Aitem);
2328 Decls := Visible_Declarations (Specification (N));
2330 if No (Decls) then
2331 Decls := New_List;
2332 Set_Visible_Declarations (Specification (N), Decls);
2333 end if;
2335 Prepend_To (Decls, Aitem);
2336 goto Continue;
2337 end if;
2338 end SPARK_Mode;
2340 -- Refined_Depends
2342 -- Aspect Refined_Depends must be delayed because it can
2343 -- mention state refinements introduced by aspect Refined_State
2344 -- and further classified by aspect Refined_Global. Since both
2345 -- those aspects are delayed, so is Refined_Depends.
2347 when Aspect_Refined_Depends =>
2348 Make_Aitem_Pragma
2349 (Pragma_Argument_Associations => New_List (
2350 Make_Pragma_Argument_Association (Loc,
2351 Expression => Relocate_Node (Expr))),
2352 Pragma_Name => Name_Refined_Depends);
2354 Decorate_Aspect_And_Pragma
2355 (Aspect, Aitem, Delayed => True);
2356 Insert_Delayed_Pragma (Aitem);
2357 goto Continue;
2359 -- Refined_Global
2361 -- Aspect Refined_Global must be delayed because it can mention
2362 -- state refinements introduced by aspect Refined_State. Since
2363 -- Refined_State is already delayed due to forward references,
2364 -- so is Refined_Global.
2366 when Aspect_Refined_Global =>
2367 Make_Aitem_Pragma
2368 (Pragma_Argument_Associations => New_List (
2369 Make_Pragma_Argument_Association (Loc,
2370 Expression => Relocate_Node (Expr))),
2371 Pragma_Name => Name_Refined_Global);
2373 Decorate_Aspect_And_Pragma (Aspect, Aitem, Delayed => True);
2374 Insert_Delayed_Pragma (Aitem);
2375 goto Continue;
2377 -- Refined_Post
2379 when Aspect_Refined_Post =>
2380 Make_Aitem_Pragma
2381 (Pragma_Argument_Associations => New_List (
2382 Make_Pragma_Argument_Association (Loc,
2383 Expression => Relocate_Node (Expr))),
2384 Pragma_Name => Name_Refined_Post);
2386 -- Refined_State
2388 when Aspect_Refined_State => Refined_State : declare
2389 Decl : Node_Id;
2390 Decls : List_Id;
2392 begin
2393 -- The corresponding pragma for Refined_State is inserted in
2394 -- the declarations of the related package body. This action
2395 -- synchronizes both the source and from-aspect versions of
2396 -- the pragma.
2398 if Nkind (N) = N_Package_Body then
2399 Make_Aitem_Pragma
2400 (Pragma_Argument_Associations => New_List (
2401 Make_Pragma_Argument_Association (Loc,
2402 Expression => Relocate_Node (Expr))),
2403 Pragma_Name => Name_Refined_State);
2404 Decorate_Aspect_And_Pragma (Aspect, Aitem);
2406 Decls := Declarations (N);
2408 -- When the package body is subject to pragma SPARK_Mode,
2409 -- insert pragma Refined_State after SPARK_Mode.
2411 if Present (Decls) then
2412 Decl := First (Decls);
2414 if Nkind (Decl) = N_Pragma
2415 and then Pragma_Name (Decl) = Name_SPARK_Mode
2416 then
2417 Insert_After (Decl, Aitem);
2419 -- The related package body lacks SPARK_Mode, the
2420 -- corresponding pragma must be the first declaration.
2422 else
2423 Prepend_To (Decls, Aitem);
2424 end if;
2426 -- Otherwise the pragma forms a new declarative list
2428 else
2429 Set_Declarations (N, New_List (Aitem));
2430 end if;
2432 else
2433 Error_Msg_NE
2434 ("aspect & must apply to a package body", Aspect, Id);
2435 end if;
2437 goto Continue;
2438 end Refined_State;
2440 -- Relative_Deadline
2442 when Aspect_Relative_Deadline =>
2443 Make_Aitem_Pragma
2444 (Pragma_Argument_Associations => New_List (
2445 Make_Pragma_Argument_Association (Loc,
2446 Expression => Relocate_Node (Expr))),
2447 Pragma_Name => Name_Relative_Deadline);
2449 -- If the aspect applies to a task, the corresponding pragma
2450 -- must appear within its declarations, not after.
2452 if Nkind (N) = N_Task_Type_Declaration then
2453 declare
2454 Def : Node_Id;
2455 V : List_Id;
2457 begin
2458 if No (Task_Definition (N)) then
2459 Set_Task_Definition (N,
2460 Make_Task_Definition (Loc,
2461 Visible_Declarations => New_List,
2462 End_Label => Empty));
2463 end if;
2465 Def := Task_Definition (N);
2466 V := Visible_Declarations (Def);
2467 if not Is_Empty_List (V) then
2468 Insert_Before (First (V), Aitem);
2470 else
2471 Set_Visible_Declarations (Def, New_List (Aitem));
2472 end if;
2474 goto Continue;
2475 end;
2476 end if;
2478 -- Case 3 : Aspects that don't correspond to pragma/attribute
2479 -- definition clause.
2481 -- Case 3a: The aspects listed below don't correspond to
2482 -- pragmas/attributes but do require delayed analysis.
2484 -- Default_Value, Default_Component_Value
2486 when Aspect_Default_Value |
2487 Aspect_Default_Component_Value =>
2488 Aitem := Empty;
2490 -- Case 3b: The aspects listed below don't correspond to
2491 -- pragmas/attributes and don't need delayed analysis.
2493 -- Implicit_Dereference
2495 -- For Implicit_Dereference, External_Name and Link_Name, only
2496 -- the legality checks are done during the analysis, thus no
2497 -- delay is required.
2499 when Aspect_Implicit_Dereference =>
2500 Analyze_Aspect_Implicit_Dereference;
2501 goto Continue;
2503 -- External_Name, Link_Name
2505 when Aspect_External_Name |
2506 Aspect_Link_Name =>
2507 Analyze_Aspect_External_Or_Link_Name;
2508 goto Continue;
2510 -- Dimension
2512 when Aspect_Dimension =>
2513 Analyze_Aspect_Dimension (N, Id, Expr);
2514 goto Continue;
2516 -- Dimension_System
2518 when Aspect_Dimension_System =>
2519 Analyze_Aspect_Dimension_System (N, Id, Expr);
2520 goto Continue;
2522 -- Case 4: Aspects requiring special handling
2524 -- Pre/Post/Test_Case/Contract_Cases whose corresponding
2525 -- pragmas take care of the delay.
2527 -- Pre/Post
2529 -- Aspects Pre/Post generate Precondition/Postcondition pragmas
2530 -- with a first argument that is the expression, and a second
2531 -- argument that is an informative message if the test fails.
2532 -- This is inserted right after the declaration, to get the
2533 -- required pragma placement. The processing for the pragmas
2534 -- takes care of the required delay.
2536 when Pre_Post_Aspects => Pre_Post : declare
2537 Pname : Name_Id;
2539 begin
2540 if A_Id = Aspect_Pre or else A_Id = Aspect_Precondition then
2541 Pname := Name_Precondition;
2542 else
2543 Pname := Name_Postcondition;
2544 end if;
2546 -- If the expressions is of the form A and then B, then
2547 -- we generate separate Pre/Post aspects for the separate
2548 -- clauses. Since we allow multiple pragmas, there is no
2549 -- problem in allowing multiple Pre/Post aspects internally.
2550 -- These should be treated in reverse order (B first and
2551 -- A second) since they are later inserted just after N in
2552 -- the order they are treated. This way, the pragma for A
2553 -- ends up preceding the pragma for B, which may have an
2554 -- importance for the error raised (either constraint error
2555 -- or precondition error).
2557 -- We do not do this for Pre'Class, since we have to put
2558 -- these conditions together in a complex OR expression
2560 -- We do not do this in ASIS mode, as ASIS relies on the
2561 -- original node representing the complete expression, when
2562 -- retrieving it through the source aspect table.
2564 if not ASIS_Mode
2565 and then (Pname = Name_Postcondition
2566 or else not Class_Present (Aspect))
2567 then
2568 while Nkind (Expr) = N_And_Then loop
2569 Insert_After (Aspect,
2570 Make_Aspect_Specification (Sloc (Left_Opnd (Expr)),
2571 Identifier => Identifier (Aspect),
2572 Expression => Relocate_Node (Left_Opnd (Expr)),
2573 Class_Present => Class_Present (Aspect),
2574 Split_PPC => True));
2575 Rewrite (Expr, Relocate_Node (Right_Opnd (Expr)));
2576 Eloc := Sloc (Expr);
2577 end loop;
2578 end if;
2580 -- Build the precondition/postcondition pragma
2582 -- Add note about why we do NOT need Copy_Tree here ???
2584 Make_Aitem_Pragma
2585 (Pragma_Argument_Associations => New_List (
2586 Make_Pragma_Argument_Association (Eloc,
2587 Chars => Name_Check,
2588 Expression => Relocate_Node (Expr))),
2589 Pragma_Name => Pname);
2591 -- Add message unless exception messages are suppressed
2593 if not Opt.Exception_Locations_Suppressed then
2594 Append_To (Pragma_Argument_Associations (Aitem),
2595 Make_Pragma_Argument_Association (Eloc,
2596 Chars => Name_Message,
2597 Expression =>
2598 Make_String_Literal (Eloc,
2599 Strval => "failed "
2600 & Get_Name_String (Pname)
2601 & " from "
2602 & Build_Location_String (Eloc))));
2603 end if;
2605 Set_Is_Delayed_Aspect (Aspect);
2607 -- For Pre/Post cases, insert immediately after the entity
2608 -- declaration, since that is the required pragma placement.
2609 -- Note that for these aspects, we do not have to worry
2610 -- about delay issues, since the pragmas themselves deal
2611 -- with delay of visibility for the expression analysis.
2613 Insert_Delayed_Pragma (Aitem);
2614 goto Continue;
2615 end Pre_Post;
2617 -- Test_Case
2619 when Aspect_Test_Case => Test_Case : declare
2620 Args : List_Id;
2621 Comp_Expr : Node_Id;
2622 Comp_Assn : Node_Id;
2623 New_Expr : Node_Id;
2625 begin
2626 Args := New_List;
2628 if Nkind (Parent (N)) = N_Compilation_Unit then
2629 Error_Msg_Name_1 := Nam;
2630 Error_Msg_N ("incorrect placement of aspect `%`", E);
2631 goto Continue;
2632 end if;
2634 if Nkind (Expr) /= N_Aggregate then
2635 Error_Msg_Name_1 := Nam;
2636 Error_Msg_NE
2637 ("wrong syntax for aspect `%` for &", Id, E);
2638 goto Continue;
2639 end if;
2641 -- Make pragma expressions refer to the original aspect
2642 -- expressions through the Original_Node link. This is
2643 -- used in semantic analysis for ASIS mode, so that the
2644 -- original expression also gets analyzed.
2646 Comp_Expr := First (Expressions (Expr));
2647 while Present (Comp_Expr) loop
2648 New_Expr := Relocate_Node (Comp_Expr);
2649 Set_Original_Node (New_Expr, Comp_Expr);
2650 Append_To (Args,
2651 Make_Pragma_Argument_Association (Sloc (Comp_Expr),
2652 Expression => New_Expr));
2653 Next (Comp_Expr);
2654 end loop;
2656 Comp_Assn := First (Component_Associations (Expr));
2657 while Present (Comp_Assn) loop
2658 if List_Length (Choices (Comp_Assn)) /= 1
2659 or else
2660 Nkind (First (Choices (Comp_Assn))) /= N_Identifier
2661 then
2662 Error_Msg_Name_1 := Nam;
2663 Error_Msg_NE
2664 ("wrong syntax for aspect `%` for &", Id, E);
2665 goto Continue;
2666 end if;
2668 New_Expr := Relocate_Node (Expression (Comp_Assn));
2669 Set_Original_Node (New_Expr, Expression (Comp_Assn));
2670 Append_To (Args,
2671 Make_Pragma_Argument_Association (Sloc (Comp_Assn),
2672 Chars => Chars (First (Choices (Comp_Assn))),
2673 Expression => New_Expr));
2674 Next (Comp_Assn);
2675 end loop;
2677 -- Build the test-case pragma
2679 Make_Aitem_Pragma
2680 (Pragma_Argument_Associations => Args,
2681 Pragma_Name => Nam);
2682 end Test_Case;
2684 -- Contract_Cases
2686 when Aspect_Contract_Cases =>
2687 Make_Aitem_Pragma
2688 (Pragma_Argument_Associations => New_List (
2689 Make_Pragma_Argument_Association (Loc,
2690 Expression => Relocate_Node (Expr))),
2691 Pragma_Name => Nam);
2693 Decorate_Aspect_And_Pragma
2694 (Aspect, Aitem, Delayed => True);
2695 Insert_Delayed_Pragma (Aitem);
2696 goto Continue;
2698 -- Case 5: Special handling for aspects with an optional
2699 -- boolean argument.
2701 -- In the general case, the corresponding pragma cannot be
2702 -- generated yet because the evaluation of the boolean needs
2703 -- to be delayed till the freeze point.
2705 when Boolean_Aspects |
2706 Library_Unit_Aspects =>
2708 Set_Is_Boolean_Aspect (Aspect);
2710 -- Lock_Free aspect only apply to protected objects
2712 if A_Id = Aspect_Lock_Free then
2713 if Ekind (E) /= E_Protected_Type then
2714 Error_Msg_Name_1 := Nam;
2715 Error_Msg_N
2716 ("aspect % only applies to a protected object",
2717 Aspect);
2719 else
2720 -- Set the Uses_Lock_Free flag to True if there is no
2721 -- expression or if the expression is True. The
2722 -- evaluation of this aspect should be delayed to the
2723 -- freeze point (why???)
2725 if No (Expr)
2726 or else Is_True (Static_Boolean (Expr))
2727 then
2728 Set_Uses_Lock_Free (E);
2729 end if;
2731 Record_Rep_Item (E, Aspect);
2732 end if;
2734 goto Continue;
2736 elsif A_Id = Aspect_Import or else A_Id = Aspect_Export then
2738 -- For the case of aspects Import and Export, we don't
2739 -- consider that we know the entity is never set in the
2740 -- source, since it is is likely modified outside the
2741 -- program.
2743 -- Note: one might think that the analysis of the
2744 -- resulting pragma would take care of that, but
2745 -- that's not the case since it won't be from source.
2747 if Ekind (E) = E_Variable then
2748 Set_Never_Set_In_Source (E, False);
2749 end if;
2751 -- In older versions of Ada the corresponding pragmas
2752 -- specified a Convention. In Ada 2012 the convention
2753 -- is specified as a separate aspect, and it is optional,
2754 -- given that it defaults to Convention_Ada. The code
2755 -- that verifed that there was a matching convention
2756 -- is now obsolete.
2758 goto Continue;
2759 end if;
2761 -- Library unit aspects require special handling in the case
2762 -- of a package declaration, the pragma needs to be inserted
2763 -- in the list of declarations for the associated package.
2764 -- There is no issue of visibility delay for these aspects.
2766 if A_Id in Library_Unit_Aspects
2767 and then
2768 Nkind_In (N, N_Package_Declaration,
2769 N_Generic_Package_Declaration)
2770 and then Nkind (Parent (N)) /= N_Compilation_Unit
2771 then
2772 Error_Msg_N
2773 ("incorrect context for library unit aspect&", Id);
2774 goto Continue;
2775 end if;
2777 -- Cases where we do not delay, includes all cases where
2778 -- the expression is missing other than the above cases.
2780 if not Delay_Required or else No (Expr) then
2781 Make_Aitem_Pragma
2782 (Pragma_Argument_Associations => New_List (
2783 Make_Pragma_Argument_Association (Sloc (Ent),
2784 Expression => Ent)),
2785 Pragma_Name => Chars (Id));
2786 Delay_Required := False;
2788 -- In general cases, the corresponding pragma/attribute
2789 -- definition clause will be inserted later at the freezing
2790 -- point, and we do not need to build it now
2792 else
2793 Aitem := Empty;
2794 end if;
2796 -- Storage_Size
2798 -- This is special because for access types we need to generate
2799 -- an attribute definition clause. This also works for single
2800 -- task declarations, but it does not work for task type
2801 -- declarations, because we have the case where the expression
2802 -- references a discriminant of the task type. That can't use
2803 -- an attribute definition clause because we would not have
2804 -- visibility on the discriminant. For that case we must
2805 -- generate a pragma in the task definition.
2807 when Aspect_Storage_Size =>
2809 -- Task type case
2811 if Ekind (E) = E_Task_Type then
2812 declare
2813 Decl : constant Node_Id := Declaration_Node (E);
2815 begin
2816 pragma Assert (Nkind (Decl) = N_Task_Type_Declaration);
2818 -- If no task definition, create one
2820 if No (Task_Definition (Decl)) then
2821 Set_Task_Definition (Decl,
2822 Make_Task_Definition (Loc,
2823 Visible_Declarations => Empty_List,
2824 End_Label => Empty));
2825 end if;
2827 -- Create a pragma and put it at the start of the
2828 -- task definition for the task type declaration.
2830 Make_Aitem_Pragma
2831 (Pragma_Argument_Associations => New_List (
2832 Make_Pragma_Argument_Association (Loc,
2833 Expression => Relocate_Node (Expr))),
2834 Pragma_Name => Name_Storage_Size);
2836 Prepend
2837 (Aitem,
2838 Visible_Declarations (Task_Definition (Decl)));
2839 goto Continue;
2840 end;
2842 -- All other cases, generate attribute definition
2844 else
2845 Aitem :=
2846 Make_Attribute_Definition_Clause (Loc,
2847 Name => Ent,
2848 Chars => Chars (Id),
2849 Expression => Relocate_Node (Expr));
2850 end if;
2851 end case;
2853 -- Attach the corresponding pragma/attribute definition clause to
2854 -- the aspect specification node.
2856 if Present (Aitem) then
2857 Set_From_Aspect_Specification (Aitem, True);
2858 end if;
2860 -- In the context of a compilation unit, we directly put the
2861 -- pragma in the Pragmas_After list of the N_Compilation_Unit_Aux
2862 -- node (no delay is required here) except for aspects on a
2863 -- subprogram body (see below) and a generic package, for which
2864 -- we need to introduce the pragma before building the generic
2865 -- copy (see sem_ch12), and for package instantiations, where
2866 -- the library unit pragmas are better handled early.
2868 if Nkind (Parent (N)) = N_Compilation_Unit
2869 and then (Present (Aitem) or else Is_Boolean_Aspect (Aspect))
2870 then
2871 declare
2872 Aux : constant Node_Id := Aux_Decls_Node (Parent (N));
2874 begin
2875 pragma Assert (Nkind (Aux) = N_Compilation_Unit_Aux);
2877 -- For a Boolean aspect, create the corresponding pragma if
2878 -- no expression or if the value is True.
2880 if Is_Boolean_Aspect (Aspect) and then No (Aitem) then
2881 if Is_True (Static_Boolean (Expr)) then
2882 Make_Aitem_Pragma
2883 (Pragma_Argument_Associations => New_List (
2884 Make_Pragma_Argument_Association (Sloc (Ent),
2885 Expression => Ent)),
2886 Pragma_Name => Chars (Id));
2888 Set_From_Aspect_Specification (Aitem, True);
2889 Set_Corresponding_Aspect (Aitem, Aspect);
2891 else
2892 goto Continue;
2893 end if;
2894 end if;
2896 -- If the aspect is on a subprogram body (relevant aspect
2897 -- is Inline), add the pragma in front of the declarations.
2899 if Nkind (N) = N_Subprogram_Body then
2900 if No (Declarations (N)) then
2901 Set_Declarations (N, New_List);
2902 end if;
2904 Prepend (Aitem, Declarations (N));
2906 elsif Nkind (N) = N_Generic_Package_Declaration then
2907 if No (Visible_Declarations (Specification (N))) then
2908 Set_Visible_Declarations (Specification (N), New_List);
2909 end if;
2911 Prepend (Aitem,
2912 Visible_Declarations (Specification (N)));
2914 elsif Nkind (N) = N_Package_Instantiation then
2915 declare
2916 Spec : constant Node_Id :=
2917 Specification (Instance_Spec (N));
2918 begin
2919 if No (Visible_Declarations (Spec)) then
2920 Set_Visible_Declarations (Spec, New_List);
2921 end if;
2923 Prepend (Aitem, Visible_Declarations (Spec));
2924 end;
2926 else
2927 if No (Pragmas_After (Aux)) then
2928 Set_Pragmas_After (Aux, New_List);
2929 end if;
2931 Append (Aitem, Pragmas_After (Aux));
2932 end if;
2934 goto Continue;
2935 end;
2936 end if;
2938 -- The evaluation of the aspect is delayed to the freezing point.
2939 -- The pragma or attribute clause if there is one is then attached
2940 -- to the aspect specification which is put in the rep item list.
2942 if Delay_Required then
2943 if Present (Aitem) then
2944 Set_Is_Delayed_Aspect (Aitem);
2945 Set_Aspect_Rep_Item (Aspect, Aitem);
2946 Set_Parent (Aitem, Aspect);
2947 end if;
2949 Set_Is_Delayed_Aspect (Aspect);
2951 -- In the case of Default_Value, link the aspect to base type
2952 -- as well, even though it appears on a first subtype. This is
2953 -- mandated by the semantics of the aspect. Do not establish
2954 -- the link when processing the base type itself as this leads
2955 -- to a rep item circularity. Verify that we are dealing with
2956 -- a scalar type to prevent cascaded errors.
2958 if A_Id = Aspect_Default_Value
2959 and then Is_Scalar_Type (E)
2960 and then Base_Type (E) /= E
2961 then
2962 Set_Has_Delayed_Aspects (Base_Type (E));
2963 Record_Rep_Item (Base_Type (E), Aspect);
2964 end if;
2966 Set_Has_Delayed_Aspects (E);
2967 Record_Rep_Item (E, Aspect);
2969 -- When delay is not required and the context is a package or a
2970 -- subprogram body, insert the pragma in the body declarations.
2972 elsif Nkind_In (N, N_Package_Body, N_Subprogram_Body) then
2973 if No (Declarations (N)) then
2974 Set_Declarations (N, New_List);
2975 end if;
2977 -- The pragma is added before source declarations
2979 Prepend_To (Declarations (N), Aitem);
2981 -- When delay is not required and the context is not a compilation
2982 -- unit, we simply insert the pragma/attribute definition clause
2983 -- in sequence.
2985 else
2986 Insert_After (Ins_Node, Aitem);
2987 Ins_Node := Aitem;
2988 end if;
2989 end Analyze_One_Aspect;
2991 <<Continue>>
2992 Next (Aspect);
2993 end loop Aspect_Loop;
2995 if Has_Delayed_Aspects (E) then
2996 Ensure_Freeze_Node (E);
2997 end if;
2998 end Analyze_Aspect_Specifications;
3000 -----------------------
3001 -- Analyze_At_Clause --
3002 -----------------------
3004 -- An at clause is replaced by the corresponding Address attribute
3005 -- definition clause that is the preferred approach in Ada 95.
3007 procedure Analyze_At_Clause (N : Node_Id) is
3008 CS : constant Boolean := Comes_From_Source (N);
3010 begin
3011 -- This is an obsolescent feature
3013 Check_Restriction (No_Obsolescent_Features, N);
3015 if Warn_On_Obsolescent_Feature then
3016 Error_Msg_N
3017 ("?j?at clause is an obsolescent feature (RM J.7(2))", N);
3018 Error_Msg_N
3019 ("\?j?use address attribute definition clause instead", N);
3020 end if;
3022 -- Rewrite as address clause
3024 Rewrite (N,
3025 Make_Attribute_Definition_Clause (Sloc (N),
3026 Name => Identifier (N),
3027 Chars => Name_Address,
3028 Expression => Expression (N)));
3030 -- We preserve Comes_From_Source, since logically the clause still comes
3031 -- from the source program even though it is changed in form.
3033 Set_Comes_From_Source (N, CS);
3035 -- Analyze rewritten clause
3037 Analyze_Attribute_Definition_Clause (N);
3038 end Analyze_At_Clause;
3040 -----------------------------------------
3041 -- Analyze_Attribute_Definition_Clause --
3042 -----------------------------------------
3044 procedure Analyze_Attribute_Definition_Clause (N : Node_Id) is
3045 Loc : constant Source_Ptr := Sloc (N);
3046 Nam : constant Node_Id := Name (N);
3047 Attr : constant Name_Id := Chars (N);
3048 Expr : constant Node_Id := Expression (N);
3049 Id : constant Attribute_Id := Get_Attribute_Id (Attr);
3051 Ent : Entity_Id;
3052 -- The entity of Nam after it is analyzed. In the case of an incomplete
3053 -- type, this is the underlying type.
3055 U_Ent : Entity_Id;
3056 -- The underlying entity to which the attribute applies. Generally this
3057 -- is the Underlying_Type of Ent, except in the case where the clause
3058 -- applies to full view of incomplete type or private type in which case
3059 -- U_Ent is just a copy of Ent.
3061 FOnly : Boolean := False;
3062 -- Reset to True for subtype specific attribute (Alignment, Size)
3063 -- and for stream attributes, i.e. those cases where in the call
3064 -- to Rep_Item_Too_Late, FOnly is set True so that only the freezing
3065 -- rules are checked. Note that the case of stream attributes is not
3066 -- clear from the RM, but see AI95-00137. Also, the RM seems to
3067 -- disallow Storage_Size for derived task types, but that is also
3068 -- clearly unintentional.
3070 procedure Analyze_Stream_TSS_Definition (TSS_Nam : TSS_Name_Type);
3071 -- Common processing for 'Read, 'Write, 'Input and 'Output attribute
3072 -- definition clauses.
3074 function Duplicate_Clause return Boolean;
3075 -- This routine checks if the aspect for U_Ent being given by attribute
3076 -- definition clause N is for an aspect that has already been specified,
3077 -- and if so gives an error message. If there is a duplicate, True is
3078 -- returned, otherwise if there is no error, False is returned.
3080 procedure Check_Indexing_Functions;
3081 -- Check that the function in Constant_Indexing or Variable_Indexing
3082 -- attribute has the proper type structure. If the name is overloaded,
3083 -- check that some interpretation is legal.
3085 procedure Check_Iterator_Functions;
3086 -- Check that there is a single function in Default_Iterator attribute
3087 -- has the proper type structure.
3089 function Check_Primitive_Function (Subp : Entity_Id) return Boolean;
3090 -- Common legality check for the previous two
3092 -----------------------------------
3093 -- Analyze_Stream_TSS_Definition --
3094 -----------------------------------
3096 procedure Analyze_Stream_TSS_Definition (TSS_Nam : TSS_Name_Type) is
3097 Subp : Entity_Id := Empty;
3098 I : Interp_Index;
3099 It : Interp;
3100 Pnam : Entity_Id;
3102 Is_Read : constant Boolean := (TSS_Nam = TSS_Stream_Read);
3103 -- True for Read attribute, false for other attributes
3105 function Has_Good_Profile (Subp : Entity_Id) return Boolean;
3106 -- Return true if the entity is a subprogram with an appropriate
3107 -- profile for the attribute being defined.
3109 ----------------------
3110 -- Has_Good_Profile --
3111 ----------------------
3113 function Has_Good_Profile (Subp : Entity_Id) return Boolean is
3114 F : Entity_Id;
3115 Is_Function : constant Boolean := (TSS_Nam = TSS_Stream_Input);
3116 Expected_Ekind : constant array (Boolean) of Entity_Kind :=
3117 (False => E_Procedure, True => E_Function);
3118 Typ : Entity_Id;
3120 begin
3121 if Ekind (Subp) /= Expected_Ekind (Is_Function) then
3122 return False;
3123 end if;
3125 F := First_Formal (Subp);
3127 if No (F)
3128 or else Ekind (Etype (F)) /= E_Anonymous_Access_Type
3129 or else Designated_Type (Etype (F)) /=
3130 Class_Wide_Type (RTE (RE_Root_Stream_Type))
3131 then
3132 return False;
3133 end if;
3135 if not Is_Function then
3136 Next_Formal (F);
3138 declare
3139 Expected_Mode : constant array (Boolean) of Entity_Kind :=
3140 (False => E_In_Parameter,
3141 True => E_Out_Parameter);
3142 begin
3143 if Parameter_Mode (F) /= Expected_Mode (Is_Read) then
3144 return False;
3145 end if;
3146 end;
3148 Typ := Etype (F);
3150 else
3151 Typ := Etype (Subp);
3152 end if;
3154 -- Verify that the prefix of the attribute and the local name
3155 -- for the type of the formal match.
3157 if Base_Type (Typ) /= Base_Type (Ent)
3158 or else Present ((Next_Formal (F)))
3159 then
3160 return False;
3162 elsif not Is_Scalar_Type (Typ)
3163 and then not Is_First_Subtype (Typ)
3164 and then not Is_Class_Wide_Type (Typ)
3165 then
3166 return False;
3168 else
3169 return True;
3170 end if;
3171 end Has_Good_Profile;
3173 -- Start of processing for Analyze_Stream_TSS_Definition
3175 begin
3176 FOnly := True;
3178 if not Is_Type (U_Ent) then
3179 Error_Msg_N ("local name must be a subtype", Nam);
3180 return;
3182 elsif not Is_First_Subtype (U_Ent) then
3183 Error_Msg_N ("local name must be a first subtype", Nam);
3184 return;
3185 end if;
3187 Pnam := TSS (Base_Type (U_Ent), TSS_Nam);
3189 -- If Pnam is present, it can be either inherited from an ancestor
3190 -- type (in which case it is legal to redefine it for this type), or
3191 -- be a previous definition of the attribute for the same type (in
3192 -- which case it is illegal).
3194 -- In the first case, it will have been analyzed already, and we
3195 -- can check that its profile does not match the expected profile
3196 -- for a stream attribute of U_Ent. In the second case, either Pnam
3197 -- has been analyzed (and has the expected profile), or it has not
3198 -- been analyzed yet (case of a type that has not been frozen yet
3199 -- and for which the stream attribute has been set using Set_TSS).
3201 if Present (Pnam)
3202 and then (No (First_Entity (Pnam)) or else Has_Good_Profile (Pnam))
3203 then
3204 Error_Msg_Sloc := Sloc (Pnam);
3205 Error_Msg_Name_1 := Attr;
3206 Error_Msg_N ("% attribute already defined #", Nam);
3207 return;
3208 end if;
3210 Analyze (Expr);
3212 if Is_Entity_Name (Expr) then
3213 if not Is_Overloaded (Expr) then
3214 if Has_Good_Profile (Entity (Expr)) then
3215 Subp := Entity (Expr);
3216 end if;
3218 else
3219 Get_First_Interp (Expr, I, It);
3220 while Present (It.Nam) loop
3221 if Has_Good_Profile (It.Nam) then
3222 Subp := It.Nam;
3223 exit;
3224 end if;
3226 Get_Next_Interp (I, It);
3227 end loop;
3228 end if;
3229 end if;
3231 if Present (Subp) then
3232 if Is_Abstract_Subprogram (Subp) then
3233 Error_Msg_N ("stream subprogram must not be abstract", Expr);
3234 return;
3236 -- Test for stream subprogram for interface type being non-null
3238 elsif Is_Interface (U_Ent)
3239 and then not Inside_A_Generic
3240 and then Ekind (Subp) = E_Procedure
3241 and then
3242 not Null_Present
3243 (Specification
3244 (Unit_Declaration_Node (Ultimate_Alias (Subp))))
3245 then
3246 Error_Msg_N
3247 ("stream subprogram for interface type "
3248 & "must be null procedure", Expr);
3249 end if;
3251 Set_Entity (Expr, Subp);
3252 Set_Etype (Expr, Etype (Subp));
3254 New_Stream_Subprogram (N, U_Ent, Subp, TSS_Nam);
3256 else
3257 Error_Msg_Name_1 := Attr;
3258 Error_Msg_N ("incorrect expression for% attribute", Expr);
3259 end if;
3260 end Analyze_Stream_TSS_Definition;
3262 ------------------------------
3263 -- Check_Indexing_Functions --
3264 ------------------------------
3266 procedure Check_Indexing_Functions is
3267 Indexing_Found : Boolean;
3269 procedure Check_One_Function (Subp : Entity_Id);
3270 -- Check one possible interpretation. Sets Indexing_Found True if an
3271 -- indexing function is found.
3273 ------------------------
3274 -- Check_One_Function --
3275 ------------------------
3277 procedure Check_One_Function (Subp : Entity_Id) is
3278 Default_Element : constant Node_Id :=
3279 Find_Value_Of_Aspect
3280 (Etype (First_Formal (Subp)),
3281 Aspect_Iterator_Element);
3283 begin
3284 if not Check_Primitive_Function (Subp)
3285 and then not Is_Overloaded (Expr)
3286 then
3287 Error_Msg_NE
3288 ("aspect Indexing requires a function that applies to type&",
3289 Subp, Ent);
3290 end if;
3292 -- An indexing function must return either the default element of
3293 -- the container, or a reference type. For variable indexing it
3294 -- must be the latter.
3296 if Present (Default_Element) then
3297 Analyze (Default_Element);
3299 if Is_Entity_Name (Default_Element)
3300 and then Covers (Entity (Default_Element), Etype (Subp))
3301 then
3302 Indexing_Found := True;
3303 return;
3304 end if;
3305 end if;
3307 -- For variable_indexing the return type must be a reference type
3309 if Attr = Name_Variable_Indexing
3310 and then not Has_Implicit_Dereference (Etype (Subp))
3311 then
3312 Error_Msg_N
3313 ("function for indexing must return a reference type", Subp);
3315 else
3316 Indexing_Found := True;
3317 end if;
3318 end Check_One_Function;
3320 -- Start of processing for Check_Indexing_Functions
3322 begin
3323 if In_Instance then
3324 return;
3325 end if;
3327 Analyze (Expr);
3329 if not Is_Overloaded (Expr) then
3330 Check_One_Function (Entity (Expr));
3332 else
3333 declare
3334 I : Interp_Index;
3335 It : Interp;
3337 begin
3338 Indexing_Found := False;
3339 Get_First_Interp (Expr, I, It);
3340 while Present (It.Nam) loop
3342 -- Note that analysis will have added the interpretation
3343 -- that corresponds to the dereference. We only check the
3344 -- subprogram itself.
3346 if Is_Overloadable (It.Nam) then
3347 Check_One_Function (It.Nam);
3348 end if;
3350 Get_Next_Interp (I, It);
3351 end loop;
3353 if not Indexing_Found then
3354 Error_Msg_NE
3355 ("aspect Indexing requires a function that "
3356 & "applies to type&", Expr, Ent);
3357 end if;
3358 end;
3359 end if;
3360 end Check_Indexing_Functions;
3362 ------------------------------
3363 -- Check_Iterator_Functions --
3364 ------------------------------
3366 procedure Check_Iterator_Functions is
3367 Default : Entity_Id;
3369 function Valid_Default_Iterator (Subp : Entity_Id) return Boolean;
3370 -- Check one possible interpretation for validity
3372 ----------------------------
3373 -- Valid_Default_Iterator --
3374 ----------------------------
3376 function Valid_Default_Iterator (Subp : Entity_Id) return Boolean is
3377 Formal : Entity_Id;
3379 begin
3380 if not Check_Primitive_Function (Subp) then
3381 return False;
3382 else
3383 Formal := First_Formal (Subp);
3384 end if;
3386 -- False if any subsequent formal has no default expression
3388 Formal := Next_Formal (Formal);
3389 while Present (Formal) loop
3390 if No (Expression (Parent (Formal))) then
3391 return False;
3392 end if;
3394 Next_Formal (Formal);
3395 end loop;
3397 -- True if all subsequent formals have default expressions
3399 return True;
3400 end Valid_Default_Iterator;
3402 -- Start of processing for Check_Iterator_Functions
3404 begin
3405 Analyze (Expr);
3407 if not Is_Entity_Name (Expr) then
3408 Error_Msg_N ("aspect Iterator must be a function name", Expr);
3409 end if;
3411 if not Is_Overloaded (Expr) then
3412 if not Check_Primitive_Function (Entity (Expr)) then
3413 Error_Msg_NE
3414 ("aspect Indexing requires a function that applies to type&",
3415 Entity (Expr), Ent);
3416 end if;
3418 if not Valid_Default_Iterator (Entity (Expr)) then
3419 Error_Msg_N ("improper function for default iterator", Expr);
3420 end if;
3422 else
3423 Default := Empty;
3424 declare
3425 I : Interp_Index;
3426 It : Interp;
3428 begin
3429 Get_First_Interp (Expr, I, It);
3430 while Present (It.Nam) loop
3431 if not Check_Primitive_Function (It.Nam)
3432 or else not Valid_Default_Iterator (It.Nam)
3433 then
3434 Remove_Interp (I);
3436 elsif Present (Default) then
3437 Error_Msg_N ("default iterator must be unique", Expr);
3439 else
3440 Default := It.Nam;
3441 end if;
3443 Get_Next_Interp (I, It);
3444 end loop;
3445 end;
3447 if Present (Default) then
3448 Set_Entity (Expr, Default);
3449 Set_Is_Overloaded (Expr, False);
3450 end if;
3451 end if;
3452 end Check_Iterator_Functions;
3454 -------------------------------
3455 -- Check_Primitive_Function --
3456 -------------------------------
3458 function Check_Primitive_Function (Subp : Entity_Id) return Boolean is
3459 Ctrl : Entity_Id;
3461 begin
3462 if Ekind (Subp) /= E_Function then
3463 return False;
3464 end if;
3466 if No (First_Formal (Subp)) then
3467 return False;
3468 else
3469 Ctrl := Etype (First_Formal (Subp));
3470 end if;
3472 if Ctrl = Ent
3473 or else Ctrl = Class_Wide_Type (Ent)
3474 or else
3475 (Ekind (Ctrl) = E_Anonymous_Access_Type
3476 and then
3477 (Designated_Type (Ctrl) = Ent
3478 or else Designated_Type (Ctrl) = Class_Wide_Type (Ent)))
3479 then
3480 null;
3482 else
3483 return False;
3484 end if;
3486 return True;
3487 end Check_Primitive_Function;
3489 ----------------------
3490 -- Duplicate_Clause --
3491 ----------------------
3493 function Duplicate_Clause return Boolean is
3494 A : Node_Id;
3496 begin
3497 -- Nothing to do if this attribute definition clause comes from
3498 -- an aspect specification, since we could not be duplicating an
3499 -- explicit clause, and we dealt with the case of duplicated aspects
3500 -- in Analyze_Aspect_Specifications.
3502 if From_Aspect_Specification (N) then
3503 return False;
3504 end if;
3506 -- Otherwise current clause may duplicate previous clause, or a
3507 -- previously given pragma or aspect specification for the same
3508 -- aspect.
3510 A := Get_Rep_Item (U_Ent, Chars (N), Check_Parents => False);
3512 if Present (A) then
3513 Error_Msg_Name_1 := Chars (N);
3514 Error_Msg_Sloc := Sloc (A);
3516 Error_Msg_NE ("aspect% for & previously given#", N, U_Ent);
3517 return True;
3518 end if;
3520 return False;
3521 end Duplicate_Clause;
3523 -- Start of processing for Analyze_Attribute_Definition_Clause
3525 begin
3526 -- The following code is a defense against recursion. Not clear that
3527 -- this can happen legitimately, but perhaps some error situations
3528 -- can cause it, and we did see this recursion during testing.
3530 if Analyzed (N) then
3531 return;
3532 else
3533 Set_Analyzed (N, True);
3534 end if;
3536 -- Ignore some selected attributes in CodePeer mode since they are not
3537 -- relevant in this context.
3539 if CodePeer_Mode then
3540 case Id is
3542 -- Ignore Component_Size in CodePeer mode, to avoid changing the
3543 -- internal representation of types by implicitly packing them.
3545 when Attribute_Component_Size =>
3546 Rewrite (N, Make_Null_Statement (Sloc (N)));
3547 return;
3549 when others =>
3550 null;
3551 end case;
3552 end if;
3554 -- Process Ignore_Rep_Clauses option
3556 if Ignore_Rep_Clauses then
3557 case Id is
3559 -- The following should be ignored. They do not affect legality
3560 -- and may be target dependent. The basic idea of -gnatI is to
3561 -- ignore any rep clauses that may be target dependent but do not
3562 -- affect legality (except possibly to be rejected because they
3563 -- are incompatible with the compilation target).
3565 when Attribute_Alignment |
3566 Attribute_Bit_Order |
3567 Attribute_Component_Size |
3568 Attribute_Machine_Radix |
3569 Attribute_Object_Size |
3570 Attribute_Size |
3571 Attribute_Stream_Size |
3572 Attribute_Value_Size =>
3573 Rewrite (N, Make_Null_Statement (Sloc (N)));
3574 return;
3576 -- Perhaps 'Small should not be ignored by Ignore_Rep_Clauses ???
3578 when Attribute_Small =>
3579 if Ignore_Rep_Clauses then
3580 Rewrite (N, Make_Null_Statement (Sloc (N)));
3581 return;
3582 end if;
3584 -- The following should not be ignored, because in the first place
3585 -- they are reasonably portable, and should not cause problems in
3586 -- compiling code from another target, and also they do affect
3587 -- legality, e.g. failing to provide a stream attribute for a
3588 -- type may make a program illegal.
3590 when Attribute_External_Tag |
3591 Attribute_Input |
3592 Attribute_Output |
3593 Attribute_Read |
3594 Attribute_Simple_Storage_Pool |
3595 Attribute_Storage_Pool |
3596 Attribute_Storage_Size |
3597 Attribute_Write =>
3598 null;
3600 -- Other cases are errors ("attribute& cannot be set with
3601 -- definition clause"), which will be caught below.
3603 when others =>
3604 null;
3605 end case;
3606 end if;
3608 Analyze (Nam);
3609 Ent := Entity (Nam);
3611 if Rep_Item_Too_Early (Ent, N) then
3612 return;
3613 end if;
3615 -- Rep clause applies to full view of incomplete type or private type if
3616 -- we have one (if not, this is a premature use of the type). However,
3617 -- certain semantic checks need to be done on the specified entity (i.e.
3618 -- the private view), so we save it in Ent.
3620 if Is_Private_Type (Ent)
3621 and then Is_Derived_Type (Ent)
3622 and then not Is_Tagged_Type (Ent)
3623 and then No (Full_View (Ent))
3624 then
3625 -- If this is a private type whose completion is a derivation from
3626 -- another private type, there is no full view, and the attribute
3627 -- belongs to the type itself, not its underlying parent.
3629 U_Ent := Ent;
3631 elsif Ekind (Ent) = E_Incomplete_Type then
3633 -- The attribute applies to the full view, set the entity of the
3634 -- attribute definition accordingly.
3636 Ent := Underlying_Type (Ent);
3637 U_Ent := Ent;
3638 Set_Entity (Nam, Ent);
3640 else
3641 U_Ent := Underlying_Type (Ent);
3642 end if;
3644 -- Avoid cascaded error
3646 if Etype (Nam) = Any_Type then
3647 return;
3649 -- Must be declared in current scope or in case of an aspect
3650 -- specification, must be visible in current scope.
3652 elsif Scope (Ent) /= Current_Scope
3653 and then
3654 not (From_Aspect_Specification (N)
3655 and then Scope_Within_Or_Same (Current_Scope, Scope (Ent)))
3656 then
3657 Error_Msg_N ("entity must be declared in this scope", Nam);
3658 return;
3660 -- Must not be a source renaming (we do have some cases where the
3661 -- expander generates a renaming, and those cases are OK, in such
3662 -- cases any attribute applies to the renamed object as well).
3664 elsif Is_Object (Ent)
3665 and then Present (Renamed_Object (Ent))
3666 then
3667 -- Case of renamed object from source, this is an error
3669 if Comes_From_Source (Renamed_Object (Ent)) then
3670 Get_Name_String (Chars (N));
3671 Error_Msg_Strlen := Name_Len;
3672 Error_Msg_String (1 .. Name_Len) := Name_Buffer (1 .. Name_Len);
3673 Error_Msg_N
3674 ("~ clause not allowed for a renaming declaration "
3675 & "(RM 13.1(6))", Nam);
3676 return;
3678 -- For the case of a compiler generated renaming, the attribute
3679 -- definition clause applies to the renamed object created by the
3680 -- expander. The easiest general way to handle this is to create a
3681 -- copy of the attribute definition clause for this object.
3683 elsif Is_Entity_Name (Renamed_Object (Ent)) then
3684 Insert_Action (N,
3685 Make_Attribute_Definition_Clause (Loc,
3686 Name =>
3687 New_Occurrence_Of (Entity (Renamed_Object (Ent)), Loc),
3688 Chars => Chars (N),
3689 Expression => Duplicate_Subexpr (Expression (N))));
3691 -- If the renamed object is not an entity, it must be a dereference
3692 -- of an unconstrained function call, and we must introduce a new
3693 -- declaration to capture the expression. This is needed in the case
3694 -- of 'Alignment, where the original declaration must be rewritten.
3696 else
3697 pragma Assert
3698 (Nkind (Renamed_Object (Ent)) = N_Explicit_Dereference);
3699 null;
3700 end if;
3702 -- If no underlying entity, use entity itself, applies to some
3703 -- previously detected error cases ???
3705 elsif No (U_Ent) then
3706 U_Ent := Ent;
3708 -- Cannot specify for a subtype (exception Object/Value_Size)
3710 elsif Is_Type (U_Ent)
3711 and then not Is_First_Subtype (U_Ent)
3712 and then Id /= Attribute_Object_Size
3713 and then Id /= Attribute_Value_Size
3714 and then not From_At_Mod (N)
3715 then
3716 Error_Msg_N ("cannot specify attribute for subtype", Nam);
3717 return;
3718 end if;
3720 Set_Entity (N, U_Ent);
3721 Check_Restriction_No_Use_Of_Attribute (N);
3723 -- Switch on particular attribute
3725 case Id is
3727 -------------
3728 -- Address --
3729 -------------
3731 -- Address attribute definition clause
3733 when Attribute_Address => Address : begin
3735 -- A little error check, catch for X'Address use X'Address;
3737 if Nkind (Nam) = N_Identifier
3738 and then Nkind (Expr) = N_Attribute_Reference
3739 and then Attribute_Name (Expr) = Name_Address
3740 and then Nkind (Prefix (Expr)) = N_Identifier
3741 and then Chars (Nam) = Chars (Prefix (Expr))
3742 then
3743 Error_Msg_NE
3744 ("address for & is self-referencing", Prefix (Expr), Ent);
3745 return;
3746 end if;
3748 -- Not that special case, carry on with analysis of expression
3750 Analyze_And_Resolve (Expr, RTE (RE_Address));
3752 -- Even when ignoring rep clauses we need to indicate that the
3753 -- entity has an address clause and thus it is legal to declare
3754 -- it imported.
3756 if Ignore_Rep_Clauses then
3757 if Ekind_In (U_Ent, E_Variable, E_Constant) then
3758 Record_Rep_Item (U_Ent, N);
3759 end if;
3761 return;
3762 end if;
3764 if Duplicate_Clause then
3765 null;
3767 -- Case of address clause for subprogram
3769 elsif Is_Subprogram (U_Ent) then
3770 if Has_Homonym (U_Ent) then
3771 Error_Msg_N
3772 ("address clause cannot be given " &
3773 "for overloaded subprogram",
3774 Nam);
3775 return;
3776 end if;
3778 -- For subprograms, all address clauses are permitted, and we
3779 -- mark the subprogram as having a deferred freeze so that Gigi
3780 -- will not elaborate it too soon.
3782 -- Above needs more comments, what is too soon about???
3784 Set_Has_Delayed_Freeze (U_Ent);
3786 -- Case of address clause for entry
3788 elsif Ekind (U_Ent) = E_Entry then
3789 if Nkind (Parent (N)) = N_Task_Body then
3790 Error_Msg_N
3791 ("entry address must be specified in task spec", Nam);
3792 return;
3793 end if;
3795 -- For entries, we require a constant address
3797 Check_Constant_Address_Clause (Expr, U_Ent);
3799 -- Special checks for task types
3801 if Is_Task_Type (Scope (U_Ent))
3802 and then Comes_From_Source (Scope (U_Ent))
3803 then
3804 Error_Msg_N
3805 ("??entry address declared for entry in task type", N);
3806 Error_Msg_N
3807 ("\??only one task can be declared of this type", N);
3808 end if;
3810 -- Entry address clauses are obsolescent
3812 Check_Restriction (No_Obsolescent_Features, N);
3814 if Warn_On_Obsolescent_Feature then
3815 Error_Msg_N
3816 ("?j?attaching interrupt to task entry is an " &
3817 "obsolescent feature (RM J.7.1)", N);
3818 Error_Msg_N
3819 ("\?j?use interrupt procedure instead", N);
3820 end if;
3822 -- Case of an address clause for a controlled object which we
3823 -- consider to be erroneous.
3825 elsif Is_Controlled (Etype (U_Ent))
3826 or else Has_Controlled_Component (Etype (U_Ent))
3827 then
3828 Error_Msg_NE
3829 ("??controlled object& must not be overlaid", Nam, U_Ent);
3830 Error_Msg_N
3831 ("\??Program_Error will be raised at run time", Nam);
3832 Insert_Action (Declaration_Node (U_Ent),
3833 Make_Raise_Program_Error (Loc,
3834 Reason => PE_Overlaid_Controlled_Object));
3835 return;
3837 -- Case of address clause for a (non-controlled) object
3839 elsif
3840 Ekind (U_Ent) = E_Variable
3841 or else
3842 Ekind (U_Ent) = E_Constant
3843 then
3844 declare
3845 Expr : constant Node_Id := Expression (N);
3846 O_Ent : Entity_Id;
3847 Off : Boolean;
3849 begin
3850 -- Exported variables cannot have an address clause, because
3851 -- this cancels the effect of the pragma Export.
3853 if Is_Exported (U_Ent) then
3854 Error_Msg_N
3855 ("cannot export object with address clause", Nam);
3856 return;
3857 end if;
3859 Find_Overlaid_Entity (N, O_Ent, Off);
3861 -- Overlaying controlled objects is erroneous
3863 if Present (O_Ent)
3864 and then (Has_Controlled_Component (Etype (O_Ent))
3865 or else Is_Controlled (Etype (O_Ent)))
3866 then
3867 Error_Msg_N
3868 ("??cannot overlay with controlled object", Expr);
3869 Error_Msg_N
3870 ("\??Program_Error will be raised at run time", Expr);
3871 Insert_Action (Declaration_Node (U_Ent),
3872 Make_Raise_Program_Error (Loc,
3873 Reason => PE_Overlaid_Controlled_Object));
3874 return;
3876 elsif Present (O_Ent)
3877 and then Ekind (U_Ent) = E_Constant
3878 and then not Is_Constant_Object (O_Ent)
3879 then
3880 Error_Msg_N ("??constant overlays a variable", Expr);
3882 -- Imported variables can have an address clause, but then
3883 -- the import is pretty meaningless except to suppress
3884 -- initializations, so we do not need such variables to
3885 -- be statically allocated (and in fact it causes trouble
3886 -- if the address clause is a local value).
3888 elsif Is_Imported (U_Ent) then
3889 Set_Is_Statically_Allocated (U_Ent, False);
3890 end if;
3892 -- We mark a possible modification of a variable with an
3893 -- address clause, since it is likely aliasing is occurring.
3895 Note_Possible_Modification (Nam, Sure => False);
3897 -- Here we are checking for explicit overlap of one variable
3898 -- by another, and if we find this then mark the overlapped
3899 -- variable as also being volatile to prevent unwanted
3900 -- optimizations. This is a significant pessimization so
3901 -- avoid it when there is an offset, i.e. when the object
3902 -- is composite; they cannot be optimized easily anyway.
3904 if Present (O_Ent)
3905 and then Is_Object (O_Ent)
3906 and then not Off
3908 -- The following test is an expedient solution to what
3909 -- is really a problem in CodePeer. Suppressing the
3910 -- Set_Treat_As_Volatile call here prevents later
3911 -- generation (in some cases) of trees that CodePeer
3912 -- should, but currently does not, handle correctly.
3913 -- This test should probably be removed when CodePeer
3914 -- is improved, just because we want the tree CodePeer
3915 -- analyzes to match the tree for which we generate code
3916 -- as closely as is practical. ???
3918 and then not CodePeer_Mode
3919 then
3920 -- ??? O_Ent might not be in current unit
3922 Set_Treat_As_Volatile (O_Ent);
3923 end if;
3925 -- Legality checks on the address clause for initialized
3926 -- objects is deferred until the freeze point, because
3927 -- a subsequent pragma might indicate that the object
3928 -- is imported and thus not initialized. Also, the address
3929 -- clause might involve entities that have yet to be
3930 -- elaborated.
3932 Set_Has_Delayed_Freeze (U_Ent);
3934 -- If an initialization call has been generated for this
3935 -- object, it needs to be deferred to after the freeze node
3936 -- we have just now added, otherwise GIGI will see a
3937 -- reference to the variable (as actual to the IP call)
3938 -- before its definition.
3940 declare
3941 Init_Call : constant Node_Id :=
3942 Remove_Init_Call (U_Ent, N);
3944 begin
3945 if Present (Init_Call) then
3946 Append_Freeze_Action (U_Ent, Init_Call);
3948 -- Reset Initialization_Statements pointer so that
3949 -- if there is a pragma Import further down, it can
3950 -- clear any default initialization.
3952 Set_Initialization_Statements (U_Ent, Init_Call);
3953 end if;
3954 end;
3956 if Is_Exported (U_Ent) then
3957 Error_Msg_N
3958 ("& cannot be exported if an address clause is given",
3959 Nam);
3960 Error_Msg_N
3961 ("\define and export a variable "
3962 & "that holds its address instead", Nam);
3963 end if;
3965 -- Entity has delayed freeze, so we will generate an
3966 -- alignment check at the freeze point unless suppressed.
3968 if not Range_Checks_Suppressed (U_Ent)
3969 and then not Alignment_Checks_Suppressed (U_Ent)
3970 then
3971 Set_Check_Address_Alignment (N);
3972 end if;
3974 -- Kill the size check code, since we are not allocating
3975 -- the variable, it is somewhere else.
3977 Kill_Size_Check_Code (U_Ent);
3979 -- If the address clause is of the form:
3981 -- for Y'Address use X'Address
3983 -- or
3985 -- Const : constant Address := X'Address;
3986 -- ...
3987 -- for Y'Address use Const;
3989 -- then we make an entry in the table for checking the size
3990 -- and alignment of the overlaying variable. We defer this
3991 -- check till after code generation to take full advantage
3992 -- of the annotation done by the back end.
3994 -- If the entity has a generic type, the check will be
3995 -- performed in the instance if the actual type justifies
3996 -- it, and we do not insert the clause in the table to
3997 -- prevent spurious warnings.
3999 -- Note: we used to test Comes_From_Source and only give
4000 -- this warning for source entities, but we have removed
4001 -- this test. It really seems bogus to generate overlays
4002 -- that would trigger this warning in generated code.
4003 -- Furthermore, by removing the test, we handle the
4004 -- aspect case properly.
4006 if Address_Clause_Overlay_Warnings
4007 and then Present (O_Ent)
4008 and then Is_Object (O_Ent)
4009 then
4010 if not Is_Generic_Type (Etype (U_Ent)) then
4011 Address_Clause_Checks.Append ((N, U_Ent, O_Ent, Off));
4012 end if;
4014 -- If variable overlays a constant view, and we are
4015 -- warning on overlays, then mark the variable as
4016 -- overlaying a constant (we will give warnings later
4017 -- if this variable is assigned).
4019 if Is_Constant_Object (O_Ent)
4020 and then Ekind (U_Ent) = E_Variable
4021 then
4022 Set_Overlays_Constant (U_Ent);
4023 end if;
4024 end if;
4025 end;
4027 -- Not a valid entity for an address clause
4029 else
4030 Error_Msg_N ("address cannot be given for &", Nam);
4031 end if;
4032 end Address;
4034 ---------------
4035 -- Alignment --
4036 ---------------
4038 -- Alignment attribute definition clause
4040 when Attribute_Alignment => Alignment : declare
4041 Align : constant Uint := Get_Alignment_Value (Expr);
4042 Max_Align : constant Uint := UI_From_Int (Maximum_Alignment);
4044 begin
4045 FOnly := True;
4047 if not Is_Type (U_Ent)
4048 and then Ekind (U_Ent) /= E_Variable
4049 and then Ekind (U_Ent) /= E_Constant
4050 then
4051 Error_Msg_N ("alignment cannot be given for &", Nam);
4053 elsif Duplicate_Clause then
4054 null;
4056 elsif Align /= No_Uint then
4057 Set_Has_Alignment_Clause (U_Ent);
4059 -- Tagged type case, check for attempt to set alignment to a
4060 -- value greater than Max_Align, and reset if so.
4062 if Is_Tagged_Type (U_Ent) and then Align > Max_Align then
4063 Error_Msg_N
4064 ("alignment for & set to Maximum_Aligment??", Nam);
4065 Set_Alignment (U_Ent, Max_Align);
4067 -- All other cases
4069 else
4070 Set_Alignment (U_Ent, Align);
4071 end if;
4073 -- For an array type, U_Ent is the first subtype. In that case,
4074 -- also set the alignment of the anonymous base type so that
4075 -- other subtypes (such as the itypes for aggregates of the
4076 -- type) also receive the expected alignment.
4078 if Is_Array_Type (U_Ent) then
4079 Set_Alignment (Base_Type (U_Ent), Align);
4080 end if;
4081 end if;
4082 end Alignment;
4084 ---------------
4085 -- Bit_Order --
4086 ---------------
4088 -- Bit_Order attribute definition clause
4090 when Attribute_Bit_Order => Bit_Order : declare
4091 begin
4092 if not Is_Record_Type (U_Ent) then
4093 Error_Msg_N
4094 ("Bit_Order can only be defined for record type", Nam);
4096 elsif Duplicate_Clause then
4097 null;
4099 else
4100 Analyze_And_Resolve (Expr, RTE (RE_Bit_Order));
4102 if Etype (Expr) = Any_Type then
4103 return;
4105 elsif not Is_Static_Expression (Expr) then
4106 Flag_Non_Static_Expr
4107 ("Bit_Order requires static expression!", Expr);
4109 else
4110 if (Expr_Value (Expr) = 0) /= Bytes_Big_Endian then
4111 Set_Reverse_Bit_Order (U_Ent, True);
4112 end if;
4113 end if;
4114 end if;
4115 end Bit_Order;
4117 --------------------
4118 -- Component_Size --
4119 --------------------
4121 -- Component_Size attribute definition clause
4123 when Attribute_Component_Size => Component_Size_Case : declare
4124 Csize : constant Uint := Static_Integer (Expr);
4125 Ctyp : Entity_Id;
4126 Btype : Entity_Id;
4127 Biased : Boolean;
4128 New_Ctyp : Entity_Id;
4129 Decl : Node_Id;
4131 begin
4132 if not Is_Array_Type (U_Ent) then
4133 Error_Msg_N ("component size requires array type", Nam);
4134 return;
4135 end if;
4137 Btype := Base_Type (U_Ent);
4138 Ctyp := Component_Type (Btype);
4140 if Duplicate_Clause then
4141 null;
4143 elsif Rep_Item_Too_Early (Btype, N) then
4144 null;
4146 elsif Csize /= No_Uint then
4147 Check_Size (Expr, Ctyp, Csize, Biased);
4149 -- For the biased case, build a declaration for a subtype that
4150 -- will be used to represent the biased subtype that reflects
4151 -- the biased representation of components. We need the subtype
4152 -- to get proper conversions on referencing elements of the
4153 -- array. Note: component size clauses are ignored in VM mode.
4155 if VM_Target = No_VM then
4156 if Biased then
4157 New_Ctyp :=
4158 Make_Defining_Identifier (Loc,
4159 Chars =>
4160 New_External_Name (Chars (U_Ent), 'C', 0, 'T'));
4162 Decl :=
4163 Make_Subtype_Declaration (Loc,
4164 Defining_Identifier => New_Ctyp,
4165 Subtype_Indication =>
4166 New_Occurrence_Of (Component_Type (Btype), Loc));
4168 Set_Parent (Decl, N);
4169 Analyze (Decl, Suppress => All_Checks);
4171 Set_Has_Delayed_Freeze (New_Ctyp, False);
4172 Set_Esize (New_Ctyp, Csize);
4173 Set_RM_Size (New_Ctyp, Csize);
4174 Init_Alignment (New_Ctyp);
4175 Set_Is_Itype (New_Ctyp, True);
4176 Set_Associated_Node_For_Itype (New_Ctyp, U_Ent);
4178 Set_Component_Type (Btype, New_Ctyp);
4179 Set_Biased (New_Ctyp, N, "component size clause");
4180 end if;
4182 Set_Component_Size (Btype, Csize);
4184 -- For VM case, we ignore component size clauses
4186 else
4187 -- Give a warning unless we are in GNAT mode, in which case
4188 -- the warning is suppressed since it is not useful.
4190 if not GNAT_Mode then
4191 Error_Msg_N
4192 ("component size ignored in this configuration??", N);
4193 end if;
4194 end if;
4196 -- Deal with warning on overridden size
4198 if Warn_On_Overridden_Size
4199 and then Has_Size_Clause (Ctyp)
4200 and then RM_Size (Ctyp) /= Csize
4201 then
4202 Error_Msg_NE
4203 ("component size overrides size clause for&?S?", N, Ctyp);
4204 end if;
4206 Set_Has_Component_Size_Clause (Btype, True);
4207 Set_Has_Non_Standard_Rep (Btype, True);
4208 end if;
4209 end Component_Size_Case;
4211 -----------------------
4212 -- Constant_Indexing --
4213 -----------------------
4215 when Attribute_Constant_Indexing =>
4216 Check_Indexing_Functions;
4218 ---------
4219 -- CPU --
4220 ---------
4222 when Attribute_CPU => CPU :
4223 begin
4224 -- CPU attribute definition clause not allowed except from aspect
4225 -- specification.
4227 if From_Aspect_Specification (N) then
4228 if not Is_Task_Type (U_Ent) then
4229 Error_Msg_N ("CPU can only be defined for task", Nam);
4231 elsif Duplicate_Clause then
4232 null;
4234 else
4235 -- The expression must be analyzed in the special manner
4236 -- described in "Handling of Default and Per-Object
4237 -- Expressions" in sem.ads.
4239 -- The visibility to the discriminants must be restored
4241 Push_Scope_And_Install_Discriminants (U_Ent);
4242 Preanalyze_Spec_Expression (Expr, RTE (RE_CPU_Range));
4243 Uninstall_Discriminants_And_Pop_Scope (U_Ent);
4245 if not Is_Static_Expression (Expr) then
4246 Check_Restriction (Static_Priorities, Expr);
4247 end if;
4248 end if;
4250 else
4251 Error_Msg_N
4252 ("attribute& cannot be set with definition clause", N);
4253 end if;
4254 end CPU;
4256 ----------------------
4257 -- Default_Iterator --
4258 ----------------------
4260 when Attribute_Default_Iterator => Default_Iterator : declare
4261 Func : Entity_Id;
4263 begin
4264 if not Is_Tagged_Type (U_Ent) then
4265 Error_Msg_N
4266 ("aspect Default_Iterator applies to tagged type", Nam);
4267 end if;
4269 Check_Iterator_Functions;
4271 Analyze (Expr);
4273 if not Is_Entity_Name (Expr)
4274 or else Ekind (Entity (Expr)) /= E_Function
4275 then
4276 Error_Msg_N ("aspect Iterator must be a function", Expr);
4277 else
4278 Func := Entity (Expr);
4279 end if;
4281 if No (First_Formal (Func))
4282 or else Etype (First_Formal (Func)) /= U_Ent
4283 then
4284 Error_Msg_NE
4285 ("Default Iterator must be a primitive of&", Func, U_Ent);
4286 end if;
4287 end Default_Iterator;
4289 ------------------------
4290 -- Dispatching_Domain --
4291 ------------------------
4293 when Attribute_Dispatching_Domain => Dispatching_Domain :
4294 begin
4295 -- Dispatching_Domain attribute definition clause not allowed
4296 -- except from aspect specification.
4298 if From_Aspect_Specification (N) then
4299 if not Is_Task_Type (U_Ent) then
4300 Error_Msg_N ("Dispatching_Domain can only be defined" &
4301 "for task",
4302 Nam);
4304 elsif Duplicate_Clause then
4305 null;
4307 else
4308 -- The expression must be analyzed in the special manner
4309 -- described in "Handling of Default and Per-Object
4310 -- Expressions" in sem.ads.
4312 -- The visibility to the discriminants must be restored
4314 Push_Scope_And_Install_Discriminants (U_Ent);
4316 Preanalyze_Spec_Expression
4317 (Expr, RTE (RE_Dispatching_Domain));
4319 Uninstall_Discriminants_And_Pop_Scope (U_Ent);
4320 end if;
4322 else
4323 Error_Msg_N
4324 ("attribute& cannot be set with definition clause", N);
4325 end if;
4326 end Dispatching_Domain;
4328 ------------------
4329 -- External_Tag --
4330 ------------------
4332 when Attribute_External_Tag => External_Tag :
4333 begin
4334 if not Is_Tagged_Type (U_Ent) then
4335 Error_Msg_N ("should be a tagged type", Nam);
4336 end if;
4338 if Duplicate_Clause then
4339 null;
4341 else
4342 Analyze_And_Resolve (Expr, Standard_String);
4344 if not Is_Static_Expression (Expr) then
4345 Flag_Non_Static_Expr
4346 ("static string required for tag name!", Nam);
4347 end if;
4349 if VM_Target = No_VM then
4350 Set_Has_External_Tag_Rep_Clause (U_Ent);
4351 else
4352 Error_Msg_Name_1 := Attr;
4353 Error_Msg_N
4354 ("% attribute unsupported in this configuration", Nam);
4355 end if;
4357 if not Is_Library_Level_Entity (U_Ent) then
4358 Error_Msg_NE
4359 ("??non-unique external tag supplied for &", N, U_Ent);
4360 Error_Msg_N
4361 ("\??same external tag applies to all "
4362 & "subprogram calls", N);
4363 Error_Msg_N
4364 ("\??corresponding internal tag cannot be obtained", N);
4365 end if;
4366 end if;
4367 end External_Tag;
4369 --------------------------
4370 -- Implicit_Dereference --
4371 --------------------------
4373 when Attribute_Implicit_Dereference =>
4375 -- Legality checks already performed at the point of the type
4376 -- declaration, aspect is not delayed.
4378 null;
4380 -----------
4381 -- Input --
4382 -----------
4384 when Attribute_Input =>
4385 Analyze_Stream_TSS_Definition (TSS_Stream_Input);
4386 Set_Has_Specified_Stream_Input (Ent);
4388 ------------------------
4389 -- Interrupt_Priority --
4390 ------------------------
4392 when Attribute_Interrupt_Priority => Interrupt_Priority :
4393 begin
4394 -- Interrupt_Priority attribute definition clause not allowed
4395 -- except from aspect specification.
4397 if From_Aspect_Specification (N) then
4398 if not (Is_Protected_Type (U_Ent)
4399 or else Is_Task_Type (U_Ent))
4400 then
4401 Error_Msg_N
4402 ("Interrupt_Priority can only be defined for task" &
4403 "and protected object",
4404 Nam);
4406 elsif Duplicate_Clause then
4407 null;
4409 else
4410 -- The expression must be analyzed in the special manner
4411 -- described in "Handling of Default and Per-Object
4412 -- Expressions" in sem.ads.
4414 -- The visibility to the discriminants must be restored
4416 Push_Scope_And_Install_Discriminants (U_Ent);
4418 Preanalyze_Spec_Expression
4419 (Expr, RTE (RE_Interrupt_Priority));
4421 Uninstall_Discriminants_And_Pop_Scope (U_Ent);
4422 end if;
4424 else
4425 Error_Msg_N
4426 ("attribute& cannot be set with definition clause", N);
4427 end if;
4428 end Interrupt_Priority;
4430 --------------
4431 -- Iterable --
4432 --------------
4434 when Attribute_Iterable =>
4435 Analyze (Expr);
4437 if Nkind (Expr) /= N_Aggregate then
4438 Error_Msg_N ("aspect Iterable must be an aggregate", Expr);
4439 end if;
4441 declare
4442 Assoc : Node_Id;
4444 begin
4445 Assoc := First (Component_Associations (Expr));
4446 while Present (Assoc) loop
4447 if not Is_Entity_Name (Expression (Assoc)) then
4448 Error_Msg_N ("value must be a function", Assoc);
4449 end if;
4451 Next (Assoc);
4452 end loop;
4453 end;
4455 ----------------------
4456 -- Iterator_Element --
4457 ----------------------
4459 when Attribute_Iterator_Element =>
4460 Analyze (Expr);
4462 if not Is_Entity_Name (Expr)
4463 or else not Is_Type (Entity (Expr))
4464 then
4465 Error_Msg_N ("aspect Iterator_Element must be a type", Expr);
4466 end if;
4468 -------------------
4469 -- Machine_Radix --
4470 -------------------
4472 -- Machine radix attribute definition clause
4474 when Attribute_Machine_Radix => Machine_Radix : declare
4475 Radix : constant Uint := Static_Integer (Expr);
4477 begin
4478 if not Is_Decimal_Fixed_Point_Type (U_Ent) then
4479 Error_Msg_N ("decimal fixed-point type expected for &", Nam);
4481 elsif Duplicate_Clause then
4482 null;
4484 elsif Radix /= No_Uint then
4485 Set_Has_Machine_Radix_Clause (U_Ent);
4486 Set_Has_Non_Standard_Rep (Base_Type (U_Ent));
4488 if Radix = 2 then
4489 null;
4490 elsif Radix = 10 then
4491 Set_Machine_Radix_10 (U_Ent);
4492 else
4493 Error_Msg_N ("machine radix value must be 2 or 10", Expr);
4494 end if;
4495 end if;
4496 end Machine_Radix;
4498 -----------------
4499 -- Object_Size --
4500 -----------------
4502 -- Object_Size attribute definition clause
4504 when Attribute_Object_Size => Object_Size : declare
4505 Size : constant Uint := Static_Integer (Expr);
4507 Biased : Boolean;
4508 pragma Warnings (Off, Biased);
4510 begin
4511 if not Is_Type (U_Ent) then
4512 Error_Msg_N ("Object_Size cannot be given for &", Nam);
4514 elsif Duplicate_Clause then
4515 null;
4517 else
4518 Check_Size (Expr, U_Ent, Size, Biased);
4520 if Is_Scalar_Type (U_Ent) then
4521 if Size /= 8 and then Size /= 16 and then Size /= 32
4522 and then UI_Mod (Size, 64) /= 0
4523 then
4524 Error_Msg_N
4525 ("Object_Size must be 8, 16, 32, or multiple of 64",
4526 Expr);
4527 end if;
4529 elsif Size mod 8 /= 0 then
4530 Error_Msg_N ("Object_Size must be a multiple of 8", Expr);
4531 end if;
4533 Set_Esize (U_Ent, Size);
4534 Set_Has_Object_Size_Clause (U_Ent);
4535 Alignment_Check_For_Size_Change (U_Ent, Size);
4536 end if;
4537 end Object_Size;
4539 ------------
4540 -- Output --
4541 ------------
4543 when Attribute_Output =>
4544 Analyze_Stream_TSS_Definition (TSS_Stream_Output);
4545 Set_Has_Specified_Stream_Output (Ent);
4547 --------------
4548 -- Priority --
4549 --------------
4551 when Attribute_Priority => Priority :
4552 begin
4553 -- Priority attribute definition clause not allowed except from
4554 -- aspect specification.
4556 if From_Aspect_Specification (N) then
4557 if not (Is_Protected_Type (U_Ent)
4558 or else Is_Task_Type (U_Ent)
4559 or else Ekind (U_Ent) = E_Procedure)
4560 then
4561 Error_Msg_N
4562 ("Priority can only be defined for task and protected " &
4563 "object",
4564 Nam);
4566 elsif Duplicate_Clause then
4567 null;
4569 else
4570 -- The expression must be analyzed in the special manner
4571 -- described in "Handling of Default and Per-Object
4572 -- Expressions" in sem.ads.
4574 -- The visibility to the discriminants must be restored
4576 Push_Scope_And_Install_Discriminants (U_Ent);
4577 Preanalyze_Spec_Expression (Expr, Standard_Integer);
4578 Uninstall_Discriminants_And_Pop_Scope (U_Ent);
4580 if not Is_Static_Expression (Expr) then
4581 Check_Restriction (Static_Priorities, Expr);
4582 end if;
4583 end if;
4585 else
4586 Error_Msg_N
4587 ("attribute& cannot be set with definition clause", N);
4588 end if;
4589 end Priority;
4591 ----------
4592 -- Read --
4593 ----------
4595 when Attribute_Read =>
4596 Analyze_Stream_TSS_Definition (TSS_Stream_Read);
4597 Set_Has_Specified_Stream_Read (Ent);
4599 --------------------------
4600 -- Scalar_Storage_Order --
4601 --------------------------
4603 -- Scalar_Storage_Order attribute definition clause
4605 when Attribute_Scalar_Storage_Order => Scalar_Storage_Order : declare
4606 begin
4607 if not (Is_Record_Type (U_Ent) or else Is_Array_Type (U_Ent)) then
4608 Error_Msg_N
4609 ("Scalar_Storage_Order can only be defined for "
4610 & "record or array type", Nam);
4612 elsif Duplicate_Clause then
4613 null;
4615 else
4616 Analyze_And_Resolve (Expr, RTE (RE_Bit_Order));
4618 if Etype (Expr) = Any_Type then
4619 return;
4621 elsif not Is_Static_Expression (Expr) then
4622 Flag_Non_Static_Expr
4623 ("Scalar_Storage_Order requires static expression!", Expr);
4625 elsif (Expr_Value (Expr) = 0) /= Bytes_Big_Endian then
4627 -- Here for the case of a non-default (i.e. non-confirming)
4628 -- Scalar_Storage_Order attribute definition.
4630 if Support_Nondefault_SSO_On_Target then
4631 Set_Reverse_Storage_Order (Base_Type (U_Ent), True);
4632 else
4633 Error_Msg_N
4634 ("non-default Scalar_Storage_Order "
4635 & "not supported on target", Expr);
4636 end if;
4637 end if;
4638 end if;
4639 end Scalar_Storage_Order;
4641 ----------
4642 -- Size --
4643 ----------
4645 -- Size attribute definition clause
4647 when Attribute_Size => Size : declare
4648 Size : constant Uint := Static_Integer (Expr);
4649 Etyp : Entity_Id;
4650 Biased : Boolean;
4652 begin
4653 FOnly := True;
4655 if Duplicate_Clause then
4656 null;
4658 elsif not Is_Type (U_Ent)
4659 and then Ekind (U_Ent) /= E_Variable
4660 and then Ekind (U_Ent) /= E_Constant
4661 then
4662 Error_Msg_N ("size cannot be given for &", Nam);
4664 elsif Is_Array_Type (U_Ent)
4665 and then not Is_Constrained (U_Ent)
4666 then
4667 Error_Msg_N
4668 ("size cannot be given for unconstrained array", Nam);
4670 elsif Size /= No_Uint then
4671 if VM_Target /= No_VM and then not GNAT_Mode then
4673 -- Size clause is not handled properly on VM targets.
4674 -- Display a warning unless we are in GNAT mode, in which
4675 -- case this is useless.
4677 Error_Msg_N
4678 ("size clauses are ignored in this configuration??", N);
4679 end if;
4681 if Is_Type (U_Ent) then
4682 Etyp := U_Ent;
4683 else
4684 Etyp := Etype (U_Ent);
4685 end if;
4687 -- Check size, note that Gigi is in charge of checking that the
4688 -- size of an array or record type is OK. Also we do not check
4689 -- the size in the ordinary fixed-point case, since it is too
4690 -- early to do so (there may be subsequent small clause that
4691 -- affects the size). We can check the size if a small clause
4692 -- has already been given.
4694 if not Is_Ordinary_Fixed_Point_Type (U_Ent)
4695 or else Has_Small_Clause (U_Ent)
4696 then
4697 Check_Size (Expr, Etyp, Size, Biased);
4698 Set_Biased (U_Ent, N, "size clause", Biased);
4699 end if;
4701 -- For types set RM_Size and Esize if possible
4703 if Is_Type (U_Ent) then
4704 Set_RM_Size (U_Ent, Size);
4706 -- For elementary types, increase Object_Size to power of 2,
4707 -- but not less than a storage unit in any case (normally
4708 -- this means it will be byte addressable).
4710 -- For all other types, nothing else to do, we leave Esize
4711 -- (object size) unset, the back end will set it from the
4712 -- size and alignment in an appropriate manner.
4714 -- In both cases, we check whether the alignment must be
4715 -- reset in the wake of the size change.
4717 if Is_Elementary_Type (U_Ent) then
4718 if Size <= System_Storage_Unit then
4719 Init_Esize (U_Ent, System_Storage_Unit);
4720 elsif Size <= 16 then
4721 Init_Esize (U_Ent, 16);
4722 elsif Size <= 32 then
4723 Init_Esize (U_Ent, 32);
4724 else
4725 Set_Esize (U_Ent, (Size + 63) / 64 * 64);
4726 end if;
4728 Alignment_Check_For_Size_Change (U_Ent, Esize (U_Ent));
4729 else
4730 Alignment_Check_For_Size_Change (U_Ent, Size);
4731 end if;
4733 -- For objects, set Esize only
4735 else
4736 if Is_Elementary_Type (Etyp) then
4737 if Size /= System_Storage_Unit
4738 and then
4739 Size /= System_Storage_Unit * 2
4740 and then
4741 Size /= System_Storage_Unit * 4
4742 and then
4743 Size /= System_Storage_Unit * 8
4744 then
4745 Error_Msg_Uint_1 := UI_From_Int (System_Storage_Unit);
4746 Error_Msg_Uint_2 := Error_Msg_Uint_1 * 8;
4747 Error_Msg_N
4748 ("size for primitive object must be a power of 2"
4749 & " in the range ^-^", N);
4750 end if;
4751 end if;
4753 Set_Esize (U_Ent, Size);
4754 end if;
4756 Set_Has_Size_Clause (U_Ent);
4757 end if;
4758 end Size;
4760 -----------
4761 -- Small --
4762 -----------
4764 -- Small attribute definition clause
4766 when Attribute_Small => Small : declare
4767 Implicit_Base : constant Entity_Id := Base_Type (U_Ent);
4768 Small : Ureal;
4770 begin
4771 Analyze_And_Resolve (Expr, Any_Real);
4773 if Etype (Expr) = Any_Type then
4774 return;
4776 elsif not Is_Static_Expression (Expr) then
4777 Flag_Non_Static_Expr
4778 ("small requires static expression!", Expr);
4779 return;
4781 else
4782 Small := Expr_Value_R (Expr);
4784 if Small <= Ureal_0 then
4785 Error_Msg_N ("small value must be greater than zero", Expr);
4786 return;
4787 end if;
4789 end if;
4791 if not Is_Ordinary_Fixed_Point_Type (U_Ent) then
4792 Error_Msg_N
4793 ("small requires an ordinary fixed point type", Nam);
4795 elsif Has_Small_Clause (U_Ent) then
4796 Error_Msg_N ("small already given for &", Nam);
4798 elsif Small > Delta_Value (U_Ent) then
4799 Error_Msg_N
4800 ("small value must not be greater than delta value", Nam);
4802 else
4803 Set_Small_Value (U_Ent, Small);
4804 Set_Small_Value (Implicit_Base, Small);
4805 Set_Has_Small_Clause (U_Ent);
4806 Set_Has_Small_Clause (Implicit_Base);
4807 Set_Has_Non_Standard_Rep (Implicit_Base);
4808 end if;
4809 end Small;
4811 ------------------
4812 -- Storage_Pool --
4813 ------------------
4815 -- Storage_Pool attribute definition clause
4817 when Attribute_Storage_Pool | Attribute_Simple_Storage_Pool => declare
4818 Pool : Entity_Id;
4819 T : Entity_Id;
4821 begin
4822 if Ekind (U_Ent) = E_Access_Subprogram_Type then
4823 Error_Msg_N
4824 ("storage pool cannot be given for access-to-subprogram type",
4825 Nam);
4826 return;
4828 elsif not
4829 Ekind_In (U_Ent, E_Access_Type, E_General_Access_Type)
4830 then
4831 Error_Msg_N
4832 ("storage pool can only be given for access types", Nam);
4833 return;
4835 elsif Is_Derived_Type (U_Ent) then
4836 Error_Msg_N
4837 ("storage pool cannot be given for a derived access type",
4838 Nam);
4840 elsif Duplicate_Clause then
4841 return;
4843 elsif Present (Associated_Storage_Pool (U_Ent)) then
4844 Error_Msg_N ("storage pool already given for &", Nam);
4845 return;
4846 end if;
4848 -- Check for Storage_Size previously given
4850 declare
4851 SS : constant Node_Id :=
4852 Get_Attribute_Definition_Clause
4853 (U_Ent, Attribute_Storage_Size);
4854 begin
4855 if Present (SS) then
4856 Check_Pool_Size_Clash (U_Ent, N, SS);
4857 end if;
4858 end;
4860 -- Storage_Pool case
4862 if Id = Attribute_Storage_Pool then
4863 Analyze_And_Resolve
4864 (Expr, Class_Wide_Type (RTE (RE_Root_Storage_Pool)));
4866 -- In the Simple_Storage_Pool case, we allow a variable of any
4867 -- simple storage pool type, so we Resolve without imposing an
4868 -- expected type.
4870 else
4871 Analyze_And_Resolve (Expr);
4873 if not Present (Get_Rep_Pragma
4874 (Etype (Expr), Name_Simple_Storage_Pool_Type))
4875 then
4876 Error_Msg_N
4877 ("expression must be of a simple storage pool type", Expr);
4878 end if;
4879 end if;
4881 if not Denotes_Variable (Expr) then
4882 Error_Msg_N ("storage pool must be a variable", Expr);
4883 return;
4884 end if;
4886 if Nkind (Expr) = N_Type_Conversion then
4887 T := Etype (Expression (Expr));
4888 else
4889 T := Etype (Expr);
4890 end if;
4892 -- The Stack_Bounded_Pool is used internally for implementing
4893 -- access types with a Storage_Size. Since it only work properly
4894 -- when used on one specific type, we need to check that it is not
4895 -- hijacked improperly:
4897 -- type T is access Integer;
4898 -- for T'Storage_Size use n;
4899 -- type Q is access Float;
4900 -- for Q'Storage_Size use T'Storage_Size; -- incorrect
4902 if RTE_Available (RE_Stack_Bounded_Pool)
4903 and then Base_Type (T) = RTE (RE_Stack_Bounded_Pool)
4904 then
4905 Error_Msg_N ("non-shareable internal Pool", Expr);
4906 return;
4907 end if;
4909 -- If the argument is a name that is not an entity name, then
4910 -- we construct a renaming operation to define an entity of
4911 -- type storage pool.
4913 if not Is_Entity_Name (Expr)
4914 and then Is_Object_Reference (Expr)
4915 then
4916 Pool := Make_Temporary (Loc, 'P', Expr);
4918 declare
4919 Rnode : constant Node_Id :=
4920 Make_Object_Renaming_Declaration (Loc,
4921 Defining_Identifier => Pool,
4922 Subtype_Mark =>
4923 New_Occurrence_Of (Etype (Expr), Loc),
4924 Name => Expr);
4926 begin
4927 -- If the attribute definition clause comes from an aspect
4928 -- clause, then insert the renaming before the associated
4929 -- entity's declaration, since the attribute clause has
4930 -- not yet been appended to the declaration list.
4932 if From_Aspect_Specification (N) then
4933 Insert_Before (Parent (Entity (N)), Rnode);
4934 else
4935 Insert_Before (N, Rnode);
4936 end if;
4938 Analyze (Rnode);
4939 Set_Associated_Storage_Pool (U_Ent, Pool);
4940 end;
4942 elsif Is_Entity_Name (Expr) then
4943 Pool := Entity (Expr);
4945 -- If pool is a renamed object, get original one. This can
4946 -- happen with an explicit renaming, and within instances.
4948 while Present (Renamed_Object (Pool))
4949 and then Is_Entity_Name (Renamed_Object (Pool))
4950 loop
4951 Pool := Entity (Renamed_Object (Pool));
4952 end loop;
4954 if Present (Renamed_Object (Pool))
4955 and then Nkind (Renamed_Object (Pool)) = N_Type_Conversion
4956 and then Is_Entity_Name (Expression (Renamed_Object (Pool)))
4957 then
4958 Pool := Entity (Expression (Renamed_Object (Pool)));
4959 end if;
4961 Set_Associated_Storage_Pool (U_Ent, Pool);
4963 elsif Nkind (Expr) = N_Type_Conversion
4964 and then Is_Entity_Name (Expression (Expr))
4965 and then Nkind (Original_Node (Expr)) = N_Attribute_Reference
4966 then
4967 Pool := Entity (Expression (Expr));
4968 Set_Associated_Storage_Pool (U_Ent, Pool);
4970 else
4971 Error_Msg_N ("incorrect reference to a Storage Pool", Expr);
4972 return;
4973 end if;
4974 end;
4976 ------------------
4977 -- Storage_Size --
4978 ------------------
4980 -- Storage_Size attribute definition clause
4982 when Attribute_Storage_Size => Storage_Size : declare
4983 Btype : constant Entity_Id := Base_Type (U_Ent);
4985 begin
4986 if Is_Task_Type (U_Ent) then
4988 -- Check obsolescent (but never obsolescent if from aspect)
4990 if not From_Aspect_Specification (N) then
4991 Check_Restriction (No_Obsolescent_Features, N);
4993 if Warn_On_Obsolescent_Feature then
4994 Error_Msg_N
4995 ("?j?storage size clause for task is an " &
4996 "obsolescent feature (RM J.9)", N);
4997 Error_Msg_N ("\?j?use Storage_Size pragma instead", N);
4998 end if;
4999 end if;
5001 FOnly := True;
5002 end if;
5004 if not Is_Access_Type (U_Ent)
5005 and then Ekind (U_Ent) /= E_Task_Type
5006 then
5007 Error_Msg_N ("storage size cannot be given for &", Nam);
5009 elsif Is_Access_Type (U_Ent) and Is_Derived_Type (U_Ent) then
5010 Error_Msg_N
5011 ("storage size cannot be given for a derived access type",
5012 Nam);
5014 elsif Duplicate_Clause then
5015 null;
5017 else
5018 Analyze_And_Resolve (Expr, Any_Integer);
5020 if Is_Access_Type (U_Ent) then
5022 -- Check for Storage_Pool previously given
5024 declare
5025 SP : constant Node_Id :=
5026 Get_Attribute_Definition_Clause
5027 (U_Ent, Attribute_Storage_Pool);
5029 begin
5030 if Present (SP) then
5031 Check_Pool_Size_Clash (U_Ent, SP, N);
5032 end if;
5033 end;
5035 -- Special case of for x'Storage_Size use 0
5037 if Is_OK_Static_Expression (Expr)
5038 and then Expr_Value (Expr) = 0
5039 then
5040 Set_No_Pool_Assigned (Btype);
5041 end if;
5042 end if;
5044 Set_Has_Storage_Size_Clause (Btype);
5045 end if;
5046 end Storage_Size;
5048 -----------------
5049 -- Stream_Size --
5050 -----------------
5052 when Attribute_Stream_Size => Stream_Size : declare
5053 Size : constant Uint := Static_Integer (Expr);
5055 begin
5056 if Ada_Version <= Ada_95 then
5057 Check_Restriction (No_Implementation_Attributes, N);
5058 end if;
5060 if Duplicate_Clause then
5061 null;
5063 elsif Is_Elementary_Type (U_Ent) then
5064 if Size /= System_Storage_Unit
5065 and then
5066 Size /= System_Storage_Unit * 2
5067 and then
5068 Size /= System_Storage_Unit * 4
5069 and then
5070 Size /= System_Storage_Unit * 8
5071 then
5072 Error_Msg_Uint_1 := UI_From_Int (System_Storage_Unit);
5073 Error_Msg_N
5074 ("stream size for elementary type must be a"
5075 & " power of 2 and at least ^", N);
5077 elsif RM_Size (U_Ent) > Size then
5078 Error_Msg_Uint_1 := RM_Size (U_Ent);
5079 Error_Msg_N
5080 ("stream size for elementary type must be a"
5081 & " power of 2 and at least ^", N);
5082 end if;
5084 Set_Has_Stream_Size_Clause (U_Ent);
5086 else
5087 Error_Msg_N ("Stream_Size cannot be given for &", Nam);
5088 end if;
5089 end Stream_Size;
5091 ----------------
5092 -- Value_Size --
5093 ----------------
5095 -- Value_Size attribute definition clause
5097 when Attribute_Value_Size => Value_Size : declare
5098 Size : constant Uint := Static_Integer (Expr);
5099 Biased : Boolean;
5101 begin
5102 if not Is_Type (U_Ent) then
5103 Error_Msg_N ("Value_Size cannot be given for &", Nam);
5105 elsif Duplicate_Clause then
5106 null;
5108 elsif Is_Array_Type (U_Ent)
5109 and then not Is_Constrained (U_Ent)
5110 then
5111 Error_Msg_N
5112 ("Value_Size cannot be given for unconstrained array", Nam);
5114 else
5115 if Is_Elementary_Type (U_Ent) then
5116 Check_Size (Expr, U_Ent, Size, Biased);
5117 Set_Biased (U_Ent, N, "value size clause", Biased);
5118 end if;
5120 Set_RM_Size (U_Ent, Size);
5121 end if;
5122 end Value_Size;
5124 -----------------------
5125 -- Variable_Indexing --
5126 -----------------------
5128 when Attribute_Variable_Indexing =>
5129 Check_Indexing_Functions;
5131 -----------
5132 -- Write --
5133 -----------
5135 when Attribute_Write =>
5136 Analyze_Stream_TSS_Definition (TSS_Stream_Write);
5137 Set_Has_Specified_Stream_Write (Ent);
5139 -- All other attributes cannot be set
5141 when others =>
5142 Error_Msg_N
5143 ("attribute& cannot be set with definition clause", N);
5144 end case;
5146 -- The test for the type being frozen must be performed after any
5147 -- expression the clause has been analyzed since the expression itself
5148 -- might cause freezing that makes the clause illegal.
5150 if Rep_Item_Too_Late (U_Ent, N, FOnly) then
5151 return;
5152 end if;
5153 end Analyze_Attribute_Definition_Clause;
5155 ----------------------------
5156 -- Analyze_Code_Statement --
5157 ----------------------------
5159 procedure Analyze_Code_Statement (N : Node_Id) is
5160 HSS : constant Node_Id := Parent (N);
5161 SBody : constant Node_Id := Parent (HSS);
5162 Subp : constant Entity_Id := Current_Scope;
5163 Stmt : Node_Id;
5164 Decl : Node_Id;
5165 StmtO : Node_Id;
5166 DeclO : Node_Id;
5168 begin
5169 -- Analyze and check we get right type, note that this implements the
5170 -- requirement (RM 13.8(1)) that Machine_Code be with'ed, since that
5171 -- is the only way that Asm_Insn could possibly be visible.
5173 Analyze_And_Resolve (Expression (N));
5175 if Etype (Expression (N)) = Any_Type then
5176 return;
5177 elsif Etype (Expression (N)) /= RTE (RE_Asm_Insn) then
5178 Error_Msg_N ("incorrect type for code statement", N);
5179 return;
5180 end if;
5182 Check_Code_Statement (N);
5184 -- Make sure we appear in the handled statement sequence of a
5185 -- subprogram (RM 13.8(3)).
5187 if Nkind (HSS) /= N_Handled_Sequence_Of_Statements
5188 or else Nkind (SBody) /= N_Subprogram_Body
5189 then
5190 Error_Msg_N
5191 ("code statement can only appear in body of subprogram", N);
5192 return;
5193 end if;
5195 -- Do remaining checks (RM 13.8(3)) if not already done
5197 if not Is_Machine_Code_Subprogram (Subp) then
5198 Set_Is_Machine_Code_Subprogram (Subp);
5200 -- No exception handlers allowed
5202 if Present (Exception_Handlers (HSS)) then
5203 Error_Msg_N
5204 ("exception handlers not permitted in machine code subprogram",
5205 First (Exception_Handlers (HSS)));
5206 end if;
5208 -- No declarations other than use clauses and pragmas (we allow
5209 -- certain internally generated declarations as well).
5211 Decl := First (Declarations (SBody));
5212 while Present (Decl) loop
5213 DeclO := Original_Node (Decl);
5214 if Comes_From_Source (DeclO)
5215 and not Nkind_In (DeclO, N_Pragma,
5216 N_Use_Package_Clause,
5217 N_Use_Type_Clause,
5218 N_Implicit_Label_Declaration)
5219 then
5220 Error_Msg_N
5221 ("this declaration not allowed in machine code subprogram",
5222 DeclO);
5223 end if;
5225 Next (Decl);
5226 end loop;
5228 -- No statements other than code statements, pragmas, and labels.
5229 -- Again we allow certain internally generated statements.
5231 -- In Ada 2012, qualified expressions are names, and the code
5232 -- statement is initially parsed as a procedure call.
5234 Stmt := First (Statements (HSS));
5235 while Present (Stmt) loop
5236 StmtO := Original_Node (Stmt);
5238 -- A procedure call transformed into a code statement is OK.
5240 if Ada_Version >= Ada_2012
5241 and then Nkind (StmtO) = N_Procedure_Call_Statement
5242 and then Nkind (Name (StmtO)) = N_Qualified_Expression
5243 then
5244 null;
5246 elsif Comes_From_Source (StmtO)
5247 and then not Nkind_In (StmtO, N_Pragma,
5248 N_Label,
5249 N_Code_Statement)
5250 then
5251 Error_Msg_N
5252 ("this statement is not allowed in machine code subprogram",
5253 StmtO);
5254 end if;
5256 Next (Stmt);
5257 end loop;
5258 end if;
5259 end Analyze_Code_Statement;
5261 -----------------------------------------------
5262 -- Analyze_Enumeration_Representation_Clause --
5263 -----------------------------------------------
5265 procedure Analyze_Enumeration_Representation_Clause (N : Node_Id) is
5266 Ident : constant Node_Id := Identifier (N);
5267 Aggr : constant Node_Id := Array_Aggregate (N);
5268 Enumtype : Entity_Id;
5269 Elit : Entity_Id;
5270 Expr : Node_Id;
5271 Assoc : Node_Id;
5272 Choice : Node_Id;
5273 Val : Uint;
5275 Err : Boolean := False;
5276 -- Set True to avoid cascade errors and crashes on incorrect source code
5278 Lo : constant Uint := Expr_Value (Type_Low_Bound (Universal_Integer));
5279 Hi : constant Uint := Expr_Value (Type_High_Bound (Universal_Integer));
5280 -- Allowed range of universal integer (= allowed range of enum lit vals)
5282 Min : Uint;
5283 Max : Uint;
5284 -- Minimum and maximum values of entries
5286 Max_Node : Node_Id;
5287 -- Pointer to node for literal providing max value
5289 begin
5290 if Ignore_Rep_Clauses then
5291 return;
5292 end if;
5294 -- Ignore enumeration rep clauses by default in CodePeer mode,
5295 -- unless -gnatd.I is specified, as a work around for potential false
5296 -- positive messages.
5298 if CodePeer_Mode and not Debug_Flag_Dot_II then
5299 return;
5300 end if;
5302 -- First some basic error checks
5304 Find_Type (Ident);
5305 Enumtype := Entity (Ident);
5307 if Enumtype = Any_Type
5308 or else Rep_Item_Too_Early (Enumtype, N)
5309 then
5310 return;
5311 else
5312 Enumtype := Underlying_Type (Enumtype);
5313 end if;
5315 if not Is_Enumeration_Type (Enumtype) then
5316 Error_Msg_NE
5317 ("enumeration type required, found}",
5318 Ident, First_Subtype (Enumtype));
5319 return;
5320 end if;
5322 -- Ignore rep clause on generic actual type. This will already have
5323 -- been flagged on the template as an error, and this is the safest
5324 -- way to ensure we don't get a junk cascaded message in the instance.
5326 if Is_Generic_Actual_Type (Enumtype) then
5327 return;
5329 -- Type must be in current scope
5331 elsif Scope (Enumtype) /= Current_Scope then
5332 Error_Msg_N ("type must be declared in this scope", Ident);
5333 return;
5335 -- Type must be a first subtype
5337 elsif not Is_First_Subtype (Enumtype) then
5338 Error_Msg_N ("cannot give enumeration rep clause for subtype", N);
5339 return;
5341 -- Ignore duplicate rep clause
5343 elsif Has_Enumeration_Rep_Clause (Enumtype) then
5344 Error_Msg_N ("duplicate enumeration rep clause ignored", N);
5345 return;
5347 -- Don't allow rep clause for standard [wide_[wide_]]character
5349 elsif Is_Standard_Character_Type (Enumtype) then
5350 Error_Msg_N ("enumeration rep clause not allowed for this type", N);
5351 return;
5353 -- Check that the expression is a proper aggregate (no parentheses)
5355 elsif Paren_Count (Aggr) /= 0 then
5356 Error_Msg
5357 ("extra parentheses surrounding aggregate not allowed",
5358 First_Sloc (Aggr));
5359 return;
5361 -- All tests passed, so set rep clause in place
5363 else
5364 Set_Has_Enumeration_Rep_Clause (Enumtype);
5365 Set_Has_Enumeration_Rep_Clause (Base_Type (Enumtype));
5366 end if;
5368 -- Now we process the aggregate. Note that we don't use the normal
5369 -- aggregate code for this purpose, because we don't want any of the
5370 -- normal expansion activities, and a number of special semantic
5371 -- rules apply (including the component type being any integer type)
5373 Elit := First_Literal (Enumtype);
5375 -- First the positional entries if any
5377 if Present (Expressions (Aggr)) then
5378 Expr := First (Expressions (Aggr));
5379 while Present (Expr) loop
5380 if No (Elit) then
5381 Error_Msg_N ("too many entries in aggregate", Expr);
5382 return;
5383 end if;
5385 Val := Static_Integer (Expr);
5387 -- Err signals that we found some incorrect entries processing
5388 -- the list. The final checks for completeness and ordering are
5389 -- skipped in this case.
5391 if Val = No_Uint then
5392 Err := True;
5393 elsif Val < Lo or else Hi < Val then
5394 Error_Msg_N ("value outside permitted range", Expr);
5395 Err := True;
5396 end if;
5398 Set_Enumeration_Rep (Elit, Val);
5399 Set_Enumeration_Rep_Expr (Elit, Expr);
5400 Next (Expr);
5401 Next (Elit);
5402 end loop;
5403 end if;
5405 -- Now process the named entries if present
5407 if Present (Component_Associations (Aggr)) then
5408 Assoc := First (Component_Associations (Aggr));
5409 while Present (Assoc) loop
5410 Choice := First (Choices (Assoc));
5412 if Present (Next (Choice)) then
5413 Error_Msg_N
5414 ("multiple choice not allowed here", Next (Choice));
5415 Err := True;
5416 end if;
5418 if Nkind (Choice) = N_Others_Choice then
5419 Error_Msg_N ("others choice not allowed here", Choice);
5420 Err := True;
5422 elsif Nkind (Choice) = N_Range then
5424 -- ??? should allow zero/one element range here
5426 Error_Msg_N ("range not allowed here", Choice);
5427 Err := True;
5429 else
5430 Analyze_And_Resolve (Choice, Enumtype);
5432 if Error_Posted (Choice) then
5433 Err := True;
5434 end if;
5436 if not Err then
5437 if Is_Entity_Name (Choice)
5438 and then Is_Type (Entity (Choice))
5439 then
5440 Error_Msg_N ("subtype name not allowed here", Choice);
5441 Err := True;
5443 -- ??? should allow static subtype with zero/one entry
5445 elsif Etype (Choice) = Base_Type (Enumtype) then
5446 if not Is_Static_Expression (Choice) then
5447 Flag_Non_Static_Expr
5448 ("non-static expression used for choice!", Choice);
5449 Err := True;
5451 else
5452 Elit := Expr_Value_E (Choice);
5454 if Present (Enumeration_Rep_Expr (Elit)) then
5455 Error_Msg_Sloc :=
5456 Sloc (Enumeration_Rep_Expr (Elit));
5457 Error_Msg_NE
5458 ("representation for& previously given#",
5459 Choice, Elit);
5460 Err := True;
5461 end if;
5463 Set_Enumeration_Rep_Expr (Elit, Expression (Assoc));
5465 Expr := Expression (Assoc);
5466 Val := Static_Integer (Expr);
5468 if Val = No_Uint then
5469 Err := True;
5471 elsif Val < Lo or else Hi < Val then
5472 Error_Msg_N ("value outside permitted range", Expr);
5473 Err := True;
5474 end if;
5476 Set_Enumeration_Rep (Elit, Val);
5477 end if;
5478 end if;
5479 end if;
5480 end if;
5482 Next (Assoc);
5483 end loop;
5484 end if;
5486 -- Aggregate is fully processed. Now we check that a full set of
5487 -- representations was given, and that they are in range and in order.
5488 -- These checks are only done if no other errors occurred.
5490 if not Err then
5491 Min := No_Uint;
5492 Max := No_Uint;
5494 Elit := First_Literal (Enumtype);
5495 while Present (Elit) loop
5496 if No (Enumeration_Rep_Expr (Elit)) then
5497 Error_Msg_NE ("missing representation for&!", N, Elit);
5499 else
5500 Val := Enumeration_Rep (Elit);
5502 if Min = No_Uint then
5503 Min := Val;
5504 end if;
5506 if Val /= No_Uint then
5507 if Max /= No_Uint and then Val <= Max then
5508 Error_Msg_NE
5509 ("enumeration value for& not ordered!",
5510 Enumeration_Rep_Expr (Elit), Elit);
5511 end if;
5513 Max_Node := Enumeration_Rep_Expr (Elit);
5514 Max := Val;
5515 end if;
5517 -- If there is at least one literal whose representation is not
5518 -- equal to the Pos value, then note that this enumeration type
5519 -- has a non-standard representation.
5521 if Val /= Enumeration_Pos (Elit) then
5522 Set_Has_Non_Standard_Rep (Base_Type (Enumtype));
5523 end if;
5524 end if;
5526 Next (Elit);
5527 end loop;
5529 -- Now set proper size information
5531 declare
5532 Minsize : Uint := UI_From_Int (Minimum_Size (Enumtype));
5534 begin
5535 if Has_Size_Clause (Enumtype) then
5537 -- All OK, if size is OK now
5539 if RM_Size (Enumtype) >= Minsize then
5540 null;
5542 else
5543 -- Try if we can get by with biasing
5545 Minsize :=
5546 UI_From_Int (Minimum_Size (Enumtype, Biased => True));
5548 -- Error message if even biasing does not work
5550 if RM_Size (Enumtype) < Minsize then
5551 Error_Msg_Uint_1 := RM_Size (Enumtype);
5552 Error_Msg_Uint_2 := Max;
5553 Error_Msg_N
5554 ("previously given size (^) is too small "
5555 & "for this value (^)", Max_Node);
5557 -- If biasing worked, indicate that we now have biased rep
5559 else
5560 Set_Biased
5561 (Enumtype, Size_Clause (Enumtype), "size clause");
5562 end if;
5563 end if;
5565 else
5566 Set_RM_Size (Enumtype, Minsize);
5567 Set_Enum_Esize (Enumtype);
5568 end if;
5570 Set_RM_Size (Base_Type (Enumtype), RM_Size (Enumtype));
5571 Set_Esize (Base_Type (Enumtype), Esize (Enumtype));
5572 Set_Alignment (Base_Type (Enumtype), Alignment (Enumtype));
5573 end;
5574 end if;
5576 -- We repeat the too late test in case it froze itself
5578 if Rep_Item_Too_Late (Enumtype, N) then
5579 null;
5580 end if;
5581 end Analyze_Enumeration_Representation_Clause;
5583 ----------------------------
5584 -- Analyze_Free_Statement --
5585 ----------------------------
5587 procedure Analyze_Free_Statement (N : Node_Id) is
5588 begin
5589 Analyze (Expression (N));
5590 end Analyze_Free_Statement;
5592 ---------------------------
5593 -- Analyze_Freeze_Entity --
5594 ---------------------------
5596 procedure Analyze_Freeze_Entity (N : Node_Id) is
5597 begin
5598 Freeze_Entity_Checks (N);
5599 end Analyze_Freeze_Entity;
5601 -----------------------------------
5602 -- Analyze_Freeze_Generic_Entity --
5603 -----------------------------------
5605 procedure Analyze_Freeze_Generic_Entity (N : Node_Id) is
5606 begin
5607 Freeze_Entity_Checks (N);
5608 end Analyze_Freeze_Generic_Entity;
5610 ------------------------------------------
5611 -- Analyze_Record_Representation_Clause --
5612 ------------------------------------------
5614 -- Note: we check as much as we can here, but we can't do any checks
5615 -- based on the position values (e.g. overlap checks) until freeze time
5616 -- because especially in Ada 2005 (machine scalar mode), the processing
5617 -- for non-standard bit order can substantially change the positions.
5618 -- See procedure Check_Record_Representation_Clause (called from Freeze)
5619 -- for the remainder of this processing.
5621 procedure Analyze_Record_Representation_Clause (N : Node_Id) is
5622 Ident : constant Node_Id := Identifier (N);
5623 Biased : Boolean;
5624 CC : Node_Id;
5625 Comp : Entity_Id;
5626 Fbit : Uint;
5627 Hbit : Uint := Uint_0;
5628 Lbit : Uint;
5629 Ocomp : Entity_Id;
5630 Posit : Uint;
5631 Rectype : Entity_Id;
5632 Recdef : Node_Id;
5634 function Is_Inherited (Comp : Entity_Id) return Boolean;
5635 -- True if Comp is an inherited component in a record extension
5637 ------------------
5638 -- Is_Inherited --
5639 ------------------
5641 function Is_Inherited (Comp : Entity_Id) return Boolean is
5642 Comp_Base : Entity_Id;
5644 begin
5645 if Ekind (Rectype) = E_Record_Subtype then
5646 Comp_Base := Original_Record_Component (Comp);
5647 else
5648 Comp_Base := Comp;
5649 end if;
5651 return Comp_Base /= Original_Record_Component (Comp_Base);
5652 end Is_Inherited;
5654 -- Local variables
5656 Is_Record_Extension : Boolean;
5657 -- True if Rectype is a record extension
5659 CR_Pragma : Node_Id := Empty;
5660 -- Points to N_Pragma node if Complete_Representation pragma present
5662 -- Start of processing for Analyze_Record_Representation_Clause
5664 begin
5665 if Ignore_Rep_Clauses then
5666 return;
5667 end if;
5669 Find_Type (Ident);
5670 Rectype := Entity (Ident);
5672 if Rectype = Any_Type or else Rep_Item_Too_Early (Rectype, N) then
5673 return;
5674 else
5675 Rectype := Underlying_Type (Rectype);
5676 end if;
5678 -- First some basic error checks
5680 if not Is_Record_Type (Rectype) then
5681 Error_Msg_NE
5682 ("record type required, found}", Ident, First_Subtype (Rectype));
5683 return;
5685 elsif Scope (Rectype) /= Current_Scope then
5686 Error_Msg_N ("type must be declared in this scope", N);
5687 return;
5689 elsif not Is_First_Subtype (Rectype) then
5690 Error_Msg_N ("cannot give record rep clause for subtype", N);
5691 return;
5693 elsif Has_Record_Rep_Clause (Rectype) then
5694 Error_Msg_N ("duplicate record rep clause ignored", N);
5695 return;
5697 elsif Rep_Item_Too_Late (Rectype, N) then
5698 return;
5699 end if;
5701 -- We know we have a first subtype, now possibly go the the anonymous
5702 -- base type to determine whether Rectype is a record extension.
5704 Recdef := Type_Definition (Declaration_Node (Base_Type (Rectype)));
5705 Is_Record_Extension :=
5706 Nkind (Recdef) = N_Derived_Type_Definition
5707 and then Present (Record_Extension_Part (Recdef));
5709 if Present (Mod_Clause (N)) then
5710 declare
5711 Loc : constant Source_Ptr := Sloc (N);
5712 M : constant Node_Id := Mod_Clause (N);
5713 P : constant List_Id := Pragmas_Before (M);
5714 AtM_Nod : Node_Id;
5716 Mod_Val : Uint;
5717 pragma Warnings (Off, Mod_Val);
5719 begin
5720 Check_Restriction (No_Obsolescent_Features, Mod_Clause (N));
5722 if Warn_On_Obsolescent_Feature then
5723 Error_Msg_N
5724 ("?j?mod clause is an obsolescent feature (RM J.8)", N);
5725 Error_Msg_N
5726 ("\?j?use alignment attribute definition clause instead", N);
5727 end if;
5729 if Present (P) then
5730 Analyze_List (P);
5731 end if;
5733 -- In ASIS_Mode mode, expansion is disabled, but we must convert
5734 -- the Mod clause into an alignment clause anyway, so that the
5735 -- back-end can compute and back-annotate properly the size and
5736 -- alignment of types that may include this record.
5738 -- This seems dubious, this destroys the source tree in a manner
5739 -- not detectable by ASIS ???
5741 if Operating_Mode = Check_Semantics and then ASIS_Mode then
5742 AtM_Nod :=
5743 Make_Attribute_Definition_Clause (Loc,
5744 Name => New_Occurrence_Of (Base_Type (Rectype), Loc),
5745 Chars => Name_Alignment,
5746 Expression => Relocate_Node (Expression (M)));
5748 Set_From_At_Mod (AtM_Nod);
5749 Insert_After (N, AtM_Nod);
5750 Mod_Val := Get_Alignment_Value (Expression (AtM_Nod));
5751 Set_Mod_Clause (N, Empty);
5753 else
5754 -- Get the alignment value to perform error checking
5756 Mod_Val := Get_Alignment_Value (Expression (M));
5757 end if;
5758 end;
5759 end if;
5761 -- For untagged types, clear any existing component clauses for the
5762 -- type. If the type is derived, this is what allows us to override
5763 -- a rep clause for the parent. For type extensions, the representation
5764 -- of the inherited components is inherited, so we want to keep previous
5765 -- component clauses for completeness.
5767 if not Is_Tagged_Type (Rectype) then
5768 Comp := First_Component_Or_Discriminant (Rectype);
5769 while Present (Comp) loop
5770 Set_Component_Clause (Comp, Empty);
5771 Next_Component_Or_Discriminant (Comp);
5772 end loop;
5773 end if;
5775 -- All done if no component clauses
5777 CC := First (Component_Clauses (N));
5779 if No (CC) then
5780 return;
5781 end if;
5783 -- A representation like this applies to the base type
5785 Set_Has_Record_Rep_Clause (Base_Type (Rectype));
5786 Set_Has_Non_Standard_Rep (Base_Type (Rectype));
5787 Set_Has_Specified_Layout (Base_Type (Rectype));
5789 -- Process the component clauses
5791 while Present (CC) loop
5793 -- Pragma
5795 if Nkind (CC) = N_Pragma then
5796 Analyze (CC);
5798 -- The only pragma of interest is Complete_Representation
5800 if Pragma_Name (CC) = Name_Complete_Representation then
5801 CR_Pragma := CC;
5802 end if;
5804 -- Processing for real component clause
5806 else
5807 Posit := Static_Integer (Position (CC));
5808 Fbit := Static_Integer (First_Bit (CC));
5809 Lbit := Static_Integer (Last_Bit (CC));
5811 if Posit /= No_Uint
5812 and then Fbit /= No_Uint
5813 and then Lbit /= No_Uint
5814 then
5815 if Posit < 0 then
5816 Error_Msg_N
5817 ("position cannot be negative", Position (CC));
5819 elsif Fbit < 0 then
5820 Error_Msg_N
5821 ("first bit cannot be negative", First_Bit (CC));
5823 -- The Last_Bit specified in a component clause must not be
5824 -- less than the First_Bit minus one (RM-13.5.1(10)).
5826 elsif Lbit < Fbit - 1 then
5827 Error_Msg_N
5828 ("last bit cannot be less than first bit minus one",
5829 Last_Bit (CC));
5831 -- Values look OK, so find the corresponding record component
5832 -- Even though the syntax allows an attribute reference for
5833 -- implementation-defined components, GNAT does not allow the
5834 -- tag to get an explicit position.
5836 elsif Nkind (Component_Name (CC)) = N_Attribute_Reference then
5837 if Attribute_Name (Component_Name (CC)) = Name_Tag then
5838 Error_Msg_N ("position of tag cannot be specified", CC);
5839 else
5840 Error_Msg_N ("illegal component name", CC);
5841 end if;
5843 else
5844 Comp := First_Entity (Rectype);
5845 while Present (Comp) loop
5846 exit when Chars (Comp) = Chars (Component_Name (CC));
5847 Next_Entity (Comp);
5848 end loop;
5850 if No (Comp) then
5852 -- Maybe component of base type that is absent from
5853 -- statically constrained first subtype.
5855 Comp := First_Entity (Base_Type (Rectype));
5856 while Present (Comp) loop
5857 exit when Chars (Comp) = Chars (Component_Name (CC));
5858 Next_Entity (Comp);
5859 end loop;
5860 end if;
5862 if No (Comp) then
5863 Error_Msg_N
5864 ("component clause is for non-existent field", CC);
5866 -- Ada 2012 (AI05-0026): Any name that denotes a
5867 -- discriminant of an object of an unchecked union type
5868 -- shall not occur within a record_representation_clause.
5870 -- The general restriction of using record rep clauses on
5871 -- Unchecked_Union types has now been lifted. Since it is
5872 -- possible to introduce a record rep clause which mentions
5873 -- the discriminant of an Unchecked_Union in non-Ada 2012
5874 -- code, this check is applied to all versions of the
5875 -- language.
5877 elsif Ekind (Comp) = E_Discriminant
5878 and then Is_Unchecked_Union (Rectype)
5879 then
5880 Error_Msg_N
5881 ("cannot reference discriminant of unchecked union",
5882 Component_Name (CC));
5884 elsif Is_Record_Extension and then Is_Inherited (Comp) then
5885 Error_Msg_NE
5886 ("component clause not allowed for inherited "
5887 & "component&", CC, Comp);
5889 elsif Present (Component_Clause (Comp)) then
5891 -- Diagnose duplicate rep clause, or check consistency
5892 -- if this is an inherited component. In a double fault,
5893 -- there may be a duplicate inconsistent clause for an
5894 -- inherited component.
5896 if Scope (Original_Record_Component (Comp)) = Rectype
5897 or else Parent (Component_Clause (Comp)) = N
5898 then
5899 Error_Msg_Sloc := Sloc (Component_Clause (Comp));
5900 Error_Msg_N ("component clause previously given#", CC);
5902 else
5903 declare
5904 Rep1 : constant Node_Id := Component_Clause (Comp);
5905 begin
5906 if Intval (Position (Rep1)) /=
5907 Intval (Position (CC))
5908 or else Intval (First_Bit (Rep1)) /=
5909 Intval (First_Bit (CC))
5910 or else Intval (Last_Bit (Rep1)) /=
5911 Intval (Last_Bit (CC))
5912 then
5913 Error_Msg_N
5914 ("component clause inconsistent "
5915 & "with representation of ancestor", CC);
5917 elsif Warn_On_Redundant_Constructs then
5918 Error_Msg_N
5919 ("?r?redundant confirming component clause "
5920 & "for component!", CC);
5921 end if;
5922 end;
5923 end if;
5925 -- Normal case where this is the first component clause we
5926 -- have seen for this entity, so set it up properly.
5928 else
5929 -- Make reference for field in record rep clause and set
5930 -- appropriate entity field in the field identifier.
5932 Generate_Reference
5933 (Comp, Component_Name (CC), Set_Ref => False);
5934 Set_Entity (Component_Name (CC), Comp);
5936 -- Update Fbit and Lbit to the actual bit number
5938 Fbit := Fbit + UI_From_Int (SSU) * Posit;
5939 Lbit := Lbit + UI_From_Int (SSU) * Posit;
5941 if Has_Size_Clause (Rectype)
5942 and then RM_Size (Rectype) <= Lbit
5943 then
5944 Error_Msg_N
5945 ("bit number out of range of specified size",
5946 Last_Bit (CC));
5947 else
5948 Set_Component_Clause (Comp, CC);
5949 Set_Component_Bit_Offset (Comp, Fbit);
5950 Set_Esize (Comp, 1 + (Lbit - Fbit));
5951 Set_Normalized_First_Bit (Comp, Fbit mod SSU);
5952 Set_Normalized_Position (Comp, Fbit / SSU);
5954 if Warn_On_Overridden_Size
5955 and then Has_Size_Clause (Etype (Comp))
5956 and then RM_Size (Etype (Comp)) /= Esize (Comp)
5957 then
5958 Error_Msg_NE
5959 ("?S?component size overrides size clause for&",
5960 Component_Name (CC), Etype (Comp));
5961 end if;
5963 -- This information is also set in the corresponding
5964 -- component of the base type, found by accessing the
5965 -- Original_Record_Component link if it is present.
5967 Ocomp := Original_Record_Component (Comp);
5969 if Hbit < Lbit then
5970 Hbit := Lbit;
5971 end if;
5973 Check_Size
5974 (Component_Name (CC),
5975 Etype (Comp),
5976 Esize (Comp),
5977 Biased);
5979 Set_Biased
5980 (Comp, First_Node (CC), "component clause", Biased);
5982 if Present (Ocomp) then
5983 Set_Component_Clause (Ocomp, CC);
5984 Set_Component_Bit_Offset (Ocomp, Fbit);
5985 Set_Normalized_First_Bit (Ocomp, Fbit mod SSU);
5986 Set_Normalized_Position (Ocomp, Fbit / SSU);
5987 Set_Esize (Ocomp, 1 + (Lbit - Fbit));
5989 Set_Normalized_Position_Max
5990 (Ocomp, Normalized_Position (Ocomp));
5992 -- Note: we don't use Set_Biased here, because we
5993 -- already gave a warning above if needed, and we
5994 -- would get a duplicate for the same name here.
5996 Set_Has_Biased_Representation
5997 (Ocomp, Has_Biased_Representation (Comp));
5998 end if;
6000 if Esize (Comp) < 0 then
6001 Error_Msg_N ("component size is negative", CC);
6002 end if;
6003 end if;
6004 end if;
6005 end if;
6006 end if;
6007 end if;
6009 Next (CC);
6010 end loop;
6012 -- Check missing components if Complete_Representation pragma appeared
6014 if Present (CR_Pragma) then
6015 Comp := First_Component_Or_Discriminant (Rectype);
6016 while Present (Comp) loop
6017 if No (Component_Clause (Comp)) then
6018 Error_Msg_NE
6019 ("missing component clause for &", CR_Pragma, Comp);
6020 end if;
6022 Next_Component_Or_Discriminant (Comp);
6023 end loop;
6025 -- Give missing components warning if required
6027 elsif Warn_On_Unrepped_Components then
6028 declare
6029 Num_Repped_Components : Nat := 0;
6030 Num_Unrepped_Components : Nat := 0;
6032 begin
6033 -- First count number of repped and unrepped components
6035 Comp := First_Component_Or_Discriminant (Rectype);
6036 while Present (Comp) loop
6037 if Present (Component_Clause (Comp)) then
6038 Num_Repped_Components := Num_Repped_Components + 1;
6039 else
6040 Num_Unrepped_Components := Num_Unrepped_Components + 1;
6041 end if;
6043 Next_Component_Or_Discriminant (Comp);
6044 end loop;
6046 -- We are only interested in the case where there is at least one
6047 -- unrepped component, and at least half the components have rep
6048 -- clauses. We figure that if less than half have them, then the
6049 -- partial rep clause is really intentional. If the component
6050 -- type has no underlying type set at this point (as for a generic
6051 -- formal type), we don't know enough to give a warning on the
6052 -- component.
6054 if Num_Unrepped_Components > 0
6055 and then Num_Unrepped_Components < Num_Repped_Components
6056 then
6057 Comp := First_Component_Or_Discriminant (Rectype);
6058 while Present (Comp) loop
6059 if No (Component_Clause (Comp))
6060 and then Comes_From_Source (Comp)
6061 and then Present (Underlying_Type (Etype (Comp)))
6062 and then (Is_Scalar_Type (Underlying_Type (Etype (Comp)))
6063 or else Size_Known_At_Compile_Time
6064 (Underlying_Type (Etype (Comp))))
6065 and then not Has_Warnings_Off (Rectype)
6066 then
6067 Error_Msg_Sloc := Sloc (Comp);
6068 Error_Msg_NE
6069 ("?C?no component clause given for & declared #",
6070 N, Comp);
6071 end if;
6073 Next_Component_Or_Discriminant (Comp);
6074 end loop;
6075 end if;
6076 end;
6077 end if;
6078 end Analyze_Record_Representation_Clause;
6080 -------------------------------------------
6081 -- Build_Invariant_Procedure_Declaration --
6082 -------------------------------------------
6084 function Build_Invariant_Procedure_Declaration
6085 (Typ : Entity_Id) return Node_Id
6087 Loc : constant Source_Ptr := Sloc (Typ);
6088 Object_Entity : constant Entity_Id :=
6089 Make_Defining_Identifier (Loc, New_Internal_Name ('I'));
6090 Spec : Node_Id;
6091 SId : Entity_Id;
6093 begin
6094 Set_Etype (Object_Entity, Typ);
6096 -- Check for duplicate definiations.
6098 if Has_Invariants (Typ) and then Present (Invariant_Procedure (Typ)) then
6099 return Empty;
6100 end if;
6102 SId :=
6103 Make_Defining_Identifier (Loc,
6104 Chars => New_External_Name (Chars (Typ), "Invariant"));
6105 Set_Has_Invariants (Typ);
6106 Set_Ekind (SId, E_Procedure);
6107 Set_Is_Invariant_Procedure (SId);
6108 Set_Invariant_Procedure (Typ, SId);
6110 Spec :=
6111 Make_Procedure_Specification (Loc,
6112 Defining_Unit_Name => SId,
6113 Parameter_Specifications => New_List (
6114 Make_Parameter_Specification (Loc,
6115 Defining_Identifier => Object_Entity,
6116 Parameter_Type => New_Occurrence_Of (Typ, Loc))));
6118 return Make_Subprogram_Declaration (Loc, Specification => Spec);
6119 end Build_Invariant_Procedure_Declaration;
6121 -------------------------------
6122 -- Build_Invariant_Procedure --
6123 -------------------------------
6125 -- The procedure that is constructed here has the form
6127 -- procedure typInvariant (Ixxx : typ) is
6128 -- begin
6129 -- pragma Check (Invariant, exp, "failed invariant from xxx");
6130 -- pragma Check (Invariant, exp, "failed invariant from xxx");
6131 -- ...
6132 -- pragma Check (Invariant, exp, "failed inherited invariant from xxx");
6133 -- ...
6134 -- end typInvariant;
6136 procedure Build_Invariant_Procedure (Typ : Entity_Id; N : Node_Id) is
6137 Loc : constant Source_Ptr := Sloc (Typ);
6138 Stmts : List_Id;
6139 Spec : Node_Id;
6140 SId : Entity_Id;
6141 PDecl : Node_Id;
6142 PBody : Node_Id;
6144 Visible_Decls : constant List_Id := Visible_Declarations (N);
6145 Private_Decls : constant List_Id := Private_Declarations (N);
6147 procedure Add_Invariants (T : Entity_Id; Inherit : Boolean);
6148 -- Appends statements to Stmts for any invariants in the rep item chain
6149 -- of the given type. If Inherit is False, then we only process entries
6150 -- on the chain for the type Typ. If Inherit is True, then we ignore any
6151 -- Invariant aspects, but we process all Invariant'Class aspects, adding
6152 -- "inherited" to the exception message and generating an informational
6153 -- message about the inheritance of an invariant.
6155 Object_Name : Name_Id;
6156 -- Name for argument of invariant procedure
6158 Object_Entity : Node_Id;
6159 -- The entity of the formal for the procedure
6161 --------------------
6162 -- Add_Invariants --
6163 --------------------
6165 procedure Add_Invariants (T : Entity_Id; Inherit : Boolean) is
6166 Ritem : Node_Id;
6167 Arg1 : Node_Id;
6168 Arg2 : Node_Id;
6169 Arg3 : Node_Id;
6170 Exp : Node_Id;
6171 Loc : Source_Ptr;
6172 Assoc : List_Id;
6173 Str : String_Id;
6175 procedure Replace_Type_Reference (N : Node_Id);
6176 -- Replace a single occurrence N of the subtype name with a reference
6177 -- to the formal of the predicate function. N can be an identifier
6178 -- referencing the subtype, or a selected component, representing an
6179 -- appropriately qualified occurrence of the subtype name.
6181 procedure Replace_Type_References is
6182 new Replace_Type_References_Generic (Replace_Type_Reference);
6183 -- Traverse an expression replacing all occurrences of the subtype
6184 -- name with appropriate references to the object that is the formal
6185 -- parameter of the predicate function. Note that we must ensure
6186 -- that the type and entity information is properly set in the
6187 -- replacement node, since we will do a Preanalyze call of this
6188 -- expression without proper visibility of the procedure argument.
6190 ----------------------------
6191 -- Replace_Type_Reference --
6192 ----------------------------
6194 -- Note: See comments in Add_Predicates.Replace_Type_Reference
6195 -- regarding handling of Sloc and Comes_From_Source.
6197 procedure Replace_Type_Reference (N : Node_Id) is
6198 begin
6200 -- Add semantic information to node to be rewritten, for ASIS
6201 -- navigation needs.
6203 if Nkind (N) = N_Identifier then
6204 Set_Entity (N, T);
6205 Set_Etype (N, T);
6207 elsif Nkind (N) = N_Selected_Component then
6208 Analyze (Prefix (N));
6209 Set_Entity (Selector_Name (N), T);
6210 Set_Etype (Selector_Name (N), T);
6211 end if;
6213 -- Invariant'Class, replace with T'Class (obj)
6215 if Class_Present (Ritem) then
6216 Rewrite (N,
6217 Make_Type_Conversion (Sloc (N),
6218 Subtype_Mark =>
6219 Make_Attribute_Reference (Sloc (N),
6220 Prefix => New_Occurrence_Of (T, Sloc (N)),
6221 Attribute_Name => Name_Class),
6222 Expression => Make_Identifier (Sloc (N), Object_Name)));
6224 Set_Entity (Expression (N), Object_Entity);
6225 Set_Etype (Expression (N), Typ);
6227 -- Invariant, replace with obj
6229 else
6230 Rewrite (N, Make_Identifier (Sloc (N), Object_Name));
6231 Set_Entity (N, Object_Entity);
6232 Set_Etype (N, Typ);
6233 end if;
6235 Set_Comes_From_Source (N, True);
6236 end Replace_Type_Reference;
6238 -- Start of processing for Add_Invariants
6240 begin
6241 Ritem := First_Rep_Item (T);
6242 while Present (Ritem) loop
6243 if Nkind (Ritem) = N_Pragma
6244 and then Pragma_Name (Ritem) = Name_Invariant
6245 then
6246 Arg1 := First (Pragma_Argument_Associations (Ritem));
6247 Arg2 := Next (Arg1);
6248 Arg3 := Next (Arg2);
6250 Arg1 := Get_Pragma_Arg (Arg1);
6251 Arg2 := Get_Pragma_Arg (Arg2);
6253 -- For Inherit case, ignore Invariant, process only Class case
6255 if Inherit then
6256 if not Class_Present (Ritem) then
6257 goto Continue;
6258 end if;
6260 -- For Inherit false, process only item for right type
6262 else
6263 if Entity (Arg1) /= Typ then
6264 goto Continue;
6265 end if;
6266 end if;
6268 if No (Stmts) then
6269 Stmts := Empty_List;
6270 end if;
6272 Exp := New_Copy_Tree (Arg2);
6274 -- Preserve sloc of original pragma Invariant
6276 Loc := Sloc (Ritem);
6278 -- We need to replace any occurrences of the name of the type
6279 -- with references to the object, converted to type'Class in
6280 -- the case of Invariant'Class aspects.
6282 Replace_Type_References (Exp, Chars (T));
6284 -- If this invariant comes from an aspect, find the aspect
6285 -- specification, and replace the saved expression because
6286 -- we need the subtype references replaced for the calls to
6287 -- Preanalyze_Spec_Expressin in Check_Aspect_At_Freeze_Point
6288 -- and Check_Aspect_At_End_Of_Declarations.
6290 if From_Aspect_Specification (Ritem) then
6291 declare
6292 Aitem : Node_Id;
6294 begin
6295 -- Loop to find corresponding aspect, note that this
6296 -- must be present given the pragma is marked delayed.
6298 Aitem := Next_Rep_Item (Ritem);
6299 while Present (Aitem) loop
6300 if Nkind (Aitem) = N_Aspect_Specification
6301 and then Aspect_Rep_Item (Aitem) = Ritem
6302 then
6303 Set_Entity
6304 (Identifier (Aitem), New_Copy_Tree (Exp));
6305 exit;
6306 end if;
6308 Aitem := Next_Rep_Item (Aitem);
6309 end loop;
6310 end;
6311 end if;
6313 -- Now we need to preanalyze the expression to properly capture
6314 -- the visibility in the visible part. The expression will not
6315 -- be analyzed for real until the body is analyzed, but that is
6316 -- at the end of the private part and has the wrong visibility.
6318 Set_Parent (Exp, N);
6319 Preanalyze_Assert_Expression (Exp, Standard_Boolean);
6321 -- In ASIS mode, even if assertions are not enabled, we must
6322 -- analyze the original expression in the aspect specification
6323 -- because it is part of the original tree.
6325 if ASIS_Mode then
6326 declare
6327 Inv : constant Node_Id :=
6328 Expression (Corresponding_Aspect (Ritem));
6329 begin
6330 Replace_Type_References (Inv, Chars (T));
6331 Preanalyze_Assert_Expression (Inv, Standard_Boolean);
6332 end;
6333 end if;
6335 -- Build first two arguments for Check pragma
6337 Assoc := New_List (
6338 Make_Pragma_Argument_Association (Loc,
6339 Expression => Make_Identifier (Loc, Name_Invariant)),
6340 Make_Pragma_Argument_Association (Loc,
6341 Expression => Exp));
6343 -- Add message if present in Invariant pragma
6345 if Present (Arg3) then
6346 Str := Strval (Get_Pragma_Arg (Arg3));
6348 -- If inherited case, and message starts "failed invariant",
6349 -- change it to be "failed inherited invariant".
6351 if Inherit then
6352 String_To_Name_Buffer (Str);
6354 if Name_Buffer (1 .. 16) = "failed invariant" then
6355 Insert_Str_In_Name_Buffer ("inherited ", 8);
6356 Str := String_From_Name_Buffer;
6357 end if;
6358 end if;
6360 Append_To (Assoc,
6361 Make_Pragma_Argument_Association (Loc,
6362 Expression => Make_String_Literal (Loc, Str)));
6363 end if;
6365 -- Add Check pragma to list of statements
6367 Append_To (Stmts,
6368 Make_Pragma (Loc,
6369 Pragma_Identifier =>
6370 Make_Identifier (Loc, Name_Check),
6371 Pragma_Argument_Associations => Assoc));
6373 -- If Inherited case and option enabled, output info msg. Note
6374 -- that we know this is a case of Invariant'Class.
6376 if Inherit and Opt.List_Inherited_Aspects then
6377 Error_Msg_Sloc := Sloc (Ritem);
6378 Error_Msg_N
6379 ("info: & inherits `Invariant''Class` aspect from #?L?",
6380 Typ);
6381 end if;
6382 end if;
6384 <<Continue>>
6385 Next_Rep_Item (Ritem);
6386 end loop;
6387 end Add_Invariants;
6389 -- Start of processing for Build_Invariant_Procedure
6391 begin
6392 Stmts := No_List;
6393 PDecl := Empty;
6394 PBody := Empty;
6395 SId := Empty;
6397 -- If the aspect specification exists for some view of the type, the
6398 -- declaration for the procedure has been created.
6400 if Has_Invariants (Typ) then
6401 SId := Invariant_Procedure (Typ);
6402 end if;
6404 if Present (SId) then
6405 PDecl := Unit_Declaration_Node (SId);
6406 else
6407 PDecl := Build_Invariant_Procedure_Declaration (Typ);
6408 end if;
6410 -- Recover formal of procedure, for use in the calls to invariant
6411 -- functions (including inherited ones).
6413 Object_Entity :=
6414 Defining_Identifier
6415 (First (Parameter_Specifications (Specification (PDecl))));
6416 Object_Name := Chars (Object_Entity);
6418 -- Add invariants for the current type
6420 Add_Invariants (Typ, Inherit => False);
6422 -- Add invariants for parent types
6424 declare
6425 Current_Typ : Entity_Id;
6426 Parent_Typ : Entity_Id;
6428 begin
6429 Current_Typ := Typ;
6430 loop
6431 Parent_Typ := Etype (Current_Typ);
6433 if Is_Private_Type (Parent_Typ)
6434 and then Present (Full_View (Base_Type (Parent_Typ)))
6435 then
6436 Parent_Typ := Full_View (Base_Type (Parent_Typ));
6437 end if;
6439 exit when Parent_Typ = Current_Typ;
6441 Current_Typ := Parent_Typ;
6442 Add_Invariants (Current_Typ, Inherit => True);
6443 end loop;
6444 end;
6446 -- Build the procedure if we generated at least one Check pragma
6448 if Stmts /= No_List then
6449 Spec := Copy_Separate_Tree (Specification (PDecl));
6451 PBody :=
6452 Make_Subprogram_Body (Loc,
6453 Specification => Spec,
6454 Declarations => Empty_List,
6455 Handled_Statement_Sequence =>
6456 Make_Handled_Sequence_Of_Statements (Loc,
6457 Statements => Stmts));
6459 -- Insert procedure declaration and spec at the appropriate points.
6460 -- If declaration is already analyzed, it was processed by the
6461 -- generated pragma.
6463 if Present (Private_Decls) then
6465 -- The spec goes at the end of visible declarations, but they have
6466 -- already been analyzed, so we need to explicitly do the analyze.
6468 if not Analyzed (PDecl) then
6469 Append_To (Visible_Decls, PDecl);
6470 Analyze (PDecl);
6471 end if;
6473 -- The body goes at the end of the private declarations, which we
6474 -- have not analyzed yet, so we do not need to perform an explicit
6475 -- analyze call. We skip this if there are no private declarations
6476 -- (this is an error that will be caught elsewhere);
6478 Append_To (Private_Decls, PBody);
6480 -- If the invariant appears on the full view of a type, the
6481 -- analysis of the private part is complete, and we must
6482 -- analyze the new body explicitly.
6484 if In_Private_Part (Current_Scope) then
6485 Analyze (PBody);
6486 end if;
6488 -- If there are no private declarations this may be an error that
6489 -- will be diagnosed elsewhere. However, if this is a non-private
6490 -- type that inherits invariants, it needs no completion and there
6491 -- may be no private part. In this case insert invariant procedure
6492 -- at end of current declarative list, and analyze at once, given
6493 -- that the type is about to be frozen.
6495 elsif not Is_Private_Type (Typ) then
6496 Append_To (Visible_Decls, PDecl);
6497 Append_To (Visible_Decls, PBody);
6498 Analyze (PDecl);
6499 Analyze (PBody);
6500 end if;
6501 end if;
6502 end Build_Invariant_Procedure;
6504 -------------------------------
6505 -- Build_Predicate_Functions --
6506 -------------------------------
6508 -- The procedures that are constructed here have the form:
6510 -- function typPredicate (Ixxx : typ) return Boolean is
6511 -- begin
6512 -- return
6513 -- exp1 and then exp2 and then ...
6514 -- and then typ1Predicate (typ1 (Ixxx))
6515 -- and then typ2Predicate (typ2 (Ixxx))
6516 -- and then ...;
6517 -- end typPredicate;
6519 -- Here exp1, and exp2 are expressions from Predicate pragmas. Note that
6520 -- this is the point at which these expressions get analyzed, providing the
6521 -- required delay, and typ1, typ2, are entities from which predicates are
6522 -- inherited. Note that we do NOT generate Check pragmas, that's because we
6523 -- use this function even if checks are off, e.g. for membership tests.
6525 -- If the expression has at least one Raise_Expression, then we also build
6526 -- the typPredicateM version of the function, in which any occurrence of a
6527 -- Raise_Expression is converted to "return False".
6529 procedure Build_Predicate_Functions (Typ : Entity_Id; N : Node_Id) is
6530 Loc : constant Source_Ptr := Sloc (Typ);
6532 Expr : Node_Id;
6533 -- This is the expression for the result of the function. It is
6534 -- is build by connecting the component predicates with AND THEN.
6536 Expr_M : Node_Id;
6537 -- This is the corresponding return expression for the Predicate_M
6538 -- function. It differs in that raise expressions are marked for
6539 -- special expansion (see Process_REs).
6541 Object_Name : constant Name_Id := New_Internal_Name ('I');
6542 -- Name for argument of Predicate procedure. Note that we use the same
6543 -- name for both predicate procedure. That way the reference within the
6544 -- predicate expression is the same in both functions.
6546 Object_Entity : constant Entity_Id :=
6547 Make_Defining_Identifier (Loc, Chars => Object_Name);
6548 -- Entity for argument of Predicate procedure
6550 Object_Entity_M : constant Entity_Id :=
6551 Make_Defining_Identifier (Loc, Chars => Object_Name);
6552 -- Entity for argument of Predicate_M procedure
6554 Raise_Expression_Present : Boolean := False;
6555 -- Set True if Expr has at least one Raise_Expression
6557 Static_Predic : Node_Id := Empty;
6558 -- Set to N_Pragma node for a static predicate if one is encountered
6560 procedure Add_Call (T : Entity_Id);
6561 -- Includes a call to the predicate function for type T in Expr if T
6562 -- has predicates and Predicate_Function (T) is non-empty.
6564 procedure Add_Predicates;
6565 -- Appends expressions for any Predicate pragmas in the rep item chain
6566 -- Typ to Expr. Note that we look only at items for this exact entity.
6567 -- Inheritance of predicates for the parent type is done by calling the
6568 -- Predicate_Function of the parent type, using Add_Call above.
6570 function Test_RE (N : Node_Id) return Traverse_Result;
6571 -- Used in Test_REs, tests one node for being a raise expression, and if
6572 -- so sets Raise_Expression_Present True.
6574 procedure Test_REs is new Traverse_Proc (Test_RE);
6575 -- Tests to see if Expr contains any raise expressions
6577 function Process_RE (N : Node_Id) return Traverse_Result;
6578 -- Used in Process REs, tests if node N is a raise expression, and if
6579 -- so, marks it to be converted to return False.
6581 procedure Process_REs is new Traverse_Proc (Process_RE);
6582 -- Marks any raise expressions in Expr_M to return False
6584 --------------
6585 -- Add_Call --
6586 --------------
6588 procedure Add_Call (T : Entity_Id) is
6589 Exp : Node_Id;
6591 begin
6592 if Present (T) and then Present (Predicate_Function (T)) then
6593 Set_Has_Predicates (Typ);
6595 -- Build the call to the predicate function of T
6597 Exp :=
6598 Make_Predicate_Call
6599 (T, Convert_To (T, Make_Identifier (Loc, Object_Name)));
6601 -- Add call to evolving expression, using AND THEN if needed
6603 if No (Expr) then
6604 Expr := Exp;
6605 else
6606 Expr :=
6607 Make_And_Then (Loc,
6608 Left_Opnd => Relocate_Node (Expr),
6609 Right_Opnd => Exp);
6610 end if;
6612 -- Output info message on inheritance if required. Note we do not
6613 -- give this information for generic actual types, since it is
6614 -- unwelcome noise in that case in instantiations. We also
6615 -- generally suppress the message in instantiations, and also
6616 -- if it involves internal names.
6618 if Opt.List_Inherited_Aspects
6619 and then not Is_Generic_Actual_Type (Typ)
6620 and then Instantiation_Depth (Sloc (Typ)) = 0
6621 and then not Is_Internal_Name (Chars (T))
6622 and then not Is_Internal_Name (Chars (Typ))
6623 then
6624 Error_Msg_Sloc := Sloc (Predicate_Function (T));
6625 Error_Msg_Node_2 := T;
6626 Error_Msg_N ("info: & inherits predicate from & #?L?", Typ);
6627 end if;
6628 end if;
6629 end Add_Call;
6631 --------------------
6632 -- Add_Predicates --
6633 --------------------
6635 procedure Add_Predicates is
6636 Ritem : Node_Id;
6637 Arg1 : Node_Id;
6638 Arg2 : Node_Id;
6640 procedure Replace_Type_Reference (N : Node_Id);
6641 -- Replace a single occurrence N of the subtype name with a reference
6642 -- to the formal of the predicate function. N can be an identifier
6643 -- referencing the subtype, or a selected component, representing an
6644 -- appropriately qualified occurrence of the subtype name.
6646 procedure Replace_Type_References is
6647 new Replace_Type_References_Generic (Replace_Type_Reference);
6648 -- Traverse an expression changing every occurrence of an identifier
6649 -- whose name matches the name of the subtype with a reference to
6650 -- the formal parameter of the predicate function.
6652 ----------------------------
6653 -- Replace_Type_Reference --
6654 ----------------------------
6656 procedure Replace_Type_Reference (N : Node_Id) is
6657 begin
6658 Rewrite (N, Make_Identifier (Sloc (N), Object_Name));
6659 -- Use the Sloc of the usage name, not the defining name
6661 Set_Etype (N, Typ);
6662 Set_Entity (N, Object_Entity);
6664 -- We want to treat the node as if it comes from source, so that
6665 -- ASIS will not ignore it
6667 Set_Comes_From_Source (N, True);
6668 end Replace_Type_Reference;
6670 -- Start of processing for Add_Predicates
6672 begin
6673 Ritem := First_Rep_Item (Typ);
6674 while Present (Ritem) loop
6675 if Nkind (Ritem) = N_Pragma
6676 and then Pragma_Name (Ritem) = Name_Predicate
6677 then
6678 -- Save the static predicate of the type for diagnostics and
6679 -- error reporting purposes.
6681 if Present (Corresponding_Aspect (Ritem))
6682 and then Chars (Identifier (Corresponding_Aspect (Ritem))) =
6683 Name_Static_Predicate
6684 then
6685 Static_Predic := Ritem;
6686 end if;
6688 -- Acquire arguments
6690 Arg1 := First (Pragma_Argument_Associations (Ritem));
6691 Arg2 := Next (Arg1);
6693 Arg1 := Get_Pragma_Arg (Arg1);
6694 Arg2 := Get_Pragma_Arg (Arg2);
6696 -- See if this predicate pragma is for the current type or for
6697 -- its full view. A predicate on a private completion is placed
6698 -- on the partial view beause this is the visible entity that
6699 -- is frozen.
6701 if Entity (Arg1) = Typ
6702 or else Full_View (Entity (Arg1)) = Typ
6703 then
6704 -- We have a match, this entry is for our subtype
6706 -- We need to replace any occurrences of the name of the
6707 -- type with references to the object.
6709 Replace_Type_References (Arg2, Chars (Typ));
6711 -- If this predicate comes from an aspect, find the aspect
6712 -- specification, and replace the saved expression because
6713 -- we need the subtype references replaced for the calls to
6714 -- Preanalyze_Spec_Expressin in Check_Aspect_At_Freeze_Point
6715 -- and Check_Aspect_At_End_Of_Declarations.
6717 if From_Aspect_Specification (Ritem) then
6718 declare
6719 Aitem : Node_Id;
6721 begin
6722 -- Loop to find corresponding aspect, note that this
6723 -- must be present given the pragma is marked delayed.
6725 Aitem := Next_Rep_Item (Ritem);
6726 loop
6727 if Nkind (Aitem) = N_Aspect_Specification
6728 and then Aspect_Rep_Item (Aitem) = Ritem
6729 then
6730 Set_Entity
6731 (Identifier (Aitem), New_Copy_Tree (Arg2));
6732 exit;
6733 end if;
6735 Aitem := Next_Rep_Item (Aitem);
6736 end loop;
6737 end;
6738 end if;
6740 -- Now we can add the expression
6742 if No (Expr) then
6743 Expr := Relocate_Node (Arg2);
6745 -- There already was a predicate, so add to it
6747 else
6748 Expr :=
6749 Make_And_Then (Loc,
6750 Left_Opnd => Relocate_Node (Expr),
6751 Right_Opnd => Relocate_Node (Arg2));
6752 end if;
6753 end if;
6754 end if;
6756 Next_Rep_Item (Ritem);
6757 end loop;
6758 end Add_Predicates;
6760 ----------------
6761 -- Process_RE --
6762 ----------------
6764 function Process_RE (N : Node_Id) return Traverse_Result is
6765 begin
6766 if Nkind (N) = N_Raise_Expression then
6767 Set_Convert_To_Return_False (N);
6768 return Skip;
6769 else
6770 return OK;
6771 end if;
6772 end Process_RE;
6774 -------------
6775 -- Test_RE --
6776 -------------
6778 function Test_RE (N : Node_Id) return Traverse_Result is
6779 begin
6780 if Nkind (N) = N_Raise_Expression then
6781 Raise_Expression_Present := True;
6782 return Abandon;
6783 else
6784 return OK;
6785 end if;
6786 end Test_RE;
6788 -- Start of processing for Build_Predicate_Functions
6790 begin
6791 -- Return if already built or if type does not have predicates
6793 if not Has_Predicates (Typ)
6794 or else Present (Predicate_Function (Typ))
6795 then
6796 return;
6797 end if;
6799 -- Prepare to construct predicate expression
6801 Expr := Empty;
6803 -- Add Predicates for the current type
6805 Add_Predicates;
6807 -- Add predicates for ancestor if present
6809 declare
6810 Atyp : constant Entity_Id := Nearest_Ancestor (Typ);
6811 begin
6812 if Present (Atyp) then
6813 Add_Call (Atyp);
6814 end if;
6815 end;
6817 -- Case where predicates are present
6819 if Present (Expr) then
6821 -- Test for raise expression present
6823 Test_REs (Expr);
6825 -- If raise expression is present, capture a copy of Expr for use
6826 -- in building the predicateM function version later on. For this
6827 -- copy we replace references to Object_Entity by Object_Entity_M.
6829 if Raise_Expression_Present then
6830 declare
6831 Map : constant Elist_Id := New_Elmt_List;
6832 begin
6833 Append_Elmt (Object_Entity, Map);
6834 Append_Elmt (Object_Entity_M, Map);
6835 Expr_M := New_Copy_Tree (Expr, Map => Map);
6836 end;
6837 end if;
6839 -- Build the main predicate function
6841 declare
6842 SId : constant Entity_Id :=
6843 Make_Defining_Identifier (Loc,
6844 Chars => New_External_Name (Chars (Typ), "Predicate"));
6845 -- The entity for the the function spec
6847 SIdB : constant Entity_Id :=
6848 Make_Defining_Identifier (Loc,
6849 Chars => New_External_Name (Chars (Typ), "Predicate"));
6850 -- The entity for the function body
6852 Spec : Node_Id;
6853 FDecl : Node_Id;
6854 FBody : Node_Id;
6856 begin
6857 -- Build function declaration
6859 Set_Ekind (SId, E_Function);
6860 Set_Is_Internal (SId);
6861 Set_Is_Predicate_Function (SId);
6862 Set_Predicate_Function (Typ, SId);
6864 -- The predicate function is shared between views of a type
6866 if Is_Private_Type (Typ) and then Present (Full_View (Typ)) then
6867 Set_Predicate_Function (Full_View (Typ), SId);
6868 end if;
6870 Spec :=
6871 Make_Function_Specification (Loc,
6872 Defining_Unit_Name => SId,
6873 Parameter_Specifications => New_List (
6874 Make_Parameter_Specification (Loc,
6875 Defining_Identifier => Object_Entity,
6876 Parameter_Type => New_Occurrence_Of (Typ, Loc))),
6877 Result_Definition =>
6878 New_Occurrence_Of (Standard_Boolean, Loc));
6880 FDecl :=
6881 Make_Subprogram_Declaration (Loc,
6882 Specification => Spec);
6884 -- Build function body
6886 Spec :=
6887 Make_Function_Specification (Loc,
6888 Defining_Unit_Name => SIdB,
6889 Parameter_Specifications => New_List (
6890 Make_Parameter_Specification (Loc,
6891 Defining_Identifier =>
6892 Make_Defining_Identifier (Loc, Object_Name),
6893 Parameter_Type =>
6894 New_Occurrence_Of (Typ, Loc))),
6895 Result_Definition =>
6896 New_Occurrence_Of (Standard_Boolean, Loc));
6898 FBody :=
6899 Make_Subprogram_Body (Loc,
6900 Specification => Spec,
6901 Declarations => Empty_List,
6902 Handled_Statement_Sequence =>
6903 Make_Handled_Sequence_Of_Statements (Loc,
6904 Statements => New_List (
6905 Make_Simple_Return_Statement (Loc,
6906 Expression => Expr))));
6908 -- Insert declaration before freeze node and body after
6910 Insert_Before_And_Analyze (N, FDecl);
6911 Insert_After_And_Analyze (N, FBody);
6912 end;
6914 -- Test for raise expressions present and if so build M version
6916 if Raise_Expression_Present then
6917 declare
6918 SId : constant Entity_Id :=
6919 Make_Defining_Identifier (Loc,
6920 Chars => New_External_Name (Chars (Typ), "PredicateM"));
6921 -- The entity for the the function spec
6923 SIdB : constant Entity_Id :=
6924 Make_Defining_Identifier (Loc,
6925 Chars => New_External_Name (Chars (Typ), "PredicateM"));
6926 -- The entity for the function body
6928 Spec : Node_Id;
6929 FDecl : Node_Id;
6930 FBody : Node_Id;
6931 BTemp : Entity_Id;
6933 begin
6934 -- Mark any raise expressions for special expansion
6936 Process_REs (Expr_M);
6938 -- Build function declaration
6940 Set_Ekind (SId, E_Function);
6941 Set_Is_Predicate_Function_M (SId);
6942 Set_Predicate_Function_M (Typ, SId);
6944 -- The predicate function is shared between views of a type
6946 if Is_Private_Type (Typ) and then Present (Full_View (Typ)) then
6947 Set_Predicate_Function_M (Full_View (Typ), SId);
6948 end if;
6950 Spec :=
6951 Make_Function_Specification (Loc,
6952 Defining_Unit_Name => SId,
6953 Parameter_Specifications => New_List (
6954 Make_Parameter_Specification (Loc,
6955 Defining_Identifier => Object_Entity_M,
6956 Parameter_Type => New_Occurrence_Of (Typ, Loc))),
6957 Result_Definition =>
6958 New_Occurrence_Of (Standard_Boolean, Loc));
6960 FDecl :=
6961 Make_Subprogram_Declaration (Loc,
6962 Specification => Spec);
6964 -- Build function body
6966 Spec :=
6967 Make_Function_Specification (Loc,
6968 Defining_Unit_Name => SIdB,
6969 Parameter_Specifications => New_List (
6970 Make_Parameter_Specification (Loc,
6971 Defining_Identifier =>
6972 Make_Defining_Identifier (Loc, Object_Name),
6973 Parameter_Type =>
6974 New_Occurrence_Of (Typ, Loc))),
6975 Result_Definition =>
6976 New_Occurrence_Of (Standard_Boolean, Loc));
6978 -- Build the body, we declare the boolean expression before
6979 -- doing the return, because we are not really confident of
6980 -- what happens if a return appears within a return.
6982 BTemp :=
6983 Make_Defining_Identifier (Loc,
6984 Chars => New_Internal_Name ('B'));
6986 FBody :=
6987 Make_Subprogram_Body (Loc,
6988 Specification => Spec,
6990 Declarations => New_List (
6991 Make_Object_Declaration (Loc,
6992 Defining_Identifier => BTemp,
6993 Constant_Present => True,
6994 Object_Definition =>
6995 New_Occurrence_Of (Standard_Boolean, Loc),
6996 Expression => Expr_M)),
6998 Handled_Statement_Sequence =>
6999 Make_Handled_Sequence_Of_Statements (Loc,
7000 Statements => New_List (
7001 Make_Simple_Return_Statement (Loc,
7002 Expression => New_Occurrence_Of (BTemp, Loc)))));
7004 -- Insert declaration before freeze node and body after
7006 Insert_Before_And_Analyze (N, FDecl);
7007 Insert_After_And_Analyze (N, FBody);
7008 end;
7009 end if;
7011 if Is_Scalar_Type (Typ) then
7013 -- Attempt to build a static predicate for a discrete or a real
7014 -- subtype. This action may fail because the actual expression may
7015 -- not be static. Note that the presence of an inherited or
7016 -- explicitly declared dynamic predicate is orthogonal to this
7017 -- check because we are only interested in the static predicate.
7019 if Ekind_In (Typ, E_Decimal_Fixed_Point_Subtype,
7020 E_Enumeration_Subtype,
7021 E_Floating_Point_Subtype,
7022 E_Modular_Integer_Subtype,
7023 E_Ordinary_Fixed_Point_Subtype,
7024 E_Signed_Integer_Subtype)
7025 then
7026 Build_Static_Predicate (Typ, Expr, Object_Name);
7028 -- Emit an error when the predicate is categorized as static
7029 -- but its expression is dynamic.
7031 if Present (Static_Predic)
7032 and then No (Static_Predicate (Typ))
7033 then
7034 Error_Msg_F
7035 ("expression does not have required form for "
7036 & "static predicate",
7037 Next (First (Pragma_Argument_Associations
7038 (Static_Predic))));
7039 end if;
7040 end if;
7042 -- If a static predicate applies on other types, that's an error:
7043 -- either the type is scalar but non-static, or it's not even a
7044 -- scalar type. We do not issue an error on generated types, as
7045 -- these may be duplicates of the same error on a source type.
7047 elsif Present (Static_Predic) and then Comes_From_Source (Typ) then
7048 if Is_Scalar_Type (Typ) then
7049 Error_Msg_FE
7050 ("static predicate not allowed for non-static type&",
7051 Typ, Typ);
7052 else
7053 Error_Msg_FE
7054 ("static predicate not allowed for non-scalar type&",
7055 Typ, Typ);
7056 end if;
7057 end if;
7058 end if;
7059 end Build_Predicate_Functions;
7061 ----------------------------
7062 -- Build_Static_Predicate --
7063 ----------------------------
7065 procedure Build_Static_Predicate
7066 (Typ : Entity_Id;
7067 Expr : Node_Id;
7068 Nam : Name_Id)
7070 Loc : constant Source_Ptr := Sloc (Expr);
7072 Non_Static : exception;
7073 -- Raised if something non-static is found
7075 Btyp : constant Entity_Id := Base_Type (Typ);
7077 BLo : constant Uint := Expr_Value (Type_Low_Bound (Btyp));
7078 BHi : constant Uint := Expr_Value (Type_High_Bound (Btyp));
7079 -- Low bound and high bound value of base type of Typ
7081 TLo : constant Uint := Expr_Value (Type_Low_Bound (Typ));
7082 THi : constant Uint := Expr_Value (Type_High_Bound (Typ));
7083 -- Low bound and high bound values of static subtype Typ
7085 type REnt is record
7086 Lo, Hi : Uint;
7087 end record;
7088 -- One entry in a Rlist value, a single REnt (range entry) value denotes
7089 -- one range from Lo to Hi. To represent a single value range Lo = Hi =
7090 -- value.
7092 type RList is array (Nat range <>) of REnt;
7093 -- A list of ranges. The ranges are sorted in increasing order, and are
7094 -- disjoint (there is a gap of at least one value between each range in
7095 -- the table). A value is in the set of ranges in Rlist if it lies
7096 -- within one of these ranges.
7098 False_Range : constant RList :=
7099 RList'(1 .. 0 => REnt'(No_Uint, No_Uint));
7100 -- An empty set of ranges represents a range list that can never be
7101 -- satisfied, since there are no ranges in which the value could lie,
7102 -- so it does not lie in any of them. False_Range is a canonical value
7103 -- for this empty set, but general processing should test for an Rlist
7104 -- with length zero (see Is_False predicate), since other null ranges
7105 -- may appear which must be treated as False.
7107 True_Range : constant RList := RList'(1 => REnt'(BLo, BHi));
7108 -- Range representing True, value must be in the base range
7110 function "and" (Left : RList; Right : RList) return RList;
7111 -- And's together two range lists, returning a range list. This is a set
7112 -- intersection operation.
7114 function "or" (Left : RList; Right : RList) return RList;
7115 -- Or's together two range lists, returning a range list. This is a set
7116 -- union operation.
7118 function "not" (Right : RList) return RList;
7119 -- Returns complement of a given range list, i.e. a range list
7120 -- representing all the values in TLo .. THi that are not in the input
7121 -- operand Right.
7123 function Build_Val (V : Uint) return Node_Id;
7124 -- Return an analyzed N_Identifier node referencing this value, suitable
7125 -- for use as an entry in the Static_Predicate list. This node is typed
7126 -- with the base type.
7128 function Build_Range (Lo : Uint; Hi : Uint) return Node_Id;
7129 -- Return an analyzed N_Range node referencing this range, suitable for
7130 -- use as an entry in the Static_Predicate list. This node is typed with
7131 -- the base type.
7133 function Get_RList (Exp : Node_Id) return RList;
7134 -- This is a recursive routine that converts the given expression into a
7135 -- list of ranges, suitable for use in building the static predicate.
7137 function Is_False (R : RList) return Boolean;
7138 pragma Inline (Is_False);
7139 -- Returns True if the given range list is empty, and thus represents a
7140 -- False list of ranges that can never be satisfied.
7142 function Is_True (R : RList) return Boolean;
7143 -- Returns True if R trivially represents the True predicate by having a
7144 -- single range from BLo to BHi.
7146 function Is_Type_Ref (N : Node_Id) return Boolean;
7147 pragma Inline (Is_Type_Ref);
7148 -- Returns if True if N is a reference to the type for the predicate in
7149 -- the expression (i.e. if it is an identifier whose Chars field matches
7150 -- the Nam given in the call).
7152 function Lo_Val (N : Node_Id) return Uint;
7153 -- Given static expression or static range from a Static_Predicate list,
7154 -- gets expression value or low bound of range.
7156 function Hi_Val (N : Node_Id) return Uint;
7157 -- Given static expression or static range from a Static_Predicate list,
7158 -- gets expression value of high bound of range.
7160 function Membership_Entry (N : Node_Id) return RList;
7161 -- Given a single membership entry (range, value, or subtype), returns
7162 -- the corresponding range list. Raises Static_Error if not static.
7164 function Membership_Entries (N : Node_Id) return RList;
7165 -- Given an element on an alternatives list of a membership operation,
7166 -- returns the range list corresponding to this entry and all following
7167 -- entries (i.e. returns the "or" of this list of values).
7169 function Stat_Pred (Typ : Entity_Id) return RList;
7170 -- Given a type, if it has a static predicate, then return the predicate
7171 -- as a range list, otherwise raise Non_Static.
7173 -----------
7174 -- "and" --
7175 -----------
7177 function "and" (Left : RList; Right : RList) return RList is
7178 FEnt : REnt;
7179 -- First range of result
7181 SLeft : Nat := Left'First;
7182 -- Start of rest of left entries
7184 SRight : Nat := Right'First;
7185 -- Start of rest of right entries
7187 begin
7188 -- If either range is True, return the other
7190 if Is_True (Left) then
7191 return Right;
7192 elsif Is_True (Right) then
7193 return Left;
7194 end if;
7196 -- If either range is False, return False
7198 if Is_False (Left) or else Is_False (Right) then
7199 return False_Range;
7200 end if;
7202 -- Loop to remove entries at start that are disjoint, and thus just
7203 -- get discarded from the result entirely.
7205 loop
7206 -- If no operands left in either operand, result is false
7208 if SLeft > Left'Last or else SRight > Right'Last then
7209 return False_Range;
7211 -- Discard first left operand entry if disjoint with right
7213 elsif Left (SLeft).Hi < Right (SRight).Lo then
7214 SLeft := SLeft + 1;
7216 -- Discard first right operand entry if disjoint with left
7218 elsif Right (SRight).Hi < Left (SLeft).Lo then
7219 SRight := SRight + 1;
7221 -- Otherwise we have an overlapping entry
7223 else
7224 exit;
7225 end if;
7226 end loop;
7228 -- Now we have two non-null operands, and first entries overlap. The
7229 -- first entry in the result will be the overlapping part of these
7230 -- two entries.
7232 FEnt := REnt'(Lo => UI_Max (Left (SLeft).Lo, Right (SRight).Lo),
7233 Hi => UI_Min (Left (SLeft).Hi, Right (SRight).Hi));
7235 -- Now we can remove the entry that ended at a lower value, since its
7236 -- contribution is entirely contained in Fent.
7238 if Left (SLeft).Hi <= Right (SRight).Hi then
7239 SLeft := SLeft + 1;
7240 else
7241 SRight := SRight + 1;
7242 end if;
7244 -- Compute result by concatenating this first entry with the "and" of
7245 -- the remaining parts of the left and right operands. Note that if
7246 -- either of these is empty, "and" will yield empty, so that we will
7247 -- end up with just Fent, which is what we want in that case.
7249 return
7250 FEnt & (Left (SLeft .. Left'Last) and Right (SRight .. Right'Last));
7251 end "and";
7253 -----------
7254 -- "not" --
7255 -----------
7257 function "not" (Right : RList) return RList is
7258 begin
7259 -- Return True if False range
7261 if Is_False (Right) then
7262 return True_Range;
7263 end if;
7265 -- Return False if True range
7267 if Is_True (Right) then
7268 return False_Range;
7269 end if;
7271 -- Here if not trivial case
7273 declare
7274 Result : RList (1 .. Right'Length + 1);
7275 -- May need one more entry for gap at beginning and end
7277 Count : Nat := 0;
7278 -- Number of entries stored in Result
7280 begin
7281 -- Gap at start
7283 if Right (Right'First).Lo > TLo then
7284 Count := Count + 1;
7285 Result (Count) := REnt'(TLo, Right (Right'First).Lo - 1);
7286 end if;
7288 -- Gaps between ranges
7290 for J in Right'First .. Right'Last - 1 loop
7291 Count := Count + 1;
7292 Result (Count) :=
7293 REnt'(Right (J).Hi + 1, Right (J + 1).Lo - 1);
7294 end loop;
7296 -- Gap at end
7298 if Right (Right'Last).Hi < THi then
7299 Count := Count + 1;
7300 Result (Count) := REnt'(Right (Right'Last).Hi + 1, THi);
7301 end if;
7303 return Result (1 .. Count);
7304 end;
7305 end "not";
7307 ----------
7308 -- "or" --
7309 ----------
7311 function "or" (Left : RList; Right : RList) return RList is
7312 FEnt : REnt;
7313 -- First range of result
7315 SLeft : Nat := Left'First;
7316 -- Start of rest of left entries
7318 SRight : Nat := Right'First;
7319 -- Start of rest of right entries
7321 begin
7322 -- If either range is True, return True
7324 if Is_True (Left) or else Is_True (Right) then
7325 return True_Range;
7326 end if;
7328 -- If either range is False (empty), return the other
7330 if Is_False (Left) then
7331 return Right;
7332 elsif Is_False (Right) then
7333 return Left;
7334 end if;
7336 -- Initialize result first entry from left or right operand depending
7337 -- on which starts with the lower range.
7339 if Left (SLeft).Lo < Right (SRight).Lo then
7340 FEnt := Left (SLeft);
7341 SLeft := SLeft + 1;
7342 else
7343 FEnt := Right (SRight);
7344 SRight := SRight + 1;
7345 end if;
7347 -- This loop eats ranges from left and right operands that are
7348 -- contiguous with the first range we are gathering.
7350 loop
7351 -- Eat first entry in left operand if contiguous or overlapped by
7352 -- gathered first operand of result.
7354 if SLeft <= Left'Last
7355 and then Left (SLeft).Lo <= FEnt.Hi + 1
7356 then
7357 FEnt.Hi := UI_Max (FEnt.Hi, Left (SLeft).Hi);
7358 SLeft := SLeft + 1;
7360 -- Eat first entry in right operand if contiguous or overlapped by
7361 -- gathered right operand of result.
7363 elsif SRight <= Right'Last
7364 and then Right (SRight).Lo <= FEnt.Hi + 1
7365 then
7366 FEnt.Hi := UI_Max (FEnt.Hi, Right (SRight).Hi);
7367 SRight := SRight + 1;
7369 -- All done if no more entries to eat
7371 else
7372 exit;
7373 end if;
7374 end loop;
7376 -- Obtain result as the first entry we just computed, concatenated
7377 -- to the "or" of the remaining results (if one operand is empty,
7378 -- this will just concatenate with the other
7380 return
7381 FEnt & (Left (SLeft .. Left'Last) or Right (SRight .. Right'Last));
7382 end "or";
7384 -----------------
7385 -- Build_Range --
7386 -----------------
7388 function Build_Range (Lo : Uint; Hi : Uint) return Node_Id is
7389 Result : Node_Id;
7391 begin
7392 Result :=
7393 Make_Range (Loc,
7394 Low_Bound => Build_Val (Lo),
7395 High_Bound => Build_Val (Hi));
7396 Set_Etype (Result, Btyp);
7397 Set_Analyzed (Result);
7399 return Result;
7400 end Build_Range;
7402 ---------------
7403 -- Build_Val --
7404 ---------------
7406 function Build_Val (V : Uint) return Node_Id is
7407 Result : Node_Id;
7409 begin
7410 if Is_Enumeration_Type (Typ) then
7411 Result := Get_Enum_Lit_From_Pos (Typ, V, Loc);
7412 else
7413 Result := Make_Integer_Literal (Loc, V);
7414 end if;
7416 Set_Etype (Result, Btyp);
7417 Set_Is_Static_Expression (Result);
7418 Set_Analyzed (Result);
7419 return Result;
7420 end Build_Val;
7422 ---------------
7423 -- Get_RList --
7424 ---------------
7426 function Get_RList (Exp : Node_Id) return RList is
7427 Op : Node_Kind;
7428 Val : Uint;
7430 begin
7431 -- Static expression can only be true or false
7433 if Is_OK_Static_Expression (Exp) then
7435 -- For False
7437 if Expr_Value (Exp) = 0 then
7438 return False_Range;
7439 else
7440 return True_Range;
7441 end if;
7442 end if;
7444 -- Otherwise test node type
7446 Op := Nkind (Exp);
7448 case Op is
7450 -- And
7452 when N_Op_And | N_And_Then =>
7453 return Get_RList (Left_Opnd (Exp))
7455 Get_RList (Right_Opnd (Exp));
7457 -- Or
7459 when N_Op_Or | N_Or_Else =>
7460 return Get_RList (Left_Opnd (Exp))
7462 Get_RList (Right_Opnd (Exp));
7464 -- Not
7466 when N_Op_Not =>
7467 return not Get_RList (Right_Opnd (Exp));
7469 -- Comparisons of type with static value
7471 when N_Op_Compare =>
7473 -- Type is left operand
7475 if Is_Type_Ref (Left_Opnd (Exp))
7476 and then Is_OK_Static_Expression (Right_Opnd (Exp))
7477 then
7478 Val := Expr_Value (Right_Opnd (Exp));
7480 -- Typ is right operand
7482 elsif Is_Type_Ref (Right_Opnd (Exp))
7483 and then Is_OK_Static_Expression (Left_Opnd (Exp))
7484 then
7485 Val := Expr_Value (Left_Opnd (Exp));
7487 -- Invert sense of comparison
7489 case Op is
7490 when N_Op_Gt => Op := N_Op_Lt;
7491 when N_Op_Lt => Op := N_Op_Gt;
7492 when N_Op_Ge => Op := N_Op_Le;
7493 when N_Op_Le => Op := N_Op_Ge;
7494 when others => null;
7495 end case;
7497 -- Other cases are non-static
7499 else
7500 raise Non_Static;
7501 end if;
7503 -- Construct range according to comparison operation
7505 case Op is
7506 when N_Op_Eq =>
7507 return RList'(1 => REnt'(Val, Val));
7509 when N_Op_Ge =>
7510 return RList'(1 => REnt'(Val, BHi));
7512 when N_Op_Gt =>
7513 return RList'(1 => REnt'(Val + 1, BHi));
7515 when N_Op_Le =>
7516 return RList'(1 => REnt'(BLo, Val));
7518 when N_Op_Lt =>
7519 return RList'(1 => REnt'(BLo, Val - 1));
7521 when N_Op_Ne =>
7522 return RList'(REnt'(BLo, Val - 1),
7523 REnt'(Val + 1, BHi));
7525 when others =>
7526 raise Program_Error;
7527 end case;
7529 -- Membership (IN)
7531 when N_In =>
7532 if not Is_Type_Ref (Left_Opnd (Exp)) then
7533 raise Non_Static;
7534 end if;
7536 if Present (Right_Opnd (Exp)) then
7537 return Membership_Entry (Right_Opnd (Exp));
7538 else
7539 return Membership_Entries (First (Alternatives (Exp)));
7540 end if;
7542 -- Negative membership (NOT IN)
7544 when N_Not_In =>
7545 if not Is_Type_Ref (Left_Opnd (Exp)) then
7546 raise Non_Static;
7547 end if;
7549 if Present (Right_Opnd (Exp)) then
7550 return not Membership_Entry (Right_Opnd (Exp));
7551 else
7552 return not Membership_Entries (First (Alternatives (Exp)));
7553 end if;
7555 -- Function call, may be call to static predicate
7557 when N_Function_Call =>
7558 if Is_Entity_Name (Name (Exp)) then
7559 declare
7560 Ent : constant Entity_Id := Entity (Name (Exp));
7561 begin
7562 if Is_Predicate_Function (Ent)
7563 or else
7564 Is_Predicate_Function_M (Ent)
7565 then
7566 return Stat_Pred (Etype (First_Formal (Ent)));
7567 end if;
7568 end;
7569 end if;
7571 -- Other function call cases are non-static
7573 raise Non_Static;
7575 -- Qualified expression, dig out the expression
7577 when N_Qualified_Expression =>
7578 return Get_RList (Expression (Exp));
7580 -- Expression with actions: if no actions, dig out expression
7582 when N_Expression_With_Actions =>
7583 if Is_Empty_List (Actions (Exp)) then
7584 return Get_RList (Expression (Exp));
7586 else
7587 raise Non_Static;
7588 end if;
7590 -- Xor operator
7592 when N_Op_Xor =>
7593 return (Get_RList (Left_Opnd (Exp))
7594 and not Get_RList (Right_Opnd (Exp)))
7595 or (Get_RList (Right_Opnd (Exp))
7596 and not Get_RList (Left_Opnd (Exp)));
7598 -- Any other node type is non-static
7600 when others =>
7601 raise Non_Static;
7602 end case;
7603 end Get_RList;
7605 ------------
7606 -- Hi_Val --
7607 ------------
7609 function Hi_Val (N : Node_Id) return Uint is
7610 begin
7611 if Is_Static_Expression (N) then
7612 return Expr_Value (N);
7613 else
7614 pragma Assert (Nkind (N) = N_Range);
7615 return Expr_Value (High_Bound (N));
7616 end if;
7617 end Hi_Val;
7619 --------------
7620 -- Is_False --
7621 --------------
7623 function Is_False (R : RList) return Boolean is
7624 begin
7625 return R'Length = 0;
7626 end Is_False;
7628 -------------
7629 -- Is_True --
7630 -------------
7632 function Is_True (R : RList) return Boolean is
7633 begin
7634 return R'Length = 1
7635 and then R (R'First).Lo = BLo
7636 and then R (R'First).Hi = BHi;
7637 end Is_True;
7639 -----------------
7640 -- Is_Type_Ref --
7641 -----------------
7643 function Is_Type_Ref (N : Node_Id) return Boolean is
7644 begin
7645 return Nkind (N) = N_Identifier and then Chars (N) = Nam;
7646 end Is_Type_Ref;
7648 ------------
7649 -- Lo_Val --
7650 ------------
7652 function Lo_Val (N : Node_Id) return Uint is
7653 begin
7654 if Is_Static_Expression (N) then
7655 return Expr_Value (N);
7656 else
7657 pragma Assert (Nkind (N) = N_Range);
7658 return Expr_Value (Low_Bound (N));
7659 end if;
7660 end Lo_Val;
7662 ------------------------
7663 -- Membership_Entries --
7664 ------------------------
7666 function Membership_Entries (N : Node_Id) return RList is
7667 begin
7668 if No (Next (N)) then
7669 return Membership_Entry (N);
7670 else
7671 return Membership_Entry (N) or Membership_Entries (Next (N));
7672 end if;
7673 end Membership_Entries;
7675 ----------------------
7676 -- Membership_Entry --
7677 ----------------------
7679 function Membership_Entry (N : Node_Id) return RList is
7680 Val : Uint;
7681 SLo : Uint;
7682 SHi : Uint;
7684 begin
7685 -- Range case
7687 if Nkind (N) = N_Range then
7688 if not Is_Static_Expression (Low_Bound (N))
7689 or else
7690 not Is_Static_Expression (High_Bound (N))
7691 then
7692 raise Non_Static;
7693 else
7694 SLo := Expr_Value (Low_Bound (N));
7695 SHi := Expr_Value (High_Bound (N));
7696 return RList'(1 => REnt'(SLo, SHi));
7697 end if;
7699 -- Static expression case
7701 elsif Is_Static_Expression (N) then
7702 Val := Expr_Value (N);
7703 return RList'(1 => REnt'(Val, Val));
7705 -- Identifier (other than static expression) case
7707 else pragma Assert (Nkind (N) = N_Identifier);
7709 -- Type case
7711 if Is_Type (Entity (N)) then
7713 -- If type has predicates, process them
7715 if Has_Predicates (Entity (N)) then
7716 return Stat_Pred (Entity (N));
7718 -- For static subtype without predicates, get range
7720 elsif Is_Static_Subtype (Entity (N)) then
7721 SLo := Expr_Value (Type_Low_Bound (Entity (N)));
7722 SHi := Expr_Value (Type_High_Bound (Entity (N)));
7723 return RList'(1 => REnt'(SLo, SHi));
7725 -- Any other type makes us non-static
7727 else
7728 raise Non_Static;
7729 end if;
7731 -- Any other kind of identifier in predicate (e.g. a non-static
7732 -- expression value) means this is not a static predicate.
7734 else
7735 raise Non_Static;
7736 end if;
7737 end if;
7738 end Membership_Entry;
7740 ---------------
7741 -- Stat_Pred --
7742 ---------------
7744 function Stat_Pred (Typ : Entity_Id) return RList is
7745 begin
7746 -- Not static if type does not have static predicates
7748 if not Has_Predicates (Typ) or else No (Static_Predicate (Typ)) then
7749 raise Non_Static;
7750 end if;
7752 -- Otherwise we convert the predicate list to a range list
7754 declare
7755 Result : RList (1 .. List_Length (Static_Predicate (Typ)));
7756 P : Node_Id;
7758 begin
7759 P := First (Static_Predicate (Typ));
7760 for J in Result'Range loop
7761 Result (J) := REnt'(Lo_Val (P), Hi_Val (P));
7762 Next (P);
7763 end loop;
7765 return Result;
7766 end;
7767 end Stat_Pred;
7769 -- Start of processing for Build_Static_Predicate
7771 begin
7772 -- Now analyze the expression to see if it is a static predicate
7774 declare
7775 Ranges : constant RList := Get_RList (Expr);
7776 -- Range list from expression if it is static
7778 Plist : List_Id;
7780 begin
7781 -- Convert range list into a form for the static predicate. In the
7782 -- Ranges array, we just have raw ranges, these must be converted
7783 -- to properly typed and analyzed static expressions or range nodes.
7785 -- Note: here we limit ranges to the ranges of the subtype, so that
7786 -- a predicate is always false for values outside the subtype. That
7787 -- seems fine, such values are invalid anyway, and considering them
7788 -- to fail the predicate seems allowed and friendly, and furthermore
7789 -- simplifies processing for case statements and loops.
7791 Plist := New_List;
7793 for J in Ranges'Range loop
7794 declare
7795 Lo : Uint := Ranges (J).Lo;
7796 Hi : Uint := Ranges (J).Hi;
7798 begin
7799 -- Ignore completely out of range entry
7801 if Hi < TLo or else Lo > THi then
7802 null;
7804 -- Otherwise process entry
7806 else
7807 -- Adjust out of range value to subtype range
7809 if Lo < TLo then
7810 Lo := TLo;
7811 end if;
7813 if Hi > THi then
7814 Hi := THi;
7815 end if;
7817 -- Convert range into required form
7819 Append_To (Plist, Build_Range (Lo, Hi));
7820 end if;
7821 end;
7822 end loop;
7824 -- Processing was successful and all entries were static, so now we
7825 -- can store the result as the predicate list.
7827 Set_Static_Predicate (Typ, Plist);
7829 -- The processing for static predicates put the expression into
7830 -- canonical form as a series of ranges. It also eliminated
7831 -- duplicates and collapsed and combined ranges. We might as well
7832 -- replace the alternatives list of the right operand of the
7833 -- membership test with the static predicate list, which will
7834 -- usually be more efficient.
7836 declare
7837 New_Alts : constant List_Id := New_List;
7838 Old_Node : Node_Id;
7839 New_Node : Node_Id;
7841 begin
7842 Old_Node := First (Plist);
7843 while Present (Old_Node) loop
7844 New_Node := New_Copy (Old_Node);
7846 if Nkind (New_Node) = N_Range then
7847 Set_Low_Bound (New_Node, New_Copy (Low_Bound (Old_Node)));
7848 Set_High_Bound (New_Node, New_Copy (High_Bound (Old_Node)));
7849 end if;
7851 Append_To (New_Alts, New_Node);
7852 Next (Old_Node);
7853 end loop;
7855 -- If empty list, replace by False
7857 if Is_Empty_List (New_Alts) then
7858 Rewrite (Expr, New_Occurrence_Of (Standard_False, Loc));
7860 -- Else replace by set membership test
7862 else
7863 Rewrite (Expr,
7864 Make_In (Loc,
7865 Left_Opnd => Make_Identifier (Loc, Nam),
7866 Right_Opnd => Empty,
7867 Alternatives => New_Alts));
7869 -- Resolve new expression in function context
7871 Install_Formals (Predicate_Function (Typ));
7872 Push_Scope (Predicate_Function (Typ));
7873 Analyze_And_Resolve (Expr, Standard_Boolean);
7874 Pop_Scope;
7875 end if;
7876 end;
7877 end;
7879 -- If non-static, return doing nothing
7881 exception
7882 when Non_Static =>
7883 return;
7884 end Build_Static_Predicate;
7886 -----------------------------------------
7887 -- Check_Aspect_At_End_Of_Declarations --
7888 -----------------------------------------
7890 procedure Check_Aspect_At_End_Of_Declarations (ASN : Node_Id) is
7891 Ent : constant Entity_Id := Entity (ASN);
7892 Ident : constant Node_Id := Identifier (ASN);
7893 A_Id : constant Aspect_Id := Get_Aspect_Id (Chars (Ident));
7895 End_Decl_Expr : constant Node_Id := Entity (Ident);
7896 -- Expression to be analyzed at end of declarations
7898 Freeze_Expr : constant Node_Id := Expression (ASN);
7899 -- Expression from call to Check_Aspect_At_Freeze_Point
7901 T : constant Entity_Id := Etype (Freeze_Expr);
7902 -- Type required for preanalyze call
7904 Err : Boolean;
7905 -- Set False if error
7907 -- On entry to this procedure, Entity (Ident) contains a copy of the
7908 -- original expression from the aspect, saved for this purpose, and
7909 -- but Expression (Ident) is a preanalyzed copy of the expression,
7910 -- preanalyzed just after the freeze point.
7912 procedure Check_Overloaded_Name;
7913 -- For aspects whose expression is simply a name, this routine checks if
7914 -- the name is overloaded or not. If so, it verifies there is an
7915 -- interpretation that matches the entity obtained at the freeze point,
7916 -- otherwise the compiler complains.
7918 ---------------------------
7919 -- Check_Overloaded_Name --
7920 ---------------------------
7922 procedure Check_Overloaded_Name is
7923 begin
7924 if not Is_Overloaded (End_Decl_Expr) then
7925 Err := Entity (End_Decl_Expr) /= Entity (Freeze_Expr);
7927 else
7928 Err := True;
7930 declare
7931 Index : Interp_Index;
7932 It : Interp;
7934 begin
7935 Get_First_Interp (End_Decl_Expr, Index, It);
7936 while Present (It.Typ) loop
7937 if It.Nam = Entity (Freeze_Expr) then
7938 Err := False;
7939 exit;
7940 end if;
7942 Get_Next_Interp (Index, It);
7943 end loop;
7944 end;
7945 end if;
7946 end Check_Overloaded_Name;
7948 -- Start of processing for Check_Aspect_At_End_Of_Declarations
7950 begin
7951 -- Case of aspects Dimension, Dimension_System and Synchronization
7953 if A_Id = Aspect_Synchronization then
7954 return;
7956 -- Case of stream attributes, just have to compare entities. However,
7957 -- the expression is just a name (possibly overloaded), and there may
7958 -- be stream operations declared for unrelated types, so we just need
7959 -- to verify that one of these interpretations is the one available at
7960 -- at the freeze point.
7962 elsif A_Id = Aspect_Input or else
7963 A_Id = Aspect_Output or else
7964 A_Id = Aspect_Read or else
7965 A_Id = Aspect_Write
7966 then
7967 Analyze (End_Decl_Expr);
7968 Check_Overloaded_Name;
7970 elsif A_Id = Aspect_Variable_Indexing or else
7971 A_Id = Aspect_Constant_Indexing or else
7972 A_Id = Aspect_Default_Iterator or else
7973 A_Id = Aspect_Iterator_Element
7974 then
7975 -- Make type unfrozen before analysis, to prevent spurious errors
7976 -- about late attributes.
7978 Set_Is_Frozen (Ent, False);
7979 Analyze (End_Decl_Expr);
7980 Set_Is_Frozen (Ent, True);
7982 -- If the end of declarations comes before any other freeze
7983 -- point, the Freeze_Expr is not analyzed: no check needed.
7985 if Analyzed (Freeze_Expr) and then not In_Instance then
7986 Check_Overloaded_Name;
7987 else
7988 Err := False;
7989 end if;
7991 -- All other cases
7993 else
7994 -- In a generic context the aspect expressions have not been
7995 -- preanalyzed, so do it now. There are no conformance checks
7996 -- to perform in this case.
7998 if No (T) then
7999 Check_Aspect_At_Freeze_Point (ASN);
8000 return;
8002 -- The default values attributes may be defined in the private part,
8003 -- and the analysis of the expression may take place when only the
8004 -- partial view is visible. The expression must be scalar, so use
8005 -- the full view to resolve.
8007 elsif (A_Id = Aspect_Default_Value
8008 or else
8009 A_Id = Aspect_Default_Component_Value)
8010 and then Is_Private_Type (T)
8011 then
8012 Preanalyze_Spec_Expression (End_Decl_Expr, Full_View (T));
8013 else
8014 Preanalyze_Spec_Expression (End_Decl_Expr, T);
8015 end if;
8017 Err := not Fully_Conformant_Expressions (End_Decl_Expr, Freeze_Expr);
8018 end if;
8020 -- Output error message if error
8022 if Err then
8023 Error_Msg_NE
8024 ("visibility of aspect for& changes after freeze point",
8025 ASN, Ent);
8026 Error_Msg_NE
8027 ("info: & is frozen here, aspects evaluated at this point??",
8028 Freeze_Node (Ent), Ent);
8029 end if;
8030 end Check_Aspect_At_End_Of_Declarations;
8032 ----------------------------------
8033 -- Check_Aspect_At_Freeze_Point --
8034 ----------------------------------
8036 procedure Check_Aspect_At_Freeze_Point (ASN : Node_Id) is
8037 Ident : constant Node_Id := Identifier (ASN);
8038 -- Identifier (use Entity field to save expression)
8040 A_Id : constant Aspect_Id := Get_Aspect_Id (Chars (Ident));
8042 T : Entity_Id := Empty;
8043 -- Type required for preanalyze call
8045 begin
8046 -- On entry to this procedure, Entity (Ident) contains a copy of the
8047 -- original expression from the aspect, saved for this purpose.
8049 -- On exit from this procedure Entity (Ident) is unchanged, still
8050 -- containing that copy, but Expression (Ident) is a preanalyzed copy
8051 -- of the expression, preanalyzed just after the freeze point.
8053 -- Make a copy of the expression to be preanalyzed
8055 Set_Expression (ASN, New_Copy_Tree (Entity (Ident)));
8057 -- Find type for preanalyze call
8059 case A_Id is
8061 -- No_Aspect should be impossible
8063 when No_Aspect =>
8064 raise Program_Error;
8066 -- Aspects taking an optional boolean argument
8068 when Boolean_Aspects |
8069 Library_Unit_Aspects =>
8071 T := Standard_Boolean;
8073 -- Aspects corresponding to attribute definition clauses
8075 when Aspect_Address =>
8076 T := RTE (RE_Address);
8078 when Aspect_Attach_Handler =>
8079 T := RTE (RE_Interrupt_ID);
8081 when Aspect_Bit_Order | Aspect_Scalar_Storage_Order =>
8082 T := RTE (RE_Bit_Order);
8084 when Aspect_Convention =>
8085 return;
8087 when Aspect_CPU =>
8088 T := RTE (RE_CPU_Range);
8090 -- Default_Component_Value is resolved with the component type
8092 when Aspect_Default_Component_Value =>
8093 T := Component_Type (Entity (ASN));
8095 -- Default_Value is resolved with the type entity in question
8097 when Aspect_Default_Value =>
8098 T := Entity (ASN);
8100 -- Depends is a delayed aspect because it mentiones names first
8101 -- introduced by aspect Global which is already delayed. There is
8102 -- no action to be taken with respect to the aspect itself as the
8103 -- analysis is done by the corresponding pragma.
8105 when Aspect_Depends =>
8106 return;
8108 when Aspect_Dispatching_Domain =>
8109 T := RTE (RE_Dispatching_Domain);
8111 when Aspect_External_Tag =>
8112 T := Standard_String;
8114 when Aspect_External_Name =>
8115 T := Standard_String;
8117 -- Global is a delayed aspect because it may reference names that
8118 -- have not been declared yet. There is no action to be taken with
8119 -- respect to the aspect itself as the reference checking is done
8120 -- on the corresponding pragma.
8122 when Aspect_Global =>
8123 return;
8125 when Aspect_Link_Name =>
8126 T := Standard_String;
8128 when Aspect_Priority | Aspect_Interrupt_Priority =>
8129 T := Standard_Integer;
8131 when Aspect_Relative_Deadline =>
8132 T := RTE (RE_Time_Span);
8134 when Aspect_Small =>
8135 T := Universal_Real;
8137 -- For a simple storage pool, we have to retrieve the type of the
8138 -- pool object associated with the aspect's corresponding attribute
8139 -- definition clause.
8141 when Aspect_Simple_Storage_Pool =>
8142 T := Etype (Expression (Aspect_Rep_Item (ASN)));
8144 when Aspect_Storage_Pool =>
8145 T := Class_Wide_Type (RTE (RE_Root_Storage_Pool));
8147 when Aspect_Alignment |
8148 Aspect_Component_Size |
8149 Aspect_Machine_Radix |
8150 Aspect_Object_Size |
8151 Aspect_Size |
8152 Aspect_Storage_Size |
8153 Aspect_Stream_Size |
8154 Aspect_Value_Size =>
8155 T := Any_Integer;
8157 when Aspect_Linker_Section =>
8158 T := Standard_String;
8160 when Aspect_Synchronization =>
8161 return;
8163 -- Special case, the expression of these aspects is just an entity
8164 -- that does not need any resolution, so just analyze.
8166 when Aspect_Input |
8167 Aspect_Output |
8168 Aspect_Read |
8169 Aspect_Suppress |
8170 Aspect_Unsuppress |
8171 Aspect_Warnings |
8172 Aspect_Write =>
8173 Analyze (Expression (ASN));
8174 return;
8176 -- Same for Iterator aspects, where the expression is a function
8177 -- name. Legality rules are checked separately.
8179 when Aspect_Constant_Indexing |
8180 Aspect_Default_Iterator |
8181 Aspect_Iterator_Element |
8182 Aspect_Variable_Indexing =>
8183 Analyze (Expression (ASN));
8184 return;
8186 -- Ditto for Iterable, legality checks in Validate_Iterable_Aspect.
8188 when Aspect_Iterable =>
8189 T := Entity (ASN);
8191 declare
8192 Cursor : constant Entity_Id := Get_Cursor_Type (ASN, T);
8193 Assoc : Node_Id;
8194 Expr : Node_Id;
8196 begin
8197 if Cursor = Any_Type then
8198 return;
8199 end if;
8201 Assoc := First (Component_Associations (Expression (ASN)));
8202 while Present (Assoc) loop
8203 Expr := Expression (Assoc);
8204 Analyze (Expr);
8206 if not Error_Posted (Expr) then
8207 Resolve_Iterable_Operation
8208 (Expr, Cursor, T, Chars (First (Choices (Assoc))));
8209 end if;
8211 Next (Assoc);
8212 end loop;
8213 end;
8215 return;
8217 -- Invariant/Predicate take boolean expressions
8219 when Aspect_Dynamic_Predicate |
8220 Aspect_Invariant |
8221 Aspect_Predicate |
8222 Aspect_Static_Predicate |
8223 Aspect_Type_Invariant =>
8224 T := Standard_Boolean;
8226 -- Here is the list of aspects that don't require delay analysis
8228 when Aspect_Abstract_State |
8229 Aspect_Contract_Cases |
8230 Aspect_Dimension |
8231 Aspect_Dimension_System |
8232 Aspect_Implicit_Dereference |
8233 Aspect_Initial_Condition |
8234 Aspect_Initializes |
8235 Aspect_Part_Of |
8236 Aspect_Post |
8237 Aspect_Postcondition |
8238 Aspect_Pre |
8239 Aspect_Precondition |
8240 Aspect_Refined_Depends |
8241 Aspect_Refined_Global |
8242 Aspect_Refined_Post |
8243 Aspect_Refined_State |
8244 Aspect_SPARK_Mode |
8245 Aspect_Test_Case =>
8246 raise Program_Error;
8248 end case;
8250 -- Do the preanalyze call
8252 Preanalyze_Spec_Expression (Expression (ASN), T);
8253 end Check_Aspect_At_Freeze_Point;
8255 -----------------------------------
8256 -- Check_Constant_Address_Clause --
8257 -----------------------------------
8259 procedure Check_Constant_Address_Clause
8260 (Expr : Node_Id;
8261 U_Ent : Entity_Id)
8263 procedure Check_At_Constant_Address (Nod : Node_Id);
8264 -- Checks that the given node N represents a name whose 'Address is
8265 -- constant (in the same sense as OK_Constant_Address_Clause, i.e. the
8266 -- address value is the same at the point of declaration of U_Ent and at
8267 -- the time of elaboration of the address clause.
8269 procedure Check_Expr_Constants (Nod : Node_Id);
8270 -- Checks that Nod meets the requirements for a constant address clause
8271 -- in the sense of the enclosing procedure.
8273 procedure Check_List_Constants (Lst : List_Id);
8274 -- Check that all elements of list Lst meet the requirements for a
8275 -- constant address clause in the sense of the enclosing procedure.
8277 -------------------------------
8278 -- Check_At_Constant_Address --
8279 -------------------------------
8281 procedure Check_At_Constant_Address (Nod : Node_Id) is
8282 begin
8283 if Is_Entity_Name (Nod) then
8284 if Present (Address_Clause (Entity ((Nod)))) then
8285 Error_Msg_NE
8286 ("invalid address clause for initialized object &!",
8287 Nod, U_Ent);
8288 Error_Msg_NE
8289 ("address for& cannot" &
8290 " depend on another address clause! (RM 13.1(22))!",
8291 Nod, U_Ent);
8293 elsif In_Same_Source_Unit (Entity (Nod), U_Ent)
8294 and then Sloc (U_Ent) < Sloc (Entity (Nod))
8295 then
8296 Error_Msg_NE
8297 ("invalid address clause for initialized object &!",
8298 Nod, U_Ent);
8299 Error_Msg_Node_2 := U_Ent;
8300 Error_Msg_NE
8301 ("\& must be defined before & (RM 13.1(22))!",
8302 Nod, Entity (Nod));
8303 end if;
8305 elsif Nkind (Nod) = N_Selected_Component then
8306 declare
8307 T : constant Entity_Id := Etype (Prefix (Nod));
8309 begin
8310 if (Is_Record_Type (T)
8311 and then Has_Discriminants (T))
8312 or else
8313 (Is_Access_Type (T)
8314 and then Is_Record_Type (Designated_Type (T))
8315 and then Has_Discriminants (Designated_Type (T)))
8316 then
8317 Error_Msg_NE
8318 ("invalid address clause for initialized object &!",
8319 Nod, U_Ent);
8320 Error_Msg_N
8321 ("\address cannot depend on component" &
8322 " of discriminated record (RM 13.1(22))!",
8323 Nod);
8324 else
8325 Check_At_Constant_Address (Prefix (Nod));
8326 end if;
8327 end;
8329 elsif Nkind (Nod) = N_Indexed_Component then
8330 Check_At_Constant_Address (Prefix (Nod));
8331 Check_List_Constants (Expressions (Nod));
8333 else
8334 Check_Expr_Constants (Nod);
8335 end if;
8336 end Check_At_Constant_Address;
8338 --------------------------
8339 -- Check_Expr_Constants --
8340 --------------------------
8342 procedure Check_Expr_Constants (Nod : Node_Id) is
8343 Loc_U_Ent : constant Source_Ptr := Sloc (U_Ent);
8344 Ent : Entity_Id := Empty;
8346 begin
8347 if Nkind (Nod) in N_Has_Etype
8348 and then Etype (Nod) = Any_Type
8349 then
8350 return;
8351 end if;
8353 case Nkind (Nod) is
8354 when N_Empty | N_Error =>
8355 return;
8357 when N_Identifier | N_Expanded_Name =>
8358 Ent := Entity (Nod);
8360 -- We need to look at the original node if it is different
8361 -- from the node, since we may have rewritten things and
8362 -- substituted an identifier representing the rewrite.
8364 if Original_Node (Nod) /= Nod then
8365 Check_Expr_Constants (Original_Node (Nod));
8367 -- If the node is an object declaration without initial
8368 -- value, some code has been expanded, and the expression
8369 -- is not constant, even if the constituents might be
8370 -- acceptable, as in A'Address + offset.
8372 if Ekind (Ent) = E_Variable
8373 and then
8374 Nkind (Declaration_Node (Ent)) = N_Object_Declaration
8375 and then
8376 No (Expression (Declaration_Node (Ent)))
8377 then
8378 Error_Msg_NE
8379 ("invalid address clause for initialized object &!",
8380 Nod, U_Ent);
8382 -- If entity is constant, it may be the result of expanding
8383 -- a check. We must verify that its declaration appears
8384 -- before the object in question, else we also reject the
8385 -- address clause.
8387 elsif Ekind (Ent) = E_Constant
8388 and then In_Same_Source_Unit (Ent, U_Ent)
8389 and then Sloc (Ent) > Loc_U_Ent
8390 then
8391 Error_Msg_NE
8392 ("invalid address clause for initialized object &!",
8393 Nod, U_Ent);
8394 end if;
8396 return;
8397 end if;
8399 -- Otherwise look at the identifier and see if it is OK
8401 if Ekind_In (Ent, E_Named_Integer, E_Named_Real)
8402 or else Is_Type (Ent)
8403 then
8404 return;
8406 elsif
8407 Ekind (Ent) = E_Constant
8408 or else
8409 Ekind (Ent) = E_In_Parameter
8410 then
8411 -- This is the case where we must have Ent defined before
8412 -- U_Ent. Clearly if they are in different units this
8413 -- requirement is met since the unit containing Ent is
8414 -- already processed.
8416 if not In_Same_Source_Unit (Ent, U_Ent) then
8417 return;
8419 -- Otherwise location of Ent must be before the location
8420 -- of U_Ent, that's what prior defined means.
8422 elsif Sloc (Ent) < Loc_U_Ent then
8423 return;
8425 else
8426 Error_Msg_NE
8427 ("invalid address clause for initialized object &!",
8428 Nod, U_Ent);
8429 Error_Msg_Node_2 := U_Ent;
8430 Error_Msg_NE
8431 ("\& must be defined before & (RM 13.1(22))!",
8432 Nod, Ent);
8433 end if;
8435 elsif Nkind (Original_Node (Nod)) = N_Function_Call then
8436 Check_Expr_Constants (Original_Node (Nod));
8438 else
8439 Error_Msg_NE
8440 ("invalid address clause for initialized object &!",
8441 Nod, U_Ent);
8443 if Comes_From_Source (Ent) then
8444 Error_Msg_NE
8445 ("\reference to variable& not allowed"
8446 & " (RM 13.1(22))!", Nod, Ent);
8447 else
8448 Error_Msg_N
8449 ("non-static expression not allowed"
8450 & " (RM 13.1(22))!", Nod);
8451 end if;
8452 end if;
8454 when N_Integer_Literal =>
8456 -- If this is a rewritten unchecked conversion, in a system
8457 -- where Address is an integer type, always use the base type
8458 -- for a literal value. This is user-friendly and prevents
8459 -- order-of-elaboration issues with instances of unchecked
8460 -- conversion.
8462 if Nkind (Original_Node (Nod)) = N_Function_Call then
8463 Set_Etype (Nod, Base_Type (Etype (Nod)));
8464 end if;
8466 when N_Real_Literal |
8467 N_String_Literal |
8468 N_Character_Literal =>
8469 return;
8471 when N_Range =>
8472 Check_Expr_Constants (Low_Bound (Nod));
8473 Check_Expr_Constants (High_Bound (Nod));
8475 when N_Explicit_Dereference =>
8476 Check_Expr_Constants (Prefix (Nod));
8478 when N_Indexed_Component =>
8479 Check_Expr_Constants (Prefix (Nod));
8480 Check_List_Constants (Expressions (Nod));
8482 when N_Slice =>
8483 Check_Expr_Constants (Prefix (Nod));
8484 Check_Expr_Constants (Discrete_Range (Nod));
8486 when N_Selected_Component =>
8487 Check_Expr_Constants (Prefix (Nod));
8489 when N_Attribute_Reference =>
8490 if Nam_In (Attribute_Name (Nod), Name_Address,
8491 Name_Access,
8492 Name_Unchecked_Access,
8493 Name_Unrestricted_Access)
8494 then
8495 Check_At_Constant_Address (Prefix (Nod));
8497 else
8498 Check_Expr_Constants (Prefix (Nod));
8499 Check_List_Constants (Expressions (Nod));
8500 end if;
8502 when N_Aggregate =>
8503 Check_List_Constants (Component_Associations (Nod));
8504 Check_List_Constants (Expressions (Nod));
8506 when N_Component_Association =>
8507 Check_Expr_Constants (Expression (Nod));
8509 when N_Extension_Aggregate =>
8510 Check_Expr_Constants (Ancestor_Part (Nod));
8511 Check_List_Constants (Component_Associations (Nod));
8512 Check_List_Constants (Expressions (Nod));
8514 when N_Null =>
8515 return;
8517 when N_Binary_Op | N_Short_Circuit | N_Membership_Test =>
8518 Check_Expr_Constants (Left_Opnd (Nod));
8519 Check_Expr_Constants (Right_Opnd (Nod));
8521 when N_Unary_Op =>
8522 Check_Expr_Constants (Right_Opnd (Nod));
8524 when N_Type_Conversion |
8525 N_Qualified_Expression |
8526 N_Allocator |
8527 N_Unchecked_Type_Conversion =>
8528 Check_Expr_Constants (Expression (Nod));
8530 when N_Function_Call =>
8531 if not Is_Pure (Entity (Name (Nod))) then
8532 Error_Msg_NE
8533 ("invalid address clause for initialized object &!",
8534 Nod, U_Ent);
8536 Error_Msg_NE
8537 ("\function & is not pure (RM 13.1(22))!",
8538 Nod, Entity (Name (Nod)));
8540 else
8541 Check_List_Constants (Parameter_Associations (Nod));
8542 end if;
8544 when N_Parameter_Association =>
8545 Check_Expr_Constants (Explicit_Actual_Parameter (Nod));
8547 when others =>
8548 Error_Msg_NE
8549 ("invalid address clause for initialized object &!",
8550 Nod, U_Ent);
8551 Error_Msg_NE
8552 ("\must be constant defined before& (RM 13.1(22))!",
8553 Nod, U_Ent);
8554 end case;
8555 end Check_Expr_Constants;
8557 --------------------------
8558 -- Check_List_Constants --
8559 --------------------------
8561 procedure Check_List_Constants (Lst : List_Id) is
8562 Nod1 : Node_Id;
8564 begin
8565 if Present (Lst) then
8566 Nod1 := First (Lst);
8567 while Present (Nod1) loop
8568 Check_Expr_Constants (Nod1);
8569 Next (Nod1);
8570 end loop;
8571 end if;
8572 end Check_List_Constants;
8574 -- Start of processing for Check_Constant_Address_Clause
8576 begin
8577 -- If rep_clauses are to be ignored, no need for legality checks. In
8578 -- particular, no need to pester user about rep clauses that violate
8579 -- the rule on constant addresses, given that these clauses will be
8580 -- removed by Freeze before they reach the back end.
8582 if not Ignore_Rep_Clauses then
8583 Check_Expr_Constants (Expr);
8584 end if;
8585 end Check_Constant_Address_Clause;
8587 ---------------------------
8588 -- Check_Pool_Size_Clash --
8589 ---------------------------
8591 procedure Check_Pool_Size_Clash (Ent : Entity_Id; SP, SS : Node_Id) is
8592 Post : Node_Id;
8594 begin
8595 -- We need to find out which one came first. Note that in the case of
8596 -- aspects mixed with pragmas there are cases where the processing order
8597 -- is reversed, which is why we do the check here.
8599 if Sloc (SP) < Sloc (SS) then
8600 Error_Msg_Sloc := Sloc (SP);
8601 Post := SS;
8602 Error_Msg_NE ("Storage_Pool previously given for&#", Post, Ent);
8604 else
8605 Error_Msg_Sloc := Sloc (SS);
8606 Post := SP;
8607 Error_Msg_NE ("Storage_Size previously given for&#", Post, Ent);
8608 end if;
8610 Error_Msg_N
8611 ("\cannot have Storage_Size and Storage_Pool (RM 13.11(3))", Post);
8612 end Check_Pool_Size_Clash;
8614 ----------------------------------------
8615 -- Check_Record_Representation_Clause --
8616 ----------------------------------------
8618 procedure Check_Record_Representation_Clause (N : Node_Id) is
8619 Loc : constant Source_Ptr := Sloc (N);
8620 Ident : constant Node_Id := Identifier (N);
8621 Rectype : Entity_Id;
8622 Fent : Entity_Id;
8623 CC : Node_Id;
8624 Fbit : Uint;
8625 Lbit : Uint;
8626 Hbit : Uint := Uint_0;
8627 Comp : Entity_Id;
8628 Pcomp : Entity_Id;
8630 Max_Bit_So_Far : Uint;
8631 -- Records the maximum bit position so far. If all field positions
8632 -- are monotonically increasing, then we can skip the circuit for
8633 -- checking for overlap, since no overlap is possible.
8635 Tagged_Parent : Entity_Id := Empty;
8636 -- This is set in the case of a derived tagged type for which we have
8637 -- Is_Fully_Repped_Tagged_Type True (indicating that all components are
8638 -- positioned by record representation clauses). In this case we must
8639 -- check for overlap between components of this tagged type, and the
8640 -- components of its parent. Tagged_Parent will point to this parent
8641 -- type. For all other cases Tagged_Parent is left set to Empty.
8643 Parent_Last_Bit : Uint;
8644 -- Relevant only if Tagged_Parent is set, Parent_Last_Bit indicates the
8645 -- last bit position for any field in the parent type. We only need to
8646 -- check overlap for fields starting below this point.
8648 Overlap_Check_Required : Boolean;
8649 -- Used to keep track of whether or not an overlap check is required
8651 Overlap_Detected : Boolean := False;
8652 -- Set True if an overlap is detected
8654 Ccount : Natural := 0;
8655 -- Number of component clauses in record rep clause
8657 procedure Check_Component_Overlap (C1_Ent, C2_Ent : Entity_Id);
8658 -- Given two entities for record components or discriminants, checks
8659 -- if they have overlapping component clauses and issues errors if so.
8661 procedure Find_Component;
8662 -- Finds component entity corresponding to current component clause (in
8663 -- CC), and sets Comp to the entity, and Fbit/Lbit to the zero origin
8664 -- start/stop bits for the field. If there is no matching component or
8665 -- if the matching component does not have a component clause, then
8666 -- that's an error and Comp is set to Empty, but no error message is
8667 -- issued, since the message was already given. Comp is also set to
8668 -- Empty if the current "component clause" is in fact a pragma.
8670 -----------------------------
8671 -- Check_Component_Overlap --
8672 -----------------------------
8674 procedure Check_Component_Overlap (C1_Ent, C2_Ent : Entity_Id) is
8675 CC1 : constant Node_Id := Component_Clause (C1_Ent);
8676 CC2 : constant Node_Id := Component_Clause (C2_Ent);
8678 begin
8679 if Present (CC1) and then Present (CC2) then
8681 -- Exclude odd case where we have two tag components in the same
8682 -- record, both at location zero. This seems a bit strange, but
8683 -- it seems to happen in some circumstances, perhaps on an error.
8685 if Nam_In (Chars (C1_Ent), Name_uTag, Name_uTag) then
8686 return;
8687 end if;
8689 -- Here we check if the two fields overlap
8691 declare
8692 S1 : constant Uint := Component_Bit_Offset (C1_Ent);
8693 S2 : constant Uint := Component_Bit_Offset (C2_Ent);
8694 E1 : constant Uint := S1 + Esize (C1_Ent);
8695 E2 : constant Uint := S2 + Esize (C2_Ent);
8697 begin
8698 if E2 <= S1 or else E1 <= S2 then
8699 null;
8700 else
8701 Error_Msg_Node_2 := Component_Name (CC2);
8702 Error_Msg_Sloc := Sloc (Error_Msg_Node_2);
8703 Error_Msg_Node_1 := Component_Name (CC1);
8704 Error_Msg_N
8705 ("component& overlaps & #", Component_Name (CC1));
8706 Overlap_Detected := True;
8707 end if;
8708 end;
8709 end if;
8710 end Check_Component_Overlap;
8712 --------------------
8713 -- Find_Component --
8714 --------------------
8716 procedure Find_Component is
8718 procedure Search_Component (R : Entity_Id);
8719 -- Search components of R for a match. If found, Comp is set
8721 ----------------------
8722 -- Search_Component --
8723 ----------------------
8725 procedure Search_Component (R : Entity_Id) is
8726 begin
8727 Comp := First_Component_Or_Discriminant (R);
8728 while Present (Comp) loop
8730 -- Ignore error of attribute name for component name (we
8731 -- already gave an error message for this, so no need to
8732 -- complain here)
8734 if Nkind (Component_Name (CC)) = N_Attribute_Reference then
8735 null;
8736 else
8737 exit when Chars (Comp) = Chars (Component_Name (CC));
8738 end if;
8740 Next_Component_Or_Discriminant (Comp);
8741 end loop;
8742 end Search_Component;
8744 -- Start of processing for Find_Component
8746 begin
8747 -- Return with Comp set to Empty if we have a pragma
8749 if Nkind (CC) = N_Pragma then
8750 Comp := Empty;
8751 return;
8752 end if;
8754 -- Search current record for matching component
8756 Search_Component (Rectype);
8758 -- If not found, maybe component of base type discriminant that is
8759 -- absent from statically constrained first subtype.
8761 if No (Comp) then
8762 Search_Component (Base_Type (Rectype));
8763 end if;
8765 -- If no component, or the component does not reference the component
8766 -- clause in question, then there was some previous error for which
8767 -- we already gave a message, so just return with Comp Empty.
8769 if No (Comp) or else Component_Clause (Comp) /= CC then
8770 Check_Error_Detected;
8771 Comp := Empty;
8773 -- Normal case where we have a component clause
8775 else
8776 Fbit := Component_Bit_Offset (Comp);
8777 Lbit := Fbit + Esize (Comp) - 1;
8778 end if;
8779 end Find_Component;
8781 -- Start of processing for Check_Record_Representation_Clause
8783 begin
8784 Find_Type (Ident);
8785 Rectype := Entity (Ident);
8787 if Rectype = Any_Type then
8788 return;
8789 else
8790 Rectype := Underlying_Type (Rectype);
8791 end if;
8793 -- See if we have a fully repped derived tagged type
8795 declare
8796 PS : constant Entity_Id := Parent_Subtype (Rectype);
8798 begin
8799 if Present (PS) and then Is_Fully_Repped_Tagged_Type (PS) then
8800 Tagged_Parent := PS;
8802 -- Find maximum bit of any component of the parent type
8804 Parent_Last_Bit := UI_From_Int (System_Address_Size - 1);
8805 Pcomp := First_Entity (Tagged_Parent);
8806 while Present (Pcomp) loop
8807 if Ekind_In (Pcomp, E_Discriminant, E_Component) then
8808 if Component_Bit_Offset (Pcomp) /= No_Uint
8809 and then Known_Static_Esize (Pcomp)
8810 then
8811 Parent_Last_Bit :=
8812 UI_Max
8813 (Parent_Last_Bit,
8814 Component_Bit_Offset (Pcomp) + Esize (Pcomp) - 1);
8815 end if;
8817 Next_Entity (Pcomp);
8818 end if;
8819 end loop;
8820 end if;
8821 end;
8823 -- All done if no component clauses
8825 CC := First (Component_Clauses (N));
8827 if No (CC) then
8828 return;
8829 end if;
8831 -- If a tag is present, then create a component clause that places it
8832 -- at the start of the record (otherwise gigi may place it after other
8833 -- fields that have rep clauses).
8835 Fent := First_Entity (Rectype);
8837 if Nkind (Fent) = N_Defining_Identifier
8838 and then Chars (Fent) = Name_uTag
8839 then
8840 Set_Component_Bit_Offset (Fent, Uint_0);
8841 Set_Normalized_Position (Fent, Uint_0);
8842 Set_Normalized_First_Bit (Fent, Uint_0);
8843 Set_Normalized_Position_Max (Fent, Uint_0);
8844 Init_Esize (Fent, System_Address_Size);
8846 Set_Component_Clause (Fent,
8847 Make_Component_Clause (Loc,
8848 Component_Name => Make_Identifier (Loc, Name_uTag),
8850 Position => Make_Integer_Literal (Loc, Uint_0),
8851 First_Bit => Make_Integer_Literal (Loc, Uint_0),
8852 Last_Bit =>
8853 Make_Integer_Literal (Loc,
8854 UI_From_Int (System_Address_Size))));
8856 Ccount := Ccount + 1;
8857 end if;
8859 Max_Bit_So_Far := Uint_Minus_1;
8860 Overlap_Check_Required := False;
8862 -- Process the component clauses
8864 while Present (CC) loop
8865 Find_Component;
8867 if Present (Comp) then
8868 Ccount := Ccount + 1;
8870 -- We need a full overlap check if record positions non-monotonic
8872 if Fbit <= Max_Bit_So_Far then
8873 Overlap_Check_Required := True;
8874 end if;
8876 Max_Bit_So_Far := Lbit;
8878 -- Check bit position out of range of specified size
8880 if Has_Size_Clause (Rectype)
8881 and then RM_Size (Rectype) <= Lbit
8882 then
8883 Error_Msg_N
8884 ("bit number out of range of specified size",
8885 Last_Bit (CC));
8887 -- Check for overlap with tag component
8889 else
8890 if Is_Tagged_Type (Rectype)
8891 and then Fbit < System_Address_Size
8892 then
8893 Error_Msg_NE
8894 ("component overlaps tag field of&",
8895 Component_Name (CC), Rectype);
8896 Overlap_Detected := True;
8897 end if;
8899 if Hbit < Lbit then
8900 Hbit := Lbit;
8901 end if;
8902 end if;
8904 -- Check parent overlap if component might overlap parent field
8906 if Present (Tagged_Parent) and then Fbit <= Parent_Last_Bit then
8907 Pcomp := First_Component_Or_Discriminant (Tagged_Parent);
8908 while Present (Pcomp) loop
8909 if not Is_Tag (Pcomp)
8910 and then Chars (Pcomp) /= Name_uParent
8911 then
8912 Check_Component_Overlap (Comp, Pcomp);
8913 end if;
8915 Next_Component_Or_Discriminant (Pcomp);
8916 end loop;
8917 end if;
8918 end if;
8920 Next (CC);
8921 end loop;
8923 -- Now that we have processed all the component clauses, check for
8924 -- overlap. We have to leave this till last, since the components can
8925 -- appear in any arbitrary order in the representation clause.
8927 -- We do not need this check if all specified ranges were monotonic,
8928 -- as recorded by Overlap_Check_Required being False at this stage.
8930 -- This first section checks if there are any overlapping entries at
8931 -- all. It does this by sorting all entries and then seeing if there are
8932 -- any overlaps. If there are none, then that is decisive, but if there
8933 -- are overlaps, they may still be OK (they may result from fields in
8934 -- different variants).
8936 if Overlap_Check_Required then
8937 Overlap_Check1 : declare
8939 OC_Fbit : array (0 .. Ccount) of Uint;
8940 -- First-bit values for component clauses, the value is the offset
8941 -- of the first bit of the field from start of record. The zero
8942 -- entry is for use in sorting.
8944 OC_Lbit : array (0 .. Ccount) of Uint;
8945 -- Last-bit values for component clauses, the value is the offset
8946 -- of the last bit of the field from start of record. The zero
8947 -- entry is for use in sorting.
8949 OC_Count : Natural := 0;
8950 -- Count of entries in OC_Fbit and OC_Lbit
8952 function OC_Lt (Op1, Op2 : Natural) return Boolean;
8953 -- Compare routine for Sort
8955 procedure OC_Move (From : Natural; To : Natural);
8956 -- Move routine for Sort
8958 package Sorting is new GNAT.Heap_Sort_G (OC_Move, OC_Lt);
8960 -----------
8961 -- OC_Lt --
8962 -----------
8964 function OC_Lt (Op1, Op2 : Natural) return Boolean is
8965 begin
8966 return OC_Fbit (Op1) < OC_Fbit (Op2);
8967 end OC_Lt;
8969 -------------
8970 -- OC_Move --
8971 -------------
8973 procedure OC_Move (From : Natural; To : Natural) is
8974 begin
8975 OC_Fbit (To) := OC_Fbit (From);
8976 OC_Lbit (To) := OC_Lbit (From);
8977 end OC_Move;
8979 -- Start of processing for Overlap_Check
8981 begin
8982 CC := First (Component_Clauses (N));
8983 while Present (CC) loop
8985 -- Exclude component clause already marked in error
8987 if not Error_Posted (CC) then
8988 Find_Component;
8990 if Present (Comp) then
8991 OC_Count := OC_Count + 1;
8992 OC_Fbit (OC_Count) := Fbit;
8993 OC_Lbit (OC_Count) := Lbit;
8994 end if;
8995 end if;
8997 Next (CC);
8998 end loop;
9000 Sorting.Sort (OC_Count);
9002 Overlap_Check_Required := False;
9003 for J in 1 .. OC_Count - 1 loop
9004 if OC_Lbit (J) >= OC_Fbit (J + 1) then
9005 Overlap_Check_Required := True;
9006 exit;
9007 end if;
9008 end loop;
9009 end Overlap_Check1;
9010 end if;
9012 -- If Overlap_Check_Required is still True, then we have to do the full
9013 -- scale overlap check, since we have at least two fields that do
9014 -- overlap, and we need to know if that is OK since they are in
9015 -- different variant, or whether we have a definite problem.
9017 if Overlap_Check_Required then
9018 Overlap_Check2 : declare
9019 C1_Ent, C2_Ent : Entity_Id;
9020 -- Entities of components being checked for overlap
9022 Clist : Node_Id;
9023 -- Component_List node whose Component_Items are being checked
9025 Citem : Node_Id;
9026 -- Component declaration for component being checked
9028 begin
9029 C1_Ent := First_Entity (Base_Type (Rectype));
9031 -- Loop through all components in record. For each component check
9032 -- for overlap with any of the preceding elements on the component
9033 -- list containing the component and also, if the component is in
9034 -- a variant, check against components outside the case structure.
9035 -- This latter test is repeated recursively up the variant tree.
9037 Main_Component_Loop : while Present (C1_Ent) loop
9038 if not Ekind_In (C1_Ent, E_Component, E_Discriminant) then
9039 goto Continue_Main_Component_Loop;
9040 end if;
9042 -- Skip overlap check if entity has no declaration node. This
9043 -- happens with discriminants in constrained derived types.
9044 -- Possibly we are missing some checks as a result, but that
9045 -- does not seem terribly serious.
9047 if No (Declaration_Node (C1_Ent)) then
9048 goto Continue_Main_Component_Loop;
9049 end if;
9051 Clist := Parent (List_Containing (Declaration_Node (C1_Ent)));
9053 -- Loop through component lists that need checking. Check the
9054 -- current component list and all lists in variants above us.
9056 Component_List_Loop : loop
9058 -- If derived type definition, go to full declaration
9059 -- If at outer level, check discriminants if there are any.
9061 if Nkind (Clist) = N_Derived_Type_Definition then
9062 Clist := Parent (Clist);
9063 end if;
9065 -- Outer level of record definition, check discriminants
9067 if Nkind_In (Clist, N_Full_Type_Declaration,
9068 N_Private_Type_Declaration)
9069 then
9070 if Has_Discriminants (Defining_Identifier (Clist)) then
9071 C2_Ent :=
9072 First_Discriminant (Defining_Identifier (Clist));
9073 while Present (C2_Ent) loop
9074 exit when C1_Ent = C2_Ent;
9075 Check_Component_Overlap (C1_Ent, C2_Ent);
9076 Next_Discriminant (C2_Ent);
9077 end loop;
9078 end if;
9080 -- Record extension case
9082 elsif Nkind (Clist) = N_Derived_Type_Definition then
9083 Clist := Empty;
9085 -- Otherwise check one component list
9087 else
9088 Citem := First (Component_Items (Clist));
9089 while Present (Citem) loop
9090 if Nkind (Citem) = N_Component_Declaration then
9091 C2_Ent := Defining_Identifier (Citem);
9092 exit when C1_Ent = C2_Ent;
9093 Check_Component_Overlap (C1_Ent, C2_Ent);
9094 end if;
9096 Next (Citem);
9097 end loop;
9098 end if;
9100 -- Check for variants above us (the parent of the Clist can
9101 -- be a variant, in which case its parent is a variant part,
9102 -- and the parent of the variant part is a component list
9103 -- whose components must all be checked against the current
9104 -- component for overlap).
9106 if Nkind (Parent (Clist)) = N_Variant then
9107 Clist := Parent (Parent (Parent (Clist)));
9109 -- Check for possible discriminant part in record, this
9110 -- is treated essentially as another level in the
9111 -- recursion. For this case the parent of the component
9112 -- list is the record definition, and its parent is the
9113 -- full type declaration containing the discriminant
9114 -- specifications.
9116 elsif Nkind (Parent (Clist)) = N_Record_Definition then
9117 Clist := Parent (Parent ((Clist)));
9119 -- If neither of these two cases, we are at the top of
9120 -- the tree.
9122 else
9123 exit Component_List_Loop;
9124 end if;
9125 end loop Component_List_Loop;
9127 <<Continue_Main_Component_Loop>>
9128 Next_Entity (C1_Ent);
9130 end loop Main_Component_Loop;
9131 end Overlap_Check2;
9132 end if;
9134 -- The following circuit deals with warning on record holes (gaps). We
9135 -- skip this check if overlap was detected, since it makes sense for the
9136 -- programmer to fix this illegality before worrying about warnings.
9138 if not Overlap_Detected and Warn_On_Record_Holes then
9139 Record_Hole_Check : declare
9140 Decl : constant Node_Id := Declaration_Node (Base_Type (Rectype));
9141 -- Full declaration of record type
9143 procedure Check_Component_List
9144 (CL : Node_Id;
9145 Sbit : Uint;
9146 DS : List_Id);
9147 -- Check component list CL for holes. The starting bit should be
9148 -- Sbit. which is zero for the main record component list and set
9149 -- appropriately for recursive calls for variants. DS is set to
9150 -- a list of discriminant specifications to be included in the
9151 -- consideration of components. It is No_List if none to consider.
9153 --------------------------
9154 -- Check_Component_List --
9155 --------------------------
9157 procedure Check_Component_List
9158 (CL : Node_Id;
9159 Sbit : Uint;
9160 DS : List_Id)
9162 Compl : Integer;
9164 begin
9165 Compl := Integer (List_Length (Component_Items (CL)));
9167 if DS /= No_List then
9168 Compl := Compl + Integer (List_Length (DS));
9169 end if;
9171 declare
9172 Comps : array (Natural range 0 .. Compl) of Entity_Id;
9173 -- Gather components (zero entry is for sort routine)
9175 Ncomps : Natural := 0;
9176 -- Number of entries stored in Comps (starting at Comps (1))
9178 Citem : Node_Id;
9179 -- One component item or discriminant specification
9181 Nbit : Uint;
9182 -- Starting bit for next component
9184 CEnt : Entity_Id;
9185 -- Component entity
9187 Variant : Node_Id;
9188 -- One variant
9190 function Lt (Op1, Op2 : Natural) return Boolean;
9191 -- Compare routine for Sort
9193 procedure Move (From : Natural; To : Natural);
9194 -- Move routine for Sort
9196 package Sorting is new GNAT.Heap_Sort_G (Move, Lt);
9198 --------
9199 -- Lt --
9200 --------
9202 function Lt (Op1, Op2 : Natural) return Boolean is
9203 begin
9204 return Component_Bit_Offset (Comps (Op1))
9206 Component_Bit_Offset (Comps (Op2));
9207 end Lt;
9209 ----------
9210 -- Move --
9211 ----------
9213 procedure Move (From : Natural; To : Natural) is
9214 begin
9215 Comps (To) := Comps (From);
9216 end Move;
9218 begin
9219 -- Gather discriminants into Comp
9221 if DS /= No_List then
9222 Citem := First (DS);
9223 while Present (Citem) loop
9224 if Nkind (Citem) = N_Discriminant_Specification then
9225 declare
9226 Ent : constant Entity_Id :=
9227 Defining_Identifier (Citem);
9228 begin
9229 if Ekind (Ent) = E_Discriminant then
9230 Ncomps := Ncomps + 1;
9231 Comps (Ncomps) := Ent;
9232 end if;
9233 end;
9234 end if;
9236 Next (Citem);
9237 end loop;
9238 end if;
9240 -- Gather component entities into Comp
9242 Citem := First (Component_Items (CL));
9243 while Present (Citem) loop
9244 if Nkind (Citem) = N_Component_Declaration then
9245 Ncomps := Ncomps + 1;
9246 Comps (Ncomps) := Defining_Identifier (Citem);
9247 end if;
9249 Next (Citem);
9250 end loop;
9252 -- Now sort the component entities based on the first bit.
9253 -- Note we already know there are no overlapping components.
9255 Sorting.Sort (Ncomps);
9257 -- Loop through entries checking for holes
9259 Nbit := Sbit;
9260 for J in 1 .. Ncomps loop
9261 CEnt := Comps (J);
9262 Error_Msg_Uint_1 := Component_Bit_Offset (CEnt) - Nbit;
9264 if Error_Msg_Uint_1 > 0 then
9265 Error_Msg_NE
9266 ("?H?^-bit gap before component&",
9267 Component_Name (Component_Clause (CEnt)), CEnt);
9268 end if;
9270 Nbit := Component_Bit_Offset (CEnt) + Esize (CEnt);
9271 end loop;
9273 -- Process variant parts recursively if present
9275 if Present (Variant_Part (CL)) then
9276 Variant := First (Variants (Variant_Part (CL)));
9277 while Present (Variant) loop
9278 Check_Component_List
9279 (Component_List (Variant), Nbit, No_List);
9280 Next (Variant);
9281 end loop;
9282 end if;
9283 end;
9284 end Check_Component_List;
9286 -- Start of processing for Record_Hole_Check
9288 begin
9289 declare
9290 Sbit : Uint;
9292 begin
9293 if Is_Tagged_Type (Rectype) then
9294 Sbit := UI_From_Int (System_Address_Size);
9295 else
9296 Sbit := Uint_0;
9297 end if;
9299 if Nkind (Decl) = N_Full_Type_Declaration
9300 and then Nkind (Type_Definition (Decl)) = N_Record_Definition
9301 then
9302 Check_Component_List
9303 (Component_List (Type_Definition (Decl)),
9304 Sbit,
9305 Discriminant_Specifications (Decl));
9306 end if;
9307 end;
9308 end Record_Hole_Check;
9309 end if;
9311 -- For records that have component clauses for all components, and whose
9312 -- size is less than or equal to 32, we need to know the size in the
9313 -- front end to activate possible packed array processing where the
9314 -- component type is a record.
9316 -- At this stage Hbit + 1 represents the first unused bit from all the
9317 -- component clauses processed, so if the component clauses are
9318 -- complete, then this is the length of the record.
9320 -- For records longer than System.Storage_Unit, and for those where not
9321 -- all components have component clauses, the back end determines the
9322 -- length (it may for example be appropriate to round up the size
9323 -- to some convenient boundary, based on alignment considerations, etc).
9325 if Unknown_RM_Size (Rectype) and then Hbit + 1 <= 32 then
9327 -- Nothing to do if at least one component has no component clause
9329 Comp := First_Component_Or_Discriminant (Rectype);
9330 while Present (Comp) loop
9331 exit when No (Component_Clause (Comp));
9332 Next_Component_Or_Discriminant (Comp);
9333 end loop;
9335 -- If we fall out of loop, all components have component clauses
9336 -- and so we can set the size to the maximum value.
9338 if No (Comp) then
9339 Set_RM_Size (Rectype, Hbit + 1);
9340 end if;
9341 end if;
9342 end Check_Record_Representation_Clause;
9344 ----------------
9345 -- Check_Size --
9346 ----------------
9348 procedure Check_Size
9349 (N : Node_Id;
9350 T : Entity_Id;
9351 Siz : Uint;
9352 Biased : out Boolean)
9354 UT : constant Entity_Id := Underlying_Type (T);
9355 M : Uint;
9357 begin
9358 Biased := False;
9360 -- Reject patently improper size values.
9362 if Is_Elementary_Type (T)
9363 and then Siz > UI_From_Int (Int'Last)
9364 then
9365 Error_Msg_N ("Size value too large for elementary type", N);
9367 if Nkind (Original_Node (N)) = N_Op_Expon then
9368 Error_Msg_N
9369 ("\maybe '* was meant, rather than '*'*", Original_Node (N));
9370 end if;
9371 end if;
9373 -- Dismiss generic types
9375 if Is_Generic_Type (T)
9376 or else
9377 Is_Generic_Type (UT)
9378 or else
9379 Is_Generic_Type (Root_Type (UT))
9380 then
9381 return;
9383 -- Guard against previous errors
9385 elsif No (UT) or else UT = Any_Type then
9386 Check_Error_Detected;
9387 return;
9389 -- Check case of bit packed array
9391 elsif Is_Array_Type (UT)
9392 and then Known_Static_Component_Size (UT)
9393 and then Is_Bit_Packed_Array (UT)
9394 then
9395 declare
9396 Asiz : Uint;
9397 Indx : Node_Id;
9398 Ityp : Entity_Id;
9400 begin
9401 Asiz := Component_Size (UT);
9402 Indx := First_Index (UT);
9403 loop
9404 Ityp := Etype (Indx);
9406 -- If non-static bound, then we are not in the business of
9407 -- trying to check the length, and indeed an error will be
9408 -- issued elsewhere, since sizes of non-static array types
9409 -- cannot be set implicitly or explicitly.
9411 if not Is_Static_Subtype (Ityp) then
9412 return;
9413 end if;
9415 -- Otherwise accumulate next dimension
9417 Asiz := Asiz * (Expr_Value (Type_High_Bound (Ityp)) -
9418 Expr_Value (Type_Low_Bound (Ityp)) +
9419 Uint_1);
9421 Next_Index (Indx);
9422 exit when No (Indx);
9423 end loop;
9425 if Asiz <= Siz then
9426 return;
9428 else
9429 Error_Msg_Uint_1 := Asiz;
9430 Error_Msg_NE
9431 ("size for& too small, minimum allowed is ^", N, T);
9432 Set_Esize (T, Asiz);
9433 Set_RM_Size (T, Asiz);
9434 end if;
9435 end;
9437 -- All other composite types are ignored
9439 elsif Is_Composite_Type (UT) then
9440 return;
9442 -- For fixed-point types, don't check minimum if type is not frozen,
9443 -- since we don't know all the characteristics of the type that can
9444 -- affect the size (e.g. a specified small) till freeze time.
9446 elsif Is_Fixed_Point_Type (UT)
9447 and then not Is_Frozen (UT)
9448 then
9449 null;
9451 -- Cases for which a minimum check is required
9453 else
9454 -- Ignore if specified size is correct for the type
9456 if Known_Esize (UT) and then Siz = Esize (UT) then
9457 return;
9458 end if;
9460 -- Otherwise get minimum size
9462 M := UI_From_Int (Minimum_Size (UT));
9464 if Siz < M then
9466 -- Size is less than minimum size, but one possibility remains
9467 -- that we can manage with the new size if we bias the type.
9469 M := UI_From_Int (Minimum_Size (UT, Biased => True));
9471 if Siz < M then
9472 Error_Msg_Uint_1 := M;
9473 Error_Msg_NE
9474 ("size for& too small, minimum allowed is ^", N, T);
9475 Set_Esize (T, M);
9476 Set_RM_Size (T, M);
9477 else
9478 Biased := True;
9479 end if;
9480 end if;
9481 end if;
9482 end Check_Size;
9484 --------------------------
9485 -- Freeze_Entity_Checks --
9486 --------------------------
9488 procedure Freeze_Entity_Checks (N : Node_Id) is
9489 E : constant Entity_Id := Entity (N);
9491 Non_Generic_Case : constant Boolean := Nkind (N) = N_Freeze_Entity;
9492 -- True in non-generic case. Some of the processing here is skipped
9493 -- for the generic case since it is not needed. Basically in the
9494 -- generic case, we only need to do stuff that might generate error
9495 -- messages or warnings.
9496 begin
9497 -- Remember that we are processing a freezing entity. Required to
9498 -- ensure correct decoration of internal entities associated with
9499 -- interfaces (see New_Overloaded_Entity).
9501 Inside_Freezing_Actions := Inside_Freezing_Actions + 1;
9503 -- For tagged types covering interfaces add internal entities that link
9504 -- the primitives of the interfaces with the primitives that cover them.
9505 -- Note: These entities were originally generated only when generating
9506 -- code because their main purpose was to provide support to initialize
9507 -- the secondary dispatch tables. They are now generated also when
9508 -- compiling with no code generation to provide ASIS the relationship
9509 -- between interface primitives and tagged type primitives. They are
9510 -- also used to locate primitives covering interfaces when processing
9511 -- generics (see Derive_Subprograms).
9513 -- This is not needed in the generic case
9515 if Ada_Version >= Ada_2005
9516 and then Non_Generic_Case
9517 and then Ekind (E) = E_Record_Type
9518 and then Is_Tagged_Type (E)
9519 and then not Is_Interface (E)
9520 and then Has_Interfaces (E)
9521 then
9522 -- This would be a good common place to call the routine that checks
9523 -- overriding of interface primitives (and thus factorize calls to
9524 -- Check_Abstract_Overriding located at different contexts in the
9525 -- compiler). However, this is not possible because it causes
9526 -- spurious errors in case of late overriding.
9528 Add_Internal_Interface_Entities (E);
9529 end if;
9531 -- Check CPP types
9533 if Ekind (E) = E_Record_Type
9534 and then Is_CPP_Class (E)
9535 and then Is_Tagged_Type (E)
9536 and then Tagged_Type_Expansion
9537 then
9538 if CPP_Num_Prims (E) = 0 then
9540 -- If the CPP type has user defined components then it must import
9541 -- primitives from C++. This is required because if the C++ class
9542 -- has no primitives then the C++ compiler does not added the _tag
9543 -- component to the type.
9545 if First_Entity (E) /= Last_Entity (E) then
9546 Error_Msg_N
9547 ("'C'P'P type must import at least one primitive from C++??",
9549 end if;
9550 end if;
9552 -- Check that all its primitives are abstract or imported from C++.
9553 -- Check also availability of the C++ constructor.
9555 declare
9556 Has_Constructors : constant Boolean := Has_CPP_Constructors (E);
9557 Elmt : Elmt_Id;
9558 Error_Reported : Boolean := False;
9559 Prim : Node_Id;
9561 begin
9562 Elmt := First_Elmt (Primitive_Operations (E));
9563 while Present (Elmt) loop
9564 Prim := Node (Elmt);
9566 if Comes_From_Source (Prim) then
9567 if Is_Abstract_Subprogram (Prim) then
9568 null;
9570 elsif not Is_Imported (Prim)
9571 or else Convention (Prim) /= Convention_CPP
9572 then
9573 Error_Msg_N
9574 ("primitives of 'C'P'P types must be imported from C++ "
9575 & "or abstract??", Prim);
9577 elsif not Has_Constructors
9578 and then not Error_Reported
9579 then
9580 Error_Msg_Name_1 := Chars (E);
9581 Error_Msg_N
9582 ("??'C'P'P constructor required for type %", Prim);
9583 Error_Reported := True;
9584 end if;
9585 end if;
9587 Next_Elmt (Elmt);
9588 end loop;
9589 end;
9590 end if;
9592 -- Check Ada derivation of CPP type
9594 if Expander_Active -- why? losing errors in -gnatc mode???
9595 and then Tagged_Type_Expansion
9596 and then Ekind (E) = E_Record_Type
9597 and then Etype (E) /= E
9598 and then Is_CPP_Class (Etype (E))
9599 and then CPP_Num_Prims (Etype (E)) > 0
9600 and then not Is_CPP_Class (E)
9601 and then not Has_CPP_Constructors (Etype (E))
9602 then
9603 -- If the parent has C++ primitives but it has no constructor then
9604 -- check that all the primitives are overridden in this derivation;
9605 -- otherwise the constructor of the parent is needed to build the
9606 -- dispatch table.
9608 declare
9609 Elmt : Elmt_Id;
9610 Prim : Node_Id;
9612 begin
9613 Elmt := First_Elmt (Primitive_Operations (E));
9614 while Present (Elmt) loop
9615 Prim := Node (Elmt);
9617 if not Is_Abstract_Subprogram (Prim)
9618 and then No (Interface_Alias (Prim))
9619 and then Find_Dispatching_Type (Ultimate_Alias (Prim)) /= E
9620 then
9621 Error_Msg_Name_1 := Chars (Etype (E));
9622 Error_Msg_N
9623 ("'C'P'P constructor required for parent type %", E);
9624 exit;
9625 end if;
9627 Next_Elmt (Elmt);
9628 end loop;
9629 end;
9630 end if;
9632 Inside_Freezing_Actions := Inside_Freezing_Actions - 1;
9634 -- If we have a type with predicates, build predicate function. This
9635 -- is not needed in the generic case, and is not needed within TSS
9636 -- subprograms and other predefined primitives.
9638 if Non_Generic_Case
9639 and then Is_Type (E)
9640 and then Has_Predicates (E)
9641 and then not Within_Internal_Subprogram
9642 then
9643 Build_Predicate_Functions (E, N);
9644 end if;
9646 -- If type has delayed aspects, this is where we do the preanalysis at
9647 -- the freeze point, as part of the consistent visibility check. Note
9648 -- that this must be done after calling Build_Predicate_Functions or
9649 -- Build_Invariant_Procedure since these subprograms fix occurrences of
9650 -- the subtype name in the saved expression so that they will not cause
9651 -- trouble in the preanalysis.
9653 -- This is also not needed in the generic case
9655 if Non_Generic_Case
9656 and then Has_Delayed_Aspects (E)
9657 and then Scope (E) = Current_Scope
9658 then
9659 -- Retrieve the visibility to the discriminants in order to properly
9660 -- analyze the aspects.
9662 Push_Scope_And_Install_Discriminants (E);
9664 declare
9665 Ritem : Node_Id;
9667 begin
9668 -- Look for aspect specification entries for this entity
9670 Ritem := First_Rep_Item (E);
9671 while Present (Ritem) loop
9672 if Nkind (Ritem) = N_Aspect_Specification
9673 and then Entity (Ritem) = E
9674 and then Is_Delayed_Aspect (Ritem)
9675 then
9676 Check_Aspect_At_Freeze_Point (Ritem);
9677 end if;
9679 Next_Rep_Item (Ritem);
9680 end loop;
9681 end;
9683 Uninstall_Discriminants_And_Pop_Scope (E);
9684 end if;
9686 -- For a record type, deal with variant parts. This has to be delayed
9687 -- to this point, because of the issue of statically precicated
9688 -- subtypes, which we have to ensure are frozen before checking
9689 -- choices, since we need to have the static choice list set.
9691 if Is_Record_Type (E) then
9692 Check_Variant_Part : declare
9693 D : constant Node_Id := Declaration_Node (E);
9694 T : Node_Id;
9695 C : Node_Id;
9696 VP : Node_Id;
9698 Others_Present : Boolean;
9699 pragma Warnings (Off, Others_Present);
9700 -- Indicates others present, not used in this case
9702 procedure Non_Static_Choice_Error (Choice : Node_Id);
9703 -- Error routine invoked by the generic instantiation below when
9704 -- the variant part has a non static choice.
9706 procedure Process_Declarations (Variant : Node_Id);
9707 -- Processes declarations associated with a variant. We analyzed
9708 -- the declarations earlier (in Sem_Ch3.Analyze_Variant_Part),
9709 -- but we still need the recursive call to Check_Choices for any
9710 -- nested variant to get its choices properly processed. This is
9711 -- also where we expand out the choices if expansion is active.
9713 package Variant_Choices_Processing is new
9714 Generic_Check_Choices
9715 (Process_Empty_Choice => No_OP,
9716 Process_Non_Static_Choice => Non_Static_Choice_Error,
9717 Process_Associated_Node => Process_Declarations);
9718 use Variant_Choices_Processing;
9720 -----------------------------
9721 -- Non_Static_Choice_Error --
9722 -----------------------------
9724 procedure Non_Static_Choice_Error (Choice : Node_Id) is
9725 begin
9726 Flag_Non_Static_Expr
9727 ("choice given in variant part is not static!", Choice);
9728 end Non_Static_Choice_Error;
9730 --------------------------
9731 -- Process_Declarations --
9732 --------------------------
9734 procedure Process_Declarations (Variant : Node_Id) is
9735 CL : constant Node_Id := Component_List (Variant);
9736 VP : Node_Id;
9738 begin
9739 -- Check for static predicate present in this variant
9741 if Has_SP_Choice (Variant) then
9743 -- Here we expand. You might expect to find this call in
9744 -- Expand_N_Variant_Part, but that is called when we first
9745 -- see the variant part, and we cannot do this expansion
9746 -- earlier than the freeze point, since for statically
9747 -- predicated subtypes, the predicate is not known till
9748 -- the freeze point.
9750 -- Furthermore, we do this expansion even if the expander
9751 -- is not active, because other semantic processing, e.g.
9752 -- for aggregates, requires the expanded list of choices.
9754 -- If the expander is not active, then we can't just clobber
9755 -- the list since it would invalidate the ASIS -gnatct tree.
9756 -- So we have to rewrite the variant part with a Rewrite
9757 -- call that replaces it with a copy and clobber the copy.
9759 if not Expander_Active then
9760 declare
9761 NewV : constant Node_Id := New_Copy (Variant);
9762 begin
9763 Set_Discrete_Choices
9764 (NewV, New_Copy_List (Discrete_Choices (Variant)));
9765 Rewrite (Variant, NewV);
9766 end;
9767 end if;
9769 Expand_Static_Predicates_In_Choices (Variant);
9770 end if;
9772 -- We don't need to worry about the declarations in the variant
9773 -- (since they were analyzed by Analyze_Choices when we first
9774 -- encountered the variant), but we do need to take care of
9775 -- expansion of any nested variants.
9777 if not Null_Present (CL) then
9778 VP := Variant_Part (CL);
9780 if Present (VP) then
9781 Check_Choices
9782 (VP, Variants (VP), Etype (Name (VP)), Others_Present);
9783 end if;
9784 end if;
9785 end Process_Declarations;
9787 -- Start of processing for Check_Variant_Part
9789 begin
9790 -- Find component list
9792 C := Empty;
9794 if Nkind (D) = N_Full_Type_Declaration then
9795 T := Type_Definition (D);
9797 if Nkind (T) = N_Record_Definition then
9798 C := Component_List (T);
9800 elsif Nkind (T) = N_Derived_Type_Definition
9801 and then Present (Record_Extension_Part (T))
9802 then
9803 C := Component_List (Record_Extension_Part (T));
9804 end if;
9805 end if;
9807 -- Case of variant part present
9809 if Present (C) and then Present (Variant_Part (C)) then
9810 VP := Variant_Part (C);
9812 -- Check choices
9814 Check_Choices
9815 (VP, Variants (VP), Etype (Name (VP)), Others_Present);
9817 -- If the last variant does not contain the Others choice,
9818 -- replace it with an N_Others_Choice node since Gigi always
9819 -- wants an Others. Note that we do not bother to call Analyze
9820 -- on the modified variant part, since its only effect would be
9821 -- to compute the Others_Discrete_Choices node laboriously, and
9822 -- of course we already know the list of choices corresponding
9823 -- to the others choice (it's the list we're replacing).
9825 -- We only want to do this if the expander is active, since
9826 -- we do not want to clobber the ASIS tree.
9828 if Expander_Active then
9829 declare
9830 Last_Var : constant Node_Id :=
9831 Last_Non_Pragma (Variants (VP));
9833 Others_Node : Node_Id;
9835 begin
9836 if Nkind (First (Discrete_Choices (Last_Var))) /=
9837 N_Others_Choice
9838 then
9839 Others_Node := Make_Others_Choice (Sloc (Last_Var));
9840 Set_Others_Discrete_Choices
9841 (Others_Node, Discrete_Choices (Last_Var));
9842 Set_Discrete_Choices
9843 (Last_Var, New_List (Others_Node));
9844 end if;
9845 end;
9846 end if;
9847 end if;
9848 end Check_Variant_Part;
9849 end if;
9850 end Freeze_Entity_Checks;
9852 -------------------------
9853 -- Get_Alignment_Value --
9854 -------------------------
9856 function Get_Alignment_Value (Expr : Node_Id) return Uint is
9857 Align : constant Uint := Static_Integer (Expr);
9859 begin
9860 if Align = No_Uint then
9861 return No_Uint;
9863 elsif Align <= 0 then
9864 Error_Msg_N ("alignment value must be positive", Expr);
9865 return No_Uint;
9867 else
9868 for J in Int range 0 .. 64 loop
9869 declare
9870 M : constant Uint := Uint_2 ** J;
9872 begin
9873 exit when M = Align;
9875 if M > Align then
9876 Error_Msg_N
9877 ("alignment value must be power of 2", Expr);
9878 return No_Uint;
9879 end if;
9880 end;
9881 end loop;
9883 return Align;
9884 end if;
9885 end Get_Alignment_Value;
9887 -------------------------------------
9888 -- Inherit_Aspects_At_Freeze_Point --
9889 -------------------------------------
9891 procedure Inherit_Aspects_At_Freeze_Point (Typ : Entity_Id) is
9892 function Is_Pragma_Or_Corr_Pragma_Present_In_Rep_Item
9893 (Rep_Item : Node_Id) return Boolean;
9894 -- This routine checks if Rep_Item is either a pragma or an aspect
9895 -- specification node whose correponding pragma (if any) is present in
9896 -- the Rep Item chain of the entity it has been specified to.
9898 --------------------------------------------------
9899 -- Is_Pragma_Or_Corr_Pragma_Present_In_Rep_Item --
9900 --------------------------------------------------
9902 function Is_Pragma_Or_Corr_Pragma_Present_In_Rep_Item
9903 (Rep_Item : Node_Id) return Boolean
9905 begin
9906 return Nkind (Rep_Item) = N_Pragma
9907 or else Present_In_Rep_Item
9908 (Entity (Rep_Item), Aspect_Rep_Item (Rep_Item));
9909 end Is_Pragma_Or_Corr_Pragma_Present_In_Rep_Item;
9911 -- Start of processing for Inherit_Aspects_At_Freeze_Point
9913 begin
9914 -- A representation item is either subtype-specific (Size and Alignment
9915 -- clauses) or type-related (all others). Subtype-specific aspects may
9916 -- differ for different subtypes of the same type (RM 13.1.8).
9918 -- A derived type inherits each type-related representation aspect of
9919 -- its parent type that was directly specified before the declaration of
9920 -- the derived type (RM 13.1.15).
9922 -- A derived subtype inherits each subtype-specific representation
9923 -- aspect of its parent subtype that was directly specified before the
9924 -- declaration of the derived type (RM 13.1.15).
9926 -- The general processing involves inheriting a representation aspect
9927 -- from a parent type whenever the first rep item (aspect specification,
9928 -- attribute definition clause, pragma) corresponding to the given
9929 -- representation aspect in the rep item chain of Typ, if any, isn't
9930 -- directly specified to Typ but to one of its parents.
9932 -- ??? Note that, for now, just a limited number of representation
9933 -- aspects have been inherited here so far. Many of them are
9934 -- still inherited in Sem_Ch3. This will be fixed soon. Here is
9935 -- a non- exhaustive list of aspects that likely also need to
9936 -- be moved to this routine: Alignment, Component_Alignment,
9937 -- Component_Size, Machine_Radix, Object_Size, Pack, Predicates,
9938 -- Preelaborable_Initialization, RM_Size and Small.
9940 if Nkind (Parent (Typ)) = N_Private_Extension_Declaration then
9941 return;
9942 end if;
9944 -- Ada_05/Ada_2005
9946 if not Has_Rep_Item (Typ, Name_Ada_05, Name_Ada_2005, False)
9947 and then Has_Rep_Item (Typ, Name_Ada_05, Name_Ada_2005)
9948 and then Is_Pragma_Or_Corr_Pragma_Present_In_Rep_Item
9949 (Get_Rep_Item (Typ, Name_Ada_05, Name_Ada_2005))
9950 then
9951 Set_Is_Ada_2005_Only (Typ);
9952 end if;
9954 -- Ada_12/Ada_2012
9956 if not Has_Rep_Item (Typ, Name_Ada_12, Name_Ada_2012, False)
9957 and then Has_Rep_Item (Typ, Name_Ada_12, Name_Ada_2012)
9958 and then Is_Pragma_Or_Corr_Pragma_Present_In_Rep_Item
9959 (Get_Rep_Item (Typ, Name_Ada_12, Name_Ada_2012))
9960 then
9961 Set_Is_Ada_2012_Only (Typ);
9962 end if;
9964 -- Atomic/Shared
9966 if not Has_Rep_Item (Typ, Name_Atomic, Name_Shared, False)
9967 and then Has_Rep_Pragma (Typ, Name_Atomic, Name_Shared)
9968 and then Is_Pragma_Or_Corr_Pragma_Present_In_Rep_Item
9969 (Get_Rep_Item (Typ, Name_Atomic, Name_Shared))
9970 then
9971 Set_Is_Atomic (Typ);
9972 Set_Treat_As_Volatile (Typ);
9973 Set_Is_Volatile (Typ);
9974 end if;
9976 -- Default_Component_Value
9978 if Is_Array_Type (Typ)
9979 and then Is_Base_Type (Typ)
9980 and then Has_Rep_Item (Typ, Name_Default_Component_Value, False)
9981 and then Has_Rep_Item (Typ, Name_Default_Component_Value)
9982 then
9983 Set_Default_Aspect_Component_Value (Typ,
9984 Default_Aspect_Component_Value
9985 (Entity (Get_Rep_Item (Typ, Name_Default_Component_Value))));
9986 end if;
9988 -- Default_Value
9990 if Is_Scalar_Type (Typ)
9991 and then Is_Base_Type (Typ)
9992 and then Has_Rep_Item (Typ, Name_Default_Value, False)
9993 and then Has_Rep_Item (Typ, Name_Default_Value)
9994 then
9995 Set_Default_Aspect_Value (Typ,
9996 Default_Aspect_Value
9997 (Entity (Get_Rep_Item (Typ, Name_Default_Value))));
9998 end if;
10000 -- Discard_Names
10002 if not Has_Rep_Item (Typ, Name_Discard_Names, False)
10003 and then Has_Rep_Item (Typ, Name_Discard_Names)
10004 and then Is_Pragma_Or_Corr_Pragma_Present_In_Rep_Item
10005 (Get_Rep_Item (Typ, Name_Discard_Names))
10006 then
10007 Set_Discard_Names (Typ);
10008 end if;
10010 -- Invariants
10012 if not Has_Rep_Item (Typ, Name_Invariant, False)
10013 and then Has_Rep_Item (Typ, Name_Invariant)
10014 and then Is_Pragma_Or_Corr_Pragma_Present_In_Rep_Item
10015 (Get_Rep_Item (Typ, Name_Invariant))
10016 then
10017 Set_Has_Invariants (Typ);
10019 if Class_Present (Get_Rep_Item (Typ, Name_Invariant)) then
10020 Set_Has_Inheritable_Invariants (Typ);
10021 end if;
10022 end if;
10024 -- Volatile
10026 if not Has_Rep_Item (Typ, Name_Volatile, False)
10027 and then Has_Rep_Item (Typ, Name_Volatile)
10028 and then Is_Pragma_Or_Corr_Pragma_Present_In_Rep_Item
10029 (Get_Rep_Item (Typ, Name_Volatile))
10030 then
10031 Set_Treat_As_Volatile (Typ);
10032 Set_Is_Volatile (Typ);
10033 end if;
10035 -- Inheritance for derived types only
10037 if Is_Derived_Type (Typ) then
10038 declare
10039 Bas_Typ : constant Entity_Id := Base_Type (Typ);
10040 Imp_Bas_Typ : constant Entity_Id := Implementation_Base_Type (Typ);
10042 begin
10043 -- Atomic_Components
10045 if not Has_Rep_Item (Typ, Name_Atomic_Components, False)
10046 and then Has_Rep_Item (Typ, Name_Atomic_Components)
10047 and then Is_Pragma_Or_Corr_Pragma_Present_In_Rep_Item
10048 (Get_Rep_Item (Typ, Name_Atomic_Components))
10049 then
10050 Set_Has_Atomic_Components (Imp_Bas_Typ);
10051 end if;
10053 -- Volatile_Components
10055 if not Has_Rep_Item (Typ, Name_Volatile_Components, False)
10056 and then Has_Rep_Item (Typ, Name_Volatile_Components)
10057 and then Is_Pragma_Or_Corr_Pragma_Present_In_Rep_Item
10058 (Get_Rep_Item (Typ, Name_Volatile_Components))
10059 then
10060 Set_Has_Volatile_Components (Imp_Bas_Typ);
10061 end if;
10063 -- Finalize_Storage_Only.
10065 if not Has_Rep_Pragma (Typ, Name_Finalize_Storage_Only, False)
10066 and then Has_Rep_Pragma (Typ, Name_Finalize_Storage_Only)
10067 then
10068 Set_Finalize_Storage_Only (Bas_Typ);
10069 end if;
10071 -- Universal_Aliasing
10073 if not Has_Rep_Item (Typ, Name_Universal_Aliasing, False)
10074 and then Has_Rep_Item (Typ, Name_Universal_Aliasing)
10075 and then Is_Pragma_Or_Corr_Pragma_Present_In_Rep_Item
10076 (Get_Rep_Item (Typ, Name_Universal_Aliasing))
10077 then
10078 Set_Universal_Aliasing (Imp_Bas_Typ);
10079 end if;
10081 -- Record type specific aspects
10083 if Is_Record_Type (Typ) then
10085 -- Bit_Order
10087 if not Has_Rep_Item (Typ, Name_Bit_Order, False)
10088 and then Has_Rep_Item (Typ, Name_Bit_Order)
10089 then
10090 Set_Reverse_Bit_Order (Bas_Typ,
10091 Reverse_Bit_Order (Entity (Name
10092 (Get_Rep_Item (Typ, Name_Bit_Order)))));
10093 end if;
10095 -- Scalar_Storage_Order
10097 if not Has_Rep_Item (Typ, Name_Scalar_Storage_Order, False)
10098 and then Has_Rep_Item (Typ, Name_Scalar_Storage_Order)
10099 then
10100 Set_Reverse_Storage_Order (Bas_Typ,
10101 Reverse_Storage_Order (Entity (Name
10102 (Get_Rep_Item (Typ, Name_Scalar_Storage_Order)))));
10103 end if;
10104 end if;
10105 end;
10106 end if;
10107 end Inherit_Aspects_At_Freeze_Point;
10109 ----------------
10110 -- Initialize --
10111 ----------------
10113 procedure Initialize is
10114 begin
10115 Address_Clause_Checks.Init;
10116 Independence_Checks.Init;
10117 Unchecked_Conversions.Init;
10118 end Initialize;
10120 ---------------------------
10121 -- Install_Discriminants --
10122 ---------------------------
10124 procedure Install_Discriminants (E : Entity_Id) is
10125 Disc : Entity_Id;
10126 Prev : Entity_Id;
10127 begin
10128 Disc := First_Discriminant (E);
10129 while Present (Disc) loop
10130 Prev := Current_Entity (Disc);
10131 Set_Current_Entity (Disc);
10132 Set_Is_Immediately_Visible (Disc);
10133 Set_Homonym (Disc, Prev);
10134 Next_Discriminant (Disc);
10135 end loop;
10136 end Install_Discriminants;
10138 -------------------------
10139 -- Is_Operational_Item --
10140 -------------------------
10142 function Is_Operational_Item (N : Node_Id) return Boolean is
10143 begin
10144 if Nkind (N) /= N_Attribute_Definition_Clause then
10145 return False;
10147 else
10148 declare
10149 Id : constant Attribute_Id := Get_Attribute_Id (Chars (N));
10150 begin
10151 return Id = Attribute_Input
10152 or else Id = Attribute_Output
10153 or else Id = Attribute_Read
10154 or else Id = Attribute_Write
10155 or else Id = Attribute_External_Tag;
10156 end;
10157 end if;
10158 end Is_Operational_Item;
10160 ------------------
10161 -- Minimum_Size --
10162 ------------------
10164 function Minimum_Size
10165 (T : Entity_Id;
10166 Biased : Boolean := False) return Nat
10168 Lo : Uint := No_Uint;
10169 Hi : Uint := No_Uint;
10170 LoR : Ureal := No_Ureal;
10171 HiR : Ureal := No_Ureal;
10172 LoSet : Boolean := False;
10173 HiSet : Boolean := False;
10174 B : Uint;
10175 S : Nat;
10176 Ancest : Entity_Id;
10177 R_Typ : constant Entity_Id := Root_Type (T);
10179 begin
10180 -- If bad type, return 0
10182 if T = Any_Type then
10183 return 0;
10185 -- For generic types, just return zero. There cannot be any legitimate
10186 -- need to know such a size, but this routine may be called with a
10187 -- generic type as part of normal processing.
10189 elsif Is_Generic_Type (R_Typ)
10190 or else R_Typ = Any_Type
10191 then
10192 return 0;
10194 -- Access types. Normally an access type cannot have a size smaller
10195 -- than the size of System.Address. The exception is on VMS, where
10196 -- we have short and long addresses, and it is possible for an access
10197 -- type to have a short address size (and thus be less than the size
10198 -- of System.Address itself). We simply skip the check for VMS, and
10199 -- leave it to the back end to do the check.
10201 elsif Is_Access_Type (T) then
10202 if OpenVMS_On_Target then
10203 return 0;
10204 else
10205 return System_Address_Size;
10206 end if;
10208 -- Floating-point types
10210 elsif Is_Floating_Point_Type (T) then
10211 return UI_To_Int (Esize (R_Typ));
10213 -- Discrete types
10215 elsif Is_Discrete_Type (T) then
10217 -- The following loop is looking for the nearest compile time known
10218 -- bounds following the ancestor subtype chain. The idea is to find
10219 -- the most restrictive known bounds information.
10221 Ancest := T;
10222 loop
10223 if Ancest = Any_Type or else Etype (Ancest) = Any_Type then
10224 return 0;
10225 end if;
10227 if not LoSet then
10228 if Compile_Time_Known_Value (Type_Low_Bound (Ancest)) then
10229 Lo := Expr_Rep_Value (Type_Low_Bound (Ancest));
10230 LoSet := True;
10231 exit when HiSet;
10232 end if;
10233 end if;
10235 if not HiSet then
10236 if Compile_Time_Known_Value (Type_High_Bound (Ancest)) then
10237 Hi := Expr_Rep_Value (Type_High_Bound (Ancest));
10238 HiSet := True;
10239 exit when LoSet;
10240 end if;
10241 end if;
10243 Ancest := Ancestor_Subtype (Ancest);
10245 if No (Ancest) then
10246 Ancest := Base_Type (T);
10248 if Is_Generic_Type (Ancest) then
10249 return 0;
10250 end if;
10251 end if;
10252 end loop;
10254 -- Fixed-point types. We can't simply use Expr_Value to get the
10255 -- Corresponding_Integer_Value values of the bounds, since these do not
10256 -- get set till the type is frozen, and this routine can be called
10257 -- before the type is frozen. Similarly the test for bounds being static
10258 -- needs to include the case where we have unanalyzed real literals for
10259 -- the same reason.
10261 elsif Is_Fixed_Point_Type (T) then
10263 -- The following loop is looking for the nearest compile time known
10264 -- bounds following the ancestor subtype chain. The idea is to find
10265 -- the most restrictive known bounds information.
10267 Ancest := T;
10268 loop
10269 if Ancest = Any_Type or else Etype (Ancest) = Any_Type then
10270 return 0;
10271 end if;
10273 -- Note: In the following two tests for LoSet and HiSet, it may
10274 -- seem redundant to test for N_Real_Literal here since normally
10275 -- one would assume that the test for the value being known at
10276 -- compile time includes this case. However, there is a glitch.
10277 -- If the real literal comes from folding a non-static expression,
10278 -- then we don't consider any non- static expression to be known
10279 -- at compile time if we are in configurable run time mode (needed
10280 -- in some cases to give a clearer definition of what is and what
10281 -- is not accepted). So the test is indeed needed. Without it, we
10282 -- would set neither Lo_Set nor Hi_Set and get an infinite loop.
10284 if not LoSet then
10285 if Nkind (Type_Low_Bound (Ancest)) = N_Real_Literal
10286 or else Compile_Time_Known_Value (Type_Low_Bound (Ancest))
10287 then
10288 LoR := Expr_Value_R (Type_Low_Bound (Ancest));
10289 LoSet := True;
10290 exit when HiSet;
10291 end if;
10292 end if;
10294 if not HiSet then
10295 if Nkind (Type_High_Bound (Ancest)) = N_Real_Literal
10296 or else Compile_Time_Known_Value (Type_High_Bound (Ancest))
10297 then
10298 HiR := Expr_Value_R (Type_High_Bound (Ancest));
10299 HiSet := True;
10300 exit when LoSet;
10301 end if;
10302 end if;
10304 Ancest := Ancestor_Subtype (Ancest);
10306 if No (Ancest) then
10307 Ancest := Base_Type (T);
10309 if Is_Generic_Type (Ancest) then
10310 return 0;
10311 end if;
10312 end if;
10313 end loop;
10315 Lo := UR_To_Uint (LoR / Small_Value (T));
10316 Hi := UR_To_Uint (HiR / Small_Value (T));
10318 -- No other types allowed
10320 else
10321 raise Program_Error;
10322 end if;
10324 -- Fall through with Hi and Lo set. Deal with biased case
10326 if (Biased
10327 and then not Is_Fixed_Point_Type (T)
10328 and then not (Is_Enumeration_Type (T)
10329 and then Has_Non_Standard_Rep (T)))
10330 or else Has_Biased_Representation (T)
10331 then
10332 Hi := Hi - Lo;
10333 Lo := Uint_0;
10334 end if;
10336 -- Signed case. Note that we consider types like range 1 .. -1 to be
10337 -- signed for the purpose of computing the size, since the bounds have
10338 -- to be accommodated in the base type.
10340 if Lo < 0 or else Hi < 0 then
10341 S := 1;
10342 B := Uint_1;
10344 -- S = size, B = 2 ** (size - 1) (can accommodate -B .. +(B - 1))
10345 -- Note that we accommodate the case where the bounds cross. This
10346 -- can happen either because of the way the bounds are declared
10347 -- or because of the algorithm in Freeze_Fixed_Point_Type.
10349 while Lo < -B
10350 or else Hi < -B
10351 or else Lo >= B
10352 or else Hi >= B
10353 loop
10354 B := Uint_2 ** S;
10355 S := S + 1;
10356 end loop;
10358 -- Unsigned case
10360 else
10361 -- If both bounds are positive, make sure that both are represen-
10362 -- table in the case where the bounds are crossed. This can happen
10363 -- either because of the way the bounds are declared, or because of
10364 -- the algorithm in Freeze_Fixed_Point_Type.
10366 if Lo > Hi then
10367 Hi := Lo;
10368 end if;
10370 -- S = size, (can accommodate 0 .. (2**size - 1))
10372 S := 0;
10373 while Hi >= Uint_2 ** S loop
10374 S := S + 1;
10375 end loop;
10376 end if;
10378 return S;
10379 end Minimum_Size;
10381 ---------------------------
10382 -- New_Stream_Subprogram --
10383 ---------------------------
10385 procedure New_Stream_Subprogram
10386 (N : Node_Id;
10387 Ent : Entity_Id;
10388 Subp : Entity_Id;
10389 Nam : TSS_Name_Type)
10391 Loc : constant Source_Ptr := Sloc (N);
10392 Sname : constant Name_Id := Make_TSS_Name (Base_Type (Ent), Nam);
10393 Subp_Id : Entity_Id;
10394 Subp_Decl : Node_Id;
10395 F : Entity_Id;
10396 Etyp : Entity_Id;
10398 Defer_Declaration : constant Boolean :=
10399 Is_Tagged_Type (Ent) or else Is_Private_Type (Ent);
10400 -- For a tagged type, there is a declaration for each stream attribute
10401 -- at the freeze point, and we must generate only a completion of this
10402 -- declaration. We do the same for private types, because the full view
10403 -- might be tagged. Otherwise we generate a declaration at the point of
10404 -- the attribute definition clause.
10406 function Build_Spec return Node_Id;
10407 -- Used for declaration and renaming declaration, so that this is
10408 -- treated as a renaming_as_body.
10410 ----------------
10411 -- Build_Spec --
10412 ----------------
10414 function Build_Spec return Node_Id is
10415 Out_P : constant Boolean := (Nam = TSS_Stream_Read);
10416 Formals : List_Id;
10417 Spec : Node_Id;
10418 T_Ref : constant Node_Id := New_Occurrence_Of (Etyp, Loc);
10420 begin
10421 Subp_Id := Make_Defining_Identifier (Loc, Sname);
10423 -- S : access Root_Stream_Type'Class
10425 Formals := New_List (
10426 Make_Parameter_Specification (Loc,
10427 Defining_Identifier =>
10428 Make_Defining_Identifier (Loc, Name_S),
10429 Parameter_Type =>
10430 Make_Access_Definition (Loc,
10431 Subtype_Mark =>
10432 New_Occurrence_Of (
10433 Designated_Type (Etype (F)), Loc))));
10435 if Nam = TSS_Stream_Input then
10436 Spec :=
10437 Make_Function_Specification (Loc,
10438 Defining_Unit_Name => Subp_Id,
10439 Parameter_Specifications => Formals,
10440 Result_Definition => T_Ref);
10441 else
10442 -- V : [out] T
10444 Append_To (Formals,
10445 Make_Parameter_Specification (Loc,
10446 Defining_Identifier => Make_Defining_Identifier (Loc, Name_V),
10447 Out_Present => Out_P,
10448 Parameter_Type => T_Ref));
10450 Spec :=
10451 Make_Procedure_Specification (Loc,
10452 Defining_Unit_Name => Subp_Id,
10453 Parameter_Specifications => Formals);
10454 end if;
10456 return Spec;
10457 end Build_Spec;
10459 -- Start of processing for New_Stream_Subprogram
10461 begin
10462 F := First_Formal (Subp);
10464 if Ekind (Subp) = E_Procedure then
10465 Etyp := Etype (Next_Formal (F));
10466 else
10467 Etyp := Etype (Subp);
10468 end if;
10470 -- Prepare subprogram declaration and insert it as an action on the
10471 -- clause node. The visibility for this entity is used to test for
10472 -- visibility of the attribute definition clause (in the sense of
10473 -- 8.3(23) as amended by AI-195).
10475 if not Defer_Declaration then
10476 Subp_Decl :=
10477 Make_Subprogram_Declaration (Loc,
10478 Specification => Build_Spec);
10480 -- For a tagged type, there is always a visible declaration for each
10481 -- stream TSS (it is a predefined primitive operation), and the
10482 -- completion of this declaration occurs at the freeze point, which is
10483 -- not always visible at places where the attribute definition clause is
10484 -- visible. So, we create a dummy entity here for the purpose of
10485 -- tracking the visibility of the attribute definition clause itself.
10487 else
10488 Subp_Id :=
10489 Make_Defining_Identifier (Loc, New_External_Name (Sname, 'V'));
10490 Subp_Decl :=
10491 Make_Object_Declaration (Loc,
10492 Defining_Identifier => Subp_Id,
10493 Object_Definition => New_Occurrence_Of (Standard_Boolean, Loc));
10494 end if;
10496 Insert_Action (N, Subp_Decl);
10497 Set_Entity (N, Subp_Id);
10499 Subp_Decl :=
10500 Make_Subprogram_Renaming_Declaration (Loc,
10501 Specification => Build_Spec,
10502 Name => New_Occurrence_Of (Subp, Loc));
10504 if Defer_Declaration then
10505 Set_TSS (Base_Type (Ent), Subp_Id);
10506 else
10507 Insert_Action (N, Subp_Decl);
10508 Copy_TSS (Subp_Id, Base_Type (Ent));
10509 end if;
10510 end New_Stream_Subprogram;
10512 ------------------------------------------
10513 -- Push_Scope_And_Install_Discriminants --
10514 ------------------------------------------
10516 procedure Push_Scope_And_Install_Discriminants (E : Entity_Id) is
10517 begin
10518 if Has_Discriminants (E) then
10519 Push_Scope (E);
10521 -- Make discriminants visible for type declarations and protected
10522 -- type declarations, not for subtype declarations (RM 13.1.1 (12/3))
10524 if Nkind (Parent (E)) /= N_Subtype_Declaration then
10525 Install_Discriminants (E);
10526 end if;
10527 end if;
10528 end Push_Scope_And_Install_Discriminants;
10530 ------------------------
10531 -- Rep_Item_Too_Early --
10532 ------------------------
10534 function Rep_Item_Too_Early (T : Entity_Id; N : Node_Id) return Boolean is
10535 begin
10536 -- Cannot apply non-operational rep items to generic types
10538 if Is_Operational_Item (N) then
10539 return False;
10541 elsif Is_Type (T)
10542 and then Is_Generic_Type (Root_Type (T))
10543 then
10544 Error_Msg_N ("representation item not allowed for generic type", N);
10545 return True;
10546 end if;
10548 -- Otherwise check for incomplete type
10550 if Is_Incomplete_Or_Private_Type (T)
10551 and then No (Underlying_Type (T))
10552 and then
10553 (Nkind (N) /= N_Pragma
10554 or else Get_Pragma_Id (N) /= Pragma_Import)
10555 then
10556 Error_Msg_N
10557 ("representation item must be after full type declaration", N);
10558 return True;
10560 -- If the type has incomplete components, a representation clause is
10561 -- illegal but stream attributes and Convention pragmas are correct.
10563 elsif Has_Private_Component (T) then
10564 if Nkind (N) = N_Pragma then
10565 return False;
10567 else
10568 Error_Msg_N
10569 ("representation item must appear after type is fully defined",
10571 return True;
10572 end if;
10573 else
10574 return False;
10575 end if;
10576 end Rep_Item_Too_Early;
10578 -----------------------
10579 -- Rep_Item_Too_Late --
10580 -----------------------
10582 function Rep_Item_Too_Late
10583 (T : Entity_Id;
10584 N : Node_Id;
10585 FOnly : Boolean := False) return Boolean
10587 S : Entity_Id;
10588 Parent_Type : Entity_Id;
10590 procedure Too_Late;
10591 -- Output the too late message. Note that this is not considered a
10592 -- serious error, since the effect is simply that we ignore the
10593 -- representation clause in this case.
10595 --------------
10596 -- Too_Late --
10597 --------------
10599 procedure Too_Late is
10600 begin
10601 -- Other compilers seem more relaxed about rep items appearing too
10602 -- late. Since analysis tools typically don't care about rep items
10603 -- anyway, no reason to be too strict about this.
10605 if not Relaxed_RM_Semantics then
10606 Error_Msg_N ("|representation item appears too late!", N);
10607 end if;
10608 end Too_Late;
10610 -- Start of processing for Rep_Item_Too_Late
10612 begin
10613 -- First make sure entity is not frozen (RM 13.1(9))
10615 if Is_Frozen (T)
10617 -- Exclude imported types, which may be frozen if they appear in a
10618 -- representation clause for a local type.
10620 and then not From_Limited_With (T)
10622 -- Exclude generated entities (not coming from source). The common
10623 -- case is when we generate a renaming which prematurely freezes the
10624 -- renamed internal entity, but we still want to be able to set copies
10625 -- of attribute values such as Size/Alignment.
10627 and then Comes_From_Source (T)
10628 then
10629 Too_Late;
10630 S := First_Subtype (T);
10632 if Present (Freeze_Node (S)) then
10633 Error_Msg_NE
10634 ("??no more representation items for }", Freeze_Node (S), S);
10635 end if;
10637 return True;
10639 -- Check for case of non-tagged derived type whose parent either has
10640 -- primitive operations, or is a by reference type (RM 13.1(10)).
10642 elsif Is_Type (T)
10643 and then not FOnly
10644 and then Is_Derived_Type (T)
10645 and then not Is_Tagged_Type (T)
10646 then
10647 Parent_Type := Etype (Base_Type (T));
10649 if Has_Primitive_Operations (Parent_Type) then
10650 Too_Late;
10651 Error_Msg_NE
10652 ("primitive operations already defined for&!", N, Parent_Type);
10653 return True;
10655 elsif Is_By_Reference_Type (Parent_Type) then
10656 Too_Late;
10657 Error_Msg_NE
10658 ("parent type & is a by reference type!", N, Parent_Type);
10659 return True;
10660 end if;
10661 end if;
10663 -- No error, link item into head of chain of rep items for the entity,
10664 -- but avoid chaining if we have an overloadable entity, and the pragma
10665 -- is one that can apply to multiple overloaded entities.
10667 if Is_Overloadable (T) and then Nkind (N) = N_Pragma then
10668 declare
10669 Pname : constant Name_Id := Pragma_Name (N);
10670 begin
10671 if Nam_In (Pname, Name_Convention, Name_Import, Name_Export,
10672 Name_External, Name_Interface)
10673 then
10674 return False;
10675 end if;
10676 end;
10677 end if;
10679 Record_Rep_Item (T, N);
10680 return False;
10681 end Rep_Item_Too_Late;
10683 -------------------------------------
10684 -- Replace_Type_References_Generic --
10685 -------------------------------------
10687 procedure Replace_Type_References_Generic (N : Node_Id; TName : Name_Id) is
10689 function Replace_Node (N : Node_Id) return Traverse_Result;
10690 -- Processes a single node in the traversal procedure below, checking
10691 -- if node N should be replaced, and if so, doing the replacement.
10693 procedure Replace_Type_Refs is new Traverse_Proc (Replace_Node);
10694 -- This instantiation provides the body of Replace_Type_References
10696 ------------------
10697 -- Replace_Node --
10698 ------------------
10700 function Replace_Node (N : Node_Id) return Traverse_Result is
10701 S : Entity_Id;
10702 P : Node_Id;
10704 begin
10705 -- Case of identifier
10707 if Nkind (N) = N_Identifier then
10709 -- If not the type name, all done with this node
10711 if Chars (N) /= TName then
10712 return Skip;
10714 -- Otherwise do the replacement and we are done with this node
10716 else
10717 Replace_Type_Reference (N);
10718 return Skip;
10719 end if;
10721 -- Case of selected component (which is what a qualification
10722 -- looks like in the unanalyzed tree, which is what we have.
10724 elsif Nkind (N) = N_Selected_Component then
10726 -- If selector name is not our type, keeping going (we might
10727 -- still have an occurrence of the type in the prefix).
10729 if Nkind (Selector_Name (N)) /= N_Identifier
10730 or else Chars (Selector_Name (N)) /= TName
10731 then
10732 return OK;
10734 -- Selector name is our type, check qualification
10736 else
10737 -- Loop through scopes and prefixes, doing comparison
10739 S := Current_Scope;
10740 P := Prefix (N);
10741 loop
10742 -- Continue if no more scopes or scope with no name
10744 if No (S) or else Nkind (S) not in N_Has_Chars then
10745 return OK;
10746 end if;
10748 -- Do replace if prefix is an identifier matching the
10749 -- scope that we are currently looking at.
10751 if Nkind (P) = N_Identifier
10752 and then Chars (P) = Chars (S)
10753 then
10754 Replace_Type_Reference (N);
10755 return Skip;
10756 end if;
10758 -- Go check scope above us if prefix is itself of the
10759 -- form of a selected component, whose selector matches
10760 -- the scope we are currently looking at.
10762 if Nkind (P) = N_Selected_Component
10763 and then Nkind (Selector_Name (P)) = N_Identifier
10764 and then Chars (Selector_Name (P)) = Chars (S)
10765 then
10766 S := Scope (S);
10767 P := Prefix (P);
10769 -- For anything else, we don't have a match, so keep on
10770 -- going, there are still some weird cases where we may
10771 -- still have a replacement within the prefix.
10773 else
10774 return OK;
10775 end if;
10776 end loop;
10777 end if;
10779 -- Continue for any other node kind
10781 else
10782 return OK;
10783 end if;
10784 end Replace_Node;
10786 begin
10787 Replace_Type_Refs (N);
10788 end Replace_Type_References_Generic;
10790 -------------------------
10791 -- Same_Representation --
10792 -------------------------
10794 function Same_Representation (Typ1, Typ2 : Entity_Id) return Boolean is
10795 T1 : constant Entity_Id := Underlying_Type (Typ1);
10796 T2 : constant Entity_Id := Underlying_Type (Typ2);
10798 begin
10799 -- A quick check, if base types are the same, then we definitely have
10800 -- the same representation, because the subtype specific representation
10801 -- attributes (Size and Alignment) do not affect representation from
10802 -- the point of view of this test.
10804 if Base_Type (T1) = Base_Type (T2) then
10805 return True;
10807 elsif Is_Private_Type (Base_Type (T2))
10808 and then Base_Type (T1) = Full_View (Base_Type (T2))
10809 then
10810 return True;
10811 end if;
10813 -- Tagged types never have differing representations
10815 if Is_Tagged_Type (T1) then
10816 return True;
10817 end if;
10819 -- Representations are definitely different if conventions differ
10821 if Convention (T1) /= Convention (T2) then
10822 return False;
10823 end if;
10825 -- Representations are different if component alignments or scalar
10826 -- storage orders differ.
10828 if (Is_Record_Type (T1) or else Is_Array_Type (T1))
10829 and then
10830 (Is_Record_Type (T2) or else Is_Array_Type (T2))
10831 and then
10832 (Component_Alignment (T1) /= Component_Alignment (T2)
10833 or else
10834 Reverse_Storage_Order (T1) /= Reverse_Storage_Order (T2))
10835 then
10836 return False;
10837 end if;
10839 -- For arrays, the only real issue is component size. If we know the
10840 -- component size for both arrays, and it is the same, then that's
10841 -- good enough to know we don't have a change of representation.
10843 if Is_Array_Type (T1) then
10844 if Known_Component_Size (T1)
10845 and then Known_Component_Size (T2)
10846 and then Component_Size (T1) = Component_Size (T2)
10847 then
10848 if VM_Target = No_VM then
10849 return True;
10851 -- In VM targets the representation of arrays with aliased
10852 -- components differs from arrays with non-aliased components
10854 else
10855 return Has_Aliased_Components (Base_Type (T1))
10857 Has_Aliased_Components (Base_Type (T2));
10858 end if;
10859 end if;
10860 end if;
10862 -- Types definitely have same representation if neither has non-standard
10863 -- representation since default representations are always consistent.
10864 -- If only one has non-standard representation, and the other does not,
10865 -- then we consider that they do not have the same representation. They
10866 -- might, but there is no way of telling early enough.
10868 if Has_Non_Standard_Rep (T1) then
10869 if not Has_Non_Standard_Rep (T2) then
10870 return False;
10871 end if;
10872 else
10873 return not Has_Non_Standard_Rep (T2);
10874 end if;
10876 -- Here the two types both have non-standard representation, and we need
10877 -- to determine if they have the same non-standard representation.
10879 -- For arrays, we simply need to test if the component sizes are the
10880 -- same. Pragma Pack is reflected in modified component sizes, so this
10881 -- check also deals with pragma Pack.
10883 if Is_Array_Type (T1) then
10884 return Component_Size (T1) = Component_Size (T2);
10886 -- Tagged types always have the same representation, because it is not
10887 -- possible to specify different representations for common fields.
10889 elsif Is_Tagged_Type (T1) then
10890 return True;
10892 -- Case of record types
10894 elsif Is_Record_Type (T1) then
10896 -- Packed status must conform
10898 if Is_Packed (T1) /= Is_Packed (T2) then
10899 return False;
10901 -- Otherwise we must check components. Typ2 maybe a constrained
10902 -- subtype with fewer components, so we compare the components
10903 -- of the base types.
10905 else
10906 Record_Case : declare
10907 CD1, CD2 : Entity_Id;
10909 function Same_Rep return Boolean;
10910 -- CD1 and CD2 are either components or discriminants. This
10911 -- function tests whether they have the same representation.
10913 --------------
10914 -- Same_Rep --
10915 --------------
10917 function Same_Rep return Boolean is
10918 begin
10919 if No (Component_Clause (CD1)) then
10920 return No (Component_Clause (CD2));
10921 else
10922 -- Note: at this point, component clauses have been
10923 -- normalized to the default bit order, so that the
10924 -- comparison of Component_Bit_Offsets is meaningful.
10926 return
10927 Present (Component_Clause (CD2))
10928 and then
10929 Component_Bit_Offset (CD1) = Component_Bit_Offset (CD2)
10930 and then
10931 Esize (CD1) = Esize (CD2);
10932 end if;
10933 end Same_Rep;
10935 -- Start of processing for Record_Case
10937 begin
10938 if Has_Discriminants (T1) then
10940 -- The number of discriminants may be different if the
10941 -- derived type has fewer (constrained by values). The
10942 -- invisible discriminants retain the representation of
10943 -- the original, so the discrepancy does not per se
10944 -- indicate a different representation.
10946 CD1 := First_Discriminant (T1);
10947 CD2 := First_Discriminant (T2);
10948 while Present (CD1) and then Present (CD2) loop
10949 if not Same_Rep then
10950 return False;
10951 else
10952 Next_Discriminant (CD1);
10953 Next_Discriminant (CD2);
10954 end if;
10955 end loop;
10956 end if;
10958 CD1 := First_Component (Underlying_Type (Base_Type (T1)));
10959 CD2 := First_Component (Underlying_Type (Base_Type (T2)));
10960 while Present (CD1) loop
10961 if not Same_Rep then
10962 return False;
10963 else
10964 Next_Component (CD1);
10965 Next_Component (CD2);
10966 end if;
10967 end loop;
10969 return True;
10970 end Record_Case;
10971 end if;
10973 -- For enumeration types, we must check each literal to see if the
10974 -- representation is the same. Note that we do not permit enumeration
10975 -- representation clauses for Character and Wide_Character, so these
10976 -- cases were already dealt with.
10978 elsif Is_Enumeration_Type (T1) then
10979 Enumeration_Case : declare
10980 L1, L2 : Entity_Id;
10982 begin
10983 L1 := First_Literal (T1);
10984 L2 := First_Literal (T2);
10985 while Present (L1) loop
10986 if Enumeration_Rep (L1) /= Enumeration_Rep (L2) then
10987 return False;
10988 else
10989 Next_Literal (L1);
10990 Next_Literal (L2);
10991 end if;
10992 end loop;
10994 return True;
10995 end Enumeration_Case;
10997 -- Any other types have the same representation for these purposes
10999 else
11000 return True;
11001 end if;
11002 end Same_Representation;
11004 --------------------------------
11005 -- Resolve_Iterable_Operation --
11006 --------------------------------
11008 procedure Resolve_Iterable_Operation
11009 (N : Node_Id;
11010 Cursor : Entity_Id;
11011 Typ : Entity_Id;
11012 Nam : Name_Id)
11014 Ent : Entity_Id;
11015 F1 : Entity_Id;
11016 F2 : Entity_Id;
11018 begin
11019 if not Is_Overloaded (N) then
11020 if not Is_Entity_Name (N)
11021 or else Ekind (Entity (N)) /= E_Function
11022 or else Scope (Entity (N)) /= Scope (Typ)
11023 or else No (First_Formal (Entity (N)))
11024 or else Etype (First_Formal (Entity (N))) /= Typ
11025 then
11026 Error_Msg_N ("iterable primitive must be local function name "
11027 & "whose first formal is an iterable type", N);
11028 return;
11029 end if;
11031 Ent := Entity (N);
11032 F1 := First_Formal (Ent);
11033 if Nam = Name_First then
11035 -- First (Container) => Cursor
11037 if Etype (Ent) /= Cursor then
11038 Error_Msg_N ("primitive for First must yield a curosr", N);
11039 end if;
11041 elsif Nam = Name_Next then
11043 -- Next (Container, Cursor) => Cursor
11045 F2 := Next_Formal (F1);
11047 if Etype (F2) /= Cursor
11048 or else Etype (Ent) /= Cursor
11049 or else Present (Next_Formal (F2))
11050 then
11051 Error_Msg_N ("no match for Next iterable primitive", N);
11052 end if;
11054 elsif Nam = Name_Has_Element then
11056 -- Has_Element (Container, Cursor) => Boolean
11058 F2 := Next_Formal (F1);
11059 if Etype (F2) /= Cursor
11060 or else Etype (Ent) /= Standard_Boolean
11061 or else Present (Next_Formal (F2))
11062 then
11063 Error_Msg_N ("no match for Has_Element iterable primitive", N);
11064 end if;
11066 elsif Nam = Name_Element then
11067 F2 := Next_Formal (F1);
11069 if No (F2)
11070 or else Etype (F2) /= Cursor
11071 or else Present (Next_Formal (F2))
11072 then
11073 Error_Msg_N ("no match for Element iterable primitive", N);
11074 end if;
11075 null;
11077 else
11078 raise Program_Error;
11079 end if;
11081 else
11082 -- Overloaded case: find subprogram with proper signature.
11083 -- Caller will report error if no match is found.
11085 declare
11086 I : Interp_Index;
11087 It : Interp;
11089 begin
11090 Get_First_Interp (N, I, It);
11091 while Present (It.Typ) loop
11092 if Ekind (It.Nam) = E_Function
11093 and then Scope (It.Nam) = Scope (Typ)
11094 and then Etype (First_Formal (It.Nam)) = Typ
11095 then
11096 F1 := First_Formal (It.Nam);
11098 if Nam = Name_First then
11099 if Etype (It.Nam) = Cursor
11100 and then No (Next_Formal (F1))
11101 then
11102 Set_Entity (N, It.Nam);
11103 exit;
11104 end if;
11106 elsif Nam = Name_Next then
11107 F2 := Next_Formal (F1);
11109 if Present (F2)
11110 and then No (Next_Formal (F2))
11111 and then Etype (F2) = Cursor
11112 and then Etype (It.Nam) = Cursor
11113 then
11114 Set_Entity (N, It.Nam);
11115 exit;
11116 end if;
11118 elsif Nam = Name_Has_Element then
11119 F2 := Next_Formal (F1);
11121 if Present (F2)
11122 and then No (Next_Formal (F2))
11123 and then Etype (F2) = Cursor
11124 and then Etype (It.Nam) = Standard_Boolean
11125 then
11126 Set_Entity (N, It.Nam);
11127 F2 := Next_Formal (F1);
11128 exit;
11129 end if;
11131 elsif Nam = Name_Element then
11132 F2 := Next_Formal (F1);
11134 if Present (F2)
11135 and then No (Next_Formal (F2))
11136 and then Etype (F2) = Cursor
11137 then
11138 Set_Entity (N, It.Nam);
11139 exit;
11140 end if;
11141 end if;
11142 end if;
11144 Get_Next_Interp (I, It);
11145 end loop;
11146 end;
11147 end if;
11148 end Resolve_Iterable_Operation;
11150 ----------------
11151 -- Set_Biased --
11152 ----------------
11154 procedure Set_Biased
11155 (E : Entity_Id;
11156 N : Node_Id;
11157 Msg : String;
11158 Biased : Boolean := True)
11160 begin
11161 if Biased then
11162 Set_Has_Biased_Representation (E);
11164 if Warn_On_Biased_Representation then
11165 Error_Msg_NE
11166 ("?B?" & Msg & " forces biased representation for&", N, E);
11167 end if;
11168 end if;
11169 end Set_Biased;
11171 --------------------
11172 -- Set_Enum_Esize --
11173 --------------------
11175 procedure Set_Enum_Esize (T : Entity_Id) is
11176 Lo : Uint;
11177 Hi : Uint;
11178 Sz : Nat;
11180 begin
11181 Init_Alignment (T);
11183 -- Find the minimum standard size (8,16,32,64) that fits
11185 Lo := Enumeration_Rep (Entity (Type_Low_Bound (T)));
11186 Hi := Enumeration_Rep (Entity (Type_High_Bound (T)));
11188 if Lo < 0 then
11189 if Lo >= -Uint_2**07 and then Hi < Uint_2**07 then
11190 Sz := Standard_Character_Size; -- May be > 8 on some targets
11192 elsif Lo >= -Uint_2**15 and then Hi < Uint_2**15 then
11193 Sz := 16;
11195 elsif Lo >= -Uint_2**31 and then Hi < Uint_2**31 then
11196 Sz := 32;
11198 else pragma Assert (Lo >= -Uint_2**63 and then Hi < Uint_2**63);
11199 Sz := 64;
11200 end if;
11202 else
11203 if Hi < Uint_2**08 then
11204 Sz := Standard_Character_Size; -- May be > 8 on some targets
11206 elsif Hi < Uint_2**16 then
11207 Sz := 16;
11209 elsif Hi < Uint_2**32 then
11210 Sz := 32;
11212 else pragma Assert (Hi < Uint_2**63);
11213 Sz := 64;
11214 end if;
11215 end if;
11217 -- That minimum is the proper size unless we have a foreign convention
11218 -- and the size required is 32 or less, in which case we bump the size
11219 -- up to 32. This is required for C and C++ and seems reasonable for
11220 -- all other foreign conventions.
11222 if Has_Foreign_Convention (T)
11223 and then Esize (T) < Standard_Integer_Size
11225 -- Don't do this if Short_Enums on target
11227 and then not Target_Short_Enums
11228 then
11229 Init_Esize (T, Standard_Integer_Size);
11230 else
11231 Init_Esize (T, Sz);
11232 end if;
11233 end Set_Enum_Esize;
11235 -----------------------------
11236 -- Uninstall_Discriminants --
11237 -----------------------------
11239 procedure Uninstall_Discriminants (E : Entity_Id) is
11240 Disc : Entity_Id;
11241 Prev : Entity_Id;
11242 Outer : Entity_Id;
11244 begin
11245 -- Discriminants have been made visible for type declarations and
11246 -- protected type declarations, not for subtype declarations.
11248 if Nkind (Parent (E)) /= N_Subtype_Declaration then
11249 Disc := First_Discriminant (E);
11250 while Present (Disc) loop
11251 if Disc /= Current_Entity (Disc) then
11252 Prev := Current_Entity (Disc);
11253 while Present (Prev)
11254 and then Present (Homonym (Prev))
11255 and then Homonym (Prev) /= Disc
11256 loop
11257 Prev := Homonym (Prev);
11258 end loop;
11259 else
11260 Prev := Empty;
11261 end if;
11263 Set_Is_Immediately_Visible (Disc, False);
11265 Outer := Homonym (Disc);
11266 while Present (Outer) and then Scope (Outer) = E loop
11267 Outer := Homonym (Outer);
11268 end loop;
11270 -- Reset homonym link of other entities, but do not modify link
11271 -- between entities in current scope, so that the back-end can
11272 -- have a proper count of local overloadings.
11274 if No (Prev) then
11275 Set_Name_Entity_Id (Chars (Disc), Outer);
11277 elsif Scope (Prev) /= Scope (Disc) then
11278 Set_Homonym (Prev, Outer);
11279 end if;
11281 Next_Discriminant (Disc);
11282 end loop;
11283 end if;
11284 end Uninstall_Discriminants;
11286 -------------------------------------------
11287 -- Uninstall_Discriminants_And_Pop_Scope --
11288 -------------------------------------------
11290 procedure Uninstall_Discriminants_And_Pop_Scope (E : Entity_Id) is
11291 begin
11292 if Has_Discriminants (E) then
11293 Uninstall_Discriminants (E);
11294 Pop_Scope;
11295 end if;
11296 end Uninstall_Discriminants_And_Pop_Scope;
11298 ------------------------------
11299 -- Validate_Address_Clauses --
11300 ------------------------------
11302 procedure Validate_Address_Clauses is
11303 begin
11304 for J in Address_Clause_Checks.First .. Address_Clause_Checks.Last loop
11305 declare
11306 ACCR : Address_Clause_Check_Record
11307 renames Address_Clause_Checks.Table (J);
11309 Expr : Node_Id;
11311 X_Alignment : Uint;
11312 Y_Alignment : Uint;
11314 X_Size : Uint;
11315 Y_Size : Uint;
11317 begin
11318 -- Skip processing of this entry if warning already posted
11320 if not Address_Warning_Posted (ACCR.N) then
11321 Expr := Original_Node (Expression (ACCR.N));
11323 -- Get alignments
11325 X_Alignment := Alignment (ACCR.X);
11326 Y_Alignment := Alignment (ACCR.Y);
11328 -- Similarly obtain sizes
11330 X_Size := Esize (ACCR.X);
11331 Y_Size := Esize (ACCR.Y);
11333 -- Check for large object overlaying smaller one
11335 if Y_Size > Uint_0
11336 and then X_Size > Uint_0
11337 and then X_Size > Y_Size
11338 then
11339 Error_Msg_NE
11340 ("??& overlays smaller object", ACCR.N, ACCR.X);
11341 Error_Msg_N
11342 ("\??program execution may be erroneous", ACCR.N);
11343 Error_Msg_Uint_1 := X_Size;
11344 Error_Msg_NE
11345 ("\??size of & is ^", ACCR.N, ACCR.X);
11346 Error_Msg_Uint_1 := Y_Size;
11347 Error_Msg_NE
11348 ("\??size of & is ^", ACCR.N, ACCR.Y);
11350 -- Check for inadequate alignment, both of the base object
11351 -- and of the offset, if any.
11353 -- Note: we do not check the alignment if we gave a size
11354 -- warning, since it would likely be redundant.
11356 elsif Y_Alignment /= Uint_0
11357 and then (Y_Alignment < X_Alignment
11358 or else (ACCR.Off
11359 and then
11360 Nkind (Expr) = N_Attribute_Reference
11361 and then
11362 Attribute_Name (Expr) = Name_Address
11363 and then
11364 Has_Compatible_Alignment
11365 (ACCR.X, Prefix (Expr))
11366 /= Known_Compatible))
11367 then
11368 Error_Msg_NE
11369 ("??specified address for& may be inconsistent "
11370 & "with alignment", ACCR.N, ACCR.X);
11371 Error_Msg_N
11372 ("\??program execution may be erroneous (RM 13.3(27))",
11373 ACCR.N);
11374 Error_Msg_Uint_1 := X_Alignment;
11375 Error_Msg_NE
11376 ("\??alignment of & is ^", ACCR.N, ACCR.X);
11377 Error_Msg_Uint_1 := Y_Alignment;
11378 Error_Msg_NE
11379 ("\??alignment of & is ^", ACCR.N, ACCR.Y);
11380 if Y_Alignment >= X_Alignment then
11381 Error_Msg_N
11382 ("\??but offset is not multiple of alignment", ACCR.N);
11383 end if;
11384 end if;
11385 end if;
11386 end;
11387 end loop;
11388 end Validate_Address_Clauses;
11390 ---------------------------
11391 -- Validate_Independence --
11392 ---------------------------
11394 procedure Validate_Independence is
11395 SU : constant Uint := UI_From_Int (System_Storage_Unit);
11396 N : Node_Id;
11397 E : Entity_Id;
11398 IC : Boolean;
11399 Comp : Entity_Id;
11400 Addr : Node_Id;
11401 P : Node_Id;
11403 procedure Check_Array_Type (Atyp : Entity_Id);
11404 -- Checks if the array type Atyp has independent components, and
11405 -- if not, outputs an appropriate set of error messages.
11407 procedure No_Independence;
11408 -- Output message that independence cannot be guaranteed
11410 function OK_Component (C : Entity_Id) return Boolean;
11411 -- Checks one component to see if it is independently accessible, and
11412 -- if so yields True, otherwise yields False if independent access
11413 -- cannot be guaranteed. This is a conservative routine, it only
11414 -- returns True if it knows for sure, it returns False if it knows
11415 -- there is a problem, or it cannot be sure there is no problem.
11417 procedure Reason_Bad_Component (C : Entity_Id);
11418 -- Outputs continuation message if a reason can be determined for
11419 -- the component C being bad.
11421 ----------------------
11422 -- Check_Array_Type --
11423 ----------------------
11425 procedure Check_Array_Type (Atyp : Entity_Id) is
11426 Ctyp : constant Entity_Id := Component_Type (Atyp);
11428 begin
11429 -- OK if no alignment clause, no pack, and no component size
11431 if not Has_Component_Size_Clause (Atyp)
11432 and then not Has_Alignment_Clause (Atyp)
11433 and then not Is_Packed (Atyp)
11434 then
11435 return;
11436 end if;
11438 -- Check actual component size
11440 if not Known_Component_Size (Atyp)
11441 or else not (Addressable (Component_Size (Atyp))
11442 and then Component_Size (Atyp) < 64)
11443 or else Component_Size (Atyp) mod Esize (Ctyp) /= 0
11444 then
11445 No_Independence;
11447 -- Bad component size, check reason
11449 if Has_Component_Size_Clause (Atyp) then
11450 P := Get_Attribute_Definition_Clause
11451 (Atyp, Attribute_Component_Size);
11453 if Present (P) then
11454 Error_Msg_Sloc := Sloc (P);
11455 Error_Msg_N ("\because of Component_Size clause#", N);
11456 return;
11457 end if;
11458 end if;
11460 if Is_Packed (Atyp) then
11461 P := Get_Rep_Pragma (Atyp, Name_Pack);
11463 if Present (P) then
11464 Error_Msg_Sloc := Sloc (P);
11465 Error_Msg_N ("\because of pragma Pack#", N);
11466 return;
11467 end if;
11468 end if;
11470 -- No reason found, just return
11472 return;
11473 end if;
11475 -- Array type is OK independence-wise
11477 return;
11478 end Check_Array_Type;
11480 ---------------------
11481 -- No_Independence --
11482 ---------------------
11484 procedure No_Independence is
11485 begin
11486 if Pragma_Name (N) = Name_Independent then
11487 Error_Msg_NE ("independence cannot be guaranteed for&", N, E);
11488 else
11489 Error_Msg_NE
11490 ("independent components cannot be guaranteed for&", N, E);
11491 end if;
11492 end No_Independence;
11494 ------------------
11495 -- OK_Component --
11496 ------------------
11498 function OK_Component (C : Entity_Id) return Boolean is
11499 Rec : constant Entity_Id := Scope (C);
11500 Ctyp : constant Entity_Id := Etype (C);
11502 begin
11503 -- OK if no component clause, no Pack, and no alignment clause
11505 if No (Component_Clause (C))
11506 and then not Is_Packed (Rec)
11507 and then not Has_Alignment_Clause (Rec)
11508 then
11509 return True;
11510 end if;
11512 -- Here we look at the actual component layout. A component is
11513 -- addressable if its size is a multiple of the Esize of the
11514 -- component type, and its starting position in the record has
11515 -- appropriate alignment, and the record itself has appropriate
11516 -- alignment to guarantee the component alignment.
11518 -- Make sure sizes are static, always assume the worst for any
11519 -- cases where we cannot check static values.
11521 if not (Known_Static_Esize (C)
11522 and then
11523 Known_Static_Esize (Ctyp))
11524 then
11525 return False;
11526 end if;
11528 -- Size of component must be addressable or greater than 64 bits
11529 -- and a multiple of bytes.
11531 if not Addressable (Esize (C)) and then Esize (C) < Uint_64 then
11532 return False;
11533 end if;
11535 -- Check size is proper multiple
11537 if Esize (C) mod Esize (Ctyp) /= 0 then
11538 return False;
11539 end if;
11541 -- Check alignment of component is OK
11543 if not Known_Component_Bit_Offset (C)
11544 or else Component_Bit_Offset (C) < Uint_0
11545 or else Component_Bit_Offset (C) mod Esize (Ctyp) /= 0
11546 then
11547 return False;
11548 end if;
11550 -- Check alignment of record type is OK
11552 if not Known_Alignment (Rec)
11553 or else (Alignment (Rec) * SU) mod Esize (Ctyp) /= 0
11554 then
11555 return False;
11556 end if;
11558 -- All tests passed, component is addressable
11560 return True;
11561 end OK_Component;
11563 --------------------------
11564 -- Reason_Bad_Component --
11565 --------------------------
11567 procedure Reason_Bad_Component (C : Entity_Id) is
11568 Rec : constant Entity_Id := Scope (C);
11569 Ctyp : constant Entity_Id := Etype (C);
11571 begin
11572 -- If component clause present assume that's the problem
11574 if Present (Component_Clause (C)) then
11575 Error_Msg_Sloc := Sloc (Component_Clause (C));
11576 Error_Msg_N ("\because of Component_Clause#", N);
11577 return;
11578 end if;
11580 -- If pragma Pack clause present, assume that's the problem
11582 if Is_Packed (Rec) then
11583 P := Get_Rep_Pragma (Rec, Name_Pack);
11585 if Present (P) then
11586 Error_Msg_Sloc := Sloc (P);
11587 Error_Msg_N ("\because of pragma Pack#", N);
11588 return;
11589 end if;
11590 end if;
11592 -- See if record has bad alignment clause
11594 if Has_Alignment_Clause (Rec)
11595 and then Known_Alignment (Rec)
11596 and then (Alignment (Rec) * SU) mod Esize (Ctyp) /= 0
11597 then
11598 P := Get_Attribute_Definition_Clause (Rec, Attribute_Alignment);
11600 if Present (P) then
11601 Error_Msg_Sloc := Sloc (P);
11602 Error_Msg_N ("\because of Alignment clause#", N);
11603 end if;
11604 end if;
11606 -- Couldn't find a reason, so return without a message
11608 return;
11609 end Reason_Bad_Component;
11611 -- Start of processing for Validate_Independence
11613 begin
11614 for J in Independence_Checks.First .. Independence_Checks.Last loop
11615 N := Independence_Checks.Table (J).N;
11616 E := Independence_Checks.Table (J).E;
11617 IC := Pragma_Name (N) = Name_Independent_Components;
11619 -- Deal with component case
11621 if Ekind (E) = E_Discriminant or else Ekind (E) = E_Component then
11622 if not OK_Component (E) then
11623 No_Independence;
11624 Reason_Bad_Component (E);
11625 goto Continue;
11626 end if;
11627 end if;
11629 -- Deal with record with Independent_Components
11631 if IC and then Is_Record_Type (E) then
11632 Comp := First_Component_Or_Discriminant (E);
11633 while Present (Comp) loop
11634 if not OK_Component (Comp) then
11635 No_Independence;
11636 Reason_Bad_Component (Comp);
11637 goto Continue;
11638 end if;
11640 Next_Component_Or_Discriminant (Comp);
11641 end loop;
11642 end if;
11644 -- Deal with address clause case
11646 if Is_Object (E) then
11647 Addr := Address_Clause (E);
11649 if Present (Addr) then
11650 No_Independence;
11651 Error_Msg_Sloc := Sloc (Addr);
11652 Error_Msg_N ("\because of Address clause#", N);
11653 goto Continue;
11654 end if;
11655 end if;
11657 -- Deal with independent components for array type
11659 if IC and then Is_Array_Type (E) then
11660 Check_Array_Type (E);
11661 end if;
11663 -- Deal with independent components for array object
11665 if IC and then Is_Object (E) and then Is_Array_Type (Etype (E)) then
11666 Check_Array_Type (Etype (E));
11667 end if;
11669 <<Continue>> null;
11670 end loop;
11671 end Validate_Independence;
11673 ------------------------------
11674 -- Validate_Iterable_Aspect --
11675 ------------------------------
11677 procedure Validate_Iterable_Aspect (Typ : Entity_Id; ASN : Node_Id) is
11678 Assoc : Node_Id;
11679 Expr : Node_Id;
11681 Prim : Node_Id;
11682 Cursor : constant Entity_Id := Get_Cursor_Type (ASN, Typ);
11684 First_Id : Entity_Id;
11685 Next_Id : Entity_Id;
11686 Has_Element_Id : Entity_Id;
11687 Element_Id : Entity_Id;
11689 begin
11690 -- If previous error aspect is unusable
11692 if Cursor = Any_Type then
11693 return;
11694 end if;
11696 First_Id := Empty;
11697 Next_Id := Empty;
11698 Has_Element_Id := Empty;
11699 Element_Id := Empty;
11701 -- Each expression must resolve to a function with the proper signature
11703 Assoc := First (Component_Associations (Expression (ASN)));
11704 while Present (Assoc) loop
11705 Expr := Expression (Assoc);
11706 Analyze (Expr);
11708 Prim := First (Choices (Assoc));
11710 if Nkind (Prim) /= N_Identifier
11711 or else Present (Next (Prim))
11712 then
11713 Error_Msg_N ("illegal name in association", Prim);
11715 elsif Chars (Prim) = Name_First then
11716 Resolve_Iterable_Operation (Expr, Cursor, Typ, Name_First);
11717 First_Id := Entity (Expr);
11719 elsif Chars (Prim) = Name_Next then
11720 Resolve_Iterable_Operation (Expr, Cursor, Typ, Name_Next);
11721 Next_Id := Entity (Expr);
11723 elsif Chars (Prim) = Name_Has_Element then
11724 Resolve_Iterable_Operation (Expr, Cursor, Typ, Name_Has_Element);
11725 Has_Element_Id := Entity (Expr);
11727 elsif Chars (Prim) = Name_Element then
11728 Resolve_Iterable_Operation (Expr, Cursor, Typ, Name_Element);
11729 Element_Id := Entity (Expr);
11731 else
11732 Error_Msg_N ("invalid name for iterable function", Prim);
11733 end if;
11735 Next (Assoc);
11736 end loop;
11738 if No (First_Id) then
11739 Error_Msg_N ("match for First primitive not found", ASN);
11741 elsif No (Next_Id) then
11742 Error_Msg_N ("match for Next primitive not found", ASN);
11744 elsif No (Has_Element_Id) then
11745 Error_Msg_N ("match for Has_Element primitive not found", ASN);
11747 elsif No (Element_Id) then
11748 null; -- Optional.
11749 end if;
11750 end Validate_Iterable_Aspect;
11752 -----------------------------------
11753 -- Validate_Unchecked_Conversion --
11754 -----------------------------------
11756 procedure Validate_Unchecked_Conversion
11757 (N : Node_Id;
11758 Act_Unit : Entity_Id)
11760 Source : Entity_Id;
11761 Target : Entity_Id;
11762 Vnode : Node_Id;
11764 begin
11765 -- Obtain source and target types. Note that we call Ancestor_Subtype
11766 -- here because the processing for generic instantiation always makes
11767 -- subtypes, and we want the original frozen actual types.
11769 -- If we are dealing with private types, then do the check on their
11770 -- fully declared counterparts if the full declarations have been
11771 -- encountered (they don't have to be visible, but they must exist).
11773 Source := Ancestor_Subtype (Etype (First_Formal (Act_Unit)));
11775 if Is_Private_Type (Source)
11776 and then Present (Underlying_Type (Source))
11777 then
11778 Source := Underlying_Type (Source);
11779 end if;
11781 Target := Ancestor_Subtype (Etype (Act_Unit));
11783 -- If either type is generic, the instantiation happens within a generic
11784 -- unit, and there is nothing to check. The proper check will happen
11785 -- when the enclosing generic is instantiated.
11787 if Is_Generic_Type (Source) or else Is_Generic_Type (Target) then
11788 return;
11789 end if;
11791 if Is_Private_Type (Target)
11792 and then Present (Underlying_Type (Target))
11793 then
11794 Target := Underlying_Type (Target);
11795 end if;
11797 -- Source may be unconstrained array, but not target
11799 if Is_Array_Type (Target) and then not Is_Constrained (Target) then
11800 Error_Msg_N
11801 ("unchecked conversion to unconstrained array not allowed", N);
11802 return;
11803 end if;
11805 -- Warn if conversion between two different convention pointers
11807 if Is_Access_Type (Target)
11808 and then Is_Access_Type (Source)
11809 and then Convention (Target) /= Convention (Source)
11810 and then Warn_On_Unchecked_Conversion
11811 then
11812 -- Give warnings for subprogram pointers only on most targets. The
11813 -- exception is VMS, where data pointers can have different lengths
11814 -- depending on the pointer convention.
11816 if Is_Access_Subprogram_Type (Target)
11817 or else Is_Access_Subprogram_Type (Source)
11818 or else OpenVMS_On_Target
11819 then
11820 Error_Msg_N
11821 ("?z?conversion between pointers with different conventions!",
11823 end if;
11824 end if;
11826 -- Warn if one of the operands is Ada.Calendar.Time. Do not emit a
11827 -- warning when compiling GNAT-related sources.
11829 if Warn_On_Unchecked_Conversion
11830 and then not In_Predefined_Unit (N)
11831 and then RTU_Loaded (Ada_Calendar)
11832 and then
11833 (Chars (Source) = Name_Time
11834 or else
11835 Chars (Target) = Name_Time)
11836 then
11837 -- If Ada.Calendar is loaded and the name of one of the operands is
11838 -- Time, there is a good chance that this is Ada.Calendar.Time.
11840 declare
11841 Calendar_Time : constant Entity_Id :=
11842 Full_View (RTE (RO_CA_Time));
11843 begin
11844 pragma Assert (Present (Calendar_Time));
11846 if Source = Calendar_Time or else Target = Calendar_Time then
11847 Error_Msg_N
11848 ("?z?representation of 'Time values may change between " &
11849 "'G'N'A'T versions", N);
11850 end if;
11851 end;
11852 end if;
11854 -- Make entry in unchecked conversion table for later processing by
11855 -- Validate_Unchecked_Conversions, which will check sizes and alignments
11856 -- (using values set by the back-end where possible). This is only done
11857 -- if the appropriate warning is active.
11859 if Warn_On_Unchecked_Conversion then
11860 Unchecked_Conversions.Append
11861 (New_Val => UC_Entry'(Eloc => Sloc (N),
11862 Source => Source,
11863 Target => Target,
11864 Act_Unit => Act_Unit));
11866 -- If both sizes are known statically now, then back end annotation
11867 -- is not required to do a proper check but if either size is not
11868 -- known statically, then we need the annotation.
11870 if Known_Static_RM_Size (Source)
11871 and then
11872 Known_Static_RM_Size (Target)
11873 then
11874 null;
11875 else
11876 Back_Annotate_Rep_Info := True;
11877 end if;
11878 end if;
11880 -- If unchecked conversion to access type, and access type is declared
11881 -- in the same unit as the unchecked conversion, then set the flag
11882 -- No_Strict_Aliasing (no strict aliasing is implicit here)
11884 if Is_Access_Type (Target) and then
11885 In_Same_Source_Unit (Target, N)
11886 then
11887 Set_No_Strict_Aliasing (Implementation_Base_Type (Target));
11888 end if;
11890 -- Generate N_Validate_Unchecked_Conversion node for back end in case
11891 -- the back end needs to perform special validation checks.
11893 -- Shouldn't this be in Exp_Ch13, since the check only gets done if we
11894 -- have full expansion and the back end is called ???
11896 Vnode :=
11897 Make_Validate_Unchecked_Conversion (Sloc (N));
11898 Set_Source_Type (Vnode, Source);
11899 Set_Target_Type (Vnode, Target);
11901 -- If the unchecked conversion node is in a list, just insert before it.
11902 -- If not we have some strange case, not worth bothering about.
11904 if Is_List_Member (N) then
11905 Insert_After (N, Vnode);
11906 end if;
11907 end Validate_Unchecked_Conversion;
11909 ------------------------------------
11910 -- Validate_Unchecked_Conversions --
11911 ------------------------------------
11913 procedure Validate_Unchecked_Conversions is
11914 begin
11915 for N in Unchecked_Conversions.First .. Unchecked_Conversions.Last loop
11916 declare
11917 T : UC_Entry renames Unchecked_Conversions.Table (N);
11919 Eloc : constant Source_Ptr := T.Eloc;
11920 Source : constant Entity_Id := T.Source;
11921 Target : constant Entity_Id := T.Target;
11922 Act_Unit : constant Entity_Id := T.Act_Unit;
11924 Source_Siz : Uint;
11925 Target_Siz : Uint;
11927 begin
11928 -- Skip if function marked as warnings off
11930 if Warnings_Off (Act_Unit) then
11931 goto Continue;
11932 end if;
11934 -- This validation check, which warns if we have unequal sizes for
11935 -- unchecked conversion, and thus potentially implementation
11936 -- dependent semantics, is one of the few occasions on which we
11937 -- use the official RM size instead of Esize. See description in
11938 -- Einfo "Handling of Type'Size Values" for details.
11940 if Serious_Errors_Detected = 0
11941 and then Known_Static_RM_Size (Source)
11942 and then Known_Static_RM_Size (Target)
11944 -- Don't do the check if warnings off for either type, note the
11945 -- deliberate use of OR here instead of OR ELSE to get the flag
11946 -- Warnings_Off_Used set for both types if appropriate.
11948 and then not (Has_Warnings_Off (Source)
11950 Has_Warnings_Off (Target))
11951 then
11952 Source_Siz := RM_Size (Source);
11953 Target_Siz := RM_Size (Target);
11955 if Source_Siz /= Target_Siz then
11956 Error_Msg
11957 ("?z?types for unchecked conversion have different sizes!",
11958 Eloc);
11960 if All_Errors_Mode then
11961 Error_Msg_Name_1 := Chars (Source);
11962 Error_Msg_Uint_1 := Source_Siz;
11963 Error_Msg_Name_2 := Chars (Target);
11964 Error_Msg_Uint_2 := Target_Siz;
11965 Error_Msg ("\size of % is ^, size of % is ^?z?", Eloc);
11967 Error_Msg_Uint_1 := UI_Abs (Source_Siz - Target_Siz);
11969 if Is_Discrete_Type (Source)
11970 and then
11971 Is_Discrete_Type (Target)
11972 then
11973 if Source_Siz > Target_Siz then
11974 Error_Msg
11975 ("\?z?^ high order bits of source will "
11976 & "be ignored!", Eloc);
11978 elsif Is_Unsigned_Type (Source) then
11979 Error_Msg
11980 ("\?z?source will be extended with ^ high order "
11981 & "zero bits!", Eloc);
11983 else
11984 Error_Msg
11985 ("\?z?source will be extended with ^ high order "
11986 & "sign bits!", Eloc);
11987 end if;
11989 elsif Source_Siz < Target_Siz then
11990 if Is_Discrete_Type (Target) then
11991 if Bytes_Big_Endian then
11992 Error_Msg
11993 ("\?z?target value will include ^ undefined "
11994 & "low order bits!", Eloc);
11995 else
11996 Error_Msg
11997 ("\?z?target value will include ^ undefined "
11998 & "high order bits!", Eloc);
11999 end if;
12001 else
12002 Error_Msg
12003 ("\?z?^ trailing bits of target value will be "
12004 & "undefined!", Eloc);
12005 end if;
12007 else pragma Assert (Source_Siz > Target_Siz);
12008 Error_Msg
12009 ("\?z?^ trailing bits of source will be ignored!",
12010 Eloc);
12011 end if;
12012 end if;
12013 end if;
12014 end if;
12016 -- If both types are access types, we need to check the alignment.
12017 -- If the alignment of both is specified, we can do it here.
12019 if Serious_Errors_Detected = 0
12020 and then Ekind (Source) in Access_Kind
12021 and then Ekind (Target) in Access_Kind
12022 and then Target_Strict_Alignment
12023 and then Present (Designated_Type (Source))
12024 and then Present (Designated_Type (Target))
12025 then
12026 declare
12027 D_Source : constant Entity_Id := Designated_Type (Source);
12028 D_Target : constant Entity_Id := Designated_Type (Target);
12030 begin
12031 if Known_Alignment (D_Source)
12032 and then
12033 Known_Alignment (D_Target)
12034 then
12035 declare
12036 Source_Align : constant Uint := Alignment (D_Source);
12037 Target_Align : constant Uint := Alignment (D_Target);
12039 begin
12040 if Source_Align < Target_Align
12041 and then not Is_Tagged_Type (D_Source)
12043 -- Suppress warning if warnings suppressed on either
12044 -- type or either designated type. Note the use of
12045 -- OR here instead of OR ELSE. That is intentional,
12046 -- we would like to set flag Warnings_Off_Used in
12047 -- all types for which warnings are suppressed.
12049 and then not (Has_Warnings_Off (D_Source)
12051 Has_Warnings_Off (D_Target)
12053 Has_Warnings_Off (Source)
12055 Has_Warnings_Off (Target))
12056 then
12057 Error_Msg_Uint_1 := Target_Align;
12058 Error_Msg_Uint_2 := Source_Align;
12059 Error_Msg_Node_1 := D_Target;
12060 Error_Msg_Node_2 := D_Source;
12061 Error_Msg
12062 ("?z?alignment of & (^) is stricter than "
12063 & "alignment of & (^)!", Eloc);
12064 Error_Msg
12065 ("\?z?resulting access value may have invalid "
12066 & "alignment!", Eloc);
12067 end if;
12068 end;
12069 end if;
12070 end;
12071 end if;
12072 end;
12074 <<Continue>>
12075 null;
12076 end loop;
12077 end Validate_Unchecked_Conversions;
12079 end Sem_Ch13;