X-Git-Url: http://repo.macrolet.net/gitweb/?a=blobdiff_plain;f=tests%2Fcompiler.pure.lisp;h=fb5d3e4b44c0924f9db0f7014f889b22c4bc0eb3;hb=fe240ce504041bfb181a81cb11b7b4bba112f65f;hp=41baa31d1dc652299e130a4519bf090aba7b4e9b;hpb=510a9c48b7a80bf89ee54bdbd92519e76e8e178d;p=sbcl.git diff --git a/tests/compiler.pure.lisp b/tests/compiler.pure.lisp index 41baa31..fb5d3e4 100644 --- a/tests/compiler.pure.lisp +++ b/tests/compiler.pure.lisp @@ -1,4 +1,4 @@ -;;;; various compiler tests without side-effects +;;;; various compiler tests without side effects ;;;; This software is part of the SBCL system. See the README file for ;;;; more information. @@ -85,3 +85,259 @@ (list x))))) (assert (null value)) (assert (typep error 'error))) + +;;; bug 169 (reported by Alexey Dejneka 2002-05-12, fixed by David +;;; Lichteblau 2002-05-21) +(progn + (multiple-value-bind (fun warnings-p failure-p) + (compile nil + ;; Compiling this code should cause a STYLE-WARNING + ;; about *X* looking like a special variable but not + ;; being one. + '(lambda (n) + (let ((*x* n)) + (funcall (symbol-function 'x-getter)) + (print *x*)))) + (assert (functionp fun)) + (assert warnings-p) + (assert (not failure-p))) + (multiple-value-bind (fun warnings-p failure-p) + (compile nil + ;; Compiling this code should not cause a warning + ;; (because the DECLARE turns *X* into a special + ;; variable as its name suggests it should be). + '(lambda (n) + (let ((*x* n)) + (declare (special *x*)) + (funcall (symbol-function 'x-getter)) + (print *x*)))) + (assert (functionp fun)) + (assert (not warnings-p)) + (assert (not failure-p)))) + +;;; a bug in 0.7.4.11 +(dolist (i '(a b 1 2 "x" "y")) + ;; In sbcl-0.7.4.11, the compiler tried to source-transform the + ;; TYPEP here but got confused and died, doing + ;; (ASSOC '(AND INTEGERP (SATISFIES PLUSP))) + ;; *BACKEND-TYPE-PREDICATES* + ;; :TEST #'TYPE=) + ;; and blowing up because TYPE= tried to call PLUSP on the + ;; characters of the MEMBER-TYPE representing STANDARD-CHAR. + (when (typep i '(and integer (satisfies oddp))) + (print i))) +(dotimes (i 14) + (when (typep i '(and integer (satisfies oddp))) + (print i))) + +;;; bug 156 (reported by APD sbcl-devel 2002-04-12, fixed by CSR patch +;;; sbcl-devel 2002-07-02): FUNCTION-LAMBDA-EXPRESSION of +;;; interactively-compiled functions was broken by sleaziness and +;;; confusion in the assault on 0.7.0, so this expression used to +;;; signal TYPE-ERROR when it found NIL instead of a DEBUG-SOURCE. +(eval '(function-lambda-expression #'(lambda (x) x))) + +;;; bug caught and fixed by Raymond Toy cmucl-imp 2002-07-10: &REST +;;; variable is not optional. +(assert (null (ignore-errors (eval '(funcall (lambda (&rest) 12)))))) + +;;; on the PPC, we got the magic numbers in undefined_tramp wrong for +;;; a while; fixed by CSR 2002-07-18 +(multiple-value-bind (value error) + (ignore-errors (some-undefined-function)) + (assert (null value)) + (assert (eq (cell-error-name error) 'some-undefined-function))) + +;;; Non-symbols shouldn't be allowed as VARs in lambda lists. (Where VAR +;;; is a variable name, as in section 3.4.1 of the ANSI spec.) +(assert (null (ignore-errors (eval '(lambda ("foo") 12))))) +(assert (ignore-errors (eval '(lambda (foo) 12)))) +(assert (null (ignore-errors (eval '(lambda (&optional 12) "foo"))))) +(assert (ignore-errors (eval '(lambda (&optional twelve) "foo")))) +(assert (null (ignore-errors (eval '(lambda (&optional (12 12)) "foo"))))) +(assert (ignore-errors (eval '(lambda (&optional (twelve 12)) "foo")))) +(assert (null (ignore-errors (eval '(lambda (&key #\c) "foo"))))) +(assert (ignore-errors (eval '(lambda (&key c) "foo")))) +(assert (null (ignore-errors (eval '(lambda (&key (#\c #\c)) "foo"))))) +(assert (ignore-errors (eval '(lambda (&key (c #\c)) "foo")))) +(assert (null (ignore-errors (eval '(lambda (&key ((#\c #\c) #\c)) "foo"))))) +(assert (ignore-errors (eval '(lambda (&key ((:c cbyanyothername) #\c)) "foo")))) + +;;; As reported and fixed by Antonio Martinez-Shotton sbcl-devel +;;; 2002-09-12, this failed in sbcl-0.7.7.23. (with failed AVER +;;; "(LEAF-HAS-SOURCE-NAME-P LEAF)") +(assert (= (funcall (eval `(lambda (x) (funcall ,(lambda (y) (+ y 3)) x))) 14) + 17)) + +;;; bug 181: bad type specifier dropped compiler into debugger +(assert (list (compile nil '(lambda (x) + (declare (type (0) x)) + x)))) + +(let ((f (compile nil '(lambda (x) + (make-array 1 :element-type '(0)))))) + (assert (null (ignore-errors (funcall f))))) + +;;; the following functions must not be flushable +(dolist (form '((make-sequence 'fixnum 10) + (concatenate 'fixnum nil) + (map 'fixnum #'identity nil) + (merge 'fixnum nil nil #'<))) + (assert (not (eval `(locally (declare (optimize (safety 0))) + (ignore-errors (progn ,form t))))))) + +(dolist (form '((values-list (car (list '(1 . 2)))) + (fboundp '(set bet)) + (atan #c(1 1) (car (list #c(2 2)))) + (nthcdr (car (list (floor (cos 3)))) '(1 2 3 4 5)) + (nthcdr (car (list 5)) '(1 2 . 3)))) + (assert (not (eval `(locally (declare (optimize (safety 3))) + (ignore-errors (progn ,form t))))))) + +;;; a bug in the MAP deftransform caused non-VECTOR array specifiers +;;; to cause errors in the compiler. Fixed by CSR in 0.7.8.10 +(assert (list (compile nil '(lambda (x) (map 'simple-array 'identity x))))) + +;;; bug 129: insufficient syntax checking in MACROLET +(multiple-value-bind (result error) + (ignore-errors (eval '(macrolet ((foo x `',x)) (foo 1 2 3)))) + (assert (null result)) + (assert (typep error 'error))) + +;;; bug 124: environment of MACROLET-introduced macro expanders +(assert (equal + (macrolet ((mext (x) `(cons :mext ,x))) + (macrolet ((mint (y) `'(:mint ,(mext y)))) + (list (mext '(1 2)) + (mint (1 2))))) + '((:MEXT 1 2) (:MINT (:MEXT 1 2))))) + +;;; bug 48c: SYMBOL-MACROLET should signal PROGRAM-ERROR if introduced +;;; symbol is declared to be SPECIAL +(multiple-value-bind (result error) + (ignore-errors (funcall (lambda () + (symbol-macrolet ((s '(1 2))) + (declare (special s)) + s)))) + (assert (null result)) + (assert (typep error 'program-error))) + +;;; ECASE should treat a bare T as a literal key +(multiple-value-bind (result error) + (ignore-errors (ecase 1 (t 0))) + (assert (null result)) + (assert (typep error 'type-error))) + +(multiple-value-bind (result error) + (ignore-errors (ecase 1 (t 0) (1 2))) + (assert (eql result 2)) + (assert (null error))) + +;;; FTYPE should accept any functional type specifier +(compile nil '(lambda (x) (declare (ftype function f)) (f x))) + +;;; FUNCALL of special operators and macros should signal an +;;; UNDEFINED-FUNCTION error +(multiple-value-bind (result error) + (ignore-errors (funcall 'quote 1)) + (assert (null result)) + (assert (typep error 'undefined-function)) + (assert (eq (cell-error-name error) 'quote))) +(multiple-value-bind (result error) + (ignore-errors (funcall 'and 1)) + (assert (null result)) + (assert (typep error 'undefined-function)) + (assert (eq (cell-error-name error) 'and))) + +;;; PSETQ should behave when given complex symbol-macro arguments +(multiple-value-bind (sequence index) + (symbol-macrolet ((x (aref a (incf i))) + (y (aref a (incf i)))) + (let ((a (copy-seq #(0 1 2 3 4 5 6 7 8 9))) + (i 0)) + (psetq x (aref a (incf i)) + y (aref a (incf i))) + (values a i))) + (assert (equalp sequence #(0 2 2 4 4 5 6 7 8 9))) + (assert (= index 4))) + +(multiple-value-bind (result error) + (ignore-errors + (let ((x (list 1 2))) + (psetq (car x) 3) + x)) + (assert (null result)) + (assert (typep error 'program-error))) + +;;; COPY-SEQ should work on known-complex vectors: +(assert (equalp #(1) + (let ((v (make-array 0 :fill-pointer 0))) + (vector-push-extend 1 v) + (copy-seq v)))) + +;;; to support INLINE functions inside MACROLET, it is necessary for +;;; FUNCTION-LAMBDA-EXPRESSION to return a proper lambda expression in +;;; certain circumstances, one of which is when compile is called from +;;; top-level. +(assert (equal + (function-lambda-expression + (compile nil '(lambda (x) (block nil (print x))))) + '(lambda (x) (block nil (print x))))) + +;;; bug 62: too cautious type inference in a loop +(assert (nth-value + 2 + (compile nil + '(lambda (a) + (declare (optimize speed (safety 0))) + (typecase a + (array (loop (print (car a))))))))) + +;;; Bug reported by Robert E. Brown sbcl-devel 2003-02-02: compiler +;;; failure +(compile nil + '(lambda (key tree collect-path-p) + (let ((lessp (key-lessp tree)) + (equalp (key-equalp tree))) + (declare (type (function (t t) boolean) lessp equalp)) + (let ((path '(nil))) + (loop for node = (root-node tree) + then (if (funcall lessp key (node-key node)) + (left-child node) + (right-child node)) + when (null node) + do (return (values nil nil nil)) + do (when collect-path-p + (push node path)) + (when (funcall equalp key (node-key node)) + (return (values node path t)))))))) + +;;; CONSTANTLY should return a side-effect-free function (bug caught +;;; by Paul Dietz' test suite) +(let ((i 0)) + (let ((fn (constantly (progn (incf i) 1)))) + (assert (= i 1)) + (assert (= (funcall fn) 1)) + (assert (= i 1)) + (assert (= (funcall fn) 1)) + (assert (= i 1)))) + +;;; Bug 240 reported by tonyms on #lisp IRC 2003-02-25 (modified version) +(loop for (fun warns-p) in + '(((lambda (&optional *x*) *x*) t) + ((lambda (&optional *x* &rest y) (values *x* y)) t) + ((lambda (&optional *print-base*) (values *print-base*)) nil) + ((lambda (&optional *print-base* &rest y) (values *print-base* y)) nil) + ((lambda (&optional *x*) (declare (special *x*)) (values *x*)) nil) + ((lambda (&optional *x* &rest y) (declare (special *x*)) (values *x* y)) nil)) + for real-warns-p = (nth-value 1 (compile nil fun)) + do (assert (eq warns-p real-warns-p))) + +;;; Bug reported by Gilbert Baumann on #lisp IRC 2003-03-26 +(assert (equal (funcall (eval '(lambda (x &optional (y (pop x))) (list x y))) + '(1 2)) + '((2) 1))) + +;;; Bug reported by Paul Dietz on cmucl-imp and fixed by Gerd +;;; Moellmann: CONVERT-MORE-CALL failed on the following call +(assert (eq (eval '((lambda (&key) 'u) :allow-other-keys nil)) 'u))