0.9.11.16:
[sbcl.git] / src / code / run-program.lisp
1 ;;;; RUN-PROGRAM and friends, a facility for running Unix programs
2 ;;;; from inside SBCL
3
4 ;;;; This software is part of the SBCL system. See the README file for
5 ;;;; more information.
6 ;;;;
7 ;;;; This software is derived from the CMU CL system, which was
8 ;;;; written at Carnegie Mellon University and released into the
9 ;;;; public domain. The software is in the public domain and is
10 ;;;; provided with absolutely no warranty. See the COPYING and CREDITS
11 ;;;; files for more information.
12
13 (in-package "SB-IMPL") ;(SB-IMPL, not SB!IMPL, since we're built in warm load.)
14 \f
15 ;;;; hacking the Unix environment
16 ;;;;
17 ;;;; In the original CMU CL code that LOAD-FOREIGN is derived from, the
18 ;;;; Unix environment (as in "man environ") was represented as an
19 ;;;; alist from keywords to strings, so that e.g. the Unix environment
20 ;;;;   "SHELL=/bin/bash" "HOME=/root" "PAGER=less"
21 ;;;; was represented as
22 ;;;;   ((:SHELL . "/bin/bash") (:HOME . "/root") (:PAGER "less"))
23 ;;;; This had a few problems in principle: the mapping into
24 ;;;; keyword symbols smashed the case of environment
25 ;;;; variables, and the whole mapping depended on the presence of
26 ;;;; #\= characters in the environment strings. In practice these
27 ;;;; problems weren't hugely important, since conventionally environment
28 ;;;; variables are uppercase strings followed by #\= followed by
29 ;;;; arbitrary data. However, since it's so manifestly not The Right
30 ;;;; Thing to make code which breaks unnecessarily on input which
31 ;;;; doesn't follow what is, after all, only a tradition, we've switched
32 ;;;; formats in SBCL, so that the fundamental environment list
33 ;;;; is just a list of strings, with a one-to-one-correspondence
34 ;;;; to the C-level representation. I.e., in the example above,
35 ;;;; the SBCL representation is
36 ;;;;   '("SHELL=/bin/bash" "HOME=/root" "PAGER=less")
37 ;;;; CMU CL's implementation is currently supported to help with porting.
38 ;;;;
39 ;;;; It's not obvious that this code belongs here (instead of e.g. in
40 ;;;; unix.lisp), since it has only a weak logical connection with
41 ;;;; RUN-PROGRAM. However, physically it's convenient to put it here.
42 ;;;; It's not needed at cold init, so we *can* put it in this
43 ;;;; warm-loaded file. And by putting it in this warm-loaded file, we
44 ;;;; make it easy for it to get to the C-level 'environ' variable.
45 ;;;; which (at least in sbcl-0.6.10 on Red Hat Linux 6.2) is not
46 ;;;; visible at GENESIS time.
47
48 #-win32 (define-alien-routine wrapped-environ (* c-string))
49 #-win32 (defun posix-environ ()
50   "Return the Unix environment (\"man environ\") as a list of SIMPLE-STRINGs."
51   (c-strings->string-list (wrapped-environ)))
52
53 ;#+win32 (sb-alien:define-alien-routine msvcrt-environ (* c-string))
54
55 ;;; Convert as best we can from an SBCL representation of a Unix
56 ;;; environment to a CMU CL representation.
57 ;;;
58 ;;; * (UNIX-ENVIRONMENT-CMUCL-FROM-SBCL '("Bletch=fub" "Noggin" "YES=No!"))
59 ;;; WARNING:
60 ;;;   smashing case of "Bletch=fub" in conversion to CMU-CL-style
61 ;;;     environment alist
62 ;;; WARNING:
63 ;;;   no #\= in "Noggin", eliding it in CMU-CL-style environment alist
64 ;;; ((:BLETCH . "fub") (:YES . "No!"))
65 (defun unix-environment-cmucl-from-sbcl (sbcl)
66   (mapcan
67    (lambda (string)
68      (declare (type simple-base-string string))
69      (let ((=-pos (position #\= string :test #'equal)))
70        (if =-pos
71            (list
72             (let* ((key-as-string (subseq string 0 =-pos))
73                    (key-as-upcase-string (string-upcase key-as-string))
74                    (key (keywordicate key-as-upcase-string))
75                    (val (subseq string (1+ =-pos))))
76               (unless (string= key-as-string key-as-upcase-string)
77                 (warn "smashing case of ~S in conversion to CMU-CL-style ~
78                       environment alist"
79                       string))
80               (cons key val)))
81            (warn "no #\\= in ~S, eliding it in CMU-CL-style environment alist"
82                  string))))
83    sbcl))
84
85 ;;; Convert from a CMU CL representation of a Unix environment to a
86 ;;; SBCL representation.
87 (defun unix-environment-sbcl-from-cmucl (cmucl)
88   (mapcar
89    (lambda (cons)
90      (destructuring-bind (key . val) cons
91        (declare (type keyword key) (type simple-base-string val))
92        (concatenate 'simple-base-string (symbol-name key) "=" val)))
93    cmucl))
94 \f
95 ;;;; Import wait3(2) from Unix.
96
97 #-win32
98 (define-alien-routine ("wait3" c-wait3) sb-alien:int
99   (status sb-alien:int :out)
100   (options sb-alien:int)
101   (rusage sb-alien:int))
102
103 #-win32
104 (defun wait3 (&optional do-not-hang check-for-stopped)
105   #+sb-doc
106   "Return any available status information on child process. "
107   (multiple-value-bind (pid status)
108       (c-wait3 (logior (if do-not-hang
109                            sb-unix:wnohang
110                            0)
111                        (if check-for-stopped
112                            sb-unix:wuntraced
113                            0))
114                0)
115     (cond ((or (minusp pid)
116                (zerop pid))
117            nil)
118           ((eql (ldb (byte 8 0) status)
119                 sb-unix:wstopped)
120            (values pid
121                    :stopped
122                    (ldb (byte 8 8) status)))
123           ((zerop (ldb (byte 7 0) status))
124            (values pid
125                    :exited
126                    (ldb (byte 8 8) status)))
127           (t
128            (let ((signal (ldb (byte 7 0) status)))
129              (values pid
130                      (if (position signal
131                                    #.(vector
132                                       sb-unix:sigstop
133                                       sb-unix:sigtstp
134                                       sb-unix:sigttin
135                                       sb-unix:sigttou))
136                          :stopped
137                          :signaled)
138                      signal
139                      (not (zerop (ldb (byte 1 7) status)))))))))
140 \f
141 ;;;; process control stuff
142 #-win32
143 (defvar *active-processes* nil
144   #+sb-doc
145   "List of process structures for all active processes.")
146
147 #-win32
148 (defvar *active-processes-lock*
149   (sb-thread:make-mutex :name "Lock for active processes."))
150
151 ;;; *ACTIVE-PROCESSES* can be accessed from multiple threads so a
152 ;;; mutex is needed. More importantly the sigchld signal handler also
153 ;;; accesses it, that's why we need without-interrupts.
154 #-win32
155 (defmacro with-active-processes-lock (() &body body)
156   `(without-interrupts
157     (sb-thread:with-mutex (*active-processes-lock*)
158       ,@body)))
159
160
161 (defstruct (process (:copier nil))
162   pid                 ; PID of child process
163   %status             ; either :RUNNING, :STOPPED, :EXITED, or :SIGNALED
164   exit-code           ; either exit code or signal
165   core-dumped         ; T if a core image was dumped
166   #-win32 pty                 ; stream to child's pty, or NIL
167   input               ; stream to child's input, or NIL
168   output              ; stream from child's output, or NIL
169   error               ; stream from child's error output, or NIL
170   status-hook         ; closure to call when PROC changes status
171   plist               ; a place for clients to stash things
172   cookie)             ; list of the number of pipes from the subproc
173
174
175
176 #-win32 (defmethod print-object ((process process) stream)
177   (print-unreadable-object (process stream :type t)
178     (format stream
179             "~W ~S"
180             (process-pid process)
181             (process-status process)))
182   process)
183
184 #+sb-doc
185 (setf (documentation 'process-p 'function)
186       "T if OBJECT is a PROCESS, NIL otherwise.")
187
188 #+sb-doc
189 (setf (documentation 'process-pid 'function) "The pid of the child process.")
190
191 #-win32
192 (defun process-status (process)
193   #+sb-doc
194   "Return the current status of PROCESS.  The result is one of :RUNNING,
195    :STOPPED, :EXITED, or :SIGNALED."
196   (get-processes-status-changes)
197   (process-%status process))
198
199 #+sb-doc
200 (setf (documentation 'process-exit-code 'function)
201       "The exit code or the signal of a stopped process.")
202
203 #+sb-doc
204 (setf (documentation 'process-core-dumped 'function)
205       "T if a core image was dumped by the process.")
206
207 #+sb-doc
208 (setf (documentation 'process-pty 'function)
209       "The pty stream of the process or NIL.")
210
211 #+sb-doc
212 (setf (documentation 'process-input 'function)
213       "The input stream of the process or NIL.")
214
215 #+sb-doc
216 (setf (documentation 'process-output 'function)
217       "The output stream of the process or NIL.")
218
219 #+sb-doc
220 (setf (documentation 'process-error 'function)
221       "The error stream of the process or NIL.")
222
223 #+sb-doc
224 (setf (documentation 'process-status-hook  'function)
225       "A function that is called when PROCESS changes its status.
226 The function is called with PROCESS as its only argument.")
227
228 #+sb-doc
229 (setf (documentation 'process-plist  'function)
230       "A place for clients to stash things.")
231
232 #-win32
233 (defun process-wait (process &optional check-for-stopped)
234   #+sb-doc
235   "Wait for PROCESS to quit running for some reason.
236    When CHECK-FOR-STOPPED is T, also returns when PROCESS is
237    stopped.  Returns PROCESS."
238   (loop
239       (case (process-status process)
240         (:running)
241         (:stopped
242          (when check-for-stopped
243            (return)))
244         (t
245          (when (zerop (car (process-cookie process)))
246            (return))))
247       (sb-sys:serve-all-events 1))
248   process)
249
250 #-(or hpux win32)
251 ;;; Find the current foreground process group id.
252 (defun find-current-foreground-process (proc)
253   (with-alien ((result sb-alien:int))
254     (multiple-value-bind
255           (wonp error)
256         (sb-unix:unix-ioctl (sb-sys:fd-stream-fd (process-pty proc))
257                             sb-unix:TIOCGPGRP
258                             (alien-sap (sb-alien:addr result)))
259       (unless wonp
260         (error "TIOCPGRP ioctl failed: ~S" (strerror error)))
261       result))
262   (process-pid proc))
263
264 #-win32
265 (defun process-kill (process signal &optional (whom :pid))
266   #+sb-doc
267   "Hand SIGNAL to PROCESS. If WHOM is :PID, use the kill Unix system call. If
268    WHOM is :PROCESS-GROUP, use the killpg Unix system call. If WHOM is
269    :PTY-PROCESS-GROUP deliver the signal to whichever process group is
270    currently in the foreground."
271   (let ((pid (ecase whom
272                ((:pid :process-group)
273                 (process-pid process))
274                (:pty-process-group
275                 #-hpux
276                 (find-current-foreground-process process)))))
277     (multiple-value-bind
278           (okay errno)
279         (case whom
280           #+hpux
281           (:pty-process-group
282            (sb-unix:unix-ioctl (sb-sys:fd-stream-fd (process-pty process))
283                                sb-unix:TIOCSIGSEND
284                                (sb-sys:int-sap
285                                 signal)))
286           ((:process-group #-hpux :pty-process-group)
287            (sb-unix:unix-killpg pid signal))
288           (t
289            (sb-unix:unix-kill pid signal)))
290       (cond ((not okay)
291              (values nil errno))
292             ((and (eql pid (process-pid process))
293                   (= signal sb-unix:sigcont))
294              (setf (process-%status process) :running)
295              (setf (process-exit-code process) nil)
296              (when (process-status-hook process)
297                (funcall (process-status-hook process) process))
298              t)
299             (t
300              t)))))
301
302 #-win32
303 (defun process-alive-p (process)
304   #+sb-doc
305   "Return T if PROCESS is still alive, NIL otherwise."
306   (let ((status (process-status process)))
307     (if (or (eq status :running)
308             (eq status :stopped))
309         t
310         nil)))
311
312 #-win32
313 (defun process-close (process)
314   #+sb-doc
315   "Close all streams connected to PROCESS and stop maintaining the status slot."
316   (macrolet ((frob (stream abort)
317                `(when ,stream (close ,stream :abort ,abort))))
318     (frob (process-pty    process)   t) ; Don't FLUSH-OUTPUT to dead process, ..
319     (frob (process-input  process)   t) ; .. 'cause it will generate SIGPIPE.
320     (frob (process-output process) nil)
321     (frob (process-error  process) nil))
322   (with-active-processes-lock ()
323    (setf *active-processes* (delete process *active-processes*)))
324   process)
325
326 ;;; the handler for SIGCHLD signals that RUN-PROGRAM establishes
327 #-win32 (defun sigchld-handler (ignore1 ignore2 ignore3)
328   (declare (ignore ignore1 ignore2 ignore3))
329   (get-processes-status-changes))
330
331 #-win32 (defun get-processes-status-changes ()
332   (loop
333       (multiple-value-bind (pid what code core)
334           (wait3 t t)
335         (unless pid
336           (return))
337         (let ((proc (with-active-processes-lock ()
338                       (find pid *active-processes* :key #'process-pid))))
339           (when proc
340             (setf (process-%status proc) what)
341             (setf (process-exit-code proc) code)
342             (setf (process-core-dumped proc) core)
343             (when (process-status-hook proc)
344               (funcall (process-status-hook proc) proc))
345             (when (position what #(:exited :signaled))
346               (with-active-processes-lock ()
347                 (setf *active-processes*
348                       (delete proc *active-processes*)))))))))
349 \f
350 ;;;; RUN-PROGRAM and close friends
351
352 ;;; list of file descriptors to close when RUN-PROGRAM exits due to an error
353 (defvar *close-on-error* nil)
354
355 ;;; list of file descriptors to close when RUN-PROGRAM returns in the parent
356 (defvar *close-in-parent* nil)
357
358 ;;; list of handlers installed by RUN-PROGRAM
359 #-win32 (defvar *handlers-installed* nil)
360
361 ;;; Find an unused pty. Return three values: the file descriptor for
362 ;;; the master side of the pty, the file descriptor for the slave side
363 ;;; of the pty, and the name of the tty device for the slave side.
364 #-win32 (defun find-a-pty ()
365   (dolist (char '(#\p #\q))
366     (dotimes (digit 16)
367       (let* ((master-name (coerce (format nil "/dev/pty~C~X" char digit) 'base-string))
368              (master-fd (sb-unix:unix-open master-name
369                                            sb-unix:o_rdwr
370                                            #o666)))
371         (when master-fd
372           (let* ((slave-name (coerce (format nil "/dev/tty~C~X" char digit) 'base-string))
373                  (slave-fd (sb-unix:unix-open slave-name
374                                               sb-unix:o_rdwr
375                                               #o666)))
376             (when slave-fd
377               (return-from find-a-pty
378                 (values master-fd
379                         slave-fd
380                         slave-name)))
381             (sb-unix:unix-close master-fd))))))
382   (error "could not find a pty"))
383
384 #-win32 (defun open-pty (pty cookie)
385   (when pty
386     (multiple-value-bind
387           (master slave name)
388         (find-a-pty)
389       (push master *close-on-error*)
390       (push slave *close-in-parent*)
391       (when (streamp pty)
392         (multiple-value-bind (new-fd errno) (sb-unix:unix-dup master)
393           (unless new-fd
394             (error "couldn't SB-UNIX:UNIX-DUP ~W: ~A" master (strerror errno)))
395           (push new-fd *close-on-error*)
396           (copy-descriptor-to-stream new-fd pty cookie)))
397       (values name
398               (sb-sys:make-fd-stream master :input t :output t
399                                      :element-type :default
400                                      :dual-channel-p t)))))
401
402 (defmacro round-bytes-to-words (n)
403   `(logand (the fixnum (+ (the fixnum ,n) 3)) (lognot 3)))
404
405 (defun string-list-to-c-strvec (string-list)
406   ;; Make a pass over STRING-LIST to calculate the amount of memory
407   ;; needed to hold the strvec.
408   (let ((string-bytes 0)
409         ;; We need an extra for the null, and an extra 'cause exect
410         ;; clobbers argv[-1].
411         (vec-bytes (* #.(/ sb-vm::n-machine-word-bits sb-vm::n-byte-bits)
412                       (+ (length string-list) 2))))
413     (declare (fixnum string-bytes vec-bytes))
414     (dolist (s string-list)
415       (enforce-type s simple-string)
416       (incf string-bytes (round-bytes-to-words (1+ (length s)))))
417     ;; Now allocate the memory and fill it in.
418     (let* ((total-bytes (+ string-bytes vec-bytes))
419            (vec-sap (sb-sys:allocate-system-memory total-bytes))
420            (string-sap (sap+ vec-sap vec-bytes))
421            (i #.(/ sb-vm::n-machine-word-bits sb-vm::n-byte-bits)))
422       (declare (type (and unsigned-byte fixnum) total-bytes i)
423                (type sb-sys:system-area-pointer vec-sap string-sap))
424       (dolist (s string-list)
425         (declare (simple-string s))
426         (let ((n (length s)))
427           ;; Blast the string into place.
428           (sb-kernel:copy-ub8-to-system-area (the simple-base-string
429                                                ;; FIXME
430                                                (coerce s 'simple-base-string))
431                                              0
432                                              string-sap 0
433                                              (1+ n))
434           ;; Blast the pointer to the string into place.
435           (setf (sap-ref-sap vec-sap i) string-sap)
436           (setf string-sap (sap+ string-sap (round-bytes-to-words (1+ n))))
437           (incf i #.(/ sb-vm::n-machine-word-bits sb-vm::n-byte-bits))))
438       ;; Blast in the last null pointer.
439       (setf (sap-ref-sap vec-sap i) (int-sap 0))
440       (values vec-sap (sap+ vec-sap #.(/ sb-vm::n-machine-word-bits
441                                          sb-vm::n-byte-bits))
442               total-bytes))))
443
444 (defmacro with-c-strvec ((var str-list) &body body)
445   (with-unique-names (sap size)
446     `(multiple-value-bind
447       (,sap ,var ,size)
448       (string-list-to-c-strvec ,str-list)
449       (unwind-protect
450            (progn
451              ,@body)
452         (sb-sys:deallocate-system-memory ,sap ,size)))))
453
454 #-win32 (sb-alien:define-alien-routine spawn sb-alien:int
455   (program sb-alien:c-string)
456   (argv (* sb-alien:c-string))
457   (envp (* sb-alien:c-string))
458   (pty-name sb-alien:c-string)
459   (stdin sb-alien:int)
460   (stdout sb-alien:int)
461   (stderr sb-alien:int))
462
463 #+win32 (sb-alien:define-alien-routine spawn sb-win32::handle
464   (program sb-alien:c-string)
465   (argv (* sb-alien:c-string))
466   (stdin sb-alien:int)
467   (stdout sb-alien:int)
468   (stderr sb-alien:int)
469   (wait sb-alien:int))
470
471 ;;; Is UNIX-FILENAME the name of a file that we can execute?
472 #-win32 (defun unix-filename-is-executable-p (unix-filename)
473   (declare (type simple-string unix-filename))
474   (setf unix-filename (coerce unix-filename 'base-string))
475   (values (and (eq (sb-unix:unix-file-kind unix-filename) :file)
476                (sb-unix:unix-access unix-filename sb-unix:x_ok))))
477
478 (defun find-executable-in-search-path (pathname
479                                        &optional
480                                        (search-path (posix-getenv "PATH")))
481   #+sb-doc
482   "Find the first executable file matching PATHNAME in any of the
483 colon-separated list of pathnames SEARCH-PATH"
484   (loop for end =  (position #-win32 #\: #+win32 #\; search-path :start (if end (1+ end) 0))
485         and start = 0 then (and end (1+ end))
486         while start
487         ;; <Krystof> the truename of a file naming a directory is the
488         ;; directory, at least until pfdietz comes along and says why
489         ;; that's noncompliant  -- CSR, c. 2003-08-10
490         for truename = (probe-file (subseq search-path start end))
491         for fullpath = (when truename (merge-pathnames pathname truename))
492         when #-win32 (and fullpath
493                   (unix-filename-is-executable-p (namestring fullpath)))
494              #+win32 t
495         return fullpath))
496
497 ;;; FIXME: There shouldn't be two semiredundant versions of the
498 ;;; documentation. Since this is a public extension function, the
499 ;;; documentation should be in the doc string. So all information from
500 ;;; this comment should be merged into the doc string, and then this
501 ;;; comment can go away.
502 ;;;
503 ;;; RUN-PROGRAM uses fork() and execve() to run a different program.
504 ;;; Strange stuff happens to keep the Unix state of the world
505 ;;; coherent.
506 ;;;
507 ;;; The child process needs to get its input from somewhere, and send
508 ;;; its output (both standard and error) to somewhere. We have to do
509 ;;; different things depending on where these somewheres really are.
510 ;;;
511 ;;; For input, there are five options:
512 ;;;  -- T: Just leave fd 0 alone. Pretty simple.
513 ;;;  -- "file": Read from the file. We need to open the file and
514 ;;;     pull the descriptor out of the stream. The parent should close
515 ;;;     this stream after the child is up and running to free any
516 ;;;     storage used in the parent.
517 ;;;  -- NIL: Same as "file", but use "/dev/null" as the file.
518 ;;;  -- :STREAM: Use Unix pipe() to create two descriptors. Use
519 ;;;     SB-SYS:MAKE-FD-STREAM to create the output stream on the
520 ;;;     writeable descriptor, and pass the readable descriptor to
521 ;;;     the child. The parent must close the readable descriptor for
522 ;;;     EOF to be passed up correctly.
523 ;;;  -- a stream: If it's a fd-stream, just pull the descriptor out
524 ;;;     of it. Otherwise make a pipe as in :STREAM, and copy
525 ;;;     everything across.
526 ;;;
527 ;;; For output, there are five options:
528 ;;;  -- T: Leave descriptor 1 alone.
529 ;;;  -- "file": dump output to the file.
530 ;;;  -- NIL: dump output to /dev/null.
531 ;;;  -- :STREAM: return a stream that can be read from.
532 ;;;  -- a stream: if it's a fd-stream, use the descriptor in it.
533 ;;;     Otherwise, copy stuff from output to stream.
534 ;;;
535 ;;; For error, there are all the same options as output plus:
536 ;;;  -- :OUTPUT: redirect to the same place as output.
537 ;;;
538 ;;; RUN-PROGRAM returns a PROCESS structure for the process if
539 ;;; the fork worked, and NIL if it did not.
540
541 #-win32 (defun run-program (program args
542                     &key
543                     (env nil env-p)
544                     (environment (if env-p
545                                      (unix-environment-sbcl-from-cmucl env)
546                                      (posix-environ))
547                                  environment-p)
548                     (wait t)
549                     search
550                     pty
551                     input
552                     if-input-does-not-exist
553                     output
554                     (if-output-exists :error)
555                     (error :output)
556                     (if-error-exists :error)
557                     status-hook)
558   #+sb-doc
559   "RUN-PROGRAM creates a new Unix process running the Unix program found in
560    the file specified by the PROGRAM argument.  ARGS are the standard
561    arguments that can be passed to a Unix program. For no arguments, use NIL
562    (which means that just the name of the program is passed as arg 0).
563
564    RUN-PROGRAM will return a PROCESS structure or NIL on failure.
565    See the CMU Common Lisp Users Manual for details about the
566    PROCESS structure.
567
568    Notes about Unix environments (as in the :ENVIRONMENT and :ENV args):
569
570    - The SBCL implementation of RUN-PROGRAM, like Perl and many other
571      programs, but unlike the original CMU CL implementation, copies
572      the Unix environment by default.
573
574    - Running Unix programs from a setuid process, or in any other
575      situation where the Unix environment is under the control of someone
576      else, is a mother lode of security problems. If you are contemplating
577      doing this, read about it first. (The Perl community has a lot of good
578      documentation about this and other security issues in script-like
579      programs.)
580
581    The &KEY arguments have the following meanings:
582
583    :ENVIRONMENT
584       a list of SIMPLE-BASE-STRINGs describing the new Unix environment
585       (as in \"man environ\"). The default is to copy the environment of
586       the current process.
587    :ENV
588       an alternative lossy representation of the new Unix environment,
589       for compatibility with CMU CL
590    :SEARCH
591       Look for PROGRAM in each of the directories along the $PATH
592       environment variable.  Otherwise an absolute pathname is required.
593       (See also FIND-EXECUTABLE-IN-SEARCH-PATH)
594    :WAIT
595       If non-NIL (default), wait until the created process finishes.  If
596       NIL, continue running Lisp until the program finishes.
597    :PTY
598       Either T, NIL, or a stream.  Unless NIL, the subprocess is established
599       under a PTY.  If :pty is a stream, all output to this pty is sent to
600       this stream, otherwise the PROCESS-PTY slot is filled in with a stream
601       connected to pty that can read output and write input.
602    :INPUT
603       Either T, NIL, a pathname, a stream, or :STREAM.  If T, the standard
604       input for the current process is inherited.  If NIL, /dev/null
605       is used.  If a pathname, the file so specified is used.  If a stream,
606       all the input is read from that stream and send to the subprocess.  If
607       :STREAM, the PROCESS-INPUT slot is filled in with a stream that sends
608       its output to the process. Defaults to NIL.
609    :IF-INPUT-DOES-NOT-EXIST (when :INPUT is the name of a file)
610       can be one of:
611          :ERROR to generate an error
612          :CREATE to create an empty file
613          NIL (the default) to return NIL from RUN-PROGRAM
614    :OUTPUT
615       Either T, NIL, a pathname, a stream, or :STREAM.  If T, the standard
616       output for the current process is inherited.  If NIL, /dev/null
617       is used.  If a pathname, the file so specified is used.  If a stream,
618       all the output from the process is written to this stream. If
619       :STREAM, the PROCESS-OUTPUT slot is filled in with a stream that can
620       be read to get the output. Defaults to NIL.
621    :IF-OUTPUT-EXISTS (when :OUTPUT is the name of a file)
622       can be one of:
623          :ERROR (the default) to generate an error
624          :SUPERSEDE to supersede the file with output from the program
625          :APPEND to append output from the program to the file
626          NIL to return NIL from RUN-PROGRAM, without doing anything
627    :ERROR and :IF-ERROR-EXISTS
628       Same as :OUTPUT and :IF-OUTPUT-EXISTS, except that :ERROR can also be
629       specified as :OUTPUT in which case all error output is routed to the
630       same place as normal output.
631    :STATUS-HOOK
632       This is a function the system calls whenever the status of the
633       process changes.  The function takes the process as an argument."
634
635   (when (and env-p environment-p)
636     (error "can't specify :ENV and :ENVIRONMENT simultaneously"))
637   ;; Make sure that the interrupt handler is installed.
638   (sb-sys:enable-interrupt sb-unix:sigchld #'sigchld-handler)
639   ;; Prepend the program to the argument list.
640   (push (namestring program) args)
641   (let (;; Clear various specials used by GET-DESCRIPTOR-FOR to
642         ;; communicate cleanup info.
643         *close-on-error*
644         *close-in-parent*
645         *handlers-installed*
646         ;; Establish PROC at this level so that we can return it.
647         proc
648         ;; It's friendly to allow the caller to pass any string
649         ;; designator, but internally we'd like SIMPLE-STRINGs.
650         (simple-args (mapcar (lambda (x) (coerce x 'simple-string)) args)))
651     (unwind-protect
652          (let ((pfile
653                 (if search
654                     (let ((p (find-executable-in-search-path program)))
655                       (and p (unix-namestring p t)))
656                     (unix-namestring program t)))
657                (cookie (list 0)))
658            (unless pfile
659              (error "no such program: ~S" program))
660            (unless (unix-filename-is-executable-p pfile)
661              (error "not executable: ~S" program))
662            (multiple-value-bind (stdin input-stream)
663                (get-descriptor-for input cookie
664                                    :direction :input
665                                    :if-does-not-exist if-input-does-not-exist)
666              (multiple-value-bind (stdout output-stream)
667                  (get-descriptor-for output cookie
668                                      :direction :output
669                                      :if-exists if-output-exists)
670                (multiple-value-bind (stderr error-stream)
671                    (if (eq error :output)
672                        (values stdout output-stream)
673                        (get-descriptor-for error cookie
674                                            :direction :output
675                                            :if-exists if-error-exists))
676                  (multiple-value-bind (pty-name pty-stream)
677                      (open-pty pty cookie)
678                    ;; Make sure we are not notified about the child
679                    ;; death before we have installed the PROCESS
680                    ;; structure in *ACTIVE-PROCESSES*.
681                    (with-active-processes-lock ()
682                     (with-c-strvec (args-vec simple-args)
683                       (with-c-strvec (environment-vec environment)
684                         (let ((child-pid
685                                (without-gcing
686                                 (spawn pfile args-vec environment-vec pty-name
687                                        stdin stdout stderr))))
688                           (when (< child-pid 0)
689                             (error "couldn't fork child process: ~A"
690                                    (strerror)))
691                           (setf proc (make-process :pid child-pid
692                                                    :%status :running
693                                                    :pty pty-stream
694                                                    :input input-stream
695                                                    :output output-stream
696                                                    :error error-stream
697                                                    :status-hook status-hook
698                                                    :cookie cookie))
699                           (push proc *active-processes*))))))))))
700       (dolist (fd *close-in-parent*)
701         (sb-unix:unix-close fd))
702       (unless proc
703         (dolist (fd *close-on-error*)
704           (sb-unix:unix-close fd))
705         (dolist (handler *handlers-installed*)
706           (sb-sys:remove-fd-handler handler))))
707     (when (and wait proc)
708       (process-wait proc))
709     proc))
710
711 #+win32 (defun run-program (program args
712                     &key
713                     (wait t)
714                     search
715                     input
716                     if-input-does-not-exist
717                     output
718                     (if-output-exists :error)
719                     (error :output)
720                     (if-error-exists :error)
721                     status-hook)
722   "RUN-PROGRAM creates a new process specified by the PROGRAM argument.
723    ARGS are the standard arguments that can be passed to a program. For no
724    arguments, use NIL (which means that just the name of the program is
725    passed as arg 0).
726
727    RUN-PROGRAM will either return NIL or a PROCESS structure.  See the CMU
728    Common Lisp Users Manual for details about the PROCESS structure.
729
730    The &KEY arguments have the following meanings:
731      :SEARCH
732         Look for PROGRAM in each of the directories along the $PATH
733         environment variable.  Otherwise an absolute pathname is required.
734         (See also FIND-EXECUTABLE-IN-SEARCH-PATH)
735      :WAIT
736         If non-NIL (default), wait until the created process finishes.  If
737         NIL, continue running Lisp until the program finishes.
738      :INPUT
739         Either T, NIL, a pathname, a stream, or :STREAM.  If T, the standard
740         input for the current process is inherited.  If NIL, /dev/null
741         is used.  If a pathname, the file so specified is used.  If a stream,
742         all the input is read from that stream and send to the subprocess.  If
743         :STREAM, the PROCESS-INPUT slot is filled in with a stream that sends
744         its output to the process. Defaults to NIL.
745      :IF-INPUT-DOES-NOT-EXIST (when :INPUT is the name of a file)
746         can be one of:
747            :ERROR to generate an error
748            :CREATE to create an empty file
749            NIL (the default) to return NIL from RUN-PROGRAM
750      :OUTPUT
751         Either T, NIL, a pathname, a stream, or :STREAM.  If T, the standard
752         output for the current process is inherited.  If NIL, /dev/null
753         is used.  If a pathname, the file so specified is used.  If a stream,
754         all the output from the process is written to this stream. If
755         :STREAM, the PROCESS-OUTPUT slot is filled in with a stream that can
756         be read to get the output. Defaults to NIL.
757      :IF-OUTPUT-EXISTS (when :OUTPUT is the name of a file)
758         can be one of:
759            :ERROR (the default) to generate an error
760            :SUPERSEDE to supersede the file with output from the program
761            :APPEND to append output from the program to the file
762            NIL to return NIL from RUN-PROGRAM, without doing anything
763      :ERROR and :IF-ERROR-EXISTS
764         Same as :OUTPUT and :IF-OUTPUT-EXISTS, except that :ERROR can also be
765         specified as :OUTPUT in which case all error output is routed to the
766         same place as normal output.
767      :STATUS-HOOK
768         This is a function the system calls whenever the status of the
769         process changes.  The function takes the process as an argument."
770
771   ;; Prepend the program to the argument list.
772   (push (namestring program) args)
773   (let (;; Clear various specials used by GET-DESCRIPTOR-FOR to
774         ;; communicate cleanup info.
775         *close-on-error*
776         *close-in-parent*
777         ;; Establish PROC at this level so that we can return it.
778         proc
779         ;; It's friendly to allow the caller to pass any string
780         ;; designator, but internally we'd like SIMPLE-STRINGs.
781         (simple-args (mapcar (lambda (x) (coerce x 'simple-string)) args)))
782     (unwind-protect
783          (let ((pfile
784                 (if search
785                     (namestring (find-executable-in-search-path program))
786                     (namestring program)))
787                (cookie (list 0)))
788            (unless pfile
789              (error "no such program: ~S" program))
790            (multiple-value-bind (stdin input-stream)
791                (get-descriptor-for input cookie
792                                    :direction :input
793                                    :if-does-not-exist if-input-does-not-exist)
794              (multiple-value-bind (stdout output-stream)
795                  (get-descriptor-for output cookie
796                                      :direction :output
797                                      :if-exists if-output-exists)
798                (multiple-value-bind (stderr error-stream)
799                    (if (eq error :output)
800                        (values stdout output-stream)
801                        (get-descriptor-for error cookie
802                                            :direction :output
803                                            :if-exists if-error-exists))
804                     (with-c-strvec (args-vec simple-args)
805                         (let ((iwait (if wait 1 0)))
806                           (declare (type fixnum iwait))
807                           (let ((child-pid
808                                  (without-gcing
809                                   (spawn pfile args-vec
810                                          stdin stdout stderr
811                                          iwait))))
812                             (when (< child-pid 0)
813                               (error "couldn't spawn program: ~A"
814                                      (strerror)))
815                             (setf proc
816                                   (if wait
817                                       nil
818                                     (make-process :pid child-pid
819                                                   :%status :running
820                                                   :input input-stream
821                                                   :output output-stream
822                                                   :error error-stream
823                                                   :status-hook status-hook
824                                                   :cookie cookie)))))))))))
825     proc))
826
827 ;;; Install a handler for any input that shows up on the file
828 ;;; descriptor. The handler reads the data and writes it to the
829 ;;; stream.
830 (defun copy-descriptor-to-stream (descriptor stream cookie)
831   (incf (car cookie))
832   (let ((string (make-string 256 :element-type 'base-char))
833         handler)
834     (setf handler
835           (sb-sys:add-fd-handler
836            descriptor
837            :input (lambda (fd)
838                     (declare (ignore fd))
839                     (loop
840                      (unless handler
841                        (return))
842                      (multiple-value-bind
843                          (result readable/errno)
844                          (sb-unix:unix-select (1+ descriptor)
845                                               (ash 1 descriptor)
846                                               0 0 0)
847                        (cond ((null result)
848                               (error "~@<couldn't select on sub-process: ~
849                                            ~2I~_~A~:>"
850                                      (strerror readable/errno)))
851                              ((zerop result)
852                               (return))))
853                      (sb-alien:with-alien ((buf (sb-alien:array
854                                                  sb-alien:char
855                                                  256)))
856                        (multiple-value-bind
857                            (count errno)
858                            (sb-unix:unix-read descriptor
859                                               (alien-sap buf)
860                                               256)
861                            (cond (#-win32(or (and (null count)
862                                                   (eql errno sb-unix:eio))
863                                              (eql count 0))
864                                          #+win32(<= count 0)
865                                 (sb-sys:remove-fd-handler handler)
866                                 (setf handler nil)
867                                 (decf (car cookie))
868                                 (sb-unix:unix-close descriptor)
869                                 (return))
870                                ((null count)
871                                 (sb-sys:remove-fd-handler handler)
872                                 (setf handler nil)
873                                 (decf (car cookie))
874                                 (error
875                                  "~@<couldn't read input from sub-process: ~
876                                      ~2I~_~A~:>"
877                                  (strerror errno)))
878                                (t
879                                 (sb-kernel:copy-ub8-from-system-area
880                                  (alien-sap buf) 0
881                                  string 0
882                                  count)
883                                 (write-string string stream
884                                               :end count)))))))))))
885
886 ;;; Find a file descriptor to use for object given the direction.
887 ;;; Returns the descriptor. If object is :STREAM, returns the created
888 ;;; stream as the second value.
889 (defun get-descriptor-for (object
890                            cookie
891                            &rest keys
892                            &key direction
893                            &allow-other-keys)
894   (cond ((eq object t)
895          ;; No new descriptor is needed.
896          (values -1 nil))
897         ((eq object nil)
898          ;; Use /dev/null.
899          (multiple-value-bind
900                (fd errno)
901              (sb-unix:unix-open #-win32 #.(coerce "/dev/null" 'base-string)
902                                 #+win32 #.(coerce "nul" 'base-string)
903                                 (case direction
904                                   (:input sb-unix:o_rdonly)
905                                   (:output sb-unix:o_wronly)
906                                   (t sb-unix:o_rdwr))
907                                 #o666)
908            (unless fd
909              (error "~@<couldn't open \"/dev/null\": ~2I~_~A~:>"
910                     (strerror errno)))
911            (push fd *close-in-parent*)
912            (values fd nil)))
913         ((eq object :stream)
914          (multiple-value-bind (read-fd write-fd) (sb-unix:unix-pipe)
915            (unless read-fd
916              (error "couldn't create pipe: ~A" (strerror write-fd)))
917            (case direction
918              (:input
919               (push read-fd *close-in-parent*)
920               (push write-fd *close-on-error*)
921               (let ((stream (sb-sys:make-fd-stream write-fd :output t
922                                                    :element-type :default)))
923                 (values read-fd stream)))
924              (:output
925               (push read-fd *close-on-error*)
926               (push write-fd *close-in-parent*)
927               (let ((stream (sb-sys:make-fd-stream read-fd :input t
928                                                    :element-type :default)))
929                 (values write-fd stream)))
930              (t
931               (sb-unix:unix-close read-fd)
932               (sb-unix:unix-close write-fd)
933               (error "Direction must be either :INPUT or :OUTPUT, not ~S."
934                      direction)))))
935         ((or (pathnamep object) (stringp object))
936          (with-open-stream (file (apply #'open object keys))
937            (multiple-value-bind
938                  (fd errno)
939                (sb-unix:unix-dup (sb-sys:fd-stream-fd file))
940              (cond (fd
941                     (push fd *close-in-parent*)
942                     (values fd nil))
943                    (t
944                     (error "couldn't duplicate file descriptor: ~A"
945                            (strerror errno)))))))
946         ((sb-sys:fd-stream-p object)
947          (values (sb-sys:fd-stream-fd object) nil))
948         ((streamp object)
949          (ecase direction
950            (:input
951             ;; FIXME: We could use a better way of setting up
952             ;; temporary files, both here and in LOAD-FOREIGN.
953             (dotimes (count
954                        256
955                       (error "could not open a temporary file in /tmp"))
956               (let* ((name (coerce (format nil "/tmp/.run-program-~D" count) 'base-string))
957                      (fd (sb-unix:unix-open name
958                                             (logior sb-unix:o_rdwr
959                                                     sb-unix:o_creat
960                                                     sb-unix:o_excl)
961                                             #o666)))
962                 (sb-unix:unix-unlink name)
963                 (when fd
964                   (let ((newline (string #\Newline)))
965                     (loop
966                         (multiple-value-bind
967                               (line no-cr)
968                             (read-line object nil nil)
969                           (unless line
970                             (return))
971                           (sb-unix:unix-write
972                            fd
973                            ;; FIXME: this really should be
974                            ;; (STRING-TO-OCTETS :EXTERNAL-FORMAT ...).
975                            ;; RUN-PROGRAM should take an
976                            ;; external-format argument, which should
977                            ;; be passed down to here.  Something
978                            ;; similar should happen on :OUTPUT, too.
979                            (map '(vector (unsigned-byte 8)) #'char-code line)
980                            0 (length line))
981                           (if no-cr
982                               (return)
983                               (sb-unix:unix-write fd newline 0 1)))))
984                   (sb-unix:unix-lseek fd 0 sb-unix:l_set)
985                   (push fd *close-in-parent*)
986                   (return (values fd nil))))))
987            (:output
988             (multiple-value-bind (read-fd write-fd)
989                 (sb-unix:unix-pipe)
990               (unless read-fd
991                 (error "couldn't create pipe: ~S" (strerror write-fd)))
992               (copy-descriptor-to-stream read-fd object cookie)
993               (push read-fd *close-on-error*)
994               (push write-fd *close-in-parent*)
995               (values write-fd nil)))))
996         (t
997          (error "invalid option to RUN-PROGRAM: ~S" object))))