1.0.25.15: less compilation warnings
[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-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-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-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::whitespace[2]p 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             ;; Attempt buffer refill
296             (when (and (not (any-stream-instance-flags stream :dual :string))
297                        (>= (sm mode stream) 0))
298               ;; single-channel stream dirty -> write data before reading
299               (flush-buffer stream nil))
300             (>= (refill-buffer stream nil) width)))))
301
302 (defun %clear-input (stream buffer-only)
303   (declare (type simple-stream stream))
304   (with-stream-class (simple-stream stream)
305     (%check stream :input)
306     (setf (sm buffpos stream) 0
307           (sm buffer-ptr stream) 0
308           (sm last-char-read-size stream) 0
309           #|(sm unread-past-soft-eof stream) nil|#)
310     #| (setf (sm reread-count stream) 0)  on dual-channel streams? |#
311     )
312   (device-clear-input stream buffer-only))
313
314
315 (defun %read-byte (stream eof-error-p eof-value)
316   (declare (type simple-stream stream))
317   (with-stream-class (simple-stream stream)
318     (%check stream :input)
319     (if (any-stream-instance-flags stream :eof)
320         (sb-impl::eof-or-lose stream eof-error-p eof-value)
321         (etypecase stream
322           (single-channel-simple-stream
323            (read-byte-internal stream eof-error-p eof-value t))
324           (dual-channel-simple-stream
325            (read-byte-internal stream eof-error-p eof-value t))
326           (string-simple-stream
327            (with-stream-class (string-simple-stream stream)
328              (let ((encap (sm input-handle stream)))
329                (unless encap
330                  (error 'simple-type-error
331                         :datum stream
332                         :expected-type 'stream
333                         :format-control "Can't read-byte on string streams"
334                         :format-arguments '()))
335                (prog1
336                    (read-byte encap eof-error-p eof-value)
337                  (setf (sm last-char-read-size stream) 0
338                        (sm encapsulated-char-read-size stream) 0)))))))))
339
340
341 (defun %write-char (stream character)
342   (declare (type simple-stream stream))
343   (with-stream-class (simple-stream stream)
344     (%check stream :output)
345     (funcall-stm-handler-2 j-write-char character (sm melded-stream stream))))
346
347
348 (defun %fresh-line (stream)
349   (declare (type simple-stream stream))
350   (with-stream-class (simple-stream stream)
351     (%check stream :output)
352     (when (/= (or (sm charpos stream) 1) 0)
353       (funcall-stm-handler-2 j-write-char #\Newline (sm melded-stream stream))
354       t)))
355
356
357 (defun %write-string (stream string start end)
358   (declare (type simple-stream stream))
359   (with-stream-class (simple-stream stream)
360     (%check stream :output)
361     (funcall-stm-handler-2 j-write-chars string (sm melded-stream stream)
362                            start end)))
363
364
365 (defun %line-length (stream)
366   (declare (type simple-stream stream))
367   (%check stream :output)
368   ;; implement me
369   nil)
370
371
372 (defun %finish-output (stream)
373   (declare (type simple-stream stream))
374   (with-stream-class (simple-stream stream)
375     (%check stream :output)
376     (when (sm handler stream)
377       (do ()
378           ((null (sm pending stream)))
379         (sb-sys:serve-all-events)))
380     (etypecase stream
381       (single-channel-simple-stream
382        ;(when (and (> (sm mode stream) 0) (> (sm buffer-ptr stream) 0))
383        ;  (setf (device-file-position stream)
384        ;        (- (device-file-position stream) (sm buffer-ptr stream))))
385        ;(device-write stream :flush 0 nil t)
386        (flush-buffer stream t)
387        (setf (sm buffpos stream) 0))
388       (dual-channel-simple-stream
389        (with-stream-class (dual-channel-simple-stream stream)
390          (device-write stream :flush 0 nil t)
391          (setf (sm outpos stream) 0)))
392       (string-simple-stream
393            (device-write stream :flush 0 nil t))))
394   nil)
395
396
397 (defun %force-output (stream)
398   (declare (type simple-stream stream))
399   (with-stream-class (simple-stream stream)
400     (%check stream :output)
401     (etypecase stream
402       (single-channel-simple-stream
403        ;(when (> (sm buffer-ptr stream) 0)
404        ;  (setf (device-file-position stream)
405        ;        (- (device-file-position stream) (sm buffer-ptr stream))))
406        ;(device-write stream :flush 0 nil nil)
407        (flush-buffer stream nil)
408        (setf (sm buffpos stream) 0))
409       (dual-channel-simple-stream
410        (with-stream-class (dual-channel-simple-stream stream)
411          (device-write stream :flush 0 nil nil)
412          (setf (sm outpos stream) 0)))
413       (string-simple-stream
414        (device-write stream :flush 0 nil nil))))
415   nil)
416
417
418 (defun %clear-output (stream)
419   (declare (type simple-stream stream))
420   (with-stream-class (simple-stream stream)
421     (%check stream :output)
422     (when (sm handler stream)
423       (sb-sys:remove-fd-handler (sm handler stream))
424       (setf (sm handler stream) nil
425             (sm pending stream) nil))
426     (etypecase stream
427       (single-channel-simple-stream
428        (with-stream-class (single-channel-simple-stream stream)
429          (case (sm mode stream)
430            (1 (setf (sm buffpos stream) 0))
431            (3 (setf (sm mode stream) 0)))))
432       (dual-channel-simple-stream
433        (setf (sm outpos stream) 0))
434       (string-simple-stream
435        nil))
436     (device-clear-output stream)))
437
438
439 (defun %write-byte (stream integer)
440   (declare (type simple-stream stream))
441   (with-stream-class (simple-stream stream)
442     (%check stream :output)
443     (etypecase stream
444       (single-channel-simple-stream
445        (with-stream-class (single-channel-simple-stream stream)
446          (let ((ptr (sm buffpos stream)))
447           (when (>= ptr (sm buf-len stream))
448             (setf ptr (flush-buffer stream t)))
449           (setf (sm buffpos stream) (1+ ptr))
450           (setf (sm charpos stream) nil)
451           (setf (bref (sm buffer stream) ptr) integer)
452           (sc-set-dirty stream))))
453       (dual-channel-simple-stream
454        (with-stream-class (dual-channel-simple-stream stream)
455          (let ((ptr (sm outpos stream)))
456            (when (>= ptr (sm max-out-pos stream))
457              (setf ptr (flush-out-buffer stream t)))
458            (setf (sm outpos stream) (1+ ptr))
459            (setf (sm charpos stream) nil)
460            (setf (bref (sm out-buffer stream) ptr) integer))))
461       (string-simple-stream
462        (with-stream-class (string-simple-stream stream)
463          (let ((encap (sm output-handle stream)))
464            (unless encap
465              (error 'simple-type-error
466                     :datum stream
467                     :expected-type 'stream
468                     :format-control "Can't write-byte on string streams."
469                     :format-arguments '()))
470            (write-byte integer encap)))))))
471
472
473 (defun %read-sequence (stream seq start end partial-fill)
474   (declare (type simple-stream stream)
475            (type sequence seq)
476            (type sb-int:index start end)
477            (type boolean partial-fill))
478   (with-stream-class (simple-stream stream)
479     (%check stream :input)
480     (when (any-stream-instance-flags stream :eof)
481       (return-from %read-sequence 0))
482     (when (and (not (any-stream-instance-flags stream :dual :string))
483                (sc-dirty-p stream))
484       (flush-buffer stream t))
485     (etypecase seq
486       (string
487        (funcall-stm-handler j-read-chars (sm melded-stream stream) seq nil
488                             start end
489                             (if partial-fill :bnb t)))
490       ((or (simple-array (unsigned-byte 8) (*))
491            (simple-array (signed-byte 8) (*)))
492        (when (any-stream-instance-flags stream :string)
493          (error "Can't read into byte sequence from a string stream."))
494        ;; "read-vector" equivalent, but blocking if partial-fill is NIL
495        ;; FIXME: this could be implemented faster via buffer-copy
496        (loop with encap = (sm melded-stream stream)
497             for index from start below end
498             for byte = (read-byte-internal encap nil nil t)
499               then (read-byte-internal encap nil nil partial-fill)
500             while byte
501             do (setf (bref seq index) byte)
502             finally (return index)))
503       ;; extend to work on other sequences: repeated read-byte
504       )))
505
506 (defun %write-sequence (stream seq start end)
507   (declare (type simple-stream stream)
508            (type sequence seq)
509            (type sb-int:index start end))
510   (with-stream-class (simple-stream stream)
511     (%check stream :output)
512     (etypecase seq
513       (string
514        (funcall-stm-handler-2 j-write-chars seq (sm melded-stream stream)
515                               start end))
516       ((or (simple-array (unsigned-byte 8) (*))
517            (simple-array (signed-byte 8) (*)))
518        ;; "write-vector" equivalent
519        (setf (sm charpos stream) nil)
520        (etypecase stream
521          (single-channel-simple-stream
522           (with-stream-class (single-channel-simple-stream stream)
523             (loop with max-ptr fixnum = (sm buf-len stream)
524                   for src-pos fixnum = start then (+ src-pos count)
525                   for src-rest fixnum = (- end src-pos)
526                   while (> src-rest 0) ; FIXME: this is non-ANSI
527                   for ptr fixnum = (let ((ptr (sm buffpos stream)))
528                                      (if (>= ptr max-ptr)
529                                          (flush-buffer stream t)
530                                          ptr))
531                   for buf-rest fixnum = (- max-ptr ptr)
532                   for count fixnum = (min buf-rest src-rest)
533                   do (progn (setf (sm mode stream) 1)
534                             (setf (sm buffpos stream) (+ ptr count))
535                             (buffer-copy seq src-pos (sm buffer stream) ptr count)))))
536          (dual-channel-simple-stream
537           (with-stream-class (dual-channel-simple-stream stream)
538             (loop with max-ptr fixnum = (sm max-out-pos stream)
539                   for src-pos fixnum = start then (+ src-pos count)
540                   for src-rest fixnum = (- end src-pos)
541                   while (> src-rest 0) ; FIXME: this is non-ANSI
542                   for ptr fixnum = (let ((ptr (sm outpos stream)))
543                                      (if (>= ptr max-ptr)
544                                          (flush-out-buffer stream t)
545                                          ptr))
546                   for buf-rest fixnum = (- max-ptr ptr)
547                   for count fixnum = (min buf-rest src-rest)
548                   do (progn (setf (sm outpos stream) (+ ptr count))
549                             (buffer-copy seq src-pos (sm out-buffer stream) ptr count)))))
550          (string-simple-stream
551           (error 'simple-type-error
552                  :datum stream
553                  :expected-type 'stream
554                  :format-control "Can't write a byte sequence to a string stream."
555                  :format-arguments '())))
556        )
557       ;; extend to work on other sequences: repeated write-byte
558       ))
559   seq)
560
561
562 (defun read-vector (vector stream &key (start 0) end (endian-swap :byte-8))
563   (declare (type (sb-kernel:simple-unboxed-array (*)) vector)
564            (type stream stream))
565   ;; START and END are octet offsets, not vector indices!  [Except for strings]
566   ;; Return value is index of next octet to be read into (i.e., start+count)
567   (etypecase stream
568     (simple-stream
569      (with-stream-class (simple-stream stream)
570        (cond ((stringp vector)
571               (let* ((start (or start 0))
572                      (end (or end (length vector)))
573                      (encap (sm melded-stream stream))
574                      (char (funcall-stm-handler j-read-char encap nil nil t)))
575                 (when char
576                   (setf (schar vector start) char)
577                   (incf start)
578                   (+ start (funcall-stm-handler j-read-chars encap vector nil
579                                                 start end nil)))))
580              ((any-stream-instance-flags stream :string)
581               (error "Can't READ-BYTE on string streams."))
582              (t
583               (do* ((encap (sm melded-stream stream))
584                     (index (or start 0) (1+ index))
585                     (end (or end (* (length vector) (vector-elt-width vector))))
586                     (endian-swap (endian-swap-value vector endian-swap))
587                     (byte (read-byte-internal encap nil nil t)
588                           (read-byte-internal encap nil nil nil)))
589                    ((or (null byte) (>= index end)) index)
590                 (setf (bref vector (logxor index endian-swap)) byte))))))
591     ((or ansi-stream fundamental-stream)
592      (unless (typep vector '(or string
593                              (simple-array (signed-byte 8) (*))
594                              (simple-array (unsigned-byte 8) (*))))
595        (error "Wrong vector type for read-vector on stream not of type simple-stream."))
596      (read-sequence vector stream :start (or start 0) :end end))))
597
598
599 ;;;
600 ;;; USER-LEVEL FUNCTIONS
601 ;;;
602
603 (defmethod open-stream-p ((stream simple-stream))
604   (any-stream-instance-flags stream :input :output))
605
606 (defmethod input-stream-p ((stream simple-stream))
607   (any-stream-instance-flags stream :input))
608
609 (defmethod output-stream-p ((stream simple-stream))
610   (any-stream-instance-flags stream :output))
611
612 (defmethod stream-element-type ((stream simple-stream))
613   '(unsigned-byte 8))
614
615 (defun interactive-stream-p (stream)
616   "Return true if Stream does I/O on a terminal or other interactive device."
617   (etypecase stream
618     (simple-stream
619      (%check stream :open)
620      (any-stream-instance-flags stream :interactive))
621     (ansi-stream
622      (funcall (sb-kernel:ansi-stream-misc stream) stream :interactive-p))
623     (fundamental-stream
624      nil)))
625
626 (defun (setf interactive-stream-p) (flag stream)
627   (typecase stream
628     (simple-stream
629      (%check stream :open)
630      (if flag
631          (add-stream-instance-flags stream :interactive)
632          (remove-stream-instance-flags stream :interactive)))
633     (t
634      (error 'simple-type-error
635             :datum stream
636             :expected-type 'simple-stream
637             :format-control "Can't set interactive flag on ~S."
638             :format-arguments (list stream)))))
639
640 (defun file-string-length (stream object)
641   (declare (type (or string character) object) (type stream stream))
642   "Return the delta in STREAM's FILE-POSITION that would be caused by writing
643    OBJECT to STREAM. Non-trivial only in implementations that support
644    international character sets."
645   (typecase stream
646     (simple-stream (%file-string-length stream object))
647     (t
648      (etypecase object
649        (character 1)
650        (string (length object))))))
651
652 (defun stream-external-format (stream)
653   "Returns Stream's external-format."
654   (etypecase stream
655     (simple-stream
656      (with-stream-class (simple-stream)
657        (%check stream :open)
658        (sm external-format stream)))
659     (ansi-stream
660      :default)
661     (fundamental-stream
662      :default)))
663
664 (defun open (filename &rest options
665              &key (direction :input)
666              (element-type 'character element-type-given)
667              if-exists if-does-not-exist
668              (external-format :default)
669              class mapped input-handle output-handle
670              &allow-other-keys)
671   "Return a stream which reads from or writes to Filename.
672   Defined keywords:
673    :direction - one of :input, :output, :io, or :probe
674    :element-type - type of object to read or write, default BASE-CHAR
675    :if-exists - one of :error, :new-version, :rename, :rename-and-delete,
676                        :overwrite, :append, :supersede or NIL
677    :if-does-not-exist - one of :error, :create or NIL
678    :external-format - :default
679   See the manual for details.
680
681   The following are simple-streams-specific additions:
682    :class - class of stream object to be created
683    :mapped - T to open a memory-mapped file
684    :input-handle - a stream or Unix file descriptor to read from
685    :output-handle - a stream or Unix file descriptor to write to"
686   (declare (ignore element-type external-format input-handle output-handle
687                    if-exists if-does-not-exist))
688   (let ((class (or class 'sb-sys:fd-stream))
689         (options (copy-list options))
690         (filespec (merge-pathnames filename)))
691     (cond ((eq class 'sb-sys:fd-stream)
692            (remf options :class)
693            (remf options :mapped)
694            (remf options :input-handle)
695            (remf options :output-handle)
696            (apply #'open-fd-stream filespec options))
697           ((subtypep class 'simple-stream)
698            (when element-type-given
699              (cerror "Do it anyway."
700                      "Can't create simple-streams with an element-type."))
701            (when (and (eq class 'file-simple-stream) mapped)
702              (setq class 'mapped-file-simple-stream)
703              (setf (getf options :class) 'mapped-file-simple-stream))
704            (when (subtypep class 'file-simple-stream)
705              (when (eq direction :probe)
706                (setq class 'probe-simple-stream)))
707            (apply #'make-instance class :filename filespec options))
708           ((subtypep class 'sb-gray:fundamental-stream)
709            (remf options :class)
710            (remf options :mapped)
711            (remf options :input-handle)
712            (remf options :output-handle)
713            (make-instance class :lisp-stream
714                           (apply #'open-fd-stream filespec options))))))
715
716
717 (declaim (inline read-byte read-char read-char-no-hang unread-char))
718
719 (defun read-byte (stream &optional (eof-error-p t) eof-value)
720   "Returns the next byte of the Stream."
721   (let ((stream (sb-impl::in-synonym-of stream)))
722     (etypecase stream
723       (simple-stream
724        (%read-byte stream eof-error-p eof-value))
725       (ansi-stream
726        (sb-impl::ansi-stream-read-byte stream eof-error-p eof-value nil))
727       (fundamental-stream
728        (let ((char (sb-gray:stream-read-byte stream)))
729          (if (eq char :eof)
730              (sb-impl::eof-or-lose stream eof-error-p eof-value)
731              char))))))
732
733 (defun read-char (&optional (stream *standard-input*) (eof-error-p t)
734                             eof-value recursive-p)
735   "Inputs a character from Stream and returns it."
736   (let ((stream (sb-impl::in-synonym-of stream)))
737     (etypecase stream
738       (simple-stream
739        (%read-char stream eof-error-p eof-value recursive-p t))
740       (ansi-stream
741        (sb-impl::ansi-stream-read-char stream eof-error-p eof-value
742                                        recursive-p))
743       (fundamental-stream
744        (let ((char (sb-gray:stream-read-char stream)))
745          (if (eq char :eof)
746              (sb-impl::eof-or-lose stream eof-error-p eof-value)
747              char))))))
748
749 (defun read-char-no-hang (&optional (stream *standard-input*) (eof-error-p t)
750                                     eof-value recursive-p)
751   "Returns the next character from the Stream if one is availible, or nil."
752   (let ((stream (sb-impl::in-synonym-of stream)))
753     (etypecase stream
754       (simple-stream
755        (%check stream :input)
756        (with-stream-class (simple-stream)
757          (funcall-stm-handler j-read-char stream eof-error-p eof-value nil)))
758       (ansi-stream
759        (sb-impl::ansi-stream-read-char-no-hang stream eof-error-p eof-value
760                                                recursive-p))
761       (fundamental-stream
762        (let ((char (sb-gray:stream-read-char-no-hang stream)))
763          (if (eq char :eof)
764              (sb-impl::eof-or-lose stream eof-error-p eof-value)
765              char))))))
766
767 (defun unread-char (character &optional (stream *standard-input*))
768   "Puts the Character back on the front of the input Stream."
769   (let ((stream (sb-impl::in-synonym-of stream)))
770     (etypecase stream
771       (simple-stream
772        (%unread-char stream character))
773       (ansi-stream
774        (sb-impl::ansi-stream-unread-char character stream))
775       (fundamental-stream
776        (sb-gray:stream-unread-char stream character))))
777   nil)
778
779 (declaim (notinline read-byte read-char read-char-no-hang unread-char))
780
781 (defun peek-char (&optional (peek-type nil) (stream *standard-input*)
782                             (eof-error-p t) eof-value recursive-p)
783   "Peeks at the next character in the input Stream.  See manual for details."
784   (let ((stream (sb-impl::in-synonym-of stream)))
785     (etypecase stream
786       (simple-stream
787        (%peek-char stream peek-type eof-error-p eof-value recursive-p))
788       ;; FIXME: Broken on ECHO-STREAM (cf internal implementation?) --
789       ;; CSR, 2004-01-19
790       (ansi-stream
791        (sb-impl::ansi-stream-peek-char peek-type stream eof-error-p eof-value
792                                        recursive-p))
793       (fundamental-stream
794        (cond ((characterp peek-type)
795               (do ((char (sb-gray:stream-read-char stream)
796                          (sb-gray:stream-read-char stream)))
797                   ((or (eq char :eof) (char= char peek-type))
798                    (cond ((eq char :eof)
799                           (sb-impl::eof-or-lose stream eof-error-p eof-value))
800                          (t
801                           (sb-gray:stream-unread-char stream char)
802                           char)))))
803              ((eq peek-type t)
804               (do ((char (sb-gray:stream-read-char stream)
805                          (sb-gray:stream-read-char stream)))
806                   ((or (eq char :eof) (not (sb-impl::whitespace[2]p char)))
807                    (cond ((eq char :eof)
808                           (sb-impl::eof-or-lose stream eof-error-p eof-value))
809                          (t
810                           (sb-gray:stream-unread-char stream char)
811                           char)))))
812              (t
813               (let ((char (sb-gray:stream-peek-char stream)))
814                 (if (eq char :eof)
815                     (sb-impl::eof-or-lose stream eof-error-p eof-value)
816                     char))))))))
817
818 (defun listen (&optional (stream *standard-input*) (width 1))
819   "Returns T if WIDTH octets are available on STREAM.  If WIDTH is
820 given as 'CHARACTER, check for a character.  Note: the WIDTH argument
821 is supported only on simple-streams."
822   ;; WIDTH is number of octets which must be available; any value
823   ;; other than 1 is treated as 'character.
824   (let ((stream (sb-impl::in-synonym-of stream)))
825     (etypecase stream
826       (simple-stream
827        (%listen stream width))
828       (ansi-stream
829        (sb-impl::ansi-stream-listen stream))
830       (fundamental-stream
831        (sb-gray:stream-listen stream)))))
832
833
834 (defun read-line (&optional (stream *standard-input*) (eof-error-p t)
835                             eof-value recursive-p)
836   "Returns a line of text read from the Stream as a string, discarding the
837   newline character."
838   (let ((stream (sb-impl::in-synonym-of stream)))
839     (etypecase stream
840       (simple-stream
841        (%read-line stream eof-error-p eof-value recursive-p))
842       (ansi-stream
843        (sb-impl::ansi-stream-read-line stream eof-error-p eof-value
844                                        recursive-p))
845       (fundamental-stream
846        (multiple-value-bind (string eof) (sb-gray:stream-read-line stream)
847          (if (and eof (zerop (length string)))
848              (values (sb-impl::eof-or-lose stream eof-error-p eof-value) t)
849              (values string eof)))))))
850
851 (defun read-sequence (seq stream &key (start 0) (end nil) partial-fill)
852   "Destructively modify SEQ by reading elements from STREAM.
853   SEQ is bounded by START and END. SEQ is destructively modified by
854   copying successive elements into it from STREAM. If the end of file
855   for STREAM is reached before copying all elements of the subsequence,
856   then the extra elements near the end of sequence are not updated, and
857   the index of the next element is returned."
858   (let ((stream (sb-impl::in-synonym-of stream))
859         (end (or end (length seq))))
860     (etypecase stream
861       (simple-stream
862        (with-stream-class (simple-stream stream)
863          (%read-sequence stream seq start end partial-fill)))
864       (ansi-stream
865        (sb-impl::ansi-stream-read-sequence seq stream start end))
866       (fundamental-stream
867        (sb-gray:stream-read-sequence stream seq start end)))))
868
869 (defun clear-input (&optional (stream *standard-input*) buffer-only)
870   "Clears any buffered input associated with the Stream."
871   (let ((stream (sb-impl::in-synonym-of stream)))
872     (etypecase stream
873       (simple-stream
874        (%clear-input stream buffer-only))
875       (ansi-stream
876        (sb-impl::ansi-stream-clear-input stream))
877       (fundamental-stream
878        (sb-gray:stream-clear-input stream))))
879   nil)
880
881 (defun write-byte (integer stream)
882   "Outputs an octet to the Stream."
883   (let ((stream (sb-impl::out-synonym-of stream)))
884     (etypecase stream
885       (simple-stream
886        (%write-byte stream integer))
887       (ansi-stream
888        (funcall (sb-kernel:ansi-stream-bout stream) stream integer))
889       (fundamental-stream
890        (sb-gray:stream-write-byte stream integer))))
891   integer)
892
893 (defun write-char (character &optional (stream *standard-output*))
894   "Outputs the Character to the Stream."
895   (let ((stream (sb-impl::out-synonym-of stream)))
896     (etypecase stream
897       (simple-stream
898        (%write-char stream character))
899       (ansi-stream
900        (funcall (sb-kernel:ansi-stream-out stream) stream character))
901       (fundamental-stream
902        (sb-gray:stream-write-char stream character))))
903   character)
904
905 (defun write-string (string &optional (stream *standard-output*)
906                             &key (start 0) (end nil))
907   "Outputs the String to the given Stream."
908   (let ((stream (sb-impl::out-synonym-of stream))
909         (end (sb-impl::%check-vector-sequence-bounds string start end)))
910     (etypecase stream
911       (simple-stream
912        (%write-string stream string start end)
913        string)
914       (ansi-stream
915        (sb-impl::ansi-stream-write-string string stream start end))
916       (fundamental-stream
917        (sb-gray:stream-write-string stream string start end)))))
918
919 (defun write-line (string &optional (stream *standard-output*)
920                           &key (start 0) end)
921   (declare (type string string))
922   (let ((stream (sb-impl::out-synonym-of stream))
923         (end (sb-impl::%check-vector-sequence-bounds string start end)))
924     (etypecase stream
925       (simple-stream
926        (%check stream :output)
927        (with-stream-class (simple-stream stream)
928          (funcall-stm-handler-2 j-write-chars string stream start end)
929          (funcall-stm-handler-2 j-write-char #\Newline stream)))
930       (ansi-stream
931        (sb-impl::ansi-stream-write-string string stream start end)
932        (funcall (sb-kernel:ansi-stream-out stream) stream #\Newline))
933       (fundamental-stream
934        (sb-gray:stream-write-string stream string start end)
935        (sb-gray:stream-terpri stream))))
936   string)
937
938 (defun write-sequence (seq stream &key (start 0) (end nil))
939   "Write the elements of SEQ bounded by START and END to STREAM."
940   (let ((stream (sb-impl::out-synonym-of stream))
941         (end (or end (length seq))))
942     (etypecase stream
943       (simple-stream
944        (%write-sequence stream seq start end))
945       (ansi-stream
946        (sb-impl::ansi-stream-write-sequence seq stream start end))
947       (fundamental-stream
948        (sb-gray:stream-write-sequence stream seq start end)))))
949
950 (defun terpri (&optional (stream *standard-output*))
951   "Outputs a new line to the Stream."
952   (let ((stream (sb-impl::out-synonym-of stream)))
953     (etypecase stream
954       (simple-stream
955        (%check stream :output)
956        (with-stream-class (simple-stream stream)
957          (funcall-stm-handler-2 j-write-char #\Newline stream)))
958       (ansi-stream
959        (funcall (sb-kernel:ansi-stream-out stream) stream #\Newline))
960       (fundamental-stream
961        (sb-gray:stream-terpri stream))))
962   nil)
963
964 (defun fresh-line (&optional (stream *standard-output*))
965   "Outputs a new line to the Stream if it is not positioned at the beginning of
966    a line.  Returns T if it output a new line, nil otherwise."
967   (let ((stream (sb-impl::out-synonym-of stream)))
968     (etypecase stream
969       (simple-stream
970        (%fresh-line stream))
971       (ansi-stream
972        (sb-impl::ansi-stream-fresh-line stream))
973       (fundamental-stream
974        (sb-gray:stream-fresh-line stream)))))
975
976 (defun finish-output (&optional (stream *standard-output*))
977   "Attempts to ensure that all output sent to the Stream has reached its
978    destination, and only then returns."
979   (let ((stream (sb-impl::out-synonym-of stream)))
980     (etypecase stream
981       (simple-stream
982        (%finish-output stream))
983       (ansi-stream
984        (funcall (sb-kernel:ansi-stream-misc stream) stream :finish-output))
985       (fundamental-stream
986        (sb-gray:stream-finish-output stream))))
987   nil)
988
989 (defun force-output (&optional (stream *standard-output*))
990   "Attempts to force any buffered output to be sent."
991   (let ((stream (sb-impl::out-synonym-of stream)))
992     (etypecase stream
993       (simple-stream
994        (%force-output stream))
995       (ansi-stream
996        (funcall (sb-kernel:ansi-stream-misc stream) stream :force-output))
997       (fundamental-stream
998        (sb-gray:stream-force-output stream))))
999   nil)
1000
1001 (defun clear-output (&optional (stream *standard-output*))
1002   "Clears the given output Stream."
1003   (let ((stream (sb-impl::out-synonym-of stream)))
1004     (etypecase stream
1005       (simple-stream
1006        (%clear-output stream))
1007       (ansi-stream
1008        (funcall (sb-kernel:ansi-stream-misc stream) stream :clear-output))
1009       (fundamental-stream
1010        (sb-gray:stream-clear-output stream))))
1011   nil)
1012
1013
1014 (defun file-position (stream &optional position)
1015   "With one argument returns the current position within the file
1016    File-Stream is open to.  If the second argument is supplied, then
1017    this becomes the new file position.  The second argument may also
1018    be :start or :end for the start and end of the file, respectively."
1019   (declare (type (or sb-int:index (member nil :start :end)) position))
1020   (etypecase stream
1021     (simple-stream
1022      (%file-position stream position))
1023     (ansi-stream
1024      (sb-impl::ansi-stream-file-position stream position))))
1025
1026 (defun file-length (stream)
1027   "This function returns the length of the file that File-Stream is open to."
1028   (etypecase stream
1029     (simple-stream
1030      (%file-length stream))
1031     (ansi-stream
1032      (sb-impl::stream-must-be-associated-with-file stream)
1033      (funcall (sb-kernel:ansi-stream-misc stream) stream :file-length))))
1034
1035 (defun charpos (&optional (stream *standard-output*))
1036   "Returns the number of characters on the current line of output of the given
1037   Stream, or Nil if that information is not availible."
1038   (let ((stream (sb-impl::out-synonym-of stream)))
1039     (etypecase stream
1040       (simple-stream
1041        (with-stream-class (simple-stream stream)
1042          (%check stream :open)
1043          (sm charpos stream)))
1044       (ansi-stream
1045        (funcall (sb-kernel:ansi-stream-misc stream) stream :charpos))
1046       (fundamental-stream
1047        (sb-gray:stream-line-column stream)))))
1048
1049 (defun line-length (&optional (stream *standard-output*))
1050   "Returns the number of characters in a line of output of the given
1051   Stream, or Nil if that information is not availible."
1052   (let ((stream (sb-impl::out-synonym-of stream)))
1053     (etypecase stream
1054       (simple-stream
1055        (%check stream :output)
1056        ;; TODO (sat 2003-04-02): a way to specify a line length would
1057        ;; be good, I suppose.  Returning nil here means
1058        ;; sb-pretty::default-line-length is used.
1059        nil)
1060       (ansi-stream
1061        (funcall (sb-kernel:ansi-stream-misc stream) stream :line-length))
1062       (fundamental-stream
1063        (sb-gray:stream-line-length stream)))))
1064
1065 (defun wait-for-input-available (stream &optional timeout)
1066   "Waits for input to become available on the Stream and returns T.  If
1067   Timeout expires, Nil is returned."
1068   (let ((stream (sb-impl::in-synonym-of stream)))
1069     (etypecase stream
1070       (fixnum
1071        (sb-sys:wait-until-fd-usable stream :input timeout))
1072       (simple-stream
1073        (%check stream :input)
1074        (with-stream-class (simple-stream stream)
1075          (or (< (sm buffpos stream) (sm buffer-ptr stream))
1076              (wait-for-input-available (sm input-handle stream) timeout))))
1077       (two-way-stream
1078        (wait-for-input-available (two-way-stream-input-stream stream) timeout))
1079       (synonym-stream
1080        (wait-for-input-available (symbol-value (synonym-stream-symbol stream))
1081                                  timeout))
1082       (sb-sys:fd-stream
1083        (or (< (sb-impl::fd-stream-in-index stream)
1084               (length (sb-impl::fd-stream-in-buffer stream)))
1085            (wait-for-input-available (sb-sys:fd-stream-fd stream) timeout))))))
1086
1087 ;; Make PATHNAME and NAMESTRING work
1088 (defun sb-int:file-name (stream &optional new-name)
1089   (typecase stream
1090     (file-simple-stream
1091      (with-stream-class (file-simple-stream stream)
1092        (cond (new-name
1093               (%file-rename stream new-name))
1094              (t
1095               (%file-name stream)))))
1096     (sb-sys:fd-stream
1097      (cond (new-name
1098             (setf (sb-impl::fd-stream-pathname stream) new-name)
1099             (setf (sb-impl::fd-stream-file stream)
1100                   (sb-int:unix-namestring new-name nil))
1101             t)
1102            (t
1103             (sb-impl::fd-stream-pathname stream))))))