diff options
Diffstat (limited to 'gcc/ada/lib-xref.adb')
-rw-r--r-- | gcc/ada/lib-xref.adb | 931 |
1 files changed, 729 insertions, 202 deletions
diff --git a/gcc/ada/lib-xref.adb b/gcc/ada/lib-xref.adb index dd1e61cbd3f..014a9e97030 100644 --- a/gcc/ada/lib-xref.adb +++ b/gcc/ada/lib-xref.adb @@ -6,7 +6,7 @@ -- -- -- B o d y -- -- -- --- Copyright (C) 1998-2002, Free Software Foundation, Inc. -- +-- Copyright (C) 1998-2003, Free Software Foundation, Inc. -- -- -- -- GNAT is free software; you can redistribute it and/or modify it under -- -- terms of the GNU General Public License as published by the Free Soft- -- @@ -26,12 +26,17 @@ with Atree; use Atree; with Csets; use Csets; +with Elists; use Elists; with Errout; use Errout; with Lib.Util; use Lib.Util; with Namet; use Namet; +with Nlists; use Nlists; with Opt; use Opt; +with Sem_Prag; use Sem_Prag; with Sinfo; use Sinfo; with Sinput; use Sinput; +with Snames; use Snames; +with Stringt; use Stringt; with Stand; use Stand; with Table; use Table; with Widechar; use Widechar; @@ -124,6 +129,7 @@ package body Lib.Xref is Xrefs.Table (Indx).Loc := No_Location; Xrefs.Table (Indx).Eun := Get_Source_Unit (Loc); Xrefs.Table (Indx).Lun := No_Unit; + Set_Has_Xref_Entry (E); end if; end Generate_Definition; @@ -131,7 +137,10 @@ package body Lib.Xref is -- Generate_Operator_Reference -- --------------------------------- - procedure Generate_Operator_Reference (N : Node_Id) is + procedure Generate_Operator_Reference + (N : Node_Id; + T : Entity_Id) + is begin if not In_Extended_Main_Source_Unit (N) then return; @@ -161,18 +170,14 @@ package body Lib.Xref is -- marked as referenced is the first subtype, which is the user -- defined entity that is relevant. - else - if Nkind (N) = N_Op_Eq - or else Nkind (N) = N_Op_Ne - or else Nkind (N) = N_Op_Le - or else Nkind (N) = N_Op_Lt - or else Nkind (N) = N_Op_Ge - or else Nkind (N) = N_Op_Gt - then - Set_Referenced (First_Subtype (Etype (Right_Opnd (N)))); - else - Set_Referenced (First_Subtype (Etype (N))); - end if; + -- Note: we only do this for operators that come from source. + -- The generated code sometimes reaches for entities that do + -- not need to be explicitly visible (for example, when we + -- expand the code for comparing two record types, the fields + -- of the record may not be visible). + + elsif Comes_From_Source (N) then + Set_Referenced (First_Subtype (T)); end if; end Generate_Operator_Reference; @@ -197,7 +202,7 @@ package body Lib.Xref is pragma Assert (Nkind (E) in N_Entity); -- Never collect references if not in main source unit. However, - -- we omit this test if Typ is 'e', since these entries are + -- we omit this test if Typ is 'e' or 'k', since these entries are -- really structural, and it is useful to have them in units -- that reference packages as well as units that define packages. -- We also omit the test for the case of 'p' since we want to @@ -206,11 +211,12 @@ package body Lib.Xref is if not In_Extended_Main_Source_Unit (N) and then Typ /= 'e' and then Typ /= 'p' + and then Typ /= 'k' then return; end if; - -- For reference type p, then entity must be in main source unit + -- For reference type p, the entity must be in main source unit if Typ = 'p' and then not In_Extended_Main_Source_Unit (E) then return; @@ -233,9 +239,43 @@ package body Lib.Xref is -- package contains no referenced entities). if Set_Ref then - Set_Referenced (E); - -- Check for pragma unreferenced given + -- For a variable that appears on the left side of an + -- assignment statement, we set the Referenced_As_LHS + -- flag since this is indeed a left hand side. + + if Ekind (E) = E_Variable + and then Nkind (Parent (N)) = N_Assignment_Statement + and then Name (Parent (N)) = N + and then No (Renamed_Object (E)) + then + Set_Referenced_As_LHS (E); + + -- Check for a reference in a pragma that should not count as a + -- making the variable referenced for warning purposes. + + elsif Is_Non_Significant_Pragma_Reference (N) then + null; + + -- A reference in an attribute definition clause does not + -- count as a reference except for the case of Address. + -- The reason that 'Address is an exception is that it + -- creates an alias through which the variable may be + -- referenced. + + elsif Nkind (Parent (N)) = N_Attribute_Definition_Clause + and then Chars (Parent (N)) /= Name_Address + and then N = Name (Parent (N)) + then + null; + + -- Any other occurrence counts as referencing the entity + + else + Set_Referenced (E); + end if; + + -- Check for pragma Unreferenced given if Has_Pragma_Unreferenced (E) then @@ -248,6 +288,15 @@ package body Lib.Xref is then null; + -- Neither does a reference to a variable on the left side + -- of an assignment + + elsif Ekind (E) = E_Variable + and then Nkind (Parent (N)) = N_Assignment_Statement + and then Name (Parent (N)) = N + then + null; + -- Here we issue the warning, since this is a real reference else @@ -299,6 +348,8 @@ package body Lib.Xref is or else Nkind (N) = N_Defining_Operator_Symbol or else + Nkind (N) = N_Operator_Symbol + or else (Nkind (N) = N_Character_Literal and then Sloc (Entity (N)) /= Standard_Location) or else @@ -322,16 +373,33 @@ package body Lib.Xref is Ent := E; -- Entity does not come from source, but is a derived subprogram - -- and the derived subprogram comes from source, in which case - -- the reference is to this parent subprogram. + -- and the derived subprogram comes from source (after one or more + -- derivations) in which case the reference is to parent subprogram. elsif Is_Overloadable (E) and then Present (Alias (E)) - and then Comes_From_Source (Alias (E)) then Ent := Alias (E); - -- Ignore reference to any other source that is not from source + loop + if Comes_From_Source (Ent) then + exit; + elsif No (Alias (Ent)) then + return; + else + Ent := Alias (Ent); + end if; + end loop; + + -- Record components of discriminated subtypes or derived types + -- must be treated as references to the original component. + + elsif Ekind (E) = E_Component + and then Comes_From_Source (Original_Record_Component (E)) + then + Ent := Original_Record_Component (E); + + -- Ignore reference to any other entity that is not from source else return; @@ -346,79 +414,295 @@ package body Lib.Xref is Indx := Xrefs.Last; Xrefs.Table (Indx).Loc := Ref; - Xrefs.Table (Indx).Typ := Typ; + + -- Overriding operations are marked with 'P'. + + if Typ = 'p' + and then Is_Subprogram (N) + and then Is_Overriding_Operation (N) + then + Xrefs.Table (Indx).Typ := 'P'; + else + Xrefs.Table (Indx).Typ := Typ; + end if; + Xrefs.Table (Indx).Eun := Get_Source_Unit (Def); Xrefs.Table (Indx).Lun := Get_Source_Unit (Ref); Xrefs.Table (Indx).Ent := Ent; + Set_Has_Xref_Entry (Ent); end if; end Generate_Reference; + ----------------------------------- + -- Generate_Reference_To_Formals -- + ----------------------------------- + + procedure Generate_Reference_To_Formals (E : Entity_Id) is + Formal : Entity_Id; + + begin + if Is_Generic_Subprogram (E) then + Formal := First_Entity (E); + + while Present (Formal) + and then not Is_Formal (Formal) + loop + Next_Entity (Formal); + end loop; + + else + Formal := First_Formal (E); + end if; + + while Present (Formal) loop + if Ekind (Formal) = E_In_Parameter then + + if Nkind (Parameter_Type (Parent (Formal))) + = N_Access_Definition + then + Generate_Reference (E, Formal, '^', False); + else + Generate_Reference (E, Formal, '>', False); + end if; + + elsif Ekind (Formal) = E_In_Out_Parameter then + Generate_Reference (E, Formal, '=', False); + + else + Generate_Reference (E, Formal, '<', False); + end if; + + Next_Formal (Formal); + end loop; + end Generate_Reference_To_Formals; + + ------------------------------------------- + -- Generate_Reference_To_Generic_Formals -- + ------------------------------------------- + + procedure Generate_Reference_To_Generic_Formals (E : Entity_Id) is + Formal : Entity_Id; + + begin + Formal := First_Entity (E); + + while Present (Formal) loop + if Comes_From_Source (Formal) then + Generate_Reference (E, Formal, 'z', False); + end if; + + Next_Entity (Formal); + end loop; + end Generate_Reference_To_Generic_Formals; + + ---------------- + -- Initialize -- + ---------------- + + procedure Initialize is + begin + Xrefs.Init; + end Initialize; + ----------------------- -- Output_References -- ----------------------- procedure Output_References is - Nrefs : constant Nat := Xrefs.Last; - Rnums : array (0 .. Nrefs) of Nat; - -- This array contains numbers of references in the Xrefs table. This - -- list is sorted in output order. The extra 0'th entry is convenient - -- for the call to sort. When we sort the table, we move these entries - -- around, but we do not move the original table entries. + procedure Get_Type_Reference + (Ent : Entity_Id; + Tref : out Entity_Id; + Left : out Character; + Right : out Character); + -- Given an entity id Ent, determines whether a type reference is + -- required. If so, Tref is set to the entity for the type reference + -- and Left and Right are set to the left/right brackets to be + -- output for the reference. If no type reference is required, then + -- Tref is set to Empty, and Left/Right are set to space. + + procedure Output_Import_Export_Info (Ent : Entity_Id); + -- Ouput language and external name information for an interfaced + -- entity, using the format <language, external_name>, + + ------------------------ + -- Get_Type_Reference -- + ------------------------ + + procedure Get_Type_Reference + (Ent : Entity_Id; + Tref : out Entity_Id; + Left : out Character; + Right : out Character) + is + Sav : Entity_Id; + + begin + -- See if we have a type reference - function Lt (Op1, Op2 : Natural) return Boolean; - -- Comparison function for Sort call + Tref := Ent; + Left := '{'; + Right := '}'; - procedure Move (From : Natural; To : Natural); - -- Move procedure for Sort call + loop + Sav := Tref; - function Lt (Op1, Op2 : Natural) return Boolean is - T1 : Xref_Entry renames Xrefs.Table (Rnums (Nat (Op1))); - T2 : Xref_Entry renames Xrefs.Table (Rnums (Nat (Op2))); + -- Processing for types - begin - -- First test. If entity is in different unit, sort by unit + if Is_Type (Tref) then + + -- Case of base type + + if Base_Type (Tref) = Tref then + + -- If derived, then get first subtype + + if Tref /= Etype (Tref) then + Tref := First_Subtype (Etype (Tref)); + + -- Set brackets for derived type, but don't + -- override pointer case since the fact that + -- something is a pointer is more important + + if Left /= '(' then + Left := '<'; + Right := '>'; + end if; + + -- If non-derived ptr, get directly designated type. + -- If the type has a full view, all references are + -- on the partial view, that is seen first. + + elsif Is_Access_Type (Tref) then + Tref := Directly_Designated_Type (Tref); + Left := '('; + Right := ')'; + + elsif Is_Private_Type (Tref) + and then Present (Full_View (Tref)) + and then Is_Access_Type (Full_View (Tref)) + then + Tref := Directly_Designated_Type (Full_View (Tref)); + Left := '('; + Right := ')'; + + -- If non-derived array, get component type. + -- Skip component type for case of String + -- or Wide_String, saves worthwhile space. + + elsif Is_Array_Type (Tref) + and then Tref /= Standard_String + and then Tref /= Standard_Wide_String + then + Tref := Component_Type (Tref); + Left := '('; + Right := ')'; + + -- For other non-derived base types, nothing + + else + exit; + end if; + + -- For a subtype, go to ancestor subtype. If it is a + -- subtype created for a generic actual, not clear yet + -- what is the right type to use ??? + + else + Tref := Ancestor_Subtype (Tref); + + -- If no ancestor subtype, go to base type + + if No (Tref) then + Tref := Base_Type (Sav); + end if; + end if; + + -- For objects, functions, enum literals, + -- just get type from Etype field. + + elsif Is_Object (Tref) + or else Ekind (Tref) = E_Enumeration_Literal + or else Ekind (Tref) = E_Function + or else Ekind (Tref) = E_Operator + then + Tref := Etype (Tref); - if T1.Eun /= T2.Eun then - return Dependency_Num (T1.Eun) < Dependency_Num (T2.Eun); + -- For anything else, exit - -- Second test, within same unit, sort by entity Sloc + else + exit; + end if; - elsif T1.Def /= T2.Def then - return T1.Def < T2.Def; + -- Exit if no type reference, or we are stuck in + -- some loop trying to find the type reference, or + -- if the type is standard void type (the latter is + -- an implementation artifact that should not show + -- up in the generated cross-references). - -- Third test, sort definitions ahead of references + exit when No (Tref) + or else Tref = Sav + or else Tref = Standard_Void_Type; - elsif T1.Loc = No_Location then - return True; + -- If we have a usable type reference, return, otherwise + -- keep looking for something useful (we are looking for + -- something that either comes from source or standard) + + if Sloc (Tref) = Standard_Location + or else Comes_From_Source (Tref) + then + return; + end if; + end loop; - elsif T2.Loc = No_Location then - return False; + -- If we fall through the loop, no type reference - -- Fourth test, for same entity, sort by reference location unit + Tref := Empty; + Left := ' '; + Right := ' '; + end Get_Type_Reference; - elsif T1.Lun /= T2.Lun then - return Dependency_Num (T1.Lun) < Dependency_Num (T2.Lun); + ------------------------------- + -- Output_Import_Export_Info -- + ------------------------------- - -- Fifth test order of location within referencing unit + procedure Output_Import_Export_Info (Ent : Entity_Id) is + Language_Name : Name_Id; + Conv : constant Convention_Id := Convention (Ent); + begin + if Conv = Convention_C then + Language_Name := Name_C; - elsif T1.Loc /= T2.Loc then - return T1.Loc < T2.Loc; + elsif Conv = Convention_CPP then + Language_Name := Name_CPP; - -- Finally, for two locations at the same address, we prefer - -- the one that does NOT have the type 'r' so that a modification - -- or extension takes preference, when there are more than one - -- reference at the same location. + elsif Conv = Convention_Ada then + Language_Name := Name_Ada; else - return T2.Typ = 'r'; + -- These are the only languages that GPS knows about. + + return; end if; - end Lt; - procedure Move (From : Natural; To : Natural) is - begin - Rnums (Nat (To)) := Rnums (Nat (From)); - end Move; + Write_Info_Char ('<'); + Get_Unqualified_Name_String (Language_Name); + + for J in 1 .. Name_Len loop + Write_Info_Char (Name_Buffer (J)); + end loop; + + if Present (Interface_Name (Ent)) then + Write_Info_Char (','); + String_To_Name_Buffer (Strval (Interface_Name (Ent))); + + for J in 1 .. Name_Len loop + Write_Info_Char (Name_Buffer (J)); + end loop; + end if; + + Write_Info_Char ('>'); + end Output_Import_Export_Info; -- Start of processing for Output_References @@ -427,28 +711,141 @@ package body Lib.Xref is return; end if; - -- Capture the definition Sloc values. We delay doing this till now, - -- since at the time the reference or definition is made, private - -- types may be swapped, and the Sloc value may be incorrect. We - -- also set up the pointer vector for the sort. + -- Before we go ahead and output the references we have a problem + -- that needs dealing with. So far we have captured things that are + -- definitely referenced by the main unit, or defined in the main + -- unit. That's because we don't want to clutter up the ali file + -- for this unit with definition lines for entities in other units + -- that are not referenced. + + -- But there is a glitch. We may reference an entity in another unit, + -- and it may have a type reference to an entity that is not directly + -- referenced in the main unit, which may mean that there is no xref + -- entry for this entity yet in the list of references. + + -- If we don't do something about this, we will end with an orphan + -- type reference, i.e. it will point to an entity that does not + -- appear within the generated references in the ali file. That is + -- not good for tools using the xref information. + + -- To fix this, we go through the references adding definition + -- entries for any unreferenced entities that can be referenced + -- in a type reference. There is a recursion problem here, and + -- that is dealt with by making sure that this traversal also + -- traverses any entries that get added by the traversal. + + declare + J : Nat; + Tref : Entity_Id; + L, R : Character; + Indx : Nat; + Ent : Entity_Id; + Loc : Source_Ptr; - for J in 1 .. Nrefs loop - Rnums (J) := J; - Xrefs.Table (J).Def := - Original_Location (Sloc (Xrefs.Table (J).Ent)); - end loop; + begin + -- Note that this is not a for loop for a very good reason. The + -- processing of items in the table can add new items to the + -- table, and they must be processed as well + + J := 1; + while J <= Xrefs.Last loop + Ent := Xrefs.Table (J).Ent; + Get_Type_Reference (Ent, Tref, L, R); + + if Present (Tref) + and then not Has_Xref_Entry (Tref) + and then Sloc (Tref) > No_Location + then + Xrefs.Increment_Last; + Indx := Xrefs.Last; + Loc := Original_Location (Sloc (Tref)); + Xrefs.Table (Indx).Ent := Tref; + Xrefs.Table (Indx).Loc := No_Location; + Xrefs.Table (Indx).Eun := Get_Source_Unit (Loc); + Xrefs.Table (Indx).Lun := No_Unit; + Set_Has_Xref_Entry (Tref); + end if; + + -- Collect inherited primitive operations that may be + -- declared in another unit and have no visible reference + -- in the current one. + + if Is_Type (Ent) + and then Is_Tagged_Type (Ent) + and then Is_Derived_Type (Ent) + and then Ent = Base_Type (Ent) + and then In_Extended_Main_Source_Unit (Ent) + then - -- Sort the references + declare + Op_List : Elist_Id := Primitive_Operations (Ent); + Op : Elmt_Id; + Prim : Entity_Id; - GNAT.Heap_Sort_A.Sort - (Integer (Nrefs), - Move'Unrestricted_Access, - Lt'Unrestricted_Access); + function Parent_Op (E : Entity_Id) return Entity_Id; + -- Find original operation, which may be inherited + -- through several derivations. - -- Now output the references + function Parent_Op (E : Entity_Id) return Entity_Id is + Orig_Op : Entity_Id := Alias (E); + begin + if No (Orig_Op) then + return Empty; + + elsif not Comes_From_Source (E) + and then not Has_Xref_Entry (Orig_Op) + and then Comes_From_Source (Orig_Op) + then + return Orig_Op; + else + return Parent_Op (Orig_Op); + end if; + end Parent_Op; + + begin + Op := First_Elmt (Op_List); + + while Present (Op) loop + + Prim := Parent_Op (Node (Op)); + + if Present (Prim) then + Xrefs.Increment_Last; + Indx := Xrefs.Last; + Loc := Original_Location (Sloc (Prim)); + Xrefs.Table (Indx).Ent := Prim; + Xrefs.Table (Indx).Loc := No_Location; + Xrefs.Table (Indx).Eun := + Get_Source_Unit (Sloc (Prim)); + Xrefs.Table (Indx).Lun := No_Unit; + Set_Has_Xref_Entry (Prim); + end if; + + Next_Elmt (Op); + end loop; + end; + end if; + + J := J + 1; + end loop; + end; + + -- Now we have all the references, including those for any embedded + -- type references, so we can sort them, and output them. Output_Refs : declare + Nrefs : Nat := Xrefs.Last; + -- Number of references in table. This value may get reset + -- (reduced) when we eliminate duplicate reference entries. + + Rnums : array (0 .. Nrefs) of Nat; + -- This array contains numbers of references in the Xrefs table. + -- This list is sorted in output order. The extra 0'th entry is + -- convenient for the call to sort. When we sort the table, we + -- move the entries in Rnums around, but we do not move the + -- original table entries. + Curxu : Unit_Number_Type; -- Current xref unit @@ -483,9 +880,71 @@ package body Lib.Xref is Trunit : Unit_Number_Type; -- Unit number for type reference + function Lt (Op1, Op2 : Natural) return Boolean; + -- Comparison function for Sort call + function Name_Change (X : Entity_Id) return Boolean; -- Determines if entity X has a different simple name from Curent + procedure Move (From : Natural; To : Natural); + -- Move procedure for Sort call + + -------- + -- Lt -- + -------- + + function Lt (Op1, Op2 : Natural) return Boolean is + T1 : Xref_Entry renames Xrefs.Table (Rnums (Nat (Op1))); + T2 : Xref_Entry renames Xrefs.Table (Rnums (Nat (Op2))); + + begin + -- First test. If entity is in different unit, sort by unit + + if T1.Eun /= T2.Eun then + return Dependency_Num (T1.Eun) < Dependency_Num (T2.Eun); + + -- Second test, within same unit, sort by entity Sloc + + elsif T1.Def /= T2.Def then + return T1.Def < T2.Def; + + -- Third test, sort definitions ahead of references + + elsif T1.Loc = No_Location then + return True; + + elsif T2.Loc = No_Location then + return False; + + -- Fourth test, for same entity, sort by reference location unit + + elsif T1.Lun /= T2.Lun then + return Dependency_Num (T1.Lun) < Dependency_Num (T2.Lun); + + -- Fifth test order of location within referencing unit + + elsif T1.Loc /= T2.Loc then + return T1.Loc < T2.Loc; + + -- Finally, for two locations at the same address, we prefer + -- the one that does NOT have the type 'r' so that a modification + -- or extension takes preference, when there are more than one + -- reference at the same location. + + else + return T2.Typ = 'r'; + end if; + end Lt; + + ---------- + -- Move -- + ---------- + + procedure Move (From : Natural; To : Natural) is + begin + Rnums (Nat (To)) := Rnums (Nat (From)); + end Move; + ----------------- -- Name_Change -- ----------------- @@ -505,15 +964,64 @@ package body Lib.Xref is -- Start of processing for Output_Refs begin + -- Capture the definition Sloc values. We delay doing this till now, + -- since at the time the reference or definition is made, private + -- types may be swapped, and the Sloc value may be incorrect. We + -- also set up the pointer vector for the sort. + + for J in 1 .. Nrefs loop + Rnums (J) := J; + Xrefs.Table (J).Def := + Original_Location (Sloc (Xrefs.Table (J).Ent)); + end loop; + + -- Sort the references + + GNAT.Heap_Sort_A.Sort + (Integer (Nrefs), + Move'Unrestricted_Access, + Lt'Unrestricted_Access); + + -- Eliminate duplicate entries + + declare + NR : constant Nat := Nrefs; + + begin + -- We need this test for NR because if we force ALI file + -- generation in case of errors detected, it may be the case + -- that Nrefs is 0, so we should not reset it here + + if NR >= 2 then + Nrefs := 1; + + for J in 2 .. NR loop + if Xrefs.Table (Rnums (J)) /= + Xrefs.Table (Rnums (Nrefs)) + then + Nrefs := Nrefs + 1; + Rnums (Nrefs) := Rnums (J); + end if; + end loop; + end if; + end; + + -- Initialize loop through references + Curxu := No_Unit; Curent := Empty; Curdef := No_Location; Curru := No_Unit; Crloc := No_Location; - for Refno in 1 .. Nrefs loop + -- Loop to output references + for Refno in 1 .. Nrefs loop Output_One_Ref : declare + P2 : Source_Ptr; + WC : Char_Code; + Err : Boolean; + Ent : Entity_Id; XE : Xref_Entry renames Xrefs.Table (Rnums (Refno)); -- The current entry to be accessed @@ -521,15 +1029,9 @@ package body Lib.Xref is P : Source_Ptr; -- Used to index into source buffer to get entity name - P2 : Source_Ptr; - WC : Char_Code; - Err : Boolean; - Ent : Entity_Id; - Sav : Entity_Id; - Left : Character; Right : Character; - -- Used for {} or <> for type reference + -- Used for {} or <> or () for type reference procedure Output_Instantiation_Refs (Loc : Source_Ptr); -- Recursive procedure to output instantiation references for @@ -543,6 +1045,7 @@ package body Lib.Xref is procedure Output_Instantiation_Refs (Loc : Source_Ptr) is Iloc : constant Source_Ptr := Instantiation_Location (Loc); Lun : Unit_Number_Type; + Cu : constant Unit_Number_Type := Curru; begin -- Nothing to do if this is not an instantiation @@ -557,7 +1060,7 @@ package body Lib.Xref is Lun := Get_Source_Unit (Iloc); if Lun /= Curru then - Curru := XE.Lun; + Curru := Lun; Write_Info_Nat (Dependency_Num (Curru)); Write_Info_Char ('|'); end if; @@ -571,6 +1074,7 @@ package body Lib.Xref is -- Output final ] after call to get proper nesting Write_Info_Char (']'); + Curru := Cu; return; end Output_Instantiation_Refs; @@ -628,7 +1132,7 @@ package body Lib.Xref is Ent := Underlying_Type (Etype (XE.Ent)); if Present (Ent) then - Ctyp := Xref_Entity_Letters (Ekind (Ent)); + Ctyp := Fold_Lower (Xref_Entity_Letters (Ekind (Ent))); end if; end if; @@ -646,20 +1150,41 @@ package body Lib.Xref is end if; end if; + -- Special handling for abstract types and operations. + + if Is_Abstract (XE.Ent) then + + if Ctyp = 'U' then + Ctyp := 'x'; -- abstract procedure + + elsif Ctyp = 'V' then + Ctyp := 'y'; -- abstract function + + elsif Ctyp = 'R' then + Ctyp := 'H'; -- abstract type + end if; + end if; + -- Only output reference if interesting type of entity, - -- and suppress self references. Also suppress definitions - -- of body formals (we only treat these as references, and - -- the references were separately recorded). - - if Ctyp /= ' ' - and then XE.Loc /= XE.Def - and then (not Is_Formal (XE.Ent) - or else No (Spec_Entity (XE.Ent))) + -- and suppress self references, except for bodies that + -- act as specs. Also suppress definitions of body formals + -- (we only treat these as references, and the references + -- were separately recorded). + + if Ctyp = ' ' + or else (XE.Loc = XE.Def + and then + (XE.Typ /= 'b' + or else not Is_Subprogram (XE.Ent))) + or else (Is_Formal (XE.Ent) + and then Present (Spec_Entity (XE.Ent))) then + null; + + else -- Start new Xref section if new xref unit if XE.Eun /= Curxu then - if Write_Info_Col > 1 then Write_Info_EOL; end if; @@ -705,11 +1230,92 @@ package body Lib.Xref is -- Write level information - if Is_Public (Curent) and then not Is_Hidden (Curent) then - Write_Info_Char ('*'); - else - Write_Info_Char (' '); - end if; + Write_Level_Info : declare + function Is_Visible_Generic_Entity + (E : Entity_Id) return Boolean; + -- Check whether E is declared in the visible part + -- of a generic package. For source navigation + -- purposes, treat this as a visible entity. + + function Is_Private_Record_Component + (E : Entity_Id) return Boolean; + -- Check whether E is a non-inherited component of a + -- private extension. Even if the enclosing record is + -- public, we want to treat the component as private + -- for navigation purposes. + + --------------------------------- + -- Is_Private_Record_Component -- + --------------------------------- + + function Is_Private_Record_Component + (E : Entity_Id) return Boolean + is + S : constant Entity_Id := Scope (E); + begin + return + Ekind (E) = E_Component + and then Nkind (Declaration_Node (S)) = + N_Private_Extension_Declaration + and then Original_Record_Component (E) = E; + end Is_Private_Record_Component; + + ------------------------------- + -- Is_Visible_Generic_Entity -- + ------------------------------- + + function Is_Visible_Generic_Entity + (E : Entity_Id) return Boolean + is + Par : Node_Id; + + begin + if Ekind (Scope (E)) /= E_Generic_Package then + return False; + end if; + + Par := Parent (E); + while Present (Par) loop + if + Nkind (Par) = N_Generic_Package_Declaration + then + -- Entity is a generic formal + + return False; + + elsif + Nkind (Parent (Par)) = N_Package_Specification + then + return + Is_List_Member (Par) + and then List_Containing (Par) = + Visible_Declarations (Parent (Par)); + else + Par := Parent (Par); + end if; + end loop; + + return False; + end Is_Visible_Generic_Entity; + + -- Start of processing for Write_Level_Info + + begin + if Is_Hidden (Curent) + or else Is_Private_Record_Component (Curent) + then + Write_Info_Char (' '); + + elsif + Is_Public (Curent) + or else Is_Visible_Generic_Entity (Curent) + then + Write_Info_Char ('*'); + + else + Write_Info_Char (' '); + end if; + end Write_Level_Info; -- Output entity name. We use the occurrence from the -- actual source program at the definition point @@ -799,89 +1405,16 @@ package body Lib.Xref is (Int (Get_Column_Number (Sloc (Rref)))); end if; - -- See if we have a type reference - - Tref := XE.Ent; - Left := '{'; - Right := '}'; - - loop - Sav := Tref; - - -- Processing for types - - if Is_Type (Tref) then - - -- Case of base type - - if Base_Type (Tref) = Tref then - - -- If derived, then get first subtype - - if Tref /= Etype (Tref) then - Tref := First_Subtype (Etype (Tref)); - - -- Set brackets for derived type, but don't - -- override pointer case since the fact that - -- something is a pointer is more important - - if Left /= '(' then - Left := '<'; - Right := '>'; - end if; - - -- If non-derived ptr, get designated type - - elsif Is_Access_Type (Tref) then - Tref := Designated_Type (Tref); - Left := '('; - Right := ')'; + -- Indicate that the entity is in the unit + -- of the current xref xection. - -- For other non-derived base types, nothing - - else - exit; - end if; - - -- For a subtype, go to ancestor subtype - - else - Tref := Ancestor_Subtype (Tref); - - -- If no ancestor subtype, go to base type - - if No (Tref) then - Tref := Base_Type (Sav); - end if; - end if; - - -- For objects, functions, enum literals, - -- just get type from Etype field. - - elsif Is_Object (Tref) - or else Ekind (Tref) = E_Enumeration_Literal - or else Ekind (Tref) = E_Function - or else Ekind (Tref) = E_Operator - then - Tref := Etype (Tref); - - -- For anything else, exit - - else - exit; - end if; + Curru := Curxu; - -- Exit if no type reference, or we are stuck in - -- some loop trying to find the type reference, or - -- if the type is standard void type (the latter is - -- an implementation artifact that should not show - -- up in the generated cross-references). + -- See if we have a type reference and if so output - exit when No (Tref) - or else Tref = Sav - or else Tref = Standard_Void_Type; + Get_Type_Reference (XE.Ent, Tref, Left, Right); - -- Here we have a type reference to output + if Present (Tref) then -- Case of standard entity, output name @@ -889,22 +1422,10 @@ package body Lib.Xref is Write_Info_Char (Left); Write_Info_Name (Chars (Tref)); Write_Info_Char (Right); - exit; -- Case of source entity, output location - elsif Comes_From_Source (Tref) then - - -- Do not output type reference if referenced - -- entity is not in the main unit and is itself - -- not referenced, since otherwise the reference - -- will dangle. - - exit when not Referenced (Tref) - and then not In_Extended_Main_Source_Unit (Tref); - - -- Output the reference - + else Write_Info_Char (Left); Trunit := Get_Source_Unit (Sloc (Tref)); @@ -937,19 +1458,17 @@ package body Lib.Xref is Write_Info_Nat (Int (Get_Column_Number (Sloc (Tref)))); - Write_Info_Char (Right); - exit; - -- If non-standard, non-source entity, keep looking + -- If the type comes from an instantiation, + -- add the corresponding info. - else - null; + Output_Instantiation_Refs (Sloc (Tref)); + Write_Info_Char (Right); end if; - end loop; + end if; -- End of processing for entity output - Curru := Curxu; Crloc := No_Location; end if; @@ -979,6 +1498,14 @@ package body Lib.Xref is Write_Info_Nat (Int (Get_Logical_Line_Number (XE.Loc))); Write_Info_Char (XE.Typ); + + if Is_Overloadable (XE.Ent) + and then Is_Imported (XE.Ent) + and then XE.Typ = 'b' + then + Output_Import_Export_Info (XE.Ent); + end if; + Write_Info_Nat (Int (Get_Column_Number (XE.Loc))); Output_Instantiation_Refs (Sloc (XE.Ent)); |