1.0.1.23:
[sbcl.git] / src / pcl / gray-streams.lisp
1 ;;;; Gray streams implementation for SBCL, based on the Gray streams
2 ;;;; implementation for CMU CL, based on the stream-definition-by-user
3 ;;;; proposal by David N. Gray.
4
5 ;;;; This software is part of the SBCL system. See the README file for
6 ;;;; more information.
7
8 ;;;; This software is in the public domain and is provided with
9 ;;;; absolutely no warranty. See the COPYING and CREDITS files for
10 ;;;; more information.
11
12 (in-package "SB-GRAY")
13
14 ;;; BUG-OR-ERROR: because we have extensible streams, wherewith the
15 ;;; user is responsible for some of the protocol implementation, it's
16 ;;; not necessarily a bug in SBCL itself if we fall through to one of
17 ;;; these default methods.
18 ;;;
19 ;;; FIXME: there's a lot of similarity in these Gray stream
20 ;;; implementation generic functions.  All of them could (maybe
21 ;;; should?) have two default methods: one on STREAM calling
22 ;;; BUG-OR-ERROR, and one on T signalling a TYPE-ERROR.
23 (defmacro bug-or-error (stream fun)
24   `(error
25     "~@<The stream ~S has no suitable method for ~S, ~
26      and so has fallen through to this method.  If you think that this is ~
27      a bug, please report it to the applicable authority (bugs in SBCL itself ~
28      should go to the mailing lists referenced from ~
29      <http://www.sbcl.org/>).~@:>"
30     ,stream ,fun))
31 \f
32 (fmakunbound 'stream-element-type)
33
34 (defgeneric stream-element-type (stream)
35   #+sb-doc
36   (:documentation
37    "Return a type specifier for the kind of object returned by the
38   STREAM. The class FUNDAMENTAL-CHARACTER-STREAM provides a default method
39   which returns CHARACTER."))
40
41 (defmethod stream-element-type ((stream ansi-stream))
42   (ansi-stream-element-type stream))
43
44 (defmethod stream-element-type ((stream fundamental-character-stream))
45   'character)
46
47 (defmethod stream-element-type ((stream stream))
48   (bug-or-error stream 'stream-element-type))
49
50 (defmethod stream-element-type ((non-stream t))
51   (error 'type-error :datum non-stream :expected-type 'stream))
52 \f
53 (defgeneric pcl-open-stream-p (stream)
54   #+sb-doc
55   (:documentation
56    "Return true if STREAM is not closed. A default method is provided
57   by class FUNDAMENTAL-STREAM which returns true if CLOSE has not been
58   called on the stream."))
59
60 (defmethod pcl-open-stream-p ((stream ansi-stream))
61   (ansi-stream-open-stream-p stream))
62
63 (defmethod pcl-open-stream-p ((stream fundamental-stream))
64   (stream-open-p stream))
65
66 (defmethod pcl-open-stream-p ((stream stream))
67   (bug-or-error stream 'open-stream-p))
68
69 (defmethod pcl-open-stream-p ((non-stream t))
70   (error 'type-error :datum non-stream :expected-type 'stream))
71
72 ;;; bootstrapping hack
73 (pcl-open-stream-p (make-string-output-stream))
74 (setf (fdefinition 'open-stream-p) #'pcl-open-stream-p)
75 \f
76 (defgeneric pcl-close (stream &key abort)
77   #+sb-doc
78   (:documentation
79    "Close the given STREAM. No more I/O may be performed, but
80   inquiries may still be made. If :ABORT is true, an attempt is made
81   to clean up the side effects of having created the stream."))
82
83 (defmethod pcl-close ((stream ansi-stream) &key abort)
84   (ansi-stream-close stream abort))
85
86 (defmethod pcl-close ((stream fundamental-stream) &key abort)
87   (declare (ignore abort))
88   (setf (stream-open-p stream) nil)
89   t)
90
91 (setf (fdefinition 'close) #'pcl-close)
92 \f
93 (let ()
94   (fmakunbound 'input-stream-p)
95
96   (defgeneric input-stream-p (stream)
97     #+sb-doc
98     (:documentation "Can STREAM perform input operations?"))
99
100   (defmethod input-stream-p ((stream ansi-stream))
101     (ansi-stream-input-stream-p stream))
102
103   (defmethod input-stream-p ((stream fundamental-stream))
104     nil)
105
106   (defmethod input-stream-p ((stream fundamental-input-stream))
107     t)
108
109   (defmethod input-stream-p ((stream stream))
110     (bug-or-error stream 'input-stream-p))
111
112   (defmethod input-stream-p ((non-stream t))
113     (error 'type-error :datum non-stream :expected-type 'stream)))
114 \f
115 (let ()
116   (fmakunbound 'interactive-stream-p)
117
118   (defgeneric interactive-stream-p (stream)
119     #+sb-doc
120     (:documentation "Is STREAM an interactive stream?"))
121
122   (defmethod interactive-stream-p ((stream ansi-stream))
123     (funcall (ansi-stream-misc stream) stream :interactive-p))
124
125   (defmethod interactive-stream-p ((stream fundamental-stream))
126     nil)
127
128   (defmethod interactive-stream-p ((stream stream))
129     (bug-or-error stream 'interactive-stream-p))
130
131   (defmethod interactive-stream-p ((non-stream t))
132     (error 'type-error :datum non-stream :expected-type 'stream)))
133 \f
134 (let ()
135   (fmakunbound 'output-stream-p)
136
137   (defgeneric output-stream-p (stream)
138     #+sb-doc
139     (:documentation "Can STREAM perform output operations?"))
140
141   (defmethod output-stream-p ((stream ansi-stream))
142     (ansi-stream-output-stream-p stream))
143
144   (defmethod output-stream-p ((stream fundamental-stream))
145     nil)
146
147   (defmethod output-stream-p ((stream fundamental-output-stream))
148     t)
149
150   (defmethod output-stream-p ((stream stream))
151     (bug-or-error stream 'output-stream-p))
152
153   (defmethod output-stream-p ((non-stream t))
154     (error 'type-error :datum non-stream :expected-type 'stream)))
155 \f
156 ;;; character input streams
157 ;;;
158 ;;; A character input stream can be created by defining a class that
159 ;;; includes FUNDAMENTAL-CHARACTER-INPUT-STREAM and defining methods
160 ;;; for the generic functions below.
161
162 (defgeneric stream-read-char (stream)
163   #+sb-doc
164   (:documentation
165    "Read one character from the stream. Return either a
166   character object, or the symbol :EOF if the stream is at end-of-file.
167   Every subclass of FUNDAMENTAL-CHARACTER-INPUT-STREAM must define a
168   method for this function."))
169
170 (defgeneric stream-unread-char (stream character)
171   #+sb-doc
172   (:documentation
173    "Un-do the last call to STREAM-READ-CHAR, as in UNREAD-CHAR.
174   Return NIL. Every subclass of FUNDAMENTAL-CHARACTER-INPUT-STREAM
175   must define a method for this function."))
176
177 (defgeneric stream-read-char-no-hang (stream)
178   #+sb-doc
179   (:documentation
180    "This is used to implement READ-CHAR-NO-HANG. It returns either a
181   character, or NIL if no input is currently available, or :EOF if
182   end-of-file is reached. The default method provided by
183   FUNDAMENTAL-CHARACTER-INPUT-STREAM simply calls STREAM-READ-CHAR; this
184   is sufficient for file streams, but interactive streams should define
185   their own method."))
186
187 (defmethod stream-read-char-no-hang ((stream fundamental-character-input-stream))
188   (stream-read-char stream))
189
190 (defgeneric stream-peek-char (stream)
191   #+sb-doc
192   (:documentation
193    "This is used to implement PEEK-CHAR; this corresponds to PEEK-TYPE of NIL.
194   It returns either a character or :EOF. The default method calls
195   STREAM-READ-CHAR and STREAM-UNREAD-CHAR."))
196
197 (defmethod stream-peek-char ((stream fundamental-character-input-stream))
198   (let ((char (stream-read-char stream)))
199     (unless (eq char :eof)
200       (stream-unread-char stream char))
201     char))
202
203 (defgeneric stream-listen (stream)
204   #+sb-doc
205   (:documentation
206    "This is used by LISTEN. It returns true or false. The default method uses
207   STREAM-READ-CHAR-NO-HANG and STREAM-UNREAD-CHAR. Most streams should
208   define their own method since it will usually be trivial and will
209   always be more efficient than the default method."))
210
211 (defmethod stream-listen ((stream fundamental-character-input-stream))
212   (let ((char (stream-read-char-no-hang stream)))
213     (when (characterp char)
214       (stream-unread-char stream char)
215       t)))
216
217 (defgeneric stream-read-line (stream)
218   #+sb-doc
219   (:documentation
220    "This is used by READ-LINE. A string is returned as the first value. The
221   second value is true if the string was terminated by end-of-file
222   instead of the end of a line. The default method uses repeated
223   calls to STREAM-READ-CHAR."))
224
225 (defmethod stream-read-line ((stream fundamental-character-input-stream))
226   (let ((res (make-string 80))
227         (len 80)
228         (index 0))
229     (loop
230      (let ((ch (stream-read-char stream)))
231        (cond ((eq ch :eof)
232               (return (values (%shrink-vector res index) t)))
233              (t
234               (when (char= ch #\newline)
235                 (return (values (%shrink-vector res index) nil)))
236               (when (= index len)
237                 (setq len (* len 2))
238                 (let ((new (make-string len)))
239                   (replace new res)
240                   (setq res new)))
241               (setf (schar res index) ch)
242               (incf index)))))))
243
244 (defgeneric stream-clear-input (stream)
245   #+sb-doc
246   (:documentation
247    "This is like CL:CLEAR-INPUT, but for Gray streams, returning NIL.
248   The default method does nothing."))
249
250 (defmethod stream-clear-input ((stream fundamental-character-input-stream))
251   nil)
252 (defmethod stream-clear-input ((stream stream))
253   (bug-or-error stream 'stream-clear-input))
254 (defmethod stream-clear-input ((non-stream t))
255   (error 'type-error :datum non-stream :expected-type 'stream))
256
257 (defgeneric stream-read-sequence (stream seq &optional start end)
258   #+sb-doc
259   (:documentation
260    "This is like CL:READ-SEQUENCE, but for Gray streams."))
261
262 ;;; Destructively modify SEQ by reading elements from STREAM. That
263 ;;; part of SEQ bounded by START and END is destructively modified by
264 ;;; copying successive elements into it from STREAM. If the end of
265 ;;; file for STREAM is reached before copying all elements of the
266 ;;; subsequence, then the extra elements near the end of sequence are
267 ;;; not updated, and the index of the next element is returned.
268 (defun basic-io-type-stream-read-sequence (stream seq start end read-fun)
269   (declare (type sequence seq)
270            (type stream stream)
271            (type index start)
272            (type sequence-end end)
273            (type function read-fun)
274            (values index))
275   (let ((end (or end (length seq))))
276     (declare (type index end))
277     (etypecase seq
278       (list
279         (do ((rem (nthcdr start seq) (rest rem))
280              (i start (1+ i)))
281             ((or (endp rem) (>= i end)) i)
282           (declare (type list rem)
283                    (type index i))
284           (let ((el (funcall read-fun stream)))
285             (when (eq el :eof)
286               (return i))
287             (setf (first rem) el))))
288       (vector
289         (with-array-data ((data seq) (offset-start start) (offset-end end))
290           (do ((i offset-start (1+ i)))
291               ((>= i offset-end) end)
292             (declare (type index i))
293             (let ((el (funcall read-fun stream)))
294               (when (eq el :eof)
295                 (return (+ start (- i offset-start))))
296               (setf (aref data i) el))))))))
297
298 (defmethod stream-read-sequence ((stream fundamental-character-input-stream)
299                                  (seq sequence)
300                                  &optional (start 0) (end nil))
301   (basic-io-type-stream-read-sequence stream seq start end
302                                       #'stream-read-char))
303
304 (defmethod stream-read-sequence ((stream fundamental-binary-input-stream)
305                                  (seq sequence)
306                                  &optional (start 0) (end nil))
307   (basic-io-type-stream-read-sequence stream seq start end
308                                       #'stream-read-byte))
309
310 \f
311 ;;; character output streams
312 ;;;
313 ;;; A character output stream can be created by defining a class that
314 ;;; includes FUNDAMENTAL-CHARACTER-OUTPUT-STREAM and defining methods
315 ;;; for the generic functions below.
316
317 (defgeneric stream-write-char (stream character)
318   #+sb-doc
319   (:documentation
320    "Write CHARACTER to STREAM and return CHARACTER. Every
321   subclass of FUNDAMENTAL-CHARACTER-OUTPUT-STREAM must have a method
322   defined for this function."))
323
324 (defgeneric stream-line-column (stream)
325   #+sb-doc
326   (:documentation
327    "Return the column number where the next character
328   will be written, or NIL if that is not meaningful for this stream.
329   The first column on a line is numbered 0. This function is used in
330   the implementation of PPRINT and the FORMAT ~T directive. For every
331   character output stream class that is defined, a method must be
332   defined for this function, although it is permissible for it to
333   always return NIL."))
334
335 (defmethod stream-line-column ((stream fundamental-character-output-stream))
336    nil)
337
338 ;;; STREAM-LINE-LENGTH is a CMU CL extension to Gray streams.
339 ;;; FIXME: Should we support it? Probably not..
340 (defgeneric stream-line-length (stream)
341   #+sb-doc
342   (:documentation "Return the stream line length or NIL."))
343
344 (defmethod stream-line-length ((stream fundamental-character-output-stream))
345   nil)
346
347 (defgeneric stream-start-line-p (stream)
348   #+sb-doc
349   (:documentation
350    "Is STREAM known to be positioned at the beginning of a line?
351   It is permissible for an implementation to always return
352   NIL. This is used in the implementation of FRESH-LINE. Note that
353   while a value of 0 from STREAM-LINE-COLUMN also indicates the
354   beginning of a line, there are cases where STREAM-START-LINE-P can be
355   meaningfully implemented although STREAM-LINE-COLUMN can't be. For
356   example, for a window using variable-width characters, the column
357   number isn't very meaningful, but the beginning of the line does have
358   a clear meaning. The default method for STREAM-START-LINE-P on class
359   FUNDAMENTAL-CHARACTER-OUTPUT-STREAM uses STREAM-LINE-COLUMN, so if
360   that is defined to return NIL, then a method should be provided for
361   either STREAM-START-LINE-P or STREAM-FRESH-LINE."))
362
363 (defmethod stream-start-line-p ((stream fundamental-character-output-stream))
364   (eql (stream-line-column stream) 0))
365
366 (defgeneric stream-write-string (stream string &optional start end)
367   #+sb-doc
368   (:documentation
369    "This is used by WRITE-STRING. It writes the string to the stream,
370   optionally delimited by start and end, which default to 0 and NIL.
371   The string argument is returned. The default method provided by
372   FUNDAMENTAL-CHARACTER-OUTPUT-STREAM uses repeated calls to
373   STREAM-WRITE-CHAR."))
374
375 (defmethod stream-write-string ((stream fundamental-character-output-stream)
376                                 string &optional (start 0) end)
377   (declare (string string)
378            (fixnum start))
379   (let ((end (or end (length string))))
380     (declare (fixnum end))
381     (do ((pos start (1+ pos)))
382         ((>= pos end))
383       (declare (type index pos))
384       (stream-write-char stream (aref string pos))))
385   string)
386
387 (defgeneric stream-terpri (stream)
388   #+sb-doc
389   (:documentation
390    "Writes an end of line, as for TERPRI. Returns NIL. The default
391   method does (STREAM-WRITE-CHAR stream #\NEWLINE)."))
392
393 (defmethod stream-terpri ((stream fundamental-character-output-stream))
394   (stream-write-char stream #\Newline))
395
396 (defgeneric stream-fresh-line (stream)
397   #+sb-doc
398   (:documentation
399    "Outputs a new line to the Stream if it is not positioned at the
400   begining of a line. Returns T if it output a new line, nil
401   otherwise. Used by FRESH-LINE. The default method uses
402   STREAM-START-LINE-P and STREAM-TERPRI."))
403
404 (defmethod stream-fresh-line ((stream fundamental-character-output-stream))
405   (unless (stream-start-line-p stream)
406     (stream-terpri stream)
407     t))
408
409 (defgeneric stream-finish-output (stream)
410   #+sb-doc
411   (:documentation
412    "Attempts to ensure that all output sent to the Stream has reached
413   its destination, and only then returns false. Implements
414   FINISH-OUTPUT. The default method does nothing."))
415
416 (defmethod stream-finish-output ((stream fundamental-output-stream))
417   nil)
418 (defmethod stream-finish-output ((stream stream))
419   (bug-or-error stream 'stream-finish-output))
420 (defmethod stream-finish-output ((non-stream t))
421   (error 'type-error :datum non-stream :expected-type 'stream))
422
423 (defgeneric stream-force-output (stream)
424   #+sb-doc
425   (:documentation
426    "Attempts to force any buffered output to be sent. Implements
427   FORCE-OUTPUT. The default method does nothing."))
428
429 (defmethod stream-force-output ((stream fundamental-output-stream))
430   nil)
431 (defmethod stream-force-output ((stream stream))
432   (bug-or-error stream 'stream-force-output))
433 (defmethod stream-force-output ((non-stream t))
434   (error 'type-error :datum non-stream :expected-type 'stream))
435
436 (defgeneric stream-clear-output (stream)
437   #+sb-doc
438   (:documentation
439    "This is like CL:CLEAR-OUTPUT, but for Gray streams: clear the given
440   output STREAM. The default method does nothing."))
441
442 (defmethod stream-clear-output ((stream fundamental-output-stream))
443   nil)
444 (defmethod stream-clear-output ((stream stream))
445   (bug-or-error stream 'stream-clear-output))
446 (defmethod stream-clear-output ((non-stream t))
447   (error 'type-error :datum non-stream :expected-type 'stream))
448
449 (defgeneric stream-advance-to-column (stream column)
450   #+sb-doc
451   (:documentation
452    "Write enough blank space so that the next character will be
453   written at the specified column. Returns true if the operation is
454   successful, or NIL if it is not supported for this stream. This is
455   intended for use by by PPRINT and FORMAT ~T. The default method uses
456   STREAM-LINE-COLUMN and repeated calls to STREAM-WRITE-CHAR with a
457   #\SPACE character; it returns NIL if STREAM-LINE-COLUMN returns NIL."))
458
459 (defmethod stream-advance-to-column ((stream fundamental-character-output-stream)
460                                      column)
461   (let ((current-column (stream-line-column stream)))
462     (when current-column
463       (let ((fill (- column current-column)))
464         (dotimes (i fill)
465           (stream-write-char stream #\Space)))
466       T)))
467
468 (defgeneric stream-write-sequence (stream seq &optional start end)
469   #+sb-doc
470   (:documentation
471    "This is like CL:WRITE-SEQUENCE, but for Gray streams."))
472
473 ;;; Write the elements of SEQ bounded by START and END to STREAM.
474 (defun basic-io-type-stream-write-sequence (stream seq start end write-fun)
475   (declare (type sequence seq)
476            (type stream stream)
477            (type index start)
478            (type sequence-end end)
479            (type function write-fun)
480            (values sequence))
481   (let ((end (or end (length seq))))
482     (declare (type index start end))
483     (etypecase seq
484       (list
485         (do ((rem (nthcdr start seq) (rest rem))
486              (i start (1+ i)))
487             ((or (endp rem) (>= i end)) seq)
488           (declare (type list rem)
489                    (type index i))
490           (funcall write-fun stream (first rem))))
491       (vector
492         (do ((i start (1+ i)))
493             ((>= i end) seq)
494           (declare (type index i))
495           (funcall write-fun stream (aref seq i)))))))
496
497 (defmethod stream-write-sequence ((stream fundamental-character-output-stream)
498                                   (seq sequence)
499                                   &optional (start 0) (end nil))
500   (typecase seq
501     (string
502       (stream-write-string stream seq start end))
503     (t
504       (basic-io-type-stream-write-sequence stream seq start end
505                                            #'stream-write-char))))
506
507 \f
508 ;;; binary streams
509 ;;;
510 ;;; Binary streams can be created by defining a class that includes
511 ;;; either FUNDAMENTAL-BINARY-INPUT-STREAM or
512 ;;; FUNDAMENTAL-BINARY-OUTPUT-STREAM (or both) and defining a method
513 ;;; for STREAM-ELEMENT-TYPE and for one or both of the following
514 ;;; generic functions.
515
516 (defgeneric stream-read-byte (stream)
517   #+sb-doc
518   (:documentation
519    "Used by READ-BYTE; returns either an integer, or the symbol :EOF
520   if the stream is at end-of-file."))
521
522 (defmethod stream-read-byte ((stream stream))
523   (bug-or-error stream 'stream-read-byte))
524 (defmethod stream-read-byte ((non-stream t))
525   (error 'type-error :datum non-stream :expected-type 'stream))
526
527 (defgeneric stream-write-byte (stream integer)
528   #+sb-doc
529   (:documentation
530    "Implements WRITE-BYTE; writes the integer to the stream and
531   returns the integer as the result."))
532
533 (defmethod stream-write-byte ((stream stream) integer)
534   (bug-or-error stream 'stream-write-byte))
535 (defmethod stream-write-byte ((non-stream t) integer)
536   (error 'type-error :datum non-stream :expected-type 'stream))
537
538 ;; Provide a reasonable default for binary Gray streams.  We might be
539 ;; able to do better by specializing on the sequence type, but at
540 ;; least the behaviour is reasonable. --tony 2003/05/08.
541 (defmethod stream-write-sequence ((stream fundamental-binary-output-stream)
542                                   (seq sequence)
543                                   &optional (start 0) (end nil))
544   (basic-io-type-stream-write-sequence stream seq start end
545                                        #'stream-write-byte))
546
547 (defgeneric stream-file-position (stream &optional position-spec)
548   #+sb-doc
549   (:documentation
550    "Used by FILE-POSITION. Returns or changes the current position within STREAM."))
551
552 (defmethod stream-file-position ((stream ansi-stream) &optional position-spec)
553   (ansi-stream-file-position stream position-spec))
554
555 (defmethod stream-file-position ((stream t) &optional position-spec)
556   (declare (ignore stream position-spec))
557   nil)
558
559 \f
560 ;;; This is not in the Gray stream proposal, so it is left here
561 ;;; as example code.
562 #|
563 ;;; example character output stream encapsulating a lisp-stream
564 (defun make-character-output-stream (lisp-stream)
565   (declare (type lisp-stream lisp-stream))
566   (make-instance 'character-output-stream :lisp-stream lisp-stream))
567
568 (defmethod open-stream-p ((stream character-output-stream))
569   (open-stream-p (character-output-stream-lisp-stream stream)))
570
571 (defmethod close ((stream character-output-stream) &key abort)
572   (close (character-output-stream-lisp-stream stream) :abort abort))
573
574 (defmethod input-stream-p ((stream character-output-stream))
575   (input-stream-p (character-output-stream-lisp-stream stream)))
576
577 (defmethod output-stream-p ((stream character-output-stream))
578   (output-stream-p (character-output-stream-lisp-stream stream)))
579
580 (defmethod stream-write-char ((stream character-output-stream) character)
581   (write-char character (character-output-stream-lisp-stream stream)))
582
583 (defmethod stream-line-column ((stream character-output-stream))
584   (charpos (character-output-stream-lisp-stream stream)))
585
586 (defmethod stream-line-length ((stream character-output-stream))
587   (line-length (character-output-stream-lisp-stream stream)))
588
589 (defmethod stream-finish-output ((stream character-output-stream))
590   (finish-output (character-output-stream-lisp-stream stream)))
591
592 (defmethod stream-force-output ((stream character-output-stream))
593   (force-output (character-output-stream-lisp-stream stream)))
594
595 (defmethod stream-clear-output ((stream character-output-stream))
596   (clear-output (character-output-stream-lisp-stream stream)))
597 \f
598 ;;; example character input stream encapsulating a lisp-stream
599
600 (defun make-character-input-stream (lisp-stream)
601   (declare (type lisp-stream lisp-stream))
602   (make-instance 'character-input-stream :lisp-stream lisp-stream))
603
604 (defmethod open-stream-p ((stream character-input-stream))
605   (open-stream-p (character-input-stream-lisp-stream stream)))
606
607 (defmethod close ((stream character-input-stream) &key abort)
608   (close (character-input-stream-lisp-stream stream) :abort abort))
609
610 (defmethod input-stream-p ((stream character-input-stream))
611   (input-stream-p (character-input-stream-lisp-stream stream)))
612
613 (defmethod output-stream-p ((stream character-input-stream))
614   (output-stream-p (character-input-stream-lisp-stream stream)))
615
616 (defmethod stream-read-char ((stream character-input-stream))
617   (read-char (character-input-stream-lisp-stream stream) nil :eof))
618
619 (defmethod stream-unread-char ((stream character-input-stream) character)
620   (unread-char character (character-input-stream-lisp-stream stream)))
621
622 (defmethod stream-read-char-no-hang ((stream character-input-stream))
623   (read-char-no-hang (character-input-stream-lisp-stream stream) nil :eof))
624
625 #+nil
626 (defmethod stream-peek-char ((stream character-input-stream))
627   (peek-char nil (character-input-stream-lisp-stream stream) nil :eof))
628
629 #+nil
630 (defmethod stream-listen ((stream character-input-stream))
631   (listen (character-input-stream-lisp-stream stream)))
632
633 (defmethod stream-clear-input ((stream character-input-stream))
634   (clear-input (character-input-stream-lisp-stream stream)))
635 |#