d658516140fced218cb6c0959e17c17d05fa97e9
[sbcl.git] / src / code / stream.lisp
1 ;;;; os-independent stream functions
2
3 ;;;; This software is part of the SBCL system. See the README file for
4 ;;;; more information.
5 ;;;;
6 ;;;; This software is derived from the CMU CL system, which was
7 ;;;; written at Carnegie Mellon University and released into the
8 ;;;; public domain. The software is in the public domain and is
9 ;;;; provided with absolutely no warranty. See the COPYING and CREDITS
10 ;;;; files for more information.
11
12 (in-package "SB!IMPL")
13
14 ;;;; standard streams
15
16 ;;; The initialization of these streams is performed by
17 ;;; STREAM-COLD-INIT-OR-RESET.
18 (defvar *terminal-io* () #!+sb-doc "terminal I/O stream")
19 (defvar *standard-input* () #!+sb-doc "default input stream")
20 (defvar *standard-output* () #!+sb-doc "default output stream")
21 (defvar *error-output* () #!+sb-doc "error output stream")
22 (defvar *query-io* () #!+sb-doc "query I/O stream")
23 (defvar *trace-output* () #!+sb-doc "trace output stream")
24 (defvar *debug-io* () #!+sb-doc "interactive debugging stream")
25
26 (defun ill-in (stream &rest ignore)
27   (declare (ignore ignore))
28   (error 'simple-type-error
29          :datum stream
30          :expected-type '(satisfies input-stream-p)
31          :format-control "~S is not a character input stream."
32          :format-arguments (list stream)))
33 (defun ill-out (stream &rest ignore)
34   (declare (ignore ignore))
35   (error 'simple-type-error
36          :datum stream
37          :expected-type '(satisfies output-stream-p)
38          :format-control "~S is not a character output stream."
39          :format-arguments (list stream)))
40 (defun ill-bin (stream &rest ignore)
41   (declare (ignore ignore))
42   (error 'simple-type-error
43          :datum stream
44          :expected-type '(satisfies input-stream-p)
45          :format-control "~S is not a binary input stream."
46          :format-arguments (list stream)))
47 (defun ill-bout (stream &rest ignore)
48   (declare (ignore ignore))
49   (error 'simple-type-error
50          :datum stream
51          :expected-type '(satisfies output-stream-p)
52          :format-control "~S is not a binary output stream."
53          :format-arguments (list stream)))
54 (defun closed-flame (stream &rest ignore)
55   (declare (ignore ignore))
56   (error "~S is closed." stream))
57 (defun no-op-placeholder (&rest ignore)
58   (declare (ignore ignore)))
59 \f
60 ;;; stream manipulation functions
61
62 (declaim (inline ansi-stream-input-stream-p))
63 (defun ansi-stream-input-stream-p (stream)
64   (declare (type ansi-stream stream))
65
66   (when (synonym-stream-p stream)
67     (setf stream
68           (symbol-value (synonym-stream-symbol stream))))
69
70   (and (not (eq (ansi-stream-in stream) #'closed-flame))
71        ;;; KLUDGE: It's probably not good to have EQ tests on function
72        ;;; values like this. What if someone's redefined the function?
73        ;;; Is there a better way? (Perhaps just VALID-FOR-INPUT and
74        ;;; VALID-FOR-OUTPUT flags? -- WHN 19990902
75        (or (not (eq (ansi-stream-in stream) #'ill-in))
76            (not (eq (ansi-stream-bin stream) #'ill-bin)))))
77
78 (defun input-stream-p (stream)
79   (declare (type stream stream))
80   (and (ansi-stream-p stream)
81        (ansi-stream-input-stream-p stream)))
82
83 (declaim (inline ansi-stream-output-stream-p))
84 (defun ansi-stream-output-stream-p (stream)
85   (declare (type ansi-stream stream))
86
87   (when (synonym-stream-p stream)
88     (setf stream (symbol-value
89                   (synonym-stream-symbol stream))))
90
91   (and (not (eq (ansi-stream-in stream) #'closed-flame))
92        (or (not (eq (ansi-stream-out stream) #'ill-out))
93            (not (eq (ansi-stream-bout stream) #'ill-bout)))))
94
95 (defun output-stream-p (stream)
96   (declare (type stream stream))
97
98   (and (ansi-stream-p stream)
99        (ansi-stream-output-stream-p stream)))
100
101 (declaim (inline ansi-stream-open-stream-p))
102 (defun ansi-stream-open-stream-p (stream)
103   (declare (type ansi-stream stream))
104   ;; CLHS 22.1.4 lets us not worry about synonym streams here.
105   (not (eq (ansi-stream-in stream) #'closed-flame)))
106
107 (defun open-stream-p (stream)
108   (ansi-stream-open-stream-p stream))
109
110 (declaim (inline ansi-stream-element-type))
111 (defun ansi-stream-element-type (stream)
112   (declare (type ansi-stream stream))
113   (funcall (ansi-stream-misc stream) stream :element-type))
114
115 (defun stream-element-type (stream)
116   (ansi-stream-element-type stream))
117
118 (defun stream-external-format (stream)
119   (funcall (ansi-stream-misc stream) stream :external-format))
120
121 (defun interactive-stream-p (stream)
122   (declare (type stream stream))
123   (funcall (ansi-stream-misc stream) stream :interactive-p))
124
125 (declaim (inline ansi-stream-close))
126 (defun ansi-stream-close (stream abort)
127   (declare (type ansi-stream stream))
128   (when (open-stream-p stream)
129     (funcall (ansi-stream-misc stream) stream :close abort))
130   t)
131
132 (defun close (stream &key abort)
133   (ansi-stream-close stream abort))
134
135 (defun set-closed-flame (stream)
136   (setf (ansi-stream-in stream) #'closed-flame)
137   (setf (ansi-stream-bin stream) #'closed-flame)
138   (setf (ansi-stream-n-bin stream) #'closed-flame)
139   (setf (ansi-stream-in stream) #'closed-flame)
140   (setf (ansi-stream-out stream) #'closed-flame)
141   (setf (ansi-stream-bout stream) #'closed-flame)
142   (setf (ansi-stream-sout stream) #'closed-flame)
143   (setf (ansi-stream-misc stream) #'closed-flame))
144 \f
145 ;;;; file position and file length
146
147 ;;; Call the MISC method with the :FILE-POSITION operation.
148 #!-sb-fluid (declaim (inline ansi-stream-file-position))
149 (defun ansi-stream-file-position (stream position)
150   (declare (type stream stream))
151   (declare (type (or index (alien sb!unix:off-t) (member nil :start :end))
152                  position))
153   (cond
154     (position
155      (setf (ansi-stream-in-index stream) +ansi-stream-in-buffer-length+)
156      (funcall (ansi-stream-misc stream) stream :file-position position))
157     (t
158      (let ((res (funcall (ansi-stream-misc stream) stream :file-position nil)))
159        (when res
160          (- res
161             (- +ansi-stream-in-buffer-length+
162                (ansi-stream-in-index stream))))))))
163
164
165 (defun file-position (stream &optional position)
166   (ansi-stream-file-position stream position))
167
168 ;;; This is a literal translation of the ANSI glossary entry "stream
169 ;;; associated with a file".
170 ;;;
171 ;;; KLUDGE: Note that since Unix famously thinks "everything is a
172 ;;; file", and in particular stdin, stdout, and stderr are files, we
173 ;;; end up with this test being satisfied for weird things like
174 ;;; *STANDARD-OUTPUT* (to a tty). That seems unlikely to be what the
175 ;;; ANSI spec really had in mind, especially since this is used as a
176 ;;; qualification for operations like FILE-LENGTH (so that ANSI was
177 ;;; probably thinking of something like what Unix calls block devices)
178 ;;; but I can't see any better way to do it. -- WHN 2001-04-14
179 (defun stream-associated-with-file-p (x)
180   "Test for the ANSI concept \"stream associated with a file\"."
181   (or (typep x 'file-stream)
182       (and (synonym-stream-p x)
183            (stream-associated-with-file-p (symbol-value
184                                            (synonym-stream-symbol x))))))
185
186 (defun stream-must-be-associated-with-file (stream)
187   (declare (type stream stream))
188   (unless (stream-associated-with-file-p stream)
189     (error 'simple-type-error
190            ;; KLUDGE: The ANSI spec for FILE-LENGTH specifically says
191            ;; this should be TYPE-ERROR. But what then can we use for
192            ;; EXPECTED-TYPE? This SATISFIES type (with a nonstandard
193            ;; private predicate function..) is ugly and confusing, but
194            ;; I can't see any other way. -- WHN 2001-04-14
195            :datum stream
196            :expected-type '(satisfies stream-associated-with-file-p)
197            :format-control
198            "~@<The stream ~2I~_~S ~I~_isn't associated with a file.~:>"
199            :format-arguments (list stream))))
200
201 ;;; like FILE-POSITION, only using :FILE-LENGTH
202 (defun file-length (stream)
203   ;; FIXME: The following declaration uses yet undefined types, which
204   ;; cause cross-compiler hangup.
205   ;;
206   ;; (declare (type (or file-stream synonym-stream) stream))
207   ;; 
208   ;; The description for FILE-LENGTH says that an error must be raised
209   ;; for streams not associated with files (which broadcast streams
210   ;; aren't according to the glossary). However, the behaviour of
211   ;; FILE-LENGTH for broadcast streams is explicitly described in the
212   ;; BROADCAST-STREAM entry.
213   (unless (typep stream 'broadcast-stream)            
214     (stream-must-be-associated-with-file stream))
215   (funcall (ansi-stream-misc stream) stream :file-length))
216
217 (defun file-string-length (stream object)
218   (funcall (ansi-stream-misc stream) stream :file-string-length object))
219 \f
220 ;;;; input functions
221
222 #!-sb-fluid (declaim (inline ansi-stream-read-line))
223 (defun ansi-stream-read-line (stream eof-error-p eof-value recursive-p)
224   (declare (ignore recursive-p))
225   (prepare-for-fast-read-char stream
226           (let ((res (make-string 80))
227                 (len 80)
228                 (index 0))
229             (loop
230              (let ((ch (fast-read-char nil nil)))
231                (cond (ch
232                       (when (char= ch #\newline)
233                         (done-with-fast-read-char)
234                         (return (values (shrink-vector res index) nil)))
235                       (when (= index len)
236                         (setq len (* len 2))
237                         (let ((new (make-string len)))
238                           (replace new res)
239                           (setq res new)))
240                       (setf (schar res index) ch)
241                       (incf index))
242                      ((zerop index)
243                       (done-with-fast-read-char)
244                       (return (values (eof-or-lose stream
245                                                    eof-error-p
246                                                    eof-value)
247                                       t)))
248                      ;; Since FAST-READ-CHAR already hit the eof char, we
249                      ;; shouldn't do another READ-CHAR.
250                      (t
251                       (done-with-fast-read-char)
252                       (return (values (shrink-vector res index) t)))))))))
253
254 (defun read-line (&optional (stream *standard-input*) (eof-error-p t) eof-value
255                             recursive-p)
256   (let ((stream (in-synonym-of stream)))
257     (if (ansi-stream-p stream)
258         (ansi-stream-read-line stream eof-error-p eof-value recursive-p)
259         ;; must be Gray streams FUNDAMENTAL-STREAM
260         (multiple-value-bind (string eof) (stream-read-line stream)
261           (if (and eof (zerop (length string)))
262               (values (eof-or-lose stream eof-error-p eof-value) t)
263               (values string eof))))))
264
265 ;;; We proclaim them INLINE here, then proclaim them NOTINLINE later on,
266 ;;; so, except in this file, they are not inline by default, but they can be.
267 #!-sb-fluid (declaim (inline read-char unread-char read-byte listen))
268
269 #!-sb-fluid (declaim (inline ansi-stream-read-char))
270 (defun ansi-stream-read-char (stream eof-error-p eof-value recursive-p)
271   (declare (ignore recursive-p))
272   (prepare-for-fast-read-char stream
273     (prog1
274         (fast-read-char eof-error-p eof-value)
275       (done-with-fast-read-char))))
276
277 (defun read-char (&optional (stream *standard-input*)
278                             (eof-error-p t)
279                             eof-value
280                             recursive-p)
281   (let ((stream (in-synonym-of stream)))
282     (if (ansi-stream-p stream)
283         (ansi-stream-read-char stream eof-error-p eof-value recursive-p)
284         ;; must be Gray streams FUNDAMENTAL-STREAM
285         (let ((char (stream-read-char stream)))
286           (if (eq char :eof)
287               (eof-or-lose stream eof-error-p eof-value)
288               char)))))
289
290 #!-sb-fluid (declaim (inline ansi-stream-unread-char))
291 (defun ansi-stream-unread-char (character stream)
292   (let ((index (1- (ansi-stream-in-index stream)))
293         (buffer (ansi-stream-cin-buffer stream)))
294     (declare (fixnum index))
295     (when (minusp index) (error "nothing to unread"))
296     (cond (buffer
297            (setf (aref buffer index) character)
298            (setf (ansi-stream-in-index stream) index))
299           (t
300            (funcall (ansi-stream-misc stream) stream
301                     :unread character)))))
302
303 (defun unread-char (character &optional (stream *standard-input*))
304   (let ((stream (in-synonym-of stream)))
305     (if (ansi-stream-p stream)
306         (ansi-stream-unread-char character stream)
307         ;; must be Gray streams FUNDAMENTAL-STREAM
308         (stream-unread-char stream character)))
309   nil)
310
311 #!-sb-fluid (declaim (inline ansi-stream-listen))
312 (defun ansi-stream-listen (stream)
313   (or (/= (the fixnum (ansi-stream-in-index stream))
314           +ansi-stream-in-buffer-length+)
315       ;; Handle :EOF return from misc methods specially
316       (let ((result (funcall (ansi-stream-misc stream) stream :listen)))
317         (if (eq result :eof)
318             nil
319             result))))
320
321 (defun listen (&optional (stream *standard-input*))
322   (let ((stream (in-synonym-of stream)))
323     (if (ansi-stream-p stream)
324         (ansi-stream-listen stream)
325         ;; Fall through to Gray streams FUNDAMENTAL-STREAM case.
326         (stream-listen stream))))
327
328 #!-sb-fluid (declaim (inline ansi-stream-read-char-no-hang))
329 (defun ansi-stream-read-char-no-hang (stream eof-error-p eof-value recursive-p)
330   (if (funcall (ansi-stream-misc stream) stream :listen)
331       ;; On T or :EOF get READ-CHAR to do the work.
332       (ansi-stream-read-char stream eof-error-p eof-value recursive-p)
333       nil))
334
335 (defun read-char-no-hang (&optional (stream *standard-input*)
336                                     (eof-error-p t)
337                                     eof-value
338                                     recursive-p)
339   (let ((stream (in-synonym-of stream)))
340     (if (ansi-stream-p stream)
341         (ansi-stream-read-char-no-hang stream eof-error-p eof-value
342                                        recursive-p)
343         ;; must be Gray streams FUNDAMENTAL-STREAM
344         (let ((char (stream-read-char-no-hang stream)))
345           (if (eq char :eof)
346               (eof-or-lose stream eof-error-p eof-value)
347               char)))))
348
349 #!-sb-fluid (declaim (inline ansi-stream-clear-input))
350 (defun ansi-stream-clear-input (stream)
351   (setf (ansi-stream-in-index stream) +ansi-stream-in-buffer-length+)
352   (funcall (ansi-stream-misc stream) stream :clear-input))
353
354 (defun clear-input (&optional (stream *standard-input*))
355   (let ((stream (in-synonym-of stream)))
356     (if (ansi-stream-p stream)
357         (ansi-stream-clear-input stream)
358         ;; must be Gray streams FUNDAMENTAL-STREAM
359         (stream-clear-input stream)))
360   nil)
361 \f
362 #!-sb-fluid (declaim (inline ansi-stream-read-byte))
363 (defun ansi-stream-read-byte (stream eof-error-p eof-value recursive-p)
364   ;; Why the "recursive-p" parameter?  a-s-r-b is funcall'ed from
365   ;; a-s-read-sequence and needs a lambda list that's congruent with
366   ;; that of a-s-read-char
367   (declare (ignore recursive-p))
368   (prepare-for-fast-read-byte stream
369     (prog1
370         (fast-read-byte eof-error-p eof-value t)
371       (done-with-fast-read-byte))))
372
373 (defun read-byte (stream &optional (eof-error-p t) eof-value)
374   (let ((stream (in-synonym-of stream)))
375     (if (ansi-stream-p stream)
376         (ansi-stream-read-byte stream eof-error-p eof-value nil)
377         ;; must be Gray streams FUNDAMENTAL-STREAM
378         (let ((char (stream-read-byte stream)))
379           (if (eq char :eof)
380               (eof-or-lose stream eof-error-p eof-value)
381               char)))))
382
383 ;;; Read NUMBYTES bytes into BUFFER beginning at START, and return the
384 ;;; number of bytes read.
385 ;;;
386 ;;; Note: CMU CL's version of this had a special interpretation of
387 ;;; EOF-ERROR-P which SBCL does not have. (In the EOF-ERROR-P=NIL
388 ;;; case, CMU CL's version would return as soon as any data became
389 ;;; available.) This could be useful behavior for things like pipes in
390 ;;; some cases, but it wasn't being used in SBCL, so it was dropped.
391 ;;; If we ever need it, it could be added later as a new variant N-BIN
392 ;;; method (perhaps N-BIN-ASAP?) or something.
393 (defun read-n-bytes (stream buffer start numbytes &optional (eof-error-p t))
394   (declare (type ansi-stream stream)
395            (type index numbytes start)
396            (type (or (simple-array * (*)) system-area-pointer) buffer))
397   (let* ((stream (in-synonym-of stream ansi-stream))
398          (in-buffer (ansi-stream-in-buffer stream))
399          (index (ansi-stream-in-index stream))
400          (num-buffered (- +ansi-stream-in-buffer-length+ index)))
401     (declare (fixnum index num-buffered))
402     (cond
403      ((not in-buffer)
404       (funcall (ansi-stream-n-bin stream)
405                stream
406                buffer
407                start
408                numbytes
409                eof-error-p))
410      ((<= numbytes num-buffered)
411       #+nil
412       (let ((copy-function (typecase buffer
413                              ((simple-array * (*)) #'ub8-bash-copy)
414                              (system-area-pointer #'copy-ub8-to-system-area))))
415         (funcall copy-function in-buffer index buffer start numbytes))
416       (%byte-blt in-buffer index
417                  buffer start (+ start numbytes))
418       (setf (ansi-stream-in-index stream) (+ index numbytes))
419       numbytes)
420      (t
421       (let ((end (+ start num-buffered)))
422         #+nil
423         (let ((copy-function (typecase buffer
424                              ((simple-array * (*)) #'ub8-bash-copy)
425                              (system-area-pointer #'copy-ub8-to-system-area))))
426           (funcall copy-function in-buffer index buffer start num-buffered))
427         (%byte-blt in-buffer index buffer start end)
428         (setf (ansi-stream-in-index stream) +ansi-stream-in-buffer-length+)
429         (+ (funcall (ansi-stream-n-bin stream)
430                     stream
431                     buffer
432                     end
433                     (- numbytes num-buffered)
434                     eof-error-p)
435            num-buffered))))))
436
437 ;;; the amount of space we leave at the start of the in-buffer for
438 ;;; unreading
439 ;;;
440 ;;; (It's 4 instead of 1 to allow word-aligned copies.)
441 (defconstant +ansi-stream-in-buffer-extra+
442   4) ; FIXME: should be symbolic constant
443
444 ;;; This function is called by the FAST-READ-CHAR expansion to refill
445 ;;; the IN-BUFFER for text streams. There is definitely an IN-BUFFER,
446 ;;; and hence must be an N-BIN method.
447 (defun fast-read-char-refill (stream eof-error-p eof-value)
448   (let* ((ibuf (ansi-stream-cin-buffer stream))
449          (count (funcall (ansi-stream-n-bin stream)
450                          stream
451                          ibuf
452                          +ansi-stream-in-buffer-extra+
453                          (- +ansi-stream-in-buffer-length+
454                             +ansi-stream-in-buffer-extra+)
455                          nil))
456          (start (- +ansi-stream-in-buffer-length+ count)))
457     (declare (type index start count))
458     (cond ((zerop count)
459            (setf (ansi-stream-in-index stream)
460                  +ansi-stream-in-buffer-length+)
461            (funcall (ansi-stream-in stream) stream eof-error-p eof-value))
462           (t
463            (when (/= start +ansi-stream-in-buffer-extra+)
464              (#.(let* ((n-character-array-bits
465                         (sb!vm:saetp-n-bits
466                          (find 'character
467                                sb!vm:*specialized-array-element-type-properties*
468                                :key #'sb!vm:saetp-specifier)))
469                        (bash-function (intern (format nil "UB~D-BASH-COPY" n-character-array-bits)
470                                               (find-package "SB!KERNEL"))))
471                   bash-function)
472                 ibuf +ansi-stream-in-buffer-extra+
473                 ibuf start
474                 count))
475            (setf (ansi-stream-in-index stream) (1+ start))
476            (aref ibuf start)))))
477
478 ;;; This is similar to FAST-READ-CHAR-REFILL, but we don't have to
479 ;;; leave room for unreading.
480 (defun fast-read-byte-refill (stream eof-error-p eof-value)
481   (let* ((ibuf (ansi-stream-in-buffer stream))
482          (count (funcall (ansi-stream-n-bin stream) stream
483                          ibuf 0 +ansi-stream-in-buffer-length+
484                          nil))
485          (start (- +ansi-stream-in-buffer-length+ count)))
486     (declare (type index start count))
487     (cond ((zerop count)
488            (setf (ansi-stream-in-index stream) +ansi-stream-in-buffer-length+)
489            (funcall (ansi-stream-bin stream) stream eof-error-p eof-value))
490           (t
491            (unless (zerop start)
492              (ub8-bash-copy ibuf 0
493                             ibuf start 
494                             count))
495            (setf (ansi-stream-in-index stream) (1+ start))
496            (aref ibuf start)))))
497 \f
498 ;;; output functions
499
500 (defun write-char (character &optional (stream *standard-output*))
501   (with-out-stream stream (ansi-stream-out character)
502                    (stream-write-char character))
503   character)
504
505 (defun terpri (&optional (stream *standard-output*))
506   (with-out-stream stream (ansi-stream-out #\newline) (stream-terpri))
507   nil)
508
509 #!-sb-fluid (declaim (inline ansi-stream-fresh-line))
510 (defun ansi-stream-fresh-line (stream)
511   (when (/= (or (charpos stream) 1) 0)
512     (funcall (ansi-stream-out stream) stream #\newline)
513     t))
514
515 (defun fresh-line (&optional (stream *standard-output*))
516   (let ((stream (out-synonym-of stream)))
517     (if (ansi-stream-p stream)
518         (ansi-stream-fresh-line stream)
519         ;; must be Gray streams FUNDAMENTAL-STREAM
520         (stream-fresh-line stream))))
521
522 (defun write-string (string &optional (stream *standard-output*)
523                             &key (start 0) end)
524   (declare (type string string))
525   ;; Note that even though you might expect, based on the behavior of
526   ;; things like AREF, that the correct upper bound here is
527   ;; (ARRAY-DIMENSION STRING 0), the ANSI glossary definitions for
528   ;; "bounding index" and "length" indicate that in this case (i.e.
529   ;; for the ANSI-specified functions WRITE-STRING [and WRITE-LINE]),
530   ;; (LENGTH STRING) is the required upper bound. A foolish
531   ;; consistency is the hobgoblin of lesser languages..
532   (%write-string string stream start (%check-vector-sequence-bounds
533                                       string start end))
534   string)
535
536 #!-sb-fluid (declaim (inline ansi-stream-write-string))
537 (defun ansi-stream-write-string (string stream start end)
538   (declare (type string string))
539   (declare (type ansi-stream stream))
540   (declare (type index start end))
541   (if (array-header-p string)
542       (with-array-data ((data string) (offset-start start)
543                         (offset-end end))
544         (funcall (ansi-stream-sout stream)
545                  stream data offset-start offset-end))
546       (funcall (ansi-stream-sout stream) stream string start end))
547   string)
548
549 (defun %write-string (string stream start end)
550   (declare (type string string))
551   (declare (type stream-designator stream))
552   (declare (type index start end))
553   (let ((stream (out-synonym-of stream)))
554     (if(ansi-stream-p stream)
555        (ansi-stream-write-string string stream start end)
556        ;; must be Gray streams FUNDAMENTAL-STREAM
557        (stream-write-string stream string start end))))
558
559 ;;; A wrapper function for all those (MACROLET OUT-FUN) definitions,
560 ;;; which cannot deal with keyword arguments.
561 (declaim (inline write-string-no-key))
562 (defun write-string-no-key (string stream start end)
563   (write-string string stream :start start :end end))
564
565 (defun write-line (string &optional (stream *standard-output*)
566                           &key (start 0) end)
567   (declare (type string string))
568   ;; FIXME: Why is there this difference between the treatments of the
569   ;; STREAM argument in WRITE-STRING and WRITE-LINE?
570   (let ((defaulted-stream (out-synonym-of stream)))
571     (%write-string string defaulted-stream start (%check-vector-sequence-bounds
572                                                   string start end))
573     (write-char #\newline defaulted-stream))
574   string)
575
576 (defun charpos (&optional (stream *standard-output*))
577   (with-out-stream stream (ansi-stream-misc :charpos) (stream-line-column)))
578
579 (defun line-length (&optional (stream *standard-output*))
580   (with-out-stream stream (ansi-stream-misc :line-length)
581                    (stream-line-length)))
582
583 (defun finish-output (&optional (stream *standard-output*))
584   (with-out-stream stream (ansi-stream-misc :finish-output)
585                    (stream-finish-output))
586   nil)
587
588 (defun force-output (&optional (stream *standard-output*))
589   (with-out-stream stream (ansi-stream-misc :force-output)
590                    (stream-force-output))
591   nil)
592
593 (defun clear-output (&optional (stream *standard-output*))
594   (with-out-stream stream (ansi-stream-misc :clear-output)
595                    (stream-force-output))
596   nil)
597
598 (defun write-byte (integer stream)
599   (with-out-stream stream (ansi-stream-bout integer)
600                    (stream-write-byte integer))
601   integer)
602 \f
603
604 ;;; (These were inline throughout this file, but that's not appropriate
605 ;;; globally.  And we must not inline them in the rest of this file if
606 ;;; dispatch to gray or simple streams is to work, since both redefine
607 ;;; these functions later.)
608 (declaim (notinline read-char unread-char read-byte listen))
609
610 ;;; This is called from ANSI-STREAM routines that encapsulate CLOS
611 ;;; streams to handle the misc routines and dispatch to the
612 ;;; appropriate SIMPLE- or FUNDAMENTAL-STREAM functions.
613 (defun stream-misc-dispatch (stream operation &optional arg1 arg2)
614   (declare (type stream stream) (ignore arg2))
615   (ecase operation
616     (:listen
617      ;; Return T if input available, :EOF for end-of-file, otherwise NIL.
618      (let ((char (read-char-no-hang stream nil :eof)))
619        (when (characterp char)
620          (unread-char char stream))
621        char))
622     (:unread
623      (unread-char arg1 stream))
624     (:close
625      (close stream))
626     (:clear-input
627      (clear-input stream))
628     (:force-output
629      (force-output stream))
630     (:finish-output
631      (finish-output stream))
632     (:element-type
633      (stream-element-type stream))
634     (:stream-external-format
635      (stream-external-format stream))
636     (:interactive-p
637      (interactive-stream-p stream))
638     (:line-length
639      (line-length stream))
640     (:charpos
641      (charpos stream))
642     (:file-length
643      (file-length stream))
644     (:file-string-length
645      (file-string-length stream arg1))
646     (:file-position
647      (file-position stream arg1))))
648 \f
649 ;;;; broadcast streams
650
651 (defstruct (broadcast-stream (:include ansi-stream
652                                        (out #'broadcast-out)
653                                        (bout #'broadcast-bout)
654                                        (sout #'broadcast-sout)
655                                        (misc #'broadcast-misc))
656                              (:constructor %make-broadcast-stream
657                                            (&rest streams))
658                              (:copier nil))
659   ;; a list of all the streams we broadcast to
660   (streams () :type list :read-only t))
661
662 (defun make-broadcast-stream (&rest streams)
663   (dolist (stream streams)
664     (unless (output-stream-p stream)
665       (error 'type-error
666              :datum stream
667              :expected-type '(satisfies output-stream-p))))
668   (apply #'%make-broadcast-stream streams))
669
670 (macrolet ((out-fun (name fun &rest args)
671              `(defun ,name (stream ,@args)
672                 (dolist (stream (broadcast-stream-streams stream))
673                   (,fun ,(car args) stream ,@(cdr args))))))
674   (out-fun broadcast-out write-char char)
675   (out-fun broadcast-bout write-byte byte)
676   (out-fun broadcast-sout write-string-no-key string start end))
677
678 (defun broadcast-misc (stream operation &optional arg1 arg2)
679   (let ((streams (broadcast-stream-streams stream)))
680     (case operation
681       ;; FIXME: This may not be the best place to note this, but I
682       ;; think the :CHARPOS protocol needs revision.  Firstly, I think
683       ;; this is the last place where a NULL return value was possible
684       ;; (before adjusting it to be 0), so a bunch of conditionals IF
685       ;; CHARPOS can be removed; secondly, it is my belief that
686       ;; FD-STREAMS, when running FILE-POSITION, do not update the
687       ;; CHARPOS, and consequently there will be much wrongness.
688       ;;
689       ;; FIXME: see also TWO-WAY-STREAM treatment of :CHARPOS -- why
690       ;; is it testing the :charpos of an input stream?
691       ;;
692       ;; -- CSR, 2004-02-04
693       (:charpos
694        (dolist (stream streams 0)
695          (let ((charpos (charpos stream)))
696            (if charpos (return charpos)))))
697       (:line-length
698        (let ((min nil))
699          (dolist (stream streams min)
700            (let ((res (line-length stream)))
701              (when res (setq min (if min (min res min) res)))))))
702       (:element-type
703        #+nil ; old, arguably more logical, version
704        (let (res)
705          (dolist (stream streams (if (> (length res) 1) `(and ,@res) t))
706            (pushnew (stream-element-type stream) res :test #'equal)))
707        ;; ANSI-specified version (under System Class BROADCAST-STREAM)
708        (let ((res t))
709          (do ((streams streams (cdr streams)))
710              ((null streams) res)
711            (when (null (cdr streams))
712              (setq res (stream-element-type (car streams)))))))
713       (:external-format
714        (let ((res :default))
715          (dolist (stream streams res)
716            (setq res (stream-external-format stream)))))
717       (:file-length
718        (let ((last (last streams)))
719          (if last            
720              (file-length (car last))
721              0)))
722       (:file-position
723        (if arg1
724            (let ((res (or (eql arg1 :start) (eql arg1 0))))
725              (dolist (stream streams res)
726                (setq res (file-position stream arg1))))
727            (let ((res 0))
728              (dolist (stream streams res)
729                (setq res (file-position stream))))))
730       (:file-string-length
731        (let ((res 1))
732          (dolist (stream streams res)
733            (setq res (file-string-length stream arg1)))))
734       (:close
735        (set-closed-flame stream))
736       (t
737        (let ((res nil))
738          (dolist (stream streams res)
739            (setq res
740                  (if (ansi-stream-p stream)
741                      (funcall (ansi-stream-misc stream) stream operation
742                               arg1 arg2)
743                      (stream-misc-dispatch stream operation arg1 arg2)))))))))
744 \f
745 ;;;; synonym streams
746
747 (defstruct (synonym-stream (:include ansi-stream
748                                      (in #'synonym-in)
749                                      (bin #'synonym-bin)
750                                      (n-bin #'synonym-n-bin)
751                                      (out #'synonym-out)
752                                      (bout #'synonym-bout)
753                                      (sout #'synonym-sout)
754                                      (misc #'synonym-misc))
755                            (:constructor make-synonym-stream (symbol))
756                            (:copier nil))
757   ;; This is the symbol, the value of which is the stream we are synonym to.
758   (symbol nil :type symbol :read-only t))
759 (def!method print-object ((x synonym-stream) stream)
760   (print-unreadable-object (x stream :type t :identity t)
761     (format stream ":SYMBOL ~S" (synonym-stream-symbol x))))
762
763 ;;; The output simple output methods just call the corresponding
764 ;;; function on the synonymed stream.
765 (macrolet ((out-fun (name fun &rest args)
766              `(defun ,name (stream ,@args)
767                 (declare (optimize (safety 1)))
768                 (let ((syn (symbol-value (synonym-stream-symbol stream))))
769                   (,fun ,(car args) syn ,@(cdr args))))))
770   (out-fun synonym-out write-char ch)
771   (out-fun synonym-bout write-byte n)
772   (out-fun synonym-sout write-string-no-key string start end))
773
774 ;;; For the input methods, we just call the corresponding function on the
775 ;;; synonymed stream. These functions deal with getting input out of
776 ;;; the In-Buffer if there is any.
777 (macrolet ((in-fun (name fun &rest args)
778              `(defun ,name (stream ,@args)
779                 (declare (optimize (safety 1)))
780                 (,fun (symbol-value (synonym-stream-symbol stream))
781                       ,@args))))
782   (in-fun synonym-in read-char eof-error-p eof-value)
783   (in-fun synonym-bin read-byte eof-error-p eof-value)
784   (in-fun synonym-n-bin read-n-bytes buffer start numbytes eof-error-p))
785
786 (defun synonym-misc (stream operation &optional arg1 arg2)
787   (declare (optimize (safety 1)))
788   (let ((syn (symbol-value (synonym-stream-symbol stream))))
789     (if (ansi-stream-p syn)
790         ;; We have to special-case some operations which interact with
791         ;; the in-buffer of the wrapped stream, since just calling
792         ;; ANSI-STREAM-MISC on them
793         (case operation
794           (:listen (or (/= (the fixnum (ansi-stream-in-index syn))
795                            +ansi-stream-in-buffer-length+)
796                        (funcall (ansi-stream-misc syn) syn :listen)))
797           (:clear-input (clear-input syn))
798           (:unread (unread-char arg1 syn))
799           (t
800            (funcall (ansi-stream-misc syn) syn operation arg1 arg2)))
801         (stream-misc-dispatch syn operation arg1 arg2))))
802 \f
803 ;;;; two-way streams
804
805 (defstruct (two-way-stream
806             (:include ansi-stream
807                       (in #'two-way-in)
808                       (bin #'two-way-bin)
809                       (n-bin #'two-way-n-bin)
810                       (out #'two-way-out)
811                       (bout #'two-way-bout)
812                       (sout #'two-way-sout)
813                       (misc #'two-way-misc))
814             (:constructor %make-two-way-stream (input-stream output-stream))
815             (:copier nil))
816   (input-stream (missing-arg) :type stream :read-only t)
817   (output-stream (missing-arg) :type stream :read-only t))
818 (defprinter (two-way-stream) input-stream output-stream)
819
820 (defun make-two-way-stream (input-stream output-stream)
821   #!+sb-doc
822   "Return a bidirectional stream which gets its input from INPUT-STREAM and
823    sends its output to OUTPUT-STREAM."
824   ;; FIXME: This idiom of the-real-stream-of-a-possibly-synonym-stream
825   ;; should be encapsulated in a function, and used here and most of
826   ;; the other places that SYNONYM-STREAM-P appears.
827   (unless (output-stream-p output-stream)
828     (error 'type-error
829            :datum output-stream
830            :expected-type '(satisfies output-stream-p)))
831   (unless (input-stream-p input-stream)
832     (error 'type-error
833            :datum input-stream
834            :expected-type '(satisfies input-stream-p)))
835   (funcall #'%make-two-way-stream input-stream output-stream))
836
837 (macrolet ((out-fun (name fun &rest args)
838              `(defun ,name (stream ,@args)
839                 (let ((syn (two-way-stream-output-stream stream)))
840                   (,fun ,(car args) syn ,@(cdr args))))))
841   (out-fun two-way-out write-char ch)
842   (out-fun two-way-bout write-byte n)
843   (out-fun two-way-sout write-string-no-key string start end))
844
845 (macrolet ((in-fun (name fun &rest args)
846              `(defun ,name (stream ,@args)
847                 (force-output (two-way-stream-output-stream stream))
848                 (,fun (two-way-stream-input-stream stream) ,@args))))
849   (in-fun two-way-in read-char eof-error-p eof-value)
850   (in-fun two-way-bin read-byte eof-error-p eof-value)
851   (in-fun two-way-n-bin read-n-bytes buffer start numbytes eof-error-p))
852
853 (defun two-way-misc (stream operation &optional arg1 arg2)
854   (let* ((in (two-way-stream-input-stream stream))
855          (out (two-way-stream-output-stream stream))
856          (in-ansi-stream-p (ansi-stream-p in))
857          (out-ansi-stream-p (ansi-stream-p out)))
858     (case operation
859       (:listen
860        (if in-ansi-stream-p
861            (or (/= (the fixnum (ansi-stream-in-index in))
862                    +ansi-stream-in-buffer-length+)
863                (funcall (ansi-stream-misc in) in :listen))
864            (listen in)))
865       ((:finish-output :force-output :clear-output)
866        (if out-ansi-stream-p
867            (funcall (ansi-stream-misc out) out operation arg1 arg2)
868            (stream-misc-dispatch out operation arg1 arg2)))
869       (:clear-input (clear-input in))
870       (:unread (unread-char arg1 in))
871       (:element-type
872        (let ((in-type (stream-element-type in))
873              (out-type (stream-element-type out)))
874          (if (equal in-type out-type)
875              in-type `(and ,in-type ,out-type))))
876       (:close
877        (set-closed-flame stream))
878       (t
879        (or (if in-ansi-stream-p
880                (funcall (ansi-stream-misc in) in operation arg1 arg2)
881                (stream-misc-dispatch in operation arg1 arg2))
882            (if out-ansi-stream-p
883                (funcall (ansi-stream-misc out) out operation arg1 arg2)
884                (stream-misc-dispatch out operation arg1 arg2)))))))
885 \f
886 ;;;; concatenated streams
887
888 (defstruct (concatenated-stream
889             (:include ansi-stream
890                       (in #'concatenated-in)
891                       (bin #'concatenated-bin)
892                       (n-bin #'concatenated-n-bin)
893                       (misc #'concatenated-misc))
894             (:constructor %make-concatenated-stream (&rest streams))
895             (:copier nil))
896   ;; The car of this is the substream we are reading from now.
897   (streams nil :type list))
898 (def!method print-object ((x concatenated-stream) stream)
899   (print-unreadable-object (x stream :type t :identity t)
900     (format stream
901             ":STREAMS ~S"
902             (concatenated-stream-streams x))))
903
904 (defun make-concatenated-stream (&rest streams)
905   #!+sb-doc
906   "Return a stream which takes its input from each of the streams in turn,
907    going on to the next at EOF."
908   (dolist (stream streams)
909     (unless (input-stream-p stream)
910       (error 'type-error
911              :datum stream
912              :expected-type '(satisfies input-stream-p))))
913   (apply #'%make-concatenated-stream streams))
914
915 (macrolet ((in-fun (name fun)
916              `(defun ,name (stream eof-error-p eof-value)
917                 (do ((streams (concatenated-stream-streams stream)
918                               (cdr streams)))
919                     ((null streams)
920                      (eof-or-lose stream eof-error-p eof-value))
921                   (let* ((stream (car streams))
922                          (result (,fun stream nil nil)))
923                     (when result (return result)))
924                   (pop (concatenated-stream-streams stream))))))
925   (in-fun concatenated-in read-char)
926   (in-fun concatenated-bin read-byte))
927
928 (defun concatenated-n-bin (stream buffer start numbytes eof-errorp)
929   (do ((streams (concatenated-stream-streams stream) (cdr streams))
930        (current-start start)
931        (remaining-bytes numbytes))
932       ((null streams)
933        (if eof-errorp
934            (error 'end-of-file :stream stream)
935            (- numbytes remaining-bytes)))
936     (let* ((stream (car streams))
937            (bytes-read (read-n-bytes stream buffer current-start
938                                      remaining-bytes nil)))
939       (incf current-start bytes-read)
940       (decf remaining-bytes bytes-read)
941       (when (zerop remaining-bytes) (return numbytes)))
942     (setf (concatenated-stream-streams stream) (cdr streams))))
943
944 (defun concatenated-misc (stream operation &optional arg1 arg2)
945   (let* ((left (concatenated-stream-streams stream))
946          (current (car left)))
947     (case operation
948       (:listen
949        (unless left
950          (return-from concatenated-misc :eof))
951        (loop
952         (let ((stuff (if (ansi-stream-p current)
953                          (funcall (ansi-stream-misc current) current
954                                   :listen)
955                          (stream-misc-dispatch current :listen))))
956           (cond ((eq stuff :eof)
957                  ;; Advance STREAMS, and try again.
958                  (pop (concatenated-stream-streams stream))
959                  (setf current
960                        (car (concatenated-stream-streams stream)))
961                  (unless current
962                    ;; No further streams. EOF.
963                    (return :eof)))
964                 (stuff
965                  ;; Stuff's available.
966                  (return t))
967                 (t
968                  ;; Nothing is available yet.
969                  (return nil))))))
970       (:clear-input (when left (clear-input current)))
971       (:unread (when left (unread-char arg1 current)))
972       (:close
973        (set-closed-flame stream))
974       (t
975        (when left
976          (if (ansi-stream-p current)
977              (funcall (ansi-stream-misc current) current operation arg1 arg2)
978              (stream-misc-dispatch current operation arg1 arg2)))))))
979 \f
980 ;;;; echo streams
981
982 (defstruct (echo-stream
983             (:include two-way-stream
984                       (in #'echo-in)
985                       (bin #'echo-bin)
986                       (misc #'echo-misc)
987                       (n-bin #'echo-n-bin))
988             (:constructor %make-echo-stream (input-stream output-stream))
989             (:copier nil))
990   unread-stuff)
991 (def!method print-object ((x echo-stream) stream)
992   (print-unreadable-object (x stream :type t :identity t)
993     (format stream
994             ":INPUT-STREAM ~S :OUTPUT-STREAM ~S"
995             (two-way-stream-input-stream x)
996             (two-way-stream-output-stream x))))
997
998 (defun make-echo-stream (input-stream output-stream)
999   #!+sb-doc
1000   "Return a bidirectional stream which gets its input from INPUT-STREAM and
1001    sends its output to OUTPUT-STREAM. In addition, all input is echoed to
1002    the output stream."
1003   (unless (output-stream-p output-stream)
1004     (error 'type-error
1005            :datum output-stream
1006            :expected-type '(satisfies output-stream-p)))
1007   (unless (input-stream-p input-stream)
1008     (error 'type-error
1009            :datum input-stream
1010            :expected-type '(satisfies input-stream-p)))
1011   (funcall #'%make-echo-stream input-stream output-stream))
1012
1013 (macrolet ((in-fun (name in-fun out-fun &rest args)
1014              `(defun ,name (stream ,@args)
1015                 (or (pop (echo-stream-unread-stuff stream))
1016                     (let* ((in (echo-stream-input-stream stream))
1017                            (out (echo-stream-output-stream stream))
1018                            (result (if eof-error-p
1019                                        (,in-fun in ,@args)
1020                                        (,in-fun in nil in))))
1021                       (cond
1022                         ((eql result in) eof-value)
1023                         (t (,out-fun result out) result)))))))
1024   (in-fun echo-in read-char write-char eof-error-p eof-value)
1025   (in-fun echo-bin read-byte write-byte eof-error-p eof-value))
1026
1027 (defun echo-n-bin (stream buffer start numbytes eof-error-p)
1028   (let ((new-start start)
1029         (read 0))
1030     (loop
1031      (let ((thing (pop (echo-stream-unread-stuff stream))))
1032        (cond
1033          (thing
1034           (setf (aref buffer new-start) thing)
1035           (incf new-start)
1036           (incf read)
1037           (when (= read numbytes)
1038             (return-from echo-n-bin numbytes)))
1039          (t (return nil)))))
1040     (let ((bytes-read (read-n-bytes (echo-stream-input-stream stream) buffer
1041                                     new-start (- numbytes read) nil)))
1042       (cond
1043         ((not eof-error-p)
1044          (write-sequence buffer (echo-stream-output-stream stream)
1045                          :start new-start :end (+ new-start bytes-read))
1046          (+ bytes-read read))
1047         ((> numbytes (+ read bytes-read))
1048          (write-sequence buffer (echo-stream-output-stream stream)
1049                          :start new-start :end (+ new-start bytes-read))
1050          (error 'end-of-file :stream stream))
1051         (t
1052          (write-sequence buffer (echo-stream-output-stream stream)
1053                          :start new-start :end (+ new-start bytes-read))
1054          (aver (= numbytes (+ new-start bytes-read)))
1055          numbytes)))))
1056 \f
1057 ;;;; STRING-INPUT-STREAM stuff
1058
1059 (defstruct (string-input-stream
1060              (:include ansi-stream
1061                        (in #'string-inch)
1062                        (bin #'ill-bin)
1063                        (n-bin #'ill-bin)
1064                        (misc #'string-in-misc))
1065              (:constructor internal-make-string-input-stream
1066                            (string current end))
1067              (:copier nil))
1068   (string (missing-arg) :type simple-string)
1069   (current (missing-arg) :type index)
1070   (end (missing-arg) :type index))
1071
1072 (defun string-inch (stream eof-error-p eof-value)
1073   (declare (type string-input-stream stream))
1074   (let ((string (string-input-stream-string stream))
1075         (index (string-input-stream-current stream)))
1076     (cond ((>= index (the index (string-input-stream-end stream)))
1077            (eof-or-lose stream eof-error-p eof-value))
1078           (t
1079            (setf (string-input-stream-current stream) (1+ index))
1080            (char string index)))))
1081
1082 (defun string-binch (stream eof-error-p eof-value)
1083   (declare (type string-input-stream stream))
1084   (let ((string (string-input-stream-string stream))
1085         (index (string-input-stream-current stream)))
1086     (cond ((>= index (the index (string-input-stream-end stream)))
1087            (eof-or-lose stream eof-error-p eof-value))
1088           (t
1089            (setf (string-input-stream-current stream) (1+ index))
1090            (char-code (char string index))))))
1091
1092 (defun string-stream-read-n-bytes (stream buffer start requested eof-error-p)
1093   (declare (type string-input-stream stream)
1094            (type index start requested))
1095   (let* ((string (string-input-stream-string stream))
1096          (index (string-input-stream-current stream))
1097          (available (- (string-input-stream-end stream) index))
1098          (copy (min available requested)))
1099     (declare (type simple-string string))
1100     (when (plusp copy)
1101       (setf (string-input-stream-current stream)
1102             (truly-the index (+ index copy)))
1103       ;; FIXME: why are we VECTOR-SAP'ing things here?  what's the point?
1104       ;; and are there SB-UNICODE issues here as well?  --njf, 2005-03-24
1105       (sb!sys:without-gcing
1106        (system-area-ub8-copy (vector-sap string)
1107                              index
1108                              (if (typep buffer 'system-area-pointer)
1109                                  buffer
1110                                  (vector-sap buffer))
1111                              start
1112                              copy)))
1113     (if (and (> requested copy) eof-error-p)
1114         (error 'end-of-file :stream stream)
1115         copy)))
1116
1117 (defun string-in-misc (stream operation &optional arg1 arg2)
1118   (declare (type string-input-stream stream)
1119            (ignore arg2))
1120   (case operation
1121     (:file-position
1122      (if arg1
1123          (setf (string-input-stream-current stream)
1124                (case arg1
1125                  (:start 0)
1126                  (:end (string-input-stream-end stream))
1127                  ;; We allow moving position beyond EOF. Errors happen
1128                  ;; on read, not move -- or the user may extend the
1129                  ;; input string.
1130                  (t arg1)))
1131          (string-input-stream-current stream)))
1132     ;; According to ANSI: "Should signal an error of type type-error
1133     ;; if stream is not a stream associated with a file."
1134     ;; This is checked by FILE-LENGTH, so no need to do it here either.
1135     ;; (:file-length (length (string-input-stream-string stream)))
1136     (:unread (decf (string-input-stream-current stream)))
1137     (:close (set-closed-flame stream))
1138     (:listen (or (/= (the index (string-input-stream-current stream))
1139                      (the index (string-input-stream-end stream)))
1140                  :eof))
1141     (:element-type (array-element-type (string-input-stream-string stream)))))
1142
1143 (defun make-string-input-stream (string &optional (start 0) end)
1144   #!+sb-doc
1145   "Return an input stream which will supply the characters of STRING between
1146   START and END in order."
1147   (declare (type string string)
1148            (type index start)
1149            (type (or index null) end))
1150   (let* ((string (coerce string '(simple-array character (*))))
1151          (end (%check-vector-sequence-bounds string start end)))
1152     (with-array-data ((string string) (start start) (end end))
1153       (internal-make-string-input-stream
1154        string ;; now simple
1155        start
1156        end))))
1157 \f
1158 ;;;; STRING-OUTPUT-STREAM stuff
1159
1160 (defstruct (string-output-stream
1161             (:include ansi-stream
1162                       (out #'string-ouch)
1163                       (sout #'string-sout)
1164                       (misc #'string-out-misc))
1165             (:constructor make-string-output-stream 
1166                           (&key (element-type 'character)
1167                            &aux (string (make-string 40))))
1168             (:copier nil))
1169   ;; The string we throw stuff in.
1170   (string (missing-arg) :type (simple-array character (*)))
1171   ;; Index of the next location to use.
1172   (index 0 :type fixnum)
1173   ;; Index cache for string-output-stream-last-index
1174   (index-cache 0 :type fixnum)
1175   ;; Requested element type
1176   (element-type 'character))
1177
1178 #!+sb-doc
1179 (setf (fdocumentation 'make-string-output-stream 'function)
1180   "Return an output stream which will accumulate all output given it for
1181    the benefit of the function GET-OUTPUT-STREAM-STRING.")
1182
1183 (defun string-output-stream-last-index (stream)
1184   (max (string-output-stream-index stream)
1185        (string-output-stream-index-cache stream)))
1186
1187 (defun string-ouch (stream character)
1188   (let ((current (string-output-stream-index stream))
1189         (workspace (string-output-stream-string stream)))
1190     (declare (type (simple-array character (*)) workspace)
1191              (type fixnum current))
1192     (if (= current (the fixnum (length workspace)))
1193         (let ((new-workspace (make-string (* current 2))))
1194           (replace new-workspace workspace)
1195           (setf (aref new-workspace current) character
1196                 (string-output-stream-string stream) new-workspace))
1197         (setf (aref workspace current) character))
1198     (setf (string-output-stream-index stream) (1+ current))))
1199
1200 (defun string-sout (stream string start end)
1201   (declare (type simple-string string)
1202            (type fixnum start end))
1203   (let* ((string (if (typep string '(simple-array character (*)))
1204                      string
1205                      (coerce string '(simple-array character (*)))))
1206          (current (string-output-stream-index stream))
1207          (length (- end start))
1208          (dst-end (+ length current))
1209          (workspace (string-output-stream-string stream)))
1210     (declare (type (simple-array character (*)) workspace string)
1211              (type fixnum current length dst-end))
1212     (if (> dst-end (the fixnum (length workspace)))
1213         (let ((new-workspace (make-string (+ (* current 2) length))))
1214           (replace new-workspace workspace :end2 current)
1215           (replace new-workspace string
1216                    :start1 current :end1 dst-end
1217                    :start2 start :end2 end)
1218           (setf (string-output-stream-string stream) new-workspace))
1219         (replace workspace string
1220                  :start1 current :end1 dst-end
1221                  :start2 start :end2 end))
1222     (setf (string-output-stream-index stream) dst-end)))
1223
1224 (defun string-out-misc (stream operation &optional arg1 arg2)
1225   (declare (ignore arg2))
1226   (case operation
1227     (:file-position
1228      (if arg1
1229          (let ((end (string-output-stream-last-index stream)))
1230            (setf (string-output-stream-index-cache stream) end
1231                  (string-output-stream-index stream)
1232                  (case arg1
1233                    (:start 0)
1234                    (:end end)
1235                    (t
1236                     ;; We allow moving beyond the end of stream,
1237                     ;; implicitly extending the output stream.
1238                     (let ((buffer (string-output-stream-string stream)))
1239                       (when (> arg1 (length buffer))
1240                         (setf (string-output-stream-string stream)
1241                               (make-string
1242                                arg1 :element-type (array-element-type buffer))
1243                               (subseq (string-output-stream-string stream)
1244                                       0 end)
1245                               (subseq buffer 0 end))))
1246                       arg1))))
1247          (string-output-stream-index stream)))
1248     (:close (set-closed-flame stream))
1249     (:charpos
1250      (do ((index (1- (the fixnum (string-output-stream-index stream)))
1251                  (1- index))
1252           (count 0 (1+ count))
1253           (string (string-output-stream-string stream)))
1254          ((< index 0) count)
1255        (declare (type (simple-array character (*)) string)
1256                 (type fixnum index count))
1257        (if (char= (schar string index) #\newline)
1258            (return count))))
1259     (:element-type (array-element-type (string-output-stream-string stream)))))
1260
1261 ;;; Return a string of all the characters sent to a stream made by
1262 ;;; MAKE-STRING-OUTPUT-STREAM since the last call to this function.
1263 (defun get-output-stream-string (stream)
1264   (declare (type string-output-stream stream))
1265   (let* ((length (string-output-stream-last-index stream))
1266          (element-type (string-output-stream-element-type stream))
1267          (result 
1268           (case element-type
1269             ;; overwhelmingly common case: can be inlined
1270             ((character) (make-string length))
1271             ;; slightly less common cases: inline it anyway
1272             ((base-char standard-char)
1273              (make-string length :element-type 'base-char))
1274             (t (make-string length :element-type element-type)))))
1275     ;; For the benefit of the REPLACE transform, let's do this, so
1276     ;; that the common case isn't ludicrously expensive.
1277     (etypecase result 
1278       ((simple-array character (*)) 
1279        (replace result (string-output-stream-string stream)))
1280       (simple-base-string
1281        (replace result (string-output-stream-string stream)))
1282       ((simple-array nil (*))
1283        (replace result (string-output-stream-string stream))))
1284     (setf (string-output-stream-index stream) 0
1285           (string-output-stream-index-cache stream) 0)
1286     result))
1287
1288 ;;; Dump the characters buffer up in IN-STREAM to OUT-STREAM as
1289 ;;; GET-OUTPUT-STREAM-STRING would return them.
1290 (defun dump-output-stream-string (in-stream out-stream)
1291   (%write-string (string-output-stream-string in-stream)
1292                  out-stream
1293                  0
1294                  (string-output-stream-last-index in-stream))
1295   (setf (string-output-stream-index in-stream) 0
1296         (string-output-stream-index-cache in-stream) 0))
1297 \f
1298 ;;;; fill-pointer streams
1299
1300 ;;; Fill pointer STRING-OUTPUT-STREAMs are not explicitly mentioned in
1301 ;;; the CLM, but they are required for the implementation of
1302 ;;; WITH-OUTPUT-TO-STRING.
1303
1304 ;;; FIXME: need to support (VECTOR BASE-CHAR) and (VECTOR NIL),
1305 ;;; ideally without destroying all hope of efficiency.
1306 (deftype string-with-fill-pointer ()
1307   '(and (vector character)
1308         (satisfies array-has-fill-pointer-p)))
1309
1310 (defstruct (fill-pointer-output-stream
1311             (:include ansi-stream
1312                       (out #'fill-pointer-ouch)
1313                       (sout #'fill-pointer-sout)
1314                       (misc #'fill-pointer-misc))
1315             (:constructor make-fill-pointer-output-stream (string))
1316             (:copier nil))
1317   ;; a string with a fill pointer where we stuff the stuff we write
1318   (string (missing-arg) :type string-with-fill-pointer :read-only t))
1319
1320 (defun fill-pointer-ouch (stream character)
1321   (let* ((buffer (fill-pointer-output-stream-string stream))
1322          (current (fill-pointer buffer))
1323          (current+1 (1+ current)))
1324     (declare (fixnum current))
1325     (with-array-data ((workspace buffer) (start) (end))
1326       (declare (type (simple-array character (*)) workspace))
1327       (let ((offset-current (+ start current)))
1328         (declare (fixnum offset-current))
1329         (if (= offset-current end)
1330             (let* ((new-length (1+ (* current 2)))
1331                    (new-workspace (make-string new-length)))
1332               (declare (type (simple-array character (*)) new-workspace))
1333               (replace new-workspace workspace
1334                        :start2 start :end2 offset-current)
1335               (setf workspace new-workspace
1336                     offset-current current)
1337               (set-array-header buffer workspace new-length
1338                                 current+1 0 new-length nil))
1339             (setf (fill-pointer buffer) current+1))
1340         (setf (schar workspace offset-current) character)))
1341     current+1))
1342
1343 (defun fill-pointer-sout (stream string start end)
1344   (declare (simple-string string) (fixnum start end))
1345   (let* ((string (if (typep string '(simple-array character (*)))
1346                      string
1347                      (coerce string '(simple-array character (*)))))
1348          (buffer (fill-pointer-output-stream-string stream))
1349          (current (fill-pointer buffer))
1350          (string-len (- end start))
1351          (dst-end (+ string-len current)))
1352     (declare (fixnum current dst-end string-len))
1353     (with-array-data ((workspace buffer) (dst-start) (dst-length))
1354       (declare (type (simple-array character (*)) workspace))
1355       (let ((offset-dst-end (+ dst-start dst-end))
1356             (offset-current (+ dst-start current)))
1357         (declare (fixnum offset-dst-end offset-current))
1358         (if (> offset-dst-end dst-length)
1359             (let* ((new-length (+ (the fixnum (* current 2)) string-len))
1360                    (new-workspace (make-string new-length)))
1361               (declare (type (simple-array character (*)) new-workspace))
1362               (replace new-workspace workspace
1363                        :start2 dst-start :end2 offset-current)
1364               (setf workspace new-workspace
1365                     offset-current current
1366                     offset-dst-end dst-end)
1367               (set-array-header buffer workspace new-length
1368                                 dst-end 0 new-length nil))
1369             (setf (fill-pointer buffer) dst-end))
1370         (replace workspace string
1371                  :start1 offset-current :start2 start :end2 end)))
1372     dst-end))
1373
1374 (defun fill-pointer-misc (stream operation &optional arg1 arg2)
1375   (declare (ignore arg2))
1376   (case operation
1377     (:file-position
1378      (let ((buffer (fill-pointer-output-stream-string stream)))
1379        (if arg1
1380            (setf (fill-pointer buffer)
1381                  (case arg1
1382                    (:start 0)
1383                    ;; Fill-pointer is always at fill-pointer we will
1384                    ;; make :END move to the end of the actual string.
1385                    (:end (array-total-size buffer))
1386                    ;; We allow moving beyond the end of string if the
1387                    ;; string is adjustable.
1388                    (t (when (>= arg1 (array-total-size buffer))
1389                         (if (adjustable-array-p buffer)
1390                             (adjust-array buffer arg1)
1391                             (error "Cannot move FILE-POSITION beyond the end ~
1392                                     of WITH-OUTPUT-TO-STRING stream ~
1393                                     constructed with non-adjustable string.")))
1394                       arg1)))
1395            (fill-pointer buffer))))
1396     (:charpos
1397      (let* ((buffer (fill-pointer-output-stream-string stream))
1398             (current (fill-pointer buffer)))
1399        (with-array-data ((string buffer) (start) (end current))
1400          (declare (simple-string string) (ignore start))
1401          (let ((found (position #\newline string :test #'char=
1402                                 :end end :from-end t)))
1403            (if found
1404                (- end (the fixnum found))
1405                current)))))
1406      (:element-type (array-element-type
1407                      (fill-pointer-output-stream-string stream)))))
1408 \f
1409 ;;;; indenting streams
1410
1411 (defstruct (indenting-stream (:include ansi-stream
1412                                        (out #'indenting-out)
1413                                        (sout #'indenting-sout)
1414                                        (misc #'indenting-misc))
1415                              (:constructor make-indenting-stream (stream))
1416                              (:copier nil))
1417   ;; the stream we're based on
1418   stream
1419   ;; how much we indent on each line
1420   (indentation 0))
1421
1422 #!+sb-doc
1423 (setf (fdocumentation 'make-indenting-stream 'function)
1424  "Return an output stream which indents its output by some amount.")
1425
1426 ;;; INDENTING-INDENT writes the correct number of spaces needed to indent
1427 ;;; output on the given STREAM based on the specified SUB-STREAM.
1428 (defmacro indenting-indent (stream sub-stream)
1429   ;; KLUDGE: bare magic number 60
1430   `(do ((i 0 (+ i 60))
1431         (indentation (indenting-stream-indentation ,stream)))
1432        ((>= i indentation))
1433      (%write-string
1434       #.(make-string 60 :initial-element #\Space)
1435       ,sub-stream
1436       0
1437       (min 60 (- indentation i)))))
1438
1439 ;;; INDENTING-OUT writes a character to an indenting stream.
1440 (defun indenting-out (stream char)
1441   (let ((sub-stream (indenting-stream-stream stream)))
1442     (write-char char sub-stream)
1443     (if (char= char #\newline)
1444         (indenting-indent stream sub-stream))))
1445
1446 ;;; INDENTING-SOUT writes a string to an indenting stream.
1447 (defun indenting-sout (stream string start end)
1448   (declare (simple-string string) (fixnum start end))
1449   (do ((i start)
1450        (sub-stream (indenting-stream-stream stream)))
1451       ((= i end))
1452     (let ((newline (position #\newline string :start i :end end)))
1453       (cond (newline
1454              (%write-string string sub-stream i (1+ newline))
1455              (indenting-indent stream sub-stream)
1456              (setq i (+ newline 1)))
1457             (t
1458              (%write-string string sub-stream i end)
1459              (setq i end))))))
1460
1461 ;;; INDENTING-MISC just treats just the :LINE-LENGTH message
1462 ;;; differently. INDENTING-CHARPOS says the charpos is the charpos of
1463 ;;; the base stream minus the stream's indentation.
1464 (defun indenting-misc (stream operation &optional arg1 arg2)
1465   (let ((sub-stream (indenting-stream-stream stream)))
1466     (if (ansi-stream-p sub-stream)
1467         (let ((method (ansi-stream-misc sub-stream)))
1468           (case operation
1469             (:line-length
1470              (let ((line-length (funcall method sub-stream operation)))
1471                (if line-length
1472                    (- line-length (indenting-stream-indentation stream)))))
1473             (:charpos
1474              (let ((charpos (funcall method sub-stream operation)))
1475                (if charpos
1476                    (- charpos (indenting-stream-indentation stream)))))
1477             (t
1478              (funcall method sub-stream operation arg1 arg2))))
1479         ;; must be Gray streams FUNDAMENTAL-STREAM
1480         (case operation
1481           (:line-length
1482            (let ((line-length (stream-line-length sub-stream)))
1483              (if line-length
1484                  (- line-length (indenting-stream-indentation stream)))))
1485           (:charpos
1486            (let ((charpos (stream-line-column sub-stream)))
1487              (if charpos
1488                  (- charpos (indenting-stream-indentation stream)))))
1489           (t
1490            (stream-misc-dispatch sub-stream operation arg1 arg2))))))
1491
1492 (declaim (maybe-inline read-char unread-char read-byte listen))
1493 \f
1494 ;;;; case frobbing streams, used by FORMAT ~(...~)
1495
1496 (defstruct (case-frob-stream
1497             (:include ansi-stream
1498                       (misc #'case-frob-misc))
1499             (:constructor %make-case-frob-stream (target out sout))
1500             (:copier nil))
1501   (target (missing-arg) :type stream))
1502
1503 (defun make-case-frob-stream (target kind)
1504   #!+sb-doc
1505   "Return a stream that sends all output to the stream TARGET, but modifies
1506    the case of letters, depending on KIND, which should be one of:
1507      :UPCASE - convert to upper case.
1508      :DOWNCASE - convert to lower case.
1509      :CAPITALIZE - convert the first letter of words to upper case and the
1510         rest of the word to lower case.
1511      :CAPITALIZE-FIRST - convert the first letter of the first word to upper
1512         case and everything else to lower case."
1513   (declare (type stream target)
1514            (type (member :upcase :downcase :capitalize :capitalize-first)
1515                  kind)
1516            (values stream))
1517   (if (case-frob-stream-p target)
1518       ;; If we are going to be writing to a stream that already does
1519       ;; case frobbing, why bother frobbing the case just so it can
1520       ;; frob it again?
1521       target
1522       (multiple-value-bind (out sout)
1523           (ecase kind
1524             (:upcase
1525              (values #'case-frob-upcase-out
1526                      #'case-frob-upcase-sout))
1527             (:downcase
1528              (values #'case-frob-downcase-out
1529                      #'case-frob-downcase-sout))
1530             (:capitalize
1531              (values #'case-frob-capitalize-out
1532                      #'case-frob-capitalize-sout))
1533             (:capitalize-first
1534              (values #'case-frob-capitalize-first-out
1535                      #'case-frob-capitalize-first-sout)))
1536         (%make-case-frob-stream target out sout))))
1537
1538 (defun case-frob-misc (stream op &optional arg1 arg2)
1539   (declare (type case-frob-stream stream))
1540   (case op
1541     (:close
1542      (set-closed-flame stream))
1543     (t
1544      (let ((target (case-frob-stream-target stream)))
1545        (if (ansi-stream-p target)
1546            (funcall (ansi-stream-misc target) target op arg1 arg2)
1547            (stream-misc-dispatch target op arg1 arg2))))))
1548
1549 (defun case-frob-upcase-out (stream char)
1550   (declare (type case-frob-stream stream)
1551            (type character char))
1552   (let ((target (case-frob-stream-target stream))
1553         (char (char-upcase char)))
1554     (if (ansi-stream-p target)
1555         (funcall (ansi-stream-out target) target char)
1556         (stream-write-char target char))))
1557
1558 (defun case-frob-upcase-sout (stream str start end)
1559   (declare (type case-frob-stream stream)
1560            (type simple-string str)
1561            (type index start)
1562            (type (or index null) end))
1563   (let* ((target (case-frob-stream-target stream))
1564          (len (length str))
1565          (end (or end len))
1566          (string (if (and (zerop start) (= len end))
1567                      (string-upcase str)
1568                      (nstring-upcase (subseq str start end))))
1569          (string-len (- end start)))
1570     (if (ansi-stream-p target)
1571         (funcall (ansi-stream-sout target) target string 0 string-len)
1572         (stream-write-string target string 0 string-len))))
1573
1574 (defun case-frob-downcase-out (stream char)
1575   (declare (type case-frob-stream stream)
1576            (type character char))
1577   (let ((target (case-frob-stream-target stream))
1578         (char (char-downcase char)))
1579     (if (ansi-stream-p target)
1580         (funcall (ansi-stream-out target) target char)
1581         (stream-write-char target char))))
1582
1583 (defun case-frob-downcase-sout (stream str start end)
1584   (declare (type case-frob-stream stream)
1585            (type simple-string str)
1586            (type index start)
1587            (type (or index null) end))
1588   (let* ((target (case-frob-stream-target stream))
1589          (len (length str))
1590          (end (or end len))
1591          (string (if (and (zerop start) (= len end))
1592                      (string-downcase str)
1593                      (nstring-downcase (subseq str start end))))
1594          (string-len (- end start)))
1595     (if (ansi-stream-p target)
1596         (funcall (ansi-stream-sout target) target string 0 string-len)
1597         (stream-write-string target string 0 string-len))))
1598
1599 (defun case-frob-capitalize-out (stream char)
1600   (declare (type case-frob-stream stream)
1601            (type character char))
1602   (let ((target (case-frob-stream-target stream)))
1603     (cond ((alphanumericp char)
1604            (let ((char (char-upcase char)))
1605              (if (ansi-stream-p target)
1606                  (funcall (ansi-stream-out target) target char)
1607                  (stream-write-char target char)))
1608            (setf (case-frob-stream-out stream) #'case-frob-capitalize-aux-out)
1609            (setf (case-frob-stream-sout stream)
1610                  #'case-frob-capitalize-aux-sout))
1611           (t
1612            (if (ansi-stream-p target)
1613                (funcall (ansi-stream-out target) target char)
1614                (stream-write-char target char))))))
1615
1616 (defun case-frob-capitalize-sout (stream str start end)
1617   (declare (type case-frob-stream stream)
1618            (type simple-string str)
1619            (type index start)
1620            (type (or index null) end))
1621   (let* ((target (case-frob-stream-target stream))
1622          (str (subseq str start end))
1623          (len (length str))
1624          (inside-word nil))
1625     (dotimes (i len)
1626       (let ((char (schar str i)))
1627         (cond ((not (alphanumericp char))
1628                (setf inside-word nil))
1629               (inside-word
1630                (setf (schar str i) (char-downcase char)))
1631               (t
1632                (setf inside-word t)
1633                (setf (schar str i) (char-upcase char))))))
1634     (when inside-word
1635       (setf (case-frob-stream-out stream)
1636             #'case-frob-capitalize-aux-out)
1637       (setf (case-frob-stream-sout stream)
1638             #'case-frob-capitalize-aux-sout))
1639     (if (ansi-stream-p target)
1640         (funcall (ansi-stream-sout target) target str 0 len)
1641         (stream-write-string target str 0 len))))
1642
1643 (defun case-frob-capitalize-aux-out (stream char)
1644   (declare (type case-frob-stream stream)
1645            (type character char))
1646   (let ((target (case-frob-stream-target stream)))
1647     (cond ((alphanumericp char)
1648            (let ((char (char-downcase char)))
1649              (if (ansi-stream-p target)
1650                  (funcall (ansi-stream-out target) target char)
1651                  (stream-write-char target char))))
1652           (t
1653            (if (ansi-stream-p target)
1654                (funcall (ansi-stream-out target) target char)
1655                (stream-write-char target char))
1656            (setf (case-frob-stream-out stream)
1657                  #'case-frob-capitalize-out)
1658            (setf (case-frob-stream-sout stream)
1659                  #'case-frob-capitalize-sout)))))
1660
1661 (defun case-frob-capitalize-aux-sout (stream str start end)
1662   (declare (type case-frob-stream stream)
1663            (type simple-string str)
1664            (type index start)
1665            (type (or index null) end))
1666   (let* ((target (case-frob-stream-target stream))
1667          (str (subseq str start end))
1668          (len (length str))
1669          (inside-word t))
1670     (dotimes (i len)
1671       (let ((char (schar str i)))
1672         (cond ((not (alphanumericp char))
1673                (setf inside-word nil))
1674               (inside-word
1675                (setf (schar str i) (char-downcase char)))
1676               (t
1677                (setf inside-word t)
1678                (setf (schar str i) (char-upcase char))))))
1679     (unless inside-word
1680       (setf (case-frob-stream-out stream)
1681             #'case-frob-capitalize-out)
1682       (setf (case-frob-stream-sout stream)
1683             #'case-frob-capitalize-sout))
1684     (if (ansi-stream-p target)
1685         (funcall (ansi-stream-sout target) target str 0 len)
1686         (stream-write-string target str 0 len))))
1687
1688 (defun case-frob-capitalize-first-out (stream char)
1689   (declare (type case-frob-stream stream)
1690            (type character char))
1691   (let ((target (case-frob-stream-target stream)))
1692     (cond ((alphanumericp char)
1693            (let ((char (char-upcase char)))
1694              (if (ansi-stream-p target)
1695                  (funcall (ansi-stream-out target) target char)
1696                  (stream-write-char target char)))
1697            (setf (case-frob-stream-out stream)
1698                  #'case-frob-downcase-out)
1699            (setf (case-frob-stream-sout stream)
1700                  #'case-frob-downcase-sout))
1701           (t
1702            (if (ansi-stream-p target)
1703                (funcall (ansi-stream-out target) target char)
1704                (stream-write-char target char))))))
1705
1706 (defun case-frob-capitalize-first-sout (stream str start end)
1707   (declare (type case-frob-stream stream)
1708            (type simple-string str)
1709            (type index start)
1710            (type (or index null) end))
1711   (let* ((target (case-frob-stream-target stream))
1712          (str (subseq str start end))
1713          (len (length str)))
1714     (dotimes (i len)
1715       (let ((char (schar str i)))
1716         (when (alphanumericp char)
1717           (setf (schar str i) (char-upcase char))
1718           (do ((i (1+ i) (1+ i)))
1719               ((= i len))
1720             (setf (schar str i) (char-downcase (schar str i))))
1721           (setf (case-frob-stream-out stream)
1722                 #'case-frob-downcase-out)
1723           (setf (case-frob-stream-sout stream)
1724                 #'case-frob-downcase-sout)
1725           (return))))
1726     (if (ansi-stream-p target)
1727         (funcall (ansi-stream-sout target) target str 0 len)
1728         (stream-write-string target str 0 len))))
1729 \f
1730 ;;;; READ-SEQUENCE
1731
1732 (defun read-sequence (seq stream &key (start 0) end)
1733   #!+sb-doc
1734   "Destructively modify SEQ by reading elements from STREAM.
1735   That part of SEQ bounded by START and END is destructively modified by
1736   copying successive elements into it from STREAM. If the end of file
1737   for STREAM is reached before copying all elements of the subsequence,
1738   then the extra elements near the end of sequence are not updated, and
1739   the index of the next element is returned."
1740   (declare (type sequence seq)
1741            (type stream stream)
1742            (type index start)
1743            (type sequence-end end)
1744            (values index))
1745   (if (ansi-stream-p stream)
1746       (ansi-stream-read-sequence seq stream start end)
1747       ;; must be Gray streams FUNDAMENTAL-STREAM
1748       (stream-read-sequence stream seq start end)))
1749
1750 (defun ansi-stream-read-sequence (seq stream start %end)
1751   (declare (type sequence seq)
1752            (type ansi-stream stream)
1753            (type index start)
1754            (type sequence-end %end)
1755            (values index))
1756   (let ((end (or %end (length seq))))
1757     (declare (type index end))
1758     (etypecase seq
1759       (list
1760        (let ((read-function
1761               (if (subtypep (stream-element-type stream) 'character)
1762                   #'ansi-stream-read-char
1763                   #'ansi-stream-read-byte)))
1764          (do ((rem (nthcdr start seq) (rest rem))
1765               (i start (1+ i)))
1766              ((or (endp rem) (>= i end)) i)
1767            (declare (type list rem)
1768                     (type index i))
1769            (let ((el (funcall read-function stream nil :eof nil)))
1770              (when (eq el :eof)
1771                (return i))
1772              (setf (first rem) el)))))
1773       (vector
1774        (with-array-data ((data seq) (offset-start start) (offset-end end))
1775          (typecase data
1776            ((or (simple-array (unsigned-byte 8) (*))
1777                 (simple-array (signed-byte 8) (*)))
1778             (let* ((numbytes (- end start))
1779                    (bytes-read (read-n-bytes stream data offset-start
1780                                              numbytes nil)))
1781               (if (< bytes-read numbytes)
1782                   (+ start bytes-read)
1783                   end)))
1784            (t
1785             (let ((read-function
1786                    (if (subtypep (stream-element-type stream) 'character)
1787                        #'ansi-stream-read-char
1788                        #'ansi-stream-read-byte)))
1789               (do ((i offset-start (1+ i)))
1790                   ((>= i offset-end) end)
1791                 (declare (type index i))
1792                 (let ((el (funcall read-function stream nil :eof nil)))
1793                   (when (eq el :eof)
1794                     (return (+ start (- i offset-start))))
1795                   (setf (aref data i) el)))))))))))
1796 \f
1797 ;;;; WRITE-SEQUENCE
1798
1799 (defun write-sequence (seq stream &key (start 0) (end nil))
1800   #!+sb-doc
1801   "Write the elements of SEQ bounded by START and END to STREAM."
1802   (declare (type sequence seq)
1803            (type stream stream)
1804            (type index start)
1805            (type sequence-end end)
1806            (values sequence))
1807   (if (ansi-stream-p stream)
1808       (ansi-stream-write-sequence seq stream start end)
1809       ;; must be Gray-streams FUNDAMENTAL-STREAM
1810       (stream-write-sequence stream seq start end)))
1811
1812 (defun ansi-stream-write-sequence (seq stream start %end)
1813   (declare (type sequence seq)
1814            (type ansi-stream stream)
1815            (type index start)
1816            (type sequence-end %end)
1817            (values sequence))
1818   (let ((end (or %end (length seq))))
1819     (declare (type index end))
1820     (etypecase seq
1821       (list
1822        (let ((write-function
1823               (if (subtypep (stream-element-type stream) 'character)
1824                   (ansi-stream-out stream)
1825                   (ansi-stream-bout stream))))
1826          (do ((rem (nthcdr start seq) (rest rem))
1827               (i start (1+ i)))
1828              ((or (endp rem) (>= i end)))
1829            (declare (type list rem)
1830                     (type index i))
1831            (funcall write-function stream (first rem)))))
1832       (string
1833        (%write-string seq stream start end))
1834       (vector
1835        (with-array-data ((data seq) (offset-start start) (offset-end end))
1836          (labels
1837              ((output-seq-in-loop ()
1838                 (let ((write-function
1839                        (if (subtypep (stream-element-type stream) 'character)
1840                            (ansi-stream-out stream)
1841                            (ansi-stream-bout stream))))
1842                   (do ((i offset-start (1+ i)))
1843                       ((>= i offset-end))
1844                     (declare (type index i))
1845                     (funcall write-function stream (aref data i))))))
1846            (typecase data
1847              ((or (simple-array (unsigned-byte 8) (*))
1848                   (simple-array (signed-byte 8) (*)))
1849               (if (fd-stream-p stream)
1850                   (output-raw-bytes stream data offset-start offset-end)
1851                   (output-seq-in-loop)))
1852              (t
1853               (output-seq-in-loop))))))))
1854   seq)
1855 \f
1856 ;;;; etc.