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