OSDN Git Service

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