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-2019, Free Software Foundation, Inc.         --
10--                                                                          --
11-- GNAT is free software;  you can  redistribute it  and/or modify it under --
12-- terms of the  GNU General Public License as published  by the Free Soft- --
13-- ware  Foundation;  either version 3,  or (at your option) any later ver- --
14-- sion.  GNAT is distributed in the hope that it will be useful, but WITH- --
15-- OUT ANY WARRANTY;  without even the  implied warranty of MERCHANTABILITY --
16-- or FITNESS FOR A PARTICULAR PURPOSE.  See the GNU General Public License --
17-- for  more details.  You should have  received  a copy of the GNU General --
18-- Public License  distributed with GNAT; see file COPYING3.  If not, go to --
19-- http://www.gnu.org/licenses for a complete copy of the license.          --
20--                                                                          --
21-- GNAT was originally developed  by the GNAT team at  New York University. --
22-- Extensive contributions were provided by Ada Core Technologies Inc.      --
23--                                                                          --
24------------------------------------------------------------------------------
25
26with Aspects;  use Aspects;
27with Atree;    use Atree;
28with Checks;   use Checks;
29with Debug;    use Debug;
30with Einfo;    use Einfo;
31with Elists;   use Elists;
32with Errout;   use Errout;
33with Expander; use Expander;
34with Exp_Disp; use Exp_Disp;
35with Exp_Tss;  use Exp_Tss;
36with Exp_Util; use Exp_Util;
37with Freeze;   use Freeze;
38with Ghost;    use Ghost;
39with Lib;      use Lib;
40with Lib.Xref; use Lib.Xref;
41with Namet;    use Namet;
42with Nlists;   use Nlists;
43with Nmake;    use Nmake;
44with Opt;      use Opt;
45with Par_SCO;  use Par_SCO;
46with Restrict; use Restrict;
47with Rident;   use Rident;
48with Rtsfind;  use Rtsfind;
49with Sem;      use Sem;
50with Sem_Aux;  use Sem_Aux;
51with Sem_Case; use Sem_Case;
52with Sem_Ch3;  use Sem_Ch3;
53with Sem_Ch6;  use Sem_Ch6;
54with Sem_Ch7;  use Sem_Ch7;
55with Sem_Ch8;  use Sem_Ch8;
56with Sem_Dim;  use Sem_Dim;
57with Sem_Disp; use Sem_Disp;
58with Sem_Eval; use Sem_Eval;
59with Sem_Prag; use Sem_Prag;
60with Sem_Res;  use Sem_Res;
61with Sem_Type; use Sem_Type;
62with Sem_Util; use Sem_Util;
63with Sem_Warn; use Sem_Warn;
64with Sinfo;    use Sinfo;
65with Sinput;   use Sinput;
66with Snames;   use Snames;
67with Stand;    use Stand;
68with Targparm; use Targparm;
69with Ttypes;   use Ttypes;
70with Tbuild;   use Tbuild;
71with Urealp;   use Urealp;
72with Warnsw;   use Warnsw;
73
74with GNAT.Heap_Sort_G;
75
76package body Sem_Ch13 is
77
78   SSU : constant Pos := System_Storage_Unit;
79   --  Convenient short hand for commonly used constant
80
81   -----------------------
82   -- Local Subprograms --
83   -----------------------
84
85   procedure Adjust_Record_For_Reverse_Bit_Order_Ada_95 (R : Entity_Id);
86   --  Helper routine providing the original (pre-AI95-0133) behavior for
87   --  Adjust_Record_For_Reverse_Bit_Order.
88
89   procedure Alignment_Check_For_Size_Change (Typ : Entity_Id; Size : Uint);
90   --  This routine is called after setting one of the sizes of type entity
91   --  Typ to Size. The purpose is to deal with the situation of a derived
92   --  type whose inherited alignment is no longer appropriate for the new
93   --  size value. In this case, we reset the Alignment to unknown.
94
95   procedure Build_Discrete_Static_Predicate
96     (Typ  : Entity_Id;
97      Expr : Node_Id;
98      Nam  : Name_Id);
99   --  Given a predicated type Typ, where Typ is a discrete static subtype,
100   --  whose predicate expression is Expr, tests if Expr is a static predicate,
101   --  and if so, builds the predicate range list. Nam is the name of the one
102   --  argument to the predicate function. Occurrences of the type name in the
103   --  predicate expression have been replaced by identifier references to this
104   --  name, which is unique, so any identifier with Chars matching Nam must be
105   --  a reference to the type. If the predicate is non-static, this procedure
106   --  returns doing nothing. If the predicate is static, then the predicate
107   --  list is stored in Static_Discrete_Predicate (Typ), and the Expr is
108   --  rewritten as a canonicalized membership operation.
109
110   function Build_Export_Import_Pragma
111     (Asp : Node_Id;
112      Id  : Entity_Id) return Node_Id;
113   --  Create the corresponding pragma for aspect Export or Import denoted by
114   --  Asp. Id is the related entity subject to the aspect. Return Empty when
115   --  the expression of aspect Asp evaluates to False or is erroneous.
116
117   function Build_Predicate_Function_Declaration
118      (Typ : Entity_Id) return Node_Id;
119   --  Build the declaration for a predicate function. The declaration is built
120   --  at the end of the declarative part containing the type definition, which
121   --  may be before the freeze point of the type. The predicate expression is
122   --  preanalyzed at this point, to catch visibility errors.
123
124   procedure Build_Predicate_Functions (Typ : Entity_Id; N : Node_Id);
125   --  If Typ has predicates (indicated by Has_Predicates being set for Typ),
126   --  then either there are pragma Predicate entries on the rep chain for the
127   --  type (note that Predicate aspects are converted to pragma Predicate), or
128   --  there are inherited aspects from a parent type, or ancestor subtypes.
129   --  This procedure builds body for the Predicate function that tests these
130   --  predicates. N is the freeze node for the type. The spec of the function
131   --  is inserted before the freeze node, and the body of the function is
132   --  inserted after the freeze node. If the predicate expression has a least
133   --  one Raise_Expression, then this procedure also builds the M version of
134   --  the predicate function for use in membership tests.
135
136   procedure Check_Pool_Size_Clash (Ent : Entity_Id; SP, SS : Node_Id);
137   --  Called if both Storage_Pool and Storage_Size attribute definition
138   --  clauses (SP and SS) are present for entity Ent. Issue error message.
139
140   procedure Freeze_Entity_Checks (N : Node_Id);
141   --  Called from Analyze_Freeze_Entity and Analyze_Generic_Freeze Entity
142   --  to generate appropriate semantic checks that are delayed until this
143   --  point (they had to be delayed this long for cases of delayed aspects,
144   --  e.g. analysis of statically predicated subtypes in choices, for which
145   --  we have to be sure the subtypes in question are frozen before checking).
146
147   function Get_Alignment_Value (Expr : Node_Id) return Uint;
148   --  Given the expression for an alignment value, returns the corresponding
149   --  Uint value. If the value is inappropriate, then error messages are
150   --  posted as required, and a value of No_Uint is returned.
151
152   function Is_Operational_Item (N : Node_Id) return Boolean;
153   --  A specification for a stream attribute is allowed before the full type
154   --  is declared, as explained in AI-00137 and the corrigendum. Attributes
155   --  that do not specify a representation characteristic are operational
156   --  attributes.
157
158   function Is_Predicate_Static
159     (Expr : Node_Id;
160      Nam  : Name_Id) return Boolean;
161   --  Given predicate expression Expr, tests if Expr is predicate-static in
162   --  the sense of the rules in (RM 3.2.4 (15-24)). Occurrences of the type
163   --  name in the predicate expression have been replaced by references to
164   --  an identifier whose Chars field is Nam. This name is unique, so any
165   --  identifier with Chars matching Nam must be a reference to the type.
166   --  Returns True if the expression is predicate-static and False otherwise,
167   --  but is not in the business of setting flags or issuing error messages.
168   --
169   --  Only scalar types can have static predicates, so False is always
170   --  returned for non-scalar types.
171   --
172   --  Note: the RM seems to suggest that string types can also have static
173   --  predicates. But that really makes lttle sense as very few useful
174   --  predicates can be constructed for strings. Remember that:
175   --
176   --     "ABC" < "DEF"
177   --
178   --  is not a static expression. So even though the clearly faulty RM wording
179   --  allows the following:
180   --
181   --     subtype S is String with Static_Predicate => S < "DEF"
182   --
183   --  We can't allow this, otherwise we have predicate-static applying to a
184   --  larger class than static expressions, which was never intended.
185
186   procedure New_Stream_Subprogram
187     (N    : Node_Id;
188      Ent  : Entity_Id;
189      Subp : Entity_Id;
190      Nam  : TSS_Name_Type);
191   --  Create a subprogram renaming of a given stream attribute to the
192   --  designated subprogram and then in the tagged case, provide this as a
193   --  primitive operation, or in the untagged case make an appropriate TSS
194   --  entry. This is more properly an expansion activity than just semantics,
195   --  but the presence of user-defined stream functions for limited types
196   --  is a legality check, which is why this takes place here rather than in
197   --  exp_ch13, where it was previously. Nam indicates the name of the TSS
198   --  function to be generated.
199   --
200   --  To avoid elaboration anomalies with freeze nodes, for untagged types
201   --  we generate both a subprogram declaration and a subprogram renaming
202   --  declaration, so that the attribute specification is handled as a
203   --  renaming_as_body. For tagged types, the specification is one of the
204   --  primitive specs.
205
206   procedure Register_Address_Clause_Check
207     (N   : Node_Id;
208      X   : Entity_Id;
209      A   : Uint;
210      Y   : Entity_Id;
211      Off : Boolean);
212   --  Register a check for the address clause N. The rest of the parameters
213   --  are in keeping with the components of Address_Clause_Check_Record below.
214
215   procedure Resolve_Iterable_Operation
216     (N      : Node_Id;
217      Cursor : Entity_Id;
218      Typ    : Entity_Id;
219      Nam    : Name_Id);
220   --  If the name of a primitive operation for an Iterable aspect is
221   --  overloaded, resolve according to required signature.
222
223   procedure Set_Biased
224     (E      : Entity_Id;
225      N      : Node_Id;
226      Msg    : String;
227      Biased : Boolean := True);
228   --  If Biased is True, sets Has_Biased_Representation flag for E, and
229   --  outputs a warning message at node N if Warn_On_Biased_Representation is
230   --  is True. This warning inserts the string Msg to describe the construct
231   --  causing biasing.
232
233   -----------------------------------------------------------
234   --  Visibility of Discriminants in Aspect Specifications --
235   -----------------------------------------------------------
236
237   --  The discriminants of a type are visible when analyzing the aspect
238   --  specifications of a type declaration or protected type declaration,
239   --  but not when analyzing those of a subtype declaration. The following
240   --  routines enforce this distinction.
241
242   procedure Push_Type (E : Entity_Id);
243   --  Push scope E and make visible the discriminants of type entity E if E
244   --  has discriminants and is not a subtype.
245
246   procedure Pop_Type (E : Entity_Id);
247   --  Remove visibility to the discriminants of type entity E and pop the
248   --  scope stack if E has discriminants and is not a subtype.
249
250   ---------------------------------------------------
251   -- Table for Validate_Compile_Time_Warning_Error --
252   ---------------------------------------------------
253
254   --  The following table collects pragmas Compile_Time_Error and Compile_
255   --  Time_Warning for validation. Entries are made by calls to subprogram
256   --  Validate_Compile_Time_Warning_Error, and the call to the procedure
257   --  Validate_Compile_Time_Warning_Errors does the actual error checking
258   --  and posting of warning and error messages. The reason for this delayed
259   --  processing is to take advantage of back-annotations of attributes size
260   --  and alignment values performed by the back end.
261
262   --  Note: the reason we store a Source_Ptr value instead of a Node_Id is
263   --  that by the time Validate_Unchecked_Conversions is called, Sprint will
264   --  already have modified all Sloc values if the -gnatD option is set.
265
266   type CTWE_Entry is record
267      Eloc  : Source_Ptr;
268      --  Source location used in warnings and error messages
269
270      Prag  : Node_Id;
271      --  Pragma Compile_Time_Error or Compile_Time_Warning
272
273      Scope : Node_Id;
274      --  The scope which encloses the pragma
275   end record;
276
277   package Compile_Time_Warnings_Errors is new Table.Table (
278     Table_Component_Type => CTWE_Entry,
279     Table_Index_Type     => Int,
280     Table_Low_Bound      => 1,
281     Table_Initial        => 50,
282     Table_Increment      => 200,
283     Table_Name           => "Compile_Time_Warnings_Errors");
284
285   ----------------------------------------------
286   -- Table for Validate_Unchecked_Conversions --
287   ----------------------------------------------
288
289   --  The following table collects unchecked conversions for validation.
290   --  Entries are made by Validate_Unchecked_Conversion and then the call
291   --  to Validate_Unchecked_Conversions does the actual error checking and
292   --  posting of warnings. The reason for this delayed processing is to take
293   --  advantage of back-annotations of size and alignment values performed by
294   --  the back end.
295
296   --  Note: the reason we store a Source_Ptr value instead of a Node_Id is
297   --  that by the time Validate_Unchecked_Conversions is called, Sprint will
298   --  already have modified all Sloc values if the -gnatD option is set.
299
300   type UC_Entry is record
301      Eloc     : Source_Ptr; -- node used for posting warnings
302      Source   : Entity_Id;  -- source type for unchecked conversion
303      Target   : Entity_Id;  -- target type for unchecked conversion
304      Act_Unit : Entity_Id;  -- actual function instantiated
305   end record;
306
307   package Unchecked_Conversions is new Table.Table (
308     Table_Component_Type => UC_Entry,
309     Table_Index_Type     => Int,
310     Table_Low_Bound      => 1,
311     Table_Initial        => 50,
312     Table_Increment      => 200,
313     Table_Name           => "Unchecked_Conversions");
314
315   ----------------------------------------
316   -- Table for Validate_Address_Clauses --
317   ----------------------------------------
318
319   --  If an address clause has the form
320
321   --    for X'Address use Expr
322
323   --  where Expr has a value known at compile time or is of the form Y'Address
324   --  or recursively is a reference to a constant initialized with either of
325   --  these forms, and the value of Expr is not a multiple of X's alignment,
326   --  or if Y has a smaller alignment than X, then that merits a warning about
327   --  possible bad alignment. The following table collects address clauses of
328   --  this kind. We put these in a table so that they can be checked after the
329   --  back end has completed annotation of the alignments of objects, since we
330   --  can catch more cases that way.
331
332   type Address_Clause_Check_Record is record
333      N : Node_Id;
334      --  The address clause
335
336      X : Entity_Id;
337      --  The entity of the object subject to the address clause
338
339      A : Uint;
340      --  The value of the address in the first case
341
342      Y : Entity_Id;
343      --  The entity of the object being overlaid in the second case
344
345      Off : Boolean;
346      --  Whether the address is offset within Y in the second case
347
348      Alignment_Checks_Suppressed : Boolean;
349      --  Whether alignment checks are suppressed by an active scope suppress
350      --  setting. We need to save the value in order to be able to reuse it
351      --  after the back end has been run.
352   end record;
353
354   package Address_Clause_Checks is new Table.Table (
355     Table_Component_Type => Address_Clause_Check_Record,
356     Table_Index_Type     => Int,
357     Table_Low_Bound      => 1,
358     Table_Initial        => 20,
359     Table_Increment      => 200,
360     Table_Name           => "Address_Clause_Checks");
361
362   function Alignment_Checks_Suppressed
363     (ACCR : Address_Clause_Check_Record) return Boolean;
364   --  Return whether the alignment check generated for the address clause
365   --  is suppressed.
366
367   ---------------------------------
368   -- Alignment_Checks_Suppressed --
369   ---------------------------------
370
371   function Alignment_Checks_Suppressed
372     (ACCR : Address_Clause_Check_Record) return Boolean
373   is
374   begin
375      if Checks_May_Be_Suppressed (ACCR.X) then
376         return Is_Check_Suppressed (ACCR.X, Alignment_Check);
377      else
378         return ACCR.Alignment_Checks_Suppressed;
379      end if;
380   end Alignment_Checks_Suppressed;
381
382   -----------------------------------------
383   -- Adjust_Record_For_Reverse_Bit_Order --
384   -----------------------------------------
385
386   procedure Adjust_Record_For_Reverse_Bit_Order (R : Entity_Id) is
387      Max_Machine_Scalar_Size : constant Uint :=
388                                  UI_From_Int
389                                    (Standard_Long_Long_Integer_Size);
390      --  We use this as the maximum machine scalar size
391
392      SSU : constant Uint := UI_From_Int (System_Storage_Unit);
393
394      CC     : Node_Id;
395      Comp   : Node_Id;
396      Num_CC : Natural;
397
398   begin
399      --  Processing here used to depend on Ada version: the behavior was
400      --  changed by AI95-0133. However this AI is a Binding interpretation,
401      --  so we now implement it even in Ada 95 mode. The original behavior
402      --  from unamended Ada 95 is still available for compatibility under
403      --  debugging switch -gnatd.
404
405      if Ada_Version < Ada_2005 and then Debug_Flag_Dot_P then
406         Adjust_Record_For_Reverse_Bit_Order_Ada_95 (R);
407         return;
408      end if;
409
410      --  For Ada 2005, we do machine scalar processing, as fully described In
411      --  AI-133. This involves gathering all components which start at the
412      --  same byte offset and processing them together. Same approach is still
413      --  valid in later versions including Ada 2012.
414
415      --  This first loop through components does two things. First it deals
416      --  with the case of components with component clauses whose length is
417      --  greater than the maximum machine scalar size (either accepting them
418      --  or rejecting as needed). Second, it counts the number of components
419      --  with component clauses whose length does not exceed this maximum for
420      --  later processing.
421
422      Num_CC := 0;
423      Comp   := First_Component_Or_Discriminant (R);
424      while Present (Comp) loop
425         CC := Component_Clause (Comp);
426
427         if Present (CC) then
428            declare
429               Fbit : constant Uint := Static_Integer (First_Bit (CC));
430               Lbit : constant Uint := Static_Integer (Last_Bit (CC));
431
432            begin
433               --  Case of component with last bit >= max machine scalar
434
435               if Lbit >= Max_Machine_Scalar_Size then
436
437                  --  This is allowed only if first bit is zero, and last bit
438                  --  + 1 is a multiple of storage unit size.
439
440                  if Fbit = 0 and then (Lbit + 1) mod SSU = 0 then
441
442                     --  This is the case to give a warning if enabled
443
444                     if Warn_On_Reverse_Bit_Order then
445                        Error_Msg_N
446                          ("info: multi-byte field specified with "
447                           & "non-standard Bit_Order?V?", CC);
448
449                        if Bytes_Big_Endian then
450                           Error_Msg_N
451                             ("\bytes are not reversed "
452                              & "(component is big-endian)?V?", CC);
453                        else
454                           Error_Msg_N
455                             ("\bytes are not reversed "
456                              & "(component is little-endian)?V?", CC);
457                        end if;
458                     end if;
459
460                  --  Give error message for RM 13.5.1(10) violation
461
462                  else
463                     Error_Msg_FE
464                       ("machine scalar rules not followed for&",
465                        First_Bit (CC), Comp);
466
467                     Error_Msg_Uint_1 := Lbit + 1;
468                     Error_Msg_Uint_2 := Max_Machine_Scalar_Size;
469                     Error_Msg_F
470                       ("\last bit + 1 (^) exceeds maximum machine scalar "
471                        & "size (^)", First_Bit (CC));
472
473                     if (Lbit + 1) mod SSU /= 0 then
474                        Error_Msg_Uint_1 := SSU;
475                        Error_Msg_F
476                          ("\and is not a multiple of Storage_Unit (^) "
477                           & "(RM 13.5.1(10))", First_Bit (CC));
478
479                     else
480                        Error_Msg_Uint_1 := Fbit;
481                        Error_Msg_F
482                          ("\and first bit (^) is non-zero "
483                           & "(RM 13.4.1(10))", First_Bit (CC));
484                     end if;
485                  end if;
486
487               --  OK case of machine scalar related component clause. For now,
488               --  just count them.
489
490               else
491                  Num_CC := Num_CC + 1;
492               end if;
493            end;
494         end if;
495
496         Next_Component_Or_Discriminant (Comp);
497      end loop;
498
499      --  We need to sort the component clauses on the basis of the Position
500      --  values in the clause, so we can group clauses with the same Position
501      --  together to determine the relevant machine scalar size.
502
503      Sort_CC : declare
504         Comps : array (0 .. Num_CC) of Entity_Id;
505         --  Array to collect component and discriminant entities. The data
506         --  starts at index 1, the 0'th entry is for the sort routine.
507
508         function CP_Lt (Op1, Op2 : Natural) return Boolean;
509         --  Compare routine for Sort
510
511         procedure CP_Move (From : Natural; To : Natural);
512         --  Move routine for Sort
513
514         package Sorting is new GNAT.Heap_Sort_G (CP_Move, CP_Lt);
515
516         MaxL : Uint;
517         --  Maximum last bit value of any component in this set
518
519         MSS : Uint;
520         --  Corresponding machine scalar size
521
522         Start : Natural;
523         Stop  : Natural;
524         --  Start and stop positions in the component list of the set of
525         --  components with the same starting position (that constitute
526         --  components in a single machine scalar).
527
528         -----------
529         -- CP_Lt --
530         -----------
531
532         function CP_Lt (Op1, Op2 : Natural) return Boolean is
533         begin
534            return
535              Position (Component_Clause (Comps (Op1))) <
536              Position (Component_Clause (Comps (Op2)));
537         end CP_Lt;
538
539         -------------
540         -- CP_Move --
541         -------------
542
543         procedure CP_Move (From : Natural; To : Natural) is
544         begin
545            Comps (To) := Comps (From);
546         end CP_Move;
547
548      --  Start of processing for Sort_CC
549
550      begin
551         --  Collect the machine scalar relevant component clauses
552
553         Num_CC := 0;
554         Comp   := First_Component_Or_Discriminant (R);
555         while Present (Comp) loop
556            declare
557               CC   : constant Node_Id := Component_Clause (Comp);
558
559            begin
560               --  Collect only component clauses whose last bit is less than
561               --  machine scalar size. Any component clause whose last bit
562               --  exceeds this value does not take part in machine scalar
563               --  layout considerations. The test for Error_Posted makes sure
564               --  we exclude component clauses for which we already posted an
565               --  error.
566
567               if Present (CC)
568                 and then not Error_Posted (Last_Bit (CC))
569                 and then Static_Integer (Last_Bit (CC)) <
570                                              Max_Machine_Scalar_Size
571               then
572                  Num_CC := Num_CC + 1;
573                  Comps (Num_CC) := Comp;
574               end if;
575            end;
576
577            Next_Component_Or_Discriminant (Comp);
578         end loop;
579
580         --  Sort by ascending position number
581
582         Sorting.Sort (Num_CC);
583
584         --  We now have all the components whose size does not exceed the max
585         --  machine scalar value, sorted by starting position. In this loop we
586         --  gather groups of clauses starting at the same position, to process
587         --  them in accordance with AI-133.
588
589         Stop := 0;
590         while Stop < Num_CC loop
591            Start := Stop + 1;
592            Stop  := Start;
593            MaxL  :=
594              Static_Integer
595                (Last_Bit (Component_Clause (Comps (Start))));
596            while Stop < Num_CC loop
597               if Static_Integer
598                    (Position (Component_Clause (Comps (Stop + 1)))) =
599                  Static_Integer
600                    (Position (Component_Clause (Comps (Stop))))
601               then
602                  Stop := Stop + 1;
603                  MaxL :=
604                    UI_Max
605                      (MaxL,
606                       Static_Integer
607                         (Last_Bit
608                            (Component_Clause (Comps (Stop)))));
609               else
610                  exit;
611               end if;
612            end loop;
613
614            --  Now we have a group of component clauses from Start to Stop
615            --  whose positions are identical, and MaxL is the maximum last
616            --  bit value of any of these components.
617
618            --  We need to determine the corresponding machine scalar size.
619            --  This loop assumes that machine scalar sizes are even, and that
620            --  each possible machine scalar has twice as many bits as the next
621            --  smaller one.
622
623            MSS := Max_Machine_Scalar_Size;
624            while MSS mod 2 = 0
625              and then (MSS / 2) >= SSU
626              and then (MSS / 2) > MaxL
627            loop
628               MSS := MSS / 2;
629            end loop;
630
631            --  Here is where we fix up the Component_Bit_Offset value to
632            --  account for the reverse bit order. Some examples of what needs
633            --  to be done for the case of a machine scalar size of 8 are:
634
635            --    First_Bit .. Last_Bit     Component_Bit_Offset
636            --      old          new          old       new
637
638            --     0 .. 0       7 .. 7         0         7
639            --     0 .. 1       6 .. 7         0         6
640            --     0 .. 2       5 .. 7         0         5
641            --     0 .. 7       0 .. 7         0         4
642
643            --     1 .. 1       6 .. 6         1         6
644            --     1 .. 4       3 .. 6         1         3
645            --     4 .. 7       0 .. 3         4         0
646
647            --  The rule is that the first bit is obtained by subtracting the
648            --  old ending bit from machine scalar size - 1.
649
650            for C in Start .. Stop loop
651               declare
652                  Comp : constant Entity_Id := Comps (C);
653                  CC   : constant Node_Id   := Component_Clause (Comp);
654
655                  LB   : constant Uint := Static_Integer (Last_Bit (CC));
656                  NFB  : constant Uint := MSS - Uint_1 - LB;
657                  NLB  : constant Uint := NFB + Esize (Comp) - 1;
658                  Pos  : constant Uint := Static_Integer (Position (CC));
659
660               begin
661                  if Warn_On_Reverse_Bit_Order then
662                     Error_Msg_Uint_1 := MSS;
663                     Error_Msg_N
664                       ("info: reverse bit order in machine scalar of "
665                        & "length^?V?", First_Bit (CC));
666                     Error_Msg_Uint_1 := NFB;
667                     Error_Msg_Uint_2 := NLB;
668
669                     if Bytes_Big_Endian then
670                        Error_Msg_NE
671                          ("\big-endian range for component & is ^ .. ^?V?",
672                           First_Bit (CC), Comp);
673                     else
674                        Error_Msg_NE
675                          ("\little-endian range for component & is ^ .. ^?V?",
676                           First_Bit (CC), Comp);
677                     end if;
678                  end if;
679
680                  Set_Component_Bit_Offset (Comp, Pos * SSU + NFB);
681                  Set_Normalized_Position  (Comp, Pos + NFB / SSU);
682                  Set_Normalized_First_Bit (Comp, NFB mod SSU);
683               end;
684            end loop;
685         end loop;
686      end Sort_CC;
687   end Adjust_Record_For_Reverse_Bit_Order;
688
689   ------------------------------------------------
690   -- Adjust_Record_For_Reverse_Bit_Order_Ada_95 --
691   ------------------------------------------------
692
693   procedure Adjust_Record_For_Reverse_Bit_Order_Ada_95 (R : Entity_Id) is
694      CC   : Node_Id;
695      Comp : Node_Id;
696
697   begin
698      --  For Ada 95, we just renumber bits within a storage unit. We do the
699      --  same for Ada 83 mode, since we recognize the Bit_Order attribute in
700      --  Ada 83, and are free to add this extension.
701
702      Comp := First_Component_Or_Discriminant (R);
703      while Present (Comp) loop
704         CC := Component_Clause (Comp);
705
706         --  If component clause is present, then deal with the non-default
707         --  bit order case for Ada 95 mode.
708
709         --  We only do this processing for the base type, and in fact that
710         --  is important, since otherwise if there are record subtypes, we
711         --  could reverse the bits once for each subtype, which is wrong.
712
713         if Present (CC) and then Ekind (R) = E_Record_Type then
714            declare
715               CFB : constant Uint    := Component_Bit_Offset (Comp);
716               CSZ : constant Uint    := Esize (Comp);
717               CLC : constant Node_Id := Component_Clause (Comp);
718               Pos : constant Node_Id := Position (CLC);
719               FB  : constant Node_Id := First_Bit (CLC);
720
721               Storage_Unit_Offset : constant Uint :=
722                                       CFB / System_Storage_Unit;
723
724               Start_Bit : constant Uint :=
725                             CFB mod System_Storage_Unit;
726
727            begin
728               --  Cases where field goes over storage unit boundary
729
730               if Start_Bit + CSZ > System_Storage_Unit then
731
732                  --  Allow multi-byte field but generate warning
733
734                  if Start_Bit mod System_Storage_Unit = 0
735                    and then CSZ mod System_Storage_Unit = 0
736                  then
737                     Error_Msg_N
738                       ("info: multi-byte field specified with non-standard "
739                        & "Bit_Order?V?", CLC);
740
741                     if Bytes_Big_Endian then
742                        Error_Msg_N
743                          ("\bytes are not reversed "
744                           & "(component is big-endian)?V?", CLC);
745                     else
746                        Error_Msg_N
747                          ("\bytes are not reversed "
748                           & "(component is little-endian)?V?", CLC);
749                     end if;
750
751                  --  Do not allow non-contiguous field
752
753                  else
754                     Error_Msg_N
755                       ("attempt to specify non-contiguous field not "
756                        & "permitted", CLC);
757                     Error_Msg_N
758                       ("\caused by non-standard Bit_Order specified in "
759                        & "legacy Ada 95 mode", CLC);
760                  end if;
761
762               --  Case where field fits in one storage unit
763
764               else
765                  --  Give warning if suspicious component clause
766
767                  if Intval (FB) >= System_Storage_Unit
768                    and then Warn_On_Reverse_Bit_Order
769                  then
770                     Error_Msg_N
771                       ("info: Bit_Order clause does not affect byte "
772                        & "ordering?V?", Pos);
773                     Error_Msg_Uint_1 :=
774                       Intval (Pos) + Intval (FB) /
775                       System_Storage_Unit;
776                     Error_Msg_N
777                       ("info: position normalized to ^ before bit order "
778                        & "interpreted?V?", Pos);
779                  end if;
780
781                  --  Here is where we fix up the Component_Bit_Offset value
782                  --  to account for the reverse bit order. Some examples of
783                  --  what needs to be done are:
784
785                  --    First_Bit .. Last_Bit     Component_Bit_Offset
786                  --      old          new          old       new
787
788                  --     0 .. 0       7 .. 7         0         7
789                  --     0 .. 1       6 .. 7         0         6
790                  --     0 .. 2       5 .. 7         0         5
791                  --     0 .. 7       0 .. 7         0         4
792
793                  --     1 .. 1       6 .. 6         1         6
794                  --     1 .. 4       3 .. 6         1         3
795                  --     4 .. 7       0 .. 3         4         0
796
797                  --  The rule is that the first bit is is obtained by
798                  --  subtracting the old ending bit from storage_unit - 1.
799
800                  Set_Component_Bit_Offset (Comp,
801                    (Storage_Unit_Offset * System_Storage_Unit) +
802                      (System_Storage_Unit - 1) -
803                      (Start_Bit + CSZ - 1));
804
805                  Set_Normalized_Position (Comp,
806                    Component_Bit_Offset (Comp) / System_Storage_Unit);
807
808                  Set_Normalized_First_Bit (Comp,
809                    Component_Bit_Offset (Comp) mod System_Storage_Unit);
810               end if;
811            end;
812         end if;
813
814         Next_Component_Or_Discriminant (Comp);
815      end loop;
816   end Adjust_Record_For_Reverse_Bit_Order_Ada_95;
817
818   -------------------------------------
819   -- Alignment_Check_For_Size_Change --
820   -------------------------------------
821
822   procedure Alignment_Check_For_Size_Change (Typ : Entity_Id; Size : Uint) is
823   begin
824      --  If the alignment is known, and not set by a rep clause, and is
825      --  inconsistent with the size being set, then reset it to unknown,
826      --  we assume in this case that the size overrides the inherited
827      --  alignment, and that the alignment must be recomputed.
828
829      if Known_Alignment (Typ)
830        and then not Has_Alignment_Clause (Typ)
831        and then Size mod (Alignment (Typ) * SSU) /= 0
832      then
833         Init_Alignment (Typ);
834      end if;
835   end Alignment_Check_For_Size_Change;
836
837   -------------------------------------
838   -- Analyze_Aspects_At_Freeze_Point --
839   -------------------------------------
840
841   procedure Analyze_Aspects_At_Freeze_Point (E : Entity_Id) is
842      procedure Analyze_Aspect_Default_Value (ASN : Node_Id);
843      --  This routine analyzes an Aspect_Default_[Component_]Value denoted by
844      --  the aspect specification node ASN.
845
846      procedure Inherit_Delayed_Rep_Aspects (ASN : Node_Id);
847      --  As discussed in the spec of Aspects (see Aspect_Delay declaration),
848      --  a derived type can inherit aspects from its parent which have been
849      --  specified at the time of the derivation using an aspect, as in:
850      --
851      --    type A is range 1 .. 10
852      --      with Size => Not_Defined_Yet;
853      --    ..
854      --    type B is new A;
855      --    ..
856      --    Not_Defined_Yet : constant := 64;
857      --
858      --  In this example, the Size of A is considered to be specified prior
859      --  to the derivation, and thus inherited, even though the value is not
860      --  known at the time of derivation. To deal with this, we use two entity
861      --  flags. The flag Has_Derived_Rep_Aspects is set in the parent type (A
862      --  here), and then the flag May_Inherit_Delayed_Rep_Aspects is set in
863      --  the derived type (B here). If this flag is set when the derived type
864      --  is frozen, then this procedure is called to ensure proper inheritance
865      --  of all delayed aspects from the parent type. The derived type is E,
866      --  the argument to Analyze_Aspects_At_Freeze_Point. ASN is the first
867      --  aspect specification node in the Rep_Item chain for the parent type.
868
869      procedure Make_Pragma_From_Boolean_Aspect (ASN : Node_Id);
870      --  Given an aspect specification node ASN whose expression is an
871      --  optional Boolean, this routines creates the corresponding pragma
872      --  at the freezing point.
873
874      ----------------------------------
875      -- Analyze_Aspect_Default_Value --
876      ----------------------------------
877
878      procedure Analyze_Aspect_Default_Value (ASN : Node_Id) is
879         A_Id : constant Aspect_Id := Get_Aspect_Id (ASN);
880         Ent  : constant Entity_Id := Entity (ASN);
881         Expr : constant Node_Id   := Expression (ASN);
882         Id   : constant Node_Id   := Identifier (ASN);
883
884      begin
885         Error_Msg_Name_1 := Chars (Id);
886
887         if not Is_Type (Ent) then
888            Error_Msg_N ("aspect% can only apply to a type", Id);
889            return;
890
891         elsif not Is_First_Subtype (Ent) then
892            Error_Msg_N ("aspect% cannot apply to subtype", Id);
893            return;
894
895         elsif A_Id = Aspect_Default_Value
896           and then not Is_Scalar_Type (Ent)
897         then
898            Error_Msg_N ("aspect% can only be applied to scalar type", Id);
899            return;
900
901         elsif A_Id = Aspect_Default_Component_Value then
902            if not Is_Array_Type (Ent) then
903               Error_Msg_N ("aspect% can only be applied to array type", Id);
904               return;
905
906            elsif not Is_Scalar_Type (Component_Type (Ent)) then
907               Error_Msg_N ("aspect% requires scalar components", Id);
908               return;
909            end if;
910         end if;
911
912         Set_Has_Default_Aspect (Base_Type (Ent));
913
914         if Is_Scalar_Type (Ent) then
915            Set_Default_Aspect_Value (Base_Type (Ent), Expr);
916         else
917            Set_Default_Aspect_Component_Value (Base_Type (Ent), Expr);
918         end if;
919      end Analyze_Aspect_Default_Value;
920
921      ---------------------------------
922      -- Inherit_Delayed_Rep_Aspects --
923      ---------------------------------
924
925      procedure Inherit_Delayed_Rep_Aspects (ASN : Node_Id) is
926         A_Id : constant Aspect_Id := Get_Aspect_Id (ASN);
927         P    : constant Entity_Id := Entity (ASN);
928         --  Entithy for parent type
929
930         N : Node_Id;
931         --  Item from Rep_Item chain
932
933         A : Aspect_Id;
934
935      begin
936         --  Loop through delayed aspects for the parent type
937
938         N := ASN;
939         while Present (N) loop
940            if Nkind (N) = N_Aspect_Specification then
941               exit when Entity (N) /= P;
942
943               if Is_Delayed_Aspect (N) then
944                  A := Get_Aspect_Id (Chars (Identifier (N)));
945
946                  --  Process delayed rep aspect. For Boolean attributes it is
947                  --  not possible to cancel an attribute once set (the attempt
948                  --  to use an aspect with xxx => False is an error) for a
949                  --  derived type. So for those cases, we do not have to check
950                  --  if a clause has been given for the derived type, since it
951                  --  is harmless to set it again if it is already set.
952
953                  case A is
954
955                     --  Alignment
956
957                     when Aspect_Alignment =>
958                        if not Has_Alignment_Clause (E) then
959                           Set_Alignment (E, Alignment (P));
960                        end if;
961
962                     --  Atomic
963
964                     when Aspect_Atomic =>
965                        if Is_Atomic (P) then
966                           Set_Is_Atomic (E);
967                        end if;
968
969                     --  Atomic_Components
970
971                     when Aspect_Atomic_Components =>
972                        if Has_Atomic_Components (P) then
973                           Set_Has_Atomic_Components (Base_Type (E));
974                        end if;
975
976                     --  Bit_Order
977
978                     when Aspect_Bit_Order =>
979                        if Is_Record_Type (E)
980                          and then No (Get_Attribute_Definition_Clause
981                                         (E, Attribute_Bit_Order))
982                          and then Reverse_Bit_Order (P)
983                        then
984                           Set_Reverse_Bit_Order (Base_Type (E));
985                        end if;
986
987                     --  Component_Size
988
989                     when Aspect_Component_Size =>
990                        if Is_Array_Type (E)
991                          and then not Has_Component_Size_Clause (E)
992                        then
993                           Set_Component_Size
994                             (Base_Type (E), Component_Size (P));
995                        end if;
996
997                     --  Machine_Radix
998
999                     when Aspect_Machine_Radix =>
1000                        if Is_Decimal_Fixed_Point_Type (E)
1001                          and then not Has_Machine_Radix_Clause (E)
1002                        then
1003                           Set_Machine_Radix_10 (E, Machine_Radix_10 (P));
1004                        end if;
1005
1006                     --  Object_Size (also Size which also sets Object_Size)
1007
1008                     when Aspect_Object_Size
1009                        | Aspect_Size
1010                     =>
1011                        if not Has_Size_Clause (E)
1012                          and then
1013                            No (Get_Attribute_Definition_Clause
1014                                  (E, Attribute_Object_Size))
1015                        then
1016                           Set_Esize (E, Esize (P));
1017                        end if;
1018
1019                     --  Pack
1020
1021                     when Aspect_Pack =>
1022                        if not Is_Packed (E) then
1023                           Set_Is_Packed (Base_Type (E));
1024
1025                           if Is_Bit_Packed_Array (P) then
1026                              Set_Is_Bit_Packed_Array (Base_Type (E));
1027                              Set_Packed_Array_Impl_Type
1028                                (E, Packed_Array_Impl_Type (P));
1029                           end if;
1030                        end if;
1031
1032                     --  Scalar_Storage_Order
1033
1034                     when Aspect_Scalar_Storage_Order =>
1035                        if (Is_Record_Type (E) or else Is_Array_Type (E))
1036                          and then No (Get_Attribute_Definition_Clause
1037                                         (E, Attribute_Scalar_Storage_Order))
1038                          and then Reverse_Storage_Order (P)
1039                        then
1040                           Set_Reverse_Storage_Order (Base_Type (E));
1041
1042                           --  Clear default SSO indications, since the aspect
1043                           --  overrides the default.
1044
1045                           Set_SSO_Set_Low_By_Default  (Base_Type (E), False);
1046                           Set_SSO_Set_High_By_Default (Base_Type (E), False);
1047                        end if;
1048
1049                     --  Small
1050
1051                     when Aspect_Small =>
1052                        if Is_Fixed_Point_Type (E)
1053                          and then not Has_Small_Clause (E)
1054                        then
1055                           Set_Small_Value (E, Small_Value (P));
1056                        end if;
1057
1058                     --  Storage_Size
1059
1060                     when Aspect_Storage_Size =>
1061                        if (Is_Access_Type (E) or else Is_Task_Type (E))
1062                          and then not Has_Storage_Size_Clause (E)
1063                        then
1064                           Set_Storage_Size_Variable
1065                             (Base_Type (E), Storage_Size_Variable (P));
1066                        end if;
1067
1068                     --  Value_Size
1069
1070                     when Aspect_Value_Size =>
1071
1072                        --  Value_Size is never inherited, it is either set by
1073                        --  default, or it is explicitly set for the derived
1074                        --  type. So nothing to do here.
1075
1076                        null;
1077
1078                     --  Volatile
1079
1080                     when Aspect_Volatile =>
1081                        if Is_Volatile (P) then
1082                           Set_Is_Volatile (E);
1083                        end if;
1084
1085                     --  Volatile_Full_Access
1086
1087                     when Aspect_Volatile_Full_Access =>
1088                        if Is_Volatile_Full_Access (P) then
1089                           Set_Is_Volatile_Full_Access (E);
1090                        end if;
1091
1092                     --  Volatile_Components
1093
1094                     when Aspect_Volatile_Components =>
1095                        if Has_Volatile_Components (P) then
1096                           Set_Has_Volatile_Components (Base_Type (E));
1097                        end if;
1098
1099                     --  That should be all the Rep Aspects
1100
1101                     when others =>
1102                        pragma Assert (Aspect_Delay (A_Id) /= Rep_Aspect);
1103                        null;
1104                  end case;
1105               end if;
1106            end if;
1107
1108            N := Next_Rep_Item (N);
1109         end loop;
1110      end Inherit_Delayed_Rep_Aspects;
1111
1112      -------------------------------------
1113      -- Make_Pragma_From_Boolean_Aspect --
1114      -------------------------------------
1115
1116      procedure Make_Pragma_From_Boolean_Aspect (ASN : Node_Id) is
1117         Ident  : constant Node_Id    := Identifier (ASN);
1118         A_Name : constant Name_Id    := Chars (Ident);
1119         A_Id   : constant Aspect_Id  := Get_Aspect_Id (A_Name);
1120         Ent    : constant Entity_Id  := Entity (ASN);
1121         Expr   : constant Node_Id    := Expression (ASN);
1122         Loc    : constant Source_Ptr := Sloc (ASN);
1123
1124         procedure Check_False_Aspect_For_Derived_Type;
1125         --  This procedure checks for the case of a false aspect for a derived
1126         --  type, which improperly tries to cancel an aspect inherited from
1127         --  the parent.
1128
1129         -----------------------------------------
1130         -- Check_False_Aspect_For_Derived_Type --
1131         -----------------------------------------
1132
1133         procedure Check_False_Aspect_For_Derived_Type is
1134            Par : Node_Id;
1135
1136         begin
1137            --  We are only checking derived types
1138
1139            if not Is_Derived_Type (E) then
1140               return;
1141            end if;
1142
1143            Par := Nearest_Ancestor (E);
1144
1145            case A_Id is
1146               when Aspect_Atomic
1147                  | Aspect_Shared
1148               =>
1149                  if not Is_Atomic (Par) then
1150                     return;
1151                  end if;
1152
1153               when Aspect_Atomic_Components =>
1154                  if not Has_Atomic_Components (Par) then
1155                     return;
1156                  end if;
1157
1158               when Aspect_Discard_Names =>
1159                  if not Discard_Names (Par) then
1160                     return;
1161                  end if;
1162
1163               when Aspect_Pack =>
1164                  if not Is_Packed (Par) then
1165                     return;
1166                  end if;
1167
1168               when Aspect_Unchecked_Union =>
1169                  if not Is_Unchecked_Union (Par) then
1170                     return;
1171                  end if;
1172
1173               when Aspect_Volatile =>
1174                  if not Is_Volatile (Par) then
1175                     return;
1176                  end if;
1177
1178               when Aspect_Volatile_Components =>
1179                  if not Has_Volatile_Components (Par) then
1180                     return;
1181                  end if;
1182
1183               when Aspect_Volatile_Full_Access =>
1184                  if not Is_Volatile_Full_Access (Par) then
1185                     return;
1186                  end if;
1187
1188               when others =>
1189                  return;
1190            end case;
1191
1192            --  Fall through means we are canceling an inherited aspect
1193
1194            Error_Msg_Name_1 := A_Name;
1195            Error_Msg_NE
1196              ("derived type& inherits aspect%, cannot cancel", Expr, E);
1197         end Check_False_Aspect_For_Derived_Type;
1198
1199         --  Local variables
1200
1201         Prag : Node_Id;
1202
1203      --  Start of processing for Make_Pragma_From_Boolean_Aspect
1204
1205      begin
1206         --  Note that we know Expr is present, because for a missing Expr
1207         --  argument, we knew it was True and did not need to delay the
1208         --  evaluation to the freeze point.
1209
1210         if Is_False (Static_Boolean (Expr)) then
1211            Check_False_Aspect_For_Derived_Type;
1212
1213         else
1214            Prag :=
1215              Make_Pragma (Loc,
1216                Pragma_Identifier            =>
1217                  Make_Identifier (Sloc (Ident), Chars (Ident)),
1218                Pragma_Argument_Associations => New_List (
1219                  Make_Pragma_Argument_Association (Sloc (Ident),
1220                    Expression => New_Occurrence_Of (Ent, Sloc (Ident)))));
1221
1222            Set_From_Aspect_Specification (Prag, True);
1223            Set_Corresponding_Aspect (Prag, ASN);
1224            Set_Aspect_Rep_Item (ASN, Prag);
1225            Set_Is_Delayed_Aspect (Prag);
1226            Set_Parent (Prag, ASN);
1227         end if;
1228      end Make_Pragma_From_Boolean_Aspect;
1229
1230      --  Local variables
1231
1232      A_Id  : Aspect_Id;
1233      ASN   : Node_Id;
1234      Ritem : Node_Id;
1235
1236   --  Start of processing for Analyze_Aspects_At_Freeze_Point
1237
1238   begin
1239      --  Must be visible in current scope, but if this is a type from a nested
1240      --  package it may be frozen from an object declaration in the enclosing
1241      --  scope, so install the package declarations to complete the analysis
1242      --  of the aspects, if any. If the package itself is frozen the type will
1243      --  have been frozen as well.
1244
1245      if not Scope_Within_Or_Same (Current_Scope, Scope (E)) then
1246         if Is_Type (E) and then From_Nested_Package (E) then
1247            declare
1248               Pack : constant Entity_Id := Scope (E);
1249
1250            begin
1251               Push_Scope (Pack);
1252               Install_Visible_Declarations (Pack);
1253               Install_Private_Declarations (Pack);
1254               Analyze_Aspects_At_Freeze_Point (E);
1255
1256               if Is_Private_Type (E)
1257                 and then Present (Full_View (E))
1258               then
1259                  Analyze_Aspects_At_Freeze_Point (Full_View (E));
1260               end if;
1261
1262               End_Package_Scope (Pack);
1263               return;
1264            end;
1265
1266         --  Aspects from other entities in different contexts are analyzed
1267         --  elsewhere.
1268
1269         else
1270            return;
1271         end if;
1272      end if;
1273
1274      --  Look for aspect specification entries for this entity
1275
1276      ASN := First_Rep_Item (E);
1277      while Present (ASN) loop
1278         if Nkind (ASN) = N_Aspect_Specification then
1279            exit when Entity (ASN) /= E;
1280
1281            if Is_Delayed_Aspect (ASN) then
1282               A_Id := Get_Aspect_Id (ASN);
1283
1284               case A_Id is
1285
1286                  --  For aspects whose expression is an optional Boolean, make
1287                  --  the corresponding pragma at the freeze point.
1288
1289                  when Boolean_Aspects
1290                     | Library_Unit_Aspects
1291                  =>
1292                     --  Aspects Export and Import require special handling.
1293                     --  Both are by definition Boolean and may benefit from
1294                     --  forward references, however their expressions are
1295                     --  treated as static. In addition, the syntax of their
1296                     --  corresponding pragmas requires extra "pieces" which
1297                     --  may also contain forward references. To account for
1298                     --  all of this, the corresponding pragma is created by
1299                     --  Analyze_Aspect_Export_Import, but is not analyzed as
1300                     --  the complete analysis must happen now.
1301
1302                     if A_Id = Aspect_Export or else A_Id = Aspect_Import then
1303                        null;
1304
1305                     --  Otherwise create a corresponding pragma
1306
1307                     else
1308                        Make_Pragma_From_Boolean_Aspect (ASN);
1309                     end if;
1310
1311                  --  Special handling for aspects that don't correspond to
1312                  --  pragmas/attributes.
1313
1314                  when Aspect_Default_Value
1315                     | Aspect_Default_Component_Value
1316                  =>
1317                     --  Do not inherit aspect for anonymous base type of a
1318                     --  scalar or array type, because they apply to the first
1319                     --  subtype of the type, and will be processed when that
1320                     --  first subtype is frozen.
1321
1322                     if Is_Derived_Type (E)
1323                       and then not Comes_From_Source (E)
1324                       and then E /= First_Subtype (E)
1325                     then
1326                        null;
1327                     else
1328                        Analyze_Aspect_Default_Value (ASN);
1329                     end if;
1330
1331                  --  Ditto for iterator aspects, because the corresponding
1332                  --  attributes may not have been analyzed yet.
1333
1334                  when Aspect_Constant_Indexing
1335                     | Aspect_Default_Iterator
1336                     | Aspect_Iterator_Element
1337                     | Aspect_Variable_Indexing
1338                  =>
1339                     Analyze (Expression (ASN));
1340
1341                     if Etype (Expression (ASN)) = Any_Type then
1342                        Error_Msg_NE
1343                          ("\aspect must be fully defined before & is frozen",
1344                           ASN, E);
1345                     end if;
1346
1347                  when Aspect_Iterable =>
1348                     Validate_Iterable_Aspect (E, ASN);
1349
1350                  when others =>
1351                     null;
1352               end case;
1353
1354               Ritem := Aspect_Rep_Item (ASN);
1355
1356               if Present (Ritem) then
1357                  Analyze (Ritem);
1358               end if;
1359            end if;
1360         end if;
1361
1362         Next_Rep_Item (ASN);
1363      end loop;
1364
1365      --  This is where we inherit delayed rep aspects from our parent. Note
1366      --  that if we fell out of the above loop with ASN non-empty, it means
1367      --  we hit an aspect for an entity other than E, and it must be the
1368      --  type from which we were derived.
1369
1370      if May_Inherit_Delayed_Rep_Aspects (E) then
1371         Inherit_Delayed_Rep_Aspects (ASN);
1372      end if;
1373
1374      if In_Instance
1375        and then E /= Base_Type (E)
1376        and then Is_First_Subtype (E)
1377      then
1378         Inherit_Rep_Item_Chain (Base_Type (E), E);
1379      end if;
1380   end Analyze_Aspects_At_Freeze_Point;
1381
1382   -----------------------------------
1383   -- Analyze_Aspect_Specifications --
1384   -----------------------------------
1385
1386   procedure Analyze_Aspect_Specifications (N : Node_Id; E : Entity_Id) is
1387      pragma Assert (Present (E));
1388
1389      procedure Decorate (Asp : Node_Id; Prag : Node_Id);
1390      --  Establish linkages between an aspect and its corresponding pragma
1391
1392      procedure Insert_Pragma
1393        (Prag        : Node_Id;
1394         Is_Instance : Boolean := False);
1395      --  Subsidiary to the analysis of aspects
1396      --    Abstract_State
1397      --    Attach_Handler
1398      --    Contract_Cases
1399      --    Depends
1400      --    Ghost
1401      --    Global
1402      --    Initial_Condition
1403      --    Initializes
1404      --    Post
1405      --    Pre
1406      --    Refined_Depends
1407      --    Refined_Global
1408      --    Refined_State
1409      --    SPARK_Mode
1410      --    Warnings
1411      --  Insert pragma Prag such that it mimics the placement of a source
1412      --  pragma of the same kind. Flag Is_Generic should be set when the
1413      --  context denotes a generic instance.
1414
1415      --------------
1416      -- Decorate --
1417      --------------
1418
1419      procedure Decorate (Asp : Node_Id; Prag : Node_Id) is
1420      begin
1421         Set_Aspect_Rep_Item           (Asp, Prag);
1422         Set_Corresponding_Aspect      (Prag, Asp);
1423         Set_From_Aspect_Specification (Prag);
1424         Set_Parent                    (Prag, Asp);
1425      end Decorate;
1426
1427      -------------------
1428      -- Insert_Pragma --
1429      -------------------
1430
1431      procedure Insert_Pragma
1432        (Prag        : Node_Id;
1433         Is_Instance : Boolean := False)
1434      is
1435         Aux      : Node_Id;
1436         Decl     : Node_Id;
1437         Decls    : List_Id;
1438         Def      : Node_Id;
1439         Inserted : Boolean := False;
1440
1441      begin
1442         --  When the aspect appears on an entry, package, protected unit,
1443         --  subprogram, or task unit body, insert the generated pragma at the
1444         --  top of the body declarations to emulate the behavior of a source
1445         --  pragma.
1446
1447         --    package body Pack with Aspect is
1448
1449         --    package body Pack is
1450         --       pragma Prag;
1451
1452         if Nkind_In (N, N_Entry_Body,
1453                         N_Package_Body,
1454                         N_Protected_Body,
1455                         N_Subprogram_Body,
1456                         N_Task_Body)
1457         then
1458            Decls := Declarations (N);
1459
1460            if No (Decls) then
1461               Decls := New_List;
1462               Set_Declarations (N, Decls);
1463            end if;
1464
1465            Prepend_To (Decls, Prag);
1466
1467         --  When the aspect is associated with a [generic] package declaration
1468         --  insert the generated pragma at the top of the visible declarations
1469         --  to emulate the behavior of a source pragma.
1470
1471         --    package Pack with Aspect is
1472
1473         --    package Pack is
1474         --       pragma Prag;
1475
1476         elsif Nkind_In (N, N_Generic_Package_Declaration,
1477                            N_Package_Declaration)
1478         then
1479            Decls := Visible_Declarations (Specification (N));
1480
1481            if No (Decls) then
1482               Decls := New_List;
1483               Set_Visible_Declarations (Specification (N), Decls);
1484            end if;
1485
1486            --  The visible declarations of a generic instance have the
1487            --  following structure:
1488
1489            --    <renamings of generic formals>
1490            --    <renamings of internally-generated spec and body>
1491            --    <first source declaration>
1492
1493            --  Insert the pragma before the first source declaration by
1494            --  skipping the instance "header" to ensure proper visibility of
1495            --  all formals.
1496
1497            if Is_Instance then
1498               Decl := First (Decls);
1499               while Present (Decl) loop
1500                  if Comes_From_Source (Decl) then
1501                     Insert_Before (Decl, Prag);
1502                     Inserted := True;
1503                     exit;
1504                  else
1505                     Next (Decl);
1506                  end if;
1507               end loop;
1508
1509               --  The pragma is placed after the instance "header"
1510
1511               if not Inserted then
1512                  Append_To (Decls, Prag);
1513               end if;
1514
1515            --  Otherwise this is not a generic instance
1516
1517            else
1518               Prepend_To (Decls, Prag);
1519            end if;
1520
1521         --  When the aspect is associated with a protected unit declaration,
1522         --  insert the generated pragma at the top of the visible declarations
1523         --  the emulate the behavior of a source pragma.
1524
1525         --    protected [type] Prot with Aspect is
1526
1527         --    protected [type] Prot is
1528         --       pragma Prag;
1529
1530         elsif Nkind (N) = N_Protected_Type_Declaration then
1531            Def := Protected_Definition (N);
1532
1533            if No (Def) then
1534               Def :=
1535                 Make_Protected_Definition (Sloc (N),
1536                   Visible_Declarations => New_List,
1537                   End_Label            => Empty);
1538
1539               Set_Protected_Definition (N, Def);
1540            end if;
1541
1542            Decls := Visible_Declarations (Def);
1543
1544            if No (Decls) then
1545               Decls := New_List;
1546               Set_Visible_Declarations (Def, Decls);
1547            end if;
1548
1549            Prepend_To (Decls, Prag);
1550
1551         --  When the aspect is associated with a task unit declaration, insert
1552         --  insert the generated pragma at the top of the visible declarations
1553         --  the emulate the behavior of a source pragma.
1554
1555         --    task [type] Prot with Aspect is
1556
1557         --    task [type] Prot is
1558         --       pragma Prag;
1559
1560         elsif Nkind (N) = N_Task_Type_Declaration then
1561            Def := Task_Definition (N);
1562
1563            if No (Def) then
1564               Def :=
1565                 Make_Task_Definition (Sloc (N),
1566                   Visible_Declarations => New_List,
1567                   End_Label            => Empty);
1568
1569               Set_Task_Definition (N, Def);
1570            end if;
1571
1572            Decls := Visible_Declarations (Def);
1573
1574            if No (Decls) then
1575               Decls := New_List;
1576               Set_Visible_Declarations (Def, Decls);
1577            end if;
1578
1579            Prepend_To (Decls, Prag);
1580
1581         --  When the context is a library unit, the pragma is added to the
1582         --  Pragmas_After list.
1583
1584         elsif Nkind (Parent (N)) = N_Compilation_Unit then
1585            Aux := Aux_Decls_Node (Parent (N));
1586
1587            if No (Pragmas_After (Aux)) then
1588               Set_Pragmas_After (Aux, New_List);
1589            end if;
1590
1591            Prepend (Prag, Pragmas_After (Aux));
1592
1593         --  Default, the pragma is inserted after the context
1594
1595         else
1596            Insert_After (N, Prag);
1597         end if;
1598      end Insert_Pragma;
1599
1600      --  Local variables
1601
1602      Aspect : Node_Id;
1603      Aitem  : Node_Id;
1604      Ent    : Node_Id;
1605
1606      L : constant List_Id := Aspect_Specifications (N);
1607      pragma Assert (Present (L));
1608
1609      Ins_Node : Node_Id := N;
1610      --  Insert pragmas/attribute definition clause after this node when no
1611      --  delayed analysis is required.
1612
1613   --  Start of processing for Analyze_Aspect_Specifications
1614
1615   begin
1616      --  The general processing involves building an attribute definition
1617      --  clause or a pragma node that corresponds to the aspect. Then in order
1618      --  to delay the evaluation of this aspect to the freeze point, we attach
1619      --  the corresponding pragma/attribute definition clause to the aspect
1620      --  specification node, which is then placed in the Rep Item chain. In
1621      --  this case we mark the entity by setting the flag Has_Delayed_Aspects
1622      --  and we evaluate the rep item at the freeze point. When the aspect
1623      --  doesn't have a corresponding pragma/attribute definition clause, then
1624      --  its analysis is simply delayed at the freeze point.
1625
1626      --  Some special cases don't require delay analysis, thus the aspect is
1627      --  analyzed right now.
1628
1629      --  Note that there is a special handling for Pre, Post, Test_Case,
1630      --  Contract_Cases aspects. In these cases, we do not have to worry
1631      --  about delay issues, since the pragmas themselves deal with delay
1632      --  of visibility for the expression analysis. Thus, we just insert
1633      --  the pragma after the node N.
1634
1635      --  Loop through aspects
1636
1637      Aspect := First (L);
1638      Aspect_Loop : while Present (Aspect) loop
1639         Analyze_One_Aspect : declare
1640            Expr : constant Node_Id    := Expression (Aspect);
1641            Id   : constant Node_Id    := Identifier (Aspect);
1642            Loc  : constant Source_Ptr := Sloc (Aspect);
1643            Nam  : constant Name_Id    := Chars (Id);
1644            A_Id : constant Aspect_Id  := Get_Aspect_Id (Nam);
1645            Anod : Node_Id;
1646
1647            Delay_Required : Boolean;
1648            --  Set False if delay is not required
1649
1650            Eloc : Source_Ptr := No_Location;
1651            --  Source location of expression, modified when we split PPC's. It
1652            --  is set below when Expr is present.
1653
1654            procedure Analyze_Aspect_Convention;
1655            --  Perform analysis of aspect Convention
1656
1657            procedure Analyze_Aspect_Disable_Controlled;
1658            --  Perform analysis of aspect Disable_Controlled
1659
1660            procedure Analyze_Aspect_Export_Import;
1661            --  Perform analysis of aspects Export or Import
1662
1663            procedure Analyze_Aspect_External_Link_Name;
1664            --  Perform analysis of aspects External_Name or Link_Name
1665
1666            procedure Analyze_Aspect_Implicit_Dereference;
1667            --  Perform analysis of the Implicit_Dereference aspects
1668
1669            procedure Make_Aitem_Pragma
1670              (Pragma_Argument_Associations : List_Id;
1671               Pragma_Name                  : Name_Id);
1672            --  This is a wrapper for Make_Pragma used for converting aspects
1673            --  to pragmas. It takes care of Sloc (set from Loc) and building
1674            --  the pragma identifier from the given name. In addition the
1675            --  flags Class_Present and Split_PPC are set from the aspect
1676            --  node, as well as Is_Ignored. This routine also sets the
1677            --  From_Aspect_Specification in the resulting pragma node to
1678            --  True, and sets Corresponding_Aspect to point to the aspect.
1679            --  The resulting pragma is assigned to Aitem.
1680
1681            -------------------------------
1682            -- Analyze_Aspect_Convention --
1683            -------------------------------
1684
1685            procedure Analyze_Aspect_Convention is
1686               Conv    : Node_Id;
1687               Dummy_1 : Node_Id;
1688               Dummy_2 : Node_Id;
1689               Dummy_3 : Node_Id;
1690               Expo    : Node_Id;
1691               Imp     : Node_Id;
1692
1693            begin
1694               --  Obtain all interfacing aspects that apply to the related
1695               --  entity.
1696
1697               Get_Interfacing_Aspects
1698                 (Iface_Asp => Aspect,
1699                  Conv_Asp  => Dummy_1,
1700                  EN_Asp    => Dummy_2,
1701                  Expo_Asp  => Expo,
1702                  Imp_Asp   => Imp,
1703                  LN_Asp    => Dummy_3,
1704                  Do_Checks => True);
1705
1706               --  The related entity is subject to aspect Export or Import.
1707               --  Do not process Convention now because it must be analysed
1708               --  as part of Export or Import.
1709
1710               if Present (Expo) or else Present (Imp) then
1711                  return;
1712
1713               --  Otherwise Convention appears by itself
1714
1715               else
1716                  --  The aspect specifies a particular convention
1717
1718                  if Present (Expr) then
1719                     Conv := New_Copy_Tree (Expr);
1720
1721                  --  Otherwise assume convention Ada
1722
1723                  else
1724                     Conv := Make_Identifier (Loc, Name_Ada);
1725                  end if;
1726
1727                  --  Generate:
1728                  --    pragma Convention (<Conv>, <E>);
1729
1730                  Make_Aitem_Pragma
1731                    (Pragma_Name => Name_Convention,
1732                     Pragma_Argument_Associations => New_List (
1733                       Make_Pragma_Argument_Association (Loc,
1734                         Expression => Conv),
1735                       Make_Pragma_Argument_Association (Loc,
1736                         Expression => New_Occurrence_Of (E, Loc))));
1737
1738                  Decorate (Aspect, Aitem);
1739                  Insert_Pragma (Aitem);
1740               end if;
1741            end Analyze_Aspect_Convention;
1742
1743            ---------------------------------------
1744            -- Analyze_Aspect_Disable_Controlled --
1745            ---------------------------------------
1746
1747            procedure Analyze_Aspect_Disable_Controlled is
1748            begin
1749               --  The aspect applies only to controlled records
1750
1751               if not (Ekind (E) = E_Record_Type
1752                        and then Is_Controlled_Active (E))
1753               then
1754                  Error_Msg_N
1755                    ("aspect % requires controlled record type", Aspect);
1756                  return;
1757               end if;
1758
1759               --  Preanalyze the expression (if any) when the aspect resides
1760               --  in a generic unit.
1761
1762               if Inside_A_Generic then
1763                  if Present (Expr) then
1764                     Preanalyze_And_Resolve (Expr, Any_Boolean);
1765                  end if;
1766
1767               --  Otherwise the aspect resides in a nongeneric context
1768
1769               else
1770                  --  A controlled record type loses its controlled semantics
1771                  --  when the expression statically evaluates to True.
1772
1773                  if Present (Expr) then
1774                     Analyze_And_Resolve (Expr, Any_Boolean);
1775
1776                     if Is_OK_Static_Expression (Expr) then
1777                        if Is_True (Static_Boolean (Expr)) then
1778                           Set_Disable_Controlled (E);
1779                        end if;
1780
1781                     --  Otherwise the expression is not static
1782
1783                     else
1784                        Error_Msg_N
1785                          ("expression of aspect % must be static", Aspect);
1786                     end if;
1787
1788                  --  Otherwise the aspect appears without an expression and
1789                  --  defaults to True.
1790
1791                  else
1792                     Set_Disable_Controlled (E);
1793                  end if;
1794               end if;
1795            end Analyze_Aspect_Disable_Controlled;
1796
1797            ----------------------------------
1798            -- Analyze_Aspect_Export_Import --
1799            ----------------------------------
1800
1801            procedure Analyze_Aspect_Export_Import is
1802               Dummy_1 : Node_Id;
1803               Dummy_2 : Node_Id;
1804               Dummy_3 : Node_Id;
1805               Expo    : Node_Id;
1806               Imp     : Node_Id;
1807
1808            begin
1809               --  Obtain all interfacing aspects that apply to the related
1810               --  entity.
1811
1812               Get_Interfacing_Aspects
1813                 (Iface_Asp => Aspect,
1814                  Conv_Asp  => Dummy_1,
1815                  EN_Asp    => Dummy_2,
1816                  Expo_Asp  => Expo,
1817                  Imp_Asp   => Imp,
1818                  LN_Asp    => Dummy_3,
1819                  Do_Checks => True);
1820
1821               --  The related entity cannot be subject to both aspects Export
1822               --  and Import.
1823
1824               if Present (Expo) and then Present (Imp) then
1825                  Error_Msg_N
1826                    ("incompatible interfacing aspects given for &", E);
1827                  Error_Msg_Sloc := Sloc (Expo);
1828                  Error_Msg_N ("\aspect `Export` #", E);
1829                  Error_Msg_Sloc := Sloc (Imp);
1830                  Error_Msg_N ("\aspect `Import` #", E);
1831               end if;
1832
1833               --  A variable is most likely modified from the outside. Take
1834               --  the optimistic approach to avoid spurious errors.
1835
1836               if Ekind (E) = E_Variable then
1837                  Set_Never_Set_In_Source (E, False);
1838               end if;
1839
1840               --  Resolve the expression of an Import or Export here, and
1841               --  require it to be of type Boolean and static. This is not
1842               --  quite right, because in general this should be delayed,
1843               --  but that seems tricky for these, because normally Boolean
1844               --  aspects are replaced with pragmas at the freeze point in
1845               --  Make_Pragma_From_Boolean_Aspect.
1846
1847               if not Present (Expr)
1848                 or else Is_True (Static_Boolean (Expr))
1849               then
1850                  if A_Id = Aspect_Import then
1851                     Set_Has_Completion (E);
1852                     Set_Is_Imported (E);
1853
1854                     --  An imported object cannot be explicitly initialized
1855
1856                     if Nkind (N) = N_Object_Declaration
1857                       and then Present (Expression (N))
1858                     then
1859                        Error_Msg_N
1860                          ("imported entities cannot be initialized "
1861                           & "(RM B.1(24))", Expression (N));
1862                     end if;
1863
1864                  else
1865                     pragma Assert (A_Id = Aspect_Export);
1866                     Set_Is_Exported (E);
1867                  end if;
1868
1869                  --  Create the proper form of pragma Export or Import taking
1870                  --  into account Conversion, External_Name, and Link_Name.
1871
1872                  Aitem := Build_Export_Import_Pragma (Aspect, E);
1873
1874               --  Otherwise the expression is either False or erroneous. There
1875               --  is no corresponding pragma.
1876
1877               else
1878                  Aitem := Empty;
1879               end if;
1880            end Analyze_Aspect_Export_Import;
1881
1882            ---------------------------------------
1883            -- Analyze_Aspect_External_Link_Name --
1884            ---------------------------------------
1885
1886            procedure Analyze_Aspect_External_Link_Name is
1887               Dummy_1 : Node_Id;
1888               Dummy_2 : Node_Id;
1889               Dummy_3 : Node_Id;
1890               Expo    : Node_Id;
1891               Imp     : Node_Id;
1892
1893            begin
1894               --  Obtain all interfacing aspects that apply to the related
1895               --  entity.
1896
1897               Get_Interfacing_Aspects
1898                 (Iface_Asp => Aspect,
1899                  Conv_Asp  => Dummy_1,
1900                  EN_Asp    => Dummy_2,
1901                  Expo_Asp  => Expo,
1902                  Imp_Asp   => Imp,
1903                  LN_Asp    => Dummy_3,
1904                  Do_Checks => True);
1905
1906               --  Ensure that aspect External_Name applies to aspect Export or
1907               --  Import.
1908
1909               if A_Id = Aspect_External_Name then
1910                  if No (Expo) and then No (Imp) then
1911                     Error_Msg_N
1912                       ("aspect `External_Name` requires aspect `Import` or "
1913                        & "`Export`", Aspect);
1914                  end if;
1915
1916               --  Otherwise ensure that aspect Link_Name applies to aspect
1917               --  Export or Import.
1918
1919               else
1920                  pragma Assert (A_Id = Aspect_Link_Name);
1921                  if No (Expo) and then No (Imp) then
1922                     Error_Msg_N
1923                       ("aspect `Link_Name` requires aspect `Import` or "
1924                        & "`Export`", Aspect);
1925                  end if;
1926               end if;
1927            end Analyze_Aspect_External_Link_Name;
1928
1929            -----------------------------------------
1930            -- Analyze_Aspect_Implicit_Dereference --
1931            -----------------------------------------
1932
1933            procedure Analyze_Aspect_Implicit_Dereference is
1934            begin
1935               if not Is_Type (E) or else not Has_Discriminants (E) then
1936                  Error_Msg_N
1937                    ("aspect must apply to a type with discriminants", Expr);
1938
1939               elsif not Is_Entity_Name (Expr) then
1940                  Error_Msg_N
1941                    ("aspect must name a discriminant of current type", Expr);
1942
1943               else
1944                  --  Discriminant type be an anonymous access type or an
1945                  --  anonymous access to subprogram.
1946
1947                  --  Missing synchronized types???
1948
1949                  declare
1950                     Disc : Entity_Id := First_Discriminant (E);
1951                  begin
1952                     while Present (Disc) loop
1953                        if Chars (Expr) = Chars (Disc)
1954                          and then Ekind_In
1955                            (Etype (Disc),
1956                             E_Anonymous_Access_Subprogram_Type,
1957                             E_Anonymous_Access_Type)
1958                        then
1959                           Set_Has_Implicit_Dereference (E);
1960                           Set_Has_Implicit_Dereference (Disc);
1961                           exit;
1962                        end if;
1963
1964                        Next_Discriminant (Disc);
1965                     end loop;
1966
1967                     --  Error if no proper access discriminant
1968
1969                     if Present (Disc) then
1970                        --  For a type extension, check whether parent has
1971                        --  a reference discriminant, to verify that use is
1972                        --  proper.
1973
1974                        if Is_Derived_Type (E)
1975                          and then Has_Discriminants (Etype (E))
1976                        then
1977                           declare
1978                              Parent_Disc : constant Entity_Id :=
1979                                Get_Reference_Discriminant (Etype (E));
1980                           begin
1981                              if Present (Parent_Disc)
1982                                and then Corresponding_Discriminant (Disc) /=
1983                                           Parent_Disc
1984                              then
1985                                 Error_Msg_N
1986                                   ("reference discriminant does not match "
1987                                      & "discriminant of parent type", Expr);
1988                              end if;
1989                           end;
1990                        end if;
1991
1992                     else
1993                        Error_Msg_NE
1994                          ("not an access discriminant of&", Expr, E);
1995                     end if;
1996                  end;
1997               end if;
1998
1999            end Analyze_Aspect_Implicit_Dereference;
2000
2001            -----------------------
2002            -- Make_Aitem_Pragma --
2003            -----------------------
2004
2005            procedure Make_Aitem_Pragma
2006              (Pragma_Argument_Associations : List_Id;
2007               Pragma_Name                  : Name_Id)
2008            is
2009               Args : List_Id := Pragma_Argument_Associations;
2010
2011            begin
2012               --  We should never get here if aspect was disabled
2013
2014               pragma Assert (not Is_Disabled (Aspect));
2015
2016               --  Certain aspects allow for an optional name or expression. Do
2017               --  not generate a pragma with empty argument association list.
2018
2019               if No (Args) or else No (Expression (First (Args))) then
2020                  Args := No_List;
2021               end if;
2022
2023               --  Build the pragma
2024
2025               Aitem :=
2026                 Make_Pragma (Loc,
2027                   Pragma_Argument_Associations => Args,
2028                   Pragma_Identifier =>
2029                     Make_Identifier (Sloc (Id), Pragma_Name),
2030                   Class_Present     => Class_Present (Aspect),
2031                   Split_PPC         => Split_PPC (Aspect));
2032
2033               --  Set additional semantic fields
2034
2035               if Is_Ignored (Aspect) then
2036                  Set_Is_Ignored (Aitem);
2037               elsif Is_Checked (Aspect) then
2038                  Set_Is_Checked (Aitem);
2039               end if;
2040
2041               Set_Corresponding_Aspect (Aitem, Aspect);
2042               Set_From_Aspect_Specification (Aitem);
2043            end Make_Aitem_Pragma;
2044
2045         --  Start of processing for Analyze_One_Aspect
2046
2047         begin
2048            --  Skip aspect if already analyzed, to avoid looping in some cases
2049
2050            if Analyzed (Aspect) then
2051               goto Continue;
2052            end if;
2053
2054            --  Skip looking at aspect if it is totally disabled. Just mark it
2055            --  as such for later reference in the tree. This also sets the
2056            --  Is_Ignored and Is_Checked flags appropriately.
2057
2058            Check_Applicable_Policy (Aspect);
2059
2060            if Is_Disabled (Aspect) then
2061               goto Continue;
2062            end if;
2063
2064            --  Set the source location of expression, used in the case of
2065            --  a failed precondition/postcondition or invariant. Note that
2066            --  the source location of the expression is not usually the best
2067            --  choice here. For example, it gets located on the last AND
2068            --  keyword in a chain of boolean expressiond AND'ed together.
2069            --  It is best to put the message on the first character of the
2070            --  assertion, which is the effect of the First_Node call here.
2071
2072            if Present (Expr) then
2073               Eloc := Sloc (First_Node (Expr));
2074            end if;
2075
2076            --  Check restriction No_Implementation_Aspect_Specifications
2077
2078            if Implementation_Defined_Aspect (A_Id) then
2079               Check_Restriction
2080                 (No_Implementation_Aspect_Specifications, Aspect);
2081            end if;
2082
2083            --  Check restriction No_Specification_Of_Aspect
2084
2085            Check_Restriction_No_Specification_Of_Aspect (Aspect);
2086
2087            --  Mark aspect analyzed (actual analysis is delayed till later)
2088
2089            Set_Analyzed (Aspect);
2090            Set_Entity (Aspect, E);
2091
2092            --  Build the reference to E that will be used in the built pragmas
2093
2094            Ent := New_Occurrence_Of (E, Sloc (Id));
2095
2096            if A_Id = Aspect_Attach_Handler
2097              or else A_Id = Aspect_Interrupt_Handler
2098            then
2099
2100               --  Treat the specification as a reference to the protected
2101               --  operation, which might otherwise appear unreferenced and
2102               --  generate spurious warnings.
2103
2104               Generate_Reference (E, Id);
2105            end if;
2106
2107            --  Check for duplicate aspect. Note that the Comes_From_Source
2108            --  test allows duplicate Pre/Post's that we generate internally
2109            --  to escape being flagged here.
2110
2111            if No_Duplicates_Allowed (A_Id) then
2112               Anod := First (L);
2113               while Anod /= Aspect loop
2114                  if Comes_From_Source (Aspect)
2115                    and then Same_Aspect (A_Id, Get_Aspect_Id (Anod))
2116                  then
2117                     Error_Msg_Name_1 := Nam;
2118                     Error_Msg_Sloc := Sloc (Anod);
2119
2120                     --  Case of same aspect specified twice
2121
2122                     if Class_Present (Anod) = Class_Present (Aspect) then
2123                        if not Class_Present (Anod) then
2124                           Error_Msg_NE
2125                             ("aspect% for & previously given#",
2126                              Id, E);
2127                        else
2128                           Error_Msg_NE
2129                             ("aspect `%''Class` for & previously given#",
2130                              Id, E);
2131                        end if;
2132                     end if;
2133                  end if;
2134
2135                  Next (Anod);
2136               end loop;
2137            end if;
2138
2139            --  Check some general restrictions on language defined aspects
2140
2141            if not Implementation_Defined_Aspect (A_Id) then
2142               Error_Msg_Name_1 := Nam;
2143
2144               --  Not allowed for renaming declarations. Examine the original
2145               --  node because a subprogram renaming may have been rewritten
2146               --  as a body.
2147
2148               if Nkind (Original_Node (N)) in N_Renaming_Declaration then
2149                  Error_Msg_N
2150                    ("aspect % not allowed for renaming declaration",
2151                     Aspect);
2152               end if;
2153
2154               --  Not allowed for formal type declarations
2155
2156               if Nkind (N) = N_Formal_Type_Declaration then
2157                  Error_Msg_N
2158                    ("aspect % not allowed for formal type declaration",
2159                     Aspect);
2160               end if;
2161            end if;
2162
2163            --  Copy expression for later processing by the procedures
2164            --  Check_Aspect_At_[Freeze_Point | End_Of_Declarations]
2165
2166            Set_Entity (Id, New_Copy_Tree (Expr));
2167
2168            --  Set Delay_Required as appropriate to aspect
2169
2170            case Aspect_Delay (A_Id) is
2171               when Always_Delay =>
2172                  Delay_Required := True;
2173
2174               when Never_Delay =>
2175                  Delay_Required := False;
2176
2177               when Rep_Aspect =>
2178
2179                  --  If expression has the form of an integer literal, then
2180                  --  do not delay, since we know the value cannot change.
2181                  --  This optimization catches most rep clause cases.
2182
2183                  --  For Boolean aspects, don't delay if no expression
2184
2185                  if A_Id in Boolean_Aspects and then No (Expr) then
2186                     Delay_Required := False;
2187
2188                  --  For non-Boolean aspects, don't delay if integer literal,
2189                  --  unless the aspect is Alignment, which affects the
2190                  --  freezing of an initialized object.
2191
2192                  elsif A_Id not in Boolean_Aspects
2193                    and then A_Id /= Aspect_Alignment
2194                    and then Present (Expr)
2195                    and then Nkind (Expr) = N_Integer_Literal
2196                  then
2197                     Delay_Required := False;
2198
2199                  --  All other cases are delayed
2200
2201                  else
2202                     Delay_Required := True;
2203                     Set_Has_Delayed_Rep_Aspects (E);
2204                  end if;
2205            end case;
2206
2207            --  Processing based on specific aspect
2208
2209            case A_Id is
2210               when Aspect_Unimplemented =>
2211                  null; -- ??? temp for now
2212
2213               --  No_Aspect should be impossible
2214
2215               when No_Aspect =>
2216                  raise Program_Error;
2217
2218               --  Case 1: Aspects corresponding to attribute definition
2219               --  clauses.
2220
2221               when Aspect_Address
2222                  | Aspect_Alignment
2223                  | Aspect_Bit_Order
2224                  | Aspect_Component_Size
2225                  | Aspect_Constant_Indexing
2226                  | Aspect_Default_Iterator
2227                  | Aspect_Dispatching_Domain
2228                  | Aspect_External_Tag
2229                  | Aspect_Input
2230                  | Aspect_Iterable
2231                  | Aspect_Iterator_Element
2232                  | Aspect_Machine_Radix
2233                  | Aspect_Object_Size
2234                  | Aspect_Output
2235                  | Aspect_Read
2236                  | Aspect_Scalar_Storage_Order
2237                  | Aspect_Simple_Storage_Pool
2238                  | Aspect_Size
2239                  | Aspect_Small
2240                  | Aspect_Storage_Pool
2241                  | Aspect_Stream_Size
2242                  | Aspect_Value_Size
2243                  | Aspect_Variable_Indexing
2244                  | Aspect_Write
2245               =>
2246                  --  Indexing aspects apply only to tagged type
2247
2248                  if (A_Id = Aspect_Constant_Indexing
2249                        or else
2250                      A_Id = Aspect_Variable_Indexing)
2251                    and then not (Is_Type (E)
2252                                   and then Is_Tagged_Type (E))
2253                  then
2254                     Error_Msg_N
2255                       ("indexing aspect can only apply to a tagged type",
2256                        Aspect);
2257                     goto Continue;
2258                  end if;
2259
2260                  --  For the case of aspect Address, we don't consider that we
2261                  --  know the entity is never set in the source, since it is
2262                  --  is likely aliasing is occurring.
2263
2264                  --  Note: one might think that the analysis of the resulting
2265                  --  attribute definition clause would take care of that, but
2266                  --  that's not the case since it won't be from source.
2267
2268                  if A_Id = Aspect_Address then
2269                     Set_Never_Set_In_Source (E, False);
2270                  end if;
2271
2272                  --  Correctness of the profile of a stream operation is
2273                  --  verified at the freeze point, but we must detect the
2274                  --  illegal specification of this aspect for a subtype now,
2275                  --  to prevent malformed rep_item chains.
2276
2277                  if A_Id = Aspect_Input  or else
2278                     A_Id = Aspect_Output or else
2279                     A_Id = Aspect_Read   or else
2280                     A_Id = Aspect_Write
2281                  then
2282                     if not Is_First_Subtype (E) then
2283                        Error_Msg_N
2284                          ("local name must be a first subtype", Aspect);
2285                        goto Continue;
2286
2287                     --  If stream aspect applies to the class-wide type,
2288                     --  the generated attribute definition applies to the
2289                     --  class-wide type as well.
2290
2291                     elsif Class_Present (Aspect) then
2292                        Ent :=
2293                          Make_Attribute_Reference (Loc,
2294                            Prefix         => Ent,
2295                            Attribute_Name => Name_Class);
2296                     end if;
2297                  end if;
2298
2299                  --  Construct the attribute_definition_clause. The expression
2300                  --  in the aspect specification is simply shared with the
2301                  --  constructed attribute, because it will be fully analyzed
2302                  --  when the attribute is processed. However, in ASIS mode
2303                  --  the aspect expression itself is preanalyzed and resolved
2304                  --  to catch visibility errors that are otherwise caught
2305                  --  later, and we create a separate copy of the expression
2306                  --  to prevent analysis of a malformed tree (e.g. a function
2307                  --  call with parameter associations).
2308
2309                  if ASIS_Mode then
2310                     Aitem :=
2311                       Make_Attribute_Definition_Clause (Loc,
2312                         Name       => Ent,
2313                         Chars      => Chars (Id),
2314                         Expression => New_Copy_Tree (Expr));
2315                  else
2316                     Aitem :=
2317                       Make_Attribute_Definition_Clause (Loc,
2318                         Name       => Ent,
2319                         Chars      => Chars (Id),
2320                         Expression => Relocate_Node (Expr));
2321                  end if;
2322
2323                  --  If the address is specified, then we treat the entity as
2324                  --  referenced, to avoid spurious warnings. This is analogous
2325                  --  to what is done with an attribute definition clause, but
2326                  --  here we don't want to generate a reference because this
2327                  --  is the point of definition of the entity.
2328
2329                  if A_Id = Aspect_Address then
2330                     Set_Referenced (E);
2331                  end if;
2332
2333               --  Case 2: Aspects corresponding to pragmas
2334
2335               --  Case 2a: Aspects corresponding to pragmas with two
2336               --  arguments, where the first argument is a local name
2337               --  referring to the entity, and the second argument is the
2338               --  aspect definition expression.
2339
2340               --  Linker_Section/Suppress/Unsuppress
2341
2342               when Aspect_Linker_Section
2343                  | Aspect_Suppress
2344                  | Aspect_Unsuppress
2345               =>
2346                  Make_Aitem_Pragma
2347                    (Pragma_Argument_Associations => New_List (
2348                       Make_Pragma_Argument_Association (Loc,
2349                         Expression => New_Occurrence_Of (E, Loc)),
2350                       Make_Pragma_Argument_Association (Sloc (Expr),
2351                         Expression => Relocate_Node (Expr))),
2352                     Pragma_Name                  => Chars (Id));
2353
2354                  --  Linker_Section does not need delaying, as its argument
2355                  --  must be a static string. Furthermore, if applied to
2356                  --  an object with an explicit initialization, the object
2357                  --  must be frozen in order to elaborate the initialization
2358                  --  code. (This is already done for types with implicit
2359                  --  initialization, such as protected types.)
2360
2361                  if A_Id = Aspect_Linker_Section
2362                    and then Nkind (N) = N_Object_Declaration
2363                    and then Has_Init_Expression (N)
2364                  then
2365                     Delay_Required := False;
2366                  end if;
2367
2368               --  Synchronization
2369
2370               --  Corresponds to pragma Implemented, construct the pragma
2371
2372               when Aspect_Synchronization =>
2373                  Make_Aitem_Pragma
2374                    (Pragma_Argument_Associations => New_List (
2375                       Make_Pragma_Argument_Association (Loc,
2376                         Expression => New_Occurrence_Of (E, Loc)),
2377                       Make_Pragma_Argument_Association (Sloc (Expr),
2378                         Expression => Relocate_Node (Expr))),
2379                     Pragma_Name                  => Name_Implemented);
2380
2381               --  Attach_Handler
2382
2383               when Aspect_Attach_Handler =>
2384                  Make_Aitem_Pragma
2385                    (Pragma_Argument_Associations => New_List (
2386                       Make_Pragma_Argument_Association (Sloc (Ent),
2387                         Expression => Ent),
2388                       Make_Pragma_Argument_Association (Sloc (Expr),
2389                         Expression => Relocate_Node (Expr))),
2390                     Pragma_Name                  => Name_Attach_Handler);
2391
2392                  --  We need to insert this pragma into the tree to get proper
2393                  --  processing and to look valid from a placement viewpoint.
2394
2395                  Insert_Pragma (Aitem);
2396                  goto Continue;
2397
2398               --  Dynamic_Predicate, Predicate, Static_Predicate
2399
2400               when Aspect_Dynamic_Predicate
2401                  | Aspect_Predicate
2402                  | Aspect_Static_Predicate
2403               =>
2404                  --  These aspects apply only to subtypes
2405
2406                  if not Is_Type (E) then
2407                     Error_Msg_N
2408                       ("predicate can only be specified for a subtype",
2409                        Aspect);
2410                     goto Continue;
2411
2412                  elsif Is_Incomplete_Type (E) then
2413                     Error_Msg_N
2414                       ("predicate cannot apply to incomplete view", Aspect);
2415
2416                  elsif Is_Generic_Type (E) then
2417                     Error_Msg_N
2418                       ("predicate cannot apply to formal type", Aspect);
2419                     goto Continue;
2420                  end if;
2421
2422                  --  Construct the pragma (always a pragma Predicate, with
2423                  --  flags recording whether it is static/dynamic). We also
2424                  --  set flags recording this in the type itself.
2425
2426                  Make_Aitem_Pragma
2427                    (Pragma_Argument_Associations => New_List (
2428                       Make_Pragma_Argument_Association (Sloc (Ent),
2429                         Expression => Ent),
2430                       Make_Pragma_Argument_Association (Sloc (Expr),
2431                         Expression => Relocate_Node (Expr))),
2432                     Pragma_Name => Name_Predicate);
2433
2434                  --  Mark type has predicates, and remember what kind of
2435                  --  aspect lead to this predicate (we need this to access
2436                  --  the right set of check policies later on).
2437
2438                  Set_Has_Predicates (E);
2439
2440                  if A_Id = Aspect_Dynamic_Predicate then
2441                     Set_Has_Dynamic_Predicate_Aspect (E);
2442
2443                     --  If the entity has a dynamic predicate, any inherited
2444                     --  static predicate becomes dynamic as well, and the
2445                     --  predicate function includes the conjunction of both.
2446
2447                     Set_Has_Static_Predicate_Aspect (E, False);
2448
2449                  elsif A_Id = Aspect_Static_Predicate then
2450                     Set_Has_Static_Predicate_Aspect (E);
2451                  end if;
2452
2453                  --  If the type is private, indicate that its completion
2454                  --  has a freeze node, because that is the one that will
2455                  --  be visible at freeze time.
2456
2457                  if Is_Private_Type (E) and then Present (Full_View (E)) then
2458                     Set_Has_Predicates (Full_View (E));
2459
2460                     if A_Id = Aspect_Dynamic_Predicate then
2461                        Set_Has_Dynamic_Predicate_Aspect (Full_View (E));
2462                     elsif A_Id = Aspect_Static_Predicate then
2463                        Set_Has_Static_Predicate_Aspect (Full_View (E));
2464                     end if;
2465
2466                     Set_Has_Delayed_Aspects (Full_View (E));
2467                     Ensure_Freeze_Node (Full_View (E));
2468                  end if;
2469
2470               --  Predicate_Failure
2471
2472               when Aspect_Predicate_Failure =>
2473
2474                  --  This aspect applies only to subtypes
2475
2476                  if not Is_Type (E) then
2477                     Error_Msg_N
2478                       ("predicate can only be specified for a subtype",
2479                        Aspect);
2480                     goto Continue;
2481
2482                  elsif Is_Incomplete_Type (E) then
2483                     Error_Msg_N
2484                       ("predicate cannot apply to incomplete view", Aspect);
2485                     goto Continue;
2486                  end if;
2487
2488                  --  Construct the pragma
2489
2490                  Make_Aitem_Pragma
2491                    (Pragma_Argument_Associations => New_List (
2492                       Make_Pragma_Argument_Association (Sloc (Ent),
2493                         Expression => Ent),
2494                       Make_Pragma_Argument_Association (Sloc (Expr),
2495                         Expression => Relocate_Node (Expr))),
2496                     Pragma_Name => Name_Predicate_Failure);
2497
2498                  Set_Has_Predicates (E);
2499
2500                  --  If the type is private, indicate that its completion
2501                  --  has a freeze node, because that is the one that will
2502                  --  be visible at freeze time.
2503
2504                  if Is_Private_Type (E) and then Present (Full_View (E)) then
2505                     Set_Has_Predicates (Full_View (E));
2506                     Set_Has_Delayed_Aspects (Full_View (E));
2507                     Ensure_Freeze_Node (Full_View (E));
2508                  end if;
2509
2510               --  Case 2b: Aspects corresponding to pragmas with two
2511               --  arguments, where the second argument is a local name
2512               --  referring to the entity, and the first argument is the
2513               --  aspect definition expression.
2514
2515               --  Convention
2516
2517               when Aspect_Convention =>
2518                  Analyze_Aspect_Convention;
2519                  goto Continue;
2520
2521               --  External_Name, Link_Name
2522
2523               when Aspect_External_Name
2524                  | Aspect_Link_Name
2525               =>
2526                  Analyze_Aspect_External_Link_Name;
2527                  goto Continue;
2528
2529               --  CPU, Interrupt_Priority, Priority
2530
2531               --  These three aspects can be specified for a subprogram spec
2532               --  or body, in which case we analyze the expression and export
2533               --  the value of the aspect.
2534
2535               --  Previously, we generated an equivalent pragma for bodies
2536               --  (note that the specs cannot contain these pragmas). The
2537               --  pragma was inserted ahead of local declarations, rather than
2538               --  after the body. This leads to a certain duplication between
2539               --  the processing performed for the aspect and the pragma, but
2540               --  given the straightforward handling required it is simpler
2541               --  to duplicate than to translate the aspect in the spec into
2542               --  a pragma in the declarative part of the body.
2543
2544               when Aspect_CPU
2545                  | Aspect_Interrupt_Priority
2546                  | Aspect_Priority
2547               =>
2548                  if Nkind_In (N, N_Subprogram_Body,
2549                                  N_Subprogram_Declaration)
2550                  then
2551                     --  Analyze the aspect expression
2552
2553                     Analyze_And_Resolve (Expr, Standard_Integer);
2554
2555                     --  Interrupt_Priority aspect not allowed for main
2556                     --  subprograms. RM D.1 does not forbid this explicitly,
2557                     --  but RM J.15.11(6/3) does not permit pragma
2558                     --  Interrupt_Priority for subprograms.
2559
2560                     if A_Id = Aspect_Interrupt_Priority then
2561                        Error_Msg_N
2562                          ("Interrupt_Priority aspect cannot apply to "
2563                           & "subprogram", Expr);
2564
2565                     --  The expression must be static
2566
2567                     elsif not Is_OK_Static_Expression (Expr) then
2568                        Flag_Non_Static_Expr
2569                          ("aspect requires static expression!", Expr);
2570
2571                     --  Check whether this is the main subprogram. Issue a
2572                     --  warning only if it is obviously not a main program
2573                     --  (when it has parameters or when the subprogram is
2574                     --  within a package).
2575
2576                     elsif Present (Parameter_Specifications
2577                                      (Specification (N)))
2578                       or else not Is_Compilation_Unit (Defining_Entity (N))
2579                     then
2580                        --  See RM D.1(14/3) and D.16(12/3)
2581
2582                        Error_Msg_N
2583                          ("aspect applied to subprogram other than the "
2584                           & "main subprogram has no effect??", Expr);
2585
2586                     --  Otherwise check in range and export the value
2587
2588                     --  For the CPU aspect
2589
2590                     elsif A_Id = Aspect_CPU then
2591                        if Is_In_Range (Expr, RTE (RE_CPU_Range)) then
2592
2593                           --  Value is correct so we export the value to make
2594                           --  it available at execution time.
2595
2596                           Set_Main_CPU
2597                             (Main_Unit, UI_To_Int (Expr_Value (Expr)));
2598
2599                        else
2600                           Error_Msg_N
2601                             ("main subprogram CPU is out of range", Expr);
2602                        end if;
2603
2604                     --  For the Priority aspect
2605
2606                     elsif A_Id = Aspect_Priority then
2607                        if Is_In_Range (Expr, RTE (RE_Priority)) then
2608
2609                           --  Value is correct so we export the value to make
2610                           --  it available at execution time.
2611
2612                           Set_Main_Priority
2613                             (Main_Unit, UI_To_Int (Expr_Value (Expr)));
2614
2615                        --  Ignore pragma if Relaxed_RM_Semantics to support
2616                        --  other targets/non GNAT compilers.
2617
2618                        elsif not Relaxed_RM_Semantics then
2619                           Error_Msg_N
2620                             ("main subprogram priority is out of range",
2621                              Expr);
2622                        end if;
2623                     end if;
2624
2625                     --  Load an arbitrary entity from System.Tasking.Stages
2626                     --  or System.Tasking.Restricted.Stages (depending on
2627                     --  the supported profile) to make sure that one of these
2628                     --  packages is implicitly with'ed, since we need to have
2629                     --  the tasking run time active for the pragma Priority to
2630                     --  have any effect. Previously we with'ed the package
2631                     --  System.Tasking, but this package does not trigger the
2632                     --  required initialization of the run-time library.
2633
2634                     declare
2635                        Discard : Entity_Id;
2636                     begin
2637                        if Restricted_Profile then
2638                           Discard := RTE (RE_Activate_Restricted_Tasks);
2639                        else
2640                           Discard := RTE (RE_Activate_Tasks);
2641                        end if;
2642                     end;
2643
2644                     --  Handling for these aspects in subprograms is complete
2645
2646                     goto Continue;
2647
2648                  --  For task and protected types pass the aspect as an
2649                  --  attribute.
2650
2651                  else
2652                     Aitem :=
2653                       Make_Attribute_Definition_Clause (Loc,
2654                         Name       => Ent,
2655                         Chars      => Chars (Id),
2656                         Expression => Relocate_Node (Expr));
2657                  end if;
2658
2659               --  Warnings
2660
2661               when Aspect_Warnings =>
2662                  Make_Aitem_Pragma
2663                    (Pragma_Argument_Associations => New_List (
2664                       Make_Pragma_Argument_Association (Sloc (Expr),
2665                         Expression => Relocate_Node (Expr)),
2666                       Make_Pragma_Argument_Association (Loc,
2667                         Expression => New_Occurrence_Of (E, Loc))),
2668                     Pragma_Name                  => Chars (Id));
2669
2670                  Decorate (Aspect, Aitem);
2671                  Insert_Pragma (Aitem);
2672                  goto Continue;
2673
2674               --  Case 2c: Aspects corresponding to pragmas with three
2675               --  arguments.
2676
2677               --  Invariant aspects have a first argument that references the
2678               --  entity, a second argument that is the expression and a third
2679               --  argument that is an appropriate message.
2680
2681               --  Invariant, Type_Invariant
2682
2683               when Aspect_Invariant
2684                  | Aspect_Type_Invariant
2685               =>
2686                  --  Analysis of the pragma will verify placement legality:
2687                  --  an invariant must apply to a private type, or appear in
2688                  --  the private part of a spec and apply to a completion.
2689
2690                  Make_Aitem_Pragma
2691                    (Pragma_Argument_Associations => New_List (
2692                       Make_Pragma_Argument_Association (Sloc (Ent),
2693                         Expression => Ent),
2694                       Make_Pragma_Argument_Association (Sloc (Expr),
2695                         Expression => Relocate_Node (Expr))),
2696                     Pragma_Name                  => Name_Invariant);
2697
2698                  --  Add message unless exception messages are suppressed
2699
2700                  if not Opt.Exception_Locations_Suppressed then
2701                     Append_To (Pragma_Argument_Associations (Aitem),
2702                       Make_Pragma_Argument_Association (Eloc,
2703                         Chars      => Name_Message,
2704                         Expression =>
2705                           Make_String_Literal (Eloc,
2706                             Strval => "failed invariant from "
2707                                       & Build_Location_String (Eloc))));
2708                  end if;
2709
2710                  --  For Invariant case, insert immediately after the entity
2711                  --  declaration. We do not have to worry about delay issues
2712                  --  since the pragma processing takes care of this.
2713
2714                  Delay_Required := False;
2715
2716               --  Case 2d : Aspects that correspond to a pragma with one
2717               --  argument.
2718
2719               --  Abstract_State
2720
2721               --  Aspect Abstract_State introduces implicit declarations for
2722               --  all state abstraction entities it defines. To emulate this
2723               --  behavior, insert the pragma at the beginning of the visible
2724               --  declarations of the related package so that it is analyzed
2725               --  immediately.
2726
2727               when Aspect_Abstract_State => Abstract_State : declare
2728                  Context : Node_Id := N;
2729
2730               begin
2731                  --  When aspect Abstract_State appears on a generic package,
2732                  --  it is propageted to the package instance. The context in
2733                  --  this case is the instance spec.
2734
2735                  if Nkind (Context) = N_Package_Instantiation then
2736                     Context := Instance_Spec (Context);
2737                  end if;
2738
2739                  if Nkind_In (Context, N_Generic_Package_Declaration,
2740                                        N_Package_Declaration)
2741                  then
2742                     Make_Aitem_Pragma
2743                       (Pragma_Argument_Associations => New_List (
2744                          Make_Pragma_Argument_Association (Loc,
2745                            Expression => Relocate_Node (Expr))),
2746                        Pragma_Name                  => Name_Abstract_State);
2747
2748                     Decorate (Aspect, Aitem);
2749                     Insert_Pragma
2750                       (Prag        => Aitem,
2751                        Is_Instance =>
2752                          Is_Generic_Instance (Defining_Entity (Context)));
2753
2754                  else
2755                     Error_Msg_NE
2756                       ("aspect & must apply to a package declaration",
2757                        Aspect, Id);
2758                  end if;
2759
2760                  goto Continue;
2761               end Abstract_State;
2762
2763               --  Aspect Async_Readers is never delayed because it is
2764               --  equivalent to a source pragma which appears after the
2765               --  related object declaration.
2766
2767               when Aspect_Async_Readers =>
2768                  Make_Aitem_Pragma
2769                    (Pragma_Argument_Associations => New_List (
2770                       Make_Pragma_Argument_Association (Loc,
2771                         Expression => Relocate_Node (Expr))),
2772                     Pragma_Name                  => Name_Async_Readers);
2773
2774                  Decorate (Aspect, Aitem);
2775                  Insert_Pragma (Aitem);
2776                  goto Continue;
2777
2778               --  Aspect Async_Writers is never delayed because it is
2779               --  equivalent to a source pragma which appears after the
2780               --  related object declaration.
2781
2782               when Aspect_Async_Writers =>
2783                  Make_Aitem_Pragma
2784                    (Pragma_Argument_Associations => New_List (
2785                       Make_Pragma_Argument_Association (Loc,
2786                         Expression => Relocate_Node (Expr))),
2787                     Pragma_Name                  => Name_Async_Writers);
2788
2789                  Decorate (Aspect, Aitem);
2790                  Insert_Pragma (Aitem);
2791                  goto Continue;
2792
2793               --  Aspect Constant_After_Elaboration is never delayed because
2794               --  it is equivalent to a source pragma which appears after the
2795               --  related object declaration.
2796
2797               when Aspect_Constant_After_Elaboration =>
2798                  Make_Aitem_Pragma
2799                    (Pragma_Argument_Associations => New_List (
2800                       Make_Pragma_Argument_Association (Loc,
2801                         Expression => Relocate_Node (Expr))),
2802                     Pragma_Name                  =>
2803                       Name_Constant_After_Elaboration);
2804
2805                  Decorate (Aspect, Aitem);
2806                  Insert_Pragma (Aitem);
2807                  goto Continue;
2808
2809               --  Aspect Default_Internal_Condition is never delayed because
2810               --  it is equivalent to a source pragma which appears after the
2811               --  related private type. To deal with forward references, the
2812               --  generated pragma is stored in the rep chain of the related
2813               --  private type as types do not carry contracts. The pragma is
2814               --  wrapped inside of a procedure at the freeze point of the
2815               --  private type's full view.
2816
2817               when Aspect_Default_Initial_Condition =>
2818                  Make_Aitem_Pragma
2819                    (Pragma_Argument_Associations => New_List (
2820                       Make_Pragma_Argument_Association (Loc,
2821                         Expression => Relocate_Node (Expr))),
2822                     Pragma_Name                  =>
2823                       Name_Default_Initial_Condition);
2824
2825                  Decorate (Aspect, Aitem);
2826                  Insert_Pragma (Aitem);
2827                  goto Continue;
2828
2829               --  Default_Storage_Pool
2830
2831               when Aspect_Default_Storage_Pool =>
2832                  Make_Aitem_Pragma
2833                    (Pragma_Argument_Associations => New_List (
2834                       Make_Pragma_Argument_Association (Loc,
2835                         Expression => Relocate_Node (Expr))),
2836                     Pragma_Name                  =>
2837                       Name_Default_Storage_Pool);
2838
2839                  Decorate (Aspect, Aitem);
2840                  Insert_Pragma (Aitem);
2841                  goto Continue;
2842
2843               --  Depends
2844
2845               --  Aspect Depends is never delayed because it is equivalent to
2846               --  a source pragma which appears after the related subprogram.
2847               --  To deal with forward references, the generated pragma is
2848               --  stored in the contract of the related subprogram and later
2849               --  analyzed at the end of the declarative region. See routine
2850               --  Analyze_Depends_In_Decl_Part for details.
2851
2852               when Aspect_Depends =>
2853                  Make_Aitem_Pragma
2854                    (Pragma_Argument_Associations => New_List (
2855                       Make_Pragma_Argument_Association (Loc,
2856                         Expression => Relocate_Node (Expr))),
2857                     Pragma_Name                  => Name_Depends);
2858
2859                  Decorate (Aspect, Aitem);
2860                  Insert_Pragma (Aitem);
2861                  goto Continue;
2862
2863               --  Aspect Effecitve_Reads is never delayed because it is
2864               --  equivalent to a source pragma which appears after the
2865               --  related object declaration.
2866
2867               when Aspect_Effective_Reads =>
2868                  Make_Aitem_Pragma
2869                    (Pragma_Argument_Associations => New_List (
2870                       Make_Pragma_Argument_Association (Loc,
2871                         Expression => Relocate_Node (Expr))),
2872                     Pragma_Name                  => Name_Effective_Reads);
2873
2874                  Decorate (Aspect, Aitem);
2875                  Insert_Pragma (Aitem);
2876                  goto Continue;
2877
2878               --  Aspect Effective_Writes is never delayed because it is
2879               --  equivalent to a source pragma which appears after the
2880               --  related object declaration.
2881
2882               when Aspect_Effective_Writes =>
2883                  Make_Aitem_Pragma
2884                    (Pragma_Argument_Associations => New_List (
2885                       Make_Pragma_Argument_Association (Loc,
2886                         Expression => Relocate_Node (Expr))),
2887                     Pragma_Name                  => Name_Effective_Writes);
2888
2889                  Decorate (Aspect, Aitem);
2890                  Insert_Pragma (Aitem);
2891                  goto Continue;
2892
2893               --  Aspect Extensions_Visible is never delayed because it is
2894               --  equivalent to a source pragma which appears after the
2895               --  related subprogram.
2896
2897               when Aspect_Extensions_Visible =>
2898                  Make_Aitem_Pragma
2899                    (Pragma_Argument_Associations => New_List (
2900                       Make_Pragma_Argument_Association (Loc,
2901                         Expression => Relocate_Node (Expr))),
2902                     Pragma_Name                  => Name_Extensions_Visible);
2903
2904                  Decorate (Aspect, Aitem);
2905                  Insert_Pragma (Aitem);
2906                  goto Continue;
2907
2908               --  Aspect Ghost is never delayed because it is equivalent to a
2909               --  source pragma which appears at the top of [generic] package
2910               --  declarations or after an object, a [generic] subprogram, or
2911               --  a type declaration.
2912
2913               when Aspect_Ghost =>
2914                  Make_Aitem_Pragma
2915                    (Pragma_Argument_Associations => New_List (
2916                       Make_Pragma_Argument_Association (Loc,
2917                         Expression => Relocate_Node (Expr))),
2918                     Pragma_Name                  => Name_Ghost);
2919
2920                  Decorate (Aspect, Aitem);
2921                  Insert_Pragma (Aitem);
2922                  goto Continue;
2923
2924               --  Global
2925
2926               --  Aspect Global is never delayed because it is equivalent to
2927               --  a source pragma which appears after the related subprogram.
2928               --  To deal with forward references, the generated pragma is
2929               --  stored in the contract of the related subprogram and later
2930               --  analyzed at the end of the declarative region. See routine
2931               --  Analyze_Global_In_Decl_Part for details.
2932
2933               when Aspect_Global =>
2934                  Make_Aitem_Pragma
2935                    (Pragma_Argument_Associations => New_List (
2936                       Make_Pragma_Argument_Association (Loc,
2937                         Expression => Relocate_Node (Expr))),
2938                     Pragma_Name                  => Name_Global);
2939
2940                  Decorate (Aspect, Aitem);
2941                  Insert_Pragma (Aitem);
2942                  goto Continue;
2943
2944               --  Initial_Condition
2945
2946               --  Aspect Initial_Condition is never delayed because it is
2947               --  equivalent to a source pragma which appears after the
2948               --  related package. To deal with forward references, the
2949               --  generated pragma is stored in the contract of the related
2950               --  package and later analyzed at the end of the declarative
2951               --  region. See routine Analyze_Initial_Condition_In_Decl_Part
2952               --  for details.
2953
2954               when Aspect_Initial_Condition => Initial_Condition : declare
2955                  Context : Node_Id := N;
2956
2957               begin
2958                  --  When aspect Initial_Condition appears on a generic
2959                  --  package, it is propageted to the package instance. The
2960                  --  context in this case is the instance spec.
2961
2962                  if Nkind (Context) = N_Package_Instantiation then
2963                     Context := Instance_Spec (Context);
2964                  end if;
2965
2966                  if Nkind_In (Context, N_Generic_Package_Declaration,
2967                                        N_Package_Declaration)
2968                  then
2969                     Make_Aitem_Pragma
2970                       (Pragma_Argument_Associations => New_List (
2971                          Make_Pragma_Argument_Association (Loc,
2972                            Expression => Relocate_Node (Expr))),
2973                        Pragma_Name                  =>
2974                          Name_Initial_Condition);
2975
2976                     Decorate (Aspect, Aitem);
2977                     Insert_Pragma
2978                       (Prag        => Aitem,
2979                        Is_Instance =>
2980                          Is_Generic_Instance (Defining_Entity (Context)));
2981
2982                  --  Otherwise the context is illegal
2983
2984                  else
2985                     Error_Msg_NE
2986                       ("aspect & must apply to a package declaration",
2987                        Aspect, Id);
2988                  end if;
2989
2990                  goto Continue;
2991               end Initial_Condition;
2992
2993               --  Initializes
2994
2995               --  Aspect Initializes is never delayed because it is equivalent
2996               --  to a source pragma appearing after the related package. To
2997               --  deal with forward references, the generated pragma is stored
2998               --  in the contract of the related package and later analyzed at
2999               --  the end of the declarative region. For details, see routine
3000               --  Analyze_Initializes_In_Decl_Part.
3001
3002               when Aspect_Initializes => Initializes : declare
3003                  Context : Node_Id := N;
3004
3005               begin
3006                  --  When aspect Initializes appears on a generic package,
3007                  --  it is propageted to the package instance. The context
3008                  --  in this case is the instance spec.
3009
3010                  if Nkind (Context) = N_Package_Instantiation then
3011                     Context := Instance_Spec (Context);
3012                  end if;
3013
3014                  if Nkind_In (Context, N_Generic_Package_Declaration,
3015                                        N_Package_Declaration)
3016                  then
3017                     Make_Aitem_Pragma
3018                       (Pragma_Argument_Associations => New_List (
3019                          Make_Pragma_Argument_Association (Loc,
3020                            Expression => Relocate_Node (Expr))),
3021                        Pragma_Name                  => Name_Initializes);
3022
3023                     Decorate (Aspect, Aitem);
3024                     Insert_Pragma
3025                       (Prag        => Aitem,
3026                        Is_Instance =>
3027                          Is_Generic_Instance (Defining_Entity (Context)));
3028
3029                  --  Otherwise the context is illegal
3030
3031                  else
3032                     Error_Msg_NE
3033                       ("aspect & must apply to a package declaration",
3034                        Aspect, Id);
3035                  end if;
3036
3037                  goto Continue;
3038               end Initializes;
3039
3040               --  Max_Entry_Queue_Depth
3041
3042               when Aspect_Max_Entry_Queue_Depth =>
3043                  Make_Aitem_Pragma
3044                    (Pragma_Argument_Associations => New_List (
3045                       Make_Pragma_Argument_Association (Loc,
3046                         Expression => Relocate_Node (Expr))),
3047                     Pragma_Name => Name_Max_Entry_Queue_Depth);
3048
3049                  Decorate (Aspect, Aitem);
3050                  Insert_Pragma (Aitem);
3051                  goto Continue;
3052
3053               --  Max_Queue_Length
3054
3055               when Aspect_Max_Queue_Length =>
3056                  Make_Aitem_Pragma
3057                    (Pragma_Argument_Associations => New_List (
3058                       Make_Pragma_Argument_Association (Loc,
3059                         Expression => Relocate_Node (Expr))),
3060                     Pragma_Name                  => Name_Max_Queue_Length);
3061
3062                  Decorate (Aspect, Aitem);
3063                  Insert_Pragma (Aitem);
3064                  goto Continue;
3065
3066               --  Obsolescent
3067
3068               when Aspect_Obsolescent => declare
3069                  Args : List_Id;
3070
3071               begin
3072                  if No (Expr) then
3073                     Args := No_List;
3074                  else
3075                     Args := New_List (
3076                       Make_Pragma_Argument_Association (Sloc (Expr),
3077                         Expression => Relocate_Node (Expr)));
3078                  end if;
3079
3080                  Make_Aitem_Pragma
3081                    (Pragma_Argument_Associations => Args,
3082                     Pragma_Name                  => Chars (Id));
3083               end;
3084
3085               --  Part_Of
3086
3087               when Aspect_Part_Of =>
3088                  if Nkind_In (N, N_Object_Declaration,
3089                                  N_Package_Instantiation)
3090                    or else Is_Single_Concurrent_Type_Declaration (N)
3091                  then
3092                     Make_Aitem_Pragma
3093                       (Pragma_Argument_Associations => New_List (
3094                          Make_Pragma_Argument_Association (Loc,
3095                            Expression => Relocate_Node (Expr))),
3096                        Pragma_Name                  => Name_Part_Of);
3097
3098                     Decorate (Aspect, Aitem);
3099                     Insert_Pragma (Aitem);
3100
3101                  else
3102                     Error_Msg_NE
3103                       ("aspect & must apply to package instantiation, "
3104                        & "object, single protected type or single task type",
3105                        Aspect, Id);
3106                  end if;
3107
3108                  goto Continue;
3109
3110               --  SPARK_Mode
3111
3112               when Aspect_SPARK_Mode =>
3113                  Make_Aitem_Pragma
3114                    (Pragma_Argument_Associations => New_List (
3115                       Make_Pragma_Argument_Association (Loc,
3116                         Expression => Relocate_Node (Expr))),
3117                     Pragma_Name                  => Name_SPARK_Mode);
3118
3119                  Decorate (Aspect, Aitem);
3120                  Insert_Pragma (Aitem);
3121                  goto Continue;
3122
3123               --  Refined_Depends
3124
3125               --  Aspect Refined_Depends is never delayed because it is
3126               --  equivalent to a source pragma which appears in the
3127               --  declarations of the related subprogram body. To deal with
3128               --  forward references, the generated pragma is stored in the
3129               --  contract of the related subprogram body and later analyzed
3130               --  at the end of the declarative region. For details, see
3131               --  routine Analyze_Refined_Depends_In_Decl_Part.
3132
3133               when Aspect_Refined_Depends =>
3134                  Make_Aitem_Pragma
3135                    (Pragma_Argument_Associations => New_List (
3136                       Make_Pragma_Argument_Association (Loc,
3137                         Expression => Relocate_Node (Expr))),
3138                     Pragma_Name                  => Name_Refined_Depends);
3139
3140                  Decorate (Aspect, Aitem);
3141                  Insert_Pragma (Aitem);
3142                  goto Continue;
3143
3144               --  Refined_Global
3145
3146               --  Aspect Refined_Global is never delayed because it is
3147               --  equivalent to a source pragma which appears in the
3148               --  declarations of the related subprogram body. To deal with
3149               --  forward references, the generated pragma is stored in the
3150               --  contract of the related subprogram body and later analyzed
3151               --  at the end of the declarative region. For details, see
3152               --  routine Analyze_Refined_Global_In_Decl_Part.
3153
3154               when Aspect_Refined_Global =>
3155                  Make_Aitem_Pragma
3156                    (Pragma_Argument_Associations => New_List (
3157                       Make_Pragma_Argument_Association (Loc,
3158                         Expression => Relocate_Node (Expr))),
3159                     Pragma_Name                  => Name_Refined_Global);
3160
3161                  Decorate (Aspect, Aitem);
3162                  Insert_Pragma (Aitem);
3163                  goto Continue;
3164
3165               --  Refined_Post
3166
3167               when Aspect_Refined_Post =>
3168                  Make_Aitem_Pragma
3169                    (Pragma_Argument_Associations => New_List (
3170                       Make_Pragma_Argument_Association (Loc,
3171                         Expression => Relocate_Node (Expr))),
3172                     Pragma_Name                  => Name_Refined_Post);
3173
3174                  Decorate (Aspect, Aitem);
3175                  Insert_Pragma (Aitem);
3176                  goto Continue;
3177
3178               --  Refined_State
3179
3180               when Aspect_Refined_State =>
3181
3182                  --  The corresponding pragma for Refined_State is inserted in
3183                  --  the declarations of the related package body. This action
3184                  --  synchronizes both the source and from-aspect versions of
3185                  --  the pragma.
3186
3187                  if Nkind (N) = N_Package_Body then
3188                     Make_Aitem_Pragma
3189                       (Pragma_Argument_Associations => New_List (
3190                          Make_Pragma_Argument_Association (Loc,
3191                            Expression => Relocate_Node (Expr))),
3192                        Pragma_Name                  => Name_Refined_State);
3193
3194                     Decorate (Aspect, Aitem);
3195                     Insert_Pragma (Aitem);
3196
3197                  --  Otherwise the context is illegal
3198
3199                  else
3200                     Error_Msg_NE
3201                       ("aspect & must apply to a package body", Aspect, Id);
3202                  end if;
3203
3204                  goto Continue;
3205
3206               --  Relative_Deadline
3207
3208               when Aspect_Relative_Deadline =>
3209                  Make_Aitem_Pragma
3210                    (Pragma_Argument_Associations => New_List (
3211                       Make_Pragma_Argument_Association (Loc,
3212                         Expression => Relocate_Node (Expr))),
3213                      Pragma_Name                 => Name_Relative_Deadline);
3214
3215                  --  If the aspect applies to a task, the corresponding pragma
3216                  --  must appear within its declarations, not after.
3217
3218                  if Nkind (N) = N_Task_Type_Declaration then
3219                     declare
3220                        Def : Node_Id;
3221                        V   : List_Id;
3222
3223                     begin
3224                        if No (Task_Definition (N)) then
3225                           Set_Task_Definition (N,
3226                             Make_Task_Definition (Loc,
3227                                Visible_Declarations => New_List,
3228                                End_Label => Empty));
3229                        end if;
3230
3231                        Def := Task_Definition (N);
3232                        V  := Visible_Declarations (Def);
3233                        if not Is_Empty_List (V) then
3234                           Insert_Before (First (V), Aitem);
3235
3236                        else
3237                           Set_Visible_Declarations (Def, New_List (Aitem));
3238                        end if;
3239
3240                        goto Continue;
3241                     end;
3242                  end if;
3243
3244               --  Secondary_Stack_Size
3245
3246               --  Aspect Secondary_Stack_Size needs to be converted into a
3247               --  pragma for two reasons: the attribute is not analyzed until
3248               --  after the expansion of the task type declaration and the
3249               --  attribute does not have visibility on the discriminant.
3250
3251               when Aspect_Secondary_Stack_Size =>
3252                  Make_Aitem_Pragma
3253                    (Pragma_Argument_Associations => New_List (
3254                       Make_Pragma_Argument_Association (Loc,
3255                         Expression => Relocate_Node (Expr))),
3256                     Pragma_Name                  =>
3257                       Name_Secondary_Stack_Size);
3258
3259                  Decorate (Aspect, Aitem);
3260                  Insert_Pragma (Aitem);
3261                  goto Continue;
3262
3263               --  Volatile_Function
3264
3265               --  Aspect Volatile_Function is never delayed because it is
3266               --  equivalent to a source pragma which appears after the
3267               --  related subprogram.
3268
3269               when Aspect_Volatile_Function =>
3270                  Make_Aitem_Pragma
3271                    (Pragma_Argument_Associations => New_List (
3272                       Make_Pragma_Argument_Association (Loc,
3273                         Expression => Relocate_Node (Expr))),
3274                     Pragma_Name                  => Name_Volatile_Function);
3275
3276                  Decorate (Aspect, Aitem);
3277                  Insert_Pragma (Aitem);
3278                  goto Continue;
3279
3280               --  Case 2e: Annotate aspect
3281
3282               when Aspect_Annotate =>
3283                  declare
3284                     Args  : List_Id;
3285                     Pargs : List_Id;
3286                     Arg   : Node_Id;
3287
3288                  begin
3289                     --  The argument can be a single identifier
3290
3291                     if Nkind (Expr) = N_Identifier then
3292
3293                        --  One level of parens is allowed
3294
3295                        if Paren_Count (Expr) > 1 then
3296                           Error_Msg_F ("extra parentheses ignored", Expr);
3297                        end if;
3298
3299                        Set_Paren_Count (Expr, 0);
3300
3301                        --  Add the single item to the list
3302
3303                        Args := New_List (Expr);
3304
3305                     --  Otherwise we must have an aggregate
3306
3307                     elsif Nkind (Expr) = N_Aggregate then
3308
3309                        --  Must be positional
3310
3311                        if Present (Component_Associations (Expr)) then
3312                           Error_Msg_F
3313                             ("purely positional aggregate required", Expr);
3314                           goto Continue;
3315                        end if;
3316
3317                        --  Must not be parenthesized
3318
3319                        if Paren_Count (Expr) /= 0 then
3320                           Error_Msg_F ("extra parentheses ignored", Expr);
3321                        end if;
3322
3323                        --  List of arguments is list of aggregate expressions
3324
3325                        Args := Expressions (Expr);
3326
3327                     --  Anything else is illegal
3328
3329                     else
3330                        Error_Msg_F ("wrong form for Annotate aspect", Expr);
3331                        goto Continue;
3332                     end if;
3333
3334                     --  Prepare pragma arguments
3335
3336                     Pargs := New_List;
3337                     Arg := First (Args);
3338                     while Present (Arg) loop
3339                        Append_To (Pargs,
3340                          Make_Pragma_Argument_Association (Sloc (Arg),
3341                            Expression => Relocate_Node (Arg)));
3342                        Next (Arg);
3343                     end loop;
3344
3345                     Append_To (Pargs,
3346                       Make_Pragma_Argument_Association (Sloc (Ent),
3347                         Chars      => Name_Entity,
3348                         Expression => Ent));
3349
3350                     Make_Aitem_Pragma
3351                       (Pragma_Argument_Associations => Pargs,
3352                        Pragma_Name                  => Name_Annotate);
3353                  end;
3354
3355               --  Case 3 : Aspects that don't correspond to pragma/attribute
3356               --  definition clause.
3357
3358               --  Case 3a: The aspects listed below don't correspond to
3359               --  pragmas/attributes but do require delayed analysis.
3360
3361               --  Default_Value can only apply to a scalar type
3362
3363               when Aspect_Default_Value =>
3364                  if not Is_Scalar_Type (E) then
3365                     Error_Msg_N
3366                       ("aspect Default_Value must apply to a scalar type", N);
3367                  end if;
3368
3369                  Aitem := Empty;
3370
3371               --  Default_Component_Value can only apply to an array type
3372               --  with scalar components.
3373
3374               when Aspect_Default_Component_Value =>
3375                  if not (Is_Array_Type (E)
3376                           and then Is_Scalar_Type (Component_Type (E)))
3377                  then
3378                     Error_Msg_N
3379                       ("aspect Default_Component_Value can only apply to an "
3380                        & "array of scalar components", N);
3381                  end if;
3382
3383                  Aitem := Empty;
3384
3385               --  Case 3b: The aspects listed below don't correspond to
3386               --  pragmas/attributes and don't need delayed analysis.
3387
3388               --  Implicit_Dereference
3389
3390               --  For Implicit_Dereference, External_Name and Link_Name, only
3391               --  the legality checks are done during the analysis, thus no
3392               --  delay is required.
3393
3394               when Aspect_Implicit_Dereference =>
3395                  Analyze_Aspect_Implicit_Dereference;
3396                  goto Continue;
3397
3398               --  Dimension
3399
3400               when Aspect_Dimension =>
3401                  Analyze_Aspect_Dimension (N, Id, Expr);
3402                  goto Continue;
3403
3404               --  Dimension_System
3405
3406               when Aspect_Dimension_System =>
3407                  Analyze_Aspect_Dimension_System (N, Id, Expr);
3408                  goto Continue;
3409
3410               --  Case 4: Aspects requiring special handling
3411
3412               --  Pre/Post/Test_Case/Contract_Cases whose corresponding
3413               --  pragmas take care of the delay.
3414
3415               --  Pre/Post
3416
3417               --  Aspects Pre/Post generate Precondition/Postcondition pragmas
3418               --  with a first argument that is the expression, and a second
3419               --  argument that is an informative message if the test fails.
3420               --  This is inserted right after the declaration, to get the
3421               --  required pragma placement. The processing for the pragmas
3422               --  takes care of the required delay.
3423
3424               when Pre_Post_Aspects => Pre_Post : declare
3425                  Pname : Name_Id;
3426
3427               begin
3428                  if A_Id = Aspect_Pre or else A_Id = Aspect_Precondition then
3429                     Pname := Name_Precondition;
3430                  else
3431                     Pname := Name_Postcondition;
3432                  end if;
3433
3434                  --  Check that the class-wide predicate cannot be applied to
3435                  --  an operation of a synchronized type. AI12-0182 forbids
3436                  --  these altogether, while earlier language semantics made
3437                  --  them legal on tagged synchronized types.
3438
3439                  --  Other legality checks are performed when analyzing the
3440                  --  contract of the operation.
3441
3442                  if Class_Present (Aspect)
3443                    and then Is_Concurrent_Type (Current_Scope)
3444                    and then Ekind_In (E, E_Entry, E_Function, E_Procedure)
3445                  then
3446                     Error_Msg_Name_1 := Original_Aspect_Pragma_Name (Aspect);
3447                     Error_Msg_N
3448                       ("aspect % can only be specified for a primitive "
3449                        & "operation of a tagged type", Aspect);
3450
3451                     goto Continue;
3452                  end if;
3453
3454                  --  If the expressions is of the form A and then B, then
3455                  --  we generate separate Pre/Post aspects for the separate
3456                  --  clauses. Since we allow multiple pragmas, there is no
3457                  --  problem in allowing multiple Pre/Post aspects internally.
3458                  --  These should be treated in reverse order (B first and
3459                  --  A second) since they are later inserted just after N in
3460                  --  the order they are treated. This way, the pragma for A
3461                  --  ends up preceding the pragma for B, which may have an
3462                  --  importance for the error raised (either constraint error
3463                  --  or precondition error).
3464
3465                  --  We do not do this for Pre'Class, since we have to put
3466                  --  these conditions together in a complex OR expression.
3467
3468                  --  We do not do this in ASIS mode, as ASIS relies on the
3469                  --  original node representing the complete expression, when
3470                  --  retrieving it through the source aspect table. Also, we
3471                  --  don't do this in GNATprove mode, because it brings no
3472                  --  benefit for proof and causes annoynace for flow analysis,
3473                  --  which prefers to be as close to the original source code
3474                  --  as possible.
3475
3476                  if not (ASIS_Mode or GNATprove_Mode)
3477                    and then (Pname = Name_Postcondition
3478                               or else not Class_Present (Aspect))
3479                  then
3480                     while Nkind (Expr) = N_And_Then loop
3481                        Insert_After (Aspect,
3482                          Make_Aspect_Specification (Sloc (Left_Opnd (Expr)),
3483                            Identifier    => Identifier (Aspect),
3484                            Expression    => Relocate_Node (Left_Opnd (Expr)),
3485                            Class_Present => Class_Present (Aspect),
3486                            Split_PPC     => True));
3487                        Rewrite (Expr, Relocate_Node (Right_Opnd (Expr)));
3488                        Eloc := Sloc (Expr);
3489                     end loop;
3490                  end if;
3491
3492                  --  Build the precondition/postcondition pragma
3493
3494                  --  Add note about why we do NOT need Copy_Tree here???
3495
3496                  Make_Aitem_Pragma
3497                    (Pragma_Argument_Associations => New_List (
3498                       Make_Pragma_Argument_Association (Eloc,
3499                         Chars      => Name_Check,
3500                         Expression => Relocate_Node (Expr))),
3501                       Pragma_Name                => Pname);
3502
3503                  --  Add message unless exception messages are suppressed
3504
3505                  if not Opt.Exception_Locations_Suppressed then
3506                     Append_To (Pragma_Argument_Associations (Aitem),
3507                       Make_Pragma_Argument_Association (Eloc,
3508                         Chars      => Name_Message,
3509                         Expression =>
3510                           Make_String_Literal (Eloc,
3511                             Strval => "failed "
3512                                       & Get_Name_String (Pname)
3513                                       & " from "
3514                                       & Build_Location_String (Eloc))));
3515                  end if;
3516
3517                  Set_Is_Delayed_Aspect (Aspect);
3518
3519                  --  For Pre/Post cases, insert immediately after the entity
3520                  --  declaration, since that is the required pragma placement.
3521                  --  Note that for these aspects, we do not have to worry
3522                  --  about delay issues, since the pragmas themselves deal
3523                  --  with delay of visibility for the expression analysis.
3524
3525                  Insert_Pragma (Aitem);
3526
3527                  goto Continue;
3528               end Pre_Post;
3529
3530               --  Test_Case
3531
3532               when Aspect_Test_Case => Test_Case : declare
3533                  Args      : List_Id;
3534                  Comp_Expr : Node_Id;
3535                  Comp_Assn : Node_Id;
3536                  New_Expr  : Node_Id;
3537
3538               begin
3539                  Args := New_List;
3540
3541                  if Nkind (Parent (N)) = N_Compilation_Unit then
3542                     Error_Msg_Name_1 := Nam;
3543                     Error_Msg_N ("incorrect placement of aspect `%`", E);
3544                     goto Continue;
3545                  end if;
3546
3547                  if Nkind (Expr) /= N_Aggregate then
3548                     Error_Msg_Name_1 := Nam;
3549                     Error_Msg_NE
3550                       ("wrong syntax for aspect `%` for &", Id, E);
3551                     goto Continue;
3552                  end if;
3553
3554                  --  Make pragma expressions refer to the original aspect
3555                  --  expressions through the Original_Node link. This is used
3556                  --  in semantic analysis for ASIS mode, so that the original
3557                  --  expression also gets analyzed.
3558
3559                  Comp_Expr := First (Expressions (Expr));
3560                  while Present (Comp_Expr) loop
3561                     New_Expr := Relocate_Node (Comp_Expr);
3562                     Append_To (Args,
3563                       Make_Pragma_Argument_Association (Sloc (Comp_Expr),
3564                         Expression => New_Expr));
3565                     Next (Comp_Expr);
3566                  end loop;
3567
3568                  Comp_Assn := First (Component_Associations (Expr));
3569                  while Present (Comp_Assn) loop
3570                     if List_Length (Choices (Comp_Assn)) /= 1
3571                       or else
3572                         Nkind (First (Choices (Comp_Assn))) /= N_Identifier
3573                     then
3574                        Error_Msg_Name_1 := Nam;
3575                        Error_Msg_NE
3576                          ("wrong syntax for aspect `%` for &", Id, E);
3577                        goto Continue;
3578                     end if;
3579
3580                     Append_To (Args,
3581                       Make_Pragma_Argument_Association (Sloc (Comp_Assn),
3582                         Chars      => Chars (First (Choices (Comp_Assn))),
3583                         Expression =>
3584                           Relocate_Node (Expression (Comp_Assn))));
3585                     Next (Comp_Assn);
3586                  end loop;
3587
3588                  --  Build the test-case pragma
3589
3590                  Make_Aitem_Pragma
3591                    (Pragma_Argument_Associations => Args,
3592                     Pragma_Name                  => Nam);
3593               end Test_Case;
3594
3595               --  Contract_Cases
3596
3597               when Aspect_Contract_Cases =>
3598                  Make_Aitem_Pragma
3599                    (Pragma_Argument_Associations => New_List (
3600                       Make_Pragma_Argument_Association (Loc,
3601                         Expression => Relocate_Node (Expr))),
3602                     Pragma_Name                  => Nam);
3603
3604                  Decorate (Aspect, Aitem);
3605                  Insert_Pragma (Aitem);
3606                  goto Continue;
3607
3608               --  Case 5: Special handling for aspects with an optional
3609               --  boolean argument.
3610
3611               --  In the delayed case, the corresponding pragma cannot be
3612               --  generated yet because the evaluation of the boolean needs
3613               --  to be delayed till the freeze point.
3614
3615               when Boolean_Aspects
3616                  | Library_Unit_Aspects
3617               =>
3618                  Set_Is_Boolean_Aspect (Aspect);
3619
3620                  --  Lock_Free aspect only apply to protected objects
3621
3622                  if A_Id = Aspect_Lock_Free then
3623                     if Ekind (E) /= E_Protected_Type then
3624                        Error_Msg_Name_1 := Nam;
3625                        Error_Msg_N
3626                          ("aspect % only applies to a protected object",
3627                           Aspect);
3628
3629                     else
3630                        --  Set the Uses_Lock_Free flag to True if there is no
3631                        --  expression or if the expression is True. The
3632                        --  evaluation of this aspect should be delayed to the
3633                        --  freeze point (why???)
3634
3635                        if No (Expr)
3636                          or else Is_True (Static_Boolean (Expr))
3637                        then
3638                           Set_Uses_Lock_Free (E);
3639                        end if;
3640
3641                        Record_Rep_Item (E, Aspect);
3642                     end if;
3643
3644                     goto Continue;
3645
3646                  elsif A_Id = Aspect_Export or else A_Id = Aspect_Import then
3647                     Analyze_Aspect_Export_Import;
3648
3649                  --  Disable_Controlled
3650
3651                  elsif A_Id = Aspect_Disable_Controlled then
3652                     Analyze_Aspect_Disable_Controlled;
3653                     goto Continue;
3654                  end if;
3655
3656                  --  Library unit aspects require special handling in the case
3657                  --  of a package declaration, the pragma needs to be inserted
3658                  --  in the list of declarations for the associated package.
3659                  --  There is no issue of visibility delay for these aspects.
3660
3661                  if A_Id in Library_Unit_Aspects
3662                    and then
3663                      Nkind_In (N, N_Package_Declaration,
3664                                   N_Generic_Package_Declaration)
3665                    and then Nkind (Parent (N)) /= N_Compilation_Unit
3666
3667                    --  Aspect is legal on a local instantiation of a library-
3668                    --  level generic unit.
3669
3670                    and then not Is_Generic_Instance (Defining_Entity (N))
3671                  then
3672                     Error_Msg_N
3673                       ("incorrect context for library unit aspect&", Id);
3674                     goto Continue;
3675                  end if;
3676
3677                  --  Cases where we do not delay, includes all cases where the
3678                  --  expression is missing other than the above cases.
3679
3680                  if not Delay_Required or else No (Expr) then
3681
3682                     --  Exclude aspects Export and Import because their pragma
3683                     --  syntax does not map directly to a Boolean aspect.
3684
3685                     if A_Id /= Aspect_Export
3686                       and then A_Id /= Aspect_Import
3687                     then
3688                        Make_Aitem_Pragma
3689                          (Pragma_Argument_Associations => New_List (
3690                             Make_Pragma_Argument_Association (Sloc (Ent),
3691                               Expression => Ent)),
3692                           Pragma_Name                  => Chars (Id));
3693                     end if;
3694
3695                     Delay_Required := False;
3696
3697                  --  In general cases, the corresponding pragma/attribute
3698                  --  definition clause will be inserted later at the freezing
3699                  --  point, and we do not need to build it now.
3700
3701                  else
3702                     Aitem := Empty;
3703                  end if;
3704
3705               --  Storage_Size
3706
3707               --  This is special because for access types we need to generate
3708               --  an attribute definition clause. This also works for single
3709               --  task declarations, but it does not work for task type
3710               --  declarations, because we have the case where the expression
3711               --  references a discriminant of the task type. That can't use
3712               --  an attribute definition clause because we would not have
3713               --  visibility on the discriminant. For that case we must
3714               --  generate a pragma in the task definition.
3715
3716               when Aspect_Storage_Size =>
3717
3718                  --  Task type case
3719
3720                  if Ekind (E) = E_Task_Type then
3721                     declare
3722                        Decl : constant Node_Id := Declaration_Node (E);
3723
3724                     begin
3725                        pragma Assert (Nkind (Decl) = N_Task_Type_Declaration);
3726
3727                        --  If no task definition, create one
3728
3729                        if No (Task_Definition (Decl)) then
3730                           Set_Task_Definition (Decl,
3731                             Make_Task_Definition (Loc,
3732                               Visible_Declarations => Empty_List,
3733                               End_Label            => Empty));
3734                        end if;
3735
3736                        --  Create a pragma and put it at the start of the task
3737                        --  definition for the task type declaration.
3738
3739                        Make_Aitem_Pragma
3740                          (Pragma_Argument_Associations => New_List (
3741                             Make_Pragma_Argument_Association (Loc,
3742                               Expression => Relocate_Node (Expr))),
3743                           Pragma_Name                  => Name_Storage_Size);
3744
3745                        Prepend
3746                          (Aitem,
3747                           Visible_Declarations (Task_Definition (Decl)));
3748                        goto Continue;
3749                     end;
3750
3751                  --  All other cases, generate attribute definition
3752
3753                  else
3754                     Aitem :=
3755                       Make_Attribute_Definition_Clause (Loc,
3756                         Name       => Ent,
3757                         Chars      => Chars (Id),
3758                         Expression => Relocate_Node (Expr));
3759                  end if;
3760            end case;
3761
3762            --  Attach the corresponding pragma/attribute definition clause to
3763            --  the aspect specification node.
3764
3765            if Present (Aitem) then
3766               Set_From_Aspect_Specification (Aitem);
3767            end if;
3768
3769            --  In the context of a compilation unit, we directly put the
3770            --  pragma in the Pragmas_After list of the N_Compilation_Unit_Aux
3771            --  node (no delay is required here) except for aspects on a
3772            --  subprogram body (see below) and a generic package, for which we
3773            --  need to introduce the pragma before building the generic copy
3774            --  (see sem_ch12), and for package instantiations, where the
3775            --  library unit pragmas are better handled early.
3776
3777            if Nkind (Parent (N)) = N_Compilation_Unit
3778              and then (Present (Aitem) or else Is_Boolean_Aspect (Aspect))
3779            then
3780               declare
3781                  Aux : constant Node_Id := Aux_Decls_Node (Parent (N));
3782
3783               begin
3784                  pragma Assert (Nkind (Aux) = N_Compilation_Unit_Aux);
3785
3786                  --  For a Boolean aspect, create the corresponding pragma if
3787                  --  no expression or if the value is True.
3788
3789                  if Is_Boolean_Aspect (Aspect) and then No (Aitem) then
3790                     if Is_True (Static_Boolean (Expr)) then
3791                        Make_Aitem_Pragma
3792                          (Pragma_Argument_Associations => New_List (
3793                             Make_Pragma_Argument_Association (Sloc (Ent),
3794                               Expression => Ent)),
3795                           Pragma_Name                  => Chars (Id));
3796
3797                        Set_From_Aspect_Specification (Aitem, True);
3798                        Set_Corresponding_Aspect (Aitem, Aspect);
3799
3800                     else
3801                        goto Continue;
3802                     end if;
3803                  end if;
3804
3805                  --  If the aspect is on a subprogram body (relevant aspect
3806                  --  is Inline), add the pragma in front of the declarations.
3807
3808                  if Nkind (N) = N_Subprogram_Body then
3809                     if No (Declarations (N)) then
3810                        Set_Declarations (N, New_List);
3811                     end if;
3812
3813                     Prepend (Aitem, Declarations (N));
3814
3815                  elsif Nkind (N) = N_Generic_Package_Declaration then
3816                     if No (Visible_Declarations (Specification (N))) then
3817                        Set_Visible_Declarations (Specification (N), New_List);
3818                     end if;
3819
3820                     Prepend (Aitem,
3821                       Visible_Declarations (Specification (N)));
3822
3823                  elsif Nkind (N) = N_Package_Instantiation then
3824                     declare
3825                        Spec : constant Node_Id :=
3826                                 Specification (Instance_Spec (N));
3827                     begin
3828                        if No (Visible_Declarations (Spec)) then
3829                           Set_Visible_Declarations (Spec, New_List);
3830                        end if;
3831
3832                        Prepend (Aitem, Visible_Declarations (Spec));
3833                     end;
3834
3835                  else
3836                     if No (Pragmas_After (Aux)) then
3837                        Set_Pragmas_After (Aux, New_List);
3838                     end if;
3839
3840                     Append (Aitem, Pragmas_After (Aux));
3841                  end if;
3842
3843                  goto Continue;
3844               end;
3845            end if;
3846
3847            --  The evaluation of the aspect is delayed to the freezing point.
3848            --  The pragma or attribute clause if there is one is then attached
3849            --  to the aspect specification which is put in the rep item list.
3850
3851            if Delay_Required then
3852               if Present (Aitem) then
3853                  Set_Is_Delayed_Aspect (Aitem);
3854                  Set_Aspect_Rep_Item (Aspect, Aitem);
3855                  Set_Parent (Aitem, Aspect);
3856               end if;
3857
3858               Set_Is_Delayed_Aspect (Aspect);
3859
3860               --  In the case of Default_Value, link the aspect to base type
3861               --  as well, even though it appears on a first subtype. This is
3862               --  mandated by the semantics of the aspect. Do not establish
3863               --  the link when processing the base type itself as this leads
3864               --  to a rep item circularity. Verify that we are dealing with
3865               --  a scalar type to prevent cascaded errors.
3866
3867               if A_Id = Aspect_Default_Value
3868                 and then Is_Scalar_Type (E)
3869                 and then Base_Type (E) /= E
3870               then
3871                  Set_Has_Delayed_Aspects (Base_Type (E));
3872                  Record_Rep_Item (Base_Type (E), Aspect);
3873               end if;
3874
3875               Set_Has_Delayed_Aspects (E);
3876               Record_Rep_Item (E, Aspect);
3877
3878            --  When delay is not required and the context is a package or a
3879            --  subprogram body, insert the pragma in the body declarations.
3880
3881            elsif Nkind_In (N, N_Package_Body, N_Subprogram_Body) then
3882               if No (Declarations (N)) then
3883                  Set_Declarations (N, New_List);
3884               end if;
3885
3886               --  The pragma is added before source declarations
3887
3888               Prepend_To (Declarations (N), Aitem);
3889
3890            --  When delay is not required and the context is not a compilation
3891            --  unit, we simply insert the pragma/attribute definition clause
3892            --  in sequence.
3893
3894            elsif Present (Aitem) then
3895               Insert_After (Ins_Node, Aitem);
3896               Ins_Node := Aitem;
3897            end if;
3898         end Analyze_One_Aspect;
3899
3900      <<Continue>>
3901         Next (Aspect);
3902      end loop Aspect_Loop;
3903
3904      if Has_Delayed_Aspects (E) then
3905         Ensure_Freeze_Node (E);
3906      end if;
3907   end Analyze_Aspect_Specifications;
3908
3909   ------------------------------------------------
3910   -- Analyze_Aspects_On_Subprogram_Body_Or_Stub --
3911   ------------------------------------------------
3912
3913   procedure Analyze_Aspects_On_Subprogram_Body_Or_Stub (N : Node_Id) is
3914      Body_Id : constant Entity_Id := Defining_Entity (N);
3915
3916      procedure Diagnose_Misplaced_Aspects (Spec_Id : Entity_Id);
3917      --  Body [stub] N has aspects, but they are not properly placed. Emit an
3918      --  error message depending on the aspects involved. Spec_Id denotes the
3919      --  entity of the corresponding spec.
3920
3921      --------------------------------
3922      -- Diagnose_Misplaced_Aspects --
3923      --------------------------------
3924
3925      procedure Diagnose_Misplaced_Aspects (Spec_Id : Entity_Id) is
3926         procedure Misplaced_Aspect_Error
3927           (Asp     : Node_Id;
3928            Ref_Nam : Name_Id);
3929         --  Emit an error message concerning misplaced aspect Asp. Ref_Nam is
3930         --  the name of the refined version of the aspect.
3931
3932         ----------------------------
3933         -- Misplaced_Aspect_Error --
3934         ----------------------------
3935
3936         procedure Misplaced_Aspect_Error
3937           (Asp     : Node_Id;
3938            Ref_Nam : Name_Id)
3939         is
3940            Asp_Nam : constant Name_Id   := Chars (Identifier (Asp));
3941            Asp_Id  : constant Aspect_Id := Get_Aspect_Id (Asp_Nam);
3942
3943         begin
3944            --  The corresponding spec already contains the aspect in question
3945            --  and the one appearing on the body must be the refined form:
3946
3947            --    procedure P with Global ...;
3948            --    procedure P with Global ... is ... end P;
3949            --                     ^
3950            --                     Refined_Global
3951
3952            if Has_Aspect (Spec_Id, Asp_Id) then
3953               Error_Msg_Name_1 := Asp_Nam;
3954
3955               --  Subunits cannot carry aspects that apply to a subprogram
3956               --  declaration.
3957
3958               if Nkind (Parent (N)) = N_Subunit then
3959                  Error_Msg_N ("aspect % cannot apply to a subunit", Asp);
3960
3961               --  Otherwise suggest the refined form
3962
3963               else
3964                  Error_Msg_Name_2 := Ref_Nam;
3965                  Error_Msg_N ("aspect % should be %", Asp);
3966               end if;
3967
3968            --  Otherwise the aspect must appear on the spec, not on the body
3969
3970            --    procedure P;
3971            --    procedure P with Global ... is ... end P;
3972
3973            else
3974               Error_Msg_N
3975                 ("aspect specification must appear on initial declaration",
3976                  Asp);
3977            end if;
3978         end Misplaced_Aspect_Error;
3979
3980         --  Local variables
3981
3982         Asp     : Node_Id;
3983         Asp_Nam : Name_Id;
3984
3985      --  Start of processing for Diagnose_Misplaced_Aspects
3986
3987      begin
3988         --  Iterate over the aspect specifications and emit specific errors
3989         --  where applicable.
3990
3991         Asp := First (Aspect_Specifications (N));
3992         while Present (Asp) loop
3993            Asp_Nam := Chars (Identifier (Asp));
3994
3995            --  Do not emit errors on aspects that can appear on a subprogram
3996            --  body. This scenario occurs when the aspect specification list
3997            --  contains both misplaced and properly placed aspects.
3998
3999            if Aspect_On_Body_Or_Stub_OK (Get_Aspect_Id (Asp_Nam)) then
4000               null;
4001
4002            --  Special diagnostics for SPARK aspects
4003
4004            elsif Asp_Nam = Name_Depends then
4005               Misplaced_Aspect_Error (Asp, Name_Refined_Depends);
4006
4007            elsif Asp_Nam = Name_Global then
4008               Misplaced_Aspect_Error (Asp, Name_Refined_Global);
4009
4010            elsif Asp_Nam = Name_Post then
4011               Misplaced_Aspect_Error (Asp, Name_Refined_Post);
4012
4013            --  Otherwise a language-defined aspect is misplaced
4014
4015            else
4016               Error_Msg_N
4017                 ("aspect specification must appear on initial declaration",
4018                  Asp);
4019            end if;
4020
4021            Next (Asp);
4022         end loop;
4023      end Diagnose_Misplaced_Aspects;
4024
4025      --  Local variables
4026
4027      Spec_Id : constant Entity_Id := Unique_Defining_Entity (N);
4028
4029   --  Start of processing for Analyze_Aspects_On_Subprogram_Body_Or_Stub
4030
4031   begin
4032      --  Language-defined aspects cannot be associated with a subprogram body
4033      --  [stub] if the subprogram has a spec. Certain implementation defined
4034      --  aspects are allowed to break this rule (for all applicable cases, see
4035      --  table Aspects.Aspect_On_Body_Or_Stub_OK).
4036
4037      if Spec_Id /= Body_Id and then not Aspects_On_Body_Or_Stub_OK (N) then
4038         Diagnose_Misplaced_Aspects (Spec_Id);
4039      else
4040         Analyze_Aspect_Specifications (N, Body_Id);
4041      end if;
4042   end Analyze_Aspects_On_Subprogram_Body_Or_Stub;
4043
4044   -----------------------
4045   -- Analyze_At_Clause --
4046   -----------------------
4047
4048   --  An at clause is replaced by the corresponding Address attribute
4049   --  definition clause that is the preferred approach in Ada 95.
4050
4051   procedure Analyze_At_Clause (N : Node_Id) is
4052      CS : constant Boolean := Comes_From_Source (N);
4053
4054   begin
4055      --  This is an obsolescent feature
4056
4057      Check_Restriction (No_Obsolescent_Features, N);
4058
4059      if Warn_On_Obsolescent_Feature then
4060         Error_Msg_N
4061           ("?j?at clause is an obsolescent feature (RM J.7(2))", N);
4062         Error_Msg_N
4063           ("\?j?use address attribute definition clause instead", N);
4064      end if;
4065
4066      --  Rewrite as address clause
4067
4068      Rewrite (N,
4069        Make_Attribute_Definition_Clause (Sloc (N),
4070          Name       => Identifier (N),
4071          Chars      => Name_Address,
4072          Expression => Expression (N)));
4073
4074      --  We preserve Comes_From_Source, since logically the clause still comes
4075      --  from the source program even though it is changed in form.
4076
4077      Set_Comes_From_Source (N, CS);
4078
4079      --  Analyze rewritten clause
4080
4081      Analyze_Attribute_Definition_Clause (N);
4082   end Analyze_At_Clause;
4083
4084   -----------------------------------------
4085   -- Analyze_Attribute_Definition_Clause --
4086   -----------------------------------------
4087
4088   procedure Analyze_Attribute_Definition_Clause (N : Node_Id) is
4089      Loc   : constant Source_Ptr   := Sloc (N);
4090      Nam   : constant Node_Id      := Name (N);
4091      Attr  : constant Name_Id      := Chars (N);
4092      Expr  : constant Node_Id      := Expression (N);
4093      Id    : constant Attribute_Id := Get_Attribute_Id (Attr);
4094
4095      Ent : Entity_Id;
4096      --  The entity of Nam after it is analyzed. In the case of an incomplete
4097      --  type, this is the underlying type.
4098
4099      U_Ent : Entity_Id;
4100      --  The underlying entity to which the attribute applies. Generally this
4101      --  is the Underlying_Type of Ent, except in the case where the clause
4102      --  applies to the full view of an incomplete or private type, in which
4103      --  case U_Ent is just a copy of Ent.
4104
4105      FOnly : Boolean := False;
4106      --  Reset to True for subtype specific attribute (Alignment, Size)
4107      --  and for stream attributes, i.e. those cases where in the call to
4108      --  Rep_Item_Too_Late, FOnly is set True so that only the freezing rules
4109      --  are checked. Note that the case of stream attributes is not clear
4110      --  from the RM, but see AI95-00137. Also, the RM seems to disallow
4111      --  Storage_Size for derived task types, but that is also clearly
4112      --  unintentional.
4113
4114      procedure Analyze_Stream_TSS_Definition (TSS_Nam : TSS_Name_Type);
4115      --  Common processing for 'Read, 'Write, 'Input and 'Output attribute
4116      --  definition clauses.
4117
4118      function Duplicate_Clause return Boolean;
4119      --  This routine checks if the aspect for U_Ent being given by attribute
4120      --  definition clause N is for an aspect that has already been specified,
4121      --  and if so gives an error message. If there is a duplicate, True is
4122      --  returned, otherwise if there is no error, False is returned.
4123
4124      procedure Check_Indexing_Functions;
4125      --  Check that the function in Constant_Indexing or Variable_Indexing
4126      --  attribute has the proper type structure. If the name is overloaded,
4127      --  check that some interpretation is legal.
4128
4129      procedure Check_Iterator_Functions;
4130      --  Check that there is a single function in Default_Iterator attribute
4131      --  that has the proper type structure.
4132
4133      function Check_Primitive_Function (Subp : Entity_Id) return Boolean;
4134      --  Common legality check for the previous two
4135
4136      -----------------------------------
4137      -- Analyze_Stream_TSS_Definition --
4138      -----------------------------------
4139
4140      procedure Analyze_Stream_TSS_Definition (TSS_Nam : TSS_Name_Type) is
4141         Subp : Entity_Id := Empty;
4142         I    : Interp_Index;
4143         It   : Interp;
4144         Pnam : Entity_Id;
4145
4146         Is_Read : constant Boolean := (TSS_Nam = TSS_Stream_Read);
4147         --  True for Read attribute, False for other attributes
4148
4149         function Has_Good_Profile
4150           (Subp   : Entity_Id;
4151            Report : Boolean := False) return Boolean;
4152         --  Return true if the entity is a subprogram with an appropriate
4153         --  profile for the attribute being defined. If result is False and
4154         --  Report is True, function emits appropriate error.
4155
4156         ----------------------
4157         -- Has_Good_Profile --
4158         ----------------------
4159
4160         function Has_Good_Profile
4161           (Subp   : Entity_Id;
4162            Report : Boolean := False) return Boolean
4163         is
4164            Expected_Ekind : constant array (Boolean) of Entity_Kind :=
4165                               (False => E_Procedure, True => E_Function);
4166            Is_Function    : constant Boolean := (TSS_Nam = TSS_Stream_Input);
4167            F              : Entity_Id;
4168            Typ            : Entity_Id;
4169
4170         begin
4171            if Ekind (Subp) /= Expected_Ekind (Is_Function) then
4172               return False;
4173            end if;
4174
4175            F := First_Formal (Subp);
4176
4177            if No (F)
4178              or else Ekind (Etype (F)) /= E_Anonymous_Access_Type
4179              or else Designated_Type (Etype (F)) /=
4180                        Class_Wide_Type (RTE (RE_Root_Stream_Type))
4181            then
4182               return False;
4183            end if;
4184
4185            if not Is_Function then
4186               Next_Formal (F);
4187
4188               declare
4189                  Expected_Mode : constant array (Boolean) of Entity_Kind :=
4190                                    (False => E_In_Parameter,
4191                                     True  => E_Out_Parameter);
4192               begin
4193                  if Parameter_Mode (F) /= Expected_Mode (Is_Read) then
4194                     return False;
4195                  end if;
4196               end;
4197
4198               Typ := Etype (F);
4199
4200               --  If the attribute specification comes from an aspect
4201               --  specification for a class-wide stream, the parameter must be
4202               --  a class-wide type of the entity to which the aspect applies.
4203
4204               if From_Aspect_Specification (N)
4205                 and then Class_Present (Parent (N))
4206                 and then Is_Class_Wide_Type (Typ)
4207               then
4208                  Typ := Etype (Typ);
4209               end if;
4210
4211            else
4212               Typ := Etype (Subp);
4213            end if;
4214
4215            --  Verify that the prefix of the attribute and the local name for
4216            --  the type of the formal match, or one is the class-wide of the
4217            --  other, in the case of a class-wide stream operation.
4218
4219            if Base_Type (Typ) = Base_Type (Ent)
4220              or else (Is_Class_Wide_Type (Typ)
4221                        and then Typ = Class_Wide_Type (Base_Type (Ent)))
4222              or else (Is_Class_Wide_Type (Ent)
4223                        and then Ent = Class_Wide_Type (Base_Type (Typ)))
4224            then
4225               null;
4226            else
4227               return False;
4228            end if;
4229
4230            if Present (Next_Formal (F)) then
4231               return False;
4232
4233            elsif not Is_Scalar_Type (Typ)
4234              and then not Is_First_Subtype (Typ)
4235              and then not Is_Class_Wide_Type (Typ)
4236            then
4237               if Report and not Is_First_Subtype (Typ) then
4238                  Error_Msg_N
4239                    ("subtype of formal in stream operation must be a first "
4240                     & "subtype", Parameter_Type (Parent (F)));
4241               end if;
4242
4243               return False;
4244
4245            else
4246               return True;
4247            end if;
4248         end Has_Good_Profile;
4249
4250      --  Start of processing for Analyze_Stream_TSS_Definition
4251
4252      begin
4253         FOnly := True;
4254
4255         if not Is_Type (U_Ent) then
4256            Error_Msg_N ("local name must be a subtype", Nam);
4257            return;
4258
4259         elsif not Is_First_Subtype (U_Ent) then
4260            Error_Msg_N ("local name must be a first subtype", Nam);
4261            return;
4262         end if;
4263
4264         Pnam := TSS (Base_Type (U_Ent), TSS_Nam);
4265
4266         --  If Pnam is present, it can be either inherited from an ancestor
4267         --  type (in which case it is legal to redefine it for this type), or
4268         --  be a previous definition of the attribute for the same type (in
4269         --  which case it is illegal).
4270
4271         --  In the first case, it will have been analyzed already, and we
4272         --  can check that its profile does not match the expected profile
4273         --  for a stream attribute of U_Ent. In the second case, either Pnam
4274         --  has been analyzed (and has the expected profile), or it has not
4275         --  been analyzed yet (case of a type that has not been frozen yet
4276         --  and for which the stream attribute has been set using Set_TSS).
4277
4278         if Present (Pnam)
4279           and then (No (First_Entity (Pnam)) or else Has_Good_Profile (Pnam))
4280         then
4281            Error_Msg_Sloc := Sloc (Pnam);
4282            Error_Msg_Name_1 := Attr;
4283            Error_Msg_N ("% attribute already defined #", Nam);
4284            return;
4285         end if;
4286
4287         Analyze (Expr);
4288
4289         if Is_Entity_Name (Expr) then
4290            if not Is_Overloaded (Expr) then
4291               if Has_Good_Profile (Entity (Expr), Report => True) then
4292                  Subp := Entity (Expr);
4293               end if;
4294
4295            else
4296               Get_First_Interp (Expr, I, It);
4297               while Present (It.Nam) loop
4298                  if Has_Good_Profile (It.Nam) then
4299                     Subp := It.Nam;
4300                     exit;
4301                  end if;
4302
4303                  Get_Next_Interp (I, It);
4304               end loop;
4305            end if;
4306         end if;
4307
4308         if Present (Subp) then
4309            if Is_Abstract_Subprogram (Subp) then
4310               Error_Msg_N ("stream subprogram must not be abstract", Expr);
4311               return;
4312
4313            --  A stream subprogram for an interface type must be a null
4314            --  procedure (RM 13.13.2 (38/3)). Note that the class-wide type
4315            --  of an interface is not an interface type (3.9.4 (6.b/2)).
4316
4317            elsif Is_Interface (U_Ent)
4318              and then not Is_Class_Wide_Type (U_Ent)
4319              and then not Inside_A_Generic
4320              and then
4321                (Ekind (Subp) = E_Function
4322                  or else
4323                    not Null_Present
4324                          (Specification
4325                             (Unit_Declaration_Node (Ultimate_Alias (Subp)))))
4326            then
4327               Error_Msg_N
4328                 ("stream subprogram for interface type must be null "
4329                  & "procedure", Expr);
4330            end if;
4331
4332            Set_Entity (Expr, Subp);
4333            Set_Etype (Expr, Etype (Subp));
4334
4335            New_Stream_Subprogram (N, U_Ent, Subp, TSS_Nam);
4336
4337         else
4338            Error_Msg_Name_1 := Attr;
4339            Error_Msg_N ("incorrect expression for% attribute", Expr);
4340         end if;
4341      end Analyze_Stream_TSS_Definition;
4342
4343      ------------------------------
4344      -- Check_Indexing_Functions --
4345      ------------------------------
4346
4347      procedure Check_Indexing_Functions is
4348         Indexing_Found : Boolean := False;
4349
4350         procedure Check_Inherited_Indexing;
4351         --  For a derived type, check that no indexing aspect is specified
4352         --  for the type if it is also inherited
4353
4354         procedure Check_One_Function (Subp : Entity_Id);
4355         --  Check one possible interpretation. Sets Indexing_Found True if a
4356         --  legal indexing function is found.
4357
4358         procedure Illegal_Indexing (Msg : String);
4359         --  Diagnose illegal indexing function if not overloaded. In the
4360         --  overloaded case indicate that no legal interpretation  exists.
4361
4362         ------------------------------
4363         -- Check_Inherited_Indexing --
4364         ------------------------------
4365
4366         procedure Check_Inherited_Indexing is
4367            Inherited : Node_Id;
4368
4369         begin
4370            if Attr = Name_Constant_Indexing then
4371               Inherited :=
4372                 Find_Aspect (Etype (Ent), Aspect_Constant_Indexing);
4373            else pragma Assert (Attr = Name_Variable_Indexing);
4374               Inherited :=
4375                  Find_Aspect (Etype (Ent), Aspect_Variable_Indexing);
4376            end if;
4377
4378            if Present (Inherited) then
4379               if Debug_Flag_Dot_XX then
4380                  null;
4381
4382               --  OK if current attribute_definition_clause is expansion of
4383               --  inherited aspect.
4384
4385               elsif Aspect_Rep_Item (Inherited) = N then
4386                  null;
4387
4388               --  Indicate the operation that must be overridden, rather than
4389               --  redefining the indexing aspect.
4390
4391               else
4392                  Illegal_Indexing
4393                    ("indexing function already inherited from parent type");
4394                  Error_Msg_NE
4395                    ("!override & instead",
4396                     N, Entity (Expression (Inherited)));
4397               end if;
4398            end if;
4399         end Check_Inherited_Indexing;
4400
4401         ------------------------
4402         -- Check_One_Function --
4403         ------------------------
4404
4405         procedure Check_One_Function (Subp : Entity_Id) is
4406            Default_Element : Node_Id;
4407            Ret_Type        : constant Entity_Id := Etype (Subp);
4408
4409         begin
4410            if not Is_Overloadable (Subp) then
4411               Illegal_Indexing ("illegal indexing function for type&");
4412               return;
4413
4414            elsif Scope (Subp) /= Scope (Ent) then
4415               if Nkind (Expr) = N_Expanded_Name then
4416
4417                  --  Indexing function can't be declared elsewhere
4418
4419                  Illegal_Indexing
4420                    ("indexing function must be declared in scope of type&");
4421               end if;
4422
4423               return;
4424
4425            elsif No (First_Formal (Subp)) then
4426               Illegal_Indexing
4427                 ("Indexing requires a function that applies to type&");
4428               return;
4429
4430            elsif No (Next_Formal (First_Formal (Subp))) then
4431               Illegal_Indexing
4432                 ("indexing function must have at least two parameters");
4433               return;
4434
4435            elsif Is_Derived_Type (Ent) then
4436               Check_Inherited_Indexing;
4437            end if;
4438
4439            if not Check_Primitive_Function (Subp) then
4440               Illegal_Indexing
4441                 ("Indexing aspect requires a function that applies to type&");
4442               return;
4443            end if;
4444
4445            --  If partial declaration exists, verify that it is not tagged.
4446
4447            if Ekind (Current_Scope) = E_Package
4448              and then Has_Private_Declaration (Ent)
4449              and then From_Aspect_Specification (N)
4450              and then
4451                List_Containing (Parent (Ent)) =
4452                  Private_Declarations
4453                    (Specification (Unit_Declaration_Node (Current_Scope)))
4454              and then Nkind (N) = N_Attribute_Definition_Clause
4455            then
4456               declare
4457                  Decl : Node_Id;
4458
4459               begin
4460                  Decl :=
4461                     First (Visible_Declarations
4462                              (Specification
4463                                 (Unit_Declaration_Node (Current_Scope))));
4464
4465                  while Present (Decl) loop
4466                     if Nkind (Decl) = N_Private_Type_Declaration
4467                       and then Ent = Full_View (Defining_Identifier (Decl))
4468                       and then Tagged_Present (Decl)
4469                       and then No (Aspect_Specifications (Decl))
4470                     then
4471                        Illegal_Indexing
4472                          ("Indexing aspect cannot be specified on full view "
4473                           & "if partial view is tagged");
4474                        return;
4475                     end if;
4476
4477                     Next (Decl);
4478                  end loop;
4479               end;
4480            end if;
4481
4482            --  An indexing function must return either the default element of
4483            --  the container, or a reference type. For variable indexing it
4484            --  must be the latter.
4485
4486            Default_Element :=
4487              Find_Value_Of_Aspect
4488               (Etype (First_Formal (Subp)), Aspect_Iterator_Element);
4489
4490            if Present (Default_Element) then
4491               Analyze (Default_Element);
4492            end if;
4493
4494            --  For variable_indexing the return type must be a reference type
4495
4496            if Attr = Name_Variable_Indexing then
4497               if not Has_Implicit_Dereference (Ret_Type) then
4498                  Illegal_Indexing
4499                     ("variable indexing must return a reference type");
4500                  return;
4501
4502               elsif Is_Access_Constant
4503                       (Etype (First_Discriminant (Ret_Type)))
4504               then
4505                  Illegal_Indexing
4506                    ("variable indexing must return an access to variable");
4507                  return;
4508               end if;
4509
4510            else
4511               if  Has_Implicit_Dereference (Ret_Type)
4512                 and then not
4513                   Is_Access_Constant (Etype (First_Discriminant (Ret_Type)))
4514               then
4515                  Illegal_Indexing
4516                    ("constant indexing must return an access to constant");
4517                  return;
4518
4519               elsif Is_Access_Type (Etype (First_Formal (Subp)))
4520                 and then not Is_Access_Constant (Etype (First_Formal (Subp)))
4521               then
4522                  Illegal_Indexing
4523                    ("constant indexing must apply to an access to constant");
4524                  return;
4525               end if;
4526            end if;
4527
4528            --  All checks succeeded.
4529
4530            Indexing_Found := True;
4531         end Check_One_Function;
4532
4533         -----------------------
4534         --  Illegal_Indexing --
4535         -----------------------
4536
4537         procedure Illegal_Indexing (Msg : String) is
4538         begin
4539            Error_Msg_NE (Msg, N, Ent);
4540         end Illegal_Indexing;
4541
4542      --  Start of processing for Check_Indexing_Functions
4543
4544      begin
4545         if In_Instance then
4546            Check_Inherited_Indexing;
4547         end if;
4548
4549         Analyze (Expr);
4550
4551         if not Is_Overloaded (Expr) then
4552            Check_One_Function (Entity (Expr));
4553
4554         else
4555            declare
4556               I  : Interp_Index;
4557               It : Interp;
4558
4559            begin
4560               Indexing_Found := False;
4561               Get_First_Interp (Expr, I, It);
4562               while Present (It.Nam) loop
4563
4564                  --  Note that analysis will have added the interpretation
4565                  --  that corresponds to the dereference. We only check the
4566                  --  subprogram itself. Ignore homonyms that may come from
4567                  --  derived types in the context.
4568
4569                  if Is_Overloadable (It.Nam)
4570                    and then Comes_From_Source (It.Nam)
4571                  then
4572                     Check_One_Function (It.Nam);
4573                  end if;
4574
4575                  Get_Next_Interp (I, It);
4576               end loop;
4577            end;
4578         end if;
4579
4580         if not Indexing_Found and then not Error_Posted (N) then
4581            Error_Msg_NE
4582              ("aspect Indexing requires a local function that applies to "
4583               & "type&", Expr, Ent);
4584         end if;
4585      end Check_Indexing_Functions;
4586
4587      ------------------------------
4588      -- Check_Iterator_Functions --
4589      ------------------------------
4590
4591      procedure Check_Iterator_Functions is
4592         function Valid_Default_Iterator (Subp : Entity_Id) return Boolean;
4593         --  Check one possible interpretation for validity
4594
4595         ----------------------------
4596         -- Valid_Default_Iterator --
4597         ----------------------------
4598
4599         function Valid_Default_Iterator (Subp : Entity_Id) return Boolean is
4600            Root_T : constant Entity_Id := Root_Type (Etype (Etype (Subp)));
4601            Formal : Entity_Id;
4602
4603         begin
4604            if not Check_Primitive_Function (Subp) then
4605               return False;
4606
4607            --  The return type must be derived from a type in an instance
4608            --  of Iterator.Interfaces, and thus its root type must have a
4609            --  predefined name.
4610
4611            elsif Chars (Root_T) /= Name_Forward_Iterator
4612             and then Chars (Root_T) /= Name_Reversible_Iterator
4613            then
4614               return False;
4615
4616            else
4617               Formal := First_Formal (Subp);
4618            end if;
4619
4620            --  False if any subsequent formal has no default expression
4621
4622            Formal := Next_Formal (Formal);
4623            while Present (Formal) loop
4624               if No (Expression (Parent (Formal))) then
4625                  return False;
4626               end if;
4627
4628               Next_Formal (Formal);
4629            end loop;
4630
4631            --  True if all subsequent formals have default expressions
4632
4633            return True;
4634         end Valid_Default_Iterator;
4635
4636      --  Start of processing for Check_Iterator_Functions
4637
4638      begin
4639         Analyze (Expr);
4640
4641         if not Is_Entity_Name (Expr) then
4642            Error_Msg_N ("aspect Iterator must be a function name", Expr);
4643         end if;
4644
4645         if not Is_Overloaded (Expr) then
4646            if not Check_Primitive_Function (Entity (Expr)) then
4647               Error_Msg_NE
4648                 ("aspect Indexing requires a function that applies to type&",
4649                   Entity (Expr), Ent);
4650            end if;
4651
4652            --  Flag the default_iterator as well as the denoted function.
4653
4654            if not Valid_Default_Iterator (Entity (Expr)) then
4655               Error_Msg_N ("improper function for default iterator!", Expr);
4656            end if;
4657
4658         else
4659            declare
4660               Default : Entity_Id := Empty;
4661               I       : Interp_Index;
4662               It      : Interp;
4663
4664            begin
4665               Get_First_Interp (Expr, I, It);
4666               while Present (It.Nam) loop
4667                  if not Check_Primitive_Function (It.Nam)
4668                    or else not Valid_Default_Iterator (It.Nam)
4669                  then
4670                     Remove_Interp (I);
4671
4672                  elsif Present (Default) then
4673
4674                     --  An explicit one should override an implicit one
4675
4676                     if Comes_From_Source (Default) =
4677                          Comes_From_Source (It.Nam)
4678                     then
4679                        Error_Msg_N ("default iterator must be unique", Expr);
4680                        Error_Msg_Sloc := Sloc (Default);
4681                        Error_Msg_N ("\\possible interpretation#", Expr);
4682                        Error_Msg_Sloc := Sloc (It.Nam);
4683                        Error_Msg_N ("\\possible interpretation#", Expr);
4684
4685                     elsif Comes_From_Source (It.Nam) then
4686                        Default := It.Nam;
4687                     end if;
4688                  else
4689                     Default := It.Nam;
4690                  end if;
4691
4692                  Get_Next_Interp (I, It);
4693               end loop;
4694
4695               if Present (Default) then
4696                  Set_Entity (Expr, Default);
4697                  Set_Is_Overloaded (Expr, False);
4698               else
4699                  Error_Msg_N
4700                    ("no interpretation is a valid default iterator!", Expr);
4701               end if;
4702            end;
4703         end if;
4704      end Check_Iterator_Functions;
4705
4706      -------------------------------
4707      -- Check_Primitive_Function  --
4708      -------------------------------
4709
4710      function Check_Primitive_Function (Subp : Entity_Id) return Boolean is
4711         Ctrl : Entity_Id;
4712
4713      begin
4714         if Ekind (Subp) /= E_Function then
4715            return False;
4716         end if;
4717
4718         if No (First_Formal (Subp)) then
4719            return False;
4720         else
4721            Ctrl := Etype (First_Formal (Subp));
4722         end if;
4723
4724         --  To be a primitive operation subprogram has to be in same scope.
4725
4726         if Scope (Ctrl) /= Scope (Subp) then
4727            return False;
4728         end if;
4729
4730         --  Type of formal may be the class-wide type, an access to such,
4731         --  or an incomplete view.
4732
4733         if Ctrl = Ent
4734           or else Ctrl = Class_Wide_Type (Ent)
4735           or else
4736             (Ekind (Ctrl) = E_Anonymous_Access_Type
4737               and then (Designated_Type (Ctrl) = Ent
4738                           or else
4739                         Designated_Type (Ctrl) = Class_Wide_Type (Ent)))
4740           or else
4741             (Ekind (Ctrl) = E_Incomplete_Type
4742               and then Full_View (Ctrl) = Ent)
4743         then
4744            null;
4745         else
4746            return False;
4747         end if;
4748
4749         return True;
4750      end Check_Primitive_Function;
4751
4752      ----------------------
4753      -- Duplicate_Clause --
4754      ----------------------
4755
4756      function Duplicate_Clause return Boolean is
4757         A : Node_Id;
4758
4759      begin
4760         --  Nothing to do if this attribute definition clause comes from
4761         --  an aspect specification, since we could not be duplicating an
4762         --  explicit clause, and we dealt with the case of duplicated aspects
4763         --  in Analyze_Aspect_Specifications.
4764
4765         if From_Aspect_Specification (N) then
4766            return False;
4767         end if;
4768
4769         --  Otherwise current clause may duplicate previous clause, or a
4770         --  previously given pragma or aspect specification for the same
4771         --  aspect.
4772
4773         A := Get_Rep_Item (U_Ent, Chars (N), Check_Parents => False);
4774
4775         if Present (A) then
4776            Error_Msg_Name_1 := Chars (N);
4777            Error_Msg_Sloc := Sloc (A);
4778
4779            Error_Msg_NE ("aspect% for & previously given#", N, U_Ent);
4780            return True;
4781         end if;
4782
4783         return False;
4784      end Duplicate_Clause;
4785
4786   --  Start of processing for Analyze_Attribute_Definition_Clause
4787
4788   begin
4789      --  The following code is a defense against recursion. Not clear that
4790      --  this can happen legitimately, but perhaps some error situations can
4791      --  cause it, and we did see this recursion during testing.
4792
4793      if Analyzed (N) then
4794         return;
4795      else
4796         Set_Analyzed (N, True);
4797      end if;
4798
4799      Check_Restriction_No_Use_Of_Attribute (N);
4800
4801      --  Ignore some selected attributes in CodePeer mode since they are not
4802      --  relevant in this context.
4803
4804      if CodePeer_Mode then
4805         case Id is
4806
4807            --  Ignore Component_Size in CodePeer mode, to avoid changing the
4808            --  internal representation of types by implicitly packing them.
4809
4810            when Attribute_Component_Size =>
4811               Rewrite (N, Make_Null_Statement (Sloc (N)));
4812               return;
4813
4814            when others =>
4815               null;
4816         end case;
4817      end if;
4818
4819      --  Process Ignore_Rep_Clauses option
4820
4821      if Ignore_Rep_Clauses then
4822         case Id is
4823
4824            --  The following should be ignored. They do not affect legality
4825            --  and may be target dependent. The basic idea of -gnatI is to
4826            --  ignore any rep clauses that may be target dependent but do not
4827            --  affect legality (except possibly to be rejected because they
4828            --  are incompatible with the compilation target).
4829
4830            when Attribute_Alignment
4831               | Attribute_Bit_Order
4832               | Attribute_Component_Size
4833               | Attribute_Default_Scalar_Storage_Order
4834               | Attribute_Machine_Radix
4835               | Attribute_Object_Size
4836               | Attribute_Scalar_Storage_Order
4837               | Attribute_Size
4838               | Attribute_Small
4839               | Attribute_Stream_Size
4840               | Attribute_Value_Size
4841            =>
4842               Kill_Rep_Clause (N);
4843               return;
4844
4845            --  The following should not be ignored, because in the first place
4846            --  they are reasonably portable, and should not cause problems
4847            --  in compiling code from another target, and also they do affect
4848            --  legality, e.g. failing to provide a stream attribute for a type
4849            --  may make a program illegal.
4850
4851            when Attribute_External_Tag
4852               | Attribute_Input
4853               | Attribute_Output
4854               | Attribute_Read
4855               | Attribute_Simple_Storage_Pool
4856               | Attribute_Storage_Pool
4857               | Attribute_Storage_Size
4858               | Attribute_Write
4859            =>
4860               null;
4861
4862            --  We do not do anything here with address clauses, they will be
4863            --  removed by Freeze later on, but for now, it works better to
4864            --  keep them in the tree.
4865
4866            when Attribute_Address =>
4867               null;
4868
4869            --  Other cases are errors ("attribute& cannot be set with
4870            --  definition clause"), which will be caught below.
4871
4872            when others =>
4873               null;
4874         end case;
4875      end if;
4876
4877      Analyze (Nam);
4878      Ent := Entity (Nam);
4879
4880      if Rep_Item_Too_Early (Ent, N) then
4881         return;
4882      end if;
4883
4884      --  Rep clause applies to full view of incomplete type or private type if
4885      --  we have one (if not, this is a premature use of the type). However,
4886      --  certain semantic checks need to be done on the specified entity (i.e.
4887      --  the private view), so we save it in Ent.
4888
4889      if Is_Private_Type (Ent)
4890        and then Is_Derived_Type (Ent)
4891        and then not Is_Tagged_Type (Ent)
4892        and then No (Full_View (Ent))
4893      then
4894         --  If this is a private type whose completion is a derivation from
4895         --  another private type, there is no full view, and the attribute
4896         --  belongs to the type itself, not its underlying parent.
4897
4898         U_Ent := Ent;
4899
4900      elsif Ekind (Ent) = E_Incomplete_Type then
4901
4902         --  The attribute applies to the full view, set the entity of the
4903         --  attribute definition accordingly.
4904
4905         Ent := Underlying_Type (Ent);
4906         U_Ent := Ent;
4907         Set_Entity (Nam, Ent);
4908
4909      else
4910         U_Ent := Underlying_Type (Ent);
4911      end if;
4912
4913      --  Avoid cascaded error
4914
4915      if Etype (Nam) = Any_Type then
4916         return;
4917
4918      --  Must be declared in current scope or in case of an aspect
4919      --  specification, must be visible in current scope.
4920
4921      elsif Scope (Ent) /= Current_Scope
4922        and then
4923          not (From_Aspect_Specification (N)
4924                and then Scope_Within_Or_Same (Current_Scope, Scope (Ent)))
4925      then
4926         Error_Msg_N ("entity must be declared in this scope", Nam);
4927         return;
4928
4929      --  Must not be a source renaming (we do have some cases where the
4930      --  expander generates a renaming, and those cases are OK, in such
4931      --  cases any attribute applies to the renamed object as well).
4932
4933      elsif Is_Object (Ent)
4934        and then Present (Renamed_Object (Ent))
4935      then
4936         --  Case of renamed object from source, this is an error
4937
4938         if Comes_From_Source (Renamed_Object (Ent)) then
4939            Get_Name_String (Chars (N));
4940            Error_Msg_Strlen := Name_Len;
4941            Error_Msg_String (1 .. Name_Len) := Name_Buffer (1 .. Name_Len);
4942            Error_Msg_N
4943              ("~ clause not allowed for a renaming declaration "
4944               & "(RM 13.1(6))", Nam);
4945            return;
4946
4947         --  For the case of a compiler generated renaming, the attribute
4948         --  definition clause applies to the renamed object created by the
4949         --  expander. The easiest general way to handle this is to create a
4950         --  copy of the attribute definition clause for this object.
4951
4952         elsif Is_Entity_Name (Renamed_Object (Ent)) then
4953            Insert_Action (N,
4954              Make_Attribute_Definition_Clause (Loc,
4955                Name       =>
4956                  New_Occurrence_Of (Entity (Renamed_Object (Ent)), Loc),
4957                Chars      => Chars (N),
4958                Expression => Duplicate_Subexpr (Expression (N))));
4959
4960         --  If the renamed object is not an entity, it must be a dereference
4961         --  of an unconstrained function call, and we must introduce a new
4962         --  declaration to capture the expression. This is needed in the case
4963         --  of 'Alignment, where the original declaration must be rewritten.
4964
4965         else
4966            pragma Assert
4967              (Nkind (Renamed_Object (Ent)) = N_Explicit_Dereference);
4968            null;
4969         end if;
4970
4971      --  If no underlying entity, use entity itself, applies to some
4972      --  previously detected error cases ???
4973
4974      elsif No (U_Ent) then
4975         U_Ent := Ent;
4976
4977      --  Cannot specify for a subtype (exception Object/Value_Size)
4978
4979      elsif Is_Type (U_Ent)
4980        and then not Is_First_Subtype (U_Ent)
4981        and then Id /= Attribute_Object_Size
4982        and then Id /= Attribute_Value_Size
4983        and then not From_At_Mod (N)
4984      then
4985         Error_Msg_N ("cannot specify attribute for subtype", Nam);
4986         return;
4987      end if;
4988
4989      Set_Entity (N, U_Ent);
4990
4991      --  Switch on particular attribute
4992
4993      case Id is
4994
4995         -------------
4996         -- Address --
4997         -------------
4998
4999         --  Address attribute definition clause
5000
5001         when Attribute_Address => Address : begin
5002
5003            --  A little error check, catch for X'Address use X'Address;
5004
5005            if Nkind (Nam) = N_Identifier
5006              and then Nkind (Expr) = N_Attribute_Reference
5007              and then Attribute_Name (Expr) = Name_Address
5008              and then Nkind (Prefix (Expr)) = N_Identifier
5009              and then Chars (Nam) = Chars (Prefix (Expr))
5010            then
5011               Error_Msg_NE
5012                 ("address for & is self-referencing", Prefix (Expr), Ent);
5013               return;
5014            end if;
5015
5016            --  Not that special case, carry on with analysis of expression
5017
5018            Analyze_And_Resolve (Expr, RTE (RE_Address));
5019
5020            --  Even when ignoring rep clauses we need to indicate that the
5021            --  entity has an address clause and thus it is legal to declare
5022            --  it imported. Freeze will get rid of the address clause later.
5023            --  Also call Set_Address_Taken to indicate that an address clause
5024            --  was present, even if we are about to remove it.
5025
5026            if Ignore_Rep_Clauses then
5027               Set_Address_Taken (U_Ent);
5028
5029               if Ekind_In (U_Ent, E_Variable, E_Constant) then
5030                  Record_Rep_Item (U_Ent, N);
5031               end if;
5032
5033               return;
5034            end if;
5035
5036            if Duplicate_Clause then
5037               null;
5038
5039            --  Case of address clause for subprogram
5040
5041            elsif Is_Subprogram (U_Ent) then
5042               if Has_Homonym (U_Ent) then
5043                  Error_Msg_N
5044                    ("address clause cannot be given for overloaded "
5045                     & "subprogram", Nam);
5046                  return;
5047               end if;
5048
5049               --  For subprograms, all address clauses are permitted, and we
5050               --  mark the subprogram as having a deferred freeze so that Gigi
5051               --  will not elaborate it too soon.
5052
5053               --  Above needs more comments, what is too soon about???
5054
5055               Set_Has_Delayed_Freeze (U_Ent);
5056
5057            --  Case of address clause for entry
5058
5059            elsif Ekind (U_Ent) = E_Entry then
5060               if Nkind (Parent (N)) = N_Task_Body then
5061                  Error_Msg_N
5062                    ("entry address must be specified in task spec", Nam);
5063                  return;
5064               end if;
5065
5066               --  For entries, we require a constant address
5067
5068               Check_Constant_Address_Clause (Expr, U_Ent);
5069
5070               --  Special checks for task types
5071
5072               if Is_Task_Type (Scope (U_Ent))
5073                 and then Comes_From_Source (Scope (U_Ent))
5074               then
5075                  Error_Msg_N
5076                    ("??entry address declared for entry in task type", N);
5077                  Error_Msg_N
5078                    ("\??only one task can be declared of this type", N);
5079               end if;
5080
5081               --  Entry address clauses are obsolescent
5082
5083               Check_Restriction (No_Obsolescent_Features, N);
5084
5085               if Warn_On_Obsolescent_Feature then
5086                  Error_Msg_N
5087                    ("?j?attaching interrupt to task entry is an obsolescent "
5088                     & "feature (RM J.7.1)", N);
5089                  Error_Msg_N
5090                    ("\?j?use interrupt procedure instead", N);
5091               end if;
5092
5093            --  Case of an address clause for a class-wide object, which is
5094            --  considered erroneous.
5095
5096            elsif Is_Class_Wide_Type (Etype (U_Ent)) then
5097               Error_Msg_NE
5098                 ("??class-wide object & must not be overlaid", Nam, U_Ent);
5099               Error_Msg_N
5100                 ("\??Program_Error will be raised at run time", Nam);
5101               Insert_Action (Declaration_Node (U_Ent),
5102                 Make_Raise_Program_Error (Loc,
5103                   Reason => PE_Overlaid_Controlled_Object));
5104               return;
5105
5106            --  Case of address clause for an object
5107
5108            elsif Ekind_In (U_Ent, E_Constant, E_Variable) then
5109               declare
5110                  Expr  : constant Node_Id := Expression (N);
5111                  O_Ent : Entity_Id;
5112                  Off   : Boolean;
5113
5114               begin
5115                  --  Exported variables cannot have an address clause, because
5116                  --  this cancels the effect of the pragma Export.
5117
5118                  if Is_Exported (U_Ent) then
5119                     Error_Msg_N
5120                       ("cannot export object with address clause", Nam);
5121                     return;
5122                  end if;
5123
5124                  Find_Overlaid_Entity (N, O_Ent, Off);
5125
5126                  if Present (O_Ent) then
5127
5128                     --  If the object overlays a constant object, mark it so
5129
5130                     if Is_Constant_Object (O_Ent) then
5131                        Set_Overlays_Constant (U_Ent);
5132                     end if;
5133
5134                     --  If the address clause is of the form:
5135
5136                     --    for X'Address use Y'Address;
5137
5138                     --  or
5139
5140                     --    C : constant Address := Y'Address;
5141                     --    ...
5142                     --    for X'Address use C;
5143
5144                     --  then we make an entry in the table to check the size
5145                     --  and alignment of the overlaying variable. But we defer
5146                     --  this check till after code generation to take full
5147                     --  advantage of the annotation done by the back end.
5148
5149                     --  If the entity has a generic type, the check will be
5150                     --  performed in the instance if the actual type justifies
5151                     --  it, and we do not insert the clause in the table to
5152                     --  prevent spurious warnings.
5153
5154                     --  Note: we used to test Comes_From_Source and only give
5155                     --  this warning for source entities, but we have removed
5156                     --  this test. It really seems bogus to generate overlays
5157                     --  that would trigger this warning in generated code.
5158                     --  Furthermore, by removing the test, we handle the
5159                     --  aspect case properly.
5160
5161                     if Is_Object (O_Ent)
5162                       and then not Is_Generic_Type (Etype (U_Ent))
5163                       and then Address_Clause_Overlay_Warnings
5164                     then
5165                        Register_Address_Clause_Check
5166                          (N, U_Ent, No_Uint, O_Ent, Off);
5167                     end if;
5168
5169                     --  If the overlay changes the storage order, mark the
5170                     --  entity as being volatile to block any optimization
5171                     --  for it since the construct is not really supported
5172                     --  by the back end.
5173
5174                     if (Is_Record_Type (Etype (U_Ent))
5175                          or else Is_Array_Type (Etype (U_Ent)))
5176                       and then (Is_Record_Type (Etype (O_Ent))
5177                                  or else Is_Array_Type (Etype (O_Ent)))
5178                       and then Reverse_Storage_Order (Etype (U_Ent)) /=
5179                                Reverse_Storage_Order (Etype (O_Ent))
5180                     then
5181                        Set_Treat_As_Volatile (U_Ent);
5182                     end if;
5183
5184                  else
5185                     --  If this is not an overlay, mark a variable as being
5186                     --  volatile to prevent unwanted optimizations. It's a
5187                     --  conservative interpretation of RM 13.3(19) for the
5188                     --  cases where the compiler cannot detect potential
5189                     --  aliasing issues easily and it also covers the case
5190                     --  of an absolute address where the volatile aspect is
5191                     --  kind of implicit.
5192
5193                     if Ekind (U_Ent) = E_Variable then
5194                        Set_Treat_As_Volatile (U_Ent);
5195                     end if;
5196
5197                     --  Make an entry in the table for an absolute address as
5198                     --  above to check that the value is compatible with the
5199                     --  alignment of the object.
5200
5201                     declare
5202                        Addr : constant Node_Id := Address_Value (Expr);
5203                     begin
5204                        if Compile_Time_Known_Value (Addr)
5205                          and then Address_Clause_Overlay_Warnings
5206                        then
5207                           Register_Address_Clause_Check
5208                             (N, U_Ent, Expr_Value (Addr), Empty, False);
5209                        end if;
5210                     end;
5211                  end if;
5212
5213                  --  Issue an unconditional warning for a constant overlaying
5214                  --  a variable. For the reverse case, we will issue it only
5215                  --  if the variable is modified.
5216
5217                  if Ekind (U_Ent) = E_Constant
5218                    and then Present (O_Ent)
5219                    and then not Overlays_Constant (U_Ent)
5220                    and then Address_Clause_Overlay_Warnings
5221                  then
5222                     Error_Msg_N ("??constant overlays a variable", Expr);
5223
5224                  --  Imported variables can have an address clause, but then
5225                  --  the import is pretty meaningless except to suppress
5226                  --  initializations, so we do not need such variables to
5227                  --  be statically allocated (and in fact it causes trouble
5228                  --  if the address clause is a local value).
5229
5230                  elsif Is_Imported (U_Ent) then
5231                     Set_Is_Statically_Allocated (U_Ent, False);
5232                  end if;
5233
5234                  --  We mark a possible modification of a variable with an
5235                  --  address clause, since it is likely aliasing is occurring.
5236
5237                  Note_Possible_Modification (Nam, Sure => False);
5238
5239                  --  Legality checks on the address clause for initialized
5240                  --  objects is deferred until the freeze point, because
5241                  --  a subsequent pragma might indicate that the object
5242                  --  is imported and thus not initialized. Also, the address
5243                  --  clause might involve entities that have yet to be
5244                  --  elaborated.
5245
5246                  Set_Has_Delayed_Freeze (U_Ent);
5247
5248                  --  If an initialization call has been generated for this
5249                  --  object, it needs to be deferred to after the freeze node
5250                  --  we have just now added, otherwise GIGI will see a
5251                  --  reference to the variable (as actual to the IP call)
5252                  --  before its definition.
5253
5254                  declare
5255                     Init_Call : constant Node_Id :=
5256                                   Remove_Init_Call (U_Ent, N);
5257
5258                  begin
5259                     if Present (Init_Call) then
5260                        Append_Freeze_Action (U_Ent, Init_Call);
5261
5262                        --  Reset Initialization_Statements pointer so that
5263                        --  if there is a pragma Import further down, it can
5264                        --  clear any default initialization.
5265
5266                        Set_Initialization_Statements (U_Ent, Init_Call);
5267                     end if;
5268                  end;
5269
5270                  --  Entity has delayed freeze, so we will generate an
5271                  --  alignment check at the freeze point unless suppressed.
5272
5273                  if not Range_Checks_Suppressed (U_Ent)
5274                    and then not Alignment_Checks_Suppressed (U_Ent)
5275                  then
5276                     Set_Check_Address_Alignment (N);
5277                  end if;
5278
5279                  --  Kill the size check code, since we are not allocating
5280                  --  the variable, it is somewhere else.
5281
5282                  Kill_Size_Check_Code (U_Ent);
5283               end;
5284
5285            --  Not a valid entity for an address clause
5286
5287            else
5288               Error_Msg_N ("address cannot be given for &", Nam);
5289            end if;
5290         end Address;
5291
5292         ---------------
5293         -- Alignment --
5294         ---------------
5295
5296         --  Alignment attribute definition clause
5297
5298         when Attribute_Alignment => Alignment : declare
5299            Align     : constant Uint := Get_Alignment_Value (Expr);
5300            Max_Align : constant Uint := UI_From_Int (Maximum_Alignment);
5301
5302         begin
5303            FOnly := True;
5304
5305            if not Is_Type (U_Ent)
5306              and then Ekind (U_Ent) /= E_Variable
5307              and then Ekind (U_Ent) /= E_Constant
5308            then
5309               Error_Msg_N ("alignment cannot be given for &", Nam);
5310
5311            elsif Duplicate_Clause then
5312               null;
5313
5314            elsif Align /= No_Uint then
5315               Set_Has_Alignment_Clause (U_Ent);
5316
5317               --  Tagged type case, check for attempt to set alignment to a
5318               --  value greater than Max_Align, and reset if so. This error
5319               --  is suppressed in ASIS mode to allow for different ASIS
5320               --  back ends or ASIS-based tools to query the illegal clause.
5321
5322               if Is_Tagged_Type (U_Ent)
5323                 and then Align > Max_Align
5324                 and then not ASIS_Mode
5325               then
5326                  Error_Msg_N
5327                    ("alignment for & set to Maximum_Aligment??", Nam);
5328                  Set_Alignment (U_Ent, Max_Align);
5329
5330               --  All other cases
5331
5332               else
5333                  Set_Alignment (U_Ent, Align);
5334               end if;
5335
5336               --  For an array type, U_Ent is the first subtype. In that case,
5337               --  also set the alignment of the anonymous base type so that
5338               --  other subtypes (such as the itypes for aggregates of the
5339               --  type) also receive the expected alignment.
5340
5341               if Is_Array_Type (U_Ent) then
5342                  Set_Alignment (Base_Type (U_Ent), Align);
5343               end if;
5344            end if;
5345         end Alignment;
5346
5347         ---------------
5348         -- Bit_Order --
5349         ---------------
5350
5351         --  Bit_Order attribute definition clause
5352
5353         when Attribute_Bit_Order =>
5354            if not Is_Record_Type (U_Ent) then
5355               Error_Msg_N
5356                 ("Bit_Order can only be defined for record type", Nam);
5357
5358            elsif Is_Tagged_Type (U_Ent) and then Is_Derived_Type (U_Ent) then
5359               Error_Msg_N
5360                 ("Bit_Order cannot be defined for record extensions", Nam);
5361
5362            elsif Duplicate_Clause then
5363               null;
5364
5365            else
5366               Analyze_And_Resolve (Expr, RTE (RE_Bit_Order));
5367
5368               if Etype (Expr) = Any_Type then
5369                  return;
5370
5371               elsif not Is_OK_Static_Expression (Expr) then
5372                  Flag_Non_Static_Expr
5373                    ("Bit_Order requires static expression!", Expr);
5374
5375               elsif (Expr_Value (Expr) = 0) /= Bytes_Big_Endian then
5376                  Set_Reverse_Bit_Order (Base_Type (U_Ent), True);
5377               end if;
5378            end if;
5379
5380         --------------------
5381         -- Component_Size --
5382         --------------------
5383
5384         --  Component_Size attribute definition clause
5385
5386         when Attribute_Component_Size => Component_Size_Case : declare
5387            Csize    : constant Uint := Static_Integer (Expr);
5388            Ctyp     : Entity_Id;
5389            Btype    : Entity_Id;
5390            Biased   : Boolean;
5391            New_Ctyp : Entity_Id;
5392            Decl     : Node_Id;
5393
5394         begin
5395            if not Is_Array_Type (U_Ent) then
5396               Error_Msg_N ("component size requires array type", Nam);
5397               return;
5398            end if;
5399
5400            Btype := Base_Type (U_Ent);
5401            Ctyp  := Component_Type (Btype);
5402
5403            if Duplicate_Clause then
5404               null;
5405
5406            elsif Rep_Item_Too_Early (Btype, N) then
5407               null;
5408
5409            elsif Csize /= No_Uint then
5410               Check_Size (Expr, Ctyp, Csize, Biased);
5411
5412               --  For the biased case, build a declaration for a subtype that
5413               --  will be used to represent the biased subtype that reflects
5414               --  the biased representation of components. We need the subtype
5415               --  to get proper conversions on referencing elements of the
5416               --  array.
5417
5418               if Biased then
5419                  New_Ctyp :=
5420                    Make_Defining_Identifier (Loc,
5421                      Chars =>
5422                        New_External_Name (Chars (U_Ent), 'C', 0, 'T'));
5423
5424                  Decl :=
5425                    Make_Subtype_Declaration (Loc,
5426                      Defining_Identifier => New_Ctyp,
5427                      Subtype_Indication  =>
5428                        New_Occurrence_Of (Component_Type (Btype), Loc));
5429
5430                  Set_Parent (Decl, N);
5431                  Analyze (Decl, Suppress => All_Checks);
5432
5433                  Set_Has_Delayed_Freeze        (New_Ctyp, False);
5434                  Set_Esize                     (New_Ctyp, Csize);
5435                  Set_RM_Size                   (New_Ctyp, Csize);
5436                  Init_Alignment                (New_Ctyp);
5437                  Set_Is_Itype                  (New_Ctyp, True);
5438                  Set_Associated_Node_For_Itype (New_Ctyp, U_Ent);
5439
5440                  Set_Component_Type (Btype, New_Ctyp);
5441                  Set_Biased (New_Ctyp, N, "component size clause");
5442               end if;
5443
5444               Set_Component_Size (Btype, Csize);
5445
5446               --  Deal with warning on overridden size
5447
5448               if Warn_On_Overridden_Size
5449                 and then Has_Size_Clause (Ctyp)
5450                 and then RM_Size (Ctyp) /= Csize
5451               then
5452                  Error_Msg_NE
5453                    ("component size overrides size clause for&?S?", N, Ctyp);
5454               end if;
5455
5456               Set_Has_Component_Size_Clause (Btype, True);
5457               Set_Has_Non_Standard_Rep (Btype, True);
5458            end if;
5459         end Component_Size_Case;
5460
5461         -----------------------
5462         -- Constant_Indexing --
5463         -----------------------
5464
5465         when Attribute_Constant_Indexing =>
5466            Check_Indexing_Functions;
5467
5468         ---------
5469         -- CPU --
5470         ---------
5471
5472         when Attribute_CPU =>
5473
5474            --  CPU attribute definition clause not allowed except from aspect
5475            --  specification.
5476
5477            if From_Aspect_Specification (N) then
5478               if not Is_Task_Type (U_Ent) then
5479                  Error_Msg_N ("CPU can only be defined for task", Nam);
5480
5481               elsif Duplicate_Clause then
5482                  null;
5483
5484               else
5485                  --  The expression must be analyzed in the special manner
5486                  --  described in "Handling of Default and Per-Object
5487                  --  Expressions" in sem.ads.
5488
5489                  --  The visibility to the components must be established
5490                  --  and restored before and after analysis.
5491
5492                  Push_Type (U_Ent);
5493                  Preanalyze_Spec_Expression (Expr, RTE (RE_CPU_Range));
5494                  Pop_Type (U_Ent);
5495
5496                  if not Is_OK_Static_Expression (Expr) then
5497                     Check_Restriction (Static_Priorities, Expr);
5498                  end if;
5499               end if;
5500
5501            else
5502               Error_Msg_N
5503                 ("attribute& cannot be set with definition clause", N);
5504            end if;
5505
5506         ----------------------
5507         -- Default_Iterator --
5508         ----------------------
5509
5510         when Attribute_Default_Iterator =>  Default_Iterator : declare
5511            Func : Entity_Id;
5512            Typ  : Entity_Id;
5513
5514         begin
5515            --  If target type is untagged, further checks are irrelevant
5516
5517            if not Is_Tagged_Type (U_Ent) then
5518               Error_Msg_N
5519                 ("aspect Default_Iterator applies to tagged type", Nam);
5520               return;
5521            end if;
5522
5523            Check_Iterator_Functions;
5524
5525            Analyze (Expr);
5526
5527            if not Is_Entity_Name (Expr)
5528              or else Ekind (Entity (Expr)) /= E_Function
5529            then
5530               Error_Msg_N ("aspect Iterator must be a function", Expr);
5531               return;
5532            else
5533               Func := Entity (Expr);
5534            end if;
5535
5536            --  The type of the first parameter must be T, T'class, or a
5537            --  corresponding access type (5.5.1 (8/3). If function is
5538            --  parameterless label type accordingly.
5539
5540            if No (First_Formal (Func)) then
5541               Typ := Any_Type;
5542            else
5543               Typ := Etype (First_Formal (Func));
5544            end if;
5545
5546            if Typ = U_Ent
5547              or else Typ = Class_Wide_Type (U_Ent)
5548              or else (Is_Access_Type (Typ)
5549                        and then Designated_Type (Typ) = U_Ent)
5550              or else (Is_Access_Type (Typ)
5551                        and then Designated_Type (Typ) =
5552                                          Class_Wide_Type (U_Ent))
5553            then
5554               null;
5555
5556            else
5557               Error_Msg_NE
5558                 ("Default Iterator must be a primitive of&", Func, U_Ent);
5559            end if;
5560         end Default_Iterator;
5561
5562         ------------------------
5563         -- Dispatching_Domain --
5564         ------------------------
5565
5566         when Attribute_Dispatching_Domain =>
5567
5568            --  Dispatching_Domain attribute definition clause not allowed
5569            --  except from aspect specification.
5570
5571            if From_Aspect_Specification (N) then
5572               if not Is_Task_Type (U_Ent) then
5573                  Error_Msg_N
5574                    ("Dispatching_Domain can only be defined for task", Nam);
5575
5576               elsif Duplicate_Clause then
5577                  null;
5578
5579               else
5580                  --  The expression must be analyzed in the special manner
5581                  --  described in "Handling of Default and Per-Object
5582                  --  Expressions" in sem.ads.
5583
5584                  --  The visibility to the components must be restored
5585
5586                  Push_Type (U_Ent);
5587
5588                  Preanalyze_Spec_Expression
5589                    (Expr, RTE (RE_Dispatching_Domain));
5590
5591                  Pop_Type (U_Ent);
5592               end if;
5593
5594            else
5595               Error_Msg_N
5596                 ("attribute& cannot be set with definition clause", N);
5597            end if;
5598
5599         ------------------
5600         -- External_Tag --
5601         ------------------
5602
5603         when Attribute_External_Tag =>
5604            if not Is_Tagged_Type (U_Ent) then
5605               Error_Msg_N ("should be a tagged type", Nam);
5606            end if;
5607
5608            if Duplicate_Clause then
5609               null;
5610
5611            else
5612               Analyze_And_Resolve (Expr, Standard_String);
5613
5614               if not Is_OK_Static_Expression (Expr) then
5615                  Flag_Non_Static_Expr
5616                    ("static string required for tag name!", Nam);
5617               end if;
5618
5619               if not Is_Library_Level_Entity (U_Ent) then
5620                  Error_Msg_NE
5621                    ("??non-unique external tag supplied for &", N, U_Ent);
5622                  Error_Msg_N
5623                    ("\??same external tag applies to all subprogram calls",
5624                     N);
5625                  Error_Msg_N
5626                    ("\??corresponding internal tag cannot be obtained", N);
5627               end if;
5628            end if;
5629
5630         --------------------------
5631         -- Implicit_Dereference --
5632         --------------------------
5633
5634         when Attribute_Implicit_Dereference =>
5635
5636            --  Legality checks already performed at the point of the type
5637            --  declaration, aspect is not delayed.
5638
5639            null;
5640
5641         -----------
5642         -- Input --
5643         -----------
5644
5645         when Attribute_Input =>
5646            Analyze_Stream_TSS_Definition (TSS_Stream_Input);
5647            Set_Has_Specified_Stream_Input (Ent);
5648
5649         ------------------------
5650         -- Interrupt_Priority --
5651         ------------------------
5652
5653         when Attribute_Interrupt_Priority =>
5654
5655            --  Interrupt_Priority attribute definition clause not allowed
5656            --  except from aspect specification.
5657
5658            if From_Aspect_Specification (N) then
5659               if not Is_Concurrent_Type (U_Ent) then
5660                  Error_Msg_N
5661                    ("Interrupt_Priority can only be defined for task and "
5662                     & "protected object", Nam);
5663
5664               elsif Duplicate_Clause then
5665                  null;
5666
5667               else
5668                  --  The expression must be analyzed in the special manner
5669                  --  described in "Handling of Default and Per-Object
5670                  --  Expressions" in sem.ads.
5671
5672                  --  The visibility to the components must be restored
5673
5674                  Push_Type (U_Ent);
5675
5676                  Preanalyze_Spec_Expression
5677                    (Expr, RTE (RE_Interrupt_Priority));
5678
5679                  Pop_Type (U_Ent);
5680
5681                  --  Check the No_Task_At_Interrupt_Priority restriction
5682
5683                  if Is_Task_Type (U_Ent) then
5684                     Check_Restriction (No_Task_At_Interrupt_Priority, N);
5685                  end if;
5686               end if;
5687
5688            else
5689               Error_Msg_N
5690                 ("attribute& cannot be set with definition clause", N);
5691            end if;
5692
5693         --------------
5694         -- Iterable --
5695         --------------
5696
5697         when Attribute_Iterable =>
5698            Analyze (Expr);
5699
5700            if Nkind (Expr) /= N_Aggregate then
5701               Error_Msg_N ("aspect Iterable must be an aggregate", Expr);
5702            end if;
5703
5704            declare
5705               Assoc : Node_Id;
5706
5707            begin
5708               Assoc := First (Component_Associations (Expr));
5709               while Present (Assoc) loop
5710                  Analyze (Expression (Assoc));
5711
5712                  if not Is_Entity_Name (Expression (Assoc)) then
5713                     Error_Msg_N ("value must be a function", Assoc);
5714                  end if;
5715
5716                  Next (Assoc);
5717               end loop;
5718            end;
5719
5720         ----------------------
5721         -- Iterator_Element --
5722         ----------------------
5723
5724         when Attribute_Iterator_Element =>
5725            Analyze (Expr);
5726
5727            if not Is_Entity_Name (Expr)
5728              or else not Is_Type (Entity (Expr))
5729            then
5730               Error_Msg_N ("aspect Iterator_Element must be a type", Expr);
5731            end if;
5732
5733         -------------------
5734         -- Machine_Radix --
5735         -------------------
5736
5737         --  Machine radix attribute definition clause
5738
5739         when Attribute_Machine_Radix => Machine_Radix : declare
5740            Radix : constant Uint := Static_Integer (Expr);
5741
5742         begin
5743            if not Is_Decimal_Fixed_Point_Type (U_Ent) then
5744               Error_Msg_N ("decimal fixed-point type expected for &", Nam);
5745
5746            elsif Duplicate_Clause then
5747               null;
5748
5749            elsif Radix /= No_Uint then
5750               Set_Has_Machine_Radix_Clause (U_Ent);
5751               Set_Has_Non_Standard_Rep (Base_Type (U_Ent));
5752
5753               if Radix = 2 then
5754                  null;
5755
5756               elsif Radix = 10 then
5757                  Set_Machine_Radix_10 (U_Ent);
5758
5759               --  The following error is suppressed in ASIS mode to allow for
5760               --  different ASIS back ends or ASIS-based tools to query the
5761               --  illegal clause.
5762
5763               elsif not ASIS_Mode then
5764                  Error_Msg_N ("machine radix value must be 2 or 10", Expr);
5765               end if;
5766            end if;
5767         end Machine_Radix;
5768
5769         -----------------
5770         -- Object_Size --
5771         -----------------
5772
5773         --  Object_Size attribute definition clause
5774
5775         when Attribute_Object_Size => Object_Size : declare
5776            Size : constant Uint := Static_Integer (Expr);
5777
5778            Biased : Boolean;
5779            pragma Warnings (Off, Biased);
5780
5781         begin
5782            if not Is_Type (U_Ent) then
5783               Error_Msg_N ("Object_Size cannot be given for &", Nam);
5784
5785            elsif Duplicate_Clause then
5786               null;
5787
5788            else
5789               Check_Size (Expr, U_Ent, Size, Biased);
5790
5791               --  The following errors are suppressed in ASIS mode to allow
5792               --  for different ASIS back ends or ASIS-based tools to query
5793               --  the illegal clause.
5794
5795               if ASIS_Mode then
5796                  null;
5797
5798               elsif Is_Scalar_Type (U_Ent) then
5799                  if Size /= 8 and then Size /= 16 and then Size /= 32
5800                    and then UI_Mod (Size, 64) /= 0
5801                  then
5802                     Error_Msg_N
5803                       ("Object_Size must be 8, 16, 32, or multiple of 64",
5804                        Expr);
5805                  end if;
5806
5807               elsif Size mod 8 /= 0 then
5808                  Error_Msg_N ("Object_Size must be a multiple of 8", Expr);
5809               end if;
5810
5811               Set_Esize (U_Ent, Size);
5812               Set_Has_Object_Size_Clause (U_Ent);
5813               Alignment_Check_For_Size_Change (U_Ent, Size);
5814            end if;
5815         end Object_Size;
5816
5817         ------------
5818         -- Output --
5819         ------------
5820
5821         when Attribute_Output =>
5822            Analyze_Stream_TSS_Definition (TSS_Stream_Output);
5823            Set_Has_Specified_Stream_Output (Ent);
5824
5825         --------------
5826         -- Priority --
5827         --------------
5828
5829         when Attribute_Priority =>
5830
5831            --  Priority attribute definition clause not allowed except from
5832            --  aspect specification.
5833
5834            if From_Aspect_Specification (N) then
5835               if not (Is_Concurrent_Type (U_Ent)
5836                        or else Ekind (U_Ent) = E_Procedure)
5837               then
5838                  Error_Msg_N
5839                    ("Priority can only be defined for task and protected "
5840                     & "object", Nam);
5841
5842               elsif Duplicate_Clause then
5843                  null;
5844
5845               else
5846                  --  The expression must be analyzed in the special manner
5847                  --  described in "Handling of Default and Per-Object
5848                  --  Expressions" in sem.ads.
5849
5850                  --  The visibility to the components must be restored
5851
5852                  Push_Type (U_Ent);
5853                  Preanalyze_Spec_Expression (Expr, Standard_Integer);
5854                  Pop_Type (U_Ent);
5855
5856                  if not Is_OK_Static_Expression (Expr) then
5857                     Check_Restriction (Static_Priorities, Expr);
5858                  end if;
5859               end if;
5860
5861            else
5862               Error_Msg_N
5863                 ("attribute& cannot be set with definition clause", N);
5864            end if;
5865
5866         ----------
5867         -- Read --
5868         ----------
5869
5870         when Attribute_Read =>
5871            Analyze_Stream_TSS_Definition (TSS_Stream_Read);
5872            Set_Has_Specified_Stream_Read (Ent);
5873
5874         --------------------------
5875         -- Scalar_Storage_Order --
5876         --------------------------
5877
5878         --  Scalar_Storage_Order attribute definition clause
5879
5880         when Attribute_Scalar_Storage_Order =>
5881            if not (Is_Record_Type (U_Ent) or else Is_Array_Type (U_Ent)) then
5882               Error_Msg_N
5883                 ("Scalar_Storage_Order can only be defined for record or "
5884                  & "array type", Nam);
5885
5886            elsif Duplicate_Clause then
5887               null;
5888
5889            else
5890               Analyze_And_Resolve (Expr, RTE (RE_Bit_Order));
5891
5892               if Etype (Expr) = Any_Type then
5893                  return;
5894
5895               elsif not Is_OK_Static_Expression (Expr) then
5896                  Flag_Non_Static_Expr
5897                    ("Scalar_Storage_Order requires static expression!", Expr);
5898
5899               elsif (Expr_Value (Expr) = 0) /= Bytes_Big_Endian then
5900
5901                  --  Here for the case of a non-default (i.e. non-confirming)
5902                  --  Scalar_Storage_Order attribute definition.
5903
5904                  if Support_Nondefault_SSO_On_Target then
5905                     Set_Reverse_Storage_Order (Base_Type (U_Ent), True);
5906                  else
5907                     Error_Msg_N
5908                       ("non-default Scalar_Storage_Order not supported on "
5909                        & "target", Expr);
5910                  end if;
5911               end if;
5912
5913               --  Clear SSO default indications since explicit setting of the
5914               --  order overrides the defaults.
5915
5916               Set_SSO_Set_Low_By_Default  (Base_Type (U_Ent), False);
5917               Set_SSO_Set_High_By_Default (Base_Type (U_Ent), False);
5918            end if;
5919
5920         ----------
5921         -- Size --
5922         ----------
5923
5924         --  Size attribute definition clause
5925
5926         when Attribute_Size => Size : declare
5927            Size   : constant Uint := Static_Integer (Expr);
5928            Etyp   : Entity_Id;
5929            Biased : Boolean;
5930
5931         begin
5932            FOnly := True;
5933
5934            if Duplicate_Clause then
5935               null;
5936
5937            elsif not Is_Type (U_Ent)
5938              and then Ekind (U_Ent) /= E_Variable
5939              and then Ekind (U_Ent) /= E_Constant
5940            then
5941               Error_Msg_N ("size cannot be given for &", Nam);
5942
5943            elsif Is_Array_Type (U_Ent)
5944              and then not Is_Constrained (U_Ent)
5945            then
5946               Error_Msg_N
5947                 ("size cannot be given for unconstrained array", Nam);
5948
5949            elsif Size /= No_Uint then
5950               if Is_Type (U_Ent) then
5951                  Etyp := U_Ent;
5952               else
5953                  Etyp := Etype (U_Ent);
5954               end if;
5955
5956               --  Check size, note that Gigi is in charge of checking that the
5957               --  size of an array or record type is OK. Also we do not check
5958               --  the size in the ordinary fixed-point case, since it is too
5959               --  early to do so (there may be subsequent small clause that
5960               --  affects the size). We can check the size if a small clause
5961               --  has already been given.
5962
5963               if not Is_Ordinary_Fixed_Point_Type (U_Ent)
5964                 or else Has_Small_Clause (U_Ent)
5965               then
5966                  Check_Size (Expr, Etyp, Size, Biased);
5967                  Set_Biased (U_Ent, N, "size clause", Biased);
5968               end if;
5969
5970               --  For types set RM_Size and Esize if possible
5971
5972               if Is_Type (U_Ent) then
5973                  Set_RM_Size (U_Ent, Size);
5974
5975                  --  For elementary types, increase Object_Size to power of 2,
5976                  --  but not less than a storage unit in any case (normally
5977                  --  this means it will be byte addressable).
5978
5979                  --  For all other types, nothing else to do, we leave Esize
5980                  --  (object size) unset, the back end will set it from the
5981                  --  size and alignment in an appropriate manner.
5982
5983                  --  In both cases, we check whether the alignment must be
5984                  --  reset in the wake of the size change.
5985
5986                  if Is_Elementary_Type (U_Ent) then
5987                     if Size <= System_Storage_Unit then
5988                        Init_Esize (U_Ent, System_Storage_Unit);
5989                     elsif Size <= 16 then
5990                        Init_Esize (U_Ent, 16);
5991                     elsif Size <= 32 then
5992                        Init_Esize (U_Ent, 32);
5993                     else
5994                        Set_Esize  (U_Ent, (Size + 63) / 64 * 64);
5995                     end if;
5996
5997                     Alignment_Check_For_Size_Change (U_Ent, Esize (U_Ent));
5998                  else
5999                     Alignment_Check_For_Size_Change (U_Ent, Size);
6000                  end if;
6001
6002               --  For objects, set Esize only
6003
6004               else
6005                  --  The following error is suppressed in ASIS mode to allow
6006                  --  for different ASIS back ends or ASIS-based tools to query
6007                  --  the illegal clause.
6008
6009                  if Is_Elementary_Type (Etyp)
6010                    and then Size /= System_Storage_Unit
6011                    and then Size /= System_Storage_Unit * 2
6012                    and then Size /= System_Storage_Unit * 4
6013                    and then Size /= System_Storage_Unit * 8
6014                    and then not ASIS_Mode
6015                  then
6016                     Error_Msg_Uint_1 := UI_From_Int (System_Storage_Unit);
6017                     Error_Msg_Uint_2 := Error_Msg_Uint_1 * 8;
6018                     Error_Msg_N
6019                       ("size for primitive object must be a power of 2 in "
6020                        & "the range ^-^", N);
6021                  end if;
6022
6023                  Set_Esize (U_Ent, Size);
6024               end if;
6025
6026               Set_Has_Size_Clause (U_Ent);
6027            end if;
6028         end Size;
6029
6030         -----------
6031         -- Small --
6032         -----------
6033
6034         --  Small attribute definition clause
6035
6036         when Attribute_Small => Small : declare
6037            Implicit_Base : constant Entity_Id := Base_Type (U_Ent);
6038            Small         : Ureal;
6039
6040         begin
6041            Analyze_And_Resolve (Expr, Any_Real);
6042
6043            if Etype (Expr) = Any_Type then
6044               return;
6045
6046            elsif not Is_OK_Static_Expression (Expr) then
6047               Flag_Non_Static_Expr
6048                 ("small requires static expression!", Expr);
6049               return;
6050
6051            else
6052               Small := Expr_Value_R (Expr);
6053
6054               if Small <= Ureal_0 then
6055                  Error_Msg_N ("small value must be greater than zero", Expr);
6056                  return;
6057               end if;
6058
6059            end if;
6060
6061            if not Is_Ordinary_Fixed_Point_Type (U_Ent) then
6062               Error_Msg_N
6063                 ("small requires an ordinary fixed point type", Nam);
6064
6065            elsif Has_Small_Clause (U_Ent) then
6066               Error_Msg_N ("small already given for &", Nam);
6067
6068            elsif Small > Delta_Value (U_Ent) then
6069               Error_Msg_N
6070                 ("small value must not be greater than delta value", Nam);
6071
6072            else
6073               Set_Small_Value (U_Ent, Small);
6074               Set_Small_Value (Implicit_Base, Small);
6075               Set_Has_Small_Clause (U_Ent);
6076               Set_Has_Small_Clause (Implicit_Base);
6077               Set_Has_Non_Standard_Rep (Implicit_Base);
6078            end if;
6079         end Small;
6080
6081         ------------------
6082         -- Storage_Pool --
6083         ------------------
6084
6085         --  Storage_Pool attribute definition clause
6086
6087         when Attribute_Simple_Storage_Pool
6088            | Attribute_Storage_Pool
6089         =>
6090         Storage_Pool : declare
6091            Pool : Entity_Id;
6092            T    : Entity_Id;
6093
6094         begin
6095            if Ekind (U_Ent) = E_Access_Subprogram_Type then
6096               Error_Msg_N
6097                 ("storage pool cannot be given for access-to-subprogram type",
6098                  Nam);
6099               return;
6100
6101            elsif not Ekind_In (U_Ent, E_Access_Type, E_General_Access_Type)
6102            then
6103               Error_Msg_N
6104                 ("storage pool can only be given for access types", Nam);
6105               return;
6106
6107            elsif Is_Derived_Type (U_Ent) then
6108               Error_Msg_N
6109                 ("storage pool cannot be given for a derived access type",
6110                  Nam);
6111
6112            elsif Duplicate_Clause then
6113               return;
6114
6115            elsif Present (Associated_Storage_Pool (U_Ent)) then
6116               Error_Msg_N ("storage pool already given for &", Nam);
6117               return;
6118            end if;
6119
6120            --  Check for Storage_Size previously given
6121
6122            declare
6123               SS : constant Node_Id :=
6124                      Get_Attribute_Definition_Clause
6125                        (U_Ent, Attribute_Storage_Size);
6126            begin
6127               if Present (SS) then
6128                  Check_Pool_Size_Clash (U_Ent, N, SS);
6129               end if;
6130            end;
6131
6132            --  Storage_Pool case
6133
6134            if Id = Attribute_Storage_Pool then
6135               Analyze_And_Resolve
6136                 (Expr, Class_Wide_Type (RTE (RE_Root_Storage_Pool)));
6137
6138            --  In the Simple_Storage_Pool case, we allow a variable of any
6139            --  simple storage pool type, so we Resolve without imposing an
6140            --  expected type.
6141
6142            else
6143               Analyze_And_Resolve (Expr);
6144
6145               if not Present (Get_Rep_Pragma
6146                                 (Etype (Expr), Name_Simple_Storage_Pool_Type))
6147               then
6148                  Error_Msg_N
6149                    ("expression must be of a simple storage pool type", Expr);
6150               end if;
6151            end if;
6152
6153            if not Denotes_Variable (Expr) then
6154               Error_Msg_N ("storage pool must be a variable", Expr);
6155               return;
6156            end if;
6157
6158            if Nkind (Expr) = N_Type_Conversion then
6159               T := Etype (Expression (Expr));
6160            else
6161               T := Etype (Expr);
6162            end if;
6163
6164            --  The Stack_Bounded_Pool is used internally for implementing
6165            --  access types with a Storage_Size. Since it only work properly
6166            --  when used on one specific type, we need to check that it is not
6167            --  hijacked improperly:
6168
6169            --    type T is access Integer;
6170            --    for T'Storage_Size use n;
6171            --    type Q is access Float;
6172            --    for Q'Storage_Size use T'Storage_Size; -- incorrect
6173
6174            if RTE_Available (RE_Stack_Bounded_Pool)
6175              and then Base_Type (T) = RTE (RE_Stack_Bounded_Pool)
6176            then
6177               Error_Msg_N ("non-shareable internal Pool", Expr);
6178               return;
6179            end if;
6180
6181            --  If the argument is a name that is not an entity name, then
6182            --  we construct a renaming operation to define an entity of
6183            --  type storage pool.
6184
6185            if not Is_Entity_Name (Expr)
6186              and then Is_Object_Reference (Expr)
6187            then
6188               Pool := Make_Temporary (Loc, 'P', Expr);
6189
6190               declare
6191                  Rnode : constant Node_Id :=
6192                            Make_Object_Renaming_Declaration (Loc,
6193                              Defining_Identifier => Pool,
6194                              Subtype_Mark        =>
6195                                New_Occurrence_Of (Etype (Expr), Loc),
6196                              Name                => Expr);
6197
6198               begin
6199                  --  If the attribute definition clause comes from an aspect
6200                  --  clause, then insert the renaming before the associated
6201                  --  entity's declaration, since the attribute clause has
6202                  --  not yet been appended to the declaration list.
6203
6204                  if From_Aspect_Specification (N) then
6205                     Insert_Before (Parent (Entity (N)), Rnode);
6206                  else
6207                     Insert_Before (N, Rnode);
6208                  end if;
6209
6210                  Analyze (Rnode);
6211                  Set_Associated_Storage_Pool (U_Ent, Pool);
6212               end;
6213
6214            elsif Is_Entity_Name (Expr) then
6215               Pool := Entity (Expr);
6216
6217               --  If pool is a renamed object, get original one. This can
6218               --  happen with an explicit renaming, and within instances.
6219
6220               while Present (Renamed_Object (Pool))
6221                 and then Is_Entity_Name (Renamed_Object (Pool))
6222               loop
6223                  Pool := Entity (Renamed_Object (Pool));
6224               end loop;
6225
6226               if Present (Renamed_Object (Pool))
6227                 and then Nkind (Renamed_Object (Pool)) = N_Type_Conversion
6228                 and then Is_Entity_Name (Expression (Renamed_Object (Pool)))
6229               then
6230                  Pool := Entity (Expression (Renamed_Object (Pool)));
6231               end if;
6232
6233               Set_Associated_Storage_Pool (U_Ent, Pool);
6234
6235            elsif Nkind (Expr) = N_Type_Conversion
6236              and then Is_Entity_Name (Expression (Expr))
6237              and then Nkind (Original_Node (Expr)) = N_Attribute_Reference
6238            then
6239               Pool := Entity (Expression (Expr));
6240               Set_Associated_Storage_Pool (U_Ent, Pool);
6241
6242            else
6243               Error_Msg_N ("incorrect reference to a Storage Pool", Expr);
6244               return;
6245            end if;
6246         end Storage_Pool;
6247
6248         ------------------
6249         -- Storage_Size --
6250         ------------------
6251
6252         --  Storage_Size attribute definition clause
6253
6254         when Attribute_Storage_Size => Storage_Size : declare
6255            Btype : constant Entity_Id := Base_Type (U_Ent);
6256
6257         begin
6258            if Is_Task_Type (U_Ent) then
6259
6260               --  Check obsolescent (but never obsolescent if from aspect)
6261
6262               if not From_Aspect_Specification (N) then
6263                  Check_Restriction (No_Obsolescent_Features, N);
6264
6265                  if Warn_On_Obsolescent_Feature then
6266                     Error_Msg_N
6267                       ("?j?storage size clause for task is an obsolescent "
6268                        & "feature (RM J.9)", N);
6269                     Error_Msg_N ("\?j?use Storage_Size pragma instead", N);
6270                  end if;
6271               end if;
6272
6273               FOnly := True;
6274            end if;
6275
6276            if not Is_Access_Type (U_Ent)
6277              and then Ekind (U_Ent) /= E_Task_Type
6278            then
6279               Error_Msg_N ("storage size cannot be given for &", Nam);
6280
6281            elsif Is_Access_Type (U_Ent) and Is_Derived_Type (U_Ent) then
6282               Error_Msg_N
6283                 ("storage size cannot be given for a derived access type",
6284                  Nam);
6285
6286            elsif Duplicate_Clause then
6287               null;
6288
6289            else
6290               Analyze_And_Resolve (Expr, Any_Integer);
6291
6292               if Is_Access_Type (U_Ent) then
6293
6294                  --  Check for Storage_Pool previously given
6295
6296                  declare
6297                     SP : constant Node_Id :=
6298                            Get_Attribute_Definition_Clause
6299                              (U_Ent, Attribute_Storage_Pool);
6300
6301                  begin
6302                     if Present (SP) then
6303                        Check_Pool_Size_Clash (U_Ent, SP, N);
6304                     end if;
6305                  end;
6306
6307                  --  Special case of for x'Storage_Size use 0
6308
6309                  if Is_OK_Static_Expression (Expr)
6310                    and then Expr_Value (Expr) = 0
6311                  then
6312                     Set_No_Pool_Assigned (Btype);
6313                  end if;
6314               end if;
6315
6316               Set_Has_Storage_Size_Clause (Btype);
6317            end if;
6318         end Storage_Size;
6319
6320         -----------------
6321         -- Stream_Size --
6322         -----------------
6323
6324         when Attribute_Stream_Size => Stream_Size : declare
6325            Size : constant Uint := Static_Integer (Expr);
6326
6327         begin
6328            if Ada_Version <= Ada_95 then
6329               Check_Restriction (No_Implementation_Attributes, N);
6330            end if;
6331
6332            if Duplicate_Clause then
6333               null;
6334
6335            elsif Is_Elementary_Type (U_Ent) then
6336
6337               --  The following errors are suppressed in ASIS mode to allow
6338               --  for different ASIS back ends or ASIS-based tools to query
6339               --  the illegal clause.
6340
6341               if ASIS_Mode then
6342                  null;
6343
6344               elsif Size /= System_Storage_Unit
6345                 and then Size /= System_Storage_Unit * 2
6346                 and then Size /= System_Storage_Unit * 4
6347                 and then Size /= System_Storage_Unit * 8
6348               then
6349                  Error_Msg_Uint_1 := UI_From_Int (System_Storage_Unit);
6350                  Error_Msg_N
6351                    ("stream size for elementary type must be a power of 2 "
6352                     & "and at least ^", N);
6353
6354               elsif RM_Size (U_Ent) > Size then
6355                  Error_Msg_Uint_1 := RM_Size (U_Ent);
6356                  Error_Msg_N
6357                    ("stream size for elementary type must be a power of 2 "
6358                     & "and at least ^", N);
6359               end if;
6360
6361               Set_Has_Stream_Size_Clause (U_Ent);
6362
6363            else
6364               Error_Msg_N ("Stream_Size cannot be given for &", Nam);
6365            end if;
6366         end Stream_Size;
6367
6368         ----------------
6369         -- Value_Size --
6370         ----------------
6371
6372         --  Value_Size attribute definition clause
6373
6374         when Attribute_Value_Size => Value_Size : declare
6375            Size   : constant Uint := Static_Integer (Expr);
6376            Biased : Boolean;
6377
6378         begin
6379            if not Is_Type (U_Ent) then
6380               Error_Msg_N ("Value_Size cannot be given for &", Nam);
6381
6382            elsif Duplicate_Clause then
6383               null;
6384
6385            elsif Is_Array_Type (U_Ent)
6386              and then not Is_Constrained (U_Ent)
6387            then
6388               Error_Msg_N
6389                 ("Value_Size cannot be given for unconstrained array", Nam);
6390
6391            else
6392               if Is_Elementary_Type (U_Ent) then
6393                  Check_Size (Expr, U_Ent, Size, Biased);
6394                  Set_Biased (U_Ent, N, "value size clause", Biased);
6395               end if;
6396
6397               Set_RM_Size (U_Ent, Size);
6398            end if;
6399         end Value_Size;
6400
6401         -----------------------
6402         -- Variable_Indexing --
6403         -----------------------
6404
6405         when Attribute_Variable_Indexing =>
6406            Check_Indexing_Functions;
6407
6408         -----------
6409         -- Write --
6410         -----------
6411
6412         when Attribute_Write =>
6413            Analyze_Stream_TSS_Definition (TSS_Stream_Write);
6414            Set_Has_Specified_Stream_Write (Ent);
6415
6416         --  All other attributes cannot be set
6417
6418         when others =>
6419            Error_Msg_N
6420              ("attribute& cannot be set with definition clause", N);
6421      end case;
6422
6423      --  The test for the type being frozen must be performed after any
6424      --  expression the clause has been analyzed since the expression itself
6425      --  might cause freezing that makes the clause illegal.
6426
6427      if Rep_Item_Too_Late (U_Ent, N, FOnly) then
6428         return;
6429      end if;
6430   end Analyze_Attribute_Definition_Clause;
6431
6432   ----------------------------
6433   -- Analyze_Code_Statement --
6434   ----------------------------
6435
6436   procedure Analyze_Code_Statement (N : Node_Id) is
6437      HSS   : constant Node_Id   := Parent (N);
6438      SBody : constant Node_Id   := Parent (HSS);
6439      Subp  : constant Entity_Id := Current_Scope;
6440      Stmt  : Node_Id;
6441      Decl  : Node_Id;
6442      StmtO : Node_Id;
6443      DeclO : Node_Id;
6444
6445   begin
6446      --  Accept foreign code statements for CodePeer. The analysis is skipped
6447      --  to avoid rejecting unrecognized constructs.
6448
6449      if CodePeer_Mode then
6450         Set_Analyzed (N);
6451         return;
6452      end if;
6453
6454      --  Analyze and check we get right type, note that this implements the
6455      --  requirement (RM 13.8(1)) that Machine_Code be with'ed, since that is
6456      --  the only way that Asm_Insn could possibly be visible.
6457
6458      Analyze_And_Resolve (Expression (N));
6459
6460      if Etype (Expression (N)) = Any_Type then
6461         return;
6462      elsif Etype (Expression (N)) /= RTE (RE_Asm_Insn) then
6463         Error_Msg_N ("incorrect type for code statement", N);
6464         return;
6465      end if;
6466
6467      Check_Code_Statement (N);
6468
6469      --  Make sure we appear in the handled statement sequence of a subprogram
6470      --  (RM 13.8(3)).
6471
6472      if Nkind (HSS) /= N_Handled_Sequence_Of_Statements
6473        or else Nkind (SBody) /= N_Subprogram_Body
6474      then
6475         Error_Msg_N
6476           ("code statement can only appear in body of subprogram", N);
6477         return;
6478      end if;
6479
6480      --  Do remaining checks (RM 13.8(3)) if not already done
6481
6482      if not Is_Machine_Code_Subprogram (Subp) then
6483         Set_Is_Machine_Code_Subprogram (Subp);
6484
6485         --  No exception handlers allowed
6486
6487         if Present (Exception_Handlers (HSS)) then
6488            Error_Msg_N
6489              ("exception handlers not permitted in machine code subprogram",
6490               First (Exception_Handlers (HSS)));
6491         end if;
6492
6493         --  No declarations other than use clauses and pragmas (we allow
6494         --  certain internally generated declarations as well).
6495
6496         Decl := First (Declarations (SBody));
6497         while Present (Decl) loop
6498            DeclO := Original_Node (Decl);
6499            if Comes_From_Source (DeclO)
6500              and not Nkind_In (DeclO, N_Pragma,
6501                                       N_Use_Package_Clause,
6502                                       N_Use_Type_Clause,
6503                                       N_Implicit_Label_Declaration)
6504            then
6505               Error_Msg_N
6506                 ("this declaration not allowed in machine code subprogram",
6507                  DeclO);
6508            end if;
6509
6510            Next (Decl);
6511         end loop;
6512
6513         --  No statements other than code statements, pragmas, and labels.
6514         --  Again we allow certain internally generated statements.
6515
6516         --  In Ada 2012, qualified expressions are names, and the code
6517         --  statement is initially parsed as a procedure call.
6518
6519         Stmt := First (Statements (HSS));
6520         while Present (Stmt) loop
6521            StmtO := Original_Node (Stmt);
6522
6523            --  A procedure call transformed into a code statement is OK
6524
6525            if Ada_Version >= Ada_2012
6526              and then Nkind (StmtO) = N_Procedure_Call_Statement
6527              and then Nkind (Name (StmtO)) = N_Qualified_Expression
6528            then
6529               null;
6530
6531            elsif Comes_From_Source (StmtO)
6532              and then not Nkind_In (StmtO, N_Pragma,
6533                                            N_Label,
6534                                            N_Code_Statement)
6535            then
6536               Error_Msg_N
6537                 ("this statement is not allowed in machine code subprogram",
6538                  StmtO);
6539            end if;
6540
6541            Next (Stmt);
6542         end loop;
6543      end if;
6544   end Analyze_Code_Statement;
6545
6546   -----------------------------------------------
6547   -- Analyze_Enumeration_Representation_Clause --
6548   -----------------------------------------------
6549
6550   procedure Analyze_Enumeration_Representation_Clause (N : Node_Id) is
6551      Ident    : constant Node_Id := Identifier (N);
6552      Aggr     : constant Node_Id := Array_Aggregate (N);
6553      Enumtype : Entity_Id;
6554      Elit     : Entity_Id;
6555      Expr     : Node_Id;
6556      Assoc    : Node_Id;
6557      Choice   : Node_Id;
6558      Val      : Uint;
6559
6560      Err : Boolean := False;
6561      --  Set True to avoid cascade errors and crashes on incorrect source code
6562
6563      Lo : constant Uint := Expr_Value (Type_Low_Bound (Universal_Integer));
6564      Hi : constant Uint := Expr_Value (Type_High_Bound (Universal_Integer));
6565      --  Allowed range of universal integer (= allowed range of enum lit vals)
6566
6567      Min : Uint;
6568      Max : Uint;
6569      --  Minimum and maximum values of entries
6570
6571      Max_Node : Node_Id := Empty; -- init to avoid warning
6572      --  Pointer to node for literal providing max value
6573
6574   begin
6575      if Ignore_Rep_Clauses then
6576         Kill_Rep_Clause (N);
6577         return;
6578      end if;
6579
6580      --  Ignore enumeration rep clauses by default in CodePeer mode,
6581      --  unless -gnatd.I is specified, as a work around for potential false
6582      --  positive messages.
6583
6584      if CodePeer_Mode and not Debug_Flag_Dot_II then
6585         return;
6586      end if;
6587
6588      --  First some basic error checks
6589
6590      Find_Type (Ident);
6591      Enumtype := Entity (Ident);
6592
6593      if Enumtype = Any_Type
6594        or else Rep_Item_Too_Early (Enumtype, N)
6595      then
6596         return;
6597      else
6598         Enumtype := Underlying_Type (Enumtype);
6599      end if;
6600
6601      if not Is_Enumeration_Type (Enumtype) then
6602         Error_Msg_NE
6603           ("enumeration type required, found}",
6604            Ident, First_Subtype (Enumtype));
6605         return;
6606      end if;
6607
6608      --  Ignore rep clause on generic actual type. This will already have
6609      --  been flagged on the template as an error, and this is the safest
6610      --  way to ensure we don't get a junk cascaded message in the instance.
6611
6612      if Is_Generic_Actual_Type (Enumtype) then
6613         return;
6614
6615      --  Type must be in current scope
6616
6617      elsif Scope (Enumtype) /= Current_Scope then
6618         Error_Msg_N ("type must be declared in this scope", Ident);
6619         return;
6620
6621      --  Type must be a first subtype
6622
6623      elsif not Is_First_Subtype (Enumtype) then
6624         Error_Msg_N ("cannot give enumeration rep clause for subtype", N);
6625         return;
6626
6627      --  Ignore duplicate rep clause
6628
6629      elsif Has_Enumeration_Rep_Clause (Enumtype) then
6630         Error_Msg_N ("duplicate enumeration rep clause ignored", N);
6631         return;
6632
6633      --  Don't allow rep clause for standard [wide_[wide_]]character
6634
6635      elsif Is_Standard_Character_Type (Enumtype) then
6636         Error_Msg_N ("enumeration rep clause not allowed for this type", N);
6637         return;
6638
6639      --  Check that the expression is a proper aggregate (no parentheses)
6640
6641      elsif Paren_Count (Aggr) /= 0 then
6642         Error_Msg
6643           ("extra parentheses surrounding aggregate not allowed",
6644            First_Sloc (Aggr));
6645         return;
6646
6647      --  All tests passed, so set rep clause in place
6648
6649      else
6650         Set_Has_Enumeration_Rep_Clause (Enumtype);
6651         Set_Has_Enumeration_Rep_Clause (Base_Type (Enumtype));
6652      end if;
6653
6654      --  Now we process the aggregate. Note that we don't use the normal
6655      --  aggregate code for this purpose, because we don't want any of the
6656      --  normal expansion activities, and a number of special semantic
6657      --  rules apply (including the component type being any integer type)
6658
6659      Elit := First_Literal (Enumtype);
6660
6661      --  First the positional entries if any
6662
6663      if Present (Expressions (Aggr)) then
6664         Expr := First (Expressions (Aggr));
6665         while Present (Expr) loop
6666            if No (Elit) then
6667               Error_Msg_N ("too many entries in aggregate", Expr);
6668               return;
6669            end if;
6670
6671            Val := Static_Integer (Expr);
6672
6673            --  Err signals that we found some incorrect entries processing
6674            --  the list. The final checks for completeness and ordering are
6675            --  skipped in this case.
6676
6677            if Val = No_Uint then
6678               Err := True;
6679
6680            elsif Val < Lo or else Hi < Val then
6681               Error_Msg_N ("value outside permitted range", Expr);
6682               Err := True;
6683            end if;
6684
6685            Set_Enumeration_Rep (Elit, Val);
6686            Set_Enumeration_Rep_Expr (Elit, Expr);
6687            Next (Expr);
6688            Next (Elit);
6689         end loop;
6690      end if;
6691
6692      --  Now process the named entries if present
6693
6694      if Present (Component_Associations (Aggr)) then
6695         Assoc := First (Component_Associations (Aggr));
6696         while Present (Assoc) loop
6697            Choice := First (Choices (Assoc));
6698
6699            if Present (Next (Choice)) then
6700               Error_Msg_N
6701                 ("multiple choice not allowed here", Next (Choice));
6702               Err := True;
6703            end if;
6704
6705            if Nkind (Choice) = N_Others_Choice then
6706               Error_Msg_N ("others choice not allowed here", Choice);
6707               Err := True;
6708
6709            elsif Nkind (Choice) = N_Range then
6710
6711               --  ??? should allow zero/one element range here
6712
6713               Error_Msg_N ("range not allowed here", Choice);
6714               Err := True;
6715
6716            else
6717               Analyze_And_Resolve (Choice, Enumtype);
6718
6719               if Error_Posted (Choice) then
6720                  Err := True;
6721               end if;
6722
6723               if not Err then
6724                  if Is_Entity_Name (Choice)
6725                    and then Is_Type (Entity (Choice))
6726                  then
6727                     Error_Msg_N ("subtype name not allowed here", Choice);
6728                     Err := True;
6729
6730                     --  ??? should allow static subtype with zero/one entry
6731
6732                  elsif Etype (Choice) = Base_Type (Enumtype) then
6733                     if not Is_OK_Static_Expression (Choice) then
6734                        Flag_Non_Static_Expr
6735                          ("non-static expression used for choice!", Choice);
6736                        Err := True;
6737
6738                     else
6739                        Elit := Expr_Value_E (Choice);
6740
6741                        if Present (Enumeration_Rep_Expr (Elit)) then
6742                           Error_Msg_Sloc :=
6743                             Sloc (Enumeration_Rep_Expr (Elit));
6744                           Error_Msg_NE
6745                             ("representation for& previously given#",
6746                              Choice, Elit);
6747                           Err := True;
6748                        end if;
6749
6750                        Set_Enumeration_Rep_Expr (Elit, Expression (Assoc));
6751
6752                        Expr := Expression (Assoc);
6753                        Val := Static_Integer (Expr);
6754
6755                        if Val = No_Uint then
6756                           Err := True;
6757
6758                        elsif Val < Lo or else Hi < Val then
6759                           Error_Msg_N ("value outside permitted range", Expr);
6760                           Err := True;
6761                        end if;
6762
6763                        Set_Enumeration_Rep (Elit, Val);
6764                     end if;
6765                  end if;
6766               end if;
6767            end if;
6768
6769            Next (Assoc);
6770         end loop;
6771      end if;
6772
6773      --  Aggregate is fully processed. Now we check that a full set of
6774      --  representations was given, and that they are in range and in order.
6775      --  These checks are only done if no other errors occurred.
6776
6777      if not Err then
6778         Min  := No_Uint;
6779         Max  := No_Uint;
6780
6781         Elit := First_Literal (Enumtype);
6782         while Present (Elit) loop
6783            if No (Enumeration_Rep_Expr (Elit)) then
6784               Error_Msg_NE ("missing representation for&!", N, Elit);
6785
6786            else
6787               Val := Enumeration_Rep (Elit);
6788
6789               if Min = No_Uint then
6790                  Min := Val;
6791               end if;
6792
6793               if Val /= No_Uint then
6794                  if Max /= No_Uint and then Val <= Max then
6795                     Error_Msg_NE
6796                       ("enumeration value for& not ordered!",
6797                        Enumeration_Rep_Expr (Elit), Elit);
6798                  end if;
6799
6800                  Max_Node := Enumeration_Rep_Expr (Elit);
6801                  Max := Val;
6802               end if;
6803
6804               --  If there is at least one literal whose representation is not
6805               --  equal to the Pos value, then note that this enumeration type
6806               --  has a non-standard representation.
6807
6808               if Val /= Enumeration_Pos (Elit) then
6809                  Set_Has_Non_Standard_Rep (Base_Type (Enumtype));
6810               end if;
6811            end if;
6812
6813            Next (Elit);
6814         end loop;
6815
6816         --  Now set proper size information
6817
6818         declare
6819            Minsize : Uint := UI_From_Int (Minimum_Size (Enumtype));
6820
6821         begin
6822            if Has_Size_Clause (Enumtype) then
6823
6824               --  All OK, if size is OK now
6825
6826               if RM_Size (Enumtype) >= Minsize then
6827                  null;
6828
6829               else
6830                  --  Try if we can get by with biasing
6831
6832                  Minsize :=
6833                    UI_From_Int (Minimum_Size (Enumtype, Biased => True));
6834
6835                  --  Error message if even biasing does not work
6836
6837                  if RM_Size (Enumtype) < Minsize then
6838                     Error_Msg_Uint_1 := RM_Size (Enumtype);
6839                     Error_Msg_Uint_2 := Max;
6840                     Error_Msg_N
6841                       ("previously given size (^) is too small "
6842                        & "for this value (^)", Max_Node);
6843
6844                  --  If biasing worked, indicate that we now have biased rep
6845
6846                  else
6847                     Set_Biased
6848                       (Enumtype, Size_Clause (Enumtype), "size clause");
6849                  end if;
6850               end if;
6851
6852            else
6853               Set_RM_Size    (Enumtype, Minsize);
6854               Set_Enum_Esize (Enumtype);
6855            end if;
6856
6857            Set_RM_Size   (Base_Type (Enumtype), RM_Size   (Enumtype));
6858            Set_Esize     (Base_Type (Enumtype), Esize     (Enumtype));
6859            Set_Alignment (Base_Type (Enumtype), Alignment (Enumtype));
6860         end;
6861      end if;
6862
6863      --  We repeat the too late test in case it froze itself
6864
6865      if Rep_Item_Too_Late (Enumtype, N) then
6866         null;
6867      end if;
6868   end Analyze_Enumeration_Representation_Clause;
6869
6870   ----------------------------
6871   -- Analyze_Free_Statement --
6872   ----------------------------
6873
6874   procedure Analyze_Free_Statement (N : Node_Id) is
6875   begin
6876      Analyze (Expression (N));
6877   end Analyze_Free_Statement;
6878
6879   ---------------------------
6880   -- Analyze_Freeze_Entity --
6881   ---------------------------
6882
6883   procedure Analyze_Freeze_Entity (N : Node_Id) is
6884   begin
6885      Freeze_Entity_Checks (N);
6886   end Analyze_Freeze_Entity;
6887
6888   -----------------------------------
6889   -- Analyze_Freeze_Generic_Entity --
6890   -----------------------------------
6891
6892   procedure Analyze_Freeze_Generic_Entity (N : Node_Id) is
6893      E : constant Entity_Id := Entity (N);
6894
6895   begin
6896      if not Is_Frozen (E) and then Has_Delayed_Aspects (E) then
6897         Analyze_Aspects_At_Freeze_Point (E);
6898      end if;
6899
6900      Freeze_Entity_Checks (N);
6901   end Analyze_Freeze_Generic_Entity;
6902
6903   ------------------------------------------
6904   -- Analyze_Record_Representation_Clause --
6905   ------------------------------------------
6906
6907   --  Note: we check as much as we can here, but we can't do any checks
6908   --  based on the position values (e.g. overlap checks) until freeze time
6909   --  because especially in Ada 2005 (machine scalar mode), the processing
6910   --  for non-standard bit order can substantially change the positions.
6911   --  See procedure Check_Record_Representation_Clause (called from Freeze)
6912   --  for the remainder of this processing.
6913
6914   procedure Analyze_Record_Representation_Clause (N : Node_Id) is
6915      Ident   : constant Node_Id := Identifier (N);
6916      Biased  : Boolean;
6917      CC      : Node_Id;
6918      Comp    : Entity_Id;
6919      Fbit    : Uint;
6920      Hbit    : Uint := Uint_0;
6921      Lbit    : Uint;
6922      Ocomp   : Entity_Id;
6923      Posit   : Uint;
6924      Rectype : Entity_Id;
6925      Recdef  : Node_Id;
6926
6927      function Is_Inherited (Comp : Entity_Id) return Boolean;
6928      --  True if Comp is an inherited component in a record extension
6929
6930      ------------------
6931      -- Is_Inherited --
6932      ------------------
6933
6934      function Is_Inherited (Comp : Entity_Id) return Boolean is
6935         Comp_Base : Entity_Id;
6936
6937      begin
6938         if Ekind (Rectype) = E_Record_Subtype then
6939            Comp_Base := Original_Record_Component (Comp);
6940         else
6941            Comp_Base := Comp;
6942         end if;
6943
6944         return Comp_Base /= Original_Record_Component (Comp_Base);
6945      end Is_Inherited;
6946
6947      --  Local variables
6948
6949      Is_Record_Extension : Boolean;
6950      --  True if Rectype is a record extension
6951
6952      CR_Pragma : Node_Id := Empty;
6953      --  Points to N_Pragma node if Complete_Representation pragma present
6954
6955   --  Start of processing for Analyze_Record_Representation_Clause
6956
6957   begin
6958      if Ignore_Rep_Clauses then
6959         Kill_Rep_Clause (N);
6960         return;
6961      end if;
6962
6963      Find_Type (Ident);
6964      Rectype := Entity (Ident);
6965
6966      if Rectype = Any_Type or else Rep_Item_Too_Early (Rectype, N) then
6967         return;
6968      else
6969         Rectype := Underlying_Type (Rectype);
6970      end if;
6971
6972      --  First some basic error checks
6973
6974      if not Is_Record_Type (Rectype) then
6975         Error_Msg_NE
6976           ("record type required, found}", Ident, First_Subtype (Rectype));
6977         return;
6978
6979      elsif Scope (Rectype) /= Current_Scope then
6980         Error_Msg_N ("type must be declared in this scope", N);
6981         return;
6982
6983      elsif not Is_First_Subtype (Rectype) then
6984         Error_Msg_N ("cannot give record rep clause for subtype", N);
6985         return;
6986
6987      elsif Has_Record_Rep_Clause (Rectype) then
6988         Error_Msg_N ("duplicate record rep clause ignored", N);
6989         return;
6990
6991      elsif Rep_Item_Too_Late (Rectype, N) then
6992         return;
6993      end if;
6994
6995      --  We know we have a first subtype, now possibly go to the anonymous
6996      --  base type to determine whether Rectype is a record extension.
6997
6998      Recdef := Type_Definition (Declaration_Node (Base_Type (Rectype)));
6999      Is_Record_Extension :=
7000        Nkind (Recdef) = N_Derived_Type_Definition
7001          and then Present (Record_Extension_Part (Recdef));
7002
7003      if Present (Mod_Clause (N)) then
7004         declare
7005            Loc     : constant Source_Ptr := Sloc (N);
7006            M       : constant Node_Id := Mod_Clause (N);
7007            P       : constant List_Id := Pragmas_Before (M);
7008            AtM_Nod : Node_Id;
7009
7010            Mod_Val : Uint;
7011            pragma Warnings (Off, Mod_Val);
7012
7013         begin
7014            Check_Restriction (No_Obsolescent_Features, Mod_Clause (N));
7015
7016            if Warn_On_Obsolescent_Feature then
7017               Error_Msg_N
7018                 ("?j?mod clause is an obsolescent feature (RM J.8)", N);
7019               Error_Msg_N
7020                 ("\?j?use alignment attribute definition clause instead", N);
7021            end if;
7022
7023            if Present (P) then
7024               Analyze_List (P);
7025            end if;
7026
7027            --  In ASIS_Mode mode, expansion is disabled, but we must convert
7028            --  the Mod clause into an alignment clause anyway, so that the
7029            --  back end can compute and back-annotate properly the size and
7030            --  alignment of types that may include this record.
7031
7032            --  This seems dubious, this destroys the source tree in a manner
7033            --  not detectable by ASIS ???
7034
7035            if Operating_Mode = Check_Semantics and then ASIS_Mode then
7036               AtM_Nod :=
7037                 Make_Attribute_Definition_Clause (Loc,
7038                   Name       => New_Occurrence_Of (Base_Type (Rectype), Loc),
7039                   Chars      => Name_Alignment,
7040                   Expression => Relocate_Node (Expression (M)));
7041
7042               Set_From_At_Mod (AtM_Nod);
7043               Insert_After (N, AtM_Nod);
7044               Mod_Val := Get_Alignment_Value (Expression (AtM_Nod));
7045               Set_Mod_Clause (N, Empty);
7046
7047            else
7048               --  Get the alignment value to perform error checking
7049
7050               Mod_Val := Get_Alignment_Value (Expression (M));
7051            end if;
7052         end;
7053      end if;
7054
7055      --  For untagged types, clear any existing component clauses for the
7056      --  type. If the type is derived, this is what allows us to override
7057      --  a rep clause for the parent. For type extensions, the representation
7058      --  of the inherited components is inherited, so we want to keep previous
7059      --  component clauses for completeness.
7060
7061      if not Is_Tagged_Type (Rectype) then
7062         Comp := First_Component_Or_Discriminant (Rectype);
7063         while Present (Comp) loop
7064            Set_Component_Clause (Comp, Empty);
7065            Next_Component_Or_Discriminant (Comp);
7066         end loop;
7067      end if;
7068
7069      --  All done if no component clauses
7070
7071      CC := First (Component_Clauses (N));
7072
7073      if No (CC) then
7074         return;
7075      end if;
7076
7077      --  A representation like this applies to the base type
7078
7079      Set_Has_Record_Rep_Clause (Base_Type (Rectype));
7080      Set_Has_Non_Standard_Rep  (Base_Type (Rectype));
7081      Set_Has_Specified_Layout  (Base_Type (Rectype));
7082
7083      --  Process the component clauses
7084
7085      while Present (CC) loop
7086
7087         --  Pragma
7088
7089         if Nkind (CC) = N_Pragma then
7090            Analyze (CC);
7091
7092            --  The only pragma of interest is Complete_Representation
7093
7094            if Pragma_Name (CC) = Name_Complete_Representation then
7095               CR_Pragma := CC;
7096            end if;
7097
7098         --  Processing for real component clause
7099
7100         else
7101            Posit := Static_Integer (Position  (CC));
7102            Fbit  := Static_Integer (First_Bit (CC));
7103            Lbit  := Static_Integer (Last_Bit  (CC));
7104
7105            if Posit /= No_Uint
7106              and then Fbit /= No_Uint
7107              and then Lbit /= No_Uint
7108            then
7109               if Posit < 0 then
7110                  Error_Msg_N ("position cannot be negative", Position (CC));
7111
7112               elsif Fbit < 0 then
7113                  Error_Msg_N ("first bit cannot be negative", First_Bit (CC));
7114
7115               --  The Last_Bit specified in a component clause must not be
7116               --  less than the First_Bit minus one (RM-13.5.1(10)).
7117
7118               elsif Lbit < Fbit - 1 then
7119                  Error_Msg_N
7120                    ("last bit cannot be less than first bit minus one",
7121                     Last_Bit (CC));
7122
7123               --  Values look OK, so find the corresponding record component
7124               --  Even though the syntax allows an attribute reference for
7125               --  implementation-defined components, GNAT does not allow the
7126               --  tag to get an explicit position.
7127
7128               elsif Nkind (Component_Name (CC)) = N_Attribute_Reference then
7129                  if Attribute_Name (Component_Name (CC)) = Name_Tag then
7130                     Error_Msg_N ("position of tag cannot be specified", CC);
7131                  else
7132                     Error_Msg_N ("illegal component name", CC);
7133                  end if;
7134
7135               else
7136                  Comp := First_Entity (Rectype);
7137                  while Present (Comp) loop
7138                     exit when Chars (Comp) = Chars (Component_Name (CC));
7139                     Next_Entity (Comp);
7140                  end loop;
7141
7142                  if No (Comp) then
7143
7144                     --  Maybe component of base type that is absent from
7145                     --  statically constrained first subtype.
7146
7147                     Comp := First_Entity (Base_Type (Rectype));
7148                     while Present (Comp) loop
7149                        exit when Chars (Comp) = Chars (Component_Name (CC));
7150                        Next_Entity (Comp);
7151                     end loop;
7152                  end if;
7153
7154                  if No (Comp) then
7155                     Error_Msg_N
7156                       ("component clause is for non-existent field", CC);
7157
7158                  --  Ada 2012 (AI05-0026): Any name that denotes a
7159                  --  discriminant of an object of an unchecked union type
7160                  --  shall not occur within a record_representation_clause.
7161
7162                  --  The general restriction of using record rep clauses on
7163                  --  Unchecked_Union types has now been lifted. Since it is
7164                  --  possible to introduce a record rep clause which mentions
7165                  --  the discriminant of an Unchecked_Union in non-Ada 2012
7166                  --  code, this check is applied to all versions of the
7167                  --  language.
7168
7169                  elsif Ekind (Comp) = E_Discriminant
7170                    and then Is_Unchecked_Union (Rectype)
7171                  then
7172                     Error_Msg_N
7173                       ("cannot reference discriminant of unchecked union",
7174                        Component_Name (CC));
7175
7176                  elsif Is_Record_Extension and then Is_Inherited (Comp) then
7177                     Error_Msg_NE
7178                       ("component clause not allowed for inherited "
7179                        & "component&", CC, Comp);
7180
7181                  elsif Present (Component_Clause (Comp)) then
7182
7183                     --  Diagnose duplicate rep clause, or check consistency
7184                     --  if this is an inherited component. In a double fault,
7185                     --  there may be a duplicate inconsistent clause for an
7186                     --  inherited component.
7187
7188                     if Scope (Original_Record_Component (Comp)) = Rectype
7189                       or else Parent (Component_Clause (Comp)) = N
7190                     then
7191                        Error_Msg_Sloc := Sloc (Component_Clause (Comp));
7192                        Error_Msg_N ("component clause previously given#", CC);
7193
7194                     else
7195                        declare
7196                           Rep1 : constant Node_Id := Component_Clause (Comp);
7197                        begin
7198                           if Intval (Position (Rep1)) /=
7199                                                   Intval (Position (CC))
7200                             or else Intval (First_Bit (Rep1)) /=
7201                                                   Intval (First_Bit (CC))
7202                             or else Intval (Last_Bit (Rep1)) /=
7203                                                   Intval (Last_Bit (CC))
7204                           then
7205                              Error_Msg_N
7206                                ("component clause inconsistent with "
7207                                 & "representation of ancestor", CC);
7208
7209                           elsif Warn_On_Redundant_Constructs then
7210                              Error_Msg_N
7211                                ("?r?redundant confirming component clause "
7212                                 & "for component!", CC);
7213                           end if;
7214                        end;
7215                     end if;
7216
7217                  --  Normal case where this is the first component clause we
7218                  --  have seen for this entity, so set it up properly.
7219
7220                  else
7221                     --  Make reference for field in record rep clause and set
7222                     --  appropriate entity field in the field identifier.
7223
7224                     Generate_Reference
7225                       (Comp, Component_Name (CC), Set_Ref => False);
7226                     Set_Entity (Component_Name (CC), Comp);
7227
7228                     --  Update Fbit and Lbit to the actual bit number
7229
7230                     Fbit := Fbit + UI_From_Int (SSU) * Posit;
7231                     Lbit := Lbit + UI_From_Int (SSU) * Posit;
7232
7233                     if Has_Size_Clause (Rectype)
7234                       and then RM_Size (Rectype) <= Lbit
7235                     then
7236                        Error_Msg_N
7237                          ("bit number out of range of specified size",
7238                           Last_Bit (CC));
7239                     else
7240                        Set_Component_Clause     (Comp, CC);
7241                        Set_Component_Bit_Offset (Comp, Fbit);
7242                        Set_Esize                (Comp, 1 + (Lbit - Fbit));
7243                        Set_Normalized_First_Bit (Comp, Fbit mod SSU);
7244                        Set_Normalized_Position  (Comp, Fbit / SSU);
7245
7246                        if Warn_On_Overridden_Size
7247                          and then Has_Size_Clause (Etype (Comp))
7248                          and then RM_Size (Etype (Comp)) /= Esize (Comp)
7249                        then
7250                           Error_Msg_NE
7251                             ("?S?component size overrides size clause for&",
7252                              Component_Name (CC), Etype (Comp));
7253                        end if;
7254
7255                        --  This information is also set in the corresponding
7256                        --  component of the base type, found by accessing the
7257                        --  Original_Record_Component link if it is present.
7258
7259                        Ocomp := Original_Record_Component (Comp);
7260
7261                        if Hbit < Lbit then
7262                           Hbit := Lbit;
7263                        end if;
7264
7265                        Check_Size
7266                          (Component_Name (CC),
7267                           Etype (Comp),
7268                           Esize (Comp),
7269                           Biased);
7270
7271                        Set_Biased
7272                          (Comp, First_Node (CC), "component clause", Biased);
7273
7274                        if Present (Ocomp) then
7275                           Set_Component_Clause     (Ocomp, CC);
7276                           Set_Component_Bit_Offset (Ocomp, Fbit);
7277                           Set_Normalized_First_Bit (Ocomp, Fbit mod SSU);
7278                           Set_Normalized_Position  (Ocomp, Fbit / SSU);
7279                           Set_Esize                (Ocomp, 1 + (Lbit - Fbit));
7280
7281                           Set_Normalized_Position_Max
7282                             (Ocomp, Normalized_Position (Ocomp));
7283
7284                           --  Note: we don't use Set_Biased here, because we
7285                           --  already gave a warning above if needed, and we
7286                           --  would get a duplicate for the same name here.
7287
7288                           Set_Has_Biased_Representation
7289                             (Ocomp, Has_Biased_Representation (Comp));
7290                        end if;
7291
7292                        if Esize (Comp) < 0 then
7293                           Error_Msg_N ("component size is negative", CC);
7294                        end if;
7295                     end if;
7296                  end if;
7297               end if;
7298            end if;
7299         end if;
7300
7301         Next (CC);
7302      end loop;
7303
7304      --  Check missing components if Complete_Representation pragma appeared
7305
7306      if Present (CR_Pragma) then
7307         Comp := First_Component_Or_Discriminant (Rectype);
7308         while Present (Comp) loop
7309            if No (Component_Clause (Comp)) then
7310               Error_Msg_NE
7311                 ("missing component clause for &", CR_Pragma, Comp);
7312            end if;
7313
7314            Next_Component_Or_Discriminant (Comp);
7315         end loop;
7316
7317      --  Give missing components warning if required
7318
7319      elsif Warn_On_Unrepped_Components then
7320         declare
7321            Num_Repped_Components   : Nat := 0;
7322            Num_Unrepped_Components : Nat := 0;
7323
7324         begin
7325            --  First count number of repped and unrepped components
7326
7327            Comp := First_Component_Or_Discriminant (Rectype);
7328            while Present (Comp) loop
7329               if Present (Component_Clause (Comp)) then
7330                  Num_Repped_Components := Num_Repped_Components + 1;
7331               else
7332                  Num_Unrepped_Components := Num_Unrepped_Components + 1;
7333               end if;
7334
7335               Next_Component_Or_Discriminant (Comp);
7336            end loop;
7337
7338            --  We are only interested in the case where there is at least one
7339            --  unrepped component, and at least half the components have rep
7340            --  clauses. We figure that if less than half have them, then the
7341            --  partial rep clause is really intentional. If the component
7342            --  type has no underlying type set at this point (as for a generic
7343            --  formal type), we don't know enough to give a warning on the
7344            --  component.
7345
7346            if Num_Unrepped_Components > 0
7347              and then Num_Unrepped_Components < Num_Repped_Components
7348            then
7349               Comp := First_Component_Or_Discriminant (Rectype);
7350               while Present (Comp) loop
7351                  if No (Component_Clause (Comp))
7352                    and then Comes_From_Source (Comp)
7353                    and then Present (Underlying_Type (Etype (Comp)))
7354                    and then (Is_Scalar_Type (Underlying_Type (Etype (Comp)))
7355                               or else Size_Known_At_Compile_Time
7356                                         (Underlying_Type (Etype (Comp))))
7357                    and then not Has_Warnings_Off (Rectype)
7358
7359                    --  Ignore discriminant in unchecked union, since it is
7360                    --  not there, and cannot have a component clause.
7361
7362                    and then (not Is_Unchecked_Union (Rectype)
7363                               or else Ekind (Comp) /= E_Discriminant)
7364                  then
7365                     Error_Msg_Sloc := Sloc (Comp);
7366                     Error_Msg_NE
7367                       ("?C?no component clause given for & declared #",
7368                        N, Comp);
7369                  end if;
7370
7371                  Next_Component_Or_Discriminant (Comp);
7372               end loop;
7373            end if;
7374         end;
7375      end if;
7376   end Analyze_Record_Representation_Clause;
7377
7378   -------------------------------------
7379   -- Build_Discrete_Static_Predicate --
7380   -------------------------------------
7381
7382   procedure Build_Discrete_Static_Predicate
7383     (Typ  : Entity_Id;
7384      Expr : Node_Id;
7385      Nam  : Name_Id)
7386   is
7387      Loc : constant Source_Ptr := Sloc (Expr);
7388
7389      Non_Static : exception;
7390      --  Raised if something non-static is found
7391
7392      Btyp : constant Entity_Id := Base_Type (Typ);
7393
7394      BLo : constant Uint := Expr_Value (Type_Low_Bound  (Btyp));
7395      BHi : constant Uint := Expr_Value (Type_High_Bound (Btyp));
7396      --  Low bound and high bound value of base type of Typ
7397
7398      TLo : Uint;
7399      THi : Uint;
7400      --  Bounds for constructing the static predicate. We use the bound of the
7401      --  subtype if it is static, otherwise the corresponding base type bound.
7402      --  Note: a non-static subtype can have a static predicate.
7403
7404      type REnt is record
7405         Lo, Hi : Uint;
7406      end record;
7407      --  One entry in a Rlist value, a single REnt (range entry) value denotes
7408      --  one range from Lo to Hi. To represent a single value range Lo = Hi =
7409      --  value.
7410
7411      type RList is array (Nat range <>) of REnt;
7412      --  A list of ranges. The ranges are sorted in increasing order, and are
7413      --  disjoint (there is a gap of at least one value between each range in
7414      --  the table). A value is in the set of ranges in Rlist if it lies
7415      --  within one of these ranges.
7416
7417      False_Range : constant RList :=
7418        RList'(1 .. 0 => REnt'(No_Uint, No_Uint));
7419      --  An empty set of ranges represents a range list that can never be
7420      --  satisfied, since there are no ranges in which the value could lie,
7421      --  so it does not lie in any of them. False_Range is a canonical value
7422      --  for this empty set, but general processing should test for an Rlist
7423      --  with length zero (see Is_False predicate), since other null ranges
7424      --  may appear which must be treated as False.
7425
7426      True_Range : constant RList := RList'(1 => REnt'(BLo, BHi));
7427      --  Range representing True, value must be in the base range
7428
7429      function "and" (Left : RList; Right : RList) return RList;
7430      --  And's together two range lists, returning a range list. This is a set
7431      --  intersection operation.
7432
7433      function "or" (Left : RList; Right : RList) return RList;
7434      --  Or's together two range lists, returning a range list. This is a set
7435      --  union operation.
7436
7437      function "not" (Right : RList) return RList;
7438      --  Returns complement of a given range list, i.e. a range list
7439      --  representing all the values in TLo .. THi that are not in the input
7440      --  operand Right.
7441
7442      function Build_Val (V : Uint) return Node_Id;
7443      --  Return an analyzed N_Identifier node referencing this value, suitable
7444      --  for use as an entry in the Static_Discrte_Predicate list. This node
7445      --  is typed with the base type.
7446
7447      function Build_Range (Lo : Uint; Hi : Uint) return Node_Id;
7448      --  Return an analyzed N_Range node referencing this range, suitable for
7449      --  use as an entry in the Static_Discrete_Predicate list. This node is
7450      --  typed with the base type.
7451
7452      function Get_RList (Exp : Node_Id) return RList;
7453      --  This is a recursive routine that converts the given expression into a
7454      --  list of ranges, suitable for use in building the static predicate.
7455
7456      function Is_False (R : RList) return Boolean;
7457      pragma Inline (Is_False);
7458      --  Returns True if the given range list is empty, and thus represents a
7459      --  False list of ranges that can never be satisfied.
7460
7461      function Is_True (R : RList) return Boolean;
7462      --  Returns True if R trivially represents the True predicate by having a
7463      --  single range from BLo to BHi.
7464
7465      function Is_Type_Ref (N : Node_Id) return Boolean;
7466      pragma Inline (Is_Type_Ref);
7467      --  Returns if True if N is a reference to the type for the predicate in
7468      --  the expression (i.e. if it is an identifier whose Chars field matches
7469      --  the Nam given in the call). N must not be parenthesized, if the type
7470      --  name appears in parens, this routine will return False.
7471
7472      function Lo_Val (N : Node_Id) return Uint;
7473      --  Given an entry from a Static_Discrete_Predicate list that is either
7474      --  a static expression or static range, gets either the expression value
7475      --  or the low bound of the range.
7476
7477      function Hi_Val (N : Node_Id) return Uint;
7478      --  Given an entry from a Static_Discrete_Predicate list that is either
7479      --  a static expression or static range, gets either the expression value
7480      --  or the high bound of the range.
7481
7482      function Membership_Entry (N : Node_Id) return RList;
7483      --  Given a single membership entry (range, value, or subtype), returns
7484      --  the corresponding range list. Raises Static_Error if not static.
7485
7486      function Membership_Entries (N : Node_Id) return RList;
7487      --  Given an element on an alternatives list of a membership operation,
7488      --  returns the range list corresponding to this entry and all following
7489      --  entries (i.e. returns the "or" of this list of values).
7490
7491      function Stat_Pred (Typ : Entity_Id) return RList;
7492      --  Given a type, if it has a static predicate, then return the predicate
7493      --  as a range list, otherwise raise Non_Static.
7494
7495      -----------
7496      -- "and" --
7497      -----------
7498
7499      function "and" (Left : RList; Right : RList) return RList is
7500         FEnt : REnt;
7501         --  First range of result
7502
7503         SLeft : Nat := Left'First;
7504         --  Start of rest of left entries
7505
7506         SRight : Nat := Right'First;
7507         --  Start of rest of right entries
7508
7509      begin
7510         --  If either range is True, return the other
7511
7512         if Is_True (Left) then
7513            return Right;
7514         elsif Is_True (Right) then
7515            return Left;
7516         end if;
7517
7518         --  If either range is False, return False
7519
7520         if Is_False (Left) or else Is_False (Right) then
7521            return False_Range;
7522         end if;
7523
7524         --  Loop to remove entries at start that are disjoint, and thus just
7525         --  get discarded from the result entirely.
7526
7527         loop
7528            --  If no operands left in either operand, result is false
7529
7530            if SLeft > Left'Last or else SRight > Right'Last then
7531               return False_Range;
7532
7533            --  Discard first left operand entry if disjoint with right
7534
7535            elsif Left (SLeft).Hi < Right (SRight).Lo then
7536               SLeft := SLeft + 1;
7537
7538            --  Discard first right operand entry if disjoint with left
7539
7540            elsif Right (SRight).Hi < Left (SLeft).Lo then
7541               SRight := SRight + 1;
7542
7543            --  Otherwise we have an overlapping entry
7544
7545            else
7546               exit;
7547            end if;
7548         end loop;
7549
7550         --  Now we have two non-null operands, and first entries overlap. The
7551         --  first entry in the result will be the overlapping part of these
7552         --  two entries.
7553
7554         FEnt := REnt'(Lo => UI_Max (Left (SLeft).Lo, Right (SRight).Lo),
7555                       Hi => UI_Min (Left (SLeft).Hi, Right (SRight).Hi));
7556
7557         --  Now we can remove the entry that ended at a lower value, since its
7558         --  contribution is entirely contained in Fent.
7559
7560         if Left (SLeft).Hi <= Right (SRight).Hi then
7561            SLeft := SLeft + 1;
7562         else
7563            SRight := SRight + 1;
7564         end if;
7565
7566         --  Compute result by concatenating this first entry with the "and" of
7567         --  the remaining parts of the left and right operands. Note that if
7568         --  either of these is empty, "and" will yield empty, so that we will
7569         --  end up with just Fent, which is what we want in that case.
7570
7571         return
7572           FEnt & (Left (SLeft .. Left'Last) and Right (SRight .. Right'Last));
7573      end "and";
7574
7575      -----------
7576      -- "not" --
7577      -----------
7578
7579      function "not" (Right : RList) return RList is
7580      begin
7581         --  Return True if False range
7582
7583         if Is_False (Right) then
7584            return True_Range;
7585         end if;
7586
7587         --  Return False if True range
7588
7589         if Is_True (Right) then
7590            return False_Range;
7591         end if;
7592
7593         --  Here if not trivial case
7594
7595         declare
7596            Result : RList (1 .. Right'Length + 1);
7597            --  May need one more entry for gap at beginning and end
7598
7599            Count : Nat := 0;
7600            --  Number of entries stored in Result
7601
7602         begin
7603            --  Gap at start
7604
7605            if Right (Right'First).Lo > TLo then
7606               Count := Count + 1;
7607               Result (Count) := REnt'(TLo, Right (Right'First).Lo - 1);
7608            end if;
7609
7610            --  Gaps between ranges
7611
7612            for J in Right'First .. Right'Last - 1 loop
7613               Count := Count + 1;
7614               Result (Count) := REnt'(Right (J).Hi + 1, Right (J + 1).Lo - 1);
7615            end loop;
7616
7617            --  Gap at end
7618
7619            if Right (Right'Last).Hi < THi then
7620               Count := Count + 1;
7621               Result (Count) := REnt'(Right (Right'Last).Hi + 1, THi);
7622            end if;
7623
7624            return Result (1 .. Count);
7625         end;
7626      end "not";
7627
7628      ----------
7629      -- "or" --
7630      ----------
7631
7632      function "or" (Left : RList; Right : RList) return RList is
7633         FEnt : REnt;
7634         --  First range of result
7635
7636         SLeft : Nat := Left'First;
7637         --  Start of rest of left entries
7638
7639         SRight : Nat := Right'First;
7640         --  Start of rest of right entries
7641
7642      begin
7643         --  If either range is True, return True
7644
7645         if Is_True (Left) or else Is_True (Right) then
7646            return True_Range;
7647         end if;
7648
7649         --  If either range is False (empty), return the other
7650
7651         if Is_False (Left) then
7652            return Right;
7653         elsif Is_False (Right) then
7654            return Left;
7655         end if;
7656
7657         --  Initialize result first entry from left or right operand depending
7658         --  on which starts with the lower range.
7659
7660         if Left (SLeft).Lo < Right (SRight).Lo then
7661            FEnt := Left (SLeft);
7662            SLeft := SLeft + 1;
7663         else
7664            FEnt := Right (SRight);
7665            SRight := SRight + 1;
7666         end if;
7667
7668         --  This loop eats ranges from left and right operands that are
7669         --  contiguous with the first range we are gathering.
7670
7671         loop
7672            --  Eat first entry in left operand if contiguous or overlapped by
7673            --  gathered first operand of result.
7674
7675            if SLeft <= Left'Last
7676              and then Left (SLeft).Lo <= FEnt.Hi + 1
7677            then
7678               FEnt.Hi := UI_Max (FEnt.Hi, Left (SLeft).Hi);
7679               SLeft := SLeft + 1;
7680
7681            --  Eat first entry in right operand if contiguous or overlapped by
7682            --  gathered right operand of result.
7683
7684            elsif SRight <= Right'Last
7685              and then Right (SRight).Lo <= FEnt.Hi + 1
7686            then
7687               FEnt.Hi := UI_Max (FEnt.Hi, Right (SRight).Hi);
7688               SRight := SRight + 1;
7689
7690            --  All done if no more entries to eat
7691
7692            else
7693               exit;
7694            end if;
7695         end loop;
7696
7697         --  Obtain result as the first entry we just computed, concatenated
7698         --  to the "or" of the remaining results (if one operand is empty,
7699         --  this will just concatenate with the other
7700
7701         return
7702           FEnt & (Left (SLeft .. Left'Last) or Right (SRight .. Right'Last));
7703      end "or";
7704
7705      -----------------
7706      -- Build_Range --
7707      -----------------
7708
7709      function Build_Range (Lo : Uint; Hi : Uint) return Node_Id is
7710         Result : Node_Id;
7711      begin
7712         Result :=
7713           Make_Range (Loc,
7714              Low_Bound  => Build_Val (Lo),
7715              High_Bound => Build_Val (Hi));
7716         Set_Etype (Result, Btyp);
7717         Set_Analyzed (Result);
7718         return Result;
7719      end Build_Range;
7720
7721      ---------------
7722      -- Build_Val --
7723      ---------------
7724
7725      function Build_Val (V : Uint) return Node_Id is
7726         Result : Node_Id;
7727
7728      begin
7729         if Is_Enumeration_Type (Typ) then
7730            Result := Get_Enum_Lit_From_Pos (Typ, V, Loc);
7731         else
7732            Result := Make_Integer_Literal (Loc, V);
7733         end if;
7734
7735         Set_Etype (Result, Btyp);
7736         Set_Is_Static_Expression (Result);
7737         Set_Analyzed (Result);
7738         return Result;
7739      end Build_Val;
7740
7741      ---------------
7742      -- Get_RList --
7743      ---------------
7744
7745      function Get_RList (Exp : Node_Id) return RList is
7746         Op  : Node_Kind;
7747         Val : Uint;
7748
7749      begin
7750         --  Static expression can only be true or false
7751
7752         if Is_OK_Static_Expression (Exp) then
7753            if Expr_Value (Exp) = 0 then
7754               return False_Range;
7755            else
7756               return True_Range;
7757            end if;
7758         end if;
7759
7760         --  Otherwise test node type
7761
7762         Op := Nkind (Exp);
7763
7764         case Op is
7765
7766            --  And
7767
7768            when N_And_Then
7769               | N_Op_And
7770            =>
7771               return Get_RList (Left_Opnd (Exp))
7772                        and
7773                      Get_RList (Right_Opnd (Exp));
7774
7775            --  Or
7776
7777            when N_Op_Or
7778               | N_Or_Else
7779            =>
7780               return Get_RList (Left_Opnd (Exp))
7781                        or
7782                      Get_RList (Right_Opnd (Exp));
7783
7784            --  Not
7785
7786            when N_Op_Not =>
7787               return not Get_RList (Right_Opnd (Exp));
7788
7789               --  Comparisons of type with static value
7790
7791            when N_Op_Compare =>
7792
7793               --  Type is left operand
7794
7795               if Is_Type_Ref (Left_Opnd (Exp))
7796                 and then Is_OK_Static_Expression (Right_Opnd (Exp))
7797               then
7798                  Val := Expr_Value (Right_Opnd (Exp));
7799
7800               --  Typ is right operand
7801
7802               elsif Is_Type_Ref (Right_Opnd (Exp))
7803                 and then Is_OK_Static_Expression (Left_Opnd (Exp))
7804               then
7805                  Val := Expr_Value (Left_Opnd (Exp));
7806
7807                  --  Invert sense of comparison
7808
7809                  case Op is
7810                     when N_Op_Gt => Op := N_Op_Lt;
7811                     when N_Op_Lt => Op := N_Op_Gt;
7812                     when N_Op_Ge => Op := N_Op_Le;
7813                     when N_Op_Le => Op := N_Op_Ge;
7814                     when others  => null;
7815                  end case;
7816
7817               --  Other cases are non-static
7818
7819               else
7820                  raise Non_Static;
7821               end if;
7822
7823               --  Construct range according to comparison operation
7824
7825               case Op is
7826                  when N_Op_Eq =>
7827                     return RList'(1 => REnt'(Val, Val));
7828
7829                  when N_Op_Ge =>
7830                     return RList'(1 => REnt'(Val, BHi));
7831
7832                  when N_Op_Gt =>
7833                     return RList'(1 => REnt'(Val + 1, BHi));
7834
7835                  when N_Op_Le =>
7836                     return RList'(1 => REnt'(BLo, Val));
7837
7838                  when N_Op_Lt =>
7839                     return RList'(1 => REnt'(BLo, Val - 1));
7840
7841                  when N_Op_Ne =>
7842                     return RList'(REnt'(BLo, Val - 1), REnt'(Val + 1, BHi));
7843
7844                  when others  =>
7845                     raise Program_Error;
7846               end case;
7847
7848            --  Membership (IN)
7849
7850            when N_In =>
7851               if not Is_Type_Ref (Left_Opnd (Exp)) then
7852                  raise Non_Static;
7853               end if;
7854
7855               if Present (Right_Opnd (Exp)) then
7856                  return Membership_Entry (Right_Opnd (Exp));
7857               else
7858                  return Membership_Entries (First (Alternatives (Exp)));
7859               end if;
7860
7861            --  Negative membership (NOT IN)
7862
7863            when N_Not_In =>
7864               if not Is_Type_Ref (Left_Opnd (Exp)) then
7865                  raise Non_Static;
7866               end if;
7867
7868               if Present (Right_Opnd (Exp)) then
7869                  return not Membership_Entry (Right_Opnd (Exp));
7870               else
7871                  return not Membership_Entries (First (Alternatives (Exp)));
7872               end if;
7873
7874            --  Function call, may be call to static predicate
7875
7876            when N_Function_Call =>
7877               if Is_Entity_Name (Name (Exp)) then
7878                  declare
7879                     Ent : constant Entity_Id := Entity (Name (Exp));
7880                  begin
7881                     if Is_Predicate_Function (Ent)
7882                          or else
7883                        Is_Predicate_Function_M (Ent)
7884                     then
7885                        return Stat_Pred (Etype (First_Formal (Ent)));
7886                     end if;
7887                  end;
7888               end if;
7889
7890               --  Other function call cases are non-static
7891
7892               raise Non_Static;
7893
7894            --  Qualified expression, dig out the expression
7895
7896            when N_Qualified_Expression =>
7897               return Get_RList (Expression (Exp));
7898
7899            when N_Case_Expression =>
7900               declare
7901                  Alt     : Node_Id;
7902                  Choices : List_Id;
7903                  Dep     : Node_Id;
7904
7905               begin
7906                  if not Is_Entity_Name (Expression (Expr))
7907                    or else Etype (Expression (Expr)) /= Typ
7908                  then
7909                     Error_Msg_N
7910                       ("expression must denaote subtype", Expression (Expr));
7911                     return False_Range;
7912                  end if;
7913
7914                  --  Collect discrete choices in all True alternatives
7915
7916                  Choices := New_List;
7917                  Alt := First (Alternatives (Exp));
7918                  while Present (Alt) loop
7919                     Dep := Expression (Alt);
7920
7921                     if not Is_OK_Static_Expression (Dep) then
7922                        raise Non_Static;
7923
7924                     elsif Is_True (Expr_Value (Dep)) then
7925                        Append_List_To (Choices,
7926                          New_Copy_List (Discrete_Choices (Alt)));
7927                     end if;
7928
7929                     Next (Alt);
7930                  end loop;
7931
7932                  return Membership_Entries (First (Choices));
7933               end;
7934
7935            --  Expression with actions: if no actions, dig out expression
7936
7937            when N_Expression_With_Actions =>
7938               if Is_Empty_List (Actions (Exp)) then
7939                  return Get_RList (Expression (Exp));
7940               else
7941                  raise Non_Static;
7942               end if;
7943
7944            --  Xor operator
7945
7946            when N_Op_Xor =>
7947               return (Get_RList (Left_Opnd (Exp))
7948                        and not Get_RList (Right_Opnd (Exp)))
7949                 or   (Get_RList (Right_Opnd (Exp))
7950                        and not Get_RList (Left_Opnd (Exp)));
7951
7952            --  Any other node type is non-static
7953
7954            when others =>
7955               raise Non_Static;
7956         end case;
7957      end Get_RList;
7958
7959      ------------
7960      -- Hi_Val --
7961      ------------
7962
7963      function Hi_Val (N : Node_Id) return Uint is
7964      begin
7965         if Is_OK_Static_Expression (N) then
7966            return Expr_Value (N);
7967         else
7968            pragma Assert (Nkind (N) = N_Range);
7969            return Expr_Value (High_Bound (N));
7970         end if;
7971      end Hi_Val;
7972
7973      --------------
7974      -- Is_False --
7975      --------------
7976
7977      function Is_False (R : RList) return Boolean is
7978      begin
7979         return R'Length = 0;
7980      end Is_False;
7981
7982      -------------
7983      -- Is_True --
7984      -------------
7985
7986      function Is_True (R : RList) return Boolean is
7987      begin
7988         return R'Length = 1
7989           and then R (R'First).Lo = BLo
7990           and then R (R'First).Hi = BHi;
7991      end Is_True;
7992
7993      -----------------
7994      -- Is_Type_Ref --
7995      -----------------
7996
7997      function Is_Type_Ref (N : Node_Id) return Boolean is
7998      begin
7999         return Nkind (N) = N_Identifier
8000           and then Chars (N) = Nam
8001           and then Paren_Count (N) = 0;
8002      end Is_Type_Ref;
8003
8004      ------------
8005      -- Lo_Val --
8006      ------------
8007
8008      function Lo_Val (N : Node_Id) return Uint is
8009      begin
8010         if Is_OK_Static_Expression (N) then
8011            return Expr_Value (N);
8012         else
8013            pragma Assert (Nkind (N) = N_Range);
8014            return Expr_Value (Low_Bound (N));
8015         end if;
8016      end Lo_Val;
8017
8018      ------------------------
8019      -- Membership_Entries --
8020      ------------------------
8021
8022      function Membership_Entries (N : Node_Id) return RList is
8023      begin
8024         if No (Next (N)) then
8025            return Membership_Entry (N);
8026         else
8027            return Membership_Entry (N) or Membership_Entries (Next (N));
8028         end if;
8029      end Membership_Entries;
8030
8031      ----------------------
8032      -- Membership_Entry --
8033      ----------------------
8034
8035      function Membership_Entry (N : Node_Id) return RList is
8036         Val : Uint;
8037         SLo : Uint;
8038         SHi : Uint;
8039
8040      begin
8041         --  Range case
8042
8043         if Nkind (N) = N_Range then
8044            if not Is_OK_Static_Expression (Low_Bound  (N))
8045                 or else
8046               not Is_OK_Static_Expression (High_Bound (N))
8047            then
8048               raise Non_Static;
8049            else
8050               SLo := Expr_Value (Low_Bound  (N));
8051               SHi := Expr_Value (High_Bound (N));
8052               return RList'(1 => REnt'(SLo, SHi));
8053            end if;
8054
8055         --  Static expression case
8056
8057         elsif Is_OK_Static_Expression (N) then
8058            Val := Expr_Value (N);
8059            return RList'(1 => REnt'(Val, Val));
8060
8061         --  Identifier (other than static expression) case
8062
8063         else pragma Assert (Nkind (N) = N_Identifier);
8064
8065            --  Type case
8066
8067            if Is_Type (Entity (N)) then
8068
8069               --  If type has predicates, process them
8070
8071               if Has_Predicates (Entity (N)) then
8072                  return Stat_Pred (Entity (N));
8073
8074               --  For static subtype without predicates, get range
8075
8076               elsif Is_OK_Static_Subtype (Entity (N)) then
8077                  SLo := Expr_Value (Type_Low_Bound  (Entity (N)));
8078                  SHi := Expr_Value (Type_High_Bound (Entity (N)));
8079                  return RList'(1 => REnt'(SLo, SHi));
8080
8081               --  Any other type makes us non-static
8082
8083               else
8084                  raise Non_Static;
8085               end if;
8086
8087            --  Any other kind of identifier in predicate (e.g. a non-static
8088            --  expression value) means this is not a static predicate.
8089
8090            else
8091               raise Non_Static;
8092            end if;
8093         end if;
8094      end Membership_Entry;
8095
8096      ---------------
8097      -- Stat_Pred --
8098      ---------------
8099
8100      function Stat_Pred (Typ : Entity_Id) return RList is
8101      begin
8102         --  Not static if type does not have static predicates
8103
8104         if not Has_Static_Predicate (Typ) then
8105            raise Non_Static;
8106         end if;
8107
8108         --  Otherwise we convert the predicate list to a range list
8109
8110         declare
8111            Spred  : constant List_Id := Static_Discrete_Predicate (Typ);
8112            Result : RList (1 .. List_Length (Spred));
8113            P      : Node_Id;
8114
8115         begin
8116            P := First (Static_Discrete_Predicate (Typ));
8117            for J in Result'Range loop
8118               Result (J) := REnt'(Lo_Val (P), Hi_Val (P));
8119               Next (P);
8120            end loop;
8121
8122            return Result;
8123         end;
8124      end Stat_Pred;
8125
8126   --  Start of processing for Build_Discrete_Static_Predicate
8127
8128   begin
8129      --  Establish bounds for the predicate
8130
8131      if Compile_Time_Known_Value (Type_Low_Bound (Typ)) then
8132         TLo := Expr_Value (Type_Low_Bound (Typ));
8133      else
8134         TLo := BLo;
8135      end if;
8136
8137      if Compile_Time_Known_Value (Type_High_Bound (Typ)) then
8138         THi := Expr_Value (Type_High_Bound (Typ));
8139      else
8140         THi := BHi;
8141      end if;
8142
8143      --  Analyze the expression to see if it is a static predicate
8144
8145      declare
8146         Ranges : constant RList := Get_RList (Expr);
8147         --  Range list from expression if it is static
8148
8149         Plist : List_Id;
8150
8151      begin
8152         --  Convert range list into a form for the static predicate. In the
8153         --  Ranges array, we just have raw ranges, these must be converted
8154         --  to properly typed and analyzed static expressions or range nodes.
8155
8156         --  Note: here we limit ranges to the ranges of the subtype, so that
8157         --  a predicate is always false for values outside the subtype. That
8158         --  seems fine, such values are invalid anyway, and considering them
8159         --  to fail the predicate seems allowed and friendly, and furthermore
8160         --  simplifies processing for case statements and loops.
8161
8162         Plist := New_List;
8163
8164         for J in Ranges'Range loop
8165            declare
8166               Lo : Uint := Ranges (J).Lo;
8167               Hi : Uint := Ranges (J).Hi;
8168
8169            begin
8170               --  Ignore completely out of range entry
8171
8172               if Hi < TLo or else Lo > THi then
8173                  null;
8174
8175               --  Otherwise process entry
8176
8177               else
8178                  --  Adjust out of range value to subtype range
8179
8180                  if Lo < TLo then
8181                     Lo := TLo;
8182                  end if;
8183
8184                  if Hi > THi then
8185                     Hi := THi;
8186                  end if;
8187
8188                  --  Convert range into required form
8189
8190                  Append_To (Plist, Build_Range (Lo, Hi));
8191               end if;
8192            end;
8193         end loop;
8194
8195         --  Processing was successful and all entries were static, so now we
8196         --  can store the result as the predicate list.
8197
8198         Set_Static_Discrete_Predicate (Typ, Plist);
8199
8200         --  The processing for static predicates put the expression into
8201         --  canonical form as a series of ranges. It also eliminated
8202         --  duplicates and collapsed and combined ranges. We might as well
8203         --  replace the alternatives list of the right operand of the
8204         --  membership test with the static predicate list, which will
8205         --  usually be more efficient.
8206
8207         declare
8208            New_Alts : constant List_Id := New_List;
8209            Old_Node : Node_Id;
8210            New_Node : Node_Id;
8211
8212         begin
8213            Old_Node := First (Plist);
8214            while Present (Old_Node) loop
8215               New_Node := New_Copy (Old_Node);
8216
8217               if Nkind (New_Node) = N_Range then
8218                  Set_Low_Bound  (New_Node, New_Copy (Low_Bound  (Old_Node)));
8219                  Set_High_Bound (New_Node, New_Copy (High_Bound (Old_Node)));
8220               end if;
8221
8222               Append_To (New_Alts, New_Node);
8223               Next (Old_Node);
8224            end loop;
8225
8226            --  If empty list, replace by False
8227
8228            if Is_Empty_List (New_Alts) then
8229               Rewrite (Expr, New_Occurrence_Of (Standard_False, Loc));
8230
8231               --  Else replace by set membership test
8232
8233            else
8234               Rewrite (Expr,
8235                 Make_In (Loc,
8236                   Left_Opnd    => Make_Identifier (Loc, Nam),
8237                   Right_Opnd   => Empty,
8238                   Alternatives => New_Alts));
8239
8240               --  Resolve new expression in function context
8241
8242               Install_Formals (Predicate_Function (Typ));
8243               Push_Scope (Predicate_Function (Typ));
8244               Analyze_And_Resolve (Expr, Standard_Boolean);
8245               Pop_Scope;
8246            end if;
8247         end;
8248      end;
8249
8250      --  If non-static, return doing nothing
8251
8252   exception
8253      when Non_Static =>
8254         return;
8255   end Build_Discrete_Static_Predicate;
8256
8257   --------------------------------
8258   -- Build_Export_Import_Pragma --
8259   --------------------------------
8260
8261   function Build_Export_Import_Pragma
8262     (Asp : Node_Id;
8263      Id  : Entity_Id) return Node_Id
8264   is
8265      Asp_Id : constant Aspect_Id  := Get_Aspect_Id (Asp);
8266      Expr   : constant Node_Id    := Expression (Asp);
8267      Loc    : constant Source_Ptr := Sloc (Asp);
8268
8269      Args     : List_Id;
8270      Conv     : Node_Id;
8271      Conv_Arg : Node_Id;
8272      Dummy_1  : Node_Id;
8273      Dummy_2  : Node_Id;
8274      EN       : Node_Id;
8275      LN       : Node_Id;
8276      Prag     : Node_Id;
8277
8278      Create_Pragma : Boolean := False;
8279      --  This flag is set when the aspect form is such that it warrants the
8280      --  creation of a corresponding pragma.
8281
8282   begin
8283      if Present (Expr) then
8284         if Error_Posted (Expr) then
8285            null;
8286
8287         elsif Is_True (Expr_Value (Expr)) then
8288            Create_Pragma := True;
8289         end if;
8290
8291      --  Otherwise the aspect defaults to True
8292
8293      else
8294         Create_Pragma := True;
8295      end if;
8296
8297      --  Nothing to do when the expression is False or is erroneous
8298
8299      if not Create_Pragma then
8300         return Empty;
8301      end if;
8302
8303      --  Obtain all interfacing aspects that apply to the related entity
8304
8305      Get_Interfacing_Aspects
8306        (Iface_Asp => Asp,
8307         Conv_Asp  => Conv,
8308         EN_Asp    => EN,
8309         Expo_Asp  => Dummy_1,
8310         Imp_Asp   => Dummy_2,
8311         LN_Asp    => LN);
8312
8313      Args := New_List;
8314
8315      --  Handle the convention argument
8316
8317      if Present (Conv) then
8318         Conv_Arg := New_Copy_Tree (Expression (Conv));
8319
8320      --  Assume convention "Ada' when aspect Convention is missing
8321
8322      else
8323         Conv_Arg := Make_Identifier (Loc, Name_Ada);
8324      end if;
8325
8326      Append_To (Args,
8327        Make_Pragma_Argument_Association (Loc,
8328          Chars      => Name_Convention,
8329          Expression => Conv_Arg));
8330
8331      --  Handle the entity argument
8332
8333      Append_To (Args,
8334        Make_Pragma_Argument_Association (Loc,
8335          Chars      => Name_Entity,
8336          Expression => New_Occurrence_Of (Id, Loc)));
8337
8338      --  Handle the External_Name argument
8339
8340      if Present (EN) then
8341         Append_To (Args,
8342           Make_Pragma_Argument_Association (Loc,
8343             Chars      => Name_External_Name,
8344             Expression => New_Copy_Tree (Expression (EN))));
8345      end if;
8346
8347      --  Handle the Link_Name argument
8348
8349      if Present (LN) then
8350         Append_To (Args,
8351           Make_Pragma_Argument_Association (Loc,
8352             Chars      => Name_Link_Name,
8353             Expression => New_Copy_Tree (Expression (LN))));
8354      end if;
8355
8356      --  Generate:
8357      --    pragma Export/Import
8358      --      (Convention    => <Conv>/Ada,
8359      --       Entity        => <Id>,
8360      --      [External_Name => <EN>,]
8361      --      [Link_Name     => <LN>]);
8362
8363      Prag :=
8364        Make_Pragma (Loc,
8365          Pragma_Identifier            =>
8366            Make_Identifier (Loc, Chars (Identifier (Asp))),
8367          Pragma_Argument_Associations => Args);
8368
8369      --  Decorate the relevant aspect and the pragma
8370
8371      Set_Aspect_Rep_Item (Asp, Prag);
8372
8373      Set_Corresponding_Aspect      (Prag, Asp);
8374      Set_From_Aspect_Specification (Prag);
8375      Set_Parent                    (Prag, Asp);
8376
8377      if Asp_Id = Aspect_Import and then Is_Subprogram (Id) then
8378         Set_Import_Pragma (Id, Prag);
8379      end if;
8380
8381      return Prag;
8382   end Build_Export_Import_Pragma;
8383
8384   -------------------------------
8385   -- Build_Predicate_Functions --
8386   -------------------------------
8387
8388   --  The functions that are constructed here have the form:
8389
8390   --    function typPredicate (Ixxx : typ) return Boolean is
8391   --    begin
8392   --       return
8393   --          typ1Predicate (typ1 (Ixxx))
8394   --          and then typ2Predicate (typ2 (Ixxx))
8395   --          and then ...
8396   --          and then exp1 and then exp2 and then ...;
8397   --    end typPredicate;
8398
8399   --  Here exp1, and exp2 are expressions from Predicate pragmas. Note that
8400   --  this is the point at which these expressions get analyzed, providing the
8401   --  required delay, and typ1, typ2, are entities from which predicates are
8402   --  inherited. Note that we do NOT generate Check pragmas, that's because we
8403   --  use this function even if checks are off, e.g. for membership tests.
8404
8405   --  Note that the inherited predicates are evaluated first, as required by
8406   --  AI12-0071-1.
8407
8408   --  Note that Sem_Eval.Real_Or_String_Static_Predicate_Matches depends on
8409   --  the form of this return expression.
8410
8411   --  If the expression has at least one Raise_Expression, then we also build
8412   --  the typPredicateM version of the function, in which any occurrence of a
8413   --  Raise_Expression is converted to "return False".
8414
8415   --  WARNING: This routine manages Ghost regions. Return statements must be
8416   --  replaced by gotos which jump to the end of the routine and restore the
8417   --  Ghost mode.
8418
8419   procedure Build_Predicate_Functions (Typ : Entity_Id; N : Node_Id) is
8420      Loc : constant Source_Ptr := Sloc (Typ);
8421
8422      Expr : Node_Id;
8423      --  This is the expression for the result of the function. It is
8424      --  is build by connecting the component predicates with AND THEN.
8425
8426      Expr_M : Node_Id := Empty; -- init to avoid warning
8427      --  This is the corresponding return expression for the Predicate_M
8428      --  function. It differs in that raise expressions are marked for
8429      --  special expansion (see Process_REs).
8430
8431      Object_Name : Name_Id;
8432      --  Name for argument of Predicate procedure. Note that we use the same
8433      --  name for both predicate functions. That way the reference within the
8434      --  predicate expression is the same in both functions.
8435
8436      Object_Entity : Entity_Id;
8437      --  Entity for argument of Predicate procedure
8438
8439      Object_Entity_M : Entity_Id;
8440      --  Entity for argument of separate Predicate procedure when exceptions
8441      --  are present in expression.
8442
8443      FDecl : Node_Id;
8444      --  The function declaration
8445
8446      SId : Entity_Id;
8447      --  Its entity
8448
8449      Raise_Expression_Present : Boolean := False;
8450      --  Set True if Expr has at least one Raise_Expression
8451
8452      procedure Add_Condition (Cond : Node_Id);
8453      --  Append Cond to Expr using "and then" (or just copy Cond to Expr if
8454      --  Expr is empty).
8455
8456      procedure Add_Predicates;
8457      --  Appends expressions for any Predicate pragmas in the rep item chain
8458      --  Typ to Expr. Note that we look only at items for this exact entity.
8459      --  Inheritance of predicates for the parent type is done by calling the
8460      --  Predicate_Function of the parent type, using Add_Call above.
8461
8462      procedure Add_Call (T : Entity_Id);
8463      --  Includes a call to the predicate function for type T in Expr if T
8464      --  has predicates and Predicate_Function (T) is non-empty.
8465
8466      function Process_RE (N : Node_Id) return Traverse_Result;
8467      --  Used in Process REs, tests if node N is a raise expression, and if
8468      --  so, marks it to be converted to return False.
8469
8470      procedure Process_REs is new Traverse_Proc (Process_RE);
8471      --  Marks any raise expressions in Expr_M to return False
8472
8473      function Test_RE (N : Node_Id) return Traverse_Result;
8474      --  Used in Test_REs, tests one node for being a raise expression, and if
8475      --  so sets Raise_Expression_Present True.
8476
8477      procedure Test_REs is new Traverse_Proc (Test_RE);
8478      --  Tests to see if Expr contains any raise expressions
8479
8480      --------------
8481      -- Add_Call --
8482      --------------
8483
8484      procedure Add_Call (T : Entity_Id) is
8485         Exp : Node_Id;
8486
8487      begin
8488         if Present (T) and then Present (Predicate_Function (T)) then
8489            Set_Has_Predicates (Typ);
8490
8491            --  Build the call to the predicate function of T. The type may be
8492            --  derived, so use an unchecked conversion for the actual.
8493
8494            Exp :=
8495              Make_Predicate_Call
8496                (Typ  => T,
8497                 Expr =>
8498                   Unchecked_Convert_To (T,
8499                     Make_Identifier (Loc, Object_Name)));
8500
8501            --  "and"-in the call to evolving expression
8502
8503            Add_Condition (Exp);
8504
8505            --  Output info message on inheritance if required. Note we do not
8506            --  give this information for generic actual types, since it is
8507            --  unwelcome noise in that case in instantiations. We also
8508            --  generally suppress the message in instantiations, and also
8509            --  if it involves internal names.
8510
8511            if Opt.List_Inherited_Aspects
8512              and then not Is_Generic_Actual_Type (Typ)
8513              and then Instantiation_Depth (Sloc (Typ)) = 0
8514              and then not Is_Internal_Name (Chars (T))
8515              and then not Is_Internal_Name (Chars (Typ))
8516            then
8517               Error_Msg_Sloc := Sloc (Predicate_Function (T));
8518               Error_Msg_Node_2 := T;
8519               Error_Msg_N ("info: & inherits predicate from & #?L?", Typ);
8520            end if;
8521         end if;
8522      end Add_Call;
8523
8524      -------------------
8525      -- Add_Condition --
8526      -------------------
8527
8528      procedure Add_Condition (Cond : Node_Id) is
8529      begin
8530         --  This is the first predicate expression
8531
8532         if No (Expr) then
8533            Expr := Cond;
8534
8535         --  Otherwise concatenate to the existing predicate expressions by
8536         --  using "and then".
8537
8538         else
8539            Expr :=
8540              Make_And_Then (Loc,
8541                Left_Opnd  => Relocate_Node (Expr),
8542                Right_Opnd => Cond);
8543         end if;
8544      end Add_Condition;
8545
8546      --------------------
8547      -- Add_Predicates --
8548      --------------------
8549
8550      procedure Add_Predicates is
8551         procedure Add_Predicate (Prag : Node_Id);
8552         --  Concatenate the expression of predicate pragma Prag to Expr by
8553         --  using a short circuit "and then" operator.
8554
8555         -------------------
8556         -- Add_Predicate --
8557         -------------------
8558
8559         procedure Add_Predicate (Prag : Node_Id) is
8560            procedure Replace_Type_Reference (N : Node_Id);
8561            --  Replace a single occurrence N of the subtype name with a
8562            --  reference to the formal of the predicate function. N can be an
8563            --  identifier referencing the subtype, or a selected component,
8564            --  representing an appropriately qualified occurrence of the
8565            --  subtype name.
8566
8567            procedure Replace_Type_References is
8568              new Replace_Type_References_Generic (Replace_Type_Reference);
8569            --  Traverse an expression changing every occurrence of an
8570            --  identifier whose name matches the name of the subtype with a
8571            --  reference to the formal parameter of the predicate function.
8572
8573            ----------------------------
8574            -- Replace_Type_Reference --
8575            ----------------------------
8576
8577            procedure Replace_Type_Reference (N : Node_Id) is
8578            begin
8579               Rewrite (N, Make_Identifier (Sloc (N), Object_Name));
8580               --  Use the Sloc of the usage name, not the defining name
8581
8582               Set_Etype (N, Typ);
8583               Set_Entity (N, Object_Entity);
8584
8585               --  We want to treat the node as if it comes from source, so
8586               --  that ASIS will not ignore it.
8587
8588               Set_Comes_From_Source (N, True);
8589            end Replace_Type_Reference;
8590
8591            --  Local variables
8592
8593            Asp  : constant Node_Id := Corresponding_Aspect (Prag);
8594            Arg1 : Node_Id;
8595            Arg2 : Node_Id;
8596
8597         --  Start of processing for Add_Predicate
8598
8599         begin
8600            --  Mark corresponding SCO as enabled
8601
8602            Set_SCO_Pragma_Enabled (Sloc (Prag));
8603
8604            --  Extract the arguments of the pragma. The expression itself
8605            --  is copied for use in the predicate function, to preserve the
8606            --  original version for ASIS use.
8607
8608            Arg1 := First (Pragma_Argument_Associations (Prag));
8609            Arg2 := Next (Arg1);
8610
8611            Arg1 := Get_Pragma_Arg (Arg1);
8612            Arg2 := New_Copy_Tree (Get_Pragma_Arg (Arg2));
8613
8614            --  When the predicate pragma applies to the current type or its
8615            --  full view, replace all occurrences of the subtype name with
8616            --  references to the formal parameter of the predicate function.
8617
8618            if Entity (Arg1) = Typ
8619              or else Full_View (Entity (Arg1)) = Typ
8620            then
8621               Replace_Type_References (Arg2, Typ);
8622
8623               --  If the predicate pragma comes from an aspect, replace the
8624               --  saved expression because we need the subtype references
8625               --  replaced for the calls to Preanalyze_Spec_Expression in
8626               --  Check_Aspect_At_xxx routines.
8627
8628               if Present (Asp) then
8629                  Set_Entity (Identifier (Asp), New_Copy_Tree (Arg2));
8630               end if;
8631
8632               --  "and"-in the Arg2 condition to evolving expression
8633
8634               Add_Condition (Relocate_Node (Arg2));
8635            end if;
8636         end Add_Predicate;
8637
8638         --  Local variables
8639
8640         Ritem : Node_Id;
8641
8642      --  Start of processing for Add_Predicates
8643
8644      begin
8645         Ritem := First_Rep_Item (Typ);
8646
8647         --  If the type is private, check whether full view has inherited
8648         --  predicates.
8649
8650         if Is_Private_Type (Typ) and then No (Ritem) then
8651            Ritem := First_Rep_Item (Full_View (Typ));
8652         end if;
8653
8654         while Present (Ritem) loop
8655            if Nkind (Ritem) = N_Pragma
8656              and then Pragma_Name (Ritem) = Name_Predicate
8657            then
8658               Add_Predicate (Ritem);
8659
8660            --  If the type is declared in an inner package it may be frozen
8661            --  outside of the package, and the generated pragma has not been
8662            --  analyzed yet, so capture the expression for the predicate
8663            --  function at this point.
8664
8665            elsif Nkind (Ritem) = N_Aspect_Specification
8666              and then Present (Aspect_Rep_Item (Ritem))
8667              and then Scope (Typ) /= Current_Scope
8668            then
8669               declare
8670                  Prag : constant Node_Id := Aspect_Rep_Item (Ritem);
8671
8672               begin
8673                  if Nkind (Prag) = N_Pragma
8674                    and then Pragma_Name (Prag) = Name_Predicate
8675                  then
8676                     Add_Predicate (Prag);
8677                  end if;
8678               end;
8679            end if;
8680
8681            Next_Rep_Item (Ritem);
8682         end loop;
8683      end Add_Predicates;
8684
8685      ----------------
8686      -- Process_RE --
8687      ----------------
8688
8689      function Process_RE (N : Node_Id) return Traverse_Result is
8690      begin
8691         if Nkind (N) = N_Raise_Expression then
8692            Set_Convert_To_Return_False (N);
8693            return Skip;
8694         else
8695            return OK;
8696         end if;
8697      end Process_RE;
8698
8699      -------------
8700      -- Test_RE --
8701      -------------
8702
8703      function Test_RE (N : Node_Id) return Traverse_Result is
8704      begin
8705         if Nkind (N) = N_Raise_Expression then
8706            Raise_Expression_Present := True;
8707            return Abandon;
8708         else
8709            return OK;
8710         end if;
8711      end Test_RE;
8712
8713      --  Local variables
8714
8715      Saved_GM  : constant Ghost_Mode_Type := Ghost_Mode;
8716      Saved_IGR : constant Node_Id         := Ignored_Ghost_Region;
8717      --  Save the Ghost-related attributes to restore on exit
8718
8719   --  Start of processing for Build_Predicate_Functions
8720
8721   begin
8722      --  Return if already built or if type does not have predicates
8723
8724      SId := Predicate_Function (Typ);
8725      if not Has_Predicates (Typ)
8726        or else (Present (SId) and then Has_Completion (SId))
8727      then
8728         return;
8729
8730        --  Do not generate predicate bodies within a generic unit. The
8731        --  expressions have been analyzed already, and the bodies play
8732        --  no role if not within an executable unit.
8733
8734      elsif Inside_A_Generic then
8735         return;
8736      end if;
8737
8738      --  The related type may be subject to pragma Ghost. Set the mode now to
8739      --  ensure that the predicate functions are properly marked as Ghost.
8740
8741      Set_Ghost_Mode (Typ);
8742
8743      --  Prepare to construct predicate expression
8744
8745      Expr := Empty;
8746
8747      if Present (SId) then
8748         FDecl := Unit_Declaration_Node (SId);
8749
8750      else
8751         FDecl := Build_Predicate_Function_Declaration (Typ);
8752         SId   := Defining_Entity (FDecl);
8753      end if;
8754
8755      --  Recover name of formal parameter of function that replaces references
8756      --  to the type in predicate expressions.
8757
8758      Object_Entity :=
8759         Defining_Identifier
8760           (First (Parameter_Specifications (Specification (FDecl))));
8761
8762      Object_Name     := Chars (Object_Entity);
8763      Object_Entity_M := Make_Defining_Identifier (Loc, Chars => Object_Name);
8764
8765      --  Add predicates for ancestor if present. These must come before the
8766      --  ones for the current type, as required by AI12-0071-1.
8767
8768      declare
8769         Atyp : Entity_Id;
8770      begin
8771         Atyp := Nearest_Ancestor (Typ);
8772
8773         --  The type may be private but the full view may inherit predicates
8774
8775         if No (Atyp) and then Is_Private_Type (Typ) then
8776            Atyp := Nearest_Ancestor (Full_View (Typ));
8777         end if;
8778
8779         if Present (Atyp) then
8780            Add_Call (Atyp);
8781         end if;
8782      end;
8783
8784      --  Add Predicates for the current type
8785
8786      Add_Predicates;
8787
8788      --  Case where predicates are present
8789
8790      if Present (Expr) then
8791
8792         --  Test for raise expression present
8793
8794         Test_REs (Expr);
8795
8796         --  If raise expression is present, capture a copy of Expr for use
8797         --  in building the predicateM function version later on. For this
8798         --  copy we replace references to Object_Entity by Object_Entity_M.
8799
8800         if Raise_Expression_Present then
8801            declare
8802               function Reset_Loop_Variable
8803                 (N : Node_Id) return Traverse_Result;
8804
8805               procedure Reset_Loop_Variables is
8806                 new Traverse_Proc (Reset_Loop_Variable);
8807
8808               ------------------------
8809               -- Reset_Loop_Variable --
8810               ------------------------
8811
8812               function Reset_Loop_Variable
8813                 (N : Node_Id) return Traverse_Result
8814               is
8815               begin
8816                  if Nkind (N) = N_Iterator_Specification then
8817                     Set_Defining_Identifier (N,
8818                       Make_Defining_Identifier
8819                         (Sloc (N), Chars (Defining_Identifier (N))));
8820                  end if;
8821
8822                  return OK;
8823               end Reset_Loop_Variable;
8824
8825               --  Local variables
8826
8827               Map : constant Elist_Id := New_Elmt_List;
8828
8829            begin
8830               Append_Elmt (Object_Entity, Map);
8831               Append_Elmt (Object_Entity_M, Map);
8832               Expr_M := New_Copy_Tree (Expr, Map => Map);
8833
8834               --  The unanalyzed expression will be copied and appear in
8835               --  both functions. Normally expressions do not declare new
8836               --  entities, but quantified expressions do, so we need to
8837               --  create new entities for their bound variables, to prevent
8838               --  multiple definitions in gigi.
8839
8840               Reset_Loop_Variables (Expr_M);
8841            end;
8842         end if;
8843
8844         --  Build the main predicate function
8845
8846         declare
8847            SIdB : constant Entity_Id :=
8848              Make_Defining_Identifier (Loc,
8849                Chars => New_External_Name (Chars (Typ), "Predicate"));
8850            --  The entity for the function body
8851
8852            Spec  : Node_Id;
8853            FBody : Node_Id;
8854
8855         begin
8856            Set_Ekind (SIdB, E_Function);
8857            Set_Is_Predicate_Function (SIdB);
8858
8859            --  The predicate function is shared between views of a type
8860
8861            if Is_Private_Type (Typ) and then Present (Full_View (Typ)) then
8862               Set_Predicate_Function (Full_View (Typ), SId);
8863            end if;
8864
8865            --  Build function body
8866
8867            Spec :=
8868              Make_Function_Specification (Loc,
8869                Defining_Unit_Name       => SIdB,
8870                Parameter_Specifications => New_List (
8871                  Make_Parameter_Specification (Loc,
8872                    Defining_Identifier =>
8873                      Make_Defining_Identifier (Loc, Object_Name),
8874                    Parameter_Type =>
8875                      New_Occurrence_Of (Typ, Loc))),
8876                Result_Definition        =>
8877                  New_Occurrence_Of (Standard_Boolean, Loc));
8878
8879            FBody :=
8880              Make_Subprogram_Body (Loc,
8881                Specification              => Spec,
8882                Declarations               => Empty_List,
8883                Handled_Statement_Sequence =>
8884                  Make_Handled_Sequence_Of_Statements (Loc,
8885                    Statements => New_List (
8886                      Make_Simple_Return_Statement (Loc,
8887                        Expression => Expr))));
8888
8889            --  The declaration has been analyzed when created, and placed
8890            --  after type declaration. Insert body itself after freeze node.
8891
8892            Insert_After_And_Analyze (N, FBody);
8893
8894            --  The defining identifier of a quantified expression carries the
8895            --  scope in which the type appears, but when unnesting we need
8896            --  to indicate that its proper scope is the constructed predicate
8897            --  function. The quantified expressions have been converted into
8898            --  loops during analysis and expansion.
8899
8900            declare
8901               function Reset_Quantified_Variable_Scope
8902                 (N : Node_Id) return Traverse_Result;
8903
8904               procedure Reset_Quantified_Variables_Scope is
8905                 new Traverse_Proc (Reset_Quantified_Variable_Scope);
8906
8907               -------------------------------------
8908               -- Reset_Quantified_Variable_Scope --
8909               -------------------------------------
8910
8911               function Reset_Quantified_Variable_Scope
8912                 (N : Node_Id) return Traverse_Result
8913               is
8914               begin
8915                  if Nkind_In (N, N_Iterator_Specification,
8916                                  N_Loop_Parameter_Specification)
8917                  then
8918                     Set_Scope (Defining_Identifier (N),
8919                       Predicate_Function (Typ));
8920                  end if;
8921
8922                  return OK;
8923               end Reset_Quantified_Variable_Scope;
8924
8925            begin
8926               if Unnest_Subprogram_Mode then
8927                  Reset_Quantified_Variables_Scope (Expr);
8928               end if;
8929            end;
8930
8931            --  within a generic unit, prevent a double analysis of the body
8932            --  which will not be marked analyzed yet. This will happen when
8933            --  the freeze node is created during the preanalysis of an
8934            --  expression function.
8935
8936            if Inside_A_Generic then
8937               Set_Analyzed (FBody);
8938            end if;
8939
8940            --  Static predicate functions are always side-effect free, and
8941            --  in most cases dynamic predicate functions are as well. Mark
8942            --  them as such whenever possible, so redundant predicate checks
8943            --  can be optimized. If there is a variable reference within the
8944            --  expression, the function is not pure.
8945
8946            if Expander_Active then
8947               Set_Is_Pure (SId,
8948                 Side_Effect_Free (Expr, Variable_Ref => True));
8949               Set_Is_Inlined (SId);
8950            end if;
8951         end;
8952
8953         --  Test for raise expressions present and if so build M version
8954
8955         if Raise_Expression_Present then
8956            declare
8957               SId : constant Entity_Id :=
8958                 Make_Defining_Identifier (Loc,
8959                   Chars => New_External_Name (Chars (Typ), "PredicateM"));
8960               --  The entity for the function spec
8961
8962               SIdB : constant Entity_Id :=
8963                 Make_Defining_Identifier (Loc,
8964                   Chars => New_External_Name (Chars (Typ), "PredicateM"));
8965               --  The entity for the function body
8966
8967               Spec  : Node_Id;
8968               FBody : Node_Id;
8969               FDecl : Node_Id;
8970               BTemp : Entity_Id;
8971
8972            begin
8973               --  Mark any raise expressions for special expansion
8974
8975               Process_REs (Expr_M);
8976
8977               --  Build function declaration
8978
8979               Set_Ekind (SId, E_Function);
8980               Set_Is_Predicate_Function_M (SId);
8981               Set_Predicate_Function_M (Typ, SId);
8982
8983               --  The predicate function is shared between views of a type
8984
8985               if Is_Private_Type (Typ) and then Present (Full_View (Typ)) then
8986                  Set_Predicate_Function_M (Full_View (Typ), SId);
8987               end if;
8988
8989               Spec :=
8990                 Make_Function_Specification (Loc,
8991                   Defining_Unit_Name       => SId,
8992                   Parameter_Specifications => New_List (
8993                     Make_Parameter_Specification (Loc,
8994                       Defining_Identifier => Object_Entity_M,
8995                       Parameter_Type      => New_Occurrence_Of (Typ, Loc))),
8996                   Result_Definition        =>
8997                     New_Occurrence_Of (Standard_Boolean, Loc));
8998
8999               FDecl :=
9000                 Make_Subprogram_Declaration (Loc,
9001                   Specification => Spec);
9002
9003               --  Build function body
9004
9005               Spec :=
9006                 Make_Function_Specification (Loc,
9007                   Defining_Unit_Name       => SIdB,
9008                   Parameter_Specifications => New_List (
9009                     Make_Parameter_Specification (Loc,
9010                       Defining_Identifier =>
9011                         Make_Defining_Identifier (Loc, Object_Name),
9012                       Parameter_Type =>
9013                         New_Occurrence_Of (Typ, Loc))),
9014                   Result_Definition        =>
9015                     New_Occurrence_Of (Standard_Boolean, Loc));
9016
9017               --  Build the body, we declare the boolean expression before
9018               --  doing the return, because we are not really confident of
9019               --  what happens if a return appears within a return.
9020
9021               BTemp :=
9022                 Make_Defining_Identifier (Loc,
9023                   Chars => New_Internal_Name ('B'));
9024
9025               FBody :=
9026                 Make_Subprogram_Body (Loc,
9027                   Specification              => Spec,
9028
9029                   Declarations               => New_List (
9030                     Make_Object_Declaration (Loc,
9031                       Defining_Identifier => BTemp,
9032                       Constant_Present    => True,
9033                         Object_Definition =>
9034                           New_Occurrence_Of (Standard_Boolean, Loc),
9035                         Expression        => Expr_M)),
9036
9037                   Handled_Statement_Sequence =>
9038                     Make_Handled_Sequence_Of_Statements (Loc,
9039                       Statements => New_List (
9040                         Make_Simple_Return_Statement (Loc,
9041                           Expression => New_Occurrence_Of (BTemp, Loc)))));
9042
9043               --  Insert declaration before freeze node and body after
9044
9045               Insert_Before_And_Analyze (N, FDecl);
9046               Insert_After_And_Analyze  (N, FBody);
9047
9048               --  Should quantified expressions be handled here as well ???
9049            end;
9050         end if;
9051
9052         --  See if we have a static predicate. Note that the answer may be
9053         --  yes even if we have an explicit Dynamic_Predicate present.
9054
9055         declare
9056            PS : Boolean;
9057            EN : Node_Id;
9058
9059         begin
9060            if not Is_Scalar_Type (Typ) and then not Is_String_Type (Typ) then
9061               PS := False;
9062            else
9063               PS := Is_Predicate_Static (Expr, Object_Name);
9064            end if;
9065
9066            --  Case where we have a predicate-static aspect
9067
9068            if PS then
9069
9070               --  We don't set Has_Static_Predicate_Aspect, since we can have
9071               --  any of the three cases (Predicate, Dynamic_Predicate, or
9072               --  Static_Predicate) generating a predicate with an expression
9073               --  that is predicate-static. We just indicate that we have a
9074               --  predicate that can be treated as static.
9075
9076               Set_Has_Static_Predicate (Typ);
9077
9078               --  For discrete subtype, build the static predicate list
9079
9080               if Is_Discrete_Type (Typ) then
9081                  Build_Discrete_Static_Predicate (Typ, Expr, Object_Name);
9082
9083                  --  If we don't get a static predicate list, it means that we
9084                  --  have a case where this is not possible, most typically in
9085                  --  the case where we inherit a dynamic predicate. We do not
9086                  --  consider this an error, we just leave the predicate as
9087                  --  dynamic. But if we do succeed in building the list, then
9088                  --  we mark the predicate as static.
9089
9090                  if No (Static_Discrete_Predicate (Typ)) then
9091                     Set_Has_Static_Predicate (Typ, False);
9092                  end if;
9093
9094               --  For real or string subtype, save predicate expression
9095
9096               elsif Is_Real_Type (Typ) or else Is_String_Type (Typ) then
9097                  Set_Static_Real_Or_String_Predicate (Typ, Expr);
9098               end if;
9099
9100            --  Case of dynamic predicate (expression is not predicate-static)
9101
9102            else
9103               --  Again, we don't set Has_Dynamic_Predicate_Aspect, since that
9104               --  is only set if we have an explicit Dynamic_Predicate aspect
9105               --  given. Here we may simply have a Predicate aspect where the
9106               --  expression happens not to be predicate-static.
9107
9108               --  Emit an error when the predicate is categorized as static
9109               --  but its expression is not predicate-static.
9110
9111               --  First a little fiddling to get a nice location for the
9112               --  message. If the expression is of the form (A and then B),
9113               --  where A is an inherited predicate, then use the right
9114               --  operand for the Sloc. This avoids getting confused by a call
9115               --  to an inherited predicate with a less convenient source
9116               --  location.
9117
9118               EN := Expr;
9119               while Nkind (EN) = N_And_Then
9120                 and then Nkind (Left_Opnd (EN)) = N_Function_Call
9121                 and then Is_Predicate_Function
9122                            (Entity (Name (Left_Opnd (EN))))
9123               loop
9124                  EN := Right_Opnd (EN);
9125               end loop;
9126
9127               --  Now post appropriate message
9128
9129               if Has_Static_Predicate_Aspect (Typ) then
9130                  if Is_Scalar_Type (Typ) or else Is_String_Type (Typ) then
9131                     Error_Msg_F
9132                       ("expression is not predicate-static (RM 3.2.4(16-22))",
9133                        EN);
9134                  else
9135                     Error_Msg_F
9136                       ("static predicate requires scalar or string type", EN);
9137                  end if;
9138               end if;
9139            end if;
9140         end;
9141      end if;
9142
9143      Restore_Ghost_Region (Saved_GM, Saved_IGR);
9144   end Build_Predicate_Functions;
9145
9146   ------------------------------------------
9147   -- Build_Predicate_Function_Declaration --
9148   ------------------------------------------
9149
9150   --  WARNING: This routine manages Ghost regions. Return statements must be
9151   --  replaced by gotos which jump to the end of the routine and restore the
9152   --  Ghost mode.
9153
9154   function Build_Predicate_Function_Declaration
9155     (Typ : Entity_Id) return Node_Id
9156   is
9157      Loc : constant Source_Ptr := Sloc (Typ);
9158
9159      Saved_GM  : constant Ghost_Mode_Type := Ghost_Mode;
9160      Saved_IGR : constant Node_Id         := Ignored_Ghost_Region;
9161      --  Save the Ghost-related attributes to restore on exit
9162
9163      Func_Decl : Node_Id;
9164      Func_Id   : Entity_Id;
9165      Spec      : Node_Id;
9166
9167   begin
9168      --  The related type may be subject to pragma Ghost. Set the mode now to
9169      --  ensure that the predicate functions are properly marked as Ghost.
9170
9171      Set_Ghost_Mode (Typ);
9172
9173      Func_Id :=
9174        Make_Defining_Identifier (Loc,
9175          Chars => New_External_Name (Chars (Typ), "Predicate"));
9176
9177      --  The predicate function requires debug info when the predicates are
9178      --  subject to Source Coverage Obligations.
9179
9180      if Opt.Generate_SCO then
9181         Set_Debug_Info_Needed (Func_Id);
9182      end if;
9183
9184      Spec :=
9185        Make_Function_Specification (Loc,
9186          Defining_Unit_Name       => Func_Id,
9187          Parameter_Specifications => New_List (
9188            Make_Parameter_Specification (Loc,
9189              Defining_Identifier => Make_Temporary (Loc, 'I'),
9190              Parameter_Type      => New_Occurrence_Of (Typ, Loc))),
9191          Result_Definition        =>
9192            New_Occurrence_Of (Standard_Boolean, Loc));
9193
9194      Func_Decl := Make_Subprogram_Declaration (Loc, Specification => Spec);
9195
9196      Set_Ekind (Func_Id, E_Function);
9197      Set_Etype (Func_Id, Standard_Boolean);
9198      Set_Is_Internal (Func_Id);
9199      Set_Is_Predicate_Function (Func_Id);
9200      Set_Predicate_Function (Typ, Func_Id);
9201
9202      Insert_After (Parent (Typ), Func_Decl);
9203      Analyze (Func_Decl);
9204
9205      Restore_Ghost_Region (Saved_GM, Saved_IGR);
9206
9207      return Func_Decl;
9208   end Build_Predicate_Function_Declaration;
9209
9210   -----------------------------------------
9211   -- Check_Aspect_At_End_Of_Declarations --
9212   -----------------------------------------
9213
9214   procedure Check_Aspect_At_End_Of_Declarations (ASN : Node_Id) is
9215      Ent   : constant Entity_Id := Entity     (ASN);
9216      Ident : constant Node_Id   := Identifier (ASN);
9217      A_Id  : constant Aspect_Id := Get_Aspect_Id (Chars (Ident));
9218
9219      End_Decl_Expr : constant Node_Id := Entity (Ident);
9220      --  Expression to be analyzed at end of declarations
9221
9222      Freeze_Expr : constant Node_Id := Expression (ASN);
9223      --  Expression from call to Check_Aspect_At_Freeze_Point.
9224
9225      T : constant Entity_Id := Etype (Original_Node (Freeze_Expr));
9226      --  Type required for preanalyze call. We use the original expression to
9227      --  get the proper type, to prevent cascaded errors when the expression
9228      --  is constant-folded.
9229
9230      Err : Boolean;
9231      --  Set False if error
9232
9233      --  On entry to this procedure, Entity (Ident) contains a copy of the
9234      --  original expression from the aspect, saved for this purpose, and
9235      --  but Expression (Ident) is a preanalyzed copy of the expression,
9236      --  preanalyzed just after the freeze point.
9237
9238      procedure Check_Overloaded_Name;
9239      --  For aspects whose expression is simply a name, this routine checks if
9240      --  the name is overloaded or not. If so, it verifies there is an
9241      --  interpretation that matches the entity obtained at the freeze point,
9242      --  otherwise the compiler complains.
9243
9244      ---------------------------
9245      -- Check_Overloaded_Name --
9246      ---------------------------
9247
9248      procedure Check_Overloaded_Name is
9249      begin
9250         if not Is_Overloaded (End_Decl_Expr) then
9251            Err := not Is_Entity_Name (End_Decl_Expr)
9252                     or else Entity (End_Decl_Expr) /= Entity (Freeze_Expr);
9253
9254         else
9255            Err := True;
9256
9257            declare
9258               Index : Interp_Index;
9259               It    : Interp;
9260
9261            begin
9262               Get_First_Interp (End_Decl_Expr, Index, It);
9263               while Present (It.Typ) loop
9264                  if It.Nam = Entity (Freeze_Expr) then
9265                     Err := False;
9266                     exit;
9267                  end if;
9268
9269                  Get_Next_Interp (Index, It);
9270               end loop;
9271            end;
9272         end if;
9273      end Check_Overloaded_Name;
9274
9275   --  Start of processing for Check_Aspect_At_End_Of_Declarations
9276
9277   begin
9278      --  In an instance we do not perform the consistency check between freeze
9279      --  point and end of declarations, because it was done already in the
9280      --  analysis of the generic. Furthermore, the delayed analysis of an
9281      --  aspect of the instance may produce spurious errors when the generic
9282      --  is a child unit that references entities in the parent (which might
9283      --  not be in scope at the freeze point of the instance).
9284
9285      if In_Instance then
9286         return;
9287
9288      --  The enclosing scope may have been rewritten during expansion (.e.g. a
9289      --  task body is rewritten as a procedure) after this conformance check
9290      --  has been performed, so do not perform it again (it may not easily be
9291      --  done if full visibility of local entities is not available).
9292
9293      elsif not Comes_From_Source (Current_Scope) then
9294         return;
9295
9296      --  Case of aspects Dimension, Dimension_System and Synchronization
9297
9298      elsif A_Id = Aspect_Synchronization then
9299         return;
9300
9301      --  Case of stream attributes, just have to compare entities. However,
9302      --  the expression is just a name (possibly overloaded), and there may
9303      --  be stream operations declared for unrelated types, so we just need
9304      --  to verify that one of these interpretations is the one available at
9305      --  at the freeze point.
9306
9307      elsif A_Id = Aspect_Input  or else
9308            A_Id = Aspect_Output or else
9309            A_Id = Aspect_Read   or else
9310            A_Id = Aspect_Write
9311      then
9312         Analyze (End_Decl_Expr);
9313         Check_Overloaded_Name;
9314
9315      elsif A_Id = Aspect_Variable_Indexing or else
9316            A_Id = Aspect_Constant_Indexing or else
9317            A_Id = Aspect_Default_Iterator  or else
9318            A_Id = Aspect_Iterator_Element
9319      then
9320         --  Make type unfrozen before analysis, to prevent spurious errors
9321         --  about late attributes.
9322
9323         Set_Is_Frozen (Ent, False);
9324         Analyze (End_Decl_Expr);
9325         Set_Is_Frozen (Ent, True);
9326
9327         --  If the end of declarations comes before any other freeze
9328         --  point, the Freeze_Expr is not analyzed: no check needed.
9329
9330         if Analyzed (Freeze_Expr) and then not In_Instance then
9331            Check_Overloaded_Name;
9332         else
9333            Err := False;
9334         end if;
9335
9336      --  All other cases
9337
9338      else
9339         --  Indicate that the expression comes from an aspect specification,
9340         --  which is used in subsequent analysis even if expansion is off.
9341
9342         Set_Parent (End_Decl_Expr, ASN);
9343
9344         --  In a generic context the aspect expressions have not been
9345         --  preanalyzed, so do it now. There are no conformance checks
9346         --  to perform in this case.
9347
9348         if No (T) then
9349            Check_Aspect_At_Freeze_Point (ASN);
9350            return;
9351
9352         --  The default values attributes may be defined in the private part,
9353         --  and the analysis of the expression may take place when only the
9354         --  partial view is visible. The expression must be scalar, so use
9355         --  the full view to resolve.
9356
9357         elsif (A_Id = Aspect_Default_Value
9358                  or else
9359                A_Id = Aspect_Default_Component_Value)
9360            and then Is_Private_Type (T)
9361         then
9362            Preanalyze_Spec_Expression (End_Decl_Expr, Full_View (T));
9363
9364         --  The following aspect expressions may contain references to
9365         --  components and discriminants of the type.
9366
9367         elsif A_Id = Aspect_Dynamic_Predicate
9368           or else A_Id = Aspect_Predicate
9369           or else A_Id = Aspect_Priority
9370         then
9371            Push_Type (Ent);
9372            Preanalyze_Spec_Expression (End_Decl_Expr, T);
9373            Pop_Type (Ent);
9374
9375         else
9376            Preanalyze_Spec_Expression (End_Decl_Expr, T);
9377         end if;
9378
9379         Err :=
9380           not Fully_Conformant_Expressions
9381                 (End_Decl_Expr, Freeze_Expr, Report => True);
9382      end if;
9383
9384      --  Output error message if error. Force error on aspect specification
9385      --  even if there is an error on the expression itself.
9386
9387      if Err then
9388         Error_Msg_NE
9389           ("!visibility of aspect for& changes after freeze point",
9390            ASN, Ent);
9391         Error_Msg_NE
9392           ("info: & is frozen here, (RM 13.1.1 (13/3))??",
9393            Freeze_Node (Ent), Ent);
9394      end if;
9395   end Check_Aspect_At_End_Of_Declarations;
9396
9397   ----------------------------------
9398   -- Check_Aspect_At_Freeze_Point --
9399   ----------------------------------
9400
9401   procedure Check_Aspect_At_Freeze_Point (ASN : Node_Id) is
9402      Ident : constant Node_Id := Identifier (ASN);
9403      --  Identifier (use Entity field to save expression)
9404
9405      A_Id : constant Aspect_Id := Get_Aspect_Id (Chars (Ident));
9406
9407      T : Entity_Id := Empty;
9408      --  Type required for preanalyze call
9409
9410   begin
9411      --  On entry to this procedure, Entity (Ident) contains a copy of the
9412      --  original expression from the aspect, saved for this purpose.
9413
9414      --  On exit from this procedure Entity (Ident) is unchanged, still
9415      --  containing that copy, but Expression (Ident) is a preanalyzed copy
9416      --  of the expression, preanalyzed just after the freeze point.
9417
9418      --  Make a copy of the expression to be preanalyzed
9419
9420      Set_Expression (ASN, New_Copy_Tree (Entity (Ident)));
9421
9422      --  Find type for preanalyze call
9423
9424      case A_Id is
9425
9426         --  No_Aspect should be impossible
9427
9428         when No_Aspect =>
9429            raise Program_Error;
9430
9431         --  Aspects taking an optional boolean argument
9432
9433         when Boolean_Aspects
9434            | Library_Unit_Aspects
9435         =>
9436            T := Standard_Boolean;
9437
9438         --  Aspects corresponding to attribute definition clauses
9439
9440         when Aspect_Address =>
9441            T := RTE (RE_Address);
9442
9443         when Aspect_Attach_Handler =>
9444            T := RTE (RE_Interrupt_ID);
9445
9446         when Aspect_Bit_Order
9447            | Aspect_Scalar_Storage_Order
9448         =>
9449            T := RTE (RE_Bit_Order);
9450
9451         when Aspect_Convention =>
9452            return;
9453
9454         when Aspect_CPU =>
9455            T := RTE (RE_CPU_Range);
9456
9457         --  Default_Component_Value is resolved with the component type
9458
9459         when Aspect_Default_Component_Value =>
9460            T := Component_Type (Entity (ASN));
9461
9462         when Aspect_Default_Storage_Pool =>
9463            T := Class_Wide_Type (RTE (RE_Root_Storage_Pool));
9464
9465         --  Default_Value is resolved with the type entity in question
9466
9467         when Aspect_Default_Value =>
9468            T := Entity (ASN);
9469
9470         when Aspect_Dispatching_Domain =>
9471            T := RTE (RE_Dispatching_Domain);
9472
9473         when Aspect_External_Tag =>
9474            T := Standard_String;
9475
9476         when Aspect_External_Name =>
9477            T := Standard_String;
9478
9479         when Aspect_Link_Name =>
9480            T := Standard_String;
9481
9482         when Aspect_Interrupt_Priority
9483            | Aspect_Priority
9484         =>
9485            T := Standard_Integer;
9486
9487         when Aspect_Relative_Deadline =>
9488            T := RTE (RE_Time_Span);
9489
9490         when Aspect_Secondary_Stack_Size =>
9491            T := Standard_Integer;
9492
9493         when Aspect_Small =>
9494
9495            --  Note that the expression can be of any real type (not just a
9496            --  real universal literal) as long as it is a static constant.
9497
9498            T := Any_Real;
9499
9500         --  For a simple storage pool, we have to retrieve the type of the
9501         --  pool object associated with the aspect's corresponding attribute
9502         --  definition clause.
9503
9504         when Aspect_Simple_Storage_Pool =>
9505            T := Etype (Expression (Aspect_Rep_Item (ASN)));
9506
9507         when Aspect_Storage_Pool =>
9508            T := Class_Wide_Type (RTE (RE_Root_Storage_Pool));
9509
9510         when Aspect_Alignment
9511            | Aspect_Component_Size
9512            | Aspect_Machine_Radix
9513            | Aspect_Object_Size
9514            | Aspect_Size
9515            | Aspect_Storage_Size
9516            | Aspect_Stream_Size
9517            | Aspect_Value_Size
9518         =>
9519            T := Any_Integer;
9520
9521         when Aspect_Linker_Section =>
9522            T := Standard_String;
9523
9524         when Aspect_Synchronization =>
9525            return;
9526
9527         --  Special case, the expression of these aspects is just an entity
9528         --  that does not need any resolution, so just analyze.
9529
9530         when Aspect_Input
9531            | Aspect_Output
9532            | Aspect_Read
9533            | Aspect_Suppress
9534            | Aspect_Unsuppress
9535            | Aspect_Warnings
9536            | Aspect_Write
9537         =>
9538            Analyze (Expression (ASN));
9539            return;
9540
9541         --  Same for Iterator aspects, where the expression is a function
9542         --  name. Legality rules are checked separately.
9543
9544         when Aspect_Constant_Indexing
9545            | Aspect_Default_Iterator
9546            | Aspect_Iterator_Element
9547            | Aspect_Variable_Indexing
9548         =>
9549            Analyze (Expression (ASN));
9550            return;
9551
9552         --  Ditto for Iterable, legality checks in Validate_Iterable_Aspect.
9553
9554         when Aspect_Iterable =>
9555            T := Entity (ASN);
9556
9557            declare
9558               Cursor : constant Entity_Id := Get_Cursor_Type (ASN, T);
9559               Assoc  : Node_Id;
9560               Expr   : Node_Id;
9561
9562            begin
9563               if Cursor = Any_Type then
9564                  return;
9565               end if;
9566
9567               Assoc := First (Component_Associations (Expression (ASN)));
9568               while Present (Assoc) loop
9569                  Expr := Expression (Assoc);
9570                  Analyze (Expr);
9571
9572                  if not Error_Posted (Expr) then
9573                     Resolve_Iterable_Operation
9574                       (Expr, Cursor, T, Chars (First (Choices (Assoc))));
9575                  end if;
9576
9577                  Next (Assoc);
9578               end loop;
9579            end;
9580
9581            return;
9582
9583         --  Invariant/Predicate take boolean expressions
9584
9585         when Aspect_Dynamic_Predicate
9586            | Aspect_Invariant
9587            | Aspect_Predicate
9588            | Aspect_Static_Predicate
9589            | Aspect_Type_Invariant
9590         =>
9591            T := Standard_Boolean;
9592
9593         when Aspect_Predicate_Failure =>
9594            T := Standard_String;
9595
9596         --  Here is the list of aspects that don't require delay analysis
9597
9598         when Aspect_Abstract_State
9599            | Aspect_Annotate
9600            | Aspect_Async_Readers
9601            | Aspect_Async_Writers
9602            | Aspect_Constant_After_Elaboration
9603            | Aspect_Contract_Cases
9604            | Aspect_Default_Initial_Condition
9605            | Aspect_Depends
9606            | Aspect_Dimension
9607            | Aspect_Dimension_System
9608            | Aspect_Effective_Reads
9609            | Aspect_Effective_Writes
9610            | Aspect_Extensions_Visible
9611            | Aspect_Ghost
9612            | Aspect_Global
9613            | Aspect_Implicit_Dereference
9614            | Aspect_Initial_Condition
9615            | Aspect_Initializes
9616            | Aspect_Max_Entry_Queue_Depth
9617            | Aspect_Max_Queue_Length
9618            | Aspect_Obsolescent
9619            | Aspect_Part_Of
9620            | Aspect_Post
9621            | Aspect_Postcondition
9622            | Aspect_Pre
9623            | Aspect_Precondition
9624            | Aspect_Refined_Depends
9625            | Aspect_Refined_Global
9626            | Aspect_Refined_Post
9627            | Aspect_Refined_State
9628            | Aspect_SPARK_Mode
9629            | Aspect_Test_Case
9630            | Aspect_Unimplemented
9631            | Aspect_Volatile_Function
9632         =>
9633            raise Program_Error;
9634
9635      end case;
9636
9637      --  Do the preanalyze call
9638
9639      Preanalyze_Spec_Expression (Expression (ASN), T);
9640   end Check_Aspect_At_Freeze_Point;
9641
9642   -----------------------------------
9643   -- Check_Constant_Address_Clause --
9644   -----------------------------------
9645
9646   procedure Check_Constant_Address_Clause
9647     (Expr  : Node_Id;
9648      U_Ent : Entity_Id)
9649   is
9650      procedure Check_At_Constant_Address (Nod : Node_Id);
9651      --  Checks that the given node N represents a name whose 'Address is
9652      --  constant (in the same sense as OK_Constant_Address_Clause, i.e. the
9653      --  address value is the same at the point of declaration of U_Ent and at
9654      --  the time of elaboration of the address clause.
9655
9656      procedure Check_Expr_Constants (Nod : Node_Id);
9657      --  Checks that Nod meets the requirements for a constant address clause
9658      --  in the sense of the enclosing procedure.
9659
9660      procedure Check_List_Constants (Lst : List_Id);
9661      --  Check that all elements of list Lst meet the requirements for a
9662      --  constant address clause in the sense of the enclosing procedure.
9663
9664      -------------------------------
9665      -- Check_At_Constant_Address --
9666      -------------------------------
9667
9668      procedure Check_At_Constant_Address (Nod : Node_Id) is
9669      begin
9670         if Is_Entity_Name (Nod) then
9671            if Present (Address_Clause (Entity ((Nod)))) then
9672               Error_Msg_NE
9673                 ("invalid address clause for initialized object &!",
9674                  Nod, U_Ent);
9675               Error_Msg_NE
9676                 ("address for& cannot depend on another address clause! "
9677                  & "(RM 13.1(22))!", Nod, U_Ent);
9678
9679            elsif In_Same_Source_Unit (Entity (Nod), U_Ent)
9680              and then Sloc (U_Ent) < Sloc (Entity (Nod))
9681            then
9682               Error_Msg_NE
9683                 ("invalid address clause for initialized object &!",
9684                  Nod, U_Ent);
9685               Error_Msg_Node_2 := U_Ent;
9686               Error_Msg_NE
9687                 ("\& must be defined before & (RM 13.1(22))!",
9688                  Nod, Entity (Nod));
9689            end if;
9690
9691         elsif Nkind (Nod) = N_Selected_Component then
9692            declare
9693               T : constant Entity_Id := Etype (Prefix (Nod));
9694
9695            begin
9696               if (Is_Record_Type (T)
9697                    and then Has_Discriminants (T))
9698                 or else
9699                  (Is_Access_Type (T)
9700                    and then Is_Record_Type (Designated_Type (T))
9701                    and then Has_Discriminants (Designated_Type (T)))
9702               then
9703                  Error_Msg_NE
9704                    ("invalid address clause for initialized object &!",
9705                     Nod, U_Ent);
9706                  Error_Msg_N
9707                    ("\address cannot depend on component of discriminated "
9708                     & "record (RM 13.1(22))!", Nod);
9709               else
9710                  Check_At_Constant_Address (Prefix (Nod));
9711               end if;
9712            end;
9713
9714         elsif Nkind (Nod) = N_Indexed_Component then
9715            Check_At_Constant_Address (Prefix (Nod));
9716            Check_List_Constants (Expressions (Nod));
9717
9718         else
9719            Check_Expr_Constants (Nod);
9720         end if;
9721      end Check_At_Constant_Address;
9722
9723      --------------------------
9724      -- Check_Expr_Constants --
9725      --------------------------
9726
9727      procedure Check_Expr_Constants (Nod : Node_Id) is
9728         Loc_U_Ent : constant Source_Ptr := Sloc (U_Ent);
9729         Ent       : Entity_Id           := Empty;
9730
9731      begin
9732         if Nkind (Nod) in N_Has_Etype
9733           and then Etype (Nod) = Any_Type
9734         then
9735            return;
9736         end if;
9737
9738         case Nkind (Nod) is
9739            when N_Empty
9740               | N_Error
9741            =>
9742               return;
9743
9744            when N_Expanded_Name
9745               | N_Identifier
9746            =>
9747               Ent := Entity (Nod);
9748
9749               --  We need to look at the original node if it is different
9750               --  from the node, since we may have rewritten things and
9751               --  substituted an identifier representing the rewrite.
9752
9753               if Is_Rewrite_Substitution (Nod) then
9754                  Check_Expr_Constants (Original_Node (Nod));
9755
9756                  --  If the node is an object declaration without initial
9757                  --  value, some code has been expanded, and the expression
9758                  --  is not constant, even if the constituents might be
9759                  --  acceptable, as in A'Address + offset.
9760
9761                  if Ekind (Ent) = E_Variable
9762                    and then
9763                      Nkind (Declaration_Node (Ent)) = N_Object_Declaration
9764                    and then
9765                      No (Expression (Declaration_Node (Ent)))
9766                  then
9767                     Error_Msg_NE
9768                       ("invalid address clause for initialized object &!",
9769                        Nod, U_Ent);
9770
9771                  --  If entity is constant, it may be the result of expanding
9772                  --  a check. We must verify that its declaration appears
9773                  --  before the object in question, else we also reject the
9774                  --  address clause.
9775
9776                  elsif Ekind (Ent) = E_Constant
9777                    and then In_Same_Source_Unit (Ent, U_Ent)
9778                    and then Sloc (Ent) > Loc_U_Ent
9779                  then
9780                     Error_Msg_NE
9781                       ("invalid address clause for initialized object &!",
9782                        Nod, U_Ent);
9783                  end if;
9784
9785                  return;
9786               end if;
9787
9788               --  Otherwise look at the identifier and see if it is OK
9789
9790               if Ekind_In (Ent, E_Named_Integer, E_Named_Real)
9791                 or else Is_Type (Ent)
9792               then
9793                  return;
9794
9795               elsif Ekind_In (Ent, E_Constant, E_In_Parameter) then
9796
9797                  --  This is the case where we must have Ent defined before
9798                  --  U_Ent. Clearly if they are in different units this
9799                  --  requirement is met since the unit containing Ent is
9800                  --  already processed.
9801
9802                  if not In_Same_Source_Unit (Ent, U_Ent) then
9803                     return;
9804
9805                  --  Otherwise location of Ent must be before the location
9806                  --  of U_Ent, that's what prior defined means.
9807
9808                  elsif Sloc (Ent) < Loc_U_Ent then
9809                     return;
9810
9811                  else
9812                     Error_Msg_NE
9813                       ("invalid address clause for initialized object &!",
9814                        Nod, U_Ent);
9815                     Error_Msg_Node_2 := U_Ent;
9816                     Error_Msg_NE
9817                       ("\& must be defined before & (RM 13.1(22))!",
9818                        Nod, Ent);
9819                  end if;
9820
9821               elsif Nkind (Original_Node (Nod)) = N_Function_Call then
9822                  Check_Expr_Constants (Original_Node (Nod));
9823
9824               else
9825                  Error_Msg_NE
9826                    ("invalid address clause for initialized object &!",
9827                     Nod, U_Ent);
9828
9829                  if Comes_From_Source (Ent) then
9830                     Error_Msg_NE
9831                       ("\reference to variable& not allowed"
9832                          & " (RM 13.1(22))!", Nod, Ent);
9833                  else
9834                     Error_Msg_N
9835                       ("non-static expression not allowed"
9836                          & " (RM 13.1(22))!", Nod);
9837                  end if;
9838               end if;
9839
9840            when N_Integer_Literal   =>
9841
9842               --  If this is a rewritten unchecked conversion, in a system
9843               --  where Address is an integer type, always use the base type
9844               --  for a literal value. This is user-friendly and prevents
9845               --  order-of-elaboration issues with instances of unchecked
9846               --  conversion.
9847
9848               if Nkind (Original_Node (Nod)) = N_Function_Call then
9849                  Set_Etype (Nod, Base_Type (Etype (Nod)));
9850               end if;
9851
9852            when N_Character_Literal
9853               | N_Real_Literal
9854               | N_String_Literal
9855            =>
9856               return;
9857
9858            when N_Range =>
9859               Check_Expr_Constants (Low_Bound (Nod));
9860               Check_Expr_Constants (High_Bound (Nod));
9861
9862            when N_Explicit_Dereference =>
9863               Check_Expr_Constants (Prefix (Nod));
9864
9865            when N_Indexed_Component =>
9866               Check_Expr_Constants (Prefix (Nod));
9867               Check_List_Constants (Expressions (Nod));
9868
9869            when N_Slice =>
9870               Check_Expr_Constants (Prefix (Nod));
9871               Check_Expr_Constants (Discrete_Range (Nod));
9872
9873            when N_Selected_Component =>
9874               Check_Expr_Constants (Prefix (Nod));
9875
9876            when N_Attribute_Reference =>
9877               if Nam_In (Attribute_Name (Nod), Name_Address,
9878                                                Name_Access,
9879                                                Name_Unchecked_Access,
9880                                                Name_Unrestricted_Access)
9881               then
9882                  Check_At_Constant_Address (Prefix (Nod));
9883
9884               --  Normally, System'To_Address will have been transformed into
9885               --  an Unchecked_Conversion, but in -gnatc mode, it will not,
9886               --  and we don't want to give an error, because the whole point
9887               --  of 'To_Address is that it is static.
9888
9889               elsif Attribute_Name (Nod) = Name_To_Address then
9890                  pragma Assert (Operating_Mode = Check_Semantics);
9891                  null;
9892
9893               else
9894                  Check_Expr_Constants (Prefix (Nod));
9895                  Check_List_Constants (Expressions (Nod));
9896               end if;
9897
9898            when N_Aggregate =>
9899               Check_List_Constants (Component_Associations (Nod));
9900               Check_List_Constants (Expressions (Nod));
9901
9902            when N_Component_Association =>
9903               Check_Expr_Constants (Expression (Nod));
9904
9905            when N_Extension_Aggregate =>
9906               Check_Expr_Constants (Ancestor_Part (Nod));
9907               Check_List_Constants (Component_Associations (Nod));
9908               Check_List_Constants (Expressions (Nod));
9909
9910            when N_Null =>
9911               return;
9912
9913            when N_Binary_Op
9914               | N_Membership_Test
9915               | N_Short_Circuit
9916            =>
9917               Check_Expr_Constants (Left_Opnd (Nod));
9918               Check_Expr_Constants (Right_Opnd (Nod));
9919
9920            when N_Unary_Op =>
9921               Check_Expr_Constants (Right_Opnd (Nod));
9922
9923            when N_Allocator
9924               | N_Qualified_Expression
9925               | N_Type_Conversion
9926               | N_Unchecked_Type_Conversion
9927            =>
9928               Check_Expr_Constants (Expression (Nod));
9929
9930            when N_Function_Call =>
9931               if not Is_Pure (Entity (Name (Nod))) then
9932                  Error_Msg_NE
9933                    ("invalid address clause for initialized object &!",
9934                     Nod, U_Ent);
9935
9936                  Error_Msg_NE
9937                    ("\function & is not pure (RM 13.1(22))!",
9938                     Nod, Entity (Name (Nod)));
9939
9940               else
9941                  Check_List_Constants (Parameter_Associations (Nod));
9942               end if;
9943
9944            when N_Parameter_Association =>
9945               Check_Expr_Constants (Explicit_Actual_Parameter (Nod));
9946
9947            when others =>
9948               Error_Msg_NE
9949                 ("invalid address clause for initialized object &!",
9950                  Nod, U_Ent);
9951               Error_Msg_NE
9952                 ("\must be constant defined before& (RM 13.1(22))!",
9953                  Nod, U_Ent);
9954         end case;
9955      end Check_Expr_Constants;
9956
9957      --------------------------
9958      -- Check_List_Constants --
9959      --------------------------
9960
9961      procedure Check_List_Constants (Lst : List_Id) is
9962         Nod1 : Node_Id;
9963
9964      begin
9965         if Present (Lst) then
9966            Nod1 := First (Lst);
9967            while Present (Nod1) loop
9968               Check_Expr_Constants (Nod1);
9969               Next (Nod1);
9970            end loop;
9971         end if;
9972      end Check_List_Constants;
9973
9974   --  Start of processing for Check_Constant_Address_Clause
9975
9976   begin
9977      --  If rep_clauses are to be ignored, no need for legality checks. In
9978      --  particular, no need to pester user about rep clauses that violate the
9979      --  rule on constant addresses, given that these clauses will be removed
9980      --  by Freeze before they reach the back end. Similarly in CodePeer mode,
9981      --  we want to relax these checks.
9982
9983      if not Ignore_Rep_Clauses and not CodePeer_Mode then
9984         Check_Expr_Constants (Expr);
9985      end if;
9986   end Check_Constant_Address_Clause;
9987
9988   ---------------------------
9989   -- Check_Pool_Size_Clash --
9990   ---------------------------
9991
9992   procedure Check_Pool_Size_Clash (Ent : Entity_Id; SP, SS : Node_Id) is
9993      Post : Node_Id;
9994
9995   begin
9996      --  We need to find out which one came first. Note that in the case of
9997      --  aspects mixed with pragmas there are cases where the processing order
9998      --  is reversed, which is why we do the check here.
9999
10000      if Sloc (SP) < Sloc (SS) then
10001         Error_Msg_Sloc := Sloc (SP);
10002         Post := SS;
10003         Error_Msg_NE ("Storage_Pool previously given for&#", Post, Ent);
10004
10005      else
10006         Error_Msg_Sloc := Sloc (SS);
10007         Post := SP;
10008         Error_Msg_NE ("Storage_Size previously given for&#", Post, Ent);
10009      end if;
10010
10011      Error_Msg_N
10012        ("\cannot have Storage_Size and Storage_Pool (RM 13.11(3))", Post);
10013   end Check_Pool_Size_Clash;
10014
10015   ----------------------------------------
10016   -- Check_Record_Representation_Clause --
10017   ----------------------------------------
10018
10019   procedure Check_Record_Representation_Clause (N : Node_Id) is
10020      Loc     : constant Source_Ptr := Sloc (N);
10021      Ident   : constant Node_Id    := Identifier (N);
10022      Rectype : Entity_Id;
10023      Fent    : Entity_Id;
10024      CC      : Node_Id;
10025      Fbit    : Uint;
10026      Lbit    : Uint;
10027      Hbit    : Uint := Uint_0;
10028      Comp    : Entity_Id;
10029      Pcomp   : Entity_Id;
10030
10031      Max_Bit_So_Far : Uint;
10032      --  Records the maximum bit position so far. If all field positions
10033      --  are monotonically increasing, then we can skip the circuit for
10034      --  checking for overlap, since no overlap is possible.
10035
10036      Tagged_Parent : Entity_Id := Empty;
10037      --  This is set in the case of an extension for which we have either a
10038      --  size clause or Is_Fully_Repped_Tagged_Type True (indicating that all
10039      --  components are positioned by record representation clauses) on the
10040      --  parent type. In this case we check for overlap between components of
10041      --  this tagged type and the parent component. Tagged_Parent will point
10042      --  to this parent type. For all other cases, Tagged_Parent is Empty.
10043
10044      Parent_Last_Bit : Uint := No_Uint; -- init to avoid warning
10045      --  Relevant only if Tagged_Parent is set, Parent_Last_Bit indicates the
10046      --  last bit position for any field in the parent type. We only need to
10047      --  check overlap for fields starting below this point.
10048
10049      Overlap_Check_Required : Boolean;
10050      --  Used to keep track of whether or not an overlap check is required
10051
10052      Overlap_Detected : Boolean := False;
10053      --  Set True if an overlap is detected
10054
10055      Ccount : Natural := 0;
10056      --  Number of component clauses in record rep clause
10057
10058      procedure Check_Component_Overlap (C1_Ent, C2_Ent : Entity_Id);
10059      --  Given two entities for record components or discriminants, checks
10060      --  if they have overlapping component clauses and issues errors if so.
10061
10062      procedure Find_Component;
10063      --  Finds component entity corresponding to current component clause (in
10064      --  CC), and sets Comp to the entity, and Fbit/Lbit to the zero origin
10065      --  start/stop bits for the field. If there is no matching component or
10066      --  if the matching component does not have a component clause, then
10067      --  that's an error and Comp is set to Empty, but no error message is
10068      --  issued, since the message was already given. Comp is also set to
10069      --  Empty if the current "component clause" is in fact a pragma.
10070
10071      -----------------------------
10072      -- Check_Component_Overlap --
10073      -----------------------------
10074
10075      procedure Check_Component_Overlap (C1_Ent, C2_Ent : Entity_Id) is
10076         CC1 : constant Node_Id := Component_Clause (C1_Ent);
10077         CC2 : constant Node_Id := Component_Clause (C2_Ent);
10078
10079      begin
10080         if Present (CC1) and then Present (CC2) then
10081
10082            --  Exclude odd case where we have two tag components in the same
10083            --  record, both at location zero. This seems a bit strange, but
10084            --  it seems to happen in some circumstances, perhaps on an error.
10085
10086            if Nam_In (Chars (C1_Ent), Name_uTag, Name_uTag) then
10087               return;
10088            end if;
10089
10090            --  Here we check if the two fields overlap
10091
10092            declare
10093               S1 : constant Uint := Component_Bit_Offset (C1_Ent);
10094               S2 : constant Uint := Component_Bit_Offset (C2_Ent);
10095               E1 : constant Uint := S1 + Esize (C1_Ent);
10096               E2 : constant Uint := S2 + Esize (C2_Ent);
10097
10098            begin
10099               if E2 <= S1 or else E1 <= S2 then
10100                  null;
10101               else
10102                  Error_Msg_Node_2 := Component_Name (CC2);
10103                  Error_Msg_Sloc := Sloc (Error_Msg_Node_2);
10104                  Error_Msg_Node_1 := Component_Name (CC1);
10105                  Error_Msg_N
10106                    ("component& overlaps & #", Component_Name (CC1));
10107                  Overlap_Detected := True;
10108               end if;
10109            end;
10110         end if;
10111      end Check_Component_Overlap;
10112
10113      --------------------
10114      -- Find_Component --
10115      --------------------
10116
10117      procedure Find_Component is
10118
10119         procedure Search_Component (R : Entity_Id);
10120         --  Search components of R for a match. If found, Comp is set
10121
10122         ----------------------
10123         -- Search_Component --
10124         ----------------------
10125
10126         procedure Search_Component (R : Entity_Id) is
10127         begin
10128            Comp := First_Component_Or_Discriminant (R);
10129            while Present (Comp) loop
10130
10131               --  Ignore error of attribute name for component name (we
10132               --  already gave an error message for this, so no need to
10133               --  complain here)
10134
10135               if Nkind (Component_Name (CC)) = N_Attribute_Reference then
10136                  null;
10137               else
10138                  exit when Chars (Comp) = Chars (Component_Name (CC));
10139               end if;
10140
10141               Next_Component_Or_Discriminant (Comp);
10142            end loop;
10143         end Search_Component;
10144
10145      --  Start of processing for Find_Component
10146
10147      begin
10148         --  Return with Comp set to Empty if we have a pragma
10149
10150         if Nkind (CC) = N_Pragma then
10151            Comp := Empty;
10152            return;
10153         end if;
10154
10155         --  Search current record for matching component
10156
10157         Search_Component (Rectype);
10158
10159         --  If not found, maybe component of base type discriminant that is
10160         --  absent from statically constrained first subtype.
10161
10162         if No (Comp) then
10163            Search_Component (Base_Type (Rectype));
10164         end if;
10165
10166         --  If no component, or the component does not reference the component
10167         --  clause in question, then there was some previous error for which
10168         --  we already gave a message, so just return with Comp Empty.
10169
10170         if No (Comp) or else Component_Clause (Comp) /= CC then
10171            Check_Error_Detected;
10172            Comp := Empty;
10173
10174         --  Normal case where we have a component clause
10175
10176         else
10177            Fbit := Component_Bit_Offset (Comp);
10178            Lbit := Fbit + Esize (Comp) - 1;
10179         end if;
10180      end Find_Component;
10181
10182   --  Start of processing for Check_Record_Representation_Clause
10183
10184   begin
10185      Find_Type (Ident);
10186      Rectype := Entity (Ident);
10187
10188      if Rectype = Any_Type then
10189         return;
10190      end if;
10191
10192      Rectype := Underlying_Type (Rectype);
10193
10194      --  See if we have a fully repped derived tagged type
10195
10196      declare
10197         PS : constant Entity_Id := Parent_Subtype (Rectype);
10198
10199      begin
10200         if Present (PS) and then Known_Static_RM_Size (PS) then
10201            Tagged_Parent := PS;
10202            Parent_Last_Bit := RM_Size (PS) - 1;
10203
10204         elsif Present (PS) and then Is_Fully_Repped_Tagged_Type (PS) then
10205            Tagged_Parent := PS;
10206
10207            --  Find maximum bit of any component of the parent type
10208
10209            Parent_Last_Bit := UI_From_Int (System_Address_Size - 1);
10210            Pcomp := First_Entity (Tagged_Parent);
10211            while Present (Pcomp) loop
10212               if Ekind_In (Pcomp, E_Discriminant, E_Component) then
10213                  if Component_Bit_Offset (Pcomp) /= No_Uint
10214                    and then Known_Static_Esize (Pcomp)
10215                  then
10216                     Parent_Last_Bit :=
10217                       UI_Max
10218                         (Parent_Last_Bit,
10219                          Component_Bit_Offset (Pcomp) + Esize (Pcomp) - 1);
10220                  end if;
10221               else
10222
10223                  --  Skip anonymous types generated for constrained array
10224                  --  or record components.
10225
10226                  null;
10227               end if;
10228
10229               Next_Entity (Pcomp);
10230            end loop;
10231         end if;
10232      end;
10233
10234      --  All done if no component clauses
10235
10236      CC := First (Component_Clauses (N));
10237
10238      if No (CC) then
10239         return;
10240      end if;
10241
10242      --  If a tag is present, then create a component clause that places it
10243      --  at the start of the record (otherwise gigi may place it after other
10244      --  fields that have rep clauses).
10245
10246      Fent := First_Entity (Rectype);
10247
10248      if Nkind (Fent) = N_Defining_Identifier
10249        and then Chars (Fent) = Name_uTag
10250      then
10251         Set_Component_Bit_Offset    (Fent, Uint_0);
10252         Set_Normalized_Position     (Fent, Uint_0);
10253         Set_Normalized_First_Bit    (Fent, Uint_0);
10254         Set_Normalized_Position_Max (Fent, Uint_0);
10255         Init_Esize                  (Fent, System_Address_Size);
10256
10257         Set_Component_Clause (Fent,
10258           Make_Component_Clause (Loc,
10259             Component_Name => Make_Identifier (Loc, Name_uTag),
10260
10261             Position  => Make_Integer_Literal (Loc, Uint_0),
10262             First_Bit => Make_Integer_Literal (Loc, Uint_0),
10263             Last_Bit  =>
10264               Make_Integer_Literal (Loc,
10265                 UI_From_Int (System_Address_Size))));
10266
10267         Ccount := Ccount + 1;
10268      end if;
10269
10270      Max_Bit_So_Far := Uint_Minus_1;
10271      Overlap_Check_Required := False;
10272
10273      --  Process the component clauses
10274
10275      while Present (CC) loop
10276         Find_Component;
10277
10278         if Present (Comp) then
10279            Ccount := Ccount + 1;
10280
10281            --  We need a full overlap check if record positions non-monotonic
10282
10283            if Fbit <= Max_Bit_So_Far then
10284               Overlap_Check_Required := True;
10285            end if;
10286
10287            Max_Bit_So_Far := Lbit;
10288
10289            --  Check bit position out of range of specified size
10290
10291            if Has_Size_Clause (Rectype)
10292              and then RM_Size (Rectype) <= Lbit
10293            then
10294               Error_Msg_N
10295                 ("bit number out of range of specified size",
10296                  Last_Bit (CC));
10297
10298               --  Check for overlap with tag or parent component
10299
10300            else
10301               if Is_Tagged_Type (Rectype)
10302                 and then Fbit < System_Address_Size
10303               then
10304                  Error_Msg_NE
10305                    ("component overlaps tag field of&",
10306                     Component_Name (CC), Rectype);
10307                  Overlap_Detected := True;
10308
10309               elsif Present (Tagged_Parent)
10310                 and then Fbit <= Parent_Last_Bit
10311               then
10312                  Error_Msg_NE
10313                    ("component overlaps parent field of&",
10314                     Component_Name (CC), Rectype);
10315                  Overlap_Detected := True;
10316               end if;
10317
10318               if Hbit < Lbit then
10319                  Hbit := Lbit;
10320               end if;
10321            end if;
10322         end if;
10323
10324         Next (CC);
10325      end loop;
10326
10327      --  Now that we have processed all the component clauses, check for
10328      --  overlap. We have to leave this till last, since the components can
10329      --  appear in any arbitrary order in the representation clause.
10330
10331      --  We do not need this check if all specified ranges were monotonic,
10332      --  as recorded by Overlap_Check_Required being False at this stage.
10333
10334      --  This first section checks if there are any overlapping entries at
10335      --  all. It does this by sorting all entries and then seeing if there are
10336      --  any overlaps. If there are none, then that is decisive, but if there
10337      --  are overlaps, they may still be OK (they may result from fields in
10338      --  different variants).
10339
10340      if Overlap_Check_Required then
10341         Overlap_Check1 : declare
10342
10343            OC_Fbit : array (0 .. Ccount) of Uint;
10344            --  First-bit values for component clauses, the value is the offset
10345            --  of the first bit of the field from start of record. The zero
10346            --  entry is for use in sorting.
10347
10348            OC_Lbit : array (0 .. Ccount) of Uint;
10349            --  Last-bit values for component clauses, the value is the offset
10350            --  of the last bit of the field from start of record. The zero
10351            --  entry is for use in sorting.
10352
10353            OC_Count : Natural := 0;
10354            --  Count of entries in OC_Fbit and OC_Lbit
10355
10356            function OC_Lt (Op1, Op2 : Natural) return Boolean;
10357            --  Compare routine for Sort
10358
10359            procedure OC_Move (From : Natural; To : Natural);
10360            --  Move routine for Sort
10361
10362            package Sorting is new GNAT.Heap_Sort_G (OC_Move, OC_Lt);
10363
10364            -----------
10365            -- OC_Lt --
10366            -----------
10367
10368            function OC_Lt (Op1, Op2 : Natural) return Boolean is
10369            begin
10370               return OC_Fbit (Op1) < OC_Fbit (Op2);
10371            end OC_Lt;
10372
10373            -------------
10374            -- OC_Move --
10375            -------------
10376
10377            procedure OC_Move (From : Natural; To : Natural) is
10378            begin
10379               OC_Fbit (To) := OC_Fbit (From);
10380               OC_Lbit (To) := OC_Lbit (From);
10381            end OC_Move;
10382
10383            --  Start of processing for Overlap_Check
10384
10385         begin
10386            CC := First (Component_Clauses (N));
10387            while Present (CC) loop
10388
10389               --  Exclude component clause already marked in error
10390
10391               if not Error_Posted (CC) then
10392                  Find_Component;
10393
10394                  if Present (Comp) then
10395                     OC_Count := OC_Count + 1;
10396                     OC_Fbit (OC_Count) := Fbit;
10397                     OC_Lbit (OC_Count) := Lbit;
10398                  end if;
10399               end if;
10400
10401               Next (CC);
10402            end loop;
10403
10404            Sorting.Sort (OC_Count);
10405
10406            Overlap_Check_Required := False;
10407            for J in 1 .. OC_Count - 1 loop
10408               if OC_Lbit (J) >= OC_Fbit (J + 1) then
10409                  Overlap_Check_Required := True;
10410                  exit;
10411               end if;
10412            end loop;
10413         end Overlap_Check1;
10414      end if;
10415
10416      --  If Overlap_Check_Required is still True, then we have to do the full
10417      --  scale overlap check, since we have at least two fields that do
10418      --  overlap, and we need to know if that is OK since they are in
10419      --  different variant, or whether we have a definite problem.
10420
10421      if Overlap_Check_Required then
10422         Overlap_Check2 : declare
10423            C1_Ent, C2_Ent : Entity_Id;
10424            --  Entities of components being checked for overlap
10425
10426            Clist : Node_Id;
10427            --  Component_List node whose Component_Items are being checked
10428
10429            Citem : Node_Id;
10430            --  Component declaration for component being checked
10431
10432         begin
10433            C1_Ent := First_Entity (Base_Type (Rectype));
10434
10435            --  Loop through all components in record. For each component check
10436            --  for overlap with any of the preceding elements on the component
10437            --  list containing the component and also, if the component is in
10438            --  a variant, check against components outside the case structure.
10439            --  This latter test is repeated recursively up the variant tree.
10440
10441            Main_Component_Loop : while Present (C1_Ent) loop
10442               if not Ekind_In (C1_Ent, E_Component, E_Discriminant) then
10443                  goto Continue_Main_Component_Loop;
10444               end if;
10445
10446               --  Skip overlap check if entity has no declaration node. This
10447               --  happens with discriminants in constrained derived types.
10448               --  Possibly we are missing some checks as a result, but that
10449               --  does not seem terribly serious.
10450
10451               if No (Declaration_Node (C1_Ent)) then
10452                  goto Continue_Main_Component_Loop;
10453               end if;
10454
10455               Clist := Parent (List_Containing (Declaration_Node (C1_Ent)));
10456
10457               --  Loop through component lists that need checking. Check the
10458               --  current component list and all lists in variants above us.
10459
10460               Component_List_Loop : loop
10461
10462                  --  If derived type definition, go to full declaration
10463                  --  If at outer level, check discriminants if there are any.
10464
10465                  if Nkind (Clist) = N_Derived_Type_Definition then
10466                     Clist := Parent (Clist);
10467                  end if;
10468
10469                  --  Outer level of record definition, check discriminants
10470
10471                  if Nkind_In (Clist, N_Full_Type_Declaration,
10472                                      N_Private_Type_Declaration)
10473                  then
10474                     if Has_Discriminants (Defining_Identifier (Clist)) then
10475                        C2_Ent :=
10476                          First_Discriminant (Defining_Identifier (Clist));
10477                        while Present (C2_Ent) loop
10478                           exit when C1_Ent = C2_Ent;
10479                           Check_Component_Overlap (C1_Ent, C2_Ent);
10480                           Next_Discriminant (C2_Ent);
10481                        end loop;
10482                     end if;
10483
10484                     --  Record extension case
10485
10486                  elsif Nkind (Clist) = N_Derived_Type_Definition then
10487                     Clist := Empty;
10488
10489                     --  Otherwise check one component list
10490
10491                  else
10492                     Citem := First (Component_Items (Clist));
10493                     while Present (Citem) loop
10494                        if Nkind (Citem) = N_Component_Declaration then
10495                           C2_Ent := Defining_Identifier (Citem);
10496                           exit when C1_Ent = C2_Ent;
10497                           Check_Component_Overlap (C1_Ent, C2_Ent);
10498                        end if;
10499
10500                        Next (Citem);
10501                     end loop;
10502                  end if;
10503
10504                  --  Check for variants above us (the parent of the Clist can
10505                  --  be a variant, in which case its parent is a variant part,
10506                  --  and the parent of the variant part is a component list
10507                  --  whose components must all be checked against the current
10508                  --  component for overlap).
10509
10510                  if Nkind (Parent (Clist)) = N_Variant then
10511                     Clist := Parent (Parent (Parent (Clist)));
10512
10513                     --  Check for possible discriminant part in record, this
10514                     --  is treated essentially as another level in the
10515                     --  recursion. For this case the parent of the component
10516                     --  list is the record definition, and its parent is the
10517                     --  full type declaration containing the discriminant
10518                     --  specifications.
10519
10520                  elsif Nkind (Parent (Clist)) = N_Record_Definition then
10521                     Clist := Parent (Parent ((Clist)));
10522
10523                     --  If neither of these two cases, we are at the top of
10524                     --  the tree.
10525
10526                  else
10527                     exit Component_List_Loop;
10528                  end if;
10529               end loop Component_List_Loop;
10530
10531               <<Continue_Main_Component_Loop>>
10532               Next_Entity (C1_Ent);
10533
10534            end loop Main_Component_Loop;
10535         end Overlap_Check2;
10536      end if;
10537
10538      --  The following circuit deals with warning on record holes (gaps). We
10539      --  skip this check if overlap was detected, since it makes sense for the
10540      --  programmer to fix this illegality before worrying about warnings.
10541
10542      if not Overlap_Detected and Warn_On_Record_Holes then
10543         Record_Hole_Check : declare
10544            Decl : constant Node_Id := Declaration_Node (Base_Type (Rectype));
10545            --  Full declaration of record type
10546
10547            procedure Check_Component_List
10548              (CL   : Node_Id;
10549               Sbit : Uint;
10550               DS   : List_Id);
10551            --  Check component list CL for holes. The starting bit should be
10552            --  Sbit. which is zero for the main record component list and set
10553            --  appropriately for recursive calls for variants. DS is set to
10554            --  a list of discriminant specifications to be included in the
10555            --  consideration of components. It is No_List if none to consider.
10556
10557            --------------------------
10558            -- Check_Component_List --
10559            --------------------------
10560
10561            procedure Check_Component_List
10562              (CL   : Node_Id;
10563               Sbit : Uint;
10564               DS   : List_Id)
10565            is
10566               Compl : Integer;
10567
10568            begin
10569               Compl := Integer (List_Length (Component_Items (CL)));
10570
10571               if DS /= No_List then
10572                  Compl := Compl + Integer (List_Length (DS));
10573               end if;
10574
10575               declare
10576                  Comps : array (Natural range 0 .. Compl) of Entity_Id;
10577                  --  Gather components (zero entry is for sort routine)
10578
10579                  Ncomps : Natural := 0;
10580                  --  Number of entries stored in Comps (starting at Comps (1))
10581
10582                  Citem : Node_Id;
10583                  --  One component item or discriminant specification
10584
10585                  Nbit  : Uint;
10586                  --  Starting bit for next component
10587
10588                  CEnt  : Entity_Id;
10589                  --  Component entity
10590
10591                  Variant : Node_Id;
10592                  --  One variant
10593
10594                  function Lt (Op1, Op2 : Natural) return Boolean;
10595                  --  Compare routine for Sort
10596
10597                  procedure Move (From : Natural; To : Natural);
10598                  --  Move routine for Sort
10599
10600                  package Sorting is new GNAT.Heap_Sort_G (Move, Lt);
10601
10602                  --------
10603                  -- Lt --
10604                  --------
10605
10606                  function Lt (Op1, Op2 : Natural) return Boolean is
10607                  begin
10608                     return Component_Bit_Offset (Comps (Op1))
10609                       <
10610                       Component_Bit_Offset (Comps (Op2));
10611                  end Lt;
10612
10613                  ----------
10614                  -- Move --
10615                  ----------
10616
10617                  procedure Move (From : Natural; To : Natural) is
10618                  begin
10619                     Comps (To) := Comps (From);
10620                  end Move;
10621
10622               begin
10623                  --  Gather discriminants into Comp
10624
10625                  if DS /= No_List then
10626                     Citem := First (DS);
10627                     while Present (Citem) loop
10628                        if Nkind (Citem) = N_Discriminant_Specification then
10629                           declare
10630                              Ent : constant Entity_Id :=
10631                                      Defining_Identifier (Citem);
10632                           begin
10633                              if Ekind (Ent) = E_Discriminant then
10634                                 Ncomps := Ncomps + 1;
10635                                 Comps (Ncomps) := Ent;
10636                              end if;
10637                           end;
10638                        end if;
10639
10640                        Next (Citem);
10641                     end loop;
10642                  end if;
10643
10644                  --  Gather component entities into Comp
10645
10646                  Citem := First (Component_Items (CL));
10647                  while Present (Citem) loop
10648                     if Nkind (Citem) = N_Component_Declaration then
10649                        Ncomps := Ncomps + 1;
10650                        Comps (Ncomps) := Defining_Identifier (Citem);
10651                     end if;
10652
10653                     Next (Citem);
10654                  end loop;
10655
10656                  --  Now sort the component entities based on the first bit.
10657                  --  Note we already know there are no overlapping components.
10658
10659                  Sorting.Sort (Ncomps);
10660
10661                  --  Loop through entries checking for holes
10662
10663                  Nbit := Sbit;
10664                  for J in 1 .. Ncomps loop
10665                     CEnt := Comps (J);
10666
10667                     declare
10668                        CBO : constant Uint := Component_Bit_Offset (CEnt);
10669
10670                     begin
10671                        --  Skip components with unknown offsets
10672
10673                        if CBO /= No_Uint and then CBO >= 0 then
10674                           Error_Msg_Uint_1 := CBO - Nbit;
10675
10676                           if Error_Msg_Uint_1 > 0 then
10677                              Error_Msg_NE
10678                                ("?H?^-bit gap before component&",
10679                                 Component_Name (Component_Clause (CEnt)),
10680                                 CEnt);
10681                           end if;
10682
10683                           Nbit := CBO + Esize (CEnt);
10684                        end if;
10685                     end;
10686                  end loop;
10687
10688                  --  Process variant parts recursively if present
10689
10690                  if Present (Variant_Part (CL)) then
10691                     Variant := First (Variants (Variant_Part (CL)));
10692                     while Present (Variant) loop
10693                        Check_Component_List
10694                          (Component_List (Variant), Nbit, No_List);
10695                        Next (Variant);
10696                     end loop;
10697                  end if;
10698               end;
10699            end Check_Component_List;
10700
10701         --  Start of processing for Record_Hole_Check
10702
10703         begin
10704            declare
10705               Sbit : Uint;
10706
10707            begin
10708               if Is_Tagged_Type (Rectype) then
10709                  Sbit := UI_From_Int (System_Address_Size);
10710               else
10711                  Sbit := Uint_0;
10712               end if;
10713
10714               if Nkind (Decl) = N_Full_Type_Declaration
10715                 and then Nkind (Type_Definition (Decl)) = N_Record_Definition
10716               then
10717                  Check_Component_List
10718                    (Component_List (Type_Definition (Decl)),
10719                     Sbit,
10720                     Discriminant_Specifications (Decl));
10721               end if;
10722            end;
10723         end Record_Hole_Check;
10724      end if;
10725
10726      --  For records that have component clauses for all components, and whose
10727      --  size is less than or equal to 32, we need to know the size in the
10728      --  front end to activate possible packed array processing where the
10729      --  component type is a record.
10730
10731      --  At this stage Hbit + 1 represents the first unused bit from all the
10732      --  component clauses processed, so if the component clauses are
10733      --  complete, then this is the length of the record.
10734
10735      --  For records longer than System.Storage_Unit, and for those where not
10736      --  all components have component clauses, the back end determines the
10737      --  length (it may for example be appropriate to round up the size
10738      --  to some convenient boundary, based on alignment considerations, etc).
10739
10740      if Unknown_RM_Size (Rectype) and then Hbit + 1 <= 32 then
10741
10742         --  Nothing to do if at least one component has no component clause
10743
10744         Comp := First_Component_Or_Discriminant (Rectype);
10745         while Present (Comp) loop
10746            exit when No (Component_Clause (Comp));
10747            Next_Component_Or_Discriminant (Comp);
10748         end loop;
10749
10750         --  If we fall out of loop, all components have component clauses
10751         --  and so we can set the size to the maximum value.
10752
10753         if No (Comp) then
10754            Set_RM_Size (Rectype, Hbit + 1);
10755         end if;
10756      end if;
10757   end Check_Record_Representation_Clause;
10758
10759   ----------------
10760   -- Check_Size --
10761   ----------------
10762
10763   procedure Check_Size
10764     (N      : Node_Id;
10765      T      : Entity_Id;
10766      Siz    : Uint;
10767      Biased : out Boolean)
10768   is
10769      procedure Size_Too_Small_Error (Min_Siz : Uint);
10770      --  Emit an error concerning illegal size Siz. Min_Siz denotes the
10771      --  minimum size.
10772
10773      --------------------------
10774      -- Size_Too_Small_Error --
10775      --------------------------
10776
10777      procedure Size_Too_Small_Error (Min_Siz : Uint) is
10778      begin
10779         --  This error is suppressed in ASIS mode to allow for different ASIS
10780         --  back ends or ASIS-based tools to query the illegal clause.
10781
10782         if not ASIS_Mode then
10783            Error_Msg_Uint_1 := Min_Siz;
10784            Error_Msg_NE ("size for& too small, minimum allowed is ^", N, T);
10785         end if;
10786      end Size_Too_Small_Error;
10787
10788      --  Local variables
10789
10790      UT : constant Entity_Id := Underlying_Type (T);
10791      M  : Uint;
10792
10793   --  Start of processing for Check_Size
10794
10795   begin
10796      Biased := False;
10797
10798      --  Reject patently improper size values
10799
10800      if Is_Elementary_Type (T)
10801        and then Siz > UI_From_Int (Int'Last)
10802      then
10803         Error_Msg_N ("Size value too large for elementary type", N);
10804
10805         if Nkind (Original_Node (N)) = N_Op_Expon then
10806            Error_Msg_N
10807              ("\maybe '* was meant, rather than '*'*", Original_Node (N));
10808         end if;
10809      end if;
10810
10811      --  Dismiss generic types
10812
10813      if Is_Generic_Type (T)
10814           or else
10815         Is_Generic_Type (UT)
10816           or else
10817         Is_Generic_Type (Root_Type (UT))
10818      then
10819         return;
10820
10821      --  Guard against previous errors
10822
10823      elsif No (UT) or else UT = Any_Type then
10824         Check_Error_Detected;
10825         return;
10826
10827      --  Check case of bit packed array
10828
10829      elsif Is_Array_Type (UT)
10830        and then Known_Static_Component_Size (UT)
10831        and then Is_Bit_Packed_Array (UT)
10832      then
10833         declare
10834            Asiz : Uint;
10835            Indx : Node_Id;
10836            Ityp : Entity_Id;
10837
10838         begin
10839            Asiz := Component_Size (UT);
10840            Indx := First_Index (UT);
10841            loop
10842               Ityp := Etype (Indx);
10843
10844               --  If non-static bound, then we are not in the business of
10845               --  trying to check the length, and indeed an error will be
10846               --  issued elsewhere, since sizes of non-static array types
10847               --  cannot be set implicitly or explicitly.
10848
10849               if not Is_OK_Static_Subtype (Ityp) then
10850                  return;
10851               end if;
10852
10853               --  Otherwise accumulate next dimension
10854
10855               Asiz := Asiz * (Expr_Value (Type_High_Bound (Ityp)) -
10856                               Expr_Value (Type_Low_Bound  (Ityp)) +
10857                               Uint_1);
10858
10859               Next_Index (Indx);
10860               exit when No (Indx);
10861            end loop;
10862
10863            if Asiz <= Siz then
10864               return;
10865
10866            else
10867               Size_Too_Small_Error (Asiz);
10868               Set_Esize   (T, Asiz);
10869               Set_RM_Size (T, Asiz);
10870            end if;
10871         end;
10872
10873      --  All other composite types are ignored
10874
10875      elsif Is_Composite_Type (UT) then
10876         return;
10877
10878      --  For fixed-point types, don't check minimum if type is not frozen,
10879      --  since we don't know all the characteristics of the type that can
10880      --  affect the size (e.g. a specified small) till freeze time.
10881
10882      elsif Is_Fixed_Point_Type (UT) and then not Is_Frozen (UT) then
10883         null;
10884
10885      --  Cases for which a minimum check is required
10886
10887      else
10888         --  Ignore if specified size is correct for the type
10889
10890         if Known_Esize (UT) and then Siz = Esize (UT) then
10891            return;
10892         end if;
10893
10894         --  Otherwise get minimum size
10895
10896         M := UI_From_Int (Minimum_Size (UT));
10897
10898         if Siz < M then
10899
10900            --  Size is less than minimum size, but one possibility remains
10901            --  that we can manage with the new size if we bias the type.
10902
10903            M := UI_From_Int (Minimum_Size (UT, Biased => True));
10904
10905            if Siz < M then
10906               Size_Too_Small_Error (M);
10907               Set_Esize   (T, M);
10908               Set_RM_Size (T, M);
10909            else
10910               Biased := True;
10911            end if;
10912         end if;
10913      end if;
10914   end Check_Size;
10915
10916   --------------------------
10917   -- Freeze_Entity_Checks --
10918   --------------------------
10919
10920   procedure Freeze_Entity_Checks (N : Node_Id) is
10921      procedure Hide_Non_Overridden_Subprograms (Typ : Entity_Id);
10922      --  Inspect the primitive operations of type Typ and hide all pairs of
10923      --  implicitly declared non-overridden non-fully conformant homographs
10924      --  (Ada RM 8.3 12.3/2).
10925
10926      -------------------------------------
10927      -- Hide_Non_Overridden_Subprograms --
10928      -------------------------------------
10929
10930      procedure Hide_Non_Overridden_Subprograms (Typ : Entity_Id) is
10931         procedure Hide_Matching_Homographs
10932           (Subp_Id    : Entity_Id;
10933            Start_Elmt : Elmt_Id);
10934         --  Inspect a list of primitive operations starting with Start_Elmt
10935         --  and find matching implicitly declared non-overridden non-fully
10936         --  conformant homographs of Subp_Id. If found, all matches along
10937         --  with Subp_Id are hidden from all visibility.
10938
10939         function Is_Non_Overridden_Or_Null_Procedure
10940           (Subp_Id : Entity_Id) return Boolean;
10941         --  Determine whether subprogram Subp_Id is implicitly declared non-
10942         --  overridden subprogram or an implicitly declared null procedure.
10943
10944         ------------------------------
10945         -- Hide_Matching_Homographs --
10946         ------------------------------
10947
10948         procedure Hide_Matching_Homographs
10949           (Subp_Id    : Entity_Id;
10950            Start_Elmt : Elmt_Id)
10951         is
10952            Prim      : Entity_Id;
10953            Prim_Elmt : Elmt_Id;
10954
10955         begin
10956            Prim_Elmt := Start_Elmt;
10957            while Present (Prim_Elmt) loop
10958               Prim := Node (Prim_Elmt);
10959
10960               --  The current primitive is implicitly declared non-overridden
10961               --  non-fully conformant homograph of Subp_Id. Both subprograms
10962               --  must be hidden from visibility.
10963
10964               if Chars (Prim) = Chars (Subp_Id)
10965                 and then Is_Non_Overridden_Or_Null_Procedure (Prim)
10966                 and then not Fully_Conformant (Prim, Subp_Id)
10967               then
10968                  Set_Is_Hidden_Non_Overridden_Subpgm (Prim);
10969                  Set_Is_Immediately_Visible          (Prim, False);
10970                  Set_Is_Potentially_Use_Visible      (Prim, False);
10971
10972                  Set_Is_Hidden_Non_Overridden_Subpgm (Subp_Id);
10973                  Set_Is_Immediately_Visible          (Subp_Id, False);
10974                  Set_Is_Potentially_Use_Visible      (Subp_Id, False);
10975               end if;
10976
10977               Next_Elmt (Prim_Elmt);
10978            end loop;
10979         end Hide_Matching_Homographs;
10980
10981         -----------------------------------------
10982         -- Is_Non_Overridden_Or_Null_Procedure --
10983         -----------------------------------------
10984
10985         function Is_Non_Overridden_Or_Null_Procedure
10986           (Subp_Id : Entity_Id) return Boolean
10987         is
10988            Alias_Id : Entity_Id;
10989
10990         begin
10991            --  The subprogram is inherited (implicitly declared), it does not
10992            --  override and does not cover a primitive of an interface.
10993
10994            if Ekind_In (Subp_Id, E_Function, E_Procedure)
10995              and then Present (Alias (Subp_Id))
10996              and then No (Interface_Alias (Subp_Id))
10997              and then No (Overridden_Operation (Subp_Id))
10998            then
10999               Alias_Id := Alias (Subp_Id);
11000
11001               if Requires_Overriding (Alias_Id) then
11002                  return True;
11003
11004               elsif Nkind (Parent (Alias_Id)) = N_Procedure_Specification
11005                 and then Null_Present (Parent (Alias_Id))
11006               then
11007                  return True;
11008               end if;
11009            end if;
11010
11011            return False;
11012         end Is_Non_Overridden_Or_Null_Procedure;
11013
11014         --  Local variables
11015
11016         Prim_Ops  : constant Elist_Id := Direct_Primitive_Operations (Typ);
11017         Prim      : Entity_Id;
11018         Prim_Elmt : Elmt_Id;
11019
11020      --  Start of processing for Hide_Non_Overridden_Subprograms
11021
11022      begin
11023         --  Inspect the list of primitives looking for non-overridden
11024         --  subprograms.
11025
11026         if Present (Prim_Ops) then
11027            Prim_Elmt := First_Elmt (Prim_Ops);
11028            while Present (Prim_Elmt) loop
11029               Prim := Node (Prim_Elmt);
11030               Next_Elmt (Prim_Elmt);
11031
11032               if Is_Non_Overridden_Or_Null_Procedure (Prim) then
11033                  Hide_Matching_Homographs
11034                    (Subp_Id    => Prim,
11035                     Start_Elmt => Prim_Elmt);
11036               end if;
11037            end loop;
11038         end if;
11039      end Hide_Non_Overridden_Subprograms;
11040
11041      --  Local variables
11042
11043      E : constant Entity_Id := Entity (N);
11044
11045      Nongeneric_Case : constant Boolean := Nkind (N) = N_Freeze_Entity;
11046      --  True in nongeneric case. Some of the processing here is skipped
11047      --  for the generic case since it is not needed. Basically in the
11048      --  generic case, we only need to do stuff that might generate error
11049      --  messages or warnings.
11050
11051   --  Start of processing for Freeze_Entity_Checks
11052
11053   begin
11054      --  Remember that we are processing a freezing entity. Required to
11055      --  ensure correct decoration of internal entities associated with
11056      --  interfaces (see New_Overloaded_Entity).
11057
11058      Inside_Freezing_Actions := Inside_Freezing_Actions + 1;
11059
11060      --  For tagged types covering interfaces add internal entities that link
11061      --  the primitives of the interfaces with the primitives that cover them.
11062      --  Note: These entities were originally generated only when generating
11063      --  code because their main purpose was to provide support to initialize
11064      --  the secondary dispatch tables. They are now generated also when
11065      --  compiling with no code generation to provide ASIS the relationship
11066      --  between interface primitives and tagged type primitives. They are
11067      --  also used to locate primitives covering interfaces when processing
11068      --  generics (see Derive_Subprograms).
11069
11070      --  This is not needed in the generic case
11071
11072      if Ada_Version >= Ada_2005
11073        and then Nongeneric_Case
11074        and then Ekind (E) = E_Record_Type
11075        and then Is_Tagged_Type (E)
11076        and then not Is_Interface (E)
11077        and then Has_Interfaces (E)
11078      then
11079         --  This would be a good common place to call the routine that checks
11080         --  overriding of interface primitives (and thus factorize calls to
11081         --  Check_Abstract_Overriding located at different contexts in the
11082         --  compiler). However, this is not possible because it causes
11083         --  spurious errors in case of late overriding.
11084
11085         Add_Internal_Interface_Entities (E);
11086      end if;
11087
11088      --  After all forms of overriding have been resolved, a tagged type may
11089      --  be left with a set of implicitly declared and possibly erroneous
11090      --  abstract subprograms, null procedures and subprograms that require
11091      --  overriding. If this set contains fully conformant homographs, then
11092      --  one is chosen arbitrarily (already done during resolution), otherwise
11093      --  all remaining non-fully conformant homographs are hidden from
11094      --  visibility (Ada RM 8.3 12.3/2).
11095
11096      if Is_Tagged_Type (E) then
11097         Hide_Non_Overridden_Subprograms (E);
11098      end if;
11099
11100      --  Check CPP types
11101
11102      if Ekind (E) = E_Record_Type
11103        and then Is_CPP_Class (E)
11104        and then Is_Tagged_Type (E)
11105        and then Tagged_Type_Expansion
11106      then
11107         if CPP_Num_Prims (E) = 0 then
11108
11109            --  If the CPP type has user defined components then it must import
11110            --  primitives from C++. This is required because if the C++ class
11111            --  has no primitives then the C++ compiler does not added the _tag
11112            --  component to the type.
11113
11114            if First_Entity (E) /= Last_Entity (E) then
11115               Error_Msg_N
11116                 ("'C'P'P type must import at least one primitive from C++??",
11117                  E);
11118            end if;
11119         end if;
11120
11121         --  Check that all its primitives are abstract or imported from C++.
11122         --  Check also availability of the C++ constructor.
11123
11124         declare
11125            Has_Constructors : constant Boolean := Has_CPP_Constructors (E);
11126            Elmt             : Elmt_Id;
11127            Error_Reported   : Boolean := False;
11128            Prim             : Node_Id;
11129
11130         begin
11131            Elmt := First_Elmt (Primitive_Operations (E));
11132            while Present (Elmt) loop
11133               Prim := Node (Elmt);
11134
11135               if Comes_From_Source (Prim) then
11136                  if Is_Abstract_Subprogram (Prim) then
11137                     null;
11138
11139                  elsif not Is_Imported (Prim)
11140                    or else Convention (Prim) /= Convention_CPP
11141                  then
11142                     Error_Msg_N
11143                       ("primitives of 'C'P'P types must be imported from C++ "
11144                        & "or abstract??", Prim);
11145
11146                  elsif not Has_Constructors
11147                     and then not Error_Reported
11148                  then
11149                     Error_Msg_Name_1 := Chars (E);
11150                     Error_Msg_N
11151                       ("??'C'P'P constructor required for type %", Prim);
11152                     Error_Reported := True;
11153                  end if;
11154               end if;
11155
11156               Next_Elmt (Elmt);
11157            end loop;
11158         end;
11159      end if;
11160
11161      --  Check Ada derivation of CPP type
11162
11163      if Expander_Active              -- why? losing errors in -gnatc mode???
11164        and then Present (Etype (E))  -- defend against errors
11165        and then Tagged_Type_Expansion
11166        and then Ekind (E) = E_Record_Type
11167        and then Etype (E) /= E
11168        and then Is_CPP_Class (Etype (E))
11169        and then CPP_Num_Prims (Etype (E)) > 0
11170        and then not Is_CPP_Class (E)
11171        and then not Has_CPP_Constructors (Etype (E))
11172      then
11173         --  If the parent has C++ primitives but it has no constructor then
11174         --  check that all the primitives are overridden in this derivation;
11175         --  otherwise the constructor of the parent is needed to build the
11176         --  dispatch table.
11177
11178         declare
11179            Elmt : Elmt_Id;
11180            Prim : Node_Id;
11181
11182         begin
11183            Elmt := First_Elmt (Primitive_Operations (E));
11184            while Present (Elmt) loop
11185               Prim := Node (Elmt);
11186
11187               if not Is_Abstract_Subprogram (Prim)
11188                 and then No (Interface_Alias (Prim))
11189                 and then Find_Dispatching_Type (Ultimate_Alias (Prim)) /= E
11190               then
11191                  Error_Msg_Name_1 := Chars (Etype (E));
11192                  Error_Msg_N
11193                    ("'C'P'P constructor required for parent type %", E);
11194                  exit;
11195               end if;
11196
11197               Next_Elmt (Elmt);
11198            end loop;
11199         end;
11200      end if;
11201
11202      Inside_Freezing_Actions := Inside_Freezing_Actions - 1;
11203
11204      --  If we have a type with predicates, build predicate function. This is
11205      --  not needed in the generic case, nor within TSS subprograms and other
11206      --  predefined primitives. For a derived type, ensure that the parent
11207      --  type is already frozen so that its predicate function has been
11208      --  constructed already. This is necessary if the parent is declared
11209      --  in a nested package and its own freeze point has not been reached.
11210
11211      if Is_Type (E)
11212        and then Nongeneric_Case
11213        and then not Within_Internal_Subprogram
11214        and then Has_Predicates (E)
11215      then
11216         declare
11217            Atyp : constant Entity_Id := Nearest_Ancestor (E);
11218         begin
11219            if Present (Atyp)
11220              and then Has_Predicates (Atyp)
11221              and then not Is_Frozen (Atyp)
11222            then
11223               Freeze_Before (N, Atyp);
11224            end if;
11225         end;
11226
11227         Build_Predicate_Functions (E, N);
11228      end if;
11229
11230      --  If type has delayed aspects, this is where we do the preanalysis at
11231      --  the freeze point, as part of the consistent visibility check. Note
11232      --  that this must be done after calling Build_Predicate_Functions or
11233      --  Build_Invariant_Procedure since these subprograms fix occurrences of
11234      --  the subtype name in the saved expression so that they will not cause
11235      --  trouble in the preanalysis.
11236
11237      --  This is also not needed in the generic case
11238
11239      if Nongeneric_Case
11240        and then Has_Delayed_Aspects (E)
11241        and then Scope (E) = Current_Scope
11242      then
11243         declare
11244            A_Id  : Aspect_Id;
11245            Ritem : Node_Id;
11246
11247         begin
11248            --  Look for aspect specification entries for this entity
11249
11250            Ritem := First_Rep_Item (E);
11251            while Present (Ritem) loop
11252               if Nkind (Ritem) = N_Aspect_Specification
11253                 and then Entity (Ritem) = E
11254                 and then Is_Delayed_Aspect (Ritem)
11255               then
11256                  A_Id := Get_Aspect_Id (Ritem);
11257
11258                  if A_Id = Aspect_Dynamic_Predicate
11259                    or else A_Id = Aspect_Predicate
11260                    or else A_Id = Aspect_Priority
11261                  then
11262                    --  Retrieve the visibility to components and discriminants
11263                    --  in order to properly analyze the aspects.
11264
11265                     Push_Type (E);
11266                     Check_Aspect_At_Freeze_Point (Ritem);
11267                     Pop_Type (E);
11268
11269                  else
11270                     Check_Aspect_At_Freeze_Point (Ritem);
11271                  end if;
11272               end if;
11273
11274               Next_Rep_Item (Ritem);
11275            end loop;
11276         end;
11277
11278      end if;
11279
11280      --  For a record type, deal with variant parts. This has to be delayed to
11281      --  this point, because of the issue of statically predicated subtypes,
11282      --  which we have to ensure are frozen before checking choices, since we
11283      --  need to have the static choice list set.
11284
11285      if Is_Record_Type (E) then
11286         Check_Variant_Part : declare
11287            D  : constant Node_Id := Declaration_Node (E);
11288            T  : Node_Id;
11289            C  : Node_Id;
11290            VP : Node_Id;
11291
11292            Others_Present : Boolean;
11293            pragma Warnings (Off, Others_Present);
11294            --  Indicates others present, not used in this case
11295
11296            procedure Non_Static_Choice_Error (Choice : Node_Id);
11297            --  Error routine invoked by the generic instantiation below when
11298            --  the variant part has a non static choice.
11299
11300            procedure Process_Declarations (Variant : Node_Id);
11301            --  Processes declarations associated with a variant. We analyzed
11302            --  the declarations earlier (in Sem_Ch3.Analyze_Variant_Part),
11303            --  but we still need the recursive call to Check_Choices for any
11304            --  nested variant to get its choices properly processed. This is
11305            --  also where we expand out the choices if expansion is active.
11306
11307            package Variant_Choices_Processing is new
11308              Generic_Check_Choices
11309                (Process_Empty_Choice      => No_OP,
11310                 Process_Non_Static_Choice => Non_Static_Choice_Error,
11311                 Process_Associated_Node   => Process_Declarations);
11312            use Variant_Choices_Processing;
11313
11314            -----------------------------
11315            -- Non_Static_Choice_Error --
11316            -----------------------------
11317
11318            procedure Non_Static_Choice_Error (Choice : Node_Id) is
11319            begin
11320               Flag_Non_Static_Expr
11321                 ("choice given in variant part is not static!", Choice);
11322            end Non_Static_Choice_Error;
11323
11324            --------------------------
11325            -- Process_Declarations --
11326            --------------------------
11327
11328            procedure Process_Declarations (Variant : Node_Id) is
11329               CL : constant Node_Id := Component_List (Variant);
11330               VP : Node_Id;
11331
11332            begin
11333               --  Check for static predicate present in this variant
11334
11335               if Has_SP_Choice (Variant) then
11336
11337                  --  Here we expand. You might expect to find this call in
11338                  --  Expand_N_Variant_Part, but that is called when we first
11339                  --  see the variant part, and we cannot do this expansion
11340                  --  earlier than the freeze point, since for statically
11341                  --  predicated subtypes, the predicate is not known till
11342                  --  the freeze point.
11343
11344                  --  Furthermore, we do this expansion even if the expander
11345                  --  is not active, because other semantic processing, e.g.
11346                  --  for aggregates, requires the expanded list of choices.
11347
11348                  --  If the expander is not active, then we can't just clobber
11349                  --  the list since it would invalidate the ASIS -gnatct tree.
11350                  --  So we have to rewrite the variant part with a Rewrite
11351                  --  call that replaces it with a copy and clobber the copy.
11352
11353                  if not Expander_Active then
11354                     declare
11355                        NewV : constant Node_Id := New_Copy (Variant);
11356                     begin
11357                        Set_Discrete_Choices
11358                          (NewV, New_Copy_List (Discrete_Choices (Variant)));
11359                        Rewrite (Variant, NewV);
11360                     end;
11361                  end if;
11362
11363                  Expand_Static_Predicates_In_Choices (Variant);
11364               end if;
11365
11366               --  We don't need to worry about the declarations in the variant
11367               --  (since they were analyzed by Analyze_Choices when we first
11368               --  encountered the variant), but we do need to take care of
11369               --  expansion of any nested variants.
11370
11371               if not Null_Present (CL) then
11372                  VP := Variant_Part (CL);
11373
11374                  if Present (VP) then
11375                     Check_Choices
11376                       (VP, Variants (VP), Etype (Name (VP)), Others_Present);
11377                  end if;
11378               end if;
11379            end Process_Declarations;
11380
11381         --  Start of processing for Check_Variant_Part
11382
11383         begin
11384            --  Find component list
11385
11386            C := Empty;
11387
11388            if Nkind (D) = N_Full_Type_Declaration then
11389               T := Type_Definition (D);
11390
11391               if Nkind (T) = N_Record_Definition then
11392                  C := Component_List (T);
11393
11394               elsif Nkind (T) = N_Derived_Type_Definition
11395                 and then Present (Record_Extension_Part (T))
11396               then
11397                  C := Component_List (Record_Extension_Part (T));
11398               end if;
11399            end if;
11400
11401            --  Case of variant part present
11402
11403            if Present (C) and then Present (Variant_Part (C)) then
11404               VP := Variant_Part (C);
11405
11406               --  Check choices
11407
11408               Check_Choices
11409                 (VP, Variants (VP), Etype (Name (VP)), Others_Present);
11410
11411               --  If the last variant does not contain the Others choice,
11412               --  replace it with an N_Others_Choice node since Gigi always
11413               --  wants an Others. Note that we do not bother to call Analyze
11414               --  on the modified variant part, since its only effect would be
11415               --  to compute the Others_Discrete_Choices node laboriously, and
11416               --  of course we already know the list of choices corresponding
11417               --  to the others choice (it's the list we're replacing).
11418
11419               --  We only want to do this if the expander is active, since
11420               --  we do not want to clobber the ASIS tree.
11421
11422               if Expander_Active then
11423                  declare
11424                     Last_Var : constant Node_Id :=
11425                                     Last_Non_Pragma (Variants (VP));
11426
11427                     Others_Node : Node_Id;
11428
11429                  begin
11430                     if Nkind (First (Discrete_Choices (Last_Var))) /=
11431                                                            N_Others_Choice
11432                     then
11433                        Others_Node := Make_Others_Choice (Sloc (Last_Var));
11434                        Set_Others_Discrete_Choices
11435                          (Others_Node, Discrete_Choices (Last_Var));
11436                        Set_Discrete_Choices
11437                          (Last_Var, New_List (Others_Node));
11438                     end if;
11439                  end;
11440               end if;
11441            end if;
11442         end Check_Variant_Part;
11443      end if;
11444   end Freeze_Entity_Checks;
11445
11446   -------------------------
11447   -- Get_Alignment_Value --
11448   -------------------------
11449
11450   function Get_Alignment_Value (Expr : Node_Id) return Uint is
11451      Align : constant Uint := Static_Integer (Expr);
11452
11453   begin
11454      if Align = No_Uint then
11455         return No_Uint;
11456
11457      elsif Align <= 0 then
11458
11459         --  This error is suppressed in ASIS mode to allow for different ASIS
11460         --  back ends or ASIS-based tools to query the illegal clause.
11461
11462         if not ASIS_Mode then
11463            Error_Msg_N ("alignment value must be positive", Expr);
11464         end if;
11465
11466         return No_Uint;
11467
11468      else
11469         for J in Int range 0 .. 64 loop
11470            declare
11471               M : constant Uint := Uint_2 ** J;
11472
11473            begin
11474               exit when M = Align;
11475
11476               if M > Align then
11477
11478                  --  This error is suppressed in ASIS mode to allow for
11479                  --  different ASIS back ends or ASIS-based tools to query the
11480                  --  illegal clause.
11481
11482                  if not ASIS_Mode then
11483                     Error_Msg_N ("alignment value must be power of 2", Expr);
11484                  end if;
11485
11486                  return No_Uint;
11487               end if;
11488            end;
11489         end loop;
11490
11491         return Align;
11492      end if;
11493   end Get_Alignment_Value;
11494
11495   -------------------------------------
11496   -- Inherit_Aspects_At_Freeze_Point --
11497   -------------------------------------
11498
11499   procedure Inherit_Aspects_At_Freeze_Point (Typ : Entity_Id) is
11500      function Is_Pragma_Or_Corr_Pragma_Present_In_Rep_Item
11501        (Rep_Item : Node_Id) return Boolean;
11502      --  This routine checks if Rep_Item is either a pragma or an aspect
11503      --  specification node whose correponding pragma (if any) is present in
11504      --  the Rep Item chain of the entity it has been specified to.
11505
11506      function Rep_Item_Entity (Rep_Item : Node_Id) return Entity_Id;
11507      --  Return the entity for which Rep_Item is specified
11508
11509      --------------------------------------------------
11510      -- Is_Pragma_Or_Corr_Pragma_Present_In_Rep_Item --
11511      --------------------------------------------------
11512
11513      function Is_Pragma_Or_Corr_Pragma_Present_In_Rep_Item
11514        (Rep_Item : Node_Id) return Boolean
11515      is
11516      begin
11517         return
11518           Nkind (Rep_Item) = N_Pragma
11519             or else Present_In_Rep_Item
11520                       (Entity (Rep_Item), Aspect_Rep_Item (Rep_Item));
11521      end Is_Pragma_Or_Corr_Pragma_Present_In_Rep_Item;
11522
11523      ---------------------
11524      -- Rep_Item_Entity --
11525      ---------------------
11526
11527      function Rep_Item_Entity (Rep_Item : Node_Id) return Entity_Id is
11528      begin
11529         if Nkind (Rep_Item) = N_Aspect_Specification then
11530            return Entity (Rep_Item);
11531
11532         else
11533            pragma Assert (Nkind_In (Rep_Item,
11534                                     N_Attribute_Definition_Clause,
11535                                     N_Pragma));
11536            return Entity (Name (Rep_Item));
11537         end if;
11538      end Rep_Item_Entity;
11539
11540   --  Start of processing for Inherit_Aspects_At_Freeze_Point
11541
11542   begin
11543      --  A representation item is either subtype-specific (Size and Alignment
11544      --  clauses) or type-related (all others).  Subtype-specific aspects may
11545      --  differ for different subtypes of the same type (RM 13.1.8).
11546
11547      --  A derived type inherits each type-related representation aspect of
11548      --  its parent type that was directly specified before the declaration of
11549      --  the derived type (RM 13.1.15).
11550
11551      --  A derived subtype inherits each subtype-specific representation
11552      --  aspect of its parent subtype that was directly specified before the
11553      --  declaration of the derived type (RM 13.1.15).
11554
11555      --  The general processing involves inheriting a representation aspect
11556      --  from a parent type whenever the first rep item (aspect specification,
11557      --  attribute definition clause, pragma) corresponding to the given
11558      --  representation aspect in the rep item chain of Typ, if any, isn't
11559      --  directly specified to Typ but to one of its parents.
11560
11561      --  ??? Note that, for now, just a limited number of representation
11562      --  aspects have been inherited here so far. Many of them are
11563      --  still inherited in Sem_Ch3. This will be fixed soon. Here is
11564      --  a non- exhaustive list of aspects that likely also need to
11565      --  be moved to this routine: Alignment, Component_Alignment,
11566      --  Component_Size, Machine_Radix, Object_Size, Pack, Predicates,
11567      --  Preelaborable_Initialization, RM_Size and Small.
11568
11569      --  In addition, Convention must be propagated from base type to subtype,
11570      --  because the subtype may have been declared on an incomplete view.
11571
11572      if Nkind (Parent (Typ)) = N_Private_Extension_Declaration then
11573         return;
11574      end if;
11575
11576      --  Ada_05/Ada_2005
11577
11578      if not Has_Rep_Item (Typ, Name_Ada_05, Name_Ada_2005, False)
11579        and then Has_Rep_Item (Typ, Name_Ada_05, Name_Ada_2005)
11580        and then Is_Pragma_Or_Corr_Pragma_Present_In_Rep_Item
11581                   (Get_Rep_Item (Typ, Name_Ada_05, Name_Ada_2005))
11582      then
11583         Set_Is_Ada_2005_Only (Typ);
11584      end if;
11585
11586      --  Ada_12/Ada_2012
11587
11588      if not Has_Rep_Item (Typ, Name_Ada_12, Name_Ada_2012, False)
11589        and then Has_Rep_Item (Typ, Name_Ada_12, Name_Ada_2012)
11590        and then Is_Pragma_Or_Corr_Pragma_Present_In_Rep_Item
11591                   (Get_Rep_Item (Typ, Name_Ada_12, Name_Ada_2012))
11592      then
11593         Set_Is_Ada_2012_Only (Typ);
11594      end if;
11595
11596      --  Atomic/Shared
11597
11598      if not Has_Rep_Item (Typ, Name_Atomic, Name_Shared, False)
11599        and then Has_Rep_Pragma (Typ, Name_Atomic, Name_Shared)
11600        and then Is_Pragma_Or_Corr_Pragma_Present_In_Rep_Item
11601                   (Get_Rep_Item (Typ, Name_Atomic, Name_Shared))
11602      then
11603         Set_Is_Atomic (Typ);
11604         Set_Is_Volatile (Typ);
11605         Set_Treat_As_Volatile (Typ);
11606      end if;
11607
11608      --  Convention
11609
11610      if Is_Record_Type (Typ)
11611        and then Typ /= Base_Type (Typ) and then Is_Frozen (Base_Type (Typ))
11612      then
11613         Set_Convention (Typ, Convention (Base_Type (Typ)));
11614      end if;
11615
11616      --  Default_Component_Value
11617
11618      --  Verify that there is no rep_item declared for the type, and there
11619      --  is one coming from an ancestor.
11620
11621      if Is_Array_Type (Typ)
11622        and then Is_Base_Type (Typ)
11623        and then not Has_Rep_Item (Typ, Name_Default_Component_Value, False)
11624        and then Has_Rep_Item (Typ, Name_Default_Component_Value)
11625      then
11626         Set_Default_Aspect_Component_Value (Typ,
11627           Default_Aspect_Component_Value
11628             (Entity (Get_Rep_Item (Typ, Name_Default_Component_Value))));
11629      end if;
11630
11631      --  Default_Value
11632
11633      if Is_Scalar_Type (Typ)
11634        and then Is_Base_Type (Typ)
11635        and then not Has_Rep_Item (Typ, Name_Default_Value, False)
11636        and then Has_Rep_Item (Typ, Name_Default_Value)
11637      then
11638         Set_Has_Default_Aspect (Typ);
11639         Set_Default_Aspect_Value (Typ,
11640           Default_Aspect_Value
11641             (Entity (Get_Rep_Item (Typ, Name_Default_Value))));
11642      end if;
11643
11644      --  Discard_Names
11645
11646      if not Has_Rep_Item (Typ, Name_Discard_Names, False)
11647        and then Has_Rep_Item (Typ, Name_Discard_Names)
11648        and then Is_Pragma_Or_Corr_Pragma_Present_In_Rep_Item
11649                   (Get_Rep_Item (Typ, Name_Discard_Names))
11650      then
11651         Set_Discard_Names (Typ);
11652      end if;
11653
11654      --  Volatile
11655
11656      if not Has_Rep_Item (Typ, Name_Volatile, False)
11657        and then Has_Rep_Item (Typ, Name_Volatile)
11658        and then Is_Pragma_Or_Corr_Pragma_Present_In_Rep_Item
11659                   (Get_Rep_Item (Typ, Name_Volatile))
11660      then
11661         Set_Is_Volatile (Typ);
11662         Set_Treat_As_Volatile (Typ);
11663      end if;
11664
11665      --  Volatile_Full_Access
11666
11667      if not Has_Rep_Item (Typ, Name_Volatile_Full_Access, False)
11668        and then Has_Rep_Pragma (Typ, Name_Volatile_Full_Access)
11669        and then Is_Pragma_Or_Corr_Pragma_Present_In_Rep_Item
11670                   (Get_Rep_Item (Typ, Name_Volatile_Full_Access))
11671      then
11672         Set_Is_Volatile_Full_Access (Typ);
11673         Set_Is_Volatile (Typ);
11674         Set_Treat_As_Volatile (Typ);
11675      end if;
11676
11677      --  Inheritance for derived types only
11678
11679      if Is_Derived_Type (Typ) then
11680         declare
11681            Bas_Typ     : constant Entity_Id := Base_Type (Typ);
11682            Imp_Bas_Typ : constant Entity_Id := Implementation_Base_Type (Typ);
11683
11684         begin
11685            --  Atomic_Components
11686
11687            if not Has_Rep_Item (Typ, Name_Atomic_Components, False)
11688              and then Has_Rep_Item (Typ, Name_Atomic_Components)
11689              and then Is_Pragma_Or_Corr_Pragma_Present_In_Rep_Item
11690                   (Get_Rep_Item (Typ, Name_Atomic_Components))
11691            then
11692               Set_Has_Atomic_Components (Imp_Bas_Typ);
11693            end if;
11694
11695            --  Volatile_Components
11696
11697            if not Has_Rep_Item (Typ, Name_Volatile_Components, False)
11698              and then Has_Rep_Item (Typ, Name_Volatile_Components)
11699              and then Is_Pragma_Or_Corr_Pragma_Present_In_Rep_Item
11700                   (Get_Rep_Item (Typ, Name_Volatile_Components))
11701            then
11702               Set_Has_Volatile_Components (Imp_Bas_Typ);
11703            end if;
11704
11705            --  Finalize_Storage_Only
11706
11707            if not Has_Rep_Pragma (Typ, Name_Finalize_Storage_Only, False)
11708              and then Has_Rep_Pragma (Typ, Name_Finalize_Storage_Only)
11709            then
11710               Set_Finalize_Storage_Only (Bas_Typ);
11711            end if;
11712
11713            --  Universal_Aliasing
11714
11715            if not Has_Rep_Item (Typ, Name_Universal_Aliasing, False)
11716              and then Has_Rep_Item (Typ, Name_Universal_Aliasing)
11717              and then Is_Pragma_Or_Corr_Pragma_Present_In_Rep_Item
11718                   (Get_Rep_Item (Typ, Name_Universal_Aliasing))
11719            then
11720               Set_Universal_Aliasing (Imp_Bas_Typ);
11721            end if;
11722
11723            --  Bit_Order
11724
11725            if Is_Record_Type (Typ) then
11726               if not Has_Rep_Item (Typ, Name_Bit_Order, False)
11727                 and then Has_Rep_Item (Typ, Name_Bit_Order)
11728               then
11729                  Set_Reverse_Bit_Order (Bas_Typ,
11730                    Reverse_Bit_Order (Rep_Item_Entity
11731                      (Get_Rep_Item (Typ, Name_Bit_Order))));
11732               end if;
11733            end if;
11734
11735            --  Scalar_Storage_Order
11736
11737            --  Note: the aspect is specified on a first subtype, but recorded
11738            --  in a flag of the base type!
11739
11740            if (Is_Record_Type (Typ) or else Is_Array_Type (Typ))
11741                 and then Typ = Bas_Typ
11742            then
11743               --  For a type extension, always inherit from parent; otherwise
11744               --  inherit if no default applies. Note: we do not check for
11745               --  an explicit rep item on the parent type when inheriting,
11746               --  because the parent SSO may itself have been set by default.
11747
11748               if not Has_Rep_Item (First_Subtype (Typ),
11749                                    Name_Scalar_Storage_Order, False)
11750                 and then (Is_Tagged_Type (Bas_Typ)
11751                            or else not (SSO_Set_Low_By_Default  (Bas_Typ)
11752                                           or else
11753                                         SSO_Set_High_By_Default (Bas_Typ)))
11754               then
11755                  Set_Reverse_Storage_Order (Bas_Typ,
11756                    Reverse_Storage_Order
11757                      (Implementation_Base_Type (Etype (Bas_Typ))));
11758
11759                  --  Clear default SSO indications, since the inherited aspect
11760                  --  which was set explicitly overrides the default.
11761
11762                  Set_SSO_Set_Low_By_Default  (Bas_Typ, False);
11763                  Set_SSO_Set_High_By_Default (Bas_Typ, False);
11764               end if;
11765            end if;
11766         end;
11767      end if;
11768   end Inherit_Aspects_At_Freeze_Point;
11769
11770   ----------------
11771   -- Initialize --
11772   ----------------
11773
11774   procedure Initialize is
11775   begin
11776      Address_Clause_Checks.Init;
11777      Compile_Time_Warnings_Errors.Init;
11778      Unchecked_Conversions.Init;
11779
11780      --  ??? Might be needed in the future for some non GCC back-ends
11781      --  if AAMP_On_Target then
11782      --     Independence_Checks.Init;
11783      --  end if;
11784   end Initialize;
11785
11786   ---------------------------
11787   -- Install_Discriminants --
11788   ---------------------------
11789
11790   procedure Install_Discriminants (E : Entity_Id) is
11791      Disc : Entity_Id;
11792      Prev : Entity_Id;
11793   begin
11794      Disc := First_Discriminant (E);
11795      while Present (Disc) loop
11796         Prev := Current_Entity (Disc);
11797         Set_Current_Entity (Disc);
11798         Set_Is_Immediately_Visible (Disc);
11799         Set_Homonym (Disc, Prev);
11800         Next_Discriminant (Disc);
11801      end loop;
11802   end Install_Discriminants;
11803
11804   -------------------------
11805   -- Is_Operational_Item --
11806   -------------------------
11807
11808   function Is_Operational_Item (N : Node_Id) return Boolean is
11809   begin
11810      if Nkind (N) /= N_Attribute_Definition_Clause then
11811         return False;
11812
11813      else
11814         declare
11815            Id : constant Attribute_Id := Get_Attribute_Id (Chars (N));
11816         begin
11817
11818            --  List of operational items is given in AARM 13.1(8.mm/1).
11819            --  It is clearly incomplete, as it does not include iterator
11820            --  aspects, among others.
11821
11822            return    Id = Attribute_Constant_Indexing
11823              or else Id = Attribute_Default_Iterator
11824              or else Id = Attribute_Implicit_Dereference
11825              or else Id = Attribute_Input
11826              or else Id = Attribute_Iterator_Element
11827              or else Id = Attribute_Iterable
11828              or else Id = Attribute_Output
11829              or else Id = Attribute_Read
11830              or else Id = Attribute_Variable_Indexing
11831              or else Id = Attribute_Write
11832              or else Id = Attribute_External_Tag;
11833         end;
11834      end if;
11835   end Is_Operational_Item;
11836
11837   -------------------------
11838   -- Is_Predicate_Static --
11839   -------------------------
11840
11841   --  Note: the basic legality of the expression has already been checked, so
11842   --  we don't need to worry about cases or ranges on strings for example.
11843
11844   function Is_Predicate_Static
11845     (Expr : Node_Id;
11846      Nam  : Name_Id) return Boolean
11847   is
11848      function All_Static_Case_Alternatives (L : List_Id) return Boolean;
11849      --  Given a list of case expression alternatives, returns True if all
11850      --  the alternatives are static (have all static choices, and a static
11851      --  expression).
11852
11853      function All_Static_Choices (L : List_Id) return Boolean;
11854      --  Returns true if all elements of the list are OK static choices
11855      --  as defined below for Is_Static_Choice. Used for case expression
11856      --  alternatives and for the right operand of a membership test. An
11857      --  others_choice is static if the corresponding expression is static.
11858      --  The staticness of the bounds is checked separately.
11859
11860      function Is_Static_Choice (N : Node_Id) return Boolean;
11861      --  Returns True if N represents a static choice (static subtype, or
11862      --  static subtype indication, or static expression, or static range).
11863      --
11864      --  Note that this is a bit more inclusive than we actually need
11865      --  (in particular membership tests do not allow the use of subtype
11866      --  indications). But that doesn't matter, we have already checked
11867      --  that the construct is legal to get this far.
11868
11869      function Is_Type_Ref (N : Node_Id) return Boolean;
11870      pragma Inline (Is_Type_Ref);
11871      --  Returns True if N is a reference to the type for the predicate in the
11872      --  expression (i.e. if it is an identifier whose Chars field matches the
11873      --  Nam given in the call). N must not be parenthesized, if the type name
11874      --  appears in parens, this routine will return False.
11875      --
11876      --  The routine also returns True for function calls generated during the
11877      --  expansion of comparison operators on strings, which are intended to
11878      --  be legal in static predicates, and are converted into calls to array
11879      --  comparison routines in the body of the corresponding predicate
11880      --  function.
11881
11882      ----------------------------------
11883      -- All_Static_Case_Alternatives --
11884      ----------------------------------
11885
11886      function All_Static_Case_Alternatives (L : List_Id) return Boolean is
11887         N : Node_Id;
11888
11889      begin
11890         N := First (L);
11891         while Present (N) loop
11892            if not (All_Static_Choices (Discrete_Choices (N))
11893                     and then Is_OK_Static_Expression (Expression (N)))
11894            then
11895               return False;
11896            end if;
11897
11898            Next (N);
11899         end loop;
11900
11901         return True;
11902      end All_Static_Case_Alternatives;
11903
11904      ------------------------
11905      -- All_Static_Choices --
11906      ------------------------
11907
11908      function All_Static_Choices (L : List_Id) return Boolean is
11909         N : Node_Id;
11910
11911      begin
11912         N := First (L);
11913         while Present (N) loop
11914            if not Is_Static_Choice (N) then
11915               return False;
11916            end if;
11917
11918            Next (N);
11919         end loop;
11920
11921         return True;
11922      end All_Static_Choices;
11923
11924      ----------------------
11925      -- Is_Static_Choice --
11926      ----------------------
11927
11928      function Is_Static_Choice (N : Node_Id) return Boolean is
11929      begin
11930         return Nkind (N) = N_Others_Choice
11931           or else Is_OK_Static_Expression (N)
11932           or else (Is_Entity_Name (N) and then Is_Type (Entity (N))
11933                     and then Is_OK_Static_Subtype (Entity (N)))
11934           or else (Nkind (N) = N_Subtype_Indication
11935                     and then Is_OK_Static_Subtype (Entity (N)))
11936           or else (Nkind (N) = N_Range and then Is_OK_Static_Range (N));
11937      end Is_Static_Choice;
11938
11939      -----------------
11940      -- Is_Type_Ref --
11941      -----------------
11942
11943      function Is_Type_Ref (N : Node_Id) return Boolean is
11944      begin
11945         return (Nkind (N) = N_Identifier
11946                  and then Chars (N) = Nam
11947                  and then Paren_Count (N) = 0)
11948           or else Nkind (N) = N_Function_Call;
11949      end Is_Type_Ref;
11950
11951   --  Start of processing for Is_Predicate_Static
11952
11953   begin
11954      --  Predicate_Static means one of the following holds. Numbers are the
11955      --  corresponding paragraph numbers in (RM 3.2.4(16-22)).
11956
11957      --  16: A static expression
11958
11959      if Is_OK_Static_Expression (Expr) then
11960         return True;
11961
11962      --  17: A membership test whose simple_expression is the current
11963      --  instance, and whose membership_choice_list meets the requirements
11964      --  for a static membership test.
11965
11966      elsif Nkind (Expr) in N_Membership_Test
11967        and then ((Present (Right_Opnd (Expr))
11968                    and then Is_Static_Choice (Right_Opnd (Expr)))
11969                  or else
11970                    (Present (Alternatives (Expr))
11971                      and then All_Static_Choices (Alternatives (Expr))))
11972      then
11973         return True;
11974
11975      --  18. A case_expression whose selecting_expression is the current
11976      --  instance, and whose dependent expressions are static expressions.
11977
11978      elsif Nkind (Expr) = N_Case_Expression
11979        and then Is_Type_Ref (Expression (Expr))
11980        and then All_Static_Case_Alternatives (Alternatives (Expr))
11981      then
11982         return True;
11983
11984      --  19. A call to a predefined equality or ordering operator, where one
11985      --  operand is the current instance, and the other is a static
11986      --  expression.
11987
11988      --  Note: the RM is clearly wrong here in not excluding string types.
11989      --  Without this exclusion, we would allow expressions like X > "ABC"
11990      --  to be considered as predicate-static, which is clearly not intended,
11991      --  since the idea is for predicate-static to be a subset of normal
11992      --  static expressions (and "DEF" > "ABC" is not a static expression).
11993
11994      --  However, we do allow internally generated (not from source) equality
11995      --  and inequality operations to be valid on strings (this helps deal
11996      --  with cases where we transform A in "ABC" to A = "ABC).
11997
11998      --  In fact, it appears that the intent of the ARG is to extend static
11999      --  predicates to strings, and that the extension should probably apply
12000      --  to static expressions themselves. The code below accepts comparison
12001      --  operators that apply to static strings.
12002
12003      elsif Nkind (Expr) in N_Op_Compare
12004        and then ((Is_Type_Ref (Left_Opnd (Expr))
12005                    and then Is_OK_Static_Expression (Right_Opnd (Expr)))
12006                  or else
12007                    (Is_Type_Ref (Right_Opnd (Expr))
12008                      and then Is_OK_Static_Expression (Left_Opnd (Expr))))
12009      then
12010         return True;
12011
12012      --  20. A call to a predefined boolean logical operator, where each
12013      --  operand is predicate-static.
12014
12015      elsif (Nkind_In (Expr, N_Op_And, N_Op_Or, N_Op_Xor)
12016              and then Is_Predicate_Static (Left_Opnd (Expr), Nam)
12017              and then Is_Predicate_Static (Right_Opnd (Expr), Nam))
12018        or else
12019            (Nkind (Expr) = N_Op_Not
12020              and then Is_Predicate_Static (Right_Opnd (Expr), Nam))
12021      then
12022         return True;
12023
12024      --  21. A short-circuit control form where both operands are
12025      --  predicate-static.
12026
12027      elsif Nkind (Expr) in N_Short_Circuit
12028        and then Is_Predicate_Static (Left_Opnd (Expr), Nam)
12029        and then Is_Predicate_Static (Right_Opnd (Expr), Nam)
12030      then
12031         return True;
12032
12033      --  22. A parenthesized predicate-static expression. This does not
12034      --  require any special test, since we just ignore paren levels in
12035      --  all the cases above.
12036
12037      --  One more test that is an implementation artifact caused by the fact
12038      --  that we are analyzing not the original expression, but the generated
12039      --  expression in the body of the predicate function. This can include
12040      --  references to inherited predicates, so that the expression we are
12041      --  processing looks like:
12042
12043      --    xxPredicate (typ (Inns)) and then expression
12044
12045      --  Where the call is to a Predicate function for an inherited predicate.
12046      --  We simply ignore such a call, which could be to either a dynamic or
12047      --  a static predicate. Note that if the parent predicate is dynamic then
12048      --  eventually this type will be marked as dynamic, but you are allowed
12049      --  to specify a static predicate for a subtype which is inheriting a
12050      --  dynamic predicate, so the static predicate validation here ignores
12051      --  the inherited predicate even if it is dynamic.
12052      --  In all cases, a static predicate can only apply to a scalar type.
12053
12054      elsif Nkind (Expr) = N_Function_Call
12055        and then Is_Predicate_Function (Entity (Name (Expr)))
12056        and then Is_Scalar_Type (Etype (First_Entity (Entity (Name (Expr)))))
12057      then
12058         return True;
12059
12060      elsif Is_Entity_Name (Expr)
12061        and then Entity (Expr) = Standard_True
12062      then
12063         Error_Msg_N ("predicate is redundant (always True)?", Expr);
12064         return True;
12065
12066      --  That's an exhaustive list of tests, all other cases are not
12067      --  predicate-static, so we return False.
12068
12069      else
12070         return False;
12071      end if;
12072   end Is_Predicate_Static;
12073
12074   ---------------------
12075   -- Kill_Rep_Clause --
12076   ---------------------
12077
12078   procedure Kill_Rep_Clause (N : Node_Id) is
12079   begin
12080      pragma Assert (Ignore_Rep_Clauses);
12081
12082      --  Note: we use Replace rather than Rewrite, because we don't want
12083      --  ASIS to be able to use Original_Node to dig out the (undecorated)
12084      --  rep clause that is being replaced.
12085
12086      Replace (N, Make_Null_Statement (Sloc (N)));
12087
12088      --  The null statement must be marked as not coming from source. This is
12089      --  so that ASIS ignores it, and also the back end does not expect bogus
12090      --  "from source" null statements in weird places (e.g. in declarative
12091      --  regions where such null statements are not allowed).
12092
12093      Set_Comes_From_Source (N, False);
12094   end Kill_Rep_Clause;
12095
12096   ------------------
12097   -- Minimum_Size --
12098   ------------------
12099
12100   function Minimum_Size
12101     (T      : Entity_Id;
12102      Biased : Boolean := False) return Nat
12103   is
12104      Lo     : Uint    := No_Uint;
12105      Hi     : Uint    := No_Uint;
12106      LoR    : Ureal   := No_Ureal;
12107      HiR    : Ureal   := No_Ureal;
12108      LoSet  : Boolean := False;
12109      HiSet  : Boolean := False;
12110      B      : Uint;
12111      S      : Nat;
12112      Ancest : Entity_Id;
12113      R_Typ  : constant Entity_Id := Root_Type (T);
12114
12115   begin
12116      --  If bad type, return 0
12117
12118      if T = Any_Type then
12119         return 0;
12120
12121      --  For generic types, just return zero. There cannot be any legitimate
12122      --  need to know such a size, but this routine may be called with a
12123      --  generic type as part of normal processing.
12124
12125      elsif Is_Generic_Type (R_Typ) or else R_Typ = Any_Type then
12126         return 0;
12127
12128         --  Access types (cannot have size smaller than System.Address)
12129
12130      elsif Is_Access_Type (T) then
12131         return System_Address_Size;
12132
12133      --  Floating-point types
12134
12135      elsif Is_Floating_Point_Type (T) then
12136         return UI_To_Int (Esize (R_Typ));
12137
12138      --  Discrete types
12139
12140      elsif Is_Discrete_Type (T) then
12141
12142         --  The following loop is looking for the nearest compile time known
12143         --  bounds following the ancestor subtype chain. The idea is to find
12144         --  the most restrictive known bounds information.
12145
12146         Ancest := T;
12147         loop
12148            if Ancest = Any_Type or else Etype (Ancest) = Any_Type then
12149               return 0;
12150            end if;
12151
12152            if not LoSet then
12153               if Compile_Time_Known_Value (Type_Low_Bound (Ancest)) then
12154                  Lo := Expr_Rep_Value (Type_Low_Bound (Ancest));
12155                  LoSet := True;
12156                  exit when HiSet;
12157               end if;
12158            end if;
12159
12160            if not HiSet then
12161               if Compile_Time_Known_Value (Type_High_Bound (Ancest)) then
12162                  Hi := Expr_Rep_Value (Type_High_Bound (Ancest));
12163                  HiSet := True;
12164                  exit when LoSet;
12165               end if;
12166            end if;
12167
12168            Ancest := Ancestor_Subtype (Ancest);
12169
12170            if No (Ancest) then
12171               Ancest := Base_Type (T);
12172
12173               if Is_Generic_Type (Ancest) then
12174                  return 0;
12175               end if;
12176            end if;
12177         end loop;
12178
12179      --  Fixed-point types. We can't simply use Expr_Value to get the
12180      --  Corresponding_Integer_Value values of the bounds, since these do not
12181      --  get set till the type is frozen, and this routine can be called
12182      --  before the type is frozen. Similarly the test for bounds being static
12183      --  needs to include the case where we have unanalyzed real literals for
12184      --  the same reason.
12185
12186      elsif Is_Fixed_Point_Type (T) then
12187
12188         --  The following loop is looking for the nearest compile time known
12189         --  bounds following the ancestor subtype chain. The idea is to find
12190         --  the most restrictive known bounds information.
12191
12192         Ancest := T;
12193         loop
12194            if Ancest = Any_Type or else Etype (Ancest) = Any_Type then
12195               return 0;
12196            end if;
12197
12198            --  Note: In the following two tests for LoSet and HiSet, it may
12199            --  seem redundant to test for N_Real_Literal here since normally
12200            --  one would assume that the test for the value being known at
12201            --  compile time includes this case. However, there is a glitch.
12202            --  If the real literal comes from folding a non-static expression,
12203            --  then we don't consider any non- static expression to be known
12204            --  at compile time if we are in configurable run time mode (needed
12205            --  in some cases to give a clearer definition of what is and what
12206            --  is not accepted). So the test is indeed needed. Without it, we
12207            --  would set neither Lo_Set nor Hi_Set and get an infinite loop.
12208
12209            if not LoSet then
12210               if Nkind (Type_Low_Bound (Ancest)) = N_Real_Literal
12211                 or else Compile_Time_Known_Value (Type_Low_Bound (Ancest))
12212               then
12213                  LoR := Expr_Value_R (Type_Low_Bound (Ancest));
12214                  LoSet := True;
12215                  exit when HiSet;
12216               end if;
12217            end if;
12218
12219            if not HiSet then
12220               if Nkind (Type_High_Bound (Ancest)) = N_Real_Literal
12221                 or else Compile_Time_Known_Value (Type_High_Bound (Ancest))
12222               then
12223                  HiR := Expr_Value_R (Type_High_Bound (Ancest));
12224                  HiSet := True;
12225                  exit when LoSet;
12226               end if;
12227            end if;
12228
12229            Ancest := Ancestor_Subtype (Ancest);
12230
12231            if No (Ancest) then
12232               Ancest := Base_Type (T);
12233
12234               if Is_Generic_Type (Ancest) then
12235                  return 0;
12236               end if;
12237            end if;
12238         end loop;
12239
12240         Lo := UR_To_Uint (LoR / Small_Value (T));
12241         Hi := UR_To_Uint (HiR / Small_Value (T));
12242
12243      --  No other types allowed
12244
12245      else
12246         raise Program_Error;
12247      end if;
12248
12249      --  Fall through with Hi and Lo set. Deal with biased case
12250
12251      if (Biased
12252           and then not Is_Fixed_Point_Type (T)
12253           and then not (Is_Enumeration_Type (T)
12254                          and then Has_Non_Standard_Rep (T)))
12255        or else Has_Biased_Representation (T)
12256      then
12257         Hi := Hi - Lo;
12258         Lo := Uint_0;
12259      end if;
12260
12261      --  Null range case, size is always zero. We only do this in the discrete
12262      --  type case, since that's the odd case that came up. Probably we should
12263      --  also do this in the fixed-point case, but doing so causes peculiar
12264      --  gigi failures, and it is not worth worrying about this incredibly
12265      --  marginal case (explicit null-range fixed-point type declarations)???
12266
12267      if Lo > Hi and then Is_Discrete_Type (T) then
12268         S := 0;
12269
12270      --  Signed case. Note that we consider types like range 1 .. -1 to be
12271      --  signed for the purpose of computing the size, since the bounds have
12272      --  to be accommodated in the base type.
12273
12274      elsif Lo < 0 or else Hi < 0 then
12275         S := 1;
12276         B := Uint_1;
12277
12278         --  S = size, B = 2 ** (size - 1) (can accommodate -B .. +(B - 1))
12279         --  Note that we accommodate the case where the bounds cross. This
12280         --  can happen either because of the way the bounds are declared
12281         --  or because of the algorithm in Freeze_Fixed_Point_Type.
12282
12283         while Lo < -B
12284           or else Hi < -B
12285           or else Lo >= B
12286           or else Hi >= B
12287         loop
12288            B := Uint_2 ** S;
12289            S := S + 1;
12290         end loop;
12291
12292      --  Unsigned case
12293
12294      else
12295         --  If both bounds are positive, make sure that both are represen-
12296         --  table in the case where the bounds are crossed. This can happen
12297         --  either because of the way the bounds are declared, or because of
12298         --  the algorithm in Freeze_Fixed_Point_Type.
12299
12300         if Lo > Hi then
12301            Hi := Lo;
12302         end if;
12303
12304         --  S = size, (can accommodate 0 .. (2**size - 1))
12305
12306         S := 0;
12307         while Hi >= Uint_2 ** S loop
12308            S := S + 1;
12309         end loop;
12310      end if;
12311
12312      return S;
12313   end Minimum_Size;
12314
12315   ---------------------------
12316   -- New_Stream_Subprogram --
12317   ---------------------------
12318
12319   procedure New_Stream_Subprogram
12320     (N     : Node_Id;
12321      Ent   : Entity_Id;
12322      Subp  : Entity_Id;
12323      Nam   : TSS_Name_Type)
12324   is
12325      Loc       : constant Source_Ptr := Sloc (N);
12326      Sname     : constant Name_Id    := Make_TSS_Name (Base_Type (Ent), Nam);
12327      Subp_Id   : Entity_Id;
12328      Subp_Decl : Node_Id;
12329      F         : Entity_Id;
12330      Etyp      : Entity_Id;
12331
12332      Defer_Declaration : constant Boolean :=
12333                            Is_Tagged_Type (Ent) or else Is_Private_Type (Ent);
12334      --  For a tagged type, there is a declaration for each stream attribute
12335      --  at the freeze point, and we must generate only a completion of this
12336      --  declaration. We do the same for private types, because the full view
12337      --  might be tagged. Otherwise we generate a declaration at the point of
12338      --  the attribute definition clause. If the attribute definition comes
12339      --  from an aspect specification the declaration is part of the freeze
12340      --  actions of the type.
12341
12342      function Build_Spec return Node_Id;
12343      --  Used for declaration and renaming declaration, so that this is
12344      --  treated as a renaming_as_body.
12345
12346      ----------------
12347      -- Build_Spec --
12348      ----------------
12349
12350      function Build_Spec return Node_Id is
12351         Out_P   : constant Boolean := (Nam = TSS_Stream_Read);
12352         Formals : List_Id;
12353         Spec    : Node_Id;
12354         T_Ref   : constant Node_Id := New_Occurrence_Of (Etyp, Loc);
12355
12356      begin
12357         Subp_Id := Make_Defining_Identifier (Loc, Sname);
12358
12359         --  S : access Root_Stream_Type'Class
12360
12361         Formals := New_List (
12362                      Make_Parameter_Specification (Loc,
12363                        Defining_Identifier =>
12364                          Make_Defining_Identifier (Loc, Name_S),
12365                        Parameter_Type =>
12366                          Make_Access_Definition (Loc,
12367                            Subtype_Mark =>
12368                              New_Occurrence_Of (
12369                                Designated_Type (Etype (F)), Loc))));
12370
12371         if Nam = TSS_Stream_Input then
12372            Spec :=
12373              Make_Function_Specification (Loc,
12374                Defining_Unit_Name       => Subp_Id,
12375                Parameter_Specifications => Formals,
12376                Result_Definition        => T_Ref);
12377         else
12378            --  V : [out] T
12379
12380            Append_To (Formals,
12381              Make_Parameter_Specification (Loc,
12382                Defining_Identifier => Make_Defining_Identifier (Loc, Name_V),
12383                Out_Present         => Out_P,
12384                Parameter_Type      => T_Ref));
12385
12386            Spec :=
12387              Make_Procedure_Specification (Loc,
12388                Defining_Unit_Name       => Subp_Id,
12389                Parameter_Specifications => Formals);
12390         end if;
12391
12392         return Spec;
12393      end Build_Spec;
12394
12395   --  Start of processing for New_Stream_Subprogram
12396
12397   begin
12398      F := First_Formal (Subp);
12399
12400      if Ekind (Subp) = E_Procedure then
12401         Etyp := Etype (Next_Formal (F));
12402      else
12403         Etyp := Etype (Subp);
12404      end if;
12405
12406      --  Prepare subprogram declaration and insert it as an action on the
12407      --  clause node. The visibility for this entity is used to test for
12408      --  visibility of the attribute definition clause (in the sense of
12409      --  8.3(23) as amended by AI-195).
12410
12411      if not Defer_Declaration then
12412         Subp_Decl :=
12413           Make_Subprogram_Declaration (Loc,
12414             Specification => Build_Spec);
12415
12416      --  For a tagged type, there is always a visible declaration for each
12417      --  stream TSS (it is a predefined primitive operation), and the
12418      --  completion of this declaration occurs at the freeze point, which is
12419      --  not always visible at places where the attribute definition clause is
12420      --  visible. So, we create a dummy entity here for the purpose of
12421      --  tracking the visibility of the attribute definition clause itself.
12422
12423      else
12424         Subp_Id :=
12425           Make_Defining_Identifier (Loc, New_External_Name (Sname, 'V'));
12426         Subp_Decl :=
12427           Make_Object_Declaration (Loc,
12428             Defining_Identifier => Subp_Id,
12429             Object_Definition   => New_Occurrence_Of (Standard_Boolean, Loc));
12430      end if;
12431
12432      if not Defer_Declaration
12433        and then From_Aspect_Specification (N)
12434        and then Has_Delayed_Freeze (Ent)
12435      then
12436         Append_Freeze_Action (Ent, Subp_Decl);
12437
12438      else
12439         Insert_Action (N, Subp_Decl);
12440         Set_Entity (N, Subp_Id);
12441      end if;
12442
12443      Subp_Decl :=
12444        Make_Subprogram_Renaming_Declaration (Loc,
12445          Specification => Build_Spec,
12446          Name          => New_Occurrence_Of (Subp, Loc));
12447
12448      if Defer_Declaration then
12449         Set_TSS (Base_Type (Ent), Subp_Id);
12450
12451      else
12452         if From_Aspect_Specification (N) then
12453            Append_Freeze_Action (Ent, Subp_Decl);
12454         else
12455            Insert_Action (N, Subp_Decl);
12456         end if;
12457
12458         Copy_TSS (Subp_Id, Base_Type (Ent));
12459      end if;
12460   end New_Stream_Subprogram;
12461
12462   --------------
12463   -- Pop_Type --
12464   --------------
12465
12466   procedure Pop_Type (E : Entity_Id) is
12467   begin
12468      if Ekind (E) = E_Record_Type and then E = Current_Scope then
12469         End_Scope;
12470
12471      elsif Is_Type (E)
12472        and then Has_Discriminants (E)
12473        and then Nkind (Parent (E)) /= N_Subtype_Declaration
12474      then
12475         Uninstall_Discriminants (E);
12476         Pop_Scope;
12477      end if;
12478   end Pop_Type;
12479
12480   ---------------
12481   -- Push_Type --
12482   ---------------
12483
12484   procedure Push_Type (E : Entity_Id) is
12485      Comp : Entity_Id;
12486
12487   begin
12488      if Ekind (E) = E_Record_Type then
12489         Push_Scope (E);
12490
12491         Comp := First_Component (E);
12492         while Present (Comp) loop
12493            Install_Entity (Comp);
12494            Next_Component (Comp);
12495         end loop;
12496
12497         if Has_Discriminants (E) then
12498            Install_Discriminants (E);
12499         end if;
12500
12501      elsif Is_Type (E)
12502        and then Has_Discriminants (E)
12503        and then Nkind (Parent (E)) /= N_Subtype_Declaration
12504      then
12505         Push_Scope (E);
12506         Install_Discriminants (E);
12507      end if;
12508   end Push_Type;
12509
12510   -----------------------------------
12511   -- Register_Address_Clause_Check --
12512   -----------------------------------
12513
12514   procedure Register_Address_Clause_Check
12515     (N   : Node_Id;
12516      X   : Entity_Id;
12517      A   : Uint;
12518      Y   : Entity_Id;
12519      Off : Boolean)
12520   is
12521      ACS : constant Boolean := Scope_Suppress.Suppress (Alignment_Check);
12522   begin
12523      Address_Clause_Checks.Append ((N, X, A, Y, Off, ACS));
12524   end Register_Address_Clause_Check;
12525
12526   ------------------------
12527   -- Rep_Item_Too_Early --
12528   ------------------------
12529
12530   function Rep_Item_Too_Early (T : Entity_Id; N : Node_Id) return Boolean is
12531   begin
12532      --  Cannot apply non-operational rep items to generic types
12533
12534      if Is_Operational_Item (N) then
12535         return False;
12536
12537      elsif Is_Type (T)
12538        and then Is_Generic_Type (Root_Type (T))
12539        and then (Nkind (N) /= N_Pragma
12540                   or else Get_Pragma_Id (N) /= Pragma_Convention)
12541      then
12542         Error_Msg_N ("representation item not allowed for generic type", N);
12543         return True;
12544      end if;
12545
12546      --  Otherwise check for incomplete type
12547
12548      if Is_Incomplete_Or_Private_Type (T)
12549        and then No (Underlying_Type (T))
12550        and then
12551          (Nkind (N) /= N_Pragma
12552            or else Get_Pragma_Id (N) /= Pragma_Import)
12553      then
12554         Error_Msg_N
12555           ("representation item must be after full type declaration", N);
12556         return True;
12557
12558      --  If the type has incomplete components, a representation clause is
12559      --  illegal but stream attributes and Convention pragmas are correct.
12560
12561      elsif Has_Private_Component (T) then
12562         if Nkind (N) = N_Pragma then
12563            return False;
12564
12565         else
12566            Error_Msg_N
12567              ("representation item must appear after type is fully defined",
12568                N);
12569            return True;
12570         end if;
12571      else
12572         return False;
12573      end if;
12574   end Rep_Item_Too_Early;
12575
12576   -----------------------
12577   -- Rep_Item_Too_Late --
12578   -----------------------
12579
12580   function Rep_Item_Too_Late
12581     (T     : Entity_Id;
12582      N     : Node_Id;
12583      FOnly : Boolean := False) return Boolean
12584   is
12585      function Is_Derived_Type_With_Constraint return Boolean;
12586      --  Check whether T is a derived type with an explicit constraint, in
12587      --  which case the constraint has frozen the type and the item is too
12588      --  late.  This compensates for the fact that for derived scalar types
12589      --  we freeze the base type unconditionally on account of a long-standing
12590      --  issue in gigi.
12591
12592      procedure No_Type_Rep_Item;
12593      --  Output message indicating that no type-related aspects can be
12594      --  specified due to some property of the parent type.
12595
12596      procedure Too_Late;
12597      --  Output message for an aspect being specified too late
12598
12599      --  Note that neither of the above errors is considered a serious one,
12600      --  since the effect is simply that we ignore the representation clause
12601      --  in these cases.
12602      --  Is this really true? In any case if we make this change we must
12603      --  document the requirement in the spec of Rep_Item_Too_Late that
12604      --  if True is returned, then the rep item must be completely ignored???
12605
12606      --------------------------------------
12607      --  Is_Derived_Type_With_Constraint --
12608      --------------------------------------
12609
12610      function Is_Derived_Type_With_Constraint return Boolean is
12611         Decl : constant Node_Id := Declaration_Node (T);
12612
12613      begin
12614         return Is_Derived_Type (T)
12615           and then Is_Frozen (Base_Type (T))
12616           and then Is_Enumeration_Type (T)
12617           and then False
12618           and then Nkind (N) = N_Enumeration_Representation_Clause
12619           and then Nkind (Decl) = N_Subtype_Declaration
12620           and then not Is_Entity_Name (Subtype_Indication (Decl));
12621      end Is_Derived_Type_With_Constraint;
12622
12623      ----------------------
12624      -- No_Type_Rep_Item --
12625      ----------------------
12626
12627      procedure No_Type_Rep_Item is
12628      begin
12629         Error_Msg_N ("|type-related representation item not permitted!", N);
12630      end No_Type_Rep_Item;
12631
12632      --------------
12633      -- Too_Late --
12634      --------------
12635
12636      procedure Too_Late is
12637      begin
12638         --  Other compilers seem more relaxed about rep items appearing too
12639         --  late. Since analysis tools typically don't care about rep items
12640         --  anyway, no reason to be too strict about this.
12641
12642         if not Relaxed_RM_Semantics then
12643            Error_Msg_N ("|representation item appears too late!", N);
12644         end if;
12645      end Too_Late;
12646
12647      --  Local variables
12648
12649      Parent_Type : Entity_Id;
12650      S           : Entity_Id;
12651
12652   --  Start of processing for Rep_Item_Too_Late
12653
12654   begin
12655      --  First make sure entity is not frozen (RM 13.1(9))
12656
12657      if (Is_Frozen (T)
12658           or else (Is_Type (T)
12659                     and then Is_Derived_Type_With_Constraint))
12660
12661        --  Exclude imported types, which may be frozen if they appear in a
12662        --  representation clause for a local type.
12663
12664        and then not From_Limited_With (T)
12665
12666        --  Exclude generated entities (not coming from source). The common
12667        --  case is when we generate a renaming which prematurely freezes the
12668        --  renamed internal entity, but we still want to be able to set copies
12669        --  of attribute values such as Size/Alignment.
12670
12671        and then Comes_From_Source (T)
12672      then
12673         --  A self-referential aspect is illegal if it forces freezing the
12674         --  entity before the corresponding pragma has been analyzed.
12675
12676         if Nkind_In (N, N_Attribute_Definition_Clause, N_Pragma)
12677           and then From_Aspect_Specification (N)
12678         then
12679            Error_Msg_NE
12680              ("aspect specification causes premature freezing of&", N, T);
12681            Set_Has_Delayed_Freeze (T, False);
12682            return True;
12683         end if;
12684
12685         Too_Late;
12686         S := First_Subtype (T);
12687
12688         if Present (Freeze_Node (S)) then
12689            if not Relaxed_RM_Semantics then
12690               Error_Msg_NE
12691                 ("??no more representation items for }", Freeze_Node (S), S);
12692            end if;
12693         end if;
12694
12695         return True;
12696
12697      --  Check for case of untagged derived type whose parent either has
12698      --  primitive operations, or is a by reference type (RM 13.1(10)). In
12699      --  this case we do not output a Too_Late message, since there is no
12700      --  earlier point where the rep item could be placed to make it legal.
12701
12702      elsif Is_Type (T)
12703        and then not FOnly
12704        and then Is_Derived_Type (T)
12705        and then not Is_Tagged_Type (T)
12706      then
12707         Parent_Type := Etype (Base_Type (T));
12708
12709         if Has_Primitive_Operations (Parent_Type) then
12710            No_Type_Rep_Item;
12711
12712            if not Relaxed_RM_Semantics then
12713               Error_Msg_NE
12714                 ("\parent type & has primitive operations!", N, Parent_Type);
12715            end if;
12716
12717            return True;
12718
12719         elsif Is_By_Reference_Type (Parent_Type) then
12720            No_Type_Rep_Item;
12721
12722            if not Relaxed_RM_Semantics then
12723               Error_Msg_NE
12724                 ("\parent type & is a by reference type!", N, Parent_Type);
12725            end if;
12726
12727            return True;
12728         end if;
12729      end if;
12730
12731      --  No error, but one more warning to consider. The RM (surprisingly)
12732      --  allows this pattern:
12733
12734      --    type S is ...
12735      --    primitive operations for S
12736      --    type R is new S;
12737      --    rep clause for S
12738
12739      --  Meaning that calls on the primitive operations of S for values of
12740      --  type R may require possibly expensive implicit conversion operations.
12741      --  This is not an error, but is worth a warning.
12742
12743      if not Relaxed_RM_Semantics and then Is_Type (T) then
12744         declare
12745            DTL : constant Entity_Id := Derived_Type_Link (Base_Type (T));
12746
12747         begin
12748            if Present (DTL)
12749              and then Has_Primitive_Operations (Base_Type (T))
12750
12751              --  For now, do not generate this warning for the case of aspect
12752              --  specification using Ada 2012 syntax, since we get wrong
12753              --  messages we do not understand. The whole business of derived
12754              --  types and rep items seems a bit confused when aspects are
12755              --  used, since the aspects are not evaluated till freeze time.
12756
12757              and then not From_Aspect_Specification (N)
12758            then
12759               Error_Msg_Sloc := Sloc (DTL);
12760               Error_Msg_N
12761                 ("representation item for& appears after derived type "
12762                  & "declaration#??", N);
12763               Error_Msg_NE
12764                 ("\may result in implicit conversions for primitive "
12765                  & "operations of&??", N, T);
12766               Error_Msg_NE
12767                 ("\to change representations when called with arguments "
12768                  & "of type&??", N, DTL);
12769            end if;
12770         end;
12771      end if;
12772
12773      --  No error, link item into head of chain of rep items for the entity,
12774      --  but avoid chaining if we have an overloadable entity, and the pragma
12775      --  is one that can apply to multiple overloaded entities.
12776
12777      if Is_Overloadable (T) and then Nkind (N) = N_Pragma then
12778         declare
12779            Pname : constant Name_Id := Pragma_Name (N);
12780         begin
12781            if Nam_In (Pname, Name_Convention, Name_Import,   Name_Export,
12782                              Name_External,   Name_Interface)
12783            then
12784               return False;
12785            end if;
12786         end;
12787      end if;
12788
12789      Record_Rep_Item (T, N);
12790      return False;
12791   end Rep_Item_Too_Late;
12792
12793   -------------------------------------
12794   -- Replace_Type_References_Generic --
12795   -------------------------------------
12796
12797   procedure Replace_Type_References_Generic (N : Node_Id; T : Entity_Id) is
12798      TName : constant Name_Id := Chars (T);
12799
12800      function Replace_Type_Ref (N : Node_Id) return Traverse_Result;
12801      --  Processes a single node in the traversal procedure below, checking
12802      --  if node N should be replaced, and if so, doing the replacement.
12803
12804      function Visible_Component (Comp : Name_Id) return Entity_Id;
12805      --  Given an identifier in the expression, check whether there is a
12806      --  discriminant or component of the type that is directy visible, and
12807      --  rewrite it as the corresponding selected component of the formal of
12808      --  the subprogram. The entity is located by a sequential search, which
12809      --  seems acceptable given the typical size of component lists and check
12810      --  expressions. Possible optimization ???
12811
12812      ----------------------
12813      -- Replace_Type_Ref --
12814      ----------------------
12815
12816      function Replace_Type_Ref (N : Node_Id) return Traverse_Result is
12817         Loc : constant Source_Ptr := Sloc (N);
12818
12819         procedure Add_Prefix (Ref : Node_Id; Comp : Entity_Id);
12820         --  Add the proper prefix to a reference to a component of the type
12821         --  when it is not already a selected component.
12822
12823         ----------------
12824         -- Add_Prefix --
12825         ----------------
12826
12827         procedure Add_Prefix (Ref : Node_Id; Comp : Entity_Id) is
12828         begin
12829            Rewrite (Ref,
12830              Make_Selected_Component (Loc,
12831                Prefix        => New_Occurrence_Of (T, Loc),
12832                Selector_Name => New_Occurrence_Of (Comp, Loc)));
12833            Replace_Type_Reference (Prefix (Ref));
12834         end Add_Prefix;
12835
12836         --  Local variables
12837
12838         Comp : Entity_Id;
12839         Pref : Node_Id;
12840         Scop : Entity_Id;
12841
12842      --  Start of processing for Replace_Type_Ref
12843
12844      begin
12845         if Nkind (N) = N_Identifier then
12846
12847            --  If not the type name, check whether it is a reference to some
12848            --  other type, which must be frozen before the predicate function
12849            --  is analyzed, i.e. before the freeze node of the type to which
12850            --  the predicate applies.
12851
12852            if Chars (N) /= TName then
12853               if Present (Current_Entity (N))
12854                 and then Is_Type (Current_Entity (N))
12855               then
12856                  Freeze_Before (Freeze_Node (T), Current_Entity (N));
12857               end if;
12858
12859               --  The components of the type are directly visible and can
12860               --  be referenced without a prefix.
12861
12862               if Nkind (Parent (N)) = N_Selected_Component then
12863                  null;
12864
12865               --  In expression C (I), C may be a directly visible function
12866               --  or a visible component that has an array type. Disambiguate
12867               --  by examining the component type.
12868
12869               elsif Nkind (Parent (N)) = N_Indexed_Component
12870                 and then N = Prefix (Parent (N))
12871               then
12872                  Comp := Visible_Component (Chars (N));
12873
12874                  if Present (Comp) and then Is_Array_Type (Etype (Comp)) then
12875                     Add_Prefix (N, Comp);
12876                  end if;
12877
12878               else
12879                  Comp := Visible_Component (Chars (N));
12880
12881                  if Present (Comp) then
12882                     Add_Prefix (N, Comp);
12883                  end if;
12884               end if;
12885
12886               return Skip;
12887
12888            --  Otherwise do the replacement if this is not a qualified
12889            --  reference to a homograph of the type itself. Note that the
12890            --  current instance could not appear in such a context, e.g.
12891            --  the prefix of a type conversion.
12892
12893            else
12894               if Nkind (Parent (N)) /= N_Selected_Component
12895                 or else N /= Selector_Name (Parent (N))
12896               then
12897                  Replace_Type_Reference (N);
12898               end if;
12899
12900               return Skip;
12901            end if;
12902
12903         --  Case of selected component, which may be a subcomponent of the
12904         --  current instance, or an expanded name which is still unanalyzed.
12905
12906         elsif Nkind (N) = N_Selected_Component then
12907
12908            --  If selector name is not our type, keep going (we might still
12909            --  have an occurrence of the type in the prefix). If it is a
12910            --  subcomponent of the current entity, add prefix.
12911
12912            if Nkind (Selector_Name (N)) /= N_Identifier
12913              or else Chars (Selector_Name (N)) /= TName
12914            then
12915               if Nkind (Prefix (N)) = N_Identifier then
12916                  Comp := Visible_Component (Chars (Prefix (N)));
12917
12918                  if Present (Comp) then
12919                     Add_Prefix (Prefix (N), Comp);
12920                  end if;
12921               end if;
12922
12923               return OK;
12924
12925            --  Selector name is our type, check qualification
12926
12927            else
12928               --  Loop through scopes and prefixes, doing comparison
12929
12930               Scop := Current_Scope;
12931               Pref := Prefix (N);
12932               loop
12933                  --  Continue if no more scopes or scope with no name
12934
12935                  if No (Scop) or else Nkind (Scop) not in N_Has_Chars then
12936                     return OK;
12937                  end if;
12938
12939                  --  Do replace if prefix is an identifier matching the scope
12940                  --  that we are currently looking at.
12941
12942                  if Nkind (Pref) = N_Identifier
12943                    and then Chars (Pref) = Chars (Scop)
12944                  then
12945                     Replace_Type_Reference (N);
12946                     return Skip;
12947                  end if;
12948
12949                  --  Go check scope above us if prefix is itself of the form
12950                  --  of a selected component, whose selector matches the scope
12951                  --  we are currently looking at.
12952
12953                  if Nkind (Pref) = N_Selected_Component
12954                    and then Nkind (Selector_Name (Pref)) = N_Identifier
12955                    and then Chars (Selector_Name (Pref)) = Chars (Scop)
12956                  then
12957                     Scop := Scope (Scop);
12958                     Pref := Prefix (Pref);
12959
12960                  --  For anything else, we don't have a match, so keep on
12961                  --  going, there are still some weird cases where we may
12962                  --  still have a replacement within the prefix.
12963
12964                  else
12965                     return OK;
12966                  end if;
12967               end loop;
12968            end if;
12969
12970         --  Continue for any other node kind
12971
12972         else
12973            return OK;
12974         end if;
12975      end Replace_Type_Ref;
12976
12977      procedure Replace_Type_Refs is new Traverse_Proc (Replace_Type_Ref);
12978
12979      -----------------------
12980      -- Visible_Component --
12981      -----------------------
12982
12983      function Visible_Component (Comp : Name_Id) return Entity_Id is
12984         E : Entity_Id;
12985
12986      begin
12987         --  Types with nameable components are records and discriminated
12988         --  private types.
12989
12990         if Ekind (T) = E_Record_Type
12991           or else (Is_Private_Type (T) and then Has_Discriminants (T))
12992         then
12993            E := First_Entity (T);
12994            while Present (E) loop
12995               if Comes_From_Source (E) and then Chars (E) = Comp then
12996                  return E;
12997               end if;
12998
12999               Next_Entity (E);
13000            end loop;
13001         end if;
13002
13003         --  Nothing by that name, or the type has no components
13004
13005         return Empty;
13006      end Visible_Component;
13007
13008   --  Start of processing for Replace_Type_References_Generic
13009
13010   begin
13011      Replace_Type_Refs (N);
13012   end Replace_Type_References_Generic;
13013
13014   --------------------------------
13015   -- Resolve_Aspect_Expressions --
13016   --------------------------------
13017
13018   procedure Resolve_Aspect_Expressions (E : Entity_Id) is
13019      function Resolve_Name (N : Node_Id) return Traverse_Result;
13020      --  Verify that all identifiers in the expression, with the exception
13021      --  of references to the current entity, denote visible entities. This
13022      --  is done only to detect visibility errors, as the expression will be
13023      --  properly analyzed/expanded during analysis of the predicate function
13024      --  body. We omit quantified expressions from this test, given that they
13025      --  introduce a local identifier that would require proper expansion to
13026      --  handle properly.
13027
13028      --  In ASIS_Mode we preserve the entity in the source because there is
13029      --  no subsequent expansion to decorate the tree.
13030
13031      ------------------
13032      -- Resolve_Name --
13033      ------------------
13034
13035      function Resolve_Name (N : Node_Id) return Traverse_Result is
13036         Dummy : Traverse_Result;
13037
13038      begin
13039         if Nkind (N) = N_Selected_Component then
13040            if Nkind (Prefix (N)) = N_Identifier
13041              and then Chars (Prefix (N)) /= Chars (E)
13042            then
13043               Find_Selected_Component (N);
13044            end if;
13045
13046            return Skip;
13047
13048         --  Resolve identifiers that are not selectors in parameter
13049         --  associations (these are never resolved by visibility).
13050
13051         elsif Nkind (N) = N_Identifier
13052           and then Chars (N) /= Chars (E)
13053           and then (Nkind (Parent (N)) /= N_Parameter_Association
13054                      or else N /= Selector_Name (Parent (N)))
13055         then
13056            Find_Direct_Name (N);
13057
13058            --  In ASIS mode we must analyze overloaded identifiers to ensure
13059            --  their correct decoration because expansion is disabled (and
13060            --  the expansion of freeze nodes takes care of resolving aspect
13061            --  expressions).
13062
13063            if ASIS_Mode then
13064               if Is_Overloaded (N) then
13065                  Analyze (Parent (N));
13066               end if;
13067            else
13068               Set_Entity (N, Empty);
13069            end if;
13070
13071         --  The name is component association needs no resolution.
13072
13073         elsif Nkind (N) = N_Component_Association then
13074            Dummy := Resolve_Name (Expression (N));
13075            return Skip;
13076
13077         elsif Nkind (N) = N_Quantified_Expression then
13078            return Skip;
13079         end if;
13080
13081         return OK;
13082      end Resolve_Name;
13083
13084      procedure Resolve_Aspect_Expression is new Traverse_Proc (Resolve_Name);
13085
13086      --  Local variables
13087
13088      ASN : Node_Id := First_Rep_Item (E);
13089
13090   --  Start of processing for Resolve_Aspect_Expressions
13091
13092   begin
13093      if No (ASN) then
13094         return;
13095      end if;
13096
13097      while Present (ASN) loop
13098         if Nkind (ASN) = N_Aspect_Specification and then Entity (ASN) = E then
13099            declare
13100               A_Id : constant Aspect_Id := Get_Aspect_Id (ASN);
13101               Expr : constant Node_Id   := Expression (ASN);
13102
13103            begin
13104               case A_Id is
13105
13106                  --  For now we only deal with aspects that do not generate
13107                  --  subprograms, or that may mention current instances of
13108                  --  types. These will require special handling (???TBD).
13109
13110                  when Aspect_Invariant
13111                     | Aspect_Predicate
13112                     | Aspect_Predicate_Failure
13113                  =>
13114                     null;
13115
13116                  when Aspect_Dynamic_Predicate
13117                     | Aspect_Static_Predicate
13118                  =>
13119                     --  Build predicate function specification and preanalyze
13120                     --  expression after type replacement. The function
13121                     --  declaration must be analyzed in the scope of the
13122                     --  type, but the the expression can reference components
13123                     --  and discriminants of the type.
13124
13125                     if No (Predicate_Function (E)) then
13126                        declare
13127                           FDecl : constant Node_Id :=
13128                                     Build_Predicate_Function_Declaration (E);
13129                           pragma Unreferenced (FDecl);
13130
13131                        begin
13132                           Push_Type (E);
13133                           Resolve_Aspect_Expression (Expr);
13134                           Pop_Type (E);
13135                        end;
13136                     end if;
13137
13138                  when Pre_Post_Aspects =>
13139                     null;
13140
13141                  when Aspect_Iterable =>
13142                     if Nkind (Expr) = N_Aggregate then
13143                        declare
13144                           Assoc : Node_Id;
13145
13146                        begin
13147                           Assoc := First (Component_Associations (Expr));
13148                           while Present (Assoc) loop
13149                              Find_Direct_Name (Expression (Assoc));
13150                              Next (Assoc);
13151                           end loop;
13152                        end;
13153                     end if;
13154
13155                  --  The expression for Default_Value is a static expression
13156                  --  of the type, but this expression does not freeze the
13157                  --  type, so it can still appear in a representation clause
13158                  --  before the actual freeze point.
13159
13160                  when Aspect_Default_Value =>
13161                     Set_Must_Not_Freeze (Expr);
13162                     Preanalyze_Spec_Expression (Expr, E);
13163
13164                  when Aspect_Priority =>
13165                     Push_Type (E);
13166                     Preanalyze_Spec_Expression (Expr, Any_Integer);
13167                     Pop_Type (E);
13168
13169                  --  Ditto for Storage_Size. Any other aspects that carry
13170                  --  expressions that should not freeze ??? This is only
13171                  --  relevant to the misuse of deferred constants.
13172
13173                  when Aspect_Storage_Size =>
13174                     Set_Must_Not_Freeze (Expr);
13175                     Preanalyze_Spec_Expression (Expr, Any_Integer);
13176
13177                  when others =>
13178                     if Present (Expr) then
13179                        case Aspect_Argument (A_Id) is
13180                           when Expression
13181                              | Optional_Expression
13182                           =>
13183                              Analyze_And_Resolve (Expr);
13184
13185                           when Name
13186                              | Optional_Name
13187                           =>
13188                              if Nkind (Expr) = N_Identifier then
13189                                 Find_Direct_Name (Expr);
13190
13191                              elsif Nkind (Expr) = N_Selected_Component then
13192                                 Find_Selected_Component (Expr);
13193                              end if;
13194                        end case;
13195                     end if;
13196               end case;
13197            end;
13198         end if;
13199
13200         ASN := Next_Rep_Item (ASN);
13201      end loop;
13202   end Resolve_Aspect_Expressions;
13203
13204   -------------------------
13205   -- Same_Representation --
13206   -------------------------
13207
13208   function Same_Representation (Typ1, Typ2 : Entity_Id) return Boolean is
13209      T1 : constant Entity_Id := Underlying_Type (Typ1);
13210      T2 : constant Entity_Id := Underlying_Type (Typ2);
13211
13212   begin
13213      --  A quick check, if base types are the same, then we definitely have
13214      --  the same representation, because the subtype specific representation
13215      --  attributes (Size and Alignment) do not affect representation from
13216      --  the point of view of this test.
13217
13218      if Base_Type (T1) = Base_Type (T2) then
13219         return True;
13220
13221      elsif Is_Private_Type (Base_Type (T2))
13222        and then Base_Type (T1) = Full_View (Base_Type (T2))
13223      then
13224         return True;
13225      end if;
13226
13227      --  Tagged types always have the same representation, because it is not
13228      --  possible to specify different representations for common fields.
13229
13230      if Is_Tagged_Type (T1) then
13231         return True;
13232      end if;
13233
13234      --  Representations are definitely different if conventions differ
13235
13236      if Convention (T1) /= Convention (T2) then
13237         return False;
13238      end if;
13239
13240      --  Representations are different if component alignments or scalar
13241      --  storage orders differ.
13242
13243      if (Is_Record_Type (T1) or else Is_Array_Type (T1))
13244            and then
13245         (Is_Record_Type (T2) or else Is_Array_Type (T2))
13246        and then
13247         (Component_Alignment (T1) /= Component_Alignment (T2)
13248           or else Reverse_Storage_Order (T1) /= Reverse_Storage_Order (T2))
13249      then
13250         return False;
13251      end if;
13252
13253      --  For arrays, the only real issue is component size. If we know the
13254      --  component size for both arrays, and it is the same, then that's
13255      --  good enough to know we don't have a change of representation.
13256
13257      if Is_Array_Type (T1) then
13258         if Known_Component_Size (T1)
13259           and then Known_Component_Size (T2)
13260           and then Component_Size (T1) = Component_Size (T2)
13261         then
13262            return True;
13263         end if;
13264      end if;
13265
13266      --  For records, representations are different if reorderings differ
13267
13268      if Is_Record_Type (T1)
13269        and then Is_Record_Type (T2)
13270        and then No_Reordering (T1) /= No_Reordering (T2)
13271      then
13272         return False;
13273      end if;
13274
13275      --  Types definitely have same representation if neither has non-standard
13276      --  representation since default representations are always consistent.
13277      --  If only one has non-standard representation, and the other does not,
13278      --  then we consider that they do not have the same representation. They
13279      --  might, but there is no way of telling early enough.
13280
13281      if Has_Non_Standard_Rep (T1) then
13282         if not Has_Non_Standard_Rep (T2) then
13283            return False;
13284         end if;
13285      else
13286         return not Has_Non_Standard_Rep (T2);
13287      end if;
13288
13289      --  Here the two types both have non-standard representation, and we need
13290      --  to determine if they have the same non-standard representation.
13291
13292      --  For arrays, we simply need to test if the component sizes are the
13293      --  same. Pragma Pack is reflected in modified component sizes, so this
13294      --  check also deals with pragma Pack.
13295
13296      if Is_Array_Type (T1) then
13297         return Component_Size (T1) = Component_Size (T2);
13298
13299      --  Case of record types
13300
13301      elsif Is_Record_Type (T1) then
13302
13303         --  Packed status must conform
13304
13305         if Is_Packed (T1) /= Is_Packed (T2) then
13306            return False;
13307
13308         --  Otherwise we must check components. Typ2 maybe a constrained
13309         --  subtype with fewer components, so we compare the components
13310         --  of the base types.
13311
13312         else
13313            Record_Case : declare
13314               CD1, CD2 : Entity_Id;
13315
13316               function Same_Rep return Boolean;
13317               --  CD1 and CD2 are either components or discriminants. This
13318               --  function tests whether they have the same representation.
13319
13320               --------------
13321               -- Same_Rep --
13322               --------------
13323
13324               function Same_Rep return Boolean is
13325               begin
13326                  if No (Component_Clause (CD1)) then
13327                     return No (Component_Clause (CD2));
13328                  else
13329                     --  Note: at this point, component clauses have been
13330                     --  normalized to the default bit order, so that the
13331                     --  comparison of Component_Bit_Offsets is meaningful.
13332
13333                     return
13334                        Present (Component_Clause (CD2))
13335                          and then
13336                        Component_Bit_Offset (CD1) = Component_Bit_Offset (CD2)
13337                          and then
13338                        Esize (CD1) = Esize (CD2);
13339                  end if;
13340               end Same_Rep;
13341
13342            --  Start of processing for Record_Case
13343
13344            begin
13345               if Has_Discriminants (T1) then
13346
13347                  --  The number of discriminants may be different if the
13348                  --  derived type has fewer (constrained by values). The
13349                  --  invisible discriminants retain the representation of
13350                  --  the original, so the discrepancy does not per se
13351                  --  indicate a different representation.
13352
13353                  CD1 := First_Discriminant (T1);
13354                  CD2 := First_Discriminant (T2);
13355                  while Present (CD1) and then Present (CD2) loop
13356                     if not Same_Rep then
13357                        return False;
13358                     else
13359                        Next_Discriminant (CD1);
13360                        Next_Discriminant (CD2);
13361                     end if;
13362                  end loop;
13363               end if;
13364
13365               CD1 := First_Component (Underlying_Type (Base_Type (T1)));
13366               CD2 := First_Component (Underlying_Type (Base_Type (T2)));
13367               while Present (CD1) loop
13368                  if not Same_Rep then
13369                     return False;
13370                  else
13371                     Next_Component (CD1);
13372                     Next_Component (CD2);
13373                  end if;
13374               end loop;
13375
13376               return True;
13377            end Record_Case;
13378         end if;
13379
13380      --  For enumeration types, we must check each literal to see if the
13381      --  representation is the same. Note that we do not permit enumeration
13382      --  representation clauses for Character and Wide_Character, so these
13383      --  cases were already dealt with.
13384
13385      elsif Is_Enumeration_Type (T1) then
13386         Enumeration_Case : declare
13387            L1, L2 : Entity_Id;
13388
13389         begin
13390            L1 := First_Literal (T1);
13391            L2 := First_Literal (T2);
13392            while Present (L1) loop
13393               if Enumeration_Rep (L1) /= Enumeration_Rep (L2) then
13394                  return False;
13395               else
13396                  Next_Literal (L1);
13397                  Next_Literal (L2);
13398               end if;
13399            end loop;
13400
13401            return True;
13402         end Enumeration_Case;
13403
13404      --  Any other types have the same representation for these purposes
13405
13406      else
13407         return True;
13408      end if;
13409   end Same_Representation;
13410
13411   --------------------------------
13412   -- Resolve_Iterable_Operation --
13413   --------------------------------
13414
13415   procedure Resolve_Iterable_Operation
13416     (N      : Node_Id;
13417      Cursor : Entity_Id;
13418      Typ    : Entity_Id;
13419      Nam    : Name_Id)
13420   is
13421      Ent : Entity_Id;
13422      F1  : Entity_Id;
13423      F2  : Entity_Id;
13424
13425   begin
13426      if not Is_Overloaded (N) then
13427         if not Is_Entity_Name (N)
13428           or else Ekind (Entity (N)) /= E_Function
13429           or else Scope (Entity (N)) /= Scope (Typ)
13430           or else No (First_Formal (Entity (N)))
13431           or else Etype (First_Formal (Entity (N))) /= Typ
13432         then
13433            Error_Msg_N
13434              ("iterable primitive must be local function name whose first "
13435               & "formal is an iterable type", N);
13436            return;
13437         end if;
13438
13439         Ent := Entity (N);
13440         F1  := First_Formal (Ent);
13441
13442         if Nam = Name_First or else Nam = Name_Last then
13443
13444            --  First or Last (Container) => Cursor
13445
13446            if Etype (Ent) /= Cursor then
13447               Error_Msg_N ("primitive for First must yield a curosr", N);
13448            end if;
13449
13450         elsif Nam = Name_Next then
13451
13452            --  Next (Container, Cursor) => Cursor
13453
13454            F2 := Next_Formal (F1);
13455
13456            if Etype (F2) /= Cursor
13457              or else Etype (Ent) /= Cursor
13458              or else Present (Next_Formal (F2))
13459            then
13460               Error_Msg_N ("no match for Next iterable primitive", N);
13461            end if;
13462
13463         elsif Nam = Name_Previous then
13464
13465            --  Previous (Container, Cursor) => Cursor
13466
13467            F2 := Next_Formal (F1);
13468
13469            if Etype (F2) /= Cursor
13470              or else Etype (Ent) /= Cursor
13471              or else Present (Next_Formal (F2))
13472            then
13473               Error_Msg_N ("no match for Previous iterable primitive", N);
13474            end if;
13475
13476         elsif Nam = Name_Has_Element then
13477
13478            --  Has_Element (Container, Cursor) => Boolean
13479
13480            F2 := Next_Formal (F1);
13481
13482            if Etype (F2) /= Cursor
13483              or else Etype (Ent) /= Standard_Boolean
13484              or else Present (Next_Formal (F2))
13485            then
13486               Error_Msg_N ("no match for Has_Element iterable primitive", N);
13487            end if;
13488
13489         elsif Nam = Name_Element then
13490            F2 := Next_Formal (F1);
13491
13492            if No (F2)
13493              or else Etype (F2) /= Cursor
13494              or else Present (Next_Formal (F2))
13495            then
13496               Error_Msg_N ("no match for Element iterable primitive", N);
13497            end if;
13498
13499         else
13500            raise Program_Error;
13501         end if;
13502
13503      else
13504         --  Overloaded case: find subprogram with proper signature. Caller
13505         --  will report error if no match is found.
13506
13507         declare
13508            I  : Interp_Index;
13509            It : Interp;
13510
13511         begin
13512            Get_First_Interp (N, I, It);
13513            while Present (It.Typ) loop
13514               if Ekind (It.Nam) = E_Function
13515                  and then Scope (It.Nam) = Scope (Typ)
13516                  and then Etype (First_Formal (It.Nam)) = Typ
13517               then
13518                  F1 := First_Formal (It.Nam);
13519
13520                  if Nam = Name_First then
13521                     if Etype (It.Nam) = Cursor
13522                       and then No (Next_Formal (F1))
13523                     then
13524                        Set_Entity (N, It.Nam);
13525                        exit;
13526                     end if;
13527
13528                  elsif Nam = Name_Next then
13529                     F2 := Next_Formal (F1);
13530
13531                     if Present (F2)
13532                       and then No (Next_Formal (F2))
13533                       and then Etype (F2) = Cursor
13534                       and then Etype (It.Nam) = Cursor
13535                     then
13536                        Set_Entity (N, It.Nam);
13537                        exit;
13538                     end if;
13539
13540                  elsif Nam = Name_Has_Element then
13541                     F2 := Next_Formal (F1);
13542
13543                     if Present (F2)
13544                       and then No (Next_Formal (F2))
13545                       and then Etype (F2) = Cursor
13546                       and then Etype (It.Nam) = Standard_Boolean
13547                     then
13548                        Set_Entity (N, It.Nam);
13549                        F2 := Next_Formal (F1);
13550                        exit;
13551                     end if;
13552
13553                  elsif Nam = Name_Element then
13554                     F2 := Next_Formal (F1);
13555
13556                     if Present (F2)
13557                       and then No (Next_Formal (F2))
13558                       and then Etype (F2) = Cursor
13559                     then
13560                        Set_Entity (N, It.Nam);
13561                        exit;
13562                     end if;
13563                  end if;
13564               end if;
13565
13566               Get_Next_Interp (I, It);
13567            end loop;
13568         end;
13569      end if;
13570   end Resolve_Iterable_Operation;
13571
13572   ----------------
13573   -- Set_Biased --
13574   ----------------
13575
13576   procedure Set_Biased
13577     (E      : Entity_Id;
13578      N      : Node_Id;
13579      Msg    : String;
13580      Biased : Boolean := True)
13581   is
13582   begin
13583      if Biased then
13584         Set_Has_Biased_Representation (E);
13585
13586         if Warn_On_Biased_Representation then
13587            Error_Msg_NE
13588              ("?B?" & Msg & " forces biased representation for&", N, E);
13589         end if;
13590      end if;
13591   end Set_Biased;
13592
13593   --------------------
13594   -- Set_Enum_Esize --
13595   --------------------
13596
13597   procedure Set_Enum_Esize (T : Entity_Id) is
13598      Lo : Uint;
13599      Hi : Uint;
13600      Sz : Nat;
13601
13602   begin
13603      Init_Alignment (T);
13604
13605      --  Find the minimum standard size (8,16,32,64) that fits
13606
13607      Lo := Enumeration_Rep (Entity (Type_Low_Bound (T)));
13608      Hi := Enumeration_Rep (Entity (Type_High_Bound (T)));
13609
13610      if Lo < 0 then
13611         if Lo >= -Uint_2**07 and then Hi < Uint_2**07 then
13612            Sz := Standard_Character_Size;  -- May be > 8 on some targets
13613
13614         elsif Lo >= -Uint_2**15 and then Hi < Uint_2**15 then
13615            Sz := 16;
13616
13617         elsif Lo >= -Uint_2**31 and then Hi < Uint_2**31 then
13618            Sz := 32;
13619
13620         else pragma Assert (Lo >= -Uint_2**63 and then Hi < Uint_2**63);
13621            Sz := 64;
13622         end if;
13623
13624      else
13625         if Hi < Uint_2**08 then
13626            Sz := Standard_Character_Size;  -- May be > 8 on some targets
13627
13628         elsif Hi < Uint_2**16 then
13629            Sz := 16;
13630
13631         elsif Hi < Uint_2**32 then
13632            Sz := 32;
13633
13634         else pragma Assert (Hi < Uint_2**63);
13635            Sz := 64;
13636         end if;
13637      end if;
13638
13639      --  That minimum is the proper size unless we have a foreign convention
13640      --  and the size required is 32 or less, in which case we bump the size
13641      --  up to 32. This is required for C and C++ and seems reasonable for
13642      --  all other foreign conventions.
13643
13644      if Has_Foreign_Convention (T)
13645        and then Esize (T) < Standard_Integer_Size
13646
13647        --  Don't do this if Short_Enums on target
13648
13649        and then not Target_Short_Enums
13650      then
13651         Init_Esize (T, Standard_Integer_Size);
13652      else
13653         Init_Esize (T, Sz);
13654      end if;
13655   end Set_Enum_Esize;
13656
13657   -----------------------------
13658   -- Uninstall_Discriminants --
13659   -----------------------------
13660
13661   procedure Uninstall_Discriminants (E : Entity_Id) is
13662      Disc  : Entity_Id;
13663      Prev  : Entity_Id;
13664      Outer : Entity_Id;
13665
13666   begin
13667      --  Discriminants have been made visible for type declarations and
13668      --  protected type declarations, not for subtype declarations.
13669
13670      if Nkind (Parent (E)) /= N_Subtype_Declaration then
13671         Disc := First_Discriminant (E);
13672         while Present (Disc) loop
13673            if Disc /= Current_Entity (Disc) then
13674               Prev := Current_Entity (Disc);
13675               while Present (Prev)
13676                 and then Present (Homonym (Prev))
13677                 and then Homonym (Prev) /= Disc
13678               loop
13679                  Prev := Homonym (Prev);
13680               end loop;
13681            else
13682               Prev := Empty;
13683            end if;
13684
13685            Set_Is_Immediately_Visible (Disc, False);
13686
13687            Outer := Homonym (Disc);
13688            while Present (Outer) and then Scope (Outer) = E loop
13689               Outer := Homonym (Outer);
13690            end loop;
13691
13692            --  Reset homonym link of other entities, but do not modify link
13693            --  between entities in current scope, so that the back end can
13694            --  have a proper count of local overloadings.
13695
13696            if No (Prev) then
13697               Set_Name_Entity_Id (Chars (Disc), Outer);
13698
13699            elsif Scope (Prev) /= Scope (Disc) then
13700               Set_Homonym (Prev,  Outer);
13701            end if;
13702
13703            Next_Discriminant (Disc);
13704         end loop;
13705      end if;
13706   end Uninstall_Discriminants;
13707
13708   ------------------------------
13709   -- Validate_Address_Clauses --
13710   ------------------------------
13711
13712   procedure Validate_Address_Clauses is
13713      function Offset_Value (Expr : Node_Id) return Uint;
13714      --  Given an Address attribute reference, return the value in bits of its
13715      --  offset from the first bit of the underlying entity, or 0 if it is not
13716      --  known at compile time.
13717
13718      ------------------
13719      -- Offset_Value --
13720      ------------------
13721
13722      function Offset_Value (Expr : Node_Id) return Uint is
13723         N   : Node_Id := Prefix (Expr);
13724         Off : Uint;
13725         Val : Uint := Uint_0;
13726
13727      begin
13728         --  Climb the prefix chain and compute the cumulative offset
13729
13730         loop
13731            if Is_Entity_Name (N) then
13732               return Val;
13733
13734            elsif Nkind (N) = N_Selected_Component then
13735               Off := Component_Bit_Offset (Entity (Selector_Name (N)));
13736               if Off /= No_Uint and then Off >= Uint_0 then
13737                  Val := Val + Off;
13738                  N   := Prefix (N);
13739               else
13740                  return Uint_0;
13741               end if;
13742
13743            elsif Nkind (N) = N_Indexed_Component then
13744               Off := Indexed_Component_Bit_Offset (N);
13745               if Off /= No_Uint then
13746                  Val := Val + Off;
13747                  N   := Prefix (N);
13748               else
13749                  return Uint_0;
13750               end if;
13751
13752            else
13753               return Uint_0;
13754            end if;
13755         end loop;
13756      end Offset_Value;
13757
13758   --  Start of processing for Validate_Address_Clauses
13759
13760   begin
13761      for J in Address_Clause_Checks.First .. Address_Clause_Checks.Last loop
13762         declare
13763            ACCR : Address_Clause_Check_Record
13764                     renames Address_Clause_Checks.Table (J);
13765
13766            Expr : Node_Id;
13767
13768            X_Alignment : Uint;
13769            Y_Alignment : Uint := Uint_0;
13770
13771            X_Size : Uint;
13772            Y_Size : Uint := Uint_0;
13773
13774            X_Offs : Uint;
13775
13776         begin
13777            --  Skip processing of this entry if warning already posted
13778
13779            if not Address_Warning_Posted (ACCR.N) then
13780               Expr := Original_Node (Expression (ACCR.N));
13781
13782               --  Get alignments, sizes and offset, if any
13783
13784               X_Alignment := Alignment (ACCR.X);
13785               X_Size      := Esize (ACCR.X);
13786
13787               if Present (ACCR.Y) then
13788                  Y_Alignment := Alignment (ACCR.Y);
13789                  Y_Size      := Esize (ACCR.Y);
13790               end if;
13791
13792               if ACCR.Off
13793                 and then Nkind (Expr) = N_Attribute_Reference
13794                 and then Attribute_Name (Expr) = Name_Address
13795               then
13796                  X_Offs := Offset_Value (Expr);
13797               else
13798                  X_Offs := Uint_0;
13799               end if;
13800
13801               --  Check for known value not multiple of alignment
13802
13803               if No (ACCR.Y) then
13804                  if not Alignment_Checks_Suppressed (ACCR)
13805                    and then X_Alignment /= 0
13806                    and then ACCR.A mod X_Alignment /= 0
13807                  then
13808                     Error_Msg_NE
13809                       ("??specified address for& is inconsistent with "
13810                        & "alignment", ACCR.N, ACCR.X);
13811                     Error_Msg_N
13812                       ("\??program execution may be erroneous (RM 13.3(27))",
13813                        ACCR.N);
13814
13815                     Error_Msg_Uint_1 := X_Alignment;
13816                     Error_Msg_NE ("\??alignment of & is ^", ACCR.N, ACCR.X);
13817                  end if;
13818
13819               --  Check for large object overlaying smaller one
13820
13821               elsif Y_Size > Uint_0
13822                 and then X_Size > Uint_0
13823                 and then X_Offs + X_Size > Y_Size
13824               then
13825                  Error_Msg_NE ("??& overlays smaller object", ACCR.N, ACCR.X);
13826                  Error_Msg_N
13827                    ("\??program execution may be erroneous", ACCR.N);
13828
13829                  Error_Msg_Uint_1 := X_Size;
13830                  Error_Msg_NE ("\??size of & is ^", ACCR.N, ACCR.X);
13831
13832                  Error_Msg_Uint_1 := Y_Size;
13833                  Error_Msg_NE ("\??size of & is ^", ACCR.N, ACCR.Y);
13834
13835                  if Y_Size >= X_Size then
13836                     Error_Msg_Uint_1 := X_Offs;
13837                     Error_Msg_NE ("\??but offset of & is ^", ACCR.N, ACCR.X);
13838                  end if;
13839
13840               --  Check for inadequate alignment, both of the base object
13841               --  and of the offset, if any. We only do this check if the
13842               --  run-time Alignment_Check is active. No point in warning
13843               --  if this check has been suppressed (or is suppressed by
13844               --  default in the non-strict alignment machine case).
13845
13846               --  Note: we do not check the alignment if we gave a size
13847               --  warning, since it would likely be redundant.
13848
13849               elsif not Alignment_Checks_Suppressed (ACCR)
13850                 and then Y_Alignment /= Uint_0
13851                 and then
13852                   (Y_Alignment < X_Alignment
13853                     or else
13854                       (ACCR.Off
13855                         and then Nkind (Expr) = N_Attribute_Reference
13856                         and then Attribute_Name (Expr) = Name_Address
13857                         and then Has_Compatible_Alignment
13858                                    (ACCR.X, Prefix (Expr), True) /=
13859                                      Known_Compatible))
13860               then
13861                  Error_Msg_NE
13862                    ("??specified address for& may be inconsistent with "
13863                     & "alignment", ACCR.N, ACCR.X);
13864                  Error_Msg_N
13865                    ("\??program execution may be erroneous (RM 13.3(27))",
13866                     ACCR.N);
13867
13868                  Error_Msg_Uint_1 := X_Alignment;
13869                  Error_Msg_NE ("\??alignment of & is ^", ACCR.N, ACCR.X);
13870
13871                  Error_Msg_Uint_1 := Y_Alignment;
13872                  Error_Msg_NE ("\??alignment of & is ^", ACCR.N, ACCR.Y);
13873
13874                  if Y_Alignment >= X_Alignment then
13875                     Error_Msg_N
13876                       ("\??but offset is not multiple of alignment", ACCR.N);
13877                  end if;
13878               end if;
13879            end if;
13880         end;
13881      end loop;
13882   end Validate_Address_Clauses;
13883
13884   -----------------------------------------
13885   -- Validate_Compile_Time_Warning_Error --
13886   -----------------------------------------
13887
13888   procedure Validate_Compile_Time_Warning_Error (N : Node_Id) is
13889   begin
13890      Compile_Time_Warnings_Errors.Append
13891        (New_Val => CTWE_Entry'(Eloc  => Sloc (N),
13892                                Scope => Current_Scope,
13893                                Prag  => N));
13894   end Validate_Compile_Time_Warning_Error;
13895
13896   ------------------------------------------
13897   -- Validate_Compile_Time_Warning_Errors --
13898   ------------------------------------------
13899
13900   procedure Validate_Compile_Time_Warning_Errors is
13901      procedure Set_Scope (S : Entity_Id);
13902      --  Install all enclosing scopes of S along with S itself
13903
13904      procedure Unset_Scope (S : Entity_Id);
13905      --  Uninstall all enclosing scopes of S along with S itself
13906
13907      ---------------
13908      -- Set_Scope --
13909      ---------------
13910
13911      procedure Set_Scope (S : Entity_Id) is
13912      begin
13913         if S /= Standard_Standard then
13914            Set_Scope (Scope (S));
13915         end if;
13916
13917         Push_Scope (S);
13918      end Set_Scope;
13919
13920      -----------------
13921      -- Unset_Scope --
13922      -----------------
13923
13924      procedure Unset_Scope (S : Entity_Id) is
13925      begin
13926         if S /= Standard_Standard then
13927            Unset_Scope (Scope (S));
13928         end if;
13929
13930         Pop_Scope;
13931      end Unset_Scope;
13932
13933   --  Start of processing for Validate_Compile_Time_Warning_Errors
13934
13935   begin
13936      Expander_Mode_Save_And_Set (False);
13937      In_Compile_Time_Warning_Or_Error := True;
13938
13939      for N in Compile_Time_Warnings_Errors.First ..
13940               Compile_Time_Warnings_Errors.Last
13941      loop
13942         declare
13943            T : CTWE_Entry renames Compile_Time_Warnings_Errors.Table (N);
13944
13945         begin
13946            Set_Scope (T.Scope);
13947            Reset_Analyzed_Flags (T.Prag);
13948            Process_Compile_Time_Warning_Or_Error (T.Prag, T.Eloc);
13949            Unset_Scope (T.Scope);
13950         end;
13951      end loop;
13952
13953      In_Compile_Time_Warning_Or_Error := False;
13954      Expander_Mode_Restore;
13955   end Validate_Compile_Time_Warning_Errors;
13956
13957   ---------------------------
13958   -- Validate_Independence --
13959   ---------------------------
13960
13961   procedure Validate_Independence is
13962      SU   : constant Uint := UI_From_Int (System_Storage_Unit);
13963      N    : Node_Id;
13964      E    : Entity_Id;
13965      IC   : Boolean;
13966      Comp : Entity_Id;
13967      Addr : Node_Id;
13968      P    : Node_Id;
13969
13970      procedure Check_Array_Type (Atyp : Entity_Id);
13971      --  Checks if the array type Atyp has independent components, and
13972      --  if not, outputs an appropriate set of error messages.
13973
13974      procedure No_Independence;
13975      --  Output message that independence cannot be guaranteed
13976
13977      function OK_Component (C : Entity_Id) return Boolean;
13978      --  Checks one component to see if it is independently accessible, and
13979      --  if so yields True, otherwise yields False if independent access
13980      --  cannot be guaranteed. This is a conservative routine, it only
13981      --  returns True if it knows for sure, it returns False if it knows
13982      --  there is a problem, or it cannot be sure there is no problem.
13983
13984      procedure Reason_Bad_Component (C : Entity_Id);
13985      --  Outputs continuation message if a reason can be determined for
13986      --  the component C being bad.
13987
13988      ----------------------
13989      -- Check_Array_Type --
13990      ----------------------
13991
13992      procedure Check_Array_Type (Atyp : Entity_Id) is
13993         Ctyp : constant Entity_Id := Component_Type (Atyp);
13994
13995      begin
13996         --  OK if no alignment clause, no pack, and no component size
13997
13998         if not Has_Component_Size_Clause (Atyp)
13999           and then not Has_Alignment_Clause (Atyp)
14000           and then not Is_Packed (Atyp)
14001         then
14002            return;
14003         end if;
14004
14005         --  Case of component size is greater than or equal to 64 and the
14006         --  alignment of the array is at least as large as the alignment
14007         --  of the component. We are definitely OK in this situation.
14008
14009         if Known_Component_Size (Atyp)
14010           and then Component_Size (Atyp) >= 64
14011           and then Known_Alignment (Atyp)
14012           and then Known_Alignment (Ctyp)
14013           and then Alignment (Atyp) >= Alignment (Ctyp)
14014         then
14015            return;
14016         end if;
14017
14018         --  Check actual component size
14019
14020         if not Known_Component_Size (Atyp)
14021           or else not (Addressable (Component_Size (Atyp))
14022                         and then Component_Size (Atyp) < 64)
14023           or else Component_Size (Atyp) mod Esize (Ctyp) /= 0
14024         then
14025            No_Independence;
14026
14027            --  Bad component size, check reason
14028
14029            if Has_Component_Size_Clause (Atyp) then
14030               P := Get_Attribute_Definition_Clause
14031                      (Atyp, Attribute_Component_Size);
14032
14033               if Present (P) then
14034                  Error_Msg_Sloc := Sloc (P);
14035                  Error_Msg_N ("\because of Component_Size clause#", N);
14036                  return;
14037               end if;
14038            end if;
14039
14040            if Is_Packed (Atyp) then
14041               P := Get_Rep_Pragma (Atyp, Name_Pack);
14042
14043               if Present (P) then
14044                  Error_Msg_Sloc := Sloc (P);
14045                  Error_Msg_N ("\because of pragma Pack#", N);
14046                  return;
14047               end if;
14048            end if;
14049
14050            --  No reason found, just return
14051
14052            return;
14053         end if;
14054
14055         --  Array type is OK independence-wise
14056
14057         return;
14058      end Check_Array_Type;
14059
14060      ---------------------
14061      -- No_Independence --
14062      ---------------------
14063
14064      procedure No_Independence is
14065      begin
14066         if Pragma_Name (N) = Name_Independent then
14067            Error_Msg_NE ("independence cannot be guaranteed for&", N, E);
14068         else
14069            Error_Msg_NE
14070              ("independent components cannot be guaranteed for&", N, E);
14071         end if;
14072      end No_Independence;
14073
14074      ------------------
14075      -- OK_Component --
14076      ------------------
14077
14078      function OK_Component (C : Entity_Id) return Boolean is
14079         Rec  : constant Entity_Id := Scope (C);
14080         Ctyp : constant Entity_Id := Etype (C);
14081
14082      begin
14083         --  OK if no component clause, no Pack, and no alignment clause
14084
14085         if No (Component_Clause (C))
14086           and then not Is_Packed (Rec)
14087           and then not Has_Alignment_Clause (Rec)
14088         then
14089            return True;
14090         end if;
14091
14092         --  Here we look at the actual component layout. A component is
14093         --  addressable if its size is a multiple of the Esize of the
14094         --  component type, and its starting position in the record has
14095         --  appropriate alignment, and the record itself has appropriate
14096         --  alignment to guarantee the component alignment.
14097
14098         --  Make sure sizes are static, always assume the worst for any
14099         --  cases where we cannot check static values.
14100
14101         if not (Known_Static_Esize (C)
14102                  and then
14103                 Known_Static_Esize (Ctyp))
14104         then
14105            return False;
14106         end if;
14107
14108         --  Size of component must be addressable or greater than 64 bits
14109         --  and a multiple of bytes.
14110
14111         if not Addressable (Esize (C)) and then Esize (C) < Uint_64 then
14112            return False;
14113         end if;
14114
14115         --  Check size is proper multiple
14116
14117         if Esize (C) mod Esize (Ctyp) /= 0 then
14118            return False;
14119         end if;
14120
14121         --  Check alignment of component is OK
14122
14123         if not Known_Component_Bit_Offset (C)
14124           or else Component_Bit_Offset (C) < Uint_0
14125           or else Component_Bit_Offset (C) mod Esize (Ctyp) /= 0
14126         then
14127            return False;
14128         end if;
14129
14130         --  Check alignment of record type is OK
14131
14132         if not Known_Alignment (Rec)
14133           or else (Alignment (Rec) * SU) mod Esize (Ctyp) /= 0
14134         then
14135            return False;
14136         end if;
14137
14138         --  All tests passed, component is addressable
14139
14140         return True;
14141      end OK_Component;
14142
14143      --------------------------
14144      -- Reason_Bad_Component --
14145      --------------------------
14146
14147      procedure Reason_Bad_Component (C : Entity_Id) is
14148         Rec  : constant Entity_Id := Scope (C);
14149         Ctyp : constant Entity_Id := Etype (C);
14150
14151      begin
14152         --  If component clause present assume that's the problem
14153
14154         if Present (Component_Clause (C)) then
14155            Error_Msg_Sloc := Sloc (Component_Clause (C));
14156            Error_Msg_N ("\because of Component_Clause#", N);
14157            return;
14158         end if;
14159
14160         --  If pragma Pack clause present, assume that's the problem
14161
14162         if Is_Packed (Rec) then
14163            P := Get_Rep_Pragma (Rec, Name_Pack);
14164
14165            if Present (P) then
14166               Error_Msg_Sloc := Sloc (P);
14167               Error_Msg_N ("\because of pragma Pack#", N);
14168               return;
14169            end if;
14170         end if;
14171
14172         --  See if record has bad alignment clause
14173
14174         if Has_Alignment_Clause (Rec)
14175           and then Known_Alignment (Rec)
14176           and then (Alignment (Rec) * SU) mod Esize (Ctyp) /= 0
14177         then
14178            P := Get_Attribute_Definition_Clause (Rec, Attribute_Alignment);
14179
14180            if Present (P) then
14181               Error_Msg_Sloc := Sloc (P);
14182               Error_Msg_N ("\because of Alignment clause#", N);
14183            end if;
14184         end if;
14185
14186         --  Couldn't find a reason, so return without a message
14187
14188         return;
14189      end Reason_Bad_Component;
14190
14191   --  Start of processing for Validate_Independence
14192
14193   begin
14194      for J in Independence_Checks.First .. Independence_Checks.Last loop
14195         N  := Independence_Checks.Table (J).N;
14196         E  := Independence_Checks.Table (J).E;
14197         IC := Pragma_Name (N) = Name_Independent_Components;
14198
14199         --  Deal with component case
14200
14201         if Ekind (E) = E_Discriminant or else Ekind (E) = E_Component then
14202            if not OK_Component (E) then
14203               No_Independence;
14204               Reason_Bad_Component (E);
14205               goto Continue;
14206            end if;
14207         end if;
14208
14209         --  Deal with record with Independent_Components
14210
14211         if IC and then Is_Record_Type (E) then
14212            Comp := First_Component_Or_Discriminant (E);
14213            while Present (Comp) loop
14214               if not OK_Component (Comp) then
14215                  No_Independence;
14216                  Reason_Bad_Component (Comp);
14217                  goto Continue;
14218               end if;
14219
14220               Next_Component_Or_Discriminant (Comp);
14221            end loop;
14222         end if;
14223
14224         --  Deal with address clause case
14225
14226         if Is_Object (E) then
14227            Addr := Address_Clause (E);
14228
14229            if Present (Addr) then
14230               No_Independence;
14231               Error_Msg_Sloc := Sloc (Addr);
14232               Error_Msg_N ("\because of Address clause#", N);
14233               goto Continue;
14234            end if;
14235         end if;
14236
14237         --  Deal with independent components for array type
14238
14239         if IC and then Is_Array_Type (E) then
14240            Check_Array_Type (E);
14241         end if;
14242
14243         --  Deal with independent components for array object
14244
14245         if IC and then Is_Object (E) and then Is_Array_Type (Etype (E)) then
14246            Check_Array_Type (Etype (E));
14247         end if;
14248
14249      <<Continue>> null;
14250      end loop;
14251   end Validate_Independence;
14252
14253   ------------------------------
14254   -- Validate_Iterable_Aspect --
14255   ------------------------------
14256
14257   procedure Validate_Iterable_Aspect (Typ : Entity_Id; ASN : Node_Id) is
14258      Assoc : Node_Id;
14259      Expr  : Node_Id;
14260
14261      Prim   : Node_Id;
14262      Cursor : constant Entity_Id := Get_Cursor_Type (ASN, Typ);
14263
14264      First_Id       : Entity_Id;
14265      Last_Id        : Entity_Id;
14266      Next_Id        : Entity_Id;
14267      Has_Element_Id : Entity_Id;
14268      Element_Id     : Entity_Id;
14269
14270   begin
14271      --  If previous error aspect is unusable
14272
14273      if Cursor = Any_Type then
14274         return;
14275      end if;
14276
14277      First_Id       := Empty;
14278      Last_Id        := Empty;
14279      Next_Id        := Empty;
14280      Has_Element_Id := Empty;
14281      Element_Id     := Empty;
14282
14283      --  Each expression must resolve to a function with the proper signature
14284
14285      Assoc := First (Component_Associations (Expression (ASN)));
14286      while Present (Assoc) loop
14287         Expr := Expression (Assoc);
14288         Analyze (Expr);
14289
14290         Prim := First (Choices (Assoc));
14291
14292         if Nkind (Prim) /= N_Identifier or else Present (Next (Prim)) then
14293            Error_Msg_N ("illegal name in association", Prim);
14294
14295         elsif Chars (Prim) = Name_First then
14296            Resolve_Iterable_Operation (Expr, Cursor, Typ, Name_First);
14297            First_Id := Entity (Expr);
14298
14299         elsif Chars (Prim) = Name_Last then
14300            Resolve_Iterable_Operation (Expr, Cursor, Typ, Name_Last);
14301            Last_Id := Entity (Expr);
14302
14303         elsif Chars (Prim) = Name_Previous then
14304            Resolve_Iterable_Operation (Expr, Cursor, Typ, Name_Previous);
14305            Last_Id := Entity (Expr);
14306
14307         elsif Chars (Prim) = Name_Next then
14308            Resolve_Iterable_Operation (Expr, Cursor, Typ, Name_Next);
14309            Next_Id := Entity (Expr);
14310
14311         elsif Chars (Prim) = Name_Has_Element then
14312            Resolve_Iterable_Operation (Expr, Cursor, Typ, Name_Has_Element);
14313            Has_Element_Id := Entity (Expr);
14314
14315         elsif Chars (Prim) = Name_Element then
14316            Resolve_Iterable_Operation (Expr, Cursor, Typ, Name_Element);
14317            Element_Id := Entity (Expr);
14318
14319         else
14320            Error_Msg_N ("invalid name for iterable function", Prim);
14321         end if;
14322
14323         Next (Assoc);
14324      end loop;
14325
14326      if No (First_Id) then
14327         Error_Msg_N ("match for First primitive not found", ASN);
14328
14329      elsif No (Next_Id) then
14330         Error_Msg_N ("match for Next primitive not found", ASN);
14331
14332      elsif No (Has_Element_Id) then
14333         Error_Msg_N ("match for Has_Element primitive not found", ASN);
14334
14335      elsif No (Element_Id) or else No (Last_Id) then
14336         null;  --  optional
14337      end if;
14338   end Validate_Iterable_Aspect;
14339
14340   -----------------------------------
14341   -- Validate_Unchecked_Conversion --
14342   -----------------------------------
14343
14344   procedure Validate_Unchecked_Conversion
14345     (N        : Node_Id;
14346      Act_Unit : Entity_Id)
14347   is
14348      Source : Entity_Id;
14349      Target : Entity_Id;
14350      Vnode  : Node_Id;
14351
14352   begin
14353      --  Obtain source and target types. Note that we call Ancestor_Subtype
14354      --  here because the processing for generic instantiation always makes
14355      --  subtypes, and we want the original frozen actual types.
14356
14357      --  If we are dealing with private types, then do the check on their
14358      --  fully declared counterparts if the full declarations have been
14359      --  encountered (they don't have to be visible, but they must exist).
14360
14361      Source := Ancestor_Subtype (Etype (First_Formal (Act_Unit)));
14362
14363      if Is_Private_Type (Source)
14364        and then Present (Underlying_Type (Source))
14365      then
14366         Source := Underlying_Type (Source);
14367      end if;
14368
14369      Target := Ancestor_Subtype (Etype (Act_Unit));
14370
14371      --  If either type is generic, the instantiation happens within a generic
14372      --  unit, and there is nothing to check. The proper check will happen
14373      --  when the enclosing generic is instantiated.
14374
14375      if Is_Generic_Type (Source) or else Is_Generic_Type (Target) then
14376         return;
14377      end if;
14378
14379      if Is_Private_Type (Target)
14380        and then Present (Underlying_Type (Target))
14381      then
14382         Target := Underlying_Type (Target);
14383      end if;
14384
14385      --  Source may be unconstrained array, but not target, except in relaxed
14386      --  semantics mode.
14387
14388      if Is_Array_Type (Target)
14389        and then not Is_Constrained (Target)
14390        and then not Relaxed_RM_Semantics
14391      then
14392         Error_Msg_N
14393           ("unchecked conversion to unconstrained array not allowed", N);
14394         return;
14395      end if;
14396
14397      --  Warn if conversion between two different convention pointers
14398
14399      if Is_Access_Type (Target)
14400        and then Is_Access_Type (Source)
14401        and then Convention (Target) /= Convention (Source)
14402        and then Warn_On_Unchecked_Conversion
14403      then
14404         --  Give warnings for subprogram pointers only on most targets
14405
14406         if Is_Access_Subprogram_Type (Target)
14407           or else Is_Access_Subprogram_Type (Source)
14408         then
14409            Error_Msg_N
14410              ("?z?conversion between pointers with different conventions!",
14411               N);
14412         end if;
14413      end if;
14414
14415      --  Warn if one of the operands is Ada.Calendar.Time. Do not emit a
14416      --  warning when compiling GNAT-related sources.
14417
14418      if Warn_On_Unchecked_Conversion
14419        and then not In_Predefined_Unit (N)
14420        and then RTU_Loaded (Ada_Calendar)
14421        and then (Chars (Source) = Name_Time
14422                    or else
14423                  Chars (Target) = Name_Time)
14424      then
14425         --  If Ada.Calendar is loaded and the name of one of the operands is
14426         --  Time, there is a good chance that this is Ada.Calendar.Time.
14427
14428         declare
14429            Calendar_Time : constant Entity_Id := Full_View (RTE (RO_CA_Time));
14430         begin
14431            pragma Assert (Present (Calendar_Time));
14432
14433            if Source = Calendar_Time or else Target = Calendar_Time then
14434               Error_Msg_N
14435                 ("?z?representation of 'Time values may change between "
14436                  & "'G'N'A'T versions", N);
14437            end if;
14438         end;
14439      end if;
14440
14441      --  Make entry in unchecked conversion table for later processing by
14442      --  Validate_Unchecked_Conversions, which will check sizes and alignments
14443      --  (using values set by the back end where possible). This is only done
14444      --  if the appropriate warning is active.
14445
14446      if Warn_On_Unchecked_Conversion then
14447         Unchecked_Conversions.Append
14448           (New_Val => UC_Entry'(Eloc     => Sloc (N),
14449                                 Source   => Source,
14450                                 Target   => Target,
14451                                 Act_Unit => Act_Unit));
14452
14453         --  If both sizes are known statically now, then back-end annotation
14454         --  is not required to do a proper check but if either size is not
14455         --  known statically, then we need the annotation.
14456
14457         if Known_Static_RM_Size (Source)
14458              and then
14459            Known_Static_RM_Size (Target)
14460         then
14461            null;
14462         else
14463            Back_Annotate_Rep_Info := True;
14464         end if;
14465      end if;
14466
14467      --  If unchecked conversion to access type, and access type is declared
14468      --  in the same unit as the unchecked conversion, then set the flag
14469      --  No_Strict_Aliasing (no strict aliasing is implicit here)
14470
14471      if Is_Access_Type (Target) and then
14472        In_Same_Source_Unit (Target, N)
14473      then
14474         Set_No_Strict_Aliasing (Implementation_Base_Type (Target));
14475      end if;
14476
14477      --  Generate N_Validate_Unchecked_Conversion node for back end in case
14478      --  the back end needs to perform special validation checks.
14479
14480      --  Shouldn't this be in Exp_Ch13, since the check only gets done if we
14481      --  have full expansion and the back end is called ???
14482
14483      Vnode :=
14484        Make_Validate_Unchecked_Conversion (Sloc (N));
14485      Set_Source_Type (Vnode, Source);
14486      Set_Target_Type (Vnode, Target);
14487
14488      --  If the unchecked conversion node is in a list, just insert before it.
14489      --  If not we have some strange case, not worth bothering about.
14490
14491      if Is_List_Member (N) then
14492         Insert_After (N, Vnode);
14493      end if;
14494   end Validate_Unchecked_Conversion;
14495
14496   ------------------------------------
14497   -- Validate_Unchecked_Conversions --
14498   ------------------------------------
14499
14500   procedure Validate_Unchecked_Conversions is
14501   begin
14502      for N in Unchecked_Conversions.First .. Unchecked_Conversions.Last loop
14503         declare
14504            T : UC_Entry renames Unchecked_Conversions.Table (N);
14505
14506            Act_Unit : constant Entity_Id  := T.Act_Unit;
14507            Eloc     : constant Source_Ptr := T.Eloc;
14508            Source   : constant Entity_Id  := T.Source;
14509            Target   : constant Entity_Id  := T.Target;
14510
14511            Source_Siz : Uint;
14512            Target_Siz : Uint;
14513
14514         begin
14515            --  Skip if function marked as warnings off
14516
14517            if Warnings_Off (Act_Unit) then
14518               goto Continue;
14519            end if;
14520
14521            --  This validation check, which warns if we have unequal sizes for
14522            --  unchecked conversion, and thus potentially implementation
14523            --  dependent semantics, is one of the few occasions on which we
14524            --  use the official RM size instead of Esize. See description in
14525            --  Einfo "Handling of Type'Size Values" for details.
14526
14527            if Serious_Errors_Detected = 0
14528              and then Known_Static_RM_Size (Source)
14529              and then Known_Static_RM_Size (Target)
14530
14531              --  Don't do the check if warnings off for either type, note the
14532              --  deliberate use of OR here instead of OR ELSE to get the flag
14533              --  Warnings_Off_Used set for both types if appropriate.
14534
14535              and then not (Has_Warnings_Off (Source)
14536                              or
14537                            Has_Warnings_Off (Target))
14538            then
14539               Source_Siz := RM_Size (Source);
14540               Target_Siz := RM_Size (Target);
14541
14542               if Source_Siz /= Target_Siz then
14543                  Error_Msg
14544                    ("?z?types for unchecked conversion have different sizes!",
14545                     Eloc, Act_Unit);
14546
14547                  if All_Errors_Mode then
14548                     Error_Msg_Name_1 := Chars (Source);
14549                     Error_Msg_Uint_1 := Source_Siz;
14550                     Error_Msg_Name_2 := Chars (Target);
14551                     Error_Msg_Uint_2 := Target_Siz;
14552                     Error_Msg ("\size of % is ^, size of % is ^?z?", Eloc);
14553
14554                     Error_Msg_Uint_1 := UI_Abs (Source_Siz - Target_Siz);
14555
14556                     if Is_Discrete_Type (Source)
14557                          and then
14558                        Is_Discrete_Type (Target)
14559                     then
14560                        if Source_Siz > Target_Siz then
14561                           Error_Msg
14562                             ("\?z?^ high order bits of source will "
14563                              & "be ignored!", Eloc);
14564
14565                        elsif Is_Unsigned_Type (Source) then
14566                           Error_Msg
14567                             ("\?z?source will be extended with ^ high order "
14568                              & "zero bits!", Eloc);
14569
14570                        else
14571                           Error_Msg
14572                             ("\?z?source will be extended with ^ high order "
14573                              & "sign bits!", Eloc);
14574                        end if;
14575
14576                     elsif Source_Siz < Target_Siz then
14577                        if Is_Discrete_Type (Target) then
14578                           if Bytes_Big_Endian then
14579                              Error_Msg
14580                                ("\?z?target value will include ^ undefined "
14581                                 & "low order bits!", Eloc, Act_Unit);
14582                           else
14583                              Error_Msg
14584                                ("\?z?target value will include ^ undefined "
14585                                 & "high order bits!", Eloc, Act_Unit);
14586                           end if;
14587
14588                        else
14589                           Error_Msg
14590                             ("\?z?^ trailing bits of target value will be "
14591                              & "undefined!", Eloc, Act_Unit);
14592                        end if;
14593
14594                     else pragma Assert (Source_Siz > Target_Siz);
14595                        if Is_Discrete_Type (Source) then
14596                           if Bytes_Big_Endian then
14597                              Error_Msg
14598                                ("\?z?^ low order bits of source will be "
14599                                 & "ignored!", Eloc, Act_Unit);
14600                           else
14601                              Error_Msg
14602                                ("\?z?^ high order bits of source will be "
14603                                 & "ignored!", Eloc, Act_Unit);
14604                           end if;
14605
14606                        else
14607                           Error_Msg
14608                             ("\?z?^ trailing bits of source will be "
14609                              & "ignored!", Eloc, Act_Unit);
14610                        end if;
14611                     end if;
14612                  end if;
14613               end if;
14614            end if;
14615
14616            --  If both types are access types, we need to check the alignment.
14617            --  If the alignment of both is specified, we can do it here.
14618
14619            if Serious_Errors_Detected = 0
14620              and then Is_Access_Type (Source)
14621              and then Is_Access_Type (Target)
14622              and then Target_Strict_Alignment
14623              and then Present (Designated_Type (Source))
14624              and then Present (Designated_Type (Target))
14625            then
14626               declare
14627                  D_Source : constant Entity_Id := Designated_Type (Source);
14628                  D_Target : constant Entity_Id := Designated_Type (Target);
14629
14630               begin
14631                  if Known_Alignment (D_Source)
14632                       and then
14633                     Known_Alignment (D_Target)
14634                  then
14635                     declare
14636                        Source_Align : constant Uint := Alignment (D_Source);
14637                        Target_Align : constant Uint := Alignment (D_Target);
14638
14639                     begin
14640                        if Source_Align < Target_Align
14641                          and then not Is_Tagged_Type (D_Source)
14642
14643                          --  Suppress warning if warnings suppressed on either
14644                          --  type or either designated type. Note the use of
14645                          --  OR here instead of OR ELSE. That is intentional,
14646                          --  we would like to set flag Warnings_Off_Used in
14647                          --  all types for which warnings are suppressed.
14648
14649                          and then not (Has_Warnings_Off (D_Source)
14650                                          or
14651                                        Has_Warnings_Off (D_Target)
14652                                          or
14653                                        Has_Warnings_Off (Source)
14654                                          or
14655                                        Has_Warnings_Off (Target))
14656                        then
14657                           Error_Msg_Uint_1 := Target_Align;
14658                           Error_Msg_Uint_2 := Source_Align;
14659                           Error_Msg_Node_1 := D_Target;
14660                           Error_Msg_Node_2 := D_Source;
14661                           Error_Msg
14662                             ("?z?alignment of & (^) is stricter than "
14663                              & "alignment of & (^)!", Eloc, Act_Unit);
14664                           Error_Msg
14665                             ("\?z?resulting access value may have invalid "
14666                              & "alignment!", Eloc, Act_Unit);
14667                        end if;
14668                     end;
14669                  end if;
14670               end;
14671            end if;
14672         end;
14673
14674      <<Continue>>
14675         null;
14676      end loop;
14677   end Validate_Unchecked_Conversions;
14678
14679end Sem_Ch13;
14680