1 ------------------------------------------------------------------------------
3 -- GNAT COMPILER COMPONENTS --
9 -- Copyright (C) 1998-2005, 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 an assignment statement, check whether
266 return Name
(Parent
(N
)) = N
;
269 -- Start of processing for Generate_Reference
272 pragma Assert
(Nkind
(E
) in N_Entity
);
274 -- Check for obsolescent reference to ASCII
276 if E
= Standard_ASCII
then
277 Check_Restriction
(No_Obsolescent_Features
, N
);
280 -- Warn if reference to Ada 2005 entity not in Ada 2005 mode
283 and then Ada_Version
< Ada_05
284 and then Warn_On_Ada_2005_Compatibility
286 Error_Msg_NE
("& is only defined in Ada 2005?", N
, E
);
289 -- Never collect references if not in main source unit. However,
290 -- we omit this test if Typ is 'e' or 'k', since these entries are
291 -- really structural, and it is useful to have them in units
292 -- that reference packages as well as units that define packages.
293 -- We also omit the test for the case of 'p' since we want to
294 -- include inherited primitive operations from other packages.
296 if not In_Extended_Main_Source_Unit
(N
)
304 -- For reference type p, the entity must be in main source unit
306 if Typ
= 'p' and then not In_Extended_Main_Source_Unit
(E
) then
310 -- Unless the reference is forced, we ignore references where
311 -- the reference itself does not come from Source.
313 if not Force
and then not Comes_From_Source
(N
) then
317 -- Deal with setting entity as referenced, unless suppressed.
318 -- Note that we still do Set_Referenced on entities that do not
319 -- come from source. This situation arises when we have a source
320 -- reference to a derived operation, where the derived operation
321 -- itself does not come from source, but we still want to mark it
322 -- as referenced, since we really are referencing an entity in the
323 -- corresponding package (this avoids incorrect complaints that the
324 -- package contains no referenced entities).
328 -- For a variable that appears on the left side of an
329 -- assignment statement, we set the Referenced_As_LHS
330 -- flag since this is indeed a left hand side.
331 -- We also set the Referenced_As_LHS flag of a prefix
332 -- of selected or indexed component.
334 if Ekind
(E
) = E_Variable
335 and then Is_On_LHS
(N
)
337 Set_Referenced_As_LHS
(E
);
339 -- Check for a reference in a pragma that should not count as a
340 -- making the variable referenced for warning purposes.
342 elsif Is_Non_Significant_Pragma_Reference
(N
) then
345 -- A reference in an attribute definition clause does not
346 -- count as a reference except for the case of Address.
347 -- The reason that 'Address is an exception is that it
348 -- creates an alias through which the variable may be
351 elsif Nkind
(Parent
(N
)) = N_Attribute_Definition_Clause
352 and then Chars
(Parent
(N
)) /= Name_Address
353 and then N
= Name
(Parent
(N
))
357 -- Constant completion does not count as a reference
360 and then Ekind
(E
) = E_Constant
364 -- Record representation clause does not count as a reference
366 elsif Nkind
(N
) = N_Identifier
367 and then Nkind
(Parent
(N
)) = N_Record_Representation_Clause
371 -- Discriminants do not need to produce a reference to record type
374 and then Nkind
(Parent
(N
)) = N_Discriminant_Specification
378 -- Any other occurrence counts as referencing the entity
384 -- Check for pragma Unreferenced given and reference is within
385 -- this source unit (occasion for possible warning to be issued)
387 if Has_Pragma_Unreferenced
(E
)
388 and then In_Same_Extended_Unit
(E
, N
)
390 -- A reference as a named parameter in a call does not count
391 -- as a violation of pragma Unreferenced for this purpose.
393 if Nkind
(N
) = N_Identifier
394 and then Nkind
(Parent
(N
)) = N_Parameter_Association
395 and then Selector_Name
(Parent
(N
)) = N
399 -- Neither does a reference to a variable on the left side
402 elsif Ekind
(E
) = E_Variable
403 and then Nkind
(Parent
(N
)) = N_Assignment_Statement
404 and then Name
(Parent
(N
)) = N
408 -- For entry formals, we want to place the warning on the
409 -- corresponding entity in the accept statement. The current
410 -- scope is the body of the accept, so we find the formal
411 -- whose name matches that of the entry formal (there is no
412 -- link between the two entities, and the one in the accept
413 -- statement is only used for conformance checking).
415 elsif Ekind
(Scope
(E
)) = E_Entry
then
420 BE
:= First_Entity
(Current_Scope
);
421 while Present
(BE
) loop
422 if Chars
(BE
) = Chars
(E
) then
424 ("?pragma Unreferenced given for&", N
, BE
);
432 -- Here we issue the warning, since this is a real reference
435 Error_Msg_NE
("?pragma Unreferenced given for&", N
, E
);
439 -- If this is a subprogram instance, mark as well the internal
440 -- subprogram in the wrapper package, which may be a visible
443 if Is_Overloadable
(E
)
444 and then Is_Generic_Instance
(E
)
445 and then Present
(Alias
(E
))
447 Set_Referenced
(Alias
(E
));
451 -- Generate reference if all conditions are met:
454 -- Cross referencing must be active
458 -- The entity must be one for which we collect references
460 and then Xref_Entity_Letters
(Ekind
(E
)) /= ' '
462 -- Both Sloc values must be set to something sensible
464 and then Sloc
(E
) > No_Location
465 and then Sloc
(N
) > No_Location
467 -- We ignore references from within an instance
469 and then Instantiation_Location
(Sloc
(N
)) = No_Location
471 -- Ignore dummy references
475 if Nkind
(N
) = N_Identifier
477 Nkind
(N
) = N_Defining_Identifier
481 Nkind
(N
) = N_Defining_Operator_Symbol
483 Nkind
(N
) = N_Operator_Symbol
485 (Nkind
(N
) = N_Character_Literal
486 and then Sloc
(Entity
(N
)) /= Standard_Location
)
488 Nkind
(N
) = N_Defining_Character_Literal
492 elsif Nkind
(N
) = N_Expanded_Name
494 Nkind
(N
) = N_Selected_Component
496 Nod
:= Selector_Name
(N
);
502 -- Normal case of source entity comes from source
504 if Comes_From_Source
(E
) then
507 -- Entity does not come from source, but is a derived subprogram
508 -- and the derived subprogram comes from source (after one or more
509 -- derivations) in which case the reference is to parent subprogram.
511 elsif Is_Overloadable
(E
)
512 and then Present
(Alias
(E
))
517 if Comes_From_Source
(Ent
) then
519 elsif No
(Alias
(Ent
)) then
526 -- The internally created defining entity for a child subprogram
527 -- that has no previous spec has valid references.
529 elsif Is_Overloadable
(E
)
530 and then Is_Child_Unit
(E
)
534 -- Record components of discriminated subtypes or derived types
535 -- must be treated as references to the original component.
537 elsif Ekind
(E
) = E_Component
538 and then Comes_From_Source
(Original_Record_Component
(E
))
540 Ent
:= Original_Record_Component
(E
);
542 -- Ignore reference to any other entity that is not from source
548 -- Record reference to entity
550 Ref
:= Original_Location
(Sloc
(Nod
));
551 Def
:= Original_Location
(Sloc
(Ent
));
553 Xrefs
.Increment_Last
;
556 Xrefs
.Table
(Indx
).Loc
:= Ref
;
558 -- Overriding operations are marked with 'P'
561 and then Is_Subprogram
(N
)
562 and then Is_Overriding_Operation
(N
)
564 Xrefs
.Table
(Indx
).Typ
:= 'P';
566 Xrefs
.Table
(Indx
).Typ
:= Typ
;
569 Xrefs
.Table
(Indx
).Eun
:= Get_Source_Unit
(Def
);
570 Xrefs
.Table
(Indx
).Lun
:= Get_Source_Unit
(Ref
);
571 Xrefs
.Table
(Indx
).Ent
:= Ent
;
572 Set_Has_Xref_Entry
(Ent
);
574 end Generate_Reference
;
576 -----------------------------------
577 -- Generate_Reference_To_Formals --
578 -----------------------------------
580 procedure Generate_Reference_To_Formals
(E
: Entity_Id
) is
584 if Is_Generic_Subprogram
(E
) then
585 Formal
:= First_Entity
(E
);
587 while Present
(Formal
)
588 and then not Is_Formal
(Formal
)
590 Next_Entity
(Formal
);
594 Formal
:= First_Formal
(E
);
597 while Present
(Formal
) loop
598 if Ekind
(Formal
) = E_In_Parameter
then
600 if Nkind
(Parameter_Type
(Parent
(Formal
)))
601 = N_Access_Definition
603 Generate_Reference
(E
, Formal
, '^', False);
605 Generate_Reference
(E
, Formal
, '>', False);
608 elsif Ekind
(Formal
) = E_In_Out_Parameter
then
609 Generate_Reference
(E
, Formal
, '=', False);
612 Generate_Reference
(E
, Formal
, '<', False);
615 Next_Formal
(Formal
);
617 end Generate_Reference_To_Formals
;
619 -------------------------------------------
620 -- Generate_Reference_To_Generic_Formals --
621 -------------------------------------------
623 procedure Generate_Reference_To_Generic_Formals
(E
: Entity_Id
) is
627 Formal
:= First_Entity
(E
);
629 while Present
(Formal
) loop
630 if Comes_From_Source
(Formal
) then
631 Generate_Reference
(E
, Formal
, 'z', False);
634 Next_Entity
(Formal
);
636 end Generate_Reference_To_Generic_Formals
;
642 procedure Initialize
is
647 -----------------------
648 -- Output_References --
649 -----------------------
651 procedure Output_References
is
653 procedure Get_Type_Reference
655 Tref
: out Entity_Id
;
656 Left
: out Character;
657 Right
: out Character);
658 -- Given an entity id Ent, determines whether a type reference is
659 -- required. If so, Tref is set to the entity for the type reference
660 -- and Left and Right are set to the left/right brackets to be
661 -- output for the reference. If no type reference is required, then
662 -- Tref is set to Empty, and Left/Right are set to space.
664 procedure Output_Import_Export_Info
(Ent
: Entity_Id
);
665 -- Ouput language and external name information for an interfaced
666 -- entity, using the format <language, external_name>,
668 ------------------------
669 -- Get_Type_Reference --
670 ------------------------
672 procedure Get_Type_Reference
674 Tref
: out Entity_Id
;
675 Left
: out Character;
676 Right
: out Character)
681 -- See if we have a type reference
690 -- Processing for types
692 if Is_Type
(Tref
) then
696 if Base_Type
(Tref
) = Tref
then
698 -- If derived, then get first subtype
700 if Tref
/= Etype
(Tref
) then
701 Tref
:= First_Subtype
(Etype
(Tref
));
703 -- Set brackets for derived type, but don't
704 -- override pointer case since the fact that
705 -- something is a pointer is more important
712 -- If non-derived ptr, get directly designated type.
713 -- If the type has a full view, all references are
714 -- on the partial view, that is seen first.
716 elsif Is_Access_Type
(Tref
) then
717 Tref
:= Directly_Designated_Type
(Tref
);
721 elsif Is_Private_Type
(Tref
)
722 and then Present
(Full_View
(Tref
))
723 and then Is_Access_Type
(Full_View
(Tref
))
725 Tref
:= Directly_Designated_Type
(Full_View
(Tref
));
729 -- If non-derived array, get component type.
730 -- Skip component type for case of String
731 -- or Wide_String, saves worthwhile space.
733 elsif Is_Array_Type
(Tref
)
734 and then Tref
/= Standard_String
735 and then Tref
/= Standard_Wide_String
737 Tref
:= Component_Type
(Tref
);
741 -- For other non-derived base types, nothing
747 -- For a subtype, go to ancestor subtype
750 Tref
:= Ancestor_Subtype
(Tref
);
752 -- If no ancestor subtype, go to base type
755 Tref
:= Base_Type
(Sav
);
759 -- For objects, functions, enum literals,
760 -- just get type from Etype field.
762 elsif Is_Object
(Tref
)
763 or else Ekind
(Tref
) = E_Enumeration_Literal
764 or else Ekind
(Tref
) = E_Function
765 or else Ekind
(Tref
) = E_Operator
767 Tref
:= Etype
(Tref
);
769 -- For anything else, exit
775 -- Exit if no type reference, or we are stuck in
776 -- some loop trying to find the type reference, or
777 -- if the type is standard void type (the latter is
778 -- an implementation artifact that should not show
779 -- up in the generated cross-references).
783 or else Tref
= Standard_Void_Type
;
785 -- If we have a usable type reference, return, otherwise
786 -- keep looking for something useful (we are looking for
787 -- something that either comes from source or standard)
789 if Sloc
(Tref
) = Standard_Location
790 or else Comes_From_Source
(Tref
)
792 -- If the reference is a subtype created for a generic
793 -- actual, go to actual directly, the inner subtype is
796 if Nkind
(Parent
(Tref
)) = N_Subtype_Declaration
797 and then not Comes_From_Source
(Parent
(Tref
))
799 (Is_Wrapper_Package
(Scope
(Tref
))
800 or else Is_Generic_Instance
(Scope
(Tref
)))
802 Tref
:= First_Subtype
(Base_Type
(Tref
));
809 -- If we fall through the loop, no type reference
814 end Get_Type_Reference
;
816 -------------------------------
817 -- Output_Import_Export_Info --
818 -------------------------------
820 procedure Output_Import_Export_Info
(Ent
: Entity_Id
) is
821 Language_Name
: Name_Id
;
822 Conv
: constant Convention_Id
:= Convention
(Ent
);
824 if Conv
= Convention_C
then
825 Language_Name
:= Name_C
;
827 elsif Conv
= Convention_CPP
then
828 Language_Name
:= Name_CPP
;
830 elsif Conv
= Convention_Ada
then
831 Language_Name
:= Name_Ada
;
834 -- These are the only languages that GPS knows about
839 Write_Info_Char
('<');
840 Get_Unqualified_Name_String
(Language_Name
);
842 for J
in 1 .. Name_Len
loop
843 Write_Info_Char
(Name_Buffer
(J
));
846 if Present
(Interface_Name
(Ent
)) then
847 Write_Info_Char
(',');
848 String_To_Name_Buffer
(Strval
(Interface_Name
(Ent
)));
850 for J
in 1 .. Name_Len
loop
851 Write_Info_Char
(Name_Buffer
(J
));
855 Write_Info_Char
('>');
856 end Output_Import_Export_Info
;
858 -- Start of processing for Output_References
861 if not Opt
.Xref_Active
then
865 -- Before we go ahead and output the references we have a problem
866 -- that needs dealing with. So far we have captured things that are
867 -- definitely referenced by the main unit, or defined in the main
868 -- unit. That's because we don't want to clutter up the ali file
869 -- for this unit with definition lines for entities in other units
870 -- that are not referenced.
872 -- But there is a glitch. We may reference an entity in another unit,
873 -- and it may have a type reference to an entity that is not directly
874 -- referenced in the main unit, which may mean that there is no xref
875 -- entry for this entity yet in the list of references.
877 -- If we don't do something about this, we will end with an orphan
878 -- type reference, i.e. it will point to an entity that does not
879 -- appear within the generated references in the ali file. That is
880 -- not good for tools using the xref information.
882 -- To fix this, we go through the references adding definition
883 -- entries for any unreferenced entities that can be referenced
884 -- in a type reference. There is a recursion problem here, and
885 -- that is dealt with by making sure that this traversal also
886 -- traverses any entries that get added by the traversal.
897 -- Note that this is not a for loop for a very good reason. The
898 -- processing of items in the table can add new items to the
899 -- table, and they must be processed as well
902 while J
<= Xrefs
.Last
loop
903 Ent
:= Xrefs
.Table
(J
).Ent
;
904 Get_Type_Reference
(Ent
, Tref
, L
, R
);
907 and then not Has_Xref_Entry
(Tref
)
908 and then Sloc
(Tref
) > No_Location
910 Xrefs
.Increment_Last
;
912 Loc
:= Original_Location
(Sloc
(Tref
));
913 Xrefs
.Table
(Indx
).Ent
:= Tref
;
914 Xrefs
.Table
(Indx
).Loc
:= No_Location
;
915 Xrefs
.Table
(Indx
).Eun
:= Get_Source_Unit
(Loc
);
916 Xrefs
.Table
(Indx
).Lun
:= No_Unit
;
917 Set_Has_Xref_Entry
(Tref
);
920 -- Collect inherited primitive operations that may be
921 -- declared in another unit and have no visible reference
922 -- in the current one.
925 and then Is_Tagged_Type
(Ent
)
926 and then Is_Derived_Type
(Ent
)
927 and then Ent
= Base_Type
(Ent
)
928 and then In_Extended_Main_Source_Unit
(Ent
)
931 Op_List
: constant Elist_Id
:= Primitive_Operations
(Ent
);
935 function Parent_Op
(E
: Entity_Id
) return Entity_Id
;
936 -- Find original operation, which may be inherited
937 -- through several derivations.
939 function Parent_Op
(E
: Entity_Id
) return Entity_Id
is
940 Orig_Op
: constant Entity_Id
:= Alias
(E
);
944 elsif not Comes_From_Source
(E
)
945 and then not Has_Xref_Entry
(Orig_Op
)
946 and then Comes_From_Source
(Orig_Op
)
950 return Parent_Op
(Orig_Op
);
955 Op
:= First_Elmt
(Op_List
);
956 while Present
(Op
) loop
957 Prim
:= Parent_Op
(Node
(Op
));
959 if Present
(Prim
) then
960 Xrefs
.Increment_Last
;
962 Loc
:= Original_Location
(Sloc
(Prim
));
963 Xrefs
.Table
(Indx
).Ent
:= Prim
;
964 Xrefs
.Table
(Indx
).Loc
:= No_Location
;
965 Xrefs
.Table
(Indx
).Eun
:=
966 Get_Source_Unit
(Sloc
(Prim
));
967 Xrefs
.Table
(Indx
).Lun
:= No_Unit
;
968 Set_Has_Xref_Entry
(Prim
);
980 -- Now we have all the references, including those for any embedded
981 -- type references, so we can sort them, and output them.
983 Output_Refs
: declare
985 Nrefs
: Nat
:= Xrefs
.Last
;
986 -- Number of references in table. This value may get reset
987 -- (reduced) when we eliminate duplicate reference entries.
989 Rnums
: array (0 .. Nrefs
) of Nat
;
990 -- This array contains numbers of references in the Xrefs table.
991 -- This list is sorted in output order. The extra 0'th entry is
992 -- convenient for the call to sort. When we sort the table, we
993 -- move the entries in Rnums around, but we do not move the
994 -- original table entries.
996 Curxu
: Unit_Number_Type
;
999 Curru
: Unit_Number_Type
;
1000 -- Current reference unit for one entity
1002 Cursrc
: Source_Buffer_Ptr
;
1003 -- Current xref unit source text
1008 Curnam
: String (1 .. Name_Buffer
'Length);
1010 -- Simple name and length of current entity
1012 Curdef
: Source_Ptr
;
1013 -- Original source location for current entity
1016 -- Current reference location
1019 -- Entity type character
1025 -- Renaming reference
1027 Trunit
: Unit_Number_Type
;
1028 -- Unit number for type reference
1030 function Lt
(Op1
, Op2
: Natural) return Boolean;
1031 -- Comparison function for Sort call
1033 function Name_Change
(X
: Entity_Id
) return Boolean;
1034 -- Determines if entity X has a different simple name from Curent
1036 procedure Move
(From
: Natural; To
: Natural);
1037 -- Move procedure for Sort call
1043 function Lt
(Op1
, Op2
: Natural) return Boolean is
1044 T1
: Xref_Entry
renames Xrefs
.Table
(Rnums
(Nat
(Op1
)));
1045 T2
: Xref_Entry
renames Xrefs
.Table
(Rnums
(Nat
(Op2
)));
1048 -- First test. If entity is in different unit, sort by unit
1050 if T1
.Eun
/= T2
.Eun
then
1051 return Dependency_Num
(T1
.Eun
) < Dependency_Num
(T2
.Eun
);
1053 -- Second test, within same unit, sort by entity Sloc
1055 elsif T1
.Def
/= T2
.Def
then
1056 return T1
.Def
< T2
.Def
;
1058 -- Third test, sort definitions ahead of references
1060 elsif T1
.Loc
= No_Location
then
1063 elsif T2
.Loc
= No_Location
then
1066 -- Fourth test, for same entity, sort by reference location unit
1068 elsif T1
.Lun
/= T2
.Lun
then
1069 return Dependency_Num
(T1
.Lun
) < Dependency_Num
(T2
.Lun
);
1071 -- Fifth test order of location within referencing unit
1073 elsif T1
.Loc
/= T2
.Loc
then
1074 return T1
.Loc
< T2
.Loc
;
1076 -- Finally, for two locations at the same address, we prefer
1077 -- the one that does NOT have the type 'r' so that a modification
1078 -- or extension takes preference, when there are more than one
1079 -- reference at the same location.
1082 return T2
.Typ
= 'r';
1090 procedure Move
(From
: Natural; To
: Natural) is
1092 Rnums
(Nat
(To
)) := Rnums
(Nat
(From
));
1099 function Name_Change
(X
: Entity_Id
) return Boolean is
1101 Get_Unqualified_Name_String
(Chars
(X
));
1103 if Name_Len
/= Curlen
then
1107 return Name_Buffer
(1 .. Curlen
) /= Curnam
(1 .. Curlen
);
1111 -- Start of processing for Output_Refs
1114 -- Capture the definition Sloc values. We delay doing this till now,
1115 -- since at the time the reference or definition is made, private
1116 -- types may be swapped, and the Sloc value may be incorrect. We
1117 -- also set up the pointer vector for the sort.
1119 for J
in 1 .. Nrefs
loop
1121 Xrefs
.Table
(J
).Def
:=
1122 Original_Location
(Sloc
(Xrefs
.Table
(J
).Ent
));
1125 -- Sort the references
1127 GNAT
.Heap_Sort_A
.Sort
1129 Move
'Unrestricted_Access,
1130 Lt
'Unrestricted_Access);
1132 -- Eliminate duplicate entries
1135 NR
: constant Nat
:= Nrefs
;
1138 -- We need this test for NR because if we force ALI file
1139 -- generation in case of errors detected, it may be the case
1140 -- that Nrefs is 0, so we should not reset it here
1145 for J
in 2 .. NR
loop
1146 if Xrefs
.Table
(Rnums
(J
)) /=
1147 Xrefs
.Table
(Rnums
(Nrefs
))
1150 Rnums
(Nrefs
) := Rnums
(J
);
1156 -- Initialize loop through references
1160 Curdef
:= No_Location
;
1162 Crloc
:= No_Location
;
1164 -- Loop to output references
1166 for Refno
in 1 .. Nrefs
loop
1167 Output_One_Ref
: declare
1173 XE
: Xref_Entry
renames Xrefs
.Table
(Rnums
(Refno
));
1174 -- The current entry to be accessed
1177 -- Used to index into source buffer to get entity name
1181 -- Used for {} or <> or () for type reference
1183 procedure Output_Instantiation_Refs
(Loc
: Source_Ptr
);
1184 -- Recursive procedure to output instantiation references for
1185 -- the given source ptr in [file|line[...]] form. No output
1186 -- if the given location is not a generic template reference.
1188 procedure Output_Overridden_Op
(Old_E
: Entity_Id
);
1189 -- For a subprogram that is overriding, display information
1190 -- about the inherited operation that it overrides.
1192 -------------------------------
1193 -- Output_Instantiation_Refs --
1194 -------------------------------
1196 procedure Output_Instantiation_Refs
(Loc
: Source_Ptr
) is
1197 Iloc
: constant Source_Ptr
:= Instantiation_Location
(Loc
);
1198 Lun
: Unit_Number_Type
;
1199 Cu
: constant Unit_Number_Type
:= Curru
;
1202 -- Nothing to do if this is not an instantiation
1204 if Iloc
= No_Location
then
1208 -- Output instantiation reference
1210 Write_Info_Char
('[');
1211 Lun
:= Get_Source_Unit
(Iloc
);
1213 if Lun
/= Curru
then
1215 Write_Info_Nat
(Dependency_Num
(Curru
));
1216 Write_Info_Char
('|');
1219 Write_Info_Nat
(Int
(Get_Logical_Line_Number
(Iloc
)));
1221 -- Recursive call to get nested instantiations
1223 Output_Instantiation_Refs
(Iloc
);
1225 -- Output final ] after call to get proper nesting
1227 Write_Info_Char
(']');
1230 end Output_Instantiation_Refs
;
1232 --------------------------
1233 -- Output_Overridden_Op --
1234 --------------------------
1236 procedure Output_Overridden_Op
(Old_E
: Entity_Id
) is
1239 and then Sloc
(Old_E
) /= Standard_Location
1242 Loc
: constant Source_Ptr
:= Sloc
(Old_E
);
1243 Par_Unit
: constant Unit_Number_Type
:=
1244 Get_Source_Unit
(Loc
);
1246 Write_Info_Char
('<');
1248 if Par_Unit
/= Curxu
then
1249 Write_Info_Nat
(Dependency_Num
(Par_Unit
));
1250 Write_Info_Char
('|');
1253 Write_Info_Nat
(Int
(Get_Logical_Line_Number
(Loc
)));
1254 Write_Info_Char
('p');
1255 Write_Info_Nat
(Int
(Get_Column_Number
(Loc
)));
1256 Write_Info_Char
('>');
1259 end Output_Overridden_Op
;
1261 -- Start of processing for Output_One_Ref
1265 Ctyp
:= Xref_Entity_Letters
(Ekind
(Ent
));
1267 -- Skip reference if it is the only reference to an entity,
1268 -- and it is an end-line reference, and the entity is not in
1269 -- the current extended source. This prevents junk entries
1270 -- consisting only of packages with end lines, where no
1271 -- entity from the package is actually referenced.
1274 and then Ent
/= Curent
1275 and then (Refno
= Nrefs
or else
1276 Ent
/= Xrefs
.Table
(Rnums
(Refno
+ 1)).Ent
)
1278 not In_Extended_Main_Source_Unit
(Ent
)
1283 -- For private type, get full view type
1286 and then Present
(Full_View
(XE
.Ent
))
1288 Ent
:= Underlying_Type
(Ent
);
1290 if Present
(Ent
) then
1291 Ctyp
:= Xref_Entity_Letters
(Ekind
(Ent
));
1295 -- Special exception for Boolean
1297 if Ctyp
= 'E' and then Is_Boolean_Type
(Ent
) then
1301 -- For variable reference, get corresponding type
1304 Ent
:= Etype
(XE
.Ent
);
1305 Ctyp
:= Fold_Lower
(Xref_Entity_Letters
(Ekind
(Ent
)));
1307 -- If variable is private type, get full view type
1310 and then Present
(Full_View
(Etype
(XE
.Ent
)))
1312 Ent
:= Underlying_Type
(Etype
(XE
.Ent
));
1314 if Present
(Ent
) then
1315 Ctyp
:= Fold_Lower
(Xref_Entity_Letters
(Ekind
(Ent
)));
1318 elsif Is_Generic_Type
(Ent
) then
1320 -- If the type of the entity is a generic private type
1321 -- there is no usable full view, so retain the indication
1322 -- that this is an object.
1327 -- Special handling for access parameter
1330 K
: constant Entity_Kind
:= Ekind
(Etype
(XE
.Ent
));
1333 if (K
= E_Anonymous_Access_Type
1335 K
= E_Anonymous_Access_Subprogram_Type
1337 E_Anonymous_Access_Protected_Subprogram_Type
)
1338 and then Is_Formal
(XE
.Ent
)
1342 -- Special handling for Boolean
1344 elsif Ctyp
= 'e' and then Is_Boolean_Type
(Ent
) then
1350 -- Special handling for abstract types and operations
1352 if Is_Abstract
(XE
.Ent
) then
1355 Ctyp
:= 'x'; -- abstract procedure
1357 elsif Ctyp
= 'V' then
1358 Ctyp
:= 'y'; -- abstract function
1360 elsif Ctyp
= 'R' then
1361 Ctyp
:= 'H'; -- abstract type
1365 -- Only output reference if interesting type of entity,
1366 -- and suppress self references, except for bodies that
1367 -- act as specs. Also suppress definitions of body formals
1368 -- (we only treat these as references, and the references
1369 -- were separately recorded).
1372 or else (XE
.Loc
= XE
.Def
1375 or else not Is_Subprogram
(XE
.Ent
)))
1376 or else (Is_Formal
(XE
.Ent
)
1377 and then Present
(Spec_Entity
(XE
.Ent
)))
1382 -- Start new Xref section if new xref unit
1384 if XE
.Eun
/= Curxu
then
1385 if Write_Info_Col
> 1 then
1390 Cursrc
:= Source_Text
(Source_Index
(Curxu
));
1392 Write_Info_Initiate
('X');
1393 Write_Info_Char
(' ');
1394 Write_Info_Nat
(Dependency_Num
(XE
.Eun
));
1395 Write_Info_Char
(' ');
1396 Write_Info_Name
(Reference_Name
(Source_Index
(XE
.Eun
)));
1399 -- Start new Entity line if new entity. Note that we
1400 -- consider two entities the same if they have the same
1401 -- name and source location. This causes entities in
1402 -- instantiations to be treated as though they referred
1409 (Name_Change
(XE
.Ent
) or else XE
.Def
/= Curdef
))
1414 Get_Unqualified_Name_String
(Chars
(XE
.Ent
));
1416 Curnam
(1 .. Curlen
) := Name_Buffer
(1 .. Curlen
);
1418 if Write_Info_Col
> 1 then
1422 -- Write column number information
1424 Write_Info_Nat
(Int
(Get_Logical_Line_Number
(XE
.Def
)));
1425 Write_Info_Char
(Ctyp
);
1426 Write_Info_Nat
(Int
(Get_Column_Number
(XE
.Def
)));
1428 -- Write level information
1430 Write_Level_Info
: declare
1431 function Is_Visible_Generic_Entity
1432 (E
: Entity_Id
) return Boolean;
1433 -- Check whether E is declared in the visible part
1434 -- of a generic package. For source navigation
1435 -- purposes, treat this as a visible entity.
1437 function Is_Private_Record_Component
1438 (E
: Entity_Id
) return Boolean;
1439 -- Check whether E is a non-inherited component of a
1440 -- private extension. Even if the enclosing record is
1441 -- public, we want to treat the component as private
1442 -- for navigation purposes.
1444 ---------------------------------
1445 -- Is_Private_Record_Component --
1446 ---------------------------------
1448 function Is_Private_Record_Component
1449 (E
: Entity_Id
) return Boolean
1451 S
: constant Entity_Id
:= Scope
(E
);
1454 Ekind
(E
) = E_Component
1455 and then Nkind
(Declaration_Node
(S
)) =
1456 N_Private_Extension_Declaration
1457 and then Original_Record_Component
(E
) = E
;
1458 end Is_Private_Record_Component
;
1460 -------------------------------
1461 -- Is_Visible_Generic_Entity --
1462 -------------------------------
1464 function Is_Visible_Generic_Entity
1465 (E
: Entity_Id
) return Boolean
1470 if Ekind
(Scope
(E
)) /= E_Generic_Package
then
1475 while Present
(Par
) loop
1477 Nkind
(Par
) = N_Generic_Package_Declaration
1479 -- Entity is a generic formal
1484 Nkind
(Parent
(Par
)) = N_Package_Specification
1487 Is_List_Member
(Par
)
1488 and then List_Containing
(Par
) =
1489 Visible_Declarations
(Parent
(Par
));
1491 Par
:= Parent
(Par
);
1496 end Is_Visible_Generic_Entity
;
1498 -- Start of processing for Write_Level_Info
1501 if Is_Hidden
(Curent
)
1502 or else Is_Private_Record_Component
(Curent
)
1504 Write_Info_Char
(' ');
1508 or else Is_Visible_Generic_Entity
(Curent
)
1510 Write_Info_Char
('*');
1513 Write_Info_Char
(' ');
1515 end Write_Level_Info
;
1517 -- Output entity name. We use the occurrence from the
1518 -- actual source program at the definition point
1520 P
:= Original_Location
(Sloc
(XE
.Ent
));
1522 -- Entity is character literal
1524 if Cursrc
(P
) = ''' then
1525 Write_Info_Char
(Cursrc
(P
));
1526 Write_Info_Char
(Cursrc
(P
+ 1));
1527 Write_Info_Char
(Cursrc
(P
+ 2));
1529 -- Entity is operator symbol
1531 elsif Cursrc
(P
) = '"' or else Cursrc
(P
) = '%' then
1532 Write_Info_Char
(Cursrc
(P
));
1537 Write_Info_Char
(Cursrc
(P2
));
1538 exit when Cursrc
(P2
) = Cursrc
(P
);
1541 -- Entity is identifier
1545 if Is_Start_Of_Wide_Char
(Cursrc
, P
) then
1546 Scan_Wide
(Cursrc
, P
, WC
, Err
);
1547 elsif not Identifier_Char
(Cursrc
(P
)) then
1555 Original_Location
(Sloc
(XE
.Ent
)) .. P
- 1
1557 Write_Info_Char
(Cursrc
(J
));
1561 -- See if we have a renaming reference
1563 if Is_Object
(XE
.Ent
)
1564 and then Present
(Renamed_Object
(XE
.Ent
))
1566 Rref
:= Renamed_Object
(XE
.Ent
);
1568 elsif Is_Overloadable
(XE
.Ent
)
1569 and then Nkind
(Parent
(Declaration_Node
(XE
.Ent
))) =
1570 N_Subprogram_Renaming_Declaration
1572 Rref
:= Name
(Parent
(Declaration_Node
(XE
.Ent
)));
1574 elsif Ekind
(XE
.Ent
) = E_Package
1575 and then Nkind
(Declaration_Node
(XE
.Ent
)) =
1576 N_Package_Renaming_Declaration
1578 Rref
:= Name
(Declaration_Node
(XE
.Ent
));
1584 if Present
(Rref
) then
1585 if Nkind
(Rref
) = N_Expanded_Name
then
1586 Rref
:= Selector_Name
(Rref
);
1589 if Nkind
(Rref
) = N_Identifier
1590 or else Nkind
(Rref
) = N_Operator_Symbol
1594 -- For renamed array components, use the array name
1595 -- for the renamed entity, which reflect the fact that
1596 -- in general the whole array is aliased.
1598 elsif Nkind
(Rref
) = N_Indexed_Component
then
1599 if Nkind
(Prefix
(Rref
)) = N_Identifier
then
1600 Rref
:= Prefix
(Rref
);
1601 elsif Nkind
(Prefix
(Rref
)) = N_Expanded_Name
then
1602 Rref
:= Selector_Name
(Prefix
(Rref
));
1612 -- Write out renaming reference if we have one
1614 if Present
(Rref
) then
1615 Write_Info_Char
('=');
1617 (Int
(Get_Logical_Line_Number
(Sloc
(Rref
))));
1618 Write_Info_Char
(':');
1620 (Int
(Get_Column_Number
(Sloc
(Rref
))));
1623 -- Indicate that the entity is in the unit
1624 -- of the current xref xection.
1628 -- Write out information about generic parent,
1629 -- if entity is an instance.
1631 if Is_Generic_Instance
(XE
.Ent
) then
1633 Gen_Par
: constant Entity_Id
:=
1636 (Unit_Declaration_Node
(XE
.Ent
)));
1637 Loc
: constant Source_Ptr
:= Sloc
(Gen_Par
);
1638 Gen_U
: constant Unit_Number_Type
:=
1639 Get_Source_Unit
(Loc
);
1641 Write_Info_Char
('[');
1642 if Curru
/= Gen_U
then
1643 Write_Info_Nat
(Dependency_Num
(Gen_U
));
1644 Write_Info_Char
('|');
1648 (Int
(Get_Logical_Line_Number
(Loc
)));
1649 Write_Info_Char
(']');
1653 -- See if we have a type reference and if so output
1655 Get_Type_Reference
(XE
.Ent
, Tref
, Left
, Right
);
1657 if Present
(Tref
) then
1659 -- Case of standard entity, output name
1661 if Sloc
(Tref
) = Standard_Location
then
1662 Write_Info_Char
(Left
);
1663 Write_Info_Name
(Chars
(Tref
));
1664 Write_Info_Char
(Right
);
1666 -- Case of source entity, output location
1669 Write_Info_Char
(Left
);
1670 Trunit
:= Get_Source_Unit
(Sloc
(Tref
));
1672 if Trunit
/= Curxu
then
1673 Write_Info_Nat
(Dependency_Num
(Trunit
));
1674 Write_Info_Char
('|');
1678 (Int
(Get_Logical_Line_Number
(Sloc
(Tref
))));
1681 Ent
: Entity_Id
:= Tref
;
1682 Kind
: constant Entity_Kind
:= Ekind
(Ent
);
1683 Ctyp
: Character := Xref_Entity_Letters
(Kind
);
1687 and then Present
(Full_View
(Ent
))
1689 Ent
:= Underlying_Type
(Ent
);
1691 if Present
(Ent
) then
1692 Ctyp
:= Xref_Entity_Letters
(Ekind
(Ent
));
1696 Write_Info_Char
(Ctyp
);
1700 (Int
(Get_Column_Number
(Sloc
(Tref
))));
1702 -- If the type comes from an instantiation,
1703 -- add the corresponding info.
1705 Output_Instantiation_Refs
(Sloc
(Tref
));
1706 Write_Info_Char
(Right
);
1710 -- If the entity is an overriding operation, write
1711 -- info on operation that was overridden.
1713 if Is_Subprogram
(XE
.Ent
)
1714 and then Is_Overriding_Operation
(XE
.Ent
)
1716 Output_Overridden_Op
(Overridden_Operation
(XE
.Ent
));
1719 -- End of processing for entity output
1721 Crloc
:= No_Location
;
1724 -- Output the reference
1726 if XE
.Loc
/= No_Location
1727 and then XE
.Loc
/= Crloc
1731 -- Start continuation if line full, else blank
1733 if Write_Info_Col
> 72 then
1735 Write_Info_Initiate
('.');
1738 Write_Info_Char
(' ');
1740 -- Output file number if changed
1742 if XE
.Lun
/= Curru
then
1744 Write_Info_Nat
(Dependency_Num
(Curru
));
1745 Write_Info_Char
('|');
1748 Write_Info_Nat
(Int
(Get_Logical_Line_Number
(XE
.Loc
)));
1749 Write_Info_Char
(XE
.Typ
);
1751 if Is_Overloadable
(XE
.Ent
)
1752 and then Is_Imported
(XE
.Ent
)
1753 and then XE
.Typ
= 'b'
1755 Output_Import_Export_Info
(XE
.Ent
);
1758 Write_Info_Nat
(Int
(Get_Column_Number
(XE
.Loc
)));
1760 Output_Instantiation_Refs
(Sloc
(XE
.Ent
));
1771 end Output_References
;