gcc/ChangeLog:
[official-gcc.git] / gcc / ada / sem_util.adb
blob3b241bde58af3a3935e5a73b6481c214feb93b9e
1 ------------------------------------------------------------------------------
2 -- --
3 -- GNAT COMPILER COMPONENTS --
4 -- --
5 -- S E M _ U T I L --
6 -- --
7 -- B o d y --
8 -- --
9 -- Copyright (C) 1992-2016, Free Software Foundation, Inc. --
10 -- --
11 -- GNAT is free software; you can redistribute it and/or modify it under --
12 -- terms of the GNU General Public License as published by the Free Soft- --
13 -- ware Foundation; either version 3, or (at your option) any later ver- --
14 -- sion. GNAT is distributed in the hope that it will be useful, but WITH- --
15 -- OUT ANY WARRANTY; without even the implied warranty of MERCHANTABILITY --
16 -- or FITNESS FOR A PARTICULAR PURPOSE. See the GNU General Public License --
17 -- for more details. You should have received a copy of the GNU General --
18 -- Public License distributed with GNAT; see file COPYING3. If not, go to --
19 -- http://www.gnu.org/licenses for a complete copy of the license. --
20 -- --
21 -- GNAT was originally developed by the GNAT team at New York University. --
22 -- Extensive contributions were provided by Ada Core Technologies Inc. --
23 -- --
24 ------------------------------------------------------------------------------
26 with Treepr; -- ???For debugging code below
28 with Aspects; use Aspects;
29 with Atree; use Atree;
30 with Casing; use Casing;
31 with Checks; use Checks;
32 with Debug; use Debug;
33 with Elists; use Elists;
34 with Errout; use Errout;
35 with Exp_Ch11; use Exp_Ch11;
36 with Exp_Disp; use Exp_Disp;
37 with Exp_Util; use Exp_Util;
38 with Fname; use Fname;
39 with Freeze; use Freeze;
40 with Ghost; use Ghost;
41 with Lib; use Lib;
42 with Lib.Xref; use Lib.Xref;
43 with Namet.Sp; use Namet.Sp;
44 with Nlists; use Nlists;
45 with Nmake; use Nmake;
46 with Output; use Output;
47 with Restrict; use Restrict;
48 with Rident; use Rident;
49 with Rtsfind; use Rtsfind;
50 with Sem; use Sem;
51 with Sem_Aux; use Sem_Aux;
52 with Sem_Attr; use Sem_Attr;
53 with Sem_Ch6; use Sem_Ch6;
54 with Sem_Ch8; use Sem_Ch8;
55 with Sem_Ch13; use Sem_Ch13;
56 with Sem_Disp; use Sem_Disp;
57 with Sem_Eval; use Sem_Eval;
58 with Sem_Prag; use Sem_Prag;
59 with Sem_Res; use Sem_Res;
60 with Sem_Warn; use Sem_Warn;
61 with Sem_Type; use Sem_Type;
62 with Sinfo; use Sinfo;
63 with Sinput; use Sinput;
64 with Stand; use Stand;
65 with Style;
66 with Stringt; use Stringt;
67 with Targparm; use Targparm;
68 with Tbuild; use Tbuild;
69 with Ttypes; use Ttypes;
70 with Uname; use Uname;
72 with GNAT.HTable; use GNAT.HTable;
74 package body Sem_Util is
76 ----------------------------------------
77 -- Global Variables for New_Copy_Tree --
78 ----------------------------------------
80 -- These global variables are used by New_Copy_Tree. See description of the
81 -- body of this subprogram for details. Global variables can be safely used
82 -- by New_Copy_Tree, since there is no case of a recursive call from the
83 -- processing inside New_Copy_Tree.
85 NCT_Hash_Threshold : constant := 20;
86 -- If there are more than this number of pairs of entries in the map, then
87 -- Hash_Tables_Used will be set, and the hash tables will be initialized
88 -- and used for the searches.
90 NCT_Hash_Tables_Used : Boolean := False;
91 -- Set to True if hash tables are in use
93 NCT_Table_Entries : Nat := 0;
94 -- Count entries in table to see if threshold is reached
96 NCT_Hash_Table_Setup : Boolean := False;
97 -- Set to True if hash table contains data. We set this True if we setup
98 -- the hash table with data, and leave it set permanently from then on,
99 -- this is a signal that second and subsequent users of the hash table
100 -- must clear the old entries before reuse.
102 subtype NCT_Header_Num is Int range 0 .. 511;
103 -- Defines range of headers in hash tables (512 headers)
105 -----------------------
106 -- Local Subprograms --
107 -----------------------
109 function Build_Component_Subtype
110 (C : List_Id;
111 Loc : Source_Ptr;
112 T : Entity_Id) return Node_Id;
113 -- This function builds the subtype for Build_Actual_Subtype_Of_Component
114 -- and Build_Discriminal_Subtype_Of_Component. C is a list of constraints,
115 -- Loc is the source location, T is the original subtype.
117 function Has_Enabled_Property
118 (Item_Id : Entity_Id;
119 Property : Name_Id) return Boolean;
120 -- Subsidiary to routines Async_xxx_Enabled and Effective_xxx_Enabled.
121 -- Determine whether an abstract state or a variable denoted by entity
122 -- Item_Id has enabled property Property.
124 function Has_Null_Extension (T : Entity_Id) return Boolean;
125 -- T is a derived tagged type. Check whether the type extension is null.
126 -- If the parent type is fully initialized, T can be treated as such.
128 function Is_Fully_Initialized_Variant (Typ : Entity_Id) return Boolean;
129 -- Subsidiary to Is_Fully_Initialized_Type. For an unconstrained type
130 -- with discriminants whose default values are static, examine only the
131 -- components in the selected variant to determine whether all of them
132 -- have a default.
134 ------------------------------
135 -- Abstract_Interface_List --
136 ------------------------------
138 function Abstract_Interface_List (Typ : Entity_Id) return List_Id is
139 Nod : Node_Id;
141 begin
142 if Is_Concurrent_Type (Typ) then
144 -- If we are dealing with a synchronized subtype, go to the base
145 -- type, whose declaration has the interface list.
147 -- Shouldn't this be Declaration_Node???
149 Nod := Parent (Base_Type (Typ));
151 if Nkind (Nod) = N_Full_Type_Declaration then
152 return Empty_List;
153 end if;
155 elsif Ekind (Typ) = E_Record_Type_With_Private then
156 if Nkind (Parent (Typ)) = N_Full_Type_Declaration then
157 Nod := Type_Definition (Parent (Typ));
159 elsif Nkind (Parent (Typ)) = N_Private_Type_Declaration then
160 if Present (Full_View (Typ))
161 and then
162 Nkind (Parent (Full_View (Typ))) = N_Full_Type_Declaration
163 then
164 Nod := Type_Definition (Parent (Full_View (Typ)));
166 -- If the full-view is not available we cannot do anything else
167 -- here (the source has errors).
169 else
170 return Empty_List;
171 end if;
173 -- Support for generic formals with interfaces is still missing ???
175 elsif Nkind (Parent (Typ)) = N_Formal_Type_Declaration then
176 return Empty_List;
178 else
179 pragma Assert
180 (Nkind (Parent (Typ)) = N_Private_Extension_Declaration);
181 Nod := Parent (Typ);
182 end if;
184 elsif Ekind (Typ) = E_Record_Subtype then
185 Nod := Type_Definition (Parent (Etype (Typ)));
187 elsif Ekind (Typ) = E_Record_Subtype_With_Private then
189 -- Recurse, because parent may still be a private extension. Also
190 -- note that the full view of the subtype or the full view of its
191 -- base type may (both) be unavailable.
193 return Abstract_Interface_List (Etype (Typ));
195 else pragma Assert ((Ekind (Typ)) = E_Record_Type);
196 if Nkind (Parent (Typ)) = N_Formal_Type_Declaration then
197 Nod := Formal_Type_Definition (Parent (Typ));
198 else
199 Nod := Type_Definition (Parent (Typ));
200 end if;
201 end if;
203 return Interface_List (Nod);
204 end Abstract_Interface_List;
206 --------------------------------
207 -- Add_Access_Type_To_Process --
208 --------------------------------
210 procedure Add_Access_Type_To_Process (E : Entity_Id; A : Entity_Id) is
211 L : Elist_Id;
213 begin
214 Ensure_Freeze_Node (E);
215 L := Access_Types_To_Process (Freeze_Node (E));
217 if No (L) then
218 L := New_Elmt_List;
219 Set_Access_Types_To_Process (Freeze_Node (E), L);
220 end if;
222 Append_Elmt (A, L);
223 end Add_Access_Type_To_Process;
225 --------------------------
226 -- Add_Block_Identifier --
227 --------------------------
229 procedure Add_Block_Identifier (N : Node_Id; Id : out Entity_Id) is
230 Loc : constant Source_Ptr := Sloc (N);
232 begin
233 pragma Assert (Nkind (N) = N_Block_Statement);
235 -- The block already has a label, return its entity
237 if Present (Identifier (N)) then
238 Id := Entity (Identifier (N));
240 -- Create a new block label and set its attributes
242 else
243 Id := New_Internal_Entity (E_Block, Current_Scope, Loc, 'B');
244 Set_Etype (Id, Standard_Void_Type);
245 Set_Parent (Id, N);
247 Set_Identifier (N, New_Occurrence_Of (Id, Loc));
248 Set_Block_Node (Id, Identifier (N));
249 end if;
250 end Add_Block_Identifier;
252 ----------------------------
253 -- Add_Global_Declaration --
254 ----------------------------
256 procedure Add_Global_Declaration (N : Node_Id) is
257 Aux_Node : constant Node_Id := Aux_Decls_Node (Cunit (Current_Sem_Unit));
259 begin
260 if No (Declarations (Aux_Node)) then
261 Set_Declarations (Aux_Node, New_List);
262 end if;
264 Append_To (Declarations (Aux_Node), N);
265 Analyze (N);
266 end Add_Global_Declaration;
268 --------------------------------
269 -- Address_Integer_Convert_OK --
270 --------------------------------
272 function Address_Integer_Convert_OK (T1, T2 : Entity_Id) return Boolean is
273 begin
274 if Allow_Integer_Address
275 and then ((Is_Descendant_Of_Address (T1)
276 and then Is_Private_Type (T1)
277 and then Is_Integer_Type (T2))
278 or else
279 (Is_Descendant_Of_Address (T2)
280 and then Is_Private_Type (T2)
281 and then Is_Integer_Type (T1)))
282 then
283 return True;
284 else
285 return False;
286 end if;
287 end Address_Integer_Convert_OK;
289 -----------------
290 -- Addressable --
291 -----------------
293 -- For now, just 8/16/32/64
295 function Addressable (V : Uint) return Boolean is
296 begin
297 return V = Uint_8 or else
298 V = Uint_16 or else
299 V = Uint_32 or else
300 V = Uint_64;
301 end Addressable;
303 function Addressable (V : Int) return Boolean is
304 begin
305 return V = 8 or else
306 V = 16 or else
307 V = 32 or else
308 V = 64;
309 end Addressable;
311 ---------------------------------
312 -- Aggregate_Constraint_Checks --
313 ---------------------------------
315 procedure Aggregate_Constraint_Checks
316 (Exp : Node_Id;
317 Check_Typ : Entity_Id)
319 Exp_Typ : constant Entity_Id := Etype (Exp);
321 begin
322 if Raises_Constraint_Error (Exp) then
323 return;
324 end if;
326 -- Ada 2005 (AI-230): Generate a conversion to an anonymous access
327 -- component's type to force the appropriate accessibility checks.
329 -- Ada 2005 (AI-231): Generate conversion to the null-excluding type to
330 -- force the corresponding run-time check
332 if Is_Access_Type (Check_Typ)
333 and then Is_Local_Anonymous_Access (Check_Typ)
334 then
335 Rewrite (Exp, Convert_To (Check_Typ, Relocate_Node (Exp)));
336 Analyze_And_Resolve (Exp, Check_Typ);
337 Check_Unset_Reference (Exp);
338 end if;
340 -- What follows is really expansion activity, so check that expansion
341 -- is on and is allowed. In GNATprove mode, we also want check flags to
342 -- be added in the tree, so that the formal verification can rely on
343 -- those to be present. In GNATprove mode for formal verification, some
344 -- treatment typically only done during expansion needs to be performed
345 -- on the tree, but it should not be applied inside generics. Otherwise,
346 -- this breaks the name resolution mechanism for generic instances.
348 if not Expander_Active
349 and (Inside_A_Generic or not Full_Analysis or not GNATprove_Mode)
350 then
351 return;
352 end if;
354 if Is_Access_Type (Check_Typ)
355 and then Can_Never_Be_Null (Check_Typ)
356 and then not Can_Never_Be_Null (Exp_Typ)
357 then
358 Install_Null_Excluding_Check (Exp);
359 end if;
361 -- First check if we have to insert discriminant checks
363 if Has_Discriminants (Exp_Typ) then
364 Apply_Discriminant_Check (Exp, Check_Typ);
366 -- Next emit length checks for array aggregates
368 elsif Is_Array_Type (Exp_Typ) then
369 Apply_Length_Check (Exp, Check_Typ);
371 -- Finally emit scalar and string checks. If we are dealing with a
372 -- scalar literal we need to check by hand because the Etype of
373 -- literals is not necessarily correct.
375 elsif Is_Scalar_Type (Exp_Typ)
376 and then Compile_Time_Known_Value (Exp)
377 then
378 if Is_Out_Of_Range (Exp, Base_Type (Check_Typ)) then
379 Apply_Compile_Time_Constraint_Error
380 (Exp, "value not in range of}??", CE_Range_Check_Failed,
381 Ent => Base_Type (Check_Typ),
382 Typ => Base_Type (Check_Typ));
384 elsif Is_Out_Of_Range (Exp, Check_Typ) then
385 Apply_Compile_Time_Constraint_Error
386 (Exp, "value not in range of}??", CE_Range_Check_Failed,
387 Ent => Check_Typ,
388 Typ => Check_Typ);
390 elsif not Range_Checks_Suppressed (Check_Typ) then
391 Apply_Scalar_Range_Check (Exp, Check_Typ);
392 end if;
394 -- Verify that target type is also scalar, to prevent view anomalies
395 -- in instantiations.
397 elsif (Is_Scalar_Type (Exp_Typ)
398 or else Nkind (Exp) = N_String_Literal)
399 and then Is_Scalar_Type (Check_Typ)
400 and then Exp_Typ /= Check_Typ
401 then
402 if Is_Entity_Name (Exp)
403 and then Ekind (Entity (Exp)) = E_Constant
404 then
405 -- If expression is a constant, it is worthwhile checking whether
406 -- it is a bound of the type.
408 if (Is_Entity_Name (Type_Low_Bound (Check_Typ))
409 and then Entity (Exp) = Entity (Type_Low_Bound (Check_Typ)))
410 or else
411 (Is_Entity_Name (Type_High_Bound (Check_Typ))
412 and then Entity (Exp) = Entity (Type_High_Bound (Check_Typ)))
413 then
414 return;
416 else
417 Rewrite (Exp, Convert_To (Check_Typ, Relocate_Node (Exp)));
418 Analyze_And_Resolve (Exp, Check_Typ);
419 Check_Unset_Reference (Exp);
420 end if;
422 -- Could use a comment on this case ???
424 else
425 Rewrite (Exp, Convert_To (Check_Typ, Relocate_Node (Exp)));
426 Analyze_And_Resolve (Exp, Check_Typ);
427 Check_Unset_Reference (Exp);
428 end if;
430 end if;
431 end Aggregate_Constraint_Checks;
433 -----------------------
434 -- Alignment_In_Bits --
435 -----------------------
437 function Alignment_In_Bits (E : Entity_Id) return Uint is
438 begin
439 return Alignment (E) * System_Storage_Unit;
440 end Alignment_In_Bits;
442 --------------------------------------
443 -- All_Composite_Constraints_Static --
444 --------------------------------------
446 function All_Composite_Constraints_Static
447 (Constr : Node_Id) return Boolean
449 begin
450 if No (Constr) or else Error_Posted (Constr) then
451 return True;
452 end if;
454 case Nkind (Constr) is
455 when N_Subexpr =>
456 if Nkind (Constr) in N_Has_Entity
457 and then Present (Entity (Constr))
458 then
459 if Is_Type (Entity (Constr)) then
460 return
461 not Is_Discrete_Type (Entity (Constr))
462 or else Is_OK_Static_Subtype (Entity (Constr));
463 end if;
465 elsif Nkind (Constr) = N_Range then
466 return
467 Is_OK_Static_Expression (Low_Bound (Constr))
468 and then
469 Is_OK_Static_Expression (High_Bound (Constr));
471 elsif Nkind (Constr) = N_Attribute_Reference
472 and then Attribute_Name (Constr) = Name_Range
473 then
474 return
475 Is_OK_Static_Expression
476 (Type_Low_Bound (Etype (Prefix (Constr))))
477 and then
478 Is_OK_Static_Expression
479 (Type_High_Bound (Etype (Prefix (Constr))));
480 end if;
482 return
483 not Present (Etype (Constr)) -- previous error
484 or else not Is_Discrete_Type (Etype (Constr))
485 or else Is_OK_Static_Expression (Constr);
487 when N_Discriminant_Association =>
488 return All_Composite_Constraints_Static (Expression (Constr));
490 when N_Range_Constraint =>
491 return
492 All_Composite_Constraints_Static (Range_Expression (Constr));
494 when N_Index_Or_Discriminant_Constraint =>
495 declare
496 One_Cstr : Entity_Id;
497 begin
498 One_Cstr := First (Constraints (Constr));
499 while Present (One_Cstr) loop
500 if not All_Composite_Constraints_Static (One_Cstr) then
501 return False;
502 end if;
504 Next (One_Cstr);
505 end loop;
506 end;
508 return True;
510 when N_Subtype_Indication =>
511 return
512 All_Composite_Constraints_Static (Subtype_Mark (Constr))
513 and then
514 All_Composite_Constraints_Static (Constraint (Constr));
516 when others =>
517 raise Program_Error;
518 end case;
519 end All_Composite_Constraints_Static;
521 ---------------------------------
522 -- Append_Inherited_Subprogram --
523 ---------------------------------
525 procedure Append_Inherited_Subprogram (S : Entity_Id) is
526 Par : constant Entity_Id := Alias (S);
527 -- The parent subprogram
529 Scop : constant Entity_Id := Scope (Par);
530 -- The scope of definition of the parent subprogram
532 Typ : constant Entity_Id := Defining_Entity (Parent (S));
533 -- The derived type of which S is a primitive operation
535 Decl : Node_Id;
536 Next_E : Entity_Id;
538 begin
539 if Ekind (Current_Scope) = E_Package
540 and then In_Private_Part (Current_Scope)
541 and then Has_Private_Declaration (Typ)
542 and then Is_Tagged_Type (Typ)
543 and then Scop = Current_Scope
544 then
545 -- The inherited operation is available at the earliest place after
546 -- the derived type declaration ( RM 7.3.1 (6/1)). This is only
547 -- relevant for type extensions. If the parent operation appears
548 -- after the type extension, the operation is not visible.
550 Decl := First
551 (Visible_Declarations
552 (Package_Specification (Current_Scope)));
553 while Present (Decl) loop
554 if Nkind (Decl) = N_Private_Extension_Declaration
555 and then Defining_Entity (Decl) = Typ
556 then
557 if Sloc (Decl) > Sloc (Par) then
558 Next_E := Next_Entity (Par);
559 Set_Next_Entity (Par, S);
560 Set_Next_Entity (S, Next_E);
561 return;
563 else
564 exit;
565 end if;
566 end if;
568 Next (Decl);
569 end loop;
570 end if;
572 -- If partial view is not a type extension, or it appears before the
573 -- subprogram declaration, insert normally at end of entity list.
575 Append_Entity (S, Current_Scope);
576 end Append_Inherited_Subprogram;
578 -----------------------------------------
579 -- Apply_Compile_Time_Constraint_Error --
580 -----------------------------------------
582 procedure Apply_Compile_Time_Constraint_Error
583 (N : Node_Id;
584 Msg : String;
585 Reason : RT_Exception_Code;
586 Ent : Entity_Id := Empty;
587 Typ : Entity_Id := Empty;
588 Loc : Source_Ptr := No_Location;
589 Rep : Boolean := True;
590 Warn : Boolean := False)
592 Stat : constant Boolean := Is_Static_Expression (N);
593 R_Stat : constant Node_Id :=
594 Make_Raise_Constraint_Error (Sloc (N), Reason => Reason);
595 Rtyp : Entity_Id;
597 begin
598 if No (Typ) then
599 Rtyp := Etype (N);
600 else
601 Rtyp := Typ;
602 end if;
604 Discard_Node
605 (Compile_Time_Constraint_Error (N, Msg, Ent, Loc, Warn => Warn));
607 -- In GNATprove mode, do not replace the node with an exception raised.
608 -- In such a case, either the call to Compile_Time_Constraint_Error
609 -- issues an error which stops analysis, or it issues a warning in
610 -- a few cases where a suitable check flag is set for GNATprove to
611 -- generate a check message.
613 if not Rep or GNATprove_Mode then
614 return;
615 end if;
617 -- Now we replace the node by an N_Raise_Constraint_Error node
618 -- This does not need reanalyzing, so set it as analyzed now.
620 Rewrite (N, R_Stat);
621 Set_Analyzed (N, True);
623 Set_Etype (N, Rtyp);
624 Set_Raises_Constraint_Error (N);
626 -- Now deal with possible local raise handling
628 Possible_Local_Raise (N, Standard_Constraint_Error);
630 -- If the original expression was marked as static, the result is
631 -- still marked as static, but the Raises_Constraint_Error flag is
632 -- always set so that further static evaluation is not attempted.
634 if Stat then
635 Set_Is_Static_Expression (N);
636 end if;
637 end Apply_Compile_Time_Constraint_Error;
639 ---------------------------
640 -- Async_Readers_Enabled --
641 ---------------------------
643 function Async_Readers_Enabled (Id : Entity_Id) return Boolean is
644 begin
645 return Has_Enabled_Property (Id, Name_Async_Readers);
646 end Async_Readers_Enabled;
648 ---------------------------
649 -- Async_Writers_Enabled --
650 ---------------------------
652 function Async_Writers_Enabled (Id : Entity_Id) return Boolean is
653 begin
654 return Has_Enabled_Property (Id, Name_Async_Writers);
655 end Async_Writers_Enabled;
657 --------------------------------------
658 -- Available_Full_View_Of_Component --
659 --------------------------------------
661 function Available_Full_View_Of_Component (T : Entity_Id) return Boolean is
662 ST : constant Entity_Id := Scope (T);
663 SCT : constant Entity_Id := Scope (Component_Type (T));
664 begin
665 return In_Open_Scopes (ST)
666 and then In_Open_Scopes (SCT)
667 and then Scope_Depth (ST) >= Scope_Depth (SCT);
668 end Available_Full_View_Of_Component;
670 -------------------
671 -- Bad_Attribute --
672 -------------------
674 procedure Bad_Attribute
675 (N : Node_Id;
676 Nam : Name_Id;
677 Warn : Boolean := False)
679 begin
680 Error_Msg_Warn := Warn;
681 Error_Msg_N ("unrecognized attribute&<<", N);
683 -- Check for possible misspelling
685 Error_Msg_Name_1 := First_Attribute_Name;
686 while Error_Msg_Name_1 <= Last_Attribute_Name loop
687 if Is_Bad_Spelling_Of (Nam, Error_Msg_Name_1) then
688 Error_Msg_N -- CODEFIX
689 ("\possible misspelling of %<<", N);
690 exit;
691 end if;
693 Error_Msg_Name_1 := Error_Msg_Name_1 + 1;
694 end loop;
695 end Bad_Attribute;
697 --------------------------------
698 -- Bad_Predicated_Subtype_Use --
699 --------------------------------
701 procedure Bad_Predicated_Subtype_Use
702 (Msg : String;
703 N : Node_Id;
704 Typ : Entity_Id;
705 Suggest_Static : Boolean := False)
707 Gen : Entity_Id;
709 begin
710 -- Avoid cascaded errors
712 if Error_Posted (N) then
713 return;
714 end if;
716 if Inside_A_Generic then
717 Gen := Current_Scope;
718 while Present (Gen) and then Ekind (Gen) /= E_Generic_Package loop
719 Gen := Scope (Gen);
720 end loop;
722 if No (Gen) then
723 return;
724 end if;
726 if Is_Generic_Formal (Typ) and then Is_Discrete_Type (Typ) then
727 Set_No_Predicate_On_Actual (Typ);
728 end if;
730 elsif Has_Predicates (Typ) then
731 if Is_Generic_Actual_Type (Typ) then
733 -- The restriction on loop parameters is only that the type
734 -- should have no dynamic predicates.
736 if Nkind (Parent (N)) = N_Loop_Parameter_Specification
737 and then not Has_Dynamic_Predicate_Aspect (Typ)
738 and then Is_OK_Static_Subtype (Typ)
739 then
740 return;
741 end if;
743 Gen := Current_Scope;
744 while not Is_Generic_Instance (Gen) loop
745 Gen := Scope (Gen);
746 end loop;
748 pragma Assert (Present (Gen));
750 if Ekind (Gen) = E_Package and then In_Package_Body (Gen) then
751 Error_Msg_Warn := SPARK_Mode /= On;
752 Error_Msg_FE (Msg & "<<", N, Typ);
753 Error_Msg_F ("\Program_Error [<<", N);
755 Insert_Action (N,
756 Make_Raise_Program_Error (Sloc (N),
757 Reason => PE_Bad_Predicated_Generic_Type));
759 else
760 Error_Msg_FE (Msg & "<<", N, Typ);
761 end if;
763 else
764 Error_Msg_FE (Msg, N, Typ);
765 end if;
767 -- Emit an optional suggestion on how to remedy the error if the
768 -- context warrants it.
770 if Suggest_Static and then Has_Static_Predicate (Typ) then
771 Error_Msg_FE ("\predicate of & should be marked static", N, Typ);
772 end if;
773 end if;
774 end Bad_Predicated_Subtype_Use;
776 -----------------------------------------
777 -- Bad_Unordered_Enumeration_Reference --
778 -----------------------------------------
780 function Bad_Unordered_Enumeration_Reference
781 (N : Node_Id;
782 T : Entity_Id) return Boolean
784 begin
785 return Is_Enumeration_Type (T)
786 and then Warn_On_Unordered_Enumeration_Type
787 and then not Is_Generic_Type (T)
788 and then Comes_From_Source (N)
789 and then not Has_Pragma_Ordered (T)
790 and then not In_Same_Extended_Unit (N, T);
791 end Bad_Unordered_Enumeration_Reference;
793 --------------------------
794 -- Build_Actual_Subtype --
795 --------------------------
797 function Build_Actual_Subtype
798 (T : Entity_Id;
799 N : Node_Or_Entity_Id) return Node_Id
801 Loc : Source_Ptr;
802 -- Normally Sloc (N), but may point to corresponding body in some cases
804 Constraints : List_Id;
805 Decl : Node_Id;
806 Discr : Entity_Id;
807 Hi : Node_Id;
808 Lo : Node_Id;
809 Subt : Entity_Id;
810 Disc_Type : Entity_Id;
811 Obj : Node_Id;
813 begin
814 Loc := Sloc (N);
816 if Nkind (N) = N_Defining_Identifier then
817 Obj := New_Occurrence_Of (N, Loc);
819 -- If this is a formal parameter of a subprogram declaration, and
820 -- we are compiling the body, we want the declaration for the
821 -- actual subtype to carry the source position of the body, to
822 -- prevent anomalies in gdb when stepping through the code.
824 if Is_Formal (N) then
825 declare
826 Decl : constant Node_Id := Unit_Declaration_Node (Scope (N));
827 begin
828 if Nkind (Decl) = N_Subprogram_Declaration
829 and then Present (Corresponding_Body (Decl))
830 then
831 Loc := Sloc (Corresponding_Body (Decl));
832 end if;
833 end;
834 end if;
836 else
837 Obj := N;
838 end if;
840 if Is_Array_Type (T) then
841 Constraints := New_List;
842 for J in 1 .. Number_Dimensions (T) loop
844 -- Build an array subtype declaration with the nominal subtype and
845 -- the bounds of the actual. Add the declaration in front of the
846 -- local declarations for the subprogram, for analysis before any
847 -- reference to the formal in the body.
849 Lo :=
850 Make_Attribute_Reference (Loc,
851 Prefix =>
852 Duplicate_Subexpr_No_Checks (Obj, Name_Req => True),
853 Attribute_Name => Name_First,
854 Expressions => New_List (
855 Make_Integer_Literal (Loc, J)));
857 Hi :=
858 Make_Attribute_Reference (Loc,
859 Prefix =>
860 Duplicate_Subexpr_No_Checks (Obj, Name_Req => True),
861 Attribute_Name => Name_Last,
862 Expressions => New_List (
863 Make_Integer_Literal (Loc, J)));
865 Append (Make_Range (Loc, Lo, Hi), Constraints);
866 end loop;
868 -- If the type has unknown discriminants there is no constrained
869 -- subtype to build. This is never called for a formal or for a
870 -- lhs, so returning the type is ok ???
872 elsif Has_Unknown_Discriminants (T) then
873 return T;
875 else
876 Constraints := New_List;
878 -- Type T is a generic derived type, inherit the discriminants from
879 -- the parent type.
881 if Is_Private_Type (T)
882 and then No (Full_View (T))
884 -- T was flagged as an error if it was declared as a formal
885 -- derived type with known discriminants. In this case there
886 -- is no need to look at the parent type since T already carries
887 -- its own discriminants.
889 and then not Error_Posted (T)
890 then
891 Disc_Type := Etype (Base_Type (T));
892 else
893 Disc_Type := T;
894 end if;
896 Discr := First_Discriminant (Disc_Type);
897 while Present (Discr) loop
898 Append_To (Constraints,
899 Make_Selected_Component (Loc,
900 Prefix =>
901 Duplicate_Subexpr_No_Checks (Obj),
902 Selector_Name => New_Occurrence_Of (Discr, Loc)));
903 Next_Discriminant (Discr);
904 end loop;
905 end if;
907 Subt := Make_Temporary (Loc, 'S', Related_Node => N);
908 Set_Is_Internal (Subt);
910 Decl :=
911 Make_Subtype_Declaration (Loc,
912 Defining_Identifier => Subt,
913 Subtype_Indication =>
914 Make_Subtype_Indication (Loc,
915 Subtype_Mark => New_Occurrence_Of (T, Loc),
916 Constraint =>
917 Make_Index_Or_Discriminant_Constraint (Loc,
918 Constraints => Constraints)));
920 Mark_Rewrite_Insertion (Decl);
921 return Decl;
922 end Build_Actual_Subtype;
924 ---------------------------------------
925 -- Build_Actual_Subtype_Of_Component --
926 ---------------------------------------
928 function Build_Actual_Subtype_Of_Component
929 (T : Entity_Id;
930 N : Node_Id) return Node_Id
932 Loc : constant Source_Ptr := Sloc (N);
933 P : constant Node_Id := Prefix (N);
934 D : Elmt_Id;
935 Id : Node_Id;
936 Index_Typ : Entity_Id;
938 Desig_Typ : Entity_Id;
939 -- This is either a copy of T, or if T is an access type, then it is
940 -- the directly designated type of this access type.
942 function Build_Actual_Array_Constraint return List_Id;
943 -- If one or more of the bounds of the component depends on
944 -- discriminants, build actual constraint using the discriminants
945 -- of the prefix.
947 function Build_Actual_Record_Constraint return List_Id;
948 -- Similar to previous one, for discriminated components constrained
949 -- by the discriminant of the enclosing object.
951 -----------------------------------
952 -- Build_Actual_Array_Constraint --
953 -----------------------------------
955 function Build_Actual_Array_Constraint return List_Id is
956 Constraints : constant List_Id := New_List;
957 Indx : Node_Id;
958 Hi : Node_Id;
959 Lo : Node_Id;
960 Old_Hi : Node_Id;
961 Old_Lo : Node_Id;
963 begin
964 Indx := First_Index (Desig_Typ);
965 while Present (Indx) loop
966 Old_Lo := Type_Low_Bound (Etype (Indx));
967 Old_Hi := Type_High_Bound (Etype (Indx));
969 if Denotes_Discriminant (Old_Lo) then
970 Lo :=
971 Make_Selected_Component (Loc,
972 Prefix => New_Copy_Tree (P),
973 Selector_Name => New_Occurrence_Of (Entity (Old_Lo), Loc));
975 else
976 Lo := New_Copy_Tree (Old_Lo);
978 -- The new bound will be reanalyzed in the enclosing
979 -- declaration. For literal bounds that come from a type
980 -- declaration, the type of the context must be imposed, so
981 -- insure that analysis will take place. For non-universal
982 -- types this is not strictly necessary.
984 Set_Analyzed (Lo, False);
985 end if;
987 if Denotes_Discriminant (Old_Hi) then
988 Hi :=
989 Make_Selected_Component (Loc,
990 Prefix => New_Copy_Tree (P),
991 Selector_Name => New_Occurrence_Of (Entity (Old_Hi), Loc));
993 else
994 Hi := New_Copy_Tree (Old_Hi);
995 Set_Analyzed (Hi, False);
996 end if;
998 Append (Make_Range (Loc, Lo, Hi), Constraints);
999 Next_Index (Indx);
1000 end loop;
1002 return Constraints;
1003 end Build_Actual_Array_Constraint;
1005 ------------------------------------
1006 -- Build_Actual_Record_Constraint --
1007 ------------------------------------
1009 function Build_Actual_Record_Constraint return List_Id is
1010 Constraints : constant List_Id := New_List;
1011 D : Elmt_Id;
1012 D_Val : Node_Id;
1014 begin
1015 D := First_Elmt (Discriminant_Constraint (Desig_Typ));
1016 while Present (D) loop
1017 if Denotes_Discriminant (Node (D)) then
1018 D_Val := Make_Selected_Component (Loc,
1019 Prefix => New_Copy_Tree (P),
1020 Selector_Name => New_Occurrence_Of (Entity (Node (D)), Loc));
1022 else
1023 D_Val := New_Copy_Tree (Node (D));
1024 end if;
1026 Append (D_Val, Constraints);
1027 Next_Elmt (D);
1028 end loop;
1030 return Constraints;
1031 end Build_Actual_Record_Constraint;
1033 -- Start of processing for Build_Actual_Subtype_Of_Component
1035 begin
1036 -- Why the test for Spec_Expression mode here???
1038 if In_Spec_Expression then
1039 return Empty;
1041 -- More comments for the rest of this body would be good ???
1043 elsif Nkind (N) = N_Explicit_Dereference then
1044 if Is_Composite_Type (T)
1045 and then not Is_Constrained (T)
1046 and then not (Is_Class_Wide_Type (T)
1047 and then Is_Constrained (Root_Type (T)))
1048 and then not Has_Unknown_Discriminants (T)
1049 then
1050 -- If the type of the dereference is already constrained, it is an
1051 -- actual subtype.
1053 if Is_Array_Type (Etype (N))
1054 and then Is_Constrained (Etype (N))
1055 then
1056 return Empty;
1057 else
1058 Remove_Side_Effects (P);
1059 return Build_Actual_Subtype (T, N);
1060 end if;
1061 else
1062 return Empty;
1063 end if;
1064 end if;
1066 if Ekind (T) = E_Access_Subtype then
1067 Desig_Typ := Designated_Type (T);
1068 else
1069 Desig_Typ := T;
1070 end if;
1072 if Ekind (Desig_Typ) = E_Array_Subtype then
1073 Id := First_Index (Desig_Typ);
1074 while Present (Id) loop
1075 Index_Typ := Underlying_Type (Etype (Id));
1077 if Denotes_Discriminant (Type_Low_Bound (Index_Typ))
1078 or else
1079 Denotes_Discriminant (Type_High_Bound (Index_Typ))
1080 then
1081 Remove_Side_Effects (P);
1082 return
1083 Build_Component_Subtype
1084 (Build_Actual_Array_Constraint, Loc, Base_Type (T));
1085 end if;
1087 Next_Index (Id);
1088 end loop;
1090 elsif Is_Composite_Type (Desig_Typ)
1091 and then Has_Discriminants (Desig_Typ)
1092 and then not Has_Unknown_Discriminants (Desig_Typ)
1093 then
1094 if Is_Private_Type (Desig_Typ)
1095 and then No (Discriminant_Constraint (Desig_Typ))
1096 then
1097 Desig_Typ := Full_View (Desig_Typ);
1098 end if;
1100 D := First_Elmt (Discriminant_Constraint (Desig_Typ));
1101 while Present (D) loop
1102 if Denotes_Discriminant (Node (D)) then
1103 Remove_Side_Effects (P);
1104 return
1105 Build_Component_Subtype (
1106 Build_Actual_Record_Constraint, Loc, Base_Type (T));
1107 end if;
1109 Next_Elmt (D);
1110 end loop;
1111 end if;
1113 -- If none of the above, the actual and nominal subtypes are the same
1115 return Empty;
1116 end Build_Actual_Subtype_Of_Component;
1118 -----------------------------
1119 -- Build_Component_Subtype --
1120 -----------------------------
1122 function Build_Component_Subtype
1123 (C : List_Id;
1124 Loc : Source_Ptr;
1125 T : Entity_Id) return Node_Id
1127 Subt : Entity_Id;
1128 Decl : Node_Id;
1130 begin
1131 -- Unchecked_Union components do not require component subtypes
1133 if Is_Unchecked_Union (T) then
1134 return Empty;
1135 end if;
1137 Subt := Make_Temporary (Loc, 'S');
1138 Set_Is_Internal (Subt);
1140 Decl :=
1141 Make_Subtype_Declaration (Loc,
1142 Defining_Identifier => Subt,
1143 Subtype_Indication =>
1144 Make_Subtype_Indication (Loc,
1145 Subtype_Mark => New_Occurrence_Of (Base_Type (T), Loc),
1146 Constraint =>
1147 Make_Index_Or_Discriminant_Constraint (Loc,
1148 Constraints => C)));
1150 Mark_Rewrite_Insertion (Decl);
1151 return Decl;
1152 end Build_Component_Subtype;
1154 ----------------------------------
1155 -- Build_Default_Init_Cond_Call --
1156 ----------------------------------
1158 function Build_Default_Init_Cond_Call
1159 (Loc : Source_Ptr;
1160 Obj_Id : Entity_Id;
1161 Typ : Entity_Id) return Node_Id
1163 Proc_Id : constant Entity_Id := Default_Init_Cond_Procedure (Typ);
1164 Formal_Typ : constant Entity_Id := Etype (First_Formal (Proc_Id));
1166 begin
1167 return
1168 Make_Procedure_Call_Statement (Loc,
1169 Name => New_Occurrence_Of (Proc_Id, Loc),
1170 Parameter_Associations => New_List (
1171 Make_Unchecked_Type_Conversion (Loc,
1172 Subtype_Mark => New_Occurrence_Of (Formal_Typ, Loc),
1173 Expression => New_Occurrence_Of (Obj_Id, Loc))));
1174 end Build_Default_Init_Cond_Call;
1176 ----------------------------------------------
1177 -- Build_Default_Init_Cond_Procedure_Bodies --
1178 ----------------------------------------------
1180 procedure Build_Default_Init_Cond_Procedure_Bodies (Priv_Decls : List_Id) is
1181 procedure Build_Default_Init_Cond_Procedure_Body (Typ : Entity_Id);
1182 -- If type Typ is subject to pragma Default_Initial_Condition, build the
1183 -- body of the procedure which verifies the assumption of the pragma at
1184 -- run time. The generated body is added after the type declaration.
1186 --------------------------------------------
1187 -- Build_Default_Init_Cond_Procedure_Body --
1188 --------------------------------------------
1190 procedure Build_Default_Init_Cond_Procedure_Body (Typ : Entity_Id) is
1191 Param_Id : Entity_Id;
1192 -- The entity of the sole formal parameter of the default initial
1193 -- condition procedure.
1195 procedure Replace_Type_Reference (N : Node_Id);
1196 -- Replace a single reference to type Typ with a reference to formal
1197 -- parameter Param_Id.
1199 ----------------------------
1200 -- Replace_Type_Reference --
1201 ----------------------------
1203 procedure Replace_Type_Reference (N : Node_Id) is
1204 begin
1205 Rewrite (N, New_Occurrence_Of (Param_Id, Sloc (N)));
1206 end Replace_Type_Reference;
1208 procedure Replace_Type_References is
1209 new Replace_Type_References_Generic (Replace_Type_Reference);
1211 -- Local variables
1213 Loc : constant Source_Ptr := Sloc (Typ);
1214 Prag : constant Node_Id :=
1215 Get_Pragma (Typ, Pragma_Default_Initial_Condition);
1216 Proc_Id : constant Entity_Id := Default_Init_Cond_Procedure (Typ);
1217 Spec_Decl : constant Node_Id := Unit_Declaration_Node (Proc_Id);
1218 Body_Decl : Node_Id;
1219 Expr : Node_Id;
1220 Stmt : Node_Id;
1222 Save_Ghost_Mode : constant Ghost_Mode_Type := Ghost_Mode;
1224 -- Start of processing for Build_Default_Init_Cond_Procedure_Body
1226 begin
1227 -- The procedure should be generated only for [sub]types subject to
1228 -- pragma Default_Initial_Condition. Types that inherit the pragma do
1229 -- not get this specialized procedure.
1231 pragma Assert (Has_Default_Init_Cond (Typ));
1232 pragma Assert (Present (Prag));
1233 pragma Assert (Present (Proc_Id));
1235 -- Nothing to do if the body was already built
1237 if Present (Corresponding_Body (Spec_Decl)) then
1238 return;
1239 end if;
1241 -- The related type may be subject to pragma Ghost. Set the mode now
1242 -- to ensure that the analysis and expansion produce Ghost nodes.
1244 Set_Ghost_Mode_From_Entity (Typ);
1246 Param_Id := First_Formal (Proc_Id);
1248 -- The pragma has an argument. Note that the argument is analyzed
1249 -- after all references to the current instance of the type are
1250 -- replaced.
1252 if Present (Pragma_Argument_Associations (Prag)) then
1253 Expr :=
1254 Get_Pragma_Arg (First (Pragma_Argument_Associations (Prag)));
1256 if Nkind (Expr) = N_Null then
1257 Stmt := Make_Null_Statement (Loc);
1259 -- Preserve the original argument of the pragma by replicating it.
1260 -- Replace all references to the current instance of the type with
1261 -- references to the formal parameter.
1263 else
1264 Expr := New_Copy_Tree (Expr);
1265 Replace_Type_References (Expr, Typ);
1267 -- Generate:
1268 -- pragma Check (Default_Initial_Condition, <Expr>);
1270 Stmt :=
1271 Make_Pragma (Loc,
1272 Pragma_Identifier =>
1273 Make_Identifier (Loc, Name_Check),
1275 Pragma_Argument_Associations => New_List (
1276 Make_Pragma_Argument_Association (Loc,
1277 Expression =>
1278 Make_Identifier (Loc,
1279 Chars => Name_Default_Initial_Condition)),
1280 Make_Pragma_Argument_Association (Loc,
1281 Expression => Expr)));
1282 end if;
1284 -- Otherwise the pragma appears without an argument
1286 else
1287 Stmt := Make_Null_Statement (Loc);
1288 end if;
1290 -- Generate:
1291 -- procedure <Typ>Default_Init_Cond (I : <Typ>) is
1292 -- begin
1293 -- <Stmt>;
1294 -- end <Typ>Default_Init_Cond;
1296 Body_Decl :=
1297 Make_Subprogram_Body (Loc,
1298 Specification =>
1299 Copy_Separate_Tree (Specification (Spec_Decl)),
1300 Declarations => Empty_List,
1301 Handled_Statement_Sequence =>
1302 Make_Handled_Sequence_Of_Statements (Loc,
1303 Statements => New_List (Stmt)));
1305 -- Link the spec and body of the default initial condition procedure
1306 -- to prevent the generation of a duplicate body.
1308 Set_Corresponding_Body (Spec_Decl, Defining_Entity (Body_Decl));
1309 Set_Corresponding_Spec (Body_Decl, Proc_Id);
1311 Insert_After_And_Analyze (Declaration_Node (Typ), Body_Decl);
1312 Ghost_Mode := Save_Ghost_Mode;
1313 end Build_Default_Init_Cond_Procedure_Body;
1315 -- Local variables
1317 Decl : Node_Id;
1318 Typ : Entity_Id;
1320 -- Start of processing for Build_Default_Init_Cond_Procedure_Bodies
1322 begin
1323 -- Inspect the private declarations looking for [sub]type declarations
1325 Decl := First (Priv_Decls);
1326 while Present (Decl) loop
1327 if Nkind_In (Decl, N_Full_Type_Declaration,
1328 N_Subtype_Declaration)
1329 then
1330 Typ := Defining_Entity (Decl);
1332 -- Guard against partially decorate types due to previous errors
1334 if Is_Type (Typ) then
1336 -- If the type is subject to pragma Default_Initial_Condition,
1337 -- generate the body of the internal procedure which verifies
1338 -- the assertion of the pragma at run time.
1340 if Has_Default_Init_Cond (Typ) then
1341 Build_Default_Init_Cond_Procedure_Body (Typ);
1343 -- A derived type inherits the default initial condition
1344 -- procedure from its parent type.
1346 elsif Has_Inherited_Default_Init_Cond (Typ) then
1347 Inherit_Default_Init_Cond_Procedure (Typ);
1348 end if;
1349 end if;
1350 end if;
1352 Next (Decl);
1353 end loop;
1354 end Build_Default_Init_Cond_Procedure_Bodies;
1356 ---------------------------------------------------
1357 -- Build_Default_Init_Cond_Procedure_Declaration --
1358 ---------------------------------------------------
1360 procedure Build_Default_Init_Cond_Procedure_Declaration (Typ : Entity_Id) is
1361 Loc : constant Source_Ptr := Sloc (Typ);
1362 Prag : constant Node_Id :=
1363 Get_Pragma (Typ, Pragma_Default_Initial_Condition);
1365 Save_Ghost_Mode : constant Ghost_Mode_Type := Ghost_Mode;
1367 Proc_Id : Entity_Id;
1369 begin
1370 -- The procedure should be generated only for types subject to pragma
1371 -- Default_Initial_Condition. Types that inherit the pragma do not get
1372 -- this specialized procedure.
1374 pragma Assert (Has_Default_Init_Cond (Typ));
1375 pragma Assert (Present (Prag));
1377 -- Nothing to do if default initial condition procedure already built
1379 if Present (Default_Init_Cond_Procedure (Typ)) then
1380 return;
1381 end if;
1383 -- The related type may be subject to pragma Ghost. Set the mode now to
1384 -- ensure that the analysis and expansion produce Ghost nodes.
1386 Set_Ghost_Mode_From_Entity (Typ);
1388 Proc_Id :=
1389 Make_Defining_Identifier (Loc,
1390 Chars => New_External_Name (Chars (Typ), "Default_Init_Cond"));
1392 -- Associate default initial condition procedure with the private type
1394 Set_Ekind (Proc_Id, E_Procedure);
1395 Set_Is_Default_Init_Cond_Procedure (Proc_Id);
1396 Set_Default_Init_Cond_Procedure (Typ, Proc_Id);
1398 -- Mark the default initial condition procedure explicitly as Ghost
1399 -- because it does not come from source.
1401 if Ghost_Mode > None then
1402 Set_Is_Ghost_Entity (Proc_Id);
1403 end if;
1405 -- Generate:
1406 -- procedure <Typ>Default_Init_Cond (Inn : <Typ>);
1408 Insert_After_And_Analyze (Prag,
1409 Make_Subprogram_Declaration (Loc,
1410 Specification =>
1411 Make_Procedure_Specification (Loc,
1412 Defining_Unit_Name => Proc_Id,
1413 Parameter_Specifications => New_List (
1414 Make_Parameter_Specification (Loc,
1415 Defining_Identifier => Make_Temporary (Loc, 'I'),
1416 Parameter_Type => New_Occurrence_Of (Typ, Loc))))));
1418 Ghost_Mode := Save_Ghost_Mode;
1419 end Build_Default_Init_Cond_Procedure_Declaration;
1421 ---------------------------
1422 -- Build_Default_Subtype --
1423 ---------------------------
1425 function Build_Default_Subtype
1426 (T : Entity_Id;
1427 N : Node_Id) return Entity_Id
1429 Loc : constant Source_Ptr := Sloc (N);
1430 Disc : Entity_Id;
1432 Bas : Entity_Id;
1433 -- The base type that is to be constrained by the defaults
1435 begin
1436 if not Has_Discriminants (T) or else Is_Constrained (T) then
1437 return T;
1438 end if;
1440 Bas := Base_Type (T);
1442 -- If T is non-private but its base type is private, this is the
1443 -- completion of a subtype declaration whose parent type is private
1444 -- (see Complete_Private_Subtype in Sem_Ch3). The proper discriminants
1445 -- are to be found in the full view of the base. Check that the private
1446 -- status of T and its base differ.
1448 if Is_Private_Type (Bas)
1449 and then not Is_Private_Type (T)
1450 and then Present (Full_View (Bas))
1451 then
1452 Bas := Full_View (Bas);
1453 end if;
1455 Disc := First_Discriminant (T);
1457 if No (Discriminant_Default_Value (Disc)) then
1458 return T;
1459 end if;
1461 declare
1462 Act : constant Entity_Id := Make_Temporary (Loc, 'S');
1463 Constraints : constant List_Id := New_List;
1464 Decl : Node_Id;
1466 begin
1467 while Present (Disc) loop
1468 Append_To (Constraints,
1469 New_Copy_Tree (Discriminant_Default_Value (Disc)));
1470 Next_Discriminant (Disc);
1471 end loop;
1473 Decl :=
1474 Make_Subtype_Declaration (Loc,
1475 Defining_Identifier => Act,
1476 Subtype_Indication =>
1477 Make_Subtype_Indication (Loc,
1478 Subtype_Mark => New_Occurrence_Of (Bas, Loc),
1479 Constraint =>
1480 Make_Index_Or_Discriminant_Constraint (Loc,
1481 Constraints => Constraints)));
1483 Insert_Action (N, Decl);
1485 -- If the context is a component declaration the subtype declaration
1486 -- will be analyzed when the enclosing type is frozen, otherwise do
1487 -- it now.
1489 if Ekind (Current_Scope) /= E_Record_Type then
1490 Analyze (Decl);
1491 end if;
1493 return Act;
1494 end;
1495 end Build_Default_Subtype;
1497 --------------------------------------------
1498 -- Build_Discriminal_Subtype_Of_Component --
1499 --------------------------------------------
1501 function Build_Discriminal_Subtype_Of_Component
1502 (T : Entity_Id) return Node_Id
1504 Loc : constant Source_Ptr := Sloc (T);
1505 D : Elmt_Id;
1506 Id : Node_Id;
1508 function Build_Discriminal_Array_Constraint return List_Id;
1509 -- If one or more of the bounds of the component depends on
1510 -- discriminants, build actual constraint using the discriminants
1511 -- of the prefix.
1513 function Build_Discriminal_Record_Constraint return List_Id;
1514 -- Similar to previous one, for discriminated components constrained by
1515 -- the discriminant of the enclosing object.
1517 ----------------------------------------
1518 -- Build_Discriminal_Array_Constraint --
1519 ----------------------------------------
1521 function Build_Discriminal_Array_Constraint return List_Id is
1522 Constraints : constant List_Id := New_List;
1523 Indx : Node_Id;
1524 Hi : Node_Id;
1525 Lo : Node_Id;
1526 Old_Hi : Node_Id;
1527 Old_Lo : Node_Id;
1529 begin
1530 Indx := First_Index (T);
1531 while Present (Indx) loop
1532 Old_Lo := Type_Low_Bound (Etype (Indx));
1533 Old_Hi := Type_High_Bound (Etype (Indx));
1535 if Denotes_Discriminant (Old_Lo) then
1536 Lo := New_Occurrence_Of (Discriminal (Entity (Old_Lo)), Loc);
1538 else
1539 Lo := New_Copy_Tree (Old_Lo);
1540 end if;
1542 if Denotes_Discriminant (Old_Hi) then
1543 Hi := New_Occurrence_Of (Discriminal (Entity (Old_Hi)), Loc);
1545 else
1546 Hi := New_Copy_Tree (Old_Hi);
1547 end if;
1549 Append (Make_Range (Loc, Lo, Hi), Constraints);
1550 Next_Index (Indx);
1551 end loop;
1553 return Constraints;
1554 end Build_Discriminal_Array_Constraint;
1556 -----------------------------------------
1557 -- Build_Discriminal_Record_Constraint --
1558 -----------------------------------------
1560 function Build_Discriminal_Record_Constraint return List_Id is
1561 Constraints : constant List_Id := New_List;
1562 D : Elmt_Id;
1563 D_Val : Node_Id;
1565 begin
1566 D := First_Elmt (Discriminant_Constraint (T));
1567 while Present (D) loop
1568 if Denotes_Discriminant (Node (D)) then
1569 D_Val :=
1570 New_Occurrence_Of (Discriminal (Entity (Node (D))), Loc);
1571 else
1572 D_Val := New_Copy_Tree (Node (D));
1573 end if;
1575 Append (D_Val, Constraints);
1576 Next_Elmt (D);
1577 end loop;
1579 return Constraints;
1580 end Build_Discriminal_Record_Constraint;
1582 -- Start of processing for Build_Discriminal_Subtype_Of_Component
1584 begin
1585 if Ekind (T) = E_Array_Subtype then
1586 Id := First_Index (T);
1587 while Present (Id) loop
1588 if Denotes_Discriminant (Type_Low_Bound (Etype (Id)))
1589 or else
1590 Denotes_Discriminant (Type_High_Bound (Etype (Id)))
1591 then
1592 return Build_Component_Subtype
1593 (Build_Discriminal_Array_Constraint, Loc, T);
1594 end if;
1596 Next_Index (Id);
1597 end loop;
1599 elsif Ekind (T) = E_Record_Subtype
1600 and then Has_Discriminants (T)
1601 and then not Has_Unknown_Discriminants (T)
1602 then
1603 D := First_Elmt (Discriminant_Constraint (T));
1604 while Present (D) loop
1605 if Denotes_Discriminant (Node (D)) then
1606 return Build_Component_Subtype
1607 (Build_Discriminal_Record_Constraint, Loc, T);
1608 end if;
1610 Next_Elmt (D);
1611 end loop;
1612 end if;
1614 -- If none of the above, the actual and nominal subtypes are the same
1616 return Empty;
1617 end Build_Discriminal_Subtype_Of_Component;
1619 ------------------------------
1620 -- Build_Elaboration_Entity --
1621 ------------------------------
1623 procedure Build_Elaboration_Entity (N : Node_Id; Spec_Id : Entity_Id) is
1624 Loc : constant Source_Ptr := Sloc (N);
1625 Decl : Node_Id;
1626 Elab_Ent : Entity_Id;
1628 procedure Set_Package_Name (Ent : Entity_Id);
1629 -- Given an entity, sets the fully qualified name of the entity in
1630 -- Name_Buffer, with components separated by double underscores. This
1631 -- is a recursive routine that climbs the scope chain to Standard.
1633 ----------------------
1634 -- Set_Package_Name --
1635 ----------------------
1637 procedure Set_Package_Name (Ent : Entity_Id) is
1638 begin
1639 if Scope (Ent) /= Standard_Standard then
1640 Set_Package_Name (Scope (Ent));
1642 declare
1643 Nam : constant String := Get_Name_String (Chars (Ent));
1644 begin
1645 Name_Buffer (Name_Len + 1) := '_';
1646 Name_Buffer (Name_Len + 2) := '_';
1647 Name_Buffer (Name_Len + 3 .. Name_Len + Nam'Length + 2) := Nam;
1648 Name_Len := Name_Len + Nam'Length + 2;
1649 end;
1651 else
1652 Get_Name_String (Chars (Ent));
1653 end if;
1654 end Set_Package_Name;
1656 -- Start of processing for Build_Elaboration_Entity
1658 begin
1659 -- Ignore call if already constructed
1661 if Present (Elaboration_Entity (Spec_Id)) then
1662 return;
1664 -- Ignore in ASIS mode, elaboration entity is not in source and plays
1665 -- no role in analysis.
1667 elsif ASIS_Mode then
1668 return;
1670 -- See if we need elaboration entity.
1672 -- We always need an elaboration entity when preserving control flow, as
1673 -- we want to remain explicit about the unit's elaboration order.
1675 elsif Opt.Suppress_Control_Flow_Optimizations then
1676 null;
1678 -- We always need an elaboration entity for the dynamic elaboration
1679 -- model, since it is needed to properly generate the PE exception for
1680 -- access before elaboration.
1682 elsif Dynamic_Elaboration_Checks then
1683 null;
1685 -- For the static model, we don't need the elaboration counter if this
1686 -- unit is sure to have no elaboration code, since that means there
1687 -- is no elaboration unit to be called. Note that we can't just decide
1688 -- after the fact by looking to see whether there was elaboration code,
1689 -- because that's too late to make this decision.
1691 elsif Restriction_Active (No_Elaboration_Code) then
1692 return;
1694 -- Similarly, for the static model, we can skip the elaboration counter
1695 -- if we have the No_Multiple_Elaboration restriction, since for the
1696 -- static model, that's the only purpose of the counter (to avoid
1697 -- multiple elaboration).
1699 elsif Restriction_Active (No_Multiple_Elaboration) then
1700 return;
1701 end if;
1703 -- Here we need the elaboration entity
1705 -- Construct name of elaboration entity as xxx_E, where xxx is the unit
1706 -- name with dots replaced by double underscore. We have to manually
1707 -- construct this name, since it will be elaborated in the outer scope,
1708 -- and thus will not have the unit name automatically prepended.
1710 Set_Package_Name (Spec_Id);
1711 Add_Str_To_Name_Buffer ("_E");
1713 -- Create elaboration counter
1715 Elab_Ent := Make_Defining_Identifier (Loc, Chars => Name_Find);
1716 Set_Elaboration_Entity (Spec_Id, Elab_Ent);
1718 Decl :=
1719 Make_Object_Declaration (Loc,
1720 Defining_Identifier => Elab_Ent,
1721 Object_Definition =>
1722 New_Occurrence_Of (Standard_Short_Integer, Loc),
1723 Expression => Make_Integer_Literal (Loc, Uint_0));
1725 Push_Scope (Standard_Standard);
1726 Add_Global_Declaration (Decl);
1727 Pop_Scope;
1729 -- Reset True_Constant indication, since we will indeed assign a value
1730 -- to the variable in the binder main. We also kill the Current_Value
1731 -- and Last_Assignment fields for the same reason.
1733 Set_Is_True_Constant (Elab_Ent, False);
1734 Set_Current_Value (Elab_Ent, Empty);
1735 Set_Last_Assignment (Elab_Ent, Empty);
1737 -- We do not want any further qualification of the name (if we did not
1738 -- do this, we would pick up the name of the generic package in the case
1739 -- of a library level generic instantiation).
1741 Set_Has_Qualified_Name (Elab_Ent);
1742 Set_Has_Fully_Qualified_Name (Elab_Ent);
1743 end Build_Elaboration_Entity;
1745 --------------------------------
1746 -- Build_Explicit_Dereference --
1747 --------------------------------
1749 procedure Build_Explicit_Dereference
1750 (Expr : Node_Id;
1751 Disc : Entity_Id)
1753 Loc : constant Source_Ptr := Sloc (Expr);
1754 I : Interp_Index;
1755 It : Interp;
1757 begin
1758 -- An entity of a type with a reference aspect is overloaded with
1759 -- both interpretations: with and without the dereference. Now that
1760 -- the dereference is made explicit, set the type of the node properly,
1761 -- to prevent anomalies in the backend. Same if the expression is an
1762 -- overloaded function call whose return type has a reference aspect.
1764 if Is_Entity_Name (Expr) then
1765 Set_Etype (Expr, Etype (Entity (Expr)));
1767 -- The designated entity will not be examined again when resolving
1768 -- the dereference, so generate a reference to it now.
1770 Generate_Reference (Entity (Expr), Expr);
1772 elsif Nkind (Expr) = N_Function_Call then
1774 -- If the name of the indexing function is overloaded, locate the one
1775 -- whose return type has an implicit dereference on the desired
1776 -- discriminant, and set entity and type of function call.
1778 if Is_Overloaded (Name (Expr)) then
1779 Get_First_Interp (Name (Expr), I, It);
1781 while Present (It.Nam) loop
1782 if Ekind ((It.Typ)) = E_Record_Type
1783 and then First_Entity ((It.Typ)) = Disc
1784 then
1785 Set_Entity (Name (Expr), It.Nam);
1786 Set_Etype (Name (Expr), Etype (It.Nam));
1787 exit;
1788 end if;
1790 Get_Next_Interp (I, It);
1791 end loop;
1792 end if;
1794 -- Set type of call from resolved function name.
1796 Set_Etype (Expr, Etype (Name (Expr)));
1797 end if;
1799 Set_Is_Overloaded (Expr, False);
1801 -- The expression will often be a generalized indexing that yields a
1802 -- container element that is then dereferenced, in which case the
1803 -- generalized indexing call is also non-overloaded.
1805 if Nkind (Expr) = N_Indexed_Component
1806 and then Present (Generalized_Indexing (Expr))
1807 then
1808 Set_Is_Overloaded (Generalized_Indexing (Expr), False);
1809 end if;
1811 Rewrite (Expr,
1812 Make_Explicit_Dereference (Loc,
1813 Prefix =>
1814 Make_Selected_Component (Loc,
1815 Prefix => Relocate_Node (Expr),
1816 Selector_Name => New_Occurrence_Of (Disc, Loc))));
1817 Set_Etype (Prefix (Expr), Etype (Disc));
1818 Set_Etype (Expr, Designated_Type (Etype (Disc)));
1819 end Build_Explicit_Dereference;
1821 -----------------------------------
1822 -- Cannot_Raise_Constraint_Error --
1823 -----------------------------------
1825 function Cannot_Raise_Constraint_Error (Expr : Node_Id) return Boolean is
1826 begin
1827 if Compile_Time_Known_Value (Expr) then
1828 return True;
1830 elsif Do_Range_Check (Expr) then
1831 return False;
1833 elsif Raises_Constraint_Error (Expr) then
1834 return False;
1836 else
1837 case Nkind (Expr) is
1838 when N_Identifier =>
1839 return True;
1841 when N_Expanded_Name =>
1842 return True;
1844 when N_Selected_Component =>
1845 return not Do_Discriminant_Check (Expr);
1847 when N_Attribute_Reference =>
1848 if Do_Overflow_Check (Expr) then
1849 return False;
1851 elsif No (Expressions (Expr)) then
1852 return True;
1854 else
1855 declare
1856 N : Node_Id;
1858 begin
1859 N := First (Expressions (Expr));
1860 while Present (N) loop
1861 if Cannot_Raise_Constraint_Error (N) then
1862 Next (N);
1863 else
1864 return False;
1865 end if;
1866 end loop;
1868 return True;
1869 end;
1870 end if;
1872 when N_Type_Conversion =>
1873 if Do_Overflow_Check (Expr)
1874 or else Do_Length_Check (Expr)
1875 or else Do_Tag_Check (Expr)
1876 then
1877 return False;
1878 else
1879 return Cannot_Raise_Constraint_Error (Expression (Expr));
1880 end if;
1882 when N_Unchecked_Type_Conversion =>
1883 return Cannot_Raise_Constraint_Error (Expression (Expr));
1885 when N_Unary_Op =>
1886 if Do_Overflow_Check (Expr) then
1887 return False;
1888 else
1889 return Cannot_Raise_Constraint_Error (Right_Opnd (Expr));
1890 end if;
1892 when N_Op_Divide |
1893 N_Op_Mod |
1894 N_Op_Rem
1896 if Do_Division_Check (Expr)
1897 or else
1898 Do_Overflow_Check (Expr)
1899 then
1900 return False;
1901 else
1902 return
1903 Cannot_Raise_Constraint_Error (Left_Opnd (Expr))
1904 and then
1905 Cannot_Raise_Constraint_Error (Right_Opnd (Expr));
1906 end if;
1908 when N_Op_Add |
1909 N_Op_And |
1910 N_Op_Concat |
1911 N_Op_Eq |
1912 N_Op_Expon |
1913 N_Op_Ge |
1914 N_Op_Gt |
1915 N_Op_Le |
1916 N_Op_Lt |
1917 N_Op_Multiply |
1918 N_Op_Ne |
1919 N_Op_Or |
1920 N_Op_Rotate_Left |
1921 N_Op_Rotate_Right |
1922 N_Op_Shift_Left |
1923 N_Op_Shift_Right |
1924 N_Op_Shift_Right_Arithmetic |
1925 N_Op_Subtract |
1926 N_Op_Xor
1928 if Do_Overflow_Check (Expr) then
1929 return False;
1930 else
1931 return
1932 Cannot_Raise_Constraint_Error (Left_Opnd (Expr))
1933 and then
1934 Cannot_Raise_Constraint_Error (Right_Opnd (Expr));
1935 end if;
1937 when others =>
1938 return False;
1939 end case;
1940 end if;
1941 end Cannot_Raise_Constraint_Error;
1943 -----------------------------
1944 -- Check_Part_Of_Reference --
1945 -----------------------------
1947 procedure Check_Part_Of_Reference (Var_Id : Entity_Id; Ref : Node_Id) is
1948 Conc_Typ : constant Entity_Id := Encapsulating_State (Var_Id);
1949 Decl : Node_Id;
1950 OK_Use : Boolean := False;
1951 Par : Node_Id;
1952 Prag_Nam : Name_Id;
1953 Spec_Id : Entity_Id;
1955 begin
1956 -- Traverse the parent chain looking for a suitable context for the
1957 -- reference to the concurrent constituent.
1959 Par := Parent (Ref);
1960 while Present (Par) loop
1961 if Nkind (Par) = N_Pragma then
1962 Prag_Nam := Pragma_Name (Par);
1964 -- A concurrent constituent is allowed to appear in pragmas
1965 -- Initial_Condition and Initializes as this is part of the
1966 -- elaboration checks for the constituent (SPARK RM 9.3).
1968 if Nam_In (Prag_Nam, Name_Initial_Condition, Name_Initializes) then
1969 OK_Use := True;
1970 exit;
1972 -- When the reference appears within pragma Depends or Global,
1973 -- check whether the pragma applies to a single task type. Note
1974 -- that the pragma is not encapsulated by the type definition,
1975 -- but this is still a valid context.
1977 elsif Nam_In (Prag_Nam, Name_Depends, Name_Global) then
1978 Decl := Find_Related_Declaration_Or_Body (Par);
1980 if Nkind (Decl) = N_Object_Declaration
1981 and then Defining_Entity (Decl) = Conc_Typ
1982 then
1983 OK_Use := True;
1984 exit;
1985 end if;
1986 end if;
1988 -- The reference appears somewhere in the definition of the single
1989 -- protected/task type (SPARK RM 9.3).
1991 elsif Nkind_In (Par, N_Single_Protected_Declaration,
1992 N_Single_Task_Declaration)
1993 and then Defining_Entity (Par) = Conc_Typ
1994 then
1995 OK_Use := True;
1996 exit;
1998 -- The reference appears within the expanded declaration or the body
1999 -- of the single protected/task type (SPARK RM 9.3).
2001 elsif Nkind_In (Par, N_Protected_Body,
2002 N_Protected_Type_Declaration,
2003 N_Task_Body,
2004 N_Task_Type_Declaration)
2005 then
2006 Spec_Id := Unique_Defining_Entity (Par);
2008 if Present (Anonymous_Object (Spec_Id))
2009 and then Anonymous_Object (Spec_Id) = Conc_Typ
2010 then
2011 OK_Use := True;
2012 exit;
2013 end if;
2015 -- The reference has been relocated within an internally generated
2016 -- package or subprogram. Assume that the reference is legal as the
2017 -- real check was already performed in the original context of the
2018 -- reference.
2020 elsif Nkind_In (Par, N_Package_Body,
2021 N_Package_Declaration,
2022 N_Subprogram_Body,
2023 N_Subprogram_Declaration)
2024 and then not Comes_From_Source (Par)
2025 then
2026 OK_Use := True;
2027 exit;
2029 -- The reference has been relocated to an inlined body for GNATprove.
2030 -- Assume that the reference is legal as the real check was already
2031 -- performed in the original context of the reference.
2033 elsif GNATprove_Mode
2034 and then Nkind (Par) = N_Subprogram_Body
2035 and then Chars (Defining_Entity (Par)) = Name_uParent
2036 then
2037 OK_Use := True;
2038 exit;
2039 end if;
2041 Par := Parent (Par);
2042 end loop;
2044 -- The reference is illegal as it appears outside the definition or
2045 -- body of the single protected/task type.
2047 if not OK_Use then
2048 Error_Msg_NE
2049 ("reference to variable & cannot appear in this context",
2050 Ref, Var_Id);
2051 Error_Msg_Name_1 := Chars (Var_Id);
2053 if Ekind (Conc_Typ) = E_Protected_Type then
2054 Error_Msg_NE
2055 ("\% is constituent of single protected type &", Ref, Conc_Typ);
2056 else
2057 Error_Msg_NE
2058 ("\% is constituent of single task type &", Ref, Conc_Typ);
2059 end if;
2060 end if;
2061 end Check_Part_Of_Reference;
2063 -----------------------------------------
2064 -- Check_Dynamically_Tagged_Expression --
2065 -----------------------------------------
2067 procedure Check_Dynamically_Tagged_Expression
2068 (Expr : Node_Id;
2069 Typ : Entity_Id;
2070 Related_Nod : Node_Id)
2072 begin
2073 pragma Assert (Is_Tagged_Type (Typ));
2075 -- In order to avoid spurious errors when analyzing the expanded code,
2076 -- this check is done only for nodes that come from source and for
2077 -- actuals of generic instantiations.
2079 if (Comes_From_Source (Related_Nod)
2080 or else In_Generic_Actual (Expr))
2081 and then (Is_Class_Wide_Type (Etype (Expr))
2082 or else Is_Dynamically_Tagged (Expr))
2083 and then Is_Tagged_Type (Typ)
2084 and then not Is_Class_Wide_Type (Typ)
2085 then
2086 Error_Msg_N ("dynamically tagged expression not allowed!", Expr);
2087 end if;
2088 end Check_Dynamically_Tagged_Expression;
2090 --------------------------
2091 -- Check_Fully_Declared --
2092 --------------------------
2094 procedure Check_Fully_Declared (T : Entity_Id; N : Node_Id) is
2095 begin
2096 if Ekind (T) = E_Incomplete_Type then
2098 -- Ada 2005 (AI-50217): If the type is available through a limited
2099 -- with_clause, verify that its full view has been analyzed.
2101 if From_Limited_With (T)
2102 and then Present (Non_Limited_View (T))
2103 and then Ekind (Non_Limited_View (T)) /= E_Incomplete_Type
2104 then
2105 -- The non-limited view is fully declared
2107 null;
2109 else
2110 Error_Msg_NE
2111 ("premature usage of incomplete}", N, First_Subtype (T));
2112 end if;
2114 -- Need comments for these tests ???
2116 elsif Has_Private_Component (T)
2117 and then not Is_Generic_Type (Root_Type (T))
2118 and then not In_Spec_Expression
2119 then
2120 -- Special case: if T is the anonymous type created for a single
2121 -- task or protected object, use the name of the source object.
2123 if Is_Concurrent_Type (T)
2124 and then not Comes_From_Source (T)
2125 and then Nkind (N) = N_Object_Declaration
2126 then
2127 Error_Msg_NE
2128 ("type of& has incomplete component",
2129 N, Defining_Identifier (N));
2130 else
2131 Error_Msg_NE
2132 ("premature usage of incomplete}",
2133 N, First_Subtype (T));
2134 end if;
2135 end if;
2136 end Check_Fully_Declared;
2138 -------------------------------------------
2139 -- Check_Function_With_Address_Parameter --
2140 -------------------------------------------
2142 procedure Check_Function_With_Address_Parameter (Subp_Id : Entity_Id) is
2143 F : Entity_Id;
2144 T : Entity_Id;
2146 begin
2147 F := First_Formal (Subp_Id);
2148 while Present (F) loop
2149 T := Etype (F);
2151 if Is_Private_Type (T) and then Present (Full_View (T)) then
2152 T := Full_View (T);
2153 end if;
2155 if Is_Descendant_Of_Address (T) or else Is_Limited_Type (T) then
2156 Set_Is_Pure (Subp_Id, False);
2157 exit;
2158 end if;
2160 Next_Formal (F);
2161 end loop;
2162 end Check_Function_With_Address_Parameter;
2164 -------------------------------------
2165 -- Check_Function_Writable_Actuals --
2166 -------------------------------------
2168 procedure Check_Function_Writable_Actuals (N : Node_Id) is
2169 Writable_Actuals_List : Elist_Id := No_Elist;
2170 Identifiers_List : Elist_Id := No_Elist;
2171 Aggr_Error_Node : Node_Id := Empty;
2172 Error_Node : Node_Id := Empty;
2174 procedure Collect_Identifiers (N : Node_Id);
2175 -- In a single traversal of subtree N collect in Writable_Actuals_List
2176 -- all the actuals of functions with writable actuals, and in the list
2177 -- Identifiers_List collect all the identifiers that are not actuals of
2178 -- functions with writable actuals. If a writable actual is referenced
2179 -- twice as writable actual then Error_Node is set to reference its
2180 -- second occurrence, the error is reported, and the tree traversal
2181 -- is abandoned.
2183 function Get_Function_Id (Call : Node_Id) return Entity_Id;
2184 -- Return the entity associated with the function call
2186 procedure Preanalyze_Without_Errors (N : Node_Id);
2187 -- Preanalyze N without reporting errors. Very dubious, you can't just
2188 -- go analyzing things more than once???
2190 -------------------------
2191 -- Collect_Identifiers --
2192 -------------------------
2194 procedure Collect_Identifiers (N : Node_Id) is
2196 function Check_Node (N : Node_Id) return Traverse_Result;
2197 -- Process a single node during the tree traversal to collect the
2198 -- writable actuals of functions and all the identifiers which are
2199 -- not writable actuals of functions.
2201 function Contains (List : Elist_Id; N : Node_Id) return Boolean;
2202 -- Returns True if List has a node whose Entity is Entity (N)
2204 -------------------------
2205 -- Check_Function_Call --
2206 -------------------------
2208 function Check_Node (N : Node_Id) return Traverse_Result is
2209 Is_Writable_Actual : Boolean := False;
2210 Id : Entity_Id;
2212 begin
2213 if Nkind (N) = N_Identifier then
2215 -- No analysis possible if the entity is not decorated
2217 if No (Entity (N)) then
2218 return Skip;
2220 -- Don't collect identifiers of packages, called functions, etc
2222 elsif Ekind_In (Entity (N), E_Package,
2223 E_Function,
2224 E_Procedure,
2225 E_Entry)
2226 then
2227 return Skip;
2229 -- For rewritten nodes, continue the traversal in the original
2230 -- subtree. Needed to handle aggregates in original expressions
2231 -- extracted from the tree by Remove_Side_Effects.
2233 elsif Is_Rewrite_Substitution (N) then
2234 Collect_Identifiers (Original_Node (N));
2235 return Skip;
2237 -- For now we skip aggregate discriminants, since they require
2238 -- performing the analysis in two phases to identify conflicts:
2239 -- first one analyzing discriminants and second one analyzing
2240 -- the rest of components (since at run time, discriminants are
2241 -- evaluated prior to components): too much computation cost
2242 -- to identify a corner case???
2244 elsif Nkind (Parent (N)) = N_Component_Association
2245 and then Nkind_In (Parent (Parent (N)),
2246 N_Aggregate,
2247 N_Extension_Aggregate)
2248 then
2249 declare
2250 Choice : constant Node_Id := First (Choices (Parent (N)));
2252 begin
2253 if Ekind (Entity (N)) = E_Discriminant then
2254 return Skip;
2256 elsif Expression (Parent (N)) = N
2257 and then Nkind (Choice) = N_Identifier
2258 and then Ekind (Entity (Choice)) = E_Discriminant
2259 then
2260 return Skip;
2261 end if;
2262 end;
2264 -- Analyze if N is a writable actual of a function
2266 elsif Nkind (Parent (N)) = N_Function_Call then
2267 declare
2268 Call : constant Node_Id := Parent (N);
2269 Actual : Node_Id;
2270 Formal : Node_Id;
2272 begin
2273 Id := Get_Function_Id (Call);
2275 -- In case of previous error, no check is possible
2277 if No (Id) then
2278 return Abandon;
2279 end if;
2281 if Ekind_In (Id, E_Function, E_Generic_Function)
2282 and then Has_Out_Or_In_Out_Parameter (Id)
2283 then
2284 Formal := First_Formal (Id);
2285 Actual := First_Actual (Call);
2286 while Present (Actual) and then Present (Formal) loop
2287 if Actual = N then
2288 if Ekind_In (Formal, E_Out_Parameter,
2289 E_In_Out_Parameter)
2290 then
2291 Is_Writable_Actual := True;
2292 end if;
2294 exit;
2295 end if;
2297 Next_Formal (Formal);
2298 Next_Actual (Actual);
2299 end loop;
2300 end if;
2301 end;
2302 end if;
2304 if Is_Writable_Actual then
2306 -- Skip checking the error in non-elementary types since
2307 -- RM 6.4.1(6.15/3) is restricted to elementary types, but
2308 -- store this actual in Writable_Actuals_List since it is
2309 -- needed to perform checks on other constructs that have
2310 -- arbitrary order of evaluation (for example, aggregates).
2312 if not Is_Elementary_Type (Etype (N)) then
2313 if not Contains (Writable_Actuals_List, N) then
2314 Append_New_Elmt (N, To => Writable_Actuals_List);
2315 end if;
2317 -- Second occurrence of an elementary type writable actual
2319 elsif Contains (Writable_Actuals_List, N) then
2321 -- Report the error on the second occurrence of the
2322 -- identifier. We cannot assume that N is the second
2323 -- occurrence (according to their location in the
2324 -- sources), since Traverse_Func walks through Field2
2325 -- last (see comment in the body of Traverse_Func).
2327 declare
2328 Elmt : Elmt_Id;
2330 begin
2331 Elmt := First_Elmt (Writable_Actuals_List);
2332 while Present (Elmt)
2333 and then Entity (Node (Elmt)) /= Entity (N)
2334 loop
2335 Next_Elmt (Elmt);
2336 end loop;
2338 if Sloc (N) > Sloc (Node (Elmt)) then
2339 Error_Node := N;
2340 else
2341 Error_Node := Node (Elmt);
2342 end if;
2344 Error_Msg_NE
2345 ("value may be affected by call to & "
2346 & "because order of evaluation is arbitrary",
2347 Error_Node, Id);
2348 return Abandon;
2349 end;
2351 -- First occurrence of a elementary type writable actual
2353 else
2354 Append_New_Elmt (N, To => Writable_Actuals_List);
2355 end if;
2357 else
2358 if Identifiers_List = No_Elist then
2359 Identifiers_List := New_Elmt_List;
2360 end if;
2362 Append_Unique_Elmt (N, Identifiers_List);
2363 end if;
2364 end if;
2366 return OK;
2367 end Check_Node;
2369 --------------
2370 -- Contains --
2371 --------------
2373 function Contains
2374 (List : Elist_Id;
2375 N : Node_Id) return Boolean
2377 pragma Assert (Nkind (N) in N_Has_Entity);
2379 Elmt : Elmt_Id;
2381 begin
2382 if List = No_Elist then
2383 return False;
2384 end if;
2386 Elmt := First_Elmt (List);
2387 while Present (Elmt) loop
2388 if Entity (Node (Elmt)) = Entity (N) then
2389 return True;
2390 else
2391 Next_Elmt (Elmt);
2392 end if;
2393 end loop;
2395 return False;
2396 end Contains;
2398 ------------------
2399 -- Do_Traversal --
2400 ------------------
2402 procedure Do_Traversal is new Traverse_Proc (Check_Node);
2403 -- The traversal procedure
2405 -- Start of processing for Collect_Identifiers
2407 begin
2408 if Present (Error_Node) then
2409 return;
2410 end if;
2412 if Nkind (N) in N_Subexpr and then Is_OK_Static_Expression (N) then
2413 return;
2414 end if;
2416 Do_Traversal (N);
2417 end Collect_Identifiers;
2419 ---------------------
2420 -- Get_Function_Id --
2421 ---------------------
2423 function Get_Function_Id (Call : Node_Id) return Entity_Id is
2424 Nam : constant Node_Id := Name (Call);
2425 Id : Entity_Id;
2427 begin
2428 if Nkind (Nam) = N_Explicit_Dereference then
2429 Id := Etype (Nam);
2430 pragma Assert (Ekind (Id) = E_Subprogram_Type);
2432 elsif Nkind (Nam) = N_Selected_Component then
2433 Id := Entity (Selector_Name (Nam));
2435 elsif Nkind (Nam) = N_Indexed_Component then
2436 Id := Entity (Selector_Name (Prefix (Nam)));
2438 else
2439 Id := Entity (Nam);
2440 end if;
2442 return Id;
2443 end Get_Function_Id;
2445 -------------------------------
2446 -- Preanalyze_Without_Errors --
2447 -------------------------------
2449 procedure Preanalyze_Without_Errors (N : Node_Id) is
2450 Status : constant Boolean := Get_Ignore_Errors;
2451 begin
2452 Set_Ignore_Errors (True);
2453 Preanalyze (N);
2454 Set_Ignore_Errors (Status);
2455 end Preanalyze_Without_Errors;
2457 -- Start of processing for Check_Function_Writable_Actuals
2459 begin
2460 -- The check only applies to Ada 2012 code on which Check_Actuals has
2461 -- been set, and only to constructs that have multiple constituents
2462 -- whose order of evaluation is not specified by the language.
2464 if Ada_Version < Ada_2012
2465 or else not Check_Actuals (N)
2466 or else (not (Nkind (N) in N_Op)
2467 and then not (Nkind (N) in N_Membership_Test)
2468 and then not Nkind_In (N, N_Range,
2469 N_Aggregate,
2470 N_Extension_Aggregate,
2471 N_Full_Type_Declaration,
2472 N_Function_Call,
2473 N_Procedure_Call_Statement,
2474 N_Entry_Call_Statement))
2475 or else (Nkind (N) = N_Full_Type_Declaration
2476 and then not Is_Record_Type (Defining_Identifier (N)))
2478 -- In addition, this check only applies to source code, not to code
2479 -- generated by constraint checks.
2481 or else not Comes_From_Source (N)
2482 then
2483 return;
2484 end if;
2486 -- If a construct C has two or more direct constituents that are names
2487 -- or expressions whose evaluation may occur in an arbitrary order, at
2488 -- least one of which contains a function call with an in out or out
2489 -- parameter, then the construct is legal only if: for each name N that
2490 -- is passed as a parameter of mode in out or out to some inner function
2491 -- call C2 (not including the construct C itself), there is no other
2492 -- name anywhere within a direct constituent of the construct C other
2493 -- than the one containing C2, that is known to refer to the same
2494 -- object (RM 6.4.1(6.17/3)).
2496 case Nkind (N) is
2497 when N_Range =>
2498 Collect_Identifiers (Low_Bound (N));
2499 Collect_Identifiers (High_Bound (N));
2501 when N_Op | N_Membership_Test =>
2502 declare
2503 Expr : Node_Id;
2505 begin
2506 Collect_Identifiers (Left_Opnd (N));
2508 if Present (Right_Opnd (N)) then
2509 Collect_Identifiers (Right_Opnd (N));
2510 end if;
2512 if Nkind_In (N, N_In, N_Not_In)
2513 and then Present (Alternatives (N))
2514 then
2515 Expr := First (Alternatives (N));
2516 while Present (Expr) loop
2517 Collect_Identifiers (Expr);
2519 Next (Expr);
2520 end loop;
2521 end if;
2522 end;
2524 when N_Full_Type_Declaration =>
2525 declare
2526 function Get_Record_Part (N : Node_Id) return Node_Id;
2527 -- Return the record part of this record type definition
2529 function Get_Record_Part (N : Node_Id) return Node_Id is
2530 Type_Def : constant Node_Id := Type_Definition (N);
2531 begin
2532 if Nkind (Type_Def) = N_Derived_Type_Definition then
2533 return Record_Extension_Part (Type_Def);
2534 else
2535 return Type_Def;
2536 end if;
2537 end Get_Record_Part;
2539 Comp : Node_Id;
2540 Def_Id : Entity_Id := Defining_Identifier (N);
2541 Rec : Node_Id := Get_Record_Part (N);
2543 begin
2544 -- No need to perform any analysis if the record has no
2545 -- components
2547 if No (Rec) or else No (Component_List (Rec)) then
2548 return;
2549 end if;
2551 -- Collect the identifiers starting from the deepest
2552 -- derivation. Done to report the error in the deepest
2553 -- derivation.
2555 loop
2556 if Present (Component_List (Rec)) then
2557 Comp := First (Component_Items (Component_List (Rec)));
2558 while Present (Comp) loop
2559 if Nkind (Comp) = N_Component_Declaration
2560 and then Present (Expression (Comp))
2561 then
2562 Collect_Identifiers (Expression (Comp));
2563 end if;
2565 Next (Comp);
2566 end loop;
2567 end if;
2569 exit when No (Underlying_Type (Etype (Def_Id)))
2570 or else Base_Type (Underlying_Type (Etype (Def_Id)))
2571 = Def_Id;
2573 Def_Id := Base_Type (Underlying_Type (Etype (Def_Id)));
2574 Rec := Get_Record_Part (Parent (Def_Id));
2575 end loop;
2576 end;
2578 when N_Subprogram_Call |
2579 N_Entry_Call_Statement =>
2580 declare
2581 Id : constant Entity_Id := Get_Function_Id (N);
2582 Formal : Node_Id;
2583 Actual : Node_Id;
2585 begin
2586 Formal := First_Formal (Id);
2587 Actual := First_Actual (N);
2588 while Present (Actual) and then Present (Formal) loop
2589 if Ekind_In (Formal, E_Out_Parameter,
2590 E_In_Out_Parameter)
2591 then
2592 Collect_Identifiers (Actual);
2593 end if;
2595 Next_Formal (Formal);
2596 Next_Actual (Actual);
2597 end loop;
2598 end;
2600 when N_Aggregate |
2601 N_Extension_Aggregate =>
2602 declare
2603 Assoc : Node_Id;
2604 Choice : Node_Id;
2605 Comp_Expr : Node_Id;
2607 begin
2608 -- Handle the N_Others_Choice of array aggregates with static
2609 -- bounds. There is no need to perform this analysis in
2610 -- aggregates without static bounds since we cannot evaluate
2611 -- if the N_Others_Choice covers several elements. There is
2612 -- no need to handle the N_Others choice of record aggregates
2613 -- since at this stage it has been already expanded by
2614 -- Resolve_Record_Aggregate.
2616 if Is_Array_Type (Etype (N))
2617 and then Nkind (N) = N_Aggregate
2618 and then Present (Aggregate_Bounds (N))
2619 and then Compile_Time_Known_Bounds (Etype (N))
2620 and then Expr_Value (High_Bound (Aggregate_Bounds (N)))
2622 Expr_Value (Low_Bound (Aggregate_Bounds (N)))
2623 then
2624 declare
2625 Count_Components : Uint := Uint_0;
2626 Num_Components : Uint;
2627 Others_Assoc : Node_Id;
2628 Others_Choice : Node_Id := Empty;
2629 Others_Box_Present : Boolean := False;
2631 begin
2632 -- Count positional associations
2634 if Present (Expressions (N)) then
2635 Comp_Expr := First (Expressions (N));
2636 while Present (Comp_Expr) loop
2637 Count_Components := Count_Components + 1;
2638 Next (Comp_Expr);
2639 end loop;
2640 end if;
2642 -- Count the rest of elements and locate the N_Others
2643 -- choice (if any)
2645 Assoc := First (Component_Associations (N));
2646 while Present (Assoc) loop
2647 Choice := First (Choices (Assoc));
2648 while Present (Choice) loop
2649 if Nkind (Choice) = N_Others_Choice then
2650 Others_Assoc := Assoc;
2651 Others_Choice := Choice;
2652 Others_Box_Present := Box_Present (Assoc);
2654 -- Count several components
2656 elsif Nkind_In (Choice, N_Range,
2657 N_Subtype_Indication)
2658 or else (Is_Entity_Name (Choice)
2659 and then Is_Type (Entity (Choice)))
2660 then
2661 declare
2662 L, H : Node_Id;
2663 begin
2664 Get_Index_Bounds (Choice, L, H);
2665 pragma Assert
2666 (Compile_Time_Known_Value (L)
2667 and then Compile_Time_Known_Value (H));
2668 Count_Components :=
2669 Count_Components
2670 + Expr_Value (H) - Expr_Value (L) + 1;
2671 end;
2673 -- Count single component. No other case available
2674 -- since we are handling an aggregate with static
2675 -- bounds.
2677 else
2678 pragma Assert (Is_OK_Static_Expression (Choice)
2679 or else Nkind (Choice) = N_Identifier
2680 or else Nkind (Choice) = N_Integer_Literal);
2682 Count_Components := Count_Components + 1;
2683 end if;
2685 Next (Choice);
2686 end loop;
2688 Next (Assoc);
2689 end loop;
2691 Num_Components :=
2692 Expr_Value (High_Bound (Aggregate_Bounds (N))) -
2693 Expr_Value (Low_Bound (Aggregate_Bounds (N))) + 1;
2695 pragma Assert (Count_Components <= Num_Components);
2697 -- Handle the N_Others choice if it covers several
2698 -- components
2700 if Present (Others_Choice)
2701 and then (Num_Components - Count_Components) > 1
2702 then
2703 if not Others_Box_Present then
2705 -- At this stage, if expansion is active, the
2706 -- expression of the others choice has not been
2707 -- analyzed. Hence we generate a duplicate and
2708 -- we analyze it silently to have available the
2709 -- minimum decoration required to collect the
2710 -- identifiers.
2712 if not Expander_Active then
2713 Comp_Expr := Expression (Others_Assoc);
2714 else
2715 Comp_Expr :=
2716 New_Copy_Tree (Expression (Others_Assoc));
2717 Preanalyze_Without_Errors (Comp_Expr);
2718 end if;
2720 Collect_Identifiers (Comp_Expr);
2722 if Writable_Actuals_List /= No_Elist then
2724 -- As suggested by Robert, at current stage we
2725 -- report occurrences of this case as warnings.
2727 Error_Msg_N
2728 ("writable function parameter may affect "
2729 & "value in other component because order "
2730 & "of evaluation is unspecified??",
2731 Node (First_Elmt (Writable_Actuals_List)));
2732 end if;
2733 end if;
2734 end if;
2735 end;
2737 -- For an array aggregate, a discrete_choice_list that has
2738 -- a nonstatic range is considered as two or more separate
2739 -- occurrences of the expression (RM 6.4.1(20/3)).
2741 elsif Is_Array_Type (Etype (N))
2742 and then Nkind (N) = N_Aggregate
2743 and then Present (Aggregate_Bounds (N))
2744 and then not Compile_Time_Known_Bounds (Etype (N))
2745 then
2746 -- Collect identifiers found in the dynamic bounds
2748 declare
2749 Count_Components : Natural := 0;
2750 Low, High : Node_Id;
2752 begin
2753 Assoc := First (Component_Associations (N));
2754 while Present (Assoc) loop
2755 Choice := First (Choices (Assoc));
2756 while Present (Choice) loop
2757 if Nkind_In (Choice, N_Range,
2758 N_Subtype_Indication)
2759 or else (Is_Entity_Name (Choice)
2760 and then Is_Type (Entity (Choice)))
2761 then
2762 Get_Index_Bounds (Choice, Low, High);
2764 if not Compile_Time_Known_Value (Low) then
2765 Collect_Identifiers (Low);
2767 if No (Aggr_Error_Node) then
2768 Aggr_Error_Node := Low;
2769 end if;
2770 end if;
2772 if not Compile_Time_Known_Value (High) then
2773 Collect_Identifiers (High);
2775 if No (Aggr_Error_Node) then
2776 Aggr_Error_Node := High;
2777 end if;
2778 end if;
2780 -- The RM rule is violated if there is more than
2781 -- a single choice in a component association.
2783 else
2784 Count_Components := Count_Components + 1;
2786 if No (Aggr_Error_Node)
2787 and then Count_Components > 1
2788 then
2789 Aggr_Error_Node := Choice;
2790 end if;
2792 if not Compile_Time_Known_Value (Choice) then
2793 Collect_Identifiers (Choice);
2794 end if;
2795 end if;
2797 Next (Choice);
2798 end loop;
2800 Next (Assoc);
2801 end loop;
2802 end;
2803 end if;
2805 -- Handle ancestor part of extension aggregates
2807 if Nkind (N) = N_Extension_Aggregate then
2808 Collect_Identifiers (Ancestor_Part (N));
2809 end if;
2811 -- Handle positional associations
2813 if Present (Expressions (N)) then
2814 Comp_Expr := First (Expressions (N));
2815 while Present (Comp_Expr) loop
2816 if not Is_OK_Static_Expression (Comp_Expr) then
2817 Collect_Identifiers (Comp_Expr);
2818 end if;
2820 Next (Comp_Expr);
2821 end loop;
2822 end if;
2824 -- Handle discrete associations
2826 if Present (Component_Associations (N)) then
2827 Assoc := First (Component_Associations (N));
2828 while Present (Assoc) loop
2830 if not Box_Present (Assoc) then
2831 Choice := First (Choices (Assoc));
2832 while Present (Choice) loop
2834 -- For now we skip discriminants since it requires
2835 -- performing the analysis in two phases: first one
2836 -- analyzing discriminants and second one analyzing
2837 -- the rest of components since discriminants are
2838 -- evaluated prior to components: too much extra
2839 -- work to detect a corner case???
2841 if Nkind (Choice) in N_Has_Entity
2842 and then Present (Entity (Choice))
2843 and then Ekind (Entity (Choice)) = E_Discriminant
2844 then
2845 null;
2847 elsif Box_Present (Assoc) then
2848 null;
2850 else
2851 if not Analyzed (Expression (Assoc)) then
2852 Comp_Expr :=
2853 New_Copy_Tree (Expression (Assoc));
2854 Set_Parent (Comp_Expr, Parent (N));
2855 Preanalyze_Without_Errors (Comp_Expr);
2856 else
2857 Comp_Expr := Expression (Assoc);
2858 end if;
2860 Collect_Identifiers (Comp_Expr);
2861 end if;
2863 Next (Choice);
2864 end loop;
2865 end if;
2867 Next (Assoc);
2868 end loop;
2869 end if;
2870 end;
2872 when others =>
2873 return;
2874 end case;
2876 -- No further action needed if we already reported an error
2878 if Present (Error_Node) then
2879 return;
2880 end if;
2882 -- Check violation of RM 6.20/3 in aggregates
2884 if Present (Aggr_Error_Node)
2885 and then Writable_Actuals_List /= No_Elist
2886 then
2887 Error_Msg_N
2888 ("value may be affected by call in other component because they "
2889 & "are evaluated in unspecified order",
2890 Node (First_Elmt (Writable_Actuals_List)));
2891 return;
2892 end if;
2894 -- Check if some writable argument of a function is referenced
2896 if Writable_Actuals_List /= No_Elist
2897 and then Identifiers_List /= No_Elist
2898 then
2899 declare
2900 Elmt_1 : Elmt_Id;
2901 Elmt_2 : Elmt_Id;
2903 begin
2904 Elmt_1 := First_Elmt (Writable_Actuals_List);
2905 while Present (Elmt_1) loop
2906 Elmt_2 := First_Elmt (Identifiers_List);
2907 while Present (Elmt_2) loop
2908 if Entity (Node (Elmt_1)) = Entity (Node (Elmt_2)) then
2909 case Nkind (Parent (Node (Elmt_2))) is
2910 when N_Aggregate |
2911 N_Component_Association |
2912 N_Component_Declaration =>
2913 Error_Msg_N
2914 ("value may be affected by call in other "
2915 & "component because they are evaluated "
2916 & "in unspecified order",
2917 Node (Elmt_2));
2919 when N_In | N_Not_In =>
2920 Error_Msg_N
2921 ("value may be affected by call in other "
2922 & "alternative because they are evaluated "
2923 & "in unspecified order",
2924 Node (Elmt_2));
2926 when others =>
2927 Error_Msg_N
2928 ("value of actual may be affected by call in "
2929 & "other actual because they are evaluated "
2930 & "in unspecified order",
2931 Node (Elmt_2));
2932 end case;
2933 end if;
2935 Next_Elmt (Elmt_2);
2936 end loop;
2938 Next_Elmt (Elmt_1);
2939 end loop;
2940 end;
2941 end if;
2942 end Check_Function_Writable_Actuals;
2944 --------------------------------
2945 -- Check_Implicit_Dereference --
2946 --------------------------------
2948 procedure Check_Implicit_Dereference (N : Node_Id; Typ : Entity_Id) is
2949 Disc : Entity_Id;
2950 Desig : Entity_Id;
2951 Nam : Node_Id;
2953 begin
2954 if Nkind (N) = N_Indexed_Component
2955 and then Present (Generalized_Indexing (N))
2956 then
2957 Nam := Generalized_Indexing (N);
2958 else
2959 Nam := N;
2960 end if;
2962 if Ada_Version < Ada_2012
2963 or else not Has_Implicit_Dereference (Base_Type (Typ))
2964 then
2965 return;
2967 elsif not Comes_From_Source (N)
2968 and then Nkind (N) /= N_Indexed_Component
2969 then
2970 return;
2972 elsif Is_Entity_Name (Nam) and then Is_Type (Entity (Nam)) then
2973 null;
2975 else
2976 Disc := First_Discriminant (Typ);
2977 while Present (Disc) loop
2978 if Has_Implicit_Dereference (Disc) then
2979 Desig := Designated_Type (Etype (Disc));
2980 Add_One_Interp (Nam, Disc, Desig);
2982 -- If the node is a generalized indexing, add interpretation
2983 -- to that node as well, for subsequent resolution.
2985 if Nkind (N) = N_Indexed_Component then
2986 Add_One_Interp (N, Disc, Desig);
2987 end if;
2989 -- If the operation comes from a generic unit and the context
2990 -- is a selected component, the selector name may be global
2991 -- and set in the instance already. Remove the entity to
2992 -- force resolution of the selected component, and the
2993 -- generation of an explicit dereference if needed.
2995 if In_Instance
2996 and then Nkind (Parent (Nam)) = N_Selected_Component
2997 then
2998 Set_Entity (Selector_Name (Parent (Nam)), Empty);
2999 end if;
3001 exit;
3002 end if;
3004 Next_Discriminant (Disc);
3005 end loop;
3006 end if;
3007 end Check_Implicit_Dereference;
3009 ----------------------------------
3010 -- Check_Internal_Protected_Use --
3011 ----------------------------------
3013 procedure Check_Internal_Protected_Use (N : Node_Id; Nam : Entity_Id) is
3014 S : Entity_Id;
3015 Prot : Entity_Id;
3017 begin
3018 S := Current_Scope;
3019 while Present (S) loop
3020 if S = Standard_Standard then
3021 return;
3023 elsif Ekind (S) = E_Function
3024 and then Ekind (Scope (S)) = E_Protected_Type
3025 then
3026 Prot := Scope (S);
3027 exit;
3028 end if;
3030 S := Scope (S);
3031 end loop;
3033 if Scope (Nam) = Prot and then Ekind (Nam) /= E_Function then
3035 -- An indirect function call (e.g. a callback within a protected
3036 -- function body) is not statically illegal. If the access type is
3037 -- anonymous and is the type of an access parameter, the scope of Nam
3038 -- will be the protected type, but it is not a protected operation.
3040 if Ekind (Nam) = E_Subprogram_Type
3041 and then
3042 Nkind (Associated_Node_For_Itype (Nam)) = N_Function_Specification
3043 then
3044 null;
3046 elsif Nkind (N) = N_Subprogram_Renaming_Declaration then
3047 Error_Msg_N
3048 ("within protected function cannot use protected "
3049 & "procedure in renaming or as generic actual", N);
3051 elsif Nkind (N) = N_Attribute_Reference then
3052 Error_Msg_N
3053 ("within protected function cannot take access of "
3054 & " protected procedure", N);
3056 else
3057 Error_Msg_N
3058 ("within protected function, protected object is constant", N);
3059 Error_Msg_N
3060 ("\cannot call operation that may modify it", N);
3061 end if;
3062 end if;
3063 end Check_Internal_Protected_Use;
3065 ---------------------------------------
3066 -- Check_Later_Vs_Basic_Declarations --
3067 ---------------------------------------
3069 procedure Check_Later_Vs_Basic_Declarations
3070 (Decls : List_Id;
3071 During_Parsing : Boolean)
3073 Body_Sloc : Source_Ptr;
3074 Decl : Node_Id;
3076 function Is_Later_Declarative_Item (Decl : Node_Id) return Boolean;
3077 -- Return whether Decl is considered as a declarative item.
3078 -- When During_Parsing is True, the semantics of Ada 83 is followed.
3079 -- When During_Parsing is False, the semantics of SPARK is followed.
3081 -------------------------------
3082 -- Is_Later_Declarative_Item --
3083 -------------------------------
3085 function Is_Later_Declarative_Item (Decl : Node_Id) return Boolean is
3086 begin
3087 if Nkind (Decl) in N_Later_Decl_Item then
3088 return True;
3090 elsif Nkind (Decl) = N_Pragma then
3091 return True;
3093 elsif During_Parsing then
3094 return False;
3096 -- In SPARK, a package declaration is not considered as a later
3097 -- declarative item.
3099 elsif Nkind (Decl) = N_Package_Declaration then
3100 return False;
3102 -- In SPARK, a renaming is considered as a later declarative item
3104 elsif Nkind (Decl) in N_Renaming_Declaration then
3105 return True;
3107 else
3108 return False;
3109 end if;
3110 end Is_Later_Declarative_Item;
3112 -- Start of processing for Check_Later_Vs_Basic_Declarations
3114 begin
3115 Decl := First (Decls);
3117 -- Loop through sequence of basic declarative items
3119 Outer : while Present (Decl) loop
3120 if not Nkind_In (Decl, N_Subprogram_Body, N_Package_Body, N_Task_Body)
3121 and then Nkind (Decl) not in N_Body_Stub
3122 then
3123 Next (Decl);
3125 -- Once a body is encountered, we only allow later declarative
3126 -- items. The inner loop checks the rest of the list.
3128 else
3129 Body_Sloc := Sloc (Decl);
3131 Inner : while Present (Decl) loop
3132 if not Is_Later_Declarative_Item (Decl) then
3133 if During_Parsing then
3134 if Ada_Version = Ada_83 then
3135 Error_Msg_Sloc := Body_Sloc;
3136 Error_Msg_N
3137 ("(Ada 83) decl cannot appear after body#", Decl);
3138 end if;
3139 else
3140 Error_Msg_Sloc := Body_Sloc;
3141 Check_SPARK_05_Restriction
3142 ("decl cannot appear after body#", Decl);
3143 end if;
3144 end if;
3146 Next (Decl);
3147 end loop Inner;
3148 end if;
3149 end loop Outer;
3150 end Check_Later_Vs_Basic_Declarations;
3152 ---------------------------
3153 -- Check_No_Hidden_State --
3154 ---------------------------
3156 procedure Check_No_Hidden_State (Id : Entity_Id) is
3157 function Has_Null_Abstract_State (Pkg : Entity_Id) return Boolean;
3158 -- Determine whether the entity of a package denoted by Pkg has a null
3159 -- abstract state.
3161 -----------------------------
3162 -- Has_Null_Abstract_State --
3163 -----------------------------
3165 function Has_Null_Abstract_State (Pkg : Entity_Id) return Boolean is
3166 States : constant Elist_Id := Abstract_States (Pkg);
3168 begin
3169 -- Check first available state of related package. A null abstract
3170 -- state always appears as the sole element of the state list.
3172 return
3173 Present (States)
3174 and then Is_Null_State (Node (First_Elmt (States)));
3175 end Has_Null_Abstract_State;
3177 -- Local variables
3179 Context : Entity_Id := Empty;
3180 Not_Visible : Boolean := False;
3181 Scop : Entity_Id;
3183 -- Start of processing for Check_No_Hidden_State
3185 begin
3186 pragma Assert (Ekind_In (Id, E_Abstract_State, E_Variable));
3188 -- Find the proper context where the object or state appears
3190 Scop := Scope (Id);
3191 while Present (Scop) loop
3192 Context := Scop;
3194 -- Keep track of the context's visibility
3196 Not_Visible := Not_Visible or else In_Private_Part (Context);
3198 -- Prevent the search from going too far
3200 if Context = Standard_Standard then
3201 return;
3203 -- Objects and states that appear immediately within a subprogram or
3204 -- inside a construct nested within a subprogram do not introduce a
3205 -- hidden state. They behave as local variable declarations.
3207 elsif Is_Subprogram (Context) then
3208 return;
3210 -- When examining a package body, use the entity of the spec as it
3211 -- carries the abstract state declarations.
3213 elsif Ekind (Context) = E_Package_Body then
3214 Context := Spec_Entity (Context);
3215 end if;
3217 -- Stop the traversal when a package subject to a null abstract state
3218 -- has been found.
3220 if Ekind_In (Context, E_Generic_Package, E_Package)
3221 and then Has_Null_Abstract_State (Context)
3222 then
3223 exit;
3224 end if;
3226 Scop := Scope (Scop);
3227 end loop;
3229 -- At this point we know that there is at least one package with a null
3230 -- abstract state in visibility. Emit an error message unconditionally
3231 -- if the entity being processed is a state because the placement of the
3232 -- related package is irrelevant. This is not the case for objects as
3233 -- the intermediate context matters.
3235 if Present (Context)
3236 and then (Ekind (Id) = E_Abstract_State or else Not_Visible)
3237 then
3238 Error_Msg_N ("cannot introduce hidden state &", Id);
3239 Error_Msg_NE ("\package & has null abstract state", Id, Context);
3240 end if;
3241 end Check_No_Hidden_State;
3243 ----------------------------------------
3244 -- Check_Nonvolatile_Function_Profile --
3245 ----------------------------------------
3247 procedure Check_Nonvolatile_Function_Profile (Func_Id : Entity_Id) is
3248 Formal : Entity_Id;
3250 begin
3251 -- Inspect all formal parameters
3253 Formal := First_Formal (Func_Id);
3254 while Present (Formal) loop
3255 if Is_Effectively_Volatile (Etype (Formal)) then
3256 Error_Msg_NE
3257 ("nonvolatile function & cannot have a volatile parameter",
3258 Formal, Func_Id);
3259 end if;
3261 Next_Formal (Formal);
3262 end loop;
3264 -- Inspect the return type
3266 if Is_Effectively_Volatile (Etype (Func_Id)) then
3267 Error_Msg_NE
3268 ("nonvolatile function & cannot have a volatile return type",
3269 Result_Definition (Parent (Func_Id)), Func_Id);
3270 end if;
3271 end Check_Nonvolatile_Function_Profile;
3273 ------------------------------------------
3274 -- Check_Potentially_Blocking_Operation --
3275 ------------------------------------------
3277 procedure Check_Potentially_Blocking_Operation (N : Node_Id) is
3278 S : Entity_Id;
3280 begin
3281 -- N is one of the potentially blocking operations listed in 9.5.1(8).
3282 -- When pragma Detect_Blocking is active, the run time will raise
3283 -- Program_Error. Here we only issue a warning, since we generally
3284 -- support the use of potentially blocking operations in the absence
3285 -- of the pragma.
3287 -- Indirect blocking through a subprogram call cannot be diagnosed
3288 -- statically without interprocedural analysis, so we do not attempt
3289 -- to do it here.
3291 S := Scope (Current_Scope);
3292 while Present (S) and then S /= Standard_Standard loop
3293 if Is_Protected_Type (S) then
3294 Error_Msg_N
3295 ("potentially blocking operation in protected operation??", N);
3296 return;
3297 end if;
3299 S := Scope (S);
3300 end loop;
3301 end Check_Potentially_Blocking_Operation;
3303 ---------------------------------
3304 -- Check_Result_And_Post_State --
3305 ---------------------------------
3307 procedure Check_Result_And_Post_State (Subp_Id : Entity_Id) is
3308 procedure Check_Result_And_Post_State_In_Pragma
3309 (Prag : Node_Id;
3310 Result_Seen : in out Boolean);
3311 -- Determine whether pragma Prag mentions attribute 'Result and whether
3312 -- the pragma contains an expression that evaluates differently in pre-
3313 -- and post-state. Prag is a [refined] postcondition or a contract-cases
3314 -- pragma. Result_Seen is set when the pragma mentions attribute 'Result
3316 function Has_In_Out_Parameter (Subp_Id : Entity_Id) return Boolean;
3317 -- Determine whether subprogram Subp_Id contains at least one IN OUT
3318 -- formal parameter.
3320 -------------------------------------------
3321 -- Check_Result_And_Post_State_In_Pragma --
3322 -------------------------------------------
3324 procedure Check_Result_And_Post_State_In_Pragma
3325 (Prag : Node_Id;
3326 Result_Seen : in out Boolean)
3328 procedure Check_Expression (Expr : Node_Id);
3329 -- Perform the 'Result and post-state checks on a given expression
3331 function Is_Function_Result (N : Node_Id) return Traverse_Result;
3332 -- Attempt to find attribute 'Result in a subtree denoted by N
3334 function Is_Trivial_Boolean (N : Node_Id) return Boolean;
3335 -- Determine whether source node N denotes "True" or "False"
3337 function Mentions_Post_State (N : Node_Id) return Boolean;
3338 -- Determine whether a subtree denoted by N mentions any construct
3339 -- that denotes a post-state.
3341 procedure Check_Function_Result is
3342 new Traverse_Proc (Is_Function_Result);
3344 ----------------------
3345 -- Check_Expression --
3346 ----------------------
3348 procedure Check_Expression (Expr : Node_Id) is
3349 begin
3350 if not Is_Trivial_Boolean (Expr) then
3351 Check_Function_Result (Expr);
3353 if not Mentions_Post_State (Expr) then
3354 if Pragma_Name (Prag) = Name_Contract_Cases then
3355 Error_Msg_NE
3356 ("contract case does not check the outcome of calling "
3357 & "&?T?", Expr, Subp_Id);
3359 elsif Pragma_Name (Prag) = Name_Refined_Post then
3360 Error_Msg_NE
3361 ("refined postcondition does not check the outcome of "
3362 & "calling &?T?", Prag, Subp_Id);
3364 else
3365 Error_Msg_NE
3366 ("postcondition does not check the outcome of calling "
3367 & "&?T?", Prag, Subp_Id);
3368 end if;
3369 end if;
3370 end if;
3371 end Check_Expression;
3373 ------------------------
3374 -- Is_Function_Result --
3375 ------------------------
3377 function Is_Function_Result (N : Node_Id) return Traverse_Result is
3378 begin
3379 if Is_Attribute_Result (N) then
3380 Result_Seen := True;
3381 return Abandon;
3383 -- Continue the traversal
3385 else
3386 return OK;
3387 end if;
3388 end Is_Function_Result;
3390 ------------------------
3391 -- Is_Trivial_Boolean --
3392 ------------------------
3394 function Is_Trivial_Boolean (N : Node_Id) return Boolean is
3395 begin
3396 return
3397 Comes_From_Source (N)
3398 and then Is_Entity_Name (N)
3399 and then (Entity (N) = Standard_True
3400 or else
3401 Entity (N) = Standard_False);
3402 end Is_Trivial_Boolean;
3404 -------------------------
3405 -- Mentions_Post_State --
3406 -------------------------
3408 function Mentions_Post_State (N : Node_Id) return Boolean is
3409 Post_State_Seen : Boolean := False;
3411 function Is_Post_State (N : Node_Id) return Traverse_Result;
3412 -- Attempt to find a construct that denotes a post-state. If this
3413 -- is the case, set flag Post_State_Seen.
3415 -------------------
3416 -- Is_Post_State --
3417 -------------------
3419 function Is_Post_State (N : Node_Id) return Traverse_Result is
3420 Ent : Entity_Id;
3422 begin
3423 if Nkind_In (N, N_Explicit_Dereference, N_Function_Call) then
3424 Post_State_Seen := True;
3425 return Abandon;
3427 elsif Nkind_In (N, N_Expanded_Name, N_Identifier) then
3428 Ent := Entity (N);
3430 -- The entity may be modifiable through an implicit
3431 -- dereference.
3433 if No (Ent)
3434 or else Ekind (Ent) in Assignable_Kind
3435 or else (Is_Access_Type (Etype (Ent))
3436 and then Nkind (Parent (N)) =
3437 N_Selected_Component)
3438 then
3439 Post_State_Seen := True;
3440 return Abandon;
3441 end if;
3443 elsif Nkind (N) = N_Attribute_Reference then
3444 if Attribute_Name (N) = Name_Old then
3445 return Skip;
3447 elsif Attribute_Name (N) = Name_Result then
3448 Post_State_Seen := True;
3449 return Abandon;
3450 end if;
3451 end if;
3453 return OK;
3454 end Is_Post_State;
3456 procedure Find_Post_State is new Traverse_Proc (Is_Post_State);
3458 -- Start of processing for Mentions_Post_State
3460 begin
3461 Find_Post_State (N);
3463 return Post_State_Seen;
3464 end Mentions_Post_State;
3466 -- Local variables
3468 Expr : constant Node_Id :=
3469 Get_Pragma_Arg
3470 (First (Pragma_Argument_Associations (Prag)));
3471 Nam : constant Name_Id := Pragma_Name (Prag);
3472 CCase : Node_Id;
3474 -- Start of processing for Check_Result_And_Post_State_In_Pragma
3476 begin
3477 -- Examine all consequences
3479 if Nam = Name_Contract_Cases then
3480 CCase := First (Component_Associations (Expr));
3481 while Present (CCase) loop
3482 Check_Expression (Expression (CCase));
3484 Next (CCase);
3485 end loop;
3487 -- Examine the expression of a postcondition
3489 else pragma Assert (Nam_In (Nam, Name_Postcondition,
3490 Name_Refined_Post));
3491 Check_Expression (Expr);
3492 end if;
3493 end Check_Result_And_Post_State_In_Pragma;
3495 --------------------------
3496 -- Has_In_Out_Parameter --
3497 --------------------------
3499 function Has_In_Out_Parameter (Subp_Id : Entity_Id) return Boolean is
3500 Formal : Entity_Id;
3502 begin
3503 -- Traverse the formals looking for an IN OUT parameter
3505 Formal := First_Formal (Subp_Id);
3506 while Present (Formal) loop
3507 if Ekind (Formal) = E_In_Out_Parameter then
3508 return True;
3509 end if;
3511 Next_Formal (Formal);
3512 end loop;
3514 return False;
3515 end Has_In_Out_Parameter;
3517 -- Local variables
3519 Items : constant Node_Id := Contract (Subp_Id);
3520 Subp_Decl : constant Node_Id := Unit_Declaration_Node (Subp_Id);
3521 Case_Prag : Node_Id := Empty;
3522 Post_Prag : Node_Id := Empty;
3523 Prag : Node_Id;
3524 Seen_In_Case : Boolean := False;
3525 Seen_In_Post : Boolean := False;
3526 Spec_Id : Entity_Id;
3528 -- Start of processing for Check_Result_And_Post_State
3530 begin
3531 -- The lack of attribute 'Result or a post-state is classified as a
3532 -- suspicious contract. Do not perform the check if the corresponding
3533 -- swich is not set.
3535 if not Warn_On_Suspicious_Contract then
3536 return;
3538 -- Nothing to do if there is no contract
3540 elsif No (Items) then
3541 return;
3542 end if;
3544 -- Retrieve the entity of the subprogram spec (if any)
3546 if Nkind (Subp_Decl) = N_Subprogram_Body
3547 and then Present (Corresponding_Spec (Subp_Decl))
3548 then
3549 Spec_Id := Corresponding_Spec (Subp_Decl);
3551 elsif Nkind (Subp_Decl) = N_Subprogram_Body_Stub
3552 and then Present (Corresponding_Spec_Of_Stub (Subp_Decl))
3553 then
3554 Spec_Id := Corresponding_Spec_Of_Stub (Subp_Decl);
3556 else
3557 Spec_Id := Subp_Id;
3558 end if;
3560 -- Examine all postconditions for attribute 'Result and a post-state
3562 Prag := Pre_Post_Conditions (Items);
3563 while Present (Prag) loop
3564 if Nam_In (Pragma_Name (Prag), Name_Postcondition,
3565 Name_Refined_Post)
3566 and then not Error_Posted (Prag)
3567 then
3568 Post_Prag := Prag;
3569 Check_Result_And_Post_State_In_Pragma (Prag, Seen_In_Post);
3570 end if;
3572 Prag := Next_Pragma (Prag);
3573 end loop;
3575 -- Examine the contract cases of the subprogram for attribute 'Result
3576 -- and a post-state.
3578 Prag := Contract_Test_Cases (Items);
3579 while Present (Prag) loop
3580 if Pragma_Name (Prag) = Name_Contract_Cases
3581 and then not Error_Posted (Prag)
3582 then
3583 Case_Prag := Prag;
3584 Check_Result_And_Post_State_In_Pragma (Prag, Seen_In_Case);
3585 end if;
3587 Prag := Next_Pragma (Prag);
3588 end loop;
3590 -- Do not emit any errors if the subprogram is not a function
3592 if not Ekind_In (Spec_Id, E_Function, E_Generic_Function) then
3593 null;
3595 -- Regardless of whether the function has postconditions or contract
3596 -- cases, or whether they mention attribute 'Result, an IN OUT formal
3597 -- parameter is always treated as a result.
3599 elsif Has_In_Out_Parameter (Spec_Id) then
3600 null;
3602 -- The function has both a postcondition and contract cases and they do
3603 -- not mention attribute 'Result.
3605 elsif Present (Case_Prag)
3606 and then not Seen_In_Case
3607 and then Present (Post_Prag)
3608 and then not Seen_In_Post
3609 then
3610 Error_Msg_N
3611 ("neither postcondition nor contract cases mention function "
3612 & "result?T?", Post_Prag);
3614 -- The function has contract cases only and they do not mention
3615 -- attribute 'Result.
3617 elsif Present (Case_Prag) and then not Seen_In_Case then
3618 Error_Msg_N ("contract cases do not mention result?T?", Case_Prag);
3620 -- The function has postconditions only and they do not mention
3621 -- attribute 'Result.
3623 elsif Present (Post_Prag) and then not Seen_In_Post then
3624 Error_Msg_N
3625 ("postcondition does not mention function result?T?", Post_Prag);
3626 end if;
3627 end Check_Result_And_Post_State;
3629 -----------------------------
3630 -- Check_State_Refinements --
3631 -----------------------------
3633 procedure Check_State_Refinements
3634 (Context : Node_Id;
3635 Is_Main_Unit : Boolean := False)
3637 procedure Check_Package (Pack : Node_Id);
3638 -- Verify that all abstract states of a [generic] package denoted by its
3639 -- declarative node Pack have proper refinement. Recursively verify the
3640 -- visible and private declarations of the [generic] package for other
3641 -- nested packages.
3643 procedure Check_Packages_In (Decls : List_Id);
3644 -- Seek out [generic] package declarations within declarative list Decls
3645 -- and verify the status of their abstract state refinement.
3647 function SPARK_Mode_Is_Off (N : Node_Id) return Boolean;
3648 -- Determine whether construct N is subject to pragma SPARK_Mode Off
3650 -------------------
3651 -- Check_Package --
3652 -------------------
3654 procedure Check_Package (Pack : Node_Id) is
3655 Body_Id : constant Entity_Id := Corresponding_Body (Pack);
3656 Spec : constant Node_Id := Specification (Pack);
3657 States : constant Elist_Id :=
3658 Abstract_States (Defining_Entity (Pack));
3660 State_Elmt : Elmt_Id;
3661 State_Id : Entity_Id;
3663 begin
3664 -- Do not verify proper state refinement when the package is subject
3665 -- to pragma SPARK_Mode Off because this disables the requirement for
3666 -- state refinement.
3668 if SPARK_Mode_Is_Off (Pack) then
3669 null;
3671 -- State refinement can only occur in a completing packge body. Do
3672 -- not verify proper state refinement when the body is subject to
3673 -- pragma SPARK_Mode Off because this disables the requirement for
3674 -- state refinement.
3676 elsif Present (Body_Id)
3677 and then SPARK_Mode_Is_Off (Unit_Declaration_Node (Body_Id))
3678 then
3679 null;
3681 -- Do not verify proper state refinement when the package is an
3682 -- instance as this check was already performed in the generic.
3684 elsif Present (Generic_Parent (Spec)) then
3685 null;
3687 -- Otherwise examine the contents of the package
3689 else
3690 if Present (States) then
3691 State_Elmt := First_Elmt (States);
3692 while Present (State_Elmt) loop
3693 State_Id := Node (State_Elmt);
3695 -- Emit an error when a non-null state lacks any form of
3696 -- refinement.
3698 if not Is_Null_State (State_Id)
3699 and then not Has_Null_Refinement (State_Id)
3700 and then not Has_Non_Null_Refinement (State_Id)
3701 then
3702 Error_Msg_N ("state & requires refinement", State_Id);
3703 end if;
3705 Next_Elmt (State_Elmt);
3706 end loop;
3707 end if;
3709 Check_Packages_In (Visible_Declarations (Spec));
3710 Check_Packages_In (Private_Declarations (Spec));
3711 end if;
3712 end Check_Package;
3714 -----------------------
3715 -- Check_Packages_In --
3716 -----------------------
3718 procedure Check_Packages_In (Decls : List_Id) is
3719 Decl : Node_Id;
3721 begin
3722 if Present (Decls) then
3723 Decl := First (Decls);
3724 while Present (Decl) loop
3725 if Nkind_In (Decl, N_Generic_Package_Declaration,
3726 N_Package_Declaration)
3727 then
3728 Check_Package (Decl);
3729 end if;
3731 Next (Decl);
3732 end loop;
3733 end if;
3734 end Check_Packages_In;
3736 -----------------------
3737 -- SPARK_Mode_Is_Off --
3738 -----------------------
3740 function SPARK_Mode_Is_Off (N : Node_Id) return Boolean is
3741 Prag : constant Node_Id := SPARK_Pragma (Defining_Entity (N));
3743 begin
3744 return
3745 Present (Prag) and then Get_SPARK_Mode_From_Annotation (Prag) = Off;
3746 end SPARK_Mode_Is_Off;
3748 -- Start of processing for Check_State_Refinements
3750 begin
3751 -- A block may declare a nested package
3753 if Nkind (Context) = N_Block_Statement then
3754 Check_Packages_In (Declarations (Context));
3756 -- An entry, protected, subprogram, or task body may declare a nested
3757 -- package.
3759 elsif Nkind_In (Context, N_Entry_Body,
3760 N_Protected_Body,
3761 N_Subprogram_Body,
3762 N_Task_Body)
3763 then
3764 -- Do not verify proper state refinement when the body is subject to
3765 -- pragma SPARK_Mode Off because this disables the requirement for
3766 -- state refinement.
3768 if not SPARK_Mode_Is_Off (Context) then
3769 Check_Packages_In (Declarations (Context));
3770 end if;
3772 -- A package body may declare a nested package
3774 elsif Nkind (Context) = N_Package_Body then
3775 Check_Package (Unit_Declaration_Node (Corresponding_Spec (Context)));
3777 -- Do not verify proper state refinement when the body is subject to
3778 -- pragma SPARK_Mode Off because this disables the requirement for
3779 -- state refinement.
3781 if not SPARK_Mode_Is_Off (Context) then
3782 Check_Packages_In (Declarations (Context));
3783 end if;
3785 -- A library level [generic] package may declare a nested package
3787 elsif Nkind_In (Context, N_Generic_Package_Declaration,
3788 N_Package_Declaration)
3789 and then Is_Main_Unit
3790 then
3791 Check_Package (Context);
3792 end if;
3793 end Check_State_Refinements;
3795 ------------------------------
3796 -- Check_Unprotected_Access --
3797 ------------------------------
3799 procedure Check_Unprotected_Access
3800 (Context : Node_Id;
3801 Expr : Node_Id)
3803 Cont_Encl_Typ : Entity_Id;
3804 Pref_Encl_Typ : Entity_Id;
3806 function Enclosing_Protected_Type (Obj : Node_Id) return Entity_Id;
3807 -- Check whether Obj is a private component of a protected object.
3808 -- Return the protected type where the component resides, Empty
3809 -- otherwise.
3811 function Is_Public_Operation return Boolean;
3812 -- Verify that the enclosing operation is callable from outside the
3813 -- protected object, to minimize false positives.
3815 ------------------------------
3816 -- Enclosing_Protected_Type --
3817 ------------------------------
3819 function Enclosing_Protected_Type (Obj : Node_Id) return Entity_Id is
3820 begin
3821 if Is_Entity_Name (Obj) then
3822 declare
3823 Ent : Entity_Id := Entity (Obj);
3825 begin
3826 -- The object can be a renaming of a private component, use
3827 -- the original record component.
3829 if Is_Prival (Ent) then
3830 Ent := Prival_Link (Ent);
3831 end if;
3833 if Is_Protected_Type (Scope (Ent)) then
3834 return Scope (Ent);
3835 end if;
3836 end;
3837 end if;
3839 -- For indexed and selected components, recursively check the prefix
3841 if Nkind_In (Obj, N_Indexed_Component, N_Selected_Component) then
3842 return Enclosing_Protected_Type (Prefix (Obj));
3844 -- The object does not denote a protected component
3846 else
3847 return Empty;
3848 end if;
3849 end Enclosing_Protected_Type;
3851 -------------------------
3852 -- Is_Public_Operation --
3853 -------------------------
3855 function Is_Public_Operation return Boolean is
3856 S : Entity_Id;
3857 E : Entity_Id;
3859 begin
3860 S := Current_Scope;
3861 while Present (S) and then S /= Pref_Encl_Typ loop
3862 if Scope (S) = Pref_Encl_Typ then
3863 E := First_Entity (Pref_Encl_Typ);
3864 while Present (E)
3865 and then E /= First_Private_Entity (Pref_Encl_Typ)
3866 loop
3867 if E = S then
3868 return True;
3869 end if;
3871 Next_Entity (E);
3872 end loop;
3873 end if;
3875 S := Scope (S);
3876 end loop;
3878 return False;
3879 end Is_Public_Operation;
3881 -- Start of processing for Check_Unprotected_Access
3883 begin
3884 if Nkind (Expr) = N_Attribute_Reference
3885 and then Attribute_Name (Expr) = Name_Unchecked_Access
3886 then
3887 Cont_Encl_Typ := Enclosing_Protected_Type (Context);
3888 Pref_Encl_Typ := Enclosing_Protected_Type (Prefix (Expr));
3890 -- Check whether we are trying to export a protected component to a
3891 -- context with an equal or lower access level.
3893 if Present (Pref_Encl_Typ)
3894 and then No (Cont_Encl_Typ)
3895 and then Is_Public_Operation
3896 and then Scope_Depth (Pref_Encl_Typ) >=
3897 Object_Access_Level (Context)
3898 then
3899 Error_Msg_N
3900 ("??possible unprotected access to protected data", Expr);
3901 end if;
3902 end if;
3903 end Check_Unprotected_Access;
3905 ------------------------------
3906 -- Check_Unused_Body_States --
3907 ------------------------------
3909 procedure Check_Unused_Body_States (Body_Id : Entity_Id) is
3910 procedure Process_Refinement_Clause
3911 (Clause : Node_Id;
3912 States : Elist_Id);
3913 -- Inspect all constituents of refinement clause Clause and remove any
3914 -- matches from body state list States.
3916 procedure Report_Unused_Body_States (States : Elist_Id);
3917 -- Emit errors for each abstract state or object found in list States
3919 -------------------------------
3920 -- Process_Refinement_Clause --
3921 -------------------------------
3923 procedure Process_Refinement_Clause
3924 (Clause : Node_Id;
3925 States : Elist_Id)
3927 procedure Process_Constituent (Constit : Node_Id);
3928 -- Remove constituent Constit from body state list States
3930 -------------------------
3931 -- Process_Constituent --
3932 -------------------------
3934 procedure Process_Constituent (Constit : Node_Id) is
3935 Constit_Id : Entity_Id;
3937 begin
3938 -- Guard against illegal constituents. Only abstract states and
3939 -- objects can appear on the right hand side of a refinement.
3941 if Is_Entity_Name (Constit) then
3942 Constit_Id := Entity_Of (Constit);
3944 if Present (Constit_Id)
3945 and then Ekind_In (Constit_Id, E_Abstract_State,
3946 E_Constant,
3947 E_Variable)
3948 then
3949 Remove (States, Constit_Id);
3950 end if;
3951 end if;
3952 end Process_Constituent;
3954 -- Local variables
3956 Constit : Node_Id;
3958 -- Start of processing for Process_Refinement_Clause
3960 begin
3961 if Nkind (Clause) = N_Component_Association then
3962 Constit := Expression (Clause);
3964 -- Multiple constituents appear as an aggregate
3966 if Nkind (Constit) = N_Aggregate then
3967 Constit := First (Expressions (Constit));
3968 while Present (Constit) loop
3969 Process_Constituent (Constit);
3970 Next (Constit);
3971 end loop;
3973 -- Various forms of a single constituent
3975 else
3976 Process_Constituent (Constit);
3977 end if;
3978 end if;
3979 end Process_Refinement_Clause;
3981 -------------------------------
3982 -- Report_Unused_Body_States --
3983 -------------------------------
3985 procedure Report_Unused_Body_States (States : Elist_Id) is
3986 Posted : Boolean := False;
3987 State_Elmt : Elmt_Id;
3988 State_Id : Entity_Id;
3990 begin
3991 if Present (States) then
3992 State_Elmt := First_Elmt (States);
3993 while Present (State_Elmt) loop
3994 State_Id := Node (State_Elmt);
3996 -- Constants are part of the hidden state of a package, but the
3997 -- compiler cannot determine whether they have variable input
3998 -- (SPARK RM 7.1.1(2)) and cannot classify them properly as a
3999 -- hidden state. Do not emit an error when a constant does not
4000 -- participate in a state refinement, even though it acts as a
4001 -- hidden state.
4003 if Ekind (State_Id) = E_Constant then
4004 null;
4006 -- Generate an error message of the form:
4008 -- body of package ... has unused hidden states
4009 -- abstract state ... defined at ...
4010 -- variable ... defined at ...
4012 else
4013 if not Posted then
4014 Posted := True;
4015 SPARK_Msg_N
4016 ("body of package & has unused hidden states", Body_Id);
4017 end if;
4019 Error_Msg_Sloc := Sloc (State_Id);
4021 if Ekind (State_Id) = E_Abstract_State then
4022 SPARK_Msg_NE
4023 ("\abstract state & defined #", Body_Id, State_Id);
4025 else
4026 SPARK_Msg_NE ("\variable & defined #", Body_Id, State_Id);
4027 end if;
4028 end if;
4030 Next_Elmt (State_Elmt);
4031 end loop;
4032 end if;
4033 end Report_Unused_Body_States;
4035 -- Local variables
4037 Prag : constant Node_Id := Get_Pragma (Body_Id, Pragma_Refined_State);
4038 Spec_Id : constant Entity_Id := Spec_Entity (Body_Id);
4039 Clause : Node_Id;
4040 States : Elist_Id;
4042 -- Start of processing for Check_Unused_Body_States
4044 begin
4045 -- Inspect the clauses of pragma Refined_State and determine whether all
4046 -- visible states declared within the package body participate in the
4047 -- refinement.
4049 if Present (Prag) then
4050 Clause := Expression (Get_Argument (Prag, Spec_Id));
4051 States := Collect_Body_States (Body_Id);
4053 -- Multiple non-null state refinements appear as an aggregate
4055 if Nkind (Clause) = N_Aggregate then
4056 Clause := First (Component_Associations (Clause));
4057 while Present (Clause) loop
4058 Process_Refinement_Clause (Clause, States);
4059 Next (Clause);
4060 end loop;
4062 -- Various forms of a single state refinement
4064 else
4065 Process_Refinement_Clause (Clause, States);
4066 end if;
4068 -- Ensure that all abstract states and objects declared in the
4069 -- package body state space are utilized as constituents.
4071 Report_Unused_Body_States (States);
4072 end if;
4073 end Check_Unused_Body_States;
4075 -------------------------
4076 -- Collect_Body_States --
4077 -------------------------
4079 function Collect_Body_States (Body_Id : Entity_Id) return Elist_Id is
4080 function Is_Visible_Object (Obj_Id : Entity_Id) return Boolean;
4081 -- Determine whether object Obj_Id is a suitable visible state of a
4082 -- package body.
4084 procedure Collect_Visible_States
4085 (Pack_Id : Entity_Id;
4086 States : in out Elist_Id);
4087 -- Gather the entities of all abstract states and objects declared in
4088 -- the visible state space of package Pack_Id.
4090 ----------------------------
4091 -- Collect_Visible_States --
4092 ----------------------------
4094 procedure Collect_Visible_States
4095 (Pack_Id : Entity_Id;
4096 States : in out Elist_Id)
4098 Item_Id : Entity_Id;
4100 begin
4101 -- Traverse the entity chain of the package and inspect all visible
4102 -- items.
4104 Item_Id := First_Entity (Pack_Id);
4105 while Present (Item_Id) and then not In_Private_Part (Item_Id) loop
4107 -- Do not consider internally generated items as those cannot be
4108 -- named and participate in refinement.
4110 if not Comes_From_Source (Item_Id) then
4111 null;
4113 elsif Ekind (Item_Id) = E_Abstract_State then
4114 Append_New_Elmt (Item_Id, States);
4116 elsif Ekind_In (Item_Id, E_Constant, E_Variable)
4117 and then Is_Visible_Object (Item_Id)
4118 then
4119 Append_New_Elmt (Item_Id, States);
4121 -- Recursively gather the visible states of a nested package
4123 elsif Ekind (Item_Id) = E_Package then
4124 Collect_Visible_States (Item_Id, States);
4125 end if;
4127 Next_Entity (Item_Id);
4128 end loop;
4129 end Collect_Visible_States;
4131 -----------------------
4132 -- Is_Visible_Object --
4133 -----------------------
4135 function Is_Visible_Object (Obj_Id : Entity_Id) return Boolean is
4136 begin
4137 -- Objects that map generic formals to their actuals are not visible
4138 -- from outside the generic instantiation.
4140 if Present (Corresponding_Generic_Association
4141 (Declaration_Node (Obj_Id)))
4142 then
4143 return False;
4145 -- Constituents of a single protected/task type act as components of
4146 -- the type and are not visible from outside the type.
4148 elsif Ekind (Obj_Id) = E_Variable
4149 and then Present (Encapsulating_State (Obj_Id))
4150 and then Is_Single_Concurrent_Object (Encapsulating_State (Obj_Id))
4151 then
4152 return False;
4154 else
4155 return True;
4156 end if;
4157 end Is_Visible_Object;
4159 -- Local variables
4161 Body_Decl : constant Node_Id := Unit_Declaration_Node (Body_Id);
4162 Decl : Node_Id;
4163 Item_Id : Entity_Id;
4164 States : Elist_Id := No_Elist;
4166 -- Start of processing for Collect_Body_States
4168 begin
4169 -- Inspect the declarations of the body looking for source objects,
4170 -- packages and package instantiations. Note that even though this
4171 -- processing is very similar to Collect_Visible_States, a package
4172 -- body does not have a First/Next_Entity list.
4174 Decl := First (Declarations (Body_Decl));
4175 while Present (Decl) loop
4177 -- Capture source objects as internally generated temporaries cannot
4178 -- be named and participate in refinement.
4180 if Nkind (Decl) = N_Object_Declaration then
4181 Item_Id := Defining_Entity (Decl);
4183 if Comes_From_Source (Item_Id)
4184 and then Is_Visible_Object (Item_Id)
4185 then
4186 Append_New_Elmt (Item_Id, States);
4187 end if;
4189 -- Capture the visible abstract states and objects of a source
4190 -- package [instantiation].
4192 elsif Nkind (Decl) = N_Package_Declaration then
4193 Item_Id := Defining_Entity (Decl);
4195 if Comes_From_Source (Item_Id) then
4196 Collect_Visible_States (Item_Id, States);
4197 end if;
4198 end if;
4200 Next (Decl);
4201 end loop;
4203 return States;
4204 end Collect_Body_States;
4206 ------------------------
4207 -- Collect_Interfaces --
4208 ------------------------
4210 procedure Collect_Interfaces
4211 (T : Entity_Id;
4212 Ifaces_List : out Elist_Id;
4213 Exclude_Parents : Boolean := False;
4214 Use_Full_View : Boolean := True)
4216 procedure Collect (Typ : Entity_Id);
4217 -- Subsidiary subprogram used to traverse the whole list
4218 -- of directly and indirectly implemented interfaces
4220 -------------
4221 -- Collect --
4222 -------------
4224 procedure Collect (Typ : Entity_Id) is
4225 Ancestor : Entity_Id;
4226 Full_T : Entity_Id;
4227 Id : Node_Id;
4228 Iface : Entity_Id;
4230 begin
4231 Full_T := Typ;
4233 -- Handle private types and subtypes
4235 if Use_Full_View
4236 and then Is_Private_Type (Typ)
4237 and then Present (Full_View (Typ))
4238 then
4239 Full_T := Full_View (Typ);
4241 if Ekind (Full_T) = E_Record_Subtype then
4242 Full_T := Full_View (Etype (Typ));
4243 end if;
4244 end if;
4246 -- Include the ancestor if we are generating the whole list of
4247 -- abstract interfaces.
4249 if Etype (Full_T) /= Typ
4251 -- Protect the frontend against wrong sources. For example:
4253 -- package P is
4254 -- type A is tagged null record;
4255 -- type B is new A with private;
4256 -- type C is new A with private;
4257 -- private
4258 -- type B is new C with null record;
4259 -- type C is new B with null record;
4260 -- end P;
4262 and then Etype (Full_T) /= T
4263 then
4264 Ancestor := Etype (Full_T);
4265 Collect (Ancestor);
4267 if Is_Interface (Ancestor) and then not Exclude_Parents then
4268 Append_Unique_Elmt (Ancestor, Ifaces_List);
4269 end if;
4270 end if;
4272 -- Traverse the graph of ancestor interfaces
4274 if Is_Non_Empty_List (Abstract_Interface_List (Full_T)) then
4275 Id := First (Abstract_Interface_List (Full_T));
4276 while Present (Id) loop
4277 Iface := Etype (Id);
4279 -- Protect against wrong uses. For example:
4280 -- type I is interface;
4281 -- type O is tagged null record;
4282 -- type Wrong is new I and O with null record; -- ERROR
4284 if Is_Interface (Iface) then
4285 if Exclude_Parents
4286 and then Etype (T) /= T
4287 and then Interface_Present_In_Ancestor (Etype (T), Iface)
4288 then
4289 null;
4290 else
4291 Collect (Iface);
4292 Append_Unique_Elmt (Iface, Ifaces_List);
4293 end if;
4294 end if;
4296 Next (Id);
4297 end loop;
4298 end if;
4299 end Collect;
4301 -- Start of processing for Collect_Interfaces
4303 begin
4304 pragma Assert (Is_Tagged_Type (T) or else Is_Concurrent_Type (T));
4305 Ifaces_List := New_Elmt_List;
4306 Collect (T);
4307 end Collect_Interfaces;
4309 ----------------------------------
4310 -- Collect_Interface_Components --
4311 ----------------------------------
4313 procedure Collect_Interface_Components
4314 (Tagged_Type : Entity_Id;
4315 Components_List : out Elist_Id)
4317 procedure Collect (Typ : Entity_Id);
4318 -- Subsidiary subprogram used to climb to the parents
4320 -------------
4321 -- Collect --
4322 -------------
4324 procedure Collect (Typ : Entity_Id) is
4325 Tag_Comp : Entity_Id;
4326 Parent_Typ : Entity_Id;
4328 begin
4329 -- Handle private types
4331 if Present (Full_View (Etype (Typ))) then
4332 Parent_Typ := Full_View (Etype (Typ));
4333 else
4334 Parent_Typ := Etype (Typ);
4335 end if;
4337 if Parent_Typ /= Typ
4339 -- Protect the frontend against wrong sources. For example:
4341 -- package P is
4342 -- type A is tagged null record;
4343 -- type B is new A with private;
4344 -- type C is new A with private;
4345 -- private
4346 -- type B is new C with null record;
4347 -- type C is new B with null record;
4348 -- end P;
4350 and then Parent_Typ /= Tagged_Type
4351 then
4352 Collect (Parent_Typ);
4353 end if;
4355 -- Collect the components containing tags of secondary dispatch
4356 -- tables.
4358 Tag_Comp := Next_Tag_Component (First_Tag_Component (Typ));
4359 while Present (Tag_Comp) loop
4360 pragma Assert (Present (Related_Type (Tag_Comp)));
4361 Append_Elmt (Tag_Comp, Components_List);
4363 Tag_Comp := Next_Tag_Component (Tag_Comp);
4364 end loop;
4365 end Collect;
4367 -- Start of processing for Collect_Interface_Components
4369 begin
4370 pragma Assert (Ekind (Tagged_Type) = E_Record_Type
4371 and then Is_Tagged_Type (Tagged_Type));
4373 Components_List := New_Elmt_List;
4374 Collect (Tagged_Type);
4375 end Collect_Interface_Components;
4377 -----------------------------
4378 -- Collect_Interfaces_Info --
4379 -----------------------------
4381 procedure Collect_Interfaces_Info
4382 (T : Entity_Id;
4383 Ifaces_List : out Elist_Id;
4384 Components_List : out Elist_Id;
4385 Tags_List : out Elist_Id)
4387 Comps_List : Elist_Id;
4388 Comp_Elmt : Elmt_Id;
4389 Comp_Iface : Entity_Id;
4390 Iface_Elmt : Elmt_Id;
4391 Iface : Entity_Id;
4393 function Search_Tag (Iface : Entity_Id) return Entity_Id;
4394 -- Search for the secondary tag associated with the interface type
4395 -- Iface that is implemented by T.
4397 ----------------
4398 -- Search_Tag --
4399 ----------------
4401 function Search_Tag (Iface : Entity_Id) return Entity_Id is
4402 ADT : Elmt_Id;
4403 begin
4404 if not Is_CPP_Class (T) then
4405 ADT := Next_Elmt (Next_Elmt (First_Elmt (Access_Disp_Table (T))));
4406 else
4407 ADT := Next_Elmt (First_Elmt (Access_Disp_Table (T)));
4408 end if;
4410 while Present (ADT)
4411 and then Is_Tag (Node (ADT))
4412 and then Related_Type (Node (ADT)) /= Iface
4413 loop
4414 -- Skip secondary dispatch table referencing thunks to user
4415 -- defined primitives covered by this interface.
4417 pragma Assert (Has_Suffix (Node (ADT), 'P'));
4418 Next_Elmt (ADT);
4420 -- Skip secondary dispatch tables of Ada types
4422 if not Is_CPP_Class (T) then
4424 -- Skip secondary dispatch table referencing thunks to
4425 -- predefined primitives.
4427 pragma Assert (Has_Suffix (Node (ADT), 'Y'));
4428 Next_Elmt (ADT);
4430 -- Skip secondary dispatch table referencing user-defined
4431 -- primitives covered by this interface.
4433 pragma Assert (Has_Suffix (Node (ADT), 'D'));
4434 Next_Elmt (ADT);
4436 -- Skip secondary dispatch table referencing predefined
4437 -- primitives.
4439 pragma Assert (Has_Suffix (Node (ADT), 'Z'));
4440 Next_Elmt (ADT);
4441 end if;
4442 end loop;
4444 pragma Assert (Is_Tag (Node (ADT)));
4445 return Node (ADT);
4446 end Search_Tag;
4448 -- Start of processing for Collect_Interfaces_Info
4450 begin
4451 Collect_Interfaces (T, Ifaces_List);
4452 Collect_Interface_Components (T, Comps_List);
4454 -- Search for the record component and tag associated with each
4455 -- interface type of T.
4457 Components_List := New_Elmt_List;
4458 Tags_List := New_Elmt_List;
4460 Iface_Elmt := First_Elmt (Ifaces_List);
4461 while Present (Iface_Elmt) loop
4462 Iface := Node (Iface_Elmt);
4464 -- Associate the primary tag component and the primary dispatch table
4465 -- with all the interfaces that are parents of T
4467 if Is_Ancestor (Iface, T, Use_Full_View => True) then
4468 Append_Elmt (First_Tag_Component (T), Components_List);
4469 Append_Elmt (Node (First_Elmt (Access_Disp_Table (T))), Tags_List);
4471 -- Otherwise search for the tag component and secondary dispatch
4472 -- table of Iface
4474 else
4475 Comp_Elmt := First_Elmt (Comps_List);
4476 while Present (Comp_Elmt) loop
4477 Comp_Iface := Related_Type (Node (Comp_Elmt));
4479 if Comp_Iface = Iface
4480 or else Is_Ancestor (Iface, Comp_Iface, Use_Full_View => True)
4481 then
4482 Append_Elmt (Node (Comp_Elmt), Components_List);
4483 Append_Elmt (Search_Tag (Comp_Iface), Tags_List);
4484 exit;
4485 end if;
4487 Next_Elmt (Comp_Elmt);
4488 end loop;
4489 pragma Assert (Present (Comp_Elmt));
4490 end if;
4492 Next_Elmt (Iface_Elmt);
4493 end loop;
4494 end Collect_Interfaces_Info;
4496 ---------------------
4497 -- Collect_Parents --
4498 ---------------------
4500 procedure Collect_Parents
4501 (T : Entity_Id;
4502 List : out Elist_Id;
4503 Use_Full_View : Boolean := True)
4505 Current_Typ : Entity_Id := T;
4506 Parent_Typ : Entity_Id;
4508 begin
4509 List := New_Elmt_List;
4511 -- No action if the if the type has no parents
4513 if T = Etype (T) then
4514 return;
4515 end if;
4517 loop
4518 Parent_Typ := Etype (Current_Typ);
4520 if Is_Private_Type (Parent_Typ)
4521 and then Present (Full_View (Parent_Typ))
4522 and then Use_Full_View
4523 then
4524 Parent_Typ := Full_View (Base_Type (Parent_Typ));
4525 end if;
4527 Append_Elmt (Parent_Typ, List);
4529 exit when Parent_Typ = Current_Typ;
4530 Current_Typ := Parent_Typ;
4531 end loop;
4532 end Collect_Parents;
4534 ----------------------------------
4535 -- Collect_Primitive_Operations --
4536 ----------------------------------
4538 function Collect_Primitive_Operations (T : Entity_Id) return Elist_Id is
4539 B_Type : constant Entity_Id := Base_Type (T);
4540 B_Decl : constant Node_Id := Original_Node (Parent (B_Type));
4541 B_Scope : Entity_Id := Scope (B_Type);
4542 Op_List : Elist_Id;
4543 Formal : Entity_Id;
4544 Is_Prim : Boolean;
4545 Is_Type_In_Pkg : Boolean;
4546 Formal_Derived : Boolean := False;
4547 Id : Entity_Id;
4549 function Match (E : Entity_Id) return Boolean;
4550 -- True if E's base type is B_Type, or E is of an anonymous access type
4551 -- and the base type of its designated type is B_Type.
4553 -----------
4554 -- Match --
4555 -----------
4557 function Match (E : Entity_Id) return Boolean is
4558 Etyp : Entity_Id := Etype (E);
4560 begin
4561 if Ekind (Etyp) = E_Anonymous_Access_Type then
4562 Etyp := Designated_Type (Etyp);
4563 end if;
4565 -- In Ada 2012 a primitive operation may have a formal of an
4566 -- incomplete view of the parent type.
4568 return Base_Type (Etyp) = B_Type
4569 or else
4570 (Ada_Version >= Ada_2012
4571 and then Ekind (Etyp) = E_Incomplete_Type
4572 and then Full_View (Etyp) = B_Type);
4573 end Match;
4575 -- Start of processing for Collect_Primitive_Operations
4577 begin
4578 -- For tagged types, the primitive operations are collected as they
4579 -- are declared, and held in an explicit list which is simply returned.
4581 if Is_Tagged_Type (B_Type) then
4582 return Primitive_Operations (B_Type);
4584 -- An untagged generic type that is a derived type inherits the
4585 -- primitive operations of its parent type. Other formal types only
4586 -- have predefined operators, which are not explicitly represented.
4588 elsif Is_Generic_Type (B_Type) then
4589 if Nkind (B_Decl) = N_Formal_Type_Declaration
4590 and then Nkind (Formal_Type_Definition (B_Decl)) =
4591 N_Formal_Derived_Type_Definition
4592 then
4593 Formal_Derived := True;
4594 else
4595 return New_Elmt_List;
4596 end if;
4597 end if;
4599 Op_List := New_Elmt_List;
4601 if B_Scope = Standard_Standard then
4602 if B_Type = Standard_String then
4603 Append_Elmt (Standard_Op_Concat, Op_List);
4605 elsif B_Type = Standard_Wide_String then
4606 Append_Elmt (Standard_Op_Concatw, Op_List);
4608 else
4609 null;
4610 end if;
4612 -- Locate the primitive subprograms of the type
4614 else
4615 -- The primitive operations appear after the base type, except
4616 -- if the derivation happens within the private part of B_Scope
4617 -- and the type is a private type, in which case both the type
4618 -- and some primitive operations may appear before the base
4619 -- type, and the list of candidates starts after the type.
4621 if In_Open_Scopes (B_Scope)
4622 and then Scope (T) = B_Scope
4623 and then In_Private_Part (B_Scope)
4624 then
4625 Id := Next_Entity (T);
4627 -- In Ada 2012, If the type has an incomplete partial view, there
4628 -- may be primitive operations declared before the full view, so
4629 -- we need to start scanning from the incomplete view, which is
4630 -- earlier on the entity chain.
4632 elsif Nkind (Parent (B_Type)) = N_Full_Type_Declaration
4633 and then Present (Incomplete_View (Parent (B_Type)))
4634 then
4635 Id := Defining_Entity (Incomplete_View (Parent (B_Type)));
4637 -- If T is a derived from a type with an incomplete view declared
4638 -- elsewhere, that incomplete view is irrelevant, we want the
4639 -- operations in the scope of T.
4641 if Scope (Id) /= Scope (B_Type) then
4642 Id := Next_Entity (B_Type);
4643 end if;
4645 else
4646 Id := Next_Entity (B_Type);
4647 end if;
4649 -- Set flag if this is a type in a package spec
4651 Is_Type_In_Pkg :=
4652 Is_Package_Or_Generic_Package (B_Scope)
4653 and then
4654 Nkind (Parent (Declaration_Node (First_Subtype (T)))) /=
4655 N_Package_Body;
4657 while Present (Id) loop
4659 -- Test whether the result type or any of the parameter types of
4660 -- each subprogram following the type match that type when the
4661 -- type is declared in a package spec, is a derived type, or the
4662 -- subprogram is marked as primitive. (The Is_Primitive test is
4663 -- needed to find primitives of nonderived types in declarative
4664 -- parts that happen to override the predefined "=" operator.)
4666 -- Note that generic formal subprograms are not considered to be
4667 -- primitive operations and thus are never inherited.
4669 if Is_Overloadable (Id)
4670 and then (Is_Type_In_Pkg
4671 or else Is_Derived_Type (B_Type)
4672 or else Is_Primitive (Id))
4673 and then Nkind (Parent (Parent (Id)))
4674 not in N_Formal_Subprogram_Declaration
4675 then
4676 Is_Prim := False;
4678 if Match (Id) then
4679 Is_Prim := True;
4681 else
4682 Formal := First_Formal (Id);
4683 while Present (Formal) loop
4684 if Match (Formal) then
4685 Is_Prim := True;
4686 exit;
4687 end if;
4689 Next_Formal (Formal);
4690 end loop;
4691 end if;
4693 -- For a formal derived type, the only primitives are the ones
4694 -- inherited from the parent type. Operations appearing in the
4695 -- package declaration are not primitive for it.
4697 if Is_Prim
4698 and then (not Formal_Derived or else Present (Alias (Id)))
4699 then
4700 -- In the special case of an equality operator aliased to
4701 -- an overriding dispatching equality belonging to the same
4702 -- type, we don't include it in the list of primitives.
4703 -- This avoids inheriting multiple equality operators when
4704 -- deriving from untagged private types whose full type is
4705 -- tagged, which can otherwise cause ambiguities. Note that
4706 -- this should only happen for this kind of untagged parent
4707 -- type, since normally dispatching operations are inherited
4708 -- using the type's Primitive_Operations list.
4710 if Chars (Id) = Name_Op_Eq
4711 and then Is_Dispatching_Operation (Id)
4712 and then Present (Alias (Id))
4713 and then Present (Overridden_Operation (Alias (Id)))
4714 and then Base_Type (Etype (First_Entity (Id))) =
4715 Base_Type (Etype (First_Entity (Alias (Id))))
4716 then
4717 null;
4719 -- Include the subprogram in the list of primitives
4721 else
4722 Append_Elmt (Id, Op_List);
4723 end if;
4724 end if;
4725 end if;
4727 Next_Entity (Id);
4729 -- For a type declared in System, some of its operations may
4730 -- appear in the target-specific extension to System.
4732 if No (Id)
4733 and then B_Scope = RTU_Entity (System)
4734 and then Present_System_Aux
4735 then
4736 B_Scope := System_Aux_Id;
4737 Id := First_Entity (System_Aux_Id);
4738 end if;
4739 end loop;
4740 end if;
4742 return Op_List;
4743 end Collect_Primitive_Operations;
4745 -----------------------------------
4746 -- Compile_Time_Constraint_Error --
4747 -----------------------------------
4749 function Compile_Time_Constraint_Error
4750 (N : Node_Id;
4751 Msg : String;
4752 Ent : Entity_Id := Empty;
4753 Loc : Source_Ptr := No_Location;
4754 Warn : Boolean := False) return Node_Id
4756 Msgc : String (1 .. Msg'Length + 3);
4757 -- Copy of message, with room for possible ?? or << and ! at end
4759 Msgl : Natural;
4760 Wmsg : Boolean;
4761 Eloc : Source_Ptr;
4763 -- Start of processing for Compile_Time_Constraint_Error
4765 begin
4766 -- If this is a warning, convert it into an error if we are in code
4767 -- subject to SPARK_Mode being set On, unless Warn is True to force a
4768 -- warning. The rationale is that a compile-time constraint error should
4769 -- lead to an error instead of a warning when SPARK_Mode is On, but in
4770 -- a few cases we prefer to issue a warning and generate both a suitable
4771 -- run-time error in GNAT and a suitable check message in GNATprove.
4772 -- Those cases are those that likely correspond to deactivated SPARK
4773 -- code, so that this kind of code can be compiled and analyzed instead
4774 -- of being rejected.
4776 Error_Msg_Warn := Warn or SPARK_Mode /= On;
4778 -- A static constraint error in an instance body is not a fatal error.
4779 -- we choose to inhibit the message altogether, because there is no
4780 -- obvious node (for now) on which to post it. On the other hand the
4781 -- offending node must be replaced with a constraint_error in any case.
4783 -- No messages are generated if we already posted an error on this node
4785 if not Error_Posted (N) then
4786 if Loc /= No_Location then
4787 Eloc := Loc;
4788 else
4789 Eloc := Sloc (N);
4790 end if;
4792 -- Copy message to Msgc, converting any ? in the message into
4793 -- < instead, so that we have an error in GNATprove mode.
4795 Msgl := Msg'Length;
4797 for J in 1 .. Msgl loop
4798 if Msg (J) = '?' and then (J = 1 or else Msg (J) /= ''') then
4799 Msgc (J) := '<';
4800 else
4801 Msgc (J) := Msg (J);
4802 end if;
4803 end loop;
4805 -- Message is a warning, even in Ada 95 case
4807 if Msg (Msg'Last) = '?' or else Msg (Msg'Last) = '<' then
4808 Wmsg := True;
4810 -- In Ada 83, all messages are warnings. In the private part and
4811 -- the body of an instance, constraint_checks are only warnings.
4812 -- We also make this a warning if the Warn parameter is set.
4814 elsif Warn
4815 or else (Ada_Version = Ada_83 and then Comes_From_Source (N))
4816 then
4817 Msgl := Msgl + 1;
4818 Msgc (Msgl) := '<';
4819 Msgl := Msgl + 1;
4820 Msgc (Msgl) := '<';
4821 Wmsg := True;
4823 elsif In_Instance_Not_Visible then
4824 Msgl := Msgl + 1;
4825 Msgc (Msgl) := '<';
4826 Msgl := Msgl + 1;
4827 Msgc (Msgl) := '<';
4828 Wmsg := True;
4830 -- Otherwise we have a real error message (Ada 95 static case)
4831 -- and we make this an unconditional message. Note that in the
4832 -- warning case we do not make the message unconditional, it seems
4833 -- quite reasonable to delete messages like this (about exceptions
4834 -- that will be raised) in dead code.
4836 else
4837 Wmsg := False;
4838 Msgl := Msgl + 1;
4839 Msgc (Msgl) := '!';
4840 end if;
4842 -- One more test, skip the warning if the related expression is
4843 -- statically unevaluated, since we don't want to warn about what
4844 -- will happen when something is evaluated if it never will be
4845 -- evaluated.
4847 if not Is_Statically_Unevaluated (N) then
4848 if Present (Ent) then
4849 Error_Msg_NEL (Msgc (1 .. Msgl), N, Ent, Eloc);
4850 else
4851 Error_Msg_NEL (Msgc (1 .. Msgl), N, Etype (N), Eloc);
4852 end if;
4854 if Wmsg then
4856 -- Check whether the context is an Init_Proc
4858 if Inside_Init_Proc then
4859 declare
4860 Conc_Typ : constant Entity_Id :=
4861 Corresponding_Concurrent_Type
4862 (Entity (Parameter_Type (First
4863 (Parameter_Specifications
4864 (Parent (Current_Scope))))));
4866 begin
4867 -- Don't complain if the corresponding concurrent type
4868 -- doesn't come from source (i.e. a single task/protected
4869 -- object).
4871 if Present (Conc_Typ)
4872 and then not Comes_From_Source (Conc_Typ)
4873 then
4874 Error_Msg_NEL
4875 ("\& [<<", N, Standard_Constraint_Error, Eloc);
4877 else
4878 if GNATprove_Mode then
4879 Error_Msg_NEL
4880 ("\& would have been raised for objects of this "
4881 & "type", N, Standard_Constraint_Error, Eloc);
4882 else
4883 Error_Msg_NEL
4884 ("\& will be raised for objects of this type??",
4885 N, Standard_Constraint_Error, Eloc);
4886 end if;
4887 end if;
4888 end;
4890 else
4891 Error_Msg_NEL ("\& [<<", N, Standard_Constraint_Error, Eloc);
4892 end if;
4894 else
4895 Error_Msg ("\static expression fails Constraint_Check", Eloc);
4896 Set_Error_Posted (N);
4897 end if;
4898 end if;
4899 end if;
4901 return N;
4902 end Compile_Time_Constraint_Error;
4904 -----------------------
4905 -- Conditional_Delay --
4906 -----------------------
4908 procedure Conditional_Delay (New_Ent, Old_Ent : Entity_Id) is
4909 begin
4910 if Has_Delayed_Freeze (Old_Ent) and then not Is_Frozen (Old_Ent) then
4911 Set_Has_Delayed_Freeze (New_Ent);
4912 end if;
4913 end Conditional_Delay;
4915 ----------------------------
4916 -- Contains_Refined_State --
4917 ----------------------------
4919 function Contains_Refined_State (Prag : Node_Id) return Boolean is
4920 function Has_State_In_Dependency (List : Node_Id) return Boolean;
4921 -- Determine whether a dependency list mentions a state with a visible
4922 -- refinement.
4924 function Has_State_In_Global (List : Node_Id) return Boolean;
4925 -- Determine whether a global list mentions a state with a visible
4926 -- refinement.
4928 function Is_Refined_State (Item : Node_Id) return Boolean;
4929 -- Determine whether Item is a reference to an abstract state with a
4930 -- visible refinement.
4932 -----------------------------
4933 -- Has_State_In_Dependency --
4934 -----------------------------
4936 function Has_State_In_Dependency (List : Node_Id) return Boolean is
4937 Clause : Node_Id;
4938 Output : Node_Id;
4940 begin
4941 -- A null dependency list does not mention any states
4943 if Nkind (List) = N_Null then
4944 return False;
4946 -- Dependency clauses appear as component associations of an
4947 -- aggregate.
4949 elsif Nkind (List) = N_Aggregate
4950 and then Present (Component_Associations (List))
4951 then
4952 Clause := First (Component_Associations (List));
4953 while Present (Clause) loop
4955 -- Inspect the outputs of a dependency clause
4957 Output := First (Choices (Clause));
4958 while Present (Output) loop
4959 if Is_Refined_State (Output) then
4960 return True;
4961 end if;
4963 Next (Output);
4964 end loop;
4966 -- Inspect the outputs of a dependency clause
4968 if Is_Refined_State (Expression (Clause)) then
4969 return True;
4970 end if;
4972 Next (Clause);
4973 end loop;
4975 -- If we get here, then none of the dependency clauses mention a
4976 -- state with visible refinement.
4978 return False;
4980 -- An illegal pragma managed to sneak in
4982 else
4983 raise Program_Error;
4984 end if;
4985 end Has_State_In_Dependency;
4987 -------------------------
4988 -- Has_State_In_Global --
4989 -------------------------
4991 function Has_State_In_Global (List : Node_Id) return Boolean is
4992 Item : Node_Id;
4994 begin
4995 -- A null global list does not mention any states
4997 if Nkind (List) = N_Null then
4998 return False;
5000 -- Simple global list or moded global list declaration
5002 elsif Nkind (List) = N_Aggregate then
5004 -- The declaration of a simple global list appear as a collection
5005 -- of expressions.
5007 if Present (Expressions (List)) then
5008 Item := First (Expressions (List));
5009 while Present (Item) loop
5010 if Is_Refined_State (Item) then
5011 return True;
5012 end if;
5014 Next (Item);
5015 end loop;
5017 -- The declaration of a moded global list appears as a collection
5018 -- of component associations where individual choices denote
5019 -- modes.
5021 else
5022 Item := First (Component_Associations (List));
5023 while Present (Item) loop
5024 if Has_State_In_Global (Expression (Item)) then
5025 return True;
5026 end if;
5028 Next (Item);
5029 end loop;
5030 end if;
5032 -- If we get here, then the simple/moded global list did not
5033 -- mention any states with a visible refinement.
5035 return False;
5037 -- Single global item declaration
5039 elsif Is_Entity_Name (List) then
5040 return Is_Refined_State (List);
5042 -- An illegal pragma managed to sneak in
5044 else
5045 raise Program_Error;
5046 end if;
5047 end Has_State_In_Global;
5049 ----------------------
5050 -- Is_Refined_State --
5051 ----------------------
5053 function Is_Refined_State (Item : Node_Id) return Boolean is
5054 Elmt : Node_Id;
5055 Item_Id : Entity_Id;
5057 begin
5058 if Nkind (Item) = N_Null then
5059 return False;
5061 -- States cannot be subject to attribute 'Result. This case arises
5062 -- in dependency relations.
5064 elsif Nkind (Item) = N_Attribute_Reference
5065 and then Attribute_Name (Item) = Name_Result
5066 then
5067 return False;
5069 -- Multiple items appear as an aggregate. This case arises in
5070 -- dependency relations.
5072 elsif Nkind (Item) = N_Aggregate
5073 and then Present (Expressions (Item))
5074 then
5075 Elmt := First (Expressions (Item));
5076 while Present (Elmt) loop
5077 if Is_Refined_State (Elmt) then
5078 return True;
5079 end if;
5081 Next (Elmt);
5082 end loop;
5084 -- If we get here, then none of the inputs or outputs reference a
5085 -- state with visible refinement.
5087 return False;
5089 -- Single item
5091 else
5092 Item_Id := Entity_Of (Item);
5094 return
5095 Present (Item_Id)
5096 and then Ekind (Item_Id) = E_Abstract_State
5097 and then Has_Visible_Refinement (Item_Id);
5098 end if;
5099 end Is_Refined_State;
5101 -- Local variables
5103 Arg : constant Node_Id :=
5104 Get_Pragma_Arg (First (Pragma_Argument_Associations (Prag)));
5105 Nam : constant Name_Id := Pragma_Name (Prag);
5107 -- Start of processing for Contains_Refined_State
5109 begin
5110 if Nam = Name_Depends then
5111 return Has_State_In_Dependency (Arg);
5113 else pragma Assert (Nam = Name_Global);
5114 return Has_State_In_Global (Arg);
5115 end if;
5116 end Contains_Refined_State;
5118 -------------------------
5119 -- Copy_Component_List --
5120 -------------------------
5122 function Copy_Component_List
5123 (R_Typ : Entity_Id;
5124 Loc : Source_Ptr) return List_Id
5126 Comp : Node_Id;
5127 Comps : constant List_Id := New_List;
5129 begin
5130 Comp := First_Component (Underlying_Type (R_Typ));
5131 while Present (Comp) loop
5132 if Comes_From_Source (Comp) then
5133 declare
5134 Comp_Decl : constant Node_Id := Declaration_Node (Comp);
5135 begin
5136 Append_To (Comps,
5137 Make_Component_Declaration (Loc,
5138 Defining_Identifier =>
5139 Make_Defining_Identifier (Loc, Chars (Comp)),
5140 Component_Definition =>
5141 New_Copy_Tree
5142 (Component_Definition (Comp_Decl), New_Sloc => Loc)));
5143 end;
5144 end if;
5146 Next_Component (Comp);
5147 end loop;
5149 return Comps;
5150 end Copy_Component_List;
5152 -------------------------
5153 -- Copy_Parameter_List --
5154 -------------------------
5156 function Copy_Parameter_List (Subp_Id : Entity_Id) return List_Id is
5157 Loc : constant Source_Ptr := Sloc (Subp_Id);
5158 Plist : List_Id;
5159 Formal : Entity_Id;
5161 begin
5162 if No (First_Formal (Subp_Id)) then
5163 return No_List;
5164 else
5165 Plist := New_List;
5166 Formal := First_Formal (Subp_Id);
5167 while Present (Formal) loop
5168 Append_To (Plist,
5169 Make_Parameter_Specification (Loc,
5170 Defining_Identifier =>
5171 Make_Defining_Identifier (Sloc (Formal), Chars (Formal)),
5172 In_Present => In_Present (Parent (Formal)),
5173 Out_Present => Out_Present (Parent (Formal)),
5174 Parameter_Type =>
5175 New_Occurrence_Of (Etype (Formal), Loc),
5176 Expression =>
5177 New_Copy_Tree (Expression (Parent (Formal)))));
5179 Next_Formal (Formal);
5180 end loop;
5181 end if;
5183 return Plist;
5184 end Copy_Parameter_List;
5186 --------------------------
5187 -- Copy_Subprogram_Spec --
5188 --------------------------
5190 function Copy_Subprogram_Spec (Spec : Node_Id) return Node_Id is
5191 Def_Id : Node_Id;
5192 Formal_Spec : Node_Id;
5193 Result : Node_Id;
5195 begin
5196 -- The structure of the original tree must be replicated without any
5197 -- alterations. Use New_Copy_Tree for this purpose.
5199 Result := New_Copy_Tree (Spec);
5201 -- Create a new entity for the defining unit name
5203 Def_Id := Defining_Unit_Name (Result);
5204 Set_Defining_Unit_Name (Result,
5205 Make_Defining_Identifier (Sloc (Def_Id), Chars (Def_Id)));
5207 -- Create new entities for the formal parameters
5209 if Present (Parameter_Specifications (Result)) then
5210 Formal_Spec := First (Parameter_Specifications (Result));
5211 while Present (Formal_Spec) loop
5212 Def_Id := Defining_Identifier (Formal_Spec);
5213 Set_Defining_Identifier (Formal_Spec,
5214 Make_Defining_Identifier (Sloc (Def_Id), Chars (Def_Id)));
5216 Next (Formal_Spec);
5217 end loop;
5218 end if;
5220 return Result;
5221 end Copy_Subprogram_Spec;
5223 --------------------------------
5224 -- Corresponding_Generic_Type --
5225 --------------------------------
5227 function Corresponding_Generic_Type (T : Entity_Id) return Entity_Id is
5228 Inst : Entity_Id;
5229 Gen : Entity_Id;
5230 Typ : Entity_Id;
5232 begin
5233 if not Is_Generic_Actual_Type (T) then
5234 return Any_Type;
5236 -- If the actual is the actual of an enclosing instance, resolution
5237 -- was correct in the generic.
5239 elsif Nkind (Parent (T)) = N_Subtype_Declaration
5240 and then Is_Entity_Name (Subtype_Indication (Parent (T)))
5241 and then
5242 Is_Generic_Actual_Type (Entity (Subtype_Indication (Parent (T))))
5243 then
5244 return Any_Type;
5246 else
5247 Inst := Scope (T);
5249 if Is_Wrapper_Package (Inst) then
5250 Inst := Related_Instance (Inst);
5251 end if;
5253 Gen :=
5254 Generic_Parent
5255 (Specification (Unit_Declaration_Node (Inst)));
5257 -- Generic actual has the same name as the corresponding formal
5259 Typ := First_Entity (Gen);
5260 while Present (Typ) loop
5261 if Chars (Typ) = Chars (T) then
5262 return Typ;
5263 end if;
5265 Next_Entity (Typ);
5266 end loop;
5268 return Any_Type;
5269 end if;
5270 end Corresponding_Generic_Type;
5272 --------------------
5273 -- Current_Entity --
5274 --------------------
5276 -- The currently visible definition for a given identifier is the
5277 -- one most chained at the start of the visibility chain, i.e. the
5278 -- one that is referenced by the Node_Id value of the name of the
5279 -- given identifier.
5281 function Current_Entity (N : Node_Id) return Entity_Id is
5282 begin
5283 return Get_Name_Entity_Id (Chars (N));
5284 end Current_Entity;
5286 -----------------------------
5287 -- Current_Entity_In_Scope --
5288 -----------------------------
5290 function Current_Entity_In_Scope (N : Node_Id) return Entity_Id is
5291 E : Entity_Id;
5292 CS : constant Entity_Id := Current_Scope;
5294 Transient_Case : constant Boolean := Scope_Is_Transient;
5296 begin
5297 E := Get_Name_Entity_Id (Chars (N));
5298 while Present (E)
5299 and then Scope (E) /= CS
5300 and then (not Transient_Case or else Scope (E) /= Scope (CS))
5301 loop
5302 E := Homonym (E);
5303 end loop;
5305 return E;
5306 end Current_Entity_In_Scope;
5308 -------------------
5309 -- Current_Scope --
5310 -------------------
5312 function Current_Scope return Entity_Id is
5313 begin
5314 if Scope_Stack.Last = -1 then
5315 return Standard_Standard;
5316 else
5317 declare
5318 C : constant Entity_Id :=
5319 Scope_Stack.Table (Scope_Stack.Last).Entity;
5320 begin
5321 if Present (C) then
5322 return C;
5323 else
5324 return Standard_Standard;
5325 end if;
5326 end;
5327 end if;
5328 end Current_Scope;
5330 ----------------------------
5331 -- Current_Scope_No_Loops --
5332 ----------------------------
5334 function Current_Scope_No_Loops return Entity_Id is
5335 S : Entity_Id;
5337 begin
5338 -- Examine the scope stack starting from the current scope and skip any
5339 -- internally generated loops.
5341 S := Current_Scope;
5342 while Present (S) and then S /= Standard_Standard loop
5343 if Ekind (S) = E_Loop and then not Comes_From_Source (S) then
5344 S := Scope (S);
5345 else
5346 exit;
5347 end if;
5348 end loop;
5350 return S;
5351 end Current_Scope_No_Loops;
5353 ------------------------
5354 -- Current_Subprogram --
5355 ------------------------
5357 function Current_Subprogram return Entity_Id is
5358 Scop : constant Entity_Id := Current_Scope;
5359 begin
5360 if Is_Subprogram_Or_Generic_Subprogram (Scop) then
5361 return Scop;
5362 else
5363 return Enclosing_Subprogram (Scop);
5364 end if;
5365 end Current_Subprogram;
5367 ----------------------------------
5368 -- Deepest_Type_Access_Level --
5369 ----------------------------------
5371 function Deepest_Type_Access_Level (Typ : Entity_Id) return Uint is
5372 begin
5373 if Ekind (Typ) = E_Anonymous_Access_Type
5374 and then not Is_Local_Anonymous_Access (Typ)
5375 and then Nkind (Associated_Node_For_Itype (Typ)) = N_Object_Declaration
5376 then
5377 -- Typ is the type of an Ada 2012 stand-alone object of an anonymous
5378 -- access type.
5380 return
5381 Scope_Depth (Enclosing_Dynamic_Scope
5382 (Defining_Identifier
5383 (Associated_Node_For_Itype (Typ))));
5385 -- For generic formal type, return Int'Last (infinite).
5386 -- See comment preceding Is_Generic_Type call in Type_Access_Level.
5388 elsif Is_Generic_Type (Root_Type (Typ)) then
5389 return UI_From_Int (Int'Last);
5391 else
5392 return Type_Access_Level (Typ);
5393 end if;
5394 end Deepest_Type_Access_Level;
5396 ---------------------
5397 -- Defining_Entity --
5398 ---------------------
5400 function Defining_Entity
5401 (N : Node_Id;
5402 Empty_On_Errors : Boolean := False) return Entity_Id
5404 Err : Entity_Id := Empty;
5406 begin
5407 case Nkind (N) is
5408 when N_Abstract_Subprogram_Declaration |
5409 N_Expression_Function |
5410 N_Formal_Subprogram_Declaration |
5411 N_Generic_Package_Declaration |
5412 N_Generic_Subprogram_Declaration |
5413 N_Package_Declaration |
5414 N_Subprogram_Body |
5415 N_Subprogram_Body_Stub |
5416 N_Subprogram_Declaration |
5417 N_Subprogram_Renaming_Declaration
5419 return Defining_Entity (Specification (N));
5421 when N_Component_Declaration |
5422 N_Defining_Program_Unit_Name |
5423 N_Discriminant_Specification |
5424 N_Entry_Body |
5425 N_Entry_Declaration |
5426 N_Entry_Index_Specification |
5427 N_Exception_Declaration |
5428 N_Exception_Renaming_Declaration |
5429 N_Formal_Object_Declaration |
5430 N_Formal_Package_Declaration |
5431 N_Formal_Type_Declaration |
5432 N_Full_Type_Declaration |
5433 N_Implicit_Label_Declaration |
5434 N_Incomplete_Type_Declaration |
5435 N_Loop_Parameter_Specification |
5436 N_Number_Declaration |
5437 N_Object_Declaration |
5438 N_Object_Renaming_Declaration |
5439 N_Package_Body_Stub |
5440 N_Parameter_Specification |
5441 N_Private_Extension_Declaration |
5442 N_Private_Type_Declaration |
5443 N_Protected_Body |
5444 N_Protected_Body_Stub |
5445 N_Protected_Type_Declaration |
5446 N_Single_Protected_Declaration |
5447 N_Single_Task_Declaration |
5448 N_Subtype_Declaration |
5449 N_Task_Body |
5450 N_Task_Body_Stub |
5451 N_Task_Type_Declaration
5453 return Defining_Identifier (N);
5455 when N_Subunit =>
5456 return Defining_Entity (Proper_Body (N));
5458 when N_Function_Instantiation |
5459 N_Function_Specification |
5460 N_Generic_Function_Renaming_Declaration |
5461 N_Generic_Package_Renaming_Declaration |
5462 N_Generic_Procedure_Renaming_Declaration |
5463 N_Package_Body |
5464 N_Package_Instantiation |
5465 N_Package_Renaming_Declaration |
5466 N_Package_Specification |
5467 N_Procedure_Instantiation |
5468 N_Procedure_Specification
5470 declare
5471 Nam : constant Node_Id := Defining_Unit_Name (N);
5473 begin
5474 if Nkind (Nam) in N_Entity then
5475 return Nam;
5477 -- For Error, make up a name and attach to declaration so we
5478 -- can continue semantic analysis.
5480 elsif Nam = Error then
5481 if Empty_On_Errors then
5482 return Empty;
5483 else
5484 Err := Make_Temporary (Sloc (N), 'T');
5485 Set_Defining_Unit_Name (N, Err);
5487 return Err;
5488 end if;
5490 -- If not an entity, get defining identifier
5492 else
5493 return Defining_Identifier (Nam);
5494 end if;
5495 end;
5497 when N_Block_Statement |
5498 N_Loop_Statement =>
5499 return Entity (Identifier (N));
5501 when others =>
5502 if Empty_On_Errors then
5503 return Empty;
5504 else
5505 raise Program_Error;
5506 end if;
5508 end case;
5509 end Defining_Entity;
5511 --------------------------
5512 -- Denotes_Discriminant --
5513 --------------------------
5515 function Denotes_Discriminant
5516 (N : Node_Id;
5517 Check_Concurrent : Boolean := False) return Boolean
5519 E : Entity_Id;
5521 begin
5522 if not Is_Entity_Name (N) or else No (Entity (N)) then
5523 return False;
5524 else
5525 E := Entity (N);
5526 end if;
5528 -- If we are checking for a protected type, the discriminant may have
5529 -- been rewritten as the corresponding discriminal of the original type
5530 -- or of the corresponding concurrent record, depending on whether we
5531 -- are in the spec or body of the protected type.
5533 return Ekind (E) = E_Discriminant
5534 or else
5535 (Check_Concurrent
5536 and then Ekind (E) = E_In_Parameter
5537 and then Present (Discriminal_Link (E))
5538 and then
5539 (Is_Concurrent_Type (Scope (Discriminal_Link (E)))
5540 or else
5541 Is_Concurrent_Record_Type (Scope (Discriminal_Link (E)))));
5542 end Denotes_Discriminant;
5544 -------------------------
5545 -- Denotes_Same_Object --
5546 -------------------------
5548 function Denotes_Same_Object (A1, A2 : Node_Id) return Boolean is
5549 Obj1 : Node_Id := A1;
5550 Obj2 : Node_Id := A2;
5552 function Has_Prefix (N : Node_Id) return Boolean;
5553 -- Return True if N has attribute Prefix
5555 function Is_Renaming (N : Node_Id) return Boolean;
5556 -- Return true if N names a renaming entity
5558 function Is_Valid_Renaming (N : Node_Id) return Boolean;
5559 -- For renamings, return False if the prefix of any dereference within
5560 -- the renamed object_name is a variable, or any expression within the
5561 -- renamed object_name contains references to variables or calls on
5562 -- nonstatic functions; otherwise return True (RM 6.4.1(6.10/3))
5564 ----------------
5565 -- Has_Prefix --
5566 ----------------
5568 function Has_Prefix (N : Node_Id) return Boolean is
5569 begin
5570 return
5571 Nkind_In (N,
5572 N_Attribute_Reference,
5573 N_Expanded_Name,
5574 N_Explicit_Dereference,
5575 N_Indexed_Component,
5576 N_Reference,
5577 N_Selected_Component,
5578 N_Slice);
5579 end Has_Prefix;
5581 -----------------
5582 -- Is_Renaming --
5583 -----------------
5585 function Is_Renaming (N : Node_Id) return Boolean is
5586 begin
5587 return Is_Entity_Name (N)
5588 and then Present (Renamed_Entity (Entity (N)));
5589 end Is_Renaming;
5591 -----------------------
5592 -- Is_Valid_Renaming --
5593 -----------------------
5595 function Is_Valid_Renaming (N : Node_Id) return Boolean is
5597 function Check_Renaming (N : Node_Id) return Boolean;
5598 -- Recursive function used to traverse all the prefixes of N
5600 function Check_Renaming (N : Node_Id) return Boolean is
5601 begin
5602 if Is_Renaming (N)
5603 and then not Check_Renaming (Renamed_Entity (Entity (N)))
5604 then
5605 return False;
5606 end if;
5608 if Nkind (N) = N_Indexed_Component then
5609 declare
5610 Indx : Node_Id;
5612 begin
5613 Indx := First (Expressions (N));
5614 while Present (Indx) loop
5615 if not Is_OK_Static_Expression (Indx) then
5616 return False;
5617 end if;
5619 Next_Index (Indx);
5620 end loop;
5621 end;
5622 end if;
5624 if Has_Prefix (N) then
5625 declare
5626 P : constant Node_Id := Prefix (N);
5628 begin
5629 if Nkind (N) = N_Explicit_Dereference
5630 and then Is_Variable (P)
5631 then
5632 return False;
5634 elsif Is_Entity_Name (P)
5635 and then Ekind (Entity (P)) = E_Function
5636 then
5637 return False;
5639 elsif Nkind (P) = N_Function_Call then
5640 return False;
5641 end if;
5643 -- Recursion to continue traversing the prefix of the
5644 -- renaming expression
5646 return Check_Renaming (P);
5647 end;
5648 end if;
5650 return True;
5651 end Check_Renaming;
5653 -- Start of processing for Is_Valid_Renaming
5655 begin
5656 return Check_Renaming (N);
5657 end Is_Valid_Renaming;
5659 -- Start of processing for Denotes_Same_Object
5661 begin
5662 -- Both names statically denote the same stand-alone object or parameter
5663 -- (RM 6.4.1(6.5/3))
5665 if Is_Entity_Name (Obj1)
5666 and then Is_Entity_Name (Obj2)
5667 and then Entity (Obj1) = Entity (Obj2)
5668 then
5669 return True;
5670 end if;
5672 -- For renamings, the prefix of any dereference within the renamed
5673 -- object_name is not a variable, and any expression within the
5674 -- renamed object_name contains no references to variables nor
5675 -- calls on nonstatic functions (RM 6.4.1(6.10/3)).
5677 if Is_Renaming (Obj1) then
5678 if Is_Valid_Renaming (Obj1) then
5679 Obj1 := Renamed_Entity (Entity (Obj1));
5680 else
5681 return False;
5682 end if;
5683 end if;
5685 if Is_Renaming (Obj2) then
5686 if Is_Valid_Renaming (Obj2) then
5687 Obj2 := Renamed_Entity (Entity (Obj2));
5688 else
5689 return False;
5690 end if;
5691 end if;
5693 -- No match if not same node kind (such cases are handled by
5694 -- Denotes_Same_Prefix)
5696 if Nkind (Obj1) /= Nkind (Obj2) then
5697 return False;
5699 -- After handling valid renamings, one of the two names statically
5700 -- denoted a renaming declaration whose renamed object_name is known
5701 -- to denote the same object as the other (RM 6.4.1(6.10/3))
5703 elsif Is_Entity_Name (Obj1) then
5704 if Is_Entity_Name (Obj2) then
5705 return Entity (Obj1) = Entity (Obj2);
5706 else
5707 return False;
5708 end if;
5710 -- Both names are selected_components, their prefixes are known to
5711 -- denote the same object, and their selector_names denote the same
5712 -- component (RM 6.4.1(6.6/3)).
5714 elsif Nkind (Obj1) = N_Selected_Component then
5715 return Denotes_Same_Object (Prefix (Obj1), Prefix (Obj2))
5716 and then
5717 Entity (Selector_Name (Obj1)) = Entity (Selector_Name (Obj2));
5719 -- Both names are dereferences and the dereferenced names are known to
5720 -- denote the same object (RM 6.4.1(6.7/3))
5722 elsif Nkind (Obj1) = N_Explicit_Dereference then
5723 return Denotes_Same_Object (Prefix (Obj1), Prefix (Obj2));
5725 -- Both names are indexed_components, their prefixes are known to denote
5726 -- the same object, and each of the pairs of corresponding index values
5727 -- are either both static expressions with the same static value or both
5728 -- names that are known to denote the same object (RM 6.4.1(6.8/3))
5730 elsif Nkind (Obj1) = N_Indexed_Component then
5731 if not Denotes_Same_Object (Prefix (Obj1), Prefix (Obj2)) then
5732 return False;
5733 else
5734 declare
5735 Indx1 : Node_Id;
5736 Indx2 : Node_Id;
5738 begin
5739 Indx1 := First (Expressions (Obj1));
5740 Indx2 := First (Expressions (Obj2));
5741 while Present (Indx1) loop
5743 -- Indexes must denote the same static value or same object
5745 if Is_OK_Static_Expression (Indx1) then
5746 if not Is_OK_Static_Expression (Indx2) then
5747 return False;
5749 elsif Expr_Value (Indx1) /= Expr_Value (Indx2) then
5750 return False;
5751 end if;
5753 elsif not Denotes_Same_Object (Indx1, Indx2) then
5754 return False;
5755 end if;
5757 Next (Indx1);
5758 Next (Indx2);
5759 end loop;
5761 return True;
5762 end;
5763 end if;
5765 -- Both names are slices, their prefixes are known to denote the same
5766 -- object, and the two slices have statically matching index constraints
5767 -- (RM 6.4.1(6.9/3))
5769 elsif Nkind (Obj1) = N_Slice
5770 and then Denotes_Same_Object (Prefix (Obj1), Prefix (Obj2))
5771 then
5772 declare
5773 Lo1, Lo2, Hi1, Hi2 : Node_Id;
5775 begin
5776 Get_Index_Bounds (Etype (Obj1), Lo1, Hi1);
5777 Get_Index_Bounds (Etype (Obj2), Lo2, Hi2);
5779 -- Check whether bounds are statically identical. There is no
5780 -- attempt to detect partial overlap of slices.
5782 return Denotes_Same_Object (Lo1, Lo2)
5783 and then
5784 Denotes_Same_Object (Hi1, Hi2);
5785 end;
5787 -- In the recursion, literals appear as indexes
5789 elsif Nkind (Obj1) = N_Integer_Literal
5790 and then
5791 Nkind (Obj2) = N_Integer_Literal
5792 then
5793 return Intval (Obj1) = Intval (Obj2);
5795 else
5796 return False;
5797 end if;
5798 end Denotes_Same_Object;
5800 -------------------------
5801 -- Denotes_Same_Prefix --
5802 -------------------------
5804 function Denotes_Same_Prefix (A1, A2 : Node_Id) return Boolean is
5805 begin
5806 if Is_Entity_Name (A1) then
5807 if Nkind_In (A2, N_Selected_Component, N_Indexed_Component)
5808 and then not Is_Access_Type (Etype (A1))
5809 then
5810 return Denotes_Same_Object (A1, Prefix (A2))
5811 or else Denotes_Same_Prefix (A1, Prefix (A2));
5812 else
5813 return False;
5814 end if;
5816 elsif Is_Entity_Name (A2) then
5817 return Denotes_Same_Prefix (A1 => A2, A2 => A1);
5819 elsif Nkind_In (A1, N_Selected_Component, N_Indexed_Component, N_Slice)
5820 and then
5821 Nkind_In (A2, N_Selected_Component, N_Indexed_Component, N_Slice)
5822 then
5823 declare
5824 Root1, Root2 : Node_Id;
5825 Depth1, Depth2 : Nat := 0;
5827 begin
5828 Root1 := Prefix (A1);
5829 while not Is_Entity_Name (Root1) loop
5830 if not Nkind_In
5831 (Root1, N_Selected_Component, N_Indexed_Component)
5832 then
5833 return False;
5834 else
5835 Root1 := Prefix (Root1);
5836 end if;
5838 Depth1 := Depth1 + 1;
5839 end loop;
5841 Root2 := Prefix (A2);
5842 while not Is_Entity_Name (Root2) loop
5843 if not Nkind_In (Root2, N_Selected_Component,
5844 N_Indexed_Component)
5845 then
5846 return False;
5847 else
5848 Root2 := Prefix (Root2);
5849 end if;
5851 Depth2 := Depth2 + 1;
5852 end loop;
5854 -- If both have the same depth and they do not denote the same
5855 -- object, they are disjoint and no warning is needed.
5857 if Depth1 = Depth2 then
5858 return False;
5860 elsif Depth1 > Depth2 then
5861 Root1 := Prefix (A1);
5862 for J in 1 .. Depth1 - Depth2 - 1 loop
5863 Root1 := Prefix (Root1);
5864 end loop;
5866 return Denotes_Same_Object (Root1, A2);
5868 else
5869 Root2 := Prefix (A2);
5870 for J in 1 .. Depth2 - Depth1 - 1 loop
5871 Root2 := Prefix (Root2);
5872 end loop;
5874 return Denotes_Same_Object (A1, Root2);
5875 end if;
5876 end;
5878 else
5879 return False;
5880 end if;
5881 end Denotes_Same_Prefix;
5883 ----------------------
5884 -- Denotes_Variable --
5885 ----------------------
5887 function Denotes_Variable (N : Node_Id) return Boolean is
5888 begin
5889 return Is_Variable (N) and then Paren_Count (N) = 0;
5890 end Denotes_Variable;
5892 -----------------------------
5893 -- Depends_On_Discriminant --
5894 -----------------------------
5896 function Depends_On_Discriminant (N : Node_Id) return Boolean is
5897 L : Node_Id;
5898 H : Node_Id;
5900 begin
5901 Get_Index_Bounds (N, L, H);
5902 return Denotes_Discriminant (L) or else Denotes_Discriminant (H);
5903 end Depends_On_Discriminant;
5905 -------------------------
5906 -- Designate_Same_Unit --
5907 -------------------------
5909 function Designate_Same_Unit
5910 (Name1 : Node_Id;
5911 Name2 : Node_Id) return Boolean
5913 K1 : constant Node_Kind := Nkind (Name1);
5914 K2 : constant Node_Kind := Nkind (Name2);
5916 function Prefix_Node (N : Node_Id) return Node_Id;
5917 -- Returns the parent unit name node of a defining program unit name
5918 -- or the prefix if N is a selected component or an expanded name.
5920 function Select_Node (N : Node_Id) return Node_Id;
5921 -- Returns the defining identifier node of a defining program unit
5922 -- name or the selector node if N is a selected component or an
5923 -- expanded name.
5925 -----------------
5926 -- Prefix_Node --
5927 -----------------
5929 function Prefix_Node (N : Node_Id) return Node_Id is
5930 begin
5931 if Nkind (N) = N_Defining_Program_Unit_Name then
5932 return Name (N);
5933 else
5934 return Prefix (N);
5935 end if;
5936 end Prefix_Node;
5938 -----------------
5939 -- Select_Node --
5940 -----------------
5942 function Select_Node (N : Node_Id) return Node_Id is
5943 begin
5944 if Nkind (N) = N_Defining_Program_Unit_Name then
5945 return Defining_Identifier (N);
5946 else
5947 return Selector_Name (N);
5948 end if;
5949 end Select_Node;
5951 -- Start of processing for Designate_Same_Unit
5953 begin
5954 if Nkind_In (K1, N_Identifier, N_Defining_Identifier)
5955 and then
5956 Nkind_In (K2, N_Identifier, N_Defining_Identifier)
5957 then
5958 return Chars (Name1) = Chars (Name2);
5960 elsif Nkind_In (K1, N_Expanded_Name,
5961 N_Selected_Component,
5962 N_Defining_Program_Unit_Name)
5963 and then
5964 Nkind_In (K2, N_Expanded_Name,
5965 N_Selected_Component,
5966 N_Defining_Program_Unit_Name)
5967 then
5968 return
5969 (Chars (Select_Node (Name1)) = Chars (Select_Node (Name2)))
5970 and then
5971 Designate_Same_Unit (Prefix_Node (Name1), Prefix_Node (Name2));
5973 else
5974 return False;
5975 end if;
5976 end Designate_Same_Unit;
5978 ------------------------------------------
5979 -- function Dynamic_Accessibility_Level --
5980 ------------------------------------------
5982 function Dynamic_Accessibility_Level (Expr : Node_Id) return Node_Id is
5983 E : Entity_Id;
5984 Loc : constant Source_Ptr := Sloc (Expr);
5986 function Make_Level_Literal (Level : Uint) return Node_Id;
5987 -- Construct an integer literal representing an accessibility level
5988 -- with its type set to Natural.
5990 ------------------------
5991 -- Make_Level_Literal --
5992 ------------------------
5994 function Make_Level_Literal (Level : Uint) return Node_Id is
5995 Result : constant Node_Id := Make_Integer_Literal (Loc, Level);
5996 begin
5997 Set_Etype (Result, Standard_Natural);
5998 return Result;
5999 end Make_Level_Literal;
6001 -- Start of processing for Dynamic_Accessibility_Level
6003 begin
6004 if Is_Entity_Name (Expr) then
6005 E := Entity (Expr);
6007 if Present (Renamed_Object (E)) then
6008 return Dynamic_Accessibility_Level (Renamed_Object (E));
6009 end if;
6011 if Is_Formal (E) or else Ekind_In (E, E_Variable, E_Constant) then
6012 if Present (Extra_Accessibility (E)) then
6013 return New_Occurrence_Of (Extra_Accessibility (E), Loc);
6014 end if;
6015 end if;
6016 end if;
6018 -- Unimplemented: Ptr.all'Access, where Ptr has Extra_Accessibility ???
6020 case Nkind (Expr) is
6022 -- For access discriminant, the level of the enclosing object
6024 when N_Selected_Component =>
6025 if Ekind (Entity (Selector_Name (Expr))) = E_Discriminant
6026 and then Ekind (Etype (Entity (Selector_Name (Expr)))) =
6027 E_Anonymous_Access_Type
6028 then
6029 return Make_Level_Literal (Object_Access_Level (Expr));
6030 end if;
6032 when N_Attribute_Reference =>
6033 case Get_Attribute_Id (Attribute_Name (Expr)) is
6035 -- For X'Access, the level of the prefix X
6037 when Attribute_Access =>
6038 return Make_Level_Literal
6039 (Object_Access_Level (Prefix (Expr)));
6041 -- Treat the unchecked attributes as library-level
6043 when Attribute_Unchecked_Access |
6044 Attribute_Unrestricted_Access =>
6045 return Make_Level_Literal (Scope_Depth (Standard_Standard));
6047 -- No other access-valued attributes
6049 when others =>
6050 raise Program_Error;
6051 end case;
6053 when N_Allocator =>
6055 -- Unimplemented: depends on context. As an actual parameter where
6056 -- formal type is anonymous, use
6057 -- Scope_Depth (Current_Scope) + 1.
6058 -- For other cases, see 3.10.2(14/3) and following. ???
6060 null;
6062 when N_Type_Conversion =>
6063 if not Is_Local_Anonymous_Access (Etype (Expr)) then
6065 -- Handle type conversions introduced for a rename of an
6066 -- Ada 2012 stand-alone object of an anonymous access type.
6068 return Dynamic_Accessibility_Level (Expression (Expr));
6069 end if;
6071 when others =>
6072 null;
6073 end case;
6075 return Make_Level_Literal (Type_Access_Level (Etype (Expr)));
6076 end Dynamic_Accessibility_Level;
6078 -----------------------------------
6079 -- Effective_Extra_Accessibility --
6080 -----------------------------------
6082 function Effective_Extra_Accessibility (Id : Entity_Id) return Entity_Id is
6083 begin
6084 if Present (Renamed_Object (Id))
6085 and then Is_Entity_Name (Renamed_Object (Id))
6086 then
6087 return Effective_Extra_Accessibility (Entity (Renamed_Object (Id)));
6088 else
6089 return Extra_Accessibility (Id);
6090 end if;
6091 end Effective_Extra_Accessibility;
6093 -----------------------------
6094 -- Effective_Reads_Enabled --
6095 -----------------------------
6097 function Effective_Reads_Enabled (Id : Entity_Id) return Boolean is
6098 begin
6099 return Has_Enabled_Property (Id, Name_Effective_Reads);
6100 end Effective_Reads_Enabled;
6102 ------------------------------
6103 -- Effective_Writes_Enabled --
6104 ------------------------------
6106 function Effective_Writes_Enabled (Id : Entity_Id) return Boolean is
6107 begin
6108 return Has_Enabled_Property (Id, Name_Effective_Writes);
6109 end Effective_Writes_Enabled;
6111 ------------------------------
6112 -- Enclosing_Comp_Unit_Node --
6113 ------------------------------
6115 function Enclosing_Comp_Unit_Node (N : Node_Id) return Node_Id is
6116 Current_Node : Node_Id;
6118 begin
6119 Current_Node := N;
6120 while Present (Current_Node)
6121 and then Nkind (Current_Node) /= N_Compilation_Unit
6122 loop
6123 Current_Node := Parent (Current_Node);
6124 end loop;
6126 if Nkind (Current_Node) /= N_Compilation_Unit then
6127 return Empty;
6128 else
6129 return Current_Node;
6130 end if;
6131 end Enclosing_Comp_Unit_Node;
6133 --------------------------
6134 -- Enclosing_CPP_Parent --
6135 --------------------------
6137 function Enclosing_CPP_Parent (Typ : Entity_Id) return Entity_Id is
6138 Parent_Typ : Entity_Id := Typ;
6140 begin
6141 while not Is_CPP_Class (Parent_Typ)
6142 and then Etype (Parent_Typ) /= Parent_Typ
6143 loop
6144 Parent_Typ := Etype (Parent_Typ);
6146 if Is_Private_Type (Parent_Typ) then
6147 Parent_Typ := Full_View (Base_Type (Parent_Typ));
6148 end if;
6149 end loop;
6151 pragma Assert (Is_CPP_Class (Parent_Typ));
6152 return Parent_Typ;
6153 end Enclosing_CPP_Parent;
6155 ---------------------------
6156 -- Enclosing_Declaration --
6157 ---------------------------
6159 function Enclosing_Declaration (N : Node_Id) return Node_Id is
6160 Decl : Node_Id := N;
6162 begin
6163 while Present (Decl)
6164 and then not (Nkind (Decl) in N_Declaration
6165 or else
6166 Nkind (Decl) in N_Later_Decl_Item)
6167 loop
6168 Decl := Parent (Decl);
6169 end loop;
6171 return Decl;
6172 end Enclosing_Declaration;
6174 ----------------------------
6175 -- Enclosing_Generic_Body --
6176 ----------------------------
6178 function Enclosing_Generic_Body
6179 (N : Node_Id) return Node_Id
6181 P : Node_Id;
6182 Decl : Node_Id;
6183 Spec : Node_Id;
6185 begin
6186 P := Parent (N);
6187 while Present (P) loop
6188 if Nkind (P) = N_Package_Body
6189 or else Nkind (P) = N_Subprogram_Body
6190 then
6191 Spec := Corresponding_Spec (P);
6193 if Present (Spec) then
6194 Decl := Unit_Declaration_Node (Spec);
6196 if Nkind (Decl) = N_Generic_Package_Declaration
6197 or else Nkind (Decl) = N_Generic_Subprogram_Declaration
6198 then
6199 return P;
6200 end if;
6201 end if;
6202 end if;
6204 P := Parent (P);
6205 end loop;
6207 return Empty;
6208 end Enclosing_Generic_Body;
6210 ----------------------------
6211 -- Enclosing_Generic_Unit --
6212 ----------------------------
6214 function Enclosing_Generic_Unit
6215 (N : Node_Id) return Node_Id
6217 P : Node_Id;
6218 Decl : Node_Id;
6219 Spec : Node_Id;
6221 begin
6222 P := Parent (N);
6223 while Present (P) loop
6224 if Nkind (P) = N_Generic_Package_Declaration
6225 or else Nkind (P) = N_Generic_Subprogram_Declaration
6226 then
6227 return P;
6229 elsif Nkind (P) = N_Package_Body
6230 or else Nkind (P) = N_Subprogram_Body
6231 then
6232 Spec := Corresponding_Spec (P);
6234 if Present (Spec) then
6235 Decl := Unit_Declaration_Node (Spec);
6237 if Nkind (Decl) = N_Generic_Package_Declaration
6238 or else Nkind (Decl) = N_Generic_Subprogram_Declaration
6239 then
6240 return Decl;
6241 end if;
6242 end if;
6243 end if;
6245 P := Parent (P);
6246 end loop;
6248 return Empty;
6249 end Enclosing_Generic_Unit;
6251 -------------------------------
6252 -- Enclosing_Lib_Unit_Entity --
6253 -------------------------------
6255 function Enclosing_Lib_Unit_Entity
6256 (E : Entity_Id := Current_Scope) return Entity_Id
6258 Unit_Entity : Entity_Id;
6260 begin
6261 -- Look for enclosing library unit entity by following scope links.
6262 -- Equivalent to, but faster than indexing through the scope stack.
6264 Unit_Entity := E;
6265 while (Present (Scope (Unit_Entity))
6266 and then Scope (Unit_Entity) /= Standard_Standard)
6267 and not Is_Child_Unit (Unit_Entity)
6268 loop
6269 Unit_Entity := Scope (Unit_Entity);
6270 end loop;
6272 return Unit_Entity;
6273 end Enclosing_Lib_Unit_Entity;
6275 -----------------------------
6276 -- Enclosing_Lib_Unit_Node --
6277 -----------------------------
6279 function Enclosing_Lib_Unit_Node (N : Node_Id) return Node_Id is
6280 Encl_Unit : Node_Id;
6282 begin
6283 Encl_Unit := Enclosing_Comp_Unit_Node (N);
6284 while Present (Encl_Unit)
6285 and then Nkind (Unit (Encl_Unit)) = N_Subunit
6286 loop
6287 Encl_Unit := Library_Unit (Encl_Unit);
6288 end loop;
6290 return Encl_Unit;
6291 end Enclosing_Lib_Unit_Node;
6293 -----------------------
6294 -- Enclosing_Package --
6295 -----------------------
6297 function Enclosing_Package (E : Entity_Id) return Entity_Id is
6298 Dynamic_Scope : constant Entity_Id := Enclosing_Dynamic_Scope (E);
6300 begin
6301 if Dynamic_Scope = Standard_Standard then
6302 return Standard_Standard;
6304 elsif Dynamic_Scope = Empty then
6305 return Empty;
6307 elsif Ekind_In (Dynamic_Scope, E_Package, E_Package_Body,
6308 E_Generic_Package)
6309 then
6310 return Dynamic_Scope;
6312 else
6313 return Enclosing_Package (Dynamic_Scope);
6314 end if;
6315 end Enclosing_Package;
6317 -------------------------------------
6318 -- Enclosing_Package_Or_Subprogram --
6319 -------------------------------------
6321 function Enclosing_Package_Or_Subprogram (E : Entity_Id) return Entity_Id is
6322 S : Entity_Id;
6324 begin
6325 S := Scope (E);
6326 while Present (S) loop
6327 if Is_Package_Or_Generic_Package (S)
6328 or else Ekind (S) = E_Package_Body
6329 then
6330 return S;
6332 elsif Is_Subprogram_Or_Generic_Subprogram (S)
6333 or else Ekind (S) = E_Subprogram_Body
6334 then
6335 return S;
6337 else
6338 S := Scope (S);
6339 end if;
6340 end loop;
6342 return Empty;
6343 end Enclosing_Package_Or_Subprogram;
6345 --------------------------
6346 -- Enclosing_Subprogram --
6347 --------------------------
6349 function Enclosing_Subprogram (E : Entity_Id) return Entity_Id is
6350 Dynamic_Scope : constant Entity_Id := Enclosing_Dynamic_Scope (E);
6352 begin
6353 if Dynamic_Scope = Standard_Standard then
6354 return Empty;
6356 elsif Dynamic_Scope = Empty then
6357 return Empty;
6359 elsif Ekind (Dynamic_Scope) = E_Subprogram_Body then
6360 return Corresponding_Spec (Parent (Parent (Dynamic_Scope)));
6362 elsif Ekind (Dynamic_Scope) = E_Block
6363 or else Ekind (Dynamic_Scope) = E_Return_Statement
6364 then
6365 return Enclosing_Subprogram (Dynamic_Scope);
6367 elsif Ekind (Dynamic_Scope) = E_Task_Type then
6368 return Get_Task_Body_Procedure (Dynamic_Scope);
6370 elsif Ekind (Dynamic_Scope) = E_Limited_Private_Type
6371 and then Present (Full_View (Dynamic_Scope))
6372 and then Ekind (Full_View (Dynamic_Scope)) = E_Task_Type
6373 then
6374 return Get_Task_Body_Procedure (Full_View (Dynamic_Scope));
6376 -- No body is generated if the protected operation is eliminated
6378 elsif Convention (Dynamic_Scope) = Convention_Protected
6379 and then not Is_Eliminated (Dynamic_Scope)
6380 and then Present (Protected_Body_Subprogram (Dynamic_Scope))
6381 then
6382 return Protected_Body_Subprogram (Dynamic_Scope);
6384 else
6385 return Dynamic_Scope;
6386 end if;
6387 end Enclosing_Subprogram;
6389 ------------------------
6390 -- Ensure_Freeze_Node --
6391 ------------------------
6393 procedure Ensure_Freeze_Node (E : Entity_Id) is
6394 FN : Node_Id;
6395 begin
6396 if No (Freeze_Node (E)) then
6397 FN := Make_Freeze_Entity (Sloc (E));
6398 Set_Has_Delayed_Freeze (E);
6399 Set_Freeze_Node (E, FN);
6400 Set_Access_Types_To_Process (FN, No_Elist);
6401 Set_TSS_Elist (FN, No_Elist);
6402 Set_Entity (FN, E);
6403 end if;
6404 end Ensure_Freeze_Node;
6406 ----------------
6407 -- Enter_Name --
6408 ----------------
6410 procedure Enter_Name (Def_Id : Entity_Id) is
6411 C : constant Entity_Id := Current_Entity (Def_Id);
6412 E : constant Entity_Id := Current_Entity_In_Scope (Def_Id);
6413 S : constant Entity_Id := Current_Scope;
6415 begin
6416 Generate_Definition (Def_Id);
6418 -- Add new name to current scope declarations. Check for duplicate
6419 -- declaration, which may or may not be a genuine error.
6421 if Present (E) then
6423 -- Case of previous entity entered because of a missing declaration
6424 -- or else a bad subtype indication. Best is to use the new entity,
6425 -- and make the previous one invisible.
6427 if Etype (E) = Any_Type then
6428 Set_Is_Immediately_Visible (E, False);
6430 -- Case of renaming declaration constructed for package instances.
6431 -- if there is an explicit declaration with the same identifier,
6432 -- the renaming is not immediately visible any longer, but remains
6433 -- visible through selected component notation.
6435 elsif Nkind (Parent (E)) = N_Package_Renaming_Declaration
6436 and then not Comes_From_Source (E)
6437 then
6438 Set_Is_Immediately_Visible (E, False);
6440 -- The new entity may be the package renaming, which has the same
6441 -- same name as a generic formal which has been seen already.
6443 elsif Nkind (Parent (Def_Id)) = N_Package_Renaming_Declaration
6444 and then not Comes_From_Source (Def_Id)
6445 then
6446 Set_Is_Immediately_Visible (E, False);
6448 -- For a fat pointer corresponding to a remote access to subprogram,
6449 -- we use the same identifier as the RAS type, so that the proper
6450 -- name appears in the stub. This type is only retrieved through
6451 -- the RAS type and never by visibility, and is not added to the
6452 -- visibility list (see below).
6454 elsif Nkind (Parent (Def_Id)) = N_Full_Type_Declaration
6455 and then Ekind (Def_Id) = E_Record_Type
6456 and then Present (Corresponding_Remote_Type (Def_Id))
6457 then
6458 null;
6460 -- Case of an implicit operation or derived literal. The new entity
6461 -- hides the implicit one, which is removed from all visibility,
6462 -- i.e. the entity list of its scope, and homonym chain of its name.
6464 elsif (Is_Overloadable (E) and then Is_Inherited_Operation (E))
6465 or else Is_Internal (E)
6466 then
6467 declare
6468 Decl : constant Node_Id := Parent (E);
6469 Prev : Entity_Id;
6470 Prev_Vis : Entity_Id;
6472 begin
6473 -- If E is an implicit declaration, it cannot be the first
6474 -- entity in the scope.
6476 Prev := First_Entity (Current_Scope);
6477 while Present (Prev) and then Next_Entity (Prev) /= E loop
6478 Next_Entity (Prev);
6479 end loop;
6481 if No (Prev) then
6483 -- If E is not on the entity chain of the current scope,
6484 -- it is an implicit declaration in the generic formal
6485 -- part of a generic subprogram. When analyzing the body,
6486 -- the generic formals are visible but not on the entity
6487 -- chain of the subprogram. The new entity will become
6488 -- the visible one in the body.
6490 pragma Assert
6491 (Nkind (Parent (Decl)) = N_Generic_Subprogram_Declaration);
6492 null;
6494 else
6495 Set_Next_Entity (Prev, Next_Entity (E));
6497 if No (Next_Entity (Prev)) then
6498 Set_Last_Entity (Current_Scope, Prev);
6499 end if;
6501 if E = Current_Entity (E) then
6502 Prev_Vis := Empty;
6504 else
6505 Prev_Vis := Current_Entity (E);
6506 while Homonym (Prev_Vis) /= E loop
6507 Prev_Vis := Homonym (Prev_Vis);
6508 end loop;
6509 end if;
6511 if Present (Prev_Vis) then
6513 -- Skip E in the visibility chain
6515 Set_Homonym (Prev_Vis, Homonym (E));
6517 else
6518 Set_Name_Entity_Id (Chars (E), Homonym (E));
6519 end if;
6520 end if;
6521 end;
6523 -- This section of code could use a comment ???
6525 elsif Present (Etype (E))
6526 and then Is_Concurrent_Type (Etype (E))
6527 and then E = Def_Id
6528 then
6529 return;
6531 -- If the homograph is a protected component renaming, it should not
6532 -- be hiding the current entity. Such renamings are treated as weak
6533 -- declarations.
6535 elsif Is_Prival (E) then
6536 Set_Is_Immediately_Visible (E, False);
6538 -- In this case the current entity is a protected component renaming.
6539 -- Perform minimal decoration by setting the scope and return since
6540 -- the prival should not be hiding other visible entities.
6542 elsif Is_Prival (Def_Id) then
6543 Set_Scope (Def_Id, Current_Scope);
6544 return;
6546 -- Analogous to privals, the discriminal generated for an entry index
6547 -- parameter acts as a weak declaration. Perform minimal decoration
6548 -- to avoid bogus errors.
6550 elsif Is_Discriminal (Def_Id)
6551 and then Ekind (Discriminal_Link (Def_Id)) = E_Entry_Index_Parameter
6552 then
6553 Set_Scope (Def_Id, Current_Scope);
6554 return;
6556 -- In the body or private part of an instance, a type extension may
6557 -- introduce a component with the same name as that of an actual. The
6558 -- legality rule is not enforced, but the semantics of the full type
6559 -- with two components of same name are not clear at this point???
6561 elsif In_Instance_Not_Visible then
6562 null;
6564 -- When compiling a package body, some child units may have become
6565 -- visible. They cannot conflict with local entities that hide them.
6567 elsif Is_Child_Unit (E)
6568 and then In_Open_Scopes (Scope (E))
6569 and then not Is_Immediately_Visible (E)
6570 then
6571 null;
6573 -- Conversely, with front-end inlining we may compile the parent body
6574 -- first, and a child unit subsequently. The context is now the
6575 -- parent spec, and body entities are not visible.
6577 elsif Is_Child_Unit (Def_Id)
6578 and then Is_Package_Body_Entity (E)
6579 and then not In_Package_Body (Current_Scope)
6580 then
6581 null;
6583 -- Case of genuine duplicate declaration
6585 else
6586 Error_Msg_Sloc := Sloc (E);
6588 -- If the previous declaration is an incomplete type declaration
6589 -- this may be an attempt to complete it with a private type. The
6590 -- following avoids confusing cascaded errors.
6592 if Nkind (Parent (E)) = N_Incomplete_Type_Declaration
6593 and then Nkind (Parent (Def_Id)) = N_Private_Type_Declaration
6594 then
6595 Error_Msg_N
6596 ("incomplete type cannot be completed with a private " &
6597 "declaration", Parent (Def_Id));
6598 Set_Is_Immediately_Visible (E, False);
6599 Set_Full_View (E, Def_Id);
6601 -- An inherited component of a record conflicts with a new
6602 -- discriminant. The discriminant is inserted first in the scope,
6603 -- but the error should be posted on it, not on the component.
6605 elsif Ekind (E) = E_Discriminant
6606 and then Present (Scope (Def_Id))
6607 and then Scope (Def_Id) /= Current_Scope
6608 then
6609 Error_Msg_Sloc := Sloc (Def_Id);
6610 Error_Msg_N ("& conflicts with declaration#", E);
6611 return;
6613 -- If the name of the unit appears in its own context clause, a
6614 -- dummy package with the name has already been created, and the
6615 -- error emitted. Try to continue quietly.
6617 elsif Error_Posted (E)
6618 and then Sloc (E) = No_Location
6619 and then Nkind (Parent (E)) = N_Package_Specification
6620 and then Current_Scope = Standard_Standard
6621 then
6622 Set_Scope (Def_Id, Current_Scope);
6623 return;
6625 else
6626 Error_Msg_N ("& conflicts with declaration#", Def_Id);
6628 -- Avoid cascaded messages with duplicate components in
6629 -- derived types.
6631 if Ekind_In (E, E_Component, E_Discriminant) then
6632 return;
6633 end if;
6634 end if;
6636 if Nkind (Parent (Parent (Def_Id))) =
6637 N_Generic_Subprogram_Declaration
6638 and then Def_Id =
6639 Defining_Entity (Specification (Parent (Parent (Def_Id))))
6640 then
6641 Error_Msg_N ("\generic units cannot be overloaded", Def_Id);
6642 end if;
6644 -- If entity is in standard, then we are in trouble, because it
6645 -- means that we have a library package with a duplicated name.
6646 -- That's hard to recover from, so abort.
6648 if S = Standard_Standard then
6649 raise Unrecoverable_Error;
6651 -- Otherwise we continue with the declaration. Having two
6652 -- identical declarations should not cause us too much trouble.
6654 else
6655 null;
6656 end if;
6657 end if;
6658 end if;
6660 -- If we fall through, declaration is OK, at least OK enough to continue
6662 -- If Def_Id is a discriminant or a record component we are in the midst
6663 -- of inheriting components in a derived record definition. Preserve
6664 -- their Ekind and Etype.
6666 if Ekind_In (Def_Id, E_Discriminant, E_Component) then
6667 null;
6669 -- If a type is already set, leave it alone (happens when a type
6670 -- declaration is reanalyzed following a call to the optimizer).
6672 elsif Present (Etype (Def_Id)) then
6673 null;
6675 -- Otherwise, the kind E_Void insures that premature uses of the entity
6676 -- will be detected. Any_Type insures that no cascaded errors will occur
6678 else
6679 Set_Ekind (Def_Id, E_Void);
6680 Set_Etype (Def_Id, Any_Type);
6681 end if;
6683 -- Inherited discriminants and components in derived record types are
6684 -- immediately visible. Itypes are not.
6686 -- Unless the Itype is for a record type with a corresponding remote
6687 -- type (what is that about, it was not commented ???)
6689 if Ekind_In (Def_Id, E_Discriminant, E_Component)
6690 or else
6691 ((not Is_Record_Type (Def_Id)
6692 or else No (Corresponding_Remote_Type (Def_Id)))
6693 and then not Is_Itype (Def_Id))
6694 then
6695 Set_Is_Immediately_Visible (Def_Id);
6696 Set_Current_Entity (Def_Id);
6697 end if;
6699 Set_Homonym (Def_Id, C);
6700 Append_Entity (Def_Id, S);
6701 Set_Public_Status (Def_Id);
6703 -- Declaring a homonym is not allowed in SPARK ...
6705 if Present (C) and then Restriction_Check_Required (SPARK_05) then
6706 declare
6707 Enclosing_Subp : constant Node_Id := Enclosing_Subprogram (Def_Id);
6708 Enclosing_Pack : constant Node_Id := Enclosing_Package (Def_Id);
6709 Other_Scope : constant Node_Id := Enclosing_Dynamic_Scope (C);
6711 begin
6712 -- ... unless the new declaration is in a subprogram, and the
6713 -- visible declaration is a variable declaration or a parameter
6714 -- specification outside that subprogram.
6716 if Present (Enclosing_Subp)
6717 and then Nkind_In (Parent (C), N_Object_Declaration,
6718 N_Parameter_Specification)
6719 and then not Scope_Within_Or_Same (Other_Scope, Enclosing_Subp)
6720 then
6721 null;
6723 -- ... or the new declaration is in a package, and the visible
6724 -- declaration occurs outside that package.
6726 elsif Present (Enclosing_Pack)
6727 and then not Scope_Within_Or_Same (Other_Scope, Enclosing_Pack)
6728 then
6729 null;
6731 -- ... or the new declaration is a component declaration in a
6732 -- record type definition.
6734 elsif Nkind (Parent (Def_Id)) = N_Component_Declaration then
6735 null;
6737 -- Don't issue error for non-source entities
6739 elsif Comes_From_Source (Def_Id)
6740 and then Comes_From_Source (C)
6741 then
6742 Error_Msg_Sloc := Sloc (C);
6743 Check_SPARK_05_Restriction
6744 ("redeclaration of identifier &#", Def_Id);
6745 end if;
6746 end;
6747 end if;
6749 -- Warn if new entity hides an old one
6751 if Warn_On_Hiding and then Present (C)
6753 -- Don't warn for record components since they always have a well
6754 -- defined scope which does not confuse other uses. Note that in
6755 -- some cases, Ekind has not been set yet.
6757 and then Ekind (C) /= E_Component
6758 and then Ekind (C) /= E_Discriminant
6759 and then Nkind (Parent (C)) /= N_Component_Declaration
6760 and then Ekind (Def_Id) /= E_Component
6761 and then Ekind (Def_Id) /= E_Discriminant
6762 and then Nkind (Parent (Def_Id)) /= N_Component_Declaration
6764 -- Don't warn for one character variables. It is too common to use
6765 -- such variables as locals and will just cause too many false hits.
6767 and then Length_Of_Name (Chars (C)) /= 1
6769 -- Don't warn for non-source entities
6771 and then Comes_From_Source (C)
6772 and then Comes_From_Source (Def_Id)
6774 -- Don't warn unless entity in question is in extended main source
6776 and then In_Extended_Main_Source_Unit (Def_Id)
6778 -- Finally, the hidden entity must be either immediately visible or
6779 -- use visible (i.e. from a used package).
6781 and then
6782 (Is_Immediately_Visible (C)
6783 or else
6784 Is_Potentially_Use_Visible (C))
6785 then
6786 Error_Msg_Sloc := Sloc (C);
6787 Error_Msg_N ("declaration hides &#?h?", Def_Id);
6788 end if;
6789 end Enter_Name;
6791 ---------------
6792 -- Entity_Of --
6793 ---------------
6795 function Entity_Of (N : Node_Id) return Entity_Id is
6796 Id : Entity_Id;
6798 begin
6799 Id := Empty;
6801 if Is_Entity_Name (N) then
6802 Id := Entity (N);
6804 -- Follow a possible chain of renamings to reach the root renamed
6805 -- object.
6807 while Present (Id)
6808 and then Is_Object (Id)
6809 and then Present (Renamed_Object (Id))
6810 loop
6811 if Is_Entity_Name (Renamed_Object (Id)) then
6812 Id := Entity (Renamed_Object (Id));
6813 else
6814 Id := Empty;
6815 exit;
6816 end if;
6817 end loop;
6818 end if;
6820 return Id;
6821 end Entity_Of;
6823 --------------------------
6824 -- Explain_Limited_Type --
6825 --------------------------
6827 procedure Explain_Limited_Type (T : Entity_Id; N : Node_Id) is
6828 C : Entity_Id;
6830 begin
6831 -- For array, component type must be limited
6833 if Is_Array_Type (T) then
6834 Error_Msg_Node_2 := T;
6835 Error_Msg_NE
6836 ("\component type& of type& is limited", N, Component_Type (T));
6837 Explain_Limited_Type (Component_Type (T), N);
6839 elsif Is_Record_Type (T) then
6841 -- No need for extra messages if explicit limited record
6843 if Is_Limited_Record (Base_Type (T)) then
6844 return;
6845 end if;
6847 -- Otherwise find a limited component. Check only components that
6848 -- come from source, or inherited components that appear in the
6849 -- source of the ancestor.
6851 C := First_Component (T);
6852 while Present (C) loop
6853 if Is_Limited_Type (Etype (C))
6854 and then
6855 (Comes_From_Source (C)
6856 or else
6857 (Present (Original_Record_Component (C))
6858 and then
6859 Comes_From_Source (Original_Record_Component (C))))
6860 then
6861 Error_Msg_Node_2 := T;
6862 Error_Msg_NE ("\component& of type& has limited type", N, C);
6863 Explain_Limited_Type (Etype (C), N);
6864 return;
6865 end if;
6867 Next_Component (C);
6868 end loop;
6870 -- The type may be declared explicitly limited, even if no component
6871 -- of it is limited, in which case we fall out of the loop.
6872 return;
6873 end if;
6874 end Explain_Limited_Type;
6876 -------------------------------
6877 -- Extensions_Visible_Status --
6878 -------------------------------
6880 function Extensions_Visible_Status
6881 (Id : Entity_Id) return Extensions_Visible_Mode
6883 Arg : Node_Id;
6884 Decl : Node_Id;
6885 Expr : Node_Id;
6886 Prag : Node_Id;
6887 Subp : Entity_Id;
6889 begin
6890 -- When a formal parameter is subject to Extensions_Visible, the pragma
6891 -- is stored in the contract of related subprogram.
6893 if Is_Formal (Id) then
6894 Subp := Scope (Id);
6896 elsif Is_Subprogram_Or_Generic_Subprogram (Id) then
6897 Subp := Id;
6899 -- No other construct carries this pragma
6901 else
6902 return Extensions_Visible_None;
6903 end if;
6905 Prag := Get_Pragma (Subp, Pragma_Extensions_Visible);
6907 -- In certain cases analysis may request the Extensions_Visible status
6908 -- of an expression function before the pragma has been analyzed yet.
6909 -- Inspect the declarative items after the expression function looking
6910 -- for the pragma (if any).
6912 if No (Prag) and then Is_Expression_Function (Subp) then
6913 Decl := Next (Unit_Declaration_Node (Subp));
6914 while Present (Decl) loop
6915 if Nkind (Decl) = N_Pragma
6916 and then Pragma_Name (Decl) = Name_Extensions_Visible
6917 then
6918 Prag := Decl;
6919 exit;
6921 -- A source construct ends the region where Extensions_Visible may
6922 -- appear, stop the traversal. An expanded expression function is
6923 -- no longer a source construct, but it must still be recognized.
6925 elsif Comes_From_Source (Decl)
6926 or else
6927 (Nkind_In (Decl, N_Subprogram_Body,
6928 N_Subprogram_Declaration)
6929 and then Is_Expression_Function (Defining_Entity (Decl)))
6930 then
6931 exit;
6932 end if;
6934 Next (Decl);
6935 end loop;
6936 end if;
6938 -- Extract the value from the Boolean expression (if any)
6940 if Present (Prag) then
6941 Arg := First (Pragma_Argument_Associations (Prag));
6943 if Present (Arg) then
6944 Expr := Get_Pragma_Arg (Arg);
6946 -- When the associated subprogram is an expression function, the
6947 -- argument of the pragma may not have been analyzed.
6949 if not Analyzed (Expr) then
6950 Preanalyze_And_Resolve (Expr, Standard_Boolean);
6951 end if;
6953 -- Guard against cascading errors when the argument of pragma
6954 -- Extensions_Visible is not a valid static Boolean expression.
6956 if Error_Posted (Expr) then
6957 return Extensions_Visible_None;
6959 elsif Is_True (Expr_Value (Expr)) then
6960 return Extensions_Visible_True;
6962 else
6963 return Extensions_Visible_False;
6964 end if;
6966 -- Otherwise the aspect or pragma defaults to True
6968 else
6969 return Extensions_Visible_True;
6970 end if;
6972 -- Otherwise aspect or pragma Extensions_Visible is not inherited or
6973 -- directly specified. In SPARK code, its value defaults to "False".
6975 elsif SPARK_Mode = On then
6976 return Extensions_Visible_False;
6978 -- In non-SPARK code, aspect or pragma Extensions_Visible defaults to
6979 -- "True".
6981 else
6982 return Extensions_Visible_True;
6983 end if;
6984 end Extensions_Visible_Status;
6986 -----------------
6987 -- Find_Actual --
6988 -----------------
6990 procedure Find_Actual
6991 (N : Node_Id;
6992 Formal : out Entity_Id;
6993 Call : out Node_Id)
6995 Context : constant Node_Id := Parent (N);
6996 Actual : Node_Id;
6997 Call_Nam : Node_Id;
6999 begin
7000 if Nkind_In (Context, N_Indexed_Component, N_Selected_Component)
7001 and then N = Prefix (Context)
7002 then
7003 Find_Actual (Context, Formal, Call);
7004 return;
7006 elsif Nkind (Context) = N_Parameter_Association
7007 and then N = Explicit_Actual_Parameter (Context)
7008 then
7009 Call := Parent (Context);
7011 elsif Nkind_In (Context, N_Entry_Call_Statement,
7012 N_Function_Call,
7013 N_Procedure_Call_Statement)
7014 then
7015 Call := Context;
7017 else
7018 Formal := Empty;
7019 Call := Empty;
7020 return;
7021 end if;
7023 -- If we have a call to a subprogram look for the parameter. Note that
7024 -- we exclude overloaded calls, since we don't know enough to be sure
7025 -- of giving the right answer in this case.
7027 if Nkind_In (Call, N_Entry_Call_Statement,
7028 N_Function_Call,
7029 N_Procedure_Call_Statement)
7030 then
7031 Call_Nam := Name (Call);
7033 -- A call to a protected or task entry appears as a selected
7034 -- component rather than an expanded name.
7036 if Nkind (Call_Nam) = N_Selected_Component then
7037 Call_Nam := Selector_Name (Call_Nam);
7038 end if;
7040 if Is_Entity_Name (Call_Nam)
7041 and then Present (Entity (Call_Nam))
7042 and then Is_Overloadable (Entity (Call_Nam))
7043 and then not Is_Overloaded (Call_Nam)
7044 then
7045 -- If node is name in call it is not an actual
7047 if N = Call_Nam then
7048 Formal := Empty;
7049 Call := Empty;
7050 return;
7051 end if;
7053 -- Fall here if we are definitely a parameter
7055 Actual := First_Actual (Call);
7056 Formal := First_Formal (Entity (Call_Nam));
7057 while Present (Formal) and then Present (Actual) loop
7058 if Actual = N then
7059 return;
7061 -- An actual that is the prefix in a prefixed call may have
7062 -- been rewritten in the call, after the deferred reference
7063 -- was collected. Check if sloc and kinds and names match.
7065 elsif Sloc (Actual) = Sloc (N)
7066 and then Nkind (Actual) = N_Identifier
7067 and then Nkind (Actual) = Nkind (N)
7068 and then Chars (Actual) = Chars (N)
7069 then
7070 return;
7072 else
7073 Actual := Next_Actual (Actual);
7074 Formal := Next_Formal (Formal);
7075 end if;
7076 end loop;
7077 end if;
7078 end if;
7080 -- Fall through here if we did not find matching actual
7082 Formal := Empty;
7083 Call := Empty;
7084 end Find_Actual;
7086 ---------------------------
7087 -- Find_Body_Discriminal --
7088 ---------------------------
7090 function Find_Body_Discriminal
7091 (Spec_Discriminant : Entity_Id) return Entity_Id
7093 Tsk : Entity_Id;
7094 Disc : Entity_Id;
7096 begin
7097 -- If expansion is suppressed, then the scope can be the concurrent type
7098 -- itself rather than a corresponding concurrent record type.
7100 if Is_Concurrent_Type (Scope (Spec_Discriminant)) then
7101 Tsk := Scope (Spec_Discriminant);
7103 else
7104 pragma Assert (Is_Concurrent_Record_Type (Scope (Spec_Discriminant)));
7106 Tsk := Corresponding_Concurrent_Type (Scope (Spec_Discriminant));
7107 end if;
7109 -- Find discriminant of original concurrent type, and use its current
7110 -- discriminal, which is the renaming within the task/protected body.
7112 Disc := First_Discriminant (Tsk);
7113 while Present (Disc) loop
7114 if Chars (Disc) = Chars (Spec_Discriminant) then
7115 return Discriminal (Disc);
7116 end if;
7118 Next_Discriminant (Disc);
7119 end loop;
7121 -- That loop should always succeed in finding a matching entry and
7122 -- returning. Fatal error if not.
7124 raise Program_Error;
7125 end Find_Body_Discriminal;
7127 -------------------------------------
7128 -- Find_Corresponding_Discriminant --
7129 -------------------------------------
7131 function Find_Corresponding_Discriminant
7132 (Id : Node_Id;
7133 Typ : Entity_Id) return Entity_Id
7135 Par_Disc : Entity_Id;
7136 Old_Disc : Entity_Id;
7137 New_Disc : Entity_Id;
7139 begin
7140 Par_Disc := Original_Record_Component (Original_Discriminant (Id));
7142 -- The original type may currently be private, and the discriminant
7143 -- only appear on its full view.
7145 if Is_Private_Type (Scope (Par_Disc))
7146 and then not Has_Discriminants (Scope (Par_Disc))
7147 and then Present (Full_View (Scope (Par_Disc)))
7148 then
7149 Old_Disc := First_Discriminant (Full_View (Scope (Par_Disc)));
7150 else
7151 Old_Disc := First_Discriminant (Scope (Par_Disc));
7152 end if;
7154 if Is_Class_Wide_Type (Typ) then
7155 New_Disc := First_Discriminant (Root_Type (Typ));
7156 else
7157 New_Disc := First_Discriminant (Typ);
7158 end if;
7160 while Present (Old_Disc) and then Present (New_Disc) loop
7161 if Old_Disc = Par_Disc then
7162 return New_Disc;
7163 end if;
7165 Next_Discriminant (Old_Disc);
7166 Next_Discriminant (New_Disc);
7167 end loop;
7169 -- Should always find it
7171 raise Program_Error;
7172 end Find_Corresponding_Discriminant;
7174 ----------------------------------
7175 -- Find_Enclosing_Iterator_Loop --
7176 ----------------------------------
7178 function Find_Enclosing_Iterator_Loop (Id : Entity_Id) return Entity_Id is
7179 Constr : Node_Id;
7180 S : Entity_Id;
7182 begin
7183 -- Traverse the scope chain looking for an iterator loop. Such loops are
7184 -- usually transformed into blocks, hence the use of Original_Node.
7186 S := Id;
7187 while Present (S) and then S /= Standard_Standard loop
7188 if Ekind (S) = E_Loop
7189 and then Nkind (Parent (S)) = N_Implicit_Label_Declaration
7190 then
7191 Constr := Original_Node (Label_Construct (Parent (S)));
7193 if Nkind (Constr) = N_Loop_Statement
7194 and then Present (Iteration_Scheme (Constr))
7195 and then Nkind (Iterator_Specification
7196 (Iteration_Scheme (Constr))) =
7197 N_Iterator_Specification
7198 then
7199 return S;
7200 end if;
7201 end if;
7203 S := Scope (S);
7204 end loop;
7206 return Empty;
7207 end Find_Enclosing_Iterator_Loop;
7209 ------------------------------------
7210 -- Find_Loop_In_Conditional_Block --
7211 ------------------------------------
7213 function Find_Loop_In_Conditional_Block (N : Node_Id) return Node_Id is
7214 Stmt : Node_Id;
7216 begin
7217 Stmt := N;
7219 if Nkind (Stmt) = N_If_Statement then
7220 Stmt := First (Then_Statements (Stmt));
7221 end if;
7223 pragma Assert (Nkind (Stmt) = N_Block_Statement);
7225 -- Inspect the statements of the conditional block. In general the loop
7226 -- should be the first statement in the statement sequence of the block,
7227 -- but the finalization machinery may have introduced extra object
7228 -- declarations.
7230 Stmt := First (Statements (Handled_Statement_Sequence (Stmt)));
7231 while Present (Stmt) loop
7232 if Nkind (Stmt) = N_Loop_Statement then
7233 return Stmt;
7234 end if;
7236 Next (Stmt);
7237 end loop;
7239 -- The expansion of attribute 'Loop_Entry produced a malformed block
7241 raise Program_Error;
7242 end Find_Loop_In_Conditional_Block;
7244 --------------------------
7245 -- Find_Overlaid_Entity --
7246 --------------------------
7248 procedure Find_Overlaid_Entity
7249 (N : Node_Id;
7250 Ent : out Entity_Id;
7251 Off : out Boolean)
7253 Expr : Node_Id;
7255 begin
7256 -- We are looking for one of the two following forms:
7258 -- for X'Address use Y'Address
7260 -- or
7262 -- Const : constant Address := expr;
7263 -- ...
7264 -- for X'Address use Const;
7266 -- In the second case, the expr is either Y'Address, or recursively a
7267 -- constant that eventually references Y'Address.
7269 Ent := Empty;
7270 Off := False;
7272 if Nkind (N) = N_Attribute_Definition_Clause
7273 and then Chars (N) = Name_Address
7274 then
7275 Expr := Expression (N);
7277 -- This loop checks the form of the expression for Y'Address,
7278 -- using recursion to deal with intermediate constants.
7280 loop
7281 -- Check for Y'Address
7283 if Nkind (Expr) = N_Attribute_Reference
7284 and then Attribute_Name (Expr) = Name_Address
7285 then
7286 Expr := Prefix (Expr);
7287 exit;
7289 -- Check for Const where Const is a constant entity
7291 elsif Is_Entity_Name (Expr)
7292 and then Ekind (Entity (Expr)) = E_Constant
7293 then
7294 Expr := Constant_Value (Entity (Expr));
7296 -- Anything else does not need checking
7298 else
7299 return;
7300 end if;
7301 end loop;
7303 -- This loop checks the form of the prefix for an entity, using
7304 -- recursion to deal with intermediate components.
7306 loop
7307 -- Check for Y where Y is an entity
7309 if Is_Entity_Name (Expr) then
7310 Ent := Entity (Expr);
7311 return;
7313 -- Check for components
7315 elsif
7316 Nkind_In (Expr, N_Selected_Component, N_Indexed_Component)
7317 then
7318 Expr := Prefix (Expr);
7319 Off := True;
7321 -- Anything else does not need checking
7323 else
7324 return;
7325 end if;
7326 end loop;
7327 end if;
7328 end Find_Overlaid_Entity;
7330 -------------------------
7331 -- Find_Parameter_Type --
7332 -------------------------
7334 function Find_Parameter_Type (Param : Node_Id) return Entity_Id is
7335 begin
7336 if Nkind (Param) /= N_Parameter_Specification then
7337 return Empty;
7339 -- For an access parameter, obtain the type from the formal entity
7340 -- itself, because access to subprogram nodes do not carry a type.
7341 -- Shouldn't we always use the formal entity ???
7343 elsif Nkind (Parameter_Type (Param)) = N_Access_Definition then
7344 return Etype (Defining_Identifier (Param));
7346 else
7347 return Etype (Parameter_Type (Param));
7348 end if;
7349 end Find_Parameter_Type;
7351 -----------------------------------
7352 -- Find_Placement_In_State_Space --
7353 -----------------------------------
7355 procedure Find_Placement_In_State_Space
7356 (Item_Id : Entity_Id;
7357 Placement : out State_Space_Kind;
7358 Pack_Id : out Entity_Id)
7360 Context : Entity_Id;
7362 begin
7363 -- Assume that the item does not appear in the state space of a package
7365 Placement := Not_In_Package;
7366 Pack_Id := Empty;
7368 -- Climb the scope stack and examine the enclosing context
7370 Context := Scope (Item_Id);
7371 while Present (Context) and then Context /= Standard_Standard loop
7372 if Ekind (Context) = E_Package then
7373 Pack_Id := Context;
7375 -- A package body is a cut off point for the traversal as the item
7376 -- cannot be visible to the outside from this point on. Note that
7377 -- this test must be done first as a body is also classified as a
7378 -- private part.
7380 if In_Package_Body (Context) then
7381 Placement := Body_State_Space;
7382 return;
7384 -- The private part of a package is a cut off point for the
7385 -- traversal as the item cannot be visible to the outside from
7386 -- this point on.
7388 elsif In_Private_Part (Context) then
7389 Placement := Private_State_Space;
7390 return;
7392 -- When the item appears in the visible state space of a package,
7393 -- continue to climb the scope stack as this may not be the final
7394 -- state space.
7396 else
7397 Placement := Visible_State_Space;
7399 -- The visible state space of a child unit acts as the proper
7400 -- placement of an item.
7402 if Is_Child_Unit (Context) then
7403 return;
7404 end if;
7405 end if;
7407 -- The item or its enclosing package appear in a construct that has
7408 -- no state space.
7410 else
7411 Placement := Not_In_Package;
7412 return;
7413 end if;
7415 Context := Scope (Context);
7416 end loop;
7417 end Find_Placement_In_State_Space;
7419 ------------------------
7420 -- Find_Specific_Type --
7421 ------------------------
7423 function Find_Specific_Type (CW : Entity_Id) return Entity_Id is
7424 Typ : Entity_Id := Root_Type (CW);
7426 begin
7427 if Ekind (Typ) = E_Incomplete_Type then
7428 if From_Limited_With (Typ) then
7429 Typ := Non_Limited_View (Typ);
7430 else
7431 Typ := Full_View (Typ);
7432 end if;
7433 end if;
7435 if Is_Private_Type (Typ)
7436 and then not Is_Tagged_Type (Typ)
7437 and then Present (Full_View (Typ))
7438 then
7439 return Full_View (Typ);
7440 else
7441 return Typ;
7442 end if;
7443 end Find_Specific_Type;
7445 -----------------------------
7446 -- Find_Static_Alternative --
7447 -----------------------------
7449 function Find_Static_Alternative (N : Node_Id) return Node_Id is
7450 Expr : constant Node_Id := Expression (N);
7451 Val : constant Uint := Expr_Value (Expr);
7452 Alt : Node_Id;
7453 Choice : Node_Id;
7455 begin
7456 Alt := First (Alternatives (N));
7458 Search : loop
7459 if Nkind (Alt) /= N_Pragma then
7460 Choice := First (Discrete_Choices (Alt));
7461 while Present (Choice) loop
7463 -- Others choice, always matches
7465 if Nkind (Choice) = N_Others_Choice then
7466 exit Search;
7468 -- Range, check if value is in the range
7470 elsif Nkind (Choice) = N_Range then
7471 exit Search when
7472 Val >= Expr_Value (Low_Bound (Choice))
7473 and then
7474 Val <= Expr_Value (High_Bound (Choice));
7476 -- Choice is a subtype name. Note that we know it must
7477 -- be a static subtype, since otherwise it would have
7478 -- been diagnosed as illegal.
7480 elsif Is_Entity_Name (Choice)
7481 and then Is_Type (Entity (Choice))
7482 then
7483 exit Search when Is_In_Range (Expr, Etype (Choice),
7484 Assume_Valid => False);
7486 -- Choice is a subtype indication
7488 elsif Nkind (Choice) = N_Subtype_Indication then
7489 declare
7490 C : constant Node_Id := Constraint (Choice);
7491 R : constant Node_Id := Range_Expression (C);
7493 begin
7494 exit Search when
7495 Val >= Expr_Value (Low_Bound (R))
7496 and then
7497 Val <= Expr_Value (High_Bound (R));
7498 end;
7500 -- Choice is a simple expression
7502 else
7503 exit Search when Val = Expr_Value (Choice);
7504 end if;
7506 Next (Choice);
7507 end loop;
7508 end if;
7510 Next (Alt);
7511 pragma Assert (Present (Alt));
7512 end loop Search;
7514 -- The above loop *must* terminate by finding a match, since
7515 -- we know the case statement is valid, and the value of the
7516 -- expression is known at compile time. When we fall out of
7517 -- the loop, Alt points to the alternative that we know will
7518 -- be selected at run time.
7520 return Alt;
7521 end Find_Static_Alternative;
7523 ------------------
7524 -- First_Actual --
7525 ------------------
7527 function First_Actual (Node : Node_Id) return Node_Id is
7528 N : Node_Id;
7530 begin
7531 if No (Parameter_Associations (Node)) then
7532 return Empty;
7533 end if;
7535 N := First (Parameter_Associations (Node));
7537 if Nkind (N) = N_Parameter_Association then
7538 return First_Named_Actual (Node);
7539 else
7540 return N;
7541 end if;
7542 end First_Actual;
7544 -------------
7545 -- Fix_Msg --
7546 -------------
7548 function Fix_Msg (Id : Entity_Id; Msg : String) return String is
7549 Is_Task : constant Boolean :=
7550 Ekind_In (Id, E_Task_Body, E_Task_Type)
7551 or else Is_Single_Task_Object (Id);
7552 Msg_Last : constant Natural := Msg'Last;
7553 Msg_Index : Natural;
7554 Res : String (Msg'Range) := (others => ' ');
7555 Res_Index : Natural;
7557 begin
7558 -- Copy all characters from the input message Msg to result Res with
7559 -- suitable replacements.
7561 Msg_Index := Msg'First;
7562 Res_Index := Res'First;
7563 while Msg_Index <= Msg_Last loop
7565 -- Replace "subprogram" with a different word
7567 if Msg_Index <= Msg_Last - 10
7568 and then Msg (Msg_Index .. Msg_Index + 9) = "subprogram"
7569 then
7570 if Ekind_In (Id, E_Entry, E_Entry_Family) then
7571 Res (Res_Index .. Res_Index + 4) := "entry";
7572 Res_Index := Res_Index + 5;
7574 elsif Is_Task then
7575 Res (Res_Index .. Res_Index + 8) := "task type";
7576 Res_Index := Res_Index + 9;
7578 else
7579 Res (Res_Index .. Res_Index + 9) := "subprogram";
7580 Res_Index := Res_Index + 10;
7581 end if;
7583 Msg_Index := Msg_Index + 10;
7585 -- Replace "protected" with a different word
7587 elsif Msg_Index <= Msg_Last - 9
7588 and then Msg (Msg_Index .. Msg_Index + 8) = "protected"
7589 and then Is_Task
7590 then
7591 Res (Res_Index .. Res_Index + 3) := "task";
7592 Res_Index := Res_Index + 4;
7593 Msg_Index := Msg_Index + 9;
7595 -- Otherwise copy the character
7597 else
7598 Res (Res_Index) := Msg (Msg_Index);
7599 Msg_Index := Msg_Index + 1;
7600 Res_Index := Res_Index + 1;
7601 end if;
7602 end loop;
7604 return Res (Res'First .. Res_Index - 1);
7605 end Fix_Msg;
7607 -----------------------
7608 -- Gather_Components --
7609 -----------------------
7611 procedure Gather_Components
7612 (Typ : Entity_Id;
7613 Comp_List : Node_Id;
7614 Governed_By : List_Id;
7615 Into : Elist_Id;
7616 Report_Errors : out Boolean)
7618 Assoc : Node_Id;
7619 Variant : Node_Id;
7620 Discrete_Choice : Node_Id;
7621 Comp_Item : Node_Id;
7623 Discrim : Entity_Id;
7624 Discrim_Name : Node_Id;
7625 Discrim_Value : Node_Id;
7627 begin
7628 Report_Errors := False;
7630 if No (Comp_List) or else Null_Present (Comp_List) then
7631 return;
7633 elsif Present (Component_Items (Comp_List)) then
7634 Comp_Item := First (Component_Items (Comp_List));
7636 else
7637 Comp_Item := Empty;
7638 end if;
7640 while Present (Comp_Item) loop
7642 -- Skip the tag of a tagged record, the interface tags, as well
7643 -- as all items that are not user components (anonymous types,
7644 -- rep clauses, Parent field, controller field).
7646 if Nkind (Comp_Item) = N_Component_Declaration then
7647 declare
7648 Comp : constant Entity_Id := Defining_Identifier (Comp_Item);
7649 begin
7650 if not Is_Tag (Comp) and then Chars (Comp) /= Name_uParent then
7651 Append_Elmt (Comp, Into);
7652 end if;
7653 end;
7654 end if;
7656 Next (Comp_Item);
7657 end loop;
7659 if No (Variant_Part (Comp_List)) then
7660 return;
7661 else
7662 Discrim_Name := Name (Variant_Part (Comp_List));
7663 Variant := First_Non_Pragma (Variants (Variant_Part (Comp_List)));
7664 end if;
7666 -- Look for the discriminant that governs this variant part.
7667 -- The discriminant *must* be in the Governed_By List
7669 Assoc := First (Governed_By);
7670 Find_Constraint : loop
7671 Discrim := First (Choices (Assoc));
7672 exit Find_Constraint when Chars (Discrim_Name) = Chars (Discrim)
7673 or else (Present (Corresponding_Discriminant (Entity (Discrim)))
7674 and then
7675 Chars (Corresponding_Discriminant (Entity (Discrim))) =
7676 Chars (Discrim_Name))
7677 or else Chars (Original_Record_Component (Entity (Discrim)))
7678 = Chars (Discrim_Name);
7680 if No (Next (Assoc)) then
7681 if not Is_Constrained (Typ)
7682 and then Is_Derived_Type (Typ)
7683 and then Present (Stored_Constraint (Typ))
7684 then
7685 -- If the type is a tagged type with inherited discriminants,
7686 -- use the stored constraint on the parent in order to find
7687 -- the values of discriminants that are otherwise hidden by an
7688 -- explicit constraint. Renamed discriminants are handled in
7689 -- the code above.
7691 -- If several parent discriminants are renamed by a single
7692 -- discriminant of the derived type, the call to obtain the
7693 -- Corresponding_Discriminant field only retrieves the last
7694 -- of them. We recover the constraint on the others from the
7695 -- Stored_Constraint as well.
7697 declare
7698 D : Entity_Id;
7699 C : Elmt_Id;
7701 begin
7702 D := First_Discriminant (Etype (Typ));
7703 C := First_Elmt (Stored_Constraint (Typ));
7704 while Present (D) and then Present (C) loop
7705 if Chars (Discrim_Name) = Chars (D) then
7706 if Is_Entity_Name (Node (C))
7707 and then Entity (Node (C)) = Entity (Discrim)
7708 then
7709 -- D is renamed by Discrim, whose value is given in
7710 -- Assoc.
7712 null;
7714 else
7715 Assoc :=
7716 Make_Component_Association (Sloc (Typ),
7717 New_List
7718 (New_Occurrence_Of (D, Sloc (Typ))),
7719 Duplicate_Subexpr_No_Checks (Node (C)));
7720 end if;
7721 exit Find_Constraint;
7722 end if;
7724 Next_Discriminant (D);
7725 Next_Elmt (C);
7726 end loop;
7727 end;
7728 end if;
7729 end if;
7731 if No (Next (Assoc)) then
7732 Error_Msg_NE (" missing value for discriminant&",
7733 First (Governed_By), Discrim_Name);
7734 Report_Errors := True;
7735 return;
7736 end if;
7738 Next (Assoc);
7739 end loop Find_Constraint;
7741 Discrim_Value := Expression (Assoc);
7743 if not Is_OK_Static_Expression (Discrim_Value) then
7745 -- If the variant part is governed by a discriminant of the type
7746 -- this is an error. If the variant part and the discriminant are
7747 -- inherited from an ancestor this is legal (AI05-120) unless the
7748 -- components are being gathered for an aggregate, in which case
7749 -- the caller must check Report_Errors.
7751 if Scope (Original_Record_Component
7752 ((Entity (First (Choices (Assoc)))))) = Typ
7753 then
7754 Error_Msg_FE
7755 ("value for discriminant & must be static!",
7756 Discrim_Value, Discrim);
7757 Why_Not_Static (Discrim_Value);
7758 end if;
7760 Report_Errors := True;
7761 return;
7762 end if;
7764 Search_For_Discriminant_Value : declare
7765 Low : Node_Id;
7766 High : Node_Id;
7768 UI_High : Uint;
7769 UI_Low : Uint;
7770 UI_Discrim_Value : constant Uint := Expr_Value (Discrim_Value);
7772 begin
7773 Find_Discrete_Value : while Present (Variant) loop
7774 Discrete_Choice := First (Discrete_Choices (Variant));
7775 while Present (Discrete_Choice) loop
7776 exit Find_Discrete_Value when
7777 Nkind (Discrete_Choice) = N_Others_Choice;
7779 Get_Index_Bounds (Discrete_Choice, Low, High);
7781 UI_Low := Expr_Value (Low);
7782 UI_High := Expr_Value (High);
7784 exit Find_Discrete_Value when
7785 UI_Low <= UI_Discrim_Value
7786 and then
7787 UI_High >= UI_Discrim_Value;
7789 Next (Discrete_Choice);
7790 end loop;
7792 Next_Non_Pragma (Variant);
7793 end loop Find_Discrete_Value;
7794 end Search_For_Discriminant_Value;
7796 if No (Variant) then
7797 Error_Msg_NE
7798 ("value of discriminant & is out of range", Discrim_Value, Discrim);
7799 Report_Errors := True;
7800 return;
7801 end if;
7803 -- If we have found the corresponding choice, recursively add its
7804 -- components to the Into list. The nested components are part of
7805 -- the same record type.
7807 Gather_Components
7808 (Typ, Component_List (Variant), Governed_By, Into, Report_Errors);
7809 end Gather_Components;
7811 ------------------------
7812 -- Get_Actual_Subtype --
7813 ------------------------
7815 function Get_Actual_Subtype (N : Node_Id) return Entity_Id is
7816 Typ : constant Entity_Id := Etype (N);
7817 Utyp : Entity_Id := Underlying_Type (Typ);
7818 Decl : Node_Id;
7819 Atyp : Entity_Id;
7821 begin
7822 if No (Utyp) then
7823 Utyp := Typ;
7824 end if;
7826 -- If what we have is an identifier that references a subprogram
7827 -- formal, or a variable or constant object, then we get the actual
7828 -- subtype from the referenced entity if one has been built.
7830 if Nkind (N) = N_Identifier
7831 and then
7832 (Is_Formal (Entity (N))
7833 or else Ekind (Entity (N)) = E_Constant
7834 or else Ekind (Entity (N)) = E_Variable)
7835 and then Present (Actual_Subtype (Entity (N)))
7836 then
7837 return Actual_Subtype (Entity (N));
7839 -- Actual subtype of unchecked union is always itself. We never need
7840 -- the "real" actual subtype. If we did, we couldn't get it anyway
7841 -- because the discriminant is not available. The restrictions on
7842 -- Unchecked_Union are designed to make sure that this is OK.
7844 elsif Is_Unchecked_Union (Base_Type (Utyp)) then
7845 return Typ;
7847 -- Here for the unconstrained case, we must find actual subtype
7848 -- No actual subtype is available, so we must build it on the fly.
7850 -- Checking the type, not the underlying type, for constrainedness
7851 -- seems to be necessary. Maybe all the tests should be on the type???
7853 elsif (not Is_Constrained (Typ))
7854 and then (Is_Array_Type (Utyp)
7855 or else (Is_Record_Type (Utyp)
7856 and then Has_Discriminants (Utyp)))
7857 and then not Has_Unknown_Discriminants (Utyp)
7858 and then not (Ekind (Utyp) = E_String_Literal_Subtype)
7859 then
7860 -- Nothing to do if in spec expression (why not???)
7862 if In_Spec_Expression then
7863 return Typ;
7865 elsif Is_Private_Type (Typ) and then not Has_Discriminants (Typ) then
7867 -- If the type has no discriminants, there is no subtype to
7868 -- build, even if the underlying type is discriminated.
7870 return Typ;
7872 -- Else build the actual subtype
7874 else
7875 Decl := Build_Actual_Subtype (Typ, N);
7876 Atyp := Defining_Identifier (Decl);
7878 -- If Build_Actual_Subtype generated a new declaration then use it
7880 if Atyp /= Typ then
7882 -- The actual subtype is an Itype, so analyze the declaration,
7883 -- but do not attach it to the tree, to get the type defined.
7885 Set_Parent (Decl, N);
7886 Set_Is_Itype (Atyp);
7887 Analyze (Decl, Suppress => All_Checks);
7888 Set_Associated_Node_For_Itype (Atyp, N);
7889 Set_Has_Delayed_Freeze (Atyp, False);
7891 -- We need to freeze the actual subtype immediately. This is
7892 -- needed, because otherwise this Itype will not get frozen
7893 -- at all, and it is always safe to freeze on creation because
7894 -- any associated types must be frozen at this point.
7896 Freeze_Itype (Atyp, N);
7897 return Atyp;
7899 -- Otherwise we did not build a declaration, so return original
7901 else
7902 return Typ;
7903 end if;
7904 end if;
7906 -- For all remaining cases, the actual subtype is the same as
7907 -- the nominal type.
7909 else
7910 return Typ;
7911 end if;
7912 end Get_Actual_Subtype;
7914 -------------------------------------
7915 -- Get_Actual_Subtype_If_Available --
7916 -------------------------------------
7918 function Get_Actual_Subtype_If_Available (N : Node_Id) return Entity_Id is
7919 Typ : constant Entity_Id := Etype (N);
7921 begin
7922 -- If what we have is an identifier that references a subprogram
7923 -- formal, or a variable or constant object, then we get the actual
7924 -- subtype from the referenced entity if one has been built.
7926 if Nkind (N) = N_Identifier
7927 and then
7928 (Is_Formal (Entity (N))
7929 or else Ekind (Entity (N)) = E_Constant
7930 or else Ekind (Entity (N)) = E_Variable)
7931 and then Present (Actual_Subtype (Entity (N)))
7932 then
7933 return Actual_Subtype (Entity (N));
7935 -- Otherwise the Etype of N is returned unchanged
7937 else
7938 return Typ;
7939 end if;
7940 end Get_Actual_Subtype_If_Available;
7942 ------------------------
7943 -- Get_Body_From_Stub --
7944 ------------------------
7946 function Get_Body_From_Stub (N : Node_Id) return Node_Id is
7947 begin
7948 return Proper_Body (Unit (Library_Unit (N)));
7949 end Get_Body_From_Stub;
7951 ---------------------
7952 -- Get_Cursor_Type --
7953 ---------------------
7955 function Get_Cursor_Type
7956 (Aspect : Node_Id;
7957 Typ : Entity_Id) return Entity_Id
7959 Assoc : Node_Id;
7960 Func : Entity_Id;
7961 First_Op : Entity_Id;
7962 Cursor : Entity_Id;
7964 begin
7965 -- If error already detected, return
7967 if Error_Posted (Aspect) then
7968 return Any_Type;
7969 end if;
7971 -- The cursor type for an Iterable aspect is the return type of a
7972 -- non-overloaded First primitive operation. Locate association for
7973 -- First.
7975 Assoc := First (Component_Associations (Expression (Aspect)));
7976 First_Op := Any_Id;
7977 while Present (Assoc) loop
7978 if Chars (First (Choices (Assoc))) = Name_First then
7979 First_Op := Expression (Assoc);
7980 exit;
7981 end if;
7983 Next (Assoc);
7984 end loop;
7986 if First_Op = Any_Id then
7987 Error_Msg_N ("aspect Iterable must specify First operation", Aspect);
7988 return Any_Type;
7989 end if;
7991 Cursor := Any_Type;
7993 -- Locate function with desired name and profile in scope of type
7994 -- In the rare case where the type is an integer type, a base type
7995 -- is created for it, check that the base type of the first formal
7996 -- of First matches the base type of the domain.
7998 Func := First_Entity (Scope (Typ));
7999 while Present (Func) loop
8000 if Chars (Func) = Chars (First_Op)
8001 and then Ekind (Func) = E_Function
8002 and then Present (First_Formal (Func))
8003 and then Base_Type (Etype (First_Formal (Func))) = Base_Type (Typ)
8004 and then No (Next_Formal (First_Formal (Func)))
8005 then
8006 if Cursor /= Any_Type then
8007 Error_Msg_N
8008 ("Operation First for iterable type must be unique", Aspect);
8009 return Any_Type;
8010 else
8011 Cursor := Etype (Func);
8012 end if;
8013 end if;
8015 Next_Entity (Func);
8016 end loop;
8018 -- If not found, no way to resolve remaining primitives.
8020 if Cursor = Any_Type then
8021 Error_Msg_N
8022 ("No legal primitive operation First for Iterable type", Aspect);
8023 end if;
8025 return Cursor;
8026 end Get_Cursor_Type;
8028 function Get_Cursor_Type (Typ : Entity_Id) return Entity_Id is
8029 begin
8030 return Etype (Get_Iterable_Type_Primitive (Typ, Name_First));
8031 end Get_Cursor_Type;
8033 -------------------------------
8034 -- Get_Default_External_Name --
8035 -------------------------------
8037 function Get_Default_External_Name (E : Node_Or_Entity_Id) return Node_Id is
8038 begin
8039 Get_Decoded_Name_String (Chars (E));
8041 if Opt.External_Name_Imp_Casing = Uppercase then
8042 Set_Casing (All_Upper_Case);
8043 else
8044 Set_Casing (All_Lower_Case);
8045 end if;
8047 return
8048 Make_String_Literal (Sloc (E),
8049 Strval => String_From_Name_Buffer);
8050 end Get_Default_External_Name;
8052 --------------------------
8053 -- Get_Enclosing_Object --
8054 --------------------------
8056 function Get_Enclosing_Object (N : Node_Id) return Entity_Id is
8057 begin
8058 if Is_Entity_Name (N) then
8059 return Entity (N);
8060 else
8061 case Nkind (N) is
8062 when N_Indexed_Component |
8063 N_Slice |
8064 N_Selected_Component =>
8066 -- If not generating code, a dereference may be left implicit.
8067 -- In thoses cases, return Empty.
8069 if Is_Access_Type (Etype (Prefix (N))) then
8070 return Empty;
8071 else
8072 return Get_Enclosing_Object (Prefix (N));
8073 end if;
8075 when N_Type_Conversion =>
8076 return Get_Enclosing_Object (Expression (N));
8078 when others =>
8079 return Empty;
8080 end case;
8081 end if;
8082 end Get_Enclosing_Object;
8084 ---------------------------
8085 -- Get_Enum_Lit_From_Pos --
8086 ---------------------------
8088 function Get_Enum_Lit_From_Pos
8089 (T : Entity_Id;
8090 Pos : Uint;
8091 Loc : Source_Ptr) return Node_Id
8093 Btyp : Entity_Id := Base_Type (T);
8094 Lit : Node_Id;
8096 begin
8097 -- In the case where the literal is of type Character, Wide_Character
8098 -- or Wide_Wide_Character or of a type derived from them, there needs
8099 -- to be some special handling since there is no explicit chain of
8100 -- literals to search. Instead, an N_Character_Literal node is created
8101 -- with the appropriate Char_Code and Chars fields.
8103 if Is_Standard_Character_Type (T) then
8104 Set_Character_Literal_Name (UI_To_CC (Pos));
8105 return
8106 Make_Character_Literal (Loc,
8107 Chars => Name_Find,
8108 Char_Literal_Value => Pos);
8110 -- For all other cases, we have a complete table of literals, and
8111 -- we simply iterate through the chain of literal until the one
8112 -- with the desired position value is found.
8114 else
8115 if Is_Private_Type (Btyp) and then Present (Full_View (Btyp)) then
8116 Btyp := Full_View (Btyp);
8117 end if;
8119 Lit := First_Literal (Btyp);
8120 for J in 1 .. UI_To_Int (Pos) loop
8121 Next_Literal (Lit);
8122 end loop;
8124 return New_Occurrence_Of (Lit, Loc);
8125 end if;
8126 end Get_Enum_Lit_From_Pos;
8128 ------------------------
8129 -- Get_Generic_Entity --
8130 ------------------------
8132 function Get_Generic_Entity (N : Node_Id) return Entity_Id is
8133 Ent : constant Entity_Id := Entity (Name (N));
8134 begin
8135 if Present (Renamed_Object (Ent)) then
8136 return Renamed_Object (Ent);
8137 else
8138 return Ent;
8139 end if;
8140 end Get_Generic_Entity;
8142 -------------------------------------
8143 -- Get_Incomplete_View_Of_Ancestor --
8144 -------------------------------------
8146 function Get_Incomplete_View_Of_Ancestor (E : Entity_Id) return Entity_Id is
8147 Cur_Unit : constant Entity_Id := Cunit_Entity (Current_Sem_Unit);
8148 Par_Scope : Entity_Id;
8149 Par_Type : Entity_Id;
8151 begin
8152 -- The incomplete view of an ancestor is only relevant for private
8153 -- derived types in child units.
8155 if not Is_Derived_Type (E)
8156 or else not Is_Child_Unit (Cur_Unit)
8157 then
8158 return Empty;
8160 else
8161 Par_Scope := Scope (Cur_Unit);
8162 if No (Par_Scope) then
8163 return Empty;
8164 end if;
8166 Par_Type := Etype (Base_Type (E));
8168 -- Traverse list of ancestor types until we find one declared in
8169 -- a parent or grandparent unit (two levels seem sufficient).
8171 while Present (Par_Type) loop
8172 if Scope (Par_Type) = Par_Scope
8173 or else Scope (Par_Type) = Scope (Par_Scope)
8174 then
8175 return Par_Type;
8177 elsif not Is_Derived_Type (Par_Type) then
8178 return Empty;
8180 else
8181 Par_Type := Etype (Base_Type (Par_Type));
8182 end if;
8183 end loop;
8185 -- If none found, there is no relevant ancestor type.
8187 return Empty;
8188 end if;
8189 end Get_Incomplete_View_Of_Ancestor;
8191 ----------------------
8192 -- Get_Index_Bounds --
8193 ----------------------
8195 procedure Get_Index_Bounds (N : Node_Id; L, H : out Node_Id) is
8196 Kind : constant Node_Kind := Nkind (N);
8197 R : Node_Id;
8199 begin
8200 if Kind = N_Range then
8201 L := Low_Bound (N);
8202 H := High_Bound (N);
8204 elsif Kind = N_Subtype_Indication then
8205 R := Range_Expression (Constraint (N));
8207 if R = Error then
8208 L := Error;
8209 H := Error;
8210 return;
8212 else
8213 L := Low_Bound (Range_Expression (Constraint (N)));
8214 H := High_Bound (Range_Expression (Constraint (N)));
8215 end if;
8217 elsif Is_Entity_Name (N) and then Is_Type (Entity (N)) then
8218 if Error_Posted (Scalar_Range (Entity (N))) then
8219 L := Error;
8220 H := Error;
8222 elsif Nkind (Scalar_Range (Entity (N))) = N_Subtype_Indication then
8223 Get_Index_Bounds (Scalar_Range (Entity (N)), L, H);
8225 else
8226 L := Low_Bound (Scalar_Range (Entity (N)));
8227 H := High_Bound (Scalar_Range (Entity (N)));
8228 end if;
8230 else
8231 -- N is an expression, indicating a range with one value
8233 L := N;
8234 H := N;
8235 end if;
8236 end Get_Index_Bounds;
8238 ---------------------------------
8239 -- Get_Iterable_Type_Primitive --
8240 ---------------------------------
8242 function Get_Iterable_Type_Primitive
8243 (Typ : Entity_Id;
8244 Nam : Name_Id) return Entity_Id
8246 Funcs : constant Node_Id := Find_Value_Of_Aspect (Typ, Aspect_Iterable);
8247 Assoc : Node_Id;
8249 begin
8250 if No (Funcs) then
8251 return Empty;
8253 else
8254 Assoc := First (Component_Associations (Funcs));
8255 while Present (Assoc) loop
8256 if Chars (First (Choices (Assoc))) = Nam then
8257 return Entity (Expression (Assoc));
8258 end if;
8260 Assoc := Next (Assoc);
8261 end loop;
8263 return Empty;
8264 end if;
8265 end Get_Iterable_Type_Primitive;
8267 ----------------------------------
8268 -- Get_Library_Unit_Name_string --
8269 ----------------------------------
8271 procedure Get_Library_Unit_Name_String (Decl_Node : Node_Id) is
8272 Unit_Name_Id : constant Unit_Name_Type := Get_Unit_Name (Decl_Node);
8274 begin
8275 Get_Unit_Name_String (Unit_Name_Id);
8277 -- Remove seven last character (" (spec)" or " (body)")
8279 Name_Len := Name_Len - 7;
8280 pragma Assert (Name_Buffer (Name_Len + 1) = ' ');
8281 end Get_Library_Unit_Name_String;
8283 ------------------------
8284 -- Get_Name_Entity_Id --
8285 ------------------------
8287 function Get_Name_Entity_Id (Id : Name_Id) return Entity_Id is
8288 begin
8289 return Entity_Id (Get_Name_Table_Int (Id));
8290 end Get_Name_Entity_Id;
8292 ------------------------------
8293 -- Get_Name_From_CTC_Pragma --
8294 ------------------------------
8296 function Get_Name_From_CTC_Pragma (N : Node_Id) return String_Id is
8297 Arg : constant Node_Id :=
8298 Get_Pragma_Arg (First (Pragma_Argument_Associations (N)));
8299 begin
8300 return Strval (Expr_Value_S (Arg));
8301 end Get_Name_From_CTC_Pragma;
8303 -----------------------
8304 -- Get_Parent_Entity --
8305 -----------------------
8307 function Get_Parent_Entity (Unit : Node_Id) return Entity_Id is
8308 begin
8309 if Nkind (Unit) = N_Package_Body
8310 and then Nkind (Original_Node (Unit)) = N_Package_Instantiation
8311 then
8312 return Defining_Entity
8313 (Specification (Instance_Spec (Original_Node (Unit))));
8314 elsif Nkind (Unit) = N_Package_Instantiation then
8315 return Defining_Entity (Specification (Instance_Spec (Unit)));
8316 else
8317 return Defining_Entity (Unit);
8318 end if;
8319 end Get_Parent_Entity;
8321 -------------------
8322 -- Get_Pragma_Id --
8323 -------------------
8325 function Get_Pragma_Id (N : Node_Id) return Pragma_Id is
8326 begin
8327 return Get_Pragma_Id (Pragma_Name (N));
8328 end Get_Pragma_Id;
8330 ------------------------
8331 -- Get_Qualified_Name --
8332 ------------------------
8334 function Get_Qualified_Name
8335 (Id : Entity_Id;
8336 Suffix : Entity_Id := Empty) return Name_Id
8338 Suffix_Nam : Name_Id := No_Name;
8340 begin
8341 if Present (Suffix) then
8342 Suffix_Nam := Chars (Suffix);
8343 end if;
8345 return Get_Qualified_Name (Chars (Id), Suffix_Nam, Scope (Id));
8346 end Get_Qualified_Name;
8348 function Get_Qualified_Name
8349 (Nam : Name_Id;
8350 Suffix : Name_Id := No_Name;
8351 Scop : Entity_Id := Current_Scope) return Name_Id
8353 procedure Add_Scope (S : Entity_Id);
8354 -- Add the fully qualified form of scope S to the name buffer. The
8355 -- format is:
8356 -- s-1__s__
8358 ---------------
8359 -- Add_Scope --
8360 ---------------
8362 procedure Add_Scope (S : Entity_Id) is
8363 begin
8364 if S = Empty then
8365 null;
8367 elsif S = Standard_Standard then
8368 null;
8370 else
8371 Add_Scope (Scope (S));
8372 Get_Name_String_And_Append (Chars (S));
8373 Add_Str_To_Name_Buffer ("__");
8374 end if;
8375 end Add_Scope;
8377 -- Start of processing for Get_Qualified_Name
8379 begin
8380 Name_Len := 0;
8381 Add_Scope (Scop);
8383 -- Append the base name after all scopes have been chained
8385 Get_Name_String_And_Append (Nam);
8387 -- Append the suffix (if present)
8389 if Suffix /= No_Name then
8390 Add_Str_To_Name_Buffer ("__");
8391 Get_Name_String_And_Append (Suffix);
8392 end if;
8394 return Name_Find;
8395 end Get_Qualified_Name;
8397 -----------------------
8398 -- Get_Reason_String --
8399 -----------------------
8401 procedure Get_Reason_String (N : Node_Id) is
8402 begin
8403 if Nkind (N) = N_String_Literal then
8404 Store_String_Chars (Strval (N));
8406 elsif Nkind (N) = N_Op_Concat then
8407 Get_Reason_String (Left_Opnd (N));
8408 Get_Reason_String (Right_Opnd (N));
8410 -- If not of required form, error
8412 else
8413 Error_Msg_N
8414 ("Reason for pragma Warnings has wrong form", N);
8415 Error_Msg_N
8416 ("\must be string literal or concatenation of string literals", N);
8417 return;
8418 end if;
8419 end Get_Reason_String;
8421 --------------------------------
8422 -- Get_Reference_Discriminant --
8423 --------------------------------
8425 function Get_Reference_Discriminant (Typ : Entity_Id) return Entity_Id is
8426 D : Entity_Id;
8428 begin
8429 D := First_Discriminant (Typ);
8430 while Present (D) loop
8431 if Has_Implicit_Dereference (D) then
8432 return D;
8433 end if;
8434 Next_Discriminant (D);
8435 end loop;
8437 return Empty;
8438 end Get_Reference_Discriminant;
8440 ---------------------------
8441 -- Get_Referenced_Object --
8442 ---------------------------
8444 function Get_Referenced_Object (N : Node_Id) return Node_Id is
8445 R : Node_Id;
8447 begin
8448 R := N;
8449 while Is_Entity_Name (R)
8450 and then Present (Renamed_Object (Entity (R)))
8451 loop
8452 R := Renamed_Object (Entity (R));
8453 end loop;
8455 return R;
8456 end Get_Referenced_Object;
8458 ------------------------
8459 -- Get_Renamed_Entity --
8460 ------------------------
8462 function Get_Renamed_Entity (E : Entity_Id) return Entity_Id is
8463 R : Entity_Id;
8465 begin
8466 R := E;
8467 while Present (Renamed_Entity (R)) loop
8468 R := Renamed_Entity (R);
8469 end loop;
8471 return R;
8472 end Get_Renamed_Entity;
8474 -----------------------
8475 -- Get_Return_Object --
8476 -----------------------
8478 function Get_Return_Object (N : Node_Id) return Entity_Id is
8479 Decl : Node_Id;
8481 begin
8482 Decl := First (Return_Object_Declarations (N));
8483 while Present (Decl) loop
8484 exit when Nkind (Decl) = N_Object_Declaration
8485 and then Is_Return_Object (Defining_Identifier (Decl));
8486 Next (Decl);
8487 end loop;
8489 pragma Assert (Present (Decl));
8490 return Defining_Identifier (Decl);
8491 end Get_Return_Object;
8493 ---------------------------
8494 -- Get_Subprogram_Entity --
8495 ---------------------------
8497 function Get_Subprogram_Entity (Nod : Node_Id) return Entity_Id is
8498 Subp : Node_Id;
8499 Subp_Id : Entity_Id;
8501 begin
8502 if Nkind (Nod) = N_Accept_Statement then
8503 Subp := Entry_Direct_Name (Nod);
8505 elsif Nkind (Nod) = N_Slice then
8506 Subp := Prefix (Nod);
8508 else
8509 Subp := Name (Nod);
8510 end if;
8512 -- Strip the subprogram call
8514 loop
8515 if Nkind_In (Subp, N_Explicit_Dereference,
8516 N_Indexed_Component,
8517 N_Selected_Component)
8518 then
8519 Subp := Prefix (Subp);
8521 elsif Nkind_In (Subp, N_Type_Conversion,
8522 N_Unchecked_Type_Conversion)
8523 then
8524 Subp := Expression (Subp);
8526 else
8527 exit;
8528 end if;
8529 end loop;
8531 -- Extract the entity of the subprogram call
8533 if Is_Entity_Name (Subp) then
8534 Subp_Id := Entity (Subp);
8536 if Ekind (Subp_Id) = E_Access_Subprogram_Type then
8537 Subp_Id := Directly_Designated_Type (Subp_Id);
8538 end if;
8540 if Is_Subprogram (Subp_Id) then
8541 return Subp_Id;
8542 else
8543 return Empty;
8544 end if;
8546 -- The search did not find a construct that denotes a subprogram
8548 else
8549 return Empty;
8550 end if;
8551 end Get_Subprogram_Entity;
8553 -----------------------------
8554 -- Get_Task_Body_Procedure --
8555 -----------------------------
8557 function Get_Task_Body_Procedure (E : Entity_Id) return Node_Id is
8558 begin
8559 -- Note: A task type may be the completion of a private type with
8560 -- discriminants. When performing elaboration checks on a task
8561 -- declaration, the current view of the type may be the private one,
8562 -- and the procedure that holds the body of the task is held in its
8563 -- underlying type.
8565 -- This is an odd function, why not have Task_Body_Procedure do
8566 -- the following digging???
8568 return Task_Body_Procedure (Underlying_Type (Root_Type (E)));
8569 end Get_Task_Body_Procedure;
8571 -------------------------
8572 -- Get_User_Defined_Eq --
8573 -------------------------
8575 function Get_User_Defined_Eq (E : Entity_Id) return Entity_Id is
8576 Prim : Elmt_Id;
8577 Op : Entity_Id;
8579 begin
8580 Prim := First_Elmt (Collect_Primitive_Operations (E));
8581 while Present (Prim) loop
8582 Op := Node (Prim);
8584 if Chars (Op) = Name_Op_Eq
8585 and then Etype (Op) = Standard_Boolean
8586 and then Etype (First_Formal (Op)) = E
8587 and then Etype (Next_Formal (First_Formal (Op))) = E
8588 then
8589 return Op;
8590 end if;
8592 Next_Elmt (Prim);
8593 end loop;
8595 return Empty;
8596 end Get_User_Defined_Eq;
8598 -----------------------
8599 -- Has_Access_Values --
8600 -----------------------
8602 function Has_Access_Values (T : Entity_Id) return Boolean is
8603 Typ : constant Entity_Id := Underlying_Type (T);
8605 begin
8606 -- Case of a private type which is not completed yet. This can only
8607 -- happen in the case of a generic format type appearing directly, or
8608 -- as a component of the type to which this function is being applied
8609 -- at the top level. Return False in this case, since we certainly do
8610 -- not know that the type contains access types.
8612 if No (Typ) then
8613 return False;
8615 elsif Is_Access_Type (Typ) then
8616 return True;
8618 elsif Is_Array_Type (Typ) then
8619 return Has_Access_Values (Component_Type (Typ));
8621 elsif Is_Record_Type (Typ) then
8622 declare
8623 Comp : Entity_Id;
8625 begin
8626 -- Loop to Check components
8628 Comp := First_Component_Or_Discriminant (Typ);
8629 while Present (Comp) loop
8631 -- Check for access component, tag field does not count, even
8632 -- though it is implemented internally using an access type.
8634 if Has_Access_Values (Etype (Comp))
8635 and then Chars (Comp) /= Name_uTag
8636 then
8637 return True;
8638 end if;
8640 Next_Component_Or_Discriminant (Comp);
8641 end loop;
8642 end;
8644 return False;
8646 else
8647 return False;
8648 end if;
8649 end Has_Access_Values;
8651 ------------------------------
8652 -- Has_Compatible_Alignment --
8653 ------------------------------
8655 function Has_Compatible_Alignment
8656 (Obj : Entity_Id;
8657 Expr : Node_Id;
8658 Layout_Done : Boolean) return Alignment_Result
8660 function Has_Compatible_Alignment_Internal
8661 (Obj : Entity_Id;
8662 Expr : Node_Id;
8663 Layout_Done : Boolean;
8664 Default : Alignment_Result) return Alignment_Result;
8665 -- This is the internal recursive function that actually does the work.
8666 -- There is one additional parameter, which says what the result should
8667 -- be if no alignment information is found, and there is no definite
8668 -- indication of compatible alignments. At the outer level, this is set
8669 -- to Unknown, but for internal recursive calls in the case where types
8670 -- are known to be correct, it is set to Known_Compatible.
8672 ---------------------------------------
8673 -- Has_Compatible_Alignment_Internal --
8674 ---------------------------------------
8676 function Has_Compatible_Alignment_Internal
8677 (Obj : Entity_Id;
8678 Expr : Node_Id;
8679 Layout_Done : Boolean;
8680 Default : Alignment_Result) return Alignment_Result
8682 Result : Alignment_Result := Known_Compatible;
8683 -- Holds the current status of the result. Note that once a value of
8684 -- Known_Incompatible is set, it is sticky and does not get changed
8685 -- to Unknown (the value in Result only gets worse as we go along,
8686 -- never better).
8688 Offs : Uint := No_Uint;
8689 -- Set to a factor of the offset from the base object when Expr is a
8690 -- selected or indexed component, based on Component_Bit_Offset and
8691 -- Component_Size respectively. A negative value is used to represent
8692 -- a value which is not known at compile time.
8694 procedure Check_Prefix;
8695 -- Checks the prefix recursively in the case where the expression
8696 -- is an indexed or selected component.
8698 procedure Set_Result (R : Alignment_Result);
8699 -- If R represents a worse outcome (unknown instead of known
8700 -- compatible, or known incompatible), then set Result to R.
8702 ------------------
8703 -- Check_Prefix --
8704 ------------------
8706 procedure Check_Prefix is
8707 begin
8708 -- The subtlety here is that in doing a recursive call to check
8709 -- the prefix, we have to decide what to do in the case where we
8710 -- don't find any specific indication of an alignment problem.
8712 -- At the outer level, we normally set Unknown as the result in
8713 -- this case, since we can only set Known_Compatible if we really
8714 -- know that the alignment value is OK, but for the recursive
8715 -- call, in the case where the types match, and we have not
8716 -- specified a peculiar alignment for the object, we are only
8717 -- concerned about suspicious rep clauses, the default case does
8718 -- not affect us, since the compiler will, in the absence of such
8719 -- rep clauses, ensure that the alignment is correct.
8721 if Default = Known_Compatible
8722 or else
8723 (Etype (Obj) = Etype (Expr)
8724 and then (Unknown_Alignment (Obj)
8725 or else
8726 Alignment (Obj) = Alignment (Etype (Obj))))
8727 then
8728 Set_Result
8729 (Has_Compatible_Alignment_Internal
8730 (Obj, Prefix (Expr), Layout_Done, Known_Compatible));
8732 -- In all other cases, we need a full check on the prefix
8734 else
8735 Set_Result
8736 (Has_Compatible_Alignment_Internal
8737 (Obj, Prefix (Expr), Layout_Done, Unknown));
8738 end if;
8739 end Check_Prefix;
8741 ----------------
8742 -- Set_Result --
8743 ----------------
8745 procedure Set_Result (R : Alignment_Result) is
8746 begin
8747 if R > Result then
8748 Result := R;
8749 end if;
8750 end Set_Result;
8752 -- Start of processing for Has_Compatible_Alignment_Internal
8754 begin
8755 -- If Expr is a selected component, we must make sure there is no
8756 -- potentially troublesome component clause and that the record is
8757 -- not packed if the layout is not done.
8759 if Nkind (Expr) = N_Selected_Component then
8761 -- Packing generates unknown alignment if layout is not done
8763 if Is_Packed (Etype (Prefix (Expr))) and then not Layout_Done then
8764 Set_Result (Unknown);
8765 end if;
8767 -- Check prefix and component offset
8769 Check_Prefix;
8770 Offs := Component_Bit_Offset (Entity (Selector_Name (Expr)));
8772 -- If Expr is an indexed component, we must make sure there is no
8773 -- potentially troublesome Component_Size clause and that the array
8774 -- is not bit-packed if the layout is not done.
8776 elsif Nkind (Expr) = N_Indexed_Component then
8777 declare
8778 Typ : constant Entity_Id := Etype (Prefix (Expr));
8779 Ind : constant Node_Id := First_Index (Typ);
8781 begin
8782 -- Packing generates unknown alignment if layout is not done
8784 if Is_Bit_Packed_Array (Typ) and then not Layout_Done then
8785 Set_Result (Unknown);
8786 end if;
8788 -- Check prefix and component offset
8790 Check_Prefix;
8791 Offs := Component_Size (Typ);
8793 -- Small optimization: compute the full offset when possible
8795 if Offs /= No_Uint
8796 and then Offs > Uint_0
8797 and then Present (Ind)
8798 and then Nkind (Ind) = N_Range
8799 and then Compile_Time_Known_Value (Low_Bound (Ind))
8800 and then Compile_Time_Known_Value (First (Expressions (Expr)))
8801 then
8802 Offs := Offs * (Expr_Value (First (Expressions (Expr)))
8803 - Expr_Value (Low_Bound ((Ind))));
8804 end if;
8805 end;
8806 end if;
8808 -- If we have a null offset, the result is entirely determined by
8809 -- the base object and has already been computed recursively.
8811 if Offs = Uint_0 then
8812 null;
8814 -- Case where we know the alignment of the object
8816 elsif Known_Alignment (Obj) then
8817 declare
8818 ObjA : constant Uint := Alignment (Obj);
8819 ExpA : Uint := No_Uint;
8820 SizA : Uint := No_Uint;
8822 begin
8823 -- If alignment of Obj is 1, then we are always OK
8825 if ObjA = 1 then
8826 Set_Result (Known_Compatible);
8828 -- Alignment of Obj is greater than 1, so we need to check
8830 else
8831 -- If we have an offset, see if it is compatible
8833 if Offs /= No_Uint and Offs > Uint_0 then
8834 if Offs mod (System_Storage_Unit * ObjA) /= 0 then
8835 Set_Result (Known_Incompatible);
8836 end if;
8838 -- See if Expr is an object with known alignment
8840 elsif Is_Entity_Name (Expr)
8841 and then Known_Alignment (Entity (Expr))
8842 then
8843 ExpA := Alignment (Entity (Expr));
8845 -- Otherwise, we can use the alignment of the type of
8846 -- Expr given that we already checked for
8847 -- discombobulating rep clauses for the cases of indexed
8848 -- and selected components above.
8850 elsif Known_Alignment (Etype (Expr)) then
8851 ExpA := Alignment (Etype (Expr));
8853 -- Otherwise the alignment is unknown
8855 else
8856 Set_Result (Default);
8857 end if;
8859 -- If we got an alignment, see if it is acceptable
8861 if ExpA /= No_Uint and then ExpA < ObjA then
8862 Set_Result (Known_Incompatible);
8863 end if;
8865 -- If Expr is not a piece of a larger object, see if size
8866 -- is given. If so, check that it is not too small for the
8867 -- required alignment.
8869 if Offs /= No_Uint then
8870 null;
8872 -- See if Expr is an object with known size
8874 elsif Is_Entity_Name (Expr)
8875 and then Known_Static_Esize (Entity (Expr))
8876 then
8877 SizA := Esize (Entity (Expr));
8879 -- Otherwise, we check the object size of the Expr type
8881 elsif Known_Static_Esize (Etype (Expr)) then
8882 SizA := Esize (Etype (Expr));
8883 end if;
8885 -- If we got a size, see if it is a multiple of the Obj
8886 -- alignment, if not, then the alignment cannot be
8887 -- acceptable, since the size is always a multiple of the
8888 -- alignment.
8890 if SizA /= No_Uint then
8891 if SizA mod (ObjA * Ttypes.System_Storage_Unit) /= 0 then
8892 Set_Result (Known_Incompatible);
8893 end if;
8894 end if;
8895 end if;
8896 end;
8898 -- If we do not know required alignment, any non-zero offset is a
8899 -- potential problem (but certainly may be OK, so result is unknown).
8901 elsif Offs /= No_Uint then
8902 Set_Result (Unknown);
8904 -- If we can't find the result by direct comparison of alignment
8905 -- values, then there is still one case that we can determine known
8906 -- result, and that is when we can determine that the types are the
8907 -- same, and no alignments are specified. Then we known that the
8908 -- alignments are compatible, even if we don't know the alignment
8909 -- value in the front end.
8911 elsif Etype (Obj) = Etype (Expr) then
8913 -- Types are the same, but we have to check for possible size
8914 -- and alignments on the Expr object that may make the alignment
8915 -- different, even though the types are the same.
8917 if Is_Entity_Name (Expr) then
8919 -- First check alignment of the Expr object. Any alignment less
8920 -- than Maximum_Alignment is worrisome since this is the case
8921 -- where we do not know the alignment of Obj.
8923 if Known_Alignment (Entity (Expr))
8924 and then UI_To_Int (Alignment (Entity (Expr))) <
8925 Ttypes.Maximum_Alignment
8926 then
8927 Set_Result (Unknown);
8929 -- Now check size of Expr object. Any size that is not an
8930 -- even multiple of Maximum_Alignment is also worrisome
8931 -- since it may cause the alignment of the object to be less
8932 -- than the alignment of the type.
8934 elsif Known_Static_Esize (Entity (Expr))
8935 and then
8936 (UI_To_Int (Esize (Entity (Expr))) mod
8937 (Ttypes.Maximum_Alignment * Ttypes.System_Storage_Unit))
8938 /= 0
8939 then
8940 Set_Result (Unknown);
8942 -- Otherwise same type is decisive
8944 else
8945 Set_Result (Known_Compatible);
8946 end if;
8947 end if;
8949 -- Another case to deal with is when there is an explicit size or
8950 -- alignment clause when the types are not the same. If so, then the
8951 -- result is Unknown. We don't need to do this test if the Default is
8952 -- Unknown, since that result will be set in any case.
8954 elsif Default /= Unknown
8955 and then (Has_Size_Clause (Etype (Expr))
8956 or else
8957 Has_Alignment_Clause (Etype (Expr)))
8958 then
8959 Set_Result (Unknown);
8961 -- If no indication found, set default
8963 else
8964 Set_Result (Default);
8965 end if;
8967 -- Return worst result found
8969 return Result;
8970 end Has_Compatible_Alignment_Internal;
8972 -- Start of processing for Has_Compatible_Alignment
8974 begin
8975 -- If Obj has no specified alignment, then set alignment from the type
8976 -- alignment. Perhaps we should always do this, but for sure we should
8977 -- do it when there is an address clause since we can do more if the
8978 -- alignment is known.
8980 if Unknown_Alignment (Obj) then
8981 Set_Alignment (Obj, Alignment (Etype (Obj)));
8982 end if;
8984 -- Now do the internal call that does all the work
8986 return
8987 Has_Compatible_Alignment_Internal (Obj, Expr, Layout_Done, Unknown);
8988 end Has_Compatible_Alignment;
8990 ----------------------
8991 -- Has_Declarations --
8992 ----------------------
8994 function Has_Declarations (N : Node_Id) return Boolean is
8995 begin
8996 return Nkind_In (Nkind (N), N_Accept_Statement,
8997 N_Block_Statement,
8998 N_Compilation_Unit_Aux,
8999 N_Entry_Body,
9000 N_Package_Body,
9001 N_Protected_Body,
9002 N_Subprogram_Body,
9003 N_Task_Body,
9004 N_Package_Specification);
9005 end Has_Declarations;
9007 ---------------------------------
9008 -- Has_Defaulted_Discriminants --
9009 ---------------------------------
9011 function Has_Defaulted_Discriminants (Typ : Entity_Id) return Boolean is
9012 begin
9013 return Has_Discriminants (Typ)
9014 and then Present (First_Discriminant (Typ))
9015 and then Present (Discriminant_Default_Value
9016 (First_Discriminant (Typ)));
9017 end Has_Defaulted_Discriminants;
9019 -------------------
9020 -- Has_Denormals --
9021 -------------------
9023 function Has_Denormals (E : Entity_Id) return Boolean is
9024 begin
9025 return Is_Floating_Point_Type (E) and then Denorm_On_Target;
9026 end Has_Denormals;
9028 -------------------------------------------
9029 -- Has_Discriminant_Dependent_Constraint --
9030 -------------------------------------------
9032 function Has_Discriminant_Dependent_Constraint
9033 (Comp : Entity_Id) return Boolean
9035 Comp_Decl : constant Node_Id := Parent (Comp);
9036 Subt_Indic : Node_Id;
9037 Constr : Node_Id;
9038 Assn : Node_Id;
9040 begin
9041 -- Discriminants can't depend on discriminants
9043 if Ekind (Comp) = E_Discriminant then
9044 return False;
9046 else
9047 Subt_Indic := Subtype_Indication (Component_Definition (Comp_Decl));
9049 if Nkind (Subt_Indic) = N_Subtype_Indication then
9050 Constr := Constraint (Subt_Indic);
9052 if Nkind (Constr) = N_Index_Or_Discriminant_Constraint then
9053 Assn := First (Constraints (Constr));
9054 while Present (Assn) loop
9055 case Nkind (Assn) is
9056 when N_Subtype_Indication |
9057 N_Range |
9058 N_Identifier
9060 if Depends_On_Discriminant (Assn) then
9061 return True;
9062 end if;
9064 when N_Discriminant_Association =>
9065 if Depends_On_Discriminant (Expression (Assn)) then
9066 return True;
9067 end if;
9069 when others =>
9070 null;
9071 end case;
9073 Next (Assn);
9074 end loop;
9075 end if;
9076 end if;
9077 end if;
9079 return False;
9080 end Has_Discriminant_Dependent_Constraint;
9082 --------------------------------------
9083 -- Has_Effectively_Volatile_Profile --
9084 --------------------------------------
9086 function Has_Effectively_Volatile_Profile
9087 (Subp_Id : Entity_Id) return Boolean
9089 Formal : Entity_Id;
9091 begin
9092 -- Inspect the formal parameters looking for an effectively volatile
9093 -- type.
9095 Formal := First_Formal (Subp_Id);
9096 while Present (Formal) loop
9097 if Is_Effectively_Volatile (Etype (Formal)) then
9098 return True;
9099 end if;
9101 Next_Formal (Formal);
9102 end loop;
9104 -- Inspect the return type of functions
9106 if Ekind_In (Subp_Id, E_Function, E_Generic_Function)
9107 and then Is_Effectively_Volatile (Etype (Subp_Id))
9108 then
9109 return True;
9110 end if;
9112 return False;
9113 end Has_Effectively_Volatile_Profile;
9115 --------------------------
9116 -- Has_Enabled_Property --
9117 --------------------------
9119 function Has_Enabled_Property
9120 (Item_Id : Entity_Id;
9121 Property : Name_Id) return Boolean
9123 function State_Has_Enabled_Property return Boolean;
9124 -- Determine whether a state denoted by Item_Id has the property enabled
9126 function Variable_Has_Enabled_Property return Boolean;
9127 -- Determine whether a variable denoted by Item_Id has the property
9128 -- enabled.
9130 --------------------------------
9131 -- State_Has_Enabled_Property --
9132 --------------------------------
9134 function State_Has_Enabled_Property return Boolean is
9135 Decl : constant Node_Id := Parent (Item_Id);
9136 Opt : Node_Id;
9137 Opt_Nam : Node_Id;
9138 Prop : Node_Id;
9139 Prop_Nam : Node_Id;
9140 Props : Node_Id;
9142 begin
9143 -- The declaration of an external abstract state appears as an
9144 -- extension aggregate. If this is not the case, properties can never
9145 -- be set.
9147 if Nkind (Decl) /= N_Extension_Aggregate then
9148 return False;
9149 end if;
9151 -- When External appears as a simple option, it automatically enables
9152 -- all properties.
9154 Opt := First (Expressions (Decl));
9155 while Present (Opt) loop
9156 if Nkind (Opt) = N_Identifier
9157 and then Chars (Opt) = Name_External
9158 then
9159 return True;
9160 end if;
9162 Next (Opt);
9163 end loop;
9165 -- When External specifies particular properties, inspect those and
9166 -- find the desired one (if any).
9168 Opt := First (Component_Associations (Decl));
9169 while Present (Opt) loop
9170 Opt_Nam := First (Choices (Opt));
9172 if Nkind (Opt_Nam) = N_Identifier
9173 and then Chars (Opt_Nam) = Name_External
9174 then
9175 Props := Expression (Opt);
9177 -- Multiple properties appear as an aggregate
9179 if Nkind (Props) = N_Aggregate then
9181 -- Simple property form
9183 Prop := First (Expressions (Props));
9184 while Present (Prop) loop
9185 if Chars (Prop) = Property then
9186 return True;
9187 end if;
9189 Next (Prop);
9190 end loop;
9192 -- Property with expression form
9194 Prop := First (Component_Associations (Props));
9195 while Present (Prop) loop
9196 Prop_Nam := First (Choices (Prop));
9198 -- The property can be represented in two ways:
9199 -- others => <value>
9200 -- <property> => <value>
9202 if Nkind (Prop_Nam) = N_Others_Choice
9203 or else (Nkind (Prop_Nam) = N_Identifier
9204 and then Chars (Prop_Nam) = Property)
9205 then
9206 return Is_True (Expr_Value (Expression (Prop)));
9207 end if;
9209 Next (Prop);
9210 end loop;
9212 -- Single property
9214 else
9215 return Chars (Props) = Property;
9216 end if;
9217 end if;
9219 Next (Opt);
9220 end loop;
9222 return False;
9223 end State_Has_Enabled_Property;
9225 -----------------------------------
9226 -- Variable_Has_Enabled_Property --
9227 -----------------------------------
9229 function Variable_Has_Enabled_Property return Boolean is
9230 function Is_Enabled (Prag : Node_Id) return Boolean;
9231 -- Determine whether property pragma Prag (if present) denotes an
9232 -- enabled property.
9234 ----------------
9235 -- Is_Enabled --
9236 ----------------
9238 function Is_Enabled (Prag : Node_Id) return Boolean is
9239 Arg1 : Node_Id;
9241 begin
9242 if Present (Prag) then
9243 Arg1 := First (Pragma_Argument_Associations (Prag));
9245 -- The pragma has an optional Boolean expression, the related
9246 -- property is enabled only when the expression evaluates to
9247 -- True.
9249 if Present (Arg1) then
9250 return Is_True (Expr_Value (Get_Pragma_Arg (Arg1)));
9252 -- Otherwise the lack of expression enables the property by
9253 -- default.
9255 else
9256 return True;
9257 end if;
9259 -- The property was never set in the first place
9261 else
9262 return False;
9263 end if;
9264 end Is_Enabled;
9266 -- Local variables
9268 AR : constant Node_Id :=
9269 Get_Pragma (Item_Id, Pragma_Async_Readers);
9270 AW : constant Node_Id :=
9271 Get_Pragma (Item_Id, Pragma_Async_Writers);
9272 ER : constant Node_Id :=
9273 Get_Pragma (Item_Id, Pragma_Effective_Reads);
9274 EW : constant Node_Id :=
9275 Get_Pragma (Item_Id, Pragma_Effective_Writes);
9277 -- Start of processing for Variable_Has_Enabled_Property
9279 begin
9280 -- A non-effectively volatile object can never possess external
9281 -- properties.
9283 if not Is_Effectively_Volatile (Item_Id) then
9284 return False;
9286 -- External properties related to variables come in two flavors -
9287 -- explicit and implicit. The explicit case is characterized by the
9288 -- presence of a property pragma with an optional Boolean flag. The
9289 -- property is enabled when the flag evaluates to True or the flag is
9290 -- missing altogether.
9292 elsif Property = Name_Async_Readers and then Is_Enabled (AR) then
9293 return True;
9295 elsif Property = Name_Async_Writers and then Is_Enabled (AW) then
9296 return True;
9298 elsif Property = Name_Effective_Reads and then Is_Enabled (ER) then
9299 return True;
9301 elsif Property = Name_Effective_Writes and then Is_Enabled (EW) then
9302 return True;
9304 -- The implicit case lacks all property pragmas
9306 elsif No (AR) and then No (AW) and then No (ER) and then No (EW) then
9307 return True;
9309 else
9310 return False;
9311 end if;
9312 end Variable_Has_Enabled_Property;
9314 -- Start of processing for Has_Enabled_Property
9316 begin
9317 -- Abstract states and variables have a flexible scheme of specifying
9318 -- external properties.
9320 if Ekind (Item_Id) = E_Abstract_State then
9321 return State_Has_Enabled_Property;
9323 elsif Ekind (Item_Id) = E_Variable then
9324 return Variable_Has_Enabled_Property;
9326 -- Otherwise a property is enabled when the related item is effectively
9327 -- volatile.
9329 else
9330 return Is_Effectively_Volatile (Item_Id);
9331 end if;
9332 end Has_Enabled_Property;
9334 -------------------------------------
9335 -- Has_Full_Default_Initialization --
9336 -------------------------------------
9338 function Has_Full_Default_Initialization (Typ : Entity_Id) return Boolean is
9339 Arg : Node_Id;
9340 Comp : Entity_Id;
9341 Prag : Node_Id;
9343 begin
9344 -- A private type and its full view is fully default initialized when it
9345 -- is subject to pragma Default_Initial_Condition without an argument or
9346 -- with a non-null argument. Since any type may act as the full view of
9347 -- a private type, this check must be performed prior to the specialized
9348 -- tests below.
9350 if Has_Default_Init_Cond (Typ)
9351 or else Has_Inherited_Default_Init_Cond (Typ)
9352 then
9353 Prag := Get_Pragma (Typ, Pragma_Default_Initial_Condition);
9355 -- Pragma Default_Initial_Condition must be present if one of the
9356 -- related entity flags is set.
9358 pragma Assert (Present (Prag));
9359 Arg := First (Pragma_Argument_Associations (Prag));
9361 -- A non-null argument guarantees full default initialization
9363 if Present (Arg) then
9364 return Nkind (Arg) /= N_Null;
9366 -- Otherwise the missing argument defaults the pragma to "True" which
9367 -- is considered a non-null argument (see above).
9369 else
9370 return True;
9371 end if;
9372 end if;
9374 -- A scalar type is fully default initialized if it is subject to aspect
9375 -- Default_Value.
9377 if Is_Scalar_Type (Typ) then
9378 return Has_Default_Aspect (Typ);
9380 -- An array type is fully default initialized if its element type is
9381 -- scalar and the array type carries aspect Default_Component_Value or
9382 -- the element type is fully default initialized.
9384 elsif Is_Array_Type (Typ) then
9385 return
9386 Has_Default_Aspect (Typ)
9387 or else Has_Full_Default_Initialization (Component_Type (Typ));
9389 -- A protected type, record type, or type extension is fully default
9390 -- initialized if all its components either carry an initialization
9391 -- expression or have a type that is fully default initialized. The
9392 -- parent type of a type extension must be fully default initialized.
9394 elsif Is_Record_Type (Typ) or else Is_Protected_Type (Typ) then
9396 -- Inspect all entities defined in the scope of the type, looking for
9397 -- uninitialized components.
9399 Comp := First_Entity (Typ);
9400 while Present (Comp) loop
9401 if Ekind (Comp) = E_Component
9402 and then Comes_From_Source (Comp)
9403 and then No (Expression (Parent (Comp)))
9404 and then not Has_Full_Default_Initialization (Etype (Comp))
9405 then
9406 return False;
9407 end if;
9409 Next_Entity (Comp);
9410 end loop;
9412 -- Ensure that the parent type of a type extension is fully default
9413 -- initialized.
9415 if Etype (Typ) /= Typ
9416 and then not Has_Full_Default_Initialization (Etype (Typ))
9417 then
9418 return False;
9419 end if;
9421 -- If we get here, then all components and parent portion are fully
9422 -- default initialized.
9424 return True;
9426 -- A task type is fully default initialized by default
9428 elsif Is_Task_Type (Typ) then
9429 return True;
9431 -- Otherwise the type is not fully default initialized
9433 else
9434 return False;
9435 end if;
9436 end Has_Full_Default_Initialization;
9438 --------------------
9439 -- Has_Infinities --
9440 --------------------
9442 function Has_Infinities (E : Entity_Id) return Boolean is
9443 begin
9444 return
9445 Is_Floating_Point_Type (E)
9446 and then Nkind (Scalar_Range (E)) = N_Range
9447 and then Includes_Infinities (Scalar_Range (E));
9448 end Has_Infinities;
9450 --------------------
9451 -- Has_Interfaces --
9452 --------------------
9454 function Has_Interfaces
9455 (T : Entity_Id;
9456 Use_Full_View : Boolean := True) return Boolean
9458 Typ : Entity_Id := Base_Type (T);
9460 begin
9461 -- Handle concurrent types
9463 if Is_Concurrent_Type (Typ) then
9464 Typ := Corresponding_Record_Type (Typ);
9465 end if;
9467 if not Present (Typ)
9468 or else not Is_Record_Type (Typ)
9469 or else not Is_Tagged_Type (Typ)
9470 then
9471 return False;
9472 end if;
9474 -- Handle private types
9476 if Use_Full_View and then Present (Full_View (Typ)) then
9477 Typ := Full_View (Typ);
9478 end if;
9480 -- Handle concurrent record types
9482 if Is_Concurrent_Record_Type (Typ)
9483 and then Is_Non_Empty_List (Abstract_Interface_List (Typ))
9484 then
9485 return True;
9486 end if;
9488 loop
9489 if Is_Interface (Typ)
9490 or else
9491 (Is_Record_Type (Typ)
9492 and then Present (Interfaces (Typ))
9493 and then not Is_Empty_Elmt_List (Interfaces (Typ)))
9494 then
9495 return True;
9496 end if;
9498 exit when Etype (Typ) = Typ
9500 -- Handle private types
9502 or else (Present (Full_View (Etype (Typ)))
9503 and then Full_View (Etype (Typ)) = Typ)
9505 -- Protect frontend against wrong sources with cyclic derivations
9507 or else Etype (Typ) = T;
9509 -- Climb to the ancestor type handling private types
9511 if Present (Full_View (Etype (Typ))) then
9512 Typ := Full_View (Etype (Typ));
9513 else
9514 Typ := Etype (Typ);
9515 end if;
9516 end loop;
9518 return False;
9519 end Has_Interfaces;
9521 ---------------------------------
9522 -- Has_No_Obvious_Side_Effects --
9523 ---------------------------------
9525 function Has_No_Obvious_Side_Effects (N : Node_Id) return Boolean is
9526 begin
9527 -- For now, just handle literals, constants, and non-volatile
9528 -- variables and expressions combining these with operators or
9529 -- short circuit forms.
9531 if Nkind (N) in N_Numeric_Or_String_Literal then
9532 return True;
9534 elsif Nkind (N) = N_Character_Literal then
9535 return True;
9537 elsif Nkind (N) in N_Unary_Op then
9538 return Has_No_Obvious_Side_Effects (Right_Opnd (N));
9540 elsif Nkind (N) in N_Binary_Op or else Nkind (N) in N_Short_Circuit then
9541 return Has_No_Obvious_Side_Effects (Left_Opnd (N))
9542 and then
9543 Has_No_Obvious_Side_Effects (Right_Opnd (N));
9545 elsif Nkind (N) = N_Expression_With_Actions
9546 and then Is_Empty_List (Actions (N))
9547 then
9548 return Has_No_Obvious_Side_Effects (Expression (N));
9550 elsif Nkind (N) in N_Has_Entity then
9551 return Present (Entity (N))
9552 and then Ekind_In (Entity (N), E_Variable,
9553 E_Constant,
9554 E_Enumeration_Literal,
9555 E_In_Parameter,
9556 E_Out_Parameter,
9557 E_In_Out_Parameter)
9558 and then not Is_Volatile (Entity (N));
9560 else
9561 return False;
9562 end if;
9563 end Has_No_Obvious_Side_Effects;
9565 -----------------------------
9566 -- Has_Non_Null_Refinement --
9567 -----------------------------
9569 function Has_Non_Null_Refinement (Id : Entity_Id) return Boolean is
9570 Constits : Elist_Id;
9572 begin
9573 pragma Assert (Ekind (Id) = E_Abstract_State);
9574 Constits := Refinement_Constituents (Id);
9576 -- For a refinement to be non-null, the first constituent must be
9577 -- anything other than null.
9579 return
9580 Present (Constits)
9581 and then Nkind (Node (First_Elmt (Constits))) /= N_Null;
9582 end Has_Non_Null_Refinement;
9584 ------------------------
9585 -- Has_Null_Exclusion --
9586 ------------------------
9588 function Has_Null_Exclusion (N : Node_Id) return Boolean is
9589 begin
9590 case Nkind (N) is
9591 when N_Access_Definition |
9592 N_Access_Function_Definition |
9593 N_Access_Procedure_Definition |
9594 N_Access_To_Object_Definition |
9595 N_Allocator |
9596 N_Derived_Type_Definition |
9597 N_Function_Specification |
9598 N_Subtype_Declaration =>
9599 return Null_Exclusion_Present (N);
9601 when N_Component_Definition |
9602 N_Formal_Object_Declaration |
9603 N_Object_Renaming_Declaration =>
9604 if Present (Subtype_Mark (N)) then
9605 return Null_Exclusion_Present (N);
9606 else pragma Assert (Present (Access_Definition (N)));
9607 return Null_Exclusion_Present (Access_Definition (N));
9608 end if;
9610 when N_Discriminant_Specification =>
9611 if Nkind (Discriminant_Type (N)) = N_Access_Definition then
9612 return Null_Exclusion_Present (Discriminant_Type (N));
9613 else
9614 return Null_Exclusion_Present (N);
9615 end if;
9617 when N_Object_Declaration =>
9618 if Nkind (Object_Definition (N)) = N_Access_Definition then
9619 return Null_Exclusion_Present (Object_Definition (N));
9620 else
9621 return Null_Exclusion_Present (N);
9622 end if;
9624 when N_Parameter_Specification =>
9625 if Nkind (Parameter_Type (N)) = N_Access_Definition then
9626 return Null_Exclusion_Present (Parameter_Type (N));
9627 else
9628 return Null_Exclusion_Present (N);
9629 end if;
9631 when others =>
9632 return False;
9634 end case;
9635 end Has_Null_Exclusion;
9637 ------------------------
9638 -- Has_Null_Extension --
9639 ------------------------
9641 function Has_Null_Extension (T : Entity_Id) return Boolean is
9642 B : constant Entity_Id := Base_Type (T);
9643 Comps : Node_Id;
9644 Ext : Node_Id;
9646 begin
9647 if Nkind (Parent (B)) = N_Full_Type_Declaration
9648 and then Present (Record_Extension_Part (Type_Definition (Parent (B))))
9649 then
9650 Ext := Record_Extension_Part (Type_Definition (Parent (B)));
9652 if Present (Ext) then
9653 if Null_Present (Ext) then
9654 return True;
9655 else
9656 Comps := Component_List (Ext);
9658 -- The null component list is rewritten during analysis to
9659 -- include the parent component. Any other component indicates
9660 -- that the extension was not originally null.
9662 return Null_Present (Comps)
9663 or else No (Next (First (Component_Items (Comps))));
9664 end if;
9665 else
9666 return False;
9667 end if;
9669 else
9670 return False;
9671 end if;
9672 end Has_Null_Extension;
9674 -------------------------
9675 -- Has_Null_Refinement --
9676 -------------------------
9678 function Has_Null_Refinement (Id : Entity_Id) return Boolean is
9679 Constits : Elist_Id;
9681 begin
9682 pragma Assert (Ekind (Id) = E_Abstract_State);
9683 Constits := Refinement_Constituents (Id);
9685 -- For a refinement to be null, the state's sole constituent must be a
9686 -- null.
9688 return
9689 Present (Constits)
9690 and then Nkind (Node (First_Elmt (Constits))) = N_Null;
9691 end Has_Null_Refinement;
9693 -------------------------------
9694 -- Has_Overriding_Initialize --
9695 -------------------------------
9697 function Has_Overriding_Initialize (T : Entity_Id) return Boolean is
9698 BT : constant Entity_Id := Base_Type (T);
9699 P : Elmt_Id;
9701 begin
9702 if Is_Controlled (BT) then
9703 if Is_RTU (Scope (BT), Ada_Finalization) then
9704 return False;
9706 elsif Present (Primitive_Operations (BT)) then
9707 P := First_Elmt (Primitive_Operations (BT));
9708 while Present (P) loop
9709 declare
9710 Init : constant Entity_Id := Node (P);
9711 Formal : constant Entity_Id := First_Formal (Init);
9712 begin
9713 if Ekind (Init) = E_Procedure
9714 and then Chars (Init) = Name_Initialize
9715 and then Comes_From_Source (Init)
9716 and then Present (Formal)
9717 and then Etype (Formal) = BT
9718 and then No (Next_Formal (Formal))
9719 and then (Ada_Version < Ada_2012
9720 or else not Null_Present (Parent (Init)))
9721 then
9722 return True;
9723 end if;
9724 end;
9726 Next_Elmt (P);
9727 end loop;
9728 end if;
9730 -- Here if type itself does not have a non-null Initialize operation:
9731 -- check immediate ancestor.
9733 if Is_Derived_Type (BT)
9734 and then Has_Overriding_Initialize (Etype (BT))
9735 then
9736 return True;
9737 end if;
9738 end if;
9740 return False;
9741 end Has_Overriding_Initialize;
9743 --------------------------------------
9744 -- Has_Preelaborable_Initialization --
9745 --------------------------------------
9747 function Has_Preelaborable_Initialization (E : Entity_Id) return Boolean is
9748 Has_PE : Boolean;
9750 procedure Check_Components (E : Entity_Id);
9751 -- Check component/discriminant chain, sets Has_PE False if a component
9752 -- or discriminant does not meet the preelaborable initialization rules.
9754 ----------------------
9755 -- Check_Components --
9756 ----------------------
9758 procedure Check_Components (E : Entity_Id) is
9759 Ent : Entity_Id;
9760 Exp : Node_Id;
9762 function Is_Preelaborable_Expression (N : Node_Id) return Boolean;
9763 -- Returns True if and only if the expression denoted by N does not
9764 -- violate restrictions on preelaborable constructs (RM-10.2.1(5-9)).
9766 ---------------------------------
9767 -- Is_Preelaborable_Expression --
9768 ---------------------------------
9770 function Is_Preelaborable_Expression (N : Node_Id) return Boolean is
9771 Exp : Node_Id;
9772 Assn : Node_Id;
9773 Choice : Node_Id;
9774 Comp_Type : Entity_Id;
9775 Is_Array_Aggr : Boolean;
9777 begin
9778 if Is_OK_Static_Expression (N) then
9779 return True;
9781 elsif Nkind (N) = N_Null then
9782 return True;
9784 -- Attributes are allowed in general, even if their prefix is a
9785 -- formal type. (It seems that certain attributes known not to be
9786 -- static might not be allowed, but there are no rules to prevent
9787 -- them.)
9789 elsif Nkind (N) = N_Attribute_Reference then
9790 return True;
9792 -- The name of a discriminant evaluated within its parent type is
9793 -- defined to be preelaborable (10.2.1(8)). Note that we test for
9794 -- names that denote discriminals as well as discriminants to
9795 -- catch references occurring within init procs.
9797 elsif Is_Entity_Name (N)
9798 and then
9799 (Ekind (Entity (N)) = E_Discriminant
9800 or else (Ekind_In (Entity (N), E_Constant, E_In_Parameter)
9801 and then Present (Discriminal_Link (Entity (N)))))
9802 then
9803 return True;
9805 elsif Nkind (N) = N_Qualified_Expression then
9806 return Is_Preelaborable_Expression (Expression (N));
9808 -- For aggregates we have to check that each of the associations
9809 -- is preelaborable.
9811 elsif Nkind_In (N, N_Aggregate, N_Extension_Aggregate) then
9812 Is_Array_Aggr := Is_Array_Type (Etype (N));
9814 if Is_Array_Aggr then
9815 Comp_Type := Component_Type (Etype (N));
9816 end if;
9818 -- Check the ancestor part of extension aggregates, which must
9819 -- be either the name of a type that has preelaborable init or
9820 -- an expression that is preelaborable.
9822 if Nkind (N) = N_Extension_Aggregate then
9823 declare
9824 Anc_Part : constant Node_Id := Ancestor_Part (N);
9826 begin
9827 if Is_Entity_Name (Anc_Part)
9828 and then Is_Type (Entity (Anc_Part))
9829 then
9830 if not Has_Preelaborable_Initialization
9831 (Entity (Anc_Part))
9832 then
9833 return False;
9834 end if;
9836 elsif not Is_Preelaborable_Expression (Anc_Part) then
9837 return False;
9838 end if;
9839 end;
9840 end if;
9842 -- Check positional associations
9844 Exp := First (Expressions (N));
9845 while Present (Exp) loop
9846 if not Is_Preelaborable_Expression (Exp) then
9847 return False;
9848 end if;
9850 Next (Exp);
9851 end loop;
9853 -- Check named associations
9855 Assn := First (Component_Associations (N));
9856 while Present (Assn) loop
9857 Choice := First (Choices (Assn));
9858 while Present (Choice) loop
9859 if Is_Array_Aggr then
9860 if Nkind (Choice) = N_Others_Choice then
9861 null;
9863 elsif Nkind (Choice) = N_Range then
9864 if not Is_OK_Static_Range (Choice) then
9865 return False;
9866 end if;
9868 elsif not Is_OK_Static_Expression (Choice) then
9869 return False;
9870 end if;
9872 else
9873 Comp_Type := Etype (Choice);
9874 end if;
9876 Next (Choice);
9877 end loop;
9879 -- If the association has a <> at this point, then we have
9880 -- to check whether the component's type has preelaborable
9881 -- initialization. Note that this only occurs when the
9882 -- association's corresponding component does not have a
9883 -- default expression, the latter case having already been
9884 -- expanded as an expression for the association.
9886 if Box_Present (Assn) then
9887 if not Has_Preelaborable_Initialization (Comp_Type) then
9888 return False;
9889 end if;
9891 -- In the expression case we check whether the expression
9892 -- is preelaborable.
9894 elsif
9895 not Is_Preelaborable_Expression (Expression (Assn))
9896 then
9897 return False;
9898 end if;
9900 Next (Assn);
9901 end loop;
9903 -- If we get here then aggregate as a whole is preelaborable
9905 return True;
9907 -- All other cases are not preelaborable
9909 else
9910 return False;
9911 end if;
9912 end Is_Preelaborable_Expression;
9914 -- Start of processing for Check_Components
9916 begin
9917 -- Loop through entities of record or protected type
9919 Ent := E;
9920 while Present (Ent) loop
9922 -- We are interested only in components and discriminants
9924 Exp := Empty;
9926 case Ekind (Ent) is
9927 when E_Component =>
9929 -- Get default expression if any. If there is no declaration
9930 -- node, it means we have an internal entity. The parent and
9931 -- tag fields are examples of such entities. For such cases,
9932 -- we just test the type of the entity.
9934 if Present (Declaration_Node (Ent)) then
9935 Exp := Expression (Declaration_Node (Ent));
9936 end if;
9938 when E_Discriminant =>
9940 -- Note: for a renamed discriminant, the Declaration_Node
9941 -- may point to the one from the ancestor, and have a
9942 -- different expression, so use the proper attribute to
9943 -- retrieve the expression from the derived constraint.
9945 Exp := Discriminant_Default_Value (Ent);
9947 when others =>
9948 goto Check_Next_Entity;
9949 end case;
9951 -- A component has PI if it has no default expression and the
9952 -- component type has PI.
9954 if No (Exp) then
9955 if not Has_Preelaborable_Initialization (Etype (Ent)) then
9956 Has_PE := False;
9957 exit;
9958 end if;
9960 -- Require the default expression to be preelaborable
9962 elsif not Is_Preelaborable_Expression (Exp) then
9963 Has_PE := False;
9964 exit;
9965 end if;
9967 <<Check_Next_Entity>>
9968 Next_Entity (Ent);
9969 end loop;
9970 end Check_Components;
9972 -- Start of processing for Has_Preelaborable_Initialization
9974 begin
9975 -- Immediate return if already marked as known preelaborable init. This
9976 -- covers types for which this function has already been called once
9977 -- and returned True (in which case the result is cached), and also
9978 -- types to which a pragma Preelaborable_Initialization applies.
9980 if Known_To_Have_Preelab_Init (E) then
9981 return True;
9982 end if;
9984 -- If the type is a subtype representing a generic actual type, then
9985 -- test whether its base type has preelaborable initialization since
9986 -- the subtype representing the actual does not inherit this attribute
9987 -- from the actual or formal. (but maybe it should???)
9989 if Is_Generic_Actual_Type (E) then
9990 return Has_Preelaborable_Initialization (Base_Type (E));
9991 end if;
9993 -- All elementary types have preelaborable initialization
9995 if Is_Elementary_Type (E) then
9996 Has_PE := True;
9998 -- Array types have PI if the component type has PI
10000 elsif Is_Array_Type (E) then
10001 Has_PE := Has_Preelaborable_Initialization (Component_Type (E));
10003 -- A derived type has preelaborable initialization if its parent type
10004 -- has preelaborable initialization and (in the case of a derived record
10005 -- extension) if the non-inherited components all have preelaborable
10006 -- initialization. However, a user-defined controlled type with an
10007 -- overriding Initialize procedure does not have preelaborable
10008 -- initialization.
10010 elsif Is_Derived_Type (E) then
10012 -- If the derived type is a private extension then it doesn't have
10013 -- preelaborable initialization.
10015 if Ekind (Base_Type (E)) = E_Record_Type_With_Private then
10016 return False;
10017 end if;
10019 -- First check whether ancestor type has preelaborable initialization
10021 Has_PE := Has_Preelaborable_Initialization (Etype (Base_Type (E)));
10023 -- If OK, check extension components (if any)
10025 if Has_PE and then Is_Record_Type (E) then
10026 Check_Components (First_Entity (E));
10027 end if;
10029 -- Check specifically for 10.2.1(11.4/2) exception: a controlled type
10030 -- with a user defined Initialize procedure does not have PI. If
10031 -- the type is untagged, the control primitives come from a component
10032 -- that has already been checked.
10034 if Has_PE
10035 and then Is_Controlled (E)
10036 and then Is_Tagged_Type (E)
10037 and then Has_Overriding_Initialize (E)
10038 then
10039 Has_PE := False;
10040 end if;
10042 -- Private types not derived from a type having preelaborable init and
10043 -- that are not marked with pragma Preelaborable_Initialization do not
10044 -- have preelaborable initialization.
10046 elsif Is_Private_Type (E) then
10047 return False;
10049 -- Record type has PI if it is non private and all components have PI
10051 elsif Is_Record_Type (E) then
10052 Has_PE := True;
10053 Check_Components (First_Entity (E));
10055 -- Protected types must not have entries, and components must meet
10056 -- same set of rules as for record components.
10058 elsif Is_Protected_Type (E) then
10059 if Has_Entries (E) then
10060 Has_PE := False;
10061 else
10062 Has_PE := True;
10063 Check_Components (First_Entity (E));
10064 Check_Components (First_Private_Entity (E));
10065 end if;
10067 -- Type System.Address always has preelaborable initialization
10069 elsif Is_RTE (E, RE_Address) then
10070 Has_PE := True;
10072 -- In all other cases, type does not have preelaborable initialization
10074 else
10075 return False;
10076 end if;
10078 -- If type has preelaborable initialization, cache result
10080 if Has_PE then
10081 Set_Known_To_Have_Preelab_Init (E);
10082 end if;
10084 return Has_PE;
10085 end Has_Preelaborable_Initialization;
10087 ---------------------------
10088 -- Has_Private_Component --
10089 ---------------------------
10091 function Has_Private_Component (Type_Id : Entity_Id) return Boolean is
10092 Btype : Entity_Id := Base_Type (Type_Id);
10093 Component : Entity_Id;
10095 begin
10096 if Error_Posted (Type_Id)
10097 or else Error_Posted (Btype)
10098 then
10099 return False;
10100 end if;
10102 if Is_Class_Wide_Type (Btype) then
10103 Btype := Root_Type (Btype);
10104 end if;
10106 if Is_Private_Type (Btype) then
10107 declare
10108 UT : constant Entity_Id := Underlying_Type (Btype);
10109 begin
10110 if No (UT) then
10111 if No (Full_View (Btype)) then
10112 return not Is_Generic_Type (Btype)
10113 and then
10114 not Is_Generic_Type (Root_Type (Btype));
10115 else
10116 return not Is_Generic_Type (Root_Type (Full_View (Btype)));
10117 end if;
10118 else
10119 return not Is_Frozen (UT) and then Has_Private_Component (UT);
10120 end if;
10121 end;
10123 elsif Is_Array_Type (Btype) then
10124 return Has_Private_Component (Component_Type (Btype));
10126 elsif Is_Record_Type (Btype) then
10127 Component := First_Component (Btype);
10128 while Present (Component) loop
10129 if Has_Private_Component (Etype (Component)) then
10130 return True;
10131 end if;
10133 Next_Component (Component);
10134 end loop;
10136 return False;
10138 elsif Is_Protected_Type (Btype)
10139 and then Present (Corresponding_Record_Type (Btype))
10140 then
10141 return Has_Private_Component (Corresponding_Record_Type (Btype));
10143 else
10144 return False;
10145 end if;
10146 end Has_Private_Component;
10148 ----------------------
10149 -- Has_Signed_Zeros --
10150 ----------------------
10152 function Has_Signed_Zeros (E : Entity_Id) return Boolean is
10153 begin
10154 return Is_Floating_Point_Type (E) and then Signed_Zeros_On_Target;
10155 end Has_Signed_Zeros;
10157 ------------------------------
10158 -- Has_Significant_Contract --
10159 ------------------------------
10161 function Has_Significant_Contract (Subp_Id : Entity_Id) return Boolean is
10162 Subp_Nam : constant Name_Id := Chars (Subp_Id);
10164 begin
10165 -- _Finalizer procedure
10167 if Subp_Nam = Name_uFinalizer then
10168 return False;
10170 -- _Postconditions procedure
10172 elsif Subp_Nam = Name_uPostconditions then
10173 return False;
10175 -- Predicate function
10177 elsif Ekind (Subp_Id) = E_Function
10178 and then Is_Predicate_Function (Subp_Id)
10179 then
10180 return False;
10182 -- TSS subprogram
10184 elsif Get_TSS_Name (Subp_Id) /= TSS_Null then
10185 return False;
10187 else
10188 return True;
10189 end if;
10190 end Has_Significant_Contract;
10192 -----------------------------
10193 -- Has_Static_Array_Bounds --
10194 -----------------------------
10196 function Has_Static_Array_Bounds (Typ : Node_Id) return Boolean is
10197 Ndims : constant Nat := Number_Dimensions (Typ);
10199 Index : Node_Id;
10200 Low : Node_Id;
10201 High : Node_Id;
10203 begin
10204 -- Unconstrained types do not have static bounds
10206 if not Is_Constrained (Typ) then
10207 return False;
10208 end if;
10210 -- First treat string literals specially, as the lower bound and length
10211 -- of string literals are not stored like those of arrays.
10213 -- A string literal always has static bounds
10215 if Ekind (Typ) = E_String_Literal_Subtype then
10216 return True;
10217 end if;
10219 -- Treat all dimensions in turn
10221 Index := First_Index (Typ);
10222 for Indx in 1 .. Ndims loop
10224 -- In case of an illegal index which is not a discrete type, return
10225 -- that the type is not static.
10227 if not Is_Discrete_Type (Etype (Index))
10228 or else Etype (Index) = Any_Type
10229 then
10230 return False;
10231 end if;
10233 Get_Index_Bounds (Index, Low, High);
10235 if Error_Posted (Low) or else Error_Posted (High) then
10236 return False;
10237 end if;
10239 if Is_OK_Static_Expression (Low)
10240 and then
10241 Is_OK_Static_Expression (High)
10242 then
10243 null;
10244 else
10245 return False;
10246 end if;
10248 Next (Index);
10249 end loop;
10251 -- If we fall through the loop, all indexes matched
10253 return True;
10254 end Has_Static_Array_Bounds;
10256 ----------------
10257 -- Has_Stream --
10258 ----------------
10260 function Has_Stream (T : Entity_Id) return Boolean is
10261 E : Entity_Id;
10263 begin
10264 if No (T) then
10265 return False;
10267 elsif Is_RTE (Root_Type (T), RE_Root_Stream_Type) then
10268 return True;
10270 elsif Is_Array_Type (T) then
10271 return Has_Stream (Component_Type (T));
10273 elsif Is_Record_Type (T) then
10274 E := First_Component (T);
10275 while Present (E) loop
10276 if Has_Stream (Etype (E)) then
10277 return True;
10278 else
10279 Next_Component (E);
10280 end if;
10281 end loop;
10283 return False;
10285 elsif Is_Private_Type (T) then
10286 return Has_Stream (Underlying_Type (T));
10288 else
10289 return False;
10290 end if;
10291 end Has_Stream;
10293 ----------------
10294 -- Has_Suffix --
10295 ----------------
10297 function Has_Suffix (E : Entity_Id; Suffix : Character) return Boolean is
10298 begin
10299 Get_Name_String (Chars (E));
10300 return Name_Buffer (Name_Len) = Suffix;
10301 end Has_Suffix;
10303 ----------------
10304 -- Add_Suffix --
10305 ----------------
10307 function Add_Suffix (E : Entity_Id; Suffix : Character) return Name_Id is
10308 begin
10309 Get_Name_String (Chars (E));
10310 Add_Char_To_Name_Buffer (Suffix);
10311 return Name_Find;
10312 end Add_Suffix;
10314 -------------------
10315 -- Remove_Suffix --
10316 -------------------
10318 function Remove_Suffix (E : Entity_Id; Suffix : Character) return Name_Id is
10319 begin
10320 pragma Assert (Has_Suffix (E, Suffix));
10321 Get_Name_String (Chars (E));
10322 Name_Len := Name_Len - 1;
10323 return Name_Find;
10324 end Remove_Suffix;
10326 --------------------------
10327 -- Has_Tagged_Component --
10328 --------------------------
10330 function Has_Tagged_Component (Typ : Entity_Id) return Boolean is
10331 Comp : Entity_Id;
10333 begin
10334 if Is_Private_Type (Typ) and then Present (Underlying_Type (Typ)) then
10335 return Has_Tagged_Component (Underlying_Type (Typ));
10337 elsif Is_Array_Type (Typ) then
10338 return Has_Tagged_Component (Component_Type (Typ));
10340 elsif Is_Tagged_Type (Typ) then
10341 return True;
10343 elsif Is_Record_Type (Typ) then
10344 Comp := First_Component (Typ);
10345 while Present (Comp) loop
10346 if Has_Tagged_Component (Etype (Comp)) then
10347 return True;
10348 end if;
10350 Next_Component (Comp);
10351 end loop;
10353 return False;
10355 else
10356 return False;
10357 end if;
10358 end Has_Tagged_Component;
10360 -----------------------------
10361 -- Has_Undefined_Reference --
10362 -----------------------------
10364 function Has_Undefined_Reference (Expr : Node_Id) return Boolean is
10365 Has_Undef_Ref : Boolean := False;
10366 -- Flag set when expression Expr contains at least one undefined
10367 -- reference.
10369 function Is_Undefined_Reference (N : Node_Id) return Traverse_Result;
10370 -- Determine whether N denotes a reference and if it does, whether it is
10371 -- undefined.
10373 ----------------------------
10374 -- Is_Undefined_Reference --
10375 ----------------------------
10377 function Is_Undefined_Reference (N : Node_Id) return Traverse_Result is
10378 begin
10379 if Is_Entity_Name (N)
10380 and then Present (Entity (N))
10381 and then Entity (N) = Any_Id
10382 then
10383 Has_Undef_Ref := True;
10384 return Abandon;
10385 end if;
10387 return OK;
10388 end Is_Undefined_Reference;
10390 procedure Find_Undefined_References is
10391 new Traverse_Proc (Is_Undefined_Reference);
10393 -- Start of processing for Has_Undefined_Reference
10395 begin
10396 Find_Undefined_References (Expr);
10398 return Has_Undef_Ref;
10399 end Has_Undefined_Reference;
10401 ----------------------------
10402 -- Has_Volatile_Component --
10403 ----------------------------
10405 function Has_Volatile_Component (Typ : Entity_Id) return Boolean is
10406 Comp : Entity_Id;
10408 begin
10409 if Has_Volatile_Components (Typ) then
10410 return True;
10412 elsif Is_Array_Type (Typ) then
10413 return Is_Volatile (Component_Type (Typ));
10415 elsif Is_Record_Type (Typ) then
10416 Comp := First_Component (Typ);
10417 while Present (Comp) loop
10418 if Is_Volatile_Object (Comp) then
10419 return True;
10420 end if;
10422 Comp := Next_Component (Comp);
10423 end loop;
10424 end if;
10426 return False;
10427 end Has_Volatile_Component;
10429 -------------------------
10430 -- Implementation_Kind --
10431 -------------------------
10433 function Implementation_Kind (Subp : Entity_Id) return Name_Id is
10434 Impl_Prag : constant Node_Id := Get_Rep_Pragma (Subp, Name_Implemented);
10435 Arg : Node_Id;
10436 begin
10437 pragma Assert (Present (Impl_Prag));
10438 Arg := Last (Pragma_Argument_Associations (Impl_Prag));
10439 return Chars (Get_Pragma_Arg (Arg));
10440 end Implementation_Kind;
10442 --------------------------
10443 -- Implements_Interface --
10444 --------------------------
10446 function Implements_Interface
10447 (Typ_Ent : Entity_Id;
10448 Iface_Ent : Entity_Id;
10449 Exclude_Parents : Boolean := False) return Boolean
10451 Ifaces_List : Elist_Id;
10452 Elmt : Elmt_Id;
10453 Iface : Entity_Id := Base_Type (Iface_Ent);
10454 Typ : Entity_Id := Base_Type (Typ_Ent);
10456 begin
10457 if Is_Class_Wide_Type (Typ) then
10458 Typ := Root_Type (Typ);
10459 end if;
10461 if not Has_Interfaces (Typ) then
10462 return False;
10463 end if;
10465 if Is_Class_Wide_Type (Iface) then
10466 Iface := Root_Type (Iface);
10467 end if;
10469 Collect_Interfaces (Typ, Ifaces_List);
10471 Elmt := First_Elmt (Ifaces_List);
10472 while Present (Elmt) loop
10473 if Is_Ancestor (Node (Elmt), Typ, Use_Full_View => True)
10474 and then Exclude_Parents
10475 then
10476 null;
10478 elsif Node (Elmt) = Iface then
10479 return True;
10480 end if;
10482 Next_Elmt (Elmt);
10483 end loop;
10485 return False;
10486 end Implements_Interface;
10488 ------------------------------------
10489 -- In_Assertion_Expression_Pragma --
10490 ------------------------------------
10492 function In_Assertion_Expression_Pragma (N : Node_Id) return Boolean is
10493 Par : Node_Id;
10494 Prag : Node_Id := Empty;
10496 begin
10497 -- Climb the parent chain looking for an enclosing pragma
10499 Par := N;
10500 while Present (Par) loop
10501 if Nkind (Par) = N_Pragma then
10502 Prag := Par;
10503 exit;
10505 -- Precondition-like pragmas are expanded into if statements, check
10506 -- the original node instead.
10508 elsif Nkind (Original_Node (Par)) = N_Pragma then
10509 Prag := Original_Node (Par);
10510 exit;
10512 -- The expansion of attribute 'Old generates a constant to capture
10513 -- the result of the prefix. If the parent traversal reaches
10514 -- one of these constants, then the node technically came from a
10515 -- postcondition-like pragma. Note that the Ekind is not tested here
10516 -- because N may be the expression of an object declaration which is
10517 -- currently being analyzed. Such objects carry Ekind of E_Void.
10519 elsif Nkind (Par) = N_Object_Declaration
10520 and then Constant_Present (Par)
10521 and then Stores_Attribute_Old_Prefix (Defining_Entity (Par))
10522 then
10523 return True;
10525 -- Prevent the search from going too far
10527 elsif Is_Body_Or_Package_Declaration (Par) then
10528 return False;
10529 end if;
10531 Par := Parent (Par);
10532 end loop;
10534 return
10535 Present (Prag)
10536 and then Assertion_Expression_Pragma (Get_Pragma_Id (Prag));
10537 end In_Assertion_Expression_Pragma;
10539 -----------------
10540 -- In_Instance --
10541 -----------------
10543 function In_Instance return Boolean is
10544 Curr_Unit : constant Entity_Id := Cunit_Entity (Current_Sem_Unit);
10545 S : Entity_Id;
10547 begin
10548 S := Current_Scope;
10549 while Present (S) and then S /= Standard_Standard loop
10550 if Ekind_In (S, E_Function, E_Package, E_Procedure)
10551 and then Is_Generic_Instance (S)
10552 then
10553 -- A child instance is always compiled in the context of a parent
10554 -- instance. Nevertheless, the actuals are not analyzed in an
10555 -- instance context. We detect this case by examining the current
10556 -- compilation unit, which must be a child instance, and checking
10557 -- that it is not currently on the scope stack.
10559 if Is_Child_Unit (Curr_Unit)
10560 and then Nkind (Unit (Cunit (Current_Sem_Unit))) =
10561 N_Package_Instantiation
10562 and then not In_Open_Scopes (Curr_Unit)
10563 then
10564 return False;
10565 else
10566 return True;
10567 end if;
10568 end if;
10570 S := Scope (S);
10571 end loop;
10573 return False;
10574 end In_Instance;
10576 ----------------------
10577 -- In_Instance_Body --
10578 ----------------------
10580 function In_Instance_Body return Boolean is
10581 S : Entity_Id;
10583 begin
10584 S := Current_Scope;
10585 while Present (S) and then S /= Standard_Standard loop
10586 if Ekind_In (S, E_Function, E_Procedure)
10587 and then Is_Generic_Instance (S)
10588 then
10589 return True;
10591 elsif Ekind (S) = E_Package
10592 and then In_Package_Body (S)
10593 and then Is_Generic_Instance (S)
10594 then
10595 return True;
10596 end if;
10598 S := Scope (S);
10599 end loop;
10601 return False;
10602 end In_Instance_Body;
10604 -----------------------------
10605 -- In_Instance_Not_Visible --
10606 -----------------------------
10608 function In_Instance_Not_Visible return Boolean is
10609 S : Entity_Id;
10611 begin
10612 S := Current_Scope;
10613 while Present (S) and then S /= Standard_Standard loop
10614 if Ekind_In (S, E_Function, E_Procedure)
10615 and then Is_Generic_Instance (S)
10616 then
10617 return True;
10619 elsif Ekind (S) = E_Package
10620 and then (In_Package_Body (S) or else In_Private_Part (S))
10621 and then Is_Generic_Instance (S)
10622 then
10623 return True;
10624 end if;
10626 S := Scope (S);
10627 end loop;
10629 return False;
10630 end In_Instance_Not_Visible;
10632 ------------------------------
10633 -- In_Instance_Visible_Part --
10634 ------------------------------
10636 function In_Instance_Visible_Part return Boolean is
10637 S : Entity_Id;
10639 begin
10640 S := Current_Scope;
10641 while Present (S) and then S /= Standard_Standard loop
10642 if Ekind (S) = E_Package
10643 and then Is_Generic_Instance (S)
10644 and then not In_Package_Body (S)
10645 and then not In_Private_Part (S)
10646 then
10647 return True;
10648 end if;
10650 S := Scope (S);
10651 end loop;
10653 return False;
10654 end In_Instance_Visible_Part;
10656 ---------------------
10657 -- In_Package_Body --
10658 ---------------------
10660 function In_Package_Body return Boolean is
10661 S : Entity_Id;
10663 begin
10664 S := Current_Scope;
10665 while Present (S) and then S /= Standard_Standard loop
10666 if Ekind (S) = E_Package and then In_Package_Body (S) then
10667 return True;
10668 else
10669 S := Scope (S);
10670 end if;
10671 end loop;
10673 return False;
10674 end In_Package_Body;
10676 --------------------------------
10677 -- In_Parameter_Specification --
10678 --------------------------------
10680 function In_Parameter_Specification (N : Node_Id) return Boolean is
10681 PN : Node_Id;
10683 begin
10684 PN := Parent (N);
10685 while Present (PN) loop
10686 if Nkind (PN) = N_Parameter_Specification then
10687 return True;
10688 end if;
10690 PN := Parent (PN);
10691 end loop;
10693 return False;
10694 end In_Parameter_Specification;
10696 --------------------------
10697 -- In_Pragma_Expression --
10698 --------------------------
10700 function In_Pragma_Expression (N : Node_Id; Nam : Name_Id) return Boolean is
10701 P : Node_Id;
10702 begin
10703 P := Parent (N);
10704 loop
10705 if No (P) then
10706 return False;
10707 elsif Nkind (P) = N_Pragma and then Pragma_Name (P) = Nam then
10708 return True;
10709 else
10710 P := Parent (P);
10711 end if;
10712 end loop;
10713 end In_Pragma_Expression;
10715 ---------------------------
10716 -- In_Pre_Post_Condition --
10717 ---------------------------
10719 function In_Pre_Post_Condition (N : Node_Id) return Boolean is
10720 Par : Node_Id;
10721 Prag : Node_Id := Empty;
10722 Prag_Id : Pragma_Id;
10724 begin
10725 -- Climb the parent chain looking for an enclosing pragma
10727 Par := N;
10728 while Present (Par) loop
10729 if Nkind (Par) = N_Pragma then
10730 Prag := Par;
10731 exit;
10733 -- Prevent the search from going too far
10735 elsif Is_Body_Or_Package_Declaration (Par) then
10736 exit;
10737 end if;
10739 Par := Parent (Par);
10740 end loop;
10742 if Present (Prag) then
10743 Prag_Id := Get_Pragma_Id (Prag);
10745 return
10746 Prag_Id = Pragma_Post
10747 or else Prag_Id = Pragma_Post_Class
10748 or else Prag_Id = Pragma_Postcondition
10749 or else Prag_Id = Pragma_Pre
10750 or else Prag_Id = Pragma_Pre_Class
10751 or else Prag_Id = Pragma_Precondition;
10753 -- Otherwise the node is not enclosed by a pre/postcondition pragma
10755 else
10756 return False;
10757 end if;
10758 end In_Pre_Post_Condition;
10760 -------------------------------------
10761 -- In_Reverse_Storage_Order_Object --
10762 -------------------------------------
10764 function In_Reverse_Storage_Order_Object (N : Node_Id) return Boolean is
10765 Pref : Node_Id;
10766 Btyp : Entity_Id := Empty;
10768 begin
10769 -- Climb up indexed components
10771 Pref := N;
10772 loop
10773 case Nkind (Pref) is
10774 when N_Selected_Component =>
10775 Pref := Prefix (Pref);
10776 exit;
10778 when N_Indexed_Component =>
10779 Pref := Prefix (Pref);
10781 when others =>
10782 Pref := Empty;
10783 exit;
10784 end case;
10785 end loop;
10787 if Present (Pref) then
10788 Btyp := Base_Type (Etype (Pref));
10789 end if;
10791 return Present (Btyp)
10792 and then (Is_Record_Type (Btyp) or else Is_Array_Type (Btyp))
10793 and then Reverse_Storage_Order (Btyp);
10794 end In_Reverse_Storage_Order_Object;
10796 --------------------------------------
10797 -- In_Subprogram_Or_Concurrent_Unit --
10798 --------------------------------------
10800 function In_Subprogram_Or_Concurrent_Unit return Boolean is
10801 E : Entity_Id;
10802 K : Entity_Kind;
10804 begin
10805 -- Use scope chain to check successively outer scopes
10807 E := Current_Scope;
10808 loop
10809 K := Ekind (E);
10811 if K in Subprogram_Kind
10812 or else K in Concurrent_Kind
10813 or else K in Generic_Subprogram_Kind
10814 then
10815 return True;
10817 elsif E = Standard_Standard then
10818 return False;
10819 end if;
10821 E := Scope (E);
10822 end loop;
10823 end In_Subprogram_Or_Concurrent_Unit;
10825 ---------------------
10826 -- In_Visible_Part --
10827 ---------------------
10829 function In_Visible_Part (Scope_Id : Entity_Id) return Boolean is
10830 begin
10831 return Is_Package_Or_Generic_Package (Scope_Id)
10832 and then In_Open_Scopes (Scope_Id)
10833 and then not In_Package_Body (Scope_Id)
10834 and then not In_Private_Part (Scope_Id);
10835 end In_Visible_Part;
10837 --------------------------------
10838 -- Incomplete_Or_Partial_View --
10839 --------------------------------
10841 function Incomplete_Or_Partial_View (Id : Entity_Id) return Entity_Id is
10842 function Inspect_Decls
10843 (Decls : List_Id;
10844 Taft : Boolean := False) return Entity_Id;
10845 -- Check whether a declarative region contains the incomplete or partial
10846 -- view of Id.
10848 -------------------
10849 -- Inspect_Decls --
10850 -------------------
10852 function Inspect_Decls
10853 (Decls : List_Id;
10854 Taft : Boolean := False) return Entity_Id
10856 Decl : Node_Id;
10857 Match : Node_Id;
10859 begin
10860 Decl := First (Decls);
10861 while Present (Decl) loop
10862 Match := Empty;
10864 if Taft then
10865 if Nkind (Decl) = N_Incomplete_Type_Declaration then
10866 Match := Defining_Identifier (Decl);
10867 end if;
10869 else
10870 if Nkind_In (Decl, N_Private_Extension_Declaration,
10871 N_Private_Type_Declaration)
10872 then
10873 Match := Defining_Identifier (Decl);
10874 end if;
10875 end if;
10877 if Present (Match)
10878 and then Present (Full_View (Match))
10879 and then Full_View (Match) = Id
10880 then
10881 return Match;
10882 end if;
10884 Next (Decl);
10885 end loop;
10887 return Empty;
10888 end Inspect_Decls;
10890 -- Local variables
10892 Prev : Entity_Id;
10894 -- Start of processing for Incomplete_Or_Partial_View
10896 begin
10897 -- Deferred constant or incomplete type case
10899 Prev := Current_Entity_In_Scope (Id);
10901 if Present (Prev)
10902 and then (Is_Incomplete_Type (Prev) or else Ekind (Prev) = E_Constant)
10903 and then Present (Full_View (Prev))
10904 and then Full_View (Prev) = Id
10905 then
10906 return Prev;
10907 end if;
10909 -- Private or Taft amendment type case
10911 declare
10912 Pkg : constant Entity_Id := Scope (Id);
10913 Pkg_Decl : Node_Id := Pkg;
10915 begin
10916 if Present (Pkg) and then Ekind (Pkg) = E_Package then
10917 while Nkind (Pkg_Decl) /= N_Package_Specification loop
10918 Pkg_Decl := Parent (Pkg_Decl);
10919 end loop;
10921 -- It is knows that Typ has a private view, look for it in the
10922 -- visible declarations of the enclosing scope. A special case
10923 -- of this is when the two views have been exchanged - the full
10924 -- appears earlier than the private.
10926 if Has_Private_Declaration (Id) then
10927 Prev := Inspect_Decls (Visible_Declarations (Pkg_Decl));
10929 -- Exchanged view case, look in the private declarations
10931 if No (Prev) then
10932 Prev := Inspect_Decls (Private_Declarations (Pkg_Decl));
10933 end if;
10935 return Prev;
10937 -- Otherwise if this is the package body, then Typ is a potential
10938 -- Taft amendment type. The incomplete view should be located in
10939 -- the private declarations of the enclosing scope.
10941 elsif In_Package_Body (Pkg) then
10942 return Inspect_Decls (Private_Declarations (Pkg_Decl), True);
10943 end if;
10944 end if;
10945 end;
10947 -- The type has no incomplete or private view
10949 return Empty;
10950 end Incomplete_Or_Partial_View;
10952 -----------------------------------------
10953 -- Inherit_Default_Init_Cond_Procedure --
10954 -----------------------------------------
10956 procedure Inherit_Default_Init_Cond_Procedure (Typ : Entity_Id) is
10957 Par_Typ : constant Entity_Id := Etype (Typ);
10959 begin
10960 -- A derived type inherits the default initial condition procedure of
10961 -- its parent type.
10963 if No (Default_Init_Cond_Procedure (Typ)) then
10964 Set_Default_Init_Cond_Procedure
10965 (Typ, Default_Init_Cond_Procedure (Par_Typ));
10966 end if;
10967 end Inherit_Default_Init_Cond_Procedure;
10969 ----------------------------
10970 -- Inherit_Rep_Item_Chain --
10971 ----------------------------
10973 procedure Inherit_Rep_Item_Chain (Typ : Entity_Id; From_Typ : Entity_Id) is
10974 Item : Node_Id;
10975 Next_Item : Node_Id;
10977 begin
10978 -- There are several inheritance scenarios to consider depending on
10979 -- whether both types have rep item chains and whether the destination
10980 -- type already inherits part of the source type's rep item chain.
10982 -- 1) The source type lacks a rep item chain
10983 -- From_Typ ---> Empty
10985 -- Typ --------> Item (or Empty)
10987 -- In this case inheritance cannot take place because there are no items
10988 -- to inherit.
10990 -- 2) The destination type lacks a rep item chain
10991 -- From_Typ ---> Item ---> ...
10993 -- Typ --------> Empty
10995 -- Inheritance takes place by setting the First_Rep_Item of the
10996 -- destination type to the First_Rep_Item of the source type.
10997 -- From_Typ ---> Item ---> ...
10998 -- ^
10999 -- Typ -----------+
11001 -- 3.1) Both source and destination types have at least one rep item.
11002 -- The destination type does NOT inherit a rep item from the source
11003 -- type.
11004 -- From_Typ ---> Item ---> Item
11006 -- Typ --------> Item ---> Item
11008 -- Inheritance takes place by setting the Next_Rep_Item of the last item
11009 -- of the destination type to the First_Rep_Item of the source type.
11010 -- From_Typ -------------------> Item ---> Item
11011 -- ^
11012 -- Typ --------> Item ---> Item --+
11014 -- 3.2) Both source and destination types have at least one rep item.
11015 -- The destination type DOES inherit part of the rep item chain of the
11016 -- source type.
11017 -- From_Typ ---> Item ---> Item ---> Item
11018 -- ^
11019 -- Typ --------> Item ------+
11021 -- This rare case arises when the full view of a private extension must
11022 -- inherit the rep item chain from the full view of its parent type and
11023 -- the full view of the parent type contains extra rep items. Currently
11024 -- only invariants may lead to such form of inheritance.
11026 -- type From_Typ is tagged private
11027 -- with Type_Invariant'Class => Item_2;
11029 -- type Typ is new From_Typ with private
11030 -- with Type_Invariant => Item_4;
11032 -- At this point the rep item chains contain the following items
11034 -- From_Typ -----------> Item_2 ---> Item_3
11035 -- ^
11036 -- Typ --------> Item_4 --+
11038 -- The full views of both types may introduce extra invariants
11040 -- type From_Typ is tagged null record
11041 -- with Type_Invariant => Item_1;
11043 -- type Typ is new From_Typ with null record;
11045 -- The full view of Typ would have to inherit any new rep items added to
11046 -- the full view of From_Typ.
11048 -- From_Typ -----------> Item_1 ---> Item_2 ---> Item_3
11049 -- ^
11050 -- Typ --------> Item_4 --+
11052 -- To achieve this form of inheritance, the destination type must first
11053 -- sever the link between its own rep chain and that of the source type,
11054 -- then inheritance 3.1 takes place.
11056 -- Case 1: The source type lacks a rep item chain
11058 if No (First_Rep_Item (From_Typ)) then
11059 return;
11061 -- Case 2: The destination type lacks a rep item chain
11063 elsif No (First_Rep_Item (Typ)) then
11064 Set_First_Rep_Item (Typ, First_Rep_Item (From_Typ));
11066 -- Case 3: Both the source and destination types have at least one rep
11067 -- item. Traverse the rep item chain of the destination type to find the
11068 -- last rep item.
11070 else
11071 Item := Empty;
11072 Next_Item := First_Rep_Item (Typ);
11073 while Present (Next_Item) loop
11075 -- Detect a link between the destination type's rep chain and that
11076 -- of the source type. There are two possibilities:
11078 -- Variant 1
11079 -- Next_Item
11080 -- V
11081 -- From_Typ ---> Item_1 --->
11082 -- ^
11083 -- Typ -----------+
11085 -- Item is Empty
11087 -- Variant 2
11088 -- Next_Item
11089 -- V
11090 -- From_Typ ---> Item_1 ---> Item_2 --->
11091 -- ^
11092 -- Typ --------> Item_3 ------+
11093 -- ^
11094 -- Item
11096 if Has_Rep_Item (From_Typ, Next_Item) then
11097 exit;
11098 end if;
11100 Item := Next_Item;
11101 Next_Item := Next_Rep_Item (Next_Item);
11102 end loop;
11104 -- Inherit the source type's rep item chain
11106 if Present (Item) then
11107 Set_Next_Rep_Item (Item, First_Rep_Item (From_Typ));
11108 else
11109 Set_First_Rep_Item (Typ, First_Rep_Item (From_Typ));
11110 end if;
11111 end if;
11112 end Inherit_Rep_Item_Chain;
11114 ---------------------------------
11115 -- Insert_Explicit_Dereference --
11116 ---------------------------------
11118 procedure Insert_Explicit_Dereference (N : Node_Id) is
11119 New_Prefix : constant Node_Id := Relocate_Node (N);
11120 Ent : Entity_Id := Empty;
11121 Pref : Node_Id;
11122 I : Interp_Index;
11123 It : Interp;
11124 T : Entity_Id;
11126 begin
11127 Save_Interps (N, New_Prefix);
11129 Rewrite (N,
11130 Make_Explicit_Dereference (Sloc (Parent (N)),
11131 Prefix => New_Prefix));
11133 Set_Etype (N, Designated_Type (Etype (New_Prefix)));
11135 if Is_Overloaded (New_Prefix) then
11137 -- The dereference is also overloaded, and its interpretations are
11138 -- the designated types of the interpretations of the original node.
11140 Set_Etype (N, Any_Type);
11142 Get_First_Interp (New_Prefix, I, It);
11143 while Present (It.Nam) loop
11144 T := It.Typ;
11146 if Is_Access_Type (T) then
11147 Add_One_Interp (N, Designated_Type (T), Designated_Type (T));
11148 end if;
11150 Get_Next_Interp (I, It);
11151 end loop;
11153 End_Interp_List;
11155 else
11156 -- Prefix is unambiguous: mark the original prefix (which might
11157 -- Come_From_Source) as a reference, since the new (relocated) one
11158 -- won't be taken into account.
11160 if Is_Entity_Name (New_Prefix) then
11161 Ent := Entity (New_Prefix);
11162 Pref := New_Prefix;
11164 -- For a retrieval of a subcomponent of some composite object,
11165 -- retrieve the ultimate entity if there is one.
11167 elsif Nkind_In (New_Prefix, N_Selected_Component,
11168 N_Indexed_Component)
11169 then
11170 Pref := Prefix (New_Prefix);
11171 while Present (Pref)
11172 and then Nkind_In (Pref, N_Selected_Component,
11173 N_Indexed_Component)
11174 loop
11175 Pref := Prefix (Pref);
11176 end loop;
11178 if Present (Pref) and then Is_Entity_Name (Pref) then
11179 Ent := Entity (Pref);
11180 end if;
11181 end if;
11183 -- Place the reference on the entity node
11185 if Present (Ent) then
11186 Generate_Reference (Ent, Pref);
11187 end if;
11188 end if;
11189 end Insert_Explicit_Dereference;
11191 ------------------------------------------
11192 -- Inspect_Deferred_Constant_Completion --
11193 ------------------------------------------
11195 procedure Inspect_Deferred_Constant_Completion (Decls : List_Id) is
11196 Decl : Node_Id;
11198 begin
11199 Decl := First (Decls);
11200 while Present (Decl) loop
11202 -- Deferred constant signature
11204 if Nkind (Decl) = N_Object_Declaration
11205 and then Constant_Present (Decl)
11206 and then No (Expression (Decl))
11208 -- No need to check internally generated constants
11210 and then Comes_From_Source (Decl)
11212 -- The constant is not completed. A full object declaration or a
11213 -- pragma Import complete a deferred constant.
11215 and then not Has_Completion (Defining_Identifier (Decl))
11216 then
11217 Error_Msg_N
11218 ("constant declaration requires initialization expression",
11219 Defining_Identifier (Decl));
11220 end if;
11222 Decl := Next (Decl);
11223 end loop;
11224 end Inspect_Deferred_Constant_Completion;
11226 -----------------------------
11227 -- Install_Generic_Formals --
11228 -----------------------------
11230 procedure Install_Generic_Formals (Subp_Id : Entity_Id) is
11231 E : Entity_Id;
11233 begin
11234 pragma Assert (Is_Generic_Subprogram (Subp_Id));
11236 E := First_Entity (Subp_Id);
11237 while Present (E) loop
11238 Install_Entity (E);
11239 Next_Entity (E);
11240 end loop;
11241 end Install_Generic_Formals;
11243 -----------------------------
11244 -- Is_Actual_Out_Parameter --
11245 -----------------------------
11247 function Is_Actual_Out_Parameter (N : Node_Id) return Boolean is
11248 Formal : Entity_Id;
11249 Call : Node_Id;
11250 begin
11251 Find_Actual (N, Formal, Call);
11252 return Present (Formal) and then Ekind (Formal) = E_Out_Parameter;
11253 end Is_Actual_Out_Parameter;
11255 -------------------------
11256 -- Is_Actual_Parameter --
11257 -------------------------
11259 function Is_Actual_Parameter (N : Node_Id) return Boolean is
11260 PK : constant Node_Kind := Nkind (Parent (N));
11262 begin
11263 case PK is
11264 when N_Parameter_Association =>
11265 return N = Explicit_Actual_Parameter (Parent (N));
11267 when N_Subprogram_Call =>
11268 return Is_List_Member (N)
11269 and then
11270 List_Containing (N) = Parameter_Associations (Parent (N));
11272 when others =>
11273 return False;
11274 end case;
11275 end Is_Actual_Parameter;
11277 --------------------------------
11278 -- Is_Actual_Tagged_Parameter --
11279 --------------------------------
11281 function Is_Actual_Tagged_Parameter (N : Node_Id) return Boolean is
11282 Formal : Entity_Id;
11283 Call : Node_Id;
11284 begin
11285 Find_Actual (N, Formal, Call);
11286 return Present (Formal) and then Is_Tagged_Type (Etype (Formal));
11287 end Is_Actual_Tagged_Parameter;
11289 ---------------------
11290 -- Is_Aliased_View --
11291 ---------------------
11293 function Is_Aliased_View (Obj : Node_Id) return Boolean is
11294 E : Entity_Id;
11296 begin
11297 if Is_Entity_Name (Obj) then
11298 E := Entity (Obj);
11300 return
11301 (Is_Object (E)
11302 and then
11303 (Is_Aliased (E)
11304 or else (Present (Renamed_Object (E))
11305 and then Is_Aliased_View (Renamed_Object (E)))))
11307 or else ((Is_Formal (E)
11308 or else Ekind_In (E, E_Generic_In_Out_Parameter,
11309 E_Generic_In_Parameter))
11310 and then Is_Tagged_Type (Etype (E)))
11312 or else (Is_Concurrent_Type (E) and then In_Open_Scopes (E))
11314 -- Current instance of type, either directly or as rewritten
11315 -- reference to the current object.
11317 or else (Is_Entity_Name (Original_Node (Obj))
11318 and then Present (Entity (Original_Node (Obj)))
11319 and then Is_Type (Entity (Original_Node (Obj))))
11321 or else (Is_Type (E) and then E = Current_Scope)
11323 or else (Is_Incomplete_Or_Private_Type (E)
11324 and then Full_View (E) = Current_Scope)
11326 -- Ada 2012 AI05-0053: the return object of an extended return
11327 -- statement is aliased if its type is immutably limited.
11329 or else (Is_Return_Object (E)
11330 and then Is_Limited_View (Etype (E)));
11332 elsif Nkind (Obj) = N_Selected_Component then
11333 return Is_Aliased (Entity (Selector_Name (Obj)));
11335 elsif Nkind (Obj) = N_Indexed_Component then
11336 return Has_Aliased_Components (Etype (Prefix (Obj)))
11337 or else
11338 (Is_Access_Type (Etype (Prefix (Obj)))
11339 and then Has_Aliased_Components
11340 (Designated_Type (Etype (Prefix (Obj)))));
11342 elsif Nkind_In (Obj, N_Unchecked_Type_Conversion, N_Type_Conversion) then
11343 return Is_Tagged_Type (Etype (Obj))
11344 and then Is_Aliased_View (Expression (Obj));
11346 elsif Nkind (Obj) = N_Explicit_Dereference then
11347 return Nkind (Original_Node (Obj)) /= N_Function_Call;
11349 else
11350 return False;
11351 end if;
11352 end Is_Aliased_View;
11354 -------------------------
11355 -- Is_Ancestor_Package --
11356 -------------------------
11358 function Is_Ancestor_Package
11359 (E1 : Entity_Id;
11360 E2 : Entity_Id) return Boolean
11362 Par : Entity_Id;
11364 begin
11365 Par := E2;
11366 while Present (Par) and then Par /= Standard_Standard loop
11367 if Par = E1 then
11368 return True;
11369 end if;
11371 Par := Scope (Par);
11372 end loop;
11374 return False;
11375 end Is_Ancestor_Package;
11377 ----------------------
11378 -- Is_Atomic_Object --
11379 ----------------------
11381 function Is_Atomic_Object (N : Node_Id) return Boolean is
11383 function Object_Has_Atomic_Components (N : Node_Id) return Boolean;
11384 -- Determines if given object has atomic components
11386 function Is_Atomic_Prefix (N : Node_Id) return Boolean;
11387 -- If prefix is an implicit dereference, examine designated type
11389 ----------------------
11390 -- Is_Atomic_Prefix --
11391 ----------------------
11393 function Is_Atomic_Prefix (N : Node_Id) return Boolean is
11394 begin
11395 if Is_Access_Type (Etype (N)) then
11396 return
11397 Has_Atomic_Components (Designated_Type (Etype (N)));
11398 else
11399 return Object_Has_Atomic_Components (N);
11400 end if;
11401 end Is_Atomic_Prefix;
11403 ----------------------------------
11404 -- Object_Has_Atomic_Components --
11405 ----------------------------------
11407 function Object_Has_Atomic_Components (N : Node_Id) return Boolean is
11408 begin
11409 if Has_Atomic_Components (Etype (N))
11410 or else Is_Atomic (Etype (N))
11411 then
11412 return True;
11414 elsif Is_Entity_Name (N)
11415 and then (Has_Atomic_Components (Entity (N))
11416 or else Is_Atomic (Entity (N)))
11417 then
11418 return True;
11420 elsif Nkind (N) = N_Selected_Component
11421 and then Is_Atomic (Entity (Selector_Name (N)))
11422 then
11423 return True;
11425 elsif Nkind (N) = N_Indexed_Component
11426 or else Nkind (N) = N_Selected_Component
11427 then
11428 return Is_Atomic_Prefix (Prefix (N));
11430 else
11431 return False;
11432 end if;
11433 end Object_Has_Atomic_Components;
11435 -- Start of processing for Is_Atomic_Object
11437 begin
11438 -- Predicate is not relevant to subprograms
11440 if Is_Entity_Name (N) and then Is_Overloadable (Entity (N)) then
11441 return False;
11443 elsif Is_Atomic (Etype (N))
11444 or else (Is_Entity_Name (N) and then Is_Atomic (Entity (N)))
11445 then
11446 return True;
11448 elsif Nkind (N) = N_Selected_Component
11449 and then Is_Atomic (Entity (Selector_Name (N)))
11450 then
11451 return True;
11453 elsif Nkind (N) = N_Indexed_Component
11454 or else Nkind (N) = N_Selected_Component
11455 then
11456 return Is_Atomic_Prefix (Prefix (N));
11458 else
11459 return False;
11460 end if;
11461 end Is_Atomic_Object;
11463 -----------------------------
11464 -- Is_Atomic_Or_VFA_Object --
11465 -----------------------------
11467 function Is_Atomic_Or_VFA_Object (N : Node_Id) return Boolean is
11468 begin
11469 return Is_Atomic_Object (N)
11470 or else (Is_Object_Reference (N)
11471 and then Is_Entity_Name (N)
11472 and then (Is_Volatile_Full_Access (Entity (N))
11473 or else
11474 Is_Volatile_Full_Access (Etype (Entity (N)))));
11475 end Is_Atomic_Or_VFA_Object;
11477 -------------------------
11478 -- Is_Attribute_Result --
11479 -------------------------
11481 function Is_Attribute_Result (N : Node_Id) return Boolean is
11482 begin
11483 return Nkind (N) = N_Attribute_Reference
11484 and then Attribute_Name (N) = Name_Result;
11485 end Is_Attribute_Result;
11487 -------------------------
11488 -- Is_Attribute_Update --
11489 -------------------------
11491 function Is_Attribute_Update (N : Node_Id) return Boolean is
11492 begin
11493 return Nkind (N) = N_Attribute_Reference
11494 and then Attribute_Name (N) = Name_Update;
11495 end Is_Attribute_Update;
11497 ------------------------------------
11498 -- Is_Body_Or_Package_Declaration --
11499 ------------------------------------
11501 function Is_Body_Or_Package_Declaration (N : Node_Id) return Boolean is
11502 begin
11503 return Nkind_In (N, N_Entry_Body,
11504 N_Package_Body,
11505 N_Package_Declaration,
11506 N_Protected_Body,
11507 N_Subprogram_Body,
11508 N_Task_Body);
11509 end Is_Body_Or_Package_Declaration;
11511 -----------------------
11512 -- Is_Bounded_String --
11513 -----------------------
11515 function Is_Bounded_String (T : Entity_Id) return Boolean is
11516 Under : constant Entity_Id := Underlying_Type (Root_Type (T));
11518 begin
11519 -- Check whether T is ultimately derived from Ada.Strings.Superbounded.
11520 -- Super_String, or one of the [Wide_]Wide_ versions. This will
11521 -- be True for all the Bounded_String types in instances of the
11522 -- Generic_Bounded_Length generics, and for types derived from those.
11524 return Present (Under)
11525 and then (Is_RTE (Root_Type (Under), RO_SU_Super_String) or else
11526 Is_RTE (Root_Type (Under), RO_WI_Super_String) or else
11527 Is_RTE (Root_Type (Under), RO_WW_Super_String));
11528 end Is_Bounded_String;
11530 -------------------------
11531 -- Is_Child_Or_Sibling --
11532 -------------------------
11534 function Is_Child_Or_Sibling
11535 (Pack_1 : Entity_Id;
11536 Pack_2 : Entity_Id) return Boolean
11538 function Distance_From_Standard (Pack : Entity_Id) return Nat;
11539 -- Given an arbitrary package, return the number of "climbs" necessary
11540 -- to reach scope Standard_Standard.
11542 procedure Equalize_Depths
11543 (Pack : in out Entity_Id;
11544 Depth : in out Nat;
11545 Depth_To_Reach : Nat);
11546 -- Given an arbitrary package, its depth and a target depth to reach,
11547 -- climb the scope chain until the said depth is reached. The pointer
11548 -- to the package and its depth a modified during the climb.
11550 ----------------------------
11551 -- Distance_From_Standard --
11552 ----------------------------
11554 function Distance_From_Standard (Pack : Entity_Id) return Nat is
11555 Dist : Nat;
11556 Scop : Entity_Id;
11558 begin
11559 Dist := 0;
11560 Scop := Pack;
11561 while Present (Scop) and then Scop /= Standard_Standard loop
11562 Dist := Dist + 1;
11563 Scop := Scope (Scop);
11564 end loop;
11566 return Dist;
11567 end Distance_From_Standard;
11569 ---------------------
11570 -- Equalize_Depths --
11571 ---------------------
11573 procedure Equalize_Depths
11574 (Pack : in out Entity_Id;
11575 Depth : in out Nat;
11576 Depth_To_Reach : Nat)
11578 begin
11579 -- The package must be at a greater or equal depth
11581 if Depth < Depth_To_Reach then
11582 raise Program_Error;
11583 end if;
11585 -- Climb the scope chain until the desired depth is reached
11587 while Present (Pack) and then Depth /= Depth_To_Reach loop
11588 Pack := Scope (Pack);
11589 Depth := Depth - 1;
11590 end loop;
11591 end Equalize_Depths;
11593 -- Local variables
11595 P_1 : Entity_Id := Pack_1;
11596 P_1_Child : Boolean := False;
11597 P_1_Depth : Nat := Distance_From_Standard (P_1);
11598 P_2 : Entity_Id := Pack_2;
11599 P_2_Child : Boolean := False;
11600 P_2_Depth : Nat := Distance_From_Standard (P_2);
11602 -- Start of processing for Is_Child_Or_Sibling
11604 begin
11605 pragma Assert
11606 (Ekind (Pack_1) = E_Package and then Ekind (Pack_2) = E_Package);
11608 -- Both packages denote the same entity, therefore they cannot be
11609 -- children or siblings.
11611 if P_1 = P_2 then
11612 return False;
11614 -- One of the packages is at a deeper level than the other. Note that
11615 -- both may still come from differen hierarchies.
11617 -- (root) P_2
11618 -- / \ :
11619 -- X P_2 or X
11620 -- : :
11621 -- P_1 P_1
11623 elsif P_1_Depth > P_2_Depth then
11624 Equalize_Depths
11625 (Pack => P_1,
11626 Depth => P_1_Depth,
11627 Depth_To_Reach => P_2_Depth);
11628 P_1_Child := True;
11630 -- (root) P_1
11631 -- / \ :
11632 -- P_1 X or X
11633 -- : :
11634 -- P_2 P_2
11636 elsif P_2_Depth > P_1_Depth then
11637 Equalize_Depths
11638 (Pack => P_2,
11639 Depth => P_2_Depth,
11640 Depth_To_Reach => P_1_Depth);
11641 P_2_Child := True;
11642 end if;
11644 -- At this stage the package pointers have been elevated to the same
11645 -- depth. If the related entities are the same, then one package is a
11646 -- potential child of the other:
11648 -- P_1
11649 -- :
11650 -- X became P_1 P_2 or vica versa
11651 -- :
11652 -- P_2
11654 if P_1 = P_2 then
11655 if P_1_Child then
11656 return Is_Child_Unit (Pack_1);
11658 else pragma Assert (P_2_Child);
11659 return Is_Child_Unit (Pack_2);
11660 end if;
11662 -- The packages may come from the same package chain or from entirely
11663 -- different hierarcies. To determine this, climb the scope stack until
11664 -- a common root is found.
11666 -- (root) (root 1) (root 2)
11667 -- / \ | |
11668 -- P_1 P_2 P_1 P_2
11670 else
11671 while Present (P_1) and then Present (P_2) loop
11673 -- The two packages may be siblings
11675 if P_1 = P_2 then
11676 return Is_Child_Unit (Pack_1) and then Is_Child_Unit (Pack_2);
11677 end if;
11679 P_1 := Scope (P_1);
11680 P_2 := Scope (P_2);
11681 end loop;
11682 end if;
11684 return False;
11685 end Is_Child_Or_Sibling;
11687 -----------------------------
11688 -- Is_Concurrent_Interface --
11689 -----------------------------
11691 function Is_Concurrent_Interface (T : Entity_Id) return Boolean is
11692 begin
11693 return Is_Interface (T)
11694 and then
11695 (Is_Protected_Interface (T)
11696 or else Is_Synchronized_Interface (T)
11697 or else Is_Task_Interface (T));
11698 end Is_Concurrent_Interface;
11700 -----------------------
11701 -- Is_Constant_Bound --
11702 -----------------------
11704 function Is_Constant_Bound (Exp : Node_Id) return Boolean is
11705 begin
11706 if Compile_Time_Known_Value (Exp) then
11707 return True;
11709 elsif Is_Entity_Name (Exp) and then Present (Entity (Exp)) then
11710 return Is_Constant_Object (Entity (Exp))
11711 or else Ekind (Entity (Exp)) = E_Enumeration_Literal;
11713 elsif Nkind (Exp) in N_Binary_Op then
11714 return Is_Constant_Bound (Left_Opnd (Exp))
11715 and then Is_Constant_Bound (Right_Opnd (Exp))
11716 and then Scope (Entity (Exp)) = Standard_Standard;
11718 else
11719 return False;
11720 end if;
11721 end Is_Constant_Bound;
11723 ---------------------------
11724 -- Is_Container_Element --
11725 ---------------------------
11727 function Is_Container_Element (Exp : Node_Id) return Boolean is
11728 Loc : constant Source_Ptr := Sloc (Exp);
11729 Pref : constant Node_Id := Prefix (Exp);
11731 Call : Node_Id;
11732 -- Call to an indexing aspect
11734 Cont_Typ : Entity_Id;
11735 -- The type of the container being accessed
11737 Elem_Typ : Entity_Id;
11738 -- Its element type
11740 Indexing : Entity_Id;
11741 Is_Const : Boolean;
11742 -- Indicates that constant indexing is used, and the element is thus
11743 -- a constant.
11745 Ref_Typ : Entity_Id;
11746 -- The reference type returned by the indexing operation
11748 begin
11749 -- If C is a container, in a context that imposes the element type of
11750 -- that container, the indexing notation C (X) is rewritten as:
11752 -- Indexing (C, X).Discr.all
11754 -- where Indexing is one of the indexing aspects of the container.
11755 -- If the context does not require a reference, the construct can be
11756 -- rewritten as
11758 -- Element (C, X)
11760 -- First, verify that the construct has the proper form
11762 if not Expander_Active then
11763 return False;
11765 elsif Nkind (Pref) /= N_Selected_Component then
11766 return False;
11768 elsif Nkind (Prefix (Pref)) /= N_Function_Call then
11769 return False;
11771 else
11772 Call := Prefix (Pref);
11773 Ref_Typ := Etype (Call);
11774 end if;
11776 if not Has_Implicit_Dereference (Ref_Typ)
11777 or else No (First (Parameter_Associations (Call)))
11778 or else not Is_Entity_Name (Name (Call))
11779 then
11780 return False;
11781 end if;
11783 -- Retrieve type of container object, and its iterator aspects
11785 Cont_Typ := Etype (First (Parameter_Associations (Call)));
11786 Indexing := Find_Value_Of_Aspect (Cont_Typ, Aspect_Constant_Indexing);
11787 Is_Const := False;
11789 if No (Indexing) then
11791 -- Container should have at least one indexing operation
11793 return False;
11795 elsif Entity (Name (Call)) /= Entity (Indexing) then
11797 -- This may be a variable indexing operation
11799 Indexing := Find_Value_Of_Aspect (Cont_Typ, Aspect_Variable_Indexing);
11801 if No (Indexing)
11802 or else Entity (Name (Call)) /= Entity (Indexing)
11803 then
11804 return False;
11805 end if;
11807 else
11808 Is_Const := True;
11809 end if;
11811 Elem_Typ := Find_Value_Of_Aspect (Cont_Typ, Aspect_Iterator_Element);
11813 if No (Elem_Typ) or else Entity (Elem_Typ) /= Etype (Exp) then
11814 return False;
11815 end if;
11817 -- Check that the expression is not the target of an assignment, in
11818 -- which case the rewriting is not possible.
11820 if not Is_Const then
11821 declare
11822 Par : Node_Id;
11824 begin
11825 Par := Exp;
11826 while Present (Par)
11827 loop
11828 if Nkind (Parent (Par)) = N_Assignment_Statement
11829 and then Par = Name (Parent (Par))
11830 then
11831 return False;
11833 -- A renaming produces a reference, and the transformation
11834 -- does not apply.
11836 elsif Nkind (Parent (Par)) = N_Object_Renaming_Declaration then
11837 return False;
11839 elsif Nkind_In
11840 (Nkind (Parent (Par)), N_Function_Call,
11841 N_Procedure_Call_Statement,
11842 N_Entry_Call_Statement)
11843 then
11844 -- Check that the element is not part of an actual for an
11845 -- in-out parameter.
11847 declare
11848 F : Entity_Id;
11849 A : Node_Id;
11851 begin
11852 F := First_Formal (Entity (Name (Parent (Par))));
11853 A := First (Parameter_Associations (Parent (Par)));
11854 while Present (F) loop
11855 if A = Par and then Ekind (F) /= E_In_Parameter then
11856 return False;
11857 end if;
11859 Next_Formal (F);
11860 Next (A);
11861 end loop;
11862 end;
11864 -- E_In_Parameter in a call: element is not modified.
11866 exit;
11867 end if;
11869 Par := Parent (Par);
11870 end loop;
11871 end;
11872 end if;
11874 -- The expression has the proper form and the context requires the
11875 -- element type. Retrieve the Element function of the container and
11876 -- rewrite the construct as a call to it.
11878 declare
11879 Op : Elmt_Id;
11881 begin
11882 Op := First_Elmt (Primitive_Operations (Cont_Typ));
11883 while Present (Op) loop
11884 exit when Chars (Node (Op)) = Name_Element;
11885 Next_Elmt (Op);
11886 end loop;
11888 if No (Op) then
11889 return False;
11891 else
11892 Rewrite (Exp,
11893 Make_Function_Call (Loc,
11894 Name => New_Occurrence_Of (Node (Op), Loc),
11895 Parameter_Associations => Parameter_Associations (Call)));
11896 Analyze_And_Resolve (Exp, Entity (Elem_Typ));
11897 return True;
11898 end if;
11899 end;
11900 end Is_Container_Element;
11902 ----------------------------
11903 -- Is_Contract_Annotation --
11904 ----------------------------
11906 function Is_Contract_Annotation (Item : Node_Id) return Boolean is
11907 begin
11908 return Is_Package_Contract_Annotation (Item)
11909 or else
11910 Is_Subprogram_Contract_Annotation (Item);
11911 end Is_Contract_Annotation;
11913 --------------------------------------
11914 -- Is_Controlling_Limited_Procedure --
11915 --------------------------------------
11917 function Is_Controlling_Limited_Procedure
11918 (Proc_Nam : Entity_Id) return Boolean
11920 Param_Typ : Entity_Id := Empty;
11922 begin
11923 if Ekind (Proc_Nam) = E_Procedure
11924 and then Present (Parameter_Specifications (Parent (Proc_Nam)))
11925 then
11926 Param_Typ := Etype (Parameter_Type (First (
11927 Parameter_Specifications (Parent (Proc_Nam)))));
11929 -- In this case where an Itype was created, the procedure call has been
11930 -- rewritten.
11932 elsif Present (Associated_Node_For_Itype (Proc_Nam))
11933 and then Present (Original_Node (Associated_Node_For_Itype (Proc_Nam)))
11934 and then
11935 Present (Parameter_Associations
11936 (Associated_Node_For_Itype (Proc_Nam)))
11937 then
11938 Param_Typ :=
11939 Etype (First (Parameter_Associations
11940 (Associated_Node_For_Itype (Proc_Nam))));
11941 end if;
11943 if Present (Param_Typ) then
11944 return
11945 Is_Interface (Param_Typ)
11946 and then Is_Limited_Record (Param_Typ);
11947 end if;
11949 return False;
11950 end Is_Controlling_Limited_Procedure;
11952 -----------------------------
11953 -- Is_CPP_Constructor_Call --
11954 -----------------------------
11956 function Is_CPP_Constructor_Call (N : Node_Id) return Boolean is
11957 begin
11958 return Nkind (N) = N_Function_Call
11959 and then Is_CPP_Class (Etype (Etype (N)))
11960 and then Is_Constructor (Entity (Name (N)))
11961 and then Is_Imported (Entity (Name (N)));
11962 end Is_CPP_Constructor_Call;
11964 -------------------------
11965 -- Is_Current_Instance --
11966 -------------------------
11968 function Is_Current_Instance (N : Node_Id) return Boolean is
11969 Typ : constant Entity_Id := Entity (N);
11970 P : Node_Id;
11972 begin
11973 -- Simplest case: entity is a concurrent type and we are currently
11974 -- inside the body. This will eventually be expanded into a
11975 -- call to Self (for tasks) or _object (for protected objects).
11977 if Is_Concurrent_Type (Typ) and then In_Open_Scopes (Typ) then
11978 return True;
11980 else
11981 -- Check whether the context is a (sub)type declaration for the
11982 -- type entity.
11984 P := Parent (N);
11985 while Present (P) loop
11986 if Nkind_In (P, N_Full_Type_Declaration,
11987 N_Private_Type_Declaration,
11988 N_Subtype_Declaration)
11989 and then Comes_From_Source (P)
11990 and then Defining_Entity (P) = Typ
11991 then
11992 return True;
11994 -- A subtype name may appear in an aspect specification for a
11995 -- Predicate_Failure aspect, for which we do not construct a
11996 -- wrapper procedure. The subtype will be replaced by the
11997 -- expression being tested when the corresponding predicate
11998 -- check is expanded.
12000 elsif Nkind (P) = N_Aspect_Specification
12001 and then Nkind (Parent (P)) = N_Subtype_Declaration
12002 then
12003 return True;
12005 elsif Nkind (P) = N_Pragma
12006 and then
12007 Get_Pragma_Id (Pragma_Name (P)) = Pragma_Predicate_Failure
12008 then
12009 return True;
12010 end if;
12012 P := Parent (P);
12013 end loop;
12014 end if;
12016 -- In any other context this is not a current occurrence
12018 return False;
12019 end Is_Current_Instance;
12021 --------------------
12022 -- Is_Declaration --
12023 --------------------
12025 function Is_Declaration (N : Node_Id) return Boolean is
12026 begin
12027 case Nkind (N) is
12028 when N_Abstract_Subprogram_Declaration |
12029 N_Exception_Declaration |
12030 N_Exception_Renaming_Declaration |
12031 N_Full_Type_Declaration |
12032 N_Generic_Function_Renaming_Declaration |
12033 N_Generic_Package_Declaration |
12034 N_Generic_Package_Renaming_Declaration |
12035 N_Generic_Procedure_Renaming_Declaration |
12036 N_Generic_Subprogram_Declaration |
12037 N_Number_Declaration |
12038 N_Object_Declaration |
12039 N_Object_Renaming_Declaration |
12040 N_Package_Declaration |
12041 N_Package_Renaming_Declaration |
12042 N_Private_Extension_Declaration |
12043 N_Private_Type_Declaration |
12044 N_Subprogram_Declaration |
12045 N_Subprogram_Renaming_Declaration |
12046 N_Subtype_Declaration =>
12047 return True;
12049 when others =>
12050 return False;
12051 end case;
12052 end Is_Declaration;
12054 --------------------------------
12055 -- Is_Declared_Within_Variant --
12056 --------------------------------
12058 function Is_Declared_Within_Variant (Comp : Entity_Id) return Boolean is
12059 Comp_Decl : constant Node_Id := Parent (Comp);
12060 Comp_List : constant Node_Id := Parent (Comp_Decl);
12061 begin
12062 return Nkind (Parent (Comp_List)) = N_Variant;
12063 end Is_Declared_Within_Variant;
12065 ----------------------------------------------
12066 -- Is_Dependent_Component_Of_Mutable_Object --
12067 ----------------------------------------------
12069 function Is_Dependent_Component_Of_Mutable_Object
12070 (Object : Node_Id) return Boolean
12072 P : Node_Id;
12073 Prefix_Type : Entity_Id;
12074 P_Aliased : Boolean := False;
12075 Comp : Entity_Id;
12077 Deref : Node_Id := Object;
12078 -- Dereference node, in something like X.all.Y(2)
12080 -- Start of processing for Is_Dependent_Component_Of_Mutable_Object
12082 begin
12083 -- Find the dereference node if any
12085 while Nkind_In (Deref, N_Indexed_Component,
12086 N_Selected_Component,
12087 N_Slice)
12088 loop
12089 Deref := Prefix (Deref);
12090 end loop;
12092 -- Ada 2005: If we have a component or slice of a dereference,
12093 -- something like X.all.Y (2), and the type of X is access-to-constant,
12094 -- Is_Variable will return False, because it is indeed a constant
12095 -- view. But it might be a view of a variable object, so we want the
12096 -- following condition to be True in that case.
12098 if Is_Variable (Object)
12099 or else (Ada_Version >= Ada_2005
12100 and then Nkind (Deref) = N_Explicit_Dereference)
12101 then
12102 if Nkind (Object) = N_Selected_Component then
12103 P := Prefix (Object);
12104 Prefix_Type := Etype (P);
12106 if Is_Entity_Name (P) then
12107 if Ekind (Entity (P)) = E_Generic_In_Out_Parameter then
12108 Prefix_Type := Base_Type (Prefix_Type);
12109 end if;
12111 if Is_Aliased (Entity (P)) then
12112 P_Aliased := True;
12113 end if;
12115 -- A discriminant check on a selected component may be expanded
12116 -- into a dereference when removing side-effects. Recover the
12117 -- original node and its type, which may be unconstrained.
12119 elsif Nkind (P) = N_Explicit_Dereference
12120 and then not (Comes_From_Source (P))
12121 then
12122 P := Original_Node (P);
12123 Prefix_Type := Etype (P);
12125 else
12126 -- Check for prefix being an aliased component???
12128 null;
12130 end if;
12132 -- A heap object is constrained by its initial value
12134 -- Ada 2005 (AI-363): Always assume the object could be mutable in
12135 -- the dereferenced case, since the access value might denote an
12136 -- unconstrained aliased object, whereas in Ada 95 the designated
12137 -- object is guaranteed to be constrained. A worst-case assumption
12138 -- has to apply in Ada 2005 because we can't tell at compile
12139 -- time whether the object is "constrained by its initial value"
12140 -- (despite the fact that 3.10.2(26/2) and 8.5.1(5/2) are semantic
12141 -- rules (these rules are acknowledged to need fixing).
12143 if Ada_Version < Ada_2005 then
12144 if Is_Access_Type (Prefix_Type)
12145 or else Nkind (P) = N_Explicit_Dereference
12146 then
12147 return False;
12148 end if;
12150 else pragma Assert (Ada_Version >= Ada_2005);
12151 if Is_Access_Type (Prefix_Type) then
12153 -- If the access type is pool-specific, and there is no
12154 -- constrained partial view of the designated type, then the
12155 -- designated object is known to be constrained.
12157 if Ekind (Prefix_Type) = E_Access_Type
12158 and then not Object_Type_Has_Constrained_Partial_View
12159 (Typ => Designated_Type (Prefix_Type),
12160 Scop => Current_Scope)
12161 then
12162 return False;
12164 -- Otherwise (general access type, or there is a constrained
12165 -- partial view of the designated type), we need to check
12166 -- based on the designated type.
12168 else
12169 Prefix_Type := Designated_Type (Prefix_Type);
12170 end if;
12171 end if;
12172 end if;
12174 Comp :=
12175 Original_Record_Component (Entity (Selector_Name (Object)));
12177 -- As per AI-0017, the renaming is illegal in a generic body, even
12178 -- if the subtype is indefinite.
12180 -- Ada 2005 (AI-363): In Ada 2005 an aliased object can be mutable
12182 if not Is_Constrained (Prefix_Type)
12183 and then (Is_Definite_Subtype (Prefix_Type)
12184 or else
12185 (Is_Generic_Type (Prefix_Type)
12186 and then Ekind (Current_Scope) = E_Generic_Package
12187 and then In_Package_Body (Current_Scope)))
12189 and then (Is_Declared_Within_Variant (Comp)
12190 or else Has_Discriminant_Dependent_Constraint (Comp))
12191 and then (not P_Aliased or else Ada_Version >= Ada_2005)
12192 then
12193 return True;
12195 -- If the prefix is of an access type at this point, then we want
12196 -- to return False, rather than calling this function recursively
12197 -- on the access object (which itself might be a discriminant-
12198 -- dependent component of some other object, but that isn't
12199 -- relevant to checking the object passed to us). This avoids
12200 -- issuing wrong errors when compiling with -gnatc, where there
12201 -- can be implicit dereferences that have not been expanded.
12203 elsif Is_Access_Type (Etype (Prefix (Object))) then
12204 return False;
12206 else
12207 return
12208 Is_Dependent_Component_Of_Mutable_Object (Prefix (Object));
12209 end if;
12211 elsif Nkind (Object) = N_Indexed_Component
12212 or else Nkind (Object) = N_Slice
12213 then
12214 return Is_Dependent_Component_Of_Mutable_Object (Prefix (Object));
12216 -- A type conversion that Is_Variable is a view conversion:
12217 -- go back to the denoted object.
12219 elsif Nkind (Object) = N_Type_Conversion then
12220 return
12221 Is_Dependent_Component_Of_Mutable_Object (Expression (Object));
12222 end if;
12223 end if;
12225 return False;
12226 end Is_Dependent_Component_Of_Mutable_Object;
12228 ---------------------
12229 -- Is_Dereferenced --
12230 ---------------------
12232 function Is_Dereferenced (N : Node_Id) return Boolean is
12233 P : constant Node_Id := Parent (N);
12234 begin
12235 return Nkind_In (P, N_Selected_Component,
12236 N_Explicit_Dereference,
12237 N_Indexed_Component,
12238 N_Slice)
12239 and then Prefix (P) = N;
12240 end Is_Dereferenced;
12242 ----------------------
12243 -- Is_Descendant_Of --
12244 ----------------------
12246 function Is_Descendant_Of (T1 : Entity_Id; T2 : Entity_Id) return Boolean is
12247 T : Entity_Id;
12248 Etyp : Entity_Id;
12250 begin
12251 pragma Assert (Nkind (T1) in N_Entity);
12252 pragma Assert (Nkind (T2) in N_Entity);
12254 T := Base_Type (T1);
12256 -- Immediate return if the types match
12258 if T = T2 then
12259 return True;
12261 -- Comment needed here ???
12263 elsif Ekind (T) = E_Class_Wide_Type then
12264 return Etype (T) = T2;
12266 -- All other cases
12268 else
12269 loop
12270 Etyp := Etype (T);
12272 -- Done if we found the type we are looking for
12274 if Etyp = T2 then
12275 return True;
12277 -- Done if no more derivations to check
12279 elsif T = T1
12280 or else T = Etyp
12281 then
12282 return False;
12284 -- Following test catches error cases resulting from prev errors
12286 elsif No (Etyp) then
12287 return False;
12289 elsif Is_Private_Type (T) and then Etyp = Full_View (T) then
12290 return False;
12292 elsif Is_Private_Type (Etyp) and then Full_View (Etyp) = T then
12293 return False;
12294 end if;
12296 T := Base_Type (Etyp);
12297 end loop;
12298 end if;
12299 end Is_Descendant_Of;
12301 ----------------------------------------
12302 -- Is_Descendant_Of_Suspension_Object --
12303 ----------------------------------------
12305 function Is_Descendant_Of_Suspension_Object
12306 (Typ : Entity_Id) return Boolean
12308 Cur_Typ : Entity_Id;
12309 Par_Typ : Entity_Id;
12311 begin
12312 -- Climb the type derivation chain checking each parent type against
12313 -- Suspension_Object.
12315 Cur_Typ := Base_Type (Typ);
12316 while Present (Cur_Typ) loop
12317 Par_Typ := Etype (Cur_Typ);
12319 -- The current type is a match
12321 if Is_Suspension_Object (Cur_Typ) then
12322 return True;
12324 -- Stop the traversal once the root of the derivation chain has been
12325 -- reached. In that case the current type is its own base type.
12327 elsif Cur_Typ = Par_Typ then
12328 exit;
12329 end if;
12331 Cur_Typ := Base_Type (Par_Typ);
12332 end loop;
12334 return False;
12335 end Is_Descendant_Of_Suspension_Object;
12337 ---------------------------------------------
12338 -- Is_Double_Precision_Floating_Point_Type --
12339 ---------------------------------------------
12341 function Is_Double_Precision_Floating_Point_Type
12342 (E : Entity_Id) return Boolean is
12343 begin
12344 return Is_Floating_Point_Type (E)
12345 and then Machine_Radix_Value (E) = Uint_2
12346 and then Machine_Mantissa_Value (E) = UI_From_Int (53)
12347 and then Machine_Emax_Value (E) = Uint_2 ** Uint_10
12348 and then Machine_Emin_Value (E) = Uint_3 - (Uint_2 ** Uint_10);
12349 end Is_Double_Precision_Floating_Point_Type;
12351 -----------------------------
12352 -- Is_Effectively_Volatile --
12353 -----------------------------
12355 function Is_Effectively_Volatile (Id : Entity_Id) return Boolean is
12356 begin
12357 if Is_Type (Id) then
12359 -- An arbitrary type is effectively volatile when it is subject to
12360 -- pragma Atomic or Volatile.
12362 if Is_Volatile (Id) then
12363 return True;
12365 -- An array type is effectively volatile when it is subject to pragma
12366 -- Atomic_Components or Volatile_Components or its compolent type is
12367 -- effectively volatile.
12369 elsif Is_Array_Type (Id) then
12370 return
12371 Has_Volatile_Components (Id)
12372 or else
12373 Is_Effectively_Volatile (Component_Type (Base_Type (Id)));
12375 -- A protected type is always volatile
12377 elsif Is_Protected_Type (Id) then
12378 return True;
12380 -- A descendant of Ada.Synchronous_Task_Control.Suspension_Object is
12381 -- automatically volatile.
12383 elsif Is_Descendant_Of_Suspension_Object (Id) then
12384 return True;
12386 -- Otherwise the type is not effectively volatile
12388 else
12389 return False;
12390 end if;
12392 -- Otherwise Id denotes an object
12394 else
12395 return
12396 Is_Volatile (Id)
12397 or else Has_Volatile_Components (Id)
12398 or else Is_Effectively_Volatile (Etype (Id));
12399 end if;
12400 end Is_Effectively_Volatile;
12402 ------------------------------------
12403 -- Is_Effectively_Volatile_Object --
12404 ------------------------------------
12406 function Is_Effectively_Volatile_Object (N : Node_Id) return Boolean is
12407 begin
12408 if Is_Entity_Name (N) then
12409 return Is_Effectively_Volatile (Entity (N));
12411 elsif Nkind (N) = N_Expanded_Name then
12412 return Is_Effectively_Volatile (Entity (N));
12414 elsif Nkind (N) = N_Indexed_Component then
12415 return Is_Effectively_Volatile_Object (Prefix (N));
12417 elsif Nkind (N) = N_Selected_Component then
12418 return
12419 Is_Effectively_Volatile_Object (Prefix (N))
12420 or else
12421 Is_Effectively_Volatile_Object (Selector_Name (N));
12423 else
12424 return False;
12425 end if;
12426 end Is_Effectively_Volatile_Object;
12428 -------------------
12429 -- Is_Entry_Body --
12430 -------------------
12432 function Is_Entry_Body (Id : Entity_Id) return Boolean is
12433 begin
12434 return
12435 Ekind_In (Id, E_Entry, E_Entry_Family)
12436 and then Nkind (Unit_Declaration_Node (Id)) = N_Entry_Body;
12437 end Is_Entry_Body;
12439 --------------------------
12440 -- Is_Entry_Declaration --
12441 --------------------------
12443 function Is_Entry_Declaration (Id : Entity_Id) return Boolean is
12444 begin
12445 return
12446 Ekind_In (Id, E_Entry, E_Entry_Family)
12447 and then Nkind (Unit_Declaration_Node (Id)) = N_Entry_Declaration;
12448 end Is_Entry_Declaration;
12450 ------------------------------------
12451 -- Is_Expanded_Priority_Attribute --
12452 ------------------------------------
12454 function Is_Expanded_Priority_Attribute (E : Entity_Id) return Boolean is
12455 begin
12456 return
12457 Nkind (E) = N_Function_Call
12458 and then not Configurable_Run_Time_Mode
12459 and then (Entity (Name (E)) = RTE (RE_Get_Ceiling)
12460 or else Entity (Name (E)) = RTE (RO_PE_Get_Ceiling));
12461 end Is_Expanded_Priority_Attribute;
12463 ----------------------------
12464 -- Is_Expression_Function --
12465 ----------------------------
12467 function Is_Expression_Function (Subp : Entity_Id) return Boolean is
12468 begin
12469 if Ekind_In (Subp, E_Function, E_Subprogram_Body) then
12470 return
12471 Nkind (Original_Node (Unit_Declaration_Node (Subp))) =
12472 N_Expression_Function;
12473 else
12474 return False;
12475 end if;
12476 end Is_Expression_Function;
12478 ------------------------------------------
12479 -- Is_Expression_Function_Or_Completion --
12480 ------------------------------------------
12482 function Is_Expression_Function_Or_Completion
12483 (Subp : Entity_Id) return Boolean
12485 Subp_Decl : Node_Id;
12487 begin
12488 if Ekind (Subp) = E_Function then
12489 Subp_Decl := Unit_Declaration_Node (Subp);
12491 -- The function declaration is either an expression function or is
12492 -- completed by an expression function body.
12494 return
12495 Is_Expression_Function (Subp)
12496 or else (Nkind (Subp_Decl) = N_Subprogram_Declaration
12497 and then Present (Corresponding_Body (Subp_Decl))
12498 and then Is_Expression_Function
12499 (Corresponding_Body (Subp_Decl)));
12501 elsif Ekind (Subp) = E_Subprogram_Body then
12502 return Is_Expression_Function (Subp);
12504 else
12505 return False;
12506 end if;
12507 end Is_Expression_Function_Or_Completion;
12509 -----------------------
12510 -- Is_EVF_Expression --
12511 -----------------------
12513 function Is_EVF_Expression (N : Node_Id) return Boolean is
12514 Orig_N : constant Node_Id := Original_Node (N);
12515 Alt : Node_Id;
12516 Expr : Node_Id;
12517 Id : Entity_Id;
12519 begin
12520 -- Detect a reference to a formal parameter of a specific tagged type
12521 -- whose related subprogram is subject to pragma Expresions_Visible with
12522 -- value "False".
12524 if Is_Entity_Name (N) and then Present (Entity (N)) then
12525 Id := Entity (N);
12527 return
12528 Is_Formal (Id)
12529 and then Is_Specific_Tagged_Type (Etype (Id))
12530 and then Extensions_Visible_Status (Id) =
12531 Extensions_Visible_False;
12533 -- A case expression is an EVF expression when it contains at least one
12534 -- EVF dependent_expression. Note that a case expression may have been
12535 -- expanded, hence the use of Original_Node.
12537 elsif Nkind (Orig_N) = N_Case_Expression then
12538 Alt := First (Alternatives (Orig_N));
12539 while Present (Alt) loop
12540 if Is_EVF_Expression (Expression (Alt)) then
12541 return True;
12542 end if;
12544 Next (Alt);
12545 end loop;
12547 -- An if expression is an EVF expression when it contains at least one
12548 -- EVF dependent_expression. Note that an if expression may have been
12549 -- expanded, hence the use of Original_Node.
12551 elsif Nkind (Orig_N) = N_If_Expression then
12552 Expr := Next (First (Expressions (Orig_N)));
12553 while Present (Expr) loop
12554 if Is_EVF_Expression (Expr) then
12555 return True;
12556 end if;
12558 Next (Expr);
12559 end loop;
12561 -- A qualified expression or a type conversion is an EVF expression when
12562 -- its operand is an EVF expression.
12564 elsif Nkind_In (N, N_Qualified_Expression,
12565 N_Unchecked_Type_Conversion,
12566 N_Type_Conversion)
12567 then
12568 return Is_EVF_Expression (Expression (N));
12570 -- Attributes 'Loop_Entry, 'Old, and 'Update are EVF expressions when
12571 -- their prefix denotes an EVF expression.
12573 elsif Nkind (N) = N_Attribute_Reference
12574 and then Nam_In (Attribute_Name (N), Name_Loop_Entry,
12575 Name_Old,
12576 Name_Update)
12577 then
12578 return Is_EVF_Expression (Prefix (N));
12579 end if;
12581 return False;
12582 end Is_EVF_Expression;
12584 --------------
12585 -- Is_False --
12586 --------------
12588 function Is_False (U : Uint) return Boolean is
12589 begin
12590 return (U = 0);
12591 end Is_False;
12593 ---------------------------
12594 -- Is_Fixed_Model_Number --
12595 ---------------------------
12597 function Is_Fixed_Model_Number (U : Ureal; T : Entity_Id) return Boolean is
12598 S : constant Ureal := Small_Value (T);
12599 M : Urealp.Save_Mark;
12600 R : Boolean;
12601 begin
12602 M := Urealp.Mark;
12603 R := (U = UR_Trunc (U / S) * S);
12604 Urealp.Release (M);
12605 return R;
12606 end Is_Fixed_Model_Number;
12608 -------------------------------
12609 -- Is_Fully_Initialized_Type --
12610 -------------------------------
12612 function Is_Fully_Initialized_Type (Typ : Entity_Id) return Boolean is
12613 begin
12614 -- Scalar types
12616 if Is_Scalar_Type (Typ) then
12618 -- A scalar type with an aspect Default_Value is fully initialized
12620 -- Note: Iniitalize/Normalize_Scalars also ensure full initialization
12621 -- of a scalar type, but we don't take that into account here, since
12622 -- we don't want these to affect warnings.
12624 return Has_Default_Aspect (Typ);
12626 elsif Is_Access_Type (Typ) then
12627 return True;
12629 elsif Is_Array_Type (Typ) then
12630 if Is_Fully_Initialized_Type (Component_Type (Typ))
12631 or else (Ada_Version >= Ada_2012 and then Has_Default_Aspect (Typ))
12632 then
12633 return True;
12634 end if;
12636 -- An interesting case, if we have a constrained type one of whose
12637 -- bounds is known to be null, then there are no elements to be
12638 -- initialized, so all the elements are initialized.
12640 if Is_Constrained (Typ) then
12641 declare
12642 Indx : Node_Id;
12643 Indx_Typ : Entity_Id;
12644 Lbd, Hbd : Node_Id;
12646 begin
12647 Indx := First_Index (Typ);
12648 while Present (Indx) loop
12649 if Etype (Indx) = Any_Type then
12650 return False;
12652 -- If index is a range, use directly
12654 elsif Nkind (Indx) = N_Range then
12655 Lbd := Low_Bound (Indx);
12656 Hbd := High_Bound (Indx);
12658 else
12659 Indx_Typ := Etype (Indx);
12661 if Is_Private_Type (Indx_Typ) then
12662 Indx_Typ := Full_View (Indx_Typ);
12663 end if;
12665 if No (Indx_Typ) or else Etype (Indx_Typ) = Any_Type then
12666 return False;
12667 else
12668 Lbd := Type_Low_Bound (Indx_Typ);
12669 Hbd := Type_High_Bound (Indx_Typ);
12670 end if;
12671 end if;
12673 if Compile_Time_Known_Value (Lbd)
12674 and then
12675 Compile_Time_Known_Value (Hbd)
12676 then
12677 if Expr_Value (Hbd) < Expr_Value (Lbd) then
12678 return True;
12679 end if;
12680 end if;
12682 Next_Index (Indx);
12683 end loop;
12684 end;
12685 end if;
12687 -- If no null indexes, then type is not fully initialized
12689 return False;
12691 -- Record types
12693 elsif Is_Record_Type (Typ) then
12694 if Has_Discriminants (Typ)
12695 and then
12696 Present (Discriminant_Default_Value (First_Discriminant (Typ)))
12697 and then Is_Fully_Initialized_Variant (Typ)
12698 then
12699 return True;
12700 end if;
12702 -- We consider bounded string types to be fully initialized, because
12703 -- otherwise we get false alarms when the Data component is not
12704 -- default-initialized.
12706 if Is_Bounded_String (Typ) then
12707 return True;
12708 end if;
12710 -- Controlled records are considered to be fully initialized if
12711 -- there is a user defined Initialize routine. This may not be
12712 -- entirely correct, but as the spec notes, we are guessing here
12713 -- what is best from the point of view of issuing warnings.
12715 if Is_Controlled (Typ) then
12716 declare
12717 Utyp : constant Entity_Id := Underlying_Type (Typ);
12719 begin
12720 if Present (Utyp) then
12721 declare
12722 Init : constant Entity_Id :=
12723 (Find_Optional_Prim_Op
12724 (Underlying_Type (Typ), Name_Initialize));
12726 begin
12727 if Present (Init)
12728 and then Comes_From_Source (Init)
12729 and then not
12730 Is_Predefined_File_Name
12731 (File_Name (Get_Source_File_Index (Sloc (Init))))
12732 then
12733 return True;
12735 elsif Has_Null_Extension (Typ)
12736 and then
12737 Is_Fully_Initialized_Type
12738 (Etype (Base_Type (Typ)))
12739 then
12740 return True;
12741 end if;
12742 end;
12743 end if;
12744 end;
12745 end if;
12747 -- Otherwise see if all record components are initialized
12749 declare
12750 Ent : Entity_Id;
12752 begin
12753 Ent := First_Entity (Typ);
12754 while Present (Ent) loop
12755 if Ekind (Ent) = E_Component
12756 and then (No (Parent (Ent))
12757 or else No (Expression (Parent (Ent))))
12758 and then not Is_Fully_Initialized_Type (Etype (Ent))
12760 -- Special VM case for tag components, which need to be
12761 -- defined in this case, but are never initialized as VMs
12762 -- are using other dispatching mechanisms. Ignore this
12763 -- uninitialized case. Note that this applies both to the
12764 -- uTag entry and the main vtable pointer (CPP_Class case).
12766 and then (Tagged_Type_Expansion or else not Is_Tag (Ent))
12767 then
12768 return False;
12769 end if;
12771 Next_Entity (Ent);
12772 end loop;
12773 end;
12775 -- No uninitialized components, so type is fully initialized.
12776 -- Note that this catches the case of no components as well.
12778 return True;
12780 elsif Is_Concurrent_Type (Typ) then
12781 return True;
12783 elsif Is_Private_Type (Typ) then
12784 declare
12785 U : constant Entity_Id := Underlying_Type (Typ);
12787 begin
12788 if No (U) then
12789 return False;
12790 else
12791 return Is_Fully_Initialized_Type (U);
12792 end if;
12793 end;
12795 else
12796 return False;
12797 end if;
12798 end Is_Fully_Initialized_Type;
12800 ----------------------------------
12801 -- Is_Fully_Initialized_Variant --
12802 ----------------------------------
12804 function Is_Fully_Initialized_Variant (Typ : Entity_Id) return Boolean is
12805 Loc : constant Source_Ptr := Sloc (Typ);
12806 Constraints : constant List_Id := New_List;
12807 Components : constant Elist_Id := New_Elmt_List;
12808 Comp_Elmt : Elmt_Id;
12809 Comp_Id : Node_Id;
12810 Comp_List : Node_Id;
12811 Discr : Entity_Id;
12812 Discr_Val : Node_Id;
12814 Report_Errors : Boolean;
12815 pragma Warnings (Off, Report_Errors);
12817 begin
12818 if Serious_Errors_Detected > 0 then
12819 return False;
12820 end if;
12822 if Is_Record_Type (Typ)
12823 and then Nkind (Parent (Typ)) = N_Full_Type_Declaration
12824 and then Nkind (Type_Definition (Parent (Typ))) = N_Record_Definition
12825 then
12826 Comp_List := Component_List (Type_Definition (Parent (Typ)));
12828 Discr := First_Discriminant (Typ);
12829 while Present (Discr) loop
12830 if Nkind (Parent (Discr)) = N_Discriminant_Specification then
12831 Discr_Val := Expression (Parent (Discr));
12833 if Present (Discr_Val)
12834 and then Is_OK_Static_Expression (Discr_Val)
12835 then
12836 Append_To (Constraints,
12837 Make_Component_Association (Loc,
12838 Choices => New_List (New_Occurrence_Of (Discr, Loc)),
12839 Expression => New_Copy (Discr_Val)));
12840 else
12841 return False;
12842 end if;
12843 else
12844 return False;
12845 end if;
12847 Next_Discriminant (Discr);
12848 end loop;
12850 Gather_Components
12851 (Typ => Typ,
12852 Comp_List => Comp_List,
12853 Governed_By => Constraints,
12854 Into => Components,
12855 Report_Errors => Report_Errors);
12857 -- Check that each component present is fully initialized
12859 Comp_Elmt := First_Elmt (Components);
12860 while Present (Comp_Elmt) loop
12861 Comp_Id := Node (Comp_Elmt);
12863 if Ekind (Comp_Id) = E_Component
12864 and then (No (Parent (Comp_Id))
12865 or else No (Expression (Parent (Comp_Id))))
12866 and then not Is_Fully_Initialized_Type (Etype (Comp_Id))
12867 then
12868 return False;
12869 end if;
12871 Next_Elmt (Comp_Elmt);
12872 end loop;
12874 return True;
12876 elsif Is_Private_Type (Typ) then
12877 declare
12878 U : constant Entity_Id := Underlying_Type (Typ);
12880 begin
12881 if No (U) then
12882 return False;
12883 else
12884 return Is_Fully_Initialized_Variant (U);
12885 end if;
12886 end;
12888 else
12889 return False;
12890 end if;
12891 end Is_Fully_Initialized_Variant;
12893 ------------------------------------
12894 -- Is_Generic_Declaration_Or_Body --
12895 ------------------------------------
12897 function Is_Generic_Declaration_Or_Body (Decl : Node_Id) return Boolean is
12898 Spec_Decl : Node_Id;
12900 begin
12901 -- Package/subprogram body
12903 if Nkind_In (Decl, N_Package_Body, N_Subprogram_Body)
12904 and then Present (Corresponding_Spec (Decl))
12905 then
12906 Spec_Decl := Unit_Declaration_Node (Corresponding_Spec (Decl));
12908 -- Package/subprogram body stub
12910 elsif Nkind_In (Decl, N_Package_Body_Stub, N_Subprogram_Body_Stub)
12911 and then Present (Corresponding_Spec_Of_Stub (Decl))
12912 then
12913 Spec_Decl :=
12914 Unit_Declaration_Node (Corresponding_Spec_Of_Stub (Decl));
12916 -- All other cases
12918 else
12919 Spec_Decl := Decl;
12920 end if;
12922 -- Rather than inspecting the defining entity of the spec declaration,
12923 -- look at its Nkind. This takes care of the case where the analysis of
12924 -- a generic body modifies the Ekind of its spec to allow for recursive
12925 -- calls.
12927 return
12928 Nkind_In (Spec_Decl, N_Generic_Package_Declaration,
12929 N_Generic_Subprogram_Declaration);
12930 end Is_Generic_Declaration_Or_Body;
12932 ----------------------------
12933 -- Is_Inherited_Operation --
12934 ----------------------------
12936 function Is_Inherited_Operation (E : Entity_Id) return Boolean is
12937 pragma Assert (Is_Overloadable (E));
12938 Kind : constant Node_Kind := Nkind (Parent (E));
12939 begin
12940 return Kind = N_Full_Type_Declaration
12941 or else Kind = N_Private_Extension_Declaration
12942 or else Kind = N_Subtype_Declaration
12943 or else (Ekind (E) = E_Enumeration_Literal
12944 and then Is_Derived_Type (Etype (E)));
12945 end Is_Inherited_Operation;
12947 -------------------------------------
12948 -- Is_Inherited_Operation_For_Type --
12949 -------------------------------------
12951 function Is_Inherited_Operation_For_Type
12952 (E : Entity_Id;
12953 Typ : Entity_Id) return Boolean
12955 begin
12956 -- Check that the operation has been created by the type declaration
12958 return Is_Inherited_Operation (E)
12959 and then Defining_Identifier (Parent (E)) = Typ;
12960 end Is_Inherited_Operation_For_Type;
12962 -----------------
12963 -- Is_Iterator --
12964 -----------------
12966 function Is_Iterator (Typ : Entity_Id) return Boolean is
12967 function Denotes_Iterator (Iter_Typ : Entity_Id) return Boolean;
12968 -- Determine whether type Iter_Typ is a predefined forward or reversible
12969 -- iterator.
12971 ----------------------
12972 -- Denotes_Iterator --
12973 ----------------------
12975 function Denotes_Iterator (Iter_Typ : Entity_Id) return Boolean is
12976 begin
12977 -- Check that the name matches, and that the ultimate ancestor is in
12978 -- a predefined unit, i.e the one that declares iterator interfaces.
12980 return
12981 Nam_In (Chars (Iter_Typ), Name_Forward_Iterator,
12982 Name_Reversible_Iterator)
12983 and then Is_Predefined_File_Name
12984 (Unit_File_Name (Get_Source_Unit (Root_Type (Iter_Typ))));
12985 end Denotes_Iterator;
12987 -- Local variables
12989 Iface_Elmt : Elmt_Id;
12990 Ifaces : Elist_Id;
12992 -- Start of processing for Is_Iterator
12994 begin
12995 -- The type may be a subtype of a descendant of the proper instance of
12996 -- the predefined interface type, so we must use the root type of the
12997 -- given type. The same is done for Is_Reversible_Iterator.
12999 if Is_Class_Wide_Type (Typ)
13000 and then Denotes_Iterator (Root_Type (Typ))
13001 then
13002 return True;
13004 elsif not Is_Tagged_Type (Typ) or else not Is_Derived_Type (Typ) then
13005 return False;
13007 elsif Present (Find_Value_Of_Aspect (Typ, Aspect_Iterable)) then
13008 return True;
13010 else
13011 Collect_Interfaces (Typ, Ifaces);
13013 Iface_Elmt := First_Elmt (Ifaces);
13014 while Present (Iface_Elmt) loop
13015 if Denotes_Iterator (Node (Iface_Elmt)) then
13016 return True;
13017 end if;
13019 Next_Elmt (Iface_Elmt);
13020 end loop;
13022 return False;
13023 end if;
13024 end Is_Iterator;
13026 ----------------------------
13027 -- Is_Iterator_Over_Array --
13028 ----------------------------
13030 function Is_Iterator_Over_Array (N : Node_Id) return Boolean is
13031 Container : constant Node_Id := Name (N);
13032 Container_Typ : constant Entity_Id := Base_Type (Etype (Container));
13033 begin
13034 return Is_Array_Type (Container_Typ);
13035 end Is_Iterator_Over_Array;
13037 ------------
13038 -- Is_LHS --
13039 ------------
13041 -- We seem to have a lot of overlapping functions that do similar things
13042 -- (testing for left hand sides or lvalues???).
13044 function Is_LHS (N : Node_Id) return Is_LHS_Result is
13045 P : constant Node_Id := Parent (N);
13047 begin
13048 -- Return True if we are the left hand side of an assignment statement
13050 if Nkind (P) = N_Assignment_Statement then
13051 if Name (P) = N then
13052 return Yes;
13053 else
13054 return No;
13055 end if;
13057 -- Case of prefix of indexed or selected component or slice
13059 elsif Nkind_In (P, N_Indexed_Component, N_Selected_Component, N_Slice)
13060 and then N = Prefix (P)
13061 then
13062 -- Here we have the case where the parent P is N.Q or N(Q .. R).
13063 -- If P is an LHS, then N is also effectively an LHS, but there
13064 -- is an important exception. If N is of an access type, then
13065 -- what we really have is N.all.Q (or N.all(Q .. R)). In either
13066 -- case this makes N.all a left hand side but not N itself.
13068 -- If we don't know the type yet, this is the case where we return
13069 -- Unknown, since the answer depends on the type which is unknown.
13071 if No (Etype (N)) then
13072 return Unknown;
13074 -- We have an Etype set, so we can check it
13076 elsif Is_Access_Type (Etype (N)) then
13077 return No;
13079 -- OK, not access type case, so just test whole expression
13081 else
13082 return Is_LHS (P);
13083 end if;
13085 -- All other cases are not left hand sides
13087 else
13088 return No;
13089 end if;
13090 end Is_LHS;
13092 -----------------------------
13093 -- Is_Library_Level_Entity --
13094 -----------------------------
13096 function Is_Library_Level_Entity (E : Entity_Id) return Boolean is
13097 begin
13098 -- The following is a small optimization, and it also properly handles
13099 -- discriminals, which in task bodies might appear in expressions before
13100 -- the corresponding procedure has been created, and which therefore do
13101 -- not have an assigned scope.
13103 if Is_Formal (E) then
13104 return False;
13105 end if;
13107 -- Normal test is simply that the enclosing dynamic scope is Standard
13109 return Enclosing_Dynamic_Scope (E) = Standard_Standard;
13110 end Is_Library_Level_Entity;
13112 --------------------------------
13113 -- Is_Limited_Class_Wide_Type --
13114 --------------------------------
13116 function Is_Limited_Class_Wide_Type (Typ : Entity_Id) return Boolean is
13117 begin
13118 return
13119 Is_Class_Wide_Type (Typ)
13120 and then (Is_Limited_Type (Typ) or else From_Limited_With (Typ));
13121 end Is_Limited_Class_Wide_Type;
13123 ---------------------------------
13124 -- Is_Local_Variable_Reference --
13125 ---------------------------------
13127 function Is_Local_Variable_Reference (Expr : Node_Id) return Boolean is
13128 begin
13129 if not Is_Entity_Name (Expr) then
13130 return False;
13132 else
13133 declare
13134 Ent : constant Entity_Id := Entity (Expr);
13135 Sub : constant Entity_Id := Enclosing_Subprogram (Ent);
13136 begin
13137 if not Ekind_In (Ent, E_Variable, E_In_Out_Parameter) then
13138 return False;
13139 else
13140 return Present (Sub) and then Sub = Current_Subprogram;
13141 end if;
13142 end;
13143 end if;
13144 end Is_Local_Variable_Reference;
13146 -----------------------------------------------
13147 -- Is_Nontrivial_Default_Init_Cond_Procedure --
13148 -----------------------------------------------
13150 function Is_Nontrivial_Default_Init_Cond_Procedure
13151 (Id : Entity_Id) return Boolean
13153 Body_Decl : Node_Id;
13154 Stmt : Node_Id;
13156 begin
13157 if Ekind (Id) = E_Procedure
13158 and then Is_Default_Init_Cond_Procedure (Id)
13159 then
13160 Body_Decl :=
13161 Unit_Declaration_Node
13162 (Corresponding_Body (Unit_Declaration_Node (Id)));
13164 -- The body of the Default_Initial_Condition procedure must contain
13165 -- at least one statement, otherwise the generation of the subprogram
13166 -- body failed.
13168 pragma Assert (Present (Handled_Statement_Sequence (Body_Decl)));
13170 -- To qualify as nontrivial, the first statement of the procedure
13171 -- must be a check in the form of an if statement. If the original
13172 -- Default_Initial_Condition expression was folded, then the first
13173 -- statement is not a check.
13175 Stmt := First (Statements (Handled_Statement_Sequence (Body_Decl)));
13177 return
13178 Nkind (Stmt) = N_If_Statement
13179 and then Nkind (Original_Node (Stmt)) = N_Pragma;
13180 end if;
13182 return False;
13183 end Is_Nontrivial_Default_Init_Cond_Procedure;
13185 -------------------------
13186 -- Is_Null_Record_Type --
13187 -------------------------
13189 function Is_Null_Record_Type (T : Entity_Id) return Boolean is
13190 Decl : constant Node_Id := Parent (T);
13191 begin
13192 return Nkind (Decl) = N_Full_Type_Declaration
13193 and then Nkind (Type_Definition (Decl)) = N_Record_Definition
13194 and then
13195 (No (Component_List (Type_Definition (Decl)))
13196 or else Null_Present (Component_List (Type_Definition (Decl))));
13197 end Is_Null_Record_Type;
13199 -------------------------
13200 -- Is_Object_Reference --
13201 -------------------------
13203 function Is_Object_Reference (N : Node_Id) return Boolean is
13204 function Is_Internally_Generated_Renaming (N : Node_Id) return Boolean;
13205 -- Determine whether N is the name of an internally-generated renaming
13207 --------------------------------------
13208 -- Is_Internally_Generated_Renaming --
13209 --------------------------------------
13211 function Is_Internally_Generated_Renaming (N : Node_Id) return Boolean is
13212 P : Node_Id;
13214 begin
13215 P := N;
13216 while Present (P) loop
13217 if Nkind (P) = N_Object_Renaming_Declaration then
13218 return not Comes_From_Source (P);
13219 elsif Is_List_Member (P) then
13220 return False;
13221 end if;
13223 P := Parent (P);
13224 end loop;
13226 return False;
13227 end Is_Internally_Generated_Renaming;
13229 -- Start of processing for Is_Object_Reference
13231 begin
13232 if Is_Entity_Name (N) then
13233 return Present (Entity (N)) and then Is_Object (Entity (N));
13235 else
13236 case Nkind (N) is
13237 when N_Indexed_Component | N_Slice =>
13238 return
13239 Is_Object_Reference (Prefix (N))
13240 or else Is_Access_Type (Etype (Prefix (N)));
13242 -- In Ada 95, a function call is a constant object; a procedure
13243 -- call is not.
13245 when N_Function_Call =>
13246 return Etype (N) /= Standard_Void_Type;
13248 -- Attributes 'Input, 'Loop_Entry, 'Old, and 'Result produce
13249 -- objects.
13251 when N_Attribute_Reference =>
13252 return
13253 Nam_In (Attribute_Name (N), Name_Input,
13254 Name_Loop_Entry,
13255 Name_Old,
13256 Name_Result);
13258 when N_Selected_Component =>
13259 return
13260 Is_Object_Reference (Selector_Name (N))
13261 and then
13262 (Is_Object_Reference (Prefix (N))
13263 or else Is_Access_Type (Etype (Prefix (N))));
13265 when N_Explicit_Dereference =>
13266 return True;
13268 -- A view conversion of a tagged object is an object reference
13270 when N_Type_Conversion =>
13271 return Is_Tagged_Type (Etype (Subtype_Mark (N)))
13272 and then Is_Tagged_Type (Etype (Expression (N)))
13273 and then Is_Object_Reference (Expression (N));
13275 -- An unchecked type conversion is considered to be an object if
13276 -- the operand is an object (this construction arises only as a
13277 -- result of expansion activities).
13279 when N_Unchecked_Type_Conversion =>
13280 return True;
13282 -- Allow string literals to act as objects as long as they appear
13283 -- in internally-generated renamings. The expansion of iterators
13284 -- may generate such renamings when the range involves a string
13285 -- literal.
13287 when N_String_Literal =>
13288 return Is_Internally_Generated_Renaming (Parent (N));
13290 -- AI05-0003: In Ada 2012 a qualified expression is a name.
13291 -- This allows disambiguation of function calls and the use
13292 -- of aggregates in more contexts.
13294 when N_Qualified_Expression =>
13295 if Ada_Version < Ada_2012 then
13296 return False;
13297 else
13298 return Is_Object_Reference (Expression (N))
13299 or else Nkind (Expression (N)) = N_Aggregate;
13300 end if;
13302 when others =>
13303 return False;
13304 end case;
13305 end if;
13306 end Is_Object_Reference;
13308 -----------------------------------
13309 -- Is_OK_Variable_For_Out_Formal --
13310 -----------------------------------
13312 function Is_OK_Variable_For_Out_Formal (AV : Node_Id) return Boolean is
13313 begin
13314 Note_Possible_Modification (AV, Sure => True);
13316 -- We must reject parenthesized variable names. Comes_From_Source is
13317 -- checked because there are currently cases where the compiler violates
13318 -- this rule (e.g. passing a task object to its controlled Initialize
13319 -- routine). This should be properly documented in sinfo???
13321 if Paren_Count (AV) > 0 and then Comes_From_Source (AV) then
13322 return False;
13324 -- A variable is always allowed
13326 elsif Is_Variable (AV) then
13327 return True;
13329 -- Generalized indexing operations are rewritten as explicit
13330 -- dereferences, and it is only during resolution that we can
13331 -- check whether the context requires an access_to_variable type.
13333 elsif Nkind (AV) = N_Explicit_Dereference
13334 and then Ada_Version >= Ada_2012
13335 and then Nkind (Original_Node (AV)) = N_Indexed_Component
13336 and then Present (Etype (Original_Node (AV)))
13337 and then Has_Implicit_Dereference (Etype (Original_Node (AV)))
13338 then
13339 return not Is_Access_Constant (Etype (Prefix (AV)));
13341 -- Unchecked conversions are allowed only if they come from the
13342 -- generated code, which sometimes uses unchecked conversions for out
13343 -- parameters in cases where code generation is unaffected. We tell
13344 -- source unchecked conversions by seeing if they are rewrites of
13345 -- an original Unchecked_Conversion function call, or of an explicit
13346 -- conversion of a function call or an aggregate (as may happen in the
13347 -- expansion of a packed array aggregate).
13349 elsif Nkind (AV) = N_Unchecked_Type_Conversion then
13350 if Nkind_In (Original_Node (AV), N_Function_Call, N_Aggregate) then
13351 return False;
13353 elsif Comes_From_Source (AV)
13354 and then Nkind (Original_Node (Expression (AV))) = N_Function_Call
13355 then
13356 return False;
13358 elsif Nkind (Original_Node (AV)) = N_Type_Conversion then
13359 return Is_OK_Variable_For_Out_Formal (Expression (AV));
13361 else
13362 return True;
13363 end if;
13365 -- Normal type conversions are allowed if argument is a variable
13367 elsif Nkind (AV) = N_Type_Conversion then
13368 if Is_Variable (Expression (AV))
13369 and then Paren_Count (Expression (AV)) = 0
13370 then
13371 Note_Possible_Modification (Expression (AV), Sure => True);
13372 return True;
13374 -- We also allow a non-parenthesized expression that raises
13375 -- constraint error if it rewrites what used to be a variable
13377 elsif Raises_Constraint_Error (Expression (AV))
13378 and then Paren_Count (Expression (AV)) = 0
13379 and then Is_Variable (Original_Node (Expression (AV)))
13380 then
13381 return True;
13383 -- Type conversion of something other than a variable
13385 else
13386 return False;
13387 end if;
13389 -- If this node is rewritten, then test the original form, if that is
13390 -- OK, then we consider the rewritten node OK (for example, if the
13391 -- original node is a conversion, then Is_Variable will not be true
13392 -- but we still want to allow the conversion if it converts a variable).
13394 elsif Original_Node (AV) /= AV then
13396 -- In Ada 2012, the explicit dereference may be a rewritten call to a
13397 -- Reference function.
13399 if Ada_Version >= Ada_2012
13400 and then Nkind (Original_Node (AV)) = N_Function_Call
13401 and then
13402 Has_Implicit_Dereference (Etype (Name (Original_Node (AV))))
13403 then
13405 -- Check that this is not a constant reference.
13407 return not Is_Access_Constant (Etype (Prefix (AV)));
13409 elsif Has_Implicit_Dereference (Etype (Original_Node (AV))) then
13410 return
13411 not Is_Access_Constant (Etype
13412 (Get_Reference_Discriminant (Etype (Original_Node (AV)))));
13414 else
13415 return Is_OK_Variable_For_Out_Formal (Original_Node (AV));
13416 end if;
13418 -- All other non-variables are rejected
13420 else
13421 return False;
13422 end if;
13423 end Is_OK_Variable_For_Out_Formal;
13425 ----------------------------
13426 -- Is_OK_Volatile_Context --
13427 ----------------------------
13429 function Is_OK_Volatile_Context
13430 (Context : Node_Id;
13431 Obj_Ref : Node_Id) return Boolean
13433 function Is_Protected_Operation_Call (Nod : Node_Id) return Boolean;
13434 -- Determine whether an arbitrary node denotes a call to a protected
13435 -- entry, function, or procedure in prefixed form where the prefix is
13436 -- Obj_Ref.
13438 function Within_Check (Nod : Node_Id) return Boolean;
13439 -- Determine whether an arbitrary node appears in a check node
13441 function Within_Subprogram_Call (Nod : Node_Id) return Boolean;
13442 -- Determine whether an arbitrary node appears in an entry, function, or
13443 -- procedure call.
13445 function Within_Volatile_Function (Id : Entity_Id) return Boolean;
13446 -- Determine whether an arbitrary entity appears in a volatile function
13448 ---------------------------------
13449 -- Is_Protected_Operation_Call --
13450 ---------------------------------
13452 function Is_Protected_Operation_Call (Nod : Node_Id) return Boolean is
13453 Pref : Node_Id;
13454 Subp : Node_Id;
13456 begin
13457 -- A call to a protected operations retains its selected component
13458 -- form as opposed to other prefixed calls that are transformed in
13459 -- expanded names.
13461 if Nkind (Nod) = N_Selected_Component then
13462 Pref := Prefix (Nod);
13463 Subp := Selector_Name (Nod);
13465 return
13466 Pref = Obj_Ref
13467 and then Present (Etype (Pref))
13468 and then Is_Protected_Type (Etype (Pref))
13469 and then Is_Entity_Name (Subp)
13470 and then Present (Entity (Subp))
13471 and then Ekind_In (Entity (Subp), E_Entry,
13472 E_Entry_Family,
13473 E_Function,
13474 E_Procedure);
13475 else
13476 return False;
13477 end if;
13478 end Is_Protected_Operation_Call;
13480 ------------------
13481 -- Within_Check --
13482 ------------------
13484 function Within_Check (Nod : Node_Id) return Boolean is
13485 Par : Node_Id;
13487 begin
13488 -- Climb the parent chain looking for a check node
13490 Par := Nod;
13491 while Present (Par) loop
13492 if Nkind (Par) in N_Raise_xxx_Error then
13493 return True;
13495 -- Prevent the search from going too far
13497 elsif Is_Body_Or_Package_Declaration (Par) then
13498 exit;
13499 end if;
13501 Par := Parent (Par);
13502 end loop;
13504 return False;
13505 end Within_Check;
13507 ----------------------------
13508 -- Within_Subprogram_Call --
13509 ----------------------------
13511 function Within_Subprogram_Call (Nod : Node_Id) return Boolean is
13512 Par : Node_Id;
13514 begin
13515 -- Climb the parent chain looking for a function or procedure call
13517 Par := Nod;
13518 while Present (Par) loop
13519 if Nkind_In (Par, N_Entry_Call_Statement,
13520 N_Function_Call,
13521 N_Procedure_Call_Statement)
13522 then
13523 return True;
13525 -- Prevent the search from going too far
13527 elsif Is_Body_Or_Package_Declaration (Par) then
13528 exit;
13529 end if;
13531 Par := Parent (Par);
13532 end loop;
13534 return False;
13535 end Within_Subprogram_Call;
13537 ------------------------------
13538 -- Within_Volatile_Function --
13539 ------------------------------
13541 function Within_Volatile_Function (Id : Entity_Id) return Boolean is
13542 Func_Id : Entity_Id;
13544 begin
13545 -- Traverse the scope stack looking for a [generic] function
13547 Func_Id := Id;
13548 while Present (Func_Id) and then Func_Id /= Standard_Standard loop
13549 if Ekind_In (Func_Id, E_Function, E_Generic_Function) then
13550 return Is_Volatile_Function (Func_Id);
13551 end if;
13553 Func_Id := Scope (Func_Id);
13554 end loop;
13556 return False;
13557 end Within_Volatile_Function;
13559 -- Local variables
13561 Obj_Id : Entity_Id;
13563 -- Start of processing for Is_OK_Volatile_Context
13565 begin
13566 -- The volatile object appears on either side of an assignment
13568 if Nkind (Context) = N_Assignment_Statement then
13569 return True;
13571 -- The volatile object is part of the initialization expression of
13572 -- another object.
13574 elsif Nkind (Context) = N_Object_Declaration
13575 and then Present (Expression (Context))
13576 and then Expression (Context) = Obj_Ref
13577 then
13578 Obj_Id := Defining_Entity (Context);
13580 -- The volatile object acts as the initialization expression of an
13581 -- extended return statement. This is valid context as long as the
13582 -- function is volatile.
13584 if Is_Return_Object (Obj_Id) then
13585 return Within_Volatile_Function (Obj_Id);
13587 -- Otherwise this is a normal object initialization
13589 else
13590 return True;
13591 end if;
13593 -- The volatile object acts as the name of a renaming declaration
13595 elsif Nkind (Context) = N_Object_Renaming_Declaration
13596 and then Name (Context) = Obj_Ref
13597 then
13598 return True;
13600 -- The volatile object appears as an actual parameter in a call to an
13601 -- instance of Unchecked_Conversion whose result is renamed.
13603 elsif Nkind (Context) = N_Function_Call
13604 and then Is_Entity_Name (Name (Context))
13605 and then Is_Unchecked_Conversion_Instance (Entity (Name (Context)))
13606 and then Nkind (Parent (Context)) = N_Object_Renaming_Declaration
13607 then
13608 return True;
13610 -- The volatile object is actually the prefix in a protected entry,
13611 -- function, or procedure call.
13613 elsif Is_Protected_Operation_Call (Context) then
13614 return True;
13616 -- The volatile object appears as the expression of a simple return
13617 -- statement that applies to a volatile function.
13619 elsif Nkind (Context) = N_Simple_Return_Statement
13620 and then Expression (Context) = Obj_Ref
13621 then
13622 return
13623 Within_Volatile_Function (Return_Statement_Entity (Context));
13625 -- The volatile object appears as the prefix of a name occurring in a
13626 -- non-interfering context.
13628 elsif Nkind_In (Context, N_Attribute_Reference,
13629 N_Explicit_Dereference,
13630 N_Indexed_Component,
13631 N_Selected_Component,
13632 N_Slice)
13633 and then Prefix (Context) = Obj_Ref
13634 and then Is_OK_Volatile_Context
13635 (Context => Parent (Context),
13636 Obj_Ref => Context)
13637 then
13638 return True;
13640 -- The volatile object appears as the expression of a type conversion
13641 -- occurring in a non-interfering context.
13643 elsif Nkind_In (Context, N_Type_Conversion,
13644 N_Unchecked_Type_Conversion)
13645 and then Expression (Context) = Obj_Ref
13646 and then Is_OK_Volatile_Context
13647 (Context => Parent (Context),
13648 Obj_Ref => Context)
13649 then
13650 return True;
13652 -- Allow references to volatile objects in various checks. This is not a
13653 -- direct SPARK 2014 requirement.
13655 elsif Within_Check (Context) then
13656 return True;
13658 -- Assume that references to effectively volatile objects that appear
13659 -- as actual parameters in a subprogram call are always legal. A full
13660 -- legality check is done when the actuals are resolved (see routine
13661 -- Resolve_Actuals).
13663 elsif Within_Subprogram_Call (Context) then
13664 return True;
13666 -- Otherwise the context is not suitable for an effectively volatile
13667 -- object.
13669 else
13670 return False;
13671 end if;
13672 end Is_OK_Volatile_Context;
13674 ------------------------------------
13675 -- Is_Package_Contract_Annotation --
13676 ------------------------------------
13678 function Is_Package_Contract_Annotation (Item : Node_Id) return Boolean is
13679 Nam : Name_Id;
13681 begin
13682 if Nkind (Item) = N_Aspect_Specification then
13683 Nam := Chars (Identifier (Item));
13685 else pragma Assert (Nkind (Item) = N_Pragma);
13686 Nam := Pragma_Name (Item);
13687 end if;
13689 return Nam = Name_Abstract_State
13690 or else Nam = Name_Initial_Condition
13691 or else Nam = Name_Initializes
13692 or else Nam = Name_Refined_State;
13693 end Is_Package_Contract_Annotation;
13695 -----------------------------------
13696 -- Is_Partially_Initialized_Type --
13697 -----------------------------------
13699 function Is_Partially_Initialized_Type
13700 (Typ : Entity_Id;
13701 Include_Implicit : Boolean := True) return Boolean
13703 begin
13704 if Is_Scalar_Type (Typ) then
13705 return False;
13707 elsif Is_Access_Type (Typ) then
13708 return Include_Implicit;
13710 elsif Is_Array_Type (Typ) then
13712 -- If component type is partially initialized, so is array type
13714 if Is_Partially_Initialized_Type
13715 (Component_Type (Typ), Include_Implicit)
13716 then
13717 return True;
13719 -- Otherwise we are only partially initialized if we are fully
13720 -- initialized (this is the empty array case, no point in us
13721 -- duplicating that code here).
13723 else
13724 return Is_Fully_Initialized_Type (Typ);
13725 end if;
13727 elsif Is_Record_Type (Typ) then
13729 -- A discriminated type is always partially initialized if in
13730 -- all mode
13732 if Has_Discriminants (Typ) and then Include_Implicit then
13733 return True;
13735 -- A tagged type is always partially initialized
13737 elsif Is_Tagged_Type (Typ) then
13738 return True;
13740 -- Case of non-discriminated record
13742 else
13743 declare
13744 Ent : Entity_Id;
13746 Component_Present : Boolean := False;
13747 -- Set True if at least one component is present. If no
13748 -- components are present, then record type is fully
13749 -- initialized (another odd case, like the null array).
13751 begin
13752 -- Loop through components
13754 Ent := First_Entity (Typ);
13755 while Present (Ent) loop
13756 if Ekind (Ent) = E_Component then
13757 Component_Present := True;
13759 -- If a component has an initialization expression then
13760 -- the enclosing record type is partially initialized
13762 if Present (Parent (Ent))
13763 and then Present (Expression (Parent (Ent)))
13764 then
13765 return True;
13767 -- If a component is of a type which is itself partially
13768 -- initialized, then the enclosing record type is also.
13770 elsif Is_Partially_Initialized_Type
13771 (Etype (Ent), Include_Implicit)
13772 then
13773 return True;
13774 end if;
13775 end if;
13777 Next_Entity (Ent);
13778 end loop;
13780 -- No initialized components found. If we found any components
13781 -- they were all uninitialized so the result is false.
13783 if Component_Present then
13784 return False;
13786 -- But if we found no components, then all the components are
13787 -- initialized so we consider the type to be initialized.
13789 else
13790 return True;
13791 end if;
13792 end;
13793 end if;
13795 -- Concurrent types are always fully initialized
13797 elsif Is_Concurrent_Type (Typ) then
13798 return True;
13800 -- For a private type, go to underlying type. If there is no underlying
13801 -- type then just assume this partially initialized. Not clear if this
13802 -- can happen in a non-error case, but no harm in testing for this.
13804 elsif Is_Private_Type (Typ) then
13805 declare
13806 U : constant Entity_Id := Underlying_Type (Typ);
13807 begin
13808 if No (U) then
13809 return True;
13810 else
13811 return Is_Partially_Initialized_Type (U, Include_Implicit);
13812 end if;
13813 end;
13815 -- For any other type (are there any?) assume partially initialized
13817 else
13818 return True;
13819 end if;
13820 end Is_Partially_Initialized_Type;
13822 ------------------------------------
13823 -- Is_Potentially_Persistent_Type --
13824 ------------------------------------
13826 function Is_Potentially_Persistent_Type (T : Entity_Id) return Boolean is
13827 Comp : Entity_Id;
13828 Indx : Node_Id;
13830 begin
13831 -- For private type, test corresponding full type
13833 if Is_Private_Type (T) then
13834 return Is_Potentially_Persistent_Type (Full_View (T));
13836 -- Scalar types are potentially persistent
13838 elsif Is_Scalar_Type (T) then
13839 return True;
13841 -- Record type is potentially persistent if not tagged and the types of
13842 -- all it components are potentially persistent, and no component has
13843 -- an initialization expression.
13845 elsif Is_Record_Type (T)
13846 and then not Is_Tagged_Type (T)
13847 and then not Is_Partially_Initialized_Type (T)
13848 then
13849 Comp := First_Component (T);
13850 while Present (Comp) loop
13851 if not Is_Potentially_Persistent_Type (Etype (Comp)) then
13852 return False;
13853 else
13854 Next_Entity (Comp);
13855 end if;
13856 end loop;
13858 return True;
13860 -- Array type is potentially persistent if its component type is
13861 -- potentially persistent and if all its constraints are static.
13863 elsif Is_Array_Type (T) then
13864 if not Is_Potentially_Persistent_Type (Component_Type (T)) then
13865 return False;
13866 end if;
13868 Indx := First_Index (T);
13869 while Present (Indx) loop
13870 if not Is_OK_Static_Subtype (Etype (Indx)) then
13871 return False;
13872 else
13873 Next_Index (Indx);
13874 end if;
13875 end loop;
13877 return True;
13879 -- All other types are not potentially persistent
13881 else
13882 return False;
13883 end if;
13884 end Is_Potentially_Persistent_Type;
13886 --------------------------------
13887 -- Is_Potentially_Unevaluated --
13888 --------------------------------
13890 function Is_Potentially_Unevaluated (N : Node_Id) return Boolean is
13891 Par : Node_Id;
13892 Expr : Node_Id;
13894 begin
13895 Expr := N;
13896 Par := Parent (N);
13898 -- A postcondition whose expression is a short-circuit is broken down
13899 -- into individual aspects for better exception reporting. The original
13900 -- short-circuit expression is rewritten as the second operand, and an
13901 -- occurrence of 'Old in that operand is potentially unevaluated.
13902 -- See Sem_ch13.adb for details of this transformation.
13904 if Nkind (Original_Node (Par)) = N_And_Then then
13905 return True;
13906 end if;
13908 while not Nkind_In (Par, N_If_Expression,
13909 N_Case_Expression,
13910 N_And_Then,
13911 N_Or_Else,
13912 N_In,
13913 N_Not_In)
13914 loop
13915 Expr := Par;
13916 Par := Parent (Par);
13918 -- If the context is not an expression, or if is the result of
13919 -- expansion of an enclosing construct (such as another attribute)
13920 -- the predicate does not apply.
13922 if Nkind (Par) not in N_Subexpr
13923 or else not Comes_From_Source (Par)
13924 then
13925 return False;
13926 end if;
13927 end loop;
13929 if Nkind (Par) = N_If_Expression then
13930 return Is_Elsif (Par) or else Expr /= First (Expressions (Par));
13932 elsif Nkind (Par) = N_Case_Expression then
13933 return Expr /= Expression (Par);
13935 elsif Nkind_In (Par, N_And_Then, N_Or_Else) then
13936 return Expr = Right_Opnd (Par);
13938 elsif Nkind_In (Par, N_In, N_Not_In) then
13939 return Expr /= Left_Opnd (Par);
13941 else
13942 return False;
13943 end if;
13944 end Is_Potentially_Unevaluated;
13946 ---------------------------------
13947 -- Is_Protected_Self_Reference --
13948 ---------------------------------
13950 function Is_Protected_Self_Reference (N : Node_Id) return Boolean is
13952 function In_Access_Definition (N : Node_Id) return Boolean;
13953 -- Returns true if N belongs to an access definition
13955 --------------------------
13956 -- In_Access_Definition --
13957 --------------------------
13959 function In_Access_Definition (N : Node_Id) return Boolean is
13960 P : Node_Id;
13962 begin
13963 P := Parent (N);
13964 while Present (P) loop
13965 if Nkind (P) = N_Access_Definition then
13966 return True;
13967 end if;
13969 P := Parent (P);
13970 end loop;
13972 return False;
13973 end In_Access_Definition;
13975 -- Start of processing for Is_Protected_Self_Reference
13977 begin
13978 -- Verify that prefix is analyzed and has the proper form. Note that
13979 -- the attributes Elab_Spec, Elab_Body, and Elab_Subp_Body, which also
13980 -- produce the address of an entity, do not analyze their prefix
13981 -- because they denote entities that are not necessarily visible.
13982 -- Neither of them can apply to a protected type.
13984 return Ada_Version >= Ada_2005
13985 and then Is_Entity_Name (N)
13986 and then Present (Entity (N))
13987 and then Is_Protected_Type (Entity (N))
13988 and then In_Open_Scopes (Entity (N))
13989 and then not In_Access_Definition (N);
13990 end Is_Protected_Self_Reference;
13992 -----------------------------
13993 -- Is_RCI_Pkg_Spec_Or_Body --
13994 -----------------------------
13996 function Is_RCI_Pkg_Spec_Or_Body (Cunit : Node_Id) return Boolean is
13998 function Is_RCI_Pkg_Decl_Cunit (Cunit : Node_Id) return Boolean;
13999 -- Return True if the unit of Cunit is an RCI package declaration
14001 ---------------------------
14002 -- Is_RCI_Pkg_Decl_Cunit --
14003 ---------------------------
14005 function Is_RCI_Pkg_Decl_Cunit (Cunit : Node_Id) return Boolean is
14006 The_Unit : constant Node_Id := Unit (Cunit);
14008 begin
14009 if Nkind (The_Unit) /= N_Package_Declaration then
14010 return False;
14011 end if;
14013 return Is_Remote_Call_Interface (Defining_Entity (The_Unit));
14014 end Is_RCI_Pkg_Decl_Cunit;
14016 -- Start of processing for Is_RCI_Pkg_Spec_Or_Body
14018 begin
14019 return Is_RCI_Pkg_Decl_Cunit (Cunit)
14020 or else
14021 (Nkind (Unit (Cunit)) = N_Package_Body
14022 and then Is_RCI_Pkg_Decl_Cunit (Library_Unit (Cunit)));
14023 end Is_RCI_Pkg_Spec_Or_Body;
14025 -----------------------------------------
14026 -- Is_Remote_Access_To_Class_Wide_Type --
14027 -----------------------------------------
14029 function Is_Remote_Access_To_Class_Wide_Type
14030 (E : Entity_Id) return Boolean
14032 begin
14033 -- A remote access to class-wide type is a general access to object type
14034 -- declared in the visible part of a Remote_Types or Remote_Call_
14035 -- Interface unit.
14037 return Ekind (E) = E_General_Access_Type
14038 and then (Is_Remote_Call_Interface (E) or else Is_Remote_Types (E));
14039 end Is_Remote_Access_To_Class_Wide_Type;
14041 -----------------------------------------
14042 -- Is_Remote_Access_To_Subprogram_Type --
14043 -----------------------------------------
14045 function Is_Remote_Access_To_Subprogram_Type
14046 (E : Entity_Id) return Boolean
14048 begin
14049 return (Ekind (E) = E_Access_Subprogram_Type
14050 or else (Ekind (E) = E_Record_Type
14051 and then Present (Corresponding_Remote_Type (E))))
14052 and then (Is_Remote_Call_Interface (E) or else Is_Remote_Types (E));
14053 end Is_Remote_Access_To_Subprogram_Type;
14055 --------------------
14056 -- Is_Remote_Call --
14057 --------------------
14059 function Is_Remote_Call (N : Node_Id) return Boolean is
14060 begin
14061 if Nkind (N) not in N_Subprogram_Call then
14063 -- An entry call cannot be remote
14065 return False;
14067 elsif Nkind (Name (N)) in N_Has_Entity
14068 and then Is_Remote_Call_Interface (Entity (Name (N)))
14069 then
14070 -- A subprogram declared in the spec of a RCI package is remote
14072 return True;
14074 elsif Nkind (Name (N)) = N_Explicit_Dereference
14075 and then Is_Remote_Access_To_Subprogram_Type
14076 (Etype (Prefix (Name (N))))
14077 then
14078 -- The dereference of a RAS is a remote call
14080 return True;
14082 elsif Present (Controlling_Argument (N))
14083 and then Is_Remote_Access_To_Class_Wide_Type
14084 (Etype (Controlling_Argument (N)))
14085 then
14086 -- Any primitive operation call with a controlling argument of
14087 -- a RACW type is a remote call.
14089 return True;
14090 end if;
14092 -- All other calls are local calls
14094 return False;
14095 end Is_Remote_Call;
14097 ----------------------
14098 -- Is_Renamed_Entry --
14099 ----------------------
14101 function Is_Renamed_Entry (Proc_Nam : Entity_Id) return Boolean is
14102 Orig_Node : Node_Id := Empty;
14103 Subp_Decl : Node_Id := Parent (Parent (Proc_Nam));
14105 function Is_Entry (Nam : Node_Id) return Boolean;
14106 -- Determine whether Nam is an entry. Traverse selectors if there are
14107 -- nested selected components.
14109 --------------
14110 -- Is_Entry --
14111 --------------
14113 function Is_Entry (Nam : Node_Id) return Boolean is
14114 begin
14115 if Nkind (Nam) = N_Selected_Component then
14116 return Is_Entry (Selector_Name (Nam));
14117 end if;
14119 return Ekind (Entity (Nam)) = E_Entry;
14120 end Is_Entry;
14122 -- Start of processing for Is_Renamed_Entry
14124 begin
14125 if Present (Alias (Proc_Nam)) then
14126 Subp_Decl := Parent (Parent (Alias (Proc_Nam)));
14127 end if;
14129 -- Look for a rewritten subprogram renaming declaration
14131 if Nkind (Subp_Decl) = N_Subprogram_Declaration
14132 and then Present (Original_Node (Subp_Decl))
14133 then
14134 Orig_Node := Original_Node (Subp_Decl);
14135 end if;
14137 -- The rewritten subprogram is actually an entry
14139 if Present (Orig_Node)
14140 and then Nkind (Orig_Node) = N_Subprogram_Renaming_Declaration
14141 and then Is_Entry (Name (Orig_Node))
14142 then
14143 return True;
14144 end if;
14146 return False;
14147 end Is_Renamed_Entry;
14149 -----------------------------
14150 -- Is_Renaming_Declaration --
14151 -----------------------------
14153 function Is_Renaming_Declaration (N : Node_Id) return Boolean is
14154 begin
14155 case Nkind (N) is
14156 when N_Exception_Renaming_Declaration |
14157 N_Generic_Function_Renaming_Declaration |
14158 N_Generic_Package_Renaming_Declaration |
14159 N_Generic_Procedure_Renaming_Declaration |
14160 N_Object_Renaming_Declaration |
14161 N_Package_Renaming_Declaration |
14162 N_Subprogram_Renaming_Declaration =>
14163 return True;
14165 when others =>
14166 return False;
14167 end case;
14168 end Is_Renaming_Declaration;
14170 ----------------------------
14171 -- Is_Reversible_Iterator --
14172 ----------------------------
14174 function Is_Reversible_Iterator (Typ : Entity_Id) return Boolean is
14175 Ifaces_List : Elist_Id;
14176 Iface_Elmt : Elmt_Id;
14177 Iface : Entity_Id;
14179 begin
14180 if Is_Class_Wide_Type (Typ)
14181 and then Chars (Root_Type (Typ)) = Name_Reversible_Iterator
14182 and then Is_Predefined_File_Name
14183 (Unit_File_Name (Get_Source_Unit (Root_Type (Typ))))
14184 then
14185 return True;
14187 elsif not Is_Tagged_Type (Typ) or else not Is_Derived_Type (Typ) then
14188 return False;
14190 else
14191 Collect_Interfaces (Typ, Ifaces_List);
14193 Iface_Elmt := First_Elmt (Ifaces_List);
14194 while Present (Iface_Elmt) loop
14195 Iface := Node (Iface_Elmt);
14196 if Chars (Iface) = Name_Reversible_Iterator
14197 and then
14198 Is_Predefined_File_Name
14199 (Unit_File_Name (Get_Source_Unit (Iface)))
14200 then
14201 return True;
14202 end if;
14204 Next_Elmt (Iface_Elmt);
14205 end loop;
14206 end if;
14208 return False;
14209 end Is_Reversible_Iterator;
14211 ----------------------
14212 -- Is_Selector_Name --
14213 ----------------------
14215 function Is_Selector_Name (N : Node_Id) return Boolean is
14216 begin
14217 if not Is_List_Member (N) then
14218 declare
14219 P : constant Node_Id := Parent (N);
14220 begin
14221 return Nkind_In (P, N_Expanded_Name,
14222 N_Generic_Association,
14223 N_Parameter_Association,
14224 N_Selected_Component)
14225 and then Selector_Name (P) = N;
14226 end;
14228 else
14229 declare
14230 L : constant List_Id := List_Containing (N);
14231 P : constant Node_Id := Parent (L);
14232 begin
14233 return (Nkind (P) = N_Discriminant_Association
14234 and then Selector_Names (P) = L)
14235 or else
14236 (Nkind (P) = N_Component_Association
14237 and then Choices (P) = L);
14238 end;
14239 end if;
14240 end Is_Selector_Name;
14242 ---------------------------------
14243 -- Is_Single_Concurrent_Object --
14244 ---------------------------------
14246 function Is_Single_Concurrent_Object (Id : Entity_Id) return Boolean is
14247 begin
14248 return
14249 Is_Single_Protected_Object (Id) or else Is_Single_Task_Object (Id);
14250 end Is_Single_Concurrent_Object;
14252 -------------------------------
14253 -- Is_Single_Concurrent_Type --
14254 -------------------------------
14256 function Is_Single_Concurrent_Type (Id : Entity_Id) return Boolean is
14257 begin
14258 return
14259 Ekind_In (Id, E_Protected_Type, E_Task_Type)
14260 and then Is_Single_Concurrent_Type_Declaration
14261 (Declaration_Node (Id));
14262 end Is_Single_Concurrent_Type;
14264 -------------------------------------------
14265 -- Is_Single_Concurrent_Type_Declaration --
14266 -------------------------------------------
14268 function Is_Single_Concurrent_Type_Declaration
14269 (N : Node_Id) return Boolean
14271 begin
14272 return Nkind_In (Original_Node (N), N_Single_Protected_Declaration,
14273 N_Single_Task_Declaration);
14274 end Is_Single_Concurrent_Type_Declaration;
14276 ---------------------------------------------
14277 -- Is_Single_Precision_Floating_Point_Type --
14278 ---------------------------------------------
14280 function Is_Single_Precision_Floating_Point_Type
14281 (E : Entity_Id) return Boolean is
14282 begin
14283 return Is_Floating_Point_Type (E)
14284 and then Machine_Radix_Value (E) = Uint_2
14285 and then Machine_Mantissa_Value (E) = Uint_24
14286 and then Machine_Emax_Value (E) = Uint_2 ** Uint_7
14287 and then Machine_Emin_Value (E) = Uint_3 - (Uint_2 ** Uint_7);
14288 end Is_Single_Precision_Floating_Point_Type;
14290 --------------------------------
14291 -- Is_Single_Protected_Object --
14292 --------------------------------
14294 function Is_Single_Protected_Object (Id : Entity_Id) return Boolean is
14295 begin
14296 return
14297 Ekind (Id) = E_Variable
14298 and then Ekind (Etype (Id)) = E_Protected_Type
14299 and then Is_Single_Concurrent_Type (Etype (Id));
14300 end Is_Single_Protected_Object;
14302 ---------------------------
14303 -- Is_Single_Task_Object --
14304 ---------------------------
14306 function Is_Single_Task_Object (Id : Entity_Id) return Boolean is
14307 begin
14308 return
14309 Ekind (Id) = E_Variable
14310 and then Ekind (Etype (Id)) = E_Task_Type
14311 and then Is_Single_Concurrent_Type (Etype (Id));
14312 end Is_Single_Task_Object;
14314 -------------------------------------
14315 -- Is_SPARK_05_Initialization_Expr --
14316 -------------------------------------
14318 function Is_SPARK_05_Initialization_Expr (N : Node_Id) return Boolean is
14319 Is_Ok : Boolean;
14320 Expr : Node_Id;
14321 Comp_Assn : Node_Id;
14322 Orig_N : constant Node_Id := Original_Node (N);
14324 begin
14325 Is_Ok := True;
14327 if not Comes_From_Source (Orig_N) then
14328 goto Done;
14329 end if;
14331 pragma Assert (Nkind (Orig_N) in N_Subexpr);
14333 case Nkind (Orig_N) is
14334 when N_Character_Literal |
14335 N_Integer_Literal |
14336 N_Real_Literal |
14337 N_String_Literal =>
14338 null;
14340 when N_Identifier |
14341 N_Expanded_Name =>
14342 if Is_Entity_Name (Orig_N)
14343 and then Present (Entity (Orig_N)) -- needed in some cases
14344 then
14345 case Ekind (Entity (Orig_N)) is
14346 when E_Constant |
14347 E_Enumeration_Literal |
14348 E_Named_Integer |
14349 E_Named_Real =>
14350 null;
14351 when others =>
14352 if Is_Type (Entity (Orig_N)) then
14353 null;
14354 else
14355 Is_Ok := False;
14356 end if;
14357 end case;
14358 end if;
14360 when N_Qualified_Expression |
14361 N_Type_Conversion =>
14362 Is_Ok := Is_SPARK_05_Initialization_Expr (Expression (Orig_N));
14364 when N_Unary_Op =>
14365 Is_Ok := Is_SPARK_05_Initialization_Expr (Right_Opnd (Orig_N));
14367 when N_Binary_Op |
14368 N_Short_Circuit |
14369 N_Membership_Test =>
14370 Is_Ok := Is_SPARK_05_Initialization_Expr (Left_Opnd (Orig_N))
14371 and then
14372 Is_SPARK_05_Initialization_Expr (Right_Opnd (Orig_N));
14374 when N_Aggregate |
14375 N_Extension_Aggregate =>
14376 if Nkind (Orig_N) = N_Extension_Aggregate then
14377 Is_Ok :=
14378 Is_SPARK_05_Initialization_Expr (Ancestor_Part (Orig_N));
14379 end if;
14381 Expr := First (Expressions (Orig_N));
14382 while Present (Expr) loop
14383 if not Is_SPARK_05_Initialization_Expr (Expr) then
14384 Is_Ok := False;
14385 goto Done;
14386 end if;
14388 Next (Expr);
14389 end loop;
14391 Comp_Assn := First (Component_Associations (Orig_N));
14392 while Present (Comp_Assn) loop
14393 Expr := Expression (Comp_Assn);
14395 -- Note: test for Present here needed for box assocation
14397 if Present (Expr)
14398 and then not Is_SPARK_05_Initialization_Expr (Expr)
14399 then
14400 Is_Ok := False;
14401 goto Done;
14402 end if;
14404 Next (Comp_Assn);
14405 end loop;
14407 when N_Attribute_Reference =>
14408 if Nkind (Prefix (Orig_N)) in N_Subexpr then
14409 Is_Ok := Is_SPARK_05_Initialization_Expr (Prefix (Orig_N));
14410 end if;
14412 Expr := First (Expressions (Orig_N));
14413 while Present (Expr) loop
14414 if not Is_SPARK_05_Initialization_Expr (Expr) then
14415 Is_Ok := False;
14416 goto Done;
14417 end if;
14419 Next (Expr);
14420 end loop;
14422 -- Selected components might be expanded named not yet resolved, so
14423 -- default on the safe side. (Eg on sparklex.ads)
14425 when N_Selected_Component =>
14426 null;
14428 when others =>
14429 Is_Ok := False;
14430 end case;
14432 <<Done>>
14433 return Is_Ok;
14434 end Is_SPARK_05_Initialization_Expr;
14436 ----------------------------------
14437 -- Is_SPARK_05_Object_Reference --
14438 ----------------------------------
14440 function Is_SPARK_05_Object_Reference (N : Node_Id) return Boolean is
14441 begin
14442 if Is_Entity_Name (N) then
14443 return Present (Entity (N))
14444 and then
14445 (Ekind_In (Entity (N), E_Constant, E_Variable)
14446 or else Ekind (Entity (N)) in Formal_Kind);
14448 else
14449 case Nkind (N) is
14450 when N_Selected_Component =>
14451 return Is_SPARK_05_Object_Reference (Prefix (N));
14453 when others =>
14454 return False;
14455 end case;
14456 end if;
14457 end Is_SPARK_05_Object_Reference;
14459 -----------------------------
14460 -- Is_Specific_Tagged_Type --
14461 -----------------------------
14463 function Is_Specific_Tagged_Type (Typ : Entity_Id) return Boolean is
14464 Full_Typ : Entity_Id;
14466 begin
14467 -- Handle private types
14469 if Is_Private_Type (Typ) and then Present (Full_View (Typ)) then
14470 Full_Typ := Full_View (Typ);
14471 else
14472 Full_Typ := Typ;
14473 end if;
14475 -- A specific tagged type is a non-class-wide tagged type
14477 return Is_Tagged_Type (Full_Typ) and not Is_Class_Wide_Type (Full_Typ);
14478 end Is_Specific_Tagged_Type;
14480 ------------------
14481 -- Is_Statement --
14482 ------------------
14484 function Is_Statement (N : Node_Id) return Boolean is
14485 begin
14486 return
14487 Nkind (N) in N_Statement_Other_Than_Procedure_Call
14488 or else Nkind (N) = N_Procedure_Call_Statement;
14489 end Is_Statement;
14491 ---------------------------------------
14492 -- Is_Subprogram_Contract_Annotation --
14493 ---------------------------------------
14495 function Is_Subprogram_Contract_Annotation
14496 (Item : Node_Id) return Boolean
14498 Nam : Name_Id;
14500 begin
14501 if Nkind (Item) = N_Aspect_Specification then
14502 Nam := Chars (Identifier (Item));
14504 else pragma Assert (Nkind (Item) = N_Pragma);
14505 Nam := Pragma_Name (Item);
14506 end if;
14508 return Nam = Name_Contract_Cases
14509 or else Nam = Name_Depends
14510 or else Nam = Name_Extensions_Visible
14511 or else Nam = Name_Global
14512 or else Nam = Name_Post
14513 or else Nam = Name_Post_Class
14514 or else Nam = Name_Postcondition
14515 or else Nam = Name_Pre
14516 or else Nam = Name_Pre_Class
14517 or else Nam = Name_Precondition
14518 or else Nam = Name_Refined_Depends
14519 or else Nam = Name_Refined_Global
14520 or else Nam = Name_Refined_Post
14521 or else Nam = Name_Test_Case;
14522 end Is_Subprogram_Contract_Annotation;
14524 --------------------------------------------------
14525 -- Is_Subprogram_Stub_Without_Prior_Declaration --
14526 --------------------------------------------------
14528 function Is_Subprogram_Stub_Without_Prior_Declaration
14529 (N : Node_Id) return Boolean
14531 begin
14532 -- A subprogram stub without prior declaration serves as declaration for
14533 -- the actual subprogram body. As such, it has an attached defining
14534 -- entity of E_[Generic_]Function or E_[Generic_]Procedure.
14536 return Nkind (N) = N_Subprogram_Body_Stub
14537 and then Ekind (Defining_Entity (N)) /= E_Subprogram_Body;
14538 end Is_Subprogram_Stub_Without_Prior_Declaration;
14540 --------------------------
14541 -- Is_Suspension_Object --
14542 --------------------------
14544 function Is_Suspension_Object (Id : Entity_Id) return Boolean is
14545 begin
14546 -- This approach does an exact name match rather than to rely on
14547 -- RTSfind. Routine Is_Effectively_Volatile is used by clients of the
14548 -- front end at point where all auxiliary tables are locked and any
14549 -- modifications to them are treated as violations. Do not tamper with
14550 -- the tables, instead examine the Chars fields of all the scopes of Id.
14552 return
14553 Chars (Id) = Name_Suspension_Object
14554 and then Present (Scope (Id))
14555 and then Chars (Scope (Id)) = Name_Synchronous_Task_Control
14556 and then Present (Scope (Scope (Id)))
14557 and then Chars (Scope (Scope (Id))) = Name_Ada
14558 and then Present (Scope (Scope (Scope (Id))))
14559 and then Scope (Scope (Scope (Id))) = Standard_Standard;
14560 end Is_Suspension_Object;
14562 ----------------------------
14563 -- Is_Synchronized_Object --
14564 ----------------------------
14566 function Is_Synchronized_Object (Id : Entity_Id) return Boolean is
14567 Prag : Node_Id;
14569 begin
14570 if Is_Object (Id) then
14572 -- The object is synchronized if it is of a type that yields a
14573 -- synchronized object.
14575 if Yields_Synchronized_Object (Etype (Id)) then
14576 return True;
14578 -- The object is synchronized if it is atomic and Async_Writers is
14579 -- enabled.
14581 elsif Is_Atomic (Id) and then Async_Writers_Enabled (Id) then
14582 return True;
14584 -- A constant is a synchronized object by default
14586 elsif Ekind (Id) = E_Constant then
14587 return True;
14589 -- A variable is a synchronized object if it is subject to pragma
14590 -- Constant_After_Elaboration.
14592 elsif Ekind (Id) = E_Variable then
14593 Prag := Get_Pragma (Id, Pragma_Constant_After_Elaboration);
14595 return Present (Prag) and then Is_Enabled_Pragma (Prag);
14596 end if;
14597 end if;
14599 -- Otherwise the input is not an object or it does not qualify as a
14600 -- synchronized object.
14602 return False;
14603 end Is_Synchronized_Object;
14605 ---------------------------------
14606 -- Is_Synchronized_Tagged_Type --
14607 ---------------------------------
14609 function Is_Synchronized_Tagged_Type (E : Entity_Id) return Boolean is
14610 Kind : constant Entity_Kind := Ekind (Base_Type (E));
14612 begin
14613 -- A task or protected type derived from an interface is a tagged type.
14614 -- Such a tagged type is called a synchronized tagged type, as are
14615 -- synchronized interfaces and private extensions whose declaration
14616 -- includes the reserved word synchronized.
14618 return (Is_Tagged_Type (E)
14619 and then (Kind = E_Task_Type
14620 or else
14621 Kind = E_Protected_Type))
14622 or else
14623 (Is_Interface (E)
14624 and then Is_Synchronized_Interface (E))
14625 or else
14626 (Ekind (E) = E_Record_Type_With_Private
14627 and then Nkind (Parent (E)) = N_Private_Extension_Declaration
14628 and then (Synchronized_Present (Parent (E))
14629 or else Is_Synchronized_Interface (Etype (E))));
14630 end Is_Synchronized_Tagged_Type;
14632 -----------------
14633 -- Is_Transfer --
14634 -----------------
14636 function Is_Transfer (N : Node_Id) return Boolean is
14637 Kind : constant Node_Kind := Nkind (N);
14639 begin
14640 if Kind = N_Simple_Return_Statement
14641 or else
14642 Kind = N_Extended_Return_Statement
14643 or else
14644 Kind = N_Goto_Statement
14645 or else
14646 Kind = N_Raise_Statement
14647 or else
14648 Kind = N_Requeue_Statement
14649 then
14650 return True;
14652 elsif (Kind = N_Exit_Statement or else Kind in N_Raise_xxx_Error)
14653 and then No (Condition (N))
14654 then
14655 return True;
14657 elsif Kind = N_Procedure_Call_Statement
14658 and then Is_Entity_Name (Name (N))
14659 and then Present (Entity (Name (N)))
14660 and then No_Return (Entity (Name (N)))
14661 then
14662 return True;
14664 elsif Nkind (Original_Node (N)) = N_Raise_Statement then
14665 return True;
14667 else
14668 return False;
14669 end if;
14670 end Is_Transfer;
14672 -------------
14673 -- Is_True --
14674 -------------
14676 function Is_True (U : Uint) return Boolean is
14677 begin
14678 return (U /= 0);
14679 end Is_True;
14681 --------------------------------------
14682 -- Is_Unchecked_Conversion_Instance --
14683 --------------------------------------
14685 function Is_Unchecked_Conversion_Instance (Id : Entity_Id) return Boolean is
14686 Par : Node_Id;
14688 begin
14689 -- Look for a function whose generic parent is the predefined intrinsic
14690 -- function Unchecked_Conversion, or for one that renames such an
14691 -- instance.
14693 if Ekind (Id) = E_Function then
14694 Par := Parent (Id);
14696 if Nkind (Par) = N_Function_Specification then
14697 Par := Generic_Parent (Par);
14699 if Present (Par) then
14700 return
14701 Chars (Par) = Name_Unchecked_Conversion
14702 and then Is_Intrinsic_Subprogram (Par)
14703 and then Is_Predefined_File_Name
14704 (Unit_File_Name (Get_Source_Unit (Par)));
14705 else
14706 return
14707 Present (Alias (Id))
14708 and then Is_Unchecked_Conversion_Instance (Alias (Id));
14709 end if;
14710 end if;
14711 end if;
14713 return False;
14714 end Is_Unchecked_Conversion_Instance;
14716 -------------------------------
14717 -- Is_Universal_Numeric_Type --
14718 -------------------------------
14720 function Is_Universal_Numeric_Type (T : Entity_Id) return Boolean is
14721 begin
14722 return T = Universal_Integer or else T = Universal_Real;
14723 end Is_Universal_Numeric_Type;
14725 ----------------------------
14726 -- Is_Variable_Size_Array --
14727 ----------------------------
14729 function Is_Variable_Size_Array (E : Entity_Id) return Boolean is
14730 Idx : Node_Id;
14732 begin
14733 pragma Assert (Is_Array_Type (E));
14735 -- Check if some index is initialized with a non-constant value
14737 Idx := First_Index (E);
14738 while Present (Idx) loop
14739 if Nkind (Idx) = N_Range then
14740 if not Is_Constant_Bound (Low_Bound (Idx))
14741 or else not Is_Constant_Bound (High_Bound (Idx))
14742 then
14743 return True;
14744 end if;
14745 end if;
14747 Idx := Next_Index (Idx);
14748 end loop;
14750 return False;
14751 end Is_Variable_Size_Array;
14753 -----------------------------
14754 -- Is_Variable_Size_Record --
14755 -----------------------------
14757 function Is_Variable_Size_Record (E : Entity_Id) return Boolean is
14758 Comp : Entity_Id;
14759 Comp_Typ : Entity_Id;
14761 begin
14762 pragma Assert (Is_Record_Type (E));
14764 Comp := First_Entity (E);
14765 while Present (Comp) loop
14766 Comp_Typ := Etype (Comp);
14768 -- Recursive call if the record type has discriminants
14770 if Is_Record_Type (Comp_Typ)
14771 and then Has_Discriminants (Comp_Typ)
14772 and then Is_Variable_Size_Record (Comp_Typ)
14773 then
14774 return True;
14776 elsif Is_Array_Type (Comp_Typ)
14777 and then Is_Variable_Size_Array (Comp_Typ)
14778 then
14779 return True;
14780 end if;
14782 Next_Entity (Comp);
14783 end loop;
14785 return False;
14786 end Is_Variable_Size_Record;
14788 -----------------
14789 -- Is_Variable --
14790 -----------------
14792 function Is_Variable
14793 (N : Node_Id;
14794 Use_Original_Node : Boolean := True) return Boolean
14796 Orig_Node : Node_Id;
14798 function In_Protected_Function (E : Entity_Id) return Boolean;
14799 -- Within a protected function, the private components of the enclosing
14800 -- protected type are constants. A function nested within a (protected)
14801 -- procedure is not itself protected. Within the body of a protected
14802 -- function the current instance of the protected type is a constant.
14804 function Is_Variable_Prefix (P : Node_Id) return Boolean;
14805 -- Prefixes can involve implicit dereferences, in which case we must
14806 -- test for the case of a reference of a constant access type, which can
14807 -- can never be a variable.
14809 ---------------------------
14810 -- In_Protected_Function --
14811 ---------------------------
14813 function In_Protected_Function (E : Entity_Id) return Boolean is
14814 Prot : Entity_Id;
14815 S : Entity_Id;
14817 begin
14818 -- E is the current instance of a type
14820 if Is_Type (E) then
14821 Prot := E;
14823 -- E is an object
14825 else
14826 Prot := Scope (E);
14827 end if;
14829 if not Is_Protected_Type (Prot) then
14830 return False;
14832 else
14833 S := Current_Scope;
14834 while Present (S) and then S /= Prot loop
14835 if Ekind (S) = E_Function and then Scope (S) = Prot then
14836 return True;
14837 end if;
14839 S := Scope (S);
14840 end loop;
14842 return False;
14843 end if;
14844 end In_Protected_Function;
14846 ------------------------
14847 -- Is_Variable_Prefix --
14848 ------------------------
14850 function Is_Variable_Prefix (P : Node_Id) return Boolean is
14851 begin
14852 if Is_Access_Type (Etype (P)) then
14853 return not Is_Access_Constant (Root_Type (Etype (P)));
14855 -- For the case of an indexed component whose prefix has a packed
14856 -- array type, the prefix has been rewritten into a type conversion.
14857 -- Determine variable-ness from the converted expression.
14859 elsif Nkind (P) = N_Type_Conversion
14860 and then not Comes_From_Source (P)
14861 and then Is_Array_Type (Etype (P))
14862 and then Is_Packed (Etype (P))
14863 then
14864 return Is_Variable (Expression (P));
14866 else
14867 return Is_Variable (P);
14868 end if;
14869 end Is_Variable_Prefix;
14871 -- Start of processing for Is_Variable
14873 begin
14874 -- Special check, allow x'Deref(expr) as a variable
14876 if Nkind (N) = N_Attribute_Reference
14877 and then Attribute_Name (N) = Name_Deref
14878 then
14879 return True;
14880 end if;
14882 -- Check if we perform the test on the original node since this may be a
14883 -- test of syntactic categories which must not be disturbed by whatever
14884 -- rewriting might have occurred. For example, an aggregate, which is
14885 -- certainly NOT a variable, could be turned into a variable by
14886 -- expansion.
14888 if Use_Original_Node then
14889 Orig_Node := Original_Node (N);
14890 else
14891 Orig_Node := N;
14892 end if;
14894 -- Definitely OK if Assignment_OK is set. Since this is something that
14895 -- only gets set for expanded nodes, the test is on N, not Orig_Node.
14897 if Nkind (N) in N_Subexpr and then Assignment_OK (N) then
14898 return True;
14900 -- Normally we go to the original node, but there is one exception where
14901 -- we use the rewritten node, namely when it is an explicit dereference.
14902 -- The generated code may rewrite a prefix which is an access type with
14903 -- an explicit dereference. The dereference is a variable, even though
14904 -- the original node may not be (since it could be a constant of the
14905 -- access type).
14907 -- In Ada 2005 we have a further case to consider: the prefix may be a
14908 -- function call given in prefix notation. The original node appears to
14909 -- be a selected component, but we need to examine the call.
14911 elsif Nkind (N) = N_Explicit_Dereference
14912 and then Nkind (Orig_Node) /= N_Explicit_Dereference
14913 and then Present (Etype (Orig_Node))
14914 and then Is_Access_Type (Etype (Orig_Node))
14915 then
14916 -- Note that if the prefix is an explicit dereference that does not
14917 -- come from source, we must check for a rewritten function call in
14918 -- prefixed notation before other forms of rewriting, to prevent a
14919 -- compiler crash.
14921 return
14922 (Nkind (Orig_Node) = N_Function_Call
14923 and then not Is_Access_Constant (Etype (Prefix (N))))
14924 or else
14925 Is_Variable_Prefix (Original_Node (Prefix (N)));
14927 -- in Ada 2012, the dereference may have been added for a type with
14928 -- a declared implicit dereference aspect. Check that it is not an
14929 -- access to constant.
14931 elsif Nkind (N) = N_Explicit_Dereference
14932 and then Present (Etype (Orig_Node))
14933 and then Ada_Version >= Ada_2012
14934 and then Has_Implicit_Dereference (Etype (Orig_Node))
14935 then
14936 return not Is_Access_Constant (Etype (Prefix (N)));
14938 -- A function call is never a variable
14940 elsif Nkind (N) = N_Function_Call then
14941 return False;
14943 -- All remaining checks use the original node
14945 elsif Is_Entity_Name (Orig_Node)
14946 and then Present (Entity (Orig_Node))
14947 then
14948 declare
14949 E : constant Entity_Id := Entity (Orig_Node);
14950 K : constant Entity_Kind := Ekind (E);
14952 begin
14953 return (K = E_Variable
14954 and then Nkind (Parent (E)) /= N_Exception_Handler)
14955 or else (K = E_Component
14956 and then not In_Protected_Function (E))
14957 or else K = E_Out_Parameter
14958 or else K = E_In_Out_Parameter
14959 or else K = E_Generic_In_Out_Parameter
14961 -- Current instance of type. If this is a protected type, check
14962 -- we are not within the body of one of its protected functions.
14964 or else (Is_Type (E)
14965 and then In_Open_Scopes (E)
14966 and then not In_Protected_Function (E))
14968 or else (Is_Incomplete_Or_Private_Type (E)
14969 and then In_Open_Scopes (Full_View (E)));
14970 end;
14972 else
14973 case Nkind (Orig_Node) is
14974 when N_Indexed_Component | N_Slice =>
14975 return Is_Variable_Prefix (Prefix (Orig_Node));
14977 when N_Selected_Component =>
14978 return (Is_Variable (Selector_Name (Orig_Node))
14979 and then Is_Variable_Prefix (Prefix (Orig_Node)))
14980 or else
14981 (Nkind (N) = N_Expanded_Name
14982 and then Scope (Entity (N)) = Entity (Prefix (N)));
14984 -- For an explicit dereference, the type of the prefix cannot
14985 -- be an access to constant or an access to subprogram.
14987 when N_Explicit_Dereference =>
14988 declare
14989 Typ : constant Entity_Id := Etype (Prefix (Orig_Node));
14990 begin
14991 return Is_Access_Type (Typ)
14992 and then not Is_Access_Constant (Root_Type (Typ))
14993 and then Ekind (Typ) /= E_Access_Subprogram_Type;
14994 end;
14996 -- The type conversion is the case where we do not deal with the
14997 -- context dependent special case of an actual parameter. Thus
14998 -- the type conversion is only considered a variable for the
14999 -- purposes of this routine if the target type is tagged. However,
15000 -- a type conversion is considered to be a variable if it does not
15001 -- come from source (this deals for example with the conversions
15002 -- of expressions to their actual subtypes).
15004 when N_Type_Conversion =>
15005 return Is_Variable (Expression (Orig_Node))
15006 and then
15007 (not Comes_From_Source (Orig_Node)
15008 or else
15009 (Is_Tagged_Type (Etype (Subtype_Mark (Orig_Node)))
15010 and then
15011 Is_Tagged_Type (Etype (Expression (Orig_Node)))));
15013 -- GNAT allows an unchecked type conversion as a variable. This
15014 -- only affects the generation of internal expanded code, since
15015 -- calls to instantiations of Unchecked_Conversion are never
15016 -- considered variables (since they are function calls).
15018 when N_Unchecked_Type_Conversion =>
15019 return Is_Variable (Expression (Orig_Node));
15021 when others =>
15022 return False;
15023 end case;
15024 end if;
15025 end Is_Variable;
15027 ---------------------------
15028 -- Is_Visibly_Controlled --
15029 ---------------------------
15031 function Is_Visibly_Controlled (T : Entity_Id) return Boolean is
15032 Root : constant Entity_Id := Root_Type (T);
15033 begin
15034 return Chars (Scope (Root)) = Name_Finalization
15035 and then Chars (Scope (Scope (Root))) = Name_Ada
15036 and then Scope (Scope (Scope (Root))) = Standard_Standard;
15037 end Is_Visibly_Controlled;
15039 --------------------------
15040 -- Is_Volatile_Function --
15041 --------------------------
15043 function Is_Volatile_Function (Func_Id : Entity_Id) return Boolean is
15044 begin
15045 pragma Assert (Ekind_In (Func_Id, E_Function, E_Generic_Function));
15047 -- A function declared within a protected type is volatile
15049 if Is_Protected_Type (Scope (Func_Id)) then
15050 return True;
15052 -- An instance of Ada.Unchecked_Conversion is a volatile function if
15053 -- either the source or the target are effectively volatile.
15055 elsif Is_Unchecked_Conversion_Instance (Func_Id)
15056 and then Has_Effectively_Volatile_Profile (Func_Id)
15057 then
15058 return True;
15060 -- Otherwise the function is treated as volatile if it is subject to
15061 -- enabled pragma Volatile_Function.
15063 else
15064 return
15065 Is_Enabled_Pragma (Get_Pragma (Func_Id, Pragma_Volatile_Function));
15066 end if;
15067 end Is_Volatile_Function;
15069 ------------------------
15070 -- Is_Volatile_Object --
15071 ------------------------
15073 function Is_Volatile_Object (N : Node_Id) return Boolean is
15075 function Is_Volatile_Prefix (N : Node_Id) return Boolean;
15076 -- If prefix is an implicit dereference, examine designated type
15078 function Object_Has_Volatile_Components (N : Node_Id) return Boolean;
15079 -- Determines if given object has volatile components
15081 ------------------------
15082 -- Is_Volatile_Prefix --
15083 ------------------------
15085 function Is_Volatile_Prefix (N : Node_Id) return Boolean is
15086 Typ : constant Entity_Id := Etype (N);
15088 begin
15089 if Is_Access_Type (Typ) then
15090 declare
15091 Dtyp : constant Entity_Id := Designated_Type (Typ);
15093 begin
15094 return Is_Volatile (Dtyp)
15095 or else Has_Volatile_Components (Dtyp);
15096 end;
15098 else
15099 return Object_Has_Volatile_Components (N);
15100 end if;
15101 end Is_Volatile_Prefix;
15103 ------------------------------------
15104 -- Object_Has_Volatile_Components --
15105 ------------------------------------
15107 function Object_Has_Volatile_Components (N : Node_Id) return Boolean is
15108 Typ : constant Entity_Id := Etype (N);
15110 begin
15111 if Is_Volatile (Typ)
15112 or else Has_Volatile_Components (Typ)
15113 then
15114 return True;
15116 elsif Is_Entity_Name (N)
15117 and then (Has_Volatile_Components (Entity (N))
15118 or else Is_Volatile (Entity (N)))
15119 then
15120 return True;
15122 elsif Nkind (N) = N_Indexed_Component
15123 or else Nkind (N) = N_Selected_Component
15124 then
15125 return Is_Volatile_Prefix (Prefix (N));
15127 else
15128 return False;
15129 end if;
15130 end Object_Has_Volatile_Components;
15132 -- Start of processing for Is_Volatile_Object
15134 begin
15135 if Nkind (N) = N_Defining_Identifier then
15136 return Is_Volatile (N) or else Is_Volatile (Etype (N));
15138 elsif Nkind (N) = N_Expanded_Name then
15139 return Is_Volatile_Object (Entity (N));
15141 elsif Is_Volatile (Etype (N))
15142 or else (Is_Entity_Name (N) and then Is_Volatile (Entity (N)))
15143 then
15144 return True;
15146 elsif Nkind_In (N, N_Indexed_Component, N_Selected_Component)
15147 and then Is_Volatile_Prefix (Prefix (N))
15148 then
15149 return True;
15151 elsif Nkind (N) = N_Selected_Component
15152 and then Is_Volatile (Entity (Selector_Name (N)))
15153 then
15154 return True;
15156 else
15157 return False;
15158 end if;
15159 end Is_Volatile_Object;
15161 ---------------------------
15162 -- Itype_Has_Declaration --
15163 ---------------------------
15165 function Itype_Has_Declaration (Id : Entity_Id) return Boolean is
15166 begin
15167 pragma Assert (Is_Itype (Id));
15168 return Present (Parent (Id))
15169 and then Nkind_In (Parent (Id), N_Full_Type_Declaration,
15170 N_Subtype_Declaration)
15171 and then Defining_Entity (Parent (Id)) = Id;
15172 end Itype_Has_Declaration;
15174 -------------------------
15175 -- Kill_Current_Values --
15176 -------------------------
15178 procedure Kill_Current_Values
15179 (Ent : Entity_Id;
15180 Last_Assignment_Only : Boolean := False)
15182 begin
15183 if Is_Assignable (Ent) then
15184 Set_Last_Assignment (Ent, Empty);
15185 end if;
15187 if Is_Object (Ent) then
15188 if not Last_Assignment_Only then
15189 Kill_Checks (Ent);
15190 Set_Current_Value (Ent, Empty);
15192 -- Do not reset the Is_Known_[Non_]Null and Is_Known_Valid flags
15193 -- for a constant. Once the constant is elaborated, its value is
15194 -- not changed, therefore the associated flags that describe the
15195 -- value should not be modified either.
15197 if Ekind (Ent) = E_Constant then
15198 null;
15200 -- Non-constant entities
15202 else
15203 if not Can_Never_Be_Null (Ent) then
15204 Set_Is_Known_Non_Null (Ent, False);
15205 end if;
15207 Set_Is_Known_Null (Ent, False);
15209 -- Reset the Is_Known_Valid flag unless the type is always
15210 -- valid. This does not apply to a loop parameter because its
15211 -- bounds are defined by the loop header and therefore always
15212 -- valid.
15214 if not Is_Known_Valid (Etype (Ent))
15215 and then Ekind (Ent) /= E_Loop_Parameter
15216 then
15217 Set_Is_Known_Valid (Ent, False);
15218 end if;
15219 end if;
15220 end if;
15221 end if;
15222 end Kill_Current_Values;
15224 procedure Kill_Current_Values (Last_Assignment_Only : Boolean := False) is
15225 S : Entity_Id;
15227 procedure Kill_Current_Values_For_Entity_Chain (E : Entity_Id);
15228 -- Clear current value for entity E and all entities chained to E
15230 ------------------------------------------
15231 -- Kill_Current_Values_For_Entity_Chain --
15232 ------------------------------------------
15234 procedure Kill_Current_Values_For_Entity_Chain (E : Entity_Id) is
15235 Ent : Entity_Id;
15236 begin
15237 Ent := E;
15238 while Present (Ent) loop
15239 Kill_Current_Values (Ent, Last_Assignment_Only);
15240 Next_Entity (Ent);
15241 end loop;
15242 end Kill_Current_Values_For_Entity_Chain;
15244 -- Start of processing for Kill_Current_Values
15246 begin
15247 -- Kill all saved checks, a special case of killing saved values
15249 if not Last_Assignment_Only then
15250 Kill_All_Checks;
15251 end if;
15253 -- Loop through relevant scopes, which includes the current scope and
15254 -- any parent scopes if the current scope is a block or a package.
15256 S := Current_Scope;
15257 Scope_Loop : loop
15259 -- Clear current values of all entities in current scope
15261 Kill_Current_Values_For_Entity_Chain (First_Entity (S));
15263 -- If scope is a package, also clear current values of all private
15264 -- entities in the scope.
15266 if Is_Package_Or_Generic_Package (S)
15267 or else Is_Concurrent_Type (S)
15268 then
15269 Kill_Current_Values_For_Entity_Chain (First_Private_Entity (S));
15270 end if;
15272 -- If this is a not a subprogram, deal with parents
15274 if not Is_Subprogram (S) then
15275 S := Scope (S);
15276 exit Scope_Loop when S = Standard_Standard;
15277 else
15278 exit Scope_Loop;
15279 end if;
15280 end loop Scope_Loop;
15281 end Kill_Current_Values;
15283 --------------------------
15284 -- Kill_Size_Check_Code --
15285 --------------------------
15287 procedure Kill_Size_Check_Code (E : Entity_Id) is
15288 begin
15289 if (Ekind (E) = E_Constant or else Ekind (E) = E_Variable)
15290 and then Present (Size_Check_Code (E))
15291 then
15292 Remove (Size_Check_Code (E));
15293 Set_Size_Check_Code (E, Empty);
15294 end if;
15295 end Kill_Size_Check_Code;
15297 --------------------------
15298 -- Known_To_Be_Assigned --
15299 --------------------------
15301 function Known_To_Be_Assigned (N : Node_Id) return Boolean is
15302 P : constant Node_Id := Parent (N);
15304 begin
15305 case Nkind (P) is
15307 -- Test left side of assignment
15309 when N_Assignment_Statement =>
15310 return N = Name (P);
15312 -- Function call arguments are never lvalues
15314 when N_Function_Call =>
15315 return False;
15317 -- Positional parameter for procedure or accept call
15319 when N_Procedure_Call_Statement |
15320 N_Accept_Statement
15322 declare
15323 Proc : Entity_Id;
15324 Form : Entity_Id;
15325 Act : Node_Id;
15327 begin
15328 Proc := Get_Subprogram_Entity (P);
15330 if No (Proc) then
15331 return False;
15332 end if;
15334 -- If we are not a list member, something is strange, so
15335 -- be conservative and return False.
15337 if not Is_List_Member (N) then
15338 return False;
15339 end if;
15341 -- We are going to find the right formal by stepping forward
15342 -- through the formals, as we step backwards in the actuals.
15344 Form := First_Formal (Proc);
15345 Act := N;
15346 loop
15347 -- If no formal, something is weird, so be conservative
15348 -- and return False.
15350 if No (Form) then
15351 return False;
15352 end if;
15354 Prev (Act);
15355 exit when No (Act);
15356 Next_Formal (Form);
15357 end loop;
15359 return Ekind (Form) /= E_In_Parameter;
15360 end;
15362 -- Named parameter for procedure or accept call
15364 when N_Parameter_Association =>
15365 declare
15366 Proc : Entity_Id;
15367 Form : Entity_Id;
15369 begin
15370 Proc := Get_Subprogram_Entity (Parent (P));
15372 if No (Proc) then
15373 return False;
15374 end if;
15376 -- Loop through formals to find the one that matches
15378 Form := First_Formal (Proc);
15379 loop
15380 -- If no matching formal, that's peculiar, some kind of
15381 -- previous error, so return False to be conservative.
15382 -- Actually this also happens in legal code in the case
15383 -- where P is a parameter association for an Extra_Formal???
15385 if No (Form) then
15386 return False;
15387 end if;
15389 -- Else test for match
15391 if Chars (Form) = Chars (Selector_Name (P)) then
15392 return Ekind (Form) /= E_In_Parameter;
15393 end if;
15395 Next_Formal (Form);
15396 end loop;
15397 end;
15399 -- Test for appearing in a conversion that itself appears
15400 -- in an lvalue context, since this should be an lvalue.
15402 when N_Type_Conversion =>
15403 return Known_To_Be_Assigned (P);
15405 -- All other references are definitely not known to be modifications
15407 when others =>
15408 return False;
15410 end case;
15411 end Known_To_Be_Assigned;
15413 ---------------------------
15414 -- Last_Source_Statement --
15415 ---------------------------
15417 function Last_Source_Statement (HSS : Node_Id) return Node_Id is
15418 N : Node_Id;
15420 begin
15421 N := Last (Statements (HSS));
15422 while Present (N) loop
15423 exit when Comes_From_Source (N);
15424 Prev (N);
15425 end loop;
15427 return N;
15428 end Last_Source_Statement;
15430 ----------------------------------
15431 -- Matching_Static_Array_Bounds --
15432 ----------------------------------
15434 function Matching_Static_Array_Bounds
15435 (L_Typ : Node_Id;
15436 R_Typ : Node_Id) return Boolean
15438 L_Ndims : constant Nat := Number_Dimensions (L_Typ);
15439 R_Ndims : constant Nat := Number_Dimensions (R_Typ);
15441 L_Index : Node_Id;
15442 R_Index : Node_Id;
15443 L_Low : Node_Id;
15444 L_High : Node_Id;
15445 L_Len : Uint;
15446 R_Low : Node_Id;
15447 R_High : Node_Id;
15448 R_Len : Uint;
15450 begin
15451 if L_Ndims /= R_Ndims then
15452 return False;
15453 end if;
15455 -- Unconstrained types do not have static bounds
15457 if not Is_Constrained (L_Typ) or else not Is_Constrained (R_Typ) then
15458 return False;
15459 end if;
15461 -- First treat specially the first dimension, as the lower bound and
15462 -- length of string literals are not stored like those of arrays.
15464 if Ekind (L_Typ) = E_String_Literal_Subtype then
15465 L_Low := String_Literal_Low_Bound (L_Typ);
15466 L_Len := String_Literal_Length (L_Typ);
15467 else
15468 L_Index := First_Index (L_Typ);
15469 Get_Index_Bounds (L_Index, L_Low, L_High);
15471 if Is_OK_Static_Expression (L_Low)
15472 and then
15473 Is_OK_Static_Expression (L_High)
15474 then
15475 if Expr_Value (L_High) < Expr_Value (L_Low) then
15476 L_Len := Uint_0;
15477 else
15478 L_Len := (Expr_Value (L_High) - Expr_Value (L_Low)) + 1;
15479 end if;
15480 else
15481 return False;
15482 end if;
15483 end if;
15485 if Ekind (R_Typ) = E_String_Literal_Subtype then
15486 R_Low := String_Literal_Low_Bound (R_Typ);
15487 R_Len := String_Literal_Length (R_Typ);
15488 else
15489 R_Index := First_Index (R_Typ);
15490 Get_Index_Bounds (R_Index, R_Low, R_High);
15492 if Is_OK_Static_Expression (R_Low)
15493 and then
15494 Is_OK_Static_Expression (R_High)
15495 then
15496 if Expr_Value (R_High) < Expr_Value (R_Low) then
15497 R_Len := Uint_0;
15498 else
15499 R_Len := (Expr_Value (R_High) - Expr_Value (R_Low)) + 1;
15500 end if;
15501 else
15502 return False;
15503 end if;
15504 end if;
15506 if (Is_OK_Static_Expression (L_Low)
15507 and then
15508 Is_OK_Static_Expression (R_Low))
15509 and then Expr_Value (L_Low) = Expr_Value (R_Low)
15510 and then L_Len = R_Len
15511 then
15512 null;
15513 else
15514 return False;
15515 end if;
15517 -- Then treat all other dimensions
15519 for Indx in 2 .. L_Ndims loop
15520 Next (L_Index);
15521 Next (R_Index);
15523 Get_Index_Bounds (L_Index, L_Low, L_High);
15524 Get_Index_Bounds (R_Index, R_Low, R_High);
15526 if (Is_OK_Static_Expression (L_Low) and then
15527 Is_OK_Static_Expression (L_High) and then
15528 Is_OK_Static_Expression (R_Low) and then
15529 Is_OK_Static_Expression (R_High))
15530 and then (Expr_Value (L_Low) = Expr_Value (R_Low)
15531 and then
15532 Expr_Value (L_High) = Expr_Value (R_High))
15533 then
15534 null;
15535 else
15536 return False;
15537 end if;
15538 end loop;
15540 -- If we fall through the loop, all indexes matched
15542 return True;
15543 end Matching_Static_Array_Bounds;
15545 -------------------
15546 -- May_Be_Lvalue --
15547 -------------------
15549 function May_Be_Lvalue (N : Node_Id) return Boolean is
15550 P : constant Node_Id := Parent (N);
15552 begin
15553 case Nkind (P) is
15555 -- Test left side of assignment
15557 when N_Assignment_Statement =>
15558 return N = Name (P);
15560 -- Test prefix of component or attribute. Note that the prefix of an
15561 -- explicit or implicit dereference cannot be an l-value.
15563 when N_Attribute_Reference =>
15564 return N = Prefix (P)
15565 and then Name_Implies_Lvalue_Prefix (Attribute_Name (P));
15567 -- For an expanded name, the name is an lvalue if the expanded name
15568 -- is an lvalue, but the prefix is never an lvalue, since it is just
15569 -- the scope where the name is found.
15571 when N_Expanded_Name =>
15572 if N = Prefix (P) then
15573 return May_Be_Lvalue (P);
15574 else
15575 return False;
15576 end if;
15578 -- For a selected component A.B, A is certainly an lvalue if A.B is.
15579 -- B is a little interesting, if we have A.B := 3, there is some
15580 -- discussion as to whether B is an lvalue or not, we choose to say
15581 -- it is. Note however that A is not an lvalue if it is of an access
15582 -- type since this is an implicit dereference.
15584 when N_Selected_Component =>
15585 if N = Prefix (P)
15586 and then Present (Etype (N))
15587 and then Is_Access_Type (Etype (N))
15588 then
15589 return False;
15590 else
15591 return May_Be_Lvalue (P);
15592 end if;
15594 -- For an indexed component or slice, the index or slice bounds is
15595 -- never an lvalue. The prefix is an lvalue if the indexed component
15596 -- or slice is an lvalue, except if it is an access type, where we
15597 -- have an implicit dereference.
15599 when N_Indexed_Component | N_Slice =>
15600 if N /= Prefix (P)
15601 or else (Present (Etype (N)) and then Is_Access_Type (Etype (N)))
15602 then
15603 return False;
15604 else
15605 return May_Be_Lvalue (P);
15606 end if;
15608 -- Prefix of a reference is an lvalue if the reference is an lvalue
15610 when N_Reference =>
15611 return May_Be_Lvalue (P);
15613 -- Prefix of explicit dereference is never an lvalue
15615 when N_Explicit_Dereference =>
15616 return False;
15618 -- Positional parameter for subprogram, entry, or accept call.
15619 -- In older versions of Ada function call arguments are never
15620 -- lvalues. In Ada 2012 functions can have in-out parameters.
15622 when N_Subprogram_Call |
15623 N_Entry_Call_Statement |
15624 N_Accept_Statement
15626 if Nkind (P) = N_Function_Call and then Ada_Version < Ada_2012 then
15627 return False;
15628 end if;
15630 -- The following mechanism is clumsy and fragile. A single flag
15631 -- set in Resolve_Actuals would be preferable ???
15633 declare
15634 Proc : Entity_Id;
15635 Form : Entity_Id;
15636 Act : Node_Id;
15638 begin
15639 Proc := Get_Subprogram_Entity (P);
15641 if No (Proc) then
15642 return True;
15643 end if;
15645 -- If we are not a list member, something is strange, so be
15646 -- conservative and return True.
15648 if not Is_List_Member (N) then
15649 return True;
15650 end if;
15652 -- We are going to find the right formal by stepping forward
15653 -- through the formals, as we step backwards in the actuals.
15655 Form := First_Formal (Proc);
15656 Act := N;
15657 loop
15658 -- If no formal, something is weird, so be conservative and
15659 -- return True.
15661 if No (Form) then
15662 return True;
15663 end if;
15665 Prev (Act);
15666 exit when No (Act);
15667 Next_Formal (Form);
15668 end loop;
15670 return Ekind (Form) /= E_In_Parameter;
15671 end;
15673 -- Named parameter for procedure or accept call
15675 when N_Parameter_Association =>
15676 declare
15677 Proc : Entity_Id;
15678 Form : Entity_Id;
15680 begin
15681 Proc := Get_Subprogram_Entity (Parent (P));
15683 if No (Proc) then
15684 return True;
15685 end if;
15687 -- Loop through formals to find the one that matches
15689 Form := First_Formal (Proc);
15690 loop
15691 -- If no matching formal, that's peculiar, some kind of
15692 -- previous error, so return True to be conservative.
15693 -- Actually happens with legal code for an unresolved call
15694 -- where we may get the wrong homonym???
15696 if No (Form) then
15697 return True;
15698 end if;
15700 -- Else test for match
15702 if Chars (Form) = Chars (Selector_Name (P)) then
15703 return Ekind (Form) /= E_In_Parameter;
15704 end if;
15706 Next_Formal (Form);
15707 end loop;
15708 end;
15710 -- Test for appearing in a conversion that itself appears in an
15711 -- lvalue context, since this should be an lvalue.
15713 when N_Type_Conversion =>
15714 return May_Be_Lvalue (P);
15716 -- Test for appearance in object renaming declaration
15718 when N_Object_Renaming_Declaration =>
15719 return True;
15721 -- All other references are definitely not lvalues
15723 when others =>
15724 return False;
15726 end case;
15727 end May_Be_Lvalue;
15729 -----------------------
15730 -- Mark_Coextensions --
15731 -----------------------
15733 procedure Mark_Coextensions (Context_Nod : Node_Id; Root_Nod : Node_Id) is
15734 Is_Dynamic : Boolean;
15735 -- Indicates whether the context causes nested coextensions to be
15736 -- dynamic or static
15738 function Mark_Allocator (N : Node_Id) return Traverse_Result;
15739 -- Recognize an allocator node and label it as a dynamic coextension
15741 --------------------
15742 -- Mark_Allocator --
15743 --------------------
15745 function Mark_Allocator (N : Node_Id) return Traverse_Result is
15746 begin
15747 if Nkind (N) = N_Allocator then
15748 if Is_Dynamic then
15749 Set_Is_Dynamic_Coextension (N);
15751 -- If the allocator expression is potentially dynamic, it may
15752 -- be expanded out of order and require dynamic allocation
15753 -- anyway, so we treat the coextension itself as dynamic.
15754 -- Potential optimization ???
15756 elsif Nkind (Expression (N)) = N_Qualified_Expression
15757 and then Nkind (Expression (Expression (N))) = N_Op_Concat
15758 then
15759 Set_Is_Dynamic_Coextension (N);
15760 else
15761 Set_Is_Static_Coextension (N);
15762 end if;
15763 end if;
15765 return OK;
15766 end Mark_Allocator;
15768 procedure Mark_Allocators is new Traverse_Proc (Mark_Allocator);
15770 -- Start of processing for Mark_Coextensions
15772 begin
15773 -- An allocator that appears on the right-hand side of an assignment is
15774 -- treated as a potentially dynamic coextension when the right-hand side
15775 -- is an allocator or a qualified expression.
15777 -- Obj := new ...'(new Coextension ...);
15779 if Nkind (Context_Nod) = N_Assignment_Statement then
15780 Is_Dynamic :=
15781 Nkind_In (Expression (Context_Nod), N_Allocator,
15782 N_Qualified_Expression);
15784 -- An allocator that appears within the expression of a simple return
15785 -- statement is treated as a potentially dynamic coextension when the
15786 -- expression is either aggregate, allocator, or qualified expression.
15788 -- return (new Coextension ...);
15789 -- return new ...'(new Coextension ...);
15791 elsif Nkind (Context_Nod) = N_Simple_Return_Statement then
15792 Is_Dynamic :=
15793 Nkind_In (Expression (Context_Nod), N_Aggregate,
15794 N_Allocator,
15795 N_Qualified_Expression);
15797 -- An alloctor that appears within the initialization expression of an
15798 -- object declaration is considered a potentially dynamic coextension
15799 -- when the initialization expression is an allocator or a qualified
15800 -- expression.
15802 -- Obj : ... := new ...'(new Coextension ...);
15804 -- A similar case arises when the object declaration is part of an
15805 -- extended return statement.
15807 -- return Obj : ... := new ...'(new Coextension ...);
15808 -- return Obj : ... := (new Coextension ...);
15810 elsif Nkind (Context_Nod) = N_Object_Declaration then
15811 Is_Dynamic :=
15812 Nkind_In (Root_Nod, N_Allocator, N_Qualified_Expression)
15813 or else
15814 Nkind (Parent (Context_Nod)) = N_Extended_Return_Statement;
15816 -- This routine should not be called with constructs that cannot contain
15817 -- coextensions.
15819 else
15820 raise Program_Error;
15821 end if;
15823 Mark_Allocators (Root_Nod);
15824 end Mark_Coextensions;
15826 ----------------------
15827 -- Needs_One_Actual --
15828 ----------------------
15830 function Needs_One_Actual (E : Entity_Id) return Boolean is
15831 Formal : Entity_Id;
15833 begin
15834 -- Ada 2005 or later, and formals present
15836 if Ada_Version >= Ada_2005 and then Present (First_Formal (E)) then
15837 Formal := Next_Formal (First_Formal (E));
15838 while Present (Formal) loop
15839 if No (Default_Value (Formal)) then
15840 return False;
15841 end if;
15843 Next_Formal (Formal);
15844 end loop;
15846 return True;
15848 -- Ada 83/95 or no formals
15850 else
15851 return False;
15852 end if;
15853 end Needs_One_Actual;
15855 ------------------------
15856 -- New_Copy_List_Tree --
15857 ------------------------
15859 function New_Copy_List_Tree (List : List_Id) return List_Id is
15860 NL : List_Id;
15861 E : Node_Id;
15863 begin
15864 if List = No_List then
15865 return No_List;
15867 else
15868 NL := New_List;
15869 E := First (List);
15871 while Present (E) loop
15872 Append (New_Copy_Tree (E), NL);
15873 E := Next (E);
15874 end loop;
15876 return NL;
15877 end if;
15878 end New_Copy_List_Tree;
15880 --------------------------------------------------
15881 -- New_Copy_Tree Auxiliary Data and Subprograms --
15882 --------------------------------------------------
15884 use Atree.Unchecked_Access;
15885 use Atree_Private_Part;
15887 -- Our approach here requires a two pass traversal of the tree. The
15888 -- first pass visits all nodes that eventually will be copied looking
15889 -- for defining Itypes. If any defining Itypes are found, then they are
15890 -- copied, and an entry is added to the replacement map. In the second
15891 -- phase, the tree is copied, using the replacement map to replace any
15892 -- Itype references within the copied tree.
15894 -- The following hash tables are used if the Map supplied has more
15895 -- than hash threshold entries to speed up access to the map. If
15896 -- there are fewer entries, then the map is searched sequentially
15897 -- (because setting up a hash table for only a few entries takes
15898 -- more time than it saves.
15900 function New_Copy_Hash (E : Entity_Id) return NCT_Header_Num;
15901 -- Hash function used for hash operations
15903 -------------------
15904 -- New_Copy_Hash --
15905 -------------------
15907 function New_Copy_Hash (E : Entity_Id) return NCT_Header_Num is
15908 begin
15909 return Nat (E) mod (NCT_Header_Num'Last + 1);
15910 end New_Copy_Hash;
15912 ---------------
15913 -- NCT_Assoc --
15914 ---------------
15916 -- The hash table NCT_Assoc associates old entities in the table
15917 -- with their corresponding new entities (i.e. the pairs of entries
15918 -- presented in the original Map argument are Key-Element pairs).
15920 package NCT_Assoc is new Simple_HTable (
15921 Header_Num => NCT_Header_Num,
15922 Element => Entity_Id,
15923 No_Element => Empty,
15924 Key => Entity_Id,
15925 Hash => New_Copy_Hash,
15926 Equal => Types."=");
15928 ---------------------
15929 -- NCT_Itype_Assoc --
15930 ---------------------
15932 -- The hash table NCT_Itype_Assoc contains entries only for those
15933 -- old nodes which have a non-empty Associated_Node_For_Itype set.
15934 -- The key is the associated node, and the element is the new node
15935 -- itself (NOT the associated node for the new node).
15937 package NCT_Itype_Assoc is new Simple_HTable (
15938 Header_Num => NCT_Header_Num,
15939 Element => Entity_Id,
15940 No_Element => Empty,
15941 Key => Entity_Id,
15942 Hash => New_Copy_Hash,
15943 Equal => Types."=");
15945 -------------------
15946 -- New_Copy_Tree --
15947 -------------------
15949 function New_Copy_Tree
15950 (Source : Node_Id;
15951 Map : Elist_Id := No_Elist;
15952 New_Sloc : Source_Ptr := No_Location;
15953 New_Scope : Entity_Id := Empty) return Node_Id
15955 Actual_Map : Elist_Id := Map;
15956 -- This is the actual map for the copy. It is initialized with the
15957 -- given elements, and then enlarged as required for Itypes that are
15958 -- copied during the first phase of the copy operation. The visit
15959 -- procedures add elements to this map as Itypes are encountered.
15960 -- The reason we cannot use Map directly, is that it may well be
15961 -- (and normally is) initialized to No_Elist, and if we have mapped
15962 -- entities, we have to reset it to point to a real Elist.
15964 function Assoc (N : Node_Or_Entity_Id) return Node_Id;
15965 -- Called during second phase to map entities into their corresponding
15966 -- copies using Actual_Map. If the argument is not an entity, or is not
15967 -- in Actual_Map, then it is returned unchanged.
15969 procedure Build_NCT_Hash_Tables;
15970 -- Builds hash tables (number of elements >= threshold value)
15972 function Copy_Elist_With_Replacement
15973 (Old_Elist : Elist_Id) return Elist_Id;
15974 -- Called during second phase to copy element list doing replacements
15976 procedure Copy_Itype_With_Replacement (New_Itype : Entity_Id);
15977 -- Called during the second phase to process a copied Itype. The actual
15978 -- copy happened during the first phase (so that we could make the entry
15979 -- in the mapping), but we still have to deal with the descendants of
15980 -- the copied Itype and copy them where necessary.
15982 function Copy_List_With_Replacement (Old_List : List_Id) return List_Id;
15983 -- Called during second phase to copy list doing replacements
15985 function Copy_Node_With_Replacement (Old_Node : Node_Id) return Node_Id;
15986 -- Called during second phase to copy node doing replacements
15988 procedure Visit_Elist (E : Elist_Id);
15989 -- Called during first phase to visit all elements of an Elist
15991 procedure Visit_Field (F : Union_Id; N : Node_Id);
15992 -- Visit a single field, recursing to call Visit_Node or Visit_List
15993 -- if the field is a syntactic descendant of the current node (i.e.
15994 -- its parent is Node N).
15996 procedure Visit_Itype (Old_Itype : Entity_Id);
15997 -- Called during first phase to visit subsidiary fields of a defining
15998 -- Itype, and also create a copy and make an entry in the replacement
15999 -- map for the new copy.
16001 procedure Visit_List (L : List_Id);
16002 -- Called during first phase to visit all elements of a List
16004 procedure Visit_Node (N : Node_Or_Entity_Id);
16005 -- Called during first phase to visit a node and all its subtrees
16007 -----------
16008 -- Assoc --
16009 -----------
16011 function Assoc (N : Node_Or_Entity_Id) return Node_Id is
16012 E : Elmt_Id;
16013 Ent : Entity_Id;
16015 begin
16016 if not Has_Extension (N) or else No (Actual_Map) then
16017 return N;
16019 elsif NCT_Hash_Tables_Used then
16020 Ent := NCT_Assoc.Get (Entity_Id (N));
16022 if Present (Ent) then
16023 return Ent;
16024 else
16025 return N;
16026 end if;
16028 -- No hash table used, do serial search
16030 else
16031 E := First_Elmt (Actual_Map);
16032 while Present (E) loop
16033 if Node (E) = N then
16034 return Node (Next_Elmt (E));
16035 else
16036 E := Next_Elmt (Next_Elmt (E));
16037 end if;
16038 end loop;
16039 end if;
16041 return N;
16042 end Assoc;
16044 ---------------------------
16045 -- Build_NCT_Hash_Tables --
16046 ---------------------------
16048 procedure Build_NCT_Hash_Tables is
16049 Elmt : Elmt_Id;
16050 Ent : Entity_Id;
16051 begin
16052 if NCT_Hash_Table_Setup then
16053 NCT_Assoc.Reset;
16054 NCT_Itype_Assoc.Reset;
16055 end if;
16057 Elmt := First_Elmt (Actual_Map);
16058 while Present (Elmt) loop
16059 Ent := Node (Elmt);
16061 -- Get new entity, and associate old and new
16063 Next_Elmt (Elmt);
16064 NCT_Assoc.Set (Ent, Node (Elmt));
16066 if Is_Type (Ent) then
16067 declare
16068 Anode : constant Entity_Id :=
16069 Associated_Node_For_Itype (Ent);
16071 begin
16072 if Present (Anode) then
16074 -- Enter a link between the associated node of the
16075 -- old Itype and the new Itype, for updating later
16076 -- when node is copied.
16078 NCT_Itype_Assoc.Set (Anode, Node (Elmt));
16079 end if;
16080 end;
16081 end if;
16083 Next_Elmt (Elmt);
16084 end loop;
16086 NCT_Hash_Tables_Used := True;
16087 NCT_Hash_Table_Setup := True;
16088 end Build_NCT_Hash_Tables;
16090 ---------------------------------
16091 -- Copy_Elist_With_Replacement --
16092 ---------------------------------
16094 function Copy_Elist_With_Replacement
16095 (Old_Elist : Elist_Id) return Elist_Id
16097 M : Elmt_Id;
16098 New_Elist : Elist_Id;
16100 begin
16101 if No (Old_Elist) then
16102 return No_Elist;
16104 else
16105 New_Elist := New_Elmt_List;
16107 M := First_Elmt (Old_Elist);
16108 while Present (M) loop
16109 Append_Elmt (Copy_Node_With_Replacement (Node (M)), New_Elist);
16110 Next_Elmt (M);
16111 end loop;
16112 end if;
16114 return New_Elist;
16115 end Copy_Elist_With_Replacement;
16117 ---------------------------------
16118 -- Copy_Itype_With_Replacement --
16119 ---------------------------------
16121 -- This routine exactly parallels its phase one analog Visit_Itype,
16123 procedure Copy_Itype_With_Replacement (New_Itype : Entity_Id) is
16124 begin
16125 -- Translate Next_Entity, Scope, and Etype fields, in case they
16126 -- reference entities that have been mapped into copies.
16128 Set_Next_Entity (New_Itype, Assoc (Next_Entity (New_Itype)));
16129 Set_Etype (New_Itype, Assoc (Etype (New_Itype)));
16131 if Present (New_Scope) then
16132 Set_Scope (New_Itype, New_Scope);
16133 else
16134 Set_Scope (New_Itype, Assoc (Scope (New_Itype)));
16135 end if;
16137 -- Copy referenced fields
16139 if Is_Discrete_Type (New_Itype) then
16140 Set_Scalar_Range (New_Itype,
16141 Copy_Node_With_Replacement (Scalar_Range (New_Itype)));
16143 elsif Has_Discriminants (Base_Type (New_Itype)) then
16144 Set_Discriminant_Constraint (New_Itype,
16145 Copy_Elist_With_Replacement
16146 (Discriminant_Constraint (New_Itype)));
16148 elsif Is_Array_Type (New_Itype) then
16149 if Present (First_Index (New_Itype)) then
16150 Set_First_Index (New_Itype,
16151 First (Copy_List_With_Replacement
16152 (List_Containing (First_Index (New_Itype)))));
16153 end if;
16155 if Is_Packed (New_Itype) then
16156 Set_Packed_Array_Impl_Type (New_Itype,
16157 Copy_Node_With_Replacement
16158 (Packed_Array_Impl_Type (New_Itype)));
16159 end if;
16160 end if;
16161 end Copy_Itype_With_Replacement;
16163 --------------------------------
16164 -- Copy_List_With_Replacement --
16165 --------------------------------
16167 function Copy_List_With_Replacement
16168 (Old_List : List_Id) return List_Id
16170 New_List : List_Id;
16171 E : Node_Id;
16173 begin
16174 if Old_List = No_List then
16175 return No_List;
16177 else
16178 New_List := Empty_List;
16180 E := First (Old_List);
16181 while Present (E) loop
16182 Append (Copy_Node_With_Replacement (E), New_List);
16183 Next (E);
16184 end loop;
16186 return New_List;
16187 end if;
16188 end Copy_List_With_Replacement;
16190 --------------------------------
16191 -- Copy_Node_With_Replacement --
16192 --------------------------------
16194 function Copy_Node_With_Replacement
16195 (Old_Node : Node_Id) return Node_Id
16197 New_Node : Node_Id;
16199 procedure Adjust_Named_Associations
16200 (Old_Node : Node_Id;
16201 New_Node : Node_Id);
16202 -- If a call node has named associations, these are chained through
16203 -- the First_Named_Actual, Next_Named_Actual links. These must be
16204 -- propagated separately to the new parameter list, because these
16205 -- are not syntactic fields.
16207 function Copy_Field_With_Replacement
16208 (Field : Union_Id) return Union_Id;
16209 -- Given Field, which is a field of Old_Node, return a copy of it
16210 -- if it is a syntactic field (i.e. its parent is Node), setting
16211 -- the parent of the copy to poit to New_Node. Otherwise returns
16212 -- the field (possibly mapped if it is an entity).
16214 -------------------------------
16215 -- Adjust_Named_Associations --
16216 -------------------------------
16218 procedure Adjust_Named_Associations
16219 (Old_Node : Node_Id;
16220 New_Node : Node_Id)
16222 Old_E : Node_Id;
16223 New_E : Node_Id;
16225 Old_Next : Node_Id;
16226 New_Next : Node_Id;
16228 begin
16229 Old_E := First (Parameter_Associations (Old_Node));
16230 New_E := First (Parameter_Associations (New_Node));
16231 while Present (Old_E) loop
16232 if Nkind (Old_E) = N_Parameter_Association
16233 and then Present (Next_Named_Actual (Old_E))
16234 then
16235 if First_Named_Actual (Old_Node)
16236 = Explicit_Actual_Parameter (Old_E)
16237 then
16238 Set_First_Named_Actual
16239 (New_Node, Explicit_Actual_Parameter (New_E));
16240 end if;
16242 -- Now scan parameter list from the beginning,to locate
16243 -- next named actual, which can be out of order.
16245 Old_Next := First (Parameter_Associations (Old_Node));
16246 New_Next := First (Parameter_Associations (New_Node));
16248 while Nkind (Old_Next) /= N_Parameter_Association
16249 or else Explicit_Actual_Parameter (Old_Next) /=
16250 Next_Named_Actual (Old_E)
16251 loop
16252 Next (Old_Next);
16253 Next (New_Next);
16254 end loop;
16256 Set_Next_Named_Actual
16257 (New_E, Explicit_Actual_Parameter (New_Next));
16258 end if;
16260 Next (Old_E);
16261 Next (New_E);
16262 end loop;
16263 end Adjust_Named_Associations;
16265 ---------------------------------
16266 -- Copy_Field_With_Replacement --
16267 ---------------------------------
16269 function Copy_Field_With_Replacement
16270 (Field : Union_Id) return Union_Id
16272 begin
16273 if Field = Union_Id (Empty) then
16274 return Field;
16276 elsif Field in Node_Range then
16277 declare
16278 Old_N : constant Node_Id := Node_Id (Field);
16279 New_N : Node_Id;
16281 begin
16282 -- If syntactic field, as indicated by the parent pointer
16283 -- being set, then copy the referenced node recursively.
16285 if Parent (Old_N) = Old_Node then
16286 New_N := Copy_Node_With_Replacement (Old_N);
16288 if New_N /= Old_N then
16289 Set_Parent (New_N, New_Node);
16290 end if;
16292 -- For semantic fields, update possible entity reference
16293 -- from the replacement map.
16295 else
16296 New_N := Assoc (Old_N);
16297 end if;
16299 return Union_Id (New_N);
16300 end;
16302 elsif Field in List_Range then
16303 declare
16304 Old_L : constant List_Id := List_Id (Field);
16305 New_L : List_Id;
16307 begin
16308 -- If syntactic field, as indicated by the parent pointer,
16309 -- then recursively copy the entire referenced list.
16311 if Parent (Old_L) = Old_Node then
16312 New_L := Copy_List_With_Replacement (Old_L);
16313 Set_Parent (New_L, New_Node);
16315 -- For semantic list, just returned unchanged
16317 else
16318 New_L := Old_L;
16319 end if;
16321 return Union_Id (New_L);
16322 end;
16324 -- Anything other than a list or a node is returned unchanged
16326 else
16327 return Field;
16328 end if;
16329 end Copy_Field_With_Replacement;
16331 -- Start of processing for Copy_Node_With_Replacement
16333 begin
16334 if Old_Node <= Empty_Or_Error then
16335 return Old_Node;
16337 elsif Has_Extension (Old_Node) then
16338 return Assoc (Old_Node);
16340 else
16341 New_Node := New_Copy (Old_Node);
16343 -- If the node we are copying is the associated node of a
16344 -- previously copied Itype, then adjust the associated node
16345 -- of the copy of that Itype accordingly.
16347 if Present (Actual_Map) then
16348 declare
16349 E : Elmt_Id;
16350 Ent : Entity_Id;
16352 begin
16353 -- Case of hash table used
16355 if NCT_Hash_Tables_Used then
16356 Ent := NCT_Itype_Assoc.Get (Old_Node);
16358 if Present (Ent) then
16359 Set_Associated_Node_For_Itype (Ent, New_Node);
16360 end if;
16362 -- Case of no hash table used
16364 else
16365 E := First_Elmt (Actual_Map);
16366 while Present (E) loop
16367 if Is_Itype (Node (E))
16368 and then
16369 Old_Node = Associated_Node_For_Itype (Node (E))
16370 then
16371 Set_Associated_Node_For_Itype
16372 (Node (Next_Elmt (E)), New_Node);
16373 end if;
16375 E := Next_Elmt (Next_Elmt (E));
16376 end loop;
16377 end if;
16378 end;
16379 end if;
16381 -- Recursively copy descendants
16383 Set_Field1
16384 (New_Node, Copy_Field_With_Replacement (Field1 (New_Node)));
16385 Set_Field2
16386 (New_Node, Copy_Field_With_Replacement (Field2 (New_Node)));
16387 Set_Field3
16388 (New_Node, Copy_Field_With_Replacement (Field3 (New_Node)));
16389 Set_Field4
16390 (New_Node, Copy_Field_With_Replacement (Field4 (New_Node)));
16391 Set_Field5
16392 (New_Node, Copy_Field_With_Replacement (Field5 (New_Node)));
16394 -- Adjust Sloc of new node if necessary
16396 if New_Sloc /= No_Location then
16397 Set_Sloc (New_Node, New_Sloc);
16399 -- If we adjust the Sloc, then we are essentially making a
16400 -- completely new node, so the Comes_From_Source flag should
16401 -- be reset to the proper default value.
16403 Set_Comes_From_Source
16404 (New_Node, Default_Node.Comes_From_Source);
16405 end if;
16407 -- If the node is a call and has named associations, set the
16408 -- corresponding links in the copy.
16410 if Nkind_In (Old_Node, N_Entry_Call_Statement,
16411 N_Function_Call,
16412 N_Procedure_Call_Statement)
16413 and then Present (First_Named_Actual (Old_Node))
16414 then
16415 Adjust_Named_Associations (Old_Node, New_Node);
16416 end if;
16418 -- Reset First_Real_Statement for Handled_Sequence_Of_Statements.
16419 -- The replacement mechanism applies to entities, and is not used
16420 -- here. Eventually we may need a more general graph-copying
16421 -- routine. For now, do a sequential search to find desired node.
16423 if Nkind (Old_Node) = N_Handled_Sequence_Of_Statements
16424 and then Present (First_Real_Statement (Old_Node))
16425 then
16426 declare
16427 Old_F : constant Node_Id := First_Real_Statement (Old_Node);
16428 N1, N2 : Node_Id;
16430 begin
16431 N1 := First (Statements (Old_Node));
16432 N2 := First (Statements (New_Node));
16434 while N1 /= Old_F loop
16435 Next (N1);
16436 Next (N2);
16437 end loop;
16439 Set_First_Real_Statement (New_Node, N2);
16440 end;
16441 end if;
16442 end if;
16444 -- All done, return copied node
16446 return New_Node;
16447 end Copy_Node_With_Replacement;
16449 -----------------
16450 -- Visit_Elist --
16451 -----------------
16453 procedure Visit_Elist (E : Elist_Id) is
16454 Elmt : Elmt_Id;
16455 begin
16456 if Present (E) then
16457 Elmt := First_Elmt (E);
16459 while Elmt /= No_Elmt loop
16460 Visit_Node (Node (Elmt));
16461 Next_Elmt (Elmt);
16462 end loop;
16463 end if;
16464 end Visit_Elist;
16466 -----------------
16467 -- Visit_Field --
16468 -----------------
16470 procedure Visit_Field (F : Union_Id; N : Node_Id) is
16471 begin
16472 if F = Union_Id (Empty) then
16473 return;
16475 elsif F in Node_Range then
16477 -- Copy node if it is syntactic, i.e. its parent pointer is
16478 -- set to point to the field that referenced it (certain
16479 -- Itypes will also meet this criterion, which is fine, since
16480 -- these are clearly Itypes that do need to be copied, since
16481 -- we are copying their parent.)
16483 if Parent (Node_Id (F)) = N then
16484 Visit_Node (Node_Id (F));
16485 return;
16487 -- Another case, if we are pointing to an Itype, then we want
16488 -- to copy it if its associated node is somewhere in the tree
16489 -- being copied.
16491 -- Note: the exclusion of self-referential copies is just an
16492 -- optimization, since the search of the already copied list
16493 -- would catch it, but it is a common case (Etype pointing
16494 -- to itself for an Itype that is a base type).
16496 elsif Has_Extension (Node_Id (F))
16497 and then Is_Itype (Entity_Id (F))
16498 and then Node_Id (F) /= N
16499 then
16500 declare
16501 P : Node_Id;
16503 begin
16504 P := Associated_Node_For_Itype (Node_Id (F));
16505 while Present (P) loop
16506 if P = Source then
16507 Visit_Node (Node_Id (F));
16508 return;
16509 else
16510 P := Parent (P);
16511 end if;
16512 end loop;
16514 -- An Itype whose parent is not being copied definitely
16515 -- should NOT be copied, since it does not belong in any
16516 -- sense to the copied subtree.
16518 return;
16519 end;
16520 end if;
16522 elsif F in List_Range and then Parent (List_Id (F)) = N then
16523 Visit_List (List_Id (F));
16524 return;
16525 end if;
16526 end Visit_Field;
16528 -----------------
16529 -- Visit_Itype --
16530 -----------------
16532 procedure Visit_Itype (Old_Itype : Entity_Id) is
16533 New_Itype : Entity_Id;
16534 E : Elmt_Id;
16535 Ent : Entity_Id;
16537 begin
16538 -- Itypes that describe the designated type of access to subprograms
16539 -- have the structure of subprogram declarations, with signatures,
16540 -- etc. Either we duplicate the signatures completely, or choose to
16541 -- share such itypes, which is fine because their elaboration will
16542 -- have no side effects.
16544 if Ekind (Old_Itype) = E_Subprogram_Type then
16545 return;
16546 end if;
16548 New_Itype := New_Copy (Old_Itype);
16550 -- The new Itype has all the attributes of the old one, and
16551 -- we just copy the contents of the entity. However, the back-end
16552 -- needs different names for debugging purposes, so we create a
16553 -- new internal name for it in all cases.
16555 Set_Chars (New_Itype, New_Internal_Name ('T'));
16557 -- If our associated node is an entity that has already been copied,
16558 -- then set the associated node of the copy to point to the right
16559 -- copy. If we have copied an Itype that is itself the associated
16560 -- node of some previously copied Itype, then we set the right
16561 -- pointer in the other direction.
16563 if Present (Actual_Map) then
16565 -- Case of hash tables used
16567 if NCT_Hash_Tables_Used then
16569 Ent := NCT_Assoc.Get (Associated_Node_For_Itype (Old_Itype));
16571 if Present (Ent) then
16572 Set_Associated_Node_For_Itype (New_Itype, Ent);
16573 end if;
16575 Ent := NCT_Itype_Assoc.Get (Old_Itype);
16576 if Present (Ent) then
16577 Set_Associated_Node_For_Itype (Ent, New_Itype);
16579 -- If the hash table has no association for this Itype and
16580 -- its associated node, enter one now.
16582 else
16583 NCT_Itype_Assoc.Set
16584 (Associated_Node_For_Itype (Old_Itype), New_Itype);
16585 end if;
16587 -- Case of hash tables not used
16589 else
16590 E := First_Elmt (Actual_Map);
16591 while Present (E) loop
16592 if Associated_Node_For_Itype (Old_Itype) = Node (E) then
16593 Set_Associated_Node_For_Itype
16594 (New_Itype, Node (Next_Elmt (E)));
16595 end if;
16597 if Is_Type (Node (E))
16598 and then Old_Itype = Associated_Node_For_Itype (Node (E))
16599 then
16600 Set_Associated_Node_For_Itype
16601 (Node (Next_Elmt (E)), New_Itype);
16602 end if;
16604 E := Next_Elmt (Next_Elmt (E));
16605 end loop;
16606 end if;
16607 end if;
16609 if Present (Freeze_Node (New_Itype)) then
16610 Set_Is_Frozen (New_Itype, False);
16611 Set_Freeze_Node (New_Itype, Empty);
16612 end if;
16614 -- Add new association to map
16616 if No (Actual_Map) then
16617 Actual_Map := New_Elmt_List;
16618 end if;
16620 Append_Elmt (Old_Itype, Actual_Map);
16621 Append_Elmt (New_Itype, Actual_Map);
16623 if NCT_Hash_Tables_Used then
16624 NCT_Assoc.Set (Old_Itype, New_Itype);
16626 else
16627 NCT_Table_Entries := NCT_Table_Entries + 1;
16629 if NCT_Table_Entries > NCT_Hash_Threshold then
16630 Build_NCT_Hash_Tables;
16631 end if;
16632 end if;
16634 -- If a record subtype is simply copied, the entity list will be
16635 -- shared. Thus cloned_Subtype must be set to indicate the sharing.
16637 if Ekind_In (Old_Itype, E_Record_Subtype, E_Class_Wide_Subtype) then
16638 Set_Cloned_Subtype (New_Itype, Old_Itype);
16639 end if;
16641 -- Visit descendants that eventually get copied
16643 Visit_Field (Union_Id (Etype (Old_Itype)), Old_Itype);
16645 if Is_Discrete_Type (Old_Itype) then
16646 Visit_Field (Union_Id (Scalar_Range (Old_Itype)), Old_Itype);
16648 elsif Has_Discriminants (Base_Type (Old_Itype)) then
16649 -- ??? This should involve call to Visit_Field
16650 Visit_Elist (Discriminant_Constraint (Old_Itype));
16652 elsif Is_Array_Type (Old_Itype) then
16653 if Present (First_Index (Old_Itype)) then
16654 Visit_Field (Union_Id (List_Containing
16655 (First_Index (Old_Itype))),
16656 Old_Itype);
16657 end if;
16659 if Is_Packed (Old_Itype) then
16660 Visit_Field (Union_Id (Packed_Array_Impl_Type (Old_Itype)),
16661 Old_Itype);
16662 end if;
16663 end if;
16664 end Visit_Itype;
16666 ----------------
16667 -- Visit_List --
16668 ----------------
16670 procedure Visit_List (L : List_Id) is
16671 N : Node_Id;
16672 begin
16673 if L /= No_List then
16674 N := First (L);
16676 while Present (N) loop
16677 Visit_Node (N);
16678 Next (N);
16679 end loop;
16680 end if;
16681 end Visit_List;
16683 ----------------
16684 -- Visit_Node --
16685 ----------------
16687 procedure Visit_Node (N : Node_Or_Entity_Id) is
16689 -- Start of processing for Visit_Node
16691 begin
16692 -- Handle case of an Itype, which must be copied
16694 if Has_Extension (N) and then Is_Itype (N) then
16696 -- Nothing to do if already in the list. This can happen with an
16697 -- Itype entity that appears more than once in the tree.
16698 -- Note that we do not want to visit descendants in this case.
16700 -- Test for already in list when hash table is used
16702 if NCT_Hash_Tables_Used then
16703 if Present (NCT_Assoc.Get (Entity_Id (N))) then
16704 return;
16705 end if;
16707 -- Test for already in list when hash table not used
16709 else
16710 declare
16711 E : Elmt_Id;
16712 begin
16713 if Present (Actual_Map) then
16714 E := First_Elmt (Actual_Map);
16715 while Present (E) loop
16716 if Node (E) = N then
16717 return;
16718 else
16719 E := Next_Elmt (Next_Elmt (E));
16720 end if;
16721 end loop;
16722 end if;
16723 end;
16724 end if;
16726 Visit_Itype (N);
16727 end if;
16729 -- Visit descendants
16731 Visit_Field (Field1 (N), N);
16732 Visit_Field (Field2 (N), N);
16733 Visit_Field (Field3 (N), N);
16734 Visit_Field (Field4 (N), N);
16735 Visit_Field (Field5 (N), N);
16736 end Visit_Node;
16738 -- Start of processing for New_Copy_Tree
16740 begin
16741 Actual_Map := Map;
16743 -- See if we should use hash table
16745 if No (Actual_Map) then
16746 NCT_Hash_Tables_Used := False;
16748 else
16749 declare
16750 Elmt : Elmt_Id;
16752 begin
16753 NCT_Table_Entries := 0;
16755 Elmt := First_Elmt (Actual_Map);
16756 while Present (Elmt) loop
16757 NCT_Table_Entries := NCT_Table_Entries + 1;
16758 Next_Elmt (Elmt);
16759 Next_Elmt (Elmt);
16760 end loop;
16762 if NCT_Table_Entries > NCT_Hash_Threshold then
16763 Build_NCT_Hash_Tables;
16764 else
16765 NCT_Hash_Tables_Used := False;
16766 end if;
16767 end;
16768 end if;
16770 -- Hash table set up if required, now start phase one by visiting
16771 -- top node (we will recursively visit the descendants).
16773 Visit_Node (Source);
16775 -- Now the second phase of the copy can start. First we process
16776 -- all the mapped entities, copying their descendants.
16778 if Present (Actual_Map) then
16779 declare
16780 Elmt : Elmt_Id;
16781 New_Itype : Entity_Id;
16782 begin
16783 Elmt := First_Elmt (Actual_Map);
16784 while Present (Elmt) loop
16785 Next_Elmt (Elmt);
16786 New_Itype := Node (Elmt);
16788 if Is_Itype (New_Itype) then
16789 Copy_Itype_With_Replacement (New_Itype);
16790 end if;
16791 Next_Elmt (Elmt);
16792 end loop;
16793 end;
16794 end if;
16796 -- Now we can copy the actual tree
16798 return Copy_Node_With_Replacement (Source);
16799 end New_Copy_Tree;
16801 -------------------------
16802 -- New_External_Entity --
16803 -------------------------
16805 function New_External_Entity
16806 (Kind : Entity_Kind;
16807 Scope_Id : Entity_Id;
16808 Sloc_Value : Source_Ptr;
16809 Related_Id : Entity_Id;
16810 Suffix : Character;
16811 Suffix_Index : Nat := 0;
16812 Prefix : Character := ' ') return Entity_Id
16814 N : constant Entity_Id :=
16815 Make_Defining_Identifier (Sloc_Value,
16816 New_External_Name
16817 (Chars (Related_Id), Suffix, Suffix_Index, Prefix));
16819 begin
16820 Set_Ekind (N, Kind);
16821 Set_Is_Internal (N, True);
16822 Append_Entity (N, Scope_Id);
16823 Set_Public_Status (N);
16825 if Kind in Type_Kind then
16826 Init_Size_Align (N);
16827 end if;
16829 return N;
16830 end New_External_Entity;
16832 -------------------------
16833 -- New_Internal_Entity --
16834 -------------------------
16836 function New_Internal_Entity
16837 (Kind : Entity_Kind;
16838 Scope_Id : Entity_Id;
16839 Sloc_Value : Source_Ptr;
16840 Id_Char : Character) return Entity_Id
16842 N : constant Entity_Id := Make_Temporary (Sloc_Value, Id_Char);
16844 begin
16845 Set_Ekind (N, Kind);
16846 Set_Is_Internal (N, True);
16847 Append_Entity (N, Scope_Id);
16849 if Kind in Type_Kind then
16850 Init_Size_Align (N);
16851 end if;
16853 return N;
16854 end New_Internal_Entity;
16856 -----------------
16857 -- Next_Actual --
16858 -----------------
16860 function Next_Actual (Actual_Id : Node_Id) return Node_Id is
16861 N : Node_Id;
16863 begin
16864 -- If we are pointing at a positional parameter, it is a member of a
16865 -- node list (the list of parameters), and the next parameter is the
16866 -- next node on the list, unless we hit a parameter association, then
16867 -- we shift to using the chain whose head is the First_Named_Actual in
16868 -- the parent, and then is threaded using the Next_Named_Actual of the
16869 -- Parameter_Association. All this fiddling is because the original node
16870 -- list is in the textual call order, and what we need is the
16871 -- declaration order.
16873 if Is_List_Member (Actual_Id) then
16874 N := Next (Actual_Id);
16876 if Nkind (N) = N_Parameter_Association then
16877 return First_Named_Actual (Parent (Actual_Id));
16878 else
16879 return N;
16880 end if;
16882 else
16883 return Next_Named_Actual (Parent (Actual_Id));
16884 end if;
16885 end Next_Actual;
16887 procedure Next_Actual (Actual_Id : in out Node_Id) is
16888 begin
16889 Actual_Id := Next_Actual (Actual_Id);
16890 end Next_Actual;
16892 -----------------------
16893 -- Normalize_Actuals --
16894 -----------------------
16896 -- Chain actuals according to formals of subprogram. If there are no named
16897 -- associations, the chain is simply the list of Parameter Associations,
16898 -- since the order is the same as the declaration order. If there are named
16899 -- associations, then the First_Named_Actual field in the N_Function_Call
16900 -- or N_Procedure_Call_Statement node points to the Parameter_Association
16901 -- node for the parameter that comes first in declaration order. The
16902 -- remaining named parameters are then chained in declaration order using
16903 -- Next_Named_Actual.
16905 -- This routine also verifies that the number of actuals is compatible with
16906 -- the number and default values of formals, but performs no type checking
16907 -- (type checking is done by the caller).
16909 -- If the matching succeeds, Success is set to True and the caller proceeds
16910 -- with type-checking. If the match is unsuccessful, then Success is set to
16911 -- False, and the caller attempts a different interpretation, if there is
16912 -- one.
16914 -- If the flag Report is on, the call is not overloaded, and a failure to
16915 -- match can be reported here, rather than in the caller.
16917 procedure Normalize_Actuals
16918 (N : Node_Id;
16919 S : Entity_Id;
16920 Report : Boolean;
16921 Success : out Boolean)
16923 Actuals : constant List_Id := Parameter_Associations (N);
16924 Actual : Node_Id := Empty;
16925 Formal : Entity_Id;
16926 Last : Node_Id := Empty;
16927 First_Named : Node_Id := Empty;
16928 Found : Boolean;
16930 Formals_To_Match : Integer := 0;
16931 Actuals_To_Match : Integer := 0;
16933 procedure Chain (A : Node_Id);
16934 -- Add named actual at the proper place in the list, using the
16935 -- Next_Named_Actual link.
16937 function Reporting return Boolean;
16938 -- Determines if an error is to be reported. To report an error, we
16939 -- need Report to be True, and also we do not report errors caused
16940 -- by calls to init procs that occur within other init procs. Such
16941 -- errors must always be cascaded errors, since if all the types are
16942 -- declared correctly, the compiler will certainly build decent calls.
16944 -----------
16945 -- Chain --
16946 -----------
16948 procedure Chain (A : Node_Id) is
16949 begin
16950 if No (Last) then
16952 -- Call node points to first actual in list
16954 Set_First_Named_Actual (N, Explicit_Actual_Parameter (A));
16956 else
16957 Set_Next_Named_Actual (Last, Explicit_Actual_Parameter (A));
16958 end if;
16960 Last := A;
16961 Set_Next_Named_Actual (Last, Empty);
16962 end Chain;
16964 ---------------
16965 -- Reporting --
16966 ---------------
16968 function Reporting return Boolean is
16969 begin
16970 if not Report then
16971 return False;
16973 elsif not Within_Init_Proc then
16974 return True;
16976 elsif Is_Init_Proc (Entity (Name (N))) then
16977 return False;
16979 else
16980 return True;
16981 end if;
16982 end Reporting;
16984 -- Start of processing for Normalize_Actuals
16986 begin
16987 if Is_Access_Type (S) then
16989 -- The name in the call is a function call that returns an access
16990 -- to subprogram. The designated type has the list of formals.
16992 Formal := First_Formal (Designated_Type (S));
16993 else
16994 Formal := First_Formal (S);
16995 end if;
16997 while Present (Formal) loop
16998 Formals_To_Match := Formals_To_Match + 1;
16999 Next_Formal (Formal);
17000 end loop;
17002 -- Find if there is a named association, and verify that no positional
17003 -- associations appear after named ones.
17005 if Present (Actuals) then
17006 Actual := First (Actuals);
17007 end if;
17009 while Present (Actual)
17010 and then Nkind (Actual) /= N_Parameter_Association
17011 loop
17012 Actuals_To_Match := Actuals_To_Match + 1;
17013 Next (Actual);
17014 end loop;
17016 if No (Actual) and Actuals_To_Match = Formals_To_Match then
17018 -- Most common case: positional notation, no defaults
17020 Success := True;
17021 return;
17023 elsif Actuals_To_Match > Formals_To_Match then
17025 -- Too many actuals: will not work
17027 if Reporting then
17028 if Is_Entity_Name (Name (N)) then
17029 Error_Msg_N ("too many arguments in call to&", Name (N));
17030 else
17031 Error_Msg_N ("too many arguments in call", N);
17032 end if;
17033 end if;
17035 Success := False;
17036 return;
17037 end if;
17039 First_Named := Actual;
17041 while Present (Actual) loop
17042 if Nkind (Actual) /= N_Parameter_Association then
17043 Error_Msg_N
17044 ("positional parameters not allowed after named ones", Actual);
17045 Success := False;
17046 return;
17048 else
17049 Actuals_To_Match := Actuals_To_Match + 1;
17050 end if;
17052 Next (Actual);
17053 end loop;
17055 if Present (Actuals) then
17056 Actual := First (Actuals);
17057 end if;
17059 Formal := First_Formal (S);
17060 while Present (Formal) loop
17062 -- Match the formals in order. If the corresponding actual is
17063 -- positional, nothing to do. Else scan the list of named actuals
17064 -- to find the one with the right name.
17066 if Present (Actual)
17067 and then Nkind (Actual) /= N_Parameter_Association
17068 then
17069 Next (Actual);
17070 Actuals_To_Match := Actuals_To_Match - 1;
17071 Formals_To_Match := Formals_To_Match - 1;
17073 else
17074 -- For named parameters, search the list of actuals to find
17075 -- one that matches the next formal name.
17077 Actual := First_Named;
17078 Found := False;
17079 while Present (Actual) loop
17080 if Chars (Selector_Name (Actual)) = Chars (Formal) then
17081 Found := True;
17082 Chain (Actual);
17083 Actuals_To_Match := Actuals_To_Match - 1;
17084 Formals_To_Match := Formals_To_Match - 1;
17085 exit;
17086 end if;
17088 Next (Actual);
17089 end loop;
17091 if not Found then
17092 if Ekind (Formal) /= E_In_Parameter
17093 or else No (Default_Value (Formal))
17094 then
17095 if Reporting then
17096 if (Comes_From_Source (S)
17097 or else Sloc (S) = Standard_Location)
17098 and then Is_Overloadable (S)
17099 then
17100 if No (Actuals)
17101 and then
17102 Nkind_In (Parent (N), N_Procedure_Call_Statement,
17103 N_Function_Call,
17104 N_Parameter_Association)
17105 and then Ekind (S) /= E_Function
17106 then
17107 Set_Etype (N, Etype (S));
17109 else
17110 Error_Msg_Name_1 := Chars (S);
17111 Error_Msg_Sloc := Sloc (S);
17112 Error_Msg_NE
17113 ("missing argument for parameter & "
17114 & "in call to % declared #", N, Formal);
17115 end if;
17117 elsif Is_Overloadable (S) then
17118 Error_Msg_Name_1 := Chars (S);
17120 -- Point to type derivation that generated the
17121 -- operation.
17123 Error_Msg_Sloc := Sloc (Parent (S));
17125 Error_Msg_NE
17126 ("missing argument for parameter & "
17127 & "in call to % (inherited) #", N, Formal);
17129 else
17130 Error_Msg_NE
17131 ("missing argument for parameter &", N, Formal);
17132 end if;
17133 end if;
17135 Success := False;
17136 return;
17138 else
17139 Formals_To_Match := Formals_To_Match - 1;
17140 end if;
17141 end if;
17142 end if;
17144 Next_Formal (Formal);
17145 end loop;
17147 if Formals_To_Match = 0 and then Actuals_To_Match = 0 then
17148 Success := True;
17149 return;
17151 else
17152 if Reporting then
17154 -- Find some superfluous named actual that did not get
17155 -- attached to the list of associations.
17157 Actual := First (Actuals);
17158 while Present (Actual) loop
17159 if Nkind (Actual) = N_Parameter_Association
17160 and then Actual /= Last
17161 and then No (Next_Named_Actual (Actual))
17162 then
17163 -- A validity check may introduce a copy of a call that
17164 -- includes an extra actual (for example for an unrelated
17165 -- accessibility check). Check that the extra actual matches
17166 -- some extra formal, which must exist already because
17167 -- subprogram must be frozen at this point.
17169 if Present (Extra_Formals (S))
17170 and then not Comes_From_Source (Actual)
17171 and then Nkind (Actual) = N_Parameter_Association
17172 and then Chars (Extra_Formals (S)) =
17173 Chars (Selector_Name (Actual))
17174 then
17175 null;
17176 else
17177 Error_Msg_N
17178 ("unmatched actual & in call", Selector_Name (Actual));
17179 exit;
17180 end if;
17181 end if;
17183 Next (Actual);
17184 end loop;
17185 end if;
17187 Success := False;
17188 return;
17189 end if;
17190 end Normalize_Actuals;
17192 --------------------------------
17193 -- Note_Possible_Modification --
17194 --------------------------------
17196 procedure Note_Possible_Modification (N : Node_Id; Sure : Boolean) is
17197 Modification_Comes_From_Source : constant Boolean :=
17198 Comes_From_Source (Parent (N));
17200 Ent : Entity_Id;
17201 Exp : Node_Id;
17203 begin
17204 -- Loop to find referenced entity, if there is one
17206 Exp := N;
17207 loop
17208 Ent := Empty;
17210 if Is_Entity_Name (Exp) then
17211 Ent := Entity (Exp);
17213 -- If the entity is missing, it is an undeclared identifier,
17214 -- and there is nothing to annotate.
17216 if No (Ent) then
17217 return;
17218 end if;
17220 elsif Nkind (Exp) = N_Explicit_Dereference then
17221 declare
17222 P : constant Node_Id := Prefix (Exp);
17224 begin
17225 -- In formal verification mode, keep track of all reads and
17226 -- writes through explicit dereferences.
17228 if GNATprove_Mode then
17229 SPARK_Specific.Generate_Dereference (N, 'm');
17230 end if;
17232 if Nkind (P) = N_Selected_Component
17233 and then Present (Entry_Formal (Entity (Selector_Name (P))))
17234 then
17235 -- Case of a reference to an entry formal
17237 Ent := Entry_Formal (Entity (Selector_Name (P)));
17239 elsif Nkind (P) = N_Identifier
17240 and then Nkind (Parent (Entity (P))) = N_Object_Declaration
17241 and then Present (Expression (Parent (Entity (P))))
17242 and then Nkind (Expression (Parent (Entity (P)))) =
17243 N_Reference
17244 then
17245 -- Case of a reference to a value on which side effects have
17246 -- been removed.
17248 Exp := Prefix (Expression (Parent (Entity (P))));
17249 goto Continue;
17251 else
17252 return;
17253 end if;
17254 end;
17256 elsif Nkind_In (Exp, N_Type_Conversion,
17257 N_Unchecked_Type_Conversion)
17258 then
17259 Exp := Expression (Exp);
17260 goto Continue;
17262 elsif Nkind_In (Exp, N_Slice,
17263 N_Indexed_Component,
17264 N_Selected_Component)
17265 then
17266 -- Special check, if the prefix is an access type, then return
17267 -- since we are modifying the thing pointed to, not the prefix.
17268 -- When we are expanding, most usually the prefix is replaced
17269 -- by an explicit dereference, and this test is not needed, but
17270 -- in some cases (notably -gnatc mode and generics) when we do
17271 -- not do full expansion, we need this special test.
17273 if Is_Access_Type (Etype (Prefix (Exp))) then
17274 return;
17276 -- Otherwise go to prefix and keep going
17278 else
17279 Exp := Prefix (Exp);
17280 goto Continue;
17281 end if;
17283 -- All other cases, not a modification
17285 else
17286 return;
17287 end if;
17289 -- Now look for entity being referenced
17291 if Present (Ent) then
17292 if Is_Object (Ent) then
17293 if Comes_From_Source (Exp)
17294 or else Modification_Comes_From_Source
17295 then
17296 -- Give warning if pragma unmodified given and we are
17297 -- sure this is a modification.
17299 if Has_Pragma_Unmodified (Ent) and then Sure then
17300 Error_Msg_NE ("??pragma Unmodified given for &!", N, Ent);
17301 end if;
17303 Set_Never_Set_In_Source (Ent, False);
17304 end if;
17306 Set_Is_True_Constant (Ent, False);
17307 Set_Current_Value (Ent, Empty);
17308 Set_Is_Known_Null (Ent, False);
17310 if not Can_Never_Be_Null (Ent) then
17311 Set_Is_Known_Non_Null (Ent, False);
17312 end if;
17314 -- Follow renaming chain
17316 if (Ekind (Ent) = E_Variable or else Ekind (Ent) = E_Constant)
17317 and then Present (Renamed_Object (Ent))
17318 then
17319 Exp := Renamed_Object (Ent);
17321 -- If the entity is the loop variable in an iteration over
17322 -- a container, retrieve container expression to indicate
17323 -- possible modification.
17325 if Present (Related_Expression (Ent))
17326 and then Nkind (Parent (Related_Expression (Ent))) =
17327 N_Iterator_Specification
17328 then
17329 Exp := Original_Node (Related_Expression (Ent));
17330 end if;
17332 goto Continue;
17334 -- The expression may be the renaming of a subcomponent of an
17335 -- array or container. The assignment to the subcomponent is
17336 -- a modification of the container.
17338 elsif Comes_From_Source (Original_Node (Exp))
17339 and then Nkind_In (Original_Node (Exp), N_Selected_Component,
17340 N_Indexed_Component)
17341 then
17342 Exp := Prefix (Original_Node (Exp));
17343 goto Continue;
17344 end if;
17346 -- Generate a reference only if the assignment comes from
17347 -- source. This excludes, for example, calls to a dispatching
17348 -- assignment operation when the left-hand side is tagged. In
17349 -- GNATprove mode, we need those references also on generated
17350 -- code, as these are used to compute the local effects of
17351 -- subprograms.
17353 if Modification_Comes_From_Source or GNATprove_Mode then
17354 Generate_Reference (Ent, Exp, 'm');
17356 -- If the target of the assignment is the bound variable
17357 -- in an iterator, indicate that the corresponding array
17358 -- or container is also modified.
17360 if Ada_Version >= Ada_2012
17361 and then Nkind (Parent (Ent)) = N_Iterator_Specification
17362 then
17363 declare
17364 Domain : constant Node_Id := Name (Parent (Ent));
17366 begin
17367 -- TBD : in the full version of the construct, the
17368 -- domain of iteration can be given by an expression.
17370 if Is_Entity_Name (Domain) then
17371 Generate_Reference (Entity (Domain), Exp, 'm');
17372 Set_Is_True_Constant (Entity (Domain), False);
17373 Set_Never_Set_In_Source (Entity (Domain), False);
17374 end if;
17375 end;
17376 end if;
17377 end if;
17378 end if;
17380 Kill_Checks (Ent);
17382 -- If we are sure this is a modification from source, and we know
17383 -- this modifies a constant, then give an appropriate warning.
17385 if Sure
17386 and then Modification_Comes_From_Source
17387 and then Overlays_Constant (Ent)
17388 and then Address_Clause_Overlay_Warnings
17389 then
17390 declare
17391 Addr : constant Node_Id := Address_Clause (Ent);
17392 O_Ent : Entity_Id;
17393 Off : Boolean;
17395 begin
17396 Find_Overlaid_Entity (Addr, O_Ent, Off);
17398 Error_Msg_Sloc := Sloc (Addr);
17399 Error_Msg_NE
17400 ("??constant& may be modified via address clause#",
17401 N, O_Ent);
17402 end;
17403 end if;
17405 return;
17406 end if;
17408 <<Continue>>
17409 null;
17410 end loop;
17411 end Note_Possible_Modification;
17413 -------------------------
17414 -- Object_Access_Level --
17415 -------------------------
17417 -- Returns the static accessibility level of the view denoted by Obj. Note
17418 -- that the value returned is the result of a call to Scope_Depth. Only
17419 -- scope depths associated with dynamic scopes can actually be returned.
17420 -- Since only relative levels matter for accessibility checking, the fact
17421 -- that the distance between successive levels of accessibility is not
17422 -- always one is immaterial (invariant: if level(E2) is deeper than
17423 -- level(E1), then Scope_Depth(E1) < Scope_Depth(E2)).
17425 function Object_Access_Level (Obj : Node_Id) return Uint is
17426 function Is_Interface_Conversion (N : Node_Id) return Boolean;
17427 -- Determine whether N is a construct of the form
17428 -- Some_Type (Operand._tag'Address)
17429 -- This construct appears in the context of dispatching calls.
17431 function Reference_To (Obj : Node_Id) return Node_Id;
17432 -- An explicit dereference is created when removing side-effects from
17433 -- expressions for constraint checking purposes. In this case a local
17434 -- access type is created for it. The correct access level is that of
17435 -- the original source node. We detect this case by noting that the
17436 -- prefix of the dereference is created by an object declaration whose
17437 -- initial expression is a reference.
17439 -----------------------------
17440 -- Is_Interface_Conversion --
17441 -----------------------------
17443 function Is_Interface_Conversion (N : Node_Id) return Boolean is
17444 begin
17445 return Nkind (N) = N_Unchecked_Type_Conversion
17446 and then Nkind (Expression (N)) = N_Attribute_Reference
17447 and then Attribute_Name (Expression (N)) = Name_Address;
17448 end Is_Interface_Conversion;
17450 ------------------
17451 -- Reference_To --
17452 ------------------
17454 function Reference_To (Obj : Node_Id) return Node_Id is
17455 Pref : constant Node_Id := Prefix (Obj);
17456 begin
17457 if Is_Entity_Name (Pref)
17458 and then Nkind (Parent (Entity (Pref))) = N_Object_Declaration
17459 and then Present (Expression (Parent (Entity (Pref))))
17460 and then Nkind (Expression (Parent (Entity (Pref)))) = N_Reference
17461 then
17462 return (Prefix (Expression (Parent (Entity (Pref)))));
17463 else
17464 return Empty;
17465 end if;
17466 end Reference_To;
17468 -- Local variables
17470 E : Entity_Id;
17472 -- Start of processing for Object_Access_Level
17474 begin
17475 if Nkind (Obj) = N_Defining_Identifier
17476 or else Is_Entity_Name (Obj)
17477 then
17478 if Nkind (Obj) = N_Defining_Identifier then
17479 E := Obj;
17480 else
17481 E := Entity (Obj);
17482 end if;
17484 if Is_Prival (E) then
17485 E := Prival_Link (E);
17486 end if;
17488 -- If E is a type then it denotes a current instance. For this case
17489 -- we add one to the normal accessibility level of the type to ensure
17490 -- that current instances are treated as always being deeper than
17491 -- than the level of any visible named access type (see 3.10.2(21)).
17493 if Is_Type (E) then
17494 return Type_Access_Level (E) + 1;
17496 elsif Present (Renamed_Object (E)) then
17497 return Object_Access_Level (Renamed_Object (E));
17499 -- Similarly, if E is a component of the current instance of a
17500 -- protected type, any instance of it is assumed to be at a deeper
17501 -- level than the type. For a protected object (whose type is an
17502 -- anonymous protected type) its components are at the same level
17503 -- as the type itself.
17505 elsif not Is_Overloadable (E)
17506 and then Ekind (Scope (E)) = E_Protected_Type
17507 and then Comes_From_Source (Scope (E))
17508 then
17509 return Type_Access_Level (Scope (E)) + 1;
17511 else
17512 -- Aliased formals of functions take their access level from the
17513 -- point of call, i.e. require a dynamic check. For static check
17514 -- purposes, this is smaller than the level of the subprogram
17515 -- itself. For procedures the aliased makes no difference.
17517 if Is_Formal (E)
17518 and then Is_Aliased (E)
17519 and then Ekind (Scope (E)) = E_Function
17520 then
17521 return Type_Access_Level (Etype (E));
17523 else
17524 return Scope_Depth (Enclosing_Dynamic_Scope (E));
17525 end if;
17526 end if;
17528 elsif Nkind (Obj) = N_Selected_Component then
17529 if Is_Access_Type (Etype (Prefix (Obj))) then
17530 return Type_Access_Level (Etype (Prefix (Obj)));
17531 else
17532 return Object_Access_Level (Prefix (Obj));
17533 end if;
17535 elsif Nkind (Obj) = N_Indexed_Component then
17536 if Is_Access_Type (Etype (Prefix (Obj))) then
17537 return Type_Access_Level (Etype (Prefix (Obj)));
17538 else
17539 return Object_Access_Level (Prefix (Obj));
17540 end if;
17542 elsif Nkind (Obj) = N_Explicit_Dereference then
17544 -- If the prefix is a selected access discriminant then we make a
17545 -- recursive call on the prefix, which will in turn check the level
17546 -- of the prefix object of the selected discriminant.
17548 -- In Ada 2012, if the discriminant has implicit dereference and
17549 -- the context is a selected component, treat this as an object of
17550 -- unknown scope (see below). This is necessary in compile-only mode;
17551 -- otherwise expansion will already have transformed the prefix into
17552 -- a temporary.
17554 if Nkind (Prefix (Obj)) = N_Selected_Component
17555 and then Ekind (Etype (Prefix (Obj))) = E_Anonymous_Access_Type
17556 and then
17557 Ekind (Entity (Selector_Name (Prefix (Obj)))) = E_Discriminant
17558 and then
17559 (not Has_Implicit_Dereference
17560 (Entity (Selector_Name (Prefix (Obj))))
17561 or else Nkind (Parent (Obj)) /= N_Selected_Component)
17562 then
17563 return Object_Access_Level (Prefix (Obj));
17565 -- Detect an interface conversion in the context of a dispatching
17566 -- call. Use the original form of the conversion to find the access
17567 -- level of the operand.
17569 elsif Is_Interface (Etype (Obj))
17570 and then Is_Interface_Conversion (Prefix (Obj))
17571 and then Nkind (Original_Node (Obj)) = N_Type_Conversion
17572 then
17573 return Object_Access_Level (Original_Node (Obj));
17575 elsif not Comes_From_Source (Obj) then
17576 declare
17577 Ref : constant Node_Id := Reference_To (Obj);
17578 begin
17579 if Present (Ref) then
17580 return Object_Access_Level (Ref);
17581 else
17582 return Type_Access_Level (Etype (Prefix (Obj)));
17583 end if;
17584 end;
17586 else
17587 return Type_Access_Level (Etype (Prefix (Obj)));
17588 end if;
17590 elsif Nkind_In (Obj, N_Type_Conversion, N_Unchecked_Type_Conversion) then
17591 return Object_Access_Level (Expression (Obj));
17593 elsif Nkind (Obj) = N_Function_Call then
17595 -- Function results are objects, so we get either the access level of
17596 -- the function or, in the case of an indirect call, the level of the
17597 -- access-to-subprogram type. (This code is used for Ada 95, but it
17598 -- looks wrong, because it seems that we should be checking the level
17599 -- of the call itself, even for Ada 95. However, using the Ada 2005
17600 -- version of the code causes regressions in several tests that are
17601 -- compiled with -gnat95. ???)
17603 if Ada_Version < Ada_2005 then
17604 if Is_Entity_Name (Name (Obj)) then
17605 return Subprogram_Access_Level (Entity (Name (Obj)));
17606 else
17607 return Type_Access_Level (Etype (Prefix (Name (Obj))));
17608 end if;
17610 -- For Ada 2005, the level of the result object of a function call is
17611 -- defined to be the level of the call's innermost enclosing master.
17612 -- We determine that by querying the depth of the innermost enclosing
17613 -- dynamic scope.
17615 else
17616 Return_Master_Scope_Depth_Of_Call : declare
17618 function Innermost_Master_Scope_Depth
17619 (N : Node_Id) return Uint;
17620 -- Returns the scope depth of the given node's innermost
17621 -- enclosing dynamic scope (effectively the accessibility
17622 -- level of the innermost enclosing master).
17624 ----------------------------------
17625 -- Innermost_Master_Scope_Depth --
17626 ----------------------------------
17628 function Innermost_Master_Scope_Depth
17629 (N : Node_Id) return Uint
17631 Node_Par : Node_Id := Parent (N);
17633 begin
17634 -- Locate the nearest enclosing node (by traversing Parents)
17635 -- that Defining_Entity can be applied to, and return the
17636 -- depth of that entity's nearest enclosing dynamic scope.
17638 while Present (Node_Par) loop
17639 case Nkind (Node_Par) is
17640 when N_Component_Declaration |
17641 N_Entry_Declaration |
17642 N_Formal_Object_Declaration |
17643 N_Formal_Type_Declaration |
17644 N_Full_Type_Declaration |
17645 N_Incomplete_Type_Declaration |
17646 N_Loop_Parameter_Specification |
17647 N_Object_Declaration |
17648 N_Protected_Type_Declaration |
17649 N_Private_Extension_Declaration |
17650 N_Private_Type_Declaration |
17651 N_Subtype_Declaration |
17652 N_Function_Specification |
17653 N_Procedure_Specification |
17654 N_Task_Type_Declaration |
17655 N_Body_Stub |
17656 N_Generic_Instantiation |
17657 N_Proper_Body |
17658 N_Implicit_Label_Declaration |
17659 N_Package_Declaration |
17660 N_Single_Task_Declaration |
17661 N_Subprogram_Declaration |
17662 N_Generic_Declaration |
17663 N_Renaming_Declaration |
17664 N_Block_Statement |
17665 N_Formal_Subprogram_Declaration |
17666 N_Abstract_Subprogram_Declaration |
17667 N_Entry_Body |
17668 N_Exception_Declaration |
17669 N_Formal_Package_Declaration |
17670 N_Number_Declaration |
17671 N_Package_Specification |
17672 N_Parameter_Specification |
17673 N_Single_Protected_Declaration |
17674 N_Subunit =>
17676 return Scope_Depth
17677 (Nearest_Dynamic_Scope
17678 (Defining_Entity (Node_Par)));
17680 when others =>
17681 null;
17682 end case;
17684 Node_Par := Parent (Node_Par);
17685 end loop;
17687 pragma Assert (False);
17689 -- Should never reach the following return
17691 return Scope_Depth (Current_Scope) + 1;
17692 end Innermost_Master_Scope_Depth;
17694 -- Start of processing for Return_Master_Scope_Depth_Of_Call
17696 begin
17697 return Innermost_Master_Scope_Depth (Obj);
17698 end Return_Master_Scope_Depth_Of_Call;
17699 end if;
17701 -- For convenience we handle qualified expressions, even though they
17702 -- aren't technically object names.
17704 elsif Nkind (Obj) = N_Qualified_Expression then
17705 return Object_Access_Level (Expression (Obj));
17707 -- Ditto for aggregates. They have the level of the temporary that
17708 -- will hold their value.
17710 elsif Nkind (Obj) = N_Aggregate then
17711 return Object_Access_Level (Current_Scope);
17713 -- Otherwise return the scope level of Standard. (If there are cases
17714 -- that fall through to this point they will be treated as having
17715 -- global accessibility for now. ???)
17717 else
17718 return Scope_Depth (Standard_Standard);
17719 end if;
17720 end Object_Access_Level;
17722 ---------------------------------
17723 -- Original_Aspect_Pragma_Name --
17724 ---------------------------------
17726 function Original_Aspect_Pragma_Name (N : Node_Id) return Name_Id is
17727 Item : Node_Id;
17728 Item_Nam : Name_Id;
17730 begin
17731 pragma Assert (Nkind_In (N, N_Aspect_Specification, N_Pragma));
17733 Item := N;
17735 -- The pragma was generated to emulate an aspect, use the original
17736 -- aspect specification.
17738 if Nkind (Item) = N_Pragma and then From_Aspect_Specification (Item) then
17739 Item := Corresponding_Aspect (Item);
17740 end if;
17742 -- Retrieve the name of the aspect/pragma. Note that Pre, Pre_Class,
17743 -- Post and Post_Class rewrite their pragma identifier to preserve the
17744 -- original name.
17745 -- ??? this is kludgey
17747 if Nkind (Item) = N_Pragma then
17748 Item_Nam := Chars (Original_Node (Pragma_Identifier (Item)));
17750 else
17751 pragma Assert (Nkind (Item) = N_Aspect_Specification);
17752 Item_Nam := Chars (Identifier (Item));
17753 end if;
17755 -- Deal with 'Class by converting the name to its _XXX form
17757 if Class_Present (Item) then
17758 if Item_Nam = Name_Invariant then
17759 Item_Nam := Name_uInvariant;
17761 elsif Item_Nam = Name_Post then
17762 Item_Nam := Name_uPost;
17764 elsif Item_Nam = Name_Pre then
17765 Item_Nam := Name_uPre;
17767 elsif Nam_In (Item_Nam, Name_Type_Invariant,
17768 Name_Type_Invariant_Class)
17769 then
17770 Item_Nam := Name_uType_Invariant;
17772 -- Nothing to do for other cases (e.g. a Check that derived from
17773 -- Pre_Class and has the flag set). Also we do nothing if the name
17774 -- is already in special _xxx form.
17776 end if;
17777 end if;
17779 return Item_Nam;
17780 end Original_Aspect_Pragma_Name;
17782 --------------------------------------
17783 -- Original_Corresponding_Operation --
17784 --------------------------------------
17786 function Original_Corresponding_Operation (S : Entity_Id) return Entity_Id
17788 Typ : constant Entity_Id := Find_Dispatching_Type (S);
17790 begin
17791 -- If S is an inherited primitive S2 the original corresponding
17792 -- operation of S is the original corresponding operation of S2
17794 if Present (Alias (S))
17795 and then Find_Dispatching_Type (Alias (S)) /= Typ
17796 then
17797 return Original_Corresponding_Operation (Alias (S));
17799 -- If S overrides an inherited subprogram S2 the original corresponding
17800 -- operation of S is the original corresponding operation of S2
17802 elsif Present (Overridden_Operation (S)) then
17803 return Original_Corresponding_Operation (Overridden_Operation (S));
17805 -- otherwise it is S itself
17807 else
17808 return S;
17809 end if;
17810 end Original_Corresponding_Operation;
17812 -------------------
17813 -- Output_Entity --
17814 -------------------
17816 procedure Output_Entity (Id : Entity_Id) is
17817 Scop : Entity_Id;
17819 begin
17820 Scop := Scope (Id);
17822 -- The entity may lack a scope when it is in the process of being
17823 -- analyzed. Use the current scope as an approximation.
17825 if No (Scop) then
17826 Scop := Current_Scope;
17827 end if;
17829 Output_Name (Chars (Id), Scop);
17830 end Output_Entity;
17832 -----------------
17833 -- Output_Name --
17834 -----------------
17836 procedure Output_Name (Nam : Name_Id; Scop : Entity_Id := Current_Scope) is
17837 begin
17838 Write_Str
17839 (Get_Name_String
17840 (Get_Qualified_Name
17841 (Nam => Nam,
17842 Suffix => No_Name,
17843 Scop => Scop)));
17844 Write_Eol;
17845 end Output_Name;
17847 ----------------------
17848 -- Policy_In_Effect --
17849 ----------------------
17851 function Policy_In_Effect (Policy : Name_Id) return Name_Id is
17852 function Policy_In_List (List : Node_Id) return Name_Id;
17853 -- Determine the mode of a policy in a N_Pragma list
17855 --------------------
17856 -- Policy_In_List --
17857 --------------------
17859 function Policy_In_List (List : Node_Id) return Name_Id is
17860 Arg1 : Node_Id;
17861 Arg2 : Node_Id;
17862 Prag : Node_Id;
17864 begin
17865 Prag := List;
17866 while Present (Prag) loop
17867 Arg1 := First (Pragma_Argument_Associations (Prag));
17868 Arg2 := Next (Arg1);
17870 Arg1 := Get_Pragma_Arg (Arg1);
17871 Arg2 := Get_Pragma_Arg (Arg2);
17873 -- The current Check_Policy pragma matches the requested policy or
17874 -- appears in the single argument form (Assertion, policy_id).
17876 if Nam_In (Chars (Arg1), Name_Assertion, Policy) then
17877 return Chars (Arg2);
17878 end if;
17880 Prag := Next_Pragma (Prag);
17881 end loop;
17883 return No_Name;
17884 end Policy_In_List;
17886 -- Local variables
17888 Kind : Name_Id;
17890 -- Start of processing for Policy_In_Effect
17892 begin
17893 if not Is_Valid_Assertion_Kind (Policy) then
17894 raise Program_Error;
17895 end if;
17897 -- Inspect all policy pragmas that appear within scopes (if any)
17899 Kind := Policy_In_List (Check_Policy_List);
17901 -- Inspect all configuration policy pragmas (if any)
17903 if Kind = No_Name then
17904 Kind := Policy_In_List (Check_Policy_List_Config);
17905 end if;
17907 -- The context lacks policy pragmas, determine the mode based on whether
17908 -- assertions are enabled at the configuration level. This ensures that
17909 -- the policy is preserved when analyzing generics.
17911 if Kind = No_Name then
17912 if Assertions_Enabled_Config then
17913 Kind := Name_Check;
17914 else
17915 Kind := Name_Ignore;
17916 end if;
17917 end if;
17919 return Kind;
17920 end Policy_In_Effect;
17922 ----------------------------------
17923 -- Predicate_Tests_On_Arguments --
17924 ----------------------------------
17926 function Predicate_Tests_On_Arguments (Subp : Entity_Id) return Boolean is
17927 begin
17928 -- Always test predicates on indirect call
17930 if Ekind (Subp) = E_Subprogram_Type then
17931 return True;
17933 -- Do not test predicates on call to generated default Finalize, since
17934 -- we are not interested in whether something we are finalizing (and
17935 -- typically destroying) satisfies its predicates.
17937 elsif Chars (Subp) = Name_Finalize
17938 and then not Comes_From_Source (Subp)
17939 then
17940 return False;
17942 -- Do not test predicates on any internally generated routines
17944 elsif Is_Internal_Name (Chars (Subp)) then
17945 return False;
17947 -- Do not test predicates on call to Init_Proc, since if needed the
17948 -- predicate test will occur at some other point.
17950 elsif Is_Init_Proc (Subp) then
17951 return False;
17953 -- Do not test predicates on call to predicate function, since this
17954 -- would cause infinite recursion.
17956 elsif Ekind (Subp) = E_Function
17957 and then (Is_Predicate_Function (Subp)
17958 or else
17959 Is_Predicate_Function_M (Subp))
17960 then
17961 return False;
17963 -- For now, no other exceptions
17965 else
17966 return True;
17967 end if;
17968 end Predicate_Tests_On_Arguments;
17970 -----------------------
17971 -- Private_Component --
17972 -----------------------
17974 function Private_Component (Type_Id : Entity_Id) return Entity_Id is
17975 Ancestor : constant Entity_Id := Base_Type (Type_Id);
17977 function Trace_Components
17978 (T : Entity_Id;
17979 Check : Boolean) return Entity_Id;
17980 -- Recursive function that does the work, and checks against circular
17981 -- definition for each subcomponent type.
17983 ----------------------
17984 -- Trace_Components --
17985 ----------------------
17987 function Trace_Components
17988 (T : Entity_Id;
17989 Check : Boolean) return Entity_Id
17991 Btype : constant Entity_Id := Base_Type (T);
17992 Component : Entity_Id;
17993 P : Entity_Id;
17994 Candidate : Entity_Id := Empty;
17996 begin
17997 if Check and then Btype = Ancestor then
17998 Error_Msg_N ("circular type definition", Type_Id);
17999 return Any_Type;
18000 end if;
18002 if Is_Private_Type (Btype) and then not Is_Generic_Type (Btype) then
18003 if Present (Full_View (Btype))
18004 and then Is_Record_Type (Full_View (Btype))
18005 and then not Is_Frozen (Btype)
18006 then
18007 -- To indicate that the ancestor depends on a private type, the
18008 -- current Btype is sufficient. However, to check for circular
18009 -- definition we must recurse on the full view.
18011 Candidate := Trace_Components (Full_View (Btype), True);
18013 if Candidate = Any_Type then
18014 return Any_Type;
18015 else
18016 return Btype;
18017 end if;
18019 else
18020 return Btype;
18021 end if;
18023 elsif Is_Array_Type (Btype) then
18024 return Trace_Components (Component_Type (Btype), True);
18026 elsif Is_Record_Type (Btype) then
18027 Component := First_Entity (Btype);
18028 while Present (Component)
18029 and then Comes_From_Source (Component)
18030 loop
18031 -- Skip anonymous types generated by constrained components
18033 if not Is_Type (Component) then
18034 P := Trace_Components (Etype (Component), True);
18036 if Present (P) then
18037 if P = Any_Type then
18038 return P;
18039 else
18040 Candidate := P;
18041 end if;
18042 end if;
18043 end if;
18045 Next_Entity (Component);
18046 end loop;
18048 return Candidate;
18050 else
18051 return Empty;
18052 end if;
18053 end Trace_Components;
18055 -- Start of processing for Private_Component
18057 begin
18058 return Trace_Components (Type_Id, False);
18059 end Private_Component;
18061 ---------------------------
18062 -- Primitive_Names_Match --
18063 ---------------------------
18065 function Primitive_Names_Match (E1, E2 : Entity_Id) return Boolean is
18067 function Non_Internal_Name (E : Entity_Id) return Name_Id;
18068 -- Given an internal name, returns the corresponding non-internal name
18070 ------------------------
18071 -- Non_Internal_Name --
18072 ------------------------
18074 function Non_Internal_Name (E : Entity_Id) return Name_Id is
18075 begin
18076 Get_Name_String (Chars (E));
18077 Name_Len := Name_Len - 1;
18078 return Name_Find;
18079 end Non_Internal_Name;
18081 -- Start of processing for Primitive_Names_Match
18083 begin
18084 pragma Assert (Present (E1) and then Present (E2));
18086 return Chars (E1) = Chars (E2)
18087 or else
18088 (not Is_Internal_Name (Chars (E1))
18089 and then Is_Internal_Name (Chars (E2))
18090 and then Non_Internal_Name (E2) = Chars (E1))
18091 or else
18092 (not Is_Internal_Name (Chars (E2))
18093 and then Is_Internal_Name (Chars (E1))
18094 and then Non_Internal_Name (E1) = Chars (E2))
18095 or else
18096 (Is_Predefined_Dispatching_Operation (E1)
18097 and then Is_Predefined_Dispatching_Operation (E2)
18098 and then Same_TSS (E1, E2))
18099 or else
18100 (Is_Init_Proc (E1) and then Is_Init_Proc (E2));
18101 end Primitive_Names_Match;
18103 -----------------------
18104 -- Process_End_Label --
18105 -----------------------
18107 procedure Process_End_Label
18108 (N : Node_Id;
18109 Typ : Character;
18110 Ent : Entity_Id)
18112 Loc : Source_Ptr;
18113 Nam : Node_Id;
18114 Scop : Entity_Id;
18116 Label_Ref : Boolean;
18117 -- Set True if reference to end label itself is required
18119 Endl : Node_Id;
18120 -- Gets set to the operator symbol or identifier that references the
18121 -- entity Ent. For the child unit case, this is the identifier from the
18122 -- designator. For other cases, this is simply Endl.
18124 procedure Generate_Parent_Ref (N : Node_Id; E : Entity_Id);
18125 -- N is an identifier node that appears as a parent unit reference in
18126 -- the case where Ent is a child unit. This procedure generates an
18127 -- appropriate cross-reference entry. E is the corresponding entity.
18129 -------------------------
18130 -- Generate_Parent_Ref --
18131 -------------------------
18133 procedure Generate_Parent_Ref (N : Node_Id; E : Entity_Id) is
18134 begin
18135 -- If names do not match, something weird, skip reference
18137 if Chars (E) = Chars (N) then
18139 -- Generate the reference. We do NOT consider this as a reference
18140 -- for unreferenced symbol purposes.
18142 Generate_Reference (E, N, 'r', Set_Ref => False, Force => True);
18144 if Style_Check then
18145 Style.Check_Identifier (N, E);
18146 end if;
18147 end if;
18148 end Generate_Parent_Ref;
18150 -- Start of processing for Process_End_Label
18152 begin
18153 -- If no node, ignore. This happens in some error situations, and
18154 -- also for some internally generated structures where no end label
18155 -- references are required in any case.
18157 if No (N) then
18158 return;
18159 end if;
18161 -- Nothing to do if no End_Label, happens for internally generated
18162 -- constructs where we don't want an end label reference anyway. Also
18163 -- nothing to do if Endl is a string literal, which means there was
18164 -- some prior error (bad operator symbol)
18166 Endl := End_Label (N);
18168 if No (Endl) or else Nkind (Endl) = N_String_Literal then
18169 return;
18170 end if;
18172 -- Reference node is not in extended main source unit
18174 if not In_Extended_Main_Source_Unit (N) then
18176 -- Generally we do not collect references except for the extended
18177 -- main source unit. The one exception is the 'e' entry for a
18178 -- package spec, where it is useful for a client to have the
18179 -- ending information to define scopes.
18181 if Typ /= 'e' then
18182 return;
18184 else
18185 Label_Ref := False;
18187 -- For this case, we can ignore any parent references, but we
18188 -- need the package name itself for the 'e' entry.
18190 if Nkind (Endl) = N_Designator then
18191 Endl := Identifier (Endl);
18192 end if;
18193 end if;
18195 -- Reference is in extended main source unit
18197 else
18198 Label_Ref := True;
18200 -- For designator, generate references for the parent entries
18202 if Nkind (Endl) = N_Designator then
18204 -- Generate references for the prefix if the END line comes from
18205 -- source (otherwise we do not need these references) We climb the
18206 -- scope stack to find the expected entities.
18208 if Comes_From_Source (Endl) then
18209 Nam := Name (Endl);
18210 Scop := Current_Scope;
18211 while Nkind (Nam) = N_Selected_Component loop
18212 Scop := Scope (Scop);
18213 exit when No (Scop);
18214 Generate_Parent_Ref (Selector_Name (Nam), Scop);
18215 Nam := Prefix (Nam);
18216 end loop;
18218 if Present (Scop) then
18219 Generate_Parent_Ref (Nam, Scope (Scop));
18220 end if;
18221 end if;
18223 Endl := Identifier (Endl);
18224 end if;
18225 end if;
18227 -- If the end label is not for the given entity, then either we have
18228 -- some previous error, or this is a generic instantiation for which
18229 -- we do not need to make a cross-reference in this case anyway. In
18230 -- either case we simply ignore the call.
18232 if Chars (Ent) /= Chars (Endl) then
18233 return;
18234 end if;
18236 -- If label was really there, then generate a normal reference and then
18237 -- adjust the location in the end label to point past the name (which
18238 -- should almost always be the semicolon).
18240 Loc := Sloc (Endl);
18242 if Comes_From_Source (Endl) then
18244 -- If a label reference is required, then do the style check and
18245 -- generate an l-type cross-reference entry for the label
18247 if Label_Ref then
18248 if Style_Check then
18249 Style.Check_Identifier (Endl, Ent);
18250 end if;
18252 Generate_Reference (Ent, Endl, 'l', Set_Ref => False);
18253 end if;
18255 -- Set the location to point past the label (normally this will
18256 -- mean the semicolon immediately following the label). This is
18257 -- done for the sake of the 'e' or 't' entry generated below.
18259 Get_Decoded_Name_String (Chars (Endl));
18260 Set_Sloc (Endl, Sloc (Endl) + Source_Ptr (Name_Len));
18262 else
18263 -- In SPARK mode, no missing label is allowed for packages and
18264 -- subprogram bodies. Detect those cases by testing whether
18265 -- Process_End_Label was called for a body (Typ = 't') or a package.
18267 if Restriction_Check_Required (SPARK_05)
18268 and then (Typ = 't' or else Ekind (Ent) = E_Package)
18269 then
18270 Error_Msg_Node_1 := Endl;
18271 Check_SPARK_05_Restriction
18272 ("`END &` required", Endl, Force => True);
18273 end if;
18274 end if;
18276 -- Now generate the e/t reference
18278 Generate_Reference (Ent, Endl, Typ, Set_Ref => False, Force => True);
18280 -- Restore Sloc, in case modified above, since we have an identifier
18281 -- and the normal Sloc should be left set in the tree.
18283 Set_Sloc (Endl, Loc);
18284 end Process_End_Label;
18286 ---------------------------------------
18287 -- Record_Possible_Part_Of_Reference --
18288 ---------------------------------------
18290 procedure Record_Possible_Part_Of_Reference
18291 (Var_Id : Entity_Id;
18292 Ref : Node_Id)
18294 Encap : constant Entity_Id := Encapsulating_State (Var_Id);
18295 Refs : Elist_Id;
18297 begin
18298 -- The variable is a constituent of a single protected/task type. Such
18299 -- a variable acts as a component of the type and must appear within a
18300 -- specific region (SPARK RM 9.3). Instead of recording the reference,
18301 -- verify its legality now.
18303 if Present (Encap) and then Is_Single_Concurrent_Object (Encap) then
18304 Check_Part_Of_Reference (Var_Id, Ref);
18306 -- The variable is subject to pragma Part_Of and may eventually become a
18307 -- constituent of a single protected/task type. Record the reference to
18308 -- verify its placement when the contract of the variable is analyzed.
18310 elsif Present (Get_Pragma (Var_Id, Pragma_Part_Of)) then
18311 Refs := Part_Of_References (Var_Id);
18313 if No (Refs) then
18314 Refs := New_Elmt_List;
18315 Set_Part_Of_References (Var_Id, Refs);
18316 end if;
18318 Append_Elmt (Ref, Refs);
18319 end if;
18320 end Record_Possible_Part_Of_Reference;
18322 ----------------
18323 -- Referenced --
18324 ----------------
18326 function Referenced (Id : Entity_Id; Expr : Node_Id) return Boolean is
18327 Seen : Boolean := False;
18329 function Is_Reference (N : Node_Id) return Traverse_Result;
18330 -- Determine whether node N denotes a reference to Id. If this is the
18331 -- case, set global flag Seen to True and stop the traversal.
18333 ------------------
18334 -- Is_Reference --
18335 ------------------
18337 function Is_Reference (N : Node_Id) return Traverse_Result is
18338 begin
18339 if Is_Entity_Name (N)
18340 and then Present (Entity (N))
18341 and then Entity (N) = Id
18342 then
18343 Seen := True;
18344 return Abandon;
18345 else
18346 return OK;
18347 end if;
18348 end Is_Reference;
18350 procedure Inspect_Expression is new Traverse_Proc (Is_Reference);
18352 -- Start of processing for Referenced
18354 begin
18355 Inspect_Expression (Expr);
18356 return Seen;
18357 end Referenced;
18359 ------------------------------------
18360 -- References_Generic_Formal_Type --
18361 ------------------------------------
18363 function References_Generic_Formal_Type (N : Node_Id) return Boolean is
18365 function Process (N : Node_Id) return Traverse_Result;
18366 -- Process one node in search for generic formal type
18368 -------------
18369 -- Process --
18370 -------------
18372 function Process (N : Node_Id) return Traverse_Result is
18373 begin
18374 if Nkind (N) in N_Has_Entity then
18375 declare
18376 E : constant Entity_Id := Entity (N);
18377 begin
18378 if Present (E) then
18379 if Is_Generic_Type (E) then
18380 return Abandon;
18381 elsif Present (Etype (E))
18382 and then Is_Generic_Type (Etype (E))
18383 then
18384 return Abandon;
18385 end if;
18386 end if;
18387 end;
18388 end if;
18390 return Atree.OK;
18391 end Process;
18393 function Traverse is new Traverse_Func (Process);
18394 -- Traverse tree to look for generic type
18396 begin
18397 if Inside_A_Generic then
18398 return Traverse (N) = Abandon;
18399 else
18400 return False;
18401 end if;
18402 end References_Generic_Formal_Type;
18404 --------------------
18405 -- Remove_Homonym --
18406 --------------------
18408 procedure Remove_Homonym (E : Entity_Id) is
18409 Prev : Entity_Id := Empty;
18410 H : Entity_Id;
18412 begin
18413 if E = Current_Entity (E) then
18414 if Present (Homonym (E)) then
18415 Set_Current_Entity (Homonym (E));
18416 else
18417 Set_Name_Entity_Id (Chars (E), Empty);
18418 end if;
18420 else
18421 H := Current_Entity (E);
18422 while Present (H) and then H /= E loop
18423 Prev := H;
18424 H := Homonym (H);
18425 end loop;
18427 -- If E is not on the homonym chain, nothing to do
18429 if Present (H) then
18430 Set_Homonym (Prev, Homonym (E));
18431 end if;
18432 end if;
18433 end Remove_Homonym;
18435 ------------------------------
18436 -- Remove_Overloaded_Entity --
18437 ------------------------------
18439 procedure Remove_Overloaded_Entity (Id : Entity_Id) is
18440 procedure Remove_Primitive_Of (Typ : Entity_Id);
18441 -- Remove primitive subprogram Id from the list of primitives that
18442 -- belong to type Typ.
18444 -------------------------
18445 -- Remove_Primitive_Of --
18446 -------------------------
18448 procedure Remove_Primitive_Of (Typ : Entity_Id) is
18449 Prims : Elist_Id;
18451 begin
18452 if Is_Tagged_Type (Typ) then
18453 Prims := Direct_Primitive_Operations (Typ);
18455 if Present (Prims) then
18456 Remove (Prims, Id);
18457 end if;
18458 end if;
18459 end Remove_Primitive_Of;
18461 -- Local variables
18463 Scop : constant Entity_Id := Scope (Id);
18464 Formal : Entity_Id;
18465 Prev_Id : Entity_Id;
18467 -- Start of processing for Remove_Overloaded_Entity
18469 begin
18470 -- Remove the entity from the homonym chain. When the entity is the
18471 -- head of the chain, associate the entry in the name table with its
18472 -- homonym effectively making it the new head of the chain.
18474 if Current_Entity (Id) = Id then
18475 Set_Name_Entity_Id (Chars (Id), Homonym (Id));
18477 -- Otherwise link the previous and next homonyms
18479 else
18480 Prev_Id := Current_Entity (Id);
18481 while Present (Prev_Id) and then Homonym (Prev_Id) /= Id loop
18482 Prev_Id := Homonym (Prev_Id);
18483 end loop;
18485 Set_Homonym (Prev_Id, Homonym (Id));
18486 end if;
18488 -- Remove the entity from the scope entity chain. When the entity is
18489 -- the head of the chain, set the next entity as the new head of the
18490 -- chain.
18492 if First_Entity (Scop) = Id then
18493 Prev_Id := Empty;
18494 Set_First_Entity (Scop, Next_Entity (Id));
18496 -- Otherwise the entity is either in the middle of the chain or it acts
18497 -- as its tail. Traverse and link the previous and next entities.
18499 else
18500 Prev_Id := First_Entity (Scop);
18501 while Present (Prev_Id) and then Next_Entity (Prev_Id) /= Id loop
18502 Next_Entity (Prev_Id);
18503 end loop;
18505 Set_Next_Entity (Prev_Id, Next_Entity (Id));
18506 end if;
18508 -- Handle the case where the entity acts as the tail of the scope entity
18509 -- chain.
18511 if Last_Entity (Scop) = Id then
18512 Set_Last_Entity (Scop, Prev_Id);
18513 end if;
18515 -- The entity denotes a primitive subprogram. Remove it from the list of
18516 -- primitives of the associated controlling type.
18518 if Ekind_In (Id, E_Function, E_Procedure) and then Is_Primitive (Id) then
18519 Formal := First_Formal (Id);
18520 while Present (Formal) loop
18521 if Is_Controlling_Formal (Formal) then
18522 Remove_Primitive_Of (Etype (Formal));
18523 exit;
18524 end if;
18526 Next_Formal (Formal);
18527 end loop;
18529 if Ekind (Id) = E_Function and then Has_Controlling_Result (Id) then
18530 Remove_Primitive_Of (Etype (Id));
18531 end if;
18532 end if;
18533 end Remove_Overloaded_Entity;
18535 ---------------------
18536 -- Rep_To_Pos_Flag --
18537 ---------------------
18539 function Rep_To_Pos_Flag (E : Entity_Id; Loc : Source_Ptr) return Node_Id is
18540 begin
18541 return New_Occurrence_Of
18542 (Boolean_Literals (not Range_Checks_Suppressed (E)), Loc);
18543 end Rep_To_Pos_Flag;
18545 --------------------
18546 -- Require_Entity --
18547 --------------------
18549 procedure Require_Entity (N : Node_Id) is
18550 begin
18551 if Is_Entity_Name (N) and then No (Entity (N)) then
18552 if Total_Errors_Detected /= 0 then
18553 Set_Entity (N, Any_Id);
18554 else
18555 raise Program_Error;
18556 end if;
18557 end if;
18558 end Require_Entity;
18560 ------------------------------
18561 -- Requires_Transient_Scope --
18562 ------------------------------
18564 -- A transient scope is required when variable-sized temporaries are
18565 -- allocated on the secondary stack, or when finalization actions must be
18566 -- generated before the next instruction.
18568 function Old_Requires_Transient_Scope (Id : Entity_Id) return Boolean;
18569 function New_Requires_Transient_Scope (Id : Entity_Id) return Boolean;
18570 -- ???We retain the old and new algorithms for Requires_Transient_Scope for
18571 -- the time being. New_Requires_Transient_Scope is used by default; the
18572 -- debug switch -gnatdQ can be used to do Old_Requires_Transient_Scope
18573 -- instead. The intent is to use this temporarily to measure before/after
18574 -- efficiency. Note: when this temporary code is removed, the documentation
18575 -- of dQ in debug.adb should be removed.
18577 procedure Results_Differ (Id : Entity_Id);
18578 -- ???Debugging code. Called when the Old_ and New_ results differ. Will be
18579 -- removed when New_Requires_Transient_Scope becomes
18580 -- Requires_Transient_Scope and Old_Requires_Transient_Scope is eliminated.
18582 procedure Results_Differ (Id : Entity_Id) is
18583 begin
18584 if False then -- False to disable; True for debugging
18585 Treepr.Print_Tree_Node (Id);
18587 if Old_Requires_Transient_Scope (Id) =
18588 New_Requires_Transient_Scope (Id)
18589 then
18590 raise Program_Error;
18591 end if;
18592 end if;
18593 end Results_Differ;
18595 function Requires_Transient_Scope (Id : Entity_Id) return Boolean is
18596 Old_Result : constant Boolean := Old_Requires_Transient_Scope (Id);
18598 begin
18599 if Debug_Flag_QQ then
18600 return Old_Result;
18601 end if;
18603 declare
18604 New_Result : constant Boolean := New_Requires_Transient_Scope (Id);
18606 begin
18607 -- Assert that we're not putting things on the secondary stack if we
18608 -- didn't before; we are trying to AVOID secondary stack when
18609 -- possible.
18611 if not Old_Result then
18612 pragma Assert (not New_Result);
18613 null;
18614 end if;
18616 if New_Result /= Old_Result then
18617 Results_Differ (Id);
18618 end if;
18620 return New_Result;
18621 end;
18622 end Requires_Transient_Scope;
18624 ----------------------------------
18625 -- Old_Requires_Transient_Scope --
18626 ----------------------------------
18628 function Old_Requires_Transient_Scope (Id : Entity_Id) return Boolean is
18629 Typ : constant Entity_Id := Underlying_Type (Id);
18631 begin
18632 -- This is a private type which is not completed yet. This can only
18633 -- happen in a default expression (of a formal parameter or of a
18634 -- record component). Do not expand transient scope in this case.
18636 if No (Typ) then
18637 return False;
18639 -- Do not expand transient scope for non-existent procedure return
18641 elsif Typ = Standard_Void_Type then
18642 return False;
18644 -- Elementary types do not require a transient scope
18646 elsif Is_Elementary_Type (Typ) then
18647 return False;
18649 -- Generally, indefinite subtypes require a transient scope, since the
18650 -- back end cannot generate temporaries, since this is not a valid type
18651 -- for declaring an object. It might be possible to relax this in the
18652 -- future, e.g. by declaring the maximum possible space for the type.
18654 elsif not Is_Definite_Subtype (Typ) then
18655 return True;
18657 -- Functions returning tagged types may dispatch on result so their
18658 -- returned value is allocated on the secondary stack. Controlled
18659 -- type temporaries need finalization.
18661 elsif Is_Tagged_Type (Typ) or else Has_Controlled_Component (Typ) then
18662 return True;
18664 -- Record type
18666 elsif Is_Record_Type (Typ) then
18667 declare
18668 Comp : Entity_Id;
18670 begin
18671 Comp := First_Entity (Typ);
18672 while Present (Comp) loop
18673 if Ekind (Comp) = E_Component then
18675 -- ???It's not clear we need a full recursive call to
18676 -- Old_Requires_Transient_Scope here. Note that the
18677 -- following can't happen.
18679 pragma Assert (Is_Definite_Subtype (Etype (Comp)));
18680 pragma Assert (not Has_Controlled_Component (Etype (Comp)));
18682 if Old_Requires_Transient_Scope (Etype (Comp)) then
18683 return True;
18684 end if;
18685 end if;
18687 Next_Entity (Comp);
18688 end loop;
18689 end;
18691 return False;
18693 -- String literal types never require transient scope
18695 elsif Ekind (Typ) = E_String_Literal_Subtype then
18696 return False;
18698 -- Array type. Note that we already know that this is a constrained
18699 -- array, since unconstrained arrays will fail the indefinite test.
18701 elsif Is_Array_Type (Typ) then
18703 -- If component type requires a transient scope, the array does too
18705 if Old_Requires_Transient_Scope (Component_Type (Typ)) then
18706 return True;
18708 -- Otherwise, we only need a transient scope if the size depends on
18709 -- the value of one or more discriminants.
18711 else
18712 return Size_Depends_On_Discriminant (Typ);
18713 end if;
18715 -- All other cases do not require a transient scope
18717 else
18718 pragma Assert (Is_Protected_Type (Typ) or else Is_Task_Type (Typ));
18719 return False;
18720 end if;
18721 end Old_Requires_Transient_Scope;
18723 ----------------------------------
18724 -- New_Requires_Transient_Scope --
18725 ----------------------------------
18727 function New_Requires_Transient_Scope (Id : Entity_Id) return Boolean is
18729 function Caller_Known_Size_Record (Typ : Entity_Id) return Boolean;
18730 -- This is called for untagged records and protected types, with
18731 -- nondefaulted discriminants. Returns True if the size of function
18732 -- results is known at the call site, False otherwise. Returns False
18733 -- if there is a variant part that depends on the discriminants of
18734 -- this type, or if there is an array constrained by the discriminants
18735 -- of this type. ???Currently, this is overly conservative (the array
18736 -- could be nested inside some other record that is constrained by
18737 -- nondiscriminants). That is, the recursive calls are too conservative.
18739 function Large_Max_Size_Mutable (Typ : Entity_Id) return Boolean;
18740 -- Returns True if Typ is a nonlimited record with defaulted
18741 -- discriminants whose max size makes it unsuitable for allocating on
18742 -- the primary stack.
18744 ------------------------------
18745 -- Caller_Known_Size_Record --
18746 ------------------------------
18748 function Caller_Known_Size_Record (Typ : Entity_Id) return Boolean is
18749 pragma Assert (Typ = Underlying_Type (Typ));
18751 begin
18752 if Has_Variant_Part (Typ) and then not Is_Definite_Subtype (Typ) then
18753 return False;
18754 end if;
18756 declare
18757 Comp : Entity_Id;
18759 begin
18760 Comp := First_Entity (Typ);
18761 while Present (Comp) loop
18763 -- Only look at E_Component entities. No need to look at
18764 -- E_Discriminant entities, and we must ignore internal
18765 -- subtypes generated for constrained components.
18767 if Ekind (Comp) = E_Component then
18768 declare
18769 Comp_Type : constant Entity_Id :=
18770 Underlying_Type (Etype (Comp));
18772 begin
18773 if Is_Record_Type (Comp_Type)
18774 or else
18775 Is_Protected_Type (Comp_Type)
18776 then
18777 if not Caller_Known_Size_Record (Comp_Type) then
18778 return False;
18779 end if;
18781 elsif Is_Array_Type (Comp_Type) then
18782 if Size_Depends_On_Discriminant (Comp_Type) then
18783 return False;
18784 end if;
18785 end if;
18786 end;
18787 end if;
18789 Next_Entity (Comp);
18790 end loop;
18791 end;
18793 return True;
18794 end Caller_Known_Size_Record;
18796 ------------------------------
18797 -- Large_Max_Size_Mutable --
18798 ------------------------------
18800 function Large_Max_Size_Mutable (Typ : Entity_Id) return Boolean is
18801 pragma Assert (Typ = Underlying_Type (Typ));
18803 function Is_Large_Discrete_Type (T : Entity_Id) return Boolean;
18804 -- Returns true if the discrete type T has a large range
18806 ----------------------------
18807 -- Is_Large_Discrete_Type --
18808 ----------------------------
18810 function Is_Large_Discrete_Type (T : Entity_Id) return Boolean is
18811 Threshold : constant Int := 16;
18812 -- Arbitrary threshold above which we consider it "large". We want
18813 -- a fairly large threshold, because these large types really
18814 -- shouldn't have default discriminants in the first place, in
18815 -- most cases.
18817 begin
18818 return UI_To_Int (RM_Size (T)) > Threshold;
18819 end Is_Large_Discrete_Type;
18821 begin
18822 if Is_Record_Type (Typ)
18823 and then not Is_Limited_View (Typ)
18824 and then Has_Defaulted_Discriminants (Typ)
18825 then
18826 -- Loop through the components, looking for an array whose upper
18827 -- bound(s) depends on discriminants, where both the subtype of
18828 -- the discriminant and the index subtype are too large.
18830 declare
18831 Comp : Entity_Id;
18833 begin
18834 Comp := First_Entity (Typ);
18835 while Present (Comp) loop
18836 if Ekind (Comp) = E_Component then
18837 declare
18838 Comp_Type : constant Entity_Id :=
18839 Underlying_Type (Etype (Comp));
18840 Indx : Node_Id;
18841 Ityp : Entity_Id;
18842 Hi : Node_Id;
18844 begin
18845 if Is_Array_Type (Comp_Type) then
18846 Indx := First_Index (Comp_Type);
18848 while Present (Indx) loop
18849 Ityp := Etype (Indx);
18850 Hi := Type_High_Bound (Ityp);
18852 if Nkind (Hi) = N_Identifier
18853 and then Ekind (Entity (Hi)) = E_Discriminant
18854 and then Is_Large_Discrete_Type (Ityp)
18855 and then Is_Large_Discrete_Type
18856 (Etype (Entity (Hi)))
18857 then
18858 return True;
18859 end if;
18861 Next_Index (Indx);
18862 end loop;
18863 end if;
18864 end;
18865 end if;
18867 Next_Entity (Comp);
18868 end loop;
18869 end;
18870 end if;
18872 return False;
18873 end Large_Max_Size_Mutable;
18875 -- Local declarations
18877 Typ : constant Entity_Id := Underlying_Type (Id);
18879 -- Start of processing for New_Requires_Transient_Scope
18881 begin
18882 -- This is a private type which is not completed yet. This can only
18883 -- happen in a default expression (of a formal parameter or of a
18884 -- record component). Do not expand transient scope in this case.
18886 if No (Typ) then
18887 return False;
18889 -- Do not expand transient scope for non-existent procedure return or
18890 -- string literal types.
18892 elsif Typ = Standard_Void_Type
18893 or else Ekind (Typ) = E_String_Literal_Subtype
18894 then
18895 return False;
18897 -- If Typ is a generic formal incomplete type, then we want to look at
18898 -- the actual type.
18900 elsif Ekind (Typ) = E_Record_Subtype
18901 and then Present (Cloned_Subtype (Typ))
18902 then
18903 return New_Requires_Transient_Scope (Cloned_Subtype (Typ));
18905 -- Functions returning specific tagged types may dispatch on result, so
18906 -- their returned value is allocated on the secondary stack, even in the
18907 -- definite case. We must treat nondispatching functions the same way,
18908 -- because access-to-function types can point at both, so the calling
18909 -- conventions must be compatible. Is_Tagged_Type includes controlled
18910 -- types and class-wide types. Controlled type temporaries need
18911 -- finalization.
18913 -- ???It's not clear why we need to return noncontrolled types with
18914 -- controlled components on the secondary stack.
18916 elsif Is_Tagged_Type (Typ) or else Has_Controlled_Component (Typ) then
18917 return True;
18919 -- Untagged definite subtypes are known size. This includes all
18920 -- elementary [sub]types. Tasks are known size even if they have
18921 -- discriminants. So we return False here, with one exception:
18922 -- For a type like:
18923 -- type T (Last : Natural := 0) is
18924 -- X : String (1 .. Last);
18925 -- end record;
18926 -- we return True. That's because for "P(F(...));", where F returns T,
18927 -- we don't know the size of the result at the call site, so if we
18928 -- allocated it on the primary stack, we would have to allocate the
18929 -- maximum size, which is way too big.
18931 elsif Is_Definite_Subtype (Typ) or else Is_Task_Type (Typ) then
18932 return Large_Max_Size_Mutable (Typ);
18934 -- Indefinite (discriminated) untagged record or protected type
18936 elsif Is_Record_Type (Typ) or else Is_Protected_Type (Typ) then
18937 return not Caller_Known_Size_Record (Typ);
18939 -- Unconstrained array
18941 else
18942 pragma Assert (Is_Array_Type (Typ) and not Is_Definite_Subtype (Typ));
18943 return True;
18944 end if;
18945 end New_Requires_Transient_Scope;
18947 --------------------------
18948 -- Reset_Analyzed_Flags --
18949 --------------------------
18951 procedure Reset_Analyzed_Flags (N : Node_Id) is
18953 function Clear_Analyzed (N : Node_Id) return Traverse_Result;
18954 -- Function used to reset Analyzed flags in tree. Note that we do
18955 -- not reset Analyzed flags in entities, since there is no need to
18956 -- reanalyze entities, and indeed, it is wrong to do so, since it
18957 -- can result in generating auxiliary stuff more than once.
18959 --------------------
18960 -- Clear_Analyzed --
18961 --------------------
18963 function Clear_Analyzed (N : Node_Id) return Traverse_Result is
18964 begin
18965 if not Has_Extension (N) then
18966 Set_Analyzed (N, False);
18967 end if;
18969 return OK;
18970 end Clear_Analyzed;
18972 procedure Reset_Analyzed is new Traverse_Proc (Clear_Analyzed);
18974 -- Start of processing for Reset_Analyzed_Flags
18976 begin
18977 Reset_Analyzed (N);
18978 end Reset_Analyzed_Flags;
18980 ------------------------
18981 -- Restore_SPARK_Mode --
18982 ------------------------
18984 procedure Restore_SPARK_Mode (Mode : SPARK_Mode_Type) is
18985 begin
18986 SPARK_Mode := Mode;
18987 end Restore_SPARK_Mode;
18989 --------------------------------
18990 -- Returns_Unconstrained_Type --
18991 --------------------------------
18993 function Returns_Unconstrained_Type (Subp : Entity_Id) return Boolean is
18994 begin
18995 return Ekind (Subp) = E_Function
18996 and then not Is_Scalar_Type (Etype (Subp))
18997 and then not Is_Access_Type (Etype (Subp))
18998 and then not Is_Constrained (Etype (Subp));
18999 end Returns_Unconstrained_Type;
19001 ----------------------------
19002 -- Root_Type_Of_Full_View --
19003 ----------------------------
19005 function Root_Type_Of_Full_View (T : Entity_Id) return Entity_Id is
19006 Rtyp : constant Entity_Id := Root_Type (T);
19008 begin
19009 -- The root type of the full view may itself be a private type. Keep
19010 -- looking for the ultimate derivation parent.
19012 if Is_Private_Type (Rtyp) and then Present (Full_View (Rtyp)) then
19013 return Root_Type_Of_Full_View (Full_View (Rtyp));
19014 else
19015 return Rtyp;
19016 end if;
19017 end Root_Type_Of_Full_View;
19019 ---------------------------
19020 -- Safe_To_Capture_Value --
19021 ---------------------------
19023 function Safe_To_Capture_Value
19024 (N : Node_Id;
19025 Ent : Entity_Id;
19026 Cond : Boolean := False) return Boolean
19028 begin
19029 -- The only entities for which we track constant values are variables
19030 -- which are not renamings, constants, out parameters, and in out
19031 -- parameters, so check if we have this case.
19033 -- Note: it may seem odd to track constant values for constants, but in
19034 -- fact this routine is used for other purposes than simply capturing
19035 -- the value. In particular, the setting of Known[_Non]_Null.
19037 if (Ekind (Ent) = E_Variable and then No (Renamed_Object (Ent)))
19038 or else
19039 Ekind_In (Ent, E_Constant, E_Out_Parameter, E_In_Out_Parameter)
19040 then
19041 null;
19043 -- For conditionals, we also allow loop parameters and all formals,
19044 -- including in parameters.
19046 elsif Cond and then Ekind_In (Ent, E_Loop_Parameter, E_In_Parameter) then
19047 null;
19049 -- For all other cases, not just unsafe, but impossible to capture
19050 -- Current_Value, since the above are the only entities which have
19051 -- Current_Value fields.
19053 else
19054 return False;
19055 end if;
19057 -- Skip if volatile or aliased, since funny things might be going on in
19058 -- these cases which we cannot necessarily track. Also skip any variable
19059 -- for which an address clause is given, or whose address is taken. Also
19060 -- never capture value of library level variables (an attempt to do so
19061 -- can occur in the case of package elaboration code).
19063 if Treat_As_Volatile (Ent)
19064 or else Is_Aliased (Ent)
19065 or else Present (Address_Clause (Ent))
19066 or else Address_Taken (Ent)
19067 or else (Is_Library_Level_Entity (Ent)
19068 and then Ekind (Ent) = E_Variable)
19069 then
19070 return False;
19071 end if;
19073 -- OK, all above conditions are met. We also require that the scope of
19074 -- the reference be the same as the scope of the entity, not counting
19075 -- packages and blocks and loops.
19077 declare
19078 E_Scope : constant Entity_Id := Scope (Ent);
19079 R_Scope : Entity_Id;
19081 begin
19082 R_Scope := Current_Scope;
19083 while R_Scope /= Standard_Standard loop
19084 exit when R_Scope = E_Scope;
19086 if not Ekind_In (R_Scope, E_Package, E_Block, E_Loop) then
19087 return False;
19088 else
19089 R_Scope := Scope (R_Scope);
19090 end if;
19091 end loop;
19092 end;
19094 -- We also require that the reference does not appear in a context
19095 -- where it is not sure to be executed (i.e. a conditional context
19096 -- or an exception handler). We skip this if Cond is True, since the
19097 -- capturing of values from conditional tests handles this ok.
19099 if Cond then
19100 return True;
19101 end if;
19103 declare
19104 Desc : Node_Id;
19105 P : Node_Id;
19107 begin
19108 Desc := N;
19110 -- Seems dubious that case expressions are not handled here ???
19112 P := Parent (N);
19113 while Present (P) loop
19114 if Nkind (P) = N_If_Statement
19115 or else Nkind (P) = N_Case_Statement
19116 or else (Nkind (P) in N_Short_Circuit
19117 and then Desc = Right_Opnd (P))
19118 or else (Nkind (P) = N_If_Expression
19119 and then Desc /= First (Expressions (P)))
19120 or else Nkind (P) = N_Exception_Handler
19121 or else Nkind (P) = N_Selective_Accept
19122 or else Nkind (P) = N_Conditional_Entry_Call
19123 or else Nkind (P) = N_Timed_Entry_Call
19124 or else Nkind (P) = N_Asynchronous_Select
19125 then
19126 return False;
19128 else
19129 Desc := P;
19130 P := Parent (P);
19132 -- A special Ada 2012 case: the original node may be part
19133 -- of the else_actions of a conditional expression, in which
19134 -- case it might not have been expanded yet, and appears in
19135 -- a non-syntactic list of actions. In that case it is clearly
19136 -- not safe to save a value.
19138 if No (P)
19139 and then Is_List_Member (Desc)
19140 and then No (Parent (List_Containing (Desc)))
19141 then
19142 return False;
19143 end if;
19144 end if;
19145 end loop;
19146 end;
19148 -- OK, looks safe to set value
19150 return True;
19151 end Safe_To_Capture_Value;
19153 ---------------
19154 -- Same_Name --
19155 ---------------
19157 function Same_Name (N1, N2 : Node_Id) return Boolean is
19158 K1 : constant Node_Kind := Nkind (N1);
19159 K2 : constant Node_Kind := Nkind (N2);
19161 begin
19162 if (K1 = N_Identifier or else K1 = N_Defining_Identifier)
19163 and then (K2 = N_Identifier or else K2 = N_Defining_Identifier)
19164 then
19165 return Chars (N1) = Chars (N2);
19167 elsif (K1 = N_Selected_Component or else K1 = N_Expanded_Name)
19168 and then (K2 = N_Selected_Component or else K2 = N_Expanded_Name)
19169 then
19170 return Same_Name (Selector_Name (N1), Selector_Name (N2))
19171 and then Same_Name (Prefix (N1), Prefix (N2));
19173 else
19174 return False;
19175 end if;
19176 end Same_Name;
19178 -----------------
19179 -- Same_Object --
19180 -----------------
19182 function Same_Object (Node1, Node2 : Node_Id) return Boolean is
19183 N1 : constant Node_Id := Original_Node (Node1);
19184 N2 : constant Node_Id := Original_Node (Node2);
19185 -- We do the tests on original nodes, since we are most interested
19186 -- in the original source, not any expansion that got in the way.
19188 K1 : constant Node_Kind := Nkind (N1);
19189 K2 : constant Node_Kind := Nkind (N2);
19191 begin
19192 -- First case, both are entities with same entity
19194 if K1 in N_Has_Entity and then K2 in N_Has_Entity then
19195 declare
19196 EN1 : constant Entity_Id := Entity (N1);
19197 EN2 : constant Entity_Id := Entity (N2);
19198 begin
19199 if Present (EN1) and then Present (EN2)
19200 and then (Ekind_In (EN1, E_Variable, E_Constant)
19201 or else Is_Formal (EN1))
19202 and then EN1 = EN2
19203 then
19204 return True;
19205 end if;
19206 end;
19207 end if;
19209 -- Second case, selected component with same selector, same record
19211 if K1 = N_Selected_Component
19212 and then K2 = N_Selected_Component
19213 and then Chars (Selector_Name (N1)) = Chars (Selector_Name (N2))
19214 then
19215 return Same_Object (Prefix (N1), Prefix (N2));
19217 -- Third case, indexed component with same subscripts, same array
19219 elsif K1 = N_Indexed_Component
19220 and then K2 = N_Indexed_Component
19221 and then Same_Object (Prefix (N1), Prefix (N2))
19222 then
19223 declare
19224 E1, E2 : Node_Id;
19225 begin
19226 E1 := First (Expressions (N1));
19227 E2 := First (Expressions (N2));
19228 while Present (E1) loop
19229 if not Same_Value (E1, E2) then
19230 return False;
19231 else
19232 Next (E1);
19233 Next (E2);
19234 end if;
19235 end loop;
19237 return True;
19238 end;
19240 -- Fourth case, slice of same array with same bounds
19242 elsif K1 = N_Slice
19243 and then K2 = N_Slice
19244 and then Nkind (Discrete_Range (N1)) = N_Range
19245 and then Nkind (Discrete_Range (N2)) = N_Range
19246 and then Same_Value (Low_Bound (Discrete_Range (N1)),
19247 Low_Bound (Discrete_Range (N2)))
19248 and then Same_Value (High_Bound (Discrete_Range (N1)),
19249 High_Bound (Discrete_Range (N2)))
19250 then
19251 return Same_Name (Prefix (N1), Prefix (N2));
19253 -- All other cases, not clearly the same object
19255 else
19256 return False;
19257 end if;
19258 end Same_Object;
19260 ---------------
19261 -- Same_Type --
19262 ---------------
19264 function Same_Type (T1, T2 : Entity_Id) return Boolean is
19265 begin
19266 if T1 = T2 then
19267 return True;
19269 elsif not Is_Constrained (T1)
19270 and then not Is_Constrained (T2)
19271 and then Base_Type (T1) = Base_Type (T2)
19272 then
19273 return True;
19275 -- For now don't bother with case of identical constraints, to be
19276 -- fiddled with later on perhaps (this is only used for optimization
19277 -- purposes, so it is not critical to do a best possible job)
19279 else
19280 return False;
19281 end if;
19282 end Same_Type;
19284 ----------------
19285 -- Same_Value --
19286 ----------------
19288 function Same_Value (Node1, Node2 : Node_Id) return Boolean is
19289 begin
19290 if Compile_Time_Known_Value (Node1)
19291 and then Compile_Time_Known_Value (Node2)
19292 and then Expr_Value (Node1) = Expr_Value (Node2)
19293 then
19294 return True;
19295 elsif Same_Object (Node1, Node2) then
19296 return True;
19297 else
19298 return False;
19299 end if;
19300 end Same_Value;
19302 -----------------------------
19303 -- Save_SPARK_Mode_And_Set --
19304 -----------------------------
19306 procedure Save_SPARK_Mode_And_Set
19307 (Context : Entity_Id;
19308 Mode : out SPARK_Mode_Type)
19310 begin
19311 -- Save the current mode in effect
19313 Mode := SPARK_Mode;
19315 -- Do not consider illegal or partially decorated constructs
19317 if Ekind (Context) = E_Void or else Error_Posted (Context) then
19318 null;
19320 elsif Present (SPARK_Pragma (Context)) then
19321 SPARK_Mode := Get_SPARK_Mode_From_Annotation (SPARK_Pragma (Context));
19322 end if;
19323 end Save_SPARK_Mode_And_Set;
19325 -------------------------
19326 -- Scalar_Part_Present --
19327 -------------------------
19329 function Scalar_Part_Present (T : Entity_Id) return Boolean is
19330 C : Entity_Id;
19332 begin
19333 if Is_Scalar_Type (T) then
19334 return True;
19336 elsif Is_Array_Type (T) then
19337 return Scalar_Part_Present (Component_Type (T));
19339 elsif Is_Record_Type (T) or else Has_Discriminants (T) then
19340 C := First_Component_Or_Discriminant (T);
19341 while Present (C) loop
19342 if Scalar_Part_Present (Etype (C)) then
19343 return True;
19344 else
19345 Next_Component_Or_Discriminant (C);
19346 end if;
19347 end loop;
19348 end if;
19350 return False;
19351 end Scalar_Part_Present;
19353 ------------------------
19354 -- Scope_Is_Transient --
19355 ------------------------
19357 function Scope_Is_Transient return Boolean is
19358 begin
19359 return Scope_Stack.Table (Scope_Stack.Last).Is_Transient;
19360 end Scope_Is_Transient;
19362 ------------------
19363 -- Scope_Within --
19364 ------------------
19366 function Scope_Within (Scope1, Scope2 : Entity_Id) return Boolean is
19367 Scop : Entity_Id;
19369 begin
19370 Scop := Scope1;
19371 while Scop /= Standard_Standard loop
19372 Scop := Scope (Scop);
19374 if Scop = Scope2 then
19375 return True;
19376 end if;
19377 end loop;
19379 return False;
19380 end Scope_Within;
19382 --------------------------
19383 -- Scope_Within_Or_Same --
19384 --------------------------
19386 function Scope_Within_Or_Same (Scope1, Scope2 : Entity_Id) return Boolean is
19387 Scop : Entity_Id;
19389 begin
19390 Scop := Scope1;
19391 while Scop /= Standard_Standard loop
19392 if Scop = Scope2 then
19393 return True;
19394 else
19395 Scop := Scope (Scop);
19396 end if;
19397 end loop;
19399 return False;
19400 end Scope_Within_Or_Same;
19402 --------------------
19403 -- Set_Convention --
19404 --------------------
19406 procedure Set_Convention (E : Entity_Id; Val : Snames.Convention_Id) is
19407 begin
19408 Basic_Set_Convention (E, Val);
19410 if Is_Type (E)
19411 and then Is_Access_Subprogram_Type (Base_Type (E))
19412 and then Has_Foreign_Convention (E)
19413 then
19415 -- A pragma Convention in an instance may apply to the subtype
19416 -- created for a formal, in which case we have already verified
19417 -- that conventions of actual and formal match and there is nothing
19418 -- to flag on the subtype.
19420 if In_Instance then
19421 null;
19422 else
19423 Set_Can_Use_Internal_Rep (E, False);
19424 end if;
19425 end if;
19427 -- If E is an object or component, and the type of E is an anonymous
19428 -- access type with no convention set, then also set the convention of
19429 -- the anonymous access type. We do not do this for anonymous protected
19430 -- types, since protected types always have the default convention.
19432 if Present (Etype (E))
19433 and then (Is_Object (E)
19434 or else Ekind (E) = E_Component
19436 -- Allow E_Void (happens for pragma Convention appearing
19437 -- in the middle of a record applying to a component)
19439 or else Ekind (E) = E_Void)
19440 then
19441 declare
19442 Typ : constant Entity_Id := Etype (E);
19444 begin
19445 if Ekind_In (Typ, E_Anonymous_Access_Type,
19446 E_Anonymous_Access_Subprogram_Type)
19447 and then not Has_Convention_Pragma (Typ)
19448 then
19449 Basic_Set_Convention (Typ, Val);
19450 Set_Has_Convention_Pragma (Typ);
19452 -- And for the access subprogram type, deal similarly with the
19453 -- designated E_Subprogram_Type if it is also internal (which
19454 -- it always is?)
19456 if Ekind (Typ) = E_Anonymous_Access_Subprogram_Type then
19457 declare
19458 Dtype : constant Entity_Id := Designated_Type (Typ);
19459 begin
19460 if Ekind (Dtype) = E_Subprogram_Type
19461 and then Is_Itype (Dtype)
19462 and then not Has_Convention_Pragma (Dtype)
19463 then
19464 Basic_Set_Convention (Dtype, Val);
19465 Set_Has_Convention_Pragma (Dtype);
19466 end if;
19467 end;
19468 end if;
19469 end if;
19470 end;
19471 end if;
19472 end Set_Convention;
19474 ------------------------
19475 -- Set_Current_Entity --
19476 ------------------------
19478 -- The given entity is to be set as the currently visible definition of its
19479 -- associated name (i.e. the Node_Id associated with its name). All we have
19480 -- to do is to get the name from the identifier, and then set the
19481 -- associated Node_Id to point to the given entity.
19483 procedure Set_Current_Entity (E : Entity_Id) is
19484 begin
19485 Set_Name_Entity_Id (Chars (E), E);
19486 end Set_Current_Entity;
19488 ---------------------------
19489 -- Set_Debug_Info_Needed --
19490 ---------------------------
19492 procedure Set_Debug_Info_Needed (T : Entity_Id) is
19494 procedure Set_Debug_Info_Needed_If_Not_Set (E : Entity_Id);
19495 pragma Inline (Set_Debug_Info_Needed_If_Not_Set);
19496 -- Used to set debug info in a related node if not set already
19498 --------------------------------------
19499 -- Set_Debug_Info_Needed_If_Not_Set --
19500 --------------------------------------
19502 procedure Set_Debug_Info_Needed_If_Not_Set (E : Entity_Id) is
19503 begin
19504 if Present (E) and then not Needs_Debug_Info (E) then
19505 Set_Debug_Info_Needed (E);
19507 -- For a private type, indicate that the full view also needs
19508 -- debug information.
19510 if Is_Type (E)
19511 and then Is_Private_Type (E)
19512 and then Present (Full_View (E))
19513 then
19514 Set_Debug_Info_Needed (Full_View (E));
19515 end if;
19516 end if;
19517 end Set_Debug_Info_Needed_If_Not_Set;
19519 -- Start of processing for Set_Debug_Info_Needed
19521 begin
19522 -- Nothing to do if argument is Empty or has Debug_Info_Off set, which
19523 -- indicates that Debug_Info_Needed is never required for the entity.
19524 -- Nothing to do if entity comes from a predefined file. Library files
19525 -- are compiled without debug information, but inlined bodies of these
19526 -- routines may appear in user code, and debug information on them ends
19527 -- up complicating debugging the user code.
19529 if No (T)
19530 or else Debug_Info_Off (T)
19531 then
19532 return;
19534 elsif In_Inlined_Body
19535 and then Is_Predefined_File_Name
19536 (Unit_File_Name (Get_Source_Unit (Sloc (T))))
19537 then
19538 Set_Needs_Debug_Info (T, False);
19539 end if;
19541 -- Set flag in entity itself. Note that we will go through the following
19542 -- circuitry even if the flag is already set on T. That's intentional,
19543 -- it makes sure that the flag will be set in subsidiary entities.
19545 Set_Needs_Debug_Info (T);
19547 -- Set flag on subsidiary entities if not set already
19549 if Is_Object (T) then
19550 Set_Debug_Info_Needed_If_Not_Set (Etype (T));
19552 elsif Is_Type (T) then
19553 Set_Debug_Info_Needed_If_Not_Set (Etype (T));
19555 if Is_Record_Type (T) then
19556 declare
19557 Ent : Entity_Id := First_Entity (T);
19558 begin
19559 while Present (Ent) loop
19560 Set_Debug_Info_Needed_If_Not_Set (Ent);
19561 Next_Entity (Ent);
19562 end loop;
19563 end;
19565 -- For a class wide subtype, we also need debug information
19566 -- for the equivalent type.
19568 if Ekind (T) = E_Class_Wide_Subtype then
19569 Set_Debug_Info_Needed_If_Not_Set (Equivalent_Type (T));
19570 end if;
19572 elsif Is_Array_Type (T) then
19573 Set_Debug_Info_Needed_If_Not_Set (Component_Type (T));
19575 declare
19576 Indx : Node_Id := First_Index (T);
19577 begin
19578 while Present (Indx) loop
19579 Set_Debug_Info_Needed_If_Not_Set (Etype (Indx));
19580 Indx := Next_Index (Indx);
19581 end loop;
19582 end;
19584 -- For a packed array type, we also need debug information for
19585 -- the type used to represent the packed array. Conversely, we
19586 -- also need it for the former if we need it for the latter.
19588 if Is_Packed (T) then
19589 Set_Debug_Info_Needed_If_Not_Set (Packed_Array_Impl_Type (T));
19590 end if;
19592 if Is_Packed_Array_Impl_Type (T) then
19593 Set_Debug_Info_Needed_If_Not_Set (Original_Array_Type (T));
19594 end if;
19596 elsif Is_Access_Type (T) then
19597 Set_Debug_Info_Needed_If_Not_Set (Directly_Designated_Type (T));
19599 elsif Is_Private_Type (T) then
19600 declare
19601 FV : constant Entity_Id := Full_View (T);
19603 begin
19604 Set_Debug_Info_Needed_If_Not_Set (FV);
19606 -- If the full view is itself a derived private type, we need
19607 -- debug information on its underlying type.
19609 if Present (FV)
19610 and then Is_Private_Type (FV)
19611 and then Present (Underlying_Full_View (FV))
19612 then
19613 Set_Needs_Debug_Info (Underlying_Full_View (FV));
19614 end if;
19615 end;
19617 elsif Is_Protected_Type (T) then
19618 Set_Debug_Info_Needed_If_Not_Set (Corresponding_Record_Type (T));
19620 elsif Is_Scalar_Type (T) then
19622 -- If the subrange bounds are materialized by dedicated constant
19623 -- objects, also include them in the debug info to make sure the
19624 -- debugger can properly use them.
19626 if Present (Scalar_Range (T))
19627 and then Nkind (Scalar_Range (T)) = N_Range
19628 then
19629 declare
19630 Low_Bnd : constant Node_Id := Type_Low_Bound (T);
19631 High_Bnd : constant Node_Id := Type_High_Bound (T);
19633 begin
19634 if Is_Entity_Name (Low_Bnd) then
19635 Set_Debug_Info_Needed_If_Not_Set (Entity (Low_Bnd));
19636 end if;
19638 if Is_Entity_Name (High_Bnd) then
19639 Set_Debug_Info_Needed_If_Not_Set (Entity (High_Bnd));
19640 end if;
19641 end;
19642 end if;
19643 end if;
19644 end if;
19645 end Set_Debug_Info_Needed;
19647 ----------------------------
19648 -- Set_Entity_With_Checks --
19649 ----------------------------
19651 procedure Set_Entity_With_Checks (N : Node_Id; Val : Entity_Id) is
19652 Val_Actual : Entity_Id;
19653 Nod : Node_Id;
19654 Post_Node : Node_Id;
19656 begin
19657 -- Unconditionally set the entity
19659 Set_Entity (N, Val);
19661 -- The node to post on is the selector in the case of an expanded name,
19662 -- and otherwise the node itself.
19664 if Nkind (N) = N_Expanded_Name then
19665 Post_Node := Selector_Name (N);
19666 else
19667 Post_Node := N;
19668 end if;
19670 -- Check for violation of No_Fixed_IO
19672 if Restriction_Check_Required (No_Fixed_IO)
19673 and then
19674 ((RTU_Loaded (Ada_Text_IO)
19675 and then (Is_RTE (Val, RE_Decimal_IO)
19676 or else
19677 Is_RTE (Val, RE_Fixed_IO)))
19679 or else
19680 (RTU_Loaded (Ada_Wide_Text_IO)
19681 and then (Is_RTE (Val, RO_WT_Decimal_IO)
19682 or else
19683 Is_RTE (Val, RO_WT_Fixed_IO)))
19685 or else
19686 (RTU_Loaded (Ada_Wide_Wide_Text_IO)
19687 and then (Is_RTE (Val, RO_WW_Decimal_IO)
19688 or else
19689 Is_RTE (Val, RO_WW_Fixed_IO))))
19691 -- A special extra check, don't complain about a reference from within
19692 -- the Ada.Interrupts package itself!
19694 and then not In_Same_Extended_Unit (N, Val)
19695 then
19696 Check_Restriction (No_Fixed_IO, Post_Node);
19697 end if;
19699 -- Remaining checks are only done on source nodes. Note that we test
19700 -- for violation of No_Fixed_IO even on non-source nodes, because the
19701 -- cases for checking violations of this restriction are instantiations
19702 -- where the reference in the instance has Comes_From_Source False.
19704 if not Comes_From_Source (N) then
19705 return;
19706 end if;
19708 -- Check for violation of No_Abort_Statements, which is triggered by
19709 -- call to Ada.Task_Identification.Abort_Task.
19711 if Restriction_Check_Required (No_Abort_Statements)
19712 and then (Is_RTE (Val, RE_Abort_Task))
19714 -- A special extra check, don't complain about a reference from within
19715 -- the Ada.Task_Identification package itself!
19717 and then not In_Same_Extended_Unit (N, Val)
19718 then
19719 Check_Restriction (No_Abort_Statements, Post_Node);
19720 end if;
19722 if Val = Standard_Long_Long_Integer then
19723 Check_Restriction (No_Long_Long_Integers, Post_Node);
19724 end if;
19726 -- Check for violation of No_Dynamic_Attachment
19728 if Restriction_Check_Required (No_Dynamic_Attachment)
19729 and then RTU_Loaded (Ada_Interrupts)
19730 and then (Is_RTE (Val, RE_Is_Reserved) or else
19731 Is_RTE (Val, RE_Is_Attached) or else
19732 Is_RTE (Val, RE_Current_Handler) or else
19733 Is_RTE (Val, RE_Attach_Handler) or else
19734 Is_RTE (Val, RE_Exchange_Handler) or else
19735 Is_RTE (Val, RE_Detach_Handler) or else
19736 Is_RTE (Val, RE_Reference))
19738 -- A special extra check, don't complain about a reference from within
19739 -- the Ada.Interrupts package itself!
19741 and then not In_Same_Extended_Unit (N, Val)
19742 then
19743 Check_Restriction (No_Dynamic_Attachment, Post_Node);
19744 end if;
19746 -- Check for No_Implementation_Identifiers
19748 if Restriction_Check_Required (No_Implementation_Identifiers) then
19750 -- We have an implementation defined entity if it is marked as
19751 -- implementation defined, or is defined in a package marked as
19752 -- implementation defined. However, library packages themselves
19753 -- are excluded (we don't want to flag Interfaces itself, just
19754 -- the entities within it).
19756 if (Is_Implementation_Defined (Val)
19757 or else
19758 (Present (Scope (Val))
19759 and then Is_Implementation_Defined (Scope (Val))))
19760 and then not (Ekind_In (Val, E_Package, E_Generic_Package)
19761 and then Is_Library_Level_Entity (Val))
19762 then
19763 Check_Restriction (No_Implementation_Identifiers, Post_Node);
19764 end if;
19765 end if;
19767 -- Do the style check
19769 if Style_Check
19770 and then not Suppress_Style_Checks (Val)
19771 and then not In_Instance
19772 then
19773 if Nkind (N) = N_Identifier then
19774 Nod := N;
19775 elsif Nkind (N) = N_Expanded_Name then
19776 Nod := Selector_Name (N);
19777 else
19778 return;
19779 end if;
19781 -- A special situation arises for derived operations, where we want
19782 -- to do the check against the parent (since the Sloc of the derived
19783 -- operation points to the derived type declaration itself).
19785 Val_Actual := Val;
19786 while not Comes_From_Source (Val_Actual)
19787 and then Nkind (Val_Actual) in N_Entity
19788 and then (Ekind (Val_Actual) = E_Enumeration_Literal
19789 or else Is_Subprogram_Or_Generic_Subprogram (Val_Actual))
19790 and then Present (Alias (Val_Actual))
19791 loop
19792 Val_Actual := Alias (Val_Actual);
19793 end loop;
19795 -- Renaming declarations for generic actuals do not come from source,
19796 -- and have a different name from that of the entity they rename, so
19797 -- there is no style check to perform here.
19799 if Chars (Nod) = Chars (Val_Actual) then
19800 Style.Check_Identifier (Nod, Val_Actual);
19801 end if;
19802 end if;
19804 Set_Entity (N, Val);
19805 end Set_Entity_With_Checks;
19807 ------------------------
19808 -- Set_Name_Entity_Id --
19809 ------------------------
19811 procedure Set_Name_Entity_Id (Id : Name_Id; Val : Entity_Id) is
19812 begin
19813 Set_Name_Table_Int (Id, Int (Val));
19814 end Set_Name_Entity_Id;
19816 ---------------------
19817 -- Set_Next_Actual --
19818 ---------------------
19820 procedure Set_Next_Actual (Ass1_Id : Node_Id; Ass2_Id : Node_Id) is
19821 begin
19822 if Nkind (Parent (Ass1_Id)) = N_Parameter_Association then
19823 Set_First_Named_Actual (Parent (Ass1_Id), Ass2_Id);
19824 end if;
19825 end Set_Next_Actual;
19827 ----------------------------------
19828 -- Set_Optimize_Alignment_Flags --
19829 ----------------------------------
19831 procedure Set_Optimize_Alignment_Flags (E : Entity_Id) is
19832 begin
19833 if Optimize_Alignment = 'S' then
19834 Set_Optimize_Alignment_Space (E);
19835 elsif Optimize_Alignment = 'T' then
19836 Set_Optimize_Alignment_Time (E);
19837 end if;
19838 end Set_Optimize_Alignment_Flags;
19840 -----------------------
19841 -- Set_Public_Status --
19842 -----------------------
19844 procedure Set_Public_Status (Id : Entity_Id) is
19845 S : constant Entity_Id := Current_Scope;
19847 function Within_HSS_Or_If (E : Entity_Id) return Boolean;
19848 -- Determines if E is defined within handled statement sequence or
19849 -- an if statement, returns True if so, False otherwise.
19851 ----------------------
19852 -- Within_HSS_Or_If --
19853 ----------------------
19855 function Within_HSS_Or_If (E : Entity_Id) return Boolean is
19856 N : Node_Id;
19857 begin
19858 N := Declaration_Node (E);
19859 loop
19860 N := Parent (N);
19862 if No (N) then
19863 return False;
19865 elsif Nkind_In (N, N_Handled_Sequence_Of_Statements,
19866 N_If_Statement)
19867 then
19868 return True;
19869 end if;
19870 end loop;
19871 end Within_HSS_Or_If;
19873 -- Start of processing for Set_Public_Status
19875 begin
19876 -- Everything in the scope of Standard is public
19878 if S = Standard_Standard then
19879 Set_Is_Public (Id);
19881 -- Entity is definitely not public if enclosing scope is not public
19883 elsif not Is_Public (S) then
19884 return;
19886 -- An object or function declaration that occurs in a handled sequence
19887 -- of statements or within an if statement is the declaration for a
19888 -- temporary object or local subprogram generated by the expander. It
19889 -- never needs to be made public and furthermore, making it public can
19890 -- cause back end problems.
19892 elsif Nkind_In (Parent (Id), N_Object_Declaration,
19893 N_Function_Specification)
19894 and then Within_HSS_Or_If (Id)
19895 then
19896 return;
19898 -- Entities in public packages or records are public
19900 elsif Ekind (S) = E_Package or Is_Record_Type (S) then
19901 Set_Is_Public (Id);
19903 -- The bounds of an entry family declaration can generate object
19904 -- declarations that are visible to the back-end, e.g. in the
19905 -- the declaration of a composite type that contains tasks.
19907 elsif Is_Concurrent_Type (S)
19908 and then not Has_Completion (S)
19909 and then Nkind (Parent (Id)) = N_Object_Declaration
19910 then
19911 Set_Is_Public (Id);
19912 end if;
19913 end Set_Public_Status;
19915 -----------------------------
19916 -- Set_Referenced_Modified --
19917 -----------------------------
19919 procedure Set_Referenced_Modified (N : Node_Id; Out_Param : Boolean) is
19920 Pref : Node_Id;
19922 begin
19923 -- Deal with indexed or selected component where prefix is modified
19925 if Nkind_In (N, N_Indexed_Component, N_Selected_Component) then
19926 Pref := Prefix (N);
19928 -- If prefix is access type, then it is the designated object that is
19929 -- being modified, which means we have no entity to set the flag on.
19931 if No (Etype (Pref)) or else Is_Access_Type (Etype (Pref)) then
19932 return;
19934 -- Otherwise chase the prefix
19936 else
19937 Set_Referenced_Modified (Pref, Out_Param);
19938 end if;
19940 -- Otherwise see if we have an entity name (only other case to process)
19942 elsif Is_Entity_Name (N) and then Present (Entity (N)) then
19943 Set_Referenced_As_LHS (Entity (N), not Out_Param);
19944 Set_Referenced_As_Out_Parameter (Entity (N), Out_Param);
19945 end if;
19946 end Set_Referenced_Modified;
19948 ----------------------------
19949 -- Set_Scope_Is_Transient --
19950 ----------------------------
19952 procedure Set_Scope_Is_Transient (V : Boolean := True) is
19953 begin
19954 Scope_Stack.Table (Scope_Stack.Last).Is_Transient := V;
19955 end Set_Scope_Is_Transient;
19957 -------------------
19958 -- Set_Size_Info --
19959 -------------------
19961 procedure Set_Size_Info (T1, T2 : Entity_Id) is
19962 begin
19963 -- We copy Esize, but not RM_Size, since in general RM_Size is
19964 -- subtype specific and does not get inherited by all subtypes.
19966 Set_Esize (T1, Esize (T2));
19967 Set_Has_Biased_Representation (T1, Has_Biased_Representation (T2));
19969 if Is_Discrete_Or_Fixed_Point_Type (T1)
19970 and then
19971 Is_Discrete_Or_Fixed_Point_Type (T2)
19972 then
19973 Set_Is_Unsigned_Type (T1, Is_Unsigned_Type (T2));
19974 end if;
19976 Set_Alignment (T1, Alignment (T2));
19977 end Set_Size_Info;
19979 --------------------
19980 -- Static_Boolean --
19981 --------------------
19983 function Static_Boolean (N : Node_Id) return Uint is
19984 begin
19985 Analyze_And_Resolve (N, Standard_Boolean);
19987 if N = Error
19988 or else Error_Posted (N)
19989 or else Etype (N) = Any_Type
19990 then
19991 return No_Uint;
19992 end if;
19994 if Is_OK_Static_Expression (N) then
19995 if not Raises_Constraint_Error (N) then
19996 return Expr_Value (N);
19997 else
19998 return No_Uint;
19999 end if;
20001 elsif Etype (N) = Any_Type then
20002 return No_Uint;
20004 else
20005 Flag_Non_Static_Expr
20006 ("static boolean expression required here", N);
20007 return No_Uint;
20008 end if;
20009 end Static_Boolean;
20011 --------------------
20012 -- Static_Integer --
20013 --------------------
20015 function Static_Integer (N : Node_Id) return Uint is
20016 begin
20017 Analyze_And_Resolve (N, Any_Integer);
20019 if N = Error
20020 or else Error_Posted (N)
20021 or else Etype (N) = Any_Type
20022 then
20023 return No_Uint;
20024 end if;
20026 if Is_OK_Static_Expression (N) then
20027 if not Raises_Constraint_Error (N) then
20028 return Expr_Value (N);
20029 else
20030 return No_Uint;
20031 end if;
20033 elsif Etype (N) = Any_Type then
20034 return No_Uint;
20036 else
20037 Flag_Non_Static_Expr
20038 ("static integer expression required here", N);
20039 return No_Uint;
20040 end if;
20041 end Static_Integer;
20043 --------------------------
20044 -- Statically_Different --
20045 --------------------------
20047 function Statically_Different (E1, E2 : Node_Id) return Boolean is
20048 R1 : constant Node_Id := Get_Referenced_Object (E1);
20049 R2 : constant Node_Id := Get_Referenced_Object (E2);
20050 begin
20051 return Is_Entity_Name (R1)
20052 and then Is_Entity_Name (R2)
20053 and then Entity (R1) /= Entity (R2)
20054 and then not Is_Formal (Entity (R1))
20055 and then not Is_Formal (Entity (R2));
20056 end Statically_Different;
20058 --------------------------------------
20059 -- Subject_To_Loop_Entry_Attributes --
20060 --------------------------------------
20062 function Subject_To_Loop_Entry_Attributes (N : Node_Id) return Boolean is
20063 Stmt : Node_Id;
20065 begin
20066 Stmt := N;
20068 -- The expansion mechanism transform a loop subject to at least one
20069 -- 'Loop_Entry attribute into a conditional block. Infinite loops lack
20070 -- the conditional part.
20072 if Nkind_In (Stmt, N_Block_Statement, N_If_Statement)
20073 and then Nkind (Original_Node (N)) = N_Loop_Statement
20074 then
20075 Stmt := Original_Node (N);
20076 end if;
20078 return
20079 Nkind (Stmt) = N_Loop_Statement
20080 and then Present (Identifier (Stmt))
20081 and then Present (Entity (Identifier (Stmt)))
20082 and then Has_Loop_Entry_Attributes (Entity (Identifier (Stmt)));
20083 end Subject_To_Loop_Entry_Attributes;
20085 -----------------------------
20086 -- Subprogram_Access_Level --
20087 -----------------------------
20089 function Subprogram_Access_Level (Subp : Entity_Id) return Uint is
20090 begin
20091 if Present (Alias (Subp)) then
20092 return Subprogram_Access_Level (Alias (Subp));
20093 else
20094 return Scope_Depth (Enclosing_Dynamic_Scope (Subp));
20095 end if;
20096 end Subprogram_Access_Level;
20098 -------------------------------
20099 -- Support_Atomic_Primitives --
20100 -------------------------------
20102 function Support_Atomic_Primitives (Typ : Entity_Id) return Boolean is
20103 Size : Int;
20105 begin
20106 -- Verify the alignment of Typ is known
20108 if not Known_Alignment (Typ) then
20109 return False;
20110 end if;
20112 if Known_Static_Esize (Typ) then
20113 Size := UI_To_Int (Esize (Typ));
20115 -- If the Esize (Object_Size) is unknown at compile time, look at the
20116 -- RM_Size (Value_Size) which may have been set by an explicit rep item.
20118 elsif Known_Static_RM_Size (Typ) then
20119 Size := UI_To_Int (RM_Size (Typ));
20121 -- Otherwise, the size is considered to be unknown.
20123 else
20124 return False;
20125 end if;
20127 -- Check that the size of the component is 8, 16, 32, or 64 bits and
20128 -- that Typ is properly aligned.
20130 case Size is
20131 when 8 | 16 | 32 | 64 =>
20132 return Size = UI_To_Int (Alignment (Typ)) * 8;
20133 when others =>
20134 return False;
20135 end case;
20136 end Support_Atomic_Primitives;
20138 -----------------
20139 -- Trace_Scope --
20140 -----------------
20142 procedure Trace_Scope (N : Node_Id; E : Entity_Id; Msg : String) is
20143 begin
20144 if Debug_Flag_W then
20145 for J in 0 .. Scope_Stack.Last loop
20146 Write_Str (" ");
20147 end loop;
20149 Write_Str (Msg);
20150 Write_Name (Chars (E));
20151 Write_Str (" from ");
20152 Write_Location (Sloc (N));
20153 Write_Eol;
20154 end if;
20155 end Trace_Scope;
20157 -----------------------
20158 -- Transfer_Entities --
20159 -----------------------
20161 procedure Transfer_Entities (From : Entity_Id; To : Entity_Id) is
20162 procedure Set_Public_Status_Of (Id : Entity_Id);
20163 -- Set the Is_Public attribute of arbitrary entity Id by calling routine
20164 -- Set_Public_Status. If successfull and Id denotes a record type, set
20165 -- the Is_Public attribute of its fields.
20167 --------------------------
20168 -- Set_Public_Status_Of --
20169 --------------------------
20171 procedure Set_Public_Status_Of (Id : Entity_Id) is
20172 Field : Entity_Id;
20174 begin
20175 if not Is_Public (Id) then
20176 Set_Public_Status (Id);
20178 -- When the input entity is a public record type, ensure that all
20179 -- its internal fields are also exposed to the linker. The fields
20180 -- of a class-wide type are never made public.
20182 if Is_Public (Id)
20183 and then Is_Record_Type (Id)
20184 and then not Is_Class_Wide_Type (Id)
20185 then
20186 Field := First_Entity (Id);
20187 while Present (Field) loop
20188 Set_Is_Public (Field);
20189 Next_Entity (Field);
20190 end loop;
20191 end if;
20192 end if;
20193 end Set_Public_Status_Of;
20195 -- Local variables
20197 Full_Id : Entity_Id;
20198 Id : Entity_Id;
20200 -- Start of processing for Transfer_Entities
20202 begin
20203 Id := First_Entity (From);
20205 if Present (Id) then
20207 -- Merge the entity chain of the source scope with that of the
20208 -- destination scope.
20210 if Present (Last_Entity (To)) then
20211 Set_Next_Entity (Last_Entity (To), Id);
20212 else
20213 Set_First_Entity (To, Id);
20214 end if;
20216 Set_Last_Entity (To, Last_Entity (From));
20218 -- Inspect the entities of the source scope and update their Scope
20219 -- attribute.
20221 while Present (Id) loop
20222 Set_Scope (Id, To);
20223 Set_Public_Status_Of (Id);
20225 -- Handle an internally generated full view for a private type
20227 if Is_Private_Type (Id)
20228 and then Present (Full_View (Id))
20229 and then Is_Itype (Full_View (Id))
20230 then
20231 Full_Id := Full_View (Id);
20233 Set_Scope (Full_Id, To);
20234 Set_Public_Status_Of (Full_Id);
20235 end if;
20237 Next_Entity (Id);
20238 end loop;
20240 Set_First_Entity (From, Empty);
20241 Set_Last_Entity (From, Empty);
20242 end if;
20243 end Transfer_Entities;
20245 -----------------------
20246 -- Type_Access_Level --
20247 -----------------------
20249 function Type_Access_Level (Typ : Entity_Id) return Uint is
20250 Btyp : Entity_Id;
20252 begin
20253 Btyp := Base_Type (Typ);
20255 -- Ada 2005 (AI-230): For most cases of anonymous access types, we
20256 -- simply use the level where the type is declared. This is true for
20257 -- stand-alone object declarations, and for anonymous access types
20258 -- associated with components the level is the same as that of the
20259 -- enclosing composite type. However, special treatment is needed for
20260 -- the cases of access parameters, return objects of an anonymous access
20261 -- type, and, in Ada 95, access discriminants of limited types.
20263 if Is_Access_Type (Btyp) then
20264 if Ekind (Btyp) = E_Anonymous_Access_Type then
20266 -- If the type is a nonlocal anonymous access type (such as for
20267 -- an access parameter) we treat it as being declared at the
20268 -- library level to ensure that names such as X.all'access don't
20269 -- fail static accessibility checks.
20271 if not Is_Local_Anonymous_Access (Typ) then
20272 return Scope_Depth (Standard_Standard);
20274 -- If this is a return object, the accessibility level is that of
20275 -- the result subtype of the enclosing function. The test here is
20276 -- little complicated, because we have to account for extended
20277 -- return statements that have been rewritten as blocks, in which
20278 -- case we have to find and the Is_Return_Object attribute of the
20279 -- itype's associated object. It would be nice to find a way to
20280 -- simplify this test, but it doesn't seem worthwhile to add a new
20281 -- flag just for purposes of this test. ???
20283 elsif Ekind (Scope (Btyp)) = E_Return_Statement
20284 or else
20285 (Is_Itype (Btyp)
20286 and then Nkind (Associated_Node_For_Itype (Btyp)) =
20287 N_Object_Declaration
20288 and then Is_Return_Object
20289 (Defining_Identifier
20290 (Associated_Node_For_Itype (Btyp))))
20291 then
20292 declare
20293 Scop : Entity_Id;
20295 begin
20296 Scop := Scope (Scope (Btyp));
20297 while Present (Scop) loop
20298 exit when Ekind (Scop) = E_Function;
20299 Scop := Scope (Scop);
20300 end loop;
20302 -- Treat the return object's type as having the level of the
20303 -- function's result subtype (as per RM05-6.5(5.3/2)).
20305 return Type_Access_Level (Etype (Scop));
20306 end;
20307 end if;
20308 end if;
20310 Btyp := Root_Type (Btyp);
20312 -- The accessibility level of anonymous access types associated with
20313 -- discriminants is that of the current instance of the type, and
20314 -- that's deeper than the type itself (AARM 3.10.2 (12.3.21)).
20316 -- AI-402: access discriminants have accessibility based on the
20317 -- object rather than the type in Ada 2005, so the above paragraph
20318 -- doesn't apply.
20320 -- ??? Needs completion with rules from AI-416
20322 if Ada_Version <= Ada_95
20323 and then Ekind (Typ) = E_Anonymous_Access_Type
20324 and then Present (Associated_Node_For_Itype (Typ))
20325 and then Nkind (Associated_Node_For_Itype (Typ)) =
20326 N_Discriminant_Specification
20327 then
20328 return Scope_Depth (Enclosing_Dynamic_Scope (Btyp)) + 1;
20329 end if;
20330 end if;
20332 -- Return library level for a generic formal type. This is done because
20333 -- RM(10.3.2) says that "The statically deeper relationship does not
20334 -- apply to ... a descendant of a generic formal type". Rather than
20335 -- checking at each point where a static accessibility check is
20336 -- performed to see if we are dealing with a formal type, this rule is
20337 -- implemented by having Type_Access_Level and Deepest_Type_Access_Level
20338 -- return extreme values for a formal type; Deepest_Type_Access_Level
20339 -- returns Int'Last. By calling the appropriate function from among the
20340 -- two, we ensure that the static accessibility check will pass if we
20341 -- happen to run into a formal type. More specifically, we should call
20342 -- Deepest_Type_Access_Level instead of Type_Access_Level whenever the
20343 -- call occurs as part of a static accessibility check and the error
20344 -- case is the case where the type's level is too shallow (as opposed
20345 -- to too deep).
20347 if Is_Generic_Type (Root_Type (Btyp)) then
20348 return Scope_Depth (Standard_Standard);
20349 end if;
20351 return Scope_Depth (Enclosing_Dynamic_Scope (Btyp));
20352 end Type_Access_Level;
20354 ------------------------------------
20355 -- Type_Without_Stream_Operation --
20356 ------------------------------------
20358 function Type_Without_Stream_Operation
20359 (T : Entity_Id;
20360 Op : TSS_Name_Type := TSS_Null) return Entity_Id
20362 BT : constant Entity_Id := Base_Type (T);
20363 Op_Missing : Boolean;
20365 begin
20366 if not Restriction_Active (No_Default_Stream_Attributes) then
20367 return Empty;
20368 end if;
20370 if Is_Elementary_Type (T) then
20371 if Op = TSS_Null then
20372 Op_Missing :=
20373 No (TSS (BT, TSS_Stream_Read))
20374 or else No (TSS (BT, TSS_Stream_Write));
20376 else
20377 Op_Missing := No (TSS (BT, Op));
20378 end if;
20380 if Op_Missing then
20381 return T;
20382 else
20383 return Empty;
20384 end if;
20386 elsif Is_Array_Type (T) then
20387 return Type_Without_Stream_Operation (Component_Type (T), Op);
20389 elsif Is_Record_Type (T) then
20390 declare
20391 Comp : Entity_Id;
20392 C_Typ : Entity_Id;
20394 begin
20395 Comp := First_Component (T);
20396 while Present (Comp) loop
20397 C_Typ := Type_Without_Stream_Operation (Etype (Comp), Op);
20399 if Present (C_Typ) then
20400 return C_Typ;
20401 end if;
20403 Next_Component (Comp);
20404 end loop;
20406 return Empty;
20407 end;
20409 elsif Is_Private_Type (T) and then Present (Full_View (T)) then
20410 return Type_Without_Stream_Operation (Full_View (T), Op);
20411 else
20412 return Empty;
20413 end if;
20414 end Type_Without_Stream_Operation;
20416 ----------------------------
20417 -- Unique_Defining_Entity --
20418 ----------------------------
20420 function Unique_Defining_Entity (N : Node_Id) return Entity_Id is
20421 begin
20422 return Unique_Entity (Defining_Entity (N));
20423 end Unique_Defining_Entity;
20425 -------------------
20426 -- Unique_Entity --
20427 -------------------
20429 function Unique_Entity (E : Entity_Id) return Entity_Id is
20430 U : Entity_Id := E;
20431 P : Node_Id;
20433 begin
20434 case Ekind (E) is
20435 when E_Constant =>
20436 if Present (Full_View (E)) then
20437 U := Full_View (E);
20438 end if;
20440 when Entry_Kind =>
20441 if Nkind (Parent (E)) = N_Entry_Body then
20442 declare
20443 Prot_Item : Entity_Id;
20444 begin
20445 -- Traverse the entity list of the protected type and locate
20446 -- an entry declaration which matches the entry body.
20448 Prot_Item := First_Entity (Scope (E));
20449 while Present (Prot_Item) loop
20450 if Ekind (Prot_Item) = E_Entry
20451 and then Corresponding_Body (Parent (Prot_Item)) = E
20452 then
20453 U := Prot_Item;
20454 exit;
20455 end if;
20457 Next_Entity (Prot_Item);
20458 end loop;
20459 end;
20460 end if;
20462 when Formal_Kind =>
20463 if Present (Spec_Entity (E)) then
20464 U := Spec_Entity (E);
20465 end if;
20467 when E_Package_Body =>
20468 P := Parent (E);
20470 if Nkind (P) = N_Defining_Program_Unit_Name then
20471 P := Parent (P);
20472 end if;
20474 if Nkind (P) = N_Package_Body
20475 and then Present (Corresponding_Spec (P))
20476 then
20477 U := Corresponding_Spec (P);
20479 elsif Nkind (P) = N_Package_Body_Stub
20480 and then Present (Corresponding_Spec_Of_Stub (P))
20481 then
20482 U := Corresponding_Spec_Of_Stub (P);
20483 end if;
20485 when E_Protected_Body =>
20486 P := Parent (E);
20488 if Nkind (P) = N_Protected_Body
20489 and then Present (Corresponding_Spec (P))
20490 then
20491 U := Corresponding_Spec (P);
20493 elsif Nkind (P) = N_Protected_Body_Stub
20494 and then Present (Corresponding_Spec_Of_Stub (P))
20495 then
20496 U := Corresponding_Spec_Of_Stub (P);
20497 end if;
20499 when E_Subprogram_Body =>
20500 P := Parent (E);
20502 if Nkind (P) = N_Defining_Program_Unit_Name then
20503 P := Parent (P);
20504 end if;
20506 P := Parent (P);
20508 if Nkind (P) = N_Subprogram_Body
20509 and then Present (Corresponding_Spec (P))
20510 then
20511 U := Corresponding_Spec (P);
20513 elsif Nkind (P) = N_Subprogram_Body_Stub
20514 and then Present (Corresponding_Spec_Of_Stub (P))
20515 then
20516 U := Corresponding_Spec_Of_Stub (P);
20518 elsif Nkind (P) = N_Subprogram_Renaming_Declaration then
20519 U := Corresponding_Spec (P);
20520 end if;
20522 when E_Task_Body =>
20523 P := Parent (E);
20525 if Nkind (P) = N_Task_Body
20526 and then Present (Corresponding_Spec (P))
20527 then
20528 U := Corresponding_Spec (P);
20530 elsif Nkind (P) = N_Task_Body_Stub
20531 and then Present (Corresponding_Spec_Of_Stub (P))
20532 then
20533 U := Corresponding_Spec_Of_Stub (P);
20534 end if;
20536 when Type_Kind =>
20537 if Present (Full_View (E)) then
20538 U := Full_View (E);
20539 end if;
20541 when others =>
20542 null;
20543 end case;
20545 return U;
20546 end Unique_Entity;
20548 -----------------
20549 -- Unique_Name --
20550 -----------------
20552 function Unique_Name (E : Entity_Id) return String is
20554 -- Names of E_Subprogram_Body or E_Package_Body entities are not
20555 -- reliable, as they may not include the overloading suffix. Instead,
20556 -- when looking for the name of E or one of its enclosing scope, we get
20557 -- the name of the corresponding Unique_Entity.
20559 function Get_Scoped_Name (E : Entity_Id) return String;
20560 -- Return the name of E prefixed by all the names of the scopes to which
20561 -- E belongs, except for Standard.
20563 ---------------------
20564 -- Get_Scoped_Name --
20565 ---------------------
20567 function Get_Scoped_Name (E : Entity_Id) return String is
20568 Name : constant String := Get_Name_String (Chars (E));
20569 begin
20570 if Has_Fully_Qualified_Name (E)
20571 or else Scope (E) = Standard_Standard
20572 then
20573 return Name;
20574 else
20575 return Get_Scoped_Name (Unique_Entity (Scope (E))) & "__" & Name;
20576 end if;
20577 end Get_Scoped_Name;
20579 -- Start of processing for Unique_Name
20581 begin
20582 if E = Standard_Standard then
20583 return Get_Name_String (Name_Standard);
20585 elsif Scope (E) = Standard_Standard
20586 and then not (Ekind (E) = E_Package or else Is_Subprogram (E))
20587 then
20588 return Get_Name_String (Name_Standard) & "__" &
20589 Get_Name_String (Chars (E));
20591 elsif Ekind (E) = E_Enumeration_Literal then
20592 return Unique_Name (Etype (E)) & "__" & Get_Name_String (Chars (E));
20594 else
20595 return Get_Scoped_Name (Unique_Entity (E));
20596 end if;
20597 end Unique_Name;
20599 ---------------------
20600 -- Unit_Is_Visible --
20601 ---------------------
20603 function Unit_Is_Visible (U : Entity_Id) return Boolean is
20604 Curr : constant Node_Id := Cunit (Current_Sem_Unit);
20605 Curr_Entity : constant Entity_Id := Cunit_Entity (Current_Sem_Unit);
20607 function Unit_In_Parent_Context (Par_Unit : Node_Id) return Boolean;
20608 -- For a child unit, check whether unit appears in a with_clause
20609 -- of a parent.
20611 function Unit_In_Context (Comp_Unit : Node_Id) return Boolean;
20612 -- Scan the context clause of one compilation unit looking for a
20613 -- with_clause for the unit in question.
20615 ----------------------------
20616 -- Unit_In_Parent_Context --
20617 ----------------------------
20619 function Unit_In_Parent_Context (Par_Unit : Node_Id) return Boolean is
20620 begin
20621 if Unit_In_Context (Par_Unit) then
20622 return True;
20624 elsif Is_Child_Unit (Defining_Entity (Unit (Par_Unit))) then
20625 return Unit_In_Parent_Context (Parent_Spec (Unit (Par_Unit)));
20627 else
20628 return False;
20629 end if;
20630 end Unit_In_Parent_Context;
20632 ---------------------
20633 -- Unit_In_Context --
20634 ---------------------
20636 function Unit_In_Context (Comp_Unit : Node_Id) return Boolean is
20637 Clause : Node_Id;
20639 begin
20640 Clause := First (Context_Items (Comp_Unit));
20641 while Present (Clause) loop
20642 if Nkind (Clause) = N_With_Clause then
20643 if Library_Unit (Clause) = U then
20644 return True;
20646 -- The with_clause may denote a renaming of the unit we are
20647 -- looking for, eg. Text_IO which renames Ada.Text_IO.
20649 elsif
20650 Renamed_Entity (Entity (Name (Clause))) =
20651 Defining_Entity (Unit (U))
20652 then
20653 return True;
20654 end if;
20655 end if;
20657 Next (Clause);
20658 end loop;
20660 return False;
20661 end Unit_In_Context;
20663 -- Start of processing for Unit_Is_Visible
20665 begin
20666 -- The currrent unit is directly visible
20668 if Curr = U then
20669 return True;
20671 elsif Unit_In_Context (Curr) then
20672 return True;
20674 -- If the current unit is a body, check the context of the spec
20676 elsif Nkind (Unit (Curr)) = N_Package_Body
20677 or else
20678 (Nkind (Unit (Curr)) = N_Subprogram_Body
20679 and then not Acts_As_Spec (Unit (Curr)))
20680 then
20681 if Unit_In_Context (Library_Unit (Curr)) then
20682 return True;
20683 end if;
20684 end if;
20686 -- If the spec is a child unit, examine the parents
20688 if Is_Child_Unit (Curr_Entity) then
20689 if Nkind (Unit (Curr)) in N_Unit_Body then
20690 return
20691 Unit_In_Parent_Context
20692 (Parent_Spec (Unit (Library_Unit (Curr))));
20693 else
20694 return Unit_In_Parent_Context (Parent_Spec (Unit (Curr)));
20695 end if;
20697 else
20698 return False;
20699 end if;
20700 end Unit_Is_Visible;
20702 ------------------------------
20703 -- Universal_Interpretation --
20704 ------------------------------
20706 function Universal_Interpretation (Opnd : Node_Id) return Entity_Id is
20707 Index : Interp_Index;
20708 It : Interp;
20710 begin
20711 -- The argument may be a formal parameter of an operator or subprogram
20712 -- with multiple interpretations, or else an expression for an actual.
20714 if Nkind (Opnd) = N_Defining_Identifier
20715 or else not Is_Overloaded (Opnd)
20716 then
20717 if Etype (Opnd) = Universal_Integer
20718 or else Etype (Opnd) = Universal_Real
20719 then
20720 return Etype (Opnd);
20721 else
20722 return Empty;
20723 end if;
20725 else
20726 Get_First_Interp (Opnd, Index, It);
20727 while Present (It.Typ) loop
20728 if It.Typ = Universal_Integer
20729 or else It.Typ = Universal_Real
20730 then
20731 return It.Typ;
20732 end if;
20734 Get_Next_Interp (Index, It);
20735 end loop;
20737 return Empty;
20738 end if;
20739 end Universal_Interpretation;
20741 ---------------
20742 -- Unqualify --
20743 ---------------
20745 function Unqualify (Expr : Node_Id) return Node_Id is
20746 begin
20747 -- Recurse to handle unlikely case of multiple levels of qualification
20749 if Nkind (Expr) = N_Qualified_Expression then
20750 return Unqualify (Expression (Expr));
20752 -- Normal case, not a qualified expression
20754 else
20755 return Expr;
20756 end if;
20757 end Unqualify;
20759 -----------------------
20760 -- Visible_Ancestors --
20761 -----------------------
20763 function Visible_Ancestors (Typ : Entity_Id) return Elist_Id is
20764 List_1 : Elist_Id;
20765 List_2 : Elist_Id;
20766 Elmt : Elmt_Id;
20768 begin
20769 pragma Assert (Is_Record_Type (Typ) and then Is_Tagged_Type (Typ));
20771 -- Collect all the parents and progenitors of Typ. If the full-view of
20772 -- private parents and progenitors is available then it is used to
20773 -- generate the list of visible ancestors; otherwise their partial
20774 -- view is added to the resulting list.
20776 Collect_Parents
20777 (T => Typ,
20778 List => List_1,
20779 Use_Full_View => True);
20781 Collect_Interfaces
20782 (T => Typ,
20783 Ifaces_List => List_2,
20784 Exclude_Parents => True,
20785 Use_Full_View => True);
20787 -- Join the two lists. Avoid duplications because an interface may
20788 -- simultaneously be parent and progenitor of a type.
20790 Elmt := First_Elmt (List_2);
20791 while Present (Elmt) loop
20792 Append_Unique_Elmt (Node (Elmt), List_1);
20793 Next_Elmt (Elmt);
20794 end loop;
20796 return List_1;
20797 end Visible_Ancestors;
20799 ----------------------
20800 -- Within_Init_Proc --
20801 ----------------------
20803 function Within_Init_Proc return Boolean is
20804 S : Entity_Id;
20806 begin
20807 S := Current_Scope;
20808 while not Is_Overloadable (S) loop
20809 if S = Standard_Standard then
20810 return False;
20811 else
20812 S := Scope (S);
20813 end if;
20814 end loop;
20816 return Is_Init_Proc (S);
20817 end Within_Init_Proc;
20819 ------------------
20820 -- Within_Scope --
20821 ------------------
20823 function Within_Scope (E : Entity_Id; S : Entity_Id) return Boolean is
20824 begin
20825 return Scope_Within_Or_Same (Scope (E), S);
20826 end Within_Scope;
20828 ----------------
20829 -- Wrong_Type --
20830 ----------------
20832 procedure Wrong_Type (Expr : Node_Id; Expected_Type : Entity_Id) is
20833 Found_Type : constant Entity_Id := First_Subtype (Etype (Expr));
20834 Expec_Type : constant Entity_Id := First_Subtype (Expected_Type);
20836 Matching_Field : Entity_Id;
20837 -- Entity to give a more precise suggestion on how to write a one-
20838 -- element positional aggregate.
20840 function Has_One_Matching_Field return Boolean;
20841 -- Determines if Expec_Type is a record type with a single component or
20842 -- discriminant whose type matches the found type or is one dimensional
20843 -- array whose component type matches the found type. In the case of
20844 -- one discriminant, we ignore the variant parts. That's not accurate,
20845 -- but good enough for the warning.
20847 ----------------------------
20848 -- Has_One_Matching_Field --
20849 ----------------------------
20851 function Has_One_Matching_Field return Boolean is
20852 E : Entity_Id;
20854 begin
20855 Matching_Field := Empty;
20857 if Is_Array_Type (Expec_Type)
20858 and then Number_Dimensions (Expec_Type) = 1
20859 and then Covers (Etype (Component_Type (Expec_Type)), Found_Type)
20860 then
20861 -- Use type name if available. This excludes multidimensional
20862 -- arrays and anonymous arrays.
20864 if Comes_From_Source (Expec_Type) then
20865 Matching_Field := Expec_Type;
20867 -- For an assignment, use name of target
20869 elsif Nkind (Parent (Expr)) = N_Assignment_Statement
20870 and then Is_Entity_Name (Name (Parent (Expr)))
20871 then
20872 Matching_Field := Entity (Name (Parent (Expr)));
20873 end if;
20875 return True;
20877 elsif not Is_Record_Type (Expec_Type) then
20878 return False;
20880 else
20881 E := First_Entity (Expec_Type);
20882 loop
20883 if No (E) then
20884 return False;
20886 elsif not Ekind_In (E, E_Discriminant, E_Component)
20887 or else Nam_In (Chars (E), Name_uTag, Name_uParent)
20888 then
20889 Next_Entity (E);
20891 else
20892 exit;
20893 end if;
20894 end loop;
20896 if not Covers (Etype (E), Found_Type) then
20897 return False;
20899 elsif Present (Next_Entity (E))
20900 and then (Ekind (E) = E_Component
20901 or else Ekind (Next_Entity (E)) = E_Discriminant)
20902 then
20903 return False;
20905 else
20906 Matching_Field := E;
20907 return True;
20908 end if;
20909 end if;
20910 end Has_One_Matching_Field;
20912 -- Start of processing for Wrong_Type
20914 begin
20915 -- Don't output message if either type is Any_Type, or if a message
20916 -- has already been posted for this node. We need to do the latter
20917 -- check explicitly (it is ordinarily done in Errout), because we
20918 -- are using ! to force the output of the error messages.
20920 if Expec_Type = Any_Type
20921 or else Found_Type = Any_Type
20922 or else Error_Posted (Expr)
20923 then
20924 return;
20926 -- If one of the types is a Taft-Amendment type and the other it its
20927 -- completion, it must be an illegal use of a TAT in the spec, for
20928 -- which an error was already emitted. Avoid cascaded errors.
20930 elsif Is_Incomplete_Type (Expec_Type)
20931 and then Has_Completion_In_Body (Expec_Type)
20932 and then Full_View (Expec_Type) = Etype (Expr)
20933 then
20934 return;
20936 elsif Is_Incomplete_Type (Etype (Expr))
20937 and then Has_Completion_In_Body (Etype (Expr))
20938 and then Full_View (Etype (Expr)) = Expec_Type
20939 then
20940 return;
20942 -- In an instance, there is an ongoing problem with completion of
20943 -- type derived from private types. Their structure is what Gigi
20944 -- expects, but the Etype is the parent type rather than the
20945 -- derived private type itself. Do not flag error in this case. The
20946 -- private completion is an entity without a parent, like an Itype.
20947 -- Similarly, full and partial views may be incorrect in the instance.
20948 -- There is no simple way to insure that it is consistent ???
20950 -- A similar view discrepancy can happen in an inlined body, for the
20951 -- same reason: inserted body may be outside of the original package
20952 -- and only partial views are visible at the point of insertion.
20954 elsif In_Instance or else In_Inlined_Body then
20955 if Etype (Etype (Expr)) = Etype (Expected_Type)
20956 and then
20957 (Has_Private_Declaration (Expected_Type)
20958 or else Has_Private_Declaration (Etype (Expr)))
20959 and then No (Parent (Expected_Type))
20960 then
20961 return;
20963 elsif Nkind (Parent (Expr)) = N_Qualified_Expression
20964 and then Entity (Subtype_Mark (Parent (Expr))) = Expected_Type
20965 then
20966 return;
20968 elsif Is_Private_Type (Expected_Type)
20969 and then Present (Full_View (Expected_Type))
20970 and then Covers (Full_View (Expected_Type), Etype (Expr))
20971 then
20972 return;
20974 -- Conversely, type of expression may be the private one
20976 elsif Is_Private_Type (Base_Type (Etype (Expr)))
20977 and then Full_View (Base_Type (Etype (Expr))) = Expected_Type
20978 then
20979 return;
20980 end if;
20981 end if;
20983 -- An interesting special check. If the expression is parenthesized
20984 -- and its type corresponds to the type of the sole component of the
20985 -- expected record type, or to the component type of the expected one
20986 -- dimensional array type, then assume we have a bad aggregate attempt.
20988 if Nkind (Expr) in N_Subexpr
20989 and then Paren_Count (Expr) /= 0
20990 and then Has_One_Matching_Field
20991 then
20992 Error_Msg_N ("positional aggregate cannot have one component", Expr);
20994 if Present (Matching_Field) then
20995 if Is_Array_Type (Expec_Type) then
20996 Error_Msg_NE
20997 ("\write instead `&''First ='> ...`", Expr, Matching_Field);
20998 else
20999 Error_Msg_NE
21000 ("\write instead `& ='> ...`", Expr, Matching_Field);
21001 end if;
21002 end if;
21004 -- Another special check, if we are looking for a pool-specific access
21005 -- type and we found an E_Access_Attribute_Type, then we have the case
21006 -- of an Access attribute being used in a context which needs a pool-
21007 -- specific type, which is never allowed. The one extra check we make
21008 -- is that the expected designated type covers the Found_Type.
21010 elsif Is_Access_Type (Expec_Type)
21011 and then Ekind (Found_Type) = E_Access_Attribute_Type
21012 and then Ekind (Base_Type (Expec_Type)) /= E_General_Access_Type
21013 and then Ekind (Base_Type (Expec_Type)) /= E_Anonymous_Access_Type
21014 and then Covers
21015 (Designated_Type (Expec_Type), Designated_Type (Found_Type))
21016 then
21017 Error_Msg_N -- CODEFIX
21018 ("result must be general access type!", Expr);
21019 Error_Msg_NE -- CODEFIX
21020 ("add ALL to }!", Expr, Expec_Type);
21022 -- Another special check, if the expected type is an integer type,
21023 -- but the expression is of type System.Address, and the parent is
21024 -- an addition or subtraction operation whose left operand is the
21025 -- expression in question and whose right operand is of an integral
21026 -- type, then this is an attempt at address arithmetic, so give
21027 -- appropriate message.
21029 elsif Is_Integer_Type (Expec_Type)
21030 and then Is_RTE (Found_Type, RE_Address)
21031 and then Nkind_In (Parent (Expr), N_Op_Add, N_Op_Subtract)
21032 and then Expr = Left_Opnd (Parent (Expr))
21033 and then Is_Integer_Type (Etype (Right_Opnd (Parent (Expr))))
21034 then
21035 Error_Msg_N
21036 ("address arithmetic not predefined in package System",
21037 Parent (Expr));
21038 Error_Msg_N
21039 ("\possible missing with/use of System.Storage_Elements",
21040 Parent (Expr));
21041 return;
21043 -- If the expected type is an anonymous access type, as for access
21044 -- parameters and discriminants, the error is on the designated types.
21046 elsif Ekind (Expec_Type) = E_Anonymous_Access_Type then
21047 if Comes_From_Source (Expec_Type) then
21048 Error_Msg_NE ("expected}!", Expr, Expec_Type);
21049 else
21050 Error_Msg_NE
21051 ("expected an access type with designated}",
21052 Expr, Designated_Type (Expec_Type));
21053 end if;
21055 if Is_Access_Type (Found_Type)
21056 and then not Comes_From_Source (Found_Type)
21057 then
21058 Error_Msg_NE
21059 ("\\found an access type with designated}!",
21060 Expr, Designated_Type (Found_Type));
21061 else
21062 if From_Limited_With (Found_Type) then
21063 Error_Msg_NE ("\\found incomplete}!", Expr, Found_Type);
21064 Error_Msg_Qual_Level := 99;
21065 Error_Msg_NE -- CODEFIX
21066 ("\\missing `WITH &;", Expr, Scope (Found_Type));
21067 Error_Msg_Qual_Level := 0;
21068 else
21069 Error_Msg_NE ("found}!", Expr, Found_Type);
21070 end if;
21071 end if;
21073 -- Normal case of one type found, some other type expected
21075 else
21076 -- If the names of the two types are the same, see if some number
21077 -- of levels of qualification will help. Don't try more than three
21078 -- levels, and if we get to standard, it's no use (and probably
21079 -- represents an error in the compiler) Also do not bother with
21080 -- internal scope names.
21082 declare
21083 Expec_Scope : Entity_Id;
21084 Found_Scope : Entity_Id;
21086 begin
21087 Expec_Scope := Expec_Type;
21088 Found_Scope := Found_Type;
21090 for Levels in Nat range 0 .. 3 loop
21091 if Chars (Expec_Scope) /= Chars (Found_Scope) then
21092 Error_Msg_Qual_Level := Levels;
21093 exit;
21094 end if;
21096 Expec_Scope := Scope (Expec_Scope);
21097 Found_Scope := Scope (Found_Scope);
21099 exit when Expec_Scope = Standard_Standard
21100 or else Found_Scope = Standard_Standard
21101 or else not Comes_From_Source (Expec_Scope)
21102 or else not Comes_From_Source (Found_Scope);
21103 end loop;
21104 end;
21106 if Is_Record_Type (Expec_Type)
21107 and then Present (Corresponding_Remote_Type (Expec_Type))
21108 then
21109 Error_Msg_NE ("expected}!", Expr,
21110 Corresponding_Remote_Type (Expec_Type));
21111 else
21112 Error_Msg_NE ("expected}!", Expr, Expec_Type);
21113 end if;
21115 if Is_Entity_Name (Expr)
21116 and then Is_Package_Or_Generic_Package (Entity (Expr))
21117 then
21118 Error_Msg_N ("\\found package name!", Expr);
21120 elsif Is_Entity_Name (Expr)
21121 and then Ekind_In (Entity (Expr), E_Procedure, E_Generic_Procedure)
21122 then
21123 if Ekind (Expec_Type) = E_Access_Subprogram_Type then
21124 Error_Msg_N
21125 ("found procedure name, possibly missing Access attribute!",
21126 Expr);
21127 else
21128 Error_Msg_N
21129 ("\\found procedure name instead of function!", Expr);
21130 end if;
21132 elsif Nkind (Expr) = N_Function_Call
21133 and then Ekind (Expec_Type) = E_Access_Subprogram_Type
21134 and then Etype (Designated_Type (Expec_Type)) = Etype (Expr)
21135 and then No (Parameter_Associations (Expr))
21136 then
21137 Error_Msg_N
21138 ("found function name, possibly missing Access attribute!",
21139 Expr);
21141 -- Catch common error: a prefix or infix operator which is not
21142 -- directly visible because the type isn't.
21144 elsif Nkind (Expr) in N_Op
21145 and then Is_Overloaded (Expr)
21146 and then not Is_Immediately_Visible (Expec_Type)
21147 and then not Is_Potentially_Use_Visible (Expec_Type)
21148 and then not In_Use (Expec_Type)
21149 and then Has_Compatible_Type (Right_Opnd (Expr), Expec_Type)
21150 then
21151 Error_Msg_N
21152 ("operator of the type is not directly visible!", Expr);
21154 elsif Ekind (Found_Type) = E_Void
21155 and then Present (Parent (Found_Type))
21156 and then Nkind (Parent (Found_Type)) = N_Full_Type_Declaration
21157 then
21158 Error_Msg_NE ("\\found premature usage of}!", Expr, Found_Type);
21160 else
21161 Error_Msg_NE ("\\found}!", Expr, Found_Type);
21162 end if;
21164 -- A special check for cases like M1 and M2 = 0 where M1 and M2 are
21165 -- of the same modular type, and (M1 and M2) = 0 was intended.
21167 if Expec_Type = Standard_Boolean
21168 and then Is_Modular_Integer_Type (Found_Type)
21169 and then Nkind_In (Parent (Expr), N_Op_And, N_Op_Or, N_Op_Xor)
21170 and then Nkind (Right_Opnd (Parent (Expr))) in N_Op_Compare
21171 then
21172 declare
21173 Op : constant Node_Id := Right_Opnd (Parent (Expr));
21174 L : constant Node_Id := Left_Opnd (Op);
21175 R : constant Node_Id := Right_Opnd (Op);
21177 begin
21178 -- The case for the message is when the left operand of the
21179 -- comparison is the same modular type, or when it is an
21180 -- integer literal (or other universal integer expression),
21181 -- which would have been typed as the modular type if the
21182 -- parens had been there.
21184 if (Etype (L) = Found_Type
21185 or else
21186 Etype (L) = Universal_Integer)
21187 and then Is_Integer_Type (Etype (R))
21188 then
21189 Error_Msg_N
21190 ("\\possible missing parens for modular operation", Expr);
21191 end if;
21192 end;
21193 end if;
21195 -- Reset error message qualification indication
21197 Error_Msg_Qual_Level := 0;
21198 end if;
21199 end Wrong_Type;
21201 --------------------------------
21202 -- Yields_Synchronized_Object --
21203 --------------------------------
21205 function Yields_Synchronized_Object (Typ : Entity_Id) return Boolean is
21206 Has_Sync_Comp : Boolean := False;
21207 Id : Entity_Id;
21209 begin
21210 -- An array type yields a synchronized object if its component type
21211 -- yields a synchronized object.
21213 if Is_Array_Type (Typ) then
21214 return Yields_Synchronized_Object (Component_Type (Typ));
21216 -- A descendant of type Ada.Synchronous_Task_Control.Suspension_Object
21217 -- yields a synchronized object by default.
21219 elsif Is_Descendant_Of_Suspension_Object (Typ) then
21220 return True;
21222 -- A protected type yields a synchronized object by default
21224 elsif Is_Protected_Type (Typ) then
21225 return True;
21227 -- A record type or type extension yields a synchronized object when its
21228 -- discriminants (if any) lack default values and all components are of
21229 -- a type that yelds a synchronized object.
21231 elsif Is_Record_Type (Typ) then
21233 -- Inspect all entities defined in the scope of the type, looking for
21234 -- components of a type that does not yeld a synchronized object or
21235 -- for discriminants with default values.
21237 Id := First_Entity (Typ);
21238 while Present (Id) loop
21239 if Comes_From_Source (Id) then
21240 if Ekind (Id) = E_Component then
21241 if Yields_Synchronized_Object (Etype (Id)) then
21242 Has_Sync_Comp := True;
21244 -- The component does not yield a synchronized object
21246 else
21247 return False;
21248 end if;
21250 elsif Ekind (Id) = E_Discriminant
21251 and then Present (Expression (Parent (Id)))
21252 then
21253 return False;
21254 end if;
21255 end if;
21257 Next_Entity (Id);
21258 end loop;
21260 -- Ensure that the parent type of a type extension yields a
21261 -- synchronized object.
21263 if Etype (Typ) /= Typ
21264 and then not Yields_Synchronized_Object (Etype (Typ))
21265 then
21266 return False;
21267 end if;
21269 -- If we get here, then all discriminants lack default values and all
21270 -- components are of a type that yields a synchronized object.
21272 return Has_Sync_Comp;
21274 -- A synchronized interface type yields a synchronized object by default
21276 elsif Is_Synchronized_Interface (Typ) then
21277 return True;
21279 -- A task type yelds a synchronized object by default
21281 elsif Is_Task_Type (Typ) then
21282 return True;
21284 -- Otherwise the type does not yield a synchronized object
21286 else
21287 return False;
21288 end if;
21289 end Yields_Synchronized_Object;
21291 ---------------------------
21292 -- Yields_Universal_Type --
21293 ---------------------------
21295 function Yields_Universal_Type (N : Node_Id) return Boolean is
21296 begin
21297 -- Integer and real literals are of a universal type
21299 if Nkind_In (N, N_Integer_Literal, N_Real_Literal) then
21300 return True;
21302 -- The values of certain attributes are of a universal type
21304 elsif Nkind (N) = N_Attribute_Reference then
21305 return
21306 Universal_Type_Attribute (Get_Attribute_Id (Attribute_Name (N)));
21308 -- ??? There are possibly other cases to consider
21310 else
21311 return False;
21312 end if;
21313 end Yields_Universal_Type;
21315 end Sem_Util;