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, 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 Restrict
; use Restrict
;
36 with Rident
; use Rident
;
37 with Sem_Prag
; use Sem_Prag
;
38 with Sem_Util
; use Sem_Util
;
39 with Sinfo
; use Sinfo
;
40 with Sinput
; use Sinput
;
41 with Snames
; use Snames
;
42 with Stringt
; use Stringt
;
43 with Stand
; use Stand
;
44 with Table
; use Table
;
45 with Widechar
; use Widechar
;
47 with GNAT
.Heap_Sort_A
;
49 package body Lib
.Xref
is
55 -- The Xref table is used to record references. The Loc field is set
56 -- to No_Location for a definition entry.
58 subtype Xref_Entry_Number
is Int
;
60 type Xref_Entry
is record
62 -- Entity referenced (E parameter to Generate_Reference)
65 -- Original source location for entity being referenced. Note that
66 -- these values are used only during the output process, they are
67 -- not set when the entries are originally built. This is because
68 -- private entities can be swapped when the initial call is made.
71 -- Location of reference (Original_Location (Sloc field of N parameter
72 -- to Generate_Reference). Set to No_Location for the case of a
73 -- defining occurrence.
76 -- Reference type (Typ param to Generate_Reference)
78 Eun
: Unit_Number_Type
;
79 -- Unit number corresponding to Ent
81 Lun
: Unit_Number_Type
;
82 -- Unit number corresponding to Loc. Value is undefined and not
83 -- referenced if Loc is set to No_Location.
87 package Xrefs
is new Table
.Table
(
88 Table_Component_Type
=> Xref_Entry
,
89 Table_Index_Type
=> Xref_Entry_Number
,
91 Table_Initial
=> Alloc
.Xrefs_Initial
,
92 Table_Increment
=> Alloc
.Xrefs_Increment
,
93 Table_Name
=> "Xrefs");
95 -------------------------
96 -- Generate_Definition --
97 -------------------------
99 procedure Generate_Definition
(E
: Entity_Id
) is
104 pragma Assert
(Nkind
(E
) in N_Entity
);
106 -- Note that we do not test Xref_Entity_Letters here. It is too
107 -- early to do so, since we are often called before the entity
108 -- is fully constructed, so that the Ekind is still E_Void.
112 -- Definition must come from source
114 and then Comes_From_Source
(E
)
116 -- And must have a reasonable source location that is not
117 -- within an instance (all entities in instances are ignored)
119 and then Sloc
(E
) > No_Location
120 and then Instantiation_Location
(Sloc
(E
)) = No_Location
122 -- And must be a non-internal name from the main source unit
124 and then In_Extended_Main_Source_Unit
(E
)
125 and then not Is_Internal_Name
(Chars
(E
))
127 Xrefs
.Increment_Last
;
129 Loc
:= Original_Location
(Sloc
(E
));
131 Xrefs
.Table
(Indx
).Ent
:= E
;
132 Xrefs
.Table
(Indx
).Loc
:= No_Location
;
133 Xrefs
.Table
(Indx
).Eun
:= Get_Source_Unit
(Loc
);
134 Xrefs
.Table
(Indx
).Lun
:= No_Unit
;
135 Set_Has_Xref_Entry
(E
);
137 end Generate_Definition
;
139 ---------------------------------
140 -- Generate_Operator_Reference --
141 ---------------------------------
143 procedure Generate_Operator_Reference
148 if not In_Extended_Main_Source_Unit
(N
) then
152 -- If the operator is not a Standard operator, then we generate
153 -- a real reference to the user defined operator.
155 if Sloc
(Entity
(N
)) /= Standard_Location
then
156 Generate_Reference
(Entity
(N
), N
);
158 -- A reference to an implicit inequality operator is a also a
159 -- reference to the user-defined equality.
161 if Nkind
(N
) = N_Op_Ne
162 and then not Comes_From_Source
(Entity
(N
))
163 and then Present
(Corresponding_Equality
(Entity
(N
)))
165 Generate_Reference
(Corresponding_Equality
(Entity
(N
)), N
);
168 -- For the case of Standard operators, we mark the result type
169 -- as referenced. This ensures that in the case where we are
170 -- using a derived operator, we mark an entity of the unit that
171 -- implicitly defines this operator as used. Otherwise we may
172 -- think that no entity of the unit is used. The actual entity
173 -- marked as referenced is the first subtype, which is the user
174 -- defined entity that is relevant.
176 -- Note: we only do this for operators that come from source.
177 -- The generated code sometimes reaches for entities that do
178 -- not need to be explicitly visible (for example, when we
179 -- expand the code for comparing two record types, the fields
180 -- of the record may not be visible).
182 elsif Comes_From_Source
(N
) then
183 Set_Referenced
(First_Subtype
(T
));
185 end Generate_Operator_Reference
;
187 ------------------------
188 -- Generate_Reference --
189 ------------------------
191 procedure Generate_Reference
194 Typ
: Character := 'r';
195 Set_Ref
: Boolean := True;
196 Force
: Boolean := False)
204 function Is_On_LHS
(Node
: Node_Id
) return Boolean;
205 -- Used to check if a node is on the left hand side of an
206 -- assignment. The following cases are handled:
208 -- Variable Node is a direct descendant of an assignment
211 -- Prefix Of an indexed or selected component that is
212 -- present in a subtree rooted by an assignment
213 -- statement. There is no restriction of nesting
214 -- of components, thus cases such as A.B(C).D are
221 -- Couldn't we use Is_Lvalue or whatever it is called ???
223 function Is_On_LHS
(Node
: Node_Id
) return Boolean is
227 -- Only identifiers are considered, is this necessary???
229 if Nkind
(N
) /= N_Identifier
then
233 -- Reach the assignment statement subtree root. In the
234 -- case of a variable being a direct descendant of an
235 -- assignment statement, the loop is skiped.
237 while Nkind
(Parent
(N
)) /= N_Assignment_Statement
loop
239 -- Check whether the parent is a component and the
240 -- current node is its prefix.
242 if (Nkind
(Parent
(N
)) = N_Selected_Component
244 Nkind
(Parent
(N
)) = N_Indexed_Component
)
245 and then Prefix
(Parent
(N
)) = N
253 -- Parent (N) is an assignment statement, check whether
256 return Name
(Parent
(N
)) = N
;
259 -- Start of processing for Generate_Reference
262 pragma Assert
(Nkind
(E
) in N_Entity
);
264 -- Check for obsolescent reference to ASCII
266 if E
= Standard_ASCII
then
267 Check_Restriction
(No_Obsolescent_Features
, N
);
270 -- Warn if reference to Ada 2005 entity not in Ada 2005 mode
272 if Is_Ada_2005
(E
) and then Ada_Version
< Ada_05
then
273 Error_Msg_NE
("& is only defined in Ada 2005?", N
, E
);
276 -- Never collect references if not in main source unit. However,
277 -- we omit this test if Typ is 'e' or 'k', since these entries are
278 -- really structural, and it is useful to have them in units
279 -- that reference packages as well as units that define packages.
280 -- We also omit the test for the case of 'p' since we want to
281 -- include inherited primitive operations from other packages.
283 if not In_Extended_Main_Source_Unit
(N
)
291 -- For reference type p, the entity must be in main source unit
293 if Typ
= 'p' and then not In_Extended_Main_Source_Unit
(E
) then
297 -- Unless the reference is forced, we ignore references where
298 -- the reference itself does not come from Source.
300 if not Force
and then not Comes_From_Source
(N
) then
304 -- Deal with setting entity as referenced, unless suppressed.
305 -- Note that we still do Set_Referenced on entities that do not
306 -- come from source. This situation arises when we have a source
307 -- reference to a derived operation, where the derived operation
308 -- itself does not come from source, but we still want to mark it
309 -- as referenced, since we really are referencing an entity in the
310 -- corresponding package (this avoids incorrect complaints that the
311 -- package contains no referenced entities).
315 -- For a variable that appears on the left side of an
316 -- assignment statement, we set the Referenced_As_LHS
317 -- flag since this is indeed a left hand side.
318 -- We also set the Referenced_As_LHS flag of a prefix
319 -- of selected or indexed component.
321 if Ekind
(E
) = E_Variable
322 and then Is_On_LHS
(N
)
324 Set_Referenced_As_LHS
(E
);
326 -- Check for a reference in a pragma that should not count as a
327 -- making the variable referenced for warning purposes.
329 elsif Is_Non_Significant_Pragma_Reference
(N
) then
332 -- A reference in an attribute definition clause does not
333 -- count as a reference except for the case of Address.
334 -- The reason that 'Address is an exception is that it
335 -- creates an alias through which the variable may be
338 elsif Nkind
(Parent
(N
)) = N_Attribute_Definition_Clause
339 and then Chars
(Parent
(N
)) /= Name_Address
340 and then N
= Name
(Parent
(N
))
344 -- Constant completion does not count as a reference
347 and then Ekind
(E
) = E_Constant
351 -- Record representation clause does not count as a reference
353 elsif Nkind
(N
) = N_Identifier
354 and then Nkind
(Parent
(N
)) = N_Record_Representation_Clause
358 -- Discriminants do not need to produce a reference to record type
361 and then Nkind
(Parent
(N
)) = N_Discriminant_Specification
365 -- Any other occurrence counts as referencing the entity
371 -- Check for pragma Unreferenced given and reference is within
372 -- this source unit (occasion for possible warning to be issued)
374 if Has_Pragma_Unreferenced
(E
)
375 and then In_Same_Extended_Unit
(E
, N
)
377 -- A reference as a named parameter in a call does not count
378 -- as a violation of pragma Unreferenced for this purpose.
380 if Nkind
(N
) = N_Identifier
381 and then Nkind
(Parent
(N
)) = N_Parameter_Association
382 and then Selector_Name
(Parent
(N
)) = N
386 -- Neither does a reference to a variable on the left side
389 elsif Ekind
(E
) = E_Variable
390 and then Nkind
(Parent
(N
)) = N_Assignment_Statement
391 and then Name
(Parent
(N
)) = N
395 -- For entry formals, we want to place the warning on the
396 -- corresponding entity in the accept statement. The current
397 -- scope is the body of the accept, so we find the formal
398 -- whose name matches that of the entry formal (there is no
399 -- link between the two entities, and the one in the accept
400 -- statement is only used for conformance checking).
402 elsif Ekind
(Scope
(E
)) = E_Entry
then
407 BE
:= First_Entity
(Current_Scope
);
408 while Present
(BE
) loop
409 if Chars
(BE
) = Chars
(E
) then
411 ("?pragma Unreferenced given for&", N
, BE
);
419 -- Here we issue the warning, since this is a real reference
422 Error_Msg_NE
("?pragma Unreferenced given for&", N
, E
);
426 -- If this is a subprogram instance, mark as well the internal
427 -- subprogram in the wrapper package, which may be a visible
430 if Is_Overloadable
(E
)
431 and then Is_Generic_Instance
(E
)
432 and then Present
(Alias
(E
))
434 Set_Referenced
(Alias
(E
));
438 -- Generate reference if all conditions are met:
441 -- Cross referencing must be active
445 -- The entity must be one for which we collect references
447 and then Xref_Entity_Letters
(Ekind
(E
)) /= ' '
449 -- Both Sloc values must be set to something sensible
451 and then Sloc
(E
) > No_Location
452 and then Sloc
(N
) > No_Location
454 -- We ignore references from within an instance
456 and then Instantiation_Location
(Sloc
(N
)) = No_Location
458 -- Ignore dummy references
462 if Nkind
(N
) = N_Identifier
464 Nkind
(N
) = N_Defining_Identifier
468 Nkind
(N
) = N_Defining_Operator_Symbol
470 Nkind
(N
) = N_Operator_Symbol
472 (Nkind
(N
) = N_Character_Literal
473 and then Sloc
(Entity
(N
)) /= Standard_Location
)
475 Nkind
(N
) = N_Defining_Character_Literal
479 elsif Nkind
(N
) = N_Expanded_Name
481 Nkind
(N
) = N_Selected_Component
483 Nod
:= Selector_Name
(N
);
489 -- Normal case of source entity comes from source
491 if Comes_From_Source
(E
) then
494 -- Entity does not come from source, but is a derived subprogram
495 -- and the derived subprogram comes from source (after one or more
496 -- derivations) in which case the reference is to parent subprogram.
498 elsif Is_Overloadable
(E
)
499 and then Present
(Alias
(E
))
504 if Comes_From_Source
(Ent
) then
506 elsif No
(Alias
(Ent
)) then
513 -- Record components of discriminated subtypes or derived types
514 -- must be treated as references to the original component.
516 elsif Ekind
(E
) = E_Component
517 and then Comes_From_Source
(Original_Record_Component
(E
))
519 Ent
:= Original_Record_Component
(E
);
521 -- Ignore reference to any other entity that is not from source
527 -- Record reference to entity
529 Ref
:= Original_Location
(Sloc
(Nod
));
530 Def
:= Original_Location
(Sloc
(Ent
));
532 Xrefs
.Increment_Last
;
535 Xrefs
.Table
(Indx
).Loc
:= Ref
;
537 -- Overriding operations are marked with 'P'.
540 and then Is_Subprogram
(N
)
541 and then Is_Overriding_Operation
(N
)
543 Xrefs
.Table
(Indx
).Typ
:= 'P';
545 Xrefs
.Table
(Indx
).Typ
:= Typ
;
548 Xrefs
.Table
(Indx
).Eun
:= Get_Source_Unit
(Def
);
549 Xrefs
.Table
(Indx
).Lun
:= Get_Source_Unit
(Ref
);
550 Xrefs
.Table
(Indx
).Ent
:= Ent
;
551 Set_Has_Xref_Entry
(Ent
);
553 end Generate_Reference
;
555 -----------------------------------
556 -- Generate_Reference_To_Formals --
557 -----------------------------------
559 procedure Generate_Reference_To_Formals
(E
: Entity_Id
) is
563 if Is_Generic_Subprogram
(E
) then
564 Formal
:= First_Entity
(E
);
566 while Present
(Formal
)
567 and then not Is_Formal
(Formal
)
569 Next_Entity
(Formal
);
573 Formal
:= First_Formal
(E
);
576 while Present
(Formal
) loop
577 if Ekind
(Formal
) = E_In_Parameter
then
579 if Nkind
(Parameter_Type
(Parent
(Formal
)))
580 = N_Access_Definition
582 Generate_Reference
(E
, Formal
, '^', False);
584 Generate_Reference
(E
, Formal
, '>', False);
587 elsif Ekind
(Formal
) = E_In_Out_Parameter
then
588 Generate_Reference
(E
, Formal
, '=', False);
591 Generate_Reference
(E
, Formal
, '<', False);
594 Next_Formal
(Formal
);
596 end Generate_Reference_To_Formals
;
598 -------------------------------------------
599 -- Generate_Reference_To_Generic_Formals --
600 -------------------------------------------
602 procedure Generate_Reference_To_Generic_Formals
(E
: Entity_Id
) is
606 Formal
:= First_Entity
(E
);
608 while Present
(Formal
) loop
609 if Comes_From_Source
(Formal
) then
610 Generate_Reference
(E
, Formal
, 'z', False);
613 Next_Entity
(Formal
);
615 end Generate_Reference_To_Generic_Formals
;
621 procedure Initialize
is
626 -----------------------
627 -- Output_References --
628 -----------------------
630 procedure Output_References
is
632 procedure Get_Type_Reference
634 Tref
: out Entity_Id
;
635 Left
: out Character;
636 Right
: out Character);
637 -- Given an entity id Ent, determines whether a type reference is
638 -- required. If so, Tref is set to the entity for the type reference
639 -- and Left and Right are set to the left/right brackets to be
640 -- output for the reference. If no type reference is required, then
641 -- Tref is set to Empty, and Left/Right are set to space.
643 procedure Output_Import_Export_Info
(Ent
: Entity_Id
);
644 -- Ouput language and external name information for an interfaced
645 -- entity, using the format <language, external_name>,
647 ------------------------
648 -- Get_Type_Reference --
649 ------------------------
651 procedure Get_Type_Reference
653 Tref
: out Entity_Id
;
654 Left
: out Character;
655 Right
: out Character)
660 -- See if we have a type reference
669 -- Processing for types
671 if Is_Type
(Tref
) then
675 if Base_Type
(Tref
) = Tref
then
677 -- If derived, then get first subtype
679 if Tref
/= Etype
(Tref
) then
680 Tref
:= First_Subtype
(Etype
(Tref
));
682 -- Set brackets for derived type, but don't
683 -- override pointer case since the fact that
684 -- something is a pointer is more important
691 -- If non-derived ptr, get directly designated type.
692 -- If the type has a full view, all references are
693 -- on the partial view, that is seen first.
695 elsif Is_Access_Type
(Tref
) then
696 Tref
:= Directly_Designated_Type
(Tref
);
700 elsif Is_Private_Type
(Tref
)
701 and then Present
(Full_View
(Tref
))
702 and then Is_Access_Type
(Full_View
(Tref
))
704 Tref
:= Directly_Designated_Type
(Full_View
(Tref
));
708 -- If non-derived array, get component type.
709 -- Skip component type for case of String
710 -- or Wide_String, saves worthwhile space.
712 elsif Is_Array_Type
(Tref
)
713 and then Tref
/= Standard_String
714 and then Tref
/= Standard_Wide_String
716 Tref
:= Component_Type
(Tref
);
720 -- For other non-derived base types, nothing
726 -- For a subtype, go to ancestor subtype.
729 Tref
:= Ancestor_Subtype
(Tref
);
731 -- If no ancestor subtype, go to base type
734 Tref
:= Base_Type
(Sav
);
738 -- For objects, functions, enum literals,
739 -- just get type from Etype field.
741 elsif Is_Object
(Tref
)
742 or else Ekind
(Tref
) = E_Enumeration_Literal
743 or else Ekind
(Tref
) = E_Function
744 or else Ekind
(Tref
) = E_Operator
746 Tref
:= Etype
(Tref
);
748 -- For anything else, exit
754 -- Exit if no type reference, or we are stuck in
755 -- some loop trying to find the type reference, or
756 -- if the type is standard void type (the latter is
757 -- an implementation artifact that should not show
758 -- up in the generated cross-references).
762 or else Tref
= Standard_Void_Type
;
764 -- If we have a usable type reference, return, otherwise
765 -- keep looking for something useful (we are looking for
766 -- something that either comes from source or standard)
768 if Sloc
(Tref
) = Standard_Location
769 or else Comes_From_Source
(Tref
)
771 -- If the reference is a subtype created for a generic
772 -- actual, go to actual directly, the inner subtype is
775 if Nkind
(Parent
(Tref
)) = N_Subtype_Declaration
776 and then not Comes_From_Source
(Parent
(Tref
))
778 (Is_Wrapper_Package
(Scope
(Tref
))
779 or else Is_Generic_Instance
(Scope
(Tref
)))
781 Tref
:= Base_Type
(Tref
);
788 -- If we fall through the loop, no type reference
793 end Get_Type_Reference
;
795 -------------------------------
796 -- Output_Import_Export_Info --
797 -------------------------------
799 procedure Output_Import_Export_Info
(Ent
: Entity_Id
) is
800 Language_Name
: Name_Id
;
801 Conv
: constant Convention_Id
:= Convention
(Ent
);
803 if Conv
= Convention_C
then
804 Language_Name
:= Name_C
;
806 elsif Conv
= Convention_CPP
then
807 Language_Name
:= Name_CPP
;
809 elsif Conv
= Convention_Ada
then
810 Language_Name
:= Name_Ada
;
813 -- These are the only languages that GPS knows about.
818 Write_Info_Char
('<');
819 Get_Unqualified_Name_String
(Language_Name
);
821 for J
in 1 .. Name_Len
loop
822 Write_Info_Char
(Name_Buffer
(J
));
825 if Present
(Interface_Name
(Ent
)) then
826 Write_Info_Char
(',');
827 String_To_Name_Buffer
(Strval
(Interface_Name
(Ent
)));
829 for J
in 1 .. Name_Len
loop
830 Write_Info_Char
(Name_Buffer
(J
));
834 Write_Info_Char
('>');
835 end Output_Import_Export_Info
;
837 -- Start of processing for Output_References
840 if not Opt
.Xref_Active
then
844 -- Before we go ahead and output the references we have a problem
845 -- that needs dealing with. So far we have captured things that are
846 -- definitely referenced by the main unit, or defined in the main
847 -- unit. That's because we don't want to clutter up the ali file
848 -- for this unit with definition lines for entities in other units
849 -- that are not referenced.
851 -- But there is a glitch. We may reference an entity in another unit,
852 -- and it may have a type reference to an entity that is not directly
853 -- referenced in the main unit, which may mean that there is no xref
854 -- entry for this entity yet in the list of references.
856 -- If we don't do something about this, we will end with an orphan
857 -- type reference, i.e. it will point to an entity that does not
858 -- appear within the generated references in the ali file. That is
859 -- not good for tools using the xref information.
861 -- To fix this, we go through the references adding definition
862 -- entries for any unreferenced entities that can be referenced
863 -- in a type reference. There is a recursion problem here, and
864 -- that is dealt with by making sure that this traversal also
865 -- traverses any entries that get added by the traversal.
876 -- Note that this is not a for loop for a very good reason. The
877 -- processing of items in the table can add new items to the
878 -- table, and they must be processed as well
881 while J
<= Xrefs
.Last
loop
882 Ent
:= Xrefs
.Table
(J
).Ent
;
883 Get_Type_Reference
(Ent
, Tref
, L
, R
);
886 and then not Has_Xref_Entry
(Tref
)
887 and then Sloc
(Tref
) > No_Location
889 Xrefs
.Increment_Last
;
891 Loc
:= Original_Location
(Sloc
(Tref
));
892 Xrefs
.Table
(Indx
).Ent
:= Tref
;
893 Xrefs
.Table
(Indx
).Loc
:= No_Location
;
894 Xrefs
.Table
(Indx
).Eun
:= Get_Source_Unit
(Loc
);
895 Xrefs
.Table
(Indx
).Lun
:= No_Unit
;
896 Set_Has_Xref_Entry
(Tref
);
899 -- Collect inherited primitive operations that may be
900 -- declared in another unit and have no visible reference
901 -- in the current one.
904 and then Is_Tagged_Type
(Ent
)
905 and then Is_Derived_Type
(Ent
)
906 and then Ent
= Base_Type
(Ent
)
907 and then In_Extended_Main_Source_Unit
(Ent
)
910 Op_List
: constant Elist_Id
:= Primitive_Operations
(Ent
);
914 function Parent_Op
(E
: Entity_Id
) return Entity_Id
;
915 -- Find original operation, which may be inherited
916 -- through several derivations.
918 function Parent_Op
(E
: Entity_Id
) return Entity_Id
is
919 Orig_Op
: constant Entity_Id
:= Alias
(E
);
923 elsif not Comes_From_Source
(E
)
924 and then not Has_Xref_Entry
(Orig_Op
)
925 and then Comes_From_Source
(Orig_Op
)
929 return Parent_Op
(Orig_Op
);
934 Op
:= First_Elmt
(Op_List
);
935 while Present
(Op
) loop
936 Prim
:= Parent_Op
(Node
(Op
));
938 if Present
(Prim
) then
939 Xrefs
.Increment_Last
;
941 Loc
:= Original_Location
(Sloc
(Prim
));
942 Xrefs
.Table
(Indx
).Ent
:= Prim
;
943 Xrefs
.Table
(Indx
).Loc
:= No_Location
;
944 Xrefs
.Table
(Indx
).Eun
:=
945 Get_Source_Unit
(Sloc
(Prim
));
946 Xrefs
.Table
(Indx
).Lun
:= No_Unit
;
947 Set_Has_Xref_Entry
(Prim
);
959 -- Now we have all the references, including those for any embedded
960 -- type references, so we can sort them, and output them.
962 Output_Refs
: declare
964 Nrefs
: Nat
:= Xrefs
.Last
;
965 -- Number of references in table. This value may get reset
966 -- (reduced) when we eliminate duplicate reference entries.
968 Rnums
: array (0 .. Nrefs
) of Nat
;
969 -- This array contains numbers of references in the Xrefs table.
970 -- This list is sorted in output order. The extra 0'th entry is
971 -- convenient for the call to sort. When we sort the table, we
972 -- move the entries in Rnums around, but we do not move the
973 -- original table entries.
975 Curxu
: Unit_Number_Type
;
978 Curru
: Unit_Number_Type
;
979 -- Current reference unit for one entity
981 Cursrc
: Source_Buffer_Ptr
;
982 -- Current xref unit source text
987 Curnam
: String (1 .. Name_Buffer
'Length);
989 -- Simple name and length of current entity
992 -- Original source location for current entity
995 -- Current reference location
998 -- Entity type character
1004 -- Renaming reference
1006 Trunit
: Unit_Number_Type
;
1007 -- Unit number for type reference
1009 function Lt
(Op1
, Op2
: Natural) return Boolean;
1010 -- Comparison function for Sort call
1012 function Name_Change
(X
: Entity_Id
) return Boolean;
1013 -- Determines if entity X has a different simple name from Curent
1015 procedure Move
(From
: Natural; To
: Natural);
1016 -- Move procedure for Sort call
1022 function Lt
(Op1
, Op2
: Natural) return Boolean is
1023 T1
: Xref_Entry
renames Xrefs
.Table
(Rnums
(Nat
(Op1
)));
1024 T2
: Xref_Entry
renames Xrefs
.Table
(Rnums
(Nat
(Op2
)));
1027 -- First test. If entity is in different unit, sort by unit
1029 if T1
.Eun
/= T2
.Eun
then
1030 return Dependency_Num
(T1
.Eun
) < Dependency_Num
(T2
.Eun
);
1032 -- Second test, within same unit, sort by entity Sloc
1034 elsif T1
.Def
/= T2
.Def
then
1035 return T1
.Def
< T2
.Def
;
1037 -- Third test, sort definitions ahead of references
1039 elsif T1
.Loc
= No_Location
then
1042 elsif T2
.Loc
= No_Location
then
1045 -- Fourth test, for same entity, sort by reference location unit
1047 elsif T1
.Lun
/= T2
.Lun
then
1048 return Dependency_Num
(T1
.Lun
) < Dependency_Num
(T2
.Lun
);
1050 -- Fifth test order of location within referencing unit
1052 elsif T1
.Loc
/= T2
.Loc
then
1053 return T1
.Loc
< T2
.Loc
;
1055 -- Finally, for two locations at the same address, we prefer
1056 -- the one that does NOT have the type 'r' so that a modification
1057 -- or extension takes preference, when there are more than one
1058 -- reference at the same location.
1061 return T2
.Typ
= 'r';
1069 procedure Move
(From
: Natural; To
: Natural) is
1071 Rnums
(Nat
(To
)) := Rnums
(Nat
(From
));
1078 function Name_Change
(X
: Entity_Id
) return Boolean is
1080 Get_Unqualified_Name_String
(Chars
(X
));
1082 if Name_Len
/= Curlen
then
1086 return Name_Buffer
(1 .. Curlen
) /= Curnam
(1 .. Curlen
);
1090 -- Start of processing for Output_Refs
1093 -- Capture the definition Sloc values. We delay doing this till now,
1094 -- since at the time the reference or definition is made, private
1095 -- types may be swapped, and the Sloc value may be incorrect. We
1096 -- also set up the pointer vector for the sort.
1098 for J
in 1 .. Nrefs
loop
1100 Xrefs
.Table
(J
).Def
:=
1101 Original_Location
(Sloc
(Xrefs
.Table
(J
).Ent
));
1104 -- Sort the references
1106 GNAT
.Heap_Sort_A
.Sort
1108 Move
'Unrestricted_Access,
1109 Lt
'Unrestricted_Access);
1111 -- Eliminate duplicate entries
1114 NR
: constant Nat
:= Nrefs
;
1117 -- We need this test for NR because if we force ALI file
1118 -- generation in case of errors detected, it may be the case
1119 -- that Nrefs is 0, so we should not reset it here
1124 for J
in 2 .. NR
loop
1125 if Xrefs
.Table
(Rnums
(J
)) /=
1126 Xrefs
.Table
(Rnums
(Nrefs
))
1129 Rnums
(Nrefs
) := Rnums
(J
);
1135 -- Initialize loop through references
1139 Curdef
:= No_Location
;
1141 Crloc
:= No_Location
;
1143 -- Loop to output references
1145 for Refno
in 1 .. Nrefs
loop
1146 Output_One_Ref
: declare
1152 XE
: Xref_Entry
renames Xrefs
.Table
(Rnums
(Refno
));
1153 -- The current entry to be accessed
1156 -- Used to index into source buffer to get entity name
1160 -- Used for {} or <> or () for type reference
1162 procedure Output_Instantiation_Refs
(Loc
: Source_Ptr
);
1163 -- Recursive procedure to output instantiation references for
1164 -- the given source ptr in [file|line[...]] form. No output
1165 -- if the given location is not a generic template reference.
1167 -------------------------------
1168 -- Output_Instantiation_Refs --
1169 -------------------------------
1171 procedure Output_Instantiation_Refs
(Loc
: Source_Ptr
) is
1172 Iloc
: constant Source_Ptr
:= Instantiation_Location
(Loc
);
1173 Lun
: Unit_Number_Type
;
1174 Cu
: constant Unit_Number_Type
:= Curru
;
1177 -- Nothing to do if this is not an instantiation
1179 if Iloc
= No_Location
then
1183 -- Output instantiation reference
1185 Write_Info_Char
('[');
1186 Lun
:= Get_Source_Unit
(Iloc
);
1188 if Lun
/= Curru
then
1190 Write_Info_Nat
(Dependency_Num
(Curru
));
1191 Write_Info_Char
('|');
1194 Write_Info_Nat
(Int
(Get_Logical_Line_Number
(Iloc
)));
1196 -- Recursive call to get nested instantiations
1198 Output_Instantiation_Refs
(Iloc
);
1200 -- Output final ] after call to get proper nesting
1202 Write_Info_Char
(']');
1205 end Output_Instantiation_Refs
;
1207 -- Start of processing for Output_One_Ref
1211 Ctyp
:= Xref_Entity_Letters
(Ekind
(Ent
));
1213 -- Skip reference if it is the only reference to an entity,
1214 -- and it is an end-line reference, and the entity is not in
1215 -- the current extended source. This prevents junk entries
1216 -- consisting only of packages with end lines, where no
1217 -- entity from the package is actually referenced.
1220 and then Ent
/= Curent
1221 and then (Refno
= Nrefs
or else
1222 Ent
/= Xrefs
.Table
(Rnums
(Refno
+ 1)).Ent
)
1224 not In_Extended_Main_Source_Unit
(Ent
)
1229 -- For private type, get full view type
1232 and then Present
(Full_View
(XE
.Ent
))
1234 Ent
:= Underlying_Type
(Ent
);
1236 if Present
(Ent
) then
1237 Ctyp
:= Xref_Entity_Letters
(Ekind
(Ent
));
1241 -- Special exception for Boolean
1243 if Ctyp
= 'E' and then Is_Boolean_Type
(Ent
) then
1247 -- For variable reference, get corresponding type
1250 Ent
:= Etype
(XE
.Ent
);
1251 Ctyp
:= Fold_Lower
(Xref_Entity_Letters
(Ekind
(Ent
)));
1253 -- If variable is private type, get full view type
1256 and then Present
(Full_View
(Etype
(XE
.Ent
)))
1258 Ent
:= Underlying_Type
(Etype
(XE
.Ent
));
1260 if Present
(Ent
) then
1261 Ctyp
:= Fold_Lower
(Xref_Entity_Letters
(Ekind
(Ent
)));
1265 -- Special handling for access parameter
1268 K
: constant Entity_Kind
:= Ekind
(Etype
(XE
.Ent
));
1271 if (K
= E_Anonymous_Access_Type
1273 K
= E_Anonymous_Access_Subprogram_Type
1275 E_Anonymous_Access_Protected_Subprogram_Type
)
1276 and then Is_Formal
(XE
.Ent
)
1280 -- Special handling for Boolean
1282 elsif Ctyp
= 'e' and then Is_Boolean_Type
(Ent
) then
1288 -- Special handling for abstract types and operations.
1290 if Is_Abstract
(XE
.Ent
) then
1293 Ctyp
:= 'x'; -- abstract procedure
1295 elsif Ctyp
= 'V' then
1296 Ctyp
:= 'y'; -- abstract function
1298 elsif Ctyp
= 'R' then
1299 Ctyp
:= 'H'; -- abstract type
1303 -- Only output reference if interesting type of entity,
1304 -- and suppress self references, except for bodies that
1305 -- act as specs. Also suppress definitions of body formals
1306 -- (we only treat these as references, and the references
1307 -- were separately recorded).
1310 or else (XE
.Loc
= XE
.Def
1313 or else not Is_Subprogram
(XE
.Ent
)))
1314 or else (Is_Formal
(XE
.Ent
)
1315 and then Present
(Spec_Entity
(XE
.Ent
)))
1320 -- Start new Xref section if new xref unit
1322 if XE
.Eun
/= Curxu
then
1323 if Write_Info_Col
> 1 then
1328 Cursrc
:= Source_Text
(Source_Index
(Curxu
));
1330 Write_Info_Initiate
('X');
1331 Write_Info_Char
(' ');
1332 Write_Info_Nat
(Dependency_Num
(XE
.Eun
));
1333 Write_Info_Char
(' ');
1334 Write_Info_Name
(Reference_Name
(Source_Index
(XE
.Eun
)));
1337 -- Start new Entity line if new entity. Note that we
1338 -- consider two entities the same if they have the same
1339 -- name and source location. This causes entities in
1340 -- instantiations to be treated as though they referred
1347 (Name_Change
(XE
.Ent
) or else XE
.Def
/= Curdef
))
1352 Get_Unqualified_Name_String
(Chars
(XE
.Ent
));
1354 Curnam
(1 .. Curlen
) := Name_Buffer
(1 .. Curlen
);
1356 if Write_Info_Col
> 1 then
1360 -- Write column number information
1362 Write_Info_Nat
(Int
(Get_Logical_Line_Number
(XE
.Def
)));
1363 Write_Info_Char
(Ctyp
);
1364 Write_Info_Nat
(Int
(Get_Column_Number
(XE
.Def
)));
1366 -- Write level information
1368 Write_Level_Info
: declare
1369 function Is_Visible_Generic_Entity
1370 (E
: Entity_Id
) return Boolean;
1371 -- Check whether E is declared in the visible part
1372 -- of a generic package. For source navigation
1373 -- purposes, treat this as a visible entity.
1375 function Is_Private_Record_Component
1376 (E
: Entity_Id
) return Boolean;
1377 -- Check whether E is a non-inherited component of a
1378 -- private extension. Even if the enclosing record is
1379 -- public, we want to treat the component as private
1380 -- for navigation purposes.
1382 ---------------------------------
1383 -- Is_Private_Record_Component --
1384 ---------------------------------
1386 function Is_Private_Record_Component
1387 (E
: Entity_Id
) return Boolean
1389 S
: constant Entity_Id
:= Scope
(E
);
1392 Ekind
(E
) = E_Component
1393 and then Nkind
(Declaration_Node
(S
)) =
1394 N_Private_Extension_Declaration
1395 and then Original_Record_Component
(E
) = E
;
1396 end Is_Private_Record_Component
;
1398 -------------------------------
1399 -- Is_Visible_Generic_Entity --
1400 -------------------------------
1402 function Is_Visible_Generic_Entity
1403 (E
: Entity_Id
) return Boolean
1408 if Ekind
(Scope
(E
)) /= E_Generic_Package
then
1413 while Present
(Par
) loop
1415 Nkind
(Par
) = N_Generic_Package_Declaration
1417 -- Entity is a generic formal
1422 Nkind
(Parent
(Par
)) = N_Package_Specification
1425 Is_List_Member
(Par
)
1426 and then List_Containing
(Par
) =
1427 Visible_Declarations
(Parent
(Par
));
1429 Par
:= Parent
(Par
);
1434 end Is_Visible_Generic_Entity
;
1436 -- Start of processing for Write_Level_Info
1439 if Is_Hidden
(Curent
)
1440 or else Is_Private_Record_Component
(Curent
)
1442 Write_Info_Char
(' ');
1446 or else Is_Visible_Generic_Entity
(Curent
)
1448 Write_Info_Char
('*');
1451 Write_Info_Char
(' ');
1453 end Write_Level_Info
;
1455 -- Output entity name. We use the occurrence from the
1456 -- actual source program at the definition point
1458 P
:= Original_Location
(Sloc
(XE
.Ent
));
1460 -- Entity is character literal
1462 if Cursrc
(P
) = ''' then
1463 Write_Info_Char
(Cursrc
(P
));
1464 Write_Info_Char
(Cursrc
(P
+ 1));
1465 Write_Info_Char
(Cursrc
(P
+ 2));
1467 -- Entity is operator symbol
1469 elsif Cursrc
(P
) = '"' or else Cursrc
(P
) = '%' then
1470 Write_Info_Char
(Cursrc
(P
));
1475 Write_Info_Char
(Cursrc
(P2
));
1476 exit when Cursrc
(P2
) = Cursrc
(P
);
1479 -- Entity is identifier
1483 if Is_Start_Of_Wide_Char
(Cursrc
, P
) then
1484 Scan_Wide
(Cursrc
, P
, WC
, Err
);
1485 elsif not Identifier_Char
(Cursrc
(P
)) then
1493 Original_Location
(Sloc
(XE
.Ent
)) .. P
- 1
1495 Write_Info_Char
(Cursrc
(J
));
1499 -- See if we have a renaming reference
1501 if Is_Object
(XE
.Ent
)
1502 and then Present
(Renamed_Object
(XE
.Ent
))
1504 Rref
:= Renamed_Object
(XE
.Ent
);
1506 elsif Is_Overloadable
(XE
.Ent
)
1507 and then Nkind
(Parent
(Declaration_Node
(XE
.Ent
))) =
1508 N_Subprogram_Renaming_Declaration
1510 Rref
:= Name
(Parent
(Declaration_Node
(XE
.Ent
)));
1512 elsif Ekind
(XE
.Ent
) = E_Package
1513 and then Nkind
(Declaration_Node
(XE
.Ent
)) =
1514 N_Package_Renaming_Declaration
1516 Rref
:= Name
(Declaration_Node
(XE
.Ent
));
1522 if Present
(Rref
) then
1523 if Nkind
(Rref
) = N_Expanded_Name
then
1524 Rref
:= Selector_Name
(Rref
);
1527 if Nkind
(Rref
) /= N_Identifier
then
1532 -- Write out renaming reference if we have one
1534 if Present
(Rref
) then
1535 Write_Info_Char
('=');
1537 (Int
(Get_Logical_Line_Number
(Sloc
(Rref
))));
1538 Write_Info_Char
(':');
1540 (Int
(Get_Column_Number
(Sloc
(Rref
))));
1543 -- Indicate that the entity is in the unit
1544 -- of the current xref xection.
1548 -- See if we have a type reference and if so output
1550 Get_Type_Reference
(XE
.Ent
, Tref
, Left
, Right
);
1552 if Present
(Tref
) then
1554 -- Case of standard entity, output name
1556 if Sloc
(Tref
) = Standard_Location
then
1557 Write_Info_Char
(Left
);
1558 Write_Info_Name
(Chars
(Tref
));
1559 Write_Info_Char
(Right
);
1561 -- Case of source entity, output location
1564 Write_Info_Char
(Left
);
1565 Trunit
:= Get_Source_Unit
(Sloc
(Tref
));
1567 if Trunit
/= Curxu
then
1568 Write_Info_Nat
(Dependency_Num
(Trunit
));
1569 Write_Info_Char
('|');
1573 (Int
(Get_Logical_Line_Number
(Sloc
(Tref
))));
1576 Ent
: Entity_Id
:= Tref
;
1577 Kind
: constant Entity_Kind
:= Ekind
(Ent
);
1578 Ctyp
: Character := Xref_Entity_Letters
(Kind
);
1582 and then Present
(Full_View
(Ent
))
1584 Ent
:= Underlying_Type
(Ent
);
1586 if Present
(Ent
) then
1587 Ctyp
:= Xref_Entity_Letters
(Ekind
(Ent
));
1591 Write_Info_Char
(Ctyp
);
1595 (Int
(Get_Column_Number
(Sloc
(Tref
))));
1597 -- If the type comes from an instantiation,
1598 -- add the corresponding info.
1600 Output_Instantiation_Refs
(Sloc
(Tref
));
1601 Write_Info_Char
(Right
);
1605 -- End of processing for entity output
1607 Crloc
:= No_Location
;
1610 -- Output the reference
1612 if XE
.Loc
/= No_Location
1613 and then XE
.Loc
/= Crloc
1617 -- Start continuation if line full, else blank
1619 if Write_Info_Col
> 72 then
1621 Write_Info_Initiate
('.');
1624 Write_Info_Char
(' ');
1626 -- Output file number if changed
1628 if XE
.Lun
/= Curru
then
1630 Write_Info_Nat
(Dependency_Num
(Curru
));
1631 Write_Info_Char
('|');
1634 Write_Info_Nat
(Int
(Get_Logical_Line_Number
(XE
.Loc
)));
1635 Write_Info_Char
(XE
.Typ
);
1637 if Is_Overloadable
(XE
.Ent
)
1638 and then Is_Imported
(XE
.Ent
)
1639 and then XE
.Typ
= 'b'
1641 Output_Import_Export_Info
(XE
.Ent
);
1644 Write_Info_Nat
(Int
(Get_Column_Number
(XE
.Loc
)));
1646 Output_Instantiation_Refs
(Sloc
(XE
.Ent
));
1657 end Output_References
;