2016-04-27 Arnaud Charlet <charlet@adacore.com>
[official-gcc.git] / gcc / ada / exp_util.adb
blobb4efc938060285575386691eda7e06645945d927
1 ------------------------------------------------------------------------------
2 -- --
3 -- GNAT COMPILER COMPONENTS --
4 -- --
5 -- E X P _ 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 Aspects; use Aspects;
27 with Atree; use Atree;
28 with Casing; use Casing;
29 with Checks; use Checks;
30 with Debug; use Debug;
31 with Einfo; use Einfo;
32 with Elists; use Elists;
33 with Errout; use Errout;
34 with Exp_Aggr; use Exp_Aggr;
35 with Exp_Ch6; use Exp_Ch6;
36 with Exp_Ch7; use Exp_Ch7;
37 with Ghost; use Ghost;
38 with Inline; use Inline;
39 with Itypes; use Itypes;
40 with Lib; use Lib;
41 with Nlists; use Nlists;
42 with Nmake; use Nmake;
43 with Opt; use Opt;
44 with Restrict; use Restrict;
45 with Rident; use Rident;
46 with Sem; use Sem;
47 with Sem_Aux; use Sem_Aux;
48 with Sem_Ch8; use Sem_Ch8;
49 with Sem_Ch13; use Sem_Ch13;
50 with Sem_Eval; use Sem_Eval;
51 with Sem_Res; use Sem_Res;
52 with Sem_Type; use Sem_Type;
53 with Sem_Util; use Sem_Util;
54 with Snames; use Snames;
55 with Stand; use Stand;
56 with Stringt; use Stringt;
57 with Targparm; use Targparm;
58 with Tbuild; use Tbuild;
59 with Ttypes; use Ttypes;
60 with Urealp; use Urealp;
61 with Validsw; use Validsw;
63 package body Exp_Util is
65 -----------------------
66 -- Local Subprograms --
67 -----------------------
69 function Build_Task_Array_Image
70 (Loc : Source_Ptr;
71 Id_Ref : Node_Id;
72 A_Type : Entity_Id;
73 Dyn : Boolean := False) return Node_Id;
74 -- Build function to generate the image string for a task that is an array
75 -- component, concatenating the images of each index. To avoid storage
76 -- leaks, the string is built with successive slice assignments. The flag
77 -- Dyn indicates whether this is called for the initialization procedure of
78 -- an array of tasks, or for the name of a dynamically created task that is
79 -- assigned to an indexed component.
81 function Build_Task_Image_Function
82 (Loc : Source_Ptr;
83 Decls : List_Id;
84 Stats : List_Id;
85 Res : Entity_Id) return Node_Id;
86 -- Common processing for Task_Array_Image and Task_Record_Image. Build
87 -- function body that computes image.
89 procedure Build_Task_Image_Prefix
90 (Loc : Source_Ptr;
91 Len : out Entity_Id;
92 Res : out Entity_Id;
93 Pos : out Entity_Id;
94 Prefix : Entity_Id;
95 Sum : Node_Id;
96 Decls : List_Id;
97 Stats : List_Id);
98 -- Common processing for Task_Array_Image and Task_Record_Image. Create
99 -- local variables and assign prefix of name to result string.
101 function Build_Task_Record_Image
102 (Loc : Source_Ptr;
103 Id_Ref : Node_Id;
104 Dyn : Boolean := False) return Node_Id;
105 -- Build function to generate the image string for a task that is a record
106 -- component. Concatenate name of variable with that of selector. The flag
107 -- Dyn indicates whether this is called for the initialization procedure of
108 -- record with task components, or for a dynamically created task that is
109 -- assigned to a selected component.
111 procedure Evaluate_Slice_Bounds (Slice : Node_Id);
112 -- Force evaluation of bounds of a slice, which may be given by a range
113 -- or by a subtype indication with or without a constraint.
115 function Make_CW_Equivalent_Type
116 (T : Entity_Id;
117 E : Node_Id) return Entity_Id;
118 -- T is a class-wide type entity, E is the initial expression node that
119 -- constrains T in case such as: " X: T := E" or "new T'(E)". This function
120 -- returns the entity of the Equivalent type and inserts on the fly the
121 -- necessary declaration such as:
123 -- type anon is record
124 -- _parent : Root_Type (T); constrained with E discriminants (if any)
125 -- Extension : String (1 .. expr to match size of E);
126 -- end record;
128 -- This record is compatible with any object of the class of T thanks to
129 -- the first field and has the same size as E thanks to the second.
131 function Make_Literal_Range
132 (Loc : Source_Ptr;
133 Literal_Typ : Entity_Id) return Node_Id;
134 -- Produce a Range node whose bounds are:
135 -- Low_Bound (Literal_Type) ..
136 -- Low_Bound (Literal_Type) + (Length (Literal_Typ) - 1)
137 -- this is used for expanding declarations like X : String := "sdfgdfg";
139 -- If the index type of the target array is not integer, we generate:
140 -- Low_Bound (Literal_Type) ..
141 -- Literal_Type'Val
142 -- (Literal_Type'Pos (Low_Bound (Literal_Type))
143 -- + (Length (Literal_Typ) -1))
145 function Make_Non_Empty_Check
146 (Loc : Source_Ptr;
147 N : Node_Id) return Node_Id;
148 -- Produce a boolean expression checking that the unidimensional array
149 -- node N is not empty.
151 function New_Class_Wide_Subtype
152 (CW_Typ : Entity_Id;
153 N : Node_Id) return Entity_Id;
154 -- Create an implicit subtype of CW_Typ attached to node N
156 function Requires_Cleanup_Actions
157 (L : List_Id;
158 Lib_Level : Boolean;
159 Nested_Constructs : Boolean) return Boolean;
160 -- Given a list L, determine whether it contains one of the following:
162 -- 1) controlled objects
163 -- 2) library-level tagged types
165 -- Lib_Level is True when the list comes from a construct at the library
166 -- level, and False otherwise. Nested_Constructs is True when any nested
167 -- packages declared in L must be processed, and False otherwise.
169 -------------------------------------
170 -- Activate_Atomic_Synchronization --
171 -------------------------------------
173 procedure Activate_Atomic_Synchronization (N : Node_Id) is
174 Msg_Node : Node_Id;
176 begin
177 case Nkind (Parent (N)) is
179 -- Check for cases of appearing in the prefix of a construct where
180 -- we don't need atomic synchronization for this kind of usage.
182 when
183 -- Nothing to do if we are the prefix of an attribute, since we
184 -- do not want an atomic sync operation for things like 'Size.
186 N_Attribute_Reference |
188 -- The N_Reference node is like an attribute
190 N_Reference |
192 -- Nothing to do for a reference to a component (or components)
193 -- of a composite object. Only reads and updates of the object
194 -- as a whole require atomic synchronization (RM C.6 (15)).
196 N_Indexed_Component |
197 N_Selected_Component |
198 N_Slice =>
200 -- For all the above cases, nothing to do if we are the prefix
202 if Prefix (Parent (N)) = N then
203 return;
204 end if;
206 when others => null;
207 end case;
209 -- Nothing to do for the identifier in an object renaming declaration,
210 -- the renaming itself does not need atomic synchronization.
212 if Nkind (Parent (N)) = N_Object_Renaming_Declaration then
213 return;
214 end if;
216 -- Go ahead and set the flag
218 Set_Atomic_Sync_Required (N);
220 -- Generate info message if requested
222 if Warn_On_Atomic_Synchronization then
223 case Nkind (N) is
224 when N_Identifier =>
225 Msg_Node := N;
227 when N_Selected_Component | N_Expanded_Name =>
228 Msg_Node := Selector_Name (N);
230 when N_Explicit_Dereference | N_Indexed_Component =>
231 Msg_Node := Empty;
233 when others =>
234 pragma Assert (False);
235 return;
236 end case;
238 if Present (Msg_Node) then
239 Error_Msg_N
240 ("info: atomic synchronization set for &?N?", Msg_Node);
241 else
242 Error_Msg_N
243 ("info: atomic synchronization set?N?", N);
244 end if;
245 end if;
246 end Activate_Atomic_Synchronization;
248 ----------------------
249 -- Adjust_Condition --
250 ----------------------
252 procedure Adjust_Condition (N : Node_Id) is
253 begin
254 if No (N) then
255 return;
256 end if;
258 declare
259 Loc : constant Source_Ptr := Sloc (N);
260 T : constant Entity_Id := Etype (N);
261 Ti : Entity_Id;
263 begin
264 -- Defend against a call where the argument has no type, or has a
265 -- type that is not Boolean. This can occur because of prior errors.
267 if No (T) or else not Is_Boolean_Type (T) then
268 return;
269 end if;
271 -- Apply validity checking if needed
273 if Validity_Checks_On and Validity_Check_Tests then
274 Ensure_Valid (N);
275 end if;
277 -- Immediate return if standard boolean, the most common case,
278 -- where nothing needs to be done.
280 if Base_Type (T) = Standard_Boolean then
281 return;
282 end if;
284 -- Case of zero/non-zero semantics or non-standard enumeration
285 -- representation. In each case, we rewrite the node as:
287 -- ityp!(N) /= False'Enum_Rep
289 -- where ityp is an integer type with large enough size to hold any
290 -- value of type T.
292 if Nonzero_Is_True (T) or else Has_Non_Standard_Rep (T) then
293 if Esize (T) <= Esize (Standard_Integer) then
294 Ti := Standard_Integer;
295 else
296 Ti := Standard_Long_Long_Integer;
297 end if;
299 Rewrite (N,
300 Make_Op_Ne (Loc,
301 Left_Opnd => Unchecked_Convert_To (Ti, N),
302 Right_Opnd =>
303 Make_Attribute_Reference (Loc,
304 Attribute_Name => Name_Enum_Rep,
305 Prefix =>
306 New_Occurrence_Of (First_Literal (T), Loc))));
307 Analyze_And_Resolve (N, Standard_Boolean);
309 else
310 Rewrite (N, Convert_To (Standard_Boolean, N));
311 Analyze_And_Resolve (N, Standard_Boolean);
312 end if;
313 end;
314 end Adjust_Condition;
316 ------------------------
317 -- Adjust_Result_Type --
318 ------------------------
320 procedure Adjust_Result_Type (N : Node_Id; T : Entity_Id) is
321 begin
322 -- Ignore call if current type is not Standard.Boolean
324 if Etype (N) /= Standard_Boolean then
325 return;
326 end if;
328 -- If result is already of correct type, nothing to do. Note that
329 -- this will get the most common case where everything has a type
330 -- of Standard.Boolean.
332 if Base_Type (T) = Standard_Boolean then
333 return;
335 else
336 declare
337 KP : constant Node_Kind := Nkind (Parent (N));
339 begin
340 -- If result is to be used as a Condition in the syntax, no need
341 -- to convert it back, since if it was changed to Standard.Boolean
342 -- using Adjust_Condition, that is just fine for this usage.
344 if KP in N_Raise_xxx_Error or else KP in N_Has_Condition then
345 return;
347 -- If result is an operand of another logical operation, no need
348 -- to reset its type, since Standard.Boolean is just fine, and
349 -- such operations always do Adjust_Condition on their operands.
351 elsif KP in N_Op_Boolean
352 or else KP in N_Short_Circuit
353 or else KP = N_Op_Not
354 then
355 return;
357 -- Otherwise we perform a conversion from the current type, which
358 -- must be Standard.Boolean, to the desired type.
360 else
361 Set_Analyzed (N);
362 Rewrite (N, Convert_To (T, N));
363 Analyze_And_Resolve (N, T);
364 end if;
365 end;
366 end if;
367 end Adjust_Result_Type;
369 --------------------------
370 -- Append_Freeze_Action --
371 --------------------------
373 procedure Append_Freeze_Action (T : Entity_Id; N : Node_Id) is
374 Fnode : Node_Id;
376 begin
377 Ensure_Freeze_Node (T);
378 Fnode := Freeze_Node (T);
380 if No (Actions (Fnode)) then
381 Set_Actions (Fnode, New_List (N));
382 else
383 Append (N, Actions (Fnode));
384 end if;
386 end Append_Freeze_Action;
388 ---------------------------
389 -- Append_Freeze_Actions --
390 ---------------------------
392 procedure Append_Freeze_Actions (T : Entity_Id; L : List_Id) is
393 Fnode : Node_Id;
395 begin
396 if No (L) then
397 return;
398 end if;
400 Ensure_Freeze_Node (T);
401 Fnode := Freeze_Node (T);
403 if No (Actions (Fnode)) then
404 Set_Actions (Fnode, L);
405 else
406 Append_List (L, Actions (Fnode));
407 end if;
408 end Append_Freeze_Actions;
410 ------------------------------------
411 -- Build_Allocate_Deallocate_Proc --
412 ------------------------------------
414 procedure Build_Allocate_Deallocate_Proc
415 (N : Node_Id;
416 Is_Allocate : Boolean)
418 Desig_Typ : Entity_Id;
419 Expr : Node_Id;
420 Pool_Id : Entity_Id;
421 Proc_To_Call : Node_Id := Empty;
422 Ptr_Typ : Entity_Id;
424 function Find_Object (E : Node_Id) return Node_Id;
425 -- Given an arbitrary expression of an allocator, try to find an object
426 -- reference in it, otherwise return the original expression.
428 function Is_Allocate_Deallocate_Proc (Subp : Entity_Id) return Boolean;
429 -- Determine whether subprogram Subp denotes a custom allocate or
430 -- deallocate.
432 -----------------
433 -- Find_Object --
434 -----------------
436 function Find_Object (E : Node_Id) return Node_Id is
437 Expr : Node_Id;
439 begin
440 pragma Assert (Is_Allocate);
442 Expr := E;
443 loop
444 if Nkind (Expr) = N_Explicit_Dereference then
445 Expr := Prefix (Expr);
447 elsif Nkind (Expr) = N_Qualified_Expression then
448 Expr := Expression (Expr);
450 elsif Nkind (Expr) = N_Unchecked_Type_Conversion then
452 -- When interface class-wide types are involved in allocation,
453 -- the expander introduces several levels of address arithmetic
454 -- to perform dispatch table displacement. In this scenario the
455 -- object appears as:
457 -- Tag_Ptr (Base_Address (<object>'Address))
459 -- Detect this case and utilize the whole expression as the
460 -- "object" since it now points to the proper dispatch table.
462 if Is_RTE (Etype (Expr), RE_Tag_Ptr) then
463 exit;
465 -- Continue to strip the object
467 else
468 Expr := Expression (Expr);
469 end if;
471 else
472 exit;
473 end if;
474 end loop;
476 return Expr;
477 end Find_Object;
479 ---------------------------------
480 -- Is_Allocate_Deallocate_Proc --
481 ---------------------------------
483 function Is_Allocate_Deallocate_Proc (Subp : Entity_Id) return Boolean is
484 begin
485 -- Look for a subprogram body with only one statement which is a
486 -- call to Allocate_Any_Controlled / Deallocate_Any_Controlled.
488 if Ekind (Subp) = E_Procedure
489 and then Nkind (Parent (Parent (Subp))) = N_Subprogram_Body
490 then
491 declare
492 HSS : constant Node_Id :=
493 Handled_Statement_Sequence (Parent (Parent (Subp)));
494 Proc : Entity_Id;
496 begin
497 if Present (Statements (HSS))
498 and then Nkind (First (Statements (HSS))) =
499 N_Procedure_Call_Statement
500 then
501 Proc := Entity (Name (First (Statements (HSS))));
503 return
504 Is_RTE (Proc, RE_Allocate_Any_Controlled)
505 or else Is_RTE (Proc, RE_Deallocate_Any_Controlled);
506 end if;
507 end;
508 end if;
510 return False;
511 end Is_Allocate_Deallocate_Proc;
513 -- Start of processing for Build_Allocate_Deallocate_Proc
515 begin
516 -- Obtain the attributes of the allocation / deallocation
518 if Nkind (N) = N_Free_Statement then
519 Expr := Expression (N);
520 Ptr_Typ := Base_Type (Etype (Expr));
521 Proc_To_Call := Procedure_To_Call (N);
523 else
524 if Nkind (N) = N_Object_Declaration then
525 Expr := Expression (N);
526 else
527 Expr := N;
528 end if;
530 -- In certain cases an allocator with a qualified expression may
531 -- be relocated and used as the initialization expression of a
532 -- temporary:
534 -- before:
535 -- Obj : Ptr_Typ := new Desig_Typ'(...);
537 -- after:
538 -- Tmp : Ptr_Typ := new Desig_Typ'(...);
539 -- Obj : Ptr_Typ := Tmp;
541 -- Since the allocator is always marked as analyzed to avoid infinite
542 -- expansion, it will never be processed by this routine given that
543 -- the designated type needs finalization actions. Detect this case
544 -- and complete the expansion of the allocator.
546 if Nkind (Expr) = N_Identifier
547 and then Nkind (Parent (Entity (Expr))) = N_Object_Declaration
548 and then Nkind (Expression (Parent (Entity (Expr)))) = N_Allocator
549 then
550 Build_Allocate_Deallocate_Proc (Parent (Entity (Expr)), True);
551 return;
552 end if;
554 -- The allocator may have been rewritten into something else in which
555 -- case the expansion performed by this routine does not apply.
557 if Nkind (Expr) /= N_Allocator then
558 return;
559 end if;
561 Ptr_Typ := Base_Type (Etype (Expr));
562 Proc_To_Call := Procedure_To_Call (Expr);
563 end if;
565 Pool_Id := Associated_Storage_Pool (Ptr_Typ);
566 Desig_Typ := Available_View (Designated_Type (Ptr_Typ));
568 -- Handle concurrent types
570 if Is_Concurrent_Type (Desig_Typ)
571 and then Present (Corresponding_Record_Type (Desig_Typ))
572 then
573 Desig_Typ := Corresponding_Record_Type (Desig_Typ);
574 end if;
576 -- Do not process allocations / deallocations without a pool
578 if No (Pool_Id) then
579 return;
581 -- Do not process allocations on / deallocations from the secondary
582 -- stack.
584 elsif Is_RTE (Pool_Id, RE_SS_Pool) then
585 return;
587 -- Do not replicate the machinery if the allocator / free has already
588 -- been expanded and has a custom Allocate / Deallocate.
590 elsif Present (Proc_To_Call)
591 and then Is_Allocate_Deallocate_Proc (Proc_To_Call)
592 then
593 return;
594 end if;
596 if Needs_Finalization (Desig_Typ) then
598 -- Certain run-time configurations and targets do not provide support
599 -- for controlled types.
601 if Restriction_Active (No_Finalization) then
602 return;
604 -- Do nothing if the access type may never allocate / deallocate
605 -- objects.
607 elsif No_Pool_Assigned (Ptr_Typ) then
608 return;
609 end if;
611 -- The allocation / deallocation of a controlled object must be
612 -- chained on / detached from a finalization master.
614 pragma Assert (Present (Finalization_Master (Ptr_Typ)));
616 -- The only other kind of allocation / deallocation supported by this
617 -- routine is on / from a subpool.
619 elsif Nkind (Expr) = N_Allocator
620 and then No (Subpool_Handle_Name (Expr))
621 then
622 return;
623 end if;
625 declare
626 Loc : constant Source_Ptr := Sloc (N);
627 Addr_Id : constant Entity_Id := Make_Temporary (Loc, 'A');
628 Alig_Id : constant Entity_Id := Make_Temporary (Loc, 'L');
629 Proc_Id : constant Entity_Id := Make_Temporary (Loc, 'P');
630 Size_Id : constant Entity_Id := Make_Temporary (Loc, 'S');
632 Actuals : List_Id;
633 Fin_Addr_Id : Entity_Id;
634 Fin_Mas_Act : Node_Id;
635 Fin_Mas_Id : Entity_Id;
636 Proc_To_Call : Entity_Id;
637 Subpool : Node_Id := Empty;
639 begin
640 -- Step 1: Construct all the actuals for the call to library routine
641 -- Allocate_Any_Controlled / Deallocate_Any_Controlled.
643 -- a) Storage pool
645 Actuals := New_List (New_Occurrence_Of (Pool_Id, Loc));
647 if Is_Allocate then
649 -- b) Subpool
651 if Nkind (Expr) = N_Allocator then
652 Subpool := Subpool_Handle_Name (Expr);
653 end if;
655 -- If a subpool is present it can be an arbitrary name, so make
656 -- the actual by copying the tree.
658 if Present (Subpool) then
659 Append_To (Actuals, New_Copy_Tree (Subpool, New_Sloc => Loc));
660 else
661 Append_To (Actuals, Make_Null (Loc));
662 end if;
664 -- c) Finalization master
666 if Needs_Finalization (Desig_Typ) then
667 Fin_Mas_Id := Finalization_Master (Ptr_Typ);
668 Fin_Mas_Act := New_Occurrence_Of (Fin_Mas_Id, Loc);
670 -- Handle the case where the master is actually a pointer to a
671 -- master. This case arises in build-in-place functions.
673 if Is_Access_Type (Etype (Fin_Mas_Id)) then
674 Append_To (Actuals, Fin_Mas_Act);
675 else
676 Append_To (Actuals,
677 Make_Attribute_Reference (Loc,
678 Prefix => Fin_Mas_Act,
679 Attribute_Name => Name_Unrestricted_Access));
680 end if;
681 else
682 Append_To (Actuals, Make_Null (Loc));
683 end if;
685 -- d) Finalize_Address
687 -- Primitive Finalize_Address is never generated in CodePeer mode
688 -- since it contains an Unchecked_Conversion.
690 if Needs_Finalization (Desig_Typ) and then not CodePeer_Mode then
691 Fin_Addr_Id := Finalize_Address (Desig_Typ);
692 pragma Assert (Present (Fin_Addr_Id));
694 Append_To (Actuals,
695 Make_Attribute_Reference (Loc,
696 Prefix => New_Occurrence_Of (Fin_Addr_Id, Loc),
697 Attribute_Name => Name_Unrestricted_Access));
698 else
699 Append_To (Actuals, Make_Null (Loc));
700 end if;
701 end if;
703 -- e) Address
704 -- f) Storage_Size
705 -- g) Alignment
707 Append_To (Actuals, New_Occurrence_Of (Addr_Id, Loc));
708 Append_To (Actuals, New_Occurrence_Of (Size_Id, Loc));
710 if Is_Allocate or else not Is_Class_Wide_Type (Desig_Typ) then
711 Append_To (Actuals, New_Occurrence_Of (Alig_Id, Loc));
713 -- For deallocation of class-wide types we obtain the value of
714 -- alignment from the Type Specific Record of the deallocated object.
715 -- This is needed because the frontend expansion of class-wide types
716 -- into equivalent types confuses the backend.
718 else
719 -- Generate:
720 -- Obj.all'Alignment
722 -- ... because 'Alignment applied to class-wide types is expanded
723 -- into the code that reads the value of alignment from the TSD
724 -- (see Expand_N_Attribute_Reference)
726 Append_To (Actuals,
727 Unchecked_Convert_To (RTE (RE_Storage_Offset),
728 Make_Attribute_Reference (Loc,
729 Prefix =>
730 Make_Explicit_Dereference (Loc, Relocate_Node (Expr)),
731 Attribute_Name => Name_Alignment)));
732 end if;
734 -- h) Is_Controlled
736 if Needs_Finalization (Desig_Typ) then
737 declare
738 Flag_Id : constant Entity_Id := Make_Temporary (Loc, 'F');
739 Flag_Expr : Node_Id;
740 Param : Node_Id;
741 Temp : Node_Id;
743 begin
744 if Is_Allocate then
745 Temp := Find_Object (Expression (Expr));
746 else
747 Temp := Expr;
748 end if;
750 -- Processing for allocations where the expression is a subtype
751 -- indication.
753 if Is_Allocate
754 and then Is_Entity_Name (Temp)
755 and then Is_Type (Entity (Temp))
756 then
757 Flag_Expr :=
758 New_Occurrence_Of
759 (Boolean_Literals
760 (Needs_Finalization (Entity (Temp))), Loc);
762 -- The allocation / deallocation of a class-wide object relies
763 -- on a runtime check to determine whether the object is truly
764 -- controlled or not. Depending on this check, the finalization
765 -- machinery will request or reclaim extra storage reserved for
766 -- a list header.
768 elsif Is_Class_Wide_Type (Desig_Typ) then
770 -- Detect a special case where interface class-wide types
771 -- are involved as the object appears as:
773 -- Tag_Ptr (Base_Address (<object>'Address))
775 -- The expression already yields the proper tag, generate:
777 -- Temp.all
779 if Is_RTE (Etype (Temp), RE_Tag_Ptr) then
780 Param :=
781 Make_Explicit_Dereference (Loc,
782 Prefix => Relocate_Node (Temp));
784 -- In the default case, obtain the tag of the object about
785 -- to be allocated / deallocated. Generate:
787 -- Temp'Tag
789 else
790 Param :=
791 Make_Attribute_Reference (Loc,
792 Prefix => Relocate_Node (Temp),
793 Attribute_Name => Name_Tag);
794 end if;
796 -- Generate:
797 -- Needs_Finalization (<Param>)
799 Flag_Expr :=
800 Make_Function_Call (Loc,
801 Name =>
802 New_Occurrence_Of (RTE (RE_Needs_Finalization), Loc),
803 Parameter_Associations => New_List (Param));
805 -- Processing for generic actuals
807 elsif Is_Generic_Actual_Type (Desig_Typ) then
808 Flag_Expr :=
809 New_Occurrence_Of (Boolean_Literals
810 (Needs_Finalization (Base_Type (Desig_Typ))), Loc);
812 -- The object does not require any specialized checks, it is
813 -- known to be controlled.
815 else
816 Flag_Expr := New_Occurrence_Of (Standard_True, Loc);
817 end if;
819 -- Create the temporary which represents the finalization state
820 -- of the expression. Generate:
822 -- F : constant Boolean := <Flag_Expr>;
824 Insert_Action (N,
825 Make_Object_Declaration (Loc,
826 Defining_Identifier => Flag_Id,
827 Constant_Present => True,
828 Object_Definition =>
829 New_Occurrence_Of (Standard_Boolean, Loc),
830 Expression => Flag_Expr));
832 Append_To (Actuals, New_Occurrence_Of (Flag_Id, Loc));
833 end;
835 -- The object is not controlled
837 else
838 Append_To (Actuals, New_Occurrence_Of (Standard_False, Loc));
839 end if;
841 -- i) On_Subpool
843 if Is_Allocate then
844 Append_To (Actuals,
845 New_Occurrence_Of (Boolean_Literals (Present (Subpool)), Loc));
846 end if;
848 -- Step 2: Build a wrapper Allocate / Deallocate which internally
849 -- calls Allocate_Any_Controlled / Deallocate_Any_Controlled.
851 -- Select the proper routine to call
853 if Is_Allocate then
854 Proc_To_Call := RTE (RE_Allocate_Any_Controlled);
855 else
856 Proc_To_Call := RTE (RE_Deallocate_Any_Controlled);
857 end if;
859 -- Create a custom Allocate / Deallocate routine which has identical
860 -- profile to that of System.Storage_Pools.
862 Insert_Action (N,
863 Make_Subprogram_Body (Loc,
864 Specification =>
866 -- procedure Pnn
868 Make_Procedure_Specification (Loc,
869 Defining_Unit_Name => Proc_Id,
870 Parameter_Specifications => New_List (
872 -- P : Root_Storage_Pool
874 Make_Parameter_Specification (Loc,
875 Defining_Identifier => Make_Temporary (Loc, 'P'),
876 Parameter_Type =>
877 New_Occurrence_Of (RTE (RE_Root_Storage_Pool), Loc)),
879 -- A : [out] Address
881 Make_Parameter_Specification (Loc,
882 Defining_Identifier => Addr_Id,
883 Out_Present => Is_Allocate,
884 Parameter_Type =>
885 New_Occurrence_Of (RTE (RE_Address), Loc)),
887 -- S : Storage_Count
889 Make_Parameter_Specification (Loc,
890 Defining_Identifier => Size_Id,
891 Parameter_Type =>
892 New_Occurrence_Of (RTE (RE_Storage_Count), Loc)),
894 -- L : Storage_Count
896 Make_Parameter_Specification (Loc,
897 Defining_Identifier => Alig_Id,
898 Parameter_Type =>
899 New_Occurrence_Of (RTE (RE_Storage_Count), Loc)))),
901 Declarations => No_List,
903 Handled_Statement_Sequence =>
904 Make_Handled_Sequence_Of_Statements (Loc,
905 Statements => New_List (
906 Make_Procedure_Call_Statement (Loc,
907 Name => New_Occurrence_Of (Proc_To_Call, Loc),
908 Parameter_Associations => Actuals)))));
910 -- The newly generated Allocate / Deallocate becomes the default
911 -- procedure to call when the back end processes the allocation /
912 -- deallocation.
914 if Is_Allocate then
915 Set_Procedure_To_Call (Expr, Proc_Id);
916 else
917 Set_Procedure_To_Call (N, Proc_Id);
918 end if;
919 end;
920 end Build_Allocate_Deallocate_Proc;
922 --------------------------
923 -- Build_Procedure_Form --
924 --------------------------
926 procedure Build_Procedure_Form (N : Node_Id) is
927 Loc : constant Source_Ptr := Sloc (N);
928 Subp : constant Entity_Id := Defining_Entity (N);
930 Func_Formal : Entity_Id;
931 Proc_Formals : List_Id;
932 Proc_Decl : Node_Id;
934 begin
935 -- No action needed if this transformation was already done, or in case
936 -- of subprogram renaming declarations.
938 if Nkind (Specification (N)) = N_Procedure_Specification
939 or else Nkind (N) = N_Subprogram_Renaming_Declaration
940 then
941 return;
942 end if;
944 -- Ditto when dealing with an expression function, where both the
945 -- original expression and the generated declaration end up being
946 -- expanded here.
948 if Rewritten_For_C (Subp) then
949 return;
950 end if;
952 Proc_Formals := New_List;
954 -- Create a list of formal parameters with the same types as the
955 -- function.
957 Func_Formal := First_Formal (Subp);
958 while Present (Func_Formal) loop
959 Append_To (Proc_Formals,
960 Make_Parameter_Specification (Loc,
961 Defining_Identifier =>
962 Make_Defining_Identifier (Loc, Chars (Func_Formal)),
963 Parameter_Type =>
964 New_Occurrence_Of (Etype (Func_Formal), Loc)));
966 Next_Formal (Func_Formal);
967 end loop;
969 -- Add an extra out parameter to carry the function result
971 Name_Len := 6;
972 Name_Buffer (1 .. Name_Len) := "RESULT";
973 Append_To (Proc_Formals,
974 Make_Parameter_Specification (Loc,
975 Defining_Identifier =>
976 Make_Defining_Identifier (Loc, Chars => Name_Find),
977 Out_Present => True,
978 Parameter_Type => New_Occurrence_Of (Etype (Subp), Loc)));
980 -- The new procedure declaration is inserted immediately after the
981 -- function declaration. The processing in Build_Procedure_Body_Form
982 -- relies on this order.
984 Proc_Decl :=
985 Make_Subprogram_Declaration (Loc,
986 Specification =>
987 Make_Procedure_Specification (Loc,
988 Defining_Unit_Name =>
989 Make_Defining_Identifier (Loc, Chars (Subp)),
990 Parameter_Specifications => Proc_Formals));
992 Insert_After_And_Analyze (Unit_Declaration_Node (Subp), Proc_Decl);
994 -- Entity of procedure must remain invisible so that it does not
995 -- overload subsequent references to the original function.
997 Set_Is_Immediately_Visible (Defining_Entity (Proc_Decl), False);
999 -- Mark the function as having a procedure form and link the function
1000 -- and its internally built procedure.
1002 Set_Rewritten_For_C (Subp);
1003 Set_Corresponding_Procedure (Subp, Defining_Entity (Proc_Decl));
1004 Set_Corresponding_Function (Defining_Entity (Proc_Decl), Subp);
1005 end Build_Procedure_Form;
1007 ------------------------
1008 -- Build_Runtime_Call --
1009 ------------------------
1011 function Build_Runtime_Call (Loc : Source_Ptr; RE : RE_Id) return Node_Id is
1012 begin
1013 -- If entity is not available, we can skip making the call (this avoids
1014 -- junk duplicated error messages in a number of cases).
1016 if not RTE_Available (RE) then
1017 return Make_Null_Statement (Loc);
1018 else
1019 return
1020 Make_Procedure_Call_Statement (Loc,
1021 Name => New_Occurrence_Of (RTE (RE), Loc));
1022 end if;
1023 end Build_Runtime_Call;
1025 ------------------------
1026 -- Build_SS_Mark_Call --
1027 ------------------------
1029 function Build_SS_Mark_Call
1030 (Loc : Source_Ptr;
1031 Mark : Entity_Id) return Node_Id
1033 begin
1034 -- Generate:
1035 -- Mark : constant Mark_Id := SS_Mark;
1037 return
1038 Make_Object_Declaration (Loc,
1039 Defining_Identifier => Mark,
1040 Constant_Present => True,
1041 Object_Definition =>
1042 New_Occurrence_Of (RTE (RE_Mark_Id), Loc),
1043 Expression =>
1044 Make_Function_Call (Loc,
1045 Name => New_Occurrence_Of (RTE (RE_SS_Mark), Loc)));
1046 end Build_SS_Mark_Call;
1048 ---------------------------
1049 -- Build_SS_Release_Call --
1050 ---------------------------
1052 function Build_SS_Release_Call
1053 (Loc : Source_Ptr;
1054 Mark : Entity_Id) return Node_Id
1056 begin
1057 -- Generate:
1058 -- SS_Release (Mark);
1060 return
1061 Make_Procedure_Call_Statement (Loc,
1062 Name =>
1063 New_Occurrence_Of (RTE (RE_SS_Release), Loc),
1064 Parameter_Associations => New_List (
1065 New_Occurrence_Of (Mark, Loc)));
1066 end Build_SS_Release_Call;
1068 ----------------------------
1069 -- Build_Task_Array_Image --
1070 ----------------------------
1072 -- This function generates the body for a function that constructs the
1073 -- image string for a task that is an array component. The function is
1074 -- local to the init proc for the array type, and is called for each one
1075 -- of the components. The constructed image has the form of an indexed
1076 -- component, whose prefix is the outer variable of the array type.
1077 -- The n-dimensional array type has known indexes Index, Index2...
1079 -- Id_Ref is an indexed component form created by the enclosing init proc.
1080 -- Its successive indexes are Val1, Val2, ... which are the loop variables
1081 -- in the loops that call the individual task init proc on each component.
1083 -- The generated function has the following structure:
1085 -- function F return String is
1086 -- Pref : string renames Task_Name;
1087 -- T1 : String := Index1'Image (Val1);
1088 -- ...
1089 -- Tn : String := indexn'image (Valn);
1090 -- Len : Integer := T1'Length + ... + Tn'Length + n + 1;
1091 -- -- Len includes commas and the end parentheses.
1092 -- Res : String (1..Len);
1093 -- Pos : Integer := Pref'Length;
1095 -- begin
1096 -- Res (1 .. Pos) := Pref;
1097 -- Pos := Pos + 1;
1098 -- Res (Pos) := '(';
1099 -- Pos := Pos + 1;
1100 -- Res (Pos .. Pos + T1'Length - 1) := T1;
1101 -- Pos := Pos + T1'Length;
1102 -- Res (Pos) := '.';
1103 -- Pos := Pos + 1;
1104 -- ...
1105 -- Res (Pos .. Pos + Tn'Length - 1) := Tn;
1106 -- Res (Len) := ')';
1108 -- return Res;
1109 -- end F;
1111 -- Needless to say, multidimensional arrays of tasks are rare enough that
1112 -- the bulkiness of this code is not really a concern.
1114 function Build_Task_Array_Image
1115 (Loc : Source_Ptr;
1116 Id_Ref : Node_Id;
1117 A_Type : Entity_Id;
1118 Dyn : Boolean := False) return Node_Id
1120 Dims : constant Nat := Number_Dimensions (A_Type);
1121 -- Number of dimensions for array of tasks
1123 Temps : array (1 .. Dims) of Entity_Id;
1124 -- Array of temporaries to hold string for each index
1126 Indx : Node_Id;
1127 -- Index expression
1129 Len : Entity_Id;
1130 -- Total length of generated name
1132 Pos : Entity_Id;
1133 -- Running index for substring assignments
1135 Pref : constant Entity_Id := Make_Temporary (Loc, 'P');
1136 -- Name of enclosing variable, prefix of resulting name
1138 Res : Entity_Id;
1139 -- String to hold result
1141 Val : Node_Id;
1142 -- Value of successive indexes
1144 Sum : Node_Id;
1145 -- Expression to compute total size of string
1147 T : Entity_Id;
1148 -- Entity for name at one index position
1150 Decls : constant List_Id := New_List;
1151 Stats : constant List_Id := New_List;
1153 begin
1154 -- For a dynamic task, the name comes from the target variable. For a
1155 -- static one it is a formal of the enclosing init proc.
1157 if Dyn then
1158 Get_Name_String (Chars (Entity (Prefix (Id_Ref))));
1159 Append_To (Decls,
1160 Make_Object_Declaration (Loc,
1161 Defining_Identifier => Pref,
1162 Object_Definition => New_Occurrence_Of (Standard_String, Loc),
1163 Expression =>
1164 Make_String_Literal (Loc,
1165 Strval => String_From_Name_Buffer)));
1167 else
1168 Append_To (Decls,
1169 Make_Object_Renaming_Declaration (Loc,
1170 Defining_Identifier => Pref,
1171 Subtype_Mark => New_Occurrence_Of (Standard_String, Loc),
1172 Name => Make_Identifier (Loc, Name_uTask_Name)));
1173 end if;
1175 Indx := First_Index (A_Type);
1176 Val := First (Expressions (Id_Ref));
1178 for J in 1 .. Dims loop
1179 T := Make_Temporary (Loc, 'T');
1180 Temps (J) := T;
1182 Append_To (Decls,
1183 Make_Object_Declaration (Loc,
1184 Defining_Identifier => T,
1185 Object_Definition => New_Occurrence_Of (Standard_String, Loc),
1186 Expression =>
1187 Make_Attribute_Reference (Loc,
1188 Attribute_Name => Name_Image,
1189 Prefix => New_Occurrence_Of (Etype (Indx), Loc),
1190 Expressions => New_List (New_Copy_Tree (Val)))));
1192 Next_Index (Indx);
1193 Next (Val);
1194 end loop;
1196 Sum := Make_Integer_Literal (Loc, Dims + 1);
1198 Sum :=
1199 Make_Op_Add (Loc,
1200 Left_Opnd => Sum,
1201 Right_Opnd =>
1202 Make_Attribute_Reference (Loc,
1203 Attribute_Name => Name_Length,
1204 Prefix => New_Occurrence_Of (Pref, Loc),
1205 Expressions => New_List (Make_Integer_Literal (Loc, 1))));
1207 for J in 1 .. Dims loop
1208 Sum :=
1209 Make_Op_Add (Loc,
1210 Left_Opnd => Sum,
1211 Right_Opnd =>
1212 Make_Attribute_Reference (Loc,
1213 Attribute_Name => Name_Length,
1214 Prefix =>
1215 New_Occurrence_Of (Temps (J), Loc),
1216 Expressions => New_List (Make_Integer_Literal (Loc, 1))));
1217 end loop;
1219 Build_Task_Image_Prefix (Loc, Len, Res, Pos, Pref, Sum, Decls, Stats);
1221 Set_Character_Literal_Name (Char_Code (Character'Pos ('(')));
1223 Append_To (Stats,
1224 Make_Assignment_Statement (Loc,
1225 Name =>
1226 Make_Indexed_Component (Loc,
1227 Prefix => New_Occurrence_Of (Res, Loc),
1228 Expressions => New_List (New_Occurrence_Of (Pos, Loc))),
1229 Expression =>
1230 Make_Character_Literal (Loc,
1231 Chars => Name_Find,
1232 Char_Literal_Value => UI_From_Int (Character'Pos ('(')))));
1234 Append_To (Stats,
1235 Make_Assignment_Statement (Loc,
1236 Name => New_Occurrence_Of (Pos, Loc),
1237 Expression =>
1238 Make_Op_Add (Loc,
1239 Left_Opnd => New_Occurrence_Of (Pos, Loc),
1240 Right_Opnd => Make_Integer_Literal (Loc, 1))));
1242 for J in 1 .. Dims loop
1244 Append_To (Stats,
1245 Make_Assignment_Statement (Loc,
1246 Name =>
1247 Make_Slice (Loc,
1248 Prefix => New_Occurrence_Of (Res, Loc),
1249 Discrete_Range =>
1250 Make_Range (Loc,
1251 Low_Bound => New_Occurrence_Of (Pos, Loc),
1252 High_Bound =>
1253 Make_Op_Subtract (Loc,
1254 Left_Opnd =>
1255 Make_Op_Add (Loc,
1256 Left_Opnd => New_Occurrence_Of (Pos, Loc),
1257 Right_Opnd =>
1258 Make_Attribute_Reference (Loc,
1259 Attribute_Name => Name_Length,
1260 Prefix =>
1261 New_Occurrence_Of (Temps (J), Loc),
1262 Expressions =>
1263 New_List (Make_Integer_Literal (Loc, 1)))),
1264 Right_Opnd => Make_Integer_Literal (Loc, 1)))),
1266 Expression => New_Occurrence_Of (Temps (J), Loc)));
1268 if J < Dims then
1269 Append_To (Stats,
1270 Make_Assignment_Statement (Loc,
1271 Name => New_Occurrence_Of (Pos, Loc),
1272 Expression =>
1273 Make_Op_Add (Loc,
1274 Left_Opnd => New_Occurrence_Of (Pos, Loc),
1275 Right_Opnd =>
1276 Make_Attribute_Reference (Loc,
1277 Attribute_Name => Name_Length,
1278 Prefix => New_Occurrence_Of (Temps (J), Loc),
1279 Expressions =>
1280 New_List (Make_Integer_Literal (Loc, 1))))));
1282 Set_Character_Literal_Name (Char_Code (Character'Pos (',')));
1284 Append_To (Stats,
1285 Make_Assignment_Statement (Loc,
1286 Name => Make_Indexed_Component (Loc,
1287 Prefix => New_Occurrence_Of (Res, Loc),
1288 Expressions => New_List (New_Occurrence_Of (Pos, Loc))),
1289 Expression =>
1290 Make_Character_Literal (Loc,
1291 Chars => Name_Find,
1292 Char_Literal_Value => UI_From_Int (Character'Pos (',')))));
1294 Append_To (Stats,
1295 Make_Assignment_Statement (Loc,
1296 Name => New_Occurrence_Of (Pos, Loc),
1297 Expression =>
1298 Make_Op_Add (Loc,
1299 Left_Opnd => New_Occurrence_Of (Pos, Loc),
1300 Right_Opnd => Make_Integer_Literal (Loc, 1))));
1301 end if;
1302 end loop;
1304 Set_Character_Literal_Name (Char_Code (Character'Pos (')')));
1306 Append_To (Stats,
1307 Make_Assignment_Statement (Loc,
1308 Name =>
1309 Make_Indexed_Component (Loc,
1310 Prefix => New_Occurrence_Of (Res, Loc),
1311 Expressions => New_List (New_Occurrence_Of (Len, Loc))),
1312 Expression =>
1313 Make_Character_Literal (Loc,
1314 Chars => Name_Find,
1315 Char_Literal_Value => UI_From_Int (Character'Pos (')')))));
1316 return Build_Task_Image_Function (Loc, Decls, Stats, Res);
1317 end Build_Task_Array_Image;
1319 ----------------------------
1320 -- Build_Task_Image_Decls --
1321 ----------------------------
1323 function Build_Task_Image_Decls
1324 (Loc : Source_Ptr;
1325 Id_Ref : Node_Id;
1326 A_Type : Entity_Id;
1327 In_Init_Proc : Boolean := False) return List_Id
1329 Decls : constant List_Id := New_List;
1330 T_Id : Entity_Id := Empty;
1331 Decl : Node_Id;
1332 Expr : Node_Id := Empty;
1333 Fun : Node_Id := Empty;
1334 Is_Dyn : constant Boolean :=
1335 Nkind (Parent (Id_Ref)) = N_Assignment_Statement
1336 and then
1337 Nkind (Expression (Parent (Id_Ref))) = N_Allocator;
1339 begin
1340 -- If Discard_Names or No_Implicit_Heap_Allocations are in effect,
1341 -- generate a dummy declaration only.
1343 if Restriction_Active (No_Implicit_Heap_Allocations)
1344 or else Global_Discard_Names
1345 then
1346 T_Id := Make_Temporary (Loc, 'J');
1347 Name_Len := 0;
1349 return
1350 New_List (
1351 Make_Object_Declaration (Loc,
1352 Defining_Identifier => T_Id,
1353 Object_Definition => New_Occurrence_Of (Standard_String, Loc),
1354 Expression =>
1355 Make_String_Literal (Loc,
1356 Strval => String_From_Name_Buffer)));
1358 else
1359 if Nkind (Id_Ref) = N_Identifier
1360 or else Nkind (Id_Ref) = N_Defining_Identifier
1361 then
1362 -- For a simple variable, the image of the task is built from
1363 -- the name of the variable. To avoid possible conflict with the
1364 -- anonymous type created for a single protected object, add a
1365 -- numeric suffix.
1367 T_Id :=
1368 Make_Defining_Identifier (Loc,
1369 New_External_Name (Chars (Id_Ref), 'T', 1));
1371 Get_Name_String (Chars (Id_Ref));
1373 Expr :=
1374 Make_String_Literal (Loc,
1375 Strval => String_From_Name_Buffer);
1377 elsif Nkind (Id_Ref) = N_Selected_Component then
1378 T_Id :=
1379 Make_Defining_Identifier (Loc,
1380 New_External_Name (Chars (Selector_Name (Id_Ref)), 'T'));
1381 Fun := Build_Task_Record_Image (Loc, Id_Ref, Is_Dyn);
1383 elsif Nkind (Id_Ref) = N_Indexed_Component then
1384 T_Id :=
1385 Make_Defining_Identifier (Loc,
1386 New_External_Name (Chars (A_Type), 'N'));
1388 Fun := Build_Task_Array_Image (Loc, Id_Ref, A_Type, Is_Dyn);
1389 end if;
1390 end if;
1392 if Present (Fun) then
1393 Append (Fun, Decls);
1394 Expr := Make_Function_Call (Loc,
1395 Name => New_Occurrence_Of (Defining_Entity (Fun), Loc));
1397 if not In_Init_Proc then
1398 Set_Uses_Sec_Stack (Defining_Entity (Fun));
1399 end if;
1400 end if;
1402 Decl := Make_Object_Declaration (Loc,
1403 Defining_Identifier => T_Id,
1404 Object_Definition => New_Occurrence_Of (Standard_String, Loc),
1405 Constant_Present => True,
1406 Expression => Expr);
1408 Append (Decl, Decls);
1409 return Decls;
1410 end Build_Task_Image_Decls;
1412 -------------------------------
1413 -- Build_Task_Image_Function --
1414 -------------------------------
1416 function Build_Task_Image_Function
1417 (Loc : Source_Ptr;
1418 Decls : List_Id;
1419 Stats : List_Id;
1420 Res : Entity_Id) return Node_Id
1422 Spec : Node_Id;
1424 begin
1425 Append_To (Stats,
1426 Make_Simple_Return_Statement (Loc,
1427 Expression => New_Occurrence_Of (Res, Loc)));
1429 Spec := Make_Function_Specification (Loc,
1430 Defining_Unit_Name => Make_Temporary (Loc, 'F'),
1431 Result_Definition => New_Occurrence_Of (Standard_String, Loc));
1433 -- Calls to 'Image use the secondary stack, which must be cleaned up
1434 -- after the task name is built.
1436 return Make_Subprogram_Body (Loc,
1437 Specification => Spec,
1438 Declarations => Decls,
1439 Handled_Statement_Sequence =>
1440 Make_Handled_Sequence_Of_Statements (Loc, Statements => Stats));
1441 end Build_Task_Image_Function;
1443 -----------------------------
1444 -- Build_Task_Image_Prefix --
1445 -----------------------------
1447 procedure Build_Task_Image_Prefix
1448 (Loc : Source_Ptr;
1449 Len : out Entity_Id;
1450 Res : out Entity_Id;
1451 Pos : out Entity_Id;
1452 Prefix : Entity_Id;
1453 Sum : Node_Id;
1454 Decls : List_Id;
1455 Stats : List_Id)
1457 begin
1458 Len := Make_Temporary (Loc, 'L', Sum);
1460 Append_To (Decls,
1461 Make_Object_Declaration (Loc,
1462 Defining_Identifier => Len,
1463 Object_Definition => New_Occurrence_Of (Standard_Integer, Loc),
1464 Expression => Sum));
1466 Res := Make_Temporary (Loc, 'R');
1468 Append_To (Decls,
1469 Make_Object_Declaration (Loc,
1470 Defining_Identifier => Res,
1471 Object_Definition =>
1472 Make_Subtype_Indication (Loc,
1473 Subtype_Mark => New_Occurrence_Of (Standard_String, Loc),
1474 Constraint =>
1475 Make_Index_Or_Discriminant_Constraint (Loc,
1476 Constraints =>
1477 New_List (
1478 Make_Range (Loc,
1479 Low_Bound => Make_Integer_Literal (Loc, 1),
1480 High_Bound => New_Occurrence_Of (Len, Loc)))))));
1482 -- Indicate that the result is an internal temporary, so it does not
1483 -- receive a bogus initialization when declaration is expanded. This
1484 -- is both efficient, and prevents anomalies in the handling of
1485 -- dynamic objects on the secondary stack.
1487 Set_Is_Internal (Res);
1488 Pos := Make_Temporary (Loc, 'P');
1490 Append_To (Decls,
1491 Make_Object_Declaration (Loc,
1492 Defining_Identifier => Pos,
1493 Object_Definition => New_Occurrence_Of (Standard_Integer, Loc)));
1495 -- Pos := Prefix'Length;
1497 Append_To (Stats,
1498 Make_Assignment_Statement (Loc,
1499 Name => New_Occurrence_Of (Pos, Loc),
1500 Expression =>
1501 Make_Attribute_Reference (Loc,
1502 Attribute_Name => Name_Length,
1503 Prefix => New_Occurrence_Of (Prefix, Loc),
1504 Expressions => New_List (Make_Integer_Literal (Loc, 1)))));
1506 -- Res (1 .. Pos) := Prefix;
1508 Append_To (Stats,
1509 Make_Assignment_Statement (Loc,
1510 Name =>
1511 Make_Slice (Loc,
1512 Prefix => New_Occurrence_Of (Res, Loc),
1513 Discrete_Range =>
1514 Make_Range (Loc,
1515 Low_Bound => Make_Integer_Literal (Loc, 1),
1516 High_Bound => New_Occurrence_Of (Pos, Loc))),
1518 Expression => New_Occurrence_Of (Prefix, Loc)));
1520 Append_To (Stats,
1521 Make_Assignment_Statement (Loc,
1522 Name => New_Occurrence_Of (Pos, Loc),
1523 Expression =>
1524 Make_Op_Add (Loc,
1525 Left_Opnd => New_Occurrence_Of (Pos, Loc),
1526 Right_Opnd => Make_Integer_Literal (Loc, 1))));
1527 end Build_Task_Image_Prefix;
1529 -----------------------------
1530 -- Build_Task_Record_Image --
1531 -----------------------------
1533 function Build_Task_Record_Image
1534 (Loc : Source_Ptr;
1535 Id_Ref : Node_Id;
1536 Dyn : Boolean := False) return Node_Id
1538 Len : Entity_Id;
1539 -- Total length of generated name
1541 Pos : Entity_Id;
1542 -- Index into result
1544 Res : Entity_Id;
1545 -- String to hold result
1547 Pref : constant Entity_Id := Make_Temporary (Loc, 'P');
1548 -- Name of enclosing variable, prefix of resulting name
1550 Sum : Node_Id;
1551 -- Expression to compute total size of string
1553 Sel : Entity_Id;
1554 -- Entity for selector name
1556 Decls : constant List_Id := New_List;
1557 Stats : constant List_Id := New_List;
1559 begin
1560 -- For a dynamic task, the name comes from the target variable. For a
1561 -- static one it is a formal of the enclosing init proc.
1563 if Dyn then
1564 Get_Name_String (Chars (Entity (Prefix (Id_Ref))));
1565 Append_To (Decls,
1566 Make_Object_Declaration (Loc,
1567 Defining_Identifier => Pref,
1568 Object_Definition => New_Occurrence_Of (Standard_String, Loc),
1569 Expression =>
1570 Make_String_Literal (Loc,
1571 Strval => String_From_Name_Buffer)));
1573 else
1574 Append_To (Decls,
1575 Make_Object_Renaming_Declaration (Loc,
1576 Defining_Identifier => Pref,
1577 Subtype_Mark => New_Occurrence_Of (Standard_String, Loc),
1578 Name => Make_Identifier (Loc, Name_uTask_Name)));
1579 end if;
1581 Sel := Make_Temporary (Loc, 'S');
1583 Get_Name_String (Chars (Selector_Name (Id_Ref)));
1585 Append_To (Decls,
1586 Make_Object_Declaration (Loc,
1587 Defining_Identifier => Sel,
1588 Object_Definition => New_Occurrence_Of (Standard_String, Loc),
1589 Expression =>
1590 Make_String_Literal (Loc,
1591 Strval => String_From_Name_Buffer)));
1593 Sum := Make_Integer_Literal (Loc, Nat (Name_Len + 1));
1595 Sum :=
1596 Make_Op_Add (Loc,
1597 Left_Opnd => Sum,
1598 Right_Opnd =>
1599 Make_Attribute_Reference (Loc,
1600 Attribute_Name => Name_Length,
1601 Prefix =>
1602 New_Occurrence_Of (Pref, Loc),
1603 Expressions => New_List (Make_Integer_Literal (Loc, 1))));
1605 Build_Task_Image_Prefix (Loc, Len, Res, Pos, Pref, Sum, Decls, Stats);
1607 Set_Character_Literal_Name (Char_Code (Character'Pos ('.')));
1609 -- Res (Pos) := '.';
1611 Append_To (Stats,
1612 Make_Assignment_Statement (Loc,
1613 Name => Make_Indexed_Component (Loc,
1614 Prefix => New_Occurrence_Of (Res, Loc),
1615 Expressions => New_List (New_Occurrence_Of (Pos, Loc))),
1616 Expression =>
1617 Make_Character_Literal (Loc,
1618 Chars => Name_Find,
1619 Char_Literal_Value =>
1620 UI_From_Int (Character'Pos ('.')))));
1622 Append_To (Stats,
1623 Make_Assignment_Statement (Loc,
1624 Name => New_Occurrence_Of (Pos, Loc),
1625 Expression =>
1626 Make_Op_Add (Loc,
1627 Left_Opnd => New_Occurrence_Of (Pos, Loc),
1628 Right_Opnd => Make_Integer_Literal (Loc, 1))));
1630 -- Res (Pos .. Len) := Selector;
1632 Append_To (Stats,
1633 Make_Assignment_Statement (Loc,
1634 Name => Make_Slice (Loc,
1635 Prefix => New_Occurrence_Of (Res, Loc),
1636 Discrete_Range =>
1637 Make_Range (Loc,
1638 Low_Bound => New_Occurrence_Of (Pos, Loc),
1639 High_Bound => New_Occurrence_Of (Len, Loc))),
1640 Expression => New_Occurrence_Of (Sel, Loc)));
1642 return Build_Task_Image_Function (Loc, Decls, Stats, Res);
1643 end Build_Task_Record_Image;
1645 -----------------------------
1646 -- Check_Float_Op_Overflow --
1647 -----------------------------
1649 procedure Check_Float_Op_Overflow (N : Node_Id) is
1650 begin
1651 -- Return if no check needed
1653 if not Is_Floating_Point_Type (Etype (N))
1654 or else not (Do_Overflow_Check (N) and then Check_Float_Overflow)
1656 -- In CodePeer_Mode, rely on the overflow check flag being set instead
1657 -- and do not expand the code for float overflow checking.
1659 or else CodePeer_Mode
1660 then
1661 return;
1662 end if;
1664 -- Otherwise we replace the expression by
1666 -- do Tnn : constant ftype := expression;
1667 -- constraint_error when not Tnn'Valid;
1668 -- in Tnn;
1670 declare
1671 Loc : constant Source_Ptr := Sloc (N);
1672 Tnn : constant Entity_Id := Make_Temporary (Loc, 'T', N);
1673 Typ : constant Entity_Id := Etype (N);
1675 begin
1676 -- Turn off the Do_Overflow_Check flag, since we are doing that work
1677 -- right here. We also set the node as analyzed to prevent infinite
1678 -- recursion from repeating the operation in the expansion.
1680 Set_Do_Overflow_Check (N, False);
1681 Set_Analyzed (N, True);
1683 -- Do the rewrite to include the check
1685 Rewrite (N,
1686 Make_Expression_With_Actions (Loc,
1687 Actions => New_List (
1688 Make_Object_Declaration (Loc,
1689 Defining_Identifier => Tnn,
1690 Object_Definition => New_Occurrence_Of (Typ, Loc),
1691 Constant_Present => True,
1692 Expression => Relocate_Node (N)),
1693 Make_Raise_Constraint_Error (Loc,
1694 Condition =>
1695 Make_Op_Not (Loc,
1696 Right_Opnd =>
1697 Make_Attribute_Reference (Loc,
1698 Prefix => New_Occurrence_Of (Tnn, Loc),
1699 Attribute_Name => Name_Valid)),
1700 Reason => CE_Overflow_Check_Failed)),
1701 Expression => New_Occurrence_Of (Tnn, Loc)));
1703 Analyze_And_Resolve (N, Typ);
1704 end;
1705 end Check_Float_Op_Overflow;
1707 ----------------------------------
1708 -- Component_May_Be_Bit_Aligned --
1709 ----------------------------------
1711 function Component_May_Be_Bit_Aligned (Comp : Entity_Id) return Boolean is
1712 UT : Entity_Id;
1714 begin
1715 -- If no component clause, then everything is fine, since the back end
1716 -- never bit-misaligns by default, even if there is a pragma Packed for
1717 -- the record.
1719 if No (Comp) or else No (Component_Clause (Comp)) then
1720 return False;
1721 end if;
1723 UT := Underlying_Type (Etype (Comp));
1725 -- It is only array and record types that cause trouble
1727 if not Is_Record_Type (UT) and then not Is_Array_Type (UT) then
1728 return False;
1730 -- If we know that we have a small (64 bits or less) record or small
1731 -- bit-packed array, then everything is fine, since the back end can
1732 -- handle these cases correctly.
1734 elsif Esize (Comp) <= 64
1735 and then (Is_Record_Type (UT) or else Is_Bit_Packed_Array (UT))
1736 then
1737 return False;
1739 -- Otherwise if the component is not byte aligned, we know we have the
1740 -- nasty unaligned case.
1742 elsif Normalized_First_Bit (Comp) /= Uint_0
1743 or else Esize (Comp) mod System_Storage_Unit /= Uint_0
1744 then
1745 return True;
1747 -- If we are large and byte aligned, then OK at this level
1749 else
1750 return False;
1751 end if;
1752 end Component_May_Be_Bit_Aligned;
1754 ----------------------------------------
1755 -- Containing_Package_With_Ext_Axioms --
1756 ----------------------------------------
1758 function Containing_Package_With_Ext_Axioms
1759 (E : Entity_Id) return Entity_Id
1761 begin
1762 -- E is the package or generic package which is externally axiomatized
1764 if Ekind_In (E, E_Generic_Package, E_Package)
1765 and then Has_Annotate_Pragma_For_External_Axiomatization (E)
1766 then
1767 return E;
1768 end if;
1770 -- If E's scope is axiomatized, E is axiomatized
1772 if Present (Scope (E)) then
1773 declare
1774 First_Ax_Parent_Scope : constant Entity_Id :=
1775 Containing_Package_With_Ext_Axioms (Scope (E));
1776 begin
1777 if Present (First_Ax_Parent_Scope) then
1778 return First_Ax_Parent_Scope;
1779 end if;
1780 end;
1781 end if;
1783 -- Otherwise, if E is a package instance, it is axiomatized if the
1784 -- corresponding generic package is axiomatized.
1786 if Ekind (E) = E_Package then
1787 declare
1788 Par : constant Node_Id := Parent (E);
1789 Decl : Node_Id;
1791 begin
1792 if Nkind (Par) = N_Defining_Program_Unit_Name then
1793 Decl := Parent (Par);
1794 else
1795 Decl := Par;
1796 end if;
1798 if Present (Generic_Parent (Decl)) then
1799 return
1800 Containing_Package_With_Ext_Axioms (Generic_Parent (Decl));
1801 end if;
1802 end;
1803 end if;
1805 return Empty;
1806 end Containing_Package_With_Ext_Axioms;
1808 -------------------------------
1809 -- Convert_To_Actual_Subtype --
1810 -------------------------------
1812 procedure Convert_To_Actual_Subtype (Exp : Entity_Id) is
1813 Act_ST : Entity_Id;
1815 begin
1816 Act_ST := Get_Actual_Subtype (Exp);
1818 if Act_ST = Etype (Exp) then
1819 return;
1820 else
1821 Rewrite (Exp, Convert_To (Act_ST, Relocate_Node (Exp)));
1822 Analyze_And_Resolve (Exp, Act_ST);
1823 end if;
1824 end Convert_To_Actual_Subtype;
1826 -----------------------------------
1827 -- Corresponding_Runtime_Package --
1828 -----------------------------------
1830 function Corresponding_Runtime_Package (Typ : Entity_Id) return RTU_Id is
1831 Pkg_Id : RTU_Id := RTU_Null;
1833 begin
1834 pragma Assert (Is_Concurrent_Type (Typ));
1836 if Ekind (Typ) in Protected_Kind then
1837 if Has_Entries (Typ)
1839 -- A protected type without entries that covers an interface and
1840 -- overrides the abstract routines with protected procedures is
1841 -- considered equivalent to a protected type with entries in the
1842 -- context of dispatching select statements. It is sufficient to
1843 -- check for the presence of an interface list in the declaration
1844 -- node to recognize this case.
1846 or else Present (Interface_List (Parent (Typ)))
1848 -- Protected types with interrupt handlers (when not using a
1849 -- restricted profile) are also considered equivalent to
1850 -- protected types with entries. The types which are used
1851 -- (Static_Interrupt_Protection and Dynamic_Interrupt_Protection)
1852 -- are derived from Protection_Entries.
1854 or else (Has_Attach_Handler (Typ) and then not Restricted_Profile)
1855 or else Has_Interrupt_Handler (Typ)
1856 then
1857 if Abort_Allowed
1858 or else Restriction_Active (No_Entry_Queue) = False
1859 or else Restriction_Active (No_Select_Statements) = False
1860 or else Number_Entries (Typ) > 1
1861 or else (Has_Attach_Handler (Typ)
1862 and then not Restricted_Profile)
1863 then
1864 Pkg_Id := System_Tasking_Protected_Objects_Entries;
1865 else
1866 Pkg_Id := System_Tasking_Protected_Objects_Single_Entry;
1867 end if;
1869 else
1870 Pkg_Id := System_Tasking_Protected_Objects;
1871 end if;
1872 end if;
1874 return Pkg_Id;
1875 end Corresponding_Runtime_Package;
1877 -----------------------------------
1878 -- Current_Sem_Unit_Declarations --
1879 -----------------------------------
1881 function Current_Sem_Unit_Declarations return List_Id is
1882 U : Node_Id := Unit (Cunit (Current_Sem_Unit));
1883 Decls : List_Id;
1885 begin
1886 -- If the current unit is a package body, locate the visible
1887 -- declarations of the package spec.
1889 if Nkind (U) = N_Package_Body then
1890 U := Unit (Library_Unit (Cunit (Current_Sem_Unit)));
1891 end if;
1893 if Nkind (U) = N_Package_Declaration then
1894 U := Specification (U);
1895 Decls := Visible_Declarations (U);
1897 if No (Decls) then
1898 Decls := New_List;
1899 Set_Visible_Declarations (U, Decls);
1900 end if;
1902 else
1903 Decls := Declarations (U);
1905 if No (Decls) then
1906 Decls := New_List;
1907 Set_Declarations (U, Decls);
1908 end if;
1909 end if;
1911 return Decls;
1912 end Current_Sem_Unit_Declarations;
1914 -----------------------
1915 -- Duplicate_Subexpr --
1916 -----------------------
1918 function Duplicate_Subexpr
1919 (Exp : Node_Id;
1920 Name_Req : Boolean := False;
1921 Renaming_Req : Boolean := False) return Node_Id
1923 begin
1924 Remove_Side_Effects (Exp, Name_Req, Renaming_Req);
1925 return New_Copy_Tree (Exp);
1926 end Duplicate_Subexpr;
1928 ---------------------------------
1929 -- Duplicate_Subexpr_No_Checks --
1930 ---------------------------------
1932 function Duplicate_Subexpr_No_Checks
1933 (Exp : Node_Id;
1934 Name_Req : Boolean := False;
1935 Renaming_Req : Boolean := False;
1936 Related_Id : Entity_Id := Empty;
1937 Is_Low_Bound : Boolean := False;
1938 Is_High_Bound : Boolean := False) return Node_Id
1940 New_Exp : Node_Id;
1942 begin
1943 Remove_Side_Effects
1944 (Exp => Exp,
1945 Name_Req => Name_Req,
1946 Renaming_Req => Renaming_Req,
1947 Related_Id => Related_Id,
1948 Is_Low_Bound => Is_Low_Bound,
1949 Is_High_Bound => Is_High_Bound);
1951 New_Exp := New_Copy_Tree (Exp);
1952 Remove_Checks (New_Exp);
1953 return New_Exp;
1954 end Duplicate_Subexpr_No_Checks;
1956 -----------------------------------
1957 -- Duplicate_Subexpr_Move_Checks --
1958 -----------------------------------
1960 function Duplicate_Subexpr_Move_Checks
1961 (Exp : Node_Id;
1962 Name_Req : Boolean := False;
1963 Renaming_Req : Boolean := False) return Node_Id
1965 New_Exp : Node_Id;
1967 begin
1968 Remove_Side_Effects (Exp, Name_Req, Renaming_Req);
1969 New_Exp := New_Copy_Tree (Exp);
1970 Remove_Checks (Exp);
1971 return New_Exp;
1972 end Duplicate_Subexpr_Move_Checks;
1974 --------------------
1975 -- Ensure_Defined --
1976 --------------------
1978 procedure Ensure_Defined (Typ : Entity_Id; N : Node_Id) is
1979 IR : Node_Id;
1981 begin
1982 -- An itype reference must only be created if this is a local itype, so
1983 -- that gigi can elaborate it on the proper objstack.
1985 if Is_Itype (Typ) and then Scope (Typ) = Current_Scope then
1986 IR := Make_Itype_Reference (Sloc (N));
1987 Set_Itype (IR, Typ);
1988 Insert_Action (N, IR);
1989 end if;
1990 end Ensure_Defined;
1992 --------------------
1993 -- Entry_Names_OK --
1994 --------------------
1996 function Entry_Names_OK return Boolean is
1997 begin
1998 return
1999 not Restricted_Profile
2000 and then not Global_Discard_Names
2001 and then not Restriction_Active (No_Implicit_Heap_Allocations)
2002 and then not Restriction_Active (No_Local_Allocators);
2003 end Entry_Names_OK;
2005 -------------------
2006 -- Evaluate_Name --
2007 -------------------
2009 procedure Evaluate_Name (Nam : Node_Id) is
2010 K : constant Node_Kind := Nkind (Nam);
2012 begin
2013 -- For an explicit dereference, we simply force the evaluation of the
2014 -- name expression. The dereference provides a value that is the address
2015 -- for the renamed object, and it is precisely this value that we want
2016 -- to preserve.
2018 if K = N_Explicit_Dereference then
2019 Force_Evaluation (Prefix (Nam));
2021 -- For a selected component, we simply evaluate the prefix
2023 elsif K = N_Selected_Component then
2024 Evaluate_Name (Prefix (Nam));
2026 -- For an indexed component, or an attribute reference, we evaluate the
2027 -- prefix, which is itself a name, recursively, and then force the
2028 -- evaluation of all the subscripts (or attribute expressions).
2030 elsif Nkind_In (K, N_Indexed_Component, N_Attribute_Reference) then
2031 Evaluate_Name (Prefix (Nam));
2033 declare
2034 E : Node_Id;
2036 begin
2037 E := First (Expressions (Nam));
2038 while Present (E) loop
2039 Force_Evaluation (E);
2041 if Original_Node (E) /= E then
2042 Set_Do_Range_Check (E, Do_Range_Check (Original_Node (E)));
2043 end if;
2045 Next (E);
2046 end loop;
2047 end;
2049 -- For a slice, we evaluate the prefix, as for the indexed component
2050 -- case and then, if there is a range present, either directly or as the
2051 -- constraint of a discrete subtype indication, we evaluate the two
2052 -- bounds of this range.
2054 elsif K = N_Slice then
2055 Evaluate_Name (Prefix (Nam));
2056 Evaluate_Slice_Bounds (Nam);
2058 -- For a type conversion, the expression of the conversion must be the
2059 -- name of an object, and we simply need to evaluate this name.
2061 elsif K = N_Type_Conversion then
2062 Evaluate_Name (Expression (Nam));
2064 -- For a function call, we evaluate the call
2066 elsif K = N_Function_Call then
2067 Force_Evaluation (Nam);
2069 -- The remaining cases are direct name, operator symbol and character
2070 -- literal. In all these cases, we do nothing, since we want to
2071 -- reevaluate each time the renamed object is used.
2073 else
2074 return;
2075 end if;
2076 end Evaluate_Name;
2078 ---------------------------
2079 -- Evaluate_Slice_Bounds --
2080 ---------------------------
2082 procedure Evaluate_Slice_Bounds (Slice : Node_Id) is
2083 DR : constant Node_Id := Discrete_Range (Slice);
2084 Constr : Node_Id;
2085 Rexpr : Node_Id;
2087 begin
2088 if Nkind (DR) = N_Range then
2089 Force_Evaluation (Low_Bound (DR));
2090 Force_Evaluation (High_Bound (DR));
2092 elsif Nkind (DR) = N_Subtype_Indication then
2093 Constr := Constraint (DR);
2095 if Nkind (Constr) = N_Range_Constraint then
2096 Rexpr := Range_Expression (Constr);
2098 Force_Evaluation (Low_Bound (Rexpr));
2099 Force_Evaluation (High_Bound (Rexpr));
2100 end if;
2101 end if;
2102 end Evaluate_Slice_Bounds;
2104 ---------------------
2105 -- Evolve_And_Then --
2106 ---------------------
2108 procedure Evolve_And_Then (Cond : in out Node_Id; Cond1 : Node_Id) is
2109 begin
2110 if No (Cond) then
2111 Cond := Cond1;
2112 else
2113 Cond :=
2114 Make_And_Then (Sloc (Cond1),
2115 Left_Opnd => Cond,
2116 Right_Opnd => Cond1);
2117 end if;
2118 end Evolve_And_Then;
2120 --------------------
2121 -- Evolve_Or_Else --
2122 --------------------
2124 procedure Evolve_Or_Else (Cond : in out Node_Id; Cond1 : Node_Id) is
2125 begin
2126 if No (Cond) then
2127 Cond := Cond1;
2128 else
2129 Cond :=
2130 Make_Or_Else (Sloc (Cond1),
2131 Left_Opnd => Cond,
2132 Right_Opnd => Cond1);
2133 end if;
2134 end Evolve_Or_Else;
2136 -----------------------------------------
2137 -- Expand_Static_Predicates_In_Choices --
2138 -----------------------------------------
2140 procedure Expand_Static_Predicates_In_Choices (N : Node_Id) is
2141 pragma Assert (Nkind_In (N, N_Case_Statement_Alternative, N_Variant));
2143 Choices : constant List_Id := Discrete_Choices (N);
2145 Choice : Node_Id;
2146 Next_C : Node_Id;
2147 P : Node_Id;
2148 C : Node_Id;
2150 begin
2151 Choice := First (Choices);
2152 while Present (Choice) loop
2153 Next_C := Next (Choice);
2155 -- Check for name of subtype with static predicate
2157 if Is_Entity_Name (Choice)
2158 and then Is_Type (Entity (Choice))
2159 and then Has_Predicates (Entity (Choice))
2160 then
2161 -- Loop through entries in predicate list, converting to choices
2162 -- and inserting in the list before the current choice. Note that
2163 -- if the list is empty, corresponding to a False predicate, then
2164 -- no choices are inserted.
2166 P := First (Static_Discrete_Predicate (Entity (Choice)));
2167 while Present (P) loop
2169 -- If low bound and high bounds are equal, copy simple choice
2171 if Expr_Value (Low_Bound (P)) = Expr_Value (High_Bound (P)) then
2172 C := New_Copy (Low_Bound (P));
2174 -- Otherwise copy a range
2176 else
2177 C := New_Copy (P);
2178 end if;
2180 -- Change Sloc to referencing choice (rather than the Sloc of
2181 -- the predicate declaration element itself).
2183 Set_Sloc (C, Sloc (Choice));
2184 Insert_Before (Choice, C);
2185 Next (P);
2186 end loop;
2188 -- Delete the predicated entry
2190 Remove (Choice);
2191 end if;
2193 -- Move to next choice to check
2195 Choice := Next_C;
2196 end loop;
2197 end Expand_Static_Predicates_In_Choices;
2199 ------------------------------
2200 -- Expand_Subtype_From_Expr --
2201 ------------------------------
2203 -- This function is applicable for both static and dynamic allocation of
2204 -- objects which are constrained by an initial expression. Basically it
2205 -- transforms an unconstrained subtype indication into a constrained one.
2207 -- The expression may also be transformed in certain cases in order to
2208 -- avoid multiple evaluation. In the static allocation case, the general
2209 -- scheme is:
2211 -- Val : T := Expr;
2213 -- is transformed into
2215 -- Val : Constrained_Subtype_of_T := Maybe_Modified_Expr;
2217 -- Here are the main cases :
2219 -- <if Expr is a Slice>
2220 -- Val : T ([Index_Subtype (Expr)]) := Expr;
2222 -- <elsif Expr is a String Literal>
2223 -- Val : T (T'First .. T'First + Length (string literal) - 1) := Expr;
2225 -- <elsif Expr is Constrained>
2226 -- subtype T is Type_Of_Expr
2227 -- Val : T := Expr;
2229 -- <elsif Expr is an entity_name>
2230 -- Val : T (constraints taken from Expr) := Expr;
2232 -- <else>
2233 -- type Axxx is access all T;
2234 -- Rval : Axxx := Expr'ref;
2235 -- Val : T (constraints taken from Rval) := Rval.all;
2237 -- ??? note: when the Expression is allocated in the secondary stack
2238 -- we could use it directly instead of copying it by declaring
2239 -- Val : T (...) renames Rval.all
2241 procedure Expand_Subtype_From_Expr
2242 (N : Node_Id;
2243 Unc_Type : Entity_Id;
2244 Subtype_Indic : Node_Id;
2245 Exp : Node_Id;
2246 Related_Id : Entity_Id := Empty)
2248 Loc : constant Source_Ptr := Sloc (N);
2249 Exp_Typ : constant Entity_Id := Etype (Exp);
2250 T : Entity_Id;
2252 begin
2253 -- In general we cannot build the subtype if expansion is disabled,
2254 -- because internal entities may not have been defined. However, to
2255 -- avoid some cascaded errors, we try to continue when the expression is
2256 -- an array (or string), because it is safe to compute the bounds. It is
2257 -- in fact required to do so even in a generic context, because there
2258 -- may be constants that depend on the bounds of a string literal, both
2259 -- standard string types and more generally arrays of characters.
2261 -- In GNATprove mode, these extra subtypes are not needed
2263 if GNATprove_Mode then
2264 return;
2265 end if;
2267 if not Expander_Active
2268 and then (No (Etype (Exp)) or else not Is_String_Type (Etype (Exp)))
2269 then
2270 return;
2271 end if;
2273 if Nkind (Exp) = N_Slice then
2274 declare
2275 Slice_Type : constant Entity_Id := Etype (First_Index (Exp_Typ));
2277 begin
2278 Rewrite (Subtype_Indic,
2279 Make_Subtype_Indication (Loc,
2280 Subtype_Mark => New_Occurrence_Of (Unc_Type, Loc),
2281 Constraint =>
2282 Make_Index_Or_Discriminant_Constraint (Loc,
2283 Constraints => New_List
2284 (New_Occurrence_Of (Slice_Type, Loc)))));
2286 -- This subtype indication may be used later for constraint checks
2287 -- we better make sure that if a variable was used as a bound of
2288 -- of the original slice, its value is frozen.
2290 Evaluate_Slice_Bounds (Exp);
2291 end;
2293 elsif Ekind (Exp_Typ) = E_String_Literal_Subtype then
2294 Rewrite (Subtype_Indic,
2295 Make_Subtype_Indication (Loc,
2296 Subtype_Mark => New_Occurrence_Of (Unc_Type, Loc),
2297 Constraint =>
2298 Make_Index_Or_Discriminant_Constraint (Loc,
2299 Constraints => New_List (
2300 Make_Literal_Range (Loc,
2301 Literal_Typ => Exp_Typ)))));
2303 -- If the type of the expression is an internally generated type it
2304 -- may not be necessary to create a new subtype. However there are two
2305 -- exceptions: references to the current instances, and aliased array
2306 -- object declarations for which the backend needs to create a template.
2308 elsif Is_Constrained (Exp_Typ)
2309 and then not Is_Class_Wide_Type (Unc_Type)
2310 and then
2311 (Nkind (N) /= N_Object_Declaration
2312 or else not Is_Entity_Name (Expression (N))
2313 or else not Comes_From_Source (Entity (Expression (N)))
2314 or else not Is_Array_Type (Exp_Typ)
2315 or else not Aliased_Present (N))
2316 then
2317 if Is_Itype (Exp_Typ) then
2319 -- Within an initialization procedure, a selected component
2320 -- denotes a component of the enclosing record, and it appears as
2321 -- an actual in a call to its own initialization procedure. If
2322 -- this component depends on the outer discriminant, we must
2323 -- generate the proper actual subtype for it.
2325 if Nkind (Exp) = N_Selected_Component
2326 and then Within_Init_Proc
2327 then
2328 declare
2329 Decl : constant Node_Id :=
2330 Build_Actual_Subtype_Of_Component (Exp_Typ, Exp);
2331 begin
2332 if Present (Decl) then
2333 Insert_Action (N, Decl);
2334 T := Defining_Identifier (Decl);
2335 else
2336 T := Exp_Typ;
2337 end if;
2338 end;
2340 -- No need to generate a new subtype
2342 else
2343 T := Exp_Typ;
2344 end if;
2346 else
2347 T := Make_Temporary (Loc, 'T');
2349 Insert_Action (N,
2350 Make_Subtype_Declaration (Loc,
2351 Defining_Identifier => T,
2352 Subtype_Indication => New_Occurrence_Of (Exp_Typ, Loc)));
2354 -- This type is marked as an itype even though it has an explicit
2355 -- declaration since otherwise Is_Generic_Actual_Type can get
2356 -- set, resulting in the generation of spurious errors. (See
2357 -- sem_ch8.Analyze_Package_Renaming and sem_type.covers)
2359 Set_Is_Itype (T);
2360 Set_Associated_Node_For_Itype (T, Exp);
2361 end if;
2363 Rewrite (Subtype_Indic, New_Occurrence_Of (T, Loc));
2365 -- Nothing needs to be done for private types with unknown discriminants
2366 -- if the underlying type is not an unconstrained composite type or it
2367 -- is an unchecked union.
2369 elsif Is_Private_Type (Unc_Type)
2370 and then Has_Unknown_Discriminants (Unc_Type)
2371 and then (not Is_Composite_Type (Underlying_Type (Unc_Type))
2372 or else Is_Constrained (Underlying_Type (Unc_Type))
2373 or else Is_Unchecked_Union (Underlying_Type (Unc_Type)))
2374 then
2375 null;
2377 -- Case of derived type with unknown discriminants where the parent type
2378 -- also has unknown discriminants.
2380 elsif Is_Record_Type (Unc_Type)
2381 and then not Is_Class_Wide_Type (Unc_Type)
2382 and then Has_Unknown_Discriminants (Unc_Type)
2383 and then Has_Unknown_Discriminants (Underlying_Type (Unc_Type))
2384 then
2385 -- Nothing to be done if no underlying record view available
2387 if No (Underlying_Record_View (Unc_Type)) then
2388 null;
2390 -- Otherwise use the Underlying_Record_View to create the proper
2391 -- constrained subtype for an object of a derived type with unknown
2392 -- discriminants.
2394 else
2395 Remove_Side_Effects (Exp);
2396 Rewrite (Subtype_Indic,
2397 Make_Subtype_From_Expr (Exp, Underlying_Record_View (Unc_Type)));
2398 end if;
2400 -- Renamings of class-wide interface types require no equivalent
2401 -- constrained type declarations because we only need to reference
2402 -- the tag component associated with the interface. The same is
2403 -- presumably true for class-wide types in general, so this test
2404 -- is broadened to include all class-wide renamings, which also
2405 -- avoids cases of unbounded recursion in Remove_Side_Effects.
2406 -- (Is this really correct, or are there some cases of class-wide
2407 -- renamings that require action in this procedure???)
2409 elsif Present (N)
2410 and then Nkind (N) = N_Object_Renaming_Declaration
2411 and then Is_Class_Wide_Type (Unc_Type)
2412 then
2413 null;
2415 -- In Ada 95 nothing to be done if the type of the expression is limited
2416 -- because in this case the expression cannot be copied, and its use can
2417 -- only be by reference.
2419 -- In Ada 2005 the context can be an object declaration whose expression
2420 -- is a function that returns in place. If the nominal subtype has
2421 -- unknown discriminants, the call still provides constraints on the
2422 -- object, and we have to create an actual subtype from it.
2424 -- If the type is class-wide, the expression is dynamically tagged and
2425 -- we do not create an actual subtype either. Ditto for an interface.
2426 -- For now this applies only if the type is immutably limited, and the
2427 -- function being called is build-in-place. This will have to be revised
2428 -- when build-in-place functions are generalized to other types.
2430 elsif Is_Limited_View (Exp_Typ)
2431 and then
2432 (Is_Class_Wide_Type (Exp_Typ)
2433 or else Is_Interface (Exp_Typ)
2434 or else not Has_Unknown_Discriminants (Exp_Typ)
2435 or else not Is_Composite_Type (Unc_Type))
2436 then
2437 null;
2439 -- For limited objects initialized with build in place function calls,
2440 -- nothing to be done; otherwise we prematurely introduce an N_Reference
2441 -- node in the expression initializing the object, which breaks the
2442 -- circuitry that detects and adds the additional arguments to the
2443 -- called function.
2445 elsif Is_Build_In_Place_Function_Call (Exp) then
2446 null;
2448 else
2449 Remove_Side_Effects (Exp);
2450 Rewrite (Subtype_Indic,
2451 Make_Subtype_From_Expr (Exp, Unc_Type, Related_Id));
2452 end if;
2453 end Expand_Subtype_From_Expr;
2455 ----------------------
2456 -- Finalize_Address --
2457 ----------------------
2459 function Finalize_Address (Typ : Entity_Id) return Entity_Id is
2460 Utyp : Entity_Id := Typ;
2462 begin
2463 -- Handle protected class-wide or task class-wide types
2465 if Is_Class_Wide_Type (Utyp) then
2466 if Is_Concurrent_Type (Root_Type (Utyp)) then
2467 Utyp := Root_Type (Utyp);
2469 elsif Is_Private_Type (Root_Type (Utyp))
2470 and then Present (Full_View (Root_Type (Utyp)))
2471 and then Is_Concurrent_Type (Full_View (Root_Type (Utyp)))
2472 then
2473 Utyp := Full_View (Root_Type (Utyp));
2474 end if;
2475 end if;
2477 -- Handle private types
2479 if Is_Private_Type (Utyp) and then Present (Full_View (Utyp)) then
2480 Utyp := Full_View (Utyp);
2481 end if;
2483 -- Handle protected and task types
2485 if Is_Concurrent_Type (Utyp)
2486 and then Present (Corresponding_Record_Type (Utyp))
2487 then
2488 Utyp := Corresponding_Record_Type (Utyp);
2489 end if;
2491 Utyp := Underlying_Type (Base_Type (Utyp));
2493 -- Deal with untagged derivation of private views. If the parent is
2494 -- now known to be protected, the finalization routine is the one
2495 -- defined on the corresponding record of the ancestor (corresponding
2496 -- records do not automatically inherit operations, but maybe they
2497 -- should???)
2499 if Is_Untagged_Derivation (Typ) then
2500 if Is_Protected_Type (Typ) then
2501 Utyp := Corresponding_Record_Type (Root_Type (Base_Type (Typ)));
2503 else
2504 Utyp := Underlying_Type (Root_Type (Base_Type (Typ)));
2506 if Is_Protected_Type (Utyp) then
2507 Utyp := Corresponding_Record_Type (Utyp);
2508 end if;
2509 end if;
2510 end if;
2512 -- If the underlying_type is a subtype, we are dealing with the
2513 -- completion of a private type. We need to access the base type and
2514 -- generate a conversion to it.
2516 if Utyp /= Base_Type (Utyp) then
2517 pragma Assert (Is_Private_Type (Typ));
2519 Utyp := Base_Type (Utyp);
2520 end if;
2522 -- When dealing with an internally built full view for a type with
2523 -- unknown discriminants, use the original record type.
2525 if Is_Underlying_Record_View (Utyp) then
2526 Utyp := Etype (Utyp);
2527 end if;
2529 return TSS (Utyp, TSS_Finalize_Address);
2530 end Finalize_Address;
2532 ------------------------
2533 -- Find_Interface_ADT --
2534 ------------------------
2536 function Find_Interface_ADT
2537 (T : Entity_Id;
2538 Iface : Entity_Id) return Elmt_Id
2540 ADT : Elmt_Id;
2541 Typ : Entity_Id := T;
2543 begin
2544 pragma Assert (Is_Interface (Iface));
2546 -- Handle private types
2548 if Has_Private_Declaration (Typ) and then Present (Full_View (Typ)) then
2549 Typ := Full_View (Typ);
2550 end if;
2552 -- Handle access types
2554 if Is_Access_Type (Typ) then
2555 Typ := Designated_Type (Typ);
2556 end if;
2558 -- Handle task and protected types implementing interfaces
2560 if Is_Concurrent_Type (Typ) then
2561 Typ := Corresponding_Record_Type (Typ);
2562 end if;
2564 pragma Assert
2565 (not Is_Class_Wide_Type (Typ)
2566 and then Ekind (Typ) /= E_Incomplete_Type);
2568 if Is_Ancestor (Iface, Typ, Use_Full_View => True) then
2569 return First_Elmt (Access_Disp_Table (Typ));
2571 else
2572 ADT := Next_Elmt (Next_Elmt (First_Elmt (Access_Disp_Table (Typ))));
2573 while Present (ADT)
2574 and then Present (Related_Type (Node (ADT)))
2575 and then Related_Type (Node (ADT)) /= Iface
2576 and then not Is_Ancestor (Iface, Related_Type (Node (ADT)),
2577 Use_Full_View => True)
2578 loop
2579 Next_Elmt (ADT);
2580 end loop;
2582 pragma Assert (Present (Related_Type (Node (ADT))));
2583 return ADT;
2584 end if;
2585 end Find_Interface_ADT;
2587 ------------------------
2588 -- Find_Interface_Tag --
2589 ------------------------
2591 function Find_Interface_Tag
2592 (T : Entity_Id;
2593 Iface : Entity_Id) return Entity_Id
2595 AI_Tag : Entity_Id;
2596 Found : Boolean := False;
2597 Typ : Entity_Id := T;
2599 procedure Find_Tag (Typ : Entity_Id);
2600 -- Internal subprogram used to recursively climb to the ancestors
2602 --------------
2603 -- Find_Tag --
2604 --------------
2606 procedure Find_Tag (Typ : Entity_Id) is
2607 AI_Elmt : Elmt_Id;
2608 AI : Node_Id;
2610 begin
2611 -- This routine does not handle the case in which the interface is an
2612 -- ancestor of Typ. That case is handled by the enclosing subprogram.
2614 pragma Assert (Typ /= Iface);
2616 -- Climb to the root type handling private types
2618 if Present (Full_View (Etype (Typ))) then
2619 if Full_View (Etype (Typ)) /= Typ then
2620 Find_Tag (Full_View (Etype (Typ)));
2621 end if;
2623 elsif Etype (Typ) /= Typ then
2624 Find_Tag (Etype (Typ));
2625 end if;
2627 -- Traverse the list of interfaces implemented by the type
2629 if not Found
2630 and then Present (Interfaces (Typ))
2631 and then not (Is_Empty_Elmt_List (Interfaces (Typ)))
2632 then
2633 -- Skip the tag associated with the primary table
2635 pragma Assert (Etype (First_Tag_Component (Typ)) = RTE (RE_Tag));
2636 AI_Tag := Next_Tag_Component (First_Tag_Component (Typ));
2637 pragma Assert (Present (AI_Tag));
2639 AI_Elmt := First_Elmt (Interfaces (Typ));
2640 while Present (AI_Elmt) loop
2641 AI := Node (AI_Elmt);
2643 if AI = Iface
2644 or else Is_Ancestor (Iface, AI, Use_Full_View => True)
2645 then
2646 Found := True;
2647 return;
2648 end if;
2650 AI_Tag := Next_Tag_Component (AI_Tag);
2651 Next_Elmt (AI_Elmt);
2652 end loop;
2653 end if;
2654 end Find_Tag;
2656 -- Start of processing for Find_Interface_Tag
2658 begin
2659 pragma Assert (Is_Interface (Iface));
2661 -- Handle access types
2663 if Is_Access_Type (Typ) then
2664 Typ := Designated_Type (Typ);
2665 end if;
2667 -- Handle class-wide types
2669 if Is_Class_Wide_Type (Typ) then
2670 Typ := Root_Type (Typ);
2671 end if;
2673 -- Handle private types
2675 if Has_Private_Declaration (Typ) and then Present (Full_View (Typ)) then
2676 Typ := Full_View (Typ);
2677 end if;
2679 -- Handle entities from the limited view
2681 if Ekind (Typ) = E_Incomplete_Type then
2682 pragma Assert (Present (Non_Limited_View (Typ)));
2683 Typ := Non_Limited_View (Typ);
2684 end if;
2686 -- Handle task and protected types implementing interfaces
2688 if Is_Concurrent_Type (Typ) then
2689 Typ := Corresponding_Record_Type (Typ);
2690 end if;
2692 -- If the interface is an ancestor of the type, then it shared the
2693 -- primary dispatch table.
2695 if Is_Ancestor (Iface, Typ, Use_Full_View => True) then
2696 pragma Assert (Etype (First_Tag_Component (Typ)) = RTE (RE_Tag));
2697 return First_Tag_Component (Typ);
2699 -- Otherwise we need to search for its associated tag component
2701 else
2702 Find_Tag (Typ);
2703 pragma Assert (Found);
2704 return AI_Tag;
2705 end if;
2706 end Find_Interface_Tag;
2708 ---------------------------
2709 -- Find_Optional_Prim_Op --
2710 ---------------------------
2712 function Find_Optional_Prim_Op
2713 (T : Entity_Id; Name : Name_Id) return Entity_Id
2715 Prim : Elmt_Id;
2716 Typ : Entity_Id := T;
2717 Op : Entity_Id;
2719 begin
2720 if Is_Class_Wide_Type (Typ) then
2721 Typ := Root_Type (Typ);
2722 end if;
2724 Typ := Underlying_Type (Typ);
2726 -- Loop through primitive operations
2728 Prim := First_Elmt (Primitive_Operations (Typ));
2729 while Present (Prim) loop
2730 Op := Node (Prim);
2732 -- We can retrieve primitive operations by name if it is an internal
2733 -- name. For equality we must check that both of its operands have
2734 -- the same type, to avoid confusion with user-defined equalities
2735 -- than may have a non-symmetric signature.
2737 exit when Chars (Op) = Name
2738 and then
2739 (Name /= Name_Op_Eq
2740 or else Etype (First_Formal (Op)) = Etype (Last_Formal (Op)));
2742 Next_Elmt (Prim);
2743 end loop;
2745 return Node (Prim); -- Empty if not found
2746 end Find_Optional_Prim_Op;
2748 ---------------------------
2749 -- Find_Optional_Prim_Op --
2750 ---------------------------
2752 function Find_Optional_Prim_Op
2753 (T : Entity_Id;
2754 Name : TSS_Name_Type) return Entity_Id
2756 Inher_Op : Entity_Id := Empty;
2757 Own_Op : Entity_Id := Empty;
2758 Prim_Elmt : Elmt_Id;
2759 Prim_Id : Entity_Id;
2760 Typ : Entity_Id := T;
2762 begin
2763 if Is_Class_Wide_Type (Typ) then
2764 Typ := Root_Type (Typ);
2765 end if;
2767 Typ := Underlying_Type (Typ);
2769 -- This search is based on the assertion that the dispatching version
2770 -- of the TSS routine always precedes the real primitive.
2772 Prim_Elmt := First_Elmt (Primitive_Operations (Typ));
2773 while Present (Prim_Elmt) loop
2774 Prim_Id := Node (Prim_Elmt);
2776 if Is_TSS (Prim_Id, Name) then
2777 if Present (Alias (Prim_Id)) then
2778 Inher_Op := Prim_Id;
2779 else
2780 Own_Op := Prim_Id;
2781 end if;
2782 end if;
2784 Next_Elmt (Prim_Elmt);
2785 end loop;
2787 if Present (Own_Op) then
2788 return Own_Op;
2789 elsif Present (Inher_Op) then
2790 return Inher_Op;
2791 else
2792 return Empty;
2793 end if;
2794 end Find_Optional_Prim_Op;
2796 ------------------
2797 -- Find_Prim_Op --
2798 ------------------
2800 function Find_Prim_Op
2801 (T : Entity_Id; Name : Name_Id) return Entity_Id
2803 Result : constant Entity_Id := Find_Optional_Prim_Op (T, Name);
2804 begin
2805 if No (Result) then
2806 raise Program_Error;
2807 end if;
2809 return Result;
2810 end Find_Prim_Op;
2812 ------------------
2813 -- Find_Prim_Op --
2814 ------------------
2816 function Find_Prim_Op
2817 (T : Entity_Id;
2818 Name : TSS_Name_Type) return Entity_Id
2820 Result : constant Entity_Id := Find_Optional_Prim_Op (T, Name);
2821 begin
2822 if No (Result) then
2823 raise Program_Error;
2824 end if;
2826 return Result;
2827 end Find_Prim_Op;
2829 ----------------------------
2830 -- Find_Protection_Object --
2831 ----------------------------
2833 function Find_Protection_Object (Scop : Entity_Id) return Entity_Id is
2834 S : Entity_Id;
2836 begin
2837 S := Scop;
2838 while Present (S) loop
2839 if Ekind_In (S, E_Entry, E_Entry_Family, E_Function, E_Procedure)
2840 and then Present (Protection_Object (S))
2841 then
2842 return Protection_Object (S);
2843 end if;
2845 S := Scope (S);
2846 end loop;
2848 -- If we do not find a Protection object in the scope chain, then
2849 -- something has gone wrong, most likely the object was never created.
2851 raise Program_Error;
2852 end Find_Protection_Object;
2854 --------------------------
2855 -- Find_Protection_Type --
2856 --------------------------
2858 function Find_Protection_Type (Conc_Typ : Entity_Id) return Entity_Id is
2859 Comp : Entity_Id;
2860 Typ : Entity_Id := Conc_Typ;
2862 begin
2863 if Is_Concurrent_Type (Typ) then
2864 Typ := Corresponding_Record_Type (Typ);
2865 end if;
2867 -- Since restriction violations are not considered serious errors, the
2868 -- expander remains active, but may leave the corresponding record type
2869 -- malformed. In such cases, component _object is not available so do
2870 -- not look for it.
2872 if not Analyzed (Typ) then
2873 return Empty;
2874 end if;
2876 Comp := First_Component (Typ);
2877 while Present (Comp) loop
2878 if Chars (Comp) = Name_uObject then
2879 return Base_Type (Etype (Comp));
2880 end if;
2882 Next_Component (Comp);
2883 end loop;
2885 -- The corresponding record of a protected type should always have an
2886 -- _object field.
2888 raise Program_Error;
2889 end Find_Protection_Type;
2891 -----------------------
2892 -- Find_Hook_Context --
2893 -----------------------
2895 function Find_Hook_Context (N : Node_Id) return Node_Id is
2896 Par : Node_Id;
2897 Top : Node_Id;
2899 Wrapped_Node : Node_Id;
2900 -- Note: if we are in a transient scope, we want to reuse it as
2901 -- the context for actions insertion, if possible. But if N is itself
2902 -- part of the stored actions for the current transient scope,
2903 -- then we need to insert at the appropriate (inner) location in
2904 -- the not as an action on Node_To_Be_Wrapped.
2906 In_Cond_Expr : constant Boolean := Within_Case_Or_If_Expression (N);
2908 begin
2909 -- When the node is inside a case/if expression, the lifetime of any
2910 -- temporary controlled object is extended. Find a suitable insertion
2911 -- node by locating the topmost case or if expressions.
2913 if In_Cond_Expr then
2914 Par := N;
2915 Top := N;
2916 while Present (Par) loop
2917 if Nkind_In (Original_Node (Par), N_Case_Expression,
2918 N_If_Expression)
2919 then
2920 Top := Par;
2922 -- Prevent the search from going too far
2924 elsif Is_Body_Or_Package_Declaration (Par) then
2925 exit;
2926 end if;
2928 Par := Parent (Par);
2929 end loop;
2931 -- The topmost case or if expression is now recovered, but it may
2932 -- still not be the correct place to add generated code. Climb to
2933 -- find a parent that is part of a declarative or statement list,
2934 -- and is not a list of actuals in a call.
2936 Par := Top;
2937 while Present (Par) loop
2938 if Is_List_Member (Par)
2939 and then not Nkind_In (Par, N_Component_Association,
2940 N_Discriminant_Association,
2941 N_Parameter_Association,
2942 N_Pragma_Argument_Association)
2943 and then not Nkind_In
2944 (Parent (Par), N_Function_Call,
2945 N_Procedure_Call_Statement,
2946 N_Entry_Call_Statement)
2948 then
2949 return Par;
2951 -- Prevent the search from going too far
2953 elsif Is_Body_Or_Package_Declaration (Par) then
2954 exit;
2955 end if;
2957 Par := Parent (Par);
2958 end loop;
2960 return Par;
2962 else
2963 Par := N;
2964 while Present (Par) loop
2966 -- Keep climbing past various operators
2968 if Nkind (Parent (Par)) in N_Op
2969 or else Nkind_In (Parent (Par), N_And_Then, N_Or_Else)
2970 then
2971 Par := Parent (Par);
2972 else
2973 exit;
2974 end if;
2975 end loop;
2977 Top := Par;
2979 -- The node may be located in a pragma in which case return the
2980 -- pragma itself:
2982 -- pragma Precondition (... and then Ctrl_Func_Call ...);
2984 -- Similar case occurs when the node is related to an object
2985 -- declaration or assignment:
2987 -- Obj [: Some_Typ] := ... and then Ctrl_Func_Call ...;
2989 -- Another case to consider is when the node is part of a return
2990 -- statement:
2992 -- return ... and then Ctrl_Func_Call ...;
2994 -- Another case is when the node acts as a formal in a procedure
2995 -- call statement:
2997 -- Proc (... and then Ctrl_Func_Call ...);
2999 if Scope_Is_Transient then
3000 Wrapped_Node := Node_To_Be_Wrapped;
3001 else
3002 Wrapped_Node := Empty;
3003 end if;
3005 while Present (Par) loop
3006 if Par = Wrapped_Node
3007 or else Nkind_In (Par, N_Assignment_Statement,
3008 N_Object_Declaration,
3009 N_Pragma,
3010 N_Procedure_Call_Statement,
3011 N_Simple_Return_Statement)
3012 then
3013 return Par;
3015 -- Prevent the search from going too far
3017 elsif Is_Body_Or_Package_Declaration (Par) then
3018 exit;
3019 end if;
3021 Par := Parent (Par);
3022 end loop;
3024 -- Return the topmost short circuit operator
3026 return Top;
3027 end if;
3028 end Find_Hook_Context;
3030 ------------------------------
3031 -- Following_Address_Clause --
3032 ------------------------------
3034 function Following_Address_Clause (D : Node_Id) return Node_Id is
3035 Id : constant Entity_Id := Defining_Identifier (D);
3036 Result : Node_Id;
3037 Par : Node_Id;
3039 function Check_Decls (D : Node_Id) return Node_Id;
3040 -- This internal function differs from the main function in that it
3041 -- gets called to deal with a following package private part, and
3042 -- it checks declarations starting with D (the main function checks
3043 -- declarations following D). If D is Empty, then Empty is returned.
3045 -----------------
3046 -- Check_Decls --
3047 -----------------
3049 function Check_Decls (D : Node_Id) return Node_Id is
3050 Decl : Node_Id;
3052 begin
3053 Decl := D;
3054 while Present (Decl) loop
3055 if Nkind (Decl) = N_At_Clause
3056 and then Chars (Identifier (Decl)) = Chars (Id)
3057 then
3058 return Decl;
3060 elsif Nkind (Decl) = N_Attribute_Definition_Clause
3061 and then Chars (Decl) = Name_Address
3062 and then Chars (Name (Decl)) = Chars (Id)
3063 then
3064 return Decl;
3065 end if;
3067 Next (Decl);
3068 end loop;
3070 -- Otherwise not found, return Empty
3072 return Empty;
3073 end Check_Decls;
3075 -- Start of processing for Following_Address_Clause
3077 begin
3078 -- If parser detected no address clause for the identifier in question,
3079 -- then the answer is a quick NO, without the need for a search.
3081 if not Get_Name_Table_Boolean1 (Chars (Id)) then
3082 return Empty;
3083 end if;
3085 -- Otherwise search current declarative unit
3087 Result := Check_Decls (Next (D));
3089 if Present (Result) then
3090 return Result;
3091 end if;
3093 -- Check for possible package private part following
3095 Par := Parent (D);
3097 if Nkind (Par) = N_Package_Specification
3098 and then Visible_Declarations (Par) = List_Containing (D)
3099 and then Present (Private_Declarations (Par))
3100 then
3101 -- Private part present, check declarations there
3103 return Check_Decls (First (Private_Declarations (Par)));
3105 else
3106 -- No private part, clause not found, return Empty
3108 return Empty;
3109 end if;
3110 end Following_Address_Clause;
3112 ----------------------
3113 -- Force_Evaluation --
3114 ----------------------
3116 procedure Force_Evaluation
3117 (Exp : Node_Id;
3118 Name_Req : Boolean := False;
3119 Related_Id : Entity_Id := Empty;
3120 Is_Low_Bound : Boolean := False;
3121 Is_High_Bound : Boolean := False)
3123 begin
3124 Remove_Side_Effects
3125 (Exp => Exp,
3126 Name_Req => Name_Req,
3127 Variable_Ref => True,
3128 Renaming_Req => False,
3129 Related_Id => Related_Id,
3130 Is_Low_Bound => Is_Low_Bound,
3131 Is_High_Bound => Is_High_Bound);
3132 end Force_Evaluation;
3134 ---------------------------------
3135 -- Fully_Qualified_Name_String --
3136 ---------------------------------
3138 function Fully_Qualified_Name_String
3139 (E : Entity_Id;
3140 Append_NUL : Boolean := True) return String_Id
3142 procedure Internal_Full_Qualified_Name (E : Entity_Id);
3143 -- Compute recursively the qualified name without NUL at the end, adding
3144 -- it to the currently started string being generated
3146 ----------------------------------
3147 -- Internal_Full_Qualified_Name --
3148 ----------------------------------
3150 procedure Internal_Full_Qualified_Name (E : Entity_Id) is
3151 Ent : Entity_Id;
3153 begin
3154 -- Deal properly with child units
3156 if Nkind (E) = N_Defining_Program_Unit_Name then
3157 Ent := Defining_Identifier (E);
3158 else
3159 Ent := E;
3160 end if;
3162 -- Compute qualification recursively (only "Standard" has no scope)
3164 if Present (Scope (Scope (Ent))) then
3165 Internal_Full_Qualified_Name (Scope (Ent));
3166 Store_String_Char (Get_Char_Code ('.'));
3167 end if;
3169 -- Every entity should have a name except some expanded blocks
3170 -- don't bother about those.
3172 if Chars (Ent) = No_Name then
3173 return;
3174 end if;
3176 -- Generates the entity name in upper case
3178 Get_Decoded_Name_String (Chars (Ent));
3179 Set_All_Upper_Case;
3180 Store_String_Chars (Name_Buffer (1 .. Name_Len));
3181 return;
3182 end Internal_Full_Qualified_Name;
3184 -- Start of processing for Full_Qualified_Name
3186 begin
3187 Start_String;
3188 Internal_Full_Qualified_Name (E);
3190 if Append_NUL then
3191 Store_String_Char (Get_Char_Code (ASCII.NUL));
3192 end if;
3194 return End_String;
3195 end Fully_Qualified_Name_String;
3197 ------------------------
3198 -- Generate_Poll_Call --
3199 ------------------------
3201 procedure Generate_Poll_Call (N : Node_Id) is
3202 begin
3203 -- No poll call if polling not active
3205 if not Polling_Required then
3206 return;
3208 -- Otherwise generate require poll call
3210 else
3211 Insert_Before_And_Analyze (N,
3212 Make_Procedure_Call_Statement (Sloc (N),
3213 Name => New_Occurrence_Of (RTE (RE_Poll), Sloc (N))));
3214 end if;
3215 end Generate_Poll_Call;
3217 ---------------------------------
3218 -- Get_Current_Value_Condition --
3219 ---------------------------------
3221 -- Note: the implementation of this procedure is very closely tied to the
3222 -- implementation of Set_Current_Value_Condition. In the Get procedure, we
3223 -- interpret Current_Value fields set by the Set procedure, so the two
3224 -- procedures need to be closely coordinated.
3226 procedure Get_Current_Value_Condition
3227 (Var : Node_Id;
3228 Op : out Node_Kind;
3229 Val : out Node_Id)
3231 Loc : constant Source_Ptr := Sloc (Var);
3232 Ent : constant Entity_Id := Entity (Var);
3234 procedure Process_Current_Value_Condition
3235 (N : Node_Id;
3236 S : Boolean);
3237 -- N is an expression which holds either True (S = True) or False (S =
3238 -- False) in the condition. This procedure digs out the expression and
3239 -- if it refers to Ent, sets Op and Val appropriately.
3241 -------------------------------------
3242 -- Process_Current_Value_Condition --
3243 -------------------------------------
3245 procedure Process_Current_Value_Condition
3246 (N : Node_Id;
3247 S : Boolean)
3249 Cond : Node_Id;
3250 Prev_Cond : Node_Id;
3251 Sens : Boolean;
3253 begin
3254 Cond := N;
3255 Sens := S;
3257 loop
3258 Prev_Cond := Cond;
3260 -- Deal with NOT operators, inverting sense
3262 while Nkind (Cond) = N_Op_Not loop
3263 Cond := Right_Opnd (Cond);
3264 Sens := not Sens;
3265 end loop;
3267 -- Deal with conversions, qualifications, and expressions with
3268 -- actions.
3270 while Nkind_In (Cond,
3271 N_Type_Conversion,
3272 N_Qualified_Expression,
3273 N_Expression_With_Actions)
3274 loop
3275 Cond := Expression (Cond);
3276 end loop;
3278 exit when Cond = Prev_Cond;
3279 end loop;
3281 -- Deal with AND THEN and AND cases
3283 if Nkind_In (Cond, N_And_Then, N_Op_And) then
3285 -- Don't ever try to invert a condition that is of the form of an
3286 -- AND or AND THEN (since we are not doing sufficiently general
3287 -- processing to allow this).
3289 if Sens = False then
3290 Op := N_Empty;
3291 Val := Empty;
3292 return;
3293 end if;
3295 -- Recursively process AND and AND THEN branches
3297 Process_Current_Value_Condition (Left_Opnd (Cond), True);
3299 if Op /= N_Empty then
3300 return;
3301 end if;
3303 Process_Current_Value_Condition (Right_Opnd (Cond), True);
3304 return;
3306 -- Case of relational operator
3308 elsif Nkind (Cond) in N_Op_Compare then
3309 Op := Nkind (Cond);
3311 -- Invert sense of test if inverted test
3313 if Sens = False then
3314 case Op is
3315 when N_Op_Eq => Op := N_Op_Ne;
3316 when N_Op_Ne => Op := N_Op_Eq;
3317 when N_Op_Lt => Op := N_Op_Ge;
3318 when N_Op_Gt => Op := N_Op_Le;
3319 when N_Op_Le => Op := N_Op_Gt;
3320 when N_Op_Ge => Op := N_Op_Lt;
3321 when others => raise Program_Error;
3322 end case;
3323 end if;
3325 -- Case of entity op value
3327 if Is_Entity_Name (Left_Opnd (Cond))
3328 and then Ent = Entity (Left_Opnd (Cond))
3329 and then Compile_Time_Known_Value (Right_Opnd (Cond))
3330 then
3331 Val := Right_Opnd (Cond);
3333 -- Case of value op entity
3335 elsif Is_Entity_Name (Right_Opnd (Cond))
3336 and then Ent = Entity (Right_Opnd (Cond))
3337 and then Compile_Time_Known_Value (Left_Opnd (Cond))
3338 then
3339 Val := Left_Opnd (Cond);
3341 -- We are effectively swapping operands
3343 case Op is
3344 when N_Op_Eq => null;
3345 when N_Op_Ne => null;
3346 when N_Op_Lt => Op := N_Op_Gt;
3347 when N_Op_Gt => Op := N_Op_Lt;
3348 when N_Op_Le => Op := N_Op_Ge;
3349 when N_Op_Ge => Op := N_Op_Le;
3350 when others => raise Program_Error;
3351 end case;
3353 else
3354 Op := N_Empty;
3355 end if;
3357 return;
3359 elsif Nkind_In (Cond,
3360 N_Type_Conversion,
3361 N_Qualified_Expression,
3362 N_Expression_With_Actions)
3363 then
3364 Cond := Expression (Cond);
3366 -- Case of Boolean variable reference, return as though the
3367 -- reference had said var = True.
3369 else
3370 if Is_Entity_Name (Cond) and then Ent = Entity (Cond) then
3371 Val := New_Occurrence_Of (Standard_True, Sloc (Cond));
3373 if Sens = False then
3374 Op := N_Op_Ne;
3375 else
3376 Op := N_Op_Eq;
3377 end if;
3378 end if;
3379 end if;
3380 end Process_Current_Value_Condition;
3382 -- Start of processing for Get_Current_Value_Condition
3384 begin
3385 Op := N_Empty;
3386 Val := Empty;
3388 -- Immediate return, nothing doing, if this is not an object
3390 if Ekind (Ent) not in Object_Kind then
3391 return;
3392 end if;
3394 -- Otherwise examine current value
3396 declare
3397 CV : constant Node_Id := Current_Value (Ent);
3398 Sens : Boolean;
3399 Stm : Node_Id;
3401 begin
3402 -- If statement. Condition is known true in THEN section, known False
3403 -- in any ELSIF or ELSE part, and unknown outside the IF statement.
3405 if Nkind (CV) = N_If_Statement then
3407 -- Before start of IF statement
3409 if Loc < Sloc (CV) then
3410 return;
3412 -- After end of IF statement
3414 elsif Loc >= Sloc (CV) + Text_Ptr (UI_To_Int (End_Span (CV))) then
3415 return;
3416 end if;
3418 -- At this stage we know that we are within the IF statement, but
3419 -- unfortunately, the tree does not record the SLOC of the ELSE so
3420 -- we cannot use a simple SLOC comparison to distinguish between
3421 -- the then/else statements, so we have to climb the tree.
3423 declare
3424 N : Node_Id;
3426 begin
3427 N := Parent (Var);
3428 while Parent (N) /= CV loop
3429 N := Parent (N);
3431 -- If we fall off the top of the tree, then that's odd, but
3432 -- perhaps it could occur in some error situation, and the
3433 -- safest response is simply to assume that the outcome of
3434 -- the condition is unknown. No point in bombing during an
3435 -- attempt to optimize things.
3437 if No (N) then
3438 return;
3439 end if;
3440 end loop;
3442 -- Now we have N pointing to a node whose parent is the IF
3443 -- statement in question, so now we can tell if we are within
3444 -- the THEN statements.
3446 if Is_List_Member (N)
3447 and then List_Containing (N) = Then_Statements (CV)
3448 then
3449 Sens := True;
3451 -- If the variable reference does not come from source, we
3452 -- cannot reliably tell whether it appears in the else part.
3453 -- In particular, if it appears in generated code for a node
3454 -- that requires finalization, it may be attached to a list
3455 -- that has not been yet inserted into the code. For now,
3456 -- treat it as unknown.
3458 elsif not Comes_From_Source (N) then
3459 return;
3461 -- Otherwise we must be in ELSIF or ELSE part
3463 else
3464 Sens := False;
3465 end if;
3466 end;
3468 -- ELSIF part. Condition is known true within the referenced
3469 -- ELSIF, known False in any subsequent ELSIF or ELSE part,
3470 -- and unknown before the ELSE part or after the IF statement.
3472 elsif Nkind (CV) = N_Elsif_Part then
3474 -- if the Elsif_Part had condition_actions, the elsif has been
3475 -- rewritten as a nested if, and the original elsif_part is
3476 -- detached from the tree, so there is no way to obtain useful
3477 -- information on the current value of the variable.
3478 -- Can this be improved ???
3480 if No (Parent (CV)) then
3481 return;
3482 end if;
3484 Stm := Parent (CV);
3486 -- If the tree has been otherwise rewritten there is nothing
3487 -- else to be done either.
3489 if Nkind (Stm) /= N_If_Statement then
3490 return;
3491 end if;
3493 -- Before start of ELSIF part
3495 if Loc < Sloc (CV) then
3496 return;
3498 -- After end of IF statement
3500 elsif Loc >= Sloc (Stm) +
3501 Text_Ptr (UI_To_Int (End_Span (Stm)))
3502 then
3503 return;
3504 end if;
3506 -- Again we lack the SLOC of the ELSE, so we need to climb the
3507 -- tree to see if we are within the ELSIF part in question.
3509 declare
3510 N : Node_Id;
3512 begin
3513 N := Parent (Var);
3514 while Parent (N) /= Stm loop
3515 N := Parent (N);
3517 -- If we fall off the top of the tree, then that's odd, but
3518 -- perhaps it could occur in some error situation, and the
3519 -- safest response is simply to assume that the outcome of
3520 -- the condition is unknown. No point in bombing during an
3521 -- attempt to optimize things.
3523 if No (N) then
3524 return;
3525 end if;
3526 end loop;
3528 -- Now we have N pointing to a node whose parent is the IF
3529 -- statement in question, so see if is the ELSIF part we want.
3530 -- the THEN statements.
3532 if N = CV then
3533 Sens := True;
3535 -- Otherwise we must be in subsequent ELSIF or ELSE part
3537 else
3538 Sens := False;
3539 end if;
3540 end;
3542 -- Iteration scheme of while loop. The condition is known to be
3543 -- true within the body of the loop.
3545 elsif Nkind (CV) = N_Iteration_Scheme then
3546 declare
3547 Loop_Stmt : constant Node_Id := Parent (CV);
3549 begin
3550 -- Before start of body of loop
3552 if Loc < Sloc (Loop_Stmt) then
3553 return;
3555 -- After end of LOOP statement
3557 elsif Loc >= Sloc (End_Label (Loop_Stmt)) then
3558 return;
3560 -- We are within the body of the loop
3562 else
3563 Sens := True;
3564 end if;
3565 end;
3567 -- All other cases of Current_Value settings
3569 else
3570 return;
3571 end if;
3573 -- If we fall through here, then we have a reportable condition, Sens
3574 -- is True if the condition is true and False if it needs inverting.
3576 Process_Current_Value_Condition (Condition (CV), Sens);
3577 end;
3578 end Get_Current_Value_Condition;
3580 ---------------------
3581 -- Get_Stream_Size --
3582 ---------------------
3584 function Get_Stream_Size (E : Entity_Id) return Uint is
3585 begin
3586 -- If we have a Stream_Size clause for this type use it
3588 if Has_Stream_Size_Clause (E) then
3589 return Static_Integer (Expression (Stream_Size_Clause (E)));
3591 -- Otherwise the Stream_Size if the size of the type
3593 else
3594 return Esize (E);
3595 end if;
3596 end Get_Stream_Size;
3598 ---------------------------
3599 -- Has_Access_Constraint --
3600 ---------------------------
3602 function Has_Access_Constraint (E : Entity_Id) return Boolean is
3603 Disc : Entity_Id;
3604 T : constant Entity_Id := Etype (E);
3606 begin
3607 if Has_Per_Object_Constraint (E) and then Has_Discriminants (T) then
3608 Disc := First_Discriminant (T);
3609 while Present (Disc) loop
3610 if Is_Access_Type (Etype (Disc)) then
3611 return True;
3612 end if;
3614 Next_Discriminant (Disc);
3615 end loop;
3617 return False;
3618 else
3619 return False;
3620 end if;
3621 end Has_Access_Constraint;
3623 -----------------------------------------------------
3624 -- Has_Annotate_Pragma_For_External_Axiomatization --
3625 -----------------------------------------------------
3627 function Has_Annotate_Pragma_For_External_Axiomatization
3628 (E : Entity_Id) return Boolean
3630 function Is_Annotate_Pragma_For_External_Axiomatization
3631 (N : Node_Id) return Boolean;
3632 -- Returns whether N is
3633 -- pragma Annotate (GNATprove, External_Axiomatization);
3635 ----------------------------------------------------
3636 -- Is_Annotate_Pragma_For_External_Axiomatization --
3637 ----------------------------------------------------
3639 -- The general form of pragma Annotate is
3641 -- pragma Annotate (IDENTIFIER [, IDENTIFIER {, ARG}]);
3642 -- ARG ::= NAME | EXPRESSION
3644 -- The first two arguments are by convention intended to refer to an
3645 -- external tool and a tool-specific function. These arguments are
3646 -- not analyzed.
3648 -- The following is used to annotate a package specification which
3649 -- GNATprove should treat specially, because the axiomatization of
3650 -- this unit is given by the user instead of being automatically
3651 -- generated.
3653 -- pragma Annotate (GNATprove, External_Axiomatization);
3655 function Is_Annotate_Pragma_For_External_Axiomatization
3656 (N : Node_Id) return Boolean
3658 Name_GNATprove : constant String :=
3659 "gnatprove";
3660 Name_External_Axiomatization : constant String :=
3661 "external_axiomatization";
3662 -- Special names
3664 begin
3665 if Nkind (N) = N_Pragma
3666 and then Get_Pragma_Id (Pragma_Name (N)) = Pragma_Annotate
3667 and then List_Length (Pragma_Argument_Associations (N)) = 2
3668 then
3669 declare
3670 Arg1 : constant Node_Id :=
3671 First (Pragma_Argument_Associations (N));
3672 Arg2 : constant Node_Id := Next (Arg1);
3673 Nam1 : Name_Id;
3674 Nam2 : Name_Id;
3676 begin
3677 -- Fill in Name_Buffer with Name_GNATprove first, and then with
3678 -- Name_External_Axiomatization so that Name_Find returns the
3679 -- corresponding name. This takes care of all possible casings.
3681 Name_Len := 0;
3682 Add_Str_To_Name_Buffer (Name_GNATprove);
3683 Nam1 := Name_Find;
3685 Name_Len := 0;
3686 Add_Str_To_Name_Buffer (Name_External_Axiomatization);
3687 Nam2 := Name_Find;
3689 return Chars (Get_Pragma_Arg (Arg1)) = Nam1
3690 and then
3691 Chars (Get_Pragma_Arg (Arg2)) = Nam2;
3692 end;
3694 else
3695 return False;
3696 end if;
3697 end Is_Annotate_Pragma_For_External_Axiomatization;
3699 -- Local variables
3701 Decl : Node_Id;
3702 Vis_Decls : List_Id;
3703 N : Node_Id;
3705 -- Start of processing for Has_Annotate_Pragma_For_External_Axiomatization
3707 begin
3708 if Nkind (Parent (E)) = N_Defining_Program_Unit_Name then
3709 Decl := Parent (Parent (E));
3710 else
3711 Decl := Parent (E);
3712 end if;
3714 Vis_Decls := Visible_Declarations (Decl);
3716 N := First (Vis_Decls);
3717 while Present (N) loop
3719 -- Skip declarations generated by the frontend. Skip all pragmas
3720 -- that are not the desired Annotate pragma. Stop the search on
3721 -- the first non-pragma source declaration.
3723 if Comes_From_Source (N) then
3724 if Nkind (N) = N_Pragma then
3725 if Is_Annotate_Pragma_For_External_Axiomatization (N) then
3726 return True;
3727 end if;
3728 else
3729 return False;
3730 end if;
3731 end if;
3733 Next (N);
3734 end loop;
3736 return False;
3737 end Has_Annotate_Pragma_For_External_Axiomatization;
3739 --------------------
3740 -- Homonym_Number --
3741 --------------------
3743 function Homonym_Number (Subp : Entity_Id) return Nat is
3744 Count : Nat;
3745 Hom : Entity_Id;
3747 begin
3748 Count := 1;
3749 Hom := Homonym (Subp);
3750 while Present (Hom) loop
3751 if Scope (Hom) = Scope (Subp) then
3752 Count := Count + 1;
3753 end if;
3755 Hom := Homonym (Hom);
3756 end loop;
3758 return Count;
3759 end Homonym_Number;
3761 -----------------------------------
3762 -- In_Library_Level_Package_Body --
3763 -----------------------------------
3765 function In_Library_Level_Package_Body (Id : Entity_Id) return Boolean is
3766 begin
3767 -- First determine whether the entity appears at the library level, then
3768 -- look at the containing unit.
3770 if Is_Library_Level_Entity (Id) then
3771 declare
3772 Container : constant Node_Id := Cunit (Get_Source_Unit (Id));
3774 begin
3775 return Nkind (Unit (Container)) = N_Package_Body;
3776 end;
3777 end if;
3779 return False;
3780 end In_Library_Level_Package_Body;
3782 ------------------------------
3783 -- In_Unconditional_Context --
3784 ------------------------------
3786 function In_Unconditional_Context (Node : Node_Id) return Boolean is
3787 P : Node_Id;
3789 begin
3790 P := Node;
3791 while Present (P) loop
3792 case Nkind (P) is
3793 when N_Subprogram_Body =>
3794 return True;
3796 when N_If_Statement =>
3797 return False;
3799 when N_Loop_Statement =>
3800 return False;
3802 when N_Case_Statement =>
3803 return False;
3805 when others =>
3806 P := Parent (P);
3807 end case;
3808 end loop;
3810 return False;
3811 end In_Unconditional_Context;
3813 -------------------
3814 -- Insert_Action --
3815 -------------------
3817 procedure Insert_Action (Assoc_Node : Node_Id; Ins_Action : Node_Id) is
3818 begin
3819 if Present (Ins_Action) then
3820 Insert_Actions (Assoc_Node, New_List (Ins_Action));
3821 end if;
3822 end Insert_Action;
3824 -- Version with check(s) suppressed
3826 procedure Insert_Action
3827 (Assoc_Node : Node_Id; Ins_Action : Node_Id; Suppress : Check_Id)
3829 begin
3830 Insert_Actions (Assoc_Node, New_List (Ins_Action), Suppress);
3831 end Insert_Action;
3833 -------------------------
3834 -- Insert_Action_After --
3835 -------------------------
3837 procedure Insert_Action_After
3838 (Assoc_Node : Node_Id;
3839 Ins_Action : Node_Id)
3841 begin
3842 Insert_Actions_After (Assoc_Node, New_List (Ins_Action));
3843 end Insert_Action_After;
3845 --------------------
3846 -- Insert_Actions --
3847 --------------------
3849 procedure Insert_Actions (Assoc_Node : Node_Id; Ins_Actions : List_Id) is
3850 N : Node_Id;
3851 P : Node_Id;
3853 Wrapped_Node : Node_Id := Empty;
3855 begin
3856 if No (Ins_Actions) or else Is_Empty_List (Ins_Actions) then
3857 return;
3858 end if;
3860 -- Ignore insert of actions from inside default expression (or other
3861 -- similar "spec expression") in the special spec-expression analyze
3862 -- mode. Any insertions at this point have no relevance, since we are
3863 -- only doing the analyze to freeze the types of any static expressions.
3864 -- See section "Handling of Default Expressions" in the spec of package
3865 -- Sem for further details.
3867 if In_Spec_Expression then
3868 return;
3869 end if;
3871 -- If the action derives from stuff inside a record, then the actions
3872 -- are attached to the current scope, to be inserted and analyzed on
3873 -- exit from the scope. The reason for this is that we may also be
3874 -- generating freeze actions at the same time, and they must eventually
3875 -- be elaborated in the correct order.
3877 if Is_Record_Type (Current_Scope)
3878 and then not Is_Frozen (Current_Scope)
3879 then
3880 if No (Scope_Stack.Table
3881 (Scope_Stack.Last).Pending_Freeze_Actions)
3882 then
3883 Scope_Stack.Table (Scope_Stack.Last).Pending_Freeze_Actions :=
3884 Ins_Actions;
3885 else
3886 Append_List
3887 (Ins_Actions,
3888 Scope_Stack.Table (Scope_Stack.Last).Pending_Freeze_Actions);
3889 end if;
3891 return;
3892 end if;
3894 -- We now intend to climb up the tree to find the right point to
3895 -- insert the actions. We start at Assoc_Node, unless this node is a
3896 -- subexpression in which case we start with its parent. We do this for
3897 -- two reasons. First it speeds things up. Second, if Assoc_Node is
3898 -- itself one of the special nodes like N_And_Then, then we assume that
3899 -- an initial request to insert actions for such a node does not expect
3900 -- the actions to get deposited in the node for later handling when the
3901 -- node is expanded, since clearly the node is being dealt with by the
3902 -- caller. Note that in the subexpression case, N is always the child we
3903 -- came from.
3905 -- N_Raise_xxx_Error is an annoying special case, it is a statement
3906 -- if it has type Standard_Void_Type, and a subexpression otherwise.
3907 -- Procedure calls, and similarly procedure attribute references, are
3908 -- also statements.
3910 if Nkind (Assoc_Node) in N_Subexpr
3911 and then (Nkind (Assoc_Node) not in N_Raise_xxx_Error
3912 or else Etype (Assoc_Node) /= Standard_Void_Type)
3913 and then Nkind (Assoc_Node) /= N_Procedure_Call_Statement
3914 and then (Nkind (Assoc_Node) /= N_Attribute_Reference
3915 or else not Is_Procedure_Attribute_Name
3916 (Attribute_Name (Assoc_Node)))
3917 then
3918 N := Assoc_Node;
3919 P := Parent (Assoc_Node);
3921 -- Non-subexpression case. Note that N is initially Empty in this case
3922 -- (N is only guaranteed Non-Empty in the subexpr case).
3924 else
3925 N := Empty;
3926 P := Assoc_Node;
3927 end if;
3929 -- Capture root of the transient scope
3931 if Scope_Is_Transient then
3932 Wrapped_Node := Node_To_Be_Wrapped;
3933 end if;
3935 loop
3936 pragma Assert (Present (P));
3938 -- Make sure that inserted actions stay in the transient scope
3940 if Present (Wrapped_Node) and then N = Wrapped_Node then
3941 Store_Before_Actions_In_Scope (Ins_Actions);
3942 return;
3943 end if;
3945 case Nkind (P) is
3947 -- Case of right operand of AND THEN or OR ELSE. Put the actions
3948 -- in the Actions field of the right operand. They will be moved
3949 -- out further when the AND THEN or OR ELSE operator is expanded.
3950 -- Nothing special needs to be done for the left operand since
3951 -- in that case the actions are executed unconditionally.
3953 when N_Short_Circuit =>
3954 if N = Right_Opnd (P) then
3956 -- We are now going to either append the actions to the
3957 -- actions field of the short-circuit operation. We will
3958 -- also analyze the actions now.
3960 -- This analysis is really too early, the proper thing would
3961 -- be to just park them there now, and only analyze them if
3962 -- we find we really need them, and to it at the proper
3963 -- final insertion point. However attempting to this proved
3964 -- tricky, so for now we just kill current values before and
3965 -- after the analyze call to make sure we avoid peculiar
3966 -- optimizations from this out of order insertion.
3968 Kill_Current_Values;
3970 -- If P has already been expanded, we can't park new actions
3971 -- on it, so we need to expand them immediately, introducing
3972 -- an Expression_With_Actions. N can't be an expression
3973 -- with actions, or else then the actions would have been
3974 -- inserted at an inner level.
3976 if Analyzed (P) then
3977 pragma Assert (Nkind (N) /= N_Expression_With_Actions);
3978 Rewrite (N,
3979 Make_Expression_With_Actions (Sloc (N),
3980 Actions => Ins_Actions,
3981 Expression => Relocate_Node (N)));
3982 Analyze_And_Resolve (N);
3984 elsif Present (Actions (P)) then
3985 Insert_List_After_And_Analyze
3986 (Last (Actions (P)), Ins_Actions);
3987 else
3988 Set_Actions (P, Ins_Actions);
3989 Analyze_List (Actions (P));
3990 end if;
3992 Kill_Current_Values;
3994 return;
3995 end if;
3997 -- Then or Else dependent expression of an if expression. Add
3998 -- actions to Then_Actions or Else_Actions field as appropriate.
3999 -- The actions will be moved further out when the if is expanded.
4001 when N_If_Expression =>
4002 declare
4003 ThenX : constant Node_Id := Next (First (Expressions (P)));
4004 ElseX : constant Node_Id := Next (ThenX);
4006 begin
4007 -- If the enclosing expression is already analyzed, as
4008 -- is the case for nested elaboration checks, insert the
4009 -- conditional further out.
4011 if Analyzed (P) then
4012 null;
4014 -- Actions belong to the then expression, temporarily place
4015 -- them as Then_Actions of the if expression. They will be
4016 -- moved to the proper place later when the if expression
4017 -- is expanded.
4019 elsif N = ThenX then
4020 if Present (Then_Actions (P)) then
4021 Insert_List_After_And_Analyze
4022 (Last (Then_Actions (P)), Ins_Actions);
4023 else
4024 Set_Then_Actions (P, Ins_Actions);
4025 Analyze_List (Then_Actions (P));
4026 end if;
4028 return;
4030 -- Actions belong to the else expression, temporarily place
4031 -- them as Else_Actions of the if expression. They will be
4032 -- moved to the proper place later when the if expression
4033 -- is expanded.
4035 elsif N = ElseX then
4036 if Present (Else_Actions (P)) then
4037 Insert_List_After_And_Analyze
4038 (Last (Else_Actions (P)), Ins_Actions);
4039 else
4040 Set_Else_Actions (P, Ins_Actions);
4041 Analyze_List (Else_Actions (P));
4042 end if;
4044 return;
4046 -- Actions belong to the condition. In this case they are
4047 -- unconditionally executed, and so we can continue the
4048 -- search for the proper insert point.
4050 else
4051 null;
4052 end if;
4053 end;
4055 -- Alternative of case expression, we place the action in the
4056 -- Actions field of the case expression alternative, this will
4057 -- be handled when the case expression is expanded.
4059 when N_Case_Expression_Alternative =>
4060 if Present (Actions (P)) then
4061 Insert_List_After_And_Analyze
4062 (Last (Actions (P)), Ins_Actions);
4063 else
4064 Set_Actions (P, Ins_Actions);
4065 Analyze_List (Actions (P));
4066 end if;
4068 return;
4070 -- Case of appearing within an Expressions_With_Actions node. When
4071 -- the new actions come from the expression of the expression with
4072 -- actions, they must be added to the existing actions. The other
4073 -- alternative is when the new actions are related to one of the
4074 -- existing actions of the expression with actions, and should
4075 -- never reach here: if actions are inserted on a statement
4076 -- within the Actions of an expression with actions, or on some
4077 -- sub-expression of such a statement, then the outermost proper
4078 -- insertion point is right before the statement, and we should
4079 -- never climb up as far as the N_Expression_With_Actions itself.
4081 when N_Expression_With_Actions =>
4082 if N = Expression (P) then
4083 if Is_Empty_List (Actions (P)) then
4084 Append_List_To (Actions (P), Ins_Actions);
4085 Analyze_List (Actions (P));
4086 else
4087 Insert_List_After_And_Analyze
4088 (Last (Actions (P)), Ins_Actions);
4089 end if;
4091 return;
4093 else
4094 raise Program_Error;
4095 end if;
4097 -- Case of appearing in the condition of a while expression or
4098 -- elsif. We insert the actions into the Condition_Actions field.
4099 -- They will be moved further out when the while loop or elsif
4100 -- is analyzed.
4102 when N_Iteration_Scheme |
4103 N_Elsif_Part
4105 if N = Condition (P) then
4106 if Present (Condition_Actions (P)) then
4107 Insert_List_After_And_Analyze
4108 (Last (Condition_Actions (P)), Ins_Actions);
4109 else
4110 Set_Condition_Actions (P, Ins_Actions);
4112 -- Set the parent of the insert actions explicitly. This
4113 -- is not a syntactic field, but we need the parent field
4114 -- set, in particular so that freeze can understand that
4115 -- it is dealing with condition actions, and properly
4116 -- insert the freezing actions.
4118 Set_Parent (Ins_Actions, P);
4119 Analyze_List (Condition_Actions (P));
4120 end if;
4122 return;
4123 end if;
4125 -- Statements, declarations, pragmas, representation clauses
4127 when
4128 -- Statements
4130 N_Procedure_Call_Statement |
4131 N_Statement_Other_Than_Procedure_Call |
4133 -- Pragmas
4135 N_Pragma |
4137 -- Representation_Clause
4139 N_At_Clause |
4140 N_Attribute_Definition_Clause |
4141 N_Enumeration_Representation_Clause |
4142 N_Record_Representation_Clause |
4144 -- Declarations
4146 N_Abstract_Subprogram_Declaration |
4147 N_Entry_Body |
4148 N_Exception_Declaration |
4149 N_Exception_Renaming_Declaration |
4150 N_Expression_Function |
4151 N_Formal_Abstract_Subprogram_Declaration |
4152 N_Formal_Concrete_Subprogram_Declaration |
4153 N_Formal_Object_Declaration |
4154 N_Formal_Type_Declaration |
4155 N_Full_Type_Declaration |
4156 N_Function_Instantiation |
4157 N_Generic_Function_Renaming_Declaration |
4158 N_Generic_Package_Declaration |
4159 N_Generic_Package_Renaming_Declaration |
4160 N_Generic_Procedure_Renaming_Declaration |
4161 N_Generic_Subprogram_Declaration |
4162 N_Implicit_Label_Declaration |
4163 N_Incomplete_Type_Declaration |
4164 N_Number_Declaration |
4165 N_Object_Declaration |
4166 N_Object_Renaming_Declaration |
4167 N_Package_Body |
4168 N_Package_Body_Stub |
4169 N_Package_Declaration |
4170 N_Package_Instantiation |
4171 N_Package_Renaming_Declaration |
4172 N_Private_Extension_Declaration |
4173 N_Private_Type_Declaration |
4174 N_Procedure_Instantiation |
4175 N_Protected_Body |
4176 N_Protected_Body_Stub |
4177 N_Protected_Type_Declaration |
4178 N_Single_Task_Declaration |
4179 N_Subprogram_Body |
4180 N_Subprogram_Body_Stub |
4181 N_Subprogram_Declaration |
4182 N_Subprogram_Renaming_Declaration |
4183 N_Subtype_Declaration |
4184 N_Task_Body |
4185 N_Task_Body_Stub |
4186 N_Task_Type_Declaration |
4188 -- Use clauses can appear in lists of declarations
4190 N_Use_Package_Clause |
4191 N_Use_Type_Clause |
4193 -- Freeze entity behaves like a declaration or statement
4195 N_Freeze_Entity |
4196 N_Freeze_Generic_Entity
4198 -- Do not insert here if the item is not a list member (this
4199 -- happens for example with a triggering statement, and the
4200 -- proper approach is to insert before the entire select).
4202 if not Is_List_Member (P) then
4203 null;
4205 -- Do not insert if parent of P is an N_Component_Association
4206 -- node (i.e. we are in the context of an N_Aggregate or
4207 -- N_Extension_Aggregate node. In this case we want to insert
4208 -- before the entire aggregate.
4210 elsif Nkind (Parent (P)) = N_Component_Association then
4211 null;
4213 -- Do not insert if the parent of P is either an N_Variant node
4214 -- or an N_Record_Definition node, meaning in either case that
4215 -- P is a member of a component list, and that therefore the
4216 -- actions should be inserted outside the complete record
4217 -- declaration.
4219 elsif Nkind_In (Parent (P), N_Variant, N_Record_Definition) then
4220 null;
4222 -- Do not insert freeze nodes within the loop generated for
4223 -- an aggregate, because they may be elaborated too late for
4224 -- subsequent use in the back end: within a package spec the
4225 -- loop is part of the elaboration procedure and is only
4226 -- elaborated during the second pass.
4228 -- If the loop comes from source, or the entity is local to the
4229 -- loop itself it must remain within.
4231 elsif Nkind (Parent (P)) = N_Loop_Statement
4232 and then not Comes_From_Source (Parent (P))
4233 and then Nkind (First (Ins_Actions)) = N_Freeze_Entity
4234 and then
4235 Scope (Entity (First (Ins_Actions))) /= Current_Scope
4236 then
4237 null;
4239 -- Otherwise we can go ahead and do the insertion
4241 elsif P = Wrapped_Node then
4242 Store_Before_Actions_In_Scope (Ins_Actions);
4243 return;
4245 else
4246 Insert_List_Before_And_Analyze (P, Ins_Actions);
4247 return;
4248 end if;
4250 -- A special case, N_Raise_xxx_Error can act either as a statement
4251 -- or a subexpression. We tell the difference by looking at the
4252 -- Etype. It is set to Standard_Void_Type in the statement case.
4254 when
4255 N_Raise_xxx_Error =>
4256 if Etype (P) = Standard_Void_Type then
4257 if P = Wrapped_Node then
4258 Store_Before_Actions_In_Scope (Ins_Actions);
4259 else
4260 Insert_List_Before_And_Analyze (P, Ins_Actions);
4261 end if;
4263 return;
4265 -- In the subexpression case, keep climbing
4267 else
4268 null;
4269 end if;
4271 -- If a component association appears within a loop created for
4272 -- an array aggregate, attach the actions to the association so
4273 -- they can be subsequently inserted within the loop. For other
4274 -- component associations insert outside of the aggregate. For
4275 -- an association that will generate a loop, its Loop_Actions
4276 -- attribute is already initialized (see exp_aggr.adb).
4278 -- The list of loop_actions can in turn generate additional ones,
4279 -- that are inserted before the associated node. If the associated
4280 -- node is outside the aggregate, the new actions are collected
4281 -- at the end of the loop actions, to respect the order in which
4282 -- they are to be elaborated.
4284 when
4285 N_Component_Association =>
4286 if Nkind (Parent (P)) = N_Aggregate
4287 and then Present (Loop_Actions (P))
4288 then
4289 if Is_Empty_List (Loop_Actions (P)) then
4290 Set_Loop_Actions (P, Ins_Actions);
4291 Analyze_List (Ins_Actions);
4293 else
4294 declare
4295 Decl : Node_Id;
4297 begin
4298 -- Check whether these actions were generated by a
4299 -- declaration that is part of the loop_ actions
4300 -- for the component_association.
4302 Decl := Assoc_Node;
4303 while Present (Decl) loop
4304 exit when Parent (Decl) = P
4305 and then Is_List_Member (Decl)
4306 and then
4307 List_Containing (Decl) = Loop_Actions (P);
4308 Decl := Parent (Decl);
4309 end loop;
4311 if Present (Decl) then
4312 Insert_List_Before_And_Analyze
4313 (Decl, Ins_Actions);
4314 else
4315 Insert_List_After_And_Analyze
4316 (Last (Loop_Actions (P)), Ins_Actions);
4317 end if;
4318 end;
4319 end if;
4321 return;
4323 else
4324 null;
4325 end if;
4327 -- Another special case, an attribute denoting a procedure call
4329 when
4330 N_Attribute_Reference =>
4331 if Is_Procedure_Attribute_Name (Attribute_Name (P)) then
4332 if P = Wrapped_Node then
4333 Store_Before_Actions_In_Scope (Ins_Actions);
4334 else
4335 Insert_List_Before_And_Analyze (P, Ins_Actions);
4336 end if;
4338 return;
4340 -- In the subexpression case, keep climbing
4342 else
4343 null;
4344 end if;
4346 -- A contract node should not belong to the tree
4348 when N_Contract =>
4349 raise Program_Error;
4351 -- For all other node types, keep climbing tree
4353 when
4354 N_Abortable_Part |
4355 N_Accept_Alternative |
4356 N_Access_Definition |
4357 N_Access_Function_Definition |
4358 N_Access_Procedure_Definition |
4359 N_Access_To_Object_Definition |
4360 N_Aggregate |
4361 N_Allocator |
4362 N_Aspect_Specification |
4363 N_Case_Expression |
4364 N_Case_Statement_Alternative |
4365 N_Character_Literal |
4366 N_Compilation_Unit |
4367 N_Compilation_Unit_Aux |
4368 N_Component_Clause |
4369 N_Component_Declaration |
4370 N_Component_Definition |
4371 N_Component_List |
4372 N_Constrained_Array_Definition |
4373 N_Decimal_Fixed_Point_Definition |
4374 N_Defining_Character_Literal |
4375 N_Defining_Identifier |
4376 N_Defining_Operator_Symbol |
4377 N_Defining_Program_Unit_Name |
4378 N_Delay_Alternative |
4379 N_Delta_Constraint |
4380 N_Derived_Type_Definition |
4381 N_Designator |
4382 N_Digits_Constraint |
4383 N_Discriminant_Association |
4384 N_Discriminant_Specification |
4385 N_Empty |
4386 N_Entry_Body_Formal_Part |
4387 N_Entry_Call_Alternative |
4388 N_Entry_Declaration |
4389 N_Entry_Index_Specification |
4390 N_Enumeration_Type_Definition |
4391 N_Error |
4392 N_Exception_Handler |
4393 N_Expanded_Name |
4394 N_Explicit_Dereference |
4395 N_Extension_Aggregate |
4396 N_Floating_Point_Definition |
4397 N_Formal_Decimal_Fixed_Point_Definition |
4398 N_Formal_Derived_Type_Definition |
4399 N_Formal_Discrete_Type_Definition |
4400 N_Formal_Floating_Point_Definition |
4401 N_Formal_Modular_Type_Definition |
4402 N_Formal_Ordinary_Fixed_Point_Definition |
4403 N_Formal_Package_Declaration |
4404 N_Formal_Private_Type_Definition |
4405 N_Formal_Incomplete_Type_Definition |
4406 N_Formal_Signed_Integer_Type_Definition |
4407 N_Function_Call |
4408 N_Function_Specification |
4409 N_Generic_Association |
4410 N_Handled_Sequence_Of_Statements |
4411 N_Identifier |
4412 N_In |
4413 N_Index_Or_Discriminant_Constraint |
4414 N_Indexed_Component |
4415 N_Integer_Literal |
4416 N_Iterator_Specification |
4417 N_Itype_Reference |
4418 N_Label |
4419 N_Loop_Parameter_Specification |
4420 N_Mod_Clause |
4421 N_Modular_Type_Definition |
4422 N_Not_In |
4423 N_Null |
4424 N_Op_Abs |
4425 N_Op_Add |
4426 N_Op_And |
4427 N_Op_Concat |
4428 N_Op_Divide |
4429 N_Op_Eq |
4430 N_Op_Expon |
4431 N_Op_Ge |
4432 N_Op_Gt |
4433 N_Op_Le |
4434 N_Op_Lt |
4435 N_Op_Minus |
4436 N_Op_Mod |
4437 N_Op_Multiply |
4438 N_Op_Ne |
4439 N_Op_Not |
4440 N_Op_Or |
4441 N_Op_Plus |
4442 N_Op_Rem |
4443 N_Op_Rotate_Left |
4444 N_Op_Rotate_Right |
4445 N_Op_Shift_Left |
4446 N_Op_Shift_Right |
4447 N_Op_Shift_Right_Arithmetic |
4448 N_Op_Subtract |
4449 N_Op_Xor |
4450 N_Operator_Symbol |
4451 N_Ordinary_Fixed_Point_Definition |
4452 N_Others_Choice |
4453 N_Package_Specification |
4454 N_Parameter_Association |
4455 N_Parameter_Specification |
4456 N_Pop_Constraint_Error_Label |
4457 N_Pop_Program_Error_Label |
4458 N_Pop_Storage_Error_Label |
4459 N_Pragma_Argument_Association |
4460 N_Procedure_Specification |
4461 N_Protected_Definition |
4462 N_Push_Constraint_Error_Label |
4463 N_Push_Program_Error_Label |
4464 N_Push_Storage_Error_Label |
4465 N_Qualified_Expression |
4466 N_Quantified_Expression |
4467 N_Raise_Expression |
4468 N_Range |
4469 N_Range_Constraint |
4470 N_Real_Literal |
4471 N_Real_Range_Specification |
4472 N_Record_Definition |
4473 N_Reference |
4474 N_SCIL_Dispatch_Table_Tag_Init |
4475 N_SCIL_Dispatching_Call |
4476 N_SCIL_Membership_Test |
4477 N_Selected_Component |
4478 N_Signed_Integer_Type_Definition |
4479 N_Single_Protected_Declaration |
4480 N_Slice |
4481 N_String_Literal |
4482 N_Subtype_Indication |
4483 N_Subunit |
4484 N_Task_Definition |
4485 N_Terminate_Alternative |
4486 N_Triggering_Alternative |
4487 N_Type_Conversion |
4488 N_Unchecked_Expression |
4489 N_Unchecked_Type_Conversion |
4490 N_Unconstrained_Array_Definition |
4491 N_Unused_At_End |
4492 N_Unused_At_Start |
4493 N_Variant |
4494 N_Variant_Part |
4495 N_Validate_Unchecked_Conversion |
4496 N_With_Clause
4498 null;
4500 end case;
4502 -- If we fall through above tests, keep climbing tree
4504 N := P;
4506 if Nkind (Parent (N)) = N_Subunit then
4508 -- This is the proper body corresponding to a stub. Insertion must
4509 -- be done at the point of the stub, which is in the declarative
4510 -- part of the parent unit.
4512 P := Corresponding_Stub (Parent (N));
4514 else
4515 P := Parent (N);
4516 end if;
4517 end loop;
4518 end Insert_Actions;
4520 -- Version with check(s) suppressed
4522 procedure Insert_Actions
4523 (Assoc_Node : Node_Id;
4524 Ins_Actions : List_Id;
4525 Suppress : Check_Id)
4527 begin
4528 if Suppress = All_Checks then
4529 declare
4530 Sva : constant Suppress_Array := Scope_Suppress.Suppress;
4531 begin
4532 Scope_Suppress.Suppress := (others => True);
4533 Insert_Actions (Assoc_Node, Ins_Actions);
4534 Scope_Suppress.Suppress := Sva;
4535 end;
4537 else
4538 declare
4539 Svg : constant Boolean := Scope_Suppress.Suppress (Suppress);
4540 begin
4541 Scope_Suppress.Suppress (Suppress) := True;
4542 Insert_Actions (Assoc_Node, Ins_Actions);
4543 Scope_Suppress.Suppress (Suppress) := Svg;
4544 end;
4545 end if;
4546 end Insert_Actions;
4548 --------------------------
4549 -- Insert_Actions_After --
4550 --------------------------
4552 procedure Insert_Actions_After
4553 (Assoc_Node : Node_Id;
4554 Ins_Actions : List_Id)
4556 begin
4557 if Scope_Is_Transient and then Assoc_Node = Node_To_Be_Wrapped then
4558 Store_After_Actions_In_Scope (Ins_Actions);
4559 else
4560 Insert_List_After_And_Analyze (Assoc_Node, Ins_Actions);
4561 end if;
4562 end Insert_Actions_After;
4564 ------------------------
4565 -- Insert_Declaration --
4566 ------------------------
4568 procedure Insert_Declaration (N : Node_Id; Decl : Node_Id) is
4569 P : Node_Id;
4571 begin
4572 pragma Assert (Nkind (N) in N_Subexpr);
4574 -- Climb until we find a procedure or a package
4576 P := N;
4577 loop
4578 pragma Assert (Present (Parent (P)));
4579 P := Parent (P);
4581 if Is_List_Member (P) then
4582 exit when Nkind_In (Parent (P), N_Package_Specification,
4583 N_Subprogram_Body);
4585 -- Special handling for handled sequence of statements, we must
4586 -- insert in the statements not the exception handlers!
4588 if Nkind (Parent (P)) = N_Handled_Sequence_Of_Statements then
4589 P := First (Statements (Parent (P)));
4590 exit;
4591 end if;
4592 end if;
4593 end loop;
4595 -- Now do the insertion
4597 Insert_Before (P, Decl);
4598 Analyze (Decl);
4599 end Insert_Declaration;
4601 ---------------------------------
4602 -- Insert_Library_Level_Action --
4603 ---------------------------------
4605 procedure Insert_Library_Level_Action (N : Node_Id) is
4606 Aux : constant Node_Id := Aux_Decls_Node (Cunit (Main_Unit));
4608 begin
4609 Push_Scope (Cunit_Entity (Main_Unit));
4610 -- ??? should this be Current_Sem_Unit instead of Main_Unit?
4612 if No (Actions (Aux)) then
4613 Set_Actions (Aux, New_List (N));
4614 else
4615 Append (N, Actions (Aux));
4616 end if;
4618 Analyze (N);
4619 Pop_Scope;
4620 end Insert_Library_Level_Action;
4622 ----------------------------------
4623 -- Insert_Library_Level_Actions --
4624 ----------------------------------
4626 procedure Insert_Library_Level_Actions (L : List_Id) is
4627 Aux : constant Node_Id := Aux_Decls_Node (Cunit (Main_Unit));
4629 begin
4630 if Is_Non_Empty_List (L) then
4631 Push_Scope (Cunit_Entity (Main_Unit));
4632 -- ??? should this be Current_Sem_Unit instead of Main_Unit?
4634 if No (Actions (Aux)) then
4635 Set_Actions (Aux, L);
4636 Analyze_List (L);
4637 else
4638 Insert_List_After_And_Analyze (Last (Actions (Aux)), L);
4639 end if;
4641 Pop_Scope;
4642 end if;
4643 end Insert_Library_Level_Actions;
4645 ----------------------
4646 -- Inside_Init_Proc --
4647 ----------------------
4649 function Inside_Init_Proc return Boolean is
4650 S : Entity_Id;
4652 begin
4653 S := Current_Scope;
4654 while Present (S) and then S /= Standard_Standard loop
4655 if Is_Init_Proc (S) then
4656 return True;
4657 else
4658 S := Scope (S);
4659 end if;
4660 end loop;
4662 return False;
4663 end Inside_Init_Proc;
4665 ----------------------------
4666 -- Is_All_Null_Statements --
4667 ----------------------------
4669 function Is_All_Null_Statements (L : List_Id) return Boolean is
4670 Stm : Node_Id;
4672 begin
4673 Stm := First (L);
4674 while Present (Stm) loop
4675 if Nkind (Stm) /= N_Null_Statement then
4676 return False;
4677 end if;
4679 Next (Stm);
4680 end loop;
4682 return True;
4683 end Is_All_Null_Statements;
4685 --------------------------------------------------
4686 -- Is_Displacement_Of_Object_Or_Function_Result --
4687 --------------------------------------------------
4689 function Is_Displacement_Of_Object_Or_Function_Result
4690 (Obj_Id : Entity_Id) return Boolean
4692 function Is_Controlled_Function_Call (N : Node_Id) return Boolean;
4693 -- Determine if particular node denotes a controlled function call. The
4694 -- call may have been heavily expanded.
4696 function Is_Displace_Call (N : Node_Id) return Boolean;
4697 -- Determine whether a particular node is a call to Ada.Tags.Displace.
4698 -- The call might be nested within other actions such as conversions.
4700 function Is_Source_Object (N : Node_Id) return Boolean;
4701 -- Determine whether a particular node denotes a source object
4703 ---------------------------------
4704 -- Is_Controlled_Function_Call --
4705 ---------------------------------
4707 function Is_Controlled_Function_Call (N : Node_Id) return Boolean is
4708 Expr : Node_Id := Original_Node (N);
4710 begin
4711 if Nkind (Expr) = N_Function_Call then
4712 Expr := Name (Expr);
4714 -- When a function call appears in Object.Operation format, the
4715 -- original representation has two possible forms depending on the
4716 -- availability of actual parameters:
4718 -- Obj.Func_Call N_Selected_Component
4719 -- Obj.Func_Call (Param) N_Indexed_Component
4721 else
4722 if Nkind (Expr) = N_Indexed_Component then
4723 Expr := Prefix (Expr);
4724 end if;
4726 if Nkind (Expr) = N_Selected_Component then
4727 Expr := Selector_Name (Expr);
4728 end if;
4729 end if;
4731 return
4732 Nkind_In (Expr, N_Expanded_Name, N_Identifier)
4733 and then Ekind (Entity (Expr)) = E_Function
4734 and then Needs_Finalization (Etype (Entity (Expr)));
4735 end Is_Controlled_Function_Call;
4737 ----------------------
4738 -- Is_Displace_Call --
4739 ----------------------
4741 function Is_Displace_Call (N : Node_Id) return Boolean is
4742 Call : Node_Id := N;
4744 begin
4745 -- Strip various actions which may precede a call to Displace
4747 loop
4748 if Nkind (Call) = N_Explicit_Dereference then
4749 Call := Prefix (Call);
4751 elsif Nkind_In (Call, N_Type_Conversion,
4752 N_Unchecked_Type_Conversion)
4753 then
4754 Call := Expression (Call);
4756 else
4757 exit;
4758 end if;
4759 end loop;
4761 return
4762 Present (Call)
4763 and then Nkind (Call) = N_Function_Call
4764 and then Is_RTE (Entity (Name (Call)), RE_Displace);
4765 end Is_Displace_Call;
4767 ----------------------
4768 -- Is_Source_Object --
4769 ----------------------
4771 function Is_Source_Object (N : Node_Id) return Boolean is
4772 begin
4773 return
4774 Present (N)
4775 and then Nkind (N) in N_Has_Entity
4776 and then Is_Object (Entity (N))
4777 and then Comes_From_Source (N);
4778 end Is_Source_Object;
4780 -- Local variables
4782 Decl : constant Node_Id := Parent (Obj_Id);
4783 Obj_Typ : constant Entity_Id := Base_Type (Etype (Obj_Id));
4784 Orig_Decl : constant Node_Id := Original_Node (Decl);
4786 -- Start of processing for Is_Displacement_Of_Object_Or_Function_Result
4788 begin
4789 -- Case 1:
4791 -- Obj : CW_Type := Function_Call (...);
4793 -- rewritten into:
4795 -- Tmp : ... := Function_Call (...)'reference;
4796 -- Obj : CW_Type renames (... Ada.Tags.Displace (Tmp));
4798 -- where the return type of the function and the class-wide type require
4799 -- dispatch table pointer displacement.
4801 -- Case 2:
4803 -- Obj : CW_Type := Src_Obj;
4805 -- rewritten into:
4807 -- Obj : CW_Type renames (... Ada.Tags.Displace (Src_Obj));
4809 -- where the type of the source object and the class-wide type require
4810 -- dispatch table pointer displacement.
4812 return
4813 Nkind (Decl) = N_Object_Renaming_Declaration
4814 and then Nkind (Orig_Decl) = N_Object_Declaration
4815 and then Comes_From_Source (Orig_Decl)
4816 and then Is_Class_Wide_Type (Obj_Typ)
4817 and then Is_Displace_Call (Renamed_Object (Obj_Id))
4818 and then
4819 (Is_Controlled_Function_Call (Expression (Orig_Decl))
4820 or else Is_Source_Object (Expression (Orig_Decl)));
4821 end Is_Displacement_Of_Object_Or_Function_Result;
4823 ------------------------------
4824 -- Is_Finalizable_Transient --
4825 ------------------------------
4827 function Is_Finalizable_Transient
4828 (Decl : Node_Id;
4829 Rel_Node : Node_Id) return Boolean
4831 Obj_Id : constant Entity_Id := Defining_Identifier (Decl);
4832 Obj_Typ : constant Entity_Id := Base_Type (Etype (Obj_Id));
4834 function Initialized_By_Access (Trans_Id : Entity_Id) return Boolean;
4835 -- Determine whether transient object Trans_Id is initialized either
4836 -- by a function call which returns an access type or simply renames
4837 -- another pointer.
4839 function Initialized_By_Aliased_BIP_Func_Call
4840 (Trans_Id : Entity_Id) return Boolean;
4841 -- Determine whether transient object Trans_Id is initialized by a
4842 -- build-in-place function call where the BIPalloc parameter is of
4843 -- value 1 and BIPaccess is not null. This case creates an aliasing
4844 -- between the returned value and the value denoted by BIPaccess.
4846 function Is_Aliased
4847 (Trans_Id : Entity_Id;
4848 First_Stmt : Node_Id) return Boolean;
4849 -- Determine whether transient object Trans_Id has been renamed or
4850 -- aliased through 'reference in the statement list starting from
4851 -- First_Stmt.
4853 function Is_Allocated (Trans_Id : Entity_Id) return Boolean;
4854 -- Determine whether transient object Trans_Id is allocated on the heap
4856 function Is_Iterated_Container
4857 (Trans_Id : Entity_Id;
4858 First_Stmt : Node_Id) return Boolean;
4859 -- Determine whether transient object Trans_Id denotes a container which
4860 -- is in the process of being iterated in the statement list starting
4861 -- from First_Stmt.
4863 ---------------------------
4864 -- Initialized_By_Access --
4865 ---------------------------
4867 function Initialized_By_Access (Trans_Id : Entity_Id) return Boolean is
4868 Expr : constant Node_Id := Expression (Parent (Trans_Id));
4870 begin
4871 return
4872 Present (Expr)
4873 and then Nkind (Expr) /= N_Reference
4874 and then Is_Access_Type (Etype (Expr));
4875 end Initialized_By_Access;
4877 ------------------------------------------
4878 -- Initialized_By_Aliased_BIP_Func_Call --
4879 ------------------------------------------
4881 function Initialized_By_Aliased_BIP_Func_Call
4882 (Trans_Id : Entity_Id) return Boolean
4884 Call : Node_Id := Expression (Parent (Trans_Id));
4886 begin
4887 -- Build-in-place calls usually appear in 'reference format
4889 if Nkind (Call) = N_Reference then
4890 Call := Prefix (Call);
4891 end if;
4893 if Is_Build_In_Place_Function_Call (Call) then
4894 declare
4895 Access_Nam : Name_Id := No_Name;
4896 Access_OK : Boolean := False;
4897 Actual : Node_Id;
4898 Alloc_Nam : Name_Id := No_Name;
4899 Alloc_OK : Boolean := False;
4900 Formal : Node_Id;
4901 Func_Id : Entity_Id;
4902 Param : Node_Id;
4904 begin
4905 -- Examine all parameter associations of the function call
4907 Param := First (Parameter_Associations (Call));
4908 while Present (Param) loop
4909 if Nkind (Param) = N_Parameter_Association
4910 and then Nkind (Selector_Name (Param)) = N_Identifier
4911 then
4912 Actual := Explicit_Actual_Parameter (Param);
4913 Formal := Selector_Name (Param);
4915 -- Construct the names of formals BIPaccess and BIPalloc
4916 -- using the function name retrieved from an arbitrary
4917 -- formal.
4919 if Access_Nam = No_Name
4920 and then Alloc_Nam = No_Name
4921 and then Present (Entity (Formal))
4922 then
4923 Func_Id := Scope (Entity (Formal));
4925 Access_Nam :=
4926 New_External_Name (Chars (Func_Id),
4927 BIP_Formal_Suffix (BIP_Object_Access));
4929 Alloc_Nam :=
4930 New_External_Name (Chars (Func_Id),
4931 BIP_Formal_Suffix (BIP_Alloc_Form));
4932 end if;
4934 -- A match for BIPaccess => Temp has been found
4936 if Chars (Formal) = Access_Nam
4937 and then Nkind (Actual) /= N_Null
4938 then
4939 Access_OK := True;
4940 end if;
4942 -- A match for BIPalloc => 1 has been found
4944 if Chars (Formal) = Alloc_Nam
4945 and then Nkind (Actual) = N_Integer_Literal
4946 and then Intval (Actual) = Uint_1
4947 then
4948 Alloc_OK := True;
4949 end if;
4950 end if;
4952 Next (Param);
4953 end loop;
4955 return Access_OK and Alloc_OK;
4956 end;
4957 end if;
4959 return False;
4960 end Initialized_By_Aliased_BIP_Func_Call;
4962 ----------------
4963 -- Is_Aliased --
4964 ----------------
4966 function Is_Aliased
4967 (Trans_Id : Entity_Id;
4968 First_Stmt : Node_Id) return Boolean
4970 function Find_Renamed_Object (Ren_Decl : Node_Id) return Entity_Id;
4971 -- Given an object renaming declaration, retrieve the entity of the
4972 -- renamed name. Return Empty if the renamed name is anything other
4973 -- than a variable or a constant.
4975 -------------------------
4976 -- Find_Renamed_Object --
4977 -------------------------
4979 function Find_Renamed_Object (Ren_Decl : Node_Id) return Entity_Id is
4980 Ren_Obj : Node_Id := Empty;
4982 function Find_Object (N : Node_Id) return Traverse_Result;
4983 -- Try to detect an object which is either a constant or a
4984 -- variable.
4986 -----------------
4987 -- Find_Object --
4988 -----------------
4990 function Find_Object (N : Node_Id) return Traverse_Result is
4991 begin
4992 -- Stop the search once a constant or a variable has been
4993 -- detected.
4995 if Nkind (N) = N_Identifier
4996 and then Present (Entity (N))
4997 and then Ekind_In (Entity (N), E_Constant, E_Variable)
4998 then
4999 Ren_Obj := Entity (N);
5000 return Abandon;
5001 end if;
5003 return OK;
5004 end Find_Object;
5006 procedure Search is new Traverse_Proc (Find_Object);
5008 -- Local variables
5010 Typ : constant Entity_Id := Etype (Defining_Identifier (Ren_Decl));
5012 -- Start of processing for Find_Renamed_Object
5014 begin
5015 -- Actions related to dispatching calls may appear as renamings of
5016 -- tags. Do not process this type of renaming because it does not
5017 -- use the actual value of the object.
5019 if not Is_RTE (Typ, RE_Tag_Ptr) then
5020 Search (Name (Ren_Decl));
5021 end if;
5023 return Ren_Obj;
5024 end Find_Renamed_Object;
5026 -- Local variables
5028 Expr : Node_Id;
5029 Ren_Obj : Entity_Id;
5030 Stmt : Node_Id;
5032 -- Start of processing for Is_Aliased
5034 begin
5035 -- A controlled transient object is not considered aliased when it
5036 -- appears inside an expression_with_actions node even when there are
5037 -- explicit aliases of it:
5039 -- do
5040 -- Trans_Id : Ctrl_Typ ...; -- controlled transient object
5041 -- Alias : ... := Trans_Id; -- object is aliased
5042 -- Val : constant Boolean :=
5043 -- ... Alias ...; -- aliasing ends
5044 -- <finalize Trans_Id> -- object safe to finalize
5045 -- in Val end;
5047 -- Expansion ensures that all aliases are encapsulated in the actions
5048 -- list and do not leak to the expression by forcing the evaluation
5049 -- of the expression.
5051 if Nkind (Rel_Node) = N_Expression_With_Actions then
5052 return False;
5054 -- Otherwise examine the statements after the controlled transient
5055 -- object and look for various forms of aliasing.
5057 else
5058 Stmt := First_Stmt;
5059 while Present (Stmt) loop
5060 if Nkind (Stmt) = N_Object_Declaration then
5061 Expr := Expression (Stmt);
5063 -- Aliasing of the form:
5064 -- Obj : ... := Trans_Id'reference;
5066 if Present (Expr)
5067 and then Nkind (Expr) = N_Reference
5068 and then Nkind (Prefix (Expr)) = N_Identifier
5069 and then Entity (Prefix (Expr)) = Trans_Id
5070 then
5071 return True;
5072 end if;
5074 elsif Nkind (Stmt) = N_Object_Renaming_Declaration then
5075 Ren_Obj := Find_Renamed_Object (Stmt);
5077 -- Aliasing of the form:
5078 -- Obj : ... renames ... Trans_Id ...;
5080 if Present (Ren_Obj) and then Ren_Obj = Trans_Id then
5081 return True;
5082 end if;
5083 end if;
5085 Next (Stmt);
5086 end loop;
5088 return False;
5089 end if;
5090 end Is_Aliased;
5092 ------------------
5093 -- Is_Allocated --
5094 ------------------
5096 function Is_Allocated (Trans_Id : Entity_Id) return Boolean is
5097 Expr : constant Node_Id := Expression (Parent (Trans_Id));
5098 begin
5099 return
5100 Is_Access_Type (Etype (Trans_Id))
5101 and then Present (Expr)
5102 and then Nkind (Expr) = N_Allocator;
5103 end Is_Allocated;
5105 ---------------------------
5106 -- Is_Iterated_Container --
5107 ---------------------------
5109 function Is_Iterated_Container
5110 (Trans_Id : Entity_Id;
5111 First_Stmt : Node_Id) return Boolean
5113 Aspect : Node_Id;
5114 Call : Node_Id;
5115 Iter : Entity_Id;
5116 Param : Node_Id;
5117 Stmt : Node_Id;
5118 Typ : Entity_Id;
5120 begin
5121 -- It is not possible to iterate over containers in non-Ada 2012 code
5123 if Ada_Version < Ada_2012 then
5124 return False;
5125 end if;
5127 Typ := Etype (Trans_Id);
5129 -- Handle access type created for secondary stack use
5131 if Is_Access_Type (Typ) then
5132 Typ := Designated_Type (Typ);
5133 end if;
5135 -- Look for aspect Default_Iterator. It may be part of a type
5136 -- declaration for a container, or inherited from a base type
5137 -- or parent type.
5139 Aspect := Find_Value_Of_Aspect (Typ, Aspect_Default_Iterator);
5141 if Present (Aspect) then
5142 Iter := Entity (Aspect);
5144 -- Examine the statements following the container object and
5145 -- look for a call to the default iterate routine where the
5146 -- first parameter is the transient. Such a call appears as:
5148 -- It : Access_To_CW_Iterator :=
5149 -- Iterate (Tran_Id.all, ...)'reference;
5151 Stmt := First_Stmt;
5152 while Present (Stmt) loop
5154 -- Detect an object declaration which is initialized by a
5155 -- secondary stack function call.
5157 if Nkind (Stmt) = N_Object_Declaration
5158 and then Present (Expression (Stmt))
5159 and then Nkind (Expression (Stmt)) = N_Reference
5160 and then Nkind (Prefix (Expression (Stmt))) = N_Function_Call
5161 then
5162 Call := Prefix (Expression (Stmt));
5164 -- The call must invoke the default iterate routine of
5165 -- the container and the transient object must appear as
5166 -- the first actual parameter. Skip any calls whose names
5167 -- are not entities.
5169 if Is_Entity_Name (Name (Call))
5170 and then Entity (Name (Call)) = Iter
5171 and then Present (Parameter_Associations (Call))
5172 then
5173 Param := First (Parameter_Associations (Call));
5175 if Nkind (Param) = N_Explicit_Dereference
5176 and then Entity (Prefix (Param)) = Trans_Id
5177 then
5178 return True;
5179 end if;
5180 end if;
5181 end if;
5183 Next (Stmt);
5184 end loop;
5185 end if;
5187 return False;
5188 end Is_Iterated_Container;
5190 -- Local variables
5192 Desig : Entity_Id := Obj_Typ;
5194 -- Start of processing for Is_Finalizable_Transient
5196 begin
5197 -- Handle access types
5199 if Is_Access_Type (Desig) then
5200 Desig := Available_View (Designated_Type (Desig));
5201 end if;
5203 return
5204 Ekind_In (Obj_Id, E_Constant, E_Variable)
5205 and then Needs_Finalization (Desig)
5206 and then Requires_Transient_Scope (Desig)
5207 and then Nkind (Rel_Node) /= N_Simple_Return_Statement
5209 -- Do not consider renamed or 'reference-d transient objects because
5210 -- the act of renaming extends the object's lifetime.
5212 and then not Is_Aliased (Obj_Id, Decl)
5214 -- Do not consider transient objects allocated on the heap since
5215 -- they are attached to a finalization master.
5217 and then not Is_Allocated (Obj_Id)
5219 -- If the transient object is a pointer, check that it is not
5220 -- initialized by a function that returns a pointer or acts as a
5221 -- renaming of another pointer.
5223 and then
5224 (not Is_Access_Type (Obj_Typ)
5225 or else not Initialized_By_Access (Obj_Id))
5227 -- Do not consider transient objects which act as indirect aliases
5228 -- of build-in-place function results.
5230 and then not Initialized_By_Aliased_BIP_Func_Call (Obj_Id)
5232 -- Do not consider conversions of tags to class-wide types
5234 and then not Is_Tag_To_Class_Wide_Conversion (Obj_Id)
5236 -- Do not consider iterators because those are treated as normal
5237 -- controlled objects and are processed by the usual finalization
5238 -- machinery. This avoids the double finalization of an iterator.
5240 and then not Is_Iterator (Desig)
5242 -- Do not consider containers in the context of iterator loops. Such
5243 -- transient objects must exist for as long as the loop is around,
5244 -- otherwise any operation carried out by the iterator will fail.
5246 and then not Is_Iterated_Container (Obj_Id, Decl);
5247 end Is_Finalizable_Transient;
5249 ---------------------------------
5250 -- Is_Fully_Repped_Tagged_Type --
5251 ---------------------------------
5253 function Is_Fully_Repped_Tagged_Type (T : Entity_Id) return Boolean is
5254 U : constant Entity_Id := Underlying_Type (T);
5255 Comp : Entity_Id;
5257 begin
5258 if No (U) or else not Is_Tagged_Type (U) then
5259 return False;
5260 elsif Has_Discriminants (U) then
5261 return False;
5262 elsif not Has_Specified_Layout (U) then
5263 return False;
5264 end if;
5266 -- Here we have a tagged type, see if it has any unlayed out fields
5267 -- other than a possible tag and parent fields. If so, we return False.
5269 Comp := First_Component (U);
5270 while Present (Comp) loop
5271 if not Is_Tag (Comp)
5272 and then Chars (Comp) /= Name_uParent
5273 and then No (Component_Clause (Comp))
5274 then
5275 return False;
5276 else
5277 Next_Component (Comp);
5278 end if;
5279 end loop;
5281 -- All components are layed out
5283 return True;
5284 end Is_Fully_Repped_Tagged_Type;
5286 ----------------------------------
5287 -- Is_Library_Level_Tagged_Type --
5288 ----------------------------------
5290 function Is_Library_Level_Tagged_Type (Typ : Entity_Id) return Boolean is
5291 begin
5292 return Is_Tagged_Type (Typ) and then Is_Library_Level_Entity (Typ);
5293 end Is_Library_Level_Tagged_Type;
5295 --------------------------
5296 -- Is_Non_BIP_Func_Call --
5297 --------------------------
5299 function Is_Non_BIP_Func_Call (Expr : Node_Id) return Boolean is
5300 begin
5301 -- The expected call is of the format
5303 -- Func_Call'reference
5305 return
5306 Nkind (Expr) = N_Reference
5307 and then Nkind (Prefix (Expr)) = N_Function_Call
5308 and then not Is_Build_In_Place_Function_Call (Prefix (Expr));
5309 end Is_Non_BIP_Func_Call;
5311 ------------------------------------
5312 -- Is_Object_Access_BIP_Func_Call --
5313 ------------------------------------
5315 function Is_Object_Access_BIP_Func_Call
5316 (Expr : Node_Id;
5317 Obj_Id : Entity_Id) return Boolean
5319 Access_Nam : Name_Id := No_Name;
5320 Actual : Node_Id;
5321 Call : Node_Id;
5322 Formal : Node_Id;
5323 Param : Node_Id;
5325 begin
5326 -- Build-in-place calls usually appear in 'reference format. Note that
5327 -- the accessibility check machinery may add an extra 'reference due to
5328 -- side effect removal.
5330 Call := Expr;
5331 while Nkind (Call) = N_Reference loop
5332 Call := Prefix (Call);
5333 end loop;
5335 if Nkind_In (Call, N_Qualified_Expression,
5336 N_Unchecked_Type_Conversion)
5337 then
5338 Call := Expression (Call);
5339 end if;
5341 if Is_Build_In_Place_Function_Call (Call) then
5343 -- Examine all parameter associations of the function call
5345 Param := First (Parameter_Associations (Call));
5346 while Present (Param) loop
5347 if Nkind (Param) = N_Parameter_Association
5348 and then Nkind (Selector_Name (Param)) = N_Identifier
5349 then
5350 Formal := Selector_Name (Param);
5351 Actual := Explicit_Actual_Parameter (Param);
5353 -- Construct the name of formal BIPaccess. It is much easier to
5354 -- extract the name of the function using an arbitrary formal's
5355 -- scope rather than the Name field of Call.
5357 if Access_Nam = No_Name and then Present (Entity (Formal)) then
5358 Access_Nam :=
5359 New_External_Name
5360 (Chars (Scope (Entity (Formal))),
5361 BIP_Formal_Suffix (BIP_Object_Access));
5362 end if;
5364 -- A match for BIPaccess => Obj_Id'Unrestricted_Access has been
5365 -- found.
5367 if Chars (Formal) = Access_Nam
5368 and then Nkind (Actual) = N_Attribute_Reference
5369 and then Attribute_Name (Actual) = Name_Unrestricted_Access
5370 and then Nkind (Prefix (Actual)) = N_Identifier
5371 and then Entity (Prefix (Actual)) = Obj_Id
5372 then
5373 return True;
5374 end if;
5375 end if;
5377 Next (Param);
5378 end loop;
5379 end if;
5381 return False;
5382 end Is_Object_Access_BIP_Func_Call;
5384 ----------------------------------
5385 -- Is_Possibly_Unaligned_Object --
5386 ----------------------------------
5388 function Is_Possibly_Unaligned_Object (N : Node_Id) return Boolean is
5389 T : constant Entity_Id := Etype (N);
5391 begin
5392 -- If renamed object, apply test to underlying object
5394 if Is_Entity_Name (N)
5395 and then Is_Object (Entity (N))
5396 and then Present (Renamed_Object (Entity (N)))
5397 then
5398 return Is_Possibly_Unaligned_Object (Renamed_Object (Entity (N)));
5399 end if;
5401 -- Tagged and controlled types and aliased types are always aligned, as
5402 -- are concurrent types.
5404 if Is_Aliased (T)
5405 or else Has_Controlled_Component (T)
5406 or else Is_Concurrent_Type (T)
5407 or else Is_Tagged_Type (T)
5408 or else Is_Controlled (T)
5409 then
5410 return False;
5411 end if;
5413 -- If this is an element of a packed array, may be unaligned
5415 if Is_Ref_To_Bit_Packed_Array (N) then
5416 return True;
5417 end if;
5419 -- Case of indexed component reference: test whether prefix is unaligned
5421 if Nkind (N) = N_Indexed_Component then
5422 return Is_Possibly_Unaligned_Object (Prefix (N));
5424 -- Case of selected component reference
5426 elsif Nkind (N) = N_Selected_Component then
5427 declare
5428 P : constant Node_Id := Prefix (N);
5429 C : constant Entity_Id := Entity (Selector_Name (N));
5430 M : Nat;
5431 S : Nat;
5433 begin
5434 -- If component reference is for an array with non-static bounds,
5435 -- then it is always aligned: we can only process unaligned arrays
5436 -- with static bounds (more precisely compile time known bounds).
5438 if Is_Array_Type (T)
5439 and then not Compile_Time_Known_Bounds (T)
5440 then
5441 return False;
5442 end if;
5444 -- If component is aliased, it is definitely properly aligned
5446 if Is_Aliased (C) then
5447 return False;
5448 end if;
5450 -- If component is for a type implemented as a scalar, and the
5451 -- record is packed, and the component is other than the first
5452 -- component of the record, then the component may be unaligned.
5454 if Is_Packed (Etype (P))
5455 and then Represented_As_Scalar (Etype (C))
5456 and then First_Entity (Scope (C)) /= C
5457 then
5458 return True;
5459 end if;
5461 -- Compute maximum possible alignment for T
5463 -- If alignment is known, then that settles things
5465 if Known_Alignment (T) then
5466 M := UI_To_Int (Alignment (T));
5468 -- If alignment is not known, tentatively set max alignment
5470 else
5471 M := Ttypes.Maximum_Alignment;
5473 -- We can reduce this if the Esize is known since the default
5474 -- alignment will never be more than the smallest power of 2
5475 -- that does not exceed this Esize value.
5477 if Known_Esize (T) then
5478 S := UI_To_Int (Esize (T));
5480 while (M / 2) >= S loop
5481 M := M / 2;
5482 end loop;
5483 end if;
5484 end if;
5486 -- The following code is historical, it used to be present but it
5487 -- is too cautious, because the front-end does not know the proper
5488 -- default alignments for the target. Also, if the alignment is
5489 -- not known, the front end can't know in any case. If a copy is
5490 -- needed, the back-end will take care of it. This whole section
5491 -- including this comment can be removed later ???
5493 -- If the component reference is for a record that has a specified
5494 -- alignment, and we either know it is too small, or cannot tell,
5495 -- then the component may be unaligned.
5497 -- What is the following commented out code ???
5499 -- if Known_Alignment (Etype (P))
5500 -- and then Alignment (Etype (P)) < Ttypes.Maximum_Alignment
5501 -- and then M > Alignment (Etype (P))
5502 -- then
5503 -- return True;
5504 -- end if;
5506 -- Case of component clause present which may specify an
5507 -- unaligned position.
5509 if Present (Component_Clause (C)) then
5511 -- Otherwise we can do a test to make sure that the actual
5512 -- start position in the record, and the length, are both
5513 -- consistent with the required alignment. If not, we know
5514 -- that we are unaligned.
5516 declare
5517 Align_In_Bits : constant Nat := M * System_Storage_Unit;
5518 begin
5519 if Component_Bit_Offset (C) mod Align_In_Bits /= 0
5520 or else Esize (C) mod Align_In_Bits /= 0
5521 then
5522 return True;
5523 end if;
5524 end;
5525 end if;
5527 -- Otherwise, for a component reference, test prefix
5529 return Is_Possibly_Unaligned_Object (P);
5530 end;
5532 -- If not a component reference, must be aligned
5534 else
5535 return False;
5536 end if;
5537 end Is_Possibly_Unaligned_Object;
5539 ---------------------------------
5540 -- Is_Possibly_Unaligned_Slice --
5541 ---------------------------------
5543 function Is_Possibly_Unaligned_Slice (N : Node_Id) return Boolean is
5544 begin
5545 -- Go to renamed object
5547 if Is_Entity_Name (N)
5548 and then Is_Object (Entity (N))
5549 and then Present (Renamed_Object (Entity (N)))
5550 then
5551 return Is_Possibly_Unaligned_Slice (Renamed_Object (Entity (N)));
5552 end if;
5554 -- The reference must be a slice
5556 if Nkind (N) /= N_Slice then
5557 return False;
5558 end if;
5560 -- We only need to worry if the target has strict alignment
5562 if not Target_Strict_Alignment then
5563 return False;
5564 end if;
5566 -- If it is a slice, then look at the array type being sliced
5568 declare
5569 Sarr : constant Node_Id := Prefix (N);
5570 -- Prefix of the slice, i.e. the array being sliced
5572 Styp : constant Entity_Id := Etype (Prefix (N));
5573 -- Type of the array being sliced
5575 Pref : Node_Id;
5576 Ptyp : Entity_Id;
5578 begin
5579 -- The problems arise if the array object that is being sliced
5580 -- is a component of a record or array, and we cannot guarantee
5581 -- the alignment of the array within its containing object.
5583 -- To investigate this, we look at successive prefixes to see
5584 -- if we have a worrisome indexed or selected component.
5586 Pref := Sarr;
5587 loop
5588 -- Case of array is part of an indexed component reference
5590 if Nkind (Pref) = N_Indexed_Component then
5591 Ptyp := Etype (Prefix (Pref));
5593 -- The only problematic case is when the array is packed, in
5594 -- which case we really know nothing about the alignment of
5595 -- individual components.
5597 if Is_Bit_Packed_Array (Ptyp) then
5598 return True;
5599 end if;
5601 -- Case of array is part of a selected component reference
5603 elsif Nkind (Pref) = N_Selected_Component then
5604 Ptyp := Etype (Prefix (Pref));
5606 -- We are definitely in trouble if the record in question
5607 -- has an alignment, and either we know this alignment is
5608 -- inconsistent with the alignment of the slice, or we don't
5609 -- know what the alignment of the slice should be.
5611 if Known_Alignment (Ptyp)
5612 and then (Unknown_Alignment (Styp)
5613 or else Alignment (Styp) > Alignment (Ptyp))
5614 then
5615 return True;
5616 end if;
5618 -- We are in potential trouble if the record type is packed.
5619 -- We could special case when we know that the array is the
5620 -- first component, but that's not such a simple case ???
5622 if Is_Packed (Ptyp) then
5623 return True;
5624 end if;
5626 -- We are in trouble if there is a component clause, and
5627 -- either we do not know the alignment of the slice, or
5628 -- the alignment of the slice is inconsistent with the
5629 -- bit position specified by the component clause.
5631 declare
5632 Field : constant Entity_Id := Entity (Selector_Name (Pref));
5633 begin
5634 if Present (Component_Clause (Field))
5635 and then
5636 (Unknown_Alignment (Styp)
5637 or else
5638 (Component_Bit_Offset (Field) mod
5639 (System_Storage_Unit * Alignment (Styp))) /= 0)
5640 then
5641 return True;
5642 end if;
5643 end;
5645 -- For cases other than selected or indexed components we know we
5646 -- are OK, since no issues arise over alignment.
5648 else
5649 return False;
5650 end if;
5652 -- We processed an indexed component or selected component
5653 -- reference that looked safe, so keep checking prefixes.
5655 Pref := Prefix (Pref);
5656 end loop;
5657 end;
5658 end Is_Possibly_Unaligned_Slice;
5660 -------------------------------
5661 -- Is_Related_To_Func_Return --
5662 -------------------------------
5664 function Is_Related_To_Func_Return (Id : Entity_Id) return Boolean is
5665 Expr : constant Node_Id := Related_Expression (Id);
5666 begin
5667 return
5668 Present (Expr)
5669 and then Nkind (Expr) = N_Explicit_Dereference
5670 and then Nkind (Parent (Expr)) = N_Simple_Return_Statement;
5671 end Is_Related_To_Func_Return;
5673 --------------------------------
5674 -- Is_Ref_To_Bit_Packed_Array --
5675 --------------------------------
5677 function Is_Ref_To_Bit_Packed_Array (N : Node_Id) return Boolean is
5678 Result : Boolean;
5679 Expr : Node_Id;
5681 begin
5682 if Is_Entity_Name (N)
5683 and then Is_Object (Entity (N))
5684 and then Present (Renamed_Object (Entity (N)))
5685 then
5686 return Is_Ref_To_Bit_Packed_Array (Renamed_Object (Entity (N)));
5687 end if;
5689 if Nkind_In (N, N_Indexed_Component, N_Selected_Component) then
5690 if Is_Bit_Packed_Array (Etype (Prefix (N))) then
5691 Result := True;
5692 else
5693 Result := Is_Ref_To_Bit_Packed_Array (Prefix (N));
5694 end if;
5696 if Result and then Nkind (N) = N_Indexed_Component then
5697 Expr := First (Expressions (N));
5698 while Present (Expr) loop
5699 Force_Evaluation (Expr);
5700 Next (Expr);
5701 end loop;
5702 end if;
5704 return Result;
5706 else
5707 return False;
5708 end if;
5709 end Is_Ref_To_Bit_Packed_Array;
5711 --------------------------------
5712 -- Is_Ref_To_Bit_Packed_Slice --
5713 --------------------------------
5715 function Is_Ref_To_Bit_Packed_Slice (N : Node_Id) return Boolean is
5716 begin
5717 if Nkind (N) = N_Type_Conversion then
5718 return Is_Ref_To_Bit_Packed_Slice (Expression (N));
5720 elsif Is_Entity_Name (N)
5721 and then Is_Object (Entity (N))
5722 and then Present (Renamed_Object (Entity (N)))
5723 then
5724 return Is_Ref_To_Bit_Packed_Slice (Renamed_Object (Entity (N)));
5726 elsif Nkind (N) = N_Slice
5727 and then Is_Bit_Packed_Array (Etype (Prefix (N)))
5728 then
5729 return True;
5731 elsif Nkind_In (N, N_Indexed_Component, N_Selected_Component) then
5732 return Is_Ref_To_Bit_Packed_Slice (Prefix (N));
5734 else
5735 return False;
5736 end if;
5737 end Is_Ref_To_Bit_Packed_Slice;
5739 -----------------------
5740 -- Is_Renamed_Object --
5741 -----------------------
5743 function Is_Renamed_Object (N : Node_Id) return Boolean is
5744 Pnod : constant Node_Id := Parent (N);
5745 Kind : constant Node_Kind := Nkind (Pnod);
5746 begin
5747 if Kind = N_Object_Renaming_Declaration then
5748 return True;
5749 elsif Nkind_In (Kind, N_Indexed_Component, N_Selected_Component) then
5750 return Is_Renamed_Object (Pnod);
5751 else
5752 return False;
5753 end if;
5754 end Is_Renamed_Object;
5756 --------------------------------------
5757 -- Is_Secondary_Stack_BIP_Func_Call --
5758 --------------------------------------
5760 function Is_Secondary_Stack_BIP_Func_Call (Expr : Node_Id) return Boolean is
5761 Alloc_Nam : Name_Id := No_Name;
5762 Actual : Node_Id;
5763 Call : Node_Id := Expr;
5764 Formal : Node_Id;
5765 Param : Node_Id;
5767 begin
5768 -- Build-in-place calls usually appear in 'reference format. Note that
5769 -- the accessibility check machinery may add an extra 'reference due to
5770 -- side effect removal.
5772 while Nkind (Call) = N_Reference loop
5773 Call := Prefix (Call);
5774 end loop;
5776 if Nkind_In (Call, N_Qualified_Expression,
5777 N_Unchecked_Type_Conversion)
5778 then
5779 Call := Expression (Call);
5780 end if;
5782 if Is_Build_In_Place_Function_Call (Call) then
5784 -- Examine all parameter associations of the function call
5786 Param := First (Parameter_Associations (Call));
5787 while Present (Param) loop
5788 if Nkind (Param) = N_Parameter_Association
5789 and then Nkind (Selector_Name (Param)) = N_Identifier
5790 then
5791 Formal := Selector_Name (Param);
5792 Actual := Explicit_Actual_Parameter (Param);
5794 -- Construct the name of formal BIPalloc. It is much easier to
5795 -- extract the name of the function using an arbitrary formal's
5796 -- scope rather than the Name field of Call.
5798 if Alloc_Nam = No_Name and then Present (Entity (Formal)) then
5799 Alloc_Nam :=
5800 New_External_Name
5801 (Chars (Scope (Entity (Formal))),
5802 BIP_Formal_Suffix (BIP_Alloc_Form));
5803 end if;
5805 -- A match for BIPalloc => 2 has been found
5807 if Chars (Formal) = Alloc_Nam
5808 and then Nkind (Actual) = N_Integer_Literal
5809 and then Intval (Actual) = Uint_2
5810 then
5811 return True;
5812 end if;
5813 end if;
5815 Next (Param);
5816 end loop;
5817 end if;
5819 return False;
5820 end Is_Secondary_Stack_BIP_Func_Call;
5822 -------------------------------------
5823 -- Is_Tag_To_Class_Wide_Conversion --
5824 -------------------------------------
5826 function Is_Tag_To_Class_Wide_Conversion
5827 (Obj_Id : Entity_Id) return Boolean
5829 Expr : constant Node_Id := Expression (Parent (Obj_Id));
5831 begin
5832 return
5833 Is_Class_Wide_Type (Etype (Obj_Id))
5834 and then Present (Expr)
5835 and then Nkind (Expr) = N_Unchecked_Type_Conversion
5836 and then Etype (Expression (Expr)) = RTE (RE_Tag);
5837 end Is_Tag_To_Class_Wide_Conversion;
5839 ----------------------------
5840 -- Is_Untagged_Derivation --
5841 ----------------------------
5843 function Is_Untagged_Derivation (T : Entity_Id) return Boolean is
5844 begin
5845 return (not Is_Tagged_Type (T) and then Is_Derived_Type (T))
5846 or else
5847 (Is_Private_Type (T) and then Present (Full_View (T))
5848 and then not Is_Tagged_Type (Full_View (T))
5849 and then Is_Derived_Type (Full_View (T))
5850 and then Etype (Full_View (T)) /= T);
5851 end Is_Untagged_Derivation;
5853 ---------------------------
5854 -- Is_Volatile_Reference --
5855 ---------------------------
5857 function Is_Volatile_Reference (N : Node_Id) return Boolean is
5858 begin
5859 -- Only source references are to be treated as volatile, internally
5860 -- generated stuff cannot have volatile external effects.
5862 if not Comes_From_Source (N) then
5863 return False;
5865 -- Never true for reference to a type
5867 elsif Is_Entity_Name (N) and then Is_Type (Entity (N)) then
5868 return False;
5870 -- Never true for a compile time known constant
5872 elsif Compile_Time_Known_Value (N) then
5873 return False;
5875 -- True if object reference with volatile type
5877 elsif Is_Volatile_Object (N) then
5878 return True;
5880 -- True if reference to volatile entity
5882 elsif Is_Entity_Name (N) then
5883 return Treat_As_Volatile (Entity (N));
5885 -- True for slice of volatile array
5887 elsif Nkind (N) = N_Slice then
5888 return Is_Volatile_Reference (Prefix (N));
5890 -- True if volatile component
5892 elsif Nkind_In (N, N_Indexed_Component, N_Selected_Component) then
5893 if (Is_Entity_Name (Prefix (N))
5894 and then Has_Volatile_Components (Entity (Prefix (N))))
5895 or else (Present (Etype (Prefix (N)))
5896 and then Has_Volatile_Components (Etype (Prefix (N))))
5897 then
5898 return True;
5899 else
5900 return Is_Volatile_Reference (Prefix (N));
5901 end if;
5903 -- Otherwise false
5905 else
5906 return False;
5907 end if;
5908 end Is_Volatile_Reference;
5910 --------------------
5911 -- Kill_Dead_Code --
5912 --------------------
5914 procedure Kill_Dead_Code (N : Node_Id; Warn : Boolean := False) is
5915 W : Boolean := Warn;
5916 -- Set False if warnings suppressed
5918 begin
5919 if Present (N) then
5920 Remove_Warning_Messages (N);
5922 -- Generate warning if appropriate
5924 if W then
5926 -- We suppress the warning if this code is under control of an
5927 -- if statement, whose condition is a simple identifier, and
5928 -- either we are in an instance, or warnings off is set for this
5929 -- identifier. The reason for killing it in the instance case is
5930 -- that it is common and reasonable for code to be deleted in
5931 -- instances for various reasons.
5933 -- Could we use Is_Statically_Unevaluated here???
5935 if Nkind (Parent (N)) = N_If_Statement then
5936 declare
5937 C : constant Node_Id := Condition (Parent (N));
5938 begin
5939 if Nkind (C) = N_Identifier
5940 and then
5941 (In_Instance
5942 or else (Present (Entity (C))
5943 and then Has_Warnings_Off (Entity (C))))
5944 then
5945 W := False;
5946 end if;
5947 end;
5948 end if;
5950 -- Generate warning if not suppressed
5952 if W then
5953 Error_Msg_F
5954 ("?t?this code can never be executed and has been deleted!",
5956 end if;
5957 end if;
5959 -- Recurse into block statements and bodies to process declarations
5960 -- and statements.
5962 if Nkind (N) = N_Block_Statement
5963 or else Nkind (N) = N_Subprogram_Body
5964 or else Nkind (N) = N_Package_Body
5965 then
5966 Kill_Dead_Code (Declarations (N), False);
5967 Kill_Dead_Code (Statements (Handled_Statement_Sequence (N)));
5969 if Nkind (N) = N_Subprogram_Body then
5970 Set_Is_Eliminated (Defining_Entity (N));
5971 end if;
5973 elsif Nkind (N) = N_Package_Declaration then
5974 Kill_Dead_Code (Visible_Declarations (Specification (N)));
5975 Kill_Dead_Code (Private_Declarations (Specification (N)));
5977 -- ??? After this point, Delete_Tree has been called on all
5978 -- declarations in Specification (N), so references to entities
5979 -- therein look suspicious.
5981 declare
5982 E : Entity_Id := First_Entity (Defining_Entity (N));
5984 begin
5985 while Present (E) loop
5986 if Ekind (E) = E_Operator then
5987 Set_Is_Eliminated (E);
5988 end if;
5990 Next_Entity (E);
5991 end loop;
5992 end;
5994 -- Recurse into composite statement to kill individual statements in
5995 -- particular instantiations.
5997 elsif Nkind (N) = N_If_Statement then
5998 Kill_Dead_Code (Then_Statements (N));
5999 Kill_Dead_Code (Elsif_Parts (N));
6000 Kill_Dead_Code (Else_Statements (N));
6002 elsif Nkind (N) = N_Loop_Statement then
6003 Kill_Dead_Code (Statements (N));
6005 elsif Nkind (N) = N_Case_Statement then
6006 declare
6007 Alt : Node_Id;
6008 begin
6009 Alt := First (Alternatives (N));
6010 while Present (Alt) loop
6011 Kill_Dead_Code (Statements (Alt));
6012 Next (Alt);
6013 end loop;
6014 end;
6016 elsif Nkind (N) = N_Case_Statement_Alternative then
6017 Kill_Dead_Code (Statements (N));
6019 -- Deal with dead instances caused by deleting instantiations
6021 elsif Nkind (N) in N_Generic_Instantiation then
6022 Remove_Dead_Instance (N);
6023 end if;
6024 end if;
6025 end Kill_Dead_Code;
6027 -- Case where argument is a list of nodes to be killed
6029 procedure Kill_Dead_Code (L : List_Id; Warn : Boolean := False) is
6030 N : Node_Id;
6031 W : Boolean;
6033 begin
6034 W := Warn;
6036 if Is_Non_Empty_List (L) then
6037 N := First (L);
6038 while Present (N) loop
6039 Kill_Dead_Code (N, W);
6040 W := False;
6041 Next (N);
6042 end loop;
6043 end if;
6044 end Kill_Dead_Code;
6046 ------------------------
6047 -- Known_Non_Negative --
6048 ------------------------
6050 function Known_Non_Negative (Opnd : Node_Id) return Boolean is
6051 begin
6052 if Is_OK_Static_Expression (Opnd) and then Expr_Value (Opnd) >= 0 then
6053 return True;
6055 else
6056 declare
6057 Lo : constant Node_Id := Type_Low_Bound (Etype (Opnd));
6058 begin
6059 return
6060 Is_OK_Static_Expression (Lo) and then Expr_Value (Lo) >= 0;
6061 end;
6062 end if;
6063 end Known_Non_Negative;
6065 --------------------
6066 -- Known_Non_Null --
6067 --------------------
6069 function Known_Non_Null (N : Node_Id) return Boolean is
6070 begin
6071 -- Checks for case where N is an entity reference
6073 if Is_Entity_Name (N) and then Present (Entity (N)) then
6074 declare
6075 E : constant Entity_Id := Entity (N);
6076 Op : Node_Kind;
6077 Val : Node_Id;
6079 begin
6080 -- First check if we are in decisive conditional
6082 Get_Current_Value_Condition (N, Op, Val);
6084 if Known_Null (Val) then
6085 if Op = N_Op_Eq then
6086 return False;
6087 elsif Op = N_Op_Ne then
6088 return True;
6089 end if;
6090 end if;
6092 -- If OK to do replacement, test Is_Known_Non_Null flag
6094 if OK_To_Do_Constant_Replacement (E) then
6095 return Is_Known_Non_Null (E);
6097 -- Otherwise if not safe to do replacement, then say so
6099 else
6100 return False;
6101 end if;
6102 end;
6104 -- True if access attribute
6106 elsif Nkind (N) = N_Attribute_Reference
6107 and then Nam_In (Attribute_Name (N), Name_Access,
6108 Name_Unchecked_Access,
6109 Name_Unrestricted_Access)
6110 then
6111 return True;
6113 -- True if allocator
6115 elsif Nkind (N) = N_Allocator then
6116 return True;
6118 -- For a conversion, true if expression is known non-null
6120 elsif Nkind (N) = N_Type_Conversion then
6121 return Known_Non_Null (Expression (N));
6123 -- Above are all cases where the value could be determined to be
6124 -- non-null. In all other cases, we don't know, so return False.
6126 else
6127 return False;
6128 end if;
6129 end Known_Non_Null;
6131 ----------------
6132 -- Known_Null --
6133 ----------------
6135 function Known_Null (N : Node_Id) return Boolean is
6136 begin
6137 -- Checks for case where N is an entity reference
6139 if Is_Entity_Name (N) and then Present (Entity (N)) then
6140 declare
6141 E : constant Entity_Id := Entity (N);
6142 Op : Node_Kind;
6143 Val : Node_Id;
6145 begin
6146 -- Constant null value is for sure null
6148 if Ekind (E) = E_Constant
6149 and then Known_Null (Constant_Value (E))
6150 then
6151 return True;
6152 end if;
6154 -- First check if we are in decisive conditional
6156 Get_Current_Value_Condition (N, Op, Val);
6158 if Known_Null (Val) then
6159 if Op = N_Op_Eq then
6160 return True;
6161 elsif Op = N_Op_Ne then
6162 return False;
6163 end if;
6164 end if;
6166 -- If OK to do replacement, test Is_Known_Null flag
6168 if OK_To_Do_Constant_Replacement (E) then
6169 return Is_Known_Null (E);
6171 -- Otherwise if not safe to do replacement, then say so
6173 else
6174 return False;
6175 end if;
6176 end;
6178 -- True if explicit reference to null
6180 elsif Nkind (N) = N_Null then
6181 return True;
6183 -- For a conversion, true if expression is known null
6185 elsif Nkind (N) = N_Type_Conversion then
6186 return Known_Null (Expression (N));
6188 -- Above are all cases where the value could be determined to be null.
6189 -- In all other cases, we don't know, so return False.
6191 else
6192 return False;
6193 end if;
6194 end Known_Null;
6196 -----------------------------
6197 -- Make_CW_Equivalent_Type --
6198 -----------------------------
6200 -- Create a record type used as an equivalent of any member of the class
6201 -- which takes its size from exp.
6203 -- Generate the following code:
6205 -- type Equiv_T is record
6206 -- _parent : T (List of discriminant constraints taken from Exp);
6207 -- Ext__50 : Storage_Array (1 .. (Exp'size - Typ'object_size)/8);
6208 -- end Equiv_T;
6210 -- ??? Note that this type does not guarantee same alignment as all
6211 -- derived types
6213 function Make_CW_Equivalent_Type
6214 (T : Entity_Id;
6215 E : Node_Id) return Entity_Id
6217 Loc : constant Source_Ptr := Sloc (E);
6218 Root_Typ : constant Entity_Id := Root_Type (T);
6219 List_Def : constant List_Id := Empty_List;
6220 Comp_List : constant List_Id := New_List;
6221 Equiv_Type : Entity_Id;
6222 Range_Type : Entity_Id;
6223 Str_Type : Entity_Id;
6224 Constr_Root : Entity_Id;
6225 Sizexpr : Node_Id;
6227 begin
6228 -- If the root type is already constrained, there are no discriminants
6229 -- in the expression.
6231 if not Has_Discriminants (Root_Typ)
6232 or else Is_Constrained (Root_Typ)
6233 then
6234 Constr_Root := Root_Typ;
6236 -- At this point in the expansion, non-limited view of the type
6237 -- must be available, otherwise the error will be reported later.
6239 if From_Limited_With (Constr_Root)
6240 and then Present (Non_Limited_View (Constr_Root))
6241 then
6242 Constr_Root := Non_Limited_View (Constr_Root);
6243 end if;
6245 else
6246 Constr_Root := Make_Temporary (Loc, 'R');
6248 -- subtype cstr__n is T (List of discr constraints taken from Exp)
6250 Append_To (List_Def,
6251 Make_Subtype_Declaration (Loc,
6252 Defining_Identifier => Constr_Root,
6253 Subtype_Indication => Make_Subtype_From_Expr (E, Root_Typ)));
6254 end if;
6256 -- Generate the range subtype declaration
6258 Range_Type := Make_Temporary (Loc, 'G');
6260 if not Is_Interface (Root_Typ) then
6262 -- subtype rg__xx is
6263 -- Storage_Offset range 1 .. (Expr'size - typ'size) / Storage_Unit
6265 Sizexpr :=
6266 Make_Op_Subtract (Loc,
6267 Left_Opnd =>
6268 Make_Attribute_Reference (Loc,
6269 Prefix =>
6270 OK_Convert_To (T, Duplicate_Subexpr_No_Checks (E)),
6271 Attribute_Name => Name_Size),
6272 Right_Opnd =>
6273 Make_Attribute_Reference (Loc,
6274 Prefix => New_Occurrence_Of (Constr_Root, Loc),
6275 Attribute_Name => Name_Object_Size));
6276 else
6277 -- subtype rg__xx is
6278 -- Storage_Offset range 1 .. Expr'size / Storage_Unit
6280 Sizexpr :=
6281 Make_Attribute_Reference (Loc,
6282 Prefix =>
6283 OK_Convert_To (T, Duplicate_Subexpr_No_Checks (E)),
6284 Attribute_Name => Name_Size);
6285 end if;
6287 Set_Paren_Count (Sizexpr, 1);
6289 Append_To (List_Def,
6290 Make_Subtype_Declaration (Loc,
6291 Defining_Identifier => Range_Type,
6292 Subtype_Indication =>
6293 Make_Subtype_Indication (Loc,
6294 Subtype_Mark => New_Occurrence_Of (RTE (RE_Storage_Offset), Loc),
6295 Constraint => Make_Range_Constraint (Loc,
6296 Range_Expression =>
6297 Make_Range (Loc,
6298 Low_Bound => Make_Integer_Literal (Loc, 1),
6299 High_Bound =>
6300 Make_Op_Divide (Loc,
6301 Left_Opnd => Sizexpr,
6302 Right_Opnd => Make_Integer_Literal (Loc,
6303 Intval => System_Storage_Unit)))))));
6305 -- subtype str__nn is Storage_Array (rg__x);
6307 Str_Type := Make_Temporary (Loc, 'S');
6308 Append_To (List_Def,
6309 Make_Subtype_Declaration (Loc,
6310 Defining_Identifier => Str_Type,
6311 Subtype_Indication =>
6312 Make_Subtype_Indication (Loc,
6313 Subtype_Mark => New_Occurrence_Of (RTE (RE_Storage_Array), Loc),
6314 Constraint =>
6315 Make_Index_Or_Discriminant_Constraint (Loc,
6316 Constraints =>
6317 New_List (New_Occurrence_Of (Range_Type, Loc))))));
6319 -- type Equiv_T is record
6320 -- [ _parent : Tnn; ]
6321 -- E : Str_Type;
6322 -- end Equiv_T;
6324 Equiv_Type := Make_Temporary (Loc, 'T');
6325 Set_Ekind (Equiv_Type, E_Record_Type);
6326 Set_Parent_Subtype (Equiv_Type, Constr_Root);
6328 -- Set Is_Class_Wide_Equivalent_Type very early to trigger the special
6329 -- treatment for this type. In particular, even though _parent's type
6330 -- is a controlled type or contains controlled components, we do not
6331 -- want to set Has_Controlled_Component on it to avoid making it gain
6332 -- an unwanted _controller component.
6334 Set_Is_Class_Wide_Equivalent_Type (Equiv_Type);
6336 -- A class-wide equivalent type does not require initialization
6338 Set_Suppress_Initialization (Equiv_Type);
6340 if not Is_Interface (Root_Typ) then
6341 Append_To (Comp_List,
6342 Make_Component_Declaration (Loc,
6343 Defining_Identifier =>
6344 Make_Defining_Identifier (Loc, Name_uParent),
6345 Component_Definition =>
6346 Make_Component_Definition (Loc,
6347 Aliased_Present => False,
6348 Subtype_Indication => New_Occurrence_Of (Constr_Root, Loc))));
6349 end if;
6351 Append_To (Comp_List,
6352 Make_Component_Declaration (Loc,
6353 Defining_Identifier => Make_Temporary (Loc, 'C'),
6354 Component_Definition =>
6355 Make_Component_Definition (Loc,
6356 Aliased_Present => False,
6357 Subtype_Indication => New_Occurrence_Of (Str_Type, Loc))));
6359 Append_To (List_Def,
6360 Make_Full_Type_Declaration (Loc,
6361 Defining_Identifier => Equiv_Type,
6362 Type_Definition =>
6363 Make_Record_Definition (Loc,
6364 Component_List =>
6365 Make_Component_List (Loc,
6366 Component_Items => Comp_List,
6367 Variant_Part => Empty))));
6369 -- Suppress all checks during the analysis of the expanded code to avoid
6370 -- the generation of spurious warnings under ZFP run-time.
6372 Insert_Actions (E, List_Def, Suppress => All_Checks);
6373 return Equiv_Type;
6374 end Make_CW_Equivalent_Type;
6376 -------------------------
6377 -- Make_Invariant_Call --
6378 -------------------------
6380 function Make_Invariant_Call (Expr : Node_Id) return Node_Id is
6381 Loc : constant Source_Ptr := Sloc (Expr);
6382 Typ : Entity_Id;
6384 begin
6385 Typ := Etype (Expr);
6387 -- Subtypes may be subject to invariants coming from their respective
6388 -- base types. The subtype may be fully or partially private.
6390 if Ekind_In (Typ, E_Array_Subtype,
6391 E_Private_Subtype,
6392 E_Record_Subtype,
6393 E_Record_Subtype_With_Private)
6394 then
6395 Typ := Base_Type (Typ);
6396 end if;
6398 pragma Assert
6399 (Has_Invariants (Typ) and then Present (Invariant_Procedure (Typ)));
6401 return
6402 Make_Procedure_Call_Statement (Loc,
6403 Name =>
6404 New_Occurrence_Of (Invariant_Procedure (Typ), Loc),
6405 Parameter_Associations => New_List (Relocate_Node (Expr)));
6406 end Make_Invariant_Call;
6408 ------------------------
6409 -- Make_Literal_Range --
6410 ------------------------
6412 function Make_Literal_Range
6413 (Loc : Source_Ptr;
6414 Literal_Typ : Entity_Id) return Node_Id
6416 Lo : constant Node_Id :=
6417 New_Copy_Tree (String_Literal_Low_Bound (Literal_Typ));
6418 Index : constant Entity_Id := Etype (Lo);
6420 Hi : Node_Id;
6421 Length_Expr : constant Node_Id :=
6422 Make_Op_Subtract (Loc,
6423 Left_Opnd =>
6424 Make_Integer_Literal (Loc,
6425 Intval => String_Literal_Length (Literal_Typ)),
6426 Right_Opnd =>
6427 Make_Integer_Literal (Loc, 1));
6429 begin
6430 Set_Analyzed (Lo, False);
6432 if Is_Integer_Type (Index) then
6433 Hi :=
6434 Make_Op_Add (Loc,
6435 Left_Opnd => New_Copy_Tree (Lo),
6436 Right_Opnd => Length_Expr);
6437 else
6438 Hi :=
6439 Make_Attribute_Reference (Loc,
6440 Attribute_Name => Name_Val,
6441 Prefix => New_Occurrence_Of (Index, Loc),
6442 Expressions => New_List (
6443 Make_Op_Add (Loc,
6444 Left_Opnd =>
6445 Make_Attribute_Reference (Loc,
6446 Attribute_Name => Name_Pos,
6447 Prefix => New_Occurrence_Of (Index, Loc),
6448 Expressions => New_List (New_Copy_Tree (Lo))),
6449 Right_Opnd => Length_Expr)));
6450 end if;
6452 return
6453 Make_Range (Loc,
6454 Low_Bound => Lo,
6455 High_Bound => Hi);
6456 end Make_Literal_Range;
6458 --------------------------
6459 -- Make_Non_Empty_Check --
6460 --------------------------
6462 function Make_Non_Empty_Check
6463 (Loc : Source_Ptr;
6464 N : Node_Id) return Node_Id
6466 begin
6467 return
6468 Make_Op_Ne (Loc,
6469 Left_Opnd =>
6470 Make_Attribute_Reference (Loc,
6471 Attribute_Name => Name_Length,
6472 Prefix => Duplicate_Subexpr_No_Checks (N, Name_Req => True)),
6473 Right_Opnd =>
6474 Make_Integer_Literal (Loc, 0));
6475 end Make_Non_Empty_Check;
6477 -------------------------
6478 -- Make_Predicate_Call --
6479 -------------------------
6481 function Make_Predicate_Call
6482 (Typ : Entity_Id;
6483 Expr : Node_Id;
6484 Mem : Boolean := False) return Node_Id
6486 Loc : constant Source_Ptr := Sloc (Expr);
6487 Call : Node_Id;
6488 PFM : Entity_Id;
6490 Save_Ghost_Mode : constant Ghost_Mode_Type := Ghost_Mode;
6492 begin
6493 pragma Assert (Present (Predicate_Function (Typ)));
6495 -- The related type may be subject to pragma Ghost. Set the mode now to
6496 -- ensure that the call is properly marked as Ghost.
6498 Set_Ghost_Mode_From_Entity (Typ);
6500 -- Call special membership version if requested and available
6502 if Mem then
6503 PFM := Predicate_Function_M (Typ);
6505 if Present (PFM) then
6506 Call :=
6507 Make_Function_Call (Loc,
6508 Name => New_Occurrence_Of (PFM, Loc),
6509 Parameter_Associations => New_List (Relocate_Node (Expr)));
6511 Ghost_Mode := Save_Ghost_Mode;
6512 return Call;
6513 end if;
6514 end if;
6516 -- Case of calling normal predicate function
6518 Call :=
6519 Make_Function_Call (Loc,
6520 Name =>
6521 New_Occurrence_Of (Predicate_Function (Typ), Loc),
6522 Parameter_Associations => New_List (Relocate_Node (Expr)));
6524 Ghost_Mode := Save_Ghost_Mode;
6525 return Call;
6526 end Make_Predicate_Call;
6528 --------------------------
6529 -- Make_Predicate_Check --
6530 --------------------------
6532 function Make_Predicate_Check
6533 (Typ : Entity_Id;
6534 Expr : Node_Id) return Node_Id
6536 procedure Replace_Subtype_Reference (N : Node_Id);
6537 -- Replace current occurrences of the subtype to which a dynamic
6538 -- predicate applies, by the expression that triggers a predicate
6539 -- check. This is needed for aspect Predicate_Failure, for which
6540 -- we do not generate a wrapper procedure, but simply modify the
6541 -- expression for the pragma of the predicate check.
6543 --------------------------------
6544 -- Replace_Subtype_Reference --
6545 --------------------------------
6547 procedure Replace_Subtype_Reference (N : Node_Id) is
6548 begin
6549 Rewrite (N, New_Copy_Tree (Expr));
6551 -- We want to treat the node as if it comes from source, so
6552 -- that ASIS will not ignore it.
6554 Set_Comes_From_Source (N, True);
6555 end Replace_Subtype_Reference;
6557 procedure Replace_Subtype_References is
6558 new Replace_Type_References_Generic (Replace_Subtype_Reference);
6560 -- Local variables
6562 Loc : constant Source_Ptr := Sloc (Expr);
6563 Arg_List : List_Id;
6564 Fail_Expr : Node_Id;
6565 Nam : Name_Id;
6567 -- Start of processing for Make_Predicate_Check
6569 begin
6570 -- If predicate checks are suppressed, then return a null statement. For
6571 -- this call, we check only the scope setting. If the caller wants to
6572 -- check a specific entity's setting, they must do it manually.
6574 if Predicate_Checks_Suppressed (Empty) then
6575 return Make_Null_Statement (Loc);
6576 end if;
6578 -- Do not generate a check within an internal subprogram (stream
6579 -- functions and the like, including including predicate functions).
6581 if Within_Internal_Subprogram then
6582 return Make_Null_Statement (Loc);
6583 end if;
6585 -- Compute proper name to use, we need to get this right so that the
6586 -- right set of check policies apply to the Check pragma we are making.
6588 if Has_Dynamic_Predicate_Aspect (Typ) then
6589 Nam := Name_Dynamic_Predicate;
6590 elsif Has_Static_Predicate_Aspect (Typ) then
6591 Nam := Name_Static_Predicate;
6592 else
6593 Nam := Name_Predicate;
6594 end if;
6596 Arg_List := New_List (
6597 Make_Pragma_Argument_Association (Loc,
6598 Expression => Make_Identifier (Loc, Nam)),
6599 Make_Pragma_Argument_Association (Loc,
6600 Expression => Make_Predicate_Call (Typ, Expr)));
6602 -- If subtype has Predicate_Failure defined, add the correponding
6603 -- expression as an additional pragma parameter, after replacing
6604 -- current instances with the expression being checked.
6606 if Has_Aspect (Typ, Aspect_Predicate_Failure) then
6607 Fail_Expr :=
6608 New_Copy_Tree
6609 (Expression (Find_Aspect (Typ, Aspect_Predicate_Failure)));
6610 Replace_Subtype_References (Fail_Expr, Typ);
6612 Append_To (Arg_List,
6613 Make_Pragma_Argument_Association (Loc,
6614 Expression => Fail_Expr));
6615 end if;
6617 return
6618 Make_Pragma (Loc,
6619 Pragma_Identifier => Make_Identifier (Loc, Name_Check),
6620 Pragma_Argument_Associations => Arg_List);
6621 end Make_Predicate_Check;
6623 ----------------------------
6624 -- Make_Subtype_From_Expr --
6625 ----------------------------
6627 -- 1. If Expr is an unconstrained array expression, creates
6628 -- Unc_Type(Expr'first(1)..Expr'last(1),..., Expr'first(n)..Expr'last(n))
6630 -- 2. If Expr is a unconstrained discriminated type expression, creates
6631 -- Unc_Type(Expr.Discr1, ... , Expr.Discr_n)
6633 -- 3. If Expr is class-wide, creates an implicit class-wide subtype
6635 function Make_Subtype_From_Expr
6636 (E : Node_Id;
6637 Unc_Typ : Entity_Id;
6638 Related_Id : Entity_Id := Empty) return Node_Id
6640 List_Constr : constant List_Id := New_List;
6641 Loc : constant Source_Ptr := Sloc (E);
6642 D : Entity_Id;
6643 Full_Exp : Node_Id;
6644 Full_Subtyp : Entity_Id;
6645 High_Bound : Entity_Id;
6646 Index_Typ : Entity_Id;
6647 Low_Bound : Entity_Id;
6648 Priv_Subtyp : Entity_Id;
6649 Utyp : Entity_Id;
6651 begin
6652 if Is_Private_Type (Unc_Typ)
6653 and then Has_Unknown_Discriminants (Unc_Typ)
6654 then
6655 -- The caller requests a unique external name for both the private
6656 -- and the full subtype.
6658 if Present (Related_Id) then
6659 Full_Subtyp :=
6660 Make_Defining_Identifier (Loc,
6661 Chars => New_External_Name (Chars (Related_Id), 'C'));
6662 Priv_Subtyp :=
6663 Make_Defining_Identifier (Loc,
6664 Chars => New_External_Name (Chars (Related_Id), 'P'));
6666 else
6667 Full_Subtyp := Make_Temporary (Loc, 'C');
6668 Priv_Subtyp := Make_Temporary (Loc, 'P');
6669 end if;
6671 -- Prepare the subtype completion. Use the base type to find the
6672 -- underlying type because the type may be a generic actual or an
6673 -- explicit subtype.
6675 Utyp := Underlying_Type (Base_Type (Unc_Typ));
6677 Full_Exp :=
6678 Unchecked_Convert_To (Utyp, Duplicate_Subexpr_No_Checks (E));
6679 Set_Parent (Full_Exp, Parent (E));
6681 Insert_Action (E,
6682 Make_Subtype_Declaration (Loc,
6683 Defining_Identifier => Full_Subtyp,
6684 Subtype_Indication => Make_Subtype_From_Expr (Full_Exp, Utyp)));
6686 -- Define the dummy private subtype
6688 Set_Ekind (Priv_Subtyp, Subtype_Kind (Ekind (Unc_Typ)));
6689 Set_Etype (Priv_Subtyp, Base_Type (Unc_Typ));
6690 Set_Scope (Priv_Subtyp, Full_Subtyp);
6691 Set_Is_Constrained (Priv_Subtyp);
6692 Set_Is_Tagged_Type (Priv_Subtyp, Is_Tagged_Type (Unc_Typ));
6693 Set_Is_Itype (Priv_Subtyp);
6694 Set_Associated_Node_For_Itype (Priv_Subtyp, E);
6696 if Is_Tagged_Type (Priv_Subtyp) then
6697 Set_Class_Wide_Type
6698 (Base_Type (Priv_Subtyp), Class_Wide_Type (Unc_Typ));
6699 Set_Direct_Primitive_Operations (Priv_Subtyp,
6700 Direct_Primitive_Operations (Unc_Typ));
6701 end if;
6703 Set_Full_View (Priv_Subtyp, Full_Subtyp);
6705 return New_Occurrence_Of (Priv_Subtyp, Loc);
6707 elsif Is_Array_Type (Unc_Typ) then
6708 Index_Typ := First_Index (Unc_Typ);
6709 for J in 1 .. Number_Dimensions (Unc_Typ) loop
6711 -- Capture the bounds of each index constraint in case the context
6712 -- is an object declaration of an unconstrained type initialized
6713 -- by a function call:
6715 -- Obj : Unconstr_Typ := Func_Call;
6717 -- This scenario requires secondary scope management and the index
6718 -- constraint cannot depend on the temporary used to capture the
6719 -- result of the function call.
6721 -- SS_Mark;
6722 -- Temp : Unconstr_Typ_Ptr := Func_Call'reference;
6723 -- subtype S is Unconstr_Typ (Temp.all'First .. Temp.all'Last);
6724 -- Obj : S := Temp.all;
6725 -- SS_Release; -- Temp is gone at this point, bounds of S are
6726 -- -- non existent.
6728 -- Generate:
6729 -- Low_Bound : constant Base_Type (Index_Typ) := E'First (J);
6731 Low_Bound := Make_Temporary (Loc, 'B');
6732 Insert_Action (E,
6733 Make_Object_Declaration (Loc,
6734 Defining_Identifier => Low_Bound,
6735 Object_Definition =>
6736 New_Occurrence_Of (Base_Type (Etype (Index_Typ)), Loc),
6737 Constant_Present => True,
6738 Expression =>
6739 Make_Attribute_Reference (Loc,
6740 Prefix => Duplicate_Subexpr_No_Checks (E),
6741 Attribute_Name => Name_First,
6742 Expressions => New_List (
6743 Make_Integer_Literal (Loc, J)))));
6745 -- Generate:
6746 -- High_Bound : constant Base_Type (Index_Typ) := E'Last (J);
6748 High_Bound := Make_Temporary (Loc, 'B');
6749 Insert_Action (E,
6750 Make_Object_Declaration (Loc,
6751 Defining_Identifier => High_Bound,
6752 Object_Definition =>
6753 New_Occurrence_Of (Base_Type (Etype (Index_Typ)), Loc),
6754 Constant_Present => True,
6755 Expression =>
6756 Make_Attribute_Reference (Loc,
6757 Prefix => Duplicate_Subexpr_No_Checks (E),
6758 Attribute_Name => Name_Last,
6759 Expressions => New_List (
6760 Make_Integer_Literal (Loc, J)))));
6762 Append_To (List_Constr,
6763 Make_Range (Loc,
6764 Low_Bound => New_Occurrence_Of (Low_Bound, Loc),
6765 High_Bound => New_Occurrence_Of (High_Bound, Loc)));
6767 Index_Typ := Next_Index (Index_Typ);
6768 end loop;
6770 elsif Is_Class_Wide_Type (Unc_Typ) then
6771 declare
6772 CW_Subtype : Entity_Id;
6773 EQ_Typ : Entity_Id := Empty;
6775 begin
6776 -- A class-wide equivalent type is not needed on VM targets
6777 -- because the VM back-ends handle the class-wide object
6778 -- initialization itself (and doesn't need or want the
6779 -- additional intermediate type to handle the assignment).
6781 if Expander_Active and then Tagged_Type_Expansion then
6783 -- If this is the class-wide type of a completion that is a
6784 -- record subtype, set the type of the class-wide type to be
6785 -- the full base type, for use in the expanded code for the
6786 -- equivalent type. Should this be done earlier when the
6787 -- completion is analyzed ???
6789 if Is_Private_Type (Etype (Unc_Typ))
6790 and then
6791 Ekind (Full_View (Etype (Unc_Typ))) = E_Record_Subtype
6792 then
6793 Set_Etype (Unc_Typ, Base_Type (Full_View (Etype (Unc_Typ))));
6794 end if;
6796 EQ_Typ := Make_CW_Equivalent_Type (Unc_Typ, E);
6797 end if;
6799 CW_Subtype := New_Class_Wide_Subtype (Unc_Typ, E);
6800 Set_Equivalent_Type (CW_Subtype, EQ_Typ);
6801 Set_Cloned_Subtype (CW_Subtype, Base_Type (Unc_Typ));
6803 return New_Occurrence_Of (CW_Subtype, Loc);
6804 end;
6806 -- Indefinite record type with discriminants
6808 else
6809 D := First_Discriminant (Unc_Typ);
6810 while Present (D) loop
6811 Append_To (List_Constr,
6812 Make_Selected_Component (Loc,
6813 Prefix => Duplicate_Subexpr_No_Checks (E),
6814 Selector_Name => New_Occurrence_Of (D, Loc)));
6816 Next_Discriminant (D);
6817 end loop;
6818 end if;
6820 return
6821 Make_Subtype_Indication (Loc,
6822 Subtype_Mark => New_Occurrence_Of (Unc_Typ, Loc),
6823 Constraint =>
6824 Make_Index_Or_Discriminant_Constraint (Loc,
6825 Constraints => List_Constr));
6826 end Make_Subtype_From_Expr;
6828 ----------------------------
6829 -- Matching_Standard_Type --
6830 ----------------------------
6832 function Matching_Standard_Type (Typ : Entity_Id) return Entity_Id is
6833 pragma Assert (Is_Scalar_Type (Typ));
6834 Siz : constant Uint := Esize (Typ);
6836 begin
6837 -- Floating-point cases
6839 if Is_Floating_Point_Type (Typ) then
6840 if Siz <= Esize (Standard_Short_Float) then
6841 return Standard_Short_Float;
6842 elsif Siz <= Esize (Standard_Float) then
6843 return Standard_Float;
6844 elsif Siz <= Esize (Standard_Long_Float) then
6845 return Standard_Long_Float;
6846 elsif Siz <= Esize (Standard_Long_Long_Float) then
6847 return Standard_Long_Long_Float;
6848 else
6849 raise Program_Error;
6850 end if;
6852 -- Integer cases (includes fixed-point types)
6854 -- Unsigned integer cases (includes normal enumeration types)
6856 elsif Is_Unsigned_Type (Typ) then
6857 if Siz <= Esize (Standard_Short_Short_Unsigned) then
6858 return Standard_Short_Short_Unsigned;
6859 elsif Siz <= Esize (Standard_Short_Unsigned) then
6860 return Standard_Short_Unsigned;
6861 elsif Siz <= Esize (Standard_Unsigned) then
6862 return Standard_Unsigned;
6863 elsif Siz <= Esize (Standard_Long_Unsigned) then
6864 return Standard_Long_Unsigned;
6865 elsif Siz <= Esize (Standard_Long_Long_Unsigned) then
6866 return Standard_Long_Long_Unsigned;
6867 else
6868 raise Program_Error;
6869 end if;
6871 -- Signed integer cases
6873 else
6874 if Siz <= Esize (Standard_Short_Short_Integer) then
6875 return Standard_Short_Short_Integer;
6876 elsif Siz <= Esize (Standard_Short_Integer) then
6877 return Standard_Short_Integer;
6878 elsif Siz <= Esize (Standard_Integer) then
6879 return Standard_Integer;
6880 elsif Siz <= Esize (Standard_Long_Integer) then
6881 return Standard_Long_Integer;
6882 elsif Siz <= Esize (Standard_Long_Long_Integer) then
6883 return Standard_Long_Long_Integer;
6884 else
6885 raise Program_Error;
6886 end if;
6887 end if;
6888 end Matching_Standard_Type;
6890 -----------------------------
6891 -- May_Generate_Large_Temp --
6892 -----------------------------
6894 -- At the current time, the only types that we return False for (i.e. where
6895 -- we decide we know they cannot generate large temps) are ones where we
6896 -- know the size is 256 bits or less at compile time, and we are still not
6897 -- doing a thorough job on arrays and records ???
6899 function May_Generate_Large_Temp (Typ : Entity_Id) return Boolean is
6900 begin
6901 if not Size_Known_At_Compile_Time (Typ) then
6902 return False;
6904 elsif Esize (Typ) /= 0 and then Esize (Typ) <= 256 then
6905 return False;
6907 elsif Is_Array_Type (Typ)
6908 and then Present (Packed_Array_Impl_Type (Typ))
6909 then
6910 return May_Generate_Large_Temp (Packed_Array_Impl_Type (Typ));
6912 -- We could do more here to find other small types ???
6914 else
6915 return True;
6916 end if;
6917 end May_Generate_Large_Temp;
6919 ------------------------
6920 -- Needs_Finalization --
6921 ------------------------
6923 function Needs_Finalization (T : Entity_Id) return Boolean is
6924 function Has_Some_Controlled_Component (Rec : Entity_Id) return Boolean;
6925 -- If type is not frozen yet, check explicitly among its components,
6926 -- because the Has_Controlled_Component flag is not necessarily set.
6928 -----------------------------------
6929 -- Has_Some_Controlled_Component --
6930 -----------------------------------
6932 function Has_Some_Controlled_Component
6933 (Rec : Entity_Id) return Boolean
6935 Comp : Entity_Id;
6937 begin
6938 if Has_Controlled_Component (Rec) then
6939 return True;
6941 elsif not Is_Frozen (Rec) then
6942 if Is_Record_Type (Rec) then
6943 Comp := First_Entity (Rec);
6945 while Present (Comp) loop
6946 if not Is_Type (Comp)
6947 and then Needs_Finalization (Etype (Comp))
6948 then
6949 return True;
6950 end if;
6952 Next_Entity (Comp);
6953 end loop;
6955 return False;
6957 else
6958 return
6959 Is_Array_Type (Rec)
6960 and then Needs_Finalization (Component_Type (Rec));
6961 end if;
6962 else
6963 return False;
6964 end if;
6965 end Has_Some_Controlled_Component;
6967 -- Start of processing for Needs_Finalization
6969 begin
6970 -- Certain run-time configurations and targets do not provide support
6971 -- for controlled types.
6973 if Restriction_Active (No_Finalization) then
6974 return False;
6976 -- C++ types are not considered controlled. It is assumed that the
6977 -- non-Ada side will handle their clean up.
6979 elsif Convention (T) = Convention_CPP then
6980 return False;
6982 -- Never needs finalization if Disable_Controlled set
6984 elsif Disable_Controlled (T) then
6985 return False;
6987 elsif Is_Class_Wide_Type (T) and then Disable_Controlled (Etype (T)) then
6988 return False;
6990 else
6991 -- Class-wide types are treated as controlled because derivations
6992 -- from the root type can introduce controlled components.
6994 return Is_Class_Wide_Type (T)
6995 or else Is_Controlled (T)
6996 or else Has_Some_Controlled_Component (T)
6997 or else
6998 (Is_Concurrent_Type (T)
6999 and then Present (Corresponding_Record_Type (T))
7000 and then Needs_Finalization (Corresponding_Record_Type (T)));
7001 end if;
7002 end Needs_Finalization;
7004 ----------------------------
7005 -- Needs_Constant_Address --
7006 ----------------------------
7008 function Needs_Constant_Address
7009 (Decl : Node_Id;
7010 Typ : Entity_Id) return Boolean
7012 begin
7014 -- If we have no initialization of any kind, then we don't need to place
7015 -- any restrictions on the address clause, because the object will be
7016 -- elaborated after the address clause is evaluated. This happens if the
7017 -- declaration has no initial expression, or the type has no implicit
7018 -- initialization, or the object is imported.
7020 -- The same holds for all initialized scalar types and all access types.
7021 -- Packed bit arrays of size up to 64 are represented using a modular
7022 -- type with an initialization (to zero) and can be processed like other
7023 -- initialized scalar types.
7025 -- If the type is controlled, code to attach the object to a
7026 -- finalization chain is generated at the point of declaration, and
7027 -- therefore the elaboration of the object cannot be delayed: the
7028 -- address expression must be a constant.
7030 if No (Expression (Decl))
7031 and then not Needs_Finalization (Typ)
7032 and then
7033 (not Has_Non_Null_Base_Init_Proc (Typ)
7034 or else Is_Imported (Defining_Identifier (Decl)))
7035 then
7036 return False;
7038 elsif (Present (Expression (Decl)) and then Is_Scalar_Type (Typ))
7039 or else Is_Access_Type (Typ)
7040 or else
7041 (Is_Bit_Packed_Array (Typ)
7042 and then Is_Modular_Integer_Type (Packed_Array_Impl_Type (Typ)))
7043 then
7044 return False;
7046 else
7048 -- Otherwise, we require the address clause to be constant because
7049 -- the call to the initialization procedure (or the attach code) has
7050 -- to happen at the point of the declaration.
7052 -- Actually the IP call has been moved to the freeze actions anyway,
7053 -- so maybe we can relax this restriction???
7055 return True;
7056 end if;
7057 end Needs_Constant_Address;
7059 ----------------------------
7060 -- New_Class_Wide_Subtype --
7061 ----------------------------
7063 function New_Class_Wide_Subtype
7064 (CW_Typ : Entity_Id;
7065 N : Node_Id) return Entity_Id
7067 Res : constant Entity_Id := Create_Itype (E_Void, N);
7068 Res_Name : constant Name_Id := Chars (Res);
7069 Res_Scope : constant Entity_Id := Scope (Res);
7071 begin
7072 Copy_Node (CW_Typ, Res);
7073 Set_Comes_From_Source (Res, False);
7074 Set_Sloc (Res, Sloc (N));
7075 Set_Is_Itype (Res);
7076 Set_Associated_Node_For_Itype (Res, N);
7077 Set_Is_Public (Res, False); -- By default, may be changed below.
7078 Set_Public_Status (Res);
7079 Set_Chars (Res, Res_Name);
7080 Set_Scope (Res, Res_Scope);
7081 Set_Ekind (Res, E_Class_Wide_Subtype);
7082 Set_Next_Entity (Res, Empty);
7083 Set_Etype (Res, Base_Type (CW_Typ));
7084 Set_Is_Frozen (Res, False);
7085 Set_Freeze_Node (Res, Empty);
7086 return (Res);
7087 end New_Class_Wide_Subtype;
7089 --------------------------------
7090 -- Non_Limited_Designated_Type --
7091 ---------------------------------
7093 function Non_Limited_Designated_Type (T : Entity_Id) return Entity_Id is
7094 Desig : constant Entity_Id := Designated_Type (T);
7095 begin
7096 if Has_Non_Limited_View (Desig) then
7097 return Non_Limited_View (Desig);
7098 else
7099 return Desig;
7100 end if;
7101 end Non_Limited_Designated_Type;
7103 -----------------------------------
7104 -- OK_To_Do_Constant_Replacement --
7105 -----------------------------------
7107 function OK_To_Do_Constant_Replacement (E : Entity_Id) return Boolean is
7108 ES : constant Entity_Id := Scope (E);
7109 CS : Entity_Id;
7111 begin
7112 -- Do not replace statically allocated objects, because they may be
7113 -- modified outside the current scope.
7115 if Is_Statically_Allocated (E) then
7116 return False;
7118 -- Do not replace aliased or volatile objects, since we don't know what
7119 -- else might change the value.
7121 elsif Is_Aliased (E) or else Treat_As_Volatile (E) then
7122 return False;
7124 -- Debug flag -gnatdM disconnects this optimization
7126 elsif Debug_Flag_MM then
7127 return False;
7129 -- Otherwise check scopes
7131 else
7132 CS := Current_Scope;
7134 loop
7135 -- If we are in right scope, replacement is safe
7137 if CS = ES then
7138 return True;
7140 -- Packages do not affect the determination of safety
7142 elsif Ekind (CS) = E_Package then
7143 exit when CS = Standard_Standard;
7144 CS := Scope (CS);
7146 -- Blocks do not affect the determination of safety
7148 elsif Ekind (CS) = E_Block then
7149 CS := Scope (CS);
7151 -- Loops do not affect the determination of safety. Note that we
7152 -- kill all current values on entry to a loop, so we are just
7153 -- talking about processing within a loop here.
7155 elsif Ekind (CS) = E_Loop then
7156 CS := Scope (CS);
7158 -- Otherwise, the reference is dubious, and we cannot be sure that
7159 -- it is safe to do the replacement.
7161 else
7162 exit;
7163 end if;
7164 end loop;
7166 return False;
7167 end if;
7168 end OK_To_Do_Constant_Replacement;
7170 ------------------------------------
7171 -- Possible_Bit_Aligned_Component --
7172 ------------------------------------
7174 function Possible_Bit_Aligned_Component (N : Node_Id) return Boolean is
7175 begin
7176 -- Do not process an unanalyzed node because it is not yet decorated and
7177 -- most checks performed below will fail.
7179 if not Analyzed (N) then
7180 return False;
7181 end if;
7183 case Nkind (N) is
7185 -- Case of indexed component
7187 when N_Indexed_Component =>
7188 declare
7189 P : constant Node_Id := Prefix (N);
7190 Ptyp : constant Entity_Id := Etype (P);
7192 begin
7193 -- If we know the component size and it is less than 64, then
7194 -- we are definitely OK. The back end always does assignment of
7195 -- misaligned small objects correctly.
7197 if Known_Static_Component_Size (Ptyp)
7198 and then Component_Size (Ptyp) <= 64
7199 then
7200 return False;
7202 -- Otherwise, we need to test the prefix, to see if we are
7203 -- indexing from a possibly unaligned component.
7205 else
7206 return Possible_Bit_Aligned_Component (P);
7207 end if;
7208 end;
7210 -- Case of selected component
7212 when N_Selected_Component =>
7213 declare
7214 P : constant Node_Id := Prefix (N);
7215 Comp : constant Entity_Id := Entity (Selector_Name (N));
7217 begin
7218 -- If there is no component clause, then we are in the clear
7219 -- since the back end will never misalign a large component
7220 -- unless it is forced to do so. In the clear means we need
7221 -- only the recursive test on the prefix.
7223 if Component_May_Be_Bit_Aligned (Comp) then
7224 return True;
7225 else
7226 return Possible_Bit_Aligned_Component (P);
7227 end if;
7228 end;
7230 -- For a slice, test the prefix, if that is possibly misaligned,
7231 -- then for sure the slice is.
7233 when N_Slice =>
7234 return Possible_Bit_Aligned_Component (Prefix (N));
7236 -- For an unchecked conversion, check whether the expression may
7237 -- be bit-aligned.
7239 when N_Unchecked_Type_Conversion =>
7240 return Possible_Bit_Aligned_Component (Expression (N));
7242 -- If we have none of the above, it means that we have fallen off the
7243 -- top testing prefixes recursively, and we now have a stand alone
7244 -- object, where we don't have a problem, unless this is a renaming,
7245 -- in which case we need to look into the renamed object.
7247 when others =>
7248 if Is_Entity_Name (N)
7249 and then Present (Renamed_Object (Entity (N)))
7250 then
7251 return
7252 Possible_Bit_Aligned_Component (Renamed_Object (Entity (N)));
7253 else
7254 return False;
7255 end if;
7257 end case;
7258 end Possible_Bit_Aligned_Component;
7260 -----------------------------------------------
7261 -- Process_Statements_For_Controlled_Objects --
7262 -----------------------------------------------
7264 procedure Process_Statements_For_Controlled_Objects (N : Node_Id) is
7265 Loc : constant Source_Ptr := Sloc (N);
7267 function Are_Wrapped (L : List_Id) return Boolean;
7268 -- Determine whether list L contains only one statement which is a block
7270 function Wrap_Statements_In_Block
7271 (L : List_Id;
7272 Scop : Entity_Id := Current_Scope) return Node_Id;
7273 -- Given a list of statements L, wrap it in a block statement and return
7274 -- the generated node. Scop is either the current scope or the scope of
7275 -- the context (if applicable).
7277 -----------------
7278 -- Are_Wrapped --
7279 -----------------
7281 function Are_Wrapped (L : List_Id) return Boolean is
7282 Stmt : constant Node_Id := First (L);
7283 begin
7284 return
7285 Present (Stmt)
7286 and then No (Next (Stmt))
7287 and then Nkind (Stmt) = N_Block_Statement;
7288 end Are_Wrapped;
7290 ------------------------------
7291 -- Wrap_Statements_In_Block --
7292 ------------------------------
7294 function Wrap_Statements_In_Block
7295 (L : List_Id;
7296 Scop : Entity_Id := Current_Scope) return Node_Id
7298 Block_Id : Entity_Id;
7299 Block_Nod : Node_Id;
7300 Iter_Loop : Entity_Id;
7302 begin
7303 Block_Nod :=
7304 Make_Block_Statement (Loc,
7305 Declarations => No_List,
7306 Handled_Statement_Sequence =>
7307 Make_Handled_Sequence_Of_Statements (Loc,
7308 Statements => L));
7310 -- Create a label for the block in case the block needs to manage the
7311 -- secondary stack. A label allows for flag Uses_Sec_Stack to be set.
7313 Add_Block_Identifier (Block_Nod, Block_Id);
7315 -- When wrapping the statements of an iterator loop, check whether
7316 -- the loop requires secondary stack management and if so, propagate
7317 -- the appropriate flags to the block. This ensures that the cursor
7318 -- is properly cleaned up at each iteration of the loop.
7320 Iter_Loop := Find_Enclosing_Iterator_Loop (Scop);
7322 if Present (Iter_Loop) then
7323 Set_Uses_Sec_Stack (Block_Id, Uses_Sec_Stack (Iter_Loop));
7325 -- Secondary stack reclamation is suppressed when the associated
7326 -- iterator loop contains a return statement which uses the stack.
7328 Set_Sec_Stack_Needed_For_Return
7329 (Block_Id, Sec_Stack_Needed_For_Return (Iter_Loop));
7330 end if;
7332 return Block_Nod;
7333 end Wrap_Statements_In_Block;
7335 -- Local variables
7337 Block : Node_Id;
7339 -- Start of processing for Process_Statements_For_Controlled_Objects
7341 begin
7342 -- Whenever a non-handled statement list is wrapped in a block, the
7343 -- block must be explicitly analyzed to redecorate all entities in the
7344 -- list and ensure that a finalizer is properly built.
7346 case Nkind (N) is
7347 when N_Elsif_Part |
7348 N_If_Statement |
7349 N_Conditional_Entry_Call |
7350 N_Selective_Accept =>
7352 -- Check the "then statements" for elsif parts and if statements
7354 if Nkind_In (N, N_Elsif_Part, N_If_Statement)
7355 and then not Is_Empty_List (Then_Statements (N))
7356 and then not Are_Wrapped (Then_Statements (N))
7357 and then Requires_Cleanup_Actions
7358 (Then_Statements (N), False, False)
7359 then
7360 Block := Wrap_Statements_In_Block (Then_Statements (N));
7361 Set_Then_Statements (N, New_List (Block));
7363 Analyze (Block);
7364 end if;
7366 -- Check the "else statements" for conditional entry calls, if
7367 -- statements and selective accepts.
7369 if Nkind_In (N, N_Conditional_Entry_Call,
7370 N_If_Statement,
7371 N_Selective_Accept)
7372 and then not Is_Empty_List (Else_Statements (N))
7373 and then not Are_Wrapped (Else_Statements (N))
7374 and then Requires_Cleanup_Actions
7375 (Else_Statements (N), False, False)
7376 then
7377 Block := Wrap_Statements_In_Block (Else_Statements (N));
7378 Set_Else_Statements (N, New_List (Block));
7380 Analyze (Block);
7381 end if;
7383 when N_Abortable_Part |
7384 N_Accept_Alternative |
7385 N_Case_Statement_Alternative |
7386 N_Delay_Alternative |
7387 N_Entry_Call_Alternative |
7388 N_Exception_Handler |
7389 N_Loop_Statement |
7390 N_Triggering_Alternative =>
7392 if not Is_Empty_List (Statements (N))
7393 and then not Are_Wrapped (Statements (N))
7394 and then Requires_Cleanup_Actions (Statements (N), False, False)
7395 then
7396 if Nkind (N) = N_Loop_Statement
7397 and then Present (Identifier (N))
7398 then
7399 Block :=
7400 Wrap_Statements_In_Block
7401 (L => Statements (N),
7402 Scop => Entity (Identifier (N)));
7403 else
7404 Block := Wrap_Statements_In_Block (Statements (N));
7405 end if;
7407 Set_Statements (N, New_List (Block));
7408 Analyze (Block);
7409 end if;
7411 when others =>
7412 null;
7413 end case;
7414 end Process_Statements_For_Controlled_Objects;
7416 ------------------
7417 -- Power_Of_Two --
7418 ------------------
7420 function Power_Of_Two (N : Node_Id) return Nat is
7421 Typ : constant Entity_Id := Etype (N);
7422 pragma Assert (Is_Integer_Type (Typ));
7424 Siz : constant Nat := UI_To_Int (Esize (Typ));
7425 Val : Uint;
7427 begin
7428 if not Compile_Time_Known_Value (N) then
7429 return 0;
7431 else
7432 Val := Expr_Value (N);
7433 for J in 1 .. Siz - 1 loop
7434 if Val = Uint_2 ** J then
7435 return J;
7436 end if;
7437 end loop;
7439 return 0;
7440 end if;
7441 end Power_Of_Two;
7443 ----------------------
7444 -- Remove_Init_Call --
7445 ----------------------
7447 function Remove_Init_Call
7448 (Var : Entity_Id;
7449 Rep_Clause : Node_Id) return Node_Id
7451 Par : constant Node_Id := Parent (Var);
7452 Typ : constant Entity_Id := Etype (Var);
7454 Init_Proc : Entity_Id;
7455 -- Initialization procedure for Typ
7457 function Find_Init_Call_In_List (From : Node_Id) return Node_Id;
7458 -- Look for init call for Var starting at From and scanning the
7459 -- enclosing list until Rep_Clause or the end of the list is reached.
7461 ----------------------------
7462 -- Find_Init_Call_In_List --
7463 ----------------------------
7465 function Find_Init_Call_In_List (From : Node_Id) return Node_Id is
7466 Init_Call : Node_Id;
7468 begin
7469 Init_Call := From;
7470 while Present (Init_Call) and then Init_Call /= Rep_Clause loop
7471 if Nkind (Init_Call) = N_Procedure_Call_Statement
7472 and then Is_Entity_Name (Name (Init_Call))
7473 and then Entity (Name (Init_Call)) = Init_Proc
7474 then
7475 return Init_Call;
7476 end if;
7478 Next (Init_Call);
7479 end loop;
7481 return Empty;
7482 end Find_Init_Call_In_List;
7484 Init_Call : Node_Id;
7486 -- Start of processing for Find_Init_Call
7488 begin
7489 if Present (Initialization_Statements (Var)) then
7490 Init_Call := Initialization_Statements (Var);
7491 Set_Initialization_Statements (Var, Empty);
7493 elsif not Has_Non_Null_Base_Init_Proc (Typ) then
7495 -- No init proc for the type, so obviously no call to be found
7497 return Empty;
7499 else
7500 -- We might be able to handle other cases below by just properly
7501 -- setting Initialization_Statements at the point where the init proc
7502 -- call is generated???
7504 Init_Proc := Base_Init_Proc (Typ);
7506 -- First scan the list containing the declaration of Var
7508 Init_Call := Find_Init_Call_In_List (From => Next (Par));
7510 -- If not found, also look on Var's freeze actions list, if any,
7511 -- since the init call may have been moved there (case of an address
7512 -- clause applying to Var).
7514 if No (Init_Call) and then Present (Freeze_Node (Var)) then
7515 Init_Call :=
7516 Find_Init_Call_In_List (First (Actions (Freeze_Node (Var))));
7517 end if;
7519 -- If the initialization call has actuals that use the secondary
7520 -- stack, the call may have been wrapped into a temporary block, in
7521 -- which case the block itself has to be removed.
7523 if No (Init_Call) and then Nkind (Next (Par)) = N_Block_Statement then
7524 declare
7525 Blk : constant Node_Id := Next (Par);
7526 begin
7527 if Present
7528 (Find_Init_Call_In_List
7529 (First (Statements (Handled_Statement_Sequence (Blk)))))
7530 then
7531 Init_Call := Blk;
7532 end if;
7533 end;
7534 end if;
7535 end if;
7537 if Present (Init_Call) then
7538 Remove (Init_Call);
7539 end if;
7540 return Init_Call;
7541 end Remove_Init_Call;
7543 -------------------------
7544 -- Remove_Side_Effects --
7545 -------------------------
7547 procedure Remove_Side_Effects
7548 (Exp : Node_Id;
7549 Name_Req : Boolean := False;
7550 Renaming_Req : Boolean := False;
7551 Variable_Ref : Boolean := False;
7552 Related_Id : Entity_Id := Empty;
7553 Is_Low_Bound : Boolean := False;
7554 Is_High_Bound : Boolean := False)
7556 function Build_Temporary
7557 (Loc : Source_Ptr;
7558 Id : Character;
7559 Related_Nod : Node_Id := Empty) return Entity_Id;
7560 -- Create an external symbol of the form xxx_FIRST/_LAST if Related_Nod
7561 -- is present (xxx is taken from the Chars field of Related_Nod),
7562 -- otherwise it generates an internal temporary.
7564 function Is_Name_Reference (N : Node_Id) return Boolean;
7565 -- Determine if the tree referenced by N represents a name. This is
7566 -- similar to Is_Object_Reference but returns true only if N can be
7567 -- renamed without the need for a temporary, the typical example of
7568 -- an object not in this category being a function call.
7570 ---------------------
7571 -- Build_Temporary --
7572 ---------------------
7574 function Build_Temporary
7575 (Loc : Source_Ptr;
7576 Id : Character;
7577 Related_Nod : Node_Id := Empty) return Entity_Id
7579 Temp_Nam : Name_Id;
7581 begin
7582 -- The context requires an external symbol
7584 if Present (Related_Id) then
7585 if Is_Low_Bound then
7586 Temp_Nam := New_External_Name (Chars (Related_Id), "_FIRST");
7587 else pragma Assert (Is_High_Bound);
7588 Temp_Nam := New_External_Name (Chars (Related_Id), "_LAST");
7589 end if;
7591 return Make_Defining_Identifier (Loc, Temp_Nam);
7593 -- Otherwise generate an internal temporary
7595 else
7596 return Make_Temporary (Loc, Id, Related_Nod);
7597 end if;
7598 end Build_Temporary;
7600 -----------------------
7601 -- Is_Name_Reference --
7602 -----------------------
7604 function Is_Name_Reference (N : Node_Id) return Boolean is
7605 begin
7606 if Is_Entity_Name (N) then
7607 return Present (Entity (N)) and then Is_Object (Entity (N));
7608 end if;
7610 case Nkind (N) is
7611 when N_Indexed_Component | N_Slice =>
7612 return
7613 Is_Name_Reference (Prefix (N))
7614 or else Is_Access_Type (Etype (Prefix (N)));
7616 -- Attributes 'Input, 'Old and 'Result produce objects
7618 when N_Attribute_Reference =>
7619 return
7620 Nam_In
7621 (Attribute_Name (N), Name_Input, Name_Old, Name_Result);
7623 when N_Selected_Component =>
7624 return
7625 Is_Name_Reference (Selector_Name (N))
7626 and then
7627 (Is_Name_Reference (Prefix (N))
7628 or else Is_Access_Type (Etype (Prefix (N))));
7630 when N_Explicit_Dereference =>
7631 return True;
7633 -- A view conversion of a tagged name is a name reference
7635 when N_Type_Conversion =>
7636 return Is_Tagged_Type (Etype (Subtype_Mark (N)))
7637 and then Is_Tagged_Type (Etype (Expression (N)))
7638 and then Is_Name_Reference (Expression (N));
7640 -- An unchecked type conversion is considered to be a name if
7641 -- the operand is a name (this construction arises only as a
7642 -- result of expansion activities).
7644 when N_Unchecked_Type_Conversion =>
7645 return Is_Name_Reference (Expression (N));
7647 when others =>
7648 return False;
7649 end case;
7650 end Is_Name_Reference;
7652 -- Local variables
7654 Loc : constant Source_Ptr := Sloc (Exp);
7655 Exp_Type : constant Entity_Id := Etype (Exp);
7656 Svg_Suppress : constant Suppress_Record := Scope_Suppress;
7657 Def_Id : Entity_Id;
7658 E : Node_Id;
7659 New_Exp : Node_Id;
7660 Ptr_Typ_Decl : Node_Id;
7661 Ref_Type : Entity_Id;
7662 Res : Node_Id;
7664 -- Start of processing for Remove_Side_Effects
7666 begin
7667 -- Handle cases in which there is nothing to do. In GNATprove mode,
7668 -- removal of side effects is useful for the light expansion of
7669 -- renamings. This removal should only occur when not inside a
7670 -- generic and not doing a pre-analysis.
7672 if not Expander_Active
7673 and (Inside_A_Generic or not Full_Analysis or not GNATprove_Mode)
7674 then
7675 return;
7676 end if;
7678 -- Cannot generate temporaries if the invocation to remove side effects
7679 -- was issued too early and the type of the expression is not resolved
7680 -- (this happens because routines Duplicate_Subexpr_XX implicitly invoke
7681 -- Remove_Side_Effects).
7683 if No (Exp_Type) or else Ekind (Exp_Type) = E_Access_Attribute_Type then
7684 return;
7686 -- No action needed for side-effect free expressions
7688 elsif Side_Effect_Free (Exp, Name_Req, Variable_Ref) then
7689 return;
7690 end if;
7692 -- The remaining processing is done with all checks suppressed
7694 -- Note: from now on, don't use return statements, instead do a goto
7695 -- Leave, to ensure that we properly restore Scope_Suppress.Suppress.
7697 Scope_Suppress.Suppress := (others => True);
7699 -- If it is an elementary type and we need to capture the value, just
7700 -- make a constant. Likewise if this is not a name reference, except
7701 -- for a type conversion because we would enter an infinite recursion
7702 -- with Checks.Apply_Predicate_Check if the target type has predicates.
7703 -- And type conversions need a specific treatment anyway, see below.
7704 -- Also do it if we have a volatile reference and Name_Req is not set
7705 -- (see comments for Side_Effect_Free).
7707 if Is_Elementary_Type (Exp_Type)
7708 and then (Variable_Ref
7709 or else (not Is_Name_Reference (Exp)
7710 and then Nkind (Exp) /= N_Type_Conversion)
7711 or else (not Name_Req
7712 and then Is_Volatile_Reference (Exp)))
7713 then
7714 Def_Id := Build_Temporary (Loc, 'R', Exp);
7715 Set_Etype (Def_Id, Exp_Type);
7716 Res := New_Occurrence_Of (Def_Id, Loc);
7718 -- If the expression is a packed reference, it must be reanalyzed and
7719 -- expanded, depending on context. This is the case for actuals where
7720 -- a constraint check may capture the actual before expansion of the
7721 -- call is complete.
7723 if Nkind (Exp) = N_Indexed_Component
7724 and then Is_Packed (Etype (Prefix (Exp)))
7725 then
7726 Set_Analyzed (Exp, False);
7727 Set_Analyzed (Prefix (Exp), False);
7728 end if;
7730 -- Generate:
7731 -- Rnn : Exp_Type renames Expr;
7733 if Renaming_Req then
7734 E :=
7735 Make_Object_Renaming_Declaration (Loc,
7736 Defining_Identifier => Def_Id,
7737 Subtype_Mark => New_Occurrence_Of (Exp_Type, Loc),
7738 Name => Relocate_Node (Exp));
7740 -- Generate:
7741 -- Rnn : constant Exp_Type := Expr;
7743 else
7744 E :=
7745 Make_Object_Declaration (Loc,
7746 Defining_Identifier => Def_Id,
7747 Object_Definition => New_Occurrence_Of (Exp_Type, Loc),
7748 Constant_Present => True,
7749 Expression => Relocate_Node (Exp));
7751 Set_Assignment_OK (E);
7752 end if;
7754 Insert_Action (Exp, E);
7756 -- If the expression has the form v.all then we can just capture the
7757 -- pointer, and then do an explicit dereference on the result, but
7758 -- this is not right if this is a volatile reference.
7760 elsif Nkind (Exp) = N_Explicit_Dereference
7761 and then not Is_Volatile_Reference (Exp)
7762 then
7763 Def_Id := Build_Temporary (Loc, 'R', Exp);
7764 Res :=
7765 Make_Explicit_Dereference (Loc, New_Occurrence_Of (Def_Id, Loc));
7767 Insert_Action (Exp,
7768 Make_Object_Declaration (Loc,
7769 Defining_Identifier => Def_Id,
7770 Object_Definition =>
7771 New_Occurrence_Of (Etype (Prefix (Exp)), Loc),
7772 Constant_Present => True,
7773 Expression => Relocate_Node (Prefix (Exp))));
7775 -- Similar processing for an unchecked conversion of an expression of
7776 -- the form v.all, where we want the same kind of treatment.
7778 elsif Nkind (Exp) = N_Unchecked_Type_Conversion
7779 and then Nkind (Expression (Exp)) = N_Explicit_Dereference
7780 then
7781 Remove_Side_Effects (Expression (Exp), Name_Req, Variable_Ref);
7782 goto Leave;
7784 -- If this is a type conversion, leave the type conversion and remove
7785 -- the side effects in the expression. This is important in several
7786 -- circumstances: for change of representations, and also when this is a
7787 -- view conversion to a smaller object, where gigi can end up creating
7788 -- its own temporary of the wrong size.
7790 elsif Nkind (Exp) = N_Type_Conversion then
7791 Remove_Side_Effects (Expression (Exp), Name_Req, Variable_Ref);
7793 -- Generating C code the type conversion of an access to constrained
7794 -- array type into an access to unconstrained array type involves
7795 -- initializing a fat pointer and the expression must be free of
7796 -- side effects to safely compute its bounds.
7798 if Generate_C_Code
7799 and then Is_Access_Type (Etype (Exp))
7800 and then Is_Array_Type (Designated_Type (Etype (Exp)))
7801 and then not Is_Constrained (Designated_Type (Etype (Exp)))
7802 then
7803 Def_Id := Build_Temporary (Loc, 'R', Exp);
7804 Set_Etype (Def_Id, Exp_Type);
7805 Res := New_Occurrence_Of (Def_Id, Loc);
7807 Insert_Action (Exp,
7808 Make_Object_Declaration (Loc,
7809 Defining_Identifier => Def_Id,
7810 Object_Definition => New_Occurrence_Of (Exp_Type, Loc),
7811 Constant_Present => True,
7812 Expression => Relocate_Node (Exp)));
7813 else
7814 goto Leave;
7815 end if;
7817 -- If this is an unchecked conversion that Gigi can't handle, make
7818 -- a copy or a use a renaming to capture the value.
7820 elsif Nkind (Exp) = N_Unchecked_Type_Conversion
7821 and then not Safe_Unchecked_Type_Conversion (Exp)
7822 then
7823 if CW_Or_Has_Controlled_Part (Exp_Type) then
7825 -- Use a renaming to capture the expression, rather than create
7826 -- a controlled temporary.
7828 Def_Id := Build_Temporary (Loc, 'R', Exp);
7829 Res := New_Occurrence_Of (Def_Id, Loc);
7831 Insert_Action (Exp,
7832 Make_Object_Renaming_Declaration (Loc,
7833 Defining_Identifier => Def_Id,
7834 Subtype_Mark => New_Occurrence_Of (Exp_Type, Loc),
7835 Name => Relocate_Node (Exp)));
7837 else
7838 Def_Id := Build_Temporary (Loc, 'R', Exp);
7839 Set_Etype (Def_Id, Exp_Type);
7840 Res := New_Occurrence_Of (Def_Id, Loc);
7842 E :=
7843 Make_Object_Declaration (Loc,
7844 Defining_Identifier => Def_Id,
7845 Object_Definition => New_Occurrence_Of (Exp_Type, Loc),
7846 Constant_Present => not Is_Variable (Exp),
7847 Expression => Relocate_Node (Exp));
7849 Set_Assignment_OK (E);
7850 Insert_Action (Exp, E);
7851 end if;
7853 -- For expressions that denote names, we can use a renaming scheme.
7854 -- This is needed for correctness in the case of a volatile object of
7855 -- a non-volatile type because the Make_Reference call of the "default"
7856 -- approach would generate an illegal access value (an access value
7857 -- cannot designate such an object - see Analyze_Reference).
7859 elsif Is_Name_Reference (Exp)
7861 -- We skip using this scheme if we have an object of a volatile
7862 -- type and we do not have Name_Req set true (see comments for
7863 -- Side_Effect_Free).
7865 and then (Name_Req or else not Treat_As_Volatile (Exp_Type))
7866 then
7867 Def_Id := Build_Temporary (Loc, 'R', Exp);
7868 Res := New_Occurrence_Of (Def_Id, Loc);
7870 Insert_Action (Exp,
7871 Make_Object_Renaming_Declaration (Loc,
7872 Defining_Identifier => Def_Id,
7873 Subtype_Mark => New_Occurrence_Of (Exp_Type, Loc),
7874 Name => Relocate_Node (Exp)));
7876 -- If this is a packed reference, or a selected component with
7877 -- a non-standard representation, a reference to the temporary
7878 -- will be replaced by a copy of the original expression (see
7879 -- Exp_Ch2.Expand_Renaming). Otherwise the temporary must be
7880 -- elaborated by gigi, and is of course not to be replaced in-line
7881 -- by the expression it renames, which would defeat the purpose of
7882 -- removing the side-effect.
7884 if Nkind_In (Exp, N_Selected_Component, N_Indexed_Component)
7885 and then Has_Non_Standard_Rep (Etype (Prefix (Exp)))
7886 then
7887 null;
7888 else
7889 Set_Is_Renaming_Of_Object (Def_Id, False);
7890 end if;
7892 -- Avoid generating a variable-sized temporary, by generating the
7893 -- reference just for the function call. The transformation could be
7894 -- refined to apply only when the array component is constrained by a
7895 -- discriminant???
7897 elsif Nkind (Exp) = N_Selected_Component
7898 and then Nkind (Prefix (Exp)) = N_Function_Call
7899 and then Is_Array_Type (Exp_Type)
7900 then
7901 Remove_Side_Effects (Prefix (Exp), Name_Req, Variable_Ref);
7902 goto Leave;
7904 -- Otherwise we generate a reference to the expression
7906 else
7907 -- An expression which is in SPARK mode is considered side effect
7908 -- free if the resulting value is captured by a variable or a
7909 -- constant.
7911 if GNATprove_Mode
7912 and then Nkind (Parent (Exp)) = N_Object_Declaration
7913 then
7914 goto Leave;
7916 -- When generating C code we cannot consider side effect free object
7917 -- declarations that have discriminants and are initialized by means
7918 -- of a function call since on this target there is no secondary
7919 -- stack to store the return value and the expander may generate an
7920 -- extra call to the function to compute the discriminant value. In
7921 -- addition, for targets that have secondary stack, the expansion of
7922 -- functions with side effects involves the generation of an access
7923 -- type to capture the return value stored in the secondary stack;
7924 -- by contrast when generating C code such expansion generates an
7925 -- internal object declaration (no access type involved) which must
7926 -- be identified here to avoid entering into a never-ending loop
7927 -- generating internal object declarations.
7929 elsif Generate_C_Code
7930 and then Nkind (Parent (Exp)) = N_Object_Declaration
7931 and then
7932 (Nkind (Exp) /= N_Function_Call
7933 or else not Has_Discriminants (Exp_Type)
7934 or else Is_Internal_Name
7935 (Chars (Defining_Identifier (Parent (Exp)))))
7936 then
7937 goto Leave;
7938 end if;
7940 -- Special processing for function calls that return a limited type.
7941 -- We need to build a declaration that will enable build-in-place
7942 -- expansion of the call. This is not done if the context is already
7943 -- an object declaration, to prevent infinite recursion.
7945 -- This is relevant only in Ada 2005 mode. In Ada 95 programs we have
7946 -- to accommodate functions returning limited objects by reference.
7948 if Ada_Version >= Ada_2005
7949 and then Nkind (Exp) = N_Function_Call
7950 and then Is_Limited_View (Etype (Exp))
7951 and then Nkind (Parent (Exp)) /= N_Object_Declaration
7952 then
7953 declare
7954 Obj : constant Entity_Id := Make_Temporary (Loc, 'F', Exp);
7955 Decl : Node_Id;
7957 begin
7958 Decl :=
7959 Make_Object_Declaration (Loc,
7960 Defining_Identifier => Obj,
7961 Object_Definition => New_Occurrence_Of (Exp_Type, Loc),
7962 Expression => Relocate_Node (Exp));
7964 Insert_Action (Exp, Decl);
7965 Set_Etype (Obj, Exp_Type);
7966 Rewrite (Exp, New_Occurrence_Of (Obj, Loc));
7967 goto Leave;
7968 end;
7969 end if;
7971 Def_Id := Build_Temporary (Loc, 'R', Exp);
7973 -- The regular expansion of functions with side effects involves the
7974 -- generation of an access type to capture the return value found on
7975 -- the secondary stack. Since SPARK (and why) cannot process access
7976 -- types, use a different approach which ignores the secondary stack
7977 -- and "copies" the returned object.
7978 -- When generating C code, no need for a 'reference since the
7979 -- secondary stack is not supported.
7981 if GNATprove_Mode or Generate_C_Code then
7982 Res := New_Occurrence_Of (Def_Id, Loc);
7983 Ref_Type := Exp_Type;
7985 -- Regular expansion utilizing an access type and 'reference
7987 else
7988 Res :=
7989 Make_Explicit_Dereference (Loc,
7990 Prefix => New_Occurrence_Of (Def_Id, Loc));
7992 -- Generate:
7993 -- type Ann is access all <Exp_Type>;
7995 Ref_Type := Make_Temporary (Loc, 'A');
7997 Ptr_Typ_Decl :=
7998 Make_Full_Type_Declaration (Loc,
7999 Defining_Identifier => Ref_Type,
8000 Type_Definition =>
8001 Make_Access_To_Object_Definition (Loc,
8002 All_Present => True,
8003 Subtype_Indication =>
8004 New_Occurrence_Of (Exp_Type, Loc)));
8006 Insert_Action (Exp, Ptr_Typ_Decl);
8007 end if;
8009 E := Exp;
8010 if Nkind (E) = N_Explicit_Dereference then
8011 New_Exp := Relocate_Node (Prefix (E));
8013 else
8014 E := Relocate_Node (E);
8016 -- Do not generate a 'reference in SPARK mode or C generation
8017 -- since the access type is not created in the first place.
8019 if GNATprove_Mode or Generate_C_Code then
8020 New_Exp := E;
8022 -- Otherwise generate reference, marking the value as non-null
8023 -- since we know it cannot be null and we don't want a check.
8025 else
8026 New_Exp := Make_Reference (Loc, E);
8027 Set_Is_Known_Non_Null (Def_Id);
8028 end if;
8029 end if;
8031 if Is_Delayed_Aggregate (E) then
8033 -- The expansion of nested aggregates is delayed until the
8034 -- enclosing aggregate is expanded. As aggregates are often
8035 -- qualified, the predicate applies to qualified expressions as
8036 -- well, indicating that the enclosing aggregate has not been
8037 -- expanded yet. At this point the aggregate is part of a
8038 -- stand-alone declaration, and must be fully expanded.
8040 if Nkind (E) = N_Qualified_Expression then
8041 Set_Expansion_Delayed (Expression (E), False);
8042 Set_Analyzed (Expression (E), False);
8043 else
8044 Set_Expansion_Delayed (E, False);
8045 end if;
8047 Set_Analyzed (E, False);
8048 end if;
8050 -- Generating C code of object declarations that have discriminants
8051 -- and are initialized by means of a function call we propagate the
8052 -- discriminants of the parent type to the internally built object.
8053 -- This is needed to avoid generating an extra call to the called
8054 -- function.
8056 -- For example, if we generate here the following declaration, it
8057 -- will be expanded later adding an extra call to evaluate the value
8058 -- of the discriminant (needed to compute the size of the object).
8060 -- type Rec (D : Integer) is ...
8061 -- Obj : constant Rec := SomeFunc;
8063 if Generate_C_Code
8064 and then Nkind (Parent (Exp)) = N_Object_Declaration
8065 and then Has_Discriminants (Exp_Type)
8066 and then Nkind (Exp) = N_Function_Call
8067 then
8068 Insert_Action (Exp,
8069 Make_Object_Declaration (Loc,
8070 Defining_Identifier => Def_Id,
8071 Object_Definition => New_Copy_Tree
8072 (Object_Definition (Parent (Exp))),
8073 Constant_Present => True,
8074 Expression => New_Exp));
8075 else
8076 Insert_Action (Exp,
8077 Make_Object_Declaration (Loc,
8078 Defining_Identifier => Def_Id,
8079 Object_Definition => New_Occurrence_Of (Ref_Type, Loc),
8080 Constant_Present => True,
8081 Expression => New_Exp));
8082 end if;
8083 end if;
8085 -- Preserve the Assignment_OK flag in all copies, since at least one
8086 -- copy may be used in a context where this flag must be set (otherwise
8087 -- why would the flag be set in the first place).
8089 Set_Assignment_OK (Res, Assignment_OK (Exp));
8091 -- Finally rewrite the original expression and we are done
8093 Rewrite (Exp, Res);
8094 Analyze_And_Resolve (Exp, Exp_Type);
8096 <<Leave>>
8097 Scope_Suppress := Svg_Suppress;
8098 end Remove_Side_Effects;
8100 ---------------------------
8101 -- Represented_As_Scalar --
8102 ---------------------------
8104 function Represented_As_Scalar (T : Entity_Id) return Boolean is
8105 UT : constant Entity_Id := Underlying_Type (T);
8106 begin
8107 return Is_Scalar_Type (UT)
8108 or else (Is_Bit_Packed_Array (UT)
8109 and then Is_Scalar_Type (Packed_Array_Impl_Type (UT)));
8110 end Represented_As_Scalar;
8112 ------------------------------
8113 -- Requires_Cleanup_Actions --
8114 ------------------------------
8116 function Requires_Cleanup_Actions
8117 (N : Node_Id;
8118 Lib_Level : Boolean) return Boolean
8120 At_Lib_Level : constant Boolean :=
8121 Lib_Level
8122 and then Nkind_In (N, N_Package_Body,
8123 N_Package_Specification);
8124 -- N is at the library level if the top-most context is a package and
8125 -- the path taken to reach N does not inlcude non-package constructs.
8127 begin
8128 case Nkind (N) is
8129 when N_Accept_Statement |
8130 N_Block_Statement |
8131 N_Entry_Body |
8132 N_Package_Body |
8133 N_Protected_Body |
8134 N_Subprogram_Body |
8135 N_Task_Body =>
8136 return
8137 Requires_Cleanup_Actions (Declarations (N), At_Lib_Level, True)
8138 or else
8139 (Present (Handled_Statement_Sequence (N))
8140 and then
8141 Requires_Cleanup_Actions
8142 (Statements (Handled_Statement_Sequence (N)),
8143 At_Lib_Level, True));
8145 when N_Package_Specification =>
8146 return
8147 Requires_Cleanup_Actions
8148 (Visible_Declarations (N), At_Lib_Level, True)
8149 or else
8150 Requires_Cleanup_Actions
8151 (Private_Declarations (N), At_Lib_Level, True);
8153 when others =>
8154 return False;
8155 end case;
8156 end Requires_Cleanup_Actions;
8158 ------------------------------
8159 -- Requires_Cleanup_Actions --
8160 ------------------------------
8162 function Requires_Cleanup_Actions
8163 (L : List_Id;
8164 Lib_Level : Boolean;
8165 Nested_Constructs : Boolean) return Boolean
8167 Decl : Node_Id;
8168 Expr : Node_Id;
8169 Obj_Id : Entity_Id;
8170 Obj_Typ : Entity_Id;
8171 Pack_Id : Entity_Id;
8172 Typ : Entity_Id;
8174 begin
8175 if No (L)
8176 or else Is_Empty_List (L)
8177 then
8178 return False;
8179 end if;
8181 Decl := First (L);
8182 while Present (Decl) loop
8184 -- Library-level tagged types
8186 if Nkind (Decl) = N_Full_Type_Declaration then
8187 Typ := Defining_Identifier (Decl);
8189 -- Ignored Ghost types do not need any cleanup actions because
8190 -- they will not appear in the final tree.
8192 if Is_Ignored_Ghost_Entity (Typ) then
8193 null;
8195 elsif Is_Tagged_Type (Typ)
8196 and then Is_Library_Level_Entity (Typ)
8197 and then Convention (Typ) = Convention_Ada
8198 and then Present (Access_Disp_Table (Typ))
8199 and then RTE_Available (RE_Unregister_Tag)
8200 and then not Is_Abstract_Type (Typ)
8201 and then not No_Run_Time_Mode
8202 then
8203 return True;
8204 end if;
8206 -- Regular object declarations
8208 elsif Nkind (Decl) = N_Object_Declaration then
8209 Obj_Id := Defining_Identifier (Decl);
8210 Obj_Typ := Base_Type (Etype (Obj_Id));
8211 Expr := Expression (Decl);
8213 -- Bypass any form of processing for objects which have their
8214 -- finalization disabled. This applies only to objects at the
8215 -- library level.
8217 if Lib_Level and then Finalize_Storage_Only (Obj_Typ) then
8218 null;
8220 -- Transient variables are treated separately in order to minimize
8221 -- the size of the generated code. See Exp_Ch7.Process_Transient_
8222 -- Objects.
8224 elsif Is_Processed_Transient (Obj_Id) then
8225 null;
8227 -- Ignored Ghost objects do not need any cleanup actions because
8228 -- they will not appear in the final tree.
8230 elsif Is_Ignored_Ghost_Entity (Obj_Id) then
8231 null;
8233 -- The expansion of iterator loops generates an object declaration
8234 -- where the Ekind is explicitly set to loop parameter. This is to
8235 -- ensure that the loop parameter behaves as a constant from user
8236 -- code point of view. Such object are never controlled and do not
8237 -- require cleanup actions. An iterator loop over a container of
8238 -- controlled objects does not produce such object declarations.
8240 elsif Ekind (Obj_Id) = E_Loop_Parameter then
8241 return False;
8243 -- The object is of the form:
8244 -- Obj : Typ [:= Expr];
8246 -- Do not process the incomplete view of a deferred constant. Do
8247 -- not consider tag-to-class-wide conversions.
8249 elsif not Is_Imported (Obj_Id)
8250 and then Needs_Finalization (Obj_Typ)
8251 and then not (Ekind (Obj_Id) = E_Constant
8252 and then not Has_Completion (Obj_Id))
8253 and then not Is_Tag_To_Class_Wide_Conversion (Obj_Id)
8254 then
8255 return True;
8257 -- The object is of the form:
8258 -- Obj : Access_Typ := Non_BIP_Function_Call'reference;
8260 -- Obj : Access_Typ :=
8261 -- BIP_Function_Call (BIPalloc => 2, ...)'reference;
8263 elsif Is_Access_Type (Obj_Typ)
8264 and then Needs_Finalization
8265 (Available_View (Designated_Type (Obj_Typ)))
8266 and then Present (Expr)
8267 and then
8268 (Is_Secondary_Stack_BIP_Func_Call (Expr)
8269 or else
8270 (Is_Non_BIP_Func_Call (Expr)
8271 and then not Is_Related_To_Func_Return (Obj_Id)))
8272 then
8273 return True;
8275 -- Processing for "hook" objects generated for controlled
8276 -- transients declared inside an Expression_With_Actions.
8278 elsif Is_Access_Type (Obj_Typ)
8279 and then Present (Status_Flag_Or_Transient_Decl (Obj_Id))
8280 and then Nkind (Status_Flag_Or_Transient_Decl (Obj_Id)) =
8281 N_Object_Declaration
8282 then
8283 return True;
8285 -- Processing for intermediate results of if expressions where
8286 -- one of the alternatives uses a controlled function call.
8288 elsif Is_Access_Type (Obj_Typ)
8289 and then Present (Status_Flag_Or_Transient_Decl (Obj_Id))
8290 and then Nkind (Status_Flag_Or_Transient_Decl (Obj_Id)) =
8291 N_Defining_Identifier
8292 and then Present (Expr)
8293 and then Nkind (Expr) = N_Null
8294 then
8295 return True;
8297 -- Simple protected objects which use type System.Tasking.
8298 -- Protected_Objects.Protection to manage their locks should be
8299 -- treated as controlled since they require manual cleanup.
8301 elsif Ekind (Obj_Id) = E_Variable
8302 and then (Is_Simple_Protected_Type (Obj_Typ)
8303 or else Has_Simple_Protected_Object (Obj_Typ))
8304 then
8305 return True;
8306 end if;
8308 -- Specific cases of object renamings
8310 elsif Nkind (Decl) = N_Object_Renaming_Declaration then
8311 Obj_Id := Defining_Identifier (Decl);
8312 Obj_Typ := Base_Type (Etype (Obj_Id));
8314 -- Bypass any form of processing for objects which have their
8315 -- finalization disabled. This applies only to objects at the
8316 -- library level.
8318 if Lib_Level and then Finalize_Storage_Only (Obj_Typ) then
8319 null;
8321 -- Ignored Ghost object renamings do not need any cleanup actions
8322 -- because they will not appear in the final tree.
8324 elsif Is_Ignored_Ghost_Entity (Obj_Id) then
8325 null;
8327 -- Return object of a build-in-place function. This case is
8328 -- recognized and marked by the expansion of an extended return
8329 -- statement (see Expand_N_Extended_Return_Statement).
8331 elsif Needs_Finalization (Obj_Typ)
8332 and then Is_Return_Object (Obj_Id)
8333 and then Present (Status_Flag_Or_Transient_Decl (Obj_Id))
8334 then
8335 return True;
8337 -- Detect a case where a source object has been initialized by
8338 -- a controlled function call or another object which was later
8339 -- rewritten as a class-wide conversion of Ada.Tags.Displace.
8341 -- Obj1 : CW_Type := Src_Obj;
8342 -- Obj2 : CW_Type := Function_Call (...);
8344 -- Obj1 : CW_Type renames (... Ada.Tags.Displace (Src_Obj));
8345 -- Tmp : ... := Function_Call (...)'reference;
8346 -- Obj2 : CW_Type renames (... Ada.Tags.Displace (Tmp));
8348 elsif Is_Displacement_Of_Object_Or_Function_Result (Obj_Id) then
8349 return True;
8350 end if;
8352 -- Inspect the freeze node of an access-to-controlled type and look
8353 -- for a delayed finalization master. This case arises when the
8354 -- freeze actions are inserted at a later time than the expansion of
8355 -- the context. Since Build_Finalizer is never called on a single
8356 -- construct twice, the master will be ultimately left out and never
8357 -- finalized. This is also needed for freeze actions of designated
8358 -- types themselves, since in some cases the finalization master is
8359 -- associated with a designated type's freeze node rather than that
8360 -- of the access type (see handling for freeze actions in
8361 -- Build_Finalization_Master).
8363 elsif Nkind (Decl) = N_Freeze_Entity
8364 and then Present (Actions (Decl))
8365 then
8366 Typ := Entity (Decl);
8368 -- Freeze nodes for ignored Ghost types do not need cleanup
8369 -- actions because they will never appear in the final tree.
8371 if Is_Ignored_Ghost_Entity (Typ) then
8372 null;
8374 elsif ((Is_Access_Type (Typ)
8375 and then not Is_Access_Subprogram_Type (Typ)
8376 and then Needs_Finalization
8377 (Available_View (Designated_Type (Typ))))
8378 or else (Is_Type (Typ) and then Needs_Finalization (Typ)))
8379 and then Requires_Cleanup_Actions
8380 (Actions (Decl), Lib_Level, Nested_Constructs)
8381 then
8382 return True;
8383 end if;
8385 -- Nested package declarations
8387 elsif Nested_Constructs
8388 and then Nkind (Decl) = N_Package_Declaration
8389 then
8390 Pack_Id := Defining_Entity (Decl);
8392 -- Do not inspect an ignored Ghost package because all code found
8393 -- within will not appear in the final tree.
8395 if Is_Ignored_Ghost_Entity (Pack_Id) then
8396 null;
8398 elsif Ekind (Pack_Id) /= E_Generic_Package
8399 and then Requires_Cleanup_Actions
8400 (Specification (Decl), Lib_Level)
8401 then
8402 return True;
8403 end if;
8405 -- Nested package bodies
8407 elsif Nested_Constructs and then Nkind (Decl) = N_Package_Body then
8409 -- Do not inspect an ignored Ghost package body because all code
8410 -- found within will not appear in the final tree.
8412 if Is_Ignored_Ghost_Entity (Defining_Entity (Decl)) then
8413 null;
8415 elsif Ekind (Corresponding_Spec (Decl)) /= E_Generic_Package
8416 and then Requires_Cleanup_Actions (Decl, Lib_Level)
8417 then
8418 return True;
8419 end if;
8421 elsif Nkind (Decl) = N_Block_Statement
8422 and then
8424 -- Handle a rare case caused by a controlled transient variable
8425 -- created as part of a record init proc. The variable is wrapped
8426 -- in a block, but the block is not associated with a transient
8427 -- scope.
8429 (Inside_Init_Proc
8431 -- Handle the case where the original context has been wrapped in
8432 -- a block to avoid interference between exception handlers and
8433 -- At_End handlers. Treat the block as transparent and process its
8434 -- contents.
8436 or else Is_Finalization_Wrapper (Decl))
8437 then
8438 if Requires_Cleanup_Actions (Decl, Lib_Level) then
8439 return True;
8440 end if;
8441 end if;
8443 Next (Decl);
8444 end loop;
8446 return False;
8447 end Requires_Cleanup_Actions;
8449 ------------------------------------
8450 -- Safe_Unchecked_Type_Conversion --
8451 ------------------------------------
8453 -- Note: this function knows quite a bit about the exact requirements of
8454 -- Gigi with respect to unchecked type conversions, and its code must be
8455 -- coordinated with any changes in Gigi in this area.
8457 -- The above requirements should be documented in Sinfo ???
8459 function Safe_Unchecked_Type_Conversion (Exp : Node_Id) return Boolean is
8460 Otyp : Entity_Id;
8461 Ityp : Entity_Id;
8462 Oalign : Uint;
8463 Ialign : Uint;
8464 Pexp : constant Node_Id := Parent (Exp);
8466 begin
8467 -- If the expression is the RHS of an assignment or object declaration
8468 -- we are always OK because there will always be a target.
8470 -- Object renaming declarations, (generated for view conversions of
8471 -- actuals in inlined calls), like object declarations, provide an
8472 -- explicit type, and are safe as well.
8474 if (Nkind (Pexp) = N_Assignment_Statement
8475 and then Expression (Pexp) = Exp)
8476 or else Nkind_In (Pexp, N_Object_Declaration,
8477 N_Object_Renaming_Declaration)
8478 then
8479 return True;
8481 -- If the expression is the prefix of an N_Selected_Component we should
8482 -- also be OK because GCC knows to look inside the conversion except if
8483 -- the type is discriminated. We assume that we are OK anyway if the
8484 -- type is not set yet or if it is controlled since we can't afford to
8485 -- introduce a temporary in this case.
8487 elsif Nkind (Pexp) = N_Selected_Component
8488 and then Prefix (Pexp) = Exp
8489 then
8490 if No (Etype (Pexp)) then
8491 return True;
8492 else
8493 return
8494 not Has_Discriminants (Etype (Pexp))
8495 or else Is_Constrained (Etype (Pexp));
8496 end if;
8497 end if;
8499 -- Set the output type, this comes from Etype if it is set, otherwise we
8500 -- take it from the subtype mark, which we assume was already fully
8501 -- analyzed.
8503 if Present (Etype (Exp)) then
8504 Otyp := Etype (Exp);
8505 else
8506 Otyp := Entity (Subtype_Mark (Exp));
8507 end if;
8509 -- The input type always comes from the expression, and we assume this
8510 -- is indeed always analyzed, so we can simply get the Etype.
8512 Ityp := Etype (Expression (Exp));
8514 -- Initialize alignments to unknown so far
8516 Oalign := No_Uint;
8517 Ialign := No_Uint;
8519 -- Replace a concurrent type by its corresponding record type and each
8520 -- type by its underlying type and do the tests on those. The original
8521 -- type may be a private type whose completion is a concurrent type, so
8522 -- find the underlying type first.
8524 if Present (Underlying_Type (Otyp)) then
8525 Otyp := Underlying_Type (Otyp);
8526 end if;
8528 if Present (Underlying_Type (Ityp)) then
8529 Ityp := Underlying_Type (Ityp);
8530 end if;
8532 if Is_Concurrent_Type (Otyp) then
8533 Otyp := Corresponding_Record_Type (Otyp);
8534 end if;
8536 if Is_Concurrent_Type (Ityp) then
8537 Ityp := Corresponding_Record_Type (Ityp);
8538 end if;
8540 -- If the base types are the same, we know there is no problem since
8541 -- this conversion will be a noop.
8543 if Implementation_Base_Type (Otyp) = Implementation_Base_Type (Ityp) then
8544 return True;
8546 -- Same if this is an upwards conversion of an untagged type, and there
8547 -- are no constraints involved (could be more general???)
8549 elsif Etype (Ityp) = Otyp
8550 and then not Is_Tagged_Type (Ityp)
8551 and then not Has_Discriminants (Ityp)
8552 and then No (First_Rep_Item (Base_Type (Ityp)))
8553 then
8554 return True;
8556 -- If the expression has an access type (object or subprogram) we assume
8557 -- that the conversion is safe, because the size of the target is safe,
8558 -- even if it is a record (which might be treated as having unknown size
8559 -- at this point).
8561 elsif Is_Access_Type (Ityp) then
8562 return True;
8564 -- If the size of output type is known at compile time, there is never
8565 -- a problem. Note that unconstrained records are considered to be of
8566 -- known size, but we can't consider them that way here, because we are
8567 -- talking about the actual size of the object.
8569 -- We also make sure that in addition to the size being known, we do not
8570 -- have a case which might generate an embarrassingly large temp in
8571 -- stack checking mode.
8573 elsif Size_Known_At_Compile_Time (Otyp)
8574 and then
8575 (not Stack_Checking_Enabled
8576 or else not May_Generate_Large_Temp (Otyp))
8577 and then not (Is_Record_Type (Otyp) and then not Is_Constrained (Otyp))
8578 then
8579 return True;
8581 -- If either type is tagged, then we know the alignment is OK so Gigi
8582 -- will be able to use pointer punning.
8584 elsif Is_Tagged_Type (Otyp) or else Is_Tagged_Type (Ityp) then
8585 return True;
8587 -- If either type is a limited record type, we cannot do a copy, so say
8588 -- safe since there's nothing else we can do.
8590 elsif Is_Limited_Record (Otyp) or else Is_Limited_Record (Ityp) then
8591 return True;
8593 -- Conversions to and from packed array types are always ignored and
8594 -- hence are safe.
8596 elsif Is_Packed_Array_Impl_Type (Otyp)
8597 or else Is_Packed_Array_Impl_Type (Ityp)
8598 then
8599 return True;
8600 end if;
8602 -- The only other cases known to be safe is if the input type's
8603 -- alignment is known to be at least the maximum alignment for the
8604 -- target or if both alignments are known and the output type's
8605 -- alignment is no stricter than the input's. We can use the component
8606 -- type alignement for an array if a type is an unpacked array type.
8608 if Present (Alignment_Clause (Otyp)) then
8609 Oalign := Expr_Value (Expression (Alignment_Clause (Otyp)));
8611 elsif Is_Array_Type (Otyp)
8612 and then Present (Alignment_Clause (Component_Type (Otyp)))
8613 then
8614 Oalign := Expr_Value (Expression (Alignment_Clause
8615 (Component_Type (Otyp))));
8616 end if;
8618 if Present (Alignment_Clause (Ityp)) then
8619 Ialign := Expr_Value (Expression (Alignment_Clause (Ityp)));
8621 elsif Is_Array_Type (Ityp)
8622 and then Present (Alignment_Clause (Component_Type (Ityp)))
8623 then
8624 Ialign := Expr_Value (Expression (Alignment_Clause
8625 (Component_Type (Ityp))));
8626 end if;
8628 if Ialign /= No_Uint and then Ialign > Maximum_Alignment then
8629 return True;
8631 elsif Ialign /= No_Uint
8632 and then Oalign /= No_Uint
8633 and then Ialign <= Oalign
8634 then
8635 return True;
8637 -- Otherwise, Gigi cannot handle this and we must make a temporary
8639 else
8640 return False;
8641 end if;
8642 end Safe_Unchecked_Type_Conversion;
8644 ---------------------------------
8645 -- Set_Current_Value_Condition --
8646 ---------------------------------
8648 -- Note: the implementation of this procedure is very closely tied to the
8649 -- implementation of Get_Current_Value_Condition. Here we set required
8650 -- Current_Value fields, and in Get_Current_Value_Condition, we interpret
8651 -- them, so they must have a consistent view.
8653 procedure Set_Current_Value_Condition (Cnode : Node_Id) is
8655 procedure Set_Entity_Current_Value (N : Node_Id);
8656 -- If N is an entity reference, where the entity is of an appropriate
8657 -- kind, then set the current value of this entity to Cnode, unless
8658 -- there is already a definite value set there.
8660 procedure Set_Expression_Current_Value (N : Node_Id);
8661 -- If N is of an appropriate form, sets an appropriate entry in current
8662 -- value fields of relevant entities. Multiple entities can be affected
8663 -- in the case of an AND or AND THEN.
8665 ------------------------------
8666 -- Set_Entity_Current_Value --
8667 ------------------------------
8669 procedure Set_Entity_Current_Value (N : Node_Id) is
8670 begin
8671 if Is_Entity_Name (N) then
8672 declare
8673 Ent : constant Entity_Id := Entity (N);
8675 begin
8676 -- Don't capture if not safe to do so
8678 if not Safe_To_Capture_Value (N, Ent, Cond => True) then
8679 return;
8680 end if;
8682 -- Here we have a case where the Current_Value field may need
8683 -- to be set. We set it if it is not already set to a compile
8684 -- time expression value.
8686 -- Note that this represents a decision that one condition
8687 -- blots out another previous one. That's certainly right if
8688 -- they occur at the same level. If the second one is nested,
8689 -- then the decision is neither right nor wrong (it would be
8690 -- equally OK to leave the outer one in place, or take the new
8691 -- inner one. Really we should record both, but our data
8692 -- structures are not that elaborate.
8694 if Nkind (Current_Value (Ent)) not in N_Subexpr then
8695 Set_Current_Value (Ent, Cnode);
8696 end if;
8697 end;
8698 end if;
8699 end Set_Entity_Current_Value;
8701 ----------------------------------
8702 -- Set_Expression_Current_Value --
8703 ----------------------------------
8705 procedure Set_Expression_Current_Value (N : Node_Id) is
8706 Cond : Node_Id;
8708 begin
8709 Cond := N;
8711 -- Loop to deal with (ignore for now) any NOT operators present. The
8712 -- presence of NOT operators will be handled properly when we call
8713 -- Get_Current_Value_Condition.
8715 while Nkind (Cond) = N_Op_Not loop
8716 Cond := Right_Opnd (Cond);
8717 end loop;
8719 -- For an AND or AND THEN, recursively process operands
8721 if Nkind (Cond) = N_Op_And or else Nkind (Cond) = N_And_Then then
8722 Set_Expression_Current_Value (Left_Opnd (Cond));
8723 Set_Expression_Current_Value (Right_Opnd (Cond));
8724 return;
8725 end if;
8727 -- Check possible relational operator
8729 if Nkind (Cond) in N_Op_Compare then
8730 if Compile_Time_Known_Value (Right_Opnd (Cond)) then
8731 Set_Entity_Current_Value (Left_Opnd (Cond));
8732 elsif Compile_Time_Known_Value (Left_Opnd (Cond)) then
8733 Set_Entity_Current_Value (Right_Opnd (Cond));
8734 end if;
8736 elsif Nkind_In (Cond,
8737 N_Type_Conversion,
8738 N_Qualified_Expression,
8739 N_Expression_With_Actions)
8740 then
8741 Set_Expression_Current_Value (Expression (Cond));
8743 -- Check possible boolean variable reference
8745 else
8746 Set_Entity_Current_Value (Cond);
8747 end if;
8748 end Set_Expression_Current_Value;
8750 -- Start of processing for Set_Current_Value_Condition
8752 begin
8753 Set_Expression_Current_Value (Condition (Cnode));
8754 end Set_Current_Value_Condition;
8756 --------------------------
8757 -- Set_Elaboration_Flag --
8758 --------------------------
8760 procedure Set_Elaboration_Flag (N : Node_Id; Spec_Id : Entity_Id) is
8761 Loc : constant Source_Ptr := Sloc (N);
8762 Ent : constant Entity_Id := Elaboration_Entity (Spec_Id);
8763 Asn : Node_Id;
8765 begin
8766 if Present (Ent) then
8768 -- Nothing to do if at the compilation unit level, because in this
8769 -- case the flag is set by the binder generated elaboration routine.
8771 if Nkind (Parent (N)) = N_Compilation_Unit then
8772 null;
8774 -- Here we do need to generate an assignment statement
8776 else
8777 Check_Restriction (No_Elaboration_Code, N);
8778 Asn :=
8779 Make_Assignment_Statement (Loc,
8780 Name => New_Occurrence_Of (Ent, Loc),
8781 Expression => Make_Integer_Literal (Loc, Uint_1));
8783 if Nkind (Parent (N)) = N_Subunit then
8784 Insert_After (Corresponding_Stub (Parent (N)), Asn);
8785 else
8786 Insert_After (N, Asn);
8787 end if;
8789 Analyze (Asn);
8791 -- Kill current value indication. This is necessary because the
8792 -- tests of this flag are inserted out of sequence and must not
8793 -- pick up bogus indications of the wrong constant value.
8795 Set_Current_Value (Ent, Empty);
8797 -- If the subprogram is in the current declarative part and
8798 -- 'access has been applied to it, generate an elaboration
8799 -- check at the beginning of the declarations of the body.
8801 if Nkind (N) = N_Subprogram_Body
8802 and then Address_Taken (Spec_Id)
8803 and then
8804 Ekind_In (Scope (Spec_Id), E_Block, E_Procedure, E_Function)
8805 then
8806 declare
8807 Loc : constant Source_Ptr := Sloc (N);
8808 Decls : constant List_Id := Declarations (N);
8809 Chk : Node_Id;
8811 begin
8812 -- No need to generate this check if first entry in the
8813 -- declaration list is a raise of Program_Error now.
8815 if Present (Decls)
8816 and then Nkind (First (Decls)) = N_Raise_Program_Error
8817 then
8818 return;
8819 end if;
8821 -- Otherwise generate the check
8823 Chk :=
8824 Make_Raise_Program_Error (Loc,
8825 Condition =>
8826 Make_Op_Eq (Loc,
8827 Left_Opnd => New_Occurrence_Of (Ent, Loc),
8828 Right_Opnd => Make_Integer_Literal (Loc, Uint_0)),
8829 Reason => PE_Access_Before_Elaboration);
8831 if No (Decls) then
8832 Set_Declarations (N, New_List (Chk));
8833 else
8834 Prepend (Chk, Decls);
8835 end if;
8837 Analyze (Chk);
8838 end;
8839 end if;
8840 end if;
8841 end if;
8842 end Set_Elaboration_Flag;
8844 ----------------------------
8845 -- Set_Renamed_Subprogram --
8846 ----------------------------
8848 procedure Set_Renamed_Subprogram (N : Node_Id; E : Entity_Id) is
8849 begin
8850 -- If input node is an identifier, we can just reset it
8852 if Nkind (N) = N_Identifier then
8853 Set_Chars (N, Chars (E));
8854 Set_Entity (N, E);
8856 -- Otherwise we have to do a rewrite, preserving Comes_From_Source
8858 else
8859 declare
8860 CS : constant Boolean := Comes_From_Source (N);
8861 begin
8862 Rewrite (N, Make_Identifier (Sloc (N), Chars (E)));
8863 Set_Entity (N, E);
8864 Set_Comes_From_Source (N, CS);
8865 Set_Analyzed (N, True);
8866 end;
8867 end if;
8868 end Set_Renamed_Subprogram;
8870 ----------------------
8871 -- Side_Effect_Free --
8872 ----------------------
8874 function Side_Effect_Free
8875 (N : Node_Id;
8876 Name_Req : Boolean := False;
8877 Variable_Ref : Boolean := False) return Boolean
8879 Typ : constant Entity_Id := Etype (N);
8880 -- Result type of the expression
8882 function Safe_Prefixed_Reference (N : Node_Id) return Boolean;
8883 -- The argument N is a construct where the Prefix is dereferenced if it
8884 -- is an access type and the result is a variable. The call returns True
8885 -- if the construct is side effect free (not considering side effects in
8886 -- other than the prefix which are to be tested by the caller).
8888 function Within_In_Parameter (N : Node_Id) return Boolean;
8889 -- Determines if N is a subcomponent of a composite in-parameter. If so,
8890 -- N is not side-effect free when the actual is global and modifiable
8891 -- indirectly from within a subprogram, because it may be passed by
8892 -- reference. The front-end must be conservative here and assume that
8893 -- this may happen with any array or record type. On the other hand, we
8894 -- cannot create temporaries for all expressions for which this
8895 -- condition is true, for various reasons that might require clearing up
8896 -- ??? For example, discriminant references that appear out of place, or
8897 -- spurious type errors with class-wide expressions. As a result, we
8898 -- limit the transformation to loop bounds, which is so far the only
8899 -- case that requires it.
8901 -----------------------------
8902 -- Safe_Prefixed_Reference --
8903 -----------------------------
8905 function Safe_Prefixed_Reference (N : Node_Id) return Boolean is
8906 begin
8907 -- If prefix is not side effect free, definitely not safe
8909 if not Side_Effect_Free (Prefix (N), Name_Req, Variable_Ref) then
8910 return False;
8912 -- If the prefix is of an access type that is not access-to-constant,
8913 -- then this construct is a variable reference, which means it is to
8914 -- be considered to have side effects if Variable_Ref is set True.
8916 elsif Is_Access_Type (Etype (Prefix (N)))
8917 and then not Is_Access_Constant (Etype (Prefix (N)))
8918 and then Variable_Ref
8919 then
8920 -- Exception is a prefix that is the result of a previous removal
8921 -- of side-effects.
8923 return Is_Entity_Name (Prefix (N))
8924 and then not Comes_From_Source (Prefix (N))
8925 and then Ekind (Entity (Prefix (N))) = E_Constant
8926 and then Is_Internal_Name (Chars (Entity (Prefix (N))));
8928 -- If the prefix is an explicit dereference then this construct is a
8929 -- variable reference, which means it is to be considered to have
8930 -- side effects if Variable_Ref is True.
8932 -- We do NOT exclude dereferences of access-to-constant types because
8933 -- we handle them as constant view of variables.
8935 elsif Nkind (Prefix (N)) = N_Explicit_Dereference
8936 and then Variable_Ref
8937 then
8938 return False;
8940 -- Note: The following test is the simplest way of solving a complex
8941 -- problem uncovered by the following test (Side effect on loop bound
8942 -- that is a subcomponent of a global variable:
8944 -- with Text_Io; use Text_Io;
8945 -- procedure Tloop is
8946 -- type X is
8947 -- record
8948 -- V : Natural := 4;
8949 -- S : String (1..5) := (others => 'a');
8950 -- end record;
8951 -- X1 : X;
8953 -- procedure Modi;
8955 -- generic
8956 -- with procedure Action;
8957 -- procedure Loop_G (Arg : X; Msg : String)
8959 -- procedure Loop_G (Arg : X; Msg : String) is
8960 -- begin
8961 -- Put_Line ("begin loop_g " & Msg & " will loop till: "
8962 -- & Natural'Image (Arg.V));
8963 -- for Index in 1 .. Arg.V loop
8964 -- Text_Io.Put_Line
8965 -- (Natural'Image (Index) & " " & Arg.S (Index));
8966 -- if Index > 2 then
8967 -- Modi;
8968 -- end if;
8969 -- end loop;
8970 -- Put_Line ("end loop_g " & Msg);
8971 -- end;
8973 -- procedure Loop1 is new Loop_G (Modi);
8974 -- procedure Modi is
8975 -- begin
8976 -- X1.V := 1;
8977 -- Loop1 (X1, "from modi");
8978 -- end;
8980 -- begin
8981 -- Loop1 (X1, "initial");
8982 -- end;
8984 -- The output of the above program should be:
8986 -- begin loop_g initial will loop till: 4
8987 -- 1 a
8988 -- 2 a
8989 -- 3 a
8990 -- begin loop_g from modi will loop till: 1
8991 -- 1 a
8992 -- end loop_g from modi
8993 -- 4 a
8994 -- begin loop_g from modi will loop till: 1
8995 -- 1 a
8996 -- end loop_g from modi
8997 -- end loop_g initial
8999 -- If a loop bound is a subcomponent of a global variable, a
9000 -- modification of that variable within the loop may incorrectly
9001 -- affect the execution of the loop.
9003 elsif Nkind (Parent (Parent (N))) = N_Loop_Parameter_Specification
9004 and then Within_In_Parameter (Prefix (N))
9005 and then Variable_Ref
9006 then
9007 return False;
9009 -- All other cases are side effect free
9011 else
9012 return True;
9013 end if;
9014 end Safe_Prefixed_Reference;
9016 -------------------------
9017 -- Within_In_Parameter --
9018 -------------------------
9020 function Within_In_Parameter (N : Node_Id) return Boolean is
9021 begin
9022 if not Comes_From_Source (N) then
9023 return False;
9025 elsif Is_Entity_Name (N) then
9026 return Ekind (Entity (N)) = E_In_Parameter;
9028 elsif Nkind_In (N, N_Indexed_Component, N_Selected_Component) then
9029 return Within_In_Parameter (Prefix (N));
9031 else
9032 return False;
9033 end if;
9034 end Within_In_Parameter;
9036 -- Start of processing for Side_Effect_Free
9038 begin
9039 -- If volatile reference, always consider it to have side effects
9041 if Is_Volatile_Reference (N) then
9042 return False;
9043 end if;
9045 -- Note on checks that could raise Constraint_Error. Strictly, if we
9046 -- take advantage of 11.6, these checks do not count as side effects.
9047 -- However, we would prefer to consider that they are side effects,
9048 -- since the backend CSE does not work very well on expressions which
9049 -- can raise Constraint_Error. On the other hand if we don't consider
9050 -- them to be side effect free, then we get some awkward expansions
9051 -- in -gnato mode, resulting in code insertions at a point where we
9052 -- do not have a clear model for performing the insertions.
9054 -- Special handling for entity names
9056 if Is_Entity_Name (N) then
9058 -- A type reference is always side effect free
9060 if Is_Type (Entity (N)) then
9061 return True;
9063 -- Variables are considered to be a side effect if Variable_Ref
9064 -- is set or if we have a volatile reference and Name_Req is off.
9065 -- If Name_Req is True then we can't help returning a name which
9066 -- effectively allows multiple references in any case.
9068 elsif Is_Variable (N, Use_Original_Node => False) then
9069 return not Variable_Ref
9070 and then (not Is_Volatile_Reference (N) or else Name_Req);
9072 -- Any other entity (e.g. a subtype name) is definitely side
9073 -- effect free.
9075 else
9076 return True;
9077 end if;
9079 -- A value known at compile time is always side effect free
9081 elsif Compile_Time_Known_Value (N) then
9082 return True;
9084 -- A variable renaming is not side-effect free, because the renaming
9085 -- will function like a macro in the front-end in some cases, and an
9086 -- assignment can modify the component designated by N, so we need to
9087 -- create a temporary for it.
9089 -- The guard testing for Entity being present is needed at least in
9090 -- the case of rewritten predicate expressions, and may well also be
9091 -- appropriate elsewhere. Obviously we can't go testing the entity
9092 -- field if it does not exist, so it's reasonable to say that this is
9093 -- not the renaming case if it does not exist.
9095 elsif Is_Entity_Name (Original_Node (N))
9096 and then Present (Entity (Original_Node (N)))
9097 and then Is_Renaming_Of_Object (Entity (Original_Node (N)))
9098 and then Ekind (Entity (Original_Node (N))) /= E_Constant
9099 then
9100 declare
9101 RO : constant Node_Id :=
9102 Renamed_Object (Entity (Original_Node (N)));
9104 begin
9105 -- If the renamed object is an indexed component, or an
9106 -- explicit dereference, then the designated object could
9107 -- be modified by an assignment.
9109 if Nkind_In (RO, N_Indexed_Component,
9110 N_Explicit_Dereference)
9111 then
9112 return False;
9114 -- A selected component must have a safe prefix
9116 elsif Nkind (RO) = N_Selected_Component then
9117 return Safe_Prefixed_Reference (RO);
9119 -- In all other cases, designated object cannot be changed so
9120 -- we are side effect free.
9122 else
9123 return True;
9124 end if;
9125 end;
9127 -- Remove_Side_Effects generates an object renaming declaration to
9128 -- capture the expression of a class-wide expression. In VM targets
9129 -- the frontend performs no expansion for dispatching calls to
9130 -- class- wide types since they are handled by the VM. Hence, we must
9131 -- locate here if this node corresponds to a previous invocation of
9132 -- Remove_Side_Effects to avoid a never ending loop in the frontend.
9134 elsif not Tagged_Type_Expansion
9135 and then not Comes_From_Source (N)
9136 and then Nkind (Parent (N)) = N_Object_Renaming_Declaration
9137 and then Is_Class_Wide_Type (Typ)
9138 then
9139 return True;
9141 -- Generating C the type conversion of an access to constrained array
9142 -- type into an access to unconstrained array type involves initializing
9143 -- a fat pointer and the expression cannot be assumed to be free of side
9144 -- effects since it must referenced several times to compute its bounds.
9146 elsif Generate_C_Code
9147 and then Nkind (N) = N_Type_Conversion
9148 and then Is_Access_Type (Typ)
9149 and then Is_Array_Type (Designated_Type (Typ))
9150 and then not Is_Constrained (Designated_Type (Typ))
9151 then
9152 return False;
9153 end if;
9155 -- For other than entity names and compile time known values,
9156 -- check the node kind for special processing.
9158 case Nkind (N) is
9160 -- An attribute reference is side effect free if its expressions
9161 -- are side effect free and its prefix is side effect free or
9162 -- is an entity reference.
9164 -- Is this right? what about x'first where x is a variable???
9166 when N_Attribute_Reference =>
9167 return Side_Effect_Free (Expressions (N), Name_Req, Variable_Ref)
9168 and then Attribute_Name (N) /= Name_Input
9169 and then (Is_Entity_Name (Prefix (N))
9170 or else Side_Effect_Free
9171 (Prefix (N), Name_Req, Variable_Ref));
9173 -- A binary operator is side effect free if and both operands are
9174 -- side effect free. For this purpose binary operators include
9175 -- membership tests and short circuit forms.
9177 when N_Binary_Op | N_Membership_Test | N_Short_Circuit =>
9178 return Side_Effect_Free (Left_Opnd (N), Name_Req, Variable_Ref)
9179 and then
9180 Side_Effect_Free (Right_Opnd (N), Name_Req, Variable_Ref);
9182 -- An explicit dereference is side effect free only if it is
9183 -- a side effect free prefixed reference.
9185 when N_Explicit_Dereference =>
9186 return Safe_Prefixed_Reference (N);
9188 -- An expression with action is side effect free if its expression
9189 -- is side effect free and it has no actions.
9191 when N_Expression_With_Actions =>
9192 return Is_Empty_List (Actions (N))
9193 and then
9194 Side_Effect_Free (Expression (N), Name_Req, Variable_Ref);
9196 -- A call to _rep_to_pos is side effect free, since we generate
9197 -- this pure function call ourselves. Moreover it is critically
9198 -- important to make this exception, since otherwise we can have
9199 -- discriminants in array components which don't look side effect
9200 -- free in the case of an array whose index type is an enumeration
9201 -- type with an enumeration rep clause.
9203 -- All other function calls are not side effect free
9205 when N_Function_Call =>
9206 return Nkind (Name (N)) = N_Identifier
9207 and then Is_TSS (Name (N), TSS_Rep_To_Pos)
9208 and then
9209 Side_Effect_Free
9210 (First (Parameter_Associations (N)), Name_Req, Variable_Ref);
9212 -- An IF expression is side effect free if it's of a scalar type, and
9213 -- all its components are all side effect free (conditions and then
9214 -- actions and else actions). We restrict to scalar types, since it
9215 -- is annoying to deal with things like (if A then B else C)'First
9216 -- where the type involved is a string type.
9218 when N_If_Expression =>
9219 return Is_Scalar_Type (Typ)
9220 and then
9221 Side_Effect_Free (Expressions (N), Name_Req, Variable_Ref);
9223 -- An indexed component is side effect free if it is a side
9224 -- effect free prefixed reference and all the indexing
9225 -- expressions are side effect free.
9227 when N_Indexed_Component =>
9228 return Side_Effect_Free (Expressions (N), Name_Req, Variable_Ref)
9229 and then Safe_Prefixed_Reference (N);
9231 -- A type qualification is side effect free if the expression
9232 -- is side effect free.
9234 when N_Qualified_Expression =>
9235 return Side_Effect_Free (Expression (N), Name_Req, Variable_Ref);
9237 -- A selected component is side effect free only if it is a side
9238 -- effect free prefixed reference.
9240 when N_Selected_Component =>
9241 return Safe_Prefixed_Reference (N);
9243 -- A range is side effect free if the bounds are side effect free
9245 when N_Range =>
9246 return Side_Effect_Free (Low_Bound (N), Name_Req, Variable_Ref)
9247 and then
9248 Side_Effect_Free (High_Bound (N), Name_Req, Variable_Ref);
9250 -- A slice is side effect free if it is a side effect free
9251 -- prefixed reference and the bounds are side effect free.
9253 when N_Slice =>
9254 return Side_Effect_Free
9255 (Discrete_Range (N), Name_Req, Variable_Ref)
9256 and then Safe_Prefixed_Reference (N);
9258 -- A type conversion is side effect free if the expression to be
9259 -- converted is side effect free.
9261 when N_Type_Conversion =>
9262 return Side_Effect_Free (Expression (N), Name_Req, Variable_Ref);
9264 -- A unary operator is side effect free if the operand
9265 -- is side effect free.
9267 when N_Unary_Op =>
9268 return Side_Effect_Free (Right_Opnd (N), Name_Req, Variable_Ref);
9270 -- An unchecked type conversion is side effect free only if it
9271 -- is safe and its argument is side effect free.
9273 when N_Unchecked_Type_Conversion =>
9274 return Safe_Unchecked_Type_Conversion (N)
9275 and then
9276 Side_Effect_Free (Expression (N), Name_Req, Variable_Ref);
9278 -- An unchecked expression is side effect free if its expression
9279 -- is side effect free.
9281 when N_Unchecked_Expression =>
9282 return Side_Effect_Free (Expression (N), Name_Req, Variable_Ref);
9284 -- A literal is side effect free
9286 when N_Character_Literal |
9287 N_Integer_Literal |
9288 N_Real_Literal |
9289 N_String_Literal =>
9290 return True;
9292 -- We consider that anything else has side effects. This is a bit
9293 -- crude, but we are pretty close for most common cases, and we
9294 -- are certainly correct (i.e. we never return True when the
9295 -- answer should be False).
9297 when others =>
9298 return False;
9299 end case;
9300 end Side_Effect_Free;
9302 -- A list is side effect free if all elements of the list are side
9303 -- effect free.
9305 function Side_Effect_Free
9306 (L : List_Id;
9307 Name_Req : Boolean := False;
9308 Variable_Ref : Boolean := False) return Boolean
9310 N : Node_Id;
9312 begin
9313 if L = No_List or else L = Error_List then
9314 return True;
9316 else
9317 N := First (L);
9318 while Present (N) loop
9319 if not Side_Effect_Free (N, Name_Req, Variable_Ref) then
9320 return False;
9321 else
9322 Next (N);
9323 end if;
9324 end loop;
9326 return True;
9327 end if;
9328 end Side_Effect_Free;
9330 ----------------------------------
9331 -- Silly_Boolean_Array_Not_Test --
9332 ----------------------------------
9334 -- This procedure implements an odd and silly test. We explicitly check
9335 -- for the case where the 'First of the component type is equal to the
9336 -- 'Last of this component type, and if this is the case, we make sure
9337 -- that constraint error is raised. The reason is that the NOT is bound
9338 -- to cause CE in this case, and we will not otherwise catch it.
9340 -- No such check is required for AND and OR, since for both these cases
9341 -- False op False = False, and True op True = True. For the XOR case,
9342 -- see Silly_Boolean_Array_Xor_Test.
9344 -- Believe it or not, this was reported as a bug. Note that nearly always,
9345 -- the test will evaluate statically to False, so the code will be
9346 -- statically removed, and no extra overhead caused.
9348 procedure Silly_Boolean_Array_Not_Test (N : Node_Id; T : Entity_Id) is
9349 Loc : constant Source_Ptr := Sloc (N);
9350 CT : constant Entity_Id := Component_Type (T);
9352 begin
9353 -- The check we install is
9355 -- constraint_error when
9356 -- component_type'first = component_type'last
9357 -- and then array_type'Length /= 0)
9359 -- We need the last guard because we don't want to raise CE for empty
9360 -- arrays since no out of range values result. (Empty arrays with a
9361 -- component type of True .. True -- very useful -- even the ACATS
9362 -- does not test that marginal case).
9364 Insert_Action (N,
9365 Make_Raise_Constraint_Error (Loc,
9366 Condition =>
9367 Make_And_Then (Loc,
9368 Left_Opnd =>
9369 Make_Op_Eq (Loc,
9370 Left_Opnd =>
9371 Make_Attribute_Reference (Loc,
9372 Prefix => New_Occurrence_Of (CT, Loc),
9373 Attribute_Name => Name_First),
9375 Right_Opnd =>
9376 Make_Attribute_Reference (Loc,
9377 Prefix => New_Occurrence_Of (CT, Loc),
9378 Attribute_Name => Name_Last)),
9380 Right_Opnd => Make_Non_Empty_Check (Loc, Right_Opnd (N))),
9381 Reason => CE_Range_Check_Failed));
9382 end Silly_Boolean_Array_Not_Test;
9384 ----------------------------------
9385 -- Silly_Boolean_Array_Xor_Test --
9386 ----------------------------------
9388 -- This procedure implements an odd and silly test. We explicitly check
9389 -- for the XOR case where the component type is True .. True, since this
9390 -- will raise constraint error. A special check is required since CE
9391 -- will not be generated otherwise (cf Expand_Packed_Not).
9393 -- No such check is required for AND and OR, since for both these cases
9394 -- False op False = False, and True op True = True, and no check is
9395 -- required for the case of False .. False, since False xor False = False.
9396 -- See also Silly_Boolean_Array_Not_Test
9398 procedure Silly_Boolean_Array_Xor_Test (N : Node_Id; T : Entity_Id) is
9399 Loc : constant Source_Ptr := Sloc (N);
9400 CT : constant Entity_Id := Component_Type (T);
9402 begin
9403 -- The check we install is
9405 -- constraint_error when
9406 -- Boolean (component_type'First)
9407 -- and then Boolean (component_type'Last)
9408 -- and then array_type'Length /= 0)
9410 -- We need the last guard because we don't want to raise CE for empty
9411 -- arrays since no out of range values result (Empty arrays with a
9412 -- component type of True .. True -- very useful -- even the ACATS
9413 -- does not test that marginal case).
9415 Insert_Action (N,
9416 Make_Raise_Constraint_Error (Loc,
9417 Condition =>
9418 Make_And_Then (Loc,
9419 Left_Opnd =>
9420 Make_And_Then (Loc,
9421 Left_Opnd =>
9422 Convert_To (Standard_Boolean,
9423 Make_Attribute_Reference (Loc,
9424 Prefix => New_Occurrence_Of (CT, Loc),
9425 Attribute_Name => Name_First)),
9427 Right_Opnd =>
9428 Convert_To (Standard_Boolean,
9429 Make_Attribute_Reference (Loc,
9430 Prefix => New_Occurrence_Of (CT, Loc),
9431 Attribute_Name => Name_Last))),
9433 Right_Opnd => Make_Non_Empty_Check (Loc, Right_Opnd (N))),
9434 Reason => CE_Range_Check_Failed));
9435 end Silly_Boolean_Array_Xor_Test;
9437 --------------------------
9438 -- Target_Has_Fixed_Ops --
9439 --------------------------
9441 Integer_Sized_Small : Ureal;
9442 -- Set to 2.0 ** -(Integer'Size - 1) the first time that this function is
9443 -- called (we don't want to compute it more than once).
9445 Long_Integer_Sized_Small : Ureal;
9446 -- Set to 2.0 ** -(Long_Integer'Size - 1) the first time that this function
9447 -- is called (we don't want to compute it more than once)
9449 First_Time_For_THFO : Boolean := True;
9450 -- Set to False after first call (if Fractional_Fixed_Ops_On_Target)
9452 function Target_Has_Fixed_Ops
9453 (Left_Typ : Entity_Id;
9454 Right_Typ : Entity_Id;
9455 Result_Typ : Entity_Id) return Boolean
9457 function Is_Fractional_Type (Typ : Entity_Id) return Boolean;
9458 -- Return True if the given type is a fixed-point type with a small
9459 -- value equal to 2 ** (-(T'Object_Size - 1)) and whose values have
9460 -- an absolute value less than 1.0. This is currently limited to
9461 -- fixed-point types that map to Integer or Long_Integer.
9463 ------------------------
9464 -- Is_Fractional_Type --
9465 ------------------------
9467 function Is_Fractional_Type (Typ : Entity_Id) return Boolean is
9468 begin
9469 if Esize (Typ) = Standard_Integer_Size then
9470 return Small_Value (Typ) = Integer_Sized_Small;
9472 elsif Esize (Typ) = Standard_Long_Integer_Size then
9473 return Small_Value (Typ) = Long_Integer_Sized_Small;
9475 else
9476 return False;
9477 end if;
9478 end Is_Fractional_Type;
9480 -- Start of processing for Target_Has_Fixed_Ops
9482 begin
9483 -- Return False if Fractional_Fixed_Ops_On_Target is false
9485 if not Fractional_Fixed_Ops_On_Target then
9486 return False;
9487 end if;
9489 -- Here the target has Fractional_Fixed_Ops, if first time, compute
9490 -- standard constants used by Is_Fractional_Type.
9492 if First_Time_For_THFO then
9493 First_Time_For_THFO := False;
9495 Integer_Sized_Small :=
9496 UR_From_Components
9497 (Num => Uint_1,
9498 Den => UI_From_Int (Standard_Integer_Size - 1),
9499 Rbase => 2);
9501 Long_Integer_Sized_Small :=
9502 UR_From_Components
9503 (Num => Uint_1,
9504 Den => UI_From_Int (Standard_Long_Integer_Size - 1),
9505 Rbase => 2);
9506 end if;
9508 -- Return True if target supports fixed-by-fixed multiply/divide for
9509 -- fractional fixed-point types (see Is_Fractional_Type) and the operand
9510 -- and result types are equivalent fractional types.
9512 return Is_Fractional_Type (Base_Type (Left_Typ))
9513 and then Is_Fractional_Type (Base_Type (Right_Typ))
9514 and then Is_Fractional_Type (Base_Type (Result_Typ))
9515 and then Esize (Left_Typ) = Esize (Right_Typ)
9516 and then Esize (Left_Typ) = Esize (Result_Typ);
9517 end Target_Has_Fixed_Ops;
9519 ------------------------------------------
9520 -- Type_May_Have_Bit_Aligned_Components --
9521 ------------------------------------------
9523 function Type_May_Have_Bit_Aligned_Components
9524 (Typ : Entity_Id) return Boolean
9526 begin
9527 -- Array type, check component type
9529 if Is_Array_Type (Typ) then
9530 return
9531 Type_May_Have_Bit_Aligned_Components (Component_Type (Typ));
9533 -- Record type, check components
9535 elsif Is_Record_Type (Typ) then
9536 declare
9537 E : Entity_Id;
9539 begin
9540 E := First_Component_Or_Discriminant (Typ);
9541 while Present (E) loop
9542 if Component_May_Be_Bit_Aligned (E)
9543 or else Type_May_Have_Bit_Aligned_Components (Etype (E))
9544 then
9545 return True;
9546 end if;
9548 Next_Component_Or_Discriminant (E);
9549 end loop;
9551 return False;
9552 end;
9554 -- Type other than array or record is always OK
9556 else
9557 return False;
9558 end if;
9559 end Type_May_Have_Bit_Aligned_Components;
9561 ----------------------------------
9562 -- Within_Case_Or_If_Expression --
9563 ----------------------------------
9565 function Within_Case_Or_If_Expression (N : Node_Id) return Boolean is
9566 Par : Node_Id;
9568 begin
9569 -- Locate an enclosing case or if expression. Note that these constructs
9570 -- can be expanded into Expression_With_Actions, hence the test of the
9571 -- original node.
9573 Par := Parent (N);
9574 while Present (Par) loop
9575 if Nkind_In (Original_Node (Par), N_Case_Expression,
9576 N_If_Expression)
9577 then
9578 return True;
9580 -- Prevent the search from going too far
9582 elsif Is_Body_Or_Package_Declaration (Par) then
9583 return False;
9584 end if;
9586 Par := Parent (Par);
9587 end loop;
9589 return False;
9590 end Within_Case_Or_If_Expression;
9592 --------------------------------
9593 -- Within_Internal_Subprogram --
9594 --------------------------------
9596 function Within_Internal_Subprogram return Boolean is
9597 S : Entity_Id;
9599 begin
9600 S := Current_Scope;
9601 while Present (S) and then not Is_Subprogram (S) loop
9602 S := Scope (S);
9603 end loop;
9605 return Present (S)
9606 and then Get_TSS_Name (S) /= TSS_Null
9607 and then not Is_Predicate_Function (S)
9608 and then not Is_Predicate_Function_M (S);
9609 end Within_Internal_Subprogram;
9611 end Exp_Util;