1.0.7.30: be more paranoid about saps
[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 ;;;; buffer manipulation routines
15
16 ;;; FIXME: Is it really good to maintain this pool separate from the
17 ;;; GC and the C malloc logic?
18 (defvar *available-buffers* ()
19   #!+sb-doc
20   "List of available buffers. Each buffer is an sap pointing to
21 bytes-per-buffer of memory.")
22
23 (defvar *available-buffers-mutex* (sb!thread:make-mutex
24                                    :name "lock for *AVAILABLE-BUFFERS*")
25   #!+sb-doc
26   "Mutex for access to *AVAILABLE-BUFFERS*.")
27
28 (defmacro with-available-buffers-lock ((&optional) &body body)
29   ;; CALL-WITH-SYSTEM-MUTEX because streams are low-level enough to be
30   ;; async signal safe, and in particular a C-c that brings up the
31   ;; debugger while holding the mutex would lose badly
32   `(sb!thread::call-with-system-mutex (lambda () ,@body)
33                                     *available-buffers-mutex*))
34
35 (defconstant bytes-per-buffer (* 4 1024)
36   #!+sb-doc
37   "Number of bytes per buffer.")
38
39 ;;; Return the next available buffer, creating one if necessary.
40 #!-sb-fluid (declaim (inline next-available-buffer))
41 (defun next-available-buffer ()
42   (with-available-buffers-lock ()
43     (if *available-buffers*
44         (pop *available-buffers*)
45         (allocate-system-memory bytes-per-buffer))))
46 \f
47 ;;;; the FD-STREAM structure
48
49 (defstruct (fd-stream
50             (:constructor %make-fd-stream)
51             (:conc-name fd-stream-)
52             (:predicate fd-stream-p)
53             (:include ansi-stream
54                       (misc #'fd-stream-misc-routine))
55             (:copier nil))
56
57   ;; the name of this stream
58   (name nil)
59   ;; the file this stream is for
60   (file nil)
61   ;; the backup file namestring for the old file, for :IF-EXISTS
62   ;; :RENAME or :RENAME-AND-DELETE.
63   (original nil :type (or simple-string null))
64   (delete-original nil)       ; for :if-exists :rename-and-delete
65   ;;; the number of bytes per element
66   (element-size 1 :type index)
67   ;; the type of element being transfered
68   (element-type 'base-char)
69   ;; the Unix file descriptor
70   (fd -1 :type fixnum)
71   ;; controls when the output buffer is flushed
72   (buffering :full :type (member :full :line :none))
73   ;; controls whether the input buffer must be cleared before output
74   ;; (must be done for files, not for sockets, pipes and other data
75   ;; sources where input and output aren't related).  non-NIL means
76   ;; don't clear input buffer.
77   (dual-channel-p nil)
78   ;; character position if known -- this may run into bignums, but
79   ;; we probably should flip it into null then for efficiency's sake...
80   (char-pos nil :type (or unsigned-byte null))
81   ;; T if input is waiting on FD. :EOF if we hit EOF.
82   (listen nil :type (member nil t :eof))
83
84   ;; the input buffer
85   (unread nil)
86   (ibuf-sap nil :type (or system-area-pointer null))
87   (ibuf-length nil :type (or index null))
88   (ibuf-head 0 :type index)
89   (ibuf-tail 0 :type index)
90
91   ;; the output buffer
92   (obuf-sap nil :type (or system-area-pointer null))
93   (obuf-length nil :type (or index null))
94   (obuf-tail 0 :type index)
95
96   ;; output flushed, but not written due to non-blocking io?
97   (output-later nil)
98   (handler nil)
99   ;; timeout specified for this stream as seconds or NIL if none
100   (timeout nil :type (or single-float null))
101   ;; pathname of the file this stream is opened to (returned by PATHNAME)
102   (pathname nil :type (or pathname null))
103   (external-format :default)
104   (output-bytes #'ill-out :type function))
105 (def!method print-object ((fd-stream fd-stream) stream)
106   (declare (type stream stream))
107   (print-unreadable-object (fd-stream stream :type t :identity t)
108     (format stream "for ~S" (fd-stream-name fd-stream))))
109 \f
110 ;;;; output routines and related noise
111
112 (defvar *output-routines* ()
113   #!+sb-doc
114   "List of all available output routines. Each element is a list of the
115   element-type output, the kind of buffering, the function name, and the number
116   of bytes per element.")
117
118 ;;; common idioms for reporting low-level stream and file problems
119 (defun simple-stream-perror (note-format stream errno)
120   (error 'simple-stream-error
121          :stream stream
122          :format-control "~@<~?: ~2I~_~A~:>"
123          :format-arguments (list note-format (list stream) (strerror errno))))
124 (defun simple-file-perror (note-format pathname errno)
125   (error 'simple-file-error
126          :pathname pathname
127          :format-control "~@<~?: ~2I~_~A~:>"
128          :format-arguments
129          (list note-format (list pathname) (strerror errno))))
130
131 (defun stream-decoding-error (stream octets)
132   (error 'stream-decoding-error
133          :stream stream
134          ;; FIXME: dunno how to get at OCTETS currently, or even if
135          ;; that's the right thing to report.
136          :octets octets))
137 (defun stream-encoding-error (stream code)
138   (error 'stream-encoding-error
139          :stream stream
140          :code code))
141
142 (defun c-string-encoding-error (external-format code)
143   (error 'c-string-encoding-error
144          :external-format external-format
145          :code code))
146
147 (defun c-string-decoding-error (external-format octets)
148   (error 'c-string-decoding-error
149          :external-format external-format
150          :octets octets))
151
152 ;;; Returning true goes into end of file handling, false will enter another
153 ;;; round of input buffer filling followed by re-entering character decode.
154 (defun stream-decoding-error-and-handle (stream octet-count)
155   (restart-case
156       (stream-decoding-error stream
157                              (let ((sap (fd-stream-ibuf-sap stream))
158                                    (head (fd-stream-ibuf-head stream)))
159                                (loop for i from 0 below octet-count
160                                      collect (sap-ref-8 sap (+ head i)))))
161     (attempt-resync ()
162       :report (lambda (stream)
163                 (format stream
164                         "~@<Attempt to resync the stream at a character ~
165                         character boundary and continue.~@:>"))
166       (fd-stream-resync stream)
167       nil)
168     (force-end-of-file ()
169       :report (lambda (stream)
170                 (format stream "~@<Force an end of file.~@:>"))
171       t)))
172
173 (defun stream-encoding-error-and-handle (stream code)
174   (restart-case
175       (stream-encoding-error stream code)
176     (output-nothing ()
177       :report (lambda (stream)
178                 (format stream "~@<Skip output of this character.~@:>"))
179       (throw 'output-nothing nil))))
180
181 (defun external-format-encoding-error (stream code)
182   (if (streamp stream)
183       (stream-encoding-error-and-handle stream code)
184       (c-string-encoding-error stream code)))
185
186 (defun external-format-decoding-error (stream octet-count)
187   (if (streamp stream)
188       (stream-decoding-error stream octet-count)
189       (c-string-decoding-error stream octet-count)))
190
191 ;;; This is called by the server when we can write to the given file
192 ;;; descriptor. Attempt to write the data again. If it worked, remove
193 ;;; the data from the OUTPUT-LATER list. If it didn't work, something
194 ;;; is wrong.
195 (defun frob-output-later (stream)
196   (let* ((stuff (pop (fd-stream-output-later stream)))
197          (base (car stuff))
198          (start (cadr stuff))
199          (end (caddr stuff))
200          (reuse-sap (cadddr stuff))
201          (length (- end start)))
202     (declare (type index start end length))
203     (multiple-value-bind (count errno)
204         (sb!unix:unix-write (fd-stream-fd stream)
205                             base
206                             start
207                             length)
208       (cond ((not count)
209              #!+win32
210              (simple-stream-perror "couldn't write to ~S" stream errno)
211              #!-win32
212              (if (= errno sb!unix:ewouldblock)
213                  (error "Write would have blocked, but SERVER told us to go.")
214                  (simple-stream-perror "couldn't write to ~S" stream errno)))
215             ((eql count length) ; Hot damn, it worked.
216              (when reuse-sap
217                (with-available-buffers-lock ()
218                  (push base *available-buffers*))))
219             ((not (null count)) ; sorta worked..
220              (push (list base
221                          (the index (+ start count))
222                          end)
223                    (fd-stream-output-later stream))))))
224   (unless (fd-stream-output-later stream)
225     (remove-fd-handler (fd-stream-handler stream))
226     (setf (fd-stream-handler stream) nil)))
227
228 ;;; Arange to output the string when we can write on the file descriptor.
229 (defun output-later (stream base start end reuse-sap)
230   (cond ((null (fd-stream-output-later stream))
231          (setf (fd-stream-output-later stream)
232                (list (list base start end reuse-sap)))
233          (setf (fd-stream-handler stream)
234                (add-fd-handler (fd-stream-fd stream)
235                                       :output
236                                       (lambda (fd)
237                                         (declare (ignore fd))
238                                         (frob-output-later stream)))))
239         (t
240          (nconc (fd-stream-output-later stream)
241                 (list (list base start end reuse-sap)))))
242   (when reuse-sap
243     (let ((new-buffer (next-available-buffer)))
244       (setf (fd-stream-obuf-sap stream) new-buffer)
245       (setf (fd-stream-obuf-length stream) bytes-per-buffer))))
246
247 ;;; Output the given noise. Check to see whether there are any pending
248 ;;; writes. If so, just queue this one. Otherwise, try to write it. If
249 ;;; this would block, queue it.
250 (defun frob-output (stream base start end reuse-sap)
251   (declare (type fd-stream stream)
252            (type (or system-area-pointer (simple-array * (*))) base)
253            (type index start end))
254   (if (not (null (fd-stream-output-later stream))) ; something buffered.
255       (output-later stream base start end reuse-sap)
256       ;; ### check to see whether any of this noise can be output
257       (let ((length (- end start)))
258         (multiple-value-bind (count errno)
259             (sb!unix:unix-write (fd-stream-fd stream) base start length)
260           (cond ((not count)
261                  #!+win32
262                  (simple-stream-perror "Couldn't write to ~S" stream errno)
263                  #!-win32
264                  (if (= errno sb!unix:ewouldblock)
265                      (output-later stream base start end reuse-sap)
266                      (simple-stream-perror "Couldn't write to ~S"
267                                            stream errno)))
268                 ((not (eql count length))
269                  (output-later stream base (the index (+ start count))
270                                end reuse-sap)))))))
271
272 ;;; Flush any data in the output buffer.
273 (defun flush-output-buffer (stream)
274   (let ((length (fd-stream-obuf-tail stream)))
275     (unless (= length 0)
276       (frob-output stream (fd-stream-obuf-sap stream) 0 length t)
277       (setf (fd-stream-obuf-tail stream) 0))))
278
279 (defun fd-stream-output-finished-p (stream)
280   (and (zerop (fd-stream-obuf-tail stream))
281        (not (fd-stream-output-later stream))))
282
283 (defmacro output-wrapper/variable-width ((stream size buffering restart)
284                                          &body body)
285   (let ((stream-var (gensym)))
286     `(let ((,stream-var ,stream)
287            (size ,size))
288       ,(unless (eq (car buffering) :none)
289          `(when (< (fd-stream-obuf-length ,stream-var)
290                    (+ (fd-stream-obuf-tail ,stream-var)
291                        size))
292             (flush-output-buffer ,stream-var)))
293       ,(unless (eq (car buffering) :none)
294          `(when (and (not (fd-stream-dual-channel-p ,stream-var))
295                      (> (fd-stream-ibuf-tail ,stream-var)
296                         (fd-stream-ibuf-head ,stream-var)))
297             (file-position ,stream-var (file-position ,stream-var))))
298       ,(if restart
299            `(catch 'output-nothing
300               ,@body
301               (incf (fd-stream-obuf-tail ,stream-var) size))
302            `(progn
303              ,@body
304              (incf (fd-stream-obuf-tail ,stream-var) size)))
305       ,(ecase (car buffering)
306          (:none
307           `(flush-output-buffer ,stream-var))
308          (:line
309           `(when (eq (char-code byte) (char-code #\Newline))
310              (flush-output-buffer ,stream-var)))
311          (:full))
312     (values))))
313
314 (defmacro output-wrapper ((stream size buffering restart) &body body)
315   (let ((stream-var (gensym)))
316     `(let ((,stream-var ,stream))
317       ,(unless (eq (car buffering) :none)
318          `(when (< (fd-stream-obuf-length ,stream-var)
319                    (+ (fd-stream-obuf-tail ,stream-var)
320                        ,size))
321             (flush-output-buffer ,stream-var)))
322       ,(unless (eq (car buffering) :none)
323          `(when (and (not (fd-stream-dual-channel-p ,stream-var))
324                      (> (fd-stream-ibuf-tail ,stream-var)
325                         (fd-stream-ibuf-head ,stream-var)))
326             (file-position ,stream-var (file-position ,stream-var))))
327       ,(if restart
328            `(catch 'output-nothing
329               ,@body
330               (incf (fd-stream-obuf-tail ,stream-var) ,size))
331            `(progn
332              ,@body
333              (incf (fd-stream-obuf-tail ,stream-var) ,size)))
334       ,(ecase (car buffering)
335          (:none
336           `(flush-output-buffer ,stream-var))
337          (:line
338           `(when (eq (char-code byte) (char-code #\Newline))
339              (flush-output-buffer ,stream-var)))
340          (:full))
341     (values))))
342
343 (defmacro def-output-routines/variable-width
344     ((name-fmt size restart external-format &rest bufferings)
345      &body body)
346   (declare (optimize (speed 1)))
347   (cons 'progn
348         (mapcar
349             (lambda (buffering)
350               (let ((function
351                      (intern (format nil name-fmt (string (car buffering))))))
352                 `(progn
353                    (defun ,function (stream byte)
354                      (declare (ignorable byte))
355                      (output-wrapper/variable-width (stream ,size ,buffering ,restart)
356                        ,@body))
357                    (setf *output-routines*
358                          (nconc *output-routines*
359                                 ',(mapcar
360                                    (lambda (type)
361                                      (list type
362                                            (car buffering)
363                                            function
364                                            1
365                                            external-format))
366                                    (cdr buffering)))))))
367             bufferings)))
368
369 ;;; Define output routines that output numbers SIZE bytes long for the
370 ;;; given bufferings. Use BODY to do the actual output.
371 (defmacro def-output-routines ((name-fmt size restart &rest bufferings)
372                                &body body)
373   (declare (optimize (speed 1)))
374   (cons 'progn
375         (mapcar
376             (lambda (buffering)
377               (let ((function
378                      (intern (format nil name-fmt (string (car buffering))))))
379                 `(progn
380                    (defun ,function (stream byte)
381                      (output-wrapper (stream ,size ,buffering ,restart)
382                        ,@body))
383                    (setf *output-routines*
384                          (nconc *output-routines*
385                                 ',(mapcar
386                                    (lambda (type)
387                                      (list type
388                                            (car buffering)
389                                            function
390                                            size
391                                            nil))
392                                    (cdr buffering)))))))
393             bufferings)))
394
395 ;;; FIXME: is this used anywhere any more?
396 (def-output-routines ("OUTPUT-CHAR-~A-BUFFERED"
397                       1
398                       t
399                       (:none character)
400                       (:line character)
401                       (:full character))
402   (if (char= byte #\Newline)
403       (setf (fd-stream-char-pos stream) 0)
404       (incf (fd-stream-char-pos stream)))
405   (setf (sap-ref-8 (fd-stream-obuf-sap stream) (fd-stream-obuf-tail stream))
406         (char-code byte)))
407
408 (def-output-routines ("OUTPUT-UNSIGNED-BYTE-~A-BUFFERED"
409                       1
410                       nil
411                       (:none (unsigned-byte 8))
412                       (:full (unsigned-byte 8)))
413   (setf (sap-ref-8 (fd-stream-obuf-sap stream) (fd-stream-obuf-tail stream))
414         byte))
415
416 (def-output-routines ("OUTPUT-SIGNED-BYTE-~A-BUFFERED"
417                       1
418                       nil
419                       (:none (signed-byte 8))
420                       (:full (signed-byte 8)))
421   (setf (signed-sap-ref-8 (fd-stream-obuf-sap stream)
422                           (fd-stream-obuf-tail stream))
423         byte))
424
425 (def-output-routines ("OUTPUT-UNSIGNED-SHORT-~A-BUFFERED"
426                       2
427                       nil
428                       (:none (unsigned-byte 16))
429                       (:full (unsigned-byte 16)))
430   (setf (sap-ref-16 (fd-stream-obuf-sap stream) (fd-stream-obuf-tail stream))
431         byte))
432
433 (def-output-routines ("OUTPUT-SIGNED-SHORT-~A-BUFFERED"
434                       2
435                       nil
436                       (:none (signed-byte 16))
437                       (:full (signed-byte 16)))
438   (setf (signed-sap-ref-16 (fd-stream-obuf-sap stream)
439                            (fd-stream-obuf-tail stream))
440         byte))
441
442 (def-output-routines ("OUTPUT-UNSIGNED-LONG-~A-BUFFERED"
443                       4
444                       nil
445                       (:none (unsigned-byte 32))
446                       (:full (unsigned-byte 32)))
447   (setf (sap-ref-32 (fd-stream-obuf-sap stream) (fd-stream-obuf-tail stream))
448         byte))
449
450 (def-output-routines ("OUTPUT-SIGNED-LONG-~A-BUFFERED"
451                       4
452                       nil
453                       (:none (signed-byte 32))
454                       (:full (signed-byte 32)))
455   (setf (signed-sap-ref-32 (fd-stream-obuf-sap stream)
456                            (fd-stream-obuf-tail stream))
457         byte))
458
459 #+#.(cl:if (cl:= sb!vm:n-word-bits 64) '(and) '(or))
460 (progn
461   (def-output-routines ("OUTPUT-UNSIGNED-LONG-LONG-~A-BUFFERED"
462                         8
463                         nil
464                         (:none (unsigned-byte 64))
465                         (:full (unsigned-byte 64)))
466     (setf (sap-ref-64 (fd-stream-obuf-sap stream) (fd-stream-obuf-tail stream))
467           byte))
468   (def-output-routines ("OUTPUT-SIGNED-LONG-LONG-~A-BUFFERED"
469                         8
470                         nil
471                         (:none (signed-byte 64))
472                         (:full (signed-byte 64)))
473     (setf (signed-sap-ref-64 (fd-stream-obuf-sap stream)
474                              (fd-stream-obuf-tail stream))
475           byte)))
476
477 ;;; Do the actual output. If there is space to buffer the string,
478 ;;; buffer it. If the string would normally fit in the buffer, but
479 ;;; doesn't because of other stuff in the buffer, flush the old noise
480 ;;; out of the buffer and put the string in it. Otherwise we have a
481 ;;; very long string, so just send it directly (after flushing the
482 ;;; buffer, of course).
483 (defun output-raw-bytes (fd-stream thing &optional start end)
484   #!+sb-doc
485   "Output THING to FD-STREAM. THING can be any kind of vector or a SAP. If
486   THING is a SAP, END must be supplied (as length won't work)."
487   (let ((start (or start 0))
488         (end (or end (length (the (simple-array * (*)) thing)))))
489     (declare (type index start end))
490     (when (and (not (fd-stream-dual-channel-p fd-stream))
491                (> (fd-stream-ibuf-tail fd-stream)
492                   (fd-stream-ibuf-head fd-stream)))
493       (file-position fd-stream (file-position fd-stream)))
494     (let* ((len (fd-stream-obuf-length fd-stream))
495            (tail (fd-stream-obuf-tail fd-stream))
496            (space (- len tail))
497            (bytes (- end start))
498            (newtail (+ tail bytes)))
499       (cond ((minusp bytes) ; error case
500              (error ":END before :START!"))
501             ((zerop bytes)) ; easy case
502             ((<= bytes space)
503              (if (system-area-pointer-p thing)
504                  (system-area-ub8-copy thing start
505                                        (fd-stream-obuf-sap fd-stream)
506                                        tail
507                                        bytes)
508                  ;; FIXME: There should be some type checking somewhere to
509                  ;; verify that THING here is a vector, not just <not a SAP>.
510                  (copy-ub8-to-system-area thing start
511                                           (fd-stream-obuf-sap fd-stream)
512                                           tail
513                                           bytes))
514              (setf (fd-stream-obuf-tail fd-stream) newtail))
515             ((<= bytes len)
516              (flush-output-buffer fd-stream)
517              (if (system-area-pointer-p thing)
518                  (system-area-ub8-copy thing
519                                        start
520                                        (fd-stream-obuf-sap fd-stream)
521                                        0
522                                        bytes)
523                  ;; FIXME: There should be some type checking somewhere to
524                  ;; verify that THING here is a vector, not just <not a SAP>.
525                  (copy-ub8-to-system-area thing
526                                           start
527                                           (fd-stream-obuf-sap fd-stream)
528                                           0
529                                           bytes))
530              (setf (fd-stream-obuf-tail fd-stream) bytes))
531             (t
532              (flush-output-buffer fd-stream)
533              (frob-output fd-stream thing start end nil))))))
534
535 ;;; the routine to use to output a string. If the stream is
536 ;;; unbuffered, slam the string down the file descriptor, otherwise
537 ;;; use OUTPUT-RAW-BYTES to buffer the string. Update charpos by
538 ;;; checking to see where the last newline was.
539 (defun fd-sout (stream thing start end)
540   (declare (type fd-stream stream) (type string thing))
541   (let ((start (or start 0))
542         (end (or end (length (the vector thing)))))
543     (declare (fixnum start end))
544     (let ((last-newline
545            (string-dispatch (simple-base-string
546                              #!+sb-unicode
547                              (simple-array character (*))
548                              string)
549                thing
550              (position #\newline thing :from-end t
551                        :start start :end end))))
552       (if (and (typep thing 'base-string)
553                (eq (fd-stream-external-format stream) :latin-1))
554           (ecase (fd-stream-buffering stream)
555             (:full
556              (output-raw-bytes stream thing start end))
557             (:line
558              (output-raw-bytes stream thing start end)
559              (when last-newline
560                (flush-output-buffer stream)))
561             (:none
562              (frob-output stream thing start end nil)))
563           (ecase (fd-stream-buffering stream)
564             (:full (funcall (fd-stream-output-bytes stream)
565                             stream thing nil start end))
566             (:line (funcall (fd-stream-output-bytes stream)
567                             stream thing last-newline start end))
568             (:none (funcall (fd-stream-output-bytes stream)
569                             stream thing t start end))))
570       (if last-newline
571           (setf (fd-stream-char-pos stream) (- end last-newline 1))
572           (incf (fd-stream-char-pos stream) (- end start))))))
573
574 (defvar *external-formats* ()
575   #!+sb-doc
576   "List of all available external formats. Each element is a list of the
577   element-type, string input function name, character input function name,
578   and string output function name.")
579
580 (defun get-external-format (external-format)
581   (dolist (entry *external-formats*)
582     (when (member external-format (first entry))
583       (return entry))))
584
585 (defun get-external-format-function (external-format index)
586   (let ((entry (get-external-format external-format)))
587     (when entry (nth index entry))))
588
589 ;;; Find an output routine to use given the type and buffering. Return
590 ;;; as multiple values the routine, the real type transfered, and the
591 ;;; number of bytes per element.
592 (defun pick-output-routine (type buffering &optional external-format)
593   (when (subtypep type 'character)
594     (let ((entry (get-external-format external-format)))
595       (when entry
596         (return-from pick-output-routine
597           (values (symbol-function (nth (ecase buffering
598                                           (:none 4)
599                                           (:line 5)
600                                           (:full 6))
601                                         entry))
602                   'character
603                   1
604                   (symbol-function (fourth entry))
605                   (first (first entry)))))))
606   (dolist (entry *output-routines*)
607     (when (and (subtypep type (first entry))
608                (eq buffering (second entry))
609                (or (not (fifth entry))
610                    (eq external-format (fifth entry))))
611       (return-from pick-output-routine
612         (values (symbol-function (third entry))
613                 (first entry)
614                 (fourth entry)))))
615   ;; KLUDGE: dealing with the buffering here leads to excessive code
616   ;; explosion.
617   ;;
618   ;; KLUDGE: also see comments in PICK-INPUT-ROUTINE
619   (loop for i from 40 by 8 to 1024 ; ARB (KLUDGE)
620         if (subtypep type `(unsigned-byte ,i))
621         do (return-from pick-output-routine
622              (values
623               (ecase buffering
624                 (:none
625                  (lambda (stream byte)
626                    (output-wrapper (stream (/ i 8) (:none) nil)
627                      (loop for j from 0 below (/ i 8)
628                            do (setf (sap-ref-8
629                                      (fd-stream-obuf-sap stream)
630                                      (+ j (fd-stream-obuf-tail stream)))
631                                     (ldb (byte 8 (- i 8 (* j 8))) byte))))))
632                 (:full
633                  (lambda (stream byte)
634                    (output-wrapper (stream (/ i 8) (:full) nil)
635                      (loop for j from 0 below (/ i 8)
636                            do (setf (sap-ref-8
637                                      (fd-stream-obuf-sap stream)
638                                      (+ j (fd-stream-obuf-tail stream)))
639                                     (ldb (byte 8 (- i 8 (* j 8))) byte)))))))
640               `(unsigned-byte ,i)
641               (/ i 8))))
642   (loop for i from 40 by 8 to 1024 ; ARB (KLUDGE)
643         if (subtypep type `(signed-byte ,i))
644         do (return-from pick-output-routine
645              (values
646               (ecase buffering
647                 (:none
648                  (lambda (stream byte)
649                    (output-wrapper (stream (/ i 8) (:none) nil)
650                      (loop for j from 0 below (/ i 8)
651                            do (setf (sap-ref-8
652                                      (fd-stream-obuf-sap stream)
653                                      (+ j (fd-stream-obuf-tail stream)))
654                                     (ldb (byte 8 (- i 8 (* j 8))) byte))))))
655                 (:full
656                  (lambda (stream byte)
657                    (output-wrapper (stream (/ i 8) (:full) nil)
658                      (loop for j from 0 below (/ i 8)
659                            do (setf (sap-ref-8
660                                      (fd-stream-obuf-sap stream)
661                                      (+ j (fd-stream-obuf-tail stream)))
662                                     (ldb (byte 8 (- i 8 (* j 8))) byte)))))))
663               `(signed-byte ,i)
664               (/ i 8)))))
665 \f
666 ;;;; input routines and related noise
667
668 ;;; a list of all available input routines. Each element is a list of
669 ;;; the element-type input, the function name, and the number of bytes
670 ;;; per element.
671 (defvar *input-routines* ())
672
673 ;;; Return whether a primitive partial read operation on STREAM's FD
674 ;;; would (probably) block.  Signal a `simple-stream-error' if the
675 ;;; system call implementing this operation fails.
676 ;;;
677 ;;; It is "may" instead of "would" because "would" is not quite
678 ;;; correct on win32.  However, none of the places that use it require
679 ;;; further assurance than "may" versus "will definitely not".
680 (defun sysread-may-block-p (stream)
681   #+win32
682   ;; This answers T at EOF on win32, I think.
683   (not (sb!win32:fd-listen (fd-stream-fd stream)))
684   #-win32
685   (sb!unix:with-restarted-syscall (count errno)
686     (sb!alien:with-alien ((read-fds (sb!alien:struct sb!unix:fd-set)))
687       (sb!unix:fd-zero read-fds)
688       (sb!unix:fd-set (fd-stream-fd stream) read-fds)
689       (sb!unix:unix-fast-select (1+ (fd-stream-fd stream))
690                                 (sb!alien:addr read-fds)
691                                 nil nil 0 0))
692     (case count
693       ((1) nil)
694       ((0) t)
695       (otherwise
696        (simple-stream-perror "couldn't check whether ~S is readable"
697                              stream
698                              errno)))))
699
700 ;;; If the read would block wait (using SERVE-EVENT) till input is available,
701 ;;; then fill the input buffer, and return the number of bytes read. Throws
702 ;;; to EOF-INPUT-CATCHER if the eof was reached.
703 (defun refill-buffer/fd (stream)
704   (let ((fd (fd-stream-fd stream))
705         (errno 0)
706         (count 0))
707     (tagbody
708        ;; Check for blocking input before touching the stream, as if
709        ;; we happen to wait we are liable to be interrupted, and the
710        ;; interrupt handler may use the same stream.
711        (if (sysread-may-block-p stream)
712            (go :wait-for-input)
713            (go :main))
714        ;; These (:CLOSED-FLAME and :READ-ERROR) tags are here so what
715        ;; we can signal errors outside the WITHOUT-INTERRUPTS.
716      :closed-flame
717        (closed-flame stream)
718      :read-error
719        (simple-stream-perror "couldn't read from ~S" stream errno)
720      :wait-for-input
721        ;; This tag is here so we can unwind outside the WITHOUT-INTERRUPTS
722        ;; to wait for input if read tells us EWOULDBLOCK.
723        (unless (wait-until-fd-usable fd :input (fd-stream-timeout stream))
724          (signal-timeout 'io-timeout :stream stream :direction :read
725                          :seconds (fd-stream-timeout stream)))
726      :main
727        ;; Since the read should not block, we'll disable the
728        ;; interrupts here, so that we don't accidentally unwind and
729        ;; leave the stream in an inconsistent state.
730        (without-interrupts
731          (let ((ibuf-sap (fd-stream-ibuf-sap stream))
732                (buflen (fd-stream-ibuf-length stream))
733                (head (fd-stream-ibuf-head stream))
734                (tail (fd-stream-ibuf-tail stream)))
735            (declare (type index head tail))
736            ;; Check the SAP: if it is null, then someone has closed
737            ;; the stream from underneath us. This is not ment to fix
738            ;; multithreaded races, but to deal with interrupt handlers
739            ;; closing the stream.
740            (unless ibuf-sap
741              (go :closed-flame))
742            (unless (zerop head)
743              (cond ((eql head tail)
744                     (setf head 0
745                           tail 0
746                           (fd-stream-ibuf-head stream) 0
747                           (fd-stream-ibuf-tail stream) 0))
748                    (t
749                     (decf tail head)
750                     (system-area-ub8-copy ibuf-sap head
751                                           ibuf-sap 0 tail)
752                     (setf head 0
753                           (fd-stream-ibuf-head stream) 0
754                           (fd-stream-ibuf-tail stream) tail))))
755            (setf (fd-stream-listen stream) nil)
756            (setf (values count errno)
757                  (sb!unix:unix-read fd (int-sap (+ (sap-int ibuf-sap) tail))
758                                     (- buflen tail)))
759            (cond ((null count)
760                   #!+win32
761                   (go :read-error)
762                   #!-win32
763                   (if (eql errno sb!unix:ewouldblock)
764                       (go :wait-for-input)
765                       (go :read-error)))
766                  ((zerop count)
767                   (setf (fd-stream-listen stream) :eof)
768                   (/show0 "THROWing EOF-INPUT-CATCHER")
769                   (throw 'eof-input-catcher nil))
770                  (t
771                   ;; Success!
772                   (incf (fd-stream-ibuf-tail stream) count))))))
773     count))
774
775 ;;; Make sure there are at least BYTES number of bytes in the input
776 ;;; buffer. Keep calling REFILL-BUFFER/FD until that condition is met.
777 (defmacro input-at-least (stream bytes)
778   (let ((stream-var (gensym))
779         (bytes-var (gensym)))
780     `(let ((,stream-var ,stream)
781            (,bytes-var ,bytes))
782        (loop
783          (when (>= (- (fd-stream-ibuf-tail ,stream-var)
784                       (fd-stream-ibuf-head ,stream-var))
785                    ,bytes-var)
786            (return))
787          (refill-buffer/fd ,stream-var)))))
788
789 (defmacro input-wrapper/variable-width ((stream bytes eof-error eof-value)
790                                         &body read-forms)
791   (let ((stream-var (gensym))
792         (retry-var (gensym))
793         (element-var (gensym)))
794     `(let ((,stream-var ,stream)
795            (size nil))
796        (if (fd-stream-unread ,stream-var)
797            (prog1
798                (fd-stream-unread ,stream-var)
799              (setf (fd-stream-unread ,stream-var) nil)
800              (setf (fd-stream-listen ,stream-var) nil))
801            (let ((,element-var nil)
802                  (decode-break-reason nil))
803              (do ((,retry-var t))
804                  ((not ,retry-var))
805                (unless
806                    (catch 'eof-input-catcher
807                      (setf decode-break-reason
808                            (block decode-break-reason
809                              (input-at-least ,stream-var 1)
810                              (let* ((byte (sap-ref-8 (fd-stream-ibuf-sap
811                                                       ,stream-var)
812                                                      (fd-stream-ibuf-head
813                                                       ,stream-var))))
814                                (declare (ignorable byte))
815                                (setq size ,bytes)
816                                (input-at-least ,stream-var size)
817                                (setq ,element-var (locally ,@read-forms))
818                                (setq ,retry-var nil))
819                              nil))
820                      (when decode-break-reason
821                        (stream-decoding-error-and-handle stream
822                                                          decode-break-reason))
823                      t)
824                  (let ((octet-count (- (fd-stream-ibuf-tail ,stream-var)
825                                       (fd-stream-ibuf-head ,stream-var))))
826                    (when (or (zerop octet-count)
827                              (and (not ,element-var)
828                                   (not decode-break-reason)
829                                   (stream-decoding-error-and-handle
830                                    stream octet-count)))
831                      (setq ,retry-var nil)))))
832              (cond (,element-var
833                     (incf (fd-stream-ibuf-head ,stream-var) size)
834                     ,element-var)
835                    (t
836                     (eof-or-lose ,stream-var ,eof-error ,eof-value))))))))
837
838 ;;; a macro to wrap around all input routines to handle EOF-ERROR noise
839 (defmacro input-wrapper ((stream bytes eof-error eof-value) &body read-forms)
840   (let ((stream-var (gensym))
841         (element-var (gensym)))
842     `(let ((,stream-var ,stream))
843        (if (fd-stream-unread ,stream-var)
844            (prog1
845                (fd-stream-unread ,stream-var)
846              (setf (fd-stream-unread ,stream-var) nil)
847              (setf (fd-stream-listen ,stream-var) nil))
848            (let ((,element-var
849                   (catch 'eof-input-catcher
850                     (input-at-least ,stream-var ,bytes)
851                     (locally ,@read-forms))))
852              (cond (,element-var
853                     (incf (fd-stream-ibuf-head ,stream-var) ,bytes)
854                     ,element-var)
855                    (t
856                     (eof-or-lose ,stream-var ,eof-error ,eof-value))))))))
857
858 (defmacro def-input-routine/variable-width (name
859                                             (type external-format size sap head)
860                                             &rest body)
861   `(progn
862      (defun ,name (stream eof-error eof-value)
863        (input-wrapper/variable-width (stream ,size eof-error eof-value)
864          (let ((,sap (fd-stream-ibuf-sap stream))
865                (,head (fd-stream-ibuf-head stream)))
866            ,@body)))
867      (setf *input-routines*
868            (nconc *input-routines*
869                   (list (list ',type ',name 1 ',external-format))))))
870
871 (defmacro def-input-routine (name
872                              (type size sap head)
873                              &rest body)
874   `(progn
875      (defun ,name (stream eof-error eof-value)
876        (input-wrapper (stream ,size eof-error eof-value)
877          (let ((,sap (fd-stream-ibuf-sap stream))
878                (,head (fd-stream-ibuf-head stream)))
879            ,@body)))
880      (setf *input-routines*
881            (nconc *input-routines*
882                   (list (list ',type ',name ',size nil))))))
883
884 ;;; STREAM-IN routine for reading a string char
885 (def-input-routine input-character
886                    (character 1 sap head)
887   (code-char (sap-ref-8 sap head)))
888
889 ;;; STREAM-IN routine for reading an unsigned 8 bit number
890 (def-input-routine input-unsigned-8bit-byte
891                    ((unsigned-byte 8) 1 sap head)
892   (sap-ref-8 sap head))
893
894 ;;; STREAM-IN routine for reading a signed 8 bit number
895 (def-input-routine input-signed-8bit-number
896                    ((signed-byte 8) 1 sap head)
897   (signed-sap-ref-8 sap head))
898
899 ;;; STREAM-IN routine for reading an unsigned 16 bit number
900 (def-input-routine input-unsigned-16bit-byte
901                    ((unsigned-byte 16) 2 sap head)
902   (sap-ref-16 sap head))
903
904 ;;; STREAM-IN routine for reading a signed 16 bit number
905 (def-input-routine input-signed-16bit-byte
906                    ((signed-byte 16) 2 sap head)
907   (signed-sap-ref-16 sap head))
908
909 ;;; STREAM-IN routine for reading a unsigned 32 bit number
910 (def-input-routine input-unsigned-32bit-byte
911                    ((unsigned-byte 32) 4 sap head)
912   (sap-ref-32 sap head))
913
914 ;;; STREAM-IN routine for reading a signed 32 bit number
915 (def-input-routine input-signed-32bit-byte
916                    ((signed-byte 32) 4 sap head)
917   (signed-sap-ref-32 sap head))
918
919 #+#.(cl:if (cl:= sb!vm:n-word-bits 64) '(and) '(or))
920 (progn
921   (def-input-routine input-unsigned-64bit-byte
922       ((unsigned-byte 64) 8 sap head)
923     (sap-ref-64 sap head))
924   (def-input-routine input-signed-64bit-byte
925       ((signed-byte 64) 8 sap head)
926     (signed-sap-ref-64 sap head)))
927
928 ;;; Find an input routine to use given the type. Return as multiple
929 ;;; values the routine, the real type transfered, and the number of
930 ;;; bytes per element (and for character types string input routine).
931 (defun pick-input-routine (type &optional external-format)
932   (when (subtypep type 'character)
933     (dolist (entry *external-formats*)
934       (when (member external-format (first entry))
935         (return-from pick-input-routine
936           (values (symbol-function (third entry))
937                   'character
938                   1
939                   (symbol-function (second entry))
940                   (first (first entry)))))))
941   (dolist (entry *input-routines*)
942     (when (and (subtypep type (first entry))
943                (or (not (fourth entry))
944                    (eq external-format (fourth entry))))
945       (return-from pick-input-routine
946         (values (symbol-function (second entry))
947                 (first entry)
948                 (third entry)))))
949   ;; FIXME: let's do it the hard way, then (but ignore things like
950   ;; endianness, efficiency, and the necessary coupling between these
951   ;; and the output routines).  -- CSR, 2004-02-09
952   (loop for i from 40 by 8 to 1024 ; ARB (well, KLUDGE really)
953         if (subtypep type `(unsigned-byte ,i))
954         do (return-from pick-input-routine
955              (values
956               (lambda (stream eof-error eof-value)
957                 (input-wrapper (stream (/ i 8) eof-error eof-value)
958                   (let ((sap (fd-stream-ibuf-sap stream))
959                         (head (fd-stream-ibuf-head stream)))
960                     (loop for j from 0 below (/ i 8)
961                           with result = 0
962                           do (setf result
963                                    (+ (* 256 result)
964                                       (sap-ref-8 sap (+ head j))))
965                           finally (return result)))))
966               `(unsigned-byte ,i)
967               (/ i 8))))
968   (loop for i from 40 by 8 to 1024 ; ARB (well, KLUDGE really)
969         if (subtypep type `(signed-byte ,i))
970         do (return-from pick-input-routine
971              (values
972               (lambda (stream eof-error eof-value)
973                 (input-wrapper (stream (/ i 8) eof-error eof-value)
974                   (let ((sap (fd-stream-ibuf-sap stream))
975                         (head (fd-stream-ibuf-head stream)))
976                     (loop for j from 0 below (/ i 8)
977                           with result = 0
978                           do (setf result
979                                    (+ (* 256 result)
980                                       (sap-ref-8 sap (+ head j))))
981                           finally (return (if (logbitp (1- i) result)
982                                               (dpb result (byte i 0) -1)
983                                               result))))))
984               `(signed-byte ,i)
985               (/ i 8)))))
986
987 ;;; Return a string constructed from SAP, START, and END.
988 (defun string-from-sap (sap start end)
989   (declare (type index start end))
990   (let* ((length (- end start))
991          (string (make-string length)))
992     (copy-ub8-from-system-area sap start
993                                string 0
994                                length)
995     string))
996
997 ;;; the N-BIN method for FD-STREAMs
998 ;;;
999 ;;; Note that this blocks in UNIX-READ. It is generally used where
1000 ;;; there is a definite amount of reading to be done, so blocking
1001 ;;; isn't too problematical.
1002 (defun fd-stream-read-n-bytes (stream buffer start requested eof-error-p
1003                                &aux (total-copied 0))
1004   (declare (type fd-stream stream))
1005   (declare (type index start requested total-copied))
1006   (let ((unread (fd-stream-unread stream)))
1007     (when unread
1008       ;; AVERs designed to fail when we have more complicated
1009       ;; character representations.
1010       (aver (typep unread 'base-char))
1011       (aver (= (fd-stream-element-size stream) 1))
1012       ;; KLUDGE: this is a slightly-unrolled-and-inlined version of
1013       ;; %BYTE-BLT
1014       (etypecase buffer
1015         (system-area-pointer
1016          (setf (sap-ref-8 buffer start) (char-code unread)))
1017         ((simple-unboxed-array (*))
1018          (setf (aref buffer start) unread)))
1019       (setf (fd-stream-unread stream) nil)
1020       (setf (fd-stream-listen stream) nil)
1021       (incf total-copied)))
1022   (do ()
1023       (nil)
1024     (let* ((remaining-request (- requested total-copied))
1025            (head (fd-stream-ibuf-head stream))
1026            (tail (fd-stream-ibuf-tail stream))
1027            (available (- tail head))
1028            (n-this-copy (min remaining-request available))
1029            (this-start (+ start total-copied))
1030            (this-end (+ this-start n-this-copy))
1031            (sap (fd-stream-ibuf-sap stream)))
1032       (declare (type index remaining-request head tail available))
1033       (declare (type index n-this-copy))
1034       ;; Copy data from stream buffer into user's buffer.
1035       (%byte-blt sap head buffer this-start this-end)
1036       (incf (fd-stream-ibuf-head stream) n-this-copy)
1037       (incf total-copied n-this-copy)
1038       ;; Maybe we need to refill the stream buffer.
1039       (cond (;; If there were enough data in the stream buffer, we're done.
1040              (= total-copied requested)
1041              (return total-copied))
1042             (;; If EOF, we're done in another way.
1043              (null (catch 'eof-input-catcher (refill-buffer/fd stream)))
1044              (if eof-error-p
1045                  (error 'end-of-file :stream stream)
1046                  (return total-copied)))
1047             ;; Otherwise we refilled the stream buffer, so fall
1048             ;; through into another pass of the loop.
1049             ))))
1050
1051 (defun fd-stream-resync (stream)
1052   (dolist (entry *external-formats*)
1053     (when (member (fd-stream-external-format stream) (first entry))
1054       (return-from fd-stream-resync
1055         (funcall (symbol-function (eighth entry)) stream)))))
1056
1057 (defun get-fd-stream-character-sizer (stream)
1058   (dolist (entry *external-formats*)
1059     (when (member (fd-stream-external-format stream) (first entry))
1060       (return-from get-fd-stream-character-sizer (ninth entry)))))
1061
1062 (defun fd-stream-character-size (stream char)
1063   (let ((sizer (get-fd-stream-character-sizer stream)))
1064     (when sizer (funcall sizer char))))
1065
1066 (defun fd-stream-string-size (stream string)
1067   (let ((sizer (get-fd-stream-character-sizer stream)))
1068     (when sizer
1069       (loop for char across string summing (funcall sizer char)))))
1070
1071 (defun find-external-format (external-format)
1072   (when external-format
1073     (find external-format *external-formats* :test #'member :key #'car)))
1074
1075 (defun variable-width-external-format-p (ef-entry)
1076   (when (eighth ef-entry) t))
1077
1078 (defun bytes-for-char-fun (ef-entry)
1079   (if ef-entry (symbol-function (ninth ef-entry)) (constantly 1)))
1080
1081 ;;; FIXME: OAOOM here vrt. *EXTERNAL-FORMAT-FUNCTIONS* in fd-stream.lisp
1082 (defmacro define-external-format (external-format size output-restart
1083                                   out-expr in-expr)
1084   (let* ((name (first external-format))
1085          (out-function (symbolicate "OUTPUT-BYTES/" name))
1086          (format (format nil "OUTPUT-CHAR-~A-~~A-BUFFERED" (string name)))
1087          (in-function (symbolicate "FD-STREAM-READ-N-CHARACTERS/" name))
1088          (in-char-function (symbolicate "INPUT-CHAR/" name))
1089          (size-function (symbolicate "BYTES-FOR-CHAR/" name))
1090          (read-c-string-function (symbolicate "READ-FROM-C-STRING/" name))
1091          (output-c-string-function (symbolicate "OUTPUT-TO-C-STRING/" name))
1092          (n-buffer (gensym "BUFFER")))
1093     `(progn
1094       (defun ,size-function (byte)
1095         (declare (ignore byte))
1096         ,size)
1097       (defun ,out-function (stream string flush-p start end)
1098         (let ((start (or start 0))
1099               (end (or end (length string))))
1100           (declare (type index start end))
1101           (when (and (not (fd-stream-dual-channel-p stream))
1102                      (> (fd-stream-ibuf-tail stream)
1103                         (fd-stream-ibuf-head stream)))
1104             (file-position stream (file-position stream)))
1105           (unless (<= 0 start end (length string))
1106             (signal-bounding-indices-bad-error string start end))
1107           (do ()
1108               ((= end start))
1109             (setf (fd-stream-obuf-tail stream)
1110                   (string-dispatch (simple-base-string
1111                                     #!+sb-unicode
1112                                     (simple-array character (*))
1113                                     string)
1114                       string
1115                     (let ((len (fd-stream-obuf-length stream))
1116                           (sap (fd-stream-obuf-sap stream))
1117                           (tail (fd-stream-obuf-tail stream)))
1118                       (declare (type index tail)
1119                                ;; STRING bounds have already been checked.
1120                                (optimize (safety 0)))
1121                       (loop
1122                          (,@(if output-restart
1123                                 `(catch 'output-nothing)
1124                                 `(progn))
1125                             (do* ()
1126                                  ((or (= start end) (< (- len tail) 4)))
1127                               (let* ((byte (aref string start))
1128                                      (bits (char-code byte)))
1129                                 ,out-expr
1130                                 (incf tail ,size)
1131                                 (incf start)))
1132                             ;; Exited from the loop normally
1133                             (return tail))
1134                          ;; Exited via CATCH. Skip the current character
1135                          ;; and try the inner loop again.
1136                          (incf start)))))
1137             (when (< start end)
1138               (flush-output-buffer stream)))
1139           (when flush-p
1140             (flush-output-buffer stream))))
1141       (def-output-routines (,format
1142                             ,size
1143                             ,output-restart
1144                             (:none character)
1145                             (:line character)
1146                             (:full character))
1147           (if (char= byte #\Newline)
1148               (setf (fd-stream-char-pos stream) 0)
1149               (incf (fd-stream-char-pos stream)))
1150         (let ((bits (char-code byte))
1151               (sap (fd-stream-obuf-sap stream))
1152               (tail (fd-stream-obuf-tail stream)))
1153           ,out-expr))
1154       (defun ,in-function (stream buffer start requested eof-error-p
1155                            &aux (index start) (end (+ start requested)))
1156         (declare (type fd-stream stream)
1157                  (type index start requested index end)
1158                  (type
1159                   (simple-array character (#.+ansi-stream-in-buffer-length+))
1160                   buffer))
1161         (let ((unread (fd-stream-unread stream)))
1162           (when unread
1163             (setf (aref buffer index) unread)
1164             (setf (fd-stream-unread stream) nil)
1165             (setf (fd-stream-listen stream) nil)
1166             (incf index)))
1167         (do ()
1168             (nil)
1169           (let* ((head (fd-stream-ibuf-head stream))
1170                  (tail (fd-stream-ibuf-tail stream))
1171                  (sap (fd-stream-ibuf-sap stream)))
1172             (declare (type index head tail)
1173                      (type system-area-pointer sap))
1174             ;; Copy data from stream buffer into user's buffer.
1175             (dotimes (i (min (truncate (- tail head) ,size)
1176                              (- end index)))
1177               (declare (optimize speed))
1178               (let* ((byte (sap-ref-8 sap head)))
1179                 (setf (aref buffer index) ,in-expr)
1180                 (incf index)
1181                 (incf head ,size)))
1182             (setf (fd-stream-ibuf-head stream) head)
1183             ;; Maybe we need to refill the stream buffer.
1184             (cond ( ;; If there was enough data in the stream buffer, we're done.
1185                    (= index end)
1186                    (return (- index start)))
1187                   ( ;; If EOF, we're done in another way.
1188                    (null (catch 'eof-input-catcher (refill-buffer/fd stream)))
1189                    (if eof-error-p
1190                        (error 'end-of-file :stream stream)
1191                        (return (- index start))))
1192                   ;; Otherwise we refilled the stream buffer, so fall
1193                   ;; through into another pass of the loop.
1194                   ))))
1195       (def-input-routine ,in-char-function (character ,size sap head)
1196         (let ((byte (sap-ref-8 sap head)))
1197           ,in-expr))
1198       (defun ,read-c-string-function (sap element-type)
1199         (declare (type system-area-pointer sap)
1200                  (type (member character base-char) element-type))
1201         (locally
1202             (declare (optimize (speed 3) (safety 0)))
1203           (let* ((stream ,name)
1204                  (length
1205                   (loop for head of-type index upfrom 0 by ,size
1206                         for count of-type index upto (1- array-dimension-limit)
1207                         for byte = (sap-ref-8 sap head)
1208                         for char of-type character = ,in-expr
1209                         until (zerop (char-code char))
1210                         finally (return count)))
1211                  ;; Inline the common cases
1212                  (string (make-string length :element-type element-type)))
1213             (declare (ignorable stream)
1214                      (type index length)
1215                      (type simple-string string))
1216             (/show0 before-copy-loop)
1217             (loop for head of-type index upfrom 0 by ,size
1218                for index of-type index below length
1219                for byte = (sap-ref-8 sap head)
1220                for char of-type character = ,in-expr
1221                do (setf (aref string index) char))
1222             string))) ;; last loop rewrite to dotimes?
1223         (defun ,output-c-string-function (string)
1224           (declare (type simple-string string))
1225           (locally
1226               (declare (optimize (speed 3) (safety 0)))
1227             (let* ((length (length string))
1228                    (,n-buffer (make-array (* (1+ length) ,size)
1229                                           :element-type '(unsigned-byte 8)))
1230                    (tail 0)
1231                    (stream ,name))
1232               (declare (type index length tail))
1233               (with-pinned-objects (,n-buffer)
1234                 (let ((sap (vector-sap ,n-buffer)))
1235                   (declare (system-area-pointer sap))
1236                   (dotimes (i length)
1237                     (let* ((byte (aref string i))
1238                            (bits (char-code byte)))
1239                       (declare (ignorable byte bits))
1240                       ,out-expr)
1241                     (incf tail ,size))
1242                   (let* ((bits 0)
1243                          (byte (code-char bits)))
1244                     (declare (ignorable bits byte))
1245                     ,out-expr)))
1246               ,n-buffer)))
1247       (setf *external-formats*
1248        (cons '(,external-format ,in-function ,in-char-function ,out-function
1249                ,@(mapcar #'(lambda (buffering)
1250                              (intern (format nil format (string buffering))))
1251                          '(:none :line :full))
1252                nil ; no resync-function
1253                ,size-function ,read-c-string-function ,output-c-string-function)
1254         *external-formats*)))))
1255
1256 (defmacro define-external-format/variable-width
1257     (external-format output-restart out-size-expr
1258      out-expr in-size-expr in-expr)
1259   (let* ((name (first external-format))
1260          (out-function (symbolicate "OUTPUT-BYTES/" name))
1261          (format (format nil "OUTPUT-CHAR-~A-~~A-BUFFERED" (string name)))
1262          (in-function (symbolicate "FD-STREAM-READ-N-CHARACTERS/" name))
1263          (in-char-function (symbolicate "INPUT-CHAR/" name))
1264          (resync-function (symbolicate "RESYNC/" name))
1265          (size-function (symbolicate "BYTES-FOR-CHAR/" name))
1266          (read-c-string-function (symbolicate "READ-FROM-C-STRING/" name))
1267          (output-c-string-function (symbolicate "OUTPUT-TO-C-STRING/" name))
1268          (n-buffer (gensym "BUFFER")))
1269     `(progn
1270       (defun ,size-function (byte)
1271         (declare (ignorable byte))
1272         ,out-size-expr)
1273       (defun ,out-function (stream string flush-p start end)
1274         (let ((start (or start 0))
1275               (end (or end (length string))))
1276           (declare (type index start end))
1277           (when (and (not (fd-stream-dual-channel-p stream))
1278                      (> (fd-stream-ibuf-tail stream)
1279                         (fd-stream-ibuf-head stream)))
1280             (file-position stream (file-position stream)))
1281           (unless (<= 0 start end (length string))
1282             (signal-bounding-indices-bad-error string start end))
1283           (do ()
1284               ((= end start))
1285             (setf (fd-stream-obuf-tail stream)
1286                   (string-dispatch (simple-base-string
1287                                     #!+sb-unicode
1288                                     (simple-array character (*))
1289                                     string)
1290                       string
1291                     (let ((len (fd-stream-obuf-length stream))
1292                           (sap (fd-stream-obuf-sap stream))
1293                           (tail (fd-stream-obuf-tail stream)))
1294                       (declare (type index tail)
1295                                ;; STRING bounds have already been checked.
1296                                (optimize (safety 0)))
1297                       (loop
1298                          (,@(if output-restart
1299                                 `(catch 'output-nothing)
1300                                 `(progn))
1301                             (do* ()
1302                                  ((or (= start end) (< (- len tail) 4)))
1303                               (let* ((byte (aref string start))
1304                                      (bits (char-code byte))
1305                                      (size ,out-size-expr))
1306                                 ,out-expr
1307                                 (incf tail size)
1308                                 (incf start)))
1309                             ;; Exited from the loop normally
1310                             (return tail))
1311                          ;; Exited via CATCH. Skip the current character
1312                          ;; and try the inner loop again.
1313                          (incf start)))))
1314             (when (< start end)
1315               (flush-output-buffer stream)))
1316           (when flush-p
1317             (flush-output-buffer stream))))
1318       (def-output-routines/variable-width (,format
1319                                            ,out-size-expr
1320                                            ,output-restart
1321                                            ,external-format
1322                                            (:none character)
1323                                            (:line character)
1324                                            (:full character))
1325           (if (char= byte #\Newline)
1326               (setf (fd-stream-char-pos stream) 0)
1327               (incf (fd-stream-char-pos stream)))
1328         (let ((bits (char-code byte))
1329               (sap (fd-stream-obuf-sap stream))
1330               (tail (fd-stream-obuf-tail stream)))
1331           ,out-expr))
1332       (defun ,in-function (stream buffer start requested eof-error-p
1333                            &aux (total-copied 0))
1334         (declare (type fd-stream stream)
1335                  (type index start requested total-copied)
1336                  (type
1337                   (simple-array character (#.+ansi-stream-in-buffer-length+))
1338                   buffer))
1339         (let ((unread (fd-stream-unread stream)))
1340           (when unread
1341             (setf (aref buffer start) unread)
1342             (setf (fd-stream-unread stream) nil)
1343             (setf (fd-stream-listen stream) nil)
1344             (incf total-copied)))
1345         (do ()
1346             (nil)
1347           (let* ((head (fd-stream-ibuf-head stream))
1348                  (tail (fd-stream-ibuf-tail stream))
1349                  (sap (fd-stream-ibuf-sap stream))
1350                  (decode-break-reason nil))
1351             (declare (type index head tail))
1352             ;; Copy data from stream buffer into user's buffer.
1353             (do ((size nil nil))
1354                 ((or (= tail head) (= requested total-copied)))
1355               (setf decode-break-reason
1356                     (block decode-break-reason
1357                       (let ((byte (sap-ref-8 sap head)))
1358                         (declare (ignorable byte))
1359                         (setq size ,in-size-expr)
1360                         (when (> size (- tail head))
1361                           (return))
1362                         (setf (aref buffer (+ start total-copied)) ,in-expr)
1363                         (incf total-copied)
1364                         (incf head size))
1365                       nil))
1366               (setf (fd-stream-ibuf-head stream) head)
1367               (when decode-break-reason
1368                 ;; If we've already read some characters on when the invalid
1369                 ;; code sequence is detected, we return immediately. The
1370                 ;; handling of the error is deferred until the next call
1371                 ;; (where this check will be false). This allows establishing
1372                 ;; high-level handlers for decode errors (for example
1373                 ;; automatically resyncing in Lisp comments).
1374                 (when (plusp total-copied)
1375                   (return-from ,in-function total-copied))
1376                 (when (stream-decoding-error-and-handle
1377                        stream decode-break-reason)
1378                   (if eof-error-p
1379                       (error 'end-of-file :stream stream)
1380                       (return-from ,in-function total-copied)))
1381                 (setf head (fd-stream-ibuf-head stream))
1382                 (setf tail (fd-stream-ibuf-tail stream))))
1383             (setf (fd-stream-ibuf-head stream) head)
1384             ;; Maybe we need to refill the stream buffer.
1385             (cond ( ;; If there were enough data in the stream buffer, we're done.
1386                    (= total-copied requested)
1387                    (return total-copied))
1388                   ( ;; If EOF, we're done in another way.
1389                    (or (eq decode-break-reason 'eof)
1390                        (null (catch 'eof-input-catcher
1391                                (refill-buffer/fd stream))))
1392                    (if eof-error-p
1393                        (error 'end-of-file :stream stream)
1394                        (return total-copied)))
1395                   ;; Otherwise we refilled the stream buffer, so fall
1396                   ;; through into another pass of the loop.
1397                   ))))
1398       (def-input-routine/variable-width ,in-char-function (character
1399                                                            ,external-format
1400                                                            ,in-size-expr
1401                                                            sap head)
1402         (let ((byte (sap-ref-8 sap head)))
1403           (declare (ignorable byte))
1404           ,in-expr))
1405       (defun ,resync-function (stream)
1406         (loop (input-at-least stream 2)
1407               (incf (fd-stream-ibuf-head stream))
1408               (unless (block decode-break-reason
1409                         (let* ((sap (fd-stream-ibuf-sap stream))
1410                                (head (fd-stream-ibuf-head stream))
1411                                (byte (sap-ref-8 sap head))
1412                                (size ,in-size-expr))
1413                           (declare (ignorable byte))
1414                           (input-at-least stream size)
1415                           (let ((sap (fd-stream-ibuf-sap stream))
1416                                 (head (fd-stream-ibuf-head stream)))
1417                             ,in-expr))
1418                         nil)
1419                 (return))))
1420       (defun ,read-c-string-function (sap element-type)
1421         (declare (type system-area-pointer sap))
1422         (locally
1423             (declare (optimize (speed 3) (safety 0)))
1424           (let* ((stream ,name)
1425                  (size 0) (head 0) (byte 0) (char nil)
1426                  (decode-break-reason nil)
1427                  (length (dotimes (count (1- ARRAY-DIMENSION-LIMIT) count)
1428                            (setf decode-break-reason
1429                                  (block decode-break-reason
1430                                    (setf byte (sap-ref-8 sap head)
1431                                          size ,in-size-expr
1432                                          char ,in-expr)
1433                                    (incf head size)
1434                                    nil))
1435                            (when decode-break-reason
1436                              (c-string-decoding-error ,name decode-break-reason))
1437                            (when (zerop (char-code char))
1438                              (return count))))
1439                  (string (make-string length :element-type element-type)))
1440             (declare (ignorable stream)
1441                      (type index head length) ;; size
1442                      (type (unsigned-byte 8) byte)
1443                      (type (or null character) char)
1444                      (type string string))
1445             (setf head 0)
1446             (dotimes (index length string)
1447               (setf decode-break-reason
1448                     (block decode-break-reason
1449                       (setf byte (sap-ref-8 sap head)
1450                             size ,in-size-expr
1451                             char ,in-expr)
1452                       (incf head size)
1453                       nil))
1454               (when decode-break-reason
1455                 (c-string-decoding-error ,name decode-break-reason))
1456               (setf (aref string index) char)))))
1457
1458       (defun ,output-c-string-function (string)
1459         (declare (type simple-string string))
1460         (locally
1461             (declare (optimize (speed 3) (safety 0)))
1462           (let* ((length (length string))
1463                  (char-length (make-array (1+ length) :element-type 'index))
1464                  (buffer-length
1465                   (+ (loop for i of-type index below length
1466                         for byte of-type character = (aref string i)
1467                         for bits = (char-code byte)
1468                         sum (setf (aref char-length i)
1469                                   (the index ,out-size-expr)))
1470                      (let* ((byte (code-char 0))
1471                             (bits (char-code byte)))
1472                        (declare (ignorable byte bits))
1473                        (setf (aref char-length length)
1474                              (the index ,out-size-expr)))))
1475                  (tail 0)
1476                  (,n-buffer (make-array buffer-length
1477                                         :element-type '(unsigned-byte 8)))
1478                  stream)
1479             (declare (type index length buffer-length tail)
1480                      (type null stream)
1481                      (ignorable stream))
1482             (with-pinned-objects (,n-buffer)
1483               (let ((sap (vector-sap ,n-buffer)))
1484                 (declare (system-area-pointer sap))
1485                 (loop for i of-type index below length
1486                       for byte of-type character = (aref string i)
1487                       for bits = (char-code byte)
1488                       for size of-type index = (aref char-length i)
1489                       do (prog1
1490                              ,out-expr
1491                            (incf tail size)))
1492                 (let* ((bits 0)
1493                        (byte (code-char bits))
1494                        (size (aref char-length length)))
1495                   (declare (ignorable bits byte size))
1496                   ,out-expr)))
1497             ,n-buffer)))
1498
1499       (setf *external-formats*
1500        (cons '(,external-format ,in-function ,in-char-function ,out-function
1501                ,@(mapcar #'(lambda (buffering)
1502                              (intern (format nil format (string buffering))))
1503                          '(:none :line :full))
1504                ,resync-function
1505                ,size-function ,read-c-string-function ,output-c-string-function)
1506         *external-formats*)))))
1507
1508 ;;; Multiple names for the :ISO{,-}8859-* families are needed because on
1509 ;;; FreeBSD (and maybe other BSD systems), nl_langinfo("LATIN-1") will
1510 ;;; return "ISO8859-1" instead of "ISO-8859-1".
1511 (define-external-format (:latin-1 :latin1 :iso-8859-1 :iso8859-1)
1512     1 t
1513   (if (>= bits 256)
1514       (external-format-encoding-error stream bits)
1515       (setf (sap-ref-8 sap tail) bits))
1516   (code-char byte))
1517
1518 (define-external-format (:ascii :us-ascii :ansi_x3.4-1968
1519                          :iso-646 :iso-646-us :|646|)
1520     1 t
1521   (if (>= bits 128)
1522       (external-format-encoding-error stream bits)
1523       (setf (sap-ref-8 sap tail) bits))
1524   (code-char byte))
1525
1526 (let* ((table (let ((s (make-string 256)))
1527                 (map-into s #'code-char
1528                           '(#x00 #x01 #x02 #x03 #x9c #x09 #x86 #x7f #x97 #x8d #x8e #x0b #x0c #x0d #x0e #x0f
1529                             #x10 #x11 #x12 #x13 #x9d #x85 #x08 #x87 #x18 #x19 #x92 #x8f #x1c #x1d #x1e #x1f
1530                             #x80 #x81 #x82 #x83 #x84 #x0a #x17 #x1b #x88 #x89 #x8a #x8b #x8c #x05 #x06 #x07
1531                             #x90 #x91 #x16 #x93 #x94 #x95 #x96 #x04 #x98 #x99 #x9a #x9b #x14 #x15 #x9e #x1a
1532                             #x20 #xa0 #xe2 #xe4 #xe0 #xe1 #xe3 #xe5 #xe7 #xf1 #xa2 #x2e #x3c #x28 #x2b #x7c
1533                             #x26 #xe9 #xea #xeb #xe8 #xed #xee #xef #xec #xdf #x21 #x24 #x2a #x29 #x3b #xac
1534                             #x2d #x2f #xc2 #xc4 #xc0 #xc1 #xc3 #xc5 #xc7 #xd1 #xa6 #x2c #x25 #x5f #x3e #x3f
1535                             #xf8 #xc9 #xca #xcb #xc8 #xcd #xce #xcf #xcc #x60 #x3a #x23 #x40 #x27 #x3d #x22
1536                             #xd8 #x61 #x62 #x63 #x64 #x65 #x66 #x67 #x68 #x69 #xab #xbb #xf0 #xfd #xfe #xb1
1537                             #xb0 #x6a #x6b #x6c #x6d #x6e #x6f #x70 #x71 #x72 #xaa #xba #xe6 #xb8 #xc6 #xa4
1538                             #xb5 #x7e #x73 #x74 #x75 #x76 #x77 #x78 #x79 #x7a #xa1 #xbf #xd0 #xdd #xde #xae
1539                             #x5e #xa3 #xa5 #xb7 #xa9 #xa7 #xb6 #xbc #xbd #xbe #x5b #x5d #xaf #xa8 #xb4 #xd7
1540                             #x7b #x41 #x42 #x43 #x44 #x45 #x46 #x47 #x48 #x49 #xad #xf4 #xf6 #xf2 #xf3 #xf5
1541                             #x7d #x4a #x4b #x4c #x4d #x4e #x4f #x50 #x51 #x52 #xb9 #xfb #xfc #xf9 #xfa #xff
1542                             #x5c #xf7 #x53 #x54 #x55 #x56 #x57 #x58 #x59 #x5a #xb2 #xd4 #xd6 #xd2 #xd3 #xd5
1543                             #x30 #x31 #x32 #x33 #x34 #x35 #x36 #x37 #x38 #x39 #xb3 #xdb #xdc #xd9 #xda #x9f))
1544                 s))
1545        (reverse-table (let ((rt (make-array 256 :element-type '(unsigned-byte 8) :initial-element 0)))
1546                           (loop for char across table for i from 0
1547                                do (aver (= 0 (aref rt (char-code char))))
1548                                do (setf (aref rt (char-code char)) i))
1549                           rt)))
1550   (define-external-format (:ebcdic-us :ibm-037 :ibm037)
1551       1 t
1552     (if (>= bits 256)
1553         (external-format-encoding-error stream bits)
1554         (setf (sap-ref-8 sap tail) (aref reverse-table bits)))
1555     (aref table byte)))
1556
1557
1558 #!+sb-unicode
1559 (let ((latin-9-table (let ((table (make-string 256)))
1560                        (do ((i 0 (1+ i)))
1561                            ((= i 256))
1562                          (setf (aref table i) (code-char i)))
1563                        (setf (aref table #xa4) (code-char #x20ac))
1564                        (setf (aref table #xa6) (code-char #x0160))
1565                        (setf (aref table #xa8) (code-char #x0161))
1566                        (setf (aref table #xb4) (code-char #x017d))
1567                        (setf (aref table #xb8) (code-char #x017e))
1568                        (setf (aref table #xbc) (code-char #x0152))
1569                        (setf (aref table #xbd) (code-char #x0153))
1570                        (setf (aref table #xbe) (code-char #x0178))
1571                        table))
1572       (latin-9-reverse-1 (make-array 16
1573                                      :element-type '(unsigned-byte 21)
1574                                      :initial-contents '(#x0160 #x0161 #x0152 #x0153 0 0 0 0 #x0178 0 0 0 #x20ac #x017d #x017e 0)))
1575       (latin-9-reverse-2 (make-array 16
1576                                      :element-type '(unsigned-byte 8)
1577                                      :initial-contents '(#xa6 #xa8 #xbc #xbd 0 0 0 0 #xbe 0 0 0 #xa4 #xb4 #xb8 0))))
1578   (define-external-format (:latin-9 :latin9 :iso-8859-15 :iso8859-15)
1579       1 t
1580     (setf (sap-ref-8 sap tail)
1581           (if (< bits 256)
1582               (if (= bits (char-code (aref latin-9-table bits)))
1583                   bits
1584                   (external-format-encoding-error stream byte))
1585               (if (= (aref latin-9-reverse-1 (logand bits 15)) bits)
1586                   (aref latin-9-reverse-2 (logand bits 15))
1587                   (external-format-encoding-error stream byte))))
1588     (aref latin-9-table byte)))
1589
1590 (define-external-format/variable-width (:utf-8 :utf8) nil
1591   (let ((bits (char-code byte)))
1592     (cond ((< bits #x80) 1)
1593           ((< bits #x800) 2)
1594           ((< bits #x10000) 3)
1595           (t 4)))
1596   (ecase size
1597     (1 (setf (sap-ref-8 sap tail) bits))
1598     (2 (setf (sap-ref-8 sap tail) (logior #xc0 (ldb (byte 5 6) bits))
1599              (sap-ref-8 sap (1+ tail)) (logior #x80 (ldb (byte 6 0) bits))))
1600     (3 (setf (sap-ref-8 sap tail) (logior #xe0 (ldb (byte 4 12) bits))
1601              (sap-ref-8 sap (1+ tail)) (logior #x80 (ldb (byte 6 6) bits))
1602              (sap-ref-8 sap (+ 2 tail)) (logior #x80 (ldb (byte 6 0) bits))))
1603     (4 (setf (sap-ref-8 sap tail) (logior #xf0 (ldb (byte 3 18) bits))
1604              (sap-ref-8 sap (1+ tail)) (logior #x80 (ldb (byte 6 12) bits))
1605              (sap-ref-8 sap (+ 2 tail)) (logior #x80 (ldb (byte 6 6) bits))
1606              (sap-ref-8 sap (+ 3 tail)) (logior #x80 (ldb (byte 6 0) bits)))))
1607   (cond ((< byte #x80) 1)
1608         ((< byte #xc2) (return-from decode-break-reason 1))
1609         ((< byte #xe0) 2)
1610         ((< byte #xf0) 3)
1611         (t 4))
1612   (code-char (ecase size
1613                (1 byte)
1614                (2 (let ((byte2 (sap-ref-8 sap (1+ head))))
1615                     (unless (<= #x80 byte2 #xbf)
1616                       (return-from decode-break-reason 2))
1617                     (dpb byte (byte 5 6) byte2)))
1618                (3 (let ((byte2 (sap-ref-8 sap (1+ head)))
1619                         (byte3 (sap-ref-8 sap (+ 2 head))))
1620                     (unless (and (<= #x80 byte2 #xbf)
1621                                  (<= #x80 byte3 #xbf))
1622                       (return-from decode-break-reason 3))
1623                     (dpb byte (byte 4 12) (dpb byte2 (byte 6 6) byte3))))
1624                (4 (let ((byte2 (sap-ref-8 sap (1+ head)))
1625                         (byte3 (sap-ref-8 sap (+ 2 head)))
1626                         (byte4 (sap-ref-8 sap (+ 3 head))))
1627                     (unless (and (<= #x80 byte2 #xbf)
1628                                  (<= #x80 byte3 #xbf)
1629                                  (<= #x80 byte4 #xbf))
1630                       (return-from decode-break-reason 4))
1631                     (dpb byte (byte 3 18)
1632                          (dpb byte2 (byte 6 12)
1633                               (dpb byte3 (byte 6 6) byte4))))))))
1634 \f
1635 ;;;; utility functions (misc routines, etc)
1636
1637 ;;; Fill in the various routine slots for the given type. INPUT-P and
1638 ;;; OUTPUT-P indicate what slots to fill. The buffering slot must be
1639 ;;; set prior to calling this routine.
1640 (defun set-fd-stream-routines (fd-stream element-type external-format
1641                                input-p output-p buffer-p)
1642   (let* ((target-type (case element-type
1643                         (unsigned-byte '(unsigned-byte 8))
1644                         (signed-byte '(signed-byte 8))
1645                         (:default 'character)
1646                         (t element-type)))
1647          (character-stream-p (subtypep target-type 'character))
1648          (bivalent-stream-p (eq element-type :default))
1649          normalized-external-format
1650          (bin-routine #'ill-bin)
1651          (bin-type nil)
1652          (bin-size nil)
1653          (cin-routine #'ill-in)
1654          (cin-type nil)
1655          (cin-size nil)
1656          (input-type nil)           ;calculated from bin-type/cin-type
1657          (input-size nil)           ;calculated from bin-size/cin-size
1658          (read-n-characters #'ill-in)
1659          (bout-routine #'ill-bout)
1660          (bout-type nil)
1661          (bout-size nil)
1662          (cout-routine #'ill-out)
1663          (cout-type nil)
1664          (cout-size nil)
1665          (output-type nil)
1666          (output-size nil)
1667          (output-bytes #'ill-bout))
1668
1669     ;; drop buffers when direction changes
1670     (when (and (fd-stream-obuf-sap fd-stream) (not output-p))
1671       (with-available-buffers-lock ()
1672         (push (fd-stream-obuf-sap fd-stream) *available-buffers*)
1673         (setf (fd-stream-obuf-sap fd-stream) nil)))
1674     (when (and (fd-stream-ibuf-sap fd-stream) (not input-p))
1675       (with-available-buffers-lock ()
1676         (push (fd-stream-ibuf-sap fd-stream) *available-buffers*)
1677         (setf (fd-stream-ibuf-sap fd-stream) nil)))
1678     (when input-p
1679       (setf (fd-stream-ibuf-sap fd-stream) (next-available-buffer))
1680       (setf (fd-stream-ibuf-length fd-stream) bytes-per-buffer)
1681       (setf (fd-stream-ibuf-tail fd-stream) 0))
1682     (when output-p
1683       (setf (fd-stream-obuf-sap fd-stream) (next-available-buffer))
1684       (setf (fd-stream-obuf-length fd-stream) bytes-per-buffer)
1685       (setf (fd-stream-obuf-tail fd-stream) 0)
1686       (setf (fd-stream-char-pos fd-stream) 0))
1687
1688     (when (and character-stream-p
1689                (eq external-format :default))
1690       (/show0 "/getting default external format")
1691       (setf external-format (default-external-format)))
1692
1693     (when input-p
1694       (when (or (not character-stream-p) bivalent-stream-p)
1695         (multiple-value-setq (bin-routine bin-type bin-size read-n-characters
1696                                           normalized-external-format)
1697           (pick-input-routine (if bivalent-stream-p '(unsigned-byte 8)
1698                                   target-type)
1699                               external-format))
1700         (unless bin-routine
1701           (error "could not find any input routine for ~S" target-type)))
1702       (when character-stream-p
1703         (multiple-value-setq (cin-routine cin-type cin-size read-n-characters
1704                                           normalized-external-format)
1705           (pick-input-routine target-type external-format))
1706         (unless cin-routine
1707           (error "could not find any input routine for ~S" target-type)))
1708       (setf (fd-stream-in fd-stream) cin-routine
1709             (fd-stream-bin fd-stream) bin-routine)
1710       ;; character type gets preferential treatment
1711       (setf input-size (or cin-size bin-size))
1712       (setf input-type (or cin-type bin-type))
1713       (when normalized-external-format
1714         (setf (fd-stream-external-format fd-stream)
1715               normalized-external-format))
1716       (when (= (or cin-size 1) (or bin-size 1) 1)
1717         (setf (fd-stream-n-bin fd-stream) ;XXX
1718               (if (and character-stream-p (not bivalent-stream-p))
1719                   read-n-characters
1720                   #'fd-stream-read-n-bytes))
1721         ;; Sometimes turn on fast-read-char/fast-read-byte.  Switch on
1722         ;; for character and (unsigned-byte 8) streams.  In these
1723         ;; cases, fast-read-* will read from the
1724         ;; ansi-stream-(c)in-buffer, saving function calls.
1725         ;; Otherwise, the various data-reading functions in the stream
1726         ;; structure will be called.
1727         (when (and buffer-p
1728                    (not bivalent-stream-p)
1729                    ;; temporary disable on :io streams
1730                    (not output-p))
1731           (cond (character-stream-p
1732                  (setf (ansi-stream-cin-buffer fd-stream)
1733                        (make-array +ansi-stream-in-buffer-length+
1734                                    :element-type 'character)))
1735                 ((equal target-type '(unsigned-byte 8))
1736                  (setf (ansi-stream-in-buffer fd-stream)
1737                        (make-array +ansi-stream-in-buffer-length+
1738                                    :element-type '(unsigned-byte 8))))))))
1739
1740     (when output-p
1741       (when (or (not character-stream-p) bivalent-stream-p)
1742         (multiple-value-setq (bout-routine bout-type bout-size output-bytes
1743                                            normalized-external-format)
1744           (pick-output-routine (if bivalent-stream-p
1745                                    '(unsigned-byte 8)
1746                                    target-type)
1747                                (fd-stream-buffering fd-stream)
1748                                external-format))
1749         (unless bout-routine
1750           (error "could not find any output routine for ~S buffered ~S"
1751                  (fd-stream-buffering fd-stream)
1752                  target-type)))
1753       (when character-stream-p
1754         (multiple-value-setq (cout-routine cout-type cout-size output-bytes
1755                                            normalized-external-format)
1756           (pick-output-routine target-type
1757                                (fd-stream-buffering fd-stream)
1758                                external-format))
1759         (unless cout-routine
1760           (error "could not find any output routine for ~S buffered ~S"
1761                  (fd-stream-buffering fd-stream)
1762                  target-type)))
1763       (when normalized-external-format
1764         (setf (fd-stream-external-format fd-stream)
1765               normalized-external-format))
1766       (when character-stream-p
1767         (setf (fd-stream-output-bytes fd-stream) output-bytes))
1768       (setf (fd-stream-out fd-stream) cout-routine
1769             (fd-stream-bout fd-stream) bout-routine
1770             (fd-stream-sout fd-stream) (if (eql cout-size 1)
1771                                            #'fd-sout #'ill-out))
1772       (setf output-size (or cout-size bout-size))
1773       (setf output-type (or cout-type bout-type)))
1774
1775     (when (and input-size output-size
1776                (not (eq input-size output-size)))
1777       (error "Element sizes for input (~S:~S) and output (~S:~S) differ?"
1778              input-type input-size
1779              output-type output-size))
1780     (setf (fd-stream-element-size fd-stream)
1781           (or input-size output-size))
1782
1783     (setf (fd-stream-element-type fd-stream)
1784           (cond ((equal input-type output-type)
1785                  input-type)
1786                 ((null output-type)
1787                  input-type)
1788                 ((null input-type)
1789                  output-type)
1790                 ((subtypep input-type output-type)
1791                  input-type)
1792                 ((subtypep output-type input-type)
1793                  output-type)
1794                 (t
1795                  (error "Input type (~S) and output type (~S) are unrelated?"
1796                         input-type
1797                         output-type))))))
1798
1799 ;;; Handle miscellaneous operations on FD-STREAM.
1800 (defun fd-stream-misc-routine (fd-stream operation &optional arg1 arg2)
1801   (declare (ignore arg2))
1802   (case operation
1803     (:listen
1804      (labels ((do-listen ()
1805                 (or (not (eql (fd-stream-ibuf-head fd-stream)
1806                               (fd-stream-ibuf-tail fd-stream)))
1807                     (fd-stream-listen fd-stream)
1808                     #!+win32
1809                     (sb!win32:fd-listen (fd-stream-fd fd-stream))
1810                     #!-win32
1811                     ;; If the read can block, LISTEN will certainly return NIL.
1812                     (if (sysread-may-block-p fd-stream)
1813                         nil
1814                         ;; Otherwise select(2) and CL:LISTEN have slightly
1815                         ;; different semantics.  The former returns that an FD
1816                         ;; is readable when a read operation wouldn't block.
1817                         ;; That includes EOF.  However, LISTEN must return NIL
1818                         ;; at EOF.
1819                         (progn (catch 'eof-input-catcher
1820                                  ;; r-b/f too calls select, but it shouldn't
1821                                  ;; block as long as read can return once w/o
1822                                  ;; blocking
1823                                  (refill-buffer/fd fd-stream))
1824                                ;; At this point either IBUF-HEAD != IBUF-TAIL
1825                                ;; and FD-STREAM-LISTEN is NIL, in which case
1826                                ;; we should return T, or IBUF-HEAD ==
1827                                ;; IBUF-TAIL and FD-STREAM-LISTEN is :EOF, in
1828                                ;; which case we should return :EOF for this
1829                                ;; call and all future LISTEN call on this stream.
1830                                ;; Call ourselves again to determine which case
1831                                ;; applies.
1832                                (do-listen))))))
1833        (do-listen)))
1834     (:unread
1835      (setf (fd-stream-unread fd-stream) arg1)
1836      (setf (fd-stream-listen fd-stream) t))
1837     (:close
1838      (cond (arg1                    ; We got us an abort on our hands.
1839             (when (fd-stream-handler fd-stream)
1840               (remove-fd-handler (fd-stream-handler fd-stream))
1841               (setf (fd-stream-handler fd-stream) nil))
1842             ;; We can't do anything unless we know what file were
1843             ;; dealing with, and we don't want to do anything
1844             ;; strange unless we were writing to the file.
1845             (when (and (fd-stream-file fd-stream)
1846                        (fd-stream-obuf-sap fd-stream))
1847               (if (fd-stream-original fd-stream)
1848                   ;; If the original is EQ to file we are appending
1849                   ;; and can just close the file without renaming.
1850                   (unless (eq (fd-stream-original fd-stream)
1851                               (fd-stream-file fd-stream))
1852                     ;; We have a handle on the original, just revert.
1853                     (multiple-value-bind (okay err)
1854                         (sb!unix:unix-rename (fd-stream-original fd-stream)
1855                                              (fd-stream-file fd-stream))
1856                       (unless okay
1857                         (simple-stream-perror
1858                          "couldn't restore ~S to its original contents"
1859                          fd-stream
1860                          err))))
1861                   ;; We can't restore the original, and aren't
1862                   ;; appending, so nuke that puppy.
1863                   ;;
1864                   ;; FIXME: This is currently the fate of superseded
1865                   ;; files, and according to the CLOSE spec this is
1866                   ;; wrong. However, there seems to be no clean way to
1867                   ;; do that that doesn't involve either copying the
1868                   ;; data (bad if the :abort resulted from a full
1869                   ;; disk), or renaming the old file temporarily
1870                   ;; (probably bad because stream opening becomes more
1871                   ;; racy).
1872                   (multiple-value-bind (okay err)
1873                       (sb!unix:unix-unlink (fd-stream-file fd-stream))
1874                     (unless okay
1875                       (error 'simple-file-error
1876                              :pathname (fd-stream-file fd-stream)
1877                              :format-control
1878                              "~@<couldn't remove ~S: ~2I~_~A~:>"
1879                              :format-arguments (list (fd-stream-file fd-stream)
1880                                                      (strerror err))))))))
1881            (t
1882             (fd-stream-misc-routine fd-stream :finish-output)
1883             (when (and (fd-stream-original fd-stream)
1884                        (fd-stream-delete-original fd-stream))
1885               (multiple-value-bind (okay err)
1886                   (sb!unix:unix-unlink (fd-stream-original fd-stream))
1887                 (unless okay
1888                   (error 'simple-file-error
1889                          :pathname (fd-stream-original fd-stream)
1890                          :format-control
1891                          "~@<couldn't delete ~S during close of ~S: ~
1892                           ~2I~_~A~:>"
1893                          :format-arguments
1894                          (list (fd-stream-original fd-stream)
1895                                fd-stream
1896                                (strerror err))))))))
1897      (when (fboundp 'cancel-finalization)
1898        (cancel-finalization fd-stream))
1899      (sb!unix:unix-close (fd-stream-fd fd-stream))
1900      (when (fd-stream-obuf-sap fd-stream)
1901        (with-available-buffers-lock ()
1902          (push (fd-stream-obuf-sap fd-stream) *available-buffers*)
1903          (setf (fd-stream-obuf-sap fd-stream) nil)))
1904      (when (fd-stream-ibuf-sap fd-stream)
1905        (with-available-buffers-lock ()
1906          (push (fd-stream-ibuf-sap fd-stream) *available-buffers*)
1907          (setf (fd-stream-ibuf-sap fd-stream) nil)))
1908      (sb!impl::set-closed-flame fd-stream))
1909     (:clear-input
1910      (setf (fd-stream-unread fd-stream) nil)
1911      (setf (fd-stream-ibuf-head fd-stream) 0)
1912      (setf (fd-stream-ibuf-tail fd-stream) 0)
1913      #!+win32
1914      (progn
1915        (sb!win32:fd-clear-input (fd-stream-fd fd-stream))
1916        (setf (fd-stream-listen fd-stream) nil))
1917      #!-win32
1918      (catch 'eof-input-catcher
1919        (loop until (sysread-may-block-p fd-stream)
1920              do
1921              (refill-buffer/fd fd-stream)
1922              (setf (fd-stream-ibuf-head fd-stream) 0)
1923              (setf (fd-stream-ibuf-tail fd-stream) 0))
1924        t))
1925     (:force-output
1926      (flush-output-buffer fd-stream))
1927     (:finish-output
1928      (finish-fd-stream-output fd-stream))
1929     (:element-type
1930      (fd-stream-element-type fd-stream))
1931     (:external-format
1932      (fd-stream-external-format fd-stream))
1933     (:interactive-p
1934      (= 1 (the (member 0 1)
1935             (sb!unix:unix-isatty (fd-stream-fd fd-stream)))))
1936     (:line-length
1937      80)
1938     (:charpos
1939      (fd-stream-char-pos fd-stream))
1940     (:file-length
1941      (unless (fd-stream-file fd-stream)
1942        ;; This is a TYPE-ERROR because ANSI's species FILE-LENGTH
1943        ;; "should signal an error of type TYPE-ERROR if stream is not
1944        ;; a stream associated with a file". Too bad there's no very
1945        ;; appropriate value for the EXPECTED-TYPE slot..
1946        (error 'simple-type-error
1947               :datum fd-stream
1948               :expected-type 'fd-stream
1949               :format-control "~S is not a stream associated with a file."
1950               :format-arguments (list fd-stream)))
1951      (multiple-value-bind (okay dev ino mode nlink uid gid rdev size
1952                                 atime mtime ctime blksize blocks)
1953          (sb!unix:unix-fstat (fd-stream-fd fd-stream))
1954        (declare (ignore ino nlink uid gid rdev
1955                         atime mtime ctime blksize blocks))
1956        (unless okay
1957          (simple-stream-perror "failed Unix fstat(2) on ~S" fd-stream dev))
1958        (if (zerop mode)
1959            nil
1960            (truncate size (fd-stream-element-size fd-stream)))))
1961     (:file-string-length
1962      (etypecase arg1
1963        (character (fd-stream-character-size fd-stream arg1))
1964        (string (fd-stream-string-size fd-stream arg1))))
1965     (:file-position
1966      (if arg1
1967          (fd-stream-set-file-position fd-stream arg1)
1968          (fd-stream-get-file-position fd-stream)))))
1969
1970 ;; FIXME: Think about this.
1971 ;;
1972 ;; (defun finish-fd-stream-output (fd-stream)
1973 ;;   (let ((timeout (fd-stream-timeout fd-stream)))
1974 ;;     (loop while (fd-stream-output-later fd-stream)
1975 ;;        ;; FIXME: SIGINT while waiting for a timeout will
1976 ;;        ;; cause a timeout here.
1977 ;;        do (when (and (not (serve-event timeout)) timeout)
1978 ;;             (signal-timeout 'io-timeout
1979 ;;                             :stream fd-stream
1980 ;;                             :direction :write
1981 ;;                             :seconds timeout)))))
1982
1983 (defun finish-fd-stream-output (stream)
1984   (flush-output-buffer stream)
1985   (do ()
1986       ((null (fd-stream-output-later stream)))
1987     (serve-all-events)))
1988
1989 (defun fd-stream-get-file-position (stream)
1990   (declare (fd-stream stream))
1991   (without-interrupts
1992     (let ((posn (sb!unix:unix-lseek (fd-stream-fd stream) 0 sb!unix:l_incr)))
1993       (declare (type (or (alien sb!unix:off-t) null) posn))
1994       ;; We used to return NIL for errno==ESPIPE, and signal an error
1995       ;; in other failure cases. However, CLHS says to return NIL if
1996       ;; the position cannot be determined -- so that's what we do.
1997       (when (integerp posn)
1998         ;; Adjust for buffered output: If there is any output
1999         ;; buffered, the *real* file position will be larger
2000         ;; than reported by lseek() because lseek() obviously
2001         ;; cannot take into account output we have not sent
2002         ;; yet.
2003         (dolist (later (fd-stream-output-later stream))
2004           (incf posn (- (caddr later) (cadr later))))
2005         (incf posn (fd-stream-obuf-tail stream))
2006         ;; Adjust for unread input: If there is any input
2007         ;; read from UNIX but not supplied to the user of the
2008         ;; stream, the *real* file position will smaller than
2009         ;; reported, because we want to look like the unread
2010         ;; stuff is still available.
2011         (decf posn (- (fd-stream-ibuf-tail stream)
2012                       (fd-stream-ibuf-head stream)))
2013         (when (fd-stream-unread stream)
2014           (decf posn))
2015         ;; Divide bytes by element size.
2016         (truncate posn (fd-stream-element-size stream))))))
2017
2018 (defun fd-stream-set-file-position (stream position-spec)
2019   (declare (fd-stream stream))
2020   (check-type position-spec
2021               (or (alien sb!unix:off-t) (member nil :start :end))
2022               "valid file position designator")
2023   (tagbody
2024    :again
2025      ;; Make sure we don't have any output pending, because if we
2026      ;; move the file pointer before writing this stuff, it will be
2027      ;; written in the wrong location.
2028      (finish-fd-stream-output stream)
2029      ;; Disable interrupts so that interrupt handlers doing output
2030      ;; won't screw us.
2031      (without-interrupts
2032        (unless (fd-stream-output-finished-p stream)
2033          ;; We got interrupted and more output came our way during
2034          ;; the interrupt. Wrapping the FINISH-FD-STREAM-OUTPUT in
2035          ;; WITHOUT-INTERRUPTS gets nasty as it can signal errors,
2036          ;; so we prefer to do things like this...
2037          (go :again))
2038        ;; Clear out any pending input to force the next read to go to
2039        ;; the disk.
2040        (setf (fd-stream-unread stream) nil
2041              (fd-stream-ibuf-head stream) 0
2042              (fd-stream-ibuf-tail stream) 0)
2043        ;; Trash cached value for listen, so that we check next time.
2044        (setf (fd-stream-listen stream) nil)
2045          ;; Now move it.
2046          (multiple-value-bind (offset origin)
2047              (case position-spec
2048            (:start
2049             (values 0 sb!unix:l_set))
2050            (:end
2051             (values 0 sb!unix:l_xtnd))
2052            (t
2053             (values (* position-spec (fd-stream-element-size stream))
2054                     sb!unix:l_set)))
2055            (declare (type (alien sb!unix:off-t) offset))
2056            (let ((posn (sb!unix:unix-lseek (fd-stream-fd stream)
2057                                            offset origin)))
2058              ;; CLHS says to return true if the file-position was set
2059              ;; succesfully, and NIL otherwise. We are to signal an error
2060              ;; only if the given position was out of bounds, and that is
2061              ;; dealt with above. In times past we used to return NIL for
2062              ;; errno==ESPIPE, and signal an error in other cases.
2063              ;;
2064              ;; FIXME: We are still liable to signal an error if flushing
2065              ;; output fails.
2066              (return-from fd-stream-set-file-position
2067                (typep posn '(alien sb!unix:off-t))))))))
2068
2069 \f
2070 ;;;; creation routines (MAKE-FD-STREAM and OPEN)
2071
2072 ;;; Create a stream for the given Unix file descriptor.
2073 ;;;
2074 ;;; If INPUT is non-NIL, allow input operations. If OUTPUT is non-nil,
2075 ;;; allow output operations. If neither INPUT nor OUTPUT is specified,
2076 ;;; default to allowing input.
2077 ;;;
2078 ;;; ELEMENT-TYPE indicates the element type to use (as for OPEN).
2079 ;;;
2080 ;;; BUFFERING indicates the kind of buffering to use.
2081 ;;;
2082 ;;; TIMEOUT (if true) is the number of seconds to wait for input. If
2083 ;;; NIL (the default), then wait forever. When we time out, we signal
2084 ;;; IO-TIMEOUT.
2085 ;;;
2086 ;;; FILE is the name of the file (will be returned by PATHNAME).
2087 ;;;
2088 ;;; NAME is used to identify the stream when printed.
2089 (defun make-fd-stream (fd
2090                        &key
2091                        (input nil input-p)
2092                        (output nil output-p)
2093                        (element-type 'base-char)
2094                        (buffering :full)
2095                        (external-format :default)
2096                        timeout
2097                        file
2098                        original
2099                        delete-original
2100                        pathname
2101                        input-buffer-p
2102                        dual-channel-p
2103                        (name (if file
2104                                  (format nil "file ~A" file)
2105                                  (format nil "descriptor ~W" fd)))
2106                        auto-close)
2107   (declare (type index fd) (type (or real null) timeout)
2108            (type (member :none :line :full) buffering))
2109   (cond ((not (or input-p output-p))
2110          (setf input t))
2111         ((not (or input output))
2112          (error "File descriptor must be opened either for input or output.")))
2113   (let ((stream (%make-fd-stream :fd fd
2114                                  :name name
2115                                  :file file
2116                                  :original original
2117                                  :delete-original delete-original
2118                                  :pathname pathname
2119                                  :buffering buffering
2120                                  :dual-channel-p dual-channel-p
2121                                  :external-format external-format
2122                                  :timeout
2123                                  (if timeout
2124                                      (coerce timeout 'single-float)
2125                                      nil))))
2126     (set-fd-stream-routines stream element-type external-format
2127                             input output input-buffer-p)
2128     (when (and auto-close (fboundp 'finalize))
2129       (finalize stream
2130                 (lambda ()
2131                   (sb!unix:unix-close fd)
2132                   #!+sb-show
2133                   (format *terminal-io* "** closed file descriptor ~W **~%"
2134                           fd))))
2135     stream))
2136
2137 ;;; Pick a name to use for the backup file for the :IF-EXISTS
2138 ;;; :RENAME-AND-DELETE and :RENAME options.
2139 (defun pick-backup-name (name)
2140   (declare (type simple-string name))
2141   (concatenate 'simple-string name ".bak"))
2142
2143 ;;; Ensure that the given arg is one of the given list of valid
2144 ;;; things. Allow the user to fix any problems.
2145 (defun ensure-one-of (item list what)
2146   (unless (member item list)
2147     (error 'simple-type-error
2148            :datum item
2149            :expected-type `(member ,@list)
2150            :format-control "~@<~S is ~_invalid for ~S; ~_need one of~{ ~S~}~:>"
2151            :format-arguments (list item what list))))
2152
2153 ;;; Rename NAMESTRING to ORIGINAL. First, check whether we have write
2154 ;;; access, since we don't want to trash unwritable files even if we
2155 ;;; technically can. We return true if we succeed in renaming.
2156 (defun rename-the-old-one (namestring original)
2157   (unless (sb!unix:unix-access namestring sb!unix:w_ok)
2158     (error "~@<The file ~2I~_~S ~I~_is not writable.~:>" namestring))
2159   (multiple-value-bind (okay err) (sb!unix:unix-rename namestring original)
2160     (if okay
2161         t
2162         (error 'simple-file-error
2163                :pathname namestring
2164                :format-control
2165                "~@<couldn't rename ~2I~_~S ~I~_to ~2I~_~S: ~4I~_~A~:>"
2166                :format-arguments (list namestring original (strerror err))))))
2167
2168 (defun open (filename
2169              &key
2170              (direction :input)
2171              (element-type 'base-char)
2172              (if-exists nil if-exists-given)
2173              (if-does-not-exist nil if-does-not-exist-given)
2174              (external-format :default)
2175              &aux ; Squelch assignment warning.
2176              (direction direction)
2177              (if-does-not-exist if-does-not-exist)
2178              (if-exists if-exists))
2179   #!+sb-doc
2180   "Return a stream which reads from or writes to FILENAME.
2181   Defined keywords:
2182    :DIRECTION - one of :INPUT, :OUTPUT, :IO, or :PROBE
2183    :ELEMENT-TYPE - the type of object to read or write, default BASE-CHAR
2184    :IF-EXISTS - one of :ERROR, :NEW-VERSION, :RENAME, :RENAME-AND-DELETE,
2185                        :OVERWRITE, :APPEND, :SUPERSEDE or NIL
2186    :IF-DOES-NOT-EXIST - one of :ERROR, :CREATE or NIL
2187   See the manual for details."
2188
2189   ;; Calculate useful stuff.
2190   (multiple-value-bind (input output mask)
2191       (case direction
2192         (:input  (values   t nil sb!unix:o_rdonly))
2193         (:output (values nil   t sb!unix:o_wronly))
2194         (:io     (values   t   t sb!unix:o_rdwr))
2195         (:probe  (values   t nil sb!unix:o_rdonly)))
2196     (declare (type index mask))
2197     (let* ((pathname (merge-pathnames filename))
2198            (namestring
2199             (cond ((unix-namestring pathname input))
2200                   ((and input (eq if-does-not-exist :create))
2201                    (unix-namestring pathname nil))
2202                   ((and (eq direction :io) (not if-does-not-exist-given))
2203                    (unix-namestring pathname nil)))))
2204       ;; Process if-exists argument if we are doing any output.
2205       (cond (output
2206              (unless if-exists-given
2207                (setf if-exists
2208                      (if (eq (pathname-version pathname) :newest)
2209                          :new-version
2210                          :error)))
2211              (ensure-one-of if-exists
2212                             '(:error :new-version :rename
2213                                      :rename-and-delete :overwrite
2214                                      :append :supersede nil)
2215                             :if-exists)
2216              (case if-exists
2217                ((:new-version :error nil)
2218                 (setf mask (logior mask sb!unix:o_excl)))
2219                ((:rename :rename-and-delete)
2220                 (setf mask (logior mask sb!unix:o_creat)))
2221                ((:supersede)
2222                 (setf mask (logior mask sb!unix:o_trunc)))
2223                (:append
2224                 (setf mask (logior mask sb!unix:o_append)))))
2225             (t
2226              (setf if-exists :ignore-this-arg)))
2227
2228       (unless if-does-not-exist-given
2229         (setf if-does-not-exist
2230               (cond ((eq direction :input) :error)
2231                     ((and output
2232                           (member if-exists '(:overwrite :append)))
2233                      :error)
2234                     ((eq direction :probe)
2235                      nil)
2236                     (t
2237                      :create))))
2238       (ensure-one-of if-does-not-exist
2239                      '(:error :create nil)
2240                      :if-does-not-exist)
2241       (if (eq if-does-not-exist :create)
2242         (setf mask (logior mask sb!unix:o_creat)))
2243
2244       (let ((original (case if-exists
2245                         ((:rename :rename-and-delete)
2246                          (pick-backup-name namestring))
2247                         ((:append :overwrite)
2248                          ;; KLUDGE: Provent CLOSE from deleting
2249                          ;; appending streams when called with :ABORT T
2250                          namestring)))
2251             (delete-original (eq if-exists :rename-and-delete))
2252             (mode #o666))
2253         (when (and original (not (eq original namestring)))
2254           ;; We are doing a :RENAME or :RENAME-AND-DELETE. Determine
2255           ;; whether the file already exists, make sure the original
2256           ;; file is not a directory, and keep the mode.
2257           (let ((exists
2258                  (and namestring
2259                       (multiple-value-bind (okay err/dev inode orig-mode)
2260                           (sb!unix:unix-stat namestring)
2261                         (declare (ignore inode)
2262                                  (type (or index null) orig-mode))
2263                         (cond
2264                          (okay
2265                           (when (and output (= (logand orig-mode #o170000)
2266                                                #o40000))
2267                             (error 'simple-file-error
2268                                    :pathname namestring
2269                                    :format-control
2270                                    "can't open ~S for output: is a directory"
2271                                    :format-arguments (list namestring)))
2272                           (setf mode (logand orig-mode #o777))
2273                           t)
2274                          ((eql err/dev sb!unix:enoent)
2275                           nil)
2276                          (t
2277                           (simple-file-perror "can't find ~S"
2278                                               namestring
2279                                               err/dev)))))))
2280             (unless (and exists
2281                          (rename-the-old-one namestring original))
2282               (setf original nil)
2283               (setf delete-original nil)
2284               ;; In order to use :SUPERSEDE instead, we have to make
2285               ;; sure SB!UNIX:O_CREAT corresponds to
2286               ;; IF-DOES-NOT-EXIST. SB!UNIX:O_CREAT was set before
2287               ;; because of IF-EXISTS being :RENAME.
2288               (unless (eq if-does-not-exist :create)
2289                 (setf mask
2290                       (logior (logandc2 mask sb!unix:o_creat)
2291                               sb!unix:o_trunc)))
2292               (setf if-exists :supersede))))
2293
2294         ;; Now we can try the actual Unix open(2).
2295         (multiple-value-bind (fd errno)
2296             (if namestring
2297                 (sb!unix:unix-open namestring mask mode)
2298                 (values nil sb!unix:enoent))
2299           (labels ((open-error (format-control &rest format-arguments)
2300                      (error 'simple-file-error
2301                             :pathname pathname
2302                             :format-control format-control
2303                             :format-arguments format-arguments))
2304                    (vanilla-open-error ()
2305                      (simple-file-perror "error opening ~S" pathname errno)))
2306             (cond ((numberp fd)
2307                    (case direction
2308                      ((:input :output :io)
2309                       (make-fd-stream fd
2310                                       :input input
2311                                       :output output
2312                                       :element-type element-type
2313                                       :external-format external-format
2314                                       :file namestring
2315                                       :original original
2316                                       :delete-original delete-original
2317                                       :pathname pathname
2318                                       :dual-channel-p nil
2319                                       :input-buffer-p t
2320                                       :auto-close t))
2321                      (:probe
2322                       (let ((stream
2323                              (%make-fd-stream :name namestring
2324                                               :fd fd
2325                                               :pathname pathname
2326                                               :element-type element-type)))
2327                         (close stream)
2328                         stream))))
2329                   ((eql errno sb!unix:enoent)
2330                    (case if-does-not-exist
2331                      (:error (vanilla-open-error))
2332                      (:create
2333                       (open-error "~@<The path ~2I~_~S ~I~_does not exist.~:>"
2334                                   pathname))
2335                      (t nil)))
2336                   ((and (eql errno sb!unix:eexist) (null if-exists))
2337                    nil)
2338                   (t
2339                    (vanilla-open-error)))))))))
2340 \f
2341 ;;;; initialization
2342
2343 ;;; the stream connected to the controlling terminal, or NIL if there is none
2344 (defvar *tty*)
2345
2346 ;;; the stream connected to the standard input (file descriptor 0)
2347 (defvar *stdin*)
2348
2349 ;;; the stream connected to the standard output (file descriptor 1)
2350 (defvar *stdout*)
2351
2352 ;;; the stream connected to the standard error output (file descriptor 2)
2353 (defvar *stderr*)
2354
2355 ;;; This is called when the cold load is first started up, and may also
2356 ;;; be called in an attempt to recover from nested errors.
2357 (defun stream-cold-init-or-reset ()
2358   (stream-reinit)
2359   (setf *terminal-io* (make-synonym-stream '*tty*))
2360   (setf *standard-output* (make-synonym-stream '*stdout*))
2361   (setf *standard-input* (make-synonym-stream '*stdin*))
2362   (setf *error-output* (make-synonym-stream '*stderr*))
2363   (setf *query-io* (make-synonym-stream '*terminal-io*))
2364   (setf *debug-io* *query-io*)
2365   (setf *trace-output* *standard-output*)
2366   (values))
2367
2368 ;;; This is called whenever a saved core is restarted.
2369 (defun stream-reinit ()
2370   (setf *available-buffers* nil)
2371   (with-output-to-string (*error-output*)
2372     (setf *stdin*
2373           (make-fd-stream 0 :name "standard input" :input t :buffering :line
2374                             #!+win32 :external-format #!+win32 (sb!win32::console-input-codepage)))
2375     (setf *stdout*
2376           (make-fd-stream 1 :name "standard output" :output t :buffering :line
2377                             #!+win32 :external-format #!+win32 (sb!win32::console-output-codepage)))
2378     (setf *stderr*
2379           (make-fd-stream 2 :name "standard error" :output t :buffering :line
2380                             #!+win32 :external-format #!+win32 (sb!win32::console-output-codepage)))
2381     (let* ((ttyname #.(coerce "/dev/tty" 'simple-base-string))
2382            (tty (sb!unix:unix-open ttyname sb!unix:o_rdwr #o666)))
2383       (if tty
2384           (setf *tty*
2385                 (make-fd-stream tty
2386                                 :name "the terminal"
2387                                 :input t
2388                                 :output t
2389                                 :buffering :line
2390                                 :auto-close t))
2391           (setf *tty* (make-two-way-stream *stdin* *stdout*))))
2392     (princ (get-output-stream-string *error-output*) *stderr*))
2393   (values))
2394 \f
2395 ;;;; miscellany
2396
2397 ;;; the Unix way to beep
2398 (defun beep (stream)
2399   (write-char (code-char bell-char-code) stream)
2400   (finish-output stream))
2401
2402 ;;; This is kind of like FILE-POSITION, but is an internal hack used
2403 ;;; by the filesys stuff to get and set the file name.
2404 ;;;
2405 ;;; FIXME: misleading name, screwy interface
2406 (defun file-name (stream &optional new-name)
2407   (when (typep stream 'fd-stream)
2408       (cond (new-name
2409              (setf (fd-stream-pathname stream) new-name)
2410              (setf (fd-stream-file stream)
2411                    (unix-namestring new-name nil))
2412              t)
2413             (t
2414              (fd-stream-pathname stream)))))