OSDN Git Service

2004-06-07 Robert Dewar <dewar@gnat.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-2004, 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 2,  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 COPYING.  If not, write --
19 -- to  the Free Software Foundation,  59 Temple Place - Suite 330,  Boston, --
20 -- MA 02111-1307, USA.                                                      --
21 --                                                                          --
22 -- GNAT was originally developed  by the GNAT team at  New York University. --
23 -- Extensive contributions were provided by Ada Core Technologies Inc.      --
24 --                                                                          --
25 ------------------------------------------------------------------------------
26
27 with Atree;    use Atree;
28 with Csets;    use Csets;
29 with Elists;   use Elists;
30 with Errout;   use Errout;
31 with Lib.Util; use Lib.Util;
32 with Namet;    use Namet;
33 with Nlists;   use Nlists;
34 with Opt;      use Opt;
35 with Sem_Prag; use Sem_Prag;
36 with Sinfo;    use Sinfo;
37 with Sinput;   use Sinput;
38 with Snames;   use Snames;
39 with Stringt;  use Stringt;
40 with Stand;    use Stand;
41 with Table;    use Table;
42 with Widechar; use Widechar;
43
44 with GNAT.Heap_Sort_A;
45
46 package body Lib.Xref is
47
48    ------------------
49    -- Declarations --
50    ------------------
51
52    --  The Xref table is used to record references. The Loc field is set
53    --  to No_Location for a definition entry.
54
55    subtype Xref_Entry_Number is Int;
56
57    type Xref_Entry is record
58       Ent : Entity_Id;
59       --  Entity referenced (E parameter to Generate_Reference)
60
61       Def : Source_Ptr;
62       --  Original source location for entity being referenced. Note that
63       --  these values are used only during the output process, they are
64       --  not set when the entries are originally built. This is because
65       --  private entities can be swapped when the initial call is made.
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    end record;
83
84    package Xrefs is new Table.Table (
85      Table_Component_Type => Xref_Entry,
86      Table_Index_Type     => Xref_Entry_Number,
87      Table_Low_Bound      => 1,
88      Table_Initial        => Alloc.Xrefs_Initial,
89      Table_Increment      => Alloc.Xrefs_Increment,
90      Table_Name           => "Xrefs");
91
92    -------------------------
93    -- Generate_Definition --
94    -------------------------
95
96    procedure Generate_Definition (E : Entity_Id) is
97       Loc  : Source_Ptr;
98       Indx : Nat;
99
100    begin
101       pragma Assert (Nkind (E) in N_Entity);
102
103       --  Note that we do not test Xref_Entity_Letters here. It is too
104       --  early to do so, since we are often called before the entity
105       --  is fully constructed, so that the Ekind is still E_Void.
106
107       if Opt.Xref_Active
108
109          --  Definition must come from source
110
111          and then Comes_From_Source (E)
112
113          --  And must have a reasonable source location that is not
114          --  within an instance (all entities in instances are ignored)
115
116          and then Sloc (E) > No_Location
117          and then Instantiation_Location (Sloc (E)) = No_Location
118
119          --  And must be a non-internal name from the main source unit
120
121          and then In_Extended_Main_Source_Unit (E)
122          and then not Is_Internal_Name (Chars (E))
123       then
124          Xrefs.Increment_Last;
125          Indx := Xrefs.Last;
126          Loc  := Original_Location (Sloc (E));
127
128          Xrefs.Table (Indx).Ent := E;
129          Xrefs.Table (Indx).Loc := No_Location;
130          Xrefs.Table (Indx).Eun := Get_Source_Unit (Loc);
131          Xrefs.Table (Indx).Lun := No_Unit;
132          Set_Has_Xref_Entry (E);
133       end if;
134    end Generate_Definition;
135
136    ---------------------------------
137    -- Generate_Operator_Reference --
138    ---------------------------------
139
140    procedure Generate_Operator_Reference
141      (N : Node_Id;
142       T : Entity_Id)
143    is
144    begin
145       if not In_Extended_Main_Source_Unit (N) then
146          return;
147       end if;
148
149       --  If the operator is not a Standard operator, then we generate
150       --  a real reference to the user defined operator.
151
152       if Sloc (Entity (N)) /= Standard_Location then
153          Generate_Reference (Entity (N), N);
154
155          --  A reference to an implicit inequality operator is a also a
156          --  reference to the user-defined equality.
157
158          if Nkind (N) = N_Op_Ne
159            and then not Comes_From_Source (Entity (N))
160            and then Present (Corresponding_Equality (Entity (N)))
161          then
162             Generate_Reference (Corresponding_Equality (Entity (N)), N);
163          end if;
164
165       --  For the case of Standard operators, we mark the result type
166       --  as referenced. This ensures that in the case where we are
167       --  using a derived operator, we mark an entity of the unit that
168       --  implicitly defines this operator as used. Otherwise we may
169       --  think that no entity of the unit is used. The actual entity
170       --  marked as referenced is the first subtype, which is the user
171       --  defined entity that is relevant.
172
173       --  Note: we only do this for operators that come from source.
174       --  The generated code sometimes reaches for entities that do
175       --  not need to be explicitly visible (for example, when we
176       --  expand the code for comparing two record types, the fields
177       --  of the record may not be visible).
178
179       elsif Comes_From_Source (N) then
180          Set_Referenced (First_Subtype (T));
181       end if;
182    end Generate_Operator_Reference;
183
184    ------------------------
185    -- Generate_Reference --
186    ------------------------
187
188    procedure Generate_Reference
189      (E       : Entity_Id;
190       N       : Node_Id;
191       Typ     : Character := 'r';
192       Set_Ref : Boolean   := True;
193       Force   : Boolean   := False)
194    is
195       Indx : Nat;
196       Nod  : Node_Id;
197       Ref  : Source_Ptr;
198       Def  : Source_Ptr;
199       Ent  : Entity_Id;
200
201       function Is_On_LHS (Node : Node_Id) return Boolean;
202       --  Used to check if a node is on the left hand side of an
203       --  assignment. The following cases are handled:
204       --
205       --   Variable  Node is a direct descendant of an assignment
206       --             statement.
207       --
208       --   Prefix    Of an indexed or selected component that is
209       --             present in a subtree rooted by an assignment
210       --             statement. There is no restriction of nesting
211       --             of components, thus cases such as A.B(C).D are
212       --             handled properly.
213
214       ---------------
215       -- Is_On_LHS --
216       ---------------
217
218       --  Couldn't we use Is_Lvalue or whatever it is called ???
219
220       function Is_On_LHS (Node : Node_Id) return Boolean is
221          N : Node_Id := Node;
222
223       begin
224          --  Only identifiers are considered, is this necessary???
225
226          if Nkind (N) /= N_Identifier then
227             return False;
228          end if;
229
230          --  Reach the assignment statement subtree root. In the
231          --  case of a variable being a direct descendant of an
232          --  assignment statement, the loop is skiped.
233
234          while Nkind (Parent (N)) /= N_Assignment_Statement loop
235
236             --  Check whether the parent is a component and the
237             --  current node is its prefix.
238
239             if (Nkind (Parent (N)) = N_Selected_Component
240                   or else
241                 Nkind (Parent (N)) = N_Indexed_Component)
242               and then Prefix (Parent (N)) = N
243             then
244                N := Parent (N);
245             else
246                return False;
247             end if;
248          end loop;
249
250          --  Parent (N) is an assignment statement, check whether
251          --  N is its name.
252
253          return Name (Parent (N)) = N;
254       end Is_On_LHS;
255
256    --  Start of processing for Generate_Reference
257
258    begin
259       pragma Assert (Nkind (E) in N_Entity);
260
261       --  Never collect references if not in main source unit. However,
262       --  we omit this test if Typ is 'e' or 'k', since these entries are
263       --  really structural, and it is useful to have them in units
264       --  that reference packages as well as units that define packages.
265       --  We also omit the test for the case of 'p' since we want to
266       --  include inherited primitive operations from other packages.
267
268       if not In_Extended_Main_Source_Unit (N)
269         and then Typ /= 'e'
270         and then Typ /= 'p'
271         and then Typ /= 'k'
272       then
273          return;
274       end if;
275
276       --  For reference type p, the entity must be in main source unit
277
278       if Typ = 'p' and then not In_Extended_Main_Source_Unit (E) then
279          return;
280       end if;
281
282       --  Unless the reference is forced, we ignore references where
283       --  the reference itself does not come from Source.
284
285       if not Force and then not Comes_From_Source (N) then
286          return;
287       end if;
288
289       --  Deal with setting entity as referenced, unless suppressed.
290       --  Note that we still do Set_Referenced on entities that do not
291       --  come from source. This situation arises when we have a source
292       --  reference to a derived operation, where the derived operation
293       --  itself does not come from source, but we still want to mark it
294       --  as referenced, since we really are referencing an entity in the
295       --  corresponding package (this avoids incorrect complaints that the
296       --  package contains no referenced entities).
297
298       if Set_Ref then
299
300          --  For a variable that appears on the left side of an
301          --  assignment statement, we set the Referenced_As_LHS
302          --  flag since this is indeed a left hand side.
303          --  We also set the Referenced_As_LHS flag of a prefix
304          --  of selected or indexed component.
305
306          if Ekind (E) = E_Variable
307            and then Is_On_LHS (N)
308          then
309             Set_Referenced_As_LHS (E);
310
311          --  Check for a reference in a pragma that should not count as a
312          --  making the variable referenced for warning purposes.
313
314          elsif Is_Non_Significant_Pragma_Reference (N) then
315             null;
316
317          --  A reference in an attribute definition clause does not
318          --  count as a reference except for the case of Address.
319          --  The reason that 'Address is an exception is that it
320          --  creates an alias through which the variable may be
321          --  referenced.
322
323          elsif Nkind (Parent (N)) = N_Attribute_Definition_Clause
324            and then Chars (Parent (N)) /= Name_Address
325            and then N = Name (Parent (N))
326          then
327             null;
328
329          --  Constant completion does not count as a reference
330
331          elsif Typ = 'c'
332            and then Ekind (E) = E_Constant
333          then
334             null;
335
336          --  Record representation clause does not count as a reference
337
338          elsif Nkind (N) = N_Identifier
339            and then Nkind (Parent (N)) = N_Record_Representation_Clause
340          then
341             null;
342
343          --  Discriminants do not need to produce a reference to record type
344
345          elsif Typ = 'd'
346            and then Nkind (Parent (N)) = N_Discriminant_Specification
347          then
348             null;
349
350          --  Any other occurrence counts as referencing the entity
351
352          else
353             Set_Referenced (E);
354          end if;
355
356          --  Check for pragma Unreferenced given and reference is within
357          --  this source unit (occasion for possible warning to be issued)
358
359          if Has_Pragma_Unreferenced (E)
360            and then In_Same_Extended_Unit (Sloc (E), Sloc (N))
361          then
362             --  A reference as a named parameter in a call does not count
363             --  as a violation of pragma Unreferenced for this purpose.
364
365             if Nkind (N) = N_Identifier
366               and then Nkind (Parent (N)) = N_Parameter_Association
367               and then Selector_Name (Parent (N)) = N
368             then
369                null;
370
371             --  Neither does a reference to a variable on the left side
372             --  of an assignment
373
374             elsif Ekind (E) = E_Variable
375               and then Nkind (Parent (N)) = N_Assignment_Statement
376               and then Name (Parent (N)) = N
377             then
378                null;
379
380             --  Here we issue the warning, since this is a real reference
381
382             else
383                Error_Msg_NE ("?pragma Unreferenced given for&", N, E);
384             end if;
385          end if;
386
387          --  If this is a subprogram instance, mark as well the internal
388          --  subprogram in the wrapper package, which may be a visible
389          --  compilation unit.
390
391          if Is_Overloadable (E)
392            and then Is_Generic_Instance (E)
393            and then Present (Alias (E))
394          then
395             Set_Referenced (Alias (E));
396          end if;
397       end if;
398
399       --  Generate reference if all conditions are met:
400
401       if
402          --  Cross referencing must be active
403
404          Opt.Xref_Active
405
406          --  The entity must be one for which we collect references
407
408          and then Xref_Entity_Letters (Ekind (E)) /= ' '
409
410          --  Both Sloc values must be set to something sensible
411
412          and then Sloc (E) > No_Location
413          and then Sloc (N) > No_Location
414
415          --  We ignore references from within an instance
416
417          and then Instantiation_Location (Sloc (N)) = No_Location
418
419          --  Ignore dummy references
420
421         and then Typ /= ' '
422       then
423          if Nkind (N) = N_Identifier
424               or else
425             Nkind (N) = N_Defining_Identifier
426               or else
427             Nkind (N) in N_Op
428               or else
429             Nkind (N) = N_Defining_Operator_Symbol
430               or else
431             Nkind (N) = N_Operator_Symbol
432               or else
433             (Nkind (N) = N_Character_Literal
434               and then Sloc (Entity (N)) /= Standard_Location)
435               or else
436             Nkind (N) = N_Defining_Character_Literal
437          then
438             Nod := N;
439
440          elsif Nkind (N) = N_Expanded_Name
441                  or else
442                Nkind (N) = N_Selected_Component
443          then
444             Nod := Selector_Name (N);
445
446          else
447             return;
448          end if;
449
450          --  Normal case of source entity comes from source
451
452          if Comes_From_Source (E) then
453             Ent := E;
454
455          --  Entity does not come from source, but is a derived subprogram
456          --  and the derived subprogram comes from source (after one or more
457          --  derivations) in which case the reference is to parent subprogram.
458
459          elsif Is_Overloadable (E)
460            and then Present (Alias (E))
461          then
462             Ent := Alias (E);
463
464             loop
465                if Comes_From_Source (Ent) then
466                   exit;
467                elsif No (Alias (Ent)) then
468                   return;
469                else
470                   Ent := Alias (Ent);
471                end if;
472             end loop;
473
474          --  Record components of discriminated subtypes or derived types
475          --  must be treated as references to the original component.
476
477          elsif Ekind (E) = E_Component
478            and then Comes_From_Source (Original_Record_Component (E))
479          then
480             Ent := Original_Record_Component (E);
481
482          --  Ignore reference to any other entity that is not from source
483
484          else
485             return;
486          end if;
487
488          --  Record reference to entity
489
490          Ref := Original_Location (Sloc (Nod));
491          Def := Original_Location (Sloc (Ent));
492
493          Xrefs.Increment_Last;
494          Indx := Xrefs.Last;
495
496          Xrefs.Table (Indx).Loc := Ref;
497
498          --  Overriding operations are marked with 'P'.
499
500          if Typ = 'p'
501            and then Is_Subprogram (N)
502            and then Is_Overriding_Operation (N)
503          then
504             Xrefs.Table (Indx).Typ := 'P';
505          else
506             Xrefs.Table (Indx).Typ := Typ;
507          end if;
508
509          Xrefs.Table (Indx).Eun := Get_Source_Unit (Def);
510          Xrefs.Table (Indx).Lun := Get_Source_Unit (Ref);
511          Xrefs.Table (Indx).Ent := Ent;
512          Set_Has_Xref_Entry (Ent);
513       end if;
514    end Generate_Reference;
515
516    -----------------------------------
517    -- Generate_Reference_To_Formals --
518    -----------------------------------
519
520    procedure Generate_Reference_To_Formals (E : Entity_Id) is
521       Formal : Entity_Id;
522
523    begin
524       if Is_Generic_Subprogram (E) then
525          Formal := First_Entity (E);
526
527          while Present (Formal)
528            and then not Is_Formal (Formal)
529          loop
530             Next_Entity (Formal);
531          end loop;
532
533       else
534          Formal := First_Formal (E);
535       end if;
536
537       while Present (Formal) loop
538          if Ekind (Formal) = E_In_Parameter then
539
540             if Nkind (Parameter_Type (Parent (Formal)))
541               = N_Access_Definition
542             then
543                Generate_Reference (E, Formal, '^', False);
544             else
545                Generate_Reference (E, Formal, '>', False);
546             end if;
547
548          elsif Ekind (Formal) = E_In_Out_Parameter then
549             Generate_Reference (E, Formal, '=', False);
550
551          else
552             Generate_Reference (E, Formal, '<', False);
553          end if;
554
555          Next_Formal (Formal);
556       end loop;
557    end Generate_Reference_To_Formals;
558
559    -------------------------------------------
560    -- Generate_Reference_To_Generic_Formals --
561    -------------------------------------------
562
563    procedure Generate_Reference_To_Generic_Formals (E : Entity_Id) is
564       Formal : Entity_Id;
565
566    begin
567       Formal := First_Entity (E);
568
569       while Present (Formal) loop
570          if Comes_From_Source (Formal) then
571             Generate_Reference (E, Formal, 'z', False);
572          end if;
573
574          Next_Entity (Formal);
575       end loop;
576    end Generate_Reference_To_Generic_Formals;
577
578    ----------------
579    -- Initialize --
580    ----------------
581
582    procedure Initialize is
583    begin
584       Xrefs.Init;
585    end Initialize;
586
587    -----------------------
588    -- Output_References --
589    -----------------------
590
591    procedure Output_References is
592
593       procedure Get_Type_Reference
594         (Ent   : Entity_Id;
595          Tref  : out Entity_Id;
596          Left  : out Character;
597          Right : out Character);
598       --  Given an entity id Ent, determines whether a type reference is
599       --  required. If so, Tref is set to the entity for the type reference
600       --  and Left and Right are set to the left/right brackets to be
601       --  output for the reference. If no type reference is required, then
602       --  Tref is set to Empty, and Left/Right are set to space.
603
604       procedure Output_Import_Export_Info (Ent : Entity_Id);
605       --  Ouput language and external name information for an interfaced
606       --  entity, using the format <language, external_name>,
607
608       ------------------------
609       -- Get_Type_Reference --
610       ------------------------
611
612       procedure Get_Type_Reference
613         (Ent   : Entity_Id;
614          Tref  : out Entity_Id;
615          Left  : out Character;
616          Right : out Character)
617       is
618          Sav : Entity_Id;
619
620       begin
621          --  See if we have a type reference
622
623          Tref := Ent;
624          Left := '{';
625          Right := '}';
626
627          loop
628             Sav := Tref;
629
630             --  Processing for types
631
632             if Is_Type (Tref) then
633
634                --  Case of base type
635
636                if Base_Type (Tref) = Tref then
637
638                   --  If derived, then get first subtype
639
640                   if Tref /= Etype (Tref) then
641                      Tref := First_Subtype (Etype (Tref));
642
643                      --  Set brackets for derived type, but don't
644                      --  override pointer case since the fact that
645                      --  something is a pointer is more important
646
647                      if Left /= '(' then
648                         Left := '<';
649                         Right := '>';
650                      end if;
651
652                   --  If non-derived ptr, get directly designated type.
653                   --  If the type has a full view, all references are
654                   --  on the partial view, that is seen first.
655
656                   elsif Is_Access_Type (Tref) then
657                      Tref := Directly_Designated_Type (Tref);
658                      Left := '(';
659                      Right := ')';
660
661                   elsif Is_Private_Type (Tref)
662                     and then Present (Full_View (Tref))
663                     and then Is_Access_Type (Full_View (Tref))
664                   then
665                      Tref := Directly_Designated_Type (Full_View (Tref));
666                      Left := '(';
667                      Right := ')';
668
669                   --  If non-derived array, get component type.
670                   --  Skip component type for case of String
671                   --  or Wide_String, saves worthwhile space.
672
673                   elsif Is_Array_Type (Tref)
674                     and then Tref /= Standard_String
675                     and then Tref /= Standard_Wide_String
676                   then
677                      Tref := Component_Type (Tref);
678                      Left := '(';
679                      Right := ')';
680
681                   --  For other non-derived base types, nothing
682
683                   else
684                      exit;
685                   end if;
686
687                --  For a subtype, go to ancestor subtype.
688
689                else
690                   Tref := Ancestor_Subtype (Tref);
691
692                   --  If no ancestor subtype, go to base type
693
694                   if No (Tref) then
695                      Tref := Base_Type (Sav);
696                   end if;
697                end if;
698
699             --  For objects, functions, enum literals,
700             --  just get type from Etype field.
701
702             elsif Is_Object (Tref)
703               or else Ekind (Tref) = E_Enumeration_Literal
704               or else Ekind (Tref) = E_Function
705               or else Ekind (Tref) = E_Operator
706             then
707                Tref := Etype (Tref);
708
709             --  For anything else, exit
710
711             else
712                exit;
713             end if;
714
715             --  Exit if no type reference, or we are stuck in
716             --  some loop trying to find the type reference, or
717             --  if the type is standard void type (the latter is
718             --  an implementation artifact that should not show
719             --  up in the generated cross-references).
720
721             exit when No (Tref)
722               or else Tref = Sav
723               or else Tref = Standard_Void_Type;
724
725             --  If we have a usable type reference, return, otherwise
726             --  keep looking for something useful (we are looking for
727             --  something that either comes from source or standard)
728
729             if Sloc (Tref) = Standard_Location
730               or else Comes_From_Source (Tref)
731             then
732                --  If the reference is a subtype created for a generic
733                --  actual, go to actual directly, the inner subtype is
734                --  not user visible.
735
736                if Nkind (Parent (Tref)) = N_Subtype_Declaration
737                  and then not Comes_From_Source (Parent (Tref))
738                  and then
739                   (Is_Wrapper_Package (Scope (Tref))
740                      or else Is_Generic_Instance (Scope (Tref)))
741                then
742                   Tref := Base_Type (Tref);
743                end if;
744
745                return;
746             end if;
747          end loop;
748
749          --  If we fall through the loop, no type reference
750
751          Tref := Empty;
752          Left := ' ';
753          Right := ' ';
754       end Get_Type_Reference;
755
756       -------------------------------
757       -- Output_Import_Export_Info --
758       -------------------------------
759
760       procedure Output_Import_Export_Info (Ent : Entity_Id) is
761          Language_Name : Name_Id;
762          Conv          : constant Convention_Id := Convention (Ent);
763       begin
764          if Conv  = Convention_C then
765             Language_Name := Name_C;
766
767          elsif Conv = Convention_CPP then
768             Language_Name := Name_CPP;
769
770          elsif Conv = Convention_Ada then
771             Language_Name := Name_Ada;
772
773          else
774             --  These are the only languages that GPS knows about.
775
776             return;
777          end if;
778
779          Write_Info_Char ('<');
780          Get_Unqualified_Name_String (Language_Name);
781
782          for J in 1 .. Name_Len loop
783             Write_Info_Char (Name_Buffer (J));
784          end loop;
785
786          if Present (Interface_Name (Ent)) then
787             Write_Info_Char (',');
788             String_To_Name_Buffer (Strval (Interface_Name (Ent)));
789
790             for J in 1 .. Name_Len loop
791                Write_Info_Char (Name_Buffer (J));
792             end loop;
793          end if;
794
795          Write_Info_Char ('>');
796       end Output_Import_Export_Info;
797
798    --  Start of processing for Output_References
799
800    begin
801       if not Opt.Xref_Active then
802          return;
803       end if;
804
805       --  Before we go ahead and output the references we have a problem
806       --  that needs dealing with. So far we have captured things that are
807       --  definitely referenced by the main unit, or defined in the main
808       --  unit. That's because we don't want to clutter up the ali file
809       --  for this unit with definition lines for entities in other units
810       --  that are not referenced.
811
812       --  But there is a glitch. We may reference an entity in another unit,
813       --  and it may have a type reference to an entity that is not directly
814       --  referenced in the main unit, which may mean that there is no xref
815       --  entry for this entity yet in the list of references.
816
817       --  If we don't do something about this, we will end with an orphan
818       --  type reference, i.e. it will point to an entity that does not
819       --  appear within the generated references in the ali file. That is
820       --  not good for tools using the xref information.
821
822       --  To fix this, we go through the references adding definition
823       --  entries for any unreferenced entities that can be referenced
824       --  in a type reference. There is a recursion problem here, and
825       --  that is dealt with by making sure that this traversal also
826       --  traverses any entries that get added by the traversal.
827
828       declare
829          J    : Nat;
830          Tref : Entity_Id;
831          L, R : Character;
832          Indx : Nat;
833          Ent  : Entity_Id;
834          Loc  : Source_Ptr;
835
836       begin
837          --  Note that this is not a for loop for a very good reason. The
838          --  processing of items in the table can add new items to the
839          --  table, and they must be processed as well
840
841          J := 1;
842          while J <= Xrefs.Last loop
843             Ent := Xrefs.Table (J).Ent;
844             Get_Type_Reference (Ent, Tref, L, R);
845
846             if Present (Tref)
847               and then not Has_Xref_Entry (Tref)
848               and then Sloc (Tref) > No_Location
849             then
850                Xrefs.Increment_Last;
851                Indx := Xrefs.Last;
852                Loc  := Original_Location (Sloc (Tref));
853                Xrefs.Table (Indx).Ent := Tref;
854                Xrefs.Table (Indx).Loc := No_Location;
855                Xrefs.Table (Indx).Eun := Get_Source_Unit (Loc);
856                Xrefs.Table (Indx).Lun := No_Unit;
857                Set_Has_Xref_Entry (Tref);
858             end if;
859
860             --  Collect inherited primitive operations that may be
861             --  declared in another unit and have no visible reference
862             --  in the current one.
863
864             if Is_Type (Ent)
865               and then Is_Tagged_Type (Ent)
866               and then Is_Derived_Type (Ent)
867               and then Ent = Base_Type (Ent)
868               and then In_Extended_Main_Source_Unit (Ent)
869             then
870                declare
871                   Op_List : constant Elist_Id := Primitive_Operations (Ent);
872                   Op      : Elmt_Id;
873                   Prim    : Entity_Id;
874
875                   function Parent_Op (E : Entity_Id) return Entity_Id;
876                   --  Find original operation, which may be inherited
877                   --  through several derivations.
878
879                   function Parent_Op (E : Entity_Id) return Entity_Id is
880                      Orig_Op : constant Entity_Id := Alias (E);
881                   begin
882                      if No (Orig_Op) then
883                         return Empty;
884                      elsif not Comes_From_Source (E)
885                        and then not Has_Xref_Entry (Orig_Op)
886                        and then Comes_From_Source (Orig_Op)
887                      then
888                         return Orig_Op;
889                      else
890                         return Parent_Op (Orig_Op);
891                      end if;
892                   end Parent_Op;
893
894                begin
895                   Op := First_Elmt (Op_List);
896                   while Present (Op) loop
897                      Prim := Parent_Op (Node (Op));
898
899                      if Present (Prim) then
900                         Xrefs.Increment_Last;
901                         Indx := Xrefs.Last;
902                         Loc  := Original_Location (Sloc (Prim));
903                         Xrefs.Table (Indx).Ent := Prim;
904                         Xrefs.Table (Indx).Loc := No_Location;
905                         Xrefs.Table (Indx).Eun :=
906                           Get_Source_Unit (Sloc (Prim));
907                         Xrefs.Table (Indx).Lun := No_Unit;
908                         Set_Has_Xref_Entry (Prim);
909                      end if;
910
911                      Next_Elmt (Op);
912                   end loop;
913                end;
914             end if;
915
916             J := J + 1;
917          end loop;
918       end;
919
920       --  Now we have all the references, including those for any embedded
921       --  type references, so we can sort them, and output them.
922
923       Output_Refs : declare
924
925          Nrefs : Nat := Xrefs.Last;
926          --  Number of references in table. This value may get reset
927          --  (reduced) when we eliminate duplicate reference entries.
928
929          Rnums : array (0 .. Nrefs) of Nat;
930          --  This array contains numbers of references in the Xrefs table.
931          --  This list is sorted in output order. The extra 0'th entry is
932          --  convenient for the call to sort. When we sort the table, we
933          --  move the entries in Rnums around, but we do not move the
934          --  original table entries.
935
936          Curxu : Unit_Number_Type;
937          --  Current xref unit
938
939          Curru : Unit_Number_Type;
940          --  Current reference unit for one entity
941
942          Cursrc : Source_Buffer_Ptr;
943          --  Current xref unit source text
944
945          Curent : Entity_Id;
946          --  Current entity
947
948          Curnam : String (1 .. Name_Buffer'Length);
949          Curlen : Natural;
950          --  Simple name and length of current entity
951
952          Curdef : Source_Ptr;
953          --  Original source location for current entity
954
955          Crloc : Source_Ptr;
956          --  Current reference location
957
958          Ctyp : Character;
959          --  Entity type character
960
961          Tref : Entity_Id;
962          --  Type reference
963
964          Rref : Node_Id;
965          --  Renaming reference
966
967          Trunit : Unit_Number_Type;
968          --  Unit number for type reference
969
970          function Lt (Op1, Op2 : Natural) return Boolean;
971          --  Comparison function for Sort call
972
973          function Name_Change (X : Entity_Id) return Boolean;
974          --  Determines if entity X has a different simple name from Curent
975
976          procedure Move (From : Natural; To : Natural);
977          --  Move procedure for Sort call
978
979          --------
980          -- Lt --
981          --------
982
983          function Lt (Op1, Op2 : Natural) return Boolean is
984             T1 : Xref_Entry renames Xrefs.Table (Rnums (Nat (Op1)));
985             T2 : Xref_Entry renames Xrefs.Table (Rnums (Nat (Op2)));
986
987          begin
988             --  First test. If entity is in different unit, sort by unit
989
990             if T1.Eun /= T2.Eun then
991                return Dependency_Num (T1.Eun) < Dependency_Num (T2.Eun);
992
993             --  Second test, within same unit, sort by entity Sloc
994
995             elsif T1.Def /= T2.Def then
996                return T1.Def < T2.Def;
997
998             --  Third test, sort definitions ahead of references
999
1000             elsif T1.Loc = No_Location then
1001                return True;
1002
1003             elsif T2.Loc = No_Location then
1004                return False;
1005
1006             --  Fourth test, for same entity, sort by reference location unit
1007
1008             elsif T1.Lun /= T2.Lun then
1009                return Dependency_Num (T1.Lun) < Dependency_Num (T2.Lun);
1010
1011             --  Fifth test order of location within referencing unit
1012
1013             elsif T1.Loc /= T2.Loc then
1014                return T1.Loc < T2.Loc;
1015
1016             --  Finally, for two locations at the same address, we prefer
1017             --  the one that does NOT have the type 'r' so that a modification
1018             --  or extension takes preference, when there are more than one
1019             --  reference at the same location.
1020
1021             else
1022                return T2.Typ = 'r';
1023             end if;
1024          end Lt;
1025
1026          ----------
1027          -- Move --
1028          ----------
1029
1030          procedure Move (From : Natural; To : Natural) is
1031          begin
1032             Rnums (Nat (To)) := Rnums (Nat (From));
1033          end Move;
1034
1035          -----------------
1036          -- Name_Change --
1037          -----------------
1038
1039          function Name_Change (X : Entity_Id) return Boolean is
1040          begin
1041             Get_Unqualified_Name_String (Chars (X));
1042
1043             if Name_Len /= Curlen then
1044                return True;
1045
1046             else
1047                return Name_Buffer (1 .. Curlen) /= Curnam (1 .. Curlen);
1048             end if;
1049          end Name_Change;
1050
1051       --  Start of processing for Output_Refs
1052
1053       begin
1054          --  Capture the definition Sloc values. We delay doing this till now,
1055          --  since at the time the reference or definition is made, private
1056          --  types may be swapped, and the Sloc value may be incorrect. We
1057          --  also set up the pointer vector for the sort.
1058
1059          for J in 1 .. Nrefs loop
1060             Rnums (J) := J;
1061             Xrefs.Table (J).Def :=
1062               Original_Location (Sloc (Xrefs.Table (J).Ent));
1063          end loop;
1064
1065          --  Sort the references
1066
1067          GNAT.Heap_Sort_A.Sort
1068            (Integer (Nrefs),
1069             Move'Unrestricted_Access,
1070             Lt'Unrestricted_Access);
1071
1072          --  Eliminate duplicate entries
1073
1074          declare
1075             NR : constant Nat := Nrefs;
1076
1077          begin
1078             --  We need this test for NR because if we force ALI file
1079             --  generation in case of errors detected, it may be the case
1080             --  that Nrefs is 0, so we should not reset it here
1081
1082             if NR >= 2 then
1083                Nrefs := 1;
1084
1085                for J in 2 .. NR loop
1086                   if Xrefs.Table (Rnums (J)) /=
1087                      Xrefs.Table (Rnums (Nrefs))
1088                   then
1089                      Nrefs := Nrefs + 1;
1090                      Rnums (Nrefs) := Rnums (J);
1091                   end if;
1092                end loop;
1093             end if;
1094          end;
1095
1096          --  Initialize loop through references
1097
1098          Curxu  := No_Unit;
1099          Curent := Empty;
1100          Curdef := No_Location;
1101          Curru  := No_Unit;
1102          Crloc  := No_Location;
1103
1104          --  Loop to output references
1105
1106          for Refno in 1 .. Nrefs loop
1107             Output_One_Ref : declare
1108                P2  : Source_Ptr;
1109                WC  : Char_Code;
1110                Err : Boolean;
1111                Ent : Entity_Id;
1112
1113                XE : Xref_Entry renames Xrefs.Table (Rnums (Refno));
1114                --  The current entry to be accessed
1115
1116                P : Source_Ptr;
1117                --  Used to index into source buffer to get entity name
1118
1119                Left  : Character;
1120                Right : Character;
1121                --  Used for {} or <> or () for type reference
1122
1123                procedure Output_Instantiation_Refs (Loc : Source_Ptr);
1124                --  Recursive procedure to output instantiation references for
1125                --  the given source ptr in [file|line[...]] form. No output
1126                --  if the given location is not a generic template reference.
1127
1128                -------------------------------
1129                -- Output_Instantiation_Refs --
1130                -------------------------------
1131
1132                procedure Output_Instantiation_Refs (Loc : Source_Ptr) is
1133                   Iloc : constant Source_Ptr := Instantiation_Location (Loc);
1134                   Lun  : Unit_Number_Type;
1135                   Cu   : constant Unit_Number_Type := Curru;
1136
1137                begin
1138                   --  Nothing to do if this is not an instantiation
1139
1140                   if Iloc = No_Location then
1141                      return;
1142                   end if;
1143
1144                   --  Output instantiation reference
1145
1146                   Write_Info_Char ('[');
1147                   Lun := Get_Source_Unit (Iloc);
1148
1149                   if Lun /= Curru then
1150                      Curru := Lun;
1151                      Write_Info_Nat (Dependency_Num (Curru));
1152                      Write_Info_Char ('|');
1153                   end if;
1154
1155                   Write_Info_Nat (Int (Get_Logical_Line_Number (Iloc)));
1156
1157                   --  Recursive call to get nested instantiations
1158
1159                   Output_Instantiation_Refs (Iloc);
1160
1161                   --  Output final ] after call to get proper nesting
1162
1163                   Write_Info_Char (']');
1164                   Curru := Cu;
1165                   return;
1166                end Output_Instantiation_Refs;
1167
1168             --  Start of processing for Output_One_Ref
1169
1170             begin
1171                Ent := XE.Ent;
1172                Ctyp := Xref_Entity_Letters (Ekind (Ent));
1173
1174                --  Skip reference if it is the only reference to an entity,
1175                --  and it is an end-line reference, and the entity is not in
1176                --  the current extended source. This prevents junk entries
1177                --  consisting only of packages with end lines, where no
1178                --  entity from the package is actually referenced.
1179
1180                if XE.Typ = 'e'
1181                  and then Ent /= Curent
1182                  and then (Refno = Nrefs or else
1183                              Ent /= Xrefs.Table (Rnums (Refno + 1)).Ent)
1184                  and then
1185                    not In_Extended_Main_Source_Unit (Ent)
1186                then
1187                   goto Continue;
1188                end if;
1189
1190                --  For private type, get full view type
1191
1192                if Ctyp = '+'
1193                  and then Present (Full_View (XE.Ent))
1194                then
1195                   Ent := Underlying_Type (Ent);
1196
1197                   if Present (Ent) then
1198                      Ctyp := Xref_Entity_Letters (Ekind (Ent));
1199                   end if;
1200                end if;
1201
1202                --  Special exception for Boolean
1203
1204                if Ctyp = 'E' and then Is_Boolean_Type (Ent) then
1205                   Ctyp := 'B';
1206                end if;
1207
1208                --  For variable reference, get corresponding type
1209
1210                if Ctyp = '*' then
1211                   Ent := Etype (XE.Ent);
1212                   Ctyp := Fold_Lower (Xref_Entity_Letters (Ekind (Ent)));
1213
1214                   --  If variable is private type, get full view type
1215
1216                   if Ctyp = '+'
1217                     and then Present (Full_View (Etype (XE.Ent)))
1218                   then
1219                      Ent := Underlying_Type (Etype (XE.Ent));
1220
1221                      if Present (Ent) then
1222                         Ctyp := Fold_Lower (Xref_Entity_Letters (Ekind (Ent)));
1223                      end if;
1224                   end if;
1225
1226                   --  Special handling for access parameter
1227
1228                   declare
1229                      K : constant Entity_Kind := Ekind (Etype (XE.Ent));
1230
1231                   begin
1232                      if (K = E_Anonymous_Access_Type
1233                            or else
1234                          K = E_Anonymous_Access_Subprogram_Type
1235                             or else K =
1236                          E_Anonymous_Access_Protected_Subprogram_Type)
1237                        and then Is_Formal (XE.Ent)
1238                      then
1239                         Ctyp := 'p';
1240
1241                         --  Special handling for Boolean
1242
1243                      elsif Ctyp = 'e' and then Is_Boolean_Type (Ent) then
1244                         Ctyp := 'b';
1245                      end if;
1246                   end;
1247                end if;
1248
1249                --  Special handling for abstract types and operations.
1250
1251                if Is_Abstract (XE.Ent) then
1252
1253                   if Ctyp = 'U' then
1254                      Ctyp := 'x';            --  abstract procedure
1255
1256                   elsif Ctyp = 'V' then
1257                      Ctyp := 'y';            --  abstract function
1258
1259                   elsif Ctyp = 'R' then
1260                      Ctyp := 'H';            --  abstract type
1261                   end if;
1262                end if;
1263
1264                --  Only output reference if interesting type of entity,
1265                --  and suppress self references, except for bodies that
1266                --  act as specs. Also suppress definitions of body formals
1267                --  (we only treat these as references, and the references
1268                --  were separately recorded).
1269
1270                if Ctyp = ' '
1271                  or else (XE.Loc = XE.Def
1272                             and then
1273                               (XE.Typ /= 'b'
1274                                 or else not Is_Subprogram (XE.Ent)))
1275                  or else (Is_Formal (XE.Ent)
1276                             and then Present (Spec_Entity (XE.Ent)))
1277                then
1278                   null;
1279
1280                else
1281                   --  Start new Xref section if new xref unit
1282
1283                   if XE.Eun /= Curxu then
1284                      if Write_Info_Col > 1 then
1285                         Write_Info_EOL;
1286                      end if;
1287
1288                      Curxu := XE.Eun;
1289                      Cursrc := Source_Text (Source_Index (Curxu));
1290
1291                      Write_Info_Initiate ('X');
1292                      Write_Info_Char (' ');
1293                      Write_Info_Nat (Dependency_Num (XE.Eun));
1294                      Write_Info_Char (' ');
1295                      Write_Info_Name (Reference_Name (Source_Index (XE.Eun)));
1296                   end if;
1297
1298                   --  Start new Entity line if new entity. Note that we
1299                   --  consider two entities the same if they have the same
1300                   --  name and source location. This causes entities in
1301                   --  instantiations to be treated as though they referred
1302                   --  to the template.
1303
1304                   if No (Curent)
1305                     or else
1306                       (XE.Ent /= Curent
1307                          and then
1308                            (Name_Change (XE.Ent) or else XE.Def /= Curdef))
1309                   then
1310                      Curent := XE.Ent;
1311                      Curdef := XE.Def;
1312
1313                      Get_Unqualified_Name_String (Chars (XE.Ent));
1314                      Curlen := Name_Len;
1315                      Curnam (1 .. Curlen) := Name_Buffer (1 .. Curlen);
1316
1317                      if Write_Info_Col > 1 then
1318                         Write_Info_EOL;
1319                      end if;
1320
1321                      --  Write column number information
1322
1323                      Write_Info_Nat (Int (Get_Logical_Line_Number (XE.Def)));
1324                      Write_Info_Char (Ctyp);
1325                      Write_Info_Nat (Int (Get_Column_Number (XE.Def)));
1326
1327                      --  Write level information
1328
1329                      Write_Level_Info : declare
1330                         function Is_Visible_Generic_Entity
1331                           (E : Entity_Id) return Boolean;
1332                         --  Check whether E is declared in the visible part
1333                         --  of a generic package. For source navigation
1334                         --  purposes, treat this as a visible entity.
1335
1336                         function Is_Private_Record_Component
1337                           (E : Entity_Id) return Boolean;
1338                         --  Check whether E is a non-inherited component of a
1339                         --  private extension. Even if the enclosing record is
1340                         --  public, we want to treat the component as private
1341                         --  for navigation purposes.
1342
1343                         ---------------------------------
1344                         -- Is_Private_Record_Component --
1345                         ---------------------------------
1346
1347                         function Is_Private_Record_Component
1348                           (E : Entity_Id) return Boolean
1349                         is
1350                            S : constant Entity_Id := Scope (E);
1351                         begin
1352                            return
1353                              Ekind (E) = E_Component
1354                                and then Nkind (Declaration_Node (S)) =
1355                                  N_Private_Extension_Declaration
1356                                and then Original_Record_Component (E) = E;
1357                         end Is_Private_Record_Component;
1358
1359                         -------------------------------
1360                         -- Is_Visible_Generic_Entity --
1361                         -------------------------------
1362
1363                         function Is_Visible_Generic_Entity
1364                           (E : Entity_Id) return Boolean
1365                         is
1366                            Par : Node_Id;
1367
1368                         begin
1369                            if Ekind (Scope (E)) /= E_Generic_Package then
1370                               return False;
1371                            end if;
1372
1373                            Par := Parent (E);
1374                            while Present (Par) loop
1375                               if
1376                                 Nkind (Par) = N_Generic_Package_Declaration
1377                               then
1378                                  --  Entity is a generic formal
1379
1380                                  return False;
1381
1382                               elsif
1383                                 Nkind (Parent (Par)) = N_Package_Specification
1384                               then
1385                                  return
1386                                    Is_List_Member (Par)
1387                                      and then List_Containing (Par) =
1388                                        Visible_Declarations (Parent (Par));
1389                               else
1390                                  Par := Parent (Par);
1391                               end if;
1392                            end loop;
1393
1394                            return False;
1395                         end Is_Visible_Generic_Entity;
1396
1397                      --  Start of processing for Write_Level_Info
1398
1399                      begin
1400                         if Is_Hidden (Curent)
1401                           or else Is_Private_Record_Component (Curent)
1402                         then
1403                            Write_Info_Char (' ');
1404
1405                         elsif
1406                            Is_Public (Curent)
1407                              or else Is_Visible_Generic_Entity (Curent)
1408                         then
1409                            Write_Info_Char ('*');
1410
1411                         else
1412                            Write_Info_Char (' ');
1413                         end if;
1414                      end Write_Level_Info;
1415
1416                      --  Output entity name. We use the occurrence from the
1417                      --  actual source program at the definition point
1418
1419                      P := Original_Location (Sloc (XE.Ent));
1420
1421                      --  Entity is character literal
1422
1423                      if Cursrc (P) = ''' then
1424                         Write_Info_Char (Cursrc (P));
1425                         Write_Info_Char (Cursrc (P + 1));
1426                         Write_Info_Char (Cursrc (P + 2));
1427
1428                      --  Entity is operator symbol
1429
1430                      elsif Cursrc (P) = '"' or else Cursrc (P) = '%' then
1431                         Write_Info_Char (Cursrc (P));
1432
1433                         P2 := P;
1434                         loop
1435                            P2 := P2 + 1;
1436                            Write_Info_Char (Cursrc (P2));
1437                            exit when Cursrc (P2) = Cursrc (P);
1438                         end loop;
1439
1440                      --  Entity is identifier
1441
1442                      else
1443                         loop
1444                            if Is_Start_Of_Wide_Char (Cursrc, P) then
1445                               Scan_Wide (Cursrc, P, WC, Err);
1446                            elsif not Identifier_Char (Cursrc (P)) then
1447                               exit;
1448                            else
1449                               P := P + 1;
1450                            end if;
1451                         end loop;
1452
1453                         for J in
1454                           Original_Location (Sloc (XE.Ent)) .. P - 1
1455                         loop
1456                            Write_Info_Char (Cursrc (J));
1457                         end loop;
1458                      end if;
1459
1460                      --  See if we have a renaming reference
1461
1462                      if Is_Object (XE.Ent)
1463                        and then Present (Renamed_Object (XE.Ent))
1464                      then
1465                         Rref := Renamed_Object (XE.Ent);
1466
1467                      elsif Is_Overloadable (XE.Ent)
1468                        and then Nkind (Parent (Declaration_Node (XE.Ent))) =
1469                                             N_Subprogram_Renaming_Declaration
1470                      then
1471                         Rref := Name (Parent (Declaration_Node (XE.Ent)));
1472
1473                      elsif Ekind (XE.Ent) = E_Package
1474                        and then Nkind (Declaration_Node (XE.Ent)) =
1475                                          N_Package_Renaming_Declaration
1476                      then
1477                         Rref := Name (Declaration_Node (XE.Ent));
1478
1479                      else
1480                         Rref := Empty;
1481                      end if;
1482
1483                      if Present (Rref) then
1484                         if Nkind (Rref) = N_Expanded_Name then
1485                            Rref := Selector_Name (Rref);
1486                         end if;
1487
1488                         if Nkind (Rref) /= N_Identifier then
1489                            Rref := Empty;
1490                         end if;
1491                      end if;
1492
1493                      --  Write out renaming reference if we have one
1494
1495                      if Present (Rref) then
1496                         Write_Info_Char ('=');
1497                         Write_Info_Nat
1498                           (Int (Get_Logical_Line_Number (Sloc (Rref))));
1499                         Write_Info_Char (':');
1500                         Write_Info_Nat
1501                           (Int (Get_Column_Number (Sloc (Rref))));
1502                      end if;
1503
1504                      --  Indicate that the entity is in the unit
1505                      --  of the current xref xection.
1506
1507                      Curru := Curxu;
1508
1509                      --  See if we have a type reference and if so output
1510
1511                      Get_Type_Reference (XE.Ent, Tref, Left, Right);
1512
1513                      if Present (Tref) then
1514
1515                         --  Case of standard entity, output name
1516
1517                         if Sloc (Tref) = Standard_Location then
1518                            Write_Info_Char (Left);
1519                            Write_Info_Name (Chars (Tref));
1520                            Write_Info_Char (Right);
1521
1522                         --  Case of source entity, output location
1523
1524                         else
1525                            Write_Info_Char (Left);
1526                            Trunit := Get_Source_Unit (Sloc (Tref));
1527
1528                            if Trunit /= Curxu then
1529                               Write_Info_Nat (Dependency_Num (Trunit));
1530                               Write_Info_Char ('|');
1531                            end if;
1532
1533                            Write_Info_Nat
1534                              (Int (Get_Logical_Line_Number (Sloc (Tref))));
1535
1536                            declare
1537                               Ent  : Entity_Id := Tref;
1538                               Kind : constant Entity_Kind := Ekind (Ent);
1539                               Ctyp : Character := Xref_Entity_Letters (Kind);
1540
1541                            begin
1542                               if Ctyp = '+'
1543                                 and then Present (Full_View (Ent))
1544                               then
1545                                  Ent := Underlying_Type (Ent);
1546
1547                                  if Present (Ent) then
1548                                     Ctyp := Xref_Entity_Letters (Ekind (Ent));
1549                                  end if;
1550                               end if;
1551
1552                               Write_Info_Char (Ctyp);
1553                            end;
1554
1555                            Write_Info_Nat
1556                              (Int (Get_Column_Number (Sloc (Tref))));
1557
1558                            --  If the type comes from an instantiation,
1559                            --  add the corresponding info.
1560
1561                            Output_Instantiation_Refs (Sloc (Tref));
1562                            Write_Info_Char (Right);
1563                         end if;
1564                      end if;
1565
1566                      --  End of processing for entity output
1567
1568                      Crloc := No_Location;
1569                   end if;
1570
1571                   --  Output the reference
1572
1573                   if XE.Loc /= No_Location
1574                      and then XE.Loc /= Crloc
1575                   then
1576                      Crloc := XE.Loc;
1577
1578                      --  Start continuation if line full, else blank
1579
1580                      if Write_Info_Col > 72 then
1581                         Write_Info_EOL;
1582                         Write_Info_Initiate ('.');
1583                      end if;
1584
1585                      Write_Info_Char (' ');
1586
1587                      --  Output file number if changed
1588
1589                      if XE.Lun /= Curru then
1590                         Curru := XE.Lun;
1591                         Write_Info_Nat (Dependency_Num (Curru));
1592                         Write_Info_Char ('|');
1593                      end if;
1594
1595                      Write_Info_Nat  (Int (Get_Logical_Line_Number (XE.Loc)));
1596                      Write_Info_Char (XE.Typ);
1597
1598                      if Is_Overloadable (XE.Ent)
1599                        and then Is_Imported (XE.Ent)
1600                        and then XE.Typ = 'b'
1601                      then
1602                         Output_Import_Export_Info (XE.Ent);
1603                      end if;
1604
1605                      Write_Info_Nat  (Int (Get_Column_Number (XE.Loc)));
1606
1607                      Output_Instantiation_Refs (Sloc (XE.Ent));
1608                   end if;
1609                end if;
1610             end Output_One_Ref;
1611
1612          <<Continue>>
1613             null;
1614          end loop;
1615
1616          Write_Info_EOL;
1617       end Output_Refs;
1618    end Output_References;
1619
1620 end Lib.Xref;