1 ------------------------------------------------------------------------------
3 -- GNAT COMPILER COMPONENTS --
9 -- Copyright (C) 1998-2009, 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 3, 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 COPYING3. If not, go to --
19 -- http://www.gnu.org/licenses for a complete copy of the license. --
21 -- GNAT was originally developed by the GNAT team at New York University. --
22 -- Extensive contributions were provided by Ada Core Technologies Inc. --
24 ------------------------------------------------------------------------------
26 with Atree
; use Atree
;
27 with Csets
; use Csets
;
28 with Elists
; use Elists
;
29 with Errout
; use Errout
;
30 with Lib
.Util
; use Lib
.Util
;
31 with Nlists
; use Nlists
;
33 with Restrict
; use Restrict
;
34 with Rident
; use Rident
;
36 with Sem_Aux
; use Sem_Aux
;
37 with Sem_Prag
; use Sem_Prag
;
38 with Sem_Util
; use Sem_Util
;
39 with Sem_Warn
; use Sem_Warn
;
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_G
;
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 these
67 -- values are used only during the output process, they are not set when
68 -- the entries are originally built. This is because private entities
69 -- 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 -- Local Subprograms --
98 ------------------------
100 procedure Generate_Prim_Op_References
(Typ
: Entity_Id
);
101 -- For a tagged type, generate implicit references to its primitive
102 -- operations, for source navigation. This is done right before emitting
103 -- cross-reference information rather than at the freeze point of the type
104 -- in order to handle late bodies that are primitive operations.
106 -------------------------
107 -- Generate_Definition --
108 -------------------------
110 procedure Generate_Definition
(E
: Entity_Id
) is
115 pragma Assert
(Nkind
(E
) in N_Entity
);
117 -- Note that we do not test Xref_Entity_Letters here. It is too early
118 -- to do so, since we are often called before the entity is fully
119 -- constructed, so that the Ekind is still E_Void.
123 -- Definition must come from source
125 -- We make an exception for subprogram child units that have no spec.
126 -- For these we generate a subprogram declaration for library use,
127 -- and the corresponding entity does not come from source.
128 -- Nevertheless, all references will be attached to it and we have
129 -- to treat is as coming from user code.
131 and then (Comes_From_Source
(E
) or else Is_Child_Unit
(E
))
133 -- And must have a reasonable source location that is not
134 -- within an instance (all entities in instances are ignored)
136 and then Sloc
(E
) > No_Location
137 and then Instantiation_Location
(Sloc
(E
)) = No_Location
139 -- And must be a non-internal name from the main source unit
141 and then In_Extended_Main_Source_Unit
(E
)
142 and then not Is_Internal_Name
(Chars
(E
))
144 Xrefs
.Increment_Last
;
146 Loc
:= Original_Location
(Sloc
(E
));
148 Xrefs
.Table
(Indx
).Ent
:= E
;
149 Xrefs
.Table
(Indx
).Def
:= No_Location
;
150 Xrefs
.Table
(Indx
).Loc
:= No_Location
;
151 Xrefs
.Table
(Indx
).Typ
:= ' ';
152 Xrefs
.Table
(Indx
).Eun
:= Get_Source_Unit
(Loc
);
153 Xrefs
.Table
(Indx
).Lun
:= No_Unit
;
154 Set_Has_Xref_Entry
(E
);
156 if In_Inlined_Body
then
160 end Generate_Definition
;
162 ---------------------------------
163 -- Generate_Operator_Reference --
164 ---------------------------------
166 procedure Generate_Operator_Reference
171 if not In_Extended_Main_Source_Unit
(N
) then
175 -- If the operator is not a Standard operator, then we generate a real
176 -- reference to the user defined operator.
178 if Sloc
(Entity
(N
)) /= Standard_Location
then
179 Generate_Reference
(Entity
(N
), N
);
181 -- A reference to an implicit inequality operator is also a reference
182 -- to the user-defined equality.
184 if Nkind
(N
) = N_Op_Ne
185 and then not Comes_From_Source
(Entity
(N
))
186 and then Present
(Corresponding_Equality
(Entity
(N
)))
188 Generate_Reference
(Corresponding_Equality
(Entity
(N
)), N
);
191 -- For the case of Standard operators, we mark the result type as
192 -- referenced. This ensures that in the case where we are using a
193 -- derived operator, we mark an entity of the unit that implicitly
194 -- defines this operator as used. Otherwise we may think that no entity
195 -- of the unit is used. The actual entity marked as referenced is the
196 -- first subtype, which is the relevant user defined entity.
198 -- Note: we only do this for operators that come from source. The
199 -- generated code sometimes reaches for entities that do not need to be
200 -- explicitly visible (for example, when we expand the code for
201 -- comparing two record objects, the fields of the record may not be
204 elsif Comes_From_Source
(N
) then
205 Set_Referenced
(First_Subtype
(T
));
207 end Generate_Operator_Reference
;
209 ---------------------------------
210 -- Generate_Prim_Op_References --
211 ---------------------------------
213 procedure Generate_Prim_Op_References
(Typ
: Entity_Id
) is
216 Prim_List
: Elist_Id
;
220 -- Handle subtypes of synchronized types
222 if Ekind
(Typ
) = E_Protected_Subtype
223 or else Ekind
(Typ
) = E_Task_Subtype
225 Base_T
:= Etype
(Typ
);
230 -- References to primitive operations are only relevant for tagged types
232 if not Is_Tagged_Type
(Base_T
)
233 or else Is_Class_Wide_Type
(Base_T
)
238 -- Ada 2005 (AI-345): For synchronized types generate reference
239 -- to the wrapper that allow us to dispatch calls through their
240 -- implemented abstract interface types.
242 -- The check for Present here is to protect against previously
243 -- reported critical errors.
245 if Is_Concurrent_Type
(Base_T
)
246 and then Present
(Corresponding_Record_Type
(Base_T
))
248 Prim_List
:= Primitive_Operations
249 (Corresponding_Record_Type
(Base_T
));
251 Prim_List
:= Primitive_Operations
(Base_T
);
254 if No
(Prim_List
) then
258 Prim
:= First_Elmt
(Prim_List
);
259 while Present
(Prim
) loop
261 -- If the operation is derived, get the original for cross-reference
262 -- reference purposes (it is the original for which we want the xref
263 -- and for which the comes_from_source test must be performed).
266 while Present
(Alias
(Ent
)) loop
270 Generate_Reference
(Typ
, Ent
, 'p', Set_Ref
=> False);
273 end Generate_Prim_Op_References
;
275 ------------------------
276 -- Generate_Reference --
277 ------------------------
279 procedure Generate_Reference
282 Typ
: Character := 'r';
283 Set_Ref
: Boolean := True;
284 Force
: Boolean := False)
294 -- Used for call to Find_Actual
297 -- If Formal is non-Empty, then its Ekind, otherwise E_Void
299 function Is_On_LHS
(Node
: Node_Id
) return Boolean;
300 -- Used to check if a node is on the left hand side of an assignment.
301 -- The following cases are handled:
303 -- Variable Node is a direct descendant of left hand side of an
304 -- assignment statement.
306 -- Prefix Of an indexed or selected component that is present in
307 -- a subtree rooted by an assignment statement. There is
308 -- no restriction of nesting of components, thus cases
309 -- such as A.B (C).D are handled properly. However a prefix
310 -- of a dereference (either implicit or explicit) is never
311 -- considered as on a LHS.
313 -- Out param Same as above cases, but OUT parameter
315 function OK_To_Set_Referenced
return Boolean;
316 -- Returns True if the Referenced flag can be set. There are a few
317 -- exceptions where we do not want to set this flag, see body for
318 -- details of these exceptional cases.
324 -- ??? There are several routines here and there that perform a similar
325 -- (but subtly different) computation, which should be factored:
327 -- Sem_Util.May_Be_Lvalue
328 -- Sem_Util.Known_To_Be_Assigned
329 -- Exp_Ch2.Expand_Entry_Parameter.In_Assignment_Context
330 -- Exp_Smem.Is_Out_Actual
332 function Is_On_LHS
(Node
: Node_Id
) return Boolean is
338 -- Only identifiers are considered, is this necessary???
340 if Nkind
(Node
) /= N_Identifier
then
344 -- Immediate return if appeared as OUT parameter
346 if Kind
= E_Out_Parameter
then
350 -- Search for assignment statement subtree root
357 if K
= N_Assignment_Statement
then
360 -- Check whether the parent is a component and the current node is
361 -- its prefix, but return False if the current node has an access
362 -- type, as in that case the selected or indexed component is an
363 -- implicit dereference, and the LHS is the designated object, not
364 -- the access object.
366 -- ??? case of a slice assignment?
368 -- ??? Note that in some cases this is called too early
369 -- (see comments in Sem_Ch8.Find_Direct_Name), at a point where
370 -- the tree is not fully typed yet. In that case we may lack
371 -- an Etype for N, and we must disable the check for an implicit
372 -- dereference. If the dereference is on an LHS, this causes a
375 elsif (K
= N_Selected_Component
or else K
= N_Indexed_Component
)
376 and then Prefix
(P
) = N
377 and then not (Present
(Etype
(N
))
379 Is_Access_Type
(Etype
(N
)))
383 -- All other cases, definitely not on left side
391 ---------------------------
392 -- OK_To_Set_Referenced --
393 ---------------------------
395 function OK_To_Set_Referenced
return Boolean is
399 -- A reference from a pragma Unreferenced or pragma Unmodified or
400 -- pragma Warnings does not cause the Referenced flag to be set.
401 -- This avoids silly warnings about things being referenced and
402 -- not assigned when the only reference is from the pragma.
404 if Nkind
(N
) = N_Identifier
then
407 if Nkind
(P
) = N_Pragma_Argument_Association
then
410 if Nkind
(P
) = N_Pragma
then
411 if Pragma_Name
(P
) = Name_Warnings
413 Pragma_Name
(P
) = Name_Unmodified
415 Pragma_Name
(P
) = Name_Unreferenced
424 end OK_To_Set_Referenced
;
426 -- Start of processing for Generate_Reference
429 pragma Assert
(Nkind
(E
) in N_Entity
);
430 Find_Actual
(N
, Formal
, Call
);
432 if Present
(Formal
) then
433 Kind
:= Ekind
(Formal
);
438 -- Check for obsolescent reference to package ASCII. GNAT treats this
439 -- element of annex J specially since in practice, programs make a lot
440 -- of use of this feature, so we don't include it in the set of features
441 -- diagnosed when Warn_On_Obsolescent_Features mode is set. However we
442 -- are required to note it as a violation of the RM defined restriction.
444 if E
= Standard_ASCII
then
445 Check_Restriction
(No_Obsolescent_Features
, N
);
448 -- Check for reference to entity marked with Is_Obsolescent
450 -- Note that we always allow obsolescent references in the compiler
451 -- itself and the run time, since we assume that we know what we are
452 -- doing in such cases. For example the calls in Ada.Characters.Handling
453 -- to its own obsolescent subprograms are just fine.
455 -- In any case we do not generate warnings within the extended source
456 -- unit of the entity in question, since we assume the source unit
457 -- itself knows what is going on (and for sure we do not want silly
458 -- warnings, e.g. on the end line of an obsolescent procedure body).
460 if Is_Obsolescent
(E
)
461 and then not GNAT_Mode
462 and then not In_Extended_Main_Source_Unit
(E
)
464 Check_Restriction
(No_Obsolescent_Features
, N
);
466 if Warn_On_Obsolescent_Feature
then
467 Output_Obsolescent_Entity_Warnings
(N
, E
);
471 -- Warn if reference to Ada 2005 entity not in Ada 2005 mode. We only
472 -- detect real explicit references (modifications and references).
474 if Comes_From_Source
(N
)
475 and then Is_Ada_2005_Only
(E
)
476 and then Ada_Version
< Ada_05
477 and then Warn_On_Ada_2005_Compatibility
478 and then (Typ
= 'm' or else Typ
= 'r')
480 Error_Msg_NE
("& is only defined in Ada 2005?", N
, E
);
483 -- Never collect references if not in main source unit. However, we omit
484 -- this test if Typ is 'e' or 'k', since these entries are structural,
485 -- and it is useful to have them in units that reference packages as
486 -- well as units that define packages. We also omit the test for the
487 -- case of 'p' since we want to include inherited primitive operations
488 -- from other packages.
490 -- We also omit this test is this is a body reference for a subprogram
491 -- instantiation. In this case the reference is to the generic body,
492 -- which clearly need not be in the main unit containing the instance.
493 -- For the same reason we accept an implicit reference generated for
494 -- a default in an instance.
496 if not In_Extended_Main_Source_Unit
(N
) then
501 or else (Typ
= 'b' and then Is_Generic_Instance
(E
))
509 -- For reference type p, the entity must be in main source unit
511 if Typ
= 'p' and then not In_Extended_Main_Source_Unit
(E
) then
515 -- Unless the reference is forced, we ignore references where the
516 -- reference itself does not come from source.
518 if not Force
and then not Comes_From_Source
(N
) then
522 -- Deal with setting entity as referenced, unless suppressed. Note that
523 -- we still do Set_Referenced on entities that do not come from source.
524 -- This situation arises when we have a source reference to a derived
525 -- operation, where the derived operation itself does not come from
526 -- source, but we still want to mark it as referenced, since we really
527 -- are referencing an entity in the corresponding package (this avoids
528 -- wrong complaints that the package contains no referenced entities).
532 -- Assignable object appearing on left side of assignment or as
536 and then Is_On_LHS
(N
)
537 and then Ekind
(E
) /= E_In_Out_Parameter
539 -- For objects that are renamings, just set as simply referenced
540 -- we do not try to do assignment type tracking in this case.
542 if Present
(Renamed_Object
(E
)) then
545 -- Out parameter case
547 elsif Kind
= E_Out_Parameter
then
549 -- If warning mode for all out parameters is set, or this is
550 -- the only warning parameter, then we want to mark this for
551 -- later warning logic by setting Referenced_As_Out_Parameter
553 if Warn_On_Modified_As_Out_Parameter
(Formal
) then
554 Set_Referenced_As_Out_Parameter
(E
, True);
555 Set_Referenced_As_LHS
(E
, False);
557 -- For OUT parameter not covered by the above cases, we simply
558 -- regard it as a normal reference (in this case we do not
559 -- want any of the warning machinery for out parameters).
565 -- For the left hand of an assignment case, we do nothing here.
566 -- The processing for Analyze_Assignment_Statement will set the
567 -- Referenced_As_LHS flag.
573 -- Check for a reference in a pragma that should not count as a
574 -- making the variable referenced for warning purposes.
576 elsif Is_Non_Significant_Pragma_Reference
(N
) then
579 -- A reference in an attribute definition clause does not count as a
580 -- reference except for the case of Address. The reason that 'Address
581 -- is an exception is that it creates an alias through which the
582 -- variable may be referenced.
584 elsif Nkind
(Parent
(N
)) = N_Attribute_Definition_Clause
585 and then Chars
(Parent
(N
)) /= Name_Address
586 and then N
= Name
(Parent
(N
))
590 -- Constant completion does not count as a reference
593 and then Ekind
(E
) = E_Constant
597 -- Record representation clause does not count as a reference
599 elsif Nkind
(N
) = N_Identifier
600 and then Nkind
(Parent
(N
)) = N_Record_Representation_Clause
604 -- Discriminants do not need to produce a reference to record type
607 and then Nkind
(Parent
(N
)) = N_Discriminant_Specification
614 -- Special processing for IN OUT parameters, where we have an
615 -- implicit assignment to a simple variable.
617 if Kind
= E_In_Out_Parameter
618 and then Is_Assignable
(E
)
620 -- For sure this counts as a normal read reference
623 Set_Last_Assignment
(E
, Empty
);
625 -- We count it as being referenced as an out parameter if the
626 -- option is set to warn on all out parameters, except that we
627 -- have a special exclusion for an intrinsic subprogram, which
628 -- is most likely an instantiation of Unchecked_Deallocation
629 -- which we do not want to consider as an assignment since it
630 -- generates false positives. We also exclude the case of an
631 -- IN OUT parameter if the name of the procedure is Free,
632 -- since we suspect similar semantics.
634 if Warn_On_All_Unread_Out_Parameters
635 and then Is_Entity_Name
(Name
(Call
))
636 and then not Is_Intrinsic_Subprogram
(Entity
(Name
(Call
)))
637 and then Chars
(Name
(Call
)) /= Name_Free
639 Set_Referenced_As_Out_Parameter
(E
, True);
640 Set_Referenced_As_LHS
(E
, False);
643 -- Don't count a recursive reference within a subprogram as a
644 -- reference (that allows detection of a recursive subprogram
645 -- whose only references are recursive calls as unreferenced).
647 elsif Is_Subprogram
(E
)
648 and then E
= Nearest_Dynamic_Scope
(Current_Scope
)
652 -- Any other occurrence counts as referencing the entity
654 elsif OK_To_Set_Referenced
then
657 -- If variable, this is an OK reference after an assignment
658 -- so we can clear the Last_Assignment indication.
660 if Is_Assignable
(E
) then
661 Set_Last_Assignment
(E
, Empty
);
666 -- Check for pragma Unreferenced given and reference is within
667 -- this source unit (occasion for possible warning to be issued).
669 if Has_Pragma_Unreferenced
(E
)
670 and then In_Same_Extended_Unit
(E
, N
)
672 -- A reference as a named parameter in a call does not count
673 -- as a violation of pragma Unreferenced for this purpose...
675 if Nkind
(N
) = N_Identifier
676 and then Nkind
(Parent
(N
)) = N_Parameter_Association
677 and then Selector_Name
(Parent
(N
)) = N
681 -- ... Neither does a reference to a variable on the left side
684 elsif Is_On_LHS
(N
) then
687 -- For entry formals, we want to place the warning message on the
688 -- corresponding entity in the accept statement. The current scope
689 -- is the body of the accept, so we find the formal whose name
690 -- matches that of the entry formal (there is no link between the
691 -- two entities, and the one in the accept statement is only used
692 -- for conformance checking).
694 elsif Ekind
(Scope
(E
)) = E_Entry
then
699 BE
:= First_Entity
(Current_Scope
);
700 while Present
(BE
) loop
701 if Chars
(BE
) = Chars
(E
) then
703 ("?pragma Unreferenced given for&!", N
, BE
);
711 -- Here we issue the warning, since this is a real reference
714 Error_Msg_NE
("?pragma Unreferenced given for&!", N
, E
);
718 -- If this is a subprogram instance, mark as well the internal
719 -- subprogram in the wrapper package, which may be a visible
722 if Is_Overloadable
(E
)
723 and then Is_Generic_Instance
(E
)
724 and then Present
(Alias
(E
))
726 Set_Referenced
(Alias
(E
));
730 -- Generate reference if all conditions are met:
733 -- Cross referencing must be active
737 -- The entity must be one for which we collect references
739 and then Xref_Entity_Letters
(Ekind
(E
)) /= ' '
741 -- Both Sloc values must be set to something sensible
743 and then Sloc
(E
) > No_Location
744 and then Sloc
(N
) > No_Location
746 -- We ignore references from within an instance, except for default
747 -- subprograms, for which we generate an implicit reference.
750 (Instantiation_Location
(Sloc
(N
)) = No_Location
or else Typ
= 'i')
752 -- Ignore dummy references
756 if Nkind
(N
) = N_Identifier
758 Nkind
(N
) = N_Defining_Identifier
762 Nkind
(N
) = N_Defining_Operator_Symbol
764 Nkind
(N
) = N_Operator_Symbol
766 (Nkind
(N
) = N_Character_Literal
767 and then Sloc
(Entity
(N
)) /= Standard_Location
)
769 Nkind
(N
) = N_Defining_Character_Literal
773 elsif Nkind
(N
) = N_Expanded_Name
775 Nkind
(N
) = N_Selected_Component
777 Nod
:= Selector_Name
(N
);
783 -- Normal case of source entity comes from source
785 if Comes_From_Source
(E
) then
788 -- Entity does not come from source, but is a derived subprogram and
789 -- the derived subprogram comes from source (after one or more
790 -- derivations) in which case the reference is to parent subprogram.
792 elsif Is_Overloadable
(E
)
793 and then Present
(Alias
(E
))
796 while not Comes_From_Source
(Ent
) loop
797 if No
(Alias
(Ent
)) then
804 -- The internally created defining entity for a child subprogram
805 -- that has no previous spec has valid references.
807 elsif Is_Overloadable
(E
)
808 and then Is_Child_Unit
(E
)
812 -- Record components of discriminated subtypes or derived types must
813 -- be treated as references to the original component.
815 elsif Ekind
(E
) = E_Component
816 and then Comes_From_Source
(Original_Record_Component
(E
))
818 Ent
:= Original_Record_Component
(E
);
820 -- If this is an expanded reference to a discriminant, recover the
821 -- original discriminant, which gets the reference.
823 elsif Ekind
(E
) = E_In_Parameter
824 and then Present
(Discriminal_Link
(E
))
826 Ent
:= Discriminal_Link
(E
);
827 Set_Referenced
(Ent
);
829 -- Ignore reference to any other entity that is not from source
835 -- Record reference to entity
837 Ref
:= Original_Location
(Sloc
(Nod
));
838 Def
:= Original_Location
(Sloc
(Ent
));
840 Xrefs
.Increment_Last
;
843 Xrefs
.Table
(Indx
).Loc
:= Ref
;
845 -- Overriding operations are marked with 'P'
848 and then Is_Subprogram
(N
)
849 and then Is_Overriding_Operation
(N
)
851 Xrefs
.Table
(Indx
).Typ
:= 'P';
853 Xrefs
.Table
(Indx
).Typ
:= Typ
;
856 Xrefs
.Table
(Indx
).Eun
:= Get_Source_Unit
(Def
);
857 Xrefs
.Table
(Indx
).Lun
:= Get_Source_Unit
(Ref
);
858 Xrefs
.Table
(Indx
).Ent
:= Ent
;
859 Set_Has_Xref_Entry
(Ent
);
861 end Generate_Reference
;
863 -----------------------------------
864 -- Generate_Reference_To_Formals --
865 -----------------------------------
867 procedure Generate_Reference_To_Formals
(E
: Entity_Id
) is
871 if Is_Generic_Subprogram
(E
) then
872 Formal
:= First_Entity
(E
);
874 while Present
(Formal
)
875 and then not Is_Formal
(Formal
)
877 Next_Entity
(Formal
);
881 Formal
:= First_Formal
(E
);
884 while Present
(Formal
) loop
885 if Ekind
(Formal
) = E_In_Parameter
then
887 if Nkind
(Parameter_Type
(Parent
(Formal
)))
888 = N_Access_Definition
890 Generate_Reference
(E
, Formal
, '^', False);
892 Generate_Reference
(E
, Formal
, '>', False);
895 elsif Ekind
(Formal
) = E_In_Out_Parameter
then
896 Generate_Reference
(E
, Formal
, '=', False);
899 Generate_Reference
(E
, Formal
, '<', False);
902 Next_Formal
(Formal
);
904 end Generate_Reference_To_Formals
;
906 -------------------------------------------
907 -- Generate_Reference_To_Generic_Formals --
908 -------------------------------------------
910 procedure Generate_Reference_To_Generic_Formals
(E
: Entity_Id
) is
914 Formal
:= First_Entity
(E
);
915 while Present
(Formal
) loop
916 if Comes_From_Source
(Formal
) then
917 Generate_Reference
(E
, Formal
, 'z', False);
920 Next_Entity
(Formal
);
922 end Generate_Reference_To_Generic_Formals
;
928 procedure Initialize
is
933 -----------------------
934 -- Output_References --
935 -----------------------
937 procedure Output_References
is
939 procedure Get_Type_Reference
941 Tref
: out Entity_Id
;
942 Left
: out Character;
943 Right
: out Character);
944 -- Given an Entity_Id Ent, determines whether a type reference is
945 -- required. If so, Tref is set to the entity for the type reference
946 -- and Left and Right are set to the left/right brackets to be output
947 -- for the reference. If no type reference is required, then Tref is
948 -- set to Empty, and Left/Right are set to space.
950 procedure Output_Import_Export_Info
(Ent
: Entity_Id
);
951 -- Output language and external name information for an interfaced
952 -- entity, using the format <language, external_name>,
954 ------------------------
955 -- Get_Type_Reference --
956 ------------------------
958 procedure Get_Type_Reference
960 Tref
: out Entity_Id
;
961 Left
: out Character;
962 Right
: out Character)
967 -- See if we have a type reference
976 -- Processing for types
978 if Is_Type
(Tref
) then
982 if Base_Type
(Tref
) = Tref
then
984 -- If derived, then get first subtype
986 if Tref
/= Etype
(Tref
) then
987 Tref
:= First_Subtype
(Etype
(Tref
));
989 -- Set brackets for derived type, but don't override
990 -- pointer case since the fact that something is a
991 -- pointer is more important.
998 -- If non-derived ptr, get directly designated type.
999 -- If the type has a full view, all references are on the
1000 -- partial view, that is seen first.
1002 elsif Is_Access_Type
(Tref
) then
1003 Tref
:= Directly_Designated_Type
(Tref
);
1007 elsif Is_Private_Type
(Tref
)
1008 and then Present
(Full_View
(Tref
))
1010 if Is_Access_Type
(Full_View
(Tref
)) then
1011 Tref
:= Directly_Designated_Type
(Full_View
(Tref
));
1015 -- If the full view is an array type, we also retrieve
1016 -- the corresponding component type, because the ali
1017 -- entry already indicates that this is an array.
1019 elsif Is_Array_Type
(Full_View
(Tref
)) then
1020 Tref
:= Component_Type
(Full_View
(Tref
));
1025 -- If non-derived array, get component type. Skip component
1026 -- type for case of String or Wide_String, saves worthwhile
1029 elsif Is_Array_Type
(Tref
)
1030 and then Tref
/= Standard_String
1031 and then Tref
/= Standard_Wide_String
1033 Tref
:= Component_Type
(Tref
);
1037 -- For other non-derived base types, nothing
1043 -- For a subtype, go to ancestor subtype
1046 Tref
:= Ancestor_Subtype
(Tref
);
1048 -- If no ancestor subtype, go to base type
1051 Tref
:= Base_Type
(Sav
);
1055 -- For objects, functions, enum literals, just get type from
1058 elsif Is_Object
(Tref
)
1059 or else Ekind
(Tref
) = E_Enumeration_Literal
1060 or else Ekind
(Tref
) = E_Function
1061 or else Ekind
(Tref
) = E_Operator
1063 Tref
:= Etype
(Tref
);
1065 -- For anything else, exit
1071 -- Exit if no type reference, or we are stuck in some loop trying
1072 -- to find the type reference, or if the type is standard void
1073 -- type (the latter is an implementation artifact that should not
1074 -- show up in the generated cross-references).
1078 or else Tref
= Standard_Void_Type
;
1080 -- If we have a usable type reference, return, otherwise keep
1081 -- looking for something useful (we are looking for something
1082 -- that either comes from source or standard)
1084 if Sloc
(Tref
) = Standard_Location
1085 or else Comes_From_Source
(Tref
)
1087 -- If the reference is a subtype created for a generic actual,
1088 -- go actual directly, the inner subtype is not user visible.
1090 if Nkind
(Parent
(Tref
)) = N_Subtype_Declaration
1091 and then not Comes_From_Source
(Parent
(Tref
))
1093 (Is_Wrapper_Package
(Scope
(Tref
))
1094 or else Is_Generic_Instance
(Scope
(Tref
)))
1096 Tref
:= First_Subtype
(Base_Type
(Tref
));
1103 -- If we fall through the loop, no type reference
1108 end Get_Type_Reference
;
1110 -------------------------------
1111 -- Output_Import_Export_Info --
1112 -------------------------------
1114 procedure Output_Import_Export_Info
(Ent
: Entity_Id
) is
1115 Language_Name
: Name_Id
;
1116 Conv
: constant Convention_Id
:= Convention
(Ent
);
1119 -- Generate language name from convention
1121 if Conv
= Convention_C
then
1122 Language_Name
:= Name_C
;
1124 elsif Conv
= Convention_CPP
then
1125 Language_Name
:= Name_CPP
;
1127 elsif Conv
= Convention_Ada
then
1128 Language_Name
:= Name_Ada
;
1131 -- For the moment we ignore all other cases ???
1136 Write_Info_Char
('<');
1137 Get_Unqualified_Name_String
(Language_Name
);
1139 for J
in 1 .. Name_Len
loop
1140 Write_Info_Char
(Name_Buffer
(J
));
1143 if Present
(Interface_Name
(Ent
)) then
1144 Write_Info_Char
(',');
1145 String_To_Name_Buffer
(Strval
(Interface_Name
(Ent
)));
1147 for J
in 1 .. Name_Len
loop
1148 Write_Info_Char
(Name_Buffer
(J
));
1152 Write_Info_Char
('>');
1153 end Output_Import_Export_Info
;
1155 -- Start of processing for Output_References
1158 if not Opt
.Xref_Active
then
1162 -- First we add references to the primitive operations of tagged
1163 -- types declared in the main unit.
1165 Handle_Prim_Ops
: declare
1169 for J
in 1 .. Xrefs
.Last
loop
1170 Ent
:= Xrefs
.Table
(J
).Ent
;
1173 and then Is_Tagged_Type
(Ent
)
1174 and then Ent
= Base_Type
(Ent
)
1175 and then In_Extended_Main_Source_Unit
(Ent
)
1177 Generate_Prim_Op_References
(Ent
);
1180 end Handle_Prim_Ops
;
1182 -- Before we go ahead and output the references we have a problem
1183 -- that needs dealing with. So far we have captured things that are
1184 -- definitely referenced by the main unit, or defined in the main
1185 -- unit. That's because we don't want to clutter up the ali file
1186 -- for this unit with definition lines for entities in other units
1187 -- that are not referenced.
1189 -- But there is a glitch. We may reference an entity in another unit,
1190 -- and it may have a type reference to an entity that is not directly
1191 -- referenced in the main unit, which may mean that there is no xref
1192 -- entry for this entity yet in the list of references.
1194 -- If we don't do something about this, we will end with an orphan type
1195 -- reference, i.e. it will point to an entity that does not appear
1196 -- within the generated references in the ali file. That is not good for
1197 -- tools using the xref information.
1199 -- To fix this, we go through the references adding definition entries
1200 -- for any unreferenced entities that can be referenced in a type
1201 -- reference. There is a recursion problem here, and that is dealt with
1202 -- by making sure that this traversal also traverses any entries that
1203 -- get added by the traversal.
1205 Handle_Orphan_Type_References
: declare
1213 pragma Warnings
(Off
, L
);
1214 pragma Warnings
(Off
, R
);
1216 procedure New_Entry
(E
: Entity_Id
);
1217 -- Make an additional entry into the Xref table for a type entity
1218 -- that is related to the current entity (parent, type ancestor,
1219 -- progenitor, etc.).
1225 procedure New_Entry
(E
: Entity_Id
) is
1228 and then not Has_Xref_Entry
(E
)
1229 and then Sloc
(E
) > No_Location
1231 Xrefs
.Increment_Last
;
1233 Loc
:= Original_Location
(Sloc
(E
));
1234 Xrefs
.Table
(Indx
).Ent
:= E
;
1235 Xrefs
.Table
(Indx
).Loc
:= No_Location
;
1236 Xrefs
.Table
(Indx
).Eun
:= Get_Source_Unit
(Loc
);
1237 Xrefs
.Table
(Indx
).Lun
:= No_Unit
;
1238 Set_Has_Xref_Entry
(E
);
1242 -- Start of processing for Handle_Orphan_Type_References
1245 -- Note that this is not a for loop for a very good reason. The
1246 -- processing of items in the table can add new items to the table,
1247 -- and they must be processed as well.
1250 while J
<= Xrefs
.Last
loop
1251 Ent
:= Xrefs
.Table
(J
).Ent
;
1252 Get_Type_Reference
(Ent
, Tref
, L
, R
);
1255 and then not Has_Xref_Entry
(Tref
)
1256 and then Sloc
(Tref
) > No_Location
1260 if Is_Record_Type
(Ent
)
1261 and then Present
(Interfaces
(Ent
))
1263 -- Add an entry for each one of the given interfaces
1264 -- implemented by type Ent.
1267 Elmt
: Elmt_Id
:= First_Elmt
(Interfaces
(Ent
));
1269 while Present
(Elmt
) loop
1270 New_Entry
(Node
(Elmt
));
1277 -- Collect inherited primitive operations that may be declared in
1278 -- another unit and have no visible reference in the current one.
1281 and then Is_Tagged_Type
(Ent
)
1282 and then Is_Derived_Type
(Ent
)
1283 and then Ent
= Base_Type
(Ent
)
1284 and then In_Extended_Main_Source_Unit
(Ent
)
1287 Op_List
: constant Elist_Id
:= Primitive_Operations
(Ent
);
1291 function Parent_Op
(E
: Entity_Id
) return Entity_Id
;
1292 -- Find original operation, which may be inherited through
1293 -- several derivations.
1295 function Parent_Op
(E
: Entity_Id
) return Entity_Id
is
1296 Orig_Op
: constant Entity_Id
:= Alias
(E
);
1299 if No
(Orig_Op
) then
1302 elsif not Comes_From_Source
(E
)
1303 and then not Has_Xref_Entry
(Orig_Op
)
1304 and then Comes_From_Source
(Orig_Op
)
1308 return Parent_Op
(Orig_Op
);
1313 Op
:= First_Elmt
(Op_List
);
1314 while Present
(Op
) loop
1315 Prim
:= Parent_Op
(Node
(Op
));
1317 if Present
(Prim
) then
1318 Xrefs
.Increment_Last
;
1320 Loc
:= Original_Location
(Sloc
(Prim
));
1321 Xrefs
.Table
(Indx
).Ent
:= Prim
;
1322 Xrefs
.Table
(Indx
).Loc
:= No_Location
;
1323 Xrefs
.Table
(Indx
).Eun
:=
1324 Get_Source_Unit
(Sloc
(Prim
));
1325 Xrefs
.Table
(Indx
).Lun
:= No_Unit
;
1326 Set_Has_Xref_Entry
(Prim
);
1336 end Handle_Orphan_Type_References
;
1338 -- Now we have all the references, including those for any embedded
1339 -- type references, so we can sort them, and output them.
1341 Output_Refs
: declare
1343 Nrefs
: Nat
:= Xrefs
.Last
;
1344 -- Number of references in table. This value may get reset (reduced)
1345 -- when we eliminate duplicate reference entries.
1347 Rnums
: array (0 .. Nrefs
) of Nat
;
1348 -- This array contains numbers of references in the Xrefs table.
1349 -- This list is sorted in output order. The extra 0'th entry is
1350 -- convenient for the call to sort. When we sort the table, we
1351 -- move the entries in Rnums around, but we do not move the
1352 -- original table entries.
1354 Curxu
: Unit_Number_Type
;
1355 -- Current xref unit
1357 Curru
: Unit_Number_Type
;
1358 -- Current reference unit for one entity
1360 Cursrc
: Source_Buffer_Ptr
;
1361 -- Current xref unit source text
1366 Curnam
: String (1 .. Name_Buffer
'Length);
1368 -- Simple name and length of current entity
1370 Curdef
: Source_Ptr
;
1371 -- Original source location for current entity
1374 -- Current reference location
1377 -- Entity type character
1383 -- Renaming reference
1385 Trunit
: Unit_Number_Type
;
1386 -- Unit number for type reference
1388 function Lt
(Op1
, Op2
: Natural) return Boolean;
1389 -- Comparison function for Sort call
1391 function Name_Change
(X
: Entity_Id
) return Boolean;
1392 -- Determines if entity X has a different simple name from Curent
1394 procedure Move
(From
: Natural; To
: Natural);
1395 -- Move procedure for Sort call
1397 package Sorting
is new GNAT
.Heap_Sort_G
(Move
, Lt
);
1403 function Lt
(Op1
, Op2
: Natural) return Boolean is
1404 T1
: Xref_Entry
renames Xrefs
.Table
(Rnums
(Nat
(Op1
)));
1405 T2
: Xref_Entry
renames Xrefs
.Table
(Rnums
(Nat
(Op2
)));
1408 -- First test: if entity is in different unit, sort by unit
1410 if T1
.Eun
/= T2
.Eun
then
1411 return Dependency_Num
(T1
.Eun
) < Dependency_Num
(T2
.Eun
);
1413 -- Second test: within same unit, sort by entity Sloc
1415 elsif T1
.Def
/= T2
.Def
then
1416 return T1
.Def
< T2
.Def
;
1418 -- Third test: sort definitions ahead of references
1420 elsif T1
.Loc
= No_Location
then
1423 elsif T2
.Loc
= No_Location
then
1426 -- Fourth test: for same entity, sort by reference location unit
1428 elsif T1
.Lun
/= T2
.Lun
then
1429 return Dependency_Num
(T1
.Lun
) < Dependency_Num
(T2
.Lun
);
1431 -- Fifth test: order of location within referencing unit
1433 elsif T1
.Loc
/= T2
.Loc
then
1434 return T1
.Loc
< T2
.Loc
;
1436 -- Finally, for two locations at the same address, we prefer
1437 -- the one that does NOT have the type 'r' so that a modification
1438 -- or extension takes preference, when there are more than one
1439 -- reference at the same location.
1442 return T2
.Typ
= 'r';
1450 procedure Move
(From
: Natural; To
: Natural) is
1452 Rnums
(Nat
(To
)) := Rnums
(Nat
(From
));
1459 -- Why a string comparison here??? Why not compare Name_Id values???
1461 function Name_Change
(X
: Entity_Id
) return Boolean is
1463 Get_Unqualified_Name_String
(Chars
(X
));
1465 if Name_Len
/= Curlen
then
1468 return Name_Buffer
(1 .. Curlen
) /= Curnam
(1 .. Curlen
);
1472 -- Start of processing for Output_Refs
1475 -- Capture the definition Sloc values. We delay doing this till now,
1476 -- since at the time the reference or definition is made, private
1477 -- types may be swapped, and the Sloc value may be incorrect. We
1478 -- also set up the pointer vector for the sort.
1480 for J
in 1 .. Nrefs
loop
1482 Xrefs
.Table
(J
).Def
:=
1483 Original_Location
(Sloc
(Xrefs
.Table
(J
).Ent
));
1486 -- Sort the references
1488 Sorting
.Sort
(Integer (Nrefs
));
1490 -- Eliminate duplicate entries
1493 NR
: constant Nat
:= Nrefs
;
1496 -- We need this test for NR because if we force ALI file
1497 -- generation in case of errors detected, it may be the case
1498 -- that Nrefs is 0, so we should not reset it here
1503 for J
in 2 .. NR
loop
1504 if Xrefs
.Table
(Rnums
(J
)) /=
1505 Xrefs
.Table
(Rnums
(Nrefs
))
1508 Rnums
(Nrefs
) := Rnums
(J
);
1514 -- Initialize loop through references
1518 Curdef
:= No_Location
;
1520 Crloc
:= No_Location
;
1522 -- Loop to output references
1524 for Refno
in 1 .. Nrefs
loop
1525 Output_One_Ref
: declare
1531 pragma Warnings
(Off
, WC
);
1532 pragma Warnings
(Off
, Err
);
1534 XE
: Xref_Entry
renames Xrefs
.Table
(Rnums
(Refno
));
1535 -- The current entry to be accessed
1538 -- Used to index into source buffer to get entity name
1542 -- Used for {} or <> or () for type reference
1544 procedure Check_Type_Reference
1546 List_Interface
: Boolean);
1547 -- Find whether there is a meaningful type reference for
1548 -- Ent, and display it accordingly. If List_Interface is
1549 -- true, then Ent is a progenitor interface of the current
1550 -- type entity being listed. In that case list it as is,
1551 -- without looking for a type reference for it.
1553 procedure Output_Instantiation_Refs
(Loc
: Source_Ptr
);
1554 -- Recursive procedure to output instantiation references for
1555 -- the given source ptr in [file|line[...]] form. No output
1556 -- if the given location is not a generic template reference.
1558 procedure Output_Overridden_Op
(Old_E
: Entity_Id
);
1559 -- For a subprogram that is overriding, display information
1560 -- about the inherited operation that it overrides.
1562 --------------------------
1563 -- Check_Type_Reference --
1564 --------------------------
1566 procedure Check_Type_Reference
1568 List_Interface
: Boolean)
1571 if List_Interface
then
1573 -- This is a progenitor interface of the type for which
1574 -- xref information is being generated.
1581 Get_Type_Reference
(Ent
, Tref
, Left
, Right
);
1584 if Present
(Tref
) then
1586 -- Case of standard entity, output name
1588 if Sloc
(Tref
) = Standard_Location
then
1589 Write_Info_Char
(Left
);
1590 Write_Info_Name
(Chars
(Tref
));
1591 Write_Info_Char
(Right
);
1593 -- Case of source entity, output location
1596 Write_Info_Char
(Left
);
1597 Trunit
:= Get_Source_Unit
(Sloc
(Tref
));
1599 if Trunit
/= Curxu
then
1600 Write_Info_Nat
(Dependency_Num
(Trunit
));
1601 Write_Info_Char
('|');
1605 (Int
(Get_Logical_Line_Number
(Sloc
(Tref
))));
1613 Ctyp
:= Xref_Entity_Letters
(Ekind
(Ent
));
1616 and then Present
(Full_View
(Ent
))
1618 Ent
:= Underlying_Type
(Ent
);
1620 if Present
(Ent
) then
1621 Ctyp
:= Xref_Entity_Letters
(Ekind
(Ent
));
1625 Write_Info_Char
(Ctyp
);
1629 (Int
(Get_Column_Number
(Sloc
(Tref
))));
1631 -- If the type comes from an instantiation, add the
1632 -- corresponding info.
1634 Output_Instantiation_Refs
(Sloc
(Tref
));
1635 Write_Info_Char
(Right
);
1638 end Check_Type_Reference
;
1640 -------------------------------
1641 -- Output_Instantiation_Refs --
1642 -------------------------------
1644 procedure Output_Instantiation_Refs
(Loc
: Source_Ptr
) is
1645 Iloc
: constant Source_Ptr
:= Instantiation_Location
(Loc
);
1646 Lun
: Unit_Number_Type
;
1647 Cu
: constant Unit_Number_Type
:= Curru
;
1650 -- Nothing to do if this is not an instantiation
1652 if Iloc
= No_Location
then
1656 -- Output instantiation reference
1658 Write_Info_Char
('[');
1659 Lun
:= Get_Source_Unit
(Iloc
);
1661 if Lun
/= Curru
then
1663 Write_Info_Nat
(Dependency_Num
(Curru
));
1664 Write_Info_Char
('|');
1667 Write_Info_Nat
(Int
(Get_Logical_Line_Number
(Iloc
)));
1669 -- Recursive call to get nested instantiations
1671 Output_Instantiation_Refs
(Iloc
);
1673 -- Output final ] after call to get proper nesting
1675 Write_Info_Char
(']');
1678 end Output_Instantiation_Refs
;
1680 --------------------------
1681 -- Output_Overridden_Op --
1682 --------------------------
1684 procedure Output_Overridden_Op
(Old_E
: Entity_Id
) is
1688 -- The overridden operation has an implicit declaration
1689 -- at the point of derivation. What we want to display
1690 -- is the original operation, which has the actual body
1691 -- (or abstract declaration) that is being overridden.
1692 -- The overridden operation is not always set, e.g. when
1693 -- it is a predefined operator.
1698 -- Follow alias chain if one is present
1700 elsif Present
(Alias
(Old_E
)) then
1702 -- The subprogram may have been implicitly inherited
1703 -- through several levels of derivation, so find the
1704 -- ultimate (source) ancestor.
1706 Op
:= Alias
(Old_E
);
1707 while Present
(Alias
(Op
)) loop
1711 -- Normal case of no alias present
1718 and then Sloc
(Op
) /= Standard_Location
1721 Loc
: constant Source_Ptr
:= Sloc
(Op
);
1722 Par_Unit
: constant Unit_Number_Type
:=
1723 Get_Source_Unit
(Loc
);
1726 Write_Info_Char
('<');
1728 if Par_Unit
/= Curxu
then
1729 Write_Info_Nat
(Dependency_Num
(Par_Unit
));
1730 Write_Info_Char
('|');
1733 Write_Info_Nat
(Int
(Get_Logical_Line_Number
(Loc
)));
1734 Write_Info_Char
('p');
1735 Write_Info_Nat
(Int
(Get_Column_Number
(Loc
)));
1736 Write_Info_Char
('>');
1739 end Output_Overridden_Op
;
1741 -- Start of processing for Output_One_Ref
1745 Ctyp
:= Xref_Entity_Letters
(Ekind
(Ent
));
1747 -- Skip reference if it is the only reference to an entity,
1748 -- and it is an END line reference, and the entity is not in
1749 -- the current extended source. This prevents junk entries
1750 -- consisting only of packages with END lines, where no
1751 -- entity from the package is actually referenced.
1754 and then Ent
/= Curent
1755 and then (Refno
= Nrefs
or else
1756 Ent
/= Xrefs
.Table
(Rnums
(Refno
+ 1)).Ent
)
1758 not In_Extended_Main_Source_Unit
(Ent
)
1763 -- For private type, get full view type
1766 and then Present
(Full_View
(XE
.Ent
))
1768 Ent
:= Underlying_Type
(Ent
);
1770 if Present
(Ent
) then
1771 Ctyp
:= Xref_Entity_Letters
(Ekind
(Ent
));
1775 -- Special exception for Boolean
1777 if Ctyp
= 'E' and then Is_Boolean_Type
(Ent
) then
1781 -- For variable reference, get corresponding type
1784 Ent
:= Etype
(XE
.Ent
);
1785 Ctyp
:= Fold_Lower
(Xref_Entity_Letters
(Ekind
(Ent
)));
1787 -- If variable is private type, get full view type
1790 and then Present
(Full_View
(Etype
(XE
.Ent
)))
1792 Ent
:= Underlying_Type
(Etype
(XE
.Ent
));
1794 if Present
(Ent
) then
1795 Ctyp
:= Fold_Lower
(Xref_Entity_Letters
(Ekind
(Ent
)));
1798 elsif Is_Generic_Type
(Ent
) then
1800 -- If the type of the entity is a generic private type,
1801 -- there is no usable full view, so retain the indication
1802 -- that this is an object.
1807 -- Special handling for access parameter
1810 K
: constant Entity_Kind
:= Ekind
(Etype
(XE
.Ent
));
1813 if (K
= E_Anonymous_Access_Type
1815 K
= E_Anonymous_Access_Subprogram_Type
1817 E_Anonymous_Access_Protected_Subprogram_Type
)
1818 and then Is_Formal
(XE
.Ent
)
1822 -- Special handling for Boolean
1824 elsif Ctyp
= 'e' and then Is_Boolean_Type
(Ent
) then
1830 -- Special handling for abstract types and operations
1832 if Is_Overloadable
(XE
.Ent
)
1833 and then Is_Abstract_Subprogram
(XE
.Ent
)
1836 Ctyp
:= 'x'; -- Abstract procedure
1838 elsif Ctyp
= 'V' then
1839 Ctyp
:= 'y'; -- Abstract function
1842 elsif Is_Type
(XE
.Ent
)
1843 and then Is_Abstract_Type
(XE
.Ent
)
1845 if Is_Interface
(XE
.Ent
) then
1848 elsif Ctyp
= 'R' then
1849 Ctyp
:= 'H'; -- Abstract type
1853 -- Only output reference if interesting type of entity, and
1854 -- suppress self references, except for bodies that act as
1855 -- specs. Also suppress definitions of body formals (we only
1856 -- treat these as references, and the references were
1857 -- separately recorded).
1860 or else (XE
.Loc
= XE
.Def
1863 or else not Is_Subprogram
(XE
.Ent
)))
1864 or else (Is_Formal
(XE
.Ent
)
1865 and then Present
(Spec_Entity
(XE
.Ent
)))
1870 -- Start new Xref section if new xref unit
1872 if XE
.Eun
/= Curxu
then
1873 if Write_Info_Col
> 1 then
1878 Cursrc
:= Source_Text
(Source_Index
(Curxu
));
1880 Write_Info_Initiate
('X');
1881 Write_Info_Char
(' ');
1882 Write_Info_Nat
(Dependency_Num
(XE
.Eun
));
1883 Write_Info_Char
(' ');
1884 Write_Info_Name
(Reference_Name
(Source_Index
(XE
.Eun
)));
1887 -- Start new Entity line if new entity. Note that we
1888 -- consider two entities the same if they have the same
1889 -- name and source location. This causes entities in
1890 -- instantiations to be treated as though they referred
1897 (Name_Change
(XE
.Ent
) or else XE
.Def
/= Curdef
))
1902 Get_Unqualified_Name_String
(Chars
(XE
.Ent
));
1904 Curnam
(1 .. Curlen
) := Name_Buffer
(1 .. Curlen
);
1906 if Write_Info_Col
> 1 then
1910 -- Write column number information
1912 Write_Info_Nat
(Int
(Get_Logical_Line_Number
(XE
.Def
)));
1913 Write_Info_Char
(Ctyp
);
1914 Write_Info_Nat
(Int
(Get_Column_Number
(XE
.Def
)));
1916 -- Write level information
1918 Write_Level_Info
: declare
1919 function Is_Visible_Generic_Entity
1920 (E
: Entity_Id
) return Boolean;
1921 -- Check whether E is declared in the visible part
1922 -- of a generic package. For source navigation
1923 -- purposes, treat this as a visible entity.
1925 function Is_Private_Record_Component
1926 (E
: Entity_Id
) return Boolean;
1927 -- Check whether E is a non-inherited component of a
1928 -- private extension. Even if the enclosing record is
1929 -- public, we want to treat the component as private
1930 -- for navigation purposes.
1932 ---------------------------------
1933 -- Is_Private_Record_Component --
1934 ---------------------------------
1936 function Is_Private_Record_Component
1937 (E
: Entity_Id
) return Boolean
1939 S
: constant Entity_Id
:= Scope
(E
);
1942 Ekind
(E
) = E_Component
1943 and then Nkind
(Declaration_Node
(S
)) =
1944 N_Private_Extension_Declaration
1945 and then Original_Record_Component
(E
) = E
;
1946 end Is_Private_Record_Component
;
1948 -------------------------------
1949 -- Is_Visible_Generic_Entity --
1950 -------------------------------
1952 function Is_Visible_Generic_Entity
1953 (E
: Entity_Id
) return Boolean
1958 -- The Present check here is an error defense
1960 if Present
(Scope
(E
))
1961 and then Ekind
(Scope
(E
)) /= E_Generic_Package
1967 while Present
(Par
) loop
1969 Nkind
(Par
) = N_Generic_Package_Declaration
1971 -- Entity is a generic formal
1976 Nkind
(Parent
(Par
)) = N_Package_Specification
1979 Is_List_Member
(Par
)
1980 and then List_Containing
(Par
) =
1981 Visible_Declarations
(Parent
(Par
));
1983 Par
:= Parent
(Par
);
1988 end Is_Visible_Generic_Entity
;
1990 -- Start of processing for Write_Level_Info
1993 if Is_Hidden
(Curent
)
1994 or else Is_Private_Record_Component
(Curent
)
1996 Write_Info_Char
(' ');
2000 or else Is_Visible_Generic_Entity
(Curent
)
2002 Write_Info_Char
('*');
2005 Write_Info_Char
(' ');
2007 end Write_Level_Info
;
2009 -- Output entity name. We use the occurrence from the
2010 -- actual source program at the definition point.
2012 P
:= Original_Location
(Sloc
(XE
.Ent
));
2014 -- Entity is character literal
2016 if Cursrc
(P
) = ''' then
2017 Write_Info_Char
(Cursrc
(P
));
2018 Write_Info_Char
(Cursrc
(P
+ 1));
2019 Write_Info_Char
(Cursrc
(P
+ 2));
2021 -- Entity is operator symbol
2023 elsif Cursrc
(P
) = '"' or else Cursrc
(P
) = '%' then
2024 Write_Info_Char
(Cursrc
(P
));
2029 Write_Info_Char
(Cursrc
(P2
));
2030 exit when Cursrc
(P2
) = Cursrc
(P
);
2033 -- Entity is identifier
2037 if Is_Start_Of_Wide_Char
(Cursrc
, P
) then
2038 Scan_Wide
(Cursrc
, P
, WC
, Err
);
2039 elsif not Identifier_Char
(Cursrc
(P
)) then
2046 -- Write out the identifier by copying the exact
2047 -- source characters used in its declaration. Note
2048 -- that this means wide characters will be in their
2049 -- original encoded form.
2052 Original_Location
(Sloc
(XE
.Ent
)) .. P
- 1
2054 Write_Info_Char
(Cursrc
(J
));
2058 -- See if we have a renaming reference
2060 if Is_Object
(XE
.Ent
)
2061 and then Present
(Renamed_Object
(XE
.Ent
))
2063 Rref
:= Renamed_Object
(XE
.Ent
);
2065 elsif Is_Overloadable
(XE
.Ent
)
2066 and then Nkind
(Parent
(Declaration_Node
(XE
.Ent
))) =
2067 N_Subprogram_Renaming_Declaration
2069 Rref
:= Name
(Parent
(Declaration_Node
(XE
.Ent
)));
2071 elsif Ekind
(XE
.Ent
) = E_Package
2072 and then Nkind
(Declaration_Node
(XE
.Ent
)) =
2073 N_Package_Renaming_Declaration
2075 Rref
:= Name
(Declaration_Node
(XE
.Ent
));
2081 if Present
(Rref
) then
2082 if Nkind
(Rref
) = N_Expanded_Name
then
2083 Rref
:= Selector_Name
(Rref
);
2086 if Nkind
(Rref
) = N_Identifier
2087 or else Nkind
(Rref
) = N_Operator_Symbol
2091 -- For renamed array components, use the array name
2092 -- for the renamed entity, which reflect the fact that
2093 -- in general the whole array is aliased.
2095 elsif Nkind
(Rref
) = N_Indexed_Component
then
2096 if Nkind
(Prefix
(Rref
)) = N_Identifier
then
2097 Rref
:= Prefix
(Rref
);
2098 elsif Nkind
(Prefix
(Rref
)) = N_Expanded_Name
then
2099 Rref
:= Selector_Name
(Prefix
(Rref
));
2109 -- Write out renaming reference if we have one
2111 if Present
(Rref
) then
2112 Write_Info_Char
('=');
2114 (Int
(Get_Logical_Line_Number
(Sloc
(Rref
))));
2115 Write_Info_Char
(':');
2117 (Int
(Get_Column_Number
(Sloc
(Rref
))));
2120 -- Indicate that the entity is in the unit of the current
2125 -- Write out information about generic parent, if entity
2128 if Is_Generic_Instance
(XE
.Ent
) then
2130 Gen_Par
: constant Entity_Id
:=
2133 (Unit_Declaration_Node
(XE
.Ent
)));
2134 Loc
: constant Source_Ptr
:= Sloc
(Gen_Par
);
2135 Gen_U
: constant Unit_Number_Type
:=
2136 Get_Source_Unit
(Loc
);
2139 Write_Info_Char
('[');
2141 if Curru
/= Gen_U
then
2142 Write_Info_Nat
(Dependency_Num
(Gen_U
));
2143 Write_Info_Char
('|');
2147 (Int
(Get_Logical_Line_Number
(Loc
)));
2148 Write_Info_Char
(']');
2152 -- See if we have a type reference and if so output
2154 Check_Type_Reference
(XE
.Ent
, False);
2156 -- Additional information for types with progenitors
2158 if Is_Record_Type
(XE
.Ent
)
2159 and then Present
(Interfaces
(XE
.Ent
))
2162 Elmt
: Elmt_Id
:= First_Elmt
(Interfaces
(XE
.Ent
));
2164 while Present
(Elmt
) loop
2165 Check_Type_Reference
(Node
(Elmt
), True);
2170 -- For array types, list index types as well.
2171 -- (This is not C, indices have distinct types).
2173 elsif Is_Array_Type
(XE
.Ent
) then
2177 Indx
:= First_Index
(XE
.Ent
);
2178 while Present
(Indx
) loop
2179 Check_Type_Reference
2180 (First_Subtype
(Etype
(Indx
)), True);
2186 -- If the entity is an overriding operation, write info
2187 -- on operation that was overridden.
2189 if Is_Subprogram
(XE
.Ent
)
2190 and then Is_Overriding_Operation
(XE
.Ent
)
2192 Output_Overridden_Op
(Overridden_Operation
(XE
.Ent
));
2195 -- End of processing for entity output
2197 Crloc
:= No_Location
;
2200 -- Output the reference
2202 if XE
.Loc
/= No_Location
2203 and then XE
.Loc
/= Crloc
2207 -- Start continuation if line full, else blank
2209 if Write_Info_Col
> 72 then
2211 Write_Info_Initiate
('.');
2214 Write_Info_Char
(' ');
2216 -- Output file number if changed
2218 if XE
.Lun
/= Curru
then
2220 Write_Info_Nat
(Dependency_Num
(Curru
));
2221 Write_Info_Char
('|');
2224 Write_Info_Nat
(Int
(Get_Logical_Line_Number
(XE
.Loc
)));
2225 Write_Info_Char
(XE
.Typ
);
2227 if Is_Overloadable
(XE
.Ent
)
2228 and then Is_Imported
(XE
.Ent
)
2229 and then XE
.Typ
= 'b'
2231 Output_Import_Export_Info
(XE
.Ent
);
2234 Write_Info_Nat
(Int
(Get_Column_Number
(XE
.Loc
)));
2236 Output_Instantiation_Refs
(Sloc
(XE
.Ent
));
2247 end Output_References
;