OSDN Git Service

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