0.6.11.23:
[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 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 (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              (cerror "Just go on as if nothing happened."
306                      "~S called with :END before :START!"
307                      'output-raw-bytes))
308             ((zerop bytes)) ; Easy case
309             ((<= bytes space)
310              (if (system-area-pointer-p thing)
311                  (system-area-copy thing
312                                    (* start sb!vm:byte-bits)
313                                    (fd-stream-obuf-sap fd-stream)
314                                    (* tail sb!vm:byte-bits)
315                                    (* bytes sb!vm:byte-bits))
316                  ;; FIXME: There should be some type checking somewhere to
317                  ;; verify that THING here is a vector, not just <not a SAP>.
318                  (copy-to-system-area thing
319                                       (+ (* start sb!vm:byte-bits)
320                                          (* sb!vm:vector-data-offset
321                                             sb!vm:word-bits))
322                                       (fd-stream-obuf-sap fd-stream)
323                                       (* tail sb!vm:byte-bits)
324                                       (* bytes sb!vm:byte-bits)))
325              (setf (fd-stream-obuf-tail fd-stream) newtail))
326             ((<= bytes len)
327              (flush-output-buffer fd-stream)
328              (if (system-area-pointer-p thing)
329                  (system-area-copy thing
330                                    (* start sb!vm:byte-bits)
331                                    (fd-stream-obuf-sap fd-stream)
332                                    0
333                                    (* bytes sb!vm:byte-bits))
334                  ;; FIXME: There should be some type checking somewhere to
335                  ;; verify that THING here is a vector, not just <not a SAP>.
336                  (copy-to-system-area thing
337                                       (+ (* start sb!vm:byte-bits)
338                                          (* sb!vm:vector-data-offset
339                                             sb!vm:word-bits))
340                                       (fd-stream-obuf-sap fd-stream)
341                                       0
342                                       (* bytes sb!vm:byte-bits)))
343              (setf (fd-stream-obuf-tail fd-stream) bytes))
344             (t
345              (flush-output-buffer fd-stream)
346              (do-output fd-stream thing start end nil))))))
347
348 ;;; the routine to use to output a string. If the stream is
349 ;;; unbuffered, slam the string down the file descriptor, otherwise
350 ;;; use OUTPUT-RAW-BYTES to buffer the string. Update charpos by
351 ;;; checking to see where the last newline was.
352 ;;;
353 ;;; Note: some bozos (the FASL dumper) call write-string with things
354 ;;; other than strings. Therefore, we must make sure we have a string
355 ;;; before calling POSITION on it.
356 ;;; KLUDGE: It would be better to fix the bozos instead of trying to
357 ;;; cover for them here. -- WHN 20000203
358 (defun fd-sout (stream thing start end)
359   (let ((start (or start 0))
360         (end (or end (length (the vector thing)))))
361     (declare (fixnum start end))
362     (if (stringp thing)
363         (let ((last-newline (and (find #\newline (the simple-string thing)
364                                        :start start :end end)
365                                  (position #\newline (the simple-string thing)
366                                            :from-end t
367                                            :start start
368                                            :end end))))
369           (ecase (fd-stream-buffering stream)
370             (:full
371              (output-raw-bytes stream thing start end))
372             (:line
373              (output-raw-bytes stream thing start end)
374              (when last-newline
375                (flush-output-buffer stream)))
376             (:none
377              (do-output stream thing start end nil)))
378           (if last-newline
379               (setf (fd-stream-char-pos stream)
380                     (- end last-newline 1))
381               (incf (fd-stream-char-pos stream)
382                     (- end start))))
383         (ecase (fd-stream-buffering stream)
384           ((:line :full)
385            (output-raw-bytes stream thing start end))
386           (:none
387            (do-output stream thing start end nil))))))
388
389 ;;; Find an output routine to use given the type and buffering. Return
390 ;;; as multiple values the routine, the real type transfered, and the
391 ;;; number of bytes per element.
392 (defun pick-output-routine (type buffering)
393   (dolist (entry *output-routines*)
394     (when (and (subtypep type (car entry))
395                (eq buffering (cadr entry)))
396       (return (values (symbol-function (caddr entry))
397                       (car entry)
398                       (cadddr entry))))))
399 \f
400 ;;;; input routines and related noise
401
402 (defvar *input-routines* ()
403   #!+sb-doc
404   "List of all available input routines. Each element is a list of the
405   element-type input, the function name, and the number of bytes per element.")
406
407 ;;; Fill the input buffer, and return the first character. Throw to
408 ;;; EOF-INPUT-CATCHER if the eof was reached. Drop into SYSTEM:SERVER
409 ;;; if necessary.
410 (defun do-input (stream)
411   (let ((fd (fd-stream-fd stream))
412         (ibuf-sap (fd-stream-ibuf-sap stream))
413         (buflen (fd-stream-ibuf-length stream))
414         (head (fd-stream-ibuf-head stream))
415         (tail (fd-stream-ibuf-tail stream)))
416     (declare (type index head tail))
417     (unless (zerop head)
418       (cond ((eql head tail)
419              (setf head 0)
420              (setf tail 0)
421              (setf (fd-stream-ibuf-head stream) 0)
422              (setf (fd-stream-ibuf-tail stream) 0))
423             (t
424              (decf tail head)
425              (system-area-copy ibuf-sap (* head sb!vm:byte-bits)
426                                ibuf-sap 0 (* tail sb!vm:byte-bits))
427              (setf head 0)
428              (setf (fd-stream-ibuf-head stream) 0)
429              (setf (fd-stream-ibuf-tail stream) tail))))
430     (setf (fd-stream-listen stream) nil)
431     (multiple-value-bind (count errno)
432         ;; FIXME: Judging from compiler warnings, this WITH-ALIEN form expands
433         ;; into something which uses the not-yet-defined type
434         ;;   (SB!ALIEN-INTERNALS:ALIEN (* (SB!ALIEN:STRUCT SB!UNIX:FD-SET))).
435         ;; This is probably inefficient and unsafe and generally bad, so
436         ;; try to find some way to make that type known before
437         ;; this is compiled.
438         (sb!alien:with-alien ((read-fds (sb!alien:struct sb!unix:fd-set)))
439           (sb!unix:fd-zero read-fds)
440           (sb!unix:fd-set fd read-fds)
441           (sb!unix:unix-fast-select (1+ fd)
442                                     (sb!alien:addr read-fds)
443                                     nil
444                                     nil
445                                     0
446                                     0))
447       (case count
448         (1)
449         (0
450          (unless #!-mp (sb!sys:wait-until-fd-usable
451                        fd :input (fd-stream-timeout stream))
452                  #!+mp (sb!mp:process-wait-until-fd-usable
453                        fd :input (fd-stream-timeout stream))
454            (error 'io-timeout :stream stream :direction :read)))
455         (t
456          (error "problem checking to see whether ~S is readable: ~A"
457                 stream
458                 (sb!unix:get-unix-error-msg errno)))))
459     (multiple-value-bind (count errno)
460         (sb!unix:unix-read fd
461                            (sb!sys:int-sap (+ (sb!sys:sap-int ibuf-sap) tail))
462                            (- buflen tail))
463       (cond ((null count)
464              (if (eql errno sb!unix:ewouldblock)
465                  (progn
466                    (unless #!-mp (sb!sys:wait-until-fd-usable
467                                  fd :input (fd-stream-timeout stream))
468                            #!+mp (sb!mp:process-wait-until-fd-usable
469                                  fd :input (fd-stream-timeout stream))
470                      (error 'io-timeout :stream stream :direction :read))
471                    (do-input stream))
472                  (error "error reading ~S: ~A"
473                         stream
474                         (sb!unix:get-unix-error-msg errno))))
475             ((zerop count)
476              (setf (fd-stream-listen stream) :eof)
477              (throw 'eof-input-catcher nil))
478             (t
479              (incf (fd-stream-ibuf-tail stream) count))))))
480                         
481 ;;; Make sure there are at least BYTES number of bytes in the input
482 ;;; buffer. Keep calling DO-INPUT until that condition is met.
483 (defmacro input-at-least (stream bytes)
484   (let ((stream-var (gensym))
485         (bytes-var (gensym)))
486     `(let ((,stream-var ,stream)
487            (,bytes-var ,bytes))
488        (loop
489          (when (>= (- (fd-stream-ibuf-tail ,stream-var)
490                       (fd-stream-ibuf-head ,stream-var))
491                    ,bytes-var)
492            (return))
493          (do-input ,stream-var)))))
494
495 ;;; a macro to wrap around all input routines to handle EOF-ERROR noise
496 (defmacro input-wrapper ((stream bytes eof-error eof-value) &body read-forms)
497   (let ((stream-var (gensym))
498         (element-var (gensym)))
499     `(let ((,stream-var ,stream))
500        (if (fd-stream-unread ,stream-var)
501            (prog1
502                (fd-stream-unread ,stream-var)
503              (setf (fd-stream-unread ,stream-var) nil)
504              (setf (fd-stream-listen ,stream-var) nil))
505            (let ((,element-var
506                   (catch 'eof-input-catcher
507                     (input-at-least ,stream-var ,bytes)
508                     ,@read-forms)))
509              (cond (,element-var
510                     (incf (fd-stream-ibuf-head ,stream-var) ,bytes)
511                     ,element-var)
512                    (t
513                     (eof-or-lose ,stream-var ,eof-error ,eof-value))))))))
514
515 (defmacro def-input-routine (name
516                              (type size sap head)
517                              &rest body)
518   `(progn
519      (defun ,name (stream eof-error eof-value)
520        (input-wrapper (stream ,size eof-error eof-value)
521          (let ((,sap (fd-stream-ibuf-sap stream))
522                (,head (fd-stream-ibuf-head stream)))
523            ,@body)))
524      (setf *input-routines*
525            (nconc *input-routines*
526                   (list (list ',type ',name ',size))))))
527
528 ;;; STREAM-IN routine for reading a string char
529 (def-input-routine input-character
530                    (character 1 sap head)
531   (code-char (sap-ref-8 sap head)))
532
533 ;;; STREAM-IN routine for reading an unsigned 8 bit number
534 (def-input-routine input-unsigned-8bit-byte
535                    ((unsigned-byte 8) 1 sap head)
536   (sap-ref-8 sap head))
537
538 ;;; STREAM-IN routine for reading a signed 8 bit number
539 (def-input-routine input-signed-8bit-number
540                    ((signed-byte 8) 1 sap head)
541   (signed-sap-ref-8 sap head))
542
543 ;;; STREAM-IN routine for reading an unsigned 16 bit number
544 (def-input-routine input-unsigned-16bit-byte
545                    ((unsigned-byte 16) 2 sap head)
546   (sap-ref-16 sap head))
547
548 ;;; STREAM-IN routine for reading a signed 16 bit number
549 (def-input-routine input-signed-16bit-byte
550                    ((signed-byte 16) 2 sap head)
551   (signed-sap-ref-16 sap head))
552
553 ;;; STREAM-IN routine for reading a unsigned 32 bit number
554 (def-input-routine input-unsigned-32bit-byte
555                    ((unsigned-byte 32) 4 sap head)
556   (sap-ref-32 sap head))
557
558 ;;; STREAM-IN routine for reading a signed 32 bit number
559 (def-input-routine input-signed-32bit-byte
560                    ((signed-byte 32) 4 sap head)
561   (signed-sap-ref-32 sap head))
562
563 ;;; Find an input routine to use given the type. Return as multiple
564 ;;; values the routine, the real type transfered, and the number of
565 ;;; bytes per element.
566 (defun pick-input-routine (type)
567   (dolist (entry *input-routines*)
568     (when (subtypep type (car entry))
569       (return (values (symbol-function (cadr entry))
570                       (car entry)
571                       (caddr entry))))))
572
573 ;;; Returns a string constructed from the sap, start, and end.
574 (defun string-from-sap (sap start end)
575   (declare (type index start end))
576   (let* ((length (- end start))
577          (string (make-string length)))
578     (copy-from-system-area sap (* start sb!vm:byte-bits)
579                            string (* sb!vm:vector-data-offset sb!vm:word-bits)
580                            (* length sb!vm:byte-bits))
581     string))
582
583 ;;; the N-BIN method for FD-STREAMs. This blocks in UNIX-READ. It is
584 ;;; generally used where there is a definite amount of reading to be
585 ;;; done, so blocking isn't too problematical.
586 (defun fd-stream-read-n-bytes (stream buffer start requested eof-error-p)
587   (declare (type fd-stream stream))
588   (declare (type index start requested))
589   (do ((total-copied 0))
590       (nil)
591     (declare (type index total-copied))
592     (let* ((remaining-request (- requested total-copied))
593            (head (fd-stream-ibuf-head stream))
594            (tail (fd-stream-ibuf-tail stream))
595            (available (- tail head))
596            (this-copy (min remaining-request available))
597            (this-start (+ start total-copied))
598            (sap (fd-stream-ibuf-sap stream)))
599       (declare (type index remaining-request head tail available))
600       (declare (type index this-copy))
601       ;; Copy data from stream buffer into user's buffer. 
602       (if (typep buffer 'system-area-pointer)
603           (system-area-copy sap (* head sb!vm:byte-bits)
604                             buffer (* this-start sb!vm:byte-bits)
605                             (* this-copy sb!vm:byte-bits))
606           (copy-from-system-area sap (* head sb!vm:byte-bits)
607                                  buffer (+ (* this-start sb!vm:byte-bits)
608                                            (* sb!vm:vector-data-offset
609                                               sb!vm:word-bits))
610                                  (* this-copy sb!vm:byte-bits)))
611       (incf (fd-stream-ibuf-head stream) this-copy)
612       (incf total-copied this-copy)
613       ;; Maybe we need to refill the stream buffer.
614       (cond (;; If there were enough data in the stream buffer, we're done.
615              (= total-copied requested)
616              (return total-copied))
617             (;; If EOF, we're done in another way.
618              (zerop (refill-fd-stream-buffer stream))
619              (if eof-error-p
620                  (error 'end-of-file :stream stream)
621                  (return total-copied)))
622             ;; Otherwise we refilled the stream buffer, so fall
623             ;; through into another pass of the loop.
624             ))))
625
626 ;;; Try to refill the stream buffer. Return the number of bytes read.
627 ;;; (For EOF, the return value will be zero, otherwise positive.)
628 (defun refill-fd-stream-buffer (stream)
629   ;; We don't have any logic to preserve leftover bytes in the buffer,
630   ;; so we should only be called when the buffer is empty.
631   (aver (= (fd-stream-ibuf-head stream) (fd-stream-ibuf-tail stream)))
632   (multiple-value-bind (count err)
633       (sb!unix:unix-read (fd-stream-fd stream)
634                          (fd-stream-ibuf-sap stream)
635                          (fd-stream-ibuf-length stream))
636     (declare (type (or index null) count))
637     (when (null count)
638       (error "error reading ~S: ~A"
639              stream
640              (sb!unix:get-unix-error-msg err)))
641     (setf (fd-stream-listen stream) nil
642           (fd-stream-ibuf-head stream) 0
643           (fd-stream-ibuf-tail stream) count)
644 ;    (format t "~%buffer=~%--~%")
645 ;    (dotimes (i count)
646 ;      (write-char (code-char (sap-ref-8 (fd-stream-ibuf-sap stream) i))))
647 ;    (format t "~%--~%")
648     #+nil
649     (format t "/REFILL-FD-STREAM-BUFFER = ~D~%" count)
650     count))
651 \f
652 ;;;; utility functions (misc routines, etc)
653
654 ;;; Fill in the various routine slots for the given type. INPUT-P and
655 ;;; OUTPUT-P indicate what slots to fill. The buffering slot must be
656 ;;; set prior to calling this routine.
657 (defun set-routines (stream type input-p output-p buffer-p)
658   (let ((target-type (case type
659                        ((:default unsigned-byte)
660                         '(unsigned-byte 8))
661                        (signed-byte
662                         '(signed-byte 8))
663                        (t
664                         type)))
665         (input-type nil)
666         (output-type nil)
667         (input-size nil)
668         (output-size nil))
669
670     (when (fd-stream-obuf-sap stream)
671       (push (fd-stream-obuf-sap stream) *available-buffers*)
672       (setf (fd-stream-obuf-sap stream) nil))
673     (when (fd-stream-ibuf-sap stream)
674       (push (fd-stream-ibuf-sap stream) *available-buffers*)
675       (setf (fd-stream-ibuf-sap stream) nil))
676
677     (when input-p
678       (multiple-value-bind (routine type size)
679           (pick-input-routine target-type)
680         (unless routine
681           (error "could not find any input routine for ~S" target-type))
682         (setf (fd-stream-ibuf-sap stream) (next-available-buffer))
683         (setf (fd-stream-ibuf-length stream) bytes-per-buffer)
684         (setf (fd-stream-ibuf-tail stream) 0)
685         (if (subtypep type 'character)
686             (setf (fd-stream-in stream) routine
687                   (fd-stream-bin stream) #'ill-bin)
688             (setf (fd-stream-in stream) #'ill-in
689                   (fd-stream-bin stream) routine))
690         (when (eql size 1)
691           (setf (fd-stream-n-bin stream) #'fd-stream-read-n-bytes)
692           (when buffer-p
693             (setf (lisp-stream-in-buffer stream)
694                   (make-array +in-buffer-length+
695                               :element-type '(unsigned-byte 8)))))
696         (setf input-size size)
697         (setf input-type type)))
698
699     (when output-p
700       (multiple-value-bind (routine type size)
701           (pick-output-routine target-type (fd-stream-buffering stream))
702         (unless routine
703           (error "could not find any output routine for ~S buffered ~S"
704                  (fd-stream-buffering stream)
705                  target-type))
706         (setf (fd-stream-obuf-sap stream) (next-available-buffer))
707         (setf (fd-stream-obuf-length stream) bytes-per-buffer)
708         (setf (fd-stream-obuf-tail stream) 0)
709         (if (subtypep type 'character)
710           (setf (fd-stream-out stream) routine
711                 (fd-stream-bout stream) #'ill-bout)
712           (setf (fd-stream-out stream)
713                 (or (if (eql size 1)
714                       (pick-output-routine 'base-char
715                                            (fd-stream-buffering stream)))
716                     #'ill-out)
717                 (fd-stream-bout stream) routine))
718         (setf (fd-stream-sout stream)
719               (if (eql size 1) #'fd-sout #'ill-out))
720         (setf (fd-stream-char-pos stream) 0)
721         (setf output-size size)
722         (setf output-type type)))
723
724     (when (and input-size output-size
725                (not (eq input-size output-size)))
726       (error "Element sizes for input (~S:~S) and output (~S:~S) differ?"
727              input-type input-size
728              output-type output-size))
729     (setf (fd-stream-element-size stream)
730           (or input-size output-size))
731
732     (setf (fd-stream-element-type stream)
733           (cond ((equal input-type output-type)
734                  input-type)
735                 ((null output-type)
736                  input-type)
737                 ((null input-type)
738                  output-type)
739                 ((subtypep input-type output-type)
740                  input-type)
741                 ((subtypep output-type input-type)
742                  output-type)
743                 (t
744                  (error "Input type (~S) and output type (~S) are unrelated?"
745                         input-type
746                         output-type))))))
747
748 ;;; Handle miscellaneous operations on fd-stream.
749 (defun fd-stream-misc-routine (stream operation &optional arg1 arg2)
750   (declare (ignore arg2))
751   ;; FIXME: Declare TYPE FD-STREAM STREAM?
752   (case operation
753     (:listen
754      (or (not (eql (fd-stream-ibuf-head stream)
755                    (fd-stream-ibuf-tail stream)))
756          (fd-stream-listen stream)
757          (setf (fd-stream-listen stream)
758                (eql (sb!alien:with-alien ((read-fds (sb!alien:struct
759                                                      sb!unix:fd-set)))
760                       (sb!unix:fd-zero read-fds)
761                       (sb!unix:fd-set (fd-stream-fd stream) read-fds)
762                       (sb!unix:unix-fast-select (1+ (fd-stream-fd stream))
763                                                 (sb!alien:addr read-fds)
764                                                 nil nil 0 0))
765                     1))))
766     (:unread
767      (setf (fd-stream-unread stream) arg1)
768      (setf (fd-stream-listen stream) t))
769     (:close
770      (cond (arg1
771             ;; We got us an abort on our hands.
772             (when (fd-stream-handler stream)
773                   (sb!sys:remove-fd-handler (fd-stream-handler stream))
774                   (setf (fd-stream-handler stream) nil))
775             (when (and (fd-stream-file stream)
776                        (fd-stream-obuf-sap stream))
777               ;; We can't do anything unless we know what file were
778               ;; dealing with, and we don't want to do anything
779               ;; strange unless we were writing to the file.
780               (if (fd-stream-original stream)
781                   ;; We have a handle on the original, just revert.
782                   (multiple-value-bind (okay err)
783                       (sb!unix:unix-rename (fd-stream-original stream)
784                                            (fd-stream-file stream))
785                     (unless okay
786                       (cerror "Go on as if nothing bad happened."
787                         "could not restore ~S to its original contents: ~A"
788                               (fd-stream-file stream)
789                               (sb!unix:get-unix-error-msg err))))
790                   ;; We can't restore the orignal, so nuke that puppy.
791                   (multiple-value-bind (okay err)
792                       (sb!unix:unix-unlink (fd-stream-file stream))
793                     (unless okay
794                       (cerror "Go on as if nothing bad happened."
795                               "Could not remove ~S: ~A"
796                               (fd-stream-file stream)
797                               (sb!unix:get-unix-error-msg err)))))))
798            (t
799             (fd-stream-misc-routine stream :finish-output)
800             (when (and (fd-stream-original stream)
801                        (fd-stream-delete-original stream))
802               (multiple-value-bind (okay err)
803                   (sb!unix:unix-unlink (fd-stream-original stream))
804                 (unless okay
805                   (cerror "Go on as if nothing bad happened."
806                           "could not delete ~S during close of ~S: ~A"
807                           (fd-stream-original stream)
808                           stream
809                           (sb!unix:get-unix-error-msg err)))))))
810      (when (fboundp 'cancel-finalization)
811        (cancel-finalization stream))
812      (sb!unix:unix-close (fd-stream-fd stream))
813      (when (fd-stream-obuf-sap stream)
814        (push (fd-stream-obuf-sap stream) *available-buffers*)
815        (setf (fd-stream-obuf-sap stream) nil))
816      (when (fd-stream-ibuf-sap stream)
817        (push (fd-stream-ibuf-sap stream) *available-buffers*)
818        (setf (fd-stream-ibuf-sap stream) nil))
819      (sb!impl::set-closed-flame stream))
820     (:clear-input
821      (setf (fd-stream-unread stream) nil)
822      (setf (fd-stream-ibuf-head stream) 0)
823      (setf (fd-stream-ibuf-tail stream) 0)
824      (catch 'eof-input-catcher
825        (loop
826         (let ((count (sb!alien:with-alien ((read-fds (sb!alien:struct
827                                                       sb!unix:fd-set)))
828                        (sb!unix:fd-zero read-fds)
829                        (sb!unix:fd-set (fd-stream-fd stream) read-fds)
830                        (sb!unix:unix-fast-select (1+ (fd-stream-fd stream))
831                                               (sb!alien:addr read-fds)
832                                               nil
833                                               nil
834                                               0
835                                               0))))
836           (cond ((eql count 1)
837                  (do-input stream)
838                  (setf (fd-stream-ibuf-head stream) 0)
839                  (setf (fd-stream-ibuf-tail stream) 0))
840                 (t
841                  (return t)))))))
842     (:force-output
843      (flush-output-buffer stream))
844     (:finish-output
845      (flush-output-buffer stream)
846      (do ()
847          ((null (fd-stream-output-later stream)))
848        (sb!sys:serve-all-events)))
849     (:element-type
850      (fd-stream-element-type stream))
851     (:interactive-p
852       ;; FIXME: sb!unix:unix-isatty is undefined.
853      (sb!unix:unix-isatty (fd-stream-fd stream)))
854     (:line-length
855      80)
856     (:charpos
857      (fd-stream-char-pos stream))
858     (:file-length
859      (multiple-value-bind (okay dev ino mode nlink uid gid rdev size
860                            atime mtime ctime blksize blocks)
861          (sb!unix:unix-fstat (fd-stream-fd stream))
862        (declare (ignore ino nlink uid gid rdev
863                         atime mtime ctime blksize blocks))
864        (unless okay
865          (error "error fstat'ing ~S: ~A"
866                 stream
867                 (sb!unix:get-unix-error-msg dev)))
868        (if (zerop mode)
869            nil
870            (truncate size (fd-stream-element-size stream)))))
871     (:file-position
872      (fd-stream-file-position stream arg1))))
873
874 (defun fd-stream-file-position (stream &optional newpos)
875   (declare (type fd-stream stream)
876            (type (or index (member nil :start :end)) newpos))
877   (if (null newpos)
878       (sb!sys:without-interrupts
879         ;; First, find the position of the UNIX file descriptor in the
880         ;; file.
881         (multiple-value-bind (posn errno)
882             (sb!unix:unix-lseek (fd-stream-fd stream) 0 sb!unix:l_incr)
883           (declare (type (or index null) posn))
884           (cond ((fixnump posn)
885                  ;; Adjust for buffered output: If there is any output
886                  ;; buffered, the *real* file position will be larger
887                  ;; than reported by lseek because lseek obviously
888                  ;; cannot take into account output we have not sent
889                  ;; yet.
890                  (dolist (later (fd-stream-output-later stream))
891                    (incf posn (- (the index (caddr later))
892                                  (the index (cadr later)))))
893                  (incf posn (fd-stream-obuf-tail stream))
894                  ;; Adjust for unread input: If there is any input
895                  ;; read from UNIX but not supplied to the user of the
896                  ;; stream, the *real* file position will smaller than
897                  ;; reported, because we want to look like the unread
898                  ;; stuff is still available.
899                  (decf posn (- (fd-stream-ibuf-tail stream)
900                                (fd-stream-ibuf-head stream)))
901                  (when (fd-stream-unread stream)
902                    (decf posn))
903                  ;; Divide bytes by element size.
904                  (truncate posn (fd-stream-element-size stream)))
905                 ((eq errno sb!unix:espipe)
906                  nil)
907                 (t
908                  (sb!sys:with-interrupts
909                    (error "error LSEEK'ing ~S: ~A"
910                           stream
911                           (sb!unix:get-unix-error-msg errno)))))))
912       (let ((offset 0) origin)
913         (declare (type index offset))
914         ;; Make sure we don't have any output pending, because if we
915         ;; move the file pointer before writing this stuff, it will be
916         ;; written in the wrong location.
917         (flush-output-buffer stream)
918         (do ()
919             ((null (fd-stream-output-later stream)))
920           (sb!sys:serve-all-events))
921         ;; Clear out any pending input to force the next read to go to
922         ;; the disk.
923         (setf (fd-stream-unread stream) nil)
924         (setf (fd-stream-ibuf-head stream) 0)
925         (setf (fd-stream-ibuf-tail stream) 0)
926         ;; Trash cached value for listen, so that we check next time.
927         (setf (fd-stream-listen stream) nil)
928         ;; Now move it.
929         (cond ((eq newpos :start)
930                (setf offset 0 origin sb!unix:l_set))
931               ((eq newpos :end)
932                (setf offset 0 origin sb!unix:l_xtnd))
933               ((typep newpos 'index)
934                (setf offset (* newpos (fd-stream-element-size stream))
935                      origin sb!unix:l_set))
936               (t
937                (error "invalid position given to file-position: ~S" newpos)))
938         (multiple-value-bind (posn errno)
939             (sb!unix:unix-lseek (fd-stream-fd stream) offset origin)
940           (cond ((typep posn 'fixnum)
941                  t)
942                 ((eq errno sb!unix:espipe)
943                  nil)
944                 (t
945                  (error "error lseek'ing ~S: ~A"
946                         stream
947                         (sb!unix:get-unix-error-msg errno))))))))
948 \f
949 ;;;; creation routines (MAKE-FD-STREAM and OPEN)
950
951 ;;; Returns a FD-STREAM on the given file.
952 (defun make-fd-stream (fd
953                        &key
954                        (input nil input-p)
955                        (output nil output-p)
956                        (element-type 'base-char)
957                        (buffering :full)
958                        timeout
959                        file
960                        original
961                        delete-original
962                        pathname
963                        input-buffer-p
964                        (name (if file
965                                  (format nil "file ~S" file)
966                                  (format nil "descriptor ~D" fd)))
967                        auto-close)
968   (declare (type index fd) (type (or index null) timeout)
969            (type (member :none :line :full) buffering))
970   #!+sb-doc
971   "Create a stream for the given unix file descriptor.
972   If input is non-nil, allow input operations.
973   If output is non-nil, allow output operations.
974   If neither input nor output are specified, default to allowing input.
975   Element-type indicates the element type to use (as for open).
976   Buffering indicates the kind of buffering to use.
977   Timeout (if true) is the number of seconds to wait for input. If NIL (the
978     default), then wait forever. When we time out, we signal IO-TIMEOUT.
979   File is the name of the file (will be returned by PATHNAME).
980   Name is used to identify the stream when printed."
981   (cond ((not (or input-p output-p))
982          (setf input t))
983         ((not (or input output))
984          (error "File descriptor must be opened either for input or output.")))
985   (let ((stream (%make-fd-stream :fd fd
986                                  :name name
987                                  :file file
988                                  :original original
989                                  :delete-original delete-original
990                                  :pathname pathname
991                                  :buffering buffering
992                                  :timeout timeout)))
993     (set-routines stream element-type input output input-buffer-p)
994     (when (and auto-close (fboundp 'finalize))
995       (finalize stream
996                 (lambda ()
997                   (sb!unix:unix-close fd)
998                   #!+sb-show
999                   (format *terminal-io* "** closed file descriptor ~D **~%"
1000                           fd))))
1001     stream))
1002
1003 ;;; Pick a name to use for the backup file.
1004 (defvar *backup-extension* ".BAK"
1005   #!+sb-doc
1006   "This is a string that OPEN tacks on the end of a file namestring to produce
1007    a name for the :if-exists :rename-and-delete and :rename options. Also,
1008    this can be a function that takes a namestring and returns a complete
1009    namestring.")
1010 (defun pick-backup-name (name)
1011   (declare (type simple-string name))
1012   (let ((ext *backup-extension*))
1013     (etypecase ext
1014       (simple-string (concatenate 'simple-string name ext))
1015       (function (funcall ext name)))))
1016
1017 ;;; Ensure that the given arg is one of the given list of valid things.
1018 ;;; Allow the user to fix any problems.
1019 ;;; FIXME: Why let the user fix any problems?
1020 (defun ensure-one-of (item list what)
1021   (unless (member item list)
1022     (loop
1023       (cerror "Enter new value for ~*~S"
1024               "~S is invalid for ~S. Must be one of~{ ~S~}"
1025               item
1026               what
1027               list)
1028       (format (the stream *query-io*) "Enter new value for ~S: " what)
1029       (force-output *query-io*)
1030       (setf item (read *query-io*))
1031       (when (member item list)
1032         (return))))
1033   item)
1034
1035 ;;; Rename NAMESTRING to ORIGINAL. First, check whether we have write
1036 ;;; access, since we don't want to trash unwritable files even if we
1037 ;;; technically can. We return true if we succeed in renaming.
1038 (defun do-old-rename (namestring original)
1039   (unless (sb!unix:unix-access namestring sb!unix:w_ok)
1040     (cerror "Try to rename it anyway."
1041             "File ~S is not writable."
1042             namestring))
1043   (multiple-value-bind (okay err) (sb!unix:unix-rename namestring original)
1044     (cond (okay t)
1045           (t
1046            (cerror "Use :SUPERSEDE instead."
1047                    "Could not rename ~S to ~S: ~A."
1048                    namestring
1049                    original
1050                    (sb!unix:get-unix-error-msg err))
1051            nil))))
1052
1053 (defun open (filename
1054              &key
1055              (direction :input)
1056              (element-type 'base-char)
1057              (if-exists nil if-exists-given)
1058              (if-does-not-exist nil if-does-not-exist-given)
1059              (external-format :default)
1060              &aux ; Squelch assignment warning.
1061              (direction direction)
1062              (if-does-not-exist if-does-not-exist)
1063              (if-exists if-exists))
1064   #!+sb-doc
1065   "Return a stream which reads from or writes to Filename.
1066   Defined keywords:
1067    :direction - one of :input, :output, :io, or :probe
1068    :element-type - Type of object to read or write, default BASE-CHAR
1069    :if-exists - one of :error, :new-version, :rename, :rename-and-delete,
1070                        :overwrite, :append, :supersede or nil
1071    :if-does-not-exist - one of :error, :create or nil
1072   See the manual for details."
1073
1074   (unless (eq external-format :default)
1075     (error 'simple-error
1076            :format-control
1077            "Any external format other than :DEFAULT isn't recognized."))
1078
1079   ;; First, make sure that DIRECTION is valid. Allow it to be changed
1080   ;; if not.
1081   ;;
1082   ;; FIXME: Why allow it to be changed if not?
1083   (setf direction
1084         (ensure-one-of direction
1085                        '(:input :output :io :probe)
1086                        :direction))
1087
1088   ;; Calculate useful stuff.
1089   (multiple-value-bind (input output mask)
1090       (case direction
1091         (:input  (values   t nil sb!unix:o_rdonly))
1092         (:output (values nil   t sb!unix:o_wronly))
1093         (:io     (values   t   t sb!unix:o_rdwr))
1094         (:probe  (values   t nil sb!unix:o_rdonly)))
1095     (declare (type index mask))
1096     (let* ((pathname (pathname filename))
1097            (namestring
1098             (cond ((unix-namestring pathname input))
1099                   ((and input (eq if-does-not-exist :create))
1100                    (unix-namestring pathname nil)))))
1101       ;; Process if-exists argument if we are doing any output.
1102       (cond (output
1103              (unless if-exists-given
1104                (setf if-exists
1105                      (if (eq (pathname-version pathname) :newest)
1106                          :new-version
1107                          :error)))
1108              (setf if-exists ; FIXME: should just die, not allow resetting
1109                    (ensure-one-of if-exists
1110                                   '(:error :new-version :rename
1111                                     :rename-and-delete :overwrite
1112                                     :append :supersede nil)
1113                                   :if-exists))
1114              (case if-exists
1115                ((:error nil)
1116                 (setf mask (logior mask sb!unix:o_excl)))
1117                ((:rename :rename-and-delete)
1118                 (setf mask (logior mask sb!unix:o_creat)))
1119                ((:new-version :supersede)
1120                 (setf mask (logior mask sb!unix:o_trunc)))
1121                (:append
1122                 (setf mask (logior mask sb!unix:o_append)))))
1123             (t
1124              (setf if-exists :ignore-this-arg)))
1125
1126       (unless if-does-not-exist-given
1127         (setf if-does-not-exist
1128               (cond ((eq direction :input) :error)
1129                     ((and output
1130                           (member if-exists '(:overwrite :append)))
1131                      :error)
1132                     ((eq direction :probe)
1133                      nil)
1134                     (t
1135                      :create))))
1136       (setf if-does-not-exist ; FIXME: should just die, not allow resetting
1137             (ensure-one-of if-does-not-exist
1138                            '(:error :create nil)
1139                            :if-does-not-exist))
1140       (if (eq if-does-not-exist :create)
1141         (setf mask (logior mask sb!unix:o_creat)))
1142
1143       (let ((original (if (member if-exists
1144                                   '(:rename :rename-and-delete))
1145                           (pick-backup-name namestring)))
1146             (delete-original (eq if-exists :rename-and-delete))
1147             (mode #o666))
1148         (when original
1149           ;; We are doing a :RENAME or :RENAME-AND-DELETE.
1150           ;; Determine whether the file already exists, make sure the original
1151           ;; file is not a directory, and keep the mode.
1152           (let ((exists
1153                  (and namestring
1154                       (multiple-value-bind (okay err/dev inode orig-mode)
1155                           (sb!unix:unix-stat namestring)
1156                         (declare (ignore inode)
1157                                  (type (or index null) orig-mode))
1158                         (cond
1159                          (okay
1160                           (when (and output (= (logand orig-mode #o170000)
1161                                                #o40000))
1162                             (error "cannot open ~S for output: is a directory"
1163                                    namestring))
1164                           (setf mode (logand orig-mode #o777))
1165                           t)
1166                          ((eql err/dev sb!unix:enoent)
1167                           nil)
1168                          (t
1169                           (error "cannot find ~S: ~A"
1170                                  namestring
1171                                  (sb!unix:get-unix-error-msg err/dev))))))))
1172             (unless (and exists
1173                          (do-old-rename namestring original))
1174               (setf original nil)
1175               (setf delete-original nil)
1176               ;; In order to use :SUPERSEDE instead, we have to make sure
1177               ;; SB!UNIX:O_CREAT corresponds to IF-DOES-NOT-EXIST.
1178               ;; SB!UNIX:O_CREAT was set before because of IF-EXISTS being
1179               ;; :RENAME.
1180               (unless (eq if-does-not-exist :create)
1181                 (setf mask
1182                       (logior (logandc2 mask sb!unix:o_creat)
1183                               sb!unix:o_trunc)))
1184               (setf if-exists :supersede))))
1185         
1186         ;; Okay, now we can try the actual open.
1187         (loop
1188           (multiple-value-bind (fd errno)
1189               (if namestring
1190                   (sb!unix:unix-open namestring mask mode)
1191                   (values nil sb!unix:enoent))
1192             (cond ((numberp fd)
1193                    (return
1194                     (case direction
1195                       ((:input :output :io)
1196                        (make-fd-stream fd
1197                                        :input input
1198                                        :output output
1199                                        :element-type element-type
1200                                        :file namestring
1201                                        :original original
1202                                        :delete-original delete-original
1203                                        :pathname pathname
1204                                        :input-buffer-p t
1205                                        :auto-close t))
1206                       (:probe
1207                        (let ((stream
1208                               (%make-fd-stream :name namestring :fd fd
1209                                                :pathname pathname
1210                                                :element-type element-type)))
1211                          (close stream)
1212                          stream)))))
1213                   ((eql errno sb!unix:enoent)
1214                    (case if-does-not-exist
1215                      (:error
1216                       (cerror "Return NIL."
1217                               'simple-file-error
1218                               :pathname pathname
1219                               :format-control "error opening ~S: ~A"
1220                               :format-arguments
1221                               (list pathname
1222                                     (sb!unix:get-unix-error-msg errno))))
1223                      (:create
1224                       (cerror "Return NIL."
1225                               'simple-error
1226                               :format-control
1227                               "error creating ~S: Path does not exist."
1228                               :format-arguments
1229                               (list pathname))))
1230                    (return nil))
1231                   ((eql errno sb!unix:eexist)
1232                    (unless (eq nil if-exists)
1233                      (cerror "Return NIL."
1234                              'simple-file-error
1235                              :pathname pathname
1236                              :format-control "error opening ~S: ~A"
1237                              :format-arguments
1238                              (list pathname
1239                                    (sb!unix:get-unix-error-msg errno))))
1240                    (return nil))
1241                   ((eql errno sb!unix:eacces)
1242                    (cerror "Try again."
1243                            "error opening ~S: ~A"
1244                            pathname
1245                            (sb!unix:get-unix-error-msg errno)))
1246                   (t
1247                    (cerror "Return NIL."
1248                            "error opening ~S: ~A"
1249                            pathname
1250                            (sb!unix:get-unix-error-msg errno))
1251                    (return nil)))))))))
1252 \f
1253 ;;;; initialization
1254
1255 (defvar *tty* nil
1256   #!+sb-doc
1257   "The stream connected to the controlling terminal or NIL if there is none.")
1258 (defvar *stdin* nil
1259   #!+sb-doc
1260   "The stream connected to the standard input (file descriptor 0).")
1261 (defvar *stdout* nil
1262   #!+sb-doc
1263   "The stream connected to the standard output (file descriptor 1).")
1264 (defvar *stderr* nil
1265   #!+sb-doc
1266   "The stream connected to the standard error output (file descriptor 2).")
1267
1268 ;;; This is called when the cold load is first started up, and may also
1269 ;;; be called in an attempt to recover from nested errors.
1270 (defun stream-cold-init-or-reset ()
1271   (stream-reinit)
1272   (setf *terminal-io* (make-synonym-stream '*tty*))
1273   (setf *standard-output* (make-synonym-stream '*stdout*))
1274   (setf *standard-input*
1275         (#!-high-security
1276          ;; FIXME: Why is *STANDARD-INPUT* a TWO-WAY-STREAM? ANSI says it's
1277          ;; an input stream.
1278          make-two-way-stream
1279          #!+high-security
1280          %make-two-way-stream (make-synonym-stream '*stdin*)
1281                              *standard-output*))
1282   (setf *error-output* (make-synonym-stream '*stderr*))
1283   (setf *query-io* (make-synonym-stream '*terminal-io*))
1284   (setf *debug-io* *query-io*)
1285   (setf *trace-output* *standard-output*)
1286   nil)
1287
1288 ;;; This is called whenever a saved core is restarted.
1289 (defun stream-reinit ()
1290   (setf *available-buffers* nil)
1291   (setf *stdin*
1292         (make-fd-stream 0 :name "standard input" :input t :buffering :line))
1293   (setf *stdout*
1294         (make-fd-stream 1 :name "standard output" :output t :buffering :line))
1295   (setf *stderr*
1296         (make-fd-stream 2 :name "standard error" :output t :buffering :line))
1297   (let ((tty (sb!unix:unix-open "/dev/tty" sb!unix:o_rdwr #o666)))
1298     (if tty
1299         (setf *tty*
1300               (make-fd-stream tty
1301                               :name "the terminal"
1302                               :input t
1303                               :output t
1304                               :buffering :line
1305                               :auto-close t))
1306         (setf *tty* (make-two-way-stream *stdin* *stdout*))))
1307   nil)
1308 \f
1309 ;;;; beeping
1310
1311 (defun default-beep-function (stream)
1312   (write-char (code-char bell-char-code) stream)
1313   (finish-output stream))
1314
1315 (defvar *beep-function* #'default-beep-function
1316   #!+sb-doc
1317   "This is called in BEEP to feep the user. It takes a stream.")
1318
1319 (defun beep (&optional (stream *terminal-io*))
1320   (funcall *beep-function* stream))
1321 \f
1322 ;;; This is kind of like FILE-POSITION, but is an internal hack used
1323 ;;; by the filesys stuff to get and set the file name.
1324 (defun file-name (stream &optional new-name)
1325   (when (typep stream 'fd-stream)
1326       (cond (new-name
1327              (setf (fd-stream-pathname stream) new-name)
1328              (setf (fd-stream-file stream)
1329                    (unix-namestring new-name nil))
1330              t)
1331             (t
1332              (fd-stream-pathname stream)))))
1333 \f
1334 ;;;; international character support (which is trivial for our simple
1335 ;;;; character sets)
1336
1337 ;;;; (Those who do Lisp only in English might not remember that ANSI
1338 ;;;; requires these functions to be exported from package
1339 ;;;; COMMON-LISP.)
1340
1341 (defun file-string-length (stream object)
1342   (declare (type (or string character) object) (type file-stream stream))
1343   #!+sb-doc
1344   "Return the delta in STREAM's FILE-POSITION that would be caused by writing
1345    Object to Stream. Non-trivial only in implementations that support
1346    international character sets."
1347   (declare (ignore stream))
1348   (etypecase object
1349     (character 1)
1350     (string (length object))))
1351
1352 (defun stream-external-format (stream)
1353   (declare (type file-stream stream) (ignore stream))
1354   #!+sb-doc
1355   "Return :DEFAULT."
1356   :default)