X-Git-Url: http://repo.macrolet.net/gitweb/?a=blobdiff_plain;f=src%2Fcode%2Ffd-stream.lisp;h=89bc127d3bb38512a79269d2b6d4f1edf111d6cb;hb=5cd0fc84df83d1b3321b7fc969843207721de429;hp=11a105ee38d6f9dd4e27ff5bac26f140552f3790;hpb=50eb070bdefc01733fa6b41427bbe32c7695fd71;p=sbcl.git diff --git a/src/code/fd-stream.lisp b/src/code/fd-stream.lisp index 11a105e..89bc127 100644 --- a/src/code/fd-stream.lisp +++ b/src/code/fd-stream.lisp @@ -31,16 +31,10 @@ (pop *available-buffers*) (allocate-system-memory bytes-per-buffer))) -;;;; the FILE-STREAM structure +;;;; the FD-STREAM structure -(defstruct (file-stream +(defstruct (fd-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 @@ -89,7 +83,7 @@ (pathname nil :type (or pathname null)) (external-format :default) (output-bytes #'ill-out :type function)) -(def!method print-object ((fd-stream file-stream) stream) +(def!method print-object ((fd-stream fd-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)))) @@ -126,6 +120,35 @@ :stream stream :code code)) +;;; Returning true goes into end of file handling, false will enter another +;;; round of input buffer filling followed by re-entering character decode. +(defun stream-decoding-error-and-handle (stream octet-count) + (restart-case + (stream-decoding-error stream + (let ((sap (fd-stream-ibuf-sap stream)) + (head (fd-stream-ibuf-head stream))) + (loop for i from 0 below octet-count + collect (sap-ref-8 sap (+ head i))))) + (attempt-resync () + :report (lambda (stream) + (format stream + "~@")) + (fd-stream-resync stream) + nil) + (force-end-of-file () + :report (lambda (stream) + (format stream "~@")) + t))) + +(defun stream-encoding-error-and-handle (stream code) + (restart-case + (stream-encoding-error stream code) + (output-nothing () + :report (lambda (stream) + (format stream "~@")) + (throw 'output-nothing nil)))) + ;;; 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 @@ -182,7 +205,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 file-stream stream) + (declare (type fd-stream stream) (type (or system-area-pointer (simple-array * (*))) base) (type index start end)) (if (not (null (fd-stream-output-later stream))) ; something buffered. @@ -225,11 +248,9 @@ (fd-stream-ibuf-head ,stream-var)) (file-position ,stream-var (file-position ,stream-var)))) ,(if restart - - `(with-simple-restart (output-nothing - "~@") - ,@body - (incf (fd-stream-obuf-tail ,stream-var) size)) + `(catch 'output-nothing + ,@body + (incf (fd-stream-obuf-tail ,stream-var) size)) `(progn ,@body (incf (fd-stream-obuf-tail ,stream-var) size))) @@ -255,10 +276,9 @@ (fd-stream-ibuf-head ,stream-var)) (file-position ,stream-var (file-position ,stream-var)))) ,(if restart - `(with-simple-restart (output-nothing - "~@") - ,@body - (incf (fd-stream-obuf-tail ,stream-var) ,size)) + `(catch 'output-nothing + ,@body + (incf (fd-stream-obuf-tail ,stream-var) ,size)) `(progn ,@body (incf (fd-stream-obuf-tail ,stream-var) ,size))) @@ -414,38 +434,32 @@ ((zerop bytes)) ; easy case ((<= bytes space) (if (system-area-pointer-p thing) - (system-area-copy thing - (* start sb!vm:n-byte-bits) - (fd-stream-obuf-sap fd-stream) - (* tail sb!vm:n-byte-bits) - (* bytes sb!vm:n-byte-bits)) + (system-area-ub8-copy thing start + (fd-stream-obuf-sap fd-stream) + tail + bytes) ;; FIXME: There should be some type checking somewhere to ;; verify that THING here is a vector, not just . - (copy-to-system-area thing - (+ (* start sb!vm:n-byte-bits) - (* sb!vm:vector-data-offset - sb!vm:n-word-bits)) - (fd-stream-obuf-sap fd-stream) - (* tail sb!vm:n-byte-bits) - (* bytes sb!vm:n-byte-bits))) + (copy-ub8-to-system-area thing start + (fd-stream-obuf-sap fd-stream) + tail + bytes)) (setf (fd-stream-obuf-tail fd-stream) newtail)) ((<= bytes len) (flush-output-buffer fd-stream) (if (system-area-pointer-p thing) - (system-area-copy thing - (* start sb!vm:n-byte-bits) - (fd-stream-obuf-sap fd-stream) - 0 - (* bytes sb!vm:n-byte-bits)) + (system-area-ub8-copy thing + start + (fd-stream-obuf-sap fd-stream) + 0 + bytes) ;; FIXME: There should be some type checking somewhere to ;; verify that THING here is a vector, not just . - (copy-to-system-area thing - (+ (* start sb!vm:n-byte-bits) - (* sb!vm:vector-data-offset - sb!vm:n-word-bits)) - (fd-stream-obuf-sap fd-stream) - 0 - (* bytes sb!vm:n-byte-bits))) + (copy-ub8-to-system-area thing + start + (fd-stream-obuf-sap fd-stream) + 0 + bytes)) (setf (fd-stream-obuf-tail fd-stream) bytes)) (t (flush-output-buffer fd-stream) @@ -612,8 +626,8 @@ (setf (fd-stream-ibuf-tail stream) 0)) (t (decf tail head) - (system-area-copy ibuf-sap (* head sb!vm:n-byte-bits) - ibuf-sap 0 (* tail sb!vm:n-byte-bits)) + (system-area-ub8-copy ibuf-sap head + ibuf-sap 0 tail) (setf head 0) (setf (fd-stream-ibuf-head stream) 0) (setf (fd-stream-ibuf-tail stream) tail)))) @@ -677,8 +691,7 @@ (return)) (frob-input ,stream-var))))) -(defmacro input-wrapper/variable-width ((stream bytes eof-error eof-value - resync-function) +(defmacro input-wrapper/variable-width ((stream bytes eof-error eof-value) &body read-forms) (let ((stream-var (gensym)) (retry-var (gensym)) @@ -690,47 +703,36 @@ (fd-stream-unread ,stream-var) (setf (fd-stream-unread ,stream-var) nil) (setf (fd-stream-listen ,stream-var) nil)) - (let ((,element-var nil)) + (let ((,element-var nil) + (decode-break-reason nil)) (do ((,retry-var t)) ((not ,retry-var)) - (setq ,retry-var nil) - (restart-case + (unless (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 - (if size - (loop for i from 0 below size - collect (sap-ref-8 (fd-stream-ibuf-sap + (setf decode-break-reason + (block decode-break-reason + (input-at-least ,stream-var 1) + (let* ((byte (sap-ref-8 (fd-stream-ibuf-sap ,stream-var) - (+ (fd-stream-ibuf-head - ,stream-var) - i))) - (list (sap-ref-8 (fd-stream-ibuf-sap - ,stream-var) - (fd-stream-ibuf-head - ,stream-var))))))) - (attempt-resync () - :report (lambda (stream) - (format stream - "~@")) - (,resync-function ,stream-var) - (setq ,retry-var t)) - (force-end-of-file () - :report (lambda (stream) - (format stream - "~@")) - nil))) + (fd-stream-ibuf-head + ,stream-var)))) + (setq size ,bytes) + (input-at-least ,stream-var size) + (setq ,element-var (locally ,@read-forms)) + (setq ,retry-var nil)) + nil)) + (when decode-break-reason + (stream-decoding-error-and-handle stream + decode-break-reason)) + t) + (let ((octet-count (- (fd-stream-ibuf-tail ,stream-var) + (fd-stream-ibuf-head ,stream-var)))) + (when (or (zerop octet-count) + (and (not ,element-var) + (not decode-break-reason) + (stream-decoding-error-and-handle + stream octet-count))) + (setq ,retry-var nil))))) (cond (,element-var (incf (fd-stream-ibuf-head ,stream-var) size) ,element-var) @@ -758,13 +760,11 @@ (eof-or-lose ,stream-var ,eof-error ,eof-value)))))))) (defmacro def-input-routine/variable-width (name - (type external-format size sap head - resync-function) + (type external-format size sap head) &rest body) `(progn (defun ,name (stream eof-error eof-value) - (input-wrapper/variable-width (stream ,size eof-error eof-value - ,resync-function) + (input-wrapper/variable-width (stream ,size eof-error eof-value) (let ((,sap (fd-stream-ibuf-sap stream)) (,head (fd-stream-ibuf-head stream))) ,@body))) @@ -886,10 +886,9 @@ (declare (type index start end)) (let* ((length (- end start)) (string (make-string length))) - (copy-from-system-area sap (* start sb!vm:n-byte-bits) - string (* sb!vm:vector-data-offset - sb!vm:n-word-bits) - (* length sb!vm:n-byte-bits)) + (copy-ub8-from-system-area sap start + string 0 + length) string)) ;;; the N-BIN method for FD-STREAMs @@ -899,7 +898,7 @@ ;;; isn't too problematical. (defun fd-stream-read-n-bytes (stream buffer start requested eof-error-p &aux (total-copied 0)) - (declare (type file-stream stream)) + (declare (type fd-stream stream)) (declare (type index start requested total-copied)) (let ((unread (fd-stream-unread stream))) (when unread @@ -971,6 +970,12 @@ (fd-stream-ibuf-tail stream) (+ count new-head)) count))) +(defun fd-stream-resync (stream) + (dolist (entry *external-formats*) + (when (member (fd-stream-external-format stream) (first entry)) + (return-from fd-stream-resync + (funcall (symbol-function (eighth entry)) stream))))) + (defmacro define-external-format (external-format size output-restart out-expr in-expr) (let* ((name (first external-format)) @@ -1000,12 +1005,11 @@ (tail (fd-stream-obuf-tail stream))) ((or (= start end) (< (- len tail) 4)) tail) ,(if output-restart - `(with-simple-restart (output-nothing - "~@") - (let* ((byte (aref string start)) - (bits (char-code byte))) - ,out-expr - (incf tail ,size))) + `(catch 'output-nothing + (let* ((byte (aref string start)) + (bits (char-code byte))) + ,out-expr + (incf tail ,size))) `(let* ((byte (aref string start)) (bits (char-code byte))) ,out-expr @@ -1030,7 +1034,7 @@ ,out-expr)) (defun ,in-function (stream buffer start requested eof-error-p &aux (total-copied 0)) - (declare (type file-stream stream)) + (declare (type fd-stream stream)) (declare (type index start requested total-copied)) (let ((unread (fd-stream-unread stream))) (when unread @@ -1108,12 +1112,20 @@ (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)))) + ,(if output-restart + `(catch 'output-nothing + (let* ((byte (aref string start)) + (bits (char-code byte)) + (size ,out-size-expr)) + ,out-expr + (incf tail size) + (incf start))) + `(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 @@ -1134,7 +1146,7 @@ ,out-expr)) (defun ,in-function (stream buffer start requested eof-error-p &aux (total-copied 0)) - (declare (type file-stream stream)) + (declare (type fd-stream stream)) (declare (type index start requested total-copied)) (let ((unread (fd-stream-unread stream))) (when unread @@ -1146,55 +1158,43 @@ (nil) (let* ((head (fd-stream-ibuf-head stream)) (tail (fd-stream-ibuf-tail stream)) - (sap (fd-stream-ibuf-sap stream))) + (sap (fd-stream-ibuf-sap stream)) + (head-start head) + (decode-break-reason nil)) (declare (type index head tail)) ;; Copy data from stream buffer into user's buffer. (do ((size nil nil)) ((or (= tail head) (= requested total-copied))) - (restart-case - (unless (block character-decode - (let ((byte (sap-ref-8 sap head))) - (setq 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 - (if size - (loop for i from 0 below size - collect (sap-ref-8 (fd-stream-ibuf-sap - stream) - (+ (fd-stream-ibuf-head - stream) - i))) - (list (sap-ref-8 (fd-stream-ibuf-sap stream) - (fd-stream-ibuf-head stream))))))) - (attempt-resync () - :report (lambda (stream) - (format stream - "~@")) - (,resync-function stream) - (setf head (fd-stream-ibuf-head stream))) - (force-end-of-file () - :report (lambda (stream) - (format stream "~@")) + (setf decode-break-reason + (block decode-break-reason + (let ((byte (sap-ref-8 sap head))) + (setq size ,in-size-expr) + (when (> size (- tail head)) + (return)) + (setf (aref buffer (+ start total-copied)) ,in-expr) + (incf total-copied) + (incf head size)) + nil)) + (setf (fd-stream-ibuf-head stream) head) + (when (and decode-break-reason + (= head head-start)) + (when (stream-decoding-error-and-handle + stream decode-break-reason) (if eof-error-p (error 'end-of-file :stream stream) - (return-from ,in-function total-copied))))) + (return-from ,in-function total-copied))) + (setf head (fd-stream-ibuf-head stream)) + (setf tail (fd-stream-ibuf-tail stream))) + (when (plusp total-copied) + (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)) + (or (eq decode-break-reason 'eof) + (zerop (refill-fd-stream-buffer stream))) (if eof-error-p (error 'end-of-file :stream stream) (return total-copied))) @@ -1204,19 +1204,19 @@ (def-input-routine/variable-width ,in-char-function (character ,external-format ,in-size-expr - sap head - ,resync-function) + sap head) (let ((byte (sap-ref-8 sap head))) ,in-expr)) (defun ,resync-function (stream) (loop (input-at-least stream 1) (incf (fd-stream-ibuf-head stream)) - (when (block character-decode - (let* ((sap (fd-stream-ibuf-sap stream)) - (head (fd-stream-ibuf-head stream)) - (byte (sap-ref-8 sap head)) - (size ,in-size-expr)) - ,in-expr)) + (unless (block decode-break-reason + (let* ((sap (fd-stream-ibuf-sap stream)) + (head (fd-stream-ibuf-head stream)) + (byte (sap-ref-8 sap head)) + (size ,in-size-expr)) + ,in-expr) + nil) (return)))) (setf *external-formats* (cons '(,external-format ,in-function ,in-char-function ,out-function @@ -1230,17 +1230,49 @@ (define-external-format (:latin-1 :latin1 :iso-8859-1) 1 t (if (>= bits 256) - (stream-encoding-error stream bits) + (stream-encoding-error-and-handle stream bits) (setf (sap-ref-8 sap tail) bits)) (code-char byte)) (define-external-format (:ascii :us-ascii :ansi_x3.4-1968) 1 t (if (>= bits 128) - (stream-encoding-error stream bits) + (stream-encoding-error-and-handle stream bits) (setf (sap-ref-8 sap tail) bits)) (code-char byte)) +(let* ((table (let ((s (make-string 256))) + (map-into s #'code-char + '(#x00 #x01 #x02 #x03 #x9c #x09 #x86 #x7f #x97 #x8d #x8e #x0b #x0c #x0d #x0e #x0f + #x10 #x11 #x12 #x13 #x9d #x85 #x08 #x87 #x18 #x19 #x92 #x8f #x1c #x1d #x1e #x1f + #x80 #x81 #x82 #x83 #x84 #x0a #x17 #x1b #x88 #x89 #x8a #x8b #x8c #x05 #x06 #x07 + #x90 #x91 #x16 #x93 #x94 #x95 #x96 #x04 #x98 #x99 #x9a #x9b #x14 #x15 #x9e #x1a + #x20 #xa0 #xe2 #xe4 #xe0 #xe1 #xe3 #xe5 #xe7 #xf1 #xa2 #x2e #x3c #x28 #x2b #x7c + #x26 #xe9 #xea #xeb #xe8 #xed #xee #xef #xec #xdf #x21 #x24 #x2a #x29 #x3b #xac + #x2d #x2f #xc2 #xc4 #xc0 #xc1 #xc3 #xc5 #xc7 #xd1 #xa6 #x2c #x25 #x5f #x3e #x3f + #xf8 #xc9 #xca #xcb #xc8 #xcd #xce #xcf #xcc #x60 #x3a #x23 #x40 #x27 #x3d #x22 + #xd8 #x61 #x62 #x63 #x64 #x65 #x66 #x67 #x68 #x69 #xab #xbb #xf0 #xfd #xfe #xb1 + #xb0 #x6a #x6b #x6c #x6d #x6e #x6f #x70 #x71 #x72 #xaa #xba #xe6 #xb8 #xc6 #xa4 + #xb5 #x7e #x73 #x74 #x75 #x76 #x77 #x78 #x79 #x7a #xa1 #xbf #xd0 #xdd #xde #xae + #x5e #xa3 #xa5 #xb7 #xa9 #xa7 #xb6 #xbc #xbd #xbe #x5b #x5d #xaf #xa8 #xb4 #xd7 + #x7b #x41 #x42 #x43 #x44 #x45 #x46 #x47 #x48 #x49 #xad #xf4 #xf6 #xf2 #xf3 #xf5 + #x7d #x4a #x4b #x4c #x4d #x4e #x4f #x50 #x51 #x52 #xb9 #xfb #xfc #xf9 #xfa #xff + #x5c #xf7 #x53 #x54 #x55 #x56 #x57 #x58 #x59 #x5a #xb2 #xd4 #xd6 #xd2 #xd3 #xd5 + #x30 #x31 #x32 #x33 #x34 #x35 #x36 #x37 #x38 #x39 #xb3 #xdb #xdc #xd9 #xda #x9f)) + s)) + (reverse-table (let ((rt (make-array 256 :element-type '(unsigned-byte 8) :initial-element 0))) + (loop for char across table for i from 0 + do (aver (= 0 (aref rt (char-code char)))) + do (setf (aref rt (char-code char)) i)) + rt))) + (define-external-format (:ebcdic-us :ibm-037 :ibm037) + 1 t + (if (>= bits 256) + (stream-encoding-error-and-handle stream bits) + (setf (sap-ref-8 sap tail) (aref reverse-table bits))) + (aref table byte))) + + #!+sb-unicode (let ((latin-9-table (let ((table (make-string 256))) (do ((i 0 (1+ i))) @@ -1267,10 +1299,10 @@ (if (< bits 256) (if (= bits (char-code (aref latin-9-table bits))) bits - (stream-encoding-error stream byte)) + (stream-encoding-error-and-handle 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)))) + (stream-encoding-error-and-handle stream byte)))) (aref latin-9-table byte))) (define-external-format/variable-width (:utf-8 :utf8) nil @@ -1291,7 +1323,7 @@ (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 #xc2) (return-from decode-break-reason 1)) ((< byte #xe0) 2) ((< byte #xf0) 3) (t 4)) @@ -1299,13 +1331,13 @@ (1 byte) (2 (let ((byte2 (sap-ref-8 sap (1+ head)))) (unless (<= #x80 byte2 #xbf) - (return-from character-decode)) + (return-from decode-break-reason 2)) (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)) + (return-from decode-break-reason 3)) (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))) @@ -1313,7 +1345,7 @@ (unless (and (<= #x80 byte2 #xbf) (<= #x80 byte3 #xbf) (<= #x80 byte4 #xbf)) - (return-from character-decode)) + (return-from decode-break-reason 4)) (dpb byte (byte 3 18) (dpb byte2 (byte 6 12) (dpb byte3 (byte 6 6) byte4)))))))) @@ -1595,7 +1627,7 @@ ;; appropriate value for the EXPECTED-TYPE slot.. (error 'simple-type-error :datum fd-stream - :expected-type 'file-stream + :expected-type 'fd-stream :format-control "~S is not a stream associated with a file." :format-arguments (list fd-stream))) (multiple-value-bind (okay dev ino mode nlink uid gid rdev size @@ -1612,7 +1644,7 @@ (fd-stream-file-position fd-stream arg1)))) (defun fd-stream-file-position (stream &optional newpos) - (declare (type file-stream stream) + (declare (type fd-stream stream) (type (or (alien sb!unix:off-t) (member nil :start :end)) newpos)) (if (null newpos) (sb!sys:without-interrupts @@ -2010,7 +2042,7 @@ ;;; ;;; FIXME: misleading name, screwy interface (defun file-name (stream &optional new-name) - (when (typep stream 'file-stream) + (when (typep stream 'fd-stream) (cond (new-name (setf (fd-stream-pathname stream) new-name) (setf (fd-stream-file stream) @@ -2027,7 +2059,7 @@ ;;;; COMMON-LISP.) (defun file-string-length (stream object) - (declare (type (or string character) object) (type file-stream stream)) + (declare (type (or string character) object) (type fd-stream stream)) #!+sb-doc "Return the delta in STREAM's FILE-POSITION that would be caused by writing OBJECT to STREAM. Non-trivial only in implementations that support @@ -2038,9 +2070,9 @@ (string (length object)))) (defun stream-external-format (stream) - (declare (type file-stream stream)) + (declare (type fd-stream stream)) #!+sb-doc - "Return the actual external format for file-streams, otherwise :DEFAULT." - (if (typep stream 'file-stream) + "Return the actual external format for fd-streams, otherwise :DEFAULT." + (if (typep stream 'fd-stream) (fd-stream-external-format stream) :default))