OSDN Git Service

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