0.8.3.5:
[sbcl.git] / src / code / stream.lisp
index c96d81d..e3dbd91 100644 (file)
 ;;; 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
                            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 
+          (echo-misc stream
                      :peek-char
                      peek-type
                      (list eof-error-p eof-value)))
                  (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))
 
              (:include ansi-stream)
              (:constructor nil)
              (:copier nil))
-  (string nil :type string))
+  ;; 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-STREAM stuff
 
                       (bin #'string-binch)
                       (n-bin #'string-stream-read-n-bytes)
                       (misc #'string-in-misc)
-                       (string nil :type simple-string))
+                       (string (missing-arg)
+                              :type (simple-array character (*))))
             (:constructor internal-make-string-input-stream
                           (string current end))
             (:copier nil))
 (defun string-inch (stream eof-error-p eof-value)
   (let ((string (string-input-stream-string stream))
        (index (string-input-stream-current stream)))
-    (declare (simple-string string) (fixnum index))
+    (declare (type (simple-array character (*)) string)
+            (type fixnum index))
     (cond ((= index (the index (string-input-stream-end stream)))
           (eof-or-lose stream eof-error-p eof-value))
          (t
 (defun string-binch (stream eof-error-p eof-value)
   (let ((string (string-input-stream-string stream))
        (index (string-input-stream-current stream)))
-    (declare (simple-string string)
+    (declare (type (simple-array character (*)) string)
             (type index index))
     (cond ((= index (the index (string-input-stream-end stream)))
           (eof-or-lose stream eof-error-p eof-value))
         (index (string-input-stream-current stream))
         (available (- (string-input-stream-end stream) index))
         (copy (min available requested)))
-    (declare (simple-string string)
+    (declare (type (simple-array character (*)) string)
             (type index index available copy))
     (when (plusp copy)
       (setf (string-input-stream-current stream)
   (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))
+                (t arg1)))
         (string-input-stream-current stream)))
     (:file-length (length (string-input-stream-string stream)))
     (:unread (decf (string-input-stream-current stream)))
                      (sout #'string-sout)
                      (misc #'string-out-misc)
                       ;; The string we throw stuff in.
-                      (string (make-string 40) :type simple-string))
-           (:constructor make-string-output-stream ())
+                      (string (missing-arg)
+                             :type (simple-array character (*))))
+           (:constructor make-string-output-stream 
+                         (&key (element-type 'character)
+                          &aux (string (make-string 40))))
            (:copier nil))
   ;; Index of the next location to use.
-  (index 0 :type fixnum))
+  (index 0 :type fixnum)
+  ;; Requested element type
+  (element-type 'character))
 
 #!+sb-doc
 (setf (fdocumentation 'make-string-output-stream 'function)
 (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 (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)
          (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)))
 (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))
+        (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)
     result))
 
 ;;; 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
         (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)
 
 (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)
        (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)