Add call-with-stack-overflow-handler tests
[bpt/guile.git] / test-suite / tests / reader.test
1 ;;;; reader.test --- Reader test. -*- coding: iso-8859-1; mode: scheme -*-
2 ;;;;
3 ;;;; Copyright (C) 1999, 2001, 2002, 2003, 2007, 2008, 2009, 2010, 2011,
4 ;;;; 2013, 2014 Free Software Foundation, Inc.
5 ;;;; Jim Blandy <jimb@red-bean.com>
6 ;;;;
7 ;;;; This library is free software; you can redistribute it and/or
8 ;;;; modify it under the terms of the GNU Lesser General Public
9 ;;;; License as published by the Free Software Foundation; either
10 ;;;; version 3 of the License, or (at your option) any later version.
11 ;;;;
12 ;;;; This library is distributed in the hope that it will be useful,
13 ;;;; but WITHOUT ANY WARRANTY; without even the implied warranty of
14 ;;;; MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU
15 ;;;; Lesser General Public License for more details.
16 ;;;;
17 ;;;; You should have received a copy of the GNU Lesser General Public
18 ;;;; License along with this library; if not, write to the Free Software
19 ;;;; Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301 USA
20
21 (define-module (test-suite reader)
22 :use-module (srfi srfi-1)
23 :use-module (test-suite lib))
24
25
26 (define exception:eof
27 (cons 'read-error "end of file$"))
28 (define exception:unexpected-rparen
29 (cons 'read-error "unexpected \")\"$"))
30 (define exception:unexpected-rsqbracket
31 (cons 'read-error "unexpected \"]\"$"))
32 (define exception:unterminated-block-comment
33 (cons 'read-error "unterminated `#. \\.\\.\\. .#' comment$"))
34 (define exception:unknown-character-name
35 (cons 'read-error "unknown character name .*$"))
36 (define exception:unknown-sharp-object
37 (cons 'read-error "Unknown # object: .*$"))
38 (define exception:eof-in-string
39 (cons 'read-error "end of file in string constant$"))
40 (define exception:eof-in-symbol
41 (cons 'read-error "end of file while reading symbol$"))
42 (define exception:illegal-escape
43 (cons 'read-error "illegal character in escape sequence: .*$"))
44 (define exception:missing-expression
45 (cons 'read-error "no expression after #;"))
46 (define exception:mismatched-paren
47 (cons 'read-error "mismatched close paren"))
48
49
50 (define (read-string s)
51 (with-input-from-string s (lambda () (read))))
52
53 (define (with-read-options opts thunk)
54 (let ((saved-options (read-options)))
55 (dynamic-wind
56 (lambda ()
57 (read-options opts))
58 thunk
59 (lambda ()
60 (read-options saved-options)))))
61
62 \f
63 (with-test-prefix "reading"
64 (pass-if "0"
65 (equal? (read-string "0") 0))
66 (pass-if "1++i"
67 (equal? (read-string "1++i") '1++i))
68 (pass-if "1+i+i"
69 (equal? (read-string "1+i+i") '1+i+i))
70 (pass-if "1+e10000i"
71 (equal? (read-string "1+e10000i") '1+e10000i))
72 (pass-if "-nan.0-1i"
73 (not (equal? (imag-part (read-string "-nan.0-1i"))
74 (imag-part (read-string "-nan.0+1i")))))
75
76 (pass-if-equal "'\|' in string literals"
77 "a|b"
78 (read-string "\"a\\|b\""))
79
80 (pass-if-equal "#\\escape"
81 '(a #\esc b)
82 (read-string "(a #\\escape b)"))
83
84 (pass-if-equal "#true"
85 '(a #t b)
86 (read-string "(a #true b)"))
87
88 (pass-if-equal "#false"
89 '(a #f b)
90 (read-string "(a #false b)"))
91
92 ;; At one time the arg list for "Unknown # object: ~S" didn't make it out
93 ;; of read.c. Check that `format' can be applied to this error.
94 (pass-if "error message on bad #"
95 (catch #t
96 (lambda ()
97 (read-string "#ZZZ")
98 ;; oops, this # is supposed to be unrecognised
99 #f)
100 (lambda (key subr message args rest)
101 (apply format #f message args)
102 ;; message and args are ok
103 #t)))
104
105 (pass-if "block comment"
106 (equal? '(+ 1 2 3)
107 (read-string "(+ 1 #! this is a\ncomment !# 2 3)")))
108
109 (pass-if "block comment finishing s-exp"
110 (equal? '(+ 2)
111 (read-string "(+ 2 #! a comment\n!#\n) ")))
112
113 (pass-if "R6RS lexeme comment"
114 (equal? '(+ 1 2 3)
115 (read-string "(+ 1 #!r6rs 2 3)")))
116
117 (pass-if "partial R6RS lexeme comment"
118 (equal? '(+ 1 2 3)
119 (read-string "(+ 1 #!r6r !# 2 3)")))
120
121 (pass-if "R6RS/SRFI-30 block comment"
122 (equal? '(+ 1 2 3)
123 (read-string "(+ 1 #| this is a\ncomment |# 2 3)")))
124
125 (pass-if "R6RS/SRFI-30 nested block comment"
126 (equal? '(a b c)
127 (read-string "(a b c #| d #| e |# f |#)")))
128
129 (pass-if "R6RS/SRFI-30 nested block comment (2)"
130 (equal? '(a b c)
131 (read-string "(a b c #|||||||#)")))
132
133 (pass-if "R6RS/SRFI-30 nested block comment (3)"
134 (equal? '(a b c)
135 (read-string "(a b c #||||||||#)")))
136
137 (pass-if "R6RS/SRFI-30 block comment syntax overridden"
138 ;; To be compatible with 1.8 and earlier, we should be able to override
139 ;; this syntax.
140 (with-fluids ((%read-hash-procedures (fluid-ref %read-hash-procedures)))
141 (read-hash-extend #\| (lambda args 'not))
142 (fold (lambda (x y result)
143 (and result (eq? x y)))
144 #t
145 (read-string "(this is #| a comment)")
146 `(this is not a comment))))
147
148 (pass-if "unprintable symbol"
149 ;; The reader tolerates unprintable characters for symbols.
150 (equal? (string->symbol "\x01\x02\x03")
151 (read-string "\x01\x02\x03")))
152
153 (pass-if "CR recognized as a token delimiter"
154 ;; In 1.8.3, character 0x0d was not recognized as a delimiter.
155 (equal? (read-string "one\x0dtwo") 'one))
156
157 (pass-if "returned strings are mutable"
158 ;; Per R5RS Section 3.4, "Storage Model", `read' is supposed to return
159 ;; mutable objects.
160 (let ((str (with-input-from-string "\"hello, world\"" read)))
161 (string-set! str 0 #\H)
162 (string=? str "Hello, world")))
163
164 (pass-if "square brackets are parens"
165 (equal? '() (read-string "[]")))
166
167 (pass-if-exception "paren mismatch" exception:unexpected-rparen
168 (read-string "'[)"))
169
170 (pass-if-exception "paren mismatch (2)" exception:unexpected-rsqbracket
171 (read-string "'(]"))
172
173 (pass-if-exception "paren mismatch (3)" exception:mismatched-paren
174 (read-string "'(foo bar]"))
175
176 (pass-if-exception "paren mismatch (4)" exception:mismatched-paren
177 (read-string "'[foo bar)")))
178
179
180 \f
181 (pass-if-exception "radix passed to number->string can't be zero"
182 exception:out-of-range
183 (number->string 10 0))
184 (pass-if-exception "radix passed to number->string can't be one either"
185 exception:out-of-range
186 (number->string 10 1))
187
188 \f
189 (with-test-prefix "mismatching parentheses"
190 (pass-if-exception "opening parenthesis"
191 exception:eof
192 (read-string "("))
193 (pass-if-exception "closing parenthesis following mismatched opening"
194 exception:unexpected-rparen
195 (read-string ")"))
196 (pass-if-exception "closing square bracket following mismatched opening"
197 exception:unexpected-rsqbracket
198 (read-string "]"))
199 (pass-if-exception "opening vector parenthesis"
200 exception:eof
201 (read-string "#("))
202 (pass-if-exception "closing parenthesis following mismatched vector opening"
203 exception:unexpected-rparen
204 (read-string ")")))
205
206 \f
207 (with-test-prefix "exceptions"
208
209 ;; Reader exceptions: although they are not documented, they may be relied
210 ;; on by some programs, hence these tests.
211
212 (pass-if-exception "unterminated block comment"
213 exception:unterminated-block-comment
214 (read-string "(+ 1 #! comment\n..."))
215 (pass-if-exception "R6RS/SRFI-30 unterminated nested block comment"
216 exception:unterminated-block-comment
217 (read-string "(foo #| bar #| |#)"))
218 (pass-if-exception "unknown character name"
219 exception:unknown-character-name
220 (read-string "#\\theunknowncharacter"))
221 (pass-if-exception "unknown sharp object"
222 exception:unknown-sharp-object
223 (read-string "#?"))
224 (pass-if-exception "eof in string"
225 exception:eof-in-string
226 (read-string "\"the string that never ends"))
227 (pass-if-exception "illegal escape in string"
228 exception:illegal-escape
229 (read-string "\"some string \\???\"")))
230
231 \f
232 (with-test-prefix "read-options"
233 (pass-if "case-sensitive"
234 (not (eq? 'guile 'GuiLe)))
235 (pass-if "case-insensitive"
236 (eq? 'guile
237 (with-read-options '(case-insensitive)
238 (lambda ()
239 (read-string "GuiLe")))))
240 (pass-if-equal "r7rs-symbols"
241 (list 'a (string->symbol "Hello, this is | a \"test\"") 'b)
242 (with-read-options '(r7rs-symbols)
243 (lambda ()
244 (read-string "(a |H\\x65;llo, this is \\| a \"test\"| b)"))))
245 (pass-if "prefix keywords"
246 (eq? #:keyword
247 (with-read-options '(keywords prefix case-insensitive)
248 (lambda ()
249 (read-string ":KeyWord")))))
250 (pass-if "prefix non-keywords"
251 (symbol? (with-read-options '(keywords prefix)
252 (lambda ()
253 (read-string "srfi88-keyword:")))))
254 (pass-if "postfix keywords"
255 (eq? #:keyword
256 (with-read-options '(keywords postfix)
257 (lambda ()
258 (read-string "keyword:")))))
259 (pass-if "long postfix keywords"
260 (eq? #:keyword0123456789012345678901234567890123456789012345678901234567890123456789012345678901234567890123456789012345678901234567890123456789
261 (with-read-options '(keywords postfix)
262 (lambda ()
263 (read-string "keyword0123456789012345678901234567890123456789012345678901234567890123456789012345678901234567890123456789012345678901234567890123456789:")))))
264 (pass-if "`:' is not a postfix keyword (per SRFI-88)"
265 (eq? ':
266 (with-read-options '(keywords postfix)
267 (lambda ()
268 (read-string ":")))))
269 (pass-if "no positions"
270 (let ((sexp (with-read-options '()
271 (lambda ()
272 (read-string "(+ 1 2 3)")))))
273 (and (not (source-property sexp 'line))
274 (not (source-property sexp 'column)))))
275 (pass-if "positions"
276 (let ((sexp (with-read-options '(positions)
277 (lambda ()
278 (read-string "(+ 1 2 3)")))))
279 (and (equal? (source-property sexp 'line) 0)
280 (equal? (source-property sexp 'column) 0))))
281 (pass-if "positions on quote"
282 (let ((sexp (with-read-options '(positions)
283 (lambda ()
284 (read-string "'abcde")))))
285 (and (equal? (source-property sexp 'line) 0)
286 (equal? (source-property sexp 'column) 0))))
287 (pass-if "position of SCSH block comment"
288 ;; In Guile 2.0.0 the reader would not update the port's position
289 ;; when reading an SCSH block comment.
290 (let ((sexp (with-read-options '(positions)
291 (lambda ()
292 (read-string "#!foo\nbar\nbaz\n!#\n(hello world)\n")))))
293 (= 4 (source-property sexp 'line))))
294
295 (with-test-prefix "r6rs-hex-escapes"
296 (pass-if-exception "non-hex char in two-digit hex-escape"
297 exception:illegal-escape
298 (with-read-options '(r6rs-hex-escapes)
299 (lambda ()
300 (with-input-from-string "\"\\x0g;\"" read))))
301
302 (pass-if-exception "non-hex char in four-digit hex-escape"
303 exception:illegal-escape
304 (with-read-options '(r6rs-hex-escapes)
305 (lambda ()
306 (with-input-from-string "\"\\x000g;\"" read))))
307
308 (pass-if-exception "non-hex char in six-digit hex-escape"
309 exception:illegal-escape
310 (with-read-options '(r6rs-hex-escapes)
311 (lambda ()
312 (with-input-from-string "\"\\x00000g;\"" read))))
313
314 (pass-if-exception "no semicolon at termination of one-digit hex-escape"
315 exception:illegal-escape
316 (with-read-options '(r6rs-hex-escapes)
317 (lambda ()
318 (with-input-from-string "\"\\x0\"" read))))
319
320 (pass-if-exception "no semicolon at termination of three-digit hex-escape"
321 exception:illegal-escape
322 (with-read-options '(r6rs-hex-escapes)
323 (lambda ()
324 (with-input-from-string "\"\\x000\"" read))))
325
326 (pass-if "two-digit hex escape"
327 (eqv?
328 (with-read-options '(r6rs-hex-escapes)
329 (lambda ()
330 (string-ref (with-input-from-string "\"--\\xff;--\"" read) 2)))
331 (integer->char #xff)))
332
333 (pass-if "four-digit hex escape"
334 (eqv?
335 (with-read-options '(r6rs-hex-escapes)
336 (lambda ()
337 (string-ref (with-input-from-string "\"--\\x0100;--\"" read) 2)))
338 (integer->char #x0100)))
339
340 (pass-if "six-digit hex escape"
341 (eqv?
342 (with-read-options '(r6rs-hex-escapes)
343 (lambda ()
344 (string-ref (with-input-from-string "\"--\\x010300;--\"" read) 2)))
345 (integer->char #x010300)))
346
347 (pass-if "escaped characters match non-escaped ASCII characters"
348 (string=?
349 (with-read-options '(r6rs-hex-escapes)
350 (lambda ()
351 (with-input-from-string "\"\\x41;\\x0042;\\x000043;\"" read)))
352 "ABC"))
353
354 (pass-if "write R6RS string escapes"
355 (let* ((s1 (apply string
356 (map integer->char '(#x8 ; backspace
357 #x18 ; cancel
358 #x20 ; space
359 #x30 ; zero
360 #x40 ; at sign
361 ))))
362 (s2 (with-read-options '(r6rs-hex-escapes)
363 (lambda ()
364 (with-output-to-string
365 (lambda () (write s1)))))))
366 (lset= eqv?
367 (string->list s2)
368 (list #\" #\\ #\b #\\ #\x #\1 #\8 #\; #\space #\0 #\@ #\"))))
369
370 (pass-if "display R6RS string escapes"
371 (string=?
372 (with-read-options '(r6rs-hex-escapes)
373 (lambda ()
374 (let ((pt (open-output-string))
375 (s1 (apply string (map integer->char
376 '(#xFF #x100 #xFFF #x1000 #xFFFF #x10000)))))
377 (set-port-encoding! pt "ASCII")
378 (set-port-conversion-strategy! pt 'escape)
379 (display s1 pt)
380 (get-output-string pt))))
381 "\\xff;\\x100;\\xfff;\\x1000;\\xffff;\\x10000;"))
382
383 (pass-if "one-digit hex escape"
384 (eqv? (with-input-from-string "#\\xA" read)
385 (integer->char #x0A)))
386
387 (pass-if "two-digit hex escape"
388 (eqv? (with-input-from-string "#\\xFF" read)
389 (integer->char #xFF)))
390
391 (pass-if "four-digit hex escape"
392 (eqv? (with-input-from-string "#\\x00FF" read)
393 (integer->char #xFF)))
394
395 (pass-if "eight-digit hex escape"
396 (eqv? (with-input-from-string "#\\x00006587" read)
397 (integer->char #x6587)))
398
399 (pass-if "write R6RS escapes"
400 (string=?
401 (with-read-options '(r6rs-hex-escapes)
402 (lambda ()
403 (with-output-to-string
404 (lambda ()
405 (write (integer->char #x80))))))
406 "#\\x80")))
407
408 (with-test-prefix "hungry escapes"
409 (pass-if "default not hungry"
410 ;; Assume default setting of not hungry.
411 (equal? (with-input-from-string "\"foo\\\n bar\""
412 read)
413 "foo bar"))
414 (pass-if "hungry"
415 (dynamic-wind
416 (lambda ()
417 (read-enable 'hungry-eol-escapes))
418 (lambda ()
419 (equal? (with-input-from-string "\"foo\\\n bar\""
420 read)
421 "foobar"))
422 (lambda ()
423 (read-disable 'hungry-eol-escapes))))))
424
425 (with-test-prefix "per-port-read-options"
426 (pass-if "case-sensitive"
427 (equal? '(guile GuiLe gUIle)
428 (with-read-options '(case-insensitive)
429 (lambda ()
430 (with-input-from-string "GUIle #!no-fold-case GuiLe gUIle"
431 (lambda ()
432 (list (read) (read) (read))))))))
433 (pass-if "case-insensitive"
434 (equal? '(GUIle guile guile)
435 (with-input-from-string "GUIle #!fold-case GuiLe gUIle"
436 (lambda ()
437 (list (read) (read) (read)))))))
438
439 (with-test-prefix "#;"
440 (for-each
441 (lambda (pair)
442 (pass-if (car pair)
443 (equal? (with-input-from-string (car pair) read) (cdr pair))))
444
445 '(("#;foo 10". 10)
446 ("#;(10 20 30) foo" . foo)
447 ("#; (10 20 30) foo" . foo)
448 ("#;\n10\n20" . 20)))
449
450 (pass-if "#;foo"
451 (eof-object? (with-input-from-string "#;foo" read)))
452
453 (pass-if-exception "#;"
454 exception:missing-expression
455 (with-input-from-string "#;" read))
456 (pass-if-exception "#;("
457 exception:eof
458 (with-input-from-string "#;(" read)))
459
460 (with-test-prefix "#'"
461 (for-each
462 (lambda (pair)
463 (pass-if (car pair)
464 (equal? (with-input-from-string (car pair) read) (cdr pair))))
465
466 '(("#'foo". (syntax foo))
467 ("#`foo" . (quasisyntax foo))
468 ("#,foo" . (unsyntax foo))
469 ("#,@foo" . (unsyntax-splicing foo)))))
470
471 (with-test-prefix "#{}#"
472 (pass-if (equal? (read-string "#{}#") '#{}#))
473 (pass-if (not (equal? (read-string "(a #{.}# b)") '(a . b))))
474 (pass-if (equal? (read-string "#{a}#") 'a))
475 (pass-if (equal? (read-string "#{a b}#") '#{a b}#))
476 (pass-if-exception "#{" exception:eof-in-symbol
477 (read-string "#{"))
478 (pass-if (equal? (read-string "#{a\\x20;b}#") '#{a b}#)))
479
480 (begin-deprecated
481 (with-test-prefix "deprecated #{}# escapes"
482 (pass-if (equal? (read-string "#{a\\ b}#") '#{a b}#))))
483
484 ;;; Local Variables:
485 ;;; eval: (put 'with-read-options 'scheme-indent-function 1)
486 ;;; End: