1------------------------------------------------------------------------------
2--                                                                          --
3--                         GNAT COMPILER COMPONENTS                         --
4--                                                                          --
5--                              S E M _ C A T                               --
6--                                                                          --
7--                                 B o d y                                  --
8--                                                                          --
9--          Copyright (C) 1992-2012, Free Software Foundation, Inc.         --
10--                                                                          --
11-- GNAT is free software;  you can  redistribute it  and/or modify it under --
12-- terms of the  GNU General Public License as published  by the Free Soft- --
13-- ware  Foundation;  either version 3,  or (at your option) any later ver- --
14-- sion.  GNAT is distributed in the hope that it will be useful, but WITH- --
15-- OUT ANY WARRANTY;  without even the  implied warranty of MERCHANTABILITY --
16-- or FITNESS FOR A PARTICULAR PURPOSE.  See the GNU General Public License --
17-- for  more details.  You should have  received  a copy of the GNU General --
18-- Public License  distributed with GNAT; see file COPYING3.  If not, go to --
19-- http://www.gnu.org/licenses for a complete copy of the license.          --
20--                                                                          --
21-- GNAT was originally developed  by the GNAT team at  New York University. --
22-- Extensive contributions were provided by Ada Core Technologies Inc.      --
23--                                                                          --
24------------------------------------------------------------------------------
25
26with Atree;    use Atree;
27with Debug;    use Debug;
28with Einfo;    use Einfo;
29with Elists;   use Elists;
30with Errout;   use Errout;
31with Exp_Disp; use Exp_Disp;
32with Fname;    use Fname;
33with Lib;      use Lib;
34with Namet;    use Namet;
35with Nlists;   use Nlists;
36with Opt;      use Opt;
37with Sem;      use Sem;
38with Sem_Attr; use Sem_Attr;
39with Sem_Aux;  use Sem_Aux;
40with Sem_Dist; use Sem_Dist;
41with Sem_Eval; use Sem_Eval;
42with Sem_Util; use Sem_Util;
43with Sinfo;    use Sinfo;
44with Snames;   use Snames;
45with Stand;    use Stand;
46
47package body Sem_Cat is
48
49   -----------------------
50   -- Local Subprograms --
51   -----------------------
52
53   procedure Check_Categorization_Dependencies
54     (Unit_Entity     : Entity_Id;
55      Depended_Entity : Entity_Id;
56      Info_Node       : Node_Id;
57      Is_Subunit      : Boolean);
58   --  This procedure checks that the categorization of a lib unit and that
59   --  of the depended unit satisfy dependency restrictions.
60   --  The depended_entity can be the entity in a with_clause item, in which
61   --  case Info_Node denotes that item. The depended_entity can also be the
62   --  parent unit of a child unit, in which case Info_Node is the declaration
63   --  of the child unit.  The error message is posted on Info_Node, and is
64   --  specialized if Is_Subunit is true.
65
66   procedure Check_Non_Static_Default_Expr
67     (Type_Def : Node_Id;
68      Obj_Decl : Node_Id);
69   --  Iterate through the component list of a record definition, check
70   --  that no component is declared with a nonstatic default value.
71   --  If a nonstatic default exists, report an error on Obj_Decl.
72
73   function Has_Read_Write_Attributes (E : Entity_Id) return Boolean;
74   --  Return True if entity has attribute definition clauses for Read and
75   --  Write attributes that are visible at some place.
76
77   function Is_Non_Remote_Access_Type (E : Entity_Id) return Boolean;
78   --  Returns true if the entity is a type whose full view is a non-remote
79   --  access type, for the purpose of enforcing E.2.2(8) rules.
80
81   function Has_Non_Remote_Access (Typ : Entity_Id) return Boolean;
82   --  Return true if Typ or the type of any of its subcomponents is a non
83   --  remote access type and doesn't have user-defined stream attributes.
84
85   function No_External_Streaming (E : Entity_Id) return Boolean;
86   --  Return True if the entity or one of its subcomponents does not support
87   --  external streaming.
88
89   function In_RCI_Declaration (N : Node_Id) return Boolean;
90   --  Determines if a declaration is  within the visible part of a Remote
91   --  Call Interface compilation unit, for semantic checking purposes only
92   --  (returns false within an instance and within the package body).
93
94   function In_RT_Declaration return Boolean;
95   --  Determines if current scope is within the declaration of a Remote Types
96   --  unit, for semantic checking purposes.
97
98   function In_Shared_Passive_Unit return Boolean;
99   --  Determines if current scope is within a Shared Passive compilation unit
100
101   function Static_Discriminant_Expr (L : List_Id) return Boolean;
102   --  Iterate through the list of discriminants to check if any of them
103   --  contains non-static default expression, which is a violation in
104   --  a preelaborated library unit.
105
106   procedure Validate_Remote_Access_Object_Type_Declaration (T : Entity_Id);
107   --  Check validity of declaration if RCI or RT unit. It should not contain
108   --  the declaration of an access-to-object type unless it is a general
109   --  access type that designates a class-wide limited private type. There are
110   --  also constraints about the primitive subprograms of the class-wide type.
111   --  RM E.2 (9, 13, 14)
112
113   procedure Validate_RACW_Primitive
114     (Subp : Entity_Id;
115      RACW : Entity_Id);
116   --  Check legality of the declaration of primitive Subp of the designated
117   --  type of the given RACW type.
118
119   ---------------------------------------
120   -- Check_Categorization_Dependencies --
121   ---------------------------------------
122
123   procedure Check_Categorization_Dependencies
124     (Unit_Entity     : Entity_Id;
125      Depended_Entity : Entity_Id;
126      Info_Node       : Node_Id;
127      Is_Subunit      : Boolean)
128   is
129      N   : constant Node_Id := Info_Node;
130      Err : Boolean;
131
132      --  Here we define an enumeration type to represent categorization types,
133      --  ordered so that a unit with a given categorization can only WITH
134      --  units with lower or equal categorization type.
135
136      type Categorization is
137        (Pure,
138         Shared_Passive,
139         Remote_Types,
140         Remote_Call_Interface,
141         Normal);
142
143      function Get_Categorization (E : Entity_Id) return Categorization;
144      --  Check categorization flags from entity, and return in the form
145      --  of the lowest value of the Categorization type that applies to E.
146
147      ------------------------
148      -- Get_Categorization --
149      ------------------------
150
151      function Get_Categorization (E : Entity_Id) return Categorization is
152      begin
153         --  Get the lowest categorization that corresponds to E. Note that
154         --  nothing prevents several (different) categorization pragmas
155         --  to apply to the same library unit, in which case the unit has
156         --  all associated categories, so we need to be careful here to
157         --  check pragmas in proper Categorization order in order to
158         --  return the lowest applicable value.
159
160         --  Ignore Pure specification if set by pragma Pure_Function
161
162         if Is_Pure (E)
163           and then not
164            (Has_Pragma_Pure_Function (E) and not Has_Pragma_Pure (E))
165         then
166            return Pure;
167
168         elsif Is_Shared_Passive (E) then
169            return Shared_Passive;
170
171         elsif Is_Remote_Types (E) then
172            return Remote_Types;
173
174         elsif Is_Remote_Call_Interface (E) then
175            return Remote_Call_Interface;
176
177         else
178            return Normal;
179         end if;
180      end Get_Categorization;
181
182      Unit_Category : Categorization;
183      With_Category : Categorization;
184
185   --  Start of processing for Check_Categorization_Dependencies
186
187   begin
188      --  Intrinsic subprograms are preelaborated, so do not impose any
189      --  categorization dependencies.
190
191      if Is_Intrinsic_Subprogram (Depended_Entity) then
192         return;
193      end if;
194
195      --  First check 10.2.1 (11/1) rules on preelaborate packages
196
197      if Is_Preelaborated (Unit_Entity)
198        and then not Is_Preelaborated (Depended_Entity)
199        and then not Is_Pure (Depended_Entity)
200      then
201         Err := True;
202      else
203         Err := False;
204      end if;
205
206      --  Check categorization rules of RM E.2(5)
207
208      Unit_Category := Get_Categorization (Unit_Entity);
209      With_Category := Get_Categorization (Depended_Entity);
210
211      if With_Category > Unit_Category then
212
213         --  Special case: Remote_Types and Remote_Call_Interface are allowed
214         --  to WITH anything in the package body, per (RM E.2(5)).
215
216         if (Unit_Category = Remote_Types
217              or else Unit_Category = Remote_Call_Interface)
218           and then In_Package_Body (Unit_Entity)
219         then
220            null;
221
222         --  Special case: Remote_Types and Remote_Call_Interface declarations
223         --  can depend on a preelaborated unit via a private with_clause, per
224         --  AI05-0206.
225
226         elsif (Unit_Category = Remote_Types
227                  or else
228                Unit_Category = Remote_Call_Interface)
229           and then Nkind (N) = N_With_Clause
230           and then Private_Present (N)
231           and then Is_Preelaborated (Depended_Entity)
232         then
233            null;
234
235         --  All other cases, we do have an error
236
237         else
238            Err := True;
239         end if;
240      end if;
241
242      --  Here if we have an error
243
244      if Err then
245
246         --  These messages are warnings in GNAT mode or if the -gnateP switch
247         --  was set. Otherwise these are real errors for real illegalities.
248
249         --  The reason we suppress these errors in GNAT mode is that the run-
250         --  time has several instances of violations of the categorization
251         --  errors (e.g. Pure units withing Preelaborate units. All these
252         --  violations are harmless in the cases where we intend them, and
253         --  we suppress the warnings with Warnings (Off). In cases where we
254         --  do not intend the violation, warnings are errors in GNAT mode
255         --  anyway, so we will still get an error.
256
257         Error_Msg_Warn :=
258           Treat_Categorization_Errors_As_Warnings or GNAT_Mode;
259
260         --  Don't give error if main unit is not an internal unit, and the
261         --  unit generating the message is an internal unit. This is the
262         --  situation in which such messages would be ignored in any case,
263         --  so it is convenient not to generate them (since it causes
264         --  annoying interference with debugging).
265
266         if Is_Internal_File_Name (Unit_File_Name (Current_Sem_Unit))
267           and then not Is_Internal_File_Name (Unit_File_Name (Main_Unit))
268         then
269            return;
270
271         --  Dependence of Remote_Types or Remote_Call_Interface declaration
272         --  on a preelaborated unit with a normal with_clause.
273
274         elsif (Unit_Category = Remote_Types
275                  or else
276                Unit_Category = Remote_Call_Interface)
277           and then Is_Preelaborated (Depended_Entity)
278         then
279            Error_Msg_NE
280              ("<must use private with clause for preelaborated unit& ",
281               N, Depended_Entity);
282
283         --  Subunit case
284
285         elsif Is_Subunit then
286            Error_Msg_NE
287              ("<subunit cannot depend on& " &
288               "(parent has wrong categorization)", N, Depended_Entity);
289
290         --  Normal unit, not subunit
291
292         else
293            Error_Msg_NE
294              ("<cannot depend on& " &
295               "(wrong categorization)", N, Depended_Entity);
296         end if;
297
298         --  Add further explanation for Pure/Preelaborate common cases
299
300         if Unit_Category = Pure then
301            Error_Msg_NE
302              ("\<pure unit cannot depend on non-pure unit",
303               N, Depended_Entity);
304
305         elsif Is_Preelaborated (Unit_Entity)
306           and then not Is_Preelaborated (Depended_Entity)
307           and then not Is_Pure (Depended_Entity)
308         then
309            Error_Msg_NE
310              ("\<preelaborated unit cannot depend on "
311               & "non-preelaborated unit",
312               N, Depended_Entity);
313         end if;
314      end if;
315   end Check_Categorization_Dependencies;
316
317   -----------------------------------
318   -- Check_Non_Static_Default_Expr --
319   -----------------------------------
320
321   procedure Check_Non_Static_Default_Expr
322     (Type_Def : Node_Id;
323      Obj_Decl : Node_Id)
324   is
325      Recdef         : Node_Id;
326      Component_Decl : Node_Id;
327
328   begin
329      if Nkind (Type_Def) = N_Derived_Type_Definition then
330         Recdef := Record_Extension_Part (Type_Def);
331
332         if No (Recdef) then
333            return;
334         end if;
335
336      else
337         Recdef := Type_Def;
338      end if;
339
340      --  Check that component declarations do not involve:
341
342      --    a. a non-static default expression, where the object is
343      --       declared to be default initialized.
344
345      --    b. a dynamic Itype (discriminants and constraints)
346
347      if Null_Present (Recdef) then
348         return;
349      else
350         Component_Decl := First (Component_Items (Component_List (Recdef)));
351      end if;
352
353      while Present (Component_Decl)
354        and then Nkind (Component_Decl) = N_Component_Declaration
355      loop
356         if Present (Expression (Component_Decl))
357           and then Nkind (Expression (Component_Decl)) /= N_Null
358           and then not Is_Static_Expression (Expression (Component_Decl))
359         then
360            Error_Msg_Sloc := Sloc (Component_Decl);
361            Error_Msg_F
362              ("object in preelaborated unit has non-static default#",
363               Obj_Decl);
364
365         --  Fix this later ???
366
367         --  elsif Has_Dynamic_Itype (Component_Decl) then
368         --     Error_Msg_N
369         --       ("dynamic type discriminant," &
370         --        " constraint in preelaborated unit",
371         --        Component_Decl);
372         end if;
373
374         Next (Component_Decl);
375      end loop;
376   end Check_Non_Static_Default_Expr;
377
378   ---------------------------
379   -- Has_Non_Remote_Access --
380   ---------------------------
381
382   function Has_Non_Remote_Access (Typ : Entity_Id) return Boolean is
383      Component : Entity_Id;
384      Comp_Type : Entity_Id;
385      U_Typ     : constant Entity_Id := Underlying_Type (Typ);
386
387   begin
388      if No (U_Typ) then
389         return False;
390
391      elsif Has_Read_Write_Attributes (Typ)
392        or else Has_Read_Write_Attributes (U_Typ)
393      then
394         return False;
395
396      elsif Is_Non_Remote_Access_Type (U_Typ) then
397         return True;
398      end if;
399
400      if Is_Record_Type (U_Typ) then
401         Component := First_Entity (U_Typ);
402         while Present (Component) loop
403            if not Is_Tag (Component) then
404               Comp_Type := Etype (Component);
405
406               if Has_Non_Remote_Access (Comp_Type) then
407                  return True;
408               end if;
409            end if;
410
411            Next_Entity (Component);
412         end loop;
413
414      elsif Is_Array_Type (U_Typ) then
415         return Has_Non_Remote_Access (Component_Type (U_Typ));
416
417      end if;
418
419      return False;
420   end Has_Non_Remote_Access;
421
422   -------------------------------
423   -- Has_Read_Write_Attributes --
424   -------------------------------
425
426   function Has_Read_Write_Attributes (E : Entity_Id) return Boolean is
427   begin
428      return True
429        and then Has_Stream_Attribute_Definition
430                   (E, TSS_Stream_Read,  At_Any_Place => True)
431        and then Has_Stream_Attribute_Definition
432                   (E, TSS_Stream_Write, At_Any_Place => True);
433   end Has_Read_Write_Attributes;
434
435   -------------------------------------
436   -- Has_Stream_Attribute_Definition --
437   -------------------------------------
438
439   function Has_Stream_Attribute_Definition
440     (Typ          : Entity_Id;
441      Nam          : TSS_Name_Type;
442      At_Any_Place : Boolean := False) return Boolean
443   is
444      Rep_Item  : Node_Id;
445      Full_Type : Entity_Id := Typ;
446
447   begin
448      --  In the case of a type derived from a private view, any specified
449      --  stream attributes will be attached to the derived type's underlying
450      --  type rather the derived type entity itself (which is itself private).
451
452      if Is_Private_Type (Typ)
453        and then Is_Derived_Type (Typ)
454        and then Present (Full_View (Typ))
455      then
456         Full_Type := Underlying_Type (Typ);
457      end if;
458
459      --  We start from the declaration node and then loop until the end of
460      --  the list until we find the requested attribute definition clause.
461      --  In Ada 2005 mode, clauses are ignored if they are not currently
462      --  visible (this is tested using the corresponding Entity, which is
463      --  inserted by the expander at the point where the clause occurs),
464      --  unless At_Any_Place is true.
465
466      Rep_Item := First_Rep_Item (Full_Type);
467      while Present (Rep_Item) loop
468         if Nkind (Rep_Item) = N_Attribute_Definition_Clause then
469            case Chars (Rep_Item) is
470               when Name_Read =>
471                  exit when Nam = TSS_Stream_Read;
472
473               when Name_Write =>
474                  exit when Nam = TSS_Stream_Write;
475
476               when Name_Input =>
477                  exit when Nam = TSS_Stream_Input;
478
479               when Name_Output =>
480                  exit when Nam = TSS_Stream_Output;
481
482               when others =>
483                  null;
484
485            end case;
486         end if;
487
488         Next_Rep_Item (Rep_Item);
489      end loop;
490
491      --  If At_Any_Place is true, return True if the attribute is available
492      --  at any place; if it is false, return True only if the attribute is
493      --  currently visible.
494
495      return Present (Rep_Item)
496        and then (Ada_Version < Ada_2005
497                   or else At_Any_Place
498                   or else not Is_Hidden (Entity (Rep_Item)));
499   end Has_Stream_Attribute_Definition;
500
501   ---------------------------
502   -- In_Preelaborated_Unit --
503   ---------------------------
504
505   function In_Preelaborated_Unit return Boolean is
506      Unit_Entity : Entity_Id := Current_Scope;
507      Unit_Kind   : constant Node_Kind :=
508                      Nkind (Unit (Cunit (Current_Sem_Unit)));
509
510   begin
511      --  If evaluating actuals for a child unit instantiation, then ignore
512      --  the preelaboration status of the parent; use the child instead.
513
514      if Is_Compilation_Unit (Unit_Entity)
515        and then Unit_Kind in N_Generic_Instantiation
516        and then not In_Same_Source_Unit (Unit_Entity,
517                                          Cunit (Current_Sem_Unit))
518      then
519         Unit_Entity := Cunit_Entity (Current_Sem_Unit);
520      end if;
521
522      --  There are no constraints on the body of Remote_Call_Interface or
523      --  Remote_Types packages.
524
525      return (Unit_Entity /= Standard_Standard)
526        and then (Is_Preelaborated (Unit_Entity)
527                    or else Is_Pure (Unit_Entity)
528                    or else Is_Shared_Passive (Unit_Entity)
529                    or else
530                      ((Is_Remote_Types (Unit_Entity)
531                          or else Is_Remote_Call_Interface (Unit_Entity))
532                         and then Ekind (Unit_Entity) = E_Package
533                         and then Unit_Kind /= N_Package_Body
534                         and then not In_Package_Body (Unit_Entity)
535                         and then not In_Instance));
536   end In_Preelaborated_Unit;
537
538   ------------------
539   -- In_Pure_Unit --
540   ------------------
541
542   function In_Pure_Unit return Boolean is
543   begin
544      return Is_Pure (Current_Scope);
545   end In_Pure_Unit;
546
547   ------------------------
548   -- In_RCI_Declaration --
549   ------------------------
550
551   function In_RCI_Declaration (N : Node_Id) return Boolean is
552      Unit_Entity : constant Entity_Id := Current_Scope;
553      Unit_Kind   : constant Node_Kind :=
554                      Nkind (Unit (Cunit (Current_Sem_Unit)));
555
556   begin
557      --  There are no restrictions on the private part or body
558      --  of an RCI unit.
559
560      return Is_Remote_Call_Interface (Unit_Entity)
561        and then Is_Package_Or_Generic_Package (Unit_Entity)
562        and then Unit_Kind /= N_Package_Body
563        and then List_Containing (N) =
564                   Visible_Declarations
565                     (Specification (Unit_Declaration_Node (Unit_Entity)))
566        and then not In_Package_Body (Unit_Entity)
567        and then not In_Instance;
568
569      --  What about the case of a nested package in the visible part???
570      --  This case is missed by the List_Containing check above???
571   end In_RCI_Declaration;
572
573   -----------------------
574   -- In_RT_Declaration --
575   -----------------------
576
577   function In_RT_Declaration return Boolean is
578      Unit_Entity : constant Entity_Id := Current_Scope;
579      Unit_Kind   : constant Node_Kind :=
580                      Nkind (Unit (Cunit (Current_Sem_Unit)));
581
582   begin
583      --  There are no restrictions on the body of a Remote Types unit
584
585      return Is_Remote_Types (Unit_Entity)
586        and then Is_Package_Or_Generic_Package (Unit_Entity)
587        and then Unit_Kind /= N_Package_Body
588        and then not In_Package_Body (Unit_Entity)
589        and then not In_Instance;
590   end In_RT_Declaration;
591
592   ----------------------------
593   -- In_Shared_Passive_Unit --
594   ----------------------------
595
596   function In_Shared_Passive_Unit return Boolean is
597      Unit_Entity : constant Entity_Id := Current_Scope;
598
599   begin
600      return Is_Shared_Passive (Unit_Entity);
601   end In_Shared_Passive_Unit;
602
603   ---------------------------------------
604   -- In_Subprogram_Task_Protected_Unit --
605   ---------------------------------------
606
607   function In_Subprogram_Task_Protected_Unit return Boolean is
608      E : Entity_Id;
609
610   begin
611      --  The following is to verify that a declaration is inside
612      --  subprogram, generic subprogram, task unit, protected unit.
613      --  Used to validate if a lib. unit is Pure. RM 10.2.1(16).
614
615      --  Use scope chain to check successively outer scopes
616
617      E := Current_Scope;
618      loop
619         if Is_Subprogram (E)
620              or else
621            Is_Generic_Subprogram (E)
622              or else
623            Is_Concurrent_Type (E)
624         then
625            return True;
626
627         elsif E = Standard_Standard then
628            return False;
629         end if;
630
631         E := Scope (E);
632      end loop;
633   end In_Subprogram_Task_Protected_Unit;
634
635   -------------------------------
636   -- Is_Non_Remote_Access_Type --
637   -------------------------------
638
639   function Is_Non_Remote_Access_Type (E : Entity_Id) return Boolean is
640      U_E : constant Entity_Id := Underlying_Type (E);
641   begin
642      if No (U_E) then
643
644         --  This case arises for the case of a generic formal type, in which
645         --  case E.2.2(8) rules will be enforced at instantiation time.
646
647         return False;
648      end if;
649
650      return Is_Access_Type (U_E)
651        and then not Is_Remote_Access_To_Class_Wide_Type (U_E)
652        and then not Is_Remote_Access_To_Subprogram_Type (U_E);
653   end Is_Non_Remote_Access_Type;
654
655   ---------------------------
656   -- No_External_Streaming --
657   ---------------------------
658
659   function No_External_Streaming (E : Entity_Id) return Boolean is
660      U_E : constant Entity_Id := Underlying_Type (E);
661
662   begin
663      if No (U_E) then
664         return False;
665
666      elsif Has_Read_Write_Attributes (E) then
667
668         --  Note: availability of stream attributes is tested on E, not U_E.
669         --  There may be stream attributes defined on U_E that are not visible
670         --  at the place where support of external streaming is tested.
671
672         return False;
673
674      elsif Has_Non_Remote_Access (U_E) then
675         return True;
676      end if;
677
678      return Is_Limited_Type (E);
679   end No_External_Streaming;
680
681   -------------------------------------
682   -- Set_Categorization_From_Pragmas --
683   -------------------------------------
684
685   procedure Set_Categorization_From_Pragmas (N : Node_Id) is
686      P   : constant Node_Id := Parent (N);
687      S   : constant Entity_Id := Current_Scope;
688
689      procedure Set_Parents (Visibility : Boolean);
690         --  If this is a child instance, the parents are not immediately
691         --  visible during analysis. Make them momentarily visible so that
692         --  the argument of the pragma can be resolved properly, and reset
693         --  afterwards.
694
695      -----------------
696      -- Set_Parents --
697      -----------------
698
699      procedure Set_Parents (Visibility : Boolean) is
700         Par : Entity_Id;
701      begin
702         Par := Scope (S);
703         while Present (Par) and then Par /= Standard_Standard loop
704            Set_Is_Immediately_Visible (Par, Visibility);
705            Par := Scope (Par);
706         end loop;
707      end Set_Parents;
708
709   --  Start of processing for Set_Categorization_From_Pragmas
710
711   begin
712      --  Deal with categorization pragmas in Pragmas of Compilation_Unit.
713      --  The purpose is to set categorization flags before analyzing the
714      --  unit itself, so as to diagnose violations of categorization as
715      --  we process each declaration, even though the pragma appears after
716      --  the unit.
717
718      if Nkind (P) /= N_Compilation_Unit then
719         return;
720      end if;
721
722      declare
723         PN : Node_Id;
724
725      begin
726         if Is_Child_Unit (S) and then Is_Generic_Instance (S) then
727            Set_Parents (True);
728         end if;
729
730         PN := First (Pragmas_After (Aux_Decls_Node (P)));
731         while Present (PN) loop
732
733            --  Skip implicit types that may have been introduced by
734            --  previous analysis.
735
736            if Nkind (PN) = N_Pragma then
737               case Get_Pragma_Id (PN) is
738                  when Pragma_All_Calls_Remote   |
739                    Pragma_Preelaborate          |
740                    Pragma_Pure                  |
741                    Pragma_Remote_Call_Interface |
742                    Pragma_Remote_Types          |
743                    Pragma_Shared_Passive        => Analyze (PN);
744                  when others                    => null;
745               end case;
746            end if;
747
748            Next (PN);
749         end loop;
750
751         if Is_Child_Unit (S) and then Is_Generic_Instance (S) then
752            Set_Parents (False);
753         end if;
754      end;
755   end Set_Categorization_From_Pragmas;
756
757   -----------------------------------
758   -- Set_Categorization_From_Scope --
759   -----------------------------------
760
761   procedure Set_Categorization_From_Scope (E : Entity_Id; Scop : Entity_Id) is
762      Declaration   : Node_Id := Empty;
763      Specification : Node_Id := Empty;
764
765   begin
766      Set_Is_Pure
767        (E, Is_Pure (Scop) and then Is_Library_Level_Entity (E));
768
769      if not Is_Remote_Call_Interface (E) then
770         if Ekind (E) in Subprogram_Kind then
771            Declaration := Unit_Declaration_Node (E);
772
773            if Nkind_In (Declaration, N_Subprogram_Body,
774                                      N_Subprogram_Renaming_Declaration)
775            then
776               Specification := Corresponding_Spec (Declaration);
777            end if;
778         end if;
779
780         --  A subprogram body or renaming-as-body is a remote call interface
781         --  if it serves as the completion of a subprogram declaration that
782         --  is a remote call interface.
783
784         if Nkind (Specification) in N_Entity then
785            Set_Is_Remote_Call_Interface
786              (E, Is_Remote_Call_Interface (Specification));
787
788         --  A subprogram declaration is a remote call interface when it is
789         --  declared within the visible part of, or declared by, a library
790         --  unit declaration that is a remote call interface.
791
792         else
793            Set_Is_Remote_Call_Interface
794              (E, Is_Remote_Call_Interface (Scop)
795                    and then not (In_Private_Part (Scop)
796                                   or else In_Package_Body (Scop)));
797         end if;
798      end if;
799
800      Set_Is_Remote_Types
801        (E, Is_Remote_Types (Scop)
802              and then not (In_Private_Part (Scop)
803                             or else In_Package_Body (Scop)));
804   end Set_Categorization_From_Scope;
805
806   ------------------------------
807   -- Static_Discriminant_Expr --
808   ------------------------------
809
810   --  We need to accommodate a Why_Not_Static call somehow here ???
811
812   function Static_Discriminant_Expr (L : List_Id) return Boolean is
813      Discriminant_Spec : Node_Id;
814
815   begin
816      Discriminant_Spec := First (L);
817      while Present (Discriminant_Spec) loop
818         if Present (Expression (Discriminant_Spec))
819           and then not Is_Static_Expression (Expression (Discriminant_Spec))
820         then
821            return False;
822         end if;
823
824         Next (Discriminant_Spec);
825      end loop;
826
827      return True;
828   end Static_Discriminant_Expr;
829
830   --------------------------------------
831   -- Validate_Access_Type_Declaration --
832   --------------------------------------
833
834   procedure Validate_Access_Type_Declaration (T : Entity_Id; N : Node_Id) is
835      Def : constant Node_Id := Type_Definition (N);
836
837   begin
838      case Nkind (Def) is
839
840         --  Access to subprogram case
841
842         when N_Access_To_Subprogram_Definition =>
843
844            --  A pure library_item must not contain the declaration of a
845            --  named access type, except within a subprogram, generic
846            --  subprogram, task unit, or protected unit (RM 10.2.1(16)).
847
848            --  This test is skipped in Ada 2005 (see AI-366)
849
850            if Ada_Version < Ada_2005
851              and then Comes_From_Source (T)
852              and then In_Pure_Unit
853              and then not In_Subprogram_Task_Protected_Unit
854            then
855               Error_Msg_N ("named access type not allowed in pure unit", T);
856            end if;
857
858         --  Access to object case
859
860         when N_Access_To_Object_Definition =>
861            if Comes_From_Source (T)
862              and then In_Pure_Unit
863              and then not In_Subprogram_Task_Protected_Unit
864            then
865               --  We can't give the message yet, since the type is not frozen
866               --  and in Ada 2005 mode, access types are allowed in pure units
867               --  if the type has no storage pool (see AI-366). So we set a
868               --  flag which will be checked at freeze time.
869
870               Set_Is_Pure_Unit_Access_Type (T);
871            end if;
872
873            --  Check for RCI or RT unit type declaration: declaration of an
874            --  access-to-object type is illegal unless it is a general access
875            --  type that designates a class-wide limited private type.
876            --  Note that constraints on the primitive subprograms of the
877            --  designated tagged type are not enforced here but in
878            --  Validate_RACW_Primitives, which is done separately because the
879            --  designated type might not be frozen (and therefore its
880            --  primitive operations might not be completely known) at the
881            --  point of the RACW declaration.
882
883            Validate_Remote_Access_Object_Type_Declaration (T);
884
885            --  Check for shared passive unit type declaration. It should
886            --  not contain the declaration of access to class wide type,
887            --  access to task type and access to protected type with entry.
888
889            Validate_SP_Access_Object_Type_Decl (T);
890
891         when others =>
892            null;
893      end case;
894
895      --  Set categorization flag from package on entity as well, to allow
896      --  easy checks later on for required validations of RCI or RT units.
897      --  This is only done for entities that are in the original source.
898
899      if Comes_From_Source (T)
900        and then not (In_Package_Body (Scope (T))
901                       or else In_Private_Part (Scope (T)))
902      then
903         Set_Is_Remote_Call_Interface
904           (T, Is_Remote_Call_Interface (Scope (T)));
905         Set_Is_Remote_Types
906           (T, Is_Remote_Types (Scope (T)));
907      end if;
908   end Validate_Access_Type_Declaration;
909
910   ----------------------------
911   -- Validate_Ancestor_Part --
912   ----------------------------
913
914   procedure Validate_Ancestor_Part (N : Node_Id) is
915      A : constant Node_Id   := Ancestor_Part (N);
916      T : constant Entity_Id := Entity (A);
917
918   begin
919      if In_Preelaborated_Unit
920        and then not In_Subprogram_Or_Concurrent_Unit
921        and then (not Inside_A_Generic
922                   or else Present (Enclosing_Generic_Body (N)))
923      then
924         --  If the type is private, it must have the Ada 2005 pragma
925         --  Has_Preelaborable_Initialization.
926
927         --  The check is omitted within predefined units. This is probably
928         --  obsolete code to fix the Ada 95 weakness in this area ???
929
930         if Is_Private_Type (T)
931           and then not Has_Pragma_Preelab_Init (T)
932           and then not Is_Internal_File_Name
933                          (Unit_File_Name (Get_Source_Unit (N)))
934         then
935            Error_Msg_N
936              ("private ancestor type not allowed in preelaborated unit", A);
937
938         elsif Is_Record_Type (T) then
939            if Nkind (Parent (T)) = N_Full_Type_Declaration then
940               Check_Non_Static_Default_Expr
941                 (Type_Definition (Parent (T)), A);
942            end if;
943         end if;
944      end if;
945   end Validate_Ancestor_Part;
946
947   ----------------------------------------
948   -- Validate_Categorization_Dependency --
949   ----------------------------------------
950
951   procedure Validate_Categorization_Dependency
952     (N : Node_Id;
953      E : Entity_Id)
954   is
955      K          : constant Node_Kind := Nkind (N);
956      P          : Node_Id            := Parent (N);
957      U          : Entity_Id := E;
958      Is_Subunit : constant Boolean := Nkind (P) = N_Subunit;
959
960   begin
961      --  Only validate library units and subunits. For subunits, checks
962      --  concerning withed units apply to the parent compilation unit.
963
964      if Is_Subunit then
965         P := Parent (P);
966         U := Scope (E);
967
968         while Present (U)
969           and then not Is_Compilation_Unit (U)
970           and then not Is_Child_Unit (U)
971         loop
972            U := Scope (U);
973         end loop;
974      end if;
975
976      if Nkind (P) /= N_Compilation_Unit then
977         return;
978      end if;
979
980      --  Body of RCI unit does not need validation
981
982      if Is_Remote_Call_Interface (E)
983        and then Nkind_In (N, N_Package_Body, N_Subprogram_Body)
984      then
985         return;
986      end if;
987
988      --  Ada 2005 (AI-50217): Process explicit non-limited with_clauses
989
990      declare
991         Item             : Node_Id;
992         Entity_Of_Withed : Entity_Id;
993
994      begin
995         Item := First (Context_Items (P));
996         while Present (Item) loop
997            if Nkind (Item) = N_With_Clause
998              and then not (Implicit_With (Item)
999                             or else Limited_Present (Item)
1000
1001                             --  Skip if error already posted on the WITH
1002                             --  clause (in which case the Name attribute
1003                             --  may be invalid). In particular, this fixes
1004                             --  the problem of hanging in the presence of a
1005                             --  WITH clause on a child that is an illegal
1006                             --  generic instantiation.
1007
1008                             or else Error_Posted (Item))
1009            then
1010               Entity_Of_Withed := Entity (Name (Item));
1011               Check_Categorization_Dependencies
1012                 (U, Entity_Of_Withed, Item, Is_Subunit);
1013            end if;
1014
1015            Next (Item);
1016         end loop;
1017      end;
1018
1019      --  Child depends on parent; therefore parent should also be categorized
1020      --  and satisfy the dependency hierarchy.
1021
1022      --  Check if N is a child spec
1023
1024      if (K in N_Generic_Declaration              or else
1025          K in N_Generic_Instantiation            or else
1026          K in N_Generic_Renaming_Declaration     or else
1027          K =  N_Package_Declaration              or else
1028          K =  N_Package_Renaming_Declaration     or else
1029          K =  N_Subprogram_Declaration           or else
1030          K =  N_Subprogram_Renaming_Declaration)
1031        and then Present (Parent_Spec (N))
1032      then
1033         Check_Categorization_Dependencies (E, Scope (E), N, False);
1034
1035         --  Verify that public child of an RCI library unit must also be an
1036         --  RCI library unit (RM E.2.3(15)).
1037
1038         if Is_Remote_Call_Interface (Scope (E))
1039           and then not Private_Present (P)
1040           and then not Is_Remote_Call_Interface (E)
1041         then
1042            Error_Msg_N ("public child of rci unit must also be rci unit", N);
1043         end if;
1044      end if;
1045   end Validate_Categorization_Dependency;
1046
1047   --------------------------------
1048   -- Validate_Controlled_Object --
1049   --------------------------------
1050
1051   procedure Validate_Controlled_Object (E : Entity_Id) is
1052   begin
1053      --  Don't need this check in Ada 2005 mode, where this is all taken
1054      --  care of by the mechanism for Preelaborable Initialization.
1055
1056      if Ada_Version >= Ada_2005 then
1057         return;
1058      end if;
1059
1060      --  For now, never apply this check for internal GNAT units, since we
1061      --  have a number of cases in the library where we are stuck with objects
1062      --  of this type, and the RM requires Preelaborate.
1063
1064      --  For similar reasons, we only do this check for source entities, since
1065      --  we generate entities of this type in some situations.
1066
1067      --  Note that the 10.2.1(9) restrictions are not relevant to us anyway.
1068      --  We have to enforce them for RM compatibility, but we have no trouble
1069      --  accepting these objects and doing the right thing. Note that there is
1070      --  no requirement that Preelaborate not actually generate any code!
1071
1072      if In_Preelaborated_Unit
1073        and then not Debug_Flag_PP
1074        and then Comes_From_Source (E)
1075        and then not
1076          Is_Internal_File_Name (Unit_File_Name (Get_Source_Unit (E)))
1077        and then (not Inside_A_Generic
1078                   or else Present (Enclosing_Generic_Body (E)))
1079        and then not Is_Protected_Type (Etype (E))
1080      then
1081         Error_Msg_N
1082           ("library level controlled object not allowed in " &
1083            "preelaborated unit", E);
1084      end if;
1085   end Validate_Controlled_Object;
1086
1087   --------------------------------------
1088   -- Validate_Null_Statement_Sequence --
1089   --------------------------------------
1090
1091   procedure Validate_Null_Statement_Sequence (N : Node_Id) is
1092      Item : Node_Id;
1093
1094   begin
1095      if In_Preelaborated_Unit then
1096         Item := First (Statements (Handled_Statement_Sequence (N)));
1097         while Present (Item) loop
1098            if Nkind (Item) /= N_Label
1099              and then Nkind (Item) /= N_Null_Statement
1100            then
1101               --  In GNAT mode, this is a warning, allowing the run-time
1102               --  to judiciously bypass this error condition.
1103
1104               Error_Msg_Warn := GNAT_Mode;
1105               Error_Msg_N
1106                 ("<statements not allowed in preelaborated unit", Item);
1107
1108               exit;
1109            end if;
1110
1111            Next (Item);
1112         end loop;
1113      end if;
1114   end Validate_Null_Statement_Sequence;
1115
1116   ---------------------------------
1117   -- Validate_Object_Declaration --
1118   ---------------------------------
1119
1120   procedure Validate_Object_Declaration (N : Node_Id) is
1121      Id  : constant Entity_Id  := Defining_Identifier (N);
1122      E   : constant Node_Id    := Expression (N);
1123      Odf : constant Node_Id    := Object_Definition (N);
1124      T   : constant Entity_Id  := Etype (Id);
1125
1126   begin
1127      --  Verify that any access to subprogram object does not have in its
1128      --  subprogram profile access type parameters or limited parameters
1129      --  without Read and Write attributes (E.2.3(13)).
1130
1131      Validate_RCI_Subprogram_Declaration (N);
1132
1133      --  Check that if we are in preelaborated elaboration code, then we
1134      --  do not have an instance of a default initialized private, task or
1135      --  protected object declaration which would violate (RM 10.2.1(9)).
1136      --  Note that constants are never default initialized (and the test
1137      --  below also filters out deferred constants). A variable is default
1138      --  initialized if it does *not* have an initialization expression.
1139
1140      --  Filter out cases that are not declaration of a variable from source
1141
1142      if Nkind (N) /= N_Object_Declaration
1143        or else Constant_Present (N)
1144        or else not Comes_From_Source (Id)
1145      then
1146         return;
1147      end if;
1148
1149      --  Exclude generic specs from the checks (this will get rechecked
1150      --  on instantiations).
1151
1152      if Inside_A_Generic and then No (Enclosing_Generic_Body (Id)) then
1153         return;
1154      end if;
1155
1156      --  Required checks for declaration that is in a preelaborated package
1157      --  and is not within some subprogram.
1158
1159      if In_Preelaborated_Unit
1160        and then not In_Subprogram_Or_Concurrent_Unit
1161      then
1162         --  Check for default initialized variable case. Note that in
1163         --  accordance with (RM B.1(24)) imported objects are not subject to
1164         --  default initialization.
1165         --  If the initialization does not come from source and is an
1166         --  aggregate, it is a static initialization that replaces an
1167         --  implicit call, and must be treated as such.
1168
1169         if Present (E)
1170           and then (Comes_From_Source (E) or else Nkind (E) /= N_Aggregate)
1171         then
1172            null;
1173
1174         elsif Is_Imported (Id) then
1175            null;
1176
1177         else
1178            declare
1179               Ent : Entity_Id := T;
1180
1181            begin
1182               --  An array whose component type is a record with nonstatic
1183               --  default expressions is a violation, so we get the array's
1184               --  component type.
1185
1186               if Is_Array_Type (Ent) then
1187                  declare
1188                     Comp_Type : Entity_Id;
1189
1190                  begin
1191                     Comp_Type := Component_Type (Ent);
1192                     while Is_Array_Type (Comp_Type) loop
1193                        Comp_Type := Component_Type (Comp_Type);
1194                     end loop;
1195
1196                     Ent := Comp_Type;
1197                  end;
1198               end if;
1199
1200               --  Object decl. that is of record type and has no default expr.
1201               --  should check if there is any non-static default expression
1202               --  in component decl. of the record type decl.
1203
1204               if Is_Record_Type (Ent) then
1205                  if Nkind (Parent (Ent)) = N_Full_Type_Declaration then
1206                     Check_Non_Static_Default_Expr
1207                       (Type_Definition (Parent (Ent)), N);
1208
1209                  elsif Nkind (Odf) = N_Subtype_Indication
1210                    and then not Is_Array_Type (T)
1211                    and then not Is_Private_Type (T)
1212                  then
1213                     Check_Non_Static_Default_Expr (Type_Definition
1214                       (Parent (Entity (Subtype_Mark (Odf)))), N);
1215                  end if;
1216               end if;
1217
1218               --  Check for invalid use of private object. Note that Ada 2005
1219               --  AI-161 modifies the rules for Ada 2005, including the use of
1220               --  the new pragma Preelaborable_Initialization.
1221
1222               if Is_Private_Type (Ent)
1223                 or else Depends_On_Private (Ent)
1224               then
1225                  --  Case where type has preelaborable initialization which
1226                  --  means that a pragma Preelaborable_Initialization was
1227                  --  given for the private type.
1228
1229                  if Has_Preelaborable_Initialization (Ent) then
1230
1231                     --  But for the predefined units, we will ignore this
1232                     --  status unless we are in Ada 2005 mode since we want
1233                     --  Ada 95 compatible behavior, in which the entities
1234                     --  marked with this pragma in the predefined library are
1235                     --  not treated specially.
1236
1237                     if Ada_Version < Ada_2005 then
1238                        Error_Msg_N
1239                          ("private object not allowed in preelaborated unit",
1240                           N);
1241                        Error_Msg_N ("\(would be legal in Ada 2005 mode)", N);
1242                     end if;
1243
1244                  --  Type does not have preelaborable initialization
1245
1246                  else
1247                     --  We allow this when compiling in GNAT mode to make life
1248                     --  easier for some cases where it would otherwise be hard
1249                     --  to be exactly valid Ada.
1250
1251                     if not GNAT_Mode then
1252                        Error_Msg_N
1253                          ("private object not allowed in preelaborated unit",
1254                           N);
1255
1256                        --  Add a message if it would help to provide a pragma
1257                        --  Preelaborable_Initialization on the type of the
1258                        --  object (which would make it legal in Ada 2005).
1259
1260                        --  If the type has no full view (generic type, or
1261                        --  previous error), the warning does not apply.
1262
1263                        if Is_Private_Type (Ent)
1264                          and then Present (Full_View (Ent))
1265                          and then
1266                            Has_Preelaborable_Initialization (Full_View (Ent))
1267                        then
1268                           Error_Msg_Sloc := Sloc (Ent);
1269
1270                           if Ada_Version >= Ada_2005 then
1271                              Error_Msg_NE
1272                                ("\would be legal if pragma Preelaborable_" &
1273                                 "Initialization given for & #", N, Ent);
1274                           else
1275                              Error_Msg_NE
1276                                ("\would be legal in Ada 2005 if pragma " &
1277                                 "Preelaborable_Initialization given for & #",
1278                                 N, Ent);
1279                           end if;
1280                        end if;
1281                     end if;
1282                  end if;
1283
1284               --  Access to Task or Protected type
1285
1286               elsif Is_Entity_Name (Odf)
1287                 and then Present (Etype (Odf))
1288                 and then Is_Access_Type (Etype (Odf))
1289               then
1290                  Ent := Designated_Type (Etype (Odf));
1291
1292               elsif Is_Entity_Name (Odf) then
1293                  Ent := Entity (Odf);
1294
1295               elsif Nkind (Odf) = N_Subtype_Indication then
1296                  Ent := Etype (Subtype_Mark (Odf));
1297
1298               elsif Nkind (Odf) = N_Constrained_Array_Definition then
1299                  Ent := Component_Type (T);
1300               end if;
1301
1302               if Is_Task_Type (Ent)
1303                 or else (Is_Protected_Type (Ent) and then Has_Entries (Ent))
1304               then
1305                  Error_Msg_N
1306                    ("concurrent object not allowed in preelaborated unit",
1307                     N);
1308                  return;
1309               end if;
1310            end;
1311         end if;
1312
1313         --  Non-static discriminants not allowed in preelaborated unit.
1314         --  Objects of a controlled type with a user-defined Initialize
1315         --  are forbidden as well.
1316
1317         if Is_Record_Type (Etype (Id)) then
1318            declare
1319               ET  : constant Entity_Id := Etype (Id);
1320               EE  : constant Entity_Id := Etype (Etype (Id));
1321               PEE : Node_Id;
1322
1323            begin
1324               if Has_Discriminants (ET) and then Present (EE) then
1325                  PEE := Parent (EE);
1326
1327                  if Nkind (PEE) = N_Full_Type_Declaration
1328                    and then not Static_Discriminant_Expr
1329                                   (Discriminant_Specifications (PEE))
1330                  then
1331                     Error_Msg_N
1332                       ("non-static discriminant in preelaborated unit",
1333                        PEE);
1334                  end if;
1335               end if;
1336
1337               --  For controlled type or type with controlled component, check
1338               --  preelaboration flag, as there may be a non-null Initialize
1339               --  primitive. For language versions earlier than Ada 2005,
1340               --  there is no notion of preelaborable initialization, and
1341               --  Validate_Controlled_Object is used to enforce rules for
1342               --  controlled objects.
1343
1344               if (Is_Controlled (ET) or else Has_Controlled_Component (ET))
1345                    and then Ada_Version >= Ada_2005
1346                    and then not Has_Preelaborable_Initialization (ET)
1347               then
1348                  Error_Msg_NE
1349                    ("controlled type& does not have"
1350                      & " preelaborable initialization", N, ET);
1351               end if;
1352            end;
1353
1354         end if;
1355      end if;
1356
1357      --  A pure library_item must not contain the declaration of any variable
1358      --  except within a subprogram, generic subprogram, task unit, or
1359      --  protected unit (RM 10.2.1(16)).
1360
1361      if In_Pure_Unit and then not In_Subprogram_Task_Protected_Unit then
1362         Error_Msg_N ("declaration of variable not allowed in pure unit", N);
1363
1364      --  The visible part of an RCI library unit must not contain the
1365      --  declaration of a variable (RM E.1.3(9))
1366
1367      elsif In_RCI_Declaration (N) then
1368         Error_Msg_N ("visible variable not allowed in 'R'C'I unit", N);
1369
1370      --  The visible part of a Shared Passive library unit must not contain
1371      --  the declaration of a variable (RM E.2.2(7))
1372
1373      elsif In_RT_Declaration and then not In_Private_Part (Id) then
1374         Error_Msg_N
1375           ("visible variable not allowed in remote types unit", N);
1376      end if;
1377
1378   end Validate_Object_Declaration;
1379
1380   -----------------------------
1381   -- Validate_RACW_Primitive --
1382   -----------------------------
1383
1384   procedure Validate_RACW_Primitive
1385     (Subp : Entity_Id;
1386      RACW : Entity_Id)
1387   is
1388      procedure Illegal_Remote_Subp (Msg : String; N : Node_Id);
1389      --  Diagnose illegality on N. If RACW is present, report the error on it
1390      --  rather than on N.
1391
1392      -------------------------
1393      -- Illegal_Remote_Subp --
1394      -------------------------
1395
1396      procedure Illegal_Remote_Subp (Msg : String; N : Node_Id) is
1397      begin
1398         if Present (RACW) then
1399            if not Error_Posted (RACW) then
1400               Error_Msg_N
1401                 ("illegal remote access to class-wide type&", RACW);
1402            end if;
1403
1404            Error_Msg_Sloc := Sloc (N);
1405            Error_Msg_NE ("\\" & Msg & " in primitive& #", RACW, Subp);
1406
1407         else
1408            Error_Msg_NE (Msg & " in remote subprogram&", N, Subp);
1409         end if;
1410      end Illegal_Remote_Subp;
1411
1412      Rtyp       : Entity_Id;
1413      Param      : Node_Id;
1414      Param_Spec : Node_Id;
1415      Param_Type : Entity_Id;
1416
1417   --  Start of processing for Validate_RACW_Primitive
1418
1419   begin
1420      --  Check return type
1421
1422      if Ekind (Subp) = E_Function then
1423         Rtyp := Etype (Subp);
1424
1425         --  AI05-0101 (Binding Interpretation): The result type of a remote
1426         --  function must either support external streaming or be a
1427         --  controlling access result type.
1428
1429         if Has_Controlling_Result (Subp) then
1430            null;
1431
1432         elsif Ekind (Rtyp) = E_Anonymous_Access_Type then
1433            Illegal_Remote_Subp ("anonymous access result", Rtyp);
1434
1435         elsif Is_Limited_Type (Rtyp) then
1436            if No (TSS (Rtyp, TSS_Stream_Read))
1437                 or else
1438               No (TSS (Rtyp, TSS_Stream_Write))
1439            then
1440               Illegal_Remote_Subp
1441                 ("limited return type must have Read and Write attributes",
1442                     Parent (Subp));
1443               Explain_Limited_Type (Rtyp, Parent (Subp));
1444            end if;
1445
1446         --  Check that the return type supports external streaming
1447
1448         elsif No_External_Streaming (Rtyp)
1449           and then not Error_Posted (Rtyp)
1450         then
1451            Illegal_Remote_Subp ("return type containing non-remote access "
1452              & "must have Read and Write attributes",
1453              Parent (Subp));
1454         end if;
1455      end if;
1456
1457      Param := First_Formal (Subp);
1458      while Present (Param) loop
1459
1460         --  Now find out if this parameter is a controlling parameter
1461
1462         Param_Spec := Parent (Param);
1463         Param_Type := Etype (Param);
1464
1465         if Is_Controlling_Formal (Param) then
1466
1467            --  It is a controlling parameter, so specific checks below do not
1468            --  apply.
1469
1470            null;
1471
1472         elsif Ekind_In (Param_Type, E_Anonymous_Access_Type,
1473                                     E_Anonymous_Access_Subprogram_Type)
1474         then
1475            --  From RM E.2.2(14), no anonymous access parameter other than
1476            --  controlling ones may be used (because an anonymous access
1477            --  type never supports external streaming).
1478
1479            Illegal_Remote_Subp
1480              ("non-controlling access parameter", Param_Spec);
1481
1482         elsif No_External_Streaming (Param_Type)
1483            and then not Error_Posted (Param_Type)
1484         then
1485            Illegal_Remote_Subp ("formal parameter in remote subprogram must "
1486              & "support external streaming", Param_Spec);
1487         end if;
1488
1489         --  Check next parameter in this subprogram
1490
1491         Next_Formal (Param);
1492      end loop;
1493   end Validate_RACW_Primitive;
1494
1495   ------------------------------
1496   -- Validate_RACW_Primitives --
1497   ------------------------------
1498
1499   procedure Validate_RACW_Primitives (T : Entity_Id) is
1500      Desig_Type             : Entity_Id;
1501      Primitive_Subprograms  : Elist_Id;
1502      Subprogram_Elmt        : Elmt_Id;
1503      Subprogram             : Entity_Id;
1504
1505   begin
1506      Desig_Type := Etype (Designated_Type (T));
1507
1508      --  No action needed for concurrent types
1509
1510      if Is_Concurrent_Type (Desig_Type) then
1511         return;
1512      end if;
1513
1514      Primitive_Subprograms := Primitive_Operations (Desig_Type);
1515
1516      Subprogram_Elmt := First_Elmt (Primitive_Subprograms);
1517      while Subprogram_Elmt /= No_Elmt loop
1518         Subprogram := Node (Subprogram_Elmt);
1519
1520         if Is_Predefined_Dispatching_Operation (Subprogram)
1521           or else Is_Hidden (Subprogram)
1522         then
1523            goto Next_Subprogram;
1524         end if;
1525
1526         Validate_RACW_Primitive (Subp => Subprogram, RACW => T);
1527
1528      <<Next_Subprogram>>
1529         Next_Elmt (Subprogram_Elmt);
1530      end loop;
1531   end Validate_RACW_Primitives;
1532
1533   -------------------------------
1534   -- Validate_RCI_Declarations --
1535   -------------------------------
1536
1537   procedure Validate_RCI_Declarations (P : Entity_Id) is
1538      E : Entity_Id;
1539
1540   begin
1541      E := First_Entity (P);
1542      while Present (E) loop
1543         if Comes_From_Source (E) then
1544            if Is_Limited_Type (E) then
1545               Error_Msg_N
1546                 ("limited type not allowed in rci unit", Parent (E));
1547               Explain_Limited_Type (E, Parent (E));
1548
1549            elsif Ekind_In (E, E_Generic_Function,
1550                               E_Generic_Package,
1551                               E_Generic_Procedure)
1552            then
1553               Error_Msg_N ("generic declaration not allowed in rci unit",
1554                 Parent (E));
1555
1556            elsif (Ekind (E) = E_Function or else Ekind (E) = E_Procedure)
1557              and then Has_Pragma_Inline (E)
1558            then
1559               Error_Msg_N
1560                 ("inlined subprogram not allowed in rci unit", Parent (E));
1561
1562            --  Inner packages that are renamings need not be checked. Generic
1563            --  RCI packages are subject to the checks, but entities that come
1564            --  from formal packages are not part of the visible declarations
1565            --  of the package and are not checked.
1566
1567            elsif Ekind (E) = E_Package then
1568               if Present (Renamed_Entity (E)) then
1569                  null;
1570
1571               elsif Ekind (P) /= E_Generic_Package
1572                 or else List_Containing (Unit_Declaration_Node (E)) /=
1573                           Generic_Formal_Declarations
1574                             (Unit_Declaration_Node (P))
1575               then
1576                  Validate_RCI_Declarations (E);
1577               end if;
1578            end if;
1579         end if;
1580
1581         Next_Entity (E);
1582      end loop;
1583   end Validate_RCI_Declarations;
1584
1585   -----------------------------------------
1586   -- Validate_RCI_Subprogram_Declaration --
1587   -----------------------------------------
1588
1589   procedure Validate_RCI_Subprogram_Declaration (N : Node_Id) is
1590      K               : constant Node_Kind := Nkind (N);
1591      Profile         : List_Id;
1592      Id              : Node_Id;
1593      Param_Spec      : Node_Id;
1594      Param_Type      : Entity_Id;
1595      Error_Node      : Node_Id := N;
1596
1597   begin
1598      --  This procedure enforces rules on subprogram and access to subprogram
1599      --  declarations in RCI units. These rules do not apply to expander
1600      --  generated routines, which are not remote subprograms. It is called:
1601
1602      --    1. from Analyze_Subprogram_Declaration.
1603      --    2. from Validate_Object_Declaration (access to subprogram).
1604
1605      if not (Comes_From_Source (N) and then In_RCI_Declaration (N)) then
1606         return;
1607      end if;
1608
1609      if K = N_Subprogram_Declaration then
1610         Id := Defining_Unit_Name (Specification (N));
1611         Profile := Parameter_Specifications (Specification (N));
1612
1613      else pragma Assert (K = N_Object_Declaration);
1614
1615         --  The above assertion is dubious, the visible declarations of an
1616         --  RCI unit never contain an object declaration, this should be an
1617         --  ACCESS-to-object declaration???
1618
1619         Id := Defining_Identifier (N);
1620
1621         if Nkind (Id) = N_Defining_Identifier
1622           and then Nkind (Parent (Etype (Id))) = N_Full_Type_Declaration
1623           and then Ekind (Etype (Id)) = E_Access_Subprogram_Type
1624         then
1625            Profile :=
1626              Parameter_Specifications (Type_Definition (Parent (Etype (Id))));
1627         else
1628            return;
1629         end if;
1630      end if;
1631
1632      --  Iterate through the parameter specification list, checking that
1633      --  no access parameter and no limited type parameter in the list.
1634      --  RM E.2.3(14).
1635
1636      if Present (Profile) then
1637         Param_Spec := First (Profile);
1638         while Present (Param_Spec) loop
1639            Param_Type := Etype (Defining_Identifier (Param_Spec));
1640
1641            if Ekind (Param_Type) = E_Anonymous_Access_Type then
1642               if K = N_Subprogram_Declaration then
1643                  Error_Node := Param_Spec;
1644               end if;
1645
1646               --  Report error only if declaration is in source program
1647
1648               if Comes_From_Source
1649                 (Defining_Entity (Specification (N)))
1650               then
1651                  Error_Msg_N
1652                    ("subprogram in 'R'C'I unit cannot have access parameter",
1653                      Error_Node);
1654               end if;
1655
1656            --  For a limited private type parameter, we check only the private
1657            --  declaration and ignore full type declaration, unless this is
1658            --  the only declaration for the type, e.g., as a limited record.
1659
1660            elsif No_External_Streaming (Param_Type) then
1661               if K = N_Subprogram_Declaration then
1662                  Error_Node := Param_Spec;
1663               end if;
1664
1665               Error_Msg_NE
1666                 ("formal of remote subprogram& "
1667                  & "must support external streaming",
1668                  Error_Node, Id);
1669               if Is_Limited_Type (Param_Type) then
1670                  Explain_Limited_Type (Param_Type, Error_Node);
1671               end if;
1672            end if;
1673
1674            Next (Param_Spec);
1675         end loop;
1676
1677         --  No check on return type???
1678      end if;
1679   end Validate_RCI_Subprogram_Declaration;
1680
1681   ----------------------------------------------------
1682   -- Validate_Remote_Access_Object_Type_Declaration --
1683   ----------------------------------------------------
1684
1685   procedure Validate_Remote_Access_Object_Type_Declaration (T : Entity_Id) is
1686      Direct_Designated_Type : Entity_Id;
1687      Desig_Type             : Entity_Id;
1688
1689   begin
1690      --  We are called from Analyze_Full_Type_Declaration, and the Nkind of
1691      --  the given node is N_Access_To_Object_Definition.
1692
1693      if not Comes_From_Source (T)
1694        or else (not In_RCI_Declaration (Parent (T))
1695                  and then not In_RT_Declaration)
1696      then
1697         return;
1698      end if;
1699
1700      --  An access definition in the private part of a Remote Types package
1701      --  may be legal if it has user-defined Read and Write attributes. This
1702      --  will be checked at the end of the package spec processing.
1703
1704      if In_RT_Declaration and then In_Private_Part (Scope (T)) then
1705         return;
1706      end if;
1707
1708      --  Check RCI or RT unit type declaration. It may not contain the
1709      --  declaration of an access-to-object type unless it is a general access
1710      --  type that designates a class-wide limited private type or subtype.
1711      --  There are also constraints on the primitive subprograms of the
1712      --  class-wide type (RM E.2.2(14), see Validate_RACW_Primitives).
1713
1714      if Ekind (T) /= E_General_Access_Type
1715        or else not Is_Class_Wide_Type (Designated_Type (T))
1716      then
1717         if In_RCI_Declaration (Parent (T)) then
1718            Error_Msg_N
1719              ("error in access type in Remote_Call_Interface unit", T);
1720         else
1721            Error_Msg_N
1722              ("error in access type in Remote_Types unit", T);
1723         end if;
1724
1725         Error_Msg_N ("\must be general access to class-wide type", T);
1726         return;
1727      end if;
1728
1729      Direct_Designated_Type := Designated_Type (T);
1730      Desig_Type := Etype (Direct_Designated_Type);
1731
1732      --  Why is this check not in Validate_Remote_Access_To_Class_Wide_Type???
1733
1734      if not Is_Valid_Remote_Object_Type (Desig_Type) then
1735         Error_Msg_N
1736           ("error in designated type of remote access to class-wide type", T);
1737         Error_Msg_N
1738           ("\must be tagged limited private or private extension", T);
1739         return;
1740      end if;
1741   end Validate_Remote_Access_Object_Type_Declaration;
1742
1743   -----------------------------------------------
1744   -- Validate_Remote_Access_To_Class_Wide_Type --
1745   -----------------------------------------------
1746
1747   procedure Validate_Remote_Access_To_Class_Wide_Type (N : Node_Id) is
1748      K  : constant Node_Kind := Nkind (N);
1749      PK : constant Node_Kind := Nkind (Parent (N));
1750      E  : Entity_Id;
1751
1752   begin
1753      --  This subprogram enforces the checks in (RM E.2.2(8)) for certain uses
1754      --  of class-wide limited private types.
1755
1756      --    Storage_Pool and Storage_Size are not defined for such types
1757      --
1758      --    The expected type of allocator must not be such a type.
1759
1760      --    The actual parameter of generic instantiation must not be such a
1761      --    type if the formal parameter is of an access type.
1762
1763      --  On entry, there are several cases:
1764
1765      --    1. called from sem_attr Analyze_Attribute where attribute name is
1766      --       either Storage_Pool or Storage_Size.
1767
1768      --    2. called from exp_ch4 Expand_N_Allocator
1769
1770      --    3. called from sem_ch4 Analyze_Explicit_Dereference
1771
1772      --    4. called from sem_res Resolve_Actuals
1773
1774      if K = N_Attribute_Reference then
1775         E := Etype (Prefix (N));
1776
1777         if Is_Remote_Access_To_Class_Wide_Type (E) then
1778            Error_Msg_N ("incorrect attribute of remote operand", N);
1779            return;
1780         end if;
1781
1782      elsif K = N_Allocator then
1783         E := Etype (N);
1784
1785         if Is_Remote_Access_To_Class_Wide_Type (E) then
1786            Error_Msg_N ("incorrect expected remote type of allocator", N);
1787            return;
1788         end if;
1789
1790      --  This subprogram also enforces the checks in E.2.2(13). A value of
1791      --  such type must not be dereferenced unless as controlling operand of
1792      --  a dispatching call. Explicit dereferences not coming from source are
1793      --  exempted from this checking because the expander produces them in
1794      --  some cases (such as for tag checks on dispatching calls with multiple
1795      --  controlling operands). However we do check in the case of an implicit
1796      --  dereference that is expanded to an explicit dereference (hence the
1797      --  test of whether Original_Node (N) comes from source).
1798
1799      elsif K = N_Explicit_Dereference
1800        and then Comes_From_Source (Original_Node (N))
1801      then
1802         E := Etype (Prefix (N));
1803
1804         --  If the class-wide type is not a remote one, the restrictions
1805         --  do not apply.
1806
1807         if not Is_Remote_Access_To_Class_Wide_Type (E) then
1808            return;
1809         end if;
1810
1811         --  If we have a true dereference that comes from source and that
1812         --  is a controlling argument for a dispatching call, accept it.
1813
1814         if Is_Actual_Parameter (N) and then Is_Controlling_Actual (N) then
1815            return;
1816         end if;
1817
1818         --  If we are just within a procedure or function call and the
1819         --  dereference has not been analyzed, return because this procedure
1820         --  will be called again from sem_res Resolve_Actuals. The same can
1821         --  apply in the case of dereference that is the prefix of a selected
1822         --  component, which can be a call given in prefixed form.
1823
1824         if (Is_Actual_Parameter (N) or else PK = N_Selected_Component)
1825           and then not Analyzed (N)
1826         then
1827            return;
1828         end if;
1829
1830         --  We must allow expanded code to generate a reference to the tag of
1831         --  the designated object (may be either the actual tag, or the stub
1832         --  tag in the case of a remote object).
1833
1834         if PK = N_Selected_Component
1835           and then Is_Tag (Entity (Selector_Name (Parent (N))))
1836         then
1837            return;
1838         end if;
1839
1840         Error_Msg_N
1841           ("invalid dereference of a remote access-to-class-wide value", N);
1842      end if;
1843   end Validate_Remote_Access_To_Class_Wide_Type;
1844
1845   ------------------------------------------
1846   -- Validate_Remote_Type_Type_Conversion --
1847   ------------------------------------------
1848
1849   procedure Validate_Remote_Type_Type_Conversion (N : Node_Id) is
1850      S : constant Entity_Id := Etype (N);
1851      E : constant Entity_Id := Etype (Expression (N));
1852
1853   begin
1854      --  This test is required in the case where a conversion appears inside a
1855      --  normal package, it does not necessarily have to be inside an RCI,
1856      --  Remote_Types unit (RM E.2.2(9,12)).
1857
1858      if Is_Remote_Access_To_Subprogram_Type (E)
1859        and then not Is_Remote_Access_To_Subprogram_Type (S)
1860      then
1861         Error_Msg_N
1862           ("incorrect conversion of remote operand to local type", N);
1863         return;
1864
1865      elsif not Is_Remote_Access_To_Subprogram_Type (E)
1866        and then Is_Remote_Access_To_Subprogram_Type (S)
1867      then
1868         Error_Msg_N
1869           ("incorrect conversion of local operand to remote type", N);
1870         return;
1871
1872      elsif Is_Remote_Access_To_Class_Wide_Type (E)
1873        and then not Is_Remote_Access_To_Class_Wide_Type (S)
1874      then
1875         Error_Msg_N
1876           ("incorrect conversion of remote operand to local type", N);
1877         return;
1878      end if;
1879
1880      --  If a local access type is converted into a RACW type, then the
1881      --  current unit has a pointer that may now be exported to another
1882      --  partition.
1883
1884      if Is_Remote_Access_To_Class_Wide_Type (S)
1885        and then not Is_Remote_Access_To_Class_Wide_Type (E)
1886      then
1887         Set_Has_RACW (Current_Sem_Unit);
1888      end if;
1889   end Validate_Remote_Type_Type_Conversion;
1890
1891   -------------------------------
1892   -- Validate_RT_RAT_Component --
1893   -------------------------------
1894
1895   procedure Validate_RT_RAT_Component (N : Node_Id) is
1896      Spec           : constant Node_Id   := Specification (N);
1897      Name_U         : constant Entity_Id := Defining_Entity (Spec);
1898      Typ            : Entity_Id;
1899      U_Typ          : Entity_Id;
1900      First_Priv_Ent : constant Entity_Id := First_Private_Entity (Name_U);
1901
1902      function Stream_Attributes_Available (Typ : Entity_Id) return Boolean;
1903      --  True if any stream attribute is available for Typ
1904
1905      ---------------------------------
1906      -- Stream_Attributes_Available --
1907      ---------------------------------
1908
1909      function Stream_Attributes_Available (Typ : Entity_Id) return Boolean
1910      is
1911      begin
1912         return Stream_Attribute_Available (Typ, TSS_Stream_Read)
1913                  or else
1914                Stream_Attribute_Available (Typ, TSS_Stream_Write)
1915                  or else
1916                Stream_Attribute_Available (Typ, TSS_Stream_Input)
1917                  or else
1918                Stream_Attribute_Available (Typ, TSS_Stream_Output);
1919      end Stream_Attributes_Available;
1920
1921   --  Start of processing for Validate_RT_RAT_Component
1922
1923   begin
1924      if not Is_Remote_Types (Name_U) then
1925         return;
1926      end if;
1927
1928      Typ := First_Entity (Name_U);
1929      while Present (Typ) and then Typ /= First_Priv_Ent loop
1930         U_Typ := Underlying_Type (Typ);
1931
1932         if No (U_Typ) then
1933            U_Typ := Typ;
1934         end if;
1935
1936         if Comes_From_Source (Typ) and then Is_Type (Typ) then
1937
1938            --  Check that the type can be meaningfully transmitted to another
1939            --  partition (E.2.2(8)).
1940
1941            if (Ada_Version < Ada_2005 and then Has_Non_Remote_Access (U_Typ))
1942                 or else (Stream_Attributes_Available (Typ)
1943                           and then No_External_Streaming (U_Typ))
1944            then
1945               if Is_Non_Remote_Access_Type (Typ) then
1946                  Error_Msg_N ("error in non-remote access type", U_Typ);
1947               else
1948                  Error_Msg_N
1949                    ("error in record type containing a component of a " &
1950                     "non-remote access type", U_Typ);
1951               end if;
1952
1953               if Ada_Version >= Ada_2005 then
1954                  Error_Msg_N
1955                    ("\must have visible Read and Write attribute " &
1956                     "definition clauses (RM E.2.2(8))", U_Typ);
1957               else
1958                  Error_Msg_N
1959                    ("\must have Read and Write attribute " &
1960                     "definition clauses (RM E.2.2(8))", U_Typ);
1961               end if;
1962            end if;
1963         end if;
1964
1965         Next_Entity (Typ);
1966      end loop;
1967   end Validate_RT_RAT_Component;
1968
1969   -----------------------------------------
1970   -- Validate_SP_Access_Object_Type_Decl --
1971   -----------------------------------------
1972
1973   procedure Validate_SP_Access_Object_Type_Decl (T : Entity_Id) is
1974      Direct_Designated_Type : Entity_Id;
1975
1976      function Has_Entry_Declarations (E : Entity_Id) return Boolean;
1977      --  Return true if the protected type designated by T has entry
1978      --  declarations.
1979
1980      ----------------------------
1981      -- Has_Entry_Declarations --
1982      ----------------------------
1983
1984      function Has_Entry_Declarations (E : Entity_Id) return Boolean is
1985         Ety : Entity_Id;
1986
1987      begin
1988         if Nkind (Parent (E)) = N_Protected_Type_Declaration then
1989            Ety := First_Entity (E);
1990            while Present (Ety) loop
1991               if Ekind (Ety) = E_Entry then
1992                  return True;
1993               end if;
1994
1995               Next_Entity (Ety);
1996            end loop;
1997         end if;
1998
1999         return False;
2000      end Has_Entry_Declarations;
2001
2002   --  Start of processing for Validate_SP_Access_Object_Type_Decl
2003
2004   begin
2005      --  We are called from Sem_Ch3.Analyze_Full_Type_Declaration, and the
2006      --  Nkind of the given entity is N_Access_To_Object_Definition.
2007
2008      if not Comes_From_Source (T)
2009        or else not In_Shared_Passive_Unit
2010        or else In_Subprogram_Task_Protected_Unit
2011      then
2012         return;
2013      end if;
2014
2015      --  Check Shared Passive unit. It should not contain the declaration
2016      --  of an access-to-object type whose designated type is a class-wide
2017      --  type, task type or protected type with entry (RM E.2.1(7)).
2018
2019      Direct_Designated_Type := Designated_Type (T);
2020
2021      if Ekind (Direct_Designated_Type) = E_Class_Wide_Type then
2022         Error_Msg_N
2023           ("invalid access-to-class-wide type in shared passive unit", T);
2024         return;
2025
2026      elsif Ekind (Direct_Designated_Type) in Task_Kind then
2027         Error_Msg_N
2028           ("invalid access-to-task type in shared passive unit", T);
2029         return;
2030
2031      elsif Ekind (Direct_Designated_Type) in Protected_Kind
2032        and then Has_Entry_Declarations (Direct_Designated_Type)
2033      then
2034         Error_Msg_N
2035           ("invalid access-to-protected type in shared passive unit", T);
2036         return;
2037      end if;
2038   end Validate_SP_Access_Object_Type_Decl;
2039
2040   ---------------------------------
2041   -- Validate_Static_Object_Name --
2042   ---------------------------------
2043
2044   procedure Validate_Static_Object_Name (N : Node_Id) is
2045      E : Entity_Id;
2046
2047      function Is_Primary (N : Node_Id) return Boolean;
2048      --  Determine whether node is syntactically a primary in an expression
2049      --  This function should probably be somewhere else ???
2050      --
2051      --  Also it does not do what it says, e.g if N is a binary operator
2052      --  whose parent is a binary operator, Is_Primary returns True ???
2053
2054      ----------------
2055      -- Is_Primary --
2056      ----------------
2057
2058      function Is_Primary (N : Node_Id) return Boolean is
2059         K : constant Node_Kind := Nkind (Parent (N));
2060
2061      begin
2062         case K is
2063            when N_Op | N_Membership_Test =>
2064               return True;
2065
2066            when N_Aggregate
2067               | N_Component_Association
2068               | N_Index_Or_Discriminant_Constraint =>
2069               return True;
2070
2071            when N_Attribute_Reference =>
2072               return Attribute_Name (Parent (N)) /= Name_Address
2073                 and then Attribute_Name (Parent (N)) /= Name_Access
2074                 and then Attribute_Name (Parent (N)) /= Name_Unchecked_Access
2075                 and then
2076                   Attribute_Name (Parent (N)) /= Name_Unrestricted_Access;
2077
2078            when N_Indexed_Component =>
2079               return (N /= Prefix (Parent (N))
2080                 or else Is_Primary (Parent (N)));
2081
2082            when N_Qualified_Expression | N_Type_Conversion =>
2083               return Is_Primary (Parent (N));
2084
2085            when N_Assignment_Statement | N_Object_Declaration =>
2086               return (N = Expression (Parent (N)));
2087
2088            when N_Selected_Component =>
2089               return Is_Primary (Parent (N));
2090
2091            when others =>
2092               return False;
2093         end case;
2094      end Is_Primary;
2095
2096   --  Start of processing for Validate_Static_Object_Name
2097
2098   begin
2099      if not In_Preelaborated_Unit
2100        or else not Comes_From_Source (N)
2101        or else In_Subprogram_Or_Concurrent_Unit
2102        or else Ekind (Current_Scope) = E_Block
2103      then
2104         return;
2105
2106      --  Filter out cases where primary is default in a component declaration,
2107      --  discriminant specification, or actual in a record type initialization
2108      --  call.
2109
2110      --  Initialization call of internal types
2111
2112      elsif Nkind (Parent (N)) = N_Procedure_Call_Statement then
2113
2114         if Present (Parent (Parent (N)))
2115           and then Nkind (Parent (Parent (N))) = N_Freeze_Entity
2116         then
2117            return;
2118         end if;
2119
2120         if Nkind (Name (Parent (N))) = N_Identifier
2121           and then not Comes_From_Source (Entity (Name (Parent (N))))
2122         then
2123            return;
2124         end if;
2125      end if;
2126
2127      --  Error if the name is a primary in an expression. The parent must not
2128      --  be an operator, or a selected component or an indexed component that
2129      --  is itself a primary. Entities that are actuals do not need to be
2130      --  checked, because the call itself will be diagnosed.
2131
2132      if Is_Primary (N)
2133        and then (not Inside_A_Generic
2134                   or else Present (Enclosing_Generic_Body (N)))
2135      then
2136         if Ekind (Entity (N)) = E_Variable
2137           or else Ekind (Entity (N)) in Formal_Object_Kind
2138         then
2139            Flag_Non_Static_Expr
2140              ("non-static object name in preelaborated unit", N);
2141
2142         --  Give an error for a reference to a nonstatic constant, unless the
2143         --  constant is in another GNAT library unit that is preelaborable.
2144
2145         elsif Ekind (Entity (N)) = E_Constant
2146           and then not Is_Static_Expression (N)
2147         then
2148            E := Entity (N);
2149
2150            if Is_Internal_File_Name (Unit_File_Name (Get_Source_Unit (N)))
2151              and then
2152                Enclosing_Comp_Unit_Node (N) /= Enclosing_Comp_Unit_Node (E)
2153              and then (Is_Preelaborated (Scope (E))
2154                         or else Is_Pure (Scope (E))
2155                         or else (Present (Renamed_Object (E))
2156                                   and then Is_Entity_Name (Renamed_Object (E))
2157                                   and then
2158                                     (Is_Preelaborated
2159                                       (Scope (Renamed_Object (E)))
2160                                         or else
2161                                           Is_Pure (Scope
2162                                             (Renamed_Object (E))))))
2163            then
2164               null;
2165
2166            --  This is the error case
2167
2168            else
2169               --  In GNAT mode, this is just a warning, to allow it to be
2170               --  judiciously turned off. Otherwise it is a real error.
2171
2172               if GNAT_Mode then
2173                  Error_Msg_N
2174                    ("??non-static constant in preelaborated unit", N);
2175               else
2176                  Flag_Non_Static_Expr
2177                    ("non-static constant in preelaborated unit", N);
2178               end if;
2179            end if;
2180         end if;
2181      end if;
2182   end Validate_Static_Object_Name;
2183
2184end Sem_Cat;
2185