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