X-Git-Url: http://repo.macrolet.net/gitweb/?a=blobdiff_plain;f=src%2Fcode%2Ffd-stream.lisp;h=527474d17bdd86411701f9517ac0023309383999;hb=78fa16bf55be44cc16845be84d98023e83fb14bc;hp=7015b2a8e9853feda73cfdafb8a59238998127be;hpb=dc5e3163fe667e2629c7769aa8cf2e501eeeefa6;p=sbcl.git diff --git a/src/code/fd-stream.lisp b/src/code/fd-stream.lisp index 7015b2a..527474d 100644 --- a/src/code/fd-stream.lisp +++ b/src/code/fd-stream.lisp @@ -11,14 +11,6 @@ (in-package "SB!IMPL") -;;; FIXME: Wouldn't it be clearer to just have the structure -;;; definition be DEFSTRUCT FILE-STREAM (instead of DEFSTRUCT -;;; FD-STREAM)? That way we'd have TYPE-OF and PRINT-OBJECT refer to -;;; these objects as FILE-STREAMs (the ANSI name) instead of the -;;; internal implementation name FD-STREAM, and there might be other -;;; benefits as well. -(deftype file-stream () 'fd-stream) - ;;;; buffer manipulation routines ;;; FIXME: Is it really good to maintain this pool separate from the @@ -39,10 +31,18 @@ (pop *available-buffers*) (allocate-system-memory bytes-per-buffer))) -;;;; the FD-STREAM structure +;;;; the FILE-STREAM structure -(defstruct (fd-stream +(defstruct (file-stream (:constructor %make-fd-stream) + ;; KLUDGE: in an ideal world, maybe we'd rewrite + ;; everything to use FILE-STREAM rather than simply + ;; providing this hack for compatibility with the old + ;; code. However, CVS doesn't deal terribly well with + ;; file renaming, so for now we use this + ;; backward-compatibility feature. + (:conc-name fd-stream-) + (:predicate fd-stream-p) (:include ansi-stream (misc #'fd-stream-misc-routine)) (:copier nil)) @@ -86,8 +86,10 @@ ;; timeout specified for this stream, or NIL if none (timeout nil :type (or index null)) ;; pathname of the file this stream is opened to (returned by PATHNAME) - (pathname nil :type (or pathname null))) -(def!method print-object ((fd-stream fd-stream) stream) + (pathname nil :type (or pathname null)) + (external-format :default) + (output-bytes #'ill-out :type function)) +(def!method print-object ((fd-stream file-stream) stream) (declare (type stream stream)) (print-unreadable-object (fd-stream stream :type t :identity t) (format stream "for ~S" (fd-stream-name fd-stream)))) @@ -113,6 +115,17 @@ :format-arguments (list note-format (list pathname) (strerror errno)))) +(defun stream-decoding-error (stream &rest octets) + (error 'stream-decoding-error + :stream stream + ;; FIXME: dunno how to get at OCTETS currently, or even if + ;; that's the right thing to report. + :octets octets)) +(defun stream-encoding-error (stream character) + (error 'stream-encoding-error + :stream stream + :character character)) + ;;; This is called by the server when we can write to the given file ;;; descriptor. Attempt to write the data again. If it worked, remove ;;; the data from the OUTPUT-LATER list. If it didn't work, something @@ -169,7 +182,7 @@ ;;; writes. If so, just queue this one. Otherwise, try to write it. If ;;; this would block, queue it. (defun frob-output (stream base start end reuse-sap) - (declare (type fd-stream stream) + (declare (type file-stream stream) (type (or system-area-pointer (simple-array * (*))) base) (type index start end)) (if (not (null (fd-stream-output-later stream))) ; something buffered. @@ -197,6 +210,84 @@ (frob-output stream (fd-stream-obuf-sap stream) 0 length t) (setf (fd-stream-obuf-tail stream) 0)))) +(defmacro output-wrapper/variable-width ((stream size buffering) + &body body) + (let ((stream-var (gensym))) + `(let ((,stream-var ,stream) + (size ,size)) + ,(unless (eq (car buffering) :none) + `(when (< (fd-stream-obuf-length ,stream-var) + (+ (fd-stream-obuf-tail ,stream-var) + size)) + (flush-output-buffer ,stream-var))) + ,(unless (eq (car buffering) :none) + `(when (> (fd-stream-ibuf-tail ,stream-var) + (fd-stream-ibuf-head ,stream-var)) + (file-position ,stream-var (file-position ,stream-var)))) + (with-simple-restart (output-nothing + "~@") + ,@body) + (incf (fd-stream-obuf-tail ,stream-var) size) + ,(ecase (car buffering) + (:none + `(flush-output-buffer ,stream-var)) + (:line + `(when (eq (char-code byte) (char-code #\Newline)) + (flush-output-buffer ,stream-var))) + (:full)) + (values)))) + +(defmacro output-wrapper ((stream size buffering) &body body) + (let ((stream-var (gensym))) + `(let ((,stream-var ,stream)) + ,(unless (eq (car buffering) :none) + `(when (< (fd-stream-obuf-length ,stream-var) + (+ (fd-stream-obuf-tail ,stream-var) + ,size)) + (flush-output-buffer ,stream-var))) + ,(unless (eq (car buffering) :none) + `(when (> (fd-stream-ibuf-tail ,stream-var) + (fd-stream-ibuf-head ,stream-var)) + (file-position ,stream-var (file-position ,stream-var)))) + (with-simple-restart (output-nothing + "~@") + ,@body) + (incf (fd-stream-obuf-tail ,stream-var) ,size) + ,(ecase (car buffering) + (:none + `(flush-output-buffer ,stream-var)) + (:line + `(when (eq (char-code byte) (char-code #\Newline)) + (flush-output-buffer ,stream-var))) + (:full)) + (values)))) + +(defmacro def-output-routines/variable-width ((name-fmt size external-format + &rest bufferings) + &body body) + (declare (optimize (speed 1))) + (cons 'progn + (mapcar + (lambda (buffering) + (let ((function + (intern (let ((*print-case* :upcase)) + (format nil name-fmt (car buffering)))))) + `(progn + (defun ,function (stream byte) + (output-wrapper/variable-width (stream ,size ,buffering) + ,@body)) + (setf *output-routines* + (nconc *output-routines* + ',(mapcar + (lambda (type) + (list type + (car buffering) + function + 1 + external-format)) + (cdr buffering))))))) + bufferings))) + ;;; Define output routines that output numbers SIZE bytes long for the ;;; given bufferings. Use BODY to do the actual output. (defmacro def-output-routines ((name-fmt size &rest bufferings) &body body) @@ -209,22 +300,8 @@ (format nil name-fmt (car buffering)))))) `(progn (defun ,function (stream byte) - ,(unless (eq (car buffering) :none) - `(when (< (fd-stream-obuf-length stream) - (+ (fd-stream-obuf-tail stream) - ,size)) - (flush-output-buffer stream))) - ,@body - (incf (fd-stream-obuf-tail stream) ,size) - ,(ecase (car buffering) - (:none - `(flush-output-buffer stream)) - (:line - `(when (eq (char-code byte) (char-code #\Newline)) - (flush-output-buffer stream))) - (:full - )) - (values)) + (output-wrapper (stream ,size ,buffering) + ,@body)) (setf *output-routines* (nconc *output-routines* ',(mapcar @@ -232,7 +309,8 @@ (list type (car buffering) function - size)) + size + nil)) (cdr buffering))))))) bufferings))) @@ -241,7 +319,7 @@ (:none character) (:line character) (:full character)) - (if (and (base-char-p byte) (char= byte #\Newline)) + (if (char= byte #\Newline) (setf (fd-stream-char-pos stream) 0) (incf (fd-stream-char-pos stream))) (setf (sap-ref-8 (fd-stream-obuf-sap stream) (fd-stream-obuf-tail stream)) @@ -305,6 +383,9 @@ (let ((start (or start 0)) (end (or end (length (the (simple-array * (*)) thing))))) (declare (type index start end)) + (when (> (fd-stream-ibuf-tail fd-stream) + (fd-stream-ibuf-head fd-stream)) + (file-position fd-stream (file-position fd-stream))) (let* ((len (fd-stream-obuf-length fd-stream)) (tail (fd-stream-obuf-tail fd-stream)) (space (- len tail)) @@ -376,6 +457,8 @@ :from-end t :start start :end end)))) + (if (and (typep thing 'base-string) + (eq (fd-stream-external-format stream) :latin-1)) (ecase (fd-stream-buffering stream) (:full (output-raw-bytes stream thing start end)) @@ -385,6 +468,13 @@ (flush-output-buffer stream))) (:none (frob-output stream thing start end nil))) + (ecase (fd-stream-buffering stream) + (:full (funcall (fd-stream-output-bytes stream) + stream thing nil start end)) + (:line (funcall (fd-stream-output-bytes stream) + stream thing last-newline start end)) + (:none (funcall (fd-stream-output-bytes stream) + stream thing t start end)))) (if last-newline (setf (fd-stream-char-pos stream) (- end last-newline 1)) @@ -396,16 +486,88 @@ (:none (frob-output stream thing start end nil)))))) +(defvar *external-formats* () + #!+sb-doc + "List of all available external formats. Each element is a list of the + element-type, string input function name, character input function name, + and string output function name.") + ;;; Find an output routine to use given the type and buffering. Return ;;; as multiple values the routine, the real type transfered, and the ;;; number of bytes per element. -(defun pick-output-routine (type buffering) +(defun pick-output-routine (type buffering &optional external-format) + (when (subtypep type 'character) + (dolist (entry *external-formats*) + (when (member external-format (first entry)) + (return-from pick-output-routine + (values (symbol-function (nth (ecase buffering + (:none 4) + (:line 5) + (:full 6)) + entry)) + 'character + 1 + (symbol-function (fourth entry)) + (first (first entry))))))) (dolist (entry *output-routines*) - (when (and (subtypep type (car entry)) - (eq buffering (cadr entry))) - (return (values (symbol-function (caddr entry)) - (car entry) - (cadddr entry)))))) + (when (and (subtypep type (first entry)) + (eq buffering (second entry)) + (or (not (fifth entry)) + (eq external-format (fifth entry)))) + (return-from pick-output-routine + (values (symbol-function (third entry)) + (first entry) + (fourth entry))))) + ;; KLUDGE: dealing with the buffering here leads to excessive code + ;; explosion. + ;; + ;; KLUDGE: also see comments in PICK-INPUT-ROUTINE + (loop for i from 40 by 8 to 1024 ; ARB (KLUDGE) + if (subtypep type `(unsigned-byte ,i)) + do (return-from pick-output-routine + (values + (ecase buffering + (:none + (lambda (stream byte) + (output-wrapper (stream (/ i 8) (:none)) + (loop for j from 0 below (/ i 8) + do (setf (sap-ref-8 + (fd-stream-obuf-sap stream) + (+ j (fd-stream-obuf-tail stream))) + (ldb (byte 8 (- i 8 (* j 8))) byte)))))) + (:full + (lambda (stream byte) + (output-wrapper (stream (/ i 8) (:full)) + (loop for j from 0 below (/ i 8) + do (setf (sap-ref-8 + (fd-stream-obuf-sap stream) + (+ j (fd-stream-obuf-tail stream))) + (ldb (byte 8 (- i 8 (* j 8))) byte))))))) + `(unsigned-byte ,i) + (/ i 8)))) + (loop for i from 40 by 8 to 1024 ; ARB (KLUDGE) + if (subtypep type `(signed-byte ,i)) + do (return-from pick-output-routine + (values + (ecase buffering + (:none + (lambda (stream byte) + (output-wrapper (stream (/ i 8) (:none)) + (loop for j from 0 below (/ i 8) + do (setf (sap-ref-8 + (fd-stream-obuf-sap stream) + (+ j (fd-stream-obuf-tail stream))) + (ldb (byte 8 (- i 8 (* j 8))) byte)))))) + (:full + (lambda (stream byte) + (output-wrapper (stream (/ i 8) (:full)) + (loop for j from 0 below (/ i 8) + do (setf (sap-ref-8 + (fd-stream-obuf-sap stream) + (+ j (fd-stream-obuf-tail stream))) + (ldb (byte 8 (- i 8 (* j 8))) byte))))))) + `(signed-byte ,i) + (/ i 8))))) ;;;; input routines and related noise @@ -457,10 +619,8 @@ (case count (1) (0 - (unless #!-mp (sb!sys:wait-until-fd-usable - fd :input (fd-stream-timeout stream)) - #!+mp (sb!mp:process-wait-until-fd-usable - fd :input (fd-stream-timeout stream)) + (unless (sb!sys:wait-until-fd-usable + fd :input (fd-stream-timeout stream)) (error 'io-timeout :stream stream :direction :read))) (t (simple-stream-perror "couldn't check whether ~S is readable" @@ -473,10 +633,8 @@ (cond ((null count) (if (eql errno sb!unix:ewouldblock) (progn - (unless #!-mp (sb!sys:wait-until-fd-usable - fd :input (fd-stream-timeout stream)) - #!+mp (sb!mp:process-wait-until-fd-usable - fd :input (fd-stream-timeout stream)) + (unless (sb!sys:wait-until-fd-usable + fd :input (fd-stream-timeout stream)) (error 'io-timeout :stream stream :direction :read)) (frob-input stream)) (simple-stream-perror "couldn't read from ~S" stream errno))) @@ -501,6 +659,54 @@ (return)) (frob-input ,stream-var))))) +(defmacro input-wrapper/variable-width ((stream bytes eof-error eof-value + resync-function) + &body read-forms) + (let ((stream-var (gensym)) + (retry-var (gensym)) + (element-var (gensym))) + `(let ((,stream-var ,stream) + (size nil)) + (if (fd-stream-unread ,stream-var) + (prog1 + (fd-stream-unread ,stream-var) + (setf (fd-stream-unread ,stream-var) nil) + (setf (fd-stream-listen ,stream-var) nil)) + (let ((,element-var nil)) + (do ((,retry-var t)) + ((not ,retry-var)) + (setq ,retry-var nil) + (restart-case + (catch 'eof-input-catcher + (unless + (block character-decode + (input-at-least ,stream-var 1) + (let* ((byte (sap-ref-8 (fd-stream-ibuf-sap + ,stream-var) + (fd-stream-ibuf-head + ,stream-var)))) + (setq size ,bytes) + (input-at-least ,stream-var size) + (setq ,element-var (locally ,@read-forms)))) + (stream-decoding-error ,stream-var))) + (attempt-resync () + :report (lambda (stream) + (format stream + "~@")) + (,resync-function ,stream-var) + (setq ,retry-var t)) + (end-of-file () + :report (lambda (stream) + (format stream + "~@")) + nil))) + (cond (,element-var + (incf (fd-stream-ibuf-head ,stream-var) size) + ,element-var) + (t + (eof-or-lose ,stream-var ,eof-error ,eof-value)))))))) + ;;; a macro to wrap around all input routines to handle EOF-ERROR noise (defmacro input-wrapper ((stream bytes eof-error eof-value) &body read-forms) (let ((stream-var (gensym)) @@ -514,13 +720,28 @@ (let ((,element-var (catch 'eof-input-catcher (input-at-least ,stream-var ,bytes) - ,@read-forms))) + (locally ,@read-forms)))) (cond (,element-var (incf (fd-stream-ibuf-head ,stream-var) ,bytes) ,element-var) (t (eof-or-lose ,stream-var ,eof-error ,eof-value)))))))) +(defmacro def-input-routine/variable-width (name + (type external-format size sap head + resync-function) + &rest body) + `(progn + (defun ,name (stream eof-error eof-value) + (input-wrapper/variable-width (stream ,size eof-error eof-value + ,resync-function) + (let ((,sap (fd-stream-ibuf-sap stream)) + (,head (fd-stream-ibuf-head stream))) + ,@body))) + (setf *input-routines* + (nconc *input-routines* + (list (list ',type ',name 1 ',external-format)))))) + (defmacro def-input-routine (name (type size sap head) &rest body) @@ -532,7 +753,7 @@ ,@body))) (setf *input-routines* (nconc *input-routines* - (list (list ',type ',name ',size)))))) + (list (list ',type ',name ',size nil)))))) ;;; STREAM-IN routine for reading a string char (def-input-routine input-character @@ -569,15 +790,66 @@ ((signed-byte 32) 4 sap head) (signed-sap-ref-32 sap head)) + + ;;; Find an input routine to use given the type. Return as multiple ;;; values the routine, the real type transfered, and the number of -;;; bytes per element. -(defun pick-input-routine (type) +;;; bytes per element (and for character types string input routine). +(defun pick-input-routine (type &optional external-format) + (when (subtypep type 'character) + (dolist (entry *external-formats*) + (when (member external-format (first entry)) + (return-from pick-input-routine + (values (symbol-function (third entry)) + 'character + 1 + (symbol-function (second entry)) + (first (first entry))))))) (dolist (entry *input-routines*) - (when (subtypep type (car entry)) - (return (values (symbol-function (cadr entry)) - (car entry) - (caddr entry)))))) + (when (and (subtypep type (first entry)) + (or (not (fourth entry)) + (eq external-format (fourth entry)))) + (return-from pick-input-routine + (values (symbol-function (second entry)) + (first entry) + (third entry))))) + ;; FIXME: let's do it the hard way, then (but ignore things like + ;; endianness, efficiency, and the necessary coupling between these + ;; and the output routines). -- CSR, 2004-02-09 + (loop for i from 40 by 8 to 1024 ; ARB (well, KLUDGE really) + if (subtypep type `(unsigned-byte ,i)) + do (return-from pick-input-routine + (values + (lambda (stream eof-error eof-value) + (input-wrapper (stream (/ i 8) eof-error eof-value) + (let ((sap (fd-stream-ibuf-sap stream)) + (head (fd-stream-ibuf-head stream))) + (loop for j from 0 below (/ i 8) + with result = 0 + do (setf result + (+ (* 256 result) + (sap-ref-8 sap (+ head j)))) + finally (return result))))) + `(unsigned-byte ,i) + (/ i 8)))) + (loop for i from 40 by 8 to 1024 ; ARB (well, KLUDGE really) + if (subtypep type `(signed-byte ,i)) + do (return-from pick-input-routine + (values + (lambda (stream eof-error eof-value) + (input-wrapper (stream (/ i 8) eof-error eof-value) + (let ((sap (fd-stream-ibuf-sap stream)) + (head (fd-stream-ibuf-head stream))) + (loop for j from 0 below (/ i 8) + with result = 0 + do (setf result + (+ (* 256 result) + (sap-ref-8 sap (+ head j)))) + finally (return (if (logbitp (1- i) result) + (dpb result (byte i 0) -1) + result)))))) + `(signed-byte ,i) + (/ i 8))))) ;;; Return a string constructed from SAP, START, and END. (defun string-from-sap (sap start end) @@ -595,12 +867,28 @@ ;;; Note that this blocks in UNIX-READ. It is generally used where ;;; there is a definite amount of reading to be done, so blocking ;;; isn't too problematical. -(defun fd-stream-read-n-bytes (stream buffer start requested eof-error-p) - (declare (type fd-stream stream)) - (declare (type index start requested)) - (do ((total-copied 0)) +(defun fd-stream-read-n-bytes (stream buffer start requested eof-error-p + &aux (total-copied 0)) + (declare (type file-stream stream)) + (declare (type index start requested total-copied)) + (let ((unread (fd-stream-unread stream))) + (when unread + ;; AVERs designed to fail when we have more complicated + ;; character representations. + (aver (typep unread 'base-char)) + (aver (= (fd-stream-element-size stream) 1)) + ;; KLUDGE: this is a slightly-unrolled-and-inlined version of + ;; %BYTE-BLT + (etypecase buffer + (system-area-pointer + (setf (sap-ref-8 buffer start) (char-code unread))) + ((simple-unboxed-array (*)) + (setf (aref buffer start) unread))) + (setf (fd-stream-unread stream) nil) + (setf (fd-stream-listen stream) nil) + (incf total-copied))) + (do () (nil) - (declare (type index total-copied)) (let* ((remaining-request (- requested total-copied)) (head (fd-stream-ibuf-head stream)) (tail (fd-stream-ibuf-tail stream)) @@ -633,18 +921,352 @@ (defun refill-fd-stream-buffer (stream) ;; We don't have any logic to preserve leftover bytes in the buffer, ;; so we should only be called when the buffer is empty. - (aver (= (fd-stream-ibuf-head stream) (fd-stream-ibuf-tail stream))) - (multiple-value-bind (count err) - (sb!unix:unix-read (fd-stream-fd stream) - (fd-stream-ibuf-sap stream) - (fd-stream-ibuf-length stream)) - (declare (type (or index null) count)) - (when (null count) - (simple-stream-perror "couldn't read from ~S" stream err)) - (setf (fd-stream-listen stream) nil - (fd-stream-ibuf-head stream) 0 - (fd-stream-ibuf-tail stream) count) - count)) + ;; FIXME: can have three bytes in buffer because of UTF-8 + (let ((new-head 0) + (sap (fd-stream-ibuf-sap stream))) + (do ((head (fd-stream-ibuf-head stream) (1+ head)) + (tail (fd-stream-ibuf-tail stream))) + ((= head tail)) + (setf (sap-ref-8 sap new-head) (sap-ref-8 sap head)) + (incf new-head)) + (multiple-value-bind (count err) + (sb!unix:unix-read (fd-stream-fd stream) + (sap+ sap new-head) + (- (fd-stream-ibuf-length stream) new-head)) + (declare (type (or index null) count)) + (when (null count) + (simple-stream-perror "couldn't read from ~S" stream err)) + (setf (fd-stream-listen stream) nil + (fd-stream-ibuf-head stream) new-head + (fd-stream-ibuf-tail stream) (+ count new-head)) + count))) + +(defmacro define-external-format (external-format size out-expr in-expr) + (let* ((name (first external-format)) + (out-function (intern (let ((*print-case* :upcase)) + (format nil "OUTPUT-BYTES/~A" name)))) + (format (format nil "OUTPUT-CHAR-~A-~~A-BUFFERED" name)) + (in-function (intern (let ((*print-case* :upcase)) + (format nil "FD-STREAM-READ-N-CHARACTERS/~A" + name)))) + (in-char-function (intern (let ((*print-case* :upcase)) + (format nil "INPUT-CHAR/~A" name))))) + `(progn + (defun ,out-function (stream string flush-p start end) + (let ((start (or start 0)) + (end (or end (length string)))) + (declare (type index start end)) + (when (> (fd-stream-ibuf-tail stream) + (fd-stream-ibuf-head stream)) + (file-position stream (file-position stream))) + (when (< end start) + (error ":END before :START!")) + (do () + ((= end start)) + (setf (fd-stream-obuf-tail stream) + (do* ((len (fd-stream-obuf-length stream)) + (sap (fd-stream-obuf-sap stream)) + (tail (fd-stream-obuf-tail stream))) + ((or (= start end) (< (- len tail) 4)) tail) + (with-simple-restart (output-nothing + "~@") + (let* ((byte (aref string start)) + (bits (char-code byte))) + ,out-expr + (incf tail ,size))) + (incf start))) + (when (< start end) + (flush-output-buffer stream))) + (when flush-p + (flush-output-buffer stream)))) + (def-output-routines (,format + ,size + (:none character) + (:line character) + (:full character)) + (if (char= byte #\Newline) + (setf (fd-stream-char-pos stream) 0) + (incf (fd-stream-char-pos stream))) + (let ((bits (char-code byte)) + (sap (fd-stream-obuf-sap stream)) + (tail (fd-stream-obuf-tail stream))) + ,out-expr)) + (defun ,in-function (stream buffer start requested eof-error-p + &aux (total-copied 0)) + (declare (type file-stream stream)) + (declare (type index start requested total-copied)) + (let ((unread (fd-stream-unread stream))) + (when unread + (setf (aref buffer start) unread) + (setf (fd-stream-unread stream) nil) + (setf (fd-stream-listen stream) nil) + (incf total-copied))) + (do () + (nil) + (let* ((head (fd-stream-ibuf-head stream)) + (tail (fd-stream-ibuf-tail stream)) + (sap (fd-stream-ibuf-sap stream))) + (declare (type index head tail)) + ;; Copy data from stream buffer into user's buffer. + (do () + ((or (= tail head) (= requested total-copied))) + (let* ((byte (sap-ref-8 sap head))) + (when (> ,size (- tail head)) + (return)) + (setf (aref buffer (+ start total-copied)) ,in-expr) + (incf total-copied) + (incf head ,size))) + (setf (fd-stream-ibuf-head stream) head) + ;; Maybe we need to refill the stream buffer. + (cond ( ;; If there were enough data in the stream buffer, we're done. + (= total-copied requested) + (return total-copied)) + ( ;; If EOF, we're done in another way. + (zerop (refill-fd-stream-buffer stream)) + (if eof-error-p + (error 'end-of-file :stream stream) + (return total-copied))) + ;; Otherwise we refilled the stream buffer, so fall + ;; through into another pass of the loop. + )))) + (def-input-routine ,in-char-function (character ,size sap head) + (let ((byte (sap-ref-8 sap head))) + ,in-expr)) + (setf *external-formats* + (cons '(,external-format ,in-function ,in-char-function ,out-function + ,@(mapcar #'(lambda (buffering) + (intern (let ((*print-case* :upcase)) + (format nil format buffering)))) + '(:none :line :full))) + *external-formats*))))) + +(defmacro define-external-format/variable-width (external-format out-size-expr + out-expr in-size-expr in-expr + resync-expr) + (let* ((name (first external-format)) + (out-function (intern (let ((*print-case* :upcase)) + (format nil "OUTPUT-BYTES/~A" name)))) + (format (format nil "OUTPUT-CHAR-~A-~~A-BUFFERED" name)) + (in-function (intern (let ((*print-case* :upcase)) + (format nil "FD-STREAM-READ-N-CHARACTERS/~A" + name)))) + (in-char-function (intern (let ((*print-case* :upcase)) + (format nil "INPUT-CHAR/~A" name)))) + (resync-function (intern (let ((*print-case* :upcase)) + (format nil "RESYNC/~A" name))))) + `(progn + (defun ,out-function (fd-stream string flush-p start end) + (let ((start (or start 0)) + (end (or end (length string)))) + (declare (type index start end)) + (when (> (fd-stream-ibuf-tail fd-stream) + (fd-stream-ibuf-head fd-stream)) + (file-position fd-stream (file-position fd-stream))) + (when (< end start) + (error ":END before :START!")) + (do () + ((= end start)) + (setf (fd-stream-obuf-tail fd-stream) + (do* ((len (fd-stream-obuf-length fd-stream)) + (sap (fd-stream-obuf-sap fd-stream)) + (tail (fd-stream-obuf-tail fd-stream))) + ((or (= start end) (< (- len tail) 4)) tail) + (let* ((byte (aref string start)) + (bits (char-code byte)) + (size ,out-size-expr)) + ,out-expr + (incf tail size) + (incf start)))) + (when (< start end) + (flush-output-buffer fd-stream))) + (when flush-p + (flush-output-buffer fd-stream)))) + (def-output-routines/variable-width (,format + ,out-size-expr + ,external-format + (:none character) + (:line character) + (:full character)) + (if (char= byte #\Newline) + (setf (fd-stream-char-pos stream) 0) + (incf (fd-stream-char-pos stream))) + (let ((bits (char-code byte)) + (sap (fd-stream-obuf-sap stream)) + (tail (fd-stream-obuf-tail stream))) + ,out-expr)) + (defun ,in-function (stream buffer start requested eof-error-p + &aux (total-copied 0)) + (declare (type file-stream stream)) + (declare (type index start requested total-copied)) + (let ((unread (fd-stream-unread stream))) + (when unread + (setf (aref buffer start) unread) + (setf (fd-stream-unread stream) nil) + (setf (fd-stream-listen stream) nil) + (incf total-copied))) + (do () + (nil) + (let* ((head (fd-stream-ibuf-head stream)) + (tail (fd-stream-ibuf-tail stream)) + (sap (fd-stream-ibuf-sap stream))) + (declare (type index head tail)) + ;; Copy data from stream buffer into user's buffer. + (do () + ((or (= tail head) (= requested total-copied))) + (restart-case + (unless (block character-decode + (let* ((byte (sap-ref-8 sap head)) + (size ,in-size-expr)) + (when (> size (- tail head)) + (return)) + (setf (aref buffer (+ start total-copied)) + ,in-expr) + (incf total-copied) + (incf head size))) + (setf (fd-stream-ibuf-head stream) head) + (if (plusp total-copied) + (return-from ,in-function total-copied) + (stream-decoding-error stream))) + (attempt-resync () + :report (lambda (stream) + (format stream + "~@")) + (,resync-function stream) + (setf head (fd-stream-ibuf-head stream))) + (end-of-file () + :report (lambda (stream) + (format stream "~@")) + (if eof-error-p + (error 'end-of-file :stream stream) + (return-from ,in-function total-copied))))) + (setf (fd-stream-ibuf-head stream) head) + ;; Maybe we need to refill the stream buffer. + (cond ( ;; If there were enough data in the stream buffer, we're done. + (= total-copied requested) + (return total-copied)) + ( ;; If EOF, we're done in another way. + (zerop (refill-fd-stream-buffer stream)) + (if eof-error-p + (error 'end-of-file :stream stream) + (return total-copied))) + ;; Otherwise we refilled the stream buffer, so fall + ;; through into another pass of the loop. + )))) + (def-input-routine/variable-width ,in-char-function (character + ,external-format + ,in-size-expr + sap head + ,resync-function) + (let ((byte (sap-ref-8 sap head))) + ,in-expr)) + (defun ,resync-function (stream) + ,resync-expr) + (setf *external-formats* + (cons '(,external-format ,in-function ,in-char-function ,out-function + ,@(mapcar #'(lambda (buffering) + (intern (let ((*print-case* :upcase)) + (format nil format buffering)))) + '(:none :line :full)) + ,resync-function) + *external-formats*))))) + +(define-external-format (:latin-1 :latin1 :iso-8859-1) + 1 + (if (>= bits 256) + (stream-encoding-error stream byte) + (setf (sap-ref-8 sap tail) bits)) + (code-char byte)) + +(define-external-format (:ascii :us-ascii :ansi_x3.4-1968) + 1 + (if (>= bits 128) + (stream-encoding-error stream byte) + (setf (sap-ref-8 sap tail) bits)) + (code-char byte)) + +#!+sb-unicode +(let ((latin-9-table (let ((table (make-string 256))) + (do ((i 0 (1+ i))) + ((= i 256)) + (setf (aref table i) (code-char i))) + (setf (aref table #xa4) (code-char #x20ac)) + (setf (aref table #xa6) (code-char #x0160)) + (setf (aref table #xa8) (code-char #x0161)) + (setf (aref table #xb4) (code-char #x017d)) + (setf (aref table #xb8) (code-char #x017e)) + (setf (aref table #xbc) (code-char #x0152)) + (setf (aref table #xbd) (code-char #x0153)) + (setf (aref table #xbe) (code-char #x0178)) + table)) + (latin-9-reverse-1 (make-array 16 + :element-type '(unsigned-byte 21) + :initial-contents '(#x0160 #x0161 #x0152 #x0153 0 0 0 0 #x0178 0 0 0 #x20ac #x017d #x017e 0))) + (latin-9-reverse-2 (make-array 16 + :element-type '(unsigned-byte 8) + :initial-contents '(#xa6 #xa8 #xbc #xbd 0 0 0 0 #xbe 0 0 0 #xa4 #xb4 #xb8 0)))) + (define-external-format (:latin-9 :latin9 :iso-8859-15) + 1 + (setf (sap-ref-8 sap tail) + (if (< bits 256) + (if (= bits (char-code (aref latin-9-table bits))) + bits + (stream-encoding-error stream byte)) + (if (= (aref latin-9-reverse-1 (logand bits 15)) bits) + (aref latin-9-reverse-2 (logand bits 15)) + (stream-encoding-error stream byte)))) + (aref latin-9-table byte))) + +(define-external-format/variable-width (:utf-8 :utf8) + (let ((bits (char-code byte))) + (cond ((< bits #x80) 1) + ((< bits #x800) 2) + ((< bits #x10000) 3) + (t 4))) + (ecase size + (1 (setf (sap-ref-8 sap tail) bits)) + (2 (setf (sap-ref-8 sap tail) (logior #xc0 (ldb (byte 5 6) bits)) + (sap-ref-8 sap (1+ tail)) (logior #x80 (ldb (byte 6 0) bits)))) + (3 (setf (sap-ref-8 sap tail) (logior #xe0 (ldb (byte 4 12) bits)) + (sap-ref-8 sap (1+ tail)) (logior #x80 (ldb (byte 6 6) bits)) + (sap-ref-8 sap (+ 2 tail)) (logior #x80 (ldb (byte 6 0) bits)))) + (4 (setf (sap-ref-8 sap tail) (logior #xf0 (ldb (byte 3 18) bits)) + (sap-ref-8 sap (1+ tail)) (logior #x80 (ldb (byte 6 12) bits)) + (sap-ref-8 sap (+ 2 tail)) (logior #x80 (ldb (byte 6 6) bits)) + (sap-ref-8 sap (+ 3 tail)) (logior #x80 (ldb (byte 6 0) bits))))) + (cond ((< byte #x80) 1) + ((< byte #xc2) (return-from character-decode)) + ((< byte #xe0) 2) + ((< byte #xf0) 3) + (t 4)) + (code-char (ecase size + (1 byte) + (2 (let ((byte2 (sap-ref-8 sap (1+ head)))) + (unless (<= #x80 byte2 #xbf) + (return-from character-decode)) + (dpb byte (byte 5 6) byte2))) + (3 (let ((byte2 (sap-ref-8 sap (1+ head))) + (byte3 (sap-ref-8 sap (+ 2 head)))) + (unless (and (<= #x80 byte2 #xbf) + (<= #x80 byte3 #xbf)) + (return-from character-decode)) + (dpb byte (byte 4 12) (dpb byte2 (byte 6 6) byte3)))) + (4 (let ((byte2 (sap-ref-8 sap (1+ head))) + (byte3 (sap-ref-8 sap (+ 2 head))) + (byte4 (sap-ref-8 sap (+ 3 head)))) + (unless (and (<= #x80 byte2 #xbf) + (<= #x80 byte3 #xbf) + (<= #x80 byte4 #xbf)) + (return-from character-decode)) + (dpb byte (byte 3 18) + (dpb byte2 (byte 6 12) + (dpb byte3 (byte 6 6) byte4))))))) + (loop (input-at-least stream 1) + (let ((byte (sap-ref-8 (fd-stream-ibuf-sap stream) + (fd-stream-ibuf-head stream)))) + (unless (<= #x80 byte #xc1) + (return))) + (incf (fd-stream-ibuf-head stream)))) ;;;; utility functions (misc routines, etc) @@ -662,7 +1284,8 @@ (input-type nil) (output-type nil) (input-size nil) - (output-size nil)) + (output-size nil) + (character-stream-p (subtypep type 'character))) (when (fd-stream-obuf-sap fd-stream) (push (fd-stream-obuf-sap fd-stream) *available-buffers*) @@ -671,31 +1294,73 @@ (push (fd-stream-ibuf-sap fd-stream) *available-buffers*) (setf (fd-stream-ibuf-sap fd-stream) nil)) + (when (and character-stream-p + (eq (fd-stream-external-format fd-stream) :default)) + (setf (fd-stream-external-format fd-stream) + (intern (or (alien-funcall + (extern-alien "nl_langinfo" + (function c-string int)) + sb!unix:codeset) + "LATIN-1") + "KEYWORD"))) + (dolist (entry *external-formats* + (setf (fd-stream-external-format fd-stream) :latin-1)) + (when (member (fd-stream-external-format fd-stream) (first entry)) + (return))) + (when input-p - (multiple-value-bind (routine type size) - (pick-input-routine target-type) + (multiple-value-bind (routine type size read-n-characters + normalized-external-format) + (pick-input-routine target-type + (fd-stream-external-format fd-stream)) + (when normalized-external-format + (setf (fd-stream-external-format fd-stream) + normalized-external-format)) (unless routine (error "could not find any input routine for ~S" target-type)) (setf (fd-stream-ibuf-sap fd-stream) (next-available-buffer)) (setf (fd-stream-ibuf-length fd-stream) bytes-per-buffer) (setf (fd-stream-ibuf-tail fd-stream) 0) - (if (subtypep type 'character) + (if character-stream-p (setf (fd-stream-in fd-stream) routine (fd-stream-bin fd-stream) #'ill-bin) (setf (fd-stream-in fd-stream) #'ill-in (fd-stream-bin fd-stream) routine)) (when (eql size 1) - (setf (fd-stream-n-bin fd-stream) #'fd-stream-read-n-bytes) - (when buffer-p - (setf (ansi-stream-in-buffer fd-stream) - (make-array +ansi-stream-in-buffer-length+ - :element-type '(unsigned-byte 8))))) + (setf (fd-stream-n-bin fd-stream) + (if character-stream-p + read-n-characters + #'fd-stream-read-n-bytes)) + (when (and buffer-p + ;; We only create this buffer for streams of type + ;; (unsigned-byte 8). Because there's no buffer, the + ;; other element-types will dispatch to the appropriate + ;; input (output) routine in fast-read-byte. + (or character-stream-p + (equal target-type '(unsigned-byte 8))) + (not output-p) ; temporary disable on :io streams + #+(or) + (or (eq type 'unsigned-byte) + (eq type :default))) + (if character-stream-p + (setf (ansi-stream-cin-buffer fd-stream) + (make-array +ansi-stream-in-buffer-length+ + :element-type 'character)) + (setf (ansi-stream-in-buffer fd-stream) + (make-array +ansi-stream-in-buffer-length+ + :element-type '(unsigned-byte 8)))))) (setf input-size size) (setf input-type type))) (when output-p - (multiple-value-bind (routine type size) - (pick-output-routine target-type (fd-stream-buffering fd-stream)) + (multiple-value-bind (routine type size output-bytes + normalized-external-format) + (pick-output-routine target-type + (fd-stream-buffering fd-stream) + (fd-stream-external-format fd-stream)) + (when normalized-external-format + (setf (fd-stream-external-format fd-stream) + normalized-external-format)) (unless routine (error "could not find any output routine for ~S buffered ~S" (fd-stream-buffering fd-stream) @@ -703,13 +1368,15 @@ (setf (fd-stream-obuf-sap fd-stream) (next-available-buffer)) (setf (fd-stream-obuf-length fd-stream) bytes-per-buffer) (setf (fd-stream-obuf-tail fd-stream) 0) - (if (subtypep type 'character) + (when character-stream-p + (setf (fd-stream-output-bytes fd-stream) output-bytes)) + (if character-stream-p (setf (fd-stream-out fd-stream) routine (fd-stream-bout fd-stream) #'ill-bout) (setf (fd-stream-out fd-stream) (or (if (eql size 1) - (pick-output-routine 'base-char - (fd-stream-buffering fd-stream))) + (pick-output-routine + 'base-char (fd-stream-buffering fd-stream))) #'ill-out) (fd-stream-bout fd-stream) routine)) (setf (fd-stream-sout fd-stream) @@ -763,27 +1430,40 @@ (setf (fd-stream-unread fd-stream) arg1) (setf (fd-stream-listen fd-stream) t)) (:close - (cond (arg1 - ;; We got us an abort on our hands. + (cond (arg1 ; We got us an abort on our hands. (when (fd-stream-handler fd-stream) - (sb!sys:remove-fd-handler (fd-stream-handler fd-stream)) - (setf (fd-stream-handler fd-stream) nil)) + (sb!sys:remove-fd-handler (fd-stream-handler fd-stream)) + (setf (fd-stream-handler fd-stream) nil)) + ;; We can't do anything unless we know what file were + ;; dealing with, and we don't want to do anything + ;; strange unless we were writing to the file. (when (and (fd-stream-file fd-stream) (fd-stream-obuf-sap fd-stream)) - ;; We can't do anything unless we know what file were - ;; dealing with, and we don't want to do anything - ;; strange unless we were writing to the file. (if (fd-stream-original fd-stream) - ;; We have a handle on the original, just revert. - (multiple-value-bind (okay err) - (sb!unix:unix-rename (fd-stream-original fd-stream) - (fd-stream-file fd-stream)) - (unless okay - (simple-stream-perror - "couldn't restore ~S to its original contents" - fd-stream - err))) - ;; We can't restore the original, so nuke that puppy. + ;; If the original is EQ to file we are appending + ;; and can just close the file without renaming. + (unless (eq (fd-stream-original fd-stream) + (fd-stream-file fd-stream)) + ;; We have a handle on the original, just revert. + (multiple-value-bind (okay err) + (sb!unix:unix-rename (fd-stream-original fd-stream) + (fd-stream-file fd-stream)) + (unless okay + (simple-stream-perror + "couldn't restore ~S to its original contents" + fd-stream + err)))) + ;; We can't restore the original, and aren't + ;; appending, so nuke that puppy. + ;; + ;; FIXME: This is currently the fate of superseded + ;; files, and according to the CLOSE spec this is + ;; wrong. However, there seems to be no clean way to + ;; do that that doesn't involve either copying the + ;; data (bad if the :abort resulted from a full + ;; disk), or renaming the old file temporarily + ;; (probably bad because stream opening becomes more + ;; racy). (multiple-value-bind (okay err) (sb!unix:unix-unlink (fd-stream-file fd-stream)) (unless okay @@ -851,8 +1531,8 @@ (:element-type (fd-stream-element-type fd-stream)) (:interactive-p - ;; FIXME: sb!unix:unix-isatty is undefined. - (sb!unix:unix-isatty (fd-stream-fd fd-stream))) + (= 1 (the (member 0 1) + (sb!unix:unix-isatty (fd-stream-fd fd-stream))))) (:line-length 80) (:charpos @@ -882,23 +1562,23 @@ (fd-stream-file-position fd-stream arg1)))) (defun fd-stream-file-position (stream &optional newpos) - (declare (type fd-stream stream) - (type (or index (member nil :start :end)) newpos)) + (declare (type file-stream stream) + (type (or (alien sb!unix:off-t) (member nil :start :end)) newpos)) (if (null newpos) (sb!sys:without-interrupts ;; First, find the position of the UNIX file descriptor in the file. (multiple-value-bind (posn errno) (sb!unix:unix-lseek (fd-stream-fd stream) 0 sb!unix:l_incr) - (declare (type (or index null) posn)) - (cond ((fixnump posn) + (declare (type (or (alien sb!unix:off-t) null) posn)) + (cond ((integerp posn) ;; Adjust for buffered output: If there is any output ;; buffered, the *real* file position will be larger ;; than reported by lseek() because lseek() obviously ;; cannot take into account output we have not sent ;; yet. (dolist (later (fd-stream-output-later stream)) - (incf posn (- (the index (caddr later)) - (the index (cadr later))))) + (incf posn (- (caddr later) + (cadr later)))) (incf posn (fd-stream-obuf-tail stream)) ;; Adjust for unread input: If there is any input ;; read from UNIX but not supplied to the user of the @@ -919,7 +1599,7 @@ stream errno)))))) (let ((offset 0) origin) - (declare (type index offset)) + (declare (type (alien sb!unix:off-t) offset)) ;; Make sure we don't have any output pending, because if we ;; move the file pointer before writing this stuff, it will be ;; written in the wrong location. @@ -939,14 +1619,14 @@ (setf offset 0 origin sb!unix:l_set)) ((eq newpos :end) (setf offset 0 origin sb!unix:l_xtnd)) - ((typep newpos 'index) + ((typep newpos '(alien sb!unix:off-t)) (setf offset (* newpos (fd-stream-element-size stream)) origin sb!unix:l_set)) (t (error "invalid position given to FILE-POSITION: ~S" newpos))) (multiple-value-bind (posn errno) (sb!unix:unix-lseek (fd-stream-fd stream) offset origin) - (cond ((typep posn 'fixnum) + (cond ((typep posn '(alien sb!unix:off-t)) t) ((eq errno sb!unix:espipe) nil) @@ -980,6 +1660,7 @@ (output nil output-p) (element-type 'base-char) (buffering :full) + (external-format :default) timeout file original @@ -1003,6 +1684,7 @@ :delete-original delete-original :pathname pathname :buffering buffering + :external-format external-format :timeout timeout))) (set-fd-stream-routines stream element-type input output input-buffer-p) (when (and auto-close (fboundp 'finalize)) @@ -1017,8 +1699,8 @@ ;;; Pick a name to use for the backup file for the :IF-EXISTS ;;; :RENAME-AND-DELETE and :RENAME options. (defun pick-backup-name (name) - (declare (type simple-string name)) - (concatenate 'simple-string name ".bak")) + (declare (type simple-base-string name)) + (concatenate 'simple-base-string name ".bak")) ;;; Ensure that the given arg is one of the given list of valid ;;; things. Allow the user to fix any problems. @@ -1062,18 +1744,10 @@ :DIRECTION - one of :INPUT, :OUTPUT, :IO, or :PROBE :ELEMENT-TYPE - the type of object to read or write, default BASE-CHAR :IF-EXISTS - one of :ERROR, :NEW-VERSION, :RENAME, :RENAME-AND-DELETE, - :OVERWRITE, :APPEND, :SUPERSEDE or NIL - :IF-DOES-NOT-EXIST - one of :ERROR, :CREATE or nil + :OVERWRITE, :APPEND, :SUPERSEDE or NIL + :IF-DOES-NOT-EXIST - one of :ERROR, :CREATE or NIL See the manual for details." - (unless (eq external-format :default) - (error "Any external format other than :DEFAULT isn't recognized.")) - - ;; First, make sure that DIRECTION is valid. - (ensure-one-of direction - '(:input :output :io :probe) - :direction) - ;; Calculate useful stuff. (multiple-value-bind (input output mask) (case direction @@ -1082,10 +1756,12 @@ (:io (values t t sb!unix:o_rdwr)) (:probe (values t nil sb!unix:o_rdonly))) (declare (type index mask)) - (let* ((pathname (pathname filename)) + (let* ((pathname (merge-pathnames filename)) (namestring (cond ((unix-namestring pathname input)) ((and input (eq if-does-not-exist :create)) + (unix-namestring pathname nil)) + ((and (eq direction :io) (not if-does-not-exist-given)) (unix-namestring pathname nil))))) ;; Process if-exists argument if we are doing any output. (cond (output @@ -1100,11 +1776,11 @@ :append :supersede nil) :if-exists) (case if-exists - ((:error nil) + ((:new-version :error nil) (setf mask (logior mask sb!unix:o_excl))) ((:rename :rename-and-delete) (setf mask (logior mask sb!unix:o_creat))) - ((:new-version :supersede) + ((:supersede) (setf mask (logior mask sb!unix:o_trunc))) (:append (setf mask (logior mask sb!unix:o_append))))) @@ -1127,12 +1803,16 @@ (if (eq if-does-not-exist :create) (setf mask (logior mask sb!unix:o_creat))) - (let ((original (if (member if-exists - '(:rename :rename-and-delete)) - (pick-backup-name namestring))) + (let ((original (case if-exists + ((:rename :rename-and-delete) + (pick-backup-name namestring)) + ((:append) + ;; KLUDGE: Provent CLOSE from deleting + ;; appending streams when called with :ABORT T + namestring))) (delete-original (eq if-exists :rename-and-delete)) (mode #o666)) - (when original + (when (and original (not (eq original namestring))) ;; We are doing a :RENAME or :RENAME-AND-DELETE. Determine ;; whether the file already exists, make sure the original ;; file is not a directory, and keep the mode. @@ -1172,7 +1852,7 @@ (logior (logandc2 mask sb!unix:o_creat) sb!unix:o_trunc))) (setf if-exists :supersede)))) - + ;; Now we can try the actual Unix open(2). (multiple-value-bind (fd errno) (if namestring @@ -1192,6 +1872,7 @@ :input input :output output :element-type element-type + :external-format external-format :file namestring :original original :delete-original delete-original @@ -1213,7 +1894,7 @@ (open-error "~@" pathname)) (t nil))) - ((and (eql errno sb!unix:eexist) if-exists) + ((and (eql errno sb!unix:eexist) (null if-exists)) nil) (t (vanilla-open-error))))))))) @@ -1238,14 +1919,7 @@ (stream-reinit) (setf *terminal-io* (make-synonym-stream '*tty*)) (setf *standard-output* (make-synonym-stream '*stdout*)) - (setf *standard-input* - (#!-high-security - ;; FIXME: Why is *STANDARD-INPUT* a TWO-WAY-STREAM? ANSI says - ;; it's an input stream. - make-two-way-stream - #!+high-security - %make-two-way-stream (make-synonym-stream '*stdin*) - *standard-output*)) + (setf *standard-input* (make-synonym-stream '*stdin*)) (setf *error-output* (make-synonym-stream '*stderr*)) (setf *query-io* (make-synonym-stream '*terminal-io*)) (setf *debug-io* *query-io*) @@ -1261,7 +1935,8 @@ (make-fd-stream 1 :name "standard output" :output t :buffering :line)) (setf *stderr* (make-fd-stream 2 :name "standard error" :output t :buffering :line)) - (let ((tty (sb!unix:unix-open "/dev/tty" sb!unix:o_rdwr #o666))) + (let* ((ttyname #.(coerce "/dev/tty" 'simple-base-string)) + (tty (sb!unix:unix-open ttyname sb!unix:o_rdwr #o666))) (if tty (setf *tty* (make-fd-stream tty @@ -1285,7 +1960,7 @@ ;;; ;;; FIXME: misleading name, screwy interface (defun file-name (stream &optional new-name) - (when (typep stream 'fd-stream) + (when (typep stream 'file-stream) (cond (new-name (setf (fd-stream-pathname stream) new-name) (setf (fd-stream-file stream) @@ -1313,7 +1988,9 @@ (string (length object)))) (defun stream-external-format (stream) - (declare (type file-stream stream) (ignore stream)) + (declare (type file-stream stream)) #!+sb-doc - "Return :DEFAULT." - :default) + "Return the actual external format for file-streams, otherwise :DEFAULT." + (if (typep stream 'file-stream) + (fd-stream-external-format stream) + :default))