OSDN Git Service

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