0.6.11.36:
[sbcl.git] / src / code / fd-stream.lisp
1 ;;;; streams for UNIX file descriptors
2
3 ;;;; This software is part of the SBCL system. See the README file for
4 ;;;; more information.
5 ;;;;
6 ;;;; This software is derived from the CMU CL system, which was
7 ;;;; written at Carnegie Mellon University and released into the
8 ;;;; public domain. The software is in the public domain and is
9 ;;;; provided with absolutely no warranty. See the COPYING and CREDITS
10 ;;;; files for more information.
11
12 (in-package "SB!IMPL")
13
14 ;;; FIXME: Wouldn't it be clearer to just have the structure
15 ;;; definition be DEFSTRUCT FILE-STREAM (instead of DEFSTRUCT
16 ;;; FD-STREAM)? That way we'd have TYPE-OF and PRINT-OBJECT refer to
17 ;;; these objects as FILE-STREAMs (the ANSI name) instead of the
18 ;;; internal implementation name FD-STREAM, and there might be other
19 ;;; benefits as well.
20 (deftype file-stream () 'fd-stream)
21 \f
22 ;;;; buffer manipulation routines
23
24 ;;; FIXME: Is it really good to maintain this pool separate from the
25 ;;; GC and the C malloc logic?
26 (defvar *available-buffers* ()
27   #!+sb-doc
28   "List of available buffers. Each buffer is an sap pointing to
29   bytes-per-buffer of memory.")
30
31 (defconstant bytes-per-buffer (* 4 1024)
32   #!+sb-doc
33   "Number of bytes per buffer.")
34
35 ;;; Return the next available buffer, creating one if necessary.
36 #!-sb-fluid (declaim (inline next-available-buffer))
37 (defun next-available-buffer ()
38   (if *available-buffers*
39       (pop *available-buffers*)
40       (allocate-system-memory bytes-per-buffer)))
41 \f
42 ;;;; the FD-STREAM structure
43
44 (defstruct (fd-stream
45             (:constructor %make-fd-stream)
46             (:include lisp-stream
47                       (misc #'fd-stream-misc-routine))
48             (:copier nil))
49
50   ;; the name of this stream
51   (name nil)
52   ;; the file this stream is for
53   (file nil)
54   ;; the backup file namestring for the old file, for :IF-EXISTS
55   ;; :RENAME or :RENAME-AND-DELETE.
56   (original nil :type (or simple-string null))
57   (delete-original nil)       ; for :if-exists :rename-and-delete
58   ;;; the number of bytes per element
59   (element-size 1 :type index)
60   ;; the type of element being transfered
61   (element-type 'base-char)   
62   ;; the Unix file descriptor
63   (fd -1 :type fixnum)        
64   ;; controls when the output buffer is flushed
65   (buffering :full :type (member :full :line :none))
66   ;; character position (if known)
67   (char-pos nil :type (or index null))
68   ;; T if input is waiting on FD. :EOF if we hit EOF.
69   (listen nil :type (member nil t :eof))
70
71   ;; the input buffer
72   (unread nil)
73   (ibuf-sap nil :type (or system-area-pointer null))
74   (ibuf-length nil :type (or index null))
75   (ibuf-head 0 :type index)
76   (ibuf-tail 0 :type index)
77
78   ;; the output buffer
79   (obuf-sap nil :type (or system-area-pointer null))
80   (obuf-length nil :type (or index null))
81   (obuf-tail 0 :type index)
82
83   ;; output flushed, but not written due to non-blocking io?
84   (output-later nil)
85   (handler nil)
86   ;; timeout specified for this stream, or NIL if none
87   (timeout nil :type (or index null))
88   ;; pathname of the file this stream is opened to (returned by PATHNAME)
89   (pathname nil :type (or pathname null)))
90 (def!method print-object ((fd-stream fd-stream) stream)
91   (declare (type stream stream))
92   (print-unreadable-object (fd-stream stream :type t :identity t)
93     (format stream "for ~S" (fd-stream-name fd-stream))))
94 \f
95 ;;;; output routines and related noise
96
97 (defvar *output-routines* ()
98   #!+sb-doc
99   "List of all available output routines. Each element is a list of the
100   element-type output, the kind of buffering, the function name, and the number
101   of bytes per element.")
102
103 ;;; This is called by the server when we can write to the given file
104 ;;; descriptor. Attempt to write the data again. If it worked, remove
105 ;;; the data from the OUTPUT-LATER list. If it didn't work, something
106 ;;; is wrong.
107 (defun do-output-later (stream)
108   (let* ((stuff (pop (fd-stream-output-later stream)))
109          (base (car stuff))
110          (start (cadr stuff))
111          (end (caddr stuff))
112          (reuse-sap (cadddr stuff))
113          (length (- end start)))
114     (declare (type index start end length))
115     (multiple-value-bind (count errno)
116         (sb!unix:unix-write (fd-stream-fd stream)
117                             base
118                             start
119                             length)
120       (cond ((not count)
121              (if (= errno sb!unix:ewouldblock)
122                  (error "Write would have blocked, but SERVER told us to go.")
123                  (error "while writing ~S: ~A"
124                         stream
125                         (sb!unix:get-unix-error-msg errno))))
126             ((eql count length) ; Hot damn, it worked.
127              (when reuse-sap
128                (push base *available-buffers*)))
129             ((not (null count)) ; Sorta worked.
130              (push (list base
131                          (the index (+ start count))
132                          end)
133                    (fd-stream-output-later stream))))))
134   (unless (fd-stream-output-later stream)
135     (sb!sys:remove-fd-handler (fd-stream-handler stream))
136     (setf (fd-stream-handler stream) nil)))
137
138 ;;; Arange to output the string when we can write on the file descriptor.
139 (defun output-later (stream base start end reuse-sap)
140   (cond ((null (fd-stream-output-later stream))
141          (setf (fd-stream-output-later stream)
142                (list (list base start end reuse-sap)))
143          (setf (fd-stream-handler stream)
144                (sb!sys:add-fd-handler (fd-stream-fd stream)
145                                       :output
146                                       #'(lambda (fd)
147                                           (declare (ignore fd))
148                                           (do-output-later stream)))))
149         (t
150          (nconc (fd-stream-output-later stream)
151                 (list (list base start end reuse-sap)))))
152   (when reuse-sap
153     (let ((new-buffer (next-available-buffer)))
154       (setf (fd-stream-obuf-sap stream) new-buffer)
155       (setf (fd-stream-obuf-length stream) bytes-per-buffer))))
156
157 ;;; Output the given noise. Check to see whether there are any pending
158 ;;; writes. If so, just queue this one. Otherwise, try to write it. If
159 ;;; this would block, queue it.
160 (defun do-output (stream base start end reuse-sap)
161   (declare (type fd-stream stream)
162            (type (or system-area-pointer (simple-array * (*))) base)
163            (type index start end))
164   (if (not (null (fd-stream-output-later stream))) ; something buffered.
165       (progn
166         (output-later stream base start end reuse-sap)
167         ;; ### check to see whether any of this noise can be output
168         )
169       (let ((length (- end start)))
170         (multiple-value-bind (count errno)
171             (sb!unix:unix-write (fd-stream-fd stream) base start length)
172           (cond ((not count)
173                  (if (= errno sb!unix:ewouldblock)
174                      (output-later stream base start end reuse-sap)
175                      ;; FIXME: This and various other errors in this file
176                      ;; should probably be STREAM-ERROR.
177                      (error "while writing ~S: ~A"
178                             stream
179                             (sb!unix:get-unix-error-msg errno))))
180                 ((not (eql count length))
181                  (output-later stream base (the index (+ start count))
182                                end reuse-sap)))))))
183
184 ;;; Flush any data in the output buffer.
185 (defun flush-output-buffer (stream)
186   (let ((length (fd-stream-obuf-tail stream)))
187     (unless (= length 0)
188       (do-output stream (fd-stream-obuf-sap stream) 0 length t)
189       (setf (fd-stream-obuf-tail stream) 0))))
190
191 ;;; Define output routines that output numbers SIZE bytes long for the
192 ;;; given bufferings. Use BODY to do the actual output.
193 (defmacro def-output-routines ((name-fmt size &rest bufferings) &body body)
194   (declare (optimize (speed 1)))
195   (cons 'progn
196         (mapcar
197             #'(lambda (buffering)
198                 (let ((function
199                        (intern (let ((*print-case* :upcase))
200                                  (format nil name-fmt (car buffering))))))
201                   `(progn
202                      (defun ,function (stream byte)
203                        ,(unless (eq (car buffering) :none)
204                           `(when (< (fd-stream-obuf-length stream)
205                                     (+ (fd-stream-obuf-tail stream)
206                                        ,size))
207                              (flush-output-buffer stream)))
208                        ,@body
209                        (incf (fd-stream-obuf-tail stream) ,size)
210                        ,(ecase (car buffering)
211                           (:none
212                            `(flush-output-buffer stream))
213                           (:line
214                            `(when (eq (char-code byte) (char-code #\Newline))
215                               (flush-output-buffer stream)))
216                           (:full
217                            ))
218                        (values))
219                      (setf *output-routines*
220                            (nconc *output-routines*
221                                   ',(mapcar
222                                         #'(lambda (type)
223                                             (list type
224                                                   (car buffering)
225                                                   function
226                                                   size))
227                                       (cdr buffering)))))))
228           bufferings)))
229
230 (def-output-routines ("OUTPUT-CHAR-~A-BUFFERED"
231                       1
232                       (:none character)
233                       (:line character)
234                       (:full character))
235   (if (and (base-char-p byte) (char= byte #\Newline))
236       (setf (fd-stream-char-pos stream) 0)
237       (incf (fd-stream-char-pos stream)))
238   (setf (sap-ref-8 (fd-stream-obuf-sap stream) (fd-stream-obuf-tail stream))
239         (char-code byte)))
240
241 (def-output-routines ("OUTPUT-UNSIGNED-BYTE-~A-BUFFERED"
242                       1
243                       (:none (unsigned-byte 8))
244                       (:full (unsigned-byte 8)))
245   (setf (sap-ref-8 (fd-stream-obuf-sap stream) (fd-stream-obuf-tail stream))
246         byte))
247
248 (def-output-routines ("OUTPUT-SIGNED-BYTE-~A-BUFFERED"
249                       1
250                       (:none (signed-byte 8))
251                       (:full (signed-byte 8)))
252   (setf (signed-sap-ref-8 (fd-stream-obuf-sap stream)
253                           (fd-stream-obuf-tail stream))
254         byte))
255
256 (def-output-routines ("OUTPUT-UNSIGNED-SHORT-~A-BUFFERED"
257                       2
258                       (:none (unsigned-byte 16))
259                       (:full (unsigned-byte 16)))
260   (setf (sap-ref-16 (fd-stream-obuf-sap stream) (fd-stream-obuf-tail stream))
261         byte))
262
263 (def-output-routines ("OUTPUT-SIGNED-SHORT-~A-BUFFERED"
264                       2
265                       (:none (signed-byte 16))
266                       (:full (signed-byte 16)))
267   (setf (signed-sap-ref-16 (fd-stream-obuf-sap stream)
268                            (fd-stream-obuf-tail stream))
269         byte))
270
271 (def-output-routines ("OUTPUT-UNSIGNED-LONG-~A-BUFFERED"
272                       4
273                       (:none (unsigned-byte 32))
274                       (:full (unsigned-byte 32)))
275   (setf (sap-ref-32 (fd-stream-obuf-sap stream) (fd-stream-obuf-tail stream))
276         byte))
277
278 (def-output-routines ("OUTPUT-SIGNED-LONG-~A-BUFFERED"
279                       4
280                       (:none (signed-byte 32))
281                       (:full (signed-byte 32)))
282   (setf (signed-sap-ref-32 (fd-stream-obuf-sap stream)
283                            (fd-stream-obuf-tail stream))
284         byte))
285
286 ;;; Do the actual output. If there is space to buffer the string,
287 ;;; buffer it. If the string would normally fit in the buffer, but
288 ;;; doesn't because of other stuff in the buffer, flush the old noise
289 ;;; out of the buffer and put the string in it. Otherwise we have a
290 ;;; very long string, so just send it directly (after flushing the
291 ;;; buffer, of course).
292 (defun output-raw-bytes (fd-stream thing &optional start end)
293   #!+sb-doc
294   "Output THING to FD-STREAM. THING can be any kind of vector or a SAP. If
295   THING is a SAP, END must be supplied (as length won't work)."
296   (let ((start (or start 0))
297         (end (or end (length (the (simple-array * (*)) thing)))))
298     (declare (type index start end))
299     (let* ((len (fd-stream-obuf-length fd-stream))
300            (tail (fd-stream-obuf-tail fd-stream))
301            (space (- len tail))
302            (bytes (- end start))
303            (newtail (+ tail bytes)))
304       (cond ((minusp bytes) ; error case
305              (error ":END before :START!"))
306             ((zerop bytes)) ; easy case
307             ((<= bytes space)
308              (if (system-area-pointer-p thing)
309                  (system-area-copy thing
310                                    (* start sb!vm:byte-bits)
311                                    (fd-stream-obuf-sap fd-stream)
312                                    (* tail sb!vm:byte-bits)
313                                    (* bytes sb!vm:byte-bits))
314                  ;; FIXME: There should be some type checking somewhere to
315                  ;; verify that THING here is a vector, not just <not a SAP>.
316                  (copy-to-system-area thing
317                                       (+ (* start sb!vm:byte-bits)
318                                          (* sb!vm:vector-data-offset
319                                             sb!vm:word-bits))
320                                       (fd-stream-obuf-sap fd-stream)
321                                       (* tail sb!vm:byte-bits)
322                                       (* bytes sb!vm:byte-bits)))
323              (setf (fd-stream-obuf-tail fd-stream) newtail))
324             ((<= bytes len)
325              (flush-output-buffer fd-stream)
326              (if (system-area-pointer-p thing)
327                  (system-area-copy thing
328                                    (* start sb!vm:byte-bits)
329                                    (fd-stream-obuf-sap fd-stream)
330                                    0
331                                    (* bytes sb!vm:byte-bits))
332                  ;; FIXME: There should be some type checking somewhere to
333                  ;; verify that THING here is a vector, not just <not a SAP>.
334                  (copy-to-system-area thing
335                                       (+ (* start sb!vm:byte-bits)
336                                          (* sb!vm:vector-data-offset
337                                             sb!vm:word-bits))
338                                       (fd-stream-obuf-sap fd-stream)
339                                       0
340                                       (* bytes sb!vm:byte-bits)))
341              (setf (fd-stream-obuf-tail fd-stream) bytes))
342             (t
343              (flush-output-buffer fd-stream)
344              (do-output fd-stream thing start end nil))))))
345
346 ;;; the routine to use to output a string. If the stream is
347 ;;; unbuffered, slam the string down the file descriptor, otherwise
348 ;;; use OUTPUT-RAW-BYTES to buffer the string. Update charpos by
349 ;;; checking to see where the last newline was.
350 ;;;
351 ;;; Note: some bozos (the FASL dumper) call write-string with things
352 ;;; other than strings. Therefore, we must make sure we have a string
353 ;;; before calling POSITION on it.
354 ;;; KLUDGE: It would be better to fix the bozos instead of trying to
355 ;;; cover for them here. -- WHN 20000203
356 (defun fd-sout (stream thing start end)
357   (let ((start (or start 0))
358         (end (or end (length (the vector thing)))))
359     (declare (fixnum start end))
360     (if (stringp thing)
361         (let ((last-newline (and (find #\newline (the simple-string thing)
362                                        :start start :end end)
363                                  (position #\newline (the simple-string thing)
364                                            :from-end t
365                                            :start start
366                                            :end end))))
367           (ecase (fd-stream-buffering stream)
368             (:full
369              (output-raw-bytes stream thing start end))
370             (:line
371              (output-raw-bytes stream thing start end)
372              (when last-newline
373                (flush-output-buffer stream)))
374             (:none
375              (do-output stream thing start end nil)))
376           (if last-newline
377               (setf (fd-stream-char-pos stream)
378                     (- end last-newline 1))
379               (incf (fd-stream-char-pos stream)
380                     (- end start))))
381         (ecase (fd-stream-buffering stream)
382           ((:line :full)
383            (output-raw-bytes stream thing start end))
384           (:none
385            (do-output stream thing start end nil))))))
386
387 ;;; Find an output routine to use given the type and buffering. Return
388 ;;; as multiple values the routine, the real type transfered, and the
389 ;;; number of bytes per element.
390 (defun pick-output-routine (type buffering)
391   (dolist (entry *output-routines*)
392     (when (and (subtypep type (car entry))
393                (eq buffering (cadr entry)))
394       (return (values (symbol-function (caddr entry))
395                       (car entry)
396                       (cadddr entry))))))
397 \f
398 ;;;; input routines and related noise
399
400 ;;; a list of all available input routines. Each element is a list of
401 ;;; the element-type input, the function name, and the number of bytes
402 ;;; per element.
403 (defvar *input-routines* ())
404
405 ;;; Fill the input buffer, and return the first character. Throw to
406 ;;; EOF-INPUT-CATCHER if the eof was reached. Drop into SYSTEM:SERVER
407 ;;; if necessary.
408 (defun do-input (stream)
409   (let ((fd (fd-stream-fd stream))
410         (ibuf-sap (fd-stream-ibuf-sap stream))
411         (buflen (fd-stream-ibuf-length stream))
412         (head (fd-stream-ibuf-head stream))
413         (tail (fd-stream-ibuf-tail stream)))
414     (declare (type index head tail))
415     (unless (zerop head)
416       (cond ((eql head tail)
417              (setf head 0)
418              (setf tail 0)
419              (setf (fd-stream-ibuf-head stream) 0)
420              (setf (fd-stream-ibuf-tail stream) 0))
421             (t
422              (decf tail head)
423              (system-area-copy ibuf-sap (* head sb!vm:byte-bits)
424                                ibuf-sap 0 (* tail sb!vm:byte-bits))
425              (setf head 0)
426              (setf (fd-stream-ibuf-head stream) 0)
427              (setf (fd-stream-ibuf-tail stream) tail))))
428     (setf (fd-stream-listen stream) nil)
429     (multiple-value-bind (count errno)
430         ;; FIXME: Judging from compiler warnings, this WITH-ALIEN form expands
431         ;; into something which uses the not-yet-defined type
432         ;;   (SB!ALIEN-INTERNALS:ALIEN (* (SB!ALIEN:STRUCT SB!UNIX:FD-SET))).
433         ;; This is probably inefficient and unsafe and generally bad, so
434         ;; try to find some way to make that type known before
435         ;; this is compiled.
436         (sb!alien:with-alien ((read-fds (sb!alien:struct sb!unix:fd-set)))
437           (sb!unix:fd-zero read-fds)
438           (sb!unix:fd-set fd read-fds)
439           (sb!unix:unix-fast-select (1+ fd)
440                                     (sb!alien:addr read-fds)
441                                     nil
442                                     nil
443                                     0
444                                     0))
445       (case count
446         (1)
447         (0
448          (unless #!-mp (sb!sys:wait-until-fd-usable
449                        fd :input (fd-stream-timeout stream))
450                  #!+mp (sb!mp:process-wait-until-fd-usable
451                        fd :input (fd-stream-timeout stream))
452            (error 'io-timeout :stream stream :direction :read)))
453         (t
454          (error "problem checking to see whether ~S is readable: ~A"
455                 stream
456                 (sb!unix:get-unix-error-msg errno)))))
457     (multiple-value-bind (count errno)
458         (sb!unix:unix-read fd
459                            (sb!sys:int-sap (+ (sb!sys:sap-int ibuf-sap) tail))
460                            (- buflen tail))
461       (cond ((null count)
462              (if (eql errno sb!unix:ewouldblock)
463                  (progn
464                    (unless #!-mp (sb!sys:wait-until-fd-usable
465                                  fd :input (fd-stream-timeout stream))
466                            #!+mp (sb!mp:process-wait-until-fd-usable
467                                  fd :input (fd-stream-timeout stream))
468                      (error 'io-timeout :stream stream :direction :read))
469                    (do-input stream))
470                  (error "error reading ~S: ~A"
471                         stream
472                         (sb!unix:get-unix-error-msg errno))))
473             ((zerop count)
474              (setf (fd-stream-listen stream) :eof)
475              (throw 'eof-input-catcher nil))
476             (t
477              (incf (fd-stream-ibuf-tail stream) count))))))
478                         
479 ;;; Make sure there are at least BYTES number of bytes in the input
480 ;;; buffer. Keep calling DO-INPUT until that condition is met.
481 (defmacro input-at-least (stream bytes)
482   (let ((stream-var (gensym))
483         (bytes-var (gensym)))
484     `(let ((,stream-var ,stream)
485            (,bytes-var ,bytes))
486        (loop
487          (when (>= (- (fd-stream-ibuf-tail ,stream-var)
488                       (fd-stream-ibuf-head ,stream-var))
489                    ,bytes-var)
490            (return))
491          (do-input ,stream-var)))))
492
493 ;;; a macro to wrap around all input routines to handle EOF-ERROR noise
494 (defmacro input-wrapper ((stream bytes eof-error eof-value) &body read-forms)
495   (let ((stream-var (gensym))
496         (element-var (gensym)))
497     `(let ((,stream-var ,stream))
498        (if (fd-stream-unread ,stream-var)
499            (prog1
500                (fd-stream-unread ,stream-var)
501              (setf (fd-stream-unread ,stream-var) nil)
502              (setf (fd-stream-listen ,stream-var) nil))
503            (let ((,element-var
504                   (catch 'eof-input-catcher
505                     (input-at-least ,stream-var ,bytes)
506                     ,@read-forms)))
507              (cond (,element-var
508                     (incf (fd-stream-ibuf-head ,stream-var) ,bytes)
509                     ,element-var)
510                    (t
511                     (eof-or-lose ,stream-var ,eof-error ,eof-value))))))))
512
513 (defmacro def-input-routine (name
514                              (type size sap head)
515                              &rest body)
516   `(progn
517      (defun ,name (stream eof-error eof-value)
518        (input-wrapper (stream ,size eof-error eof-value)
519          (let ((,sap (fd-stream-ibuf-sap stream))
520                (,head (fd-stream-ibuf-head stream)))
521            ,@body)))
522      (setf *input-routines*
523            (nconc *input-routines*
524                   (list (list ',type ',name ',size))))))
525
526 ;;; STREAM-IN routine for reading a string char
527 (def-input-routine input-character
528                    (character 1 sap head)
529   (code-char (sap-ref-8 sap head)))
530
531 ;;; STREAM-IN routine for reading an unsigned 8 bit number
532 (def-input-routine input-unsigned-8bit-byte
533                    ((unsigned-byte 8) 1 sap head)
534   (sap-ref-8 sap head))
535
536 ;;; STREAM-IN routine for reading a signed 8 bit number
537 (def-input-routine input-signed-8bit-number
538                    ((signed-byte 8) 1 sap head)
539   (signed-sap-ref-8 sap head))
540
541 ;;; STREAM-IN routine for reading an unsigned 16 bit number
542 (def-input-routine input-unsigned-16bit-byte
543                    ((unsigned-byte 16) 2 sap head)
544   (sap-ref-16 sap head))
545
546 ;;; STREAM-IN routine for reading a signed 16 bit number
547 (def-input-routine input-signed-16bit-byte
548                    ((signed-byte 16) 2 sap head)
549   (signed-sap-ref-16 sap head))
550
551 ;;; STREAM-IN routine for reading a unsigned 32 bit number
552 (def-input-routine input-unsigned-32bit-byte
553                    ((unsigned-byte 32) 4 sap head)
554   (sap-ref-32 sap head))
555
556 ;;; STREAM-IN routine for reading a signed 32 bit number
557 (def-input-routine input-signed-32bit-byte
558                    ((signed-byte 32) 4 sap head)
559   (signed-sap-ref-32 sap head))
560
561 ;;; Find an input routine to use given the type. Return as multiple
562 ;;; values the routine, the real type transfered, and the number of
563 ;;; bytes per element.
564 (defun pick-input-routine (type)
565   (dolist (entry *input-routines*)
566     (when (subtypep type (car entry))
567       (return (values (symbol-function (cadr entry))
568                       (car entry)
569                       (caddr entry))))))
570
571 ;;; Returns a string constructed from the sap, start, and end.
572 (defun string-from-sap (sap start end)
573   (declare (type index start end))
574   (let* ((length (- end start))
575          (string (make-string length)))
576     (copy-from-system-area sap (* start sb!vm:byte-bits)
577                            string (* sb!vm:vector-data-offset sb!vm:word-bits)
578                            (* length sb!vm:byte-bits))
579     string))
580
581 ;;; the N-BIN method for FD-STREAMs. This blocks in UNIX-READ. It is
582 ;;; generally used where there is a definite amount of reading to be
583 ;;; done, so blocking isn't too problematical.
584 (defun fd-stream-read-n-bytes (stream buffer start requested eof-error-p)
585   (declare (type fd-stream stream))
586   (declare (type index start requested))
587   (do ((total-copied 0))
588       (nil)
589     (declare (type index total-copied))
590     (let* ((remaining-request (- requested total-copied))
591            (head (fd-stream-ibuf-head stream))
592            (tail (fd-stream-ibuf-tail stream))
593            (available (- tail head))
594            (this-copy (min remaining-request available))
595            (this-start (+ start total-copied))
596            (sap (fd-stream-ibuf-sap stream)))
597       (declare (type index remaining-request head tail available))
598       (declare (type index this-copy))
599       ;; Copy data from stream buffer into user's buffer. 
600       (if (typep buffer 'system-area-pointer)
601           (system-area-copy sap (* head sb!vm:byte-bits)
602                             buffer (* this-start sb!vm:byte-bits)
603                             (* this-copy sb!vm:byte-bits))
604           (copy-from-system-area sap (* head sb!vm:byte-bits)
605                                  buffer (+ (* this-start sb!vm:byte-bits)
606                                            (* sb!vm:vector-data-offset
607                                               sb!vm:word-bits))
608                                  (* this-copy sb!vm:byte-bits)))
609       (incf (fd-stream-ibuf-head stream) this-copy)
610       (incf total-copied this-copy)
611       ;; Maybe we need to refill the stream buffer.
612       (cond (;; If there were enough data in the stream buffer, we're done.
613              (= total-copied requested)
614              (return total-copied))
615             (;; If EOF, we're done in another way.
616              (zerop (refill-fd-stream-buffer stream))
617              (if eof-error-p
618                  (error 'end-of-file :stream stream)
619                  (return total-copied)))
620             ;; Otherwise we refilled the stream buffer, so fall
621             ;; through into another pass of the loop.
622             ))))
623
624 ;;; Try to refill the stream buffer. Return the number of bytes read.
625 ;;; (For EOF, the return value will be zero, otherwise positive.)
626 (defun refill-fd-stream-buffer (stream)
627   ;; We don't have any logic to preserve leftover bytes in the buffer,
628   ;; so we should only be called when the buffer is empty.
629   (aver (= (fd-stream-ibuf-head stream) (fd-stream-ibuf-tail stream)))
630   (multiple-value-bind (count err)
631       (sb!unix:unix-read (fd-stream-fd stream)
632                          (fd-stream-ibuf-sap stream)
633                          (fd-stream-ibuf-length stream))
634     (declare (type (or index null) count))
635     (when (null count)
636       (error "error reading ~S: ~A"
637              stream
638              (sb!unix:get-unix-error-msg err)))
639     (setf (fd-stream-listen stream) nil
640           (fd-stream-ibuf-head stream) 0
641           (fd-stream-ibuf-tail stream) count)
642 ;    (format t "~%buffer=~%--~%")
643 ;    (dotimes (i count)
644 ;      (write-char (code-char (sap-ref-8 (fd-stream-ibuf-sap stream) i))))
645 ;    (format t "~%--~%")
646     #+nil
647     (format t "/REFILL-FD-STREAM-BUFFER = ~D~%" count)
648     count))
649 \f
650 ;;;; utility functions (misc routines, etc)
651
652 ;;; Fill in the various routine slots for the given type. INPUT-P and
653 ;;; OUTPUT-P indicate what slots to fill. The buffering slot must be
654 ;;; set prior to calling this routine.
655 (defun set-fd-stream-routines (fd-stream type input-p output-p buffer-p)
656   (let ((target-type (case type
657                        ((:default unsigned-byte)
658                         '(unsigned-byte 8))
659                        (signed-byte
660                         '(signed-byte 8))
661                        (t
662                         type)))
663         (input-type nil)
664         (output-type nil)
665         (input-size nil)
666         (output-size nil))
667
668     (when (fd-stream-obuf-sap fd-stream)
669       (push (fd-stream-obuf-sap fd-stream) *available-buffers*)
670       (setf (fd-stream-obuf-sap fd-stream) nil))
671     (when (fd-stream-ibuf-sap fd-stream)
672       (push (fd-stream-ibuf-sap fd-stream) *available-buffers*)
673       (setf (fd-stream-ibuf-sap fd-stream) nil))
674
675     (when input-p
676       (multiple-value-bind (routine type size)
677           (pick-input-routine target-type)
678         (unless routine
679           (error "could not find any input routine for ~S" target-type))
680         (setf (fd-stream-ibuf-sap fd-stream) (next-available-buffer))
681         (setf (fd-stream-ibuf-length fd-stream) bytes-per-buffer)
682         (setf (fd-stream-ibuf-tail fd-stream) 0)
683         (if (subtypep type 'character)
684             (setf (fd-stream-in fd-stream) routine
685                   (fd-stream-bin fd-stream) #'ill-bin)
686             (setf (fd-stream-in fd-stream) #'ill-in
687                   (fd-stream-bin fd-stream) routine))
688         (when (eql size 1)
689           (setf (fd-stream-n-bin fd-stream) #'fd-stream-read-n-bytes)
690           (when buffer-p
691             (setf (lisp-stream-in-buffer fd-stream)
692                   (make-array +in-buffer-length+
693                               :element-type '(unsigned-byte 8)))))
694         (setf input-size size)
695         (setf input-type type)))
696
697     (when output-p
698       (multiple-value-bind (routine type size)
699           (pick-output-routine target-type (fd-stream-buffering fd-stream))
700         (unless routine
701           (error "could not find any output routine for ~S buffered ~S"
702                  (fd-stream-buffering fd-stream)
703                  target-type))
704         (setf (fd-stream-obuf-sap fd-stream) (next-available-buffer))
705         (setf (fd-stream-obuf-length fd-stream) bytes-per-buffer)
706         (setf (fd-stream-obuf-tail fd-stream) 0)
707         (if (subtypep type 'character)
708           (setf (fd-stream-out fd-stream) routine
709                 (fd-stream-bout fd-stream) #'ill-bout)
710           (setf (fd-stream-out fd-stream)
711                 (or (if (eql size 1)
712                       (pick-output-routine 'base-char
713                                            (fd-stream-buffering fd-stream)))
714                     #'ill-out)
715                 (fd-stream-bout fd-stream) routine))
716         (setf (fd-stream-sout fd-stream)
717               (if (eql size 1) #'fd-sout #'ill-out))
718         (setf (fd-stream-char-pos fd-stream) 0)
719         (setf output-size size)
720         (setf output-type type)))
721
722     (when (and input-size output-size
723                (not (eq input-size output-size)))
724       (error "Element sizes for input (~S:~S) and output (~S:~S) differ?"
725              input-type input-size
726              output-type output-size))
727     (setf (fd-stream-element-size fd-stream)
728           (or input-size output-size))
729
730     (setf (fd-stream-element-type fd-stream)
731           (cond ((equal input-type output-type)
732                  input-type)
733                 ((null output-type)
734                  input-type)
735                 ((null input-type)
736                  output-type)
737                 ((subtypep input-type output-type)
738                  input-type)
739                 ((subtypep output-type input-type)
740                  output-type)
741                 (t
742                  (error "Input type (~S) and output type (~S) are unrelated?"
743                         input-type
744                         output-type))))))
745
746 ;;; Handle miscellaneous operations on FD-STREAM.
747 (defun fd-stream-misc-routine (fd-stream operation &optional arg1 arg2)
748   (declare (ignore arg2))
749   (case operation
750     (:listen
751      (or (not (eql (fd-stream-ibuf-head fd-stream)
752                    (fd-stream-ibuf-tail fd-stream)))
753          (fd-stream-listen fd-stream)
754          (setf (fd-stream-listen fd-stream)
755                (eql (sb!alien:with-alien ((read-fds (sb!alien:struct
756                                                      sb!unix:fd-set)))
757                       (sb!unix:fd-zero read-fds)
758                       (sb!unix:fd-set (fd-stream-fd fd-stream) read-fds)
759                       (sb!unix:unix-fast-select (1+ (fd-stream-fd fd-stream))
760                                                 (sb!alien:addr read-fds)
761                                                 nil nil 0 0))
762                     1))))
763     (:unread
764      (setf (fd-stream-unread fd-stream) arg1)
765      (setf (fd-stream-listen fd-stream) t))
766     (:close
767      (cond (arg1
768             ;; We got us an abort on our hands.
769             (when (fd-stream-handler fd-stream)
770                   (sb!sys:remove-fd-handler (fd-stream-handler fd-stream))
771                   (setf (fd-stream-handler fd-stream) nil))
772             (when (and (fd-stream-file fd-stream)
773                        (fd-stream-obuf-sap fd-stream))
774               ;; We can't do anything unless we know what file were
775               ;; dealing with, and we don't want to do anything
776               ;; strange unless we were writing to the file.
777               (if (fd-stream-original fd-stream)
778                   ;; We have a handle on the original, just revert.
779                   (multiple-value-bind (okay err)
780                       (sb!unix:unix-rename (fd-stream-original fd-stream)
781                                            (fd-stream-file fd-stream))
782                     (unless okay
783                       (error "~@<could not restore ~S to its original ~
784                               contents: ~2I~_~A~:>"
785                              (fd-stream-file fd-stream)
786                              (sb!unix:get-unix-error-msg err))))
787                   ;; We can't restore the original, so nuke that puppy.
788                   (multiple-value-bind (okay err)
789                       (sb!unix:unix-unlink (fd-stream-file fd-stream))
790                     (unless okay
791                       (error "~@<could not remove ~S: ~2I~_~A~:>"
792                              (fd-stream-file fd-stream)
793                              (sb!unix:get-unix-error-msg err)))))))
794            (t
795             (fd-stream-misc-routine fd-stream :finish-output)
796             (when (and (fd-stream-original fd-stream)
797                        (fd-stream-delete-original fd-stream))
798               (multiple-value-bind (okay err)
799                   (sb!unix:unix-unlink (fd-stream-original fd-stream))
800                 (unless okay
801                   (error "~@<could not delete ~S during close ~
802                            of ~S: ~2I~_~A~:>"
803                          (fd-stream-original fd-stream)
804                          fd-stream
805                          (sb!unix:get-unix-error-msg err)))))))
806      (when (fboundp 'cancel-finalization)
807        (cancel-finalization fd-stream))
808      (sb!unix:unix-close (fd-stream-fd fd-stream))
809      (when (fd-stream-obuf-sap fd-stream)
810        (push (fd-stream-obuf-sap fd-stream) *available-buffers*)
811        (setf (fd-stream-obuf-sap fd-stream) nil))
812      (when (fd-stream-ibuf-sap fd-stream)
813        (push (fd-stream-ibuf-sap fd-stream) *available-buffers*)
814        (setf (fd-stream-ibuf-sap fd-stream) nil))
815      (sb!impl::set-closed-flame fd-stream))
816     (:clear-input
817      (setf (fd-stream-unread fd-stream) nil)
818      (setf (fd-stream-ibuf-head fd-stream) 0)
819      (setf (fd-stream-ibuf-tail fd-stream) 0)
820      (catch 'eof-input-catcher
821        (loop
822         (let ((count (sb!alien:with-alien ((read-fds (sb!alien:struct
823                                                       sb!unix:fd-set)))
824                        (sb!unix:fd-zero read-fds)
825                        (sb!unix:fd-set (fd-stream-fd fd-stream) read-fds)
826                        (sb!unix:unix-fast-select (1+ (fd-stream-fd fd-stream))
827                                                  (sb!alien:addr read-fds)
828                                                  nil
829                                                  nil
830                                                  0
831                                                  0))))
832           (cond ((eql count 1)
833                  (do-input fd-stream)
834                  (setf (fd-stream-ibuf-head fd-stream) 0)
835                  (setf (fd-stream-ibuf-tail fd-stream) 0))
836                 (t
837                  (return t)))))))
838     (:force-output
839      (flush-output-buffer fd-stream))
840     (:finish-output
841      (flush-output-buffer fd-stream)
842      (do ()
843          ((null (fd-stream-output-later fd-stream)))
844        (sb!sys:serve-all-events)))
845     (:element-type
846      (fd-stream-element-type fd-stream))
847     (:interactive-p
848       ;; FIXME: sb!unix:unix-isatty is undefined.
849      (sb!unix:unix-isatty (fd-stream-fd fd-stream)))
850     (:line-length
851      80)
852     (:charpos
853      (fd-stream-char-pos fd-stream))
854     (:file-length
855      (multiple-value-bind (okay dev ino mode nlink uid gid rdev size
856                            atime mtime ctime blksize blocks)
857          (sb!unix:unix-fstat (fd-stream-fd fd-stream))
858        (declare (ignore ino nlink uid gid rdev
859                         atime mtime ctime blksize blocks))
860        (unless okay
861          (error "error in Unix fstat(2) on ~S: ~A"
862                 fd-stream
863                 (sb!unix:get-unix-error-msg dev)))
864        (if (zerop mode)
865            nil
866            (truncate size (fd-stream-element-size fd-stream)))))
867     (:file-position
868      (fd-stream-file-position fd-stream arg1))))
869
870 (defun fd-stream-file-position (stream &optional newpos)
871   (declare (type fd-stream stream)
872            (type (or index (member nil :start :end)) newpos))
873   (if (null newpos)
874       (sb!sys:without-interrupts
875         ;; First, find the position of the UNIX file descriptor in the
876         ;; file.
877         (multiple-value-bind (posn errno)
878             (sb!unix:unix-lseek (fd-stream-fd stream) 0 sb!unix:l_incr)
879           (declare (type (or index null) posn))
880           (cond ((fixnump posn)
881                  ;; Adjust for buffered output: If there is any output
882                  ;; buffered, the *real* file position will be larger
883                  ;; than reported by lseek because lseek obviously
884                  ;; cannot take into account output we have not sent
885                  ;; yet.
886                  (dolist (later (fd-stream-output-later stream))
887                    (incf posn (- (the index (caddr later))
888                                  (the index (cadr later)))))
889                  (incf posn (fd-stream-obuf-tail stream))
890                  ;; Adjust for unread input: If there is any input
891                  ;; read from UNIX but not supplied to the user of the
892                  ;; stream, the *real* file position will smaller than
893                  ;; reported, because we want to look like the unread
894                  ;; stuff is still available.
895                  (decf posn (- (fd-stream-ibuf-tail stream)
896                                (fd-stream-ibuf-head stream)))
897                  (when (fd-stream-unread stream)
898                    (decf posn))
899                  ;; Divide bytes by element size.
900                  (truncate posn (fd-stream-element-size stream)))
901                 ((eq errno sb!unix:espipe)
902                  nil)
903                 (t
904                  (sb!sys:with-interrupts
905                    (error "error LSEEK'ing ~S: ~A"
906                           stream
907                           (sb!unix:get-unix-error-msg errno)))))))
908       (let ((offset 0) origin)
909         (declare (type index offset))
910         ;; Make sure we don't have any output pending, because if we
911         ;; move the file pointer before writing this stuff, it will be
912         ;; written in the wrong location.
913         (flush-output-buffer stream)
914         (do ()
915             ((null (fd-stream-output-later stream)))
916           (sb!sys:serve-all-events))
917         ;; Clear out any pending input to force the next read to go to
918         ;; the disk.
919         (setf (fd-stream-unread stream) nil)
920         (setf (fd-stream-ibuf-head stream) 0)
921         (setf (fd-stream-ibuf-tail stream) 0)
922         ;; Trash cached value for listen, so that we check next time.
923         (setf (fd-stream-listen stream) nil)
924         ;; Now move it.
925         (cond ((eq newpos :start)
926                (setf offset 0 origin sb!unix:l_set))
927               ((eq newpos :end)
928                (setf offset 0 origin sb!unix:l_xtnd))
929               ((typep newpos 'index)
930                (setf offset (* newpos (fd-stream-element-size stream))
931                      origin sb!unix:l_set))
932               (t
933                (error "invalid position given to file-position: ~S" newpos)))
934         (multiple-value-bind (posn errno)
935             (sb!unix:unix-lseek (fd-stream-fd stream) offset origin)
936           (cond ((typep posn 'fixnum)
937                  t)
938                 ((eq errno sb!unix:espipe)
939                  nil)
940                 (t
941                  (error "error lseek'ing ~S: ~A"
942                         stream
943                         (sb!unix:get-unix-error-msg errno))))))))
944 \f
945 ;;;; creation routines (MAKE-FD-STREAM and OPEN)
946
947 ;;; Create a stream for the given Unix file descriptor.
948 ;;;
949 ;;; If INPUT is non-NIL, allow input operations. If OUTPUT is non-nil,
950 ;;; allow output operations. If neither INPUT nor OUTPUT is specified,
951 ;;; default to allowing input.
952 ;;;
953 ;;; ELEMENT-TYPE indicates the element type to use (as for OPEN).
954 ;;;
955 ;;; BUFFERING indicates the kind of buffering to use.
956 ;;;
957 ;;; TIMEOUT (if true) is the number of seconds to wait for input. If
958 ;;; NIL (the default), then wait forever. When we time out, we signal
959 ;;; IO-TIMEOUT.
960 ;;;
961 ;;; FILE is the name of the file (will be returned by PATHNAME).
962 ;;;
963 ;;; NAME is used to identify the stream when printed.
964 (defun make-fd-stream (fd
965                        &key
966                        (input nil input-p)
967                        (output nil output-p)
968                        (element-type 'base-char)
969                        (buffering :full)
970                        timeout
971                        file
972                        original
973                        delete-original
974                        pathname
975                        input-buffer-p
976                        (name (if file
977                                  (format nil "file ~S" file)
978                                  (format nil "descriptor ~D" fd)))
979                        auto-close)
980   (declare (type index fd) (type (or index null) timeout)
981            (type (member :none :line :full) buffering))
982   (cond ((not (or input-p output-p))
983          (setf input t))
984         ((not (or input output))
985          (error "File descriptor must be opened either for input or output.")))
986   (let ((stream (%make-fd-stream :fd fd
987                                  :name name
988                                  :file file
989                                  :original original
990                                  :delete-original delete-original
991                                  :pathname pathname
992                                  :buffering buffering
993                                  :timeout timeout)))
994     (set-fd-stream-routines stream element-type input output input-buffer-p)
995     (when (and auto-close (fboundp 'finalize))
996       (finalize stream
997                 (lambda ()
998                   (sb!unix:unix-close fd)
999                   #!+sb-show
1000                   (format *terminal-io* "** closed file descriptor ~D **~%"
1001                           fd))))
1002     stream))
1003
1004 ;;; Pick a name to use for the backup file for the :IF-EXISTS
1005 ;;; :RENAME-AND-DELETE and :RENAME options.
1006 (defun pick-backup-name (name)
1007   (declare (type simple-string name))
1008   (concatenate 'simple-string name ".bak"))
1009
1010 ;;; Ensure that the given arg is one of the given list of valid
1011 ;;; things. Allow the user to fix any problems.
1012 (defun ensure-one-of (item list what)
1013   (unless (member item list)
1014     (error 'simple-type-error
1015            :datum item
1016            :expected-type `(member ,@list)
1017            :format-control "~@<~S is ~_invalid for ~S; ~_need one of~{ ~S~}~:>"
1018            :format-arguments (list item what list))))
1019
1020 ;;; Rename NAMESTRING to ORIGINAL. First, check whether we have write
1021 ;;; access, since we don't want to trash unwritable files even if we
1022 ;;; technically can. We return true if we succeed in renaming.
1023 (defun do-old-rename (namestring original)
1024   (unless (sb!unix:unix-access namestring sb!unix:w_ok)
1025     (error "~@<The file ~2I~_~S ~I~_is not writable.~:>" namestring))
1026   (multiple-value-bind (okay err) (sb!unix:unix-rename namestring original)
1027     (cond (okay t)
1028           (t
1029            (error "~@<could not rename ~2I~_~S ~I~_to ~2I~_~S: ~4I~_~A~:>"
1030                   namestring
1031                   original
1032                   (sb!unix:get-unix-error-msg err))
1033            nil))))
1034
1035 (defun open (filename
1036              &key
1037              (direction :input)
1038              (element-type 'base-char)
1039              (if-exists nil if-exists-given)
1040              (if-does-not-exist nil if-does-not-exist-given)
1041              (external-format :default)
1042              &aux ; Squelch assignment warning.
1043              (direction direction)
1044              (if-does-not-exist if-does-not-exist)
1045              (if-exists if-exists))
1046   #!+sb-doc
1047   "Return a stream which reads from or writes to FILENAME.
1048   Defined keywords:
1049    :DIRECTION - one of :INPUT, :OUTPUT, :IO, or :PROBE
1050    :ELEMENT-TYPE - the type of object to read or write, default BASE-CHAR
1051    :IF-EXISTS - one of :ERROR, :NEW-VERSION, :RENAME, :RENAME-AND-DELETE,
1052                        :OVERWRITE, :APPEND, :SUPERSEDE or NIL
1053    :IF-DOES-NOT-EXIST - one of :ERROR, :CREATE or nil
1054   See the manual for details."
1055
1056   (unless (eq external-format :default)
1057     (error "Any external format other than :DEFAULT isn't recognized."))
1058
1059   ;; First, make sure that DIRECTION is valid.
1060   (ensure-one-of direction
1061                  '(:input :output :io :probe)
1062                  :direction)
1063
1064   ;; Calculate useful stuff.
1065   (multiple-value-bind (input output mask)
1066       (case direction
1067         (:input  (values   t nil sb!unix:o_rdonly))
1068         (:output (values nil   t sb!unix:o_wronly))
1069         (:io     (values   t   t sb!unix:o_rdwr))
1070         (:probe  (values   t nil sb!unix:o_rdonly)))
1071     (declare (type index mask))
1072     (let* ((pathname (pathname filename))
1073            (namestring
1074             (cond ((unix-namestring pathname input))
1075                   ((and input (eq if-does-not-exist :create))
1076                    (unix-namestring pathname nil)))))
1077       ;; Process if-exists argument if we are doing any output.
1078       (cond (output
1079              (unless if-exists-given
1080                (setf if-exists
1081                      (if (eq (pathname-version pathname) :newest)
1082                          :new-version
1083                          :error)))
1084              (ensure-one-of if-exists
1085                             '(:error :new-version :rename
1086                                      :rename-and-delete :overwrite
1087                                      :append :supersede nil)
1088                             :if-exists)
1089              (case if-exists
1090                ((:error nil)
1091                 (setf mask (logior mask sb!unix:o_excl)))
1092                ((:rename :rename-and-delete)
1093                 (setf mask (logior mask sb!unix:o_creat)))
1094                ((:new-version :supersede)
1095                 (setf mask (logior mask sb!unix:o_trunc)))
1096                (:append
1097                 (setf mask (logior mask sb!unix:o_append)))))
1098             (t
1099              (setf if-exists :ignore-this-arg)))
1100
1101       (unless if-does-not-exist-given
1102         (setf if-does-not-exist
1103               (cond ((eq direction :input) :error)
1104                     ((and output
1105                           (member if-exists '(:overwrite :append)))
1106                      :error)
1107                     ((eq direction :probe)
1108                      nil)
1109                     (t
1110                      :create))))
1111       (ensure-one-of if-does-not-exist
1112                      '(:error :create nil)
1113                      :if-does-not-exist)
1114       (if (eq if-does-not-exist :create)
1115         (setf mask (logior mask sb!unix:o_creat)))
1116
1117       (let ((original (if (member if-exists
1118                                   '(:rename :rename-and-delete))
1119                           (pick-backup-name namestring)))
1120             (delete-original (eq if-exists :rename-and-delete))
1121             (mode #o666))
1122         (when original
1123           ;; We are doing a :RENAME or :RENAME-AND-DELETE.
1124           ;; Determine whether the file already exists, make sure the original
1125           ;; file is not a directory, and keep the mode.
1126           (let ((exists
1127                  (and namestring
1128                       (multiple-value-bind (okay err/dev inode orig-mode)
1129                           (sb!unix:unix-stat namestring)
1130                         (declare (ignore inode)
1131                                  (type (or index null) orig-mode))
1132                         (cond
1133                          (okay
1134                           (when (and output (= (logand orig-mode #o170000)
1135                                                #o40000))
1136                             (error "cannot open ~S for output: is a directory"
1137                                    namestring))
1138                           (setf mode (logand orig-mode #o777))
1139                           t)
1140                          ((eql err/dev sb!unix:enoent)
1141                           nil)
1142                          (t
1143                           (error "cannot find ~S: ~A"
1144                                  namestring
1145                                  (sb!unix:get-unix-error-msg err/dev))))))))
1146             (unless (and exists
1147                          (do-old-rename namestring original))
1148               (setf original nil)
1149               (setf delete-original nil)
1150               ;; In order to use :SUPERSEDE instead, we have to make sure
1151               ;; SB!UNIX:O_CREAT corresponds to IF-DOES-NOT-EXIST.
1152               ;; SB!UNIX:O_CREAT was set before because of IF-EXISTS being
1153               ;; :RENAME.
1154               (unless (eq if-does-not-exist :create)
1155                 (setf mask
1156                       (logior (logandc2 mask sb!unix:o_creat)
1157                               sb!unix:o_trunc)))
1158               (setf if-exists :supersede))))
1159         
1160         ;; Now we can try the actual Unix open(2).
1161         (multiple-value-bind (fd errno)
1162             (if namestring
1163                 (sb!unix:unix-open namestring mask mode)
1164                 (values nil sb!unix:enoent))
1165           (labels ((open-error (format-control &rest format-arguments)
1166                      (error 'simple-file-error
1167                             :pathname pathname
1168                             :format-control format-control
1169                             :format-arguments format-arguments))
1170                    (vanilla-open-error ()
1171                      (open-error "~@<error opening ~S: ~2I~_~A~:>"
1172                                  pathname
1173                                  (sb!unix:get-unix-error-msg errno))))
1174             (cond ((numberp fd)
1175                    (case direction
1176                      ((:input :output :io)
1177                       (make-fd-stream fd
1178                                       :input input
1179                                       :output output
1180                                       :element-type element-type
1181                                       :file namestring
1182                                       :original original
1183                                       :delete-original delete-original
1184                                       :pathname pathname
1185                                       :input-buffer-p t
1186                                       :auto-close t))
1187                      (:probe
1188                       (let ((stream
1189                              (%make-fd-stream :name namestring
1190                                               :fd fd
1191                                               :pathname pathname
1192                                               :element-type element-type)))
1193                         (close stream)
1194                         stream))))
1195                   ((eql errno sb!unix:enoent)
1196                    (case if-does-not-exist
1197                      (:error (vanilla-open-error))
1198                      (:create
1199                       (open-error
1200                        "~@<The path ~2I~_~S ~I~_does not exist.~:>"
1201                        pathname))
1202                      (t nil)))
1203                   ((and (eql errno sb!unix:eexist) if-exists)
1204                    nil)
1205                   (t
1206                    (vanilla-open-error)))))))))
1207 \f
1208 ;;;; initialization
1209
1210 ;;; the stream connected to the controlling terminal, or NIL if there is none
1211 (defvar *tty*)
1212
1213 ;;; the stream connected to the standard input (file descriptor 0)
1214 (defvar *stdin*)
1215
1216 ;;; the stream connected to the standard output (file descriptor 1)
1217 (defvar *stdout*)
1218
1219 ;;; the stream connected to the standard error output (file descriptor 2)
1220 (defvar *stderr*)
1221
1222 ;;; This is called when the cold load is first started up, and may also
1223 ;;; be called in an attempt to recover from nested errors.
1224 (defun stream-cold-init-or-reset ()
1225   (stream-reinit)
1226   (setf *terminal-io* (make-synonym-stream '*tty*))
1227   (setf *standard-output* (make-synonym-stream '*stdout*))
1228   (setf *standard-input*
1229         (#!-high-security
1230          ;; FIXME: Why is *STANDARD-INPUT* a TWO-WAY-STREAM? ANSI says
1231          ;; it's an input stream.
1232          make-two-way-stream
1233          #!+high-security
1234          %make-two-way-stream (make-synonym-stream '*stdin*)
1235                              *standard-output*))
1236   (setf *error-output* (make-synonym-stream '*stderr*))
1237   (setf *query-io* (make-synonym-stream '*terminal-io*))
1238   (setf *debug-io* *query-io*)
1239   (setf *trace-output* *standard-output*)
1240   (values))
1241
1242 ;;; This is called whenever a saved core is restarted.
1243 (defun stream-reinit ()
1244   (setf *available-buffers* nil)
1245   (setf *stdin*
1246         (make-fd-stream 0 :name "standard input" :input t :buffering :line))
1247   (setf *stdout*
1248         (make-fd-stream 1 :name "standard output" :output t :buffering :line))
1249   (setf *stderr*
1250         (make-fd-stream 2 :name "standard error" :output t :buffering :line))
1251   (let ((tty (sb!unix:unix-open "/dev/tty" sb!unix:o_rdwr #o666)))
1252     (if tty
1253         (setf *tty*
1254               (make-fd-stream tty
1255                               :name "the terminal"
1256                               :input t
1257                               :output t
1258                               :buffering :line
1259                               :auto-close t))
1260         (setf *tty* (make-two-way-stream *stdin* *stdout*))))
1261   (values))
1262 \f
1263 ;;;; miscellany
1264
1265 ;;; the Unix way to beep
1266 (defun beep (stream)
1267   (write-char (code-char bell-char-code) stream)
1268   (finish-output stream))
1269
1270 ;;; This is kind of like FILE-POSITION, but is an internal hack used
1271 ;;; by the filesys stuff to get and set the file name.
1272 (defun file-name (stream &optional new-name)
1273   (when (typep stream 'fd-stream)
1274       (cond (new-name
1275              (setf (fd-stream-pathname stream) new-name)
1276              (setf (fd-stream-file stream)
1277                    (unix-namestring new-name nil))
1278              t)
1279             (t
1280              (fd-stream-pathname stream)))))
1281 \f
1282 ;;;; international character support (which is trivial for our simple
1283 ;;;; character sets)
1284
1285 ;;;; (Those who do Lisp only in English might not remember that ANSI
1286 ;;;; requires these functions to be exported from package
1287 ;;;; COMMON-LISP.)
1288
1289 (defun file-string-length (stream object)
1290   (declare (type (or string character) object) (type file-stream stream))
1291   #!+sb-doc
1292   "Return the delta in STREAM's FILE-POSITION that would be caused by writing
1293    OBJECT to STREAM. Non-trivial only in implementations that support
1294    international character sets."
1295   (declare (ignore stream))
1296   (etypecase object
1297     (character 1)
1298     (string (length object))))
1299
1300 (defun stream-external-format (stream)
1301   (declare (type file-stream stream) (ignore stream))
1302   #!+sb-doc
1303   "Return :DEFAULT."
1304   :default)