Handle run-program with :directory nil.
[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
49 (progn
50   (define-alien-routine wrapped-environ (* c-string))
51   (defun posix-environ ()
52     "Return the Unix environment (\"man environ\") as a list of SIMPLE-STRINGs."
53     (c-strings->string-list (wrapped-environ))))
54
55 #+win32
56 (progn
57   (defun decode-windows-environment (environment)
58     (loop until (zerop (sap-ref-8 environment 0))
59           collect
60           (let ((string (sb-alien::c-string-to-string environment
61                                                       (sb-alien::default-c-string-external-format)
62                                                       'character)))
63             (loop for value = (sap-ref-8 environment 0)
64                   do (setf environment (sap+ environment 1))
65                   until (zerop value))
66             string)))
67
68   (defun encode-windows-environment (list)
69     (let* ((external-format (sb-alien::default-c-string-external-format))
70            octets
71            (length 1)) ;; 1 for \0 at the very end
72       (setf octets
73             (loop for x in list
74                   for octet =
75                   (string-to-octets x :external-format external-format
76                                       :null-terminate t)
77                   collect octet
78                   do
79                   (incf length (length octet))))
80       (let ((mem (allocate-system-memory length))
81             (index 0))
82
83         (loop for string in octets
84               for length = (length string)
85               do
86               (copy-ub8-to-system-area string 0 mem index length)
87               (incf index length))
88         (setf (sap-ref-8 mem index) 0)
89         (values mem mem length))))
90
91   (defun posix-environ ()
92     (decode-windows-environment
93      (alien-funcall (extern-alien "GetEnvironmentStrings"
94                                   (function system-area-pointer))))))
95
96 ;;; Convert from a CMU CL representation of a Unix environment to a
97 ;;; SBCL representation.
98 (defun unix-environment-sbcl-from-cmucl (cmucl)
99   (mapcar
100    (lambda (cons)
101      (destructuring-bind (key . val) cons
102        (declare (type keyword key) (string val))
103        (concatenate 'simple-string (symbol-name key) "=" val)))
104    cmucl))
105 \f
106 ;;;; Import wait3(2) from Unix.
107
108 #-win32
109 (define-alien-routine ("waitpid" c-waitpid) int
110   (pid int)
111   (status int :out)
112   (options int))
113
114 #-win32
115 (defun waitpid (pid &optional do-not-hang check-for-stopped)
116   #+sb-doc
117   "Return any available status information on child process with PID."
118   (multiple-value-bind (pid status)
119       (c-waitpid pid
120                  (logior (if do-not-hang
121                              sb-unix:wnohang
122                              0)
123                          (if check-for-stopped
124                              sb-unix:wuntraced
125                              0)))
126     (cond ((or (minusp pid)
127                (zerop pid))
128            nil)
129           ((eql (ldb (byte 8 0) status)
130                 sb-unix:wstopped)
131            (values pid
132                    :stopped
133                    (ldb (byte 8 8) status)))
134           ((zerop (ldb (byte 7 0) status))
135            (values pid
136                    :exited
137                    (ldb (byte 8 8) status)))
138           (t
139            (let ((signal (ldb (byte 7 0) status)))
140              (values pid
141                      (if (position signal
142                                    #.(vector
143                                       sb-unix:sigstop
144                                       sb-unix:sigtstp
145                                       sb-unix:sigttin
146                                       sb-unix:sigttou))
147                          :stopped
148                          :signaled)
149                      signal
150                      (not (zerop (ldb (byte 1 7) status)))))))))
151 \f
152 ;;;; process control stuff
153 (defvar *active-processes* nil
154   #+sb-doc
155   "List of process structures for all active processes.")
156
157 (defvar *active-processes-lock*
158   (sb-thread:make-mutex :name "Lock for active processes."))
159
160 ;;; *ACTIVE-PROCESSES* can be accessed from multiple threads so a
161 ;;; mutex is needed. More importantly the sigchld signal handler also
162 ;;; accesses it, that's why we need without-interrupts.
163 (defmacro with-active-processes-lock (() &body body)
164   `(sb-thread::with-system-mutex (*active-processes-lock*)
165      ,@body))
166
167 (defstruct (process (:copier nil))
168   pid                 ; PID of child process
169   %status             ; either :RUNNING, :STOPPED, :EXITED, or :SIGNALED
170   %exit-code          ; either exit code or signal
171   core-dumped         ; T if a core image was dumped
172   #-win32 pty                 ; stream to child's pty, or NIL
173   input               ; stream to child's input, or NIL
174   output              ; stream from child's output, or NIL
175   error               ; stream from child's error output, or NIL
176   status-hook         ; closure to call when PROC changes status
177   plist               ; a place for clients to stash things
178   cookie)             ; list of the number of pipes from the subproc
179
180 (defmethod print-object ((process process) stream)
181   (print-unreadable-object (process stream :type t)
182     (let ((status (process-status process)))
183      (if (eq :exited status)
184          (format stream "~S ~S" status (process-%exit-code process))
185          (format stream "~S ~S" (process-pid process) status)))
186     process))
187
188 #+sb-doc
189 (setf (documentation 'process-p 'function)
190       "T if OBJECT is a PROCESS, NIL otherwise.")
191
192 #+sb-doc
193 (setf (documentation 'process-pid 'function) "The pid of the child process.")
194
195 #+win32
196 (define-alien-routine ("GetExitCodeProcess" get-exit-code-process)
197     int
198   (handle unsigned) (exit-code unsigned :out))
199
200 (defun process-exit-code (process)
201   #+sb-doc
202   "Return the exit code of PROCESS."
203   (or (process-%exit-code process)
204       (progn (get-processes-status-changes)
205              (process-%exit-code process))))
206
207 (defun process-status (process)
208   #+sb-doc
209   "Return the current status of PROCESS.  The result is one of :RUNNING,
210    :STOPPED, :EXITED, or :SIGNALED."
211   (get-processes-status-changes)
212   (process-%status process))
213
214 #+sb-doc
215 (setf (documentation 'process-exit-code 'function)
216       "The exit code or the signal of a stopped process.")
217
218 #+sb-doc
219 (setf (documentation 'process-core-dumped 'function)
220       "T if a core image was dumped by the process.")
221
222 #+sb-doc
223 (setf (documentation 'process-pty 'function)
224       "The pty stream of the process or NIL.")
225
226 #+sb-doc
227 (setf (documentation 'process-input 'function)
228       "The input stream of the process or NIL.")
229
230 #+sb-doc
231 (setf (documentation 'process-output 'function)
232       "The output stream of the process or NIL.")
233
234 #+sb-doc
235 (setf (documentation 'process-error 'function)
236       "The error stream of the process or NIL.")
237
238 #+sb-doc
239 (setf (documentation 'process-status-hook  'function)
240       "A function that is called when PROCESS changes its status.
241 The function is called with PROCESS as its only argument.")
242
243 #+sb-doc
244 (setf (documentation 'process-plist  'function)
245       "A place for clients to stash things.")
246
247 (defun process-wait (process &optional check-for-stopped)
248   #+sb-doc
249   "Wait for PROCESS to quit running for some reason. When
250 CHECK-FOR-STOPPED is T, also returns when PROCESS is stopped. Returns
251 PROCESS."
252   (declare (ignorable check-for-stopped))
253   #+win32
254   (let ((pid (process-pid process)))
255     (when (and pid (plusp pid))
256       (without-interrupts
257         (do ()
258             ((= 0
259                 (with-local-interrupts
260                   (sb-win32:wait-object-or-signal pid))))))))
261   #-win32
262   (loop
263       (case (process-status process)
264         (:running)
265         (:stopped
266          (when check-for-stopped
267            (return)))
268         (t
269          (when (zerop (car (process-cookie process)))
270            (return))))
271       (serve-all-events 1))
272   process)
273
274 #-win32
275 ;;; Find the current foreground process group id.
276 (defun find-current-foreground-process (proc)
277   (with-alien ((result int))
278     (multiple-value-bind
279           (wonp error)
280         (sb-unix:unix-ioctl (fd-stream-fd (process-pty proc))
281                             sb-unix:TIOCGPGRP
282                             (alien-sap (addr result)))
283       (unless wonp
284         (error "TIOCPGRP ioctl failed: ~S" (strerror error)))
285       result))
286   (process-pid proc))
287
288 #-win32
289 (defun process-kill (process signal &optional (whom :pid))
290   #+sb-doc
291   "Hand SIGNAL to PROCESS. If WHOM is :PID, use the kill Unix system call. If
292    WHOM is :PROCESS-GROUP, use the killpg Unix system call. If WHOM is
293    :PTY-PROCESS-GROUP deliver the signal to whichever process group is
294    currently in the foreground."
295   (let ((pid (ecase whom
296                ((:pid :process-group)
297                 (process-pid process))
298                (:pty-process-group
299                 (find-current-foreground-process process)))))
300     (multiple-value-bind
301           (okay errno)
302         (case whom
303           ((:process-group)
304            (sb-unix:unix-killpg pid signal))
305           (t
306            (sb-unix:unix-kill pid signal)))
307       (cond ((not okay)
308              (values nil errno))
309             ((and (eql pid (process-pid process))
310                   (= signal sb-unix:sigcont))
311              (setf (process-%status process) :running)
312              (setf (process-%exit-code process) nil)
313              (when (process-status-hook process)
314                (funcall (process-status-hook process) process))
315              t)
316             (t
317              t)))))
318
319 (defun process-alive-p (process)
320   #+sb-doc
321   "Return T if PROCESS is still alive, NIL otherwise."
322   (let ((status (process-status process)))
323     (if (or (eq status :running)
324             (eq status :stopped))
325         t
326         nil)))
327
328 (defun process-close (process)
329   #+sb-doc
330   "Close all streams connected to PROCESS and stop maintaining the
331 status slot."
332   (macrolet ((frob (stream abort)
333                `(when ,stream (close ,stream :abort ,abort))))
334     #-win32
335     (frob (process-pty process) t)   ; Don't FLUSH-OUTPUT to dead process,
336     (frob (process-input process) t) ; .. 'cause it will generate SIGPIPE.
337     (frob (process-output process) nil)
338     (frob (process-error process) nil))
339   ;; FIXME: Given that the status-slot is no longer updated,
340   ;; maybe it should be set to :CLOSED, or similar?
341   (with-active-processes-lock ()
342    (setf *active-processes* (delete process *active-processes*)))
343   #+win32
344   (let ((handle (shiftf (process-pid process) nil)))
345     (when (and handle (plusp handle))
346       (or (sb-win32:close-handle handle)
347           (sb-win32::win32-error 'process-close))))
348   process)
349
350 (defun get-processes-status-changes ()
351   (let (exited)
352     (with-active-processes-lock ()
353       (setf *active-processes*
354             (delete-if #-win32
355                        (lambda (proc)
356                          ;; Wait only on pids belonging to processes
357                          ;; started by RUN-PROGRAM. There used to be a
358                          ;; WAIT3 call here, but that makes direct
359                          ;; WAIT, WAITPID usage impossible due to the
360                          ;; race with the SIGCHLD signal handler.
361                          (multiple-value-bind (pid what code core)
362                              (waitpid (process-pid proc) t t)
363                            (when pid
364                              (setf (process-%status proc) what)
365                              (setf (process-%exit-code proc) code)
366                              (setf (process-core-dumped proc) core)
367                              (when (process-status-hook proc)
368                                (push proc exited))
369                              t)))
370                        #+win32
371                        (lambda (proc)
372                          (let ((pid (process-pid proc)))
373                            (when pid
374                              (multiple-value-bind (ok code)
375                                  (sb-win32::get-exit-code-process pid)
376                                (when (and (plusp ok) (/= code 259))
377                                  (setf (process-%status proc) :exited
378                                        (process-%exit-code proc) code)
379                                  (when (process-status-hook proc)
380                                    (push proc exited))
381                                  t)))))
382                        *active-processes*)))
383     ;; Can't call the hooks before all the processes have been deal
384     ;; with, as calling a hook may cause re-entry to
385     ;; GET-PROCESS-STATUS-CHANGES. That may be OK when using waitpid,
386     ;; but in the Windows implementation it would be deeply bad.
387     (dolist (proc exited)
388       (let ((hook (process-status-hook proc)))
389         (when hook
390           (funcall hook proc))))))
391 \f
392 ;;;; RUN-PROGRAM and close friends
393
394 ;;; list of file descriptors to close when RUN-PROGRAM exits due to an error
395 (defvar *close-on-error* nil)
396
397 ;;; list of file descriptors to close when RUN-PROGRAM returns in the parent
398 (defvar *close-in-parent* nil)
399
400 ;;; list of handlers installed by RUN-PROGRAM.  FIXME: nothing seems
401 ;;; to set this.
402 #-win32
403 (defvar *handlers-installed* nil)
404
405 ;;; Find an unused pty. Return three values: the file descriptor for
406 ;;; the master side of the pty, the file descriptor for the slave side
407 ;;; of the pty, and the name of the tty device for the slave side.
408 #-(or win32 openbsd)
409 (progn
410   (define-alien-routine ptsname c-string (fd int))
411   (define-alien-routine grantpt boolean (fd int))
412   (define-alien-routine unlockpt boolean (fd int))
413
414   (defun find-a-pty ()
415     ;; First try to use the Unix98 pty api.
416     (let* ((master-name (coerce (format nil "/dev/ptmx") 'base-string))
417            (master-fd (sb-unix:unix-open master-name
418                                          (logior sb-unix:o_rdwr
419                                                  sb-unix:o_noctty)
420                                          #o666)))
421       (when master-fd
422         (grantpt master-fd)
423         (unlockpt master-fd)
424         (let* ((slave-name (ptsname master-fd))
425                (slave-fd (sb-unix:unix-open slave-name
426                                             (logior sb-unix:o_rdwr
427                                                     sb-unix:o_noctty)
428                                             #o666)))
429           (when slave-fd
430             (return-from find-a-pty
431               (values master-fd
432                       slave-fd
433                       slave-name)))
434           (sb-unix:unix-close master-fd))
435         (error "could not find a pty")))
436     ;; No dice, try using the old-school method.
437     (dolist (char '(#\p #\q))
438       (dotimes (digit 16)
439         (let* ((master-name (coerce (format nil "/dev/pty~C~X" char digit)
440                                     'base-string))
441                (master-fd (sb-unix:unix-open master-name
442                                              (logior sb-unix:o_rdwr
443                                                      sb-unix:o_noctty)
444                                              #o666)))
445           (when master-fd
446             (let* ((slave-name (coerce (format nil "/dev/tty~C~X" char digit)
447                                        'base-string))
448                    (slave-fd (sb-unix:unix-open slave-name
449                                                 (logior sb-unix:o_rdwr
450                                                         sb-unix:o_noctty)
451                                                 #o666)))
452               (when slave-fd
453                 (return-from find-a-pty
454                   (values master-fd
455                           slave-fd
456                           slave-name)))
457               (sb-unix:unix-close master-fd))))))
458     (error "could not find a pty")))
459 #+openbsd
460 (progn
461   (define-alien-routine openpty int (amaster int :out) (aslave int :out)
462                         (name (* char)) (termp (* t)) (winp (* t)))
463   (defun find-a-pty ()
464     (with-alien ((name-buf (array char 16)))
465       (multiple-value-bind (return-val master-fd slave-fd)
466           (openpty (cast name-buf (* char)) nil nil)
467         (if (zerop return-val)
468             (values master-fd
469                     slave-fd
470                     (sb-alien::c-string-to-string (alien-sap name-buf)
471                                                   (sb-impl::default-external-format)
472                                                   'character))
473             (error "could not find a pty"))))))
474
475 #-win32
476 (defun open-pty (pty cookie &key (external-format :default))
477   (when pty
478     (multiple-value-bind
479           (master slave name)
480         (find-a-pty)
481       (push master *close-on-error*)
482       (push slave *close-in-parent*)
483       (when (streamp pty)
484         (multiple-value-bind (new-fd errno) (sb-unix:unix-dup master)
485           (unless new-fd
486             (error "couldn't SB-UNIX:UNIX-DUP ~W: ~A" master (strerror errno)))
487           (push new-fd *close-on-error*)
488           (copy-descriptor-to-stream new-fd pty cookie external-format)))
489       (values name
490               (make-fd-stream master :input t :output t
491                                      :external-format external-format
492                                      :element-type :default
493                                      :dual-channel-p t)))))
494
495 ;; Null terminate strings only C-side: otherwise we can run into
496 ;; A-T-S-L even for simple encodings like ASCII.  Multibyte encodings
497 ;; may need more than a single byte of zeros; assume 4 byte is enough
498 ;; for everyone.
499 #-win32
500 (defmacro round-null-terminated-bytes-to-words (n)
501   `(logandc2 (the sb-vm:signed-word (+ (the fixnum ,n)
502                                        4 (1- sb-vm:n-word-bytes)))
503              (1- sb-vm:n-word-bytes)))
504
505 #-win32
506 (defun string-list-to-c-strvec (string-list)
507   (let* (;; We need an extra for the null, and an extra 'cause exect
508          ;; clobbers argv[-1].
509          (vec-bytes (* sb-vm:n-word-bytes (+ (length string-list) 2)))
510          (octet-vector-list (mapcar (lambda (s)
511                                       (string-to-octets s))
512                                     string-list))
513          (string-bytes (reduce #'+ octet-vector-list
514                                :key (lambda (s)
515                                       (round-null-terminated-bytes-to-words
516                                        (length s)))))
517          (total-bytes (+ string-bytes vec-bytes))
518          ;; Memory to hold the vector of pointers and all the strings.
519          (vec-sap (allocate-system-memory total-bytes))
520          (string-sap (sap+ vec-sap vec-bytes))
521          ;; Index starts from [1]!
522          (vec-index-offset sb-vm:n-word-bytes))
523     (declare (sb-vm:signed-word vec-bytes)
524              (sb-vm:word string-bytes total-bytes)
525              (system-area-pointer vec-sap string-sap))
526     (dolist (octets octet-vector-list)
527       (declare (type (simple-array (unsigned-byte 8) (*)) octets))
528       (let ((size (length octets)))
529         ;; Copy string.
530         (sb-kernel:copy-ub8-to-system-area octets 0 string-sap 0 size)
531         ;; NULL-terminate it
532         (sb-kernel:system-area-ub8-fill 0 string-sap size 4)
533         ;; Put the pointer in the vector.
534         (setf (sap-ref-sap vec-sap vec-index-offset) string-sap)
535         ;; Advance string-sap for the next string.
536         (setf string-sap (sap+ string-sap
537                                (round-null-terminated-bytes-to-words size)))
538         (incf vec-index-offset sb-vm:n-word-bytes)))
539     ;; Final null pointer.
540     (setf (sap-ref-sap vec-sap vec-index-offset) (int-sap 0))
541     (values vec-sap (sap+ vec-sap sb-vm:n-word-bytes) total-bytes)))
542
543 #-win32
544 (defmacro with-args ((var str-list) &body body)
545   (with-unique-names (sap size)
546     `(multiple-value-bind (,sap ,var ,size)
547          (string-list-to-c-strvec ,str-list)
548        (unwind-protect
549             (progn
550               ,@body)
551          (deallocate-system-memory ,sap ,size)))))
552
553 (defmacro with-environment ((var str-list &key null) &body body)
554   (once-only ((null null))
555     (with-unique-names (sap size)
556       `(multiple-value-bind (,sap ,var ,size)
557            (if ,null
558                (values nil (int-sap 0))
559                #-win32 (string-list-to-c-strvec ,str-list)
560                #+win32 (encode-windows-environment ,str-list))
561          (unwind-protect
562               (progn
563                 ,@body)
564            (unless ,null
565              (deallocate-system-memory ,sap ,size)))))))
566 #-win32
567 (define-alien-routine spawn
568      int
569   (program c-string)
570   (argv (* c-string))
571   (stdin int)
572   (stdout int)
573   (stderr int)
574   (search int)
575   (envp (* c-string))
576   (pty-name c-string)
577   (wait int)
578   (dir c-string))
579
580 #+win32
581 (defun escape-arg (arg stream)
582   ;; Normally, #\\ doesn't have to be escaped
583   ;; But if #\" follows #\\, then they have to be escaped.
584   ;; Do that by counting the number of consequent backslashes, and
585   ;; upon encoutering #\" immediately after them, output the same
586   ;; number of backslashes, plus one for #\"
587   (write-char #\" stream)
588   (loop with slashes = 0
589         for i below (length arg)
590         for previous-char = #\a then char
591         for char = (char arg i)
592         do
593         (case char
594           (#\"
595            (loop repeat slashes
596                  do (write-char #\\ stream))
597            (write-string "\\\"" stream))
598           (t
599            (write-char char stream)))
600         (case char
601           (#\\
602            (incf slashes))
603           (t
604            (setf slashes 0)))
605         finally
606         ;; The final #\" counts too, but doesn't need to be escaped itself
607         (loop repeat slashes
608               do (write-char #\\ stream)))
609   (write-char #\" stream))
610
611 (defun prepare-args (args)
612   (cond #-win32
613         ((every #'simple-string-p args)
614          args)
615         #-win32
616         (t
617          (loop for arg in args
618                collect (coerce arg 'simple-string)))
619         #+win32
620         (t
621          (with-output-to-string (str)
622            (loop for (arg . rest) on args
623                  do
624                  (cond ((find-if (lambda (c) (find c '(#\Space #\Tab #\")))
625                                  arg)
626                         (escape-arg arg str))
627                        (t
628                         (princ arg str)))
629                  (when rest
630                    (write-char #\Space str)))))))
631
632 ;;; FIXME: There shouldn't be two semiredundant versions of the
633 ;;; documentation. Since this is a public extension function, the
634 ;;; documentation should be in the doc string. So all information from
635 ;;; this comment should be merged into the doc string, and then this
636 ;;; comment can go away.
637 ;;;
638 ;;; RUN-PROGRAM uses fork() and execve() to run a different program.
639 ;;; Strange stuff happens to keep the Unix state of the world
640 ;;; coherent.
641 ;;;
642 ;;; The child process needs to get its input from somewhere, and send
643 ;;; its output (both standard and error) to somewhere. We have to do
644 ;;; different things depending on where these somewheres really are.
645 ;;;
646 ;;; For input, there are five options:
647 ;;;  -- T: Just leave fd 0 alone. Pretty simple.
648 ;;;  -- "file": Read from the file. We need to open the file and
649 ;;;     pull the descriptor out of the stream. The parent should close
650 ;;;     this stream after the child is up and running to free any
651 ;;;     storage used in the parent.
652 ;;;  -- NIL: Same as "file", but use "/dev/null" as the file.
653 ;;;  -- :STREAM: Use Unix pipe() to create two descriptors. Use
654 ;;;     SB-SYS:MAKE-FD-STREAM to create the output stream on the
655 ;;;     writeable descriptor, and pass the readable descriptor to
656 ;;;     the child. The parent must close the readable descriptor for
657 ;;;     EOF to be passed up correctly.
658 ;;;  -- a stream: If it's a fd-stream, just pull the descriptor out
659 ;;;     of it. Otherwise make a pipe as in :STREAM, and copy
660 ;;;     everything across.
661 ;;;
662 ;;; For output, there are five options:
663 ;;;  -- T: Leave descriptor 1 alone.
664 ;;;  -- "file": dump output to the file.
665 ;;;  -- NIL: dump output to /dev/null.
666 ;;;  -- :STREAM: return a stream that can be read from.
667 ;;;  -- a stream: if it's a fd-stream, use the descriptor in it.
668 ;;;     Otherwise, copy stuff from output to stream.
669 ;;;
670 ;;; For error, there are all the same options as output plus:
671 ;;;  -- :OUTPUT: redirect to the same place as output.
672 ;;;
673 ;;; RUN-PROGRAM returns a PROCESS structure for the process if
674 ;;; the fork worked, and NIL if it did not.
675 (defun run-program (program args
676                     &key
677                     (env nil env-p)
678                     (environment
679                      (when env-p
680                        (unix-environment-sbcl-from-cmucl env))
681                      environment-p)
682                     (wait t)
683                     search
684                     #-win32 pty
685                     input
686                     if-input-does-not-exist
687                     output
688                     (if-output-exists :error)
689                     (error :output)
690                     (if-error-exists :error)
691                     status-hook
692                     (external-format :default)
693                     directory)
694   #+sb-doc
695   #.(concatenate
696      'string
697      ;; The Texinfoizer is sensitive to whitespace, so mind the
698      ;; placement of the #-win32 pseudosplicings.
699      "RUN-PROGRAM creates a new process specified by the PROGRAM
700 argument. ARGS are the standard arguments that can be passed to a
701 program. For no arguments, use NIL (which means that just the
702 name of the program is passed as arg 0).
703
704 The program arguments and the environment are encoded using the
705 default external format for streams.
706
707 RUN-PROGRAM will return a PROCESS structure. See the CMU Common Lisp
708 Users Manual for details about the PROCESS structure.
709
710    Notes about Unix environments (as in the :ENVIRONMENT and :ENV args):
711
712    - The SBCL implementation of RUN-PROGRAM, like Perl and many other
713      programs, but unlike the original CMU CL implementation, copies
714      the Unix environment by default."#-win32"
715    - Running Unix programs from a setuid process, or in any other
716      situation where the Unix environment is under the control of someone
717      else, is a mother lode of security problems. If you are contemplating
718      doing this, read about it first. (The Perl community has a lot of good
719      documentation about this and other security issues in script-like
720      programs.)""
721
722    The &KEY arguments have the following meanings:
723    :ENVIRONMENT
724       a list of STRINGs describing the new Unix environment
725       (as in \"man environ\"). The default is to copy the environment of
726       the current process.
727    :ENV
728       an alternative lossy representation of the new Unix environment,
729       for compatibility with CMU CL
730    :SEARCH
731       Look for PROGRAM in each of the directories in the child's $PATH
732       environment variable.  Otherwise an absolute pathname is required.
733    :WAIT
734       If non-NIL (default), wait until the created process finishes.  If
735       NIL, continue running Lisp until the program finishes."#-win32"
736    :PTY
737       Either T, NIL, or a stream.  Unless NIL, the subprocess is established
738       under a PTY.  If :pty is a stream, all output to this pty is sent to
739       this stream, otherwise the PROCESS-PTY slot is filled in with a stream
740       connected to pty that can read output and write input.""
741    :INPUT
742       Either T, NIL, a pathname, a stream, or :STREAM.  If T, the standard
743       input for the current process is inherited.  If NIL, "
744       #-win32"/dev/null"#+win32"nul""
745       is used.  If a pathname, the file so specified is used.  If a stream,
746       all the input is read from that stream and sent to the subprocess.  If
747       :STREAM, the PROCESS-INPUT slot is filled in with a stream that sends
748       its output to the process. Defaults to NIL.
749    :IF-INPUT-DOES-NOT-EXIST (when :INPUT is the name of a file)
750       can be one of:
751          :ERROR to generate an error
752          :CREATE to create an empty file
753          NIL (the default) to return NIL from RUN-PROGRAM
754    :OUTPUT
755       Either T, NIL, a pathname, a stream, or :STREAM.  If T, the standard
756       output for the current process is inherited.  If NIL, "
757       #-win32"/dev/null"#+win32"nul""
758       is used.  If a pathname, the file so specified is used.  If a stream,
759       all the output from the process is written to this stream. If
760       :STREAM, the PROCESS-OUTPUT slot is filled in with a stream that can
761       be read to get the output. Defaults to NIL.
762    :IF-OUTPUT-EXISTS (when :OUTPUT is the name of a file)
763       can be one of:
764          :ERROR (the default) to generate an error
765          :SUPERSEDE to supersede the file with output from the program
766          :APPEND to append output from the program to the file
767          NIL to return NIL from RUN-PROGRAM, without doing anything
768    :ERROR and :IF-ERROR-EXISTS
769       Same as :OUTPUT and :IF-OUTPUT-EXISTS, except that :ERROR can also be
770       specified as :OUTPUT in which case all error output is routed to the
771       same place as normal output.
772    :STATUS-HOOK
773       This is a function the system calls whenever the status of the
774       process changes.  The function takes the process as an argument.
775    :EXTERNAL-FORMAT
776       The external-format to use for :INPUT, :OUTPUT, and :ERROR :STREAMs.
777    :DIRECTORY
778       Specifies the directory in which the program should be run.
779       NIL (the default) means the directory is unchanged.")
780   (when (and env-p environment-p)
781     (error "can't specify :ENV and :ENVIRONMENT simultaneously"))
782   (let* (;; Clear various specials used by GET-DESCRIPTOR-FOR to
783          ;; communicate cleanup info.
784          *close-on-error*
785          *close-in-parent*
786          ;; Some other binding used only on non-Win32.  FIXME:
787          ;; nothing seems to set this.
788          #-win32 *handlers-installed*
789          ;; Establish PROC at this level so that we can return it.
790          proc
791          (progname (native-namestring program))
792          (args (prepare-args (cons progname args)))
793          (directory (and directory (native-namestring directory)))
794          ;; Gag.
795          (cookie (list 0)))
796     (unwind-protect
797          ;; Note: despite the WITH-* names, these macros don't
798          ;; expand into UNWIND-PROTECT forms.  They're just
799          ;; syntactic sugar to make the rest of the routine slightly
800          ;; easier to read.
801          (macrolet ((with-fd-and-stream-for (((fd stream) which &rest args)
802                                              &body body)
803                       `(multiple-value-bind (,fd ,stream)
804                            ,(ecase which
805                               ((:input :output)
806                                `(get-descriptor-for ,@args))
807                               (:error
808                                `(if (eq ,(first args) :output)
809                                     ;; kludge: we expand into
810                                     ;; hard-coded symbols here.
811                                     (values stdout output-stream)
812                                     (get-descriptor-for ,@args))))
813                          (unless ,fd
814                            (return-from run-program))
815                          ,@body))
816                     (with-open-pty (((pty-name pty-stream) (pty cookie))
817                                     &body body)
818                       (declare (ignorable pty-name pty-stream pty cookie))
819                       #+win32
820                       `(progn ,@body)
821                       #-win32
822                       `(multiple-value-bind (,pty-name ,pty-stream)
823                            (open-pty ,pty ,cookie :external-format external-format)
824                          ,@body)))
825            (with-fd-and-stream-for ((stdin input-stream) :input
826                                     input cookie
827                                     :direction :input
828                                     :if-does-not-exist if-input-does-not-exist
829                                     :external-format external-format
830                                     :wait wait)
831              (with-fd-and-stream-for ((stdout output-stream) :output
832                                       output cookie
833                                       :direction :output
834                                       :if-exists if-output-exists
835                                       :external-format external-format)
836                (with-fd-and-stream-for ((stderr error-stream)  :error
837                                         error cookie
838                                         :direction :output
839                                         :if-exists if-error-exists
840                                         :external-format external-format)
841                  (with-open-pty ((pty-name pty-stream) (pty cookie))
842                    ;; Make sure we are not notified about the child
843                    ;; death before we have installed the PROCESS
844                    ;; structure in *ACTIVE-PROCESSES*.
845                    (let (child)
846                      (with-active-processes-lock ()
847                        (with-environment (environment-vec environment
848                                           :null (not (or environment environment-p)))
849                          (setq child
850                                #+win32
851                                (sb-win32::mswin-spawn
852                                 progname
853                                 args
854                                 stdin stdout stderr
855                                 search environment-vec wait directory)
856                                #-win32
857                                (with-args (args-vec args)
858                                  (without-gcing
859                                    (spawn progname args-vec
860                                           stdin stdout stderr
861                                           (if search 1 0)
862                                           environment-vec pty-name
863                                           (if wait 1 0) directory))))
864                          (unless (minusp child)
865                            (setf proc
866                                  (make-process
867                                   :input input-stream
868                                   :output output-stream
869                                   :error error-stream
870                                   :status-hook status-hook
871                                   :cookie cookie
872                                   #-win32 :pty #-win32 pty-stream
873                                   :%status #-win32 :running
874                                            #+win32 (if wait
875                                                        :exited
876                                                        :running)
877                                   :pid #-win32 child
878                                        #+win32 (if wait
879                                                    nil
880                                                    child)
881                                   #+win32 :%exit-code #+win32 (and wait child)))
882                            (push proc *active-processes*))))
883                      ;; Report the error outside the lock.
884                      (case child
885                        (-1
886                         (error "Couldn't fork child process: ~A"
887                                (strerror)))
888                        (-2
889                         (error "Couldn't execute ~S: ~A"
890                                progname (strerror)))
891                        (-3
892                         (error "Couldn't change directory to ~S: ~A"
893                                directory (strerror))))))))))
894       (dolist (fd *close-in-parent*)
895         (sb-unix:unix-close fd))
896       (unless proc
897         (dolist (fd *close-on-error*)
898           (sb-unix:unix-close fd))
899         #-win32
900         (dolist (handler *handlers-installed*)
901           (remove-fd-handler handler)))
902       #-win32
903       (when (and wait proc)
904         (unwind-protect
905              (process-wait proc)
906           (dolist (handler *handlers-installed*)
907             (remove-fd-handler handler)))))
908     proc))
909
910 ;;; Install a handler for any input that shows up on the file
911 ;;; descriptor. The handler reads the data and writes it to the
912 ;;; stream.
913 (defun copy-descriptor-to-stream (descriptor stream cookie external-format)
914   (incf (car cookie))
915   (let* ((handler nil)
916          (buf (make-array 256 :element-type '(unsigned-byte 8)))
917          (read-end 0)
918          (et (stream-element-type stream))
919          (copy-fun
920           (cond
921             ((member et '(character base-char))
922              (lambda ()
923                (let* ((decode-end read-end)
924                       (string (handler-case
925                                   (octets-to-string
926                                    buf :end read-end
927                                    :external-format external-format)
928                                 (end-of-input-in-character (e)
929                                   (setf decode-end
930                                         (octet-decoding-error-start e))
931                                   (octets-to-string
932                                    buf :end decode-end
933                                    :external-format external-format)))))
934                  (unless (zerop (length string))
935                    (write-string string stream)
936                    (when (/= decode-end (length buf))
937                      (replace buf buf :start2 decode-end :end2 read-end))
938                    (decf read-end decode-end)))))
939             ((member et '(:default (unsigned-byte 8)) :test #'equal)
940              (lambda ()
941                (write-sequence buf stream :end read-end)
942                (setf read-end 0)))
943             (t
944              ;; FIXME.
945              (error "Don't know how to copy to stream of element-type ~S"
946                     et)))))
947     (setf handler
948           (add-fd-handler
949            descriptor
950            :input
951            (lambda (fd)
952              (declare (ignore fd))
953              (loop
954                 (unless handler
955                   (return))
956                 (multiple-value-bind
957                       (result readable/errno)
958                     (sb-unix:unix-select (1+ descriptor)
959                                          (ash 1 descriptor)
960                                          0 0 0)
961                   (cond ((null result)
962                          (if (eql sb-unix:eintr readable/errno)
963                              (return)
964                              (error "~@<Couldn't select on sub-process: ~
965                                         ~2I~_~A~:>"
966                                     (strerror readable/errno))))
967                         ((zerop result)
968                          (return))))
969                 (multiple-value-bind (count errno)
970                     (with-pinned-objects (buf)
971                       (sb-unix:unix-read descriptor
972                                          (sap+ (vector-sap buf) read-end)
973                                          (- (length buf) read-end)))
974                   (cond
975                     ((and #-win32 (or (and (null count)
976                                            (eql errno sb-unix:eio))
977                                       (eql count 0))
978                           #+win32 (<= count 0))
979                      (remove-fd-handler handler)
980                      (setf handler nil)
981                      (decf (car cookie))
982                      (sb-unix:unix-close descriptor)
983                      (unless (zerop read-end)
984                        ;; Should this be an END-OF-FILE?
985                        (error "~@<non-empty buffer when EOF reached ~
986                                while reading from child: ~S~:>" buf))
987                      (return))
988                     ((null count)
989                      (remove-fd-handler handler)
990                      (setf handler nil)
991                      (decf (car cookie))
992                      (error
993                       "~@<couldn't read input from sub-process: ~
994                                      ~2I~_~A~:>"
995                       (strerror errno)))
996                     (t
997                      (incf read-end count)
998                      (funcall copy-fun))))))))
999     #-win32
1000     (push handler *handlers-installed*)))
1001
1002 ;;; FIXME: something very like this is done in SB-POSIX to treat
1003 ;;; streams as file descriptor designators; maybe we can combine these
1004 ;;; two?  Additionally, as we have a couple of user-defined streams
1005 ;;; libraries, maybe we should have a generic function for doing this,
1006 ;;; so user-defined streams can play nicely with RUN-PROGRAM (and
1007 ;;; maybe also with SB-POSIX)?
1008 (defun get-stream-fd-and-external-format (stream direction)
1009   (typecase stream
1010     (fd-stream
1011      (values (fd-stream-fd stream) nil (stream-external-format stream)))
1012     (synonym-stream
1013      (get-stream-fd-and-external-format
1014       (symbol-value (synonym-stream-symbol stream)) direction))
1015     (two-way-stream
1016      (ecase direction
1017        (:input
1018         (get-stream-fd-and-external-format
1019          (two-way-stream-input-stream stream) direction))
1020        (:output
1021         (get-stream-fd-and-external-format
1022          (two-way-stream-output-stream stream) direction))))))
1023
1024 (defun get-temporary-directory ()
1025   #-win32 (or (sb-ext:posix-getenv "TMPDIR")
1026               "/tmp")
1027   #+win32 (or (sb-ext:posix-getenv "TEMP")
1028               "C:/Temp"))
1029
1030 \f
1031 ;;; Find a file descriptor to use for object given the direction.
1032 ;;; Returns the descriptor. If object is :STREAM, returns the created
1033 ;;; stream as the second value.
1034 (defun get-descriptor-for (object
1035                            cookie
1036                            &rest keys
1037                            &key direction (external-format :default) wait
1038                            &allow-other-keys)
1039   (declare (ignore wait)) ;This is explained below.
1040   ;; Our use of a temporary file dates back to very old CMUCLs, and
1041   ;; was probably only ever intended for use with STRING-STREAMs,
1042   ;; which are ordinarily smallish.  However, as we've got
1043   ;; user-defined stream classes, we can end up trying to copy
1044   ;; arbitrarily much data into the temp file, and so are liable to
1045   ;; run afoul of disk quotas or to choke on small /tmp file systems.
1046   (flet ((make-temp-fd ()
1047            (multiple-value-bind (fd name/errno)
1048                (sb-unix:sb-mkstemp (format nil "~a/.run-program-XXXXXX"
1049                                            (get-temporary-directory))
1050                                    #o0600)
1051              (unless fd
1052                (error "could not open a temporary file: ~A"
1053                       (strerror name/errno)))
1054              ;; Can't unlink an open file on Windows
1055              #-win32
1056              (unless (sb-unix:unix-unlink name/errno)
1057                (sb-unix:unix-close fd)
1058                (error "failed to unlink ~A" name/errno))
1059              fd)))
1060     (let ((dev-null #.(coerce #-win32 "/dev/null" #+win32 "nul" 'base-string)))
1061       (cond ((eq object t)
1062              ;; No new descriptor is needed.
1063              (values -1 nil))
1064             ((or (eq object nil)
1065                  (and (typep object 'broadcast-stream)
1066                       (not (broadcast-stream-streams object))))
1067              ;; Use /dev/null.
1068              (multiple-value-bind
1069                    (fd errno)
1070                  (sb-unix:unix-open dev-null
1071                                     (case direction
1072                                       (:input sb-unix:o_rdonly)
1073                                       (:output sb-unix:o_wronly)
1074                                       (t sb-unix:o_rdwr))
1075                                     #o666)
1076                (unless fd
1077                  (error "~@<couldn't open ~S: ~2I~_~A~:>"
1078                         dev-null (strerror errno)))
1079                #+win32
1080                (setf (sb-win32::inheritable-handle-p fd) t)
1081                (push fd *close-in-parent*)
1082                (values fd nil)))
1083             ((eq object :stream)
1084              (multiple-value-bind (read-fd write-fd) (sb-unix:unix-pipe)
1085                (unless read-fd
1086                  (error "couldn't create pipe: ~A" (strerror write-fd)))
1087                #+win32
1088                (setf (sb-win32::inheritable-handle-p read-fd)
1089                      (eq direction :input)
1090                      (sb-win32::inheritable-handle-p write-fd)
1091                      (eq direction :output))
1092                (case direction
1093                  (:input
1094                     (push read-fd *close-in-parent*)
1095                     (push write-fd *close-on-error*)
1096                     (let ((stream (make-fd-stream write-fd :output t
1097                                                          :element-type :default
1098                                                          :external-format
1099                                                          external-format)))
1100                       (values read-fd stream)))
1101                  (:output
1102                     (push read-fd *close-on-error*)
1103                     (push write-fd *close-in-parent*)
1104                     (let ((stream (make-fd-stream read-fd :input t
1105                                                          :element-type :default
1106                                                          :external-format
1107                                                          external-format)))
1108                       (values write-fd stream)))
1109                  (t
1110                     (sb-unix:unix-close read-fd)
1111                     (sb-unix:unix-close write-fd)
1112                     (error "Direction must be either :INPUT or :OUTPUT, not ~S."
1113                            direction)))))
1114             ((or (pathnamep object) (stringp object))
1115              ;; GET-DESCRIPTOR-FOR uses &allow-other-keys, so rather
1116              ;; than munge the &rest list for OPEN, just disable keyword
1117              ;; validation there.
1118              (with-open-stream (file (apply #'open object :allow-other-keys t
1119                                             keys))
1120                (when file
1121                  (multiple-value-bind
1122                        (fd errno)
1123                      (sb-unix:unix-dup (fd-stream-fd file))
1124                    (cond (fd
1125                           (push fd *close-in-parent*)
1126                           (values fd nil))
1127                          (t
1128                           (error "couldn't duplicate file descriptor: ~A"
1129                                  (strerror errno))))))))
1130           ((streamp object)
1131            (ecase direction
1132              (:input
1133               (block nil
1134                 ;; If we can get an fd for the stream, let the child
1135                 ;; process use the fd for its descriptor.  Otherwise,
1136                 ;; we copy data from the stream into a temp file, and
1137                 ;; give the temp file's descriptor to the
1138                 ;; child.
1139                 (multiple-value-bind (fd stream format)
1140                     (get-stream-fd-and-external-format object :input)
1141                   (declare (ignore format))
1142                   (when fd
1143                     (return (values fd stream))))
1144                 ;; FIXME: if we can't get the file descriptor, since
1145                 ;; the stream might be interactive or otherwise
1146                 ;; block-y, we can't know whether we can copy the
1147                 ;; stream's data to a temp file, so if RUN-PROGRAM was
1148                 ;; called with :WAIT NIL, we should probably error.
1149                 ;; However, STRING-STREAMs aren't fd-streams, but
1150                 ;; they're not prone to blocking; any user-defined
1151                 ;; streams that "read" from some in-memory data will
1152                 ;; probably be similar to STRING-STREAMs.  So maybe we
1153                 ;; should add a STREAM-INTERACTIVE-P generic function
1154                 ;; for problems like this?  Anyway, the machinery is
1155                 ;; here, if you feel like filling in the details.
1156                 #|
1157                 (when (and (null wait) #<some undetermined criterion>)
1158                   (error "~@<don't know how to get an fd for ~A, and so ~
1159                              can't ensure that copying its data to the ~
1160                              child process won't hang~:>" object))
1161                 |#
1162                 (let ((fd (make-temp-fd))
1163                       (et (stream-element-type object)))
1164                   (cond ((member et '(character base-char))
1165                          (loop
1166                            (multiple-value-bind
1167                                  (line no-cr)
1168                                (read-line object nil nil)
1169                              (unless line
1170                                (return))
1171                              (let ((vector (string-to-octets
1172                                             line
1173                                             :external-format external-format)))
1174                                (sb-unix:unix-write
1175                                 fd vector 0 (length vector)))
1176                              (if no-cr
1177                                (return)
1178                                (sb-unix:unix-write
1179                                 fd #.(string #\Newline) 0 1)))))
1180                         ((member et '(:default (unsigned-byte 8))
1181                                  :test 'equal)
1182                          (loop with buf = (make-array 256 :element-type '(unsigned-byte 8))
1183                                for p = (read-sequence buf object)
1184                                until (zerop p)
1185                                do (sb-unix:unix-write fd buf 0 p)))
1186                         (t
1187                          (error "Don't know how to copy from stream of element-type ~S"
1188                                 et)))
1189                   (sb-unix:unix-lseek fd 0 sb-unix:l_set)
1190                   (push fd *close-in-parent*)
1191                   (return (values fd nil)))))
1192              (:output
1193               (block nil
1194                 ;; Similar to the :input trick above, except we
1195                 ;; arrange to copy data from the stream.  This is
1196                 ;; slightly saner than the input case, since we don't
1197                 ;; buffer to a file, but I think we may still lose if
1198                 ;; there's unflushed data in the stream buffer and we
1199                 ;; give the file descriptor to the child.
1200                 (multiple-value-bind (fd stream format)
1201                     (get-stream-fd-and-external-format object :output)
1202                   (declare (ignore format))
1203                   (when fd
1204                     (return (values fd stream))))
1205                 (multiple-value-bind (read-fd write-fd)
1206                     (sb-unix:unix-pipe)
1207                   (unless read-fd
1208                     (error "couldn't create pipe: ~S" (strerror write-fd)))
1209                   (copy-descriptor-to-stream read-fd object cookie
1210                                              external-format)
1211                   (push read-fd *close-on-error*)
1212                   (push write-fd *close-in-parent*)
1213                   (return (values write-fd nil)))))
1214              (t
1215               (error "invalid option to RUN-PROGRAM: ~S" object))))))))