1 ------------------------------------------------------------------------------
3 -- GNAT COMPILER COMPONENTS --
9 -- Copyright (C) 1998-2006, 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, 51 Franklin Street, Fifth Floor, --
20 -- Boston, MA 02110-1301, 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 Restrict
; use Restrict
;
36 with Rident
; use Rident
;
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
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
63 -- Entity referenced (E parameter to Generate_Reference)
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.
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.
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.
88 package Xrefs
is new Table
.Table
(
89 Table_Component_Type
=> Xref_Entry
,
90 Table_Index_Type
=> Xref_Entry_Number
,
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
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.
113 -- Definition must come from source
114 -- We make an exception for subprogram child units that have no
115 -- spec. For these we generate a subprogram declaration for library
116 -- use, and the corresponding entity does not come from source.
117 -- Nevertheless, all references will be attached to it and we have
118 -- to treat is as coming from user code.
120 and then (Comes_From_Source
(E
) or else Is_Child_Unit
(E
))
122 -- And must have a reasonable source location that is not
123 -- within an instance (all entities in instances are ignored)
125 and then Sloc
(E
) > No_Location
126 and then Instantiation_Location
(Sloc
(E
)) = No_Location
128 -- And must be a non-internal name from the main source unit
130 and then In_Extended_Main_Source_Unit
(E
)
131 and then not Is_Internal_Name
(Chars
(E
))
133 Xrefs
.Increment_Last
;
135 Loc
:= Original_Location
(Sloc
(E
));
137 Xrefs
.Table
(Indx
).Ent
:= E
;
138 Xrefs
.Table
(Indx
).Loc
:= No_Location
;
139 Xrefs
.Table
(Indx
).Eun
:= Get_Source_Unit
(Loc
);
140 Xrefs
.Table
(Indx
).Lun
:= No_Unit
;
141 Set_Has_Xref_Entry
(E
);
143 if In_Inlined_Body
then
147 end Generate_Definition
;
149 ---------------------------------
150 -- Generate_Operator_Reference --
151 ---------------------------------
153 procedure Generate_Operator_Reference
158 if not In_Extended_Main_Source_Unit
(N
) then
162 -- If the operator is not a Standard operator, then we generate
163 -- a real reference to the user defined operator.
165 if Sloc
(Entity
(N
)) /= Standard_Location
then
166 Generate_Reference
(Entity
(N
), N
);
168 -- A reference to an implicit inequality operator is a also a
169 -- reference to the user-defined equality.
171 if Nkind
(N
) = N_Op_Ne
172 and then not Comes_From_Source
(Entity
(N
))
173 and then Present
(Corresponding_Equality
(Entity
(N
)))
175 Generate_Reference
(Corresponding_Equality
(Entity
(N
)), N
);
178 -- For the case of Standard operators, we mark the result type
179 -- as referenced. This ensures that in the case where we are
180 -- using a derived operator, we mark an entity of the unit that
181 -- implicitly defines this operator as used. Otherwise we may
182 -- think that no entity of the unit is used. The actual entity
183 -- marked as referenced is the first subtype, which is the user
184 -- defined entity that is relevant.
186 -- Note: we only do this for operators that come from source.
187 -- The generated code sometimes reaches for entities that do
188 -- not need to be explicitly visible (for example, when we
189 -- expand the code for comparing two record types, the fields
190 -- of the record may not be visible).
192 elsif Comes_From_Source
(N
) then
193 Set_Referenced
(First_Subtype
(T
));
195 end Generate_Operator_Reference
;
197 ------------------------
198 -- Generate_Reference --
199 ------------------------
201 procedure Generate_Reference
204 Typ
: Character := 'r';
205 Set_Ref
: Boolean := True;
206 Force
: Boolean := False)
214 function Is_On_LHS
(Node
: Node_Id
) return Boolean;
215 -- Used to check if a node is on the left hand side of an
216 -- assignment. The following cases are handled:
218 -- Variable Node is a direct descendant of an assignment
221 -- Prefix Of an indexed or selected component that is
222 -- present in a subtree rooted by an assignment
223 -- statement. There is no restriction of nesting
224 -- of components, thus cases such as A.B(C).D are
231 -- Couldn't we use Is_Lvalue or whatever it is called ???
233 function Is_On_LHS
(Node
: Node_Id
) return Boolean is
237 -- Only identifiers are considered, is this necessary???
239 if Nkind
(N
) /= N_Identifier
then
243 -- Reach the assignment statement subtree root. In the
244 -- case of a variable being a direct descendant of an
245 -- assignment statement, the loop is skiped.
247 while Nkind
(Parent
(N
)) /= N_Assignment_Statement
loop
249 -- Check whether the parent is a component and the
250 -- current node is its prefix.
252 if (Nkind
(Parent
(N
)) = N_Selected_Component
254 Nkind
(Parent
(N
)) = N_Indexed_Component
)
255 and then Prefix
(Parent
(N
)) = N
263 -- Parent (N) is assignment statement, check whether N is its name
265 return Name
(Parent
(N
)) = N
;
268 -- Start of processing for Generate_Reference
271 pragma Assert
(Nkind
(E
) in N_Entity
);
273 -- Check for obsolescent reference to ASCII
275 if E
= Standard_ASCII
then
276 Check_Restriction
(No_Obsolescent_Features
, N
);
279 -- Warn if reference to Ada 2005 entity not in Ada 2005 mode. We only
280 -- detect real explicit references (modifications and references).
283 and then Ada_Version
< Ada_05
284 and then Warn_On_Ada_2005_Compatibility
285 and then (Typ
= 'm' or else Typ
= 'r')
287 Error_Msg_NE
("& is only defined in Ada 2005?", N
, E
);
290 -- Never collect references if not in main source unit. However, we omit
291 -- this test if Typ is 'e' or 'k', since these entries are structural,
292 -- and it is useful to have them in units that reference packages as
293 -- well as units that define packages. We also omit the test for the
294 -- case of 'p' since we want to include inherited primitive operations
295 -- from other packages.
297 if not In_Extended_Main_Source_Unit
(N
)
305 -- For reference type p, the entity must be in main source unit
307 if Typ
= 'p' and then not In_Extended_Main_Source_Unit
(E
) then
311 -- Unless the reference is forced, we ignore references where
312 -- the reference itself does not come from Source.
314 if not Force
and then not Comes_From_Source
(N
) then
318 -- Deal with setting entity as referenced, unless suppressed.
319 -- Note that we still do Set_Referenced on entities that do not
320 -- come from source. This situation arises when we have a source
321 -- reference to a derived operation, where the derived operation
322 -- itself does not come from source, but we still want to mark it
323 -- as referenced, since we really are referencing an entity in the
324 -- corresponding package (this avoids incorrect complaints that the
325 -- package contains no referenced entities).
329 -- For a variable that appears on the left side of an
330 -- assignment statement, we set the Referenced_As_LHS
331 -- flag since this is indeed a left hand side.
332 -- We also set the Referenced_As_LHS flag of a prefix
333 -- of selected or indexed component.
335 if Ekind
(E
) = E_Variable
336 and then Is_On_LHS
(N
)
338 Set_Referenced_As_LHS
(E
);
340 -- Check for a reference in a pragma that should not count as a
341 -- making the variable referenced for warning purposes.
343 elsif Is_Non_Significant_Pragma_Reference
(N
) then
346 -- A reference in an attribute definition clause does not
347 -- count as a reference except for the case of Address.
348 -- The reason that 'Address is an exception is that it
349 -- creates an alias through which the variable may be
352 elsif Nkind
(Parent
(N
)) = N_Attribute_Definition_Clause
353 and then Chars
(Parent
(N
)) /= Name_Address
354 and then N
= Name
(Parent
(N
))
358 -- Constant completion does not count as a reference
361 and then Ekind
(E
) = E_Constant
365 -- Record representation clause does not count as a reference
367 elsif Nkind
(N
) = N_Identifier
368 and then Nkind
(Parent
(N
)) = N_Record_Representation_Clause
372 -- Discriminants do not need to produce a reference to record type
375 and then Nkind
(Parent
(N
)) = N_Discriminant_Specification
379 -- Any other occurrence counts as referencing the entity
385 -- Check for pragma Unreferenced given and reference is within
386 -- this source unit (occasion for possible warning to be issued)
388 if Has_Pragma_Unreferenced
(E
)
389 and then In_Same_Extended_Unit
(E
, N
)
391 -- A reference as a named parameter in a call does not count
392 -- as a violation of pragma Unreferenced for this purpose.
394 if Nkind
(N
) = N_Identifier
395 and then Nkind
(Parent
(N
)) = N_Parameter_Association
396 and then Selector_Name
(Parent
(N
)) = N
400 -- Neither does a reference to a variable on the left side
403 elsif Is_On_LHS
(N
) then
406 -- For entry formals, we want to place the warning on the
407 -- corresponding entity in the accept statement. The current
408 -- scope is the body of the accept, so we find the formal
409 -- whose name matches that of the entry formal (there is no
410 -- link between the two entities, and the one in the accept
411 -- statement is only used for conformance checking).
413 elsif Ekind
(Scope
(E
)) = E_Entry
then
418 BE
:= First_Entity
(Current_Scope
);
419 while Present
(BE
) loop
420 if Chars
(BE
) = Chars
(E
) then
422 ("?pragma Unreferenced given for&", N
, BE
);
430 -- Here we issue the warning, since this is a real reference
433 Error_Msg_NE
("?pragma Unreferenced given for&", N
, E
);
437 -- If this is a subprogram instance, mark as well the internal
438 -- subprogram in the wrapper package, which may be a visible
441 if Is_Overloadable
(E
)
442 and then Is_Generic_Instance
(E
)
443 and then Present
(Alias
(E
))
445 Set_Referenced
(Alias
(E
));
449 -- Generate reference if all conditions are met:
452 -- Cross referencing must be active
456 -- The entity must be one for which we collect references
458 and then Xref_Entity_Letters
(Ekind
(E
)) /= ' '
460 -- Both Sloc values must be set to something sensible
462 and then Sloc
(E
) > No_Location
463 and then Sloc
(N
) > No_Location
465 -- We ignore references from within an instance
467 and then Instantiation_Location
(Sloc
(N
)) = No_Location
469 -- Ignore dummy references
473 if Nkind
(N
) = N_Identifier
475 Nkind
(N
) = N_Defining_Identifier
479 Nkind
(N
) = N_Defining_Operator_Symbol
481 Nkind
(N
) = N_Operator_Symbol
483 (Nkind
(N
) = N_Character_Literal
484 and then Sloc
(Entity
(N
)) /= Standard_Location
)
486 Nkind
(N
) = N_Defining_Character_Literal
490 elsif Nkind
(N
) = N_Expanded_Name
492 Nkind
(N
) = N_Selected_Component
494 Nod
:= Selector_Name
(N
);
500 -- Normal case of source entity comes from source
502 if Comes_From_Source
(E
) then
505 -- Entity does not come from source, but is a derived subprogram
506 -- and the derived subprogram comes from source (after one or more
507 -- derivations) in which case the reference is to parent subprogram.
509 elsif Is_Overloadable
(E
)
510 and then Present
(Alias
(E
))
515 if Comes_From_Source
(Ent
) then
517 elsif No
(Alias
(Ent
)) then
524 -- The internally created defining entity for a child subprogram
525 -- that has no previous spec has valid references.
527 elsif Is_Overloadable
(E
)
528 and then Is_Child_Unit
(E
)
532 -- Record components of discriminated subtypes or derived types
533 -- must be treated as references to the original component.
535 elsif Ekind
(E
) = E_Component
536 and then Comes_From_Source
(Original_Record_Component
(E
))
538 Ent
:= Original_Record_Component
(E
);
540 -- Ignore reference to any other entity that is not from source
546 -- Record reference to entity
548 Ref
:= Original_Location
(Sloc
(Nod
));
549 Def
:= Original_Location
(Sloc
(Ent
));
551 Xrefs
.Increment_Last
;
554 Xrefs
.Table
(Indx
).Loc
:= Ref
;
556 -- Overriding operations are marked with 'P'
559 and then Is_Subprogram
(N
)
560 and then Is_Overriding_Operation
(N
)
562 Xrefs
.Table
(Indx
).Typ
:= 'P';
564 Xrefs
.Table
(Indx
).Typ
:= Typ
;
567 Xrefs
.Table
(Indx
).Eun
:= Get_Source_Unit
(Def
);
568 Xrefs
.Table
(Indx
).Lun
:= Get_Source_Unit
(Ref
);
569 Xrefs
.Table
(Indx
).Ent
:= Ent
;
570 Set_Has_Xref_Entry
(Ent
);
572 end Generate_Reference
;
574 -----------------------------------
575 -- Generate_Reference_To_Formals --
576 -----------------------------------
578 procedure Generate_Reference_To_Formals
(E
: Entity_Id
) is
582 if Is_Generic_Subprogram
(E
) then
583 Formal
:= First_Entity
(E
);
585 while Present
(Formal
)
586 and then not Is_Formal
(Formal
)
588 Next_Entity
(Formal
);
592 Formal
:= First_Formal
(E
);
595 while Present
(Formal
) loop
596 if Ekind
(Formal
) = E_In_Parameter
then
598 if Nkind
(Parameter_Type
(Parent
(Formal
)))
599 = N_Access_Definition
601 Generate_Reference
(E
, Formal
, '^', False);
603 Generate_Reference
(E
, Formal
, '>', False);
606 elsif Ekind
(Formal
) = E_In_Out_Parameter
then
607 Generate_Reference
(E
, Formal
, '=', False);
610 Generate_Reference
(E
, Formal
, '<', False);
613 Next_Formal
(Formal
);
615 end Generate_Reference_To_Formals
;
617 -------------------------------------------
618 -- Generate_Reference_To_Generic_Formals --
619 -------------------------------------------
621 procedure Generate_Reference_To_Generic_Formals
(E
: Entity_Id
) is
625 Formal
:= First_Entity
(E
);
627 while Present
(Formal
) loop
628 if Comes_From_Source
(Formal
) then
629 Generate_Reference
(E
, Formal
, 'z', False);
632 Next_Entity
(Formal
);
634 end Generate_Reference_To_Generic_Formals
;
640 procedure Initialize
is
645 -----------------------
646 -- Output_References --
647 -----------------------
649 procedure Output_References
is
651 procedure Get_Type_Reference
653 Tref
: out Entity_Id
;
654 Left
: out Character;
655 Right
: out Character);
656 -- Given an entity id Ent, determines whether a type reference is
657 -- required. If so, Tref is set to the entity for the type reference
658 -- and Left and Right are set to the left/right brackets to be
659 -- output for the reference. If no type reference is required, then
660 -- Tref is set to Empty, and Left/Right are set to space.
662 procedure Output_Import_Export_Info
(Ent
: Entity_Id
);
663 -- Ouput language and external name information for an interfaced
664 -- entity, using the format <language, external_name>,
666 ------------------------
667 -- Get_Type_Reference --
668 ------------------------
670 procedure Get_Type_Reference
672 Tref
: out Entity_Id
;
673 Left
: out Character;
674 Right
: out Character)
679 -- See if we have a type reference
688 -- Processing for types
690 if Is_Type
(Tref
) then
694 if Base_Type
(Tref
) = Tref
then
696 -- If derived, then get first subtype
698 if Tref
/= Etype
(Tref
) then
699 Tref
:= First_Subtype
(Etype
(Tref
));
701 -- Set brackets for derived type, but don't
702 -- override pointer case since the fact that
703 -- something is a pointer is more important
710 -- If non-derived ptr, get directly designated type.
711 -- If the type has a full view, all references are
712 -- on the partial view, that is seen first.
714 elsif Is_Access_Type
(Tref
) then
715 Tref
:= Directly_Designated_Type
(Tref
);
719 elsif Is_Private_Type
(Tref
)
720 and then Present
(Full_View
(Tref
))
722 if Is_Access_Type
(Full_View
(Tref
)) then
723 Tref
:= Directly_Designated_Type
(Full_View
(Tref
));
727 -- If the full view is an array type, we also retrieve
728 -- the corresponding component type, because the ali
729 -- entry already indicates that this is an array.
731 elsif Is_Array_Type
(Full_View
(Tref
)) then
732 Tref
:= Component_Type
(Full_View
(Tref
));
737 -- If non-derived array, get component type.
738 -- Skip component type for case of String
739 -- or Wide_String, saves worthwhile space.
741 elsif Is_Array_Type
(Tref
)
742 and then Tref
/= Standard_String
743 and then Tref
/= Standard_Wide_String
745 Tref
:= Component_Type
(Tref
);
749 -- For other non-derived base types, nothing
755 -- For a subtype, go to ancestor subtype
758 Tref
:= Ancestor_Subtype
(Tref
);
760 -- If no ancestor subtype, go to base type
763 Tref
:= Base_Type
(Sav
);
767 -- For objects, functions, enum literals,
768 -- just get type from Etype field.
770 elsif Is_Object
(Tref
)
771 or else Ekind
(Tref
) = E_Enumeration_Literal
772 or else Ekind
(Tref
) = E_Function
773 or else Ekind
(Tref
) = E_Operator
775 Tref
:= Etype
(Tref
);
777 -- For anything else, exit
783 -- Exit if no type reference, or we are stuck in
784 -- some loop trying to find the type reference, or
785 -- if the type is standard void type (the latter is
786 -- an implementation artifact that should not show
787 -- up in the generated cross-references).
791 or else Tref
= Standard_Void_Type
;
793 -- If we have a usable type reference, return, otherwise
794 -- keep looking for something useful (we are looking for
795 -- something that either comes from source or standard)
797 if Sloc
(Tref
) = Standard_Location
798 or else Comes_From_Source
(Tref
)
800 -- If the reference is a subtype created for a generic
801 -- actual, go to actual directly, the inner subtype is
804 if Nkind
(Parent
(Tref
)) = N_Subtype_Declaration
805 and then not Comes_From_Source
(Parent
(Tref
))
807 (Is_Wrapper_Package
(Scope
(Tref
))
808 or else Is_Generic_Instance
(Scope
(Tref
)))
810 Tref
:= First_Subtype
(Base_Type
(Tref
));
817 -- If we fall through the loop, no type reference
822 end Get_Type_Reference
;
824 -------------------------------
825 -- Output_Import_Export_Info --
826 -------------------------------
828 procedure Output_Import_Export_Info
(Ent
: Entity_Id
) is
829 Language_Name
: Name_Id
;
830 Conv
: constant Convention_Id
:= Convention
(Ent
);
832 if Conv
= Convention_C
then
833 Language_Name
:= Name_C
;
835 elsif Conv
= Convention_CPP
then
836 Language_Name
:= Name_CPP
;
838 elsif Conv
= Convention_Ada
then
839 Language_Name
:= Name_Ada
;
842 -- These are the only languages that GPS knows about
847 Write_Info_Char
('<');
848 Get_Unqualified_Name_String
(Language_Name
);
850 for J
in 1 .. Name_Len
loop
851 Write_Info_Char
(Name_Buffer
(J
));
854 if Present
(Interface_Name
(Ent
)) then
855 Write_Info_Char
(',');
856 String_To_Name_Buffer
(Strval
(Interface_Name
(Ent
)));
858 for J
in 1 .. Name_Len
loop
859 Write_Info_Char
(Name_Buffer
(J
));
863 Write_Info_Char
('>');
864 end Output_Import_Export_Info
;
866 -- Start of processing for Output_References
869 if not Opt
.Xref_Active
then
873 -- Before we go ahead and output the references we have a problem
874 -- that needs dealing with. So far we have captured things that are
875 -- definitely referenced by the main unit, or defined in the main
876 -- unit. That's because we don't want to clutter up the ali file
877 -- for this unit with definition lines for entities in other units
878 -- that are not referenced.
880 -- But there is a glitch. We may reference an entity in another unit,
881 -- and it may have a type reference to an entity that is not directly
882 -- referenced in the main unit, which may mean that there is no xref
883 -- entry for this entity yet in the list of references.
885 -- If we don't do something about this, we will end with an orphan
886 -- type reference, i.e. it will point to an entity that does not
887 -- appear within the generated references in the ali file. That is
888 -- not good for tools using the xref information.
890 -- To fix this, we go through the references adding definition
891 -- entries for any unreferenced entities that can be referenced
892 -- in a type reference. There is a recursion problem here, and
893 -- that is dealt with by making sure that this traversal also
894 -- traverses any entries that get added by the traversal.
905 -- Note that this is not a for loop for a very good reason. The
906 -- processing of items in the table can add new items to the
907 -- table, and they must be processed as well
910 while J
<= Xrefs
.Last
loop
911 Ent
:= Xrefs
.Table
(J
).Ent
;
912 Get_Type_Reference
(Ent
, Tref
, L
, R
);
915 and then not Has_Xref_Entry
(Tref
)
916 and then Sloc
(Tref
) > No_Location
918 Xrefs
.Increment_Last
;
920 Loc
:= Original_Location
(Sloc
(Tref
));
921 Xrefs
.Table
(Indx
).Ent
:= Tref
;
922 Xrefs
.Table
(Indx
).Loc
:= No_Location
;
923 Xrefs
.Table
(Indx
).Eun
:= Get_Source_Unit
(Loc
);
924 Xrefs
.Table
(Indx
).Lun
:= No_Unit
;
925 Set_Has_Xref_Entry
(Tref
);
928 -- Collect inherited primitive operations that may be
929 -- declared in another unit and have no visible reference
930 -- in the current one.
933 and then Is_Tagged_Type
(Ent
)
934 and then Is_Derived_Type
(Ent
)
935 and then Ent
= Base_Type
(Ent
)
936 and then In_Extended_Main_Source_Unit
(Ent
)
939 Op_List
: constant Elist_Id
:= Primitive_Operations
(Ent
);
943 function Parent_Op
(E
: Entity_Id
) return Entity_Id
;
944 -- Find original operation, which may be inherited
945 -- through several derivations.
947 function Parent_Op
(E
: Entity_Id
) return Entity_Id
is
948 Orig_Op
: constant Entity_Id
:= Alias
(E
);
952 elsif not Comes_From_Source
(E
)
953 and then not Has_Xref_Entry
(Orig_Op
)
954 and then Comes_From_Source
(Orig_Op
)
958 return Parent_Op
(Orig_Op
);
963 Op
:= First_Elmt
(Op_List
);
964 while Present
(Op
) loop
965 Prim
:= Parent_Op
(Node
(Op
));
967 if Present
(Prim
) then
968 Xrefs
.Increment_Last
;
970 Loc
:= Original_Location
(Sloc
(Prim
));
971 Xrefs
.Table
(Indx
).Ent
:= Prim
;
972 Xrefs
.Table
(Indx
).Loc
:= No_Location
;
973 Xrefs
.Table
(Indx
).Eun
:=
974 Get_Source_Unit
(Sloc
(Prim
));
975 Xrefs
.Table
(Indx
).Lun
:= No_Unit
;
976 Set_Has_Xref_Entry
(Prim
);
988 -- Now we have all the references, including those for any embedded
989 -- type references, so we can sort them, and output them.
991 Output_Refs
: declare
993 Nrefs
: Nat
:= Xrefs
.Last
;
994 -- Number of references in table. This value may get reset
995 -- (reduced) when we eliminate duplicate reference entries.
997 Rnums
: array (0 .. Nrefs
) of Nat
;
998 -- This array contains numbers of references in the Xrefs table.
999 -- This list is sorted in output order. The extra 0'th entry is
1000 -- convenient for the call to sort. When we sort the table, we
1001 -- move the entries in Rnums around, but we do not move the
1002 -- original table entries.
1004 Curxu
: Unit_Number_Type
;
1005 -- Current xref unit
1007 Curru
: Unit_Number_Type
;
1008 -- Current reference unit for one entity
1010 Cursrc
: Source_Buffer_Ptr
;
1011 -- Current xref unit source text
1016 Curnam
: String (1 .. Name_Buffer
'Length);
1018 -- Simple name and length of current entity
1020 Curdef
: Source_Ptr
;
1021 -- Original source location for current entity
1024 -- Current reference location
1027 -- Entity type character
1033 -- Renaming reference
1035 Trunit
: Unit_Number_Type
;
1036 -- Unit number for type reference
1038 function Lt
(Op1
, Op2
: Natural) return Boolean;
1039 -- Comparison function for Sort call
1041 function Name_Change
(X
: Entity_Id
) return Boolean;
1042 -- Determines if entity X has a different simple name from Curent
1044 procedure Move
(From
: Natural; To
: Natural);
1045 -- Move procedure for Sort call
1051 function Lt
(Op1
, Op2
: Natural) return Boolean is
1052 T1
: Xref_Entry
renames Xrefs
.Table
(Rnums
(Nat
(Op1
)));
1053 T2
: Xref_Entry
renames Xrefs
.Table
(Rnums
(Nat
(Op2
)));
1056 -- First test. If entity is in different unit, sort by unit
1058 if T1
.Eun
/= T2
.Eun
then
1059 return Dependency_Num
(T1
.Eun
) < Dependency_Num
(T2
.Eun
);
1061 -- Second test, within same unit, sort by entity Sloc
1063 elsif T1
.Def
/= T2
.Def
then
1064 return T1
.Def
< T2
.Def
;
1066 -- Third test, sort definitions ahead of references
1068 elsif T1
.Loc
= No_Location
then
1071 elsif T2
.Loc
= No_Location
then
1074 -- Fourth test, for same entity, sort by reference location unit
1076 elsif T1
.Lun
/= T2
.Lun
then
1077 return Dependency_Num
(T1
.Lun
) < Dependency_Num
(T2
.Lun
);
1079 -- Fifth test order of location within referencing unit
1081 elsif T1
.Loc
/= T2
.Loc
then
1082 return T1
.Loc
< T2
.Loc
;
1084 -- Finally, for two locations at the same address, we prefer
1085 -- the one that does NOT have the type 'r' so that a modification
1086 -- or extension takes preference, when there are more than one
1087 -- reference at the same location.
1090 return T2
.Typ
= 'r';
1098 procedure Move
(From
: Natural; To
: Natural) is
1100 Rnums
(Nat
(To
)) := Rnums
(Nat
(From
));
1107 function Name_Change
(X
: Entity_Id
) return Boolean is
1109 Get_Unqualified_Name_String
(Chars
(X
));
1111 if Name_Len
/= Curlen
then
1115 return Name_Buffer
(1 .. Curlen
) /= Curnam
(1 .. Curlen
);
1119 -- Start of processing for Output_Refs
1122 -- Capture the definition Sloc values. We delay doing this till now,
1123 -- since at the time the reference or definition is made, private
1124 -- types may be swapped, and the Sloc value may be incorrect. We
1125 -- also set up the pointer vector for the sort.
1127 for J
in 1 .. Nrefs
loop
1129 Xrefs
.Table
(J
).Def
:=
1130 Original_Location
(Sloc
(Xrefs
.Table
(J
).Ent
));
1133 -- Sort the references
1135 GNAT
.Heap_Sort_A
.Sort
1137 Move
'Unrestricted_Access,
1138 Lt
'Unrestricted_Access);
1140 -- Eliminate duplicate entries
1143 NR
: constant Nat
:= Nrefs
;
1146 -- We need this test for NR because if we force ALI file
1147 -- generation in case of errors detected, it may be the case
1148 -- that Nrefs is 0, so we should not reset it here
1153 for J
in 2 .. NR
loop
1154 if Xrefs
.Table
(Rnums
(J
)) /=
1155 Xrefs
.Table
(Rnums
(Nrefs
))
1158 Rnums
(Nrefs
) := Rnums
(J
);
1164 -- Initialize loop through references
1168 Curdef
:= No_Location
;
1170 Crloc
:= No_Location
;
1172 -- Loop to output references
1174 for Refno
in 1 .. Nrefs
loop
1175 Output_One_Ref
: declare
1181 XE
: Xref_Entry
renames Xrefs
.Table
(Rnums
(Refno
));
1182 -- The current entry to be accessed
1185 -- Used to index into source buffer to get entity name
1189 -- Used for {} or <> or () for type reference
1191 procedure Output_Instantiation_Refs
(Loc
: Source_Ptr
);
1192 -- Recursive procedure to output instantiation references for
1193 -- the given source ptr in [file|line[...]] form. No output
1194 -- if the given location is not a generic template reference.
1196 procedure Output_Overridden_Op
(Old_E
: Entity_Id
);
1197 -- For a subprogram that is overriding, display information
1198 -- about the inherited operation that it overrides.
1200 -------------------------------
1201 -- Output_Instantiation_Refs --
1202 -------------------------------
1204 procedure Output_Instantiation_Refs
(Loc
: Source_Ptr
) is
1205 Iloc
: constant Source_Ptr
:= Instantiation_Location
(Loc
);
1206 Lun
: Unit_Number_Type
;
1207 Cu
: constant Unit_Number_Type
:= Curru
;
1210 -- Nothing to do if this is not an instantiation
1212 if Iloc
= No_Location
then
1216 -- Output instantiation reference
1218 Write_Info_Char
('[');
1219 Lun
:= Get_Source_Unit
(Iloc
);
1221 if Lun
/= Curru
then
1223 Write_Info_Nat
(Dependency_Num
(Curru
));
1224 Write_Info_Char
('|');
1227 Write_Info_Nat
(Int
(Get_Logical_Line_Number
(Iloc
)));
1229 -- Recursive call to get nested instantiations
1231 Output_Instantiation_Refs
(Iloc
);
1233 -- Output final ] after call to get proper nesting
1235 Write_Info_Char
(']');
1238 end Output_Instantiation_Refs
;
1240 --------------------------
1241 -- Output_Overridden_Op --
1242 --------------------------
1244 procedure Output_Overridden_Op
(Old_E
: Entity_Id
) is
1247 and then Sloc
(Old_E
) /= Standard_Location
1250 Loc
: constant Source_Ptr
:= Sloc
(Old_E
);
1251 Par_Unit
: constant Unit_Number_Type
:=
1252 Get_Source_Unit
(Loc
);
1254 Write_Info_Char
('<');
1256 if Par_Unit
/= Curxu
then
1257 Write_Info_Nat
(Dependency_Num
(Par_Unit
));
1258 Write_Info_Char
('|');
1261 Write_Info_Nat
(Int
(Get_Logical_Line_Number
(Loc
)));
1262 Write_Info_Char
('p');
1263 Write_Info_Nat
(Int
(Get_Column_Number
(Loc
)));
1264 Write_Info_Char
('>');
1267 end Output_Overridden_Op
;
1269 -- Start of processing for Output_One_Ref
1273 Ctyp
:= Xref_Entity_Letters
(Ekind
(Ent
));
1275 -- Skip reference if it is the only reference to an entity,
1276 -- and it is an end-line reference, and the entity is not in
1277 -- the current extended source. This prevents junk entries
1278 -- consisting only of packages with end lines, where no
1279 -- entity from the package is actually referenced.
1282 and then Ent
/= Curent
1283 and then (Refno
= Nrefs
or else
1284 Ent
/= Xrefs
.Table
(Rnums
(Refno
+ 1)).Ent
)
1286 not In_Extended_Main_Source_Unit
(Ent
)
1291 -- For private type, get full view type
1294 and then Present
(Full_View
(XE
.Ent
))
1296 Ent
:= Underlying_Type
(Ent
);
1298 if Present
(Ent
) then
1299 Ctyp
:= Xref_Entity_Letters
(Ekind
(Ent
));
1303 -- Special exception for Boolean
1305 if Ctyp
= 'E' and then Is_Boolean_Type
(Ent
) then
1309 -- For variable reference, get corresponding type
1312 Ent
:= Etype
(XE
.Ent
);
1313 Ctyp
:= Fold_Lower
(Xref_Entity_Letters
(Ekind
(Ent
)));
1315 -- If variable is private type, get full view type
1318 and then Present
(Full_View
(Etype
(XE
.Ent
)))
1320 Ent
:= Underlying_Type
(Etype
(XE
.Ent
));
1322 if Present
(Ent
) then
1323 Ctyp
:= Fold_Lower
(Xref_Entity_Letters
(Ekind
(Ent
)));
1326 elsif Is_Generic_Type
(Ent
) then
1328 -- If the type of the entity is a generic private type
1329 -- there is no usable full view, so retain the indication
1330 -- that this is an object.
1335 -- Special handling for access parameter
1338 K
: constant Entity_Kind
:= Ekind
(Etype
(XE
.Ent
));
1341 if (K
= E_Anonymous_Access_Type
1343 K
= E_Anonymous_Access_Subprogram_Type
1345 E_Anonymous_Access_Protected_Subprogram_Type
)
1346 and then Is_Formal
(XE
.Ent
)
1350 -- Special handling for Boolean
1352 elsif Ctyp
= 'e' and then Is_Boolean_Type
(Ent
) then
1358 -- Special handling for abstract types and operations
1360 if Is_Abstract
(XE
.Ent
) then
1363 Ctyp
:= 'x'; -- abstract procedure
1365 elsif Ctyp
= 'V' then
1366 Ctyp
:= 'y'; -- abstract function
1368 elsif Ctyp
= 'R' then
1369 Ctyp
:= 'H'; -- abstract type
1373 -- Only output reference if interesting type of entity,
1374 -- and suppress self references, except for bodies that
1375 -- act as specs. Also suppress definitions of body formals
1376 -- (we only treat these as references, and the references
1377 -- were separately recorded).
1380 or else (XE
.Loc
= XE
.Def
1383 or else not Is_Subprogram
(XE
.Ent
)))
1384 or else (Is_Formal
(XE
.Ent
)
1385 and then Present
(Spec_Entity
(XE
.Ent
)))
1390 -- Start new Xref section if new xref unit
1392 if XE
.Eun
/= Curxu
then
1393 if Write_Info_Col
> 1 then
1398 Cursrc
:= Source_Text
(Source_Index
(Curxu
));
1400 Write_Info_Initiate
('X');
1401 Write_Info_Char
(' ');
1402 Write_Info_Nat
(Dependency_Num
(XE
.Eun
));
1403 Write_Info_Char
(' ');
1404 Write_Info_Name
(Reference_Name
(Source_Index
(XE
.Eun
)));
1407 -- Start new Entity line if new entity. Note that we
1408 -- consider two entities the same if they have the same
1409 -- name and source location. This causes entities in
1410 -- instantiations to be treated as though they referred
1417 (Name_Change
(XE
.Ent
) or else XE
.Def
/= Curdef
))
1422 Get_Unqualified_Name_String
(Chars
(XE
.Ent
));
1424 Curnam
(1 .. Curlen
) := Name_Buffer
(1 .. Curlen
);
1426 if Write_Info_Col
> 1 then
1430 -- Write column number information
1432 Write_Info_Nat
(Int
(Get_Logical_Line_Number
(XE
.Def
)));
1433 Write_Info_Char
(Ctyp
);
1434 Write_Info_Nat
(Int
(Get_Column_Number
(XE
.Def
)));
1436 -- Write level information
1438 Write_Level_Info
: declare
1439 function Is_Visible_Generic_Entity
1440 (E
: Entity_Id
) return Boolean;
1441 -- Check whether E is declared in the visible part
1442 -- of a generic package. For source navigation
1443 -- purposes, treat this as a visible entity.
1445 function Is_Private_Record_Component
1446 (E
: Entity_Id
) return Boolean;
1447 -- Check whether E is a non-inherited component of a
1448 -- private extension. Even if the enclosing record is
1449 -- public, we want to treat the component as private
1450 -- for navigation purposes.
1452 ---------------------------------
1453 -- Is_Private_Record_Component --
1454 ---------------------------------
1456 function Is_Private_Record_Component
1457 (E
: Entity_Id
) return Boolean
1459 S
: constant Entity_Id
:= Scope
(E
);
1462 Ekind
(E
) = E_Component
1463 and then Nkind
(Declaration_Node
(S
)) =
1464 N_Private_Extension_Declaration
1465 and then Original_Record_Component
(E
) = E
;
1466 end Is_Private_Record_Component
;
1468 -------------------------------
1469 -- Is_Visible_Generic_Entity --
1470 -------------------------------
1472 function Is_Visible_Generic_Entity
1473 (E
: Entity_Id
) return Boolean
1478 if Ekind
(Scope
(E
)) /= E_Generic_Package
then
1483 while Present
(Par
) loop
1485 Nkind
(Par
) = N_Generic_Package_Declaration
1487 -- Entity is a generic formal
1492 Nkind
(Parent
(Par
)) = N_Package_Specification
1495 Is_List_Member
(Par
)
1496 and then List_Containing
(Par
) =
1497 Visible_Declarations
(Parent
(Par
));
1499 Par
:= Parent
(Par
);
1504 end Is_Visible_Generic_Entity
;
1506 -- Start of processing for Write_Level_Info
1509 if Is_Hidden
(Curent
)
1510 or else Is_Private_Record_Component
(Curent
)
1512 Write_Info_Char
(' ');
1516 or else Is_Visible_Generic_Entity
(Curent
)
1518 Write_Info_Char
('*');
1521 Write_Info_Char
(' ');
1523 end Write_Level_Info
;
1525 -- Output entity name. We use the occurrence from the
1526 -- actual source program at the definition point
1528 P
:= Original_Location
(Sloc
(XE
.Ent
));
1530 -- Entity is character literal
1532 if Cursrc
(P
) = ''' then
1533 Write_Info_Char
(Cursrc
(P
));
1534 Write_Info_Char
(Cursrc
(P
+ 1));
1535 Write_Info_Char
(Cursrc
(P
+ 2));
1537 -- Entity is operator symbol
1539 elsif Cursrc
(P
) = '"' or else Cursrc
(P
) = '%' then
1540 Write_Info_Char
(Cursrc
(P
));
1545 Write_Info_Char
(Cursrc
(P2
));
1546 exit when Cursrc
(P2
) = Cursrc
(P
);
1549 -- Entity is identifier
1553 if Is_Start_Of_Wide_Char
(Cursrc
, P
) then
1554 Scan_Wide
(Cursrc
, P
, WC
, Err
);
1555 elsif not Identifier_Char
(Cursrc
(P
)) then
1563 Original_Location
(Sloc
(XE
.Ent
)) .. P
- 1
1565 Write_Info_Char
(Cursrc
(J
));
1569 -- See if we have a renaming reference
1571 if Is_Object
(XE
.Ent
)
1572 and then Present
(Renamed_Object
(XE
.Ent
))
1574 Rref
:= Renamed_Object
(XE
.Ent
);
1576 elsif Is_Overloadable
(XE
.Ent
)
1577 and then Nkind
(Parent
(Declaration_Node
(XE
.Ent
))) =
1578 N_Subprogram_Renaming_Declaration
1580 Rref
:= Name
(Parent
(Declaration_Node
(XE
.Ent
)));
1582 elsif Ekind
(XE
.Ent
) = E_Package
1583 and then Nkind
(Declaration_Node
(XE
.Ent
)) =
1584 N_Package_Renaming_Declaration
1586 Rref
:= Name
(Declaration_Node
(XE
.Ent
));
1592 if Present
(Rref
) then
1593 if Nkind
(Rref
) = N_Expanded_Name
then
1594 Rref
:= Selector_Name
(Rref
);
1597 if Nkind
(Rref
) = N_Identifier
1598 or else Nkind
(Rref
) = N_Operator_Symbol
1602 -- For renamed array components, use the array name
1603 -- for the renamed entity, which reflect the fact that
1604 -- in general the whole array is aliased.
1606 elsif Nkind
(Rref
) = N_Indexed_Component
then
1607 if Nkind
(Prefix
(Rref
)) = N_Identifier
then
1608 Rref
:= Prefix
(Rref
);
1609 elsif Nkind
(Prefix
(Rref
)) = N_Expanded_Name
then
1610 Rref
:= Selector_Name
(Prefix
(Rref
));
1620 -- Write out renaming reference if we have one
1622 if Present
(Rref
) then
1623 Write_Info_Char
('=');
1625 (Int
(Get_Logical_Line_Number
(Sloc
(Rref
))));
1626 Write_Info_Char
(':');
1628 (Int
(Get_Column_Number
(Sloc
(Rref
))));
1631 -- Indicate that the entity is in the unit
1632 -- of the current xref xection.
1636 -- Write out information about generic parent,
1637 -- if entity is an instance.
1639 if Is_Generic_Instance
(XE
.Ent
) then
1641 Gen_Par
: constant Entity_Id
:=
1644 (Unit_Declaration_Node
(XE
.Ent
)));
1645 Loc
: constant Source_Ptr
:= Sloc
(Gen_Par
);
1646 Gen_U
: constant Unit_Number_Type
:=
1647 Get_Source_Unit
(Loc
);
1649 Write_Info_Char
('[');
1650 if Curru
/= Gen_U
then
1651 Write_Info_Nat
(Dependency_Num
(Gen_U
));
1652 Write_Info_Char
('|');
1656 (Int
(Get_Logical_Line_Number
(Loc
)));
1657 Write_Info_Char
(']');
1661 -- See if we have a type reference and if so output
1663 Get_Type_Reference
(XE
.Ent
, Tref
, Left
, Right
);
1665 if Present
(Tref
) then
1667 -- Case of standard entity, output name
1669 if Sloc
(Tref
) = Standard_Location
then
1670 Write_Info_Char
(Left
);
1671 Write_Info_Name
(Chars
(Tref
));
1672 Write_Info_Char
(Right
);
1674 -- Case of source entity, output location
1677 Write_Info_Char
(Left
);
1678 Trunit
:= Get_Source_Unit
(Sloc
(Tref
));
1680 if Trunit
/= Curxu
then
1681 Write_Info_Nat
(Dependency_Num
(Trunit
));
1682 Write_Info_Char
('|');
1686 (Int
(Get_Logical_Line_Number
(Sloc
(Tref
))));
1689 Ent
: Entity_Id
:= Tref
;
1690 Kind
: constant Entity_Kind
:= Ekind
(Ent
);
1691 Ctyp
: Character := Xref_Entity_Letters
(Kind
);
1695 and then Present
(Full_View
(Ent
))
1697 Ent
:= Underlying_Type
(Ent
);
1699 if Present
(Ent
) then
1700 Ctyp
:= Xref_Entity_Letters
(Ekind
(Ent
));
1704 Write_Info_Char
(Ctyp
);
1708 (Int
(Get_Column_Number
(Sloc
(Tref
))));
1710 -- If the type comes from an instantiation,
1711 -- add the corresponding info.
1713 Output_Instantiation_Refs
(Sloc
(Tref
));
1714 Write_Info_Char
(Right
);
1718 -- If the entity is an overriding operation, write
1719 -- info on operation that was overridden.
1721 if Is_Subprogram
(XE
.Ent
)
1722 and then Is_Overriding_Operation
(XE
.Ent
)
1724 Output_Overridden_Op
(Overridden_Operation
(XE
.Ent
));
1727 -- End of processing for entity output
1729 Crloc
:= No_Location
;
1732 -- Output the reference
1734 if XE
.Loc
/= No_Location
1735 and then XE
.Loc
/= Crloc
1739 -- Start continuation if line full, else blank
1741 if Write_Info_Col
> 72 then
1743 Write_Info_Initiate
('.');
1746 Write_Info_Char
(' ');
1748 -- Output file number if changed
1750 if XE
.Lun
/= Curru
then
1752 Write_Info_Nat
(Dependency_Num
(Curru
));
1753 Write_Info_Char
('|');
1756 Write_Info_Nat
(Int
(Get_Logical_Line_Number
(XE
.Loc
)));
1757 Write_Info_Char
(XE
.Typ
);
1759 if Is_Overloadable
(XE
.Ent
)
1760 and then Is_Imported
(XE
.Ent
)
1761 and then XE
.Typ
= 'b'
1763 Output_Import_Export_Info
(XE
.Ent
);
1766 Write_Info_Nat
(Int
(Get_Column_Number
(XE
.Loc
)));
1768 Output_Instantiation_Refs
(Sloc
(XE
.Ent
));
1779 end Output_References
;