OSDN Git Service

* gcc-interface/decl.c (make_type_from_size) <INTEGER_TYPE>: Just copy
[pf3gnuchains/gcc-fork.git] / gcc / ada / xref_lib.adb
1 ------------------------------------------------------------------------------
2 --                                                                          --
3 --                         GNAT COMPILER COMPONENTS                         --
4 --                                                                          --
5 --                             X R E F _ L I B                              --
6 --                                                                          --
7 --                                 B o d y                                  --
8 --                                                                          --
9 --          Copyright (C) 1998-2009, 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 ------------------------------------------------------------------------------
25
26 with Osint;
27 with Output; use Output;
28 with Types;  use Types;
29
30 with Unchecked_Deallocation;
31
32 with Ada.Strings.Fixed; use Ada.Strings.Fixed;
33 with Ada.Text_IO;       use Ada.Text_IO;
34
35 with GNAT.Command_Line; use GNAT.Command_Line;
36 with GNAT.IO_Aux;       use GNAT.IO_Aux;
37
38 package body Xref_Lib is
39
40    Type_Position : constant := 50;
41    --  Column for label identifying type of entity
42
43    ---------------------
44    -- Local Variables --
45    ---------------------
46
47    Pipe : constant Character := '|';
48    --  First character on xref lines in the .ali file
49
50    No_Xref_Information : exception;
51    --  Exception raised when there is no cross-referencing information in
52    --  the .ali files.
53
54    procedure Parse_EOL
55      (Source                 : not null access String;
56       Ptr                    : in out Positive;
57       Skip_Continuation_Line : Boolean := False);
58    --  On return Source (Ptr) is the first character of the next line
59    --  or EOF. Source.all must be terminated by EOF.
60    --
61    --  If Skip_Continuation_Line is True, this subprogram skips as many
62    --  lines as required when the second or more lines starts with '.'
63    --  (continuation lines in ALI files).
64
65    function Current_Xref_File (File : ALI_File) return File_Reference;
66    --  Return the file matching the last 'X' line we found while parsing
67    --  the ALI file.
68
69    function File_Name (File : ALI_File; Num : Positive) return File_Reference;
70    --  Returns the dependency file name number Num
71
72    function Get_Full_Type (Decl : Declaration_Reference) return String;
73    --  Returns the full type corresponding to a type letter as found in
74    --  the .ali files.
75
76    procedure Open
77      (Name         : String;
78       File         : out ALI_File;
79       Dependencies : Boolean := False);
80    --  Open a new ALI file. If Dependencies is True, the insert every library
81    --  file 'with'ed in the files database (used for gnatxref)
82
83    procedure Parse_Identifier_Info
84      (Pattern       : Search_Pattern;
85       File          : in out ALI_File;
86       Local_Symbols : Boolean;
87       Der_Info      : Boolean := False;
88       Type_Tree     : Boolean := False;
89       Wide_Search   : Boolean := True;
90       Labels_As_Ref : Boolean := True);
91    --  Output the file and the line where the identifier was referenced,
92    --  If Local_Symbols is False then only the publicly visible symbols
93    --  will be processed.
94    --
95    --  If Labels_As_Ref is true, then the references to the entities after
96    --  the end statements ("end Foo") will be counted as actual references.
97    --  The entity will never be reported as unreferenced by gnatxref -u
98
99    procedure Parse_Token
100      (Source    : not null access String;
101       Ptr       : in out Positive;
102       Token_Ptr : out Positive);
103    --  Skips any separators and stores the start of the token in Token_Ptr.
104    --  Then stores the position of the next separator in Ptr. On return
105    --  Source (Token_Ptr .. Ptr - 1) is the token. Separators are space
106    --  and ASCII.HT. Parse_Token will never skip to the next line.
107
108    procedure Parse_Number
109      (Source : not null access String;
110       Ptr    : in out Positive;
111       Number : out Natural);
112    --  Skips any separators and parses Source up to the first character that
113    --  is not a decimal digit. Returns value of parsed digits or 0 if none.
114
115    procedure Parse_X_Filename (File : in out ALI_File);
116    --  Reads and processes "X..." lines in the ALI file
117    --  and updates the File.X_File information.
118
119    procedure Skip_To_First_X_Line
120      (File    : in out ALI_File;
121       D_Lines : Boolean;
122       W_Lines : Boolean);
123    --  Skip the lines in the ALI file until the first cross-reference line
124    --  (^X...) is found. Search is started from the beginning of the file.
125    --  If not such line is found, No_Xref_Information is raised.
126    --  If W_Lines is false, then the lines "^W" are not parsed.
127    --  If D_Lines is false, then the lines "^D" are not parsed.
128
129    ----------------
130    -- Add_Entity --
131    ----------------
132
133    procedure Add_Entity
134      (Pattern : in out Search_Pattern;
135       Entity  : String;
136       Glob    : Boolean := False)
137    is
138       File_Start : Natural;
139       Line_Start : Natural;
140       Col_Start  : Natural;
141       Line_Num   : Natural := 0;
142       Col_Num    : Natural := 0;
143
144       File_Ref : File_Reference := Empty_File;
145       pragma Warnings (Off, File_Ref);
146
147    begin
148       --  Find the end of the first item in Entity (pattern or file?)
149       --  If there is no ':', we only have a pattern
150
151       File_Start := Index (Entity, ":");
152
153       --  If the regular expression is invalid, just consider it as a string
154
155       if File_Start = 0 then
156          begin
157             Pattern.Entity := Compile (Entity, Glob, False);
158             Pattern.Initialized := True;
159
160          exception
161             when Error_In_Regexp =>
162
163                --  The basic idea is to insert a \ before every character
164
165                declare
166                   Tmp_Regexp : String (1 .. 2 * Entity'Length);
167                   Index      : Positive := 1;
168
169                begin
170                   for J in Entity'Range loop
171                      Tmp_Regexp (Index) := '\';
172                      Tmp_Regexp (Index + 1) := Entity (J);
173                      Index := Index + 2;
174                   end loop;
175
176                   Pattern.Entity := Compile (Tmp_Regexp, True, False);
177                   Pattern.Initialized := True;
178                end;
179          end;
180
181          Set_Default_Match (True);
182          return;
183       end if;
184
185       --  If there is a dot in the pattern, then it is a file name
186
187       if (Glob and then
188            Index (Entity (Entity'First .. File_Start - 1), ".") /= 0)
189              or else
190               (not Glob
191                  and then Index (Entity (Entity'First .. File_Start - 1),
192                                    "\.") /= 0)
193       then
194          Pattern.Entity      := Compile (".*", False);
195          Pattern.Initialized := True;
196          File_Start          := Entity'First;
197
198       else
199          --  If the regular expression is invalid, just consider it as a string
200
201          begin
202             Pattern.Entity :=
203               Compile (Entity (Entity'First .. File_Start - 1), Glob, False);
204             Pattern.Initialized := True;
205
206          exception
207             when Error_In_Regexp =>
208
209                --  The basic idea is to insert a \ before every character
210
211                declare
212                   Tmp_Regexp : String (1 .. 2 * (File_Start - Entity'First));
213                   Index      : Positive := 1;
214
215                begin
216                   for J in Entity'First .. File_Start - 1 loop
217                      Tmp_Regexp (Index) := '\';
218                      Tmp_Regexp (Index + 1) := Entity (J);
219                      Index := Index + 2;
220                   end loop;
221
222                   Pattern.Entity := Compile (Tmp_Regexp, True, False);
223                   Pattern.Initialized := True;
224                end;
225          end;
226
227          File_Start := File_Start + 1;
228       end if;
229
230       --  Parse the file name
231
232       Line_Start := Index (Entity (File_Start .. Entity'Last), ":");
233
234       --  Check if it was a disk:\directory item (for NT and OS/2)
235
236       if File_Start = Line_Start - 1
237         and then Line_Start < Entity'Last
238         and then Entity (Line_Start + 1) = '\'
239       then
240          Line_Start := Index (Entity (Line_Start + 1 .. Entity'Last), ":");
241       end if;
242
243       if Line_Start = 0 then
244          Line_Start := Entity'Length + 1;
245
246       elsif Line_Start /= Entity'Last then
247          Col_Start := Index (Entity (Line_Start + 1 .. Entity'Last), ":");
248
249          if Col_Start = 0 then
250             Col_Start := Entity'Last + 1;
251          end if;
252
253          if Col_Start > Line_Start + 1 then
254             begin
255                Line_Num := Natural'Value
256                  (Entity (Line_Start + 1 .. Col_Start - 1));
257
258             exception
259                when Constraint_Error =>
260                   raise Invalid_Argument;
261             end;
262          end if;
263
264          if Col_Start < Entity'Last then
265             begin
266                Col_Num := Natural'Value (Entity
267                                          (Col_Start + 1 .. Entity'Last));
268
269             exception
270                when Constraint_Error => raise Invalid_Argument;
271             end;
272          end if;
273       end if;
274
275       File_Ref :=
276         Add_To_Xref_File
277           (Entity (File_Start .. Line_Start - 1), Visited => True);
278       Pattern.File_Ref := File_Ref;
279
280       Add_Line (Pattern.File_Ref, Line_Num, Col_Num);
281
282       File_Ref :=
283         Add_To_Xref_File
284           (ALI_File_Name (Entity (File_Start .. Line_Start - 1)),
285            Visited      => False,
286            Emit_Warning => True);
287    end Add_Entity;
288
289    -------------------
290    -- Add_Xref_File --
291    -------------------
292
293    procedure Add_Xref_File (File : String) is
294       File_Ref : File_Reference := Empty_File;
295       pragma Unreferenced (File_Ref);
296
297       Iterator : Expansion_Iterator;
298
299       procedure Add_Xref_File_Internal (File : String);
300       --  Do the actual addition of the file
301
302       ----------------------------
303       -- Add_Xref_File_Internal --
304       ----------------------------
305
306       procedure Add_Xref_File_Internal (File : String) is
307       begin
308          --  Case where we have an ALI file, accept it even though this is
309          --  not official usage, since the intention is obvious
310
311          if Tail (File, 4) = "." & Osint.ALI_Suffix.all then
312             File_Ref := Add_To_Xref_File
313                           (File, Visited => False, Emit_Warning => True);
314
315          --  Normal non-ali file case
316
317          else
318             File_Ref := Add_To_Xref_File (File, Visited => True);
319
320             File_Ref := Add_To_Xref_File
321                          (ALI_File_Name (File),
322                           Visited => False, Emit_Warning => True);
323          end if;
324       end Add_Xref_File_Internal;
325
326    --  Start of processing for Add_Xref_File
327
328    begin
329       --  Check if we need to do the expansion
330
331       if Ada.Strings.Fixed.Index (File, "*") /= 0
332         or else Ada.Strings.Fixed.Index (File, "?") /= 0
333       then
334          Start_Expansion (Iterator, File);
335
336          loop
337             declare
338                S : constant String := Expansion (Iterator);
339
340             begin
341                exit when S'Length = 0;
342                Add_Xref_File_Internal (S);
343             end;
344          end loop;
345
346       else
347          Add_Xref_File_Internal (File);
348       end if;
349    end Add_Xref_File;
350
351    -----------------------
352    -- Current_Xref_File --
353    -----------------------
354
355    function Current_Xref_File (File : ALI_File) return File_Reference is
356    begin
357       return File.X_File;
358    end Current_Xref_File;
359
360    --------------------------
361    -- Default_Project_File --
362    --------------------------
363
364    function Default_Project_File (Dir_Name : String) return String is
365       My_Dir  : Dir_Type;
366       Dir_Ent : File_Name_String;
367       Last    : Natural;
368
369    begin
370       Open (My_Dir, Dir_Name);
371
372       loop
373          Read (My_Dir, Dir_Ent, Last);
374          exit when Last = 0;
375
376          if Tail (Dir_Ent (1 .. Last), 4) = ".adp" then
377
378             --  The first project file found is the good one
379
380             Close (My_Dir);
381             return Dir_Ent (1 .. Last);
382          end if;
383       end loop;
384
385       Close (My_Dir);
386       return String'(1 .. 0 => ' ');
387
388    exception
389       when Directory_Error => return String'(1 .. 0 => ' ');
390    end Default_Project_File;
391
392    ---------------
393    -- File_Name --
394    ---------------
395
396    function File_Name
397      (File : ALI_File;
398       Num  : Positive) return File_Reference
399    is
400    begin
401       return File.Dep.Table (Num);
402    end File_Name;
403
404    --------------------
405    -- Find_ALI_Files --
406    --------------------
407
408    procedure Find_ALI_Files is
409       My_Dir  : Rec_DIR;
410       Dir_Ent : File_Name_String;
411       Last    : Natural;
412
413       File_Ref : File_Reference;
414       pragma Unreferenced (File_Ref);
415
416       function Open_Next_Dir return Boolean;
417       --  Tries to open the next object directory, and return False if
418       --  the directory cannot be opened.
419
420       -------------------
421       -- Open_Next_Dir --
422       -------------------
423
424       function Open_Next_Dir return Boolean is
425       begin
426          --  Until we are able to open a new directory
427
428          loop
429             declare
430                Obj_Dir : constant String := Next_Obj_Dir;
431
432             begin
433                --  Case of no more Obj_Dir lines
434
435                if Obj_Dir'Length = 0 then
436                   return False;
437                end if;
438
439                Open (My_Dir.Dir, Obj_Dir);
440                exit;
441
442             exception
443
444                --  Could not open the directory
445
446                when Directory_Error => null;
447             end;
448          end loop;
449
450          return True;
451       end Open_Next_Dir;
452
453    --  Start of processing for Find_ALI_Files
454
455    begin
456       Reset_Obj_Dir;
457
458       if Open_Next_Dir then
459          loop
460             Read (My_Dir.Dir, Dir_Ent, Last);
461
462             if Last = 0 then
463                Close (My_Dir.Dir);
464
465                if not Open_Next_Dir then
466                   return;
467                end if;
468
469             elsif Last > 4
470               and then Dir_Ent (Last - 3 .. Last) = "." & Osint.ALI_Suffix.all
471             then
472                File_Ref :=
473                  Add_To_Xref_File (Dir_Ent (1 .. Last), Visited => False);
474             end if;
475          end loop;
476       end if;
477    end Find_ALI_Files;
478
479    -------------------
480    -- Get_Full_Type --
481    -------------------
482
483    function Get_Full_Type (Decl : Declaration_Reference) return String is
484
485       function Param_String return String;
486       --  Return the string to display depending on whether Decl is a parameter
487
488       ------------------
489       -- Param_String --
490       ------------------
491
492       function Param_String return String is
493       begin
494          if Is_Parameter (Decl) then
495             return "parameter ";
496          else
497             return "";
498          end if;
499       end Param_String;
500
501    --  Start of processing for Get_Full_Type
502
503    begin
504       case Get_Type (Decl) is
505          when 'A' => return "array type";
506          when 'B' => return "boolean type";
507          when 'C' => return "class-wide type";
508          when 'D' => return "decimal type";
509          when 'E' => return "enumeration type";
510          when 'F' => return "float type";
511          when 'I' => return "integer type";
512          when 'M' => return "modular type";
513          when 'O' => return "fixed type";
514          when 'P' => return "access type";
515          when 'R' => return "record type";
516          when 'S' => return "string type";
517          when 'T' => return "task type";
518          when 'W' => return "protected type";
519
520          when 'a' => return "array type";
521          when 'b' => return Param_String & "boolean object";
522          when 'c' => return Param_String & "class-wide object";
523          when 'd' => return Param_String & "decimal object";
524          when 'e' => return Param_String & "enumeration object";
525          when 'f' => return Param_String & "float object";
526          when 'h' => return "interface";
527          when 'i' => return Param_String & "integer object";
528          when 'm' => return Param_String & "modular object";
529          when 'o' => return Param_String & "fixed object";
530          when 'p' => return Param_String & "access object";
531          when 'r' => return Param_String & "record object";
532          when 's' => return Param_String & "string object";
533          when 't' => return Param_String & "task object";
534          when 'w' => return Param_String & "protected object";
535          when 'x' => return Param_String & "abstract procedure";
536          when 'y' => return Param_String & "abstract function";
537
538          when 'K' => return "package";
539          when 'k' => return "generic package";
540          when 'L' => return "statement label";
541          when 'l' => return "loop label";
542          when 'N' => return "named number";
543          when 'n' => return "enumeration literal";
544          when 'q' => return "block label";
545          when 'U' => return "procedure";
546          when 'u' => return "generic procedure";
547          when 'V' => return "function";
548          when 'v' => return "generic function";
549          when 'X' => return "exception";
550          when 'Y' => return "entry";
551
552          when '+' => return "private type";
553
554          --  The above should be the only possibilities, but for this kind
555          --  of informational output, we don't want to bomb if we find
556          --  something else, so just return three question marks when we
557          --  have an unknown Abbrev value
558
559          when others =>
560             return "??? (" & Get_Type (Decl) & ")";
561       end case;
562    end Get_Full_Type;
563
564    --------------------------
565    -- Skip_To_First_X_Line --
566    --------------------------
567
568    procedure Skip_To_First_X_Line
569      (File    : in out ALI_File;
570       D_Lines : Boolean;
571       W_Lines : Boolean)
572    is
573       Ali              : String_Access renames File.Buffer;
574       Token            : Positive;
575       Ptr              : Positive := Ali'First;
576       Num_Dependencies : Natural  := 0;
577       File_Start       : Positive;
578       File_End         : Positive;
579       Gnatchop_Offset  : Integer;
580       Gnatchop_Name    : Positive;
581
582       File_Ref : File_Reference;
583       pragma Unreferenced (File_Ref);
584
585    begin
586       --  Read all the lines possibly processing with-clauses and dependency
587       --  information and exit on finding the first Xref line.
588       --  A fall-through of the loop means that there is no xref information
589       --  which is an error condition.
590
591       while Ali (Ptr) /= EOF loop
592          if D_Lines and then Ali (Ptr) = 'D' then
593
594             --  Found dependency information. Format looks like:
595             --  D src-nam time-stmp checksum [subunit-name] [line:file-name]
596
597             --  Skip the D and parse the filenam
598
599             Ptr := Ptr + 1;
600             Parse_Token (Ali, Ptr, Token);
601             File_Start := Token;
602             File_End := Ptr - 1;
603
604             Num_Dependencies := Num_Dependencies + 1;
605             Set_Last (File.Dep, Num_Dependencies);
606
607             Parse_Token (Ali, Ptr, Token); --  Skip time-stamp
608             Parse_Token (Ali, Ptr, Token); --  Skip checksum
609             Parse_Token (Ali, Ptr, Token); --  Read next entity on the line
610
611             if not (Ali (Token) in '0' .. '9') then
612                Parse_Token (Ali, Ptr, Token); --  Was a subunit name
613             end if;
614
615             --  Did we have a gnatchop-ed file with a pragma Source_Reference ?
616
617             Gnatchop_Offset := 0;
618
619             if Ali (Token) in '0' .. '9' then
620                Gnatchop_Name := Token;
621                while Ali (Gnatchop_Name) /= ':' loop
622                   Gnatchop_Name := Gnatchop_Name + 1;
623                end loop;
624
625                Gnatchop_Offset :=
626                  2 - Natural'Value (Ali (Token .. Gnatchop_Name - 1));
627                Token := Gnatchop_Name + 1;
628             end if;
629
630             File.Dep.Table (Num_Dependencies) := Add_To_Xref_File
631               (Ali (File_Start .. File_End),
632                Gnatchop_File => Ali (Token .. Ptr - 1),
633                Gnatchop_Offset => Gnatchop_Offset);
634
635          elsif W_Lines and then Ali (Ptr) = 'W' then
636
637             --  Found with-clause information. Format looks like:
638             --     "W debug%s               debug.adb               debug.ali"
639
640             --  Skip the W and parse the .ali filename (3rd token)
641
642             Parse_Token (Ali, Ptr, Token);
643             Parse_Token (Ali, Ptr, Token);
644             Parse_Token (Ali, Ptr, Token);
645
646             File_Ref :=
647               Add_To_Xref_File (Ali (Token .. Ptr - 1), Visited => False);
648
649          elsif Ali (Ptr) = 'X' then
650
651             --  Found a cross-referencing line - stop processing
652
653             File.Current_Line := Ptr;
654             File.Xref_Line    := Ptr;
655             return;
656          end if;
657
658          Parse_EOL (Ali, Ptr);
659       end loop;
660
661       raise No_Xref_Information;
662    end Skip_To_First_X_Line;
663
664    ----------
665    -- Open --
666    ----------
667
668    procedure Open
669      (Name         : String;
670       File         : out ALI_File;
671       Dependencies : Boolean := False)
672    is
673       Ali : String_Access renames File.Buffer;
674       pragma Warnings (Off, Ali);
675
676    begin
677       if File.Buffer /= null then
678          Free (File.Buffer);
679       end if;
680
681       Init (File.Dep);
682
683       begin
684          Read_File (Name, Ali);
685
686       exception
687          when Ada.Text_IO.Name_Error | Ada.Text_IO.End_Error =>
688             raise No_Xref_Information;
689       end;
690
691       Skip_To_First_X_Line (File, D_Lines => True, W_Lines => Dependencies);
692    end Open;
693
694    ---------------
695    -- Parse_EOL --
696    ---------------
697
698    procedure Parse_EOL
699      (Source                 : not null access String;
700       Ptr                    : in out Positive;
701       Skip_Continuation_Line : Boolean := False)
702    is
703    begin
704       loop
705          --  Skip to end of line
706
707          while Source (Ptr) /= ASCII.CR and then Source (Ptr) /= ASCII.LF
708            and then Source (Ptr) /= EOF
709          loop
710             Ptr := Ptr + 1;
711          end loop;
712
713          --  Skip CR or LF if not at end of file
714
715          if Source (Ptr) /= EOF then
716             Ptr := Ptr + 1;
717          end if;
718
719          --  Skip past CR/LF or LF/CR combination
720
721          if (Source (Ptr) = ASCII.CR or else Source (Ptr) = ASCII.LF)
722            and then Source (Ptr) /= Source (Ptr - 1)
723          then
724             Ptr := Ptr + 1;
725          end if;
726
727          exit when not Skip_Continuation_Line or else Source (Ptr) /= '.';
728       end loop;
729    end Parse_EOL;
730
731    ---------------------------
732    -- Parse_Identifier_Info --
733    ---------------------------
734
735    procedure Parse_Identifier_Info
736      (Pattern       : Search_Pattern;
737       File          : in out ALI_File;
738       Local_Symbols : Boolean;
739       Der_Info      : Boolean := False;
740       Type_Tree     : Boolean := False;
741       Wide_Search   : Boolean := True;
742       Labels_As_Ref : Boolean := True)
743    is
744       Ptr      : Positive renames File.Current_Line;
745       Ali      : String_Access renames File.Buffer;
746
747       E_Line   : Natural;   --  Line number of current entity
748       E_Col    : Natural;   --  Column number of current entity
749       E_Type   : Character; --  Type of current entity
750       E_Name   : Positive;  --  Pointer to begin of entity name
751       E_Global : Boolean;   --  True iff entity is global
752
753       R_Line   : Natural;   --  Line number of current reference
754       R_Col    : Natural;   --  Column number of current reference
755       R_Type   : Character; --  Type of current reference
756
757       Decl_Ref : Declaration_Reference;
758       File_Ref : File_Reference := Current_Xref_File (File);
759
760       function Get_Symbol_Name (Eun, Line, Col : Natural) return String;
761       --  Returns the symbol name for the entity defined at the specified
762       --  line and column in the dependent unit number Eun. For this we need
763       --  to parse the ali file again because the parent entity is not in
764       --  the declaration table if it did not match the search pattern.
765
766       procedure Skip_To_Matching_Closing_Bracket;
767       --  When Ptr points to an opening square bracket, moves it to the
768       --  character following the matching closing bracket
769
770       ---------------------
771       -- Get_Symbol_Name --
772       ---------------------
773
774       function Get_Symbol_Name (Eun, Line, Col : Natural) return String is
775          Ptr    : Positive := 1;
776          E_Eun  : Positive;   --  Unit number of current entity
777          E_Line : Natural;    --  Line number of current entity
778          E_Col  : Natural;    --  Column number of current entity
779          E_Name : Positive;   --  Pointer to begin of entity name
780
781       begin
782          --  Look for the X lines corresponding to unit Eun
783
784          loop
785             if Ali (Ptr) = 'X' then
786                Ptr := Ptr + 1;
787                Parse_Number (Ali, Ptr, E_Eun);
788                exit when E_Eun = Eun;
789             end if;
790
791             Parse_EOL (Ali, Ptr, Skip_Continuation_Line => True);
792          end loop;
793
794          --  Here we are in the right Ali section, we now look for the entity
795          --  declared at position (Line, Col).
796
797          loop
798             Parse_Number (Ali, Ptr, E_Line);
799             exit when Ali (Ptr) = EOF;
800             Ptr := Ptr + 1;
801             Parse_Number (Ali, Ptr, E_Col);
802             exit when Ali (Ptr) = EOF;
803             Ptr := Ptr + 1;
804
805             if Line = E_Line and then Col = E_Col then
806                Parse_Token (Ali, Ptr, E_Name);
807                return Ali (E_Name .. Ptr - 1);
808             end if;
809
810             Parse_EOL (Ali, Ptr, Skip_Continuation_Line => True);
811             exit when Ali (Ptr) = EOF;
812          end loop;
813
814          --  We were not able to find the symbol, this should not happen but
815          --  since we don't want to stop here we return a string of three
816          --  question marks as the symbol name.
817
818          return "???";
819       end Get_Symbol_Name;
820
821       --------------------------------------
822       -- Skip_To_Matching_Closing_Bracket --
823       --------------------------------------
824
825       procedure Skip_To_Matching_Closing_Bracket is
826          Num_Brackets : Natural;
827
828       begin
829          Num_Brackets := 1;
830          while Num_Brackets /= 0 loop
831             Ptr := Ptr + 1;
832             if Ali (Ptr) = '[' then
833                Num_Brackets := Num_Brackets + 1;
834             elsif Ali (Ptr) = ']' then
835                Num_Brackets := Num_Brackets - 1;
836             end if;
837          end loop;
838
839          Ptr := Ptr + 1;
840       end Skip_To_Matching_Closing_Bracket;
841
842    --  Start of processing for Parse_Identifier_Info
843
844    begin
845       --  The identifier info looks like:
846       --     "38U9*Debug 12|36r6 36r19"
847
848       --  Extract the line, column and entity name information
849
850       Parse_Number (Ali, Ptr, E_Line);
851
852       if Ali (Ptr) > ' ' then
853          E_Type := Ali (Ptr);
854          Ptr := Ptr + 1;
855       end if;
856
857       --  Ignore some of the entities (labels,...)
858
859       case E_Type is
860          when 'l' | 'L' | 'q' =>
861             Parse_EOL (Ali, Ptr, Skip_Continuation_Line => True);
862             return;
863
864          when others =>
865             null;
866       end case;
867
868       Parse_Number (Ali, Ptr, E_Col);
869
870       E_Global := False;
871       if Ali (Ptr) >= ' ' then
872          E_Global := (Ali (Ptr) = '*');
873          Ptr := Ptr + 1;
874       end if;
875
876       Parse_Token (Ali, Ptr, E_Name);
877
878       --  Exit if the symbol does not match
879       --  or if we have a local symbol and we do not want it
880
881       if (not Local_Symbols and not E_Global)
882         or else (Pattern.Initialized
883                   and then not Match (Ali (E_Name .. Ptr - 1), Pattern.Entity))
884         or else (E_Name >= Ptr)
885       then
886          Decl_Ref := Add_Declaration
887            (File.X_File, Ali (E_Name .. Ptr - 1), E_Line, E_Col, E_Type,
888             Remove_Only => True);
889          Parse_EOL (Ali, Ptr, Skip_Continuation_Line => True);
890          return;
891       end if;
892
893       --  Insert the declaration in the table
894
895       Decl_Ref := Add_Declaration
896         (File.X_File, Ali (E_Name .. Ptr - 1), E_Line, E_Col, E_Type);
897
898       if Ali (Ptr) = '[' then
899          Skip_To_Matching_Closing_Bracket;
900       end if;
901
902       --  Skip any renaming indication
903
904       if Ali (Ptr) = '=' then
905          declare
906             P_Line, P_Column : Natural;
907             pragma Warnings (Off, P_Line);
908             pragma Warnings (Off, P_Column);
909          begin
910             Ptr := Ptr + 1;
911             Parse_Number (Ali, Ptr, P_Line);
912             Ptr := Ptr + 1;
913             Parse_Number (Ali, Ptr, P_Column);
914          end;
915       end if;
916
917       if Ali (Ptr) = '<'
918         or else Ali (Ptr) = '('
919         or else Ali (Ptr) = '{'
920       then
921          --  Here we have a type derivation information. The format is
922          --  <3|12I45> which means that the current entity is derived from the
923          --  type defined in unit number 3, line 12 column 45. The pipe and
924          --  unit number is optional. It is specified only if the parent type
925          --  is not defined in the current unit.
926
927          --  We also have the format for generic instantiations, as in
928          --  7a5*Uid(3|5I8[4|2]) 2|4r74
929
930          --  We could also have something like
931          --  16I9*I<integer>
932          --  that indicates that I derives from the predefined type integer.
933
934          Ptr := Ptr + 1;
935
936          if Ali (Ptr) in '0' .. '9' then
937             Parse_Derived_Info : declare
938                P_Line   : Natural;          --  parent entity line
939                P_Column : Natural;          --  parent entity column
940                P_Eun    : Positive;         --  parent entity file number
941
942             begin
943                Parse_Number (Ali, Ptr, P_Line);
944
945                --  If we have a pipe then the first number was the unit number
946
947                if Ali (Ptr) = '|' then
948                   P_Eun := P_Line;
949                   Ptr := Ptr + 1;
950
951                   --  Now we have the line number
952
953                   Parse_Number (Ali, Ptr, P_Line);
954
955                else
956                   --  We don't have a unit number specified, so we set P_Eun to
957                   --  the current unit.
958
959                   for K in Dependencies_Tables.First .. Last (File.Dep) loop
960                      P_Eun := K;
961                      exit when File.Dep.Table (K) = File_Ref;
962                   end loop;
963                end if;
964
965                --  Then parse the type and column number
966
967                Ptr := Ptr + 1;
968                Parse_Number (Ali, Ptr, P_Column);
969
970                --  Skip the information for generics instantiations
971
972                if Ali (Ptr) = '[' then
973                   Skip_To_Matching_Closing_Bracket;
974                end if;
975
976                --  Skip '>', or ')' or '>'
977
978                Ptr := Ptr + 1;
979
980                --  The derived info is needed only is the derived info mode is
981                --  on or if we want to output the type hierarchy
982
983                if Der_Info or else Type_Tree then
984                   declare
985                      Symbol : constant String :=
986                                 Get_Symbol_Name (P_Eun, P_Line, P_Column);
987                   begin
988                      if Symbol /= "???" then
989                         Add_Parent
990                           (Decl_Ref,
991                            Symbol,
992                            P_Line,
993                            P_Column,
994                            File.Dep.Table (P_Eun));
995                      end if;
996                   end;
997                end if;
998
999                if Type_Tree
1000                  and then (Pattern.File_Ref = Empty_File
1001                              or else
1002                            Pattern.File_Ref = Current_Xref_File (File))
1003                then
1004                   Search_Parent_Tree : declare
1005                      Pattern         : Search_Pattern;  --  Parent type pattern
1006                      File_Pos_Backup : Positive;
1007
1008                   begin
1009                      Add_Entity
1010                        (Pattern,
1011                         Get_Symbol_Name (P_Eun, P_Line, P_Column)
1012                         & ':' & Get_Gnatchop_File (File.Dep.Table (P_Eun))
1013                         & ':' & Get_Line (Get_Parent (Decl_Ref))
1014                         & ':' & Get_Column (Get_Parent (Decl_Ref)),
1015                         False);
1016
1017                      --  No default match is needed to look for the parent type
1018                      --  since we are using the fully qualified symbol name:
1019                      --  symbol:file:line:column
1020
1021                      Set_Default_Match (False);
1022
1023                      --  The parent hierarchy is defined in the same unit as
1024                      --  the derived type. So we want to revisit the unit.
1025
1026                      File_Pos_Backup   := File.Current_Line;
1027
1028                      Skip_To_First_X_Line
1029                        (File, D_Lines => False, W_Lines => False);
1030
1031                      while File.Buffer (File.Current_Line) /= EOF loop
1032                         Parse_X_Filename (File);
1033                         Parse_Identifier_Info
1034                           (Pattern       => Pattern,
1035                            File          => File,
1036                            Local_Symbols => False,
1037                            Der_Info      => Der_Info,
1038                            Type_Tree     => True,
1039                            Wide_Search   => False,
1040                            Labels_As_Ref => Labels_As_Ref);
1041                      end loop;
1042
1043                      File.Current_Line := File_Pos_Backup;
1044                   end Search_Parent_Tree;
1045                end if;
1046             end Parse_Derived_Info;
1047
1048          else
1049             while Ali (Ptr) /= '>'
1050               and then Ali (Ptr) /= ')'
1051               and then Ali (Ptr) /= '}'
1052             loop
1053                Ptr := Ptr + 1;
1054             end loop;
1055             Ptr := Ptr + 1;
1056          end if;
1057       end if;
1058
1059       --  To find the body, we will have to parse the file too
1060
1061       if Wide_Search then
1062          declare
1063             File_Ref : File_Reference;
1064             pragma Unreferenced (File_Ref);
1065             File_Name : constant String := Get_Gnatchop_File (File.X_File);
1066          begin
1067             File_Ref := Add_To_Xref_File (ALI_File_Name (File_Name), False);
1068          end;
1069       end if;
1070
1071       --  Parse references to this entity.
1072       --  Ptr points to next reference with leading blanks
1073
1074       loop
1075          --  Process references on current line
1076
1077          while Ali (Ptr) = ' ' or else Ali (Ptr) = ASCII.HT loop
1078
1079             --  For every reference read the line, type and column,
1080             --  optionally preceded by a file number and a pipe symbol.
1081
1082             Parse_Number (Ali, Ptr, R_Line);
1083
1084             if Ali (Ptr) = Pipe then
1085                Ptr := Ptr + 1;
1086                File_Ref := File_Name (File, R_Line);
1087
1088                Parse_Number (Ali, Ptr, R_Line);
1089             end if;
1090
1091             if Ali (Ptr) > ' ' then
1092                R_Type := Ali (Ptr);
1093                Ptr := Ptr + 1;
1094             end if;
1095
1096             --  Imported entities might special indication as to their external
1097             --  name:
1098             --    5U14*Foo2 5>20 6b<c,myfoo2>22
1099
1100             if R_Type = 'b'
1101               and then Ali (Ptr) = '<'
1102             then
1103                while Ptr <= Ali'Last
1104                  and then Ali (Ptr) /= '>'
1105                loop
1106                   Ptr := Ptr + 1;
1107                end loop;
1108                Ptr := Ptr + 1;
1109             end if;
1110
1111             Parse_Number (Ali, Ptr, R_Col);
1112
1113             --  Insert the reference or body in the table
1114
1115             Add_Reference
1116               (Decl_Ref, File_Ref, R_Line, R_Col, R_Type, Labels_As_Ref);
1117
1118             --  Skip generic information, if any
1119
1120             if Ali (Ptr) = '[' then
1121                declare
1122                   Num_Nested : Integer := 1;
1123
1124                begin
1125                   Ptr := Ptr + 1;
1126                   while Num_Nested /= 0 loop
1127                      if Ali (Ptr) = ']' then
1128                         Num_Nested := Num_Nested - 1;
1129                      elsif Ali (Ptr) = '[' then
1130                         Num_Nested := Num_Nested + 1;
1131                      end if;
1132
1133                      Ptr := Ptr + 1;
1134                   end loop;
1135                end;
1136             end if;
1137
1138          end loop;
1139
1140          Parse_EOL (Ali, Ptr);
1141
1142          --   Loop until new line is no continuation line
1143
1144          exit when Ali (Ptr) /= '.';
1145          Ptr := Ptr + 1;
1146       end loop;
1147    end Parse_Identifier_Info;
1148
1149    ------------------
1150    -- Parse_Number --
1151    ------------------
1152
1153    procedure Parse_Number
1154      (Source : not null access String;
1155       Ptr    : in out Positive;
1156       Number : out Natural)
1157    is
1158    begin
1159       --  Skip separators
1160
1161       while Source (Ptr) = ' ' or else Source (Ptr) = ASCII.HT loop
1162          Ptr := Ptr + 1;
1163       end loop;
1164
1165       Number := 0;
1166       while Source (Ptr) in '0' .. '9' loop
1167          Number :=
1168            10 * Number + (Character'Pos (Source (Ptr)) - Character'Pos ('0'));
1169          Ptr := Ptr + 1;
1170       end loop;
1171    end Parse_Number;
1172
1173    -----------------
1174    -- Parse_Token --
1175    -----------------
1176
1177    procedure Parse_Token
1178      (Source    : not null access String;
1179       Ptr       : in out Positive;
1180       Token_Ptr : out Positive)
1181    is
1182       In_Quotes : Character := ASCII.NUL;
1183
1184    begin
1185       --  Skip separators
1186
1187       while Source (Ptr) = ' ' or else Source (Ptr) = ASCII.HT loop
1188          Ptr := Ptr + 1;
1189       end loop;
1190
1191       Token_Ptr := Ptr;
1192
1193       --  Find end-of-token
1194
1195       while (In_Quotes /= ASCII.NUL or else
1196                not (Source (Ptr) = ' '
1197                      or else Source (Ptr) = ASCII.HT
1198                      or else Source (Ptr) = '<'
1199                      or else Source (Ptr) = '{'
1200                      or else Source (Ptr) = '['
1201                      or else Source (Ptr) = '='
1202                      or else Source (Ptr) = '('))
1203         and then Source (Ptr) >= ' '
1204       loop
1205          --  Double-quotes are used for operators
1206          --  Simple-quotes are used for character constants, for instance when
1207          --  they are found in an enumeration type "type A is ('+', '-');"
1208
1209          case Source (Ptr) is
1210             when '"' | ''' =>
1211                if In_Quotes = Source (Ptr) then
1212                   In_Quotes := ASCII.NUL;
1213                elsif In_Quotes = ASCII.NUL then
1214                   In_Quotes := Source (Ptr);
1215                end if;
1216
1217             when others =>
1218                null;
1219          end case;
1220
1221          Ptr := Ptr + 1;
1222       end loop;
1223    end Parse_Token;
1224
1225    ----------------------
1226    -- Parse_X_Filename --
1227    ----------------------
1228
1229    procedure Parse_X_Filename (File : in out ALI_File) is
1230       Ali     : String_Access renames File.Buffer;
1231       Ptr     : Positive renames File.Current_Line;
1232       File_Nr : Natural;
1233
1234    begin
1235       while Ali (Ptr) = 'X' loop
1236
1237          --  The current line is the start of a new Xref file section,
1238          --  whose format looks like:
1239
1240          --     " X 1 debug.ads"
1241
1242          --  Skip the X and read the file number for the new X_File
1243
1244          Ptr := Ptr + 1;
1245          Parse_Number (Ali, Ptr, File_Nr);
1246
1247          if File_Nr > 0 then
1248             File.X_File := File.Dep.Table (File_Nr);
1249          end if;
1250
1251          Parse_EOL (Ali, Ptr);
1252       end loop;
1253    end Parse_X_Filename;
1254
1255    --------------------
1256    -- Print_Gnatfind --
1257    --------------------
1258
1259    procedure Print_Gnatfind
1260      (References     : Boolean;
1261       Full_Path_Name : Boolean)
1262    is
1263       Decls : constant Declaration_Array_Access := Get_Declarations;
1264       Decl  : Declaration_Reference;
1265       Arr   : Reference_Array_Access;
1266
1267       procedure Print_Ref
1268         (Ref : Reference;
1269          Msg : String := "      ");
1270       --  Print a reference, according to the extended tag of the output
1271
1272       ---------------
1273       -- Print_Ref --
1274       ---------------
1275
1276       procedure Print_Ref
1277         (Ref : Reference;
1278          Msg : String := "      ")
1279       is
1280          F : String_Access :=
1281                Osint.To_Host_File_Spec
1282                 (Get_Gnatchop_File (Ref, Full_Path_Name));
1283
1284          Buffer : constant String :=
1285                     F.all &
1286                     ":" & Get_Line (Ref)   &
1287                     ":" & Get_Column (Ref) &
1288                     ": ";
1289
1290          Num_Blanks : Integer := Longest_File_Name + 10 - Buffer'Length;
1291
1292       begin
1293          Free (F);
1294          Num_Blanks := Integer'Max (0, Num_Blanks);
1295          Write_Line
1296            (Buffer
1297             & String'(1 .. Num_Blanks => ' ')
1298             & Msg & " " & Get_Symbol (Decl));
1299
1300          if Get_Source_Line (Ref)'Length /= 0 then
1301             Write_Line ("   " & Get_Source_Line (Ref));
1302          end if;
1303       end Print_Ref;
1304
1305    --  Start of processing for Print_Gnatfind
1306
1307    begin
1308       for D in Decls'Range loop
1309          Decl := Decls (D);
1310
1311          if Match (Decl) then
1312
1313             --  Output the declaration
1314
1315             declare
1316                Parent : constant Declaration_Reference := Get_Parent (Decl);
1317
1318                F : String_Access :=
1319                      Osint.To_Host_File_Spec
1320                       (Get_Gnatchop_File (Decl, Full_Path_Name));
1321
1322                Buffer : constant String :=
1323                           F.all &
1324                           ":" & Get_Line (Decl)   &
1325                           ":" & Get_Column (Decl) &
1326                           ": ";
1327
1328                Num_Blanks : Integer := Longest_File_Name + 10 - Buffer'Length;
1329
1330             begin
1331                Free (F);
1332                Num_Blanks := Integer'Max (0, Num_Blanks);
1333                Write_Line
1334                  (Buffer & String'(1 .. Num_Blanks => ' ')
1335                   & "(spec) " & Get_Symbol (Decl));
1336
1337                if Parent /= Empty_Declaration then
1338                   F := Osint.To_Host_File_Spec (Get_Gnatchop_File (Parent));
1339                   Write_Line
1340                     (Buffer & String'(1 .. Num_Blanks => ' ')
1341                      & "   derived from " & Get_Symbol (Parent)
1342                      & " ("
1343                      & F.all
1344                      & ':' & Get_Line (Parent)
1345                      & ':' & Get_Column (Parent) & ')');
1346                   Free (F);
1347                end if;
1348             end;
1349
1350             if Get_Source_Line (Decl)'Length /= 0 then
1351                Write_Line ("   " & Get_Source_Line (Decl));
1352             end if;
1353
1354             --  Output the body (sorted)
1355
1356             Arr := Get_References (Decl, Get_Bodies => True);
1357
1358             for R in Arr'Range loop
1359                Print_Ref (Arr (R), "(body)");
1360             end loop;
1361
1362             Free (Arr);
1363
1364             if References then
1365                Arr := Get_References
1366                  (Decl, Get_Writes => True, Get_Reads => True);
1367
1368                for R in Arr'Range loop
1369                   Print_Ref (Arr (R));
1370                end loop;
1371
1372                Free (Arr);
1373             end if;
1374          end if;
1375       end loop;
1376    end Print_Gnatfind;
1377
1378    ------------------
1379    -- Print_Unused --
1380    ------------------
1381
1382    procedure Print_Unused (Full_Path_Name : Boolean) is
1383       Decls : constant Declaration_Array_Access := Get_Declarations;
1384       Decl  : Declaration_Reference;
1385       Arr   : Reference_Array_Access;
1386       F     : String_Access;
1387
1388    begin
1389       for D in Decls'Range loop
1390          Decl := Decls (D);
1391
1392          if References_Count
1393              (Decl, Get_Reads => True, Get_Writes => True) = 0
1394          then
1395             F := Osint.To_Host_File_Spec
1396               (Get_Gnatchop_File (Decl, Full_Path_Name));
1397             Write_Str (Get_Symbol (Decl)
1398                         & " ("
1399                         & Get_Full_Type (Decl)
1400                         & ") "
1401                         & F.all
1402                         & ':'
1403                         & Get_Line (Decl)
1404                         & ':'
1405                         & Get_Column (Decl));
1406             Free (F);
1407
1408             --  Print the body if any
1409
1410             Arr := Get_References (Decl, Get_Bodies => True);
1411
1412             for R in Arr'Range loop
1413                F := Osint.To_Host_File_Spec
1414                       (Get_Gnatchop_File (Arr (R), Full_Path_Name));
1415                Write_Str (' '
1416                            & F.all
1417                            & ':' & Get_Line (Arr (R))
1418                            & ':' & Get_Column (Arr (R)));
1419                Free (F);
1420             end loop;
1421
1422             Write_Eol;
1423             Free (Arr);
1424          end if;
1425       end loop;
1426    end Print_Unused;
1427
1428    --------------
1429    -- Print_Vi --
1430    --------------
1431
1432    procedure Print_Vi (Full_Path_Name : Boolean) is
1433       Tab   : constant Character := ASCII.HT;
1434       Decls : constant Declaration_Array_Access :=
1435                 Get_Declarations (Sorted => False);
1436       Decl  : Declaration_Reference;
1437       Arr   : Reference_Array_Access;
1438       F     : String_Access;
1439
1440    begin
1441       for D in Decls'Range loop
1442          Decl := Decls (D);
1443
1444          F := Osint.To_Host_File_Spec (Get_File (Decl, Full_Path_Name));
1445          Write_Line (Get_Symbol (Decl) & Tab & F.all & Tab & Get_Line (Decl));
1446          Free (F);
1447
1448          --  Print the body if any
1449
1450          Arr := Get_References (Decl, Get_Bodies => True);
1451
1452          for R in Arr'Range loop
1453             F := Osint.To_Host_File_Spec (Get_File (Arr (R), Full_Path_Name));
1454             Write_Line
1455               (Get_Symbol (Decl) & Tab & F.all & Tab  & Get_Line (Arr (R)));
1456             Free (F);
1457          end loop;
1458
1459          Free (Arr);
1460
1461          --  Print the modifications
1462
1463          Arr := Get_References (Decl, Get_Writes => True, Get_Reads => True);
1464
1465          for R in Arr'Range loop
1466             F := Osint.To_Host_File_Spec (Get_File (Arr (R), Full_Path_Name));
1467             Write_Line
1468               (Get_Symbol (Decl) & Tab & F.all & Tab & Get_Line (Arr (R)));
1469             Free (F);
1470          end loop;
1471
1472          Free (Arr);
1473       end loop;
1474    end Print_Vi;
1475
1476    ----------------
1477    -- Print_Xref --
1478    ----------------
1479
1480    procedure Print_Xref (Full_Path_Name : Boolean) is
1481       Decls : constant Declaration_Array_Access := Get_Declarations;
1482       Decl : Declaration_Reference;
1483
1484       Margin : constant := 10;
1485       --  Column where file names start
1486
1487       procedure New_Line80;
1488       --  Go to start of new line
1489
1490       procedure Print80 (S : String);
1491       --  Print the text, respecting the 80 columns rule
1492
1493       procedure Print_Ref (Line, Column : String);
1494       --  The beginning of the output is aligned on a column multiple of 9
1495
1496       procedure Print_List
1497         (Decl       : Declaration_Reference;
1498          Msg        : String;
1499          Get_Reads  : Boolean := False;
1500          Get_Writes : Boolean := False;
1501          Get_Bodies : Boolean := False);
1502       --  Print a list of references. If the list is not empty, Msg will
1503       --  be printed prior to the list.
1504
1505       ----------------
1506       -- New_Line80 --
1507       ----------------
1508
1509       procedure New_Line80 is
1510       begin
1511          Write_Eol;
1512          Write_Str (String'(1 .. Margin - 1 => ' '));
1513       end New_Line80;
1514
1515       -------------
1516       -- Print80 --
1517       -------------
1518
1519       procedure Print80 (S : String) is
1520          Align : Natural := Margin - (Integer (Column) mod Margin);
1521
1522       begin
1523          if Align = Margin then
1524             Align := 0;
1525          end if;
1526
1527          Write_Str (String'(1 .. Align => ' ') & S);
1528       end Print80;
1529
1530       ---------------
1531       -- Print_Ref --
1532       ---------------
1533
1534       procedure Print_Ref (Line, Column : String) is
1535          Line_Align : constant Integer := 4 - Line'Length;
1536
1537          S : constant String := String'(1 .. Line_Align => ' ')
1538                                   & Line & ':' & Column;
1539
1540          Align : Natural := Margin - (Integer (Output.Column) mod Margin);
1541
1542       begin
1543          if Align = Margin then
1544             Align := 0;
1545          end if;
1546
1547          if Integer (Output.Column) + Align + S'Length > 79 then
1548             New_Line80;
1549             Align := 0;
1550          end if;
1551
1552          Write_Str (String'(1 .. Align => ' ') & S);
1553       end Print_Ref;
1554
1555       ----------------
1556       -- Print_List --
1557       ----------------
1558
1559       procedure Print_List
1560         (Decl       : Declaration_Reference;
1561          Msg        : String;
1562          Get_Reads  : Boolean := False;
1563          Get_Writes : Boolean := False;
1564          Get_Bodies : Boolean := False)
1565       is
1566          Arr : Reference_Array_Access :=
1567                  Get_References
1568                    (Decl,
1569                     Get_Writes => Get_Writes,
1570                     Get_Reads  => Get_Reads,
1571                     Get_Bodies => Get_Bodies);
1572          File : File_Reference := Empty_File;
1573          F    : String_Access;
1574
1575       begin
1576          if Arr'Length /= 0 then
1577             Write_Eol;
1578             Write_Str (Msg);
1579          end if;
1580
1581          for R in Arr'Range loop
1582             if Get_File_Ref (Arr (R)) /= File then
1583                if File /= Empty_File then
1584                   New_Line80;
1585                end if;
1586
1587                File := Get_File_Ref (Arr (R));
1588                F := Osint.To_Host_File_Spec
1589                  (Get_Gnatchop_File (Arr (R), Full_Path_Name));
1590                Write_Str (F.all & ' ');
1591                Free (F);
1592             end if;
1593
1594             Print_Ref (Get_Line (Arr (R)), Get_Column (Arr (R)));
1595          end loop;
1596
1597          Free (Arr);
1598       end Print_List;
1599
1600       F : String_Access;
1601
1602    --  Start of processing for Print_Xref
1603
1604    begin
1605       for D in Decls'Range loop
1606          Decl := Decls (D);
1607
1608          Write_Str (Get_Symbol (Decl));
1609
1610          --  Put the declaration type in column Type_Position, but if the
1611          --  declaration name is too long, put at least one space between its
1612          --  name and its type.
1613
1614          while Column < Type_Position - 1 loop
1615             Write_Char (' ');
1616          end loop;
1617
1618          Write_Char (' ');
1619
1620          Write_Line (Get_Full_Type (Decl));
1621
1622          Write_Parent_Info : declare
1623             Parent : constant Declaration_Reference := Get_Parent (Decl);
1624
1625          begin
1626             if Parent /= Empty_Declaration then
1627                Write_Str ("  Ptype: ");
1628                F := Osint.To_Host_File_Spec (Get_Gnatchop_File (Parent));
1629                Print80 (F.all);
1630                Free (F);
1631                Print_Ref (Get_Line (Parent), Get_Column (Parent));
1632                Print80 ("  " & Get_Symbol (Parent));
1633                Write_Eol;
1634             end if;
1635          end Write_Parent_Info;
1636
1637          Write_Str ("  Decl:  ");
1638          F := Osint.To_Host_File_Spec
1639                (Get_Gnatchop_File (Decl, Full_Path_Name));
1640          Print80 (F.all & ' ');
1641          Free (F);
1642          Print_Ref (Get_Line (Decl), Get_Column (Decl));
1643
1644          Print_List
1645            (Decl, "  Body:  ", Get_Bodies => True);
1646          Print_List
1647            (Decl, "  Modi:  ", Get_Writes => True);
1648          Print_List
1649            (Decl, "  Ref:   ", Get_Reads => True);
1650          Write_Eol;
1651       end loop;
1652    end Print_Xref;
1653
1654    ------------
1655    -- Search --
1656    ------------
1657
1658    procedure Search
1659      (Pattern       : Search_Pattern;
1660       Local_Symbols : Boolean;
1661       Wide_Search   : Boolean;
1662       Read_Only     : Boolean;
1663       Der_Info      : Boolean;
1664       Type_Tree     : Boolean)
1665    is
1666       type String_Access is access String;
1667       procedure Free is new Unchecked_Deallocation (String, String_Access);
1668
1669       ALIfile   : ALI_File;
1670       File_Ref  : File_Reference;
1671       Strip_Num : Natural := 0;
1672       Ali_Name  : String_Access;
1673
1674    begin
1675       --  If we want all the .ali files, then find them
1676
1677       if Wide_Search then
1678          Find_ALI_Files;
1679       end if;
1680
1681       loop
1682          --  Get the next unread ali file
1683
1684          File_Ref := Next_Unvisited_File;
1685
1686          exit when File_Ref = Empty_File;
1687
1688          --  Find the ALI file to use. Most of the time, it will be the unit
1689          --  name, with a different extension. However, when dealing with
1690          --  separates the ALI file is in fact the parent's ALI file (and this
1691          --  is recursive, in case the parent itself is a separate).
1692
1693          Strip_Num := 0;
1694          loop
1695             Free (Ali_Name);
1696             Ali_Name := new String'
1697               (Get_File (File_Ref, With_Dir => True, Strip => Strip_Num));
1698
1699             --  Stripped too many things...
1700
1701             if Ali_Name.all = "" then
1702                if Get_Emit_Warning (File_Ref) then
1703                   Set_Standard_Error;
1704                   Write_Line
1705                     ("warning : file " & Get_File (File_Ref, With_Dir => True)
1706                      & " not found");
1707                   Set_Standard_Output;
1708                end if;
1709                Free (Ali_Name);
1710                exit;
1711
1712             --  If not found, try the parent's ALI file (this is needed for
1713             --  separate units and subprograms).
1714
1715             --  Reset the cached directory first, in case the separate's
1716             --  ALI file is not in the same directory.
1717
1718             elsif not File_Exists (Ali_Name.all) then
1719                Strip_Num := Strip_Num + 1;
1720                Reset_Directory (File_Ref);
1721
1722             --  Else we finally found it
1723
1724             else
1725                exit;
1726             end if;
1727          end loop;
1728
1729          --  If we had to get the parent's ALI, insert it in the list as usual.
1730          --  This is to avoid parsing it twice in case it has already been
1731          --  parsed.
1732
1733          if Ali_Name /= null and then Strip_Num /= 0 then
1734             File_Ref := Add_To_Xref_File
1735               (File_Name => Ali_Name.all,
1736                Visited   => False);
1737
1738          --  Now that we have a file name, parse it to find any reference to
1739          --  the entity.
1740
1741          elsif Ali_Name /= null
1742            and then (Read_Only or else Is_Writable_File (Ali_Name.all))
1743          then
1744             begin
1745                Open (Ali_Name.all, ALIfile);
1746                while ALIfile.Buffer (ALIfile.Current_Line) /= EOF loop
1747                   Parse_X_Filename (ALIfile);
1748                   Parse_Identifier_Info
1749                     (Pattern, ALIfile, Local_Symbols,
1750                      Der_Info, Type_Tree, Wide_Search, Labels_As_Ref => True);
1751                end loop;
1752
1753             exception
1754                when No_Xref_Information   =>
1755                   if Get_Emit_Warning (File_Ref) then
1756                      Set_Standard_Error;
1757                      Write_Line
1758                        ("warning : No cross-referencing information in  "
1759                         & Ali_Name.all);
1760                      Set_Standard_Output;
1761                   end if;
1762             end;
1763          end if;
1764       end loop;
1765
1766       Free (Ali_Name);
1767    end Search;
1768
1769    -----------------
1770    -- Search_Xref --
1771    -----------------
1772
1773    procedure Search_Xref
1774      (Local_Symbols : Boolean;
1775       Read_Only     : Boolean;
1776       Der_Info      : Boolean)
1777    is
1778       ALIfile      : ALI_File;
1779       File_Ref     : File_Reference;
1780       Null_Pattern : Search_Pattern;
1781
1782    begin
1783       Null_Pattern.Initialized := False;
1784
1785       loop
1786          --  Find the next unvisited file
1787
1788          File_Ref := Next_Unvisited_File;
1789          exit when File_Ref = Empty_File;
1790
1791          --  Search the object directories for the .ali file
1792
1793          declare
1794             F : constant String := Get_File (File_Ref, With_Dir => True);
1795
1796          begin
1797             if Read_Only or else Is_Writable_File (F) then
1798                Open (F, ALIfile, True);
1799
1800                while ALIfile.Buffer (ALIfile.Current_Line) /= EOF loop
1801                   Parse_X_Filename (ALIfile);
1802                   Parse_Identifier_Info
1803                     (Null_Pattern, ALIfile, Local_Symbols, Der_Info,
1804                      Labels_As_Ref => False);
1805                end loop;
1806             end if;
1807
1808          exception
1809             when No_Xref_Information =>  null;
1810          end;
1811       end loop;
1812    end Search_Xref;
1813
1814 end Xref_Lib;