Merged with mainline at revision 128810.
[official-gcc.git] / gcc / ada / exp_ch2.adb
blobff56e049a7f5dbd2529009d80321d7127b0ef35b
1 ------------------------------------------------------------------------------
2 -- --
3 -- GNAT COMPILER COMPONENTS --
4 -- --
5 -- E X P _ C H 2 --
6 -- --
7 -- B o d y --
8 -- --
9 -- Copyright (C) 1992-2007, 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 Atree; use Atree;
27 with Einfo; use Einfo;
28 with Elists; use Elists;
29 with Errout; use Errout;
30 with Exp_Smem; use Exp_Smem;
31 with Exp_Tss; use Exp_Tss;
32 with Exp_Util; use Exp_Util;
33 with Exp_VFpt; use Exp_VFpt;
34 with Namet; use Namet;
35 with Nmake; use Nmake;
36 with Opt; use Opt;
37 with Sem; use Sem;
38 with Sem_Eval; use Sem_Eval;
39 with Sem_Res; use Sem_Res;
40 with Sem_Util; use Sem_Util;
41 with Sem_Warn; use Sem_Warn;
42 with Sinfo; use Sinfo;
43 with Snames; use Snames;
44 with Tbuild; use Tbuild;
45 with Uintp; use Uintp;
47 package body Exp_Ch2 is
49 -----------------------
50 -- Local Subprograms --
51 -----------------------
53 procedure Expand_Current_Value (N : Node_Id);
54 -- N is a node for a variable whose Current_Value field is set. If N is
55 -- node is for a discrete type, replaces node with a copy of the referenced
56 -- value. This provides a limited form of value propagation for variables
57 -- which are initialized or assigned not been further modified at the time
58 -- of reference. The call has no effect if the Current_Value refers to a
59 -- conditional with condition other than equality.
61 procedure Expand_Discriminant (N : Node_Id);
62 -- An occurrence of a discriminant within a discriminated type is replaced
63 -- with the corresponding discriminal, that is to say the formal parameter
64 -- of the initialization procedure for the type that is associated with
65 -- that particular discriminant. This replacement is not performed for
66 -- discriminants of records that appear in constraints of component of the
67 -- record, because Gigi uses the discriminant name to retrieve its value.
68 -- In the other hand, it has to be performed for default expressions of
69 -- components because they are used in the record init procedure. See Einfo
70 -- for more details, and Exp_Ch3, Exp_Ch9 for examples of use. For
71 -- discriminants of tasks and protected types, the transformation is more
72 -- complex when it occurs within a default expression for an entry or
73 -- protected operation. The corresponding default_expression_function has
74 -- an additional parameter which is the target of an entry call, and the
75 -- discriminant of the task must be replaced with a reference to the
76 -- discriminant of that formal parameter.
78 procedure Expand_Entity_Reference (N : Node_Id);
79 -- Common processing for expansion of identifiers and expanded names
80 -- Dispatches to specific expansion procedures.
82 procedure Expand_Entry_Index_Parameter (N : Node_Id);
83 -- A reference to the identifier in the entry index specification of
84 -- protected entry body is modified to a reference to a constant definition
85 -- equal to the index of the entry family member being called. This
86 -- constant is calculated as part of the elaboration of the expanded code
87 -- for the body, and is calculated from the object-wide entry index
88 -- returned by Next_Entry_Call.
90 procedure Expand_Entry_Parameter (N : Node_Id);
91 -- A reference to an entry parameter is modified to be a reference to the
92 -- corresponding component of the entry parameter record that is passed by
93 -- the runtime to the accept body procedure.
95 procedure Expand_Formal (N : Node_Id);
96 -- A reference to a formal parameter of a protected subprogram is expanded
97 -- into the corresponding formal of the unprotected procedure used to
98 -- represent the operation within the protected object. In other cases
99 -- Expand_Formal is a no-op.
101 procedure Expand_Protected_Private (N : Node_Id);
102 -- A reference to a private component of a protected type is expanded to a
103 -- component selected from the record used to implement the protected
104 -- object. Such a record is passed to all operations on a protected object
105 -- in a parameter named _object. This object is a constant in the body of a
106 -- function, and a variable within a procedure or entry body.
108 procedure Expand_Renaming (N : Node_Id);
109 -- For renamings, just replace the identifier by the corresponding
110 -- named expression. Note that this has been evaluated (see routine
111 -- Exp_Ch8.Expand_N_Object_Renaming.Evaluate_Name) so this gives
112 -- the correct renaming semantics.
114 --------------------------
115 -- Expand_Current_Value --
116 --------------------------
118 procedure Expand_Current_Value (N : Node_Id) is
119 Loc : constant Source_Ptr := Sloc (N);
120 E : constant Entity_Id := Entity (N);
121 CV : constant Node_Id := Current_Value (E);
122 T : constant Entity_Id := Etype (N);
123 Val : Node_Id;
124 Op : Node_Kind;
126 -- Start of processing for Expand_Current_Value
128 begin
129 if True
131 -- No replacement if value raises constraint error
133 and then Nkind (CV) /= N_Raise_Constraint_Error
135 -- Do this only for discrete types
137 and then Is_Discrete_Type (T)
139 -- Do not replace biased types, since it is problematic to
140 -- consistently generate a sensible constant value in this case.
142 and then not Has_Biased_Representation (T)
144 -- Do not replace lvalues
146 and then not May_Be_Lvalue (N)
148 -- Check that entity is suitable for replacement
150 and then OK_To_Do_Constant_Replacement (E)
152 -- Do not replace occurrences in pragmas (where names typically
153 -- appear not as values, but as simply names. If there are cases
154 -- where values are required, it is only a very minor efficiency
155 -- issue that they do not get replaced when they could be).
157 and then Nkind (Parent (N)) /= N_Pragma_Argument_Association
159 -- Do not replace the prefixes of attribute references, since this
160 -- causes trouble with cases like 4'Size. Also for Name_Asm_Input and
161 -- Name_Asm_Output, don't do replacement anywhere, since we can have
162 -- lvalue references in the arguments.
164 and then not (Nkind (Parent (N)) = N_Attribute_Reference
165 and then
166 (Attribute_Name (Parent (N)) = Name_Asm_Input
167 or else
168 Attribute_Name (Parent (N)) = Name_Asm_Output
169 or else
170 Prefix (Parent (N)) = N))
172 then
173 -- Case of Current_Value is a compile time known value
175 if Nkind (CV) in N_Subexpr then
176 Val := CV;
178 -- Case of Current_Value is a conditional expression reference
180 else
181 Get_Current_Value_Condition (N, Op, Val);
183 if Op /= N_Op_Eq then
184 return;
185 end if;
186 end if;
188 -- If constant value is an occurrence of an enumeration literal,
189 -- then we just make another occurence of the same literal.
191 if Is_Entity_Name (Val)
192 and then Ekind (Entity (Val)) = E_Enumeration_Literal
193 then
194 Rewrite (N,
195 Unchecked_Convert_To (T,
196 New_Occurrence_Of (Entity (Val), Loc)));
198 -- Otherwise get the value, and convert to appropriate type
200 else
201 Rewrite (N,
202 Unchecked_Convert_To (T,
203 Make_Integer_Literal (Loc,
204 Intval => Expr_Rep_Value (Val))));
205 end if;
207 Analyze_And_Resolve (N, T);
208 Set_Is_Static_Expression (N, False);
209 end if;
210 end Expand_Current_Value;
212 -------------------------
213 -- Expand_Discriminant --
214 -------------------------
216 procedure Expand_Discriminant (N : Node_Id) is
217 Scop : constant Entity_Id := Scope (Entity (N));
218 P : Node_Id := N;
219 Parent_P : Node_Id := Parent (P);
220 In_Entry : Boolean := False;
222 begin
223 -- The Incomplete_Or_Private_Kind happens while resolving the
224 -- discriminant constraint involved in a derived full type,
225 -- such as:
227 -- type D is private;
228 -- type D(C : ...) is new T(C);
230 if Ekind (Scop) = E_Record_Type
231 or Ekind (Scop) in Incomplete_Or_Private_Kind
232 then
233 -- Find the origin by walking up the tree till the component
234 -- declaration
236 while Present (Parent_P)
237 and then Nkind (Parent_P) /= N_Component_Declaration
238 loop
239 P := Parent_P;
240 Parent_P := Parent (P);
241 end loop;
243 -- If the discriminant reference was part of the default expression
244 -- it has to be "discriminalized"
246 if Present (Parent_P) and then P = Expression (Parent_P) then
247 Set_Entity (N, Discriminal (Entity (N)));
248 end if;
250 elsif Is_Concurrent_Type (Scop) then
251 while Present (Parent_P)
252 and then Nkind (Parent_P) /= N_Subprogram_Body
253 loop
254 P := Parent_P;
256 if Nkind (P) = N_Entry_Declaration then
257 In_Entry := True;
258 end if;
260 Parent_P := Parent (Parent_P);
261 end loop;
263 -- If the discriminant occurs within the default expression for a
264 -- formal of an entry or protected operation, create a default
265 -- function for it, and replace the discriminant with a reference to
266 -- the discriminant of the formal of the default function. The
267 -- discriminant entity is the one defined in the corresponding
268 -- record.
270 if Present (Parent_P)
271 and then Present (Corresponding_Spec (Parent_P))
272 then
273 declare
274 Loc : constant Source_Ptr := Sloc (N);
275 D_Fun : constant Entity_Id := Corresponding_Spec (Parent_P);
276 Formal : constant Entity_Id := First_Formal (D_Fun);
277 New_N : Node_Id;
278 Disc : Entity_Id;
280 begin
281 -- Verify that we are within a default function: the type of
282 -- its formal parameter is the same task or protected type.
284 if Present (Formal)
285 and then Etype (Formal) = Scope (Entity (N))
286 then
287 Disc := CR_Discriminant (Entity (N));
289 New_N :=
290 Make_Selected_Component (Loc,
291 Prefix => New_Occurrence_Of (Formal, Loc),
292 Selector_Name => New_Occurrence_Of (Disc, Loc));
294 Set_Etype (New_N, Etype (N));
295 Rewrite (N, New_N);
297 else
298 Set_Entity (N, Discriminal (Entity (N)));
299 end if;
300 end;
302 elsif Nkind (Parent (N)) = N_Range
303 and then In_Entry
304 then
305 Set_Entity (N, CR_Discriminant (Entity (N)));
306 else
307 Set_Entity (N, Discriminal (Entity (N)));
308 end if;
310 else
311 Set_Entity (N, Discriminal (Entity (N)));
312 end if;
313 end Expand_Discriminant;
315 -----------------------------
316 -- Expand_Entity_Reference --
317 -----------------------------
319 procedure Expand_Entity_Reference (N : Node_Id) is
320 E : constant Entity_Id := Entity (N);
322 begin
323 -- Defend against errors
325 if No (E) and then Total_Errors_Detected /= 0 then
326 return;
327 end if;
329 if Ekind (E) = E_Discriminant then
330 Expand_Discriminant (N);
332 elsif Is_Entry_Formal (E) then
333 Expand_Entry_Parameter (N);
335 elsif Ekind (E) = E_Component
336 and then Is_Protected_Private (E)
337 then
338 -- Protect against junk use of tasking in no run time mode
340 if No_Run_Time_Mode then
341 return;
342 end if;
344 Expand_Protected_Private (N);
346 elsif Ekind (E) = E_Entry_Index_Parameter then
347 Expand_Entry_Index_Parameter (N);
349 elsif Is_Formal (E) then
350 Expand_Formal (N);
352 elsif Is_Renaming_Of_Object (E) then
353 Expand_Renaming (N);
355 elsif Ekind (E) = E_Variable
356 and then Is_Shared_Passive (E)
357 then
358 Expand_Shared_Passive_Variable (N);
359 end if;
361 -- Interpret possible Current_Value for variable case
363 if (Ekind (E) = E_Variable
364 or else
365 Ekind (E) = E_In_Out_Parameter
366 or else
367 Ekind (E) = E_Out_Parameter)
368 and then Present (Current_Value (E))
369 then
370 Expand_Current_Value (N);
372 -- We do want to warn for the case of a boolean variable (not a
373 -- boolean constant) whose value is known at compile time.
375 if Is_Boolean_Type (Etype (N)) then
376 Warn_On_Known_Condition (N);
377 end if;
379 -- Don't mess with Current_Value for compile time known values. Not
380 -- only is it unnecessary, but we could disturb an indication of a
381 -- static value, which could cause semantic trouble.
383 elsif Compile_Time_Known_Value (N) then
384 null;
386 -- Interpret possible Current_Value for constant case
388 elsif (Ekind (E) = E_Constant
389 or else
390 Ekind (E) = E_In_Parameter
391 or else
392 Ekind (E) = E_Loop_Parameter)
393 and then Present (Current_Value (E))
394 then
395 Expand_Current_Value (N);
396 end if;
397 end Expand_Entity_Reference;
399 ----------------------------------
400 -- Expand_Entry_Index_Parameter --
401 ----------------------------------
403 procedure Expand_Entry_Index_Parameter (N : Node_Id) is
404 begin
405 Set_Entity (N, Entry_Index_Constant (Entity (N)));
406 end Expand_Entry_Index_Parameter;
408 ----------------------------
409 -- Expand_Entry_Parameter --
410 ----------------------------
412 procedure Expand_Entry_Parameter (N : Node_Id) is
413 Loc : constant Source_Ptr := Sloc (N);
414 Ent_Formal : constant Entity_Id := Entity (N);
415 Ent_Spec : constant Entity_Id := Scope (Ent_Formal);
416 Parm_Type : constant Entity_Id := Entry_Parameters_Type (Ent_Spec);
417 Acc_Stack : constant Elist_Id := Accept_Address (Ent_Spec);
418 Addr_Ent : constant Entity_Id := Node (Last_Elmt (Acc_Stack));
419 P_Comp_Ref : Entity_Id;
421 function In_Assignment_Context (N : Node_Id) return Boolean;
422 -- Check whether this is a context in which the entry formal may be
423 -- assigned to.
425 ---------------------------
426 -- In_Assignment_Context --
427 ---------------------------
429 function In_Assignment_Context (N : Node_Id) return Boolean is
430 begin
431 -- Case of use in a call
433 -- ??? passing a formal as actual for a mode IN formal is
434 -- considered as an assignment?
436 if Nkind (Parent (N)) = N_Procedure_Call_Statement
437 or else Nkind (Parent (N)) = N_Entry_Call_Statement
438 or else
439 (Nkind (Parent (N)) = N_Assignment_Statement
440 and then N = Name (Parent (N)))
441 then
442 return True;
444 -- Case of a parameter association: climb up to enclosing call
446 elsif Nkind (Parent (N)) = N_Parameter_Association then
447 return In_Assignment_Context (Parent (N));
449 -- Case of a selected component, indexed component or slice prefix:
450 -- climb up the tree, unless the prefix is of an access type (in
451 -- which case there is an implicit dereference, and the formal itself
452 -- is not being assigned to).
454 elsif (Nkind (Parent (N)) = N_Selected_Component
455 or else Nkind (Parent (N)) = N_Indexed_Component
456 or else Nkind (Parent (N)) = N_Slice)
457 and then N = Prefix (Parent (N))
458 and then not Is_Access_Type (Etype (N))
459 and then In_Assignment_Context (Parent (N))
460 then
461 return True;
463 else
464 return False;
465 end if;
466 end In_Assignment_Context;
468 -- Start of processing for Expand_Entry_Parameter
470 begin
471 if Is_Task_Type (Scope (Ent_Spec))
472 and then Comes_From_Source (Ent_Formal)
473 then
474 -- Before replacing the formal with the local renaming that is used
475 -- in the accept block, note if this is an assignment context, and
476 -- note the modification to avoid spurious warnings, because the
477 -- original entity is not used further. If formal is unconstrained,
478 -- we also generate an extra parameter to hold the Constrained
479 -- attribute of the actual. No renaming is generated for this flag.
481 if Ekind (Entity (N)) /= E_In_Parameter
482 and then In_Assignment_Context (N)
483 then
484 Note_Possible_Modification (N);
485 end if;
487 Rewrite (N, New_Occurrence_Of (Renamed_Object (Entity (N)), Loc));
488 return;
489 end if;
491 -- What we need is a reference to the corresponding component of the
492 -- parameter record object. The Accept_Address field of the entry entity
493 -- references the address variable that contains the address of the
494 -- accept parameters record. We first have to do an unchecked conversion
495 -- to turn this into a pointer to the parameter record and then we
496 -- select the required parameter field.
498 P_Comp_Ref :=
499 Make_Selected_Component (Loc,
500 Prefix =>
501 Make_Explicit_Dereference (Loc,
502 Unchecked_Convert_To (Parm_Type,
503 New_Reference_To (Addr_Ent, Loc))),
504 Selector_Name =>
505 New_Reference_To (Entry_Component (Ent_Formal), Loc));
507 -- For all types of parameters, the constructed parameter record object
508 -- contains a pointer to the parameter. Thus we must dereference them to
509 -- access them (this will often be redundant, since the needed deference
510 -- is implicit, but no harm is done by making it explicit).
512 Rewrite (N,
513 Make_Explicit_Dereference (Loc, P_Comp_Ref));
515 Analyze (N);
516 end Expand_Entry_Parameter;
518 -------------------
519 -- Expand_Formal --
520 -------------------
522 procedure Expand_Formal (N : Node_Id) is
523 E : constant Entity_Id := Entity (N);
524 Scop : constant Entity_Id := Scope (E);
526 begin
527 -- Check whether the subprogram of which this is a formal is
528 -- a protected operation. The initialization procedure for
529 -- the corresponding record type is not itself a protected operation.
531 if Is_Protected_Type (Scope (Scop))
532 and then not Is_Init_Proc (Scop)
533 and then Present (Protected_Formal (E))
534 then
535 Set_Entity (N, Protected_Formal (E));
536 end if;
537 end Expand_Formal;
539 ----------------------------
540 -- Expand_N_Expanded_Name --
541 ----------------------------
543 procedure Expand_N_Expanded_Name (N : Node_Id) is
544 begin
545 Expand_Entity_Reference (N);
546 end Expand_N_Expanded_Name;
548 -------------------------
549 -- Expand_N_Identifier --
550 -------------------------
552 procedure Expand_N_Identifier (N : Node_Id) is
553 begin
554 Expand_Entity_Reference (N);
555 end Expand_N_Identifier;
557 ---------------------------
558 -- Expand_N_Real_Literal --
559 ---------------------------
561 procedure Expand_N_Real_Literal (N : Node_Id) is
562 begin
563 if Vax_Float (Etype (N)) then
564 Expand_Vax_Real_Literal (N);
565 end if;
566 end Expand_N_Real_Literal;
568 ------------------------------
569 -- Expand_Protected_Private --
570 ------------------------------
572 procedure Expand_Protected_Private (N : Node_Id) is
573 Loc : constant Source_Ptr := Sloc (N);
574 E : constant Entity_Id := Entity (N);
575 Op : constant Node_Id := Protected_Operation (E);
576 Scop : Entity_Id;
577 Lo : Node_Id;
578 Hi : Node_Id;
579 D_Range : Node_Id;
581 begin
582 if Nkind (Op) /= N_Subprogram_Body
583 or else Nkind (Specification (Op)) /= N_Function_Specification
584 then
585 Set_Ekind (Prival (E), E_Variable);
586 else
587 Set_Ekind (Prival (E), E_Constant);
588 end if;
590 -- If the private component appears in an assignment (either lhs or
591 -- rhs) and is a one-dimensional array constrained by a discriminant,
592 -- rewrite as P (Lo .. Hi) with an explicit range, so that discriminal
593 -- is directly visible. This solves delicate visibility problems.
595 if Comes_From_Source (N)
596 and then Is_Array_Type (Etype (E))
597 and then Number_Dimensions (Etype (E)) = 1
598 and then not Within_Init_Proc
599 then
600 Lo := Type_Low_Bound (Etype (First_Index (Etype (E))));
601 Hi := Type_High_Bound (Etype (First_Index (Etype (E))));
603 if Nkind (Parent (N)) = N_Assignment_Statement
604 and then ((Is_Entity_Name (Lo)
605 and then Ekind (Entity (Lo)) = E_In_Parameter)
606 or else (Is_Entity_Name (Hi)
607 and then
608 Ekind (Entity (Hi)) = E_In_Parameter))
609 then
610 D_Range := New_Node (N_Range, Loc);
612 if Is_Entity_Name (Lo)
613 and then Ekind (Entity (Lo)) = E_In_Parameter
614 then
615 Set_Low_Bound (D_Range,
616 Make_Identifier (Loc, Chars (Entity (Lo))));
617 else
618 Set_Low_Bound (D_Range, Duplicate_Subexpr (Lo));
619 end if;
621 if Is_Entity_Name (Hi)
622 and then Ekind (Entity (Hi)) = E_In_Parameter
623 then
624 Set_High_Bound (D_Range,
625 Make_Identifier (Loc, Chars (Entity (Hi))));
626 else
627 Set_High_Bound (D_Range, Duplicate_Subexpr (Hi));
628 end if;
630 Rewrite (N,
631 Make_Slice (Loc,
632 Prefix => New_Occurrence_Of (E, Loc),
633 Discrete_Range => D_Range));
635 Analyze_And_Resolve (N, Etype (E));
636 return;
637 end if;
638 end if;
640 -- The type of the reference is the type of the prival, which may differ
641 -- from that of the original component if it is an itype.
643 Set_Entity (N, Prival (E));
644 Set_Etype (N, Etype (Prival (E)));
645 Scop := Current_Scope;
647 -- Find entity for protected operation, which must be on scope stack
649 while not Is_Protected_Type (Scope (Scop)) loop
650 Scop := Scope (Scop);
651 end loop;
653 Append_Elmt (N, Privals_Chain (Scop));
654 end Expand_Protected_Private;
656 ---------------------
657 -- Expand_Renaming --
658 ---------------------
660 procedure Expand_Renaming (N : Node_Id) is
661 E : constant Entity_Id := Entity (N);
662 T : constant Entity_Id := Etype (N);
664 begin
665 Rewrite (N, New_Copy_Tree (Renamed_Object (E)));
667 -- We mark the copy as unanalyzed, so that it is sure to be reanalyzed
668 -- at the top level. This is needed in the packed case since we
669 -- specifically avoided expanding packed array references when the
670 -- renaming declaration was analyzed.
672 Reset_Analyzed_Flags (N);
673 Analyze_And_Resolve (N, T);
674 end Expand_Renaming;
676 ------------------
677 -- Param_Entity --
678 ------------------
680 -- This would be trivial, simply a test for an identifier that was a
681 -- reference to a formal, if it were not for the fact that a previous call
682 -- to Expand_Entry_Parameter will have modified the reference to the
683 -- identifier. A formal of a protected entity is rewritten as
685 -- typ!(recobj).rec.all'Constrained
687 -- where rec is a selector whose Entry_Formal link points to the formal
688 -- For a formal of a task entity, the formal is rewritten as a local
689 -- renaming.
691 -- In addition, a formal that is marked volatile because it is aliased
692 -- through an address clause is rewritten as dereference as well.
694 function Param_Entity (N : Node_Id) return Entity_Id is
695 Renamed_Obj : Node_Id;
697 begin
698 -- Simple reference case
700 if Nkind (N) = N_Identifier or else Nkind (N) = N_Expanded_Name then
701 if Is_Formal (Entity (N)) then
702 return Entity (N);
704 -- Handle renamings of formal parameters and formals of tasks that
705 -- are rewritten as renamings.
707 elsif Nkind (Parent (Entity (N))) = N_Object_Renaming_Declaration then
708 Renamed_Obj := Get_Referenced_Object (Renamed_Object (Entity (N)));
710 if Is_Entity_Name (Renamed_Obj)
711 and then Is_Formal (Entity (Renamed_Obj))
712 then
713 return Entity (Renamed_Obj);
715 elsif
716 Nkind (Parent (Parent (Entity (N)))) = N_Accept_Statement
717 then
718 return Entity (N);
719 end if;
720 end if;
722 else
723 if Nkind (N) = N_Explicit_Dereference then
724 declare
725 P : constant Node_Id := Prefix (N);
726 S : Node_Id;
728 begin
729 if Nkind (P) = N_Selected_Component then
730 S := Selector_Name (P);
732 if Present (Entry_Formal (Entity (S))) then
733 return Entry_Formal (Entity (S));
734 end if;
736 elsif Nkind (Original_Node (N)) = N_Identifier then
737 return Param_Entity (Original_Node (N));
738 end if;
739 end;
740 end if;
741 end if;
743 return (Empty);
744 end Param_Entity;
746 end Exp_Ch2;