* gimplify.c (find_single_pointer_decl_1): New static function.
[official-gcc.git] / gcc / ada / lib-xref.adb
blob7260b0cdcc4d4955116321bda5e642b92853e5b5
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-2005, 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, 51 Franklin Street, Fifth Floor, --
20 -- Boston, MA 02110-1301, 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 ------------------------------------------------------------------------------
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 Restrict; use Restrict;
36 with Rident; use Rident;
37 with Sem; use Sem;
38 with Sem_Prag; use Sem_Prag;
39 with Sem_Util; use Sem_Util;
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;
48 with GNAT.Heap_Sort_A;
50 package body Lib.Xref is
52 ------------------
53 -- Declarations --
54 ------------------
56 -- The Xref table is used to record references. The Loc field is set
57 -- to No_Location for a definition entry.
59 subtype Xref_Entry_Number is Int;
61 type Xref_Entry is record
62 Ent : Entity_Id;
63 -- Entity referenced (E parameter to Generate_Reference)
65 Def : Source_Ptr;
66 -- Original source location for entity being referenced. Note that
67 -- these values are used only during the output process, they are
68 -- not set when the entries are originally built. This is because
69 -- private entities can be swapped when the initial call is made.
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.
76 Typ : Character;
77 -- Reference type (Typ param to Generate_Reference)
79 Eun : Unit_Number_Type;
80 -- Unit number corresponding to Ent
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.
86 end record;
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");
96 -------------------------
97 -- Generate_Definition --
98 -------------------------
100 procedure Generate_Definition (E : Entity_Id) is
101 Loc : Source_Ptr;
102 Indx : Nat;
104 begin
105 pragma Assert (Nkind (E) in N_Entity);
107 -- Note that we do not test Xref_Entity_Letters here. It is too
108 -- early to do so, since we are often called before the entity
109 -- is fully constructed, so that the Ekind is still E_Void.
111 if Opt.Xref_Active
113 -- Definition must come from source
115 and then Comes_From_Source (E)
117 -- And must have a reasonable source location that is not
118 -- within an instance (all entities in instances are ignored)
120 and then Sloc (E) > No_Location
121 and then Instantiation_Location (Sloc (E)) = No_Location
123 -- And must be a non-internal name from the main source unit
125 and then In_Extended_Main_Source_Unit (E)
126 and then not Is_Internal_Name (Chars (E))
127 then
128 Xrefs.Increment_Last;
129 Indx := Xrefs.Last;
130 Loc := Original_Location (Sloc (E));
132 Xrefs.Table (Indx).Ent := E;
133 Xrefs.Table (Indx).Loc := No_Location;
134 Xrefs.Table (Indx).Eun := Get_Source_Unit (Loc);
135 Xrefs.Table (Indx).Lun := No_Unit;
136 Set_Has_Xref_Entry (E);
138 if In_Inlined_Body then
139 Set_Referenced (E);
140 end if;
141 end if;
142 end Generate_Definition;
144 ---------------------------------
145 -- Generate_Operator_Reference --
146 ---------------------------------
148 procedure Generate_Operator_Reference
149 (N : Node_Id;
150 T : Entity_Id)
152 begin
153 if not In_Extended_Main_Source_Unit (N) then
154 return;
155 end if;
157 -- If the operator is not a Standard operator, then we generate
158 -- a real reference to the user defined operator.
160 if Sloc (Entity (N)) /= Standard_Location then
161 Generate_Reference (Entity (N), N);
163 -- A reference to an implicit inequality operator is a also a
164 -- reference to the user-defined equality.
166 if Nkind (N) = N_Op_Ne
167 and then not Comes_From_Source (Entity (N))
168 and then Present (Corresponding_Equality (Entity (N)))
169 then
170 Generate_Reference (Corresponding_Equality (Entity (N)), N);
171 end if;
173 -- For the case of Standard operators, we mark the result type
174 -- as referenced. This ensures that in the case where we are
175 -- using a derived operator, we mark an entity of the unit that
176 -- implicitly defines this operator as used. Otherwise we may
177 -- think that no entity of the unit is used. The actual entity
178 -- marked as referenced is the first subtype, which is the user
179 -- defined entity that is relevant.
181 -- Note: we only do this for operators that come from source.
182 -- The generated code sometimes reaches for entities that do
183 -- not need to be explicitly visible (for example, when we
184 -- expand the code for comparing two record types, the fields
185 -- of the record may not be visible).
187 elsif Comes_From_Source (N) then
188 Set_Referenced (First_Subtype (T));
189 end if;
190 end Generate_Operator_Reference;
192 ------------------------
193 -- Generate_Reference --
194 ------------------------
196 procedure Generate_Reference
197 (E : Entity_Id;
198 N : Node_Id;
199 Typ : Character := 'r';
200 Set_Ref : Boolean := True;
201 Force : Boolean := False)
203 Indx : Nat;
204 Nod : Node_Id;
205 Ref : Source_Ptr;
206 Def : Source_Ptr;
207 Ent : Entity_Id;
209 function Is_On_LHS (Node : Node_Id) return Boolean;
210 -- Used to check if a node is on the left hand side of an
211 -- assignment. The following cases are handled:
213 -- Variable Node is a direct descendant of an assignment
214 -- statement.
216 -- Prefix Of an indexed or selected component that is
217 -- present in a subtree rooted by an assignment
218 -- statement. There is no restriction of nesting
219 -- of components, thus cases such as A.B(C).D are
220 -- handled properly.
222 ---------------
223 -- Is_On_LHS --
224 ---------------
226 -- Couldn't we use Is_Lvalue or whatever it is called ???
228 function Is_On_LHS (Node : Node_Id) return Boolean is
229 N : Node_Id := Node;
231 begin
232 -- Only identifiers are considered, is this necessary???
234 if Nkind (N) /= N_Identifier then
235 return False;
236 end if;
238 -- Reach the assignment statement subtree root. In the
239 -- case of a variable being a direct descendant of an
240 -- assignment statement, the loop is skiped.
242 while Nkind (Parent (N)) /= N_Assignment_Statement loop
244 -- Check whether the parent is a component and the
245 -- current node is its prefix.
247 if (Nkind (Parent (N)) = N_Selected_Component
248 or else
249 Nkind (Parent (N)) = N_Indexed_Component)
250 and then Prefix (Parent (N)) = N
251 then
252 N := Parent (N);
253 else
254 return False;
255 end if;
256 end loop;
258 -- Parent (N) is an assignment statement, check whether
259 -- N is its name.
261 return Name (Parent (N)) = N;
262 end Is_On_LHS;
264 -- Start of processing for Generate_Reference
266 begin
267 pragma Assert (Nkind (E) in N_Entity);
269 -- Check for obsolescent reference to ASCII
271 if E = Standard_ASCII then
272 Check_Restriction (No_Obsolescent_Features, N);
273 end if;
275 -- Warn if reference to Ada 2005 entity not in Ada 2005 mode
277 if Is_Ada_2005 (E)
278 and then Ada_Version < Ada_05
279 and then Warn_On_Ada_2005_Compatibility
280 then
281 Error_Msg_NE ("& is only defined in Ada 2005?", N, E);
282 end if;
284 -- Never collect references if not in main source unit. However,
285 -- we omit this test if Typ is 'e' or 'k', since these entries are
286 -- really structural, and it is useful to have them in units
287 -- that reference packages as well as units that define packages.
288 -- We also omit the test for the case of 'p' since we want to
289 -- include inherited primitive operations from other packages.
291 if not In_Extended_Main_Source_Unit (N)
292 and then Typ /= 'e'
293 and then Typ /= 'p'
294 and then Typ /= 'k'
295 then
296 return;
297 end if;
299 -- For reference type p, the entity must be in main source unit
301 if Typ = 'p' and then not In_Extended_Main_Source_Unit (E) then
302 return;
303 end if;
305 -- Unless the reference is forced, we ignore references where
306 -- the reference itself does not come from Source.
308 if not Force and then not Comes_From_Source (N) then
309 return;
310 end if;
312 -- Deal with setting entity as referenced, unless suppressed.
313 -- Note that we still do Set_Referenced on entities that do not
314 -- come from source. This situation arises when we have a source
315 -- reference to a derived operation, where the derived operation
316 -- itself does not come from source, but we still want to mark it
317 -- as referenced, since we really are referencing an entity in the
318 -- corresponding package (this avoids incorrect complaints that the
319 -- package contains no referenced entities).
321 if Set_Ref then
323 -- For a variable that appears on the left side of an
324 -- assignment statement, we set the Referenced_As_LHS
325 -- flag since this is indeed a left hand side.
326 -- We also set the Referenced_As_LHS flag of a prefix
327 -- of selected or indexed component.
329 if Ekind (E) = E_Variable
330 and then Is_On_LHS (N)
331 then
332 Set_Referenced_As_LHS (E);
334 -- Check for a reference in a pragma that should not count as a
335 -- making the variable referenced for warning purposes.
337 elsif Is_Non_Significant_Pragma_Reference (N) then
338 null;
340 -- A reference in an attribute definition clause does not
341 -- count as a reference except for the case of Address.
342 -- The reason that 'Address is an exception is that it
343 -- creates an alias through which the variable may be
344 -- referenced.
346 elsif Nkind (Parent (N)) = N_Attribute_Definition_Clause
347 and then Chars (Parent (N)) /= Name_Address
348 and then N = Name (Parent (N))
349 then
350 null;
352 -- Constant completion does not count as a reference
354 elsif Typ = 'c'
355 and then Ekind (E) = E_Constant
356 then
357 null;
359 -- Record representation clause does not count as a reference
361 elsif Nkind (N) = N_Identifier
362 and then Nkind (Parent (N)) = N_Record_Representation_Clause
363 then
364 null;
366 -- Discriminants do not need to produce a reference to record type
368 elsif Typ = 'd'
369 and then Nkind (Parent (N)) = N_Discriminant_Specification
370 then
371 null;
373 -- Any other occurrence counts as referencing the entity
375 else
376 Set_Referenced (E);
377 end if;
379 -- Check for pragma Unreferenced given and reference is within
380 -- this source unit (occasion for possible warning to be issued)
382 if Has_Pragma_Unreferenced (E)
383 and then In_Same_Extended_Unit (E, N)
384 then
385 -- A reference as a named parameter in a call does not count
386 -- as a violation of pragma Unreferenced for this purpose.
388 if Nkind (N) = N_Identifier
389 and then Nkind (Parent (N)) = N_Parameter_Association
390 and then Selector_Name (Parent (N)) = N
391 then
392 null;
394 -- Neither does a reference to a variable on the left side
395 -- of an assignment
397 elsif Ekind (E) = E_Variable
398 and then Nkind (Parent (N)) = N_Assignment_Statement
399 and then Name (Parent (N)) = N
400 then
401 null;
403 -- For entry formals, we want to place the warning on the
404 -- corresponding entity in the accept statement. The current
405 -- scope is the body of the accept, so we find the formal
406 -- whose name matches that of the entry formal (there is no
407 -- link between the two entities, and the one in the accept
408 -- statement is only used for conformance checking).
410 elsif Ekind (Scope (E)) = E_Entry then
411 declare
412 BE : Entity_Id;
414 begin
415 BE := First_Entity (Current_Scope);
416 while Present (BE) loop
417 if Chars (BE) = Chars (E) then
418 Error_Msg_NE
419 ("?pragma Unreferenced given for&", N, BE);
420 exit;
421 end if;
423 Next_Entity (BE);
424 end loop;
425 end;
427 -- Here we issue the warning, since this is a real reference
429 else
430 Error_Msg_NE ("?pragma Unreferenced given for&", N, E);
431 end if;
432 end if;
434 -- If this is a subprogram instance, mark as well the internal
435 -- subprogram in the wrapper package, which may be a visible
436 -- compilation unit.
438 if Is_Overloadable (E)
439 and then Is_Generic_Instance (E)
440 and then Present (Alias (E))
441 then
442 Set_Referenced (Alias (E));
443 end if;
444 end if;
446 -- Generate reference if all conditions are met:
449 -- Cross referencing must be active
451 Opt.Xref_Active
453 -- The entity must be one for which we collect references
455 and then Xref_Entity_Letters (Ekind (E)) /= ' '
457 -- Both Sloc values must be set to something sensible
459 and then Sloc (E) > No_Location
460 and then Sloc (N) > No_Location
462 -- We ignore references from within an instance
464 and then Instantiation_Location (Sloc (N)) = No_Location
466 -- Ignore dummy references
468 and then Typ /= ' '
469 then
470 if Nkind (N) = N_Identifier
471 or else
472 Nkind (N) = N_Defining_Identifier
473 or else
474 Nkind (N) in N_Op
475 or else
476 Nkind (N) = N_Defining_Operator_Symbol
477 or else
478 Nkind (N) = N_Operator_Symbol
479 or else
480 (Nkind (N) = N_Character_Literal
481 and then Sloc (Entity (N)) /= Standard_Location)
482 or else
483 Nkind (N) = N_Defining_Character_Literal
484 then
485 Nod := N;
487 elsif Nkind (N) = N_Expanded_Name
488 or else
489 Nkind (N) = N_Selected_Component
490 then
491 Nod := Selector_Name (N);
493 else
494 return;
495 end if;
497 -- Normal case of source entity comes from source
499 if Comes_From_Source (E) then
500 Ent := E;
502 -- Entity does not come from source, but is a derived subprogram
503 -- and the derived subprogram comes from source (after one or more
504 -- derivations) in which case the reference is to parent subprogram.
506 elsif Is_Overloadable (E)
507 and then Present (Alias (E))
508 then
509 Ent := Alias (E);
511 loop
512 if Comes_From_Source (Ent) then
513 exit;
514 elsif No (Alias (Ent)) then
515 return;
516 else
517 Ent := Alias (Ent);
518 end if;
519 end loop;
521 -- Record components of discriminated subtypes or derived types
522 -- must be treated as references to the original component.
524 elsif Ekind (E) = E_Component
525 and then Comes_From_Source (Original_Record_Component (E))
526 then
527 Ent := Original_Record_Component (E);
529 -- Ignore reference to any other entity that is not from source
531 else
532 return;
533 end if;
535 -- Record reference to entity
537 Ref := Original_Location (Sloc (Nod));
538 Def := Original_Location (Sloc (Ent));
540 Xrefs.Increment_Last;
541 Indx := Xrefs.Last;
543 Xrefs.Table (Indx).Loc := Ref;
545 -- Overriding operations are marked with 'P'
547 if Typ = 'p'
548 and then Is_Subprogram (N)
549 and then Is_Overriding_Operation (N)
550 then
551 Xrefs.Table (Indx).Typ := 'P';
552 else
553 Xrefs.Table (Indx).Typ := Typ;
554 end if;
556 Xrefs.Table (Indx).Eun := Get_Source_Unit (Def);
557 Xrefs.Table (Indx).Lun := Get_Source_Unit (Ref);
558 Xrefs.Table (Indx).Ent := Ent;
559 Set_Has_Xref_Entry (Ent);
560 end if;
561 end Generate_Reference;
563 -----------------------------------
564 -- Generate_Reference_To_Formals --
565 -----------------------------------
567 procedure Generate_Reference_To_Formals (E : Entity_Id) is
568 Formal : Entity_Id;
570 begin
571 if Is_Generic_Subprogram (E) then
572 Formal := First_Entity (E);
574 while Present (Formal)
575 and then not Is_Formal (Formal)
576 loop
577 Next_Entity (Formal);
578 end loop;
580 else
581 Formal := First_Formal (E);
582 end if;
584 while Present (Formal) loop
585 if Ekind (Formal) = E_In_Parameter then
587 if Nkind (Parameter_Type (Parent (Formal)))
588 = N_Access_Definition
589 then
590 Generate_Reference (E, Formal, '^', False);
591 else
592 Generate_Reference (E, Formal, '>', False);
593 end if;
595 elsif Ekind (Formal) = E_In_Out_Parameter then
596 Generate_Reference (E, Formal, '=', False);
598 else
599 Generate_Reference (E, Formal, '<', False);
600 end if;
602 Next_Formal (Formal);
603 end loop;
604 end Generate_Reference_To_Formals;
606 -------------------------------------------
607 -- Generate_Reference_To_Generic_Formals --
608 -------------------------------------------
610 procedure Generate_Reference_To_Generic_Formals (E : Entity_Id) is
611 Formal : Entity_Id;
613 begin
614 Formal := First_Entity (E);
616 while Present (Formal) loop
617 if Comes_From_Source (Formal) then
618 Generate_Reference (E, Formal, 'z', False);
619 end if;
621 Next_Entity (Formal);
622 end loop;
623 end Generate_Reference_To_Generic_Formals;
625 ----------------
626 -- Initialize --
627 ----------------
629 procedure Initialize is
630 begin
631 Xrefs.Init;
632 end Initialize;
634 -----------------------
635 -- Output_References --
636 -----------------------
638 procedure Output_References is
640 procedure Get_Type_Reference
641 (Ent : Entity_Id;
642 Tref : out Entity_Id;
643 Left : out Character;
644 Right : out Character);
645 -- Given an entity id Ent, determines whether a type reference is
646 -- required. If so, Tref is set to the entity for the type reference
647 -- and Left and Right are set to the left/right brackets to be
648 -- output for the reference. If no type reference is required, then
649 -- Tref is set to Empty, and Left/Right are set to space.
651 procedure Output_Import_Export_Info (Ent : Entity_Id);
652 -- Ouput language and external name information for an interfaced
653 -- entity, using the format <language, external_name>,
655 ------------------------
656 -- Get_Type_Reference --
657 ------------------------
659 procedure Get_Type_Reference
660 (Ent : Entity_Id;
661 Tref : out Entity_Id;
662 Left : out Character;
663 Right : out Character)
665 Sav : Entity_Id;
667 begin
668 -- See if we have a type reference
670 Tref := Ent;
671 Left := '{';
672 Right := '}';
674 loop
675 Sav := Tref;
677 -- Processing for types
679 if Is_Type (Tref) then
681 -- Case of base type
683 if Base_Type (Tref) = Tref then
685 -- If derived, then get first subtype
687 if Tref /= Etype (Tref) then
688 Tref := First_Subtype (Etype (Tref));
690 -- Set brackets for derived type, but don't
691 -- override pointer case since the fact that
692 -- something is a pointer is more important
694 if Left /= '(' then
695 Left := '<';
696 Right := '>';
697 end if;
699 -- If non-derived ptr, get directly designated type.
700 -- If the type has a full view, all references are
701 -- on the partial view, that is seen first.
703 elsif Is_Access_Type (Tref) then
704 Tref := Directly_Designated_Type (Tref);
705 Left := '(';
706 Right := ')';
708 elsif Is_Private_Type (Tref)
709 and then Present (Full_View (Tref))
710 and then Is_Access_Type (Full_View (Tref))
711 then
712 Tref := Directly_Designated_Type (Full_View (Tref));
713 Left := '(';
714 Right := ')';
716 -- If non-derived array, get component type.
717 -- Skip component type for case of String
718 -- or Wide_String, saves worthwhile space.
720 elsif Is_Array_Type (Tref)
721 and then Tref /= Standard_String
722 and then Tref /= Standard_Wide_String
723 then
724 Tref := Component_Type (Tref);
725 Left := '(';
726 Right := ')';
728 -- For other non-derived base types, nothing
730 else
731 exit;
732 end if;
734 -- For a subtype, go to ancestor subtype
736 else
737 Tref := Ancestor_Subtype (Tref);
739 -- If no ancestor subtype, go to base type
741 if No (Tref) then
742 Tref := Base_Type (Sav);
743 end if;
744 end if;
746 -- For objects, functions, enum literals,
747 -- just get type from Etype field.
749 elsif Is_Object (Tref)
750 or else Ekind (Tref) = E_Enumeration_Literal
751 or else Ekind (Tref) = E_Function
752 or else Ekind (Tref) = E_Operator
753 then
754 Tref := Etype (Tref);
756 -- For anything else, exit
758 else
759 exit;
760 end if;
762 -- Exit if no type reference, or we are stuck in
763 -- some loop trying to find the type reference, or
764 -- if the type is standard void type (the latter is
765 -- an implementation artifact that should not show
766 -- up in the generated cross-references).
768 exit when No (Tref)
769 or else Tref = Sav
770 or else Tref = Standard_Void_Type;
772 -- If we have a usable type reference, return, otherwise
773 -- keep looking for something useful (we are looking for
774 -- something that either comes from source or standard)
776 if Sloc (Tref) = Standard_Location
777 or else Comes_From_Source (Tref)
778 then
779 -- If the reference is a subtype created for a generic
780 -- actual, go to actual directly, the inner subtype is
781 -- not user visible.
783 if Nkind (Parent (Tref)) = N_Subtype_Declaration
784 and then not Comes_From_Source (Parent (Tref))
785 and then
786 (Is_Wrapper_Package (Scope (Tref))
787 or else Is_Generic_Instance (Scope (Tref)))
788 then
789 Tref := First_Subtype (Base_Type (Tref));
790 end if;
792 return;
793 end if;
794 end loop;
796 -- If we fall through the loop, no type reference
798 Tref := Empty;
799 Left := ' ';
800 Right := ' ';
801 end Get_Type_Reference;
803 -------------------------------
804 -- Output_Import_Export_Info --
805 -------------------------------
807 procedure Output_Import_Export_Info (Ent : Entity_Id) is
808 Language_Name : Name_Id;
809 Conv : constant Convention_Id := Convention (Ent);
810 begin
811 if Conv = Convention_C then
812 Language_Name := Name_C;
814 elsif Conv = Convention_CPP then
815 Language_Name := Name_CPP;
817 elsif Conv = Convention_Ada then
818 Language_Name := Name_Ada;
820 else
821 -- These are the only languages that GPS knows about
823 return;
824 end if;
826 Write_Info_Char ('<');
827 Get_Unqualified_Name_String (Language_Name);
829 for J in 1 .. Name_Len loop
830 Write_Info_Char (Name_Buffer (J));
831 end loop;
833 if Present (Interface_Name (Ent)) then
834 Write_Info_Char (',');
835 String_To_Name_Buffer (Strval (Interface_Name (Ent)));
837 for J in 1 .. Name_Len loop
838 Write_Info_Char (Name_Buffer (J));
839 end loop;
840 end if;
842 Write_Info_Char ('>');
843 end Output_Import_Export_Info;
845 -- Start of processing for Output_References
847 begin
848 if not Opt.Xref_Active then
849 return;
850 end if;
852 -- Before we go ahead and output the references we have a problem
853 -- that needs dealing with. So far we have captured things that are
854 -- definitely referenced by the main unit, or defined in the main
855 -- unit. That's because we don't want to clutter up the ali file
856 -- for this unit with definition lines for entities in other units
857 -- that are not referenced.
859 -- But there is a glitch. We may reference an entity in another unit,
860 -- and it may have a type reference to an entity that is not directly
861 -- referenced in the main unit, which may mean that there is no xref
862 -- entry for this entity yet in the list of references.
864 -- If we don't do something about this, we will end with an orphan
865 -- type reference, i.e. it will point to an entity that does not
866 -- appear within the generated references in the ali file. That is
867 -- not good for tools using the xref information.
869 -- To fix this, we go through the references adding definition
870 -- entries for any unreferenced entities that can be referenced
871 -- in a type reference. There is a recursion problem here, and
872 -- that is dealt with by making sure that this traversal also
873 -- traverses any entries that get added by the traversal.
875 declare
876 J : Nat;
877 Tref : Entity_Id;
878 L, R : Character;
879 Indx : Nat;
880 Ent : Entity_Id;
881 Loc : Source_Ptr;
883 begin
884 -- Note that this is not a for loop for a very good reason. The
885 -- processing of items in the table can add new items to the
886 -- table, and they must be processed as well
888 J := 1;
889 while J <= Xrefs.Last loop
890 Ent := Xrefs.Table (J).Ent;
891 Get_Type_Reference (Ent, Tref, L, R);
893 if Present (Tref)
894 and then not Has_Xref_Entry (Tref)
895 and then Sloc (Tref) > No_Location
896 then
897 Xrefs.Increment_Last;
898 Indx := Xrefs.Last;
899 Loc := Original_Location (Sloc (Tref));
900 Xrefs.Table (Indx).Ent := Tref;
901 Xrefs.Table (Indx).Loc := No_Location;
902 Xrefs.Table (Indx).Eun := Get_Source_Unit (Loc);
903 Xrefs.Table (Indx).Lun := No_Unit;
904 Set_Has_Xref_Entry (Tref);
905 end if;
907 -- Collect inherited primitive operations that may be
908 -- declared in another unit and have no visible reference
909 -- in the current one.
911 if Is_Type (Ent)
912 and then Is_Tagged_Type (Ent)
913 and then Is_Derived_Type (Ent)
914 and then Ent = Base_Type (Ent)
915 and then In_Extended_Main_Source_Unit (Ent)
916 then
917 declare
918 Op_List : constant Elist_Id := Primitive_Operations (Ent);
919 Op : Elmt_Id;
920 Prim : Entity_Id;
922 function Parent_Op (E : Entity_Id) return Entity_Id;
923 -- Find original operation, which may be inherited
924 -- through several derivations.
926 function Parent_Op (E : Entity_Id) return Entity_Id is
927 Orig_Op : constant Entity_Id := Alias (E);
928 begin
929 if No (Orig_Op) then
930 return Empty;
931 elsif not Comes_From_Source (E)
932 and then not Has_Xref_Entry (Orig_Op)
933 and then Comes_From_Source (Orig_Op)
934 then
935 return Orig_Op;
936 else
937 return Parent_Op (Orig_Op);
938 end if;
939 end Parent_Op;
941 begin
942 Op := First_Elmt (Op_List);
943 while Present (Op) loop
944 Prim := Parent_Op (Node (Op));
946 if Present (Prim) then
947 Xrefs.Increment_Last;
948 Indx := Xrefs.Last;
949 Loc := Original_Location (Sloc (Prim));
950 Xrefs.Table (Indx).Ent := Prim;
951 Xrefs.Table (Indx).Loc := No_Location;
952 Xrefs.Table (Indx).Eun :=
953 Get_Source_Unit (Sloc (Prim));
954 Xrefs.Table (Indx).Lun := No_Unit;
955 Set_Has_Xref_Entry (Prim);
956 end if;
958 Next_Elmt (Op);
959 end loop;
960 end;
961 end if;
963 J := J + 1;
964 end loop;
965 end;
967 -- Now we have all the references, including those for any embedded
968 -- type references, so we can sort them, and output them.
970 Output_Refs : declare
972 Nrefs : Nat := Xrefs.Last;
973 -- Number of references in table. This value may get reset
974 -- (reduced) when we eliminate duplicate reference entries.
976 Rnums : array (0 .. Nrefs) of Nat;
977 -- This array contains numbers of references in the Xrefs table.
978 -- This list is sorted in output order. The extra 0'th entry is
979 -- convenient for the call to sort. When we sort the table, we
980 -- move the entries in Rnums around, but we do not move the
981 -- original table entries.
983 Curxu : Unit_Number_Type;
984 -- Current xref unit
986 Curru : Unit_Number_Type;
987 -- Current reference unit for one entity
989 Cursrc : Source_Buffer_Ptr;
990 -- Current xref unit source text
992 Curent : Entity_Id;
993 -- Current entity
995 Curnam : String (1 .. Name_Buffer'Length);
996 Curlen : Natural;
997 -- Simple name and length of current entity
999 Curdef : Source_Ptr;
1000 -- Original source location for current entity
1002 Crloc : Source_Ptr;
1003 -- Current reference location
1005 Ctyp : Character;
1006 -- Entity type character
1008 Tref : Entity_Id;
1009 -- Type reference
1011 Rref : Node_Id;
1012 -- Renaming reference
1014 Trunit : Unit_Number_Type;
1015 -- Unit number for type reference
1017 function Lt (Op1, Op2 : Natural) return Boolean;
1018 -- Comparison function for Sort call
1020 function Name_Change (X : Entity_Id) return Boolean;
1021 -- Determines if entity X has a different simple name from Curent
1023 procedure Move (From : Natural; To : Natural);
1024 -- Move procedure for Sort call
1026 --------
1027 -- Lt --
1028 --------
1030 function Lt (Op1, Op2 : Natural) return Boolean is
1031 T1 : Xref_Entry renames Xrefs.Table (Rnums (Nat (Op1)));
1032 T2 : Xref_Entry renames Xrefs.Table (Rnums (Nat (Op2)));
1034 begin
1035 -- First test. If entity is in different unit, sort by unit
1037 if T1.Eun /= T2.Eun then
1038 return Dependency_Num (T1.Eun) < Dependency_Num (T2.Eun);
1040 -- Second test, within same unit, sort by entity Sloc
1042 elsif T1.Def /= T2.Def then
1043 return T1.Def < T2.Def;
1045 -- Third test, sort definitions ahead of references
1047 elsif T1.Loc = No_Location then
1048 return True;
1050 elsif T2.Loc = No_Location then
1051 return False;
1053 -- Fourth test, for same entity, sort by reference location unit
1055 elsif T1.Lun /= T2.Lun then
1056 return Dependency_Num (T1.Lun) < Dependency_Num (T2.Lun);
1058 -- Fifth test order of location within referencing unit
1060 elsif T1.Loc /= T2.Loc then
1061 return T1.Loc < T2.Loc;
1063 -- Finally, for two locations at the same address, we prefer
1064 -- the one that does NOT have the type 'r' so that a modification
1065 -- or extension takes preference, when there are more than one
1066 -- reference at the same location.
1068 else
1069 return T2.Typ = 'r';
1070 end if;
1071 end Lt;
1073 ----------
1074 -- Move --
1075 ----------
1077 procedure Move (From : Natural; To : Natural) is
1078 begin
1079 Rnums (Nat (To)) := Rnums (Nat (From));
1080 end Move;
1082 -----------------
1083 -- Name_Change --
1084 -----------------
1086 function Name_Change (X : Entity_Id) return Boolean is
1087 begin
1088 Get_Unqualified_Name_String (Chars (X));
1090 if Name_Len /= Curlen then
1091 return True;
1093 else
1094 return Name_Buffer (1 .. Curlen) /= Curnam (1 .. Curlen);
1095 end if;
1096 end Name_Change;
1098 -- Start of processing for Output_Refs
1100 begin
1101 -- Capture the definition Sloc values. We delay doing this till now,
1102 -- since at the time the reference or definition is made, private
1103 -- types may be swapped, and the Sloc value may be incorrect. We
1104 -- also set up the pointer vector for the sort.
1106 for J in 1 .. Nrefs loop
1107 Rnums (J) := J;
1108 Xrefs.Table (J).Def :=
1109 Original_Location (Sloc (Xrefs.Table (J).Ent));
1110 end loop;
1112 -- Sort the references
1114 GNAT.Heap_Sort_A.Sort
1115 (Integer (Nrefs),
1116 Move'Unrestricted_Access,
1117 Lt'Unrestricted_Access);
1119 -- Eliminate duplicate entries
1121 declare
1122 NR : constant Nat := Nrefs;
1124 begin
1125 -- We need this test for NR because if we force ALI file
1126 -- generation in case of errors detected, it may be the case
1127 -- that Nrefs is 0, so we should not reset it here
1129 if NR >= 2 then
1130 Nrefs := 1;
1132 for J in 2 .. NR loop
1133 if Xrefs.Table (Rnums (J)) /=
1134 Xrefs.Table (Rnums (Nrefs))
1135 then
1136 Nrefs := Nrefs + 1;
1137 Rnums (Nrefs) := Rnums (J);
1138 end if;
1139 end loop;
1140 end if;
1141 end;
1143 -- Initialize loop through references
1145 Curxu := No_Unit;
1146 Curent := Empty;
1147 Curdef := No_Location;
1148 Curru := No_Unit;
1149 Crloc := No_Location;
1151 -- Loop to output references
1153 for Refno in 1 .. Nrefs loop
1154 Output_One_Ref : declare
1155 P2 : Source_Ptr;
1156 WC : Char_Code;
1157 Err : Boolean;
1158 Ent : Entity_Id;
1160 XE : Xref_Entry renames Xrefs.Table (Rnums (Refno));
1161 -- The current entry to be accessed
1163 P : Source_Ptr;
1164 -- Used to index into source buffer to get entity name
1166 Left : Character;
1167 Right : Character;
1168 -- Used for {} or <> or () for type reference
1170 procedure Output_Instantiation_Refs (Loc : Source_Ptr);
1171 -- Recursive procedure to output instantiation references for
1172 -- the given source ptr in [file|line[...]] form. No output
1173 -- if the given location is not a generic template reference.
1175 procedure Output_Overridden_Op (Old_E : Entity_Id);
1176 -- For a subprogram that is overriding, display information
1177 -- about the inherited operation that it overrides.
1179 -------------------------------
1180 -- Output_Instantiation_Refs --
1181 -------------------------------
1183 procedure Output_Instantiation_Refs (Loc : Source_Ptr) is
1184 Iloc : constant Source_Ptr := Instantiation_Location (Loc);
1185 Lun : Unit_Number_Type;
1186 Cu : constant Unit_Number_Type := Curru;
1188 begin
1189 -- Nothing to do if this is not an instantiation
1191 if Iloc = No_Location then
1192 return;
1193 end if;
1195 -- Output instantiation reference
1197 Write_Info_Char ('[');
1198 Lun := Get_Source_Unit (Iloc);
1200 if Lun /= Curru then
1201 Curru := Lun;
1202 Write_Info_Nat (Dependency_Num (Curru));
1203 Write_Info_Char ('|');
1204 end if;
1206 Write_Info_Nat (Int (Get_Logical_Line_Number (Iloc)));
1208 -- Recursive call to get nested instantiations
1210 Output_Instantiation_Refs (Iloc);
1212 -- Output final ] after call to get proper nesting
1214 Write_Info_Char (']');
1215 Curru := Cu;
1216 return;
1217 end Output_Instantiation_Refs;
1219 --------------------------
1220 -- Output_Overridden_Op --
1221 --------------------------
1223 procedure Output_Overridden_Op (Old_E : Entity_Id) is
1224 begin
1225 if Present (Old_E)
1226 and then Sloc (Old_E) /= Standard_Location
1227 then
1228 declare
1229 Loc : constant Source_Ptr := Sloc (Old_E);
1230 Par_Unit : constant Unit_Number_Type :=
1231 Get_Source_Unit (Loc);
1232 begin
1233 Write_Info_Char ('<');
1235 if Par_Unit /= Curxu then
1236 Write_Info_Nat (Dependency_Num (Par_Unit));
1237 Write_Info_Char ('|');
1238 end if;
1240 Write_Info_Nat (Int (Get_Logical_Line_Number (Loc)));
1241 Write_Info_Char ('p');
1242 Write_Info_Nat (Int (Get_Column_Number (Loc)));
1243 Write_Info_Char ('>');
1244 end;
1245 end if;
1246 end Output_Overridden_Op;
1248 -- Start of processing for Output_One_Ref
1250 begin
1251 Ent := XE.Ent;
1252 Ctyp := Xref_Entity_Letters (Ekind (Ent));
1254 -- Skip reference if it is the only reference to an entity,
1255 -- and it is an end-line reference, and the entity is not in
1256 -- the current extended source. This prevents junk entries
1257 -- consisting only of packages with end lines, where no
1258 -- entity from the package is actually referenced.
1260 if XE.Typ = 'e'
1261 and then Ent /= Curent
1262 and then (Refno = Nrefs or else
1263 Ent /= Xrefs.Table (Rnums (Refno + 1)).Ent)
1264 and then
1265 not In_Extended_Main_Source_Unit (Ent)
1266 then
1267 goto Continue;
1268 end if;
1270 -- For private type, get full view type
1272 if Ctyp = '+'
1273 and then Present (Full_View (XE.Ent))
1274 then
1275 Ent := Underlying_Type (Ent);
1277 if Present (Ent) then
1278 Ctyp := Xref_Entity_Letters (Ekind (Ent));
1279 end if;
1280 end if;
1282 -- Special exception for Boolean
1284 if Ctyp = 'E' and then Is_Boolean_Type (Ent) then
1285 Ctyp := 'B';
1286 end if;
1288 -- For variable reference, get corresponding type
1290 if Ctyp = '*' then
1291 Ent := Etype (XE.Ent);
1292 Ctyp := Fold_Lower (Xref_Entity_Letters (Ekind (Ent)));
1294 -- If variable is private type, get full view type
1296 if Ctyp = '+'
1297 and then Present (Full_View (Etype (XE.Ent)))
1298 then
1299 Ent := Underlying_Type (Etype (XE.Ent));
1301 if Present (Ent) then
1302 Ctyp := Fold_Lower (Xref_Entity_Letters (Ekind (Ent)));
1303 end if;
1305 elsif Is_Generic_Type (Ent) then
1307 -- If the type of the entity is a generic private type
1308 -- there is no usable full view, so retain the indication
1309 -- that this is an object.
1311 Ctyp := '*';
1312 end if;
1314 -- Special handling for access parameter
1316 declare
1317 K : constant Entity_Kind := Ekind (Etype (XE.Ent));
1319 begin
1320 if (K = E_Anonymous_Access_Type
1321 or else
1322 K = E_Anonymous_Access_Subprogram_Type
1323 or else K =
1324 E_Anonymous_Access_Protected_Subprogram_Type)
1325 and then Is_Formal (XE.Ent)
1326 then
1327 Ctyp := 'p';
1329 -- Special handling for Boolean
1331 elsif Ctyp = 'e' and then Is_Boolean_Type (Ent) then
1332 Ctyp := 'b';
1333 end if;
1334 end;
1335 end if;
1337 -- Special handling for abstract types and operations
1339 if Is_Abstract (XE.Ent) then
1341 if Ctyp = 'U' then
1342 Ctyp := 'x'; -- abstract procedure
1344 elsif Ctyp = 'V' then
1345 Ctyp := 'y'; -- abstract function
1347 elsif Ctyp = 'R' then
1348 Ctyp := 'H'; -- abstract type
1349 end if;
1350 end if;
1352 -- Only output reference if interesting type of entity,
1353 -- and suppress self references, except for bodies that
1354 -- act as specs. Also suppress definitions of body formals
1355 -- (we only treat these as references, and the references
1356 -- were separately recorded).
1358 if Ctyp = ' '
1359 or else (XE.Loc = XE.Def
1360 and then
1361 (XE.Typ /= 'b'
1362 or else not Is_Subprogram (XE.Ent)))
1363 or else (Is_Formal (XE.Ent)
1364 and then Present (Spec_Entity (XE.Ent)))
1365 then
1366 null;
1368 else
1369 -- Start new Xref section if new xref unit
1371 if XE.Eun /= Curxu then
1372 if Write_Info_Col > 1 then
1373 Write_Info_EOL;
1374 end if;
1376 Curxu := XE.Eun;
1377 Cursrc := Source_Text (Source_Index (Curxu));
1379 Write_Info_Initiate ('X');
1380 Write_Info_Char (' ');
1381 Write_Info_Nat (Dependency_Num (XE.Eun));
1382 Write_Info_Char (' ');
1383 Write_Info_Name (Reference_Name (Source_Index (XE.Eun)));
1384 end if;
1386 -- Start new Entity line if new entity. Note that we
1387 -- consider two entities the same if they have the same
1388 -- name and source location. This causes entities in
1389 -- instantiations to be treated as though they referred
1390 -- to the template.
1392 if No (Curent)
1393 or else
1394 (XE.Ent /= Curent
1395 and then
1396 (Name_Change (XE.Ent) or else XE.Def /= Curdef))
1397 then
1398 Curent := XE.Ent;
1399 Curdef := XE.Def;
1401 Get_Unqualified_Name_String (Chars (XE.Ent));
1402 Curlen := Name_Len;
1403 Curnam (1 .. Curlen) := Name_Buffer (1 .. Curlen);
1405 if Write_Info_Col > 1 then
1406 Write_Info_EOL;
1407 end if;
1409 -- Write column number information
1411 Write_Info_Nat (Int (Get_Logical_Line_Number (XE.Def)));
1412 Write_Info_Char (Ctyp);
1413 Write_Info_Nat (Int (Get_Column_Number (XE.Def)));
1415 -- Write level information
1417 Write_Level_Info : declare
1418 function Is_Visible_Generic_Entity
1419 (E : Entity_Id) return Boolean;
1420 -- Check whether E is declared in the visible part
1421 -- of a generic package. For source navigation
1422 -- purposes, treat this as a visible entity.
1424 function Is_Private_Record_Component
1425 (E : Entity_Id) return Boolean;
1426 -- Check whether E is a non-inherited component of a
1427 -- private extension. Even if the enclosing record is
1428 -- public, we want to treat the component as private
1429 -- for navigation purposes.
1431 ---------------------------------
1432 -- Is_Private_Record_Component --
1433 ---------------------------------
1435 function Is_Private_Record_Component
1436 (E : Entity_Id) return Boolean
1438 S : constant Entity_Id := Scope (E);
1439 begin
1440 return
1441 Ekind (E) = E_Component
1442 and then Nkind (Declaration_Node (S)) =
1443 N_Private_Extension_Declaration
1444 and then Original_Record_Component (E) = E;
1445 end Is_Private_Record_Component;
1447 -------------------------------
1448 -- Is_Visible_Generic_Entity --
1449 -------------------------------
1451 function Is_Visible_Generic_Entity
1452 (E : Entity_Id) return Boolean
1454 Par : Node_Id;
1456 begin
1457 if Ekind (Scope (E)) /= E_Generic_Package then
1458 return False;
1459 end if;
1461 Par := Parent (E);
1462 while Present (Par) loop
1464 Nkind (Par) = N_Generic_Package_Declaration
1465 then
1466 -- Entity is a generic formal
1468 return False;
1470 elsif
1471 Nkind (Parent (Par)) = N_Package_Specification
1472 then
1473 return
1474 Is_List_Member (Par)
1475 and then List_Containing (Par) =
1476 Visible_Declarations (Parent (Par));
1477 else
1478 Par := Parent (Par);
1479 end if;
1480 end loop;
1482 return False;
1483 end Is_Visible_Generic_Entity;
1485 -- Start of processing for Write_Level_Info
1487 begin
1488 if Is_Hidden (Curent)
1489 or else Is_Private_Record_Component (Curent)
1490 then
1491 Write_Info_Char (' ');
1493 elsif
1494 Is_Public (Curent)
1495 or else Is_Visible_Generic_Entity (Curent)
1496 then
1497 Write_Info_Char ('*');
1499 else
1500 Write_Info_Char (' ');
1501 end if;
1502 end Write_Level_Info;
1504 -- Output entity name. We use the occurrence from the
1505 -- actual source program at the definition point
1507 P := Original_Location (Sloc (XE.Ent));
1509 -- Entity is character literal
1511 if Cursrc (P) = ''' then
1512 Write_Info_Char (Cursrc (P));
1513 Write_Info_Char (Cursrc (P + 1));
1514 Write_Info_Char (Cursrc (P + 2));
1516 -- Entity is operator symbol
1518 elsif Cursrc (P) = '"' or else Cursrc (P) = '%' then
1519 Write_Info_Char (Cursrc (P));
1521 P2 := P;
1522 loop
1523 P2 := P2 + 1;
1524 Write_Info_Char (Cursrc (P2));
1525 exit when Cursrc (P2) = Cursrc (P);
1526 end loop;
1528 -- Entity is identifier
1530 else
1531 loop
1532 if Is_Start_Of_Wide_Char (Cursrc, P) then
1533 Scan_Wide (Cursrc, P, WC, Err);
1534 elsif not Identifier_Char (Cursrc (P)) then
1535 exit;
1536 else
1537 P := P + 1;
1538 end if;
1539 end loop;
1541 for J in
1542 Original_Location (Sloc (XE.Ent)) .. P - 1
1543 loop
1544 Write_Info_Char (Cursrc (J));
1545 end loop;
1546 end if;
1548 -- See if we have a renaming reference
1550 if Is_Object (XE.Ent)
1551 and then Present (Renamed_Object (XE.Ent))
1552 then
1553 Rref := Renamed_Object (XE.Ent);
1555 elsif Is_Overloadable (XE.Ent)
1556 and then Nkind (Parent (Declaration_Node (XE.Ent))) =
1557 N_Subprogram_Renaming_Declaration
1558 then
1559 Rref := Name (Parent (Declaration_Node (XE.Ent)));
1561 elsif Ekind (XE.Ent) = E_Package
1562 and then Nkind (Declaration_Node (XE.Ent)) =
1563 N_Package_Renaming_Declaration
1564 then
1565 Rref := Name (Declaration_Node (XE.Ent));
1567 else
1568 Rref := Empty;
1569 end if;
1571 if Present (Rref) then
1572 if Nkind (Rref) = N_Expanded_Name then
1573 Rref := Selector_Name (Rref);
1574 end if;
1576 if Nkind (Rref) = N_Identifier
1577 or else Nkind (Rref) = N_Operator_Symbol
1578 then
1579 null;
1581 -- For renamed array components, use the array name
1582 -- for the renamed entity, which reflect the fact that
1583 -- in general the whole array is aliased.
1585 elsif Nkind (Rref) = N_Indexed_Component then
1586 if Nkind (Prefix (Rref)) = N_Identifier then
1587 Rref := Prefix (Rref);
1588 elsif Nkind (Prefix (Rref)) = N_Expanded_Name then
1589 Rref := Selector_Name (Prefix (Rref));
1590 else
1591 Rref := Empty;
1592 end if;
1594 else
1595 Rref := Empty;
1596 end if;
1597 end if;
1599 -- Write out renaming reference if we have one
1601 if Present (Rref) then
1602 Write_Info_Char ('=');
1603 Write_Info_Nat
1604 (Int (Get_Logical_Line_Number (Sloc (Rref))));
1605 Write_Info_Char (':');
1606 Write_Info_Nat
1607 (Int (Get_Column_Number (Sloc (Rref))));
1608 end if;
1610 -- Indicate that the entity is in the unit
1611 -- of the current xref xection.
1613 Curru := Curxu;
1615 -- Write out information about generic parent,
1616 -- if entity is an instance.
1618 if Is_Generic_Instance (XE.Ent) then
1619 declare
1620 Gen_Par : constant Entity_Id :=
1621 Generic_Parent
1622 (Specification
1623 (Unit_Declaration_Node (XE.Ent)));
1624 Loc : constant Source_Ptr := Sloc (Gen_Par);
1625 Gen_U : constant Unit_Number_Type :=
1626 Get_Source_Unit (Loc);
1627 begin
1628 Write_Info_Char ('[');
1629 if Curru /= Gen_U then
1630 Write_Info_Nat (Dependency_Num (Gen_U));
1631 Write_Info_Char ('|');
1632 end if;
1634 Write_Info_Nat
1635 (Int (Get_Logical_Line_Number (Loc)));
1636 Write_Info_Char (']');
1637 end;
1638 end if;
1640 -- See if we have a type reference and if so output
1642 Get_Type_Reference (XE.Ent, Tref, Left, Right);
1644 if Present (Tref) then
1646 -- Case of standard entity, output name
1648 if Sloc (Tref) = Standard_Location then
1649 Write_Info_Char (Left);
1650 Write_Info_Name (Chars (Tref));
1651 Write_Info_Char (Right);
1653 -- Case of source entity, output location
1655 else
1656 Write_Info_Char (Left);
1657 Trunit := Get_Source_Unit (Sloc (Tref));
1659 if Trunit /= Curxu then
1660 Write_Info_Nat (Dependency_Num (Trunit));
1661 Write_Info_Char ('|');
1662 end if;
1664 Write_Info_Nat
1665 (Int (Get_Logical_Line_Number (Sloc (Tref))));
1667 declare
1668 Ent : Entity_Id := Tref;
1669 Kind : constant Entity_Kind := Ekind (Ent);
1670 Ctyp : Character := Xref_Entity_Letters (Kind);
1672 begin
1673 if Ctyp = '+'
1674 and then Present (Full_View (Ent))
1675 then
1676 Ent := Underlying_Type (Ent);
1678 if Present (Ent) then
1679 Ctyp := Xref_Entity_Letters (Ekind (Ent));
1680 end if;
1681 end if;
1683 Write_Info_Char (Ctyp);
1684 end;
1686 Write_Info_Nat
1687 (Int (Get_Column_Number (Sloc (Tref))));
1689 -- If the type comes from an instantiation,
1690 -- add the corresponding info.
1692 Output_Instantiation_Refs (Sloc (Tref));
1693 Write_Info_Char (Right);
1694 end if;
1695 end if;
1697 -- If the entity is an overriding operation, write
1698 -- info on operation that was overridden.
1700 if Is_Subprogram (XE.Ent)
1701 and then Is_Overriding_Operation (XE.Ent)
1702 then
1703 Output_Overridden_Op (Overridden_Operation (XE.Ent));
1704 end if;
1706 -- End of processing for entity output
1708 Crloc := No_Location;
1709 end if;
1711 -- Output the reference
1713 if XE.Loc /= No_Location
1714 and then XE.Loc /= Crloc
1715 then
1716 Crloc := XE.Loc;
1718 -- Start continuation if line full, else blank
1720 if Write_Info_Col > 72 then
1721 Write_Info_EOL;
1722 Write_Info_Initiate ('.');
1723 end if;
1725 Write_Info_Char (' ');
1727 -- Output file number if changed
1729 if XE.Lun /= Curru then
1730 Curru := XE.Lun;
1731 Write_Info_Nat (Dependency_Num (Curru));
1732 Write_Info_Char ('|');
1733 end if;
1735 Write_Info_Nat (Int (Get_Logical_Line_Number (XE.Loc)));
1736 Write_Info_Char (XE.Typ);
1738 if Is_Overloadable (XE.Ent)
1739 and then Is_Imported (XE.Ent)
1740 and then XE.Typ = 'b'
1741 then
1742 Output_Import_Export_Info (XE.Ent);
1743 end if;
1745 Write_Info_Nat (Int (Get_Column_Number (XE.Loc)));
1747 Output_Instantiation_Refs (Sloc (XE.Ent));
1748 end if;
1749 end if;
1750 end Output_One_Ref;
1752 <<Continue>>
1753 null;
1754 end loop;
1756 Write_Info_EOL;
1757 end Output_Refs;
1758 end Output_References;
1760 end Lib.Xref;