f50406f3d760fd46bea589d32de5ab8b0131d46d
[platform/upstream/gcc.git] / gcc / ada / lib-xref.adb
1 ------------------------------------------------------------------------------
2 --                                                                          --
3 --                         GNAT COMPILER COMPONENTS                         --
4 --                                                                          --
5 --                             L I B . X R E F                              --
6 --                                                                          --
7 --                                 B o d y                                  --
8 --                                                                          --
9 --          Copyright (C) 1998-2011, 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 Csets;    use Csets;
28 with Elists;   use Elists;
29 with Errout;   use Errout;
30 with Nlists;   use Nlists;
31 with Opt;      use Opt;
32 with Restrict; use Restrict;
33 with Rident;   use Rident;
34 with Sem;      use Sem;
35 with Sem_Aux;  use Sem_Aux;
36 with Sem_Prag; use Sem_Prag;
37 with Sem_Util; use Sem_Util;
38 with Sem_Warn; use Sem_Warn;
39 with Sinfo;    use Sinfo;
40 with Sinput;   use Sinput;
41 with Snames;   use Snames;
42 with Stringt;  use Stringt;
43 with Stand;    use Stand;
44 with Table;    use Table;
45
46 with GNAT.Heap_Sort_G;
47 with GNAT.HTable;
48
49 package body Lib.Xref is
50
51    ------------------
52    -- Declarations --
53    ------------------
54
55    --  The Xref table is used to record references. The Loc field is set
56    --  to No_Location for a definition entry.
57
58    subtype Xref_Entry_Number is Int;
59
60    type Xref_Key is record
61       --  These are the components of Xref_Entry that participate in hash
62       --  lookups.
63
64       Ent : Entity_Id;
65       --  Entity referenced (E parameter to Generate_Reference)
66
67       Loc : Source_Ptr;
68       --  Location of reference (Original_Location (Sloc field of N parameter
69       --  to Generate_Reference). Set to No_Location for the case of a
70       --  defining occurrence.
71
72       Typ : Character;
73       --  Reference type (Typ param to Generate_Reference)
74
75       Eun : Unit_Number_Type;
76       --  Unit number corresponding to Ent
77
78       Lun : Unit_Number_Type;
79       --  Unit number corresponding to Loc. Value is undefined and not
80       --  referenced if Loc is set to No_Location.
81
82       --  The following components are only used for Alfa cross-references
83
84       Ref_Scope : Entity_Id;
85       --  Entity of the closest subprogram or package enclosing the reference
86
87       Ent_Scope : Entity_Id;
88       --  Entity of the closest subprogram or package enclosing the definition,
89       --  which should be located in the same file as the definition itself.
90    end record;
91
92    type Xref_Entry is record
93       Key : Xref_Key;
94
95       Ent_Scope_File : Unit_Number_Type;
96       --  File for entity Ent_Scope
97
98       Def : Source_Ptr;
99       --  Original source location for entity being referenced. Note that these
100       --  values are used only during the output process, they are not set when
101       --  the entries are originally built. This is because private entities
102       --  can be swapped when the initial call is made.
103
104       HTable_Next : Xref_Entry_Number;
105       --  For use only by Static_HTable
106    end record;
107
108    package Xrefs is new Table.Table (
109      Table_Component_Type => Xref_Entry,
110      Table_Index_Type     => Xref_Entry_Number,
111      Table_Low_Bound      => 1,
112      Table_Initial        => Alloc.Xrefs_Initial,
113      Table_Increment      => Alloc.Xrefs_Increment,
114      Table_Name           => "Xrefs");
115
116    --------------
117    -- Xref_Set --
118    --------------
119
120    --  We keep a set of xref entries, in order to avoid inserting duplicate
121    --  entries into the above Xrefs table. An entry is in Xref_Set if and only
122    --  if it is in Xrefs.
123
124    Num_Buckets : constant := 2**16;
125
126    subtype Header_Num is Integer range 0 .. Num_Buckets - 1;
127    type Null_Type is null record;
128    pragma Unreferenced (Null_Type);
129
130    function Hash (F : Xref_Entry_Number) return Header_Num;
131
132    function Equal (F1, F2 : Xref_Entry_Number) return Boolean;
133
134    procedure HT_Set_Next (E : Xref_Entry_Number; Next : Xref_Entry_Number);
135
136    function  HT_Next (E : Xref_Entry_Number) return Xref_Entry_Number;
137
138    function Get_Key (E : Xref_Entry_Number) return Xref_Entry_Number;
139
140    pragma Inline (Hash, Equal, HT_Set_Next, HT_Next, Get_Key);
141
142    package Xref_Set is new GNAT.HTable.Static_HTable (
143      Header_Num,
144      Element    => Xref_Entry,
145      Elmt_Ptr   => Xref_Entry_Number,
146      Null_Ptr   => 0,
147      Set_Next   => HT_Set_Next,
148      Next       => HT_Next,
149      Key        => Xref_Entry_Number,
150      Get_Key    => Get_Key,
151      Hash       => Hash,
152      Equal      => Equal);
153
154    ----------------------
155    -- Alfa Information --
156    ----------------------
157
158    package body Alfa is separate;
159
160    ------------------------
161    --  Local Subprograms --
162    ------------------------
163
164    procedure Generate_Prim_Op_References (Typ : Entity_Id);
165    --  For a tagged type, generate implicit references to its primitive
166    --  operations, for source navigation. This is done right before emitting
167    --  cross-reference information rather than at the freeze point of the type
168    --  in order to handle late bodies that are primitive operations.
169
170    function Lt (T1, T2 : Xref_Entry) return Boolean;
171    --  Order cross-references
172
173    procedure Add_Entry (Key : Xref_Key; Ent_Scope_File : Unit_Number_Type);
174    --  Add an entry to the tables of Xref_Entries, avoiding duplicates
175
176    ---------------
177    -- Add_Entry --
178    ---------------
179
180    procedure Add_Entry (Key : Xref_Key; Ent_Scope_File : Unit_Number_Type) is
181    begin
182       Xrefs.Increment_Last; -- tentative
183       Xrefs.Table (Xrefs.Last).Key := Key;
184
185       --  Set the entry in Xref_Set, and if newly set, keep the above
186       --  tentative increment.
187
188       if Xref_Set.Set_If_Not_Present (Xrefs.Last) then
189          Xrefs.Table (Xrefs.Last).Ent_Scope_File := Ent_Scope_File;
190          --  Leave Def and HTable_Next uninitialized
191
192          Set_Has_Xref_Entry (Key.Ent);
193
194       --  It was already in Xref_Set, so throw away the tentatively-added
195       --  entry
196
197       else
198          Xrefs.Decrement_Last;
199       end if;
200    end Add_Entry;
201
202    -----------
203    -- Equal --
204    -----------
205
206    function Equal (F1, F2 : Xref_Entry_Number) return Boolean is
207       Result : constant Boolean :=
208                  Xrefs.Table (F1).Key = Xrefs.Table (F2).Key;
209    begin
210       return Result;
211    end Equal;
212
213    -------------------------
214    -- Generate_Definition --
215    -------------------------
216
217    procedure Generate_Definition (E : Entity_Id) is
218    begin
219       pragma Assert (Nkind (E) in N_Entity);
220
221       --  Note that we do not test Xref_Entity_Letters here. It is too early
222       --  to do so, since we are often called before the entity is fully
223       --  constructed, so that the Ekind is still E_Void.
224
225       if Opt.Xref_Active
226
227          --  Definition must come from source
228
229          --  We make an exception for subprogram child units that have no spec.
230          --  For these we generate a subprogram declaration for library use,
231          --  and the corresponding entity does not come from source.
232          --  Nevertheless, all references will be attached to it and we have
233          --  to treat is as coming from user code.
234
235          and then (Comes_From_Source (E) or else Is_Child_Unit (E))
236
237          --  And must have a reasonable source location that is not
238          --  within an instance (all entities in instances are ignored)
239
240          and then Sloc (E) > No_Location
241          and then Instantiation_Location (Sloc (E)) = No_Location
242
243          --  And must be a non-internal name from the main source unit
244
245          and then In_Extended_Main_Source_Unit (E)
246          and then not Is_Internal_Name (Chars (E))
247       then
248          Add_Entry
249            ((Ent => E,
250              Loc => No_Location,
251              Typ => ' ',
252              Eun => Get_Source_Unit (Original_Location (Sloc (E))),
253              Lun => No_Unit,
254              Ref_Scope => Empty,
255              Ent_Scope => Empty),
256             Ent_Scope_File => No_Unit);
257
258          if In_Inlined_Body then
259             Set_Referenced (E);
260          end if;
261       end if;
262    end Generate_Definition;
263
264    ---------------------------------
265    -- Generate_Operator_Reference --
266    ---------------------------------
267
268    procedure Generate_Operator_Reference
269      (N : Node_Id;
270       T : Entity_Id)
271    is
272    begin
273       if not In_Extended_Main_Source_Unit (N) then
274          return;
275       end if;
276
277       --  If the operator is not a Standard operator, then we generate a real
278       --  reference to the user defined operator.
279
280       if Sloc (Entity (N)) /= Standard_Location then
281          Generate_Reference (Entity (N), N);
282
283          --  A reference to an implicit inequality operator is also a reference
284          --  to the user-defined equality.
285
286          if Nkind (N) = N_Op_Ne
287            and then not Comes_From_Source (Entity (N))
288            and then Present (Corresponding_Equality (Entity (N)))
289          then
290             Generate_Reference (Corresponding_Equality (Entity (N)), N);
291          end if;
292
293       --  For the case of Standard operators, we mark the result type as
294       --  referenced. This ensures that in the case where we are using a
295       --  derived operator, we mark an entity of the unit that implicitly
296       --  defines this operator as used. Otherwise we may think that no entity
297       --  of the unit is used. The actual entity marked as referenced is the
298       --  first subtype, which is the relevant user defined entity.
299
300       --  Note: we only do this for operators that come from source. The
301       --  generated code sometimes reaches for entities that do not need to be
302       --  explicitly visible (for example, when we expand the code for
303       --  comparing two record objects, the fields of the record may not be
304       --  visible).
305
306       elsif Comes_From_Source (N) then
307          Set_Referenced (First_Subtype (T));
308       end if;
309    end Generate_Operator_Reference;
310
311    ---------------------------------
312    -- Generate_Prim_Op_References --
313    ---------------------------------
314
315    procedure Generate_Prim_Op_References (Typ : Entity_Id) is
316       Base_T    : Entity_Id;
317       Prim      : Elmt_Id;
318       Prim_List : Elist_Id;
319
320    begin
321       --  Handle subtypes of synchronized types
322
323       if Ekind (Typ) = E_Protected_Subtype
324         or else Ekind (Typ) = E_Task_Subtype
325       then
326          Base_T := Etype (Typ);
327       else
328          Base_T := Typ;
329       end if;
330
331       --  References to primitive operations are only relevant for tagged types
332
333       if not Is_Tagged_Type (Base_T)
334         or else Is_Class_Wide_Type (Base_T)
335       then
336          return;
337       end if;
338
339       --  Ada 2005 (AI-345): For synchronized types generate reference to the
340       --  wrapper that allow us to dispatch calls through their implemented
341       --  abstract interface types.
342
343       --  The check for Present here is to protect against previously reported
344       --  critical errors.
345
346       Prim_List := Primitive_Operations (Base_T);
347
348       if No (Prim_List) then
349          return;
350       end if;
351
352       Prim := First_Elmt (Prim_List);
353       while Present (Prim) loop
354
355          --  If the operation is derived, get the original for cross-reference
356          --  reference purposes (it is the original for which we want the xref
357          --  and for which the comes_from_source test must be performed).
358
359          Generate_Reference
360            (Typ, Ultimate_Alias (Node (Prim)), 'p', Set_Ref => False);
361          Next_Elmt (Prim);
362       end loop;
363    end Generate_Prim_Op_References;
364
365    ------------------------
366    -- Generate_Reference --
367    ------------------------
368
369    procedure Generate_Reference
370      (E       : Entity_Id;
371       N       : Node_Id;
372       Typ     : Character := 'r';
373       Set_Ref : Boolean   := True;
374       Force   : Boolean   := False)
375    is
376       Nod : Node_Id;
377       Ref : Source_Ptr;
378       Def : Source_Ptr;
379       Ent : Entity_Id;
380
381       Actual_Typ : Character := Typ;
382
383       Ref_Scope      : Entity_Id;
384       Ent_Scope      : Entity_Id;
385       Ent_Scope_File : Unit_Number_Type;
386
387       Call   : Node_Id;
388       Formal : Entity_Id;
389       --  Used for call to Find_Actual
390
391       Kind : Entity_Kind;
392       --  If Formal is non-Empty, then its Ekind, otherwise E_Void
393
394       function Get_Through_Renamings (E : Entity_Id) return Entity_Id;
395       --  Get the enclosing entity through renamings, which may come from
396       --  source or from the translation of generic instantiations.
397
398       function Is_On_LHS (Node : Node_Id) return Boolean;
399       --  Used to check if a node is on the left hand side of an assignment.
400       --  The following cases are handled:
401       --
402       --   Variable    Node is a direct descendant of left hand side of an
403       --               assignment statement.
404       --
405       --   Prefix      Of an indexed or selected component that is present in
406       --               a subtree rooted by an assignment statement. There is
407       --               no restriction of nesting of components, thus cases
408       --               such as A.B (C).D are handled properly. However a prefix
409       --               of a dereference (either implicit or explicit) is never
410       --               considered as on a LHS.
411       --
412       --   Out param   Same as above cases, but OUT parameter
413
414       function OK_To_Set_Referenced return Boolean;
415       --  Returns True if the Referenced flag can be set. There are a few
416       --  exceptions where we do not want to set this flag, see body for
417       --  details of these exceptional cases.
418
419       ---------------------------
420       -- Get_Through_Renamings --
421       ---------------------------
422
423       function Get_Through_Renamings (E : Entity_Id) return Entity_Id is
424          Result : Entity_Id := E;
425       begin
426          while Present (Result)
427            and then Is_Object (Result)
428            and then Present (Renamed_Object (Result))
429          loop
430             Result := Get_Enclosing_Object (Renamed_Object (Result));
431          end loop;
432          return Result;
433       end Get_Through_Renamings;
434
435       ---------------
436       -- Is_On_LHS --
437       ---------------
438
439       --  ??? There are several routines here and there that perform a similar
440       --      (but subtly different) computation, which should be factored:
441
442       --      Sem_Util.May_Be_Lvalue
443       --      Sem_Util.Known_To_Be_Assigned
444       --      Exp_Ch2.Expand_Entry_Parameter.In_Assignment_Context
445       --      Exp_Smem.Is_Out_Actual
446
447       function Is_On_LHS (Node : Node_Id) return Boolean is
448          N : Node_Id;
449          P : Node_Id;
450          K : Node_Kind;
451
452       begin
453          --  Only identifiers are considered, is this necessary???
454
455          if Nkind (Node) /= N_Identifier then
456             return False;
457          end if;
458
459          --  Immediate return if appeared as OUT parameter
460
461          if Kind = E_Out_Parameter then
462             return True;
463          end if;
464
465          --  Search for assignment statement subtree root
466
467          N := Node;
468          loop
469             P := Parent (N);
470             K := Nkind (P);
471
472             if K = N_Assignment_Statement then
473                return Name (P) = N;
474
475             --  Check whether the parent is a component and the current node is
476             --  its prefix, but return False if the current node has an access
477             --  type, as in that case the selected or indexed component is an
478             --  implicit dereference, and the LHS is the designated object, not
479             --  the access object.
480
481             --  ??? case of a slice assignment?
482
483             --  ??? Note that in some cases this is called too early
484             --  (see comments in Sem_Ch8.Find_Direct_Name), at a point where
485             --  the tree is not fully typed yet. In that case we may lack
486             --  an Etype for N, and we must disable the check for an implicit
487             --  dereference. If the dereference is on an LHS, this causes a
488             --  false positive.
489
490             elsif (K = N_Selected_Component or else K = N_Indexed_Component)
491               and then Prefix (P) = N
492               and then not (Present (Etype (N))
493                               and then
494                             Is_Access_Type (Etype (N)))
495             then
496                N := P;
497
498             --  All other cases, definitely not on left side
499
500             else
501                return False;
502             end if;
503          end loop;
504       end Is_On_LHS;
505
506       ---------------------------
507       -- OK_To_Set_Referenced --
508       ---------------------------
509
510       function OK_To_Set_Referenced return Boolean is
511          P : Node_Id;
512
513       begin
514          --  A reference from a pragma Unreferenced or pragma Unmodified or
515          --  pragma Warnings does not cause the Referenced flag to be set.
516          --  This avoids silly warnings about things being referenced and
517          --  not assigned when the only reference is from the pragma.
518
519          if Nkind (N) = N_Identifier then
520             P := Parent (N);
521
522             if Nkind (P) = N_Pragma_Argument_Association then
523                P := Parent (P);
524
525                if Nkind (P) = N_Pragma then
526                   if Pragma_Name (P) = Name_Warnings
527                        or else
528                      Pragma_Name (P) = Name_Unmodified
529                        or else
530                      Pragma_Name (P) = Name_Unreferenced
531                   then
532                      return False;
533                   end if;
534                end if;
535
536             --  A reference to a formal in a named parameter association does
537             --  not make the formal referenced. Formals that are unused in the
538             --  subprogram body are properly flagged as such, even if calls
539             --  elsewhere use named notation.
540
541             elsif Nkind (P) = N_Parameter_Association
542               and then N = Selector_Name (P)
543             then
544                return False;
545             end if;
546          end if;
547
548          return True;
549       end OK_To_Set_Referenced;
550
551    --  Start of processing for Generate_Reference
552
553    begin
554       pragma Assert (Nkind (E) in N_Entity);
555       Find_Actual (N, Formal, Call);
556
557       if Present (Formal) then
558          Kind := Ekind (Formal);
559       else
560          Kind := E_Void;
561       end if;
562
563       --  Check for obsolescent reference to package ASCII. GNAT treats this
564       --  element of annex J specially since in practice, programs make a lot
565       --  of use of this feature, so we don't include it in the set of features
566       --  diagnosed when Warn_On_Obsolescent_Features mode is set. However we
567       --  are required to note it as a violation of the RM defined restriction.
568
569       if E = Standard_ASCII then
570          Check_Restriction (No_Obsolescent_Features, N);
571       end if;
572
573       --  Check for reference to entity marked with Is_Obsolescent
574
575       --  Note that we always allow obsolescent references in the compiler
576       --  itself and the run time, since we assume that we know what we are
577       --  doing in such cases. For example the calls in Ada.Characters.Handling
578       --  to its own obsolescent subprograms are just fine.
579
580       --  In any case we do not generate warnings within the extended source
581       --  unit of the entity in question, since we assume the source unit
582       --  itself knows what is going on (and for sure we do not want silly
583       --  warnings, e.g. on the end line of an obsolescent procedure body).
584
585       if Is_Obsolescent (E)
586         and then not GNAT_Mode
587         and then not In_Extended_Main_Source_Unit (E)
588       then
589          Check_Restriction (No_Obsolescent_Features, N);
590
591          if Warn_On_Obsolescent_Feature then
592             Output_Obsolescent_Entity_Warnings (N, E);
593          end if;
594       end if;
595
596       --  Warn if reference to Ada 2005 entity not in Ada 2005 mode. We only
597       --  detect real explicit references (modifications and references).
598
599       if Comes_From_Source (N)
600         and then Is_Ada_2005_Only (E)
601         and then Ada_Version < Ada_2005
602         and then Warn_On_Ada_2005_Compatibility
603         and then (Typ = 'm' or else Typ = 'r' or else Typ = 's')
604       then
605          Error_Msg_NE ("& is only defined in Ada 2005?", N, E);
606       end if;
607
608       --  Warn if reference to Ada 2012 entity not in Ada 2012 mode. We only
609       --  detect real explicit references (modifications and references).
610
611       if Comes_From_Source (N)
612         and then Is_Ada_2012_Only (E)
613         and then Ada_Version < Ada_2012
614         and then Warn_On_Ada_2012_Compatibility
615         and then (Typ = 'm' or else Typ = 'r')
616       then
617          Error_Msg_NE ("& is only defined in Ada 2012?", N, E);
618       end if;
619
620       --  Never collect references if not in main source unit. However, we omit
621       --  this test if Typ is 'e' or 'k', since these entries are structural,
622       --  and it is useful to have them in units that reference packages as
623       --  well as units that define packages. We also omit the test for the
624       --  case of 'p' since we want to include inherited primitive operations
625       --  from other packages.
626
627       --  We also omit this test is this is a body reference for a subprogram
628       --  instantiation. In this case the reference is to the generic body,
629       --  which clearly need not be in the main unit containing the instance.
630       --  For the same reason we accept an implicit reference generated for
631       --  a default in an instance.
632
633       if not In_Extended_Main_Source_Unit (N) then
634          if Typ = 'e'
635            or else Typ = 'I'
636            or else Typ = 'p'
637            or else Typ = 'i'
638            or else Typ = 'k'
639            or else (Typ = 'b' and then Is_Generic_Instance (E))
640          then
641             null;
642          else
643             return;
644          end if;
645       end if;
646
647       --  For reference type p, the entity must be in main source unit
648
649       if Typ = 'p' and then not In_Extended_Main_Source_Unit (E) then
650          return;
651       end if;
652
653       --  Unless the reference is forced, we ignore references where the
654       --  reference itself does not come from source.
655
656       if not Force and then not Comes_From_Source (N) then
657          return;
658       end if;
659
660       --  Deal with setting entity as referenced, unless suppressed. Note that
661       --  we still do Set_Referenced on entities that do not come from source.
662       --  This situation arises when we have a source reference to a derived
663       --  operation, where the derived operation itself does not come from
664       --  source, but we still want to mark it as referenced, since we really
665       --  are referencing an entity in the corresponding package (this avoids
666       --  wrong complaints that the package contains no referenced entities).
667
668       if Set_Ref then
669
670          --  Assignable object appearing on left side of assignment or as
671          --  an out parameter.
672
673          if Is_Assignable (E)
674            and then Is_On_LHS (N)
675            and then Ekind (E) /= E_In_Out_Parameter
676          then
677             --  For objects that are renamings, just set as simply referenced
678             --  we do not try to do assignment type tracking in this case.
679
680             if Present (Renamed_Object (E)) then
681                Set_Referenced (E);
682
683             --  Out parameter case
684
685             elsif Kind = E_Out_Parameter then
686
687                --  If warning mode for all out parameters is set, or this is
688                --  the only warning parameter, then we want to mark this for
689                --  later warning logic by setting Referenced_As_Out_Parameter
690
691                if Warn_On_Modified_As_Out_Parameter (Formal) then
692                   Set_Referenced_As_Out_Parameter (E, True);
693                   Set_Referenced_As_LHS (E, False);
694
695                --  For OUT parameter not covered by the above cases, we simply
696                --  regard it as a normal reference (in this case we do not
697                --  want any of the warning machinery for out parameters).
698
699                else
700                   Set_Referenced (E);
701                end if;
702
703             --  For the left hand of an assignment case, we do nothing here.
704             --  The processing for Analyze_Assignment_Statement will set the
705             --  Referenced_As_LHS flag.
706
707             else
708                null;
709             end if;
710
711          --  Check for a reference in a pragma that should not count as a
712          --  making the variable referenced for warning purposes.
713
714          elsif Is_Non_Significant_Pragma_Reference (N) then
715             null;
716
717          --  A reference in an attribute definition clause does not count as a
718          --  reference except for the case of Address. The reason that 'Address
719          --  is an exception is that it creates an alias through which the
720          --  variable may be referenced.
721
722          elsif Nkind (Parent (N)) = N_Attribute_Definition_Clause
723            and then Chars (Parent (N)) /= Name_Address
724            and then N = Name (Parent (N))
725          then
726             null;
727
728          --  Constant completion does not count as a reference
729
730          elsif Typ = 'c'
731            and then Ekind (E) = E_Constant
732          then
733             null;
734
735          --  Record representation clause does not count as a reference
736
737          elsif Nkind (N) = N_Identifier
738            and then Nkind (Parent (N)) = N_Record_Representation_Clause
739          then
740             null;
741
742          --  Discriminants do not need to produce a reference to record type
743
744          elsif Typ = 'd'
745            and then Nkind (Parent (N)) = N_Discriminant_Specification
746          then
747             null;
748
749          --  All other cases
750
751          else
752             --  Special processing for IN OUT parameters, where we have an
753             --  implicit assignment to a simple variable.
754
755             if Kind = E_In_Out_Parameter
756               and then Is_Assignable (E)
757             then
758                --  For sure this counts as a normal read reference
759
760                Set_Referenced (E);
761                Set_Last_Assignment (E, Empty);
762
763                --  We count it as being referenced as an out parameter if the
764                --  option is set to warn on all out parameters, except that we
765                --  have a special exclusion for an intrinsic subprogram, which
766                --  is most likely an instantiation of Unchecked_Deallocation
767                --  which we do not want to consider as an assignment since it
768                --  generates false positives. We also exclude the case of an
769                --  IN OUT parameter if the name of the procedure is Free,
770                --  since we suspect similar semantics.
771
772                if Warn_On_All_Unread_Out_Parameters
773                  and then Is_Entity_Name (Name (Call))
774                  and then not Is_Intrinsic_Subprogram (Entity (Name (Call)))
775                  and then Chars (Name (Call)) /= Name_Free
776                then
777                   Set_Referenced_As_Out_Parameter (E, True);
778                   Set_Referenced_As_LHS (E, False);
779                end if;
780
781             --  Don't count a recursive reference within a subprogram as a
782             --  reference (that allows detection of a recursive subprogram
783             --  whose only references are recursive calls as unreferenced).
784
785             elsif Is_Subprogram (E)
786               and then E = Nearest_Dynamic_Scope (Current_Scope)
787             then
788                null;
789
790             --  Any other occurrence counts as referencing the entity
791
792             elsif OK_To_Set_Referenced then
793                Set_Referenced (E);
794
795                --  If variable, this is an OK reference after an assignment
796                --  so we can clear the Last_Assignment indication.
797
798                if Is_Assignable (E) then
799                   Set_Last_Assignment (E, Empty);
800                end if;
801             end if;
802          end if;
803
804          --  Check for pragma Unreferenced given and reference is within
805          --  this source unit (occasion for possible warning to be issued).
806
807          if Has_Unreferenced (E)
808            and then In_Same_Extended_Unit (E, N)
809          then
810             --  A reference as a named parameter in a call does not count
811             --  as a violation of pragma Unreferenced for this purpose...
812
813             if Nkind (N) = N_Identifier
814               and then Nkind (Parent (N)) = N_Parameter_Association
815               and then Selector_Name (Parent (N)) = N
816             then
817                null;
818
819             --  ... Neither does a reference to a variable on the left side
820             --  of an assignment.
821
822             elsif Is_On_LHS (N) then
823                null;
824
825             --  For entry formals, we want to place the warning message on the
826             --  corresponding entity in the accept statement. The current scope
827             --  is the body of the accept, so we find the formal whose name
828             --  matches that of the entry formal (there is no link between the
829             --  two entities, and the one in the accept statement is only used
830             --  for conformance checking).
831
832             elsif Ekind (Scope (E)) = E_Entry then
833                declare
834                   BE : Entity_Id;
835
836                begin
837                   BE := First_Entity (Current_Scope);
838                   while Present (BE) loop
839                      if Chars (BE) = Chars (E) then
840                         Error_Msg_NE -- CODEFIX
841                           ("?pragma Unreferenced given for&!", N, BE);
842                         exit;
843                      end if;
844
845                      Next_Entity (BE);
846                   end loop;
847                end;
848
849             --  Here we issue the warning, since this is a real reference
850
851             else
852                Error_Msg_NE -- CODEFIX
853                  ("?pragma Unreferenced given for&!", N, E);
854             end if;
855          end if;
856
857          --  If this is a subprogram instance, mark as well the internal
858          --  subprogram in the wrapper package, which may be a visible
859          --  compilation unit.
860
861          if Is_Overloadable (E)
862            and then Is_Generic_Instance (E)
863            and then Present (Alias (E))
864          then
865             Set_Referenced (Alias (E));
866          end if;
867       end if;
868
869       --  Generate reference if all conditions are met:
870
871       if
872          --  Cross referencing must be active
873
874          Opt.Xref_Active
875
876          --  The entity must be one for which we collect references
877
878          and then Xref_Entity_Letters (Ekind (E)) /= ' '
879
880          --  Both Sloc values must be set to something sensible
881
882          and then Sloc (E) > No_Location
883          and then Sloc (N) > No_Location
884
885          --  We ignore references from within an instance, except for default
886          --  subprograms, for which we generate an implicit reference.
887
888          and then
889            (Instantiation_Location (Sloc (N)) = No_Location or else Typ = 'i')
890
891          --  Ignore dummy references
892
893         and then Typ /= ' '
894       then
895          if Nkind (N) = N_Identifier
896               or else
897             Nkind (N) = N_Defining_Identifier
898               or else
899             Nkind (N) in N_Op
900               or else
901             Nkind (N) = N_Defining_Operator_Symbol
902               or else
903             Nkind (N) = N_Operator_Symbol
904               or else
905             (Nkind (N) = N_Character_Literal
906               and then Sloc (Entity (N)) /= Standard_Location)
907               or else
908             Nkind (N) = N_Defining_Character_Literal
909          then
910             Nod := N;
911
912          elsif Nkind (N) = N_Expanded_Name
913                  or else
914                Nkind (N) = N_Selected_Component
915          then
916             Nod := Selector_Name (N);
917
918          else
919             return;
920          end if;
921
922          --  Normal case of source entity comes from source
923
924          if Comes_From_Source (E) then
925             Ent := E;
926
927          --  Entity does not come from source, but is a derived subprogram and
928          --  the derived subprogram comes from source (after one or more
929          --  derivations) in which case the reference is to parent subprogram.
930
931          elsif Is_Overloadable (E)
932            and then Present (Alias (E))
933          then
934             Ent := Alias (E);
935             while not Comes_From_Source (Ent) loop
936                if No (Alias (Ent)) then
937                   return;
938                end if;
939
940                Ent := Alias (Ent);
941             end loop;
942
943          --  The internally created defining entity for a child subprogram
944          --  that has no previous spec has valid references.
945
946          elsif Is_Overloadable (E)
947            and then Is_Child_Unit (E)
948          then
949             Ent := E;
950
951          --  Record components of discriminated subtypes or derived types must
952          --  be treated as references to the original component.
953
954          elsif Ekind (E) = E_Component
955            and then Comes_From_Source (Original_Record_Component (E))
956          then
957             Ent := Original_Record_Component (E);
958
959          --  If this is an expanded reference to a discriminant, recover the
960          --  original discriminant, which gets the reference.
961
962          elsif Ekind (E) = E_In_Parameter
963            and then  Present (Discriminal_Link (E))
964          then
965             Ent := Discriminal_Link (E);
966             Set_Referenced (Ent);
967
968          --  Ignore reference to any other entity that is not from source
969
970          else
971             return;
972          end if;
973
974          --  In Alfa mode, consider the underlying entity renamed instead of
975          --  the renaming, which is needed to compute a valid set of effects
976          --  (reads, writes) for the enclosing subprogram.
977
978          if Alfa_Mode then
979             Ent := Get_Through_Renamings (Ent);
980
981             --  If no enclosing object, then it could be a reference to any
982             --  location not tracked individually, like heap-allocated data.
983             --  Conservatively approximate this possibility by generating a
984             --  dereference, and return.
985
986             if No (Ent) then
987                if Actual_Typ = 'w' then
988                   Alfa.Generate_Dereference (Nod, 'r');
989                   Alfa.Generate_Dereference (Nod, 'w');
990                else
991                   Alfa.Generate_Dereference (Nod, 'r');
992                end if;
993
994                return;
995             end if;
996          end if;
997
998          --  Record reference to entity
999
1000          Ref := Original_Location (Sloc (Nod));
1001          Def := Original_Location (Sloc (Ent));
1002
1003          if Actual_Typ = 'p'
1004            and then Is_Subprogram (N)
1005            and then Present (Overridden_Operation (N))
1006          then
1007             Actual_Typ := 'P';
1008          end if;
1009
1010          if Alfa_Mode then
1011             Ref_Scope := Alfa.Enclosing_Subprogram_Or_Package (N);
1012             Ent_Scope := Alfa.Enclosing_Subprogram_Or_Package (Ent);
1013             Ent_Scope_File := Get_Source_Unit (Ent_Scope);
1014
1015          else
1016             Ref_Scope := Empty;
1017             Ent_Scope := Empty;
1018             Ent_Scope_File := No_Unit;
1019          end if;
1020
1021          Add_Entry
1022            ((Ent => Ent,
1023              Loc => Ref,
1024              Typ => Actual_Typ,
1025              Eun => Get_Source_Unit (Def),
1026              Lun => Get_Source_Unit (Ref),
1027              Ref_Scope => Ref_Scope,
1028              Ent_Scope => Ent_Scope),
1029             Ent_Scope_File => Ent_Scope_File);
1030       end if;
1031    end Generate_Reference;
1032
1033    -----------------------------------
1034    -- Generate_Reference_To_Formals --
1035    -----------------------------------
1036
1037    procedure Generate_Reference_To_Formals (E : Entity_Id) is
1038       Formal : Entity_Id;
1039
1040    begin
1041       if Is_Generic_Subprogram (E) then
1042          Formal := First_Entity (E);
1043
1044          while Present (Formal)
1045            and then not Is_Formal (Formal)
1046          loop
1047             Next_Entity (Formal);
1048          end loop;
1049
1050       else
1051          Formal := First_Formal (E);
1052       end if;
1053
1054       while Present (Formal) loop
1055          if Ekind (Formal) = E_In_Parameter then
1056
1057             if Nkind (Parameter_Type (Parent (Formal)))
1058               = N_Access_Definition
1059             then
1060                Generate_Reference (E, Formal, '^', False);
1061             else
1062                Generate_Reference (E, Formal, '>', False);
1063             end if;
1064
1065          elsif Ekind (Formal) = E_In_Out_Parameter then
1066             Generate_Reference (E, Formal, '=', False);
1067
1068          else
1069             Generate_Reference (E, Formal, '<', False);
1070          end if;
1071
1072          Next_Formal (Formal);
1073       end loop;
1074    end Generate_Reference_To_Formals;
1075
1076    -------------------------------------------
1077    -- Generate_Reference_To_Generic_Formals --
1078    -------------------------------------------
1079
1080    procedure Generate_Reference_To_Generic_Formals (E : Entity_Id) is
1081       Formal : Entity_Id;
1082
1083    begin
1084       Formal := First_Entity (E);
1085       while Present (Formal) loop
1086          if Comes_From_Source (Formal) then
1087             Generate_Reference (E, Formal, 'z', False);
1088          end if;
1089
1090          Next_Entity (Formal);
1091       end loop;
1092    end Generate_Reference_To_Generic_Formals;
1093
1094    -------------
1095    -- Get_Key --
1096    -------------
1097
1098    function Get_Key (E : Xref_Entry_Number) return Xref_Entry_Number is
1099    begin
1100       return E;
1101    end Get_Key;
1102
1103    ----------
1104    -- Hash --
1105    ----------
1106
1107    function Hash (F : Xref_Entry_Number) return Header_Num is
1108       --  It is unlikely to have two references to the same entity at the same
1109       --  source location, so the hash function depends only on the Ent and Loc
1110       --  fields.
1111
1112       XE : Xref_Entry renames Xrefs.Table (F);
1113       type M is mod 2**32;
1114
1115       H : constant M := M (XE.Key.Ent) + 2 ** 7 * M (abs XE.Key.Loc);
1116       --  It would be more natural to write:
1117       --
1118       --    H : constant M := M'Mod (XE.Key.Ent) + 2**7 * M'Mod (XE.Key.Loc);
1119       --
1120       --  But we can't use M'Mod, because it prevents bootstrapping with older
1121       --  compilers. Loc can be negative, so we do "abs" before converting.
1122       --  One day this can be cleaned up ???
1123
1124    begin
1125       return Header_Num (H mod Num_Buckets);
1126    end Hash;
1127
1128    -----------------
1129    -- HT_Set_Next --
1130    -----------------
1131
1132    procedure HT_Set_Next (E : Xref_Entry_Number; Next : Xref_Entry_Number) is
1133    begin
1134       Xrefs.Table (E).HTable_Next := Next;
1135    end HT_Set_Next;
1136
1137    -------------
1138    -- HT_Next --
1139    -------------
1140
1141    function HT_Next (E : Xref_Entry_Number) return Xref_Entry_Number is
1142    begin
1143       return Xrefs.Table (E).HTable_Next;
1144    end HT_Next;
1145
1146    ----------------
1147    -- Initialize --
1148    ----------------
1149
1150    procedure Initialize is
1151    begin
1152       Xrefs.Init;
1153    end Initialize;
1154
1155    --------
1156    -- Lt --
1157    --------
1158
1159    function Lt (T1, T2 : Xref_Entry) return Boolean is
1160    begin
1161       --  First test: if entity is in different unit, sort by unit
1162
1163       if T1.Key.Eun /= T2.Key.Eun then
1164          return Dependency_Num (T1.Key.Eun) < Dependency_Num (T2.Key.Eun);
1165
1166       --  Second test: within same unit, sort by entity Sloc
1167
1168       elsif T1.Def /= T2.Def then
1169          return T1.Def < T2.Def;
1170
1171       --  Third test: sort definitions ahead of references
1172
1173       elsif T1.Key.Loc = No_Location then
1174          return True;
1175
1176       elsif T2.Key.Loc = No_Location then
1177          return False;
1178
1179       --  Fourth test: for same entity, sort by reference location unit
1180
1181       elsif T1.Key.Lun /= T2.Key.Lun then
1182          return Dependency_Num (T1.Key.Lun) < Dependency_Num (T2.Key.Lun);
1183
1184       --  Fifth test: order of location within referencing unit
1185
1186       elsif T1.Key.Loc /= T2.Key.Loc then
1187          return T1.Key.Loc < T2.Key.Loc;
1188
1189       --  Finally, for two locations at the same address, we prefer
1190       --  the one that does NOT have the type 'r' so that a modification
1191       --  or extension takes preference, when there are more than one
1192       --  reference at the same location. As a result, in the case of
1193       --  entities that are in-out actuals, the read reference follows
1194       --  the modify reference.
1195
1196       else
1197          return T2.Key.Typ = 'r';
1198       end if;
1199    end Lt;
1200
1201    -----------------------
1202    -- Output_References --
1203    -----------------------
1204
1205    procedure Output_References is
1206
1207       procedure Get_Type_Reference
1208         (Ent   : Entity_Id;
1209          Tref  : out Entity_Id;
1210          Left  : out Character;
1211          Right : out Character);
1212       --  Given an Entity_Id Ent, determines whether a type reference is
1213       --  required. If so, Tref is set to the entity for the type reference
1214       --  and Left and Right are set to the left/right brackets to be output
1215       --  for the reference. If no type reference is required, then Tref is
1216       --  set to Empty, and Left/Right are set to space.
1217
1218       procedure Output_Import_Export_Info (Ent : Entity_Id);
1219       --  Output language and external name information for an interfaced
1220       --  entity, using the format <language, external_name>.
1221
1222       ------------------------
1223       -- Get_Type_Reference --
1224       ------------------------
1225
1226       procedure Get_Type_Reference
1227         (Ent   : Entity_Id;
1228          Tref  : out Entity_Id;
1229          Left  : out Character;
1230          Right : out Character)
1231       is
1232          Sav : Entity_Id;
1233
1234       begin
1235          --  See if we have a type reference
1236
1237          Tref := Ent;
1238          Left := '{';
1239          Right := '}';
1240
1241          loop
1242             Sav := Tref;
1243
1244             --  Processing for types
1245
1246             if Is_Type (Tref) then
1247
1248                --  Case of base type
1249
1250                if Base_Type (Tref) = Tref then
1251
1252                   --  If derived, then get first subtype
1253
1254                   if Tref /= Etype (Tref) then
1255                      Tref := First_Subtype (Etype (Tref));
1256
1257                      --  Set brackets for derived type, but don't override
1258                      --  pointer case since the fact that something is a
1259                      --  pointer is more important.
1260
1261                      if Left /= '(' then
1262                         Left := '<';
1263                         Right := '>';
1264                      end if;
1265
1266                   --  If non-derived ptr, get directly designated type.
1267                   --  If the type has a full view, all references are on the
1268                   --  partial view, that is seen first.
1269
1270                   elsif Is_Access_Type (Tref) then
1271                      Tref := Directly_Designated_Type (Tref);
1272                      Left := '(';
1273                      Right := ')';
1274
1275                   elsif Is_Private_Type (Tref)
1276                     and then Present (Full_View (Tref))
1277                   then
1278                      if Is_Access_Type (Full_View (Tref)) then
1279                         Tref := Directly_Designated_Type (Full_View (Tref));
1280                         Left := '(';
1281                         Right := ')';
1282
1283                      --  If the full view is an array type, we also retrieve
1284                      --  the corresponding component type, because the ali
1285                      --  entry already indicates that this is an array.
1286
1287                      elsif Is_Array_Type (Full_View (Tref)) then
1288                         Tref := Component_Type (Full_View (Tref));
1289                         Left := '(';
1290                         Right := ')';
1291                      end if;
1292
1293                   --  If non-derived array, get component type. Skip component
1294                   --  type for case of String or Wide_String, saves worthwhile
1295                   --  space.
1296
1297                   elsif Is_Array_Type (Tref)
1298                     and then Tref /= Standard_String
1299                     and then Tref /= Standard_Wide_String
1300                   then
1301                      Tref := Component_Type (Tref);
1302                      Left := '(';
1303                      Right := ')';
1304
1305                   --  For other non-derived base types, nothing
1306
1307                   else
1308                      exit;
1309                   end if;
1310
1311                --  For a subtype, go to ancestor subtype
1312
1313                else
1314                   Tref := Ancestor_Subtype (Tref);
1315
1316                   --  If no ancestor subtype, go to base type
1317
1318                   if No (Tref) then
1319                      Tref := Base_Type (Sav);
1320                   end if;
1321                end if;
1322
1323             --  For objects, functions, enum literals, just get type from
1324             --  Etype field.
1325
1326             elsif Is_Object (Tref)
1327               or else Ekind (Tref) = E_Enumeration_Literal
1328               or else Ekind (Tref) = E_Function
1329               or else Ekind (Tref) = E_Operator
1330             then
1331                Tref := Etype (Tref);
1332
1333             --  For anything else, exit
1334
1335             else
1336                exit;
1337             end if;
1338
1339             --  Exit if no type reference, or we are stuck in some loop trying
1340             --  to find the type reference, or if the type is standard void
1341             --  type (the latter is an implementation artifact that should not
1342             --  show up in the generated cross-references).
1343
1344             exit when No (Tref)
1345               or else Tref = Sav
1346               or else Tref = Standard_Void_Type;
1347
1348             --  If we have a usable type reference, return, otherwise keep
1349             --  looking for something useful (we are looking for something
1350             --  that either comes from source or standard)
1351
1352             if Sloc (Tref) = Standard_Location
1353               or else Comes_From_Source (Tref)
1354             then
1355                --  If the reference is a subtype created for a generic actual,
1356                --  go actual directly, the inner subtype is not user visible.
1357
1358                if Nkind (Parent (Tref)) = N_Subtype_Declaration
1359                  and then not Comes_From_Source (Parent (Tref))
1360                  and then
1361                   (Is_Wrapper_Package (Scope (Tref))
1362                      or else Is_Generic_Instance (Scope (Tref)))
1363                then
1364                   Tref := First_Subtype (Base_Type (Tref));
1365                end if;
1366
1367                return;
1368             end if;
1369          end loop;
1370
1371          --  If we fall through the loop, no type reference
1372
1373          Tref := Empty;
1374          Left := ' ';
1375          Right := ' ';
1376       end Get_Type_Reference;
1377
1378       -------------------------------
1379       -- Output_Import_Export_Info --
1380       -------------------------------
1381
1382       procedure Output_Import_Export_Info (Ent : Entity_Id) is
1383          Language_Name : Name_Id;
1384          Conv          : constant Convention_Id := Convention (Ent);
1385
1386       begin
1387          --  Generate language name from convention
1388
1389          if Conv  = Convention_C then
1390             Language_Name := Name_C;
1391
1392          elsif Conv = Convention_CPP then
1393             Language_Name := Name_CPP;
1394
1395          elsif Conv = Convention_Ada then
1396             Language_Name := Name_Ada;
1397
1398          else
1399             --  For the moment we ignore all other cases ???
1400
1401             return;
1402          end if;
1403
1404          Write_Info_Char ('<');
1405          Get_Unqualified_Name_String (Language_Name);
1406
1407          for J in 1 .. Name_Len loop
1408             Write_Info_Char (Name_Buffer (J));
1409          end loop;
1410
1411          if Present (Interface_Name (Ent)) then
1412             Write_Info_Char (',');
1413             String_To_Name_Buffer (Strval (Interface_Name (Ent)));
1414
1415             for J in 1 .. Name_Len loop
1416                Write_Info_Char (Name_Buffer (J));
1417             end loop;
1418          end if;
1419
1420          Write_Info_Char ('>');
1421       end Output_Import_Export_Info;
1422
1423    --  Start of processing for Output_References
1424
1425    begin
1426       --  First we add references to the primitive operations of tagged types
1427       --  declared in the main unit.
1428
1429       Handle_Prim_Ops : declare
1430          Ent  : Entity_Id;
1431
1432       begin
1433          for J in 1 .. Xrefs.Last loop
1434             Ent := Xrefs.Table (J).Key.Ent;
1435
1436             if Is_Type (Ent)
1437               and then Is_Tagged_Type (Ent)
1438               and then Is_Base_Type (Ent)
1439               and then In_Extended_Main_Source_Unit (Ent)
1440             then
1441                Generate_Prim_Op_References (Ent);
1442             end if;
1443          end loop;
1444       end Handle_Prim_Ops;
1445
1446       --  Before we go ahead and output the references we have a problem
1447       --  that needs dealing with. So far we have captured things that are
1448       --  definitely referenced by the main unit, or defined in the main
1449       --  unit. That's because we don't want to clutter up the ali file
1450       --  for this unit with definition lines for entities in other units
1451       --  that are not referenced.
1452
1453       --  But there is a glitch. We may reference an entity in another unit,
1454       --  and it may have a type reference to an entity that is not directly
1455       --  referenced in the main unit, which may mean that there is no xref
1456       --  entry for this entity yet in the list of references.
1457
1458       --  If we don't do something about this, we will end with an orphan type
1459       --  reference, i.e. it will point to an entity that does not appear
1460       --  within the generated references in the ali file. That is not good for
1461       --  tools using the xref information.
1462
1463       --  To fix this, we go through the references adding definition entries
1464       --  for any unreferenced entities that can be referenced in a type
1465       --  reference. There is a recursion problem here, and that is dealt with
1466       --  by making sure that this traversal also traverses any entries that
1467       --  get added by the traversal.
1468
1469       Handle_Orphan_Type_References : declare
1470          J    : Nat;
1471          Tref : Entity_Id;
1472          Ent  : Entity_Id;
1473
1474          L, R : Character;
1475          pragma Warnings (Off, L);
1476          pragma Warnings (Off, R);
1477
1478          procedure New_Entry (E : Entity_Id);
1479          --  Make an additional entry into the Xref table for a type entity
1480          --  that is related to the current entity (parent, type ancestor,
1481          --  progenitor, etc.).
1482
1483          ----------------
1484          -- New_Entry --
1485          ----------------
1486
1487          procedure New_Entry (E : Entity_Id) is
1488          begin
1489             pragma Assert (Present (E));
1490
1491             if not Has_Xref_Entry (Implementation_Base_Type (E))
1492               and then Sloc (E) > No_Location
1493             then
1494                Add_Entry
1495                  ((Ent => E,
1496                    Loc => No_Location,
1497                    Typ => Character'First,
1498                    Eun => Get_Source_Unit (Original_Location (Sloc (E))),
1499                    Lun => No_Unit,
1500                    Ref_Scope => Empty,
1501                    Ent_Scope => Empty),
1502                   Ent_Scope_File => No_Unit);
1503             end if;
1504          end New_Entry;
1505
1506       --  Start of processing for Handle_Orphan_Type_References
1507
1508       begin
1509          --  Note that this is not a for loop for a very good reason. The
1510          --  processing of items in the table can add new items to the table,
1511          --  and they must be processed as well.
1512
1513          J := 1;
1514          while J <= Xrefs.Last loop
1515             Ent := Xrefs.Table (J).Key.Ent;
1516             Get_Type_Reference (Ent, Tref, L, R);
1517
1518             if Present (Tref)
1519               and then not Has_Xref_Entry (Tref)
1520               and then Sloc (Tref) > No_Location
1521             then
1522                New_Entry (Tref);
1523
1524                if Is_Record_Type (Ent)
1525                  and then Present (Interfaces (Ent))
1526                then
1527                   --  Add an entry for each one of the given interfaces
1528                   --  implemented by type Ent.
1529
1530                   declare
1531                      Elmt : Elmt_Id := First_Elmt (Interfaces (Ent));
1532                   begin
1533                      while Present (Elmt) loop
1534                         New_Entry (Node (Elmt));
1535                         Next_Elmt (Elmt);
1536                      end loop;
1537                   end;
1538                end if;
1539             end if;
1540
1541             --  Collect inherited primitive operations that may be declared in
1542             --  another unit and have no visible reference in the current one.
1543
1544             if Is_Type (Ent)
1545               and then Is_Tagged_Type (Ent)
1546               and then Is_Derived_Type (Ent)
1547               and then Is_Base_Type (Ent)
1548               and then In_Extended_Main_Source_Unit (Ent)
1549             then
1550                declare
1551                   Op_List : constant Elist_Id := Primitive_Operations (Ent);
1552                   Op      : Elmt_Id;
1553                   Prim    : Entity_Id;
1554
1555                   function Parent_Op (E : Entity_Id) return Entity_Id;
1556                   --  Find original operation, which may be inherited through
1557                   --  several derivations.
1558
1559                   function Parent_Op (E : Entity_Id) return Entity_Id is
1560                      Orig_Op : constant Entity_Id := Alias (E);
1561
1562                   begin
1563                      if No (Orig_Op) then
1564                         return Empty;
1565
1566                      elsif not Comes_From_Source (E)
1567                        and then not Has_Xref_Entry (Orig_Op)
1568                        and then Comes_From_Source (Orig_Op)
1569                      then
1570                         return Orig_Op;
1571                      else
1572                         return Parent_Op (Orig_Op);
1573                      end if;
1574                   end Parent_Op;
1575
1576                begin
1577                   Op := First_Elmt (Op_List);
1578                   while Present (Op) loop
1579                      Prim := Parent_Op (Node (Op));
1580
1581                      if Present (Prim) then
1582                         Add_Entry
1583                           ((Ent => Prim,
1584                             Loc => No_Location,
1585                             Typ => Character'First,
1586                             Eun => Get_Source_Unit (Sloc (Prim)),
1587                             Lun => No_Unit,
1588                             Ref_Scope => Empty,
1589                             Ent_Scope => Empty),
1590                            Ent_Scope_File => No_Unit);
1591                      end if;
1592
1593                      Next_Elmt (Op);
1594                   end loop;
1595                end;
1596             end if;
1597
1598             J := J + 1;
1599          end loop;
1600       end Handle_Orphan_Type_References;
1601
1602       --  Now we have all the references, including those for any embedded
1603       --  type references, so we can sort them, and output them.
1604
1605       Output_Refs : declare
1606
1607          Nrefs : constant Nat := Xrefs.Last;
1608          --  Number of references in table
1609
1610          Rnums : array (0 .. Nrefs) of Nat;
1611          --  This array contains numbers of references in the Xrefs table.
1612          --  This list is sorted in output order. The extra 0'th entry is
1613          --  convenient for the call to sort. When we sort the table, we
1614          --  move the entries in Rnums around, but we do not move the
1615          --  original table entries.
1616
1617          Curxu : Unit_Number_Type;
1618          --  Current xref unit
1619
1620          Curru : Unit_Number_Type;
1621          --  Current reference unit for one entity
1622
1623          Curent : Entity_Id;
1624          --  Current entity
1625
1626          Curnam : String (1 .. Name_Buffer'Length);
1627          Curlen : Natural;
1628          --  Simple name and length of current entity
1629
1630          Curdef : Source_Ptr;
1631          --  Original source location for current entity
1632
1633          Crloc : Source_Ptr;
1634          --  Current reference location
1635
1636          Ctyp : Character;
1637          --  Entity type character
1638
1639          Prevt : Character;
1640          --  reference kind of previous reference
1641
1642          Tref : Entity_Id;
1643          --  Type reference
1644
1645          Rref : Node_Id;
1646          --  Renaming reference
1647
1648          Trunit : Unit_Number_Type;
1649          --  Unit number for type reference
1650
1651          function Lt (Op1, Op2 : Natural) return Boolean;
1652          --  Comparison function for Sort call
1653
1654          function Name_Change (X : Entity_Id) return Boolean;
1655          --  Determines if entity X has a different simple name from Curent
1656
1657          procedure Move (From : Natural; To : Natural);
1658          --  Move procedure for Sort call
1659
1660          package Sorting is new GNAT.Heap_Sort_G (Move, Lt);
1661
1662          --------
1663          -- Lt --
1664          --------
1665
1666          function Lt (Op1, Op2 : Natural) return Boolean is
1667             T1 : Xref_Entry renames Xrefs.Table (Rnums (Nat (Op1)));
1668             T2 : Xref_Entry renames Xrefs.Table (Rnums (Nat (Op2)));
1669
1670          begin
1671             return Lt (T1, T2);
1672          end Lt;
1673
1674          ----------
1675          -- Move --
1676          ----------
1677
1678          procedure Move (From : Natural; To : Natural) is
1679          begin
1680             Rnums (Nat (To)) := Rnums (Nat (From));
1681          end Move;
1682
1683          -----------------
1684          -- Name_Change --
1685          -----------------
1686
1687          --  Why a string comparison here??? Why not compare Name_Id values???
1688
1689          function Name_Change (X : Entity_Id) return Boolean is
1690          begin
1691             Get_Unqualified_Name_String (Chars (X));
1692
1693             if Name_Len /= Curlen then
1694                return True;
1695             else
1696                return Name_Buffer (1 .. Curlen) /= Curnam (1 .. Curlen);
1697             end if;
1698          end Name_Change;
1699
1700       --  Start of processing for Output_Refs
1701
1702       begin
1703          --  Capture the definition Sloc values. We delay doing this till now,
1704          --  since at the time the reference or definition is made, private
1705          --  types may be swapped, and the Sloc value may be incorrect. We
1706          --  also set up the pointer vector for the sort.
1707
1708          for J in 1 .. Nrefs loop
1709             Rnums (J) := J;
1710             Xrefs.Table (J).Def :=
1711               Original_Location (Sloc (Xrefs.Table (J).Key.Ent));
1712          end loop;
1713
1714          --  Sort the references
1715
1716          Sorting.Sort (Integer (Nrefs));
1717
1718          --  Initialize loop through references
1719
1720          Curxu  := No_Unit;
1721          Curent := Empty;
1722          Curdef := No_Location;
1723          Curru  := No_Unit;
1724          Crloc  := No_Location;
1725          Prevt  := 'm';
1726
1727          --  Loop to output references
1728
1729          for Refno in 1 .. Nrefs loop
1730             Output_One_Ref : declare
1731                Ent : Entity_Id;
1732
1733                XE : Xref_Entry renames Xrefs.Table (Rnums (Refno));
1734                --  The current entry to be accessed
1735
1736                Left  : Character;
1737                Right : Character;
1738                --  Used for {} or <> or () for type reference
1739
1740                procedure Check_Type_Reference
1741                  (Ent            : Entity_Id;
1742                   List_Interface : Boolean);
1743                --  Find whether there is a meaningful type reference for
1744                --  Ent, and display it accordingly. If List_Interface is
1745                --  true, then Ent is a progenitor interface of the current
1746                --  type entity being listed. In that case list it as is,
1747                --  without looking for a type reference for it.
1748
1749                procedure Output_Instantiation_Refs (Loc : Source_Ptr);
1750                --  Recursive procedure to output instantiation references for
1751                --  the given source ptr in [file|line[...]] form. No output
1752                --  if the given location is not a generic template reference.
1753
1754                procedure Output_Overridden_Op (Old_E : Entity_Id);
1755                --  For a subprogram that is overriding, display information
1756                --  about the inherited operation that it overrides.
1757
1758                --------------------------
1759                -- Check_Type_Reference --
1760                --------------------------
1761
1762                procedure Check_Type_Reference
1763                  (Ent            : Entity_Id;
1764                   List_Interface : Boolean)
1765                is
1766                begin
1767                   if List_Interface then
1768
1769                      --  This is a progenitor interface of the type for which
1770                      --  xref information is being generated.
1771
1772                      Tref  := Ent;
1773                      Left  := '<';
1774                      Right := '>';
1775
1776                   else
1777                      Get_Type_Reference (Ent, Tref, Left, Right);
1778                   end if;
1779
1780                   if Present (Tref) then
1781
1782                      --  Case of standard entity, output name
1783
1784                      if Sloc (Tref) = Standard_Location then
1785                         Write_Info_Char (Left);
1786                         Write_Info_Name (Chars (Tref));
1787                         Write_Info_Char (Right);
1788
1789                      --  Case of source entity, output location
1790
1791                      else
1792                         Write_Info_Char (Left);
1793                         Trunit := Get_Source_Unit (Sloc (Tref));
1794
1795                         if Trunit /= Curxu then
1796                            Write_Info_Nat (Dependency_Num (Trunit));
1797                            Write_Info_Char ('|');
1798                         end if;
1799
1800                         Write_Info_Nat
1801                           (Int (Get_Logical_Line_Number (Sloc (Tref))));
1802
1803                         declare
1804                            Ent  : Entity_Id;
1805                            Ctyp : Character;
1806
1807                         begin
1808                            Ent := Tref;
1809                            Ctyp := Xref_Entity_Letters (Ekind (Ent));
1810
1811                            if Ctyp = '+'
1812                              and then Present (Full_View (Ent))
1813                            then
1814                               Ent := Underlying_Type (Ent);
1815
1816                               if Present (Ent) then
1817                                  Ctyp := Xref_Entity_Letters (Ekind (Ent));
1818                               end if;
1819                            end if;
1820
1821                            Write_Info_Char (Ctyp);
1822                         end;
1823
1824                         Write_Info_Nat
1825                           (Int (Get_Column_Number (Sloc (Tref))));
1826
1827                         --  If the type comes from an instantiation, add the
1828                         --  corresponding info.
1829
1830                         Output_Instantiation_Refs (Sloc (Tref));
1831                         Write_Info_Char (Right);
1832                      end if;
1833                   end if;
1834                end Check_Type_Reference;
1835
1836                -------------------------------
1837                -- Output_Instantiation_Refs --
1838                -------------------------------
1839
1840                procedure Output_Instantiation_Refs (Loc : Source_Ptr) is
1841                   Iloc : constant Source_Ptr := Instantiation_Location (Loc);
1842                   Lun  : Unit_Number_Type;
1843                   Cu   : constant Unit_Number_Type := Curru;
1844
1845                begin
1846                   --  Nothing to do if this is not an instantiation
1847
1848                   if Iloc = No_Location then
1849                      return;
1850                   end if;
1851
1852                   --  Output instantiation reference
1853
1854                   Write_Info_Char ('[');
1855                   Lun := Get_Source_Unit (Iloc);
1856
1857                   if Lun /= Curru then
1858                      Curru := Lun;
1859                      Write_Info_Nat (Dependency_Num (Curru));
1860                      Write_Info_Char ('|');
1861                   end if;
1862
1863                   Write_Info_Nat (Int (Get_Logical_Line_Number (Iloc)));
1864
1865                   --  Recursive call to get nested instantiations
1866
1867                   Output_Instantiation_Refs (Iloc);
1868
1869                   --  Output final ] after call to get proper nesting
1870
1871                   Write_Info_Char (']');
1872                   Curru := Cu;
1873                   return;
1874                end Output_Instantiation_Refs;
1875
1876                --------------------------
1877                -- Output_Overridden_Op --
1878                --------------------------
1879
1880                procedure Output_Overridden_Op (Old_E : Entity_Id) is
1881                   Op : Entity_Id;
1882
1883                begin
1884                   --  The overridden operation has an implicit declaration
1885                   --  at the point of derivation. What we want to display
1886                   --  is the original operation, which has the actual body
1887                   --  (or abstract declaration) that is being overridden.
1888                   --  The overridden operation is not always set, e.g. when
1889                   --  it is a predefined operator.
1890
1891                   if No (Old_E) then
1892                      return;
1893
1894                   --  Follow alias chain if one is present
1895
1896                   elsif Present (Alias (Old_E)) then
1897
1898                      --  The subprogram may have been implicitly inherited
1899                      --  through several levels of derivation, so find the
1900                      --  ultimate (source) ancestor.
1901
1902                      Op := Ultimate_Alias (Old_E);
1903
1904                   --  Normal case of no alias present
1905
1906                   else
1907                      Op := Old_E;
1908                   end if;
1909
1910                   if Present (Op)
1911                     and then Sloc (Op) /= Standard_Location
1912                   then
1913                      declare
1914                         Loc      : constant Source_Ptr := Sloc (Op);
1915                         Par_Unit : constant Unit_Number_Type :=
1916                                      Get_Source_Unit (Loc);
1917
1918                      begin
1919                         Write_Info_Char ('<');
1920
1921                         if Par_Unit /= Curxu then
1922                            Write_Info_Nat (Dependency_Num (Par_Unit));
1923                            Write_Info_Char ('|');
1924                         end if;
1925
1926                         Write_Info_Nat (Int (Get_Logical_Line_Number (Loc)));
1927                         Write_Info_Char ('p');
1928                         Write_Info_Nat (Int (Get_Column_Number (Loc)));
1929                         Write_Info_Char ('>');
1930                      end;
1931                   end if;
1932                end Output_Overridden_Op;
1933
1934             --  Start of processing for Output_One_Ref
1935
1936             begin
1937                Ent := XE.Key.Ent;
1938                Ctyp := Xref_Entity_Letters (Ekind (Ent));
1939
1940                --  Skip reference if it is the only reference to an entity,
1941                --  and it is an END line reference, and the entity is not in
1942                --  the current extended source. This prevents junk entries
1943                --  consisting only of packages with END lines, where no
1944                --  entity from the package is actually referenced.
1945
1946                if XE.Key.Typ = 'e'
1947                  and then Ent /= Curent
1948                  and then (Refno = Nrefs
1949                             or else
1950                               Ent /= Xrefs.Table (Rnums (Refno + 1)).Key.Ent)
1951                  and then not In_Extended_Main_Source_Unit (Ent)
1952                then
1953                   goto Continue;
1954                end if;
1955
1956                --  For private type, get full view type
1957
1958                if Ctyp = '+'
1959                  and then Present (Full_View (XE.Key.Ent))
1960                then
1961                   Ent := Underlying_Type (Ent);
1962
1963                   if Present (Ent) then
1964                      Ctyp := Xref_Entity_Letters (Ekind (Ent));
1965                   end if;
1966                end if;
1967
1968                --  Special exception for Boolean
1969
1970                if Ctyp = 'E' and then Is_Boolean_Type (Ent) then
1971                   Ctyp := 'B';
1972                end if;
1973
1974                --  For variable reference, get corresponding type
1975
1976                if Ctyp = '*' then
1977                   Ent := Etype (XE.Key.Ent);
1978                   Ctyp := Fold_Lower (Xref_Entity_Letters (Ekind (Ent)));
1979
1980                   --  If variable is private type, get full view type
1981
1982                   if Ctyp = '+'
1983                     and then Present (Full_View (Etype (XE.Key.Ent)))
1984                   then
1985                      Ent := Underlying_Type (Etype (XE.Key.Ent));
1986
1987                      if Present (Ent) then
1988                         Ctyp := Fold_Lower (Xref_Entity_Letters (Ekind (Ent)));
1989                      end if;
1990
1991                   elsif Is_Generic_Type (Ent) then
1992
1993                      --  If the type of the entity is a generic private type,
1994                      --  there is no usable full view, so retain the indication
1995                      --  that this is an object.
1996
1997                      Ctyp := '*';
1998                   end if;
1999
2000                   --  Special handling for access parameters and objects of
2001                   --  an anonymous access type.
2002
2003                   if Ekind_In (Etype (XE.Key.Ent),
2004                                E_Anonymous_Access_Type,
2005                                E_Anonymous_Access_Subprogram_Type,
2006                                E_Anonymous_Access_Protected_Subprogram_Type)
2007                   then
2008                      if Is_Formal (XE.Key.Ent)
2009                        or else Ekind_In (XE.Key.Ent, E_Variable, E_Constant)
2010                      then
2011                         Ctyp := 'p';
2012                      end if;
2013
2014                      --  Special handling for Boolean
2015
2016                   elsif Ctyp = 'e' and then Is_Boolean_Type (Ent) then
2017                      Ctyp := 'b';
2018                   end if;
2019                end if;
2020
2021                --  Special handling for abstract types and operations
2022
2023                if Is_Overloadable (XE.Key.Ent)
2024                  and then Is_Abstract_Subprogram (XE.Key.Ent)
2025                then
2026                   if Ctyp = 'U' then
2027                      Ctyp := 'x';            --  Abstract procedure
2028
2029                   elsif Ctyp = 'V' then
2030                      Ctyp := 'y';            --  Abstract function
2031                   end if;
2032
2033                elsif Is_Type (XE.Key.Ent)
2034                  and then Is_Abstract_Type (XE.Key.Ent)
2035                then
2036                   if Is_Interface (XE.Key.Ent) then
2037                      Ctyp := 'h';
2038
2039                   elsif Ctyp = 'R' then
2040                      Ctyp := 'H';            --  Abstract type
2041                   end if;
2042                end if;
2043
2044                --  Only output reference if interesting type of entity
2045
2046                if Ctyp = ' '
2047
2048                --  Suppress references to object definitions, used for local
2049                --  references.
2050
2051                  or else XE.Key.Typ = 'D'
2052                  or else XE.Key.Typ = 'I'
2053
2054                --  Suppress self references, except for bodies that act as
2055                --  specs.
2056
2057                  or else (XE.Key.Loc = XE.Def
2058                            and then
2059                              (XE.Key.Typ /= 'b'
2060                                or else not Is_Subprogram (XE.Key.Ent)))
2061
2062                --  Also suppress definitions of body formals (we only
2063                --  treat these as references, and the references were
2064                --  separately recorded).
2065
2066                  or else (Is_Formal (XE.Key.Ent)
2067                            and then Present (Spec_Entity (XE.Key.Ent)))
2068                then
2069                   null;
2070
2071                else
2072                   --  Start new Xref section if new xref unit
2073
2074                   if XE.Key.Eun /= Curxu then
2075                      if Write_Info_Col > 1 then
2076                         Write_Info_EOL;
2077                      end if;
2078
2079                      Curxu := XE.Key.Eun;
2080
2081                      Write_Info_Initiate ('X');
2082                      Write_Info_Char (' ');
2083                      Write_Info_Nat (Dependency_Num (XE.Key.Eun));
2084                      Write_Info_Char (' ');
2085                      Write_Info_Name
2086                        (Reference_Name (Source_Index (XE.Key.Eun)));
2087                   end if;
2088
2089                   --  Start new Entity line if new entity. Note that we
2090                   --  consider two entities the same if they have the same
2091                   --  name and source location. This causes entities in
2092                   --  instantiations to be treated as though they referred
2093                   --  to the template.
2094
2095                   if No (Curent)
2096                     or else
2097                       (XE.Key.Ent /= Curent
2098                          and then
2099                            (Name_Change (XE.Key.Ent) or else XE.Def /= Curdef))
2100                   then
2101                      Curent := XE.Key.Ent;
2102                      Curdef := XE.Def;
2103
2104                      Get_Unqualified_Name_String (Chars (XE.Key.Ent));
2105                      Curlen := Name_Len;
2106                      Curnam (1 .. Curlen) := Name_Buffer (1 .. Curlen);
2107
2108                      if Write_Info_Col > 1 then
2109                         Write_Info_EOL;
2110                      end if;
2111
2112                      --  Write column number information
2113
2114                      Write_Info_Nat (Int (Get_Logical_Line_Number (XE.Def)));
2115                      Write_Info_Char (Ctyp);
2116                      Write_Info_Nat (Int (Get_Column_Number (XE.Def)));
2117
2118                      --  Write level information
2119
2120                      Write_Level_Info : declare
2121                         function Is_Visible_Generic_Entity
2122                           (E : Entity_Id) return Boolean;
2123                         --  Check whether E is declared in the visible part
2124                         --  of a generic package. For source navigation
2125                         --  purposes, treat this as a visible entity.
2126
2127                         function Is_Private_Record_Component
2128                           (E : Entity_Id) return Boolean;
2129                         --  Check whether E is a non-inherited component of a
2130                         --  private extension. Even if the enclosing record is
2131                         --  public, we want to treat the component as private
2132                         --  for navigation purposes.
2133
2134                         ---------------------------------
2135                         -- Is_Private_Record_Component --
2136                         ---------------------------------
2137
2138                         function Is_Private_Record_Component
2139                           (E : Entity_Id) return Boolean
2140                         is
2141                            S : constant Entity_Id := Scope (E);
2142                         begin
2143                            return
2144                              Ekind (E) = E_Component
2145                                and then Nkind (Declaration_Node (S)) =
2146                                  N_Private_Extension_Declaration
2147                                and then Original_Record_Component (E) = E;
2148                         end Is_Private_Record_Component;
2149
2150                         -------------------------------
2151                         -- Is_Visible_Generic_Entity --
2152                         -------------------------------
2153
2154                         function Is_Visible_Generic_Entity
2155                           (E : Entity_Id) return Boolean
2156                         is
2157                            Par : Node_Id;
2158
2159                         begin
2160                            --  The Present check here is an error defense
2161
2162                            if Present (Scope (E))
2163                              and then Ekind (Scope (E)) /= E_Generic_Package
2164                            then
2165                               return False;
2166                            end if;
2167
2168                            Par := Parent (E);
2169                            while Present (Par) loop
2170                               if
2171                                 Nkind (Par) = N_Generic_Package_Declaration
2172                               then
2173                                  --  Entity is a generic formal
2174
2175                                  return False;
2176
2177                               elsif
2178                                 Nkind (Parent (Par)) = N_Package_Specification
2179                               then
2180                                  return
2181                                    Is_List_Member (Par)
2182                                      and then List_Containing (Par) =
2183                                        Visible_Declarations (Parent (Par));
2184                               else
2185                                  Par := Parent (Par);
2186                               end if;
2187                            end loop;
2188
2189                            return False;
2190                         end Is_Visible_Generic_Entity;
2191
2192                      --  Start of processing for Write_Level_Info
2193
2194                      begin
2195                         if Is_Hidden (Curent)
2196                           or else Is_Private_Record_Component (Curent)
2197                         then
2198                            Write_Info_Char (' ');
2199
2200                         elsif
2201                            Is_Public (Curent)
2202                              or else Is_Visible_Generic_Entity (Curent)
2203                         then
2204                            Write_Info_Char ('*');
2205
2206                         else
2207                            Write_Info_Char (' ');
2208                         end if;
2209                      end Write_Level_Info;
2210
2211                      --  Output entity name. We use the occurrence from the
2212                      --  actual source program at the definition point.
2213
2214                      declare
2215                         Ent_Name : constant String :=
2216                                      Exact_Source_Name (Sloc (XE.Key.Ent));
2217                      begin
2218                         for C in Ent_Name'Range loop
2219                            Write_Info_Char (Ent_Name (C));
2220                         end loop;
2221                      end;
2222
2223                      --  See if we have a renaming reference
2224
2225                      if Is_Object (XE.Key.Ent)
2226                        and then Present (Renamed_Object (XE.Key.Ent))
2227                      then
2228                         Rref := Renamed_Object (XE.Key.Ent);
2229
2230                      elsif Is_Overloadable (XE.Key.Ent)
2231                        and then Nkind (Parent (Declaration_Node (XE.Key.Ent)))
2232                                            = N_Subprogram_Renaming_Declaration
2233                      then
2234                         Rref := Name (Parent (Declaration_Node (XE.Key.Ent)));
2235
2236                      elsif Ekind (XE.Key.Ent) = E_Package
2237                        and then Nkind (Declaration_Node (XE.Key.Ent)) =
2238                                          N_Package_Renaming_Declaration
2239                      then
2240                         Rref := Name (Declaration_Node (XE.Key.Ent));
2241
2242                      else
2243                         Rref := Empty;
2244                      end if;
2245
2246                      if Present (Rref) then
2247                         if Nkind (Rref) = N_Expanded_Name then
2248                            Rref := Selector_Name (Rref);
2249                         end if;
2250
2251                         if Nkind (Rref) = N_Identifier
2252                           or else Nkind (Rref) = N_Operator_Symbol
2253                         then
2254                            null;
2255
2256                         --  For renamed array components, use the array name
2257                         --  for the renamed entity, which reflect the fact that
2258                         --  in general the whole array is aliased.
2259
2260                         elsif Nkind (Rref) = N_Indexed_Component then
2261                            if Nkind (Prefix (Rref)) = N_Identifier then
2262                               Rref := Prefix (Rref);
2263                            elsif Nkind (Prefix (Rref)) = N_Expanded_Name then
2264                               Rref := Selector_Name (Prefix (Rref));
2265                            else
2266                               Rref := Empty;
2267                            end if;
2268
2269                         else
2270                            Rref := Empty;
2271                         end if;
2272                      end if;
2273
2274                      --  Write out renaming reference if we have one
2275
2276                      if Present (Rref) then
2277                         Write_Info_Char ('=');
2278                         Write_Info_Nat
2279                           (Int (Get_Logical_Line_Number (Sloc (Rref))));
2280                         Write_Info_Char (':');
2281                         Write_Info_Nat
2282                           (Int (Get_Column_Number (Sloc (Rref))));
2283                      end if;
2284
2285                      --  Indicate that the entity is in the unit of the current
2286                      --  xref section.
2287
2288                      Curru := Curxu;
2289
2290                      --  Write out information about generic parent, if entity
2291                      --  is an instance.
2292
2293                      if  Is_Generic_Instance (XE.Key.Ent) then
2294                         declare
2295                            Gen_Par : constant Entity_Id :=
2296                                        Generic_Parent
2297                                          (Specification
2298                                             (Unit_Declaration_Node
2299                                                (XE.Key.Ent)));
2300                            Loc     : constant Source_Ptr := Sloc (Gen_Par);
2301                            Gen_U   : constant Unit_Number_Type :=
2302                                        Get_Source_Unit (Loc);
2303
2304                         begin
2305                            Write_Info_Char ('[');
2306
2307                            if Curru /= Gen_U then
2308                               Write_Info_Nat (Dependency_Num (Gen_U));
2309                               Write_Info_Char ('|');
2310                            end if;
2311
2312                            Write_Info_Nat
2313                              (Int (Get_Logical_Line_Number (Loc)));
2314                            Write_Info_Char (']');
2315                         end;
2316                      end if;
2317
2318                      --  See if we have a type reference and if so output
2319
2320                      Check_Type_Reference (XE.Key.Ent, False);
2321
2322                      --  Additional information for types with progenitors
2323
2324                      if Is_Record_Type (XE.Key.Ent)
2325                        and then Present (Interfaces (XE.Key.Ent))
2326                      then
2327                         declare
2328                            Elmt : Elmt_Id :=
2329                                     First_Elmt (Interfaces (XE.Key.Ent));
2330                         begin
2331                            while Present (Elmt) loop
2332                               Check_Type_Reference (Node (Elmt), True);
2333                               Next_Elmt (Elmt);
2334                            end loop;
2335                         end;
2336
2337                      --  For array types, list index types as well. (This is
2338                      --  not C, indexes have distinct types).
2339
2340                      elsif Is_Array_Type (XE.Key.Ent) then
2341                         declare
2342                            Indx : Node_Id;
2343                         begin
2344                            Indx := First_Index (XE.Key.Ent);
2345                            while Present (Indx) loop
2346                               Check_Type_Reference
2347                                 (First_Subtype (Etype (Indx)), True);
2348                               Next_Index (Indx);
2349                            end loop;
2350                         end;
2351                      end if;
2352
2353                      --  If the entity is an overriding operation, write info
2354                      --  on operation that was overridden.
2355
2356                      if Is_Subprogram (XE.Key.Ent)
2357                        and then Present (Overridden_Operation (XE.Key.Ent))
2358                      then
2359                         Output_Overridden_Op
2360                           (Overridden_Operation (XE.Key.Ent));
2361                      end if;
2362
2363                      --  End of processing for entity output
2364
2365                      Crloc := No_Location;
2366                   end if;
2367
2368                   --  Output the reference if it is not as the same location
2369                   --  as the previous one, or it is a read-reference that
2370                   --  indicates that the entity is an in-out actual in a call.
2371
2372                   if XE.Key.Loc /= No_Location
2373                     and then
2374                       (XE.Key.Loc /= Crloc
2375                         or else (Prevt = 'm' and then  XE.Key.Typ = 'r'))
2376                   then
2377                      Crloc := XE.Key.Loc;
2378                      Prevt := XE.Key.Typ;
2379
2380                      --  Start continuation if line full, else blank
2381
2382                      if Write_Info_Col > 72 then
2383                         Write_Info_EOL;
2384                         Write_Info_Initiate ('.');
2385                      end if;
2386
2387                      Write_Info_Char (' ');
2388
2389                      --  Output file number if changed
2390
2391                      if XE.Key.Lun /= Curru then
2392                         Curru := XE.Key.Lun;
2393                         Write_Info_Nat (Dependency_Num (Curru));
2394                         Write_Info_Char ('|');
2395                      end if;
2396
2397                      Write_Info_Nat
2398                        (Int (Get_Logical_Line_Number (XE.Key.Loc)));
2399                      Write_Info_Char (XE.Key.Typ);
2400
2401                      if Is_Overloadable (XE.Key.Ent)
2402                        and then Is_Imported (XE.Key.Ent)
2403                        and then XE.Key.Typ = 'b'
2404                      then
2405                         Output_Import_Export_Info (XE.Key.Ent);
2406                      end if;
2407
2408                      Write_Info_Nat (Int (Get_Column_Number (XE.Key.Loc)));
2409
2410                      Output_Instantiation_Refs (Sloc (XE.Key.Ent));
2411                   end if;
2412                end if;
2413             end Output_One_Ref;
2414
2415          <<Continue>>
2416             null;
2417          end loop;
2418
2419          Write_Info_EOL;
2420       end Output_Refs;
2421    end Output_References;
2422
2423 begin
2424    --  Reset is necessary because Elmt_Ptr does not default to Null_Ptr,
2425    --  because it's not an access type.
2426
2427    Xref_Set.Reset;
2428 end Lib.Xref;