OSDN Git Service

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