tests: better reports when /bin/ed is not present.
[sbcl.git] / tests / run-program.impure.lisp
1 ;;;; various RUN-PROGRAM tests with side effects
2
3 ;;;; This software is part of the SBCL system. See the README file for
4 ;;;; more information.
5 ;;;;
6 ;;;; While most of SBCL is derived from the CMU CL system, the test
7 ;;;; files (like this one) were written from scratch after the fork
8 ;;;; from CMU CL.
9 ;;;;
10 ;;;; This software is in the public domain and is provided with
11 ;;;; absolutely no warranty. See the COPYING and CREDITS files for
12 ;;;; more information.
13
14 (cl:in-package :cl-user)
15
16 ;; In addition to definitions lower down the impurity we're avoiding
17 ;; is the sigchld handler that RUN-PROGRAM sets up, which interfers
18 ;; with the manual unix process control done by the test framework
19 ;; (sometimes the handler will manage to WAIT3 a process before
20 ;; run-tests WAITPIDs it).
21
22 (with-test (:name :run-program-cat-1 :skipped-on :win32)
23   (let* ((process (sb-ext:run-program "/bin/cat" '() :wait nil
24                                       :output :stream :input :stream))
25          (out (process-input process))
26          (in (process-output process)))
27     (unwind-protect
28          (loop for i from 0 to 255 do
29               (write-byte i out)
30               (force-output out)
31               (assert (= (read-byte in) i)))
32       (process-close process))))
33
34 (with-test (:name :run-program-cat-2 :skipped-on '(or (not :sb-thread) :win32))
35   ;; Tests that reading from a FIFO is interruptible.
36   (let* ((process (sb-ext:run-program "/bin/cat" '()
37                                       :wait nil
38                                       :output :stream :input :stream))
39          (in (process-input process))
40          (out (process-output process))
41          (sem (sb-thread:make-semaphore))
42          (state :init)
43          (writer (sb-thread:make-thread (lambda ()
44                                           (sb-thread:wait-on-semaphore sem)
45                                           (setf state :sleep)
46                                           (sleep 2)
47                                           (setf state :write)
48                                           (write-line "OK" in)
49                                           (finish-output in))))
50          (timeout nil)
51          (got nil)
52          (unwind nil))
53     (sb-thread:signal-semaphore sem)
54     (handler-case
55         (with-timeout 0.1
56           (unwind-protect
57                (setf got (read-line out))
58             (setf unwind state)))
59       (timeout ()
60         (setf timeout t)))
61     (assert (not got))
62     (assert timeout)
63     (assert (eq unwind :sleep))
64     (sb-thread:join-thread writer)
65     (assert (equal "OK" (read-line out)))))
66
67 (defclass buffer-stream (sb-gray:fundamental-binary-input-stream sb-gray:fundamental-binary-output-stream)
68   ((buffer :initform (make-array 128
69                                 :element-type '(unsigned-byte 8)
70                                 :adjustable t
71                                 :fill-pointer 0))
72    (mark :initform 0)))
73
74 (defmethod stream-element-type ((stream buffer-stream))
75   '(unsigned-byte 8))
76
77 (defmethod sb-gray:stream-read-sequence ((stream buffer-stream) seq &optional (start 0) end)
78   (let* ((buffer (slot-value stream 'buffer))
79          (end (or end (length seq)))
80          (mark (slot-value stream 'mark))
81          (fill-pointer (fill-pointer buffer))
82          (new-mark (+ mark (min fill-pointer (- end start)))))
83     (setf (slot-value stream 'mark) new-mark)
84     (replace seq buffer
85              :start1 start :end1 end
86              :start2 mark :end2 fill-pointer)
87     (min end (+ start (- fill-pointer mark)))))
88
89 (defmethod sb-gray:stream-write-sequence ((stream buffer-stream) seq &optional (start 0) end)
90   (let* ((buffer (slot-value stream 'buffer))
91          (end (or end (length seq)))
92          (fill-pointer (fill-pointer buffer))
93          (new-fill (min (array-total-size buffer) (+ fill-pointer (- end start)))))
94     (setf (fill-pointer buffer) new-fill)
95     (replace buffer seq
96              :start1 fill-pointer
97              :start2 start :end2 end)
98     seq))
99
100 (with-test (:name :run-program-cat-3 :skipped-on :win32)
101   ;; User-defined binary input and output streams.
102   (let ((in (make-instance 'buffer-stream))
103         (out (make-instance 'buffer-stream))
104         (data #(0 1 2 3 4 5 6 7 8 9 10 11 12)))
105     (write-sequence data in)
106     (let ((process (sb-ext:run-program "/bin/cat" '() :wait t :output out :input in))
107           (buf (make-array (length data))))
108       (assert (= 13 (read-sequence buf out)))
109       (assert (= 0 (read-sequence (make-array 8) out)))
110       (assert (equalp buf data)))))
111
112 (with-test (:name :run-program-cat-4 :skipped-on :win32)
113   ;; Null broadcast stream as output
114   (let* ((process (sb-ext:run-program "/bin/cat" '() :wait nil
115                                       :output (make-broadcast-stream)
116                                       :input :stream))
117          (in (process-input process)))
118     (unwind-protect
119          (progn
120            (write-string "foobar" in)
121            (close in)
122            (process-wait process))
123       (process-close process))))
124
125 ;;; Test driving an external program (cat) through pipes wrapped in
126 ;;; composite streams.
127
128 (require :sb-posix)
129
130 #-win32
131 (progn
132   (defun make-pipe ()
133     (multiple-value-bind (in out) (sb-posix:pipe)
134       (let ((input (sb-sys:make-fd-stream in
135                                           :input t
136                                           :external-format :ascii
137                                           :buffering :none :name "in"))
138             (output (sb-sys:make-fd-stream out
139                                            :output t
140                                            :external-format :ascii
141                                            :buffering :none :name "out")))
142         (make-two-way-stream input output))))
143
144   (defparameter *cat-in-pipe* (make-pipe))
145   (defparameter *cat-in* (make-synonym-stream '*cat-in-pipe*))
146   (defparameter *cat-out-pipe* (make-pipe))
147   (defparameter *cat-out* (make-synonym-stream '*cat-out-pipe*)))
148
149 (with-test (:name :run-program-cat-5 :fails-on :win32)
150   (let ((cat (run-program "/bin/cat" nil :input *cat-in* :output *cat-out*
151                           :wait nil)))
152     (dolist (test '("This is a test!"
153                     "This is another test!"
154                     "This is the last test...."))
155       (write-line test *cat-in*)
156       (assert (equal test (read-line *cat-out*))))
157     (process-close cat)))
158
159 ;;; The above test used to use ed, but there were buffering issues: on some platforms
160 ;;; buffering of stdin and stdout depends on their TTYness, and ed isn't sufficiently
161 ;;; agressive about flushing them. So, here's another test using :PTY.
162
163 #-win32
164 (with-test (:name :is-/bin/ed-installed?)
165   (assert (probe-file "/bin/ed")))
166
167 #-win32
168 (progn
169   (defparameter *tmpfile* "run-program-ed-test.tmp")
170
171   (with-test (:name :run-program-/bin/ed)
172     (with-open-file (f *tmpfile*
173                        :direction :output
174                        :if-exists :supersede)
175       (write-line "bar" f))
176     (unwind-protect
177          (let* ((ed (run-program "/bin/ed" (list *tmpfile*) :wait nil :pty t))
178                 (ed-in (process-pty ed))
179                 (ed-out (process-pty ed)))
180            (labels ((read-linish (stream)
181                       (with-output-to-string (s)
182                         (loop for c = (read-char stream)
183                               while (and c (not (eq #\newline c)))
184                               ;; Some eds like to send \r\n
185                               do (unless (eq #\return c)
186                                    (write-char c s)))))
187                     (assert-ed (command response)
188                       (when command
189                         (write-line command ed-in)
190                         (force-output ed-in))
191                       (when response
192                         (let ((got (read-linish ed-out)))
193                           (unless (equal response got)
194                             (error "wanted '~A' from ed, got '~A'" response got))))
195                       ed))
196              (assert-ed nil "4")
197              (assert-ed ".s/bar/baz/g" nil)
198              (assert-ed "w" "4")
199              (assert-ed "q" nil)
200              (process-wait ed)
201              (with-open-file (f *tmpfile*)
202                (assert (equal "baz" (read-line f))))))
203       (delete-file *tmpfile*)))) ;; #-win32
204
205 ;; Around 1.0.12 there was a regression when :INPUT or :OUTPUT was a
206 ;; pathname designator.  Since these use the same code, it should
207 ;; suffice to test just :INPUT.
208 (let ((file))
209   (unwind-protect
210        (progn (with-open-file (f "run-program-test.tmp" :direction :output)
211                 (setf file (truename f))
212                 (write-line "Foo" f))
213                   (assert (run-program "cat" ()
214                                        :input file :output t
215                                        :search t :wait t)))
216     (when file
217       (delete-file file))))
218
219 ;;; This used to crash on Darwin and trigger recursive lock errors on
220 ;;; every platform.
221 (with-test (:name (:run-program :stress) :fails-on :win32)
222   ;; Do it a hundred times in batches of 10 so that with a low limit
223   ;; of the number of processes the test can have a chance to pass.
224   (loop
225    repeat 10 do
226    (map nil
227         #'sb-ext:process-wait
228         (loop repeat 10
229               collect
230               (sb-ext:run-program "/bin/echo" '
231                                   ("It would be nice if this didn't crash.")
232                                   :wait nil :output nil)))))
233
234 (with-test (:name (:run-program :pty-stream) :fails-on :win32)
235   (assert (equal "OK"
236                  (subseq
237                   (with-output-to-string (s)
238                     (assert (= 42 (process-exit-code
239                                    (run-program "/bin/sh" '("-c" "echo OK; exit 42") :wait t
240                                                 :pty s))))
241                     s)
242                   0
243                   2))))
244
245 ;; Check whether RUN-PROGRAM puts its child process into the foreground
246 ;; when stdin is inherited. If it fails to do so we will receive a SIGTTIN.
247 ;;
248 ;; We can't check for the signal itself since run-program.c resets the
249 ;; forked process' signal mask to defaults. But the default is `stop'
250 ;; of which we can be notified asynchronously by providing a status hook.
251 (with-test (:name (:run-program :inherit-stdin) :fails-on :win32)
252   (let (stopped)
253     (flet ((status-hook (proc)
254              (case (sb-ext:process-status proc)
255                (:stopped (setf stopped t)))))
256       (let ((proc (sb-ext:run-program "/bin/ed" nil :search nil :wait nil
257                                       :input t :output t
258                                       :status-hook #'status-hook)))
259         ;; Give the program a generous time to generate the SIGTTIN.
260         ;; If it hasn't done so after that time we can consider it
261         ;; to be working (i.e. waiting for input without generating SIGTTIN).
262         (sleep 0.5)
263         ;; either way we have to signal it to terminate
264         (process-kill proc sb-posix:sigterm)
265         (process-close proc)
266         (assert (not stopped))))))
267
268
269 ;; Check that in when you do run-program with :wait t that causes
270 ;; encoding error, it does not affect the following run-program
271 (with-test (:name (:run-program :clean-exit-after-encoding-error)
272                   :fails-on :win32)
273   (let ((had-error-p nil))
274     (flet ((barf (&optional (format :default))
275              (with-output-to-string (stream)
276                (run-program #-netbsd "/usr/bin/perl" #+netbsd "/usr/pkg/bin/perl"
277                             '("-e" "print \"\\x20\\xfe\\xff\\x0a\"")
278                             :output stream
279                             :external-format format)))
280            (no-barf ()
281              (with-output-to-string (stream)
282                (run-program "/bin/echo"
283                             '("This is a test")
284                             :output stream))))
285       (handler-case
286           (barf :utf-8)
287         (error ()
288           (setq had-error-p t)))
289       (assert had-error-p)
290       ;; now run the harmless program
291       (setq had-error-p nil)
292       (handler-case
293           (no-barf)
294         (error ()
295           (setq had-error-p t)))
296       (assert (not had-error-p)))))
297
298 (with-test (:name (:run-program :no-such-thing))
299   (assert (search "Couldn't execute"
300                   (handler-case
301                       (progn (run-program "no-such-program-we-hope" '()) nil)
302                     (error (e)
303                       (princ-to-string e))))))
304
305 (with-test (:name (:run-program :not-executable))
306   (assert (search "Couldn't execute"
307                   (handler-case
308                       (progn (run-program "run-program.impure.lisp" '()) nil)
309                     (error (e)
310                       (princ-to-string e))))))
311
312 #-win32
313 (with-test (:name (:run-program :if-input-does-not-exist))
314   (let ((file (pathname (sb-posix:mktemp "rpXXXXXX"))))
315     (assert (null (sb-ext:run-program "/bin/cat" '() :input file)))
316     (assert (null (sb-ext:run-program "/bin/cat" '() :output #.(or *compile-file-truename*
317                                                                    *load-truename*)
318                                       :if-output-exists nil)))))
319
320
321 (with-test (:name (:run-program :set-directory))
322   (let* ((directory #-win32 "/"
323                     #+win32 "c:\\")
324          (out (sb-ext:process-output
325                (sb-ext:run-program #-win32 "/bin/sh"
326                                    #-win32 '("-c" "pwd")
327                                    #+win32 "cmd.exe"
328                                    #+win32 '("/c" "cd")
329                                    :output :stream
330                                    :directory directory
331                                    :search t))))
332     (assert
333      (equal directory
334             (string-right-trim '(#\Return) (read-line out))))))