1 ;;;; streams for UNIX file descriptors
3 ;;;; This software is part of the SBCL system. See the README file for
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.
12 (in-package "SB!IMPL")
14 ;;;; buffer manipulation routines
16 ;;; FIXME: Is it really good to maintain this pool separate from the
17 ;;; GC and the C malloc logic?
18 (defvar *available-buffers* ()
20 "List of available buffers. Each buffer is an sap pointing to
21 bytes-per-buffer of memory.")
24 (defvar *available-buffers-mutex* (sb!thread:make-mutex
25 :name "lock for *AVAILABLE-BUFFERS*")
27 "Mutex for access to *AVAILABLE-BUFFERS*.")
29 (defmacro with-available-buffers-lock ((&optional) &body body)
30 ;; WITHOUT-INTERRUPTS because streams are low-level enough to be
31 ;; async signal safe, and in particular a C-c that brings up the
32 ;; debugger while holding the mutex would lose badly
34 (sb!thread:with-mutex (*available-buffers-mutex*)
37 (defconstant bytes-per-buffer (* 4 1024)
39 "Number of bytes per buffer.")
41 ;;; Return the next available buffer, creating one if necessary.
42 #!-sb-fluid (declaim (inline next-available-buffer))
43 (defun next-available-buffer ()
44 (with-available-buffers-lock ()
45 (if *available-buffers*
46 (pop *available-buffers*)
47 (allocate-system-memory bytes-per-buffer))))
49 ;;;; the FD-STREAM structure
52 (:constructor %make-fd-stream)
53 (:conc-name fd-stream-)
54 (:predicate fd-stream-p)
56 (misc #'fd-stream-misc-routine))
59 ;; the name of this stream
61 ;; the file this stream is for
63 ;; the backup file namestring for the old file, for :IF-EXISTS
64 ;; :RENAME or :RENAME-AND-DELETE.
65 (original nil :type (or simple-string null))
66 (delete-original nil) ; for :if-exists :rename-and-delete
67 ;;; the number of bytes per element
68 (element-size 1 :type index)
69 ;; the type of element being transfered
70 (element-type 'base-char)
71 ;; the Unix file descriptor
73 ;; controls when the output buffer is flushed
74 (buffering :full :type (member :full :line :none))
75 ;; controls whether the input buffer must be cleared before output
76 ;; (must be done for files, not for sockets, pipes and other data
77 ;; sources where input and output aren't related). non-NIL means
78 ;; don't clear input buffer.
80 ;; character position (if known)
81 (char-pos nil :type (or index null))
82 ;; T if input is waiting on FD. :EOF if we hit EOF.
83 (listen nil :type (member nil t :eof))
87 (ibuf-sap nil :type (or system-area-pointer null))
88 (ibuf-length nil :type (or index null))
89 (ibuf-head 0 :type index)
90 (ibuf-tail 0 :type index)
93 (obuf-sap nil :type (or system-area-pointer null))
94 (obuf-length nil :type (or index null))
95 (obuf-tail 0 :type index)
97 ;; output flushed, but not written due to non-blocking io?
100 ;; timeout specified for this stream, or NIL if none
101 (timeout nil :type (or index null))
102 ;; pathname of the file this stream is opened to (returned by PATHNAME)
103 (pathname nil :type (or pathname null))
104 (external-format :default)
105 (output-bytes #'ill-out :type function))
106 (def!method print-object ((fd-stream fd-stream) stream)
107 (declare (type stream stream))
108 (print-unreadable-object (fd-stream stream :type t :identity t)
109 (format stream "for ~S" (fd-stream-name fd-stream))))
111 ;;;; output routines and related noise
113 (defvar *output-routines* ()
115 "List of all available output routines. Each element is a list of the
116 element-type output, the kind of buffering, the function name, and the number
117 of bytes per element.")
119 ;;; common idioms for reporting low-level stream and file problems
120 (defun simple-stream-perror (note-format stream errno)
121 (error 'simple-stream-error
123 :format-control "~@<~?: ~2I~_~A~:>"
124 :format-arguments (list note-format (list stream) (strerror errno))))
125 (defun simple-file-perror (note-format pathname errno)
126 (error 'simple-file-error
128 :format-control "~@<~?: ~2I~_~A~:>"
130 (list note-format (list pathname) (strerror errno))))
132 (defun stream-decoding-error (stream octets)
133 (error 'stream-decoding-error
135 ;; FIXME: dunno how to get at OCTETS currently, or even if
136 ;; that's the right thing to report.
138 (defun stream-encoding-error (stream code)
139 (error 'stream-encoding-error
143 ;;; Returning true goes into end of file handling, false will enter another
144 ;;; round of input buffer filling followed by re-entering character decode.
145 (defun stream-decoding-error-and-handle (stream octet-count)
147 (stream-decoding-error stream
148 (let ((sap (fd-stream-ibuf-sap stream))
149 (head (fd-stream-ibuf-head stream)))
150 (loop for i from 0 below octet-count
151 collect (sap-ref-8 sap (+ head i)))))
153 :report (lambda (stream)
155 "~@<Attempt to resync the stream at a character ~
156 character boundary and continue.~@:>"))
157 (fd-stream-resync stream)
159 (force-end-of-file ()
160 :report (lambda (stream)
161 (format stream "~@<Force an end of file.~@:>"))
164 (defun stream-encoding-error-and-handle (stream code)
166 (stream-encoding-error stream code)
168 :report (lambda (stream)
169 (format stream "~@<Skip output of this character.~@:>"))
170 (throw 'output-nothing nil))))
172 ;;; This is called by the server when we can write to the given file
173 ;;; descriptor. Attempt to write the data again. If it worked, remove
174 ;;; the data from the OUTPUT-LATER list. If it didn't work, something
176 (defun frob-output-later (stream)
177 (let* ((stuff (pop (fd-stream-output-later stream)))
181 (reuse-sap (cadddr stuff))
182 (length (- end start)))
183 (declare (type index start end length))
184 (multiple-value-bind (count errno)
185 (sb!unix:unix-write (fd-stream-fd stream)
190 (if (= errno sb!unix:ewouldblock)
191 (error "Write would have blocked, but SERVER told us to go.")
192 (simple-stream-perror "couldn't write to ~S" stream errno)))
193 ((eql count length) ; Hot damn, it worked.
195 (with-available-buffers-lock ()
196 (push base *available-buffers*))))
197 ((not (null count)) ; sorta worked..
199 (the index (+ start count))
201 (fd-stream-output-later stream))))))
202 (unless (fd-stream-output-later stream)
203 (sb!sys:remove-fd-handler (fd-stream-handler stream))
204 (setf (fd-stream-handler stream) nil)))
206 ;;; Arange to output the string when we can write on the file descriptor.
207 (defun output-later (stream base start end reuse-sap)
208 (cond ((null (fd-stream-output-later stream))
209 (setf (fd-stream-output-later stream)
210 (list (list base start end reuse-sap)))
211 (setf (fd-stream-handler stream)
212 (sb!sys:add-fd-handler (fd-stream-fd stream)
215 (declare (ignore fd))
216 (frob-output-later stream)))))
218 (nconc (fd-stream-output-later stream)
219 (list (list base start end reuse-sap)))))
221 (let ((new-buffer (next-available-buffer)))
222 (setf (fd-stream-obuf-sap stream) new-buffer)
223 (setf (fd-stream-obuf-length stream) bytes-per-buffer))))
225 ;;; Output the given noise. Check to see whether there are any pending
226 ;;; writes. If so, just queue this one. Otherwise, try to write it. If
227 ;;; this would block, queue it.
228 (defun frob-output (stream base start end reuse-sap)
229 (declare (type fd-stream stream)
230 (type (or system-area-pointer (simple-array * (*))) base)
231 (type index start end))
232 (if (not (null (fd-stream-output-later stream))) ; something buffered.
234 (output-later stream base start end reuse-sap)
235 ;; ### check to see whether any of this noise can be output
237 (let ((length (- end start)))
238 (multiple-value-bind (count errno)
239 (sb!unix:unix-write (fd-stream-fd stream) base start length)
241 (if (= errno sb!unix:ewouldblock)
242 (output-later stream base start end reuse-sap)
243 (simple-stream-perror "couldn't write to ~S"
246 ((not (eql count length))
247 (output-later stream base (the index (+ start count))
250 ;;; Flush any data in the output buffer.
251 (defun flush-output-buffer (stream)
252 (let ((length (fd-stream-obuf-tail stream)))
254 (frob-output stream (fd-stream-obuf-sap stream) 0 length t)
255 (setf (fd-stream-obuf-tail stream) 0))))
257 (defmacro output-wrapper/variable-width ((stream size buffering restart)
259 (let ((stream-var (gensym)))
260 `(let ((,stream-var ,stream)
262 ,(unless (eq (car buffering) :none)
263 `(when (< (fd-stream-obuf-length ,stream-var)
264 (+ (fd-stream-obuf-tail ,stream-var)
266 (flush-output-buffer ,stream-var)))
267 ,(unless (eq (car buffering) :none)
268 `(when (and (not (fd-stream-dual-channel-p ,stream-var))
269 (> (fd-stream-ibuf-tail ,stream-var)
270 (fd-stream-ibuf-head ,stream-var)))
271 (file-position ,stream-var (file-position ,stream-var))))
273 `(catch 'output-nothing
275 (incf (fd-stream-obuf-tail ,stream-var) size))
278 (incf (fd-stream-obuf-tail ,stream-var) size)))
279 ,(ecase (car buffering)
281 `(flush-output-buffer ,stream-var))
283 `(when (eq (char-code byte) (char-code #\Newline))
284 (flush-output-buffer ,stream-var)))
288 (defmacro output-wrapper ((stream size buffering restart) &body body)
289 (let ((stream-var (gensym)))
290 `(let ((,stream-var ,stream))
291 ,(unless (eq (car buffering) :none)
292 `(when (< (fd-stream-obuf-length ,stream-var)
293 (+ (fd-stream-obuf-tail ,stream-var)
295 (flush-output-buffer ,stream-var)))
296 ,(unless (eq (car buffering) :none)
297 `(when (and (not (fd-stream-dual-channel-p ,stream-var))
298 (> (fd-stream-ibuf-tail ,stream-var)
299 (fd-stream-ibuf-head ,stream-var)))
300 (file-position ,stream-var (file-position ,stream-var))))
302 `(catch 'output-nothing
304 (incf (fd-stream-obuf-tail ,stream-var) ,size))
307 (incf (fd-stream-obuf-tail ,stream-var) ,size)))
308 ,(ecase (car buffering)
310 `(flush-output-buffer ,stream-var))
312 `(when (eq (char-code byte) (char-code #\Newline))
313 (flush-output-buffer ,stream-var)))
317 (defmacro def-output-routines/variable-width
318 ((name-fmt size restart external-format &rest bufferings)
320 (declare (optimize (speed 1)))
325 (intern (format nil name-fmt (string (car buffering))))))
327 (defun ,function (stream byte)
328 (output-wrapper/variable-width (stream ,size ,buffering ,restart)
330 (setf *output-routines*
331 (nconc *output-routines*
339 (cdr buffering)))))))
342 ;;; Define output routines that output numbers SIZE bytes long for the
343 ;;; given bufferings. Use BODY to do the actual output.
344 (defmacro def-output-routines ((name-fmt size restart &rest bufferings)
346 (declare (optimize (speed 1)))
351 (intern (format nil name-fmt (string (car buffering))))))
353 (defun ,function (stream byte)
354 (output-wrapper (stream ,size ,buffering ,restart)
356 (setf *output-routines*
357 (nconc *output-routines*
365 (cdr buffering)))))))
368 ;;; FIXME: is this used anywhere any more?
369 (def-output-routines ("OUTPUT-CHAR-~A-BUFFERED"
375 (if (char= byte #\Newline)
376 (setf (fd-stream-char-pos stream) 0)
377 (incf (fd-stream-char-pos stream)))
378 (setf (sap-ref-8 (fd-stream-obuf-sap stream) (fd-stream-obuf-tail stream))
381 (def-output-routines ("OUTPUT-UNSIGNED-BYTE-~A-BUFFERED"
384 (:none (unsigned-byte 8))
385 (:full (unsigned-byte 8)))
386 (setf (sap-ref-8 (fd-stream-obuf-sap stream) (fd-stream-obuf-tail stream))
389 (def-output-routines ("OUTPUT-SIGNED-BYTE-~A-BUFFERED"
392 (:none (signed-byte 8))
393 (:full (signed-byte 8)))
394 (setf (signed-sap-ref-8 (fd-stream-obuf-sap stream)
395 (fd-stream-obuf-tail stream))
398 (def-output-routines ("OUTPUT-UNSIGNED-SHORT-~A-BUFFERED"
401 (:none (unsigned-byte 16))
402 (:full (unsigned-byte 16)))
403 (setf (sap-ref-16 (fd-stream-obuf-sap stream) (fd-stream-obuf-tail stream))
406 (def-output-routines ("OUTPUT-SIGNED-SHORT-~A-BUFFERED"
409 (:none (signed-byte 16))
410 (:full (signed-byte 16)))
411 (setf (signed-sap-ref-16 (fd-stream-obuf-sap stream)
412 (fd-stream-obuf-tail stream))
415 (def-output-routines ("OUTPUT-UNSIGNED-LONG-~A-BUFFERED"
418 (:none (unsigned-byte 32))
419 (:full (unsigned-byte 32)))
420 (setf (sap-ref-32 (fd-stream-obuf-sap stream) (fd-stream-obuf-tail stream))
423 (def-output-routines ("OUTPUT-SIGNED-LONG-~A-BUFFERED"
426 (:none (signed-byte 32))
427 (:full (signed-byte 32)))
428 (setf (signed-sap-ref-32 (fd-stream-obuf-sap stream)
429 (fd-stream-obuf-tail stream))
432 ;;; Do the actual output. If there is space to buffer the string,
433 ;;; buffer it. If the string would normally fit in the buffer, but
434 ;;; doesn't because of other stuff in the buffer, flush the old noise
435 ;;; out of the buffer and put the string in it. Otherwise we have a
436 ;;; very long string, so just send it directly (after flushing the
437 ;;; buffer, of course).
438 (defun output-raw-bytes (fd-stream thing &optional start end)
440 "Output THING to FD-STREAM. THING can be any kind of vector or a SAP. If
441 THING is a SAP, END must be supplied (as length won't work)."
442 (let ((start (or start 0))
443 (end (or end (length (the (simple-array * (*)) thing)))))
444 (declare (type index start end))
445 (when (and (not (fd-stream-dual-channel-p fd-stream))
446 (> (fd-stream-ibuf-tail fd-stream)
447 (fd-stream-ibuf-head fd-stream)))
448 (file-position fd-stream (file-position fd-stream)))
449 (let* ((len (fd-stream-obuf-length fd-stream))
450 (tail (fd-stream-obuf-tail fd-stream))
452 (bytes (- end start))
453 (newtail (+ tail bytes)))
454 (cond ((minusp bytes) ; error case
455 (error ":END before :START!"))
456 ((zerop bytes)) ; easy case
458 (if (system-area-pointer-p thing)
459 (system-area-ub8-copy thing start
460 (fd-stream-obuf-sap fd-stream)
463 ;; FIXME: There should be some type checking somewhere to
464 ;; verify that THING here is a vector, not just <not a SAP>.
465 (copy-ub8-to-system-area thing start
466 (fd-stream-obuf-sap fd-stream)
469 (setf (fd-stream-obuf-tail fd-stream) newtail))
471 (flush-output-buffer fd-stream)
472 (if (system-area-pointer-p thing)
473 (system-area-ub8-copy thing
475 (fd-stream-obuf-sap fd-stream)
478 ;; FIXME: There should be some type checking somewhere to
479 ;; verify that THING here is a vector, not just <not a SAP>.
480 (copy-ub8-to-system-area thing
482 (fd-stream-obuf-sap fd-stream)
485 (setf (fd-stream-obuf-tail fd-stream) bytes))
487 (flush-output-buffer fd-stream)
488 (frob-output fd-stream thing start end nil))))))
490 ;;; the routine to use to output a string. If the stream is
491 ;;; unbuffered, slam the string down the file descriptor, otherwise
492 ;;; use OUTPUT-RAW-BYTES to buffer the string. Update charpos by
493 ;;; checking to see where the last newline was.
495 ;;; Note: some bozos (the FASL dumper) call write-string with things
496 ;;; other than strings. Therefore, we must make sure we have a string
497 ;;; before calling POSITION on it.
498 ;;; KLUDGE: It would be better to fix the bozos instead of trying to
499 ;;; cover for them here. -- WHN 20000203
500 (defun fd-sout (stream thing start end)
501 (let ((start (or start 0))
502 (end (or end (length (the vector thing)))))
503 (declare (fixnum start end))
505 (let ((last-newline (and (find #\newline (the simple-string thing)
506 :start start :end end)
507 ;; FIXME why do we need both calls?
508 ;; Is find faster forwards than
509 ;; position is backwards?
510 (position #\newline (the simple-string thing)
514 (if (and (typep thing 'base-string)
515 (eq (fd-stream-external-format stream) :latin-1))
516 (ecase (fd-stream-buffering stream)
518 (output-raw-bytes stream thing start end))
520 (output-raw-bytes stream thing start end)
522 (flush-output-buffer stream)))
524 (frob-output stream thing start end nil)))
525 (ecase (fd-stream-buffering stream)
526 (:full (funcall (fd-stream-output-bytes stream)
527 stream thing nil start end))
528 (:line (funcall (fd-stream-output-bytes stream)
529 stream thing last-newline start end))
530 (:none (funcall (fd-stream-output-bytes stream)
531 stream thing t start end))))
533 (setf (fd-stream-char-pos stream)
534 (- end last-newline 1))
535 (incf (fd-stream-char-pos stream)
537 (ecase (fd-stream-buffering stream)
539 (output-raw-bytes stream thing start end))
541 (frob-output stream thing start end nil))))))
543 (defvar *external-formats* ()
545 "List of all available external formats. Each element is a list of the
546 element-type, string input function name, character input function name,
547 and string output function name.")
549 ;;; Find an output routine to use given the type and buffering. Return
550 ;;; as multiple values the routine, the real type transfered, and the
551 ;;; number of bytes per element.
552 (defun pick-output-routine (type buffering &optional external-format)
553 (when (subtypep type 'character)
554 (dolist (entry *external-formats*)
555 (when (member external-format (first entry))
556 (return-from pick-output-routine
557 (values (symbol-function (nth (ecase buffering
564 (symbol-function (fourth entry))
565 (first (first entry)))))))
566 (dolist (entry *output-routines*)
567 (when (and (subtypep type (first entry))
568 (eq buffering (second entry))
569 (or (not (fifth entry))
570 (eq external-format (fifth entry))))
571 (return-from pick-output-routine
572 (values (symbol-function (third entry))
575 ;; KLUDGE: dealing with the buffering here leads to excessive code
578 ;; KLUDGE: also see comments in PICK-INPUT-ROUTINE
579 (loop for i from 40 by 8 to 1024 ; ARB (KLUDGE)
580 if (subtypep type `(unsigned-byte ,i))
581 do (return-from pick-output-routine
585 (lambda (stream byte)
586 (output-wrapper (stream (/ i 8) (:none) nil)
587 (loop for j from 0 below (/ i 8)
589 (fd-stream-obuf-sap stream)
590 (+ j (fd-stream-obuf-tail stream)))
591 (ldb (byte 8 (- i 8 (* j 8))) byte))))))
593 (lambda (stream byte)
594 (output-wrapper (stream (/ i 8) (:full) nil)
595 (loop for j from 0 below (/ i 8)
597 (fd-stream-obuf-sap stream)
598 (+ j (fd-stream-obuf-tail stream)))
599 (ldb (byte 8 (- i 8 (* j 8))) byte)))))))
602 (loop for i from 40 by 8 to 1024 ; ARB (KLUDGE)
603 if (subtypep type `(signed-byte ,i))
604 do (return-from pick-output-routine
608 (lambda (stream byte)
609 (output-wrapper (stream (/ i 8) (:none) nil)
610 (loop for j from 0 below (/ i 8)
612 (fd-stream-obuf-sap stream)
613 (+ j (fd-stream-obuf-tail stream)))
614 (ldb (byte 8 (- i 8 (* j 8))) byte))))))
616 (lambda (stream byte)
617 (output-wrapper (stream (/ i 8) (:full) nil)
618 (loop for j from 0 below (/ i 8)
620 (fd-stream-obuf-sap stream)
621 (+ j (fd-stream-obuf-tail stream)))
622 (ldb (byte 8 (- i 8 (* j 8))) byte)))))))
626 ;;;; input routines and related noise
628 ;;; a list of all available input routines. Each element is a list of
629 ;;; the element-type input, the function name, and the number of bytes
631 (defvar *input-routines* ())
633 ;;; Fill the input buffer, and return the number of bytes read. Throw
634 ;;; to EOF-INPUT-CATCHER if the eof was reached. Drop into
635 ;;; SYSTEM:SERVER if necessary.
636 (defun refill-buffer/fd (stream)
637 (let ((fd (fd-stream-fd stream))
638 (ibuf-sap (fd-stream-ibuf-sap stream))
639 (buflen (fd-stream-ibuf-length stream))
640 (head (fd-stream-ibuf-head stream))
641 (tail (fd-stream-ibuf-tail stream)))
642 (declare (type index head tail))
644 (cond ((eql head tail)
647 (setf (fd-stream-ibuf-head stream) 0)
648 (setf (fd-stream-ibuf-tail stream) 0))
651 (system-area-ub8-copy ibuf-sap head
654 (setf (fd-stream-ibuf-head stream) 0)
655 (setf (fd-stream-ibuf-tail stream) tail))))
656 (setf (fd-stream-listen stream) nil)
657 (sb!unix:with-restarted-syscall (count errno)
658 ;; FIXME: Judging from compiler warnings, this WITH-ALIEN form expands
659 ;; into something which uses the not-yet-defined type
660 ;; (SB!ALIEN-INTERNALS:ALIEN (* (SB!ALIEN:STRUCT SB!UNIX:FD-SET))).
661 ;; This is probably inefficient and unsafe and generally bad, so
662 ;; try to find some way to make that type known before
664 (sb!alien:with-alien ((read-fds (sb!alien:struct sb!unix:fd-set)))
665 (sb!unix:fd-zero read-fds)
666 (sb!unix:fd-set fd read-fds)
667 (sb!unix:unix-fast-select (1+ fd)
668 (sb!alien:addr read-fds)
673 (unless (sb!sys:wait-until-fd-usable
674 fd :input (fd-stream-timeout stream))
675 (error 'io-timeout :stream stream :direction :read)))
677 (simple-stream-perror "couldn't check whether ~S is readable"
680 (multiple-value-bind (count errno)
681 (sb!unix:unix-read fd
682 (sb!sys:int-sap (+ (sb!sys:sap-int ibuf-sap) tail))
685 (if (eql errno sb!unix:ewouldblock)
687 (unless (sb!sys:wait-until-fd-usable
688 fd :input (fd-stream-timeout stream))
689 (error 'io-timeout :stream stream :direction :read))
690 (refill-buffer/fd stream))
691 (simple-stream-perror "couldn't read from ~S" stream errno)))
693 (setf (fd-stream-listen stream) :eof)
694 (/show0 "THROWing EOF-INPUT-CATCHER")
695 (throw 'eof-input-catcher nil))
697 (incf (fd-stream-ibuf-tail stream) count)
700 ;;; Make sure there are at least BYTES number of bytes in the input
701 ;;; buffer. Keep calling REFILL-BUFFER/FD until that condition is met.
702 (defmacro input-at-least (stream bytes)
703 (let ((stream-var (gensym))
704 (bytes-var (gensym)))
705 `(let ((,stream-var ,stream)
708 (when (>= (- (fd-stream-ibuf-tail ,stream-var)
709 (fd-stream-ibuf-head ,stream-var))
712 (refill-buffer/fd ,stream-var)))))
714 (defmacro input-wrapper/variable-width ((stream bytes eof-error eof-value)
716 (let ((stream-var (gensym))
718 (element-var (gensym)))
719 `(let ((,stream-var ,stream)
721 (if (fd-stream-unread ,stream-var)
723 (fd-stream-unread ,stream-var)
724 (setf (fd-stream-unread ,stream-var) nil)
725 (setf (fd-stream-listen ,stream-var) nil))
726 (let ((,element-var nil)
727 (decode-break-reason nil))
731 (catch 'eof-input-catcher
732 (setf decode-break-reason
733 (block decode-break-reason
734 (input-at-least ,stream-var 1)
735 (let* ((byte (sap-ref-8 (fd-stream-ibuf-sap
740 (input-at-least ,stream-var size)
741 (setq ,element-var (locally ,@read-forms))
742 (setq ,retry-var nil))
744 (when decode-break-reason
745 (stream-decoding-error-and-handle stream
746 decode-break-reason))
748 (let ((octet-count (- (fd-stream-ibuf-tail ,stream-var)
749 (fd-stream-ibuf-head ,stream-var))))
750 (when (or (zerop octet-count)
751 (and (not ,element-var)
752 (not decode-break-reason)
753 (stream-decoding-error-and-handle
754 stream octet-count)))
755 (setq ,retry-var nil)))))
757 (incf (fd-stream-ibuf-head ,stream-var) size)
760 (eof-or-lose ,stream-var ,eof-error ,eof-value))))))))
762 ;;; a macro to wrap around all input routines to handle EOF-ERROR noise
763 (defmacro input-wrapper ((stream bytes eof-error eof-value) &body read-forms)
764 (let ((stream-var (gensym))
765 (element-var (gensym)))
766 `(let ((,stream-var ,stream))
767 (if (fd-stream-unread ,stream-var)
769 (fd-stream-unread ,stream-var)
770 (setf (fd-stream-unread ,stream-var) nil)
771 (setf (fd-stream-listen ,stream-var) nil))
773 (catch 'eof-input-catcher
774 (input-at-least ,stream-var ,bytes)
775 (locally ,@read-forms))))
777 (incf (fd-stream-ibuf-head ,stream-var) ,bytes)
780 (eof-or-lose ,stream-var ,eof-error ,eof-value))))))))
782 (defmacro def-input-routine/variable-width (name
783 (type external-format size sap head)
786 (defun ,name (stream eof-error eof-value)
787 (input-wrapper/variable-width (stream ,size eof-error eof-value)
788 (let ((,sap (fd-stream-ibuf-sap stream))
789 (,head (fd-stream-ibuf-head stream)))
791 (setf *input-routines*
792 (nconc *input-routines*
793 (list (list ',type ',name 1 ',external-format))))))
795 (defmacro def-input-routine (name
799 (defun ,name (stream eof-error eof-value)
800 (input-wrapper (stream ,size eof-error eof-value)
801 (let ((,sap (fd-stream-ibuf-sap stream))
802 (,head (fd-stream-ibuf-head stream)))
804 (setf *input-routines*
805 (nconc *input-routines*
806 (list (list ',type ',name ',size nil))))))
808 ;;; STREAM-IN routine for reading a string char
809 (def-input-routine input-character
810 (character 1 sap head)
811 (code-char (sap-ref-8 sap head)))
813 ;;; STREAM-IN routine for reading an unsigned 8 bit number
814 (def-input-routine input-unsigned-8bit-byte
815 ((unsigned-byte 8) 1 sap head)
816 (sap-ref-8 sap head))
818 ;;; STREAM-IN routine for reading a signed 8 bit number
819 (def-input-routine input-signed-8bit-number
820 ((signed-byte 8) 1 sap head)
821 (signed-sap-ref-8 sap head))
823 ;;; STREAM-IN routine for reading an unsigned 16 bit number
824 (def-input-routine input-unsigned-16bit-byte
825 ((unsigned-byte 16) 2 sap head)
826 (sap-ref-16 sap head))
828 ;;; STREAM-IN routine for reading a signed 16 bit number
829 (def-input-routine input-signed-16bit-byte
830 ((signed-byte 16) 2 sap head)
831 (signed-sap-ref-16 sap head))
833 ;;; STREAM-IN routine for reading a unsigned 32 bit number
834 (def-input-routine input-unsigned-32bit-byte
835 ((unsigned-byte 32) 4 sap head)
836 (sap-ref-32 sap head))
838 ;;; STREAM-IN routine for reading a signed 32 bit number
839 (def-input-routine input-signed-32bit-byte
840 ((signed-byte 32) 4 sap head)
841 (signed-sap-ref-32 sap head))
845 ;;; Find an input routine to use given the type. Return as multiple
846 ;;; values the routine, the real type transfered, and the number of
847 ;;; bytes per element (and for character types string input routine).
848 (defun pick-input-routine (type &optional external-format)
849 (when (subtypep type 'character)
850 (dolist (entry *external-formats*)
851 (when (member external-format (first entry))
852 (return-from pick-input-routine
853 (values (symbol-function (third entry))
856 (symbol-function (second entry))
857 (first (first entry)))))))
858 (dolist (entry *input-routines*)
859 (when (and (subtypep type (first entry))
860 (or (not (fourth entry))
861 (eq external-format (fourth entry))))
862 (return-from pick-input-routine
863 (values (symbol-function (second entry))
866 ;; FIXME: let's do it the hard way, then (but ignore things like
867 ;; endianness, efficiency, and the necessary coupling between these
868 ;; and the output routines). -- CSR, 2004-02-09
869 (loop for i from 40 by 8 to 1024 ; ARB (well, KLUDGE really)
870 if (subtypep type `(unsigned-byte ,i))
871 do (return-from pick-input-routine
873 (lambda (stream eof-error eof-value)
874 (input-wrapper (stream (/ i 8) eof-error eof-value)
875 (let ((sap (fd-stream-ibuf-sap stream))
876 (head (fd-stream-ibuf-head stream)))
877 (loop for j from 0 below (/ i 8)
881 (sap-ref-8 sap (+ head j))))
882 finally (return result)))))
885 (loop for i from 40 by 8 to 1024 ; ARB (well, KLUDGE really)
886 if (subtypep type `(signed-byte ,i))
887 do (return-from pick-input-routine
889 (lambda (stream eof-error eof-value)
890 (input-wrapper (stream (/ i 8) eof-error eof-value)
891 (let ((sap (fd-stream-ibuf-sap stream))
892 (head (fd-stream-ibuf-head stream)))
893 (loop for j from 0 below (/ i 8)
897 (sap-ref-8 sap (+ head j))))
898 finally (return (if (logbitp (1- i) result)
899 (dpb result (byte i 0) -1)
904 ;;; Return a string constructed from SAP, START, and END.
905 (defun string-from-sap (sap start end)
906 (declare (type index start end))
907 (let* ((length (- end start))
908 (string (make-string length)))
909 (copy-ub8-from-system-area sap start
914 ;;; the N-BIN method for FD-STREAMs
916 ;;; Note that this blocks in UNIX-READ. It is generally used where
917 ;;; there is a definite amount of reading to be done, so blocking
918 ;;; isn't too problematical.
919 (defun fd-stream-read-n-bytes (stream buffer start requested eof-error-p
920 &aux (total-copied 0))
921 (declare (type fd-stream stream))
922 (declare (type index start requested total-copied))
923 (let ((unread (fd-stream-unread stream)))
925 ;; AVERs designed to fail when we have more complicated
926 ;; character representations.
927 (aver (typep unread 'base-char))
928 (aver (= (fd-stream-element-size stream) 1))
929 ;; KLUDGE: this is a slightly-unrolled-and-inlined version of
933 (setf (sap-ref-8 buffer start) (char-code unread)))
934 ((simple-unboxed-array (*))
935 (setf (aref buffer start) unread)))
936 (setf (fd-stream-unread stream) nil)
937 (setf (fd-stream-listen stream) nil)
938 (incf total-copied)))
941 (let* ((remaining-request (- requested total-copied))
942 (head (fd-stream-ibuf-head stream))
943 (tail (fd-stream-ibuf-tail stream))
944 (available (- tail head))
945 (n-this-copy (min remaining-request available))
946 (this-start (+ start total-copied))
947 (this-end (+ this-start n-this-copy))
948 (sap (fd-stream-ibuf-sap stream)))
949 (declare (type index remaining-request head tail available))
950 (declare (type index n-this-copy))
951 ;; Copy data from stream buffer into user's buffer.
952 (%byte-blt sap head buffer this-start this-end)
953 (incf (fd-stream-ibuf-head stream) n-this-copy)
954 (incf total-copied n-this-copy)
955 ;; Maybe we need to refill the stream buffer.
956 (cond (;; If there were enough data in the stream buffer, we're done.
957 (= total-copied requested)
958 (return total-copied))
959 (;; If EOF, we're done in another way.
960 (null (catch 'eof-input-catcher (refill-buffer/fd stream)))
962 (error 'end-of-file :stream stream)
963 (return total-copied)))
964 ;; Otherwise we refilled the stream buffer, so fall
965 ;; through into another pass of the loop.
968 (defun fd-stream-resync (stream)
969 (dolist (entry *external-formats*)
970 (when (member (fd-stream-external-format stream) (first entry))
971 (return-from fd-stream-resync
972 (funcall (symbol-function (eighth entry)) stream)))))
974 ;;; FIXME: OAOOM here vrt. *EXTERNAL-FORMAT-FUNCTIONS* in fd-stream.lisp
975 (defmacro define-external-format (external-format size output-restart
977 (let* ((name (first external-format))
978 (out-function (symbolicate "OUTPUT-BYTES/" name))
979 (format (format nil "OUTPUT-CHAR-~A-~~A-BUFFERED" (string name)))
980 (in-function (symbolicate "FD-STREAM-READ-N-CHARACTERS/" name))
981 (in-char-function (symbolicate "INPUT-CHAR/" name)))
983 (defun ,out-function (stream string flush-p start end)
984 (let ((start (or start 0))
985 (end (or end (length string))))
986 (declare (type index start end))
987 (when (and (not (fd-stream-dual-channel-p stream))
988 (> (fd-stream-ibuf-tail stream)
989 (fd-stream-ibuf-head stream)))
990 (file-position stream (file-position stream)))
992 (error ":END before :START!"))
995 (setf (fd-stream-obuf-tail stream)
996 (do* ((len (fd-stream-obuf-length stream))
997 (sap (fd-stream-obuf-sap stream))
998 (tail (fd-stream-obuf-tail stream)))
999 ((or (= start end) (< (- len tail) 4)) tail)
1001 `(catch 'output-nothing
1002 (let* ((byte (aref string start))
1003 (bits (char-code byte)))
1006 `(let* ((byte (aref string start))
1007 (bits (char-code byte)))
1012 (flush-output-buffer stream)))
1014 (flush-output-buffer stream))))
1015 (def-output-routines (,format
1021 (if (char= byte #\Newline)
1022 (setf (fd-stream-char-pos stream) 0)
1023 (incf (fd-stream-char-pos stream)))
1024 (let ((bits (char-code byte))
1025 (sap (fd-stream-obuf-sap stream))
1026 (tail (fd-stream-obuf-tail stream)))
1028 (defun ,in-function (stream buffer start requested eof-error-p
1029 &aux (total-copied 0))
1030 (declare (type fd-stream stream))
1031 (declare (type index start requested total-copied))
1032 (declare (type (simple-array character (#.+ansi-stream-in-buffer-length+)) buffer))
1033 (let ((unread (fd-stream-unread stream)))
1035 (setf (aref buffer start) unread)
1036 (setf (fd-stream-unread stream) nil)
1037 (setf (fd-stream-listen stream) nil)
1038 (incf total-copied)))
1041 (let* ((head (fd-stream-ibuf-head stream))
1042 (tail (fd-stream-ibuf-tail stream))
1043 (sap (fd-stream-ibuf-sap stream)))
1044 (declare (type index head tail))
1045 ;; Copy data from stream buffer into user's buffer.
1047 ((or (= tail head) (= requested total-copied)))
1048 (let* ((byte (sap-ref-8 sap head)))
1049 (when (> ,size (- tail head))
1051 (setf (aref buffer (+ start total-copied)) ,in-expr)
1054 (setf (fd-stream-ibuf-head stream) head)
1055 ;; Maybe we need to refill the stream buffer.
1056 (cond ( ;; If there were enough data in the stream buffer, we're done.
1057 (= total-copied requested)
1058 (return total-copied))
1059 ( ;; If EOF, we're done in another way.
1060 (null (catch 'eof-input-catcher (refill-buffer/fd stream)))
1062 (error 'end-of-file :stream stream)
1063 (return total-copied)))
1064 ;; Otherwise we refilled the stream buffer, so fall
1065 ;; through into another pass of the loop.
1067 (def-input-routine ,in-char-function (character ,size sap head)
1068 (let ((byte (sap-ref-8 sap head)))
1070 (setf *external-formats*
1071 (cons '(,external-format ,in-function ,in-char-function ,out-function
1072 ,@(mapcar #'(lambda (buffering)
1073 (intern (format nil format (string buffering))))
1074 '(:none :line :full)))
1075 *external-formats*)))))
1077 (defmacro define-external-format/variable-width
1078 (external-format output-restart out-size-expr
1079 out-expr in-size-expr in-expr)
1080 (let* ((name (first external-format))
1081 (out-function (symbolicate "OUTPUT-BYTES/" name))
1082 (format (format nil "OUTPUT-CHAR-~A-~~A-BUFFERED" (string name)))
1083 (in-function (symbolicate "FD-STREAM-READ-N-CHARACTERS/" name))
1084 (in-char-function (symbolicate "INPUT-CHAR/" name))
1085 (resync-function (symbolicate "RESYNC/" name)))
1087 (defun ,out-function (stream string flush-p start end)
1088 (let ((start (or start 0))
1089 (end (or end (length string))))
1090 (declare (type index start end))
1091 (when (and (not (fd-stream-dual-channel-p stream))
1092 (> (fd-stream-ibuf-tail stream)
1093 (fd-stream-ibuf-head stream)))
1094 (file-position stream (file-position stream)))
1096 (error ":END before :START!"))
1099 (setf (fd-stream-obuf-tail stream)
1100 (do* ((len (fd-stream-obuf-length stream))
1101 (sap (fd-stream-obuf-sap stream))
1102 (tail (fd-stream-obuf-tail stream)))
1103 ((or (= start end) (< (- len tail) 4)) tail)
1105 `(catch 'output-nothing
1106 (let* ((byte (aref string start))
1107 (bits (char-code byte))
1108 (size ,out-size-expr))
1111 `(let* ((byte (aref string start))
1112 (bits (char-code byte))
1113 (size ,out-size-expr))
1118 (flush-output-buffer stream)))
1120 (flush-output-buffer stream))))
1121 (def-output-routines/variable-width (,format
1128 (if (char= byte #\Newline)
1129 (setf (fd-stream-char-pos stream) 0)
1130 (incf (fd-stream-char-pos stream)))
1131 (let ((bits (char-code byte))
1132 (sap (fd-stream-obuf-sap stream))
1133 (tail (fd-stream-obuf-tail stream)))
1135 (defun ,in-function (stream buffer start requested eof-error-p
1136 &aux (total-copied 0))
1137 (declare (type fd-stream stream))
1138 (declare (type index start requested total-copied))
1139 (declare (type (simple-array character (#.+ansi-stream-in-buffer-length+)) buffer))
1140 (let ((unread (fd-stream-unread stream)))
1142 (setf (aref buffer start) unread)
1143 (setf (fd-stream-unread stream) nil)
1144 (setf (fd-stream-listen stream) nil)
1145 (incf total-copied)))
1148 (let* ((head (fd-stream-ibuf-head stream))
1149 (tail (fd-stream-ibuf-tail stream))
1150 (sap (fd-stream-ibuf-sap stream))
1152 (decode-break-reason nil))
1153 (declare (type index head tail))
1154 ;; Copy data from stream buffer into user's buffer.
1155 (do ((size nil nil))
1156 ((or (= tail head) (= requested total-copied)))
1157 (setf decode-break-reason
1158 (block decode-break-reason
1159 (let ((byte (sap-ref-8 sap head)))
1160 (setq size ,in-size-expr)
1161 (when (> size (- tail head))
1163 (setf (aref buffer (+ start total-copied)) ,in-expr)
1167 (setf (fd-stream-ibuf-head stream) head)
1168 (when (and decode-break-reason
1169 (= head head-start))
1170 (when (stream-decoding-error-and-handle
1171 stream decode-break-reason)
1173 (error 'end-of-file :stream stream)
1174 (return-from ,in-function total-copied)))
1175 (setf head (fd-stream-ibuf-head stream))
1176 (setf tail (fd-stream-ibuf-tail stream)))
1177 (when (plusp total-copied)
1178 (return-from ,in-function total-copied)))
1179 (setf (fd-stream-ibuf-head stream) head)
1180 ;; Maybe we need to refill the stream buffer.
1181 (cond ( ;; If there were enough data in the stream buffer, we're done.
1182 (= total-copied requested)
1183 (return total-copied))
1184 ( ;; If EOF, we're done in another way.
1185 (or (eq decode-break-reason 'eof)
1186 (null (catch 'eof-input-catcher
1187 (refill-buffer/fd stream))))
1189 (error 'end-of-file :stream stream)
1190 (return total-copied)))
1191 ;; Otherwise we refilled the stream buffer, so fall
1192 ;; through into another pass of the loop.
1194 (def-input-routine/variable-width ,in-char-function (character
1198 (let ((byte (sap-ref-8 sap head)))
1200 (defun ,resync-function (stream)
1201 (loop (input-at-least stream 1)
1202 (incf (fd-stream-ibuf-head stream))
1203 (unless (block decode-break-reason
1204 (let* ((sap (fd-stream-ibuf-sap stream))
1205 (head (fd-stream-ibuf-head stream))
1206 (byte (sap-ref-8 sap head))
1207 (size ,in-size-expr))
1211 (setf *external-formats*
1212 (cons '(,external-format ,in-function ,in-char-function ,out-function
1213 ,@(mapcar #'(lambda (buffering)
1214 (intern (format nil format (string buffering))))
1215 '(:none :line :full))
1217 *external-formats*)))))
1219 ;;; Multiple names for the :ISO{,-}8859-* families are needed because on
1220 ;;; FreeBSD (and maybe other BSD systems), nl_langinfo("LATIN-1") will
1221 ;;; return "ISO8859-1" instead of "ISO-8859-1".
1222 (define-external-format (:latin-1 :latin1 :iso-8859-1 :iso8859-1)
1225 (stream-encoding-error-and-handle stream bits)
1226 (setf (sap-ref-8 sap tail) bits))
1229 (define-external-format (:ascii :us-ascii :ansi_x3.4-1968
1230 :iso-646 :iso-646-us :|646|)
1233 (stream-encoding-error-and-handle stream bits)
1234 (setf (sap-ref-8 sap tail) bits))
1237 (let* ((table (let ((s (make-string 256)))
1238 (map-into s #'code-char
1239 '(#x00 #x01 #x02 #x03 #x9c #x09 #x86 #x7f #x97 #x8d #x8e #x0b #x0c #x0d #x0e #x0f
1240 #x10 #x11 #x12 #x13 #x9d #x85 #x08 #x87 #x18 #x19 #x92 #x8f #x1c #x1d #x1e #x1f
1241 #x80 #x81 #x82 #x83 #x84 #x0a #x17 #x1b #x88 #x89 #x8a #x8b #x8c #x05 #x06 #x07
1242 #x90 #x91 #x16 #x93 #x94 #x95 #x96 #x04 #x98 #x99 #x9a #x9b #x14 #x15 #x9e #x1a
1243 #x20 #xa0 #xe2 #xe4 #xe0 #xe1 #xe3 #xe5 #xe7 #xf1 #xa2 #x2e #x3c #x28 #x2b #x7c
1244 #x26 #xe9 #xea #xeb #xe8 #xed #xee #xef #xec #xdf #x21 #x24 #x2a #x29 #x3b #xac
1245 #x2d #x2f #xc2 #xc4 #xc0 #xc1 #xc3 #xc5 #xc7 #xd1 #xa6 #x2c #x25 #x5f #x3e #x3f
1246 #xf8 #xc9 #xca #xcb #xc8 #xcd #xce #xcf #xcc #x60 #x3a #x23 #x40 #x27 #x3d #x22
1247 #xd8 #x61 #x62 #x63 #x64 #x65 #x66 #x67 #x68 #x69 #xab #xbb #xf0 #xfd #xfe #xb1
1248 #xb0 #x6a #x6b #x6c #x6d #x6e #x6f #x70 #x71 #x72 #xaa #xba #xe6 #xb8 #xc6 #xa4
1249 #xb5 #x7e #x73 #x74 #x75 #x76 #x77 #x78 #x79 #x7a #xa1 #xbf #xd0 #xdd #xde #xae
1250 #x5e #xa3 #xa5 #xb7 #xa9 #xa7 #xb6 #xbc #xbd #xbe #x5b #x5d #xaf #xa8 #xb4 #xd7
1251 #x7b #x41 #x42 #x43 #x44 #x45 #x46 #x47 #x48 #x49 #xad #xf4 #xf6 #xf2 #xf3 #xf5
1252 #x7d #x4a #x4b #x4c #x4d #x4e #x4f #x50 #x51 #x52 #xb9 #xfb #xfc #xf9 #xfa #xff
1253 #x5c #xf7 #x53 #x54 #x55 #x56 #x57 #x58 #x59 #x5a #xb2 #xd4 #xd6 #xd2 #xd3 #xd5
1254 #x30 #x31 #x32 #x33 #x34 #x35 #x36 #x37 #x38 #x39 #xb3 #xdb #xdc #xd9 #xda #x9f))
1256 (reverse-table (let ((rt (make-array 256 :element-type '(unsigned-byte 8) :initial-element 0)))
1257 (loop for char across table for i from 0
1258 do (aver (= 0 (aref rt (char-code char))))
1259 do (setf (aref rt (char-code char)) i))
1261 (define-external-format (:ebcdic-us :ibm-037 :ibm037)
1264 (stream-encoding-error-and-handle stream bits)
1265 (setf (sap-ref-8 sap tail) (aref reverse-table bits)))
1270 (let ((latin-9-table (let ((table (make-string 256)))
1273 (setf (aref table i) (code-char i)))
1274 (setf (aref table #xa4) (code-char #x20ac))
1275 (setf (aref table #xa6) (code-char #x0160))
1276 (setf (aref table #xa8) (code-char #x0161))
1277 (setf (aref table #xb4) (code-char #x017d))
1278 (setf (aref table #xb8) (code-char #x017e))
1279 (setf (aref table #xbc) (code-char #x0152))
1280 (setf (aref table #xbd) (code-char #x0153))
1281 (setf (aref table #xbe) (code-char #x0178))
1283 (latin-9-reverse-1 (make-array 16
1284 :element-type '(unsigned-byte 21)
1285 :initial-contents '(#x0160 #x0161 #x0152 #x0153 0 0 0 0 #x0178 0 0 0 #x20ac #x017d #x017e 0)))
1286 (latin-9-reverse-2 (make-array 16
1287 :element-type '(unsigned-byte 8)
1288 :initial-contents '(#xa6 #xa8 #xbc #xbd 0 0 0 0 #xbe 0 0 0 #xa4 #xb4 #xb8 0))))
1289 (define-external-format (:latin-9 :latin9 :iso-8859-15 :iso8859-15)
1291 (setf (sap-ref-8 sap tail)
1293 (if (= bits (char-code (aref latin-9-table bits)))
1295 (stream-encoding-error-and-handle stream byte))
1296 (if (= (aref latin-9-reverse-1 (logand bits 15)) bits)
1297 (aref latin-9-reverse-2 (logand bits 15))
1298 (stream-encoding-error-and-handle stream byte))))
1299 (aref latin-9-table byte)))
1301 (define-external-format/variable-width (:utf-8 :utf8) nil
1302 (let ((bits (char-code byte)))
1303 (cond ((< bits #x80) 1)
1305 ((< bits #x10000) 3)
1308 (1 (setf (sap-ref-8 sap tail) bits))
1309 (2 (setf (sap-ref-8 sap tail) (logior #xc0 (ldb (byte 5 6) bits))
1310 (sap-ref-8 sap (1+ tail)) (logior #x80 (ldb (byte 6 0) bits))))
1311 (3 (setf (sap-ref-8 sap tail) (logior #xe0 (ldb (byte 4 12) bits))
1312 (sap-ref-8 sap (1+ tail)) (logior #x80 (ldb (byte 6 6) bits))
1313 (sap-ref-8 sap (+ 2 tail)) (logior #x80 (ldb (byte 6 0) bits))))
1314 (4 (setf (sap-ref-8 sap tail) (logior #xf0 (ldb (byte 3 18) bits))
1315 (sap-ref-8 sap (1+ tail)) (logior #x80 (ldb (byte 6 12) bits))
1316 (sap-ref-8 sap (+ 2 tail)) (logior #x80 (ldb (byte 6 6) bits))
1317 (sap-ref-8 sap (+ 3 tail)) (logior #x80 (ldb (byte 6 0) bits)))))
1318 (cond ((< byte #x80) 1)
1319 ((< byte #xc2) (return-from decode-break-reason 1))
1323 (code-char (ecase size
1325 (2 (let ((byte2 (sap-ref-8 sap (1+ head))))
1326 (unless (<= #x80 byte2 #xbf)
1327 (return-from decode-break-reason 2))
1328 (dpb byte (byte 5 6) byte2)))
1329 (3 (let ((byte2 (sap-ref-8 sap (1+ head)))
1330 (byte3 (sap-ref-8 sap (+ 2 head))))
1331 (unless (and (<= #x80 byte2 #xbf)
1332 (<= #x80 byte3 #xbf))
1333 (return-from decode-break-reason 3))
1334 (dpb byte (byte 4 12) (dpb byte2 (byte 6 6) byte3))))
1335 (4 (let ((byte2 (sap-ref-8 sap (1+ head)))
1336 (byte3 (sap-ref-8 sap (+ 2 head)))
1337 (byte4 (sap-ref-8 sap (+ 3 head))))
1338 (unless (and (<= #x80 byte2 #xbf)
1339 (<= #x80 byte3 #xbf)
1340 (<= #x80 byte4 #xbf))
1341 (return-from decode-break-reason 4))
1342 (dpb byte (byte 3 18)
1343 (dpb byte2 (byte 6 12)
1344 (dpb byte3 (byte 6 6) byte4))))))))
1346 ;;;; utility functions (misc routines, etc)
1348 ;;; Fill in the various routine slots for the given type. INPUT-P and
1349 ;;; OUTPUT-P indicate what slots to fill. The buffering slot must be
1350 ;;; set prior to calling this routine.
1351 (defun set-fd-stream-routines (fd-stream element-type external-format
1352 input-p output-p buffer-p)
1353 (let* ((target-type (case element-type
1354 (unsigned-byte '(unsigned-byte 8))
1355 (signed-byte '(signed-byte 8))
1356 (:default 'character)
1358 (character-stream-p (subtypep target-type 'character))
1359 (bivalent-stream-p (eq element-type :default))
1360 normalized-external-format
1361 (bin-routine #'ill-bin)
1364 (cin-routine #'ill-in)
1367 (input-type nil) ;calculated from bin-type/cin-type
1368 (input-size nil) ;calculated from bin-size/cin-size
1369 (read-n-characters #'ill-in)
1370 (bout-routine #'ill-bout)
1373 (cout-routine #'ill-out)
1378 (output-bytes #'ill-bout))
1380 ;; drop buffers when direction changes
1381 (when (and (fd-stream-obuf-sap fd-stream) (not output-p))
1382 (with-available-buffers-lock ()
1383 (push (fd-stream-obuf-sap fd-stream) *available-buffers*)
1384 (setf (fd-stream-obuf-sap fd-stream) nil)))
1385 (when (and (fd-stream-ibuf-sap fd-stream) (not input-p))
1386 (with-available-buffers-lock ()
1387 (push (fd-stream-ibuf-sap fd-stream) *available-buffers*)
1388 (setf (fd-stream-ibuf-sap fd-stream) nil)))
1390 (setf (fd-stream-ibuf-sap fd-stream) (next-available-buffer))
1391 (setf (fd-stream-ibuf-length fd-stream) bytes-per-buffer)
1392 (setf (fd-stream-ibuf-tail fd-stream) 0))
1394 (setf (fd-stream-obuf-sap fd-stream) (next-available-buffer))
1395 (setf (fd-stream-obuf-length fd-stream) bytes-per-buffer)
1396 (setf (fd-stream-obuf-tail fd-stream) 0)
1397 (setf (fd-stream-char-pos fd-stream) 0))
1399 (when (and character-stream-p
1400 (eq external-format :default))
1401 (/show0 "/getting default external format")
1402 (setf external-format (default-external-format)))
1405 (when (or (not character-stream-p) bivalent-stream-p)
1406 (multiple-value-setq (bin-routine bin-type bin-size read-n-characters
1407 normalized-external-format)
1408 (pick-input-routine (if bivalent-stream-p '(unsigned-byte 8)
1412 (error "could not find any input routine for ~S" target-type)))
1413 (when character-stream-p
1414 (multiple-value-setq (cin-routine cin-type cin-size read-n-characters
1415 normalized-external-format)
1416 (pick-input-routine target-type external-format))
1418 (error "could not find any input routine for ~S" target-type)))
1419 (setf (fd-stream-in fd-stream) cin-routine
1420 (fd-stream-bin fd-stream) bin-routine)
1421 ;; character type gets preferential treatment
1422 (setf input-size (or cin-size bin-size))
1423 (setf input-type (or cin-type bin-type))
1424 (when normalized-external-format
1425 (setf (fd-stream-external-format fd-stream)
1426 normalized-external-format))
1427 (when (= (or cin-size 1) (or bin-size 1) 1)
1428 (setf (fd-stream-n-bin fd-stream) ;XXX
1429 (if (and character-stream-p (not bivalent-stream-p))
1431 #'fd-stream-read-n-bytes))
1432 ;; Sometimes turn on fast-read-char/fast-read-byte. Switch on
1433 ;; for character and (unsigned-byte 8) streams. In these
1434 ;; cases, fast-read-* will read from the
1435 ;; ansi-stream-(c)in-buffer, saving function calls.
1436 ;; Otherwise, the various data-reading functions in the stream
1437 ;; structure will be called.
1439 (not bivalent-stream-p)
1440 ;; temporary disable on :io streams
1442 (cond (character-stream-p
1443 (setf (ansi-stream-cin-buffer fd-stream)
1444 (make-array +ansi-stream-in-buffer-length+
1445 :element-type 'character)))
1446 ((equal target-type '(unsigned-byte 8))
1447 (setf (ansi-stream-in-buffer fd-stream)
1448 (make-array +ansi-stream-in-buffer-length+
1449 :element-type '(unsigned-byte 8))))))))
1452 (when (or (not character-stream-p) bivalent-stream-p)
1453 (multiple-value-setq (bout-routine bout-type bout-size output-bytes
1454 normalized-external-format)
1455 (pick-output-routine (if bivalent-stream-p
1458 (fd-stream-buffering fd-stream)
1460 (unless bout-routine
1461 (error "could not find any output routine for ~S buffered ~S"
1462 (fd-stream-buffering fd-stream)
1464 (when character-stream-p
1465 (multiple-value-setq (cout-routine cout-type cout-size output-bytes
1466 normalized-external-format)
1467 (pick-output-routine target-type
1468 (fd-stream-buffering fd-stream)
1470 (unless cout-routine
1471 (error "could not find any output routine for ~S buffered ~S"
1472 (fd-stream-buffering fd-stream)
1474 (when normalized-external-format
1475 (setf (fd-stream-external-format fd-stream)
1476 normalized-external-format))
1477 (when character-stream-p
1478 (setf (fd-stream-output-bytes fd-stream) output-bytes))
1479 (setf (fd-stream-out fd-stream) cout-routine
1480 (fd-stream-bout fd-stream) bout-routine
1481 (fd-stream-sout fd-stream) (if (eql cout-size 1)
1482 #'fd-sout #'ill-out))
1483 (setf output-size (or cout-size bout-size))
1484 (setf output-type (or cout-type bout-type)))
1486 (when (and input-size output-size
1487 (not (eq input-size output-size)))
1488 (error "Element sizes for input (~S:~S) and output (~S:~S) differ?"
1489 input-type input-size
1490 output-type output-size))
1491 (setf (fd-stream-element-size fd-stream)
1492 (or input-size output-size))
1494 (setf (fd-stream-element-type fd-stream)
1495 (cond ((equal input-type output-type)
1501 ((subtypep input-type output-type)
1503 ((subtypep output-type input-type)
1506 (error "Input type (~S) and output type (~S) are unrelated?"
1510 ;;; Handle miscellaneous operations on FD-STREAM.
1511 (defun fd-stream-misc-routine (fd-stream operation &optional arg1 arg2)
1512 (declare (ignore arg2))
1515 (or (not (eql (fd-stream-ibuf-head fd-stream)
1516 (fd-stream-ibuf-tail fd-stream)))
1517 (fd-stream-listen fd-stream)
1518 (setf (fd-stream-listen fd-stream)
1519 (eql (sb!unix:with-restarted-syscall ()
1520 (sb!alien:with-alien ((read-fds (sb!alien:struct
1522 (sb!unix:fd-zero read-fds)
1523 (sb!unix:fd-set (fd-stream-fd fd-stream) read-fds)
1524 (sb!unix:unix-fast-select (1+ (fd-stream-fd fd-stream))
1525 (sb!alien:addr read-fds)
1529 (setf (fd-stream-unread fd-stream) arg1)
1530 (setf (fd-stream-listen fd-stream) t))
1532 (cond (arg1 ; We got us an abort on our hands.
1533 (when (fd-stream-handler fd-stream)
1534 (sb!sys:remove-fd-handler (fd-stream-handler fd-stream))
1535 (setf (fd-stream-handler fd-stream) nil))
1536 ;; We can't do anything unless we know what file were
1537 ;; dealing with, and we don't want to do anything
1538 ;; strange unless we were writing to the file.
1539 (when (and (fd-stream-file fd-stream)
1540 (fd-stream-obuf-sap fd-stream))
1541 (if (fd-stream-original fd-stream)
1542 ;; If the original is EQ to file we are appending
1543 ;; and can just close the file without renaming.
1544 (unless (eq (fd-stream-original fd-stream)
1545 (fd-stream-file fd-stream))
1546 ;; We have a handle on the original, just revert.
1547 (multiple-value-bind (okay err)
1548 (sb!unix:unix-rename (fd-stream-original fd-stream)
1549 (fd-stream-file fd-stream))
1551 (simple-stream-perror
1552 "couldn't restore ~S to its original contents"
1555 ;; We can't restore the original, and aren't
1556 ;; appending, so nuke that puppy.
1558 ;; FIXME: This is currently the fate of superseded
1559 ;; files, and according to the CLOSE spec this is
1560 ;; wrong. However, there seems to be no clean way to
1561 ;; do that that doesn't involve either copying the
1562 ;; data (bad if the :abort resulted from a full
1563 ;; disk), or renaming the old file temporarily
1564 ;; (probably bad because stream opening becomes more
1566 (multiple-value-bind (okay err)
1567 (sb!unix:unix-unlink (fd-stream-file fd-stream))
1569 (error 'simple-file-error
1570 :pathname (fd-stream-file fd-stream)
1572 "~@<couldn't remove ~S: ~2I~_~A~:>"
1573 :format-arguments (list (fd-stream-file fd-stream)
1574 (strerror err))))))))
1576 (fd-stream-misc-routine fd-stream :finish-output)
1577 (when (and (fd-stream-original fd-stream)
1578 (fd-stream-delete-original fd-stream))
1579 (multiple-value-bind (okay err)
1580 (sb!unix:unix-unlink (fd-stream-original fd-stream))
1582 (error 'simple-file-error
1583 :pathname (fd-stream-original fd-stream)
1585 "~@<couldn't delete ~S during close of ~S: ~
1588 (list (fd-stream-original fd-stream)
1590 (strerror err))))))))
1591 (when (fboundp 'cancel-finalization)
1592 (cancel-finalization fd-stream))
1593 (sb!unix:unix-close (fd-stream-fd fd-stream))
1594 (when (fd-stream-obuf-sap fd-stream)
1595 (with-available-buffers-lock ()
1596 (push (fd-stream-obuf-sap fd-stream) *available-buffers*)
1597 (setf (fd-stream-obuf-sap fd-stream) nil)))
1598 (when (fd-stream-ibuf-sap fd-stream)
1599 (with-available-buffers-lock ()
1600 (push (fd-stream-ibuf-sap fd-stream) *available-buffers*)
1601 (setf (fd-stream-ibuf-sap fd-stream) nil)))
1602 (sb!impl::set-closed-flame fd-stream))
1604 (setf (fd-stream-unread fd-stream) nil)
1605 (setf (fd-stream-ibuf-head fd-stream) 0)
1606 (setf (fd-stream-ibuf-tail fd-stream) 0)
1607 (catch 'eof-input-catcher
1609 (let ((count (sb!unix:with-restarted-syscall ()
1610 (sb!alien:with-alien ((read-fds (sb!alien:struct
1612 (sb!unix:fd-zero read-fds)
1613 (sb!unix:fd-set (fd-stream-fd fd-stream) read-fds)
1614 (sb!unix:unix-fast-select (1+ (fd-stream-fd fd-stream))
1615 (sb!alien:addr read-fds)
1617 (cond ((eql count 1)
1618 (refill-buffer/fd fd-stream)
1619 (setf (fd-stream-ibuf-head fd-stream) 0)
1620 (setf (fd-stream-ibuf-tail fd-stream) 0))
1624 (flush-output-buffer fd-stream))
1626 (flush-output-buffer fd-stream)
1628 ((null (fd-stream-output-later fd-stream)))
1629 (sb!sys:serve-all-events)))
1631 (fd-stream-element-type fd-stream))
1633 (fd-stream-external-format fd-stream))
1635 (= 1 (the (member 0 1)
1636 (sb!unix:unix-isatty (fd-stream-fd fd-stream)))))
1640 (fd-stream-char-pos fd-stream))
1642 (unless (fd-stream-file fd-stream)
1643 ;; This is a TYPE-ERROR because ANSI's species FILE-LENGTH
1644 ;; "should signal an error of type TYPE-ERROR if stream is not
1645 ;; a stream associated with a file". Too bad there's no very
1646 ;; appropriate value for the EXPECTED-TYPE slot..
1647 (error 'simple-type-error
1649 :expected-type 'fd-stream
1650 :format-control "~S is not a stream associated with a file."
1651 :format-arguments (list fd-stream)))
1652 (multiple-value-bind (okay dev ino mode nlink uid gid rdev size
1653 atime mtime ctime blksize blocks)
1654 (sb!unix:unix-fstat (fd-stream-fd fd-stream))
1655 (declare (ignore ino nlink uid gid rdev
1656 atime mtime ctime blksize blocks))
1658 (simple-stream-perror "failed Unix fstat(2) on ~S" fd-stream dev))
1661 (truncate size (fd-stream-element-size fd-stream)))))
1662 ;; FIXME: I doubt this is correct in the presence of Unicode,
1663 ;; since fd-stream FILE-POSITION is measured in bytes.
1664 (:file-string-length
1667 (string (length arg1))))
1669 (fd-stream-file-position fd-stream arg1))))
1671 (defun fd-stream-file-position (stream &optional newpos)
1672 (declare (type fd-stream stream)
1673 (type (or (alien sb!unix:off-t) (member nil :start :end)) newpos))
1675 (sb!sys:without-interrupts
1676 ;; First, find the position of the UNIX file descriptor in the file.
1677 (multiple-value-bind (posn errno)
1678 (sb!unix:unix-lseek (fd-stream-fd stream) 0 sb!unix:l_incr)
1679 (declare (type (or (alien sb!unix:off-t) null) posn))
1680 (cond ((integerp posn)
1681 ;; Adjust for buffered output: If there is any output
1682 ;; buffered, the *real* file position will be larger
1683 ;; than reported by lseek() because lseek() obviously
1684 ;; cannot take into account output we have not sent
1686 (dolist (later (fd-stream-output-later stream))
1687 (incf posn (- (caddr later)
1689 (incf posn (fd-stream-obuf-tail stream))
1690 ;; Adjust for unread input: If there is any input
1691 ;; read from UNIX but not supplied to the user of the
1692 ;; stream, the *real* file position will smaller than
1693 ;; reported, because we want to look like the unread
1694 ;; stuff is still available.
1695 (decf posn (- (fd-stream-ibuf-tail stream)
1696 (fd-stream-ibuf-head stream)))
1697 (when (fd-stream-unread stream)
1699 ;; Divide bytes by element size.
1700 (truncate posn (fd-stream-element-size stream)))
1701 ((eq errno sb!unix:espipe)
1704 (sb!sys:with-interrupts
1705 (simple-stream-perror "failure in Unix lseek() on ~S"
1708 (let ((offset 0) origin)
1709 (declare (type (alien sb!unix:off-t) offset))
1710 ;; Make sure we don't have any output pending, because if we
1711 ;; move the file pointer before writing this stuff, it will be
1712 ;; written in the wrong location.
1713 (flush-output-buffer stream)
1715 ((null (fd-stream-output-later stream)))
1716 (sb!sys:serve-all-events))
1717 ;; Clear out any pending input to force the next read to go to
1719 (setf (fd-stream-unread stream) nil)
1720 (setf (fd-stream-ibuf-head stream) 0)
1721 (setf (fd-stream-ibuf-tail stream) 0)
1722 ;; Trash cached value for listen, so that we check next time.
1723 (setf (fd-stream-listen stream) nil)
1725 (cond ((eq newpos :start)
1726 (setf offset 0 origin sb!unix:l_set))
1728 (setf offset 0 origin sb!unix:l_xtnd))
1729 ((typep newpos '(alien sb!unix:off-t))
1730 (setf offset (* newpos (fd-stream-element-size stream))
1731 origin sb!unix:l_set))
1733 (error "invalid position given to FILE-POSITION: ~S" newpos)))
1734 (multiple-value-bind (posn errno)
1735 (sb!unix:unix-lseek (fd-stream-fd stream) offset origin)
1736 (cond ((typep posn '(alien sb!unix:off-t))
1738 ((eq errno sb!unix:espipe)
1741 (simple-stream-perror "error in Unix lseek() on ~S"
1745 ;;;; creation routines (MAKE-FD-STREAM and OPEN)
1747 ;;; Create a stream for the given Unix file descriptor.
1749 ;;; If INPUT is non-NIL, allow input operations. If OUTPUT is non-nil,
1750 ;;; allow output operations. If neither INPUT nor OUTPUT is specified,
1751 ;;; default to allowing input.
1753 ;;; ELEMENT-TYPE indicates the element type to use (as for OPEN).
1755 ;;; BUFFERING indicates the kind of buffering to use.
1757 ;;; TIMEOUT (if true) is the number of seconds to wait for input. If
1758 ;;; NIL (the default), then wait forever. When we time out, we signal
1761 ;;; FILE is the name of the file (will be returned by PATHNAME).
1763 ;;; NAME is used to identify the stream when printed.
1764 (defun make-fd-stream (fd
1767 (output nil output-p)
1768 (element-type 'base-char)
1770 (external-format :default)
1779 (format nil "file ~A" file)
1780 (format nil "descriptor ~W" fd)))
1782 (declare (type index fd) (type (or index null) timeout)
1783 (type (member :none :line :full) buffering))
1784 (cond ((not (or input-p output-p))
1786 ((not (or input output))
1787 (error "File descriptor must be opened either for input or output.")))
1788 (let ((stream (%make-fd-stream :fd fd
1792 :delete-original delete-original
1794 :buffering buffering
1795 :dual-channel-p dual-channel-p
1796 :external-format external-format
1798 (set-fd-stream-routines stream element-type external-format
1799 input output input-buffer-p)
1800 (when (and auto-close (fboundp 'finalize))
1803 (sb!unix:unix-close fd)
1805 (format *terminal-io* "** closed file descriptor ~W **~%"
1809 ;;; Pick a name to use for the backup file for the :IF-EXISTS
1810 ;;; :RENAME-AND-DELETE and :RENAME options.
1811 (defun pick-backup-name (name)
1812 (declare (type simple-base-string name))
1813 (concatenate 'simple-base-string name ".bak"))
1815 ;;; Ensure that the given arg is one of the given list of valid
1816 ;;; things. Allow the user to fix any problems.
1817 (defun ensure-one-of (item list what)
1818 (unless (member item list)
1819 (error 'simple-type-error
1821 :expected-type `(member ,@list)
1822 :format-control "~@<~S is ~_invalid for ~S; ~_need one of~{ ~S~}~:>"
1823 :format-arguments (list item what list))))
1825 ;;; Rename NAMESTRING to ORIGINAL. First, check whether we have write
1826 ;;; access, since we don't want to trash unwritable files even if we
1827 ;;; technically can. We return true if we succeed in renaming.
1828 (defun rename-the-old-one (namestring original)
1829 (unless (sb!unix:unix-access namestring sb!unix:w_ok)
1830 (error "~@<The file ~2I~_~S ~I~_is not writable.~:>" namestring))
1831 (multiple-value-bind (okay err) (sb!unix:unix-rename namestring original)
1834 (error 'simple-file-error
1835 :pathname namestring
1837 "~@<couldn't rename ~2I~_~S ~I~_to ~2I~_~S: ~4I~_~A~:>"
1838 :format-arguments (list namestring original (strerror err))))))
1840 (defun open (filename
1843 (element-type 'base-char)
1844 (if-exists nil if-exists-given)
1845 (if-does-not-exist nil if-does-not-exist-given)
1846 (external-format :default)
1847 &aux ; Squelch assignment warning.
1848 (direction direction)
1849 (if-does-not-exist if-does-not-exist)
1850 (if-exists if-exists))
1852 "Return a stream which reads from or writes to FILENAME.
1854 :DIRECTION - one of :INPUT, :OUTPUT, :IO, or :PROBE
1855 :ELEMENT-TYPE - the type of object to read or write, default BASE-CHAR
1856 :IF-EXISTS - one of :ERROR, :NEW-VERSION, :RENAME, :RENAME-AND-DELETE,
1857 :OVERWRITE, :APPEND, :SUPERSEDE or NIL
1858 :IF-DOES-NOT-EXIST - one of :ERROR, :CREATE or NIL
1859 See the manual for details."
1861 ;; Calculate useful stuff.
1862 (multiple-value-bind (input output mask)
1864 (:input (values t nil sb!unix:o_rdonly))
1865 (:output (values nil t sb!unix:o_wronly))
1866 (:io (values t t sb!unix:o_rdwr))
1867 (:probe (values t nil sb!unix:o_rdonly)))
1868 (declare (type index mask))
1869 (let* ((pathname (merge-pathnames filename))
1871 (cond ((unix-namestring pathname input))
1872 ((and input (eq if-does-not-exist :create))
1873 (unix-namestring pathname nil))
1874 ((and (eq direction :io) (not if-does-not-exist-given))
1875 (unix-namestring pathname nil)))))
1876 ;; Process if-exists argument if we are doing any output.
1878 (unless if-exists-given
1880 (if (eq (pathname-version pathname) :newest)
1883 (ensure-one-of if-exists
1884 '(:error :new-version :rename
1885 :rename-and-delete :overwrite
1886 :append :supersede nil)
1889 ((:new-version :error nil)
1890 (setf mask (logior mask sb!unix:o_excl)))
1891 ((:rename :rename-and-delete)
1892 (setf mask (logior mask sb!unix:o_creat)))
1894 (setf mask (logior mask sb!unix:o_trunc)))
1896 (setf mask (logior mask sb!unix:o_append)))))
1898 (setf if-exists :ignore-this-arg)))
1900 (unless if-does-not-exist-given
1901 (setf if-does-not-exist
1902 (cond ((eq direction :input) :error)
1904 (member if-exists '(:overwrite :append)))
1906 ((eq direction :probe)
1910 (ensure-one-of if-does-not-exist
1911 '(:error :create nil)
1913 (if (eq if-does-not-exist :create)
1914 (setf mask (logior mask sb!unix:o_creat)))
1916 (let ((original (case if-exists
1917 ((:rename :rename-and-delete)
1918 (pick-backup-name namestring))
1919 ((:append :overwrite)
1920 ;; KLUDGE: Provent CLOSE from deleting
1921 ;; appending streams when called with :ABORT T
1923 (delete-original (eq if-exists :rename-and-delete))
1925 (when (and original (not (eq original namestring)))
1926 ;; We are doing a :RENAME or :RENAME-AND-DELETE. Determine
1927 ;; whether the file already exists, make sure the original
1928 ;; file is not a directory, and keep the mode.
1931 (multiple-value-bind (okay err/dev inode orig-mode)
1932 (sb!unix:unix-stat namestring)
1933 (declare (ignore inode)
1934 (type (or index null) orig-mode))
1937 (when (and output (= (logand orig-mode #o170000)
1939 (error 'simple-file-error
1940 :pathname namestring
1942 "can't open ~S for output: is a directory"
1943 :format-arguments (list namestring)))
1944 (setf mode (logand orig-mode #o777))
1946 ((eql err/dev sb!unix:enoent)
1949 (simple-file-perror "can't find ~S"
1953 (rename-the-old-one namestring original))
1955 (setf delete-original nil)
1956 ;; In order to use :SUPERSEDE instead, we have to make
1957 ;; sure SB!UNIX:O_CREAT corresponds to
1958 ;; IF-DOES-NOT-EXIST. SB!UNIX:O_CREAT was set before
1959 ;; because of IF-EXISTS being :RENAME.
1960 (unless (eq if-does-not-exist :create)
1962 (logior (logandc2 mask sb!unix:o_creat)
1964 (setf if-exists :supersede))))
1966 ;; Now we can try the actual Unix open(2).
1967 (multiple-value-bind (fd errno)
1969 (sb!unix:unix-open namestring mask mode)
1970 (values nil sb!unix:enoent))
1971 (labels ((open-error (format-control &rest format-arguments)
1972 (error 'simple-file-error
1974 :format-control format-control
1975 :format-arguments format-arguments))
1976 (vanilla-open-error ()
1977 (simple-file-perror "error opening ~S" pathname errno)))
1980 ((:input :output :io)
1984 :element-type element-type
1985 :external-format external-format
1988 :delete-original delete-original
1995 (%make-fd-stream :name namestring
1998 :element-type element-type)))
2001 ((eql errno sb!unix:enoent)
2002 (case if-does-not-exist
2003 (:error (vanilla-open-error))
2005 (open-error "~@<The path ~2I~_~S ~I~_does not exist.~:>"
2008 ((and (eql errno sb!unix:eexist) (null if-exists))
2011 (vanilla-open-error)))))))))
2015 ;;; the stream connected to the controlling terminal, or NIL if there is none
2018 ;;; the stream connected to the standard input (file descriptor 0)
2021 ;;; the stream connected to the standard output (file descriptor 1)
2024 ;;; the stream connected to the standard error output (file descriptor 2)
2027 ;;; This is called when the cold load is first started up, and may also
2028 ;;; be called in an attempt to recover from nested errors.
2029 (defun stream-cold-init-or-reset ()
2031 (setf *terminal-io* (make-synonym-stream '*tty*))
2032 (setf *standard-output* (make-synonym-stream '*stdout*))
2033 (setf *standard-input* (make-synonym-stream '*stdin*))
2034 (setf *error-output* (make-synonym-stream '*stderr*))
2035 (setf *query-io* (make-synonym-stream '*terminal-io*))
2036 (setf *debug-io* *query-io*)
2037 (setf *trace-output* *standard-output*)
2040 ;;; This is called whenever a saved core is restarted.
2041 (defun stream-reinit ()
2042 (setf *available-buffers* nil)
2043 (with-output-to-string (*error-output*)
2045 (make-fd-stream 0 :name "standard input" :input t :buffering :line))
2047 (make-fd-stream 1 :name "standard output" :output t :buffering :line))
2049 (make-fd-stream 2 :name "standard error" :output t :buffering :line))
2050 (let* ((ttyname #.(coerce "/dev/tty" 'simple-base-string))
2051 (tty (sb!unix:unix-open ttyname sb!unix:o_rdwr #o666)))
2055 :name "the terminal"
2060 (setf *tty* (make-two-way-stream *stdin* *stdout*))))
2061 (princ (get-output-stream-string *error-output*) *stderr*))
2066 ;;; the Unix way to beep
2067 (defun beep (stream)
2068 (write-char (code-char bell-char-code) stream)
2069 (finish-output stream))
2071 ;;; This is kind of like FILE-POSITION, but is an internal hack used
2072 ;;; by the filesys stuff to get and set the file name.
2074 ;;; FIXME: misleading name, screwy interface
2075 (defun file-name (stream &optional new-name)
2076 (when (typep stream 'fd-stream)
2078 (setf (fd-stream-pathname stream) new-name)
2079 (setf (fd-stream-file stream)
2080 (unix-namestring new-name nil))
2083 (fd-stream-pathname stream)))))