0.8.7.19:
[sbcl.git] / src / code / stream.lisp
index 807c422..63b3fa3 100644 (file)
 
 (in-package "SB!IMPL")
 
-(deftype string-stream ()
-  '(or string-input-stream string-output-stream
-       fill-pointer-output-stream))
-
 ;;;; standard streams
 
 ;;; The initialization of these streams is performed by
 \f
 ;;; stream manipulation functions
 
-(defun input-stream-p (stream)
-  (declare (type stream stream))
+(declaim (inline ansi-stream-input-stream-p))
+(defun ansi-stream-input-stream-p (stream)
+  (declare (type ansi-stream stream))
 
   #!+high-security
   (when (synonym-stream-p stream)
     (setf stream
          (symbol-value (synonym-stream-symbol stream))))
 
-  (and (ansi-stream-p stream)
-       (not (eq (ansi-stream-in stream) #'closed-flame))
+  (and (not (eq (ansi-stream-in stream) #'closed-flame))
        ;;; KLUDGE: It's probably not good to have EQ tests on function
        ;;; values like this. What if someone's redefined the function?
        ;;; Is there a better way? (Perhaps just VALID-FOR-INPUT and
        (or (not (eq (ansi-stream-in stream) #'ill-in))
           (not (eq (ansi-stream-bin stream) #'ill-bin)))))
 
-(defun output-stream-p (stream)
+(defun input-stream-p (stream)
   (declare (type stream stream))
+  (and (ansi-stream-p stream)
+       (ansi-stream-input-stream-p stream)))
+
+(declaim (inline ansi-stream-output-stream-p))
+(defun ansi-stream-output-stream-p (stream)
+  (declare (type ansi-stream stream))
 
   #!+high-security
   (when (synonym-stream-p stream)
     (setf stream (symbol-value
                  (synonym-stream-symbol stream))))
 
-  (and (ansi-stream-p stream)
-       (not (eq (ansi-stream-in stream) #'closed-flame))
+  (and (not (eq (ansi-stream-in stream) #'closed-flame))
        (or (not (eq (ansi-stream-out stream) #'ill-out))
           (not (eq (ansi-stream-bout stream) #'ill-bout)))))
 
-(defun open-stream-p (stream)
+(defun output-stream-p (stream)
   (declare (type stream stream))
+
+  (and (ansi-stream-p stream)
+       (ansi-stream-output-stream-p stream)))
+
+(declaim (inline ansi-stream-open-stream-p))
+(defun ansi-stream-open-stream-p (stream)
+  (declare (type ansi-stream stream))
   (not (eq (ansi-stream-in stream) #'closed-flame)))
 
-(defun stream-element-type (stream)
-  (declare (type stream stream))
+(defun open-stream-p (stream)
+  (ansi-stream-open-stream-p stream))
+
+(declaim (inline ansi-stream-element-type))
+(defun ansi-stream-element-type (stream)
+  (declare (type ansi-stream stream))
   (funcall (ansi-stream-misc stream) stream :element-type))
 
+(defun stream-element-type (stream)
+  (ansi-stream-element-type stream))
+
 (defun interactive-stream-p (stream)
   (declare (type stream stream))
   (funcall (ansi-stream-misc stream) stream :interactive-p))
 
-(defun close (stream &key abort)
-  (declare (type stream stream))
+(declaim (inline ansi-stream-close))
+(defun ansi-stream-close (stream abort)
+  (declare (type ansi-stream stream))
   (when (open-stream-p stream)
     (funcall (ansi-stream-misc stream) stream :close abort))
   t)
 
+(defun close (stream &key abort)
+  (ansi-stream-close stream abort))
+
 (defun set-closed-flame (stream)
   (setf (ansi-stream-in stream) #'closed-flame)
   (setf (ansi-stream-bin stream) #'closed-flame)
 ;;; Call the MISC method with the :FILE-POSITION operation.
 (defun file-position (stream &optional position)
   (declare (type stream stream))
-  (declare (type (or index (member nil :start :end)) position))
+  (declare (type (or index (alien sb!unix:off-t) (member nil :start :end)) position))
   (cond
    (position
     (setf (ansi-stream-in-index stream) +ansi-stream-in-buffer-length+)
           ;; private predicate function..) is ugly and confusing, but
           ;; I can't see any other way. -- WHN 2001-04-14
           :expected-type '(satisfies stream-associated-with-file-p)
-          :format-string
+          :format-control
           "~@<The stream ~2I~_~S ~I~_isn't associated with a file.~:>"
           :format-arguments (list stream))))
 
 ;;; like FILE-POSITION, only using :FILE-LENGTH
 (defun file-length (stream)
-  (declare (type (or file-stream synonym-stream) stream))
+  ;; FIXME: The following declaration uses yet undefined types, which
+  ;; cause cross-compiler hangup.
+  ;;
+  ;; (declare (type (or file-stream synonym-stream) stream))
   (stream-must-be-associated-with-file stream)
   (funcall (ansi-stream-misc stream) stream :file-length))
 \f
        (stream-unread-char stream character)))
   nil)
 
-
-;;; In the interest of ``once and only once'' this macro contains the
-;;; framework necessary to implement a peek-char function, which has
-;;; two special-cases (one for gray streams and one for echo streams)
-;;; in addition to the normal case.
-;;;
-;;; All arguments are forms which will be used for a specific purpose
-;;; PEEK-TYPE - the current peek-type as defined by ANSI CL
-;;; EOF-VALUE - the eof-value argument to peek-char
-;;; CHAR-VAR - the variable which will be used to store the current character
-;;; READ-FORM - the form which will be used to read a character
-;;; UNREAD-FORM - ditto for unread-char
-;;; SKIPPED-CHAR-FORM - the form to execute when skipping a character
-;;; EOF-DETECTED-FORM - the form to execute when EOF has been detected
-;;;                     (this will default to CHAR-VAR)
-(defmacro generalized-peeking-mechanism (peek-type eof-value char-var read-form unread-form &optional (skipped-char-form nil) (eof-detected-form nil))
-  `(let ((,char-var ,read-form))
-    (cond ((eql ,char-var ,eof-value) 
-          ,(if eof-detected-form
-               eof-detected-form
-               char-var))
-         ((characterp ,peek-type)
-          (do ((,char-var ,char-var ,read-form))
-              ((or (eql ,char-var ,eof-value) 
-                   (char= ,char-var ,peek-type))
-               (cond ((eql ,char-var ,eof-value)
-                      ,(if eof-detected-form
-                           eof-detected-form
-                           char-var))
-                     (t ,unread-form
-                        ,char-var)))
-            ,skipped-char-form))
-         ((eql ,peek-type t)
-          (do ((,char-var ,char-var ,read-form))
-              ((or (eql ,char-var ,eof-value)
-                   (not (whitespace-char-p ,char-var)))
-               (cond ((eql ,char-var ,eof-value)
-                      ,(if eof-detected-form
-                           eof-detected-form
-                           char-var))
-                     (t ,unread-form
-                        ,char-var)))
-            ,skipped-char-form))
-         ((null ,peek-type)
-          ,unread-form
-          ,char-var)
-         (t
-          (bug "Impossible case reached in PEEK-CHAR")))))
-
-(defun peek-char (&optional (peek-type nil)
-                           (stream *standard-input*)
-                           (eof-error-p t)
-                           eof-value
-                           recursive-p)
-  (declare (ignore recursive-p))
-  ;; FIXME: The type of PEEK-TYPE is also declared in a DEFKNOWN, but
-  ;; the compiler doesn't seem to be smart enough to go from there to
-  ;; imposing a type check. Figure out why (because PEEK-TYPE is an
-  ;; &OPTIONAL argument?) and fix it, and then this explicit type
-  ;; check can go away.
-  (unless (typep peek-type '(or character boolean))
-    (error 'simple-type-error
-          :datum peek-type
-          :expected-type '(or character boolean)
-          :format-control "~@<bad PEEK-TYPE=~S, ~_expected ~S~:>"
-          :format-arguments (list peek-type '(or character boolean))))
-  (let ((stream (in-synonym-of stream)))
-    (cond ((typep stream 'echo-stream)
-          (echo-misc stream 
-                     :peek-char
-                     peek-type
-                     (list eof-error-p eof-value)))
-         ((ansi-stream-p stream)
-          (generalized-peeking-mechanism
-           peek-type eof-value char
-           (read-char stream eof-error-p eof-value)
-           (unread-char char stream)))
-         (t
-          ;; by elimination, must be Gray streams FUNDAMENTAL-STREAM
-          (generalized-peeking-mechanism
-           peek-type :eof char
-           (if (null peek-type)
-               (stream-peek-char stream)
-               (stream-read-char stream))
-           (if (null peek-type)
-               ()
-               (stream-unread-char stream char))
-           ()
-           (eof-or-lose stream eof-error-p eof-value))))))
-
 (defun listen (&optional (stream *standard-input*))
   (let ((stream (in-synonym-of stream)))
     (if (ansi-stream-p stream)
        (stream-fresh-line stream))))
 
 (defun write-string (string &optional (stream *standard-output*)
-                           &key (start 0) (end nil))
-  (%write-string string stream start (or end (length string)))
-  string)
-
-(defun %write-string (string stream start end)
+                           &key (start 0) end)
   (declare (type string string))
-  (declare (type streamlike stream))
-  (declare (type index start end))
-
   ;; Note that even though you might expect, based on the behavior of
   ;; things like AREF, that the correct upper bound here is
   ;; (ARRAY-DIMENSION STRING 0), the ANSI glossary definitions for
   ;; "bounding index" and "length" indicate that in this case (i.e.
-  ;; for the ANSI-specified functions WRITE-STRING and WRITE-LINE
-  ;; which are implemented in terms of this function), (LENGTH STRING)
-  ;; is the required upper bound. A foolish consistency is the
-  ;; hobgoblin of lesser languages..
-  (unless (<= 0 start end (length string))
-    (error "~@<bad bounding indices START=~W END=~W for ~2I~_~S~:>"
-          start
-          end
-          string))
+  ;; for the ANSI-specified functions WRITE-STRING [and WRITE-LINE]),
+  ;; (LENGTH STRING) is the required upper bound. A foolish
+  ;; consistency is the hobgoblin of lesser languages..
+  (%write-string string stream start (%check-vector-sequence-bounds
+                                     string start end))
+  string)
 
+(defun %write-string (string stream start end)
+  (declare (type string string))
+  (declare (type streamlike stream))
+  (declare (type index start end))
   (let ((stream (out-synonym-of stream)))
     (cond ((ansi-stream-p stream)
           (if (array-header-p string)
          (t ; must be Gray streams FUNDAMENTAL-STREAM
           (stream-write-string stream string start end)))))
 
+;;; A wrapper function for all those (MACROLET OUT-FUN) definitions,
+;;; which cannot deal with keyword arguments.
+(declaim (inline write-string-no-key))
+(defun write-string-no-key (string stream start end)
+  (write-string string stream :start start :end end))
+
 (defun write-line (string &optional (stream *standard-output*)
-                         &key (start 0) (end nil))
-  (let ((defaulted-stream (out-synonym-of stream))
-       (defaulted-end (or end (length string))))
-    (%write-string string defaulted-stream start defaulted-end)
+                         &key (start 0) end)
+  (declare (type string string))
+  ;; FIXME: Why is there this difference between the treatments of the
+  ;; STREAM argument in WRITE-STRING and WRITE-LINE?
+  (let ((defaulted-stream (out-synonym-of stream)))
+    (%write-string string defaulted-stream start (%check-vector-sequence-bounds
+                                                 string start end))
     (write-char #\newline defaulted-stream))
   string)
 
                   (stream-write-byte integer))
   integer)
 \f
+
+;;; (These were inline throughout this file, but that's not appropriate
+;;; globally.  And we must not inline them in the rest of this file if
+;;; dispatch to gray or simple streams is to work, since both redefine
+;;; these functions later.)
+(declaim (maybe-inline read-char unread-char read-byte listen))
+
 ;;; This is called from ANSI-STREAM routines that encapsulate CLOS
 ;;; streams to handle the misc routines and dispatch to the
-;;; appropriate Gray stream functions.
+;;; appropriate SIMPLE- or FUNDAMENTAL-STREAM functions.
 (defun stream-misc-dispatch (stream operation &optional arg1 arg2)
-  (declare (type fundamental-stream stream)
-          (ignore arg2))
-  (case operation
+  (declare (type stream stream) (ignore arg2))
+  (ecase operation
     (:listen
      ;; Return T if input available, :EOF for end-of-file, otherwise NIL.
-     (let ((char (stream-read-char-no-hang stream)))
+     (let ((char (read-char-no-hang stream nil :eof)))
        (when (characterp char)
-        (stream-unread-char stream char))
+        (unread-char char stream))
        char))
     (:unread
-     (stream-unread-char stream arg1))
+     (unread-char arg1 stream))
     (:close
      (close stream))
     (:clear-input
-     (stream-clear-input stream))
+     (clear-input stream))
     (:force-output
-     (stream-force-output stream))
+     (force-output stream))
     (:finish-output
-     (stream-finish-output stream))
+     (finish-output stream))
     (:element-type
      (stream-element-type stream))
     (:interactive-p
      (interactive-stream-p stream))
     (:line-length
-     (stream-line-length stream))
+     (line-length stream))
     (:charpos
-     (stream-line-column stream))
+     (charpos stream))
     (:file-length
      (file-length stream))
     (:file-position
             :expected-type '(satisfies output-stream-p))))
   (apply #'%make-broadcast-stream streams))
 
-(macrolet ((out-fun (fun method stream-method &rest args)
-            `(defun ,fun (stream ,@args)
+(macrolet ((out-fun (name fun &rest args)
+            `(defun ,name (stream ,@args)
                (dolist (stream (broadcast-stream-streams stream))
-                 (if (ansi-stream-p stream)
-                     (funcall (,method stream) stream ,@args)
-                     (,stream-method stream ,@args))))))
-  (out-fun broadcast-out ansi-stream-out stream-write-char char)
-  (out-fun broadcast-bout ansi-stream-bout stream-write-byte byte)
-  (out-fun broadcast-sout ansi-stream-sout stream-write-string
-          string start end))
+                 (,fun ,(car args) stream ,@(cdr args))))))
+  (out-fun broadcast-out write-char char)
+  (out-fun broadcast-bout write-byte byte)
+  (out-fun broadcast-sout write-string-no-key string start end))
 
 (defun broadcast-misc (stream operation &optional arg1 arg2)
   (let ((streams (broadcast-stream-streams stream)))
   (print-unreadable-object (x stream :type t :identity t)
     (format stream ":SYMBOL ~S" (synonym-stream-symbol x))))
 
-;;; The output simple output methods just call the corresponding method
-;;; in the synonymed stream.
-(macrolet ((out-fun (name slot stream-method &rest args)
+;;; The output simple output methods just call the corresponding
+;;; function on the synonymed stream.
+(macrolet ((out-fun (name fun &rest args)
             `(defun ,name (stream ,@args)
                (declare (optimize (safety 1)))
                (let ((syn (symbol-value (synonym-stream-symbol stream))))
-                 (if (ansi-stream-p syn)
-                     (funcall (,slot syn) syn ,@args)
-                     (,stream-method syn ,@args))))))
-  (out-fun synonym-out ansi-stream-out stream-write-char ch)
-  (out-fun synonym-bout ansi-stream-bout stream-write-byte n)
-  (out-fun synonym-sout ansi-stream-sout stream-write-string string start end))
+                 (,fun ,(car args) syn ,@(cdr args))))))
+  (out-fun synonym-out write-char ch)
+  (out-fun synonym-bout write-byte n)
+  (out-fun synonym-sout write-string-no-key string start end))
 
 ;;; For the input methods, we just call the corresponding function on the
 ;;; synonymed stream. These functions deal with getting input out of
           :expected-type '(satisfies input-stream-p)))
   (funcall #'%make-two-way-stream input-stream output-stream))
 
-(macrolet ((out-fun (name slot stream-method &rest args)
+(macrolet ((out-fun (name fun &rest args)
             `(defun ,name (stream ,@args)
                (let ((syn (two-way-stream-output-stream stream)))
-                 (if (ansi-stream-p syn)
-                     (funcall (,slot syn) syn ,@args)
-                     (,stream-method syn ,@args))))))
-  (out-fun two-way-out ansi-stream-out stream-write-char ch)
-  (out-fun two-way-bout ansi-stream-bout stream-write-byte n)
-  (out-fun two-way-sout ansi-stream-sout stream-write-string string start end))
+                 (,fun ,(car args) syn ,@(cdr args))))))
+  (out-fun two-way-out write-char ch)
+  (out-fun two-way-bout write-byte n)
+  (out-fun two-way-sout write-string-no-key string start end))
 
 (macrolet ((in-fun (name fun &rest args)
             `(defun ,name (stream ,@args)
                  (let* ((stream (car current))
                         (result (,fun stream nil nil)))
                    (when result (return result)))
-                 (setf (concatenated-stream-current stream) current)))))
+                 (pop (concatenated-stream-current stream))))))
   (in-fun concatenated-in read-char)
   (in-fun concatenated-bin read-byte))
 
           :expected-type '(satisfies input-stream-p)))
   (funcall #'%make-echo-stream input-stream output-stream))
 
-(macrolet ((in-fun (name fun out-slot stream-method &rest args)
+(macrolet ((in-fun (name in-fun out-fun &rest args)
             `(defun ,name (stream ,@args)
                (or (pop (echo-stream-unread-stuff stream))
                    (let* ((in (echo-stream-input-stream stream))
                           (out (echo-stream-output-stream stream))
-                          (result (,fun in ,@args)))
-                     (if (ansi-stream-p out)
-                         (funcall (,out-slot out) out result)
-                         (,stream-method out result))
+                          (result (,in-fun in ,@args)))
+                     (,out-fun result out)
                      result)))))
-  (in-fun echo-in read-char ansi-stream-out stream-write-char
-         eof-error-p eof-value)
-  (in-fun echo-bin read-byte ansi-stream-bout stream-write-byte
-         eof-error-p eof-value))
-
-
-(defun echo-misc (stream operation &optional arg1 arg2)
-  (let* ((in (two-way-stream-input-stream stream))
-        (out (two-way-stream-output-stream stream)))
-    (case operation
-      (:listen
-       (or (not (null (echo-stream-unread-stuff stream)))
-          (if (ansi-stream-p in)
-              (or (/= (the fixnum (ansi-stream-in-index in))
-                      +ansi-stream-in-buffer-length+)
-                  (funcall (ansi-stream-misc in) in :listen))
-              (stream-misc-dispatch in :listen))))
-      (:unread (push arg1 (echo-stream-unread-stuff stream)))
-      (:element-type
-       (let ((in-type (stream-element-type in))
-            (out-type (stream-element-type out)))
-        (if (equal in-type out-type)
-            in-type `(and ,in-type ,out-type))))
-      (:close
-       (set-closed-flame stream))
-      (:peek-char
-       ;; For the special case of peeking into an echo-stream
-       ;; arg1 is peek-type, arg2 is (eof-error-p eof-value)
-       ;; returns peeked-char, eof-value, or errors end-of-file
-       (flet ((outfn (c)
-               (if (ansi-stream-p out)
-                   (funcall (ansi-stream-out out) out c)
-                   ;; gray-stream
-                   (stream-write-char out c))))
-        (generalized-peeking-mechanism
-         arg1 (second arg2) char
-         (read-char in (first arg2) (second arg2))
-         (unread-char char in)
-         (outfn char))))
-      (t
-       (or (if (ansi-stream-p in)
-              (funcall (ansi-stream-misc in) in operation arg1 arg2)
-              (stream-misc-dispatch in operation arg1 arg2))
-          (if (ansi-stream-p out)
-              (funcall (ansi-stream-misc out) out operation arg1 arg2)
-              (stream-misc-dispatch out operation arg1 arg2)))))))
-
+  (in-fun echo-in read-char write-char eof-error-p eof-value)
+  (in-fun echo-bin read-byte write-byte eof-error-p eof-value))
+\f
+;;;; base STRING-STREAM stuff
+
+(defstruct (string-stream
+             (:include ansi-stream)
+             (:constructor nil)
+             (:copier nil))
+  ;; FIXME: This type declaration is true, and will probably continue
+  ;; to be true.  However, note well the comments in DEFTRANSFORM
+  ;; REPLACE, implying that performance of REPLACE is somewhat
+  ;; critical to performance of string streams.  If (VECTOR CHARACTER)
+  ;; ever becomes different from (VECTOR BASE-CHAR), the transform
+  ;; probably needs to be extended.
+  (string (missing-arg) :type (vector character)))
 \f
-;;;; string input streams
+;;;; STRING-INPUT-STREAM stuff
 
 (defstruct (string-input-stream
-            (:include ansi-stream
+            (:include string-stream
                       (in #'string-inch)
-                      (bin #'string-binch)
+                      (bin #'ill-bin)
                       (n-bin #'string-stream-read-n-bytes)
-                      (misc #'string-in-misc))
+                      (misc #'string-in-misc)
+                       (string (missing-arg) :type simple-string))
             (:constructor internal-make-string-input-stream
                           (string current end))
             (:copier nil))
-  (string nil :type simple-string)
-  (current nil :type index)
-  (end nil :type index))
+  (current (missing-arg) :type index)
+  (end (missing-arg) :type index))
 
 (defun string-inch (stream eof-error-p eof-value)
+  (declare (type string-input-stream stream))
   (let ((string (string-input-stream-string stream))
        (index (string-input-stream-current stream)))
-    (declare (simple-string string) (fixnum index))
-    (cond ((= index (the index (string-input-stream-end stream)))
+    (cond ((>= index (the index (string-input-stream-end stream)))
           (eof-or-lose stream eof-error-p eof-value))
          (t
           (setf (string-input-stream-current stream) (1+ index))
-          (aref string index)))))
+          (char string index)))))
 
 (defun string-binch (stream eof-error-p eof-value)
+  (declare (type string-input-stream stream))
   (let ((string (string-input-stream-string stream))
        (index (string-input-stream-current stream)))
-    (declare (simple-string string)
-            (type index index))
-    (cond ((= index (the index (string-input-stream-end stream)))
+    (cond ((>= index (the index (string-input-stream-end stream)))
           (eof-or-lose stream eof-error-p eof-value))
          (t
           (setf (string-input-stream-current stream) (1+ index))
-          (char-code (aref string index))))))
+          (char-code (char string index))))))
 
 (defun string-stream-read-n-bytes (stream buffer start requested eof-error-p)
   (declare (type string-input-stream stream)
         (index (string-input-stream-current stream))
         (available (- (string-input-stream-end stream) index))
         (copy (min available requested)))
-    (declare (simple-string string)
-            (type index index available copy))
+    (declare (type simple-string string))
     (when (plusp copy)
       (setf (string-input-stream-current stream)
            (truly-the index (+ index copy)))
        copy)))
 
 (defun string-in-misc (stream operation &optional arg1 arg2)
-  (declare (ignore arg2))
+  (declare (type string-input-stream stream)
+          (ignore arg2))
   (case operation
     (:file-position
      (if arg1
-        (setf (string-input-stream-current stream) arg1)
+        (setf (string-input-stream-current stream)
+              (case arg1
+                (:start 0)
+                (:end (string-input-stream-end stream))
+                ;; We allow moving position beyond EOF. Errors happen
+                ;; on read, not move -- or the user may extend the
+                ;; input string.
+                (t arg1)))
         (string-input-stream-current stream)))
-    (:file-length (length (string-input-stream-string stream)))
+    ;; According to ANSI: "Should signal an error of type type-error
+    ;; if stream is not a stream associated with a file."
+    ;; This is checked by FILE-LENGTH, so no need to do it here either.
+    ;; (:file-length (length (string-input-stream-string stream)))
     (:unread (decf (string-input-stream-current stream)))
-    (:listen (or (/= (the fixnum (string-input-stream-current stream))
-                    (the fixnum (string-input-stream-end stream)))
+    (:listen (or (/= (the index (string-input-stream-current stream))
+                    (the index (string-input-stream-end stream)))
                 :eof))
-    (:element-type 'base-char)))
+    (:element-type (array-element-type (string-input-stream-string stream)))))
 
-(defun make-string-input-stream (string &optional
-                                       (start 0) (end (length string)))
+(defun make-string-input-stream (string &optional (start 0) end)
   #!+sb-doc
   "Return an input stream which will supply the characters of STRING between
   START and END in order."
   (declare (type string string)
           (type index start)
           (type (or index null) end))
-
-  #!+high-security
-  (when (> end (length string))
-    (cerror "Continue with end changed from ~S to ~S"
-           "Write-string: end (~S) is larger then the length of the string (~S)"
-           end (1- (length string))))
-
-  (internal-make-string-input-stream (coerce string 'simple-string)
-                                    start end))
+  (let ((end (%check-vector-sequence-bounds string start end)))
+    (with-array-data ((string string) (start start) (end end))
+      (internal-make-string-input-stream
+       string ;; now simple
+       start
+       end))))
 \f
-;;;; string output streams
+;;;; STRING-OUTPUT-STREAM stuff
 
 (defstruct (string-output-stream
-           (:include ansi-stream
+           (:include string-stream
                      (out #'string-ouch)
                      (sout #'string-sout)
-                     (misc #'string-out-misc))
-           (:constructor make-string-output-stream ())
+                     (misc #'string-out-misc)
+                      ;; The string we throw stuff in.
+                      (string (missing-arg)
+                             :type (simple-array character (*))))
+           (:constructor make-string-output-stream 
+                         (&key (element-type 'character)
+                          &aux (string (make-string 40))))
            (:copier nil))
-  ;; The string we throw stuff in.
-  (string (make-string 40) :type simple-string)
   ;; Index of the next location to use.
-  (index 0 :type fixnum))
+  (index 0 :type fixnum)
+  ;; Index cache for string-output-stream-last-index
+  (index-cache 0 :type fixnum)
+  ;; Requested element type
+  (element-type 'character))
 
 #!+sb-doc
 (setf (fdocumentation 'make-string-output-stream 'function)
   "Return an output stream which will accumulate all output given it for
    the benefit of the function GET-OUTPUT-STREAM-STRING.")
 
+(defun string-output-stream-last-index (stream)
+  (max (string-output-stream-index stream)
+       (string-output-stream-index-cache stream)))
+
 (defun string-ouch (stream character)
   (let ((current (string-output-stream-index stream))
        (workspace (string-output-stream-string stream)))
-    (declare (simple-string workspace) (fixnum current))
+    (declare (type (simple-array character (*)) workspace)
+            (type fixnum current))
     (if (= current (the fixnum (length workspace)))
        (let ((new-workspace (make-string (* current 2))))
          (replace new-workspace workspace)
-         (setf (aref new-workspace current) character)
-         (setf (string-output-stream-string stream) new-workspace))
+         (setf (aref new-workspace current) character
+               (string-output-stream-string stream) new-workspace))
        (setf (aref workspace current) character))
     (setf (string-output-stream-index stream) (1+ current))))
 
 (defun string-sout (stream string start end)
-  (declare (simple-string string) (fixnum start end))
-  (let* ((current (string-output-stream-index stream))
+  (declare (type simple-string string)
+          (type fixnum start end))
+  (let* ((string (if (typep string '(simple-array character (*)))
+                    string
+                    (coerce string '(simple-array character (*)))))
+        (current (string-output-stream-index stream))
         (length (- end start))
         (dst-end (+ length current))
         (workspace (string-output-stream-string stream)))
-    (declare (simple-string workspace)
-            (fixnum current length dst-end))
+    (declare (type (simple-array character (*)) workspace string)
+            (type fixnum current length dst-end))
     (if (> dst-end (the fixnum (length workspace)))
        (let ((new-workspace (make-string (+ (* current 2) length))))
          (replace new-workspace workspace :end2 current)
   (declare (ignore arg2))
   (case operation
     (:file-position
-     (if (null arg1)
+     (if arg1
+        (let ((end (string-output-stream-last-index stream)))
+          (setf (string-output-stream-index-cache stream) end
+                (string-output-stream-index stream)
+                (case arg1
+                  (:start 0)
+                  (:end end)
+                  (t
+                   ;; We allow moving beyond the end of stream,
+                   ;; implicitly extending the output stream.
+                   (let ((buffer (string-output-stream-string stream)))
+                     (when (> arg1 (length buffer))
+                       (setf (string-output-stream-string stream)
+                             (make-string
+                              arg1 :element-type (array-element-type buffer))
+                             (subseq (string-output-stream-string stream)
+                                     0 end)
+                             (subseq buffer 0 end))))
+                     arg1))))
         (string-output-stream-index stream)))
     (:charpos
      (do ((index (1- (the fixnum (string-output-stream-index stream)))
          (count 0 (1+ count))
          (string (string-output-stream-string stream)))
         ((< index 0) count)
-       (declare (simple-string string)
-               (fixnum index count))
+       (declare (type (simple-array character (*)) string)
+               (type fixnum index count))
        (if (char= (schar string index) #\newline)
           (return count))))
-    (:element-type 'base-char)))
+    (:element-type (array-element-type (string-output-stream-string stream)))))
 
 ;;; Return a string of all the characters sent to a stream made by
 ;;; MAKE-STRING-OUTPUT-STREAM since the last call to this function.
 (defun get-output-stream-string (stream)
   (declare (type string-output-stream stream))
-  (let* ((length (string-output-stream-index stream))
-        (result (make-string length)))
-    (replace result (string-output-stream-string stream))
-    (setf (string-output-stream-index stream) 0)
+  (let* ((length (string-output-stream-last-index stream))
+        (element-type (string-output-stream-element-type stream))
+        (result 
+         (case element-type
+           ;; Overwhelmingly common case; can be inlined.
+           ((character) (make-string length))
+           (t (make-string length :element-type element-type)))))
+    ;; For the benefit of the REPLACE transform, let's do this, so
+    ;; that the common case isn't ludicrously expensive.
+    (etypecase result 
+      ((simple-array character (*)) 
+       (replace result (string-output-stream-string stream)))
+      ((simple-array nil (*))
+       (replace result (string-output-stream-string stream))))
+    (setf (string-output-stream-index stream) 0
+         (string-output-stream-index-cache stream) 0)
     result))
 
 ;;; Dump the characters buffer up in IN-STREAM to OUT-STREAM as
   (%write-string (string-output-stream-string in-stream)
                 out-stream
                 0
-                (string-output-stream-index in-stream))
-  (setf (string-output-stream-index in-stream) 0))
+                (string-output-stream-last-index in-stream))
+  (setf (string-output-stream-index in-stream) 0
+       (string-output-stream-index-cache in-stream) 0))
 \f
 ;;;; fill-pointer streams
 
 ;;; WITH-OUTPUT-TO-STRING.
 
 (deftype string-with-fill-pointer ()
-  '(and string
+  '(and (vector character)
        (satisfies array-has-fill-pointer-p)))
 
 (defstruct (fill-pointer-output-stream
-           (:include ansi-stream
+           (:include string-stream
                      (out #'fill-pointer-ouch)
                      (sout #'fill-pointer-sout)
-                     (misc #'fill-pointer-misc))
+                     (misc #'fill-pointer-misc)
+                      ;; a string with a fill pointer where we stuff
+                      ;; the stuff we write
+                      (string (missing-arg)
+                              :type string-with-fill-pointer
+                              :read-only t))
            (:constructor make-fill-pointer-output-stream (string))
-           (:copier nil))
-  ;; a string with a fill pointer where we stuff the stuff we write
-  (string (error "missing argument")
-         :type string-with-fill-pointer
-         :read-only t))
+           (:copier nil)))
 
 (defun fill-pointer-ouch (stream character)
   (let* ((buffer (fill-pointer-output-stream-string stream))
         (current+1 (1+ current)))
     (declare (fixnum current))
     (with-array-data ((workspace buffer) (start) (end))
-      (declare (simple-string workspace))
+      (declare (type (simple-array character (*)) workspace))
       (let ((offset-current (+ start current)))
        (declare (fixnum offset-current))
        (if (= offset-current end)
              (declare (simple-string new-workspace))
              (%byte-blt workspace start
                         new-workspace 0 current)
-             (setf workspace new-workspace)
-             (setf offset-current current)
+             (setf workspace new-workspace
+                   offset-current current)
              (set-array-header buffer workspace new-length
                                current+1 0 new-length nil))
            (setf (fill-pointer buffer) current+1))
 
 (defun fill-pointer-sout (stream string start end)
   (declare (simple-string string) (fixnum start end))
-  (let* ((buffer (fill-pointer-output-stream-string stream))
+  (let* ((string (if (typep string '(simple-array character (*)))
+                    string
+                    (coerce string '(simple-array character (*)))))
+        (buffer (fill-pointer-output-stream-string stream))
         (current (fill-pointer buffer))
         (string-len (- end start))
         (dst-end (+ string-len current)))
     (declare (fixnum current dst-end string-len))
     (with-array-data ((workspace buffer) (dst-start) (dst-length))
-      (declare (simple-string workspace))
+      (declare (type (simple-array character (*)) workspace))
       (let ((offset-dst-end (+ dst-start dst-end))
            (offset-current (+ dst-start current)))
        (declare (fixnum offset-dst-end offset-current))
        (if (> offset-dst-end dst-length)
            (let* ((new-length (+ (the fixnum (* current 2)) string-len))
                   (new-workspace (make-string new-length)))
-             (declare (simple-string new-workspace))
+             (declare (type (simple-array character (*)) new-workspace))
              (%byte-blt workspace dst-start
                         new-workspace 0 current)
              (setf workspace new-workspace)
 (defun fill-pointer-misc (stream operation &optional arg1 arg2)
   (declare (ignore arg1 arg2))
   (case operation
+    (:file-position
+     (let ((buffer (fill-pointer-output-stream-string stream)))
+       (if arg1
+          (setf (fill-pointer buffer)
+                (case arg1
+                  (:start 0)
+                  ;; Fill-pointer is always at fill-pointer we will
+                  ;; make :END move to the end of the actual string.
+                  (:end (array-total-size buffer))
+                  ;; We allow moving beyond the end of string if the
+                  ;; string is adjustable.
+                  (t (when (>= arg1 (array-total-size buffer))
+                       (if (adjustable-array-p buffer)
+                           (adjust-array buffer arg1)
+                           (error "Cannot move FILE-POSITION beyond the end ~
+                                    of WITH-OUTPUT-TO-STRING stream ~
+                                    constructed with non-adjustable string.")))
+                     arg1)))
+          (fill-pointer buffer))))
     (:charpos
      (let* ((buffer (fill-pointer-output-stream-string stream))
            (current (fill-pointer buffer)))
           (if found
               (- end (the fixnum found))
               current)))))
-     (:element-type 'base-char)))
+     (:element-type (array-element-type
+                    (fill-pointer-output-stream-string stream)))))
 \f
 ;;;; indenting streams
 
        (funcall (ansi-stream-sout target) target str 0 len)
        (stream-write-string target str 0 len))))
 \f
-;;;; stream commands
-
-(defstruct (stream-command (:constructor make-stream-command
-                                        (name &optional args))
-                          (:copier nil))
-  (name nil :type symbol)
-  (args nil :type list))
-(def!method print-object ((obj stream-command) str)
-  (print-unreadable-object (obj str :type t :identity t)
-    (prin1 (stream-command-name obj) str)))
-
-;;; Take a stream and wait for text or a command to appear on it. If
-;;; text appears before a command, return NIL, otherwise return a
-;;; command.
-;;;
-;;; We can't simply call the stream's misc method because NIL is an
-;;; ambiguous return value: does it mean text arrived, or does it mean
-;;; the stream's misc method had no :GET-COMMAND implementation? We
-;;; can't return NIL until there is text input. We don't need to loop
-;;; because any stream implementing :GET-COMMAND would wait until it
-;;; had some input. If the LISTEN fails, then we have some stream we
-;;; must wait on.
-(defun get-stream-command (stream)
-  (let ((cmdp (funcall (ansi-stream-misc stream) stream :get-command)))
-    (cond (cmdp)
-         ((listen stream)
-          nil)
-         (t
-          ;; This waits for input and returns NIL when it arrives.
-          (unread-char (read-char stream) stream)))))
-\f
 ;;;; READ-SEQUENCE
 
-(defun read-sequence (seq stream &key (start 0) (end nil))
+(defun read-sequence (seq stream &key (start 0) end)
   #!+sb-doc
   "Destructively modify SEQ by reading elements from STREAM.
   That part of SEQ bounded by START and END is destructively modified by
           (funcall write-function (aref seq i) stream)))))))
 \f
 ;;;; etc.
-
-;;; (These were inline throughout this file, but that's not appropriate
-;;; globally.)
-(declaim (maybe-inline read-char unread-char read-byte listen))