OSDN Git Service

* gcc-interface/misc.c (gnat_expand_expr): Remove.
[pf3gnuchains/gcc-fork.git] / gcc / ada / g-comlin.adb
1 ------------------------------------------------------------------------------
2 --                                                                          --
3 --                         GNAT COMPILER COMPONENTS                         --
4 --                                                                          --
5 --                    G N A T . C O M M A N D _ L I N E                     --
6 --                                                                          --
7 --                                 B o d y                                  --
8 --                                                                          --
9 --          Copyright (C) 1999-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.                                     --
17 --                                                                          --
18 -- As a special exception under Section 7 of GPL version 3, you are granted --
19 -- additional permissions described in the GCC Runtime Library Exception,   --
20 -- version 3.1, as published by the Free Software Foundation.               --
21 --                                                                          --
22 -- You should have received a copy of the GNU General Public License and    --
23 -- a copy of the GCC Runtime Library Exception along with this program;     --
24 -- see the files COPYING3 and COPYING.RUNTIME respectively.  If not, see    --
25 -- <http://www.gnu.org/licenses/>.                                          --
26 --                                                                          --
27 -- GNAT was originally developed  by the GNAT team at  New York University. --
28 -- Extensive contributions were provided by Ada Core Technologies Inc.      --
29 --                                                                          --
30 ------------------------------------------------------------------------------
31
32 with Ada.Unchecked_Deallocation;
33 with Ada.Strings.Unbounded;
34
35 with GNAT.OS_Lib; use GNAT.OS_Lib;
36
37 package body GNAT.Command_Line is
38
39    package CL renames Ada.Command_Line;
40
41    type Switch_Parameter_Type is
42      (Parameter_None,
43       Parameter_With_Optional_Space,  --  ':' in getopt
44       Parameter_With_Space_Or_Equal,  --  '=' in getopt
45       Parameter_No_Space,             --  '!' in getopt
46       Parameter_Optional);            --  '?' in getopt
47
48    procedure Set_Parameter
49      (Variable : out Parameter_Type;
50       Arg_Num  : Positive;
51       First    : Positive;
52       Last     : Positive;
53       Extra    : Character := ASCII.NUL);
54    pragma Inline (Set_Parameter);
55    --  Set the parameter that will be returned by Parameter below
56    --  Parameters need to be defined ???
57
58    function Goto_Next_Argument_In_Section (Parser : Opt_Parser) return Boolean;
59    --  Go to the next argument on the command line. If we are at the end of
60    --  the current section, we want to make sure there is no other identical
61    --  section on the command line (there might be multiple instances of
62    --  -largs). Returns True iff there is another argument.
63
64    function Get_File_Names_Case_Sensitive return Integer;
65    pragma Import (C, Get_File_Names_Case_Sensitive,
66                   "__gnat_get_file_names_case_sensitive");
67
68    File_Names_Case_Sensitive : constant Boolean :=
69                                  Get_File_Names_Case_Sensitive /= 0;
70
71    procedure Canonical_Case_File_Name (S : in out String);
72    --  Given a file name, converts it to canonical case form. For systems where
73    --  file names are case sensitive, this procedure has no effect. If file
74    --  names are not case sensitive (i.e. for example if you have the file
75    --  "xyz.adb", you can refer to it as XYZ.adb or XyZ.AdB), then this call
76    --  converts the given string to canonical all lower case form, so that two
77    --  file names compare equal if they refer to the same file.
78
79    procedure Internal_Initialize_Option_Scan
80      (Parser                   : Opt_Parser;
81       Switch_Char              : Character;
82       Stop_At_First_Non_Switch : Boolean;
83       Section_Delimiters       : String);
84    --  Initialize Parser, which must have been allocated already
85
86    function Argument (Parser : Opt_Parser; Index : Integer) return String;
87    --  Return the index-th command line argument
88
89    procedure Find_Longest_Matching_Switch
90      (Switches          : String;
91       Arg               : String;
92       Index_In_Switches : out Integer;
93       Switch_Length     : out Integer;
94       Param             : out Switch_Parameter_Type);
95    --  Return the Longest switch from Switches that at least partially
96    --  partially Arg. Index_In_Switches is set to 0 if none matches.
97    --  What are other parameters??? in particular Param is not always set???
98
99    procedure Unchecked_Free is new Ada.Unchecked_Deallocation
100      (Argument_List, Argument_List_Access);
101
102    procedure Unchecked_Free is new Ada.Unchecked_Deallocation
103      (Command_Line_Configuration_Record, Command_Line_Configuration);
104
105    procedure Remove (Line : in out Argument_List_Access; Index : Integer);
106    --  Remove a specific element from Line
107
108    procedure Add
109      (Line   : in out Argument_List_Access;
110       Str    : String_Access;
111       Before : Boolean := False);
112    --  Add a new element to Line. If Before is True, the item is inserted at
113    --  the beginning, else it is appended.
114
115    function Can_Have_Parameter (S : String) return Boolean;
116    --  True if S can have a parameter.
117
118    function Require_Parameter (S : String) return Boolean;
119    --  True if S requires a parameter.
120
121    function Actual_Switch (S : String) return String;
122    --  Remove any possible trailing '!', ':', '?' and '='
123
124    generic
125       with procedure Callback (Simple_Switch : String; Parameter : String);
126    procedure For_Each_Simple_Switch
127      (Cmd       : Command_Line;
128       Switch    : String;
129       Parameter : String  := "";
130       Unalias   : Boolean := True);
131    --  Breaks Switch into as simple switches as possible (expanding aliases and
132    --  ungrouping common prefixes when possible), and call Callback for each of
133    --  these.
134
135    procedure Sort_Sections
136      (Line     : GNAT.OS_Lib.Argument_List_Access;
137       Sections : GNAT.OS_Lib.Argument_List_Access;
138       Params   : GNAT.OS_Lib.Argument_List_Access);
139    --  Reorder the command line switches so that the switches belonging to a
140    --  section are grouped together.
141
142    procedure Group_Switches
143      (Cmd      : Command_Line;
144       Result   : Argument_List_Access;
145       Sections : Argument_List_Access;
146       Params   : Argument_List_Access);
147    --  Group switches with common prefixes whenever possible. Once they have
148    --  been grouped, we also check items for possible aliasing.
149
150    procedure Alias_Switches
151      (Cmd    : Command_Line;
152       Result : Argument_List_Access;
153       Params : Argument_List_Access);
154    --  When possible, replace one or more switches by an alias, i.e. a shorter
155    --  version.
156
157    function Looking_At
158      (Type_Str  : String;
159       Index     : Natural;
160       Substring : String) return Boolean;
161    --  Return True if the characters starting at Index in Type_Str are
162    --  equivalent to Substring.
163
164    --------------
165    -- Argument --
166    --------------
167
168    function Argument (Parser : Opt_Parser; Index : Integer) return String is
169    begin
170       if Parser.Arguments /= null then
171          return Parser.Arguments (Index + Parser.Arguments'First - 1).all;
172       else
173          return CL.Argument (Index);
174       end if;
175    end Argument;
176
177    ------------------------------
178    -- Canonical_Case_File_Name --
179    ------------------------------
180
181    procedure Canonical_Case_File_Name (S : in out String) is
182    begin
183       if not File_Names_Case_Sensitive then
184          for J in S'Range loop
185             if S (J) in 'A' .. 'Z' then
186                S (J) := Character'Val
187                          (Character'Pos (S (J)) +
188                           Character'Pos ('a')   -
189                           Character'Pos ('A'));
190             end if;
191          end loop;
192       end if;
193    end Canonical_Case_File_Name;
194
195    ---------------
196    -- Expansion --
197    ---------------
198
199    function Expansion (Iterator : Expansion_Iterator) return String is
200       use GNAT.Directory_Operations;
201       type Pointer is access all Expansion_Iterator;
202
203       It   : constant Pointer := Iterator'Unrestricted_Access;
204       S    : String (1 .. 1024);
205       Last : Natural;
206
207       Current : Depth := It.Current_Depth;
208       NL      : Positive;
209
210    begin
211       --  It is assumed that a directory is opened at the current level.
212       --  Otherwise GNAT.Directory_Operations.Directory_Error will be raised
213       --  at the first call to Read.
214
215       loop
216          Read (It.Levels (Current).Dir, S, Last);
217
218          --  If we have exhausted the directory, close it and go back one level
219
220          if Last = 0 then
221             Close (It.Levels (Current).Dir);
222
223             --  If we are at level 1, we are finished; return an empty string
224
225             if Current = 1 then
226                return String'(1 .. 0 => ' ');
227             else
228                --  Otherwise continue with the directory at the previous level
229
230                Current := Current - 1;
231                It.Current_Depth := Current;
232             end if;
233
234          --  If this is a directory, that is neither "." or "..", attempt to
235          --  go to the next level.
236
237          elsif Is_Directory
238            (It.Dir_Name (1 .. It.Levels (Current).Name_Last) & S (1 .. Last))
239            and then S (1 .. Last) /= "."
240            and then S (1 .. Last) /= ".."
241          then
242             --  We can go to the next level only if we have not reached the
243             --  maximum depth,
244
245             if Current < It.Maximum_Depth then
246                NL := It.Levels (Current).Name_Last;
247
248                --  And if relative path of this new directory is not too long
249
250                if NL + Last + 1 < Max_Path_Length then
251                   Current := Current + 1;
252                   It.Current_Depth := Current;
253                   It.Dir_Name (NL + 1 .. NL + Last) := S (1 .. Last);
254                   NL := NL + Last + 1;
255                   It.Dir_Name (NL) := Directory_Separator;
256                   It.Levels (Current).Name_Last := NL;
257                   Canonical_Case_File_Name (It.Dir_Name (1 .. NL));
258
259                   --  Open the new directory, and read from it
260
261                   GNAT.Directory_Operations.Open
262                     (It.Levels (Current).Dir, It.Dir_Name (1 .. NL));
263                end if;
264             end if;
265          end if;
266
267          --  Check the relative path against the pattern
268
269          --  Note that we try to match also against directory names, since
270          --  clients of this function may expect to retrieve directories.
271
272          declare
273             Name : String :=
274                      It.Dir_Name (It.Start .. It.Levels (Current).Name_Last)
275                        & S (1 .. Last);
276
277          begin
278             Canonical_Case_File_Name (Name);
279
280             --  If it matches return the relative path
281
282             if GNAT.Regexp.Match (Name, Iterator.Regexp) then
283                return Name;
284             end if;
285          end;
286       end loop;
287    end Expansion;
288
289    -----------------
290    -- Full_Switch --
291    -----------------
292
293    function Full_Switch
294      (Parser : Opt_Parser := Command_Line_Parser) return String
295    is
296    begin
297       if Parser.The_Switch.Extra = ASCII.NUL then
298          return Argument (Parser, Parser.The_Switch.Arg_Num)
299            (Parser.The_Switch.First .. Parser.The_Switch.Last);
300       else
301          return Parser.The_Switch.Extra
302            & Argument (Parser, Parser.The_Switch.Arg_Num)
303            (Parser.The_Switch.First .. Parser.The_Switch.Last);
304       end if;
305    end Full_Switch;
306
307    ------------------
308    -- Get_Argument --
309    ------------------
310
311    function Get_Argument
312      (Do_Expansion : Boolean    := False;
313       Parser       : Opt_Parser := Command_Line_Parser) return String
314    is
315    begin
316       if Parser.In_Expansion then
317          declare
318             S : constant String := Expansion (Parser.Expansion_It);
319          begin
320             if S'Length /= 0 then
321                return S;
322             else
323                Parser.In_Expansion := False;
324             end if;
325          end;
326       end if;
327
328       if Parser.Current_Argument > Parser.Arg_Count then
329
330          --  If this is the first time this function is called
331
332          if Parser.Current_Index = 1 then
333             Parser.Current_Argument := 1;
334             while Parser.Current_Argument <= Parser.Arg_Count
335               and then Parser.Section (Parser.Current_Argument) /=
336                 Parser.Current_Section
337             loop
338                Parser.Current_Argument := Parser.Current_Argument + 1;
339             end loop;
340          else
341             return String'(1 .. 0 => ' ');
342          end if;
343
344       elsif Parser.Section (Parser.Current_Argument) = 0 then
345          while Parser.Current_Argument <= Parser.Arg_Count
346            and then Parser.Section (Parser.Current_Argument) /=
347              Parser.Current_Section
348          loop
349             Parser.Current_Argument := Parser.Current_Argument + 1;
350          end loop;
351       end if;
352
353       Parser.Current_Index := Integer'Last;
354
355       while Parser.Current_Argument <= Parser.Arg_Count
356         and then Parser.Is_Switch (Parser.Current_Argument)
357       loop
358          Parser.Current_Argument := Parser.Current_Argument + 1;
359       end loop;
360
361       if Parser.Current_Argument > Parser.Arg_Count then
362          return String'(1 .. 0 => ' ');
363       elsif Parser.Section (Parser.Current_Argument) = 0 then
364          return Get_Argument (Do_Expansion);
365       end if;
366
367       Parser.Current_Argument := Parser.Current_Argument + 1;
368
369       --  Could it be a file name with wild cards to expand?
370
371       if Do_Expansion then
372          declare
373             Arg   : constant String :=
374                       Argument (Parser, Parser.Current_Argument - 1);
375             Index : Positive;
376
377          begin
378             Index := Arg'First;
379             while Index <= Arg'Last loop
380                if Arg (Index) = '*'
381                  or else Arg (Index) = '?'
382                  or else Arg (Index) = '['
383                then
384                   Parser.In_Expansion := True;
385                   Start_Expansion (Parser.Expansion_It, Arg);
386                   return Get_Argument (Do_Expansion);
387                end if;
388
389                Index := Index + 1;
390             end loop;
391          end;
392       end if;
393
394       return Argument (Parser, Parser.Current_Argument - 1);
395    end Get_Argument;
396
397    ----------------------------------
398    -- Find_Longest_Matching_Switch --
399    ----------------------------------
400
401    procedure Find_Longest_Matching_Switch
402      (Switches          : String;
403       Arg               : String;
404       Index_In_Switches : out Integer;
405       Switch_Length     : out Integer;
406       Param             : out Switch_Parameter_Type)
407    is
408       Index  : Natural;
409       Length : Natural := 1;
410       P      : Switch_Parameter_Type;
411
412    begin
413       Index_In_Switches := 0;
414       Switch_Length     := 0;
415
416       --  Remove all leading spaces first to make sure that Index points
417       --  at the start of the first switch.
418
419       Index := Switches'First;
420       while Index <= Switches'Last and then Switches (Index) = ' ' loop
421          Index := Index + 1;
422       end loop;
423
424       while Index <= Switches'Last loop
425
426          --  Search the length of the parameter at this position in Switches
427
428          Length := Index;
429          while Length <= Switches'Last
430            and then Switches (Length) /= ' '
431          loop
432             Length := Length + 1;
433          end loop;
434
435          if Length = Index + 1 then
436             P := Parameter_None;
437          else
438             case Switches (Length - 1) is
439                when ':'    =>
440                   P      := Parameter_With_Optional_Space;
441                   Length := Length - 1;
442                when '='    =>
443                   P      := Parameter_With_Space_Or_Equal;
444                   Length := Length - 1;
445                when '!'    =>
446                   P      := Parameter_No_Space;
447                   Length := Length - 1;
448                when '?'    =>
449                   P      := Parameter_Optional;
450                   Length := Length - 1;
451                when others =>
452                   P      := Parameter_None;
453             end case;
454          end if;
455
456          --  If it is the one we searched, it may be a candidate
457
458          if Arg'First + Length - 1 - Index <= Arg'Last
459            and then Switches (Index .. Length - 1) =
460                       Arg (Arg'First .. Arg'First + Length - 1 - Index)
461            and then Length - Index > Switch_Length
462          then
463             Param             := P;
464             Index_In_Switches := Index;
465             Switch_Length     := Length - Index;
466          end if;
467
468          --  Look for the next switch in Switches
469
470          while Index <= Switches'Last
471            and then Switches (Index) /= ' '
472          loop
473             Index := Index + 1;
474          end loop;
475
476          Index := Index + 1;
477       end loop;
478    end Find_Longest_Matching_Switch;
479
480    ------------
481    -- Getopt --
482    ------------
483
484    function Getopt
485      (Switches    : String;
486       Concatenate : Boolean := True;
487       Parser      : Opt_Parser := Command_Line_Parser) return Character
488    is
489       Dummy : Boolean;
490       pragma Unreferenced (Dummy);
491
492    begin
493       <<Restart>>
494
495       --  If we have finished parsing the current command line item (there
496       --  might be multiple switches in a single item), then go to the next
497       --  element
498
499       if Parser.Current_Argument > Parser.Arg_Count
500         or else (Parser.Current_Index >
501                    Argument (Parser, Parser.Current_Argument)'Last
502                  and then not Goto_Next_Argument_In_Section (Parser))
503       then
504          return ASCII.NUL;
505       end if;
506
507       --  By default, the switch will not have a parameter
508
509       Parser.The_Parameter :=
510         (Integer'Last, Integer'Last, Integer'Last - 1, ASCII.NUL);
511       Parser.The_Separator := ASCII.NUL;
512
513       declare
514          Arg            : constant String :=
515                             Argument (Parser, Parser.Current_Argument);
516          Index_Switches : Natural := 0;
517          Max_Length     : Natural := 0;
518          End_Index      : Natural;
519          Param          : Switch_Parameter_Type;
520       begin
521          --  If we are on a new item, test if this might be a switch
522
523          if Parser.Current_Index = Arg'First then
524             if Arg (Arg'First) /= Parser.Switch_Character then
525
526                --  If it isn't a switch, return it immediately. We also know it
527                --  isn't the parameter to a previous switch, since that has
528                --  already been handled
529
530                if Switches (Switches'First) = '*' then
531                   Set_Parameter
532                     (Parser.The_Switch,
533                      Arg_Num => Parser.Current_Argument,
534                      First   => Arg'First,
535                      Last    => Arg'Last);
536                   Parser.Is_Switch (Parser.Current_Argument) := True;
537                   Dummy := Goto_Next_Argument_In_Section (Parser);
538                   return '*';
539                end if;
540
541                if Parser.Stop_At_First then
542                   Parser.Current_Argument := Positive'Last;
543                   return ASCII.NUL;
544
545                elsif not Goto_Next_Argument_In_Section (Parser) then
546                   return ASCII.NUL;
547
548                else
549                   --  Recurse to get the next switch on the command line
550
551                   goto Restart;
552                end if;
553             end if;
554
555             --  We are on the first character of a new command line argument,
556             --  which starts with Switch_Character. Further analysis is needed.
557
558             Parser.Current_Index := Parser.Current_Index + 1;
559             Parser.Is_Switch (Parser.Current_Argument) := True;
560          end if;
561
562          Find_Longest_Matching_Switch
563            (Switches          => Switches,
564             Arg               => Arg (Parser.Current_Index .. Arg'Last),
565             Index_In_Switches => Index_Switches,
566             Switch_Length     => Max_Length,
567             Param             => Param);
568
569          --  If switch is not accepted, it is either invalid or is returned
570          --  in the context of '*'.
571
572          if Index_Switches = 0 then
573
574             --  Depending on the value of Concatenate, the full switch is
575             --  a single character or the rest of the argument.
576
577             if Concatenate then
578                End_Index := Parser.Current_Index;
579             else
580                End_Index := Arg'Last;
581             end if;
582
583             if Switches (Switches'First) = '*' then
584
585                --  Always prepend the switch character, so that users know that
586                --  this comes from a switch on the command line. This is
587                --  especially important when Concatenate is False, since
588                --  otherwise the current argument first character is lost.
589
590                Set_Parameter
591                  (Parser.The_Switch,
592                   Arg_Num => Parser.Current_Argument,
593                   First   => Parser.Current_Index,
594                   Last    => Arg'Last,
595                   Extra   => Parser.Switch_Character);
596                Parser.Is_Switch (Parser.Current_Argument) := True;
597                Dummy := Goto_Next_Argument_In_Section (Parser);
598                return '*';
599             end if;
600
601             Set_Parameter
602               (Parser.The_Switch,
603                Arg_Num => Parser.Current_Argument,
604                First   => Parser.Current_Index,
605                Last    => End_Index);
606             Parser.Current_Index := End_Index + 1;
607             raise Invalid_Switch;
608          end if;
609
610          End_Index := Parser.Current_Index + Max_Length - 1;
611          Set_Parameter
612            (Parser.The_Switch,
613             Arg_Num => Parser.Current_Argument,
614             First   => Parser.Current_Index,
615             Last    => End_Index);
616
617          case Param is
618             when Parameter_With_Optional_Space =>
619                if End_Index < Arg'Last then
620                   Set_Parameter
621                     (Parser.The_Parameter,
622                      Arg_Num => Parser.Current_Argument,
623                      First   => End_Index + 1,
624                      Last    => Arg'Last);
625                   Dummy := Goto_Next_Argument_In_Section (Parser);
626
627                elsif Parser.Current_Argument < Parser.Arg_Count
628                  and then Parser.Section (Parser.Current_Argument + 1) /= 0
629                then
630                   Parser.Current_Argument := Parser.Current_Argument + 1;
631                   Parser.The_Separator := ' ';
632                   Set_Parameter
633                     (Parser.The_Parameter,
634                      Arg_Num => Parser.Current_Argument,
635                      First => Argument (Parser, Parser.Current_Argument)'First,
636                      Last  => Argument (Parser, Parser.Current_Argument)'Last);
637                   Parser.Is_Switch (Parser.Current_Argument) := True;
638                   Dummy := Goto_Next_Argument_In_Section (Parser);
639
640                else
641                   Parser.Current_Index := End_Index + 1;
642                   raise Invalid_Parameter;
643                end if;
644
645             when Parameter_With_Space_Or_Equal =>
646
647                --  If the switch is of the form <switch>=xxx
648
649                if End_Index < Arg'Last then
650
651                   if Arg (End_Index + 1) = '='
652                     and then End_Index + 1 < Arg'Last
653                   then
654                      Parser.The_Separator := '=';
655                      Set_Parameter
656                        (Parser.The_Parameter,
657                         Arg_Num => Parser.Current_Argument,
658                         First   => End_Index + 2,
659                         Last    => Arg'Last);
660                      Dummy := Goto_Next_Argument_In_Section (Parser);
661                   else
662                      Parser.Current_Index := End_Index + 1;
663                      raise Invalid_Parameter;
664                   end if;
665
666                --  If the switch is of the form <switch> xxx
667
668                elsif Parser.Current_Argument < Parser.Arg_Count
669                  and then Parser.Section (Parser.Current_Argument + 1) /= 0
670                then
671                   Parser.Current_Argument := Parser.Current_Argument + 1;
672                   Parser.The_Separator := ' ';
673                   Set_Parameter
674                     (Parser.The_Parameter,
675                      Arg_Num => Parser.Current_Argument,
676                      First => Argument (Parser, Parser.Current_Argument)'First,
677                      Last  => Argument (Parser, Parser.Current_Argument)'Last);
678                   Parser.Is_Switch (Parser.Current_Argument) := True;
679                   Dummy := Goto_Next_Argument_In_Section (Parser);
680
681                else
682                   Parser.Current_Index := End_Index + 1;
683                   raise Invalid_Parameter;
684                end if;
685
686             when Parameter_No_Space =>
687
688                if End_Index < Arg'Last then
689                   Set_Parameter
690                     (Parser.The_Parameter,
691                      Arg_Num => Parser.Current_Argument,
692                      First   => End_Index + 1,
693                      Last    => Arg'Last);
694                   Dummy := Goto_Next_Argument_In_Section (Parser);
695
696                else
697                   Parser.Current_Index := End_Index + 1;
698                   raise Invalid_Parameter;
699                end if;
700
701             when Parameter_Optional =>
702
703                if End_Index < Arg'Last then
704                   Set_Parameter
705                     (Parser.The_Parameter,
706                      Arg_Num => Parser.Current_Argument,
707                      First   => End_Index + 1,
708                      Last    => Arg'Last);
709                end if;
710
711                Dummy := Goto_Next_Argument_In_Section (Parser);
712
713             when Parameter_None =>
714
715                if Concatenate or else End_Index = Arg'Last then
716                   Parser.Current_Index := End_Index + 1;
717
718                else
719                   --  If Concatenate is False and the full argument is not
720                   --  recognized as a switch, this is an invalid switch.
721
722                   if Switches (Switches'First) = '*' then
723                      Set_Parameter
724                        (Parser.The_Switch,
725                         Arg_Num => Parser.Current_Argument,
726                         First   => Arg'First,
727                         Last    => Arg'Last);
728                      Parser.Is_Switch (Parser.Current_Argument) := True;
729                      Dummy := Goto_Next_Argument_In_Section (Parser);
730                      return '*';
731                   end if;
732
733                   Set_Parameter
734                     (Parser.The_Switch,
735                      Arg_Num => Parser.Current_Argument,
736                      First   => Parser.Current_Index,
737                      Last    => Arg'Last);
738                   Parser.Current_Index := Arg'Last + 1;
739                   raise Invalid_Switch;
740                end if;
741          end case;
742
743          return Switches (Index_Switches);
744       end;
745    end Getopt;
746
747    -----------------------------------
748    -- Goto_Next_Argument_In_Section --
749    -----------------------------------
750
751    function Goto_Next_Argument_In_Section
752      (Parser : Opt_Parser) return Boolean
753    is
754    begin
755       Parser.Current_Argument := Parser.Current_Argument + 1;
756
757       if Parser.Current_Argument > Parser.Arg_Count
758         or else Parser.Section (Parser.Current_Argument) = 0
759       then
760          loop
761             Parser.Current_Argument := Parser.Current_Argument + 1;
762
763             if Parser.Current_Argument > Parser.Arg_Count then
764                Parser.Current_Index := 1;
765                return False;
766             end if;
767
768             exit when Parser.Section (Parser.Current_Argument) =
769                                                   Parser.Current_Section;
770          end loop;
771       end if;
772
773       Parser.Current_Index :=
774         Argument (Parser, Parser.Current_Argument)'First;
775
776       return True;
777    end Goto_Next_Argument_In_Section;
778
779    ------------------
780    -- Goto_Section --
781    ------------------
782
783    procedure Goto_Section
784      (Name   : String := "";
785       Parser : Opt_Parser := Command_Line_Parser)
786    is
787       Index : Integer;
788
789    begin
790       Parser.In_Expansion := False;
791
792       if Name = "" then
793          Parser.Current_Argument := 1;
794          Parser.Current_Index    := 1;
795          Parser.Current_Section  := 1;
796          return;
797       end if;
798
799       Index := 1;
800       while Index <= Parser.Arg_Count loop
801          if Parser.Section (Index) = 0
802            and then Argument (Parser, Index) = Parser.Switch_Character & Name
803          then
804             Parser.Current_Argument := Index + 1;
805             Parser.Current_Index    := 1;
806
807             if Parser.Current_Argument <= Parser.Arg_Count then
808                Parser.Current_Section :=
809                  Parser.Section (Parser.Current_Argument);
810             end if;
811             return;
812          end if;
813
814          Index := Index + 1;
815       end loop;
816
817       Parser.Current_Argument := Positive'Last;
818       Parser.Current_Index := 2;   --  so that Get_Argument returns nothing
819    end Goto_Section;
820
821    ----------------------------
822    -- Initialize_Option_Scan --
823    ----------------------------
824
825    procedure Initialize_Option_Scan
826      (Switch_Char              : Character := '-';
827       Stop_At_First_Non_Switch : Boolean   := False;
828       Section_Delimiters       : String    := "")
829    is
830    begin
831       Internal_Initialize_Option_Scan
832         (Parser                   => Command_Line_Parser,
833          Switch_Char              => Switch_Char,
834          Stop_At_First_Non_Switch => Stop_At_First_Non_Switch,
835          Section_Delimiters       => Section_Delimiters);
836    end Initialize_Option_Scan;
837
838    ----------------------------
839    -- Initialize_Option_Scan --
840    ----------------------------
841
842    procedure Initialize_Option_Scan
843      (Parser                   : out Opt_Parser;
844       Command_Line             : GNAT.OS_Lib.Argument_List_Access;
845       Switch_Char              : Character := '-';
846       Stop_At_First_Non_Switch : Boolean := False;
847       Section_Delimiters       : String := "")
848    is
849    begin
850       Free (Parser);
851
852       if Command_Line = null then
853          Parser := new Opt_Parser_Data (CL.Argument_Count);
854          Initialize_Option_Scan
855            (Switch_Char              => Switch_Char,
856             Stop_At_First_Non_Switch => Stop_At_First_Non_Switch,
857             Section_Delimiters       => Section_Delimiters);
858       else
859          Parser := new Opt_Parser_Data (Command_Line'Length);
860          Parser.Arguments := Command_Line;
861          Internal_Initialize_Option_Scan
862            (Parser                   => Parser,
863             Switch_Char              => Switch_Char,
864             Stop_At_First_Non_Switch => Stop_At_First_Non_Switch,
865             Section_Delimiters       => Section_Delimiters);
866       end if;
867    end Initialize_Option_Scan;
868
869    -------------------------------------
870    -- Internal_Initialize_Option_Scan --
871    -------------------------------------
872
873    procedure Internal_Initialize_Option_Scan
874      (Parser                   : Opt_Parser;
875       Switch_Char              : Character;
876       Stop_At_First_Non_Switch : Boolean;
877       Section_Delimiters       : String)
878    is
879       Section_Num     : Section_Number;
880       Section_Index   : Integer;
881       Last            : Integer;
882       Delimiter_Found : Boolean;
883
884       Discard : Boolean;
885       pragma Warnings (Off, Discard);
886
887    begin
888       Parser.Current_Argument := 0;
889       Parser.Current_Index    := 0;
890       Parser.In_Expansion     := False;
891       Parser.Switch_Character := Switch_Char;
892       Parser.Stop_At_First    := Stop_At_First_Non_Switch;
893       Parser.Section          := (others => 1);
894
895       --  If we are using sections, we have to preprocess the command line
896       --  to delimit them. A section can be repeated, so we just give each
897       --  item on the command line a section number
898
899       Section_Num   := 1;
900       Section_Index := Section_Delimiters'First;
901       while Section_Index <= Section_Delimiters'Last loop
902          Last := Section_Index;
903          while Last <= Section_Delimiters'Last
904            and then Section_Delimiters (Last) /= ' '
905          loop
906             Last := Last + 1;
907          end loop;
908
909          Delimiter_Found := False;
910          Section_Num := Section_Num + 1;
911
912          for Index in 1 .. Parser.Arg_Count loop
913             if Argument (Parser, Index)(1) = Parser.Switch_Character
914               and then
915                 Argument (Parser, Index) = Parser.Switch_Character &
916                                         Section_Delimiters
917                                           (Section_Index .. Last - 1)
918             then
919                Parser.Section (Index) := 0;
920                Delimiter_Found := True;
921
922             elsif Parser.Section (Index) = 0 then
923                Delimiter_Found := False;
924
925             elsif Delimiter_Found then
926                Parser.Section (Index) := Section_Num;
927             end if;
928          end loop;
929
930          Section_Index := Last + 1;
931          while Section_Index <= Section_Delimiters'Last
932            and then Section_Delimiters (Section_Index) = ' '
933          loop
934             Section_Index := Section_Index + 1;
935          end loop;
936       end loop;
937
938       Discard := Goto_Next_Argument_In_Section (Parser);
939    end Internal_Initialize_Option_Scan;
940
941    ---------------
942    -- Parameter --
943    ---------------
944
945    function Parameter
946      (Parser : Opt_Parser := Command_Line_Parser) return String
947    is
948    begin
949       if Parser.The_Parameter.First > Parser.The_Parameter.Last then
950          return String'(1 .. 0 => ' ');
951       else
952          return Argument (Parser, Parser.The_Parameter.Arg_Num)
953            (Parser.The_Parameter.First .. Parser.The_Parameter.Last);
954       end if;
955    end Parameter;
956
957    ---------------
958    -- Separator --
959    ---------------
960
961    function Separator
962      (Parser : Opt_Parser := Command_Line_Parser) return Character
963    is
964    begin
965       return Parser.The_Separator;
966    end Separator;
967
968    -------------------
969    -- Set_Parameter --
970    -------------------
971
972    procedure Set_Parameter
973      (Variable : out Parameter_Type;
974       Arg_Num  : Positive;
975       First    : Positive;
976       Last     : Positive;
977       Extra    : Character := ASCII.NUL)
978    is
979    begin
980       Variable.Arg_Num := Arg_Num;
981       Variable.First   := First;
982       Variable.Last    := Last;
983       Variable.Extra   := Extra;
984    end Set_Parameter;
985
986    ---------------------
987    -- Start_Expansion --
988    ---------------------
989
990    procedure Start_Expansion
991      (Iterator     : out Expansion_Iterator;
992       Pattern      : String;
993       Directory    : String := "";
994       Basic_Regexp : Boolean := True)
995    is
996       Directory_Separator : Character;
997       pragma Import (C, Directory_Separator, "__gnat_dir_separator");
998
999       First : Positive := Pattern'First;
1000       Pat   : String := Pattern;
1001
1002    begin
1003       Canonical_Case_File_Name (Pat);
1004       Iterator.Current_Depth := 1;
1005
1006       --  If Directory is unspecified, use the current directory ("./" or ".\")
1007
1008       if Directory = "" then
1009          Iterator.Dir_Name (1 .. 2) := "." & Directory_Separator;
1010          Iterator.Start := 3;
1011
1012       else
1013          Iterator.Dir_Name (1 .. Directory'Length) := Directory;
1014          Iterator.Start := Directory'Length + 1;
1015          Canonical_Case_File_Name (Iterator.Dir_Name (1 .. Directory'Length));
1016
1017          --  Make sure that the last character is a directory separator
1018
1019          if Directory (Directory'Last) /= Directory_Separator then
1020             Iterator.Dir_Name (Iterator.Start) := Directory_Separator;
1021             Iterator.Start := Iterator.Start + 1;
1022          end if;
1023       end if;
1024
1025       Iterator.Levels (1).Name_Last := Iterator.Start - 1;
1026
1027       --  Open the initial Directory, at depth 1
1028
1029       GNAT.Directory_Operations.Open
1030         (Iterator.Levels (1).Dir, Iterator.Dir_Name (1 .. Iterator.Start - 1));
1031
1032       --  If in the current directory and the pattern starts with "./" or ".\",
1033       --  drop the "./" or ".\" from the pattern.
1034
1035       if Directory = "" and then Pat'Length > 2
1036         and then Pat (Pat'First) = '.'
1037         and then Pat (Pat'First + 1) = Directory_Separator
1038       then
1039          First := Pat'First + 2;
1040       end if;
1041
1042       Iterator.Regexp :=
1043         GNAT.Regexp.Compile (Pat (First .. Pat'Last), Basic_Regexp, True);
1044
1045       Iterator.Maximum_Depth := 1;
1046
1047       --  Maximum_Depth is equal to 1 plus the number of directory separators
1048       --  in the pattern.
1049
1050       for Index in First .. Pat'Last loop
1051          if Pat (Index) = Directory_Separator then
1052             Iterator.Maximum_Depth := Iterator.Maximum_Depth + 1;
1053             exit when Iterator.Maximum_Depth = Max_Depth;
1054          end if;
1055       end loop;
1056    end Start_Expansion;
1057
1058    ----------
1059    -- Free --
1060    ----------
1061
1062    procedure Free (Parser : in out Opt_Parser) is
1063       procedure Unchecked_Free is new Ada.Unchecked_Deallocation
1064         (Opt_Parser_Data, Opt_Parser);
1065    begin
1066       if Parser /= null
1067         and then Parser /= Command_Line_Parser
1068       then
1069          Free (Parser.Arguments);
1070          Unchecked_Free (Parser);
1071       end if;
1072    end Free;
1073
1074    ------------------
1075    -- Define_Alias --
1076    ------------------
1077
1078    procedure Define_Alias
1079      (Config   : in out Command_Line_Configuration;
1080       Switch   : String;
1081       Expanded : String)
1082    is
1083    begin
1084       if Config = null then
1085          Config := new Command_Line_Configuration_Record;
1086       end if;
1087
1088       Add (Config.Aliases,    new String'(Switch));
1089       Add (Config.Expansions, new String'(Expanded));
1090    end Define_Alias;
1091
1092    -------------------
1093    -- Define_Prefix --
1094    -------------------
1095
1096    procedure Define_Prefix
1097      (Config : in out Command_Line_Configuration;
1098       Prefix : String)
1099    is
1100    begin
1101       if Config = null then
1102          Config := new Command_Line_Configuration_Record;
1103       end if;
1104
1105       Add (Config.Prefixes, new String'(Prefix));
1106    end Define_Prefix;
1107
1108    -------------------
1109    -- Define_Switch --
1110    -------------------
1111
1112    procedure Define_Switch
1113      (Config : in out Command_Line_Configuration;
1114       Switch : String)
1115    is
1116    begin
1117       if Config = null then
1118          Config := new Command_Line_Configuration_Record;
1119       end if;
1120
1121       Add (Config.Switches, new String'(Switch));
1122    end Define_Switch;
1123
1124    --------------------
1125    -- Define_Section --
1126    --------------------
1127
1128    procedure Define_Section
1129      (Config : in out Command_Line_Configuration;
1130       Section : String)
1131    is
1132    begin
1133       if Config = null then
1134          Config := new Command_Line_Configuration_Record;
1135       end if;
1136
1137       Add (Config.Sections, new String'(Section));
1138    end Define_Section;
1139
1140    ------------------
1141    -- Get_Switches --
1142    ------------------
1143
1144    function Get_Switches
1145      (Config      : Command_Line_Configuration;
1146       Switch_Char : Character)
1147       return String
1148    is
1149       Ret : Ada.Strings.Unbounded.Unbounded_String;
1150       use type Ada.Strings.Unbounded.Unbounded_String;
1151
1152    begin
1153       if Config = null or else Config.Switches = null then
1154          return "";
1155       end if;
1156
1157       for J in Config.Switches'Range loop
1158          if Config.Switches (J) (Config.Switches (J)'First) = Switch_Char then
1159             Ret :=
1160               Ret & " " &
1161                 Config.Switches (J)
1162                   (Config.Switches (J)'First + 1 .. Config.Switches (J)'Last);
1163          else
1164             Ret := Ret & " " & Config.Switches (J).all;
1165          end if;
1166       end loop;
1167
1168       return Ada.Strings.Unbounded.To_String (Ret);
1169    end Get_Switches;
1170
1171    -----------------------
1172    -- Set_Configuration --
1173    -----------------------
1174
1175    procedure Set_Configuration
1176      (Cmd    : in out Command_Line;
1177       Config : Command_Line_Configuration)
1178    is
1179    begin
1180       Cmd.Config := Config;
1181    end Set_Configuration;
1182
1183    -----------------------
1184    -- Get_Configuration --
1185    -----------------------
1186
1187    function Get_Configuration
1188      (Cmd : Command_Line) return Command_Line_Configuration is
1189    begin
1190       return Cmd.Config;
1191    end Get_Configuration;
1192
1193    ----------------------
1194    -- Set_Command_Line --
1195    ----------------------
1196
1197    procedure Set_Command_Line
1198      (Cmd                : in out Command_Line;
1199       Switches           : String;
1200       Getopt_Description : String := "";
1201       Switch_Char        : Character := '-')
1202    is
1203       Tmp     : Argument_List_Access;
1204       Parser  : Opt_Parser;
1205       S       : Character;
1206       Section : String_Access := null;
1207
1208       function Real_Full_Switch
1209         (S      : Character;
1210          Parser : Opt_Parser) return String;
1211       --  Ensure that the returned switch value contains the
1212       --  Switch_Char prefix if needed.
1213
1214       ----------------------
1215       -- Real_Full_Switch --
1216       ----------------------
1217
1218       function Real_Full_Switch
1219         (S      : Character;
1220          Parser : Opt_Parser) return String
1221       is
1222       begin
1223          if S = '*' then
1224             return Full_Switch (Parser);
1225          else
1226             return Switch_Char & Full_Switch (Parser);
1227          end if;
1228       end Real_Full_Switch;
1229
1230    --  Start of processing for Set_Command_Line
1231
1232    begin
1233       Free (Cmd.Expanded);
1234       Free (Cmd.Params);
1235
1236       if Switches /= "" then
1237          Tmp := Argument_String_To_List (Switches);
1238          Initialize_Option_Scan (Parser, Tmp, Switch_Char);
1239
1240          loop
1241             begin
1242                S := Getopt (Switches    => "* " & Getopt_Description,
1243                             Concatenate => False,
1244                             Parser      => Parser);
1245                exit when S = ASCII.NUL;
1246
1247                declare
1248                   Sw         : constant String :=
1249                                  Real_Full_Switch (S, Parser);
1250                   Is_Section : Boolean := False;
1251
1252                begin
1253                   if Cmd.Config /= null
1254                     and then Cmd.Config.Sections /= null
1255                   then
1256                      Section_Search :
1257                      for S in Cmd.Config.Sections'Range loop
1258                         if Sw = Cmd.Config.Sections (S).all then
1259                            Section := Cmd.Config.Sections (S);
1260                            Is_Section := True;
1261
1262                            exit Section_Search;
1263                         end if;
1264                      end loop Section_Search;
1265                   end if;
1266
1267                   if not Is_Section then
1268                      if Section = null then
1269
1270                         --  Work around some weird cases: some switches may
1271                         --  expect parameters, but have the same value as
1272                         --  longer switches: -gnaty3 (-gnaty, parameter=3) and
1273                         --  -gnatya (-gnatya, no parameter).
1274
1275                         --  So we are calling add_switch here with parameter
1276                         --  attached. This will be anyway correctly handled by
1277                         --  Add_Switch if -gnaty3 is actually provided.
1278
1279                         if Separator (Parser) = ASCII.NUL then
1280                            Add_Switch
1281                              (Cmd, Sw & Parameter (Parser), "", ASCII.NUL);
1282                         else
1283                            Add_Switch
1284                              (Cmd, Sw, Parameter (Parser), Separator (Parser));
1285                         end if;
1286                      else
1287                         if Separator (Parser) = ASCII.NUL then
1288                            Add_Switch
1289                              (Cmd, Sw & Parameter (Parser), "",
1290                               Separator (Parser),
1291                               Section.all);
1292                         else
1293                            Add_Switch
1294                              (Cmd, Sw,
1295                               Parameter (Parser),
1296                               Separator (Parser),
1297                               Section.all);
1298                         end if;
1299                      end if;
1300                   end if;
1301                end;
1302
1303             exception
1304                when Invalid_Parameter =>
1305
1306                   --  Add it with no parameter, if that's the way the user
1307                   --  wants it.
1308
1309                   --  Specify the separator in all cases, as the switch might
1310                   --  need to be unaliased, and the alias might contain
1311                   --  switches with parameters.
1312
1313                   if Section = null then
1314                      Add_Switch
1315                        (Cmd, Switch_Char & Full_Switch (Parser),
1316                         Separator => Separator (Parser));
1317                   else
1318                      Add_Switch
1319                        (Cmd, Switch_Char & Full_Switch (Parser),
1320                         Separator => Separator (Parser),
1321                         Section   => Section.all);
1322                   end if;
1323             end;
1324          end loop;
1325
1326          Free (Parser);
1327       end if;
1328    end Set_Command_Line;
1329
1330    ----------------
1331    -- Looking_At --
1332    ----------------
1333
1334    function Looking_At
1335      (Type_Str  : String;
1336       Index     : Natural;
1337       Substring : String) return Boolean is
1338    begin
1339       return Index + Substring'Length - 1 <= Type_Str'Last
1340         and then Type_Str (Index .. Index + Substring'Length - 1) = Substring;
1341    end Looking_At;
1342
1343    ------------------------
1344    -- Can_Have_Parameter --
1345    ------------------------
1346
1347    function Can_Have_Parameter (S : String) return Boolean is
1348    begin
1349       if S'Length <= 1 then
1350          return False;
1351       end if;
1352
1353       case S (S'Last) is
1354          when '!' | ':' | '?' | '=' =>
1355             return True;
1356          when others =>
1357             return False;
1358       end case;
1359    end Can_Have_Parameter;
1360
1361    -----------------------
1362    -- Require_Parameter --
1363    -----------------------
1364
1365    function Require_Parameter (S : String) return Boolean is
1366    begin
1367       if S'Length <= 1 then
1368          return False;
1369       end if;
1370
1371       case S (S'Last) is
1372          when '!' | ':' | '=' =>
1373             return True;
1374          when others =>
1375             return False;
1376       end case;
1377    end Require_Parameter;
1378
1379    -------------------
1380    -- Actual_Switch --
1381    -------------------
1382
1383    function Actual_Switch (S : String) return String is
1384    begin
1385       if S'Length <= 1 then
1386          return S;
1387       end if;
1388
1389       case S (S'Last) is
1390          when '!' | ':' | '?' | '=' =>
1391             return S (S'First .. S'Last - 1);
1392          when others =>
1393             return S;
1394       end case;
1395    end Actual_Switch;
1396
1397    ----------------------------
1398    -- For_Each_Simple_Switch --
1399    ----------------------------
1400
1401    procedure For_Each_Simple_Switch
1402      (Cmd       : Command_Line;
1403       Switch    : String;
1404       Parameter : String := "";
1405       Unalias   : Boolean := True)
1406    is
1407       function Group_Analysis
1408         (Prefix : String;
1409          Group  : String) return Boolean;
1410       --  Perform the analysis of a group of switches
1411
1412       --------------------
1413       -- Group_Analysis --
1414       --------------------
1415
1416       function Group_Analysis
1417         (Prefix : String;
1418          Group  : String) return Boolean
1419       is
1420          Idx   : Natural;
1421          Found : Boolean;
1422
1423       begin
1424          Idx := Group'First;
1425          while Idx <= Group'Last loop
1426             Found := False;
1427
1428             for S in Cmd.Config.Switches'Range loop
1429                declare
1430                   Sw              : constant String :=
1431                                       Actual_Switch
1432                                         (Cmd.Config.Switches (S).all);
1433                   Full            : constant String :=
1434                                       Prefix & Group (Idx .. Group'Last);
1435                   Last            : Natural;
1436                   Param           : Natural;
1437
1438                begin
1439                   if Sw'Length >= Prefix'Length
1440
1441                      --  Verify that sw starts with Prefix
1442
1443                      and then Looking_At (Sw, Sw'First, Prefix)
1444
1445                      --  Verify that the group starts with sw
1446
1447                      and then Looking_At (Full, Full'First, Sw)
1448                   then
1449                      Last := Idx + Sw'Length - Prefix'Length - 1;
1450                      Param := Last + 1;
1451
1452                      if Can_Have_Parameter (Cmd.Config.Switches (S).all) then
1453
1454                         --  Include potential parameter to the recursive call.
1455                         --  Only numbers are allowed.
1456
1457                         while Last < Group'Last
1458                           and then Group (Last + 1) in '0' .. '9'
1459                         loop
1460                            Last := Last + 1;
1461                         end loop;
1462                      end if;
1463
1464                      if not Require_Parameter (Cmd.Config.Switches (S).all)
1465                        or else Last >= Param
1466                      then
1467                         if Idx = Group'First
1468                           and then Last = Group'Last
1469                           and then Last < Param
1470                         then
1471                            --  The group only concerns a single switch. Do not
1472                            --  perform recursive call.
1473
1474                            --  Note that we still perform a recursive call if
1475                            --  a parameter is detected in the switch, as this
1476                            --  is a way to correctly identify such a parameter
1477                            --  in aliases.
1478
1479                            return False;
1480                         end if;
1481
1482                         Found := True;
1483
1484                         --  Recursive call, using the detected parameter if any
1485
1486                         if Last >= Param then
1487                            For_Each_Simple_Switch
1488                              (Cmd,
1489                               Prefix & Group (Idx .. Param - 1),
1490                               Group (Param .. Last));
1491                         else
1492                            For_Each_Simple_Switch
1493                              (Cmd, Prefix & Group (Idx .. Last), "");
1494                         end if;
1495
1496                         Idx := Last + 1;
1497                         exit;
1498                      end if;
1499                   end if;
1500                end;
1501             end loop;
1502
1503             if not Found then
1504                For_Each_Simple_Switch (Cmd, Prefix & Group (Idx), "");
1505                Idx := Idx + 1;
1506             end if;
1507          end loop;
1508
1509          return True;
1510       end Group_Analysis;
1511
1512    begin
1513       --  First determine if the switch corresponds to one belonging to the
1514       --  configuration. If so, run callback and exit.
1515
1516       if Cmd.Config /= null and then Cmd.Config.Switches /= null then
1517          for S in Cmd.Config.Switches'Range loop
1518             declare
1519                Config_Switch : String renames Cmd.Config.Switches (S).all;
1520             begin
1521                if Actual_Switch (Config_Switch) = Switch
1522                     and then
1523                   ((Can_Have_Parameter (Config_Switch)
1524                       and then Parameter /= "")
1525                    or else
1526                    (not Require_Parameter (Config_Switch)
1527                        and then Parameter = ""))
1528                then
1529                   Callback (Switch, Parameter);
1530                   return;
1531                end if;
1532             end;
1533          end loop;
1534       end if;
1535
1536       --  If adding a switch that can in fact be expanded through aliases,
1537       --  add separately each of its expansions.
1538
1539       --  This takes care of expansions like "-T" -> "-gnatwrs", where the
1540       --  alias and its expansion do not have the same prefix. Given the order
1541       --  in which we do things here, the expansion of the alias will itself
1542       --  be checked for a common prefix and split into simple switches.
1543
1544       if Unalias
1545         and then Cmd.Config /= null
1546         and then Cmd.Config.Aliases /= null
1547       then
1548          for A in Cmd.Config.Aliases'Range loop
1549             if Cmd.Config.Aliases (A).all = Switch and then Parameter = "" then
1550                For_Each_Simple_Switch
1551                  (Cmd, Cmd.Config.Expansions (A).all, "");
1552                return;
1553             end if;
1554          end loop;
1555       end if;
1556
1557       --  If adding a switch grouping several switches, add each of the simple
1558       --  switches instead.
1559
1560       if Cmd.Config /= null and then Cmd.Config.Prefixes /= null then
1561          for P in Cmd.Config.Prefixes'Range loop
1562             if Switch'Length > Cmd.Config.Prefixes (P)'Length + 1
1563               and then Looking_At
1564                 (Switch, Switch'First, Cmd.Config.Prefixes (P).all)
1565             then
1566                --  Alias expansion will be done recursively
1567
1568                if Cmd.Config.Switches = null then
1569                   for S in Switch'First + Cmd.Config.Prefixes (P)'Length
1570                             .. Switch'Last
1571                   loop
1572                      For_Each_Simple_Switch
1573                        (Cmd, Cmd.Config.Prefixes (P).all & Switch (S), "");
1574                   end loop;
1575
1576                   return;
1577
1578                elsif Group_Analysis
1579                  (Cmd.Config.Prefixes (P).all,
1580                   Switch
1581                     (Switch'First + Cmd.Config.Prefixes (P)'Length
1582                       .. Switch'Last))
1583                then
1584                   --  Recursive calls already done on each switch of the group:
1585                   --  Return without executing Callback.
1586
1587                   return;
1588                end if;
1589             end if;
1590          end loop;
1591       end if;
1592
1593       --  Test if added switch is a known switch with parameter attached
1594
1595       if Parameter = ""
1596         and then Cmd.Config /= null
1597         and then Cmd.Config.Switches /= null
1598       then
1599          for S in Cmd.Config.Switches'Range loop
1600             declare
1601                Sw    : constant String :=
1602                          Actual_Switch (Cmd.Config.Switches (S).all);
1603                Last  : Natural;
1604                Param : Natural;
1605
1606             begin
1607                --  Verify that switch starts with Sw
1608                --  What if the "verification" fails???
1609
1610                if Switch'Length >= Sw'Length
1611                  and then Looking_At (Switch, Switch'First, Sw)
1612                then
1613                   Param := Switch'First + Sw'Length - 1;
1614                   Last := Param;
1615
1616                   if Can_Have_Parameter (Cmd.Config.Switches (S).all) then
1617                      while Last < Switch'Last
1618                        and then Switch (Last + 1) in '0' .. '9'
1619                      loop
1620                         Last := Last + 1;
1621                      end loop;
1622                   end if;
1623
1624                   --  If full Switch is a known switch with attached parameter
1625                   --  then we use this parameter in the callback.
1626
1627                   if Last = Switch'Last then
1628                      Callback
1629                        (Switch (Switch'First .. Param),
1630                         Switch (Param + 1 .. Last));
1631                      return;
1632
1633                   end if;
1634                end if;
1635             end;
1636          end loop;
1637       end if;
1638
1639       Callback (Switch, Parameter);
1640    end For_Each_Simple_Switch;
1641
1642    ----------------
1643    -- Add_Switch --
1644    ----------------
1645
1646    procedure Add_Switch
1647      (Cmd        : in out Command_Line;
1648       Switch     : String;
1649       Parameter  : String    := "";
1650       Separator  : Character := ' ';
1651       Section    : String    := "";
1652       Add_Before : Boolean   := False)
1653    is
1654       Success : Boolean;
1655       pragma Unreferenced (Success);
1656    begin
1657       Add_Switch
1658         (Cmd, Switch, Parameter, Separator, Section, Add_Before, Success);
1659    end Add_Switch;
1660
1661    ----------------
1662    -- Add_Switch --
1663    ----------------
1664
1665    procedure Add_Switch
1666      (Cmd        : in out Command_Line;
1667       Switch     : String;
1668       Parameter  : String := "";
1669       Separator  : Character := ' ';
1670       Section    : String := "";
1671       Add_Before : Boolean := False;
1672       Success    : out Boolean)
1673    is
1674       procedure Add_Simple_Switch (Simple : String; Param : String);
1675       --  Add a new switch that has had all its aliases expanded, and switches
1676       --  ungrouped. We know there are no more aliases in Switches.
1677
1678       -----------------------
1679       -- Add_Simple_Switch --
1680       -----------------------
1681
1682       procedure Add_Simple_Switch (Simple : String; Param : String) is
1683       begin
1684          if Cmd.Expanded = null then
1685             Cmd.Expanded := new Argument_List'(1 .. 1 => new String'(Simple));
1686
1687             if Param /= "" then
1688                Cmd.Params := new Argument_List'
1689                  (1 .. 1 => new String'(Separator & Param));
1690
1691             else
1692                Cmd.Params := new Argument_List'(1 .. 1 => null);
1693             end if;
1694
1695             if Section = "" then
1696                Cmd.Sections := new Argument_List'(1 .. 1 => null);
1697
1698             else
1699                Cmd.Sections := new Argument_List'
1700                  (1 .. 1 => new String'(Section));
1701             end if;
1702
1703          else
1704             --  Do we already have this switch?
1705
1706             for C in Cmd.Expanded'Range loop
1707                if Cmd.Expanded (C).all = Simple
1708                  and then
1709                    ((Cmd.Params (C) = null and then Param = "")
1710                      or else
1711                        (Cmd.Params (C) /= null
1712                          and then Cmd.Params (C).all = Separator & Param))
1713                  and then
1714                    ((Cmd.Sections (C) = null and then Section = "")
1715                      or else
1716                        (Cmd.Sections (C) /= null
1717                          and then Cmd.Sections (C).all = Section))
1718                then
1719                   return;
1720                end if;
1721             end loop;
1722
1723             --  Inserting at least one switch
1724
1725             Success := True;
1726             Add (Cmd.Expanded, new String'(Simple), Add_Before);
1727
1728             if Param /= "" then
1729                Add
1730                  (Cmd.Params,
1731                   new String'(Separator & Param),
1732                   Add_Before);
1733
1734             else
1735                Add
1736                  (Cmd.Params,
1737                   null,
1738                   Add_Before);
1739             end if;
1740
1741             if Section = "" then
1742                Add
1743                  (Cmd.Sections,
1744                   null,
1745                   Add_Before);
1746             else
1747                Add
1748                  (Cmd.Sections,
1749                   new String'(Section),
1750                   Add_Before);
1751             end if;
1752          end if;
1753       end Add_Simple_Switch;
1754
1755       procedure Add_Simple_Switches is
1756          new For_Each_Simple_Switch (Add_Simple_Switch);
1757
1758    --  Start of processing for Add_Switch
1759
1760    begin
1761       Success := False;
1762       Add_Simple_Switches (Cmd, Switch, Parameter);
1763       Free (Cmd.Coalesce);
1764    end Add_Switch;
1765
1766    ------------
1767    -- Remove --
1768    ------------
1769
1770    procedure Remove (Line : in out Argument_List_Access; Index : Integer) is
1771       Tmp : Argument_List_Access := Line;
1772
1773    begin
1774       Line := new Argument_List (Tmp'First .. Tmp'Last - 1);
1775
1776       if Index /= Tmp'First then
1777          Line (Tmp'First .. Index - 1) := Tmp (Tmp'First .. Index - 1);
1778       end if;
1779
1780       Free (Tmp (Index));
1781
1782       if Index /= Tmp'Last then
1783          Line (Index .. Tmp'Last - 1) := Tmp (Index + 1 .. Tmp'Last);
1784       end if;
1785
1786       Unchecked_Free (Tmp);
1787    end Remove;
1788
1789    ---------
1790    -- Add --
1791    ---------
1792
1793    procedure Add
1794      (Line   : in out Argument_List_Access;
1795       Str    : String_Access;
1796       Before : Boolean := False)
1797    is
1798       Tmp : Argument_List_Access := Line;
1799
1800    begin
1801       if Tmp /= null then
1802          Line := new Argument_List (Tmp'First .. Tmp'Last + 1);
1803
1804          if Before then
1805             Line (Tmp'First)                     := Str;
1806             Line (Tmp'First + 1 .. Tmp'Last + 1) := Tmp.all;
1807          else
1808             Line (Tmp'Range)    := Tmp.all;
1809             Line (Tmp'Last + 1) := Str;
1810          end if;
1811
1812          Unchecked_Free (Tmp);
1813
1814       else
1815          Line := new Argument_List'(1 .. 1 => Str);
1816       end if;
1817    end Add;
1818
1819    -------------------
1820    -- Remove_Switch --
1821    -------------------
1822
1823    procedure Remove_Switch
1824      (Cmd           : in out Command_Line;
1825       Switch        : String;
1826       Remove_All    : Boolean := False;
1827       Has_Parameter : Boolean := False;
1828       Section       : String := "")
1829    is
1830       Success : Boolean;
1831       pragma Unreferenced (Success);
1832    begin
1833       Remove_Switch (Cmd, Switch, Remove_All, Has_Parameter, Section, Success);
1834    end Remove_Switch;
1835
1836    -------------------
1837    -- Remove_Switch --
1838    -------------------
1839
1840    procedure Remove_Switch
1841      (Cmd           : in out Command_Line;
1842       Switch        : String;
1843       Remove_All    : Boolean := False;
1844       Has_Parameter : Boolean := False;
1845       Section       : String  := "";
1846       Success       : out Boolean)
1847    is
1848       procedure Remove_Simple_Switch (Simple : String; Param : String);
1849       --  Removes a simple switch, with no aliasing or grouping
1850
1851       --------------------------
1852       -- Remove_Simple_Switch --
1853       --------------------------
1854
1855       procedure Remove_Simple_Switch (Simple : String; Param : String) is
1856          C : Integer;
1857          pragma Unreferenced (Param);
1858
1859       begin
1860          if Cmd.Expanded /= null then
1861             C := Cmd.Expanded'First;
1862             while C <= Cmd.Expanded'Last loop
1863                if Cmd.Expanded (C).all = Simple
1864                  and then
1865                    (Remove_All
1866                      or else (Cmd.Sections (C) = null
1867                                and then Section = "")
1868                      or else (Cmd.Sections (C) /= null
1869                                and then Section = Cmd.Sections (C).all))
1870                  and then (not Has_Parameter or else Cmd.Params (C) /= null)
1871                then
1872                   Remove (Cmd.Expanded, C);
1873                   Remove (Cmd.Params, C);
1874                   Remove (Cmd.Sections, C);
1875                   Success := True;
1876
1877                   if not Remove_All then
1878                      return;
1879                   end if;
1880
1881                else
1882                   C := C + 1;
1883                end if;
1884             end loop;
1885          end if;
1886       end Remove_Simple_Switch;
1887
1888       procedure Remove_Simple_Switches is
1889         new For_Each_Simple_Switch (Remove_Simple_Switch);
1890
1891    --  Start of processing for Remove_Switch
1892
1893    begin
1894       Success := False;
1895       Remove_Simple_Switches (Cmd, Switch, "", Unalias => not Has_Parameter);
1896       Free (Cmd.Coalesce);
1897    end Remove_Switch;
1898
1899    -------------------
1900    -- Remove_Switch --
1901    -------------------
1902
1903    procedure Remove_Switch
1904      (Cmd       : in out Command_Line;
1905       Switch    : String;
1906       Parameter : String;
1907       Section   : String  := "")
1908    is
1909       procedure Remove_Simple_Switch (Simple : String; Param : String);
1910       --  Removes a simple switch, with no aliasing or grouping
1911
1912       --------------------------
1913       -- Remove_Simple_Switch --
1914       --------------------------
1915
1916       procedure Remove_Simple_Switch (Simple : String; Param : String) is
1917          C : Integer;
1918
1919       begin
1920          if Cmd.Expanded /= null then
1921             C := Cmd.Expanded'First;
1922             while C <= Cmd.Expanded'Last loop
1923                if Cmd.Expanded (C).all = Simple
1924                  and then
1925                    ((Cmd.Sections (C) = null
1926                       and then Section = "")
1927                     or else
1928                       (Cmd.Sections (C) /= null
1929                         and then Section = Cmd.Sections (C).all))
1930                  and then
1931                    ((Cmd.Params (C) = null and then Param = "")
1932                       or else
1933                         (Cmd.Params (C) /= null
1934                            and then
1935
1936                            --  Ignore the separator stored in Parameter
1937
1938                              Cmd.Params (C) (Cmd.Params (C)'First + 1
1939                                              .. Cmd.Params (C)'Last) =
1940                            Param))
1941                then
1942                   Remove (Cmd.Expanded, C);
1943                   Remove (Cmd.Params, C);
1944                   Remove (Cmd.Sections, C);
1945
1946                   --  The switch is necessarily unique by construction of
1947                   --  Add_Switch.
1948
1949                   return;
1950
1951                else
1952                   C := C + 1;
1953                end if;
1954             end loop;
1955          end if;
1956       end Remove_Simple_Switch;
1957
1958       procedure Remove_Simple_Switches is
1959          new For_Each_Simple_Switch (Remove_Simple_Switch);
1960
1961    --  Start of processing for Remove_Switch
1962
1963    begin
1964       Remove_Simple_Switches (Cmd, Switch, Parameter);
1965       Free (Cmd.Coalesce);
1966    end Remove_Switch;
1967
1968    --------------------
1969    -- Group_Switches --
1970    --------------------
1971
1972    procedure Group_Switches
1973      (Cmd      : Command_Line;
1974       Result   : Argument_List_Access;
1975       Sections : Argument_List_Access;
1976       Params   : Argument_List_Access)
1977    is
1978       function Compatible_Parameter (Param : String_Access) return Boolean;
1979       --  True when the parameter can be part of a group
1980
1981       --------------------------
1982       -- Compatible_Parameter --
1983       --------------------------
1984
1985       function Compatible_Parameter (Param : String_Access) return Boolean is
1986       begin
1987          --  No parameter OK
1988
1989          if Param = null then
1990             return True;
1991
1992          --  We need parameters without separators
1993
1994          elsif Param (Param'First) /= ASCII.NUL then
1995             return False;
1996
1997          --  Parameters must be all digits
1998
1999          else
2000             for J in Param'First + 1 .. Param'Last loop
2001                if Param (J) not in '0' .. '9' then
2002                   return False;
2003                end if;
2004             end loop;
2005
2006             return True;
2007          end if;
2008       end Compatible_Parameter;
2009
2010       --  Local declarations
2011
2012       Group : Ada.Strings.Unbounded.Unbounded_String;
2013       First : Natural;
2014       use type Ada.Strings.Unbounded.Unbounded_String;
2015
2016    --  Start of processing for Group_Switches
2017
2018    begin
2019       if Cmd.Config = null
2020         or else Cmd.Config.Prefixes = null
2021       then
2022          return;
2023       end if;
2024
2025       for P in Cmd.Config.Prefixes'Range loop
2026          Group   := Ada.Strings.Unbounded.Null_Unbounded_String;
2027          First   := 0;
2028
2029          for C in Result'Range loop
2030             if Result (C) /= null
2031               and then Compatible_Parameter (Params (C))
2032               and then Looking_At
2033                 (Result (C).all, Result (C)'First, Cmd.Config.Prefixes (P).all)
2034             then
2035                --  If we are still in the same section, group the switches
2036
2037                if First = 0
2038                  or else
2039                    (Sections (C) = null
2040                      and then Sections (First) = null)
2041                  or else
2042                    (Sections (C) /= null
2043                      and then Sections (First) /= null
2044                      and then Sections (C).all = Sections (First).all)
2045                then
2046                   Group :=
2047                     Group &
2048                       Result (C)
2049                         (Result (C)'First + Cmd.Config.Prefixes (P)'Length ..
2050                          Result (C)'Last);
2051
2052                   if Params (C) /= null then
2053                      Group :=
2054                        Group &
2055                          Params (C) (Params (C)'First + 1 .. Params (C)'Last);
2056                      Free (Params (C));
2057                   end if;
2058
2059                   if First = 0 then
2060                      First := C;
2061                   end if;
2062
2063                   Free (Result (C));
2064
2065                else
2066                   --  We changed section: we put the grouped switches to the
2067                   --  first place, on continue with the new section.
2068
2069                   Result (First) :=
2070                     new String'
2071                       (Cmd.Config.Prefixes (P).all &
2072                        Ada.Strings.Unbounded.To_String (Group));
2073                   Group :=
2074                     Ada.Strings.Unbounded.To_Unbounded_String
2075                       (Result (C)
2076                        (Result (C)'First + Cmd.Config.Prefixes (P)'Length ..
2077                             Result (C)'Last));
2078                   First := C;
2079                end if;
2080             end if;
2081          end loop;
2082
2083          if First > 0 then
2084             Result (First) :=
2085               new String'
2086                 (Cmd.Config.Prefixes (P).all &
2087                  Ada.Strings.Unbounded.To_String (Group));
2088          end if;
2089       end loop;
2090    end Group_Switches;
2091
2092    --------------------
2093    -- Alias_Switches --
2094    --------------------
2095
2096    procedure Alias_Switches
2097      (Cmd    : Command_Line;
2098       Result : Argument_List_Access;
2099       Params : Argument_List_Access)
2100    is
2101       Found : Boolean;
2102       First : Natural;
2103
2104       procedure Check_Cb (Switch : String; Param : String);
2105       --  Comment required ???
2106
2107       procedure Remove_Cb (Switch : String; Param : String);
2108       --  Comment required ???
2109
2110       --------------
2111       -- Check_Cb --
2112       --------------
2113
2114       procedure Check_Cb (Switch : String; Param : String) is
2115       begin
2116          if Found then
2117             for E in Result'Range loop
2118                if Result (E) /= null
2119                  and then
2120                    (Params (E) = null
2121                     or else Params (E) (Params (E)'First + 1
2122                                             .. Params (E)'Last) = Param)
2123                  and then Result (E).all = Switch
2124                then
2125                   return;
2126                end if;
2127             end loop;
2128
2129             Found := False;
2130          end if;
2131       end Check_Cb;
2132
2133       ---------------
2134       -- Remove_Cb --
2135       ---------------
2136
2137       procedure Remove_Cb (Switch : String; Param : String) is
2138       begin
2139          for E in Result'Range loop
2140             if Result (E) /= null
2141                  and then
2142                    (Params (E) = null
2143                     or else Params (E) (Params (E)'First + 1
2144                                             .. Params (E)'Last) = Param)
2145               and then Result (E).all = Switch
2146             then
2147                if First > E then
2148                   First := E;
2149                end if;
2150                Free (Result (E));
2151                Free (Params (E));
2152                return;
2153             end if;
2154          end loop;
2155       end Remove_Cb;
2156
2157       procedure Check_All is new For_Each_Simple_Switch (Check_Cb);
2158       procedure Remove_All is new For_Each_Simple_Switch (Remove_Cb);
2159
2160    --  Start of processing for Alias_Switches
2161
2162    begin
2163       if Cmd.Config = null
2164         or else Cmd.Config.Aliases = null
2165       then
2166          return;
2167       end if;
2168
2169       for A in Cmd.Config.Aliases'Range loop
2170
2171          --  Compute the various simple switches that make up the alias. We
2172          --  split the expansion into as many simple switches as possible, and
2173          --  then check whether the expanded command line has all of them.
2174
2175          Found := True;
2176          Check_All (Cmd, Cmd.Config.Expansions (A).all);
2177
2178          if Found then
2179             First := Integer'Last;
2180             Remove_All (Cmd, Cmd.Config.Expansions (A).all);
2181             Result (First) := new String'(Cmd.Config.Aliases (A).all);
2182          end if;
2183       end loop;
2184    end Alias_Switches;
2185
2186    -------------------
2187    -- Sort_Sections --
2188    -------------------
2189
2190    procedure Sort_Sections
2191      (Line     : GNAT.OS_Lib.Argument_List_Access;
2192       Sections : GNAT.OS_Lib.Argument_List_Access;
2193       Params   : GNAT.OS_Lib.Argument_List_Access)
2194    is
2195       Sections_List : Argument_List_Access :=
2196                         new Argument_List'(1 .. 1 => null);
2197       Found         : Boolean;
2198       Old_Line      : constant Argument_List := Line.all;
2199       Old_Sections  : constant Argument_List := Sections.all;
2200       Old_Params    : constant Argument_List := Params.all;
2201       Index         : Natural;
2202
2203    begin
2204       if Line = null then
2205          return;
2206       end if;
2207
2208       --  First construct a list of all sections
2209
2210       for E in Line'Range loop
2211          if Sections (E) /= null then
2212             Found := False;
2213             for S in Sections_List'Range loop
2214                if (Sections_List (S) = null and then Sections (E) = null)
2215                  or else
2216                    (Sections_List (S) /= null
2217                      and then Sections (E) /= null
2218                      and then Sections_List (S).all = Sections (E).all)
2219                then
2220                   Found := True;
2221                   exit;
2222                end if;
2223             end loop;
2224
2225             if not Found then
2226                Add (Sections_List, Sections (E));
2227             end if;
2228          end if;
2229       end loop;
2230
2231       Index := Line'First;
2232
2233       for S in Sections_List'Range loop
2234          for E in Old_Line'Range loop
2235             if (Sections_List (S) = null and then Old_Sections (E) = null)
2236               or else
2237                 (Sections_List (S) /= null
2238                   and then Old_Sections (E) /= null
2239                   and then Sections_List (S).all = Old_Sections (E).all)
2240             then
2241                Line (Index) := Old_Line (E);
2242                Sections (Index) := Old_Sections (E);
2243                Params (Index) := Old_Params (E);
2244                Index := Index + 1;
2245             end if;
2246          end loop;
2247       end loop;
2248    end Sort_Sections;
2249
2250    -----------
2251    -- Start --
2252    -----------
2253
2254    procedure Start
2255      (Cmd      : in out Command_Line;
2256       Iter     : in out Command_Line_Iterator;
2257       Expanded : Boolean)
2258    is
2259    begin
2260       if Cmd.Expanded = null then
2261          Iter.List := null;
2262          return;
2263       end if;
2264
2265       --  Reorder the expanded line so that sections are grouped
2266
2267       Sort_Sections (Cmd.Expanded, Cmd.Sections, Cmd.Params);
2268
2269       --  Coalesce the switches as much as possible
2270
2271       if not Expanded
2272         and then Cmd.Coalesce = null
2273       then
2274          Cmd.Coalesce := new Argument_List (Cmd.Expanded'Range);
2275          for E in Cmd.Expanded'Range loop
2276             Cmd.Coalesce (E) := new String'(Cmd.Expanded (E).all);
2277          end loop;
2278
2279          Cmd.Coalesce_Sections := new Argument_List (Cmd.Sections'Range);
2280          for E in Cmd.Sections'Range loop
2281             if Cmd.Sections (E) = null then
2282                Cmd.Coalesce_Sections (E) := null;
2283             else
2284                Cmd.Coalesce_Sections (E) := new String'(Cmd.Sections (E).all);
2285             end if;
2286          end loop;
2287
2288          Cmd.Coalesce_Params := new Argument_List (Cmd.Params'Range);
2289          for E in Cmd.Params'Range loop
2290             if Cmd.Params (E) = null then
2291                Cmd.Coalesce_Params (E) := null;
2292             else
2293                Cmd.Coalesce_Params (E) := new String'(Cmd.Params (E).all);
2294             end if;
2295          end loop;
2296
2297          --  Not a clone, since we will not modify the parameters anyway
2298
2299          Alias_Switches (Cmd, Cmd.Coalesce, Cmd.Coalesce_Params);
2300          Group_Switches
2301            (Cmd, Cmd.Coalesce, Cmd.Coalesce_Sections, Cmd.Coalesce_Params);
2302       end if;
2303
2304       if Expanded then
2305          Iter.List     := Cmd.Expanded;
2306          Iter.Params   := Cmd.Params;
2307          Iter.Sections := Cmd.Sections;
2308       else
2309          Iter.List     := Cmd.Coalesce;
2310          Iter.Params   := Cmd.Coalesce_Params;
2311          Iter.Sections := Cmd.Coalesce_Sections;
2312       end if;
2313
2314       if Iter.List = null then
2315          Iter.Current := Integer'Last;
2316       else
2317          Iter.Current := Iter.List'First;
2318
2319          while Iter.Current <= Iter.List'Last
2320            and then Iter.List (Iter.Current) = null
2321          loop
2322             Iter.Current := Iter.Current + 1;
2323          end loop;
2324       end if;
2325    end Start;
2326
2327    --------------------
2328    -- Current_Switch --
2329    --------------------
2330
2331    function Current_Switch (Iter : Command_Line_Iterator) return String is
2332    begin
2333       return Iter.List (Iter.Current).all;
2334    end Current_Switch;
2335
2336    --------------------
2337    -- Is_New_Section --
2338    --------------------
2339
2340    function Is_New_Section    (Iter : Command_Line_Iterator) return Boolean is
2341       Section : constant String := Current_Section (Iter);
2342    begin
2343       if Iter.Sections = null then
2344          return False;
2345       elsif Iter.Current = Iter.Sections'First
2346         or else Iter.Sections (Iter.Current - 1) = null
2347       then
2348          return Section /= "";
2349       end if;
2350
2351       return Section /= Iter.Sections (Iter.Current - 1).all;
2352    end Is_New_Section;
2353
2354    ---------------------
2355    -- Current_Section --
2356    ---------------------
2357
2358    function Current_Section (Iter : Command_Line_Iterator) return String is
2359    begin
2360       if Iter.Sections = null
2361         or else Iter.Current > Iter.Sections'Last
2362         or else Iter.Sections (Iter.Current) = null
2363       then
2364          return "";
2365       end if;
2366
2367       return Iter.Sections (Iter.Current).all;
2368    end Current_Section;
2369
2370    -----------------------
2371    -- Current_Separator --
2372    -----------------------
2373
2374    function Current_Separator (Iter : Command_Line_Iterator) return String is
2375    begin
2376       if Iter.Params = null
2377         or else Iter.Current > Iter.Params'Last
2378         or else Iter.Params (Iter.Current) = null
2379       then
2380          return "";
2381
2382       else
2383          declare
2384             Sep : constant Character :=
2385               Iter.Params (Iter.Current) (Iter.Params (Iter.Current)'First);
2386          begin
2387             if Sep = ASCII.NUL then
2388                return "";
2389             else
2390                return "" & Sep;
2391             end if;
2392          end;
2393       end if;
2394    end Current_Separator;
2395
2396    -----------------------
2397    -- Current_Parameter --
2398    -----------------------
2399
2400    function Current_Parameter (Iter : Command_Line_Iterator) return String is
2401    begin
2402       if Iter.Params = null
2403         or else Iter.Current > Iter.Params'Last
2404         or else Iter.Params (Iter.Current) = null
2405       then
2406          return "";
2407
2408       else
2409          declare
2410             P : constant String := Iter.Params (Iter.Current).all;
2411
2412          begin
2413             --  Skip separator
2414
2415             return P (P'First + 1 .. P'Last);
2416          end;
2417       end if;
2418    end Current_Parameter;
2419
2420    --------------
2421    -- Has_More --
2422    --------------
2423
2424    function Has_More (Iter : Command_Line_Iterator) return Boolean is
2425    begin
2426       return Iter.List /= null and then Iter.Current <= Iter.List'Last;
2427    end Has_More;
2428
2429    ----------
2430    -- Next --
2431    ----------
2432
2433    procedure Next (Iter : in out Command_Line_Iterator) is
2434    begin
2435       Iter.Current := Iter.Current + 1;
2436       while Iter.Current <= Iter.List'Last
2437         and then Iter.List (Iter.Current) = null
2438       loop
2439          Iter.Current := Iter.Current + 1;
2440       end loop;
2441    end Next;
2442
2443    ----------
2444    -- Free --
2445    ----------
2446
2447    procedure Free (Config : in out Command_Line_Configuration) is
2448    begin
2449       if Config /= null then
2450          Free (Config.Aliases);
2451          Free (Config.Expansions);
2452          Free (Config.Prefixes);
2453          Free (Config.Sections);
2454          Free (Config.Switches);
2455          Unchecked_Free (Config);
2456       end if;
2457    end Free;
2458
2459    ----------
2460    -- Free --
2461    ----------
2462
2463    procedure Free (Cmd : in out Command_Line) is
2464    begin
2465       Free (Cmd.Expanded);
2466       Free (Cmd.Coalesce);
2467       Free (Cmd.Params);
2468    end Free;
2469
2470 end GNAT.Command_Line;