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