* config/rs6000/aix61.h (TARGET_DEFAULT): Add MASK_PPC_GPOPT,
[official-gcc.git] / gcc / ada / exp_util.adb
blobf7b9d450128e88862ee096d84c49138f4a6f73f2
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-2012, Free Software Foundation, Inc. --
10 -- --
11 -- GNAT is free software; you can redistribute it and/or modify it under --
12 -- terms of the GNU General Public License as published by the Free Soft- --
13 -- ware Foundation; either version 3, or (at your option) any later ver- --
14 -- sion. GNAT is distributed in the hope that it will be useful, but WITH- --
15 -- OUT ANY WARRANTY; without even the implied warranty of MERCHANTABILITY --
16 -- or FITNESS FOR A PARTICULAR PURPOSE. See the GNU General Public License --
17 -- for more details. You should have received a copy of the GNU General --
18 -- Public License distributed with GNAT; see file COPYING3. If not, go to --
19 -- http://www.gnu.org/licenses for a complete copy of the license. --
20 -- --
21 -- GNAT was originally developed by the GNAT team at New York University. --
22 -- Extensive contributions were provided by Ada Core Technologies Inc. --
23 -- --
24 ------------------------------------------------------------------------------
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_Prag; use Sem_Prag;
50 with Sem_Res; use Sem_Res;
51 with Sem_Type; use Sem_Type;
52 with Sem_Util; use Sem_Util;
53 with Snames; use Snames;
54 with Stand; use Stand;
55 with Stringt; use Stringt;
56 with Targparm; use Targparm;
57 with Tbuild; use Tbuild;
58 with Ttypes; use Ttypes;
59 with Urealp; use Urealp;
60 with Validsw; use Validsw;
62 package body Exp_Util is
64 -----------------------
65 -- Local Subprograms --
66 -----------------------
68 function Build_Task_Array_Image
69 (Loc : Source_Ptr;
70 Id_Ref : Node_Id;
71 A_Type : Entity_Id;
72 Dyn : Boolean := False) return Node_Id;
73 -- Build function to generate the image string for a task that is an array
74 -- component, concatenating the images of each index. To avoid storage
75 -- leaks, the string is built with successive slice assignments. The flag
76 -- Dyn indicates whether this is called for the initialization procedure of
77 -- an array of tasks, or for the name of a dynamically created task that is
78 -- assigned to an indexed component.
80 function Build_Task_Image_Function
81 (Loc : Source_Ptr;
82 Decls : List_Id;
83 Stats : List_Id;
84 Res : Entity_Id) return Node_Id;
85 -- Common processing for Task_Array_Image and Task_Record_Image. Build
86 -- function body that computes image.
88 procedure Build_Task_Image_Prefix
89 (Loc : Source_Ptr;
90 Len : out Entity_Id;
91 Res : out Entity_Id;
92 Pos : out Entity_Id;
93 Prefix : Entity_Id;
94 Sum : Node_Id;
95 Decls : List_Id;
96 Stats : List_Id);
97 -- Common processing for Task_Array_Image and Task_Record_Image. Create
98 -- local variables and assign prefix of name to result string.
100 function Build_Task_Record_Image
101 (Loc : Source_Ptr;
102 Id_Ref : Node_Id;
103 Dyn : Boolean := False) return Node_Id;
104 -- Build function to generate the image string for a task that is a record
105 -- component. Concatenate name of variable with that of selector. The flag
106 -- Dyn indicates whether this is called for the initialization procedure of
107 -- record with task components, or for a dynamically created task that is
108 -- assigned to a selected component.
110 function Make_CW_Equivalent_Type
111 (T : Entity_Id;
112 E : Node_Id) return Entity_Id;
113 -- T is a class-wide type entity, E is the initial expression node that
114 -- constrains T in case such as: " X: T := E" or "new T'(E)". This function
115 -- returns the entity of the Equivalent type and inserts on the fly the
116 -- necessary declaration such as:
118 -- type anon is record
119 -- _parent : Root_Type (T); constrained with E discriminants (if any)
120 -- Extension : String (1 .. expr to match size of E);
121 -- end record;
123 -- This record is compatible with any object of the class of T thanks to
124 -- the first field and has the same size as E thanks to the second.
126 function Make_Literal_Range
127 (Loc : Source_Ptr;
128 Literal_Typ : Entity_Id) return Node_Id;
129 -- Produce a Range node whose bounds are:
130 -- Low_Bound (Literal_Type) ..
131 -- Low_Bound (Literal_Type) + (Length (Literal_Typ) - 1)
132 -- this is used for expanding declarations like X : String := "sdfgdfg";
134 -- If the index type of the target array is not integer, we generate:
135 -- Low_Bound (Literal_Type) ..
136 -- Literal_Type'Val
137 -- (Literal_Type'Pos (Low_Bound (Literal_Type))
138 -- + (Length (Literal_Typ) -1))
140 function Make_Non_Empty_Check
141 (Loc : Source_Ptr;
142 N : Node_Id) return Node_Id;
143 -- Produce a boolean expression checking that the unidimensional array
144 -- node N is not empty.
146 function New_Class_Wide_Subtype
147 (CW_Typ : Entity_Id;
148 N : Node_Id) return Entity_Id;
149 -- Create an implicit subtype of CW_Typ attached to node N
151 function Requires_Cleanup_Actions
152 (L : List_Id;
153 Lib_Level : Boolean;
154 Nested_Constructs : Boolean) return Boolean;
155 -- Given a list L, determine whether it contains one of the following:
157 -- 1) controlled objects
158 -- 2) library-level tagged types
160 -- Lib_Level is True when the list comes from a construct at the library
161 -- level, and False otherwise. Nested_Constructs is True when any nested
162 -- packages declared in L must be processed, and False otherwise.
164 -------------------------------------
165 -- Activate_Atomic_Synchronization --
166 -------------------------------------
168 procedure Activate_Atomic_Synchronization (N : Node_Id) is
169 Msg_Node : Node_Id;
171 begin
172 case Nkind (Parent (N)) is
174 -- Check for cases of appearing in the prefix of a construct where
175 -- we don't need atomic synchronization for this kind of usage.
177 when
178 -- Nothing to do if we are the prefix of an attribute, since we
179 -- do not want an atomic sync operation for things like 'Size.
181 N_Attribute_Reference |
183 -- The N_Reference node is like an attribute
185 N_Reference |
187 -- Nothing to do for a reference to a component (or components)
188 -- of a composite object. Only reads and updates of the object
189 -- as a whole require atomic synchronization (RM C.6 (15)).
191 N_Indexed_Component |
192 N_Selected_Component |
193 N_Slice =>
195 -- For all the above cases, nothing to do if we are the prefix
197 if Prefix (Parent (N)) = N then
198 return;
199 end if;
201 when others => null;
202 end case;
204 -- Go ahead and set the flag
206 Set_Atomic_Sync_Required (N);
208 -- Generate info message if requested
210 if Warn_On_Atomic_Synchronization then
211 case Nkind (N) is
212 when N_Identifier =>
213 Msg_Node := N;
215 when N_Selected_Component | N_Expanded_Name =>
216 Msg_Node := Selector_Name (N);
218 when N_Explicit_Dereference | N_Indexed_Component =>
219 Msg_Node := Empty;
221 when others =>
222 pragma Assert (False);
223 return;
224 end case;
226 if Present (Msg_Node) then
227 Error_Msg_N ("?info: atomic synchronization set for &", Msg_Node);
228 else
229 Error_Msg_N ("?info: atomic synchronization set", N);
230 end if;
231 end if;
232 end Activate_Atomic_Synchronization;
234 ----------------------
235 -- Adjust_Condition --
236 ----------------------
238 procedure Adjust_Condition (N : Node_Id) is
239 begin
240 if No (N) then
241 return;
242 end if;
244 declare
245 Loc : constant Source_Ptr := Sloc (N);
246 T : constant Entity_Id := Etype (N);
247 Ti : Entity_Id;
249 begin
250 -- Defend against a call where the argument has no type, or has a
251 -- type that is not Boolean. This can occur because of prior errors.
253 if No (T) or else not Is_Boolean_Type (T) then
254 return;
255 end if;
257 -- Apply validity checking if needed
259 if Validity_Checks_On and Validity_Check_Tests then
260 Ensure_Valid (N);
261 end if;
263 -- Immediate return if standard boolean, the most common case,
264 -- where nothing needs to be done.
266 if Base_Type (T) = Standard_Boolean then
267 return;
268 end if;
270 -- Case of zero/non-zero semantics or non-standard enumeration
271 -- representation. In each case, we rewrite the node as:
273 -- ityp!(N) /= False'Enum_Rep
275 -- where ityp is an integer type with large enough size to hold any
276 -- value of type T.
278 if Nonzero_Is_True (T) or else Has_Non_Standard_Rep (T) then
279 if Esize (T) <= Esize (Standard_Integer) then
280 Ti := Standard_Integer;
281 else
282 Ti := Standard_Long_Long_Integer;
283 end if;
285 Rewrite (N,
286 Make_Op_Ne (Loc,
287 Left_Opnd => Unchecked_Convert_To (Ti, N),
288 Right_Opnd =>
289 Make_Attribute_Reference (Loc,
290 Attribute_Name => Name_Enum_Rep,
291 Prefix =>
292 New_Occurrence_Of (First_Literal (T), Loc))));
293 Analyze_And_Resolve (N, Standard_Boolean);
295 else
296 Rewrite (N, Convert_To (Standard_Boolean, N));
297 Analyze_And_Resolve (N, Standard_Boolean);
298 end if;
299 end;
300 end Adjust_Condition;
302 ------------------------
303 -- Adjust_Result_Type --
304 ------------------------
306 procedure Adjust_Result_Type (N : Node_Id; T : Entity_Id) is
307 begin
308 -- Ignore call if current type is not Standard.Boolean
310 if Etype (N) /= Standard_Boolean then
311 return;
312 end if;
314 -- If result is already of correct type, nothing to do. Note that
315 -- this will get the most common case where everything has a type
316 -- of Standard.Boolean.
318 if Base_Type (T) = Standard_Boolean then
319 return;
321 else
322 declare
323 KP : constant Node_Kind := Nkind (Parent (N));
325 begin
326 -- If result is to be used as a Condition in the syntax, no need
327 -- to convert it back, since if it was changed to Standard.Boolean
328 -- using Adjust_Condition, that is just fine for this usage.
330 if KP in N_Raise_xxx_Error or else KP in N_Has_Condition then
331 return;
333 -- If result is an operand of another logical operation, no need
334 -- to reset its type, since Standard.Boolean is just fine, and
335 -- such operations always do Adjust_Condition on their operands.
337 elsif KP in N_Op_Boolean
338 or else KP in N_Short_Circuit
339 or else KP = N_Op_Not
340 then
341 return;
343 -- Otherwise we perform a conversion from the current type, which
344 -- must be Standard.Boolean, to the desired type.
346 else
347 Set_Analyzed (N);
348 Rewrite (N, Convert_To (T, N));
349 Analyze_And_Resolve (N, T);
350 end if;
351 end;
352 end if;
353 end Adjust_Result_Type;
355 --------------------------
356 -- Append_Freeze_Action --
357 --------------------------
359 procedure Append_Freeze_Action (T : Entity_Id; N : Node_Id) is
360 Fnode : Node_Id;
362 begin
363 Ensure_Freeze_Node (T);
364 Fnode := Freeze_Node (T);
366 if No (Actions (Fnode)) then
367 Set_Actions (Fnode, New_List);
368 end if;
370 Append (N, Actions (Fnode));
371 end Append_Freeze_Action;
373 ---------------------------
374 -- Append_Freeze_Actions --
375 ---------------------------
377 procedure Append_Freeze_Actions (T : Entity_Id; L : List_Id) is
378 Fnode : constant Node_Id := Freeze_Node (T);
380 begin
381 if No (L) then
382 return;
384 else
385 if No (Actions (Fnode)) then
386 Set_Actions (Fnode, L);
387 else
388 Append_List (L, Actions (Fnode));
389 end if;
390 end if;
391 end Append_Freeze_Actions;
393 ------------------------------------
394 -- Build_Allocate_Deallocate_Proc --
395 ------------------------------------
397 procedure Build_Allocate_Deallocate_Proc
398 (N : Node_Id;
399 Is_Allocate : Boolean)
401 Desig_Typ : Entity_Id;
402 Expr : Node_Id;
403 Pool_Id : Entity_Id;
404 Proc_To_Call : Node_Id := Empty;
405 Ptr_Typ : Entity_Id;
407 function Find_Finalize_Address (Typ : Entity_Id) return Entity_Id;
408 -- Locate TSS primitive Finalize_Address in type Typ
410 function Find_Object (E : Node_Id) return Node_Id;
411 -- Given an arbitrary expression of an allocator, try to find an object
412 -- reference in it, otherwise return the original expression.
414 function Is_Allocate_Deallocate_Proc (Subp : Entity_Id) return Boolean;
415 -- Determine whether subprogram Subp denotes a custom allocate or
416 -- deallocate.
418 ---------------------------
419 -- Find_Finalize_Address --
420 ---------------------------
422 function Find_Finalize_Address (Typ : Entity_Id) return Entity_Id is
423 Utyp : Entity_Id := Typ;
425 begin
426 -- Handle protected class-wide or task class-wide types
428 if Is_Class_Wide_Type (Utyp) then
429 if Is_Concurrent_Type (Root_Type (Utyp)) then
430 Utyp := Root_Type (Utyp);
432 elsif Is_Private_Type (Root_Type (Utyp))
433 and then Present (Full_View (Root_Type (Utyp)))
434 and then Is_Concurrent_Type (Full_View (Root_Type (Utyp)))
435 then
436 Utyp := Full_View (Root_Type (Utyp));
437 end if;
438 end if;
440 -- Handle private types
442 if Is_Private_Type (Utyp)
443 and then Present (Full_View (Utyp))
444 then
445 Utyp := Full_View (Utyp);
446 end if;
448 -- Handle protected and task types
450 if Is_Concurrent_Type (Utyp)
451 and then Present (Corresponding_Record_Type (Utyp))
452 then
453 Utyp := Corresponding_Record_Type (Utyp);
454 end if;
456 Utyp := Underlying_Type (Base_Type (Utyp));
458 -- Deal with non-tagged derivation of private views. If the parent is
459 -- now known to be protected, the finalization routine is the one
460 -- defined on the corresponding record of the ancestor (corresponding
461 -- records do not automatically inherit operations, but maybe they
462 -- should???)
464 if Is_Untagged_Derivation (Typ) then
465 if Is_Protected_Type (Typ) then
466 Utyp := Corresponding_Record_Type (Root_Type (Base_Type (Typ)));
467 else
468 Utyp := Underlying_Type (Root_Type (Base_Type (Typ)));
470 if Is_Protected_Type (Utyp) then
471 Utyp := Corresponding_Record_Type (Utyp);
472 end if;
473 end if;
474 end if;
476 -- If the underlying_type is a subtype, we are dealing with the
477 -- completion of a private type. We need to access the base type and
478 -- generate a conversion to it.
480 if Utyp /= Base_Type (Utyp) then
481 pragma Assert (Is_Private_Type (Typ));
483 Utyp := Base_Type (Utyp);
484 end if;
486 -- When dealing with an internally built full view for a type with
487 -- unknown discriminants, use the original record type.
489 if Is_Underlying_Record_View (Utyp) then
490 Utyp := Etype (Utyp);
491 end if;
493 return TSS (Utyp, TSS_Finalize_Address);
494 end Find_Finalize_Address;
496 -----------------
497 -- Find_Object --
498 -----------------
500 function Find_Object (E : Node_Id) return Node_Id is
501 Expr : Node_Id;
503 begin
504 pragma Assert (Is_Allocate);
506 Expr := E;
507 loop
508 if Nkind_In (Expr, N_Qualified_Expression,
509 N_Unchecked_Type_Conversion)
510 then
511 Expr := Expression (Expr);
513 elsif Nkind (Expr) = N_Explicit_Dereference then
514 Expr := Prefix (Expr);
516 else
517 exit;
518 end if;
519 end loop;
521 return Expr;
522 end Find_Object;
524 ---------------------------------
525 -- Is_Allocate_Deallocate_Proc --
526 ---------------------------------
528 function Is_Allocate_Deallocate_Proc (Subp : Entity_Id) return Boolean is
529 begin
530 -- Look for a subprogram body with only one statement which is a
531 -- call to Allocate_Any_Controlled / Deallocate_Any_Controlled.
533 if Ekind (Subp) = E_Procedure
534 and then Nkind (Parent (Parent (Subp))) = N_Subprogram_Body
535 then
536 declare
537 HSS : constant Node_Id :=
538 Handled_Statement_Sequence (Parent (Parent (Subp)));
539 Proc : Entity_Id;
541 begin
542 if Present (Statements (HSS))
543 and then Nkind (First (Statements (HSS))) =
544 N_Procedure_Call_Statement
545 then
546 Proc := Entity (Name (First (Statements (HSS))));
548 return
549 Is_RTE (Proc, RE_Allocate_Any_Controlled)
550 or else Is_RTE (Proc, RE_Deallocate_Any_Controlled);
551 end if;
552 end;
553 end if;
555 return False;
556 end Is_Allocate_Deallocate_Proc;
558 -- Start of processing for Build_Allocate_Deallocate_Proc
560 begin
561 -- Do not perform this expansion in Alfa mode because it is not
562 -- necessary.
564 if Alfa_Mode then
565 return;
566 end if;
568 -- Obtain the attributes of the allocation / deallocation
570 if Nkind (N) = N_Free_Statement then
571 Expr := Expression (N);
572 Ptr_Typ := Base_Type (Etype (Expr));
573 Proc_To_Call := Procedure_To_Call (N);
575 else
576 if Nkind (N) = N_Object_Declaration then
577 Expr := Expression (N);
578 else
579 Expr := N;
580 end if;
582 -- In certain cases an allocator with a qualified expression may
583 -- be relocated and used as the initialization expression of a
584 -- temporary:
586 -- before:
587 -- Obj : Ptr_Typ := new Desig_Typ'(...);
589 -- after:
590 -- Tmp : Ptr_Typ := new Desig_Typ'(...);
591 -- Obj : Ptr_Typ := Tmp;
593 -- Since the allocator is always marked as analyzed to avoid infinite
594 -- expansion, it will never be processed by this routine given that
595 -- the designated type needs finalization actions. Detect this case
596 -- and complete the expansion of the allocator.
598 if Nkind (Expr) = N_Identifier
599 and then Nkind (Parent (Entity (Expr))) = N_Object_Declaration
600 and then Nkind (Expression (Parent (Entity (Expr)))) = N_Allocator
601 then
602 Build_Allocate_Deallocate_Proc (Parent (Entity (Expr)), True);
603 return;
604 end if;
606 -- The allocator may have been rewritten into something else in which
607 -- case the expansion performed by this routine does not apply.
609 if Nkind (Expr) /= N_Allocator then
610 return;
611 end if;
613 Ptr_Typ := Base_Type (Etype (Expr));
614 Proc_To_Call := Procedure_To_Call (Expr);
615 end if;
617 Pool_Id := Associated_Storage_Pool (Ptr_Typ);
618 Desig_Typ := Available_View (Designated_Type (Ptr_Typ));
620 -- Handle concurrent types
622 if Is_Concurrent_Type (Desig_Typ)
623 and then Present (Corresponding_Record_Type (Desig_Typ))
624 then
625 Desig_Typ := Corresponding_Record_Type (Desig_Typ);
626 end if;
628 -- Do not process allocations / deallocations without a pool
630 if No (Pool_Id) then
631 return;
633 -- Do not process allocations on / deallocations from the secondary
634 -- stack.
636 elsif Is_RTE (Pool_Id, RE_SS_Pool) then
637 return;
639 -- Do not replicate the machinery if the allocator / free has already
640 -- been expanded and has a custom Allocate / Deallocate.
642 elsif Present (Proc_To_Call)
643 and then Is_Allocate_Deallocate_Proc (Proc_To_Call)
644 then
645 return;
646 end if;
648 if Needs_Finalization (Desig_Typ) then
650 -- Certain run-time configurations and targets do not provide support
651 -- for controlled types.
653 if Restriction_Active (No_Finalization) then
654 return;
656 -- Do nothing if the access type may never allocate / deallocate
657 -- objects.
659 elsif No_Pool_Assigned (Ptr_Typ) then
660 return;
662 -- Access-to-controlled types are not supported on .NET/JVM since
663 -- these targets cannot support pools and address arithmetic.
665 elsif VM_Target /= No_VM then
666 return;
667 end if;
669 -- The allocation / deallocation of a controlled object must be
670 -- chained on / detached from a finalization master.
672 pragma Assert (Present (Finalization_Master (Ptr_Typ)));
674 -- The only other kind of allocation / deallocation supported by this
675 -- routine is on / from a subpool.
677 elsif Nkind (Expr) = N_Allocator
678 and then No (Subpool_Handle_Name (Expr))
679 then
680 return;
681 end if;
683 declare
684 Loc : constant Source_Ptr := Sloc (N);
685 Addr_Id : constant Entity_Id := Make_Temporary (Loc, 'A');
686 Alig_Id : constant Entity_Id := Make_Temporary (Loc, 'L');
687 Proc_Id : constant Entity_Id := Make_Temporary (Loc, 'P');
688 Size_Id : constant Entity_Id := Make_Temporary (Loc, 'S');
690 Actuals : List_Id;
691 Fin_Addr_Id : Entity_Id;
692 Fin_Mas_Act : Node_Id;
693 Fin_Mas_Id : Entity_Id;
694 Proc_To_Call : Entity_Id;
695 Subpool : Node_Id := Empty;
697 begin
698 -- Step 1: Construct all the actuals for the call to library routine
699 -- Allocate_Any_Controlled / Deallocate_Any_Controlled.
701 -- a) Storage pool
703 Actuals := New_List (New_Reference_To (Pool_Id, Loc));
705 if Is_Allocate then
707 -- b) Subpool
709 if Nkind (Expr) = N_Allocator then
710 Subpool := Subpool_Handle_Name (Expr);
711 end if;
713 if Present (Subpool) then
714 Append_To (Actuals, New_Reference_To (Entity (Subpool), Loc));
715 else
716 Append_To (Actuals, Make_Null (Loc));
717 end if;
719 -- c) Finalization master
721 if Needs_Finalization (Desig_Typ) then
722 Fin_Mas_Id := Finalization_Master (Ptr_Typ);
723 Fin_Mas_Act := New_Reference_To (Fin_Mas_Id, Loc);
725 -- Handle the case where the master is actually a pointer to a
726 -- master. This case arises in build-in-place functions.
728 if Is_Access_Type (Etype (Fin_Mas_Id)) then
729 Append_To (Actuals, Fin_Mas_Act);
730 else
731 Append_To (Actuals,
732 Make_Attribute_Reference (Loc,
733 Prefix => Fin_Mas_Act,
734 Attribute_Name => Name_Unrestricted_Access));
735 end if;
736 else
737 Append_To (Actuals, Make_Null (Loc));
738 end if;
740 -- d) Finalize_Address
742 -- Primitive Finalize_Address is never generated in CodePeer mode
743 -- since it contains an Unchecked_Conversion.
745 if Needs_Finalization (Desig_Typ)
746 and then not CodePeer_Mode
747 then
748 Fin_Addr_Id := Find_Finalize_Address (Desig_Typ);
749 pragma Assert (Present (Fin_Addr_Id));
751 Append_To (Actuals,
752 Make_Attribute_Reference (Loc,
753 Prefix => New_Reference_To (Fin_Addr_Id, Loc),
754 Attribute_Name => Name_Unrestricted_Access));
755 else
756 Append_To (Actuals, Make_Null (Loc));
757 end if;
758 end if;
760 -- e) Address
761 -- f) Storage_Size
762 -- g) Alignment
764 Append_To (Actuals, New_Reference_To (Addr_Id, Loc));
765 Append_To (Actuals, New_Reference_To (Size_Id, Loc));
767 if Is_Allocate or else not Is_Class_Wide_Type (Desig_Typ) then
768 Append_To (Actuals, New_Reference_To (Alig_Id, Loc));
770 -- For deallocation of class wide types we obtain the value of
771 -- alignment from the Type Specific Record of the deallocated object.
772 -- This is needed because the frontend expansion of class-wide types
773 -- into equivalent types confuses the backend.
775 else
776 -- Generate:
777 -- Obj.all'Alignment
779 -- ... because 'Alignment applied to class-wide types is expanded
780 -- into the code that reads the value of alignment from the TSD
781 -- (see Expand_N_Attribute_Reference)
783 Append_To (Actuals,
784 Unchecked_Convert_To (RTE (RE_Storage_Offset),
785 Make_Attribute_Reference (Loc,
786 Prefix =>
787 Make_Explicit_Dereference (Loc, Relocate_Node (Expr)),
788 Attribute_Name => Name_Alignment)));
789 end if;
791 -- h) Is_Controlled
793 -- Generate a run-time check to determine whether a class-wide object
794 -- is truly controlled.
796 if Needs_Finalization (Desig_Typ) then
797 if Is_Class_Wide_Type (Desig_Typ)
798 or else Is_Generic_Actual_Type (Desig_Typ)
799 then
800 declare
801 Flag_Id : constant Entity_Id := Make_Temporary (Loc, 'F');
802 Flag_Expr : Node_Id;
803 Param : Node_Id;
804 Temp : Node_Id;
806 begin
807 if Is_Allocate then
808 Temp := Find_Object (Expression (Expr));
809 else
810 Temp := Expr;
811 end if;
813 -- Processing for generic actuals
815 if Is_Generic_Actual_Type (Desig_Typ) then
816 Flag_Expr :=
817 New_Reference_To (Boolean_Literals
818 (Needs_Finalization (Base_Type (Desig_Typ))), Loc);
820 -- Processing for subtype indications
822 elsif Nkind (Temp) in N_Has_Entity
823 and then Is_Type (Entity (Temp))
824 then
825 Flag_Expr :=
826 New_Reference_To (Boolean_Literals
827 (Needs_Finalization (Entity (Temp))), Loc);
829 -- Generate a runtime check to test the controlled state of
830 -- an object for the purposes of allocation / deallocation.
832 else
833 -- The following case arises when allocating through an
834 -- interface class-wide type, generate:
836 -- Temp.all
838 if Is_RTE (Etype (Temp), RE_Tag_Ptr) then
839 Param :=
840 Make_Explicit_Dereference (Loc,
841 Prefix =>
842 Relocate_Node (Temp));
844 -- Generate:
845 -- Temp'Tag
847 else
848 Param :=
849 Make_Attribute_Reference (Loc,
850 Prefix =>
851 Relocate_Node (Temp),
852 Attribute_Name => Name_Tag);
853 end if;
855 -- Generate:
856 -- Needs_Finalization (<Param>)
858 Flag_Expr :=
859 Make_Function_Call (Loc,
860 Name =>
861 New_Reference_To (RTE (RE_Needs_Finalization), Loc),
862 Parameter_Associations => New_List (Param));
863 end if;
865 -- Create the temporary which represents the finalization
866 -- state of the expression. Generate:
868 -- F : constant Boolean := <Flag_Expr>;
870 Insert_Action (N,
871 Make_Object_Declaration (Loc,
872 Defining_Identifier => Flag_Id,
873 Constant_Present => True,
874 Object_Definition =>
875 New_Reference_To (Standard_Boolean, Loc),
876 Expression => Flag_Expr));
878 -- The flag acts as the last actual
880 Append_To (Actuals, New_Reference_To (Flag_Id, Loc));
881 end;
883 -- The object is statically known to be controlled
885 else
886 Append_To (Actuals, New_Reference_To (Standard_True, Loc));
887 end if;
889 else
890 Append_To (Actuals, New_Reference_To (Standard_False, Loc));
891 end if;
893 -- i) On_Subpool
895 if Is_Allocate then
896 Append_To (Actuals,
897 New_Reference_To (Boolean_Literals (Present (Subpool)), Loc));
898 end if;
900 -- Step 2: Build a wrapper Allocate / Deallocate which internally
901 -- calls Allocate_Any_Controlled / Deallocate_Any_Controlled.
903 -- Select the proper routine to call
905 if Is_Allocate then
906 Proc_To_Call := RTE (RE_Allocate_Any_Controlled);
907 else
908 Proc_To_Call := RTE (RE_Deallocate_Any_Controlled);
909 end if;
911 -- Create a custom Allocate / Deallocate routine which has identical
912 -- profile to that of System.Storage_Pools.
914 Insert_Action (N,
915 Make_Subprogram_Body (Loc,
916 Specification =>
918 -- procedure Pnn
920 Make_Procedure_Specification (Loc,
921 Defining_Unit_Name => Proc_Id,
922 Parameter_Specifications => New_List (
924 -- P : Root_Storage_Pool
926 Make_Parameter_Specification (Loc,
927 Defining_Identifier => Make_Temporary (Loc, 'P'),
928 Parameter_Type =>
929 New_Reference_To (RTE (RE_Root_Storage_Pool), Loc)),
931 -- A : [out] Address
933 Make_Parameter_Specification (Loc,
934 Defining_Identifier => Addr_Id,
935 Out_Present => Is_Allocate,
936 Parameter_Type =>
937 New_Reference_To (RTE (RE_Address), Loc)),
939 -- S : Storage_Count
941 Make_Parameter_Specification (Loc,
942 Defining_Identifier => Size_Id,
943 Parameter_Type =>
944 New_Reference_To (RTE (RE_Storage_Count), Loc)),
946 -- L : Storage_Count
948 Make_Parameter_Specification (Loc,
949 Defining_Identifier => Alig_Id,
950 Parameter_Type =>
951 New_Reference_To (RTE (RE_Storage_Count), Loc)))),
953 Declarations => No_List,
955 Handled_Statement_Sequence =>
956 Make_Handled_Sequence_Of_Statements (Loc,
957 Statements => New_List (
958 Make_Procedure_Call_Statement (Loc,
959 Name => New_Reference_To (Proc_To_Call, Loc),
960 Parameter_Associations => Actuals)))));
962 -- The newly generated Allocate / Deallocate becomes the default
963 -- procedure to call when the back end processes the allocation /
964 -- deallocation.
966 if Is_Allocate then
967 Set_Procedure_To_Call (Expr, Proc_Id);
968 else
969 Set_Procedure_To_Call (N, Proc_Id);
970 end if;
971 end;
972 end Build_Allocate_Deallocate_Proc;
974 ------------------------
975 -- Build_Runtime_Call --
976 ------------------------
978 function Build_Runtime_Call (Loc : Source_Ptr; RE : RE_Id) return Node_Id is
979 begin
980 -- If entity is not available, we can skip making the call (this avoids
981 -- junk duplicated error messages in a number of cases).
983 if not RTE_Available (RE) then
984 return Make_Null_Statement (Loc);
985 else
986 return
987 Make_Procedure_Call_Statement (Loc,
988 Name => New_Reference_To (RTE (RE), Loc));
989 end if;
990 end Build_Runtime_Call;
992 ----------------------------
993 -- Build_Task_Array_Image --
994 ----------------------------
996 -- This function generates the body for a function that constructs the
997 -- image string for a task that is an array component. The function is
998 -- local to the init proc for the array type, and is called for each one
999 -- of the components. The constructed image has the form of an indexed
1000 -- component, whose prefix is the outer variable of the array type.
1001 -- The n-dimensional array type has known indexes Index, Index2...
1003 -- Id_Ref is an indexed component form created by the enclosing init proc.
1004 -- Its successive indexes are Val1, Val2, ... which are the loop variables
1005 -- in the loops that call the individual task init proc on each component.
1007 -- The generated function has the following structure:
1009 -- function F return String is
1010 -- Pref : string renames Task_Name;
1011 -- T1 : String := Index1'Image (Val1);
1012 -- ...
1013 -- Tn : String := indexn'image (Valn);
1014 -- Len : Integer := T1'Length + ... + Tn'Length + n + 1;
1015 -- -- Len includes commas and the end parentheses.
1016 -- Res : String (1..Len);
1017 -- Pos : Integer := Pref'Length;
1019 -- begin
1020 -- Res (1 .. Pos) := Pref;
1021 -- Pos := Pos + 1;
1022 -- Res (Pos) := '(';
1023 -- Pos := Pos + 1;
1024 -- Res (Pos .. Pos + T1'Length - 1) := T1;
1025 -- Pos := Pos + T1'Length;
1026 -- Res (Pos) := '.';
1027 -- Pos := Pos + 1;
1028 -- ...
1029 -- Res (Pos .. Pos + Tn'Length - 1) := Tn;
1030 -- Res (Len) := ')';
1032 -- return Res;
1033 -- end F;
1035 -- Needless to say, multidimensional arrays of tasks are rare enough that
1036 -- the bulkiness of this code is not really a concern.
1038 function Build_Task_Array_Image
1039 (Loc : Source_Ptr;
1040 Id_Ref : Node_Id;
1041 A_Type : Entity_Id;
1042 Dyn : Boolean := False) return Node_Id
1044 Dims : constant Nat := Number_Dimensions (A_Type);
1045 -- Number of dimensions for array of tasks
1047 Temps : array (1 .. Dims) of Entity_Id;
1048 -- Array of temporaries to hold string for each index
1050 Indx : Node_Id;
1051 -- Index expression
1053 Len : Entity_Id;
1054 -- Total length of generated name
1056 Pos : Entity_Id;
1057 -- Running index for substring assignments
1059 Pref : constant Entity_Id := Make_Temporary (Loc, 'P');
1060 -- Name of enclosing variable, prefix of resulting name
1062 Res : Entity_Id;
1063 -- String to hold result
1065 Val : Node_Id;
1066 -- Value of successive indexes
1068 Sum : Node_Id;
1069 -- Expression to compute total size of string
1071 T : Entity_Id;
1072 -- Entity for name at one index position
1074 Decls : constant List_Id := New_List;
1075 Stats : constant List_Id := New_List;
1077 begin
1078 -- For a dynamic task, the name comes from the target variable. For a
1079 -- static one it is a formal of the enclosing init proc.
1081 if Dyn then
1082 Get_Name_String (Chars (Entity (Prefix (Id_Ref))));
1083 Append_To (Decls,
1084 Make_Object_Declaration (Loc,
1085 Defining_Identifier => Pref,
1086 Object_Definition => New_Occurrence_Of (Standard_String, Loc),
1087 Expression =>
1088 Make_String_Literal (Loc,
1089 Strval => String_From_Name_Buffer)));
1091 else
1092 Append_To (Decls,
1093 Make_Object_Renaming_Declaration (Loc,
1094 Defining_Identifier => Pref,
1095 Subtype_Mark => New_Occurrence_Of (Standard_String, Loc),
1096 Name => Make_Identifier (Loc, Name_uTask_Name)));
1097 end if;
1099 Indx := First_Index (A_Type);
1100 Val := First (Expressions (Id_Ref));
1102 for J in 1 .. Dims loop
1103 T := Make_Temporary (Loc, 'T');
1104 Temps (J) := T;
1106 Append_To (Decls,
1107 Make_Object_Declaration (Loc,
1108 Defining_Identifier => T,
1109 Object_Definition => New_Occurrence_Of (Standard_String, Loc),
1110 Expression =>
1111 Make_Attribute_Reference (Loc,
1112 Attribute_Name => Name_Image,
1113 Prefix => New_Occurrence_Of (Etype (Indx), Loc),
1114 Expressions => New_List (New_Copy_Tree (Val)))));
1116 Next_Index (Indx);
1117 Next (Val);
1118 end loop;
1120 Sum := Make_Integer_Literal (Loc, Dims + 1);
1122 Sum :=
1123 Make_Op_Add (Loc,
1124 Left_Opnd => Sum,
1125 Right_Opnd =>
1126 Make_Attribute_Reference (Loc,
1127 Attribute_Name => Name_Length,
1128 Prefix =>
1129 New_Occurrence_Of (Pref, Loc),
1130 Expressions => New_List (Make_Integer_Literal (Loc, 1))));
1132 for J in 1 .. Dims loop
1133 Sum :=
1134 Make_Op_Add (Loc,
1135 Left_Opnd => Sum,
1136 Right_Opnd =>
1137 Make_Attribute_Reference (Loc,
1138 Attribute_Name => Name_Length,
1139 Prefix =>
1140 New_Occurrence_Of (Temps (J), Loc),
1141 Expressions => New_List (Make_Integer_Literal (Loc, 1))));
1142 end loop;
1144 Build_Task_Image_Prefix (Loc, Len, Res, Pos, Pref, Sum, Decls, Stats);
1146 Set_Character_Literal_Name (Char_Code (Character'Pos ('(')));
1148 Append_To (Stats,
1149 Make_Assignment_Statement (Loc,
1150 Name => Make_Indexed_Component (Loc,
1151 Prefix => New_Occurrence_Of (Res, Loc),
1152 Expressions => New_List (New_Occurrence_Of (Pos, Loc))),
1153 Expression =>
1154 Make_Character_Literal (Loc,
1155 Chars => Name_Find,
1156 Char_Literal_Value =>
1157 UI_From_Int (Character'Pos ('(')))));
1159 Append_To (Stats,
1160 Make_Assignment_Statement (Loc,
1161 Name => New_Occurrence_Of (Pos, Loc),
1162 Expression =>
1163 Make_Op_Add (Loc,
1164 Left_Opnd => New_Occurrence_Of (Pos, Loc),
1165 Right_Opnd => Make_Integer_Literal (Loc, 1))));
1167 for J in 1 .. Dims loop
1169 Append_To (Stats,
1170 Make_Assignment_Statement (Loc,
1171 Name => Make_Slice (Loc,
1172 Prefix => New_Occurrence_Of (Res, Loc),
1173 Discrete_Range =>
1174 Make_Range (Loc,
1175 Low_Bound => New_Occurrence_Of (Pos, Loc),
1176 High_Bound => Make_Op_Subtract (Loc,
1177 Left_Opnd =>
1178 Make_Op_Add (Loc,
1179 Left_Opnd => New_Occurrence_Of (Pos, Loc),
1180 Right_Opnd =>
1181 Make_Attribute_Reference (Loc,
1182 Attribute_Name => Name_Length,
1183 Prefix =>
1184 New_Occurrence_Of (Temps (J), Loc),
1185 Expressions =>
1186 New_List (Make_Integer_Literal (Loc, 1)))),
1187 Right_Opnd => Make_Integer_Literal (Loc, 1)))),
1189 Expression => New_Occurrence_Of (Temps (J), Loc)));
1191 if J < Dims then
1192 Append_To (Stats,
1193 Make_Assignment_Statement (Loc,
1194 Name => New_Occurrence_Of (Pos, Loc),
1195 Expression =>
1196 Make_Op_Add (Loc,
1197 Left_Opnd => New_Occurrence_Of (Pos, Loc),
1198 Right_Opnd =>
1199 Make_Attribute_Reference (Loc,
1200 Attribute_Name => Name_Length,
1201 Prefix => New_Occurrence_Of (Temps (J), Loc),
1202 Expressions =>
1203 New_List (Make_Integer_Literal (Loc, 1))))));
1205 Set_Character_Literal_Name (Char_Code (Character'Pos (',')));
1207 Append_To (Stats,
1208 Make_Assignment_Statement (Loc,
1209 Name => Make_Indexed_Component (Loc,
1210 Prefix => New_Occurrence_Of (Res, Loc),
1211 Expressions => New_List (New_Occurrence_Of (Pos, Loc))),
1212 Expression =>
1213 Make_Character_Literal (Loc,
1214 Chars => Name_Find,
1215 Char_Literal_Value =>
1216 UI_From_Int (Character'Pos (',')))));
1218 Append_To (Stats,
1219 Make_Assignment_Statement (Loc,
1220 Name => New_Occurrence_Of (Pos, Loc),
1221 Expression =>
1222 Make_Op_Add (Loc,
1223 Left_Opnd => New_Occurrence_Of (Pos, Loc),
1224 Right_Opnd => Make_Integer_Literal (Loc, 1))));
1225 end if;
1226 end loop;
1228 Set_Character_Literal_Name (Char_Code (Character'Pos (')')));
1230 Append_To (Stats,
1231 Make_Assignment_Statement (Loc,
1232 Name => Make_Indexed_Component (Loc,
1233 Prefix => New_Occurrence_Of (Res, Loc),
1234 Expressions => New_List (New_Occurrence_Of (Len, Loc))),
1235 Expression =>
1236 Make_Character_Literal (Loc,
1237 Chars => Name_Find,
1238 Char_Literal_Value =>
1239 UI_From_Int (Character'Pos (')')))));
1240 return Build_Task_Image_Function (Loc, Decls, Stats, Res);
1241 end Build_Task_Array_Image;
1243 ----------------------------
1244 -- Build_Task_Image_Decls --
1245 ----------------------------
1247 function Build_Task_Image_Decls
1248 (Loc : Source_Ptr;
1249 Id_Ref : Node_Id;
1250 A_Type : Entity_Id;
1251 In_Init_Proc : Boolean := False) return List_Id
1253 Decls : constant List_Id := New_List;
1254 T_Id : Entity_Id := Empty;
1255 Decl : Node_Id;
1256 Expr : Node_Id := Empty;
1257 Fun : Node_Id := Empty;
1258 Is_Dyn : constant Boolean :=
1259 Nkind (Parent (Id_Ref)) = N_Assignment_Statement
1260 and then
1261 Nkind (Expression (Parent (Id_Ref))) = N_Allocator;
1263 begin
1264 -- If Discard_Names or No_Implicit_Heap_Allocations are in effect,
1265 -- generate a dummy declaration only.
1267 if Restriction_Active (No_Implicit_Heap_Allocations)
1268 or else Global_Discard_Names
1269 then
1270 T_Id := Make_Temporary (Loc, 'J');
1271 Name_Len := 0;
1273 return
1274 New_List (
1275 Make_Object_Declaration (Loc,
1276 Defining_Identifier => T_Id,
1277 Object_Definition => New_Occurrence_Of (Standard_String, Loc),
1278 Expression =>
1279 Make_String_Literal (Loc,
1280 Strval => String_From_Name_Buffer)));
1282 else
1283 if Nkind (Id_Ref) = N_Identifier
1284 or else Nkind (Id_Ref) = N_Defining_Identifier
1285 then
1286 -- For a simple variable, the image of the task is built from
1287 -- the name of the variable. To avoid possible conflict with the
1288 -- anonymous type created for a single protected object, add a
1289 -- numeric suffix.
1291 T_Id :=
1292 Make_Defining_Identifier (Loc,
1293 New_External_Name (Chars (Id_Ref), 'T', 1));
1295 Get_Name_String (Chars (Id_Ref));
1297 Expr :=
1298 Make_String_Literal (Loc,
1299 Strval => String_From_Name_Buffer);
1301 elsif Nkind (Id_Ref) = N_Selected_Component then
1302 T_Id :=
1303 Make_Defining_Identifier (Loc,
1304 New_External_Name (Chars (Selector_Name (Id_Ref)), 'T'));
1305 Fun := Build_Task_Record_Image (Loc, Id_Ref, Is_Dyn);
1307 elsif Nkind (Id_Ref) = N_Indexed_Component then
1308 T_Id :=
1309 Make_Defining_Identifier (Loc,
1310 New_External_Name (Chars (A_Type), 'N'));
1312 Fun := Build_Task_Array_Image (Loc, Id_Ref, A_Type, Is_Dyn);
1313 end if;
1314 end if;
1316 if Present (Fun) then
1317 Append (Fun, Decls);
1318 Expr := Make_Function_Call (Loc,
1319 Name => New_Occurrence_Of (Defining_Entity (Fun), Loc));
1321 if not In_Init_Proc and then VM_Target = No_VM then
1322 Set_Uses_Sec_Stack (Defining_Entity (Fun));
1323 end if;
1324 end if;
1326 Decl := Make_Object_Declaration (Loc,
1327 Defining_Identifier => T_Id,
1328 Object_Definition => New_Occurrence_Of (Standard_String, Loc),
1329 Constant_Present => True,
1330 Expression => Expr);
1332 Append (Decl, Decls);
1333 return Decls;
1334 end Build_Task_Image_Decls;
1336 -------------------------------
1337 -- Build_Task_Image_Function --
1338 -------------------------------
1340 function Build_Task_Image_Function
1341 (Loc : Source_Ptr;
1342 Decls : List_Id;
1343 Stats : List_Id;
1344 Res : Entity_Id) return Node_Id
1346 Spec : Node_Id;
1348 begin
1349 Append_To (Stats,
1350 Make_Simple_Return_Statement (Loc,
1351 Expression => New_Occurrence_Of (Res, Loc)));
1353 Spec := Make_Function_Specification (Loc,
1354 Defining_Unit_Name => Make_Temporary (Loc, 'F'),
1355 Result_Definition => New_Occurrence_Of (Standard_String, Loc));
1357 -- Calls to 'Image use the secondary stack, which must be cleaned up
1358 -- after the task name is built.
1360 return Make_Subprogram_Body (Loc,
1361 Specification => Spec,
1362 Declarations => Decls,
1363 Handled_Statement_Sequence =>
1364 Make_Handled_Sequence_Of_Statements (Loc, Statements => Stats));
1365 end Build_Task_Image_Function;
1367 -----------------------------
1368 -- Build_Task_Image_Prefix --
1369 -----------------------------
1371 procedure Build_Task_Image_Prefix
1372 (Loc : Source_Ptr;
1373 Len : out Entity_Id;
1374 Res : out Entity_Id;
1375 Pos : out Entity_Id;
1376 Prefix : Entity_Id;
1377 Sum : Node_Id;
1378 Decls : List_Id;
1379 Stats : List_Id)
1381 begin
1382 Len := Make_Temporary (Loc, 'L', Sum);
1384 Append_To (Decls,
1385 Make_Object_Declaration (Loc,
1386 Defining_Identifier => Len,
1387 Object_Definition => New_Occurrence_Of (Standard_Integer, Loc),
1388 Expression => Sum));
1390 Res := Make_Temporary (Loc, 'R');
1392 Append_To (Decls,
1393 Make_Object_Declaration (Loc,
1394 Defining_Identifier => Res,
1395 Object_Definition =>
1396 Make_Subtype_Indication (Loc,
1397 Subtype_Mark => New_Occurrence_Of (Standard_String, Loc),
1398 Constraint =>
1399 Make_Index_Or_Discriminant_Constraint (Loc,
1400 Constraints =>
1401 New_List (
1402 Make_Range (Loc,
1403 Low_Bound => Make_Integer_Literal (Loc, 1),
1404 High_Bound => New_Occurrence_Of (Len, Loc)))))));
1406 Pos := Make_Temporary (Loc, 'P');
1408 Append_To (Decls,
1409 Make_Object_Declaration (Loc,
1410 Defining_Identifier => Pos,
1411 Object_Definition => New_Occurrence_Of (Standard_Integer, Loc)));
1413 -- Pos := Prefix'Length;
1415 Append_To (Stats,
1416 Make_Assignment_Statement (Loc,
1417 Name => New_Occurrence_Of (Pos, Loc),
1418 Expression =>
1419 Make_Attribute_Reference (Loc,
1420 Attribute_Name => Name_Length,
1421 Prefix => New_Occurrence_Of (Prefix, Loc),
1422 Expressions => New_List (Make_Integer_Literal (Loc, 1)))));
1424 -- Res (1 .. Pos) := Prefix;
1426 Append_To (Stats,
1427 Make_Assignment_Statement (Loc,
1428 Name =>
1429 Make_Slice (Loc,
1430 Prefix => New_Occurrence_Of (Res, Loc),
1431 Discrete_Range =>
1432 Make_Range (Loc,
1433 Low_Bound => Make_Integer_Literal (Loc, 1),
1434 High_Bound => New_Occurrence_Of (Pos, Loc))),
1436 Expression => New_Occurrence_Of (Prefix, Loc)));
1438 Append_To (Stats,
1439 Make_Assignment_Statement (Loc,
1440 Name => New_Occurrence_Of (Pos, Loc),
1441 Expression =>
1442 Make_Op_Add (Loc,
1443 Left_Opnd => New_Occurrence_Of (Pos, Loc),
1444 Right_Opnd => Make_Integer_Literal (Loc, 1))));
1445 end Build_Task_Image_Prefix;
1447 -----------------------------
1448 -- Build_Task_Record_Image --
1449 -----------------------------
1451 function Build_Task_Record_Image
1452 (Loc : Source_Ptr;
1453 Id_Ref : Node_Id;
1454 Dyn : Boolean := False) return Node_Id
1456 Len : Entity_Id;
1457 -- Total length of generated name
1459 Pos : Entity_Id;
1460 -- Index into result
1462 Res : Entity_Id;
1463 -- String to hold result
1465 Pref : constant Entity_Id := Make_Temporary (Loc, 'P');
1466 -- Name of enclosing variable, prefix of resulting name
1468 Sum : Node_Id;
1469 -- Expression to compute total size of string
1471 Sel : Entity_Id;
1472 -- Entity for selector name
1474 Decls : constant List_Id := New_List;
1475 Stats : constant List_Id := New_List;
1477 begin
1478 -- For a dynamic task, the name comes from the target variable. For a
1479 -- static one it is a formal of the enclosing init proc.
1481 if Dyn then
1482 Get_Name_String (Chars (Entity (Prefix (Id_Ref))));
1483 Append_To (Decls,
1484 Make_Object_Declaration (Loc,
1485 Defining_Identifier => Pref,
1486 Object_Definition => New_Occurrence_Of (Standard_String, Loc),
1487 Expression =>
1488 Make_String_Literal (Loc,
1489 Strval => String_From_Name_Buffer)));
1491 else
1492 Append_To (Decls,
1493 Make_Object_Renaming_Declaration (Loc,
1494 Defining_Identifier => Pref,
1495 Subtype_Mark => New_Occurrence_Of (Standard_String, Loc),
1496 Name => Make_Identifier (Loc, Name_uTask_Name)));
1497 end if;
1499 Sel := Make_Temporary (Loc, 'S');
1501 Get_Name_String (Chars (Selector_Name (Id_Ref)));
1503 Append_To (Decls,
1504 Make_Object_Declaration (Loc,
1505 Defining_Identifier => Sel,
1506 Object_Definition => New_Occurrence_Of (Standard_String, Loc),
1507 Expression =>
1508 Make_String_Literal (Loc,
1509 Strval => String_From_Name_Buffer)));
1511 Sum := Make_Integer_Literal (Loc, Nat (Name_Len + 1));
1513 Sum :=
1514 Make_Op_Add (Loc,
1515 Left_Opnd => Sum,
1516 Right_Opnd =>
1517 Make_Attribute_Reference (Loc,
1518 Attribute_Name => Name_Length,
1519 Prefix =>
1520 New_Occurrence_Of (Pref, Loc),
1521 Expressions => New_List (Make_Integer_Literal (Loc, 1))));
1523 Build_Task_Image_Prefix (Loc, Len, Res, Pos, Pref, Sum, Decls, Stats);
1525 Set_Character_Literal_Name (Char_Code (Character'Pos ('.')));
1527 -- Res (Pos) := '.';
1529 Append_To (Stats,
1530 Make_Assignment_Statement (Loc,
1531 Name => Make_Indexed_Component (Loc,
1532 Prefix => New_Occurrence_Of (Res, Loc),
1533 Expressions => New_List (New_Occurrence_Of (Pos, Loc))),
1534 Expression =>
1535 Make_Character_Literal (Loc,
1536 Chars => Name_Find,
1537 Char_Literal_Value =>
1538 UI_From_Int (Character'Pos ('.')))));
1540 Append_To (Stats,
1541 Make_Assignment_Statement (Loc,
1542 Name => New_Occurrence_Of (Pos, Loc),
1543 Expression =>
1544 Make_Op_Add (Loc,
1545 Left_Opnd => New_Occurrence_Of (Pos, Loc),
1546 Right_Opnd => Make_Integer_Literal (Loc, 1))));
1548 -- Res (Pos .. Len) := Selector;
1550 Append_To (Stats,
1551 Make_Assignment_Statement (Loc,
1552 Name => Make_Slice (Loc,
1553 Prefix => New_Occurrence_Of (Res, Loc),
1554 Discrete_Range =>
1555 Make_Range (Loc,
1556 Low_Bound => New_Occurrence_Of (Pos, Loc),
1557 High_Bound => New_Occurrence_Of (Len, Loc))),
1558 Expression => New_Occurrence_Of (Sel, Loc)));
1560 return Build_Task_Image_Function (Loc, Decls, Stats, Res);
1561 end Build_Task_Record_Image;
1563 ----------------------------------
1564 -- Component_May_Be_Bit_Aligned --
1565 ----------------------------------
1567 function Component_May_Be_Bit_Aligned (Comp : Entity_Id) return Boolean is
1568 UT : Entity_Id;
1570 begin
1571 -- If no component clause, then everything is fine, since the back end
1572 -- never bit-misaligns by default, even if there is a pragma Packed for
1573 -- the record.
1575 if No (Comp) or else No (Component_Clause (Comp)) then
1576 return False;
1577 end if;
1579 UT := Underlying_Type (Etype (Comp));
1581 -- It is only array and record types that cause trouble
1583 if not Is_Record_Type (UT)
1584 and then not Is_Array_Type (UT)
1585 then
1586 return False;
1588 -- If we know that we have a small (64 bits or less) record or small
1589 -- bit-packed array, then everything is fine, since the back end can
1590 -- handle these cases correctly.
1592 elsif Esize (Comp) <= 64
1593 and then (Is_Record_Type (UT)
1594 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;
1736 begin
1737 Remove_Side_Effects (Exp, Name_Req);
1738 New_Exp := New_Copy_Tree (Exp);
1739 Remove_Checks (New_Exp);
1740 return New_Exp;
1741 end Duplicate_Subexpr_No_Checks;
1743 -----------------------------------
1744 -- Duplicate_Subexpr_Move_Checks --
1745 -----------------------------------
1747 function Duplicate_Subexpr_Move_Checks
1748 (Exp : Node_Id;
1749 Name_Req : Boolean := False) return Node_Id
1751 New_Exp : Node_Id;
1752 begin
1753 Remove_Side_Effects (Exp, Name_Req);
1754 New_Exp := New_Copy_Tree (Exp);
1755 Remove_Checks (Exp);
1756 return New_Exp;
1757 end Duplicate_Subexpr_Move_Checks;
1759 --------------------
1760 -- Ensure_Defined --
1761 --------------------
1763 procedure Ensure_Defined (Typ : Entity_Id; N : Node_Id) is
1764 IR : Node_Id;
1766 begin
1767 -- An itype reference must only be created if this is a local itype, so
1768 -- that gigi can elaborate it on the proper objstack.
1770 if Is_Itype (Typ)
1771 and then Scope (Typ) = Current_Scope
1772 then
1773 IR := Make_Itype_Reference (Sloc (N));
1774 Set_Itype (IR, Typ);
1775 Insert_Action (N, IR);
1776 end if;
1777 end Ensure_Defined;
1779 --------------------
1780 -- Entry_Names_OK --
1781 --------------------
1783 function Entry_Names_OK return Boolean is
1784 begin
1785 return
1786 not Restricted_Profile
1787 and then not Global_Discard_Names
1788 and then not Restriction_Active (No_Implicit_Heap_Allocations)
1789 and then not Restriction_Active (No_Local_Allocators);
1790 end Entry_Names_OK;
1792 -------------------
1793 -- Evaluate_Name --
1794 -------------------
1796 procedure Evaluate_Name (Nam : Node_Id) is
1797 K : constant Node_Kind := Nkind (Nam);
1799 begin
1800 -- For an explicit dereference, we simply force the evaluation of the
1801 -- name expression. The dereference provides a value that is the address
1802 -- for the renamed object, and it is precisely this value that we want
1803 -- to preserve.
1805 if K = N_Explicit_Dereference then
1806 Force_Evaluation (Prefix (Nam));
1808 -- For a selected component, we simply evaluate the prefix
1810 elsif K = N_Selected_Component then
1811 Evaluate_Name (Prefix (Nam));
1813 -- For an indexed component, or an attribute reference, we evaluate the
1814 -- prefix, which is itself a name, recursively, and then force the
1815 -- evaluation of all the subscripts (or attribute expressions).
1817 elsif Nkind_In (K, N_Indexed_Component, N_Attribute_Reference) then
1818 Evaluate_Name (Prefix (Nam));
1820 declare
1821 E : Node_Id;
1823 begin
1824 E := First (Expressions (Nam));
1825 while Present (E) loop
1826 Force_Evaluation (E);
1828 if Original_Node (E) /= E then
1829 Set_Do_Range_Check (E, Do_Range_Check (Original_Node (E)));
1830 end if;
1832 Next (E);
1833 end loop;
1834 end;
1836 -- For a slice, we evaluate the prefix, as for the indexed component
1837 -- case and then, if there is a range present, either directly or as the
1838 -- constraint of a discrete subtype indication, we evaluate the two
1839 -- bounds of this range.
1841 elsif K = N_Slice then
1842 Evaluate_Name (Prefix (Nam));
1844 declare
1845 DR : constant Node_Id := Discrete_Range (Nam);
1846 Constr : Node_Id;
1847 Rexpr : Node_Id;
1849 begin
1850 if Nkind (DR) = N_Range then
1851 Force_Evaluation (Low_Bound (DR));
1852 Force_Evaluation (High_Bound (DR));
1854 elsif Nkind (DR) = N_Subtype_Indication then
1855 Constr := Constraint (DR);
1857 if Nkind (Constr) = N_Range_Constraint then
1858 Rexpr := Range_Expression (Constr);
1860 Force_Evaluation (Low_Bound (Rexpr));
1861 Force_Evaluation (High_Bound (Rexpr));
1862 end if;
1863 end if;
1864 end;
1866 -- For a type conversion, the expression of the conversion must be the
1867 -- name of an object, and we simply need to evaluate this name.
1869 elsif K = N_Type_Conversion then
1870 Evaluate_Name (Expression (Nam));
1872 -- For a function call, we evaluate the call
1874 elsif K = N_Function_Call then
1875 Force_Evaluation (Nam);
1877 -- The remaining cases are direct name, operator symbol and character
1878 -- literal. In all these cases, we do nothing, since we want to
1879 -- reevaluate each time the renamed object is used.
1881 else
1882 return;
1883 end if;
1884 end Evaluate_Name;
1886 ---------------------
1887 -- Evolve_And_Then --
1888 ---------------------
1890 procedure Evolve_And_Then (Cond : in out Node_Id; Cond1 : Node_Id) is
1891 begin
1892 if No (Cond) then
1893 Cond := Cond1;
1894 else
1895 Cond :=
1896 Make_And_Then (Sloc (Cond1),
1897 Left_Opnd => Cond,
1898 Right_Opnd => Cond1);
1899 end if;
1900 end Evolve_And_Then;
1902 --------------------
1903 -- Evolve_Or_Else --
1904 --------------------
1906 procedure Evolve_Or_Else (Cond : in out Node_Id; Cond1 : Node_Id) is
1907 begin
1908 if No (Cond) then
1909 Cond := Cond1;
1910 else
1911 Cond :=
1912 Make_Or_Else (Sloc (Cond1),
1913 Left_Opnd => Cond,
1914 Right_Opnd => Cond1);
1915 end if;
1916 end Evolve_Or_Else;
1918 ------------------------------
1919 -- Expand_Subtype_From_Expr --
1920 ------------------------------
1922 -- This function is applicable for both static and dynamic allocation of
1923 -- objects which are constrained by an initial expression. Basically it
1924 -- transforms an unconstrained subtype indication into a constrained one.
1926 -- The expression may also be transformed in certain cases in order to
1927 -- avoid multiple evaluation. In the static allocation case, the general
1928 -- scheme is:
1930 -- Val : T := Expr;
1932 -- is transformed into
1934 -- Val : Constrained_Subtype_of_T := Maybe_Modified_Expr;
1936 -- Here are the main cases :
1938 -- <if Expr is a Slice>
1939 -- Val : T ([Index_Subtype (Expr)]) := Expr;
1941 -- <elsif Expr is a String Literal>
1942 -- Val : T (T'First .. T'First + Length (string literal) - 1) := Expr;
1944 -- <elsif Expr is Constrained>
1945 -- subtype T is Type_Of_Expr
1946 -- Val : T := Expr;
1948 -- <elsif Expr is an entity_name>
1949 -- Val : T (constraints taken from Expr) := Expr;
1951 -- <else>
1952 -- type Axxx is access all T;
1953 -- Rval : Axxx := Expr'ref;
1954 -- Val : T (constraints taken from Rval) := Rval.all;
1956 -- ??? note: when the Expression is allocated in the secondary stack
1957 -- we could use it directly instead of copying it by declaring
1958 -- Val : T (...) renames Rval.all
1960 procedure Expand_Subtype_From_Expr
1961 (N : Node_Id;
1962 Unc_Type : Entity_Id;
1963 Subtype_Indic : Node_Id;
1964 Exp : Node_Id)
1966 Loc : constant Source_Ptr := Sloc (N);
1967 Exp_Typ : constant Entity_Id := Etype (Exp);
1968 T : Entity_Id;
1970 begin
1971 -- In general we cannot build the subtype if expansion is disabled,
1972 -- because internal entities may not have been defined. However, to
1973 -- avoid some cascaded errors, we try to continue when the expression is
1974 -- an array (or string), because it is safe to compute the bounds. It is
1975 -- in fact required to do so even in a generic context, because there
1976 -- may be constants that depend on the bounds of a string literal, both
1977 -- standard string types and more generally arrays of characters.
1979 if not Expander_Active
1980 and then (No (Etype (Exp))
1981 or else not Is_String_Type (Etype (Exp)))
1982 then
1983 return;
1984 end if;
1986 if Nkind (Exp) = N_Slice then
1987 declare
1988 Slice_Type : constant Entity_Id := Etype (First_Index (Exp_Typ));
1990 begin
1991 Rewrite (Subtype_Indic,
1992 Make_Subtype_Indication (Loc,
1993 Subtype_Mark => New_Reference_To (Unc_Type, Loc),
1994 Constraint =>
1995 Make_Index_Or_Discriminant_Constraint (Loc,
1996 Constraints => New_List
1997 (New_Reference_To (Slice_Type, Loc)))));
1999 -- This subtype indication may be used later for constraint checks
2000 -- we better make sure that if a variable was used as a bound of
2001 -- of the original slice, its value is frozen.
2003 Force_Evaluation (Low_Bound (Scalar_Range (Slice_Type)));
2004 Force_Evaluation (High_Bound (Scalar_Range (Slice_Type)));
2005 end;
2007 elsif Ekind (Exp_Typ) = E_String_Literal_Subtype then
2008 Rewrite (Subtype_Indic,
2009 Make_Subtype_Indication (Loc,
2010 Subtype_Mark => New_Reference_To (Unc_Type, Loc),
2011 Constraint =>
2012 Make_Index_Or_Discriminant_Constraint (Loc,
2013 Constraints => New_List (
2014 Make_Literal_Range (Loc,
2015 Literal_Typ => Exp_Typ)))));
2017 elsif Is_Constrained (Exp_Typ)
2018 and then not Is_Class_Wide_Type (Unc_Type)
2019 then
2020 if Is_Itype (Exp_Typ) then
2022 -- Within an initialization procedure, a selected component
2023 -- denotes a component of the enclosing record, and it appears as
2024 -- an actual in a call to its own initialization procedure. If
2025 -- this component depends on the outer discriminant, we must
2026 -- generate the proper actual subtype for it.
2028 if Nkind (Exp) = N_Selected_Component
2029 and then Within_Init_Proc
2030 then
2031 declare
2032 Decl : constant Node_Id :=
2033 Build_Actual_Subtype_Of_Component (Exp_Typ, Exp);
2034 begin
2035 if Present (Decl) then
2036 Insert_Action (N, Decl);
2037 T := Defining_Identifier (Decl);
2038 else
2039 T := Exp_Typ;
2040 end if;
2041 end;
2043 -- No need to generate a new one (new what???)
2045 else
2046 T := Exp_Typ;
2047 end if;
2049 else
2050 T := Make_Temporary (Loc, 'T');
2052 Insert_Action (N,
2053 Make_Subtype_Declaration (Loc,
2054 Defining_Identifier => T,
2055 Subtype_Indication => New_Reference_To (Exp_Typ, Loc)));
2057 -- This type is marked as an itype even though it has an explicit
2058 -- declaration since otherwise Is_Generic_Actual_Type can get
2059 -- set, resulting in the generation of spurious errors. (See
2060 -- sem_ch8.Analyze_Package_Renaming and sem_type.covers)
2062 Set_Is_Itype (T);
2063 Set_Associated_Node_For_Itype (T, Exp);
2064 end if;
2066 Rewrite (Subtype_Indic, New_Reference_To (T, Loc));
2068 -- Nothing needs to be done for private types with unknown discriminants
2069 -- if the underlying type is not an unconstrained composite type or it
2070 -- is an unchecked union.
2072 elsif Is_Private_Type (Unc_Type)
2073 and then Has_Unknown_Discriminants (Unc_Type)
2074 and then (not Is_Composite_Type (Underlying_Type (Unc_Type))
2075 or else Is_Constrained (Underlying_Type (Unc_Type))
2076 or else Is_Unchecked_Union (Underlying_Type (Unc_Type)))
2077 then
2078 null;
2080 -- Case of derived type with unknown discriminants where the parent type
2081 -- also has unknown discriminants.
2083 elsif Is_Record_Type (Unc_Type)
2084 and then not Is_Class_Wide_Type (Unc_Type)
2085 and then Has_Unknown_Discriminants (Unc_Type)
2086 and then Has_Unknown_Discriminants (Underlying_Type (Unc_Type))
2087 then
2088 -- Nothing to be done if no underlying record view available
2090 if No (Underlying_Record_View (Unc_Type)) then
2091 null;
2093 -- Otherwise use the Underlying_Record_View to create the proper
2094 -- constrained subtype for an object of a derived type with unknown
2095 -- discriminants.
2097 else
2098 Remove_Side_Effects (Exp);
2099 Rewrite (Subtype_Indic,
2100 Make_Subtype_From_Expr (Exp, Underlying_Record_View (Unc_Type)));
2101 end if;
2103 -- Renamings of class-wide interface types require no equivalent
2104 -- constrained type declarations because we only need to reference
2105 -- the tag component associated with the interface. The same is
2106 -- presumably true for class-wide types in general, so this test
2107 -- is broadened to include all class-wide renamings, which also
2108 -- avoids cases of unbounded recursion in Remove_Side_Effects.
2109 -- (Is this really correct, or are there some cases of class-wide
2110 -- renamings that require action in this procedure???)
2112 elsif Present (N)
2113 and then Nkind (N) = N_Object_Renaming_Declaration
2114 and then Is_Class_Wide_Type (Unc_Type)
2115 then
2116 null;
2118 -- In Ada 95 nothing to be done if the type of the expression is limited
2119 -- because in this case the expression cannot be copied, and its use can
2120 -- only be by reference.
2122 -- In Ada 2005 the context can be an object declaration whose expression
2123 -- is a function that returns in place. If the nominal subtype has
2124 -- unknown discriminants, the call still provides constraints on the
2125 -- object, and we have to create an actual subtype from it.
2127 -- If the type is class-wide, the expression is dynamically tagged and
2128 -- we do not create an actual subtype either. Ditto for an interface.
2129 -- For now this applies only if the type is immutably limited, and the
2130 -- function being called is build-in-place. This will have to be revised
2131 -- when build-in-place functions are generalized to other types.
2133 elsif Is_Immutably_Limited_Type (Exp_Typ)
2134 and then
2135 (Is_Class_Wide_Type (Exp_Typ)
2136 or else Is_Interface (Exp_Typ)
2137 or else not Has_Unknown_Discriminants (Exp_Typ)
2138 or else not Is_Composite_Type (Unc_Type))
2139 then
2140 null;
2142 -- For limited objects initialized with build in place function calls,
2143 -- nothing to be done; otherwise we prematurely introduce an N_Reference
2144 -- node in the expression initializing the object, which breaks the
2145 -- circuitry that detects and adds the additional arguments to the
2146 -- called function.
2148 elsif Is_Build_In_Place_Function_Call (Exp) then
2149 null;
2151 else
2152 Remove_Side_Effects (Exp);
2153 Rewrite (Subtype_Indic,
2154 Make_Subtype_From_Expr (Exp, Unc_Type));
2155 end if;
2156 end Expand_Subtype_From_Expr;
2158 --------------------
2159 -- Find_Init_Call --
2160 --------------------
2162 function Find_Init_Call
2163 (Var : Entity_Id;
2164 Rep_Clause : Node_Id) return Node_Id
2166 Typ : constant Entity_Id := Etype (Var);
2168 Init_Proc : Entity_Id;
2169 -- Initialization procedure for Typ
2171 function Find_Init_Call_In_List (From : Node_Id) return Node_Id;
2172 -- Look for init call for Var starting at From and scanning the
2173 -- enclosing list until Rep_Clause or the end of the list is reached.
2175 ----------------------------
2176 -- Find_Init_Call_In_List --
2177 ----------------------------
2179 function Find_Init_Call_In_List (From : Node_Id) return Node_Id is
2180 Init_Call : Node_Id;
2181 begin
2182 Init_Call := From;
2184 while Present (Init_Call) and then Init_Call /= Rep_Clause loop
2185 if Nkind (Init_Call) = N_Procedure_Call_Statement
2186 and then Is_Entity_Name (Name (Init_Call))
2187 and then Entity (Name (Init_Call)) = Init_Proc
2188 then
2189 return Init_Call;
2190 end if;
2192 Next (Init_Call);
2193 end loop;
2195 return Empty;
2196 end Find_Init_Call_In_List;
2198 Init_Call : Node_Id;
2200 -- Start of processing for Find_Init_Call
2202 begin
2203 if not Has_Non_Null_Base_Init_Proc (Typ) then
2204 -- No init proc for the type, so obviously no call to be found
2206 return Empty;
2207 end if;
2209 Init_Proc := Base_Init_Proc (Typ);
2211 -- First scan the list containing the declaration of Var
2213 Init_Call := Find_Init_Call_In_List (From => Next (Parent (Var)));
2215 -- If not found, also look on Var's freeze actions list, if any, since
2216 -- the init call may have been moved there (case of an address clause
2217 -- applying to Var).
2219 if No (Init_Call) and then Present (Freeze_Node (Var)) then
2220 Init_Call :=
2221 Find_Init_Call_In_List (First (Actions (Freeze_Node (Var))));
2222 end if;
2224 return Init_Call;
2225 end Find_Init_Call;
2227 ------------------------
2228 -- Find_Interface_ADT --
2229 ------------------------
2231 function Find_Interface_ADT
2232 (T : Entity_Id;
2233 Iface : Entity_Id) return Elmt_Id
2235 ADT : Elmt_Id;
2236 Typ : Entity_Id := T;
2238 begin
2239 pragma Assert (Is_Interface (Iface));
2241 -- Handle private types
2243 if Has_Private_Declaration (Typ)
2244 and then Present (Full_View (Typ))
2245 then
2246 Typ := Full_View (Typ);
2247 end if;
2249 -- Handle access types
2251 if Is_Access_Type (Typ) then
2252 Typ := Designated_Type (Typ);
2253 end if;
2255 -- Handle task and protected types implementing interfaces
2257 if Is_Concurrent_Type (Typ) then
2258 Typ := Corresponding_Record_Type (Typ);
2259 end if;
2261 pragma Assert
2262 (not Is_Class_Wide_Type (Typ)
2263 and then Ekind (Typ) /= E_Incomplete_Type);
2265 if Is_Ancestor (Iface, Typ, Use_Full_View => True) then
2266 return First_Elmt (Access_Disp_Table (Typ));
2268 else
2269 ADT :=
2270 Next_Elmt (Next_Elmt (First_Elmt (Access_Disp_Table (Typ))));
2271 while Present (ADT)
2272 and then Present (Related_Type (Node (ADT)))
2273 and then Related_Type (Node (ADT)) /= Iface
2274 and then not Is_Ancestor (Iface, Related_Type (Node (ADT)),
2275 Use_Full_View => True)
2276 loop
2277 Next_Elmt (ADT);
2278 end loop;
2280 pragma Assert (Present (Related_Type (Node (ADT))));
2281 return ADT;
2282 end if;
2283 end Find_Interface_ADT;
2285 ------------------------
2286 -- Find_Interface_Tag --
2287 ------------------------
2289 function Find_Interface_Tag
2290 (T : Entity_Id;
2291 Iface : Entity_Id) return Entity_Id
2293 AI_Tag : Entity_Id;
2294 Found : Boolean := False;
2295 Typ : Entity_Id := T;
2297 procedure Find_Tag (Typ : Entity_Id);
2298 -- Internal subprogram used to recursively climb to the ancestors
2300 --------------
2301 -- Find_Tag --
2302 --------------
2304 procedure Find_Tag (Typ : Entity_Id) is
2305 AI_Elmt : Elmt_Id;
2306 AI : Node_Id;
2308 begin
2309 -- This routine does not handle the case in which the interface is an
2310 -- ancestor of Typ. That case is handled by the enclosing subprogram.
2312 pragma Assert (Typ /= Iface);
2314 -- Climb to the root type handling private types
2316 if Present (Full_View (Etype (Typ))) then
2317 if Full_View (Etype (Typ)) /= Typ then
2318 Find_Tag (Full_View (Etype (Typ)));
2319 end if;
2321 elsif Etype (Typ) /= Typ then
2322 Find_Tag (Etype (Typ));
2323 end if;
2325 -- Traverse the list of interfaces implemented by the type
2327 if not Found
2328 and then Present (Interfaces (Typ))
2329 and then not (Is_Empty_Elmt_List (Interfaces (Typ)))
2330 then
2331 -- Skip the tag associated with the primary table
2333 pragma Assert (Etype (First_Tag_Component (Typ)) = RTE (RE_Tag));
2334 AI_Tag := Next_Tag_Component (First_Tag_Component (Typ));
2335 pragma Assert (Present (AI_Tag));
2337 AI_Elmt := First_Elmt (Interfaces (Typ));
2338 while Present (AI_Elmt) loop
2339 AI := Node (AI_Elmt);
2341 if AI = Iface
2342 or else Is_Ancestor (Iface, AI, Use_Full_View => True)
2343 then
2344 Found := True;
2345 return;
2346 end if;
2348 AI_Tag := Next_Tag_Component (AI_Tag);
2349 Next_Elmt (AI_Elmt);
2350 end loop;
2351 end if;
2352 end Find_Tag;
2354 -- Start of processing for Find_Interface_Tag
2356 begin
2357 pragma Assert (Is_Interface (Iface));
2359 -- Handle access types
2361 if Is_Access_Type (Typ) then
2362 Typ := Designated_Type (Typ);
2363 end if;
2365 -- Handle class-wide types
2367 if Is_Class_Wide_Type (Typ) then
2368 Typ := Root_Type (Typ);
2369 end if;
2371 -- Handle private types
2373 if Has_Private_Declaration (Typ)
2374 and then Present (Full_View (Typ))
2375 then
2376 Typ := Full_View (Typ);
2377 end if;
2379 -- Handle entities from the limited view
2381 if Ekind (Typ) = E_Incomplete_Type then
2382 pragma Assert (Present (Non_Limited_View (Typ)));
2383 Typ := Non_Limited_View (Typ);
2384 end if;
2386 -- Handle task and protected types implementing interfaces
2388 if Is_Concurrent_Type (Typ) then
2389 Typ := Corresponding_Record_Type (Typ);
2390 end if;
2392 -- If the interface is an ancestor of the type, then it shared the
2393 -- primary dispatch table.
2395 if Is_Ancestor (Iface, Typ, Use_Full_View => True) then
2396 pragma Assert (Etype (First_Tag_Component (Typ)) = RTE (RE_Tag));
2397 return First_Tag_Component (Typ);
2399 -- Otherwise we need to search for its associated tag component
2401 else
2402 Find_Tag (Typ);
2403 pragma Assert (Found);
2404 return AI_Tag;
2405 end if;
2406 end Find_Interface_Tag;
2408 ------------------
2409 -- Find_Prim_Op --
2410 ------------------
2412 function Find_Prim_Op (T : Entity_Id; Name : Name_Id) return Entity_Id is
2413 Prim : Elmt_Id;
2414 Typ : Entity_Id := T;
2415 Op : Entity_Id;
2417 begin
2418 if Is_Class_Wide_Type (Typ) then
2419 Typ := Root_Type (Typ);
2420 end if;
2422 Typ := Underlying_Type (Typ);
2424 -- Loop through primitive operations
2426 Prim := First_Elmt (Primitive_Operations (Typ));
2427 while Present (Prim) loop
2428 Op := Node (Prim);
2430 -- We can retrieve primitive operations by name if it is an internal
2431 -- name. For equality we must check that both of its operands have
2432 -- the same type, to avoid confusion with user-defined equalities
2433 -- than may have a non-symmetric signature.
2435 exit when Chars (Op) = Name
2436 and then
2437 (Name /= Name_Op_Eq
2438 or else Etype (First_Formal (Op)) = Etype (Last_Formal (Op)));
2440 Next_Elmt (Prim);
2442 -- Raise Program_Error if no primitive found
2444 if No (Prim) then
2445 raise Program_Error;
2446 end if;
2447 end loop;
2449 return Node (Prim);
2450 end Find_Prim_Op;
2452 ------------------
2453 -- Find_Prim_Op --
2454 ------------------
2456 function Find_Prim_Op
2457 (T : Entity_Id;
2458 Name : TSS_Name_Type) return Entity_Id
2460 Inher_Op : Entity_Id := Empty;
2461 Own_Op : Entity_Id := Empty;
2462 Prim_Elmt : Elmt_Id;
2463 Prim_Id : Entity_Id;
2464 Typ : Entity_Id := T;
2466 begin
2467 if Is_Class_Wide_Type (Typ) then
2468 Typ := Root_Type (Typ);
2469 end if;
2471 Typ := Underlying_Type (Typ);
2473 -- This search is based on the assertion that the dispatching version
2474 -- of the TSS routine always precedes the real primitive.
2476 Prim_Elmt := First_Elmt (Primitive_Operations (Typ));
2477 while Present (Prim_Elmt) loop
2478 Prim_Id := Node (Prim_Elmt);
2480 if Is_TSS (Prim_Id, Name) then
2481 if Present (Alias (Prim_Id)) then
2482 Inher_Op := Prim_Id;
2483 else
2484 Own_Op := Prim_Id;
2485 end if;
2486 end if;
2488 Next_Elmt (Prim_Elmt);
2489 end loop;
2491 if Present (Own_Op) then
2492 return Own_Op;
2493 elsif Present (Inher_Op) then
2494 return Inher_Op;
2495 else
2496 raise Program_Error;
2497 end if;
2498 end Find_Prim_Op;
2500 ----------------------------
2501 -- Find_Protection_Object --
2502 ----------------------------
2504 function Find_Protection_Object (Scop : Entity_Id) return Entity_Id is
2505 S : Entity_Id;
2507 begin
2508 S := Scop;
2509 while Present (S) loop
2510 if (Ekind (S) = E_Entry
2511 or else Ekind (S) = E_Entry_Family
2512 or else Ekind (S) = E_Function
2513 or else Ekind (S) = E_Procedure)
2514 and then Present (Protection_Object (S))
2515 then
2516 return Protection_Object (S);
2517 end if;
2519 S := Scope (S);
2520 end loop;
2522 -- If we do not find a Protection object in the scope chain, then
2523 -- something has gone wrong, most likely the object was never created.
2525 raise Program_Error;
2526 end Find_Protection_Object;
2528 --------------------------
2529 -- Find_Protection_Type --
2530 --------------------------
2532 function Find_Protection_Type (Conc_Typ : Entity_Id) return Entity_Id is
2533 Comp : Entity_Id;
2534 Typ : Entity_Id := Conc_Typ;
2536 begin
2537 if Is_Concurrent_Type (Typ) then
2538 Typ := Corresponding_Record_Type (Typ);
2539 end if;
2541 -- Since restriction violations are not considered serious errors, the
2542 -- expander remains active, but may leave the corresponding record type
2543 -- malformed. In such cases, component _object is not available so do
2544 -- not look for it.
2546 if not Analyzed (Typ) then
2547 return Empty;
2548 end if;
2550 Comp := First_Component (Typ);
2551 while Present (Comp) loop
2552 if Chars (Comp) = Name_uObject then
2553 return Base_Type (Etype (Comp));
2554 end if;
2556 Next_Component (Comp);
2557 end loop;
2559 -- The corresponding record of a protected type should always have an
2560 -- _object field.
2562 raise Program_Error;
2563 end Find_Protection_Type;
2565 ----------------------
2566 -- Force_Evaluation --
2567 ----------------------
2569 procedure Force_Evaluation (Exp : Node_Id; Name_Req : Boolean := False) is
2570 begin
2571 Remove_Side_Effects (Exp, Name_Req, Variable_Ref => True);
2572 end Force_Evaluation;
2574 ---------------------------------
2575 -- Fully_Qualified_Name_String --
2576 ---------------------------------
2578 function Fully_Qualified_Name_String (E : Entity_Id) return String_Id is
2579 procedure Internal_Full_Qualified_Name (E : Entity_Id);
2580 -- Compute recursively the qualified name without NUL at the end, adding
2581 -- it to the currently started string being generated
2583 ----------------------------------
2584 -- Internal_Full_Qualified_Name --
2585 ----------------------------------
2587 procedure Internal_Full_Qualified_Name (E : Entity_Id) is
2588 Ent : Entity_Id;
2590 begin
2591 -- Deal properly with child units
2593 if Nkind (E) = N_Defining_Program_Unit_Name then
2594 Ent := Defining_Identifier (E);
2595 else
2596 Ent := E;
2597 end if;
2599 -- Compute qualification recursively (only "Standard" has no scope)
2601 if Present (Scope (Scope (Ent))) then
2602 Internal_Full_Qualified_Name (Scope (Ent));
2603 Store_String_Char (Get_Char_Code ('.'));
2604 end if;
2606 -- Every entity should have a name except some expanded blocks
2607 -- don't bother about those.
2609 if Chars (Ent) = No_Name then
2610 return;
2611 end if;
2613 -- Generates the entity name in upper case
2615 Get_Decoded_Name_String (Chars (Ent));
2616 Set_All_Upper_Case;
2617 Store_String_Chars (Name_Buffer (1 .. Name_Len));
2618 return;
2619 end Internal_Full_Qualified_Name;
2621 -- Start of processing for Full_Qualified_Name
2623 begin
2624 Start_String;
2625 Internal_Full_Qualified_Name (E);
2626 Store_String_Char (Get_Char_Code (ASCII.NUL));
2627 return End_String;
2628 end Fully_Qualified_Name_String;
2630 ------------------------
2631 -- Generate_Poll_Call --
2632 ------------------------
2634 procedure Generate_Poll_Call (N : Node_Id) is
2635 begin
2636 -- No poll call if polling not active
2638 if not Polling_Required then
2639 return;
2641 -- Otherwise generate require poll call
2643 else
2644 Insert_Before_And_Analyze (N,
2645 Make_Procedure_Call_Statement (Sloc (N),
2646 Name => New_Occurrence_Of (RTE (RE_Poll), Sloc (N))));
2647 end if;
2648 end Generate_Poll_Call;
2650 ---------------------------------
2651 -- Get_Current_Value_Condition --
2652 ---------------------------------
2654 -- Note: the implementation of this procedure is very closely tied to the
2655 -- implementation of Set_Current_Value_Condition. In the Get procedure, we
2656 -- interpret Current_Value fields set by the Set procedure, so the two
2657 -- procedures need to be closely coordinated.
2659 procedure Get_Current_Value_Condition
2660 (Var : Node_Id;
2661 Op : out Node_Kind;
2662 Val : out Node_Id)
2664 Loc : constant Source_Ptr := Sloc (Var);
2665 Ent : constant Entity_Id := Entity (Var);
2667 procedure Process_Current_Value_Condition
2668 (N : Node_Id;
2669 S : Boolean);
2670 -- N is an expression which holds either True (S = True) or False (S =
2671 -- False) in the condition. This procedure digs out the expression and
2672 -- if it refers to Ent, sets Op and Val appropriately.
2674 -------------------------------------
2675 -- Process_Current_Value_Condition --
2676 -------------------------------------
2678 procedure Process_Current_Value_Condition
2679 (N : Node_Id;
2680 S : Boolean)
2682 Cond : Node_Id;
2683 Sens : Boolean;
2685 begin
2686 Cond := N;
2687 Sens := S;
2689 -- Deal with NOT operators, inverting sense
2691 while Nkind (Cond) = N_Op_Not loop
2692 Cond := Right_Opnd (Cond);
2693 Sens := not Sens;
2694 end loop;
2696 -- Deal with AND THEN and AND cases
2698 if Nkind (Cond) = N_And_Then
2699 or else Nkind (Cond) = N_Op_And
2700 then
2701 -- Don't ever try to invert a condition that is of the form of an
2702 -- AND or AND THEN (since we are not doing sufficiently general
2703 -- processing to allow this).
2705 if Sens = False then
2706 Op := N_Empty;
2707 Val := Empty;
2708 return;
2709 end if;
2711 -- Recursively process AND and AND THEN branches
2713 Process_Current_Value_Condition (Left_Opnd (Cond), True);
2715 if Op /= N_Empty then
2716 return;
2717 end if;
2719 Process_Current_Value_Condition (Right_Opnd (Cond), True);
2720 return;
2722 -- Case of relational operator
2724 elsif Nkind (Cond) in N_Op_Compare then
2725 Op := Nkind (Cond);
2727 -- Invert sense of test if inverted test
2729 if Sens = False then
2730 case Op is
2731 when N_Op_Eq => Op := N_Op_Ne;
2732 when N_Op_Ne => Op := N_Op_Eq;
2733 when N_Op_Lt => Op := N_Op_Ge;
2734 when N_Op_Gt => Op := N_Op_Le;
2735 when N_Op_Le => Op := N_Op_Gt;
2736 when N_Op_Ge => Op := N_Op_Lt;
2737 when others => raise Program_Error;
2738 end case;
2739 end if;
2741 -- Case of entity op value
2743 if Is_Entity_Name (Left_Opnd (Cond))
2744 and then Ent = Entity (Left_Opnd (Cond))
2745 and then Compile_Time_Known_Value (Right_Opnd (Cond))
2746 then
2747 Val := Right_Opnd (Cond);
2749 -- Case of value op entity
2751 elsif Is_Entity_Name (Right_Opnd (Cond))
2752 and then Ent = Entity (Right_Opnd (Cond))
2753 and then Compile_Time_Known_Value (Left_Opnd (Cond))
2754 then
2755 Val := Left_Opnd (Cond);
2757 -- We are effectively swapping operands
2759 case Op is
2760 when N_Op_Eq => null;
2761 when N_Op_Ne => null;
2762 when N_Op_Lt => Op := N_Op_Gt;
2763 when N_Op_Gt => Op := N_Op_Lt;
2764 when N_Op_Le => Op := N_Op_Ge;
2765 when N_Op_Ge => Op := N_Op_Le;
2766 when others => raise Program_Error;
2767 end case;
2769 else
2770 Op := N_Empty;
2771 end if;
2773 return;
2775 -- Case of Boolean variable reference, return as though the
2776 -- reference had said var = True.
2778 else
2779 if Is_Entity_Name (Cond)
2780 and then Ent = Entity (Cond)
2781 then
2782 Val := New_Occurrence_Of (Standard_True, Sloc (Cond));
2784 if Sens = False then
2785 Op := N_Op_Ne;
2786 else
2787 Op := N_Op_Eq;
2788 end if;
2789 end if;
2790 end if;
2791 end Process_Current_Value_Condition;
2793 -- Start of processing for Get_Current_Value_Condition
2795 begin
2796 Op := N_Empty;
2797 Val := Empty;
2799 -- Immediate return, nothing doing, if this is not an object
2801 if Ekind (Ent) not in Object_Kind then
2802 return;
2803 end if;
2805 -- Otherwise examine current value
2807 declare
2808 CV : constant Node_Id := Current_Value (Ent);
2809 Sens : Boolean;
2810 Stm : Node_Id;
2812 begin
2813 -- If statement. Condition is known true in THEN section, known False
2814 -- in any ELSIF or ELSE part, and unknown outside the IF statement.
2816 if Nkind (CV) = N_If_Statement then
2818 -- Before start of IF statement
2820 if Loc < Sloc (CV) then
2821 return;
2823 -- After end of IF statement
2825 elsif Loc >= Sloc (CV) + Text_Ptr (UI_To_Int (End_Span (CV))) then
2826 return;
2827 end if;
2829 -- At this stage we know that we are within the IF statement, but
2830 -- unfortunately, the tree does not record the SLOC of the ELSE so
2831 -- we cannot use a simple SLOC comparison to distinguish between
2832 -- the then/else statements, so we have to climb the tree.
2834 declare
2835 N : Node_Id;
2837 begin
2838 N := Parent (Var);
2839 while Parent (N) /= CV loop
2840 N := Parent (N);
2842 -- If we fall off the top of the tree, then that's odd, but
2843 -- perhaps it could occur in some error situation, and the
2844 -- safest response is simply to assume that the outcome of
2845 -- the condition is unknown. No point in bombing during an
2846 -- attempt to optimize things.
2848 if No (N) then
2849 return;
2850 end if;
2851 end loop;
2853 -- Now we have N pointing to a node whose parent is the IF
2854 -- statement in question, so now we can tell if we are within
2855 -- the THEN statements.
2857 if Is_List_Member (N)
2858 and then List_Containing (N) = Then_Statements (CV)
2859 then
2860 Sens := True;
2862 -- If the variable reference does not come from source, we
2863 -- cannot reliably tell whether it appears in the else part.
2864 -- In particular, if it appears in generated code for a node
2865 -- that requires finalization, it may be attached to a list
2866 -- that has not been yet inserted into the code. For now,
2867 -- treat it as unknown.
2869 elsif not Comes_From_Source (N) then
2870 return;
2872 -- Otherwise we must be in ELSIF or ELSE part
2874 else
2875 Sens := False;
2876 end if;
2877 end;
2879 -- ELSIF part. Condition is known true within the referenced
2880 -- ELSIF, known False in any subsequent ELSIF or ELSE part,
2881 -- and unknown before the ELSE part or after the IF statement.
2883 elsif Nkind (CV) = N_Elsif_Part then
2885 -- if the Elsif_Part had condition_actions, the elsif has been
2886 -- rewritten as a nested if, and the original elsif_part is
2887 -- detached from the tree, so there is no way to obtain useful
2888 -- information on the current value of the variable.
2889 -- Can this be improved ???
2891 if No (Parent (CV)) then
2892 return;
2893 end if;
2895 Stm := Parent (CV);
2897 -- Before start of ELSIF part
2899 if Loc < Sloc (CV) then
2900 return;
2902 -- After end of IF statement
2904 elsif Loc >= Sloc (Stm) +
2905 Text_Ptr (UI_To_Int (End_Span (Stm)))
2906 then
2907 return;
2908 end if;
2910 -- Again we lack the SLOC of the ELSE, so we need to climb the
2911 -- tree to see if we are within the ELSIF part in question.
2913 declare
2914 N : Node_Id;
2916 begin
2917 N := Parent (Var);
2918 while Parent (N) /= Stm loop
2919 N := Parent (N);
2921 -- If we fall off the top of the tree, then that's odd, but
2922 -- perhaps it could occur in some error situation, and the
2923 -- safest response is simply to assume that the outcome of
2924 -- the condition is unknown. No point in bombing during an
2925 -- attempt to optimize things.
2927 if No (N) then
2928 return;
2929 end if;
2930 end loop;
2932 -- Now we have N pointing to a node whose parent is the IF
2933 -- statement in question, so see if is the ELSIF part we want.
2934 -- the THEN statements.
2936 if N = CV then
2937 Sens := True;
2939 -- Otherwise we must be in subsequent ELSIF or ELSE part
2941 else
2942 Sens := False;
2943 end if;
2944 end;
2946 -- Iteration scheme of while loop. The condition is known to be
2947 -- true within the body of the loop.
2949 elsif Nkind (CV) = N_Iteration_Scheme then
2950 declare
2951 Loop_Stmt : constant Node_Id := Parent (CV);
2953 begin
2954 -- Before start of body of loop
2956 if Loc < Sloc (Loop_Stmt) then
2957 return;
2959 -- After end of LOOP statement
2961 elsif Loc >= Sloc (End_Label (Loop_Stmt)) then
2962 return;
2964 -- We are within the body of the loop
2966 else
2967 Sens := True;
2968 end if;
2969 end;
2971 -- All other cases of Current_Value settings
2973 else
2974 return;
2975 end if;
2977 -- If we fall through here, then we have a reportable condition, Sens
2978 -- is True if the condition is true and False if it needs inverting.
2980 Process_Current_Value_Condition (Condition (CV), Sens);
2981 end;
2982 end Get_Current_Value_Condition;
2984 ---------------------
2985 -- Get_Stream_Size --
2986 ---------------------
2988 function Get_Stream_Size (E : Entity_Id) return Uint is
2989 begin
2990 -- If we have a Stream_Size clause for this type use it
2992 if Has_Stream_Size_Clause (E) then
2993 return Static_Integer (Expression (Stream_Size_Clause (E)));
2995 -- Otherwise the Stream_Size if the size of the type
2997 else
2998 return Esize (E);
2999 end if;
3000 end Get_Stream_Size;
3002 ---------------------------
3003 -- Has_Access_Constraint --
3004 ---------------------------
3006 function Has_Access_Constraint (E : Entity_Id) return Boolean is
3007 Disc : Entity_Id;
3008 T : constant Entity_Id := Etype (E);
3010 begin
3011 if Has_Per_Object_Constraint (E)
3012 and then Has_Discriminants (T)
3013 then
3014 Disc := First_Discriminant (T);
3015 while Present (Disc) loop
3016 if Is_Access_Type (Etype (Disc)) then
3017 return True;
3018 end if;
3020 Next_Discriminant (Disc);
3021 end loop;
3023 return False;
3024 else
3025 return False;
3026 end if;
3027 end Has_Access_Constraint;
3029 ----------------------------------
3030 -- Has_Following_Address_Clause --
3031 ----------------------------------
3033 -- Should this function check the private part in a package ???
3035 function Has_Following_Address_Clause (D : Node_Id) return Boolean is
3036 Id : constant Entity_Id := Defining_Identifier (D);
3037 Decl : Node_Id;
3039 begin
3040 Decl := Next (D);
3041 while Present (Decl) loop
3042 if Nkind (Decl) = N_At_Clause
3043 and then Chars (Identifier (Decl)) = Chars (Id)
3044 then
3045 return True;
3047 elsif Nkind (Decl) = N_Attribute_Definition_Clause
3048 and then Chars (Decl) = Name_Address
3049 and then Chars (Name (Decl)) = Chars (Id)
3050 then
3051 return True;
3052 end if;
3054 Next (Decl);
3055 end loop;
3057 return False;
3058 end Has_Following_Address_Clause;
3060 --------------------
3061 -- Homonym_Number --
3062 --------------------
3064 function Homonym_Number (Subp : Entity_Id) return Nat is
3065 Count : Nat;
3066 Hom : Entity_Id;
3068 begin
3069 Count := 1;
3070 Hom := Homonym (Subp);
3071 while Present (Hom) loop
3072 if Scope (Hom) = Scope (Subp) then
3073 Count := Count + 1;
3074 end if;
3076 Hom := Homonym (Hom);
3077 end loop;
3079 return Count;
3080 end Homonym_Number;
3082 -----------------------------------
3083 -- In_Library_Level_Package_Body --
3084 -----------------------------------
3086 function In_Library_Level_Package_Body (Id : Entity_Id) return Boolean is
3087 begin
3088 -- First determine whether the entity appears at the library level, then
3089 -- look at the containing unit.
3091 if Is_Library_Level_Entity (Id) then
3092 declare
3093 Container : constant Node_Id := Cunit (Get_Source_Unit (Id));
3095 begin
3096 return Nkind (Unit (Container)) = N_Package_Body;
3097 end;
3098 end if;
3100 return False;
3101 end In_Library_Level_Package_Body;
3103 ------------------------------
3104 -- In_Unconditional_Context --
3105 ------------------------------
3107 function In_Unconditional_Context (Node : Node_Id) return Boolean is
3108 P : Node_Id;
3110 begin
3111 P := Node;
3112 while Present (P) loop
3113 case Nkind (P) is
3114 when N_Subprogram_Body =>
3115 return True;
3117 when N_If_Statement =>
3118 return False;
3120 when N_Loop_Statement =>
3121 return False;
3123 when N_Case_Statement =>
3124 return False;
3126 when others =>
3127 P := Parent (P);
3128 end case;
3129 end loop;
3131 return False;
3132 end In_Unconditional_Context;
3134 -------------------
3135 -- Insert_Action --
3136 -------------------
3138 procedure Insert_Action (Assoc_Node : Node_Id; Ins_Action : Node_Id) is
3139 begin
3140 if Present (Ins_Action) then
3141 Insert_Actions (Assoc_Node, New_List (Ins_Action));
3142 end if;
3143 end Insert_Action;
3145 -- Version with check(s) suppressed
3147 procedure Insert_Action
3148 (Assoc_Node : Node_Id; Ins_Action : Node_Id; Suppress : Check_Id)
3150 begin
3151 Insert_Actions (Assoc_Node, New_List (Ins_Action), Suppress);
3152 end Insert_Action;
3154 -------------------------
3155 -- Insert_Action_After --
3156 -------------------------
3158 procedure Insert_Action_After
3159 (Assoc_Node : Node_Id;
3160 Ins_Action : Node_Id)
3162 begin
3163 Insert_Actions_After (Assoc_Node, New_List (Ins_Action));
3164 end Insert_Action_After;
3166 --------------------
3167 -- Insert_Actions --
3168 --------------------
3170 procedure Insert_Actions (Assoc_Node : Node_Id; Ins_Actions : List_Id) is
3171 N : Node_Id;
3172 P : Node_Id;
3174 Wrapped_Node : Node_Id := Empty;
3176 begin
3177 if No (Ins_Actions) or else Is_Empty_List (Ins_Actions) then
3178 return;
3179 end if;
3181 -- Ignore insert of actions from inside default expression (or other
3182 -- similar "spec expression") in the special spec-expression analyze
3183 -- mode. Any insertions at this point have no relevance, since we are
3184 -- only doing the analyze to freeze the types of any static expressions.
3185 -- See section "Handling of Default Expressions" in the spec of package
3186 -- Sem for further details.
3188 if In_Spec_Expression then
3189 return;
3190 end if;
3192 -- If the action derives from stuff inside a record, then the actions
3193 -- are attached to the current scope, to be inserted and analyzed on
3194 -- exit from the scope. The reason for this is that we may also be
3195 -- generating freeze actions at the same time, and they must eventually
3196 -- be elaborated in the correct order.
3198 if Is_Record_Type (Current_Scope)
3199 and then not Is_Frozen (Current_Scope)
3200 then
3201 if No (Scope_Stack.Table
3202 (Scope_Stack.Last).Pending_Freeze_Actions)
3203 then
3204 Scope_Stack.Table (Scope_Stack.Last).Pending_Freeze_Actions :=
3205 Ins_Actions;
3206 else
3207 Append_List
3208 (Ins_Actions,
3209 Scope_Stack.Table (Scope_Stack.Last).Pending_Freeze_Actions);
3210 end if;
3212 return;
3213 end if;
3215 -- We now intend to climb up the tree to find the right point to
3216 -- insert the actions. We start at Assoc_Node, unless this node is a
3217 -- subexpression in which case we start with its parent. We do this for
3218 -- two reasons. First it speeds things up. Second, if Assoc_Node is
3219 -- itself one of the special nodes like N_And_Then, then we assume that
3220 -- an initial request to insert actions for such a node does not expect
3221 -- the actions to get deposited in the node for later handling when the
3222 -- node is expanded, since clearly the node is being dealt with by the
3223 -- caller. Note that in the subexpression case, N is always the child we
3224 -- came from.
3226 -- N_Raise_xxx_Error is an annoying special case, it is a statement if
3227 -- it has type Standard_Void_Type, and a subexpression otherwise.
3228 -- otherwise. Procedure attribute references are also statements.
3230 if Nkind (Assoc_Node) in N_Subexpr
3231 and then (Nkind (Assoc_Node) in N_Raise_xxx_Error
3232 or else Etype (Assoc_Node) /= Standard_Void_Type)
3233 and then (Nkind (Assoc_Node) /= N_Attribute_Reference
3234 or else
3235 not Is_Procedure_Attribute_Name
3236 (Attribute_Name (Assoc_Node)))
3237 then
3238 P := Assoc_Node; -- ??? does not agree with above!
3239 N := Parent (Assoc_Node);
3241 -- Non-subexpression case. Note that N is initially Empty in this case
3242 -- (N is only guaranteed Non-Empty in the subexpr case).
3244 else
3245 P := Assoc_Node;
3246 N := Empty;
3247 end if;
3249 -- Capture root of the transient scope
3251 if Scope_Is_Transient then
3252 Wrapped_Node := Node_To_Be_Wrapped;
3253 end if;
3255 loop
3256 pragma Assert (Present (P));
3258 case Nkind (P) is
3260 -- Case of right operand of AND THEN or OR ELSE. Put the actions
3261 -- in the Actions field of the right operand. They will be moved
3262 -- out further when the AND THEN or OR ELSE operator is expanded.
3263 -- Nothing special needs to be done for the left operand since
3264 -- in that case the actions are executed unconditionally.
3266 when N_Short_Circuit =>
3267 if N = Right_Opnd (P) then
3269 -- We are now going to either append the actions to the
3270 -- actions field of the short-circuit operation. We will
3271 -- also analyze the actions now.
3273 -- This analysis is really too early, the proper thing would
3274 -- be to just park them there now, and only analyze them if
3275 -- we find we really need them, and to it at the proper
3276 -- final insertion point. However attempting to this proved
3277 -- tricky, so for now we just kill current values before and
3278 -- after the analyze call to make sure we avoid peculiar
3279 -- optimizations from this out of order insertion.
3281 Kill_Current_Values;
3283 if Present (Actions (P)) then
3284 Insert_List_After_And_Analyze
3285 (Last (Actions (P)), Ins_Actions);
3286 else
3287 Set_Actions (P, Ins_Actions);
3288 Analyze_List (Actions (P));
3289 end if;
3291 Kill_Current_Values;
3293 return;
3294 end if;
3296 -- Then or Else operand of conditional expression. Add actions to
3297 -- Then_Actions or Else_Actions field as appropriate. The actions
3298 -- will be moved further out when the conditional is expanded.
3300 when N_Conditional_Expression =>
3301 declare
3302 ThenX : constant Node_Id := Next (First (Expressions (P)));
3303 ElseX : constant Node_Id := Next (ThenX);
3305 begin
3306 -- If the enclosing expression is already analyzed, as
3307 -- is the case for nested elaboration checks, insert the
3308 -- conditional further out.
3310 if Analyzed (P) then
3311 null;
3313 -- Actions belong to the then expression, temporarily place
3314 -- them as Then_Actions of the conditional expr. They will
3315 -- be moved to the proper place later when the conditional
3316 -- expression is expanded.
3318 elsif N = ThenX then
3319 if Present (Then_Actions (P)) then
3320 Insert_List_After_And_Analyze
3321 (Last (Then_Actions (P)), Ins_Actions);
3322 else
3323 Set_Then_Actions (P, Ins_Actions);
3324 Analyze_List (Then_Actions (P));
3325 end if;
3327 return;
3329 -- Actions belong to the else expression, temporarily
3330 -- place them as Else_Actions of the conditional expr.
3331 -- They will be moved to the proper place later when
3332 -- the conditional expression is expanded.
3334 elsif N = ElseX then
3335 if Present (Else_Actions (P)) then
3336 Insert_List_After_And_Analyze
3337 (Last (Else_Actions (P)), Ins_Actions);
3338 else
3339 Set_Else_Actions (P, Ins_Actions);
3340 Analyze_List (Else_Actions (P));
3341 end if;
3343 return;
3345 -- Actions belong to the condition. In this case they are
3346 -- unconditionally executed, and so we can continue the
3347 -- search for the proper insert point.
3349 else
3350 null;
3351 end if;
3352 end;
3354 -- Alternative of case expression, we place the action in the
3355 -- Actions field of the case expression alternative, this will
3356 -- be handled when the case expression is expanded.
3358 when N_Case_Expression_Alternative =>
3359 if Present (Actions (P)) then
3360 Insert_List_After_And_Analyze
3361 (Last (Actions (P)), Ins_Actions);
3362 else
3363 Set_Actions (P, Ins_Actions);
3364 Analyze_List (Actions (P));
3365 end if;
3367 return;
3369 -- Case of appearing within an Expressions_With_Actions node. We
3370 -- prepend the actions to the list of actions already there, if
3371 -- the node has not been analyzed yet. Otherwise find insertion
3372 -- location further up the tree.
3374 when N_Expression_With_Actions =>
3375 if not Analyzed (P) then
3376 Prepend_List (Ins_Actions, Actions (P));
3377 return;
3378 end if;
3380 -- Case of appearing in the condition of a while expression or
3381 -- elsif. We insert the actions into the Condition_Actions field.
3382 -- They will be moved further out when the while loop or elsif
3383 -- is analyzed.
3385 when N_Iteration_Scheme |
3386 N_Elsif_Part
3388 if N = Condition (P) then
3389 if Present (Condition_Actions (P)) then
3390 Insert_List_After_And_Analyze
3391 (Last (Condition_Actions (P)), Ins_Actions);
3392 else
3393 Set_Condition_Actions (P, Ins_Actions);
3395 -- Set the parent of the insert actions explicitly. This
3396 -- is not a syntactic field, but we need the parent field
3397 -- set, in particular so that freeze can understand that
3398 -- it is dealing with condition actions, and properly
3399 -- insert the freezing actions.
3401 Set_Parent (Ins_Actions, P);
3402 Analyze_List (Condition_Actions (P));
3403 end if;
3405 return;
3406 end if;
3408 -- Statements, declarations, pragmas, representation clauses
3410 when
3411 -- Statements
3413 N_Procedure_Call_Statement |
3414 N_Statement_Other_Than_Procedure_Call |
3416 -- Pragmas
3418 N_Pragma |
3420 -- Representation_Clause
3422 N_At_Clause |
3423 N_Attribute_Definition_Clause |
3424 N_Enumeration_Representation_Clause |
3425 N_Record_Representation_Clause |
3427 -- Declarations
3429 N_Abstract_Subprogram_Declaration |
3430 N_Entry_Body |
3431 N_Exception_Declaration |
3432 N_Exception_Renaming_Declaration |
3433 N_Expression_Function |
3434 N_Formal_Abstract_Subprogram_Declaration |
3435 N_Formal_Concrete_Subprogram_Declaration |
3436 N_Formal_Object_Declaration |
3437 N_Formal_Type_Declaration |
3438 N_Full_Type_Declaration |
3439 N_Function_Instantiation |
3440 N_Generic_Function_Renaming_Declaration |
3441 N_Generic_Package_Declaration |
3442 N_Generic_Package_Renaming_Declaration |
3443 N_Generic_Procedure_Renaming_Declaration |
3444 N_Generic_Subprogram_Declaration |
3445 N_Implicit_Label_Declaration |
3446 N_Incomplete_Type_Declaration |
3447 N_Number_Declaration |
3448 N_Object_Declaration |
3449 N_Object_Renaming_Declaration |
3450 N_Package_Body |
3451 N_Package_Body_Stub |
3452 N_Package_Declaration |
3453 N_Package_Instantiation |
3454 N_Package_Renaming_Declaration |
3455 N_Private_Extension_Declaration |
3456 N_Private_Type_Declaration |
3457 N_Procedure_Instantiation |
3458 N_Protected_Body |
3459 N_Protected_Body_Stub |
3460 N_Protected_Type_Declaration |
3461 N_Single_Task_Declaration |
3462 N_Subprogram_Body |
3463 N_Subprogram_Body_Stub |
3464 N_Subprogram_Declaration |
3465 N_Subprogram_Renaming_Declaration |
3466 N_Subtype_Declaration |
3467 N_Task_Body |
3468 N_Task_Body_Stub |
3469 N_Task_Type_Declaration |
3471 -- Use clauses can appear in lists of declarations
3473 N_Use_Package_Clause |
3474 N_Use_Type_Clause |
3476 -- Freeze entity behaves like a declaration or statement
3478 N_Freeze_Entity
3480 -- Do not insert here if the item is not a list member (this
3481 -- happens for example with a triggering statement, and the
3482 -- proper approach is to insert before the entire select).
3484 if not Is_List_Member (P) then
3485 null;
3487 -- Do not insert if parent of P is an N_Component_Association
3488 -- node (i.e. we are in the context of an N_Aggregate or
3489 -- N_Extension_Aggregate node. In this case we want to insert
3490 -- before the entire aggregate.
3492 elsif Nkind (Parent (P)) = N_Component_Association then
3493 null;
3495 -- Do not insert if the parent of P is either an N_Variant node
3496 -- or an N_Record_Definition node, meaning in either case that
3497 -- P is a member of a component list, and that therefore the
3498 -- actions should be inserted outside the complete record
3499 -- declaration.
3501 elsif Nkind (Parent (P)) = N_Variant
3502 or else Nkind (Parent (P)) = N_Record_Definition
3503 then
3504 null;
3506 -- Do not insert freeze nodes within the loop generated for
3507 -- an aggregate, because they may be elaborated too late for
3508 -- subsequent use in the back end: within a package spec the
3509 -- loop is part of the elaboration procedure and is only
3510 -- elaborated during the second pass.
3512 -- If the loop comes from source, or the entity is local to the
3513 -- loop itself it must remain within.
3515 elsif Nkind (Parent (P)) = N_Loop_Statement
3516 and then not Comes_From_Source (Parent (P))
3517 and then Nkind (First (Ins_Actions)) = N_Freeze_Entity
3518 and then
3519 Scope (Entity (First (Ins_Actions))) /= Current_Scope
3520 then
3521 null;
3523 -- Otherwise we can go ahead and do the insertion
3525 elsif P = Wrapped_Node then
3526 Store_Before_Actions_In_Scope (Ins_Actions);
3527 return;
3529 else
3530 Insert_List_Before_And_Analyze (P, Ins_Actions);
3531 return;
3532 end if;
3534 -- A special case, N_Raise_xxx_Error can act either as a statement
3535 -- or a subexpression. We tell the difference by looking at the
3536 -- Etype. It is set to Standard_Void_Type in the statement case.
3538 when
3539 N_Raise_xxx_Error =>
3540 if Etype (P) = Standard_Void_Type then
3541 if P = Wrapped_Node then
3542 Store_Before_Actions_In_Scope (Ins_Actions);
3543 else
3544 Insert_List_Before_And_Analyze (P, Ins_Actions);
3545 end if;
3547 return;
3549 -- In the subexpression case, keep climbing
3551 else
3552 null;
3553 end if;
3555 -- If a component association appears within a loop created for
3556 -- an array aggregate, attach the actions to the association so
3557 -- they can be subsequently inserted within the loop. For other
3558 -- component associations insert outside of the aggregate. For
3559 -- an association that will generate a loop, its Loop_Actions
3560 -- attribute is already initialized (see exp_aggr.adb).
3562 -- The list of loop_actions can in turn generate additional ones,
3563 -- that are inserted before the associated node. If the associated
3564 -- node is outside the aggregate, the new actions are collected
3565 -- at the end of the loop actions, to respect the order in which
3566 -- they are to be elaborated.
3568 when
3569 N_Component_Association =>
3570 if Nkind (Parent (P)) = N_Aggregate
3571 and then Present (Loop_Actions (P))
3572 then
3573 if Is_Empty_List (Loop_Actions (P)) then
3574 Set_Loop_Actions (P, Ins_Actions);
3575 Analyze_List (Ins_Actions);
3577 else
3578 declare
3579 Decl : Node_Id;
3581 begin
3582 -- Check whether these actions were generated by a
3583 -- declaration that is part of the loop_ actions
3584 -- for the component_association.
3586 Decl := Assoc_Node;
3587 while Present (Decl) loop
3588 exit when Parent (Decl) = P
3589 and then Is_List_Member (Decl)
3590 and then
3591 List_Containing (Decl) = Loop_Actions (P);
3592 Decl := Parent (Decl);
3593 end loop;
3595 if Present (Decl) then
3596 Insert_List_Before_And_Analyze
3597 (Decl, Ins_Actions);
3598 else
3599 Insert_List_After_And_Analyze
3600 (Last (Loop_Actions (P)), Ins_Actions);
3601 end if;
3602 end;
3603 end if;
3605 return;
3607 else
3608 null;
3609 end if;
3611 -- Another special case, an attribute denoting a procedure call
3613 when
3614 N_Attribute_Reference =>
3615 if Is_Procedure_Attribute_Name (Attribute_Name (P)) then
3616 if P = Wrapped_Node then
3617 Store_Before_Actions_In_Scope (Ins_Actions);
3618 else
3619 Insert_List_Before_And_Analyze (P, Ins_Actions);
3620 end if;
3622 return;
3624 -- In the subexpression case, keep climbing
3626 else
3627 null;
3628 end if;
3630 -- A contract node should not belong to the tree
3632 when N_Contract =>
3633 raise Program_Error;
3635 -- For all other node types, keep climbing tree
3637 when
3638 N_Abortable_Part |
3639 N_Accept_Alternative |
3640 N_Access_Definition |
3641 N_Access_Function_Definition |
3642 N_Access_Procedure_Definition |
3643 N_Access_To_Object_Definition |
3644 N_Aggregate |
3645 N_Allocator |
3646 N_Aspect_Specification |
3647 N_Case_Expression |
3648 N_Case_Statement_Alternative |
3649 N_Character_Literal |
3650 N_Compilation_Unit |
3651 N_Compilation_Unit_Aux |
3652 N_Component_Clause |
3653 N_Component_Declaration |
3654 N_Component_Definition |
3655 N_Component_List |
3656 N_Constrained_Array_Definition |
3657 N_Decimal_Fixed_Point_Definition |
3658 N_Defining_Character_Literal |
3659 N_Defining_Identifier |
3660 N_Defining_Operator_Symbol |
3661 N_Defining_Program_Unit_Name |
3662 N_Delay_Alternative |
3663 N_Delta_Constraint |
3664 N_Derived_Type_Definition |
3665 N_Designator |
3666 N_Digits_Constraint |
3667 N_Discriminant_Association |
3668 N_Discriminant_Specification |
3669 N_Empty |
3670 N_Entry_Body_Formal_Part |
3671 N_Entry_Call_Alternative |
3672 N_Entry_Declaration |
3673 N_Entry_Index_Specification |
3674 N_Enumeration_Type_Definition |
3675 N_Error |
3676 N_Exception_Handler |
3677 N_Expanded_Name |
3678 N_Explicit_Dereference |
3679 N_Extension_Aggregate |
3680 N_Floating_Point_Definition |
3681 N_Formal_Decimal_Fixed_Point_Definition |
3682 N_Formal_Derived_Type_Definition |
3683 N_Formal_Discrete_Type_Definition |
3684 N_Formal_Floating_Point_Definition |
3685 N_Formal_Modular_Type_Definition |
3686 N_Formal_Ordinary_Fixed_Point_Definition |
3687 N_Formal_Package_Declaration |
3688 N_Formal_Private_Type_Definition |
3689 N_Formal_Incomplete_Type_Definition |
3690 N_Formal_Signed_Integer_Type_Definition |
3691 N_Function_Call |
3692 N_Function_Specification |
3693 N_Generic_Association |
3694 N_Handled_Sequence_Of_Statements |
3695 N_Identifier |
3696 N_In |
3697 N_Index_Or_Discriminant_Constraint |
3698 N_Indexed_Component |
3699 N_Integer_Literal |
3700 N_Iterator_Specification |
3701 N_Itype_Reference |
3702 N_Label |
3703 N_Loop_Parameter_Specification |
3704 N_Mod_Clause |
3705 N_Modular_Type_Definition |
3706 N_Not_In |
3707 N_Null |
3708 N_Op_Abs |
3709 N_Op_Add |
3710 N_Op_And |
3711 N_Op_Concat |
3712 N_Op_Divide |
3713 N_Op_Eq |
3714 N_Op_Expon |
3715 N_Op_Ge |
3716 N_Op_Gt |
3717 N_Op_Le |
3718 N_Op_Lt |
3719 N_Op_Minus |
3720 N_Op_Mod |
3721 N_Op_Multiply |
3722 N_Op_Ne |
3723 N_Op_Not |
3724 N_Op_Or |
3725 N_Op_Plus |
3726 N_Op_Rem |
3727 N_Op_Rotate_Left |
3728 N_Op_Rotate_Right |
3729 N_Op_Shift_Left |
3730 N_Op_Shift_Right |
3731 N_Op_Shift_Right_Arithmetic |
3732 N_Op_Subtract |
3733 N_Op_Xor |
3734 N_Operator_Symbol |
3735 N_Ordinary_Fixed_Point_Definition |
3736 N_Others_Choice |
3737 N_Package_Specification |
3738 N_Parameter_Association |
3739 N_Parameter_Specification |
3740 N_Pop_Constraint_Error_Label |
3741 N_Pop_Program_Error_Label |
3742 N_Pop_Storage_Error_Label |
3743 N_Pragma_Argument_Association |
3744 N_Procedure_Specification |
3745 N_Protected_Definition |
3746 N_Push_Constraint_Error_Label |
3747 N_Push_Program_Error_Label |
3748 N_Push_Storage_Error_Label |
3749 N_Qualified_Expression |
3750 N_Quantified_Expression |
3751 N_Range |
3752 N_Range_Constraint |
3753 N_Real_Literal |
3754 N_Real_Range_Specification |
3755 N_Record_Definition |
3756 N_Reference |
3757 N_SCIL_Dispatch_Table_Tag_Init |
3758 N_SCIL_Dispatching_Call |
3759 N_SCIL_Membership_Test |
3760 N_Selected_Component |
3761 N_Signed_Integer_Type_Definition |
3762 N_Single_Protected_Declaration |
3763 N_Slice |
3764 N_String_Literal |
3765 N_Subprogram_Info |
3766 N_Subtype_Indication |
3767 N_Subunit |
3768 N_Task_Definition |
3769 N_Terminate_Alternative |
3770 N_Triggering_Alternative |
3771 N_Type_Conversion |
3772 N_Unchecked_Expression |
3773 N_Unchecked_Type_Conversion |
3774 N_Unconstrained_Array_Definition |
3775 N_Unused_At_End |
3776 N_Unused_At_Start |
3777 N_Variant |
3778 N_Variant_Part |
3779 N_Validate_Unchecked_Conversion |
3780 N_With_Clause
3782 null;
3784 end case;
3786 -- Make sure that inserted actions stay in the transient scope
3788 if P = Wrapped_Node then
3789 Store_Before_Actions_In_Scope (Ins_Actions);
3790 return;
3791 end if;
3793 -- If we fall through above tests, keep climbing tree
3795 N := P;
3797 if Nkind (Parent (N)) = N_Subunit then
3799 -- This is the proper body corresponding to a stub. Insertion must
3800 -- be done at the point of the stub, which is in the declarative
3801 -- part of the parent unit.
3803 P := Corresponding_Stub (Parent (N));
3805 else
3806 P := Parent (N);
3807 end if;
3808 end loop;
3809 end Insert_Actions;
3811 -- Version with check(s) suppressed
3813 procedure Insert_Actions
3814 (Assoc_Node : Node_Id;
3815 Ins_Actions : List_Id;
3816 Suppress : Check_Id)
3818 begin
3819 if Suppress = All_Checks then
3820 declare
3821 Svg : constant Suppress_Record := Scope_Suppress;
3822 begin
3823 Scope_Suppress := Suppress_All;
3824 Insert_Actions (Assoc_Node, Ins_Actions);
3825 Scope_Suppress := Svg;
3826 end;
3828 else
3829 declare
3830 Svg : constant Boolean := Scope_Suppress.Suppress (Suppress);
3831 begin
3832 Scope_Suppress.Suppress (Suppress) := True;
3833 Insert_Actions (Assoc_Node, Ins_Actions);
3834 Scope_Suppress.Suppress (Suppress) := Svg;
3835 end;
3836 end if;
3837 end Insert_Actions;
3839 --------------------------
3840 -- Insert_Actions_After --
3841 --------------------------
3843 procedure Insert_Actions_After
3844 (Assoc_Node : Node_Id;
3845 Ins_Actions : List_Id)
3847 begin
3848 if Scope_Is_Transient
3849 and then Assoc_Node = Node_To_Be_Wrapped
3850 then
3851 Store_After_Actions_In_Scope (Ins_Actions);
3852 else
3853 Insert_List_After_And_Analyze (Assoc_Node, Ins_Actions);
3854 end if;
3855 end Insert_Actions_After;
3857 ---------------------------------
3858 -- Insert_Library_Level_Action --
3859 ---------------------------------
3861 procedure Insert_Library_Level_Action (N : Node_Id) is
3862 Aux : constant Node_Id := Aux_Decls_Node (Cunit (Main_Unit));
3864 begin
3865 Push_Scope (Cunit_Entity (Main_Unit));
3866 -- ??? should this be Current_Sem_Unit instead of Main_Unit?
3868 if No (Actions (Aux)) then
3869 Set_Actions (Aux, New_List (N));
3870 else
3871 Append (N, Actions (Aux));
3872 end if;
3874 Analyze (N);
3875 Pop_Scope;
3876 end Insert_Library_Level_Action;
3878 ----------------------------------
3879 -- Insert_Library_Level_Actions --
3880 ----------------------------------
3882 procedure Insert_Library_Level_Actions (L : List_Id) is
3883 Aux : constant Node_Id := Aux_Decls_Node (Cunit (Main_Unit));
3885 begin
3886 if Is_Non_Empty_List (L) then
3887 Push_Scope (Cunit_Entity (Main_Unit));
3888 -- ??? should this be Current_Sem_Unit instead of Main_Unit?
3890 if No (Actions (Aux)) then
3891 Set_Actions (Aux, L);
3892 Analyze_List (L);
3893 else
3894 Insert_List_After_And_Analyze (Last (Actions (Aux)), L);
3895 end if;
3897 Pop_Scope;
3898 end if;
3899 end Insert_Library_Level_Actions;
3901 ----------------------
3902 -- Inside_Init_Proc --
3903 ----------------------
3905 function Inside_Init_Proc return Boolean is
3906 S : Entity_Id;
3908 begin
3909 S := Current_Scope;
3910 while Present (S)
3911 and then S /= Standard_Standard
3912 loop
3913 if Is_Init_Proc (S) then
3914 return True;
3915 else
3916 S := Scope (S);
3917 end if;
3918 end loop;
3920 return False;
3921 end Inside_Init_Proc;
3923 ----------------------------
3924 -- Is_All_Null_Statements --
3925 ----------------------------
3927 function Is_All_Null_Statements (L : List_Id) return Boolean is
3928 Stm : Node_Id;
3930 begin
3931 Stm := First (L);
3932 while Present (Stm) loop
3933 if Nkind (Stm) /= N_Null_Statement then
3934 return False;
3935 end if;
3937 Next (Stm);
3938 end loop;
3940 return True;
3941 end Is_All_Null_Statements;
3943 --------------------------------------------------
3944 -- Is_Displacement_Of_Object_Or_Function_Result --
3945 --------------------------------------------------
3947 function Is_Displacement_Of_Object_Or_Function_Result
3948 (Obj_Id : Entity_Id) return Boolean
3950 function Is_Controlled_Function_Call (N : Node_Id) return Boolean;
3951 -- Determine if particular node denotes a controlled function call
3953 function Is_Displace_Call (N : Node_Id) return Boolean;
3954 -- Determine whether a particular node is a call to Ada.Tags.Displace.
3955 -- The call might be nested within other actions such as conversions.
3957 function Is_Source_Object (N : Node_Id) return Boolean;
3958 -- Determine whether a particular node denotes a source object
3960 ---------------------------------
3961 -- Is_Controlled_Function_Call --
3962 ---------------------------------
3964 function Is_Controlled_Function_Call (N : Node_Id) return Boolean is
3965 Expr : Node_Id := Original_Node (N);
3967 begin
3968 if Nkind (Expr) = N_Function_Call then
3969 Expr := Name (Expr);
3970 end if;
3972 -- The function call may appear in object.operation format
3974 if Nkind (Expr) = N_Selected_Component then
3975 Expr := Selector_Name (Expr);
3976 end if;
3978 return
3979 Nkind_In (Expr, N_Expanded_Name, N_Identifier)
3980 and then Ekind (Entity (Expr)) = E_Function
3981 and then Needs_Finalization (Etype (Entity (Expr)));
3982 end Is_Controlled_Function_Call;
3984 ----------------------
3985 -- Is_Displace_Call --
3986 ----------------------
3988 function Is_Displace_Call (N : Node_Id) return Boolean is
3989 Call : Node_Id := N;
3991 begin
3992 -- Strip various actions which may precede a call to Displace
3994 loop
3995 if Nkind (Call) = N_Explicit_Dereference then
3996 Call := Prefix (Call);
3998 elsif Nkind_In (Call, N_Type_Conversion,
3999 N_Unchecked_Type_Conversion)
4000 then
4001 Call := Expression (Call);
4003 else
4004 exit;
4005 end if;
4006 end loop;
4008 return
4009 Present (Call)
4010 and then Nkind (Call) = N_Function_Call
4011 and then Is_RTE (Entity (Name (Call)), RE_Displace);
4012 end Is_Displace_Call;
4014 ----------------------
4015 -- Is_Source_Object --
4016 ----------------------
4018 function Is_Source_Object (N : Node_Id) return Boolean is
4019 begin
4020 return
4021 Present (N)
4022 and then Nkind (N) in N_Has_Entity
4023 and then Is_Object (Entity (N))
4024 and then Comes_From_Source (N);
4025 end Is_Source_Object;
4027 -- Local variables
4029 Decl : constant Node_Id := Parent (Obj_Id);
4030 Obj_Typ : constant Entity_Id := Base_Type (Etype (Obj_Id));
4031 Orig_Decl : constant Node_Id := Original_Node (Decl);
4033 -- Start of processing for Is_Displacement_Of_Object_Or_Function_Result
4035 begin
4036 -- Case 1:
4038 -- Obj : CW_Type := Function_Call (...);
4040 -- rewritten into:
4042 -- Tmp : ... := Function_Call (...)'reference;
4043 -- Obj : CW_Type renames (... Ada.Tags.Displace (Tmp));
4045 -- where the return type of the function and the class-wide type require
4046 -- dispatch table pointer displacement.
4048 -- Case 2:
4050 -- Obj : CW_Type := Src_Obj;
4052 -- rewritten into:
4054 -- Obj : CW_Type renames (... Ada.Tags.Displace (Src_Obj));
4056 -- where the type of the source object and the class-wide type require
4057 -- dispatch table pointer displacement.
4059 return
4060 Nkind (Decl) = N_Object_Renaming_Declaration
4061 and then Nkind (Orig_Decl) = N_Object_Declaration
4062 and then Comes_From_Source (Orig_Decl)
4063 and then Is_Class_Wide_Type (Obj_Typ)
4064 and then Is_Displace_Call (Renamed_Object (Obj_Id))
4065 and then
4066 (Is_Controlled_Function_Call (Expression (Orig_Decl))
4067 or else Is_Source_Object (Expression (Orig_Decl)));
4068 end Is_Displacement_Of_Object_Or_Function_Result;
4070 ------------------------------
4071 -- Is_Finalizable_Transient --
4072 ------------------------------
4074 function Is_Finalizable_Transient
4075 (Decl : Node_Id;
4076 Rel_Node : Node_Id) return Boolean
4078 Obj_Id : constant Entity_Id := Defining_Identifier (Decl);
4079 Obj_Typ : constant Entity_Id := Base_Type (Etype (Obj_Id));
4080 Desig : Entity_Id := Obj_Typ;
4082 function Initialized_By_Access (Trans_Id : Entity_Id) return Boolean;
4083 -- Determine whether transient object Trans_Id is initialized either
4084 -- by a function call which returns an access type or simply renames
4085 -- another pointer.
4087 function Initialized_By_Aliased_BIP_Func_Call
4088 (Trans_Id : Entity_Id) return Boolean;
4089 -- Determine whether transient object Trans_Id is initialized by a
4090 -- build-in-place function call where the BIPalloc parameter is of
4091 -- value 1 and BIPaccess is not null. This case creates an aliasing
4092 -- between the returned value and the value denoted by BIPaccess.
4094 function Is_Aliased
4095 (Trans_Id : Entity_Id;
4096 First_Stmt : Node_Id) return Boolean;
4097 -- Determine whether transient object Trans_Id has been renamed or
4098 -- aliased through 'reference in the statement list starting from
4099 -- First_Stmt.
4101 function Is_Allocated (Trans_Id : Entity_Id) return Boolean;
4102 -- Determine whether transient object Trans_Id is allocated on the heap
4104 function Is_Iterated_Container
4105 (Trans_Id : Entity_Id;
4106 First_Stmt : Node_Id) return Boolean;
4107 -- Determine whether transient object Trans_Id denotes a container which
4108 -- is in the process of being iterated in the statement list starting
4109 -- from First_Stmt.
4111 ---------------------------
4112 -- Initialized_By_Access --
4113 ---------------------------
4115 function Initialized_By_Access (Trans_Id : Entity_Id) return Boolean is
4116 Expr : constant Node_Id := Expression (Parent (Trans_Id));
4118 begin
4119 return
4120 Present (Expr)
4121 and then Nkind (Expr) /= N_Reference
4122 and then Is_Access_Type (Etype (Expr));
4123 end Initialized_By_Access;
4125 ------------------------------------------
4126 -- Initialized_By_Aliased_BIP_Func_Call --
4127 ------------------------------------------
4129 function Initialized_By_Aliased_BIP_Func_Call
4130 (Trans_Id : Entity_Id) return Boolean
4132 Call : Node_Id := Expression (Parent (Trans_Id));
4134 begin
4135 -- Build-in-place calls usually appear in 'reference format
4137 if Nkind (Call) = N_Reference then
4138 Call := Prefix (Call);
4139 end if;
4141 if Is_Build_In_Place_Function_Call (Call) then
4142 declare
4143 Access_Nam : Name_Id := No_Name;
4144 Access_OK : Boolean := False;
4145 Actual : Node_Id;
4146 Alloc_Nam : Name_Id := No_Name;
4147 Alloc_OK : Boolean := False;
4148 Formal : Node_Id;
4149 Func_Id : Entity_Id;
4150 Param : Node_Id;
4152 begin
4153 -- Examine all parameter associations of the function call
4155 Param := First (Parameter_Associations (Call));
4156 while Present (Param) loop
4157 if Nkind (Param) = N_Parameter_Association
4158 and then Nkind (Selector_Name (Param)) = N_Identifier
4159 then
4160 Actual := Explicit_Actual_Parameter (Param);
4161 Formal := Selector_Name (Param);
4163 -- Construct the names of formals BIPaccess and BIPalloc
4164 -- using the function name retrieved from an arbitrary
4165 -- formal.
4167 if Access_Nam = No_Name
4168 and then Alloc_Nam = No_Name
4169 and then Present (Entity (Formal))
4170 then
4171 Func_Id := Scope (Entity (Formal));
4173 Access_Nam :=
4174 New_External_Name (Chars (Func_Id),
4175 BIP_Formal_Suffix (BIP_Object_Access));
4177 Alloc_Nam :=
4178 New_External_Name (Chars (Func_Id),
4179 BIP_Formal_Suffix (BIP_Alloc_Form));
4180 end if;
4182 -- A match for BIPaccess => Temp has been found
4184 if Chars (Formal) = Access_Nam
4185 and then Nkind (Actual) /= N_Null
4186 then
4187 Access_OK := True;
4188 end if;
4190 -- A match for BIPalloc => 1 has been found
4192 if Chars (Formal) = Alloc_Nam
4193 and then Nkind (Actual) = N_Integer_Literal
4194 and then Intval (Actual) = Uint_1
4195 then
4196 Alloc_OK := True;
4197 end if;
4198 end if;
4200 Next (Param);
4201 end loop;
4203 return Access_OK and then Alloc_OK;
4204 end;
4205 end if;
4207 return False;
4208 end Initialized_By_Aliased_BIP_Func_Call;
4210 ----------------
4211 -- Is_Aliased --
4212 ----------------
4214 function Is_Aliased
4215 (Trans_Id : Entity_Id;
4216 First_Stmt : Node_Id) return Boolean
4218 function Find_Renamed_Object (Ren_Decl : Node_Id) return Entity_Id;
4219 -- Given an object renaming declaration, retrieve the entity of the
4220 -- renamed name. Return Empty if the renamed name is anything other
4221 -- than a variable or a constant.
4223 -------------------------
4224 -- Find_Renamed_Object --
4225 -------------------------
4227 function Find_Renamed_Object (Ren_Decl : Node_Id) return Entity_Id is
4228 Ren_Obj : Node_Id := Empty;
4230 function Find_Object (N : Node_Id) return Traverse_Result;
4231 -- Try to detect an object which is either a constant or a
4232 -- variable.
4234 -----------------
4235 -- Find_Object --
4236 -----------------
4238 function Find_Object (N : Node_Id) return Traverse_Result is
4239 begin
4240 -- Stop the search once a constant or a variable has been
4241 -- detected.
4243 if Nkind (N) = N_Identifier
4244 and then Present (Entity (N))
4245 and then Ekind_In (Entity (N), E_Constant, E_Variable)
4246 then
4247 Ren_Obj := Entity (N);
4248 return Abandon;
4249 end if;
4251 return OK;
4252 end Find_Object;
4254 procedure Search is new Traverse_Proc (Find_Object);
4256 -- Local variables
4258 Typ : constant Entity_Id := Etype (Defining_Identifier (Ren_Decl));
4260 -- Start of processing for Find_Renamed_Object
4262 begin
4263 -- Actions related to dispatching calls may appear as renamings of
4264 -- tags. Do not process this type of renaming because it does not
4265 -- use the actual value of the object.
4267 if not Is_RTE (Typ, RE_Tag_Ptr) then
4268 Search (Name (Ren_Decl));
4269 end if;
4271 return Ren_Obj;
4272 end Find_Renamed_Object;
4274 -- Local variables
4276 Expr : Node_Id;
4277 Ren_Obj : Entity_Id;
4278 Stmt : Node_Id;
4280 -- Start of processing for Is_Aliased
4282 begin
4283 Stmt := First_Stmt;
4284 while Present (Stmt) loop
4285 if Nkind (Stmt) = N_Object_Declaration then
4286 Expr := Expression (Stmt);
4288 if Present (Expr)
4289 and then Nkind (Expr) = N_Reference
4290 and then Nkind (Prefix (Expr)) = N_Identifier
4291 and then Entity (Prefix (Expr)) = Trans_Id
4292 then
4293 return True;
4294 end if;
4296 elsif Nkind (Stmt) = N_Object_Renaming_Declaration then
4297 Ren_Obj := Find_Renamed_Object (Stmt);
4299 if Present (Ren_Obj)
4300 and then Ren_Obj = Trans_Id
4301 then
4302 return True;
4303 end if;
4304 end if;
4306 Next (Stmt);
4307 end loop;
4309 return False;
4310 end Is_Aliased;
4312 ------------------
4313 -- Is_Allocated --
4314 ------------------
4316 function Is_Allocated (Trans_Id : Entity_Id) return Boolean is
4317 Expr : constant Node_Id := Expression (Parent (Trans_Id));
4318 begin
4319 return
4320 Is_Access_Type (Etype (Trans_Id))
4321 and then Present (Expr)
4322 and then Nkind (Expr) = N_Allocator;
4323 end Is_Allocated;
4325 ---------------------------
4326 -- Is_Iterated_Container --
4327 ---------------------------
4329 function Is_Iterated_Container
4330 (Trans_Id : Entity_Id;
4331 First_Stmt : Node_Id) return Boolean
4333 Aspect : Node_Id;
4334 Call : Node_Id;
4335 Iter : Entity_Id;
4336 Param : Node_Id;
4337 Stmt : Node_Id;
4338 Typ : Entity_Id;
4340 begin
4341 -- It is not possible to iterate over containers in non-Ada 2012 code
4343 if Ada_Version < Ada_2012 then
4344 return False;
4345 end if;
4347 Typ := Etype (Trans_Id);
4349 -- Handle access type created for secondary stack use
4351 if Is_Access_Type (Typ) then
4352 Typ := Designated_Type (Typ);
4353 end if;
4355 -- Look for aspect Default_Iterator
4357 if Has_Aspects (Parent (Typ)) then
4358 Aspect := Find_Aspect (Typ, Aspect_Default_Iterator);
4360 if Present (Aspect) then
4361 Iter := Entity (Aspect);
4363 -- Examine the statements following the container object and
4364 -- look for a call to the default iterate routine where the
4365 -- first parameter is the transient. Such a call appears as:
4367 -- It : Access_To_CW_Iterator :=
4368 -- Iterate (Tran_Id.all, ...)'reference;
4370 Stmt := First_Stmt;
4371 while Present (Stmt) loop
4373 -- Detect an object declaration which is initialized by a
4374 -- secondary stack function call.
4376 if Nkind (Stmt) = N_Object_Declaration
4377 and then Present (Expression (Stmt))
4378 and then Nkind (Expression (Stmt)) = N_Reference
4379 and then Nkind (Prefix (Expression (Stmt))) =
4380 N_Function_Call
4381 then
4382 Call := Prefix (Expression (Stmt));
4384 -- The call must invoke the default iterate routine of
4385 -- the container and the transient object must appear as
4386 -- the first actual parameter. Skip any calls whose names
4387 -- are not entities.
4389 if Is_Entity_Name (Name (Call))
4390 and then Entity (Name (Call)) = Iter
4391 and then Present (Parameter_Associations (Call))
4392 then
4393 Param := First (Parameter_Associations (Call));
4395 if Nkind (Param) = N_Explicit_Dereference
4396 and then Entity (Prefix (Param)) = Trans_Id
4397 then
4398 return True;
4399 end if;
4400 end if;
4401 end if;
4403 Next (Stmt);
4404 end loop;
4405 end if;
4406 end if;
4408 return False;
4409 end Is_Iterated_Container;
4411 -- Start of processing for Is_Finalizable_Transient
4413 begin
4414 -- Handle access types
4416 if Is_Access_Type (Desig) then
4417 Desig := Available_View (Designated_Type (Desig));
4418 end if;
4420 return
4421 Ekind_In (Obj_Id, E_Constant, E_Variable)
4422 and then Needs_Finalization (Desig)
4423 and then Requires_Transient_Scope (Desig)
4424 and then Nkind (Rel_Node) /= N_Simple_Return_Statement
4426 -- Do not consider renamed or 'reference-d transient objects because
4427 -- the act of renaming extends the object's lifetime.
4429 and then not Is_Aliased (Obj_Id, Decl)
4431 -- Do not consider transient objects allocated on the heap since
4432 -- they are attached to a finalization master.
4434 and then not Is_Allocated (Obj_Id)
4436 -- If the transient object is a pointer, check that it is not
4437 -- initialized by a function which returns a pointer or acts as a
4438 -- renaming of another pointer.
4440 and then
4441 (not Is_Access_Type (Obj_Typ)
4442 or else not Initialized_By_Access (Obj_Id))
4444 -- Do not consider transient objects which act as indirect aliases
4445 -- of build-in-place function results.
4447 and then not Initialized_By_Aliased_BIP_Func_Call (Obj_Id)
4449 -- Do not consider conversions of tags to class-wide types
4451 and then not Is_Tag_To_Class_Wide_Conversion (Obj_Id)
4453 -- Do not consider containers in the context of iterator loops. Such
4454 -- transient objects must exist for as long as the loop is around,
4455 -- otherwise any operation carried out by the iterator will fail.
4457 and then not Is_Iterated_Container (Obj_Id, Decl);
4458 end Is_Finalizable_Transient;
4460 ---------------------------------
4461 -- Is_Fully_Repped_Tagged_Type --
4462 ---------------------------------
4464 function Is_Fully_Repped_Tagged_Type (T : Entity_Id) return Boolean is
4465 U : constant Entity_Id := Underlying_Type (T);
4466 Comp : Entity_Id;
4468 begin
4469 if No (U) or else not Is_Tagged_Type (U) then
4470 return False;
4471 elsif Has_Discriminants (U) then
4472 return False;
4473 elsif not Has_Specified_Layout (U) then
4474 return False;
4475 end if;
4477 -- Here we have a tagged type, see if it has any unlayed out fields
4478 -- other than a possible tag and parent fields. If so, we return False.
4480 Comp := First_Component (U);
4481 while Present (Comp) loop
4482 if not Is_Tag (Comp)
4483 and then Chars (Comp) /= Name_uParent
4484 and then No (Component_Clause (Comp))
4485 then
4486 return False;
4487 else
4488 Next_Component (Comp);
4489 end if;
4490 end loop;
4492 -- All components are layed out
4494 return True;
4495 end Is_Fully_Repped_Tagged_Type;
4497 ----------------------------------
4498 -- Is_Library_Level_Tagged_Type --
4499 ----------------------------------
4501 function Is_Library_Level_Tagged_Type (Typ : Entity_Id) return Boolean is
4502 begin
4503 return Is_Tagged_Type (Typ)
4504 and then Is_Library_Level_Entity (Typ);
4505 end Is_Library_Level_Tagged_Type;
4507 --------------------------
4508 -- Is_Non_BIP_Func_Call --
4509 --------------------------
4511 function Is_Non_BIP_Func_Call (Expr : Node_Id) return Boolean is
4512 begin
4513 -- The expected call is of the format
4515 -- Func_Call'reference
4517 return
4518 Nkind (Expr) = N_Reference
4519 and then Nkind (Prefix (Expr)) = N_Function_Call
4520 and then not Is_Build_In_Place_Function_Call (Prefix (Expr));
4521 end Is_Non_BIP_Func_Call;
4523 ----------------------------------
4524 -- Is_Possibly_Unaligned_Object --
4525 ----------------------------------
4527 function Is_Possibly_Unaligned_Object (N : Node_Id) return Boolean is
4528 T : constant Entity_Id := Etype (N);
4530 begin
4531 -- If renamed object, apply test to underlying object
4533 if Is_Entity_Name (N)
4534 and then Is_Object (Entity (N))
4535 and then Present (Renamed_Object (Entity (N)))
4536 then
4537 return Is_Possibly_Unaligned_Object (Renamed_Object (Entity (N)));
4538 end if;
4540 -- Tagged and controlled types and aliased types are always aligned, as
4541 -- are concurrent types.
4543 if Is_Aliased (T)
4544 or else Has_Controlled_Component (T)
4545 or else Is_Concurrent_Type (T)
4546 or else Is_Tagged_Type (T)
4547 or else Is_Controlled (T)
4548 then
4549 return False;
4550 end if;
4552 -- If this is an element of a packed array, may be unaligned
4554 if Is_Ref_To_Bit_Packed_Array (N) then
4555 return True;
4556 end if;
4558 -- Case of indexed component reference: test whether prefix is unaligned
4560 if Nkind (N) = N_Indexed_Component then
4561 return Is_Possibly_Unaligned_Object (Prefix (N));
4563 -- Case of selected component reference
4565 elsif Nkind (N) = N_Selected_Component then
4566 declare
4567 P : constant Node_Id := Prefix (N);
4568 C : constant Entity_Id := Entity (Selector_Name (N));
4569 M : Nat;
4570 S : Nat;
4572 begin
4573 -- If component reference is for an array with non-static bounds,
4574 -- then it is always aligned: we can only process unaligned arrays
4575 -- with static bounds (more precisely compile time known bounds).
4577 if Is_Array_Type (T)
4578 and then not Compile_Time_Known_Bounds (T)
4579 then
4580 return False;
4581 end if;
4583 -- If component is aliased, it is definitely properly aligned
4585 if Is_Aliased (C) then
4586 return False;
4587 end if;
4589 -- If component is for a type implemented as a scalar, and the
4590 -- record is packed, and the component is other than the first
4591 -- component of the record, then the component may be unaligned.
4593 if Is_Packed (Etype (P))
4594 and then Represented_As_Scalar (Etype (C))
4595 and then First_Entity (Scope (C)) /= C
4596 then
4597 return True;
4598 end if;
4600 -- Compute maximum possible alignment for T
4602 -- If alignment is known, then that settles things
4604 if Known_Alignment (T) then
4605 M := UI_To_Int (Alignment (T));
4607 -- If alignment is not known, tentatively set max alignment
4609 else
4610 M := Ttypes.Maximum_Alignment;
4612 -- We can reduce this if the Esize is known since the default
4613 -- alignment will never be more than the smallest power of 2
4614 -- that does not exceed this Esize value.
4616 if Known_Esize (T) then
4617 S := UI_To_Int (Esize (T));
4619 while (M / 2) >= S loop
4620 M := M / 2;
4621 end loop;
4622 end if;
4623 end if;
4625 -- The following code is historical, it used to be present but it
4626 -- is too cautious, because the front-end does not know the proper
4627 -- default alignments for the target. Also, if the alignment is
4628 -- not known, the front end can't know in any case! If a copy is
4629 -- needed, the back-end will take care of it. This whole section
4630 -- including this comment can be removed later ???
4632 -- If the component reference is for a record that has a specified
4633 -- alignment, and we either know it is too small, or cannot tell,
4634 -- then the component may be unaligned.
4636 -- What is the following commented out code ???
4638 -- if Known_Alignment (Etype (P))
4639 -- and then Alignment (Etype (P)) < Ttypes.Maximum_Alignment
4640 -- and then M > Alignment (Etype (P))
4641 -- then
4642 -- return True;
4643 -- end if;
4645 -- Case of component clause present which may specify an
4646 -- unaligned position.
4648 if Present (Component_Clause (C)) then
4650 -- Otherwise we can do a test to make sure that the actual
4651 -- start position in the record, and the length, are both
4652 -- consistent with the required alignment. If not, we know
4653 -- that we are unaligned.
4655 declare
4656 Align_In_Bits : constant Nat := M * System_Storage_Unit;
4657 begin
4658 if Component_Bit_Offset (C) mod Align_In_Bits /= 0
4659 or else Esize (C) mod Align_In_Bits /= 0
4660 then
4661 return True;
4662 end if;
4663 end;
4664 end if;
4666 -- Otherwise, for a component reference, test prefix
4668 return Is_Possibly_Unaligned_Object (P);
4669 end;
4671 -- If not a component reference, must be aligned
4673 else
4674 return False;
4675 end if;
4676 end Is_Possibly_Unaligned_Object;
4678 ---------------------------------
4679 -- Is_Possibly_Unaligned_Slice --
4680 ---------------------------------
4682 function Is_Possibly_Unaligned_Slice (N : Node_Id) return Boolean is
4683 begin
4684 -- Go to renamed object
4686 if Is_Entity_Name (N)
4687 and then Is_Object (Entity (N))
4688 and then Present (Renamed_Object (Entity (N)))
4689 then
4690 return Is_Possibly_Unaligned_Slice (Renamed_Object (Entity (N)));
4691 end if;
4693 -- The reference must be a slice
4695 if Nkind (N) /= N_Slice then
4696 return False;
4697 end if;
4699 -- Always assume the worst for a nested record component with a
4700 -- component clause, which gigi/gcc does not appear to handle well.
4701 -- It is not clear why this special test is needed at all ???
4703 if Nkind (Prefix (N)) = N_Selected_Component
4704 and then Nkind (Prefix (Prefix (N))) = N_Selected_Component
4705 and then
4706 Present (Component_Clause (Entity (Selector_Name (Prefix (N)))))
4707 then
4708 return True;
4709 end if;
4711 -- We only need to worry if the target has strict alignment
4713 if not Target_Strict_Alignment then
4714 return False;
4715 end if;
4717 -- If it is a slice, then look at the array type being sliced
4719 declare
4720 Sarr : constant Node_Id := Prefix (N);
4721 -- Prefix of the slice, i.e. the array being sliced
4723 Styp : constant Entity_Id := Etype (Prefix (N));
4724 -- Type of the array being sliced
4726 Pref : Node_Id;
4727 Ptyp : Entity_Id;
4729 begin
4730 -- The problems arise if the array object that is being sliced
4731 -- is a component of a record or array, and we cannot guarantee
4732 -- the alignment of the array within its containing object.
4734 -- To investigate this, we look at successive prefixes to see
4735 -- if we have a worrisome indexed or selected component.
4737 Pref := Sarr;
4738 loop
4739 -- Case of array is part of an indexed component reference
4741 if Nkind (Pref) = N_Indexed_Component then
4742 Ptyp := Etype (Prefix (Pref));
4744 -- The only problematic case is when the array is packed, in
4745 -- which case we really know nothing about the alignment of
4746 -- individual components.
4748 if Is_Bit_Packed_Array (Ptyp) then
4749 return True;
4750 end if;
4752 -- Case of array is part of a selected component reference
4754 elsif Nkind (Pref) = N_Selected_Component then
4755 Ptyp := Etype (Prefix (Pref));
4757 -- We are definitely in trouble if the record in question
4758 -- has an alignment, and either we know this alignment is
4759 -- inconsistent with the alignment of the slice, or we don't
4760 -- know what the alignment of the slice should be.
4762 if Known_Alignment (Ptyp)
4763 and then (Unknown_Alignment (Styp)
4764 or else Alignment (Styp) > Alignment (Ptyp))
4765 then
4766 return True;
4767 end if;
4769 -- We are in potential trouble if the record type is packed.
4770 -- We could special case when we know that the array is the
4771 -- first component, but that's not such a simple case ???
4773 if Is_Packed (Ptyp) then
4774 return True;
4775 end if;
4777 -- We are in trouble if there is a component clause, and
4778 -- either we do not know the alignment of the slice, or
4779 -- the alignment of the slice is inconsistent with the
4780 -- bit position specified by the component clause.
4782 declare
4783 Field : constant Entity_Id := Entity (Selector_Name (Pref));
4784 begin
4785 if Present (Component_Clause (Field))
4786 and then
4787 (Unknown_Alignment (Styp)
4788 or else
4789 (Component_Bit_Offset (Field) mod
4790 (System_Storage_Unit * Alignment (Styp))) /= 0)
4791 then
4792 return True;
4793 end if;
4794 end;
4796 -- For cases other than selected or indexed components we know we
4797 -- are OK, since no issues arise over alignment.
4799 else
4800 return False;
4801 end if;
4803 -- We processed an indexed component or selected component
4804 -- reference that looked safe, so keep checking prefixes.
4806 Pref := Prefix (Pref);
4807 end loop;
4808 end;
4809 end Is_Possibly_Unaligned_Slice;
4811 -------------------------------
4812 -- Is_Related_To_Func_Return --
4813 -------------------------------
4815 function Is_Related_To_Func_Return (Id : Entity_Id) return Boolean is
4816 Expr : constant Node_Id := Related_Expression (Id);
4817 begin
4818 return
4819 Present (Expr)
4820 and then Nkind (Expr) = N_Explicit_Dereference
4821 and then Nkind (Parent (Expr)) = N_Simple_Return_Statement;
4822 end Is_Related_To_Func_Return;
4824 --------------------------------
4825 -- Is_Ref_To_Bit_Packed_Array --
4826 --------------------------------
4828 function Is_Ref_To_Bit_Packed_Array (N : Node_Id) return Boolean is
4829 Result : Boolean;
4830 Expr : Node_Id;
4832 begin
4833 if Is_Entity_Name (N)
4834 and then Is_Object (Entity (N))
4835 and then Present (Renamed_Object (Entity (N)))
4836 then
4837 return Is_Ref_To_Bit_Packed_Array (Renamed_Object (Entity (N)));
4838 end if;
4840 if Nkind (N) = N_Indexed_Component
4841 or else
4842 Nkind (N) = N_Selected_Component
4843 then
4844 if Is_Bit_Packed_Array (Etype (Prefix (N))) then
4845 Result := True;
4846 else
4847 Result := Is_Ref_To_Bit_Packed_Array (Prefix (N));
4848 end if;
4850 if Result and then Nkind (N) = N_Indexed_Component then
4851 Expr := First (Expressions (N));
4852 while Present (Expr) loop
4853 Force_Evaluation (Expr);
4854 Next (Expr);
4855 end loop;
4856 end if;
4858 return Result;
4860 else
4861 return False;
4862 end if;
4863 end Is_Ref_To_Bit_Packed_Array;
4865 --------------------------------
4866 -- Is_Ref_To_Bit_Packed_Slice --
4867 --------------------------------
4869 function Is_Ref_To_Bit_Packed_Slice (N : Node_Id) return Boolean is
4870 begin
4871 if Nkind (N) = N_Type_Conversion then
4872 return Is_Ref_To_Bit_Packed_Slice (Expression (N));
4874 elsif Is_Entity_Name (N)
4875 and then Is_Object (Entity (N))
4876 and then Present (Renamed_Object (Entity (N)))
4877 then
4878 return Is_Ref_To_Bit_Packed_Slice (Renamed_Object (Entity (N)));
4880 elsif Nkind (N) = N_Slice
4881 and then Is_Bit_Packed_Array (Etype (Prefix (N)))
4882 then
4883 return True;
4885 elsif Nkind (N) = N_Indexed_Component
4886 or else
4887 Nkind (N) = N_Selected_Component
4888 then
4889 return Is_Ref_To_Bit_Packed_Slice (Prefix (N));
4891 else
4892 return False;
4893 end if;
4894 end Is_Ref_To_Bit_Packed_Slice;
4896 -----------------------
4897 -- Is_Renamed_Object --
4898 -----------------------
4900 function Is_Renamed_Object (N : Node_Id) return Boolean is
4901 Pnod : constant Node_Id := Parent (N);
4902 Kind : constant Node_Kind := Nkind (Pnod);
4903 begin
4904 if Kind = N_Object_Renaming_Declaration then
4905 return True;
4906 elsif Nkind_In (Kind, N_Indexed_Component, N_Selected_Component) then
4907 return Is_Renamed_Object (Pnod);
4908 else
4909 return False;
4910 end if;
4911 end Is_Renamed_Object;
4913 --------------------------------------
4914 -- Is_Secondary_Stack_BIP_Func_Call --
4915 --------------------------------------
4917 function Is_Secondary_Stack_BIP_Func_Call (Expr : Node_Id) return Boolean is
4918 Call : Node_Id := Expr;
4920 begin
4921 -- Build-in-place calls usually appear in 'reference format. Note that
4922 -- the accessibility check machinery may add an extra 'reference due to
4923 -- side effect removal.
4925 while Nkind (Call) = N_Reference loop
4926 Call := Prefix (Call);
4927 end loop;
4929 if Nkind_In (Call, N_Qualified_Expression,
4930 N_Unchecked_Type_Conversion)
4931 then
4932 Call := Expression (Call);
4933 end if;
4935 if Is_Build_In_Place_Function_Call (Call) then
4936 declare
4937 Access_Nam : Name_Id := No_Name;
4938 Actual : Node_Id;
4939 Param : Node_Id;
4940 Formal : Node_Id;
4942 begin
4943 -- Examine all parameter associations of the function call
4945 Param := First (Parameter_Associations (Call));
4946 while Present (Param) loop
4947 if Nkind (Param) = N_Parameter_Association
4948 and then Nkind (Selector_Name (Param)) = N_Identifier
4949 then
4950 Formal := Selector_Name (Param);
4951 Actual := Explicit_Actual_Parameter (Param);
4953 -- Construct the name of formal BIPalloc. It is much easier
4954 -- to extract the name of the function using an arbitrary
4955 -- formal's scope rather than the Name field of Call.
4957 if Access_Nam = No_Name
4958 and then Present (Entity (Formal))
4959 then
4960 Access_Nam :=
4961 New_External_Name
4962 (Chars (Scope (Entity (Formal))),
4963 BIP_Formal_Suffix (BIP_Alloc_Form));
4964 end if;
4966 -- A match for BIPalloc => 2 has been found
4968 if Chars (Formal) = Access_Nam
4969 and then Nkind (Actual) = N_Integer_Literal
4970 and then Intval (Actual) = Uint_2
4971 then
4972 return True;
4973 end if;
4974 end if;
4976 Next (Param);
4977 end loop;
4978 end;
4979 end if;
4981 return False;
4982 end Is_Secondary_Stack_BIP_Func_Call;
4984 -------------------------------------
4985 -- Is_Tag_To_Class_Wide_Conversion --
4986 -------------------------------------
4988 function Is_Tag_To_Class_Wide_Conversion
4989 (Obj_Id : Entity_Id) return Boolean
4991 Expr : constant Node_Id := Expression (Parent (Obj_Id));
4993 begin
4994 return
4995 Is_Class_Wide_Type (Etype (Obj_Id))
4996 and then Present (Expr)
4997 and then Nkind (Expr) = N_Unchecked_Type_Conversion
4998 and then Etype (Expression (Expr)) = RTE (RE_Tag);
4999 end Is_Tag_To_Class_Wide_Conversion;
5001 ----------------------------
5002 -- Is_Untagged_Derivation --
5003 ----------------------------
5005 function Is_Untagged_Derivation (T : Entity_Id) return Boolean is
5006 begin
5007 return (not Is_Tagged_Type (T) and then Is_Derived_Type (T))
5008 or else
5009 (Is_Private_Type (T) and then Present (Full_View (T))
5010 and then not Is_Tagged_Type (Full_View (T))
5011 and then Is_Derived_Type (Full_View (T))
5012 and then Etype (Full_View (T)) /= T);
5013 end Is_Untagged_Derivation;
5015 ---------------------------
5016 -- Is_Volatile_Reference --
5017 ---------------------------
5019 function Is_Volatile_Reference (N : Node_Id) return Boolean is
5020 begin
5021 if Nkind (N) in N_Has_Etype
5022 and then Present (Etype (N))
5023 and then Treat_As_Volatile (Etype (N))
5024 then
5025 return True;
5027 elsif Is_Entity_Name (N) then
5028 return Treat_As_Volatile (Entity (N));
5030 elsif Nkind (N) = N_Slice then
5031 return Is_Volatile_Reference (Prefix (N));
5033 elsif Nkind_In (N, N_Indexed_Component, N_Selected_Component) then
5034 if (Is_Entity_Name (Prefix (N))
5035 and then Has_Volatile_Components (Entity (Prefix (N))))
5036 or else (Present (Etype (Prefix (N)))
5037 and then Has_Volatile_Components (Etype (Prefix (N))))
5038 then
5039 return True;
5040 else
5041 return Is_Volatile_Reference (Prefix (N));
5042 end if;
5044 else
5045 return False;
5046 end if;
5047 end Is_Volatile_Reference;
5049 --------------------------
5050 -- Is_VM_By_Copy_Actual --
5051 --------------------------
5053 function Is_VM_By_Copy_Actual (N : Node_Id) return Boolean is
5054 begin
5055 return VM_Target /= No_VM
5056 and then (Nkind (N) = N_Slice
5057 or else
5058 (Nkind (N) = N_Identifier
5059 and then Present (Renamed_Object (Entity (N)))
5060 and then Nkind (Renamed_Object (Entity (N)))
5061 = N_Slice));
5062 end Is_VM_By_Copy_Actual;
5064 --------------------
5065 -- Kill_Dead_Code --
5066 --------------------
5068 procedure Kill_Dead_Code (N : Node_Id; Warn : Boolean := False) is
5069 W : Boolean := Warn;
5070 -- Set False if warnings suppressed
5072 begin
5073 if Present (N) then
5074 Remove_Warning_Messages (N);
5076 -- Generate warning if appropriate
5078 if W then
5080 -- We suppress the warning if this code is under control of an
5081 -- if statement, whose condition is a simple identifier, and
5082 -- either we are in an instance, or warnings off is set for this
5083 -- identifier. The reason for killing it in the instance case is
5084 -- that it is common and reasonable for code to be deleted in
5085 -- instances for various reasons.
5087 if Nkind (Parent (N)) = N_If_Statement then
5088 declare
5089 C : constant Node_Id := Condition (Parent (N));
5090 begin
5091 if Nkind (C) = N_Identifier
5092 and then
5093 (In_Instance
5094 or else (Present (Entity (C))
5095 and then Has_Warnings_Off (Entity (C))))
5096 then
5097 W := False;
5098 end if;
5099 end;
5100 end if;
5102 -- Generate warning if not suppressed
5104 if W then
5105 Error_Msg_F
5106 ("?this code can never be executed and has been deleted!", N);
5107 end if;
5108 end if;
5110 -- Recurse into block statements and bodies to process declarations
5111 -- and statements.
5113 if Nkind (N) = N_Block_Statement
5114 or else Nkind (N) = N_Subprogram_Body
5115 or else Nkind (N) = N_Package_Body
5116 then
5117 Kill_Dead_Code (Declarations (N), False);
5118 Kill_Dead_Code (Statements (Handled_Statement_Sequence (N)));
5120 if Nkind (N) = N_Subprogram_Body then
5121 Set_Is_Eliminated (Defining_Entity (N));
5122 end if;
5124 elsif Nkind (N) = N_Package_Declaration then
5125 Kill_Dead_Code (Visible_Declarations (Specification (N)));
5126 Kill_Dead_Code (Private_Declarations (Specification (N)));
5128 -- ??? After this point, Delete_Tree has been called on all
5129 -- declarations in Specification (N), so references to entities
5130 -- therein look suspicious.
5132 declare
5133 E : Entity_Id := First_Entity (Defining_Entity (N));
5134 begin
5135 while Present (E) loop
5136 if Ekind (E) = E_Operator then
5137 Set_Is_Eliminated (E);
5138 end if;
5140 Next_Entity (E);
5141 end loop;
5142 end;
5144 -- Recurse into composite statement to kill individual statements in
5145 -- particular instantiations.
5147 elsif Nkind (N) = N_If_Statement then
5148 Kill_Dead_Code (Then_Statements (N));
5149 Kill_Dead_Code (Elsif_Parts (N));
5150 Kill_Dead_Code (Else_Statements (N));
5152 elsif Nkind (N) = N_Loop_Statement then
5153 Kill_Dead_Code (Statements (N));
5155 elsif Nkind (N) = N_Case_Statement then
5156 declare
5157 Alt : Node_Id;
5158 begin
5159 Alt := First (Alternatives (N));
5160 while Present (Alt) loop
5161 Kill_Dead_Code (Statements (Alt));
5162 Next (Alt);
5163 end loop;
5164 end;
5166 elsif Nkind (N) = N_Case_Statement_Alternative then
5167 Kill_Dead_Code (Statements (N));
5169 -- Deal with dead instances caused by deleting instantiations
5171 elsif Nkind (N) in N_Generic_Instantiation then
5172 Remove_Dead_Instance (N);
5173 end if;
5174 end if;
5175 end Kill_Dead_Code;
5177 -- Case where argument is a list of nodes to be killed
5179 procedure Kill_Dead_Code (L : List_Id; Warn : Boolean := False) is
5180 N : Node_Id;
5181 W : Boolean;
5182 begin
5183 W := Warn;
5184 if Is_Non_Empty_List (L) then
5185 N := First (L);
5186 while Present (N) loop
5187 Kill_Dead_Code (N, W);
5188 W := False;
5189 Next (N);
5190 end loop;
5191 end if;
5192 end Kill_Dead_Code;
5194 ------------------------
5195 -- Known_Non_Negative --
5196 ------------------------
5198 function Known_Non_Negative (Opnd : Node_Id) return Boolean is
5199 begin
5200 if Is_OK_Static_Expression (Opnd)
5201 and then Expr_Value (Opnd) >= 0
5202 then
5203 return True;
5205 else
5206 declare
5207 Lo : constant Node_Id := Type_Low_Bound (Etype (Opnd));
5209 begin
5210 return
5211 Is_OK_Static_Expression (Lo) and then Expr_Value (Lo) >= 0;
5212 end;
5213 end if;
5214 end Known_Non_Negative;
5216 --------------------
5217 -- Known_Non_Null --
5218 --------------------
5220 function Known_Non_Null (N : Node_Id) return Boolean is
5221 begin
5222 -- Checks for case where N is an entity reference
5224 if Is_Entity_Name (N) and then Present (Entity (N)) then
5225 declare
5226 E : constant Entity_Id := Entity (N);
5227 Op : Node_Kind;
5228 Val : Node_Id;
5230 begin
5231 -- First check if we are in decisive conditional
5233 Get_Current_Value_Condition (N, Op, Val);
5235 if Known_Null (Val) then
5236 if Op = N_Op_Eq then
5237 return False;
5238 elsif Op = N_Op_Ne then
5239 return True;
5240 end if;
5241 end if;
5243 -- If OK to do replacement, test Is_Known_Non_Null flag
5245 if OK_To_Do_Constant_Replacement (E) then
5246 return Is_Known_Non_Null (E);
5248 -- Otherwise if not safe to do replacement, then say so
5250 else
5251 return False;
5252 end if;
5253 end;
5255 -- True if access attribute
5257 elsif Nkind (N) = N_Attribute_Reference
5258 and then (Attribute_Name (N) = Name_Access
5259 or else
5260 Attribute_Name (N) = Name_Unchecked_Access
5261 or else
5262 Attribute_Name (N) = Name_Unrestricted_Access)
5263 then
5264 return True;
5266 -- True if allocator
5268 elsif Nkind (N) = N_Allocator then
5269 return True;
5271 -- For a conversion, true if expression is known non-null
5273 elsif Nkind (N) = N_Type_Conversion then
5274 return Known_Non_Null (Expression (N));
5276 -- Above are all cases where the value could be determined to be
5277 -- non-null. In all other cases, we don't know, so return False.
5279 else
5280 return False;
5281 end if;
5282 end Known_Non_Null;
5284 ----------------
5285 -- Known_Null --
5286 ----------------
5288 function Known_Null (N : Node_Id) return Boolean is
5289 begin
5290 -- Checks for case where N is an entity reference
5292 if Is_Entity_Name (N) and then Present (Entity (N)) then
5293 declare
5294 E : constant Entity_Id := Entity (N);
5295 Op : Node_Kind;
5296 Val : Node_Id;
5298 begin
5299 -- Constant null value is for sure null
5301 if Ekind (E) = E_Constant
5302 and then Known_Null (Constant_Value (E))
5303 then
5304 return True;
5305 end if;
5307 -- First check if we are in decisive conditional
5309 Get_Current_Value_Condition (N, Op, Val);
5311 if Known_Null (Val) then
5312 if Op = N_Op_Eq then
5313 return True;
5314 elsif Op = N_Op_Ne then
5315 return False;
5316 end if;
5317 end if;
5319 -- If OK to do replacement, test Is_Known_Null flag
5321 if OK_To_Do_Constant_Replacement (E) then
5322 return Is_Known_Null (E);
5324 -- Otherwise if not safe to do replacement, then say so
5326 else
5327 return False;
5328 end if;
5329 end;
5331 -- True if explicit reference to null
5333 elsif Nkind (N) = N_Null then
5334 return True;
5336 -- For a conversion, true if expression is known null
5338 elsif Nkind (N) = N_Type_Conversion then
5339 return Known_Null (Expression (N));
5341 -- Above are all cases where the value could be determined to be null.
5342 -- In all other cases, we don't know, so return False.
5344 else
5345 return False;
5346 end if;
5347 end Known_Null;
5349 -----------------------------
5350 -- Make_CW_Equivalent_Type --
5351 -----------------------------
5353 -- Create a record type used as an equivalent of any member of the class
5354 -- which takes its size from exp.
5356 -- Generate the following code:
5358 -- type Equiv_T is record
5359 -- _parent : T (List of discriminant constraints taken from Exp);
5360 -- Ext__50 : Storage_Array (1 .. (Exp'size - Typ'object_size)/8);
5361 -- end Equiv_T;
5363 -- ??? Note that this type does not guarantee same alignment as all
5364 -- derived types
5366 function Make_CW_Equivalent_Type
5367 (T : Entity_Id;
5368 E : Node_Id) return Entity_Id
5370 Loc : constant Source_Ptr := Sloc (E);
5371 Root_Typ : constant Entity_Id := Root_Type (T);
5372 List_Def : constant List_Id := Empty_List;
5373 Comp_List : constant List_Id := New_List;
5374 Equiv_Type : Entity_Id;
5375 Range_Type : Entity_Id;
5376 Str_Type : Entity_Id;
5377 Constr_Root : Entity_Id;
5378 Sizexpr : Node_Id;
5380 begin
5381 -- If the root type is already constrained, there are no discriminants
5382 -- in the expression.
5384 if not Has_Discriminants (Root_Typ)
5385 or else Is_Constrained (Root_Typ)
5386 then
5387 Constr_Root := Root_Typ;
5388 else
5389 Constr_Root := Make_Temporary (Loc, 'R');
5391 -- subtype cstr__n is T (List of discr constraints taken from Exp)
5393 Append_To (List_Def,
5394 Make_Subtype_Declaration (Loc,
5395 Defining_Identifier => Constr_Root,
5396 Subtype_Indication => Make_Subtype_From_Expr (E, Root_Typ)));
5397 end if;
5399 -- Generate the range subtype declaration
5401 Range_Type := Make_Temporary (Loc, 'G');
5403 if not Is_Interface (Root_Typ) then
5405 -- subtype rg__xx is
5406 -- Storage_Offset range 1 .. (Expr'size - typ'size) / Storage_Unit
5408 Sizexpr :=
5409 Make_Op_Subtract (Loc,
5410 Left_Opnd =>
5411 Make_Attribute_Reference (Loc,
5412 Prefix =>
5413 OK_Convert_To (T, Duplicate_Subexpr_No_Checks (E)),
5414 Attribute_Name => Name_Size),
5415 Right_Opnd =>
5416 Make_Attribute_Reference (Loc,
5417 Prefix => New_Reference_To (Constr_Root, Loc),
5418 Attribute_Name => Name_Object_Size));
5419 else
5420 -- subtype rg__xx is
5421 -- Storage_Offset range 1 .. Expr'size / Storage_Unit
5423 Sizexpr :=
5424 Make_Attribute_Reference (Loc,
5425 Prefix =>
5426 OK_Convert_To (T, Duplicate_Subexpr_No_Checks (E)),
5427 Attribute_Name => Name_Size);
5428 end if;
5430 Set_Paren_Count (Sizexpr, 1);
5432 Append_To (List_Def,
5433 Make_Subtype_Declaration (Loc,
5434 Defining_Identifier => Range_Type,
5435 Subtype_Indication =>
5436 Make_Subtype_Indication (Loc,
5437 Subtype_Mark => New_Reference_To (RTE (RE_Storage_Offset), Loc),
5438 Constraint => Make_Range_Constraint (Loc,
5439 Range_Expression =>
5440 Make_Range (Loc,
5441 Low_Bound => Make_Integer_Literal (Loc, 1),
5442 High_Bound =>
5443 Make_Op_Divide (Loc,
5444 Left_Opnd => Sizexpr,
5445 Right_Opnd => Make_Integer_Literal (Loc,
5446 Intval => System_Storage_Unit)))))));
5448 -- subtype str__nn is Storage_Array (rg__x);
5450 Str_Type := Make_Temporary (Loc, 'S');
5451 Append_To (List_Def,
5452 Make_Subtype_Declaration (Loc,
5453 Defining_Identifier => Str_Type,
5454 Subtype_Indication =>
5455 Make_Subtype_Indication (Loc,
5456 Subtype_Mark => New_Reference_To (RTE (RE_Storage_Array), Loc),
5457 Constraint =>
5458 Make_Index_Or_Discriminant_Constraint (Loc,
5459 Constraints =>
5460 New_List (New_Reference_To (Range_Type, Loc))))));
5462 -- type Equiv_T is record
5463 -- [ _parent : Tnn; ]
5464 -- E : Str_Type;
5465 -- end Equiv_T;
5467 Equiv_Type := Make_Temporary (Loc, 'T');
5468 Set_Ekind (Equiv_Type, E_Record_Type);
5469 Set_Parent_Subtype (Equiv_Type, Constr_Root);
5471 -- Set Is_Class_Wide_Equivalent_Type very early to trigger the special
5472 -- treatment for this type. In particular, even though _parent's type
5473 -- is a controlled type or contains controlled components, we do not
5474 -- want to set Has_Controlled_Component on it to avoid making it gain
5475 -- an unwanted _controller component.
5477 Set_Is_Class_Wide_Equivalent_Type (Equiv_Type);
5479 if not Is_Interface (Root_Typ) then
5480 Append_To (Comp_List,
5481 Make_Component_Declaration (Loc,
5482 Defining_Identifier =>
5483 Make_Defining_Identifier (Loc, Name_uParent),
5484 Component_Definition =>
5485 Make_Component_Definition (Loc,
5486 Aliased_Present => False,
5487 Subtype_Indication => New_Reference_To (Constr_Root, Loc))));
5488 end if;
5490 Append_To (Comp_List,
5491 Make_Component_Declaration (Loc,
5492 Defining_Identifier => Make_Temporary (Loc, 'C'),
5493 Component_Definition =>
5494 Make_Component_Definition (Loc,
5495 Aliased_Present => False,
5496 Subtype_Indication => New_Reference_To (Str_Type, Loc))));
5498 Append_To (List_Def,
5499 Make_Full_Type_Declaration (Loc,
5500 Defining_Identifier => Equiv_Type,
5501 Type_Definition =>
5502 Make_Record_Definition (Loc,
5503 Component_List =>
5504 Make_Component_List (Loc,
5505 Component_Items => Comp_List,
5506 Variant_Part => Empty))));
5508 -- Suppress all checks during the analysis of the expanded code to avoid
5509 -- the generation of spurious warnings under ZFP run-time.
5511 Insert_Actions (E, List_Def, Suppress => All_Checks);
5512 return Equiv_Type;
5513 end Make_CW_Equivalent_Type;
5515 -------------------------
5516 -- Make_Invariant_Call --
5517 -------------------------
5519 function Make_Invariant_Call (Expr : Node_Id) return Node_Id is
5520 Loc : constant Source_Ptr := Sloc (Expr);
5521 Typ : constant Entity_Id := Etype (Expr);
5523 begin
5524 pragma Assert
5525 (Has_Invariants (Typ) and then Present (Invariant_Procedure (Typ)));
5527 if Check_Enabled (Name_Invariant)
5528 or else
5529 Check_Enabled (Name_Assertion)
5530 then
5531 return
5532 Make_Procedure_Call_Statement (Loc,
5533 Name =>
5534 New_Occurrence_Of (Invariant_Procedure (Typ), Loc),
5535 Parameter_Associations => New_List (Relocate_Node (Expr)));
5537 else
5538 return
5539 Make_Null_Statement (Loc);
5540 end if;
5541 end Make_Invariant_Call;
5543 ------------------------
5544 -- Make_Literal_Range --
5545 ------------------------
5547 function Make_Literal_Range
5548 (Loc : Source_Ptr;
5549 Literal_Typ : Entity_Id) return Node_Id
5551 Lo : constant Node_Id :=
5552 New_Copy_Tree (String_Literal_Low_Bound (Literal_Typ));
5553 Index : constant Entity_Id := Etype (Lo);
5555 Hi : Node_Id;
5556 Length_Expr : constant Node_Id :=
5557 Make_Op_Subtract (Loc,
5558 Left_Opnd =>
5559 Make_Integer_Literal (Loc,
5560 Intval => String_Literal_Length (Literal_Typ)),
5561 Right_Opnd =>
5562 Make_Integer_Literal (Loc, 1));
5564 begin
5565 Set_Analyzed (Lo, False);
5567 if Is_Integer_Type (Index) then
5568 Hi :=
5569 Make_Op_Add (Loc,
5570 Left_Opnd => New_Copy_Tree (Lo),
5571 Right_Opnd => Length_Expr);
5572 else
5573 Hi :=
5574 Make_Attribute_Reference (Loc,
5575 Attribute_Name => Name_Val,
5576 Prefix => New_Occurrence_Of (Index, Loc),
5577 Expressions => New_List (
5578 Make_Op_Add (Loc,
5579 Left_Opnd =>
5580 Make_Attribute_Reference (Loc,
5581 Attribute_Name => Name_Pos,
5582 Prefix => New_Occurrence_Of (Index, Loc),
5583 Expressions => New_List (New_Copy_Tree (Lo))),
5584 Right_Opnd => Length_Expr)));
5585 end if;
5587 return
5588 Make_Range (Loc,
5589 Low_Bound => Lo,
5590 High_Bound => Hi);
5591 end Make_Literal_Range;
5593 --------------------------
5594 -- Make_Non_Empty_Check --
5595 --------------------------
5597 function Make_Non_Empty_Check
5598 (Loc : Source_Ptr;
5599 N : Node_Id) return Node_Id
5601 begin
5602 return
5603 Make_Op_Ne (Loc,
5604 Left_Opnd =>
5605 Make_Attribute_Reference (Loc,
5606 Attribute_Name => Name_Length,
5607 Prefix => Duplicate_Subexpr_No_Checks (N, Name_Req => True)),
5608 Right_Opnd =>
5609 Make_Integer_Literal (Loc, 0));
5610 end Make_Non_Empty_Check;
5612 -------------------------
5613 -- Make_Predicate_Call --
5614 -------------------------
5616 function Make_Predicate_Call
5617 (Typ : Entity_Id;
5618 Expr : Node_Id) return Node_Id
5620 Loc : constant Source_Ptr := Sloc (Expr);
5622 begin
5623 pragma Assert (Present (Predicate_Function (Typ)));
5625 return
5626 Make_Function_Call (Loc,
5627 Name =>
5628 New_Occurrence_Of (Predicate_Function (Typ), Loc),
5629 Parameter_Associations => New_List (Relocate_Node (Expr)));
5630 end Make_Predicate_Call;
5632 --------------------------
5633 -- Make_Predicate_Check --
5634 --------------------------
5636 function Make_Predicate_Check
5637 (Typ : Entity_Id;
5638 Expr : Node_Id) return Node_Id
5640 Loc : constant Source_Ptr := Sloc (Expr);
5642 begin
5643 return
5644 Make_Pragma (Loc,
5645 Pragma_Identifier => Make_Identifier (Loc, Name_Check),
5646 Pragma_Argument_Associations => New_List (
5647 Make_Pragma_Argument_Association (Loc,
5648 Expression => Make_Identifier (Loc, Name_Predicate)),
5649 Make_Pragma_Argument_Association (Loc,
5650 Expression => Make_Predicate_Call (Typ, Expr))));
5651 end Make_Predicate_Check;
5653 ----------------------------
5654 -- Make_Subtype_From_Expr --
5655 ----------------------------
5657 -- 1. If Expr is an unconstrained array expression, creates
5658 -- Unc_Type(Expr'first(1)..Expr'last(1),..., Expr'first(n)..Expr'last(n))
5660 -- 2. If Expr is a unconstrained discriminated type expression, creates
5661 -- Unc_Type(Expr.Discr1, ... , Expr.Discr_n)
5663 -- 3. If Expr is class-wide, creates an implicit class wide subtype
5665 function Make_Subtype_From_Expr
5666 (E : Node_Id;
5667 Unc_Typ : Entity_Id) return Node_Id
5669 Loc : constant Source_Ptr := Sloc (E);
5670 List_Constr : constant List_Id := New_List;
5671 D : Entity_Id;
5673 Full_Subtyp : Entity_Id;
5674 Priv_Subtyp : Entity_Id;
5675 Utyp : Entity_Id;
5676 Full_Exp : Node_Id;
5678 begin
5679 if Is_Private_Type (Unc_Typ)
5680 and then Has_Unknown_Discriminants (Unc_Typ)
5681 then
5682 -- Prepare the subtype completion, Go to base type to
5683 -- find underlying type, because the type may be a generic
5684 -- actual or an explicit subtype.
5686 Utyp := Underlying_Type (Base_Type (Unc_Typ));
5687 Full_Subtyp := Make_Temporary (Loc, 'C');
5688 Full_Exp :=
5689 Unchecked_Convert_To (Utyp, Duplicate_Subexpr_No_Checks (E));
5690 Set_Parent (Full_Exp, Parent (E));
5692 Priv_Subtyp := Make_Temporary (Loc, 'P');
5694 Insert_Action (E,
5695 Make_Subtype_Declaration (Loc,
5696 Defining_Identifier => Full_Subtyp,
5697 Subtype_Indication => Make_Subtype_From_Expr (Full_Exp, Utyp)));
5699 -- Define the dummy private subtype
5701 Set_Ekind (Priv_Subtyp, Subtype_Kind (Ekind (Unc_Typ)));
5702 Set_Etype (Priv_Subtyp, Base_Type (Unc_Typ));
5703 Set_Scope (Priv_Subtyp, Full_Subtyp);
5704 Set_Is_Constrained (Priv_Subtyp);
5705 Set_Is_Tagged_Type (Priv_Subtyp, Is_Tagged_Type (Unc_Typ));
5706 Set_Is_Itype (Priv_Subtyp);
5707 Set_Associated_Node_For_Itype (Priv_Subtyp, E);
5709 if Is_Tagged_Type (Priv_Subtyp) then
5710 Set_Class_Wide_Type
5711 (Base_Type (Priv_Subtyp), Class_Wide_Type (Unc_Typ));
5712 Set_Direct_Primitive_Operations (Priv_Subtyp,
5713 Direct_Primitive_Operations (Unc_Typ));
5714 end if;
5716 Set_Full_View (Priv_Subtyp, Full_Subtyp);
5718 return New_Reference_To (Priv_Subtyp, Loc);
5720 elsif Is_Array_Type (Unc_Typ) then
5721 for J in 1 .. Number_Dimensions (Unc_Typ) loop
5722 Append_To (List_Constr,
5723 Make_Range (Loc,
5724 Low_Bound =>
5725 Make_Attribute_Reference (Loc,
5726 Prefix => Duplicate_Subexpr_No_Checks (E),
5727 Attribute_Name => Name_First,
5728 Expressions => New_List (
5729 Make_Integer_Literal (Loc, J))),
5731 High_Bound =>
5732 Make_Attribute_Reference (Loc,
5733 Prefix => Duplicate_Subexpr_No_Checks (E),
5734 Attribute_Name => Name_Last,
5735 Expressions => New_List (
5736 Make_Integer_Literal (Loc, J)))));
5737 end loop;
5739 elsif Is_Class_Wide_Type (Unc_Typ) then
5740 declare
5741 CW_Subtype : Entity_Id;
5742 EQ_Typ : Entity_Id := Empty;
5744 begin
5745 -- A class-wide equivalent type is not needed when VM_Target
5746 -- because the VM back-ends handle the class-wide object
5747 -- initialization itself (and doesn't need or want the
5748 -- additional intermediate type to handle the assignment).
5750 if Expander_Active and then Tagged_Type_Expansion then
5752 -- If this is the class_wide type of a completion that is a
5753 -- record subtype, set the type of the class_wide type to be
5754 -- the full base type, for use in the expanded code for the
5755 -- equivalent type. Should this be done earlier when the
5756 -- completion is analyzed ???
5758 if Is_Private_Type (Etype (Unc_Typ))
5759 and then
5760 Ekind (Full_View (Etype (Unc_Typ))) = E_Record_Subtype
5761 then
5762 Set_Etype (Unc_Typ, Base_Type (Full_View (Etype (Unc_Typ))));
5763 end if;
5765 EQ_Typ := Make_CW_Equivalent_Type (Unc_Typ, E);
5766 end if;
5768 CW_Subtype := New_Class_Wide_Subtype (Unc_Typ, E);
5769 Set_Equivalent_Type (CW_Subtype, EQ_Typ);
5770 Set_Cloned_Subtype (CW_Subtype, Base_Type (Unc_Typ));
5772 return New_Occurrence_Of (CW_Subtype, Loc);
5773 end;
5775 -- Indefinite record type with discriminants
5777 else
5778 D := First_Discriminant (Unc_Typ);
5779 while Present (D) loop
5780 Append_To (List_Constr,
5781 Make_Selected_Component (Loc,
5782 Prefix => Duplicate_Subexpr_No_Checks (E),
5783 Selector_Name => New_Reference_To (D, Loc)));
5785 Next_Discriminant (D);
5786 end loop;
5787 end if;
5789 return
5790 Make_Subtype_Indication (Loc,
5791 Subtype_Mark => New_Reference_To (Unc_Typ, Loc),
5792 Constraint =>
5793 Make_Index_Or_Discriminant_Constraint (Loc,
5794 Constraints => List_Constr));
5795 end Make_Subtype_From_Expr;
5797 -----------------------------
5798 -- May_Generate_Large_Temp --
5799 -----------------------------
5801 -- At the current time, the only types that we return False for (i.e. where
5802 -- we decide we know they cannot generate large temps) are ones where we
5803 -- know the size is 256 bits or less at compile time, and we are still not
5804 -- doing a thorough job on arrays and records ???
5806 function May_Generate_Large_Temp (Typ : Entity_Id) return Boolean is
5807 begin
5808 if not Size_Known_At_Compile_Time (Typ) then
5809 return False;
5811 elsif Esize (Typ) /= 0 and then Esize (Typ) <= 256 then
5812 return False;
5814 elsif Is_Array_Type (Typ)
5815 and then Present (Packed_Array_Type (Typ))
5816 then
5817 return May_Generate_Large_Temp (Packed_Array_Type (Typ));
5819 -- We could do more here to find other small types ???
5821 else
5822 return True;
5823 end if;
5824 end May_Generate_Large_Temp;
5826 ------------------------
5827 -- Needs_Finalization --
5828 ------------------------
5830 function Needs_Finalization (T : Entity_Id) return Boolean is
5831 function Has_Some_Controlled_Component (Rec : Entity_Id) return Boolean;
5832 -- If type is not frozen yet, check explicitly among its components,
5833 -- because the Has_Controlled_Component flag is not necessarily set.
5835 -----------------------------------
5836 -- Has_Some_Controlled_Component --
5837 -----------------------------------
5839 function Has_Some_Controlled_Component
5840 (Rec : Entity_Id) return Boolean
5842 Comp : Entity_Id;
5844 begin
5845 if Has_Controlled_Component (Rec) then
5846 return True;
5848 elsif not Is_Frozen (Rec) then
5849 if Is_Record_Type (Rec) then
5850 Comp := First_Entity (Rec);
5852 while Present (Comp) loop
5853 if not Is_Type (Comp)
5854 and then Needs_Finalization (Etype (Comp))
5855 then
5856 return True;
5857 end if;
5859 Next_Entity (Comp);
5860 end loop;
5862 return False;
5864 elsif Is_Array_Type (Rec) then
5865 return Needs_Finalization (Component_Type (Rec));
5867 else
5868 return Has_Controlled_Component (Rec);
5869 end if;
5870 else
5871 return False;
5872 end if;
5873 end Has_Some_Controlled_Component;
5875 -- Start of processing for Needs_Finalization
5877 begin
5878 -- Certain run-time configurations and targets do not provide support
5879 -- for controlled types.
5881 if Restriction_Active (No_Finalization) then
5882 return False;
5884 -- C, C++, CIL and Java types are not considered controlled. It is
5885 -- assumed that the non-Ada side will handle their clean up.
5887 elsif Convention (T) = Convention_C
5888 or else Convention (T) = Convention_CIL
5889 or else Convention (T) = Convention_CPP
5890 or else Convention (T) = Convention_Java
5891 then
5892 return False;
5894 else
5895 -- Class-wide types are treated as controlled because derivations
5896 -- from the root type can introduce controlled components.
5898 return
5899 Is_Class_Wide_Type (T)
5900 or else Is_Controlled (T)
5901 or else Has_Controlled_Component (T)
5902 or else Has_Some_Controlled_Component (T)
5903 or else
5904 (Is_Concurrent_Type (T)
5905 and then Present (Corresponding_Record_Type (T))
5906 and then Needs_Finalization (Corresponding_Record_Type (T)));
5907 end if;
5908 end Needs_Finalization;
5910 ----------------------------
5911 -- Needs_Constant_Address --
5912 ----------------------------
5914 function Needs_Constant_Address
5915 (Decl : Node_Id;
5916 Typ : Entity_Id) return Boolean
5918 begin
5920 -- If we have no initialization of any kind, then we don't need to place
5921 -- any restrictions on the address clause, because the object will be
5922 -- elaborated after the address clause is evaluated. This happens if the
5923 -- declaration has no initial expression, or the type has no implicit
5924 -- initialization, or the object is imported.
5926 -- The same holds for all initialized scalar types and all access types.
5927 -- Packed bit arrays of size up to 64 are represented using a modular
5928 -- type with an initialization (to zero) and can be processed like other
5929 -- initialized scalar types.
5931 -- If the type is controlled, code to attach the object to a
5932 -- finalization chain is generated at the point of declaration, and
5933 -- therefore the elaboration of the object cannot be delayed: the
5934 -- address expression must be a constant.
5936 if No (Expression (Decl))
5937 and then not Needs_Finalization (Typ)
5938 and then
5939 (not Has_Non_Null_Base_Init_Proc (Typ)
5940 or else Is_Imported (Defining_Identifier (Decl)))
5941 then
5942 return False;
5944 elsif (Present (Expression (Decl)) and then Is_Scalar_Type (Typ))
5945 or else Is_Access_Type (Typ)
5946 or else
5947 (Is_Bit_Packed_Array (Typ)
5948 and then Is_Modular_Integer_Type (Packed_Array_Type (Typ)))
5949 then
5950 return False;
5952 else
5954 -- Otherwise, we require the address clause to be constant because
5955 -- the call to the initialization procedure (or the attach code) has
5956 -- to happen at the point of the declaration.
5958 -- Actually the IP call has been moved to the freeze actions anyway,
5959 -- so maybe we can relax this restriction???
5961 return True;
5962 end if;
5963 end Needs_Constant_Address;
5965 ----------------------------
5966 -- New_Class_Wide_Subtype --
5967 ----------------------------
5969 function New_Class_Wide_Subtype
5970 (CW_Typ : Entity_Id;
5971 N : Node_Id) return Entity_Id
5973 Res : constant Entity_Id := Create_Itype (E_Void, N);
5974 Res_Name : constant Name_Id := Chars (Res);
5975 Res_Scope : constant Entity_Id := Scope (Res);
5977 begin
5978 Copy_Node (CW_Typ, Res);
5979 Set_Comes_From_Source (Res, False);
5980 Set_Sloc (Res, Sloc (N));
5981 Set_Is_Itype (Res);
5982 Set_Associated_Node_For_Itype (Res, N);
5983 Set_Is_Public (Res, False); -- By default, may be changed below.
5984 Set_Public_Status (Res);
5985 Set_Chars (Res, Res_Name);
5986 Set_Scope (Res, Res_Scope);
5987 Set_Ekind (Res, E_Class_Wide_Subtype);
5988 Set_Next_Entity (Res, Empty);
5989 Set_Etype (Res, Base_Type (CW_Typ));
5990 Set_Is_Frozen (Res, False);
5991 Set_Freeze_Node (Res, Empty);
5992 return (Res);
5993 end New_Class_Wide_Subtype;
5995 --------------------------------
5996 -- Non_Limited_Designated_Type --
5997 ---------------------------------
5999 function Non_Limited_Designated_Type (T : Entity_Id) return Entity_Id is
6000 Desig : constant Entity_Id := Designated_Type (T);
6001 begin
6002 if Ekind (Desig) = E_Incomplete_Type
6003 and then Present (Non_Limited_View (Desig))
6004 then
6005 return Non_Limited_View (Desig);
6006 else
6007 return Desig;
6008 end if;
6009 end Non_Limited_Designated_Type;
6011 -----------------------------------
6012 -- OK_To_Do_Constant_Replacement --
6013 -----------------------------------
6015 function OK_To_Do_Constant_Replacement (E : Entity_Id) return Boolean is
6016 ES : constant Entity_Id := Scope (E);
6017 CS : Entity_Id;
6019 begin
6020 -- Do not replace statically allocated objects, because they may be
6021 -- modified outside the current scope.
6023 if Is_Statically_Allocated (E) then
6024 return False;
6026 -- Do not replace aliased or volatile objects, since we don't know what
6027 -- else might change the value.
6029 elsif Is_Aliased (E) or else Treat_As_Volatile (E) then
6030 return False;
6032 -- Debug flag -gnatdM disconnects this optimization
6034 elsif Debug_Flag_MM then
6035 return False;
6037 -- Otherwise check scopes
6039 else
6040 CS := Current_Scope;
6042 loop
6043 -- If we are in right scope, replacement is safe
6045 if CS = ES then
6046 return True;
6048 -- Packages do not affect the determination of safety
6050 elsif Ekind (CS) = E_Package then
6051 exit when CS = Standard_Standard;
6052 CS := Scope (CS);
6054 -- Blocks do not affect the determination of safety
6056 elsif Ekind (CS) = E_Block then
6057 CS := Scope (CS);
6059 -- Loops do not affect the determination of safety. Note that we
6060 -- kill all current values on entry to a loop, so we are just
6061 -- talking about processing within a loop here.
6063 elsif Ekind (CS) = E_Loop then
6064 CS := Scope (CS);
6066 -- Otherwise, the reference is dubious, and we cannot be sure that
6067 -- it is safe to do the replacement.
6069 else
6070 exit;
6071 end if;
6072 end loop;
6074 return False;
6075 end if;
6076 end OK_To_Do_Constant_Replacement;
6078 ------------------------------------
6079 -- Possible_Bit_Aligned_Component --
6080 ------------------------------------
6082 function Possible_Bit_Aligned_Component (N : Node_Id) return Boolean is
6083 begin
6084 case Nkind (N) is
6086 -- Case of indexed component
6088 when N_Indexed_Component =>
6089 declare
6090 P : constant Node_Id := Prefix (N);
6091 Ptyp : constant Entity_Id := Etype (P);
6093 begin
6094 -- If we know the component size and it is less than 64, then
6095 -- we are definitely OK. The back end always does assignment of
6096 -- misaligned small objects correctly.
6098 if Known_Static_Component_Size (Ptyp)
6099 and then Component_Size (Ptyp) <= 64
6100 then
6101 return False;
6103 -- Otherwise, we need to test the prefix, to see if we are
6104 -- indexing from a possibly unaligned component.
6106 else
6107 return Possible_Bit_Aligned_Component (P);
6108 end if;
6109 end;
6111 -- Case of selected component
6113 when N_Selected_Component =>
6114 declare
6115 P : constant Node_Id := Prefix (N);
6116 Comp : constant Entity_Id := Entity (Selector_Name (N));
6118 begin
6119 -- If there is no component clause, then we are in the clear
6120 -- since the back end will never misalign a large component
6121 -- unless it is forced to do so. In the clear means we need
6122 -- only the recursive test on the prefix.
6124 if Component_May_Be_Bit_Aligned (Comp) then
6125 return True;
6126 else
6127 return Possible_Bit_Aligned_Component (P);
6128 end if;
6129 end;
6131 -- For a slice, test the prefix, if that is possibly misaligned,
6132 -- then for sure the slice is!
6134 when N_Slice =>
6135 return Possible_Bit_Aligned_Component (Prefix (N));
6137 -- For an unchecked conversion, check whether the expression may
6138 -- be bit-aligned.
6140 when N_Unchecked_Type_Conversion =>
6141 return Possible_Bit_Aligned_Component (Expression (N));
6143 -- If we have none of the above, it means that we have fallen off the
6144 -- top testing prefixes recursively, and we now have a stand alone
6145 -- object, where we don't have a problem.
6147 when others =>
6148 return False;
6150 end case;
6151 end Possible_Bit_Aligned_Component;
6153 -----------------------------------------------
6154 -- Process_Statements_For_Controlled_Objects --
6155 -----------------------------------------------
6157 procedure Process_Statements_For_Controlled_Objects (N : Node_Id) is
6158 Loc : constant Source_Ptr := Sloc (N);
6160 function Are_Wrapped (L : List_Id) return Boolean;
6161 -- Determine whether list L contains only one statement which is a block
6163 function Wrap_Statements_In_Block (L : List_Id) return Node_Id;
6164 -- Given a list of statements L, wrap it in a block statement and return
6165 -- the generated node.
6167 -----------------
6168 -- Are_Wrapped --
6169 -----------------
6171 function Are_Wrapped (L : List_Id) return Boolean is
6172 Stmt : constant Node_Id := First (L);
6173 begin
6174 return
6175 Present (Stmt)
6176 and then No (Next (Stmt))
6177 and then Nkind (Stmt) = N_Block_Statement;
6178 end Are_Wrapped;
6180 ------------------------------
6181 -- Wrap_Statements_In_Block --
6182 ------------------------------
6184 function Wrap_Statements_In_Block (L : List_Id) return Node_Id is
6185 begin
6186 return
6187 Make_Block_Statement (Loc,
6188 Declarations => No_List,
6189 Handled_Statement_Sequence =>
6190 Make_Handled_Sequence_Of_Statements (Loc,
6191 Statements => L));
6192 end Wrap_Statements_In_Block;
6194 -- Local variables
6196 Block : Node_Id;
6198 -- Start of processing for Process_Statements_For_Controlled_Objects
6200 begin
6201 -- Whenever a non-handled statement list is wrapped in a block, the
6202 -- block must be explicitly analyzed to redecorate all entities in the
6203 -- list and ensure that a finalizer is properly built.
6205 case Nkind (N) is
6206 when N_Elsif_Part |
6207 N_If_Statement |
6208 N_Conditional_Entry_Call |
6209 N_Selective_Accept =>
6211 -- Check the "then statements" for elsif parts and if statements
6213 if Nkind_In (N, N_Elsif_Part, N_If_Statement)
6214 and then not Is_Empty_List (Then_Statements (N))
6215 and then not Are_Wrapped (Then_Statements (N))
6216 and then Requires_Cleanup_Actions
6217 (Then_Statements (N), False, False)
6218 then
6219 Block := Wrap_Statements_In_Block (Then_Statements (N));
6220 Set_Then_Statements (N, New_List (Block));
6222 Analyze (Block);
6223 end if;
6225 -- Check the "else statements" for conditional entry calls, if
6226 -- statements and selective accepts.
6228 if Nkind_In (N, N_Conditional_Entry_Call,
6229 N_If_Statement,
6230 N_Selective_Accept)
6231 and then not Is_Empty_List (Else_Statements (N))
6232 and then not Are_Wrapped (Else_Statements (N))
6233 and then Requires_Cleanup_Actions
6234 (Else_Statements (N), False, False)
6235 then
6236 Block := Wrap_Statements_In_Block (Else_Statements (N));
6237 Set_Else_Statements (N, New_List (Block));
6239 Analyze (Block);
6240 end if;
6242 when N_Abortable_Part |
6243 N_Accept_Alternative |
6244 N_Case_Statement_Alternative |
6245 N_Delay_Alternative |
6246 N_Entry_Call_Alternative |
6247 N_Exception_Handler |
6248 N_Loop_Statement |
6249 N_Triggering_Alternative =>
6251 if not Is_Empty_List (Statements (N))
6252 and then not Are_Wrapped (Statements (N))
6253 and then Requires_Cleanup_Actions (Statements (N), False, False)
6254 then
6255 Block := Wrap_Statements_In_Block (Statements (N));
6256 Set_Statements (N, New_List (Block));
6258 Analyze (Block);
6259 end if;
6261 when others =>
6262 null;
6263 end case;
6264 end Process_Statements_For_Controlled_Objects;
6266 -------------------------
6267 -- Remove_Side_Effects --
6268 -------------------------
6270 procedure Remove_Side_Effects
6271 (Exp : Node_Id;
6272 Name_Req : Boolean := False;
6273 Variable_Ref : Boolean := False)
6275 Loc : constant Source_Ptr := Sloc (Exp);
6276 Exp_Type : constant Entity_Id := Etype (Exp);
6277 Svg_Suppress : constant Suppress_Record := Scope_Suppress;
6278 Def_Id : Entity_Id;
6279 E : Node_Id;
6280 New_Exp : Node_Id;
6281 Ptr_Typ_Decl : Node_Id;
6282 Ref_Type : Entity_Id;
6283 Res : Node_Id;
6285 function Side_Effect_Free (N : Node_Id) return Boolean;
6286 -- Determines if the tree N represents an expression that is known not
6287 -- to have side effects, and for which no processing is required.
6289 function Side_Effect_Free (L : List_Id) return Boolean;
6290 -- Determines if all elements of the list L are side effect free
6292 function Safe_Prefixed_Reference (N : Node_Id) return Boolean;
6293 -- The argument N is a construct where the Prefix is dereferenced if it
6294 -- is an access type and the result is a variable. The call returns True
6295 -- if the construct is side effect free (not considering side effects in
6296 -- other than the prefix which are to be tested by the caller).
6298 function Within_In_Parameter (N : Node_Id) return Boolean;
6299 -- Determines if N is a subcomponent of a composite in-parameter. If so,
6300 -- N is not side-effect free when the actual is global and modifiable
6301 -- indirectly from within a subprogram, because it may be passed by
6302 -- reference. The front-end must be conservative here and assume that
6303 -- this may happen with any array or record type. On the other hand, we
6304 -- cannot create temporaries for all expressions for which this
6305 -- condition is true, for various reasons that might require clearing up
6306 -- ??? For example, discriminant references that appear out of place, or
6307 -- spurious type errors with class-wide expressions. As a result, we
6308 -- limit the transformation to loop bounds, which is so far the only
6309 -- case that requires it.
6311 -----------------------------
6312 -- Safe_Prefixed_Reference --
6313 -----------------------------
6315 function Safe_Prefixed_Reference (N : Node_Id) return Boolean is
6316 begin
6317 -- If prefix is not side effect free, definitely not safe
6319 if not Side_Effect_Free (Prefix (N)) then
6320 return False;
6322 -- If the prefix is of an access type that is not access-to-constant,
6323 -- then this construct is a variable reference, which means it is to
6324 -- be considered to have side effects if Variable_Ref is set True.
6326 elsif Is_Access_Type (Etype (Prefix (N)))
6327 and then not Is_Access_Constant (Etype (Prefix (N)))
6328 and then Variable_Ref
6329 then
6330 -- Exception is a prefix that is the result of a previous removal
6331 -- of side-effects.
6333 return Is_Entity_Name (Prefix (N))
6334 and then not Comes_From_Source (Prefix (N))
6335 and then Ekind (Entity (Prefix (N))) = E_Constant
6336 and then Is_Internal_Name (Chars (Entity (Prefix (N))));
6338 -- If the prefix is an explicit dereference then this construct is a
6339 -- variable reference, which means it is to be considered to have
6340 -- side effects if Variable_Ref is True.
6342 -- We do NOT exclude dereferences of access-to-constant types because
6343 -- we handle them as constant view of variables.
6345 elsif Nkind (Prefix (N)) = N_Explicit_Dereference
6346 and then Variable_Ref
6347 then
6348 return False;
6350 -- Note: The following test is the simplest way of solving a complex
6351 -- problem uncovered by the following test (Side effect on loop bound
6352 -- that is a subcomponent of a global variable:
6354 -- with Text_Io; use Text_Io;
6355 -- procedure Tloop is
6356 -- type X is
6357 -- record
6358 -- V : Natural := 4;
6359 -- S : String (1..5) := (others => 'a');
6360 -- end record;
6361 -- X1 : X;
6363 -- procedure Modi;
6365 -- generic
6366 -- with procedure Action;
6367 -- procedure Loop_G (Arg : X; Msg : String)
6369 -- procedure Loop_G (Arg : X; Msg : String) is
6370 -- begin
6371 -- Put_Line ("begin loop_g " & Msg & " will loop till: "
6372 -- & Natural'Image (Arg.V));
6373 -- for Index in 1 .. Arg.V loop
6374 -- Text_Io.Put_Line
6375 -- (Natural'Image (Index) & " " & Arg.S (Index));
6376 -- if Index > 2 then
6377 -- Modi;
6378 -- end if;
6379 -- end loop;
6380 -- Put_Line ("end loop_g " & Msg);
6381 -- end;
6383 -- procedure Loop1 is new Loop_G (Modi);
6384 -- procedure Modi is
6385 -- begin
6386 -- X1.V := 1;
6387 -- Loop1 (X1, "from modi");
6388 -- end;
6390 -- begin
6391 -- Loop1 (X1, "initial");
6392 -- end;
6394 -- The output of the above program should be:
6396 -- begin loop_g initial will loop till: 4
6397 -- 1 a
6398 -- 2 a
6399 -- 3 a
6400 -- begin loop_g from modi will loop till: 1
6401 -- 1 a
6402 -- end loop_g from modi
6403 -- 4 a
6404 -- begin loop_g from modi will loop till: 1
6405 -- 1 a
6406 -- end loop_g from modi
6407 -- end loop_g initial
6409 -- If a loop bound is a subcomponent of a global variable, a
6410 -- modification of that variable within the loop may incorrectly
6411 -- affect the execution of the loop.
6413 elsif Nkind (Parent (Parent (N))) = N_Loop_Parameter_Specification
6414 and then Within_In_Parameter (Prefix (N))
6415 and then Variable_Ref
6416 then
6417 return False;
6419 -- All other cases are side effect free
6421 else
6422 return True;
6423 end if;
6424 end Safe_Prefixed_Reference;
6426 ----------------------
6427 -- Side_Effect_Free --
6428 ----------------------
6430 function Side_Effect_Free (N : Node_Id) return Boolean is
6431 begin
6432 -- Note on checks that could raise Constraint_Error. Strictly, if we
6433 -- take advantage of 11.6, these checks do not count as side effects.
6434 -- However, we would prefer to consider that they are side effects,
6435 -- since the backend CSE does not work very well on expressions which
6436 -- can raise Constraint_Error. On the other hand if we don't consider
6437 -- them to be side effect free, then we get some awkward expansions
6438 -- in -gnato mode, resulting in code insertions at a point where we
6439 -- do not have a clear model for performing the insertions.
6441 -- Special handling for entity names
6443 if Is_Entity_Name (N) then
6445 -- Variables are considered to be a side effect if Variable_Ref
6446 -- is set or if we have a volatile reference and Name_Req is off.
6447 -- If Name_Req is True then we can't help returning a name which
6448 -- effectively allows multiple references in any case.
6450 if Is_Variable (N, Use_Original_Node => False) then
6451 return not Variable_Ref
6452 and then (not Is_Volatile_Reference (N) or else Name_Req);
6454 -- Any other entity (e.g. a subtype name) is definitely side
6455 -- effect free.
6457 else
6458 return True;
6459 end if;
6461 -- A value known at compile time is always side effect free
6463 elsif Compile_Time_Known_Value (N) then
6464 return True;
6466 -- A variable renaming is not side-effect free, because the renaming
6467 -- will function like a macro in the front-end in some cases, and an
6468 -- assignment can modify the component designated by N, so we need to
6469 -- create a temporary for it.
6471 -- The guard testing for Entity being present is needed at least in
6472 -- the case of rewritten predicate expressions, and may well also be
6473 -- appropriate elsewhere. Obviously we can't go testing the entity
6474 -- field if it does not exist, so it's reasonable to say that this is
6475 -- not the renaming case if it does not exist.
6477 elsif Is_Entity_Name (Original_Node (N))
6478 and then Present (Entity (Original_Node (N)))
6479 and then Is_Renaming_Of_Object (Entity (Original_Node (N)))
6480 and then Ekind (Entity (Original_Node (N))) /= E_Constant
6481 then
6482 return False;
6484 -- Remove_Side_Effects generates an object renaming declaration to
6485 -- capture the expression of a class-wide expression. In VM targets
6486 -- the frontend performs no expansion for dispatching calls to
6487 -- class- wide types since they are handled by the VM. Hence, we must
6488 -- locate here if this node corresponds to a previous invocation of
6489 -- Remove_Side_Effects to avoid a never ending loop in the frontend.
6491 elsif VM_Target /= No_VM
6492 and then not Comes_From_Source (N)
6493 and then Nkind (Parent (N)) = N_Object_Renaming_Declaration
6494 and then Is_Class_Wide_Type (Etype (N))
6495 then
6496 return True;
6497 end if;
6499 -- For other than entity names and compile time known values,
6500 -- check the node kind for special processing.
6502 case Nkind (N) is
6504 -- An attribute reference is side effect free if its expressions
6505 -- are side effect free and its prefix is side effect free or
6506 -- is an entity reference.
6508 -- Is this right? what about x'first where x is a variable???
6510 when N_Attribute_Reference =>
6511 return Side_Effect_Free (Expressions (N))
6512 and then Attribute_Name (N) /= Name_Input
6513 and then (Is_Entity_Name (Prefix (N))
6514 or else Side_Effect_Free (Prefix (N)));
6516 -- A binary operator is side effect free if and both operands are
6517 -- side effect free. For this purpose binary operators include
6518 -- membership tests and short circuit forms.
6520 when N_Binary_Op | N_Membership_Test | N_Short_Circuit =>
6521 return Side_Effect_Free (Left_Opnd (N))
6522 and then
6523 Side_Effect_Free (Right_Opnd (N));
6525 -- An explicit dereference is side effect free only if it is
6526 -- a side effect free prefixed reference.
6528 when N_Explicit_Dereference =>
6529 return Safe_Prefixed_Reference (N);
6531 -- A call to _rep_to_pos is side effect free, since we generate
6532 -- this pure function call ourselves. Moreover it is critically
6533 -- important to make this exception, since otherwise we can have
6534 -- discriminants in array components which don't look side effect
6535 -- free in the case of an array whose index type is an enumeration
6536 -- type with an enumeration rep clause.
6538 -- All other function calls are not side effect free
6540 when N_Function_Call =>
6541 return Nkind (Name (N)) = N_Identifier
6542 and then Is_TSS (Name (N), TSS_Rep_To_Pos)
6543 and then
6544 Side_Effect_Free (First (Parameter_Associations (N)));
6546 -- An indexed component is side effect free if it is a side
6547 -- effect free prefixed reference and all the indexing
6548 -- expressions are side effect free.
6550 when N_Indexed_Component =>
6551 return Side_Effect_Free (Expressions (N))
6552 and then Safe_Prefixed_Reference (N);
6554 -- A type qualification is side effect free if the expression
6555 -- is side effect free.
6557 when N_Qualified_Expression =>
6558 return Side_Effect_Free (Expression (N));
6560 -- A selected component is side effect free only if it is a side
6561 -- effect free prefixed reference. If it designates a component
6562 -- with a rep. clause it must be treated has having a potential
6563 -- side effect, because it may be modified through a renaming, and
6564 -- a subsequent use of the renaming as a macro will yield the
6565 -- wrong value. This complex interaction between renaming and
6566 -- removing side effects is a reminder that the latter has become
6567 -- a headache to maintain, and that it should be removed in favor
6568 -- of the gcc mechanism to capture values ???
6570 when N_Selected_Component =>
6571 if Nkind (Parent (N)) = N_Explicit_Dereference
6572 and then Has_Non_Standard_Rep (Designated_Type (Etype (N)))
6573 then
6574 return False;
6575 else
6576 return Safe_Prefixed_Reference (N);
6577 end if;
6579 -- A range is side effect free if the bounds are side effect free
6581 when N_Range =>
6582 return Side_Effect_Free (Low_Bound (N))
6583 and then Side_Effect_Free (High_Bound (N));
6585 -- A slice is side effect free if it is a side effect free
6586 -- prefixed reference and the bounds are side effect free.
6588 when N_Slice =>
6589 return Side_Effect_Free (Discrete_Range (N))
6590 and then Safe_Prefixed_Reference (N);
6592 -- A type conversion is side effect free if the expression to be
6593 -- converted is side effect free.
6595 when N_Type_Conversion =>
6596 return Side_Effect_Free (Expression (N));
6598 -- A unary operator is side effect free if the operand
6599 -- is side effect free.
6601 when N_Unary_Op =>
6602 return Side_Effect_Free (Right_Opnd (N));
6604 -- An unchecked type conversion is side effect free only if it
6605 -- is safe and its argument is side effect free.
6607 when N_Unchecked_Type_Conversion =>
6608 return Safe_Unchecked_Type_Conversion (N)
6609 and then Side_Effect_Free (Expression (N));
6611 -- An unchecked expression is side effect free if its expression
6612 -- is side effect free.
6614 when N_Unchecked_Expression =>
6615 return Side_Effect_Free (Expression (N));
6617 -- A literal is side effect free
6619 when N_Character_Literal |
6620 N_Integer_Literal |
6621 N_Real_Literal |
6622 N_String_Literal =>
6623 return True;
6625 -- We consider that anything else has side effects. This is a bit
6626 -- crude, but we are pretty close for most common cases, and we
6627 -- are certainly correct (i.e. we never return True when the
6628 -- answer should be False).
6630 when others =>
6631 return False;
6632 end case;
6633 end Side_Effect_Free;
6635 -- A list is side effect free if all elements of the list are side
6636 -- effect free.
6638 function Side_Effect_Free (L : List_Id) return Boolean is
6639 N : Node_Id;
6641 begin
6642 if L = No_List or else L = Error_List then
6643 return True;
6645 else
6646 N := First (L);
6647 while Present (N) loop
6648 if not Side_Effect_Free (N) then
6649 return False;
6650 else
6651 Next (N);
6652 end if;
6653 end loop;
6655 return True;
6656 end if;
6657 end Side_Effect_Free;
6659 -------------------------
6660 -- Within_In_Parameter --
6661 -------------------------
6663 function Within_In_Parameter (N : Node_Id) return Boolean is
6664 begin
6665 if not Comes_From_Source (N) then
6666 return False;
6668 elsif Is_Entity_Name (N) then
6669 return Ekind (Entity (N)) = E_In_Parameter;
6671 elsif Nkind (N) = N_Indexed_Component
6672 or else Nkind (N) = N_Selected_Component
6673 then
6674 return Within_In_Parameter (Prefix (N));
6675 else
6677 return False;
6678 end if;
6679 end Within_In_Parameter;
6681 -- Start of processing for Remove_Side_Effects
6683 begin
6684 -- Handle cases in which there is nothing to do
6686 if not Expander_Active then
6687 return;
6688 end if;
6690 -- Cannot generate temporaries if the invocation to remove side effects
6691 -- was issued too early and the type of the expression is not resolved
6692 -- (this happens because routines Duplicate_Subexpr_XX implicitly invoke
6693 -- Remove_Side_Effects).
6695 if No (Exp_Type)
6696 or else Ekind (Exp_Type) = E_Access_Attribute_Type
6697 then
6698 return;
6700 -- No action needed for side-effect free expressions
6702 elsif Side_Effect_Free (Exp) then
6703 return;
6704 end if;
6706 -- All this must not have any checks
6708 Scope_Suppress := Suppress_All;
6710 -- If it is a scalar type and we need to capture the value, just make
6711 -- a copy. Likewise for a function call, an attribute reference, an
6712 -- allocator, or an operator. And if we have a volatile reference and
6713 -- Name_Req is not set (see comments above for Side_Effect_Free).
6715 if Is_Elementary_Type (Exp_Type)
6716 and then (Variable_Ref
6717 or else Nkind (Exp) = N_Function_Call
6718 or else Nkind (Exp) = N_Attribute_Reference
6719 or else Nkind (Exp) = N_Allocator
6720 or else Nkind (Exp) in N_Op
6721 or else (not Name_Req and then Is_Volatile_Reference (Exp)))
6722 then
6723 Def_Id := Make_Temporary (Loc, 'R', Exp);
6724 Set_Etype (Def_Id, Exp_Type);
6725 Res := New_Reference_To (Def_Id, Loc);
6727 -- If the expression is a packed reference, it must be reanalyzed and
6728 -- expanded, depending on context. This is the case for actuals where
6729 -- a constraint check may capture the actual before expansion of the
6730 -- call is complete.
6732 if Nkind (Exp) = N_Indexed_Component
6733 and then Is_Packed (Etype (Prefix (Exp)))
6734 then
6735 Set_Analyzed (Exp, False);
6736 Set_Analyzed (Prefix (Exp), False);
6737 end if;
6739 E :=
6740 Make_Object_Declaration (Loc,
6741 Defining_Identifier => Def_Id,
6742 Object_Definition => New_Reference_To (Exp_Type, Loc),
6743 Constant_Present => True,
6744 Expression => Relocate_Node (Exp));
6746 Set_Assignment_OK (E);
6747 Insert_Action (Exp, E);
6749 -- If the expression has the form v.all then we can just capture the
6750 -- pointer, and then do an explicit dereference on the result.
6752 elsif Nkind (Exp) = N_Explicit_Dereference then
6753 Def_Id := Make_Temporary (Loc, 'R', Exp);
6754 Res :=
6755 Make_Explicit_Dereference (Loc, New_Reference_To (Def_Id, Loc));
6757 Insert_Action (Exp,
6758 Make_Object_Declaration (Loc,
6759 Defining_Identifier => Def_Id,
6760 Object_Definition =>
6761 New_Reference_To (Etype (Prefix (Exp)), Loc),
6762 Constant_Present => True,
6763 Expression => Relocate_Node (Prefix (Exp))));
6765 -- Similar processing for an unchecked conversion of an expression of
6766 -- the form v.all, where we want the same kind of treatment.
6768 elsif Nkind (Exp) = N_Unchecked_Type_Conversion
6769 and then Nkind (Expression (Exp)) = N_Explicit_Dereference
6770 then
6771 Remove_Side_Effects (Expression (Exp), Name_Req, Variable_Ref);
6772 Scope_Suppress := Svg_Suppress;
6773 return;
6775 -- If this is a type conversion, leave the type conversion and remove
6776 -- the side effects in the expression. This is important in several
6777 -- circumstances: for change of representations, and also when this is a
6778 -- view conversion to a smaller object, where gigi can end up creating
6779 -- its own temporary of the wrong size.
6781 elsif Nkind (Exp) = N_Type_Conversion then
6782 Remove_Side_Effects (Expression (Exp), Name_Req, Variable_Ref);
6783 Scope_Suppress := Svg_Suppress;
6784 return;
6786 -- If this is an unchecked conversion that Gigi can't handle, make
6787 -- a copy or a use a renaming to capture the value.
6789 elsif Nkind (Exp) = N_Unchecked_Type_Conversion
6790 and then not Safe_Unchecked_Type_Conversion (Exp)
6791 then
6792 if CW_Or_Has_Controlled_Part (Exp_Type) then
6794 -- Use a renaming to capture the expression, rather than create
6795 -- a controlled temporary.
6797 Def_Id := Make_Temporary (Loc, 'R', Exp);
6798 Res := New_Reference_To (Def_Id, Loc);
6800 Insert_Action (Exp,
6801 Make_Object_Renaming_Declaration (Loc,
6802 Defining_Identifier => Def_Id,
6803 Subtype_Mark => New_Reference_To (Exp_Type, Loc),
6804 Name => Relocate_Node (Exp)));
6806 else
6807 Def_Id := Make_Temporary (Loc, 'R', Exp);
6808 Set_Etype (Def_Id, Exp_Type);
6809 Res := New_Reference_To (Def_Id, Loc);
6811 E :=
6812 Make_Object_Declaration (Loc,
6813 Defining_Identifier => Def_Id,
6814 Object_Definition => New_Reference_To (Exp_Type, Loc),
6815 Constant_Present => not Is_Variable (Exp),
6816 Expression => Relocate_Node (Exp));
6818 Set_Assignment_OK (E);
6819 Insert_Action (Exp, E);
6820 end if;
6822 -- For expressions that denote objects, we can use a renaming scheme.
6823 -- This is needed for correctness in the case of a volatile object of a
6824 -- non-volatile type because the Make_Reference call of the "default"
6825 -- approach would generate an illegal access value (an access value
6826 -- cannot designate such an object - see Analyze_Reference). We skip
6827 -- using this scheme if we have an object of a volatile type and we do
6828 -- not have Name_Req set true (see comments above for Side_Effect_Free).
6830 elsif Is_Object_Reference (Exp)
6831 and then Nkind (Exp) /= N_Function_Call
6832 and then (Name_Req or else not Treat_As_Volatile (Exp_Type))
6833 then
6834 Def_Id := Make_Temporary (Loc, 'R', Exp);
6836 if Nkind (Exp) = N_Selected_Component
6837 and then Nkind (Prefix (Exp)) = N_Function_Call
6838 and then Is_Array_Type (Exp_Type)
6839 then
6840 -- Avoid generating a variable-sized temporary, by generating
6841 -- the renaming declaration just for the function call. The
6842 -- transformation could be refined to apply only when the array
6843 -- component is constrained by a discriminant???
6845 Res :=
6846 Make_Selected_Component (Loc,
6847 Prefix => New_Occurrence_Of (Def_Id, Loc),
6848 Selector_Name => Selector_Name (Exp));
6850 Insert_Action (Exp,
6851 Make_Object_Renaming_Declaration (Loc,
6852 Defining_Identifier => Def_Id,
6853 Subtype_Mark =>
6854 New_Reference_To (Base_Type (Etype (Prefix (Exp))), Loc),
6855 Name => Relocate_Node (Prefix (Exp))));
6857 else
6858 Res := New_Reference_To (Def_Id, Loc);
6860 Insert_Action (Exp,
6861 Make_Object_Renaming_Declaration (Loc,
6862 Defining_Identifier => Def_Id,
6863 Subtype_Mark => New_Reference_To (Exp_Type, Loc),
6864 Name => Relocate_Node (Exp)));
6865 end if;
6867 -- If this is a packed reference, or a selected component with
6868 -- a non-standard representation, a reference to the temporary
6869 -- will be replaced by a copy of the original expression (see
6870 -- Exp_Ch2.Expand_Renaming). Otherwise the temporary must be
6871 -- elaborated by gigi, and is of course not to be replaced in-line
6872 -- by the expression it renames, which would defeat the purpose of
6873 -- removing the side-effect.
6875 if (Nkind (Exp) = N_Selected_Component
6876 or else Nkind (Exp) = N_Indexed_Component)
6877 and then Has_Non_Standard_Rep (Etype (Prefix (Exp)))
6878 then
6879 null;
6880 else
6881 Set_Is_Renaming_Of_Object (Def_Id, False);
6882 end if;
6884 -- Otherwise we generate a reference to the value
6886 else
6887 -- An expression which is in Alfa mode is considered side effect free
6888 -- if the resulting value is captured by a variable or a constant.
6890 if Alfa_Mode
6891 and then Nkind (Parent (Exp)) = N_Object_Declaration
6892 then
6893 return;
6894 end if;
6896 -- Special processing for function calls that return a limited type.
6897 -- We need to build a declaration that will enable build-in-place
6898 -- expansion of the call. This is not done if the context is already
6899 -- an object declaration, to prevent infinite recursion.
6901 -- This is relevant only in Ada 2005 mode. In Ada 95 programs we have
6902 -- to accommodate functions returning limited objects by reference.
6904 if Ada_Version >= Ada_2005
6905 and then Nkind (Exp) = N_Function_Call
6906 and then Is_Immutably_Limited_Type (Etype (Exp))
6907 and then Nkind (Parent (Exp)) /= N_Object_Declaration
6908 then
6909 declare
6910 Obj : constant Entity_Id := Make_Temporary (Loc, 'F', Exp);
6911 Decl : Node_Id;
6913 begin
6914 Decl :=
6915 Make_Object_Declaration (Loc,
6916 Defining_Identifier => Obj,
6917 Object_Definition => New_Occurrence_Of (Exp_Type, Loc),
6918 Expression => Relocate_Node (Exp));
6920 Insert_Action (Exp, Decl);
6921 Set_Etype (Obj, Exp_Type);
6922 Rewrite (Exp, New_Occurrence_Of (Obj, Loc));
6923 return;
6924 end;
6925 end if;
6927 Def_Id := Make_Temporary (Loc, 'R', Exp);
6928 Set_Etype (Def_Id, Exp_Type);
6930 -- The regular expansion of functions with side effects involves the
6931 -- generation of an access type to capture the return value found on
6932 -- the secondary stack. Since Alfa (and why) cannot process access
6933 -- types, use a different approach which ignores the secondary stack
6934 -- and "copies" the returned object.
6936 if Alfa_Mode then
6937 Res := New_Reference_To (Def_Id, Loc);
6938 Ref_Type := Exp_Type;
6940 -- Regular expansion utilizing an access type and 'reference
6942 else
6943 Res :=
6944 Make_Explicit_Dereference (Loc,
6945 Prefix => New_Reference_To (Def_Id, Loc));
6947 -- Generate:
6948 -- type Ann is access all <Exp_Type>;
6950 Ref_Type := Make_Temporary (Loc, 'A');
6952 Ptr_Typ_Decl :=
6953 Make_Full_Type_Declaration (Loc,
6954 Defining_Identifier => Ref_Type,
6955 Type_Definition =>
6956 Make_Access_To_Object_Definition (Loc,
6957 All_Present => True,
6958 Subtype_Indication =>
6959 New_Reference_To (Exp_Type, Loc)));
6961 Insert_Action (Exp, Ptr_Typ_Decl);
6962 end if;
6964 E := Exp;
6965 if Nkind (E) = N_Explicit_Dereference then
6966 New_Exp := Relocate_Node (Prefix (E));
6967 else
6968 E := Relocate_Node (E);
6970 -- Do not generate a 'reference in Alfa mode since the access type
6971 -- is not created in the first place.
6973 if Alfa_Mode then
6974 New_Exp := E;
6976 -- Otherwise generate reference, marking the value as non-null
6977 -- since we know it cannot be null and we don't want a check.
6979 else
6980 New_Exp := Make_Reference (Loc, E);
6981 Set_Is_Known_Non_Null (Def_Id);
6982 end if;
6983 end if;
6985 if Is_Delayed_Aggregate (E) then
6987 -- The expansion of nested aggregates is delayed until the
6988 -- enclosing aggregate is expanded. As aggregates are often
6989 -- qualified, the predicate applies to qualified expressions as
6990 -- well, indicating that the enclosing aggregate has not been
6991 -- expanded yet. At this point the aggregate is part of a
6992 -- stand-alone declaration, and must be fully expanded.
6994 if Nkind (E) = N_Qualified_Expression then
6995 Set_Expansion_Delayed (Expression (E), False);
6996 Set_Analyzed (Expression (E), False);
6997 else
6998 Set_Expansion_Delayed (E, False);
6999 end if;
7001 Set_Analyzed (E, False);
7002 end if;
7004 Insert_Action (Exp,
7005 Make_Object_Declaration (Loc,
7006 Defining_Identifier => Def_Id,
7007 Object_Definition => New_Reference_To (Ref_Type, Loc),
7008 Constant_Present => True,
7009 Expression => New_Exp));
7010 end if;
7012 -- Preserve the Assignment_OK flag in all copies, since at least one
7013 -- copy may be used in a context where this flag must be set (otherwise
7014 -- why would the flag be set in the first place).
7016 Set_Assignment_OK (Res, Assignment_OK (Exp));
7018 -- Finally rewrite the original expression and we are done
7020 Rewrite (Exp, Res);
7021 Analyze_And_Resolve (Exp, Exp_Type);
7022 Scope_Suppress := Svg_Suppress;
7023 end Remove_Side_Effects;
7025 ---------------------------
7026 -- Represented_As_Scalar --
7027 ---------------------------
7029 function Represented_As_Scalar (T : Entity_Id) return Boolean is
7030 UT : constant Entity_Id := Underlying_Type (T);
7031 begin
7032 return Is_Scalar_Type (UT)
7033 or else (Is_Bit_Packed_Array (UT)
7034 and then Is_Scalar_Type (Packed_Array_Type (UT)));
7035 end Represented_As_Scalar;
7037 ------------------------------
7038 -- Requires_Cleanup_Actions --
7039 ------------------------------
7041 function Requires_Cleanup_Actions
7042 (N : Node_Id;
7043 Lib_Level : Boolean) return Boolean
7045 At_Lib_Level : constant Boolean :=
7046 Lib_Level
7047 and then Nkind_In (N, N_Package_Body,
7048 N_Package_Specification);
7049 -- N is at the library level if the top-most context is a package and
7050 -- the path taken to reach N does not inlcude non-package constructs.
7052 begin
7053 case Nkind (N) is
7054 when N_Accept_Statement |
7055 N_Block_Statement |
7056 N_Entry_Body |
7057 N_Package_Body |
7058 N_Protected_Body |
7059 N_Subprogram_Body |
7060 N_Task_Body =>
7061 return
7062 Requires_Cleanup_Actions (Declarations (N), At_Lib_Level, True)
7063 or else
7064 (Present (Handled_Statement_Sequence (N))
7065 and then
7066 Requires_Cleanup_Actions
7067 (Statements (Handled_Statement_Sequence (N)),
7068 At_Lib_Level, True));
7070 when N_Package_Specification =>
7071 return
7072 Requires_Cleanup_Actions
7073 (Visible_Declarations (N), At_Lib_Level, True)
7074 or else
7075 Requires_Cleanup_Actions
7076 (Private_Declarations (N), At_Lib_Level, True);
7078 when others =>
7079 return False;
7080 end case;
7081 end Requires_Cleanup_Actions;
7083 ------------------------------
7084 -- Requires_Cleanup_Actions --
7085 ------------------------------
7087 function Requires_Cleanup_Actions
7088 (L : List_Id;
7089 Lib_Level : Boolean;
7090 Nested_Constructs : Boolean) return Boolean
7092 Decl : Node_Id;
7093 Expr : Node_Id;
7094 Obj_Id : Entity_Id;
7095 Obj_Typ : Entity_Id;
7096 Pack_Id : Entity_Id;
7097 Typ : Entity_Id;
7099 begin
7100 if No (L)
7101 or else Is_Empty_List (L)
7102 then
7103 return False;
7104 end if;
7106 Decl := First (L);
7107 while Present (Decl) loop
7109 -- Library-level tagged types
7111 if Nkind (Decl) = N_Full_Type_Declaration then
7112 Typ := Defining_Identifier (Decl);
7114 if Is_Tagged_Type (Typ)
7115 and then Is_Library_Level_Entity (Typ)
7116 and then Convention (Typ) = Convention_Ada
7117 and then Present (Access_Disp_Table (Typ))
7118 and then RTE_Available (RE_Unregister_Tag)
7119 and then not No_Run_Time_Mode
7120 and then not Is_Abstract_Type (Typ)
7121 then
7122 return True;
7123 end if;
7125 -- Regular object declarations
7127 elsif Nkind (Decl) = N_Object_Declaration then
7128 Obj_Id := Defining_Identifier (Decl);
7129 Obj_Typ := Base_Type (Etype (Obj_Id));
7130 Expr := Expression (Decl);
7132 -- Bypass any form of processing for objects which have their
7133 -- finalization disabled. This applies only to objects at the
7134 -- library level.
7136 if Lib_Level and then Finalize_Storage_Only (Obj_Typ) then
7137 null;
7139 -- Transient variables are treated separately in order to minimize
7140 -- the size of the generated code. See Exp_Ch7.Process_Transient_
7141 -- Objects.
7143 elsif Is_Processed_Transient (Obj_Id) then
7144 null;
7146 -- The object is of the form:
7147 -- Obj : Typ [:= Expr];
7149 -- Do not process the incomplete view of a deferred constant. Do
7150 -- not consider tag-to-class-wide conversions.
7152 elsif not Is_Imported (Obj_Id)
7153 and then Needs_Finalization (Obj_Typ)
7154 and then not (Ekind (Obj_Id) = E_Constant
7155 and then not Has_Completion (Obj_Id))
7156 and then not Is_Tag_To_Class_Wide_Conversion (Obj_Id)
7157 then
7158 return True;
7160 -- The object is of the form:
7161 -- Obj : Access_Typ := Non_BIP_Function_Call'reference;
7163 -- Obj : Access_Typ :=
7164 -- BIP_Function_Call (BIPalloc => 2, ...)'reference;
7166 elsif Is_Access_Type (Obj_Typ)
7167 and then Needs_Finalization
7168 (Available_View (Designated_Type (Obj_Typ)))
7169 and then Present (Expr)
7170 and then
7171 (Is_Secondary_Stack_BIP_Func_Call (Expr)
7172 or else
7173 (Is_Non_BIP_Func_Call (Expr)
7174 and then not Is_Related_To_Func_Return (Obj_Id)))
7175 then
7176 return True;
7178 -- Processing for "hook" objects generated for controlled
7179 -- transients declared inside an Expression_With_Actions.
7181 elsif Is_Access_Type (Obj_Typ)
7182 and then Present (Status_Flag_Or_Transient_Decl (Obj_Id))
7183 and then Nkind (Status_Flag_Or_Transient_Decl (Obj_Id)) =
7184 N_Object_Declaration
7185 and then Is_Finalizable_Transient
7186 (Status_Flag_Or_Transient_Decl (Obj_Id), Decl)
7187 then
7188 return True;
7190 -- Processing for intermediate results of conditional expressions
7191 -- where one of the alternatives uses a controlled function call.
7193 elsif Is_Access_Type (Obj_Typ)
7194 and then Present (Status_Flag_Or_Transient_Decl (Obj_Id))
7195 and then Nkind (Status_Flag_Or_Transient_Decl (Obj_Id)) =
7196 N_Defining_Identifier
7197 and then Present (Expr)
7198 and then Nkind (Expr) = N_Null
7199 then
7200 return True;
7202 -- Simple protected objects which use type System.Tasking.
7203 -- Protected_Objects.Protection to manage their locks should be
7204 -- treated as controlled since they require manual cleanup.
7206 elsif Ekind (Obj_Id) = E_Variable
7207 and then
7208 (Is_Simple_Protected_Type (Obj_Typ)
7209 or else Has_Simple_Protected_Object (Obj_Typ))
7210 then
7211 return True;
7212 end if;
7214 -- Specific cases of object renamings
7216 elsif Nkind (Decl) = N_Object_Renaming_Declaration then
7217 Obj_Id := Defining_Identifier (Decl);
7218 Obj_Typ := Base_Type (Etype (Obj_Id));
7220 -- Bypass any form of processing for objects which have their
7221 -- finalization disabled. This applies only to objects at the
7222 -- library level.
7224 if Lib_Level and then Finalize_Storage_Only (Obj_Typ) then
7225 null;
7227 -- Return object of a build-in-place function. This case is
7228 -- recognized and marked by the expansion of an extended return
7229 -- statement (see Expand_N_Extended_Return_Statement).
7231 elsif Needs_Finalization (Obj_Typ)
7232 and then Is_Return_Object (Obj_Id)
7233 and then Present (Status_Flag_Or_Transient_Decl (Obj_Id))
7234 then
7235 return True;
7237 -- Detect a case where a source object has been initialized by
7238 -- a controlled function call or another object which was later
7239 -- rewritten as a class-wide conversion of Ada.Tags.Displace.
7241 -- Obj1 : CW_Type := Src_Obj;
7242 -- Obj2 : CW_Type := Function_Call (...);
7244 -- Obj1 : CW_Type renames (... Ada.Tags.Displace (Src_Obj));
7245 -- Tmp : ... := Function_Call (...)'reference;
7246 -- Obj2 : CW_Type renames (... Ada.Tags.Displace (Tmp));
7248 elsif Is_Displacement_Of_Object_Or_Function_Result (Obj_Id) then
7249 return True;
7250 end if;
7252 -- Inspect the freeze node of an access-to-controlled type and look
7253 -- for a delayed finalization master. This case arises when the
7254 -- freeze actions are inserted at a later time than the expansion of
7255 -- the context. Since Build_Finalizer is never called on a single
7256 -- construct twice, the master will be ultimately left out and never
7257 -- finalized. This is also needed for freeze actions of designated
7258 -- types themselves, since in some cases the finalization master is
7259 -- associated with a designated type's freeze node rather than that
7260 -- of the access type (see handling for freeze actions in
7261 -- Build_Finalization_Master).
7263 elsif Nkind (Decl) = N_Freeze_Entity
7264 and then Present (Actions (Decl))
7265 then
7266 Typ := Entity (Decl);
7268 if ((Is_Access_Type (Typ)
7269 and then not Is_Access_Subprogram_Type (Typ)
7270 and then Needs_Finalization
7271 (Available_View (Designated_Type (Typ))))
7272 or else
7273 (Is_Type (Typ)
7274 and then Needs_Finalization (Typ)))
7275 and then Requires_Cleanup_Actions
7276 (Actions (Decl), Lib_Level, Nested_Constructs)
7277 then
7278 return True;
7279 end if;
7281 -- Nested package declarations
7283 elsif Nested_Constructs
7284 and then Nkind (Decl) = N_Package_Declaration
7285 then
7286 Pack_Id := Defining_Unit_Name (Specification (Decl));
7288 if Nkind (Pack_Id) = N_Defining_Program_Unit_Name then
7289 Pack_Id := Defining_Identifier (Pack_Id);
7290 end if;
7292 if Ekind (Pack_Id) /= E_Generic_Package
7293 and then Requires_Cleanup_Actions
7294 (Specification (Decl), Lib_Level)
7295 then
7296 return True;
7297 end if;
7299 -- Nested package bodies
7301 elsif Nested_Constructs
7302 and then Nkind (Decl) = N_Package_Body
7303 then
7304 Pack_Id := Corresponding_Spec (Decl);
7306 if Ekind (Pack_Id) /= E_Generic_Package
7307 and then Requires_Cleanup_Actions (Decl, Lib_Level)
7308 then
7309 return True;
7310 end if;
7311 end if;
7313 Next (Decl);
7314 end loop;
7316 return False;
7317 end Requires_Cleanup_Actions;
7319 ------------------------------------
7320 -- Safe_Unchecked_Type_Conversion --
7321 ------------------------------------
7323 -- Note: this function knows quite a bit about the exact requirements of
7324 -- Gigi with respect to unchecked type conversions, and its code must be
7325 -- coordinated with any changes in Gigi in this area.
7327 -- The above requirements should be documented in Sinfo ???
7329 function Safe_Unchecked_Type_Conversion (Exp : Node_Id) return Boolean is
7330 Otyp : Entity_Id;
7331 Ityp : Entity_Id;
7332 Oalign : Uint;
7333 Ialign : Uint;
7334 Pexp : constant Node_Id := Parent (Exp);
7336 begin
7337 -- If the expression is the RHS of an assignment or object declaration
7338 -- we are always OK because there will always be a target.
7340 -- Object renaming declarations, (generated for view conversions of
7341 -- actuals in inlined calls), like object declarations, provide an
7342 -- explicit type, and are safe as well.
7344 if (Nkind (Pexp) = N_Assignment_Statement
7345 and then Expression (Pexp) = Exp)
7346 or else Nkind (Pexp) = N_Object_Declaration
7347 or else Nkind (Pexp) = N_Object_Renaming_Declaration
7348 then
7349 return True;
7351 -- If the expression is the prefix of an N_Selected_Component we should
7352 -- also be OK because GCC knows to look inside the conversion except if
7353 -- the type is discriminated. We assume that we are OK anyway if the
7354 -- type is not set yet or if it is controlled since we can't afford to
7355 -- introduce a temporary in this case.
7357 elsif Nkind (Pexp) = N_Selected_Component
7358 and then Prefix (Pexp) = Exp
7359 then
7360 if No (Etype (Pexp)) then
7361 return True;
7362 else
7363 return
7364 not Has_Discriminants (Etype (Pexp))
7365 or else Is_Constrained (Etype (Pexp));
7366 end if;
7367 end if;
7369 -- Set the output type, this comes from Etype if it is set, otherwise we
7370 -- take it from the subtype mark, which we assume was already fully
7371 -- analyzed.
7373 if Present (Etype (Exp)) then
7374 Otyp := Etype (Exp);
7375 else
7376 Otyp := Entity (Subtype_Mark (Exp));
7377 end if;
7379 -- The input type always comes from the expression, and we assume
7380 -- this is indeed always analyzed, so we can simply get the Etype.
7382 Ityp := Etype (Expression (Exp));
7384 -- Initialize alignments to unknown so far
7386 Oalign := No_Uint;
7387 Ialign := No_Uint;
7389 -- Replace a concurrent type by its corresponding record type and each
7390 -- type by its underlying type and do the tests on those. The original
7391 -- type may be a private type whose completion is a concurrent type, so
7392 -- find the underlying type first.
7394 if Present (Underlying_Type (Otyp)) then
7395 Otyp := Underlying_Type (Otyp);
7396 end if;
7398 if Present (Underlying_Type (Ityp)) then
7399 Ityp := Underlying_Type (Ityp);
7400 end if;
7402 if Is_Concurrent_Type (Otyp) then
7403 Otyp := Corresponding_Record_Type (Otyp);
7404 end if;
7406 if Is_Concurrent_Type (Ityp) then
7407 Ityp := Corresponding_Record_Type (Ityp);
7408 end if;
7410 -- If the base types are the same, we know there is no problem since
7411 -- this conversion will be a noop.
7413 if Implementation_Base_Type (Otyp) = Implementation_Base_Type (Ityp) then
7414 return True;
7416 -- Same if this is an upwards conversion of an untagged type, and there
7417 -- are no constraints involved (could be more general???)
7419 elsif Etype (Ityp) = Otyp
7420 and then not Is_Tagged_Type (Ityp)
7421 and then not Has_Discriminants (Ityp)
7422 and then No (First_Rep_Item (Base_Type (Ityp)))
7423 then
7424 return True;
7426 -- If the expression has an access type (object or subprogram) we assume
7427 -- that the conversion is safe, because the size of the target is safe,
7428 -- even if it is a record (which might be treated as having unknown size
7429 -- at this point).
7431 elsif Is_Access_Type (Ityp) then
7432 return True;
7434 -- If the size of output type is known at compile time, there is never
7435 -- a problem. Note that unconstrained records are considered to be of
7436 -- known size, but we can't consider them that way here, because we are
7437 -- talking about the actual size of the object.
7439 -- We also make sure that in addition to the size being known, we do not
7440 -- have a case which might generate an embarrassingly large temp in
7441 -- stack checking mode.
7443 elsif Size_Known_At_Compile_Time (Otyp)
7444 and then
7445 (not Stack_Checking_Enabled
7446 or else not May_Generate_Large_Temp (Otyp))
7447 and then not (Is_Record_Type (Otyp) and then not Is_Constrained (Otyp))
7448 then
7449 return True;
7451 -- If either type is tagged, then we know the alignment is OK so
7452 -- Gigi will be able to use pointer punning.
7454 elsif Is_Tagged_Type (Otyp) or else Is_Tagged_Type (Ityp) then
7455 return True;
7457 -- If either type is a limited record type, we cannot do a copy, so say
7458 -- safe since there's nothing else we can do.
7460 elsif Is_Limited_Record (Otyp) or else Is_Limited_Record (Ityp) then
7461 return True;
7463 -- Conversions to and from packed array types are always ignored and
7464 -- hence are safe.
7466 elsif Is_Packed_Array_Type (Otyp)
7467 or else Is_Packed_Array_Type (Ityp)
7468 then
7469 return True;
7470 end if;
7472 -- The only other cases known to be safe is if the input type's
7473 -- alignment is known to be at least the maximum alignment for the
7474 -- target or if both alignments are known and the output type's
7475 -- alignment is no stricter than the input's. We can use the component
7476 -- type alignement for an array if a type is an unpacked array type.
7478 if Present (Alignment_Clause (Otyp)) then
7479 Oalign := Expr_Value (Expression (Alignment_Clause (Otyp)));
7481 elsif Is_Array_Type (Otyp)
7482 and then Present (Alignment_Clause (Component_Type (Otyp)))
7483 then
7484 Oalign := Expr_Value (Expression (Alignment_Clause
7485 (Component_Type (Otyp))));
7486 end if;
7488 if Present (Alignment_Clause (Ityp)) then
7489 Ialign := Expr_Value (Expression (Alignment_Clause (Ityp)));
7491 elsif Is_Array_Type (Ityp)
7492 and then Present (Alignment_Clause (Component_Type (Ityp)))
7493 then
7494 Ialign := Expr_Value (Expression (Alignment_Clause
7495 (Component_Type (Ityp))));
7496 end if;
7498 if Ialign /= No_Uint and then Ialign > Maximum_Alignment then
7499 return True;
7501 elsif Ialign /= No_Uint and then Oalign /= No_Uint
7502 and then Ialign <= Oalign
7503 then
7504 return True;
7506 -- Otherwise, Gigi cannot handle this and we must make a temporary
7508 else
7509 return False;
7510 end if;
7511 end Safe_Unchecked_Type_Conversion;
7513 ---------------------------------
7514 -- Set_Current_Value_Condition --
7515 ---------------------------------
7517 -- Note: the implementation of this procedure is very closely tied to the
7518 -- implementation of Get_Current_Value_Condition. Here we set required
7519 -- Current_Value fields, and in Get_Current_Value_Condition, we interpret
7520 -- them, so they must have a consistent view.
7522 procedure Set_Current_Value_Condition (Cnode : Node_Id) is
7524 procedure Set_Entity_Current_Value (N : Node_Id);
7525 -- If N is an entity reference, where the entity is of an appropriate
7526 -- kind, then set the current value of this entity to Cnode, unless
7527 -- there is already a definite value set there.
7529 procedure Set_Expression_Current_Value (N : Node_Id);
7530 -- If N is of an appropriate form, sets an appropriate entry in current
7531 -- value fields of relevant entities. Multiple entities can be affected
7532 -- in the case of an AND or AND THEN.
7534 ------------------------------
7535 -- Set_Entity_Current_Value --
7536 ------------------------------
7538 procedure Set_Entity_Current_Value (N : Node_Id) is
7539 begin
7540 if Is_Entity_Name (N) then
7541 declare
7542 Ent : constant Entity_Id := Entity (N);
7544 begin
7545 -- Don't capture if not safe to do so
7547 if not Safe_To_Capture_Value (N, Ent, Cond => True) then
7548 return;
7549 end if;
7551 -- Here we have a case where the Current_Value field may need
7552 -- to be set. We set it if it is not already set to a compile
7553 -- time expression value.
7555 -- Note that this represents a decision that one condition
7556 -- blots out another previous one. That's certainly right if
7557 -- they occur at the same level. If the second one is nested,
7558 -- then the decision is neither right nor wrong (it would be
7559 -- equally OK to leave the outer one in place, or take the new
7560 -- inner one. Really we should record both, but our data
7561 -- structures are not that elaborate.
7563 if Nkind (Current_Value (Ent)) not in N_Subexpr then
7564 Set_Current_Value (Ent, Cnode);
7565 end if;
7566 end;
7567 end if;
7568 end Set_Entity_Current_Value;
7570 ----------------------------------
7571 -- Set_Expression_Current_Value --
7572 ----------------------------------
7574 procedure Set_Expression_Current_Value (N : Node_Id) is
7575 Cond : Node_Id;
7577 begin
7578 Cond := N;
7580 -- Loop to deal with (ignore for now) any NOT operators present. The
7581 -- presence of NOT operators will be handled properly when we call
7582 -- Get_Current_Value_Condition.
7584 while Nkind (Cond) = N_Op_Not loop
7585 Cond := Right_Opnd (Cond);
7586 end loop;
7588 -- For an AND or AND THEN, recursively process operands
7590 if Nkind (Cond) = N_Op_And or else Nkind (Cond) = N_And_Then then
7591 Set_Expression_Current_Value (Left_Opnd (Cond));
7592 Set_Expression_Current_Value (Right_Opnd (Cond));
7593 return;
7594 end if;
7596 -- Check possible relational operator
7598 if Nkind (Cond) in N_Op_Compare then
7599 if Compile_Time_Known_Value (Right_Opnd (Cond)) then
7600 Set_Entity_Current_Value (Left_Opnd (Cond));
7601 elsif Compile_Time_Known_Value (Left_Opnd (Cond)) then
7602 Set_Entity_Current_Value (Right_Opnd (Cond));
7603 end if;
7605 -- Check possible boolean variable reference
7607 else
7608 Set_Entity_Current_Value (Cond);
7609 end if;
7610 end Set_Expression_Current_Value;
7612 -- Start of processing for Set_Current_Value_Condition
7614 begin
7615 Set_Expression_Current_Value (Condition (Cnode));
7616 end Set_Current_Value_Condition;
7618 --------------------------
7619 -- Set_Elaboration_Flag --
7620 --------------------------
7622 procedure Set_Elaboration_Flag (N : Node_Id; Spec_Id : Entity_Id) is
7623 Loc : constant Source_Ptr := Sloc (N);
7624 Ent : constant Entity_Id := Elaboration_Entity (Spec_Id);
7625 Asn : Node_Id;
7627 begin
7628 if Present (Ent) then
7630 -- Nothing to do if at the compilation unit level, because in this
7631 -- case the flag is set by the binder generated elaboration routine.
7633 if Nkind (Parent (N)) = N_Compilation_Unit then
7634 null;
7636 -- Here we do need to generate an assignment statement
7638 else
7639 Check_Restriction (No_Elaboration_Code, N);
7640 Asn :=
7641 Make_Assignment_Statement (Loc,
7642 Name => New_Occurrence_Of (Ent, Loc),
7643 Expression => Make_Integer_Literal (Loc, Uint_1));
7645 if Nkind (Parent (N)) = N_Subunit then
7646 Insert_After (Corresponding_Stub (Parent (N)), Asn);
7647 else
7648 Insert_After (N, Asn);
7649 end if;
7651 Analyze (Asn);
7653 -- Kill current value indication. This is necessary because the
7654 -- tests of this flag are inserted out of sequence and must not
7655 -- pick up bogus indications of the wrong constant value.
7657 Set_Current_Value (Ent, Empty);
7658 end if;
7659 end if;
7660 end Set_Elaboration_Flag;
7662 ----------------------------
7663 -- Set_Renamed_Subprogram --
7664 ----------------------------
7666 procedure Set_Renamed_Subprogram (N : Node_Id; E : Entity_Id) is
7667 begin
7668 -- If input node is an identifier, we can just reset it
7670 if Nkind (N) = N_Identifier then
7671 Set_Chars (N, Chars (E));
7672 Set_Entity (N, E);
7674 -- Otherwise we have to do a rewrite, preserving Comes_From_Source
7676 else
7677 declare
7678 CS : constant Boolean := Comes_From_Source (N);
7679 begin
7680 Rewrite (N, Make_Identifier (Sloc (N), Chars (E)));
7681 Set_Entity (N, E);
7682 Set_Comes_From_Source (N, CS);
7683 Set_Analyzed (N, True);
7684 end;
7685 end if;
7686 end Set_Renamed_Subprogram;
7688 ----------------------------------
7689 -- Silly_Boolean_Array_Not_Test --
7690 ----------------------------------
7692 -- This procedure implements an odd and silly test. We explicitly check
7693 -- for the case where the 'First of the component type is equal to the
7694 -- 'Last of this component type, and if this is the case, we make sure
7695 -- that constraint error is raised. The reason is that the NOT is bound
7696 -- to cause CE in this case, and we will not otherwise catch it.
7698 -- No such check is required for AND and OR, since for both these cases
7699 -- False op False = False, and True op True = True. For the XOR case,
7700 -- see Silly_Boolean_Array_Xor_Test.
7702 -- Believe it or not, this was reported as a bug. Note that nearly always,
7703 -- the test will evaluate statically to False, so the code will be
7704 -- statically removed, and no extra overhead caused.
7706 procedure Silly_Boolean_Array_Not_Test (N : Node_Id; T : Entity_Id) is
7707 Loc : constant Source_Ptr := Sloc (N);
7708 CT : constant Entity_Id := Component_Type (T);
7710 begin
7711 -- The check we install is
7713 -- constraint_error when
7714 -- component_type'first = component_type'last
7715 -- and then array_type'Length /= 0)
7717 -- We need the last guard because we don't want to raise CE for empty
7718 -- arrays since no out of range values result. (Empty arrays with a
7719 -- component type of True .. True -- very useful -- even the ACATS
7720 -- does not test that marginal case!)
7722 Insert_Action (N,
7723 Make_Raise_Constraint_Error (Loc,
7724 Condition =>
7725 Make_And_Then (Loc,
7726 Left_Opnd =>
7727 Make_Op_Eq (Loc,
7728 Left_Opnd =>
7729 Make_Attribute_Reference (Loc,
7730 Prefix => New_Occurrence_Of (CT, Loc),
7731 Attribute_Name => Name_First),
7733 Right_Opnd =>
7734 Make_Attribute_Reference (Loc,
7735 Prefix => New_Occurrence_Of (CT, Loc),
7736 Attribute_Name => Name_Last)),
7738 Right_Opnd => Make_Non_Empty_Check (Loc, Right_Opnd (N))),
7739 Reason => CE_Range_Check_Failed));
7740 end Silly_Boolean_Array_Not_Test;
7742 ----------------------------------
7743 -- Silly_Boolean_Array_Xor_Test --
7744 ----------------------------------
7746 -- This procedure implements an odd and silly test. We explicitly check
7747 -- for the XOR case where the component type is True .. True, since this
7748 -- will raise constraint error. A special check is required since CE
7749 -- will not be generated otherwise (cf Expand_Packed_Not).
7751 -- No such check is required for AND and OR, since for both these cases
7752 -- False op False = False, and True op True = True, and no check is
7753 -- required for the case of False .. False, since False xor False = False.
7754 -- See also Silly_Boolean_Array_Not_Test
7756 procedure Silly_Boolean_Array_Xor_Test (N : Node_Id; T : Entity_Id) is
7757 Loc : constant Source_Ptr := Sloc (N);
7758 CT : constant Entity_Id := Component_Type (T);
7760 begin
7761 -- The check we install is
7763 -- constraint_error when
7764 -- Boolean (component_type'First)
7765 -- and then Boolean (component_type'Last)
7766 -- and then array_type'Length /= 0)
7768 -- We need the last guard because we don't want to raise CE for empty
7769 -- arrays since no out of range values result (Empty arrays with a
7770 -- component type of True .. True -- very useful -- even the ACATS
7771 -- does not test that marginal case!).
7773 Insert_Action (N,
7774 Make_Raise_Constraint_Error (Loc,
7775 Condition =>
7776 Make_And_Then (Loc,
7777 Left_Opnd =>
7778 Make_And_Then (Loc,
7779 Left_Opnd =>
7780 Convert_To (Standard_Boolean,
7781 Make_Attribute_Reference (Loc,
7782 Prefix => New_Occurrence_Of (CT, Loc),
7783 Attribute_Name => Name_First)),
7785 Right_Opnd =>
7786 Convert_To (Standard_Boolean,
7787 Make_Attribute_Reference (Loc,
7788 Prefix => New_Occurrence_Of (CT, Loc),
7789 Attribute_Name => Name_Last))),
7791 Right_Opnd => Make_Non_Empty_Check (Loc, Right_Opnd (N))),
7792 Reason => CE_Range_Check_Failed));
7793 end Silly_Boolean_Array_Xor_Test;
7795 --------------------------
7796 -- Target_Has_Fixed_Ops --
7797 --------------------------
7799 Integer_Sized_Small : Ureal;
7800 -- Set to 2.0 ** -(Integer'Size - 1) the first time that this function is
7801 -- called (we don't want to compute it more than once!)
7803 Long_Integer_Sized_Small : Ureal;
7804 -- Set to 2.0 ** -(Long_Integer'Size - 1) the first time that this function
7805 -- is called (we don't want to compute it more than once)
7807 First_Time_For_THFO : Boolean := True;
7808 -- Set to False after first call (if Fractional_Fixed_Ops_On_Target)
7810 function Target_Has_Fixed_Ops
7811 (Left_Typ : Entity_Id;
7812 Right_Typ : Entity_Id;
7813 Result_Typ : Entity_Id) return Boolean
7815 function Is_Fractional_Type (Typ : Entity_Id) return Boolean;
7816 -- Return True if the given type is a fixed-point type with a small
7817 -- value equal to 2 ** (-(T'Object_Size - 1)) and whose values have
7818 -- an absolute value less than 1.0. This is currently limited to
7819 -- fixed-point types that map to Integer or Long_Integer.
7821 ------------------------
7822 -- Is_Fractional_Type --
7823 ------------------------
7825 function Is_Fractional_Type (Typ : Entity_Id) return Boolean is
7826 begin
7827 if Esize (Typ) = Standard_Integer_Size then
7828 return Small_Value (Typ) = Integer_Sized_Small;
7830 elsif Esize (Typ) = Standard_Long_Integer_Size then
7831 return Small_Value (Typ) = Long_Integer_Sized_Small;
7833 else
7834 return False;
7835 end if;
7836 end Is_Fractional_Type;
7838 -- Start of processing for Target_Has_Fixed_Ops
7840 begin
7841 -- Return False if Fractional_Fixed_Ops_On_Target is false
7843 if not Fractional_Fixed_Ops_On_Target then
7844 return False;
7845 end if;
7847 -- Here the target has Fractional_Fixed_Ops, if first time, compute
7848 -- standard constants used by Is_Fractional_Type.
7850 if First_Time_For_THFO then
7851 First_Time_For_THFO := False;
7853 Integer_Sized_Small :=
7854 UR_From_Components
7855 (Num => Uint_1,
7856 Den => UI_From_Int (Standard_Integer_Size - 1),
7857 Rbase => 2);
7859 Long_Integer_Sized_Small :=
7860 UR_From_Components
7861 (Num => Uint_1,
7862 Den => UI_From_Int (Standard_Long_Integer_Size - 1),
7863 Rbase => 2);
7864 end if;
7866 -- Return True if target supports fixed-by-fixed multiply/divide for
7867 -- fractional fixed-point types (see Is_Fractional_Type) and the operand
7868 -- and result types are equivalent fractional types.
7870 return Is_Fractional_Type (Base_Type (Left_Typ))
7871 and then Is_Fractional_Type (Base_Type (Right_Typ))
7872 and then Is_Fractional_Type (Base_Type (Result_Typ))
7873 and then Esize (Left_Typ) = Esize (Right_Typ)
7874 and then Esize (Left_Typ) = Esize (Result_Typ);
7875 end Target_Has_Fixed_Ops;
7877 ------------------------------------------
7878 -- Type_May_Have_Bit_Aligned_Components --
7879 ------------------------------------------
7881 function Type_May_Have_Bit_Aligned_Components
7882 (Typ : Entity_Id) return Boolean
7884 begin
7885 -- Array type, check component type
7887 if Is_Array_Type (Typ) then
7888 return
7889 Type_May_Have_Bit_Aligned_Components (Component_Type (Typ));
7891 -- Record type, check components
7893 elsif Is_Record_Type (Typ) then
7894 declare
7895 E : Entity_Id;
7897 begin
7898 E := First_Component_Or_Discriminant (Typ);
7899 while Present (E) loop
7900 if Component_May_Be_Bit_Aligned (E)
7901 or else Type_May_Have_Bit_Aligned_Components (Etype (E))
7902 then
7903 return True;
7904 end if;
7906 Next_Component_Or_Discriminant (E);
7907 end loop;
7909 return False;
7910 end;
7912 -- Type other than array or record is always OK
7914 else
7915 return False;
7916 end if;
7917 end Type_May_Have_Bit_Aligned_Components;
7919 ----------------------------
7920 -- Wrap_Cleanup_Procedure --
7921 ----------------------------
7923 procedure Wrap_Cleanup_Procedure (N : Node_Id) is
7924 Loc : constant Source_Ptr := Sloc (N);
7925 Stseq : constant Node_Id := Handled_Statement_Sequence (N);
7926 Stmts : constant List_Id := Statements (Stseq);
7928 begin
7929 if Abort_Allowed then
7930 Prepend_To (Stmts, Build_Runtime_Call (Loc, RE_Abort_Defer));
7931 Append_To (Stmts, Build_Runtime_Call (Loc, RE_Abort_Undefer));
7932 end if;
7933 end Wrap_Cleanup_Procedure;
7935 end Exp_Util;