Implement -mmemcpy-strategy= and -mmemset-strategy= options
[official-gcc.git] / gcc / ada / exp_util.adb
blobca8bc9839ab4685b2dc374cbd18116711f0625cf
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-2013, 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 Inline; use Inline;
38 with Itypes; use Itypes;
39 with Lib; use Lib;
40 with Nlists; use Nlists;
41 with Nmake; use Nmake;
42 with Opt; use Opt;
43 with Restrict; use Restrict;
44 with Rident; use Rident;
45 with Sem; use Sem;
46 with Sem_Aux; use Sem_Aux;
47 with Sem_Ch8; use Sem_Ch8;
48 with Sem_Eval; use Sem_Eval;
49 with Sem_Res; use Sem_Res;
50 with Sem_Type; use Sem_Type;
51 with Sem_Util; use Sem_Util;
52 with Snames; use Snames;
53 with Stand; use Stand;
54 with Stringt; use Stringt;
55 with Targparm; use Targparm;
56 with Tbuild; use Tbuild;
57 with Ttypes; use Ttypes;
58 with Urealp; use Urealp;
59 with Validsw; use Validsw;
61 package body Exp_Util is
63 -----------------------
64 -- Local Subprograms --
65 -----------------------
67 function Build_Task_Array_Image
68 (Loc : Source_Ptr;
69 Id_Ref : Node_Id;
70 A_Type : Entity_Id;
71 Dyn : Boolean := False) return Node_Id;
72 -- Build function to generate the image string for a task that is an array
73 -- component, concatenating the images of each index. To avoid storage
74 -- leaks, the string is built with successive slice assignments. The flag
75 -- Dyn indicates whether this is called for the initialization procedure of
76 -- an array of tasks, or for the name of a dynamically created task that is
77 -- assigned to an indexed component.
79 function Build_Task_Image_Function
80 (Loc : Source_Ptr;
81 Decls : List_Id;
82 Stats : List_Id;
83 Res : Entity_Id) return Node_Id;
84 -- Common processing for Task_Array_Image and Task_Record_Image. Build
85 -- function body that computes image.
87 procedure Build_Task_Image_Prefix
88 (Loc : Source_Ptr;
89 Len : out Entity_Id;
90 Res : out Entity_Id;
91 Pos : out Entity_Id;
92 Prefix : Entity_Id;
93 Sum : Node_Id;
94 Decls : List_Id;
95 Stats : List_Id);
96 -- Common processing for Task_Array_Image and Task_Record_Image. Create
97 -- local variables and assign prefix of name to result string.
99 function Build_Task_Record_Image
100 (Loc : Source_Ptr;
101 Id_Ref : Node_Id;
102 Dyn : Boolean := False) return Node_Id;
103 -- Build function to generate the image string for a task that is a record
104 -- component. Concatenate name of variable with that of selector. The flag
105 -- Dyn indicates whether this is called for the initialization procedure of
106 -- record with task components, or for a dynamically created task that is
107 -- assigned to a selected component.
109 function Make_CW_Equivalent_Type
110 (T : Entity_Id;
111 E : Node_Id) return Entity_Id;
112 -- T is a class-wide type entity, E is the initial expression node that
113 -- constrains T in case such as: " X: T := E" or "new T'(E)". This function
114 -- returns the entity of the Equivalent type and inserts on the fly the
115 -- necessary declaration such as:
117 -- type anon is record
118 -- _parent : Root_Type (T); constrained with E discriminants (if any)
119 -- Extension : String (1 .. expr to match size of E);
120 -- end record;
122 -- This record is compatible with any object of the class of T thanks to
123 -- the first field and has the same size as E thanks to the second.
125 function Make_Literal_Range
126 (Loc : Source_Ptr;
127 Literal_Typ : Entity_Id) return Node_Id;
128 -- Produce a Range node whose bounds are:
129 -- Low_Bound (Literal_Type) ..
130 -- Low_Bound (Literal_Type) + (Length (Literal_Typ) - 1)
131 -- this is used for expanding declarations like X : String := "sdfgdfg";
133 -- If the index type of the target array is not integer, we generate:
134 -- Low_Bound (Literal_Type) ..
135 -- Literal_Type'Val
136 -- (Literal_Type'Pos (Low_Bound (Literal_Type))
137 -- + (Length (Literal_Typ) -1))
139 function Make_Non_Empty_Check
140 (Loc : Source_Ptr;
141 N : Node_Id) return Node_Id;
142 -- Produce a boolean expression checking that the unidimensional array
143 -- node N is not empty.
145 function New_Class_Wide_Subtype
146 (CW_Typ : Entity_Id;
147 N : Node_Id) return Entity_Id;
148 -- Create an implicit subtype of CW_Typ attached to node N
150 function Requires_Cleanup_Actions
151 (L : List_Id;
152 Lib_Level : Boolean;
153 Nested_Constructs : Boolean) return Boolean;
154 -- Given a list L, determine whether it contains one of the following:
156 -- 1) controlled objects
157 -- 2) library-level tagged types
159 -- Lib_Level is True when the list comes from a construct at the library
160 -- level, and False otherwise. Nested_Constructs is True when any nested
161 -- packages declared in L must be processed, and False otherwise.
163 -------------------------------------
164 -- Activate_Atomic_Synchronization --
165 -------------------------------------
167 procedure Activate_Atomic_Synchronization (N : Node_Id) is
168 Msg_Node : Node_Id;
170 begin
171 case Nkind (Parent (N)) is
173 -- Check for cases of appearing in the prefix of a construct where
174 -- we don't need atomic synchronization for this kind of usage.
176 when
177 -- Nothing to do if we are the prefix of an attribute, since we
178 -- do not want an atomic sync operation for things like 'Size.
180 N_Attribute_Reference |
182 -- The N_Reference node is like an attribute
184 N_Reference |
186 -- Nothing to do for a reference to a component (or components)
187 -- of a composite object. Only reads and updates of the object
188 -- as a whole require atomic synchronization (RM C.6 (15)).
190 N_Indexed_Component |
191 N_Selected_Component |
192 N_Slice =>
194 -- For all the above cases, nothing to do if we are the prefix
196 if Prefix (Parent (N)) = N then
197 return;
198 end if;
200 when others => null;
201 end case;
203 -- Go ahead and set the flag
205 Set_Atomic_Sync_Required (N);
207 -- Generate info message if requested
209 if Warn_On_Atomic_Synchronization then
210 case Nkind (N) is
211 when N_Identifier =>
212 Msg_Node := N;
214 when N_Selected_Component | N_Expanded_Name =>
215 Msg_Node := Selector_Name (N);
217 when N_Explicit_Dereference | N_Indexed_Component =>
218 Msg_Node := Empty;
220 when others =>
221 pragma Assert (False);
222 return;
223 end case;
225 if Present (Msg_Node) then
226 Error_Msg_N
227 ("?N?info: atomic synchronization set for &", Msg_Node);
228 else
229 Error_Msg_N
230 ("?N?info: atomic synchronization set", N);
231 end if;
232 end if;
233 end Activate_Atomic_Synchronization;
235 ----------------------
236 -- Adjust_Condition --
237 ----------------------
239 procedure Adjust_Condition (N : Node_Id) is
240 begin
241 if No (N) then
242 return;
243 end if;
245 declare
246 Loc : constant Source_Ptr := Sloc (N);
247 T : constant Entity_Id := Etype (N);
248 Ti : Entity_Id;
250 begin
251 -- Defend against a call where the argument has no type, or has a
252 -- type that is not Boolean. This can occur because of prior errors.
254 if No (T) or else not Is_Boolean_Type (T) then
255 return;
256 end if;
258 -- Apply validity checking if needed
260 if Validity_Checks_On and Validity_Check_Tests then
261 Ensure_Valid (N);
262 end if;
264 -- Immediate return if standard boolean, the most common case,
265 -- where nothing needs to be done.
267 if Base_Type (T) = Standard_Boolean then
268 return;
269 end if;
271 -- Case of zero/non-zero semantics or non-standard enumeration
272 -- representation. In each case, we rewrite the node as:
274 -- ityp!(N) /= False'Enum_Rep
276 -- where ityp is an integer type with large enough size to hold any
277 -- value of type T.
279 if Nonzero_Is_True (T) or else Has_Non_Standard_Rep (T) then
280 if Esize (T) <= Esize (Standard_Integer) then
281 Ti := Standard_Integer;
282 else
283 Ti := Standard_Long_Long_Integer;
284 end if;
286 Rewrite (N,
287 Make_Op_Ne (Loc,
288 Left_Opnd => Unchecked_Convert_To (Ti, N),
289 Right_Opnd =>
290 Make_Attribute_Reference (Loc,
291 Attribute_Name => Name_Enum_Rep,
292 Prefix =>
293 New_Occurrence_Of (First_Literal (T), Loc))));
294 Analyze_And_Resolve (N, Standard_Boolean);
296 else
297 Rewrite (N, Convert_To (Standard_Boolean, N));
298 Analyze_And_Resolve (N, Standard_Boolean);
299 end if;
300 end;
301 end Adjust_Condition;
303 ------------------------
304 -- Adjust_Result_Type --
305 ------------------------
307 procedure Adjust_Result_Type (N : Node_Id; T : Entity_Id) is
308 begin
309 -- Ignore call if current type is not Standard.Boolean
311 if Etype (N) /= Standard_Boolean then
312 return;
313 end if;
315 -- If result is already of correct type, nothing to do. Note that
316 -- this will get the most common case where everything has a type
317 -- of Standard.Boolean.
319 if Base_Type (T) = Standard_Boolean then
320 return;
322 else
323 declare
324 KP : constant Node_Kind := Nkind (Parent (N));
326 begin
327 -- If result is to be used as a Condition in the syntax, no need
328 -- to convert it back, since if it was changed to Standard.Boolean
329 -- using Adjust_Condition, that is just fine for this usage.
331 if KP in N_Raise_xxx_Error or else KP in N_Has_Condition then
332 return;
334 -- If result is an operand of another logical operation, no need
335 -- to reset its type, since Standard.Boolean is just fine, and
336 -- such operations always do Adjust_Condition on their operands.
338 elsif KP in N_Op_Boolean
339 or else KP in N_Short_Circuit
340 or else KP = N_Op_Not
341 then
342 return;
344 -- Otherwise we perform a conversion from the current type, which
345 -- must be Standard.Boolean, to the desired type.
347 else
348 Set_Analyzed (N);
349 Rewrite (N, Convert_To (T, N));
350 Analyze_And_Resolve (N, T);
351 end if;
352 end;
353 end if;
354 end Adjust_Result_Type;
356 --------------------------
357 -- Append_Freeze_Action --
358 --------------------------
360 procedure Append_Freeze_Action (T : Entity_Id; N : Node_Id) is
361 Fnode : Node_Id;
363 begin
364 Ensure_Freeze_Node (T);
365 Fnode := Freeze_Node (T);
367 if No (Actions (Fnode)) then
368 Set_Actions (Fnode, New_List (N));
369 else
370 Append (N, Actions (Fnode));
371 end if;
373 end Append_Freeze_Action;
375 ---------------------------
376 -- Append_Freeze_Actions --
377 ---------------------------
379 procedure Append_Freeze_Actions (T : Entity_Id; L : List_Id) is
380 Fnode : Node_Id;
382 begin
383 if No (L) then
384 return;
385 end if;
387 Ensure_Freeze_Node (T);
388 Fnode := Freeze_Node (T);
390 if No (Actions (Fnode)) then
391 Set_Actions (Fnode, L);
392 else
393 Append_List (L, Actions (Fnode));
394 end if;
395 end Append_Freeze_Actions;
397 ------------------------------------
398 -- Build_Allocate_Deallocate_Proc --
399 ------------------------------------
401 procedure Build_Allocate_Deallocate_Proc
402 (N : Node_Id;
403 Is_Allocate : Boolean)
405 Desig_Typ : Entity_Id;
406 Expr : Node_Id;
407 Pool_Id : Entity_Id;
408 Proc_To_Call : Node_Id := Empty;
409 Ptr_Typ : Entity_Id;
411 function Find_Finalize_Address (Typ : Entity_Id) return Entity_Id;
412 -- Locate TSS primitive Finalize_Address in type Typ
414 function Find_Object (E : Node_Id) return Node_Id;
415 -- Given an arbitrary expression of an allocator, try to find an object
416 -- reference in it, otherwise return the original expression.
418 function Is_Allocate_Deallocate_Proc (Subp : Entity_Id) return Boolean;
419 -- Determine whether subprogram Subp denotes a custom allocate or
420 -- deallocate.
422 ---------------------------
423 -- Find_Finalize_Address --
424 ---------------------------
426 function Find_Finalize_Address (Typ : Entity_Id) return Entity_Id is
427 Utyp : Entity_Id := Typ;
429 begin
430 -- Handle protected class-wide or task class-wide types
432 if Is_Class_Wide_Type (Utyp) then
433 if Is_Concurrent_Type (Root_Type (Utyp)) then
434 Utyp := Root_Type (Utyp);
436 elsif Is_Private_Type (Root_Type (Utyp))
437 and then Present (Full_View (Root_Type (Utyp)))
438 and then Is_Concurrent_Type (Full_View (Root_Type (Utyp)))
439 then
440 Utyp := Full_View (Root_Type (Utyp));
441 end if;
442 end if;
444 -- Handle private types
446 if Is_Private_Type (Utyp) and then Present (Full_View (Utyp)) then
447 Utyp := Full_View (Utyp);
448 end if;
450 -- Handle protected and task types
452 if Is_Concurrent_Type (Utyp)
453 and then Present (Corresponding_Record_Type (Utyp))
454 then
455 Utyp := Corresponding_Record_Type (Utyp);
456 end if;
458 Utyp := Underlying_Type (Base_Type (Utyp));
460 -- Deal with non-tagged derivation of private views. If the parent is
461 -- now known to be protected, the finalization routine is the one
462 -- defined on the corresponding record of the ancestor (corresponding
463 -- records do not automatically inherit operations, but maybe they
464 -- should???)
466 if Is_Untagged_Derivation (Typ) then
467 if Is_Protected_Type (Typ) then
468 Utyp := Corresponding_Record_Type (Root_Type (Base_Type (Typ)));
469 else
470 Utyp := Underlying_Type (Root_Type (Base_Type (Typ)));
472 if Is_Protected_Type (Utyp) then
473 Utyp := Corresponding_Record_Type (Utyp);
474 end if;
475 end if;
476 end if;
478 -- If the underlying_type is a subtype, we are dealing with the
479 -- completion of a private type. We need to access the base type and
480 -- generate a conversion to it.
482 if Utyp /= Base_Type (Utyp) then
483 pragma Assert (Is_Private_Type (Typ));
485 Utyp := Base_Type (Utyp);
486 end if;
488 -- When dealing with an internally built full view for a type with
489 -- unknown discriminants, use the original record type.
491 if Is_Underlying_Record_View (Utyp) then
492 Utyp := Etype (Utyp);
493 end if;
495 return TSS (Utyp, TSS_Finalize_Address);
496 end Find_Finalize_Address;
498 -----------------
499 -- Find_Object --
500 -----------------
502 function Find_Object (E : Node_Id) return Node_Id is
503 Expr : Node_Id;
505 begin
506 pragma Assert (Is_Allocate);
508 Expr := E;
509 loop
510 if Nkind_In (Expr, N_Qualified_Expression,
511 N_Unchecked_Type_Conversion)
512 then
513 Expr := Expression (Expr);
515 elsif Nkind (Expr) = N_Explicit_Dereference then
516 Expr := Prefix (Expr);
518 else
519 exit;
520 end if;
521 end loop;
523 return Expr;
524 end Find_Object;
526 ---------------------------------
527 -- Is_Allocate_Deallocate_Proc --
528 ---------------------------------
530 function Is_Allocate_Deallocate_Proc (Subp : Entity_Id) return Boolean is
531 begin
532 -- Look for a subprogram body with only one statement which is a
533 -- call to Allocate_Any_Controlled / Deallocate_Any_Controlled.
535 if Ekind (Subp) = E_Procedure
536 and then Nkind (Parent (Parent (Subp))) = N_Subprogram_Body
537 then
538 declare
539 HSS : constant Node_Id :=
540 Handled_Statement_Sequence (Parent (Parent (Subp)));
541 Proc : Entity_Id;
543 begin
544 if Present (Statements (HSS))
545 and then Nkind (First (Statements (HSS))) =
546 N_Procedure_Call_Statement
547 then
548 Proc := Entity (Name (First (Statements (HSS))));
550 return
551 Is_RTE (Proc, RE_Allocate_Any_Controlled)
552 or else Is_RTE (Proc, RE_Deallocate_Any_Controlled);
553 end if;
554 end;
555 end if;
557 return False;
558 end Is_Allocate_Deallocate_Proc;
560 -- Start of processing for Build_Allocate_Deallocate_Proc
562 begin
563 -- Do not perform this expansion in SPARK mode because it is not
564 -- necessary.
566 if SPARK_Mode then
567 return;
568 end if;
570 -- Obtain the attributes of the allocation / deallocation
572 if Nkind (N) = N_Free_Statement then
573 Expr := Expression (N);
574 Ptr_Typ := Base_Type (Etype (Expr));
575 Proc_To_Call := Procedure_To_Call (N);
577 else
578 if Nkind (N) = N_Object_Declaration then
579 Expr := Expression (N);
580 else
581 Expr := N;
582 end if;
584 -- In certain cases an allocator with a qualified expression may
585 -- be relocated and used as the initialization expression of a
586 -- temporary:
588 -- before:
589 -- Obj : Ptr_Typ := new Desig_Typ'(...);
591 -- after:
592 -- Tmp : Ptr_Typ := new Desig_Typ'(...);
593 -- Obj : Ptr_Typ := Tmp;
595 -- Since the allocator is always marked as analyzed to avoid infinite
596 -- expansion, it will never be processed by this routine given that
597 -- the designated type needs finalization actions. Detect this case
598 -- and complete the expansion of the allocator.
600 if Nkind (Expr) = N_Identifier
601 and then Nkind (Parent (Entity (Expr))) = N_Object_Declaration
602 and then Nkind (Expression (Parent (Entity (Expr)))) = N_Allocator
603 then
604 Build_Allocate_Deallocate_Proc (Parent (Entity (Expr)), True);
605 return;
606 end if;
608 -- The allocator may have been rewritten into something else in which
609 -- case the expansion performed by this routine does not apply.
611 if Nkind (Expr) /= N_Allocator then
612 return;
613 end if;
615 Ptr_Typ := Base_Type (Etype (Expr));
616 Proc_To_Call := Procedure_To_Call (Expr);
617 end if;
619 Pool_Id := Associated_Storage_Pool (Ptr_Typ);
620 Desig_Typ := Available_View (Designated_Type (Ptr_Typ));
622 -- Handle concurrent types
624 if Is_Concurrent_Type (Desig_Typ)
625 and then Present (Corresponding_Record_Type (Desig_Typ))
626 then
627 Desig_Typ := Corresponding_Record_Type (Desig_Typ);
628 end if;
630 -- Do not process allocations / deallocations without a pool
632 if No (Pool_Id) then
633 return;
635 -- Do not process allocations on / deallocations from the secondary
636 -- stack.
638 elsif Is_RTE (Pool_Id, RE_SS_Pool) then
639 return;
641 -- Do not replicate the machinery if the allocator / free has already
642 -- been expanded and has a custom Allocate / Deallocate.
644 elsif Present (Proc_To_Call)
645 and then Is_Allocate_Deallocate_Proc (Proc_To_Call)
646 then
647 return;
648 end if;
650 if Needs_Finalization (Desig_Typ) then
652 -- Certain run-time configurations and targets do not provide support
653 -- for controlled types.
655 if Restriction_Active (No_Finalization) then
656 return;
658 -- Do nothing if the access type may never allocate / deallocate
659 -- objects.
661 elsif No_Pool_Assigned (Ptr_Typ) then
662 return;
664 -- Access-to-controlled types are not supported on .NET/JVM since
665 -- these targets cannot support pools and address arithmetic.
667 elsif VM_Target /= No_VM then
668 return;
669 end if;
671 -- The allocation / deallocation of a controlled object must be
672 -- chained on / detached from a finalization master.
674 pragma Assert (Present (Finalization_Master (Ptr_Typ)));
676 -- The only other kind of allocation / deallocation supported by this
677 -- routine is on / from a subpool.
679 elsif Nkind (Expr) = N_Allocator
680 and then No (Subpool_Handle_Name (Expr))
681 then
682 return;
683 end if;
685 declare
686 Loc : constant Source_Ptr := Sloc (N);
687 Addr_Id : constant Entity_Id := Make_Temporary (Loc, 'A');
688 Alig_Id : constant Entity_Id := Make_Temporary (Loc, 'L');
689 Proc_Id : constant Entity_Id := Make_Temporary (Loc, 'P');
690 Size_Id : constant Entity_Id := Make_Temporary (Loc, 'S');
692 Actuals : List_Id;
693 Fin_Addr_Id : Entity_Id;
694 Fin_Mas_Act : Node_Id;
695 Fin_Mas_Id : Entity_Id;
696 Proc_To_Call : Entity_Id;
697 Subpool : Node_Id := Empty;
699 begin
700 -- Step 1: Construct all the actuals for the call to library routine
701 -- Allocate_Any_Controlled / Deallocate_Any_Controlled.
703 -- a) Storage pool
705 Actuals := New_List (New_Reference_To (Pool_Id, Loc));
707 if Is_Allocate then
709 -- b) Subpool
711 if Nkind (Expr) = N_Allocator then
712 Subpool := Subpool_Handle_Name (Expr);
713 end if;
715 -- If a subpool is present it can be an arbitrary name, so make
716 -- the actual by copying the tree.
718 if Present (Subpool) then
719 Append_To (Actuals, New_Copy_Tree (Subpool, New_Sloc => Loc));
720 else
721 Append_To (Actuals, Make_Null (Loc));
722 end if;
724 -- c) Finalization master
726 if Needs_Finalization (Desig_Typ) then
727 Fin_Mas_Id := Finalization_Master (Ptr_Typ);
728 Fin_Mas_Act := New_Reference_To (Fin_Mas_Id, Loc);
730 -- Handle the case where the master is actually a pointer to a
731 -- master. This case arises in build-in-place functions.
733 if Is_Access_Type (Etype (Fin_Mas_Id)) then
734 Append_To (Actuals, Fin_Mas_Act);
735 else
736 Append_To (Actuals,
737 Make_Attribute_Reference (Loc,
738 Prefix => Fin_Mas_Act,
739 Attribute_Name => Name_Unrestricted_Access));
740 end if;
741 else
742 Append_To (Actuals, Make_Null (Loc));
743 end if;
745 -- d) Finalize_Address
747 -- Primitive Finalize_Address is never generated in CodePeer mode
748 -- since it contains an Unchecked_Conversion.
750 if Needs_Finalization (Desig_Typ) and then not CodePeer_Mode then
751 Fin_Addr_Id := Find_Finalize_Address (Desig_Typ);
752 pragma Assert (Present (Fin_Addr_Id));
754 Append_To (Actuals,
755 Make_Attribute_Reference (Loc,
756 Prefix => New_Reference_To (Fin_Addr_Id, Loc),
757 Attribute_Name => Name_Unrestricted_Access));
758 else
759 Append_To (Actuals, Make_Null (Loc));
760 end if;
761 end if;
763 -- e) Address
764 -- f) Storage_Size
765 -- g) Alignment
767 Append_To (Actuals, New_Reference_To (Addr_Id, Loc));
768 Append_To (Actuals, New_Reference_To (Size_Id, Loc));
770 if Is_Allocate or else not Is_Class_Wide_Type (Desig_Typ) then
771 Append_To (Actuals, New_Reference_To (Alig_Id, Loc));
773 -- For deallocation of class wide types we obtain the value of
774 -- alignment from the Type Specific Record of the deallocated object.
775 -- This is needed because the frontend expansion of class-wide types
776 -- into equivalent types confuses the backend.
778 else
779 -- Generate:
780 -- Obj.all'Alignment
782 -- ... because 'Alignment applied to class-wide types is expanded
783 -- into the code that reads the value of alignment from the TSD
784 -- (see Expand_N_Attribute_Reference)
786 Append_To (Actuals,
787 Unchecked_Convert_To (RTE (RE_Storage_Offset),
788 Make_Attribute_Reference (Loc,
789 Prefix =>
790 Make_Explicit_Dereference (Loc, Relocate_Node (Expr)),
791 Attribute_Name => Name_Alignment)));
792 end if;
794 -- h) Is_Controlled
796 -- Generate a run-time check to determine whether a class-wide object
797 -- is truly controlled.
799 if Needs_Finalization (Desig_Typ) then
800 if Is_Class_Wide_Type (Desig_Typ)
801 or else Is_Generic_Actual_Type (Desig_Typ)
802 then
803 declare
804 Flag_Id : constant Entity_Id := Make_Temporary (Loc, 'F');
805 Flag_Expr : Node_Id;
806 Param : Node_Id;
807 Temp : Node_Id;
809 begin
810 if Is_Allocate then
811 Temp := Find_Object (Expression (Expr));
812 else
813 Temp := Expr;
814 end if;
816 -- Processing for generic actuals
818 if Is_Generic_Actual_Type (Desig_Typ) then
819 Flag_Expr :=
820 New_Reference_To (Boolean_Literals
821 (Needs_Finalization (Base_Type (Desig_Typ))), Loc);
823 -- Processing for subtype indications
825 elsif Nkind (Temp) in N_Has_Entity
826 and then Is_Type (Entity (Temp))
827 then
828 Flag_Expr :=
829 New_Reference_To (Boolean_Literals
830 (Needs_Finalization (Entity (Temp))), Loc);
832 -- Generate a runtime check to test the controlled state of
833 -- an object for the purposes of allocation / deallocation.
835 else
836 -- The following case arises when allocating through an
837 -- interface class-wide type, generate:
839 -- Temp.all
841 if Is_RTE (Etype (Temp), RE_Tag_Ptr) then
842 Param :=
843 Make_Explicit_Dereference (Loc,
844 Prefix =>
845 Relocate_Node (Temp));
847 -- Generate:
848 -- Temp'Tag
850 else
851 Param :=
852 Make_Attribute_Reference (Loc,
853 Prefix =>
854 Relocate_Node (Temp),
855 Attribute_Name => Name_Tag);
856 end if;
858 -- Generate:
859 -- Needs_Finalization (<Param>)
861 Flag_Expr :=
862 Make_Function_Call (Loc,
863 Name =>
864 New_Reference_To (RTE (RE_Needs_Finalization), Loc),
865 Parameter_Associations => New_List (Param));
866 end if;
868 -- Create the temporary which represents the finalization
869 -- state of the expression. Generate:
871 -- F : constant Boolean := <Flag_Expr>;
873 Insert_Action (N,
874 Make_Object_Declaration (Loc,
875 Defining_Identifier => Flag_Id,
876 Constant_Present => True,
877 Object_Definition =>
878 New_Reference_To (Standard_Boolean, Loc),
879 Expression => Flag_Expr));
881 -- The flag acts as the last actual
883 Append_To (Actuals, New_Reference_To (Flag_Id, Loc));
884 end;
886 -- The object is statically known to be controlled
888 else
889 Append_To (Actuals, New_Reference_To (Standard_True, Loc));
890 end if;
892 else
893 Append_To (Actuals, New_Reference_To (Standard_False, Loc));
894 end if;
896 -- i) On_Subpool
898 if Is_Allocate then
899 Append_To (Actuals,
900 New_Reference_To (Boolean_Literals (Present (Subpool)), Loc));
901 end if;
903 -- Step 2: Build a wrapper Allocate / Deallocate which internally
904 -- calls Allocate_Any_Controlled / Deallocate_Any_Controlled.
906 -- Select the proper routine to call
908 if Is_Allocate then
909 Proc_To_Call := RTE (RE_Allocate_Any_Controlled);
910 else
911 Proc_To_Call := RTE (RE_Deallocate_Any_Controlled);
912 end if;
914 -- Create a custom Allocate / Deallocate routine which has identical
915 -- profile to that of System.Storage_Pools.
917 Insert_Action (N,
918 Make_Subprogram_Body (Loc,
919 Specification =>
921 -- procedure Pnn
923 Make_Procedure_Specification (Loc,
924 Defining_Unit_Name => Proc_Id,
925 Parameter_Specifications => New_List (
927 -- P : Root_Storage_Pool
929 Make_Parameter_Specification (Loc,
930 Defining_Identifier => Make_Temporary (Loc, 'P'),
931 Parameter_Type =>
932 New_Reference_To (RTE (RE_Root_Storage_Pool), Loc)),
934 -- A : [out] Address
936 Make_Parameter_Specification (Loc,
937 Defining_Identifier => Addr_Id,
938 Out_Present => Is_Allocate,
939 Parameter_Type =>
940 New_Reference_To (RTE (RE_Address), Loc)),
942 -- S : Storage_Count
944 Make_Parameter_Specification (Loc,
945 Defining_Identifier => Size_Id,
946 Parameter_Type =>
947 New_Reference_To (RTE (RE_Storage_Count), Loc)),
949 -- L : Storage_Count
951 Make_Parameter_Specification (Loc,
952 Defining_Identifier => Alig_Id,
953 Parameter_Type =>
954 New_Reference_To (RTE (RE_Storage_Count), Loc)))),
956 Declarations => No_List,
958 Handled_Statement_Sequence =>
959 Make_Handled_Sequence_Of_Statements (Loc,
960 Statements => New_List (
961 Make_Procedure_Call_Statement (Loc,
962 Name => New_Reference_To (Proc_To_Call, Loc),
963 Parameter_Associations => Actuals)))));
965 -- The newly generated Allocate / Deallocate becomes the default
966 -- procedure to call when the back end processes the allocation /
967 -- deallocation.
969 if Is_Allocate then
970 Set_Procedure_To_Call (Expr, Proc_Id);
971 else
972 Set_Procedure_To_Call (N, Proc_Id);
973 end if;
974 end;
975 end Build_Allocate_Deallocate_Proc;
977 ------------------------
978 -- Build_Runtime_Call --
979 ------------------------
981 function Build_Runtime_Call (Loc : Source_Ptr; RE : RE_Id) return Node_Id is
982 begin
983 -- If entity is not available, we can skip making the call (this avoids
984 -- junk duplicated error messages in a number of cases).
986 if not RTE_Available (RE) then
987 return Make_Null_Statement (Loc);
988 else
989 return
990 Make_Procedure_Call_Statement (Loc,
991 Name => New_Reference_To (RTE (RE), Loc));
992 end if;
993 end Build_Runtime_Call;
995 ----------------------------
996 -- Build_Task_Array_Image --
997 ----------------------------
999 -- This function generates the body for a function that constructs the
1000 -- image string for a task that is an array component. The function is
1001 -- local to the init proc for the array type, and is called for each one
1002 -- of the components. The constructed image has the form of an indexed
1003 -- component, whose prefix is the outer variable of the array type.
1004 -- The n-dimensional array type has known indexes Index, Index2...
1006 -- Id_Ref is an indexed component form created by the enclosing init proc.
1007 -- Its successive indexes are Val1, Val2, ... which are the loop variables
1008 -- in the loops that call the individual task init proc on each component.
1010 -- The generated function has the following structure:
1012 -- function F return String is
1013 -- Pref : string renames Task_Name;
1014 -- T1 : String := Index1'Image (Val1);
1015 -- ...
1016 -- Tn : String := indexn'image (Valn);
1017 -- Len : Integer := T1'Length + ... + Tn'Length + n + 1;
1018 -- -- Len includes commas and the end parentheses.
1019 -- Res : String (1..Len);
1020 -- Pos : Integer := Pref'Length;
1022 -- begin
1023 -- Res (1 .. Pos) := Pref;
1024 -- Pos := Pos + 1;
1025 -- Res (Pos) := '(';
1026 -- Pos := Pos + 1;
1027 -- Res (Pos .. Pos + T1'Length - 1) := T1;
1028 -- Pos := Pos + T1'Length;
1029 -- Res (Pos) := '.';
1030 -- Pos := Pos + 1;
1031 -- ...
1032 -- Res (Pos .. Pos + Tn'Length - 1) := Tn;
1033 -- Res (Len) := ')';
1035 -- return Res;
1036 -- end F;
1038 -- Needless to say, multidimensional arrays of tasks are rare enough that
1039 -- the bulkiness of this code is not really a concern.
1041 function Build_Task_Array_Image
1042 (Loc : Source_Ptr;
1043 Id_Ref : Node_Id;
1044 A_Type : Entity_Id;
1045 Dyn : Boolean := False) return Node_Id
1047 Dims : constant Nat := Number_Dimensions (A_Type);
1048 -- Number of dimensions for array of tasks
1050 Temps : array (1 .. Dims) of Entity_Id;
1051 -- Array of temporaries to hold string for each index
1053 Indx : Node_Id;
1054 -- Index expression
1056 Len : Entity_Id;
1057 -- Total length of generated name
1059 Pos : Entity_Id;
1060 -- Running index for substring assignments
1062 Pref : constant Entity_Id := Make_Temporary (Loc, 'P');
1063 -- Name of enclosing variable, prefix of resulting name
1065 Res : Entity_Id;
1066 -- String to hold result
1068 Val : Node_Id;
1069 -- Value of successive indexes
1071 Sum : Node_Id;
1072 -- Expression to compute total size of string
1074 T : Entity_Id;
1075 -- Entity for name at one index position
1077 Decls : constant List_Id := New_List;
1078 Stats : constant List_Id := New_List;
1080 begin
1081 -- For a dynamic task, the name comes from the target variable. For a
1082 -- static one it is a formal of the enclosing init proc.
1084 if Dyn then
1085 Get_Name_String (Chars (Entity (Prefix (Id_Ref))));
1086 Append_To (Decls,
1087 Make_Object_Declaration (Loc,
1088 Defining_Identifier => Pref,
1089 Object_Definition => New_Occurrence_Of (Standard_String, Loc),
1090 Expression =>
1091 Make_String_Literal (Loc,
1092 Strval => String_From_Name_Buffer)));
1094 else
1095 Append_To (Decls,
1096 Make_Object_Renaming_Declaration (Loc,
1097 Defining_Identifier => Pref,
1098 Subtype_Mark => New_Occurrence_Of (Standard_String, Loc),
1099 Name => Make_Identifier (Loc, Name_uTask_Name)));
1100 end if;
1102 Indx := First_Index (A_Type);
1103 Val := First (Expressions (Id_Ref));
1105 for J in 1 .. Dims loop
1106 T := Make_Temporary (Loc, 'T');
1107 Temps (J) := T;
1109 Append_To (Decls,
1110 Make_Object_Declaration (Loc,
1111 Defining_Identifier => T,
1112 Object_Definition => New_Occurrence_Of (Standard_String, Loc),
1113 Expression =>
1114 Make_Attribute_Reference (Loc,
1115 Attribute_Name => Name_Image,
1116 Prefix => New_Occurrence_Of (Etype (Indx), Loc),
1117 Expressions => New_List (New_Copy_Tree (Val)))));
1119 Next_Index (Indx);
1120 Next (Val);
1121 end loop;
1123 Sum := Make_Integer_Literal (Loc, Dims + 1);
1125 Sum :=
1126 Make_Op_Add (Loc,
1127 Left_Opnd => Sum,
1128 Right_Opnd =>
1129 Make_Attribute_Reference (Loc,
1130 Attribute_Name => Name_Length,
1131 Prefix => New_Occurrence_Of (Pref, Loc),
1132 Expressions => New_List (Make_Integer_Literal (Loc, 1))));
1134 for J in 1 .. Dims loop
1135 Sum :=
1136 Make_Op_Add (Loc,
1137 Left_Opnd => Sum,
1138 Right_Opnd =>
1139 Make_Attribute_Reference (Loc,
1140 Attribute_Name => Name_Length,
1141 Prefix =>
1142 New_Occurrence_Of (Temps (J), Loc),
1143 Expressions => New_List (Make_Integer_Literal (Loc, 1))));
1144 end loop;
1146 Build_Task_Image_Prefix (Loc, Len, Res, Pos, Pref, Sum, Decls, Stats);
1148 Set_Character_Literal_Name (Char_Code (Character'Pos ('(')));
1150 Append_To (Stats,
1151 Make_Assignment_Statement (Loc,
1152 Name =>
1153 Make_Indexed_Component (Loc,
1154 Prefix => New_Occurrence_Of (Res, Loc),
1155 Expressions => New_List (New_Occurrence_Of (Pos, Loc))),
1156 Expression =>
1157 Make_Character_Literal (Loc,
1158 Chars => Name_Find,
1159 Char_Literal_Value => UI_From_Int (Character'Pos ('(')))));
1161 Append_To (Stats,
1162 Make_Assignment_Statement (Loc,
1163 Name => New_Occurrence_Of (Pos, Loc),
1164 Expression =>
1165 Make_Op_Add (Loc,
1166 Left_Opnd => New_Occurrence_Of (Pos, Loc),
1167 Right_Opnd => Make_Integer_Literal (Loc, 1))));
1169 for J in 1 .. Dims loop
1171 Append_To (Stats,
1172 Make_Assignment_Statement (Loc,
1173 Name =>
1174 Make_Slice (Loc,
1175 Prefix => New_Occurrence_Of (Res, Loc),
1176 Discrete_Range =>
1177 Make_Range (Loc,
1178 Low_Bound => New_Occurrence_Of (Pos, Loc),
1179 High_Bound =>
1180 Make_Op_Subtract (Loc,
1181 Left_Opnd =>
1182 Make_Op_Add (Loc,
1183 Left_Opnd => New_Occurrence_Of (Pos, Loc),
1184 Right_Opnd =>
1185 Make_Attribute_Reference (Loc,
1186 Attribute_Name => Name_Length,
1187 Prefix =>
1188 New_Occurrence_Of (Temps (J), Loc),
1189 Expressions =>
1190 New_List (Make_Integer_Literal (Loc, 1)))),
1191 Right_Opnd => Make_Integer_Literal (Loc, 1)))),
1193 Expression => New_Occurrence_Of (Temps (J), Loc)));
1195 if J < Dims then
1196 Append_To (Stats,
1197 Make_Assignment_Statement (Loc,
1198 Name => New_Occurrence_Of (Pos, Loc),
1199 Expression =>
1200 Make_Op_Add (Loc,
1201 Left_Opnd => New_Occurrence_Of (Pos, Loc),
1202 Right_Opnd =>
1203 Make_Attribute_Reference (Loc,
1204 Attribute_Name => Name_Length,
1205 Prefix => New_Occurrence_Of (Temps (J), Loc),
1206 Expressions =>
1207 New_List (Make_Integer_Literal (Loc, 1))))));
1209 Set_Character_Literal_Name (Char_Code (Character'Pos (',')));
1211 Append_To (Stats,
1212 Make_Assignment_Statement (Loc,
1213 Name => Make_Indexed_Component (Loc,
1214 Prefix => New_Occurrence_Of (Res, Loc),
1215 Expressions => New_List (New_Occurrence_Of (Pos, Loc))),
1216 Expression =>
1217 Make_Character_Literal (Loc,
1218 Chars => Name_Find,
1219 Char_Literal_Value => UI_From_Int (Character'Pos (',')))));
1221 Append_To (Stats,
1222 Make_Assignment_Statement (Loc,
1223 Name => New_Occurrence_Of (Pos, Loc),
1224 Expression =>
1225 Make_Op_Add (Loc,
1226 Left_Opnd => New_Occurrence_Of (Pos, Loc),
1227 Right_Opnd => Make_Integer_Literal (Loc, 1))));
1228 end if;
1229 end loop;
1231 Set_Character_Literal_Name (Char_Code (Character'Pos (')')));
1233 Append_To (Stats,
1234 Make_Assignment_Statement (Loc,
1235 Name =>
1236 Make_Indexed_Component (Loc,
1237 Prefix => New_Occurrence_Of (Res, Loc),
1238 Expressions => New_List (New_Occurrence_Of (Len, Loc))),
1239 Expression =>
1240 Make_Character_Literal (Loc,
1241 Chars => Name_Find,
1242 Char_Literal_Value => UI_From_Int (Character'Pos (')')))));
1243 return Build_Task_Image_Function (Loc, Decls, Stats, Res);
1244 end Build_Task_Array_Image;
1246 ----------------------------
1247 -- Build_Task_Image_Decls --
1248 ----------------------------
1250 function Build_Task_Image_Decls
1251 (Loc : Source_Ptr;
1252 Id_Ref : Node_Id;
1253 A_Type : Entity_Id;
1254 In_Init_Proc : Boolean := False) return List_Id
1256 Decls : constant List_Id := New_List;
1257 T_Id : Entity_Id := Empty;
1258 Decl : Node_Id;
1259 Expr : Node_Id := Empty;
1260 Fun : Node_Id := Empty;
1261 Is_Dyn : constant Boolean :=
1262 Nkind (Parent (Id_Ref)) = N_Assignment_Statement
1263 and then
1264 Nkind (Expression (Parent (Id_Ref))) = N_Allocator;
1266 begin
1267 -- If Discard_Names or No_Implicit_Heap_Allocations are in effect,
1268 -- generate a dummy declaration only.
1270 if Restriction_Active (No_Implicit_Heap_Allocations)
1271 or else Global_Discard_Names
1272 then
1273 T_Id := Make_Temporary (Loc, 'J');
1274 Name_Len := 0;
1276 return
1277 New_List (
1278 Make_Object_Declaration (Loc,
1279 Defining_Identifier => T_Id,
1280 Object_Definition => New_Occurrence_Of (Standard_String, Loc),
1281 Expression =>
1282 Make_String_Literal (Loc,
1283 Strval => String_From_Name_Buffer)));
1285 else
1286 if Nkind (Id_Ref) = N_Identifier
1287 or else Nkind (Id_Ref) = N_Defining_Identifier
1288 then
1289 -- For a simple variable, the image of the task is built from
1290 -- the name of the variable. To avoid possible conflict with the
1291 -- anonymous type created for a single protected object, add a
1292 -- numeric suffix.
1294 T_Id :=
1295 Make_Defining_Identifier (Loc,
1296 New_External_Name (Chars (Id_Ref), 'T', 1));
1298 Get_Name_String (Chars (Id_Ref));
1300 Expr :=
1301 Make_String_Literal (Loc,
1302 Strval => String_From_Name_Buffer);
1304 elsif Nkind (Id_Ref) = N_Selected_Component then
1305 T_Id :=
1306 Make_Defining_Identifier (Loc,
1307 New_External_Name (Chars (Selector_Name (Id_Ref)), 'T'));
1308 Fun := Build_Task_Record_Image (Loc, Id_Ref, Is_Dyn);
1310 elsif Nkind (Id_Ref) = N_Indexed_Component then
1311 T_Id :=
1312 Make_Defining_Identifier (Loc,
1313 New_External_Name (Chars (A_Type), 'N'));
1315 Fun := Build_Task_Array_Image (Loc, Id_Ref, A_Type, Is_Dyn);
1316 end if;
1317 end if;
1319 if Present (Fun) then
1320 Append (Fun, Decls);
1321 Expr := Make_Function_Call (Loc,
1322 Name => New_Occurrence_Of (Defining_Entity (Fun), Loc));
1324 if not In_Init_Proc and then VM_Target = No_VM then
1325 Set_Uses_Sec_Stack (Defining_Entity (Fun));
1326 end if;
1327 end if;
1329 Decl := Make_Object_Declaration (Loc,
1330 Defining_Identifier => T_Id,
1331 Object_Definition => New_Occurrence_Of (Standard_String, Loc),
1332 Constant_Present => True,
1333 Expression => Expr);
1335 Append (Decl, Decls);
1336 return Decls;
1337 end Build_Task_Image_Decls;
1339 -------------------------------
1340 -- Build_Task_Image_Function --
1341 -------------------------------
1343 function Build_Task_Image_Function
1344 (Loc : Source_Ptr;
1345 Decls : List_Id;
1346 Stats : List_Id;
1347 Res : Entity_Id) return Node_Id
1349 Spec : Node_Id;
1351 begin
1352 Append_To (Stats,
1353 Make_Simple_Return_Statement (Loc,
1354 Expression => New_Occurrence_Of (Res, Loc)));
1356 Spec := Make_Function_Specification (Loc,
1357 Defining_Unit_Name => Make_Temporary (Loc, 'F'),
1358 Result_Definition => New_Occurrence_Of (Standard_String, Loc));
1360 -- Calls to 'Image use the secondary stack, which must be cleaned up
1361 -- after the task name is built.
1363 return Make_Subprogram_Body (Loc,
1364 Specification => Spec,
1365 Declarations => Decls,
1366 Handled_Statement_Sequence =>
1367 Make_Handled_Sequence_Of_Statements (Loc, Statements => Stats));
1368 end Build_Task_Image_Function;
1370 -----------------------------
1371 -- Build_Task_Image_Prefix --
1372 -----------------------------
1374 procedure Build_Task_Image_Prefix
1375 (Loc : Source_Ptr;
1376 Len : out Entity_Id;
1377 Res : out Entity_Id;
1378 Pos : out Entity_Id;
1379 Prefix : Entity_Id;
1380 Sum : Node_Id;
1381 Decls : List_Id;
1382 Stats : List_Id)
1384 begin
1385 Len := Make_Temporary (Loc, 'L', Sum);
1387 Append_To (Decls,
1388 Make_Object_Declaration (Loc,
1389 Defining_Identifier => Len,
1390 Object_Definition => New_Occurrence_Of (Standard_Integer, Loc),
1391 Expression => Sum));
1393 Res := Make_Temporary (Loc, 'R');
1395 Append_To (Decls,
1396 Make_Object_Declaration (Loc,
1397 Defining_Identifier => Res,
1398 Object_Definition =>
1399 Make_Subtype_Indication (Loc,
1400 Subtype_Mark => New_Occurrence_Of (Standard_String, Loc),
1401 Constraint =>
1402 Make_Index_Or_Discriminant_Constraint (Loc,
1403 Constraints =>
1404 New_List (
1405 Make_Range (Loc,
1406 Low_Bound => Make_Integer_Literal (Loc, 1),
1407 High_Bound => New_Occurrence_Of (Len, Loc)))))));
1409 Pos := Make_Temporary (Loc, 'P');
1411 Append_To (Decls,
1412 Make_Object_Declaration (Loc,
1413 Defining_Identifier => Pos,
1414 Object_Definition => New_Occurrence_Of (Standard_Integer, Loc)));
1416 -- Pos := Prefix'Length;
1418 Append_To (Stats,
1419 Make_Assignment_Statement (Loc,
1420 Name => New_Occurrence_Of (Pos, Loc),
1421 Expression =>
1422 Make_Attribute_Reference (Loc,
1423 Attribute_Name => Name_Length,
1424 Prefix => New_Occurrence_Of (Prefix, Loc),
1425 Expressions => New_List (Make_Integer_Literal (Loc, 1)))));
1427 -- Res (1 .. Pos) := Prefix;
1429 Append_To (Stats,
1430 Make_Assignment_Statement (Loc,
1431 Name =>
1432 Make_Slice (Loc,
1433 Prefix => New_Occurrence_Of (Res, Loc),
1434 Discrete_Range =>
1435 Make_Range (Loc,
1436 Low_Bound => Make_Integer_Literal (Loc, 1),
1437 High_Bound => New_Occurrence_Of (Pos, Loc))),
1439 Expression => New_Occurrence_Of (Prefix, Loc)));
1441 Append_To (Stats,
1442 Make_Assignment_Statement (Loc,
1443 Name => New_Occurrence_Of (Pos, Loc),
1444 Expression =>
1445 Make_Op_Add (Loc,
1446 Left_Opnd => New_Occurrence_Of (Pos, Loc),
1447 Right_Opnd => Make_Integer_Literal (Loc, 1))));
1448 end Build_Task_Image_Prefix;
1450 -----------------------------
1451 -- Build_Task_Record_Image --
1452 -----------------------------
1454 function Build_Task_Record_Image
1455 (Loc : Source_Ptr;
1456 Id_Ref : Node_Id;
1457 Dyn : Boolean := False) return Node_Id
1459 Len : Entity_Id;
1460 -- Total length of generated name
1462 Pos : Entity_Id;
1463 -- Index into result
1465 Res : Entity_Id;
1466 -- String to hold result
1468 Pref : constant Entity_Id := Make_Temporary (Loc, 'P');
1469 -- Name of enclosing variable, prefix of resulting name
1471 Sum : Node_Id;
1472 -- Expression to compute total size of string
1474 Sel : Entity_Id;
1475 -- Entity for selector name
1477 Decls : constant List_Id := New_List;
1478 Stats : constant List_Id := New_List;
1480 begin
1481 -- For a dynamic task, the name comes from the target variable. For a
1482 -- static one it is a formal of the enclosing init proc.
1484 if Dyn then
1485 Get_Name_String (Chars (Entity (Prefix (Id_Ref))));
1486 Append_To (Decls,
1487 Make_Object_Declaration (Loc,
1488 Defining_Identifier => Pref,
1489 Object_Definition => New_Occurrence_Of (Standard_String, Loc),
1490 Expression =>
1491 Make_String_Literal (Loc,
1492 Strval => String_From_Name_Buffer)));
1494 else
1495 Append_To (Decls,
1496 Make_Object_Renaming_Declaration (Loc,
1497 Defining_Identifier => Pref,
1498 Subtype_Mark => New_Occurrence_Of (Standard_String, Loc),
1499 Name => Make_Identifier (Loc, Name_uTask_Name)));
1500 end if;
1502 Sel := Make_Temporary (Loc, 'S');
1504 Get_Name_String (Chars (Selector_Name (Id_Ref)));
1506 Append_To (Decls,
1507 Make_Object_Declaration (Loc,
1508 Defining_Identifier => Sel,
1509 Object_Definition => New_Occurrence_Of (Standard_String, Loc),
1510 Expression =>
1511 Make_String_Literal (Loc,
1512 Strval => String_From_Name_Buffer)));
1514 Sum := Make_Integer_Literal (Loc, Nat (Name_Len + 1));
1516 Sum :=
1517 Make_Op_Add (Loc,
1518 Left_Opnd => Sum,
1519 Right_Opnd =>
1520 Make_Attribute_Reference (Loc,
1521 Attribute_Name => Name_Length,
1522 Prefix =>
1523 New_Occurrence_Of (Pref, Loc),
1524 Expressions => New_List (Make_Integer_Literal (Loc, 1))));
1526 Build_Task_Image_Prefix (Loc, Len, Res, Pos, Pref, Sum, Decls, Stats);
1528 Set_Character_Literal_Name (Char_Code (Character'Pos ('.')));
1530 -- Res (Pos) := '.';
1532 Append_To (Stats,
1533 Make_Assignment_Statement (Loc,
1534 Name => Make_Indexed_Component (Loc,
1535 Prefix => New_Occurrence_Of (Res, Loc),
1536 Expressions => New_List (New_Occurrence_Of (Pos, Loc))),
1537 Expression =>
1538 Make_Character_Literal (Loc,
1539 Chars => Name_Find,
1540 Char_Literal_Value =>
1541 UI_From_Int (Character'Pos ('.')))));
1543 Append_To (Stats,
1544 Make_Assignment_Statement (Loc,
1545 Name => New_Occurrence_Of (Pos, Loc),
1546 Expression =>
1547 Make_Op_Add (Loc,
1548 Left_Opnd => New_Occurrence_Of (Pos, Loc),
1549 Right_Opnd => Make_Integer_Literal (Loc, 1))));
1551 -- Res (Pos .. Len) := Selector;
1553 Append_To (Stats,
1554 Make_Assignment_Statement (Loc,
1555 Name => Make_Slice (Loc,
1556 Prefix => New_Occurrence_Of (Res, Loc),
1557 Discrete_Range =>
1558 Make_Range (Loc,
1559 Low_Bound => New_Occurrence_Of (Pos, Loc),
1560 High_Bound => New_Occurrence_Of (Len, Loc))),
1561 Expression => New_Occurrence_Of (Sel, Loc)));
1563 return Build_Task_Image_Function (Loc, Decls, Stats, Res);
1564 end Build_Task_Record_Image;
1566 ----------------------------------
1567 -- Component_May_Be_Bit_Aligned --
1568 ----------------------------------
1570 function Component_May_Be_Bit_Aligned (Comp : Entity_Id) return Boolean is
1571 UT : Entity_Id;
1573 begin
1574 -- If no component clause, then everything is fine, since the back end
1575 -- never bit-misaligns by default, even if there is a pragma Packed for
1576 -- the record.
1578 if No (Comp) or else No (Component_Clause (Comp)) then
1579 return False;
1580 end if;
1582 UT := Underlying_Type (Etype (Comp));
1584 -- It is only array and record types that cause trouble
1586 if not Is_Record_Type (UT) and then not Is_Array_Type (UT) then
1587 return False;
1589 -- If we know that we have a small (64 bits or less) record or small
1590 -- bit-packed array, then everything is fine, since the back end can
1591 -- handle these cases correctly.
1593 elsif Esize (Comp) <= 64
1594 and then (Is_Record_Type (UT) or else Is_Bit_Packed_Array (UT))
1595 then
1596 return False;
1598 -- Otherwise if the component is not byte aligned, we know we have the
1599 -- nasty unaligned case.
1601 elsif Normalized_First_Bit (Comp) /= Uint_0
1602 or else Esize (Comp) mod System_Storage_Unit /= Uint_0
1603 then
1604 return True;
1606 -- If we are large and byte aligned, then OK at this level
1608 else
1609 return False;
1610 end if;
1611 end Component_May_Be_Bit_Aligned;
1613 -----------------------------------
1614 -- Corresponding_Runtime_Package --
1615 -----------------------------------
1617 function Corresponding_Runtime_Package (Typ : Entity_Id) return RTU_Id is
1618 Pkg_Id : RTU_Id := RTU_Null;
1620 begin
1621 pragma Assert (Is_Concurrent_Type (Typ));
1623 if Ekind (Typ) in Protected_Kind then
1624 if Has_Entries (Typ)
1626 -- A protected type without entries that covers an interface and
1627 -- overrides the abstract routines with protected procedures is
1628 -- considered equivalent to a protected type with entries in the
1629 -- context of dispatching select statements. It is sufficient to
1630 -- check for the presence of an interface list in the declaration
1631 -- node to recognize this case.
1633 or else Present (Interface_List (Parent (Typ)))
1634 or else
1635 (((Has_Attach_Handler (Typ) and then not Restricted_Profile)
1636 or else Has_Interrupt_Handler (Typ))
1637 and then not Restriction_Active (No_Dynamic_Attachment))
1638 then
1639 if Abort_Allowed
1640 or else Restriction_Active (No_Entry_Queue) = False
1641 or else Number_Entries (Typ) > 1
1642 or else (Has_Attach_Handler (Typ)
1643 and then not Restricted_Profile)
1644 then
1645 Pkg_Id := System_Tasking_Protected_Objects_Entries;
1646 else
1647 Pkg_Id := System_Tasking_Protected_Objects_Single_Entry;
1648 end if;
1650 else
1651 Pkg_Id := System_Tasking_Protected_Objects;
1652 end if;
1653 end if;
1655 return Pkg_Id;
1656 end Corresponding_Runtime_Package;
1658 -------------------------------
1659 -- Convert_To_Actual_Subtype --
1660 -------------------------------
1662 procedure Convert_To_Actual_Subtype (Exp : Entity_Id) is
1663 Act_ST : Entity_Id;
1665 begin
1666 Act_ST := Get_Actual_Subtype (Exp);
1668 if Act_ST = Etype (Exp) then
1669 return;
1670 else
1671 Rewrite (Exp, Convert_To (Act_ST, Relocate_Node (Exp)));
1672 Analyze_And_Resolve (Exp, Act_ST);
1673 end if;
1674 end Convert_To_Actual_Subtype;
1676 -----------------------------------
1677 -- Current_Sem_Unit_Declarations --
1678 -----------------------------------
1680 function Current_Sem_Unit_Declarations return List_Id is
1681 U : Node_Id := Unit (Cunit (Current_Sem_Unit));
1682 Decls : List_Id;
1684 begin
1685 -- If the current unit is a package body, locate the visible
1686 -- declarations of the package spec.
1688 if Nkind (U) = N_Package_Body then
1689 U := Unit (Library_Unit (Cunit (Current_Sem_Unit)));
1690 end if;
1692 if Nkind (U) = N_Package_Declaration then
1693 U := Specification (U);
1694 Decls := Visible_Declarations (U);
1696 if No (Decls) then
1697 Decls := New_List;
1698 Set_Visible_Declarations (U, Decls);
1699 end if;
1701 else
1702 Decls := Declarations (U);
1704 if No (Decls) then
1705 Decls := New_List;
1706 Set_Declarations (U, Decls);
1707 end if;
1708 end if;
1710 return Decls;
1711 end Current_Sem_Unit_Declarations;
1713 -----------------------
1714 -- Duplicate_Subexpr --
1715 -----------------------
1717 function Duplicate_Subexpr
1718 (Exp : Node_Id;
1719 Name_Req : Boolean := False) return Node_Id
1721 begin
1722 Remove_Side_Effects (Exp, Name_Req);
1723 return New_Copy_Tree (Exp);
1724 end Duplicate_Subexpr;
1726 ---------------------------------
1727 -- Duplicate_Subexpr_No_Checks --
1728 ---------------------------------
1730 function Duplicate_Subexpr_No_Checks
1731 (Exp : Node_Id;
1732 Name_Req : Boolean := False) return Node_Id
1734 New_Exp : Node_Id;
1735 begin
1736 Remove_Side_Effects (Exp, Name_Req);
1737 New_Exp := New_Copy_Tree (Exp);
1738 Remove_Checks (New_Exp);
1739 return New_Exp;
1740 end Duplicate_Subexpr_No_Checks;
1742 -----------------------------------
1743 -- Duplicate_Subexpr_Move_Checks --
1744 -----------------------------------
1746 function Duplicate_Subexpr_Move_Checks
1747 (Exp : Node_Id;
1748 Name_Req : Boolean := False) return Node_Id
1750 New_Exp : Node_Id;
1751 begin
1752 Remove_Side_Effects (Exp, Name_Req);
1753 New_Exp := New_Copy_Tree (Exp);
1754 Remove_Checks (Exp);
1755 return New_Exp;
1756 end Duplicate_Subexpr_Move_Checks;
1758 --------------------
1759 -- Ensure_Defined --
1760 --------------------
1762 procedure Ensure_Defined (Typ : Entity_Id; N : Node_Id) is
1763 IR : Node_Id;
1765 begin
1766 -- An itype reference must only be created if this is a local itype, so
1767 -- that gigi can elaborate it on the proper objstack.
1769 if Is_Itype (Typ) and then Scope (Typ) = Current_Scope then
1770 IR := Make_Itype_Reference (Sloc (N));
1771 Set_Itype (IR, Typ);
1772 Insert_Action (N, IR);
1773 end if;
1774 end Ensure_Defined;
1776 ---------------
1777 -- Entity_Of --
1778 ---------------
1780 function Entity_Of (N : Node_Id) return Entity_Id is
1781 Id : Entity_Id;
1783 begin
1784 Id := Empty;
1786 if Is_Entity_Name (N) then
1787 Id := Entity (N);
1789 -- Follow a possible chain of renamings to reach the root renamed
1790 -- object.
1792 while Present (Renamed_Object (Id)) loop
1793 if Is_Entity_Name (Renamed_Object (Id)) then
1794 Id := Entity (Renamed_Object (Id));
1795 else
1796 Id := Empty;
1797 exit;
1798 end if;
1799 end loop;
1800 end if;
1802 return Id;
1803 end Entity_Of;
1805 --------------------
1806 -- Entry_Names_OK --
1807 --------------------
1809 function Entry_Names_OK return Boolean is
1810 begin
1811 return
1812 not Restricted_Profile
1813 and then not Global_Discard_Names
1814 and then not Restriction_Active (No_Implicit_Heap_Allocations)
1815 and then not Restriction_Active (No_Local_Allocators);
1816 end Entry_Names_OK;
1818 -------------------
1819 -- Evaluate_Name --
1820 -------------------
1822 procedure Evaluate_Name (Nam : Node_Id) is
1823 K : constant Node_Kind := Nkind (Nam);
1825 begin
1826 -- For an explicit dereference, we simply force the evaluation of the
1827 -- name expression. The dereference provides a value that is the address
1828 -- for the renamed object, and it is precisely this value that we want
1829 -- to preserve.
1831 if K = N_Explicit_Dereference then
1832 Force_Evaluation (Prefix (Nam));
1834 -- For a selected component, we simply evaluate the prefix
1836 elsif K = N_Selected_Component then
1837 Evaluate_Name (Prefix (Nam));
1839 -- For an indexed component, or an attribute reference, we evaluate the
1840 -- prefix, which is itself a name, recursively, and then force the
1841 -- evaluation of all the subscripts (or attribute expressions).
1843 elsif Nkind_In (K, N_Indexed_Component, N_Attribute_Reference) then
1844 Evaluate_Name (Prefix (Nam));
1846 declare
1847 E : Node_Id;
1849 begin
1850 E := First (Expressions (Nam));
1851 while Present (E) loop
1852 Force_Evaluation (E);
1854 if Original_Node (E) /= E then
1855 Set_Do_Range_Check (E, Do_Range_Check (Original_Node (E)));
1856 end if;
1858 Next (E);
1859 end loop;
1860 end;
1862 -- For a slice, we evaluate the prefix, as for the indexed component
1863 -- case and then, if there is a range present, either directly or as the
1864 -- constraint of a discrete subtype indication, we evaluate the two
1865 -- bounds of this range.
1867 elsif K = N_Slice then
1868 Evaluate_Name (Prefix (Nam));
1870 declare
1871 DR : constant Node_Id := Discrete_Range (Nam);
1872 Constr : Node_Id;
1873 Rexpr : Node_Id;
1875 begin
1876 if Nkind (DR) = N_Range then
1877 Force_Evaluation (Low_Bound (DR));
1878 Force_Evaluation (High_Bound (DR));
1880 elsif Nkind (DR) = N_Subtype_Indication then
1881 Constr := Constraint (DR);
1883 if Nkind (Constr) = N_Range_Constraint then
1884 Rexpr := Range_Expression (Constr);
1886 Force_Evaluation (Low_Bound (Rexpr));
1887 Force_Evaluation (High_Bound (Rexpr));
1888 end if;
1889 end if;
1890 end;
1892 -- For a type conversion, the expression of the conversion must be the
1893 -- name of an object, and we simply need to evaluate this name.
1895 elsif K = N_Type_Conversion then
1896 Evaluate_Name (Expression (Nam));
1898 -- For a function call, we evaluate the call
1900 elsif K = N_Function_Call then
1901 Force_Evaluation (Nam);
1903 -- The remaining cases are direct name, operator symbol and character
1904 -- literal. In all these cases, we do nothing, since we want to
1905 -- reevaluate each time the renamed object is used.
1907 else
1908 return;
1909 end if;
1910 end Evaluate_Name;
1912 ---------------------
1913 -- Evolve_And_Then --
1914 ---------------------
1916 procedure Evolve_And_Then (Cond : in out Node_Id; Cond1 : Node_Id) is
1917 begin
1918 if No (Cond) then
1919 Cond := Cond1;
1920 else
1921 Cond :=
1922 Make_And_Then (Sloc (Cond1),
1923 Left_Opnd => Cond,
1924 Right_Opnd => Cond1);
1925 end if;
1926 end Evolve_And_Then;
1928 --------------------
1929 -- Evolve_Or_Else --
1930 --------------------
1932 procedure Evolve_Or_Else (Cond : in out Node_Id; Cond1 : Node_Id) is
1933 begin
1934 if No (Cond) then
1935 Cond := Cond1;
1936 else
1937 Cond :=
1938 Make_Or_Else (Sloc (Cond1),
1939 Left_Opnd => Cond,
1940 Right_Opnd => Cond1);
1941 end if;
1942 end Evolve_Or_Else;
1944 ------------------------------
1945 -- Expand_Subtype_From_Expr --
1946 ------------------------------
1948 -- This function is applicable for both static and dynamic allocation of
1949 -- objects which are constrained by an initial expression. Basically it
1950 -- transforms an unconstrained subtype indication into a constrained one.
1952 -- The expression may also be transformed in certain cases in order to
1953 -- avoid multiple evaluation. In the static allocation case, the general
1954 -- scheme is:
1956 -- Val : T := Expr;
1958 -- is transformed into
1960 -- Val : Constrained_Subtype_of_T := Maybe_Modified_Expr;
1962 -- Here are the main cases :
1964 -- <if Expr is a Slice>
1965 -- Val : T ([Index_Subtype (Expr)]) := Expr;
1967 -- <elsif Expr is a String Literal>
1968 -- Val : T (T'First .. T'First + Length (string literal) - 1) := Expr;
1970 -- <elsif Expr is Constrained>
1971 -- subtype T is Type_Of_Expr
1972 -- Val : T := Expr;
1974 -- <elsif Expr is an entity_name>
1975 -- Val : T (constraints taken from Expr) := Expr;
1977 -- <else>
1978 -- type Axxx is access all T;
1979 -- Rval : Axxx := Expr'ref;
1980 -- Val : T (constraints taken from Rval) := Rval.all;
1982 -- ??? note: when the Expression is allocated in the secondary stack
1983 -- we could use it directly instead of copying it by declaring
1984 -- Val : T (...) renames Rval.all
1986 procedure Expand_Subtype_From_Expr
1987 (N : Node_Id;
1988 Unc_Type : Entity_Id;
1989 Subtype_Indic : Node_Id;
1990 Exp : Node_Id)
1992 Loc : constant Source_Ptr := Sloc (N);
1993 Exp_Typ : constant Entity_Id := Etype (Exp);
1994 T : Entity_Id;
1996 begin
1997 -- In general we cannot build the subtype if expansion is disabled,
1998 -- because internal entities may not have been defined. However, to
1999 -- avoid some cascaded errors, we try to continue when the expression is
2000 -- an array (or string), because it is safe to compute the bounds. It is
2001 -- in fact required to do so even in a generic context, because there
2002 -- may be constants that depend on the bounds of a string literal, both
2003 -- standard string types and more generally arrays of characters.
2005 if not Expander_Active
2006 and then (No (Etype (Exp)) or else not Is_String_Type (Etype (Exp)))
2007 then
2008 return;
2009 end if;
2011 if Nkind (Exp) = N_Slice then
2012 declare
2013 Slice_Type : constant Entity_Id := Etype (First_Index (Exp_Typ));
2015 begin
2016 Rewrite (Subtype_Indic,
2017 Make_Subtype_Indication (Loc,
2018 Subtype_Mark => New_Reference_To (Unc_Type, Loc),
2019 Constraint =>
2020 Make_Index_Or_Discriminant_Constraint (Loc,
2021 Constraints => New_List
2022 (New_Reference_To (Slice_Type, Loc)))));
2024 -- This subtype indication may be used later for constraint checks
2025 -- we better make sure that if a variable was used as a bound of
2026 -- of the original slice, its value is frozen.
2028 Force_Evaluation (Low_Bound (Scalar_Range (Slice_Type)));
2029 Force_Evaluation (High_Bound (Scalar_Range (Slice_Type)));
2030 end;
2032 elsif Ekind (Exp_Typ) = E_String_Literal_Subtype then
2033 Rewrite (Subtype_Indic,
2034 Make_Subtype_Indication (Loc,
2035 Subtype_Mark => New_Reference_To (Unc_Type, Loc),
2036 Constraint =>
2037 Make_Index_Or_Discriminant_Constraint (Loc,
2038 Constraints => New_List (
2039 Make_Literal_Range (Loc,
2040 Literal_Typ => Exp_Typ)))));
2042 -- If the type of the expression is an internally generated type it
2043 -- may not be necessary to create a new subtype. However there are two
2044 -- exceptions: references to the current instances, and aliased array
2045 -- object declarations for which the backend needs to create a template.
2047 elsif Is_Constrained (Exp_Typ)
2048 and then not Is_Class_Wide_Type (Unc_Type)
2049 and then
2050 (Nkind (N) /= N_Object_Declaration
2051 or else not Is_Entity_Name (Expression (N))
2052 or else not Comes_From_Source (Entity (Expression (N)))
2053 or else not Is_Array_Type (Exp_Typ)
2054 or else not Aliased_Present (N))
2055 then
2056 if Is_Itype (Exp_Typ) then
2058 -- Within an initialization procedure, a selected component
2059 -- denotes a component of the enclosing record, and it appears as
2060 -- an actual in a call to its own initialization procedure. If
2061 -- this component depends on the outer discriminant, we must
2062 -- generate the proper actual subtype for it.
2064 if Nkind (Exp) = N_Selected_Component
2065 and then Within_Init_Proc
2066 then
2067 declare
2068 Decl : constant Node_Id :=
2069 Build_Actual_Subtype_Of_Component (Exp_Typ, Exp);
2070 begin
2071 if Present (Decl) then
2072 Insert_Action (N, Decl);
2073 T := Defining_Identifier (Decl);
2074 else
2075 T := Exp_Typ;
2076 end if;
2077 end;
2079 -- No need to generate a new subtype
2081 else
2082 T := Exp_Typ;
2083 end if;
2085 else
2086 T := Make_Temporary (Loc, 'T');
2088 Insert_Action (N,
2089 Make_Subtype_Declaration (Loc,
2090 Defining_Identifier => T,
2091 Subtype_Indication => New_Reference_To (Exp_Typ, Loc)));
2093 -- This type is marked as an itype even though it has an explicit
2094 -- declaration since otherwise Is_Generic_Actual_Type can get
2095 -- set, resulting in the generation of spurious errors. (See
2096 -- sem_ch8.Analyze_Package_Renaming and sem_type.covers)
2098 Set_Is_Itype (T);
2099 Set_Associated_Node_For_Itype (T, Exp);
2100 end if;
2102 Rewrite (Subtype_Indic, New_Reference_To (T, Loc));
2104 -- Nothing needs to be done for private types with unknown discriminants
2105 -- if the underlying type is not an unconstrained composite type or it
2106 -- is an unchecked union.
2108 elsif Is_Private_Type (Unc_Type)
2109 and then Has_Unknown_Discriminants (Unc_Type)
2110 and then (not Is_Composite_Type (Underlying_Type (Unc_Type))
2111 or else Is_Constrained (Underlying_Type (Unc_Type))
2112 or else Is_Unchecked_Union (Underlying_Type (Unc_Type)))
2113 then
2114 null;
2116 -- Case of derived type with unknown discriminants where the parent type
2117 -- also has unknown discriminants.
2119 elsif Is_Record_Type (Unc_Type)
2120 and then not Is_Class_Wide_Type (Unc_Type)
2121 and then Has_Unknown_Discriminants (Unc_Type)
2122 and then Has_Unknown_Discriminants (Underlying_Type (Unc_Type))
2123 then
2124 -- Nothing to be done if no underlying record view available
2126 if No (Underlying_Record_View (Unc_Type)) then
2127 null;
2129 -- Otherwise use the Underlying_Record_View to create the proper
2130 -- constrained subtype for an object of a derived type with unknown
2131 -- discriminants.
2133 else
2134 Remove_Side_Effects (Exp);
2135 Rewrite (Subtype_Indic,
2136 Make_Subtype_From_Expr (Exp, Underlying_Record_View (Unc_Type)));
2137 end if;
2139 -- Renamings of class-wide interface types require no equivalent
2140 -- constrained type declarations because we only need to reference
2141 -- the tag component associated with the interface. The same is
2142 -- presumably true for class-wide types in general, so this test
2143 -- is broadened to include all class-wide renamings, which also
2144 -- avoids cases of unbounded recursion in Remove_Side_Effects.
2145 -- (Is this really correct, or are there some cases of class-wide
2146 -- renamings that require action in this procedure???)
2148 elsif Present (N)
2149 and then Nkind (N) = N_Object_Renaming_Declaration
2150 and then Is_Class_Wide_Type (Unc_Type)
2151 then
2152 null;
2154 -- In Ada 95 nothing to be done if the type of the expression is limited
2155 -- because in this case the expression cannot be copied, and its use can
2156 -- only be by reference.
2158 -- In Ada 2005 the context can be an object declaration whose expression
2159 -- is a function that returns in place. If the nominal subtype has
2160 -- unknown discriminants, the call still provides constraints on the
2161 -- object, and we have to create an actual subtype from it.
2163 -- If the type is class-wide, the expression is dynamically tagged and
2164 -- we do not create an actual subtype either. Ditto for an interface.
2165 -- For now this applies only if the type is immutably limited, and the
2166 -- function being called is build-in-place. This will have to be revised
2167 -- when build-in-place functions are generalized to other types.
2169 elsif Is_Immutably_Limited_Type (Exp_Typ)
2170 and then
2171 (Is_Class_Wide_Type (Exp_Typ)
2172 or else Is_Interface (Exp_Typ)
2173 or else not Has_Unknown_Discriminants (Exp_Typ)
2174 or else not Is_Composite_Type (Unc_Type))
2175 then
2176 null;
2178 -- For limited objects initialized with build in place function calls,
2179 -- nothing to be done; otherwise we prematurely introduce an N_Reference
2180 -- node in the expression initializing the object, which breaks the
2181 -- circuitry that detects and adds the additional arguments to the
2182 -- called function.
2184 elsif Is_Build_In_Place_Function_Call (Exp) then
2185 null;
2187 else
2188 Remove_Side_Effects (Exp);
2189 Rewrite (Subtype_Indic,
2190 Make_Subtype_From_Expr (Exp, Unc_Type));
2191 end if;
2192 end Expand_Subtype_From_Expr;
2194 ------------------------
2195 -- Find_Interface_ADT --
2196 ------------------------
2198 function Find_Interface_ADT
2199 (T : Entity_Id;
2200 Iface : Entity_Id) return Elmt_Id
2202 ADT : Elmt_Id;
2203 Typ : Entity_Id := T;
2205 begin
2206 pragma Assert (Is_Interface (Iface));
2208 -- Handle private types
2210 if Has_Private_Declaration (Typ) and then Present (Full_View (Typ)) then
2211 Typ := Full_View (Typ);
2212 end if;
2214 -- Handle access types
2216 if Is_Access_Type (Typ) then
2217 Typ := Designated_Type (Typ);
2218 end if;
2220 -- Handle task and protected types implementing interfaces
2222 if Is_Concurrent_Type (Typ) then
2223 Typ := Corresponding_Record_Type (Typ);
2224 end if;
2226 pragma Assert
2227 (not Is_Class_Wide_Type (Typ)
2228 and then Ekind (Typ) /= E_Incomplete_Type);
2230 if Is_Ancestor (Iface, Typ, Use_Full_View => True) then
2231 return First_Elmt (Access_Disp_Table (Typ));
2233 else
2234 ADT := Next_Elmt (Next_Elmt (First_Elmt (Access_Disp_Table (Typ))));
2235 while Present (ADT)
2236 and then Present (Related_Type (Node (ADT)))
2237 and then Related_Type (Node (ADT)) /= Iface
2238 and then not Is_Ancestor (Iface, Related_Type (Node (ADT)),
2239 Use_Full_View => True)
2240 loop
2241 Next_Elmt (ADT);
2242 end loop;
2244 pragma Assert (Present (Related_Type (Node (ADT))));
2245 return ADT;
2246 end if;
2247 end Find_Interface_ADT;
2249 ------------------------
2250 -- Find_Interface_Tag --
2251 ------------------------
2253 function Find_Interface_Tag
2254 (T : Entity_Id;
2255 Iface : Entity_Id) return Entity_Id
2257 AI_Tag : Entity_Id;
2258 Found : Boolean := False;
2259 Typ : Entity_Id := T;
2261 procedure Find_Tag (Typ : Entity_Id);
2262 -- Internal subprogram used to recursively climb to the ancestors
2264 --------------
2265 -- Find_Tag --
2266 --------------
2268 procedure Find_Tag (Typ : Entity_Id) is
2269 AI_Elmt : Elmt_Id;
2270 AI : Node_Id;
2272 begin
2273 -- This routine does not handle the case in which the interface is an
2274 -- ancestor of Typ. That case is handled by the enclosing subprogram.
2276 pragma Assert (Typ /= Iface);
2278 -- Climb to the root type handling private types
2280 if Present (Full_View (Etype (Typ))) then
2281 if Full_View (Etype (Typ)) /= Typ then
2282 Find_Tag (Full_View (Etype (Typ)));
2283 end if;
2285 elsif Etype (Typ) /= Typ then
2286 Find_Tag (Etype (Typ));
2287 end if;
2289 -- Traverse the list of interfaces implemented by the type
2291 if not Found
2292 and then Present (Interfaces (Typ))
2293 and then not (Is_Empty_Elmt_List (Interfaces (Typ)))
2294 then
2295 -- Skip the tag associated with the primary table
2297 pragma Assert (Etype (First_Tag_Component (Typ)) = RTE (RE_Tag));
2298 AI_Tag := Next_Tag_Component (First_Tag_Component (Typ));
2299 pragma Assert (Present (AI_Tag));
2301 AI_Elmt := First_Elmt (Interfaces (Typ));
2302 while Present (AI_Elmt) loop
2303 AI := Node (AI_Elmt);
2305 if AI = Iface
2306 or else Is_Ancestor (Iface, AI, Use_Full_View => True)
2307 then
2308 Found := True;
2309 return;
2310 end if;
2312 AI_Tag := Next_Tag_Component (AI_Tag);
2313 Next_Elmt (AI_Elmt);
2314 end loop;
2315 end if;
2316 end Find_Tag;
2318 -- Start of processing for Find_Interface_Tag
2320 begin
2321 pragma Assert (Is_Interface (Iface));
2323 -- Handle access types
2325 if Is_Access_Type (Typ) then
2326 Typ := Designated_Type (Typ);
2327 end if;
2329 -- Handle class-wide types
2331 if Is_Class_Wide_Type (Typ) then
2332 Typ := Root_Type (Typ);
2333 end if;
2335 -- Handle private types
2337 if Has_Private_Declaration (Typ) and then Present (Full_View (Typ)) then
2338 Typ := Full_View (Typ);
2339 end if;
2341 -- Handle entities from the limited view
2343 if Ekind (Typ) = E_Incomplete_Type then
2344 pragma Assert (Present (Non_Limited_View (Typ)));
2345 Typ := Non_Limited_View (Typ);
2346 end if;
2348 -- Handle task and protected types implementing interfaces
2350 if Is_Concurrent_Type (Typ) then
2351 Typ := Corresponding_Record_Type (Typ);
2352 end if;
2354 -- If the interface is an ancestor of the type, then it shared the
2355 -- primary dispatch table.
2357 if Is_Ancestor (Iface, Typ, Use_Full_View => True) then
2358 pragma Assert (Etype (First_Tag_Component (Typ)) = RTE (RE_Tag));
2359 return First_Tag_Component (Typ);
2361 -- Otherwise we need to search for its associated tag component
2363 else
2364 Find_Tag (Typ);
2365 pragma Assert (Found);
2366 return AI_Tag;
2367 end if;
2368 end Find_Interface_Tag;
2370 ------------------
2371 -- Find_Prim_Op --
2372 ------------------
2374 function Find_Prim_Op (T : Entity_Id; Name : Name_Id) return Entity_Id is
2375 Prim : Elmt_Id;
2376 Typ : Entity_Id := T;
2377 Op : Entity_Id;
2379 begin
2380 if Is_Class_Wide_Type (Typ) then
2381 Typ := Root_Type (Typ);
2382 end if;
2384 Typ := Underlying_Type (Typ);
2386 -- Loop through primitive operations
2388 Prim := First_Elmt (Primitive_Operations (Typ));
2389 while Present (Prim) loop
2390 Op := Node (Prim);
2392 -- We can retrieve primitive operations by name if it is an internal
2393 -- name. For equality we must check that both of its operands have
2394 -- the same type, to avoid confusion with user-defined equalities
2395 -- than may have a non-symmetric signature.
2397 exit when Chars (Op) = Name
2398 and then
2399 (Name /= Name_Op_Eq
2400 or else Etype (First_Formal (Op)) = Etype (Last_Formal (Op)));
2402 Next_Elmt (Prim);
2404 -- Raise Program_Error if no primitive found
2406 if No (Prim) then
2407 raise Program_Error;
2408 end if;
2409 end loop;
2411 return Node (Prim);
2412 end Find_Prim_Op;
2414 ------------------
2415 -- Find_Prim_Op --
2416 ------------------
2418 function Find_Prim_Op
2419 (T : Entity_Id;
2420 Name : TSS_Name_Type) return Entity_Id
2422 Inher_Op : Entity_Id := Empty;
2423 Own_Op : Entity_Id := Empty;
2424 Prim_Elmt : Elmt_Id;
2425 Prim_Id : Entity_Id;
2426 Typ : Entity_Id := T;
2428 begin
2429 if Is_Class_Wide_Type (Typ) then
2430 Typ := Root_Type (Typ);
2431 end if;
2433 Typ := Underlying_Type (Typ);
2435 -- This search is based on the assertion that the dispatching version
2436 -- of the TSS routine always precedes the real primitive.
2438 Prim_Elmt := First_Elmt (Primitive_Operations (Typ));
2439 while Present (Prim_Elmt) loop
2440 Prim_Id := Node (Prim_Elmt);
2442 if Is_TSS (Prim_Id, Name) then
2443 if Present (Alias (Prim_Id)) then
2444 Inher_Op := Prim_Id;
2445 else
2446 Own_Op := Prim_Id;
2447 end if;
2448 end if;
2450 Next_Elmt (Prim_Elmt);
2451 end loop;
2453 if Present (Own_Op) then
2454 return Own_Op;
2455 elsif Present (Inher_Op) then
2456 return Inher_Op;
2457 else
2458 raise Program_Error;
2459 end if;
2460 end Find_Prim_Op;
2462 ----------------------------
2463 -- Find_Protection_Object --
2464 ----------------------------
2466 function Find_Protection_Object (Scop : Entity_Id) return Entity_Id is
2467 S : Entity_Id;
2469 begin
2470 S := Scop;
2471 while Present (S) loop
2472 if Ekind_In (S, E_Entry, E_Entry_Family, E_Function, E_Procedure)
2473 and then Present (Protection_Object (S))
2474 then
2475 return Protection_Object (S);
2476 end if;
2478 S := Scope (S);
2479 end loop;
2481 -- If we do not find a Protection object in the scope chain, then
2482 -- something has gone wrong, most likely the object was never created.
2484 raise Program_Error;
2485 end Find_Protection_Object;
2487 --------------------------
2488 -- Find_Protection_Type --
2489 --------------------------
2491 function Find_Protection_Type (Conc_Typ : Entity_Id) return Entity_Id is
2492 Comp : Entity_Id;
2493 Typ : Entity_Id := Conc_Typ;
2495 begin
2496 if Is_Concurrent_Type (Typ) then
2497 Typ := Corresponding_Record_Type (Typ);
2498 end if;
2500 -- Since restriction violations are not considered serious errors, the
2501 -- expander remains active, but may leave the corresponding record type
2502 -- malformed. In such cases, component _object is not available so do
2503 -- not look for it.
2505 if not Analyzed (Typ) then
2506 return Empty;
2507 end if;
2509 Comp := First_Component (Typ);
2510 while Present (Comp) loop
2511 if Chars (Comp) = Name_uObject then
2512 return Base_Type (Etype (Comp));
2513 end if;
2515 Next_Component (Comp);
2516 end loop;
2518 -- The corresponding record of a protected type should always have an
2519 -- _object field.
2521 raise Program_Error;
2522 end Find_Protection_Type;
2524 ----------------------
2525 -- Force_Evaluation --
2526 ----------------------
2528 procedure Force_Evaluation (Exp : Node_Id; Name_Req : Boolean := False) is
2529 begin
2530 Remove_Side_Effects (Exp, Name_Req, Variable_Ref => True);
2531 end Force_Evaluation;
2533 ---------------------------------
2534 -- Fully_Qualified_Name_String --
2535 ---------------------------------
2537 function Fully_Qualified_Name_String
2538 (E : Entity_Id;
2539 Append_NUL : Boolean := True) return String_Id
2541 procedure Internal_Full_Qualified_Name (E : Entity_Id);
2542 -- Compute recursively the qualified name without NUL at the end, adding
2543 -- it to the currently started string being generated
2545 ----------------------------------
2546 -- Internal_Full_Qualified_Name --
2547 ----------------------------------
2549 procedure Internal_Full_Qualified_Name (E : Entity_Id) is
2550 Ent : Entity_Id;
2552 begin
2553 -- Deal properly with child units
2555 if Nkind (E) = N_Defining_Program_Unit_Name then
2556 Ent := Defining_Identifier (E);
2557 else
2558 Ent := E;
2559 end if;
2561 -- Compute qualification recursively (only "Standard" has no scope)
2563 if Present (Scope (Scope (Ent))) then
2564 Internal_Full_Qualified_Name (Scope (Ent));
2565 Store_String_Char (Get_Char_Code ('.'));
2566 end if;
2568 -- Every entity should have a name except some expanded blocks
2569 -- don't bother about those.
2571 if Chars (Ent) = No_Name then
2572 return;
2573 end if;
2575 -- Generates the entity name in upper case
2577 Get_Decoded_Name_String (Chars (Ent));
2578 Set_All_Upper_Case;
2579 Store_String_Chars (Name_Buffer (1 .. Name_Len));
2580 return;
2581 end Internal_Full_Qualified_Name;
2583 -- Start of processing for Full_Qualified_Name
2585 begin
2586 Start_String;
2587 Internal_Full_Qualified_Name (E);
2589 if Append_NUL then
2590 Store_String_Char (Get_Char_Code (ASCII.NUL));
2591 end if;
2593 return End_String;
2594 end Fully_Qualified_Name_String;
2596 ------------------------
2597 -- Generate_Poll_Call --
2598 ------------------------
2600 procedure Generate_Poll_Call (N : Node_Id) is
2601 begin
2602 -- No poll call if polling not active
2604 if not Polling_Required then
2605 return;
2607 -- Otherwise generate require poll call
2609 else
2610 Insert_Before_And_Analyze (N,
2611 Make_Procedure_Call_Statement (Sloc (N),
2612 Name => New_Occurrence_Of (RTE (RE_Poll), Sloc (N))));
2613 end if;
2614 end Generate_Poll_Call;
2616 ---------------------------------
2617 -- Get_Current_Value_Condition --
2618 ---------------------------------
2620 -- Note: the implementation of this procedure is very closely tied to the
2621 -- implementation of Set_Current_Value_Condition. In the Get procedure, we
2622 -- interpret Current_Value fields set by the Set procedure, so the two
2623 -- procedures need to be closely coordinated.
2625 procedure Get_Current_Value_Condition
2626 (Var : Node_Id;
2627 Op : out Node_Kind;
2628 Val : out Node_Id)
2630 Loc : constant Source_Ptr := Sloc (Var);
2631 Ent : constant Entity_Id := Entity (Var);
2633 procedure Process_Current_Value_Condition
2634 (N : Node_Id;
2635 S : Boolean);
2636 -- N is an expression which holds either True (S = True) or False (S =
2637 -- False) in the condition. This procedure digs out the expression and
2638 -- if it refers to Ent, sets Op and Val appropriately.
2640 -------------------------------------
2641 -- Process_Current_Value_Condition --
2642 -------------------------------------
2644 procedure Process_Current_Value_Condition
2645 (N : Node_Id;
2646 S : Boolean)
2648 Cond : Node_Id;
2649 Sens : Boolean;
2651 begin
2652 Cond := N;
2653 Sens := S;
2655 -- Deal with NOT operators, inverting sense
2657 while Nkind (Cond) = N_Op_Not loop
2658 Cond := Right_Opnd (Cond);
2659 Sens := not Sens;
2660 end loop;
2662 -- Deal with AND THEN and AND cases
2664 if Nkind_In (Cond, N_And_Then, N_Op_And) then
2666 -- Don't ever try to invert a condition that is of the form of an
2667 -- AND or AND THEN (since we are not doing sufficiently general
2668 -- processing to allow this).
2670 if Sens = False then
2671 Op := N_Empty;
2672 Val := Empty;
2673 return;
2674 end if;
2676 -- Recursively process AND and AND THEN branches
2678 Process_Current_Value_Condition (Left_Opnd (Cond), True);
2680 if Op /= N_Empty then
2681 return;
2682 end if;
2684 Process_Current_Value_Condition (Right_Opnd (Cond), True);
2685 return;
2687 -- Case of relational operator
2689 elsif Nkind (Cond) in N_Op_Compare then
2690 Op := Nkind (Cond);
2692 -- Invert sense of test if inverted test
2694 if Sens = False then
2695 case Op is
2696 when N_Op_Eq => Op := N_Op_Ne;
2697 when N_Op_Ne => Op := N_Op_Eq;
2698 when N_Op_Lt => Op := N_Op_Ge;
2699 when N_Op_Gt => Op := N_Op_Le;
2700 when N_Op_Le => Op := N_Op_Gt;
2701 when N_Op_Ge => Op := N_Op_Lt;
2702 when others => raise Program_Error;
2703 end case;
2704 end if;
2706 -- Case of entity op value
2708 if Is_Entity_Name (Left_Opnd (Cond))
2709 and then Ent = Entity (Left_Opnd (Cond))
2710 and then Compile_Time_Known_Value (Right_Opnd (Cond))
2711 then
2712 Val := Right_Opnd (Cond);
2714 -- Case of value op entity
2716 elsif Is_Entity_Name (Right_Opnd (Cond))
2717 and then Ent = Entity (Right_Opnd (Cond))
2718 and then Compile_Time_Known_Value (Left_Opnd (Cond))
2719 then
2720 Val := Left_Opnd (Cond);
2722 -- We are effectively swapping operands
2724 case Op is
2725 when N_Op_Eq => null;
2726 when N_Op_Ne => null;
2727 when N_Op_Lt => Op := N_Op_Gt;
2728 when N_Op_Gt => Op := N_Op_Lt;
2729 when N_Op_Le => Op := N_Op_Ge;
2730 when N_Op_Ge => Op := N_Op_Le;
2731 when others => raise Program_Error;
2732 end case;
2734 else
2735 Op := N_Empty;
2736 end if;
2738 return;
2740 -- Case of Boolean variable reference, return as though the
2741 -- reference had said var = True.
2743 else
2744 if Is_Entity_Name (Cond) and then Ent = Entity (Cond) then
2745 Val := New_Occurrence_Of (Standard_True, Sloc (Cond));
2747 if Sens = False then
2748 Op := N_Op_Ne;
2749 else
2750 Op := N_Op_Eq;
2751 end if;
2752 end if;
2753 end if;
2754 end Process_Current_Value_Condition;
2756 -- Start of processing for Get_Current_Value_Condition
2758 begin
2759 Op := N_Empty;
2760 Val := Empty;
2762 -- Immediate return, nothing doing, if this is not an object
2764 if Ekind (Ent) not in Object_Kind then
2765 return;
2766 end if;
2768 -- Otherwise examine current value
2770 declare
2771 CV : constant Node_Id := Current_Value (Ent);
2772 Sens : Boolean;
2773 Stm : Node_Id;
2775 begin
2776 -- If statement. Condition is known true in THEN section, known False
2777 -- in any ELSIF or ELSE part, and unknown outside the IF statement.
2779 if Nkind (CV) = N_If_Statement then
2781 -- Before start of IF statement
2783 if Loc < Sloc (CV) then
2784 return;
2786 -- After end of IF statement
2788 elsif Loc >= Sloc (CV) + Text_Ptr (UI_To_Int (End_Span (CV))) then
2789 return;
2790 end if;
2792 -- At this stage we know that we are within the IF statement, but
2793 -- unfortunately, the tree does not record the SLOC of the ELSE so
2794 -- we cannot use a simple SLOC comparison to distinguish between
2795 -- the then/else statements, so we have to climb the tree.
2797 declare
2798 N : Node_Id;
2800 begin
2801 N := Parent (Var);
2802 while Parent (N) /= CV loop
2803 N := Parent (N);
2805 -- If we fall off the top of the tree, then that's odd, but
2806 -- perhaps it could occur in some error situation, and the
2807 -- safest response is simply to assume that the outcome of
2808 -- the condition is unknown. No point in bombing during an
2809 -- attempt to optimize things.
2811 if No (N) then
2812 return;
2813 end if;
2814 end loop;
2816 -- Now we have N pointing to a node whose parent is the IF
2817 -- statement in question, so now we can tell if we are within
2818 -- the THEN statements.
2820 if Is_List_Member (N)
2821 and then List_Containing (N) = Then_Statements (CV)
2822 then
2823 Sens := True;
2825 -- If the variable reference does not come from source, we
2826 -- cannot reliably tell whether it appears in the else part.
2827 -- In particular, if it appears in generated code for a node
2828 -- that requires finalization, it may be attached to a list
2829 -- that has not been yet inserted into the code. For now,
2830 -- treat it as unknown.
2832 elsif not Comes_From_Source (N) then
2833 return;
2835 -- Otherwise we must be in ELSIF or ELSE part
2837 else
2838 Sens := False;
2839 end if;
2840 end;
2842 -- ELSIF part. Condition is known true within the referenced
2843 -- ELSIF, known False in any subsequent ELSIF or ELSE part,
2844 -- and unknown before the ELSE part or after the IF statement.
2846 elsif Nkind (CV) = N_Elsif_Part then
2848 -- if the Elsif_Part had condition_actions, the elsif has been
2849 -- rewritten as a nested if, and the original elsif_part is
2850 -- detached from the tree, so there is no way to obtain useful
2851 -- information on the current value of the variable.
2852 -- Can this be improved ???
2854 if No (Parent (CV)) then
2855 return;
2856 end if;
2858 Stm := Parent (CV);
2860 -- Before start of ELSIF part
2862 if Loc < Sloc (CV) then
2863 return;
2865 -- After end of IF statement
2867 elsif Loc >= Sloc (Stm) +
2868 Text_Ptr (UI_To_Int (End_Span (Stm)))
2869 then
2870 return;
2871 end if;
2873 -- Again we lack the SLOC of the ELSE, so we need to climb the
2874 -- tree to see if we are within the ELSIF part in question.
2876 declare
2877 N : Node_Id;
2879 begin
2880 N := Parent (Var);
2881 while Parent (N) /= Stm loop
2882 N := Parent (N);
2884 -- If we fall off the top of the tree, then that's odd, but
2885 -- perhaps it could occur in some error situation, and the
2886 -- safest response is simply to assume that the outcome of
2887 -- the condition is unknown. No point in bombing during an
2888 -- attempt to optimize things.
2890 if No (N) then
2891 return;
2892 end if;
2893 end loop;
2895 -- Now we have N pointing to a node whose parent is the IF
2896 -- statement in question, so see if is the ELSIF part we want.
2897 -- the THEN statements.
2899 if N = CV then
2900 Sens := True;
2902 -- Otherwise we must be in subsequent ELSIF or ELSE part
2904 else
2905 Sens := False;
2906 end if;
2907 end;
2909 -- Iteration scheme of while loop. The condition is known to be
2910 -- true within the body of the loop.
2912 elsif Nkind (CV) = N_Iteration_Scheme then
2913 declare
2914 Loop_Stmt : constant Node_Id := Parent (CV);
2916 begin
2917 -- Before start of body of loop
2919 if Loc < Sloc (Loop_Stmt) then
2920 return;
2922 -- After end of LOOP statement
2924 elsif Loc >= Sloc (End_Label (Loop_Stmt)) then
2925 return;
2927 -- We are within the body of the loop
2929 else
2930 Sens := True;
2931 end if;
2932 end;
2934 -- All other cases of Current_Value settings
2936 else
2937 return;
2938 end if;
2940 -- If we fall through here, then we have a reportable condition, Sens
2941 -- is True if the condition is true and False if it needs inverting.
2943 Process_Current_Value_Condition (Condition (CV), Sens);
2944 end;
2945 end Get_Current_Value_Condition;
2947 ---------------------
2948 -- Get_Stream_Size --
2949 ---------------------
2951 function Get_Stream_Size (E : Entity_Id) return Uint is
2952 begin
2953 -- If we have a Stream_Size clause for this type use it
2955 if Has_Stream_Size_Clause (E) then
2956 return Static_Integer (Expression (Stream_Size_Clause (E)));
2958 -- Otherwise the Stream_Size if the size of the type
2960 else
2961 return Esize (E);
2962 end if;
2963 end Get_Stream_Size;
2965 ---------------------------
2966 -- Has_Access_Constraint --
2967 ---------------------------
2969 function Has_Access_Constraint (E : Entity_Id) return Boolean is
2970 Disc : Entity_Id;
2971 T : constant Entity_Id := Etype (E);
2973 begin
2974 if Has_Per_Object_Constraint (E) and then Has_Discriminants (T) then
2975 Disc := First_Discriminant (T);
2976 while Present (Disc) loop
2977 if Is_Access_Type (Etype (Disc)) then
2978 return True;
2979 end if;
2981 Next_Discriminant (Disc);
2982 end loop;
2984 return False;
2985 else
2986 return False;
2987 end if;
2988 end Has_Access_Constraint;
2990 ----------------------------------
2991 -- Has_Following_Address_Clause --
2992 ----------------------------------
2994 -- Should this function check the private part in a package ???
2996 function Has_Following_Address_Clause (D : Node_Id) return Boolean is
2997 Id : constant Entity_Id := Defining_Identifier (D);
2998 Decl : Node_Id;
3000 begin
3001 Decl := Next (D);
3002 while Present (Decl) loop
3003 if Nkind (Decl) = N_At_Clause
3004 and then Chars (Identifier (Decl)) = Chars (Id)
3005 then
3006 return True;
3008 elsif Nkind (Decl) = N_Attribute_Definition_Clause
3009 and then Chars (Decl) = Name_Address
3010 and then Chars (Name (Decl)) = Chars (Id)
3011 then
3012 return True;
3013 end if;
3015 Next (Decl);
3016 end loop;
3018 return False;
3019 end Has_Following_Address_Clause;
3021 --------------------
3022 -- Homonym_Number --
3023 --------------------
3025 function Homonym_Number (Subp : Entity_Id) return Nat is
3026 Count : Nat;
3027 Hom : Entity_Id;
3029 begin
3030 Count := 1;
3031 Hom := Homonym (Subp);
3032 while Present (Hom) loop
3033 if Scope (Hom) = Scope (Subp) then
3034 Count := Count + 1;
3035 end if;
3037 Hom := Homonym (Hom);
3038 end loop;
3040 return Count;
3041 end Homonym_Number;
3043 -----------------------------------
3044 -- In_Library_Level_Package_Body --
3045 -----------------------------------
3047 function In_Library_Level_Package_Body (Id : Entity_Id) return Boolean is
3048 begin
3049 -- First determine whether the entity appears at the library level, then
3050 -- look at the containing unit.
3052 if Is_Library_Level_Entity (Id) then
3053 declare
3054 Container : constant Node_Id := Cunit (Get_Source_Unit (Id));
3056 begin
3057 return Nkind (Unit (Container)) = N_Package_Body;
3058 end;
3059 end if;
3061 return False;
3062 end In_Library_Level_Package_Body;
3064 ------------------------------
3065 -- In_Unconditional_Context --
3066 ------------------------------
3068 function In_Unconditional_Context (Node : Node_Id) return Boolean is
3069 P : Node_Id;
3071 begin
3072 P := Node;
3073 while Present (P) loop
3074 case Nkind (P) is
3075 when N_Subprogram_Body =>
3076 return True;
3078 when N_If_Statement =>
3079 return False;
3081 when N_Loop_Statement =>
3082 return False;
3084 when N_Case_Statement =>
3085 return False;
3087 when others =>
3088 P := Parent (P);
3089 end case;
3090 end loop;
3092 return False;
3093 end In_Unconditional_Context;
3095 -------------------
3096 -- Insert_Action --
3097 -------------------
3099 procedure Insert_Action (Assoc_Node : Node_Id; Ins_Action : Node_Id) is
3100 begin
3101 if Present (Ins_Action) then
3102 Insert_Actions (Assoc_Node, New_List (Ins_Action));
3103 end if;
3104 end Insert_Action;
3106 -- Version with check(s) suppressed
3108 procedure Insert_Action
3109 (Assoc_Node : Node_Id; Ins_Action : Node_Id; Suppress : Check_Id)
3111 begin
3112 Insert_Actions (Assoc_Node, New_List (Ins_Action), Suppress);
3113 end Insert_Action;
3115 -------------------------
3116 -- Insert_Action_After --
3117 -------------------------
3119 procedure Insert_Action_After
3120 (Assoc_Node : Node_Id;
3121 Ins_Action : Node_Id)
3123 begin
3124 Insert_Actions_After (Assoc_Node, New_List (Ins_Action));
3125 end Insert_Action_After;
3127 --------------------
3128 -- Insert_Actions --
3129 --------------------
3131 procedure Insert_Actions (Assoc_Node : Node_Id; Ins_Actions : List_Id) is
3132 N : Node_Id;
3133 P : Node_Id;
3135 Wrapped_Node : Node_Id := Empty;
3137 begin
3138 if No (Ins_Actions) or else Is_Empty_List (Ins_Actions) then
3139 return;
3140 end if;
3142 -- Ignore insert of actions from inside default expression (or other
3143 -- similar "spec expression") in the special spec-expression analyze
3144 -- mode. Any insertions at this point have no relevance, since we are
3145 -- only doing the analyze to freeze the types of any static expressions.
3146 -- See section "Handling of Default Expressions" in the spec of package
3147 -- Sem for further details.
3149 if In_Spec_Expression then
3150 return;
3151 end if;
3153 -- If the action derives from stuff inside a record, then the actions
3154 -- are attached to the current scope, to be inserted and analyzed on
3155 -- exit from the scope. The reason for this is that we may also be
3156 -- generating freeze actions at the same time, and they must eventually
3157 -- be elaborated in the correct order.
3159 if Is_Record_Type (Current_Scope)
3160 and then not Is_Frozen (Current_Scope)
3161 then
3162 if No (Scope_Stack.Table
3163 (Scope_Stack.Last).Pending_Freeze_Actions)
3164 then
3165 Scope_Stack.Table (Scope_Stack.Last).Pending_Freeze_Actions :=
3166 Ins_Actions;
3167 else
3168 Append_List
3169 (Ins_Actions,
3170 Scope_Stack.Table (Scope_Stack.Last).Pending_Freeze_Actions);
3171 end if;
3173 return;
3174 end if;
3176 -- We now intend to climb up the tree to find the right point to
3177 -- insert the actions. We start at Assoc_Node, unless this node is a
3178 -- subexpression in which case we start with its parent. We do this for
3179 -- two reasons. First it speeds things up. Second, if Assoc_Node is
3180 -- itself one of the special nodes like N_And_Then, then we assume that
3181 -- an initial request to insert actions for such a node does not expect
3182 -- the actions to get deposited in the node for later handling when the
3183 -- node is expanded, since clearly the node is being dealt with by the
3184 -- caller. Note that in the subexpression case, N is always the child we
3185 -- came from.
3187 -- N_Raise_xxx_Error is an annoying special case, it is a statement if
3188 -- it has type Standard_Void_Type, and a subexpression otherwise.
3189 -- otherwise. Procedure calls, and similarly procedure attribute
3190 -- references, are also statements.
3192 if Nkind (Assoc_Node) in N_Subexpr
3193 and then (Nkind (Assoc_Node) not in N_Raise_xxx_Error
3194 or else Etype (Assoc_Node) /= Standard_Void_Type)
3195 and then Nkind (Assoc_Node) /= N_Procedure_Call_Statement
3196 and then (Nkind (Assoc_Node) /= N_Attribute_Reference
3197 or else
3198 not Is_Procedure_Attribute_Name
3199 (Attribute_Name (Assoc_Node)))
3200 then
3201 N := Assoc_Node;
3202 P := Parent (Assoc_Node);
3204 -- Non-subexpression case. Note that N is initially Empty in this case
3205 -- (N is only guaranteed Non-Empty in the subexpr case).
3207 else
3208 N := Empty;
3209 P := Assoc_Node;
3210 end if;
3212 -- Capture root of the transient scope
3214 if Scope_Is_Transient then
3215 Wrapped_Node := Node_To_Be_Wrapped;
3216 end if;
3218 loop
3219 pragma Assert (Present (P));
3221 -- Make sure that inserted actions stay in the transient scope
3223 if Present (Wrapped_Node) and then N = Wrapped_Node then
3224 Store_Before_Actions_In_Scope (Ins_Actions);
3225 return;
3226 end if;
3228 case Nkind (P) is
3230 -- Case of right operand of AND THEN or OR ELSE. Put the actions
3231 -- in the Actions field of the right operand. They will be moved
3232 -- out further when the AND THEN or OR ELSE operator is expanded.
3233 -- Nothing special needs to be done for the left operand since
3234 -- in that case the actions are executed unconditionally.
3236 when N_Short_Circuit =>
3237 if N = Right_Opnd (P) then
3239 -- We are now going to either append the actions to the
3240 -- actions field of the short-circuit operation. We will
3241 -- also analyze the actions now.
3243 -- This analysis is really too early, the proper thing would
3244 -- be to just park them there now, and only analyze them if
3245 -- we find we really need them, and to it at the proper
3246 -- final insertion point. However attempting to this proved
3247 -- tricky, so for now we just kill current values before and
3248 -- after the analyze call to make sure we avoid peculiar
3249 -- optimizations from this out of order insertion.
3251 Kill_Current_Values;
3253 if Present (Actions (P)) then
3254 Insert_List_After_And_Analyze
3255 (Last (Actions (P)), Ins_Actions);
3256 else
3257 Set_Actions (P, Ins_Actions);
3258 Analyze_List (Actions (P));
3259 end if;
3261 Kill_Current_Values;
3263 return;
3264 end if;
3266 -- Then or Else dependent expression of an if expression. Add
3267 -- actions to Then_Actions or Else_Actions field as appropriate.
3268 -- The actions will be moved further out when the if is expanded.
3270 when N_If_Expression =>
3271 declare
3272 ThenX : constant Node_Id := Next (First (Expressions (P)));
3273 ElseX : constant Node_Id := Next (ThenX);
3275 begin
3276 -- If the enclosing expression is already analyzed, as
3277 -- is the case for nested elaboration checks, insert the
3278 -- conditional further out.
3280 if Analyzed (P) then
3281 null;
3283 -- Actions belong to the then expression, temporarily place
3284 -- them as Then_Actions of the if expression. They will be
3285 -- moved to the proper place later when the if expression
3286 -- is expanded.
3288 elsif N = ThenX then
3289 if Present (Then_Actions (P)) then
3290 Insert_List_After_And_Analyze
3291 (Last (Then_Actions (P)), Ins_Actions);
3292 else
3293 Set_Then_Actions (P, Ins_Actions);
3294 Analyze_List (Then_Actions (P));
3295 end if;
3297 return;
3299 -- Actions belong to the else expression, temporarily place
3300 -- them as Else_Actions of the if expression. They will be
3301 -- moved to the proper place later when the if expression
3302 -- is expanded.
3304 elsif N = ElseX then
3305 if Present (Else_Actions (P)) then
3306 Insert_List_After_And_Analyze
3307 (Last (Else_Actions (P)), Ins_Actions);
3308 else
3309 Set_Else_Actions (P, Ins_Actions);
3310 Analyze_List (Else_Actions (P));
3311 end if;
3313 return;
3315 -- Actions belong to the condition. In this case they are
3316 -- unconditionally executed, and so we can continue the
3317 -- search for the proper insert point.
3319 else
3320 null;
3321 end if;
3322 end;
3324 -- Alternative of case expression, we place the action in the
3325 -- Actions field of the case expression alternative, this will
3326 -- be handled when the case expression is expanded.
3328 when N_Case_Expression_Alternative =>
3329 if Present (Actions (P)) then
3330 Insert_List_After_And_Analyze
3331 (Last (Actions (P)), Ins_Actions);
3332 else
3333 Set_Actions (P, Ins_Actions);
3334 Analyze_List (Actions (P));
3335 end if;
3337 return;
3339 -- Case of appearing within an Expressions_With_Actions node. When
3340 -- the new actions come from the expression of the expression with
3341 -- actions, they must be added to the existing actions. The other
3342 -- alternative is when the new actions are related to one of the
3343 -- existing actions of the expression with actions. In that case
3344 -- they must be inserted further up the tree.
3346 when N_Expression_With_Actions =>
3347 if N = Expression (P) then
3348 Insert_List_After_And_Analyze
3349 (Last (Actions (P)), Ins_Actions);
3350 return;
3351 end if;
3353 -- Case of appearing in the condition of a while expression or
3354 -- elsif. We insert the actions into the Condition_Actions field.
3355 -- They will be moved further out when the while loop or elsif
3356 -- is analyzed.
3358 when N_Iteration_Scheme |
3359 N_Elsif_Part
3361 if N = Condition (P) then
3362 if Present (Condition_Actions (P)) then
3363 Insert_List_After_And_Analyze
3364 (Last (Condition_Actions (P)), Ins_Actions);
3365 else
3366 Set_Condition_Actions (P, Ins_Actions);
3368 -- Set the parent of the insert actions explicitly. This
3369 -- is not a syntactic field, but we need the parent field
3370 -- set, in particular so that freeze can understand that
3371 -- it is dealing with condition actions, and properly
3372 -- insert the freezing actions.
3374 Set_Parent (Ins_Actions, P);
3375 Analyze_List (Condition_Actions (P));
3376 end if;
3378 return;
3379 end if;
3381 -- Statements, declarations, pragmas, representation clauses
3383 when
3384 -- Statements
3386 N_Procedure_Call_Statement |
3387 N_Statement_Other_Than_Procedure_Call |
3389 -- Pragmas
3391 N_Pragma |
3393 -- Representation_Clause
3395 N_At_Clause |
3396 N_Attribute_Definition_Clause |
3397 N_Enumeration_Representation_Clause |
3398 N_Record_Representation_Clause |
3400 -- Declarations
3402 N_Abstract_Subprogram_Declaration |
3403 N_Entry_Body |
3404 N_Exception_Declaration |
3405 N_Exception_Renaming_Declaration |
3406 N_Expression_Function |
3407 N_Formal_Abstract_Subprogram_Declaration |
3408 N_Formal_Concrete_Subprogram_Declaration |
3409 N_Formal_Object_Declaration |
3410 N_Formal_Type_Declaration |
3411 N_Full_Type_Declaration |
3412 N_Function_Instantiation |
3413 N_Generic_Function_Renaming_Declaration |
3414 N_Generic_Package_Declaration |
3415 N_Generic_Package_Renaming_Declaration |
3416 N_Generic_Procedure_Renaming_Declaration |
3417 N_Generic_Subprogram_Declaration |
3418 N_Implicit_Label_Declaration |
3419 N_Incomplete_Type_Declaration |
3420 N_Number_Declaration |
3421 N_Object_Declaration |
3422 N_Object_Renaming_Declaration |
3423 N_Package_Body |
3424 N_Package_Body_Stub |
3425 N_Package_Declaration |
3426 N_Package_Instantiation |
3427 N_Package_Renaming_Declaration |
3428 N_Private_Extension_Declaration |
3429 N_Private_Type_Declaration |
3430 N_Procedure_Instantiation |
3431 N_Protected_Body |
3432 N_Protected_Body_Stub |
3433 N_Protected_Type_Declaration |
3434 N_Single_Task_Declaration |
3435 N_Subprogram_Body |
3436 N_Subprogram_Body_Stub |
3437 N_Subprogram_Declaration |
3438 N_Subprogram_Renaming_Declaration |
3439 N_Subtype_Declaration |
3440 N_Task_Body |
3441 N_Task_Body_Stub |
3442 N_Task_Type_Declaration |
3444 -- Use clauses can appear in lists of declarations
3446 N_Use_Package_Clause |
3447 N_Use_Type_Clause |
3449 -- Freeze entity behaves like a declaration or statement
3451 N_Freeze_Entity
3453 -- Do not insert here if the item is not a list member (this
3454 -- happens for example with a triggering statement, and the
3455 -- proper approach is to insert before the entire select).
3457 if not Is_List_Member (P) then
3458 null;
3460 -- Do not insert if parent of P is an N_Component_Association
3461 -- node (i.e. we are in the context of an N_Aggregate or
3462 -- N_Extension_Aggregate node. In this case we want to insert
3463 -- before the entire aggregate.
3465 elsif Nkind (Parent (P)) = N_Component_Association then
3466 null;
3468 -- Do not insert if the parent of P is either an N_Variant node
3469 -- or an N_Record_Definition node, meaning in either case that
3470 -- P is a member of a component list, and that therefore the
3471 -- actions should be inserted outside the complete record
3472 -- declaration.
3474 elsif Nkind_In (Parent (P), N_Variant, N_Record_Definition) then
3475 null;
3477 -- Do not insert freeze nodes within the loop generated for
3478 -- an aggregate, because they may be elaborated too late for
3479 -- subsequent use in the back end: within a package spec the
3480 -- loop is part of the elaboration procedure and is only
3481 -- elaborated during the second pass.
3483 -- If the loop comes from source, or the entity is local to the
3484 -- loop itself it must remain within.
3486 elsif Nkind (Parent (P)) = N_Loop_Statement
3487 and then not Comes_From_Source (Parent (P))
3488 and then Nkind (First (Ins_Actions)) = N_Freeze_Entity
3489 and then
3490 Scope (Entity (First (Ins_Actions))) /= Current_Scope
3491 then
3492 null;
3494 -- Otherwise we can go ahead and do the insertion
3496 elsif P = Wrapped_Node then
3497 Store_Before_Actions_In_Scope (Ins_Actions);
3498 return;
3500 else
3501 Insert_List_Before_And_Analyze (P, Ins_Actions);
3502 return;
3503 end if;
3505 -- A special case, N_Raise_xxx_Error can act either as a statement
3506 -- or a subexpression. We tell the difference by looking at the
3507 -- Etype. It is set to Standard_Void_Type in the statement case.
3509 when
3510 N_Raise_xxx_Error =>
3511 if Etype (P) = Standard_Void_Type then
3512 if P = Wrapped_Node then
3513 Store_Before_Actions_In_Scope (Ins_Actions);
3514 else
3515 Insert_List_Before_And_Analyze (P, Ins_Actions);
3516 end if;
3518 return;
3520 -- In the subexpression case, keep climbing
3522 else
3523 null;
3524 end if;
3526 -- If a component association appears within a loop created for
3527 -- an array aggregate, attach the actions to the association so
3528 -- they can be subsequently inserted within the loop. For other
3529 -- component associations insert outside of the aggregate. For
3530 -- an association that will generate a loop, its Loop_Actions
3531 -- attribute is already initialized (see exp_aggr.adb).
3533 -- The list of loop_actions can in turn generate additional ones,
3534 -- that are inserted before the associated node. If the associated
3535 -- node is outside the aggregate, the new actions are collected
3536 -- at the end of the loop actions, to respect the order in which
3537 -- they are to be elaborated.
3539 when
3540 N_Component_Association =>
3541 if Nkind (Parent (P)) = N_Aggregate
3542 and then Present (Loop_Actions (P))
3543 then
3544 if Is_Empty_List (Loop_Actions (P)) then
3545 Set_Loop_Actions (P, Ins_Actions);
3546 Analyze_List (Ins_Actions);
3548 else
3549 declare
3550 Decl : Node_Id;
3552 begin
3553 -- Check whether these actions were generated by a
3554 -- declaration that is part of the loop_ actions
3555 -- for the component_association.
3557 Decl := Assoc_Node;
3558 while Present (Decl) loop
3559 exit when Parent (Decl) = P
3560 and then Is_List_Member (Decl)
3561 and then
3562 List_Containing (Decl) = Loop_Actions (P);
3563 Decl := Parent (Decl);
3564 end loop;
3566 if Present (Decl) then
3567 Insert_List_Before_And_Analyze
3568 (Decl, Ins_Actions);
3569 else
3570 Insert_List_After_And_Analyze
3571 (Last (Loop_Actions (P)), Ins_Actions);
3572 end if;
3573 end;
3574 end if;
3576 return;
3578 else
3579 null;
3580 end if;
3582 -- Another special case, an attribute denoting a procedure call
3584 when
3585 N_Attribute_Reference =>
3586 if Is_Procedure_Attribute_Name (Attribute_Name (P)) then
3587 if P = Wrapped_Node then
3588 Store_Before_Actions_In_Scope (Ins_Actions);
3589 else
3590 Insert_List_Before_And_Analyze (P, Ins_Actions);
3591 end if;
3593 return;
3595 -- In the subexpression case, keep climbing
3597 else
3598 null;
3599 end if;
3601 -- A contract node should not belong to the tree
3603 when N_Contract =>
3604 raise Program_Error;
3606 -- For all other node types, keep climbing tree
3608 when
3609 N_Abortable_Part |
3610 N_Accept_Alternative |
3611 N_Access_Definition |
3612 N_Access_Function_Definition |
3613 N_Access_Procedure_Definition |
3614 N_Access_To_Object_Definition |
3615 N_Aggregate |
3616 N_Allocator |
3617 N_Aspect_Specification |
3618 N_Case_Expression |
3619 N_Case_Statement_Alternative |
3620 N_Character_Literal |
3621 N_Compilation_Unit |
3622 N_Compilation_Unit_Aux |
3623 N_Component_Clause |
3624 N_Component_Declaration |
3625 N_Component_Definition |
3626 N_Component_List |
3627 N_Constrained_Array_Definition |
3628 N_Decimal_Fixed_Point_Definition |
3629 N_Defining_Character_Literal |
3630 N_Defining_Identifier |
3631 N_Defining_Operator_Symbol |
3632 N_Defining_Program_Unit_Name |
3633 N_Delay_Alternative |
3634 N_Delta_Constraint |
3635 N_Derived_Type_Definition |
3636 N_Designator |
3637 N_Digits_Constraint |
3638 N_Discriminant_Association |
3639 N_Discriminant_Specification |
3640 N_Empty |
3641 N_Entry_Body_Formal_Part |
3642 N_Entry_Call_Alternative |
3643 N_Entry_Declaration |
3644 N_Entry_Index_Specification |
3645 N_Enumeration_Type_Definition |
3646 N_Error |
3647 N_Exception_Handler |
3648 N_Expanded_Name |
3649 N_Explicit_Dereference |
3650 N_Extension_Aggregate |
3651 N_Floating_Point_Definition |
3652 N_Formal_Decimal_Fixed_Point_Definition |
3653 N_Formal_Derived_Type_Definition |
3654 N_Formal_Discrete_Type_Definition |
3655 N_Formal_Floating_Point_Definition |
3656 N_Formal_Modular_Type_Definition |
3657 N_Formal_Ordinary_Fixed_Point_Definition |
3658 N_Formal_Package_Declaration |
3659 N_Formal_Private_Type_Definition |
3660 N_Formal_Incomplete_Type_Definition |
3661 N_Formal_Signed_Integer_Type_Definition |
3662 N_Function_Call |
3663 N_Function_Specification |
3664 N_Generic_Association |
3665 N_Handled_Sequence_Of_Statements |
3666 N_Identifier |
3667 N_In |
3668 N_Index_Or_Discriminant_Constraint |
3669 N_Indexed_Component |
3670 N_Integer_Literal |
3671 N_Iterator_Specification |
3672 N_Itype_Reference |
3673 N_Label |
3674 N_Loop_Parameter_Specification |
3675 N_Mod_Clause |
3676 N_Modular_Type_Definition |
3677 N_Not_In |
3678 N_Null |
3679 N_Op_Abs |
3680 N_Op_Add |
3681 N_Op_And |
3682 N_Op_Concat |
3683 N_Op_Divide |
3684 N_Op_Eq |
3685 N_Op_Expon |
3686 N_Op_Ge |
3687 N_Op_Gt |
3688 N_Op_Le |
3689 N_Op_Lt |
3690 N_Op_Minus |
3691 N_Op_Mod |
3692 N_Op_Multiply |
3693 N_Op_Ne |
3694 N_Op_Not |
3695 N_Op_Or |
3696 N_Op_Plus |
3697 N_Op_Rem |
3698 N_Op_Rotate_Left |
3699 N_Op_Rotate_Right |
3700 N_Op_Shift_Left |
3701 N_Op_Shift_Right |
3702 N_Op_Shift_Right_Arithmetic |
3703 N_Op_Subtract |
3704 N_Op_Xor |
3705 N_Operator_Symbol |
3706 N_Ordinary_Fixed_Point_Definition |
3707 N_Others_Choice |
3708 N_Package_Specification |
3709 N_Parameter_Association |
3710 N_Parameter_Specification |
3711 N_Pop_Constraint_Error_Label |
3712 N_Pop_Program_Error_Label |
3713 N_Pop_Storage_Error_Label |
3714 N_Pragma_Argument_Association |
3715 N_Procedure_Specification |
3716 N_Protected_Definition |
3717 N_Push_Constraint_Error_Label |
3718 N_Push_Program_Error_Label |
3719 N_Push_Storage_Error_Label |
3720 N_Qualified_Expression |
3721 N_Quantified_Expression |
3722 N_Raise_Expression |
3723 N_Range |
3724 N_Range_Constraint |
3725 N_Real_Literal |
3726 N_Real_Range_Specification |
3727 N_Record_Definition |
3728 N_Reference |
3729 N_SCIL_Dispatch_Table_Tag_Init |
3730 N_SCIL_Dispatching_Call |
3731 N_SCIL_Membership_Test |
3732 N_Selected_Component |
3733 N_Signed_Integer_Type_Definition |
3734 N_Single_Protected_Declaration |
3735 N_Slice |
3736 N_String_Literal |
3737 N_Subprogram_Info |
3738 N_Subtype_Indication |
3739 N_Subunit |
3740 N_Task_Definition |
3741 N_Terminate_Alternative |
3742 N_Triggering_Alternative |
3743 N_Type_Conversion |
3744 N_Unchecked_Expression |
3745 N_Unchecked_Type_Conversion |
3746 N_Unconstrained_Array_Definition |
3747 N_Unused_At_End |
3748 N_Unused_At_Start |
3749 N_Variant |
3750 N_Variant_Part |
3751 N_Validate_Unchecked_Conversion |
3752 N_With_Clause
3754 null;
3756 end case;
3758 -- If we fall through above tests, keep climbing tree
3760 N := P;
3762 if Nkind (Parent (N)) = N_Subunit then
3764 -- This is the proper body corresponding to a stub. Insertion must
3765 -- be done at the point of the stub, which is in the declarative
3766 -- part of the parent unit.
3768 P := Corresponding_Stub (Parent (N));
3770 else
3771 P := Parent (N);
3772 end if;
3773 end loop;
3774 end Insert_Actions;
3776 -- Version with check(s) suppressed
3778 procedure Insert_Actions
3779 (Assoc_Node : Node_Id;
3780 Ins_Actions : List_Id;
3781 Suppress : Check_Id)
3783 begin
3784 if Suppress = All_Checks then
3785 declare
3786 Sva : constant Suppress_Array := Scope_Suppress.Suppress;
3787 begin
3788 Scope_Suppress.Suppress := (others => True);
3789 Insert_Actions (Assoc_Node, Ins_Actions);
3790 Scope_Suppress.Suppress := Sva;
3791 end;
3793 else
3794 declare
3795 Svg : constant Boolean := Scope_Suppress.Suppress (Suppress);
3796 begin
3797 Scope_Suppress.Suppress (Suppress) := True;
3798 Insert_Actions (Assoc_Node, Ins_Actions);
3799 Scope_Suppress.Suppress (Suppress) := Svg;
3800 end;
3801 end if;
3802 end Insert_Actions;
3804 --------------------------
3805 -- Insert_Actions_After --
3806 --------------------------
3808 procedure Insert_Actions_After
3809 (Assoc_Node : Node_Id;
3810 Ins_Actions : List_Id)
3812 begin
3813 if Scope_Is_Transient and then Assoc_Node = Node_To_Be_Wrapped then
3814 Store_After_Actions_In_Scope (Ins_Actions);
3815 else
3816 Insert_List_After_And_Analyze (Assoc_Node, Ins_Actions);
3817 end if;
3818 end Insert_Actions_After;
3820 ---------------------------------
3821 -- Insert_Library_Level_Action --
3822 ---------------------------------
3824 procedure Insert_Library_Level_Action (N : Node_Id) is
3825 Aux : constant Node_Id := Aux_Decls_Node (Cunit (Main_Unit));
3827 begin
3828 Push_Scope (Cunit_Entity (Main_Unit));
3829 -- ??? should this be Current_Sem_Unit instead of Main_Unit?
3831 if No (Actions (Aux)) then
3832 Set_Actions (Aux, New_List (N));
3833 else
3834 Append (N, Actions (Aux));
3835 end if;
3837 Analyze (N);
3838 Pop_Scope;
3839 end Insert_Library_Level_Action;
3841 ----------------------------------
3842 -- Insert_Library_Level_Actions --
3843 ----------------------------------
3845 procedure Insert_Library_Level_Actions (L : List_Id) is
3846 Aux : constant Node_Id := Aux_Decls_Node (Cunit (Main_Unit));
3848 begin
3849 if Is_Non_Empty_List (L) then
3850 Push_Scope (Cunit_Entity (Main_Unit));
3851 -- ??? should this be Current_Sem_Unit instead of Main_Unit?
3853 if No (Actions (Aux)) then
3854 Set_Actions (Aux, L);
3855 Analyze_List (L);
3856 else
3857 Insert_List_After_And_Analyze (Last (Actions (Aux)), L);
3858 end if;
3860 Pop_Scope;
3861 end if;
3862 end Insert_Library_Level_Actions;
3864 ----------------------
3865 -- Inside_Init_Proc --
3866 ----------------------
3868 function Inside_Init_Proc return Boolean is
3869 S : Entity_Id;
3871 begin
3872 S := Current_Scope;
3873 while Present (S) and then S /= Standard_Standard loop
3874 if Is_Init_Proc (S) then
3875 return True;
3876 else
3877 S := Scope (S);
3878 end if;
3879 end loop;
3881 return False;
3882 end Inside_Init_Proc;
3884 ----------------------------
3885 -- Is_All_Null_Statements --
3886 ----------------------------
3888 function Is_All_Null_Statements (L : List_Id) return Boolean is
3889 Stm : Node_Id;
3891 begin
3892 Stm := First (L);
3893 while Present (Stm) loop
3894 if Nkind (Stm) /= N_Null_Statement then
3895 return False;
3896 end if;
3898 Next (Stm);
3899 end loop;
3901 return True;
3902 end Is_All_Null_Statements;
3904 --------------------------------------------------
3905 -- Is_Displacement_Of_Object_Or_Function_Result --
3906 --------------------------------------------------
3908 function Is_Displacement_Of_Object_Or_Function_Result
3909 (Obj_Id : Entity_Id) return Boolean
3911 function Is_Controlled_Function_Call (N : Node_Id) return Boolean;
3912 -- Determine if particular node denotes a controlled function call
3914 function Is_Displace_Call (N : Node_Id) return Boolean;
3915 -- Determine whether a particular node is a call to Ada.Tags.Displace.
3916 -- The call might be nested within other actions such as conversions.
3918 function Is_Source_Object (N : Node_Id) return Boolean;
3919 -- Determine whether a particular node denotes a source object
3921 ---------------------------------
3922 -- Is_Controlled_Function_Call --
3923 ---------------------------------
3925 function Is_Controlled_Function_Call (N : Node_Id) return Boolean is
3926 Expr : Node_Id := Original_Node (N);
3928 begin
3929 if Nkind (Expr) = N_Function_Call then
3930 Expr := Name (Expr);
3931 end if;
3933 -- The function call may appear in object.operation format
3935 if Nkind (Expr) = N_Selected_Component then
3936 Expr := Selector_Name (Expr);
3937 end if;
3939 return
3940 Nkind_In (Expr, N_Expanded_Name, N_Identifier)
3941 and then Ekind (Entity (Expr)) = E_Function
3942 and then Needs_Finalization (Etype (Entity (Expr)));
3943 end Is_Controlled_Function_Call;
3945 ----------------------
3946 -- Is_Displace_Call --
3947 ----------------------
3949 function Is_Displace_Call (N : Node_Id) return Boolean is
3950 Call : Node_Id := N;
3952 begin
3953 -- Strip various actions which may precede a call to Displace
3955 loop
3956 if Nkind (Call) = N_Explicit_Dereference then
3957 Call := Prefix (Call);
3959 elsif Nkind_In (Call, N_Type_Conversion,
3960 N_Unchecked_Type_Conversion)
3961 then
3962 Call := Expression (Call);
3964 else
3965 exit;
3966 end if;
3967 end loop;
3969 return
3970 Present (Call)
3971 and then Nkind (Call) = N_Function_Call
3972 and then Is_RTE (Entity (Name (Call)), RE_Displace);
3973 end Is_Displace_Call;
3975 ----------------------
3976 -- Is_Source_Object --
3977 ----------------------
3979 function Is_Source_Object (N : Node_Id) return Boolean is
3980 begin
3981 return
3982 Present (N)
3983 and then Nkind (N) in N_Has_Entity
3984 and then Is_Object (Entity (N))
3985 and then Comes_From_Source (N);
3986 end Is_Source_Object;
3988 -- Local variables
3990 Decl : constant Node_Id := Parent (Obj_Id);
3991 Obj_Typ : constant Entity_Id := Base_Type (Etype (Obj_Id));
3992 Orig_Decl : constant Node_Id := Original_Node (Decl);
3994 -- Start of processing for Is_Displacement_Of_Object_Or_Function_Result
3996 begin
3997 -- Case 1:
3999 -- Obj : CW_Type := Function_Call (...);
4001 -- rewritten into:
4003 -- Tmp : ... := Function_Call (...)'reference;
4004 -- Obj : CW_Type renames (... Ada.Tags.Displace (Tmp));
4006 -- where the return type of the function and the class-wide type require
4007 -- dispatch table pointer displacement.
4009 -- Case 2:
4011 -- Obj : CW_Type := Src_Obj;
4013 -- rewritten into:
4015 -- Obj : CW_Type renames (... Ada.Tags.Displace (Src_Obj));
4017 -- where the type of the source object and the class-wide type require
4018 -- dispatch table pointer displacement.
4020 return
4021 Nkind (Decl) = N_Object_Renaming_Declaration
4022 and then Nkind (Orig_Decl) = N_Object_Declaration
4023 and then Comes_From_Source (Orig_Decl)
4024 and then Is_Class_Wide_Type (Obj_Typ)
4025 and then Is_Displace_Call (Renamed_Object (Obj_Id))
4026 and then
4027 (Is_Controlled_Function_Call (Expression (Orig_Decl))
4028 or else Is_Source_Object (Expression (Orig_Decl)));
4029 end Is_Displacement_Of_Object_Or_Function_Result;
4031 ------------------------------
4032 -- Is_Finalizable_Transient --
4033 ------------------------------
4035 function Is_Finalizable_Transient
4036 (Decl : Node_Id;
4037 Rel_Node : Node_Id) return Boolean
4039 Obj_Id : constant Entity_Id := Defining_Identifier (Decl);
4040 Obj_Typ : constant Entity_Id := Base_Type (Etype (Obj_Id));
4041 Desig : Entity_Id := Obj_Typ;
4043 function Initialized_By_Access (Trans_Id : Entity_Id) return Boolean;
4044 -- Determine whether transient object Trans_Id is initialized either
4045 -- by a function call which returns an access type or simply renames
4046 -- another pointer.
4048 function Initialized_By_Aliased_BIP_Func_Call
4049 (Trans_Id : Entity_Id) return Boolean;
4050 -- Determine whether transient object Trans_Id is initialized by a
4051 -- build-in-place function call where the BIPalloc parameter is of
4052 -- value 1 and BIPaccess is not null. This case creates an aliasing
4053 -- between the returned value and the value denoted by BIPaccess.
4055 function Is_Aliased
4056 (Trans_Id : Entity_Id;
4057 First_Stmt : Node_Id) return Boolean;
4058 -- Determine whether transient object Trans_Id has been renamed or
4059 -- aliased through 'reference in the statement list starting from
4060 -- First_Stmt.
4062 function Is_Allocated (Trans_Id : Entity_Id) return Boolean;
4063 -- Determine whether transient object Trans_Id is allocated on the heap
4065 function Is_Iterated_Container
4066 (Trans_Id : Entity_Id;
4067 First_Stmt : Node_Id) return Boolean;
4068 -- Determine whether transient object Trans_Id denotes a container which
4069 -- is in the process of being iterated in the statement list starting
4070 -- from First_Stmt.
4072 ---------------------------
4073 -- Initialized_By_Access --
4074 ---------------------------
4076 function Initialized_By_Access (Trans_Id : Entity_Id) return Boolean is
4077 Expr : constant Node_Id := Expression (Parent (Trans_Id));
4079 begin
4080 return
4081 Present (Expr)
4082 and then Nkind (Expr) /= N_Reference
4083 and then Is_Access_Type (Etype (Expr));
4084 end Initialized_By_Access;
4086 ------------------------------------------
4087 -- Initialized_By_Aliased_BIP_Func_Call --
4088 ------------------------------------------
4090 function Initialized_By_Aliased_BIP_Func_Call
4091 (Trans_Id : Entity_Id) return Boolean
4093 Call : Node_Id := Expression (Parent (Trans_Id));
4095 begin
4096 -- Build-in-place calls usually appear in 'reference format
4098 if Nkind (Call) = N_Reference then
4099 Call := Prefix (Call);
4100 end if;
4102 if Is_Build_In_Place_Function_Call (Call) then
4103 declare
4104 Access_Nam : Name_Id := No_Name;
4105 Access_OK : Boolean := False;
4106 Actual : Node_Id;
4107 Alloc_Nam : Name_Id := No_Name;
4108 Alloc_OK : Boolean := False;
4109 Formal : Node_Id;
4110 Func_Id : Entity_Id;
4111 Param : Node_Id;
4113 begin
4114 -- Examine all parameter associations of the function call
4116 Param := First (Parameter_Associations (Call));
4117 while Present (Param) loop
4118 if Nkind (Param) = N_Parameter_Association
4119 and then Nkind (Selector_Name (Param)) = N_Identifier
4120 then
4121 Actual := Explicit_Actual_Parameter (Param);
4122 Formal := Selector_Name (Param);
4124 -- Construct the names of formals BIPaccess and BIPalloc
4125 -- using the function name retrieved from an arbitrary
4126 -- formal.
4128 if Access_Nam = No_Name
4129 and then Alloc_Nam = No_Name
4130 and then Present (Entity (Formal))
4131 then
4132 Func_Id := Scope (Entity (Formal));
4134 Access_Nam :=
4135 New_External_Name (Chars (Func_Id),
4136 BIP_Formal_Suffix (BIP_Object_Access));
4138 Alloc_Nam :=
4139 New_External_Name (Chars (Func_Id),
4140 BIP_Formal_Suffix (BIP_Alloc_Form));
4141 end if;
4143 -- A match for BIPaccess => Temp has been found
4145 if Chars (Formal) = Access_Nam
4146 and then Nkind (Actual) /= N_Null
4147 then
4148 Access_OK := True;
4149 end if;
4151 -- A match for BIPalloc => 1 has been found
4153 if Chars (Formal) = Alloc_Nam
4154 and then Nkind (Actual) = N_Integer_Literal
4155 and then Intval (Actual) = Uint_1
4156 then
4157 Alloc_OK := True;
4158 end if;
4159 end if;
4161 Next (Param);
4162 end loop;
4164 return Access_OK and Alloc_OK;
4165 end;
4166 end if;
4168 return False;
4169 end Initialized_By_Aliased_BIP_Func_Call;
4171 ----------------
4172 -- Is_Aliased --
4173 ----------------
4175 function Is_Aliased
4176 (Trans_Id : Entity_Id;
4177 First_Stmt : Node_Id) return Boolean
4179 function Find_Renamed_Object (Ren_Decl : Node_Id) return Entity_Id;
4180 -- Given an object renaming declaration, retrieve the entity of the
4181 -- renamed name. Return Empty if the renamed name is anything other
4182 -- than a variable or a constant.
4184 -------------------------
4185 -- Find_Renamed_Object --
4186 -------------------------
4188 function Find_Renamed_Object (Ren_Decl : Node_Id) return Entity_Id is
4189 Ren_Obj : Node_Id := Empty;
4191 function Find_Object (N : Node_Id) return Traverse_Result;
4192 -- Try to detect an object which is either a constant or a
4193 -- variable.
4195 -----------------
4196 -- Find_Object --
4197 -----------------
4199 function Find_Object (N : Node_Id) return Traverse_Result is
4200 begin
4201 -- Stop the search once a constant or a variable has been
4202 -- detected.
4204 if Nkind (N) = N_Identifier
4205 and then Present (Entity (N))
4206 and then Ekind_In (Entity (N), E_Constant, E_Variable)
4207 then
4208 Ren_Obj := Entity (N);
4209 return Abandon;
4210 end if;
4212 return OK;
4213 end Find_Object;
4215 procedure Search is new Traverse_Proc (Find_Object);
4217 -- Local variables
4219 Typ : constant Entity_Id := Etype (Defining_Identifier (Ren_Decl));
4221 -- Start of processing for Find_Renamed_Object
4223 begin
4224 -- Actions related to dispatching calls may appear as renamings of
4225 -- tags. Do not process this type of renaming because it does not
4226 -- use the actual value of the object.
4228 if not Is_RTE (Typ, RE_Tag_Ptr) then
4229 Search (Name (Ren_Decl));
4230 end if;
4232 return Ren_Obj;
4233 end Find_Renamed_Object;
4235 -- Local variables
4237 Expr : Node_Id;
4238 Ren_Obj : Entity_Id;
4239 Stmt : Node_Id;
4241 -- Start of processing for Is_Aliased
4243 begin
4244 Stmt := First_Stmt;
4245 while Present (Stmt) loop
4246 if Nkind (Stmt) = N_Object_Declaration then
4247 Expr := Expression (Stmt);
4249 if Present (Expr)
4250 and then Nkind (Expr) = N_Reference
4251 and then Nkind (Prefix (Expr)) = N_Identifier
4252 and then Entity (Prefix (Expr)) = Trans_Id
4253 then
4254 return True;
4255 end if;
4257 elsif Nkind (Stmt) = N_Object_Renaming_Declaration then
4258 Ren_Obj := Find_Renamed_Object (Stmt);
4260 if Present (Ren_Obj) and then Ren_Obj = Trans_Id then
4261 return True;
4262 end if;
4263 end if;
4265 Next (Stmt);
4266 end loop;
4268 return False;
4269 end Is_Aliased;
4271 ------------------
4272 -- Is_Allocated --
4273 ------------------
4275 function Is_Allocated (Trans_Id : Entity_Id) return Boolean is
4276 Expr : constant Node_Id := Expression (Parent (Trans_Id));
4277 begin
4278 return
4279 Is_Access_Type (Etype (Trans_Id))
4280 and then Present (Expr)
4281 and then Nkind (Expr) = N_Allocator;
4282 end Is_Allocated;
4284 ---------------------------
4285 -- Is_Iterated_Container --
4286 ---------------------------
4288 function Is_Iterated_Container
4289 (Trans_Id : Entity_Id;
4290 First_Stmt : Node_Id) return Boolean
4292 Aspect : Node_Id;
4293 Call : Node_Id;
4294 Iter : Entity_Id;
4295 Param : Node_Id;
4296 Stmt : Node_Id;
4297 Typ : Entity_Id;
4299 begin
4300 -- It is not possible to iterate over containers in non-Ada 2012 code
4302 if Ada_Version < Ada_2012 then
4303 return False;
4304 end if;
4306 Typ := Etype (Trans_Id);
4308 -- Handle access type created for secondary stack use
4310 if Is_Access_Type (Typ) then
4311 Typ := Designated_Type (Typ);
4312 end if;
4314 -- Look for aspect Default_Iterator
4316 if Has_Aspects (Parent (Typ)) then
4317 Aspect := Find_Value_Of_Aspect (Typ, Aspect_Default_Iterator);
4319 if Present (Aspect) then
4320 Iter := Entity (Aspect);
4322 -- Examine the statements following the container object and
4323 -- look for a call to the default iterate routine where the
4324 -- first parameter is the transient. Such a call appears as:
4326 -- It : Access_To_CW_Iterator :=
4327 -- Iterate (Tran_Id.all, ...)'reference;
4329 Stmt := First_Stmt;
4330 while Present (Stmt) loop
4332 -- Detect an object declaration which is initialized by a
4333 -- secondary stack function call.
4335 if Nkind (Stmt) = N_Object_Declaration
4336 and then Present (Expression (Stmt))
4337 and then Nkind (Expression (Stmt)) = N_Reference
4338 and then Nkind (Prefix (Expression (Stmt))) =
4339 N_Function_Call
4340 then
4341 Call := Prefix (Expression (Stmt));
4343 -- The call must invoke the default iterate routine of
4344 -- the container and the transient object must appear as
4345 -- the first actual parameter. Skip any calls whose names
4346 -- are not entities.
4348 if Is_Entity_Name (Name (Call))
4349 and then Entity (Name (Call)) = Iter
4350 and then Present (Parameter_Associations (Call))
4351 then
4352 Param := First (Parameter_Associations (Call));
4354 if Nkind (Param) = N_Explicit_Dereference
4355 and then Entity (Prefix (Param)) = Trans_Id
4356 then
4357 return True;
4358 end if;
4359 end if;
4360 end if;
4362 Next (Stmt);
4363 end loop;
4364 end if;
4365 end if;
4367 return False;
4368 end Is_Iterated_Container;
4370 -- Start of processing for Is_Finalizable_Transient
4372 begin
4373 -- Handle access types
4375 if Is_Access_Type (Desig) then
4376 Desig := Available_View (Designated_Type (Desig));
4377 end if;
4379 return
4380 Ekind_In (Obj_Id, E_Constant, E_Variable)
4381 and then Needs_Finalization (Desig)
4382 and then Requires_Transient_Scope (Desig)
4383 and then Nkind (Rel_Node) /= N_Simple_Return_Statement
4385 -- Do not consider renamed or 'reference-d transient objects because
4386 -- the act of renaming extends the object's lifetime.
4388 and then not Is_Aliased (Obj_Id, Decl)
4390 -- Do not consider transient objects allocated on the heap since
4391 -- they are attached to a finalization master.
4393 and then not Is_Allocated (Obj_Id)
4395 -- If the transient object is a pointer, check that it is not
4396 -- initialized by a function which returns a pointer or acts as a
4397 -- renaming of another pointer.
4399 and then
4400 (not Is_Access_Type (Obj_Typ)
4401 or else not Initialized_By_Access (Obj_Id))
4403 -- Do not consider transient objects which act as indirect aliases
4404 -- of build-in-place function results.
4406 and then not Initialized_By_Aliased_BIP_Func_Call (Obj_Id)
4408 -- Do not consider conversions of tags to class-wide types
4410 and then not Is_Tag_To_Class_Wide_Conversion (Obj_Id)
4412 -- Do not consider containers in the context of iterator loops. Such
4413 -- transient objects must exist for as long as the loop is around,
4414 -- otherwise any operation carried out by the iterator will fail.
4416 and then not Is_Iterated_Container (Obj_Id, Decl);
4417 end Is_Finalizable_Transient;
4419 ---------------------------------
4420 -- Is_Fully_Repped_Tagged_Type --
4421 ---------------------------------
4423 function Is_Fully_Repped_Tagged_Type (T : Entity_Id) return Boolean is
4424 U : constant Entity_Id := Underlying_Type (T);
4425 Comp : Entity_Id;
4427 begin
4428 if No (U) or else not Is_Tagged_Type (U) then
4429 return False;
4430 elsif Has_Discriminants (U) then
4431 return False;
4432 elsif not Has_Specified_Layout (U) then
4433 return False;
4434 end if;
4436 -- Here we have a tagged type, see if it has any unlayed out fields
4437 -- other than a possible tag and parent fields. If so, we return False.
4439 Comp := First_Component (U);
4440 while Present (Comp) loop
4441 if not Is_Tag (Comp)
4442 and then Chars (Comp) /= Name_uParent
4443 and then No (Component_Clause (Comp))
4444 then
4445 return False;
4446 else
4447 Next_Component (Comp);
4448 end if;
4449 end loop;
4451 -- All components are layed out
4453 return True;
4454 end Is_Fully_Repped_Tagged_Type;
4456 ----------------------------------
4457 -- Is_Library_Level_Tagged_Type --
4458 ----------------------------------
4460 function Is_Library_Level_Tagged_Type (Typ : Entity_Id) return Boolean is
4461 begin
4462 return Is_Tagged_Type (Typ) and then Is_Library_Level_Entity (Typ);
4463 end Is_Library_Level_Tagged_Type;
4465 --------------------------
4466 -- Is_Non_BIP_Func_Call --
4467 --------------------------
4469 function Is_Non_BIP_Func_Call (Expr : Node_Id) return Boolean is
4470 begin
4471 -- The expected call is of the format
4473 -- Func_Call'reference
4475 return
4476 Nkind (Expr) = N_Reference
4477 and then Nkind (Prefix (Expr)) = N_Function_Call
4478 and then not Is_Build_In_Place_Function_Call (Prefix (Expr));
4479 end Is_Non_BIP_Func_Call;
4481 ----------------------------------
4482 -- Is_Possibly_Unaligned_Object --
4483 ----------------------------------
4485 function Is_Possibly_Unaligned_Object (N : Node_Id) return Boolean is
4486 T : constant Entity_Id := Etype (N);
4488 begin
4489 -- If renamed object, apply test to underlying object
4491 if Is_Entity_Name (N)
4492 and then Is_Object (Entity (N))
4493 and then Present (Renamed_Object (Entity (N)))
4494 then
4495 return Is_Possibly_Unaligned_Object (Renamed_Object (Entity (N)));
4496 end if;
4498 -- Tagged and controlled types and aliased types are always aligned, as
4499 -- are concurrent types.
4501 if Is_Aliased (T)
4502 or else Has_Controlled_Component (T)
4503 or else Is_Concurrent_Type (T)
4504 or else Is_Tagged_Type (T)
4505 or else Is_Controlled (T)
4506 then
4507 return False;
4508 end if;
4510 -- If this is an element of a packed array, may be unaligned
4512 if Is_Ref_To_Bit_Packed_Array (N) then
4513 return True;
4514 end if;
4516 -- Case of indexed component reference: test whether prefix is unaligned
4518 if Nkind (N) = N_Indexed_Component then
4519 return Is_Possibly_Unaligned_Object (Prefix (N));
4521 -- Case of selected component reference
4523 elsif Nkind (N) = N_Selected_Component then
4524 declare
4525 P : constant Node_Id := Prefix (N);
4526 C : constant Entity_Id := Entity (Selector_Name (N));
4527 M : Nat;
4528 S : Nat;
4530 begin
4531 -- If component reference is for an array with non-static bounds,
4532 -- then it is always aligned: we can only process unaligned arrays
4533 -- with static bounds (more precisely compile time known bounds).
4535 if Is_Array_Type (T)
4536 and then not Compile_Time_Known_Bounds (T)
4537 then
4538 return False;
4539 end if;
4541 -- If component is aliased, it is definitely properly aligned
4543 if Is_Aliased (C) then
4544 return False;
4545 end if;
4547 -- If component is for a type implemented as a scalar, and the
4548 -- record is packed, and the component is other than the first
4549 -- component of the record, then the component may be unaligned.
4551 if Is_Packed (Etype (P))
4552 and then Represented_As_Scalar (Etype (C))
4553 and then First_Entity (Scope (C)) /= C
4554 then
4555 return True;
4556 end if;
4558 -- Compute maximum possible alignment for T
4560 -- If alignment is known, then that settles things
4562 if Known_Alignment (T) then
4563 M := UI_To_Int (Alignment (T));
4565 -- If alignment is not known, tentatively set max alignment
4567 else
4568 M := Ttypes.Maximum_Alignment;
4570 -- We can reduce this if the Esize is known since the default
4571 -- alignment will never be more than the smallest power of 2
4572 -- that does not exceed this Esize value.
4574 if Known_Esize (T) then
4575 S := UI_To_Int (Esize (T));
4577 while (M / 2) >= S loop
4578 M := M / 2;
4579 end loop;
4580 end if;
4581 end if;
4583 -- The following code is historical, it used to be present but it
4584 -- is too cautious, because the front-end does not know the proper
4585 -- default alignments for the target. Also, if the alignment is
4586 -- not known, the front end can't know in any case! If a copy is
4587 -- needed, the back-end will take care of it. This whole section
4588 -- including this comment can be removed later ???
4590 -- If the component reference is for a record that has a specified
4591 -- alignment, and we either know it is too small, or cannot tell,
4592 -- then the component may be unaligned.
4594 -- What is the following commented out code ???
4596 -- if Known_Alignment (Etype (P))
4597 -- and then Alignment (Etype (P)) < Ttypes.Maximum_Alignment
4598 -- and then M > Alignment (Etype (P))
4599 -- then
4600 -- return True;
4601 -- end if;
4603 -- Case of component clause present which may specify an
4604 -- unaligned position.
4606 if Present (Component_Clause (C)) then
4608 -- Otherwise we can do a test to make sure that the actual
4609 -- start position in the record, and the length, are both
4610 -- consistent with the required alignment. If not, we know
4611 -- that we are unaligned.
4613 declare
4614 Align_In_Bits : constant Nat := M * System_Storage_Unit;
4615 begin
4616 if Component_Bit_Offset (C) mod Align_In_Bits /= 0
4617 or else Esize (C) mod Align_In_Bits /= 0
4618 then
4619 return True;
4620 end if;
4621 end;
4622 end if;
4624 -- Otherwise, for a component reference, test prefix
4626 return Is_Possibly_Unaligned_Object (P);
4627 end;
4629 -- If not a component reference, must be aligned
4631 else
4632 return False;
4633 end if;
4634 end Is_Possibly_Unaligned_Object;
4636 ---------------------------------
4637 -- Is_Possibly_Unaligned_Slice --
4638 ---------------------------------
4640 function Is_Possibly_Unaligned_Slice (N : Node_Id) return Boolean is
4641 begin
4642 -- Go to renamed object
4644 if Is_Entity_Name (N)
4645 and then Is_Object (Entity (N))
4646 and then Present (Renamed_Object (Entity (N)))
4647 then
4648 return Is_Possibly_Unaligned_Slice (Renamed_Object (Entity (N)));
4649 end if;
4651 -- The reference must be a slice
4653 if Nkind (N) /= N_Slice then
4654 return False;
4655 end if;
4657 -- Always assume the worst for a nested record component with a
4658 -- component clause, which gigi/gcc does not appear to handle well.
4659 -- It is not clear why this special test is needed at all ???
4661 if Nkind (Prefix (N)) = N_Selected_Component
4662 and then Nkind (Prefix (Prefix (N))) = N_Selected_Component
4663 and then
4664 Present (Component_Clause (Entity (Selector_Name (Prefix (N)))))
4665 then
4666 return True;
4667 end if;
4669 -- We only need to worry if the target has strict alignment
4671 if not Target_Strict_Alignment then
4672 return False;
4673 end if;
4675 -- If it is a slice, then look at the array type being sliced
4677 declare
4678 Sarr : constant Node_Id := Prefix (N);
4679 -- Prefix of the slice, i.e. the array being sliced
4681 Styp : constant Entity_Id := Etype (Prefix (N));
4682 -- Type of the array being sliced
4684 Pref : Node_Id;
4685 Ptyp : Entity_Id;
4687 begin
4688 -- The problems arise if the array object that is being sliced
4689 -- is a component of a record or array, and we cannot guarantee
4690 -- the alignment of the array within its containing object.
4692 -- To investigate this, we look at successive prefixes to see
4693 -- if we have a worrisome indexed or selected component.
4695 Pref := Sarr;
4696 loop
4697 -- Case of array is part of an indexed component reference
4699 if Nkind (Pref) = N_Indexed_Component then
4700 Ptyp := Etype (Prefix (Pref));
4702 -- The only problematic case is when the array is packed, in
4703 -- which case we really know nothing about the alignment of
4704 -- individual components.
4706 if Is_Bit_Packed_Array (Ptyp) then
4707 return True;
4708 end if;
4710 -- Case of array is part of a selected component reference
4712 elsif Nkind (Pref) = N_Selected_Component then
4713 Ptyp := Etype (Prefix (Pref));
4715 -- We are definitely in trouble if the record in question
4716 -- has an alignment, and either we know this alignment is
4717 -- inconsistent with the alignment of the slice, or we don't
4718 -- know what the alignment of the slice should be.
4720 if Known_Alignment (Ptyp)
4721 and then (Unknown_Alignment (Styp)
4722 or else Alignment (Styp) > Alignment (Ptyp))
4723 then
4724 return True;
4725 end if;
4727 -- We are in potential trouble if the record type is packed.
4728 -- We could special case when we know that the array is the
4729 -- first component, but that's not such a simple case ???
4731 if Is_Packed (Ptyp) then
4732 return True;
4733 end if;
4735 -- We are in trouble if there is a component clause, and
4736 -- either we do not know the alignment of the slice, or
4737 -- the alignment of the slice is inconsistent with the
4738 -- bit position specified by the component clause.
4740 declare
4741 Field : constant Entity_Id := Entity (Selector_Name (Pref));
4742 begin
4743 if Present (Component_Clause (Field))
4744 and then
4745 (Unknown_Alignment (Styp)
4746 or else
4747 (Component_Bit_Offset (Field) mod
4748 (System_Storage_Unit * Alignment (Styp))) /= 0)
4749 then
4750 return True;
4751 end if;
4752 end;
4754 -- For cases other than selected or indexed components we know we
4755 -- are OK, since no issues arise over alignment.
4757 else
4758 return False;
4759 end if;
4761 -- We processed an indexed component or selected component
4762 -- reference that looked safe, so keep checking prefixes.
4764 Pref := Prefix (Pref);
4765 end loop;
4766 end;
4767 end Is_Possibly_Unaligned_Slice;
4769 -------------------------------
4770 -- Is_Related_To_Func_Return --
4771 -------------------------------
4773 function Is_Related_To_Func_Return (Id : Entity_Id) return Boolean is
4774 Expr : constant Node_Id := Related_Expression (Id);
4775 begin
4776 return
4777 Present (Expr)
4778 and then Nkind (Expr) = N_Explicit_Dereference
4779 and then Nkind (Parent (Expr)) = N_Simple_Return_Statement;
4780 end Is_Related_To_Func_Return;
4782 --------------------------------
4783 -- Is_Ref_To_Bit_Packed_Array --
4784 --------------------------------
4786 function Is_Ref_To_Bit_Packed_Array (N : Node_Id) return Boolean is
4787 Result : Boolean;
4788 Expr : Node_Id;
4790 begin
4791 if Is_Entity_Name (N)
4792 and then Is_Object (Entity (N))
4793 and then Present (Renamed_Object (Entity (N)))
4794 then
4795 return Is_Ref_To_Bit_Packed_Array (Renamed_Object (Entity (N)));
4796 end if;
4798 if Nkind_In (N, N_Indexed_Component, N_Selected_Component) then
4799 if Is_Bit_Packed_Array (Etype (Prefix (N))) then
4800 Result := True;
4801 else
4802 Result := Is_Ref_To_Bit_Packed_Array (Prefix (N));
4803 end if;
4805 if Result and then Nkind (N) = N_Indexed_Component then
4806 Expr := First (Expressions (N));
4807 while Present (Expr) loop
4808 Force_Evaluation (Expr);
4809 Next (Expr);
4810 end loop;
4811 end if;
4813 return Result;
4815 else
4816 return False;
4817 end if;
4818 end Is_Ref_To_Bit_Packed_Array;
4820 --------------------------------
4821 -- Is_Ref_To_Bit_Packed_Slice --
4822 --------------------------------
4824 function Is_Ref_To_Bit_Packed_Slice (N : Node_Id) return Boolean is
4825 begin
4826 if Nkind (N) = N_Type_Conversion then
4827 return Is_Ref_To_Bit_Packed_Slice (Expression (N));
4829 elsif Is_Entity_Name (N)
4830 and then Is_Object (Entity (N))
4831 and then Present (Renamed_Object (Entity (N)))
4832 then
4833 return Is_Ref_To_Bit_Packed_Slice (Renamed_Object (Entity (N)));
4835 elsif Nkind (N) = N_Slice
4836 and then Is_Bit_Packed_Array (Etype (Prefix (N)))
4837 then
4838 return True;
4840 elsif Nkind_In (N, N_Indexed_Component, N_Selected_Component) then
4841 return Is_Ref_To_Bit_Packed_Slice (Prefix (N));
4843 else
4844 return False;
4845 end if;
4846 end Is_Ref_To_Bit_Packed_Slice;
4848 -----------------------
4849 -- Is_Renamed_Object --
4850 -----------------------
4852 function Is_Renamed_Object (N : Node_Id) return Boolean is
4853 Pnod : constant Node_Id := Parent (N);
4854 Kind : constant Node_Kind := Nkind (Pnod);
4855 begin
4856 if Kind = N_Object_Renaming_Declaration then
4857 return True;
4858 elsif Nkind_In (Kind, N_Indexed_Component, N_Selected_Component) then
4859 return Is_Renamed_Object (Pnod);
4860 else
4861 return False;
4862 end if;
4863 end Is_Renamed_Object;
4865 --------------------------------------
4866 -- Is_Secondary_Stack_BIP_Func_Call --
4867 --------------------------------------
4869 function Is_Secondary_Stack_BIP_Func_Call (Expr : Node_Id) return Boolean is
4870 Call : Node_Id := Expr;
4872 begin
4873 -- Build-in-place calls usually appear in 'reference format. Note that
4874 -- the accessibility check machinery may add an extra 'reference due to
4875 -- side effect removal.
4877 while Nkind (Call) = N_Reference loop
4878 Call := Prefix (Call);
4879 end loop;
4881 if Nkind_In (Call, N_Qualified_Expression,
4882 N_Unchecked_Type_Conversion)
4883 then
4884 Call := Expression (Call);
4885 end if;
4887 if Is_Build_In_Place_Function_Call (Call) then
4888 declare
4889 Access_Nam : Name_Id := No_Name;
4890 Actual : Node_Id;
4891 Param : Node_Id;
4892 Formal : Node_Id;
4894 begin
4895 -- Examine all parameter associations of the function call
4897 Param := First (Parameter_Associations (Call));
4898 while Present (Param) loop
4899 if Nkind (Param) = N_Parameter_Association
4900 and then Nkind (Selector_Name (Param)) = N_Identifier
4901 then
4902 Formal := Selector_Name (Param);
4903 Actual := Explicit_Actual_Parameter (Param);
4905 -- Construct the name of formal BIPalloc. It is much easier
4906 -- to extract the name of the function using an arbitrary
4907 -- formal's scope rather than the Name field of Call.
4909 if Access_Nam = No_Name
4910 and then Present (Entity (Formal))
4911 then
4912 Access_Nam :=
4913 New_External_Name
4914 (Chars (Scope (Entity (Formal))),
4915 BIP_Formal_Suffix (BIP_Alloc_Form));
4916 end if;
4918 -- A match for BIPalloc => 2 has been found
4920 if Chars (Formal) = Access_Nam
4921 and then Nkind (Actual) = N_Integer_Literal
4922 and then Intval (Actual) = Uint_2
4923 then
4924 return True;
4925 end if;
4926 end if;
4928 Next (Param);
4929 end loop;
4930 end;
4931 end if;
4933 return False;
4934 end Is_Secondary_Stack_BIP_Func_Call;
4936 -------------------------------------
4937 -- Is_Tag_To_Class_Wide_Conversion --
4938 -------------------------------------
4940 function Is_Tag_To_Class_Wide_Conversion
4941 (Obj_Id : Entity_Id) return Boolean
4943 Expr : constant Node_Id := Expression (Parent (Obj_Id));
4945 begin
4946 return
4947 Is_Class_Wide_Type (Etype (Obj_Id))
4948 and then Present (Expr)
4949 and then Nkind (Expr) = N_Unchecked_Type_Conversion
4950 and then Etype (Expression (Expr)) = RTE (RE_Tag);
4951 end Is_Tag_To_Class_Wide_Conversion;
4953 ----------------------------
4954 -- Is_Untagged_Derivation --
4955 ----------------------------
4957 function Is_Untagged_Derivation (T : Entity_Id) return Boolean is
4958 begin
4959 return (not Is_Tagged_Type (T) and then Is_Derived_Type (T))
4960 or else
4961 (Is_Private_Type (T) and then Present (Full_View (T))
4962 and then not Is_Tagged_Type (Full_View (T))
4963 and then Is_Derived_Type (Full_View (T))
4964 and then Etype (Full_View (T)) /= T);
4965 end Is_Untagged_Derivation;
4967 ---------------------------
4968 -- Is_Volatile_Reference --
4969 ---------------------------
4971 function Is_Volatile_Reference (N : Node_Id) return Boolean is
4972 begin
4973 if Nkind (N) in N_Has_Etype
4974 and then Present (Etype (N))
4975 and then Treat_As_Volatile (Etype (N))
4976 then
4977 return True;
4979 elsif Is_Entity_Name (N) then
4980 return Treat_As_Volatile (Entity (N));
4982 elsif Nkind (N) = N_Slice then
4983 return Is_Volatile_Reference (Prefix (N));
4985 elsif Nkind_In (N, N_Indexed_Component, N_Selected_Component) then
4986 if (Is_Entity_Name (Prefix (N))
4987 and then Has_Volatile_Components (Entity (Prefix (N))))
4988 or else (Present (Etype (Prefix (N)))
4989 and then Has_Volatile_Components (Etype (Prefix (N))))
4990 then
4991 return True;
4992 else
4993 return Is_Volatile_Reference (Prefix (N));
4994 end if;
4996 else
4997 return False;
4998 end if;
4999 end Is_Volatile_Reference;
5001 --------------------------
5002 -- Is_VM_By_Copy_Actual --
5003 --------------------------
5005 function Is_VM_By_Copy_Actual (N : Node_Id) return Boolean is
5006 begin
5007 return VM_Target /= No_VM
5008 and then (Nkind (N) = N_Slice
5009 or else
5010 (Nkind (N) = N_Identifier
5011 and then Present (Renamed_Object (Entity (N)))
5012 and then Nkind (Renamed_Object (Entity (N))) =
5013 N_Slice));
5014 end Is_VM_By_Copy_Actual;
5016 --------------------
5017 -- Kill_Dead_Code --
5018 --------------------
5020 procedure Kill_Dead_Code (N : Node_Id; Warn : Boolean := False) is
5021 W : Boolean := Warn;
5022 -- Set False if warnings suppressed
5024 begin
5025 if Present (N) then
5026 Remove_Warning_Messages (N);
5028 -- Generate warning if appropriate
5030 if W then
5032 -- We suppress the warning if this code is under control of an
5033 -- if statement, whose condition is a simple identifier, and
5034 -- either we are in an instance, or warnings off is set for this
5035 -- identifier. The reason for killing it in the instance case is
5036 -- that it is common and reasonable for code to be deleted in
5037 -- instances for various reasons.
5039 if Nkind (Parent (N)) = N_If_Statement then
5040 declare
5041 C : constant Node_Id := Condition (Parent (N));
5042 begin
5043 if Nkind (C) = N_Identifier
5044 and then
5045 (In_Instance
5046 or else (Present (Entity (C))
5047 and then Has_Warnings_Off (Entity (C))))
5048 then
5049 W := False;
5050 end if;
5051 end;
5052 end if;
5054 -- Generate warning if not suppressed
5056 if W then
5057 Error_Msg_F
5058 ("?t?this code can never be executed and has been deleted!",
5060 end if;
5061 end if;
5063 -- Recurse into block statements and bodies to process declarations
5064 -- and statements.
5066 if Nkind (N) = N_Block_Statement
5067 or else Nkind (N) = N_Subprogram_Body
5068 or else Nkind (N) = N_Package_Body
5069 then
5070 Kill_Dead_Code (Declarations (N), False);
5071 Kill_Dead_Code (Statements (Handled_Statement_Sequence (N)));
5073 if Nkind (N) = N_Subprogram_Body then
5074 Set_Is_Eliminated (Defining_Entity (N));
5075 end if;
5077 elsif Nkind (N) = N_Package_Declaration then
5078 Kill_Dead_Code (Visible_Declarations (Specification (N)));
5079 Kill_Dead_Code (Private_Declarations (Specification (N)));
5081 -- ??? After this point, Delete_Tree has been called on all
5082 -- declarations in Specification (N), so references to entities
5083 -- therein look suspicious.
5085 declare
5086 E : Entity_Id := First_Entity (Defining_Entity (N));
5087 begin
5088 while Present (E) loop
5089 if Ekind (E) = E_Operator then
5090 Set_Is_Eliminated (E);
5091 end if;
5093 Next_Entity (E);
5094 end loop;
5095 end;
5097 -- Recurse into composite statement to kill individual statements in
5098 -- particular instantiations.
5100 elsif Nkind (N) = N_If_Statement then
5101 Kill_Dead_Code (Then_Statements (N));
5102 Kill_Dead_Code (Elsif_Parts (N));
5103 Kill_Dead_Code (Else_Statements (N));
5105 elsif Nkind (N) = N_Loop_Statement then
5106 Kill_Dead_Code (Statements (N));
5108 elsif Nkind (N) = N_Case_Statement then
5109 declare
5110 Alt : Node_Id;
5111 begin
5112 Alt := First (Alternatives (N));
5113 while Present (Alt) loop
5114 Kill_Dead_Code (Statements (Alt));
5115 Next (Alt);
5116 end loop;
5117 end;
5119 elsif Nkind (N) = N_Case_Statement_Alternative then
5120 Kill_Dead_Code (Statements (N));
5122 -- Deal with dead instances caused by deleting instantiations
5124 elsif Nkind (N) in N_Generic_Instantiation then
5125 Remove_Dead_Instance (N);
5126 end if;
5127 end if;
5128 end Kill_Dead_Code;
5130 -- Case where argument is a list of nodes to be killed
5132 procedure Kill_Dead_Code (L : List_Id; Warn : Boolean := False) is
5133 N : Node_Id;
5134 W : Boolean;
5135 begin
5136 W := Warn;
5137 if Is_Non_Empty_List (L) then
5138 N := First (L);
5139 while Present (N) loop
5140 Kill_Dead_Code (N, W);
5141 W := False;
5142 Next (N);
5143 end loop;
5144 end if;
5145 end Kill_Dead_Code;
5147 ------------------------
5148 -- Known_Non_Negative --
5149 ------------------------
5151 function Known_Non_Negative (Opnd : Node_Id) return Boolean is
5152 begin
5153 if Is_OK_Static_Expression (Opnd) and then Expr_Value (Opnd) >= 0 then
5154 return True;
5156 else
5157 declare
5158 Lo : constant Node_Id := Type_Low_Bound (Etype (Opnd));
5159 begin
5160 return
5161 Is_OK_Static_Expression (Lo) and then Expr_Value (Lo) >= 0;
5162 end;
5163 end if;
5164 end Known_Non_Negative;
5166 --------------------
5167 -- Known_Non_Null --
5168 --------------------
5170 function Known_Non_Null (N : Node_Id) return Boolean is
5171 begin
5172 -- Checks for case where N is an entity reference
5174 if Is_Entity_Name (N) and then Present (Entity (N)) then
5175 declare
5176 E : constant Entity_Id := Entity (N);
5177 Op : Node_Kind;
5178 Val : Node_Id;
5180 begin
5181 -- First check if we are in decisive conditional
5183 Get_Current_Value_Condition (N, Op, Val);
5185 if Known_Null (Val) then
5186 if Op = N_Op_Eq then
5187 return False;
5188 elsif Op = N_Op_Ne then
5189 return True;
5190 end if;
5191 end if;
5193 -- If OK to do replacement, test Is_Known_Non_Null flag
5195 if OK_To_Do_Constant_Replacement (E) then
5196 return Is_Known_Non_Null (E);
5198 -- Otherwise if not safe to do replacement, then say so
5200 else
5201 return False;
5202 end if;
5203 end;
5205 -- True if access attribute
5207 elsif Nkind (N) = N_Attribute_Reference
5208 and then Nam_In (Attribute_Name (N), Name_Access,
5209 Name_Unchecked_Access,
5210 Name_Unrestricted_Access)
5211 then
5212 return True;
5214 -- True if allocator
5216 elsif Nkind (N) = N_Allocator then
5217 return True;
5219 -- For a conversion, true if expression is known non-null
5221 elsif Nkind (N) = N_Type_Conversion then
5222 return Known_Non_Null (Expression (N));
5224 -- Above are all cases where the value could be determined to be
5225 -- non-null. In all other cases, we don't know, so return False.
5227 else
5228 return False;
5229 end if;
5230 end Known_Non_Null;
5232 ----------------
5233 -- Known_Null --
5234 ----------------
5236 function Known_Null (N : Node_Id) return Boolean is
5237 begin
5238 -- Checks for case where N is an entity reference
5240 if Is_Entity_Name (N) and then Present (Entity (N)) then
5241 declare
5242 E : constant Entity_Id := Entity (N);
5243 Op : Node_Kind;
5244 Val : Node_Id;
5246 begin
5247 -- Constant null value is for sure null
5249 if Ekind (E) = E_Constant
5250 and then Known_Null (Constant_Value (E))
5251 then
5252 return True;
5253 end if;
5255 -- First check if we are in decisive conditional
5257 Get_Current_Value_Condition (N, Op, Val);
5259 if Known_Null (Val) then
5260 if Op = N_Op_Eq then
5261 return True;
5262 elsif Op = N_Op_Ne then
5263 return False;
5264 end if;
5265 end if;
5267 -- If OK to do replacement, test Is_Known_Null flag
5269 if OK_To_Do_Constant_Replacement (E) then
5270 return Is_Known_Null (E);
5272 -- Otherwise if not safe to do replacement, then say so
5274 else
5275 return False;
5276 end if;
5277 end;
5279 -- True if explicit reference to null
5281 elsif Nkind (N) = N_Null then
5282 return True;
5284 -- For a conversion, true if expression is known null
5286 elsif Nkind (N) = N_Type_Conversion then
5287 return Known_Null (Expression (N));
5289 -- Above are all cases where the value could be determined to be null.
5290 -- In all other cases, we don't know, so return False.
5292 else
5293 return False;
5294 end if;
5295 end Known_Null;
5297 -----------------------------
5298 -- Make_CW_Equivalent_Type --
5299 -----------------------------
5301 -- Create a record type used as an equivalent of any member of the class
5302 -- which takes its size from exp.
5304 -- Generate the following code:
5306 -- type Equiv_T is record
5307 -- _parent : T (List of discriminant constraints taken from Exp);
5308 -- Ext__50 : Storage_Array (1 .. (Exp'size - Typ'object_size)/8);
5309 -- end Equiv_T;
5311 -- ??? Note that this type does not guarantee same alignment as all
5312 -- derived types
5314 function Make_CW_Equivalent_Type
5315 (T : Entity_Id;
5316 E : Node_Id) return Entity_Id
5318 Loc : constant Source_Ptr := Sloc (E);
5319 Root_Typ : constant Entity_Id := Root_Type (T);
5320 List_Def : constant List_Id := Empty_List;
5321 Comp_List : constant List_Id := New_List;
5322 Equiv_Type : Entity_Id;
5323 Range_Type : Entity_Id;
5324 Str_Type : Entity_Id;
5325 Constr_Root : Entity_Id;
5326 Sizexpr : Node_Id;
5328 begin
5329 -- If the root type is already constrained, there are no discriminants
5330 -- in the expression.
5332 if not Has_Discriminants (Root_Typ)
5333 or else Is_Constrained (Root_Typ)
5334 then
5335 Constr_Root := Root_Typ;
5336 else
5337 Constr_Root := Make_Temporary (Loc, 'R');
5339 -- subtype cstr__n is T (List of discr constraints taken from Exp)
5341 Append_To (List_Def,
5342 Make_Subtype_Declaration (Loc,
5343 Defining_Identifier => Constr_Root,
5344 Subtype_Indication => Make_Subtype_From_Expr (E, Root_Typ)));
5345 end if;
5347 -- Generate the range subtype declaration
5349 Range_Type := Make_Temporary (Loc, 'G');
5351 if not Is_Interface (Root_Typ) then
5353 -- subtype rg__xx is
5354 -- Storage_Offset range 1 .. (Expr'size - typ'size) / Storage_Unit
5356 Sizexpr :=
5357 Make_Op_Subtract (Loc,
5358 Left_Opnd =>
5359 Make_Attribute_Reference (Loc,
5360 Prefix =>
5361 OK_Convert_To (T, Duplicate_Subexpr_No_Checks (E)),
5362 Attribute_Name => Name_Size),
5363 Right_Opnd =>
5364 Make_Attribute_Reference (Loc,
5365 Prefix => New_Reference_To (Constr_Root, Loc),
5366 Attribute_Name => Name_Object_Size));
5367 else
5368 -- subtype rg__xx is
5369 -- Storage_Offset range 1 .. Expr'size / Storage_Unit
5371 Sizexpr :=
5372 Make_Attribute_Reference (Loc,
5373 Prefix =>
5374 OK_Convert_To (T, Duplicate_Subexpr_No_Checks (E)),
5375 Attribute_Name => Name_Size);
5376 end if;
5378 Set_Paren_Count (Sizexpr, 1);
5380 Append_To (List_Def,
5381 Make_Subtype_Declaration (Loc,
5382 Defining_Identifier => Range_Type,
5383 Subtype_Indication =>
5384 Make_Subtype_Indication (Loc,
5385 Subtype_Mark => New_Reference_To (RTE (RE_Storage_Offset), Loc),
5386 Constraint => Make_Range_Constraint (Loc,
5387 Range_Expression =>
5388 Make_Range (Loc,
5389 Low_Bound => Make_Integer_Literal (Loc, 1),
5390 High_Bound =>
5391 Make_Op_Divide (Loc,
5392 Left_Opnd => Sizexpr,
5393 Right_Opnd => Make_Integer_Literal (Loc,
5394 Intval => System_Storage_Unit)))))));
5396 -- subtype str__nn is Storage_Array (rg__x);
5398 Str_Type := Make_Temporary (Loc, 'S');
5399 Append_To (List_Def,
5400 Make_Subtype_Declaration (Loc,
5401 Defining_Identifier => Str_Type,
5402 Subtype_Indication =>
5403 Make_Subtype_Indication (Loc,
5404 Subtype_Mark => New_Reference_To (RTE (RE_Storage_Array), Loc),
5405 Constraint =>
5406 Make_Index_Or_Discriminant_Constraint (Loc,
5407 Constraints =>
5408 New_List (New_Reference_To (Range_Type, Loc))))));
5410 -- type Equiv_T is record
5411 -- [ _parent : Tnn; ]
5412 -- E : Str_Type;
5413 -- end Equiv_T;
5415 Equiv_Type := Make_Temporary (Loc, 'T');
5416 Set_Ekind (Equiv_Type, E_Record_Type);
5417 Set_Parent_Subtype (Equiv_Type, Constr_Root);
5419 -- Set Is_Class_Wide_Equivalent_Type very early to trigger the special
5420 -- treatment for this type. In particular, even though _parent's type
5421 -- is a controlled type or contains controlled components, we do not
5422 -- want to set Has_Controlled_Component on it to avoid making it gain
5423 -- an unwanted _controller component.
5425 Set_Is_Class_Wide_Equivalent_Type (Equiv_Type);
5427 if not Is_Interface (Root_Typ) then
5428 Append_To (Comp_List,
5429 Make_Component_Declaration (Loc,
5430 Defining_Identifier =>
5431 Make_Defining_Identifier (Loc, Name_uParent),
5432 Component_Definition =>
5433 Make_Component_Definition (Loc,
5434 Aliased_Present => False,
5435 Subtype_Indication => New_Reference_To (Constr_Root, Loc))));
5436 end if;
5438 Append_To (Comp_List,
5439 Make_Component_Declaration (Loc,
5440 Defining_Identifier => Make_Temporary (Loc, 'C'),
5441 Component_Definition =>
5442 Make_Component_Definition (Loc,
5443 Aliased_Present => False,
5444 Subtype_Indication => New_Reference_To (Str_Type, Loc))));
5446 Append_To (List_Def,
5447 Make_Full_Type_Declaration (Loc,
5448 Defining_Identifier => Equiv_Type,
5449 Type_Definition =>
5450 Make_Record_Definition (Loc,
5451 Component_List =>
5452 Make_Component_List (Loc,
5453 Component_Items => Comp_List,
5454 Variant_Part => Empty))));
5456 -- Suppress all checks during the analysis of the expanded code to avoid
5457 -- the generation of spurious warnings under ZFP run-time.
5459 Insert_Actions (E, List_Def, Suppress => All_Checks);
5460 return Equiv_Type;
5461 end Make_CW_Equivalent_Type;
5463 -------------------------
5464 -- Make_Invariant_Call --
5465 -------------------------
5467 function Make_Invariant_Call (Expr : Node_Id) return Node_Id is
5468 Loc : constant Source_Ptr := Sloc (Expr);
5469 Typ : Entity_Id;
5471 begin
5472 Typ := Etype (Expr);
5474 -- Subtypes may be subject to invariants coming from their respective
5475 -- base types.
5477 if Ekind_In (Typ, E_Array_Subtype,
5478 E_Private_Subtype,
5479 E_Record_Subtype)
5480 then
5481 Typ := Base_Type (Typ);
5482 end if;
5484 pragma Assert
5485 (Has_Invariants (Typ) and then Present (Invariant_Procedure (Typ)));
5487 return
5488 Make_Procedure_Call_Statement (Loc,
5489 Name =>
5490 New_Occurrence_Of (Invariant_Procedure (Typ), Loc),
5491 Parameter_Associations => New_List (Relocate_Node (Expr)));
5492 end Make_Invariant_Call;
5494 ------------------------
5495 -- Make_Literal_Range --
5496 ------------------------
5498 function Make_Literal_Range
5499 (Loc : Source_Ptr;
5500 Literal_Typ : Entity_Id) return Node_Id
5502 Lo : constant Node_Id :=
5503 New_Copy_Tree (String_Literal_Low_Bound (Literal_Typ));
5504 Index : constant Entity_Id := Etype (Lo);
5506 Hi : Node_Id;
5507 Length_Expr : constant Node_Id :=
5508 Make_Op_Subtract (Loc,
5509 Left_Opnd =>
5510 Make_Integer_Literal (Loc,
5511 Intval => String_Literal_Length (Literal_Typ)),
5512 Right_Opnd =>
5513 Make_Integer_Literal (Loc, 1));
5515 begin
5516 Set_Analyzed (Lo, False);
5518 if Is_Integer_Type (Index) then
5519 Hi :=
5520 Make_Op_Add (Loc,
5521 Left_Opnd => New_Copy_Tree (Lo),
5522 Right_Opnd => Length_Expr);
5523 else
5524 Hi :=
5525 Make_Attribute_Reference (Loc,
5526 Attribute_Name => Name_Val,
5527 Prefix => New_Occurrence_Of (Index, Loc),
5528 Expressions => New_List (
5529 Make_Op_Add (Loc,
5530 Left_Opnd =>
5531 Make_Attribute_Reference (Loc,
5532 Attribute_Name => Name_Pos,
5533 Prefix => New_Occurrence_Of (Index, Loc),
5534 Expressions => New_List (New_Copy_Tree (Lo))),
5535 Right_Opnd => Length_Expr)));
5536 end if;
5538 return
5539 Make_Range (Loc,
5540 Low_Bound => Lo,
5541 High_Bound => Hi);
5542 end Make_Literal_Range;
5544 --------------------------
5545 -- Make_Non_Empty_Check --
5546 --------------------------
5548 function Make_Non_Empty_Check
5549 (Loc : Source_Ptr;
5550 N : Node_Id) return Node_Id
5552 begin
5553 return
5554 Make_Op_Ne (Loc,
5555 Left_Opnd =>
5556 Make_Attribute_Reference (Loc,
5557 Attribute_Name => Name_Length,
5558 Prefix => Duplicate_Subexpr_No_Checks (N, Name_Req => True)),
5559 Right_Opnd =>
5560 Make_Integer_Literal (Loc, 0));
5561 end Make_Non_Empty_Check;
5563 -------------------------
5564 -- Make_Predicate_Call --
5565 -------------------------
5567 function Make_Predicate_Call
5568 (Typ : Entity_Id;
5569 Expr : Node_Id;
5570 Mem : Boolean := False) return Node_Id
5572 Loc : constant Source_Ptr := Sloc (Expr);
5574 begin
5575 pragma Assert (Present (Predicate_Function (Typ)));
5577 -- Call special membership version if requested and available
5579 if Mem then
5580 declare
5581 PFM : constant Entity_Id := Predicate_Function_M (Typ);
5582 begin
5583 if Present (PFM) then
5584 return
5585 Make_Function_Call (Loc,
5586 Name => New_Occurrence_Of (PFM, Loc),
5587 Parameter_Associations => New_List (Relocate_Node (Expr)));
5588 end if;
5589 end;
5590 end if;
5592 -- Case of calling normal predicate function
5594 return
5595 Make_Function_Call (Loc,
5596 Name =>
5597 New_Occurrence_Of (Predicate_Function (Typ), Loc),
5598 Parameter_Associations => New_List (Relocate_Node (Expr)));
5599 end Make_Predicate_Call;
5601 --------------------------
5602 -- Make_Predicate_Check --
5603 --------------------------
5605 function Make_Predicate_Check
5606 (Typ : Entity_Id;
5607 Expr : Node_Id) return Node_Id
5609 Loc : constant Source_Ptr := Sloc (Expr);
5610 Nam : Name_Id;
5612 begin
5613 -- If predicate checks are suppressed, then return a null statement.
5614 -- For this call, we check only the scope setting. If the caller wants
5615 -- to check a specific entity's setting, they must do it manually.
5617 if Predicate_Checks_Suppressed (Empty) then
5618 return Make_Null_Statement (Loc);
5619 end if;
5621 -- Compute proper name to use, we need to get this right so that the
5622 -- right set of check policies apply to the Check pragma we are making.
5624 if Has_Dynamic_Predicate_Aspect (Typ) then
5625 Nam := Name_Dynamic_Predicate;
5626 elsif Has_Static_Predicate_Aspect (Typ) then
5627 Nam := Name_Static_Predicate;
5628 else
5629 Nam := Name_Predicate;
5630 end if;
5632 return
5633 Make_Pragma (Loc,
5634 Pragma_Identifier => Make_Identifier (Loc, Name_Check),
5635 Pragma_Argument_Associations => New_List (
5636 Make_Pragma_Argument_Association (Loc,
5637 Expression => Make_Identifier (Loc, Nam)),
5638 Make_Pragma_Argument_Association (Loc,
5639 Expression => Make_Predicate_Call (Typ, Expr))));
5640 end Make_Predicate_Check;
5642 ----------------------------
5643 -- Make_Subtype_From_Expr --
5644 ----------------------------
5646 -- 1. If Expr is an unconstrained array expression, creates
5647 -- Unc_Type(Expr'first(1)..Expr'last(1),..., Expr'first(n)..Expr'last(n))
5649 -- 2. If Expr is a unconstrained discriminated type expression, creates
5650 -- Unc_Type(Expr.Discr1, ... , Expr.Discr_n)
5652 -- 3. If Expr is class-wide, creates an implicit class wide subtype
5654 function Make_Subtype_From_Expr
5655 (E : Node_Id;
5656 Unc_Typ : Entity_Id) return Node_Id
5658 Loc : constant Source_Ptr := Sloc (E);
5659 List_Constr : constant List_Id := New_List;
5660 D : Entity_Id;
5662 Full_Subtyp : Entity_Id;
5663 Priv_Subtyp : Entity_Id;
5664 Utyp : Entity_Id;
5665 Full_Exp : Node_Id;
5667 begin
5668 if Is_Private_Type (Unc_Typ)
5669 and then Has_Unknown_Discriminants (Unc_Typ)
5670 then
5671 -- Prepare the subtype completion, Go to base type to
5672 -- find underlying type, because the type may be a generic
5673 -- actual or an explicit subtype.
5675 Utyp := Underlying_Type (Base_Type (Unc_Typ));
5676 Full_Subtyp := Make_Temporary (Loc, 'C');
5677 Full_Exp :=
5678 Unchecked_Convert_To (Utyp, Duplicate_Subexpr_No_Checks (E));
5679 Set_Parent (Full_Exp, Parent (E));
5681 Priv_Subtyp := Make_Temporary (Loc, 'P');
5683 Insert_Action (E,
5684 Make_Subtype_Declaration (Loc,
5685 Defining_Identifier => Full_Subtyp,
5686 Subtype_Indication => Make_Subtype_From_Expr (Full_Exp, Utyp)));
5688 -- Define the dummy private subtype
5690 Set_Ekind (Priv_Subtyp, Subtype_Kind (Ekind (Unc_Typ)));
5691 Set_Etype (Priv_Subtyp, Base_Type (Unc_Typ));
5692 Set_Scope (Priv_Subtyp, Full_Subtyp);
5693 Set_Is_Constrained (Priv_Subtyp);
5694 Set_Is_Tagged_Type (Priv_Subtyp, Is_Tagged_Type (Unc_Typ));
5695 Set_Is_Itype (Priv_Subtyp);
5696 Set_Associated_Node_For_Itype (Priv_Subtyp, E);
5698 if Is_Tagged_Type (Priv_Subtyp) then
5699 Set_Class_Wide_Type
5700 (Base_Type (Priv_Subtyp), Class_Wide_Type (Unc_Typ));
5701 Set_Direct_Primitive_Operations (Priv_Subtyp,
5702 Direct_Primitive_Operations (Unc_Typ));
5703 end if;
5705 Set_Full_View (Priv_Subtyp, Full_Subtyp);
5707 return New_Reference_To (Priv_Subtyp, Loc);
5709 elsif Is_Array_Type (Unc_Typ) then
5710 for J in 1 .. Number_Dimensions (Unc_Typ) loop
5711 Append_To (List_Constr,
5712 Make_Range (Loc,
5713 Low_Bound =>
5714 Make_Attribute_Reference (Loc,
5715 Prefix => Duplicate_Subexpr_No_Checks (E),
5716 Attribute_Name => Name_First,
5717 Expressions => New_List (
5718 Make_Integer_Literal (Loc, J))),
5720 High_Bound =>
5721 Make_Attribute_Reference (Loc,
5722 Prefix => Duplicate_Subexpr_No_Checks (E),
5723 Attribute_Name => Name_Last,
5724 Expressions => New_List (
5725 Make_Integer_Literal (Loc, J)))));
5726 end loop;
5728 elsif Is_Class_Wide_Type (Unc_Typ) then
5729 declare
5730 CW_Subtype : Entity_Id;
5731 EQ_Typ : Entity_Id := Empty;
5733 begin
5734 -- A class-wide equivalent type is not needed when VM_Target
5735 -- because the VM back-ends handle the class-wide object
5736 -- initialization itself (and doesn't need or want the
5737 -- additional intermediate type to handle the assignment).
5739 if Expander_Active and then Tagged_Type_Expansion then
5741 -- If this is the class_wide type of a completion that is a
5742 -- record subtype, set the type of the class_wide type to be
5743 -- the full base type, for use in the expanded code for the
5744 -- equivalent type. Should this be done earlier when the
5745 -- completion is analyzed ???
5747 if Is_Private_Type (Etype (Unc_Typ))
5748 and then
5749 Ekind (Full_View (Etype (Unc_Typ))) = E_Record_Subtype
5750 then
5751 Set_Etype (Unc_Typ, Base_Type (Full_View (Etype (Unc_Typ))));
5752 end if;
5754 EQ_Typ := Make_CW_Equivalent_Type (Unc_Typ, E);
5755 end if;
5757 CW_Subtype := New_Class_Wide_Subtype (Unc_Typ, E);
5758 Set_Equivalent_Type (CW_Subtype, EQ_Typ);
5759 Set_Cloned_Subtype (CW_Subtype, Base_Type (Unc_Typ));
5761 return New_Occurrence_Of (CW_Subtype, Loc);
5762 end;
5764 -- Indefinite record type with discriminants
5766 else
5767 D := First_Discriminant (Unc_Typ);
5768 while Present (D) loop
5769 Append_To (List_Constr,
5770 Make_Selected_Component (Loc,
5771 Prefix => Duplicate_Subexpr_No_Checks (E),
5772 Selector_Name => New_Reference_To (D, Loc)));
5774 Next_Discriminant (D);
5775 end loop;
5776 end if;
5778 return
5779 Make_Subtype_Indication (Loc,
5780 Subtype_Mark => New_Reference_To (Unc_Typ, Loc),
5781 Constraint =>
5782 Make_Index_Or_Discriminant_Constraint (Loc,
5783 Constraints => List_Constr));
5784 end Make_Subtype_From_Expr;
5786 -----------------------------
5787 -- May_Generate_Large_Temp --
5788 -----------------------------
5790 -- At the current time, the only types that we return False for (i.e. where
5791 -- we decide we know they cannot generate large temps) are ones where we
5792 -- know the size is 256 bits or less at compile time, and we are still not
5793 -- doing a thorough job on arrays and records ???
5795 function May_Generate_Large_Temp (Typ : Entity_Id) return Boolean is
5796 begin
5797 if not Size_Known_At_Compile_Time (Typ) then
5798 return False;
5800 elsif Esize (Typ) /= 0 and then Esize (Typ) <= 256 then
5801 return False;
5803 elsif Is_Array_Type (Typ) and then Present (Packed_Array_Type (Typ)) then
5804 return May_Generate_Large_Temp (Packed_Array_Type (Typ));
5806 -- We could do more here to find other small types ???
5808 else
5809 return True;
5810 end if;
5811 end May_Generate_Large_Temp;
5813 ------------------------
5814 -- Needs_Finalization --
5815 ------------------------
5817 function Needs_Finalization (T : Entity_Id) return Boolean is
5818 function Has_Some_Controlled_Component (Rec : Entity_Id) return Boolean;
5819 -- If type is not frozen yet, check explicitly among its components,
5820 -- because the Has_Controlled_Component flag is not necessarily set.
5822 -----------------------------------
5823 -- Has_Some_Controlled_Component --
5824 -----------------------------------
5826 function Has_Some_Controlled_Component
5827 (Rec : Entity_Id) return Boolean
5829 Comp : Entity_Id;
5831 begin
5832 if Has_Controlled_Component (Rec) then
5833 return True;
5835 elsif not Is_Frozen (Rec) then
5836 if Is_Record_Type (Rec) then
5837 Comp := First_Entity (Rec);
5839 while Present (Comp) loop
5840 if not Is_Type (Comp)
5841 and then Needs_Finalization (Etype (Comp))
5842 then
5843 return True;
5844 end if;
5846 Next_Entity (Comp);
5847 end loop;
5849 return False;
5851 elsif Is_Array_Type (Rec) then
5852 return Needs_Finalization (Component_Type (Rec));
5854 else
5855 return Has_Controlled_Component (Rec);
5856 end if;
5857 else
5858 return False;
5859 end if;
5860 end Has_Some_Controlled_Component;
5862 -- Start of processing for Needs_Finalization
5864 begin
5865 -- Certain run-time configurations and targets do not provide support
5866 -- for controlled types.
5868 if Restriction_Active (No_Finalization) then
5869 return False;
5871 -- C, C++, CIL and Java types are not considered controlled. It is
5872 -- assumed that the non-Ada side will handle their clean up.
5874 elsif Convention (T) = Convention_C
5875 or else Convention (T) = Convention_CIL
5876 or else Convention (T) = Convention_CPP
5877 or else Convention (T) = Convention_Java
5878 then
5879 return False;
5881 else
5882 -- Class-wide types are treated as controlled because derivations
5883 -- from the root type can introduce controlled components.
5885 return
5886 Is_Class_Wide_Type (T)
5887 or else Is_Controlled (T)
5888 or else Has_Controlled_Component (T)
5889 or else Has_Some_Controlled_Component (T)
5890 or else
5891 (Is_Concurrent_Type (T)
5892 and then Present (Corresponding_Record_Type (T))
5893 and then Needs_Finalization (Corresponding_Record_Type (T)));
5894 end if;
5895 end Needs_Finalization;
5897 ----------------------------
5898 -- Needs_Constant_Address --
5899 ----------------------------
5901 function Needs_Constant_Address
5902 (Decl : Node_Id;
5903 Typ : Entity_Id) return Boolean
5905 begin
5907 -- If we have no initialization of any kind, then we don't need to place
5908 -- any restrictions on the address clause, because the object will be
5909 -- elaborated after the address clause is evaluated. This happens if the
5910 -- declaration has no initial expression, or the type has no implicit
5911 -- initialization, or the object is imported.
5913 -- The same holds for all initialized scalar types and all access types.
5914 -- Packed bit arrays of size up to 64 are represented using a modular
5915 -- type with an initialization (to zero) and can be processed like other
5916 -- initialized scalar types.
5918 -- If the type is controlled, code to attach the object to a
5919 -- finalization chain is generated at the point of declaration, and
5920 -- therefore the elaboration of the object cannot be delayed: the
5921 -- address expression must be a constant.
5923 if No (Expression (Decl))
5924 and then not Needs_Finalization (Typ)
5925 and then
5926 (not Has_Non_Null_Base_Init_Proc (Typ)
5927 or else Is_Imported (Defining_Identifier (Decl)))
5928 then
5929 return False;
5931 elsif (Present (Expression (Decl)) and then Is_Scalar_Type (Typ))
5932 or else Is_Access_Type (Typ)
5933 or else
5934 (Is_Bit_Packed_Array (Typ)
5935 and then Is_Modular_Integer_Type (Packed_Array_Type (Typ)))
5936 then
5937 return False;
5939 else
5941 -- Otherwise, we require the address clause to be constant because
5942 -- the call to the initialization procedure (or the attach code) has
5943 -- to happen at the point of the declaration.
5945 -- Actually the IP call has been moved to the freeze actions anyway,
5946 -- so maybe we can relax this restriction???
5948 return True;
5949 end if;
5950 end Needs_Constant_Address;
5952 ----------------------------
5953 -- New_Class_Wide_Subtype --
5954 ----------------------------
5956 function New_Class_Wide_Subtype
5957 (CW_Typ : Entity_Id;
5958 N : Node_Id) return Entity_Id
5960 Res : constant Entity_Id := Create_Itype (E_Void, N);
5961 Res_Name : constant Name_Id := Chars (Res);
5962 Res_Scope : constant Entity_Id := Scope (Res);
5964 begin
5965 Copy_Node (CW_Typ, Res);
5966 Set_Comes_From_Source (Res, False);
5967 Set_Sloc (Res, Sloc (N));
5968 Set_Is_Itype (Res);
5969 Set_Associated_Node_For_Itype (Res, N);
5970 Set_Is_Public (Res, False); -- By default, may be changed below.
5971 Set_Public_Status (Res);
5972 Set_Chars (Res, Res_Name);
5973 Set_Scope (Res, Res_Scope);
5974 Set_Ekind (Res, E_Class_Wide_Subtype);
5975 Set_Next_Entity (Res, Empty);
5976 Set_Etype (Res, Base_Type (CW_Typ));
5977 Set_Is_Frozen (Res, False);
5978 Set_Freeze_Node (Res, Empty);
5979 return (Res);
5980 end New_Class_Wide_Subtype;
5982 --------------------------------
5983 -- Non_Limited_Designated_Type --
5984 ---------------------------------
5986 function Non_Limited_Designated_Type (T : Entity_Id) return Entity_Id is
5987 Desig : constant Entity_Id := Designated_Type (T);
5988 begin
5989 if Ekind (Desig) = E_Incomplete_Type
5990 and then Present (Non_Limited_View (Desig))
5991 then
5992 return Non_Limited_View (Desig);
5993 else
5994 return Desig;
5995 end if;
5996 end Non_Limited_Designated_Type;
5998 -----------------------------------
5999 -- OK_To_Do_Constant_Replacement --
6000 -----------------------------------
6002 function OK_To_Do_Constant_Replacement (E : Entity_Id) return Boolean is
6003 ES : constant Entity_Id := Scope (E);
6004 CS : Entity_Id;
6006 begin
6007 -- Do not replace statically allocated objects, because they may be
6008 -- modified outside the current scope.
6010 if Is_Statically_Allocated (E) then
6011 return False;
6013 -- Do not replace aliased or volatile objects, since we don't know what
6014 -- else might change the value.
6016 elsif Is_Aliased (E) or else Treat_As_Volatile (E) then
6017 return False;
6019 -- Debug flag -gnatdM disconnects this optimization
6021 elsif Debug_Flag_MM then
6022 return False;
6024 -- Otherwise check scopes
6026 else
6027 CS := Current_Scope;
6029 loop
6030 -- If we are in right scope, replacement is safe
6032 if CS = ES then
6033 return True;
6035 -- Packages do not affect the determination of safety
6037 elsif Ekind (CS) = E_Package then
6038 exit when CS = Standard_Standard;
6039 CS := Scope (CS);
6041 -- Blocks do not affect the determination of safety
6043 elsif Ekind (CS) = E_Block then
6044 CS := Scope (CS);
6046 -- Loops do not affect the determination of safety. Note that we
6047 -- kill all current values on entry to a loop, so we are just
6048 -- talking about processing within a loop here.
6050 elsif Ekind (CS) = E_Loop then
6051 CS := Scope (CS);
6053 -- Otherwise, the reference is dubious, and we cannot be sure that
6054 -- it is safe to do the replacement.
6056 else
6057 exit;
6058 end if;
6059 end loop;
6061 return False;
6062 end if;
6063 end OK_To_Do_Constant_Replacement;
6065 ------------------------------------
6066 -- Possible_Bit_Aligned_Component --
6067 ------------------------------------
6069 function Possible_Bit_Aligned_Component (N : Node_Id) return Boolean is
6070 begin
6071 case Nkind (N) is
6073 -- Case of indexed component
6075 when N_Indexed_Component =>
6076 declare
6077 P : constant Node_Id := Prefix (N);
6078 Ptyp : constant Entity_Id := Etype (P);
6080 begin
6081 -- If we know the component size and it is less than 64, then
6082 -- we are definitely OK. The back end always does assignment of
6083 -- misaligned small objects correctly.
6085 if Known_Static_Component_Size (Ptyp)
6086 and then Component_Size (Ptyp) <= 64
6087 then
6088 return False;
6090 -- Otherwise, we need to test the prefix, to see if we are
6091 -- indexing from a possibly unaligned component.
6093 else
6094 return Possible_Bit_Aligned_Component (P);
6095 end if;
6096 end;
6098 -- Case of selected component
6100 when N_Selected_Component =>
6101 declare
6102 P : constant Node_Id := Prefix (N);
6103 Comp : constant Entity_Id := Entity (Selector_Name (N));
6105 begin
6106 -- If there is no component clause, then we are in the clear
6107 -- since the back end will never misalign a large component
6108 -- unless it is forced to do so. In the clear means we need
6109 -- only the recursive test on the prefix.
6111 if Component_May_Be_Bit_Aligned (Comp) then
6112 return True;
6113 else
6114 return Possible_Bit_Aligned_Component (P);
6115 end if;
6116 end;
6118 -- For a slice, test the prefix, if that is possibly misaligned,
6119 -- then for sure the slice is!
6121 when N_Slice =>
6122 return Possible_Bit_Aligned_Component (Prefix (N));
6124 -- For an unchecked conversion, check whether the expression may
6125 -- be bit-aligned.
6127 when N_Unchecked_Type_Conversion =>
6128 return Possible_Bit_Aligned_Component (Expression (N));
6130 -- If we have none of the above, it means that we have fallen off the
6131 -- top testing prefixes recursively, and we now have a stand alone
6132 -- object, where we don't have a problem.
6134 when others =>
6135 return False;
6137 end case;
6138 end Possible_Bit_Aligned_Component;
6140 -----------------------------------------------
6141 -- Process_Statements_For_Controlled_Objects --
6142 -----------------------------------------------
6144 procedure Process_Statements_For_Controlled_Objects (N : Node_Id) is
6145 Loc : constant Source_Ptr := Sloc (N);
6147 function Are_Wrapped (L : List_Id) return Boolean;
6148 -- Determine whether list L contains only one statement which is a block
6150 function Wrap_Statements_In_Block (L : List_Id) return Node_Id;
6151 -- Given a list of statements L, wrap it in a block statement and return
6152 -- the generated node.
6154 -----------------
6155 -- Are_Wrapped --
6156 -----------------
6158 function Are_Wrapped (L : List_Id) return Boolean is
6159 Stmt : constant Node_Id := First (L);
6160 begin
6161 return
6162 Present (Stmt)
6163 and then No (Next (Stmt))
6164 and then Nkind (Stmt) = N_Block_Statement;
6165 end Are_Wrapped;
6167 ------------------------------
6168 -- Wrap_Statements_In_Block --
6169 ------------------------------
6171 function Wrap_Statements_In_Block (L : List_Id) return Node_Id is
6172 begin
6173 return
6174 Make_Block_Statement (Loc,
6175 Declarations => No_List,
6176 Handled_Statement_Sequence =>
6177 Make_Handled_Sequence_Of_Statements (Loc,
6178 Statements => L));
6179 end Wrap_Statements_In_Block;
6181 -- Local variables
6183 Block : Node_Id;
6185 -- Start of processing for Process_Statements_For_Controlled_Objects
6187 begin
6188 -- Whenever a non-handled statement list is wrapped in a block, the
6189 -- block must be explicitly analyzed to redecorate all entities in the
6190 -- list and ensure that a finalizer is properly built.
6192 case Nkind (N) is
6193 when N_Elsif_Part |
6194 N_If_Statement |
6195 N_Conditional_Entry_Call |
6196 N_Selective_Accept =>
6198 -- Check the "then statements" for elsif parts and if statements
6200 if Nkind_In (N, N_Elsif_Part, N_If_Statement)
6201 and then not Is_Empty_List (Then_Statements (N))
6202 and then not Are_Wrapped (Then_Statements (N))
6203 and then Requires_Cleanup_Actions
6204 (Then_Statements (N), False, False)
6205 then
6206 Block := Wrap_Statements_In_Block (Then_Statements (N));
6207 Set_Then_Statements (N, New_List (Block));
6209 Analyze (Block);
6210 end if;
6212 -- Check the "else statements" for conditional entry calls, if
6213 -- statements and selective accepts.
6215 if Nkind_In (N, N_Conditional_Entry_Call,
6216 N_If_Statement,
6217 N_Selective_Accept)
6218 and then not Is_Empty_List (Else_Statements (N))
6219 and then not Are_Wrapped (Else_Statements (N))
6220 and then Requires_Cleanup_Actions
6221 (Else_Statements (N), False, False)
6222 then
6223 Block := Wrap_Statements_In_Block (Else_Statements (N));
6224 Set_Else_Statements (N, New_List (Block));
6226 Analyze (Block);
6227 end if;
6229 when N_Abortable_Part |
6230 N_Accept_Alternative |
6231 N_Case_Statement_Alternative |
6232 N_Delay_Alternative |
6233 N_Entry_Call_Alternative |
6234 N_Exception_Handler |
6235 N_Loop_Statement |
6236 N_Triggering_Alternative =>
6238 if not Is_Empty_List (Statements (N))
6239 and then not Are_Wrapped (Statements (N))
6240 and then Requires_Cleanup_Actions (Statements (N), False, False)
6241 then
6242 Block := Wrap_Statements_In_Block (Statements (N));
6243 Set_Statements (N, New_List (Block));
6245 Analyze (Block);
6246 end if;
6248 when others =>
6249 null;
6250 end case;
6251 end Process_Statements_For_Controlled_Objects;
6253 ----------------------
6254 -- Remove_Init_Call --
6255 ----------------------
6257 function Remove_Init_Call
6258 (Var : Entity_Id;
6259 Rep_Clause : Node_Id) return Node_Id
6261 Par : constant Node_Id := Parent (Var);
6262 Typ : constant Entity_Id := Etype (Var);
6264 Init_Proc : Entity_Id;
6265 -- Initialization procedure for Typ
6267 function Find_Init_Call_In_List (From : Node_Id) return Node_Id;
6268 -- Look for init call for Var starting at From and scanning the
6269 -- enclosing list until Rep_Clause or the end of the list is reached.
6271 ----------------------------
6272 -- Find_Init_Call_In_List --
6273 ----------------------------
6275 function Find_Init_Call_In_List (From : Node_Id) return Node_Id is
6276 Init_Call : Node_Id;
6278 begin
6279 Init_Call := From;
6280 while Present (Init_Call) and then Init_Call /= Rep_Clause loop
6281 if Nkind (Init_Call) = N_Procedure_Call_Statement
6282 and then Is_Entity_Name (Name (Init_Call))
6283 and then Entity (Name (Init_Call)) = Init_Proc
6284 then
6285 return Init_Call;
6286 end if;
6288 Next (Init_Call);
6289 end loop;
6291 return Empty;
6292 end Find_Init_Call_In_List;
6294 Init_Call : Node_Id;
6296 -- Start of processing for Find_Init_Call
6298 begin
6299 if Present (Initialization_Statements (Var)) then
6300 Init_Call := Initialization_Statements (Var);
6301 Set_Initialization_Statements (Var, Empty);
6303 elsif not Has_Non_Null_Base_Init_Proc (Typ) then
6305 -- No init proc for the type, so obviously no call to be found
6307 return Empty;
6309 else
6310 -- We might be able to handle other cases below by just properly
6311 -- setting Initialization_Statements at the point where the init proc
6312 -- call is generated???
6314 Init_Proc := Base_Init_Proc (Typ);
6316 -- First scan the list containing the declaration of Var
6318 Init_Call := Find_Init_Call_In_List (From => Next (Par));
6320 -- If not found, also look on Var's freeze actions list, if any,
6321 -- since the init call may have been moved there (case of an address
6322 -- clause applying to Var).
6324 if No (Init_Call) and then Present (Freeze_Node (Var)) then
6325 Init_Call :=
6326 Find_Init_Call_In_List (First (Actions (Freeze_Node (Var))));
6327 end if;
6329 -- If the initialization call has actuals that use the secondary
6330 -- stack, the call may have been wrapped into a temporary block, in
6331 -- which case the block itself has to be removed.
6333 if No (Init_Call) and then Nkind (Next (Par)) = N_Block_Statement then
6334 declare
6335 Blk : constant Node_Id := Next (Par);
6336 begin
6337 if Present
6338 (Find_Init_Call_In_List
6339 (First (Statements (Handled_Statement_Sequence (Blk)))))
6340 then
6341 Init_Call := Blk;
6342 end if;
6343 end;
6344 end if;
6345 end if;
6347 if Present (Init_Call) then
6348 Remove (Init_Call);
6349 end if;
6350 return Init_Call;
6351 end Remove_Init_Call;
6353 -------------------------
6354 -- Remove_Side_Effects --
6355 -------------------------
6357 procedure Remove_Side_Effects
6358 (Exp : Node_Id;
6359 Name_Req : Boolean := False;
6360 Variable_Ref : Boolean := False)
6362 Loc : constant Source_Ptr := Sloc (Exp);
6363 Exp_Type : constant Entity_Id := Etype (Exp);
6364 Svg_Suppress : constant Suppress_Record := Scope_Suppress;
6365 Def_Id : Entity_Id;
6366 E : Node_Id;
6367 New_Exp : Node_Id;
6368 Ptr_Typ_Decl : Node_Id;
6369 Ref_Type : Entity_Id;
6370 Res : Node_Id;
6372 function Side_Effect_Free (N : Node_Id) return Boolean;
6373 -- Determines if the tree N represents an expression that is known not
6374 -- to have side effects, and for which no processing is required.
6376 function Side_Effect_Free (L : List_Id) return Boolean;
6377 -- Determines if all elements of the list L are side effect free
6379 function Safe_Prefixed_Reference (N : Node_Id) return Boolean;
6380 -- The argument N is a construct where the Prefix is dereferenced if it
6381 -- is an access type and the result is a variable. The call returns True
6382 -- if the construct is side effect free (not considering side effects in
6383 -- other than the prefix which are to be tested by the caller).
6385 function Within_In_Parameter (N : Node_Id) return Boolean;
6386 -- Determines if N is a subcomponent of a composite in-parameter. If so,
6387 -- N is not side-effect free when the actual is global and modifiable
6388 -- indirectly from within a subprogram, because it may be passed by
6389 -- reference. The front-end must be conservative here and assume that
6390 -- this may happen with any array or record type. On the other hand, we
6391 -- cannot create temporaries for all expressions for which this
6392 -- condition is true, for various reasons that might require clearing up
6393 -- ??? For example, discriminant references that appear out of place, or
6394 -- spurious type errors with class-wide expressions. As a result, we
6395 -- limit the transformation to loop bounds, which is so far the only
6396 -- case that requires it.
6398 -----------------------------
6399 -- Safe_Prefixed_Reference --
6400 -----------------------------
6402 function Safe_Prefixed_Reference (N : Node_Id) return Boolean is
6403 begin
6404 -- If prefix is not side effect free, definitely not safe
6406 if not Side_Effect_Free (Prefix (N)) then
6407 return False;
6409 -- If the prefix is of an access type that is not access-to-constant,
6410 -- then this construct is a variable reference, which means it is to
6411 -- be considered to have side effects if Variable_Ref is set True.
6413 elsif Is_Access_Type (Etype (Prefix (N)))
6414 and then not Is_Access_Constant (Etype (Prefix (N)))
6415 and then Variable_Ref
6416 then
6417 -- Exception is a prefix that is the result of a previous removal
6418 -- of side-effects.
6420 return Is_Entity_Name (Prefix (N))
6421 and then not Comes_From_Source (Prefix (N))
6422 and then Ekind (Entity (Prefix (N))) = E_Constant
6423 and then Is_Internal_Name (Chars (Entity (Prefix (N))));
6425 -- If the prefix is an explicit dereference then this construct is a
6426 -- variable reference, which means it is to be considered to have
6427 -- side effects if Variable_Ref is True.
6429 -- We do NOT exclude dereferences of access-to-constant types because
6430 -- we handle them as constant view of variables.
6432 elsif Nkind (Prefix (N)) = N_Explicit_Dereference
6433 and then Variable_Ref
6434 then
6435 return False;
6437 -- Note: The following test is the simplest way of solving a complex
6438 -- problem uncovered by the following test (Side effect on loop bound
6439 -- that is a subcomponent of a global variable:
6441 -- with Text_Io; use Text_Io;
6442 -- procedure Tloop is
6443 -- type X is
6444 -- record
6445 -- V : Natural := 4;
6446 -- S : String (1..5) := (others => 'a');
6447 -- end record;
6448 -- X1 : X;
6450 -- procedure Modi;
6452 -- generic
6453 -- with procedure Action;
6454 -- procedure Loop_G (Arg : X; Msg : String)
6456 -- procedure Loop_G (Arg : X; Msg : String) is
6457 -- begin
6458 -- Put_Line ("begin loop_g " & Msg & " will loop till: "
6459 -- & Natural'Image (Arg.V));
6460 -- for Index in 1 .. Arg.V loop
6461 -- Text_Io.Put_Line
6462 -- (Natural'Image (Index) & " " & Arg.S (Index));
6463 -- if Index > 2 then
6464 -- Modi;
6465 -- end if;
6466 -- end loop;
6467 -- Put_Line ("end loop_g " & Msg);
6468 -- end;
6470 -- procedure Loop1 is new Loop_G (Modi);
6471 -- procedure Modi is
6472 -- begin
6473 -- X1.V := 1;
6474 -- Loop1 (X1, "from modi");
6475 -- end;
6477 -- begin
6478 -- Loop1 (X1, "initial");
6479 -- end;
6481 -- The output of the above program should be:
6483 -- begin loop_g initial will loop till: 4
6484 -- 1 a
6485 -- 2 a
6486 -- 3 a
6487 -- begin loop_g from modi will loop till: 1
6488 -- 1 a
6489 -- end loop_g from modi
6490 -- 4 a
6491 -- begin loop_g from modi will loop till: 1
6492 -- 1 a
6493 -- end loop_g from modi
6494 -- end loop_g initial
6496 -- If a loop bound is a subcomponent of a global variable, a
6497 -- modification of that variable within the loop may incorrectly
6498 -- affect the execution of the loop.
6500 elsif Nkind (Parent (Parent (N))) = N_Loop_Parameter_Specification
6501 and then Within_In_Parameter (Prefix (N))
6502 and then Variable_Ref
6503 then
6504 return False;
6506 -- All other cases are side effect free
6508 else
6509 return True;
6510 end if;
6511 end Safe_Prefixed_Reference;
6513 ----------------------
6514 -- Side_Effect_Free --
6515 ----------------------
6517 function Side_Effect_Free (N : Node_Id) return Boolean is
6518 begin
6519 -- Note on checks that could raise Constraint_Error. Strictly, if we
6520 -- take advantage of 11.6, these checks do not count as side effects.
6521 -- However, we would prefer to consider that they are side effects,
6522 -- since the backend CSE does not work very well on expressions which
6523 -- can raise Constraint_Error. On the other hand if we don't consider
6524 -- them to be side effect free, then we get some awkward expansions
6525 -- in -gnato mode, resulting in code insertions at a point where we
6526 -- do not have a clear model for performing the insertions.
6528 -- Special handling for entity names
6530 if Is_Entity_Name (N) then
6532 -- Variables are considered to be a side effect if Variable_Ref
6533 -- is set or if we have a volatile reference and Name_Req is off.
6534 -- If Name_Req is True then we can't help returning a name which
6535 -- effectively allows multiple references in any case.
6537 if Is_Variable (N, Use_Original_Node => False) then
6538 return not Variable_Ref
6539 and then (not Is_Volatile_Reference (N) or else Name_Req);
6541 -- Any other entity (e.g. a subtype name) is definitely side
6542 -- effect free.
6544 else
6545 return True;
6546 end if;
6548 -- A value known at compile time is always side effect free
6550 elsif Compile_Time_Known_Value (N) then
6551 return True;
6553 -- A variable renaming is not side-effect free, because the renaming
6554 -- will function like a macro in the front-end in some cases, and an
6555 -- assignment can modify the component designated by N, so we need to
6556 -- create a temporary for it.
6558 -- The guard testing for Entity being present is needed at least in
6559 -- the case of rewritten predicate expressions, and may well also be
6560 -- appropriate elsewhere. Obviously we can't go testing the entity
6561 -- field if it does not exist, so it's reasonable to say that this is
6562 -- not the renaming case if it does not exist.
6564 elsif Is_Entity_Name (Original_Node (N))
6565 and then Present (Entity (Original_Node (N)))
6566 and then Is_Renaming_Of_Object (Entity (Original_Node (N)))
6567 and then Ekind (Entity (Original_Node (N))) /= E_Constant
6568 then
6569 declare
6570 RO : constant Node_Id :=
6571 Renamed_Object (Entity (Original_Node (N)));
6573 begin
6574 -- If the renamed object is an indexed component, or an
6575 -- explicit dereference, then the designated object could
6576 -- be modified by an assignment.
6578 if Nkind_In (RO, N_Indexed_Component,
6579 N_Explicit_Dereference)
6580 then
6581 return False;
6583 -- A selected component must have a safe prefix
6585 elsif Nkind (RO) = N_Selected_Component then
6586 return Safe_Prefixed_Reference (RO);
6588 -- In all other cases, designated object cannot be changed so
6589 -- we are side effect free.
6591 else
6592 return True;
6593 end if;
6594 end;
6596 -- Remove_Side_Effects generates an object renaming declaration to
6597 -- capture the expression of a class-wide expression. In VM targets
6598 -- the frontend performs no expansion for dispatching calls to
6599 -- class- wide types since they are handled by the VM. Hence, we must
6600 -- locate here if this node corresponds to a previous invocation of
6601 -- Remove_Side_Effects to avoid a never ending loop in the frontend.
6603 elsif VM_Target /= No_VM
6604 and then not Comes_From_Source (N)
6605 and then Nkind (Parent (N)) = N_Object_Renaming_Declaration
6606 and then Is_Class_Wide_Type (Etype (N))
6607 then
6608 return True;
6609 end if;
6611 -- For other than entity names and compile time known values,
6612 -- check the node kind for special processing.
6614 case Nkind (N) is
6616 -- An attribute reference is side effect free if its expressions
6617 -- are side effect free and its prefix is side effect free or
6618 -- is an entity reference.
6620 -- Is this right? what about x'first where x is a variable???
6622 when N_Attribute_Reference =>
6623 return Side_Effect_Free (Expressions (N))
6624 and then Attribute_Name (N) /= Name_Input
6625 and then (Is_Entity_Name (Prefix (N))
6626 or else Side_Effect_Free (Prefix (N)));
6628 -- A binary operator is side effect free if and both operands are
6629 -- side effect free. For this purpose binary operators include
6630 -- membership tests and short circuit forms.
6632 when N_Binary_Op | N_Membership_Test | N_Short_Circuit =>
6633 return Side_Effect_Free (Left_Opnd (N))
6634 and then
6635 Side_Effect_Free (Right_Opnd (N));
6637 -- An explicit dereference is side effect free only if it is
6638 -- a side effect free prefixed reference.
6640 when N_Explicit_Dereference =>
6641 return Safe_Prefixed_Reference (N);
6643 -- A call to _rep_to_pos is side effect free, since we generate
6644 -- this pure function call ourselves. Moreover it is critically
6645 -- important to make this exception, since otherwise we can have
6646 -- discriminants in array components which don't look side effect
6647 -- free in the case of an array whose index type is an enumeration
6648 -- type with an enumeration rep clause.
6650 -- All other function calls are not side effect free
6652 when N_Function_Call =>
6653 return Nkind (Name (N)) = N_Identifier
6654 and then Is_TSS (Name (N), TSS_Rep_To_Pos)
6655 and then
6656 Side_Effect_Free (First (Parameter_Associations (N)));
6658 -- An indexed component is side effect free if it is a side
6659 -- effect free prefixed reference and all the indexing
6660 -- expressions are side effect free.
6662 when N_Indexed_Component =>
6663 return Side_Effect_Free (Expressions (N))
6664 and then Safe_Prefixed_Reference (N);
6666 -- A type qualification is side effect free if the expression
6667 -- is side effect free.
6669 when N_Qualified_Expression =>
6670 return Side_Effect_Free (Expression (N));
6672 -- A selected component is side effect free only if it is a side
6673 -- effect free prefixed reference. If it designates a component
6674 -- with a rep. clause it must be treated has having a potential
6675 -- side effect, because it may be modified through a renaming, and
6676 -- a subsequent use of the renaming as a macro will yield the
6677 -- wrong value. This complex interaction between renaming and
6678 -- removing side effects is a reminder that the latter has become
6679 -- a headache to maintain, and that it should be removed in favor
6680 -- of the gcc mechanism to capture values ???
6682 when N_Selected_Component =>
6683 if Nkind (Parent (N)) = N_Explicit_Dereference
6684 and then Has_Non_Standard_Rep (Designated_Type (Etype (N)))
6685 then
6686 return False;
6687 else
6688 return Safe_Prefixed_Reference (N);
6689 end if;
6691 -- A range is side effect free if the bounds are side effect free
6693 when N_Range =>
6694 return Side_Effect_Free (Low_Bound (N))
6695 and then Side_Effect_Free (High_Bound (N));
6697 -- A slice is side effect free if it is a side effect free
6698 -- prefixed reference and the bounds are side effect free.
6700 when N_Slice =>
6701 return Side_Effect_Free (Discrete_Range (N))
6702 and then Safe_Prefixed_Reference (N);
6704 -- A type conversion is side effect free if the expression to be
6705 -- converted is side effect free.
6707 when N_Type_Conversion =>
6708 return Side_Effect_Free (Expression (N));
6710 -- A unary operator is side effect free if the operand
6711 -- is side effect free.
6713 when N_Unary_Op =>
6714 return Side_Effect_Free (Right_Opnd (N));
6716 -- An unchecked type conversion is side effect free only if it
6717 -- is safe and its argument is side effect free.
6719 when N_Unchecked_Type_Conversion =>
6720 return Safe_Unchecked_Type_Conversion (N)
6721 and then Side_Effect_Free (Expression (N));
6723 -- An unchecked expression is side effect free if its expression
6724 -- is side effect free.
6726 when N_Unchecked_Expression =>
6727 return Side_Effect_Free (Expression (N));
6729 -- A literal is side effect free
6731 when N_Character_Literal |
6732 N_Integer_Literal |
6733 N_Real_Literal |
6734 N_String_Literal =>
6735 return True;
6737 -- We consider that anything else has side effects. This is a bit
6738 -- crude, but we are pretty close for most common cases, and we
6739 -- are certainly correct (i.e. we never return True when the
6740 -- answer should be False).
6742 when others =>
6743 return False;
6744 end case;
6745 end Side_Effect_Free;
6747 -- A list is side effect free if all elements of the list are side
6748 -- effect free.
6750 function Side_Effect_Free (L : List_Id) return Boolean is
6751 N : Node_Id;
6753 begin
6754 if L = No_List or else L = Error_List then
6755 return True;
6757 else
6758 N := First (L);
6759 while Present (N) loop
6760 if not Side_Effect_Free (N) then
6761 return False;
6762 else
6763 Next (N);
6764 end if;
6765 end loop;
6767 return True;
6768 end if;
6769 end Side_Effect_Free;
6771 -------------------------
6772 -- Within_In_Parameter --
6773 -------------------------
6775 function Within_In_Parameter (N : Node_Id) return Boolean is
6776 begin
6777 if not Comes_From_Source (N) then
6778 return False;
6780 elsif Is_Entity_Name (N) then
6781 return Ekind (Entity (N)) = E_In_Parameter;
6783 elsif Nkind_In (N, N_Indexed_Component, N_Selected_Component) then
6784 return Within_In_Parameter (Prefix (N));
6786 else
6787 return False;
6788 end if;
6789 end Within_In_Parameter;
6791 -- Start of processing for Remove_Side_Effects
6793 begin
6794 -- Handle cases in which there is nothing to do
6796 if not Expander_Active then
6797 return;
6798 end if;
6800 -- Cannot generate temporaries if the invocation to remove side effects
6801 -- was issued too early and the type of the expression is not resolved
6802 -- (this happens because routines Duplicate_Subexpr_XX implicitly invoke
6803 -- Remove_Side_Effects).
6805 if No (Exp_Type)
6806 or else Ekind (Exp_Type) = E_Access_Attribute_Type
6807 then
6808 return;
6810 -- No action needed for side-effect free expressions
6812 elsif Side_Effect_Free (Exp) then
6813 return;
6814 end if;
6816 -- The remaining procesaing is done with all checks suppressed
6818 -- Note: from now on, don't use return statements, instead do a goto
6819 -- Leave, to ensure that we properly restore Scope_Suppress.Suppress.
6821 Scope_Suppress.Suppress := (others => True);
6823 -- If it is a scalar type and we need to capture the value, just make
6824 -- a copy. Likewise for a function call, an attribute reference, an
6825 -- allocator, or an operator. And if we have a volatile reference and
6826 -- Name_Req is not set (see comments above for Side_Effect_Free).
6828 if Is_Elementary_Type (Exp_Type)
6829 and then (Variable_Ref
6830 or else Nkind_In (Exp, N_Function_Call,
6831 N_Attribute_Reference,
6832 N_Allocator)
6833 or else Nkind (Exp) in N_Op
6834 or else (not Name_Req and then Is_Volatile_Reference (Exp)))
6835 then
6836 Def_Id := Make_Temporary (Loc, 'R', Exp);
6837 Set_Etype (Def_Id, Exp_Type);
6838 Res := New_Reference_To (Def_Id, Loc);
6840 -- If the expression is a packed reference, it must be reanalyzed and
6841 -- expanded, depending on context. This is the case for actuals where
6842 -- a constraint check may capture the actual before expansion of the
6843 -- call is complete.
6845 if Nkind (Exp) = N_Indexed_Component
6846 and then Is_Packed (Etype (Prefix (Exp)))
6847 then
6848 Set_Analyzed (Exp, False);
6849 Set_Analyzed (Prefix (Exp), False);
6850 end if;
6852 E :=
6853 Make_Object_Declaration (Loc,
6854 Defining_Identifier => Def_Id,
6855 Object_Definition => New_Reference_To (Exp_Type, Loc),
6856 Constant_Present => True,
6857 Expression => Relocate_Node (Exp));
6859 Set_Assignment_OK (E);
6860 Insert_Action (Exp, E);
6862 -- If the expression has the form v.all then we can just capture the
6863 -- pointer, and then do an explicit dereference on the result.
6865 elsif Nkind (Exp) = N_Explicit_Dereference then
6866 Def_Id := Make_Temporary (Loc, 'R', Exp);
6867 Res :=
6868 Make_Explicit_Dereference (Loc, New_Reference_To (Def_Id, Loc));
6870 Insert_Action (Exp,
6871 Make_Object_Declaration (Loc,
6872 Defining_Identifier => Def_Id,
6873 Object_Definition =>
6874 New_Reference_To (Etype (Prefix (Exp)), Loc),
6875 Constant_Present => True,
6876 Expression => Relocate_Node (Prefix (Exp))));
6878 -- Similar processing for an unchecked conversion of an expression of
6879 -- the form v.all, where we want the same kind of treatment.
6881 elsif Nkind (Exp) = N_Unchecked_Type_Conversion
6882 and then Nkind (Expression (Exp)) = N_Explicit_Dereference
6883 then
6884 Remove_Side_Effects (Expression (Exp), Name_Req, Variable_Ref);
6885 goto Leave;
6887 -- If this is a type conversion, leave the type conversion and remove
6888 -- the side effects in the expression. This is important in several
6889 -- circumstances: for change of representations, and also when this is a
6890 -- view conversion to a smaller object, where gigi can end up creating
6891 -- its own temporary of the wrong size.
6893 elsif Nkind (Exp) = N_Type_Conversion then
6894 Remove_Side_Effects (Expression (Exp), Name_Req, Variable_Ref);
6895 goto Leave;
6897 -- If this is an unchecked conversion that Gigi can't handle, make
6898 -- a copy or a use a renaming to capture the value.
6900 elsif Nkind (Exp) = N_Unchecked_Type_Conversion
6901 and then not Safe_Unchecked_Type_Conversion (Exp)
6902 then
6903 if CW_Or_Has_Controlled_Part (Exp_Type) then
6905 -- Use a renaming to capture the expression, rather than create
6906 -- a controlled temporary.
6908 Def_Id := Make_Temporary (Loc, 'R', Exp);
6909 Res := New_Reference_To (Def_Id, Loc);
6911 Insert_Action (Exp,
6912 Make_Object_Renaming_Declaration (Loc,
6913 Defining_Identifier => Def_Id,
6914 Subtype_Mark => New_Reference_To (Exp_Type, Loc),
6915 Name => Relocate_Node (Exp)));
6917 else
6918 Def_Id := Make_Temporary (Loc, 'R', Exp);
6919 Set_Etype (Def_Id, Exp_Type);
6920 Res := New_Reference_To (Def_Id, Loc);
6922 E :=
6923 Make_Object_Declaration (Loc,
6924 Defining_Identifier => Def_Id,
6925 Object_Definition => New_Reference_To (Exp_Type, Loc),
6926 Constant_Present => not Is_Variable (Exp),
6927 Expression => Relocate_Node (Exp));
6929 Set_Assignment_OK (E);
6930 Insert_Action (Exp, E);
6931 end if;
6933 -- For expressions that denote objects, we can use a renaming scheme.
6934 -- This is needed for correctness in the case of a volatile object of
6935 -- a non-volatile type because the Make_Reference call of the "default"
6936 -- approach would generate an illegal access value (an access value
6937 -- cannot designate such an object - see Analyze_Reference). We skip
6938 -- using this scheme if we have an object of a volatile type and we do
6939 -- not have Name_Req set true (see comments above for Side_Effect_Free).
6941 -- In Ada 2012 a qualified expression is an object, but for purposes of
6942 -- removing side effects it still need to be transformed into a separate
6943 -- declaration, particularly if the expression is an aggregate.
6945 elsif Is_Object_Reference (Exp)
6946 and then Nkind (Exp) /= N_Function_Call
6947 and then Nkind (Exp) /= N_Qualified_Expression
6948 and then (Name_Req or else not Treat_As_Volatile (Exp_Type))
6949 then
6950 Def_Id := Make_Temporary (Loc, 'R', Exp);
6952 if Nkind (Exp) = N_Selected_Component
6953 and then Nkind (Prefix (Exp)) = N_Function_Call
6954 and then Is_Array_Type (Exp_Type)
6955 then
6956 -- Avoid generating a variable-sized temporary, by generating
6957 -- the renaming declaration just for the function call. The
6958 -- transformation could be refined to apply only when the array
6959 -- component is constrained by a discriminant???
6961 Res :=
6962 Make_Selected_Component (Loc,
6963 Prefix => New_Occurrence_Of (Def_Id, Loc),
6964 Selector_Name => Selector_Name (Exp));
6966 Insert_Action (Exp,
6967 Make_Object_Renaming_Declaration (Loc,
6968 Defining_Identifier => Def_Id,
6969 Subtype_Mark =>
6970 New_Reference_To (Base_Type (Etype (Prefix (Exp))), Loc),
6971 Name => Relocate_Node (Prefix (Exp))));
6973 else
6974 Res := New_Reference_To (Def_Id, Loc);
6976 Insert_Action (Exp,
6977 Make_Object_Renaming_Declaration (Loc,
6978 Defining_Identifier => Def_Id,
6979 Subtype_Mark => New_Reference_To (Exp_Type, Loc),
6980 Name => Relocate_Node (Exp)));
6981 end if;
6983 -- If this is a packed reference, or a selected component with
6984 -- a non-standard representation, a reference to the temporary
6985 -- will be replaced by a copy of the original expression (see
6986 -- Exp_Ch2.Expand_Renaming). Otherwise the temporary must be
6987 -- elaborated by gigi, and is of course not to be replaced in-line
6988 -- by the expression it renames, which would defeat the purpose of
6989 -- removing the side-effect.
6991 if Nkind_In (Exp, N_Selected_Component, N_Indexed_Component)
6992 and then Has_Non_Standard_Rep (Etype (Prefix (Exp)))
6993 then
6994 null;
6995 else
6996 Set_Is_Renaming_Of_Object (Def_Id, False);
6997 end if;
6999 -- Otherwise we generate a reference to the value
7001 else
7002 -- An expression which is in SPARK mode is considered side effect
7003 -- free if the resulting value is captured by a variable or a
7004 -- constant.
7006 if SPARK_Mode
7007 and then Nkind (Parent (Exp)) = N_Object_Declaration
7008 then
7009 goto Leave;
7010 end if;
7012 -- Special processing for function calls that return a limited type.
7013 -- We need to build a declaration that will enable build-in-place
7014 -- expansion of the call. This is not done if the context is already
7015 -- an object declaration, to prevent infinite recursion.
7017 -- This is relevant only in Ada 2005 mode. In Ada 95 programs we have
7018 -- to accommodate functions returning limited objects by reference.
7020 if Ada_Version >= Ada_2005
7021 and then Nkind (Exp) = N_Function_Call
7022 and then Is_Immutably_Limited_Type (Etype (Exp))
7023 and then Nkind (Parent (Exp)) /= N_Object_Declaration
7024 then
7025 declare
7026 Obj : constant Entity_Id := Make_Temporary (Loc, 'F', Exp);
7027 Decl : Node_Id;
7029 begin
7030 Decl :=
7031 Make_Object_Declaration (Loc,
7032 Defining_Identifier => Obj,
7033 Object_Definition => New_Occurrence_Of (Exp_Type, Loc),
7034 Expression => Relocate_Node (Exp));
7036 Insert_Action (Exp, Decl);
7037 Set_Etype (Obj, Exp_Type);
7038 Rewrite (Exp, New_Occurrence_Of (Obj, Loc));
7039 goto Leave;
7040 end;
7041 end if;
7043 Def_Id := Make_Temporary (Loc, 'R', Exp);
7044 Set_Etype (Def_Id, Exp_Type);
7046 -- The regular expansion of functions with side effects involves the
7047 -- generation of an access type to capture the return value found on
7048 -- the secondary stack. Since SPARK (and why) cannot process access
7049 -- types, use a different approach which ignores the secondary stack
7050 -- and "copies" the returned object.
7052 if SPARK_Mode then
7053 Res := New_Reference_To (Def_Id, Loc);
7054 Ref_Type := Exp_Type;
7056 -- Regular expansion utilizing an access type and 'reference
7058 else
7059 Res :=
7060 Make_Explicit_Dereference (Loc,
7061 Prefix => New_Reference_To (Def_Id, Loc));
7063 -- Generate:
7064 -- type Ann is access all <Exp_Type>;
7066 Ref_Type := Make_Temporary (Loc, 'A');
7068 Ptr_Typ_Decl :=
7069 Make_Full_Type_Declaration (Loc,
7070 Defining_Identifier => Ref_Type,
7071 Type_Definition =>
7072 Make_Access_To_Object_Definition (Loc,
7073 All_Present => True,
7074 Subtype_Indication =>
7075 New_Reference_To (Exp_Type, Loc)));
7077 Insert_Action (Exp, Ptr_Typ_Decl);
7078 end if;
7080 E := Exp;
7081 if Nkind (E) = N_Explicit_Dereference then
7082 New_Exp := Relocate_Node (Prefix (E));
7083 else
7084 E := Relocate_Node (E);
7086 -- Do not generate a 'reference in SPARK mode since the access
7087 -- type is not created in the first place.
7089 if SPARK_Mode then
7090 New_Exp := E;
7092 -- Otherwise generate reference, marking the value as non-null
7093 -- since we know it cannot be null and we don't want a check.
7095 else
7096 New_Exp := Make_Reference (Loc, E);
7097 Set_Is_Known_Non_Null (Def_Id);
7098 end if;
7099 end if;
7101 if Is_Delayed_Aggregate (E) then
7103 -- The expansion of nested aggregates is delayed until the
7104 -- enclosing aggregate is expanded. As aggregates are often
7105 -- qualified, the predicate applies to qualified expressions as
7106 -- well, indicating that the enclosing aggregate has not been
7107 -- expanded yet. At this point the aggregate is part of a
7108 -- stand-alone declaration, and must be fully expanded.
7110 if Nkind (E) = N_Qualified_Expression then
7111 Set_Expansion_Delayed (Expression (E), False);
7112 Set_Analyzed (Expression (E), False);
7113 else
7114 Set_Expansion_Delayed (E, False);
7115 end if;
7117 Set_Analyzed (E, False);
7118 end if;
7120 Insert_Action (Exp,
7121 Make_Object_Declaration (Loc,
7122 Defining_Identifier => Def_Id,
7123 Object_Definition => New_Reference_To (Ref_Type, Loc),
7124 Constant_Present => True,
7125 Expression => New_Exp));
7126 end if;
7128 -- Preserve the Assignment_OK flag in all copies, since at least one
7129 -- copy may be used in a context where this flag must be set (otherwise
7130 -- why would the flag be set in the first place).
7132 Set_Assignment_OK (Res, Assignment_OK (Exp));
7134 -- Finally rewrite the original expression and we are done
7136 Rewrite (Exp, Res);
7137 Analyze_And_Resolve (Exp, Exp_Type);
7139 <<Leave>>
7140 Scope_Suppress := Svg_Suppress;
7141 end Remove_Side_Effects;
7143 ---------------------------
7144 -- Represented_As_Scalar --
7145 ---------------------------
7147 function Represented_As_Scalar (T : Entity_Id) return Boolean is
7148 UT : constant Entity_Id := Underlying_Type (T);
7149 begin
7150 return Is_Scalar_Type (UT)
7151 or else (Is_Bit_Packed_Array (UT)
7152 and then Is_Scalar_Type (Packed_Array_Type (UT)));
7153 end Represented_As_Scalar;
7155 ------------------------------
7156 -- Requires_Cleanup_Actions --
7157 ------------------------------
7159 function Requires_Cleanup_Actions
7160 (N : Node_Id;
7161 Lib_Level : Boolean) return Boolean
7163 At_Lib_Level : constant Boolean :=
7164 Lib_Level
7165 and then Nkind_In (N, N_Package_Body,
7166 N_Package_Specification);
7167 -- N is at the library level if the top-most context is a package and
7168 -- the path taken to reach N does not inlcude non-package constructs.
7170 begin
7171 case Nkind (N) is
7172 when N_Accept_Statement |
7173 N_Block_Statement |
7174 N_Entry_Body |
7175 N_Package_Body |
7176 N_Protected_Body |
7177 N_Subprogram_Body |
7178 N_Task_Body =>
7179 return
7180 Requires_Cleanup_Actions (Declarations (N), At_Lib_Level, True)
7181 or else
7182 (Present (Handled_Statement_Sequence (N))
7183 and then
7184 Requires_Cleanup_Actions
7185 (Statements (Handled_Statement_Sequence (N)),
7186 At_Lib_Level, True));
7188 when N_Package_Specification =>
7189 return
7190 Requires_Cleanup_Actions
7191 (Visible_Declarations (N), At_Lib_Level, True)
7192 or else
7193 Requires_Cleanup_Actions
7194 (Private_Declarations (N), At_Lib_Level, True);
7196 when others =>
7197 return False;
7198 end case;
7199 end Requires_Cleanup_Actions;
7201 ------------------------------
7202 -- Requires_Cleanup_Actions --
7203 ------------------------------
7205 function Requires_Cleanup_Actions
7206 (L : List_Id;
7207 Lib_Level : Boolean;
7208 Nested_Constructs : Boolean) return Boolean
7210 Decl : Node_Id;
7211 Expr : Node_Id;
7212 Obj_Id : Entity_Id;
7213 Obj_Typ : Entity_Id;
7214 Pack_Id : Entity_Id;
7215 Typ : Entity_Id;
7217 begin
7218 if No (L)
7219 or else Is_Empty_List (L)
7220 then
7221 return False;
7222 end if;
7224 Decl := First (L);
7225 while Present (Decl) loop
7227 -- Library-level tagged types
7229 if Nkind (Decl) = N_Full_Type_Declaration then
7230 Typ := Defining_Identifier (Decl);
7232 if Is_Tagged_Type (Typ)
7233 and then Is_Library_Level_Entity (Typ)
7234 and then Convention (Typ) = Convention_Ada
7235 and then Present (Access_Disp_Table (Typ))
7236 and then RTE_Available (RE_Unregister_Tag)
7237 and then not No_Run_Time_Mode
7238 and then not Is_Abstract_Type (Typ)
7239 then
7240 return True;
7241 end if;
7243 -- Regular object declarations
7245 elsif Nkind (Decl) = N_Object_Declaration then
7246 Obj_Id := Defining_Identifier (Decl);
7247 Obj_Typ := Base_Type (Etype (Obj_Id));
7248 Expr := Expression (Decl);
7250 -- Bypass any form of processing for objects which have their
7251 -- finalization disabled. This applies only to objects at the
7252 -- library level.
7254 if Lib_Level and then Finalize_Storage_Only (Obj_Typ) then
7255 null;
7257 -- Transient variables are treated separately in order to minimize
7258 -- the size of the generated code. See Exp_Ch7.Process_Transient_
7259 -- Objects.
7261 elsif Is_Processed_Transient (Obj_Id) then
7262 null;
7264 -- The object is of the form:
7265 -- Obj : Typ [:= Expr];
7267 -- Do not process the incomplete view of a deferred constant. Do
7268 -- not consider tag-to-class-wide conversions.
7270 elsif not Is_Imported (Obj_Id)
7271 and then Needs_Finalization (Obj_Typ)
7272 and then not (Ekind (Obj_Id) = E_Constant
7273 and then not Has_Completion (Obj_Id))
7274 and then not Is_Tag_To_Class_Wide_Conversion (Obj_Id)
7275 then
7276 return True;
7278 -- The object is of the form:
7279 -- Obj : Access_Typ := Non_BIP_Function_Call'reference;
7281 -- Obj : Access_Typ :=
7282 -- BIP_Function_Call (BIPalloc => 2, ...)'reference;
7284 elsif Is_Access_Type (Obj_Typ)
7285 and then Needs_Finalization
7286 (Available_View (Designated_Type (Obj_Typ)))
7287 and then Present (Expr)
7288 and then
7289 (Is_Secondary_Stack_BIP_Func_Call (Expr)
7290 or else
7291 (Is_Non_BIP_Func_Call (Expr)
7292 and then not Is_Related_To_Func_Return (Obj_Id)))
7293 then
7294 return True;
7296 -- Processing for "hook" objects generated for controlled
7297 -- transients declared inside an Expression_With_Actions.
7299 elsif Is_Access_Type (Obj_Typ)
7300 and then Present (Status_Flag_Or_Transient_Decl (Obj_Id))
7301 and then Nkind (Status_Flag_Or_Transient_Decl (Obj_Id)) =
7302 N_Object_Declaration
7303 and then Is_Finalizable_Transient
7304 (Status_Flag_Or_Transient_Decl (Obj_Id), Decl)
7305 then
7306 return True;
7308 -- Processing for intermediate results of if expressions where
7309 -- one of the alternatives uses a controlled function call.
7311 elsif Is_Access_Type (Obj_Typ)
7312 and then Present (Status_Flag_Or_Transient_Decl (Obj_Id))
7313 and then Nkind (Status_Flag_Or_Transient_Decl (Obj_Id)) =
7314 N_Defining_Identifier
7315 and then Present (Expr)
7316 and then Nkind (Expr) = N_Null
7317 then
7318 return True;
7320 -- Simple protected objects which use type System.Tasking.
7321 -- Protected_Objects.Protection to manage their locks should be
7322 -- treated as controlled since they require manual cleanup.
7324 elsif Ekind (Obj_Id) = E_Variable
7325 and then
7326 (Is_Simple_Protected_Type (Obj_Typ)
7327 or else Has_Simple_Protected_Object (Obj_Typ))
7328 then
7329 return True;
7330 end if;
7332 -- Specific cases of object renamings
7334 elsif Nkind (Decl) = N_Object_Renaming_Declaration then
7335 Obj_Id := Defining_Identifier (Decl);
7336 Obj_Typ := Base_Type (Etype (Obj_Id));
7338 -- Bypass any form of processing for objects which have their
7339 -- finalization disabled. This applies only to objects at the
7340 -- library level.
7342 if Lib_Level and then Finalize_Storage_Only (Obj_Typ) then
7343 null;
7345 -- Return object of a build-in-place function. This case is
7346 -- recognized and marked by the expansion of an extended return
7347 -- statement (see Expand_N_Extended_Return_Statement).
7349 elsif Needs_Finalization (Obj_Typ)
7350 and then Is_Return_Object (Obj_Id)
7351 and then Present (Status_Flag_Or_Transient_Decl (Obj_Id))
7352 then
7353 return True;
7355 -- Detect a case where a source object has been initialized by
7356 -- a controlled function call or another object which was later
7357 -- rewritten as a class-wide conversion of Ada.Tags.Displace.
7359 -- Obj1 : CW_Type := Src_Obj;
7360 -- Obj2 : CW_Type := Function_Call (...);
7362 -- Obj1 : CW_Type renames (... Ada.Tags.Displace (Src_Obj));
7363 -- Tmp : ... := Function_Call (...)'reference;
7364 -- Obj2 : CW_Type renames (... Ada.Tags.Displace (Tmp));
7366 elsif Is_Displacement_Of_Object_Or_Function_Result (Obj_Id) then
7367 return True;
7368 end if;
7370 -- Inspect the freeze node of an access-to-controlled type and look
7371 -- for a delayed finalization master. This case arises when the
7372 -- freeze actions are inserted at a later time than the expansion of
7373 -- the context. Since Build_Finalizer is never called on a single
7374 -- construct twice, the master will be ultimately left out and never
7375 -- finalized. This is also needed for freeze actions of designated
7376 -- types themselves, since in some cases the finalization master is
7377 -- associated with a designated type's freeze node rather than that
7378 -- of the access type (see handling for freeze actions in
7379 -- Build_Finalization_Master).
7381 elsif Nkind (Decl) = N_Freeze_Entity
7382 and then Present (Actions (Decl))
7383 then
7384 Typ := Entity (Decl);
7386 if ((Is_Access_Type (Typ)
7387 and then not Is_Access_Subprogram_Type (Typ)
7388 and then Needs_Finalization
7389 (Available_View (Designated_Type (Typ))))
7390 or else
7391 (Is_Type (Typ)
7392 and then Needs_Finalization (Typ)))
7393 and then Requires_Cleanup_Actions
7394 (Actions (Decl), Lib_Level, Nested_Constructs)
7395 then
7396 return True;
7397 end if;
7399 -- Nested package declarations
7401 elsif Nested_Constructs
7402 and then Nkind (Decl) = N_Package_Declaration
7403 then
7404 Pack_Id := Defining_Unit_Name (Specification (Decl));
7406 if Nkind (Pack_Id) = N_Defining_Program_Unit_Name then
7407 Pack_Id := Defining_Identifier (Pack_Id);
7408 end if;
7410 if Ekind (Pack_Id) /= E_Generic_Package
7411 and then
7412 Requires_Cleanup_Actions (Specification (Decl), Lib_Level)
7413 then
7414 return True;
7415 end if;
7417 -- Nested package bodies
7419 elsif Nested_Constructs and then Nkind (Decl) = N_Package_Body then
7420 Pack_Id := Corresponding_Spec (Decl);
7422 if Ekind (Pack_Id) /= E_Generic_Package
7423 and then Requires_Cleanup_Actions (Decl, Lib_Level)
7424 then
7425 return True;
7426 end if;
7427 end if;
7429 Next (Decl);
7430 end loop;
7432 return False;
7433 end Requires_Cleanup_Actions;
7435 ------------------------------------
7436 -- Safe_Unchecked_Type_Conversion --
7437 ------------------------------------
7439 -- Note: this function knows quite a bit about the exact requirements of
7440 -- Gigi with respect to unchecked type conversions, and its code must be
7441 -- coordinated with any changes in Gigi in this area.
7443 -- The above requirements should be documented in Sinfo ???
7445 function Safe_Unchecked_Type_Conversion (Exp : Node_Id) return Boolean is
7446 Otyp : Entity_Id;
7447 Ityp : Entity_Id;
7448 Oalign : Uint;
7449 Ialign : Uint;
7450 Pexp : constant Node_Id := Parent (Exp);
7452 begin
7453 -- If the expression is the RHS of an assignment or object declaration
7454 -- we are always OK because there will always be a target.
7456 -- Object renaming declarations, (generated for view conversions of
7457 -- actuals in inlined calls), like object declarations, provide an
7458 -- explicit type, and are safe as well.
7460 if (Nkind (Pexp) = N_Assignment_Statement
7461 and then Expression (Pexp) = Exp)
7462 or else Nkind_In (Pexp, N_Object_Declaration,
7463 N_Object_Renaming_Declaration)
7464 then
7465 return True;
7467 -- If the expression is the prefix of an N_Selected_Component we should
7468 -- also be OK because GCC knows to look inside the conversion except if
7469 -- the type is discriminated. We assume that we are OK anyway if the
7470 -- type is not set yet or if it is controlled since we can't afford to
7471 -- introduce a temporary in this case.
7473 elsif Nkind (Pexp) = N_Selected_Component
7474 and then Prefix (Pexp) = Exp
7475 then
7476 if No (Etype (Pexp)) then
7477 return True;
7478 else
7479 return
7480 not Has_Discriminants (Etype (Pexp))
7481 or else Is_Constrained (Etype (Pexp));
7482 end if;
7483 end if;
7485 -- Set the output type, this comes from Etype if it is set, otherwise we
7486 -- take it from the subtype mark, which we assume was already fully
7487 -- analyzed.
7489 if Present (Etype (Exp)) then
7490 Otyp := Etype (Exp);
7491 else
7492 Otyp := Entity (Subtype_Mark (Exp));
7493 end if;
7495 -- The input type always comes from the expression, and we assume
7496 -- this is indeed always analyzed, so we can simply get the Etype.
7498 Ityp := Etype (Expression (Exp));
7500 -- Initialize alignments to unknown so far
7502 Oalign := No_Uint;
7503 Ialign := No_Uint;
7505 -- Replace a concurrent type by its corresponding record type and each
7506 -- type by its underlying type and do the tests on those. The original
7507 -- type may be a private type whose completion is a concurrent type, so
7508 -- find the underlying type first.
7510 if Present (Underlying_Type (Otyp)) then
7511 Otyp := Underlying_Type (Otyp);
7512 end if;
7514 if Present (Underlying_Type (Ityp)) then
7515 Ityp := Underlying_Type (Ityp);
7516 end if;
7518 if Is_Concurrent_Type (Otyp) then
7519 Otyp := Corresponding_Record_Type (Otyp);
7520 end if;
7522 if Is_Concurrent_Type (Ityp) then
7523 Ityp := Corresponding_Record_Type (Ityp);
7524 end if;
7526 -- If the base types are the same, we know there is no problem since
7527 -- this conversion will be a noop.
7529 if Implementation_Base_Type (Otyp) = Implementation_Base_Type (Ityp) then
7530 return True;
7532 -- Same if this is an upwards conversion of an untagged type, and there
7533 -- are no constraints involved (could be more general???)
7535 elsif Etype (Ityp) = Otyp
7536 and then not Is_Tagged_Type (Ityp)
7537 and then not Has_Discriminants (Ityp)
7538 and then No (First_Rep_Item (Base_Type (Ityp)))
7539 then
7540 return True;
7542 -- If the expression has an access type (object or subprogram) we assume
7543 -- that the conversion is safe, because the size of the target is safe,
7544 -- even if it is a record (which might be treated as having unknown size
7545 -- at this point).
7547 elsif Is_Access_Type (Ityp) then
7548 return True;
7550 -- If the size of output type is known at compile time, there is never
7551 -- a problem. Note that unconstrained records are considered to be of
7552 -- known size, but we can't consider them that way here, because we are
7553 -- talking about the actual size of the object.
7555 -- We also make sure that in addition to the size being known, we do not
7556 -- have a case which might generate an embarrassingly large temp in
7557 -- stack checking mode.
7559 elsif Size_Known_At_Compile_Time (Otyp)
7560 and then
7561 (not Stack_Checking_Enabled
7562 or else not May_Generate_Large_Temp (Otyp))
7563 and then not (Is_Record_Type (Otyp) and then not Is_Constrained (Otyp))
7564 then
7565 return True;
7567 -- If either type is tagged, then we know the alignment is OK so
7568 -- Gigi will be able to use pointer punning.
7570 elsif Is_Tagged_Type (Otyp) or else Is_Tagged_Type (Ityp) then
7571 return True;
7573 -- If either type is a limited record type, we cannot do a copy, so say
7574 -- safe since there's nothing else we can do.
7576 elsif Is_Limited_Record (Otyp) or else Is_Limited_Record (Ityp) then
7577 return True;
7579 -- Conversions to and from packed array types are always ignored and
7580 -- hence are safe.
7582 elsif Is_Packed_Array_Type (Otyp)
7583 or else Is_Packed_Array_Type (Ityp)
7584 then
7585 return True;
7586 end if;
7588 -- The only other cases known to be safe is if the input type's
7589 -- alignment is known to be at least the maximum alignment for the
7590 -- target or if both alignments are known and the output type's
7591 -- alignment is no stricter than the input's. We can use the component
7592 -- type alignement for an array if a type is an unpacked array type.
7594 if Present (Alignment_Clause (Otyp)) then
7595 Oalign := Expr_Value (Expression (Alignment_Clause (Otyp)));
7597 elsif Is_Array_Type (Otyp)
7598 and then Present (Alignment_Clause (Component_Type (Otyp)))
7599 then
7600 Oalign := Expr_Value (Expression (Alignment_Clause
7601 (Component_Type (Otyp))));
7602 end if;
7604 if Present (Alignment_Clause (Ityp)) then
7605 Ialign := Expr_Value (Expression (Alignment_Clause (Ityp)));
7607 elsif Is_Array_Type (Ityp)
7608 and then Present (Alignment_Clause (Component_Type (Ityp)))
7609 then
7610 Ialign := Expr_Value (Expression (Alignment_Clause
7611 (Component_Type (Ityp))));
7612 end if;
7614 if Ialign /= No_Uint and then Ialign > Maximum_Alignment then
7615 return True;
7617 elsif Ialign /= No_Uint and then Oalign /= No_Uint
7618 and then Ialign <= Oalign
7619 then
7620 return True;
7622 -- Otherwise, Gigi cannot handle this and we must make a temporary
7624 else
7625 return False;
7626 end if;
7627 end Safe_Unchecked_Type_Conversion;
7629 ---------------------------------
7630 -- Set_Current_Value_Condition --
7631 ---------------------------------
7633 -- Note: the implementation of this procedure is very closely tied to the
7634 -- implementation of Get_Current_Value_Condition. Here we set required
7635 -- Current_Value fields, and in Get_Current_Value_Condition, we interpret
7636 -- them, so they must have a consistent view.
7638 procedure Set_Current_Value_Condition (Cnode : Node_Id) is
7640 procedure Set_Entity_Current_Value (N : Node_Id);
7641 -- If N is an entity reference, where the entity is of an appropriate
7642 -- kind, then set the current value of this entity to Cnode, unless
7643 -- there is already a definite value set there.
7645 procedure Set_Expression_Current_Value (N : Node_Id);
7646 -- If N is of an appropriate form, sets an appropriate entry in current
7647 -- value fields of relevant entities. Multiple entities can be affected
7648 -- in the case of an AND or AND THEN.
7650 ------------------------------
7651 -- Set_Entity_Current_Value --
7652 ------------------------------
7654 procedure Set_Entity_Current_Value (N : Node_Id) is
7655 begin
7656 if Is_Entity_Name (N) then
7657 declare
7658 Ent : constant Entity_Id := Entity (N);
7660 begin
7661 -- Don't capture if not safe to do so
7663 if not Safe_To_Capture_Value (N, Ent, Cond => True) then
7664 return;
7665 end if;
7667 -- Here we have a case where the Current_Value field may need
7668 -- to be set. We set it if it is not already set to a compile
7669 -- time expression value.
7671 -- Note that this represents a decision that one condition
7672 -- blots out another previous one. That's certainly right if
7673 -- they occur at the same level. If the second one is nested,
7674 -- then the decision is neither right nor wrong (it would be
7675 -- equally OK to leave the outer one in place, or take the new
7676 -- inner one. Really we should record both, but our data
7677 -- structures are not that elaborate.
7679 if Nkind (Current_Value (Ent)) not in N_Subexpr then
7680 Set_Current_Value (Ent, Cnode);
7681 end if;
7682 end;
7683 end if;
7684 end Set_Entity_Current_Value;
7686 ----------------------------------
7687 -- Set_Expression_Current_Value --
7688 ----------------------------------
7690 procedure Set_Expression_Current_Value (N : Node_Id) is
7691 Cond : Node_Id;
7693 begin
7694 Cond := N;
7696 -- Loop to deal with (ignore for now) any NOT operators present. The
7697 -- presence of NOT operators will be handled properly when we call
7698 -- Get_Current_Value_Condition.
7700 while Nkind (Cond) = N_Op_Not loop
7701 Cond := Right_Opnd (Cond);
7702 end loop;
7704 -- For an AND or AND THEN, recursively process operands
7706 if Nkind (Cond) = N_Op_And or else Nkind (Cond) = N_And_Then then
7707 Set_Expression_Current_Value (Left_Opnd (Cond));
7708 Set_Expression_Current_Value (Right_Opnd (Cond));
7709 return;
7710 end if;
7712 -- Check possible relational operator
7714 if Nkind (Cond) in N_Op_Compare then
7715 if Compile_Time_Known_Value (Right_Opnd (Cond)) then
7716 Set_Entity_Current_Value (Left_Opnd (Cond));
7717 elsif Compile_Time_Known_Value (Left_Opnd (Cond)) then
7718 Set_Entity_Current_Value (Right_Opnd (Cond));
7719 end if;
7721 -- Check possible boolean variable reference
7723 else
7724 Set_Entity_Current_Value (Cond);
7725 end if;
7726 end Set_Expression_Current_Value;
7728 -- Start of processing for Set_Current_Value_Condition
7730 begin
7731 Set_Expression_Current_Value (Condition (Cnode));
7732 end Set_Current_Value_Condition;
7734 --------------------------
7735 -- Set_Elaboration_Flag --
7736 --------------------------
7738 procedure Set_Elaboration_Flag (N : Node_Id; Spec_Id : Entity_Id) is
7739 Loc : constant Source_Ptr := Sloc (N);
7740 Ent : constant Entity_Id := Elaboration_Entity (Spec_Id);
7741 Asn : Node_Id;
7743 begin
7744 if Present (Ent) then
7746 -- Nothing to do if at the compilation unit level, because in this
7747 -- case the flag is set by the binder generated elaboration routine.
7749 if Nkind (Parent (N)) = N_Compilation_Unit then
7750 null;
7752 -- Here we do need to generate an assignment statement
7754 else
7755 Check_Restriction (No_Elaboration_Code, N);
7756 Asn :=
7757 Make_Assignment_Statement (Loc,
7758 Name => New_Occurrence_Of (Ent, Loc),
7759 Expression => Make_Integer_Literal (Loc, Uint_1));
7761 if Nkind (Parent (N)) = N_Subunit then
7762 Insert_After (Corresponding_Stub (Parent (N)), Asn);
7763 else
7764 Insert_After (N, Asn);
7765 end if;
7767 Analyze (Asn);
7769 -- Kill current value indication. This is necessary because the
7770 -- tests of this flag are inserted out of sequence and must not
7771 -- pick up bogus indications of the wrong constant value.
7773 Set_Current_Value (Ent, Empty);
7774 end if;
7775 end if;
7776 end Set_Elaboration_Flag;
7778 ----------------------------
7779 -- Set_Renamed_Subprogram --
7780 ----------------------------
7782 procedure Set_Renamed_Subprogram (N : Node_Id; E : Entity_Id) is
7783 begin
7784 -- If input node is an identifier, we can just reset it
7786 if Nkind (N) = N_Identifier then
7787 Set_Chars (N, Chars (E));
7788 Set_Entity (N, E);
7790 -- Otherwise we have to do a rewrite, preserving Comes_From_Source
7792 else
7793 declare
7794 CS : constant Boolean := Comes_From_Source (N);
7795 begin
7796 Rewrite (N, Make_Identifier (Sloc (N), Chars (E)));
7797 Set_Entity (N, E);
7798 Set_Comes_From_Source (N, CS);
7799 Set_Analyzed (N, True);
7800 end;
7801 end if;
7802 end Set_Renamed_Subprogram;
7804 ----------------------------------
7805 -- Silly_Boolean_Array_Not_Test --
7806 ----------------------------------
7808 -- This procedure implements an odd and silly test. We explicitly check
7809 -- for the case where the 'First of the component type is equal to the
7810 -- 'Last of this component type, and if this is the case, we make sure
7811 -- that constraint error is raised. The reason is that the NOT is bound
7812 -- to cause CE in this case, and we will not otherwise catch it.
7814 -- No such check is required for AND and OR, since for both these cases
7815 -- False op False = False, and True op True = True. For the XOR case,
7816 -- see Silly_Boolean_Array_Xor_Test.
7818 -- Believe it or not, this was reported as a bug. Note that nearly always,
7819 -- the test will evaluate statically to False, so the code will be
7820 -- statically removed, and no extra overhead caused.
7822 procedure Silly_Boolean_Array_Not_Test (N : Node_Id; T : Entity_Id) is
7823 Loc : constant Source_Ptr := Sloc (N);
7824 CT : constant Entity_Id := Component_Type (T);
7826 begin
7827 -- The check we install is
7829 -- constraint_error when
7830 -- component_type'first = component_type'last
7831 -- and then array_type'Length /= 0)
7833 -- We need the last guard because we don't want to raise CE for empty
7834 -- arrays since no out of range values result. (Empty arrays with a
7835 -- component type of True .. True -- very useful -- even the ACATS
7836 -- does not test that marginal case!)
7838 Insert_Action (N,
7839 Make_Raise_Constraint_Error (Loc,
7840 Condition =>
7841 Make_And_Then (Loc,
7842 Left_Opnd =>
7843 Make_Op_Eq (Loc,
7844 Left_Opnd =>
7845 Make_Attribute_Reference (Loc,
7846 Prefix => New_Occurrence_Of (CT, Loc),
7847 Attribute_Name => Name_First),
7849 Right_Opnd =>
7850 Make_Attribute_Reference (Loc,
7851 Prefix => New_Occurrence_Of (CT, Loc),
7852 Attribute_Name => Name_Last)),
7854 Right_Opnd => Make_Non_Empty_Check (Loc, Right_Opnd (N))),
7855 Reason => CE_Range_Check_Failed));
7856 end Silly_Boolean_Array_Not_Test;
7858 ----------------------------------
7859 -- Silly_Boolean_Array_Xor_Test --
7860 ----------------------------------
7862 -- This procedure implements an odd and silly test. We explicitly check
7863 -- for the XOR case where the component type is True .. True, since this
7864 -- will raise constraint error. A special check is required since CE
7865 -- will not be generated otherwise (cf Expand_Packed_Not).
7867 -- No such check is required for AND and OR, since for both these cases
7868 -- False op False = False, and True op True = True, and no check is
7869 -- required for the case of False .. False, since False xor False = False.
7870 -- See also Silly_Boolean_Array_Not_Test
7872 procedure Silly_Boolean_Array_Xor_Test (N : Node_Id; T : Entity_Id) is
7873 Loc : constant Source_Ptr := Sloc (N);
7874 CT : constant Entity_Id := Component_Type (T);
7876 begin
7877 -- The check we install is
7879 -- constraint_error when
7880 -- Boolean (component_type'First)
7881 -- and then Boolean (component_type'Last)
7882 -- and then array_type'Length /= 0)
7884 -- We need the last guard because we don't want to raise CE for empty
7885 -- arrays since no out of range values result (Empty arrays with a
7886 -- component type of True .. True -- very useful -- even the ACATS
7887 -- does not test that marginal case!).
7889 Insert_Action (N,
7890 Make_Raise_Constraint_Error (Loc,
7891 Condition =>
7892 Make_And_Then (Loc,
7893 Left_Opnd =>
7894 Make_And_Then (Loc,
7895 Left_Opnd =>
7896 Convert_To (Standard_Boolean,
7897 Make_Attribute_Reference (Loc,
7898 Prefix => New_Occurrence_Of (CT, Loc),
7899 Attribute_Name => Name_First)),
7901 Right_Opnd =>
7902 Convert_To (Standard_Boolean,
7903 Make_Attribute_Reference (Loc,
7904 Prefix => New_Occurrence_Of (CT, Loc),
7905 Attribute_Name => Name_Last))),
7907 Right_Opnd => Make_Non_Empty_Check (Loc, Right_Opnd (N))),
7908 Reason => CE_Range_Check_Failed));
7909 end Silly_Boolean_Array_Xor_Test;
7911 --------------------------
7912 -- Target_Has_Fixed_Ops --
7913 --------------------------
7915 Integer_Sized_Small : Ureal;
7916 -- Set to 2.0 ** -(Integer'Size - 1) the first time that this function is
7917 -- called (we don't want to compute it more than once!)
7919 Long_Integer_Sized_Small : Ureal;
7920 -- Set to 2.0 ** -(Long_Integer'Size - 1) the first time that this function
7921 -- is called (we don't want to compute it more than once)
7923 First_Time_For_THFO : Boolean := True;
7924 -- Set to False after first call (if Fractional_Fixed_Ops_On_Target)
7926 function Target_Has_Fixed_Ops
7927 (Left_Typ : Entity_Id;
7928 Right_Typ : Entity_Id;
7929 Result_Typ : Entity_Id) return Boolean
7931 function Is_Fractional_Type (Typ : Entity_Id) return Boolean;
7932 -- Return True if the given type is a fixed-point type with a small
7933 -- value equal to 2 ** (-(T'Object_Size - 1)) and whose values have
7934 -- an absolute value less than 1.0. This is currently limited to
7935 -- fixed-point types that map to Integer or Long_Integer.
7937 ------------------------
7938 -- Is_Fractional_Type --
7939 ------------------------
7941 function Is_Fractional_Type (Typ : Entity_Id) return Boolean is
7942 begin
7943 if Esize (Typ) = Standard_Integer_Size then
7944 return Small_Value (Typ) = Integer_Sized_Small;
7946 elsif Esize (Typ) = Standard_Long_Integer_Size then
7947 return Small_Value (Typ) = Long_Integer_Sized_Small;
7949 else
7950 return False;
7951 end if;
7952 end Is_Fractional_Type;
7954 -- Start of processing for Target_Has_Fixed_Ops
7956 begin
7957 -- Return False if Fractional_Fixed_Ops_On_Target is false
7959 if not Fractional_Fixed_Ops_On_Target then
7960 return False;
7961 end if;
7963 -- Here the target has Fractional_Fixed_Ops, if first time, compute
7964 -- standard constants used by Is_Fractional_Type.
7966 if First_Time_For_THFO then
7967 First_Time_For_THFO := False;
7969 Integer_Sized_Small :=
7970 UR_From_Components
7971 (Num => Uint_1,
7972 Den => UI_From_Int (Standard_Integer_Size - 1),
7973 Rbase => 2);
7975 Long_Integer_Sized_Small :=
7976 UR_From_Components
7977 (Num => Uint_1,
7978 Den => UI_From_Int (Standard_Long_Integer_Size - 1),
7979 Rbase => 2);
7980 end if;
7982 -- Return True if target supports fixed-by-fixed multiply/divide for
7983 -- fractional fixed-point types (see Is_Fractional_Type) and the operand
7984 -- and result types are equivalent fractional types.
7986 return Is_Fractional_Type (Base_Type (Left_Typ))
7987 and then Is_Fractional_Type (Base_Type (Right_Typ))
7988 and then Is_Fractional_Type (Base_Type (Result_Typ))
7989 and then Esize (Left_Typ) = Esize (Right_Typ)
7990 and then Esize (Left_Typ) = Esize (Result_Typ);
7991 end Target_Has_Fixed_Ops;
7993 ------------------------------------------
7994 -- Type_May_Have_Bit_Aligned_Components --
7995 ------------------------------------------
7997 function Type_May_Have_Bit_Aligned_Components
7998 (Typ : Entity_Id) return Boolean
8000 begin
8001 -- Array type, check component type
8003 if Is_Array_Type (Typ) then
8004 return
8005 Type_May_Have_Bit_Aligned_Components (Component_Type (Typ));
8007 -- Record type, check components
8009 elsif Is_Record_Type (Typ) then
8010 declare
8011 E : Entity_Id;
8013 begin
8014 E := First_Component_Or_Discriminant (Typ);
8015 while Present (E) loop
8016 if Component_May_Be_Bit_Aligned (E)
8017 or else Type_May_Have_Bit_Aligned_Components (Etype (E))
8018 then
8019 return True;
8020 end if;
8022 Next_Component_Or_Discriminant (E);
8023 end loop;
8025 return False;
8026 end;
8028 -- Type other than array or record is always OK
8030 else
8031 return False;
8032 end if;
8033 end Type_May_Have_Bit_Aligned_Components;
8035 ----------------------------------
8036 -- Within_Case_Or_If_Expression --
8037 ----------------------------------
8039 function Within_Case_Or_If_Expression (N : Node_Id) return Boolean is
8040 Par : Node_Id;
8042 begin
8043 -- Locate an enclosing case or if expression. Note that these constructs
8044 -- can be expanded into Expression_With_Actions, hence the test of the
8045 -- original node.
8047 Par := Parent (N);
8048 while Present (Par) loop
8049 if Nkind_In (Original_Node (Par), N_Case_Expression,
8050 N_If_Expression)
8051 then
8052 return True;
8054 -- Prevent the search from going too far
8056 elsif Is_Body_Or_Package_Declaration (Par) then
8057 return False;
8058 end if;
8060 Par := Parent (Par);
8061 end loop;
8063 return False;
8064 end Within_Case_Or_If_Expression;
8066 ----------------------------
8067 -- Wrap_Cleanup_Procedure --
8068 ----------------------------
8070 procedure Wrap_Cleanup_Procedure (N : Node_Id) is
8071 Loc : constant Source_Ptr := Sloc (N);
8072 Stseq : constant Node_Id := Handled_Statement_Sequence (N);
8073 Stmts : constant List_Id := Statements (Stseq);
8075 begin
8076 if Abort_Allowed then
8077 Prepend_To (Stmts, Build_Runtime_Call (Loc, RE_Abort_Defer));
8078 Append_To (Stmts, Build_Runtime_Call (Loc, RE_Abort_Undefer));
8079 end if;
8080 end Wrap_Cleanup_Procedure;
8082 end Exp_Util;