OSDN Git Service

2009-07-23 Robert Dewar <dewar@adacore.com>
[pf3gnuchains/gcc-fork.git] / gcc / ada / exp_ch2.adb
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-2009, 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 ------------------------------------------------------------------------------
25
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;
46
47 package body Exp_Ch2 is
48
49    -----------------------
50    -- Local Subprograms --
51    -----------------------
52
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.
60
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.
77
78    procedure Expand_Entity_Reference (N : Node_Id);
79    --  Common processing for expansion of identifiers and expanded names
80    --  Dispatches to specific expansion procedures.
81
82    procedure Expand_Entry_Index_Parameter (N : Node_Id);
83    --  A reference to the identifier in the entry index specification of an
84    --  entry body is modified to a reference to a constant definition equal to
85    --  the index of the entry family member being called. This constant is
86    --  calculated as part of the elaboration of the expanded code for the body,
87    --  and is calculated from the object-wide entry index returned by Next_
88    --  Entry_Call.
89
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.
94
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.
100
101    procedure Expand_Protected_Component (N : Node_Id);
102    --  A reference to a private component of a protected type is expanded into
103    --  a reference to the corresponding prival in the current protected entry
104    --  or subprogram.
105
106    procedure Expand_Renaming (N : Node_Id);
107    --  For renamings, just replace the identifier by the corresponding
108    --  named expression. Note that this has been evaluated (see routine
109    --  Exp_Ch8.Expand_N_Object_Renaming.Evaluate_Name) so this gives
110    --  the correct renaming semantics.
111
112    --------------------------
113    -- Expand_Current_Value --
114    --------------------------
115
116    procedure Expand_Current_Value (N : Node_Id) is
117       Loc : constant Source_Ptr := Sloc (N);
118       E   : constant Entity_Id  := Entity (N);
119       CV  : constant Node_Id    := Current_Value (E);
120       T   : constant Entity_Id  := Etype (N);
121       Val : Node_Id;
122       Op  : Node_Kind;
123
124    --  Start of processing for Expand_Current_Value
125
126    begin
127       if True
128
129          --  No replacement if value raises constraint error
130
131          and then Nkind (CV) /= N_Raise_Constraint_Error
132
133          --  Do this only for discrete types
134
135          and then Is_Discrete_Type (T)
136
137          --  Do not replace biased types, since it is problematic to
138          --  consistently generate a sensible constant value in this case.
139
140          and then not Has_Biased_Representation (T)
141
142          --  Do not replace lvalues
143
144          and then not May_Be_Lvalue (N)
145
146          --  Check that entity is suitable for replacement
147
148          and then OK_To_Do_Constant_Replacement (E)
149
150          --  Do not replace occurrences in pragmas (where names typically
151          --  appear not as values, but as simply names. If there are cases
152          --  where values are required, it is only a very minor efficiency
153          --  issue that they do not get replaced when they could be).
154
155          and then Nkind (Parent (N)) /= N_Pragma_Argument_Association
156
157          --  Do not replace the prefixes of attribute references, since this
158          --  causes trouble with cases like 4'Size. Also for Name_Asm_Input and
159          --  Name_Asm_Output, don't do replacement anywhere, since we can have
160          --  lvalue references in the arguments.
161
162          and then not (Nkind (Parent (N)) = N_Attribute_Reference
163                          and then
164                            (Attribute_Name (Parent (N)) = Name_Asm_Input
165                               or else
166                             Attribute_Name (Parent (N)) = Name_Asm_Output
167                               or else
168                             Prefix (Parent (N)) = N))
169
170       then
171          --  Case of Current_Value is a compile time known value
172
173          if Nkind (CV) in N_Subexpr then
174             Val := CV;
175
176          --  Case of Current_Value is a conditional expression reference
177
178          else
179             Get_Current_Value_Condition (N, Op, Val);
180
181             if Op /= N_Op_Eq then
182                return;
183             end if;
184          end if;
185
186          --  If constant value is an occurrence of an enumeration literal,
187          --  then we just make another occurrence of the same literal.
188
189          if Is_Entity_Name (Val)
190            and then Ekind (Entity (Val)) = E_Enumeration_Literal
191          then
192             Rewrite (N,
193               Unchecked_Convert_To (T,
194                 New_Occurrence_Of (Entity (Val), Loc)));
195
196          --  If constant is of an integer type, just make an appropriately
197          --  integer literal, which will get the proper type.
198
199          elsif Is_Integer_Type (T) then
200             Rewrite (N,
201               Make_Integer_Literal (Loc,
202                 Intval => Expr_Rep_Value (Val)));
203
204          --  Otherwise do unchecked conversion of value to right type
205
206          else
207             Rewrite (N,
208               Unchecked_Convert_To (T,
209                  Make_Integer_Literal (Loc,
210                    Intval => Expr_Rep_Value (Val))));
211          end if;
212
213          Analyze_And_Resolve (N, T);
214          Set_Is_Static_Expression (N, False);
215       end if;
216    end Expand_Current_Value;
217
218    -------------------------
219    -- Expand_Discriminant --
220    -------------------------
221
222    procedure Expand_Discriminant (N : Node_Id) is
223       Scop     : constant Entity_Id := Scope (Entity (N));
224       P        : Node_Id := N;
225       Parent_P : Node_Id := Parent (P);
226       In_Entry : Boolean := False;
227
228    begin
229       --  The Incomplete_Or_Private_Kind happens while resolving the
230       --  discriminant constraint involved in a derived full type,
231       --  such as:
232
233       --    type D is private;
234       --    type D(C : ...) is new T(C);
235
236       if Ekind (Scop) = E_Record_Type
237         or Ekind (Scop) in Incomplete_Or_Private_Kind
238       then
239          --  Find the origin by walking up the tree till the component
240          --  declaration
241
242          while Present (Parent_P)
243            and then Nkind (Parent_P) /= N_Component_Declaration
244          loop
245             P := Parent_P;
246             Parent_P := Parent (P);
247          end loop;
248
249          --  If the discriminant reference was part of the default expression
250          --  it has to be "discriminalized"
251
252          if Present (Parent_P) and then P = Expression (Parent_P) then
253             Set_Entity (N, Discriminal (Entity (N)));
254          end if;
255
256       elsif Is_Concurrent_Type (Scop) then
257          while Present (Parent_P)
258            and then Nkind (Parent_P) /= N_Subprogram_Body
259          loop
260             P := Parent_P;
261
262             if Nkind (P) = N_Entry_Declaration then
263                In_Entry := True;
264             end if;
265
266             Parent_P := Parent (Parent_P);
267          end loop;
268
269          --  If the discriminant occurs within the default expression for a
270          --  formal of an entry or protected operation, replace it with a
271          --  reference to the discriminant of the formal of the enclosing
272          --  operation.
273
274          if Present (Parent_P)
275            and then Present (Corresponding_Spec (Parent_P))
276          then
277             declare
278                Loc    : constant Source_Ptr := Sloc (N);
279                D_Fun  : constant Entity_Id := Corresponding_Spec  (Parent_P);
280                Formal : constant Entity_Id := First_Formal (D_Fun);
281                New_N  : Node_Id;
282                Disc   : Entity_Id;
283
284             begin
285                --  Verify that we are within the body of an entry or protected
286                --  operation. Its first formal parameter is the synchronized
287                --  type itself.
288
289                if Present (Formal)
290                  and then Etype (Formal) = Scope (Entity (N))
291                then
292                   Disc := CR_Discriminant (Entity (N));
293
294                   New_N :=
295                     Make_Selected_Component (Loc,
296                       Prefix => New_Occurrence_Of (Formal, Loc),
297                       Selector_Name => New_Occurrence_Of (Disc, Loc));
298
299                   Set_Etype (New_N, Etype (N));
300                   Rewrite (N, New_N);
301
302                else
303                   Set_Entity (N, Discriminal (Entity (N)));
304                end if;
305             end;
306
307          elsif Nkind (Parent (N)) = N_Range
308            and then In_Entry
309          then
310             Set_Entity (N, CR_Discriminant (Entity (N)));
311
312             --  Finally, if the entity is the discriminant of the original
313             --  type declaration, and we are within the initialization
314             --  procedure for a task, the designated entity is the
315             --  discriminal of the task body. This can happen when the
316             --  argument of pragma Task_Name mentions a discriminant,
317             --  because the pragma is analyzed in the task declaration
318             --  but is expanded in the call to Create_Task in the init_proc.
319
320          elsif Within_Init_Proc then
321             Set_Entity (N, Discriminal (CR_Discriminant (Entity (N))));
322          else
323             Set_Entity (N, Discriminal (Entity (N)));
324          end if;
325
326       else
327          Set_Entity (N, Discriminal (Entity (N)));
328       end if;
329    end Expand_Discriminant;
330
331    -----------------------------
332    -- Expand_Entity_Reference --
333    -----------------------------
334
335    procedure Expand_Entity_Reference (N : Node_Id) is
336       E : constant Entity_Id := Entity (N);
337
338    begin
339       --  Defend against errors
340
341       if No (E) and then Total_Errors_Detected /= 0 then
342          return;
343       end if;
344
345       if Ekind (E) = E_Discriminant then
346          Expand_Discriminant (N);
347
348       elsif Is_Entry_Formal (E) then
349          Expand_Entry_Parameter (N);
350
351       elsif Is_Protected_Component (E) then
352          if No_Run_Time_Mode then
353             return;
354          end if;
355
356          Expand_Protected_Component (N);
357
358       elsif Ekind (E) = E_Entry_Index_Parameter then
359          Expand_Entry_Index_Parameter (N);
360
361       elsif Is_Formal (E) then
362          Expand_Formal (N);
363
364       elsif Is_Renaming_Of_Object (E) then
365          Expand_Renaming (N);
366
367       elsif Ekind (E) = E_Variable
368         and then Is_Shared_Passive (E)
369       then
370          Expand_Shared_Passive_Variable (N);
371       end if;
372
373       --  Interpret possible Current_Value for variable case
374
375       if (Ekind (E) = E_Variable
376             or else
377           Ekind (E) = E_In_Out_Parameter
378             or else
379           Ekind (E) = E_Out_Parameter)
380         and then Present (Current_Value (E))
381       then
382          Expand_Current_Value (N);
383
384          --  We do want to warn for the case of a boolean variable (not a
385          --  boolean constant) whose value is known at compile time.
386
387          if Is_Boolean_Type (Etype (N)) then
388             Warn_On_Known_Condition (N);
389          end if;
390
391       --  Don't mess with Current_Value for compile time known values. Not
392       --  only is it unnecessary, but we could disturb an indication of a
393       --  static value, which could cause semantic trouble.
394
395       elsif Compile_Time_Known_Value (N) then
396          null;
397
398       --  Interpret possible Current_Value for constant case
399
400       elsif Is_Constant_Object (E)
401         and then Present (Current_Value (E))
402       then
403          Expand_Current_Value (N);
404       end if;
405    end Expand_Entity_Reference;
406
407    ----------------------------------
408    -- Expand_Entry_Index_Parameter --
409    ----------------------------------
410
411    procedure Expand_Entry_Index_Parameter (N : Node_Id) is
412       Index_Con : constant Entity_Id := Entry_Index_Constant (Entity (N));
413    begin
414       Set_Entity (N, Index_Con);
415       Set_Etype  (N, Etype (Index_Con));
416    end Expand_Entry_Index_Parameter;
417
418    ----------------------------
419    -- Expand_Entry_Parameter --
420    ----------------------------
421
422    procedure Expand_Entry_Parameter (N : Node_Id) is
423       Loc        : constant Source_Ptr := Sloc (N);
424       Ent_Formal : constant Entity_Id  := Entity (N);
425       Ent_Spec   : constant Entity_Id  := Scope (Ent_Formal);
426       Parm_Type  : constant Entity_Id  := Entry_Parameters_Type (Ent_Spec);
427       Acc_Stack  : constant Elist_Id   := Accept_Address (Ent_Spec);
428       Addr_Ent   : constant Entity_Id  := Node (Last_Elmt (Acc_Stack));
429       P_Comp_Ref : Entity_Id;
430
431       function In_Assignment_Context (N : Node_Id) return Boolean;
432       --  Check whether this is a context in which the entry formal may be
433       --  assigned to.
434
435       ---------------------------
436       -- In_Assignment_Context --
437       ---------------------------
438
439       function In_Assignment_Context (N : Node_Id) return Boolean is
440       begin
441          --  Case of use in a call
442
443          --  ??? passing a formal as actual for a mode IN formal is
444          --  considered as an assignment?
445
446          if Nkind_In (Parent (N), N_Procedure_Call_Statement,
447                                   N_Entry_Call_Statement)
448            or else (Nkind (Parent (N)) = N_Assignment_Statement
449                       and then N = Name (Parent (N)))
450          then
451             return True;
452
453          --  Case of a parameter association: climb up to enclosing call
454
455          elsif Nkind (Parent (N)) = N_Parameter_Association then
456             return In_Assignment_Context (Parent (N));
457
458          --  Case of a selected component, indexed component or slice prefix:
459          --  climb up the tree, unless the prefix is of an access type (in
460          --  which case there is an implicit dereference, and the formal itself
461          --  is not being assigned to).
462
463          elsif Nkind_In (Parent (N), N_Selected_Component,
464                                      N_Indexed_Component,
465                                      N_Slice)
466            and then N = Prefix (Parent (N))
467            and then not Is_Access_Type (Etype (N))
468            and then In_Assignment_Context (Parent (N))
469          then
470             return True;
471
472          else
473             return False;
474          end if;
475       end In_Assignment_Context;
476
477    --  Start of processing for Expand_Entry_Parameter
478
479    begin
480       if Is_Task_Type (Scope (Ent_Spec))
481         and then Comes_From_Source (Ent_Formal)
482       then
483          --  Before replacing the formal with the local renaming that is used
484          --  in the accept block, note if this is an assignment context, and
485          --  note the modification to avoid spurious warnings, because the
486          --  original entity is not used further. If formal is unconstrained,
487          --  we also generate an extra parameter to hold the Constrained
488          --  attribute of the actual. No renaming is generated for this flag.
489
490          --  Calling Note_Possible_Modification in the expander is dubious,
491          --  because this generates a cross-reference entry, and should be
492          --  done during semantic processing so it is called in -gnatc mode???
493
494          if Ekind (Entity (N)) /= E_In_Parameter
495            and then In_Assignment_Context (N)
496          then
497             Note_Possible_Modification (N, Sure => True);
498          end if;
499
500          Rewrite (N, New_Occurrence_Of (Renamed_Object (Entity (N)), Loc));
501          return;
502       end if;
503
504       --  What we need is a reference to the corresponding component of the
505       --  parameter record object. The Accept_Address field of the entry entity
506       --  references the address variable that contains the address of the
507       --  accept parameters record. We first have to do an unchecked conversion
508       --  to turn this into a pointer to the parameter record and then we
509       --  select the required parameter field.
510
511       P_Comp_Ref :=
512         Make_Selected_Component (Loc,
513           Prefix =>
514             Make_Explicit_Dereference (Loc,
515               Unchecked_Convert_To (Parm_Type,
516                 New_Reference_To (Addr_Ent, Loc))),
517           Selector_Name =>
518             New_Reference_To (Entry_Component (Ent_Formal), Loc));
519
520       --  For all types of parameters, the constructed parameter record object
521       --  contains a pointer to the parameter. Thus we must dereference them to
522       --  access them (this will often be redundant, since the dereference is
523       --  implicit, but no harm is done by making it explicit).
524
525       Rewrite (N,
526         Make_Explicit_Dereference (Loc, P_Comp_Ref));
527
528       Analyze (N);
529    end Expand_Entry_Parameter;
530
531    -------------------
532    -- Expand_Formal --
533    -------------------
534
535    procedure Expand_Formal (N : Node_Id) is
536       E    : constant Entity_Id  := Entity (N);
537       Scop : constant Entity_Id  := Scope (E);
538
539    begin
540       --  Check whether the subprogram of which this is a formal is
541       --  a protected operation. The initialization procedure for
542       --  the corresponding record type is not itself a protected operation.
543
544       if Is_Protected_Type (Scope (Scop))
545         and then not Is_Init_Proc (Scop)
546         and then Present (Protected_Formal (E))
547       then
548          Set_Entity (N, Protected_Formal (E));
549       end if;
550    end Expand_Formal;
551
552    ----------------------------
553    -- Expand_N_Expanded_Name --
554    ----------------------------
555
556    procedure Expand_N_Expanded_Name (N : Node_Id) is
557    begin
558       Expand_Entity_Reference (N);
559    end Expand_N_Expanded_Name;
560
561    -------------------------
562    -- Expand_N_Identifier --
563    -------------------------
564
565    procedure Expand_N_Identifier (N : Node_Id) is
566    begin
567       Expand_Entity_Reference (N);
568    end Expand_N_Identifier;
569
570    ---------------------------
571    -- Expand_N_Real_Literal --
572    ---------------------------
573
574    procedure Expand_N_Real_Literal (N : Node_Id) is
575    begin
576       if Vax_Float (Etype (N)) then
577          Expand_Vax_Real_Literal (N);
578       end if;
579    end Expand_N_Real_Literal;
580
581    --------------------------------
582    -- Expand_Protected_Component --
583    --------------------------------
584
585    procedure Expand_Protected_Component (N : Node_Id) is
586
587       function Inside_Eliminated_Body return Boolean;
588       --  Determine whether the current entity is inside a subprogram or an
589       --  entry which has been marked as eliminated.
590
591       ----------------------------
592       -- Inside_Eliminated_Body --
593       ----------------------------
594
595       function Inside_Eliminated_Body return Boolean is
596          S : Entity_Id := Current_Scope;
597
598       begin
599          while Present (S) loop
600             if (Ekind (S) = E_Entry
601                   or else Ekind (S) = E_Entry_Family
602                   or else Ekind (S) = E_Function
603                   or else Ekind (S) = E_Procedure)
604               and then Is_Eliminated (S)
605             then
606                return True;
607             end if;
608
609             S := Scope (S);
610          end loop;
611
612          return False;
613       end Inside_Eliminated_Body;
614
615    --  Start of processing for Expand_Protected_Component
616
617    begin
618       --  Eliminated bodies are not expanded and thus do not need privals
619
620       if not Inside_Eliminated_Body then
621          declare
622             Priv : constant Entity_Id := Prival (Entity (N));
623          begin
624             Set_Entity (N, Priv);
625             Set_Etype  (N, Etype (Priv));
626          end;
627       end if;
628    end Expand_Protected_Component;
629
630    ---------------------
631    -- Expand_Renaming --
632    ---------------------
633
634    procedure Expand_Renaming (N : Node_Id) is
635       E : constant Entity_Id := Entity (N);
636       T : constant Entity_Id := Etype (N);
637
638    begin
639       Rewrite (N, New_Copy_Tree (Renamed_Object (E)));
640
641       --  We mark the copy as unanalyzed, so that it is sure to be reanalyzed
642       --  at the top level. This is needed in the packed case since we
643       --  specifically avoided expanding packed array references when the
644       --  renaming declaration was analyzed.
645
646       Reset_Analyzed_Flags (N);
647       Analyze_And_Resolve (N, T);
648    end Expand_Renaming;
649
650    ------------------
651    -- Param_Entity --
652    ------------------
653
654    --  This would be trivial, simply a test for an identifier that was a
655    --  reference to a formal, if it were not for the fact that a previous call
656    --  to Expand_Entry_Parameter will have modified the reference to the
657    --  identifier. A formal of a protected entity is rewritten as
658
659    --    typ!(recobj).rec.all'Constrained
660
661    --  where rec is a selector whose Entry_Formal link points to the formal
662    --  For a formal of a task entity, the formal is rewritten as a local
663    --  renaming.
664
665    --  In addition, a formal that is marked volatile because it is aliased
666    --  through an address clause is rewritten as dereference as well.
667
668    function Param_Entity (N : Node_Id) return Entity_Id is
669       Renamed_Obj : Node_Id;
670
671    begin
672       --  Simple reference case
673
674       if Nkind_In (N, N_Identifier, N_Expanded_Name) then
675          if Is_Formal (Entity (N)) then
676             return Entity (N);
677
678          --  Handle renamings of formal parameters and formals of tasks that
679          --  are rewritten as renamings.
680
681          elsif Nkind (Parent (Entity (N))) = N_Object_Renaming_Declaration then
682             Renamed_Obj := Get_Referenced_Object (Renamed_Object (Entity (N)));
683
684             if Is_Entity_Name (Renamed_Obj)
685               and then Is_Formal (Entity (Renamed_Obj))
686             then
687                return Entity (Renamed_Obj);
688
689             elsif
690               Nkind (Parent (Parent (Entity (N)))) = N_Accept_Statement
691             then
692                return Entity (N);
693             end if;
694          end if;
695
696       else
697          if Nkind (N) = N_Explicit_Dereference then
698             declare
699                P : constant Node_Id := Prefix (N);
700                S : Node_Id;
701
702             begin
703                if Nkind (P) = N_Selected_Component then
704                   S := Selector_Name (P);
705
706                   if Present (Entry_Formal (Entity (S))) then
707                      return Entry_Formal (Entity (S));
708                   end if;
709
710                elsif Nkind (Original_Node (N)) = N_Identifier then
711                   return Param_Entity (Original_Node (N));
712                end if;
713             end;
714          end if;
715       end if;
716
717       return (Empty);
718    end Param_Entity;
719
720 end Exp_Ch2;