Fix typos in docstrings and function names.
[sbcl.git] / src / pcl / gray-streams.lisp
index f34ebbb..f182d4e 100644 (file)
@@ -1,45 +1,73 @@
 ;;;; Gray streams implementation for SBCL, based on the Gray streams
-;;;; implementation for CMU CL, based on the stream-definition-by-user proposal
-;;;; by David N. Gray.
+;;;; implementation for CMU CL, based on the stream-definition-by-user
+;;;; proposal by David N. Gray.
 
 ;;;; This software is part of the SBCL system. See the README file for
 ;;;; more information.
 
-;;;; This software is in the public domain and is provided with absolutely no
-;;;; warranty. See the COPYING and CREDITS files for more information.
+;;;; This software is in the public domain and is provided with
+;;;; absolutely no warranty. See the COPYING and CREDITS files for
+;;;; more information.
 
 (in-package "SB-GRAY")
 
-(sb-int:file-comment
-  "$Header$")
+;;; BUG-OR-ERROR: because we have extensible streams, wherewith the
+;;; user is responsible for some of the protocol implementation, it's
+;;; not necessarily a bug in SBCL itself if we fall through to one of
+;;; these default methods.
+;;;
+;;; FIXME: there's a lot of similarity in these Gray stream
+;;; implementation generic functions.  All of them could (maybe
+;;; should?) have two default methods: one on STREAM calling
+;;; BUG-OR-ERROR, and one on T signalling a TYPE-ERROR.
+(defmacro bug-or-error (stream fun)
+  `(error
+    "~@<The stream ~S has no suitable method for ~S, ~
+     and so has fallen through to this method.  If you think that this is ~
+     a bug, please report it to the applicable authority (bugs in SBCL itself ~
+     should go to the mailing lists referenced from ~
+     <http://www.sbcl.org/>).~@:>"
+    ,stream ,fun))
 \f
 (fmakunbound 'stream-element-type)
 
 (defgeneric stream-element-type (stream)
   #+sb-doc
   (:documentation
-   "Returns a type specifier for the kind of object returned by the
-  Stream. Class FUNDAMENTAL-CHARACTER-STREAM provides a default method
+   "Return a type specifier for the kind of object returned by the
+  STREAM. The class FUNDAMENTAL-CHARACTER-STREAM provides a default method
   which returns CHARACTER."))
 
-(defmethod stream-element-type ((stream lisp-stream))
-  (funcall (lisp-stream-misc stream) stream :element-type))
+(defmethod stream-element-type ((stream ansi-stream))
+  (ansi-stream-element-type stream))
 
 (defmethod stream-element-type ((stream fundamental-character-stream))
   'character)
+
+(defmethod stream-element-type ((stream stream))
+  (bug-or-error stream 'stream-element-type))
+
+(defmethod stream-element-type ((non-stream t))
+  (error 'type-error :datum non-stream :expected-type 'stream))
 \f
 (defgeneric pcl-open-stream-p (stream)
   #+sb-doc
   (:documentation
-   "Return true if Stream is not closed. A default method is provided
+   "Return true if STREAM is not closed. A default method is provided
   by class FUNDAMENTAL-STREAM which returns true if CLOSE has not been
   called on the stream."))
 
-(defmethod pcl-open-stream-p ((stream lisp-stream))
-  (not (eq (lisp-stream-in stream) #'closed-flame)))
+(defmethod pcl-open-stream-p ((stream ansi-stream))
+  (ansi-stream-open-stream-p stream))
 
 (defmethod pcl-open-stream-p ((stream fundamental-stream))
-  nil)
+  (stream-open-p stream))
+
+(defmethod pcl-open-stream-p ((stream stream))
+  (bug-or-error stream 'open-stream-p))
+
+(defmethod pcl-open-stream-p ((non-stream t))
+  (error 'type-error :datum non-stream :expected-type 'stream))
 
 ;;; bootstrapping hack
 (pcl-open-stream-p (make-string-output-stream))
 (defgeneric pcl-close (stream &key abort)
   #+sb-doc
   (:documentation
-   "Closes the given Stream. No more I/O may be performed, but
-  inquiries may still be made. If :Abort is non-nil, an attempt is made
+   "Close the given STREAM. No more I/O may be performed, but
+  inquiries may still be made. If :ABORT is true, an attempt is made
   to clean up the side effects of having created the stream."))
 
-(defmethod pcl-close ((stream lisp-stream) &key abort)
-  (when (open-stream-p stream)
-    (funcall (lisp-stream-misc stream) stream :close abort))
+(defmethod pcl-close ((stream ansi-stream) &key abort)
+  (ansi-stream-close stream abort))
+
+(defmethod pcl-close ((stream fundamental-stream) &key abort)
+  (declare (ignore abort))
+  (setf (stream-open-p stream) nil)
   t)
 
-(setf (fdefinition 'close) #'pcl-close)
+(progn
+  ;; KLUDGE: Get in a call to PCL-CLOSE with a string-output-stream before
+  ;; setting it as CLOSE. Otherwise using NAMED-LAMBDAs as DFUNs causes a
+  ;; vicious metacircle from FORMAT NIL somewhere in the compiler. This is
+  ;; enough to get the dispatch settled down before we need it.
+  (pcl-close (make-string-output-stream))
+  (setf (fdefinition 'close) #'pcl-close))
 \f
-(fmakunbound 'input-stream-p)
+(let ()
+  (fmakunbound 'input-stream-p)
 
-(defgeneric input-stream-p (stream)
-  #+sb-doc
-  (:documentation "Returns non-nil if the given Stream can perform input operations."))
+  (defgeneric input-stream-p (stream)
+    #+sb-doc
+    (:documentation "Can STREAM perform input operations?"))
 
-(defmethod input-stream-p ((stream lisp-stream))
-  (and (not (eq (lisp-stream-in stream) #'closed-flame))
-       (or (not (eq (lisp-stream-in stream) #'ill-in))
-          (not (eq (lisp-stream-bin stream) #'ill-bin)))))
+  (defmethod input-stream-p ((stream ansi-stream))
+    (ansi-stream-input-stream-p stream))
 
-(defmethod input-stream-p ((stream fundamental-input-stream))
-  t)
+  (defmethod input-stream-p ((stream fundamental-stream))
+    nil)
+
+  (defmethod input-stream-p ((stream fundamental-input-stream))
+    t)
+
+  (defmethod input-stream-p ((stream stream))
+    (bug-or-error stream 'input-stream-p))
+
+  (defmethod input-stream-p ((non-stream t))
+    (error 'type-error :datum non-stream :expected-type 'stream)))
 \f
-(fmakunbound 'output-stream-p)
+(let ()
+  (fmakunbound 'interactive-stream-p)
 
-(defgeneric output-stream-p (stream)
-  #+sb-doc
-  (:documentation "Returns non-nil if the given Stream can perform output operations."))
+  (defgeneric interactive-stream-p (stream)
+    #+sb-doc
+    (:documentation "Is STREAM an interactive stream?"))
 
-(defmethod output-stream-p ((stream lisp-stream))
-  (and (not (eq (lisp-stream-in stream) #'closed-flame))
-       (or (not (eq (lisp-stream-out stream) #'ill-out))
-          (not (eq (lisp-stream-bout stream) #'ill-bout)))))
+  (defmethod interactive-stream-p ((stream ansi-stream))
+    (funcall (ansi-stream-misc stream) stream :interactive-p))
 
-(defmethod output-stream-p ((stream fundamental-output-stream))
-  t)
+  (defmethod interactive-stream-p ((stream fundamental-stream))
+    nil)
+
+  (defmethod interactive-stream-p ((stream stream))
+    (bug-or-error stream 'interactive-stream-p))
+
+  (defmethod interactive-stream-p ((non-stream t))
+    (error 'type-error :datum non-stream :expected-type 'stream)))
+\f
+(let ()
+  (fmakunbound 'output-stream-p)
+
+  (defgeneric output-stream-p (stream)
+    #+sb-doc
+    (:documentation "Can STREAM perform output operations?"))
+
+  (defmethod output-stream-p ((stream ansi-stream))
+    (ansi-stream-output-stream-p stream))
+
+  (defmethod output-stream-p ((stream fundamental-stream))
+    nil)
+
+  (defmethod output-stream-p ((stream fundamental-output-stream))
+    t)
+
+  (defmethod output-stream-p ((stream stream))
+    (bug-or-error stream 'output-stream-p))
+
+  (defmethod output-stream-p ((non-stream t))
+    (error 'type-error :datum non-stream :expected-type 'stream)))
 \f
 ;;; character input streams
 ;;;
 (defgeneric stream-read-char (stream)
   #+sb-doc
   (:documentation
-   "This reads one character from the stream. It returns either a
+   "Read one character from the stream. Return either a
   character object, or the symbol :EOF if the stream is at end-of-file.
   Every subclass of FUNDAMENTAL-CHARACTER-INPUT-STREAM must define a
   method for this function."))
 (defgeneric stream-unread-char (stream character)
   #+sb-doc
   (:documentation
-   "Un-does the last call to STREAM-READ-CHAR, as in UNREAD-CHAR.
-  Returns NIL. Every subclass of FUNDAMENTAL-CHARACTER-INPUT-STREAM
+   "Undo the last call to STREAM-READ-CHAR, as in UNREAD-CHAR.
+  Return NIL. Every subclass of FUNDAMENTAL-CHARACTER-INPUT-STREAM
   must define a method for this function."))
 
 (defgeneric stream-read-char-no-hang (stream)
 (defgeneric stream-peek-char (stream)
   #+sb-doc
   (:documentation
-   "Used to implement PEEK-CHAR; this corresponds to peek-type of NIL.
+   "This is used to implement PEEK-CHAR; this corresponds to PEEK-TYPE of NIL.
   It returns either a character or :EOF. The default method calls
   STREAM-READ-CHAR and STREAM-UNREAD-CHAR."))
 
 (defgeneric stream-listen (stream)
   #+sb-doc
   (:documentation
-   "Used by LISTEN. Returns true or false. The default method uses
+   "This is used by LISTEN. It returns true or false. The default method uses
   STREAM-READ-CHAR-NO-HANG and STREAM-UNREAD-CHAR. Most streams should
   define their own method since it will usually be trivial and will
   always be more efficient than the default method."))
 (defgeneric stream-read-line (stream)
   #+sb-doc
   (:documentation
-   "Used by READ-LINE. A string is returned as the first value. The
+   "This is used by READ-LINE. A string is returned as the first value. The
   second value is true if the string was terminated by end-of-file
   instead of the end of a line. The default method uses repeated
   calls to STREAM-READ-CHAR."))
 
 (defmethod stream-read-line ((stream fundamental-character-input-stream))
   (let ((res (make-string 80))
-       (len 80)
-       (index 0))
+        (len 80)
+        (index 0))
     (loop
      (let ((ch (stream-read-char stream)))
        (cond ((eq ch :eof)
-             (return (values (shrink-vector res index) t)))
-            (t
-             (when (char= ch #\newline)
-               (return (values (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)))))))
+              (return (values (%shrink-vector res index) t)))
+             (t
+              (when (char= ch #\newline)
+                (return (values (%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)))))))
 
 (defgeneric stream-clear-input (stream)
   #+sb-doc
   (:documentation
-   "Implements CLEAR-INPUT for the stream, returning NIL. The default
-  method does nothing."))
+   "This is like CL:CLEAR-INPUT, but for Gray streams, returning NIL.
+  The default method does nothing."))
 
 (defmethod stream-clear-input ((stream fundamental-character-input-stream))
   nil)
+(defmethod stream-clear-input ((stream stream))
+  (bug-or-error stream 'stream-clear-input))
+(defmethod stream-clear-input ((non-stream t))
+  (error 'type-error :datum non-stream :expected-type 'stream))
+
+(defgeneric stream-read-sequence (stream seq &optional start end)
+  #+sb-doc
+  (:documentation
+   "This is like CL:READ-SEQUENCE, but for Gray streams."))
+
+;;; Destructively modify SEQ by reading elements from STREAM. That
+;;; part of SEQ bounded by START and END is destructively modified by
+;;; copying successive elements into it from STREAM. If the end of
+;;; file for STREAM is reached before copying all elements of the
+;;; subsequence, then the extra elements near the end of sequence are
+;;; not updated, and the index of the next element is returned.
+(defun basic-io-type-stream-read-sequence (stream seq start end read-fun)
+  (declare (type sequence seq)
+           (type stream stream)
+           (type index start)
+           (type sequence-end end)
+           (type function read-fun)
+           (values index))
+  (let ((end (or end (length seq))))
+    (declare (type index end))
+    (etypecase seq
+      (list
+        (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-fun stream)))
+            (when (eq el :eof)
+              (return i))
+            (setf (first rem) el))))
+      (vector
+        (with-array-data ((data seq) (offset-start start) (offset-end end))
+          (do ((i offset-start (1+ i)))
+              ((>= i offset-end) end)
+            (declare (type index i))
+            (let ((el (funcall read-fun stream)))
+              (when (eq el :eof)
+                (return (+ start (- i offset-start))))
+              (setf (aref data i) el))))))))
+
+(defmethod stream-read-sequence ((stream fundamental-character-input-stream)
+                                 (seq sequence)
+                                 &optional (start 0) (end nil))
+  (basic-io-type-stream-read-sequence stream seq start end
+                                      #'stream-read-char))
+
+(defmethod stream-read-sequence ((stream fundamental-binary-input-stream)
+                                 (seq sequence)
+                                 &optional (start 0) (end nil))
+  (basic-io-type-stream-read-sequence stream seq start end
+                                      #'stream-read-byte))
+
 \f
 ;;; character output streams
 ;;;
 (defgeneric stream-write-char (stream character)
   #+sb-doc
   (:documentation
-   "Writes character to the stream and returns the character. Every
+   "Write CHARACTER to STREAM and return CHARACTER. Every
   subclass of FUNDAMENTAL-CHARACTER-OUTPUT-STREAM must have a method
   defined for this function."))
 
 (defgeneric stream-line-column (stream)
   #+sb-doc
   (:documentation
-   "This function returns the column number where the next character
+   "Return the column number where the next character
   will be written, or NIL if that is not meaningful for this stream.
   The first column on a line is numbered 0. This function is used in
   the implementation of PPRINT and the FORMAT ~T directive. For every
   defined for this function, although it is permissible for it to
   always return NIL."))
 
+(defmethod stream-line-column ((stream fundamental-character-output-stream))
+   nil)
+
 ;;; STREAM-LINE-LENGTH is a CMU CL extension to Gray streams.
 ;;; FIXME: Should we support it? Probably not..
 (defgeneric stream-line-length (stream)
   #+sb-doc
-  (:documentation "Return the stream line length or Nil."))
+  (:documentation "Return the stream line length or NIL."))
 
 (defmethod stream-line-length ((stream fundamental-character-output-stream))
   nil)
 (defgeneric stream-start-line-p (stream)
   #+sb-doc
   (:documentation
-   "This is a predicate which returns T if the stream is positioned at
-  the beginning of a line, else NIL. It is permissible to always return
+   "Is STREAM known to be positioned at the beginning of a line?
+  It is permissible for an implementation to always return
   NIL. This is used in the implementation of FRESH-LINE. Note that
   while a value of 0 from STREAM-LINE-COLUMN also indicates the
   beginning of a line, there are cases where STREAM-START-LINE-P can be
 (defmethod stream-start-line-p ((stream fundamental-character-output-stream))
   (eql (stream-line-column stream) 0))
 
-(defgeneric stream-write-string (stream string &optional (start 0) end)
+(defgeneric stream-write-string (stream string &optional start end)
   #+sb-doc
   (:documentation
    "This is used by WRITE-STRING. It writes the string to the stream,
   STREAM-WRITE-CHAR."))
 
 (defmethod stream-write-string ((stream fundamental-character-output-stream)
-                               string &optional (start 0) end)
+                                string &optional (start 0) end)
   (declare (string string)
-          (fixnum start))
+           (fixnum start))
   (let ((end (or end (length string))))
     (declare (fixnum end))
     (do ((pos start (1+ pos)))
-       ((>= pos end))
+        ((>= pos end))
       (declare (type index pos))
       (stream-write-char stream (aref string pos))))
   string)
   #+sb-doc
   (:documentation
    "Outputs a new line to the Stream if it is not positioned at the
-  begining of a line. Returns T if it output a new line, nil
+  beginning of a line. Returns T if it output a new line, nil
   otherwise. Used by FRESH-LINE. The default method uses
   STREAM-START-LINE-P and STREAM-TERPRI."))
 
 
 (defmethod stream-finish-output ((stream fundamental-output-stream))
   nil)
+(defmethod stream-finish-output ((stream stream))
+  (bug-or-error stream 'stream-finish-output))
+(defmethod stream-finish-output ((non-stream t))
+  (error 'type-error :datum non-stream :expected-type 'stream))
 
 (defgeneric stream-force-output (stream)
   #+sb-doc
 
 (defmethod stream-force-output ((stream fundamental-output-stream))
   nil)
+(defmethod stream-force-output ((stream stream))
+  (bug-or-error stream 'stream-force-output))
+(defmethod stream-force-output ((non-stream t))
+  (error 'type-error :datum non-stream :expected-type 'stream))
 
 (defgeneric stream-clear-output (stream)
   #+sb-doc
   (:documentation
-   "Clears the given output Stream. Implements CLEAR-OUTPUT. The
-  default method does nothing."))
+   "This is like CL:CLEAR-OUTPUT, but for Gray streams: clear the given
+  output STREAM. The default method does nothing."))
 
 (defmethod stream-clear-output ((stream fundamental-output-stream))
   nil)
+(defmethod stream-clear-output ((stream stream))
+  (bug-or-error stream 'stream-clear-output))
+(defmethod stream-clear-output ((non-stream t))
+  (error 'type-error :datum non-stream :expected-type 'stream))
 
 (defgeneric stream-advance-to-column (stream column)
   #+sb-doc
   (:documentation
-   "Writes enough blank space so that the next character will be
+   "Write enough blank space so that the next character will be
   written at the specified column. Returns true if the operation is
   successful, or NIL if it is not supported for this stream. This is
   intended for use by by PPRINT and FORMAT ~T. The default method uses
   #\SPACE character; it returns NIL if STREAM-LINE-COLUMN returns NIL."))
 
 (defmethod stream-advance-to-column ((stream fundamental-character-output-stream)
-                                    column)
+                                     column)
   (let ((current-column (stream-line-column stream)))
     (when current-column
       (let ((fill (- column current-column)))
-       (dotimes-fixnum (i fill)
-         (stream-write-char stream #\Space)))
+        (dotimes (i fill)
+          (stream-write-char stream #\Space)))
       T)))
+
+(defgeneric stream-write-sequence (stream seq &optional start end)
+  #+sb-doc
+  (:documentation
+   "This is like CL:WRITE-SEQUENCE, but for Gray streams."))
+
+;;; Write the elements of SEQ bounded by START and END to STREAM.
+(defun basic-io-type-stream-write-sequence (stream seq start end write-fun)
+  (declare (type sequence seq)
+           (type stream stream)
+           (type index start)
+           (type sequence-end end)
+           (type function write-fun)
+           (values sequence))
+  (let ((end (or end (length seq))))
+    (declare (type index start end))
+    (etypecase seq
+      (list
+        (do ((rem (nthcdr start seq) (rest rem))
+             (i start (1+ i)))
+            ((or (endp rem) (>= i end)) seq)
+          (declare (type list rem)
+                   (type index i))
+          (funcall write-fun stream (first rem))))
+      (vector
+        (do ((i start (1+ i)))
+            ((>= i end) seq)
+          (declare (type index i))
+          (funcall write-fun stream (aref seq i)))))))
+
+(defmethod stream-write-sequence ((stream fundamental-character-output-stream)
+                                  (seq sequence)
+                                  &optional (start 0) (end nil))
+  (typecase seq
+    (string
+      (stream-write-string stream seq start end))
+    (t
+      (basic-io-type-stream-write-sequence stream seq start end
+                                           #'stream-write-char))))
+
 \f
 ;;; binary streams
 ;;;
    "Used by READ-BYTE; returns either an integer, or the symbol :EOF
   if the stream is at end-of-file."))
 
+(defmethod stream-read-byte ((stream stream))
+  (bug-or-error stream 'stream-read-byte))
+(defmethod stream-read-byte ((non-stream t))
+  (error 'type-error :datum non-stream :expected-type 'stream))
+
 (defgeneric stream-write-byte (stream integer)
   #+sb-doc
   (:documentation
    "Implements WRITE-BYTE; writes the integer to the stream and
   returns the integer as the result."))
+
+(defmethod stream-write-byte ((stream stream) integer)
+  (bug-or-error stream 'stream-write-byte))
+(defmethod stream-write-byte ((non-stream t) integer)
+  (error 'type-error :datum non-stream :expected-type 'stream))
+
+;; Provide a reasonable default for binary Gray streams.  We might be
+;; able to do better by specializing on the sequence type, but at
+;; least the behaviour is reasonable. --tony 2003/05/08.
+(defmethod stream-write-sequence ((stream fundamental-binary-output-stream)
+                                  (seq sequence)
+                                  &optional (start 0) (end nil))
+  (basic-io-type-stream-write-sequence stream seq start end
+                                       #'stream-write-byte))
+
+(defgeneric stream-file-position (stream &optional position-spec)
+  #+sb-doc
+  (:documentation
+   "Used by FILE-POSITION. Returns or changes the current position within STREAM."))
+
+(defmethod stream-file-position ((stream ansi-stream) &optional position-spec)
+  (ansi-stream-file-position stream position-spec))
+
+(defmethod stream-file-position ((stream t) &optional position-spec)
+  (declare (ignore stream position-spec))
+  nil)
+
 \f
+;;; This is not in the Gray stream proposal, so it is left here
+;;; as example code.
+#|
 ;;; example character output stream encapsulating a lisp-stream
 (defun make-character-output-stream (lisp-stream)
   (declare (type lisp-stream lisp-stream))
   (output-stream-p (character-input-stream-lisp-stream stream)))
 
 (defmethod stream-read-char ((stream character-input-stream))
-  (read-char (character-input-stream-lisp-stream stream)))
+  (read-char (character-input-stream-lisp-stream stream) nil :eof))
 
 (defmethod stream-unread-char ((stream character-input-stream) character)
   (unread-char character (character-input-stream-lisp-stream stream)))
 
 (defmethod stream-clear-input ((stream character-input-stream))
   (clear-input (character-input-stream-lisp-stream stream)))
+|#