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