1.0.23.64: fixed bug 395
[sbcl.git] / tests / stream.pure.lisp
1 ;;;; tests related to Lisp streams
2
3 ;;;; This software is part of the SBCL system. See the README file for
4 ;;;; more information.
5 ;;;;
6 ;;;; While most of SBCL is derived from the CMU CL system, the test
7 ;;;; files (like this one) were written from scratch after the fork
8 ;;;; from CMU CL.
9 ;;;;
10 ;;;; This software is in the public domain and is provided with
11 ;;;; absolutely no warranty. See the COPYING and CREDITS files for
12 ;;;; more information.
13
14 (in-package :cl-user)
15
16 ;;; Until sbcl-0.6.11.31, we didn't have an N-BIN method for
17 ;;; CONCATENATED-STREAM, so stuff like this would fail.
18 (let ((stream (make-concatenated-stream (make-string-input-stream "Demo")))
19       (buffer (make-string 4)))
20   (read-sequence buffer stream))
21 ;;; test for the new N-BIN method doing what it's supposed to
22 (let* ((substrings (list "This " "is " "a " ""
23                          "test of concatenated streams behaving "
24                          "as ordinary streams do under READ-SEQUENCE. "
25                          (make-string 140041 :initial-element #\%)
26                          "For any size of read.."
27                          (make-string 4123 :initial-element #\.)
28                          "they should give the same results."
29                          (make-string (expt 2 14) :initial-element #\*)
30                          "There should be no differences."))
31        (substreams (mapcar #'make-string-input-stream substrings))
32        (concatenated-stream (apply #'make-concatenated-stream substreams))
33        (concatenated-string (apply #'concatenate 'string substrings))
34        (stream (make-string-input-stream concatenated-string))
35        (max-n-to-read 24)
36        (buffer-1 (make-string max-n-to-read))
37        (buffer-2 (make-string max-n-to-read)))
38   (loop
39    (let* ((n-to-read (random max-n-to-read))
40           (n-actually-read-1 (read-sequence buffer-1
41                                             concatenated-stream
42                                             :end n-to-read))
43           (n-actually-read-2 (read-sequence buffer-2
44                                             stream
45                                             :end n-to-read)))
46 ;;     (format t "buffer-1=~S~%buffer-2=~S~%" buffer-1 buffer-2)
47      (assert (= n-actually-read-1 n-actually-read-2))
48      (assert (string= buffer-1 buffer-2
49                       :end1 n-actually-read-1
50                       :end2 n-actually-read-2))
51      (unless (= n-actually-read-1 n-to-read)
52        (assert (< n-actually-read-1 n-to-read))
53        (return)))))
54
55 ;;; Entomotomy PEEK-CHAR-WRONGLY-ECHOS-TO-ECHO-STREAM bug, fixed by
56 ;;; MRD patch sbcl-devel 2002-11-02 merged ca. sbcl-0.7.9.32...
57 (assert (string=
58          (with-output-to-string (out)
59            (peek-char #\]
60                       (make-echo-stream
61                        (make-string-input-stream "ab cd e df s]") out)))
62          ;; (Before the fix, the result had a trailing #\] in it.)
63          "ab cd e df s"))
64 ;;; ...and a missing wrinkle in the original patch, dealing with
65 ;;; PEEK-CHAR/UNREAD-CHAR on ECHO-STREAMs, fixed by MRD patch
66 ;;; sbcl-devel 2002-11-18, merged ca. sbcl-0.7.9.66
67 (assert (string=
68          (let* ((in-stream (make-string-input-stream "abc"))
69                 (out-stream (make-string-output-stream))
70                 (echo-stream (make-echo-stream in-stream out-stream)))
71            (unread-char (read-char echo-stream) echo-stream)
72            (peek-char #\a echo-stream)
73            (get-output-stream-string out-stream))
74          ;; (Before the fix, the LET* expression just signalled an error.)
75          "a"))
76
77 ;;; Reported by Fredrik Sandstrom to sbcl-devel 2005-05-17 ("Bug in
78 ;;; peek-char"):
79 ;;; Description: In (peek-char nil s nil foo), if foo happens to be
80 ;;; the same character that peek-char returns, the character is
81 ;;; removed from the input stream, as if read by read-char.
82 (assert (equal (with-input-from-string (s "123")
83                  (list (peek-char nil s nil #\1) (read-char s) (read-char s)))
84                '(#\1 #\1 #\2)))
85
86 ;;; ... and verify that the fix does not break echo streams
87 (assert (string= (let ((out (make-string-output-stream)))
88                    (with-open-stream (s (make-echo-stream
89                                          (make-string-input-stream "123")
90                                          out))
91                      (format s "=>~{~A~}"
92                              (list (peek-char nil s nil #\1)
93                                    (read-char s)
94                                    (read-char s)))
95                      (get-output-stream-string out)))
96                  "12=>112"))
97
98 ;;; 0.7.12 doesn't advance current stream in concatenated streams
99 ;;; correctly when searching a stream for a char to read.
100 (with-input-from-string (p "")
101   (with-input-from-string (q "foo")
102     (let* ((r (make-concatenated-stream p q)))
103       (peek-char nil r))))
104
105 ;;; 0.7.14 and previous SBCLs don't have a working INTERACTIVE-STREAM-P
106 ;;; because it called UNIX-ISATTY, which wasn't defined.
107 (with-input-from-string (s "a non-interactive stream")
108   (assert (not (interactive-stream-p s))))
109 ;;; KLUDGE: Unfortunately it's hard to find a reliably interactive
110 ;;; stream to test, since it's reasonable for these tests to be run
111 ;;; from a script, conceivably even as something like a cron job.
112 ;;; Ideas?
113 #+nil (assert (eq (interactive-stream-p *terminal-io*) t))
114
115 ;;; MAKE-STRING-INPUT-STREAM
116 ;;;
117 ;;; * Observe FILE-POSITION :START and :END, and allow setting of
118 ;;;   FILE-POSITION beyond the end of string, signalling END-OF-FILE only
119 ;;;   on read.
120 (let* ((string (copy-seq "abc"))
121        (stream (make-string-input-stream string)))
122   (assert (char= (read-char stream) #\a))
123   (assert (= 1 (file-position stream)))
124   (assert (file-position stream :start))
125   (assert (= 0 (file-position stream)))
126   (assert (file-position stream :end))
127   (assert (= (length string) (file-position stream)))
128   (assert (file-position stream (1- (file-position stream))))
129   (assert (char= (read-char stream) #\c))
130   (assert (file-position stream (1- (file-position stream))))
131   (assert (char= (read-char stream) #\c))
132   (assert (file-position stream :end))
133   (let ((eof (cons nil nil)))
134     (assert (eq (read-char stream nil eof) eof)))
135   (assert (file-position stream 10))
136   (multiple-value-bind (val cond) (ignore-errors (file-position stream -1))
137     (assert (null val))
138     (assert (typep cond 'error)))
139   (multiple-value-bind (val cond) (ignore-errors (read-char stream))
140     (assert (null val))
141     (assert (typep cond 'end-of-file))))
142
143 ;;; MAKE-STRING-OUTPUT-STREAM
144 ;;;
145 ;;; * Observe FILE-POSITION :START and :END, and allow setting of
146 ;;;   FILE-POSITION to an arbitrary index.
147 ;;;
148 ;;; * END will always refer to the farthest position of stream so-far
149 ;;;   seen, and setting FILE-POSITION beyond the current END will extend
150 ;;;   the string/stream with uninitialized elements.
151 ;;;
152 ;;; * Rewinding the stream works with overwriting semantics.
153 ;;;
154 (let ((stream (make-string-output-stream)))
155   (princ "abcd" stream)
156   (assert (= 4 (file-position stream)))
157   (assert (file-position stream :start))
158   (assert (= 0 (file-position stream)))
159   (princ "0" stream)
160   (assert (= 1 (file-position stream)))
161   (file-position stream 2)
162   (assert (= 2 (file-position stream)))
163   (princ "2" stream)
164   (assert (file-position stream :end))
165   (assert (= 4 (file-position stream)))
166   (assert (file-position stream 6))
167   (assert (file-position stream 4))
168   (assert (file-position stream :end))
169   (assert (= 6 (file-position stream)))
170   (assert (file-position stream 4))
171   (multiple-value-bind (val cond) (ignore-errors (file-position stream -1))
172     (assert (null val))
173     (assert (typep cond 'error)))
174   (princ "!!" stream)
175   (assert (equal "0b2d!!" (get-output-stream-string stream))))
176
177 ;;; WITH-OUTPUT-TO-STRING (when provided with a string argument)
178 ;;;
179 ;;; * Observe FILE-POSITION :START and :END, and allow setting of
180 ;;; FILE-POSITION to an arbitrary index. If the new position is beyond
181 ;;; the end of string and the string is adjustable the string will be
182 ;;; implicitly extended, otherwise an error will be signalled. The
183 ;;; latter case is provided for in the code, but not currently
184 ;;; excercised since SBCL fill-pointer arrays are always (currently)
185 ;;; adjustable.
186 ;;;
187 ;;; * END will refer to the ARRAY-TOTAL-SIZE of string, not
188 ;;; FILL-POINTER, since by definition the FILE-POSITION will always be
189 ;;; a FILL-POINTER, so that would be of limited use.
190 ;;;
191 ;;; * Rewinding the stream works with overwriting semantics.
192 ;;;
193 #+nil (let ((str (make-array 0
194                        :element-type 'character
195                        :adjustable nil
196                        :fill-pointer t)))
197   (with-output-to-string (stream str)
198     (princ "abcd" stream)
199     (assert (= 4 (file-position stream)))
200     (assert (file-position stream :start))
201     (assert (= 0 (file-position stream)))
202     (princ "0" stream)
203     (assert (= 1 (file-position stream)))
204     (file-position stream 2)
205     (assert (= 2 (file-position stream)))
206     (princ "2" stream)
207     (assert (file-position stream :end))
208     (assert (= 4 (file-position stream)))
209     (multiple-value-bind (val cond) (ignore-errors (file-position stream -1))
210       (assert (null val))
211       (assert (typep cond 'error)))
212     (multiple-value-bind (val cond) (ignore-errors (file-position stream 6))
213       (assert (null val))
214       (assert (typep cond 'error)))
215     (assert (equal "0b2d" str))))
216
217 (let ((str (make-array 0
218                        :element-type 'character
219                        :adjustable nil
220                        :fill-pointer t)))
221   (with-output-to-string (stream str)
222     (princ "abcd" stream)
223     (assert (= 4 (file-position stream)))
224     (assert (file-position stream :start))
225     (assert (= 0 (file-position stream)))
226     (princ "0" stream)
227     (assert (= 1 (file-position stream)))
228     (file-position stream 2)
229     (assert (= 2 (file-position stream)))
230     (princ "2" stream)
231     (assert (file-position stream :end))
232     (assert (= 4 (file-position stream)))
233     (assert (file-position stream 6))
234     (assert (file-position stream 4))
235     (assert (file-position stream :end))
236     (assert (= 6 (file-position stream)))
237     (assert (file-position stream 4))
238     (multiple-value-bind (val cond) (ignore-errors (file-position stream -1))
239       (assert (null val))
240       (assert (typep cond 'error)))
241     (princ "!!" stream)
242     (assert (equal "0b2d!!" str))))
243
244 ;;; MAKE-STRING-OUTPUT-STREAM and WITH-OUTPUT-TO-STRING take an
245 ;;; :ELEMENT-TYPE keyword argument
246 (macrolet ((frob (element-type-form)
247              `(progn
248                 (let ((s (with-output-to-string
249                            (s nil ,@(when element-type-form
250                                       `(:element-type ,element-type-form))))))
251                   (assert (typep s '(simple-array ,(if element-type-form
252                                                        (eval element-type-form)
253                                                        'character)
254                                                   (0)))))
255                 (get-output-stream-string
256                  (make-string-output-stream
257                   ,@(when element-type-form
258                       `(:element-type ,element-type-form)))))))
259   (frob nil)
260   (frob 'character)
261   (frob 'base-char)
262   (frob 'nil))
263
264 (with-open-file (s #-win32 "/dev/null" #+win32 "nul" :element-type '(signed-byte 48))
265   (assert (eq :eof (read-byte s nil :eof))))
266
267 (let* ((is (make-string-input-stream "foo"))
268        (os (make-string-output-stream))
269        (s (make-echo-stream is os))
270        (sequence (copy-seq "abcdef")))
271   (assert (= (read-sequence sequence s) 3))
272   (assert (string= sequence "foodef"))
273   (assert (string= (get-output-stream-string os) "foo")))
274
275 (let* ((is (make-string-input-stream "foo"))
276        (os (make-string-output-stream))
277        (s (make-echo-stream is os))
278        (sequence (copy-seq "abcdef")))
279   (assert (char= #\f (read-char s)))
280   (assert (= (read-sequence sequence s) 2))
281   (assert (string= sequence "oocdef"))
282   (assert (string= (get-output-stream-string os) "foo")))
283
284 (let* ((is (make-string-input-stream "foo"))
285        (os (make-string-output-stream))
286        (s (make-echo-stream is os))
287        (sequence (copy-seq "abcdef")))
288   (assert (char= #\f (read-char s)))
289   (unread-char #\f s)
290   (assert (= (read-sequence sequence s) 3))
291   (assert (string= sequence "foodef"))
292   (assert (string= (get-output-stream-string os) "foo")))
293
294 (with-standard-io-syntax
295   (open #-win32 "/dev/null" #+win32 "nul" ))
296
297 ;;; PEEK-CHAR T uses whitespace[2]
298 (let ((*readtable* (copy-readtable)))
299   (assert (char= (peek-char t (make-string-input-stream " a")) #\a))
300   (set-syntax-from-char #\Space #\a)
301   (assert (char= (peek-char t (make-string-input-stream " a")) #\Space)))
302
303 ;;; It is actually easier to run into the problem exercised by this
304 ;;; test with sockets, due to their delays between availabilities of
305 ;;; data.  However edgy the case may be for normal files, however,
306 ;;; there is still a case to be found in which CL:LISTEN answers
307 ;;; improperly.
308 ;;;
309 ;;; This test assumes that buffering is still done until a buffer of
310 ;;; SB-IMPL::+BYTES-PER-BUFFER+ bytes is filled up, that the buffer may
311 ;;; immediately be completely filled for normal files, and that the
312 ;;; buffer-fill routine is responsible for figuring out when we've
313 ;;; reached EOF.
314 (with-test (:name (stream listen-vs-select))
315   (let ((listen-testfile-name "stream.impure.lisp.testqfile")
316         ;; If non-NIL, size (in bytes) of the file that will exercise
317         ;; the LISTEN problem.
318         (bytes-per-buffer-sometime
319          (and (boundp 'sb-impl::+bytes-per-buffer+)
320               (symbol-value 'sb-impl::+bytes-per-buffer+))))
321     (when bytes-per-buffer-sometime
322       (unwind-protect
323            (progn
324              (with-open-file (stream listen-testfile-name
325                                      :direction :output :if-exists :error
326                                      :element-type '(unsigned-byte 8))
327                (dotimes (n bytes-per-buffer-sometime)
328                  (write-byte 113 stream)))
329              (with-open-file (stream listen-testfile-name
330                                      :direction :input :element-type '(unsigned-byte 8))
331                (dotimes (n bytes-per-buffer-sometime)
332                  (read-byte stream))
333                (assert (not (listen stream)))))
334         (ignore-errors (delete-file listen-testfile-name))))))
335
336 (with-test (:name :bug-395)
337   (let ((v (make-array 5 :fill-pointer 0 :element-type 'standard-char)))
338     (format v "foo")
339     (assert (equal (coerce "foo" 'base-string) v))))