0.8.13.49
authorRudi Schlatte <rudi@constantly.at>
Tue, 10 Aug 2004 11:16:15 +0000 (11:16 +0000)
committerRudi Schlatte <rudi@constantly.at>
Tue, 10 Aug 2004 11:16:15 +0000 (11:16 +0000)
  Remove cut'n'pasted (and outdated) code from sb-simple-streams:

  * Create inline ansi-stream-read-char & friends in
    (target-)stream.lisp, use them from read-char etc.

  * Use sb-impl::ansi-stream-read-char etc in simple-streams too.

contrib/sb-simple-streams/impl.lisp
src/code/stream.lisp
src/code/target-stream.lisp
version.lisp-expr

index c537300..417c870 100644 (file)
        (error "Wrong vector type for read-vector on stream not of type simple-stream."))
      (read-sequence vector stream :start (or start 0) :end end))))
 
-;;; Basic functionality for ansi-streams.  These are separate
-;;; functions because they are called in places where we already know
-;;; we operate on an ansi-stream (as opposed to a simple- or
-;;; gray-stream, or the symbols t or nil), so we can evade typecase
-;;; and (in|out)-synonym-of calls.
-
-(declaim (inline %ansi-stream-read-byte %ansi-stream-read-char
-                 %ansi-stream-unread-char %ansi-stream-read-line
-                 %ansi-stream-read-sequence))
-
-(defun %ansi-stream-read-byte (stream eof-error-p eof-value blocking)
-  (declare (ignore blocking))
-  #+nil
-  (sb-kernel:ansi-stream-read-byte stream eof-error-p eof-value)
-  (sb-int:prepare-for-fast-read-byte stream
-    (prog1
-        (sb-int:fast-read-byte eof-error-p eof-value t)
-      (sb-int:done-with-fast-read-byte))))
-
-(defun %ansi-stream-read-char (stream eof-error-p eof-value blocking)
-  (declare (ignore blocking))
-  #+nil
-  (sb-kernel:ansi-stream-read-char stream eof-error-p eof-value)
-  (sb-int:prepare-for-fast-read-char stream
-    (prog1
-        (sb-int:fast-read-char eof-error-p eof-value)
-      (sb-int:done-with-fast-read-char))))
-
-(defun %ansi-stream-unread-char (character stream)
-  (let ((index (1- (sb-kernel:ansi-stream-in-index stream)))
-        (buffer (sb-kernel:ansi-stream-in-buffer stream)))
-    (declare (fixnum index))
-    (when (minusp index) (error "nothing to unread"))
-    (cond (buffer
-           (setf (aref buffer index) (char-code character))
-           (setf (sb-kernel:ansi-stream-in-index stream) index))
-          (t
-           (funcall (sb-kernel:ansi-stream-misc stream) stream
-                    :unread character)))))
-
-(defun %ansi-stream-read-line (stream eof-error-p eof-value)
-  (sb-int:prepare-for-fast-read-char stream
-    (let ((res (make-string 80))
-          (len 80)
-          (index 0))
-      (loop
-       (let ((ch (sb-int:fast-read-char nil nil)))
-         (cond (ch
-                (when (char= ch #\newline)
-                  (sb-int:done-with-fast-read-char)
-                  (return (values (sb-kernel:shrink-vector res index) nil)))
-                (when (= index len)
-                  (setq len (* len 2))
-                  (let ((new (make-string len)))
-                    (replace new res)
-                    (setq res new)))
-                (setf (schar res index) ch)
-                (incf index))
-               ((zerop index)
-                (sb-int:done-with-fast-read-char)
-                (return (values (sb-impl::eof-or-lose stream eof-error-p
-                                                      eof-value)
-                                t)))
-               ;; Since FAST-READ-CHAR already hit the eof char, we
-               ;; shouldn't do another READ-CHAR.
-               (t
-                (sb-int:done-with-fast-read-char)
-                (return (values (sb-kernel:shrink-vector res index) t)))))))))
-
-(defun %ansi-stream-read-sequence (seq stream start %end)
-  (declare (type sequence seq)
-          (type sb-kernel:ansi-stream stream)
-          (type sb-int:index start)
-          (type sb-kernel:sequence-end %end)
-          (values sb-int:index))
-  (let ((end (or %end (length seq))))
-    (declare (type sb-int:index end))
-    (etypecase seq
-      (list
-       (let ((read-function
-             (if (subtypep (stream-element-type stream) 'character)
-                 #'%ansi-stream-read-char
-                 #'%ansi-stream-read-byte)))
-        (do ((rem (nthcdr start seq) (rest rem))
-             (i start (1+ i)))
-            ((or (endp rem) (>= i end)) i)
-          (declare (type list rem)
-                   (type sb-int:index i))
-          (let ((el (funcall read-function stream nil :eof nil)))
-            (when (eq el :eof)
-              (return i))
-            (setf (first rem) el)))))
-      (vector
-       (sb-kernel:with-array-data ((data seq) (offset-start start)
-                                   (offset-end end))
-         (typecase data
-          ((or (simple-array (unsigned-byte 8) (*))
-               (simple-array (signed-byte 8) (*))
-               simple-string)
-           (let* ((numbytes (- end start))
-                  (bytes-read (sb-sys:read-n-bytes stream
-                                                   data
-                                                   offset-start
-                                                   numbytes
-                                                   nil)))
-             (if (< bytes-read numbytes)
-                 (+ start bytes-read)
-                 end)))
-          (t
-           (let ((read-function
-                  (if (subtypep (stream-element-type stream) 'character)
-                      #'%ansi-stream-read-char
-                      #'%ansi-stream-read-byte)))
-             (do ((i offset-start (1+ i)))
-                 ((>= i offset-end) end)
-               (declare (type sb-int:index i))
-               (let ((el (funcall read-function stream nil :eof nil)))
-                 (when (eq el :eof)
-                   (return (+ start (- i offset-start))))
-                 (setf (aref data i) el)))))))))))
-
-
-(defun %ansi-stream-write-string (string stream start end)
-  (declare (type string string)
-           (type sb-kernel:ansi-stream stream)
-           (type sb-int: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))
-
-  (if (sb-kernel:array-header-p string)
-      (sb-kernel:with-array-data ((data string) (offset-start start)
-                                  (offset-end end))
-        (funcall (sb-kernel:ansi-stream-sout stream)
-                 stream data offset-start offset-end))
-      (funcall (sb-kernel:ansi-stream-sout stream) stream string start end))
-  string)
-
-(defun %ansi-stream-write-sequence (seq stream start %end)
-  (declare (type sequence seq)
-           (type sb-kernel:ansi-stream stream)
-           (type sb-int:index start)
-           (type sb-kernel:sequence-end %end)
-           (values sequence))
-  (let ((end (or %end (length seq))))
-    (declare (type sb-int:index end))
-    (etypecase seq
-      (list
-       (let ((write-function
-             (if (subtypep (stream-element-type stream) 'character)
-                  ;; TODO: Replace these with ansi-stream specific
-                  ;; functions too.
-                 #'write-char
-                 #'write-byte)))
-        (do ((rem (nthcdr start seq) (rest rem))
-             (i start (1+ i)))
-            ((or (endp rem) (>= i end)) seq)
-          (declare (type list rem)
-                   (type sb-int:index i))
-          (funcall write-function (first rem) stream))))
-      (string
-       (%ansi-stream-write-string seq stream start end))
-      (vector
-       (let ((write-function
-             (if (subtypep (stream-element-type stream) 'character)
-                  ;; TODO: Replace these with ansi-stream specific
-                  ;; functions too.
-                 #'write-char
-                 #'write-byte)))
-        (do ((i start (1+ i)))
-            ((>= i end) seq)
-          (declare (type sb-int:index i))
-          (funcall write-function (aref seq i) stream)))))))
-
 
 ;;;
 ;;; USER-LEVEL FUNCTIONS
       (simple-stream
        (%read-byte stream eof-error-p eof-value))
       (ansi-stream
-       (%ansi-stream-read-byte stream eof-error-p eof-value t))
+       (sb-impl::ansi-stream-read-byte stream eof-error-p eof-value nil))
       (fundamental-stream
        (let ((char (sb-gray:stream-read-byte stream)))
         (if (eq char :eof)
       (simple-stream
        (%read-char stream eof-error-p eof-value recursive-p t))
       (ansi-stream
-       (%ansi-stream-read-char stream eof-error-p eof-value t))
+       (sb-impl::ansi-stream-read-char stream eof-error-p eof-value
+                                       recursive-p))
       (fundamental-stream
        (let ((char (sb-gray:stream-read-char stream)))
         (if (eq char :eof)
        (with-stream-class (simple-stream)
         (funcall-stm-handler j-read-char stream eof-error-p eof-value nil)))
       (ansi-stream
-       (if (funcall (sb-kernel:ansi-stream-misc stream) stream :listen)
-           (%ansi-stream-read-char stream eof-error-p eof-value t)
-           nil))
+       (sb-impl::ansi-stream-read-char-no-hang stream eof-error-p eof-value
+                                               recursive-p))
       (fundamental-stream
        (let ((char (sb-gray:stream-read-char-no-hang stream)))
         (if (eq char :eof)
       (simple-stream
        (%unread-char stream character))
       (ansi-stream
-       (%ansi-stream-unread-char character stream))
+       (sb-impl::ansi-stream-unread-char character stream))
       (fundamental-stream
        (sb-gray:stream-unread-char stream character))))
   nil)
       ;; FIXME: Broken on ECHO-STREAM (cf internal implementation?) --
       ;; CSR, 2004-01-19
       (ansi-stream
-       (let ((char (%ansi-stream-read-char stream eof-error-p eof-value t)))
-          (cond ((eq char eof-value) char)
-                ((characterp peek-type)
-                 (do ((char char (%ansi-stream-read-char stream eof-error-p
-                                                         eof-value t)))
-                     ((or (eq char eof-value) (char= char peek-type))
-                      (unless (eq char eof-value)
-                        (%ansi-stream-unread-char char stream))
-                      char)))
-                ((eq peek-type t)
-                 (do ((char char (%ansi-stream-read-char stream eof-error-p
-                                                         eof-value t)))
-                     ((or (eq char eof-value)
-                         (not (sb-impl::whitespacep char)))
-                      (unless (eq char eof-value)
-                        (%ansi-stream-unread-char char stream))
-                      char)))
-                (t
-                 (%ansi-stream-unread-char char stream)
-                 char))))
+       (sb-impl::ansi-stream-peek-char peek-type stream eof-error-p eof-value
+                                       recursive-p))
       (fundamental-stream
        (cond ((characterp peek-type)
              (do ((char (sb-gray:stream-read-char stream)
                    char))))))))
 
 (defun listen (&optional (stream *standard-input*) (width 1))
-  "Returns T if Width octets are available on the given Stream.  If Width
-  is given as 'character, check for a character."
+  "Returns T if WIDTH octets are available on STREAM.  If WIDTH is
+given as 'CHARACTER, check for a character.  Note: the WIDTH argument
+is supported only on simple-streams."
   ;; WIDTH is number of octets which must be available; any value
   ;; other than 1 is treated as 'character.
   (let ((stream (sb-impl::in-synonym-of stream)))
       (simple-stream
        (%listen stream width))
       (ansi-stream
-       (or (/= (the fixnum (sb-kernel:ansi-stream-in-index stream))
-               sb-impl::+ansi-stream-in-buffer-length+)
-           ;; Test for T explicitly since misc methods return :EOF sometimes.
-           (eq (funcall (sb-kernel:ansi-stream-misc stream) stream :listen)
-                t)))
+       (sb-impl::ansi-stream-listen stream))
       (fundamental-stream
        (sb-gray:stream-listen stream)))))
 
       (simple-stream
        (%read-line stream eof-error-p eof-value recursive-p))
       (ansi-stream
-       (%ansi-stream-read-line stream eof-error-p eof-value))
+       (sb-impl::ansi-stream-read-line stream eof-error-p eof-value
+                                       recursive-p))
       (fundamental-stream
        (multiple-value-bind (string eof) (sb-gray:stream-read-line stream)
         (if (and eof (zerop (length string)))
        (with-stream-class (simple-stream stream)
         (%read-sequence stream seq start end partial-fill)))
       (ansi-stream
-       (%ansi-stream-read-sequence seq stream start end))
+       (sb-impl::ansi-stream-read-sequence seq stream start end))
       (fundamental-stream
        (sb-gray:stream-read-sequence stream seq start end)))))
 
       (simple-stream
        (%clear-input stream buffer-only))
       (ansi-stream
-       (setf (sb-kernel:ansi-stream-in-index stream)
-             sb-impl::+ansi-stream-in-buffer-length+)
-       (funcall (sb-kernel:ansi-stream-misc stream) stream :clear-input))
+       (sb-impl::ansi-stream-clear-input stream))
       (fundamental-stream
        (sb-gray:stream-clear-input stream))))
   nil)
                            &key (start 0) (end nil))
   "Outputs the String to the given Stream."
   (let ((stream (sb-impl::out-synonym-of stream))
-       (end (or end (length string))))
+       (end (sb-impl::%check-vector-sequence-bounds string start end)))
     (etypecase stream
       (simple-stream
        (%write-string stream string start end)
        string)
       (ansi-stream
-       (%ansi-stream-write-string string stream start end))
+       (sb-impl::ansi-stream-write-string string stream start end))
       (fundamental-stream
        (sb-gray:stream-write-string stream string start end)))))
 
 (defun write-line (string &optional (stream *standard-output*)
                          &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 ((stream (sb-impl::out-synonym-of stream))
-       (end (or end (length string))))
+       (end (sb-impl::%check-vector-sequence-bounds string start end)))
     (etypecase stream
       (simple-stream
        (%check stream :output)
         (funcall-stm-handler-2 j-write-chars string stream start end)
         (funcall-stm-handler-2 j-write-char #\Newline stream)))
       (ansi-stream
-       (%ansi-stream-write-string string stream start end)
+       (sb-impl::ansi-stream-write-string string stream start end)
        (funcall (sb-kernel:ansi-stream-out stream) stream #\Newline))
       (fundamental-stream
        (sb-gray:stream-write-string stream string start end)
       (simple-stream
        (%write-sequence stream seq start end))
       (ansi-stream
-       (%ansi-stream-write-sequence seq stream start end))
+       (sb-impl::ansi-stream-write-sequence seq stream start end))
       (fundamental-stream
        (sb-gray:stream-write-sequence stream seq start end)))))
 
       (simple-stream
        (%fresh-line stream))
       (ansi-stream
-       (when (/= (or (sb-kernel:charpos stream) 1) 0)
-        (funcall (sb-kernel:ansi-stream-out stream) stream #\Newline)
-        t))
+       (sb-impl::ansi-stream-fresh-line stream))
       (fundamental-stream
        (sb-gray:stream-fresh-line stream)))))
 
    File-Stream is open to.  If the second argument is supplied, then
    this becomes the new file position.  The second argument may also
    be :start or :end for the start and end of the file, respectively."
-  (declare (type (or (integer 0 *) (member nil :start :end)) position))
+  (declare (type (or index (alien sb!unix:off-t) (member nil :start :end))
+                 position))
   (etypecase stream
     (simple-stream
      (%file-position stream position))
     (ansi-stream
-     (cond
-       (position
-        (setf (sb-kernel:ansi-stream-in-index stream)
-              sb-impl::+ansi-stream-in-buffer-length+)
-        (funcall (sb-kernel:ansi-stream-misc stream)
-                 stream :file-position position))
-       (t
-        (let ((res (funcall (sb-kernel:ansi-stream-misc stream)
-                            stream :file-position nil)))
-          (when res
-            (- res
-               (- sb-impl::+ansi-stream-in-buffer-length+
-                  (sb-kernel:ansi-stream-in-index stream))))))))))
+     (sb-impl::ansi-stream-file-position stream position))))
 
 (defun file-length (stream)
   "This function returns the length of the file that File-Stream is open to."
     (simple-stream
      (%file-length stream))
     (ansi-stream
-     (progn (sb-impl::stream-must-be-associated-with-file stream)
-            (funcall (sb-kernel:ansi-stream-misc stream) stream :file-length)))))
+     (sb-impl::stream-must-be-associated-with-file stream)
+     (funcall (sb-kernel:ansi-stream-misc stream) stream :file-length))))
 
 (defun charpos (&optional (stream *standard-output*))
   "Returns the number of characters on the current line of output of the given
index 925daa7..bd541c6 100644 (file)
 ;;;; file position and file length
 
 ;;; Call the MISC method with the :FILE-POSITION operation.
-(defun file-position (stream &optional position)
+#!-sb-fluid (declaim (inline ansi-stream-file-position))
+(defun ansi-stream-file-position (stream position)
   (declare (type stream stream))
-  (declare (type (or index (alien sb!unix:off-t) (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+)
-    (funcall (ansi-stream-misc stream) stream :file-position position))
-   (t
-    (let ((res (funcall (ansi-stream-misc stream) stream :file-position nil)))
-      (when res
-       (- res
-          (- +ansi-stream-in-buffer-length+
-             (ansi-stream-in-index stream))))))))
+    (position
+     (setf (ansi-stream-in-index stream) +ansi-stream-in-buffer-length+)
+     (funcall (ansi-stream-misc stream) stream :file-position position))
+    (t
+     (let ((res (funcall (ansi-stream-misc stream) stream :file-position nil)))
+       (when res
+         (- res
+            (- +ansi-stream-in-buffer-length+
+               (ansi-stream-in-index stream))))))))
+
+
+(defun file-position (stream &optional position)
+  (ansi-stream-file-position stream position))
 
 ;;; This is a literal translation of the ANSI glossary entry "stream
 ;;; associated with a file".
 \f
 ;;;; input functions
 
-(defun read-line (&optional (stream *standard-input*) (eof-error-p t) eof-value
-                           recursive-p)
+#!-sb-fluid (declaim (inline ansi-stream-read-line))
+(defun ansi-stream-read-line (stream eof-error-p eof-value recursive-p)
   (declare (ignore recursive-p))
-  (let ((stream (in-synonym-of stream)))
-    (if (ansi-stream-p stream)
-       (prepare-for-fast-read-char stream
+  (prepare-for-fast-read-char stream
          (let ((res (make-string 80))
                (len 80)
                (index 0))
                     ;; shouldn't do another READ-CHAR.
                     (t
                      (done-with-fast-read-char)
-                     (return (values (shrink-vector res index) t))))))))
+                     (return (values (shrink-vector res index) t)))))))))
+
+(defun read-line (&optional (stream *standard-input*) (eof-error-p t) eof-value
+                           recursive-p)
+  (let ((stream (in-synonym-of stream)))
+    (if (ansi-stream-p stream)
+       (ansi-stream-read-line stream eof-error-p eof-value recursive-p)
        ;; must be Gray streams FUNDAMENTAL-STREAM
        (multiple-value-bind (string eof) (stream-read-line stream)
          (if (and eof (zerop (length string)))
              (values (eof-or-lose stream eof-error-p eof-value) t)
              (values string eof))))))
 
-;;; We proclaim them INLINE here, then proclaim them MAYBE-INLINE at EOF,
+;;; We proclaim them INLINE here, then proclaim them NOTINLINE later on,
 ;;; so, except in this file, they are not inline by default, but they can be.
 #!-sb-fluid (declaim (inline read-char unread-char read-byte listen))
 
+#!-sb-fluid (declaim (inline ansi-stream-read-char))
+(defun ansi-stream-read-char (stream eof-error-p eof-value recursive-p)
+  (declare (ignore recursive-p))
+  (prepare-for-fast-read-char stream
+    (prog1
+        (fast-read-char eof-error-p eof-value)
+      (done-with-fast-read-char))))
+
 (defun read-char (&optional (stream *standard-input*)
                            (eof-error-p t)
                            eof-value
                            recursive-p)
-  (declare (ignore recursive-p))
   (let ((stream (in-synonym-of stream)))
     (if (ansi-stream-p stream)
-       (prepare-for-fast-read-char stream
-         (prog1
-             (fast-read-char eof-error-p eof-value)
-           (done-with-fast-read-char)))
+       (ansi-stream-read-char stream eof-error-p eof-value recursive-p)
        ;; must be Gray streams FUNDAMENTAL-STREAM
        (let ((char (stream-read-char stream)))
          (if (eq char :eof)
              (eof-or-lose stream eof-error-p eof-value)
              char)))))
 
+#!-sb-fluid (declaim (inline ansi-stream-unread-char))
+(defun ansi-stream-unread-char (character stream)
+  (let ((index (1- (ansi-stream-in-index stream)))
+        (buffer (ansi-stream-in-buffer stream)))
+    (declare (fixnum index))
+    (when (minusp index) (error "nothing to unread"))
+    (cond (buffer
+           (setf (aref buffer index) (char-code character))
+           (setf (ansi-stream-in-index stream) index))
+          (t
+           (funcall (ansi-stream-misc stream) stream
+                    :unread character)))))
+
 (defun unread-char (character &optional (stream *standard-input*))
   (let ((stream (in-synonym-of stream)))
     (if (ansi-stream-p stream)
-       (let ((index (1- (ansi-stream-in-index stream)))
-             (buffer (ansi-stream-in-buffer stream)))
-         (declare (fixnum index))
-         (when (minusp index) (error "nothing to unread"))
-         (cond (buffer
-                (setf (aref buffer index) (char-code character))
-                (setf (ansi-stream-in-index stream) index))
-               (t
-                (funcall (ansi-stream-misc stream) stream
-                         :unread character))))
+       (ansi-stream-unread-char character stream)
        ;; must be Gray streams FUNDAMENTAL-STREAM
        (stream-unread-char stream character)))
   nil)
 
+#!-sb-fluid (declaim (inline ansi-stream-listen))
+(defun ansi-stream-listen (stream)
+  (or (/= (the fixnum (ansi-stream-in-index stream))
+          +ansi-stream-in-buffer-length+)
+      ;; Test for T explicitly since misc methods return :EOF sometimes.
+      (eq (funcall (ansi-stream-misc stream) stream :listen) t)))
+
 (defun listen (&optional (stream *standard-input*))
   (let ((stream (in-synonym-of stream)))
     (if (ansi-stream-p stream)
-       (or (/= (the fixnum (ansi-stream-in-index stream))
-               +ansi-stream-in-buffer-length+)
-           ;; Test for T explicitly since misc methods return :EOF sometimes.
-           (eq (funcall (ansi-stream-misc stream) stream :listen) t))
+       (ansi-stream-listen stream)
        ;; Fall through to Gray streams FUNDAMENTAL-STREAM case.
        (stream-listen stream))))
 
+#!-sb-fluid (declaim (inline ansi-stream-read-char-no-hang))
+(defun ansi-stream-read-char-no-hang (stream eof-error-p eof-value recursive-p)
+  (if (funcall (ansi-stream-misc stream) stream :listen)
+      ;; On T or :EOF get READ-CHAR to do the work.
+      (ansi-stream-read-char stream eof-error-p eof-value recursive-p)
+      nil))
+
 (defun read-char-no-hang (&optional (stream *standard-input*)
                                    (eof-error-p t)
                                    eof-value
                                    recursive-p)
-  (declare (ignore recursive-p))
   (let ((stream (in-synonym-of stream)))
     (if (ansi-stream-p stream)
-       (if (funcall (ansi-stream-misc stream) stream :listen)
-           ;; On T or :EOF get READ-CHAR to do the work.
-           (read-char stream eof-error-p eof-value)
-           nil)
+       (ansi-stream-read-char-no-hang stream eof-error-p eof-value
+                                       recursive-p)
        ;; must be Gray streams FUNDAMENTAL-STREAM
        (let ((char (stream-read-char-no-hang stream)))
          (if (eq char :eof)
              (eof-or-lose stream eof-error-p eof-value)
              char)))))
 
+#!-sb-fluid (declaim (inline ansi-stream-clear-input))
+(defun ansi-stream-clear-input (stream)
+  (setf (ansi-stream-in-index stream) +ansi-stream-in-buffer-length+)
+  (funcall (ansi-stream-misc stream) stream :clear-input))
+
 (defun clear-input (&optional (stream *standard-input*))
   (let ((stream (in-synonym-of stream)))
-    (cond ((ansi-stream-p stream)
-          (setf (ansi-stream-in-index stream) +ansi-stream-in-buffer-length+)
-          (funcall (ansi-stream-misc stream) stream :clear-input))
-         (t
-          (stream-clear-input stream))))
+    (if (ansi-stream-p stream)
+        (ansi-stream-clear-input stream)
+        ;; must be Gray streams FUNDAMENTAL-STREAM
+        (stream-clear-input stream)))
   nil)
 \f
-(declaim (maybe-inline read-byte))
+#!-sb-fluid (declaim (inline ansi-stream-read-byte))
+(defun ansi-stream-read-byte (stream eof-error-p eof-value recursive-p)
+  ;; Why the "recursive-p" parameter?  a-s-r-b is funcall'ed from
+  ;; a-s-read-sequence and needs a lambda list that's congruent with
+  ;; that of a-s-read-char
+  (declare (ignore recursive-p))
+  (prepare-for-fast-read-byte stream
+    (prog1
+        (fast-read-byte eof-error-p eof-value t)
+      (done-with-fast-read-byte))))
+
 (defun read-byte (stream &optional (eof-error-p t) eof-value)
   (let ((stream (in-synonym-of stream)))
     (if (ansi-stream-p stream)
-       (prepare-for-fast-read-byte stream
-         (prog1
-             (fast-read-byte eof-error-p eof-value t)
-           (done-with-fast-read-byte)))
+       (ansi-stream-read-byte stream eof-error-p eof-value nil)
        ;; must be Gray streams FUNDAMENTAL-STREAM
        (let ((char (stream-read-byte stream)))
          (if (eq char :eof)
   (with-out-stream stream (ansi-stream-out #\newline) (stream-terpri))
   nil)
 
+#!-sb-fluid (declaim (inline ansi-stream-fresh-line))
+(defun ansi-stream-fresh-line (stream)
+  (when (/= (or (charpos stream) 1) 0)
+    (funcall (ansi-stream-out stream) stream #\newline)
+    t))
+
 (defun fresh-line (&optional (stream *standard-output*))
   (let ((stream (out-synonym-of stream)))
     (if (ansi-stream-p stream)
-       (when (/= (or (charpos stream) 1) 0)
-         (funcall (ansi-stream-out stream) stream #\newline)
-         t)
+       (ansi-stream-fresh-line stream)
        ;; must be Gray streams FUNDAMENTAL-STREAM
        (stream-fresh-line stream))))
 
                                      string start end))
   string)
 
+#!-sb-fluid (declaim (inline ansi-stream-write-string))
+(defun ansi-stream-write-string (string stream start end)
+  (declare (type string string))
+  (declare (type ansi-stream stream))
+  (declare (type index start end))
+  (if (array-header-p string)
+      (with-array-data ((data string) (offset-start start)
+                        (offset-end end))
+        (funcall (ansi-stream-sout stream)
+                 stream data offset-start offset-end))
+      (funcall (ansi-stream-sout stream) stream string start end))
+  string)
+
 (defun %write-string (string stream start end)
   (declare (type string string))
   (declare (type stream-designator stream))
   (declare (type index start end))
   (let ((stream (out-synonym-of stream)))
-    (cond ((ansi-stream-p stream)
-          (if (array-header-p string)
-              (with-array-data ((data string) (offset-start start)
-                                (offset-end end))
-                (funcall (ansi-stream-sout stream)
-                         stream data offset-start offset-end))
-              (funcall (ansi-stream-sout stream) stream string start end))
-          string)
-         (t ; must be Gray streams FUNDAMENTAL-STREAM
-          (stream-write-string stream string start end)))))
+    (if(ansi-stream-p stream)
+       (ansi-stream-write-string string stream start end)
+       ;; 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.
 ;;; 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))
+(declaim (notinline 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
       (list
        (let ((read-function
              (if (subtypep (stream-element-type stream) 'character)
-                 #'read-char
-                 #'read-byte)))
+                 #'ansi-stream-read-char
+                 #'ansi-stream-read-byte)))
         (do ((rem (nthcdr start seq) (rest rem))
              (i start (1+ i)))
             ((or (endp rem) (>= i end)) i)
           (declare (type list rem)
                    (type index i))
-          (let ((el (funcall read-function stream nil :eof)))
+          (let ((el (funcall read-function stream nil :eof nil)))
             (when (eq el :eof)
               (return i))
             (setf (first rem) el)))))
           (t
            (let ((read-function
                   (if (subtypep (stream-element-type stream) 'character)
-                      #'read-char
-                      #'read-byte)))
+                      #'ansi-stream-read-char
+                      #'ansi-stream-read-byte)))
              (do ((i offset-start (1+ i)))
                  ((>= i offset-end) end)
                (declare (type index i))
-               (let ((el (funcall read-function stream nil :eof)))
+               (let ((el (funcall read-function stream nil :eof nil)))
                  (when (eq el :eof)
                    (return (+ start (- i offset-start))))
                  (setf (aref data i) el)))))))))))
       (list
        (let ((write-function
              (if (subtypep (stream-element-type stream) 'character)
+                  ;; FIXME (rudi 2004-08-09): since we know we're an
+                  ;; ansi stream here, we could replace these
+                  ;; functions with ansi-stream-specific constructs
                  #'write-char
                  #'write-byte)))
         (do ((rem (nthcdr start seq) (rest rem))
       (vector
        (let ((write-function
              (if (subtypep (stream-element-type stream) 'character)
+                  ;; FIXME (rudi 2004-08-09): since we know we're an
+                  ;; ansi stream here, we could replace these
+                  ;; functions with ansi-specific constructs
                  #'write-char
                  #'write-byte)))
         (do ((i start (1+ i)))
index 4b254f6..5e7a689 100644 (file)
             (t
              (bug "Impossible case reached in PEEK-CHAR"))))))
 
-;;; We proclaim them INLINE here, then proclaim them MAYBE-INLINE at EOF,
-;;; so, except in this file, they are not inline by default, but they can be.
-#!-sb-fluid (declaim (inline read-char unread-char read-byte listen))
+;;; rudi (2004-08-09): There was an inline declaration for read-char,
+;;; unread-char, read-byte, listen here that was removed because these
+;;; functions are redefined when simple-streams are loaded.
+
+#!-sb-fluid (declaim (inline ansi-stream-peek-char))
+(defun ansi-stream-peek-char (peek-type stream eof-error-p eof-value
+                              recursive-p)
+  (cond ((typep stream 'echo-stream)
+         (echo-misc stream
+                    :peek-char
+                    peek-type
+                    (list eof-error-p eof-value)))
+        (t
+         (generalized-peeking-mechanism
+          peek-type eof-value char
+          (ansi-stream-read-char stream eof-error-p eof-value recursive-p)
+          (ansi-stream-unread-char char stream)))))
 
 (defun peek-char (&optional (peek-type nil)
                            (stream *standard-input*)
                            (eof-error-p t)
                            eof-value
                            recursive-p)
-  (declare (ignore recursive-p))
   (the (or character boolean) peek-type)
   (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))))))
+    (if (ansi-stream-p stream)
+        (ansi-stream-peek-char peek-type stream eof-error-p eof-value
+                               recursive-p)
+        ;; 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 echo-misc (stream operation &optional arg1 arg2)
   (let* ((in (two-way-stream-input-stream stream))
               (funcall (ansi-stream-misc out) out operation arg1 arg2)
               (stream-misc-dispatch out operation arg1 arg2)))))))
 
-(declaim (maybe-inline read-char unread-char read-byte listen))
\ No newline at end of file
index 940f88c..7ce50af 100644 (file)
@@ -17,4 +17,4 @@
 ;;; checkins which aren't released. (And occasionally for internal
 ;;; versions, especially for internal versions off the main CVS
 ;;; branch, it gets hairier, e.g. "0.pre7.14.flaky4.13".)
-"0.8.13.48"
+"0.8.13.49"