libatomic: Handle AVX+CX16 ZHAOXIN like Intel for 16b atomic [PR104688]
[official-gcc.git] / gcc / ada / lib-xref.adb
blobcecbac19cf3be27aa2bb824174321a4783fedfea
1 ------------------------------------------------------------------------------
2 -- --
3 -- GNAT COMPILER COMPONENTS --
4 -- --
5 -- L I B . X R E F --
6 -- --
7 -- B o d y --
8 -- --
9 -- Copyright (C) 1998-2024, Free Software Foundation, Inc. --
10 -- --
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. --
20 -- --
21 -- GNAT was originally developed by the GNAT team at New York University. --
22 -- Extensive contributions were provided by Ada Core Technologies Inc. --
23 -- --
24 ------------------------------------------------------------------------------
26 with Atree; use Atree;
27 with Csets; use Csets;
28 with Einfo; use Einfo;
29 with Einfo.Utils; use Einfo.Utils;
30 with Elists; use Elists;
31 with Errout; use Errout;
32 with Exp_Tss; use Exp_Tss;
33 with Lib.Util; use Lib.Util;
34 with Nlists; use Nlists;
35 with Opt; use Opt;
36 with Restrict; use Restrict;
37 with Rident; use Rident;
38 with Sem; use Sem;
39 with Sem_Aux; use Sem_Aux;
40 with Sem_Prag; use Sem_Prag;
41 with Sem_Util; use Sem_Util;
42 with Sem_Warn; use Sem_Warn;
43 with Sinfo; use Sinfo;
44 with Sinfo.Nodes; use Sinfo.Nodes;
45 with Sinfo.Utils; use Sinfo.Utils;
46 with Sinput; use Sinput;
47 with Snames; use Snames;
48 with Stringt; use Stringt;
49 with Stand; use Stand;
50 with Table; use Table;
51 with Warnsw; use Warnsw;
53 with GNAT.Heap_Sort_G;
54 with GNAT.HTable;
56 package body Lib.Xref is
58 ------------------
59 -- Declarations --
60 ------------------
62 -- The Xref table is used to record references. The Loc field is set
63 -- to No_Location for a definition entry.
65 subtype Xref_Entry_Number is Int;
67 type Xref_Key is record
68 -- These are the components of Xref_Entry that participate in hash
69 -- lookups.
71 Ent : Entity_Id;
72 -- Entity referenced (E parameter to Generate_Reference)
74 Loc : Source_Ptr;
75 -- Location of reference (Original_Location (Sloc field of N parameter
76 -- to Generate_Reference)). Set to No_Location for the case of a
77 -- defining occurrence.
79 Typ : Character;
80 -- Reference type (Typ param to Generate_Reference)
82 Eun : Unit_Number_Type;
83 -- Unit number corresponding to Ent
85 Lun : Unit_Number_Type;
86 -- Unit number corresponding to Loc. Value is undefined and not
87 -- referenced if Loc is set to No_Location.
89 -- The following components are only used for SPARK cross-references
91 Ref_Scope : Entity_Id;
92 -- Entity of the closest subprogram or package enclosing the reference
94 Ent_Scope : Entity_Id;
95 -- Entity of the closest subprogram or package enclosing the definition,
96 -- which should be located in the same file as the definition itself.
97 end record;
99 type Xref_Entry is record
100 Key : Xref_Key;
102 Ent_Scope_File : Unit_Number_Type;
103 -- File for entity Ent_Scope
105 Def : Source_Ptr;
106 -- Original source location for entity being referenced. Note that these
107 -- values are used only during the output process, they are not set when
108 -- the entries are originally built. This is because private entities
109 -- can be swapped when the initial call is made.
111 HTable_Next : Xref_Entry_Number;
112 -- For use only by Static_HTable
113 end record;
115 package Xrefs is new Table.Table (
116 Table_Component_Type => Xref_Entry,
117 Table_Index_Type => Xref_Entry_Number,
118 Table_Low_Bound => 1,
119 Table_Initial => Alloc.Xrefs_Initial,
120 Table_Increment => Alloc.Xrefs_Increment,
121 Table_Name => "Xrefs");
123 --------------
124 -- Xref_Set --
125 --------------
127 -- We keep a set of xref entries, in order to avoid inserting duplicate
128 -- entries into the above Xrefs table. An entry is in Xref_Set if and only
129 -- if it is in Xrefs.
131 Num_Buckets : constant := 2**16;
133 subtype Header_Num is Integer range 0 .. Num_Buckets - 1;
134 type Null_Type is null record;
135 pragma Unreferenced (Null_Type);
137 function Hash (F : Xref_Entry_Number) return Header_Num;
139 function Equal (F1, F2 : Xref_Entry_Number) return Boolean;
141 procedure HT_Set_Next (E : Xref_Entry_Number; Next : Xref_Entry_Number);
143 function HT_Next (E : Xref_Entry_Number) return Xref_Entry_Number;
145 function Get_Key (E : Xref_Entry_Number) return Xref_Entry_Number;
147 pragma Inline (Hash, Equal, HT_Set_Next, HT_Next, Get_Key);
149 package Xref_Set is new GNAT.HTable.Static_HTable (
150 Header_Num,
151 Element => Xref_Entry,
152 Elmt_Ptr => Xref_Entry_Number,
153 Null_Ptr => 0,
154 Set_Next => HT_Set_Next,
155 Next => HT_Next,
156 Key => Xref_Entry_Number,
157 Get_Key => Get_Key,
158 Hash => Hash,
159 Equal => Equal);
161 -----------------------------
162 -- SPARK Xrefs Information --
163 -----------------------------
165 package body SPARK_Specific is separate;
167 ------------------------
168 -- Local Subprograms --
169 ------------------------
171 procedure Add_Entry (Key : Xref_Key; Ent_Scope_File : Unit_Number_Type);
172 -- Add an entry to the tables of Xref_Entries, avoiding duplicates
174 procedure Generate_Prim_Op_References (Typ : Entity_Id);
175 -- For a tagged type, generate implicit references to its primitive
176 -- operations, for source navigation. This is done right before emitting
177 -- cross-reference information rather than at the freeze point of the type
178 -- in order to handle late bodies that are primitive operations.
180 function Lt (T1, T2 : Xref_Entry) return Boolean;
181 -- Order cross-references
183 ---------------
184 -- Add_Entry --
185 ---------------
187 procedure Add_Entry (Key : Xref_Key; Ent_Scope_File : Unit_Number_Type) is
188 begin
189 Xrefs.Increment_Last; -- tentative
190 Xrefs.Table (Xrefs.Last).Key := Key;
192 -- Set the entry in Xref_Set, and if newly set, keep the above
193 -- tentative increment.
195 if Xref_Set.Set_If_Not_Present (Xrefs.Last) then
196 Xrefs.Table (Xrefs.Last).Ent_Scope_File := Ent_Scope_File;
197 -- Leave Def and HTable_Next uninitialized
199 Set_Has_Xref_Entry (Key.Ent);
201 -- It was already in Xref_Set, so throw away the tentatively-added entry
203 else
204 Xrefs.Decrement_Last;
205 end if;
206 end Add_Entry;
208 -----------
209 -- Equal --
210 -----------
212 function Equal (F1, F2 : Xref_Entry_Number) return Boolean is
213 Result : constant Boolean :=
214 Xrefs.Table (F1).Key = Xrefs.Table (F2).Key;
215 begin
216 return Result;
217 end Equal;
219 -------------------------
220 -- Generate_Definition --
221 -------------------------
223 procedure Generate_Definition (E : Entity_Id) is
224 begin
225 pragma Assert (Nkind (E) in N_Entity);
227 -- Note that we do not test Xref_Entity_Letters here. It is too early
228 -- to do so, since we are often called before the entity is fully
229 -- constructed, so that the Ekind is still E_Void.
231 if Opt.Xref_Active
233 -- Definition must come from source
235 -- We make an exception for subprogram child units that have no spec.
236 -- For these we generate a subprogram declaration for library use,
237 -- and the corresponding entity does not come from source.
238 -- Nevertheless, all references will be attached to it and we have
239 -- to treat is as coming from user code.
241 and then (Comes_From_Source (E) or else Is_Child_Unit (E))
243 -- And must have a reasonable source location that is not
244 -- within an instance (all entities in instances are ignored)
246 and then Sloc (E) > No_Location
247 and then Instantiation_Location (Sloc (E)) = No_Location
249 -- And must be a non-internal name from the main source unit
251 and then In_Extended_Main_Source_Unit (E)
252 and then not Is_Internal_Name (Chars (E))
253 then
254 Add_Entry
255 ((Ent => E,
256 Loc => No_Location,
257 Typ => ' ',
258 Eun => Get_Source_Unit (Original_Location (Sloc (E))),
259 Lun => No_Unit,
260 Ref_Scope => Empty,
261 Ent_Scope => Empty),
262 Ent_Scope_File => No_Unit);
264 if In_Inlined_Body then
265 Set_Referenced (E);
266 end if;
267 end if;
268 end Generate_Definition;
270 ---------------------------------
271 -- Generate_Operator_Reference --
272 ---------------------------------
274 procedure Generate_Operator_Reference
275 (N : Node_Id;
276 T : Entity_Id)
278 begin
279 if not In_Extended_Main_Source_Unit (N) then
280 return;
281 end if;
283 -- If the operator is not a Standard operator, then we generate a real
284 -- reference to the user defined operator.
286 if Sloc (Entity (N)) /= Standard_Location then
287 Generate_Reference (Entity (N), N);
289 -- A reference to an implicit inequality operator is also a reference
290 -- to the user-defined equality.
292 if Nkind (N) = N_Op_Ne
293 and then not Comes_From_Source (Entity (N))
294 and then Present (Corresponding_Equality (Entity (N)))
295 then
296 Generate_Reference (Corresponding_Equality (Entity (N)), N);
297 end if;
299 -- For the case of Standard operators, we mark the result type as
300 -- referenced. This ensures that in the case where we are using a
301 -- derived operator, we mark an entity of the unit that implicitly
302 -- defines this operator as used. Otherwise we may think that no entity
303 -- of the unit is used. The actual entity marked as referenced is the
304 -- first subtype, which is the relevant user defined entity.
306 -- Note: we only do this for operators that come from source. The
307 -- generated code sometimes reaches for entities that do not need to be
308 -- explicitly visible (for example, when we expand the code for
309 -- comparing two record objects, the fields of the record may not be
310 -- visible).
312 elsif Comes_From_Source (N) then
313 Set_Referenced (First_Subtype (T));
314 end if;
315 end Generate_Operator_Reference;
317 ---------------------------------
318 -- Generate_Prim_Op_References --
319 ---------------------------------
321 procedure Generate_Prim_Op_References (Typ : Entity_Id) is
322 Base_T : Entity_Id;
323 Prim : Elmt_Id;
324 Prim_List : Elist_Id;
326 begin
327 -- Handle subtypes of synchronized types
329 if Ekind (Typ) = E_Protected_Subtype
330 or else Ekind (Typ) = E_Task_Subtype
331 then
332 Base_T := Etype (Typ);
333 else
334 Base_T := Typ;
335 end if;
337 -- References to primitive operations are only relevant for tagged types
339 if not Is_Tagged_Type (Base_T)
340 or else Is_Class_Wide_Type (Base_T)
341 then
342 return;
343 end if;
345 -- Ada 2005 (AI-345): For synchronized types generate reference to the
346 -- wrapper that allow us to dispatch calls through their implemented
347 -- abstract interface types.
349 -- The check for Present here is to protect against previously reported
350 -- critical errors.
352 Prim_List := Primitive_Operations (Base_T);
354 if No (Prim_List) then
355 return;
356 end if;
358 Prim := First_Elmt (Prim_List);
359 while Present (Prim) loop
361 -- If the operation is derived, get the original for cross-reference
362 -- reference purposes (it is the original for which we want the xref
363 -- and for which the comes_from_source test must be performed).
365 Generate_Reference
366 (Typ, Ultimate_Alias (Node (Prim)), 'p', Set_Ref => False);
367 Next_Elmt (Prim);
368 end loop;
369 end Generate_Prim_Op_References;
371 ------------------------
372 -- Generate_Reference --
373 ------------------------
375 procedure Generate_Reference
376 (E : Entity_Id;
377 N : Node_Id;
378 Typ : Character := 'r';
379 Set_Ref : Boolean := True;
380 Force : Boolean := False)
382 Actual_Typ : Character := Typ;
383 Call : Node_Id;
384 Def : Source_Ptr;
385 Ent : Entity_Id;
386 Ent_Scope : Entity_Id;
387 Formal : Entity_Id;
388 Kind : Entity_Kind;
389 Nod : Node_Id;
390 Ref : Source_Ptr;
391 Ref_Scope : Entity_Id;
393 function Get_Through_Renamings (E : Entity_Id) return Entity_Id;
394 -- Get the enclosing entity through renamings, which may come from
395 -- source or from the translation of generic instantiations.
397 function OK_To_Set_Referenced return Boolean;
398 -- Returns True if the Referenced flag can be set. There are a few
399 -- exceptions where we do not want to set this flag, see body for
400 -- details of these exceptional cases.
402 ---------------------------
403 -- Get_Through_Renamings --
404 ---------------------------
406 function Get_Through_Renamings (E : Entity_Id) return Entity_Id is
407 begin
408 case Ekind (E) is
410 -- For subprograms we just need to check once if they are have a
411 -- Renamed_Entity, because Renamed_Entity is set transitively.
413 when Subprogram_Kind =>
414 declare
415 Renamed : constant Entity_Id := Renamed_Entity (E);
417 begin
418 if Present (Renamed) then
419 return Renamed;
420 else
421 return E;
422 end if;
423 end;
425 -- For objects we need to repeatedly call Renamed_Object, because
426 -- it is not transitive.
428 when Object_Kind =>
429 declare
430 Obj : Entity_Id := E;
432 begin
433 loop
434 pragma Assert (Present (Obj));
436 declare
437 Renamed : constant Entity_Id := Renamed_Object (Obj);
439 begin
440 if Present (Renamed) then
441 Obj := Get_Enclosing_Object (Renamed);
443 -- The renamed expression denotes a non-object,
444 -- e.g. function call, slicing of a function call,
445 -- pointer dereference, etc.
447 if No (Obj)
448 or else Ekind (Obj) = E_Enumeration_Literal
449 then
450 return Empty;
451 end if;
452 else
453 return Obj;
454 end if;
455 end;
456 end loop;
457 end;
459 when others =>
460 return E;
462 end case;
463 end Get_Through_Renamings;
465 ---------------------------
466 -- OK_To_Set_Referenced --
467 ---------------------------
469 function OK_To_Set_Referenced return Boolean is
470 P : Node_Id;
472 begin
473 -- A reference from a pragma Unreferenced or pragma Unmodified or
474 -- pragma Warnings does not cause the Referenced flag to be set.
475 -- This avoids silly warnings about things being referenced and
476 -- not assigned when the only reference is from the pragma.
478 if Nkind (N) = N_Identifier then
479 P := Parent (N);
481 if Nkind (P) = N_Pragma_Argument_Association then
482 P := Parent (P);
484 if Nkind (P) = N_Pragma then
485 if Pragma_Name_Unmapped (P) in Name_Warnings
486 | Name_Unmodified
487 | Name_Unreferenced
488 then
489 return False;
490 end if;
491 end if;
493 -- A reference to a formal in a named parameter association does
494 -- not make the formal referenced. Formals that are unused in the
495 -- subprogram body are properly flagged as such, even if calls
496 -- elsewhere use named notation.
498 elsif Nkind (P) = N_Parameter_Association
499 and then N = Selector_Name (P)
500 then
501 return False;
502 end if;
503 end if;
505 return True;
506 end OK_To_Set_Referenced;
508 -- Start of processing for Generate_Reference
510 begin
511 -- If Get_Ignore_Errors, then we are in Preanalyze_Without_Errors, and
512 -- we should not record cross references, because that will cause
513 -- duplicates when we call Analyze.
515 if Get_Ignore_Errors then
516 return;
517 end if;
519 -- May happen in case of severe errors
521 if Nkind (E) not in N_Entity then
522 return;
523 end if;
525 Find_Actual (N, Formal, Call);
527 if Present (Formal) then
528 Kind := Ekind (Formal);
529 else
530 Kind := E_Void;
531 end if;
533 -- Check for obsolescent reference to package ASCII. GNAT treats this
534 -- element of annex J specially since in practice, programs make a lot
535 -- of use of this feature, so we don't include it in the set of features
536 -- diagnosed when Warn_On_Obsolescent_Features mode is set. However we
537 -- are required to note it as a violation of the RM defined restriction.
539 if E = Standard_ASCII then
540 Check_Restriction (No_Obsolescent_Features, N);
541 end if;
543 -- Check for reference to entity marked with Is_Obsolescent
545 -- Note that we always allow obsolescent references in the compiler
546 -- itself and the run time, since we assume that we know what we are
547 -- doing in such cases. For example the calls in Ada.Characters.Handling
548 -- to its own obsolescent subprograms are just fine.
550 -- In any case we only generate warnings if we are in the extended main
551 -- source unit, and the entity itself is not in the extended main source
552 -- unit, since we assume the source unit itself knows what is going on
553 -- (and for sure we do not want silly warnings, e.g. on the end line of
554 -- an obsolescent procedure body).
556 if Is_Obsolescent (E)
557 and then not GNAT_Mode
558 and then not In_Extended_Main_Source_Unit (E)
559 and then In_Extended_Main_Source_Unit (N)
560 then
561 Check_Restriction (No_Obsolescent_Features, N);
563 if Warn_On_Obsolescent_Feature then
564 Output_Obsolescent_Entity_Warnings (N, E);
565 end if;
566 end if;
568 -- Warn if reference to Ada 2005 entity not in Ada 2005 mode. We only
569 -- detect real explicit references (modifications and references).
571 if Comes_From_Source (N)
572 and then Is_Ada_2005_Only (E)
573 and then Ada_Version < Ada_2005
574 and then Warn_On_Ada_2005_Compatibility
575 and then (Typ = 'm' or else Typ = 'r' or else Typ = 's')
576 then
577 Error_Msg_NE ("& is only defined in Ada 2005?y?", N, E);
578 end if;
580 -- Warn if reference to Ada 2012 entity not in Ada 2012 mode. We only
581 -- detect real explicit references (modifications and references).
583 if Comes_From_Source (N)
584 and then Is_Ada_2012_Only (E)
585 and then Ada_Version < Ada_2012
586 and then Warn_On_Ada_2012_Compatibility
587 and then (Typ = 'm' or else Typ = 'r')
588 then
589 Error_Msg_NE ("& is only defined in Ada 2012?y?", N, E);
590 end if;
592 -- Warn if reference to Ada 2022 entity not in Ada 2022 mode. We only
593 -- detect real explicit references (modifications and references).
595 if Comes_From_Source (N)
596 and then Is_Ada_2022_Only (E)
597 and then not Is_Subprogram (E)
598 and then Ada_Version < Ada_2022
599 and then Warn_On_Ada_2022_Compatibility
600 and then (Typ = 'm' or else Typ = 'r')
601 then
602 Error_Msg_NE ("& is only defined in Ada 2022?y?", N, E);
604 -- Error on static and dispatching calls to Ada 2022 subprograms that
605 -- require overriding if we are not in Ada 2022 mode (since overriding
606 -- was skipped); warn if the subprogram does not require overriding.
608 elsif Comes_From_Source (N)
609 and then Is_Ada_2022_Only (E)
610 and then Ada_Version < Ada_2022
611 and then Is_Subprogram (E)
612 and then (Typ = 'r' or else Typ = 's' or else Typ = 'R')
613 then
614 if Requires_Overriding (E) then
615 Error_Msg_NE
616 ("& is only defined in Ada 2022 and requires overriding", N, E);
618 elsif Warn_On_Ada_2022_Compatibility then
619 Error_Msg_NE ("& is only defined in Ada 2022?y?", N, E);
620 end if;
621 end if;
623 -- Never collect references if not in main source unit. However, we omit
624 -- this test if Typ is 'e' or 'k', since these entries are structural,
625 -- and it is useful to have them in units that reference packages as
626 -- well as units that define packages. We also omit the test for the
627 -- case of 'p' since we want to include inherited primitive operations
628 -- from other packages.
630 -- We also omit this test is this is a body reference for a subprogram
631 -- instantiation. In this case the reference is to the generic body,
632 -- which clearly need not be in the main unit containing the instance.
633 -- For the same reason we accept an implicit reference generated for
634 -- a default in an instance.
636 -- We also set the referenced flag in a generic package that is not in
637 -- the main source unit, when the object is of a formal private type,
638 -- to warn in the instance if the corresponding type is not a fully
639 -- initialized type.
641 if not In_Extended_Main_Source_Unit (N) then
642 if Typ = 'e' or else
643 Typ = 'I' or else
644 Typ = 'p' or else
645 Typ = 'i' or else
646 Typ = 'k'
647 or else (Typ = 'b' and then Is_Generic_Instance (E))
649 -- Allow the generation of references to reads, writes and calls
650 -- in SPARK mode when the related context comes from an instance.
652 or else
653 (GNATprove_Mode
654 and then In_Extended_Main_Code_Unit (N)
655 and then (Typ = 'm' or else Typ = 'r' or else Typ = 's'))
656 then
657 null;
659 elsif In_Instance_Body
660 and then In_Extended_Main_Code_Unit (N)
661 and then Is_Generic_Type (Etype (E))
662 then
663 Set_Referenced (E);
664 return;
666 elsif Inside_A_Generic
667 and then Is_Object (E)
668 and then Is_Generic_Type (Etype (E))
669 then
670 Set_Referenced (E);
671 return;
673 else
674 return;
675 end if;
676 end if;
678 -- For reference type p, the entity must be in main source unit
680 if Typ = 'p' and then not In_Extended_Main_Source_Unit (E) then
681 return;
682 end if;
684 -- Unless the reference is forced, we ignore references where the
685 -- reference itself does not come from source.
687 if not Force and then not Comes_From_Source (N) then
688 return;
689 end if;
691 -- Deal with setting entity as referenced, unless suppressed. Note that
692 -- we still do Set_Referenced on entities that do not come from source.
693 -- This situation arises when we have a source reference to a derived
694 -- operation, where the derived operation itself does not come from
695 -- source, but we still want to mark it as referenced, since we really
696 -- are referencing an entity in the corresponding package (this avoids
697 -- wrong complaints that the package contains no referenced entities).
699 if Set_Ref then
701 -- When E itself is an IN OUT parameter mark it referenced
703 if Is_Assignable (E)
704 and then Ekind (E) = E_In_Out_Parameter
705 and then Known_To_Be_Assigned (N)
706 then
707 Set_Referenced (E);
709 -- For the case where the entity is on the left hand side of an
710 -- assignment statement, we do nothing here.
712 -- The processing for Analyze_Assignment_Statement will set the
713 -- Referenced_As_LHS flag.
715 elsif Is_Assignable (E)
716 and then Known_To_Be_Assigned (N, Only_LHS => True)
717 then
718 null;
720 -- For objects that are renamings, just set as simply referenced.
721 -- We do not try to do assignment type tracking in this case.
723 elsif Is_Assignable (E)
724 and then Present (Renamed_Object (E))
725 then
726 Set_Referenced (E);
728 -- Check for a reference in a pragma that should not count as a
729 -- making the variable referenced for warning purposes.
731 elsif Is_Non_Significant_Pragma_Reference (N) then
732 null;
734 -- A reference in an attribute definition clause does not count as a
735 -- reference except for the case of Address. The reason that 'Address
736 -- is an exception is that it creates an alias through which the
737 -- variable may be referenced.
739 elsif Nkind (Parent (N)) = N_Attribute_Definition_Clause
740 and then Chars (Parent (N)) /= Name_Address
741 and then N = Name (Parent (N))
742 then
743 null;
745 -- Constant completion does not count as a reference
747 elsif Typ = 'c'
748 and then Ekind (E) = E_Constant
749 then
750 null;
752 -- Record representation clause does not count as a reference
754 elsif Nkind (N) = N_Identifier
755 and then Nkind (Parent (N)) = N_Record_Representation_Clause
756 then
757 null;
759 -- Discriminants do not need to produce a reference to record type
761 elsif Typ = 'd'
762 and then Nkind (Parent (N)) = N_Discriminant_Specification
763 then
764 null;
766 -- Out parameter case
768 elsif Kind = E_Out_Parameter
769 and then Is_Assignable (E)
770 then
771 -- If warning mode for all out parameters is set, or this is
772 -- the only warning parameter, then we want to mark this for
773 -- later warning logic by setting Referenced_As_Out_Parameter
775 if Warn_On_Modified_As_Out_Parameter (Formal) then
776 Set_Referenced_As_Out_Parameter (E, True);
777 Set_Referenced_As_LHS (E, False);
779 -- For OUT parameter not covered by the above cases, we simply
780 -- regard it as a reference.
782 else
783 Set_Referenced_As_Out_Parameter (E);
784 Set_Referenced (E);
785 end if;
787 -- Special processing for IN OUT parameters, where we have an
788 -- implicit assignment to a simple variable.
790 elsif Kind = E_In_Out_Parameter
791 and then Is_Assignable (E)
792 then
793 -- We count it as a read reference unless we're calling a
794 -- type support subprogram such as deep finalize.
796 if not Is_Entity_Name (Name (Call))
797 or else Get_TSS_Name (Entity (Name (Call))) = TSS_Null
798 then
799 Set_Referenced (E);
800 Set_Last_Assignment (E, Empty);
801 end if;
803 -- We count it as being referenced as an out parameter if the
804 -- option is set to warn on all out parameters, except that we
805 -- have a special exclusion for an intrinsic subprogram, which
806 -- is most likely an instantiation of Unchecked_Deallocation
807 -- which we do not want to consider as an assignment since it
808 -- generates false positives. We also exclude the case of an
809 -- IN OUT parameter if the name of the procedure is Free,
810 -- since we suspect similar semantics.
812 if Warn_On_All_Unread_Out_Parameters
813 and then Is_Entity_Name (Name (Call))
814 and then not Is_Intrinsic_Subprogram (Entity (Name (Call)))
815 and then Chars (Name (Call)) /= Name_Free
816 then
817 Set_Referenced_As_Out_Parameter (E, True);
818 Set_Referenced_As_LHS (E, False);
819 end if;
821 -- Don't count a recursive reference within a subprogram as a
822 -- reference (that allows detection of a recursive subprogram
823 -- whose only references are recursive calls as unreferenced).
825 elsif Is_Subprogram (E)
826 and then E = Nearest_Dynamic_Scope (Current_Scope)
827 then
828 null;
830 -- Any other occurrence counts as referencing the entity
832 elsif OK_To_Set_Referenced then
833 Set_Referenced (E);
835 -- If variable, this is an OK reference after an assignment
836 -- so we can clear the Last_Assignment indication.
838 if Is_Assignable (E) then
839 Set_Last_Assignment (E, Empty);
840 end if;
841 end if;
843 -- Check for pragma Unreferenced given and reference is within
844 -- this source unit (occasion for possible warning to be issued).
845 -- Note that the entity may be marked as unreferenced by pragma
846 -- Unused.
848 if Has_Unreferenced (E)
849 and then In_Same_Extended_Unit (E, N)
850 then
851 -- A reference as a named parameter in a call does not count as a
852 -- violation of pragma Unreferenced for this purpose.
854 if Nkind (N) = N_Identifier
855 and then Nkind (Parent (N)) = N_Parameter_Association
856 and then Selector_Name (Parent (N)) = N
857 then
858 null;
860 -- Neither does a reference to a variable on the left side of
861 -- an assignment or use of an out parameter with warnings for
862 -- unread out parameters specified (via -gnatw.o).
864 -- The reason for treating unread out parameters in a special
865 -- way is so that when pragma Unreferenced is specified on such
866 -- an out parameter we do not want to issue a warning about the
867 -- pragma being unnecessary - because the purpose of the flag
868 -- is to warn about them not being read (e.g. unreferenced)
869 -- after use.
871 elsif (Known_To_Be_Assigned (N, Only_LHS => True)
872 or else (Present (Formal)
873 and then Ekind (Formal) = E_Out_Parameter
874 and then Warn_On_All_Unread_Out_Parameters))
875 and then not (Ekind (E) = E_In_Out_Parameter
876 and then Known_To_Be_Assigned (N))
877 then
878 null;
880 -- Do not consider F'Result as a violation of pragma Unreferenced
881 -- since the attribute acts as an anonymous alias of the function
882 -- result and not as a real reference to the function.
884 elsif Ekind (E) in E_Function | E_Generic_Function
885 and then Is_Entity_Name (N)
886 and then Is_Attribute_Result (Parent (N))
887 then
888 null;
890 -- No warning if the reference is in a call that does not come
891 -- from source (e.g. a call to a controlled type primitive).
893 elsif not Comes_From_Source (Parent (N))
894 and then Nkind (Parent (N)) = N_Procedure_Call_Statement
895 then
896 null;
898 -- For entry formals, we want to place the warning message on the
899 -- corresponding entity in the accept statement. The current scope
900 -- is the body of the accept, so we find the formal whose name
901 -- matches that of the entry formal (there is no link between the
902 -- two entities, and the one in the accept statement is only used
903 -- for conformance checking).
905 elsif Ekind (Scope (E)) = E_Entry then
906 declare
907 BE : Entity_Id;
909 begin
910 BE := First_Entity (Current_Scope);
911 while Present (BE) loop
912 if Chars (BE) = Chars (E) then
913 if Has_Pragma_Unused (E) then
914 Error_Msg_NE -- CODEFIX
915 ("??aspect Unused specified for&!", N, BE);
916 else
917 Error_Msg_NE -- CODEFIX
918 ("??aspect Unreferenced specified for&!", N, BE);
919 end if;
920 exit;
921 end if;
923 Next_Entity (BE);
924 end loop;
925 end;
927 -- Here we issue the warning, since this is a real reference
929 elsif Has_Pragma_Unused (E) then
930 Error_Msg_NE -- CODEFIX
931 ("??aspect Unused specified for&!", N, E);
932 else
933 Error_Msg_NE -- CODEFIX
934 ("??aspect Unreferenced specified for&!", N, E);
935 end if;
936 end if;
938 -- If this is a subprogram instance, mark as well the internal
939 -- subprogram in the wrapper package, which may be a visible
940 -- compilation unit.
942 if Is_Overloadable (E)
943 and then Is_Generic_Instance (E)
944 and then Present (Alias (E))
945 then
946 Set_Referenced (Alias (E));
947 end if;
948 end if;
950 -- Generate reference if all conditions are met:
953 -- Cross referencing must be active
955 Opt.Xref_Active
957 -- The entity must be one for which we collect references
959 and then Xref_Entity_Letters (Ekind (E)) /= ' '
961 -- Both Sloc values must be set to something sensible
963 and then Sloc (E) > No_Location
964 and then Sloc (N) > No_Location
966 -- Ignore references from within an instance. The only exceptions to
967 -- this are default subprograms, for which we generate an implicit
968 -- reference and compilations in SPARK mode.
970 and then
971 (Instantiation_Location (Sloc (N)) = No_Location
972 or else Typ = 'i'
973 or else GNATprove_Mode)
975 -- Ignore dummy references
977 and then Typ /= ' '
978 then
979 if Nkind (N) in N_Identifier
980 | N_Defining_Identifier
981 | N_Defining_Operator_Symbol
982 | N_Operator_Symbol
983 | N_Defining_Character_Literal
984 | N_Op
985 or else (Nkind (N) = N_Character_Literal
986 and then Sloc (Entity (N)) /= Standard_Location)
987 then
988 Nod := N;
990 elsif Nkind (N) in N_Expanded_Name | N_Selected_Component then
991 Nod := Selector_Name (N);
993 else
994 return;
995 end if;
997 -- Normal case of source entity comes from source
999 if Comes_From_Source (E) then
1000 Ent := E;
1002 -- Because a declaration may be generated for a subprogram body
1003 -- without declaration in GNATprove mode, for inlining, some
1004 -- parameters may end up being marked as not coming from source
1005 -- although they are. Take these into account specially.
1007 elsif GNATprove_Mode and then Is_Formal (E) then
1008 Ent := E;
1010 -- Entity does not come from source, but is a derived subprogram and
1011 -- the derived subprogram comes from source (after one or more
1012 -- derivations) in which case the reference is to parent subprogram.
1014 elsif Is_Overloadable (E)
1015 and then Present (Alias (E))
1016 then
1017 Ent := Alias (E);
1018 while not Comes_From_Source (Ent) loop
1019 if No (Alias (Ent)) then
1020 return;
1021 end if;
1023 Ent := Alias (Ent);
1024 end loop;
1026 -- The internally created defining entity for a child subprogram
1027 -- that has no previous spec has valid references.
1029 elsif Is_Overloadable (E)
1030 and then Is_Child_Unit (E)
1031 then
1032 Ent := E;
1034 -- Ditto for the formals of such a subprogram
1036 elsif Is_Overloadable (Scope (E))
1037 and then Is_Child_Unit (Scope (E))
1038 then
1039 Ent := E;
1041 -- Record components of discriminated subtypes or derived types must
1042 -- be treated as references to the original component.
1044 elsif Ekind (E) = E_Component
1045 and then Comes_From_Source (Original_Record_Component (E))
1046 then
1047 Ent := Original_Record_Component (E);
1049 -- If this is an expanded reference to a discriminant, recover the
1050 -- original discriminant, which gets the reference.
1052 elsif Ekind (E) = E_In_Parameter
1053 and then Present (Discriminal_Link (E))
1054 then
1055 Ent := Discriminal_Link (E);
1056 Set_Referenced (Ent);
1058 -- Ignore reference to any other entity that is not from source
1060 else
1061 return;
1062 end if;
1064 -- In SPARK mode, consider the underlying entity renamed instead of
1065 -- the renaming, which is needed to compute a valid set of effects
1066 -- (reads, writes) for the enclosing subprogram.
1068 if GNATprove_Mode then
1069 Ent := Get_Through_Renamings (Ent);
1071 -- If no enclosing object, then it could be a reference to any
1072 -- location not tracked individually, like heap-allocated data.
1073 -- Conservatively approximate this possibility by generating a
1074 -- dereference, and return.
1076 if No (Ent) then
1077 if Actual_Typ = 'w' then
1078 SPARK_Specific.Generate_Dereference (Nod, 'r');
1079 SPARK_Specific.Generate_Dereference (Nod, 'w');
1080 else
1081 SPARK_Specific.Generate_Dereference (Nod, 'r');
1082 end if;
1084 return;
1085 end if;
1086 end if;
1088 -- Record reference to entity
1090 if Actual_Typ = 'p'
1091 and then Is_Subprogram (Nod)
1092 and then Present (Overridden_Operation (Nod))
1093 then
1094 Actual_Typ := 'P';
1095 end if;
1097 -- Comment needed here for special SPARK code ???
1099 if GNATprove_Mode then
1101 -- Ignore references to an entity which is a Part_Of single
1102 -- concurrent object. Ideally we would prefer to add it as a
1103 -- reference to the corresponding concurrent type, but it is quite
1104 -- difficult (as such references are not currently added even for)
1105 -- reads/writes of private protected components) and not worth the
1106 -- effort.
1108 if Ekind (Ent) in E_Abstract_State | E_Constant | E_Variable
1109 and then Present (Encapsulating_State (Ent))
1110 and then Is_Single_Concurrent_Object (Encapsulating_State (Ent))
1111 then
1112 return;
1113 end if;
1115 Ref := Sloc (Nod);
1116 Def := Sloc (Ent);
1118 Ref_Scope :=
1119 SPARK_Specific.Enclosing_Subprogram_Or_Library_Package (Nod);
1120 Ent_Scope :=
1121 SPARK_Specific.Enclosing_Subprogram_Or_Library_Package (Ent);
1123 -- Since we are reaching through renamings in SPARK mode, we may
1124 -- end up with standard constants. Ignore those.
1126 if Sloc (Ent_Scope) <= Standard_Location
1127 or else Def <= Standard_Location
1128 then
1129 return;
1130 end if;
1132 Add_Entry
1133 ((Ent => Ent,
1134 Loc => Ref,
1135 Typ => Actual_Typ,
1136 Eun => Get_Top_Level_Code_Unit (Def),
1137 Lun => Get_Top_Level_Code_Unit (Ref),
1138 Ref_Scope => Ref_Scope,
1139 Ent_Scope => Ent_Scope),
1140 Ent_Scope_File => Get_Top_Level_Code_Unit (Ent));
1142 else
1143 Ref := Original_Location (Sloc (Nod));
1144 Def := Original_Location (Sloc (Ent));
1146 -- If this is an operator symbol, skip the initial quote for
1147 -- navigation purposes. This is not done for the end label,
1148 -- where we want the actual position after the closing quote.
1150 if Typ = 't' then
1151 null;
1153 elsif Nkind (N) = N_Defining_Operator_Symbol
1154 or else Nkind (Nod) = N_Operator_Symbol
1155 then
1156 Ref := Ref + 1;
1157 end if;
1159 Add_Entry
1160 ((Ent => Ent,
1161 Loc => Ref,
1162 Typ => Actual_Typ,
1163 Eun => Get_Source_Unit (Def),
1164 Lun => Get_Source_Unit (Ref),
1165 Ref_Scope => Empty,
1166 Ent_Scope => Empty),
1167 Ent_Scope_File => No_Unit);
1169 -- Generate reference to the first private entity
1171 if Typ = 'e'
1172 and then Comes_From_Source (E)
1173 and then Nkind (Ent) = N_Defining_Identifier
1174 and then (Is_Package_Or_Generic_Package (Ent)
1175 or else Is_Concurrent_Type (Ent))
1176 and then Present (First_Private_Entity (E))
1177 and then In_Extended_Main_Source_Unit (N)
1178 then
1179 -- Handle case in which the full-view and partial-view of the
1180 -- first private entity are swapped.
1182 declare
1183 First_Private : Entity_Id := First_Private_Entity (E);
1185 begin
1186 if Is_Private_Type (First_Private)
1187 and then Present (Full_View (First_Private))
1188 then
1189 First_Private := Full_View (First_Private);
1190 end if;
1192 Add_Entry
1193 ((Ent => Ent,
1194 Loc => Sloc (First_Private),
1195 Typ => 'E',
1196 Eun => Get_Source_Unit (Def),
1197 Lun => Get_Source_Unit (Ref),
1198 Ref_Scope => Empty,
1199 Ent_Scope => Empty),
1200 Ent_Scope_File => No_Unit);
1201 end;
1202 end if;
1203 end if;
1204 end if;
1205 end Generate_Reference;
1207 -----------------------------------
1208 -- Generate_Reference_To_Formals --
1209 -----------------------------------
1211 procedure Generate_Reference_To_Formals (E : Entity_Id) is
1212 Formal : Entity_Id;
1214 begin
1215 if Is_Access_Subprogram_Type (E) then
1216 Formal := First_Formal (Designated_Type (E));
1217 else
1218 Formal := First_Formal (E);
1219 end if;
1221 while Present (Formal) loop
1222 if Ekind (Formal) = E_In_Parameter then
1224 if Nkind (Parameter_Type (Parent (Formal))) = N_Access_Definition
1225 then
1226 Generate_Reference (E, Formal, '^', False);
1227 else
1228 Generate_Reference (E, Formal, '>', False);
1229 end if;
1231 elsif Ekind (Formal) = E_In_Out_Parameter then
1232 Generate_Reference (E, Formal, '=', False);
1234 else
1235 Generate_Reference (E, Formal, '<', False);
1236 end if;
1238 Next_Formal (Formal);
1239 end loop;
1240 end Generate_Reference_To_Formals;
1242 -------------------------------------------
1243 -- Generate_Reference_To_Generic_Formals --
1244 -------------------------------------------
1246 procedure Generate_Reference_To_Generic_Formals (E : Entity_Id) is
1247 Formal : Entity_Id;
1249 begin
1250 Formal := First_Entity (E);
1251 while Present (Formal) loop
1252 if Comes_From_Source (Formal) then
1253 Generate_Reference (E, Formal, 'z', False);
1254 end if;
1256 Next_Entity (Formal);
1257 end loop;
1258 end Generate_Reference_To_Generic_Formals;
1260 -------------
1261 -- Get_Key --
1262 -------------
1264 function Get_Key (E : Xref_Entry_Number) return Xref_Entry_Number is
1265 begin
1266 return E;
1267 end Get_Key;
1269 ----------
1270 -- Hash --
1271 ----------
1273 function Hash (F : Xref_Entry_Number) return Header_Num is
1274 -- It is unlikely to have two references to the same entity at the same
1275 -- source location, so the hash function depends only on the Ent and Loc
1276 -- fields.
1278 XE : Xref_Entry renames Xrefs.Table (F);
1279 type M is mod 2**32;
1281 H : constant M := 3 * M (XE.Key.Ent) + 5 * M (abs XE.Key.Loc);
1282 -- It would be more natural to write:
1284 -- H : constant M := 3 * M'Mod (XE.Key.Ent) + 5 * M'Mod (XE.Key.Loc);
1286 -- But we can't use M'Mod, because it prevents bootstrapping with older
1287 -- compilers. Loc can be negative, so we do "abs" before converting.
1288 -- One day this can be cleaned up ???
1290 begin
1291 return Header_Num (H mod Num_Buckets);
1292 end Hash;
1294 -----------------
1295 -- HT_Set_Next --
1296 -----------------
1298 procedure HT_Set_Next (E : Xref_Entry_Number; Next : Xref_Entry_Number) is
1299 begin
1300 Xrefs.Table (E).HTable_Next := Next;
1301 end HT_Set_Next;
1303 -------------
1304 -- HT_Next --
1305 -------------
1307 function HT_Next (E : Xref_Entry_Number) return Xref_Entry_Number is
1308 begin
1309 return Xrefs.Table (E).HTable_Next;
1310 end HT_Next;
1312 ----------------
1313 -- Initialize --
1314 ----------------
1316 procedure Initialize is
1317 begin
1318 Xrefs.Init;
1319 end Initialize;
1321 --------
1322 -- Lt --
1323 --------
1325 function Lt (T1, T2 : Xref_Entry) return Boolean is
1326 begin
1327 -- First test: if entity is in different unit, sort by unit
1329 if T1.Key.Eun /= T2.Key.Eun then
1330 return Dependency_Num (T1.Key.Eun) < Dependency_Num (T2.Key.Eun);
1332 -- Second test: within same unit, sort by entity Sloc
1334 elsif T1.Def /= T2.Def then
1335 return T1.Def < T2.Def;
1337 -- Third test: sort definitions ahead of references
1339 elsif T1.Key.Loc = No_Location then
1340 return True;
1342 elsif T2.Key.Loc = No_Location then
1343 return False;
1345 -- Fourth test: for same entity, sort by reference location unit
1347 elsif T1.Key.Lun /= T2.Key.Lun then
1348 return Dependency_Num (T1.Key.Lun) < Dependency_Num (T2.Key.Lun);
1350 -- Fifth test: order of location within referencing unit
1352 elsif T1.Key.Loc /= T2.Key.Loc then
1353 return T1.Key.Loc < T2.Key.Loc;
1355 -- Finally, for two locations at the same address, we prefer
1356 -- the one that does NOT have the type 'r' so that a modification
1357 -- or extension takes preference, when there are more than one
1358 -- reference at the same location. As a result, in the case of
1359 -- entities that are in-out actuals, the read reference follows
1360 -- the modify reference.
1362 else
1363 return T2.Key.Typ = 'r';
1364 end if;
1365 end Lt;
1367 -----------------------
1368 -- Output_References --
1369 -----------------------
1371 procedure Output_References is
1373 procedure Get_Type_Reference
1374 (Ent : Entity_Id;
1375 Tref : out Entity_Id;
1376 Left : out Character;
1377 Right : out Character);
1378 -- Given an Entity_Id Ent, determines whether a type reference is
1379 -- required. If so, Tref is set to the entity for the type reference
1380 -- and Left and Right are set to the left/right brackets to be output
1381 -- for the reference. If no type reference is required, then Tref is
1382 -- set to Empty, and Left/Right are set to space.
1384 procedure Output_Import_Export_Info (Ent : Entity_Id);
1385 -- Output language and external name information for an interfaced
1386 -- entity, using the format <language, external_name>.
1388 ------------------------
1389 -- Get_Type_Reference --
1390 ------------------------
1392 procedure Get_Type_Reference
1393 (Ent : Entity_Id;
1394 Tref : out Entity_Id;
1395 Left : out Character;
1396 Right : out Character)
1398 Sav : Entity_Id;
1400 begin
1401 -- See if we have a type reference
1403 Tref := Ent;
1404 Left := '{';
1405 Right := '}';
1407 loop
1408 Sav := Tref;
1410 -- Processing for types
1412 if Is_Type (Tref) then
1414 -- Case of base type
1416 if Base_Type (Tref) = Tref then
1418 -- If derived, then get first subtype
1420 if Tref /= Etype (Tref) then
1421 Tref := First_Subtype (Etype (Tref));
1423 -- Set brackets for derived type, but don't override
1424 -- pointer case since the fact that something is a
1425 -- pointer is more important.
1427 if Left /= '(' then
1428 Left := '<';
1429 Right := '>';
1430 end if;
1432 -- If the completion of a private type is itself a derived
1433 -- type, we need the parent of the full view.
1435 elsif Is_Private_Type (Tref)
1436 and then Present (Full_View (Tref))
1437 and then Etype (Full_View (Tref)) /= Full_View (Tref)
1438 then
1439 Tref := Etype (Full_View (Tref));
1441 if Left /= '(' then
1442 Left := '<';
1443 Right := '>';
1444 end if;
1446 -- If non-derived pointer, get directly designated type.
1447 -- If the type has a full view, all references are on the
1448 -- partial view that is seen first.
1450 elsif Is_Access_Type (Tref) then
1451 Tref := Directly_Designated_Type (Tref);
1452 Left := '(';
1453 Right := ')';
1455 elsif Is_Private_Type (Tref)
1456 and then Present (Full_View (Tref))
1457 then
1458 if Is_Access_Type (Full_View (Tref)) then
1459 Tref := Directly_Designated_Type (Full_View (Tref));
1460 Left := '(';
1461 Right := ')';
1463 -- If the full view is an array type, we also retrieve
1464 -- the corresponding component type, because the ali
1465 -- entry already indicates that this is an array.
1467 elsif Is_Array_Type (Full_View (Tref)) then
1468 Tref := Component_Type (Full_View (Tref));
1469 Left := '(';
1470 Right := ')';
1471 end if;
1473 -- If non-derived array, get component type. Skip component
1474 -- type for case of String or Wide_String, saves worthwhile
1475 -- space.
1477 elsif Is_Array_Type (Tref)
1478 and then Tref /= Standard_String
1479 and then Tref /= Standard_Wide_String
1480 then
1481 Tref := Component_Type (Tref);
1482 Left := '(';
1483 Right := ')';
1485 -- For other non-derived base types, nothing
1487 else
1488 exit;
1489 end if;
1491 -- For a subtype, go to ancestor subtype
1493 else
1494 Tref := Ancestor_Subtype (Tref);
1496 -- If no ancestor subtype, go to base type
1498 if No (Tref) then
1499 Tref := Base_Type (Sav);
1500 end if;
1501 end if;
1503 -- For objects, functions, enum literals, just get type from
1504 -- Etype field.
1506 elsif Is_Object (Tref)
1507 or else Ekind (Tref) = E_Enumeration_Literal
1508 or else Ekind (Tref) = E_Function
1509 or else Ekind (Tref) = E_Operator
1510 then
1511 Tref := Etype (Tref);
1513 -- Another special case: an object of a classwide type
1514 -- initialized with a tag-indeterminate call gets a subtype
1515 -- of the classwide type during expansion. See if the original
1516 -- type in the declaration is named, and return it instead
1517 -- of going to the root type. The expression may be a class-
1518 -- wide function call whose result is on the secondary stack,
1519 -- which forces the declaration to be rewritten as a renaming,
1520 -- so examine the source declaration.
1522 if Ekind (Tref) = E_Class_Wide_Subtype then
1523 declare
1524 Decl : constant Node_Id := Original_Node (Parent (Ent));
1525 begin
1526 if Nkind (Decl) = N_Object_Declaration
1527 and then Is_Entity_Name
1528 (Original_Node (Object_Definition (Decl)))
1529 then
1530 Tref :=
1531 Entity (Original_Node (Object_Definition (Decl)));
1532 end if;
1533 end;
1535 -- For a function that returns a class-wide type, Tref is
1536 -- already correct.
1538 elsif Is_Overloadable (Ent)
1539 and then Is_Class_Wide_Type (Tref)
1540 then
1541 return;
1542 end if;
1544 -- For anything else, exit
1546 else
1547 exit;
1548 end if;
1550 -- Exit if no type reference, or we are stuck in some loop trying
1551 -- to find the type reference, or if the type is standard void
1552 -- type (the latter is an implementation artifact that should not
1553 -- show up in the generated cross-references).
1555 exit when No (Tref)
1556 or else Tref = Sav
1557 or else Tref = Standard_Void_Type;
1559 -- If we have a usable type reference, return, otherwise keep
1560 -- looking for something useful (we are looking for something
1561 -- that either comes from source or standard)
1563 if Sloc (Tref) = Standard_Location
1564 or else Comes_From_Source (Tref)
1565 then
1566 -- If the reference is a subtype created for a generic actual,
1567 -- go actual directly, the inner subtype is not user visible.
1569 if Nkind (Parent (Tref)) = N_Subtype_Declaration
1570 and then not Comes_From_Source (Parent (Tref))
1571 and then
1572 (Is_Wrapper_Package (Scope (Tref))
1573 or else Is_Generic_Instance (Scope (Tref)))
1574 then
1575 Tref := First_Subtype (Base_Type (Tref));
1576 end if;
1578 return;
1579 end if;
1580 end loop;
1582 -- If we fall through the loop, no type reference
1584 Tref := Empty;
1585 Left := ' ';
1586 Right := ' ';
1587 end Get_Type_Reference;
1589 -------------------------------
1590 -- Output_Import_Export_Info --
1591 -------------------------------
1593 procedure Output_Import_Export_Info (Ent : Entity_Id) is
1594 Language_Name : Name_Id;
1595 Conv : constant Convention_Id := Convention (Ent);
1597 begin
1598 -- Generate language name from convention
1600 if Conv = Convention_C or else Conv in Convention_C_Variadic then
1601 Language_Name := Name_C;
1603 elsif Conv = Convention_CPP then
1604 Language_Name := Name_CPP;
1606 elsif Conv = Convention_Ada then
1607 Language_Name := Name_Ada;
1609 else
1610 -- For the moment we ignore all other cases ???
1612 return;
1613 end if;
1615 Write_Info_Char ('<');
1616 Get_Unqualified_Name_String (Language_Name);
1618 for J in 1 .. Name_Len loop
1619 Write_Info_Char (Name_Buffer (J));
1620 end loop;
1622 if Present (Interface_Name (Ent)) then
1623 Write_Info_Char (',');
1624 String_To_Name_Buffer (Strval (Interface_Name (Ent)));
1626 for J in 1 .. Name_Len loop
1627 Write_Info_Char (Name_Buffer (J));
1628 end loop;
1629 end if;
1631 Write_Info_Char ('>');
1632 end Output_Import_Export_Info;
1634 -- Start of processing for Output_References
1636 begin
1637 -- First we add references to the primitive operations of tagged types
1638 -- declared in the main unit.
1640 Handle_Prim_Ops : declare
1641 Ent : Entity_Id;
1643 begin
1644 for J in 1 .. Xrefs.Last loop
1645 Ent := Xrefs.Table (J).Key.Ent;
1647 if Is_Type (Ent)
1648 and then Is_Tagged_Type (Ent)
1649 and then Is_Base_Type (Ent)
1650 and then In_Extended_Main_Source_Unit (Ent)
1651 then
1652 Generate_Prim_Op_References (Ent);
1653 end if;
1654 end loop;
1655 end Handle_Prim_Ops;
1657 -- Before we go ahead and output the references we have a problem
1658 -- that needs dealing with. So far we have captured things that are
1659 -- definitely referenced by the main unit, or defined in the main
1660 -- unit. That's because we don't want to clutter up the ali file
1661 -- for this unit with definition lines for entities in other units
1662 -- that are not referenced.
1664 -- But there is a glitch. We may reference an entity in another unit,
1665 -- and it may have a type reference to an entity that is not directly
1666 -- referenced in the main unit, which may mean that there is no xref
1667 -- entry for this entity yet in the list of references.
1669 -- If we don't do something about this, we will end with an orphan type
1670 -- reference, i.e. it will point to an entity that does not appear
1671 -- within the generated references in the ali file. That is not good for
1672 -- tools using the xref information.
1674 -- To fix this, we go through the references adding definition entries
1675 -- for any unreferenced entities that can be referenced in a type
1676 -- reference. There is a recursion problem here, and that is dealt with
1677 -- by making sure that this traversal also traverses any entries that
1678 -- get added by the traversal.
1680 Handle_Orphan_Type_References : declare
1681 J : Nat;
1682 Tref : Entity_Id;
1683 Ent : Entity_Id;
1685 L, R : Character;
1686 pragma Warnings (Off, L);
1687 pragma Warnings (Off, R);
1689 procedure New_Entry (E : Entity_Id);
1690 -- Make an additional entry into the Xref table for a type entity
1691 -- that is related to the current entity (parent, type ancestor,
1692 -- progenitor, etc.).
1694 ----------------
1695 -- New_Entry --
1696 ----------------
1698 procedure New_Entry (E : Entity_Id) is
1699 begin
1700 pragma Assert (Present (E));
1702 if not Has_Xref_Entry (Implementation_Base_Type (E))
1703 and then Sloc (E) > No_Location
1704 then
1705 Add_Entry
1706 ((Ent => E,
1707 Loc => No_Location,
1708 Typ => Character'First,
1709 Eun => Get_Source_Unit (Original_Location (Sloc (E))),
1710 Lun => No_Unit,
1711 Ref_Scope => Empty,
1712 Ent_Scope => Empty),
1713 Ent_Scope_File => No_Unit);
1714 end if;
1715 end New_Entry;
1717 -- Start of processing for Handle_Orphan_Type_References
1719 begin
1720 -- Note that this is not a for loop for a very good reason. The
1721 -- processing of items in the table can add new items to the table,
1722 -- and they must be processed as well.
1724 J := 1;
1725 while J <= Xrefs.Last loop
1726 Ent := Xrefs.Table (J).Key.Ent;
1728 -- Do not generate reference information for an ignored Ghost
1729 -- entity because neither the entity nor its references will
1730 -- appear in the final tree.
1732 if Is_Ignored_Ghost_Entity (Ent) then
1733 goto Orphan_Continue;
1734 end if;
1736 Get_Type_Reference (Ent, Tref, L, R);
1738 if Present (Tref)
1739 and then not Has_Xref_Entry (Tref)
1740 and then Sloc (Tref) > No_Location
1741 then
1742 New_Entry (Tref);
1744 if Is_Record_Type (Ent)
1745 and then Present (Interfaces (Ent))
1746 then
1747 -- Add an entry for each one of the given interfaces
1748 -- implemented by type Ent.
1750 declare
1751 Elmt : Elmt_Id := First_Elmt (Interfaces (Ent));
1752 begin
1753 while Present (Elmt) loop
1754 New_Entry (Node (Elmt));
1755 Next_Elmt (Elmt);
1756 end loop;
1757 end;
1758 end if;
1759 end if;
1761 -- Collect inherited primitive operations that may be declared in
1762 -- another unit and have no visible reference in the current one.
1764 if Is_Type (Ent)
1765 and then Is_Tagged_Type (Ent)
1766 and then Is_Derived_Type (Ent)
1767 and then Is_Base_Type (Ent)
1768 and then In_Extended_Main_Source_Unit (Ent)
1769 then
1770 declare
1771 Op_List : constant Elist_Id := Primitive_Operations (Ent);
1772 Op : Elmt_Id;
1773 Prim : Entity_Id;
1775 function Parent_Op (E : Entity_Id) return Entity_Id;
1776 -- Find original operation, which may be inherited through
1777 -- several derivations.
1779 function Parent_Op (E : Entity_Id) return Entity_Id is
1780 Orig_Op : constant Entity_Id := Alias (E);
1782 begin
1783 if No (Orig_Op) then
1784 return Empty;
1786 elsif not Comes_From_Source (E)
1787 and then not Has_Xref_Entry (Orig_Op)
1788 and then Comes_From_Source (Orig_Op)
1789 then
1790 return Orig_Op;
1791 else
1792 return Parent_Op (Orig_Op);
1793 end if;
1794 end Parent_Op;
1796 begin
1797 Op := First_Elmt (Op_List);
1798 while Present (Op) loop
1799 Prim := Parent_Op (Node (Op));
1801 if Present (Prim) then
1802 Add_Entry
1803 ((Ent => Prim,
1804 Loc => No_Location,
1805 Typ => Character'First,
1806 Eun => Get_Source_Unit (Sloc (Prim)),
1807 Lun => No_Unit,
1808 Ref_Scope => Empty,
1809 Ent_Scope => Empty),
1810 Ent_Scope_File => No_Unit);
1811 end if;
1813 Next_Elmt (Op);
1814 end loop;
1815 end;
1816 end if;
1818 <<Orphan_Continue>>
1819 J := J + 1;
1820 end loop;
1821 end Handle_Orphan_Type_References;
1823 -- Now we have all the references, including those for any embedded type
1824 -- references, so we can sort them, and output them.
1826 Output_Refs : declare
1827 Nrefs : constant Nat := Xrefs.Last;
1828 -- Number of references in table
1830 Rnums : array (0 .. Nrefs) of Nat;
1831 -- This array contains numbers of references in the Xrefs table.
1832 -- This list is sorted in output order. The extra 0'th entry is
1833 -- convenient for the call to sort. When we sort the table, we
1834 -- move the entries in Rnums around, but we do not move the
1835 -- original table entries.
1837 Curxu : Unit_Number_Type;
1838 -- Current xref unit
1840 Curru : Unit_Number_Type;
1841 -- Current reference unit for one entity
1843 Curent : Entity_Id;
1844 -- Current entity
1846 Curnam : String (1 .. Name_Buffer'Length);
1847 Curlen : Natural;
1848 -- Simple name and length of current entity
1850 Curdef : Source_Ptr;
1851 -- Original source location for current entity
1853 Crloc : Source_Ptr;
1854 -- Current reference location
1856 Ctyp : Character;
1857 -- Entity type character
1859 Prevt : Character;
1860 -- reference kind of previous reference
1862 Tref : Entity_Id;
1863 -- Type reference
1865 Rref : Node_Id;
1866 -- Renaming reference
1868 Trunit : Unit_Number_Type;
1869 -- Unit number for type reference
1871 function Lt (Op1, Op2 : Natural) return Boolean;
1872 -- Comparison function for Sort call
1874 function Name_Change (X : Entity_Id) return Boolean;
1875 -- Determines if entity X has a different simple name from Curent
1877 procedure Move (From : Natural; To : Natural);
1878 -- Move procedure for Sort call
1880 package Sorting is new GNAT.Heap_Sort_G (Move, Lt);
1882 --------
1883 -- Lt --
1884 --------
1886 function Lt (Op1, Op2 : Natural) return Boolean is
1887 T1 : Xref_Entry renames Xrefs.Table (Rnums (Nat (Op1)));
1888 T2 : Xref_Entry renames Xrefs.Table (Rnums (Nat (Op2)));
1890 begin
1891 return Lt (T1, T2);
1892 end Lt;
1894 ----------
1895 -- Move --
1896 ----------
1898 procedure Move (From : Natural; To : Natural) is
1899 begin
1900 Rnums (Nat (To)) := Rnums (Nat (From));
1901 end Move;
1903 -----------------
1904 -- Name_Change --
1905 -----------------
1907 -- Why a string comparison here??? Why not compare Name_Id values???
1909 function Name_Change (X : Entity_Id) return Boolean is
1910 begin
1911 Get_Unqualified_Name_String (Chars (X));
1913 if Name_Len /= Curlen then
1914 return True;
1915 else
1916 return Name_Buffer (1 .. Curlen) /= Curnam (1 .. Curlen);
1917 end if;
1918 end Name_Change;
1920 -- Start of processing for Output_Refs
1922 begin
1923 -- Capture the definition Sloc values. We delay doing this till now,
1924 -- since at the time the reference or definition is made, private
1925 -- types may be swapped, and the Sloc value may be incorrect. We
1926 -- also set up the pointer vector for the sort.
1928 -- For user-defined operators we need to skip the initial quote and
1929 -- point to the first character of the name, for navigation purposes.
1931 for J in 1 .. Nrefs loop
1932 declare
1933 E : constant Entity_Id := Xrefs.Table (J).Key.Ent;
1934 Loc : constant Source_Ptr := Original_Location (Sloc (E));
1936 begin
1937 Rnums (J) := J;
1939 if Nkind (E) = N_Defining_Operator_Symbol then
1940 Xrefs.Table (J).Def := Loc + 1;
1941 else
1942 Xrefs.Table (J).Def := Loc;
1943 end if;
1944 end;
1945 end loop;
1947 -- Sort the references
1949 Sorting.Sort (Integer (Nrefs));
1951 -- Initialize loop through references
1953 Curxu := No_Unit;
1954 Curent := Empty;
1955 Curdef := No_Location;
1956 Curru := No_Unit;
1957 Crloc := No_Location;
1958 Prevt := 'm';
1960 -- Loop to output references
1962 for Refno in 1 .. Nrefs loop
1963 Output_One_Ref : declare
1964 Ent : Entity_Id;
1966 XE : Xref_Entry renames Xrefs.Table (Rnums (Refno));
1967 -- The current entry to be accessed
1969 Left : Character;
1970 Right : Character;
1971 -- Used for {} or <> or () for type reference
1973 procedure Check_Type_Reference
1974 (Ent : Entity_Id;
1975 List_Interface : Boolean;
1976 Is_Component : Boolean := False);
1977 -- Find whether there is a meaningful type reference for
1978 -- Ent, and display it accordingly. If List_Interface is
1979 -- true, then Ent is a progenitor interface of the current
1980 -- type entity being listed. In that case list it as is,
1981 -- without looking for a type reference for it. Flag is also
1982 -- used for index types of an array type, where the caller
1983 -- supplies the intended type reference. Is_Component serves
1984 -- the same purpose, to display the component type of a
1985 -- derived array type, for which only the parent type has
1986 -- ben displayed so far.
1988 procedure Output_Instantiation_Refs (Loc : Source_Ptr);
1989 -- Recursive procedure to output instantiation references for
1990 -- the given source ptr in [file|line[...]] form. No output
1991 -- if the given location is not a generic template reference.
1993 procedure Output_Overridden_Op (Old_E : Entity_Id);
1994 -- For a subprogram that is overriding, display information
1995 -- about the inherited operation that it overrides.
1997 --------------------------
1998 -- Check_Type_Reference --
1999 --------------------------
2001 procedure Check_Type_Reference
2002 (Ent : Entity_Id;
2003 List_Interface : Boolean;
2004 Is_Component : Boolean := False)
2006 begin
2007 if List_Interface then
2009 -- This is a progenitor interface of the type for which
2010 -- xref information is being generated.
2012 Tref := Ent;
2013 Left := '<';
2014 Right := '>';
2016 -- The following is not documented in lib-xref.ads ???
2018 elsif Is_Component then
2019 Tref := Ent;
2020 Left := '(';
2021 Right := ')';
2023 else
2024 Get_Type_Reference (Ent, Tref, Left, Right);
2025 end if;
2027 if Present (Tref) then
2029 -- Case of standard entity, output name
2031 if Sloc (Tref) = Standard_Location then
2032 Write_Info_Char (Left);
2033 Write_Info_Name (Chars (Tref));
2034 Write_Info_Char (Right);
2036 -- Case of source entity, output location
2038 else
2039 Write_Info_Char (Left);
2040 Trunit := Get_Source_Unit (Sloc (Tref));
2042 if Trunit /= Curxu then
2043 Write_Info_Nat (Dependency_Num (Trunit));
2044 Write_Info_Char ('|');
2045 end if;
2047 Write_Info_Nat
2048 (Int (Get_Logical_Line_Number (Sloc (Tref))));
2050 declare
2051 Ent : Entity_Id;
2052 Ctyp : Character;
2054 begin
2055 Ent := Tref;
2056 Ctyp := Xref_Entity_Letters (Ekind (Ent));
2058 if Ctyp = '+'
2059 and then Present (Full_View (Ent))
2060 then
2061 Ent := Underlying_Type (Ent);
2063 if Present (Ent) then
2064 Ctyp := Xref_Entity_Letters (Ekind (Ent));
2065 end if;
2066 end if;
2068 Write_Info_Char (Ctyp);
2069 end;
2071 Write_Info_Nat
2072 (Int (Get_Column_Number (Sloc (Tref))));
2074 -- If the type comes from an instantiation, add the
2075 -- corresponding info.
2077 Output_Instantiation_Refs (Sloc (Tref));
2078 Write_Info_Char (Right);
2079 end if;
2080 end if;
2081 end Check_Type_Reference;
2083 -------------------------------
2084 -- Output_Instantiation_Refs --
2085 -------------------------------
2087 procedure Output_Instantiation_Refs (Loc : Source_Ptr) is
2088 Iloc : constant Source_Ptr := Instantiation_Location (Loc);
2089 Lun : Unit_Number_Type;
2090 Cu : constant Unit_Number_Type := Curru;
2092 begin
2093 -- Nothing to do if this is not an instantiation
2095 if Iloc = No_Location then
2096 return;
2097 end if;
2099 -- Output instantiation reference
2101 Write_Info_Char ('[');
2102 Lun := Get_Source_Unit (Iloc);
2104 if Lun /= Curru then
2105 Curru := Lun;
2106 Write_Info_Nat (Dependency_Num (Curru));
2107 Write_Info_Char ('|');
2108 end if;
2110 Write_Info_Nat (Int (Get_Logical_Line_Number (Iloc)));
2112 -- Recursive call to get nested instantiations
2114 Output_Instantiation_Refs (Iloc);
2116 -- Output final ] after call to get proper nesting
2118 Write_Info_Char (']');
2119 Curru := Cu;
2120 return;
2121 end Output_Instantiation_Refs;
2123 --------------------------
2124 -- Output_Overridden_Op --
2125 --------------------------
2127 procedure Output_Overridden_Op (Old_E : Entity_Id) is
2128 Op : Entity_Id;
2130 begin
2131 -- The overridden operation has an implicit declaration
2132 -- at the point of derivation. What we want to display
2133 -- is the original operation, which has the actual body
2134 -- (or abstract declaration) that is being overridden.
2135 -- The overridden operation is not always set, e.g. when
2136 -- it is a predefined operator.
2138 if No (Old_E) then
2139 return;
2141 -- Follow alias chain if one is present
2143 elsif Present (Alias (Old_E)) then
2145 -- The subprogram may have been implicitly inherited
2146 -- through several levels of derivation, so find the
2147 -- ultimate (source) ancestor.
2149 Op := Ultimate_Alias (Old_E);
2151 -- Normal case of no alias present. We omit generated
2152 -- primitives like tagged equality, that have no source
2153 -- representation.
2155 else
2156 Op := Old_E;
2157 end if;
2159 if Present (Op)
2160 and then Sloc (Op) /= Standard_Location
2161 and then Comes_From_Source (Op)
2162 then
2163 declare
2164 Loc : constant Source_Ptr := Sloc (Op);
2165 Par_Unit : constant Unit_Number_Type :=
2166 Get_Source_Unit (Loc);
2168 begin
2169 Write_Info_Char ('<');
2171 if Par_Unit /= Curxu then
2172 Write_Info_Nat (Dependency_Num (Par_Unit));
2173 Write_Info_Char ('|');
2174 end if;
2176 Write_Info_Nat (Int (Get_Logical_Line_Number (Loc)));
2177 Write_Info_Char ('p');
2178 Write_Info_Nat (Int (Get_Column_Number (Loc)));
2179 Write_Info_Char ('>');
2180 end;
2181 end if;
2182 end Output_Overridden_Op;
2184 -- Start of processing for Output_One_Ref
2186 begin
2187 Ent := XE.Key.Ent;
2189 -- Do not generate reference information for an ignored Ghost
2190 -- entity because neither the entity nor its references will
2191 -- appear in the final tree.
2193 if Is_Ignored_Ghost_Entity (Ent) then
2194 goto Continue;
2195 end if;
2197 Ctyp := Xref_Entity_Letters (Ekind (Ent));
2199 -- Skip reference if it is the only reference to an entity,
2200 -- and it is an END line reference, and the entity is not in
2201 -- the current extended source. This prevents junk entries
2202 -- consisting only of packages with END lines, where no
2203 -- entity from the package is actually referenced.
2205 if XE.Key.Typ = 'e'
2206 and then Ent /= Curent
2207 and then (Refno = Nrefs
2208 or else
2209 Ent /= Xrefs.Table (Rnums (Refno + 1)).Key.Ent)
2210 and then not In_Extended_Main_Source_Unit (Ent)
2211 then
2212 goto Continue;
2213 end if;
2215 -- For private type, get full view type
2217 if Ctyp = '+'
2218 and then Present (Full_View (XE.Key.Ent))
2219 then
2220 Ent := Underlying_Type (Ent);
2222 if Present (Ent) then
2223 Ctyp := Xref_Entity_Letters (Ekind (Ent));
2224 end if;
2225 end if;
2227 -- Special exception for Boolean
2229 if Ctyp = 'E' and then Is_Boolean_Type (Ent) then
2230 Ctyp := 'B';
2231 end if;
2233 -- For variable reference, get corresponding type
2235 if Ctyp = '*' then
2236 Ent := Etype (XE.Key.Ent);
2237 Ctyp := Fold_Lower (Xref_Entity_Letters (Ekind (Ent)));
2239 -- If variable is private type, get full view type
2241 if Ctyp = '+'
2242 and then Present (Full_View (Etype (XE.Key.Ent)))
2243 then
2244 Ent := Underlying_Type (Etype (XE.Key.Ent));
2246 if Present (Ent) then
2247 Ctyp := Fold_Lower (Xref_Entity_Letters (Ekind (Ent)));
2248 end if;
2250 elsif Is_Generic_Type (Ent) then
2252 -- If the type of the entity is a generic private type,
2253 -- there is no usable full view, so retain the indication
2254 -- that this is an object.
2256 Ctyp := '*';
2257 end if;
2259 -- Special handling for access parameters and objects and
2260 -- components of an anonymous access type.
2262 if Ekind (Etype (XE.Key.Ent)) in
2263 E_Anonymous_Access_Type
2264 | E_Anonymous_Access_Subprogram_Type
2265 | E_Anonymous_Access_Protected_Subprogram_Type
2266 then
2267 if Is_Formal (XE.Key.Ent)
2268 or else
2269 Ekind (XE.Key.Ent) in
2270 E_Variable | E_Constant | E_Component
2271 then
2272 Ctyp := 'p';
2273 end if;
2275 -- Special handling for Boolean
2277 elsif Ctyp = 'e' and then Is_Boolean_Type (Ent) then
2278 Ctyp := 'b';
2279 end if;
2280 end if;
2282 -- Special handling for abstract types and operations
2284 if Is_Overloadable (XE.Key.Ent)
2285 and then Is_Abstract_Subprogram (XE.Key.Ent)
2286 then
2287 if Ctyp = 'U' then
2288 Ctyp := 'x'; -- Abstract procedure
2290 elsif Ctyp = 'V' then
2291 Ctyp := 'y'; -- Abstract function
2292 end if;
2294 elsif Is_Type (XE.Key.Ent)
2295 and then Is_Abstract_Type (XE.Key.Ent)
2296 then
2297 if Is_Interface (XE.Key.Ent) then
2298 Ctyp := 'h';
2300 elsif Ctyp = 'R' then
2301 Ctyp := 'H'; -- Abstract type
2302 end if;
2303 end if;
2305 -- Only output reference if interesting type of entity
2307 if Ctyp = ' '
2309 -- Suppress references to object definitions, used for local
2310 -- references.
2312 or else XE.Key.Typ = 'D'
2313 or else XE.Key.Typ = 'I'
2315 -- Suppress self references, except for bodies that act as
2316 -- specs.
2318 or else (XE.Key.Loc = XE.Def
2319 and then
2320 (XE.Key.Typ /= 'b'
2321 or else not Is_Subprogram (XE.Key.Ent)))
2323 -- Also suppress definitions of body formals (we only
2324 -- treat these as references, and the references were
2325 -- separately recorded).
2327 or else (Is_Formal (XE.Key.Ent)
2328 and then Present (Spec_Entity (XE.Key.Ent)))
2329 then
2330 null;
2332 else
2333 -- Start new Xref section if new xref unit
2335 if XE.Key.Eun /= Curxu then
2336 if Write_Info_Col > 1 then
2337 Write_Info_EOL;
2338 end if;
2340 Curxu := XE.Key.Eun;
2342 Write_Info_Initiate ('X');
2343 Write_Info_Char (' ');
2344 Write_Info_Nat (Dependency_Num (XE.Key.Eun));
2345 Write_Info_Char (' ');
2346 Write_Info_Name
2347 (Reference_Name (Source_Index (XE.Key.Eun)));
2348 end if;
2350 -- Start new Entity line if new entity. Note that we
2351 -- consider two entities the same if they have the same
2352 -- name and source location. This causes entities in
2353 -- instantiations to be treated as though they referred
2354 -- to the template.
2356 if No (Curent)
2357 or else
2358 (XE.Key.Ent /= Curent
2359 and then
2360 (Name_Change (XE.Key.Ent) or else XE.Def /= Curdef))
2361 then
2362 Curent := XE.Key.Ent;
2363 Curdef := XE.Def;
2365 Get_Unqualified_Name_String (Chars (XE.Key.Ent));
2366 Curlen := Name_Len;
2367 Curnam (1 .. Curlen) := Name_Buffer (1 .. Curlen);
2369 if Write_Info_Col > 1 then
2370 Write_Info_EOL;
2371 end if;
2373 -- Write column number information
2375 Write_Info_Nat (Int (Get_Logical_Line_Number (XE.Def)));
2376 Write_Info_Char (Ctyp);
2377 Write_Info_Nat (Int (Get_Column_Number (XE.Def)));
2379 -- Write level information
2381 Write_Level_Info : declare
2382 function Is_Visible_Generic_Entity
2383 (E : Entity_Id) return Boolean;
2384 -- Check whether E is declared in the visible part
2385 -- of a generic package. For source navigation
2386 -- purposes, treat this as a visible entity.
2388 function Is_Private_Record_Component
2389 (E : Entity_Id) return Boolean;
2390 -- Check whether E is a non-inherited component of a
2391 -- private extension. Even if the enclosing record is
2392 -- public, we want to treat the component as private
2393 -- for navigation purposes.
2395 ---------------------------------
2396 -- Is_Private_Record_Component --
2397 ---------------------------------
2399 function Is_Private_Record_Component
2400 (E : Entity_Id) return Boolean
2402 S : constant Entity_Id := Scope (E);
2403 begin
2404 return
2405 Ekind (E) = E_Component
2406 and then Nkind (Declaration_Node (S)) =
2407 N_Private_Extension_Declaration
2408 and then Original_Record_Component (E) = E;
2409 end Is_Private_Record_Component;
2411 -------------------------------
2412 -- Is_Visible_Generic_Entity --
2413 -------------------------------
2415 function Is_Visible_Generic_Entity
2416 (E : Entity_Id) return Boolean
2418 Par : Node_Id;
2420 begin
2421 -- The Present check here is an error defense
2423 if Present (Scope (E))
2424 and then Ekind (Scope (E)) /= E_Generic_Package
2425 then
2426 return False;
2427 end if;
2429 Par := Parent (E);
2430 while Present (Par) loop
2432 Nkind (Par) = N_Generic_Package_Declaration
2433 then
2434 -- Entity is a generic formal
2436 return False;
2438 elsif
2439 Nkind (Parent (Par)) = N_Package_Specification
2440 then
2441 return
2442 Is_List_Member (Par)
2443 and then List_Containing (Par) =
2444 Visible_Declarations (Parent (Par));
2445 else
2446 Par := Parent (Par);
2447 end if;
2448 end loop;
2450 return False;
2451 end Is_Visible_Generic_Entity;
2453 -- Start of processing for Write_Level_Info
2455 begin
2456 if Is_Hidden (Curent)
2457 or else Is_Private_Record_Component (Curent)
2458 then
2459 Write_Info_Char (' ');
2461 elsif
2462 Is_Public (Curent)
2463 or else Is_Visible_Generic_Entity (Curent)
2464 then
2465 Write_Info_Char ('*');
2467 else
2468 Write_Info_Char (' ');
2469 end if;
2470 end Write_Level_Info;
2472 -- Output entity name. We use the occurrence from the
2473 -- actual source program at the definition point.
2475 declare
2476 Ent_Name : constant String :=
2477 Exact_Source_Name (Sloc (XE.Key.Ent));
2478 begin
2479 for C in Ent_Name'Range loop
2480 Write_Info_Char (Ent_Name (C));
2481 end loop;
2482 end;
2484 -- See if we have a renaming reference
2486 if Is_Object (XE.Key.Ent)
2487 and then Present (Renamed_Object (XE.Key.Ent))
2488 then
2489 Rref := Renamed_Object (XE.Key.Ent);
2491 elsif Is_Overloadable (XE.Key.Ent)
2492 and then Nkind (Parent (Declaration_Node (XE.Key.Ent)))
2493 = N_Subprogram_Renaming_Declaration
2494 then
2495 Rref := Name (Parent (Declaration_Node (XE.Key.Ent)));
2497 elsif Ekind (XE.Key.Ent) = E_Package
2498 and then Nkind (Declaration_Node (XE.Key.Ent)) =
2499 N_Package_Renaming_Declaration
2500 then
2501 Rref := Name (Declaration_Node (XE.Key.Ent));
2503 else
2504 Rref := Empty;
2505 end if;
2507 if Present (Rref) then
2508 if Nkind (Rref) = N_Expanded_Name then
2509 Rref := Selector_Name (Rref);
2510 end if;
2512 if Nkind (Rref) = N_Identifier
2513 or else Nkind (Rref) = N_Operator_Symbol
2514 then
2515 null;
2517 -- For renamed array components, use the array name
2518 -- for the renamed entity, which reflect the fact that
2519 -- in general the whole array is aliased.
2521 elsif Nkind (Rref) = N_Indexed_Component then
2522 if Nkind (Prefix (Rref)) = N_Identifier then
2523 Rref := Prefix (Rref);
2524 elsif Nkind (Prefix (Rref)) = N_Expanded_Name then
2525 Rref := Selector_Name (Prefix (Rref));
2526 else
2527 Rref := Empty;
2528 end if;
2530 else
2531 Rref := Empty;
2532 end if;
2533 end if;
2535 -- Write out renaming reference if we have one
2537 if Present (Rref) then
2538 Write_Info_Char ('=');
2539 Write_Info_Nat
2540 (Int (Get_Logical_Line_Number (Sloc (Rref))));
2541 Write_Info_Char (':');
2542 Write_Info_Nat
2543 (Int (Get_Column_Number (Sloc (Rref))));
2544 end if;
2546 -- Indicate that the entity is in the unit of the current
2547 -- xref section.
2549 Curru := Curxu;
2551 -- Write out information about generic parent, if entity
2552 -- is an instance.
2554 if Is_Generic_Instance (XE.Key.Ent) then
2555 declare
2556 Gen_Par : constant Entity_Id :=
2557 Generic_Parent
2558 (Specification
2559 (Unit_Declaration_Node
2560 (XE.Key.Ent)));
2561 Loc : constant Source_Ptr := Sloc (Gen_Par);
2562 Gen_U : constant Unit_Number_Type :=
2563 Get_Source_Unit (Loc);
2565 begin
2566 Write_Info_Char ('[');
2568 if Curru /= Gen_U then
2569 Write_Info_Nat (Dependency_Num (Gen_U));
2570 Write_Info_Char ('|');
2571 end if;
2573 Write_Info_Nat
2574 (Int (Get_Logical_Line_Number (Loc)));
2575 Write_Info_Char (']');
2576 end;
2577 end if;
2579 -- See if we have a type reference and if so output
2581 Check_Type_Reference (XE.Key.Ent, False);
2583 -- Additional information for types with progenitors,
2584 -- including synchronized tagged types.
2586 declare
2587 Typ : constant Entity_Id := XE.Key.Ent;
2588 Elmt : Elmt_Id;
2590 begin
2591 if Is_Record_Type (Typ)
2592 and then Present (Interfaces (Typ))
2593 then
2594 Elmt := First_Elmt (Interfaces (Typ));
2596 elsif Is_Concurrent_Type (Typ)
2597 and then Present (Corresponding_Record_Type (Typ))
2598 and then Present (
2599 Interfaces (Corresponding_Record_Type (Typ)))
2600 then
2601 Elmt :=
2602 First_Elmt (
2603 Interfaces (Corresponding_Record_Type (Typ)));
2605 else
2606 Elmt := No_Elmt;
2607 end if;
2609 while Present (Elmt) loop
2610 Check_Type_Reference (Node (Elmt), True);
2611 Next_Elmt (Elmt);
2612 end loop;
2613 end;
2615 -- For array types, list index types as well. (This is
2616 -- not C, indexes have distinct types).
2618 if Is_Array_Type (XE.Key.Ent) then
2619 declare
2620 A_Typ : constant Entity_Id := XE.Key.Ent;
2621 Indx : Node_Id;
2623 begin
2624 -- If this is a derived array type, we have
2625 -- output the parent type, so add the component
2626 -- type now.
2628 if Is_Derived_Type (A_Typ) then
2629 Check_Type_Reference
2630 (Component_Type (A_Typ), False, True);
2631 end if;
2633 -- Add references to index types.
2635 Indx := First_Index (XE.Key.Ent);
2636 while Present (Indx) loop
2637 Check_Type_Reference
2638 (First_Subtype (Etype (Indx)), True);
2639 Next_Index (Indx);
2640 end loop;
2641 end;
2642 end if;
2644 -- If the entity is an overriding operation, write info
2645 -- on operation that was overridden.
2647 if Is_Subprogram (XE.Key.Ent)
2648 and then Present (Overridden_Operation (XE.Key.Ent))
2649 then
2650 Output_Overridden_Op
2651 (Overridden_Operation (XE.Key.Ent));
2652 end if;
2654 -- End of processing for entity output
2656 Crloc := No_Location;
2657 end if;
2659 -- Output the reference if it is not as the same location
2660 -- as the previous one, or it is a read-reference that
2661 -- indicates that the entity is an in-out actual in a call.
2663 if XE.Key.Loc /= No_Location
2664 and then
2665 (XE.Key.Loc /= Crloc
2666 or else (Prevt = 'm' and then XE.Key.Typ = 'r'))
2667 then
2668 Crloc := XE.Key.Loc;
2669 Prevt := XE.Key.Typ;
2671 -- Start continuation if line full, else blank
2673 if Write_Info_Col > 72 then
2674 Write_Info_EOL;
2675 Write_Info_Initiate ('.');
2676 end if;
2678 Write_Info_Char (' ');
2680 -- Output file number if changed
2682 if XE.Key.Lun /= Curru then
2683 Curru := XE.Key.Lun;
2684 Write_Info_Nat (Dependency_Num (Curru));
2685 Write_Info_Char ('|');
2686 end if;
2688 Write_Info_Nat
2689 (Int (Get_Logical_Line_Number (XE.Key.Loc)));
2690 Write_Info_Char (XE.Key.Typ);
2692 if Is_Overloadable (XE.Key.Ent) then
2693 if (Is_Imported (XE.Key.Ent) and then XE.Key.Typ = 'b')
2694 or else
2695 (Is_Exported (XE.Key.Ent) and then XE.Key.Typ = 'i')
2696 then
2697 Output_Import_Export_Info (XE.Key.Ent);
2698 end if;
2699 end if;
2701 Write_Info_Nat (Int (Get_Column_Number (XE.Key.Loc)));
2703 Output_Instantiation_Refs (Sloc (XE.Key.Ent));
2704 end if;
2705 end if;
2706 end Output_One_Ref;
2708 <<Continue>>
2709 null;
2710 end loop;
2712 Write_Info_EOL;
2713 end Output_Refs;
2714 end Output_References;
2716 -- Start of elaboration for Lib.Xref
2718 begin
2719 -- Reset is necessary because Elmt_Ptr does not default to Null_Ptr,
2720 -- because it's not an access type.
2722 Xref_Set.Reset;
2723 end Lib.Xref;