Fix STREAM-ELEMENT-TYPE-STREAM-ELEMENT-MODE
[sbcl.git] / src / code / stream.lisp
blob933763334dfe70ecac7510cbbe7715e450f612df
1 ;;;; os-independent stream functions
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.
12 (in-package "SB!IMPL")
14 ;;;; standard streams
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")
26 (defun stream-element-type-stream-element-mode (element-type)
27 (when (eq element-type :default)
28 (return-from stream-element-type-stream-element-mode :bivalent))
30 (unless (valid-type-specifier-p element-type)
31 (return-from stream-element-type-stream-element-mode :bivalent))
33 (let* ((characterp (subtypep element-type 'character))
34 (unsigned-byte-p (subtypep element-type 'unsigned-byte))
35 ;; Every UNSIGNED-BYTE subtype is a SIGNED-BYTE
36 ;; subtype. Therefore explicitly check for intersection with
37 ;; the negative integers.
38 (signed-byte-p (and (subtypep element-type 'signed-byte)
39 (not (subtypep `(and ,element-type (integer * -1))
40 nil)))))
41 (cond
42 ((and characterp (not unsigned-byte-p) (not signed-byte-p))
43 'character)
44 ((and (not characterp) unsigned-byte-p (not signed-byte-p))
45 'unsigned-byte)
46 ((and (not characterp) (not unsigned-byte-p) signed-byte-p)
47 'signed-byte)
49 :bivalent))))
51 (defun ill-in (stream &rest ignore)
52 (declare (ignore ignore))
53 (error 'simple-type-error
54 :datum stream
55 :expected-type '(satisfies input-stream-p)
56 :format-control "~S is not a character input stream."
57 :format-arguments (list stream)))
58 (defun ill-out (stream &rest ignore)
59 (declare (ignore ignore))
60 (error 'simple-type-error
61 :datum stream
62 :expected-type '(satisfies output-stream-p)
63 :format-control "~S is not a character output stream."
64 :format-arguments (list stream)))
65 (defun ill-bin (stream &rest ignore)
66 (declare (ignore ignore))
67 (error 'simple-type-error
68 :datum stream
69 :expected-type '(satisfies input-stream-p)
70 :format-control "~S is not a binary input stream."
71 :format-arguments (list stream)))
72 (defun ill-bout (stream &rest ignore)
73 (declare (ignore ignore))
74 (error 'simple-type-error
75 :datum stream
76 :expected-type '(satisfies output-stream-p)
77 :format-control "~S is not a binary output stream."
78 :format-arguments (list stream)))
79 (defun closed-flame (stream &rest ignore)
80 (declare (ignore ignore))
81 (error 'closed-stream-error :stream stream))
82 (defun no-op-placeholder (&rest ignore)
83 (declare (ignore ignore)))
85 ;;; stream manipulation functions
87 ;;; SYNONYM-STREAM type is needed by ANSI-STREAM-{INPUT,OUTPUT}-STREAM-P
88 (defstruct (synonym-stream (:include ansi-stream
89 (in #'synonym-in)
90 (bin #'synonym-bin)
91 (n-bin #'synonym-n-bin)
92 (out #'synonym-out)
93 (bout #'synonym-bout)
94 (sout #'synonym-sout)
95 (misc #'synonym-misc))
96 (:constructor make-synonym-stream (symbol))
97 (:copier nil))
98 ;; This is the symbol, the value of which is the stream we are synonym to.
99 (symbol nil :type symbol :read-only t))
100 (declaim (freeze-type synonym-stream))
102 (defun ansi-stream-input-stream-p (stream)
103 (declare (type ansi-stream stream))
104 (if (synonym-stream-p stream)
105 (input-stream-p (symbol-value (synonym-stream-symbol stream)))
106 (and (not (eq (ansi-stream-in stream) #'closed-flame))
107 ;;; KLUDGE: It's probably not good to have EQ tests on function
108 ;;; values like this. What if someone's redefined the function?
109 ;;; Is there a better way? (Perhaps just VALID-FOR-INPUT and
110 ;;; VALID-FOR-OUTPUT flags? -- WHN 19990902
111 (or (not (eq (ansi-stream-in stream) #'ill-in))
112 (not (eq (ansi-stream-bin stream) #'ill-bin))))))
114 ;;; Temporary definition that gets overwritten by pcl/gray-streams
115 (defun input-stream-p (stream)
116 (declare (type stream stream))
117 (and (ansi-stream-p stream)
118 (ansi-stream-input-stream-p stream)))
120 (defun ansi-stream-output-stream-p (stream)
121 (declare (type ansi-stream stream))
122 (if (synonym-stream-p stream)
123 (output-stream-p (symbol-value (synonym-stream-symbol stream)))
124 (and (not (eq (ansi-stream-in stream) #'closed-flame))
125 (or (not (eq (ansi-stream-out stream) #'ill-out))
126 (not (eq (ansi-stream-bout stream) #'ill-bout))))))
128 ;;; Temporary definition that gets overwritten by pcl/gray-streams
129 (defun output-stream-p (stream)
130 (declare (type stream stream))
131 (and (ansi-stream-p stream)
132 (ansi-stream-output-stream-p stream)))
134 (declaim (inline ansi-stream-open-stream-p))
135 (defun ansi-stream-open-stream-p (stream)
136 (declare (type ansi-stream stream))
137 ;; CLHS 22.1.4 lets us not worry about synonym streams here.
138 (not (eq (ansi-stream-in stream) #'closed-flame)))
140 (defun open-stream-p (stream)
141 (ansi-stream-open-stream-p stream))
143 (declaim (inline ansi-stream-element-type))
144 (defun ansi-stream-element-type (stream)
145 (declare (type ansi-stream stream))
146 (funcall (ansi-stream-misc stream) stream :element-type))
148 (defun stream-element-type (stream)
149 (ansi-stream-element-type stream))
151 (defun stream-external-format (stream)
152 (funcall (ansi-stream-misc stream) stream :external-format))
154 (defun interactive-stream-p (stream)
155 (declare (type stream stream))
156 (funcall (ansi-stream-misc stream) stream :interactive-p))
158 (declaim (inline ansi-stream-close))
159 (defun ansi-stream-close (stream abort)
160 (declare (type ansi-stream stream))
161 (when (open-stream-p stream)
162 (funcall (ansi-stream-misc stream) stream :close abort))
165 (defun close (stream &key abort)
166 (ansi-stream-close stream abort))
168 (defun set-closed-flame (stream)
169 (setf (ansi-stream-in stream) #'closed-flame)
170 (setf (ansi-stream-bin stream) #'closed-flame)
171 (setf (ansi-stream-n-bin stream) #'closed-flame)
172 (setf (ansi-stream-out stream) #'closed-flame)
173 (setf (ansi-stream-bout stream) #'closed-flame)
174 (setf (ansi-stream-sout stream) #'closed-flame)
175 (setf (ansi-stream-misc stream) #'closed-flame))
177 ;;;; for file position and file length
178 (defun external-format-char-size (external-format)
179 (ef-char-size (get-external-format external-format)))
181 ;;; Call the MISC method with the :FILE-POSITION operation.
182 #!-sb-fluid (declaim (inline ansi-stream-file-position))
183 (defun ansi-stream-file-position (stream position)
184 (declare (type stream stream))
185 (declare (type (or index (alien sb!unix:unix-offset) (member nil :start :end))
186 position))
187 ;; FIXME: It would be good to comment on the stuff that is done here...
188 ;; FIXME: This doesn't look interrupt safe.
189 (cond
190 (position
191 (setf (ansi-stream-in-index stream) +ansi-stream-in-buffer-length+)
192 (funcall (ansi-stream-misc stream) stream :file-position position))
194 (let ((res (funcall (ansi-stream-misc stream) stream :file-position nil)))
195 (when res
196 #!-sb-unicode
197 (- res
198 (- +ansi-stream-in-buffer-length+
199 (ansi-stream-in-index stream)))
200 #!+sb-unicode
201 (let ((char-size (if (fd-stream-p stream)
202 (fd-stream-char-size stream)
203 (external-format-char-size (stream-external-format stream)))))
204 (- res
205 (etypecase char-size
206 (function
207 (loop with buffer = (ansi-stream-cin-buffer stream)
208 with start = (ansi-stream-in-index stream)
209 for i from start below +ansi-stream-in-buffer-length+
210 sum (funcall char-size (aref buffer i))))
211 (fixnum
212 (* char-size
213 (- +ansi-stream-in-buffer-length+
214 (ansi-stream-in-index stream))))))))))))
216 (defun file-position (stream &optional position)
217 (if (ansi-stream-p stream)
218 (ansi-stream-file-position stream position)
219 (stream-file-position stream position)))
221 ;;; This is a literal translation of the ANSI glossary entry "stream
222 ;;; associated with a file".
224 ;;; KLUDGE: Note that since Unix famously thinks "everything is a
225 ;;; file", and in particular stdin, stdout, and stderr are files, we
226 ;;; end up with this test being satisfied for weird things like
227 ;;; *STANDARD-OUTPUT* (to a tty). That seems unlikely to be what the
228 ;;; ANSI spec really had in mind, especially since this is used as a
229 ;;; qualification for operations like FILE-LENGTH (so that ANSI was
230 ;;; probably thinking of something like what Unix calls block devices)
231 ;;; but I can't see any better way to do it. -- WHN 2001-04-14
232 (defun stream-associated-with-file-p (x)
233 #!+sb-doc
234 "Test for the ANSI concept \"stream associated with a file\"."
235 (or (typep x 'file-stream)
236 (and (synonym-stream-p x)
237 (stream-associated-with-file-p (symbol-value
238 (synonym-stream-symbol x))))))
240 (defun stream-must-be-associated-with-file (stream)
241 (declare (type stream stream))
242 (unless (stream-associated-with-file-p stream)
243 (error 'simple-type-error
244 ;; KLUDGE: The ANSI spec for FILE-LENGTH specifically says
245 ;; this should be TYPE-ERROR. But what then can we use for
246 ;; EXPECTED-TYPE? This SATISFIES type (with a nonstandard
247 ;; private predicate function..) is ugly and confusing, but
248 ;; I can't see any other way. -- WHN 2001-04-14
249 :datum stream
250 :expected-type '(satisfies stream-associated-with-file-p)
251 :format-control
252 "~@<The stream ~2I~_~S ~I~_isn't associated with a file.~:>"
253 :format-arguments (list stream))))
255 (defun file-string-length (stream object)
256 (funcall (ansi-stream-misc stream) stream :file-string-length object))
258 ;;;; input functions
260 (defun ansi-stream-read-line-from-frc-buffer (stream eof-error-p eof-value)
261 (prepare-for-fast-read-char stream
262 (declare (ignore %frc-method%))
263 (declare (type ansi-stream-cin-buffer %frc-buffer%))
264 (let ((chunks-total-length 0)
265 (chunks nil))
266 (declare (type index chunks-total-length)
267 (list chunks))
268 (labels ((refill-buffer ()
269 (prog1 (fast-read-char-refill stream nil)
270 (setf %frc-index% (ansi-stream-in-index %frc-stream%))))
271 (build-result (pos n-more-chars)
272 (let ((res (make-string (+ chunks-total-length n-more-chars)))
273 (start1 chunks-total-length))
274 (declare (type index start1))
275 (when (>= pos 0)
276 (replace res %frc-buffer%
277 :start1 start1 :start2 %frc-index% :end2 pos)
278 (setf %frc-index% (1+ pos)))
279 (done-with-fast-read-char)
280 (dolist (chunk chunks res)
281 (declare (type (simple-array character (*)) chunk))
282 (decf start1 (length chunk))
283 (replace res chunk :start1 start1)))))
284 (declare (inline refill-buffer))
285 (if (or (< %frc-index% +ansi-stream-in-buffer-length+) (refill-buffer))
286 (loop
287 (let ((pos (position #\Newline %frc-buffer%
288 :test #'char= :start %frc-index%)))
289 (when pos
290 (return (values (build-result pos (- pos %frc-index%)) nil)))
291 (let ((chunk (subseq %frc-buffer% %frc-index%)))
292 (incf chunks-total-length (length chunk))
293 (push chunk chunks))
294 (unless (refill-buffer)
295 (return (values (build-result -1 0) t)))))
296 ;; EOF had been reached before we read anything
297 ;; at all. Return the EOF value or signal the error.
298 (progn (done-with-fast-read-char)
299 (eof-or-lose stream eof-error-p (values eof-value t))))))))
301 #!-sb-fluid (declaim (inline ansi-stream-read-line))
302 (defun ansi-stream-read-line (stream eof-error-p eof-value recursive-p)
303 (declare (ignore recursive-p))
304 (if (ansi-stream-cin-buffer stream)
305 ;; Stream has a fast-read-char buffer. Copy large chunks directly
306 ;; out of the buffer.
307 (ansi-stream-read-line-from-frc-buffer stream eof-error-p eof-value)
308 ;; Slow path, character by character.
309 (prepare-for-fast-read-char stream
310 (let ((res (make-string 80))
311 (len 80)
312 (index 0))
313 (loop
314 (let ((ch (fast-read-char nil nil)))
315 (cond (ch
316 (when (char= ch #\newline)
317 (done-with-fast-read-char)
318 (return (values (%shrink-vector res index) nil)))
319 (when (= index len)
320 (setq len (* len 2))
321 (let ((new (make-string len)))
322 (replace new res)
323 (setq res new)))
324 (setf (schar res index) ch)
325 (incf index))
326 ((zerop index)
327 (done-with-fast-read-char)
328 (return (values (eof-or-lose stream
329 eof-error-p
330 eof-value)
331 t)))
332 ;; Since FAST-READ-CHAR already hit the eof char, we
333 ;; shouldn't do another READ-CHAR.
335 (done-with-fast-read-char)
336 (return (values (%shrink-vector res index) t))))))))))
338 (defun read-line (&optional (stream *standard-input*) (eof-error-p t) eof-value
339 recursive-p)
340 (declare (explicit-check))
341 (let ((stream (in-synonym-of stream)))
342 (if (ansi-stream-p stream)
343 (ansi-stream-read-line stream eof-error-p eof-value recursive-p)
344 ;; must be Gray streams FUNDAMENTAL-STREAM
345 (multiple-value-bind (string eof) (stream-read-line stream)
346 (if (and eof (zerop (length string)))
347 (values (eof-or-lose stream eof-error-p eof-value) t)
348 (values string eof))))))
350 ;;; We proclaim them INLINE here, then proclaim them NOTINLINE later on,
351 ;;; so, except in this file, they are not inline by default, but they can be.
352 #!-sb-fluid (declaim (inline read-char unread-char read-byte listen))
354 #!-sb-fluid (declaim (inline ansi-stream-read-char))
355 (defun ansi-stream-read-char (stream eof-error-p eof-value recursive-p)
356 (declare (ignore recursive-p))
357 (prepare-for-fast-read-char stream
358 (prog1
359 (fast-read-char eof-error-p eof-value)
360 (done-with-fast-read-char))))
362 (defun read-char (&optional (stream *standard-input*)
363 (eof-error-p t)
364 eof-value
365 recursive-p)
366 (declare (explicit-check))
367 (let ((stream (in-synonym-of stream)))
368 (if (ansi-stream-p stream)
369 (ansi-stream-read-char stream eof-error-p eof-value recursive-p)
370 ;; must be Gray streams FUNDAMENTAL-STREAM
371 (let ((char (stream-read-char stream)))
372 (if (eq char :eof)
373 (eof-or-lose stream eof-error-p eof-value)
374 (the character char))))))
376 #!-sb-fluid (declaim (inline ansi-stream-unread-char))
377 (defun ansi-stream-unread-char (character stream)
378 (let ((index (1- (ansi-stream-in-index stream)))
379 (buffer (ansi-stream-cin-buffer stream)))
380 (declare (fixnum index))
381 (when (minusp index) (error "nothing to unread"))
382 (cond (buffer
383 (setf (aref buffer index) character)
384 (setf (ansi-stream-in-index stream) index)
385 ;; Ugh. an ANSI-STREAM with a char buffer never gives a chance to
386 ;; the stream's misc routine to handle the UNREAD operation.
387 (when (ansi-stream-input-char-pos stream)
388 (decf (ansi-stream-input-char-pos stream))))
390 (funcall (ansi-stream-misc stream) stream
391 :unread character)))))
393 (defun unread-char (character &optional (stream *standard-input*))
394 (declare (explicit-check))
395 (let ((stream (in-synonym-of stream)))
396 (if (ansi-stream-p stream)
397 (ansi-stream-unread-char character stream)
398 ;; must be Gray streams FUNDAMENTAL-STREAM
399 (stream-unread-char stream character)))
400 nil)
402 #!-sb-fluid (declaim (inline ansi-stream-listen))
403 (defun ansi-stream-listen (stream)
404 (or (/= (the fixnum (ansi-stream-in-index stream))
405 +ansi-stream-in-buffer-length+)
406 ;; Handle :EOF return from misc methods specially
407 (let ((result (funcall (ansi-stream-misc stream) stream :listen)))
408 (if (eq result :eof)
410 result))))
412 (defun listen (&optional (stream *standard-input*))
413 (declare (explicit-check))
414 (let ((stream (in-synonym-of stream)))
415 (if (ansi-stream-p stream)
416 (ansi-stream-listen stream)
417 ;; Fall through to Gray streams FUNDAMENTAL-STREAM case.
418 (stream-listen stream))))
420 #!-sb-fluid (declaim (inline ansi-stream-read-char-no-hang))
421 (defun ansi-stream-read-char-no-hang (stream eof-error-p eof-value recursive-p)
422 (if (funcall (ansi-stream-misc stream) stream :listen)
423 ;; On T or :EOF get READ-CHAR to do the work.
424 (ansi-stream-read-char stream eof-error-p eof-value recursive-p)
425 nil))
427 (defun read-char-no-hang (&optional (stream *standard-input*)
428 (eof-error-p t)
429 eof-value
430 recursive-p)
431 (declare (explicit-check))
432 (let ((stream (in-synonym-of stream)))
433 (if (ansi-stream-p stream)
434 (ansi-stream-read-char-no-hang stream eof-error-p eof-value
435 recursive-p)
436 ;; must be Gray streams FUNDAMENTAL-STREAM
437 (let ((char (stream-read-char-no-hang stream)))
438 (if (eq char :eof)
439 (eof-or-lose stream eof-error-p eof-value)
440 (the (or character null) char))))))
442 #!-sb-fluid (declaim (inline ansi-stream-clear-input))
443 (defun ansi-stream-clear-input (stream)
444 (setf (ansi-stream-in-index stream) +ansi-stream-in-buffer-length+)
445 (funcall (ansi-stream-misc stream) stream :clear-input))
447 (defun clear-input (&optional (stream *standard-input*))
448 (declare (explicit-check))
449 (let ((stream (in-synonym-of stream)))
450 (if (ansi-stream-p stream)
451 (ansi-stream-clear-input stream)
452 ;; must be Gray streams FUNDAMENTAL-STREAM
453 (stream-clear-input stream)))
454 nil)
456 #!-sb-fluid (declaim (inline ansi-stream-read-byte))
457 (defun ansi-stream-read-byte (stream eof-error-p eof-value recursive-p)
458 ;; Why the "recursive-p" parameter? a-s-r-b is funcall'ed from
459 ;; a-s-read-sequence and needs a lambda list that's congruent with
460 ;; that of a-s-read-char
461 (declare (ignore recursive-p))
462 (with-fast-read-byte (t stream eof-error-p eof-value)
463 (fast-read-byte)))
465 (defun read-byte (stream &optional (eof-error-p t) eof-value)
466 (declare (explicit-check))
467 (if (ansi-stream-p stream)
468 (ansi-stream-read-byte stream eof-error-p eof-value nil)
469 ;; must be Gray streams FUNDAMENTAL-STREAM
470 (let ((byte (stream-read-byte stream)))
471 (if (eq byte :eof)
472 (eof-or-lose stream eof-error-p eof-value)
473 (the integer byte)))))
475 ;;; Read NUMBYTES bytes into BUFFER beginning at START, and return the
476 ;;; number of bytes read.
478 ;;; Note: CMU CL's version of this had a special interpretation of
479 ;;; EOF-ERROR-P which SBCL does not have. (In the EOF-ERROR-P=NIL
480 ;;; case, CMU CL's version would return as soon as any data became
481 ;;; available.) This could be useful behavior for things like pipes in
482 ;;; some cases, but it wasn't being used in SBCL, so it was dropped.
483 ;;; If we ever need it, it could be added later as a new variant N-BIN
484 ;;; method (perhaps N-BIN-ASAP?) or something.
485 #!-sb-fluid (declaim (inline read-n-bytes))
486 (defun read-n-bytes (stream buffer start numbytes &optional (eof-error-p t))
487 (if (ansi-stream-p stream)
488 (ansi-stream-read-n-bytes stream buffer start numbytes eof-error-p)
489 ;; We don't need to worry about element-type size here is that
490 ;; callers are supposed to have checked everything is kosher.
491 (let* ((end (+ start numbytes))
492 (read-end (stream-read-sequence stream buffer start end)))
493 (eof-or-lose stream (and eof-error-p (< read-end end)) (- read-end start)))))
495 (defun ansi-stream-read-n-bytes (stream buffer start numbytes eof-error-p)
496 (declare (type ansi-stream stream)
497 (type index numbytes start)
498 (type (or (simple-array * (*)) system-area-pointer) buffer))
499 (let* ((in-buffer (ansi-stream-in-buffer stream))
500 (index (ansi-stream-in-index stream))
501 (num-buffered (- +ansi-stream-in-buffer-length+ index)))
502 (declare (fixnum index num-buffered))
503 (cond
504 ((not in-buffer)
505 (funcall (ansi-stream-n-bin stream)
506 stream
507 buffer
508 start
509 numbytes
510 eof-error-p))
511 ((<= numbytes num-buffered)
512 #+nil
513 (let ((copy-function (typecase buffer
514 ((simple-array * (*)) #'ub8-bash-copy)
515 (system-area-pointer #'copy-ub8-to-system-area))))
516 (funcall copy-function in-buffer index buffer start numbytes))
517 (%byte-blt in-buffer index
518 buffer start (+ start numbytes))
519 (setf (ansi-stream-in-index stream) (+ index numbytes))
520 numbytes)
522 (let ((end (+ start num-buffered)))
523 #+nil
524 (let ((copy-function (typecase buffer
525 ((simple-array * (*)) #'ub8-bash-copy)
526 (system-area-pointer #'copy-ub8-to-system-area))))
527 (funcall copy-function in-buffer index buffer start num-buffered))
528 (%byte-blt in-buffer index buffer start end)
529 (setf (ansi-stream-in-index stream) +ansi-stream-in-buffer-length+)
530 (+ (funcall (ansi-stream-n-bin stream)
531 stream
532 buffer
534 (- numbytes num-buffered)
535 eof-error-p)
536 num-buffered))))))
538 ;;; the amount of space we leave at the start of the in-buffer for
539 ;;; unreading
541 ;;; (It's 4 instead of 1 to allow word-aligned copies.)
542 (defconstant +ansi-stream-in-buffer-extra+
543 4) ; FIXME: should be symbolic constant
545 ;;; This function is called by the FAST-READ-CHAR expansion to refill
546 ;;; the IN-BUFFER for text streams. There is definitely an IN-BUFFER,
547 ;;; and hence must be an N-BIN method. It's also called by other stream
548 ;;; functions which directly peek into the frc buffer.
549 ;;; If EOF is hit and EOF-ERROR-P is false, then return NIL,
550 ;;; otherwise return the new index into CIN-BUFFER.
551 (defun fast-read-char-refill (stream eof-error-p)
552 (when (ansi-stream-input-char-pos stream)
553 ;; Characters between (ANSI-STREAM-IN-INDEX %FRC-STREAM%)
554 ;; and +ANSI-STREAM-IN-BUFFER-LENGTH+ have to be re-scanned.
555 (update-input-char-pos stream))
556 (let* ((ibuf (ansi-stream-cin-buffer stream))
557 (count (funcall (ansi-stream-n-bin stream)
558 stream
559 ibuf
560 +ansi-stream-in-buffer-extra+
561 (- +ansi-stream-in-buffer-length+
562 +ansi-stream-in-buffer-extra+)
563 nil))
564 (start (- +ansi-stream-in-buffer-length+ count)))
565 (declare (type index start count))
566 (cond ((zerop count)
567 ;; An empty count does not necessarily mean that we reached
568 ;; the EOF, it's also possible that it's e.g. due to a
569 ;; invalid octet sequence in a multibyte stream. To handle
570 ;; the resyncing case correctly we need to call the reading
571 ;; function and check whether an EOF was really reached. If
572 ;; not, we can just fill the buffer by one character, and
573 ;; hope that the next refill will not need to resync.
575 ;; KLUDGE: we can't use FD-STREAM functions (which are the
576 ;; only ones which will give us decoding errors) here,
577 ;; because this code is generic. We can't call the N-BIN
578 ;; function, because near the end of a real file that can
579 ;; legitimately bounce us to the IN function. So we have
580 ;; to call ANSI-STREAM-IN.
581 (let* ((index (1- +ansi-stream-in-buffer-length+))
582 (value (funcall (ansi-stream-in stream) stream nil :eof)))
583 (cond
584 ;; When not signaling an error, it is important that IN-INDEX
585 ;; be set to +ANSI-STREAM-IN-BUFFER-LENGTH+ here, even though
586 ;; DONE-WITH-FAST-READ-CHAR will do the same, thereby writing
587 ;; the caller's %FRC-INDEX% (= +ANSI-STREAM-IN-BUFFER-LENGTH+)
588 ;; into the slot. But because we've already bumped INPUT-CHAR-POS
589 ;; and scanned characters between the original %FRC-INDEX%
590 ;; and the buffer end (above), we must *not* do that again.
591 ((eql value :eof)
592 ;; definitely EOF now
593 (setf (ansi-stream-in-index stream)
594 +ansi-stream-in-buffer-length+)
595 (eof-or-lose stream eof-error-p nil))
596 ;; we resynced or were given something instead
598 (setf (aref ibuf index) value)
599 (setf (ansi-stream-in-index stream) index)))))
601 (when (/= start +ansi-stream-in-buffer-extra+)
602 (#.(let* ((n-character-array-bits
603 (sb!vm:saetp-n-bits
604 (find 'character
605 sb!vm:*specialized-array-element-type-properties*
606 :key #'sb!vm:saetp-specifier)))
607 (bash-function (intern (format nil "UB~D-BASH-COPY" n-character-array-bits)
608 (find-package "SB!KERNEL"))))
609 bash-function)
610 ibuf +ansi-stream-in-buffer-extra+
611 ibuf start
612 count))
613 (setf (ansi-stream-in-index stream) start)))))
615 ;;; This is similar to FAST-READ-CHAR-REFILL, but we don't have to
616 ;;; leave room for unreading.
617 (defun fast-read-byte-refill (stream eof-error-p eof-value)
618 (let* ((ibuf (ansi-stream-in-buffer stream))
619 (count (funcall (ansi-stream-n-bin stream) stream
620 ibuf 0 +ansi-stream-in-buffer-length+
621 nil))
622 (start (- +ansi-stream-in-buffer-length+ count)))
623 (declare (type index start count))
624 (cond ((zerop count)
625 (setf (ansi-stream-in-index stream) +ansi-stream-in-buffer-length+)
626 (funcall (ansi-stream-bin stream) stream eof-error-p eof-value))
628 (unless (zerop start)
629 (ub8-bash-copy ibuf 0
630 ibuf start
631 count))
632 (setf (ansi-stream-in-index stream) (1+ start))
633 (aref ibuf start)))))
635 ;;; output functions
637 (defun write-char (character &optional (stream *standard-output*))
638 (declare (explicit-check))
639 (with-out-stream stream (ansi-stream-out character)
640 (stream-write-char character))
641 character)
643 (defun terpri (&optional (stream *standard-output*))
644 (declare (explicit-check))
645 (with-out-stream stream (ansi-stream-out #\newline) (stream-terpri))
646 nil)
648 #!-sb-fluid (declaim (inline ansi-stream-fresh-line))
649 (defun ansi-stream-fresh-line (stream)
650 (when (/= (or (charpos stream) 1) 0)
651 (funcall (ansi-stream-out stream) stream #\newline)
654 (defun fresh-line (&optional (stream *standard-output*))
655 (declare (explicit-check))
656 (let ((stream (out-synonym-of stream)))
657 (if (ansi-stream-p stream)
658 (ansi-stream-fresh-line stream)
659 ;; must be Gray streams FUNDAMENTAL-STREAM
660 (stream-fresh-line stream))))
662 #!-sb-fluid (declaim (inline ansi-stream-write-string))
663 (defun ansi-stream-write-string (string stream start end)
664 (with-array-data ((data string) (offset-start start)
665 (offset-end end)
666 :check-fill-pointer t)
667 (funcall (ansi-stream-sout stream)
668 stream data offset-start offset-end)))
670 (defun %write-string (string stream start end)
671 (let ((stream (out-synonym-of stream)))
672 (if (ansi-stream-p stream)
673 (ansi-stream-write-string string stream start end)
674 ;; must be Gray streams FUNDAMENTAL-STREAM
675 (stream-write-string stream string start end)))
676 string)
678 (defun write-string (string &optional (stream *standard-output*)
679 &key (start 0) end)
680 (declare (type string string))
681 (declare (type stream-designator stream))
682 (declare (explicit-check))
683 (%write-string string stream start end))
685 (defun write-line (string &optional (stream *standard-output*)
686 &key (start 0) end)
687 (declare (type string string))
688 (declare (type stream-designator stream))
689 (declare (explicit-check))
690 (let ((stream (out-synonym-of stream)))
691 (cond ((ansi-stream-p stream)
692 (ansi-stream-write-string string stream start end)
693 (funcall (ansi-stream-out stream) stream #\newline))
695 (stream-write-string stream string start end)
696 (stream-write-char stream #\newline))))
697 string)
699 (defun charpos (&optional (stream *standard-output*))
700 (with-out-stream stream (ansi-stream-misc :charpos) (stream-line-column)))
702 (defun line-length (&optional (stream *standard-output*))
703 (with-out-stream stream (ansi-stream-misc :line-length)
704 (stream-line-length)))
706 (defun finish-output (&optional (stream *standard-output*))
707 (declare (explicit-check))
708 (with-out-stream stream (ansi-stream-misc :finish-output)
709 (stream-finish-output))
710 nil)
712 (defun force-output (&optional (stream *standard-output*))
713 (declare (explicit-check))
714 (with-out-stream stream (ansi-stream-misc :force-output)
715 (stream-force-output))
716 nil)
718 (defun clear-output (&optional (stream *standard-output*))
719 (declare (explicit-check))
720 (with-out-stream stream (ansi-stream-misc :clear-output)
721 (stream-clear-output))
722 nil)
724 (defun write-byte (integer stream)
725 (declare (explicit-check))
726 (with-out-stream/no-synonym stream (ansi-stream-bout integer)
727 (stream-write-byte integer))
728 integer)
731 ;;; Meta: the following comment is mostly true, but gray stream support
732 ;;; is already incorporated into the definitions within this file.
733 ;;; But these need to redefinable, otherwise the relative order of
734 ;;; loading sb-simple-streams and any user-defined code which executes
735 ;;; (F #'read-char ...) is sensitive to the order in which those
736 ;;; are loaded, though insensitive at compile-time.
737 ;;; (These were inline throughout this file, but that's not appropriate
738 ;;; globally. And we must not inline them in the rest of this file if
739 ;;; dispatch to gray or simple streams is to work, since both redefine
740 ;;; these functions later.)
741 (declaim (notinline read-char unread-char read-byte listen))
743 ;;; This is called from ANSI-STREAM routines that encapsulate CLOS
744 ;;; streams to handle the misc routines and dispatch to the
745 ;;; appropriate SIMPLE- or FUNDAMENTAL-STREAM functions.
746 (defun stream-misc-dispatch (stream operation &optional arg1 arg2)
747 (declare (type stream stream) (ignore arg2))
748 (ecase operation
749 (:listen
750 ;; Return T if input available, :EOF for end-of-file, otherwise NIL.
751 (let ((char (read-char-no-hang stream nil :eof)))
752 (when (characterp char)
753 (unread-char char stream))
754 char))
755 (:unread
756 (unread-char arg1 stream))
757 (:close
758 (close stream))
759 (:clear-input
760 (clear-input stream))
761 (:force-output
762 (force-output stream))
763 (:finish-output
764 (finish-output stream))
765 (:element-type
766 (stream-element-type stream))
767 (:stream-external-format
768 (stream-external-format stream))
769 (:interactive-p
770 (interactive-stream-p stream))
771 (:line-length
772 (line-length stream))
773 (:charpos
774 (charpos stream))
775 (:file-length
776 (file-length stream))
777 (:file-string-length
778 (file-string-length stream arg1))
779 (:file-position
780 (file-position stream arg1))))
782 ;;;; broadcast streams
784 (defstruct (broadcast-stream (:include ansi-stream
785 (out #'broadcast-out)
786 (bout #'broadcast-bout)
787 (sout #'broadcast-sout)
788 (misc #'broadcast-misc))
789 (:constructor %make-broadcast-stream
790 (streams))
791 (:copier nil)
792 (:predicate nil))
793 ;; a list of all the streams we broadcast to
794 (streams () :type list :read-only t))
796 (declaim (freeze-type broadcast-stream))
798 (defun make-broadcast-stream (&rest streams)
799 (dolist (stream streams)
800 (unless (output-stream-p stream)
801 (error 'type-error
802 :datum stream
803 :expected-type '(satisfies output-stream-p))))
804 (%make-broadcast-stream streams))
806 (macrolet ((out-fun (name fun &rest args)
807 `(defun ,name (stream ,@args)
808 (dolist (stream (broadcast-stream-streams stream))
809 (,fun ,(car args) stream ,@(cdr args))))))
810 (out-fun broadcast-out write-char char)
811 (out-fun broadcast-bout write-byte byte)
812 (out-fun broadcast-sout %write-string string start end))
814 (defun broadcast-misc (stream operation &optional arg1 arg2)
815 (let ((streams (broadcast-stream-streams stream)))
816 (case operation
817 ;; FIXME: This may not be the best place to note this, but I
818 ;; think the :CHARPOS protocol needs revision. Firstly, I think
819 ;; this is the last place where a NULL return value was possible
820 ;; (before adjusting it to be 0), so a bunch of conditionals IF
821 ;; CHARPOS can be removed; secondly, it is my belief that
822 ;; FD-STREAMS, when running FILE-POSITION, do not update the
823 ;; CHARPOS, and consequently there will be much wrongness.
825 ;; FIXME: see also TWO-WAY-STREAM treatment of :CHARPOS -- why
826 ;; is it testing the :charpos of an input stream?
828 ;; -- CSR, 2004-02-04
829 (:charpos
830 (dolist (stream streams 0)
831 (let ((charpos (charpos stream)))
832 (when charpos
833 (return charpos)))))
834 (:line-length
835 (let ((min nil))
836 (dolist (stream streams min)
837 (let ((res (line-length stream)))
838 (when res (setq min (if min (min res min) res)))))))
839 (:element-type
840 (let ((last (last streams)))
841 (if last
842 (stream-element-type (car last))
843 t)))
844 (:external-format
845 (let ((last (last streams)))
846 (if last
847 (stream-external-format (car last))
848 :default)))
849 (:file-length
850 (let ((last (last streams)))
851 (if last
852 (file-length (car last))
853 0)))
854 (:file-position
855 (if arg1
856 (let ((res (or (eql arg1 :start) (eql arg1 0))))
857 (dolist (stream streams res)
858 (setq res (file-position stream arg1))))
859 (let ((last (last streams)))
860 (if last
861 (file-position (car last))
862 0))))
863 (:file-string-length
864 (let ((last (last streams)))
865 (if last
866 (file-string-length (car last) arg1)
867 1)))
868 (:close
869 (set-closed-flame stream))
871 (let ((res nil))
872 (dolist (stream streams res)
873 (setq res
874 (if (ansi-stream-p stream)
875 (funcall (ansi-stream-misc stream) stream operation
876 arg1 arg2)
877 (stream-misc-dispatch stream operation arg1 arg2)))))))))
879 ;;;; synonym streams
881 (def!method print-object ((x synonym-stream) stream)
882 (print-unreadable-object (x stream :type t :identity t)
883 (format stream ":SYMBOL ~S" (synonym-stream-symbol x))))
885 ;;; The output simple output methods just call the corresponding
886 ;;; function on the synonymed stream.
887 (macrolet ((out-fun (name fun &rest args)
888 `(defun ,name (stream ,@args)
889 (declare (optimize (safety 1)))
890 (let ((syn (symbol-value (synonym-stream-symbol stream))))
891 (,fun ,(car args) syn ,@(cdr args))))))
892 (out-fun synonym-out write-char ch)
893 (out-fun synonym-bout write-byte n)
894 (out-fun synonym-sout %write-string string start end))
896 ;;; For the input methods, we just call the corresponding function on the
897 ;;; synonymed stream. These functions deal with getting input out of
898 ;;; the In-Buffer if there is any.
899 (macrolet ((in-fun (name fun &rest args)
900 `(defun ,name (stream ,@args)
901 (declare (optimize (safety 1)))
902 (,fun (symbol-value (synonym-stream-symbol stream))
903 ,@args))))
904 (in-fun synonym-in read-char eof-error-p eof-value)
905 (in-fun synonym-bin read-byte eof-error-p eof-value)
906 (in-fun synonym-n-bin read-n-bytes buffer start numbytes eof-error-p))
908 (defun synonym-misc (stream operation &optional arg1 arg2)
909 (declare (optimize (safety 1)))
910 (let ((syn (symbol-value (synonym-stream-symbol stream))))
911 (if (ansi-stream-p syn)
912 ;; We have to special-case some operations which interact with
913 ;; the in-buffer of the wrapped stream, since just calling
914 ;; ANSI-STREAM-MISC on them
915 (case operation
916 (:listen (or (/= (the fixnum (ansi-stream-in-index syn))
917 +ansi-stream-in-buffer-length+)
918 (funcall (ansi-stream-misc syn) syn :listen)))
919 (:clear-input (clear-input syn))
920 (:unread (unread-char arg1 syn))
922 (funcall (ansi-stream-misc syn) syn operation arg1 arg2)))
923 (stream-misc-dispatch syn operation arg1 arg2))))
925 ;;;; two-way streams
927 (defstruct (two-way-stream
928 (:include ansi-stream
929 (in #'two-way-in)
930 (bin #'two-way-bin)
931 (n-bin #'two-way-n-bin)
932 (out #'two-way-out)
933 (bout #'two-way-bout)
934 (sout #'two-way-sout)
935 (misc #'two-way-misc))
936 (:constructor %make-two-way-stream (input-stream output-stream))
937 (:copier nil)
938 (:predicate nil))
939 (input-stream (missing-arg) :type stream :read-only t)
940 (output-stream (missing-arg) :type stream :read-only t))
942 (defprinter (two-way-stream) input-stream output-stream)
944 (defun make-two-way-stream (input-stream output-stream)
945 #!+sb-doc
946 "Return a bidirectional stream which gets its input from INPUT-STREAM and
947 sends its output to OUTPUT-STREAM."
948 ;; FIXME: This idiom of the-real-stream-of-a-possibly-synonym-stream
949 ;; should be encapsulated in a function, and used here and most of
950 ;; the other places that SYNONYM-STREAM-P appears.
951 (unless (output-stream-p output-stream)
952 (error 'type-error
953 :datum output-stream
954 :expected-type '(satisfies output-stream-p)))
955 (unless (input-stream-p input-stream)
956 (error 'type-error
957 :datum input-stream
958 :expected-type '(satisfies input-stream-p)))
959 (%make-two-way-stream input-stream output-stream))
961 (macrolet ((out-fun (name fun &rest args)
962 `(defun ,name (stream ,@args)
963 (let ((syn (two-way-stream-output-stream stream)))
964 (,fun ,(car args) syn ,@(cdr args))))))
965 (out-fun two-way-out write-char ch)
966 (out-fun two-way-bout write-byte n)
967 (out-fun two-way-sout %write-string string start end))
969 (macrolet ((in-fun (name fun &rest args)
970 `(defun ,name (stream ,@args)
971 (,fun (two-way-stream-input-stream stream) ,@args))))
972 (in-fun two-way-in read-char eof-error-p eof-value)
973 (in-fun two-way-bin read-byte eof-error-p eof-value)
974 (in-fun two-way-n-bin read-n-bytes buffer start numbytes eof-error-p))
976 (defun two-way-misc (stream operation &optional arg1 arg2)
977 (let* ((in (two-way-stream-input-stream stream))
978 (out (two-way-stream-output-stream stream))
979 (in-ansi-stream-p (ansi-stream-p in))
980 (out-ansi-stream-p (ansi-stream-p out)))
981 (case operation
982 (:listen
983 (if in-ansi-stream-p
984 (or (/= (the fixnum (ansi-stream-in-index in))
985 +ansi-stream-in-buffer-length+)
986 (funcall (ansi-stream-misc in) in :listen))
987 (listen in)))
988 ((:finish-output :force-output :clear-output)
989 (if out-ansi-stream-p
990 (funcall (ansi-stream-misc out) out operation arg1 arg2)
991 (stream-misc-dispatch out operation arg1 arg2)))
992 (:clear-input (clear-input in))
993 (:unread (unread-char arg1 in))
994 (:element-type
995 (let ((in-type (stream-element-type in))
996 (out-type (stream-element-type out)))
997 (if (equal in-type out-type)
998 in-type `(and ,in-type ,out-type))))
999 (:close
1000 (set-closed-flame stream))
1002 (or (if in-ansi-stream-p
1003 (funcall (ansi-stream-misc in) in operation arg1 arg2)
1004 (stream-misc-dispatch in operation arg1 arg2))
1005 (if out-ansi-stream-p
1006 (funcall (ansi-stream-misc out) out operation arg1 arg2)
1007 (stream-misc-dispatch out operation arg1 arg2)))))))
1009 ;;;; concatenated streams
1011 (defstruct (concatenated-stream
1012 (:include ansi-stream
1013 (in #'concatenated-in)
1014 (bin #'concatenated-bin)
1015 (n-bin #'concatenated-n-bin)
1016 (misc #'concatenated-misc))
1017 (:constructor %make-concatenated-stream (streams))
1018 (:copier nil)
1019 (:predicate nil))
1020 ;; The car of this is the substream we are reading from now.
1021 (streams nil :type list))
1023 (declaim (freeze-type concatenated-stream))
1025 (def!method print-object ((x concatenated-stream) stream)
1026 (print-unreadable-object (x stream :type t :identity t)
1027 (format stream
1028 ":STREAMS ~S"
1029 (concatenated-stream-streams x))))
1031 (defun make-concatenated-stream (&rest streams)
1032 #!+sb-doc
1033 "Return a stream which takes its input from each of the streams in turn,
1034 going on to the next at EOF."
1035 (dolist (stream streams)
1036 (unless (input-stream-p stream)
1037 (error 'type-error
1038 :datum stream
1039 :expected-type '(satisfies input-stream-p))))
1040 (%make-concatenated-stream streams))
1042 (macrolet ((in-fun (name fun)
1043 `(defun ,name (stream eof-error-p eof-value)
1044 (do ((streams (concatenated-stream-streams stream)
1045 (cdr streams)))
1046 ((null streams)
1047 (eof-or-lose stream eof-error-p eof-value))
1048 (let* ((stream (car streams))
1049 (result (,fun stream nil nil)))
1050 (when result (return result)))
1051 (pop (concatenated-stream-streams stream))))))
1052 (in-fun concatenated-in read-char)
1053 (in-fun concatenated-bin read-byte))
1055 (defun concatenated-n-bin (stream buffer start numbytes eof-errorp)
1056 (do ((streams (concatenated-stream-streams stream) (cdr streams))
1057 (current-start start)
1058 (remaining-bytes numbytes))
1059 ((null streams)
1060 (if eof-errorp
1061 (error 'end-of-file :stream stream)
1062 (- numbytes remaining-bytes)))
1063 (let* ((stream (car streams))
1064 (bytes-read (read-n-bytes stream buffer current-start
1065 remaining-bytes nil)))
1066 (incf current-start bytes-read)
1067 (decf remaining-bytes bytes-read)
1068 (when (zerop remaining-bytes) (return numbytes)))
1069 (setf (concatenated-stream-streams stream) (cdr streams))))
1071 (defun concatenated-misc (stream operation &optional arg1 arg2)
1072 (let* ((left (concatenated-stream-streams stream))
1073 (current (car left)))
1074 (case operation
1075 (:listen
1076 (unless left
1077 (return-from concatenated-misc :eof))
1078 (loop
1079 (let ((stuff (if (ansi-stream-p current)
1080 (funcall (ansi-stream-misc current) current
1081 :listen)
1082 (stream-misc-dispatch current :listen))))
1083 (cond ((eq stuff :eof)
1084 ;; Advance STREAMS, and try again.
1085 (pop (concatenated-stream-streams stream))
1086 (setf current
1087 (car (concatenated-stream-streams stream)))
1088 (unless current
1089 ;; No further streams. EOF.
1090 (return :eof)))
1091 (stuff
1092 ;; Stuff's available.
1093 (return t))
1095 ;; Nothing is available yet.
1096 (return nil))))))
1097 (:clear-input (when left (clear-input current)))
1098 (:unread (when left (unread-char arg1 current)))
1099 (:close
1100 (set-closed-flame stream))
1102 (when left
1103 (if (ansi-stream-p current)
1104 (funcall (ansi-stream-misc current) current operation arg1 arg2)
1105 (stream-misc-dispatch current operation arg1 arg2)))))))
1107 ;;;; echo streams
1109 (defstruct (echo-stream
1110 (:include two-way-stream
1111 (in #'echo-in)
1112 (bin #'echo-bin)
1113 (misc #'echo-misc)
1114 (n-bin #'echo-n-bin))
1115 (:constructor %make-echo-stream (input-stream output-stream))
1116 (:copier nil)
1117 (:predicate nil))
1118 (unread-stuff nil :type boolean))
1120 (declaim (freeze-type echo-stream))
1122 (def!method print-object ((x echo-stream) stream)
1123 (print-unreadable-object (x stream :type t :identity t)
1124 (format stream
1125 ":INPUT-STREAM ~S :OUTPUT-STREAM ~S"
1126 (two-way-stream-input-stream x)
1127 (two-way-stream-output-stream x))))
1129 (defun make-echo-stream (input-stream output-stream)
1130 #!+sb-doc
1131 "Return a bidirectional stream which gets its input from INPUT-STREAM and
1132 sends its output to OUTPUT-STREAM. In addition, all input is echoed to
1133 the output stream."
1134 (unless (output-stream-p output-stream)
1135 (error 'type-error
1136 :datum output-stream
1137 :expected-type '(satisfies output-stream-p)))
1138 (unless (input-stream-p input-stream)
1139 (error 'type-error
1140 :datum input-stream
1141 :expected-type '(satisfies input-stream-p)))
1142 (%make-echo-stream input-stream output-stream))
1144 (macrolet ((in-fun (name in-fun out-fun &rest args)
1145 `(defun ,name (stream ,@args)
1146 (let* ((unread-stuff-p (echo-stream-unread-stuff stream))
1147 (in (echo-stream-input-stream stream))
1148 (out (echo-stream-output-stream stream))
1149 (result (if eof-error-p
1150 (,in-fun in ,@args)
1151 (,in-fun in nil in))))
1152 (setf (echo-stream-unread-stuff stream) nil)
1153 (cond
1154 ((eql result in) eof-value)
1155 ;; If unread-stuff was true, the character read
1156 ;; from the input stream was previously echoed.
1157 (t (unless unread-stuff-p (,out-fun result out)) result))))))
1158 (in-fun echo-in read-char write-char eof-error-p eof-value)
1159 (in-fun echo-bin read-byte write-byte eof-error-p eof-value))
1161 (defun echo-n-bin (stream buffer start numbytes eof-error-p)
1162 (let ((bytes-read 0))
1163 ;; Note: before ca 1.0.27.18, the logic for handling unread
1164 ;; characters never could have worked, so probably nobody has ever
1165 ;; tried doing bivalent block I/O through an echo stream; this may
1166 ;; not work either.
1167 (when (echo-stream-unread-stuff stream)
1168 (let* ((char (read-char stream))
1169 (octets (string-to-octets
1170 (string char)
1171 :external-format
1172 (stream-external-format
1173 (echo-stream-input-stream stream))))
1174 (octet-count (length octets))
1175 (blt-count (min octet-count numbytes)))
1176 (replace buffer octets :start1 start :end1 (+ start blt-count))
1177 (incf start blt-count)
1178 (decf numbytes blt-count)))
1179 (incf bytes-read (read-n-bytes (echo-stream-input-stream stream) buffer
1180 start numbytes nil))
1181 (cond
1182 ((not eof-error-p)
1183 (write-sequence buffer (echo-stream-output-stream stream)
1184 :start start :end (+ start bytes-read))
1185 bytes-read)
1186 ((> numbytes bytes-read)
1187 (write-sequence buffer (echo-stream-output-stream stream)
1188 :start start :end (+ start bytes-read))
1189 (error 'end-of-file :stream stream))
1191 (write-sequence buffer (echo-stream-output-stream stream)
1192 :start start :end (+ start bytes-read))
1193 (aver (= numbytes (+ start bytes-read)))
1194 numbytes))))
1196 ;;;; STRING-INPUT-STREAM stuff
1198 (defstruct (string-input-stream
1199 (:include ansi-stream
1200 (in #'string-inch)
1201 (misc #'string-in-misc))
1202 (:constructor %make-string-input-stream
1203 (string current end))
1204 (:copier nil)
1205 (:predicate nil))
1206 (string (missing-arg) :type simple-string :read-only t)
1207 (current (missing-arg) :type index)
1208 (end (missing-arg) :type index))
1210 (declaim (freeze-type string-input-stream))
1212 (defun string-inch (stream eof-error-p eof-value)
1213 (declare (type string-input-stream stream))
1214 (let ((string (string-input-stream-string stream))
1215 (index (string-input-stream-current stream)))
1216 (cond ((>= index (the index (string-input-stream-end stream)))
1217 (eof-or-lose stream eof-error-p eof-value))
1219 (setf (string-input-stream-current stream) (1+ index))
1220 (char string index)))))
1222 (defun string-binch (stream eof-error-p eof-value)
1223 (declare (type string-input-stream stream))
1224 (let ((string (string-input-stream-string stream))
1225 (index (string-input-stream-current stream)))
1226 (cond ((>= index (the index (string-input-stream-end stream)))
1227 (eof-or-lose stream eof-error-p eof-value))
1229 (setf (string-input-stream-current stream) (1+ index))
1230 (char-code (char string index))))))
1232 (defun string-stream-read-n-bytes (stream buffer start requested eof-error-p)
1233 (declare (type string-input-stream stream)
1234 (type index start requested))
1235 (let* ((string (string-input-stream-string stream))
1236 (index (string-input-stream-current stream))
1237 (available (- (string-input-stream-end stream) index))
1238 (copy (min available requested)))
1239 (declare (type simple-string string))
1240 (when (plusp copy)
1241 (setf (string-input-stream-current stream)
1242 (truly-the index (+ index copy)))
1243 ;; FIXME: why are we VECTOR-SAP'ing things here? what's the point?
1244 ;; and are there SB-UNICODE issues here as well? --njf, 2005-03-24
1245 (with-pinned-objects (string buffer)
1246 (system-area-ub8-copy (vector-sap string)
1247 index
1248 (if (typep buffer 'system-area-pointer)
1249 buffer
1250 (vector-sap buffer))
1251 start
1252 copy)))
1253 (if (and (> requested copy) eof-error-p)
1254 (error 'end-of-file :stream stream)
1255 copy)))
1257 (defun string-in-misc (stream operation &optional arg1 arg2)
1258 (declare (type string-input-stream stream)
1259 (ignore arg2))
1260 (case operation
1261 (:file-position
1262 (if arg1
1263 (setf (string-input-stream-current stream)
1264 (case arg1
1265 (:start 0)
1266 (:end (string-input-stream-end stream))
1267 ;; We allow moving position beyond EOF. Errors happen
1268 ;; on read, not move.
1269 (t arg1)))
1270 (string-input-stream-current stream)))
1271 ;; According to ANSI: "Should signal an error of type type-error
1272 ;; if stream is not a stream associated with a file."
1273 ;; This is checked by FILE-LENGTH, so no need to do it here either.
1274 ;; (:file-length (length (string-input-stream-string stream)))
1275 (:unread (decf (string-input-stream-current stream)))
1276 (:close (set-closed-flame stream))
1277 (:listen (or (/= (the index (string-input-stream-current stream))
1278 (the index (string-input-stream-end stream)))
1279 :eof))
1280 (:element-type (array-element-type (string-input-stream-string stream)))))
1282 (defun make-string-input-stream (string &optional (start 0) end)
1283 #!+sb-doc
1284 "Return an input stream which will supply the characters of STRING between
1285 START and END in order."
1286 (declare (type string string)
1287 (type index start)
1288 (type (or index null) end))
1289 ;; FIXME: very inefficient if the input string is, say a 100000-character
1290 ;; adjustable string but (- END START) is 100 characters. We should use
1291 ;; SUBSEQ instead of coercing the whole string. And if STRING is non-simple
1292 ;; but has element type CHARACTER, wouldn't it work to just use the
1293 ;; underlying simple-string since %MAKE-STRING-INPUT-STREAM accepts bounding
1294 ;; indices that can be fudged to deal with any offset?
1295 ;; And (for unicode builds) if the input is BASE-STRING, we should use
1296 ;; MAKE-ARRAY and REPLACE to coerce just the specified piece.
1297 (let* ((string (coerce string '(simple-array character (*)))))
1298 ;; Why WITH-ARRAY-DATA, since the array is already simple?
1299 ;; because it's a nice abstract way to check the START and END.
1300 (with-array-data ((string string) (start start) (end end))
1301 (%make-string-input-stream
1302 string ;; now simple
1303 start end))))
1305 ;;;; STRING-OUTPUT-STREAM stuff
1306 ;;;;
1307 ;;;; FIXME: This, like almost none of the stream code is particularly
1308 ;;;; interrupt or thread-safe. While it should not be possible to
1309 ;;;; corrupt the heap here, it certainly is possible to end up with
1310 ;;;; a string-output-stream whose internal state is messed up.
1311 ;;;;
1312 ;;;; FIXME: It would be nice to support space-efficient
1313 ;;;; string-output-streams with element-type base-char. This would
1314 ;;;; mean either a separate subclass, or typecases in functions.
1316 (defparameter *string-output-stream-buffer-initial-size* 64)
1318 (defstruct (string-output-stream
1319 (:include ansi-stream
1320 (out #'string-ouch)
1321 (sout #'string-sout)
1322 (misc #'string-out-misc))
1323 (:constructor %make-string-output-stream (element-type))
1324 (:copier nil)
1325 (:predicate nil))
1326 ;; The string we throw stuff in.
1327 (buffer (make-string
1328 *string-output-stream-buffer-initial-size*)
1329 :type (simple-array character (*)))
1330 ;; Chains of buffers to use
1331 (prev nil :type list)
1332 (next nil :type list)
1333 ;; Index of the next location to use in the current string.
1334 (pointer 0 :type index)
1335 ;; Global location in the stream
1336 (index 0 :type index)
1337 ;; Index cache: when we move backwards we save the greater of this
1338 ;; and index here, so the greater of index and this is always the
1339 ;; end of the stream.
1340 (index-cache 0 :type index)
1341 ;; Requested element type
1342 ;; FIXME: there seems to be no way to skip the type-check in the ctor,
1343 ;; which is redundant with the check in MAKE-STRING-OUTPUT-STREAM.
1344 (element-type 'character :type type-specifier
1345 :read-only t))
1347 (declaim (freeze-type string-output-stream))
1348 (defun make-string-output-stream (&key (element-type 'character))
1349 #!+sb-doc
1350 "Return an output stream which will accumulate all output given it for the
1351 benefit of the function GET-OUTPUT-STREAM-STRING."
1352 (declare (explicit-check))
1353 (if (csubtypep (specifier-type element-type) (specifier-type 'character))
1354 (%make-string-output-stream element-type)
1355 (error "~S is not a subtype of CHARACTER" element-type)))
1357 ;;; Pushes the current segment onto the prev-list, and either pops
1358 ;;; or allocates a new one.
1359 (defun string-output-stream-new-buffer (stream size)
1360 (declare (index size))
1361 (/noshow0 "/string-output-stream-new-buffer")
1362 (push (string-output-stream-buffer stream)
1363 (string-output-stream-prev stream))
1364 (setf (string-output-stream-buffer stream)
1365 (or (pop (string-output-stream-next stream))
1366 ;; FIXME: This would be the correct place to detect that
1367 ;; more then FIXNUM characters are being written to the
1368 ;; stream, and do something about it.
1369 (make-string size))))
1371 ;;; Moves to the end of the next segment or the current one if there are
1372 ;;; no more segments. Returns true as long as there are next segments.
1373 (defun string-output-stream-next-buffer (stream)
1374 (/noshow0 "/string-output-stream-next-buffer")
1375 (let* ((old (string-output-stream-buffer stream))
1376 (new (pop (string-output-stream-next stream)))
1377 (old-size (length old))
1378 (skipped (- old-size (string-output-stream-pointer stream))))
1379 (cond (new
1380 (let ((new-size (length new)))
1381 (push old (string-output-stream-prev stream))
1382 (setf (string-output-stream-buffer stream) new
1383 (string-output-stream-pointer stream) new-size)
1384 (incf (string-output-stream-index stream) (+ skipped new-size)))
1387 (setf (string-output-stream-pointer stream) old-size)
1388 (incf (string-output-stream-index stream) skipped)
1389 nil))))
1391 ;;; Moves to the start of the previous segment or the current one if there
1392 ;;; are no more segments. Returns true as long as there are prev segments.
1393 (defun string-output-stream-prev-buffer (stream)
1394 (/noshow0 "/string-output-stream-prev-buffer")
1395 (let ((old (string-output-stream-buffer stream))
1396 (new (pop (string-output-stream-prev stream)))
1397 (skipped (string-output-stream-pointer stream)))
1398 (cond (new
1399 (push old (string-output-stream-next stream))
1400 (setf (string-output-stream-buffer stream) new
1401 (string-output-stream-pointer stream) 0)
1402 (decf (string-output-stream-index stream) (+ skipped (length new)))
1405 (setf (string-output-stream-pointer stream) 0)
1406 (decf (string-output-stream-index stream) skipped)
1407 nil))))
1409 (defun string-ouch (stream character)
1410 (/noshow0 "/string-ouch")
1411 (let ((pointer (string-output-stream-pointer stream))
1412 (buffer (string-output-stream-buffer stream))
1413 (index (string-output-stream-index stream)))
1414 (cond ((= pointer (length buffer))
1415 (setf buffer (string-output-stream-new-buffer stream index)
1416 (aref buffer 0) character
1417 (string-output-stream-pointer stream) 1))
1419 (setf (aref buffer pointer) character
1420 (string-output-stream-pointer stream) (1+ pointer))))
1421 (setf (string-output-stream-index stream) (1+ index))))
1423 (defun string-sout (stream string start end)
1424 (declare (type simple-string string)
1425 (type index start end))
1426 (let* ((full-length (- end start))
1427 (length full-length)
1428 (buffer (string-output-stream-buffer stream))
1429 (pointer (string-output-stream-pointer stream))
1430 (space (- (length buffer) pointer))
1431 (here (min space length))
1432 (stop (+ start here))
1433 (overflow (- length space)))
1434 (declare (index length space here stop full-length)
1435 (fixnum overflow)
1436 (type (simple-array character (*)) buffer))
1437 (tagbody
1438 :more
1439 (when (plusp here)
1440 (etypecase string
1441 ((simple-array character (*))
1442 (replace buffer string :start1 pointer :start2 start :end2 stop))
1443 (simple-base-string
1444 (replace buffer string :start1 pointer :start2 start :end2 stop))
1445 ((simple-array nil (*))
1446 (replace buffer string :start1 pointer :start2 start :end2 stop)))
1447 (setf (string-output-stream-pointer stream) (+ here pointer)))
1448 (when (plusp overflow)
1449 (setf start stop
1450 length (- end start)
1451 buffer (string-output-stream-new-buffer
1452 stream (max overflow (string-output-stream-index stream)))
1453 pointer 0
1454 space (length buffer)
1455 here (min space length)
1456 stop (+ start here)
1457 ;; there may be more overflow if we used a buffer
1458 ;; already allocated to the stream
1459 overflow (- length space))
1460 (go :more)))
1461 (incf (string-output-stream-index stream) full-length)))
1463 ;;; Factored out of the -misc method due to size.
1464 (defun set-string-output-stream-file-position (stream pos)
1465 (let* ((index (string-output-stream-index stream))
1466 (end (max index (string-output-stream-index-cache stream))))
1467 (declare (index index end))
1468 (setf (string-output-stream-index-cache stream) end)
1469 (cond ((eq :start pos)
1470 (loop while (string-output-stream-prev-buffer stream)))
1471 ((eq :end pos)
1472 (loop while (string-output-stream-next-buffer stream))
1473 (let ((over (- (string-output-stream-index stream) end)))
1474 (decf (string-output-stream-pointer stream) over))
1475 (setf (string-output-stream-index stream) end))
1476 ((< pos index)
1477 (loop while (< pos index)
1478 do (string-output-stream-prev-buffer stream)
1479 (setf index (string-output-stream-index stream)))
1480 (let ((step (- pos index)))
1481 (incf (string-output-stream-pointer stream) step)
1482 (setf (string-output-stream-index stream) pos)))
1483 ((> pos index)
1484 ;; We allow moving beyond the end of stream, implicitly
1485 ;; extending the output stream.
1486 (let ((next (string-output-stream-next-buffer stream)))
1487 ;; Update after -next-buffer, INDEX is kept pointing at
1488 ;; the end of the current buffer.
1489 (setf index (string-output-stream-index stream))
1490 (loop while (and next (> pos index))
1491 do (setf next (string-output-stream-next-buffer stream)
1492 index (string-output-stream-index stream))))
1493 ;; Allocate new buffer if needed, or step back to
1494 ;; the desired index and set pointer and index
1495 ;; correctly.
1496 (let ((diff (- pos index)))
1497 (if (plusp diff)
1498 (let* ((new (string-output-stream-new-buffer stream diff))
1499 (size (length new)))
1500 (aver (= pos (+ index size)))
1501 (setf (string-output-stream-pointer stream) size
1502 (string-output-stream-index stream) pos))
1503 (let ((size (length (string-output-stream-buffer stream))))
1504 (setf (string-output-stream-pointer stream) (+ size diff)
1505 (string-output-stream-index stream) pos))))))))
1507 (defun string-out-misc (stream operation &optional arg1 arg2)
1508 (declare (ignore arg2))
1509 (declare (optimize speed))
1510 (case operation
1511 (:charpos
1512 ;; Keeping this first is a silly micro-optimization: FRESH-LINE
1513 ;; makes this the most common one.
1514 (/noshow0 "/string-out-misc charpos")
1515 (prog ((pointer (string-output-stream-pointer stream))
1516 (buffer (string-output-stream-buffer stream))
1517 (prev (string-output-stream-prev stream))
1518 (base 0))
1519 (declare (type (or null (simple-array character (*))) buffer))
1520 :next
1521 (let ((pos (when buffer
1522 (position #\newline buffer :from-end t :end pointer))))
1523 (when (or pos (not buffer))
1524 ;; If newline is at index I, and pointer at index I+N, charpos
1525 ;; is N-1. If there is no newline, and pointer is at index N,
1526 ;; charpos is N.
1527 (return (+ base (if pos (- pointer pos 1) pointer))))
1528 (setf base (+ base pointer)
1529 buffer (pop prev)
1530 pointer (length buffer))
1531 (/noshow0 "/string-out-misc charpos next")
1532 (go :next))))
1533 (:file-position
1534 (/noshow0 "/string-out-misc file-position")
1535 (when arg1
1536 (set-string-output-stream-file-position stream arg1))
1537 (string-output-stream-index stream))
1538 (:close
1539 (/noshow0 "/string-out-misc close")
1540 (set-closed-flame stream))
1541 (:element-type (string-output-stream-element-type stream))))
1543 ;;; Return a string of all the characters sent to a stream made by
1544 ;;; MAKE-STRING-OUTPUT-STREAM since the last call to this function.
1545 (defun get-output-stream-string (stream)
1546 (declare (type string-output-stream stream))
1547 (let* ((length (max (string-output-stream-index stream)
1548 (string-output-stream-index-cache stream)))
1549 (element-type (string-output-stream-element-type stream))
1550 (prev (nreverse (string-output-stream-prev stream)))
1551 (this (string-output-stream-buffer stream))
1552 (next (string-output-stream-next stream))
1553 (result
1554 (case element-type
1555 ;; overwhelmingly common case: can be inlined
1557 ;; FIXME: If we were willing to use %SHRINK-VECTOR here,
1558 ;; and allocate new strings the size of 2 * index in
1559 ;; STRING-SOUT, we would not need to allocate one here in
1560 ;; the common case, but could just use the last one
1561 ;; allocated, and chop it down to size..
1563 ((character) (make-string length))
1564 ;; slightly less common cases: inline it anyway
1565 ((base-char standard-char)
1566 (make-string length :element-type 'base-char))
1568 (make-string length :element-type element-type)))))
1570 (setf (string-output-stream-index stream) 0
1571 (string-output-stream-index-cache stream) 0
1572 (string-output-stream-pointer stream) 0
1573 ;; throw them away for simplicity's sake: this way the rest of the
1574 ;; implementation can assume that the greater of INDEX and INDEX-CACHE
1575 ;; is always within the last buffer.
1576 (string-output-stream-prev stream) nil
1577 (string-output-stream-next stream) nil)
1579 (flet ((replace-all (fun)
1580 (let ((start 0))
1581 (declare (index start))
1582 (dolist (buffer prev)
1583 (funcall fun buffer start)
1584 (incf start (length buffer)))
1585 (funcall fun this start)
1586 (incf start (length this))
1587 (dolist (buffer next)
1588 (funcall fun buffer start)
1589 (incf start (length buffer)))
1590 ;; Hack: erase the pointers to strings, to make it less
1591 ;; likely that the conservative GC will accidentally
1592 ;; retain the buffers.
1593 (fill prev nil)
1594 (fill next nil))))
1595 (macrolet ((frob (type)
1596 `(replace-all (lambda (buffer from)
1597 (declare (type ,type result)
1598 (type (simple-array character (*))
1599 buffer))
1600 (replace result buffer :start1 from)))))
1601 (etypecase result
1602 ((simple-array character (*))
1603 (frob (simple-array character (*))))
1604 (simple-base-string
1605 (frob simple-base-string))
1606 ((simple-array nil (*))
1607 (frob (simple-array nil (*)))))))
1609 result))
1611 ;;;; fill-pointer streams
1613 ;;; Fill pointer STRING-OUTPUT-STREAMs are not explicitly mentioned in
1614 ;;; the CLM, but they are required for the implementation of
1615 ;;; WITH-OUTPUT-TO-STRING.
1617 ;;; FIXME: need to support (VECTOR NIL), ideally without destroying all hope
1618 ;;; of efficiency.
1619 (declaim (inline vector-with-fill-pointer-p))
1620 (defun vector-with-fill-pointer-p (x)
1621 (and (vectorp x)
1622 (array-has-fill-pointer-p x)))
1624 (deftype string-with-fill-pointer ()
1625 `(and (or (vector character) (vector base-char))
1626 (satisfies vector-with-fill-pointer-p)))
1628 (defstruct (fill-pointer-output-stream
1629 (:include ansi-stream
1630 (out #'fill-pointer-ouch)
1631 (sout #'fill-pointer-sout)
1632 (misc #'fill-pointer-misc))
1633 (:constructor make-fill-pointer-output-stream (string))
1634 (:copier nil)
1635 (:predicate nil))
1636 ;; a string with a fill pointer where we stuff the stuff we write
1637 (string (missing-arg) :type string-with-fill-pointer :read-only t))
1639 (declaim (freeze-type fill-pointer-output-stream))
1641 (defun fill-pointer-ouch (stream character)
1642 (let* ((buffer (fill-pointer-output-stream-string stream))
1643 (current (fill-pointer buffer))
1644 (current+1 (1+ current)))
1645 (declare (fixnum current))
1646 (with-array-data ((workspace buffer) (start) (end))
1647 (string-dispatch
1648 ((simple-array character (*))
1649 (simple-array base-char (*)))
1650 workspace
1651 (let ((offset-current (+ start current)))
1652 (declare (fixnum offset-current))
1653 (if (= offset-current end)
1654 (let* ((new-length (1+ (* current 2)))
1655 (new-workspace
1656 (ecase (array-element-type workspace)
1657 (character (make-string new-length
1658 :element-type 'character))
1659 (base-char (make-string new-length
1660 :element-type 'base-char)))))
1661 (replace new-workspace workspace :start2 start :end2 offset-current)
1662 (setf workspace new-workspace
1663 offset-current current)
1664 (set-array-header buffer workspace new-length
1665 current+1 0 new-length nil nil))
1666 (setf (fill-pointer buffer) current+1))
1667 (setf (char workspace offset-current) character))))
1668 current+1))
1670 (defun fill-pointer-sout (stream string start end)
1671 (declare (fixnum start end))
1672 (string-dispatch
1673 ((simple-array character (*))
1674 (simple-array base-char (*)))
1675 string
1676 (let* ((buffer (fill-pointer-output-stream-string stream))
1677 (current (fill-pointer buffer))
1678 (string-len (- end start))
1679 (dst-end (+ string-len current)))
1680 (declare (fixnum current dst-end string-len))
1681 (with-array-data ((workspace buffer) (dst-start) (dst-length))
1682 (let ((offset-dst-end (+ dst-start dst-end))
1683 (offset-current (+ dst-start current)))
1684 (declare (fixnum offset-dst-end offset-current))
1685 (if (> offset-dst-end dst-length)
1686 (let* ((new-length (+ (the fixnum (* current 2)) string-len))
1687 (new-workspace
1688 (ecase (array-element-type workspace)
1689 (character (make-string new-length
1690 :element-type 'character))
1691 (base-char (make-string new-length
1692 :element-type 'base-char)))))
1693 (replace new-workspace workspace
1694 :start2 dst-start :end2 offset-current)
1695 (setf workspace new-workspace
1696 offset-current current
1697 offset-dst-end dst-end)
1698 (set-array-header buffer workspace new-length
1699 dst-end 0 new-length nil nil))
1700 (setf (fill-pointer buffer) dst-end))
1701 (replace workspace string
1702 :start1 offset-current :start2 start :end2 end)))
1703 dst-end)))
1705 (defun fill-pointer-misc (stream operation &optional arg1 arg2)
1706 (declare (ignore arg2))
1707 (case operation
1708 (:file-position
1709 (let ((buffer (fill-pointer-output-stream-string stream)))
1710 (if arg1
1711 (setf (fill-pointer buffer)
1712 (case arg1
1713 (:start 0)
1714 ;; Fill-pointer is always at fill-pointer we will
1715 ;; make :END move to the end of the actual string.
1716 (:end (array-total-size buffer))
1717 ;; We allow moving beyond the end of string if the
1718 ;; string is adjustable.
1719 (t (when (>= arg1 (array-total-size buffer))
1720 (if (adjustable-array-p buffer)
1721 (adjust-array buffer arg1)
1722 (error "Cannot move FILE-POSITION beyond the end ~
1723 of WITH-OUTPUT-TO-STRING stream ~
1724 constructed with non-adjustable string.")))
1725 arg1)))
1726 (fill-pointer buffer))))
1727 (:charpos
1728 (let* ((buffer (fill-pointer-output-stream-string stream))
1729 (current (fill-pointer buffer)))
1730 (with-array-data ((string buffer) (start) (end current))
1731 (declare (simple-string string) (ignore start))
1732 (let ((found (position #\newline string :test #'char=
1733 :end end :from-end t)))
1734 (if found
1735 (- end (the fixnum found))
1736 current)))))
1737 (:element-type
1738 (array-element-type
1739 (fill-pointer-output-stream-string stream)))))
1741 ;;;; case frobbing streams, used by FORMAT ~(...~)
1743 (defstruct (case-frob-stream
1744 (:include ansi-stream
1745 (misc #'case-frob-misc))
1746 (:constructor %make-case-frob-stream (target out sout))
1747 (:copier nil))
1748 (target (missing-arg) :type stream :read-only t))
1750 (declaim (freeze-type case-frob-stream))
1752 (defun make-case-frob-stream (target kind)
1753 #!+sb-doc
1754 "Return a stream that sends all output to the stream TARGET, but modifies
1755 the case of letters, depending on KIND, which should be one of:
1756 :UPCASE - convert to upper case.
1757 :DOWNCASE - convert to lower case.
1758 :CAPITALIZE - convert the first letter of words to upper case and the
1759 rest of the word to lower case.
1760 :CAPITALIZE-FIRST - convert the first letter of the first word to upper
1761 case and everything else to lower case."
1762 (declare (type stream target)
1763 (type (member :upcase :downcase :capitalize :capitalize-first)
1764 kind)
1765 (values stream))
1766 (if (case-frob-stream-p target)
1767 ;; If we are going to be writing to a stream that already does
1768 ;; case frobbing, why bother frobbing the case just so it can
1769 ;; frob it again?
1770 target
1771 (multiple-value-bind (out sout)
1772 (ecase kind
1773 (:upcase
1774 (values #'case-frob-upcase-out
1775 #'case-frob-upcase-sout))
1776 (:downcase
1777 (values #'case-frob-downcase-out
1778 #'case-frob-downcase-sout))
1779 (:capitalize
1780 (values #'case-frob-capitalize-out
1781 #'case-frob-capitalize-sout))
1782 (:capitalize-first
1783 (values #'case-frob-capitalize-first-out
1784 #'case-frob-capitalize-first-sout)))
1785 (%make-case-frob-stream target out sout))))
1787 (defun case-frob-misc (stream op &optional arg1 arg2)
1788 (declare (type case-frob-stream stream))
1789 (case op
1790 (:close
1791 (set-closed-flame stream))
1793 (let ((target (case-frob-stream-target stream)))
1794 (if (ansi-stream-p target)
1795 (funcall (ansi-stream-misc target) target op arg1 arg2)
1796 (stream-misc-dispatch target op arg1 arg2))))))
1798 (defun case-frob-upcase-out (stream char)
1799 (declare (type case-frob-stream stream)
1800 (type character char))
1801 (let ((target (case-frob-stream-target stream))
1802 (char (char-upcase char)))
1803 (if (ansi-stream-p target)
1804 (funcall (ansi-stream-out target) target char)
1805 (stream-write-char target char))))
1807 (defun case-frob-upcase-sout (stream str start end)
1808 (declare (type case-frob-stream stream)
1809 (type simple-string str)
1810 (type index start)
1811 (type (or index null) end))
1812 (let* ((target (case-frob-stream-target stream))
1813 (len (length str))
1814 (end (or end len))
1815 (string (if (and (zerop start) (= len end))
1816 (string-upcase str)
1817 (nstring-upcase (subseq str start end))))
1818 (string-len (- end start)))
1819 (if (ansi-stream-p target)
1820 (funcall (ansi-stream-sout target) target string 0 string-len)
1821 (stream-write-string target string 0 string-len))))
1823 (defun case-frob-downcase-out (stream char)
1824 (declare (type case-frob-stream stream)
1825 (type character char))
1826 (let ((target (case-frob-stream-target stream))
1827 (char (char-downcase char)))
1828 (if (ansi-stream-p target)
1829 (funcall (ansi-stream-out target) target char)
1830 (stream-write-char target char))))
1832 (defun case-frob-downcase-sout (stream str start end)
1833 (declare (type case-frob-stream stream)
1834 (type simple-string str)
1835 (type index start)
1836 (type (or index null) end))
1837 (let* ((target (case-frob-stream-target stream))
1838 (len (length str))
1839 (end (or end len))
1840 (string (if (and (zerop start) (= len end))
1841 (string-downcase str)
1842 (nstring-downcase (subseq str start end))))
1843 (string-len (- end start)))
1844 (if (ansi-stream-p target)
1845 (funcall (ansi-stream-sout target) target string 0 string-len)
1846 (stream-write-string target string 0 string-len))))
1848 (defun case-frob-capitalize-out (stream char)
1849 (declare (type case-frob-stream stream)
1850 (type character char))
1851 (let ((target (case-frob-stream-target stream)))
1852 (cond ((alphanumericp char)
1853 (let ((char (char-upcase char)))
1854 (if (ansi-stream-p target)
1855 (funcall (ansi-stream-out target) target char)
1856 (stream-write-char target char)))
1857 (setf (case-frob-stream-out stream) #'case-frob-capitalize-aux-out)
1858 (setf (case-frob-stream-sout stream)
1859 #'case-frob-capitalize-aux-sout))
1861 (if (ansi-stream-p target)
1862 (funcall (ansi-stream-out target) target char)
1863 (stream-write-char target char))))))
1865 (defun case-frob-capitalize-sout (stream str start end)
1866 (declare (type case-frob-stream stream)
1867 (type simple-string str)
1868 (type index start)
1869 (type (or index null) end))
1870 (let* ((target (case-frob-stream-target stream))
1871 (str (subseq str start end))
1872 (len (length str))
1873 (inside-word nil))
1874 (dotimes (i len)
1875 (let ((char (schar str i)))
1876 (cond ((not (alphanumericp char))
1877 (setf inside-word nil))
1878 (inside-word
1879 (setf (schar str i) (char-downcase char)))
1881 (setf inside-word t)
1882 (setf (schar str i) (char-upcase char))))))
1883 (when inside-word
1884 (setf (case-frob-stream-out stream)
1885 #'case-frob-capitalize-aux-out)
1886 (setf (case-frob-stream-sout stream)
1887 #'case-frob-capitalize-aux-sout))
1888 (if (ansi-stream-p target)
1889 (funcall (ansi-stream-sout target) target str 0 len)
1890 (stream-write-string target str 0 len))))
1892 (defun case-frob-capitalize-aux-out (stream char)
1893 (declare (type case-frob-stream stream)
1894 (type character char))
1895 (let ((target (case-frob-stream-target stream)))
1896 (cond ((alphanumericp char)
1897 (let ((char (char-downcase char)))
1898 (if (ansi-stream-p target)
1899 (funcall (ansi-stream-out target) target char)
1900 (stream-write-char target char))))
1902 (if (ansi-stream-p target)
1903 (funcall (ansi-stream-out target) target char)
1904 (stream-write-char target char))
1905 (setf (case-frob-stream-out stream)
1906 #'case-frob-capitalize-out)
1907 (setf (case-frob-stream-sout stream)
1908 #'case-frob-capitalize-sout)))))
1910 (defun case-frob-capitalize-aux-sout (stream str start end)
1911 (declare (type case-frob-stream stream)
1912 (type simple-string str)
1913 (type index start)
1914 (type (or index null) end))
1915 (let* ((target (case-frob-stream-target stream))
1916 (str (subseq str start end))
1917 (len (length str))
1918 (inside-word t))
1919 (dotimes (i len)
1920 (let ((char (schar str i)))
1921 (cond ((not (alphanumericp char))
1922 (setf inside-word nil))
1923 (inside-word
1924 (setf (schar str i) (char-downcase char)))
1926 (setf inside-word t)
1927 (setf (schar str i) (char-upcase char))))))
1928 (unless inside-word
1929 (setf (case-frob-stream-out stream)
1930 #'case-frob-capitalize-out)
1931 (setf (case-frob-stream-sout stream)
1932 #'case-frob-capitalize-sout))
1933 (if (ansi-stream-p target)
1934 (funcall (ansi-stream-sout target) target str 0 len)
1935 (stream-write-string target str 0 len))))
1937 (defun case-frob-capitalize-first-out (stream char)
1938 (declare (type case-frob-stream stream)
1939 (type character char))
1940 (let ((target (case-frob-stream-target stream)))
1941 (cond ((alphanumericp char)
1942 (let ((char (char-upcase char)))
1943 (if (ansi-stream-p target)
1944 (funcall (ansi-stream-out target) target char)
1945 (stream-write-char target char)))
1946 (setf (case-frob-stream-out stream)
1947 #'case-frob-downcase-out)
1948 (setf (case-frob-stream-sout stream)
1949 #'case-frob-downcase-sout))
1951 (if (ansi-stream-p target)
1952 (funcall (ansi-stream-out target) target char)
1953 (stream-write-char target char))))))
1955 (defun case-frob-capitalize-first-sout (stream str start end)
1956 (declare (type case-frob-stream stream)
1957 (type simple-string str)
1958 (type index start)
1959 (type (or index null) end))
1960 (let* ((target (case-frob-stream-target stream))
1961 (str (subseq str start end))
1962 (len (length str)))
1963 (dotimes (i len)
1964 (let ((char (schar str i)))
1965 (when (alphanumericp char)
1966 (setf (schar str i) (char-upcase char))
1967 (do ((i (1+ i) (1+ i)))
1968 ((= i len))
1969 (setf (schar str i) (char-downcase (schar str i))))
1970 (setf (case-frob-stream-out stream)
1971 #'case-frob-downcase-out)
1972 (setf (case-frob-stream-sout stream)
1973 #'case-frob-downcase-sout)
1974 (return))))
1975 (if (ansi-stream-p target)
1976 (funcall (ansi-stream-sout target) target str 0 len)
1977 (stream-write-string target str 0 len))))
1979 ;;;; Shared {READ,WRITE}-SEQUENCE support functions
1981 (declaim (inline ansi-stream-element-mode
1982 ansi-stream-compute-io-function
1983 compatible-vector-and-stream-element-types-p))
1985 (defun ansi-stream-element-mode (stream)
1986 (declare (type ansi-stream stream))
1987 (if (fd-stream-p stream)
1988 (fd-stream-element-mode stream)
1989 (stream-element-type-stream-element-mode
1990 (ansi-stream-element-type stream))))
1992 (defun ansi-stream-compute-io-function (stream sequence-element-type
1993 character-io binary-io bivalent-io)
1994 (declare (type ansi-stream stream))
1995 (ecase (ansi-stream-element-mode stream)
1996 (character
1997 character-io)
1998 ((unsigned-byte signed-byte)
1999 binary-io)
2000 (:bivalent
2001 (cond
2002 ((member sequence-element-type '(nil t))
2003 bivalent-io)
2004 ;; Pick off common subtypes.
2005 ((eq sequence-element-type 'character)
2006 character-io)
2007 ((or (equal sequence-element-type '(unsigned-byte 8))
2008 (equal sequence-element-type '(signed-byte 8)))
2009 binary-io)
2010 ;; Proper subtype tests.
2011 ((subtypep sequence-element-type 'character)
2012 character-io)
2013 ((subtypep sequence-element-type 'integer)
2014 binary-io)
2016 (error "~@<Cannot select IO functions to use for bivalent ~
2017 stream ~S and a sequence with element-type ~S.~@:>"
2018 stream sequence-element-type))))))
2020 (defun compatible-vector-and-stream-element-types-p (vector stream)
2021 (declare (type vector vector)
2022 (type ansi-stream stream))
2023 (or (and (typep vector '(simple-array (unsigned-byte 8) (*)))
2024 (eq (ansi-stream-element-mode stream) 'unsigned-byte))
2025 (and (typep vector '(simple-array (signed-byte 8) (*)))
2026 (eq (ansi-stream-element-mode stream) 'signed-byte))))
2028 ;;;; READ-SEQUENCE
2030 (defun read-sequence (seq stream &key (start 0) end)
2031 #!+sb-doc
2032 "Destructively modify SEQ by reading elements from STREAM.
2033 That part of SEQ bounded by START and END is destructively modified by
2034 copying successive elements into it from STREAM. If the end of file
2035 for STREAM is reached before copying all elements of the subsequence,
2036 then the extra elements near the end of sequence are not updated, and
2037 the index of the next element is returned."
2038 (declare (type sequence seq)
2039 (type stream stream)
2040 (type index start)
2041 (type sequence-end end)
2042 (values index))
2043 (if (ansi-stream-p stream)
2044 (ansi-stream-read-sequence seq stream start end)
2045 ;; must be Gray streams FUNDAMENTAL-STREAM
2046 (stream-read-sequence stream seq start end)))
2048 (defun ansi-stream-read-sequence (seq stream start %end)
2049 (declare (type sequence seq)
2050 (type ansi-stream stream)
2051 (type index start)
2052 (type sequence-end %end)
2053 (values index))
2054 (let ((end (or %end (length seq)))
2055 (in #'ansi-stream-read-char)
2056 (bin #'ansi-stream-read-byte))
2057 (declare (type index end))
2058 (labels ((compute-read-function (sequence-element-type)
2059 (ansi-stream-compute-io-function
2060 stream sequence-element-type in bin in))
2061 (read-list (read-function)
2062 (do ((rem (nthcdr start seq) (rest rem))
2063 (i start (1+ i)))
2064 ((or (endp rem) (>= i end)) i)
2065 (declare (type list rem)
2066 (type index i))
2067 (let ((el (funcall read-function stream nil :eof nil)))
2068 (when (eq el :eof)
2069 (return i))
2070 (setf (first rem) el))))
2071 (read-vector/fast (data offset-start)
2072 (let* ((numbytes (- end start))
2073 (bytes-read (read-n-bytes
2074 stream data offset-start numbytes nil)))
2075 (if (< bytes-read numbytes)
2076 (+ start bytes-read)
2077 end)))
2078 (read-vector (read-function data offset-start offset-end)
2079 (do ((i offset-start (1+ i)))
2080 ((>= i offset-end) end)
2081 (declare (type index i))
2082 (let ((el (funcall read-function stream nil :eof nil)))
2083 (when (eq el :eof)
2084 (return (+ start (- i offset-start))))
2085 (setf (aref data i) el)))))
2086 (declare (dynamic-extent #'compute-read-function
2087 #'read-list #'read-vector/fast #'read-vector))
2088 (cond
2089 ((typep seq 'list)
2090 (read-list (compute-read-function nil)))
2091 ((and (ansi-stream-cin-buffer stream)
2092 (typep seq 'simple-string))
2093 (ansi-stream-read-string-from-frc-buffer seq stream start %end))
2094 ((typep seq 'vector)
2095 (with-array-data ((data seq) (offset-start start) (offset-end end)
2096 :check-fill-pointer t)
2097 (if (compatible-vector-and-stream-element-types-p data stream)
2098 (read-vector/fast data offset-start)
2099 (read-vector (compute-read-function (array-element-type data))
2100 data offset-start offset-end))))))))
2102 (defun ansi-stream-read-string-from-frc-buffer (seq stream start %end)
2103 (declare (type simple-string seq)
2104 (type ansi-stream stream)
2105 (type index start)
2106 (type (or null index) %end))
2107 (let ((needed (- (or %end (length seq))
2108 start))
2109 (read 0))
2110 (prepare-for-fast-read-char stream
2111 (declare (ignore %frc-method%))
2112 (unless %frc-buffer%
2113 (return-from ansi-stream-read-string-from-frc-buffer nil))
2114 (labels ((refill-buffer ()
2115 (prog1 (fast-read-char-refill stream nil)
2116 (setf %frc-index% (ansi-stream-in-index %frc-stream%))))
2117 (add-chunk ()
2118 (let* ((end (length %frc-buffer%))
2119 (len (min (- end %frc-index%)
2120 (- needed read))))
2121 (declare (type index end len read needed))
2122 (string-dispatch (simple-base-string
2123 (simple-array character (*)))
2125 (replace seq %frc-buffer%
2126 :start1 (+ start read)
2127 :end1 (+ start read len)
2128 :start2 %frc-index%
2129 :end2 (+ %frc-index% len)))
2130 (incf read len)
2131 (incf %frc-index% len)
2132 (when (or (eql needed read) (not (refill-buffer)))
2133 (done-with-fast-read-char)
2134 (return-from ansi-stream-read-string-from-frc-buffer
2135 (+ start read))))))
2136 (declare (inline refill-buffer))
2137 (when (and (= %frc-index% +ansi-stream-in-buffer-length+)
2138 (not (refill-buffer)))
2139 ;; EOF had been reached before we read anything
2140 ;; at all. But READ-SEQUENCE never signals an EOF error.
2141 (done-with-fast-read-char)
2142 (return-from ansi-stream-read-string-from-frc-buffer start))
2143 (loop (add-chunk))))))
2146 ;;;; WRITE-SEQUENCE
2148 (defun write-sequence (seq stream &key (start 0) (end nil))
2149 #!+sb-doc
2150 "Write the elements of SEQ bounded by START and END to STREAM."
2151 (declare (type sequence seq)
2152 (type stream stream)
2153 (type index start)
2154 (type sequence-end end)
2155 (values sequence))
2156 (if (ansi-stream-p stream)
2157 (ansi-stream-write-sequence seq stream start end)
2158 ;; must be Gray-streams FUNDAMENTAL-STREAM
2159 (stream-write-sequence stream seq start end)))
2161 (defun ansi-stream-write-sequence (seq stream start %end)
2162 (declare (type sequence seq)
2163 (type ansi-stream stream)
2164 (type index start)
2165 (type sequence-end %end)
2166 (values sequence))
2167 (let ((end (or %end (length seq)))
2168 (out (ansi-stream-out stream))
2169 (bout (ansi-stream-bout stream)))
2170 (declare (type index end))
2171 (labels ((compute-write-function (sequence-element-type)
2172 (ansi-stream-compute-io-function
2173 stream sequence-element-type
2174 out bout #'write-element/bivalent))
2175 (write-element/bivalent (stream object)
2176 (if (characterp object)
2177 (funcall out stream object)
2178 (funcall bout stream object)))
2179 (write-list (write-function)
2180 (do ((rem (nthcdr start seq) (rest rem))
2181 (i start (1+ i)))
2182 ((or (endp rem) (>= i end)))
2183 (declare (type list rem)
2184 (type index i))
2185 (funcall write-function stream (first rem))))
2186 (write-vector (data start end write-function)
2187 (declare (type (simple-array * (*)) data)
2188 (type index start end))
2189 (do ((i start (1+ i)))
2190 ((>= i end))
2191 (declare (type index i))
2192 (funcall write-function stream (aref data i)))))
2193 (declare (dynamic-extent #'compute-write-function
2194 #'write-element/bivalent #'write-list
2195 #'write-vector))
2196 (etypecase seq
2197 (list
2198 (write-list (compute-write-function nil)))
2199 (string
2200 (ansi-stream-write-string seq stream start end))
2201 (vector
2202 (with-array-data ((data seq) (offset-start start) (offset-end end)
2203 :check-fill-pointer t)
2204 (if (and (fd-stream-p stream)
2205 (compatible-vector-and-stream-element-types-p data stream))
2206 (buffer-output stream data offset-start offset-end)
2207 (write-vector data offset-start offset-end
2208 (compute-write-function
2209 (array-element-type seq)))))))))
2210 seq)
2212 ;;; like FILE-POSITION, only using :FILE-LENGTH
2213 (defun file-length (stream)
2214 ;; FIXME: the FIXME following this one seems wrong on 2 counts:
2215 ;; 1. since when does cross-compiler hangup occur on undefined types?
2216 ;; 2. why is that the correct set of types to check for?
2217 ;; FIXME: The following declaration uses yet undefined types, which
2218 ;; cause cross-compiler hangup.
2220 ;; (declare (type (or file-stream synonym-stream) stream))
2222 ;; The description for FILE-LENGTH says that an error must be raised
2223 ;; for streams not associated with files (which broadcast streams
2224 ;; aren't according to the glossary). However, the behaviour of
2225 ;; FILE-LENGTH for broadcast streams is explicitly described in the
2226 ;; BROADCAST-STREAM entry.
2227 (unless (typep stream 'broadcast-stream)
2228 (stream-must-be-associated-with-file stream))
2229 (funcall (ansi-stream-misc stream) stream :file-length))
2231 ;; Placing this definition (formerly in "toplevel") after the important
2232 ;; stream types are known produces smaller+faster code than it did before.
2233 (defun stream-output-stream (stream)
2234 (typecase stream
2235 (fd-stream
2236 stream)
2237 (synonym-stream
2238 (stream-output-stream
2239 (symbol-value (synonym-stream-symbol stream))))
2240 (two-way-stream
2241 (stream-output-stream
2242 (two-way-stream-output-stream stream)))
2244 stream)))
2246 ;;;; etc.