* gcc.dg/store-motion-fgcse-sm.c (dg-final): Cleanup
[official-gcc.git] / gcc / ada / exp_util.adb
blob381002255c0bdb7429933f2672b3bc878a12206a
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-2014, Free Software Foundation, Inc. --
10 -- --
11 -- GNAT is free software; you can redistribute it and/or modify it under --
12 -- terms of the GNU General Public License as published by the Free Soft- --
13 -- ware Foundation; either version 3, or (at your option) any later ver- --
14 -- sion. GNAT is distributed in the hope that it will be useful, but WITH- --
15 -- OUT ANY WARRANTY; without even the implied warranty of MERCHANTABILITY --
16 -- or FITNESS FOR A PARTICULAR PURPOSE. See the GNU General Public License --
17 -- for more details. You should have received a copy of the GNU General --
18 -- Public License distributed with GNAT; see file COPYING3. If not, go to --
19 -- http://www.gnu.org/licenses for a complete copy of the license. --
20 -- --
21 -- GNAT was originally developed by the GNAT team at New York University. --
22 -- Extensive contributions were provided by Ada Core Technologies Inc. --
23 -- --
24 ------------------------------------------------------------------------------
26 with Aspects; use Aspects;
27 with Atree; use Atree;
28 with Casing; use Casing;
29 with Checks; use Checks;
30 with Debug; use Debug;
31 with Einfo; use Einfo;
32 with Elists; use Elists;
33 with Errout; use Errout;
34 with Exp_Aggr; use Exp_Aggr;
35 with Exp_Ch6; use Exp_Ch6;
36 with Exp_Ch7; use Exp_Ch7;
37 with Inline; use Inline;
38 with Itypes; use Itypes;
39 with Lib; use Lib;
40 with Nlists; use Nlists;
41 with Nmake; use Nmake;
42 with Opt; use Opt;
43 with Restrict; use Restrict;
44 with Rident; use Rident;
45 with Sem; use Sem;
46 with Sem_Aux; use Sem_Aux;
47 with Sem_Ch8; use Sem_Ch8;
48 with Sem_Eval; use Sem_Eval;
49 with Sem_Res; use Sem_Res;
50 with Sem_Type; use Sem_Type;
51 with Sem_Util; use Sem_Util;
52 with Snames; use Snames;
53 with Stand; use Stand;
54 with Stringt; use Stringt;
55 with Targparm; use Targparm;
56 with Tbuild; use Tbuild;
57 with Ttypes; use Ttypes;
58 with Urealp; use Urealp;
59 with Validsw; use Validsw;
61 package body Exp_Util is
63 -----------------------
64 -- Local Subprograms --
65 -----------------------
67 function Build_Task_Array_Image
68 (Loc : Source_Ptr;
69 Id_Ref : Node_Id;
70 A_Type : Entity_Id;
71 Dyn : Boolean := False) return Node_Id;
72 -- Build function to generate the image string for a task that is an array
73 -- component, concatenating the images of each index. To avoid storage
74 -- leaks, the string is built with successive slice assignments. The flag
75 -- Dyn indicates whether this is called for the initialization procedure of
76 -- an array of tasks, or for the name of a dynamically created task that is
77 -- assigned to an indexed component.
79 function Build_Task_Image_Function
80 (Loc : Source_Ptr;
81 Decls : List_Id;
82 Stats : List_Id;
83 Res : Entity_Id) return Node_Id;
84 -- Common processing for Task_Array_Image and Task_Record_Image. Build
85 -- function body that computes image.
87 procedure Build_Task_Image_Prefix
88 (Loc : Source_Ptr;
89 Len : out Entity_Id;
90 Res : out Entity_Id;
91 Pos : out Entity_Id;
92 Prefix : Entity_Id;
93 Sum : Node_Id;
94 Decls : List_Id;
95 Stats : List_Id);
96 -- Common processing for Task_Array_Image and Task_Record_Image. Create
97 -- local variables and assign prefix of name to result string.
99 function Build_Task_Record_Image
100 (Loc : Source_Ptr;
101 Id_Ref : Node_Id;
102 Dyn : Boolean := False) return Node_Id;
103 -- Build function to generate the image string for a task that is a record
104 -- component. Concatenate name of variable with that of selector. The flag
105 -- Dyn indicates whether this is called for the initialization procedure of
106 -- record with task components, or for a dynamically created task that is
107 -- assigned to a selected component.
109 procedure Evaluate_Slice_Bounds (Slice : Node_Id);
110 -- Force evaluation of bounds of a slice, which may be given by a range
111 -- or by a subtype indication with or without a constraint.
113 function Make_CW_Equivalent_Type
114 (T : Entity_Id;
115 E : Node_Id) return Entity_Id;
116 -- T is a class-wide type entity, E is the initial expression node that
117 -- constrains T in case such as: " X: T := E" or "new T'(E)". This function
118 -- returns the entity of the Equivalent type and inserts on the fly the
119 -- necessary declaration such as:
121 -- type anon is record
122 -- _parent : Root_Type (T); constrained with E discriminants (if any)
123 -- Extension : String (1 .. expr to match size of E);
124 -- end record;
126 -- This record is compatible with any object of the class of T thanks to
127 -- the first field and has the same size as E thanks to the second.
129 function Make_Literal_Range
130 (Loc : Source_Ptr;
131 Literal_Typ : Entity_Id) return Node_Id;
132 -- Produce a Range node whose bounds are:
133 -- Low_Bound (Literal_Type) ..
134 -- Low_Bound (Literal_Type) + (Length (Literal_Typ) - 1)
135 -- this is used for expanding declarations like X : String := "sdfgdfg";
137 -- If the index type of the target array is not integer, we generate:
138 -- Low_Bound (Literal_Type) ..
139 -- Literal_Type'Val
140 -- (Literal_Type'Pos (Low_Bound (Literal_Type))
141 -- + (Length (Literal_Typ) -1))
143 function Make_Non_Empty_Check
144 (Loc : Source_Ptr;
145 N : Node_Id) return Node_Id;
146 -- Produce a boolean expression checking that the unidimensional array
147 -- node N is not empty.
149 function New_Class_Wide_Subtype
150 (CW_Typ : Entity_Id;
151 N : Node_Id) return Entity_Id;
152 -- Create an implicit subtype of CW_Typ attached to node N
154 function Requires_Cleanup_Actions
155 (L : List_Id;
156 Lib_Level : Boolean;
157 Nested_Constructs : Boolean) return Boolean;
158 -- Given a list L, determine whether it contains one of the following:
160 -- 1) controlled objects
161 -- 2) library-level tagged types
163 -- Lib_Level is True when the list comes from a construct at the library
164 -- level, and False otherwise. Nested_Constructs is True when any nested
165 -- packages declared in L must be processed, and False otherwise.
167 -------------------------------------
168 -- Activate_Atomic_Synchronization --
169 -------------------------------------
171 procedure Activate_Atomic_Synchronization (N : Node_Id) is
172 Msg_Node : Node_Id;
174 begin
175 case Nkind (Parent (N)) is
177 -- Check for cases of appearing in the prefix of a construct where
178 -- we don't need atomic synchronization for this kind of usage.
180 when
181 -- Nothing to do if we are the prefix of an attribute, since we
182 -- do not want an atomic sync operation for things like 'Size.
184 N_Attribute_Reference |
186 -- The N_Reference node is like an attribute
188 N_Reference |
190 -- Nothing to do for a reference to a component (or components)
191 -- of a composite object. Only reads and updates of the object
192 -- as a whole require atomic synchronization (RM C.6 (15)).
194 N_Indexed_Component |
195 N_Selected_Component |
196 N_Slice =>
198 -- For all the above cases, nothing to do if we are the prefix
200 if Prefix (Parent (N)) = N then
201 return;
202 end if;
204 when others => null;
205 end case;
207 -- Go ahead and set the flag
209 Set_Atomic_Sync_Required (N);
211 -- Generate info message if requested
213 if Warn_On_Atomic_Synchronization then
214 case Nkind (N) is
215 when N_Identifier =>
216 Msg_Node := N;
218 when N_Selected_Component | N_Expanded_Name =>
219 Msg_Node := Selector_Name (N);
221 when N_Explicit_Dereference | N_Indexed_Component =>
222 Msg_Node := Empty;
224 when others =>
225 pragma Assert (False);
226 return;
227 end case;
229 if Present (Msg_Node) then
230 Error_Msg_N
231 ("info: atomic synchronization set for &?N?", Msg_Node);
232 else
233 Error_Msg_N
234 ("info: atomic synchronization set?N?", N);
235 end if;
236 end if;
237 end Activate_Atomic_Synchronization;
239 ----------------------
240 -- Adjust_Condition --
241 ----------------------
243 procedure Adjust_Condition (N : Node_Id) is
244 begin
245 if No (N) then
246 return;
247 end if;
249 declare
250 Loc : constant Source_Ptr := Sloc (N);
251 T : constant Entity_Id := Etype (N);
252 Ti : Entity_Id;
254 begin
255 -- Defend against a call where the argument has no type, or has a
256 -- type that is not Boolean. This can occur because of prior errors.
258 if No (T) or else not Is_Boolean_Type (T) then
259 return;
260 end if;
262 -- Apply validity checking if needed
264 if Validity_Checks_On and Validity_Check_Tests then
265 Ensure_Valid (N);
266 end if;
268 -- Immediate return if standard boolean, the most common case,
269 -- where nothing needs to be done.
271 if Base_Type (T) = Standard_Boolean then
272 return;
273 end if;
275 -- Case of zero/non-zero semantics or non-standard enumeration
276 -- representation. In each case, we rewrite the node as:
278 -- ityp!(N) /= False'Enum_Rep
280 -- where ityp is an integer type with large enough size to hold any
281 -- value of type T.
283 if Nonzero_Is_True (T) or else Has_Non_Standard_Rep (T) then
284 if Esize (T) <= Esize (Standard_Integer) then
285 Ti := Standard_Integer;
286 else
287 Ti := Standard_Long_Long_Integer;
288 end if;
290 Rewrite (N,
291 Make_Op_Ne (Loc,
292 Left_Opnd => Unchecked_Convert_To (Ti, N),
293 Right_Opnd =>
294 Make_Attribute_Reference (Loc,
295 Attribute_Name => Name_Enum_Rep,
296 Prefix =>
297 New_Occurrence_Of (First_Literal (T), Loc))));
298 Analyze_And_Resolve (N, Standard_Boolean);
300 else
301 Rewrite (N, Convert_To (Standard_Boolean, N));
302 Analyze_And_Resolve (N, Standard_Boolean);
303 end if;
304 end;
305 end Adjust_Condition;
307 ------------------------
308 -- Adjust_Result_Type --
309 ------------------------
311 procedure Adjust_Result_Type (N : Node_Id; T : Entity_Id) is
312 begin
313 -- Ignore call if current type is not Standard.Boolean
315 if Etype (N) /= Standard_Boolean then
316 return;
317 end if;
319 -- If result is already of correct type, nothing to do. Note that
320 -- this will get the most common case where everything has a type
321 -- of Standard.Boolean.
323 if Base_Type (T) = Standard_Boolean then
324 return;
326 else
327 declare
328 KP : constant Node_Kind := Nkind (Parent (N));
330 begin
331 -- If result is to be used as a Condition in the syntax, no need
332 -- to convert it back, since if it was changed to Standard.Boolean
333 -- using Adjust_Condition, that is just fine for this usage.
335 if KP in N_Raise_xxx_Error or else KP in N_Has_Condition then
336 return;
338 -- If result is an operand of another logical operation, no need
339 -- to reset its type, since Standard.Boolean is just fine, and
340 -- such operations always do Adjust_Condition on their operands.
342 elsif KP in N_Op_Boolean
343 or else KP in N_Short_Circuit
344 or else KP = N_Op_Not
345 then
346 return;
348 -- Otherwise we perform a conversion from the current type, which
349 -- must be Standard.Boolean, to the desired type.
351 else
352 Set_Analyzed (N);
353 Rewrite (N, Convert_To (T, N));
354 Analyze_And_Resolve (N, T);
355 end if;
356 end;
357 end if;
358 end Adjust_Result_Type;
360 --------------------------
361 -- Append_Freeze_Action --
362 --------------------------
364 procedure Append_Freeze_Action (T : Entity_Id; N : Node_Id) is
365 Fnode : Node_Id;
367 begin
368 Ensure_Freeze_Node (T);
369 Fnode := Freeze_Node (T);
371 if No (Actions (Fnode)) then
372 Set_Actions (Fnode, New_List (N));
373 else
374 Append (N, Actions (Fnode));
375 end if;
377 end Append_Freeze_Action;
379 ---------------------------
380 -- Append_Freeze_Actions --
381 ---------------------------
383 procedure Append_Freeze_Actions (T : Entity_Id; L : List_Id) is
384 Fnode : Node_Id;
386 begin
387 if No (L) then
388 return;
389 end if;
391 Ensure_Freeze_Node (T);
392 Fnode := Freeze_Node (T);
394 if No (Actions (Fnode)) then
395 Set_Actions (Fnode, L);
396 else
397 Append_List (L, Actions (Fnode));
398 end if;
399 end Append_Freeze_Actions;
401 ------------------------------------
402 -- Build_Allocate_Deallocate_Proc --
403 ------------------------------------
405 procedure Build_Allocate_Deallocate_Proc
406 (N : Node_Id;
407 Is_Allocate : Boolean)
409 Desig_Typ : Entity_Id;
410 Expr : Node_Id;
411 Pool_Id : Entity_Id;
412 Proc_To_Call : Node_Id := Empty;
413 Ptr_Typ : Entity_Id;
415 function Find_Finalize_Address (Typ : Entity_Id) return Entity_Id;
416 -- Locate TSS primitive Finalize_Address in type Typ
418 function Find_Object (E : Node_Id) return Node_Id;
419 -- Given an arbitrary expression of an allocator, try to find an object
420 -- reference in it, otherwise return the original expression.
422 function Is_Allocate_Deallocate_Proc (Subp : Entity_Id) return Boolean;
423 -- Determine whether subprogram Subp denotes a custom allocate or
424 -- deallocate.
426 ---------------------------
427 -- Find_Finalize_Address --
428 ---------------------------
430 function Find_Finalize_Address (Typ : Entity_Id) return Entity_Id is
431 Utyp : Entity_Id := Typ;
433 begin
434 -- Handle protected class-wide or task class-wide types
436 if Is_Class_Wide_Type (Utyp) then
437 if Is_Concurrent_Type (Root_Type (Utyp)) then
438 Utyp := Root_Type (Utyp);
440 elsif Is_Private_Type (Root_Type (Utyp))
441 and then Present (Full_View (Root_Type (Utyp)))
442 and then Is_Concurrent_Type (Full_View (Root_Type (Utyp)))
443 then
444 Utyp := Full_View (Root_Type (Utyp));
445 end if;
446 end if;
448 -- Handle private types
450 if Is_Private_Type (Utyp) and then Present (Full_View (Utyp)) then
451 Utyp := Full_View (Utyp);
452 end if;
454 -- Handle protected and task types
456 if Is_Concurrent_Type (Utyp)
457 and then Present (Corresponding_Record_Type (Utyp))
458 then
459 Utyp := Corresponding_Record_Type (Utyp);
460 end if;
462 Utyp := Underlying_Type (Base_Type (Utyp));
464 -- Deal with untagged derivation of private views. If the parent is
465 -- now known to be protected, the finalization routine is the one
466 -- defined on the corresponding record of the ancestor (corresponding
467 -- records do not automatically inherit operations, but maybe they
468 -- should???)
470 if Is_Untagged_Derivation (Typ) then
471 if Is_Protected_Type (Typ) then
472 Utyp := Corresponding_Record_Type (Root_Type (Base_Type (Typ)));
473 else
474 Utyp := Underlying_Type (Root_Type (Base_Type (Typ)));
476 if Is_Protected_Type (Utyp) then
477 Utyp := Corresponding_Record_Type (Utyp);
478 end if;
479 end if;
480 end if;
482 -- If the underlying_type is a subtype, we are dealing with the
483 -- completion of a private type. We need to access the base type and
484 -- generate a conversion to it.
486 if Utyp /= Base_Type (Utyp) then
487 pragma Assert (Is_Private_Type (Typ));
489 Utyp := Base_Type (Utyp);
490 end if;
492 -- When dealing with an internally built full view for a type with
493 -- unknown discriminants, use the original record type.
495 if Is_Underlying_Record_View (Utyp) then
496 Utyp := Etype (Utyp);
497 end if;
499 return TSS (Utyp, TSS_Finalize_Address);
500 end Find_Finalize_Address;
502 -----------------
503 -- Find_Object --
504 -----------------
506 function Find_Object (E : Node_Id) return Node_Id is
507 Expr : Node_Id;
509 begin
510 pragma Assert (Is_Allocate);
512 Expr := E;
513 loop
514 if Nkind (Expr) = N_Explicit_Dereference then
515 Expr := Prefix (Expr);
517 elsif Nkind (Expr) = N_Qualified_Expression then
518 Expr := Expression (Expr);
520 elsif Nkind (Expr) = N_Unchecked_Type_Conversion then
522 -- When interface class-wide types are involved in allocation,
523 -- the expander introduces several levels of address arithmetic
524 -- to perform dispatch table displacement. In this scenario the
525 -- object appears as:
527 -- Tag_Ptr (Base_Address (<object>'Address))
529 -- Detect this case and utilize the whole expression as the
530 -- "object" since it now points to the proper dispatch table.
532 if Is_RTE (Etype (Expr), RE_Tag_Ptr) then
533 exit;
535 -- Continue to strip the object
537 else
538 Expr := Expression (Expr);
539 end if;
541 else
542 exit;
543 end if;
544 end loop;
546 return Expr;
547 end Find_Object;
549 ---------------------------------
550 -- Is_Allocate_Deallocate_Proc --
551 ---------------------------------
553 function Is_Allocate_Deallocate_Proc (Subp : Entity_Id) return Boolean is
554 begin
555 -- Look for a subprogram body with only one statement which is a
556 -- call to Allocate_Any_Controlled / Deallocate_Any_Controlled.
558 if Ekind (Subp) = E_Procedure
559 and then Nkind (Parent (Parent (Subp))) = N_Subprogram_Body
560 then
561 declare
562 HSS : constant Node_Id :=
563 Handled_Statement_Sequence (Parent (Parent (Subp)));
564 Proc : Entity_Id;
566 begin
567 if Present (Statements (HSS))
568 and then Nkind (First (Statements (HSS))) =
569 N_Procedure_Call_Statement
570 then
571 Proc := Entity (Name (First (Statements (HSS))));
573 return
574 Is_RTE (Proc, RE_Allocate_Any_Controlled)
575 or else Is_RTE (Proc, RE_Deallocate_Any_Controlled);
576 end if;
577 end;
578 end if;
580 return False;
581 end Is_Allocate_Deallocate_Proc;
583 -- Start of processing for Build_Allocate_Deallocate_Proc
585 begin
586 -- Obtain the attributes of the allocation / deallocation
588 if Nkind (N) = N_Free_Statement then
589 Expr := Expression (N);
590 Ptr_Typ := Base_Type (Etype (Expr));
591 Proc_To_Call := Procedure_To_Call (N);
593 else
594 if Nkind (N) = N_Object_Declaration then
595 Expr := Expression (N);
596 else
597 Expr := N;
598 end if;
600 -- In certain cases an allocator with a qualified expression may
601 -- be relocated and used as the initialization expression of a
602 -- temporary:
604 -- before:
605 -- Obj : Ptr_Typ := new Desig_Typ'(...);
607 -- after:
608 -- Tmp : Ptr_Typ := new Desig_Typ'(...);
609 -- Obj : Ptr_Typ := Tmp;
611 -- Since the allocator is always marked as analyzed to avoid infinite
612 -- expansion, it will never be processed by this routine given that
613 -- the designated type needs finalization actions. Detect this case
614 -- and complete the expansion of the allocator.
616 if Nkind (Expr) = N_Identifier
617 and then Nkind (Parent (Entity (Expr))) = N_Object_Declaration
618 and then Nkind (Expression (Parent (Entity (Expr)))) = N_Allocator
619 then
620 Build_Allocate_Deallocate_Proc (Parent (Entity (Expr)), True);
621 return;
622 end if;
624 -- The allocator may have been rewritten into something else in which
625 -- case the expansion performed by this routine does not apply.
627 if Nkind (Expr) /= N_Allocator then
628 return;
629 end if;
631 Ptr_Typ := Base_Type (Etype (Expr));
632 Proc_To_Call := Procedure_To_Call (Expr);
633 end if;
635 Pool_Id := Associated_Storage_Pool (Ptr_Typ);
636 Desig_Typ := Available_View (Designated_Type (Ptr_Typ));
638 -- Handle concurrent types
640 if Is_Concurrent_Type (Desig_Typ)
641 and then Present (Corresponding_Record_Type (Desig_Typ))
642 then
643 Desig_Typ := Corresponding_Record_Type (Desig_Typ);
644 end if;
646 -- Do not process allocations / deallocations without a pool
648 if No (Pool_Id) then
649 return;
651 -- Do not process allocations on / deallocations from the secondary
652 -- stack.
654 elsif Is_RTE (Pool_Id, RE_SS_Pool) then
655 return;
657 -- Do not replicate the machinery if the allocator / free has already
658 -- been expanded and has a custom Allocate / Deallocate.
660 elsif Present (Proc_To_Call)
661 and then Is_Allocate_Deallocate_Proc (Proc_To_Call)
662 then
663 return;
664 end if;
666 if Needs_Finalization (Desig_Typ) then
668 -- Certain run-time configurations and targets do not provide support
669 -- for controlled types.
671 if Restriction_Active (No_Finalization) then
672 return;
674 -- Do nothing if the access type may never allocate / deallocate
675 -- objects.
677 elsif No_Pool_Assigned (Ptr_Typ) then
678 return;
680 -- Access-to-controlled types are not supported on .NET/JVM since
681 -- these targets cannot support pools and address arithmetic.
683 elsif VM_Target /= No_VM then
684 return;
685 end if;
687 -- The allocation / deallocation of a controlled object must be
688 -- chained on / detached from a finalization master.
690 pragma Assert (Present (Finalization_Master (Ptr_Typ)));
692 -- The only other kind of allocation / deallocation supported by this
693 -- routine is on / from a subpool.
695 elsif Nkind (Expr) = N_Allocator
696 and then No (Subpool_Handle_Name (Expr))
697 then
698 return;
699 end if;
701 declare
702 Loc : constant Source_Ptr := Sloc (N);
703 Addr_Id : constant Entity_Id := Make_Temporary (Loc, 'A');
704 Alig_Id : constant Entity_Id := Make_Temporary (Loc, 'L');
705 Proc_Id : constant Entity_Id := Make_Temporary (Loc, 'P');
706 Size_Id : constant Entity_Id := Make_Temporary (Loc, 'S');
708 Actuals : List_Id;
709 Fin_Addr_Id : Entity_Id;
710 Fin_Mas_Act : Node_Id;
711 Fin_Mas_Id : Entity_Id;
712 Proc_To_Call : Entity_Id;
713 Subpool : Node_Id := Empty;
715 begin
716 -- Step 1: Construct all the actuals for the call to library routine
717 -- Allocate_Any_Controlled / Deallocate_Any_Controlled.
719 -- a) Storage pool
721 Actuals := New_List (New_Occurrence_Of (Pool_Id, Loc));
723 if Is_Allocate then
725 -- b) Subpool
727 if Nkind (Expr) = N_Allocator then
728 Subpool := Subpool_Handle_Name (Expr);
729 end if;
731 -- If a subpool is present it can be an arbitrary name, so make
732 -- the actual by copying the tree.
734 if Present (Subpool) then
735 Append_To (Actuals, New_Copy_Tree (Subpool, New_Sloc => Loc));
736 else
737 Append_To (Actuals, Make_Null (Loc));
738 end if;
740 -- c) Finalization master
742 if Needs_Finalization (Desig_Typ) then
743 Fin_Mas_Id := Finalization_Master (Ptr_Typ);
744 Fin_Mas_Act := New_Occurrence_Of (Fin_Mas_Id, Loc);
746 -- Handle the case where the master is actually a pointer to a
747 -- master. This case arises in build-in-place functions.
749 if Is_Access_Type (Etype (Fin_Mas_Id)) then
750 Append_To (Actuals, Fin_Mas_Act);
751 else
752 Append_To (Actuals,
753 Make_Attribute_Reference (Loc,
754 Prefix => Fin_Mas_Act,
755 Attribute_Name => Name_Unrestricted_Access));
756 end if;
757 else
758 Append_To (Actuals, Make_Null (Loc));
759 end if;
761 -- d) Finalize_Address
763 -- Primitive Finalize_Address is never generated in CodePeer mode
764 -- since it contains an Unchecked_Conversion.
766 if Needs_Finalization (Desig_Typ) and then not CodePeer_Mode then
767 Fin_Addr_Id := Find_Finalize_Address (Desig_Typ);
768 pragma Assert (Present (Fin_Addr_Id));
770 Append_To (Actuals,
771 Make_Attribute_Reference (Loc,
772 Prefix => New_Occurrence_Of (Fin_Addr_Id, Loc),
773 Attribute_Name => Name_Unrestricted_Access));
774 else
775 Append_To (Actuals, Make_Null (Loc));
776 end if;
777 end if;
779 -- e) Address
780 -- f) Storage_Size
781 -- g) Alignment
783 Append_To (Actuals, New_Occurrence_Of (Addr_Id, Loc));
784 Append_To (Actuals, New_Occurrence_Of (Size_Id, Loc));
786 if Is_Allocate or else not Is_Class_Wide_Type (Desig_Typ) then
787 Append_To (Actuals, New_Occurrence_Of (Alig_Id, Loc));
789 -- For deallocation of class-wide types we obtain the value of
790 -- alignment from the Type Specific Record of the deallocated object.
791 -- This is needed because the frontend expansion of class-wide types
792 -- into equivalent types confuses the backend.
794 else
795 -- Generate:
796 -- Obj.all'Alignment
798 -- ... because 'Alignment applied to class-wide types is expanded
799 -- into the code that reads the value of alignment from the TSD
800 -- (see Expand_N_Attribute_Reference)
802 Append_To (Actuals,
803 Unchecked_Convert_To (RTE (RE_Storage_Offset),
804 Make_Attribute_Reference (Loc,
805 Prefix =>
806 Make_Explicit_Dereference (Loc, Relocate_Node (Expr)),
807 Attribute_Name => Name_Alignment)));
808 end if;
810 -- h) Is_Controlled
812 if Needs_Finalization (Desig_Typ) then
813 declare
814 Flag_Id : constant Entity_Id := Make_Temporary (Loc, 'F');
815 Flag_Expr : Node_Id;
816 Param : Node_Id;
817 Temp : Node_Id;
819 begin
820 if Is_Allocate then
821 Temp := Find_Object (Expression (Expr));
822 else
823 Temp := Expr;
824 end if;
826 -- Processing for allocations where the expression is a subtype
827 -- indication.
829 if Is_Allocate
830 and then Is_Entity_Name (Temp)
831 and then Is_Type (Entity (Temp))
832 then
833 Flag_Expr :=
834 New_Occurrence_Of
835 (Boolean_Literals
836 (Needs_Finalization (Entity (Temp))), Loc);
838 -- The allocation / deallocation of a class-wide object relies
839 -- on a runtime check to determine whether the object is truly
840 -- controlled or not. Depending on this check, the finalization
841 -- machinery will request or reclaim extra storage reserved for
842 -- a list header.
844 elsif Is_Class_Wide_Type (Desig_Typ) then
846 -- Detect a special case where interface class-wide types
847 -- are involved as the object appears as:
849 -- Tag_Ptr (Base_Address (<object>'Address))
851 -- The expression already yields the proper tag, generate:
853 -- Temp.all
855 if Is_RTE (Etype (Temp), RE_Tag_Ptr) then
856 Param :=
857 Make_Explicit_Dereference (Loc,
858 Prefix => Relocate_Node (Temp));
860 -- In the default case, obtain the tag of the object about
861 -- to be allocated / deallocated. Generate:
863 -- Temp'Tag
865 else
866 Param :=
867 Make_Attribute_Reference (Loc,
868 Prefix => Relocate_Node (Temp),
869 Attribute_Name => Name_Tag);
870 end if;
872 -- Generate:
873 -- Needs_Finalization (<Param>)
875 Flag_Expr :=
876 Make_Function_Call (Loc,
877 Name =>
878 New_Occurrence_Of (RTE (RE_Needs_Finalization), Loc),
879 Parameter_Associations => New_List (Param));
881 -- Processing for generic actuals
883 elsif Is_Generic_Actual_Type (Desig_Typ) then
884 Flag_Expr :=
885 New_Occurrence_Of (Boolean_Literals
886 (Needs_Finalization (Base_Type (Desig_Typ))), Loc);
888 -- The object does not require any specialized checks, it is
889 -- known to be controlled.
891 else
892 Flag_Expr := New_Occurrence_Of (Standard_True, Loc);
893 end if;
895 -- Create the temporary which represents the finalization state
896 -- of the expression. Generate:
898 -- F : constant Boolean := <Flag_Expr>;
900 Insert_Action (N,
901 Make_Object_Declaration (Loc,
902 Defining_Identifier => Flag_Id,
903 Constant_Present => True,
904 Object_Definition =>
905 New_Occurrence_Of (Standard_Boolean, Loc),
906 Expression => Flag_Expr));
908 Append_To (Actuals, New_Occurrence_Of (Flag_Id, Loc));
909 end;
911 -- The object is not controlled
913 else
914 Append_To (Actuals, New_Occurrence_Of (Standard_False, Loc));
915 end if;
917 -- i) On_Subpool
919 if Is_Allocate then
920 Append_To (Actuals,
921 New_Occurrence_Of (Boolean_Literals (Present (Subpool)), Loc));
922 end if;
924 -- Step 2: Build a wrapper Allocate / Deallocate which internally
925 -- calls Allocate_Any_Controlled / Deallocate_Any_Controlled.
927 -- Select the proper routine to call
929 if Is_Allocate then
930 Proc_To_Call := RTE (RE_Allocate_Any_Controlled);
931 else
932 Proc_To_Call := RTE (RE_Deallocate_Any_Controlled);
933 end if;
935 -- Create a custom Allocate / Deallocate routine which has identical
936 -- profile to that of System.Storage_Pools.
938 Insert_Action (N,
939 Make_Subprogram_Body (Loc,
940 Specification =>
942 -- procedure Pnn
944 Make_Procedure_Specification (Loc,
945 Defining_Unit_Name => Proc_Id,
946 Parameter_Specifications => New_List (
948 -- P : Root_Storage_Pool
950 Make_Parameter_Specification (Loc,
951 Defining_Identifier => Make_Temporary (Loc, 'P'),
952 Parameter_Type =>
953 New_Occurrence_Of (RTE (RE_Root_Storage_Pool), Loc)),
955 -- A : [out] Address
957 Make_Parameter_Specification (Loc,
958 Defining_Identifier => Addr_Id,
959 Out_Present => Is_Allocate,
960 Parameter_Type =>
961 New_Occurrence_Of (RTE (RE_Address), Loc)),
963 -- S : Storage_Count
965 Make_Parameter_Specification (Loc,
966 Defining_Identifier => Size_Id,
967 Parameter_Type =>
968 New_Occurrence_Of (RTE (RE_Storage_Count), Loc)),
970 -- L : Storage_Count
972 Make_Parameter_Specification (Loc,
973 Defining_Identifier => Alig_Id,
974 Parameter_Type =>
975 New_Occurrence_Of (RTE (RE_Storage_Count), Loc)))),
977 Declarations => No_List,
979 Handled_Statement_Sequence =>
980 Make_Handled_Sequence_Of_Statements (Loc,
981 Statements => New_List (
982 Make_Procedure_Call_Statement (Loc,
983 Name => New_Occurrence_Of (Proc_To_Call, Loc),
984 Parameter_Associations => Actuals)))));
986 -- The newly generated Allocate / Deallocate becomes the default
987 -- procedure to call when the back end processes the allocation /
988 -- deallocation.
990 if Is_Allocate then
991 Set_Procedure_To_Call (Expr, Proc_Id);
992 else
993 Set_Procedure_To_Call (N, Proc_Id);
994 end if;
995 end;
996 end Build_Allocate_Deallocate_Proc;
998 ------------------------
999 -- Build_Runtime_Call --
1000 ------------------------
1002 function Build_Runtime_Call (Loc : Source_Ptr; RE : RE_Id) return Node_Id is
1003 begin
1004 -- If entity is not available, we can skip making the call (this avoids
1005 -- junk duplicated error messages in a number of cases).
1007 if not RTE_Available (RE) then
1008 return Make_Null_Statement (Loc);
1009 else
1010 return
1011 Make_Procedure_Call_Statement (Loc,
1012 Name => New_Occurrence_Of (RTE (RE), Loc));
1013 end if;
1014 end Build_Runtime_Call;
1016 ------------------------
1017 -- Build_SS_Mark_Call --
1018 ------------------------
1020 function Build_SS_Mark_Call
1021 (Loc : Source_Ptr;
1022 Mark : Entity_Id) return Node_Id
1024 begin
1025 -- Generate:
1026 -- Mark : constant Mark_Id := SS_Mark;
1028 return
1029 Make_Object_Declaration (Loc,
1030 Defining_Identifier => Mark,
1031 Constant_Present => True,
1032 Object_Definition =>
1033 New_Occurrence_Of (RTE (RE_Mark_Id), Loc),
1034 Expression =>
1035 Make_Function_Call (Loc,
1036 Name => New_Occurrence_Of (RTE (RE_SS_Mark), Loc)));
1037 end Build_SS_Mark_Call;
1039 ---------------------------
1040 -- Build_SS_Release_Call --
1041 ---------------------------
1043 function Build_SS_Release_Call
1044 (Loc : Source_Ptr;
1045 Mark : Entity_Id) return Node_Id
1047 begin
1048 -- Generate:
1049 -- SS_Release (Mark);
1051 return
1052 Make_Procedure_Call_Statement (Loc,
1053 Name =>
1054 New_Occurrence_Of (RTE (RE_SS_Release), Loc),
1055 Parameter_Associations => New_List (
1056 New_Occurrence_Of (Mark, Loc)));
1057 end Build_SS_Release_Call;
1059 ----------------------------
1060 -- Build_Task_Array_Image --
1061 ----------------------------
1063 -- This function generates the body for a function that constructs the
1064 -- image string for a task that is an array component. The function is
1065 -- local to the init proc for the array type, and is called for each one
1066 -- of the components. The constructed image has the form of an indexed
1067 -- component, whose prefix is the outer variable of the array type.
1068 -- The n-dimensional array type has known indexes Index, Index2...
1070 -- Id_Ref is an indexed component form created by the enclosing init proc.
1071 -- Its successive indexes are Val1, Val2, ... which are the loop variables
1072 -- in the loops that call the individual task init proc on each component.
1074 -- The generated function has the following structure:
1076 -- function F return String is
1077 -- Pref : string renames Task_Name;
1078 -- T1 : String := Index1'Image (Val1);
1079 -- ...
1080 -- Tn : String := indexn'image (Valn);
1081 -- Len : Integer := T1'Length + ... + Tn'Length + n + 1;
1082 -- -- Len includes commas and the end parentheses.
1083 -- Res : String (1..Len);
1084 -- Pos : Integer := Pref'Length;
1086 -- begin
1087 -- Res (1 .. Pos) := Pref;
1088 -- Pos := Pos + 1;
1089 -- Res (Pos) := '(';
1090 -- Pos := Pos + 1;
1091 -- Res (Pos .. Pos + T1'Length - 1) := T1;
1092 -- Pos := Pos + T1'Length;
1093 -- Res (Pos) := '.';
1094 -- Pos := Pos + 1;
1095 -- ...
1096 -- Res (Pos .. Pos + Tn'Length - 1) := Tn;
1097 -- Res (Len) := ')';
1099 -- return Res;
1100 -- end F;
1102 -- Needless to say, multidimensional arrays of tasks are rare enough that
1103 -- the bulkiness of this code is not really a concern.
1105 function Build_Task_Array_Image
1106 (Loc : Source_Ptr;
1107 Id_Ref : Node_Id;
1108 A_Type : Entity_Id;
1109 Dyn : Boolean := False) return Node_Id
1111 Dims : constant Nat := Number_Dimensions (A_Type);
1112 -- Number of dimensions for array of tasks
1114 Temps : array (1 .. Dims) of Entity_Id;
1115 -- Array of temporaries to hold string for each index
1117 Indx : Node_Id;
1118 -- Index expression
1120 Len : Entity_Id;
1121 -- Total length of generated name
1123 Pos : Entity_Id;
1124 -- Running index for substring assignments
1126 Pref : constant Entity_Id := Make_Temporary (Loc, 'P');
1127 -- Name of enclosing variable, prefix of resulting name
1129 Res : Entity_Id;
1130 -- String to hold result
1132 Val : Node_Id;
1133 -- Value of successive indexes
1135 Sum : Node_Id;
1136 -- Expression to compute total size of string
1138 T : Entity_Id;
1139 -- Entity for name at one index position
1141 Decls : constant List_Id := New_List;
1142 Stats : constant List_Id := New_List;
1144 begin
1145 -- For a dynamic task, the name comes from the target variable. For a
1146 -- static one it is a formal of the enclosing init proc.
1148 if Dyn then
1149 Get_Name_String (Chars (Entity (Prefix (Id_Ref))));
1150 Append_To (Decls,
1151 Make_Object_Declaration (Loc,
1152 Defining_Identifier => Pref,
1153 Object_Definition => New_Occurrence_Of (Standard_String, Loc),
1154 Expression =>
1155 Make_String_Literal (Loc,
1156 Strval => String_From_Name_Buffer)));
1158 else
1159 Append_To (Decls,
1160 Make_Object_Renaming_Declaration (Loc,
1161 Defining_Identifier => Pref,
1162 Subtype_Mark => New_Occurrence_Of (Standard_String, Loc),
1163 Name => Make_Identifier (Loc, Name_uTask_Name)));
1164 end if;
1166 Indx := First_Index (A_Type);
1167 Val := First (Expressions (Id_Ref));
1169 for J in 1 .. Dims loop
1170 T := Make_Temporary (Loc, 'T');
1171 Temps (J) := T;
1173 Append_To (Decls,
1174 Make_Object_Declaration (Loc,
1175 Defining_Identifier => T,
1176 Object_Definition => New_Occurrence_Of (Standard_String, Loc),
1177 Expression =>
1178 Make_Attribute_Reference (Loc,
1179 Attribute_Name => Name_Image,
1180 Prefix => New_Occurrence_Of (Etype (Indx), Loc),
1181 Expressions => New_List (New_Copy_Tree (Val)))));
1183 Next_Index (Indx);
1184 Next (Val);
1185 end loop;
1187 Sum := Make_Integer_Literal (Loc, Dims + 1);
1189 Sum :=
1190 Make_Op_Add (Loc,
1191 Left_Opnd => Sum,
1192 Right_Opnd =>
1193 Make_Attribute_Reference (Loc,
1194 Attribute_Name => Name_Length,
1195 Prefix => New_Occurrence_Of (Pref, Loc),
1196 Expressions => New_List (Make_Integer_Literal (Loc, 1))));
1198 for J in 1 .. Dims loop
1199 Sum :=
1200 Make_Op_Add (Loc,
1201 Left_Opnd => Sum,
1202 Right_Opnd =>
1203 Make_Attribute_Reference (Loc,
1204 Attribute_Name => Name_Length,
1205 Prefix =>
1206 New_Occurrence_Of (Temps (J), Loc),
1207 Expressions => New_List (Make_Integer_Literal (Loc, 1))));
1208 end loop;
1210 Build_Task_Image_Prefix (Loc, Len, Res, Pos, Pref, Sum, Decls, Stats);
1212 Set_Character_Literal_Name (Char_Code (Character'Pos ('(')));
1214 Append_To (Stats,
1215 Make_Assignment_Statement (Loc,
1216 Name =>
1217 Make_Indexed_Component (Loc,
1218 Prefix => New_Occurrence_Of (Res, Loc),
1219 Expressions => New_List (New_Occurrence_Of (Pos, Loc))),
1220 Expression =>
1221 Make_Character_Literal (Loc,
1222 Chars => Name_Find,
1223 Char_Literal_Value => UI_From_Int (Character'Pos ('(')))));
1225 Append_To (Stats,
1226 Make_Assignment_Statement (Loc,
1227 Name => New_Occurrence_Of (Pos, Loc),
1228 Expression =>
1229 Make_Op_Add (Loc,
1230 Left_Opnd => New_Occurrence_Of (Pos, Loc),
1231 Right_Opnd => Make_Integer_Literal (Loc, 1))));
1233 for J in 1 .. Dims loop
1235 Append_To (Stats,
1236 Make_Assignment_Statement (Loc,
1237 Name =>
1238 Make_Slice (Loc,
1239 Prefix => New_Occurrence_Of (Res, Loc),
1240 Discrete_Range =>
1241 Make_Range (Loc,
1242 Low_Bound => New_Occurrence_Of (Pos, Loc),
1243 High_Bound =>
1244 Make_Op_Subtract (Loc,
1245 Left_Opnd =>
1246 Make_Op_Add (Loc,
1247 Left_Opnd => New_Occurrence_Of (Pos, Loc),
1248 Right_Opnd =>
1249 Make_Attribute_Reference (Loc,
1250 Attribute_Name => Name_Length,
1251 Prefix =>
1252 New_Occurrence_Of (Temps (J), Loc),
1253 Expressions =>
1254 New_List (Make_Integer_Literal (Loc, 1)))),
1255 Right_Opnd => Make_Integer_Literal (Loc, 1)))),
1257 Expression => New_Occurrence_Of (Temps (J), Loc)));
1259 if J < Dims then
1260 Append_To (Stats,
1261 Make_Assignment_Statement (Loc,
1262 Name => New_Occurrence_Of (Pos, Loc),
1263 Expression =>
1264 Make_Op_Add (Loc,
1265 Left_Opnd => New_Occurrence_Of (Pos, Loc),
1266 Right_Opnd =>
1267 Make_Attribute_Reference (Loc,
1268 Attribute_Name => Name_Length,
1269 Prefix => New_Occurrence_Of (Temps (J), Loc),
1270 Expressions =>
1271 New_List (Make_Integer_Literal (Loc, 1))))));
1273 Set_Character_Literal_Name (Char_Code (Character'Pos (',')));
1275 Append_To (Stats,
1276 Make_Assignment_Statement (Loc,
1277 Name => Make_Indexed_Component (Loc,
1278 Prefix => New_Occurrence_Of (Res, Loc),
1279 Expressions => New_List (New_Occurrence_Of (Pos, Loc))),
1280 Expression =>
1281 Make_Character_Literal (Loc,
1282 Chars => Name_Find,
1283 Char_Literal_Value => UI_From_Int (Character'Pos (',')))));
1285 Append_To (Stats,
1286 Make_Assignment_Statement (Loc,
1287 Name => New_Occurrence_Of (Pos, Loc),
1288 Expression =>
1289 Make_Op_Add (Loc,
1290 Left_Opnd => New_Occurrence_Of (Pos, Loc),
1291 Right_Opnd => Make_Integer_Literal (Loc, 1))));
1292 end if;
1293 end loop;
1295 Set_Character_Literal_Name (Char_Code (Character'Pos (')')));
1297 Append_To (Stats,
1298 Make_Assignment_Statement (Loc,
1299 Name =>
1300 Make_Indexed_Component (Loc,
1301 Prefix => New_Occurrence_Of (Res, Loc),
1302 Expressions => New_List (New_Occurrence_Of (Len, Loc))),
1303 Expression =>
1304 Make_Character_Literal (Loc,
1305 Chars => Name_Find,
1306 Char_Literal_Value => UI_From_Int (Character'Pos (')')))));
1307 return Build_Task_Image_Function (Loc, Decls, Stats, Res);
1308 end Build_Task_Array_Image;
1310 ----------------------------
1311 -- Build_Task_Image_Decls --
1312 ----------------------------
1314 function Build_Task_Image_Decls
1315 (Loc : Source_Ptr;
1316 Id_Ref : Node_Id;
1317 A_Type : Entity_Id;
1318 In_Init_Proc : Boolean := False) return List_Id
1320 Decls : constant List_Id := New_List;
1321 T_Id : Entity_Id := Empty;
1322 Decl : Node_Id;
1323 Expr : Node_Id := Empty;
1324 Fun : Node_Id := Empty;
1325 Is_Dyn : constant Boolean :=
1326 Nkind (Parent (Id_Ref)) = N_Assignment_Statement
1327 and then
1328 Nkind (Expression (Parent (Id_Ref))) = N_Allocator;
1330 begin
1331 -- If Discard_Names or No_Implicit_Heap_Allocations are in effect,
1332 -- generate a dummy declaration only.
1334 if Restriction_Active (No_Implicit_Heap_Allocations)
1335 or else Global_Discard_Names
1336 then
1337 T_Id := Make_Temporary (Loc, 'J');
1338 Name_Len := 0;
1340 return
1341 New_List (
1342 Make_Object_Declaration (Loc,
1343 Defining_Identifier => T_Id,
1344 Object_Definition => New_Occurrence_Of (Standard_String, Loc),
1345 Expression =>
1346 Make_String_Literal (Loc,
1347 Strval => String_From_Name_Buffer)));
1349 else
1350 if Nkind (Id_Ref) = N_Identifier
1351 or else Nkind (Id_Ref) = N_Defining_Identifier
1352 then
1353 -- For a simple variable, the image of the task is built from
1354 -- the name of the variable. To avoid possible conflict with the
1355 -- anonymous type created for a single protected object, add a
1356 -- numeric suffix.
1358 T_Id :=
1359 Make_Defining_Identifier (Loc,
1360 New_External_Name (Chars (Id_Ref), 'T', 1));
1362 Get_Name_String (Chars (Id_Ref));
1364 Expr :=
1365 Make_String_Literal (Loc,
1366 Strval => String_From_Name_Buffer);
1368 elsif Nkind (Id_Ref) = N_Selected_Component then
1369 T_Id :=
1370 Make_Defining_Identifier (Loc,
1371 New_External_Name (Chars (Selector_Name (Id_Ref)), 'T'));
1372 Fun := Build_Task_Record_Image (Loc, Id_Ref, Is_Dyn);
1374 elsif Nkind (Id_Ref) = N_Indexed_Component then
1375 T_Id :=
1376 Make_Defining_Identifier (Loc,
1377 New_External_Name (Chars (A_Type), 'N'));
1379 Fun := Build_Task_Array_Image (Loc, Id_Ref, A_Type, Is_Dyn);
1380 end if;
1381 end if;
1383 if Present (Fun) then
1384 Append (Fun, Decls);
1385 Expr := Make_Function_Call (Loc,
1386 Name => New_Occurrence_Of (Defining_Entity (Fun), Loc));
1388 if not In_Init_Proc and then VM_Target = No_VM then
1389 Set_Uses_Sec_Stack (Defining_Entity (Fun));
1390 end if;
1391 end if;
1393 Decl := Make_Object_Declaration (Loc,
1394 Defining_Identifier => T_Id,
1395 Object_Definition => New_Occurrence_Of (Standard_String, Loc),
1396 Constant_Present => True,
1397 Expression => Expr);
1399 Append (Decl, Decls);
1400 return Decls;
1401 end Build_Task_Image_Decls;
1403 -------------------------------
1404 -- Build_Task_Image_Function --
1405 -------------------------------
1407 function Build_Task_Image_Function
1408 (Loc : Source_Ptr;
1409 Decls : List_Id;
1410 Stats : List_Id;
1411 Res : Entity_Id) return Node_Id
1413 Spec : Node_Id;
1415 begin
1416 Append_To (Stats,
1417 Make_Simple_Return_Statement (Loc,
1418 Expression => New_Occurrence_Of (Res, Loc)));
1420 Spec := Make_Function_Specification (Loc,
1421 Defining_Unit_Name => Make_Temporary (Loc, 'F'),
1422 Result_Definition => New_Occurrence_Of (Standard_String, Loc));
1424 -- Calls to 'Image use the secondary stack, which must be cleaned up
1425 -- after the task name is built.
1427 return Make_Subprogram_Body (Loc,
1428 Specification => Spec,
1429 Declarations => Decls,
1430 Handled_Statement_Sequence =>
1431 Make_Handled_Sequence_Of_Statements (Loc, Statements => Stats));
1432 end Build_Task_Image_Function;
1434 -----------------------------
1435 -- Build_Task_Image_Prefix --
1436 -----------------------------
1438 procedure Build_Task_Image_Prefix
1439 (Loc : Source_Ptr;
1440 Len : out Entity_Id;
1441 Res : out Entity_Id;
1442 Pos : out Entity_Id;
1443 Prefix : Entity_Id;
1444 Sum : Node_Id;
1445 Decls : List_Id;
1446 Stats : List_Id)
1448 begin
1449 Len := Make_Temporary (Loc, 'L', Sum);
1451 Append_To (Decls,
1452 Make_Object_Declaration (Loc,
1453 Defining_Identifier => Len,
1454 Object_Definition => New_Occurrence_Of (Standard_Integer, Loc),
1455 Expression => Sum));
1457 Res := Make_Temporary (Loc, 'R');
1459 Append_To (Decls,
1460 Make_Object_Declaration (Loc,
1461 Defining_Identifier => Res,
1462 Object_Definition =>
1463 Make_Subtype_Indication (Loc,
1464 Subtype_Mark => New_Occurrence_Of (Standard_String, Loc),
1465 Constraint =>
1466 Make_Index_Or_Discriminant_Constraint (Loc,
1467 Constraints =>
1468 New_List (
1469 Make_Range (Loc,
1470 Low_Bound => Make_Integer_Literal (Loc, 1),
1471 High_Bound => New_Occurrence_Of (Len, Loc)))))));
1473 -- Indicate that the result is an internal temporary, so it does not
1474 -- receive a bogus initialization when declaration is expanded. This
1475 -- is both efficient, and prevents anomalies in the handling of
1476 -- dynamic objects on the secondary stack.
1478 Set_Is_Internal (Res);
1479 Pos := Make_Temporary (Loc, 'P');
1481 Append_To (Decls,
1482 Make_Object_Declaration (Loc,
1483 Defining_Identifier => Pos,
1484 Object_Definition => New_Occurrence_Of (Standard_Integer, Loc)));
1486 -- Pos := Prefix'Length;
1488 Append_To (Stats,
1489 Make_Assignment_Statement (Loc,
1490 Name => New_Occurrence_Of (Pos, Loc),
1491 Expression =>
1492 Make_Attribute_Reference (Loc,
1493 Attribute_Name => Name_Length,
1494 Prefix => New_Occurrence_Of (Prefix, Loc),
1495 Expressions => New_List (Make_Integer_Literal (Loc, 1)))));
1497 -- Res (1 .. Pos) := Prefix;
1499 Append_To (Stats,
1500 Make_Assignment_Statement (Loc,
1501 Name =>
1502 Make_Slice (Loc,
1503 Prefix => New_Occurrence_Of (Res, Loc),
1504 Discrete_Range =>
1505 Make_Range (Loc,
1506 Low_Bound => Make_Integer_Literal (Loc, 1),
1507 High_Bound => New_Occurrence_Of (Pos, Loc))),
1509 Expression => New_Occurrence_Of (Prefix, Loc)));
1511 Append_To (Stats,
1512 Make_Assignment_Statement (Loc,
1513 Name => New_Occurrence_Of (Pos, Loc),
1514 Expression =>
1515 Make_Op_Add (Loc,
1516 Left_Opnd => New_Occurrence_Of (Pos, Loc),
1517 Right_Opnd => Make_Integer_Literal (Loc, 1))));
1518 end Build_Task_Image_Prefix;
1520 -----------------------------
1521 -- Build_Task_Record_Image --
1522 -----------------------------
1524 function Build_Task_Record_Image
1525 (Loc : Source_Ptr;
1526 Id_Ref : Node_Id;
1527 Dyn : Boolean := False) return Node_Id
1529 Len : Entity_Id;
1530 -- Total length of generated name
1532 Pos : Entity_Id;
1533 -- Index into result
1535 Res : Entity_Id;
1536 -- String to hold result
1538 Pref : constant Entity_Id := Make_Temporary (Loc, 'P');
1539 -- Name of enclosing variable, prefix of resulting name
1541 Sum : Node_Id;
1542 -- Expression to compute total size of string
1544 Sel : Entity_Id;
1545 -- Entity for selector name
1547 Decls : constant List_Id := New_List;
1548 Stats : constant List_Id := New_List;
1550 begin
1551 -- For a dynamic task, the name comes from the target variable. For a
1552 -- static one it is a formal of the enclosing init proc.
1554 if Dyn then
1555 Get_Name_String (Chars (Entity (Prefix (Id_Ref))));
1556 Append_To (Decls,
1557 Make_Object_Declaration (Loc,
1558 Defining_Identifier => Pref,
1559 Object_Definition => New_Occurrence_Of (Standard_String, Loc),
1560 Expression =>
1561 Make_String_Literal (Loc,
1562 Strval => String_From_Name_Buffer)));
1564 else
1565 Append_To (Decls,
1566 Make_Object_Renaming_Declaration (Loc,
1567 Defining_Identifier => Pref,
1568 Subtype_Mark => New_Occurrence_Of (Standard_String, Loc),
1569 Name => Make_Identifier (Loc, Name_uTask_Name)));
1570 end if;
1572 Sel := Make_Temporary (Loc, 'S');
1574 Get_Name_String (Chars (Selector_Name (Id_Ref)));
1576 Append_To (Decls,
1577 Make_Object_Declaration (Loc,
1578 Defining_Identifier => Sel,
1579 Object_Definition => New_Occurrence_Of (Standard_String, Loc),
1580 Expression =>
1581 Make_String_Literal (Loc,
1582 Strval => String_From_Name_Buffer)));
1584 Sum := Make_Integer_Literal (Loc, Nat (Name_Len + 1));
1586 Sum :=
1587 Make_Op_Add (Loc,
1588 Left_Opnd => Sum,
1589 Right_Opnd =>
1590 Make_Attribute_Reference (Loc,
1591 Attribute_Name => Name_Length,
1592 Prefix =>
1593 New_Occurrence_Of (Pref, Loc),
1594 Expressions => New_List (Make_Integer_Literal (Loc, 1))));
1596 Build_Task_Image_Prefix (Loc, Len, Res, Pos, Pref, Sum, Decls, Stats);
1598 Set_Character_Literal_Name (Char_Code (Character'Pos ('.')));
1600 -- Res (Pos) := '.';
1602 Append_To (Stats,
1603 Make_Assignment_Statement (Loc,
1604 Name => Make_Indexed_Component (Loc,
1605 Prefix => New_Occurrence_Of (Res, Loc),
1606 Expressions => New_List (New_Occurrence_Of (Pos, Loc))),
1607 Expression =>
1608 Make_Character_Literal (Loc,
1609 Chars => Name_Find,
1610 Char_Literal_Value =>
1611 UI_From_Int (Character'Pos ('.')))));
1613 Append_To (Stats,
1614 Make_Assignment_Statement (Loc,
1615 Name => New_Occurrence_Of (Pos, Loc),
1616 Expression =>
1617 Make_Op_Add (Loc,
1618 Left_Opnd => New_Occurrence_Of (Pos, Loc),
1619 Right_Opnd => Make_Integer_Literal (Loc, 1))));
1621 -- Res (Pos .. Len) := Selector;
1623 Append_To (Stats,
1624 Make_Assignment_Statement (Loc,
1625 Name => Make_Slice (Loc,
1626 Prefix => New_Occurrence_Of (Res, Loc),
1627 Discrete_Range =>
1628 Make_Range (Loc,
1629 Low_Bound => New_Occurrence_Of (Pos, Loc),
1630 High_Bound => New_Occurrence_Of (Len, Loc))),
1631 Expression => New_Occurrence_Of (Sel, Loc)));
1633 return Build_Task_Image_Function (Loc, Decls, Stats, Res);
1634 end Build_Task_Record_Image;
1636 -----------------------------
1637 -- Check_Float_Op_Overflow --
1638 -----------------------------
1640 procedure Check_Float_Op_Overflow (N : Node_Id) is
1641 begin
1642 -- Return if no check needed
1644 if not Is_Floating_Point_Type (Etype (N))
1645 or else not (Do_Overflow_Check (N) and then Check_Float_Overflow)
1647 -- In CodePeer_Mode, rely on the overflow check flag being set instead
1648 -- and do not expand the code for float overflow checking.
1650 or else CodePeer_Mode
1651 then
1652 return;
1653 end if;
1655 -- Otherwise we replace the expression by
1657 -- do Tnn : constant ftype := expression;
1658 -- constraint_error when not Tnn'Valid;
1659 -- in Tnn;
1661 declare
1662 Loc : constant Source_Ptr := Sloc (N);
1663 Tnn : constant Entity_Id := Make_Temporary (Loc, 'T', N);
1664 Typ : constant Entity_Id := Etype (N);
1666 begin
1667 -- Turn off the Do_Overflow_Check flag, since we are doing that work
1668 -- right here. We also set the node as analyzed to prevent infinite
1669 -- recursion from repeating the operation in the expansion.
1671 Set_Do_Overflow_Check (N, False);
1672 Set_Analyzed (N, True);
1674 -- Do the rewrite to include the check
1676 Rewrite (N,
1677 Make_Expression_With_Actions (Loc,
1678 Actions => New_List (
1679 Make_Object_Declaration (Loc,
1680 Defining_Identifier => Tnn,
1681 Object_Definition => New_Occurrence_Of (Typ, Loc),
1682 Constant_Present => True,
1683 Expression => Relocate_Node (N)),
1684 Make_Raise_Constraint_Error (Loc,
1685 Condition =>
1686 Make_Op_Not (Loc,
1687 Right_Opnd =>
1688 Make_Attribute_Reference (Loc,
1689 Prefix => New_Occurrence_Of (Tnn, Loc),
1690 Attribute_Name => Name_Valid)),
1691 Reason => CE_Overflow_Check_Failed)),
1692 Expression => New_Occurrence_Of (Tnn, Loc)));
1694 Analyze_And_Resolve (N, Typ);
1695 end;
1696 end Check_Float_Op_Overflow;
1698 ----------------------------------
1699 -- Component_May_Be_Bit_Aligned --
1700 ----------------------------------
1702 function Component_May_Be_Bit_Aligned (Comp : Entity_Id) return Boolean is
1703 UT : Entity_Id;
1705 begin
1706 -- If no component clause, then everything is fine, since the back end
1707 -- never bit-misaligns by default, even if there is a pragma Packed for
1708 -- the record.
1710 if No (Comp) or else No (Component_Clause (Comp)) then
1711 return False;
1712 end if;
1714 UT := Underlying_Type (Etype (Comp));
1716 -- It is only array and record types that cause trouble
1718 if not Is_Record_Type (UT) and then not Is_Array_Type (UT) then
1719 return False;
1721 -- If we know that we have a small (64 bits or less) record or small
1722 -- bit-packed array, then everything is fine, since the back end can
1723 -- handle these cases correctly.
1725 elsif Esize (Comp) <= 64
1726 and then (Is_Record_Type (UT) or else Is_Bit_Packed_Array (UT))
1727 then
1728 return False;
1730 -- Otherwise if the component is not byte aligned, we know we have the
1731 -- nasty unaligned case.
1733 elsif Normalized_First_Bit (Comp) /= Uint_0
1734 or else Esize (Comp) mod System_Storage_Unit /= Uint_0
1735 then
1736 return True;
1738 -- If we are large and byte aligned, then OK at this level
1740 else
1741 return False;
1742 end if;
1743 end Component_May_Be_Bit_Aligned;
1745 ----------------------------------------
1746 -- Containing_Package_With_Ext_Axioms --
1747 ----------------------------------------
1749 function Containing_Package_With_Ext_Axioms
1750 (E : Entity_Id) return Entity_Id
1752 Decl : Node_Id;
1754 begin
1755 if Ekind (E) = E_Package then
1756 if Nkind (Parent (E)) = N_Defining_Program_Unit_Name then
1757 Decl := Parent (Parent (E));
1758 else
1759 Decl := Parent (E);
1760 end if;
1761 end if;
1763 -- E is the package or generic package which is externally axiomatized
1765 if Ekind_In (E, E_Package, E_Generic_Package)
1766 and then Has_Annotate_Pragma_For_External_Axiomatization (E)
1767 then
1768 return E;
1769 end if;
1771 -- If E's scope is axiomatized, E is axiomatized.
1773 declare
1774 First_Ax_Parent_Scope : Entity_Id := Empty;
1776 begin
1777 if Present (Scope (E)) then
1778 First_Ax_Parent_Scope :=
1779 Containing_Package_With_Ext_Axioms (Scope (E));
1780 end if;
1782 if Present (First_Ax_Parent_Scope) then
1783 return First_Ax_Parent_Scope;
1784 end if;
1786 -- otherwise, if E is a package instance, it is axiomatized if the
1787 -- corresponding generic package is axiomatized.
1789 if Ekind (E) = E_Package
1790 and then Present (Generic_Parent (Decl))
1791 then
1792 return
1793 Containing_Package_With_Ext_Axioms (Generic_Parent (Decl));
1794 else
1795 return Empty;
1796 end if;
1797 end;
1798 end Containing_Package_With_Ext_Axioms;
1800 -------------------------------
1801 -- Convert_To_Actual_Subtype --
1802 -------------------------------
1804 procedure Convert_To_Actual_Subtype (Exp : Entity_Id) is
1805 Act_ST : Entity_Id;
1807 begin
1808 Act_ST := Get_Actual_Subtype (Exp);
1810 if Act_ST = Etype (Exp) then
1811 return;
1812 else
1813 Rewrite (Exp, Convert_To (Act_ST, Relocate_Node (Exp)));
1814 Analyze_And_Resolve (Exp, Act_ST);
1815 end if;
1816 end Convert_To_Actual_Subtype;
1818 -----------------------------------
1819 -- Corresponding_Runtime_Package --
1820 -----------------------------------
1822 function Corresponding_Runtime_Package (Typ : Entity_Id) return RTU_Id is
1823 Pkg_Id : RTU_Id := RTU_Null;
1825 begin
1826 pragma Assert (Is_Concurrent_Type (Typ));
1828 if Ekind (Typ) in Protected_Kind then
1829 if Has_Entries (Typ)
1831 -- A protected type without entries that covers an interface and
1832 -- overrides the abstract routines with protected procedures is
1833 -- considered equivalent to a protected type with entries in the
1834 -- context of dispatching select statements. It is sufficient to
1835 -- check for the presence of an interface list in the declaration
1836 -- node to recognize this case.
1838 or else Present (Interface_List (Parent (Typ)))
1840 -- Protected types with interrupt handlers (when not using a
1841 -- restricted profile) are also considered equivalent to
1842 -- protected types with entries. The types which are used
1843 -- (Static_Interrupt_Protection and Dynamic_Interrupt_Protection)
1844 -- are derived from Protection_Entries.
1846 or else (Has_Attach_Handler (Typ) and then not Restricted_Profile)
1847 or else Has_Interrupt_Handler (Typ)
1848 then
1849 if Abort_Allowed
1850 or else Restriction_Active (No_Entry_Queue) = False
1851 or else Restriction_Active (No_Select_Statements) = False
1852 or else Number_Entries (Typ) > 1
1853 or else (Has_Attach_Handler (Typ)
1854 and then not Restricted_Profile)
1855 then
1856 Pkg_Id := System_Tasking_Protected_Objects_Entries;
1857 else
1858 Pkg_Id := System_Tasking_Protected_Objects_Single_Entry;
1859 end if;
1861 else
1862 Pkg_Id := System_Tasking_Protected_Objects;
1863 end if;
1864 end if;
1866 return Pkg_Id;
1867 end Corresponding_Runtime_Package;
1869 -----------------------------------
1870 -- Current_Sem_Unit_Declarations --
1871 -----------------------------------
1873 function Current_Sem_Unit_Declarations return List_Id is
1874 U : Node_Id := Unit (Cunit (Current_Sem_Unit));
1875 Decls : List_Id;
1877 begin
1878 -- If the current unit is a package body, locate the visible
1879 -- declarations of the package spec.
1881 if Nkind (U) = N_Package_Body then
1882 U := Unit (Library_Unit (Cunit (Current_Sem_Unit)));
1883 end if;
1885 if Nkind (U) = N_Package_Declaration then
1886 U := Specification (U);
1887 Decls := Visible_Declarations (U);
1889 if No (Decls) then
1890 Decls := New_List;
1891 Set_Visible_Declarations (U, Decls);
1892 end if;
1894 else
1895 Decls := Declarations (U);
1897 if No (Decls) then
1898 Decls := New_List;
1899 Set_Declarations (U, Decls);
1900 end if;
1901 end if;
1903 return Decls;
1904 end Current_Sem_Unit_Declarations;
1906 -----------------------
1907 -- Duplicate_Subexpr --
1908 -----------------------
1910 function Duplicate_Subexpr
1911 (Exp : Node_Id;
1912 Name_Req : Boolean := False;
1913 Renaming_Req : Boolean := False) return Node_Id
1915 begin
1916 Remove_Side_Effects (Exp, Name_Req, Renaming_Req);
1917 return New_Copy_Tree (Exp);
1918 end Duplicate_Subexpr;
1920 ---------------------------------
1921 -- Duplicate_Subexpr_No_Checks --
1922 ---------------------------------
1924 function Duplicate_Subexpr_No_Checks
1925 (Exp : Node_Id;
1926 Name_Req : Boolean := False;
1927 Renaming_Req : Boolean := False;
1928 Related_Id : Entity_Id := Empty;
1929 Is_Low_Bound : Boolean := False;
1930 Is_High_Bound : Boolean := False) return Node_Id
1932 New_Exp : Node_Id;
1934 begin
1935 Remove_Side_Effects
1936 (Exp => Exp,
1937 Name_Req => Name_Req,
1938 Renaming_Req => Renaming_Req,
1939 Related_Id => Related_Id,
1940 Is_Low_Bound => Is_Low_Bound,
1941 Is_High_Bound => Is_High_Bound);
1943 New_Exp := New_Copy_Tree (Exp);
1944 Remove_Checks (New_Exp);
1945 return New_Exp;
1946 end Duplicate_Subexpr_No_Checks;
1948 -----------------------------------
1949 -- Duplicate_Subexpr_Move_Checks --
1950 -----------------------------------
1952 function Duplicate_Subexpr_Move_Checks
1953 (Exp : Node_Id;
1954 Name_Req : Boolean := False;
1955 Renaming_Req : Boolean := False) return Node_Id
1957 New_Exp : Node_Id;
1959 begin
1960 Remove_Side_Effects (Exp, Name_Req, Renaming_Req);
1961 New_Exp := New_Copy_Tree (Exp);
1962 Remove_Checks (Exp);
1963 return New_Exp;
1964 end Duplicate_Subexpr_Move_Checks;
1966 --------------------
1967 -- Ensure_Defined --
1968 --------------------
1970 procedure Ensure_Defined (Typ : Entity_Id; N : Node_Id) is
1971 IR : Node_Id;
1973 begin
1974 -- An itype reference must only be created if this is a local itype, so
1975 -- that gigi can elaborate it on the proper objstack.
1977 if Is_Itype (Typ) and then Scope (Typ) = Current_Scope then
1978 IR := Make_Itype_Reference (Sloc (N));
1979 Set_Itype (IR, Typ);
1980 Insert_Action (N, IR);
1981 end if;
1982 end Ensure_Defined;
1984 --------------------
1985 -- Entry_Names_OK --
1986 --------------------
1988 function Entry_Names_OK return Boolean is
1989 begin
1990 return
1991 not Restricted_Profile
1992 and then not Global_Discard_Names
1993 and then not Restriction_Active (No_Implicit_Heap_Allocations)
1994 and then not Restriction_Active (No_Local_Allocators);
1995 end Entry_Names_OK;
1997 -------------------
1998 -- Evaluate_Name --
1999 -------------------
2001 procedure Evaluate_Name (Nam : Node_Id) is
2002 K : constant Node_Kind := Nkind (Nam);
2004 begin
2005 -- For an explicit dereference, we simply force the evaluation of the
2006 -- name expression. The dereference provides a value that is the address
2007 -- for the renamed object, and it is precisely this value that we want
2008 -- to preserve.
2010 if K = N_Explicit_Dereference then
2011 Force_Evaluation (Prefix (Nam));
2013 -- For a selected component, we simply evaluate the prefix
2015 elsif K = N_Selected_Component then
2016 Evaluate_Name (Prefix (Nam));
2018 -- For an indexed component, or an attribute reference, we evaluate the
2019 -- prefix, which is itself a name, recursively, and then force the
2020 -- evaluation of all the subscripts (or attribute expressions).
2022 elsif Nkind_In (K, N_Indexed_Component, N_Attribute_Reference) then
2023 Evaluate_Name (Prefix (Nam));
2025 declare
2026 E : Node_Id;
2028 begin
2029 E := First (Expressions (Nam));
2030 while Present (E) loop
2031 Force_Evaluation (E);
2033 if Original_Node (E) /= E then
2034 Set_Do_Range_Check (E, Do_Range_Check (Original_Node (E)));
2035 end if;
2037 Next (E);
2038 end loop;
2039 end;
2041 -- For a slice, we evaluate the prefix, as for the indexed component
2042 -- case and then, if there is a range present, either directly or as the
2043 -- constraint of a discrete subtype indication, we evaluate the two
2044 -- bounds of this range.
2046 elsif K = N_Slice then
2047 Evaluate_Name (Prefix (Nam));
2048 Evaluate_Slice_Bounds (Nam);
2050 -- For a type conversion, the expression of the conversion must be the
2051 -- name of an object, and we simply need to evaluate this name.
2053 elsif K = N_Type_Conversion then
2054 Evaluate_Name (Expression (Nam));
2056 -- For a function call, we evaluate the call
2058 elsif K = N_Function_Call then
2059 Force_Evaluation (Nam);
2061 -- The remaining cases are direct name, operator symbol and character
2062 -- literal. In all these cases, we do nothing, since we want to
2063 -- reevaluate each time the renamed object is used.
2065 else
2066 return;
2067 end if;
2068 end Evaluate_Name;
2070 ---------------------------
2071 -- Evaluate_Slice_Bounds --
2072 ---------------------------
2074 procedure Evaluate_Slice_Bounds (Slice : Node_Id) is
2075 DR : constant Node_Id := Discrete_Range (Slice);
2076 Constr : Node_Id;
2077 Rexpr : Node_Id;
2079 begin
2080 if Nkind (DR) = N_Range then
2081 Force_Evaluation (Low_Bound (DR));
2082 Force_Evaluation (High_Bound (DR));
2084 elsif Nkind (DR) = N_Subtype_Indication then
2085 Constr := Constraint (DR);
2087 if Nkind (Constr) = N_Range_Constraint then
2088 Rexpr := Range_Expression (Constr);
2090 Force_Evaluation (Low_Bound (Rexpr));
2091 Force_Evaluation (High_Bound (Rexpr));
2092 end if;
2093 end if;
2094 end Evaluate_Slice_Bounds;
2096 ---------------------
2097 -- Evolve_And_Then --
2098 ---------------------
2100 procedure Evolve_And_Then (Cond : in out Node_Id; Cond1 : Node_Id) is
2101 begin
2102 if No (Cond) then
2103 Cond := Cond1;
2104 else
2105 Cond :=
2106 Make_And_Then (Sloc (Cond1),
2107 Left_Opnd => Cond,
2108 Right_Opnd => Cond1);
2109 end if;
2110 end Evolve_And_Then;
2112 --------------------
2113 -- Evolve_Or_Else --
2114 --------------------
2116 procedure Evolve_Or_Else (Cond : in out Node_Id; Cond1 : Node_Id) is
2117 begin
2118 if No (Cond) then
2119 Cond := Cond1;
2120 else
2121 Cond :=
2122 Make_Or_Else (Sloc (Cond1),
2123 Left_Opnd => Cond,
2124 Right_Opnd => Cond1);
2125 end if;
2126 end Evolve_Or_Else;
2128 -----------------------------------------
2129 -- Expand_Static_Predicates_In_Choices --
2130 -----------------------------------------
2132 procedure Expand_Static_Predicates_In_Choices (N : Node_Id) is
2133 pragma Assert (Nkind_In (N, N_Case_Statement_Alternative, N_Variant));
2135 Choices : constant List_Id := Discrete_Choices (N);
2137 Choice : Node_Id;
2138 Next_C : Node_Id;
2139 P : Node_Id;
2140 C : Node_Id;
2142 begin
2143 Choice := First (Choices);
2144 while Present (Choice) loop
2145 Next_C := Next (Choice);
2147 -- Check for name of subtype with static predicate
2149 if Is_Entity_Name (Choice)
2150 and then Is_Type (Entity (Choice))
2151 and then Has_Predicates (Entity (Choice))
2152 then
2153 -- Loop through entries in predicate list, converting to choices
2154 -- and inserting in the list before the current choice. Note that
2155 -- if the list is empty, corresponding to a False predicate, then
2156 -- no choices are inserted.
2158 P := First (Static_Discrete_Predicate (Entity (Choice)));
2159 while Present (P) loop
2161 -- If low bound and high bounds are equal, copy simple choice
2163 if Expr_Value (Low_Bound (P)) = Expr_Value (High_Bound (P)) then
2164 C := New_Copy (Low_Bound (P));
2166 -- Otherwise copy a range
2168 else
2169 C := New_Copy (P);
2170 end if;
2172 -- Change Sloc to referencing choice (rather than the Sloc of
2173 -- the predicate declaration element itself).
2175 Set_Sloc (C, Sloc (Choice));
2176 Insert_Before (Choice, C);
2177 Next (P);
2178 end loop;
2180 -- Delete the predicated entry
2182 Remove (Choice);
2183 end if;
2185 -- Move to next choice to check
2187 Choice := Next_C;
2188 end loop;
2189 end Expand_Static_Predicates_In_Choices;
2191 ------------------------------
2192 -- Expand_Subtype_From_Expr --
2193 ------------------------------
2195 -- This function is applicable for both static and dynamic allocation of
2196 -- objects which are constrained by an initial expression. Basically it
2197 -- transforms an unconstrained subtype indication into a constrained one.
2199 -- The expression may also be transformed in certain cases in order to
2200 -- avoid multiple evaluation. In the static allocation case, the general
2201 -- scheme is:
2203 -- Val : T := Expr;
2205 -- is transformed into
2207 -- Val : Constrained_Subtype_of_T := Maybe_Modified_Expr;
2209 -- Here are the main cases :
2211 -- <if Expr is a Slice>
2212 -- Val : T ([Index_Subtype (Expr)]) := Expr;
2214 -- <elsif Expr is a String Literal>
2215 -- Val : T (T'First .. T'First + Length (string literal) - 1) := Expr;
2217 -- <elsif Expr is Constrained>
2218 -- subtype T is Type_Of_Expr
2219 -- Val : T := Expr;
2221 -- <elsif Expr is an entity_name>
2222 -- Val : T (constraints taken from Expr) := Expr;
2224 -- <else>
2225 -- type Axxx is access all T;
2226 -- Rval : Axxx := Expr'ref;
2227 -- Val : T (constraints taken from Rval) := Rval.all;
2229 -- ??? note: when the Expression is allocated in the secondary stack
2230 -- we could use it directly instead of copying it by declaring
2231 -- Val : T (...) renames Rval.all
2233 procedure Expand_Subtype_From_Expr
2234 (N : Node_Id;
2235 Unc_Type : Entity_Id;
2236 Subtype_Indic : Node_Id;
2237 Exp : Node_Id)
2239 Loc : constant Source_Ptr := Sloc (N);
2240 Exp_Typ : constant Entity_Id := Etype (Exp);
2241 T : Entity_Id;
2243 begin
2244 -- In general we cannot build the subtype if expansion is disabled,
2245 -- because internal entities may not have been defined. However, to
2246 -- avoid some cascaded errors, we try to continue when the expression is
2247 -- an array (or string), because it is safe to compute the bounds. It is
2248 -- in fact required to do so even in a generic context, because there
2249 -- may be constants that depend on the bounds of a string literal, both
2250 -- standard string types and more generally arrays of characters.
2252 -- In GNATprove mode, these extra subtypes are not needed
2254 if GNATprove_Mode then
2255 return;
2256 end if;
2258 if not Expander_Active
2259 and then (No (Etype (Exp)) or else not Is_String_Type (Etype (Exp)))
2260 then
2261 return;
2262 end if;
2264 if Nkind (Exp) = N_Slice then
2265 declare
2266 Slice_Type : constant Entity_Id := Etype (First_Index (Exp_Typ));
2268 begin
2269 Rewrite (Subtype_Indic,
2270 Make_Subtype_Indication (Loc,
2271 Subtype_Mark => New_Occurrence_Of (Unc_Type, Loc),
2272 Constraint =>
2273 Make_Index_Or_Discriminant_Constraint (Loc,
2274 Constraints => New_List
2275 (New_Occurrence_Of (Slice_Type, Loc)))));
2277 -- This subtype indication may be used later for constraint checks
2278 -- we better make sure that if a variable was used as a bound of
2279 -- of the original slice, its value is frozen.
2281 Evaluate_Slice_Bounds (Exp);
2282 end;
2284 elsif Ekind (Exp_Typ) = E_String_Literal_Subtype then
2285 Rewrite (Subtype_Indic,
2286 Make_Subtype_Indication (Loc,
2287 Subtype_Mark => New_Occurrence_Of (Unc_Type, Loc),
2288 Constraint =>
2289 Make_Index_Or_Discriminant_Constraint (Loc,
2290 Constraints => New_List (
2291 Make_Literal_Range (Loc,
2292 Literal_Typ => Exp_Typ)))));
2294 -- If the type of the expression is an internally generated type it
2295 -- may not be necessary to create a new subtype. However there are two
2296 -- exceptions: references to the current instances, and aliased array
2297 -- object declarations for which the backend needs to create a template.
2299 elsif Is_Constrained (Exp_Typ)
2300 and then not Is_Class_Wide_Type (Unc_Type)
2301 and then
2302 (Nkind (N) /= N_Object_Declaration
2303 or else not Is_Entity_Name (Expression (N))
2304 or else not Comes_From_Source (Entity (Expression (N)))
2305 or else not Is_Array_Type (Exp_Typ)
2306 or else not Aliased_Present (N))
2307 then
2308 if Is_Itype (Exp_Typ) then
2310 -- Within an initialization procedure, a selected component
2311 -- denotes a component of the enclosing record, and it appears as
2312 -- an actual in a call to its own initialization procedure. If
2313 -- this component depends on the outer discriminant, we must
2314 -- generate the proper actual subtype for it.
2316 if Nkind (Exp) = N_Selected_Component
2317 and then Within_Init_Proc
2318 then
2319 declare
2320 Decl : constant Node_Id :=
2321 Build_Actual_Subtype_Of_Component (Exp_Typ, Exp);
2322 begin
2323 if Present (Decl) then
2324 Insert_Action (N, Decl);
2325 T := Defining_Identifier (Decl);
2326 else
2327 T := Exp_Typ;
2328 end if;
2329 end;
2331 -- No need to generate a new subtype
2333 else
2334 T := Exp_Typ;
2335 end if;
2337 else
2338 T := Make_Temporary (Loc, 'T');
2340 Insert_Action (N,
2341 Make_Subtype_Declaration (Loc,
2342 Defining_Identifier => T,
2343 Subtype_Indication => New_Occurrence_Of (Exp_Typ, Loc)));
2345 -- This type is marked as an itype even though it has an explicit
2346 -- declaration since otherwise Is_Generic_Actual_Type can get
2347 -- set, resulting in the generation of spurious errors. (See
2348 -- sem_ch8.Analyze_Package_Renaming and sem_type.covers)
2350 Set_Is_Itype (T);
2351 Set_Associated_Node_For_Itype (T, Exp);
2352 end if;
2354 Rewrite (Subtype_Indic, New_Occurrence_Of (T, Loc));
2356 -- Nothing needs to be done for private types with unknown discriminants
2357 -- if the underlying type is not an unconstrained composite type or it
2358 -- is an unchecked union.
2360 elsif Is_Private_Type (Unc_Type)
2361 and then Has_Unknown_Discriminants (Unc_Type)
2362 and then (not Is_Composite_Type (Underlying_Type (Unc_Type))
2363 or else Is_Constrained (Underlying_Type (Unc_Type))
2364 or else Is_Unchecked_Union (Underlying_Type (Unc_Type)))
2365 then
2366 null;
2368 -- Case of derived type with unknown discriminants where the parent type
2369 -- also has unknown discriminants.
2371 elsif Is_Record_Type (Unc_Type)
2372 and then not Is_Class_Wide_Type (Unc_Type)
2373 and then Has_Unknown_Discriminants (Unc_Type)
2374 and then Has_Unknown_Discriminants (Underlying_Type (Unc_Type))
2375 then
2376 -- Nothing to be done if no underlying record view available
2378 if No (Underlying_Record_View (Unc_Type)) then
2379 null;
2381 -- Otherwise use the Underlying_Record_View to create the proper
2382 -- constrained subtype for an object of a derived type with unknown
2383 -- discriminants.
2385 else
2386 Remove_Side_Effects (Exp);
2387 Rewrite (Subtype_Indic,
2388 Make_Subtype_From_Expr (Exp, Underlying_Record_View (Unc_Type)));
2389 end if;
2391 -- Renamings of class-wide interface types require no equivalent
2392 -- constrained type declarations because we only need to reference
2393 -- the tag component associated with the interface. The same is
2394 -- presumably true for class-wide types in general, so this test
2395 -- is broadened to include all class-wide renamings, which also
2396 -- avoids cases of unbounded recursion in Remove_Side_Effects.
2397 -- (Is this really correct, or are there some cases of class-wide
2398 -- renamings that require action in this procedure???)
2400 elsif Present (N)
2401 and then Nkind (N) = N_Object_Renaming_Declaration
2402 and then Is_Class_Wide_Type (Unc_Type)
2403 then
2404 null;
2406 -- In Ada 95 nothing to be done if the type of the expression is limited
2407 -- because in this case the expression cannot be copied, and its use can
2408 -- only be by reference.
2410 -- In Ada 2005 the context can be an object declaration whose expression
2411 -- is a function that returns in place. If the nominal subtype has
2412 -- unknown discriminants, the call still provides constraints on the
2413 -- object, and we have to create an actual subtype from it.
2415 -- If the type is class-wide, the expression is dynamically tagged and
2416 -- we do not create an actual subtype either. Ditto for an interface.
2417 -- For now this applies only if the type is immutably limited, and the
2418 -- function being called is build-in-place. This will have to be revised
2419 -- when build-in-place functions are generalized to other types.
2421 elsif Is_Limited_View (Exp_Typ)
2422 and then
2423 (Is_Class_Wide_Type (Exp_Typ)
2424 or else Is_Interface (Exp_Typ)
2425 or else not Has_Unknown_Discriminants (Exp_Typ)
2426 or else not Is_Composite_Type (Unc_Type))
2427 then
2428 null;
2430 -- For limited objects initialized with build in place function calls,
2431 -- nothing to be done; otherwise we prematurely introduce an N_Reference
2432 -- node in the expression initializing the object, which breaks the
2433 -- circuitry that detects and adds the additional arguments to the
2434 -- called function.
2436 elsif Is_Build_In_Place_Function_Call (Exp) then
2437 null;
2439 else
2440 Remove_Side_Effects (Exp);
2441 Rewrite (Subtype_Indic,
2442 Make_Subtype_From_Expr (Exp, Unc_Type));
2443 end if;
2444 end Expand_Subtype_From_Expr;
2446 ------------------------
2447 -- Find_Interface_ADT --
2448 ------------------------
2450 function Find_Interface_ADT
2451 (T : Entity_Id;
2452 Iface : Entity_Id) return Elmt_Id
2454 ADT : Elmt_Id;
2455 Typ : Entity_Id := T;
2457 begin
2458 pragma Assert (Is_Interface (Iface));
2460 -- Handle private types
2462 if Has_Private_Declaration (Typ) and then Present (Full_View (Typ)) then
2463 Typ := Full_View (Typ);
2464 end if;
2466 -- Handle access types
2468 if Is_Access_Type (Typ) then
2469 Typ := Designated_Type (Typ);
2470 end if;
2472 -- Handle task and protected types implementing interfaces
2474 if Is_Concurrent_Type (Typ) then
2475 Typ := Corresponding_Record_Type (Typ);
2476 end if;
2478 pragma Assert
2479 (not Is_Class_Wide_Type (Typ)
2480 and then Ekind (Typ) /= E_Incomplete_Type);
2482 if Is_Ancestor (Iface, Typ, Use_Full_View => True) then
2483 return First_Elmt (Access_Disp_Table (Typ));
2485 else
2486 ADT := Next_Elmt (Next_Elmt (First_Elmt (Access_Disp_Table (Typ))));
2487 while Present (ADT)
2488 and then Present (Related_Type (Node (ADT)))
2489 and then Related_Type (Node (ADT)) /= Iface
2490 and then not Is_Ancestor (Iface, Related_Type (Node (ADT)),
2491 Use_Full_View => True)
2492 loop
2493 Next_Elmt (ADT);
2494 end loop;
2496 pragma Assert (Present (Related_Type (Node (ADT))));
2497 return ADT;
2498 end if;
2499 end Find_Interface_ADT;
2501 ------------------------
2502 -- Find_Interface_Tag --
2503 ------------------------
2505 function Find_Interface_Tag
2506 (T : Entity_Id;
2507 Iface : Entity_Id) return Entity_Id
2509 AI_Tag : Entity_Id;
2510 Found : Boolean := False;
2511 Typ : Entity_Id := T;
2513 procedure Find_Tag (Typ : Entity_Id);
2514 -- Internal subprogram used to recursively climb to the ancestors
2516 --------------
2517 -- Find_Tag --
2518 --------------
2520 procedure Find_Tag (Typ : Entity_Id) is
2521 AI_Elmt : Elmt_Id;
2522 AI : Node_Id;
2524 begin
2525 -- This routine does not handle the case in which the interface is an
2526 -- ancestor of Typ. That case is handled by the enclosing subprogram.
2528 pragma Assert (Typ /= Iface);
2530 -- Climb to the root type handling private types
2532 if Present (Full_View (Etype (Typ))) then
2533 if Full_View (Etype (Typ)) /= Typ then
2534 Find_Tag (Full_View (Etype (Typ)));
2535 end if;
2537 elsif Etype (Typ) /= Typ then
2538 Find_Tag (Etype (Typ));
2539 end if;
2541 -- Traverse the list of interfaces implemented by the type
2543 if not Found
2544 and then Present (Interfaces (Typ))
2545 and then not (Is_Empty_Elmt_List (Interfaces (Typ)))
2546 then
2547 -- Skip the tag associated with the primary table
2549 pragma Assert (Etype (First_Tag_Component (Typ)) = RTE (RE_Tag));
2550 AI_Tag := Next_Tag_Component (First_Tag_Component (Typ));
2551 pragma Assert (Present (AI_Tag));
2553 AI_Elmt := First_Elmt (Interfaces (Typ));
2554 while Present (AI_Elmt) loop
2555 AI := Node (AI_Elmt);
2557 if AI = Iface
2558 or else Is_Ancestor (Iface, AI, Use_Full_View => True)
2559 then
2560 Found := True;
2561 return;
2562 end if;
2564 AI_Tag := Next_Tag_Component (AI_Tag);
2565 Next_Elmt (AI_Elmt);
2566 end loop;
2567 end if;
2568 end Find_Tag;
2570 -- Start of processing for Find_Interface_Tag
2572 begin
2573 pragma Assert (Is_Interface (Iface));
2575 -- Handle access types
2577 if Is_Access_Type (Typ) then
2578 Typ := Designated_Type (Typ);
2579 end if;
2581 -- Handle class-wide types
2583 if Is_Class_Wide_Type (Typ) then
2584 Typ := Root_Type (Typ);
2585 end if;
2587 -- Handle private types
2589 if Has_Private_Declaration (Typ) and then Present (Full_View (Typ)) then
2590 Typ := Full_View (Typ);
2591 end if;
2593 -- Handle entities from the limited view
2595 if Ekind (Typ) = E_Incomplete_Type then
2596 pragma Assert (Present (Non_Limited_View (Typ)));
2597 Typ := Non_Limited_View (Typ);
2598 end if;
2600 -- Handle task and protected types implementing interfaces
2602 if Is_Concurrent_Type (Typ) then
2603 Typ := Corresponding_Record_Type (Typ);
2604 end if;
2606 -- If the interface is an ancestor of the type, then it shared the
2607 -- primary dispatch table.
2609 if Is_Ancestor (Iface, Typ, Use_Full_View => True) then
2610 pragma Assert (Etype (First_Tag_Component (Typ)) = RTE (RE_Tag));
2611 return First_Tag_Component (Typ);
2613 -- Otherwise we need to search for its associated tag component
2615 else
2616 Find_Tag (Typ);
2617 pragma Assert (Found);
2618 return AI_Tag;
2619 end if;
2620 end Find_Interface_Tag;
2622 ------------------
2623 -- Find_Prim_Op --
2624 ------------------
2626 function Find_Prim_Op (T : Entity_Id; Name : Name_Id) return Entity_Id is
2627 Prim : Elmt_Id;
2628 Typ : Entity_Id := T;
2629 Op : Entity_Id;
2631 begin
2632 if Is_Class_Wide_Type (Typ) then
2633 Typ := Root_Type (Typ);
2634 end if;
2636 Typ := Underlying_Type (Typ);
2638 -- Loop through primitive operations
2640 Prim := First_Elmt (Primitive_Operations (Typ));
2641 while Present (Prim) loop
2642 Op := Node (Prim);
2644 -- We can retrieve primitive operations by name if it is an internal
2645 -- name. For equality we must check that both of its operands have
2646 -- the same type, to avoid confusion with user-defined equalities
2647 -- than may have a non-symmetric signature.
2649 exit when Chars (Op) = Name
2650 and then
2651 (Name /= Name_Op_Eq
2652 or else Etype (First_Formal (Op)) = Etype (Last_Formal (Op)));
2654 Next_Elmt (Prim);
2656 -- Raise Program_Error if no primitive found
2658 if No (Prim) then
2659 raise Program_Error;
2660 end if;
2661 end loop;
2663 return Node (Prim);
2664 end Find_Prim_Op;
2666 ------------------
2667 -- Find_Prim_Op --
2668 ------------------
2670 function Find_Prim_Op
2671 (T : Entity_Id;
2672 Name : TSS_Name_Type) return Entity_Id
2674 Inher_Op : Entity_Id := Empty;
2675 Own_Op : Entity_Id := Empty;
2676 Prim_Elmt : Elmt_Id;
2677 Prim_Id : Entity_Id;
2678 Typ : Entity_Id := T;
2680 begin
2681 if Is_Class_Wide_Type (Typ) then
2682 Typ := Root_Type (Typ);
2683 end if;
2685 Typ := Underlying_Type (Typ);
2687 -- This search is based on the assertion that the dispatching version
2688 -- of the TSS routine always precedes the real primitive.
2690 Prim_Elmt := First_Elmt (Primitive_Operations (Typ));
2691 while Present (Prim_Elmt) loop
2692 Prim_Id := Node (Prim_Elmt);
2694 if Is_TSS (Prim_Id, Name) then
2695 if Present (Alias (Prim_Id)) then
2696 Inher_Op := Prim_Id;
2697 else
2698 Own_Op := Prim_Id;
2699 end if;
2700 end if;
2702 Next_Elmt (Prim_Elmt);
2703 end loop;
2705 if Present (Own_Op) then
2706 return Own_Op;
2707 elsif Present (Inher_Op) then
2708 return Inher_Op;
2709 else
2710 raise Program_Error;
2711 end if;
2712 end Find_Prim_Op;
2714 ----------------------------
2715 -- Find_Protection_Object --
2716 ----------------------------
2718 function Find_Protection_Object (Scop : Entity_Id) return Entity_Id is
2719 S : Entity_Id;
2721 begin
2722 S := Scop;
2723 while Present (S) loop
2724 if Ekind_In (S, E_Entry, E_Entry_Family, E_Function, E_Procedure)
2725 and then Present (Protection_Object (S))
2726 then
2727 return Protection_Object (S);
2728 end if;
2730 S := Scope (S);
2731 end loop;
2733 -- If we do not find a Protection object in the scope chain, then
2734 -- something has gone wrong, most likely the object was never created.
2736 raise Program_Error;
2737 end Find_Protection_Object;
2739 --------------------------
2740 -- Find_Protection_Type --
2741 --------------------------
2743 function Find_Protection_Type (Conc_Typ : Entity_Id) return Entity_Id is
2744 Comp : Entity_Id;
2745 Typ : Entity_Id := Conc_Typ;
2747 begin
2748 if Is_Concurrent_Type (Typ) then
2749 Typ := Corresponding_Record_Type (Typ);
2750 end if;
2752 -- Since restriction violations are not considered serious errors, the
2753 -- expander remains active, but may leave the corresponding record type
2754 -- malformed. In such cases, component _object is not available so do
2755 -- not look for it.
2757 if not Analyzed (Typ) then
2758 return Empty;
2759 end if;
2761 Comp := First_Component (Typ);
2762 while Present (Comp) loop
2763 if Chars (Comp) = Name_uObject then
2764 return Base_Type (Etype (Comp));
2765 end if;
2767 Next_Component (Comp);
2768 end loop;
2770 -- The corresponding record of a protected type should always have an
2771 -- _object field.
2773 raise Program_Error;
2774 end Find_Protection_Type;
2776 -----------------------
2777 -- Find_Hook_Context --
2778 -----------------------
2780 function Find_Hook_Context (N : Node_Id) return Node_Id is
2781 Par : Node_Id;
2782 Top : Node_Id;
2784 Wrapped_Node : Node_Id;
2785 -- Note: if we are in a transient scope, we want to reuse it as
2786 -- the context for actions insertion, if possible. But if N is itself
2787 -- part of the stored actions for the current transient scope,
2788 -- then we need to insert at the appropriate (inner) location in
2789 -- the not as an action on Node_To_Be_Wrapped.
2791 In_Cond_Expr : constant Boolean := Within_Case_Or_If_Expression (N);
2793 begin
2794 -- When the node is inside a case/if expression, the lifetime of any
2795 -- temporary controlled object is extended. Find a suitable insertion
2796 -- node by locating the topmost case or if expressions.
2798 if In_Cond_Expr then
2799 Par := N;
2800 Top := N;
2801 while Present (Par) loop
2802 if Nkind_In (Original_Node (Par), N_Case_Expression,
2803 N_If_Expression)
2804 then
2805 Top := Par;
2807 -- Prevent the search from going too far
2809 elsif Is_Body_Or_Package_Declaration (Par) then
2810 exit;
2811 end if;
2813 Par := Parent (Par);
2814 end loop;
2816 -- The topmost case or if expression is now recovered, but it may
2817 -- still not be the correct place to add generated code. Climb to
2818 -- find a parent that is part of a declarative or statement list,
2819 -- and is not a list of actuals in a call.
2821 Par := Top;
2822 while Present (Par) loop
2823 if Is_List_Member (Par)
2824 and then not Nkind_In (Par, N_Component_Association,
2825 N_Discriminant_Association,
2826 N_Parameter_Association,
2827 N_Pragma_Argument_Association)
2828 and then not Nkind_In
2829 (Parent (Par), N_Function_Call,
2830 N_Procedure_Call_Statement,
2831 N_Entry_Call_Statement)
2833 then
2834 return Par;
2836 -- Prevent the search from going too far
2838 elsif Is_Body_Or_Package_Declaration (Par) then
2839 exit;
2840 end if;
2842 Par := Parent (Par);
2843 end loop;
2845 return Par;
2847 else
2848 Par := N;
2849 while Present (Par) loop
2851 -- Keep climbing past various operators
2853 if Nkind (Parent (Par)) in N_Op
2854 or else Nkind_In (Parent (Par), N_And_Then, N_Or_Else)
2855 then
2856 Par := Parent (Par);
2857 else
2858 exit;
2859 end if;
2860 end loop;
2862 Top := Par;
2864 -- The node may be located in a pragma in which case return the
2865 -- pragma itself:
2867 -- pragma Precondition (... and then Ctrl_Func_Call ...);
2869 -- Similar case occurs when the node is related to an object
2870 -- declaration or assignment:
2872 -- Obj [: Some_Typ] := ... and then Ctrl_Func_Call ...;
2874 -- Another case to consider is when the node is part of a return
2875 -- statement:
2877 -- return ... and then Ctrl_Func_Call ...;
2879 -- Another case is when the node acts as a formal in a procedure
2880 -- call statement:
2882 -- Proc (... and then Ctrl_Func_Call ...);
2884 if Scope_Is_Transient then
2885 Wrapped_Node := Node_To_Be_Wrapped;
2886 else
2887 Wrapped_Node := Empty;
2888 end if;
2890 while Present (Par) loop
2891 if Par = Wrapped_Node
2892 or else Nkind_In (Par, N_Assignment_Statement,
2893 N_Object_Declaration,
2894 N_Pragma,
2895 N_Procedure_Call_Statement,
2896 N_Simple_Return_Statement)
2897 then
2898 return Par;
2900 -- Prevent the search from going too far
2902 elsif Is_Body_Or_Package_Declaration (Par) then
2903 exit;
2904 end if;
2906 Par := Parent (Par);
2907 end loop;
2909 -- Return the topmost short circuit operator
2911 return Top;
2912 end if;
2913 end Find_Hook_Context;
2915 ------------------------------
2916 -- Following_Address_Clause --
2917 ------------------------------
2919 function Following_Address_Clause (D : Node_Id) return Node_Id is
2920 Id : constant Entity_Id := Defining_Identifier (D);
2921 Result : Node_Id;
2922 Par : Node_Id;
2924 function Check_Decls (D : Node_Id) return Node_Id;
2925 -- This internal function differs from the main function in that it
2926 -- gets called to deal with a following package private part, and
2927 -- it checks declarations starting with D (the main function checks
2928 -- declarations following D). If D is Empty, then Empty is returned.
2930 -----------------
2931 -- Check_Decls --
2932 -----------------
2934 function Check_Decls (D : Node_Id) return Node_Id is
2935 Decl : Node_Id;
2937 begin
2938 Decl := D;
2939 while Present (Decl) loop
2940 if Nkind (Decl) = N_At_Clause
2941 and then Chars (Identifier (Decl)) = Chars (Id)
2942 then
2943 return Decl;
2945 elsif Nkind (Decl) = N_Attribute_Definition_Clause
2946 and then Chars (Decl) = Name_Address
2947 and then Chars (Name (Decl)) = Chars (Id)
2948 then
2949 return Decl;
2950 end if;
2952 Next (Decl);
2953 end loop;
2955 -- Otherwise not found, return Empty
2957 return Empty;
2958 end Check_Decls;
2960 -- Start of processing for Following_Address_Clause
2962 begin
2963 -- If parser detected no address clause for the identifier in question,
2964 -- then then answer is a quick NO, without the need for a search.
2966 if not Get_Name_Table_Boolean (Chars (Id)) then
2967 return Empty;
2968 end if;
2970 -- Otherwise search current declarative unit
2972 Result := Check_Decls (Next (D));
2974 if Present (Result) then
2975 return Result;
2976 end if;
2978 -- Check for possible package private part following
2980 Par := Parent (D);
2982 if Nkind (Par) = N_Package_Specification
2983 and then Visible_Declarations (Par) = List_Containing (D)
2984 and then Present (Private_Declarations (Par))
2985 then
2986 -- Private part present, check declarations there
2988 return Check_Decls (First (Private_Declarations (Par)));
2990 else
2991 -- No private part, clause not found, return Empty
2993 return Empty;
2994 end if;
2995 end Following_Address_Clause;
2997 ----------------------
2998 -- Force_Evaluation --
2999 ----------------------
3001 procedure Force_Evaluation (Exp : Node_Id; Name_Req : Boolean := False) is
3002 begin
3003 Remove_Side_Effects (Exp, Name_Req, Variable_Ref => True);
3004 end Force_Evaluation;
3006 ---------------------------------
3007 -- Fully_Qualified_Name_String --
3008 ---------------------------------
3010 function Fully_Qualified_Name_String
3011 (E : Entity_Id;
3012 Append_NUL : Boolean := True) return String_Id
3014 procedure Internal_Full_Qualified_Name (E : Entity_Id);
3015 -- Compute recursively the qualified name without NUL at the end, adding
3016 -- it to the currently started string being generated
3018 ----------------------------------
3019 -- Internal_Full_Qualified_Name --
3020 ----------------------------------
3022 procedure Internal_Full_Qualified_Name (E : Entity_Id) is
3023 Ent : Entity_Id;
3025 begin
3026 -- Deal properly with child units
3028 if Nkind (E) = N_Defining_Program_Unit_Name then
3029 Ent := Defining_Identifier (E);
3030 else
3031 Ent := E;
3032 end if;
3034 -- Compute qualification recursively (only "Standard" has no scope)
3036 if Present (Scope (Scope (Ent))) then
3037 Internal_Full_Qualified_Name (Scope (Ent));
3038 Store_String_Char (Get_Char_Code ('.'));
3039 end if;
3041 -- Every entity should have a name except some expanded blocks
3042 -- don't bother about those.
3044 if Chars (Ent) = No_Name then
3045 return;
3046 end if;
3048 -- Generates the entity name in upper case
3050 Get_Decoded_Name_String (Chars (Ent));
3051 Set_All_Upper_Case;
3052 Store_String_Chars (Name_Buffer (1 .. Name_Len));
3053 return;
3054 end Internal_Full_Qualified_Name;
3056 -- Start of processing for Full_Qualified_Name
3058 begin
3059 Start_String;
3060 Internal_Full_Qualified_Name (E);
3062 if Append_NUL then
3063 Store_String_Char (Get_Char_Code (ASCII.NUL));
3064 end if;
3066 return End_String;
3067 end Fully_Qualified_Name_String;
3069 ------------------------
3070 -- Generate_Poll_Call --
3071 ------------------------
3073 procedure Generate_Poll_Call (N : Node_Id) is
3074 begin
3075 -- No poll call if polling not active
3077 if not Polling_Required then
3078 return;
3080 -- Otherwise generate require poll call
3082 else
3083 Insert_Before_And_Analyze (N,
3084 Make_Procedure_Call_Statement (Sloc (N),
3085 Name => New_Occurrence_Of (RTE (RE_Poll), Sloc (N))));
3086 end if;
3087 end Generate_Poll_Call;
3089 ---------------------------------
3090 -- Get_Current_Value_Condition --
3091 ---------------------------------
3093 -- Note: the implementation of this procedure is very closely tied to the
3094 -- implementation of Set_Current_Value_Condition. In the Get procedure, we
3095 -- interpret Current_Value fields set by the Set procedure, so the two
3096 -- procedures need to be closely coordinated.
3098 procedure Get_Current_Value_Condition
3099 (Var : Node_Id;
3100 Op : out Node_Kind;
3101 Val : out Node_Id)
3103 Loc : constant Source_Ptr := Sloc (Var);
3104 Ent : constant Entity_Id := Entity (Var);
3106 procedure Process_Current_Value_Condition
3107 (N : Node_Id;
3108 S : Boolean);
3109 -- N is an expression which holds either True (S = True) or False (S =
3110 -- False) in the condition. This procedure digs out the expression and
3111 -- if it refers to Ent, sets Op and Val appropriately.
3113 -------------------------------------
3114 -- Process_Current_Value_Condition --
3115 -------------------------------------
3117 procedure Process_Current_Value_Condition
3118 (N : Node_Id;
3119 S : Boolean)
3121 Cond : Node_Id;
3122 Prev_Cond : Node_Id;
3123 Sens : Boolean;
3125 begin
3126 Cond := N;
3127 Sens := S;
3129 loop
3130 Prev_Cond := Cond;
3132 -- Deal with NOT operators, inverting sense
3134 while Nkind (Cond) = N_Op_Not loop
3135 Cond := Right_Opnd (Cond);
3136 Sens := not Sens;
3137 end loop;
3139 -- Deal with conversions, qualifications, and expressions with
3140 -- actions.
3142 while Nkind_In (Cond,
3143 N_Type_Conversion,
3144 N_Qualified_Expression,
3145 N_Expression_With_Actions)
3146 loop
3147 Cond := Expression (Cond);
3148 end loop;
3150 exit when Cond = Prev_Cond;
3151 end loop;
3153 -- Deal with AND THEN and AND cases
3155 if Nkind_In (Cond, N_And_Then, N_Op_And) then
3157 -- Don't ever try to invert a condition that is of the form of an
3158 -- AND or AND THEN (since we are not doing sufficiently general
3159 -- processing to allow this).
3161 if Sens = False then
3162 Op := N_Empty;
3163 Val := Empty;
3164 return;
3165 end if;
3167 -- Recursively process AND and AND THEN branches
3169 Process_Current_Value_Condition (Left_Opnd (Cond), True);
3171 if Op /= N_Empty then
3172 return;
3173 end if;
3175 Process_Current_Value_Condition (Right_Opnd (Cond), True);
3176 return;
3178 -- Case of relational operator
3180 elsif Nkind (Cond) in N_Op_Compare then
3181 Op := Nkind (Cond);
3183 -- Invert sense of test if inverted test
3185 if Sens = False then
3186 case Op is
3187 when N_Op_Eq => Op := N_Op_Ne;
3188 when N_Op_Ne => Op := N_Op_Eq;
3189 when N_Op_Lt => Op := N_Op_Ge;
3190 when N_Op_Gt => Op := N_Op_Le;
3191 when N_Op_Le => Op := N_Op_Gt;
3192 when N_Op_Ge => Op := N_Op_Lt;
3193 when others => raise Program_Error;
3194 end case;
3195 end if;
3197 -- Case of entity op value
3199 if Is_Entity_Name (Left_Opnd (Cond))
3200 and then Ent = Entity (Left_Opnd (Cond))
3201 and then Compile_Time_Known_Value (Right_Opnd (Cond))
3202 then
3203 Val := Right_Opnd (Cond);
3205 -- Case of value op entity
3207 elsif Is_Entity_Name (Right_Opnd (Cond))
3208 and then Ent = Entity (Right_Opnd (Cond))
3209 and then Compile_Time_Known_Value (Left_Opnd (Cond))
3210 then
3211 Val := Left_Opnd (Cond);
3213 -- We are effectively swapping operands
3215 case Op is
3216 when N_Op_Eq => null;
3217 when N_Op_Ne => null;
3218 when N_Op_Lt => Op := N_Op_Gt;
3219 when N_Op_Gt => Op := N_Op_Lt;
3220 when N_Op_Le => Op := N_Op_Ge;
3221 when N_Op_Ge => Op := N_Op_Le;
3222 when others => raise Program_Error;
3223 end case;
3225 else
3226 Op := N_Empty;
3227 end if;
3229 return;
3231 elsif Nkind_In (Cond,
3232 N_Type_Conversion,
3233 N_Qualified_Expression,
3234 N_Expression_With_Actions)
3235 then
3236 Cond := Expression (Cond);
3238 -- Case of Boolean variable reference, return as though the
3239 -- reference had said var = True.
3241 else
3242 if Is_Entity_Name (Cond) and then Ent = Entity (Cond) then
3243 Val := New_Occurrence_Of (Standard_True, Sloc (Cond));
3245 if Sens = False then
3246 Op := N_Op_Ne;
3247 else
3248 Op := N_Op_Eq;
3249 end if;
3250 end if;
3251 end if;
3252 end Process_Current_Value_Condition;
3254 -- Start of processing for Get_Current_Value_Condition
3256 begin
3257 Op := N_Empty;
3258 Val := Empty;
3260 -- Immediate return, nothing doing, if this is not an object
3262 if Ekind (Ent) not in Object_Kind then
3263 return;
3264 end if;
3266 -- Otherwise examine current value
3268 declare
3269 CV : constant Node_Id := Current_Value (Ent);
3270 Sens : Boolean;
3271 Stm : Node_Id;
3273 begin
3274 -- If statement. Condition is known true in THEN section, known False
3275 -- in any ELSIF or ELSE part, and unknown outside the IF statement.
3277 if Nkind (CV) = N_If_Statement then
3279 -- Before start of IF statement
3281 if Loc < Sloc (CV) then
3282 return;
3284 -- After end of IF statement
3286 elsif Loc >= Sloc (CV) + Text_Ptr (UI_To_Int (End_Span (CV))) then
3287 return;
3288 end if;
3290 -- At this stage we know that we are within the IF statement, but
3291 -- unfortunately, the tree does not record the SLOC of the ELSE so
3292 -- we cannot use a simple SLOC comparison to distinguish between
3293 -- the then/else statements, so we have to climb the tree.
3295 declare
3296 N : Node_Id;
3298 begin
3299 N := Parent (Var);
3300 while Parent (N) /= CV loop
3301 N := Parent (N);
3303 -- If we fall off the top of the tree, then that's odd, but
3304 -- perhaps it could occur in some error situation, and the
3305 -- safest response is simply to assume that the outcome of
3306 -- the condition is unknown. No point in bombing during an
3307 -- attempt to optimize things.
3309 if No (N) then
3310 return;
3311 end if;
3312 end loop;
3314 -- Now we have N pointing to a node whose parent is the IF
3315 -- statement in question, so now we can tell if we are within
3316 -- the THEN statements.
3318 if Is_List_Member (N)
3319 and then List_Containing (N) = Then_Statements (CV)
3320 then
3321 Sens := True;
3323 -- If the variable reference does not come from source, we
3324 -- cannot reliably tell whether it appears in the else part.
3325 -- In particular, if it appears in generated code for a node
3326 -- that requires finalization, it may be attached to a list
3327 -- that has not been yet inserted into the code. For now,
3328 -- treat it as unknown.
3330 elsif not Comes_From_Source (N) then
3331 return;
3333 -- Otherwise we must be in ELSIF or ELSE part
3335 else
3336 Sens := False;
3337 end if;
3338 end;
3340 -- ELSIF part. Condition is known true within the referenced
3341 -- ELSIF, known False in any subsequent ELSIF or ELSE part,
3342 -- and unknown before the ELSE part or after the IF statement.
3344 elsif Nkind (CV) = N_Elsif_Part then
3346 -- if the Elsif_Part had condition_actions, the elsif has been
3347 -- rewritten as a nested if, and the original elsif_part is
3348 -- detached from the tree, so there is no way to obtain useful
3349 -- information on the current value of the variable.
3350 -- Can this be improved ???
3352 if No (Parent (CV)) then
3353 return;
3354 end if;
3356 Stm := Parent (CV);
3358 -- Before start of ELSIF part
3360 if Loc < Sloc (CV) then
3361 return;
3363 -- After end of IF statement
3365 elsif Loc >= Sloc (Stm) +
3366 Text_Ptr (UI_To_Int (End_Span (Stm)))
3367 then
3368 return;
3369 end if;
3371 -- Again we lack the SLOC of the ELSE, so we need to climb the
3372 -- tree to see if we are within the ELSIF part in question.
3374 declare
3375 N : Node_Id;
3377 begin
3378 N := Parent (Var);
3379 while Parent (N) /= Stm loop
3380 N := Parent (N);
3382 -- If we fall off the top of the tree, then that's odd, but
3383 -- perhaps it could occur in some error situation, and the
3384 -- safest response is simply to assume that the outcome of
3385 -- the condition is unknown. No point in bombing during an
3386 -- attempt to optimize things.
3388 if No (N) then
3389 return;
3390 end if;
3391 end loop;
3393 -- Now we have N pointing to a node whose parent is the IF
3394 -- statement in question, so see if is the ELSIF part we want.
3395 -- the THEN statements.
3397 if N = CV then
3398 Sens := True;
3400 -- Otherwise we must be in subsequent ELSIF or ELSE part
3402 else
3403 Sens := False;
3404 end if;
3405 end;
3407 -- Iteration scheme of while loop. The condition is known to be
3408 -- true within the body of the loop.
3410 elsif Nkind (CV) = N_Iteration_Scheme then
3411 declare
3412 Loop_Stmt : constant Node_Id := Parent (CV);
3414 begin
3415 -- Before start of body of loop
3417 if Loc < Sloc (Loop_Stmt) then
3418 return;
3420 -- After end of LOOP statement
3422 elsif Loc >= Sloc (End_Label (Loop_Stmt)) then
3423 return;
3425 -- We are within the body of the loop
3427 else
3428 Sens := True;
3429 end if;
3430 end;
3432 -- All other cases of Current_Value settings
3434 else
3435 return;
3436 end if;
3438 -- If we fall through here, then we have a reportable condition, Sens
3439 -- is True if the condition is true and False if it needs inverting.
3441 Process_Current_Value_Condition (Condition (CV), Sens);
3442 end;
3443 end Get_Current_Value_Condition;
3445 ---------------------
3446 -- Get_Stream_Size --
3447 ---------------------
3449 function Get_Stream_Size (E : Entity_Id) return Uint is
3450 begin
3451 -- If we have a Stream_Size clause for this type use it
3453 if Has_Stream_Size_Clause (E) then
3454 return Static_Integer (Expression (Stream_Size_Clause (E)));
3456 -- Otherwise the Stream_Size if the size of the type
3458 else
3459 return Esize (E);
3460 end if;
3461 end Get_Stream_Size;
3463 ---------------------------
3464 -- Has_Access_Constraint --
3465 ---------------------------
3467 function Has_Access_Constraint (E : Entity_Id) return Boolean is
3468 Disc : Entity_Id;
3469 T : constant Entity_Id := Etype (E);
3471 begin
3472 if Has_Per_Object_Constraint (E) and then Has_Discriminants (T) then
3473 Disc := First_Discriminant (T);
3474 while Present (Disc) loop
3475 if Is_Access_Type (Etype (Disc)) then
3476 return True;
3477 end if;
3479 Next_Discriminant (Disc);
3480 end loop;
3482 return False;
3483 else
3484 return False;
3485 end if;
3486 end Has_Access_Constraint;
3488 -----------------------------------------------------
3489 -- Has_Annotate_Pragma_For_External_Axiomatization --
3490 -----------------------------------------------------
3492 function Has_Annotate_Pragma_For_External_Axiomatization
3493 (E : Entity_Id) return Boolean
3495 function Is_Annotate_Pragma_For_External_Axiomatization
3496 (N : Node_Id) return Boolean;
3497 -- Returns whether N is
3498 -- pragma Annotate (GNATprove, External_Axiomatization);
3500 ----------------------------------------------------
3501 -- Is_Annotate_Pragma_For_External_Axiomatization --
3502 ----------------------------------------------------
3504 -- The general form of pragma Annotate is
3506 -- pragma Annotate (IDENTIFIER [, IDENTIFIER {, ARG}]);
3507 -- ARG ::= NAME | EXPRESSION
3509 -- The first two arguments are by convention intended to refer to an
3510 -- external tool and a tool-specific function. These arguments are
3511 -- not analyzed.
3513 -- The following is used to annotate a package specification which
3514 -- GNATprove should treat specially, because the axiomatization of
3515 -- this unit is given by the user instead of being automatically
3516 -- generated.
3518 -- pragma Annotate (GNATprove, External_Axiomatization);
3520 function Is_Annotate_Pragma_For_External_Axiomatization
3521 (N : Node_Id) return Boolean
3523 Name_GNATprove : constant String :=
3524 "gnatprove";
3525 Name_External_Axiomatization : constant String :=
3526 "external_axiomatization";
3527 -- Special names
3529 begin
3530 if Nkind (N) = N_Pragma
3531 and then Get_Pragma_Id (Pragma_Name (N)) = Pragma_Annotate
3532 and then List_Length (Pragma_Argument_Associations (N)) = 2
3533 then
3534 declare
3535 Arg1 : constant Node_Id :=
3536 First (Pragma_Argument_Associations (N));
3537 Arg2 : constant Node_Id := Next (Arg1);
3538 Nam1 : Name_Id;
3539 Nam2 : Name_Id;
3541 begin
3542 -- Fill in Name_Buffer with Name_GNATprove first, and then with
3543 -- Name_External_Axiomatization so that Name_Find returns the
3544 -- corresponding name. This takes care of all possible casings.
3546 Name_Len := 0;
3547 Add_Str_To_Name_Buffer (Name_GNATprove);
3548 Nam1 := Name_Find;
3550 Name_Len := 0;
3551 Add_Str_To_Name_Buffer (Name_External_Axiomatization);
3552 Nam2 := Name_Find;
3554 return Chars (Get_Pragma_Arg (Arg1)) = Nam1
3555 and then
3556 Chars (Get_Pragma_Arg (Arg2)) = Nam2;
3557 end;
3559 else
3560 return False;
3561 end if;
3562 end Is_Annotate_Pragma_For_External_Axiomatization;
3564 -- Local variables
3566 Decl : Node_Id;
3567 Vis_Decls : List_Id;
3568 N : Node_Id;
3570 -- Start of processing for Has_Annotate_Pragma_For_External_Axiomatization
3572 begin
3573 if Nkind (Parent (E)) = N_Defining_Program_Unit_Name then
3574 Decl := Parent (Parent (E));
3575 else
3576 Decl := Parent (E);
3577 end if;
3579 Vis_Decls := Visible_Declarations (Decl);
3581 N := First (Vis_Decls);
3582 while Present (N) loop
3584 -- Skip declarations generated by the frontend. Skip all pragmas
3585 -- that are not the desired Annotate pragma. Stop the search on
3586 -- the first non-pragma source declaration.
3588 if Comes_From_Source (N) then
3589 if Nkind (N) = N_Pragma then
3590 if Is_Annotate_Pragma_For_External_Axiomatization (N) then
3591 return True;
3592 end if;
3593 else
3594 return False;
3595 end if;
3596 end if;
3598 Next (N);
3599 end loop;
3601 return False;
3602 end Has_Annotate_Pragma_For_External_Axiomatization;
3604 --------------------
3605 -- Homonym_Number --
3606 --------------------
3608 function Homonym_Number (Subp : Entity_Id) return Nat is
3609 Count : Nat;
3610 Hom : Entity_Id;
3612 begin
3613 Count := 1;
3614 Hom := Homonym (Subp);
3615 while Present (Hom) loop
3616 if Scope (Hom) = Scope (Subp) then
3617 Count := Count + 1;
3618 end if;
3620 Hom := Homonym (Hom);
3621 end loop;
3623 return Count;
3624 end Homonym_Number;
3626 -----------------------------------
3627 -- In_Library_Level_Package_Body --
3628 -----------------------------------
3630 function In_Library_Level_Package_Body (Id : Entity_Id) return Boolean is
3631 begin
3632 -- First determine whether the entity appears at the library level, then
3633 -- look at the containing unit.
3635 if Is_Library_Level_Entity (Id) then
3636 declare
3637 Container : constant Node_Id := Cunit (Get_Source_Unit (Id));
3639 begin
3640 return Nkind (Unit (Container)) = N_Package_Body;
3641 end;
3642 end if;
3644 return False;
3645 end In_Library_Level_Package_Body;
3647 ------------------------------
3648 -- In_Unconditional_Context --
3649 ------------------------------
3651 function In_Unconditional_Context (Node : Node_Id) return Boolean is
3652 P : Node_Id;
3654 begin
3655 P := Node;
3656 while Present (P) loop
3657 case Nkind (P) is
3658 when N_Subprogram_Body =>
3659 return True;
3661 when N_If_Statement =>
3662 return False;
3664 when N_Loop_Statement =>
3665 return False;
3667 when N_Case_Statement =>
3668 return False;
3670 when others =>
3671 P := Parent (P);
3672 end case;
3673 end loop;
3675 return False;
3676 end In_Unconditional_Context;
3678 -------------------
3679 -- Insert_Action --
3680 -------------------
3682 procedure Insert_Action (Assoc_Node : Node_Id; Ins_Action : Node_Id) is
3683 begin
3684 if Present (Ins_Action) then
3685 Insert_Actions (Assoc_Node, New_List (Ins_Action));
3686 end if;
3687 end Insert_Action;
3689 -- Version with check(s) suppressed
3691 procedure Insert_Action
3692 (Assoc_Node : Node_Id; Ins_Action : Node_Id; Suppress : Check_Id)
3694 begin
3695 Insert_Actions (Assoc_Node, New_List (Ins_Action), Suppress);
3696 end Insert_Action;
3698 -------------------------
3699 -- Insert_Action_After --
3700 -------------------------
3702 procedure Insert_Action_After
3703 (Assoc_Node : Node_Id;
3704 Ins_Action : Node_Id)
3706 begin
3707 Insert_Actions_After (Assoc_Node, New_List (Ins_Action));
3708 end Insert_Action_After;
3710 --------------------
3711 -- Insert_Actions --
3712 --------------------
3714 procedure Insert_Actions (Assoc_Node : Node_Id; Ins_Actions : List_Id) is
3715 N : Node_Id;
3716 P : Node_Id;
3718 Wrapped_Node : Node_Id := Empty;
3720 begin
3721 if No (Ins_Actions) or else Is_Empty_List (Ins_Actions) then
3722 return;
3723 end if;
3725 -- Ignore insert of actions from inside default expression (or other
3726 -- similar "spec expression") in the special spec-expression analyze
3727 -- mode. Any insertions at this point have no relevance, since we are
3728 -- only doing the analyze to freeze the types of any static expressions.
3729 -- See section "Handling of Default Expressions" in the spec of package
3730 -- Sem for further details.
3732 if In_Spec_Expression then
3733 return;
3734 end if;
3736 -- If the action derives from stuff inside a record, then the actions
3737 -- are attached to the current scope, to be inserted and analyzed on
3738 -- exit from the scope. The reason for this is that we may also be
3739 -- generating freeze actions at the same time, and they must eventually
3740 -- be elaborated in the correct order.
3742 if Is_Record_Type (Current_Scope)
3743 and then not Is_Frozen (Current_Scope)
3744 then
3745 if No (Scope_Stack.Table
3746 (Scope_Stack.Last).Pending_Freeze_Actions)
3747 then
3748 Scope_Stack.Table (Scope_Stack.Last).Pending_Freeze_Actions :=
3749 Ins_Actions;
3750 else
3751 Append_List
3752 (Ins_Actions,
3753 Scope_Stack.Table (Scope_Stack.Last).Pending_Freeze_Actions);
3754 end if;
3756 return;
3757 end if;
3759 -- We now intend to climb up the tree to find the right point to
3760 -- insert the actions. We start at Assoc_Node, unless this node is a
3761 -- subexpression in which case we start with its parent. We do this for
3762 -- two reasons. First it speeds things up. Second, if Assoc_Node is
3763 -- itself one of the special nodes like N_And_Then, then we assume that
3764 -- an initial request to insert actions for such a node does not expect
3765 -- the actions to get deposited in the node for later handling when the
3766 -- node is expanded, since clearly the node is being dealt with by the
3767 -- caller. Note that in the subexpression case, N is always the child we
3768 -- came from.
3770 -- N_Raise_xxx_Error is an annoying special case, it is a statement if
3771 -- it has type Standard_Void_Type, and a subexpression otherwise.
3772 -- otherwise. Procedure calls, and similarly procedure attribute
3773 -- references, are also statements.
3775 if Nkind (Assoc_Node) in N_Subexpr
3776 and then (Nkind (Assoc_Node) not in N_Raise_xxx_Error
3777 or else Etype (Assoc_Node) /= Standard_Void_Type)
3778 and then Nkind (Assoc_Node) /= N_Procedure_Call_Statement
3779 and then (Nkind (Assoc_Node) /= N_Attribute_Reference
3780 or else not Is_Procedure_Attribute_Name
3781 (Attribute_Name (Assoc_Node)))
3782 then
3783 N := Assoc_Node;
3784 P := Parent (Assoc_Node);
3786 -- Non-subexpression case. Note that N is initially Empty in this case
3787 -- (N is only guaranteed Non-Empty in the subexpr case).
3789 else
3790 N := Empty;
3791 P := Assoc_Node;
3792 end if;
3794 -- Capture root of the transient scope
3796 if Scope_Is_Transient then
3797 Wrapped_Node := Node_To_Be_Wrapped;
3798 end if;
3800 loop
3801 pragma Assert (Present (P));
3803 -- Make sure that inserted actions stay in the transient scope
3805 if Present (Wrapped_Node) and then N = Wrapped_Node then
3806 Store_Before_Actions_In_Scope (Ins_Actions);
3807 return;
3808 end if;
3810 case Nkind (P) is
3812 -- Case of right operand of AND THEN or OR ELSE. Put the actions
3813 -- in the Actions field of the right operand. They will be moved
3814 -- out further when the AND THEN or OR ELSE operator is expanded.
3815 -- Nothing special needs to be done for the left operand since
3816 -- in that case the actions are executed unconditionally.
3818 when N_Short_Circuit =>
3819 if N = Right_Opnd (P) then
3821 -- We are now going to either append the actions to the
3822 -- actions field of the short-circuit operation. We will
3823 -- also analyze the actions now.
3825 -- This analysis is really too early, the proper thing would
3826 -- be to just park them there now, and only analyze them if
3827 -- we find we really need them, and to it at the proper
3828 -- final insertion point. However attempting to this proved
3829 -- tricky, so for now we just kill current values before and
3830 -- after the analyze call to make sure we avoid peculiar
3831 -- optimizations from this out of order insertion.
3833 Kill_Current_Values;
3835 -- If P has already been expanded, we can't park new actions
3836 -- on it, so we need to expand them immediately, introducing
3837 -- an Expression_With_Actions. N can't be an expression
3838 -- with actions, or else then the actions would have been
3839 -- inserted at an inner level.
3841 if Analyzed (P) then
3842 pragma Assert (Nkind (N) /= N_Expression_With_Actions);
3843 Rewrite (N,
3844 Make_Expression_With_Actions (Sloc (N),
3845 Actions => Ins_Actions,
3846 Expression => Relocate_Node (N)));
3847 Analyze_And_Resolve (N);
3849 elsif Present (Actions (P)) then
3850 Insert_List_After_And_Analyze
3851 (Last (Actions (P)), Ins_Actions);
3852 else
3853 Set_Actions (P, Ins_Actions);
3854 Analyze_List (Actions (P));
3855 end if;
3857 Kill_Current_Values;
3859 return;
3860 end if;
3862 -- Then or Else dependent expression of an if expression. Add
3863 -- actions to Then_Actions or Else_Actions field as appropriate.
3864 -- The actions will be moved further out when the if is expanded.
3866 when N_If_Expression =>
3867 declare
3868 ThenX : constant Node_Id := Next (First (Expressions (P)));
3869 ElseX : constant Node_Id := Next (ThenX);
3871 begin
3872 -- If the enclosing expression is already analyzed, as
3873 -- is the case for nested elaboration checks, insert the
3874 -- conditional further out.
3876 if Analyzed (P) then
3877 null;
3879 -- Actions belong to the then expression, temporarily place
3880 -- them as Then_Actions of the if expression. They will be
3881 -- moved to the proper place later when the if expression
3882 -- is expanded.
3884 elsif N = ThenX then
3885 if Present (Then_Actions (P)) then
3886 Insert_List_After_And_Analyze
3887 (Last (Then_Actions (P)), Ins_Actions);
3888 else
3889 Set_Then_Actions (P, Ins_Actions);
3890 Analyze_List (Then_Actions (P));
3891 end if;
3893 return;
3895 -- Actions belong to the else expression, temporarily place
3896 -- them as Else_Actions of the if expression. They will be
3897 -- moved to the proper place later when the if expression
3898 -- is expanded.
3900 elsif N = ElseX then
3901 if Present (Else_Actions (P)) then
3902 Insert_List_After_And_Analyze
3903 (Last (Else_Actions (P)), Ins_Actions);
3904 else
3905 Set_Else_Actions (P, Ins_Actions);
3906 Analyze_List (Else_Actions (P));
3907 end if;
3909 return;
3911 -- Actions belong to the condition. In this case they are
3912 -- unconditionally executed, and so we can continue the
3913 -- search for the proper insert point.
3915 else
3916 null;
3917 end if;
3918 end;
3920 -- Alternative of case expression, we place the action in the
3921 -- Actions field of the case expression alternative, this will
3922 -- be handled when the case expression is expanded.
3924 when N_Case_Expression_Alternative =>
3925 if Present (Actions (P)) then
3926 Insert_List_After_And_Analyze
3927 (Last (Actions (P)), Ins_Actions);
3928 else
3929 Set_Actions (P, Ins_Actions);
3930 Analyze_List (Actions (P));
3931 end if;
3933 return;
3935 -- Case of appearing within an Expressions_With_Actions node. When
3936 -- the new actions come from the expression of the expression with
3937 -- actions, they must be added to the existing actions. The other
3938 -- alternative is when the new actions are related to one of the
3939 -- existing actions of the expression with actions, and should
3940 -- never reach here: if actions are inserted on a statement
3941 -- within the Actions of an expression with actions, or on some
3942 -- sub-expression of such a statement, then the outermost proper
3943 -- insertion point is right before the statement, and we should
3944 -- never climb up as far as the N_Expression_With_Actions itself.
3946 when N_Expression_With_Actions =>
3947 if N = Expression (P) then
3948 if Is_Empty_List (Actions (P)) then
3949 Append_List_To (Actions (P), Ins_Actions);
3950 Analyze_List (Actions (P));
3951 else
3952 Insert_List_After_And_Analyze
3953 (Last (Actions (P)), Ins_Actions);
3954 end if;
3956 return;
3958 else
3959 raise Program_Error;
3960 end if;
3962 -- Case of appearing in the condition of a while expression or
3963 -- elsif. We insert the actions into the Condition_Actions field.
3964 -- They will be moved further out when the while loop or elsif
3965 -- is analyzed.
3967 when N_Iteration_Scheme |
3968 N_Elsif_Part
3970 if N = Condition (P) then
3971 if Present (Condition_Actions (P)) then
3972 Insert_List_After_And_Analyze
3973 (Last (Condition_Actions (P)), Ins_Actions);
3974 else
3975 Set_Condition_Actions (P, Ins_Actions);
3977 -- Set the parent of the insert actions explicitly. This
3978 -- is not a syntactic field, but we need the parent field
3979 -- set, in particular so that freeze can understand that
3980 -- it is dealing with condition actions, and properly
3981 -- insert the freezing actions.
3983 Set_Parent (Ins_Actions, P);
3984 Analyze_List (Condition_Actions (P));
3985 end if;
3987 return;
3988 end if;
3990 -- Statements, declarations, pragmas, representation clauses
3992 when
3993 -- Statements
3995 N_Procedure_Call_Statement |
3996 N_Statement_Other_Than_Procedure_Call |
3998 -- Pragmas
4000 N_Pragma |
4002 -- Representation_Clause
4004 N_At_Clause |
4005 N_Attribute_Definition_Clause |
4006 N_Enumeration_Representation_Clause |
4007 N_Record_Representation_Clause |
4009 -- Declarations
4011 N_Abstract_Subprogram_Declaration |
4012 N_Entry_Body |
4013 N_Exception_Declaration |
4014 N_Exception_Renaming_Declaration |
4015 N_Expression_Function |
4016 N_Formal_Abstract_Subprogram_Declaration |
4017 N_Formal_Concrete_Subprogram_Declaration |
4018 N_Formal_Object_Declaration |
4019 N_Formal_Type_Declaration |
4020 N_Full_Type_Declaration |
4021 N_Function_Instantiation |
4022 N_Generic_Function_Renaming_Declaration |
4023 N_Generic_Package_Declaration |
4024 N_Generic_Package_Renaming_Declaration |
4025 N_Generic_Procedure_Renaming_Declaration |
4026 N_Generic_Subprogram_Declaration |
4027 N_Implicit_Label_Declaration |
4028 N_Incomplete_Type_Declaration |
4029 N_Number_Declaration |
4030 N_Object_Declaration |
4031 N_Object_Renaming_Declaration |
4032 N_Package_Body |
4033 N_Package_Body_Stub |
4034 N_Package_Declaration |
4035 N_Package_Instantiation |
4036 N_Package_Renaming_Declaration |
4037 N_Private_Extension_Declaration |
4038 N_Private_Type_Declaration |
4039 N_Procedure_Instantiation |
4040 N_Protected_Body |
4041 N_Protected_Body_Stub |
4042 N_Protected_Type_Declaration |
4043 N_Single_Task_Declaration |
4044 N_Subprogram_Body |
4045 N_Subprogram_Body_Stub |
4046 N_Subprogram_Declaration |
4047 N_Subprogram_Renaming_Declaration |
4048 N_Subtype_Declaration |
4049 N_Task_Body |
4050 N_Task_Body_Stub |
4051 N_Task_Type_Declaration |
4053 -- Use clauses can appear in lists of declarations
4055 N_Use_Package_Clause |
4056 N_Use_Type_Clause |
4058 -- Freeze entity behaves like a declaration or statement
4060 N_Freeze_Entity |
4061 N_Freeze_Generic_Entity
4063 -- Do not insert here if the item is not a list member (this
4064 -- happens for example with a triggering statement, and the
4065 -- proper approach is to insert before the entire select).
4067 if not Is_List_Member (P) then
4068 null;
4070 -- Do not insert if parent of P is an N_Component_Association
4071 -- node (i.e. we are in the context of an N_Aggregate or
4072 -- N_Extension_Aggregate node. In this case we want to insert
4073 -- before the entire aggregate.
4075 elsif Nkind (Parent (P)) = N_Component_Association then
4076 null;
4078 -- Do not insert if the parent of P is either an N_Variant node
4079 -- or an N_Record_Definition node, meaning in either case that
4080 -- P is a member of a component list, and that therefore the
4081 -- actions should be inserted outside the complete record
4082 -- declaration.
4084 elsif Nkind_In (Parent (P), N_Variant, N_Record_Definition) then
4085 null;
4087 -- Do not insert freeze nodes within the loop generated for
4088 -- an aggregate, because they may be elaborated too late for
4089 -- subsequent use in the back end: within a package spec the
4090 -- loop is part of the elaboration procedure and is only
4091 -- elaborated during the second pass.
4093 -- If the loop comes from source, or the entity is local to the
4094 -- loop itself it must remain within.
4096 elsif Nkind (Parent (P)) = N_Loop_Statement
4097 and then not Comes_From_Source (Parent (P))
4098 and then Nkind (First (Ins_Actions)) = N_Freeze_Entity
4099 and then
4100 Scope (Entity (First (Ins_Actions))) /= Current_Scope
4101 then
4102 null;
4104 -- Otherwise we can go ahead and do the insertion
4106 elsif P = Wrapped_Node then
4107 Store_Before_Actions_In_Scope (Ins_Actions);
4108 return;
4110 else
4111 Insert_List_Before_And_Analyze (P, Ins_Actions);
4112 return;
4113 end if;
4115 -- A special case, N_Raise_xxx_Error can act either as a statement
4116 -- or a subexpression. We tell the difference by looking at the
4117 -- Etype. It is set to Standard_Void_Type in the statement case.
4119 when
4120 N_Raise_xxx_Error =>
4121 if Etype (P) = Standard_Void_Type then
4122 if P = Wrapped_Node then
4123 Store_Before_Actions_In_Scope (Ins_Actions);
4124 else
4125 Insert_List_Before_And_Analyze (P, Ins_Actions);
4126 end if;
4128 return;
4130 -- In the subexpression case, keep climbing
4132 else
4133 null;
4134 end if;
4136 -- If a component association appears within a loop created for
4137 -- an array aggregate, attach the actions to the association so
4138 -- they can be subsequently inserted within the loop. For other
4139 -- component associations insert outside of the aggregate. For
4140 -- an association that will generate a loop, its Loop_Actions
4141 -- attribute is already initialized (see exp_aggr.adb).
4143 -- The list of loop_actions can in turn generate additional ones,
4144 -- that are inserted before the associated node. If the associated
4145 -- node is outside the aggregate, the new actions are collected
4146 -- at the end of the loop actions, to respect the order in which
4147 -- they are to be elaborated.
4149 when
4150 N_Component_Association =>
4151 if Nkind (Parent (P)) = N_Aggregate
4152 and then Present (Loop_Actions (P))
4153 then
4154 if Is_Empty_List (Loop_Actions (P)) then
4155 Set_Loop_Actions (P, Ins_Actions);
4156 Analyze_List (Ins_Actions);
4158 else
4159 declare
4160 Decl : Node_Id;
4162 begin
4163 -- Check whether these actions were generated by a
4164 -- declaration that is part of the loop_ actions
4165 -- for the component_association.
4167 Decl := Assoc_Node;
4168 while Present (Decl) loop
4169 exit when Parent (Decl) = P
4170 and then Is_List_Member (Decl)
4171 and then
4172 List_Containing (Decl) = Loop_Actions (P);
4173 Decl := Parent (Decl);
4174 end loop;
4176 if Present (Decl) then
4177 Insert_List_Before_And_Analyze
4178 (Decl, Ins_Actions);
4179 else
4180 Insert_List_After_And_Analyze
4181 (Last (Loop_Actions (P)), Ins_Actions);
4182 end if;
4183 end;
4184 end if;
4186 return;
4188 else
4189 null;
4190 end if;
4192 -- Another special case, an attribute denoting a procedure call
4194 when
4195 N_Attribute_Reference =>
4196 if Is_Procedure_Attribute_Name (Attribute_Name (P)) then
4197 if P = Wrapped_Node then
4198 Store_Before_Actions_In_Scope (Ins_Actions);
4199 else
4200 Insert_List_Before_And_Analyze (P, Ins_Actions);
4201 end if;
4203 return;
4205 -- In the subexpression case, keep climbing
4207 else
4208 null;
4209 end if;
4211 -- A contract node should not belong to the tree
4213 when N_Contract =>
4214 raise Program_Error;
4216 -- For all other node types, keep climbing tree
4218 when
4219 N_Abortable_Part |
4220 N_Accept_Alternative |
4221 N_Access_Definition |
4222 N_Access_Function_Definition |
4223 N_Access_Procedure_Definition |
4224 N_Access_To_Object_Definition |
4225 N_Aggregate |
4226 N_Allocator |
4227 N_Aspect_Specification |
4228 N_Case_Expression |
4229 N_Case_Statement_Alternative |
4230 N_Character_Literal |
4231 N_Compilation_Unit |
4232 N_Compilation_Unit_Aux |
4233 N_Component_Clause |
4234 N_Component_Declaration |
4235 N_Component_Definition |
4236 N_Component_List |
4237 N_Constrained_Array_Definition |
4238 N_Decimal_Fixed_Point_Definition |
4239 N_Defining_Character_Literal |
4240 N_Defining_Identifier |
4241 N_Defining_Operator_Symbol |
4242 N_Defining_Program_Unit_Name |
4243 N_Delay_Alternative |
4244 N_Delta_Constraint |
4245 N_Derived_Type_Definition |
4246 N_Designator |
4247 N_Digits_Constraint |
4248 N_Discriminant_Association |
4249 N_Discriminant_Specification |
4250 N_Empty |
4251 N_Entry_Body_Formal_Part |
4252 N_Entry_Call_Alternative |
4253 N_Entry_Declaration |
4254 N_Entry_Index_Specification |
4255 N_Enumeration_Type_Definition |
4256 N_Error |
4257 N_Exception_Handler |
4258 N_Expanded_Name |
4259 N_Explicit_Dereference |
4260 N_Extension_Aggregate |
4261 N_Floating_Point_Definition |
4262 N_Formal_Decimal_Fixed_Point_Definition |
4263 N_Formal_Derived_Type_Definition |
4264 N_Formal_Discrete_Type_Definition |
4265 N_Formal_Floating_Point_Definition |
4266 N_Formal_Modular_Type_Definition |
4267 N_Formal_Ordinary_Fixed_Point_Definition |
4268 N_Formal_Package_Declaration |
4269 N_Formal_Private_Type_Definition |
4270 N_Formal_Incomplete_Type_Definition |
4271 N_Formal_Signed_Integer_Type_Definition |
4272 N_Function_Call |
4273 N_Function_Specification |
4274 N_Generic_Association |
4275 N_Handled_Sequence_Of_Statements |
4276 N_Identifier |
4277 N_In |
4278 N_Index_Or_Discriminant_Constraint |
4279 N_Indexed_Component |
4280 N_Integer_Literal |
4281 N_Iterator_Specification |
4282 N_Itype_Reference |
4283 N_Label |
4284 N_Loop_Parameter_Specification |
4285 N_Mod_Clause |
4286 N_Modular_Type_Definition |
4287 N_Not_In |
4288 N_Null |
4289 N_Op_Abs |
4290 N_Op_Add |
4291 N_Op_And |
4292 N_Op_Concat |
4293 N_Op_Divide |
4294 N_Op_Eq |
4295 N_Op_Expon |
4296 N_Op_Ge |
4297 N_Op_Gt |
4298 N_Op_Le |
4299 N_Op_Lt |
4300 N_Op_Minus |
4301 N_Op_Mod |
4302 N_Op_Multiply |
4303 N_Op_Ne |
4304 N_Op_Not |
4305 N_Op_Or |
4306 N_Op_Plus |
4307 N_Op_Rem |
4308 N_Op_Rotate_Left |
4309 N_Op_Rotate_Right |
4310 N_Op_Shift_Left |
4311 N_Op_Shift_Right |
4312 N_Op_Shift_Right_Arithmetic |
4313 N_Op_Subtract |
4314 N_Op_Xor |
4315 N_Operator_Symbol |
4316 N_Ordinary_Fixed_Point_Definition |
4317 N_Others_Choice |
4318 N_Package_Specification |
4319 N_Parameter_Association |
4320 N_Parameter_Specification |
4321 N_Pop_Constraint_Error_Label |
4322 N_Pop_Program_Error_Label |
4323 N_Pop_Storage_Error_Label |
4324 N_Pragma_Argument_Association |
4325 N_Procedure_Specification |
4326 N_Protected_Definition |
4327 N_Push_Constraint_Error_Label |
4328 N_Push_Program_Error_Label |
4329 N_Push_Storage_Error_Label |
4330 N_Qualified_Expression |
4331 N_Quantified_Expression |
4332 N_Raise_Expression |
4333 N_Range |
4334 N_Range_Constraint |
4335 N_Real_Literal |
4336 N_Real_Range_Specification |
4337 N_Record_Definition |
4338 N_Reference |
4339 N_SCIL_Dispatch_Table_Tag_Init |
4340 N_SCIL_Dispatching_Call |
4341 N_SCIL_Membership_Test |
4342 N_Selected_Component |
4343 N_Signed_Integer_Type_Definition |
4344 N_Single_Protected_Declaration |
4345 N_Slice |
4346 N_String_Literal |
4347 N_Subtype_Indication |
4348 N_Subunit |
4349 N_Task_Definition |
4350 N_Terminate_Alternative |
4351 N_Triggering_Alternative |
4352 N_Type_Conversion |
4353 N_Unchecked_Expression |
4354 N_Unchecked_Type_Conversion |
4355 N_Unconstrained_Array_Definition |
4356 N_Unused_At_End |
4357 N_Unused_At_Start |
4358 N_Variant |
4359 N_Variant_Part |
4360 N_Validate_Unchecked_Conversion |
4361 N_With_Clause
4363 null;
4365 end case;
4367 -- If we fall through above tests, keep climbing tree
4369 N := P;
4371 if Nkind (Parent (N)) = N_Subunit then
4373 -- This is the proper body corresponding to a stub. Insertion must
4374 -- be done at the point of the stub, which is in the declarative
4375 -- part of the parent unit.
4377 P := Corresponding_Stub (Parent (N));
4379 else
4380 P := Parent (N);
4381 end if;
4382 end loop;
4383 end Insert_Actions;
4385 -- Version with check(s) suppressed
4387 procedure Insert_Actions
4388 (Assoc_Node : Node_Id;
4389 Ins_Actions : List_Id;
4390 Suppress : Check_Id)
4392 begin
4393 if Suppress = All_Checks then
4394 declare
4395 Sva : constant Suppress_Array := Scope_Suppress.Suppress;
4396 begin
4397 Scope_Suppress.Suppress := (others => True);
4398 Insert_Actions (Assoc_Node, Ins_Actions);
4399 Scope_Suppress.Suppress := Sva;
4400 end;
4402 else
4403 declare
4404 Svg : constant Boolean := Scope_Suppress.Suppress (Suppress);
4405 begin
4406 Scope_Suppress.Suppress (Suppress) := True;
4407 Insert_Actions (Assoc_Node, Ins_Actions);
4408 Scope_Suppress.Suppress (Suppress) := Svg;
4409 end;
4410 end if;
4411 end Insert_Actions;
4413 --------------------------
4414 -- Insert_Actions_After --
4415 --------------------------
4417 procedure Insert_Actions_After
4418 (Assoc_Node : Node_Id;
4419 Ins_Actions : List_Id)
4421 begin
4422 if Scope_Is_Transient and then Assoc_Node = Node_To_Be_Wrapped then
4423 Store_After_Actions_In_Scope (Ins_Actions);
4424 else
4425 Insert_List_After_And_Analyze (Assoc_Node, Ins_Actions);
4426 end if;
4427 end Insert_Actions_After;
4429 ------------------------
4430 -- Insert_Declaration --
4431 ------------------------
4433 procedure Insert_Declaration (N : Node_Id; Decl : Node_Id) is
4434 P : Node_Id;
4436 begin
4437 pragma Assert (Nkind (N) in N_Subexpr);
4439 -- Climb until we find a procedure or a package
4441 P := N;
4442 loop
4443 pragma Assert (Present (Parent (P)));
4444 P := Parent (P);
4446 if Is_List_Member (P) then
4447 exit when Nkind_In (Parent (P), N_Package_Specification,
4448 N_Subprogram_Body);
4450 -- Special handling for handled sequence of statements, we must
4451 -- insert in the statements not the exception handlers!
4453 if Nkind (Parent (P)) = N_Handled_Sequence_Of_Statements then
4454 P := First (Statements (Parent (P)));
4455 exit;
4456 end if;
4457 end if;
4458 end loop;
4460 -- Now do the insertion
4462 Insert_Before (P, Decl);
4463 Analyze (Decl);
4464 end Insert_Declaration;
4466 ---------------------------------
4467 -- Insert_Library_Level_Action --
4468 ---------------------------------
4470 procedure Insert_Library_Level_Action (N : Node_Id) is
4471 Aux : constant Node_Id := Aux_Decls_Node (Cunit (Main_Unit));
4473 begin
4474 Push_Scope (Cunit_Entity (Main_Unit));
4475 -- ??? should this be Current_Sem_Unit instead of Main_Unit?
4477 if No (Actions (Aux)) then
4478 Set_Actions (Aux, New_List (N));
4479 else
4480 Append (N, Actions (Aux));
4481 end if;
4483 Analyze (N);
4484 Pop_Scope;
4485 end Insert_Library_Level_Action;
4487 ----------------------------------
4488 -- Insert_Library_Level_Actions --
4489 ----------------------------------
4491 procedure Insert_Library_Level_Actions (L : List_Id) is
4492 Aux : constant Node_Id := Aux_Decls_Node (Cunit (Main_Unit));
4494 begin
4495 if Is_Non_Empty_List (L) then
4496 Push_Scope (Cunit_Entity (Main_Unit));
4497 -- ??? should this be Current_Sem_Unit instead of Main_Unit?
4499 if No (Actions (Aux)) then
4500 Set_Actions (Aux, L);
4501 Analyze_List (L);
4502 else
4503 Insert_List_After_And_Analyze (Last (Actions (Aux)), L);
4504 end if;
4506 Pop_Scope;
4507 end if;
4508 end Insert_Library_Level_Actions;
4510 ----------------------
4511 -- Inside_Init_Proc --
4512 ----------------------
4514 function Inside_Init_Proc return Boolean is
4515 S : Entity_Id;
4517 begin
4518 S := Current_Scope;
4519 while Present (S) and then S /= Standard_Standard loop
4520 if Is_Init_Proc (S) then
4521 return True;
4522 else
4523 S := Scope (S);
4524 end if;
4525 end loop;
4527 return False;
4528 end Inside_Init_Proc;
4530 ----------------------------
4531 -- Is_All_Null_Statements --
4532 ----------------------------
4534 function Is_All_Null_Statements (L : List_Id) return Boolean is
4535 Stm : Node_Id;
4537 begin
4538 Stm := First (L);
4539 while Present (Stm) loop
4540 if Nkind (Stm) /= N_Null_Statement then
4541 return False;
4542 end if;
4544 Next (Stm);
4545 end loop;
4547 return True;
4548 end Is_All_Null_Statements;
4550 --------------------------------------------------
4551 -- Is_Displacement_Of_Object_Or_Function_Result --
4552 --------------------------------------------------
4554 function Is_Displacement_Of_Object_Or_Function_Result
4555 (Obj_Id : Entity_Id) return Boolean
4557 function Is_Controlled_Function_Call (N : Node_Id) return Boolean;
4558 -- Determine if particular node denotes a controlled function call. The
4559 -- call may have been heavily expanded.
4561 function Is_Displace_Call (N : Node_Id) return Boolean;
4562 -- Determine whether a particular node is a call to Ada.Tags.Displace.
4563 -- The call might be nested within other actions such as conversions.
4565 function Is_Source_Object (N : Node_Id) return Boolean;
4566 -- Determine whether a particular node denotes a source object
4568 ---------------------------------
4569 -- Is_Controlled_Function_Call --
4570 ---------------------------------
4572 function Is_Controlled_Function_Call (N : Node_Id) return Boolean is
4573 Expr : Node_Id := Original_Node (N);
4575 begin
4576 if Nkind (Expr) = N_Function_Call then
4577 Expr := Name (Expr);
4579 -- When a function call appears in Object.Operation format, the
4580 -- original representation has two possible forms depending on the
4581 -- availability of actual parameters:
4583 -- Obj.Func_Call N_Selected_Component
4584 -- Obj.Func_Call (Param) N_Indexed_Component
4586 else
4587 if Nkind (Expr) = N_Indexed_Component then
4588 Expr := Prefix (Expr);
4589 end if;
4591 if Nkind (Expr) = N_Selected_Component then
4592 Expr := Selector_Name (Expr);
4593 end if;
4594 end if;
4596 return
4597 Nkind_In (Expr, N_Expanded_Name, N_Identifier)
4598 and then Ekind (Entity (Expr)) = E_Function
4599 and then Needs_Finalization (Etype (Entity (Expr)));
4600 end Is_Controlled_Function_Call;
4602 ----------------------
4603 -- Is_Displace_Call --
4604 ----------------------
4606 function Is_Displace_Call (N : Node_Id) return Boolean is
4607 Call : Node_Id := N;
4609 begin
4610 -- Strip various actions which may precede a call to Displace
4612 loop
4613 if Nkind (Call) = N_Explicit_Dereference then
4614 Call := Prefix (Call);
4616 elsif Nkind_In (Call, N_Type_Conversion,
4617 N_Unchecked_Type_Conversion)
4618 then
4619 Call := Expression (Call);
4621 else
4622 exit;
4623 end if;
4624 end loop;
4626 return
4627 Present (Call)
4628 and then Nkind (Call) = N_Function_Call
4629 and then Is_RTE (Entity (Name (Call)), RE_Displace);
4630 end Is_Displace_Call;
4632 ----------------------
4633 -- Is_Source_Object --
4634 ----------------------
4636 function Is_Source_Object (N : Node_Id) return Boolean is
4637 begin
4638 return
4639 Present (N)
4640 and then Nkind (N) in N_Has_Entity
4641 and then Is_Object (Entity (N))
4642 and then Comes_From_Source (N);
4643 end Is_Source_Object;
4645 -- Local variables
4647 Decl : constant Node_Id := Parent (Obj_Id);
4648 Obj_Typ : constant Entity_Id := Base_Type (Etype (Obj_Id));
4649 Orig_Decl : constant Node_Id := Original_Node (Decl);
4651 -- Start of processing for Is_Displacement_Of_Object_Or_Function_Result
4653 begin
4654 -- Case 1:
4656 -- Obj : CW_Type := Function_Call (...);
4658 -- rewritten into:
4660 -- Tmp : ... := Function_Call (...)'reference;
4661 -- Obj : CW_Type renames (... Ada.Tags.Displace (Tmp));
4663 -- where the return type of the function and the class-wide type require
4664 -- dispatch table pointer displacement.
4666 -- Case 2:
4668 -- Obj : CW_Type := Src_Obj;
4670 -- rewritten into:
4672 -- Obj : CW_Type renames (... Ada.Tags.Displace (Src_Obj));
4674 -- where the type of the source object and the class-wide type require
4675 -- dispatch table pointer displacement.
4677 return
4678 Nkind (Decl) = N_Object_Renaming_Declaration
4679 and then Nkind (Orig_Decl) = N_Object_Declaration
4680 and then Comes_From_Source (Orig_Decl)
4681 and then Is_Class_Wide_Type (Obj_Typ)
4682 and then Is_Displace_Call (Renamed_Object (Obj_Id))
4683 and then
4684 (Is_Controlled_Function_Call (Expression (Orig_Decl))
4685 or else Is_Source_Object (Expression (Orig_Decl)));
4686 end Is_Displacement_Of_Object_Or_Function_Result;
4688 ------------------------------
4689 -- Is_Finalizable_Transient --
4690 ------------------------------
4692 function Is_Finalizable_Transient
4693 (Decl : Node_Id;
4694 Rel_Node : Node_Id) return Boolean
4696 Obj_Id : constant Entity_Id := Defining_Identifier (Decl);
4697 Obj_Typ : constant Entity_Id := Base_Type (Etype (Obj_Id));
4698 Desig : Entity_Id := Obj_Typ;
4700 function Initialized_By_Access (Trans_Id : Entity_Id) return Boolean;
4701 -- Determine whether transient object Trans_Id is initialized either
4702 -- by a function call which returns an access type or simply renames
4703 -- another pointer.
4705 function Initialized_By_Aliased_BIP_Func_Call
4706 (Trans_Id : Entity_Id) return Boolean;
4707 -- Determine whether transient object Trans_Id is initialized by a
4708 -- build-in-place function call where the BIPalloc parameter is of
4709 -- value 1 and BIPaccess is not null. This case creates an aliasing
4710 -- between the returned value and the value denoted by BIPaccess.
4712 function Is_Aliased
4713 (Trans_Id : Entity_Id;
4714 First_Stmt : Node_Id) return Boolean;
4715 -- Determine whether transient object Trans_Id has been renamed or
4716 -- aliased through 'reference in the statement list starting from
4717 -- First_Stmt.
4719 function Is_Allocated (Trans_Id : Entity_Id) return Boolean;
4720 -- Determine whether transient object Trans_Id is allocated on the heap
4722 function Is_Iterated_Container
4723 (Trans_Id : Entity_Id;
4724 First_Stmt : Node_Id) return Boolean;
4725 -- Determine whether transient object Trans_Id denotes a container which
4726 -- is in the process of being iterated in the statement list starting
4727 -- from First_Stmt.
4729 ---------------------------
4730 -- Initialized_By_Access --
4731 ---------------------------
4733 function Initialized_By_Access (Trans_Id : Entity_Id) return Boolean is
4734 Expr : constant Node_Id := Expression (Parent (Trans_Id));
4736 begin
4737 return
4738 Present (Expr)
4739 and then Nkind (Expr) /= N_Reference
4740 and then Is_Access_Type (Etype (Expr));
4741 end Initialized_By_Access;
4743 ------------------------------------------
4744 -- Initialized_By_Aliased_BIP_Func_Call --
4745 ------------------------------------------
4747 function Initialized_By_Aliased_BIP_Func_Call
4748 (Trans_Id : Entity_Id) return Boolean
4750 Call : Node_Id := Expression (Parent (Trans_Id));
4752 begin
4753 -- Build-in-place calls usually appear in 'reference format
4755 if Nkind (Call) = N_Reference then
4756 Call := Prefix (Call);
4757 end if;
4759 if Is_Build_In_Place_Function_Call (Call) then
4760 declare
4761 Access_Nam : Name_Id := No_Name;
4762 Access_OK : Boolean := False;
4763 Actual : Node_Id;
4764 Alloc_Nam : Name_Id := No_Name;
4765 Alloc_OK : Boolean := False;
4766 Formal : Node_Id;
4767 Func_Id : Entity_Id;
4768 Param : Node_Id;
4770 begin
4771 -- Examine all parameter associations of the function call
4773 Param := First (Parameter_Associations (Call));
4774 while Present (Param) loop
4775 if Nkind (Param) = N_Parameter_Association
4776 and then Nkind (Selector_Name (Param)) = N_Identifier
4777 then
4778 Actual := Explicit_Actual_Parameter (Param);
4779 Formal := Selector_Name (Param);
4781 -- Construct the names of formals BIPaccess and BIPalloc
4782 -- using the function name retrieved from an arbitrary
4783 -- formal.
4785 if Access_Nam = No_Name
4786 and then Alloc_Nam = No_Name
4787 and then Present (Entity (Formal))
4788 then
4789 Func_Id := Scope (Entity (Formal));
4791 Access_Nam :=
4792 New_External_Name (Chars (Func_Id),
4793 BIP_Formal_Suffix (BIP_Object_Access));
4795 Alloc_Nam :=
4796 New_External_Name (Chars (Func_Id),
4797 BIP_Formal_Suffix (BIP_Alloc_Form));
4798 end if;
4800 -- A match for BIPaccess => Temp has been found
4802 if Chars (Formal) = Access_Nam
4803 and then Nkind (Actual) /= N_Null
4804 then
4805 Access_OK := True;
4806 end if;
4808 -- A match for BIPalloc => 1 has been found
4810 if Chars (Formal) = Alloc_Nam
4811 and then Nkind (Actual) = N_Integer_Literal
4812 and then Intval (Actual) = Uint_1
4813 then
4814 Alloc_OK := True;
4815 end if;
4816 end if;
4818 Next (Param);
4819 end loop;
4821 return Access_OK and Alloc_OK;
4822 end;
4823 end if;
4825 return False;
4826 end Initialized_By_Aliased_BIP_Func_Call;
4828 ----------------
4829 -- Is_Aliased --
4830 ----------------
4832 function Is_Aliased
4833 (Trans_Id : Entity_Id;
4834 First_Stmt : Node_Id) return Boolean
4836 function Find_Renamed_Object (Ren_Decl : Node_Id) return Entity_Id;
4837 -- Given an object renaming declaration, retrieve the entity of the
4838 -- renamed name. Return Empty if the renamed name is anything other
4839 -- than a variable or a constant.
4841 -------------------------
4842 -- Find_Renamed_Object --
4843 -------------------------
4845 function Find_Renamed_Object (Ren_Decl : Node_Id) return Entity_Id is
4846 Ren_Obj : Node_Id := Empty;
4848 function Find_Object (N : Node_Id) return Traverse_Result;
4849 -- Try to detect an object which is either a constant or a
4850 -- variable.
4852 -----------------
4853 -- Find_Object --
4854 -----------------
4856 function Find_Object (N : Node_Id) return Traverse_Result is
4857 begin
4858 -- Stop the search once a constant or a variable has been
4859 -- detected.
4861 if Nkind (N) = N_Identifier
4862 and then Present (Entity (N))
4863 and then Ekind_In (Entity (N), E_Constant, E_Variable)
4864 then
4865 Ren_Obj := Entity (N);
4866 return Abandon;
4867 end if;
4869 return OK;
4870 end Find_Object;
4872 procedure Search is new Traverse_Proc (Find_Object);
4874 -- Local variables
4876 Typ : constant Entity_Id := Etype (Defining_Identifier (Ren_Decl));
4878 -- Start of processing for Find_Renamed_Object
4880 begin
4881 -- Actions related to dispatching calls may appear as renamings of
4882 -- tags. Do not process this type of renaming because it does not
4883 -- use the actual value of the object.
4885 if not Is_RTE (Typ, RE_Tag_Ptr) then
4886 Search (Name (Ren_Decl));
4887 end if;
4889 return Ren_Obj;
4890 end Find_Renamed_Object;
4892 -- Local variables
4894 Expr : Node_Id;
4895 Ren_Obj : Entity_Id;
4896 Stmt : Node_Id;
4898 -- Start of processing for Is_Aliased
4900 begin
4901 Stmt := First_Stmt;
4902 while Present (Stmt) loop
4903 if Nkind (Stmt) = N_Object_Declaration then
4904 Expr := Expression (Stmt);
4906 if Present (Expr)
4907 and then Nkind (Expr) = N_Reference
4908 and then Nkind (Prefix (Expr)) = N_Identifier
4909 and then Entity (Prefix (Expr)) = Trans_Id
4910 then
4911 return True;
4912 end if;
4914 elsif Nkind (Stmt) = N_Object_Renaming_Declaration then
4915 Ren_Obj := Find_Renamed_Object (Stmt);
4917 if Present (Ren_Obj) and then Ren_Obj = Trans_Id then
4918 return True;
4919 end if;
4920 end if;
4922 Next (Stmt);
4923 end loop;
4925 return False;
4926 end Is_Aliased;
4928 ------------------
4929 -- Is_Allocated --
4930 ------------------
4932 function Is_Allocated (Trans_Id : Entity_Id) return Boolean is
4933 Expr : constant Node_Id := Expression (Parent (Trans_Id));
4934 begin
4935 return
4936 Is_Access_Type (Etype (Trans_Id))
4937 and then Present (Expr)
4938 and then Nkind (Expr) = N_Allocator;
4939 end Is_Allocated;
4941 ---------------------------
4942 -- Is_Iterated_Container --
4943 ---------------------------
4945 function Is_Iterated_Container
4946 (Trans_Id : Entity_Id;
4947 First_Stmt : Node_Id) return Boolean
4949 Aspect : Node_Id;
4950 Call : Node_Id;
4951 Iter : Entity_Id;
4952 Param : Node_Id;
4953 Stmt : Node_Id;
4954 Typ : Entity_Id;
4956 begin
4957 -- It is not possible to iterate over containers in non-Ada 2012 code
4959 if Ada_Version < Ada_2012 then
4960 return False;
4961 end if;
4963 Typ := Etype (Trans_Id);
4965 -- Handle access type created for secondary stack use
4967 if Is_Access_Type (Typ) then
4968 Typ := Designated_Type (Typ);
4969 end if;
4971 -- Look for aspect Default_Iterator. It may be part of a type
4972 -- declaration for a container, or inherited from a base type
4973 -- or parent type.
4975 Aspect := Find_Value_Of_Aspect (Typ, Aspect_Default_Iterator);
4977 if Present (Aspect) then
4978 Iter := Entity (Aspect);
4980 -- Examine the statements following the container object and
4981 -- look for a call to the default iterate routine where the
4982 -- first parameter is the transient. Such a call appears as:
4984 -- It : Access_To_CW_Iterator :=
4985 -- Iterate (Tran_Id.all, ...)'reference;
4987 Stmt := First_Stmt;
4988 while Present (Stmt) loop
4990 -- Detect an object declaration which is initialized by a
4991 -- secondary stack function call.
4993 if Nkind (Stmt) = N_Object_Declaration
4994 and then Present (Expression (Stmt))
4995 and then Nkind (Expression (Stmt)) = N_Reference
4996 and then Nkind (Prefix (Expression (Stmt))) = N_Function_Call
4997 then
4998 Call := Prefix (Expression (Stmt));
5000 -- The call must invoke the default iterate routine of
5001 -- the container and the transient object must appear as
5002 -- the first actual parameter. Skip any calls whose names
5003 -- are not entities.
5005 if Is_Entity_Name (Name (Call))
5006 and then Entity (Name (Call)) = Iter
5007 and then Present (Parameter_Associations (Call))
5008 then
5009 Param := First (Parameter_Associations (Call));
5011 if Nkind (Param) = N_Explicit_Dereference
5012 and then Entity (Prefix (Param)) = Trans_Id
5013 then
5014 return True;
5015 end if;
5016 end if;
5017 end if;
5019 Next (Stmt);
5020 end loop;
5021 end if;
5023 return False;
5024 end Is_Iterated_Container;
5026 -- Start of processing for Is_Finalizable_Transient
5028 begin
5029 -- Handle access types
5031 if Is_Access_Type (Desig) then
5032 Desig := Available_View (Designated_Type (Desig));
5033 end if;
5035 return
5036 Ekind_In (Obj_Id, E_Constant, E_Variable)
5037 and then Needs_Finalization (Desig)
5038 and then Requires_Transient_Scope (Desig)
5039 and then Nkind (Rel_Node) /= N_Simple_Return_Statement
5041 -- Do not consider renamed or 'reference-d transient objects because
5042 -- the act of renaming extends the object's lifetime.
5044 and then not Is_Aliased (Obj_Id, Decl)
5046 -- Do not consider transient objects allocated on the heap since
5047 -- they are attached to a finalization master.
5049 and then not Is_Allocated (Obj_Id)
5051 -- If the transient object is a pointer, check that it is not
5052 -- initialized by a function which returns a pointer or acts as a
5053 -- renaming of another pointer.
5055 and then
5056 (not Is_Access_Type (Obj_Typ)
5057 or else not Initialized_By_Access (Obj_Id))
5059 -- Do not consider transient objects which act as indirect aliases
5060 -- of build-in-place function results.
5062 and then not Initialized_By_Aliased_BIP_Func_Call (Obj_Id)
5064 -- Do not consider conversions of tags to class-wide types
5066 and then not Is_Tag_To_Class_Wide_Conversion (Obj_Id)
5068 -- Do not consider containers in the context of iterator loops. Such
5069 -- transient objects must exist for as long as the loop is around,
5070 -- otherwise any operation carried out by the iterator will fail.
5072 and then not Is_Iterated_Container (Obj_Id, Decl);
5073 end Is_Finalizable_Transient;
5075 ---------------------------------
5076 -- Is_Fully_Repped_Tagged_Type --
5077 ---------------------------------
5079 function Is_Fully_Repped_Tagged_Type (T : Entity_Id) return Boolean is
5080 U : constant Entity_Id := Underlying_Type (T);
5081 Comp : Entity_Id;
5083 begin
5084 if No (U) or else not Is_Tagged_Type (U) then
5085 return False;
5086 elsif Has_Discriminants (U) then
5087 return False;
5088 elsif not Has_Specified_Layout (U) then
5089 return False;
5090 end if;
5092 -- Here we have a tagged type, see if it has any unlayed out fields
5093 -- other than a possible tag and parent fields. If so, we return False.
5095 Comp := First_Component (U);
5096 while Present (Comp) loop
5097 if not Is_Tag (Comp)
5098 and then Chars (Comp) /= Name_uParent
5099 and then No (Component_Clause (Comp))
5100 then
5101 return False;
5102 else
5103 Next_Component (Comp);
5104 end if;
5105 end loop;
5107 -- All components are layed out
5109 return True;
5110 end Is_Fully_Repped_Tagged_Type;
5112 ----------------------------------
5113 -- Is_Library_Level_Tagged_Type --
5114 ----------------------------------
5116 function Is_Library_Level_Tagged_Type (Typ : Entity_Id) return Boolean is
5117 begin
5118 return Is_Tagged_Type (Typ) and then Is_Library_Level_Entity (Typ);
5119 end Is_Library_Level_Tagged_Type;
5121 --------------------------
5122 -- Is_Non_BIP_Func_Call --
5123 --------------------------
5125 function Is_Non_BIP_Func_Call (Expr : Node_Id) return Boolean is
5126 begin
5127 -- The expected call is of the format
5129 -- Func_Call'reference
5131 return
5132 Nkind (Expr) = N_Reference
5133 and then Nkind (Prefix (Expr)) = N_Function_Call
5134 and then not Is_Build_In_Place_Function_Call (Prefix (Expr));
5135 end Is_Non_BIP_Func_Call;
5137 ------------------------------------
5138 -- Is_Object_Access_BIP_Func_Call --
5139 ------------------------------------
5141 function Is_Object_Access_BIP_Func_Call
5142 (Expr : Node_Id;
5143 Obj_Id : Entity_Id) return Boolean
5145 Access_Nam : Name_Id := No_Name;
5146 Actual : Node_Id;
5147 Call : Node_Id;
5148 Formal : Node_Id;
5149 Param : Node_Id;
5151 begin
5152 -- Build-in-place calls usually appear in 'reference format. Note that
5153 -- the accessibility check machinery may add an extra 'reference due to
5154 -- side effect removal.
5156 Call := Expr;
5157 while Nkind (Call) = N_Reference loop
5158 Call := Prefix (Call);
5159 end loop;
5161 if Nkind_In (Call, N_Qualified_Expression,
5162 N_Unchecked_Type_Conversion)
5163 then
5164 Call := Expression (Call);
5165 end if;
5167 if Is_Build_In_Place_Function_Call (Call) then
5169 -- Examine all parameter associations of the function call
5171 Param := First (Parameter_Associations (Call));
5172 while Present (Param) loop
5173 if Nkind (Param) = N_Parameter_Association
5174 and then Nkind (Selector_Name (Param)) = N_Identifier
5175 then
5176 Formal := Selector_Name (Param);
5177 Actual := Explicit_Actual_Parameter (Param);
5179 -- Construct the name of formal BIPaccess. It is much easier to
5180 -- extract the name of the function using an arbitrary formal's
5181 -- scope rather than the Name field of Call.
5183 if Access_Nam = No_Name and then Present (Entity (Formal)) then
5184 Access_Nam :=
5185 New_External_Name
5186 (Chars (Scope (Entity (Formal))),
5187 BIP_Formal_Suffix (BIP_Object_Access));
5188 end if;
5190 -- A match for BIPaccess => Obj_Id'Unrestricted_Access has been
5191 -- found.
5193 if Chars (Formal) = Access_Nam
5194 and then Nkind (Actual) = N_Attribute_Reference
5195 and then Attribute_Name (Actual) = Name_Unrestricted_Access
5196 and then Nkind (Prefix (Actual)) = N_Identifier
5197 and then Entity (Prefix (Actual)) = Obj_Id
5198 then
5199 return True;
5200 end if;
5201 end if;
5203 Next (Param);
5204 end loop;
5205 end if;
5207 return False;
5208 end Is_Object_Access_BIP_Func_Call;
5210 ----------------------------------
5211 -- Is_Possibly_Unaligned_Object --
5212 ----------------------------------
5214 function Is_Possibly_Unaligned_Object (N : Node_Id) return Boolean is
5215 T : constant Entity_Id := Etype (N);
5217 begin
5218 -- Objects are never unaligned on VMs
5220 if VM_Target /= No_VM then
5221 return False;
5222 end if;
5224 -- If renamed object, apply test to underlying object
5226 if Is_Entity_Name (N)
5227 and then Is_Object (Entity (N))
5228 and then Present (Renamed_Object (Entity (N)))
5229 then
5230 return Is_Possibly_Unaligned_Object (Renamed_Object (Entity (N)));
5231 end if;
5233 -- Tagged and controlled types and aliased types are always aligned, as
5234 -- are concurrent types.
5236 if Is_Aliased (T)
5237 or else Has_Controlled_Component (T)
5238 or else Is_Concurrent_Type (T)
5239 or else Is_Tagged_Type (T)
5240 or else Is_Controlled (T)
5241 then
5242 return False;
5243 end if;
5245 -- If this is an element of a packed array, may be unaligned
5247 if Is_Ref_To_Bit_Packed_Array (N) then
5248 return True;
5249 end if;
5251 -- Case of indexed component reference: test whether prefix is unaligned
5253 if Nkind (N) = N_Indexed_Component then
5254 return Is_Possibly_Unaligned_Object (Prefix (N));
5256 -- Case of selected component reference
5258 elsif Nkind (N) = N_Selected_Component then
5259 declare
5260 P : constant Node_Id := Prefix (N);
5261 C : constant Entity_Id := Entity (Selector_Name (N));
5262 M : Nat;
5263 S : Nat;
5265 begin
5266 -- If component reference is for an array with non-static bounds,
5267 -- then it is always aligned: we can only process unaligned arrays
5268 -- with static bounds (more precisely compile time known bounds).
5270 if Is_Array_Type (T)
5271 and then not Compile_Time_Known_Bounds (T)
5272 then
5273 return False;
5274 end if;
5276 -- If component is aliased, it is definitely properly aligned
5278 if Is_Aliased (C) then
5279 return False;
5280 end if;
5282 -- If component is for a type implemented as a scalar, and the
5283 -- record is packed, and the component is other than the first
5284 -- component of the record, then the component may be unaligned.
5286 if Is_Packed (Etype (P))
5287 and then Represented_As_Scalar (Etype (C))
5288 and then First_Entity (Scope (C)) /= C
5289 then
5290 return True;
5291 end if;
5293 -- Compute maximum possible alignment for T
5295 -- If alignment is known, then that settles things
5297 if Known_Alignment (T) then
5298 M := UI_To_Int (Alignment (T));
5300 -- If alignment is not known, tentatively set max alignment
5302 else
5303 M := Ttypes.Maximum_Alignment;
5305 -- We can reduce this if the Esize is known since the default
5306 -- alignment will never be more than the smallest power of 2
5307 -- that does not exceed this Esize value.
5309 if Known_Esize (T) then
5310 S := UI_To_Int (Esize (T));
5312 while (M / 2) >= S loop
5313 M := M / 2;
5314 end loop;
5315 end if;
5316 end if;
5318 -- The following code is historical, it used to be present but it
5319 -- is too cautious, because the front-end does not know the proper
5320 -- default alignments for the target. Also, if the alignment is
5321 -- not known, the front end can't know in any case. If a copy is
5322 -- needed, the back-end will take care of it. This whole section
5323 -- including this comment can be removed later ???
5325 -- If the component reference is for a record that has a specified
5326 -- alignment, and we either know it is too small, or cannot tell,
5327 -- then the component may be unaligned.
5329 -- What is the following commented out code ???
5331 -- if Known_Alignment (Etype (P))
5332 -- and then Alignment (Etype (P)) < Ttypes.Maximum_Alignment
5333 -- and then M > Alignment (Etype (P))
5334 -- then
5335 -- return True;
5336 -- end if;
5338 -- Case of component clause present which may specify an
5339 -- unaligned position.
5341 if Present (Component_Clause (C)) then
5343 -- Otherwise we can do a test to make sure that the actual
5344 -- start position in the record, and the length, are both
5345 -- consistent with the required alignment. If not, we know
5346 -- that we are unaligned.
5348 declare
5349 Align_In_Bits : constant Nat := M * System_Storage_Unit;
5350 begin
5351 if Component_Bit_Offset (C) mod Align_In_Bits /= 0
5352 or else Esize (C) mod Align_In_Bits /= 0
5353 then
5354 return True;
5355 end if;
5356 end;
5357 end if;
5359 -- Otherwise, for a component reference, test prefix
5361 return Is_Possibly_Unaligned_Object (P);
5362 end;
5364 -- If not a component reference, must be aligned
5366 else
5367 return False;
5368 end if;
5369 end Is_Possibly_Unaligned_Object;
5371 ---------------------------------
5372 -- Is_Possibly_Unaligned_Slice --
5373 ---------------------------------
5375 function Is_Possibly_Unaligned_Slice (N : Node_Id) return Boolean is
5376 begin
5377 -- Go to renamed object
5379 if Is_Entity_Name (N)
5380 and then Is_Object (Entity (N))
5381 and then Present (Renamed_Object (Entity (N)))
5382 then
5383 return Is_Possibly_Unaligned_Slice (Renamed_Object (Entity (N)));
5384 end if;
5386 -- The reference must be a slice
5388 if Nkind (N) /= N_Slice then
5389 return False;
5390 end if;
5392 -- We only need to worry if the target has strict alignment
5394 if not Target_Strict_Alignment then
5395 return False;
5396 end if;
5398 -- If it is a slice, then look at the array type being sliced
5400 declare
5401 Sarr : constant Node_Id := Prefix (N);
5402 -- Prefix of the slice, i.e. the array being sliced
5404 Styp : constant Entity_Id := Etype (Prefix (N));
5405 -- Type of the array being sliced
5407 Pref : Node_Id;
5408 Ptyp : Entity_Id;
5410 begin
5411 -- The problems arise if the array object that is being sliced
5412 -- is a component of a record or array, and we cannot guarantee
5413 -- the alignment of the array within its containing object.
5415 -- To investigate this, we look at successive prefixes to see
5416 -- if we have a worrisome indexed or selected component.
5418 Pref := Sarr;
5419 loop
5420 -- Case of array is part of an indexed component reference
5422 if Nkind (Pref) = N_Indexed_Component then
5423 Ptyp := Etype (Prefix (Pref));
5425 -- The only problematic case is when the array is packed, in
5426 -- which case we really know nothing about the alignment of
5427 -- individual components.
5429 if Is_Bit_Packed_Array (Ptyp) then
5430 return True;
5431 end if;
5433 -- Case of array is part of a selected component reference
5435 elsif Nkind (Pref) = N_Selected_Component then
5436 Ptyp := Etype (Prefix (Pref));
5438 -- We are definitely in trouble if the record in question
5439 -- has an alignment, and either we know this alignment is
5440 -- inconsistent with the alignment of the slice, or we don't
5441 -- know what the alignment of the slice should be.
5443 if Known_Alignment (Ptyp)
5444 and then (Unknown_Alignment (Styp)
5445 or else Alignment (Styp) > Alignment (Ptyp))
5446 then
5447 return True;
5448 end if;
5450 -- We are in potential trouble if the record type is packed.
5451 -- We could special case when we know that the array is the
5452 -- first component, but that's not such a simple case ???
5454 if Is_Packed (Ptyp) then
5455 return True;
5456 end if;
5458 -- We are in trouble if there is a component clause, and
5459 -- either we do not know the alignment of the slice, or
5460 -- the alignment of the slice is inconsistent with the
5461 -- bit position specified by the component clause.
5463 declare
5464 Field : constant Entity_Id := Entity (Selector_Name (Pref));
5465 begin
5466 if Present (Component_Clause (Field))
5467 and then
5468 (Unknown_Alignment (Styp)
5469 or else
5470 (Component_Bit_Offset (Field) mod
5471 (System_Storage_Unit * Alignment (Styp))) /= 0)
5472 then
5473 return True;
5474 end if;
5475 end;
5477 -- For cases other than selected or indexed components we know we
5478 -- are OK, since no issues arise over alignment.
5480 else
5481 return False;
5482 end if;
5484 -- We processed an indexed component or selected component
5485 -- reference that looked safe, so keep checking prefixes.
5487 Pref := Prefix (Pref);
5488 end loop;
5489 end;
5490 end Is_Possibly_Unaligned_Slice;
5492 -------------------------------
5493 -- Is_Related_To_Func_Return --
5494 -------------------------------
5496 function Is_Related_To_Func_Return (Id : Entity_Id) return Boolean is
5497 Expr : constant Node_Id := Related_Expression (Id);
5498 begin
5499 return
5500 Present (Expr)
5501 and then Nkind (Expr) = N_Explicit_Dereference
5502 and then Nkind (Parent (Expr)) = N_Simple_Return_Statement;
5503 end Is_Related_To_Func_Return;
5505 --------------------------------
5506 -- Is_Ref_To_Bit_Packed_Array --
5507 --------------------------------
5509 function Is_Ref_To_Bit_Packed_Array (N : Node_Id) return Boolean is
5510 Result : Boolean;
5511 Expr : Node_Id;
5513 begin
5514 if Is_Entity_Name (N)
5515 and then Is_Object (Entity (N))
5516 and then Present (Renamed_Object (Entity (N)))
5517 then
5518 return Is_Ref_To_Bit_Packed_Array (Renamed_Object (Entity (N)));
5519 end if;
5521 if Nkind_In (N, N_Indexed_Component, N_Selected_Component) then
5522 if Is_Bit_Packed_Array (Etype (Prefix (N))) then
5523 Result := True;
5524 else
5525 Result := Is_Ref_To_Bit_Packed_Array (Prefix (N));
5526 end if;
5528 if Result and then Nkind (N) = N_Indexed_Component then
5529 Expr := First (Expressions (N));
5530 while Present (Expr) loop
5531 Force_Evaluation (Expr);
5532 Next (Expr);
5533 end loop;
5534 end if;
5536 return Result;
5538 else
5539 return False;
5540 end if;
5541 end Is_Ref_To_Bit_Packed_Array;
5543 --------------------------------
5544 -- Is_Ref_To_Bit_Packed_Slice --
5545 --------------------------------
5547 function Is_Ref_To_Bit_Packed_Slice (N : Node_Id) return Boolean is
5548 begin
5549 if Nkind (N) = N_Type_Conversion then
5550 return Is_Ref_To_Bit_Packed_Slice (Expression (N));
5552 elsif Is_Entity_Name (N)
5553 and then Is_Object (Entity (N))
5554 and then Present (Renamed_Object (Entity (N)))
5555 then
5556 return Is_Ref_To_Bit_Packed_Slice (Renamed_Object (Entity (N)));
5558 elsif Nkind (N) = N_Slice
5559 and then Is_Bit_Packed_Array (Etype (Prefix (N)))
5560 then
5561 return True;
5563 elsif Nkind_In (N, N_Indexed_Component, N_Selected_Component) then
5564 return Is_Ref_To_Bit_Packed_Slice (Prefix (N));
5566 else
5567 return False;
5568 end if;
5569 end Is_Ref_To_Bit_Packed_Slice;
5571 -----------------------
5572 -- Is_Renamed_Object --
5573 -----------------------
5575 function Is_Renamed_Object (N : Node_Id) return Boolean is
5576 Pnod : constant Node_Id := Parent (N);
5577 Kind : constant Node_Kind := Nkind (Pnod);
5578 begin
5579 if Kind = N_Object_Renaming_Declaration then
5580 return True;
5581 elsif Nkind_In (Kind, N_Indexed_Component, N_Selected_Component) then
5582 return Is_Renamed_Object (Pnod);
5583 else
5584 return False;
5585 end if;
5586 end Is_Renamed_Object;
5588 --------------------------------------
5589 -- Is_Secondary_Stack_BIP_Func_Call --
5590 --------------------------------------
5592 function Is_Secondary_Stack_BIP_Func_Call (Expr : Node_Id) return Boolean is
5593 Alloc_Nam : Name_Id := No_Name;
5594 Actual : Node_Id;
5595 Call : Node_Id := Expr;
5596 Formal : Node_Id;
5597 Param : Node_Id;
5599 begin
5600 -- Build-in-place calls usually appear in 'reference format. Note that
5601 -- the accessibility check machinery may add an extra 'reference due to
5602 -- side effect removal.
5604 while Nkind (Call) = N_Reference loop
5605 Call := Prefix (Call);
5606 end loop;
5608 if Nkind_In (Call, N_Qualified_Expression,
5609 N_Unchecked_Type_Conversion)
5610 then
5611 Call := Expression (Call);
5612 end if;
5614 if Is_Build_In_Place_Function_Call (Call) then
5616 -- Examine all parameter associations of the function call
5618 Param := First (Parameter_Associations (Call));
5619 while Present (Param) loop
5620 if Nkind (Param) = N_Parameter_Association
5621 and then Nkind (Selector_Name (Param)) = N_Identifier
5622 then
5623 Formal := Selector_Name (Param);
5624 Actual := Explicit_Actual_Parameter (Param);
5626 -- Construct the name of formal BIPalloc. It is much easier to
5627 -- extract the name of the function using an arbitrary formal's
5628 -- scope rather than the Name field of Call.
5630 if Alloc_Nam = No_Name and then Present (Entity (Formal)) then
5631 Alloc_Nam :=
5632 New_External_Name
5633 (Chars (Scope (Entity (Formal))),
5634 BIP_Formal_Suffix (BIP_Alloc_Form));
5635 end if;
5637 -- A match for BIPalloc => 2 has been found
5639 if Chars (Formal) = Alloc_Nam
5640 and then Nkind (Actual) = N_Integer_Literal
5641 and then Intval (Actual) = Uint_2
5642 then
5643 return True;
5644 end if;
5645 end if;
5647 Next (Param);
5648 end loop;
5649 end if;
5651 return False;
5652 end Is_Secondary_Stack_BIP_Func_Call;
5654 -------------------------------------
5655 -- Is_Tag_To_Class_Wide_Conversion --
5656 -------------------------------------
5658 function Is_Tag_To_Class_Wide_Conversion
5659 (Obj_Id : Entity_Id) return Boolean
5661 Expr : constant Node_Id := Expression (Parent (Obj_Id));
5663 begin
5664 return
5665 Is_Class_Wide_Type (Etype (Obj_Id))
5666 and then Present (Expr)
5667 and then Nkind (Expr) = N_Unchecked_Type_Conversion
5668 and then Etype (Expression (Expr)) = RTE (RE_Tag);
5669 end Is_Tag_To_Class_Wide_Conversion;
5671 ----------------------------
5672 -- Is_Untagged_Derivation --
5673 ----------------------------
5675 function Is_Untagged_Derivation (T : Entity_Id) return Boolean is
5676 begin
5677 return (not Is_Tagged_Type (T) and then Is_Derived_Type (T))
5678 or else
5679 (Is_Private_Type (T) and then Present (Full_View (T))
5680 and then not Is_Tagged_Type (Full_View (T))
5681 and then Is_Derived_Type (Full_View (T))
5682 and then Etype (Full_View (T)) /= T);
5683 end Is_Untagged_Derivation;
5685 ---------------------------
5686 -- Is_Volatile_Reference --
5687 ---------------------------
5689 function Is_Volatile_Reference (N : Node_Id) return Boolean is
5690 begin
5691 -- Only source references are to be treated as volatile, internally
5692 -- generated stuff cannot have volatile external effects.
5694 if not Comes_From_Source (N) then
5695 return False;
5697 -- Never true for reference to a type
5699 elsif Is_Entity_Name (N) and then Is_Type (Entity (N)) then
5700 return False;
5702 -- True if object reference with volatile type
5704 elsif Is_Volatile_Object (N) then
5705 return True;
5707 -- True if reference to volatile entity
5709 elsif Is_Entity_Name (N) then
5710 return Treat_As_Volatile (Entity (N));
5712 -- True for slice of volatile array
5714 elsif Nkind (N) = N_Slice then
5715 return Is_Volatile_Reference (Prefix (N));
5717 -- True if volatile component
5719 elsif Nkind_In (N, N_Indexed_Component, N_Selected_Component) then
5720 if (Is_Entity_Name (Prefix (N))
5721 and then Has_Volatile_Components (Entity (Prefix (N))))
5722 or else (Present (Etype (Prefix (N)))
5723 and then Has_Volatile_Components (Etype (Prefix (N))))
5724 then
5725 return True;
5726 else
5727 return Is_Volatile_Reference (Prefix (N));
5728 end if;
5730 -- Otherwise false
5732 else
5733 return False;
5734 end if;
5735 end Is_Volatile_Reference;
5737 --------------------------
5738 -- Is_VM_By_Copy_Actual --
5739 --------------------------
5741 function Is_VM_By_Copy_Actual (N : Node_Id) return Boolean is
5742 begin
5743 return VM_Target /= No_VM
5744 and then (Nkind (N) = N_Slice
5745 or else
5746 (Nkind (N) = N_Identifier
5747 and then Present (Renamed_Object (Entity (N)))
5748 and then Nkind (Renamed_Object (Entity (N))) =
5749 N_Slice));
5750 end Is_VM_By_Copy_Actual;
5752 --------------------
5753 -- Kill_Dead_Code --
5754 --------------------
5756 procedure Kill_Dead_Code (N : Node_Id; Warn : Boolean := False) is
5757 W : Boolean := Warn;
5758 -- Set False if warnings suppressed
5760 begin
5761 if Present (N) then
5762 Remove_Warning_Messages (N);
5764 -- Generate warning if appropriate
5766 if W then
5768 -- We suppress the warning if this code is under control of an
5769 -- if statement, whose condition is a simple identifier, and
5770 -- either we are in an instance, or warnings off is set for this
5771 -- identifier. The reason for killing it in the instance case is
5772 -- that it is common and reasonable for code to be deleted in
5773 -- instances for various reasons.
5775 -- Could we use Is_Statically_Unevaluated here???
5777 if Nkind (Parent (N)) = N_If_Statement then
5778 declare
5779 C : constant Node_Id := Condition (Parent (N));
5780 begin
5781 if Nkind (C) = N_Identifier
5782 and then
5783 (In_Instance
5784 or else (Present (Entity (C))
5785 and then Has_Warnings_Off (Entity (C))))
5786 then
5787 W := False;
5788 end if;
5789 end;
5790 end if;
5792 -- Generate warning if not suppressed
5794 if W then
5795 Error_Msg_F
5796 ("?t?this code can never be executed and has been deleted!",
5798 end if;
5799 end if;
5801 -- Recurse into block statements and bodies to process declarations
5802 -- and statements.
5804 if Nkind (N) = N_Block_Statement
5805 or else Nkind (N) = N_Subprogram_Body
5806 or else Nkind (N) = N_Package_Body
5807 then
5808 Kill_Dead_Code (Declarations (N), False);
5809 Kill_Dead_Code (Statements (Handled_Statement_Sequence (N)));
5811 if Nkind (N) = N_Subprogram_Body then
5812 Set_Is_Eliminated (Defining_Entity (N));
5813 end if;
5815 elsif Nkind (N) = N_Package_Declaration then
5816 Kill_Dead_Code (Visible_Declarations (Specification (N)));
5817 Kill_Dead_Code (Private_Declarations (Specification (N)));
5819 -- ??? After this point, Delete_Tree has been called on all
5820 -- declarations in Specification (N), so references to entities
5821 -- therein look suspicious.
5823 declare
5824 E : Entity_Id := First_Entity (Defining_Entity (N));
5826 begin
5827 while Present (E) loop
5828 if Ekind (E) = E_Operator then
5829 Set_Is_Eliminated (E);
5830 end if;
5832 Next_Entity (E);
5833 end loop;
5834 end;
5836 -- Recurse into composite statement to kill individual statements in
5837 -- particular instantiations.
5839 elsif Nkind (N) = N_If_Statement then
5840 Kill_Dead_Code (Then_Statements (N));
5841 Kill_Dead_Code (Elsif_Parts (N));
5842 Kill_Dead_Code (Else_Statements (N));
5844 elsif Nkind (N) = N_Loop_Statement then
5845 Kill_Dead_Code (Statements (N));
5847 elsif Nkind (N) = N_Case_Statement then
5848 declare
5849 Alt : Node_Id;
5850 begin
5851 Alt := First (Alternatives (N));
5852 while Present (Alt) loop
5853 Kill_Dead_Code (Statements (Alt));
5854 Next (Alt);
5855 end loop;
5856 end;
5858 elsif Nkind (N) = N_Case_Statement_Alternative then
5859 Kill_Dead_Code (Statements (N));
5861 -- Deal with dead instances caused by deleting instantiations
5863 elsif Nkind (N) in N_Generic_Instantiation then
5864 Remove_Dead_Instance (N);
5865 end if;
5866 end if;
5867 end Kill_Dead_Code;
5869 -- Case where argument is a list of nodes to be killed
5871 procedure Kill_Dead_Code (L : List_Id; Warn : Boolean := False) is
5872 N : Node_Id;
5873 W : Boolean;
5875 begin
5876 W := Warn;
5878 if Is_Non_Empty_List (L) then
5879 N := First (L);
5880 while Present (N) loop
5881 Kill_Dead_Code (N, W);
5882 W := False;
5883 Next (N);
5884 end loop;
5885 end if;
5886 end Kill_Dead_Code;
5888 ------------------------
5889 -- Known_Non_Negative --
5890 ------------------------
5892 function Known_Non_Negative (Opnd : Node_Id) return Boolean is
5893 begin
5894 if Is_OK_Static_Expression (Opnd) and then Expr_Value (Opnd) >= 0 then
5895 return True;
5897 else
5898 declare
5899 Lo : constant Node_Id := Type_Low_Bound (Etype (Opnd));
5900 begin
5901 return
5902 Is_OK_Static_Expression (Lo) and then Expr_Value (Lo) >= 0;
5903 end;
5904 end if;
5905 end Known_Non_Negative;
5907 --------------------
5908 -- Known_Non_Null --
5909 --------------------
5911 function Known_Non_Null (N : Node_Id) return Boolean is
5912 begin
5913 -- Checks for case where N is an entity reference
5915 if Is_Entity_Name (N) and then Present (Entity (N)) then
5916 declare
5917 E : constant Entity_Id := Entity (N);
5918 Op : Node_Kind;
5919 Val : Node_Id;
5921 begin
5922 -- First check if we are in decisive conditional
5924 Get_Current_Value_Condition (N, Op, Val);
5926 if Known_Null (Val) then
5927 if Op = N_Op_Eq then
5928 return False;
5929 elsif Op = N_Op_Ne then
5930 return True;
5931 end if;
5932 end if;
5934 -- If OK to do replacement, test Is_Known_Non_Null flag
5936 if OK_To_Do_Constant_Replacement (E) then
5937 return Is_Known_Non_Null (E);
5939 -- Otherwise if not safe to do replacement, then say so
5941 else
5942 return False;
5943 end if;
5944 end;
5946 -- True if access attribute
5948 elsif Nkind (N) = N_Attribute_Reference
5949 and then Nam_In (Attribute_Name (N), Name_Access,
5950 Name_Unchecked_Access,
5951 Name_Unrestricted_Access)
5952 then
5953 return True;
5955 -- True if allocator
5957 elsif Nkind (N) = N_Allocator then
5958 return True;
5960 -- For a conversion, true if expression is known non-null
5962 elsif Nkind (N) = N_Type_Conversion then
5963 return Known_Non_Null (Expression (N));
5965 -- Above are all cases where the value could be determined to be
5966 -- non-null. In all other cases, we don't know, so return False.
5968 else
5969 return False;
5970 end if;
5971 end Known_Non_Null;
5973 ----------------
5974 -- Known_Null --
5975 ----------------
5977 function Known_Null (N : Node_Id) return Boolean is
5978 begin
5979 -- Checks for case where N is an entity reference
5981 if Is_Entity_Name (N) and then Present (Entity (N)) then
5982 declare
5983 E : constant Entity_Id := Entity (N);
5984 Op : Node_Kind;
5985 Val : Node_Id;
5987 begin
5988 -- Constant null value is for sure null
5990 if Ekind (E) = E_Constant
5991 and then Known_Null (Constant_Value (E))
5992 then
5993 return True;
5994 end if;
5996 -- First check if we are in decisive conditional
5998 Get_Current_Value_Condition (N, Op, Val);
6000 if Known_Null (Val) then
6001 if Op = N_Op_Eq then
6002 return True;
6003 elsif Op = N_Op_Ne then
6004 return False;
6005 end if;
6006 end if;
6008 -- If OK to do replacement, test Is_Known_Null flag
6010 if OK_To_Do_Constant_Replacement (E) then
6011 return Is_Known_Null (E);
6013 -- Otherwise if not safe to do replacement, then say so
6015 else
6016 return False;
6017 end if;
6018 end;
6020 -- True if explicit reference to null
6022 elsif Nkind (N) = N_Null then
6023 return True;
6025 -- For a conversion, true if expression is known null
6027 elsif Nkind (N) = N_Type_Conversion then
6028 return Known_Null (Expression (N));
6030 -- Above are all cases where the value could be determined to be null.
6031 -- In all other cases, we don't know, so return False.
6033 else
6034 return False;
6035 end if;
6036 end Known_Null;
6038 -----------------------------
6039 -- Make_CW_Equivalent_Type --
6040 -----------------------------
6042 -- Create a record type used as an equivalent of any member of the class
6043 -- which takes its size from exp.
6045 -- Generate the following code:
6047 -- type Equiv_T is record
6048 -- _parent : T (List of discriminant constraints taken from Exp);
6049 -- Ext__50 : Storage_Array (1 .. (Exp'size - Typ'object_size)/8);
6050 -- end Equiv_T;
6052 -- ??? Note that this type does not guarantee same alignment as all
6053 -- derived types
6055 function Make_CW_Equivalent_Type
6056 (T : Entity_Id;
6057 E : Node_Id) return Entity_Id
6059 Loc : constant Source_Ptr := Sloc (E);
6060 Root_Typ : constant Entity_Id := Root_Type (T);
6061 List_Def : constant List_Id := Empty_List;
6062 Comp_List : constant List_Id := New_List;
6063 Equiv_Type : Entity_Id;
6064 Range_Type : Entity_Id;
6065 Str_Type : Entity_Id;
6066 Constr_Root : Entity_Id;
6067 Sizexpr : Node_Id;
6069 begin
6070 -- If the root type is already constrained, there are no discriminants
6071 -- in the expression.
6073 if not Has_Discriminants (Root_Typ)
6074 or else Is_Constrained (Root_Typ)
6075 then
6076 Constr_Root := Root_Typ;
6077 else
6078 Constr_Root := Make_Temporary (Loc, 'R');
6080 -- subtype cstr__n is T (List of discr constraints taken from Exp)
6082 Append_To (List_Def,
6083 Make_Subtype_Declaration (Loc,
6084 Defining_Identifier => Constr_Root,
6085 Subtype_Indication => Make_Subtype_From_Expr (E, Root_Typ)));
6086 end if;
6088 -- Generate the range subtype declaration
6090 Range_Type := Make_Temporary (Loc, 'G');
6092 if not Is_Interface (Root_Typ) then
6094 -- subtype rg__xx is
6095 -- Storage_Offset range 1 .. (Expr'size - typ'size) / Storage_Unit
6097 Sizexpr :=
6098 Make_Op_Subtract (Loc,
6099 Left_Opnd =>
6100 Make_Attribute_Reference (Loc,
6101 Prefix =>
6102 OK_Convert_To (T, Duplicate_Subexpr_No_Checks (E)),
6103 Attribute_Name => Name_Size),
6104 Right_Opnd =>
6105 Make_Attribute_Reference (Loc,
6106 Prefix => New_Occurrence_Of (Constr_Root, Loc),
6107 Attribute_Name => Name_Object_Size));
6108 else
6109 -- subtype rg__xx is
6110 -- Storage_Offset range 1 .. Expr'size / Storage_Unit
6112 Sizexpr :=
6113 Make_Attribute_Reference (Loc,
6114 Prefix =>
6115 OK_Convert_To (T, Duplicate_Subexpr_No_Checks (E)),
6116 Attribute_Name => Name_Size);
6117 end if;
6119 Set_Paren_Count (Sizexpr, 1);
6121 Append_To (List_Def,
6122 Make_Subtype_Declaration (Loc,
6123 Defining_Identifier => Range_Type,
6124 Subtype_Indication =>
6125 Make_Subtype_Indication (Loc,
6126 Subtype_Mark => New_Occurrence_Of (RTE (RE_Storage_Offset), Loc),
6127 Constraint => Make_Range_Constraint (Loc,
6128 Range_Expression =>
6129 Make_Range (Loc,
6130 Low_Bound => Make_Integer_Literal (Loc, 1),
6131 High_Bound =>
6132 Make_Op_Divide (Loc,
6133 Left_Opnd => Sizexpr,
6134 Right_Opnd => Make_Integer_Literal (Loc,
6135 Intval => System_Storage_Unit)))))));
6137 -- subtype str__nn is Storage_Array (rg__x);
6139 Str_Type := Make_Temporary (Loc, 'S');
6140 Append_To (List_Def,
6141 Make_Subtype_Declaration (Loc,
6142 Defining_Identifier => Str_Type,
6143 Subtype_Indication =>
6144 Make_Subtype_Indication (Loc,
6145 Subtype_Mark => New_Occurrence_Of (RTE (RE_Storage_Array), Loc),
6146 Constraint =>
6147 Make_Index_Or_Discriminant_Constraint (Loc,
6148 Constraints =>
6149 New_List (New_Occurrence_Of (Range_Type, Loc))))));
6151 -- type Equiv_T is record
6152 -- [ _parent : Tnn; ]
6153 -- E : Str_Type;
6154 -- end Equiv_T;
6156 Equiv_Type := Make_Temporary (Loc, 'T');
6157 Set_Ekind (Equiv_Type, E_Record_Type);
6158 Set_Parent_Subtype (Equiv_Type, Constr_Root);
6160 -- Set Is_Class_Wide_Equivalent_Type very early to trigger the special
6161 -- treatment for this type. In particular, even though _parent's type
6162 -- is a controlled type or contains controlled components, we do not
6163 -- want to set Has_Controlled_Component on it to avoid making it gain
6164 -- an unwanted _controller component.
6166 Set_Is_Class_Wide_Equivalent_Type (Equiv_Type);
6168 -- A class-wide equivalent type does not require initialization
6170 Set_Suppress_Initialization (Equiv_Type);
6172 if not Is_Interface (Root_Typ) then
6173 Append_To (Comp_List,
6174 Make_Component_Declaration (Loc,
6175 Defining_Identifier =>
6176 Make_Defining_Identifier (Loc, Name_uParent),
6177 Component_Definition =>
6178 Make_Component_Definition (Loc,
6179 Aliased_Present => False,
6180 Subtype_Indication => New_Occurrence_Of (Constr_Root, Loc))));
6181 end if;
6183 Append_To (Comp_List,
6184 Make_Component_Declaration (Loc,
6185 Defining_Identifier => Make_Temporary (Loc, 'C'),
6186 Component_Definition =>
6187 Make_Component_Definition (Loc,
6188 Aliased_Present => False,
6189 Subtype_Indication => New_Occurrence_Of (Str_Type, Loc))));
6191 Append_To (List_Def,
6192 Make_Full_Type_Declaration (Loc,
6193 Defining_Identifier => Equiv_Type,
6194 Type_Definition =>
6195 Make_Record_Definition (Loc,
6196 Component_List =>
6197 Make_Component_List (Loc,
6198 Component_Items => Comp_List,
6199 Variant_Part => Empty))));
6201 -- Suppress all checks during the analysis of the expanded code to avoid
6202 -- the generation of spurious warnings under ZFP run-time.
6204 Insert_Actions (E, List_Def, Suppress => All_Checks);
6205 return Equiv_Type;
6206 end Make_CW_Equivalent_Type;
6208 -------------------------
6209 -- Make_Invariant_Call --
6210 -------------------------
6212 function Make_Invariant_Call (Expr : Node_Id) return Node_Id is
6213 Loc : constant Source_Ptr := Sloc (Expr);
6214 Typ : Entity_Id;
6216 begin
6217 Typ := Etype (Expr);
6219 -- Subtypes may be subject to invariants coming from their respective
6220 -- base types. The subtype may be fully or partially private.
6222 if Ekind_In (Typ, E_Array_Subtype,
6223 E_Private_Subtype,
6224 E_Record_Subtype,
6225 E_Record_Subtype_With_Private)
6226 then
6227 Typ := Base_Type (Typ);
6228 end if;
6230 pragma Assert
6231 (Has_Invariants (Typ) and then Present (Invariant_Procedure (Typ)));
6233 return
6234 Make_Procedure_Call_Statement (Loc,
6235 Name =>
6236 New_Occurrence_Of (Invariant_Procedure (Typ), Loc),
6237 Parameter_Associations => New_List (Relocate_Node (Expr)));
6238 end Make_Invariant_Call;
6240 ------------------------
6241 -- Make_Literal_Range --
6242 ------------------------
6244 function Make_Literal_Range
6245 (Loc : Source_Ptr;
6246 Literal_Typ : Entity_Id) return Node_Id
6248 Lo : constant Node_Id :=
6249 New_Copy_Tree (String_Literal_Low_Bound (Literal_Typ));
6250 Index : constant Entity_Id := Etype (Lo);
6252 Hi : Node_Id;
6253 Length_Expr : constant Node_Id :=
6254 Make_Op_Subtract (Loc,
6255 Left_Opnd =>
6256 Make_Integer_Literal (Loc,
6257 Intval => String_Literal_Length (Literal_Typ)),
6258 Right_Opnd =>
6259 Make_Integer_Literal (Loc, 1));
6261 begin
6262 Set_Analyzed (Lo, False);
6264 if Is_Integer_Type (Index) then
6265 Hi :=
6266 Make_Op_Add (Loc,
6267 Left_Opnd => New_Copy_Tree (Lo),
6268 Right_Opnd => Length_Expr);
6269 else
6270 Hi :=
6271 Make_Attribute_Reference (Loc,
6272 Attribute_Name => Name_Val,
6273 Prefix => New_Occurrence_Of (Index, Loc),
6274 Expressions => New_List (
6275 Make_Op_Add (Loc,
6276 Left_Opnd =>
6277 Make_Attribute_Reference (Loc,
6278 Attribute_Name => Name_Pos,
6279 Prefix => New_Occurrence_Of (Index, Loc),
6280 Expressions => New_List (New_Copy_Tree (Lo))),
6281 Right_Opnd => Length_Expr)));
6282 end if;
6284 return
6285 Make_Range (Loc,
6286 Low_Bound => Lo,
6287 High_Bound => Hi);
6288 end Make_Literal_Range;
6290 --------------------------
6291 -- Make_Non_Empty_Check --
6292 --------------------------
6294 function Make_Non_Empty_Check
6295 (Loc : Source_Ptr;
6296 N : Node_Id) return Node_Id
6298 begin
6299 return
6300 Make_Op_Ne (Loc,
6301 Left_Opnd =>
6302 Make_Attribute_Reference (Loc,
6303 Attribute_Name => Name_Length,
6304 Prefix => Duplicate_Subexpr_No_Checks (N, Name_Req => True)),
6305 Right_Opnd =>
6306 Make_Integer_Literal (Loc, 0));
6307 end Make_Non_Empty_Check;
6309 -------------------------
6310 -- Make_Predicate_Call --
6311 -------------------------
6313 function Make_Predicate_Call
6314 (Typ : Entity_Id;
6315 Expr : Node_Id;
6316 Mem : Boolean := False) return Node_Id
6318 Loc : constant Source_Ptr := Sloc (Expr);
6320 begin
6321 pragma Assert (Present (Predicate_Function (Typ)));
6323 -- Call special membership version if requested and available
6325 if Mem then
6326 declare
6327 PFM : constant Entity_Id := Predicate_Function_M (Typ);
6328 begin
6329 if Present (PFM) then
6330 return
6331 Make_Function_Call (Loc,
6332 Name => New_Occurrence_Of (PFM, Loc),
6333 Parameter_Associations => New_List (Relocate_Node (Expr)));
6334 end if;
6335 end;
6336 end if;
6338 -- Case of calling normal predicate function
6340 return
6341 Make_Function_Call (Loc,
6342 Name =>
6343 New_Occurrence_Of (Predicate_Function (Typ), Loc),
6344 Parameter_Associations => New_List (Relocate_Node (Expr)));
6345 end Make_Predicate_Call;
6347 --------------------------
6348 -- Make_Predicate_Check --
6349 --------------------------
6351 function Make_Predicate_Check
6352 (Typ : Entity_Id;
6353 Expr : Node_Id) return Node_Id
6355 Loc : constant Source_Ptr := Sloc (Expr);
6356 Nam : Name_Id;
6358 begin
6359 -- If predicate checks are suppressed, then return a null statement.
6360 -- For this call, we check only the scope setting. If the caller wants
6361 -- to check a specific entity's setting, they must do it manually.
6363 if Predicate_Checks_Suppressed (Empty) then
6364 return Make_Null_Statement (Loc);
6365 end if;
6367 -- Do not generate a check within an internal subprogram (stream
6368 -- functions and the like, including including predicate functions).
6370 if Within_Internal_Subprogram then
6371 return Make_Null_Statement (Loc);
6372 end if;
6374 -- Compute proper name to use, we need to get this right so that the
6375 -- right set of check policies apply to the Check pragma we are making.
6377 if Has_Dynamic_Predicate_Aspect (Typ) then
6378 Nam := Name_Dynamic_Predicate;
6379 elsif Has_Static_Predicate_Aspect (Typ) then
6380 Nam := Name_Static_Predicate;
6381 else
6382 Nam := Name_Predicate;
6383 end if;
6385 return
6386 Make_Pragma (Loc,
6387 Pragma_Identifier => Make_Identifier (Loc, Name_Check),
6388 Pragma_Argument_Associations => New_List (
6389 Make_Pragma_Argument_Association (Loc,
6390 Expression => Make_Identifier (Loc, Nam)),
6391 Make_Pragma_Argument_Association (Loc,
6392 Expression => Make_Predicate_Call (Typ, Expr))));
6393 end Make_Predicate_Check;
6395 ----------------------------
6396 -- Make_Subtype_From_Expr --
6397 ----------------------------
6399 -- 1. If Expr is an unconstrained array expression, creates
6400 -- Unc_Type(Expr'first(1)..Expr'last(1),..., Expr'first(n)..Expr'last(n))
6402 -- 2. If Expr is a unconstrained discriminated type expression, creates
6403 -- Unc_Type(Expr.Discr1, ... , Expr.Discr_n)
6405 -- 3. If Expr is class-wide, creates an implicit class-wide subtype
6407 function Make_Subtype_From_Expr
6408 (E : Node_Id;
6409 Unc_Typ : Entity_Id) return Node_Id
6411 List_Constr : constant List_Id := New_List;
6412 Loc : constant Source_Ptr := Sloc (E);
6413 D : Entity_Id;
6414 Full_Exp : Node_Id;
6415 Full_Subtyp : Entity_Id;
6416 High_Bound : Entity_Id;
6417 Index_Typ : Entity_Id;
6418 Low_Bound : Entity_Id;
6419 Priv_Subtyp : Entity_Id;
6420 Utyp : Entity_Id;
6422 begin
6423 if Is_Private_Type (Unc_Typ)
6424 and then Has_Unknown_Discriminants (Unc_Typ)
6425 then
6426 -- Prepare the subtype completion. Use the base type to find the
6427 -- underlying type because the type may be a generic actual or an
6428 -- explicit subtype.
6430 Utyp := Underlying_Type (Base_Type (Unc_Typ));
6431 Full_Subtyp := Make_Temporary (Loc, 'C');
6432 Full_Exp :=
6433 Unchecked_Convert_To (Utyp, Duplicate_Subexpr_No_Checks (E));
6434 Set_Parent (Full_Exp, Parent (E));
6436 Priv_Subtyp := Make_Temporary (Loc, 'P');
6438 Insert_Action (E,
6439 Make_Subtype_Declaration (Loc,
6440 Defining_Identifier => Full_Subtyp,
6441 Subtype_Indication => Make_Subtype_From_Expr (Full_Exp, Utyp)));
6443 -- Define the dummy private subtype
6445 Set_Ekind (Priv_Subtyp, Subtype_Kind (Ekind (Unc_Typ)));
6446 Set_Etype (Priv_Subtyp, Base_Type (Unc_Typ));
6447 Set_Scope (Priv_Subtyp, Full_Subtyp);
6448 Set_Is_Constrained (Priv_Subtyp);
6449 Set_Is_Tagged_Type (Priv_Subtyp, Is_Tagged_Type (Unc_Typ));
6450 Set_Is_Itype (Priv_Subtyp);
6451 Set_Associated_Node_For_Itype (Priv_Subtyp, E);
6453 if Is_Tagged_Type (Priv_Subtyp) then
6454 Set_Class_Wide_Type
6455 (Base_Type (Priv_Subtyp), Class_Wide_Type (Unc_Typ));
6456 Set_Direct_Primitive_Operations (Priv_Subtyp,
6457 Direct_Primitive_Operations (Unc_Typ));
6458 end if;
6460 Set_Full_View (Priv_Subtyp, Full_Subtyp);
6462 return New_Occurrence_Of (Priv_Subtyp, Loc);
6464 elsif Is_Array_Type (Unc_Typ) then
6465 Index_Typ := First_Index (Unc_Typ);
6466 for J in 1 .. Number_Dimensions (Unc_Typ) loop
6468 -- Capture the bounds of each index constraint in case the context
6469 -- is an object declaration of an unconstrained type initialized
6470 -- by a function call:
6472 -- Obj : Unconstr_Typ := Func_Call;
6474 -- This scenario requires secondary scope management and the index
6475 -- constraint cannot depend on the temporary used to capture the
6476 -- result of the function call.
6478 -- SS_Mark;
6479 -- Temp : Unconstr_Typ_Ptr := Func_Call'reference;
6480 -- subtype S is Unconstr_Typ (Temp.all'First .. Temp.all'Last);
6481 -- Obj : S := Temp.all;
6482 -- SS_Release; -- Temp is gone at this point, bounds of S are
6483 -- -- non existent.
6485 -- Generate:
6486 -- Low_Bound : constant Base_Type (Index_Typ) := E'First (J);
6488 Low_Bound := Make_Temporary (Loc, 'B');
6489 Insert_Action (E,
6490 Make_Object_Declaration (Loc,
6491 Defining_Identifier => Low_Bound,
6492 Object_Definition =>
6493 New_Occurrence_Of (Base_Type (Etype (Index_Typ)), Loc),
6494 Constant_Present => True,
6495 Expression =>
6496 Make_Attribute_Reference (Loc,
6497 Prefix => Duplicate_Subexpr_No_Checks (E),
6498 Attribute_Name => Name_First,
6499 Expressions => New_List (
6500 Make_Integer_Literal (Loc, J)))));
6502 -- Generate:
6503 -- High_Bound : constant Base_Type (Index_Typ) := E'Last (J);
6505 High_Bound := Make_Temporary (Loc, 'B');
6506 Insert_Action (E,
6507 Make_Object_Declaration (Loc,
6508 Defining_Identifier => High_Bound,
6509 Object_Definition =>
6510 New_Occurrence_Of (Base_Type (Etype (Index_Typ)), Loc),
6511 Constant_Present => True,
6512 Expression =>
6513 Make_Attribute_Reference (Loc,
6514 Prefix => Duplicate_Subexpr_No_Checks (E),
6515 Attribute_Name => Name_Last,
6516 Expressions => New_List (
6517 Make_Integer_Literal (Loc, J)))));
6519 Append_To (List_Constr,
6520 Make_Range (Loc,
6521 Low_Bound => New_Occurrence_Of (Low_Bound, Loc),
6522 High_Bound => New_Occurrence_Of (High_Bound, Loc)));
6524 Index_Typ := Next_Index (Index_Typ);
6525 end loop;
6527 elsif Is_Class_Wide_Type (Unc_Typ) then
6528 declare
6529 CW_Subtype : Entity_Id;
6530 EQ_Typ : Entity_Id := Empty;
6532 begin
6533 -- A class-wide equivalent type is not needed when VM_Target
6534 -- because the VM back-ends handle the class-wide object
6535 -- initialization itself (and doesn't need or want the
6536 -- additional intermediate type to handle the assignment).
6538 if Expander_Active and then Tagged_Type_Expansion then
6540 -- If this is the class-wide type of a completion that is a
6541 -- record subtype, set the type of the class-wide type to be
6542 -- the full base type, for use in the expanded code for the
6543 -- equivalent type. Should this be done earlier when the
6544 -- completion is analyzed ???
6546 if Is_Private_Type (Etype (Unc_Typ))
6547 and then
6548 Ekind (Full_View (Etype (Unc_Typ))) = E_Record_Subtype
6549 then
6550 Set_Etype (Unc_Typ, Base_Type (Full_View (Etype (Unc_Typ))));
6551 end if;
6553 EQ_Typ := Make_CW_Equivalent_Type (Unc_Typ, E);
6554 end if;
6556 CW_Subtype := New_Class_Wide_Subtype (Unc_Typ, E);
6557 Set_Equivalent_Type (CW_Subtype, EQ_Typ);
6558 Set_Cloned_Subtype (CW_Subtype, Base_Type (Unc_Typ));
6560 return New_Occurrence_Of (CW_Subtype, Loc);
6561 end;
6563 -- Indefinite record type with discriminants
6565 else
6566 D := First_Discriminant (Unc_Typ);
6567 while Present (D) loop
6568 Append_To (List_Constr,
6569 Make_Selected_Component (Loc,
6570 Prefix => Duplicate_Subexpr_No_Checks (E),
6571 Selector_Name => New_Occurrence_Of (D, Loc)));
6573 Next_Discriminant (D);
6574 end loop;
6575 end if;
6577 return
6578 Make_Subtype_Indication (Loc,
6579 Subtype_Mark => New_Occurrence_Of (Unc_Typ, Loc),
6580 Constraint =>
6581 Make_Index_Or_Discriminant_Constraint (Loc,
6582 Constraints => List_Constr));
6583 end Make_Subtype_From_Expr;
6585 ----------------------------
6586 -- Matching_Standard_Type --
6587 ----------------------------
6589 function Matching_Standard_Type (Typ : Entity_Id) return Entity_Id is
6590 pragma Assert (Is_Scalar_Type (Typ));
6591 Siz : constant Uint := Esize (Typ);
6593 begin
6594 -- Floating-point cases
6596 if Is_Floating_Point_Type (Typ) then
6597 if Siz <= Esize (Standard_Short_Float) then
6598 return Standard_Short_Float;
6599 elsif Siz <= Esize (Standard_Float) then
6600 return Standard_Float;
6601 elsif Siz <= Esize (Standard_Long_Float) then
6602 return Standard_Long_Float;
6603 elsif Siz <= Esize (Standard_Long_Long_Float) then
6604 return Standard_Long_Long_Float;
6605 else
6606 raise Program_Error;
6607 end if;
6609 -- Integer cases (includes fixed-point types)
6611 -- Unsigned integer cases (includes normal enumeration types)
6613 elsif Is_Unsigned_Type (Typ) then
6614 if Siz <= Esize (Standard_Short_Short_Unsigned) then
6615 return Standard_Short_Short_Unsigned;
6616 elsif Siz <= Esize (Standard_Short_Unsigned) then
6617 return Standard_Short_Unsigned;
6618 elsif Siz <= Esize (Standard_Unsigned) then
6619 return Standard_Unsigned;
6620 elsif Siz <= Esize (Standard_Long_Unsigned) then
6621 return Standard_Long_Unsigned;
6622 elsif Siz <= Esize (Standard_Long_Long_Unsigned) then
6623 return Standard_Long_Long_Unsigned;
6624 else
6625 raise Program_Error;
6626 end if;
6628 -- Signed integer cases
6630 else
6631 if Siz <= Esize (Standard_Short_Short_Integer) then
6632 return Standard_Short_Short_Integer;
6633 elsif Siz <= Esize (Standard_Short_Integer) then
6634 return Standard_Short_Integer;
6635 elsif Siz <= Esize (Standard_Integer) then
6636 return Standard_Integer;
6637 elsif Siz <= Esize (Standard_Long_Integer) then
6638 return Standard_Long_Integer;
6639 elsif Siz <= Esize (Standard_Long_Long_Integer) then
6640 return Standard_Long_Long_Integer;
6641 else
6642 raise Program_Error;
6643 end if;
6644 end if;
6645 end Matching_Standard_Type;
6647 -----------------------------
6648 -- May_Generate_Large_Temp --
6649 -----------------------------
6651 -- At the current time, the only types that we return False for (i.e. where
6652 -- we decide we know they cannot generate large temps) are ones where we
6653 -- know the size is 256 bits or less at compile time, and we are still not
6654 -- doing a thorough job on arrays and records ???
6656 function May_Generate_Large_Temp (Typ : Entity_Id) return Boolean is
6657 begin
6658 if not Size_Known_At_Compile_Time (Typ) then
6659 return False;
6661 elsif Esize (Typ) /= 0 and then Esize (Typ) <= 256 then
6662 return False;
6664 elsif Is_Array_Type (Typ)
6665 and then Present (Packed_Array_Impl_Type (Typ))
6666 then
6667 return May_Generate_Large_Temp (Packed_Array_Impl_Type (Typ));
6669 -- We could do more here to find other small types ???
6671 else
6672 return True;
6673 end if;
6674 end May_Generate_Large_Temp;
6676 ------------------------
6677 -- Needs_Finalization --
6678 ------------------------
6680 function Needs_Finalization (T : Entity_Id) return Boolean is
6681 function Has_Some_Controlled_Component (Rec : Entity_Id) return Boolean;
6682 -- If type is not frozen yet, check explicitly among its components,
6683 -- because the Has_Controlled_Component flag is not necessarily set.
6685 -----------------------------------
6686 -- Has_Some_Controlled_Component --
6687 -----------------------------------
6689 function Has_Some_Controlled_Component
6690 (Rec : Entity_Id) return Boolean
6692 Comp : Entity_Id;
6694 begin
6695 if Has_Controlled_Component (Rec) then
6696 return True;
6698 elsif not Is_Frozen (Rec) then
6699 if Is_Record_Type (Rec) then
6700 Comp := First_Entity (Rec);
6702 while Present (Comp) loop
6703 if not Is_Type (Comp)
6704 and then Needs_Finalization (Etype (Comp))
6705 then
6706 return True;
6707 end if;
6709 Next_Entity (Comp);
6710 end loop;
6712 return False;
6714 elsif Is_Array_Type (Rec) then
6715 return Needs_Finalization (Component_Type (Rec));
6717 else
6718 return Has_Controlled_Component (Rec);
6719 end if;
6720 else
6721 return False;
6722 end if;
6723 end Has_Some_Controlled_Component;
6725 -- Start of processing for Needs_Finalization
6727 begin
6728 -- Certain run-time configurations and targets do not provide support
6729 -- for controlled types.
6731 if Restriction_Active (No_Finalization) then
6732 return False;
6734 -- C++, CIL and Java types are not considered controlled. It is assumed
6735 -- that the non-Ada side will handle their clean up.
6737 elsif Convention (T) = Convention_CIL
6738 or else Convention (T) = Convention_CPP
6739 or else Convention (T) = Convention_Java
6740 then
6741 return False;
6743 else
6744 -- Class-wide types are treated as controlled because derivations
6745 -- from the root type can introduce controlled components.
6747 return
6748 Is_Class_Wide_Type (T)
6749 or else Is_Controlled (T)
6750 or else Has_Controlled_Component (T)
6751 or else Has_Some_Controlled_Component (T)
6752 or else
6753 (Is_Concurrent_Type (T)
6754 and then Present (Corresponding_Record_Type (T))
6755 and then Needs_Finalization (Corresponding_Record_Type (T)));
6756 end if;
6757 end Needs_Finalization;
6759 ----------------------------
6760 -- Needs_Constant_Address --
6761 ----------------------------
6763 function Needs_Constant_Address
6764 (Decl : Node_Id;
6765 Typ : Entity_Id) return Boolean
6767 begin
6769 -- If we have no initialization of any kind, then we don't need to place
6770 -- any restrictions on the address clause, because the object will be
6771 -- elaborated after the address clause is evaluated. This happens if the
6772 -- declaration has no initial expression, or the type has no implicit
6773 -- initialization, or the object is imported.
6775 -- The same holds for all initialized scalar types and all access types.
6776 -- Packed bit arrays of size up to 64 are represented using a modular
6777 -- type with an initialization (to zero) and can be processed like other
6778 -- initialized scalar types.
6780 -- If the type is controlled, code to attach the object to a
6781 -- finalization chain is generated at the point of declaration, and
6782 -- therefore the elaboration of the object cannot be delayed: the
6783 -- address expression must be a constant.
6785 if No (Expression (Decl))
6786 and then not Needs_Finalization (Typ)
6787 and then
6788 (not Has_Non_Null_Base_Init_Proc (Typ)
6789 or else Is_Imported (Defining_Identifier (Decl)))
6790 then
6791 return False;
6793 elsif (Present (Expression (Decl)) and then Is_Scalar_Type (Typ))
6794 or else Is_Access_Type (Typ)
6795 or else
6796 (Is_Bit_Packed_Array (Typ)
6797 and then Is_Modular_Integer_Type (Packed_Array_Impl_Type (Typ)))
6798 then
6799 return False;
6801 else
6803 -- Otherwise, we require the address clause to be constant because
6804 -- the call to the initialization procedure (or the attach code) has
6805 -- to happen at the point of the declaration.
6807 -- Actually the IP call has been moved to the freeze actions anyway,
6808 -- so maybe we can relax this restriction???
6810 return True;
6811 end if;
6812 end Needs_Constant_Address;
6814 ----------------------------
6815 -- New_Class_Wide_Subtype --
6816 ----------------------------
6818 function New_Class_Wide_Subtype
6819 (CW_Typ : Entity_Id;
6820 N : Node_Id) return Entity_Id
6822 Res : constant Entity_Id := Create_Itype (E_Void, N);
6823 Res_Name : constant Name_Id := Chars (Res);
6824 Res_Scope : constant Entity_Id := Scope (Res);
6826 begin
6827 Copy_Node (CW_Typ, Res);
6828 Set_Comes_From_Source (Res, False);
6829 Set_Sloc (Res, Sloc (N));
6830 Set_Is_Itype (Res);
6831 Set_Associated_Node_For_Itype (Res, N);
6832 Set_Is_Public (Res, False); -- By default, may be changed below.
6833 Set_Public_Status (Res);
6834 Set_Chars (Res, Res_Name);
6835 Set_Scope (Res, Res_Scope);
6836 Set_Ekind (Res, E_Class_Wide_Subtype);
6837 Set_Next_Entity (Res, Empty);
6838 Set_Etype (Res, Base_Type (CW_Typ));
6839 Set_Is_Frozen (Res, False);
6840 Set_Freeze_Node (Res, Empty);
6841 return (Res);
6842 end New_Class_Wide_Subtype;
6844 --------------------------------
6845 -- Non_Limited_Designated_Type --
6846 ---------------------------------
6848 function Non_Limited_Designated_Type (T : Entity_Id) return Entity_Id is
6849 Desig : constant Entity_Id := Designated_Type (T);
6850 begin
6851 if Ekind (Desig) = E_Incomplete_Type
6852 and then Present (Non_Limited_View (Desig))
6853 then
6854 return Non_Limited_View (Desig);
6855 else
6856 return Desig;
6857 end if;
6858 end Non_Limited_Designated_Type;
6860 -----------------------------------
6861 -- OK_To_Do_Constant_Replacement --
6862 -----------------------------------
6864 function OK_To_Do_Constant_Replacement (E : Entity_Id) return Boolean is
6865 ES : constant Entity_Id := Scope (E);
6866 CS : Entity_Id;
6868 begin
6869 -- Do not replace statically allocated objects, because they may be
6870 -- modified outside the current scope.
6872 if Is_Statically_Allocated (E) then
6873 return False;
6875 -- Do not replace aliased or volatile objects, since we don't know what
6876 -- else might change the value.
6878 elsif Is_Aliased (E) or else Treat_As_Volatile (E) then
6879 return False;
6881 -- Debug flag -gnatdM disconnects this optimization
6883 elsif Debug_Flag_MM then
6884 return False;
6886 -- Otherwise check scopes
6888 else
6889 CS := Current_Scope;
6891 loop
6892 -- If we are in right scope, replacement is safe
6894 if CS = ES then
6895 return True;
6897 -- Packages do not affect the determination of safety
6899 elsif Ekind (CS) = E_Package then
6900 exit when CS = Standard_Standard;
6901 CS := Scope (CS);
6903 -- Blocks do not affect the determination of safety
6905 elsif Ekind (CS) = E_Block then
6906 CS := Scope (CS);
6908 -- Loops do not affect the determination of safety. Note that we
6909 -- kill all current values on entry to a loop, so we are just
6910 -- talking about processing within a loop here.
6912 elsif Ekind (CS) = E_Loop then
6913 CS := Scope (CS);
6915 -- Otherwise, the reference is dubious, and we cannot be sure that
6916 -- it is safe to do the replacement.
6918 else
6919 exit;
6920 end if;
6921 end loop;
6923 return False;
6924 end if;
6925 end OK_To_Do_Constant_Replacement;
6927 ------------------------------------
6928 -- Possible_Bit_Aligned_Component --
6929 ------------------------------------
6931 function Possible_Bit_Aligned_Component (N : Node_Id) return Boolean is
6932 begin
6933 case Nkind (N) is
6935 -- Case of indexed component
6937 when N_Indexed_Component =>
6938 declare
6939 P : constant Node_Id := Prefix (N);
6940 Ptyp : constant Entity_Id := Etype (P);
6942 begin
6943 -- If we know the component size and it is less than 64, then
6944 -- we are definitely OK. The back end always does assignment of
6945 -- misaligned small objects correctly.
6947 if Known_Static_Component_Size (Ptyp)
6948 and then Component_Size (Ptyp) <= 64
6949 then
6950 return False;
6952 -- Otherwise, we need to test the prefix, to see if we are
6953 -- indexing from a possibly unaligned component.
6955 else
6956 return Possible_Bit_Aligned_Component (P);
6957 end if;
6958 end;
6960 -- Case of selected component
6962 when N_Selected_Component =>
6963 declare
6964 P : constant Node_Id := Prefix (N);
6965 Comp : constant Entity_Id := Entity (Selector_Name (N));
6967 begin
6968 -- If there is no component clause, then we are in the clear
6969 -- since the back end will never misalign a large component
6970 -- unless it is forced to do so. In the clear means we need
6971 -- only the recursive test on the prefix.
6973 if Component_May_Be_Bit_Aligned (Comp) then
6974 return True;
6975 else
6976 return Possible_Bit_Aligned_Component (P);
6977 end if;
6978 end;
6980 -- For a slice, test the prefix, if that is possibly misaligned,
6981 -- then for sure the slice is.
6983 when N_Slice =>
6984 return Possible_Bit_Aligned_Component (Prefix (N));
6986 -- For an unchecked conversion, check whether the expression may
6987 -- be bit-aligned.
6989 when N_Unchecked_Type_Conversion =>
6990 return Possible_Bit_Aligned_Component (Expression (N));
6992 -- If we have none of the above, it means that we have fallen off the
6993 -- top testing prefixes recursively, and we now have a stand alone
6994 -- object, where we don't have a problem, unless this is a renaming,
6995 -- in which case we need to look into the renamed object.
6997 when others =>
6998 if Is_Entity_Name (N)
6999 and then Present (Renamed_Object (Entity (N)))
7000 then
7001 return
7002 Possible_Bit_Aligned_Component (Renamed_Object (Entity (N)));
7003 else
7004 return False;
7005 end if;
7007 end case;
7008 end Possible_Bit_Aligned_Component;
7010 -----------------------------------------------
7011 -- Process_Statements_For_Controlled_Objects --
7012 -----------------------------------------------
7014 procedure Process_Statements_For_Controlled_Objects (N : Node_Id) is
7015 Loc : constant Source_Ptr := Sloc (N);
7017 function Are_Wrapped (L : List_Id) return Boolean;
7018 -- Determine whether list L contains only one statement which is a block
7020 function Wrap_Statements_In_Block
7021 (L : List_Id;
7022 Scop : Entity_Id := Current_Scope) return Node_Id;
7023 -- Given a list of statements L, wrap it in a block statement and return
7024 -- the generated node. Scop is either the current scope or the scope of
7025 -- the context (if applicable).
7027 -----------------
7028 -- Are_Wrapped --
7029 -----------------
7031 function Are_Wrapped (L : List_Id) return Boolean is
7032 Stmt : constant Node_Id := First (L);
7033 begin
7034 return
7035 Present (Stmt)
7036 and then No (Next (Stmt))
7037 and then Nkind (Stmt) = N_Block_Statement;
7038 end Are_Wrapped;
7040 ------------------------------
7041 -- Wrap_Statements_In_Block --
7042 ------------------------------
7044 function Wrap_Statements_In_Block
7045 (L : List_Id;
7046 Scop : Entity_Id := Current_Scope) return Node_Id
7048 Block_Id : Entity_Id;
7049 Block_Nod : Node_Id;
7050 Iter_Loop : Entity_Id;
7052 begin
7053 Block_Nod :=
7054 Make_Block_Statement (Loc,
7055 Declarations => No_List,
7056 Handled_Statement_Sequence =>
7057 Make_Handled_Sequence_Of_Statements (Loc,
7058 Statements => L));
7060 -- Create a label for the block in case the block needs to manage the
7061 -- secondary stack. A label allows for flag Uses_Sec_Stack to be set.
7063 Add_Block_Identifier (Block_Nod, Block_Id);
7065 -- When wrapping the statements of an iterator loop, check whether
7066 -- the loop requires secondary stack management and if so, propagate
7067 -- the appropriate flags to the block. This ensures that the cursor
7068 -- is properly cleaned up at each iteration of the loop.
7070 Iter_Loop := Find_Enclosing_Iterator_Loop (Scop);
7072 if Present (Iter_Loop) then
7073 Set_Uses_Sec_Stack (Block_Id, Uses_Sec_Stack (Iter_Loop));
7075 -- Secondary stack reclamation is suppressed when the associated
7076 -- iterator loop contains a return statement which uses the stack.
7078 Set_Sec_Stack_Needed_For_Return
7079 (Block_Id, Sec_Stack_Needed_For_Return (Iter_Loop));
7080 end if;
7082 return Block_Nod;
7083 end Wrap_Statements_In_Block;
7085 -- Local variables
7087 Block : Node_Id;
7089 -- Start of processing for Process_Statements_For_Controlled_Objects
7091 begin
7092 -- Whenever a non-handled statement list is wrapped in a block, the
7093 -- block must be explicitly analyzed to redecorate all entities in the
7094 -- list and ensure that a finalizer is properly built.
7096 case Nkind (N) is
7097 when N_Elsif_Part |
7098 N_If_Statement |
7099 N_Conditional_Entry_Call |
7100 N_Selective_Accept =>
7102 -- Check the "then statements" for elsif parts and if statements
7104 if Nkind_In (N, N_Elsif_Part, N_If_Statement)
7105 and then not Is_Empty_List (Then_Statements (N))
7106 and then not Are_Wrapped (Then_Statements (N))
7107 and then Requires_Cleanup_Actions
7108 (Then_Statements (N), False, False)
7109 then
7110 Block := Wrap_Statements_In_Block (Then_Statements (N));
7111 Set_Then_Statements (N, New_List (Block));
7113 Analyze (Block);
7114 end if;
7116 -- Check the "else statements" for conditional entry calls, if
7117 -- statements and selective accepts.
7119 if Nkind_In (N, N_Conditional_Entry_Call,
7120 N_If_Statement,
7121 N_Selective_Accept)
7122 and then not Is_Empty_List (Else_Statements (N))
7123 and then not Are_Wrapped (Else_Statements (N))
7124 and then Requires_Cleanup_Actions
7125 (Else_Statements (N), False, False)
7126 then
7127 Block := Wrap_Statements_In_Block (Else_Statements (N));
7128 Set_Else_Statements (N, New_List (Block));
7130 Analyze (Block);
7131 end if;
7133 when N_Abortable_Part |
7134 N_Accept_Alternative |
7135 N_Case_Statement_Alternative |
7136 N_Delay_Alternative |
7137 N_Entry_Call_Alternative |
7138 N_Exception_Handler |
7139 N_Loop_Statement |
7140 N_Triggering_Alternative =>
7142 if not Is_Empty_List (Statements (N))
7143 and then not Are_Wrapped (Statements (N))
7144 and then Requires_Cleanup_Actions (Statements (N), False, False)
7145 then
7146 if Nkind (N) = N_Loop_Statement
7147 and then Present (Identifier (N))
7148 then
7149 Block :=
7150 Wrap_Statements_In_Block
7151 (L => Statements (N),
7152 Scop => Entity (Identifier (N)));
7153 else
7154 Block := Wrap_Statements_In_Block (Statements (N));
7155 end if;
7157 Set_Statements (N, New_List (Block));
7158 Analyze (Block);
7159 end if;
7161 when others =>
7162 null;
7163 end case;
7164 end Process_Statements_For_Controlled_Objects;
7166 ------------------
7167 -- Power_Of_Two --
7168 ------------------
7170 function Power_Of_Two (N : Node_Id) return Nat is
7171 Typ : constant Entity_Id := Etype (N);
7172 pragma Assert (Is_Integer_Type (Typ));
7174 Siz : constant Nat := UI_To_Int (Esize (Typ));
7175 Val : Uint;
7177 begin
7178 if not Compile_Time_Known_Value (N) then
7179 return 0;
7181 else
7182 Val := Expr_Value (N);
7183 for J in 1 .. Siz - 1 loop
7184 if Val = Uint_2 ** J then
7185 return J;
7186 end if;
7187 end loop;
7189 return 0;
7190 end if;
7191 end Power_Of_Two;
7193 ----------------------
7194 -- Remove_Init_Call --
7195 ----------------------
7197 function Remove_Init_Call
7198 (Var : Entity_Id;
7199 Rep_Clause : Node_Id) return Node_Id
7201 Par : constant Node_Id := Parent (Var);
7202 Typ : constant Entity_Id := Etype (Var);
7204 Init_Proc : Entity_Id;
7205 -- Initialization procedure for Typ
7207 function Find_Init_Call_In_List (From : Node_Id) return Node_Id;
7208 -- Look for init call for Var starting at From and scanning the
7209 -- enclosing list until Rep_Clause or the end of the list is reached.
7211 ----------------------------
7212 -- Find_Init_Call_In_List --
7213 ----------------------------
7215 function Find_Init_Call_In_List (From : Node_Id) return Node_Id is
7216 Init_Call : Node_Id;
7218 begin
7219 Init_Call := From;
7220 while Present (Init_Call) and then Init_Call /= Rep_Clause loop
7221 if Nkind (Init_Call) = N_Procedure_Call_Statement
7222 and then Is_Entity_Name (Name (Init_Call))
7223 and then Entity (Name (Init_Call)) = Init_Proc
7224 then
7225 return Init_Call;
7226 end if;
7228 Next (Init_Call);
7229 end loop;
7231 return Empty;
7232 end Find_Init_Call_In_List;
7234 Init_Call : Node_Id;
7236 -- Start of processing for Find_Init_Call
7238 begin
7239 if Present (Initialization_Statements (Var)) then
7240 Init_Call := Initialization_Statements (Var);
7241 Set_Initialization_Statements (Var, Empty);
7243 elsif not Has_Non_Null_Base_Init_Proc (Typ) then
7245 -- No init proc for the type, so obviously no call to be found
7247 return Empty;
7249 else
7250 -- We might be able to handle other cases below by just properly
7251 -- setting Initialization_Statements at the point where the init proc
7252 -- call is generated???
7254 Init_Proc := Base_Init_Proc (Typ);
7256 -- First scan the list containing the declaration of Var
7258 Init_Call := Find_Init_Call_In_List (From => Next (Par));
7260 -- If not found, also look on Var's freeze actions list, if any,
7261 -- since the init call may have been moved there (case of an address
7262 -- clause applying to Var).
7264 if No (Init_Call) and then Present (Freeze_Node (Var)) then
7265 Init_Call :=
7266 Find_Init_Call_In_List (First (Actions (Freeze_Node (Var))));
7267 end if;
7269 -- If the initialization call has actuals that use the secondary
7270 -- stack, the call may have been wrapped into a temporary block, in
7271 -- which case the block itself has to be removed.
7273 if No (Init_Call) and then Nkind (Next (Par)) = N_Block_Statement then
7274 declare
7275 Blk : constant Node_Id := Next (Par);
7276 begin
7277 if Present
7278 (Find_Init_Call_In_List
7279 (First (Statements (Handled_Statement_Sequence (Blk)))))
7280 then
7281 Init_Call := Blk;
7282 end if;
7283 end;
7284 end if;
7285 end if;
7287 if Present (Init_Call) then
7288 Remove (Init_Call);
7289 end if;
7290 return Init_Call;
7291 end Remove_Init_Call;
7293 -------------------------
7294 -- Remove_Side_Effects --
7295 -------------------------
7297 procedure Remove_Side_Effects
7298 (Exp : Node_Id;
7299 Name_Req : Boolean := False;
7300 Renaming_Req : Boolean := False;
7301 Variable_Ref : Boolean := False;
7302 Related_Id : Entity_Id := Empty;
7303 Is_Low_Bound : Boolean := False;
7304 Is_High_Bound : Boolean := False)
7306 function Build_Temporary
7307 (Loc : Source_Ptr;
7308 Id : Character;
7309 Related_Nod : Node_Id := Empty) return Entity_Id;
7310 -- Create an external symbol of the form xxx_FIRST/_LAST if Related_Id
7311 -- is present, otherwise it generates an internal temporary.
7313 ---------------------
7314 -- Build_Temporary --
7315 ---------------------
7317 function Build_Temporary
7318 (Loc : Source_Ptr;
7319 Id : Character;
7320 Related_Nod : Node_Id := Empty) return Entity_Id
7322 Temp_Nam : Name_Id;
7324 begin
7325 -- The context requires an external symbol
7327 if Present (Related_Id) then
7328 if Is_Low_Bound then
7329 Temp_Nam := New_External_Name (Chars (Related_Id), "_FIRST");
7330 else pragma Assert (Is_High_Bound);
7331 Temp_Nam := New_External_Name (Chars (Related_Id), "_LAST");
7332 end if;
7334 return Make_Defining_Identifier (Loc, Temp_Nam);
7336 -- Otherwise generate an internal temporary
7338 else
7339 return Make_Temporary (Loc, Id, Related_Nod);
7340 end if;
7341 end Build_Temporary;
7343 -- Local variables
7345 Loc : constant Source_Ptr := Sloc (Exp);
7346 Exp_Type : constant Entity_Id := Etype (Exp);
7347 Svg_Suppress : constant Suppress_Record := Scope_Suppress;
7348 Def_Id : Entity_Id;
7349 E : Node_Id;
7350 New_Exp : Node_Id;
7351 Ptr_Typ_Decl : Node_Id;
7352 Ref_Type : Entity_Id;
7353 Res : Node_Id;
7355 -- Start of processing for Remove_Side_Effects
7357 begin
7358 -- Handle cases in which there is nothing to do. In GNATprove mode,
7359 -- removal of side effects is useful for the light expansion of
7360 -- renamings. This removal should only occur when not inside a
7361 -- generic and not doing a pre-analysis.
7363 if not Expander_Active
7364 and (Inside_A_Generic or not Full_Analysis or not GNATprove_Mode)
7365 then
7366 return;
7367 end if;
7369 -- Cannot generate temporaries if the invocation to remove side effects
7370 -- was issued too early and the type of the expression is not resolved
7371 -- (this happens because routines Duplicate_Subexpr_XX implicitly invoke
7372 -- Remove_Side_Effects).
7374 if No (Exp_Type) or else Ekind (Exp_Type) = E_Access_Attribute_Type then
7375 return;
7377 -- No action needed for side-effect free expressions
7379 elsif Side_Effect_Free (Exp, Name_Req, Variable_Ref) then
7380 return;
7381 end if;
7383 -- The remaining procesaing is done with all checks suppressed
7385 -- Note: from now on, don't use return statements, instead do a goto
7386 -- Leave, to ensure that we properly restore Scope_Suppress.Suppress.
7388 Scope_Suppress.Suppress := (others => True);
7390 -- If it is a scalar type and we need to capture the value, just make
7391 -- a copy. Likewise for a function call, an attribute reference, a
7392 -- conditional expression, an allocator, or an operator. And if we have
7393 -- a volatile reference and Name_Req is not set (see comments for
7394 -- Side_Effect_Free).
7396 if Is_Elementary_Type (Exp_Type)
7398 -- Note: this test is rather mysterious??? Why can't we just test ONLY
7399 -- Is_Elementary_Type and be done with it. If we try that approach, we
7400 -- get some failures (infinite recursions) from the Duplicate_Subexpr
7401 -- call at the end of Checks.Apply_Predicate_Check. To be
7402 -- investigated ???
7404 and then (Variable_Ref
7405 or else Nkind_In (Exp, N_Attribute_Reference,
7406 N_Allocator,
7407 N_Case_Expression,
7408 N_If_Expression,
7409 N_Function_Call)
7410 or else Nkind (Exp) in N_Op
7411 or else (not Name_Req
7412 and then Is_Volatile_Reference (Exp)))
7413 then
7414 Def_Id := Build_Temporary (Loc, 'R', Exp);
7415 Set_Etype (Def_Id, Exp_Type);
7416 Res := New_Occurrence_Of (Def_Id, Loc);
7418 -- If the expression is a packed reference, it must be reanalyzed and
7419 -- expanded, depending on context. This is the case for actuals where
7420 -- a constraint check may capture the actual before expansion of the
7421 -- call is complete.
7423 if Nkind (Exp) = N_Indexed_Component
7424 and then Is_Packed (Etype (Prefix (Exp)))
7425 then
7426 Set_Analyzed (Exp, False);
7427 Set_Analyzed (Prefix (Exp), False);
7428 end if;
7430 -- Generate:
7431 -- Rnn : Exp_Type renames Expr;
7433 if Renaming_Req then
7434 E :=
7435 Make_Object_Renaming_Declaration (Loc,
7436 Defining_Identifier => Def_Id,
7437 Subtype_Mark => New_Occurrence_Of (Exp_Type, Loc),
7438 Name => Relocate_Node (Exp));
7440 -- Generate:
7441 -- Rnn : constant Exp_Type := Expr;
7443 else
7444 E :=
7445 Make_Object_Declaration (Loc,
7446 Defining_Identifier => Def_Id,
7447 Object_Definition => New_Occurrence_Of (Exp_Type, Loc),
7448 Constant_Present => True,
7449 Expression => Relocate_Node (Exp));
7451 Set_Assignment_OK (E);
7452 end if;
7454 Insert_Action (Exp, E);
7456 -- If the expression has the form v.all then we can just capture the
7457 -- pointer, and then do an explicit dereference on the result, but
7458 -- this is not right if this is a volatile reference.
7460 elsif Nkind (Exp) = N_Explicit_Dereference
7461 and then not Is_Volatile_Reference (Exp)
7462 then
7463 Def_Id := Build_Temporary (Loc, 'R', Exp);
7464 Res :=
7465 Make_Explicit_Dereference (Loc, New_Occurrence_Of (Def_Id, Loc));
7467 Insert_Action (Exp,
7468 Make_Object_Declaration (Loc,
7469 Defining_Identifier => Def_Id,
7470 Object_Definition =>
7471 New_Occurrence_Of (Etype (Prefix (Exp)), Loc),
7472 Constant_Present => True,
7473 Expression => Relocate_Node (Prefix (Exp))));
7475 -- Similar processing for an unchecked conversion of an expression of
7476 -- the form v.all, where we want the same kind of treatment.
7478 elsif Nkind (Exp) = N_Unchecked_Type_Conversion
7479 and then Nkind (Expression (Exp)) = N_Explicit_Dereference
7480 then
7481 Remove_Side_Effects (Expression (Exp), Name_Req, Variable_Ref);
7482 goto Leave;
7484 -- If this is a type conversion, leave the type conversion and remove
7485 -- the side effects in the expression. This is important in several
7486 -- circumstances: for change of representations, and also when this is a
7487 -- view conversion to a smaller object, where gigi can end up creating
7488 -- its own temporary of the wrong size.
7490 elsif Nkind (Exp) = N_Type_Conversion then
7491 Remove_Side_Effects (Expression (Exp), Name_Req, Variable_Ref);
7492 goto Leave;
7494 -- If this is an unchecked conversion that Gigi can't handle, make
7495 -- a copy or a use a renaming to capture the value.
7497 elsif Nkind (Exp) = N_Unchecked_Type_Conversion
7498 and then not Safe_Unchecked_Type_Conversion (Exp)
7499 then
7500 if CW_Or_Has_Controlled_Part (Exp_Type) then
7502 -- Use a renaming to capture the expression, rather than create
7503 -- a controlled temporary.
7505 Def_Id := Build_Temporary (Loc, 'R', Exp);
7506 Res := New_Occurrence_Of (Def_Id, Loc);
7508 Insert_Action (Exp,
7509 Make_Object_Renaming_Declaration (Loc,
7510 Defining_Identifier => Def_Id,
7511 Subtype_Mark => New_Occurrence_Of (Exp_Type, Loc),
7512 Name => Relocate_Node (Exp)));
7514 else
7515 Def_Id := Build_Temporary (Loc, 'R', Exp);
7516 Set_Etype (Def_Id, Exp_Type);
7517 Res := New_Occurrence_Of (Def_Id, Loc);
7519 E :=
7520 Make_Object_Declaration (Loc,
7521 Defining_Identifier => Def_Id,
7522 Object_Definition => New_Occurrence_Of (Exp_Type, Loc),
7523 Constant_Present => not Is_Variable (Exp),
7524 Expression => Relocate_Node (Exp));
7526 Set_Assignment_OK (E);
7527 Insert_Action (Exp, E);
7528 end if;
7530 -- For expressions that denote objects, we can use a renaming scheme.
7531 -- This is needed for correctness in the case of a volatile object of
7532 -- a non-volatile type because the Make_Reference call of the "default"
7533 -- approach would generate an illegal access value (an access value
7534 -- cannot designate such an object - see Analyze_Reference).
7536 elsif Is_Object_Reference (Exp)
7537 and then Nkind (Exp) /= N_Function_Call
7539 -- In Ada 2012 a qualified expression is an object, but for purposes
7540 -- of removing side effects it still need to be transformed into a
7541 -- separate declaration, particularly in the case of an aggregate.
7543 and then Nkind (Exp) /= N_Qualified_Expression
7545 -- We skip using this scheme if we have an object of a volatile
7546 -- type and we do not have Name_Req set true (see comments for
7547 -- Side_Effect_Free).
7549 and then (Name_Req or else not Treat_As_Volatile (Exp_Type))
7550 then
7551 Def_Id := Build_Temporary (Loc, 'R', Exp);
7553 if Nkind (Exp) = N_Selected_Component
7554 and then Nkind (Prefix (Exp)) = N_Function_Call
7555 and then Is_Array_Type (Exp_Type)
7556 then
7557 -- Avoid generating a variable-sized temporary, by generating
7558 -- the renaming declaration just for the function call. The
7559 -- transformation could be refined to apply only when the array
7560 -- component is constrained by a discriminant???
7562 Res :=
7563 Make_Selected_Component (Loc,
7564 Prefix => New_Occurrence_Of (Def_Id, Loc),
7565 Selector_Name => Selector_Name (Exp));
7567 Insert_Action (Exp,
7568 Make_Object_Renaming_Declaration (Loc,
7569 Defining_Identifier => Def_Id,
7570 Subtype_Mark =>
7571 New_Occurrence_Of (Base_Type (Etype (Prefix (Exp))), Loc),
7572 Name => Relocate_Node (Prefix (Exp))));
7574 else
7575 Res := New_Occurrence_Of (Def_Id, Loc);
7577 Insert_Action (Exp,
7578 Make_Object_Renaming_Declaration (Loc,
7579 Defining_Identifier => Def_Id,
7580 Subtype_Mark => New_Occurrence_Of (Exp_Type, Loc),
7581 Name => Relocate_Node (Exp)));
7582 end if;
7584 -- If this is a packed reference, or a selected component with
7585 -- a non-standard representation, a reference to the temporary
7586 -- will be replaced by a copy of the original expression (see
7587 -- Exp_Ch2.Expand_Renaming). Otherwise the temporary must be
7588 -- elaborated by gigi, and is of course not to be replaced in-line
7589 -- by the expression it renames, which would defeat the purpose of
7590 -- removing the side-effect.
7592 if Nkind_In (Exp, N_Selected_Component, N_Indexed_Component)
7593 and then Has_Non_Standard_Rep (Etype (Prefix (Exp)))
7594 then
7595 null;
7596 else
7597 Set_Is_Renaming_Of_Object (Def_Id, False);
7598 end if;
7600 -- Otherwise we generate a reference to the value
7602 else
7603 -- An expression which is in SPARK mode is considered side effect
7604 -- free if the resulting value is captured by a variable or a
7605 -- constant.
7607 if GNATprove_Mode
7608 and then Nkind (Parent (Exp)) = N_Object_Declaration
7609 then
7610 goto Leave;
7611 end if;
7613 -- Special processing for function calls that return a limited type.
7614 -- We need to build a declaration that will enable build-in-place
7615 -- expansion of the call. This is not done if the context is already
7616 -- an object declaration, to prevent infinite recursion.
7618 -- This is relevant only in Ada 2005 mode. In Ada 95 programs we have
7619 -- to accommodate functions returning limited objects by reference.
7621 if Ada_Version >= Ada_2005
7622 and then Nkind (Exp) = N_Function_Call
7623 and then Is_Limited_View (Etype (Exp))
7624 and then Nkind (Parent (Exp)) /= N_Object_Declaration
7625 then
7626 declare
7627 Obj : constant Entity_Id := Make_Temporary (Loc, 'F', Exp);
7628 Decl : Node_Id;
7630 begin
7631 Decl :=
7632 Make_Object_Declaration (Loc,
7633 Defining_Identifier => Obj,
7634 Object_Definition => New_Occurrence_Of (Exp_Type, Loc),
7635 Expression => Relocate_Node (Exp));
7637 Insert_Action (Exp, Decl);
7638 Set_Etype (Obj, Exp_Type);
7639 Rewrite (Exp, New_Occurrence_Of (Obj, Loc));
7640 goto Leave;
7641 end;
7642 end if;
7644 Def_Id := Build_Temporary (Loc, 'R', Exp);
7646 -- The regular expansion of functions with side effects involves the
7647 -- generation of an access type to capture the return value found on
7648 -- the secondary stack. Since SPARK (and why) cannot process access
7649 -- types, use a different approach which ignores the secondary stack
7650 -- and "copies" the returned object.
7652 if GNATprove_Mode then
7653 Res := New_Occurrence_Of (Def_Id, Loc);
7654 Ref_Type := Exp_Type;
7656 -- Regular expansion utilizing an access type and 'reference
7658 else
7659 Res :=
7660 Make_Explicit_Dereference (Loc,
7661 Prefix => New_Occurrence_Of (Def_Id, Loc));
7663 -- Generate:
7664 -- type Ann is access all <Exp_Type>;
7666 Ref_Type := Make_Temporary (Loc, 'A');
7668 Ptr_Typ_Decl :=
7669 Make_Full_Type_Declaration (Loc,
7670 Defining_Identifier => Ref_Type,
7671 Type_Definition =>
7672 Make_Access_To_Object_Definition (Loc,
7673 All_Present => True,
7674 Subtype_Indication =>
7675 New_Occurrence_Of (Exp_Type, Loc)));
7677 Insert_Action (Exp, Ptr_Typ_Decl);
7678 end if;
7680 E := Exp;
7681 if Nkind (E) = N_Explicit_Dereference then
7682 New_Exp := Relocate_Node (Prefix (E));
7684 else
7685 E := Relocate_Node (E);
7687 -- Do not generate a 'reference in SPARK mode since the access
7688 -- type is not created in the first place.
7690 if GNATprove_Mode then
7691 New_Exp := E;
7693 -- Otherwise generate reference, marking the value as non-null
7694 -- since we know it cannot be null and we don't want a check.
7696 else
7697 New_Exp := Make_Reference (Loc, E);
7698 Set_Is_Known_Non_Null (Def_Id);
7699 end if;
7700 end if;
7702 if Is_Delayed_Aggregate (E) then
7704 -- The expansion of nested aggregates is delayed until the
7705 -- enclosing aggregate is expanded. As aggregates are often
7706 -- qualified, the predicate applies to qualified expressions as
7707 -- well, indicating that the enclosing aggregate has not been
7708 -- expanded yet. At this point the aggregate is part of a
7709 -- stand-alone declaration, and must be fully expanded.
7711 if Nkind (E) = N_Qualified_Expression then
7712 Set_Expansion_Delayed (Expression (E), False);
7713 Set_Analyzed (Expression (E), False);
7714 else
7715 Set_Expansion_Delayed (E, False);
7716 end if;
7718 Set_Analyzed (E, False);
7719 end if;
7721 Insert_Action (Exp,
7722 Make_Object_Declaration (Loc,
7723 Defining_Identifier => Def_Id,
7724 Object_Definition => New_Occurrence_Of (Ref_Type, Loc),
7725 Constant_Present => True,
7726 Expression => New_Exp));
7727 end if;
7729 -- Preserve the Assignment_OK flag in all copies, since at least one
7730 -- copy may be used in a context where this flag must be set (otherwise
7731 -- why would the flag be set in the first place).
7733 Set_Assignment_OK (Res, Assignment_OK (Exp));
7735 -- Finally rewrite the original expression and we are done
7737 Rewrite (Exp, Res);
7738 Analyze_And_Resolve (Exp, Exp_Type);
7740 <<Leave>>
7741 Scope_Suppress := Svg_Suppress;
7742 end Remove_Side_Effects;
7744 ---------------------------
7745 -- Represented_As_Scalar --
7746 ---------------------------
7748 function Represented_As_Scalar (T : Entity_Id) return Boolean is
7749 UT : constant Entity_Id := Underlying_Type (T);
7750 begin
7751 return Is_Scalar_Type (UT)
7752 or else (Is_Bit_Packed_Array (UT)
7753 and then Is_Scalar_Type (Packed_Array_Impl_Type (UT)));
7754 end Represented_As_Scalar;
7756 ------------------------------
7757 -- Requires_Cleanup_Actions --
7758 ------------------------------
7760 function Requires_Cleanup_Actions
7761 (N : Node_Id;
7762 Lib_Level : Boolean) return Boolean
7764 At_Lib_Level : constant Boolean :=
7765 Lib_Level
7766 and then Nkind_In (N, N_Package_Body,
7767 N_Package_Specification);
7768 -- N is at the library level if the top-most context is a package and
7769 -- the path taken to reach N does not inlcude non-package constructs.
7771 begin
7772 case Nkind (N) is
7773 when N_Accept_Statement |
7774 N_Block_Statement |
7775 N_Entry_Body |
7776 N_Package_Body |
7777 N_Protected_Body |
7778 N_Subprogram_Body |
7779 N_Task_Body =>
7780 return
7781 Requires_Cleanup_Actions (Declarations (N), At_Lib_Level, True)
7782 or else
7783 (Present (Handled_Statement_Sequence (N))
7784 and then
7785 Requires_Cleanup_Actions
7786 (Statements (Handled_Statement_Sequence (N)),
7787 At_Lib_Level, True));
7789 when N_Package_Specification =>
7790 return
7791 Requires_Cleanup_Actions
7792 (Visible_Declarations (N), At_Lib_Level, True)
7793 or else
7794 Requires_Cleanup_Actions
7795 (Private_Declarations (N), At_Lib_Level, True);
7797 when others =>
7798 return False;
7799 end case;
7800 end Requires_Cleanup_Actions;
7802 ------------------------------
7803 -- Requires_Cleanup_Actions --
7804 ------------------------------
7806 function Requires_Cleanup_Actions
7807 (L : List_Id;
7808 Lib_Level : Boolean;
7809 Nested_Constructs : Boolean) return Boolean
7811 Decl : Node_Id;
7812 Expr : Node_Id;
7813 Obj_Id : Entity_Id;
7814 Obj_Typ : Entity_Id;
7815 Pack_Id : Entity_Id;
7816 Typ : Entity_Id;
7818 begin
7819 if No (L)
7820 or else Is_Empty_List (L)
7821 then
7822 return False;
7823 end if;
7825 Decl := First (L);
7826 while Present (Decl) loop
7828 -- Library-level tagged types
7830 if Nkind (Decl) = N_Full_Type_Declaration then
7831 Typ := Defining_Identifier (Decl);
7833 if Is_Tagged_Type (Typ)
7834 and then Is_Library_Level_Entity (Typ)
7835 and then Convention (Typ) = Convention_Ada
7836 and then Present (Access_Disp_Table (Typ))
7837 and then RTE_Available (RE_Unregister_Tag)
7838 and then not No_Run_Time_Mode
7839 and then not Is_Abstract_Type (Typ)
7840 then
7841 return True;
7842 end if;
7844 -- Regular object declarations
7846 elsif Nkind (Decl) = N_Object_Declaration then
7847 Obj_Id := Defining_Identifier (Decl);
7848 Obj_Typ := Base_Type (Etype (Obj_Id));
7849 Expr := Expression (Decl);
7851 -- Bypass any form of processing for objects which have their
7852 -- finalization disabled. This applies only to objects at the
7853 -- library level.
7855 if Lib_Level and then Finalize_Storage_Only (Obj_Typ) then
7856 null;
7858 -- Transient variables are treated separately in order to minimize
7859 -- the size of the generated code. See Exp_Ch7.Process_Transient_
7860 -- Objects.
7862 elsif Is_Processed_Transient (Obj_Id) then
7863 null;
7865 -- The object is of the form:
7866 -- Obj : Typ [:= Expr];
7868 -- Do not process the incomplete view of a deferred constant. Do
7869 -- not consider tag-to-class-wide conversions.
7871 elsif not Is_Imported (Obj_Id)
7872 and then Needs_Finalization (Obj_Typ)
7873 and then not (Ekind (Obj_Id) = E_Constant
7874 and then not Has_Completion (Obj_Id))
7875 and then not Is_Tag_To_Class_Wide_Conversion (Obj_Id)
7876 then
7877 return True;
7879 -- The object is of the form:
7880 -- Obj : Access_Typ := Non_BIP_Function_Call'reference;
7882 -- Obj : Access_Typ :=
7883 -- BIP_Function_Call (BIPalloc => 2, ...)'reference;
7885 elsif Is_Access_Type (Obj_Typ)
7886 and then Needs_Finalization
7887 (Available_View (Designated_Type (Obj_Typ)))
7888 and then Present (Expr)
7889 and then
7890 (Is_Secondary_Stack_BIP_Func_Call (Expr)
7891 or else
7892 (Is_Non_BIP_Func_Call (Expr)
7893 and then not Is_Related_To_Func_Return (Obj_Id)))
7894 then
7895 return True;
7897 -- Processing for "hook" objects generated for controlled
7898 -- transients declared inside an Expression_With_Actions.
7900 elsif Is_Access_Type (Obj_Typ)
7901 and then Present (Status_Flag_Or_Transient_Decl (Obj_Id))
7902 and then Nkind (Status_Flag_Or_Transient_Decl (Obj_Id)) =
7903 N_Object_Declaration
7904 then
7905 return True;
7907 -- Processing for intermediate results of if expressions where
7908 -- one of the alternatives uses a controlled function call.
7910 elsif Is_Access_Type (Obj_Typ)
7911 and then Present (Status_Flag_Or_Transient_Decl (Obj_Id))
7912 and then Nkind (Status_Flag_Or_Transient_Decl (Obj_Id)) =
7913 N_Defining_Identifier
7914 and then Present (Expr)
7915 and then Nkind (Expr) = N_Null
7916 then
7917 return True;
7919 -- Simple protected objects which use type System.Tasking.
7920 -- Protected_Objects.Protection to manage their locks should be
7921 -- treated as controlled since they require manual cleanup.
7923 elsif Ekind (Obj_Id) = E_Variable
7924 and then (Is_Simple_Protected_Type (Obj_Typ)
7925 or else Has_Simple_Protected_Object (Obj_Typ))
7926 then
7927 return True;
7928 end if;
7930 -- Specific cases of object renamings
7932 elsif Nkind (Decl) = N_Object_Renaming_Declaration then
7933 Obj_Id := Defining_Identifier (Decl);
7934 Obj_Typ := Base_Type (Etype (Obj_Id));
7936 -- Bypass any form of processing for objects which have their
7937 -- finalization disabled. This applies only to objects at the
7938 -- library level.
7940 if Lib_Level and then Finalize_Storage_Only (Obj_Typ) then
7941 null;
7943 -- Return object of a build-in-place function. This case is
7944 -- recognized and marked by the expansion of an extended return
7945 -- statement (see Expand_N_Extended_Return_Statement).
7947 elsif Needs_Finalization (Obj_Typ)
7948 and then Is_Return_Object (Obj_Id)
7949 and then Present (Status_Flag_Or_Transient_Decl (Obj_Id))
7950 then
7951 return True;
7953 -- Detect a case where a source object has been initialized by
7954 -- a controlled function call or another object which was later
7955 -- rewritten as a class-wide conversion of Ada.Tags.Displace.
7957 -- Obj1 : CW_Type := Src_Obj;
7958 -- Obj2 : CW_Type := Function_Call (...);
7960 -- Obj1 : CW_Type renames (... Ada.Tags.Displace (Src_Obj));
7961 -- Tmp : ... := Function_Call (...)'reference;
7962 -- Obj2 : CW_Type renames (... Ada.Tags.Displace (Tmp));
7964 elsif Is_Displacement_Of_Object_Or_Function_Result (Obj_Id) then
7965 return True;
7966 end if;
7968 -- Inspect the freeze node of an access-to-controlled type and look
7969 -- for a delayed finalization master. This case arises when the
7970 -- freeze actions are inserted at a later time than the expansion of
7971 -- the context. Since Build_Finalizer is never called on a single
7972 -- construct twice, the master will be ultimately left out and never
7973 -- finalized. This is also needed for freeze actions of designated
7974 -- types themselves, since in some cases the finalization master is
7975 -- associated with a designated type's freeze node rather than that
7976 -- of the access type (see handling for freeze actions in
7977 -- Build_Finalization_Master).
7979 elsif Nkind (Decl) = N_Freeze_Entity
7980 and then Present (Actions (Decl))
7981 then
7982 Typ := Entity (Decl);
7984 if ((Is_Access_Type (Typ)
7985 and then not Is_Access_Subprogram_Type (Typ)
7986 and then Needs_Finalization
7987 (Available_View (Designated_Type (Typ))))
7988 or else (Is_Type (Typ) and then Needs_Finalization (Typ)))
7989 and then Requires_Cleanup_Actions
7990 (Actions (Decl), Lib_Level, Nested_Constructs)
7991 then
7992 return True;
7993 end if;
7995 -- Nested package declarations
7997 elsif Nested_Constructs
7998 and then Nkind (Decl) = N_Package_Declaration
7999 then
8000 Pack_Id := Defining_Unit_Name (Specification (Decl));
8002 if Nkind (Pack_Id) = N_Defining_Program_Unit_Name then
8003 Pack_Id := Defining_Identifier (Pack_Id);
8004 end if;
8006 if Ekind (Pack_Id) /= E_Generic_Package
8007 and then
8008 Requires_Cleanup_Actions (Specification (Decl), Lib_Level)
8009 then
8010 return True;
8011 end if;
8013 -- Nested package bodies
8015 elsif Nested_Constructs and then Nkind (Decl) = N_Package_Body then
8016 Pack_Id := Corresponding_Spec (Decl);
8018 if Ekind (Pack_Id) /= E_Generic_Package
8019 and then Requires_Cleanup_Actions (Decl, Lib_Level)
8020 then
8021 return True;
8022 end if;
8023 end if;
8025 Next (Decl);
8026 end loop;
8028 return False;
8029 end Requires_Cleanup_Actions;
8031 ------------------------------------
8032 -- Safe_Unchecked_Type_Conversion --
8033 ------------------------------------
8035 -- Note: this function knows quite a bit about the exact requirements of
8036 -- Gigi with respect to unchecked type conversions, and its code must be
8037 -- coordinated with any changes in Gigi in this area.
8039 -- The above requirements should be documented in Sinfo ???
8041 function Safe_Unchecked_Type_Conversion (Exp : Node_Id) return Boolean is
8042 Otyp : Entity_Id;
8043 Ityp : Entity_Id;
8044 Oalign : Uint;
8045 Ialign : Uint;
8046 Pexp : constant Node_Id := Parent (Exp);
8048 begin
8049 -- If the expression is the RHS of an assignment or object declaration
8050 -- we are always OK because there will always be a target.
8052 -- Object renaming declarations, (generated for view conversions of
8053 -- actuals in inlined calls), like object declarations, provide an
8054 -- explicit type, and are safe as well.
8056 if (Nkind (Pexp) = N_Assignment_Statement
8057 and then Expression (Pexp) = Exp)
8058 or else Nkind_In (Pexp, N_Object_Declaration,
8059 N_Object_Renaming_Declaration)
8060 then
8061 return True;
8063 -- If the expression is the prefix of an N_Selected_Component we should
8064 -- also be OK because GCC knows to look inside the conversion except if
8065 -- the type is discriminated. We assume that we are OK anyway if the
8066 -- type is not set yet or if it is controlled since we can't afford to
8067 -- introduce a temporary in this case.
8069 elsif Nkind (Pexp) = N_Selected_Component
8070 and then Prefix (Pexp) = Exp
8071 then
8072 if No (Etype (Pexp)) then
8073 return True;
8074 else
8075 return
8076 not Has_Discriminants (Etype (Pexp))
8077 or else Is_Constrained (Etype (Pexp));
8078 end if;
8079 end if;
8081 -- Set the output type, this comes from Etype if it is set, otherwise we
8082 -- take it from the subtype mark, which we assume was already fully
8083 -- analyzed.
8085 if Present (Etype (Exp)) then
8086 Otyp := Etype (Exp);
8087 else
8088 Otyp := Entity (Subtype_Mark (Exp));
8089 end if;
8091 -- The input type always comes from the expression, and we assume
8092 -- this is indeed always analyzed, so we can simply get the Etype.
8094 Ityp := Etype (Expression (Exp));
8096 -- Initialize alignments to unknown so far
8098 Oalign := No_Uint;
8099 Ialign := No_Uint;
8101 -- Replace a concurrent type by its corresponding record type and each
8102 -- type by its underlying type and do the tests on those. The original
8103 -- type may be a private type whose completion is a concurrent type, so
8104 -- find the underlying type first.
8106 if Present (Underlying_Type (Otyp)) then
8107 Otyp := Underlying_Type (Otyp);
8108 end if;
8110 if Present (Underlying_Type (Ityp)) then
8111 Ityp := Underlying_Type (Ityp);
8112 end if;
8114 if Is_Concurrent_Type (Otyp) then
8115 Otyp := Corresponding_Record_Type (Otyp);
8116 end if;
8118 if Is_Concurrent_Type (Ityp) then
8119 Ityp := Corresponding_Record_Type (Ityp);
8120 end if;
8122 -- If the base types are the same, we know there is no problem since
8123 -- this conversion will be a noop.
8125 if Implementation_Base_Type (Otyp) = Implementation_Base_Type (Ityp) then
8126 return True;
8128 -- Same if this is an upwards conversion of an untagged type, and there
8129 -- are no constraints involved (could be more general???)
8131 elsif Etype (Ityp) = Otyp
8132 and then not Is_Tagged_Type (Ityp)
8133 and then not Has_Discriminants (Ityp)
8134 and then No (First_Rep_Item (Base_Type (Ityp)))
8135 then
8136 return True;
8138 -- If the expression has an access type (object or subprogram) we assume
8139 -- that the conversion is safe, because the size of the target is safe,
8140 -- even if it is a record (which might be treated as having unknown size
8141 -- at this point).
8143 elsif Is_Access_Type (Ityp) then
8144 return True;
8146 -- If the size of output type is known at compile time, there is never
8147 -- a problem. Note that unconstrained records are considered to be of
8148 -- known size, but we can't consider them that way here, because we are
8149 -- talking about the actual size of the object.
8151 -- We also make sure that in addition to the size being known, we do not
8152 -- have a case which might generate an embarrassingly large temp in
8153 -- stack checking mode.
8155 elsif Size_Known_At_Compile_Time (Otyp)
8156 and then
8157 (not Stack_Checking_Enabled
8158 or else not May_Generate_Large_Temp (Otyp))
8159 and then not (Is_Record_Type (Otyp) and then not Is_Constrained (Otyp))
8160 then
8161 return True;
8163 -- If either type is tagged, then we know the alignment is OK so
8164 -- Gigi will be able to use pointer punning.
8166 elsif Is_Tagged_Type (Otyp) or else Is_Tagged_Type (Ityp) then
8167 return True;
8169 -- If either type is a limited record type, we cannot do a copy, so say
8170 -- safe since there's nothing else we can do.
8172 elsif Is_Limited_Record (Otyp) or else Is_Limited_Record (Ityp) then
8173 return True;
8175 -- Conversions to and from packed array types are always ignored and
8176 -- hence are safe.
8178 elsif Is_Packed_Array_Impl_Type (Otyp)
8179 or else Is_Packed_Array_Impl_Type (Ityp)
8180 then
8181 return True;
8182 end if;
8184 -- The only other cases known to be safe is if the input type's
8185 -- alignment is known to be at least the maximum alignment for the
8186 -- target or if both alignments are known and the output type's
8187 -- alignment is no stricter than the input's. We can use the component
8188 -- type alignement for an array if a type is an unpacked array type.
8190 if Present (Alignment_Clause (Otyp)) then
8191 Oalign := Expr_Value (Expression (Alignment_Clause (Otyp)));
8193 elsif Is_Array_Type (Otyp)
8194 and then Present (Alignment_Clause (Component_Type (Otyp)))
8195 then
8196 Oalign := Expr_Value (Expression (Alignment_Clause
8197 (Component_Type (Otyp))));
8198 end if;
8200 if Present (Alignment_Clause (Ityp)) then
8201 Ialign := Expr_Value (Expression (Alignment_Clause (Ityp)));
8203 elsif Is_Array_Type (Ityp)
8204 and then Present (Alignment_Clause (Component_Type (Ityp)))
8205 then
8206 Ialign := Expr_Value (Expression (Alignment_Clause
8207 (Component_Type (Ityp))));
8208 end if;
8210 if Ialign /= No_Uint and then Ialign > Maximum_Alignment then
8211 return True;
8213 elsif Ialign /= No_Uint
8214 and then Oalign /= No_Uint
8215 and then Ialign <= Oalign
8216 then
8217 return True;
8219 -- Otherwise, Gigi cannot handle this and we must make a temporary
8221 else
8222 return False;
8223 end if;
8224 end Safe_Unchecked_Type_Conversion;
8226 ---------------------------------
8227 -- Set_Current_Value_Condition --
8228 ---------------------------------
8230 -- Note: the implementation of this procedure is very closely tied to the
8231 -- implementation of Get_Current_Value_Condition. Here we set required
8232 -- Current_Value fields, and in Get_Current_Value_Condition, we interpret
8233 -- them, so they must have a consistent view.
8235 procedure Set_Current_Value_Condition (Cnode : Node_Id) is
8237 procedure Set_Entity_Current_Value (N : Node_Id);
8238 -- If N is an entity reference, where the entity is of an appropriate
8239 -- kind, then set the current value of this entity to Cnode, unless
8240 -- there is already a definite value set there.
8242 procedure Set_Expression_Current_Value (N : Node_Id);
8243 -- If N is of an appropriate form, sets an appropriate entry in current
8244 -- value fields of relevant entities. Multiple entities can be affected
8245 -- in the case of an AND or AND THEN.
8247 ------------------------------
8248 -- Set_Entity_Current_Value --
8249 ------------------------------
8251 procedure Set_Entity_Current_Value (N : Node_Id) is
8252 begin
8253 if Is_Entity_Name (N) then
8254 declare
8255 Ent : constant Entity_Id := Entity (N);
8257 begin
8258 -- Don't capture if not safe to do so
8260 if not Safe_To_Capture_Value (N, Ent, Cond => True) then
8261 return;
8262 end if;
8264 -- Here we have a case where the Current_Value field may need
8265 -- to be set. We set it if it is not already set to a compile
8266 -- time expression value.
8268 -- Note that this represents a decision that one condition
8269 -- blots out another previous one. That's certainly right if
8270 -- they occur at the same level. If the second one is nested,
8271 -- then the decision is neither right nor wrong (it would be
8272 -- equally OK to leave the outer one in place, or take the new
8273 -- inner one. Really we should record both, but our data
8274 -- structures are not that elaborate.
8276 if Nkind (Current_Value (Ent)) not in N_Subexpr then
8277 Set_Current_Value (Ent, Cnode);
8278 end if;
8279 end;
8280 end if;
8281 end Set_Entity_Current_Value;
8283 ----------------------------------
8284 -- Set_Expression_Current_Value --
8285 ----------------------------------
8287 procedure Set_Expression_Current_Value (N : Node_Id) is
8288 Cond : Node_Id;
8290 begin
8291 Cond := N;
8293 -- Loop to deal with (ignore for now) any NOT operators present. The
8294 -- presence of NOT operators will be handled properly when we call
8295 -- Get_Current_Value_Condition.
8297 while Nkind (Cond) = N_Op_Not loop
8298 Cond := Right_Opnd (Cond);
8299 end loop;
8301 -- For an AND or AND THEN, recursively process operands
8303 if Nkind (Cond) = N_Op_And or else Nkind (Cond) = N_And_Then then
8304 Set_Expression_Current_Value (Left_Opnd (Cond));
8305 Set_Expression_Current_Value (Right_Opnd (Cond));
8306 return;
8307 end if;
8309 -- Check possible relational operator
8311 if Nkind (Cond) in N_Op_Compare then
8312 if Compile_Time_Known_Value (Right_Opnd (Cond)) then
8313 Set_Entity_Current_Value (Left_Opnd (Cond));
8314 elsif Compile_Time_Known_Value (Left_Opnd (Cond)) then
8315 Set_Entity_Current_Value (Right_Opnd (Cond));
8316 end if;
8318 elsif Nkind_In (Cond,
8319 N_Type_Conversion,
8320 N_Qualified_Expression,
8321 N_Expression_With_Actions)
8322 then
8323 Set_Expression_Current_Value (Expression (Cond));
8325 -- Check possible boolean variable reference
8327 else
8328 Set_Entity_Current_Value (Cond);
8329 end if;
8330 end Set_Expression_Current_Value;
8332 -- Start of processing for Set_Current_Value_Condition
8334 begin
8335 Set_Expression_Current_Value (Condition (Cnode));
8336 end Set_Current_Value_Condition;
8338 --------------------------
8339 -- Set_Elaboration_Flag --
8340 --------------------------
8342 procedure Set_Elaboration_Flag (N : Node_Id; Spec_Id : Entity_Id) is
8343 Loc : constant Source_Ptr := Sloc (N);
8344 Ent : constant Entity_Id := Elaboration_Entity (Spec_Id);
8345 Asn : Node_Id;
8347 begin
8348 if Present (Ent) then
8350 -- Nothing to do if at the compilation unit level, because in this
8351 -- case the flag is set by the binder generated elaboration routine.
8353 if Nkind (Parent (N)) = N_Compilation_Unit then
8354 null;
8356 -- Here we do need to generate an assignment statement
8358 else
8359 Check_Restriction (No_Elaboration_Code, N);
8360 Asn :=
8361 Make_Assignment_Statement (Loc,
8362 Name => New_Occurrence_Of (Ent, Loc),
8363 Expression => Make_Integer_Literal (Loc, Uint_1));
8365 if Nkind (Parent (N)) = N_Subunit then
8366 Insert_After (Corresponding_Stub (Parent (N)), Asn);
8367 else
8368 Insert_After (N, Asn);
8369 end if;
8371 Analyze (Asn);
8373 -- Kill current value indication. This is necessary because the
8374 -- tests of this flag are inserted out of sequence and must not
8375 -- pick up bogus indications of the wrong constant value.
8377 Set_Current_Value (Ent, Empty);
8379 -- If the subprogram is in the current declarative part and
8380 -- 'access has been applied to it, generate an elaboration
8381 -- check at the beginning of the declarations of the body.
8383 if Nkind (N) = N_Subprogram_Body
8384 and then Address_Taken (Spec_Id)
8385 and then
8386 Ekind_In (Scope (Spec_Id), E_Block, E_Procedure, E_Function)
8387 then
8388 declare
8389 Loc : constant Source_Ptr := Sloc (N);
8390 Decls : constant List_Id := Declarations (N);
8391 Chk : Node_Id;
8393 begin
8394 -- No need to generate this check if first entry in the
8395 -- declaration list is a raise of Program_Error now.
8397 if Present (Decls)
8398 and then Nkind (First (Decls)) = N_Raise_Program_Error
8399 then
8400 return;
8401 end if;
8403 -- Otherwise generate the check
8405 Chk :=
8406 Make_Raise_Program_Error (Loc,
8407 Condition =>
8408 Make_Op_Eq (Loc,
8409 Left_Opnd => New_Occurrence_Of (Ent, Loc),
8410 Right_Opnd => Make_Integer_Literal (Loc, Uint_0)),
8411 Reason => PE_Access_Before_Elaboration);
8413 if No (Decls) then
8414 Set_Declarations (N, New_List (Chk));
8415 else
8416 Prepend (Chk, Decls);
8417 end if;
8419 Analyze (Chk);
8420 end;
8421 end if;
8422 end if;
8423 end if;
8424 end Set_Elaboration_Flag;
8426 ----------------------------
8427 -- Set_Renamed_Subprogram --
8428 ----------------------------
8430 procedure Set_Renamed_Subprogram (N : Node_Id; E : Entity_Id) is
8431 begin
8432 -- If input node is an identifier, we can just reset it
8434 if Nkind (N) = N_Identifier then
8435 Set_Chars (N, Chars (E));
8436 Set_Entity (N, E);
8438 -- Otherwise we have to do a rewrite, preserving Comes_From_Source
8440 else
8441 declare
8442 CS : constant Boolean := Comes_From_Source (N);
8443 begin
8444 Rewrite (N, Make_Identifier (Sloc (N), Chars (E)));
8445 Set_Entity (N, E);
8446 Set_Comes_From_Source (N, CS);
8447 Set_Analyzed (N, True);
8448 end;
8449 end if;
8450 end Set_Renamed_Subprogram;
8452 ----------------------
8453 -- Side_Effect_Free --
8454 ----------------------
8456 function Side_Effect_Free
8457 (N : Node_Id;
8458 Name_Req : Boolean := False;
8459 Variable_Ref : Boolean := False) return Boolean
8461 Typ : constant Entity_Id := Etype (N);
8462 -- Result type of the expression
8464 function Safe_Prefixed_Reference (N : Node_Id) return Boolean;
8465 -- The argument N is a construct where the Prefix is dereferenced if it
8466 -- is an access type and the result is a variable. The call returns True
8467 -- if the construct is side effect free (not considering side effects in
8468 -- other than the prefix which are to be tested by the caller).
8470 function Within_In_Parameter (N : Node_Id) return Boolean;
8471 -- Determines if N is a subcomponent of a composite in-parameter. If so,
8472 -- N is not side-effect free when the actual is global and modifiable
8473 -- indirectly from within a subprogram, because it may be passed by
8474 -- reference. The front-end must be conservative here and assume that
8475 -- this may happen with any array or record type. On the other hand, we
8476 -- cannot create temporaries for all expressions for which this
8477 -- condition is true, for various reasons that might require clearing up
8478 -- ??? For example, discriminant references that appear out of place, or
8479 -- spurious type errors with class-wide expressions. As a result, we
8480 -- limit the transformation to loop bounds, which is so far the only
8481 -- case that requires it.
8483 -----------------------------
8484 -- Safe_Prefixed_Reference --
8485 -----------------------------
8487 function Safe_Prefixed_Reference (N : Node_Id) return Boolean is
8488 begin
8489 -- If prefix is not side effect free, definitely not safe
8491 if not Side_Effect_Free (Prefix (N), Name_Req, Variable_Ref) then
8492 return False;
8494 -- If the prefix is of an access type that is not access-to-constant,
8495 -- then this construct is a variable reference, which means it is to
8496 -- be considered to have side effects if Variable_Ref is set True.
8498 elsif Is_Access_Type (Etype (Prefix (N)))
8499 and then not Is_Access_Constant (Etype (Prefix (N)))
8500 and then Variable_Ref
8501 then
8502 -- Exception is a prefix that is the result of a previous removal
8503 -- of side-effects.
8505 return Is_Entity_Name (Prefix (N))
8506 and then not Comes_From_Source (Prefix (N))
8507 and then Ekind (Entity (Prefix (N))) = E_Constant
8508 and then Is_Internal_Name (Chars (Entity (Prefix (N))));
8510 -- If the prefix is an explicit dereference then this construct is a
8511 -- variable reference, which means it is to be considered to have
8512 -- side effects if Variable_Ref is True.
8514 -- We do NOT exclude dereferences of access-to-constant types because
8515 -- we handle them as constant view of variables.
8517 elsif Nkind (Prefix (N)) = N_Explicit_Dereference
8518 and then Variable_Ref
8519 then
8520 return False;
8522 -- Note: The following test is the simplest way of solving a complex
8523 -- problem uncovered by the following test (Side effect on loop bound
8524 -- that is a subcomponent of a global variable:
8526 -- with Text_Io; use Text_Io;
8527 -- procedure Tloop is
8528 -- type X is
8529 -- record
8530 -- V : Natural := 4;
8531 -- S : String (1..5) := (others => 'a');
8532 -- end record;
8533 -- X1 : X;
8535 -- procedure Modi;
8537 -- generic
8538 -- with procedure Action;
8539 -- procedure Loop_G (Arg : X; Msg : String)
8541 -- procedure Loop_G (Arg : X; Msg : String) is
8542 -- begin
8543 -- Put_Line ("begin loop_g " & Msg & " will loop till: "
8544 -- & Natural'Image (Arg.V));
8545 -- for Index in 1 .. Arg.V loop
8546 -- Text_Io.Put_Line
8547 -- (Natural'Image (Index) & " " & Arg.S (Index));
8548 -- if Index > 2 then
8549 -- Modi;
8550 -- end if;
8551 -- end loop;
8552 -- Put_Line ("end loop_g " & Msg);
8553 -- end;
8555 -- procedure Loop1 is new Loop_G (Modi);
8556 -- procedure Modi is
8557 -- begin
8558 -- X1.V := 1;
8559 -- Loop1 (X1, "from modi");
8560 -- end;
8562 -- begin
8563 -- Loop1 (X1, "initial");
8564 -- end;
8566 -- The output of the above program should be:
8568 -- begin loop_g initial will loop till: 4
8569 -- 1 a
8570 -- 2 a
8571 -- 3 a
8572 -- begin loop_g from modi will loop till: 1
8573 -- 1 a
8574 -- end loop_g from modi
8575 -- 4 a
8576 -- begin loop_g from modi will loop till: 1
8577 -- 1 a
8578 -- end loop_g from modi
8579 -- end loop_g initial
8581 -- If a loop bound is a subcomponent of a global variable, a
8582 -- modification of that variable within the loop may incorrectly
8583 -- affect the execution of the loop.
8585 elsif Nkind (Parent (Parent (N))) = N_Loop_Parameter_Specification
8586 and then Within_In_Parameter (Prefix (N))
8587 and then Variable_Ref
8588 then
8589 return False;
8591 -- All other cases are side effect free
8593 else
8594 return True;
8595 end if;
8596 end Safe_Prefixed_Reference;
8598 -------------------------
8599 -- Within_In_Parameter --
8600 -------------------------
8602 function Within_In_Parameter (N : Node_Id) return Boolean is
8603 begin
8604 if not Comes_From_Source (N) then
8605 return False;
8607 elsif Is_Entity_Name (N) then
8608 return Ekind (Entity (N)) = E_In_Parameter;
8610 elsif Nkind_In (N, N_Indexed_Component, N_Selected_Component) then
8611 return Within_In_Parameter (Prefix (N));
8613 else
8614 return False;
8615 end if;
8616 end Within_In_Parameter;
8618 -- Start of processing for Side_Effect_Free
8620 begin
8621 -- If volatile reference, always consider it to have side effects
8623 if Is_Volatile_Reference (N) then
8624 return False;
8625 end if;
8627 -- Note on checks that could raise Constraint_Error. Strictly, if we
8628 -- take advantage of 11.6, these checks do not count as side effects.
8629 -- However, we would prefer to consider that they are side effects,
8630 -- since the backend CSE does not work very well on expressions which
8631 -- can raise Constraint_Error. On the other hand if we don't consider
8632 -- them to be side effect free, then we get some awkward expansions
8633 -- in -gnato mode, resulting in code insertions at a point where we
8634 -- do not have a clear model for performing the insertions.
8636 -- Special handling for entity names
8638 if Is_Entity_Name (N) then
8640 -- A type reference is always side effect free
8642 if Is_Type (Entity (N)) then
8643 return True;
8645 -- Variables are considered to be a side effect if Variable_Ref
8646 -- is set or if we have a volatile reference and Name_Req is off.
8647 -- If Name_Req is True then we can't help returning a name which
8648 -- effectively allows multiple references in any case.
8650 elsif Is_Variable (N, Use_Original_Node => False) then
8651 return not Variable_Ref
8652 and then (not Is_Volatile_Reference (N) or else Name_Req);
8654 -- Any other entity (e.g. a subtype name) is definitely side
8655 -- effect free.
8657 else
8658 return True;
8659 end if;
8661 -- A value known at compile time is always side effect free
8663 elsif Compile_Time_Known_Value (N) then
8664 return True;
8666 -- A variable renaming is not side-effect free, because the renaming
8667 -- will function like a macro in the front-end in some cases, and an
8668 -- assignment can modify the component designated by N, so we need to
8669 -- create a temporary for it.
8671 -- The guard testing for Entity being present is needed at least in
8672 -- the case of rewritten predicate expressions, and may well also be
8673 -- appropriate elsewhere. Obviously we can't go testing the entity
8674 -- field if it does not exist, so it's reasonable to say that this is
8675 -- not the renaming case if it does not exist.
8677 elsif Is_Entity_Name (Original_Node (N))
8678 and then Present (Entity (Original_Node (N)))
8679 and then Is_Renaming_Of_Object (Entity (Original_Node (N)))
8680 and then Ekind (Entity (Original_Node (N))) /= E_Constant
8681 then
8682 declare
8683 RO : constant Node_Id :=
8684 Renamed_Object (Entity (Original_Node (N)));
8686 begin
8687 -- If the renamed object is an indexed component, or an
8688 -- explicit dereference, then the designated object could
8689 -- be modified by an assignment.
8691 if Nkind_In (RO, N_Indexed_Component,
8692 N_Explicit_Dereference)
8693 then
8694 return False;
8696 -- A selected component must have a safe prefix
8698 elsif Nkind (RO) = N_Selected_Component then
8699 return Safe_Prefixed_Reference (RO);
8701 -- In all other cases, designated object cannot be changed so
8702 -- we are side effect free.
8704 else
8705 return True;
8706 end if;
8707 end;
8709 -- Remove_Side_Effects generates an object renaming declaration to
8710 -- capture the expression of a class-wide expression. In VM targets
8711 -- the frontend performs no expansion for dispatching calls to
8712 -- class- wide types since they are handled by the VM. Hence, we must
8713 -- locate here if this node corresponds to a previous invocation of
8714 -- Remove_Side_Effects to avoid a never ending loop in the frontend.
8716 elsif VM_Target /= No_VM
8717 and then not Comes_From_Source (N)
8718 and then Nkind (Parent (N)) = N_Object_Renaming_Declaration
8719 and then Is_Class_Wide_Type (Typ)
8720 then
8721 return True;
8722 end if;
8724 -- For other than entity names and compile time known values,
8725 -- check the node kind for special processing.
8727 case Nkind (N) is
8729 -- An attribute reference is side effect free if its expressions
8730 -- are side effect free and its prefix is side effect free or
8731 -- is an entity reference.
8733 -- Is this right? what about x'first where x is a variable???
8735 when N_Attribute_Reference =>
8736 return Side_Effect_Free (Expressions (N), Name_Req, Variable_Ref)
8737 and then Attribute_Name (N) /= Name_Input
8738 and then (Is_Entity_Name (Prefix (N))
8739 or else Side_Effect_Free
8740 (Prefix (N), Name_Req, Variable_Ref));
8742 -- A binary operator is side effect free if and both operands are
8743 -- side effect free. For this purpose binary operators include
8744 -- membership tests and short circuit forms.
8746 when N_Binary_Op | N_Membership_Test | N_Short_Circuit =>
8747 return Side_Effect_Free (Left_Opnd (N), Name_Req, Variable_Ref)
8748 and then
8749 Side_Effect_Free (Right_Opnd (N), Name_Req, Variable_Ref);
8751 -- An explicit dereference is side effect free only if it is
8752 -- a side effect free prefixed reference.
8754 when N_Explicit_Dereference =>
8755 return Safe_Prefixed_Reference (N);
8757 -- An expression with action is side effect free if its expression
8758 -- is side effect free and it has no actions.
8760 when N_Expression_With_Actions =>
8761 return Is_Empty_List (Actions (N))
8762 and then
8763 Side_Effect_Free (Expression (N), Name_Req, Variable_Ref);
8765 -- A call to _rep_to_pos is side effect free, since we generate
8766 -- this pure function call ourselves. Moreover it is critically
8767 -- important to make this exception, since otherwise we can have
8768 -- discriminants in array components which don't look side effect
8769 -- free in the case of an array whose index type is an enumeration
8770 -- type with an enumeration rep clause.
8772 -- All other function calls are not side effect free
8774 when N_Function_Call =>
8775 return Nkind (Name (N)) = N_Identifier
8776 and then Is_TSS (Name (N), TSS_Rep_To_Pos)
8777 and then
8778 Side_Effect_Free
8779 (First (Parameter_Associations (N)), Name_Req, Variable_Ref);
8781 -- An IF expression is side effect free if it's of a scalar type, and
8782 -- all its components are all side effect free (conditions and then
8783 -- actions and else actions). We restrict to scalar types, since it
8784 -- is annoying to deal with things like (if A then B else C)'First
8785 -- where the type involved is a string type.
8787 when N_If_Expression =>
8788 return Is_Scalar_Type (Typ)
8789 and then
8790 Side_Effect_Free (Expressions (N), Name_Req, Variable_Ref);
8792 -- An indexed component is side effect free if it is a side
8793 -- effect free prefixed reference and all the indexing
8794 -- expressions are side effect free.
8796 when N_Indexed_Component =>
8797 return Side_Effect_Free (Expressions (N), Name_Req, Variable_Ref)
8798 and then Safe_Prefixed_Reference (N);
8800 -- A type qualification is side effect free if the expression
8801 -- is side effect free.
8803 when N_Qualified_Expression =>
8804 return Side_Effect_Free (Expression (N), Name_Req, Variable_Ref);
8806 -- A selected component is side effect free only if it is a side
8807 -- effect free prefixed reference. If it designates a component
8808 -- with a rep. clause it must be treated has having a potential
8809 -- side effect, because it may be modified through a renaming, and
8810 -- a subsequent use of the renaming as a macro will yield the
8811 -- wrong value. This complex interaction between renaming and
8812 -- removing side effects is a reminder that the latter has become
8813 -- a headache to maintain, and that it should be removed in favor
8814 -- of the gcc mechanism to capture values ???
8816 when N_Selected_Component =>
8817 if Nkind (Parent (N)) = N_Explicit_Dereference
8818 and then Has_Non_Standard_Rep (Designated_Type (Typ))
8819 then
8820 return False;
8821 else
8822 return Safe_Prefixed_Reference (N);
8823 end if;
8825 -- A range is side effect free if the bounds are side effect free
8827 when N_Range =>
8828 return Side_Effect_Free (Low_Bound (N), Name_Req, Variable_Ref)
8829 and then
8830 Side_Effect_Free (High_Bound (N), Name_Req, Variable_Ref);
8832 -- A slice is side effect free if it is a side effect free
8833 -- prefixed reference and the bounds are side effect free.
8835 when N_Slice =>
8836 return Side_Effect_Free
8837 (Discrete_Range (N), Name_Req, Variable_Ref)
8838 and then Safe_Prefixed_Reference (N);
8840 -- A type conversion is side effect free if the expression to be
8841 -- converted is side effect free.
8843 when N_Type_Conversion =>
8844 return Side_Effect_Free (Expression (N), Name_Req, Variable_Ref);
8846 -- A unary operator is side effect free if the operand
8847 -- is side effect free.
8849 when N_Unary_Op =>
8850 return Side_Effect_Free (Right_Opnd (N), Name_Req, Variable_Ref);
8852 -- An unchecked type conversion is side effect free only if it
8853 -- is safe and its argument is side effect free.
8855 when N_Unchecked_Type_Conversion =>
8856 return Safe_Unchecked_Type_Conversion (N)
8857 and then
8858 Side_Effect_Free (Expression (N), Name_Req, Variable_Ref);
8860 -- An unchecked expression is side effect free if its expression
8861 -- is side effect free.
8863 when N_Unchecked_Expression =>
8864 return Side_Effect_Free (Expression (N), Name_Req, Variable_Ref);
8866 -- A literal is side effect free
8868 when N_Character_Literal |
8869 N_Integer_Literal |
8870 N_Real_Literal |
8871 N_String_Literal =>
8872 return True;
8874 -- We consider that anything else has side effects. This is a bit
8875 -- crude, but we are pretty close for most common cases, and we
8876 -- are certainly correct (i.e. we never return True when the
8877 -- answer should be False).
8879 when others =>
8880 return False;
8881 end case;
8882 end Side_Effect_Free;
8884 -- A list is side effect free if all elements of the list are side
8885 -- effect free.
8887 function Side_Effect_Free
8888 (L : List_Id;
8889 Name_Req : Boolean := False;
8890 Variable_Ref : Boolean := False) return Boolean
8892 N : Node_Id;
8894 begin
8895 if L = No_List or else L = Error_List then
8896 return True;
8898 else
8899 N := First (L);
8900 while Present (N) loop
8901 if not Side_Effect_Free (N, Name_Req, Variable_Ref) then
8902 return False;
8903 else
8904 Next (N);
8905 end if;
8906 end loop;
8908 return True;
8909 end if;
8910 end Side_Effect_Free;
8912 ----------------------------------
8913 -- Silly_Boolean_Array_Not_Test --
8914 ----------------------------------
8916 -- This procedure implements an odd and silly test. We explicitly check
8917 -- for the case where the 'First of the component type is equal to the
8918 -- 'Last of this component type, and if this is the case, we make sure
8919 -- that constraint error is raised. The reason is that the NOT is bound
8920 -- to cause CE in this case, and we will not otherwise catch it.
8922 -- No such check is required for AND and OR, since for both these cases
8923 -- False op False = False, and True op True = True. For the XOR case,
8924 -- see Silly_Boolean_Array_Xor_Test.
8926 -- Believe it or not, this was reported as a bug. Note that nearly always,
8927 -- the test will evaluate statically to False, so the code will be
8928 -- statically removed, and no extra overhead caused.
8930 procedure Silly_Boolean_Array_Not_Test (N : Node_Id; T : Entity_Id) is
8931 Loc : constant Source_Ptr := Sloc (N);
8932 CT : constant Entity_Id := Component_Type (T);
8934 begin
8935 -- The check we install is
8937 -- constraint_error when
8938 -- component_type'first = component_type'last
8939 -- and then array_type'Length /= 0)
8941 -- We need the last guard because we don't want to raise CE for empty
8942 -- arrays since no out of range values result. (Empty arrays with a
8943 -- component type of True .. True -- very useful -- even the ACATS
8944 -- does not test that marginal case).
8946 Insert_Action (N,
8947 Make_Raise_Constraint_Error (Loc,
8948 Condition =>
8949 Make_And_Then (Loc,
8950 Left_Opnd =>
8951 Make_Op_Eq (Loc,
8952 Left_Opnd =>
8953 Make_Attribute_Reference (Loc,
8954 Prefix => New_Occurrence_Of (CT, Loc),
8955 Attribute_Name => Name_First),
8957 Right_Opnd =>
8958 Make_Attribute_Reference (Loc,
8959 Prefix => New_Occurrence_Of (CT, Loc),
8960 Attribute_Name => Name_Last)),
8962 Right_Opnd => Make_Non_Empty_Check (Loc, Right_Opnd (N))),
8963 Reason => CE_Range_Check_Failed));
8964 end Silly_Boolean_Array_Not_Test;
8966 ----------------------------------
8967 -- Silly_Boolean_Array_Xor_Test --
8968 ----------------------------------
8970 -- This procedure implements an odd and silly test. We explicitly check
8971 -- for the XOR case where the component type is True .. True, since this
8972 -- will raise constraint error. A special check is required since CE
8973 -- will not be generated otherwise (cf Expand_Packed_Not).
8975 -- No such check is required for AND and OR, since for both these cases
8976 -- False op False = False, and True op True = True, and no check is
8977 -- required for the case of False .. False, since False xor False = False.
8978 -- See also Silly_Boolean_Array_Not_Test
8980 procedure Silly_Boolean_Array_Xor_Test (N : Node_Id; T : Entity_Id) is
8981 Loc : constant Source_Ptr := Sloc (N);
8982 CT : constant Entity_Id := Component_Type (T);
8984 begin
8985 -- The check we install is
8987 -- constraint_error when
8988 -- Boolean (component_type'First)
8989 -- and then Boolean (component_type'Last)
8990 -- and then array_type'Length /= 0)
8992 -- We need the last guard because we don't want to raise CE for empty
8993 -- arrays since no out of range values result (Empty arrays with a
8994 -- component type of True .. True -- very useful -- even the ACATS
8995 -- does not test that marginal case).
8997 Insert_Action (N,
8998 Make_Raise_Constraint_Error (Loc,
8999 Condition =>
9000 Make_And_Then (Loc,
9001 Left_Opnd =>
9002 Make_And_Then (Loc,
9003 Left_Opnd =>
9004 Convert_To (Standard_Boolean,
9005 Make_Attribute_Reference (Loc,
9006 Prefix => New_Occurrence_Of (CT, Loc),
9007 Attribute_Name => Name_First)),
9009 Right_Opnd =>
9010 Convert_To (Standard_Boolean,
9011 Make_Attribute_Reference (Loc,
9012 Prefix => New_Occurrence_Of (CT, Loc),
9013 Attribute_Name => Name_Last))),
9015 Right_Opnd => Make_Non_Empty_Check (Loc, Right_Opnd (N))),
9016 Reason => CE_Range_Check_Failed));
9017 end Silly_Boolean_Array_Xor_Test;
9019 --------------------------
9020 -- Target_Has_Fixed_Ops --
9021 --------------------------
9023 Integer_Sized_Small : Ureal;
9024 -- Set to 2.0 ** -(Integer'Size - 1) the first time that this function is
9025 -- called (we don't want to compute it more than once).
9027 Long_Integer_Sized_Small : Ureal;
9028 -- Set to 2.0 ** -(Long_Integer'Size - 1) the first time that this function
9029 -- is called (we don't want to compute it more than once)
9031 First_Time_For_THFO : Boolean := True;
9032 -- Set to False after first call (if Fractional_Fixed_Ops_On_Target)
9034 function Target_Has_Fixed_Ops
9035 (Left_Typ : Entity_Id;
9036 Right_Typ : Entity_Id;
9037 Result_Typ : Entity_Id) return Boolean
9039 function Is_Fractional_Type (Typ : Entity_Id) return Boolean;
9040 -- Return True if the given type is a fixed-point type with a small
9041 -- value equal to 2 ** (-(T'Object_Size - 1)) and whose values have
9042 -- an absolute value less than 1.0. This is currently limited to
9043 -- fixed-point types that map to Integer or Long_Integer.
9045 ------------------------
9046 -- Is_Fractional_Type --
9047 ------------------------
9049 function Is_Fractional_Type (Typ : Entity_Id) return Boolean is
9050 begin
9051 if Esize (Typ) = Standard_Integer_Size then
9052 return Small_Value (Typ) = Integer_Sized_Small;
9054 elsif Esize (Typ) = Standard_Long_Integer_Size then
9055 return Small_Value (Typ) = Long_Integer_Sized_Small;
9057 else
9058 return False;
9059 end if;
9060 end Is_Fractional_Type;
9062 -- Start of processing for Target_Has_Fixed_Ops
9064 begin
9065 -- Return False if Fractional_Fixed_Ops_On_Target is false
9067 if not Fractional_Fixed_Ops_On_Target then
9068 return False;
9069 end if;
9071 -- Here the target has Fractional_Fixed_Ops, if first time, compute
9072 -- standard constants used by Is_Fractional_Type.
9074 if First_Time_For_THFO then
9075 First_Time_For_THFO := False;
9077 Integer_Sized_Small :=
9078 UR_From_Components
9079 (Num => Uint_1,
9080 Den => UI_From_Int (Standard_Integer_Size - 1),
9081 Rbase => 2);
9083 Long_Integer_Sized_Small :=
9084 UR_From_Components
9085 (Num => Uint_1,
9086 Den => UI_From_Int (Standard_Long_Integer_Size - 1),
9087 Rbase => 2);
9088 end if;
9090 -- Return True if target supports fixed-by-fixed multiply/divide for
9091 -- fractional fixed-point types (see Is_Fractional_Type) and the operand
9092 -- and result types are equivalent fractional types.
9094 return Is_Fractional_Type (Base_Type (Left_Typ))
9095 and then Is_Fractional_Type (Base_Type (Right_Typ))
9096 and then Is_Fractional_Type (Base_Type (Result_Typ))
9097 and then Esize (Left_Typ) = Esize (Right_Typ)
9098 and then Esize (Left_Typ) = Esize (Result_Typ);
9099 end Target_Has_Fixed_Ops;
9101 ------------------------------------------
9102 -- Type_May_Have_Bit_Aligned_Components --
9103 ------------------------------------------
9105 function Type_May_Have_Bit_Aligned_Components
9106 (Typ : Entity_Id) return Boolean
9108 begin
9109 -- Array type, check component type
9111 if Is_Array_Type (Typ) then
9112 return
9113 Type_May_Have_Bit_Aligned_Components (Component_Type (Typ));
9115 -- Record type, check components
9117 elsif Is_Record_Type (Typ) then
9118 declare
9119 E : Entity_Id;
9121 begin
9122 E := First_Component_Or_Discriminant (Typ);
9123 while Present (E) loop
9124 if Component_May_Be_Bit_Aligned (E)
9125 or else Type_May_Have_Bit_Aligned_Components (Etype (E))
9126 then
9127 return True;
9128 end if;
9130 Next_Component_Or_Discriminant (E);
9131 end loop;
9133 return False;
9134 end;
9136 -- Type other than array or record is always OK
9138 else
9139 return False;
9140 end if;
9141 end Type_May_Have_Bit_Aligned_Components;
9143 ----------------------------------
9144 -- Within_Case_Or_If_Expression --
9145 ----------------------------------
9147 function Within_Case_Or_If_Expression (N : Node_Id) return Boolean is
9148 Par : Node_Id;
9150 begin
9151 -- Locate an enclosing case or if expression. Note that these constructs
9152 -- can be expanded into Expression_With_Actions, hence the test of the
9153 -- original node.
9155 Par := Parent (N);
9156 while Present (Par) loop
9157 if Nkind_In (Original_Node (Par), N_Case_Expression,
9158 N_If_Expression)
9159 then
9160 return True;
9162 -- Prevent the search from going too far
9164 elsif Is_Body_Or_Package_Declaration (Par) then
9165 return False;
9166 end if;
9168 Par := Parent (Par);
9169 end loop;
9171 return False;
9172 end Within_Case_Or_If_Expression;
9174 --------------------------------
9175 -- Within_Internal_Subprogram --
9176 --------------------------------
9178 function Within_Internal_Subprogram return Boolean is
9179 S : Entity_Id;
9181 begin
9182 S := Current_Scope;
9183 while Present (S) and then not Is_Subprogram (S) loop
9184 S := Scope (S);
9185 end loop;
9187 return Present (S)
9188 and then Get_TSS_Name (S) /= TSS_Null
9189 and then not Is_Predicate_Function (S);
9190 end Within_Internal_Subprogram;
9192 ----------------------------
9193 -- Wrap_Cleanup_Procedure --
9194 ----------------------------
9196 procedure Wrap_Cleanup_Procedure (N : Node_Id) is
9197 Loc : constant Source_Ptr := Sloc (N);
9198 Stseq : constant Node_Id := Handled_Statement_Sequence (N);
9199 Stmts : constant List_Id := Statements (Stseq);
9200 begin
9201 if Abort_Allowed then
9202 Prepend_To (Stmts, Build_Runtime_Call (Loc, RE_Abort_Defer));
9203 Append_To (Stmts, Build_Runtime_Call (Loc, RE_Abort_Undefer));
9204 end if;
9205 end Wrap_Cleanup_Procedure;
9207 end Exp_Util;