OSDN Git Service

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