1 ------------------------------------------------------------------------------
3 -- GNAT COMPILER COMPONENTS --
9 -- Copyright (C) 1992-2004 Free Software Foundation, Inc. --
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 2, 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 COPYING. If not, write --
19 -- to the Free Software Foundation, 59 Temple Place - Suite 330, Boston, --
20 -- MA 02111-1307, USA. --
22 -- GNAT was originally developed by the GNAT team at New York University. --
23 -- Extensive contributions were provided by Ada Core Technologies Inc. --
25 ------------------------------------------------------------------------------
27 with Atree
; use Atree
;
28 with Debug
; use Debug
;
29 with Einfo
; use Einfo
;
30 with Elists
; use Elists
;
31 with Errout
; use Errout
;
32 with Exp_Smem
; use Exp_Smem
;
33 with Exp_Tss
; use Exp_Tss
;
34 with Exp_Util
; use Exp_Util
;
35 with Exp_VFpt
; use Exp_VFpt
;
36 with Nmake
; use Nmake
;
39 with Sem_Eval
; use Sem_Eval
;
40 with Sem_Res
; use Sem_Res
;
41 with Sem_Util
; use Sem_Util
;
42 with Sem_Warn
; use Sem_Warn
;
43 with Sinfo
; use Sinfo
;
44 with Snames
; use Snames
;
45 with Stand
; use Stand
;
46 with Tbuild
; use Tbuild
;
47 with Uintp
; use Uintp
;
49 package body Exp_Ch2
is
51 -----------------------
52 -- Local Subprograms --
53 -----------------------
55 procedure Expand_Current_Value
(N
: Node_Id
);
56 -- Given a node N for a variable whose Current_Value field is set.
57 -- If the node is for a discrete type, replaces the node with a
58 -- copy of the referenced value. This provides a limited form of
59 -- value propagation for variables which are initialized or assigned
60 -- not been further modified at the time of reference. The call has
61 -- no effect if the Current_Value refers to a conditional with a
62 -- condition other than equality.
64 procedure Expand_Discriminant
(N
: Node_Id
);
65 -- An occurrence of a discriminant within a discriminated type is replaced
66 -- with the corresponding discriminal, that is to say the formal parameter
67 -- of the initialization procedure for the type that is associated with
68 -- that particular discriminant. This replacement is not performed for
69 -- discriminants of records that appear in constraints of component of the
70 -- record, because Gigi uses the discriminant name to retrieve its value.
71 -- In the other hand, it has to be performed for default expressions of
72 -- components because they are used in the record init procedure. See
73 -- Einfo for more details, and Exp_Ch3, Exp_Ch9 for examples of use.
74 -- For discriminants of tasks and protected types, the transformation is
75 -- more complex when it occurs within a default expression for an entry
76 -- or protected operation. The corresponding default_expression_function
77 -- has an additional parameter which is the target of an entry call, and
78 -- the discriminant of the task must be replaced with a reference to the
79 -- discriminant of that formal parameter.
81 procedure Expand_Entity_Reference
(N
: Node_Id
);
82 -- Common processing for expansion of identifiers and expanded names
84 procedure Expand_Entry_Index_Parameter
(N
: Node_Id
);
85 -- A reference to the identifier in the entry index specification
86 -- of a protected entry body is modified to a reference to a constant
87 -- definintion equal to the index of the entry family member being
88 -- called. This constant is calculated as part of the elaboration
89 -- of the expanded code for the body, and is calculated from the
90 -- object-wide entry index returned by Next_Entry_Call.
92 procedure Expand_Entry_Parameter
(N
: Node_Id
);
93 -- A reference to an entry parameter is modified to be a reference to
94 -- the corresponding component of the entry parameter record that is
95 -- passed by the runtime to the accept body procedure
97 procedure Expand_Formal
(N
: Node_Id
);
98 -- A reference to a formal parameter of a protected subprogram is
99 -- expanded to the corresponding formal of the unprotected procedure
100 -- used to represent the protected subprogram within the protected object.
102 procedure Expand_Protected_Private
(N
: Node_Id
);
103 -- A reference to a private object of a protected type is expanded
104 -- to a component selected from the record used to implement
105 -- the protected object. Such a record is passed to all operations
106 -- on a protected object in a parameter named _object. Such an object
107 -- is a constant within a function, and a variable otherwise.
109 procedure Expand_Renaming
(N
: Node_Id
);
110 -- For renamings, just replace the identifier by the corresponding
111 -- name expression. Note that this has been evaluated (see routine
112 -- Exp_Ch8.Expand_N_Object_Renaming.Evaluate_Name) so this gives
113 -- the correct renaming semantics.
115 --------------------------
116 -- Expand_Current_Value --
117 --------------------------
119 procedure Expand_Current_Value
(N
: Node_Id
) is
120 Loc
: constant Source_Ptr
:= Sloc
(N
);
121 E
: constant Entity_Id
:= Entity
(N
);
122 CV
: constant Node_Id
:= Current_Value
(E
);
123 T
: constant Entity_Id
:= Etype
(N
);
127 function In_Appropriate_Scope
return Boolean;
128 -- Returns true if the current scope is the scope of E, or is a nested
129 -- (to any level) package declaration, package body, or block of this
130 -- scope. The idea is that such references are in the sequential
131 -- execution sequence of statements executed after E is elaborated.
133 --------------------------
134 -- In_Appropriate_Scope --
135 --------------------------
137 function In_Appropriate_Scope
return Boolean is
138 ES
: constant Entity_Id
:= Scope
(E
);
145 -- If we are in right scope, replacement is safe
150 -- Packages do not affect the determination of safety
152 elsif Ekind
(CS
) = E_Package
then
154 exit when CS
= Standard_Standard
;
156 -- Blocks do not affect the determination of safety
158 elsif Ekind
(CS
) = E_Block
then
161 -- Otherwise, the reference is dubious, and we cannot be
162 -- sure that it is safe to do the replacement.
170 end In_Appropriate_Scope
;
172 -- Start of processing for Expand_Current_Value
177 -- No replacement if value raises constraint error
179 and then Nkind
(CV
) /= N_Raise_Constraint_Error
181 -- Do this only for discrete types
183 and then Is_Discrete_Type
(T
)
185 -- Do not replace biased types, since it is problematic to
186 -- consistently generate a sensible constant value in this case.
188 and then not Has_Biased_Representation
(T
)
190 -- Do not replace lvalues
192 and then not Is_Lvalue
(N
)
194 -- Do not replace occurrences that are not in the current scope,
195 -- because in a nested subprogram we know absolutely nothing about
196 -- the sequence of execution.
198 and then In_Appropriate_Scope
200 -- Do not replace statically allocated objects, because they may
201 -- be modified outside the current scope.
203 and then not Is_Statically_Allocated
(E
)
205 -- Do not replace aliased or volatile objects, since we don't know
206 -- what else might change the value
208 and then not Is_Aliased
(E
) and then not Treat_As_Volatile
(E
)
210 -- Debug flag -gnatdM disconnects this optimization
212 and then not Debug_Flag_MM
214 -- Do not replace occurrences in pragmas (where names typically
215 -- appear not as values, but as simply names. If there are cases
216 -- where values are required, it is only a very minor efficiency
217 -- issue that they do not get replaced when they could be).
219 and then Nkind
(Parent
(N
)) /= N_Pragma_Argument_Association
221 -- Same for Asm_Input and Asm_Output attribute references
223 and then not (Nkind
(Parent
(N
)) = N_Attribute_Reference
225 (Attribute_Name
(Parent
(N
)) = Name_Asm_Input
227 Attribute_Name
(Parent
(N
)) = Name_Asm_Output
))
229 -- Case of Current_Value is a compile time known value
231 if Nkind
(CV
) in N_Subexpr
then
234 -- Case of Current_Value is a conditional expression reference
237 Get_Current_Value_Condition
(N
, Op
, Val
);
239 if Op
/= N_Op_Eq
then
244 -- If constant value is an occurrence of an enumeration literal,
245 -- then we just make another occurence of the same literal.
247 if Is_Entity_Name
(Val
)
248 and then Ekind
(Entity
(Val
)) = E_Enumeration_Literal
251 Unchecked_Convert_To
(T
,
252 New_Occurrence_Of
(Entity
(Val
), Loc
)));
254 -- Otherwise get the value, and convert to appropriate type
258 Unchecked_Convert_To
(T
,
259 Make_Integer_Literal
(Loc
,
260 Intval
=> Expr_Rep_Value
(Val
))));
263 Analyze_And_Resolve
(N
, T
);
264 Set_Is_Static_Expression
(N
, False);
266 end Expand_Current_Value
;
268 -------------------------
269 -- Expand_Discriminant --
270 -------------------------
272 procedure Expand_Discriminant
(N
: Node_Id
) is
273 Scop
: constant Entity_Id
:= Scope
(Entity
(N
));
275 Parent_P
: Node_Id
:= Parent
(P
);
276 In_Entry
: Boolean := False;
279 -- The Incomplete_Or_Private_Kind happens while resolving the
280 -- discriminant constraint involved in a derived full type,
283 -- type D is private;
284 -- type D(C : ...) is new T(C);
286 if Ekind
(Scop
) = E_Record_Type
287 or Ekind
(Scop
) in Incomplete_Or_Private_Kind
289 -- Find the origin by walking up the tree till the component
292 while Present
(Parent_P
)
293 and then Nkind
(Parent_P
) /= N_Component_Declaration
296 Parent_P
:= Parent
(P
);
299 -- If the discriminant reference was part of the default expression
300 -- it has to be "discriminalized"
302 if Present
(Parent_P
) and then P
= Expression
(Parent_P
) then
303 Set_Entity
(N
, Discriminal
(Entity
(N
)));
306 elsif Is_Concurrent_Type
(Scop
) then
307 while Present
(Parent_P
)
308 and then Nkind
(Parent_P
) /= N_Subprogram_Body
312 if Nkind
(P
) = N_Entry_Declaration
then
316 Parent_P
:= Parent
(Parent_P
);
319 -- If the discriminant occurs within the default expression for
320 -- a formal of an entry or protected operation, create a default
321 -- function for it, and replace the discriminant with a reference
322 -- to the discriminant of the formal of the default function.
323 -- The discriminant entity is the one defined in the corresponding
326 if Present
(Parent_P
)
327 and then Present
(Corresponding_Spec
(Parent_P
))
330 Loc
: constant Source_Ptr
:= Sloc
(N
);
331 D_Fun
: constant Entity_Id
:= Corresponding_Spec
(Parent_P
);
332 Formal
: constant Entity_Id
:= First_Formal
(D_Fun
);
337 -- Verify that we are within a default function: the type of
338 -- its formal parameter is the same task or protected type.
341 and then Etype
(Formal
) = Scope
(Entity
(N
))
343 Disc
:= CR_Discriminant
(Entity
(N
));
346 Make_Selected_Component
(Loc
,
347 Prefix
=> New_Occurrence_Of
(Formal
, Loc
),
348 Selector_Name
=> New_Occurrence_Of
(Disc
, Loc
));
350 Set_Etype
(New_N
, Etype
(N
));
354 Set_Entity
(N
, Discriminal
(Entity
(N
)));
358 elsif Nkind
(Parent
(N
)) = N_Range
361 Set_Entity
(N
, CR_Discriminant
(Entity
(N
)));
363 Set_Entity
(N
, Discriminal
(Entity
(N
)));
367 Set_Entity
(N
, Discriminal
(Entity
(N
)));
369 end Expand_Discriminant
;
371 -----------------------------
372 -- Expand_Entity_Reference --
373 -----------------------------
375 procedure Expand_Entity_Reference
(N
: Node_Id
) is
376 E
: constant Entity_Id
:= Entity
(N
);
379 -- Defend against errors
381 if No
(E
) and then Total_Errors_Detected
/= 0 then
385 if Ekind
(E
) = E_Discriminant
then
386 Expand_Discriminant
(N
);
388 elsif Is_Entry_Formal
(E
) then
389 Expand_Entry_Parameter
(N
);
391 elsif Ekind
(E
) = E_Component
392 and then Is_Protected_Private
(E
)
394 -- Protect against junk use of tasking in no run time mode
396 if No_Run_Time_Mode
then
400 Expand_Protected_Private
(N
);
402 elsif Ekind
(E
) = E_Entry_Index_Parameter
then
403 Expand_Entry_Index_Parameter
(N
);
405 elsif Is_Formal
(E
) then
408 elsif Is_Renaming_Of_Object
(E
) then
411 elsif Ekind
(E
) = E_Variable
412 and then Is_Shared_Passive
(E
)
414 Expand_Shared_Passive_Variable
(N
);
416 elsif (Ekind
(E
) = E_Variable
418 Ekind
(E
) = E_In_Out_Parameter
420 Ekind
(E
) = E_Out_Parameter
)
421 and then Present
(Current_Value
(E
))
423 Expand_Current_Value
(N
);
425 -- We do want to warn for the case of a boolean variable (not
426 -- a boolean constant) whose value is known at compile time.
428 if Is_Boolean_Type
(Etype
(N
)) then
429 Warn_On_Known_Condition
(N
);
432 end Expand_Entity_Reference
;
434 ----------------------------------
435 -- Expand_Entry_Index_Parameter --
436 ----------------------------------
438 procedure Expand_Entry_Index_Parameter
(N
: Node_Id
) is
440 Set_Entity
(N
, Entry_Index_Constant
(Entity
(N
)));
441 end Expand_Entry_Index_Parameter
;
443 ----------------------------
444 -- Expand_Entry_Parameter --
445 ----------------------------
447 procedure Expand_Entry_Parameter
(N
: Node_Id
) is
448 Loc
: constant Source_Ptr
:= Sloc
(N
);
449 Ent_Formal
: constant Entity_Id
:= Entity
(N
);
450 Ent_Spec
: constant Entity_Id
:= Scope
(Ent_Formal
);
451 Parm_Type
: constant Entity_Id
:= Entry_Parameters_Type
(Ent_Spec
);
452 Acc_Stack
: constant Elist_Id
:= Accept_Address
(Ent_Spec
);
453 Addr_Ent
: constant Entity_Id
:= Node
(Last_Elmt
(Acc_Stack
));
454 P_Comp_Ref
: Entity_Id
;
456 function In_Assignment_Context
(N
: Node_Id
) return Boolean;
457 -- Check whether this is a context in which the entry formal may
460 ---------------------------
461 -- In_Assignment_Context --
462 ---------------------------
464 function In_Assignment_Context
(N
: Node_Id
) return Boolean is
466 if Nkind
(Parent
(N
)) = N_Procedure_Call_Statement
467 or else Nkind
(Parent
(N
)) = N_Entry_Call_Statement
469 (Nkind
(Parent
(N
)) = N_Assignment_Statement
470 and then N
= Name
(Parent
(N
)))
474 elsif Nkind
(Parent
(N
)) = N_Parameter_Association
then
475 return In_Assignment_Context
(Parent
(N
));
477 elsif (Nkind
(Parent
(N
)) = N_Selected_Component
478 or else Nkind
(Parent
(N
)) = N_Indexed_Component
)
479 and then In_Assignment_Context
(Parent
(N
))
485 end In_Assignment_Context
;
487 -- Start of processing for Expand_Entry_Parameter
490 if Is_Task_Type
(Scope
(Ent_Spec
))
491 and then Comes_From_Source
(Ent_Formal
)
493 -- Before replacing the formal with the local renaming that is
494 -- used in the accept block, note if this is an assignment
495 -- context, and note the modification to avoid spurious warnings,
496 -- because the original entity is not used further.
497 -- If the formal is unconstrained, we also generate an extra
498 -- parameter to hold the Constrained attribute of the actual. No
499 -- renaming is generated for this flag.
501 if Ekind
(Entity
(N
)) /= E_In_Parameter
502 and then In_Assignment_Context
(N
)
504 Note_Possible_Modification
(N
);
507 Rewrite
(N
, New_Occurrence_Of
(Renamed_Object
(Entity
(N
)), Loc
));
511 -- What we need is a reference to the corresponding component of the
512 -- parameter record object. The Accept_Address field of the entry
513 -- entity references the address variable that contains the address
514 -- of the accept parameters record. We first have to do an unchecked
515 -- conversion to turn this into a pointer to the parameter record and
516 -- then we select the required parameter field.
519 Make_Selected_Component
(Loc
,
521 Make_Explicit_Dereference
(Loc
,
522 Unchecked_Convert_To
(Parm_Type
,
523 New_Reference_To
(Addr_Ent
, Loc
))),
525 New_Reference_To
(Entry_Component
(Ent_Formal
), Loc
));
527 -- For all types of parameters, the constructed parameter record
528 -- object contains a pointer to the parameter. Thus we must
529 -- dereference them to access them (this will often be redundant,
530 -- since the needed deference is implicit, but no harm is done by
531 -- making it explicit).
534 Make_Explicit_Dereference
(Loc
, P_Comp_Ref
));
537 end Expand_Entry_Parameter
;
543 procedure Expand_Formal
(N
: Node_Id
) is
544 E
: constant Entity_Id
:= Entity
(N
);
545 Subp
: constant Entity_Id
:= Scope
(E
);
548 if Is_Protected_Type
(Scope
(Subp
))
549 and then not Is_Init_Proc
(Subp
)
550 and then Present
(Protected_Formal
(E
))
552 Set_Entity
(N
, Protected_Formal
(E
));
556 ----------------------------
557 -- Expand_N_Expanded_Name --
558 ----------------------------
560 procedure Expand_N_Expanded_Name
(N
: Node_Id
) is
562 Expand_Entity_Reference
(N
);
563 end Expand_N_Expanded_Name
;
565 -------------------------
566 -- Expand_N_Identifier --
567 -------------------------
569 procedure Expand_N_Identifier
(N
: Node_Id
) is
571 Expand_Entity_Reference
(N
);
572 end Expand_N_Identifier
;
574 ---------------------------
575 -- Expand_N_Real_Literal --
576 ---------------------------
578 procedure Expand_N_Real_Literal
(N
: Node_Id
) is
580 if Vax_Float
(Etype
(N
)) then
581 Expand_Vax_Real_Literal
(N
);
583 end Expand_N_Real_Literal
;
585 ------------------------------
586 -- Expand_Protected_Private --
587 ------------------------------
589 procedure Expand_Protected_Private
(N
: Node_Id
) is
590 Loc
: constant Source_Ptr
:= Sloc
(N
);
591 E
: constant Entity_Id
:= Entity
(N
);
592 Op
: constant Node_Id
:= Protected_Operation
(E
);
599 if Nkind
(Op
) /= N_Subprogram_Body
600 or else Nkind
(Specification
(Op
)) /= N_Function_Specification
602 Set_Ekind
(Prival
(E
), E_Variable
);
604 Set_Ekind
(Prival
(E
), E_Constant
);
607 -- If the private component appears in an assignment (either lhs or
608 -- rhs) and is a one-dimensional array constrained by a discriminant,
609 -- rewrite as P (Lo .. Hi) with an explicit range, so that discriminal
610 -- is directly visible. This solves delicate visibility problems.
612 if Comes_From_Source
(N
)
613 and then Is_Array_Type
(Etype
(E
))
614 and then Number_Dimensions
(Etype
(E
)) = 1
615 and then not Within_Init_Proc
617 Lo
:= Type_Low_Bound
(Etype
(First_Index
(Etype
(E
))));
618 Hi
:= Type_High_Bound
(Etype
(First_Index
(Etype
(E
))));
620 if Nkind
(Parent
(N
)) = N_Assignment_Statement
621 and then ((Is_Entity_Name
(Lo
)
622 and then Ekind
(Entity
(Lo
)) = E_In_Parameter
)
623 or else (Is_Entity_Name
(Hi
)
625 Ekind
(Entity
(Hi
)) = E_In_Parameter
))
627 D_Range
:= New_Node
(N_Range
, Loc
);
629 if Is_Entity_Name
(Lo
)
630 and then Ekind
(Entity
(Lo
)) = E_In_Parameter
632 Set_Low_Bound
(D_Range
,
633 Make_Identifier
(Loc
, Chars
(Entity
(Lo
))));
635 Set_Low_Bound
(D_Range
, Duplicate_Subexpr
(Lo
));
638 if Is_Entity_Name
(Hi
)
639 and then Ekind
(Entity
(Hi
)) = E_In_Parameter
641 Set_High_Bound
(D_Range
,
642 Make_Identifier
(Loc
, Chars
(Entity
(Hi
))));
644 Set_High_Bound
(D_Range
, Duplicate_Subexpr
(Hi
));
649 Prefix
=> New_Occurrence_Of
(E
, Loc
),
650 Discrete_Range
=> D_Range
));
652 Analyze_And_Resolve
(N
, Etype
(E
));
657 -- The type of the reference is the type of the prival, which may
658 -- differ from that of the original component if it is an itype.
660 Set_Entity
(N
, Prival
(E
));
661 Set_Etype
(N
, Etype
(Prival
(E
)));
662 Scop
:= Current_Scope
;
664 -- Find entity for protected operation, which must be on scope stack
666 while not Is_Protected_Type
(Scope
(Scop
)) loop
667 Scop
:= Scope
(Scop
);
670 Append_Elmt
(N
, Privals_Chain
(Scop
));
671 end Expand_Protected_Private
;
673 ---------------------
674 -- Expand_Renaming --
675 ---------------------
677 procedure Expand_Renaming
(N
: Node_Id
) is
678 E
: constant Entity_Id
:= Entity
(N
);
679 T
: constant Entity_Id
:= Etype
(N
);
682 Rewrite
(N
, New_Copy_Tree
(Renamed_Object
(E
)));
684 -- We mark the copy as unanalyzed, so that it is sure to be
685 -- reanalyzed at the top level. This is needed in the packed
686 -- case since we specifically avoided expanding packed array
687 -- references when the renaming declaration was analyzed.
689 Reset_Analyzed_Flags
(N
);
690 Analyze_And_Resolve
(N
, T
);
697 -- This would be trivial, simply a test for an identifier that was a
698 -- reference to a formal, if it were not for the fact that a previous
699 -- call to Expand_Entry_Parameter will have modified the reference
700 -- to the identifier. A formal of a protected entity is rewritten as
702 -- typ!(recobj).rec.all'Constrained
704 -- where rec is a selector whose Entry_Formal link points to the formal
705 -- For a formal of a task entity, the formal is rewritten as a local
708 -- In addition, a formal that is marked volatile because it is aliased
709 -- through an address clause is rewritten as dereference as well.
711 function Param_Entity
(N
: Node_Id
) return Entity_Id
is
713 -- Simple reference case
715 if Nkind
(N
) = N_Identifier
then
716 if Is_Formal
(Entity
(N
)) then
719 elsif Nkind
(Parent
(Entity
(N
))) = N_Object_Renaming_Declaration
720 and then Nkind
(Parent
(Parent
(Entity
(N
)))) = N_Accept_Statement
726 if Nkind
(N
) = N_Explicit_Dereference
then
728 P
: constant Node_Id
:= Prefix
(N
);
732 if Nkind
(P
) = N_Selected_Component
then
733 S
:= Selector_Name
(P
);
735 if Present
(Entry_Formal
(Entity
(S
))) then
736 return Entry_Formal
(Entity
(S
));
739 elsif Nkind
(Original_Node
(N
)) = N_Identifier
then
740 return Param_Entity
(Original_Node
(N
));