c537300ac911d4190fc9540c43c19cf2d4f60818
[sbcl.git] / contrib / sb-simple-streams / impl.lisp
1 ;;; -*- lisp -*-
2 ;;;
3 ;;; **********************************************************************
4 ;;; This code was written by Paul Foley and has been placed in the public
5 ;;; domain.
6 ;;; 
7
8 ;;; Sbcl port by Rudi Schlatte.
9
10 (in-package "SB-SIMPLE-STREAMS")
11
12 ;;;
13 ;;; **********************************************************************
14 ;;;
15 ;;; Implementations of standard Common Lisp functions for simple-streams
16
17 (defun %uninitialized (stream)
18   (error "~S has not been initialized." stream))
19
20 (defun %check (stream kind)
21   (declare (type simple-stream stream)
22            (optimize (speed 3) (space 1) (debug 0) (safety 0)))
23   (with-stream-class (simple-stream stream)
24     (cond ((not (any-stream-instance-flags stream :simple))
25            (%uninitialized stream))
26           ((and (eq kind :open)
27                 (not (any-stream-instance-flags stream :input :output)))
28            (sb-kernel:closed-flame stream))
29           ((and (or (eq kind :input) (eq kind :io))
30                 (not (any-stream-instance-flags stream :input)))
31            (sb-kernel:ill-in stream))
32           ((and (or (eq kind :output) (eq kind :io))
33                 (not (any-stream-instance-flags stream :output)))
34            (sb-kernel:ill-out stream)))))
35
36 (defmethod input-stream-p ((stream simple-stream))
37   (any-stream-instance-flags stream :input))
38
39 (defmethod output-stream-p ((stream simple-stream))
40   (any-stream-instance-flags stream :output))
41
42 (defmethod open-stream-p ((stream simple-stream))
43   (any-stream-instance-flags stream :input :output))
44
45 ;;; From the simple-streams documentation: "A generic function implies
46 ;;; a specialization capability that does not exist for
47 ;;; simple-streams; simple-stream specializations should be on
48 ;;; device-close."  So don't do it.
49 (defmethod close ((stream simple-stream) &key abort)
50   (device-close stream abort))
51
52 (defun %file-position (stream position)
53   (declare (type simple-stream stream)
54            (type (or (integer 0 *) (member nil :start :end)) position))
55   (with-stream-class (simple-stream stream)
56     (%check stream :open)
57     (if position
58         ;; Adjust current position
59         (let ((position (case position (:start 0) (:end -1)
60                               (otherwise position))))
61           (etypecase stream
62             (single-channel-simple-stream
63              (when (sc-dirty-p stream)
64                (flush-buffer stream t)))
65             (dual-channel-simple-stream
66              (with-stream-class (dual-channel-simple-stream stream)
67                (when (> (sm outpos stream) 0)
68                  (device-write stream :flush 0 nil t))))
69             (string-simple-stream
70              nil))
71
72           (setf (sm last-char-read-size stream) 0)
73           (setf (sm buffpos stream) 0   ; set pointer to 0 to force a read
74                 (sm buffer-ptr stream) 0)
75           (setf (sm charpos stream) nil)
76           (remove-stream-instance-flags stream :eof)
77           (setf (device-file-position stream) position))
78         ;; Just report current position
79         (let ((posn (device-file-position stream)))
80           (when posn
81             (when (sm handler stream)
82               (dolist (queued (sm pending stream))
83                 (incf posn (- (the sb-int:index (third queued))
84                               (the sb-int:index (second queued))))))
85             (etypecase stream
86               (single-channel-simple-stream
87                (case (sm mode stream)
88                  ((0 3)         ; read, read-modify
89                   ;; Note that posn can increase here if we wrote
90                   ;; past the end of previously-read data
91                   (decf posn (- (sm buffer-ptr stream) (sm buffpos stream))))
92                  (1                     ; write
93                   (incf posn (sm buffpos stream)))))
94               (dual-channel-simple-stream
95                (with-stream-class (dual-channel-simple-stream stream)
96                  (incf posn (sm outpos stream))
97                  (when (>= (sm buffer-ptr stream) 0)
98                    (decf posn (- (sm buffer-ptr stream) (sm buffpos stream))))))
99               (string-simple-stream
100                nil)))
101           posn))))
102
103 (defun %file-length (stream)
104   (declare (type simple-stream stream))
105   (%check stream :open)
106   (device-file-length stream))
107
108
109 (defun %file-name (stream)
110   (declare (type simple-stream stream))
111   (%check stream nil)
112   (typecase stream
113     (file-simple-stream
114      (with-stream-class (file-simple-stream stream)
115        (sm pathname stream)))
116     (probe-simple-stream
117      (with-stream-class (probe-simple-stream stream)
118        (sm pathname stream)))
119     (otherwise
120      nil)))
121
122
123 (defun %file-rename (stream new-name)
124   (declare (type simple-stream stream))
125   (%check stream nil)
126   (if (typep stream 'file-simple-stream)
127       (with-stream-class (file-simple-stream stream)
128         (setf (sm pathname stream) new-name)
129         (setf (sm filename stream) (sb-int:unix-namestring new-name nil))
130         t)
131       nil))
132
133
134 (defun %file-string-length (stream object)
135   (declare (type simple-stream stream))
136   (with-stream-class (simple-stream stream)
137     (%check stream :output)
138     ;; FIXME: need to account for compositions on the stream...
139     (let ((count 0))
140       (flet ((fn (octet)
141                (declare (ignore octet))
142                (incf count)))
143         (etypecase object
144           (character
145            (let ((x nil))
146              (char-to-octets (sm external-format stream) object x #'fn)))
147           (string
148            (let ((x nil)
149                  (ef (sm external-format stream)))
150              (dotimes (i (length object))
151                (declare (type sb-int:index i))
152                (char-to-octets ef (char object i) x #'fn))))))
153       count)))
154
155
156 (defun %read-line (stream eof-error-p eof-value recursive-p)
157   (declare (optimize (speed 3) (space 1) (safety 0) (debug 0))
158            (type simple-stream stream)
159            (ignore recursive-p))
160   (with-stream-class (simple-stream stream)
161     (%check stream :input)
162     (when (any-stream-instance-flags stream :eof)
163       (return-from %read-line
164         (sb-impl::eof-or-lose stream eof-error-p eof-value)))
165     ;; for interactive streams, finish output first to force prompt
166     (when (and (any-stream-instance-flags stream :output)
167                (any-stream-instance-flags stream :interactive))
168       (%finish-output stream))
169     (let* ((encap (sm melded-stream stream)) ; encapsulating stream
170            (cbuf (make-string 80))      ; current buffer
171            (bufs (list cbuf))           ; list of buffers
172            (tail bufs)                  ; last cons of bufs list
173            (index 0)                    ; current index in current buffer
174            (total 0))                   ; total characters
175       (declare (type simple-stream encap)
176                (type simple-base-string cbuf)
177                (type cons bufs tail)
178                (type sb-int:index index total))
179       (loop
180         (multiple-value-bind (chars done)
181             (funcall-stm-handler j-read-chars encap cbuf
182                                  #\Newline index (length cbuf) t)
183           (declare (type sb-int:index chars))
184           (incf index chars)
185           (incf total chars)
186           (when (and (eq done :eof) (zerop total))
187             (if eof-error-p
188                 (error 'end-of-file :stream stream)
189                 (return (values eof-value t))))
190           (when done
191             ;; If there's only one buffer in use, return it directly
192             (when (null (cdr bufs))
193               (return (values (sb-kernel:shrink-vector cbuf total)
194                               (eq done :eof))))
195             ;; If total fits in final buffer, use it
196             (when (<= total (length cbuf))
197               (replace cbuf cbuf :start1 (- total index) :end2 index)
198               (let ((idx 0))
199                 (declare (type sb-int:index idx))
200                 (do ((list bufs (cdr list)))
201                     ((eq list tail))
202                   (let ((buf (car list)))
203                     (declare (type simple-base-string buf))
204                     (replace cbuf buf :start1 idx)
205                     (incf idx (length buf)))))
206               (return (values (sb-kernel:shrink-vector cbuf total)
207                               (eq done :eof))))
208             ;; Allocate new string of appropriate length
209             (let ((string (make-string total))
210                   (index 0))
211               (declare (type sb-int:index index))
212               (dolist (buf bufs)
213                 (declare (type simple-base-string buf))
214                 (replace string buf :start1 index)
215                 (incf index (length buf)))
216               (return  (values string (eq done :eof)))))
217           (when (>= index (length cbuf))
218             (setf cbuf (make-string (the sb-int:index (* 2 index))))
219             (setf index 0)
220             (setf (cdr tail) (cons cbuf nil))
221             (setf tail (cdr tail))))))))
222
223 (defun %read-char (stream eof-error-p eof-value recursive-p blocking-p)
224   (declare (type simple-stream stream)
225            (ignore recursive-p))
226   (with-stream-class (simple-stream stream)
227     (%check stream :input)
228     (when (any-stream-instance-flags stream :eof)
229       (return-from %read-char
230         (sb-impl::eof-or-lose stream eof-error-p eof-value)))
231     ;; for interactive streams, finish output first to force prompt
232     (when (and (any-stream-instance-flags stream :output)
233                (any-stream-instance-flags stream :interactive))
234       (%finish-output stream))
235     (funcall-stm-handler j-read-char (sm melded-stream stream)
236                          eof-error-p eof-value blocking-p)))
237
238
239 (defun %unread-char (stream character)
240   (declare (type simple-stream stream) (ignore character))
241   (with-stream-class (simple-stream stream)
242     (%check stream :input)
243     (if (zerop (sm last-char-read-size stream))
244         (error "Nothing to unread.")
245         (progn
246           (funcall-stm-handler j-unread-char (sm melded-stream stream) nil)
247           (remove-stream-instance-flags stream :eof)
248           (setf (sm last-char-read-size stream) 0)))))
249
250
251 (defun %peek-char (stream peek-type eof-error-p eof-value recursive-p)
252   (declare (type simple-stream stream)
253            (ignore recursive-p))
254   (with-stream-class (simple-stream stream)
255     (%check stream :input)
256     (when (any-stream-instance-flags stream :eof)
257       (return-from %peek-char
258         (sb-impl::eof-or-lose stream eof-error-p eof-value)))
259     (let* ((encap (sm melded-stream stream))
260            (char (funcall-stm-handler j-read-char encap
261                                      eof-error-p stream t)))
262       (cond ((eq char stream) eof-value)
263             ((characterp peek-type)
264              (do ((char char (funcall-stm-handler j-read-char encap
265                                                   eof-error-p
266                                                   stream t)))
267                  ((or (eq char stream) (char= char peek-type))
268                   (unless (eq char stream)
269                     (funcall-stm-handler j-unread-char encap t))
270                   (if (eq char stream) eof-value char))))
271             ((eq peek-type t)
272              (do ((char char (funcall-stm-handler j-read-char encap
273                                                   eof-error-p
274                                                   stream t)))
275                  ((or (eq char stream)
276                       (not (sb-impl::whitespacep char)))
277                   (unless (eq char stream)
278                     (funcall-stm-handler j-unread-char encap t))
279                   (if (eq char stream) eof-value char))))
280             (t
281              (funcall-stm-handler j-unread-char encap t)
282              char)))))
283
284 (defun %listen (stream width)
285   (declare (type simple-stream stream))
286   ;; WIDTH is number of octets which must be available; any value
287   ;; other than 1 is treated as 'character.
288   (with-stream-class (simple-stream stream)
289     (%check stream :input)
290     (when (any-stream-instance-flags stream :eof)
291       (return-from %listen nil))
292     (if (not (or (eql width 1) (null width)))
293         (funcall-stm-handler j-listen (sm melded-stream stream))
294         (or (< (sm buffpos stream) (sm buffer-ptr stream))
295             (when (or (not (any-stream-instance-flags stream :dual :string))
296                       (>= (sm mode stream) 0)) ;; device-connected @@ single-channel
297               (let ((lcrs (sm last-char-read-size stream)))
298                 (unwind-protect
299                      (progn
300                        (setf (sm last-char-read-size stream) (1+ lcrs))
301                        (plusp (refill-buffer stream nil)))
302                   (setf (sm last-char-read-size stream) lcrs))))))))
303
304 (defun %clear-input (stream buffer-only)
305   (declare (type simple-stream stream))
306   (with-stream-class (simple-stream stream)
307     (%check stream :input)
308     (setf (sm buffpos stream) 0
309           (sm buffer-ptr stream) 0
310           (sm last-char-read-size stream) 0
311           #|(sm unread-past-soft-eof stream) nil|#)
312     #| (setf (sm reread-count stream) 0)  on dual-channel streams? |#
313     )
314   (device-clear-input stream buffer-only))
315
316
317 (defun %read-byte (stream eof-error-p eof-value)
318   (declare (type simple-stream stream))
319   (with-stream-class (simple-stream stream)
320     (%check stream :input)
321     (if (any-stream-instance-flags stream :eof)
322         (sb-impl::eof-or-lose stream eof-error-p eof-value)
323         (etypecase stream
324           (single-channel-simple-stream
325            (read-byte-internal stream eof-error-p eof-value t))
326           (dual-channel-simple-stream
327            (read-byte-internal stream eof-error-p eof-value t))
328           (string-simple-stream
329            (with-stream-class (string-simple-stream stream)
330              (let ((encap (sm input-handle stream)))
331                (unless encap
332                  (error 'simple-type-error
333                         :datum stream
334                         :expected-type 'stream
335                         :format-control "Can't read-byte on string streams"
336                         :format-arguments '()))
337                (prog1
338                    (read-byte encap eof-error-p eof-value)
339                  (setf (sm last-char-read-size stream) 0
340                        (sm encapsulated-char-read-size stream) 0)))))))))
341
342
343 (defun %write-char (stream character)
344   (declare (type simple-stream stream))
345   (with-stream-class (simple-stream stream)
346     (%check stream :output)
347     (funcall-stm-handler-2 j-write-char character (sm melded-stream stream))))
348
349
350 (defun %fresh-line (stream)
351   (declare (type simple-stream stream))
352   (with-stream-class (simple-stream stream)
353     (%check stream :output)
354     (when (/= (or (sm charpos stream) 1) 0)
355       (funcall-stm-handler-2 j-write-char #\Newline (sm melded-stream stream))
356       t)))
357
358
359 (defun %write-string (stream string start end)
360   (declare (type simple-stream stream))
361   (with-stream-class (simple-stream stream)
362     (%check stream :output)
363     (funcall-stm-handler-2 j-write-chars string (sm melded-stream stream)
364                            start end)))
365
366
367 (defun %line-length (stream)
368   (declare (type simple-stream stream))
369   (%check stream :output)
370   ;; implement me
371   nil)
372
373
374 (defun %finish-output (stream)
375   (declare (type simple-stream stream))
376   (with-stream-class (simple-stream stream)
377     (%check stream :output)
378     (when (sm handler stream)
379       (do ()
380           ((null (sm pending stream)))
381         (sb-sys:serve-all-events)))
382     (etypecase stream
383       (single-channel-simple-stream
384        ;(when (and (> (sm mode stream) 0) (> (sm buffer-ptr stream) 0))
385        ;  (setf (device-file-position stream)
386        ;        (- (device-file-position stream) (sm buffer-ptr stream))))
387        ;(device-write stream :flush 0 nil t)
388        (flush-buffer stream t)
389        (setf (sm buffpos stream) 0))
390       (dual-channel-simple-stream
391        (with-stream-class (dual-channel-simple-stream stream)
392          (device-write stream :flush 0 nil t)
393          (setf (sm outpos stream) 0)))
394       (string-simple-stream
395            (device-write stream :flush 0 nil t))))
396   nil)
397
398
399 (defun %force-output (stream)
400   (declare (type simple-stream stream))
401   (with-stream-class (simple-stream stream)
402     (%check stream :output)
403     (etypecase stream
404       (single-channel-simple-stream
405        ;(when (> (sm buffer-ptr stream) 0)
406        ;  (setf (device-file-position stream)
407        ;        (- (device-file-position stream) (sm buffer-ptr stream))))
408        ;(device-write stream :flush 0 nil nil)
409        (flush-buffer stream nil)
410        (setf (sm buffpos stream) 0))
411       (dual-channel-simple-stream
412        (with-stream-class (dual-channel-simple-stream stream)
413          (device-write stream :flush 0 nil nil)
414          (setf (sm outpos stream) 0)))
415       (string-simple-stream
416        (device-write stream :flush 0 nil nil))))
417   nil)
418
419
420 (defun %clear-output (stream)
421   (declare (type simple-stream stream))
422   (with-stream-class (simple-stream stream)
423     (%check stream :output)
424     (when (sm handler stream)
425       (sb-sys:remove-fd-handler (sm handler stream))
426       (setf (sm handler stream) nil
427             (sm pending stream) nil))
428     (etypecase stream
429       (single-channel-simple-stream
430        (with-stream-class (single-channel-simple-stream stream)
431          (case (sm mode stream)
432            (1 (setf (sm buffpos stream) 0))
433            (3 (setf (sm mode stream) 0)))))
434       (dual-channel-simple-stream
435        (setf (sm outpos stream) 0))
436       (string-simple-stream
437        nil))
438     (device-clear-output stream)))
439
440
441 (defun %write-byte (stream integer)
442   (declare (type simple-stream stream))
443   (with-stream-class (simple-stream stream)
444     (%check stream :output)
445     (etypecase stream
446       (single-channel-simple-stream
447        (with-stream-class (single-channel-simple-stream stream)
448          (let ((ptr (sm buffpos stream)))
449           (when (>= ptr (sm buf-len stream))
450             (setf ptr (flush-buffer stream t)))
451           (setf (sm buffpos stream) (1+ ptr))
452           (setf (sm charpos stream) nil)
453           (setf (bref (sm buffer stream) ptr) integer)
454           (sc-set-dirty stream))))
455       (dual-channel-simple-stream
456        (with-stream-class (dual-channel-simple-stream stream)
457          (let ((ptr (sm outpos stream)))
458            (when (>= ptr (sm max-out-pos stream))
459              (setf ptr (flush-out-buffer stream t)))
460            (setf (sm outpos stream) (1+ ptr))
461            (setf (sm charpos stream) nil)
462            (setf (bref (sm out-buffer stream) ptr) integer))))
463       (string-simple-stream
464        (with-stream-class (string-simple-stream stream)
465          (let ((encap (sm output-handle stream)))
466            (unless encap
467              (error 'simple-type-error
468                     :datum stream
469                     :expected-type 'stream
470                     :format-control "Can't write-byte on string streams."
471                     :format-arguments '()))
472            (write-byte integer encap)))))))
473
474
475 (defun %read-sequence (stream seq start end partial-fill)
476   (declare (type simple-stream stream)
477            (type sequence seq)
478            (type sb-int:index start end)
479            (type boolean partial-fill))
480   (with-stream-class (simple-stream stream)
481     (%check stream :input)
482     (when (any-stream-instance-flags stream :eof)
483       (return-from %read-sequence 0))
484     (when (and (not (any-stream-instance-flags stream :dual :string))
485                (sc-dirty-p stream))
486       (flush-buffer stream t))
487     (etypecase seq
488       (string
489        (funcall-stm-handler j-read-chars (sm melded-stream stream) seq nil
490                             start end
491                             (if partial-fill :bnb t)))
492       ((or (simple-array (unsigned-byte 8) (*))
493            (simple-array (signed-byte 8) (*)))
494        (when (any-stream-instance-flags stream :string)
495          (error "Can't read into byte sequence from a string stream."))       
496        ;; "read-vector" equivalent, but blocking if partial-fill is NIL
497        ;; FIXME: this could be implemented faster via buffer-copy
498        (loop with encap = (sm melded-stream stream)
499             for index from start below end
500             for byte = (read-byte-internal encap nil nil t)
501               then (read-byte-internal encap nil nil partial-fill)
502             while byte
503             do (setf (bref seq index) byte)
504             finally (return index)))
505       ;; extend to work on other sequences: repeated read-byte
506       )))
507
508 (defun %write-sequence (stream seq start end)
509   (declare (type simple-stream stream)
510            (type sequence seq)
511            (type sb-int:index start end))
512   (with-stream-class (simple-stream stream)
513     (%check stream :output)
514     (etypecase seq
515       (string
516        (funcall-stm-handler-2 j-write-chars seq (sm melded-stream stream)
517                               start end))
518       ((or (simple-array (unsigned-byte 8) (*))
519            (simple-array (signed-byte 8) (*)))
520        ;; "write-vector" equivalent
521        (setf (sm charpos stream) nil)
522        (etypecase stream
523          (single-channel-simple-stream
524           (with-stream-class (single-channel-simple-stream stream)
525             (loop with max-ptr fixnum = (sm buf-len stream)
526                   for src-pos fixnum = start then (+ src-pos count)
527                   for src-rest fixnum = (- end src-pos)
528                   while (> src-rest 0) ; FIXME: this is non-ANSI
529                   for ptr fixnum = (let ((ptr (sm buffpos stream)))
530                                      (if (>= ptr max-ptr)
531                                          (flush-buffer stream t)
532                                          ptr))
533                   for buf-rest fixnum = (- max-ptr ptr)
534                   for count fixnum = (min buf-rest src-rest)
535                   do (progn (setf (sm mode stream) 1)
536                             (setf (sm buffpos stream) (+ ptr count))
537                             (buffer-copy seq src-pos (sm buffer stream) ptr count)))))
538          (dual-channel-simple-stream
539           (with-stream-class (dual-channel-simple-stream stream)
540             (loop with max-ptr fixnum = (sm max-out-pos stream)
541                   for src-pos fixnum = start then (+ src-pos count)
542                   for src-rest fixnum = (- end src-pos)
543                   while (> src-rest 0) ; FIXME: this is non-ANSI
544                   for ptr fixnum = (let ((ptr (sm outpos stream)))
545                                      (if (>= ptr max-ptr)
546                                          (flush-out-buffer stream t)
547                                          ptr))
548                   for buf-rest fixnum = (- max-ptr ptr)
549                   for count fixnum = (min buf-rest src-rest)
550                   do (progn (setf (sm outpos stream) (+ ptr count))
551                             (buffer-copy seq src-pos (sm out-buffer stream) ptr count)))))
552          (string-simple-stream
553           (error 'simple-type-error
554                  :datum stream
555                  :expected-type 'stream
556                  :format-control "Can't write a byte sequence to a string stream."
557                  :format-arguments '())))
558        )
559       ;; extend to work on other sequences: repeated write-byte
560       ))
561   seq)
562
563
564 (defun read-vector (vector stream &key (start 0) end (endian-swap :byte-8))
565   (declare (type (sb-kernel:simple-unboxed-array (*)) vector)
566            (type stream stream))
567   ;; START and END are octet offsets, not vector indices!  [Except for strings]
568   ;; Return value is index of next octet to be read into (i.e., start+count)
569   (etypecase stream
570     (simple-stream
571      (with-stream-class (simple-stream stream)
572        (cond ((stringp vector)
573               (let* ((start (or start 0))
574                      (end (or end (length vector)))
575                      (encap (sm melded-stream stream))
576                      (char (funcall-stm-handler j-read-char encap nil nil t)))
577                 (when char
578                   (setf (schar vector start) char)
579                   (incf start)
580                   (+ start (funcall-stm-handler j-read-chars encap vector nil
581                                                 start end nil)))))
582              ((any-stream-instance-flags stream :string)
583               (error "Can't READ-BYTE on string streams."))
584              (t
585               (do* ((encap (sm melded-stream stream))
586                     (index (or start 0) (1+ index))
587                     (end (or end (* (length vector) (vector-elt-width vector))))
588                     (endian-swap (endian-swap-value vector endian-swap))
589                     (byte (read-byte-internal encap nil nil t)
590                           (read-byte-internal encap nil nil nil)))
591                    ((or (null byte) (>= index end)) index)
592                 (setf (bref vector (logxor index endian-swap)) byte))))))
593     ((or ansi-stream fundamental-stream)
594      (unless (typep vector '(or string
595                              (simple-array (signed-byte 8) (*))
596                              (simple-array (unsigned-byte 8) (*))))
597        (error "Wrong vector type for read-vector on stream not of type simple-stream."))
598      (read-sequence vector stream :start (or start 0) :end end))))
599
600 ;;; Basic functionality for ansi-streams.  These are separate
601 ;;; functions because they are called in places where we already know
602 ;;; we operate on an ansi-stream (as opposed to a simple- or
603 ;;; gray-stream, or the symbols t or nil), so we can evade typecase
604 ;;; and (in|out)-synonym-of calls.
605
606 (declaim (inline %ansi-stream-read-byte %ansi-stream-read-char
607                  %ansi-stream-unread-char %ansi-stream-read-line
608                  %ansi-stream-read-sequence))
609
610 (defun %ansi-stream-read-byte (stream eof-error-p eof-value blocking)
611   (declare (ignore blocking))
612   #+nil
613   (sb-kernel:ansi-stream-read-byte stream eof-error-p eof-value)
614   (sb-int:prepare-for-fast-read-byte stream
615     (prog1
616         (sb-int:fast-read-byte eof-error-p eof-value t)
617       (sb-int:done-with-fast-read-byte))))
618
619 (defun %ansi-stream-read-char (stream eof-error-p eof-value blocking)
620   (declare (ignore blocking))
621   #+nil
622   (sb-kernel:ansi-stream-read-char stream eof-error-p eof-value)
623   (sb-int:prepare-for-fast-read-char stream
624     (prog1
625         (sb-int:fast-read-char eof-error-p eof-value)
626       (sb-int:done-with-fast-read-char))))
627
628 (defun %ansi-stream-unread-char (character stream)
629   (let ((index (1- (sb-kernel:ansi-stream-in-index stream)))
630         (buffer (sb-kernel:ansi-stream-in-buffer stream)))
631     (declare (fixnum index))
632     (when (minusp index) (error "nothing to unread"))
633     (cond (buffer
634            (setf (aref buffer index) (char-code character))
635            (setf (sb-kernel:ansi-stream-in-index stream) index))
636           (t
637            (funcall (sb-kernel:ansi-stream-misc stream) stream
638                     :unread character)))))
639
640 (defun %ansi-stream-read-line (stream eof-error-p eof-value)
641   (sb-int:prepare-for-fast-read-char stream
642     (let ((res (make-string 80))
643           (len 80)
644           (index 0))
645       (loop
646        (let ((ch (sb-int:fast-read-char nil nil)))
647          (cond (ch
648                 (when (char= ch #\newline)
649                   (sb-int:done-with-fast-read-char)
650                   (return (values (sb-kernel:shrink-vector res index) nil)))
651                 (when (= index len)
652                   (setq len (* len 2))
653                   (let ((new (make-string len)))
654                     (replace new res)
655                     (setq res new)))
656                 (setf (schar res index) ch)
657                 (incf index))
658                ((zerop index)
659                 (sb-int:done-with-fast-read-char)
660                 (return (values (sb-impl::eof-or-lose stream eof-error-p
661                                                       eof-value)
662                                 t)))
663                ;; Since FAST-READ-CHAR already hit the eof char, we
664                ;; shouldn't do another READ-CHAR.
665                (t
666                 (sb-int:done-with-fast-read-char)
667                 (return (values (sb-kernel:shrink-vector res index) t)))))))))
668
669 (defun %ansi-stream-read-sequence (seq stream start %end)
670   (declare (type sequence seq)
671            (type sb-kernel:ansi-stream stream)
672            (type sb-int:index start)
673            (type sb-kernel:sequence-end %end)
674            (values sb-int:index))
675   (let ((end (or %end (length seq))))
676     (declare (type sb-int:index end))
677     (etypecase seq
678       (list
679        (let ((read-function
680               (if (subtypep (stream-element-type stream) 'character)
681                   #'%ansi-stream-read-char
682                   #'%ansi-stream-read-byte)))
683          (do ((rem (nthcdr start seq) (rest rem))
684               (i start (1+ i)))
685              ((or (endp rem) (>= i end)) i)
686            (declare (type list rem)
687                     (type sb-int:index i))
688            (let ((el (funcall read-function stream nil :eof nil)))
689              (when (eq el :eof)
690                (return i))
691              (setf (first rem) el)))))
692       (vector
693        (sb-kernel:with-array-data ((data seq) (offset-start start)
694                                    (offset-end end))
695          (typecase data
696            ((or (simple-array (unsigned-byte 8) (*))
697                 (simple-array (signed-byte 8) (*))
698                 simple-string)
699             (let* ((numbytes (- end start))
700                    (bytes-read (sb-sys:read-n-bytes stream
701                                                     data
702                                                     offset-start
703                                                     numbytes
704                                                     nil)))
705               (if (< bytes-read numbytes)
706                   (+ start bytes-read)
707                   end)))
708            (t
709             (let ((read-function
710                    (if (subtypep (stream-element-type stream) 'character)
711                        #'%ansi-stream-read-char
712                        #'%ansi-stream-read-byte)))
713               (do ((i offset-start (1+ i)))
714                   ((>= i offset-end) end)
715                 (declare (type sb-int:index i))
716                 (let ((el (funcall read-function stream nil :eof nil)))
717                   (when (eq el :eof)
718                     (return (+ start (- i offset-start))))
719                   (setf (aref data i) el)))))))))))
720
721
722 (defun %ansi-stream-write-string (string stream start end)
723   (declare (type string string)
724            (type sb-kernel:ansi-stream stream)
725            (type sb-int:index start end))
726
727   ;; Note that even though you might expect, based on the behavior of
728   ;; things like AREF, that the correct upper bound here is
729   ;; (ARRAY-DIMENSION STRING 0), the ANSI glossary definitions for
730   ;; "bounding index" and "length" indicate that in this case (i.e.
731   ;; for the ANSI-specified functions WRITE-STRING and WRITE-LINE
732   ;; which are implemented in terms of this function), (LENGTH STRING)
733   ;; is the required upper bound. A foolish consistency is the
734   ;; hobgoblin of lesser languages..
735   (unless (<= 0 start end (length string))
736     (error "~@<bad bounding indices START=~W END=~W for ~2I~_~S~:>"
737            start
738            end
739            string))
740
741   (if (sb-kernel:array-header-p string)
742       (sb-kernel:with-array-data ((data string) (offset-start start)
743                                   (offset-end end))
744         (funcall (sb-kernel:ansi-stream-sout stream)
745                  stream data offset-start offset-end))
746       (funcall (sb-kernel:ansi-stream-sout stream) stream string start end))
747   string)
748
749 (defun %ansi-stream-write-sequence (seq stream start %end)
750   (declare (type sequence seq)
751            (type sb-kernel:ansi-stream stream)
752            (type sb-int:index start)
753            (type sb-kernel:sequence-end %end)
754            (values sequence))
755   (let ((end (or %end (length seq))))
756     (declare (type sb-int:index end))
757     (etypecase seq
758       (list
759        (let ((write-function
760               (if (subtypep (stream-element-type stream) 'character)
761                   ;; TODO: Replace these with ansi-stream specific
762                   ;; functions too.
763                   #'write-char
764                   #'write-byte)))
765          (do ((rem (nthcdr start seq) (rest rem))
766               (i start (1+ i)))
767              ((or (endp rem) (>= i end)) seq)
768            (declare (type list rem)
769                     (type sb-int:index i))
770            (funcall write-function (first rem) stream))))
771       (string
772        (%ansi-stream-write-string seq stream start end))
773       (vector
774        (let ((write-function
775               (if (subtypep (stream-element-type stream) 'character)
776                   ;; TODO: Replace these with ansi-stream specific
777                   ;; functions too.
778                   #'write-char
779                   #'write-byte)))
780          (do ((i start (1+ i)))
781              ((>= i end) seq)
782            (declare (type sb-int:index i))
783            (funcall write-function (aref seq i) stream)))))))
784
785
786 ;;;
787 ;;; USER-LEVEL FUNCTIONS
788 ;;;
789
790 (defmethod open-stream-p ((stream simple-stream))
791   (any-stream-instance-flags stream :input :output))
792
793 (defmethod input-stream-p ((stream simple-stream))
794   (any-stream-instance-flags stream :input))
795
796 (defmethod output-stream-p ((stream simple-stream))
797   (any-stream-instance-flags stream :output))
798
799 (defmethod stream-element-type ((stream simple-stream))
800   '(unsigned-byte 8))
801
802 (defun interactive-stream-p (stream)
803   "Return true if Stream does I/O on a terminal or other interactive device."
804   (etypecase stream
805     (simple-stream
806      (%check stream :open)
807      (any-stream-instance-flags stream :interactive))
808     (ansi-stream
809      (funcall (sb-kernel:ansi-stream-misc stream) stream :interactive-p))
810     (fundamental-stream
811      nil)))
812
813 (defun (setf interactive-stream-p) (flag stream)
814   (typecase stream
815     (simple-stream
816      (%check stream :open)
817      (if flag
818          (add-stream-instance-flags stream :interactive)
819          (remove-stream-instance-flags stream :interactive)))
820     (t
821      (error 'simple-type-error
822             :datum stream
823             :expected-type 'simple-stream
824             :format-control "Can't set interactive flag on ~S."
825             :format-arguments (list stream)))))
826
827 (defun file-string-length (stream object)
828   (declare (type (or string character) object) (type stream stream))
829   "Return the delta in STREAM's FILE-POSITION that would be caused by writing
830    OBJECT to STREAM. Non-trivial only in implementations that support
831    international character sets."
832   (typecase stream
833     (simple-stream (%file-string-length stream object))
834     (t
835      (etypecase object
836        (character 1)
837        (string (length object))))))
838
839 (defun stream-external-format (stream)
840   "Returns Stream's external-format."
841   (etypecase stream
842     (simple-stream
843      (with-stream-class (simple-stream)
844        (%check stream :open)
845        (sm external-format stream)))
846     (ansi-stream
847      :default)
848     (fundamental-stream
849      :default)))
850
851 (defun open (filename &rest options
852              &key (direction :input)
853              (element-type 'character element-type-given)
854              if-exists if-does-not-exist
855              (external-format :default)
856              class mapped input-handle output-handle
857              &allow-other-keys)
858   "Return a stream which reads from or writes to Filename.
859   Defined keywords:
860    :direction - one of :input, :output, :io, or :probe
861    :element-type - type of object to read or write, default BASE-CHAR
862    :if-exists - one of :error, :new-version, :rename, :rename-and-delete,
863                        :overwrite, :append, :supersede or NIL
864    :if-does-not-exist - one of :error, :create or NIL
865    :external-format - :default
866   See the manual for details.
867
868   The following are simple-streams-specific additions:
869    :class - class of stream object to be created
870    :mapped - T to open a memory-mapped file
871    :input-handle - a stream or Unix file descriptor to read from
872    :output-handle - a stream or Unix file descriptor to write to"
873   (declare (ignore element-type external-format input-handle output-handle
874                    if-exists if-does-not-exist))
875   (let ((class (or class 'sb-sys::file-stream))
876         (options (copy-list options))
877         (filespec (merge-pathnames filename)))
878     (cond ((eq class 'sb-sys::file-stream)
879            (remf options :class)
880            (remf options :mapped)
881            (remf options :input-handle)
882            (remf options :output-handle)
883            (apply #'open-fd-stream filespec options))
884           ((subtypep class 'simple-stream)
885            (when element-type-given
886              (cerror "Do it anyway."
887                      "Can't create simple-streams with an element-type."))
888            (when (and (eq class 'file-simple-stream) mapped)
889              (setq class 'mapped-file-simple-stream)
890              (setf (getf options :class) 'mapped-file-simple-stream))
891            (when (subtypep class 'file-simple-stream)
892              (when (eq direction :probe)
893                (setq class 'probe-simple-stream)))
894            (apply #'make-instance class :filename filespec options))
895           ((subtypep class 'sb-gray:fundamental-stream)
896            (remf options :class)
897            (remf options :mapped)
898            (remf options :input-handle)
899            (remf options :output-handle)
900            (make-instance class :lisp-stream
901                           (apply #'open-fd-stream filespec options))))))
902
903
904 (declaim (inline read-byte read-char read-char-no-hang unread-char))
905
906 (defun read-byte (stream &optional (eof-error-p t) eof-value)
907   "Returns the next byte of the Stream."
908   (let ((stream (sb-impl::in-synonym-of stream)))
909     (etypecase stream
910       (simple-stream
911        (%read-byte stream eof-error-p eof-value))
912       (ansi-stream
913        (%ansi-stream-read-byte stream eof-error-p eof-value t))
914       (fundamental-stream
915        (let ((char (sb-gray:stream-read-byte stream)))
916          (if (eq char :eof)
917              (sb-impl::eof-or-lose stream eof-error-p eof-value)
918              char))))))
919
920 (defun read-char (&optional (stream *standard-input*) (eof-error-p t)
921                             eof-value recursive-p)
922   "Inputs a character from Stream and returns it."
923   (let ((stream (sb-impl::in-synonym-of stream)))
924     (etypecase stream
925       (simple-stream
926        (%read-char stream eof-error-p eof-value recursive-p t))
927       (ansi-stream
928        (%ansi-stream-read-char stream eof-error-p eof-value t))
929       (fundamental-stream
930        (let ((char (sb-gray:stream-read-char stream)))
931          (if (eq char :eof)
932              (sb-impl::eof-or-lose stream eof-error-p eof-value)
933              char))))))
934
935 (defun read-char-no-hang (&optional (stream *standard-input*) (eof-error-p t)
936                                     eof-value recursive-p)
937   "Returns the next character from the Stream if one is availible, or nil."
938   (declare (ignore recursive-p))
939   (let ((stream (sb-impl::in-synonym-of stream)))
940     (etypecase stream
941       (simple-stream
942        (%check stream :input)
943        (with-stream-class (simple-stream)
944          (funcall-stm-handler j-read-char stream eof-error-p eof-value nil)))
945       (ansi-stream
946        (if (funcall (sb-kernel:ansi-stream-misc stream) stream :listen)
947            (%ansi-stream-read-char stream eof-error-p eof-value t)
948            nil))
949       (fundamental-stream
950        (let ((char (sb-gray:stream-read-char-no-hang stream)))
951          (if (eq char :eof)
952              (sb-impl::eof-or-lose stream eof-error-p eof-value)
953              char))))))
954
955 (defun unread-char (character &optional (stream *standard-input*))
956   "Puts the Character back on the front of the input Stream."
957   (let ((stream (sb-impl::in-synonym-of stream)))
958     (etypecase stream
959       (simple-stream
960        (%unread-char stream character))
961       (ansi-stream
962        (%ansi-stream-unread-char character stream))
963       (fundamental-stream
964        (sb-gray:stream-unread-char stream character))))
965   nil)
966
967 (declaim (notinline read-byte read-char read-char-no-hang unread-char))
968
969 (defun peek-char (&optional (peek-type nil) (stream *standard-input*)
970                             (eof-error-p t) eof-value recursive-p)
971   "Peeks at the next character in the input Stream.  See manual for details."
972   (let ((stream (sb-impl::in-synonym-of stream)))
973     (etypecase stream
974       (simple-stream
975        (%peek-char stream peek-type eof-error-p eof-value recursive-p))
976       ;; FIXME: Broken on ECHO-STREAM (cf internal implementation?) --
977       ;; CSR, 2004-01-19
978       (ansi-stream
979        (let ((char (%ansi-stream-read-char stream eof-error-p eof-value t)))
980           (cond ((eq char eof-value) char)
981                 ((characterp peek-type)
982                  (do ((char char (%ansi-stream-read-char stream eof-error-p
983                                                          eof-value t)))
984                      ((or (eq char eof-value) (char= char peek-type))
985                       (unless (eq char eof-value)
986                         (%ansi-stream-unread-char char stream))
987                       char)))
988                 ((eq peek-type t)
989                  (do ((char char (%ansi-stream-read-char stream eof-error-p
990                                                          eof-value t)))
991                      ((or (eq char eof-value)
992                           (not (sb-impl::whitespacep char)))
993                       (unless (eq char eof-value)
994                         (%ansi-stream-unread-char char stream))
995                       char)))
996                 (t
997                  (%ansi-stream-unread-char char stream)
998                  char))))
999       (fundamental-stream
1000        (cond ((characterp peek-type)
1001               (do ((char (sb-gray:stream-read-char stream)
1002                          (sb-gray:stream-read-char stream)))
1003                   ((or (eq char :eof) (char= char peek-type))
1004                    (cond ((eq char :eof)
1005                           (sb-impl::eof-or-lose stream eof-error-p eof-value))
1006                          (t
1007                           (sb-gray:stream-unread-char stream char)
1008                           char)))))
1009              ((eq peek-type t)
1010               (do ((char (sb-gray:stream-read-char stream)
1011                          (sb-gray:stream-read-char stream)))
1012                   ((or (eq char :eof) (not (sb-impl::whitespacep char)))
1013                    (cond ((eq char :eof)
1014                           (sb-impl::eof-or-lose stream eof-error-p eof-value))
1015                          (t
1016                           (sb-gray:stream-unread-char stream char)
1017                           char)))))
1018              (t
1019               (let ((char (sb-gray:stream-peek-char stream)))
1020                 (if (eq char :eof)
1021                     (sb-impl::eof-or-lose stream eof-error-p eof-value)
1022                     char))))))))
1023
1024 (defun listen (&optional (stream *standard-input*) (width 1))
1025   "Returns T if Width octets are available on the given Stream.  If Width
1026   is given as 'character, check for a character."
1027   ;; WIDTH is number of octets which must be available; any value
1028   ;; other than 1 is treated as 'character.
1029   (let ((stream (sb-impl::in-synonym-of stream)))
1030     (etypecase stream
1031       (simple-stream
1032        (%listen stream width))
1033       (ansi-stream
1034        (or (/= (the fixnum (sb-kernel:ansi-stream-in-index stream))
1035                sb-impl::+ansi-stream-in-buffer-length+)
1036             ;; Test for T explicitly since misc methods return :EOF sometimes.
1037             (eq (funcall (sb-kernel:ansi-stream-misc stream) stream :listen)
1038                 t)))
1039       (fundamental-stream
1040        (sb-gray:stream-listen stream)))))
1041
1042
1043 (defun read-line (&optional (stream *standard-input*) (eof-error-p t)
1044                             eof-value recursive-p)
1045   "Returns a line of text read from the Stream as a string, discarding the
1046   newline character."
1047   (let ((stream (sb-impl::in-synonym-of stream)))
1048     (etypecase stream
1049       (simple-stream
1050        (%read-line stream eof-error-p eof-value recursive-p))
1051       (ansi-stream
1052        (%ansi-stream-read-line stream eof-error-p eof-value))
1053       (fundamental-stream
1054        (multiple-value-bind (string eof) (sb-gray:stream-read-line stream)
1055          (if (and eof (zerop (length string)))
1056              (values (sb-impl::eof-or-lose stream eof-error-p eof-value) t)
1057              (values string eof)))))))
1058
1059 (defun read-sequence (seq stream &key (start 0) (end nil) partial-fill)
1060   "Destructively modify SEQ by reading elements from STREAM.
1061   SEQ is bounded by START and END. SEQ is destructively modified by
1062   copying successive elements into it from STREAM. If the end of file
1063   for STREAM is reached before copying all elements of the subsequence,
1064   then the extra elements near the end of sequence are not updated, and
1065   the index of the next element is returned."
1066   (let ((stream (sb-impl::in-synonym-of stream))
1067         (end (or end (length seq))))
1068     (etypecase stream
1069       (simple-stream
1070        (with-stream-class (simple-stream stream)
1071          (%read-sequence stream seq start end partial-fill)))
1072       (ansi-stream
1073        (%ansi-stream-read-sequence seq stream start end))
1074       (fundamental-stream
1075        (sb-gray:stream-read-sequence stream seq start end)))))
1076
1077 (defun clear-input (&optional (stream *standard-input*) buffer-only)
1078   "Clears any buffered input associated with the Stream."
1079   (let ((stream (sb-impl::in-synonym-of stream)))
1080     (etypecase stream
1081       (simple-stream
1082        (%clear-input stream buffer-only))
1083       (ansi-stream
1084        (setf (sb-kernel:ansi-stream-in-index stream)
1085              sb-impl::+ansi-stream-in-buffer-length+)
1086        (funcall (sb-kernel:ansi-stream-misc stream) stream :clear-input))
1087       (fundamental-stream
1088        (sb-gray:stream-clear-input stream))))
1089   nil)
1090
1091 (defun write-byte (integer stream)
1092   "Outputs an octet to the Stream."
1093   (let ((stream (sb-impl::out-synonym-of stream)))
1094     (etypecase stream
1095       (simple-stream
1096        (%write-byte stream integer))
1097       (ansi-stream
1098        (funcall (sb-kernel:ansi-stream-bout stream) stream integer))
1099       (fundamental-stream
1100        (sb-gray:stream-write-byte stream integer))))
1101   integer)
1102
1103 (defun write-char (character &optional (stream *standard-output*))
1104   "Outputs the Character to the Stream."
1105   (let ((stream (sb-impl::out-synonym-of stream)))
1106     (etypecase stream
1107       (simple-stream
1108        (%write-char stream character))
1109       (ansi-stream
1110        (funcall (sb-kernel:ansi-stream-out stream) stream character))
1111       (fundamental-stream
1112        (sb-gray:stream-write-char stream character))))
1113   character)
1114
1115 (defun write-string (string &optional (stream *standard-output*)
1116                             &key (start 0) (end nil))
1117   "Outputs the String to the given Stream."
1118   (let ((stream (sb-impl::out-synonym-of stream))
1119         (end (or end (length string))))
1120     (etypecase stream
1121       (simple-stream
1122        (%write-string stream string start end)
1123        string)
1124       (ansi-stream
1125        (%ansi-stream-write-string string stream start end))
1126       (fundamental-stream
1127        (sb-gray:stream-write-string stream string start end)))))
1128
1129 (defun write-line (string &optional (stream *standard-output*)
1130                           &key (start 0) end)
1131   (declare (type string string))
1132   ;; FIXME: Why is there this difference between the treatments of the
1133   ;; STREAM argument in WRITE-STRING and WRITE-LINE?
1134   (let ((stream (sb-impl::out-synonym-of stream))
1135         (end (or end (length string))))
1136     (etypecase stream
1137       (simple-stream
1138        (%check stream :output)
1139        (with-stream-class (simple-stream stream)
1140          (funcall-stm-handler-2 j-write-chars string stream start end)
1141          (funcall-stm-handler-2 j-write-char #\Newline stream)))
1142       (ansi-stream
1143        (%ansi-stream-write-string string stream start end)
1144        (funcall (sb-kernel:ansi-stream-out stream) stream #\Newline))
1145       (fundamental-stream
1146        (sb-gray:stream-write-string stream string start end)
1147        (sb-gray:stream-terpri stream))))
1148   string)
1149
1150 (defun write-sequence (seq stream &key (start 0) (end nil))
1151   "Write the elements of SEQ bounded by START and END to STREAM."
1152   (let ((stream (sb-impl::out-synonym-of stream))
1153         (end (or end (length seq))))
1154     (etypecase stream
1155       (simple-stream
1156        (%write-sequence stream seq start end))
1157       (ansi-stream
1158        (%ansi-stream-write-sequence seq stream start end))
1159       (fundamental-stream
1160        (sb-gray:stream-write-sequence stream seq start end)))))
1161
1162 (defun terpri (&optional (stream *standard-output*))
1163   "Outputs a new line to the Stream."
1164   (let ((stream (sb-impl::out-synonym-of stream)))
1165     (etypecase stream
1166       (simple-stream
1167        (%check stream :output)
1168        (with-stream-class (simple-stream stream)
1169          (funcall-stm-handler-2 j-write-char #\Newline stream)))
1170       (ansi-stream
1171        (funcall (sb-kernel:ansi-stream-out stream) stream #\Newline))
1172       (fundamental-stream
1173        (sb-gray:stream-terpri stream))))
1174   nil)
1175
1176 (defun fresh-line (&optional (stream *standard-output*))
1177   "Outputs a new line to the Stream if it is not positioned at the beginning of
1178    a line.  Returns T if it output a new line, nil otherwise."
1179   (let ((stream (sb-impl::out-synonym-of stream)))
1180     (etypecase stream
1181       (simple-stream
1182        (%fresh-line stream))
1183       (ansi-stream
1184        (when (/= (or (sb-kernel:charpos stream) 1) 0)
1185          (funcall (sb-kernel:ansi-stream-out stream) stream #\Newline)
1186          t))
1187       (fundamental-stream
1188        (sb-gray:stream-fresh-line stream)))))
1189
1190 (defun finish-output (&optional (stream *standard-output*))
1191   "Attempts to ensure that all output sent to the Stream has reached its
1192    destination, and only then returns."
1193   (let ((stream (sb-impl::out-synonym-of stream)))
1194     (etypecase stream
1195       (simple-stream
1196        (%finish-output stream))
1197       (ansi-stream
1198        (funcall (sb-kernel:ansi-stream-misc stream) stream :finish-output))
1199       (fundamental-stream
1200        (sb-gray:stream-finish-output stream))))
1201   nil)
1202
1203 (defun force-output (&optional (stream *standard-output*))
1204   "Attempts to force any buffered output to be sent."
1205   (let ((stream (sb-impl::out-synonym-of stream)))
1206     (etypecase stream
1207       (simple-stream
1208        (%force-output stream))
1209       (ansi-stream
1210        (funcall (sb-kernel:ansi-stream-misc stream) stream :force-output))
1211       (fundamental-stream
1212        (sb-gray:stream-force-output stream))))
1213   nil)
1214
1215 (defun clear-output (&optional (stream *standard-output*))
1216   "Clears the given output Stream."
1217   (let ((stream (sb-impl::out-synonym-of stream)))
1218     (etypecase stream
1219       (simple-stream
1220        (%clear-output stream))
1221       (ansi-stream
1222        (funcall (sb-kernel:ansi-stream-misc stream) stream :clear-output))
1223       (fundamental-stream
1224        (sb-gray:stream-clear-output stream))))
1225   nil)
1226
1227
1228 (defun file-position (stream &optional position)
1229   "With one argument returns the current position within the file
1230    File-Stream is open to.  If the second argument is supplied, then
1231    this becomes the new file position.  The second argument may also
1232    be :start or :end for the start and end of the file, respectively."
1233   (declare (type (or (integer 0 *) (member nil :start :end)) position))
1234   (etypecase stream
1235     (simple-stream
1236      (%file-position stream position))
1237     (ansi-stream
1238      (cond
1239        (position
1240         (setf (sb-kernel:ansi-stream-in-index stream)
1241               sb-impl::+ansi-stream-in-buffer-length+)
1242         (funcall (sb-kernel:ansi-stream-misc stream)
1243                  stream :file-position position))
1244        (t
1245         (let ((res (funcall (sb-kernel:ansi-stream-misc stream)
1246                             stream :file-position nil)))
1247           (when res
1248             (- res
1249                (- sb-impl::+ansi-stream-in-buffer-length+
1250                   (sb-kernel:ansi-stream-in-index stream))))))))))
1251
1252 (defun file-length (stream)
1253   "This function returns the length of the file that File-Stream is open to."
1254   (etypecase stream
1255     (simple-stream
1256      (%file-length stream))
1257     (ansi-stream
1258      (progn (sb-impl::stream-must-be-associated-with-file stream)
1259             (funcall (sb-kernel:ansi-stream-misc stream) stream :file-length)))))
1260
1261 (defun charpos (&optional (stream *standard-output*))
1262   "Returns the number of characters on the current line of output of the given
1263   Stream, or Nil if that information is not availible."
1264   (let ((stream (sb-impl::out-synonym-of stream)))
1265     (etypecase stream
1266       (simple-stream
1267        (with-stream-class (simple-stream stream)
1268          (%check stream :open)
1269          (sm charpos stream)))
1270       (ansi-stream
1271        (funcall (sb-kernel:ansi-stream-misc stream) stream :charpos))
1272       (fundamental-stream
1273        (sb-gray:stream-line-column stream)))))
1274
1275 (defun line-length (&optional (stream *standard-output*))
1276   "Returns the number of characters in a line of output of the given
1277   Stream, or Nil if that information is not availible."
1278   (let ((stream (sb-impl::out-synonym-of stream)))
1279     (etypecase stream
1280       (simple-stream
1281        (%check stream :output)
1282        ;; TODO (sat 2003-04-02): a way to specify a line length would
1283        ;; be good, I suppose.  Returning nil here means
1284        ;; sb-pretty::default-line-length is used.
1285        nil)
1286       (ansi-stream
1287        (funcall (sb-kernel:ansi-stream-misc stream) stream :line-length))
1288       (fundamental-stream
1289        (sb-gray:stream-line-length stream)))))
1290
1291 (defun wait-for-input-available (stream &optional timeout)
1292   "Waits for input to become available on the Stream and returns T.  If
1293   Timeout expires, Nil is returned."
1294   (let ((stream (sb-impl::in-synonym-of stream)))
1295     (etypecase stream
1296       (fixnum
1297        (sb-sys:wait-until-fd-usable stream :input timeout))
1298       (simple-stream
1299        (%check stream :input)
1300        (with-stream-class (simple-stream stream)
1301          (or (< (sm buffpos stream) (sm buffer-ptr stream))
1302              (wait-for-input-available (sm input-handle stream) timeout))))
1303       (two-way-stream
1304        (wait-for-input-available (two-way-stream-input-stream stream) timeout))
1305       (synonym-stream
1306        (wait-for-input-available (symbol-value (synonym-stream-symbol stream))
1307                                  timeout))
1308       (sb-sys::file-stream
1309        (or (< (sb-impl::fd-stream-in-index stream)
1310               (length (sb-impl::fd-stream-in-buffer stream)))
1311            (wait-for-input-available (sb-sys:fd-stream-fd stream) timeout))))))
1312
1313 ;; Make PATHNAME and NAMESTRING work
1314 (defun sb-int:file-name (stream &optional new-name)
1315   (typecase stream
1316     (file-simple-stream
1317      (with-stream-class (file-simple-stream stream)
1318        (cond (new-name
1319               (%file-rename stream new-name))
1320              (t
1321               (%file-name stream)))))
1322     (sb-sys::file-stream
1323      (cond (new-name
1324             (setf (sb-impl::fd-stream-pathname stream) new-name)
1325             (setf (sb-impl::fd-stream-file stream)
1326                   (sb-int:unix-namestring new-name nil))
1327             t)
1328            (t
1329             (sb-impl::fd-stream-pathname stream))))))