1 ------------------------------------------------------------------------------
3 -- GNAT COMPILER COMPONENTS --
10 -- Copyright (C) 1996-2002 Free Software Foundation, Inc. --
12 -- GNAT is free software; you can redistribute it and/or modify it under --
13 -- terms of the GNU General Public License as published by the Free Soft- --
14 -- ware Foundation; either version 2, or (at your option) any later ver- --
15 -- sion. GNAT is distributed in the hope that it will be useful, but WITH- --
16 -- OUT ANY WARRANTY; without even the implied warranty of MERCHANTABILITY --
17 -- or FITNESS FOR A PARTICULAR PURPOSE. See the GNU General Public License --
18 -- for more details. You should have received a copy of the GNU General --
19 -- Public License distributed with GNAT; see file COPYING. If not, write --
20 -- to the Free Software Foundation, 59 Temple Place - Suite 330, Boston, --
21 -- MA 02111-1307, USA. --
23 -- GNAT was originally developed by the GNAT team at New York University. --
24 -- Extensive contributions were provided by Ada Core Technologies Inc. --
26 ------------------------------------------------------------------------------
28 with Alloc
; use Alloc
;
29 with Atree
; use Atree
;
30 with Debug
; use Debug
;
31 with Einfo
; use Einfo
;
32 with Exp_Util
; use Exp_Util
;
33 with Freeze
; use Freeze
;
35 with Hostparm
; use Hostparm
;
36 with Namet
; use Namet
;
37 with Nlists
; use Nlists
;
38 with Nmake
; use Nmake
;
40 with Output
; use Output
;
41 with Sem_Eval
; use Sem_Eval
;
42 with Sem_Util
; use Sem_Util
;
43 with Sinfo
; use Sinfo
;
44 with Snames
; use Snames
;
45 with Stand
; use Stand
;
46 with Stringt
; use Stringt
;
48 with Urealp
; use Urealp
;
52 package body Exp_Dbug
is
54 -- The following table is used to queue up the entities passed as
55 -- arguments to Qualify_Entity_Names for later processing when
56 -- Qualify_All_Entity_Names is called.
58 package Name_Qualify_Units
is new Table
.Table
(
59 Table_Component_Type
=> Node_Id
,
60 Table_Index_Type
=> Nat
,
62 Table_Initial
=> Alloc
.Name_Qualify_Units_Initial
,
63 Table_Increment
=> Alloc
.Name_Qualify_Units_Increment
,
64 Table_Name
=> "Name_Qualify_Units");
66 -- Define hash table for compressed debug names
68 -- This hash table keeps track of qualification prefix strings
69 -- that have been compressed. The element is the corresponding
70 -- hash value used in the compressed symbol.
72 type Hindex
is range 0 .. 4096;
73 -- Type to define range of headers
75 function SHash
(S
: String_Ptr
) return Hindex
;
76 -- Hash function for this table
78 function SEq
(F1
, F2
: String_Ptr
) return Boolean;
79 -- Equality function for this table
86 No_Elmt
: Elmt
:= (0, null);
88 package CDN
is new GNAT
.HTable
.Simple_HTable
(
91 No_Element
=> No_Elmt
,
96 --------------------------------
97 -- Use of Qualification Flags --
98 --------------------------------
100 -- There are two flags used to keep track of qualification of entities
102 -- Has_Fully_Qualified_Name
103 -- Has_Qualified_Name
105 -- The difference between these is as follows. Has_Qualified_Name is
106 -- set to indicate that the name has been qualified as required by the
107 -- spec of this package. As described there, this may involve the full
108 -- qualification for the name, but for some entities, notably procedure
109 -- local variables, this full qualification is not required.
111 -- The flag Has_Fully_Qualified_Name is set if indeed the name has been
112 -- fully qualified in the Ada sense. If Has_Fully_Qualified_Name is set,
113 -- then Has_Qualified_Name is also set, but the other way round is not
116 -- Consider the following example:
123 -- Here B is a procedure local variable, so it does not need fully
124 -- qualification. The flag Has_Qualified_Name will be set on the
125 -- first attempt to qualify B, to indicate that the job is done
126 -- and need not be redone.
128 -- But Y is qualified as x__y, since procedures are always fully
129 -- qualified, so the first time that an attempt is made to qualify
130 -- the name y, it will be replaced by x__y, and both flags are set.
132 -- Why the two flags? Well there are cases where we derive type names
133 -- from object names. As noted in the spec, type names are always
134 -- fully qualified. Suppose for example that the backend has to build
135 -- a padded type for variable B. then it will construct the PAD name
136 -- from B, but it requires full qualification, so the fully qualified
137 -- type name will be x__b___PAD. The two flags allow the circuit for
138 -- building this name to realize efficiently that b needs further
145 -- The string defined here (and its associated length) is used to
146 -- gather the homonym string that will be appended to Name_Buffer
147 -- when the name is complete. Strip_Suffixes appends to this string
148 -- as does Append_Homonym_Number, and Output_Homonym_Numbers_Suffix
149 -- appends the string to the end of Name_Buffer.
151 Homonym_Numbers
: String (1 .. 256);
152 Homonym_Len
: Natural := 0;
154 ----------------------
155 -- Local Procedures --
156 ----------------------
158 procedure Add_Uint_To_Buffer
(U
: Uint
);
159 -- Add image of universal integer to Name_Buffer, updating Name_Len
161 procedure Add_Real_To_Buffer
(U
: Ureal
);
162 -- Add nnn_ddd to Name_Buffer, where nnn and ddd are integer values of
163 -- the normalized numerator and denominator of the given real value.
165 procedure Append_Homonym_Number
(E
: Entity_Id
);
166 -- If the entity E has homonyms in the same scope, then make an entry
167 -- in the Homonym_Numbers array, bumping Homonym_Count accordingly.
169 function Bounds_Match_Size
(E
: Entity_Id
) return Boolean;
170 -- Determine whether the bounds of E match the size of the type. This is
171 -- used to determine whether encoding is required for a discrete type.
173 function CDN_Hash
(S
: String) return Word
;
174 -- This is the hash function used to compress debug symbols. The string
175 -- S is the prefix which is a list of qualified names separated by double
176 -- underscore (no trailing double underscore). The returned value is the
177 -- hash value used in the compressed names. It is also used for the hash
178 -- table used to keep track of what prefixes have been compressed so far.
180 procedure Compress_Debug_Name
(E
: Entity_Id
);
181 -- If the name of the entity E is too long, or compression is to be
182 -- attempted on all names (Compress_Debug_Names set), then an attempt
183 -- is made to compress the name of the entity.
185 function Double_Underscore
(S
: String; J
: Natural) return Boolean;
186 -- Returns True if J is the start of a double underscore
187 -- sequence in the string S (defined as two underscores
188 -- which are preceded and followed by a non-underscore)
190 procedure Output_Homonym_Numbers_Suffix
;
191 -- If homonym numbers are stored, then output them into Name_Buffer.
193 procedure Prepend_String_To_Buffer
(S
: String);
194 -- Prepend given string to the contents of the string buffer, updating
195 -- the value in Name_Len (i.e. string is added at start of buffer).
197 procedure Prepend_Uint_To_Buffer
(U
: Uint
);
198 -- Prepend image of universal integer to Name_Buffer, updating Name_Len
200 procedure Put_Hex
(W
: Word
; N
: Natural);
201 -- Output W as 8 hex digits (0-9, a-f) in Name_Buffer (N .. N + 7)
203 procedure Qualify_Entity_Name
(Ent
: Entity_Id
);
204 -- If not already done, replaces the Chars field of the given entity
205 -- with the appropriate fully qualified name.
207 procedure Strip_Suffixes
(BNPE_Suffix_Found
: in out Boolean);
208 -- Given an qualified entity name in Name_Buffer, remove any plain X or
209 -- X{nb} qualification suffix. The contents of Name_Buffer is not changed
210 -- but Name_Len may be adjusted on return to remove the suffix. If a
211 -- BNPE suffix is found and stripped, then BNPE_Suffix_Found is set to
212 -- True. If no suffix is found, then BNPE_Suffix_Found is not modified.
213 -- This routine also searches for a homonym suffix, and if one is found
214 -- it is also stripped, and the entries are added to the global homonym
215 -- list (Homonym_Numbers) so that they can later be put back.
217 ------------------------
218 -- Add_Real_To_Buffer --
219 ------------------------
221 procedure Add_Real_To_Buffer
(U
: Ureal
) is
223 Add_Uint_To_Buffer
(Norm_Num
(U
));
224 Add_Str_To_Name_Buffer
("_");
225 Add_Uint_To_Buffer
(Norm_Den
(U
));
226 end Add_Real_To_Buffer
;
228 ------------------------
229 -- Add_Uint_To_Buffer --
230 ------------------------
232 procedure Add_Uint_To_Buffer
(U
: Uint
) is
235 Add_Uint_To_Buffer
(-U
);
236 Add_Char_To_Name_Buffer
('m');
238 UI_Image
(U
, Decimal
);
239 Add_Str_To_Name_Buffer
(UI_Image_Buffer
(1 .. UI_Image_Length
));
241 end Add_Uint_To_Buffer
;
243 ---------------------------
244 -- Append_Homonym_Number --
245 ---------------------------
247 procedure Append_Homonym_Number
(E
: Entity_Id
) is
249 procedure Add_Nat_To_H
(Nr
: Nat
);
250 -- Little procedure to append Nr to Homonym_Numbers
256 procedure Add_Nat_To_H
(Nr
: Nat
) is
259 Add_Nat_To_H
(Nr
/ 10);
262 Homonym_Len
:= Homonym_Len
+ 1;
263 Homonym_Numbers
(Homonym_Len
) :=
264 Character'Val (Nr
mod 10 + Character'Pos ('0'));
267 -- Start of processing for Append_Homonym_Number
270 if Has_Homonym
(E
) then
272 H
: Entity_Id
:= Homonym
(E
);
276 while Present
(H
) loop
277 if (Scope
(H
) = Scope
(E
)) then
284 if Homonym_Len
> 0 then
285 Homonym_Len
:= Homonym_Len
+ 1;
286 Homonym_Numbers
(Homonym_Len
) := '_';
292 end Append_Homonym_Number
;
294 -----------------------
295 -- Bounds_Match_Size --
296 -----------------------
298 function Bounds_Match_Size
(E
: Entity_Id
) return Boolean is
302 if not Is_OK_Static_Subtype
(E
) then
305 elsif Is_Integer_Type
(E
)
306 and then Subtypes_Statically_Match
(E
, Base_Type
(E
))
310 -- Here we check if the static bounds match the natural size, which
311 -- is the size passed through with the debugging information. This
312 -- is the Esize rounded up to 8, 16, 32 or 64 as appropriate.
316 Umark
: constant Uintp
.Save_Mark
:= Uintp
.Mark
;
320 if Esize
(E
) <= 8 then
322 elsif Esize
(E
) <= 16 then
324 elsif Esize
(E
) <= 32 then
330 if Is_Modular_Integer_Type
(E
) or else Is_Enumeration_Type
(E
) then
332 Expr_Rep_Value
(Type_Low_Bound
(E
)) = 0
334 2 ** Siz
- Expr_Rep_Value
(Type_High_Bound
(E
)) = 1;
338 Expr_Rep_Value
(Type_Low_Bound
(E
)) + 2 ** (Siz
- 1) = 0
340 2 ** (Siz
- 1) - Expr_Rep_Value
(Type_High_Bound
(E
)) = 1;
347 end Bounds_Match_Size
;
353 function CDN_Hash
(S
: String) return Word
is
356 function Rotate_Left
(Value
: Word
; Amount
: Natural) return Word
;
357 pragma Import
(Intrinsic
, Rotate_Left
);
361 for J
in S
'Range loop
362 H
:= Rotate_Left
(H
, 3) + Character'Pos (S
(J
));
368 -------------------------
369 -- Compress_Debug_Name --
370 -------------------------
372 procedure Compress_Debug_Name
(E
: Entity_Id
) is
378 if not Compress_Debug_Names
379 and then Length_Of_Name
(Chars
(E
)) <= Max_Debug_Name_Length
384 Get_Name_String
(Chars
(E
));
386 -- Find rightmost double underscore
390 exit when Double_Underscore
(Name_Buffer
, Ptr
);
392 -- Cannot compress if no double underscore anywhere
401 -- At this stage we have
403 -- Name_Buffer (1 .. Ptr - 1) string to compress
404 -- Name_Buffer (Ptr) underscore
405 -- Name_Buffer (Ptr + 1) underscore
406 -- Name_Buffer (Ptr + 2 .. Name_Len) simple name to retain
408 -- See if we already have an entry for the compression string
410 -- No point in compressing if it does not make things shorter
412 if Name_Len
<= (2 + 8 + 1) + (Name_Len
- (Ptr
+ 1)) then
416 -- Do not compress any reference to entity in internal file
418 if Name_Buffer
(1 .. 5) = "ada__"
420 Name_Buffer
(1 .. 8) = "system__"
422 Name_Buffer
(1 .. 6) = "gnat__"
424 Name_Buffer
(1 .. 12) = "interfaces__"
426 (OpenVMS
and then Name_Buffer
(1 .. 5) = "dec__")
431 Sptr
:= Name_Buffer
(1 .. Ptr
- 1)'Unrestricted_Access;
432 Cod
:= CDN
.Get
(Sptr
).W
;
435 Cod
:= CDN_Hash
(Sptr
.all);
436 Sptr
:= new String'(Sptr.all);
437 CDN.Set (Sptr, (Cod, Sptr));
440 Name_Buffer (1) := 'X
';
441 Name_Buffer (2) := 'C
';
443 Name_Buffer (11) := '_
';
444 Name_Buffer (12 .. Name_Len - Ptr + 10) :=
445 Name_Buffer (Ptr + 2 .. Name_Len);
446 Name_Len := Name_Len - Ptr + 10;
448 Set_Chars (E, Name_Enter);
449 end Compress_Debug_Name;
451 --------------------------------
452 -- Debug_Renaming_Declaration --
453 --------------------------------
455 function Debug_Renaming_Declaration (N : Node_Id) return Node_Id is
456 Loc : constant Source_Ptr := Sloc (N);
457 Ent : constant Node_Id := Defining_Entity (N);
458 Nam : constant Node_Id := Name (N);
466 function Output_Subscript (N : Node_Id; S : String) return Boolean;
467 -- Outputs a single subscript value as ?nnn (subscript is compile
468 -- time known value with value nnn) or as ?e (subscript is local
469 -- constant with name e), where S supplies the proper string to
470 -- use for ?. Returns False if the subscript is not of an appropriate
471 -- type to output in one of these two forms. The result is prepended
472 -- to the name stored in Name_Buffer.
474 ----------------------
475 -- Output_Subscript --
476 ----------------------
478 function Output_Subscript (N : Node_Id; S : String) return Boolean is
480 if Compile_Time_Known_Value (N) then
481 Prepend_Uint_To_Buffer (Expr_Value (N));
483 elsif Nkind (N) = N_Identifier
484 and then Scope (Entity (N)) = Scope (Ent)
485 and then Ekind (Entity (N)) = E_Constant
487 Prepend_String_To_Buffer (Get_Name_String (Chars (Entity (N))));
493 Prepend_String_To_Buffer (S);
495 end Output_Subscript;
497 -- Start of processing for Debug_Renaming_Declaration
500 if not Comes_From_Source (N) then
504 -- Prepare entity name for type declaration
506 Get_Name_String (Chars (Ent));
509 when N_Object_Renaming_Declaration =>
510 Add_Str_To_Name_Buffer ("___XR");
512 when N_Exception_Renaming_Declaration =>
513 Add_Str_To_Name_Buffer ("___XRE");
515 when N_Package_Renaming_Declaration =>
516 Add_Str_To_Name_Buffer ("___XRP");
524 -- Get renamed entity and compute suffix
534 when N_Expanded_Name =>
536 -- The entity field for an N_Expanded_Name is on the
537 -- expanded name node itself, so we are done here too.
541 when N_Selected_Component =>
542 Prepend_String_To_Buffer
543 (Get_Name_String (Chars (Selector_Name (Ren))));
544 Prepend_String_To_Buffer ("XR");
547 when N_Indexed_Component =>
549 X : Node_Id := Last (Expressions (Ren));
552 while Present (X) loop
553 if not Output_Subscript (X, "XS") then
554 Set_Materialize_Entity (Ent);
566 Typ := Etype (First_Index (Etype (Nam)));
568 if not Output_Subscript (Type_High_Bound (Typ), "XS") then
569 Set_Materialize_Entity (Ent);
573 if not Output_Subscript (Type_Low_Bound (Typ), "XL") then
574 Set_Materialize_Entity (Ent);
580 when N_Explicit_Dereference =>
581 Prepend_String_To_Buffer ("XA");
584 -- For now, anything else simply results in no translation
587 Set_Materialize_Entity (Ent);
592 Prepend_String_To_Buffer ("___XE");
594 -- For now, the literal name contains only the suffix. The Entity_Id
595 -- value for the name is used to create a link from this literal name
596 -- to the renamed entity using the Debug_Renaming_Link field. Then the
597 -- Qualify_Entity_Name procedure uses this link to create the proper
598 -- fully qualified name.
600 -- The reason we do things this way is that we really need to copy the
601 -- qualification of the renamed entity, and it is really much easier to
602 -- do this after the renamed entity has itself been fully qualified.
604 Lit := Make_Defining_Identifier (Loc, Chars => Name_Enter);
605 Set_Debug_Renaming_Link (Lit, Entity (Ren));
607 -- Return the appropriate enumeration type
609 Def := Make_Defining_Identifier (Loc, Chars => Rnm);
611 Make_Full_Type_Declaration (Loc,
612 Defining_Identifier => Def,
614 Make_Enumeration_Type_Definition (Loc,
615 Literals => New_List (Lit)));
617 Set_Needs_Debug_Info (Def);
618 Set_Needs_Debug_Info (Lit);
620 Set_Discard_Names (Defining_Identifier (Res));
623 -- If we get an exception, just figure it is a case that we cannot
624 -- successfully handle using our current approach, since this is
625 -- only for debugging, no need to take the compilation with us!
629 return Make_Null_Statement (Loc);
630 end Debug_Renaming_Declaration;
632 -----------------------
633 -- Double_Underscore --
634 -----------------------
636 function Double_Underscore (S : String; J : Natural) return Boolean is
638 if J = S'First or else J > S'Last - 2 then
643 and then S (J + 1) = '_
'
644 and then S (J - 1) /= '_
'
645 and then S (J + 2) /= '_
';
647 end Double_Underscore;
649 ------------------------------
650 -- Generate_Auxiliary_Types --
651 ------------------------------
653 -- Note: right now there is only one auxiliary type to be generated,
654 -- namely the enumeration type for the compression sequences if used.
656 procedure Generate_Auxiliary_Types is
657 Loc : constant Source_Ptr := Sloc (Cunit (Current_Sem_Unit));
665 Literal_List : List_Id := New_List;
666 -- Gathers the list of literals for the declaration
668 procedure Output_Literal;
669 -- Adds suffix of form Xnnn to name in Name_Buffer, where nnn is
670 -- a serial number that is one greater on each call, and then
671 -- builds an enumeration literal and adds it to the literal list.
674 -- Current serial number
676 procedure Output_Literal is
678 Serial := Serial + 1;
679 Add_Char_To_Name_Buffer ('X
');
680 Add_Nat_To_Name_Buffer (Serial);
683 Make_Defining_Identifier (Loc,
685 Set_Has_Qualified_Name (Lit, True);
686 Append (Lit, Literal_List);
689 -- Start of processing for Auxiliary_Types
694 while E.S /= null loop
696 -- We have E.S a String_Ptr that contains a string of the form:
700 -- In E.W is a 32-bit word representing the hash value
702 -- Our mission is to construct a type
704 -- type XChhhhhhhh is (b,c,d);
706 -- where hhhhhhhh is the 8 hex digits of the E.W value.
707 -- and append this type declaration to the result list
709 Name_Buffer (1) := 'X
';
710 Name_Buffer (2) := 'C
';
717 while Ptr <= E.S'Last loop
719 or else Double_Underscore (E.S.all, Ptr + 1)
721 Name_Len := Ptr - Start + 1;
722 Name_Buffer (1 .. Name_Len) := E.S (Start .. Ptr);
734 Name_Buffer (1) := 'X
';
735 Name_Buffer (2) := 'C
';
739 Make_Defining_Identifier (Loc,
741 Set_Has_Qualified_Name (Code, True);
743 Insert_Library_Level_Action (
744 Make_Full_Type_Declaration (Loc,
745 Defining_Identifier => Code,
747 Make_Enumeration_Type_Definition (Loc,
748 Literals => Literal_List)));
750 -- We have to manually freeze this entity, since it is inserted
751 -- very late on into the tree, and otherwise will not be frozen.
752 -- No freeze actions are generated, so we can discard the result.
754 Discard := Freeze_Entity (Code, Loc);
756 end Generate_Auxiliary_Types;
758 ----------------------
759 -- Get_Encoded_Name --
760 ----------------------
762 -- Note: see spec for details on encodings
764 procedure Get_Encoded_Name (E : Entity_Id) is
765 Has_Suffix : Boolean;
768 Get_Name_String (Chars (E));
770 -- Nothing to do if we do not have a type
774 -- Or if this is an enumeration base type
776 or else (Is_Enumeration_Type (E)
777 and then E = Base_Type (E))
779 -- Or if this is a dummy type for a renaming
781 or else (Name_Len >= 3 and then
782 Name_Buffer (Name_Len - 2 .. Name_Len) = "_XR")
784 or else (Name_Len >= 4 and then
785 (Name_Buffer (Name_Len - 3 .. Name_Len) = "_XRE"
787 Name_Buffer (Name_Len - 3 .. Name_Len) = "_XRP"))
789 -- For all these cases, just return the name unchanged
792 Name_Buffer (Name_Len + 1) := ASCII.Nul;
800 if Is_Fixed_Point_Type (E) then
801 Get_External_Name_With_Suffix (E, "XF_");
802 Add_Real_To_Buffer (Delta_Value (E));
804 if Small_Value (E) /= Delta_Value (E) then
805 Add_Str_To_Name_Buffer ("_");
806 Add_Real_To_Buffer (Small_Value (E));
809 -- Vax floating-point case
811 elsif Vax_Float (E) then
813 if Digits_Value (Base_Type (E)) = 6 then
814 Get_External_Name_With_Suffix (E, "XFF");
816 elsif Digits_Value (Base_Type (E)) = 9 then
817 Get_External_Name_With_Suffix (E, "XFF");
820 pragma Assert (Digits_Value (Base_Type (E)) = 15);
821 Get_External_Name_With_Suffix (E, "XFG");
824 -- Discrete case where bounds do not match size
826 elsif Is_Discrete_Type (E)
827 and then not Bounds_Match_Size (E)
829 if Has_Biased_Representation (E) then
830 Get_External_Name_With_Suffix (E, "XB");
832 Get_External_Name_With_Suffix (E, "XD");
836 Lo : constant Node_Id := Type_Low_Bound (E);
837 Hi : constant Node_Id := Type_High_Bound (E);
839 Lo_Stat : constant Boolean := Is_OK_Static_Expression (Lo);
840 Hi_Stat : constant Boolean := Is_OK_Static_Expression (Hi);
842 Lo_Discr : constant Boolean :=
843 Nkind (Lo) = N_Identifier
845 Ekind (Entity (Lo)) = E_Discriminant;
847 Hi_Discr : constant Boolean :=
848 Nkind (Hi) = N_Identifier
850 Ekind (Entity (Hi)) = E_Discriminant;
852 Lo_Encode : constant Boolean := Lo_Stat or Lo_Discr;
853 Hi_Encode : constant Boolean := Hi_Stat or Hi_Discr;
856 if Lo_Encode or Hi_Encode then
859 Add_Str_To_Name_Buffer ("LU_");
861 Add_Str_To_Name_Buffer ("L_");
864 Add_Str_To_Name_Buffer ("U_");
868 Add_Uint_To_Buffer (Expr_Rep_Value (Lo));
870 Get_Name_String_And_Append (Chars (Entity (Lo)));
873 if Lo_Encode and Hi_Encode then
874 Add_Str_To_Name_Buffer ("__");
878 Add_Uint_To_Buffer (Expr_Rep_Value (Hi));
880 Get_Name_String_And_Append (Chars (Entity (Hi)));
885 -- For all other cases, the encoded name is the normal type name
889 Get_External_Name (E, Has_Suffix);
892 if Debug_Flag_B and then Has_Suffix then
893 Write_Str ("**** type ");
894 Write_Name (Chars (E));
895 Write_Str (" is encoded as ");
896 Write_Str (Name_Buffer (1 .. Name_Len));
900 Name_Buffer (Name_Len + 1) := ASCII.NUL;
901 end Get_Encoded_Name;
903 -----------------------
904 -- Get_External_Name --
905 -----------------------
907 procedure Get_External_Name (Entity : Entity_Id; Has_Suffix : Boolean)
909 E : Entity_Id := Entity;
912 procedure Get_Qualified_Name_And_Append (Entity : Entity_Id);
913 -- Appends fully qualified name of given entity to Name_Buffer
915 -----------------------------------
916 -- Get_Qualified_Name_And_Append --
917 -----------------------------------
919 procedure Get_Qualified_Name_And_Append (Entity : Entity_Id) is
921 -- If the entity is a compilation unit, its scope is Standard,
922 -- there is no outer scope, and the no further qualification
925 -- If the front end has already computed a fully qualified name,
926 -- then it is also the case that no further qualification is
929 if Present (Scope (Scope (Entity)))
930 and then not Has_Fully_Qualified_Name (Entity)
932 Get_Qualified_Name_And_Append (Scope (Entity));
933 Add_Str_To_Name_Buffer ("__");
934 Get_Name_String_And_Append (Chars (Entity));
935 Append_Homonym_Number (Entity);
938 Get_Name_String_And_Append (Chars (Entity));
941 end Get_Qualified_Name_And_Append;
943 -- Start of processing for Get_External_Name
948 -- If this is a child unit, we want the child
950 if Nkind (E) = N_Defining_Program_Unit_Name then
951 E := Defining_Identifier (Entity);
956 -- Case of interface name being used
958 if (Kind = E_Procedure or else
959 Kind = E_Function or else
960 Kind = E_Constant or else
961 Kind = E_Variable or else
963 and then Present (Interface_Name (E))
964 and then No (Address_Clause (E))
965 and then not Has_Suffix
967 -- The following code needs explanation ???
969 if Convention (E) = Convention_Stdcall
970 and then Ekind (E) = E_Variable
972 Add_Str_To_Name_Buffer ("_imp__");
975 Add_String_To_Name_Buffer (Strval (Interface_Name (E)));
977 -- All other cases besides the interface name case
980 -- If this is a library level subprogram (i.e. a subprogram that is a
981 -- compilation unit other than a subunit), then we prepend _ada_ to
982 -- ensure distinctions required as described in the spec.
983 -- Check explicitly for child units, because those are not flagged
984 -- as Compilation_Units by lib. Should they be ???
987 and then (Is_Compilation_Unit (E) or Is_Child_Unit (E))
988 and then not Has_Suffix
990 Add_Str_To_Name_Buffer ("_ada_");
993 -- If the entity is a subprogram instance that is not a compilation
994 -- unit, generate the name of the original Ada entity, which is the
997 if Is_Generic_Instance (E)
998 and then Is_Subprogram (E)
999 and then not Is_Compilation_Unit (Scope (E))
1001 E := Related_Instance (Scope (E));
1004 Get_Qualified_Name_And_Append (E);
1007 Name_Buffer (Name_Len + 1) := ASCII.Nul;
1008 end Get_External_Name;
1010 -----------------------------------
1011 -- Get_External_Name_With_Suffix --
1012 -----------------------------------
1014 procedure Get_External_Name_With_Suffix
1015 (Entity : Entity_Id;
1018 Has_Suffix : constant Boolean := (Suffix /= "");
1020 Get_External_Name (Entity, Has_Suffix);
1023 Add_Str_To_Name_Buffer ("___");
1024 Add_Str_To_Name_Buffer (Suffix);
1026 Name_Buffer (Name_Len + 1) := ASCII.Nul;
1028 end Get_External_Name_With_Suffix;
1030 --------------------------
1031 -- Get_Variant_Encoding --
1032 --------------------------
1034 procedure Get_Variant_Encoding (V : Node_Id) is
1037 procedure Choice_Val (Typ : Character; Choice : Node_Id);
1038 -- Output encoded value for a single choice value. Typ is the key
1039 -- character ('S
', 'F
', or 'T
') that precedes the choice value.
1045 procedure Choice_Val (Typ : Character; Choice : Node_Id) is
1047 Add_Char_To_Name_Buffer (Typ);
1049 if Nkind (Choice) = N_Integer_Literal then
1050 Add_Uint_To_Buffer (Intval (Choice));
1052 -- Character literal with no entity present (this is the case
1053 -- Standard.Character or Standard.Wide_Character as root type)
1055 elsif Nkind (Choice) = N_Character_Literal
1056 and then No (Entity (Choice))
1059 (UI_From_Int (Int (Char_Literal_Value (Choice))));
1063 Ent : constant Entity_Id := Entity (Choice);
1066 if Ekind (Ent) = E_Enumeration_Literal then
1067 Add_Uint_To_Buffer (Enumeration_Rep (Ent));
1070 pragma Assert (Ekind (Ent) = E_Constant);
1071 Choice_Val (Typ, Constant_Value (Ent));
1077 -- Start of processing for Get_Variant_Encoding
1082 Choice := First (Discrete_Choices (V));
1083 while Present (Choice) loop
1084 if Nkind (Choice) = N_Others_Choice then
1085 Add_Char_To_Name_Buffer ('O
');
1087 elsif Nkind (Choice) = N_Range then
1088 Choice_Val ('R
', Low_Bound (Choice));
1089 Choice_Val ('T
', High_Bound (Choice));
1091 elsif Is_Entity_Name (Choice)
1092 and then Is_Type (Entity (Choice))
1094 Choice_Val ('R
', Type_Low_Bound (Entity (Choice)));
1095 Choice_Val ('T
', Type_High_Bound (Entity (Choice)));
1097 elsif Nkind (Choice) = N_Subtype_Indication then
1099 Rang : constant Node_Id :=
1100 Range_Expression (Constraint (Choice));
1102 Choice_Val ('R
', Low_Bound (Rang));
1103 Choice_Val ('T
', High_Bound (Rang));
1107 Choice_Val ('S
', Choice);
1113 Name_Buffer (Name_Len + 1) := ASCII.NUL;
1115 if Debug_Flag_B then
1117 VP : constant Node_Id := Parent (V); -- Variant_Part
1118 CL : constant Node_Id := Parent (VP); -- Component_List
1119 RD : constant Node_Id := Parent (CL); -- Record_Definition
1120 FT : constant Node_Id := Parent (RD); -- Full_Type_Declaration
1123 Write_Str ("**** variant for type ");
1124 Write_Name (Chars (Defining_Identifier (FT)));
1125 Write_Str (" is encoded as ");
1126 Write_Str (Name_Buffer (1 .. Name_Len));
1130 end Get_Variant_Encoding;
1132 ---------------------------------
1133 -- Make_Packed_Array_Type_Name --
1134 ---------------------------------
1136 function Make_Packed_Array_Type_Name
1142 Get_Name_String (Chars (Typ));
1143 Add_Str_To_Name_Buffer ("___XP");
1144 Add_Uint_To_Buffer (Csize);
1146 end Make_Packed_Array_Type_Name;
1148 -----------------------------------
1149 -- Output_Homonym_Numbers_Suffix --
1150 -----------------------------------
1152 procedure Output_Homonym_Numbers_Suffix is
1156 if Homonym_Len > 0 then
1158 -- Check for all 1's, in which case we do not output
1162 exit when Homonym_Numbers (J) /= '1';
1164 -- If we reached end of string we do not output
1166 if J = Homonym_Len then
1171 exit when Homonym_Numbers (J + 1) /= '_
';
1175 -- If we exit the loop then suffix must be output
1177 if No_Dollar_In_Label then
1178 Add_Str_To_Name_Buffer ("__");
1180 Add_Char_To_Name_Buffer ('$
');
1183 Add_Str_To_Name_Buffer (Homonym_Numbers (1 .. Homonym_Len));
1186 end Output_Homonym_Numbers_Suffix;
1188 ------------------------------
1189 -- Prepend_String_To_Buffer --
1190 ------------------------------
1192 procedure Prepend_String_To_Buffer (S : String) is
1193 N : constant Integer := S'Length;
1196 Name_Buffer (1 + N .. Name_Len + N) := Name_Buffer (1 .. Name_Len);
1197 Name_Buffer (1 .. N) := S;
1198 Name_Len := Name_Len + N;
1199 end Prepend_String_To_Buffer;
1201 ----------------------------
1202 -- Prepend_Uint_To_Buffer --
1203 ----------------------------
1205 procedure Prepend_Uint_To_Buffer (U : Uint) is
1208 Prepend_String_To_Buffer ("m");
1209 Prepend_Uint_To_Buffer (-U);
1211 UI_Image (U, Decimal);
1212 Prepend_String_To_Buffer (UI_Image_Buffer (1 .. UI_Image_Length));
1214 end Prepend_Uint_To_Buffer;
1220 procedure Put_Hex (W : Word; N : Natural) is
1221 Hex : constant array (Word range 0 .. 15) of Character :=
1228 for J in reverse N .. N + 7 loop
1229 Name_Buffer (J) := Hex (Cod and 16#F#);
1234 ------------------------------
1235 -- Qualify_All_Entity_Names --
1236 ------------------------------
1238 procedure Qualify_All_Entity_Names is
1243 for J in Name_Qualify_Units.First .. Name_Qualify_Units.Last loop
1244 E := Defining_Entity (Name_Qualify_Units.Table (J));
1245 Qualify_Entity_Name (E);
1247 Ent := First_Entity (E);
1248 while Present (Ent) loop
1249 Qualify_Entity_Name (Ent);
1252 -- There are odd cases where Last_Entity (E) = E. This happens
1253 -- in the case of renaming of packages. This test avoids getting
1254 -- stuck in such cases.
1260 -- Second loop compresses any names that need compressing
1262 for J in Name_Qualify_Units.First .. Name_Qualify_Units.Last loop
1263 E := Defining_Entity (Name_Qualify_Units.Table (J));
1264 Compress_Debug_Name (E);
1266 Ent := First_Entity (E);
1267 while Present (Ent) loop
1268 Compress_Debug_Name (Ent);
1273 end Qualify_All_Entity_Names;
1275 -------------------------
1276 -- Qualify_Entity_Name --
1277 -------------------------
1279 procedure Qualify_Entity_Name (Ent : Entity_Id) is
1281 Full_Qualify_Name : String (1 .. Name_Buffer'Length);
1282 Full_Qualify_Len : Natural := 0;
1283 -- Used to accumulate fully qualified name of subprogram
1285 procedure Fully_Qualify_Name (E : Entity_Id);
1286 -- Used to qualify a subprogram or type name, where full
1287 -- qualification up to Standard is always used. Name is set
1288 -- in Full_Qualify_Name with the length in Full_Qualify_Len.
1289 -- Note that this routine does not prepend the _ada_ string
1290 -- required for library subprograms (this is done in the back end).
1292 function Is_BNPE (S : Entity_Id) return Boolean;
1293 -- Determines if S is a BNPE, i.e. Body-Nested Package Entity, which
1294 -- is defined to be a package which is immediately nested within a
1297 function Qualify_Needed (S : Entity_Id) return Boolean;
1298 -- Given a scope, determines if the scope is to be included in the
1299 -- fully qualified name, True if so, False if not.
1301 procedure Set_BNPE_Suffix (E : Entity_Id);
1302 -- Recursive routine to append the BNPE qualification suffix. Works
1303 -- from right to left with E being the current entity in the list.
1304 -- The result does NOT have the trailing n's and trailing b stripped.
1305 -- The caller must do this required stripping.
1307 procedure Set_Entity_Name (E : Entity_Id);
1308 -- Internal recursive routine that does most of the work. This routine
1309 -- leaves the result sitting in Name_Buffer and Name_Len.
1311 BNPE_Suffix_Needed : Boolean := False;
1312 -- Set true if a body-nested package entity suffix is required
1314 Save_Chars : constant Name_Id := Chars (Ent);
1315 -- Save original name
1317 ------------------------
1318 -- Fully_Qualify_Name --
1319 ------------------------
1321 procedure Fully_Qualify_Name (E : Entity_Id) is
1322 Discard : Boolean := False;
1325 -- Ignore empty entry (can happen in error cases)
1330 -- If this we are qualifying entities local to a generic
1331 -- instance, use the name of the original instantiation,
1332 -- not that of the anonymous subprogram in the wrapper
1333 -- package, so that gdb doesn't have to know about these.
1335 elsif Is_Generic_Instance (E)
1336 and then Is_Subprogram (E)
1337 and then not Comes_From_Source (E)
1338 and then not Is_Compilation_Unit (Scope (E))
1340 Fully_Qualify_Name (Related_Instance (Scope (E)));
1344 -- If we reached fully qualified name, then just copy it
1346 if Has_Fully_Qualified_Name (E) then
1347 Get_Name_String (Chars (E));
1348 Strip_Suffixes (Discard);
1349 Full_Qualify_Name (1 .. Name_Len) := Name_Buffer (1 .. Name_Len);
1350 Full_Qualify_Len := Name_Len;
1351 Set_Has_Fully_Qualified_Name (Ent);
1353 -- Case of non-fully qualified name
1356 if Scope (E) = Standard_Standard then
1357 Set_Has_Fully_Qualified_Name (Ent);
1359 Fully_Qualify_Name (Scope (E));
1360 Full_Qualify_Name (Full_Qualify_Len + 1) := '_
';
1361 Full_Qualify_Name (Full_Qualify_Len + 2) := '_
';
1362 Full_Qualify_Len := Full_Qualify_Len + 2;
1365 if Has_Qualified_Name (E) then
1366 Get_Unqualified_Name_String (Chars (E));
1368 Get_Name_String (Chars (E));
1372 (Full_Qualify_Len + 1 .. Full_Qualify_Len + Name_Len) :=
1373 Name_Buffer (1 .. Name_Len);
1374 Full_Qualify_Len := Full_Qualify_Len + Name_Len;
1375 Append_Homonym_Number (E);
1379 BNPE_Suffix_Needed := True;
1381 end Fully_Qualify_Name;
1387 function Is_BNPE (S : Entity_Id) return Boolean is
1390 Ekind (S) = E_Package
1391 and then Is_Package_Body_Entity (S);
1394 --------------------
1395 -- Qualify_Needed --
1396 --------------------
1398 function Qualify_Needed (S : Entity_Id) return Boolean is
1400 -- If we got all the way to Standard, then we have certainly
1401 -- fully qualified the name, so set the flag appropriately,
1402 -- and then return False, since we are most certainly done!
1404 if S = Standard_Standard then
1405 Set_Has_Fully_Qualified_Name (Ent, True);
1408 -- Otherwise figure out if further qualification is required
1414 Ekind (Ent) = E_Subprogram_Body
1416 (Ekind (S) /= E_Block
1417 and then not Is_Dynamic_Scope (S));
1421 ---------------------
1422 -- Set_BNPE_Suffix --
1423 ---------------------
1425 procedure Set_BNPE_Suffix (E : Entity_Id) is
1426 S : constant Entity_Id := Scope (E);
1429 if Qualify_Needed (S) then
1430 Set_BNPE_Suffix (S);
1433 Add_Char_To_Name_Buffer ('b
');
1435 Add_Char_To_Name_Buffer ('n
');
1439 Add_Char_To_Name_Buffer ('X
');
1442 end Set_BNPE_Suffix;
1444 ---------------------
1445 -- Set_Entity_Name --
1446 ---------------------
1448 procedure Set_Entity_Name (E : Entity_Id) is
1449 S : constant Entity_Id := Scope (E);
1452 -- If we reach an already qualified name, just take the encoding
1453 -- except that we strip the package body suffixes, since these
1454 -- will be separately put on later.
1456 if Has_Qualified_Name (E) then
1457 Get_Name_String_And_Append (Chars (E));
1458 Strip_Suffixes (BNPE_Suffix_Needed);
1460 -- If the top level name we are adding is itself fully
1461 -- qualified, then that means that the name that we are
1462 -- preparing for the Fully_Qualify_Name call will also
1463 -- generate a fully qualified name.
1465 if Has_Fully_Qualified_Name (E) then
1466 Set_Has_Fully_Qualified_Name (Ent);
1469 -- Case where upper level name is not encoded yet
1472 -- Recurse if further qualification required
1474 if Qualify_Needed (S) then
1475 Set_Entity_Name (S);
1476 Add_Str_To_Name_Buffer ("__");
1479 -- Otherwise get name and note if it is a NPBE
1481 Get_Name_String_And_Append (Chars (E));
1484 BNPE_Suffix_Needed := True;
1487 Append_Homonym_Number (E);
1489 end Set_Entity_Name;
1491 -- Start of processing for Qualify_Entity_Name
1494 if Has_Qualified_Name (Ent) then
1497 -- Here is where we create the proper link for renaming
1499 elsif Ekind (Ent) = E_Enumeration_Literal
1500 and then Present (Debug_Renaming_Link (Ent))
1503 Set_Entity_Name (Debug_Renaming_Link (Ent));
1504 Get_Name_String (Chars (Ent));
1505 Prepend_String_To_Buffer
1506 (Get_Name_String (Chars (Debug_Renaming_Link (Ent))));
1507 Set_Chars (Ent, Name_Enter);
1508 Set_Has_Qualified_Name (Ent);
1511 elsif Is_Subprogram (Ent)
1512 or else Ekind (Ent) = E_Subprogram_Body
1513 or else Is_Type (Ent)
1515 Fully_Qualify_Name (Ent);
1516 Name_Len := Full_Qualify_Len;
1517 Name_Buffer (1 .. Name_Len) := Full_Qualify_Name (1 .. Name_Len);
1519 elsif Qualify_Needed (Scope (Ent)) then
1521 Set_Entity_Name (Ent);
1524 Set_Has_Qualified_Name (Ent);
1528 -- Fall through with a fully qualified name in Name_Buffer/Name_Len
1530 Output_Homonym_Numbers_Suffix;
1532 -- Add body-nested package suffix if required
1534 if BNPE_Suffix_Needed
1535 and then Ekind (Ent) /= E_Enumeration_Literal
1537 Set_BNPE_Suffix (Ent);
1539 -- Strip trailing n's and last trailing b as required. note that
1540 -- we know there is at least one b, or no suffix would be generated.
1542 while Name_Buffer (Name_Len) = 'n
' loop
1543 Name_Len := Name_Len - 1;
1546 Name_Len := Name_Len - 1;
1549 Set_Chars (Ent, Name_Enter);
1550 Set_Has_Qualified_Name (Ent);
1552 if Debug_Flag_BB then
1554 Write_Name (Save_Chars);
1555 Write_Str (" qualified as ");
1556 Write_Name (Chars (Ent));
1559 end Qualify_Entity_Name;
1561 --------------------------
1562 -- Qualify_Entity_Names --
1563 --------------------------
1565 procedure Qualify_Entity_Names (N : Node_Id) is
1567 Name_Qualify_Units.Append (N);
1568 end Qualify_Entity_Names;
1574 function SEq (F1, F2 : String_Ptr) return Boolean is
1576 return F1.all = F2.all;
1583 function SHash (S : String_Ptr) return Hindex is
1586 (Hindex'First + Hindex (CDN_Hash (S.all) mod Hindex'Range_Length));
1589 --------------------
1590 -- Strip_Suffixes --
1591 --------------------
1593 procedure Strip_Suffixes (BNPE_Suffix_Found : in out Boolean) is
1597 -- Search for and strip BNPE suffix
1599 for J in reverse 2 .. Name_Len loop
1600 if Name_Buffer (J) = 'X
' then
1602 BNPE_Suffix_Found := True;
1606 exit when Name_Buffer (J) /= 'b
' and then Name_Buffer (J) /= 'n
';
1609 -- Search for and strip homonym numbers suffix
1611 -- Case of __ used for homonym numbers suffix
1613 if No_Dollar_In_Label then
1614 for J in reverse 2 .. Name_Len - 2 loop
1615 if Name_Buffer (J) = '_
'
1616 and then Name_Buffer (J + 1) = '_
'
1618 if Name_Buffer (J + 2) in '0' .. '9' then
1619 if Homonym_Len > 0 then
1620 Homonym_Len := Homonym_Len + 1;
1621 Homonym_Numbers (Homonym_Len) := '-';
1624 SL := Name_Len - (J + 1);
1626 Homonym_Numbers (Homonym_Len + 1 .. Homonym_Len + SL) :=
1627 Name_Buffer (J + 2 .. Name_Len);
1629 Homonym_Len := Homonym_Len + SL;
1636 -- Case of $ used for homonym numbers suffix
1639 for J in reverse 2 .. Name_Len - 1 loop
1640 if Name_Buffer (J) = '$
' then
1641 if Name_Buffer (J + 1) in '0' .. '9' then
1642 if Homonym_Len > 0 then
1643 Homonym_Len := Homonym_Len + 1;
1644 Homonym_Numbers (Homonym_Len) := '-';
1649 Homonym_Numbers (Homonym_Len + 1 .. Homonym_Len + SL) :=
1650 Name_Buffer (J + 1 .. Name_Len);
1652 Homonym_Len := Homonym_Len + SL;