1 ------------------------------------------------------------------------------
3 -- GNAT LIBRARY COMPONENTS --
5 -- G N A T . E X P E C T --
9 -- Copyright (C) 2002-2010, AdaCore --
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 2, 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 COPYING. If not, write --
19 -- to the Free Software Foundation, 51 Franklin Street, Fifth Floor, --
20 -- Boston, MA 02110-1301, USA. --
22 -- As a special exception, if other files instantiate generics from this --
23 -- unit, or you link this unit with other files to produce an executable, --
24 -- this unit does not by itself cause the resulting executable to be --
25 -- covered by the GNU General Public License. This exception does not --
26 -- however invalidate any other reasons why the executable file might be --
27 -- covered by the GNU Public License. --
29 -- GNAT was originally developed by the GNAT team at New York University. --
30 -- Extensive contributions were provided by Ada Core Technologies Inc. --
32 ------------------------------------------------------------------------------
34 -- This is the VMS version
36 with System
; use System
;
37 with Ada
.Calendar
; use Ada
.Calendar
;
40 with GNAT
.OS_Lib
; use GNAT
.OS_Lib
;
41 with GNAT
.Regpat
; use GNAT
.Regpat
;
43 with Ada
.Unchecked_Deallocation
;
45 package body GNAT
.Expect
is
47 type Array_Of_Pd
is array (Positive range <>) of Process_Descriptor_Access
;
49 Save_Input
: File_Descriptor
;
50 Save_Output
: File_Descriptor
;
51 Save_Error
: File_Descriptor
;
53 Expect_Process_Died
: constant Expect_Match
:= -100;
54 Expect_Internal_Error
: constant Expect_Match
:= -101;
55 -- Additional possible outputs of Expect_Internal. These are not visible in
56 -- the spec because the user will never see them.
58 procedure Expect_Internal
59 (Descriptors
: in out Array_Of_Pd
;
60 Result
: out Expect_Match
;
62 Full_Buffer
: Boolean);
63 -- Internal function used to read from the process Descriptor.
65 -- Several outputs are possible:
66 -- Result=Expect_Timeout, if no output was available before the timeout
68 -- Result=Expect_Full_Buffer, if Full_Buffer is True and some characters
69 -- had to be discarded from the internal buffer of Descriptor.
70 -- Result=Express_Process_Died if one of the processes was terminated.
71 -- That process's Input_Fd is set to Invalid_FD
72 -- Result=Express_Internal_Error
73 -- Result=<integer>, indicates how many characters were added to the
74 -- internal buffer. These characters are from indexes
75 -- Descriptor.Buffer_Index - Result + 1 .. Descriptor.Buffer_Index
76 -- Process_Died is raised if the process is no longer valid.
78 procedure Reinitialize_Buffer
79 (Descriptor
: in out Process_Descriptor
'Class);
80 -- Reinitialize the internal buffer.
81 -- The buffer is deleted up to the end of the last match.
83 procedure Free
is new Ada
.Unchecked_Deallocation
84 (Pattern_Matcher
, Pattern_Matcher_Access
);
86 procedure Call_Filters
87 (Pid
: Process_Descriptor
'Class;
89 Filter_On
: Filter_Type
);
90 -- Call all the filters that have the appropriate type.
91 -- This function does nothing if the filters are locked
93 ------------------------------
94 -- Target dependent section --
95 ------------------------------
97 function Dup
(Fd
: File_Descriptor
) return File_Descriptor
;
98 pragma Import
(C
, Dup
, "decc$dup");
100 procedure Dup2
(Old_Fd
, New_Fd
: File_Descriptor
);
101 pragma Import
(C
, Dup2
, "decc$dup2");
103 procedure Kill
(Pid
: Process_Id
; Sig_Num
: Integer);
104 pragma Import
(C
, Kill
, "decc$kill");
106 function Create_Pipe
(Pipe
: not null access Pipe_Type
) return Integer;
107 pragma Import
(C
, Create_Pipe
, "__gnat_pipe");
110 (Fds
: System
.Address
;
113 Is_Set
: System
.Address
) return Integer;
114 pragma Import
(C
, Poll
, "__gnat_expect_poll");
115 -- Check whether there is any data waiting on the file descriptor
116 -- Out_fd, and wait if there is none, at most Timeout milliseconds
117 -- Returns -1 in case of error, 0 if the timeout expired before
118 -- data became available.
120 -- Out_Is_Set is set to 1 if data was available, 0 otherwise.
122 function Waitpid
(Pid
: Process_Id
) return Integer;
123 pragma Import
(C
, Waitpid
, "__gnat_waitpid");
124 -- Wait for a specific process id, and return its exit code
130 function "+" (S
: String) return GNAT
.OS_Lib
.String_Access
is
132 return new String'(S);
140 (P : GNAT.Regpat.Pattern_Matcher) return Pattern_Matcher_Access
143 return new GNAT.Regpat.Pattern_Matcher'(P
);
151 (Descriptor
: in out Process_Descriptor
;
152 Filter
: Filter_Function
;
153 Filter_On
: Filter_Type
:= Output
;
154 User_Data
: System
.Address
:= System
.Null_Address
;
155 After
: Boolean := False)
157 Current
: Filter_List
:= Descriptor
.Filters
;
161 while Current
/= null and then Current
.Next
/= null loop
162 Current
:= Current
.Next
;
165 if Current
= null then
166 Descriptor
.Filters
:=
167 new Filter_List_Elem
'
168 (Filter => Filter, Filter_On => Filter_On,
169 User_Data => User_Data, Next => null);
172 new Filter_List_Elem'
173 (Filter
=> Filter
, Filter_On
=> Filter_On
,
174 User_Data
=> User_Data
, Next
=> null);
178 Descriptor
.Filters
:=
179 new Filter_List_Elem
'
180 (Filter => Filter, Filter_On => Filter_On,
181 User_Data => User_Data, Next => Descriptor.Filters);
189 procedure Call_Filters
190 (Pid : Process_Descriptor'Class;
192 Filter_On : Filter_Type)
194 Current_Filter : Filter_List;
197 if Pid.Filters_Lock = 0 then
198 Current_Filter := Pid.Filters;
200 while Current_Filter /= null loop
201 if Current_Filter.Filter_On = Filter_On then
202 Current_Filter.Filter
203 (Pid, Str, Current_Filter.User_Data);
206 Current_Filter := Current_Filter.Next;
216 (Descriptor : in out Process_Descriptor;
217 Status : out Integer)
220 if Descriptor.Input_Fd /= Invalid_FD then
221 Close (Descriptor.Input_Fd);
224 if Descriptor.Error_Fd /= Descriptor.Output_Fd then
225 Close (Descriptor.Error_Fd);
228 Close (Descriptor.Output_Fd);
230 -- ??? Should have timeouts for different signals
232 if Descriptor.Pid > 0 then -- see comment in Send_Signal
233 Kill (Descriptor.Pid, Sig_Num => 9);
236 GNAT.OS_Lib.Free (Descriptor.Buffer);
237 Descriptor.Buffer_Size := 0;
239 -- Check process id (see comment in Send_Signal)
241 if Descriptor.Pid > 0 then
242 Status := Waitpid (Descriptor.Pid);
244 raise Invalid_Process;
248 procedure Close (Descriptor : in out Process_Descriptor) is
251 Close (Descriptor, Status);
259 (Descriptor : in out Process_Descriptor;
260 Result : out Expect_Match;
262 Timeout : Integer := 10_000;
263 Full_Buffer : Boolean := False)
267 Expect (Descriptor, Result, Never_Match, Timeout, Full_Buffer);
269 Expect (Descriptor, Result, Compile (Regexp), Timeout, Full_Buffer);
274 (Descriptor : in out Process_Descriptor;
275 Result : out Expect_Match;
277 Matched : out GNAT.Regpat.Match_Array;
278 Timeout : Integer := 10_000;
279 Full_Buffer : Boolean := False)
282 pragma Assert (Matched'First = 0);
285 (Descriptor, Result, Never_Match, Matched, Timeout, Full_Buffer);
288 (Descriptor, Result, Compile (Regexp), Matched, Timeout,
294 (Descriptor : in out Process_Descriptor;
295 Result : out Expect_Match;
296 Regexp : GNAT.Regpat.Pattern_Matcher;
297 Timeout : Integer := 10_000;
298 Full_Buffer : Boolean := False)
300 Matched : GNAT.Regpat.Match_Array (0 .. 0);
303 Expect (Descriptor, Result, Regexp, Matched, Timeout, Full_Buffer);
307 (Descriptor : in out Process_Descriptor;
308 Result : out Expect_Match;
309 Regexp : GNAT.Regpat.Pattern_Matcher;
310 Matched : out GNAT.Regpat.Match_Array;
311 Timeout : Integer := 10_000;
312 Full_Buffer : Boolean := False)
315 Descriptors : Array_Of_Pd := (1 => Descriptor'Unrestricted_Access);
316 Try_Until : constant Time := Clock + Duration (Timeout) / 1000.0;
317 Timeout_Tmp : Integer := Timeout;
320 pragma Assert (Matched'First = 0);
321 Reinitialize_Buffer (Descriptor);
324 -- First, test if what is already in the buffer matches (This is
325 -- required if this package is used in multi-task mode, since one of
326 -- the tasks might have added something in the buffer, and we don't
327 -- want other tasks to wait for new input to be available before
328 -- checking the regexps).
331 (Regexp, Descriptor.Buffer (1 .. Descriptor.Buffer_Index), Matched);
333 if Descriptor.Buffer_Index >= 1 and then Matched (0).First /= 0 then
335 Descriptor.Last_Match_Start := Matched (0).First;
336 Descriptor.Last_Match_End := Matched (0).Last;
340 -- Else try to read new input
342 Expect_Internal (Descriptors, N, Timeout_Tmp, Full_Buffer);
345 when Expect_Internal_Error | Expect_Process_Died =>
348 when Expect_Timeout | Expect_Full_Buffer =>
356 -- Calculate the timeout for the next turn
358 -- Note that Timeout is, from the caller's perspective, the maximum
359 -- time until a match, not the maximum time until some output is
360 -- read, and thus cannot be reused as is for Expect_Internal.
362 if Timeout /= -1 then
363 Timeout_Tmp := Integer (Try_Until - Clock) * 1000;
365 if Timeout_Tmp < 0 then
366 Result := Expect_Timeout;
372 -- Even if we had the general timeout above, we have to test that the
373 -- last test we read from the external process didn't match.
376 (Regexp, Descriptor.Buffer (1 .. Descriptor.Buffer_Index), Matched);
378 if Matched (0).First /= 0 then
380 Descriptor.Last_Match_Start := Matched (0).First;
381 Descriptor.Last_Match_End := Matched (0).Last;
387 (Descriptor : in out Process_Descriptor;
388 Result : out Expect_Match;
389 Regexps : Regexp_Array;
390 Timeout : Integer := 10_000;
391 Full_Buffer : Boolean := False)
393 Patterns : Compiled_Regexp_Array (Regexps'Range);
394 Matched : GNAT.Regpat.Match_Array (0 .. 0);
397 for J in Regexps'Range loop
398 Patterns (J) := new Pattern_Matcher'(Compile
(Regexps
(J
).all));
401 Expect
(Descriptor
, Result
, Patterns
, Matched
, Timeout
, Full_Buffer
);
403 for J
in Regexps
'Range loop
409 (Descriptor
: in out Process_Descriptor
;
410 Result
: out Expect_Match
;
411 Regexps
: Compiled_Regexp_Array
;
412 Timeout
: Integer := 10_000
;
413 Full_Buffer
: Boolean := False)
415 Matched
: GNAT
.Regpat
.Match_Array
(0 .. 0);
418 Expect
(Descriptor
, Result
, Regexps
, Matched
, Timeout
, Full_Buffer
);
422 (Result
: out Expect_Match
;
423 Regexps
: Multiprocess_Regexp_Array
;
424 Timeout
: Integer := 10_000
;
425 Full_Buffer
: Boolean := False)
427 Matched
: GNAT
.Regpat
.Match_Array
(0 .. 0);
430 Expect
(Result
, Regexps
, Matched
, Timeout
, Full_Buffer
);
434 (Descriptor
: in out Process_Descriptor
;
435 Result
: out Expect_Match
;
436 Regexps
: Regexp_Array
;
437 Matched
: out GNAT
.Regpat
.Match_Array
;
438 Timeout
: Integer := 10_000
;
439 Full_Buffer
: Boolean := False)
441 Patterns
: Compiled_Regexp_Array
(Regexps
'Range);
444 pragma Assert
(Matched
'First = 0);
446 for J
in Regexps
'Range loop
447 Patterns
(J
) := new Pattern_Matcher
'(Compile (Regexps (J).all));
450 Expect (Descriptor, Result, Patterns, Matched, Timeout, Full_Buffer);
452 for J in Regexps'Range loop
458 (Descriptor : in out Process_Descriptor;
459 Result : out Expect_Match;
460 Regexps : Compiled_Regexp_Array;
461 Matched : out GNAT.Regpat.Match_Array;
462 Timeout : Integer := 10_000;
463 Full_Buffer : Boolean := False)
466 Descriptors : Array_Of_Pd := (1 => Descriptor'Unrestricted_Access);
469 pragma Assert (Matched'First = 0);
471 Reinitialize_Buffer (Descriptor);
474 -- First, test if what is already in the buffer matches (This is
475 -- required if this package is used in multi-task mode, since one of
476 -- the tasks might have added something in the buffer, and we don't
477 -- want other tasks to wait for new input to be available before
478 -- checking the regexps).
480 if Descriptor.Buffer /= null then
481 for J in Regexps'Range loop
484 Descriptor.Buffer (1 .. Descriptor.Buffer_Index),
487 if Matched (0) /= No_Match then
488 Result := Expect_Match (J);
489 Descriptor.Last_Match_Start := Matched (0).First;
490 Descriptor.Last_Match_End := Matched (0).Last;
496 Expect_Internal (Descriptors, N, Timeout, Full_Buffer);
499 when Expect_Internal_Error | Expect_Process_Died =>
502 when Expect_Timeout | Expect_Full_Buffer =>
513 (Result : out Expect_Match;
514 Regexps : Multiprocess_Regexp_Array;
515 Matched : out GNAT.Regpat.Match_Array;
516 Timeout : Integer := 10_000;
517 Full_Buffer : Boolean := False)
520 Descriptors : Array_Of_Pd (Regexps'Range);
523 pragma Assert (Matched'First = 0);
525 for J in Descriptors'Range loop
526 Descriptors (J) := Regexps (J).Descriptor;
528 if Descriptors (J) /= null then
529 Reinitialize_Buffer (Regexps (J).Descriptor.all);
534 -- First, test if what is already in the buffer matches (This is
535 -- required if this package is used in multi-task mode, since one of
536 -- the tasks might have added something in the buffer, and we don't
537 -- want other tasks to wait for new input to be available before
538 -- checking the regexps).
540 for J in Regexps'Range loop
541 if Regexps (J).Regexp /= null
542 and then Regexps (J).Descriptor /= null
544 Match (Regexps (J).Regexp.all,
545 Regexps (J).Descriptor.Buffer
546 (1 .. Regexps (J).Descriptor.Buffer_Index),
549 if Matched (0) /= No_Match then
550 Result := Expect_Match (J);
551 Regexps (J).Descriptor.Last_Match_Start := Matched (0).First;
552 Regexps (J).Descriptor.Last_Match_End := Matched (0).Last;
558 Expect_Internal (Descriptors, N, Timeout, Full_Buffer);
561 when Expect_Internal_Error | Expect_Process_Died =>
564 when Expect_Timeout | Expect_Full_Buffer =>
574 ---------------------
575 -- Expect_Internal --
576 ---------------------
578 procedure Expect_Internal
579 (Descriptors : in out Array_Of_Pd;
580 Result : out Expect_Match;
582 Full_Buffer : Boolean)
584 Num_Descriptors : Integer;
585 Buffer_Size : Integer := 0;
589 type File_Descriptor_Array is
590 array (0 .. Descriptors'Length - 1) of File_Descriptor;
591 Fds : aliased File_Descriptor_Array;
592 Fds_Count : Natural := 0;
594 Fds_To_Descriptor : array (Fds'Range) of Integer;
595 -- Maps file descriptor entries from Fds to entries in Descriptors.
596 -- They do not have the same index when entries in Descriptors are null.
598 type Integer_Array is array (Fds'Range) of Integer;
599 Is_Set : aliased Integer_Array;
602 for J in Descriptors'Range loop
603 if Descriptors (J) /= null then
604 Fds (Fds'First + Fds_Count) := Descriptors (J).Output_Fd;
605 Fds_To_Descriptor (Fds'First + Fds_Count) := J;
606 Fds_Count := Fds_Count + 1;
608 if Descriptors (J).Buffer_Size = 0 then
609 Buffer_Size := Integer'Max (Buffer_Size, 4096);
612 Integer'Max (Buffer_Size, Descriptors (J).Buffer_Size);
618 Buffer : aliased String (1 .. Buffer_Size);
619 -- Buffer used for input. This is allocated only once, not for
620 -- every iteration of the loop
623 -- Index in Descriptors
626 -- Loop until we match or we have a timeout
630 Poll (Fds'Address, Fds_Count, Timeout, Is_Set'Address);
632 case Num_Descriptors is
637 Result := Expect_Internal_Error;
643 Result := Expect_Timeout;
649 for F in Fds'Range loop
650 if Is_Set (F) = 1 then
651 D := Fds_To_Descriptor (F);
653 Buffer_Size := Descriptors (D).Buffer_Size;
655 if Buffer_Size = 0 then
659 N := Read (Descriptors (D).Output_Fd, Buffer'Address,
662 -- Error or End of file
665 -- ??? Note that ddd tries again up to three times
666 -- in that case. See LiterateA.C:174
668 Descriptors (D).Input_Fd := Invalid_FD;
669 Result := Expect_Process_Died;
673 -- If there is no limit to the buffer size
675 if Descriptors (D).Buffer_Size = 0 then
678 Tmp : String_Access := Descriptors (D).Buffer;
682 Descriptors (D).Buffer :=
683 new String (1 .. Tmp'Length + N);
684 Descriptors (D).Buffer (1 .. Tmp'Length) :=
686 Descriptors (D).Buffer
687 (Tmp'Length + 1 .. Tmp'Length + N) :=
690 Descriptors (D).Buffer_Index :=
691 Descriptors (D).Buffer'Last;
694 Descriptors (D).Buffer :=
696 Descriptors (D).Buffer.all :=
698 Descriptors (D).Buffer_Index := N;
703 -- Add what we read to the buffer
705 if Descriptors (D).Buffer_Index + N >
706 Descriptors (D).Buffer_Size
708 -- If the user wants to know when we have
709 -- read more than the buffer can contain.
712 Result := Expect_Full_Buffer;
716 -- Keep as much as possible from the buffer,
717 -- and forget old characters.
719 Descriptors (D).Buffer
720 (1 .. Descriptors (D).Buffer_Size - N) :=
721 Descriptors (D).Buffer
722 (N - Descriptors (D).Buffer_Size +
723 Descriptors (D).Buffer_Index + 1 ..
724 Descriptors (D).Buffer_Index);
725 Descriptors (D).Buffer_Index :=
726 Descriptors (D).Buffer_Size - N;
729 -- Keep what we read in the buffer
731 Descriptors (D).Buffer
732 (Descriptors (D).Buffer_Index + 1 ..
733 Descriptors (D).Buffer_Index + N) :=
735 Descriptors (D).Buffer_Index :=
736 Descriptors (D).Buffer_Index + N;
739 -- Call each of the output filter with what we
743 (Descriptors (D).all, Buffer (1 .. N), Output);
745 Result := Expect_Match (D);
759 function Expect_Out (Descriptor : Process_Descriptor) return String is
761 return Descriptor.Buffer (1 .. Descriptor.Last_Match_End);
764 ----------------------
765 -- Expect_Out_Match --
766 ----------------------
768 function Expect_Out_Match (Descriptor : Process_Descriptor) return String is
770 return Descriptor.Buffer
771 (Descriptor.Last_Match_Start .. Descriptor.Last_Match_End);
772 end Expect_Out_Match;
774 ------------------------
775 -- First_Dead_Process --
776 ------------------------
778 function First_Dead_Process
779 (Regexp : Multiprocess_Regexp_Array) return Natural
782 for R in Regexp'Range loop
783 if Regexp (R).Descriptor /= null
784 and then Regexp (R).Descriptor.Input_Fd = GNAT.OS_Lib.Invalid_FD
791 end First_Dead_Process;
798 (Descriptor : in out Process_Descriptor;
799 Timeout : Integer := 0)
801 Buffer_Size : constant Integer := 8192;
802 Num_Descriptors : Integer;
804 Is_Set : aliased Integer;
805 Buffer : aliased String (1 .. Buffer_Size);
808 -- Empty the current buffer
810 Descriptor.Last_Match_End := Descriptor.Buffer_Index;
811 Reinitialize_Buffer (Descriptor);
813 -- Read everything from the process to flush its output
817 Poll (Descriptor.Output_Fd'Address, 1, Timeout, Is_Set'Address);
819 case Num_Descriptors is
826 -- Timeout => End of flush
835 N := Read (Descriptor.Output_Fd, Buffer'Address,
852 procedure Free (Regexp : in out Multiprocess_Regexp) is
853 procedure Unchecked_Free is new Ada.Unchecked_Deallocation
854 (Process_Descriptor'Class, Process_Descriptor_Access);
856 Unchecked_Free (Regexp.Descriptor);
857 Free (Regexp.Regexp);
860 ------------------------
861 -- Get_Command_Output --
862 ------------------------
864 function Get_Command_Output
866 Arguments : GNAT.OS_Lib.Argument_List;
868 Status : not null access Integer;
869 Err_To_Out : Boolean := False) return String
873 Process : Process_Descriptor;
875 Output : String_Access := new String (1 .. 1024);
876 -- Buffer used to accumulate standard output from the launched
877 -- command, expanded as necessary during execution.
880 -- Index of the last used character within Output
884 (Process, Command, Arguments, Err_To_Out => Err_To_Out);
886 if Input'Length > 0 then
887 Send (Process, Input);
890 GNAT.OS_Lib.Close (Get_Input_Fd (Process));
893 Result : Expect_Match;
896 -- This loop runs until the call to Expect raises Process_Died
899 Expect (Process, Result, ".+");
902 NOutput : String_Access;
903 S : constant String := Expect_Out (Process);
904 pragma Assert (S'Length > 0);
907 -- Expand buffer if we need more space
909 if Last + S'Length > Output'Last then
910 NOutput := new String (1 .. 2 * Output'Last);
911 NOutput (Output'Range) := Output.all;
914 -- Here if current buffer size is OK
920 NOutput (Last + 1 .. Last + S'Length) := S;
921 Last := Last + S'Length;
928 Close (Process, Status.all);
936 S : constant String := Output (1 .. Last);
941 end Get_Command_Output;
947 function Get_Error_Fd
948 (Descriptor : Process_Descriptor) return GNAT.OS_Lib.File_Descriptor
951 return Descriptor.Error_Fd;
958 function Get_Input_Fd
959 (Descriptor : Process_Descriptor) return GNAT.OS_Lib.File_Descriptor
962 return Descriptor.Input_Fd;
969 function Get_Output_Fd
970 (Descriptor : Process_Descriptor) return GNAT.OS_Lib.File_Descriptor
973 return Descriptor.Output_Fd;
981 (Descriptor : Process_Descriptor) return Process_Id
984 return Descriptor.Pid;
991 function Has_Process (Regexp : Multiprocess_Regexp_Array) return Boolean is
993 return Regexp /= (Regexp'Range => (null, null));
1000 procedure Interrupt (Descriptor : in out Process_Descriptor) is
1001 SIGINT : constant := 2;
1003 Send_Signal (Descriptor, SIGINT);
1010 procedure Lock_Filters (Descriptor : in out Process_Descriptor) is
1012 Descriptor.Filters_Lock := Descriptor.Filters_Lock + 1;
1015 ------------------------
1016 -- Non_Blocking_Spawn --
1017 ------------------------
1019 procedure Non_Blocking_Spawn
1020 (Descriptor : out Process_Descriptor'Class;
1022 Args : GNAT.OS_Lib.Argument_List;
1023 Buffer_Size : Natural := 4096;
1024 Err_To_Out : Boolean := False)
1027 -------------------------
1028 -- Reinitialize_Buffer --
1029 -------------------------
1031 procedure Reinitialize_Buffer
1032 (Descriptor : in out Process_Descriptor'Class)
1035 if Descriptor.Buffer_Size = 0 then
1037 Tmp : String_Access := Descriptor.Buffer;
1040 Descriptor.Buffer :=
1042 (1 .. Descriptor.Buffer_Index - Descriptor.Last_Match_End);
1045 Descriptor.Buffer.all := Tmp
1046 (Descriptor.Last_Match_End + 1 .. Descriptor.Buffer_Index);
1051 Descriptor.Buffer_Index := Descriptor.Buffer'Last;
1055 (1 .. Descriptor.Buffer_Index - Descriptor.Last_Match_End) :=
1057 (Descriptor.Last_Match_End + 1 .. Descriptor.Buffer_Index);
1059 if Descriptor.Buffer_Index > Descriptor.Last_Match_End then
1060 Descriptor.Buffer_Index :=
1061 Descriptor.Buffer_Index - Descriptor.Last_Match_End;
1063 Descriptor.Buffer_Index := 0;
1067 Descriptor.Last_Match_Start := 0;
1068 Descriptor.Last_Match_End := 0;
1069 end Reinitialize_Buffer;
1075 procedure Remove_Filter
1076 (Descriptor : in out Process_Descriptor;
1077 Filter : Filter_Function)
1079 Previous : Filter_List := null;
1080 Current : Filter_List := Descriptor.Filters;
1083 while Current /= null loop
1084 if Current.Filter = Filter then
1085 if Previous = null then
1086 Descriptor.Filters := Current.Next;
1088 Previous.Next := Current.Next;
1092 Previous := Current;
1093 Current := Current.Next;
1102 (Descriptor : in out Process_Descriptor;
1104 Add_LF : Boolean := True;
1105 Empty_Buffer : Boolean := False)
1107 Full_Str : constant String := Str & ASCII.LF;
1109 Result : Expect_Match;
1110 Descriptors : Array_Of_Pd := (1 => Descriptor'Unrestricted_Access);
1113 pragma Unreferenced (Discard);
1116 if Empty_Buffer then
1118 -- Force a read on the process if there is anything waiting
1120 Expect_Internal (Descriptors, Result,
1121 Timeout => 0, Full_Buffer => False);
1123 if Result = Expect_Internal_Error
1124 or else Result = Expect_Process_Died
1129 Descriptor.Last_Match_End := Descriptor.Buffer_Index;
1133 Reinitialize_Buffer (Descriptor);
1136 Last := (if Add_LF then Full_Str'Last else Full_Str'Last - 1);
1138 Call_Filters (Descriptor, Full_Str (Full_Str'First .. Last), Input);
1141 Write (Descriptor.Input_Fd,
1143 Last - Full_Str'First + 1);
1144 -- Shouldn't we at least have a pragma Assert on the result ???
1151 procedure Send_Signal
1152 (Descriptor : Process_Descriptor;
1156 -- A nonpositive process id passed to kill has special meanings. For
1157 -- example, -1 means kill all processes in sight, including self, in
1158 -- POSIX and Windows (and something slightly different in Linux). See
1159 -- man pages for details. In any case, we don't want to do that. Note
1160 -- that Descriptor.Pid will be -1 if the process was not successfully
1161 -- started; we don't want to kill ourself in that case.
1163 if Descriptor.Pid > 0 then
1164 Kill (Descriptor.Pid, Signal);
1165 -- ??? Need to check process status here
1167 raise Invalid_Process;
1171 ---------------------------------
1172 -- Set_Up_Child_Communications --
1173 ---------------------------------
1175 procedure Set_Up_Child_Communications
1176 (Pid : in out Process_Descriptor;
1177 Pipe1 : in out Pipe_Type;
1178 Pipe2 : in out Pipe_Type;
1179 Pipe3 : in out Pipe_Type;
1181 Args : System.Address)
1183 pragma Warnings (Off, Pid);
1184 pragma Warnings (Off, Pipe1);
1185 pragma Warnings (Off, Pipe2);
1186 pragma Warnings (Off, Pipe3);
1189 -- Since the code between fork and exec on VMS executes
1190 -- in the context of the parent process, we need to
1191 -- perform the following actions:
1192 -- - save stdin, stdout, stderr
1193 -- - replace them by our pipes
1194 -- - create the child with process handle inheritance
1195 -- - revert to the previous stdin, stdout and stderr.
1197 Save_Input := Dup (GNAT.OS_Lib.Standin);
1198 Save_Output := Dup (GNAT.OS_Lib.Standout);
1199 Save_Error := Dup (GNAT.OS_Lib.Standerr);
1201 -- Since we are still called from the parent process, there is no way
1202 -- currently we can cleanly close the unneeded ends of the pipes, but
1203 -- this doesn't really matter.
1205 -- We could close Pipe1.Output, Pipe2.Input, Pipe3.Input
1207 Dup2 (Pipe1.Input, GNAT.OS_Lib.Standin);
1208 Dup2 (Pipe2.Output, GNAT.OS_Lib.Standout);
1209 Dup2 (Pipe3.Output, GNAT.OS_Lib.Standerr);
1211 Portable_Execvp (Pid.Pid'Access, Cmd & ASCII.NUL, Args);
1212 end Set_Up_Child_Communications;
1214 ---------------------------
1215 -- Set_Up_Communications --
1216 ---------------------------
1218 procedure Set_Up_Communications
1219 (Pid : in out Process_Descriptor;
1220 Err_To_Out : Boolean;
1221 Pipe1 : not null access Pipe_Type;
1222 Pipe2 : not null access Pipe_Type;
1223 Pipe3 : not null access Pipe_Type)
1228 if Create_Pipe (Pipe1) /= 0 then
1232 if Create_Pipe (Pipe2) /= 0 then
1236 Pid.Input_Fd := Pipe1.Output;
1237 Pid.Output_Fd := Pipe2.Input;
1240 Pipe3.all := Pipe2.all;
1242 if Create_Pipe (Pipe3) /= 0 then
1247 Pid.Error_Fd := Pipe3.Input;
1248 end Set_Up_Communications;
1250 ----------------------------------
1251 -- Set_Up_Parent_Communications --
1252 ----------------------------------
1254 procedure Set_Up_Parent_Communications
1255 (Pid : in out Process_Descriptor;
1256 Pipe1 : in out Pipe_Type;
1257 Pipe2 : in out Pipe_Type;
1258 Pipe3 : in out Pipe_Type)
1260 pragma Warnings (Off, Pid);
1261 pragma Warnings (Off, Pipe1);
1262 pragma Warnings (Off, Pipe2);
1263 pragma Warnings (Off, Pipe3);
1267 Dup2 (Save_Input, GNAT.OS_Lib.Standin);
1268 Dup2 (Save_Output, GNAT.OS_Lib.Standout);
1269 Dup2 (Save_Error, GNAT.OS_Lib.Standerr);
1272 Close (Save_Output);
1275 Close (Pipe1.Input);
1276 Close (Pipe2.Output);
1277 Close (Pipe3.Output);
1278 end Set_Up_Parent_Communications;
1284 procedure Trace_Filter
1285 (Descriptor : Process_Descriptor'Class;
1287 User_Data : System.Address := System.Null_Address)
1289 pragma Warnings (Off, Descriptor);
1290 pragma Warnings (Off, User_Data);
1295 --------------------
1296 -- Unlock_Filters --
1297 --------------------
1299 procedure Unlock_Filters (Descriptor : in out Process_Descriptor) is
1301 if Descriptor.Filters_Lock > 0 then
1302 Descriptor.Filters_Lock := Descriptor.Filters_Lock - 1;