1 ------------------------------------------------------------------------------
3 -- GNAT COMPILER COMPONENTS --
9 -- Copyright (C) 1998-2004, Free Software Foundation, Inc. --
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. --
22 -- GNAT was originally developed by the GNAT team at New York University. --
23 -- Extensive contributions were provided by Ada Core Technologies Inc. --
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
;
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
;
44 with GNAT
.Heap_Sort_A
;
46 package body Lib
.Xref
is
52 -- The Xref table is used to record references. The Loc field is set
53 -- to No_Location for a definition entry.
55 subtype Xref_Entry_Number
is Int
;
57 type Xref_Entry
is record
59 -- Entity referenced (E parameter to Generate_Reference)
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.
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.
73 -- Reference type (Typ param to Generate_Reference)
75 Eun
: Unit_Number_Type
;
76 -- Unit number corresponding to Ent
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.
84 package Xrefs
is new Table
.Table
(
85 Table_Component_Type
=> Xref_Entry
,
86 Table_Index_Type
=> Xref_Entry_Number
,
88 Table_Initial
=> Alloc
.Xrefs_Initial
,
89 Table_Increment
=> Alloc
.Xrefs_Increment
,
90 Table_Name
=> "Xrefs");
92 -------------------------
93 -- Generate_Definition --
94 -------------------------
96 procedure Generate_Definition
(E
: Entity_Id
) is
101 pragma Assert
(Nkind
(E
) in N_Entity
);
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.
109 -- Definition must come from source
111 and then Comes_From_Source
(E
)
113 -- And must have a reasonable source location that is not
114 -- within an instance (all entities in instances are ignored)
116 and then Sloc
(E
) > No_Location
117 and then Instantiation_Location
(Sloc
(E
)) = No_Location
119 -- And must be a non-internal name from the main source unit
121 and then In_Extended_Main_Source_Unit
(E
)
122 and then not Is_Internal_Name
(Chars
(E
))
124 Xrefs
.Increment_Last
;
126 Loc
:= Original_Location
(Sloc
(E
));
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
);
134 end Generate_Definition
;
136 ---------------------------------
137 -- Generate_Operator_Reference --
138 ---------------------------------
140 procedure Generate_Operator_Reference
145 if not In_Extended_Main_Source_Unit
(N
) then
149 -- If the operator is not a Standard operator, then we generate
150 -- a real reference to the user defined operator.
152 if Sloc
(Entity
(N
)) /= Standard_Location
then
153 Generate_Reference
(Entity
(N
), N
);
155 -- A reference to an implicit inequality operator is a also a
156 -- reference to the user-defined equality.
158 if Nkind
(N
) = N_Op_Ne
159 and then not Comes_From_Source
(Entity
(N
))
160 and then Present
(Corresponding_Equality
(Entity
(N
)))
162 Generate_Reference
(Corresponding_Equality
(Entity
(N
)), N
);
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.
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).
179 elsif Comes_From_Source
(N
) then
180 Set_Referenced
(First_Subtype
(T
));
182 end Generate_Operator_Reference
;
184 ------------------------
185 -- Generate_Reference --
186 ------------------------
188 procedure Generate_Reference
191 Typ
: Character := 'r';
192 Set_Ref
: Boolean := True;
193 Force
: Boolean := False)
202 pragma Assert
(Nkind
(E
) in N_Entity
);
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.
211 if not In_Extended_Main_Source_Unit
(N
)
219 -- For reference type p, the entity must be in main source unit
221 if Typ
= 'p' and then not In_Extended_Main_Source_Unit
(E
) then
225 -- Unless the reference is forced, we ignore references where
226 -- the reference itself does not come from Source.
228 if not Force
and then not Comes_From_Source
(N
) then
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).
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.
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
))
252 Set_Referenced_As_LHS
(E
);
254 -- Check for a reference in a pragma that should not count as a
255 -- making the variable referenced for warning purposes.
257 elsif Is_Non_Significant_Pragma_Reference
(N
) then
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
266 elsif Nkind
(Parent
(N
)) = N_Attribute_Definition_Clause
267 and then Chars
(Parent
(N
)) /= Name_Address
268 and then N
= Name
(Parent
(N
))
272 -- Any other occurrence counts as referencing the entity
278 -- Check for pragma Unreferenced given and reference is within
279 -- this source unit (occasion for possible warning to be issued)
281 if Has_Pragma_Unreferenced
(E
)
282 and then In_Same_Extended_Unit
(Sloc
(E
), Sloc
(N
))
284 -- A reference as a named parameter in a call does not count
285 -- as a violation of pragma Unreferenced for this purpose.
287 if Nkind
(N
) = N_Identifier
288 and then Nkind
(Parent
(N
)) = N_Parameter_Association
289 and then Selector_Name
(Parent
(N
)) = N
293 -- Neither does a reference to a variable on the left side
296 elsif Ekind
(E
) = E_Variable
297 and then Nkind
(Parent
(N
)) = N_Assignment_Statement
298 and then Name
(Parent
(N
)) = N
302 -- Here we issue the warning, since this is a real reference
305 Error_Msg_NE
("?pragma Unreferenced given for&", N
, E
);
309 -- If this is a subprogram instance, mark as well the internal
310 -- subprogram in the wrapper package, which may be a visible
313 if Is_Overloadable
(E
)
314 and then Is_Generic_Instance
(E
)
315 and then Present
(Alias
(E
))
317 Set_Referenced
(Alias
(E
));
321 -- Generate reference if all conditions are met:
324 -- Cross referencing must be active
328 -- The entity must be one for which we collect references
330 and then Xref_Entity_Letters
(Ekind
(E
)) /= ' '
332 -- Both Sloc values must be set to something sensible
334 and then Sloc
(E
) > No_Location
335 and then Sloc
(N
) > No_Location
337 -- We ignore references from within an instance
339 and then Instantiation_Location
(Sloc
(N
)) = No_Location
341 -- Ignore dummy references
345 if Nkind
(N
) = N_Identifier
347 Nkind
(N
) = N_Defining_Identifier
351 Nkind
(N
) = N_Defining_Operator_Symbol
353 Nkind
(N
) = N_Operator_Symbol
355 (Nkind
(N
) = N_Character_Literal
356 and then Sloc
(Entity
(N
)) /= Standard_Location
)
358 Nkind
(N
) = N_Defining_Character_Literal
362 elsif Nkind
(N
) = N_Expanded_Name
364 Nkind
(N
) = N_Selected_Component
366 Nod
:= Selector_Name
(N
);
372 -- Normal case of source entity comes from source
374 if Comes_From_Source
(E
) then
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.
381 elsif Is_Overloadable
(E
)
382 and then Present
(Alias
(E
))
387 if Comes_From_Source
(Ent
) then
389 elsif No
(Alias
(Ent
)) then
396 -- Record components of discriminated subtypes or derived types
397 -- must be treated as references to the original component.
399 elsif Ekind
(E
) = E_Component
400 and then Comes_From_Source
(Original_Record_Component
(E
))
402 Ent
:= Original_Record_Component
(E
);
404 -- Ignore reference to any other entity that is not from source
410 -- Record reference to entity
412 Ref
:= Original_Location
(Sloc
(Nod
));
413 Def
:= Original_Location
(Sloc
(Ent
));
415 Xrefs
.Increment_Last
;
418 Xrefs
.Table
(Indx
).Loc
:= Ref
;
420 -- Overriding operations are marked with 'P'.
423 and then Is_Subprogram
(N
)
424 and then Is_Overriding_Operation
(N
)
426 Xrefs
.Table
(Indx
).Typ
:= 'P';
428 Xrefs
.Table
(Indx
).Typ
:= Typ
;
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
);
436 end Generate_Reference
;
438 -----------------------------------
439 -- Generate_Reference_To_Formals --
440 -----------------------------------
442 procedure Generate_Reference_To_Formals
(E
: Entity_Id
) is
446 if Is_Generic_Subprogram
(E
) then
447 Formal
:= First_Entity
(E
);
449 while Present
(Formal
)
450 and then not Is_Formal
(Formal
)
452 Next_Entity
(Formal
);
456 Formal
:= First_Formal
(E
);
459 while Present
(Formal
) loop
460 if Ekind
(Formal
) = E_In_Parameter
then
462 if Nkind
(Parameter_Type
(Parent
(Formal
)))
463 = N_Access_Definition
465 Generate_Reference
(E
, Formal
, '^', False);
467 Generate_Reference
(E
, Formal
, '>', False);
470 elsif Ekind
(Formal
) = E_In_Out_Parameter
then
471 Generate_Reference
(E
, Formal
, '=', False);
474 Generate_Reference
(E
, Formal
, '<', False);
477 Next_Formal
(Formal
);
479 end Generate_Reference_To_Formals
;
481 -------------------------------------------
482 -- Generate_Reference_To_Generic_Formals --
483 -------------------------------------------
485 procedure Generate_Reference_To_Generic_Formals
(E
: Entity_Id
) is
489 Formal
:= First_Entity
(E
);
491 while Present
(Formal
) loop
492 if Comes_From_Source
(Formal
) then
493 Generate_Reference
(E
, Formal
, 'z', False);
496 Next_Entity
(Formal
);
498 end Generate_Reference_To_Generic_Formals
;
504 procedure Initialize
is
509 -----------------------
510 -- Output_References --
511 -----------------------
513 procedure Output_References
is
515 procedure Get_Type_Reference
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.
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>,
530 ------------------------
531 -- Get_Type_Reference --
532 ------------------------
534 procedure Get_Type_Reference
536 Tref
: out Entity_Id
;
537 Left
: out Character;
538 Right
: out Character)
543 -- See if we have a type reference
552 -- Processing for types
554 if Is_Type
(Tref
) then
558 if Base_Type
(Tref
) = Tref
then
560 -- If derived, then get first subtype
562 if Tref
/= Etype
(Tref
) then
563 Tref
:= First_Subtype
(Etype
(Tref
));
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
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.
578 elsif Is_Access_Type
(Tref
) then
579 Tref
:= Directly_Designated_Type
(Tref
);
583 elsif Is_Private_Type
(Tref
)
584 and then Present
(Full_View
(Tref
))
585 and then Is_Access_Type
(Full_View
(Tref
))
587 Tref
:= Directly_Designated_Type
(Full_View
(Tref
));
591 -- If non-derived array, get component type.
592 -- Skip component type for case of String
593 -- or Wide_String, saves worthwhile space.
595 elsif Is_Array_Type
(Tref
)
596 and then Tref
/= Standard_String
597 and then Tref
/= Standard_Wide_String
599 Tref
:= Component_Type
(Tref
);
603 -- For other non-derived base types, nothing
609 -- For a subtype, go to ancestor subtype.
612 Tref
:= Ancestor_Subtype
(Tref
);
614 -- If no ancestor subtype, go to base type
617 Tref
:= Base_Type
(Sav
);
621 -- For objects, functions, enum literals,
622 -- just get type from Etype field.
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
629 Tref
:= Etype
(Tref
);
631 -- For anything else, exit
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).
645 or else Tref
= Standard_Void_Type
;
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)
651 if Sloc
(Tref
) = Standard_Location
652 or else Comes_From_Source
(Tref
)
654 -- If the reference is a subtype created for a generic
655 -- actual, go to actual directly, the inner subtype is
658 if Nkind
(Parent
(Tref
)) = N_Subtype_Declaration
659 and then not Comes_From_Source
(Parent
(Tref
))
661 (Is_Wrapper_Package
(Scope
(Tref
))
662 or else Is_Generic_Instance
(Scope
(Tref
)))
664 Tref
:= Base_Type
(Tref
);
671 -- If we fall through the loop, no type reference
676 end Get_Type_Reference
;
678 -------------------------------
679 -- Output_Import_Export_Info --
680 -------------------------------
682 procedure Output_Import_Export_Info
(Ent
: Entity_Id
) is
683 Language_Name
: Name_Id
;
684 Conv
: constant Convention_Id
:= Convention
(Ent
);
686 if Conv
= Convention_C
then
687 Language_Name
:= Name_C
;
689 elsif Conv
= Convention_CPP
then
690 Language_Name
:= Name_CPP
;
692 elsif Conv
= Convention_Ada
then
693 Language_Name
:= Name_Ada
;
696 -- These are the only languages that GPS knows about.
701 Write_Info_Char
('<');
702 Get_Unqualified_Name_String
(Language_Name
);
704 for J
in 1 .. Name_Len
loop
705 Write_Info_Char
(Name_Buffer
(J
));
708 if Present
(Interface_Name
(Ent
)) then
709 Write_Info_Char
(',');
710 String_To_Name_Buffer
(Strval
(Interface_Name
(Ent
)));
712 for J
in 1 .. Name_Len
loop
713 Write_Info_Char
(Name_Buffer
(J
));
717 Write_Info_Char
('>');
718 end Output_Import_Export_Info
;
720 -- Start of processing for Output_References
723 if not Opt
.Xref_Active
then
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.
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.
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.
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.
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
764 while J
<= Xrefs
.Last
loop
765 Ent
:= Xrefs
.Table
(J
).Ent
;
766 Get_Type_Reference
(Ent
, Tref
, L
, R
);
769 and then not Has_Xref_Entry
(Tref
)
770 and then Sloc
(Tref
) > No_Location
772 Xrefs
.Increment_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
);
782 -- Collect inherited primitive operations that may be
783 -- declared in another unit and have no visible reference
784 -- in the current one.
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
)
793 Op_List
: constant Elist_Id
:= Primitive_Operations
(Ent
);
797 function Parent_Op
(E
: Entity_Id
) return Entity_Id
;
798 -- Find original operation, which may be inherited
799 -- through several derivations.
801 function Parent_Op
(E
: Entity_Id
) return Entity_Id
is
802 Orig_Op
: constant Entity_Id
:= Alias
(E
);
806 elsif not Comes_From_Source
(E
)
807 and then not Has_Xref_Entry
(Orig_Op
)
808 and then Comes_From_Source
(Orig_Op
)
812 return Parent_Op
(Orig_Op
);
817 Op
:= First_Elmt
(Op_List
);
818 while Present
(Op
) loop
819 Prim
:= Parent_Op
(Node
(Op
));
821 if Present
(Prim
) then
822 Xrefs
.Increment_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
);
842 -- Now we have all the references, including those for any embedded
843 -- type references, so we can sort them, and output them.
845 Output_Refs
: declare
847 Nrefs
: Nat
:= Xrefs
.Last
;
848 -- Number of references in table. This value may get reset
849 -- (reduced) when we eliminate duplicate reference entries.
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.
858 Curxu
: Unit_Number_Type
;
861 Curru
: Unit_Number_Type
;
862 -- Current reference unit for one entity
864 Cursrc
: Source_Buffer_Ptr
;
865 -- Current xref unit source text
870 Curnam
: String (1 .. Name_Buffer
'Length);
872 -- Simple name and length of current entity
875 -- Original source location for current entity
878 -- Current reference location
881 -- Entity type character
887 -- Renaming reference
889 Trunit
: Unit_Number_Type
;
890 -- Unit number for type reference
892 function Lt
(Op1
, Op2
: Natural) return Boolean;
893 -- Comparison function for Sort call
895 function Name_Change
(X
: Entity_Id
) return Boolean;
896 -- Determines if entity X has a different simple name from Curent
898 procedure Move
(From
: Natural; To
: Natural);
899 -- Move procedure for Sort call
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
)));
910 -- First test. If entity is in different unit, sort by unit
912 if T1
.Eun
/= T2
.Eun
then
913 return Dependency_Num
(T1
.Eun
) < Dependency_Num
(T2
.Eun
);
915 -- Second test, within same unit, sort by entity Sloc
917 elsif T1
.Def
/= T2
.Def
then
918 return T1
.Def
< T2
.Def
;
920 -- Third test, sort definitions ahead of references
922 elsif T1
.Loc
= No_Location
then
925 elsif T2
.Loc
= No_Location
then
928 -- Fourth test, for same entity, sort by reference location unit
930 elsif T1
.Lun
/= T2
.Lun
then
931 return Dependency_Num
(T1
.Lun
) < Dependency_Num
(T2
.Lun
);
933 -- Fifth test order of location within referencing unit
935 elsif T1
.Loc
/= T2
.Loc
then
936 return T1
.Loc
< T2
.Loc
;
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.
952 procedure Move
(From
: Natural; To
: Natural) is
954 Rnums
(Nat
(To
)) := Rnums
(Nat
(From
));
961 function Name_Change
(X
: Entity_Id
) return Boolean is
963 Get_Unqualified_Name_String
(Chars
(X
));
965 if Name_Len
/= Curlen
then
969 return Name_Buffer
(1 .. Curlen
) /= Curnam
(1 .. Curlen
);
973 -- Start of processing for Output_Refs
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.
981 for J
in 1 .. Nrefs
loop
983 Xrefs
.Table
(J
).Def
:=
984 Original_Location
(Sloc
(Xrefs
.Table
(J
).Ent
));
987 -- Sort the references
989 GNAT
.Heap_Sort_A
.Sort
991 Move
'Unrestricted_Access,
992 Lt
'Unrestricted_Access);
994 -- Eliminate duplicate entries
997 NR
: constant Nat
:= Nrefs
;
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
1007 for J
in 2 .. NR
loop
1008 if Xrefs
.Table
(Rnums
(J
)) /=
1009 Xrefs
.Table
(Rnums
(Nrefs
))
1012 Rnums
(Nrefs
) := Rnums
(J
);
1018 -- Initialize loop through references
1022 Curdef
:= No_Location
;
1024 Crloc
:= No_Location
;
1026 -- Loop to output references
1028 for Refno
in 1 .. Nrefs
loop
1029 Output_One_Ref
: declare
1035 XE
: Xref_Entry
renames Xrefs
.Table
(Rnums
(Refno
));
1036 -- The current entry to be accessed
1039 -- Used to index into source buffer to get entity name
1043 -- Used for {} or <> or () for type reference
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.
1050 -------------------------------
1051 -- Output_Instantiation_Refs --
1052 -------------------------------
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
;
1060 -- Nothing to do if this is not an instantiation
1062 if Iloc
= No_Location
then
1066 -- Output instantiation reference
1068 Write_Info_Char
('[');
1069 Lun
:= Get_Source_Unit
(Iloc
);
1071 if Lun
/= Curru
then
1073 Write_Info_Nat
(Dependency_Num
(Curru
));
1074 Write_Info_Char
('|');
1077 Write_Info_Nat
(Int
(Get_Logical_Line_Number
(Iloc
)));
1079 -- Recursive call to get nested instantiations
1081 Output_Instantiation_Refs
(Iloc
);
1083 -- Output final ] after call to get proper nesting
1085 Write_Info_Char
(']');
1088 end Output_Instantiation_Refs
;
1090 -- Start of processing for Output_One_Ref
1094 Ctyp
:= Xref_Entity_Letters
(Ekind
(Ent
));
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.
1103 and then Ent
/= Curent
1104 and then (Refno
= Nrefs
or else
1105 Ent
/= Xrefs
.Table
(Rnums
(Refno
+ 1)).Ent
)
1107 not In_Extended_Main_Source_Unit
(Ent
)
1112 -- For private type, get full view type
1115 and then Present
(Full_View
(XE
.Ent
))
1117 Ent
:= Underlying_Type
(Ent
);
1119 if Present
(Ent
) then
1120 Ctyp
:= Xref_Entity_Letters
(Ekind
(Ent
));
1124 -- Special exception for Boolean
1126 if Ctyp
= 'E' and then Is_Boolean_Type
(Ent
) then
1130 -- For variable reference, get corresponding type
1133 Ent
:= Etype
(XE
.Ent
);
1134 Ctyp
:= Fold_Lower
(Xref_Entity_Letters
(Ekind
(Ent
)));
1136 -- If variable is private type, get full view type
1139 and then Present
(Full_View
(Etype
(XE
.Ent
)))
1141 Ent
:= Underlying_Type
(Etype
(XE
.Ent
));
1143 if Present
(Ent
) then
1144 Ctyp
:= Fold_Lower
(Xref_Entity_Letters
(Ekind
(Ent
)));
1148 -- Special handling for access parameter
1150 if Ekind
(Etype
(XE
.Ent
)) = E_Anonymous_Access_Type
1151 and then Is_Formal
(XE
.Ent
)
1155 -- Special handling for Boolean
1157 elsif Ctyp
= 'e' and then Is_Boolean_Type
(Ent
) then
1162 -- Special handling for abstract types and operations.
1164 if Is_Abstract
(XE
.Ent
) then
1167 Ctyp
:= 'x'; -- abstract procedure
1169 elsif Ctyp
= 'V' then
1170 Ctyp
:= 'y'; -- abstract function
1172 elsif Ctyp
= 'R' then
1173 Ctyp
:= 'H'; -- abstract type
1177 -- Only output reference if interesting type of entity,
1178 -- and suppress self references, except for bodies that
1179 -- act as specs. Also suppress definitions of body formals
1180 -- (we only treat these as references, and the references
1181 -- were separately recorded).
1184 or else (XE
.Loc
= XE
.Def
1187 or else not Is_Subprogram
(XE
.Ent
)))
1188 or else (Is_Formal
(XE
.Ent
)
1189 and then Present
(Spec_Entity
(XE
.Ent
)))
1194 -- Start new Xref section if new xref unit
1196 if XE
.Eun
/= Curxu
then
1197 if Write_Info_Col
> 1 then
1202 Cursrc
:= Source_Text
(Source_Index
(Curxu
));
1204 Write_Info_Initiate
('X');
1205 Write_Info_Char
(' ');
1206 Write_Info_Nat
(Dependency_Num
(XE
.Eun
));
1207 Write_Info_Char
(' ');
1208 Write_Info_Name
(Reference_Name
(Source_Index
(XE
.Eun
)));
1211 -- Start new Entity line if new entity. Note that we
1212 -- consider two entities the same if they have the same
1213 -- name and source location. This causes entities in
1214 -- instantiations to be treated as though they referred
1221 (Name_Change
(XE
.Ent
) or else XE
.Def
/= Curdef
))
1226 Get_Unqualified_Name_String
(Chars
(XE
.Ent
));
1228 Curnam
(1 .. Curlen
) := Name_Buffer
(1 .. Curlen
);
1230 if Write_Info_Col
> 1 then
1234 -- Write column number information
1236 Write_Info_Nat
(Int
(Get_Logical_Line_Number
(XE
.Def
)));
1237 Write_Info_Char
(Ctyp
);
1238 Write_Info_Nat
(Int
(Get_Column_Number
(XE
.Def
)));
1240 -- Write level information
1242 Write_Level_Info
: declare
1243 function Is_Visible_Generic_Entity
1244 (E
: Entity_Id
) return Boolean;
1245 -- Check whether E is declared in the visible part
1246 -- of a generic package. For source navigation
1247 -- purposes, treat this as a visible entity.
1249 function Is_Private_Record_Component
1250 (E
: Entity_Id
) return Boolean;
1251 -- Check whether E is a non-inherited component of a
1252 -- private extension. Even if the enclosing record is
1253 -- public, we want to treat the component as private
1254 -- for navigation purposes.
1256 ---------------------------------
1257 -- Is_Private_Record_Component --
1258 ---------------------------------
1260 function Is_Private_Record_Component
1261 (E
: Entity_Id
) return Boolean
1263 S
: constant Entity_Id
:= Scope
(E
);
1266 Ekind
(E
) = E_Component
1267 and then Nkind
(Declaration_Node
(S
)) =
1268 N_Private_Extension_Declaration
1269 and then Original_Record_Component
(E
) = E
;
1270 end Is_Private_Record_Component
;
1272 -------------------------------
1273 -- Is_Visible_Generic_Entity --
1274 -------------------------------
1276 function Is_Visible_Generic_Entity
1277 (E
: Entity_Id
) return Boolean
1282 if Ekind
(Scope
(E
)) /= E_Generic_Package
then
1287 while Present
(Par
) loop
1289 Nkind
(Par
) = N_Generic_Package_Declaration
1291 -- Entity is a generic formal
1296 Nkind
(Parent
(Par
)) = N_Package_Specification
1299 Is_List_Member
(Par
)
1300 and then List_Containing
(Par
) =
1301 Visible_Declarations
(Parent
(Par
));
1303 Par
:= Parent
(Par
);
1308 end Is_Visible_Generic_Entity
;
1310 -- Start of processing for Write_Level_Info
1313 if Is_Hidden
(Curent
)
1314 or else Is_Private_Record_Component
(Curent
)
1316 Write_Info_Char
(' ');
1320 or else Is_Visible_Generic_Entity
(Curent
)
1322 Write_Info_Char
('*');
1325 Write_Info_Char
(' ');
1327 end Write_Level_Info
;
1329 -- Output entity name. We use the occurrence from the
1330 -- actual source program at the definition point
1332 P
:= Original_Location
(Sloc
(XE
.Ent
));
1334 -- Entity is character literal
1336 if Cursrc
(P
) = ''' then
1337 Write_Info_Char
(Cursrc
(P
));
1338 Write_Info_Char
(Cursrc
(P
+ 1));
1339 Write_Info_Char
(Cursrc
(P
+ 2));
1341 -- Entity is operator symbol
1343 elsif Cursrc
(P
) = '"' or else Cursrc
(P
) = '%' then
1344 Write_Info_Char
(Cursrc
(P
));
1349 Write_Info_Char
(Cursrc
(P2
));
1350 exit when Cursrc
(P2
) = Cursrc
(P
);
1353 -- Entity is identifier
1357 if Is_Start_Of_Wide_Char
(Cursrc
, P
) then
1358 Scan_Wide
(Cursrc
, P
, WC
, Err
);
1359 elsif not Identifier_Char
(Cursrc
(P
)) then
1367 Original_Location
(Sloc
(XE
.Ent
)) .. P
- 1
1369 Write_Info_Char
(Cursrc
(J
));
1373 -- See if we have a renaming reference
1375 if Is_Object
(XE
.Ent
)
1376 and then Present
(Renamed_Object
(XE
.Ent
))
1378 Rref
:= Renamed_Object
(XE
.Ent
);
1380 elsif Is_Overloadable
(XE
.Ent
)
1381 and then Nkind
(Parent
(Declaration_Node
(XE
.Ent
))) =
1382 N_Subprogram_Renaming_Declaration
1384 Rref
:= Name
(Parent
(Declaration_Node
(XE
.Ent
)));
1386 elsif Ekind
(XE
.Ent
) = E_Package
1387 and then Nkind
(Declaration_Node
(XE
.Ent
)) =
1388 N_Package_Renaming_Declaration
1390 Rref
:= Name
(Declaration_Node
(XE
.Ent
));
1396 if Present
(Rref
) then
1397 if Nkind
(Rref
) = N_Expanded_Name
then
1398 Rref
:= Selector_Name
(Rref
);
1401 if Nkind
(Rref
) /= N_Identifier
then
1406 -- Write out renaming reference if we have one
1408 if Present
(Rref
) then
1409 Write_Info_Char
('=');
1411 (Int
(Get_Logical_Line_Number
(Sloc
(Rref
))));
1412 Write_Info_Char
(':');
1414 (Int
(Get_Column_Number
(Sloc
(Rref
))));
1417 -- Indicate that the entity is in the unit
1418 -- of the current xref xection.
1422 -- See if we have a type reference and if so output
1424 Get_Type_Reference
(XE
.Ent
, Tref
, Left
, Right
);
1426 if Present
(Tref
) then
1428 -- Case of standard entity, output name
1430 if Sloc
(Tref
) = Standard_Location
then
1431 Write_Info_Char
(Left
);
1432 Write_Info_Name
(Chars
(Tref
));
1433 Write_Info_Char
(Right
);
1435 -- Case of source entity, output location
1438 Write_Info_Char
(Left
);
1439 Trunit
:= Get_Source_Unit
(Sloc
(Tref
));
1441 if Trunit
/= Curxu
then
1442 Write_Info_Nat
(Dependency_Num
(Trunit
));
1443 Write_Info_Char
('|');
1447 (Int
(Get_Logical_Line_Number
(Sloc
(Tref
))));
1450 Ent
: Entity_Id
:= Tref
;
1451 Kind
: constant Entity_Kind
:= Ekind
(Ent
);
1452 Ctyp
: Character := Xref_Entity_Letters
(Kind
);
1456 and then Present
(Full_View
(Ent
))
1458 Ent
:= Underlying_Type
(Ent
);
1460 if Present
(Ent
) then
1461 Ctyp
:= Xref_Entity_Letters
(Ekind
(Ent
));
1465 Write_Info_Char
(Ctyp
);
1469 (Int
(Get_Column_Number
(Sloc
(Tref
))));
1471 -- If the type comes from an instantiation,
1472 -- add the corresponding info.
1474 Output_Instantiation_Refs
(Sloc
(Tref
));
1475 Write_Info_Char
(Right
);
1479 -- End of processing for entity output
1481 Crloc
:= No_Location
;
1484 -- Output the reference
1486 if XE
.Loc
/= No_Location
1487 and then XE
.Loc
/= Crloc
1491 -- Start continuation if line full, else blank
1493 if Write_Info_Col
> 72 then
1495 Write_Info_Initiate
('.');
1498 Write_Info_Char
(' ');
1500 -- Output file number if changed
1502 if XE
.Lun
/= Curru
then
1504 Write_Info_Nat
(Dependency_Num
(Curru
));
1505 Write_Info_Char
('|');
1508 Write_Info_Nat
(Int
(Get_Logical_Line_Number
(XE
.Loc
)));
1509 Write_Info_Char
(XE
.Typ
);
1511 if Is_Overloadable
(XE
.Ent
)
1512 and then Is_Imported
(XE
.Ent
)
1513 and then XE
.Typ
= 'b'
1515 Output_Import_Export_Info
(XE
.Ent
);
1518 Write_Info_Nat
(Int
(Get_Column_Number
(XE
.Loc
)));
1520 Output_Instantiation_Refs
(Sloc
(XE
.Ent
));
1531 end Output_References
;