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