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 Sem_Warn
; use Sem_Warn
;
41 with Sinfo
; use Sinfo
;
42 with Sinput
; use Sinput
;
43 with Snames
; use Snames
;
44 with Stringt
; use Stringt
;
45 with Stand
; use Stand
;
46 with Table
; use Table
;
47 with Widechar
; use Widechar
;
49 with GNAT
.Heap_Sort_A
;
51 package body Lib
.Xref
is
57 -- The Xref table is used to record references. The Loc field is set
58 -- to No_Location for a definition entry.
60 subtype Xref_Entry_Number
is Int
;
62 type Xref_Entry
is record
64 -- Entity referenced (E parameter to Generate_Reference)
67 -- Original source location for entity being referenced. Note that
68 -- these values are used only during the output process, they are
69 -- not set when the entries are originally built. This is because
70 -- private entities can be swapped when the initial call is made.
73 -- Location of reference (Original_Location (Sloc field of N parameter
74 -- to Generate_Reference). Set to No_Location for the case of a
75 -- defining occurrence.
78 -- Reference type (Typ param to Generate_Reference)
80 Eun
: Unit_Number_Type
;
81 -- Unit number corresponding to Ent
83 Lun
: Unit_Number_Type
;
84 -- Unit number corresponding to Loc. Value is undefined and not
85 -- referenced if Loc is set to No_Location.
89 package Xrefs
is new Table
.Table
(
90 Table_Component_Type
=> Xref_Entry
,
91 Table_Index_Type
=> Xref_Entry_Number
,
93 Table_Initial
=> Alloc
.Xrefs_Initial
,
94 Table_Increment
=> Alloc
.Xrefs_Increment
,
95 Table_Name
=> "Xrefs");
97 -------------------------
98 -- Generate_Definition --
99 -------------------------
101 procedure Generate_Definition
(E
: Entity_Id
) is
106 pragma Assert
(Nkind
(E
) in N_Entity
);
108 -- Note that we do not test Xref_Entity_Letters here. It is too
109 -- early to do so, since we are often called before the entity
110 -- is fully constructed, so that the Ekind is still E_Void.
114 -- Definition must come from source
116 -- We make an exception for subprogram child units that have no
117 -- spec. For these we generate a subprogram declaration for library
118 -- use, and the corresponding entity does not come from source.
119 -- Nevertheless, all references will be attached to it and we have
120 -- to treat is as coming from user code.
122 and then (Comes_From_Source
(E
) or else Is_Child_Unit
(E
))
124 -- And must have a reasonable source location that is not
125 -- within an instance (all entities in instances are ignored)
127 and then Sloc
(E
) > No_Location
128 and then Instantiation_Location
(Sloc
(E
)) = No_Location
130 -- And must be a non-internal name from the main source unit
132 and then In_Extended_Main_Source_Unit
(E
)
133 and then not Is_Internal_Name
(Chars
(E
))
135 Xrefs
.Increment_Last
;
137 Loc
:= Original_Location
(Sloc
(E
));
139 Xrefs
.Table
(Indx
).Ent
:= E
;
140 Xrefs
.Table
(Indx
).Loc
:= No_Location
;
141 Xrefs
.Table
(Indx
).Eun
:= Get_Source_Unit
(Loc
);
142 Xrefs
.Table
(Indx
).Lun
:= No_Unit
;
143 Set_Has_Xref_Entry
(E
);
145 if In_Inlined_Body
then
149 end Generate_Definition
;
151 ---------------------------------
152 -- Generate_Operator_Reference --
153 ---------------------------------
155 procedure Generate_Operator_Reference
160 if not In_Extended_Main_Source_Unit
(N
) then
164 -- If the operator is not a Standard operator, then we generate
165 -- a real reference to the user defined operator.
167 if Sloc
(Entity
(N
)) /= Standard_Location
then
168 Generate_Reference
(Entity
(N
), N
);
170 -- A reference to an implicit inequality operator is a also a
171 -- reference to the user-defined equality.
173 if Nkind
(N
) = N_Op_Ne
174 and then not Comes_From_Source
(Entity
(N
))
175 and then Present
(Corresponding_Equality
(Entity
(N
)))
177 Generate_Reference
(Corresponding_Equality
(Entity
(N
)), N
);
180 -- For the case of Standard operators, we mark the result type
181 -- as referenced. This ensures that in the case where we are
182 -- using a derived operator, we mark an entity of the unit that
183 -- implicitly defines this operator as used. Otherwise we may
184 -- think that no entity of the unit is used. The actual entity
185 -- marked as referenced is the first subtype, which is the user
186 -- defined entity that is relevant.
188 -- Note: we only do this for operators that come from source.
189 -- The generated code sometimes reaches for entities that do
190 -- not need to be explicitly visible (for example, when we
191 -- expand the code for comparing two record types, the fields
192 -- of the record may not be visible).
194 elsif Comes_From_Source
(N
) then
195 Set_Referenced
(First_Subtype
(T
));
197 end Generate_Operator_Reference
;
199 ------------------------
200 -- Generate_Reference --
201 ------------------------
203 procedure Generate_Reference
206 Typ
: Character := 'r';
207 Set_Ref
: Boolean := True;
208 Force
: Boolean := False)
216 function Is_On_LHS
(Node
: Node_Id
) return Boolean;
217 -- Used to check if a node is on the left hand side of an assignment.
218 -- The following cases are handled:
220 -- Variable Node is a direct descendant of an assignment statement.
222 -- Prefix Of an indexed or selected component that is present in a
223 -- subtree rooted by an assignment statement. There is no
224 -- restriction of nesting of components, thus cases such as
225 -- A.B(C).D are handled properly.
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 case of a
244 -- variable being a direct descendant of an assignment statement,
245 -- 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 package ASCII. GNAT treats this
274 -- element of annex J specially since in practice, programs make a lot
275 -- of use of this feature, so we don't include it in the set of features
276 -- diagnosed when Warn_On_Obsolescent_Features mode is set. However we
277 -- are required to note it as a violation of the RM defined restriction.
279 if E
= Standard_ASCII
then
280 Check_Restriction
(No_Obsolescent_Features
, N
);
283 -- Check for reference to entity marked with Is_Obsolescent
285 -- Note that we always allow obsolescent references in the compiler
286 -- itself and the run time, since we assume that we know what we are
287 -- doing in such cases. For example the calls in Ada.Characters.Handling
288 -- to its own obsolescent subprograms are just fine.
290 -- In any case we do not generate warnings within the extended source
291 -- unit of the entity in question, since we assume the source unit
292 -- itself knows what is going on (and for sure we do not want silly
293 -- warnings, e.g. on the end line of an obsolescent procedure body).
295 if Is_Obsolescent
(E
)
296 and then not GNAT_Mode
297 and then not In_Extended_Main_Source_Unit
(E
)
299 Check_Restriction
(No_Obsolescent_Features
, N
);
301 if Warn_On_Obsolescent_Feature
then
302 Output_Obsolescent_Entity_Warnings
(N
, E
);
306 -- Warn if reference to Ada 2005 entity not in Ada 2005 mode. We only
307 -- detect real explicit references (modifications and references).
309 if Is_Ada_2005_Only
(E
)
310 and then Ada_Version
< Ada_05
311 and then Warn_On_Ada_2005_Compatibility
312 and then (Typ
= 'm' or else Typ
= 'r')
314 Error_Msg_NE
("& is only defined in Ada 2005?", N
, E
);
317 -- Never collect references if not in main source unit. However, we omit
318 -- this test if Typ is 'e' or 'k', since these entries are structural,
319 -- and it is useful to have them in units that reference packages as
320 -- well as units that define packages. We also omit the test for the
321 -- case of 'p' since we want to include inherited primitive operations
322 -- from other packages.
324 -- We also omit this test is this is a body reference for a subprogram
325 -- instantiation. In this case the reference is to the generic body,
326 -- which clearly need not be in the main unit containing the instance.
327 -- For the same reason we accept an implicit reference generated for
328 -- a default in an instance.
330 if not In_Extended_Main_Source_Unit
(N
) then
335 or else (Typ
= 'b' and then Is_Generic_Instance
(E
))
343 -- For reference type p, the entity must be in main source unit
345 if Typ
= 'p' and then not In_Extended_Main_Source_Unit
(E
) then
349 -- Unless the reference is forced, we ignore references where the
350 -- reference itself does not come from Source.
352 if not Force
and then not Comes_From_Source
(N
) then
356 -- Deal with setting entity as referenced, unless suppressed. Note that
357 -- we still do Set_Referenced on entities that do not come from source.
358 -- This situation arises when we have a source reference to a derived
359 -- operation, where the derived operation itself does not come from
360 -- source, but we still want to mark it as referenced, since we really
361 -- are referencing an entity in the corresponding package (this avoids
362 -- wrong complaints that the package contains no referenced entities).
366 -- For a variable that appears on the left side of an assignment
367 -- statement, we set the Referenced_As_LHS flag since this is indeed
368 -- a left hand side. We also set the Referenced_As_LHS flag of a
369 -- prefix of selected or indexed component.
371 if Ekind
(E
) = E_Variable
372 and then Is_On_LHS
(N
)
374 Set_Referenced_As_LHS
(E
);
376 -- Check for a reference in a pragma that should not count as a
377 -- making the variable referenced for warning purposes.
379 elsif Is_Non_Significant_Pragma_Reference
(N
) then
382 -- A reference in an attribute definition clause does not count as a
383 -- reference except for the case of Address. The reason that 'Address
384 -- is an exception is that it creates an alias through which the
385 -- variable may be referenced.
387 elsif Nkind
(Parent
(N
)) = N_Attribute_Definition_Clause
388 and then Chars
(Parent
(N
)) /= Name_Address
389 and then N
= Name
(Parent
(N
))
393 -- Constant completion does not count as a reference
396 and then Ekind
(E
) = E_Constant
400 -- Record representation clause does not count as a reference
402 elsif Nkind
(N
) = N_Identifier
403 and then Nkind
(Parent
(N
)) = N_Record_Representation_Clause
407 -- Discriminants do not need to produce a reference to record type
410 and then Nkind
(Parent
(N
)) = N_Discriminant_Specification
414 -- Any other occurrence counts as referencing the entity
419 if Ekind
(E
) = E_Variable
then
420 Set_Last_Assignment
(E
, Empty
);
424 -- Check for pragma Unreferenced given and reference is within
425 -- this source unit (occasion for possible warning to be issued)
427 if Has_Pragma_Unreferenced
(E
)
428 and then In_Same_Extended_Unit
(E
, N
)
430 -- A reference as a named parameter in a call does not count
431 -- as a violation of pragma Unreferenced for this purpose.
433 if Nkind
(N
) = N_Identifier
434 and then Nkind
(Parent
(N
)) = N_Parameter_Association
435 and then Selector_Name
(Parent
(N
)) = N
439 -- Neither does a reference to a variable on the left side
442 elsif Is_On_LHS
(N
) then
445 -- For entry formals, we want to place the warning message on the
446 -- corresponding entity in the accept statement. The current scope
447 -- is the body of the accept, so we find the formal whose name
448 -- matches that of the entry formal (there is no link between the
449 -- two entities, and the one in the accept statement is only used
450 -- for conformance checking).
452 elsif Ekind
(Scope
(E
)) = E_Entry
then
457 BE
:= First_Entity
(Current_Scope
);
458 while Present
(BE
) loop
459 if Chars
(BE
) = Chars
(E
) then
461 ("?pragma Unreferenced given for&", N
, BE
);
469 -- Here we issue the warning, since this is a real reference
472 Error_Msg_NE
("?pragma Unreferenced given for&", N
, E
);
476 -- If this is a subprogram instance, mark as well the internal
477 -- subprogram in the wrapper package, which may be a visible
480 if Is_Overloadable
(E
)
481 and then Is_Generic_Instance
(E
)
482 and then Present
(Alias
(E
))
484 Set_Referenced
(Alias
(E
));
488 -- Generate reference if all conditions are met:
491 -- Cross referencing must be active
495 -- The entity must be one for which we collect references
497 and then Xref_Entity_Letters
(Ekind
(E
)) /= ' '
499 -- Both Sloc values must be set to something sensible
501 and then Sloc
(E
) > No_Location
502 and then Sloc
(N
) > No_Location
504 -- We ignore references from within an instance
506 and then Instantiation_Location
(Sloc
(N
)) = No_Location
508 -- Ignore dummy references
512 if Nkind
(N
) = N_Identifier
514 Nkind
(N
) = N_Defining_Identifier
518 Nkind
(N
) = N_Defining_Operator_Symbol
520 Nkind
(N
) = N_Operator_Symbol
522 (Nkind
(N
) = N_Character_Literal
523 and then Sloc
(Entity
(N
)) /= Standard_Location
)
525 Nkind
(N
) = N_Defining_Character_Literal
529 elsif Nkind
(N
) = N_Expanded_Name
531 Nkind
(N
) = N_Selected_Component
533 Nod
:= Selector_Name
(N
);
539 -- Normal case of source entity comes from source
541 if Comes_From_Source
(E
) then
544 -- Entity does not come from source, but is a derived subprogram
545 -- and the derived subprogram comes from source (after one or more
546 -- derivations) in which case the reference is to parent subprogram.
548 elsif Is_Overloadable
(E
)
549 and then Present
(Alias
(E
))
552 while not Comes_From_Source
(Ent
) loop
553 if No
(Alias
(Ent
)) then
560 -- The internally created defining entity for a child subprogram
561 -- that has no previous spec has valid references.
563 elsif Is_Overloadable
(E
)
564 and then Is_Child_Unit
(E
)
568 -- Record components of discriminated subtypes or derived types
569 -- must be treated as references to the original component.
571 elsif Ekind
(E
) = E_Component
572 and then Comes_From_Source
(Original_Record_Component
(E
))
574 Ent
:= Original_Record_Component
(E
);
576 -- Ignore reference to any other entity that is not from source
582 -- Record reference to entity
584 Ref
:= Original_Location
(Sloc
(Nod
));
585 Def
:= Original_Location
(Sloc
(Ent
));
587 Xrefs
.Increment_Last
;
590 Xrefs
.Table
(Indx
).Loc
:= Ref
;
592 -- Overriding operations are marked with 'P'
595 and then Is_Subprogram
(N
)
596 and then Is_Overriding_Operation
(N
)
598 Xrefs
.Table
(Indx
).Typ
:= 'P';
600 Xrefs
.Table
(Indx
).Typ
:= Typ
;
603 Xrefs
.Table
(Indx
).Eun
:= Get_Source_Unit
(Def
);
604 Xrefs
.Table
(Indx
).Lun
:= Get_Source_Unit
(Ref
);
605 Xrefs
.Table
(Indx
).Ent
:= Ent
;
606 Set_Has_Xref_Entry
(Ent
);
608 end Generate_Reference
;
610 -----------------------------------
611 -- Generate_Reference_To_Formals --
612 -----------------------------------
614 procedure Generate_Reference_To_Formals
(E
: Entity_Id
) is
618 if Is_Generic_Subprogram
(E
) then
619 Formal
:= First_Entity
(E
);
621 while Present
(Formal
)
622 and then not Is_Formal
(Formal
)
624 Next_Entity
(Formal
);
628 Formal
:= First_Formal
(E
);
631 while Present
(Formal
) loop
632 if Ekind
(Formal
) = E_In_Parameter
then
634 if Nkind
(Parameter_Type
(Parent
(Formal
)))
635 = N_Access_Definition
637 Generate_Reference
(E
, Formal
, '^', False);
639 Generate_Reference
(E
, Formal
, '>', False);
642 elsif Ekind
(Formal
) = E_In_Out_Parameter
then
643 Generate_Reference
(E
, Formal
, '=', False);
646 Generate_Reference
(E
, Formal
, '<', False);
649 Next_Formal
(Formal
);
651 end Generate_Reference_To_Formals
;
653 -------------------------------------------
654 -- Generate_Reference_To_Generic_Formals --
655 -------------------------------------------
657 procedure Generate_Reference_To_Generic_Formals
(E
: Entity_Id
) is
661 Formal
:= First_Entity
(E
);
662 while Present
(Formal
) loop
663 if Comes_From_Source
(Formal
) then
664 Generate_Reference
(E
, Formal
, 'z', False);
667 Next_Entity
(Formal
);
669 end Generate_Reference_To_Generic_Formals
;
675 procedure Initialize
is
680 -----------------------
681 -- Output_References --
682 -----------------------
684 procedure Output_References
is
686 procedure Get_Type_Reference
688 Tref
: out Entity_Id
;
689 Left
: out Character;
690 Right
: out Character);
691 -- Given an entity id Ent, determines whether a type reference is
692 -- required. If so, Tref is set to the entity for the type reference
693 -- and Left and Right are set to the left/right brackets to be
694 -- output for the reference. If no type reference is required, then
695 -- Tref is set to Empty, and Left/Right are set to space.
697 procedure Output_Import_Export_Info
(Ent
: Entity_Id
);
698 -- Ouput language and external name information for an interfaced
699 -- entity, using the format <language, external_name>,
701 ------------------------
702 -- Get_Type_Reference --
703 ------------------------
705 procedure Get_Type_Reference
707 Tref
: out Entity_Id
;
708 Left
: out Character;
709 Right
: out Character)
714 -- See if we have a type reference
723 -- Processing for types
725 if Is_Type
(Tref
) then
729 if Base_Type
(Tref
) = Tref
then
731 -- If derived, then get first subtype
733 if Tref
/= Etype
(Tref
) then
734 Tref
:= First_Subtype
(Etype
(Tref
));
736 -- Set brackets for derived type, but don't
737 -- override pointer case since the fact that
738 -- something is a pointer is more important
745 -- If non-derived ptr, get directly designated type.
746 -- If the type has a full view, all references are
747 -- on the partial view, that is seen first.
749 elsif Is_Access_Type
(Tref
) then
750 Tref
:= Directly_Designated_Type
(Tref
);
754 elsif Is_Private_Type
(Tref
)
755 and then Present
(Full_View
(Tref
))
757 if Is_Access_Type
(Full_View
(Tref
)) then
758 Tref
:= Directly_Designated_Type
(Full_View
(Tref
));
762 -- If the full view is an array type, we also retrieve
763 -- the corresponding component type, because the ali
764 -- entry already indicates that this is an array.
766 elsif Is_Array_Type
(Full_View
(Tref
)) then
767 Tref
:= Component_Type
(Full_View
(Tref
));
772 -- If non-derived array, get component type. Skip component
773 -- type for case of String or Wide_String, saves worthwhile
776 elsif Is_Array_Type
(Tref
)
777 and then Tref
/= Standard_String
778 and then Tref
/= Standard_Wide_String
780 Tref
:= Component_Type
(Tref
);
784 -- For other non-derived base types, nothing
790 -- For a subtype, go to ancestor subtype
793 Tref
:= Ancestor_Subtype
(Tref
);
795 -- If no ancestor subtype, go to base type
798 Tref
:= Base_Type
(Sav
);
802 -- For objects, functions, enum literals,
803 -- just get type from Etype field.
805 elsif Is_Object
(Tref
)
806 or else Ekind
(Tref
) = E_Enumeration_Literal
807 or else Ekind
(Tref
) = E_Function
808 or else Ekind
(Tref
) = E_Operator
810 Tref
:= Etype
(Tref
);
812 -- For anything else, exit
818 -- Exit if no type reference, or we are stuck in
819 -- some loop trying to find the type reference, or
820 -- if the type is standard void type (the latter is
821 -- an implementation artifact that should not show
822 -- up in the generated cross-references).
826 or else Tref
= Standard_Void_Type
;
828 -- If we have a usable type reference, return, otherwise
829 -- keep looking for something useful (we are looking for
830 -- something that either comes from source or standard)
832 if Sloc
(Tref
) = Standard_Location
833 or else Comes_From_Source
(Tref
)
835 -- If the reference is a subtype created for a generic
836 -- actual, go to actual directly, the inner subtype is
839 if Nkind
(Parent
(Tref
)) = N_Subtype_Declaration
840 and then not Comes_From_Source
(Parent
(Tref
))
842 (Is_Wrapper_Package
(Scope
(Tref
))
843 or else Is_Generic_Instance
(Scope
(Tref
)))
845 Tref
:= First_Subtype
(Base_Type
(Tref
));
852 -- If we fall through the loop, no type reference
857 end Get_Type_Reference
;
859 -------------------------------
860 -- Output_Import_Export_Info --
861 -------------------------------
863 procedure Output_Import_Export_Info
(Ent
: Entity_Id
) is
864 Language_Name
: Name_Id
;
865 Conv
: constant Convention_Id
:= Convention
(Ent
);
868 -- Generate language name from convention
870 if Conv
= Convention_C
then
871 Language_Name
:= Name_C
;
873 elsif Conv
= Convention_CPP
then
874 Language_Name
:= Name_CPP
;
876 elsif Conv
= Convention_Ada
then
877 Language_Name
:= Name_Ada
;
880 -- For the moment we ignore all other cases ???
885 Write_Info_Char
('<');
886 Get_Unqualified_Name_String
(Language_Name
);
888 for J
in 1 .. Name_Len
loop
889 Write_Info_Char
(Name_Buffer
(J
));
892 if Present
(Interface_Name
(Ent
)) then
893 Write_Info_Char
(',');
894 String_To_Name_Buffer
(Strval
(Interface_Name
(Ent
)));
896 for J
in 1 .. Name_Len
loop
897 Write_Info_Char
(Name_Buffer
(J
));
901 Write_Info_Char
('>');
902 end Output_Import_Export_Info
;
904 -- Start of processing for Output_References
907 if not Opt
.Xref_Active
then
911 -- Before we go ahead and output the references we have a problem
912 -- that needs dealing with. So far we have captured things that are
913 -- definitely referenced by the main unit, or defined in the main
914 -- unit. That's because we don't want to clutter up the ali file
915 -- for this unit with definition lines for entities in other units
916 -- that are not referenced.
918 -- But there is a glitch. We may reference an entity in another unit,
919 -- and it may have a type reference to an entity that is not directly
920 -- referenced in the main unit, which may mean that there is no xref
921 -- entry for this entity yet in the list of references.
923 -- If we don't do something about this, we will end with an orphan
924 -- type reference, i.e. it will point to an entity that does not
925 -- appear within the generated references in the ali file. That is
926 -- not good for tools using the xref information.
928 -- To fix this, we go through the references adding definition
929 -- entries for any unreferenced entities that can be referenced
930 -- in a type reference. There is a recursion problem here, and
931 -- that is dealt with by making sure that this traversal also
932 -- traverses any entries that get added by the traversal.
943 -- Note that this is not a for loop for a very good reason. The
944 -- processing of items in the table can add new items to the
945 -- table, and they must be processed as well
948 while J
<= Xrefs
.Last
loop
949 Ent
:= Xrefs
.Table
(J
).Ent
;
950 Get_Type_Reference
(Ent
, Tref
, L
, R
);
953 and then not Has_Xref_Entry
(Tref
)
954 and then Sloc
(Tref
) > No_Location
956 Xrefs
.Increment_Last
;
958 Loc
:= Original_Location
(Sloc
(Tref
));
959 Xrefs
.Table
(Indx
).Ent
:= Tref
;
960 Xrefs
.Table
(Indx
).Loc
:= No_Location
;
961 Xrefs
.Table
(Indx
).Eun
:= Get_Source_Unit
(Loc
);
962 Xrefs
.Table
(Indx
).Lun
:= No_Unit
;
963 Set_Has_Xref_Entry
(Tref
);
966 -- Collect inherited primitive operations that may be
967 -- declared in another unit and have no visible reference
968 -- in the current one.
971 and then Is_Tagged_Type
(Ent
)
972 and then Is_Derived_Type
(Ent
)
973 and then Ent
= Base_Type
(Ent
)
974 and then In_Extended_Main_Source_Unit
(Ent
)
977 Op_List
: constant Elist_Id
:= Primitive_Operations
(Ent
);
981 function Parent_Op
(E
: Entity_Id
) return Entity_Id
;
982 -- Find original operation, which may be inherited
983 -- through several derivations.
985 function Parent_Op
(E
: Entity_Id
) return Entity_Id
is
986 Orig_Op
: constant Entity_Id
:= Alias
(E
);
990 elsif not Comes_From_Source
(E
)
991 and then not Has_Xref_Entry
(Orig_Op
)
992 and then Comes_From_Source
(Orig_Op
)
996 return Parent_Op
(Orig_Op
);
1001 Op
:= First_Elmt
(Op_List
);
1002 while Present
(Op
) loop
1003 Prim
:= Parent_Op
(Node
(Op
));
1005 if Present
(Prim
) then
1006 Xrefs
.Increment_Last
;
1008 Loc
:= Original_Location
(Sloc
(Prim
));
1009 Xrefs
.Table
(Indx
).Ent
:= Prim
;
1010 Xrefs
.Table
(Indx
).Loc
:= No_Location
;
1011 Xrefs
.Table
(Indx
).Eun
:=
1012 Get_Source_Unit
(Sloc
(Prim
));
1013 Xrefs
.Table
(Indx
).Lun
:= No_Unit
;
1014 Set_Has_Xref_Entry
(Prim
);
1026 -- Now we have all the references, including those for any embedded
1027 -- type references, so we can sort them, and output them.
1029 Output_Refs
: declare
1031 Nrefs
: Nat
:= Xrefs
.Last
;
1032 -- Number of references in table. This value may get reset
1033 -- (reduced) when we eliminate duplicate reference entries.
1035 Rnums
: array (0 .. Nrefs
) of Nat
;
1036 -- This array contains numbers of references in the Xrefs table.
1037 -- This list is sorted in output order. The extra 0'th entry is
1038 -- convenient for the call to sort. When we sort the table, we
1039 -- move the entries in Rnums around, but we do not move the
1040 -- original table entries.
1042 Curxu
: Unit_Number_Type
;
1043 -- Current xref unit
1045 Curru
: Unit_Number_Type
;
1046 -- Current reference unit for one entity
1048 Cursrc
: Source_Buffer_Ptr
;
1049 -- Current xref unit source text
1054 Curnam
: String (1 .. Name_Buffer
'Length);
1056 -- Simple name and length of current entity
1058 Curdef
: Source_Ptr
;
1059 -- Original source location for current entity
1062 -- Current reference location
1065 -- Entity type character
1071 -- Renaming reference
1073 Trunit
: Unit_Number_Type
;
1074 -- Unit number for type reference
1076 function Lt
(Op1
, Op2
: Natural) return Boolean;
1077 -- Comparison function for Sort call
1079 function Name_Change
(X
: Entity_Id
) return Boolean;
1080 -- Determines if entity X has a different simple name from Curent
1082 procedure Move
(From
: Natural; To
: Natural);
1083 -- Move procedure for Sort call
1089 function Lt
(Op1
, Op2
: Natural) return Boolean is
1090 T1
: Xref_Entry
renames Xrefs
.Table
(Rnums
(Nat
(Op1
)));
1091 T2
: Xref_Entry
renames Xrefs
.Table
(Rnums
(Nat
(Op2
)));
1094 -- First test. If entity is in different unit, sort by unit
1096 if T1
.Eun
/= T2
.Eun
then
1097 return Dependency_Num
(T1
.Eun
) < Dependency_Num
(T2
.Eun
);
1099 -- Second test, within same unit, sort by entity Sloc
1101 elsif T1
.Def
/= T2
.Def
then
1102 return T1
.Def
< T2
.Def
;
1104 -- Third test, sort definitions ahead of references
1106 elsif T1
.Loc
= No_Location
then
1109 elsif T2
.Loc
= No_Location
then
1112 -- Fourth test, for same entity, sort by reference location unit
1114 elsif T1
.Lun
/= T2
.Lun
then
1115 return Dependency_Num
(T1
.Lun
) < Dependency_Num
(T2
.Lun
);
1117 -- Fifth test order of location within referencing unit
1119 elsif T1
.Loc
/= T2
.Loc
then
1120 return T1
.Loc
< T2
.Loc
;
1122 -- Finally, for two locations at the same address, we prefer
1123 -- the one that does NOT have the type 'r' so that a modification
1124 -- or extension takes preference, when there are more than one
1125 -- reference at the same location.
1128 return T2
.Typ
= 'r';
1136 procedure Move
(From
: Natural; To
: Natural) is
1138 Rnums
(Nat
(To
)) := Rnums
(Nat
(From
));
1145 -- Why a string comparison here??? Why not compare Name_Id values???
1147 function Name_Change
(X
: Entity_Id
) return Boolean is
1149 Get_Unqualified_Name_String
(Chars
(X
));
1151 if Name_Len
/= Curlen
then
1155 return Name_Buffer
(1 .. Curlen
) /= Curnam
(1 .. Curlen
);
1159 -- Start of processing for Output_Refs
1162 -- Capture the definition Sloc values. We delay doing this till now,
1163 -- since at the time the reference or definition is made, private
1164 -- types may be swapped, and the Sloc value may be incorrect. We
1165 -- also set up the pointer vector for the sort.
1167 for J
in 1 .. Nrefs
loop
1169 Xrefs
.Table
(J
).Def
:=
1170 Original_Location
(Sloc
(Xrefs
.Table
(J
).Ent
));
1173 -- Sort the references
1175 GNAT
.Heap_Sort_A
.Sort
1177 Move
'Unrestricted_Access,
1178 Lt
'Unrestricted_Access);
1180 -- Eliminate duplicate entries
1183 NR
: constant Nat
:= Nrefs
;
1186 -- We need this test for NR because if we force ALI file
1187 -- generation in case of errors detected, it may be the case
1188 -- that Nrefs is 0, so we should not reset it here
1193 for J
in 2 .. NR
loop
1194 if Xrefs
.Table
(Rnums
(J
)) /=
1195 Xrefs
.Table
(Rnums
(Nrefs
))
1198 Rnums
(Nrefs
) := Rnums
(J
);
1204 -- Initialize loop through references
1208 Curdef
:= No_Location
;
1210 Crloc
:= No_Location
;
1212 -- Loop to output references
1214 for Refno
in 1 .. Nrefs
loop
1215 Output_One_Ref
: declare
1221 XE
: Xref_Entry
renames Xrefs
.Table
(Rnums
(Refno
));
1222 -- The current entry to be accessed
1225 -- Used to index into source buffer to get entity name
1229 -- Used for {} or <> or () for type reference
1231 procedure Output_Instantiation_Refs
(Loc
: Source_Ptr
);
1232 -- Recursive procedure to output instantiation references for
1233 -- the given source ptr in [file|line[...]] form. No output
1234 -- if the given location is not a generic template reference.
1236 procedure Output_Overridden_Op
(Old_E
: Entity_Id
);
1237 -- For a subprogram that is overriding, display information
1238 -- about the inherited operation that it overrides.
1240 -------------------------------
1241 -- Output_Instantiation_Refs --
1242 -------------------------------
1244 procedure Output_Instantiation_Refs
(Loc
: Source_Ptr
) is
1245 Iloc
: constant Source_Ptr
:= Instantiation_Location
(Loc
);
1246 Lun
: Unit_Number_Type
;
1247 Cu
: constant Unit_Number_Type
:= Curru
;
1250 -- Nothing to do if this is not an instantiation
1252 if Iloc
= No_Location
then
1256 -- Output instantiation reference
1258 Write_Info_Char
('[');
1259 Lun
:= Get_Source_Unit
(Iloc
);
1261 if Lun
/= Curru
then
1263 Write_Info_Nat
(Dependency_Num
(Curru
));
1264 Write_Info_Char
('|');
1267 Write_Info_Nat
(Int
(Get_Logical_Line_Number
(Iloc
)));
1269 -- Recursive call to get nested instantiations
1271 Output_Instantiation_Refs
(Iloc
);
1273 -- Output final ] after call to get proper nesting
1275 Write_Info_Char
(']');
1278 end Output_Instantiation_Refs
;
1280 --------------------------
1281 -- Output_Overridden_Op --
1282 --------------------------
1284 procedure Output_Overridden_Op
(Old_E
: Entity_Id
) is
1287 and then Sloc
(Old_E
) /= Standard_Location
1290 Loc
: constant Source_Ptr
:= Sloc
(Old_E
);
1291 Par_Unit
: constant Unit_Number_Type
:=
1292 Get_Source_Unit
(Loc
);
1294 Write_Info_Char
('<');
1296 if Par_Unit
/= Curxu
then
1297 Write_Info_Nat
(Dependency_Num
(Par_Unit
));
1298 Write_Info_Char
('|');
1301 Write_Info_Nat
(Int
(Get_Logical_Line_Number
(Loc
)));
1302 Write_Info_Char
('p');
1303 Write_Info_Nat
(Int
(Get_Column_Number
(Loc
)));
1304 Write_Info_Char
('>');
1307 end Output_Overridden_Op
;
1309 -- Start of processing for Output_One_Ref
1313 Ctyp
:= Xref_Entity_Letters
(Ekind
(Ent
));
1315 -- Skip reference if it is the only reference to an entity,
1316 -- and it is an end-line reference, and the entity is not in
1317 -- the current extended source. This prevents junk entries
1318 -- consisting only of packages with end lines, where no
1319 -- entity from the package is actually referenced.
1322 and then Ent
/= Curent
1323 and then (Refno
= Nrefs
or else
1324 Ent
/= Xrefs
.Table
(Rnums
(Refno
+ 1)).Ent
)
1326 not In_Extended_Main_Source_Unit
(Ent
)
1331 -- For private type, get full view type
1334 and then Present
(Full_View
(XE
.Ent
))
1336 Ent
:= Underlying_Type
(Ent
);
1338 if Present
(Ent
) then
1339 Ctyp
:= Xref_Entity_Letters
(Ekind
(Ent
));
1343 -- Special exception for Boolean
1345 if Ctyp
= 'E' and then Is_Boolean_Type
(Ent
) then
1349 -- For variable reference, get corresponding type
1352 Ent
:= Etype
(XE
.Ent
);
1353 Ctyp
:= Fold_Lower
(Xref_Entity_Letters
(Ekind
(Ent
)));
1355 -- If variable is private type, get full view type
1358 and then Present
(Full_View
(Etype
(XE
.Ent
)))
1360 Ent
:= Underlying_Type
(Etype
(XE
.Ent
));
1362 if Present
(Ent
) then
1363 Ctyp
:= Fold_Lower
(Xref_Entity_Letters
(Ekind
(Ent
)));
1366 elsif Is_Generic_Type
(Ent
) then
1368 -- If the type of the entity is a generic private type
1369 -- there is no usable full view, so retain the indication
1370 -- that this is an object.
1375 -- Special handling for access parameter
1378 K
: constant Entity_Kind
:= Ekind
(Etype
(XE
.Ent
));
1381 if (K
= E_Anonymous_Access_Type
1383 K
= E_Anonymous_Access_Subprogram_Type
1385 E_Anonymous_Access_Protected_Subprogram_Type
)
1386 and then Is_Formal
(XE
.Ent
)
1390 -- Special handling for Boolean
1392 elsif Ctyp
= 'e' and then Is_Boolean_Type
(Ent
) then
1398 -- Special handling for abstract types and operations
1400 if Is_Abstract
(XE
.Ent
) then
1402 Ctyp
:= 'x'; -- abstract procedure
1404 elsif Ctyp
= 'V' then
1405 Ctyp
:= 'y'; -- abstract function
1407 elsif Ctyp
= 'R' then
1408 Ctyp
:= 'H'; -- abstract type
1412 -- Only output reference if interesting type of entity, and
1413 -- suppress self references, except for bodies that act as
1414 -- specs. Also suppress definitions of body formals (we only
1415 -- treat these as references, and the references were
1416 -- separately recorded).
1419 or else (XE
.Loc
= XE
.Def
1422 or else not Is_Subprogram
(XE
.Ent
)))
1423 or else (Is_Formal
(XE
.Ent
)
1424 and then Present
(Spec_Entity
(XE
.Ent
)))
1429 -- Start new Xref section if new xref unit
1431 if XE
.Eun
/= Curxu
then
1432 if Write_Info_Col
> 1 then
1437 Cursrc
:= Source_Text
(Source_Index
(Curxu
));
1439 Write_Info_Initiate
('X');
1440 Write_Info_Char
(' ');
1441 Write_Info_Nat
(Dependency_Num
(XE
.Eun
));
1442 Write_Info_Char
(' ');
1443 Write_Info_Name
(Reference_Name
(Source_Index
(XE
.Eun
)));
1446 -- Start new Entity line if new entity. Note that we
1447 -- consider two entities the same if they have the same
1448 -- name and source location. This causes entities in
1449 -- instantiations to be treated as though they referred
1456 (Name_Change
(XE
.Ent
) or else XE
.Def
/= Curdef
))
1461 Get_Unqualified_Name_String
(Chars
(XE
.Ent
));
1463 Curnam
(1 .. Curlen
) := Name_Buffer
(1 .. Curlen
);
1465 if Write_Info_Col
> 1 then
1469 -- Write column number information
1471 Write_Info_Nat
(Int
(Get_Logical_Line_Number
(XE
.Def
)));
1472 Write_Info_Char
(Ctyp
);
1473 Write_Info_Nat
(Int
(Get_Column_Number
(XE
.Def
)));
1475 -- Write level information
1477 Write_Level_Info
: declare
1478 function Is_Visible_Generic_Entity
1479 (E
: Entity_Id
) return Boolean;
1480 -- Check whether E is declared in the visible part
1481 -- of a generic package. For source navigation
1482 -- purposes, treat this as a visible entity.
1484 function Is_Private_Record_Component
1485 (E
: Entity_Id
) return Boolean;
1486 -- Check whether E is a non-inherited component of a
1487 -- private extension. Even if the enclosing record is
1488 -- public, we want to treat the component as private
1489 -- for navigation purposes.
1491 ---------------------------------
1492 -- Is_Private_Record_Component --
1493 ---------------------------------
1495 function Is_Private_Record_Component
1496 (E
: Entity_Id
) return Boolean
1498 S
: constant Entity_Id
:= Scope
(E
);
1501 Ekind
(E
) = E_Component
1502 and then Nkind
(Declaration_Node
(S
)) =
1503 N_Private_Extension_Declaration
1504 and then Original_Record_Component
(E
) = E
;
1505 end Is_Private_Record_Component
;
1507 -------------------------------
1508 -- Is_Visible_Generic_Entity --
1509 -------------------------------
1511 function Is_Visible_Generic_Entity
1512 (E
: Entity_Id
) return Boolean
1517 if Ekind
(Scope
(E
)) /= E_Generic_Package
then
1522 while Present
(Par
) loop
1524 Nkind
(Par
) = N_Generic_Package_Declaration
1526 -- Entity is a generic formal
1531 Nkind
(Parent
(Par
)) = N_Package_Specification
1534 Is_List_Member
(Par
)
1535 and then List_Containing
(Par
) =
1536 Visible_Declarations
(Parent
(Par
));
1538 Par
:= Parent
(Par
);
1543 end Is_Visible_Generic_Entity
;
1545 -- Start of processing for Write_Level_Info
1548 if Is_Hidden
(Curent
)
1549 or else Is_Private_Record_Component
(Curent
)
1551 Write_Info_Char
(' ');
1555 or else Is_Visible_Generic_Entity
(Curent
)
1557 Write_Info_Char
('*');
1560 Write_Info_Char
(' ');
1562 end Write_Level_Info
;
1564 -- Output entity name. We use the occurrence from the
1565 -- actual source program at the definition point
1567 P
:= Original_Location
(Sloc
(XE
.Ent
));
1569 -- Entity is character literal
1571 if Cursrc
(P
) = ''' then
1572 Write_Info_Char
(Cursrc
(P
));
1573 Write_Info_Char
(Cursrc
(P
+ 1));
1574 Write_Info_Char
(Cursrc
(P
+ 2));
1576 -- Entity is operator symbol
1578 elsif Cursrc
(P
) = '"' or else Cursrc
(P
) = '%' then
1579 Write_Info_Char
(Cursrc
(P
));
1584 Write_Info_Char
(Cursrc
(P2
));
1585 exit when Cursrc
(P2
) = Cursrc
(P
);
1588 -- Entity is identifier
1592 if Is_Start_Of_Wide_Char
(Cursrc
, P
) then
1593 Scan_Wide
(Cursrc
, P
, WC
, Err
);
1594 elsif not Identifier_Char
(Cursrc
(P
)) then
1601 -- Write out the identifier by copying the exact
1602 -- source characters used in its declaration. Note
1603 -- that this means wide characters will be in their
1604 -- original encoded form.
1607 Original_Location
(Sloc
(XE
.Ent
)) .. P
- 1
1609 Write_Info_Char
(Cursrc
(J
));
1613 -- See if we have a renaming reference
1615 if Is_Object
(XE
.Ent
)
1616 and then Present
(Renamed_Object
(XE
.Ent
))
1618 Rref
:= Renamed_Object
(XE
.Ent
);
1620 elsif Is_Overloadable
(XE
.Ent
)
1621 and then Nkind
(Parent
(Declaration_Node
(XE
.Ent
))) =
1622 N_Subprogram_Renaming_Declaration
1624 Rref
:= Name
(Parent
(Declaration_Node
(XE
.Ent
)));
1626 elsif Ekind
(XE
.Ent
) = E_Package
1627 and then Nkind
(Declaration_Node
(XE
.Ent
)) =
1628 N_Package_Renaming_Declaration
1630 Rref
:= Name
(Declaration_Node
(XE
.Ent
));
1636 if Present
(Rref
) then
1637 if Nkind
(Rref
) = N_Expanded_Name
then
1638 Rref
:= Selector_Name
(Rref
);
1641 if Nkind
(Rref
) = N_Identifier
1642 or else Nkind
(Rref
) = N_Operator_Symbol
1646 -- For renamed array components, use the array name
1647 -- for the renamed entity, which reflect the fact that
1648 -- in general the whole array is aliased.
1650 elsif Nkind
(Rref
) = N_Indexed_Component
then
1651 if Nkind
(Prefix
(Rref
)) = N_Identifier
then
1652 Rref
:= Prefix
(Rref
);
1653 elsif Nkind
(Prefix
(Rref
)) = N_Expanded_Name
then
1654 Rref
:= Selector_Name
(Prefix
(Rref
));
1664 -- Write out renaming reference if we have one
1666 if Present
(Rref
) then
1667 Write_Info_Char
('=');
1669 (Int
(Get_Logical_Line_Number
(Sloc
(Rref
))));
1670 Write_Info_Char
(':');
1672 (Int
(Get_Column_Number
(Sloc
(Rref
))));
1675 -- Indicate that the entity is in the unit of the current
1680 -- Write out information about generic parent, if entity
1683 if Is_Generic_Instance
(XE
.Ent
) then
1685 Gen_Par
: constant Entity_Id
:=
1688 (Unit_Declaration_Node
(XE
.Ent
)));
1689 Loc
: constant Source_Ptr
:= Sloc
(Gen_Par
);
1690 Gen_U
: constant Unit_Number_Type
:=
1691 Get_Source_Unit
(Loc
);
1694 Write_Info_Char
('[');
1695 if Curru
/= Gen_U
then
1696 Write_Info_Nat
(Dependency_Num
(Gen_U
));
1697 Write_Info_Char
('|');
1701 (Int
(Get_Logical_Line_Number
(Loc
)));
1702 Write_Info_Char
(']');
1706 -- See if we have a type reference and if so output
1708 Get_Type_Reference
(XE
.Ent
, Tref
, Left
, Right
);
1710 if Present
(Tref
) then
1712 -- Case of standard entity, output name
1714 if Sloc
(Tref
) = Standard_Location
then
1715 Write_Info_Char
(Left
);
1716 Write_Info_Name
(Chars
(Tref
));
1717 Write_Info_Char
(Right
);
1719 -- Case of source entity, output location
1722 Write_Info_Char
(Left
);
1723 Trunit
:= Get_Source_Unit
(Sloc
(Tref
));
1725 if Trunit
/= Curxu
then
1726 Write_Info_Nat
(Dependency_Num
(Trunit
));
1727 Write_Info_Char
('|');
1731 (Int
(Get_Logical_Line_Number
(Sloc
(Tref
))));
1734 Ent
: Entity_Id
:= Tref
;
1735 Kind
: constant Entity_Kind
:= Ekind
(Ent
);
1736 Ctyp
: Character := Xref_Entity_Letters
(Kind
);
1740 and then Present
(Full_View
(Ent
))
1742 Ent
:= Underlying_Type
(Ent
);
1744 if Present
(Ent
) then
1745 Ctyp
:= Xref_Entity_Letters
(Ekind
(Ent
));
1749 Write_Info_Char
(Ctyp
);
1753 (Int
(Get_Column_Number
(Sloc
(Tref
))));
1755 -- If the type comes from an instantiation,
1756 -- add the corresponding info.
1758 Output_Instantiation_Refs
(Sloc
(Tref
));
1759 Write_Info_Char
(Right
);
1763 -- If the entity is an overriding operation, write
1764 -- info on operation that was overridden.
1766 if Is_Subprogram
(XE
.Ent
)
1767 and then Is_Overriding_Operation
(XE
.Ent
)
1769 Output_Overridden_Op
(Overridden_Operation
(XE
.Ent
));
1772 -- End of processing for entity output
1774 Crloc
:= No_Location
;
1777 -- Output the reference
1779 if XE
.Loc
/= No_Location
1780 and then XE
.Loc
/= Crloc
1784 -- Start continuation if line full, else blank
1786 if Write_Info_Col
> 72 then
1788 Write_Info_Initiate
('.');
1791 Write_Info_Char
(' ');
1793 -- Output file number if changed
1795 if XE
.Lun
/= Curru
then
1797 Write_Info_Nat
(Dependency_Num
(Curru
));
1798 Write_Info_Char
('|');
1801 Write_Info_Nat
(Int
(Get_Logical_Line_Number
(XE
.Loc
)));
1802 Write_Info_Char
(XE
.Typ
);
1804 if Is_Overloadable
(XE
.Ent
)
1805 and then Is_Imported
(XE
.Ent
)
1806 and then XE
.Typ
= 'b'
1808 Output_Import_Export_Info
(XE
.Ent
);
1811 Write_Info_Nat
(Int
(Get_Column_Number
(XE
.Loc
)));
1813 Output_Instantiation_Refs
(Sloc
(XE
.Ent
));
1824 end Output_References
;