From: Bruno Haible
Subject: ANSI CL compliant or not?
Date: 
Message-ID: <6l0u9n$iv1@news.u-bordeaux.fr>
Recently I condensed the "Exceptional Situations" specifications
present in ANSI CL into a test suite. The test suite has 337 items.

Then I ran the testsuite in a widely available Common Lisp implementation,
which contains the symbol :ANSI-CL in *features*, therefore "purports to
conform" to the ANSI CL standard. "Purports to conform" is a term defined
in ANSI CL as meaning "makes a good-faith claim of conformance".

In this implementation, 155 tests failed, which is 46%.

Just for comparison, I ran the testsuite in CLISP version 1997-12-06, an
implementation which does _not_ (yet) purport to conform to ANSI CL.
82 tests failed, which is 24%.

You find below a non-exhaustive list of the conformance failures of the
first mentioned implementation. How far is the term "good-faith claim of
conformance" stretchable?

                             Bruno

=============================================================================
The tests were run with
(proclaim '(optimize (safety 3)))
(declaim (optimize (safety 3)))
i.e. in "safe code" (term of ANSI CL section 1.4.2). Therefore ANSI CL
mandates errors in the places where ANSI CL mentions "an error is signaled"
or "an error should be signaled".

Summary:
  Wrong results:              4 conformance failures
  Error instead of results:   3 conformance failures
  Missing error checking:    60 conformance failures
  Wrong error type:          80 conformance failures
Total:                      147 conformance failures

----------------------------- Wrong results ---------------------------------

(let* ((x (coerce 7821/17071 'single-float))
       (y (read-from-string (prin1-to-string x))))
  (list (rational x)
        (prin1-to-string x)
        (eql x y)
        (rational y)
        (prin1-to-string y)))
returns:
  (1921601/4194304 "0.45814538" NIL 15372807/33554432 "0.45814535")
The correct result would be:
  (1921601/4194304 "0.45814538" T 1921601/4194304 "0.45814538")
On average, print-read-consistency is violated for 10.7% of the
single-float numbers and for 9.3% of the double-float numbers.

(let ((x double-float-epsilon)
      (y (coerce (/ 4505798650626049 (ash 1 105)) 'double-float)))
  (list (= (float 1 x) (+ (float 1 x) x))
        (= (float 1 y) (+ (float 1 y) y))
        (< 0 y x)))
returns (NIL NIL T). ANSI CL section DOUBLE-FLOAT-EPSILON does not allow this.

(search '(#\A #\B #\C #\D) "0ABIABJBCBC" :end1 2 :start2 0 :from-end t)
returns 3. The correct result would be 4.

(let ((package (make-package "LOOP-TEST")))
  (intern "blah" package)
  (let ((blah2 (intern "blah2" package)))
    (export blah2 package)
  )
  (sort 
    (loop for sym being each present-symbol of package 
          for sym-name = (symbol-name sym)
          collect sym-name
    )
    #'string<
) )
returns just ("blah"). The correct result, according to ANSI CL section
6.1.2.1.7, would be ("blah" "blah2") or ("blah2" "blah").

---------------------- Error instead of results -----------------------------

(coerce '(a b c) '(vector * 3))
signals an error instead of returning #(A B C).

(acosh -1)
signals an error instead of returning #c(0.0 3.1415927).

(loop with (a b) float = '(1.0 2.0)
      and (c d) of-type integer = '(3 4)
      and (e f)
      return (list a b c d e f))
signals an error instead of returning (1.0 2.0 3 4 NIL NIL).

----------------------- Missing error checking ------------------------------

(progn
  (defgeneric foo02 (x))
  (defmethod foo02 ((x number)) t)
  (let ((m (find-method #'foo02 nil (list (find-class 'number)))))
    (remove-method #'foo02 m)
    (defgeneric foo03 (x))
    (add-method #'foo03 m)
) )
signals no error. ANSI CL section ADD-METHOD specifies that "an error of
type ERROR is signaled".

(alpha-char-p 33)
signals no error. ANSI CL section ALPHA-CHAR-P specifies that it "should
signal an error of type TYPE-ERROR".

(alphanumericp 33)
signals no error. ANSI CL section ALPHANUMERICP specifies that it "should
signal an error of type TYPE-ERROR".

(array-displacement '(x))
returns nil and 0. ANSI CL section ARRAY-DISPLACEMENT specifies that it
"should signal an error of type TYPE-ERROR".

(boole boole-set 5 #c(-3 4))
returns -1. ANSI CL section BOOLE specifies that it "should signal
TYPE-ERROR".

(both-case-p 33)
signals no error. ANSI CL section BOTH-CASE-P specifies that it "should
signal an error of type TYPE-ERROR".

(butlast '(a b c) -1)
signals no error. ANSI CL section BUTLAST specifies that it "should
signal an error of type TYPE-ERROR".

(progn
  (defgeneric foo04 (x))
  (defmethod foo04 ((x real)) 'ok)
  (defmethod foo04 ((x integer)) (call-next-method (sqrt x)))
  (foo04 -1))
(progn
  (defgeneric foo041 (x))
  (defmethod foo041 ((x real)) 'ok)
  (defmethod foo041 ((x integer)) (call-next-method (sqrt x)))
  (foo04 2))
signal no error. ANSI CL section CALL-NEXT-METHOD specifies that "an error
of type ERROR should be signaled".

(character "abc")
(character "")
signal no error. ANSI CL section CHARACTERS specifies that it "should
signal an error of type TYPE-ERROR".

(character 33)
signals no error. ANSI CL section CHARACTERS specifies that it "should
signal an error of type TYPE-ERROR", because a "character designator"
is a character, a string of length 1, or a symbol whose print-name has
length 1.

(coerce '(a b c) '(vector t 4))
(coerce '#(a b c) '(vector t 4))
(coerce '#(#\a #\b #\c) '(string 2))
(coerce '(0 1) '(simple-bit-vector 3))
signal no error. ANSI CL section COERCE specifies that "an error of type
TYPE-ERROR should be signaled".

(concatenate '(string 3) "ab" "cd")
signals no error. ANSI CL section CONCATENATE specifies that "an error of
type TYPE-ERROR should be signaled".

(defclass foo05 () (a b a))
signals no error. ANSI CL section DEFCLASS specifies: "If there are any
duplicate slot names, an error of type PROGRAM-ERROR is signaled."

(defclass foo06 () (a b) (:default-initargs x a x b))
signals no error. ANSI CL section DEFCLASS specifies: "If an initialization
argument name appears more than once in :default-initargs class option,
an error of type PROGRAM-ERROR is signaled."

(defclass foo07 () ((a :allocation :class :allocation :class)))
signals no error. ANSI CL section DEFCLASS specifies: "If any of the
following slot options appears more than once in a single slot description,
an error of type program-error is signaled: :allocation, :initform, :type,
:documentation."

(defclass foo09 () ((a :type real :type real)))
signals no error. ANSI CL section DEFCLASS specifies: "If any of the
following slot options appears more than once in a single slot description,
an error of type program-error is signaled: :allocation, :initform, :type,
:documentation."

(defclass foo10 () ((a :documentation "bla" :documentation "blabla")))
signals no error. ANSI CL section DEFCLASS specifies: "If any of the
following slot options appears more than once in a single slot description,
an error of type program-error is signaled: :allocation, :initform, :type,
:documentation."

(progn
  (defvar foo16)
  (define-symbol-macro foo16 t))
signals no error. ANSI CL section DEFINE-SYMBOL-MACRO specifies that
"an error of type PROGRAM-ERROR is signaled".

(defpackage "FOO25" (:shadow "IF") (:intern "IF"))
signals no error. ANSI CL section DEFPACKAGE specifies:
"The collection of symbol-name arguments given to the options :shadow,
:intern, :import-from, and :shadowing-import-from must all be disjoint;
additionally, the symbol-name arguments given to :export and :intern must
be disjoint. Disjoint in this context is defined as no two of the
symbol-names being string= with each other. If either condition is violated,
an error of type PROGRAM-ERROR should be signaled."

(defpackage "FOO27" (:shadow "IF") (:shadowing-import-from "USER" "IF"))
signals no error. ANSI CL section DEFPACKAGE specifies:
"The collection of symbol-name arguments given to the options :shadow,
:intern, :import-from, and :shadowing-import-from must all be disjoint;
additionally, the symbol-name arguments given to :export and :intern must
be disjoint. Disjoint in this context is defined as no two of the
symbol-names being string= with each other. If either condition is violated,
an error of type PROGRAM-ERROR should be signaled."

(defpackage "FOO28" (:intern "IF") (:import-from "USER" "IF"))
signals no error. ANSI CL section DEFPACKAGE specifies:
"The collection of symbol-name arguments given to the options :shadow,
:intern, :import-from, and :shadowing-import-from must all be disjoint;
additionally, the symbol-name arguments given to :export and :intern must
be disjoint. Disjoint in this context is defined as no two of the
symbol-names being string= with each other. If either condition is violated,
an error of type PROGRAM-ERROR should be signaled."

(defpackage "FOO29" (:intern "IF") (:shadowing-import-from "USER" "IF"))
signals no error. ANSI CL section DEFPACKAGE specifies:
"The collection of symbol-name arguments given to the options :shadow,
:intern, :import-from, and :shadowing-import-from must all be disjoint;
additionally, the symbol-name arguments given to :export and :intern must
be disjoint. Disjoint in this context is defined as no two of the
symbol-names being string= with each other. If either condition is violated,
an error of type PROGRAM-ERROR should be signaled."

(defpackage "FOO30"
  (:import-from "USER" "IF") (:shadowing-import-from "USER" "IF"))
signals no error. ANSI CL section DEFPACKAGE specifies:
"The collection of symbol-name arguments given to the options :shadow,
:intern, :import-from, and :shadowing-import-from must all be disjoint;
additionally, the symbol-name arguments given to :export and :intern must
be disjoint. Disjoint in this context is defined as no two of the
symbol-names being string= with each other. If either condition is violated,
an error of type PROGRAM-ERROR should be signaled."

(defstruct foo32 a system::a)
(progn
  (defstruct foo33 a)
  (defstruct (foo34 (:include foo33)) system::a))
signal no error. ANSI CL section DEFSTRUCT specifies: "If any two slot
names (whether present directly or inherited by the :include option) are
the same under string=, defstruct should signal an error of type
PROGRAM-ERROR."

(elt "abc" 4)
returns #\null. ANSI CL section ELT specifies that it "should signal an
error of type TYPE-ERROR".

(elt '(a b c) 4)
signals no error. ANSI CL section ELT specifies that it "should signal an
error of type TYPE-ERROR".

(every '(lambda (x) x) nil)
signals no error. ANSI CL section EVERY specifies that it "should signal
TYPE-ERROR if its first argument is neither a symbol nor a function".

(fboundp '(psetf aref))
signals no error. ANSI CL section FBOUNDP specifies that it "should signal
an error of type TYPE-ERROR".

(file-author "*")
signals no error. ANSI CL section FILE-AUTHOR specifies: "An error of type
FILE-ERROR is signaled if pathspec is wild."

(let ((filename "/tmp/foo35.tmp"))
  (close (open filename :direction :output
                        :if-exists :overwrite
                        :if-does-not-exist :create))
  (with-open-file (s filename :direction :input)
    (file-position s (+ (file-length s) 1000))))
signals no error. ANSI CL section FILE-POSITION specifies that "an error is
signaled".

(file-write-date "*")
signals no error. ANSI CL section FILE-WRITE-DATE specifies: "An error of
type FILE-ERROR is signaled if pathspec is wild."

(float-radix 2/3)
signals no error.  ANSI CL section FLOAT-RADIX specifies that it "should
signal an error".

(gentemp 't)
signals no error. ANSI CL section GENTEMP specifies that it "should signal
an error of type TYPE-ERROR".

(last '(a b c) -1)
returns nil. ANSI CL section LAST specifies that it "should signal an error
of type TYPE-ERROR".

(lower-case-p 33)
signals no error. ANSI CL section LOWER-CASE-P specifies that it "should
signal an error of type TYPE-ERROR".

(make-broadcast-stream (make-string-input-stream "abc"))
signals no error. ANSI CL section MAKE-BROADCAST-STREAM specifies that it
"should signal an error of type TYPE-ERROR".

(make-concatenated-stream (make-string-output-stream))
signals no error. ANSI CL section MAKE-CONCATENATED-STREAM specifies that it
"should signal an error of type TYPE-ERROR".

(make-sequence '(string 3) 4)
signals no error, just a warning. ANSI CL section MAKE-SEQUENCE specifies
that "an error of type TYPE-ERROR should be signaled".

(make-two-way-stream (make-string-input-stream "abc")
                     (make-string-input-stream "def"))
signals no error. ANSI CL section MAKE-TWO-WAY-STREAM specifies that it
"should signal an error of type TYPE-ERROR".

(make-two-way-stream (make-string-output-stream) (make-string-output-stream))
signals no error. ANSI CL section MAKE-TWO-WAY-STREAM specifies that it
"should signal an error of type TYPE-ERROR".

(map '(string 3) #'identity "ab")
signals no error. ANSI CL section MAP specifies that "an error of type
TYPE-ERROR should be signaled".

(merge '(vector t 5) '(3 1) '(2 4) #'<)
signals no error. ANSI CL section MERGE specifies that "an error of type
TYPE-ERROR should be signaled".

(nbutlast '(a b c) -1)
signals no error. ANSI CL section NBUTLAST specifies that it "should
signal an error of type TYPE-ERROR".

(notany '(lambda (x) x) nil)
signals no error. ANSI CL section NOTANY specifies that it "should signal
TYPE-ERROR if its first argument is neither a symbol nor a function".

(notevery '(lambda (x) x) nil)
signals no error. ANSI CL section NOTEVERY specifies that it "should signal
TYPE-ERROR if its first argument is neither a symbol nor a function".

(nthcdr 2 '(a . b))
returns 88375296. ANSI CL sections NTHCDR and CDR specify that it "should
signal TYPE-ERROR".

(parse-namestring (coerce (list #\f #\o #\o (code-char 0) #\4 #\8) 'string))
signals no error. ANSI CL section PARSE-NAMESTRING specifies that "an error
of type PARSE-ERROR is signaled if thing does not consist entirely of the
representation of a pathname", and #\Null is not a valid character in
pathnames in currently existing operating systems.

(parse-namestring "foo48:a" (logical-pathname "foo49:"))
signals no error. ANSI CL section PARSE-NAMESTRING specifies: "If thing
is a logical pathname namestring and if the host portion of the namestring
and host are both present and do not match, an error of type ERROR is
signaled."

(peek-char nil (make-string-input-stream "") nil nil t)
signals no error. ANSI CL section PEEK-CHAR specifies: "If recursive-p
is true and an end of file occurs, an error of type END-OF-FILE is signaled."

(let ((x (make-string-output-stream)))
  (pprint-logical-block (x nil :prefix 24)))
signals no error. ANSI CL section PPRINT-LOGICAL-BLOCK specifies: "An error
of type TYPE-ERROR is signaled if any of the :suffix, :prefix, or
:per-line-prefix is supplied but does not evaluate to a string."

(let ((x (make-string-output-stream)))
  (pprint-logical-block (x nil :prefix "a" :per-line-prefix "b")))
signals no error, just a warning. ANSI CL section PPRINT-LOGICAL-BLOCK
specifies: "An error is signaled if :prefix and :pre-line-prefix are both
used."

(probe-file "*")
signals no error. ANSI CL section PROBE-FILE specifies that "an error of
type FILE-ERROR is signaled if pathspec is wild."

(read-byte (pathname "foo50"))
signals an error of SYNCHRONOUS-OPERATING-SYSTEM-SIGNAL (segmentation
violation). ANSI CL section READ-BYTE specifies that it "should signal
an error of type TYPE-ERROR".

(read-sequence (list 1 2 3) (make-string-input-stream "") :end -1)
signals no error. ANSI CL section READ-SEQUENCE specifies that it
"should signal an error of type TYPE-ERROR".

(some '(lambda (x) x) nil)
signals no error. ANSI CL section SOME specifies that it "should signal
TYPE-ERROR if its first argument is neither a symbol nor a function".

(special-operator-p '(and x y))
(special-operator-p '(setf aref))
signals no error. ANSI CL section SPECIAL-OPERATOR-P specifies that it
"should signal TYPE-ERROR".

(symbol-macrolet ((foo58 t)) (declare (special foo58)))
signals no error. ANSI CL section SYMBOL-MACROLET specifies that "an error
of type PROGRAM-ERROR is signaled".

(upper-case-p 33)
signals no error. ANSI CL section UPPER-CASE-P specifies that it "should
signal an error of type TYPE-ERROR".

(write-byte 1 (pathname "foo67"))
signals an error of SYNCHRONOUS-OPERATING-SYSTEM-SIGNAL (segmentation
violation). ANSI CL section WRITE-BYTE specifies that it "should signal
an error of type TYPE-ERROR".

(write-sequence '(#\1 #\2 #\3) (make-string-output-stream) :end -1)
signals no error. ANSI CL section WRITE-SEQUENCE specifies that it
"should signal an error of type TYPE-ERROR".

-------------------------- Wrong error type ---------------------------------

(atan #c(0.0 0.4) 3.4)
signals an error of type ARITHMETIC-ERROR. ANSI CL section ATAN specifies
that it "should signal TYPE-ERROR".

(butlast '#(a b c))
signals an error of type SIMPLE-ERROR (moreover, with a bogus error message).
ANSI CL section BUTLAST specifies that it "should signal an error of type
TYPE-ERROR".

(car 'x)
(cdr '#(a b c))
(cdadar '((x y)))
signal errors of type SIMPLE-ERROR. ANSI CL section CAR/CDR specifies that it
"should signal TYPE-ERROR".

(clear-output '*terminal-io*)
signals an error of type PROGRAM-ERROR. ANSI CL section CLEAR-OUTPUT
specifies that it "should signal an error of type TYPE-ERROR".

(coerce "foo" '(string 2))
signals an error of type SIMPLE-ERROR. ANSI CL section COERCE specifies that
"an error of type TYPE-ERROR should be signaled".

(coerce nil 'nil)
signals an error of type SIMPLE-ERROR. ANSI CL section COERCE specifies that
"an error of type TYPE-ERROR should be signaled".

(copy-pprint-dispatch 'x)
signals an error of type SIMPLE-ERROR. ANSI CL section COPY-PPRINT-DISPATCH
specifies that it "should signal an error of type TYPE-ERROR".

(copy-seq 'x)
signals an error of type SIMPLE-ERROR. ANSI CL section COPY-SEQ specifies
that it "should be prepared to signal an error of type TYPE-ERROR".

(copy-symbol #\x)
signals an error of type SIMPLE-ERROR. ANSI CL section COPY-SYMBOL specifies
that it "should signal an error of type TYPE-ERROR".

(count #\x 'x)
signals an error of type SIMPLE-ERROR. ANSI CL section COUNT specifies
that it "should be prepared to signal an error of type TYPE-ERROR".

(defgeneric foo15 (x)
  (:my-option t))
signals an error of type CASE-FAILURE, subtype of TYPE-ERROR. ANSI CL
section DEFCLASS specifies: "It is required that all implementations
signal an error of type PROGRAM-ERROR if they observe a class option
or a slot option that is not implemented locally."

(defpackage "FOO22" (:size 20) (:size 20))
signals an error of type PACKAGE-ERROR. ANSI CL section DEFPACKAGE specifies
that "an error of type PROGRAM-ERROR should be signaled".

(defpackage "FOO23" (:documentation "bla"))
signals an error instead of creating package FOO23.

(defpackage "FOO23" (:documentation "bla") (:documentation "blabla"))
signals an error of type PACKAGE-ERROR. ANSI CL section DEFPACKAGE specifies
that "an error of type PROGRAM-ERROR should be signaled".

(defpackage "FOO24" (:my-option t))
signals an error of type PACKAGE-ERROR. ANSI CL section DEFPACKAGE specifies
that "an error of type PROGRAM-ERROR should be signaled if an option is
present that is not actually supported in the host implementation."

(defpackage "FOO26" (:shadow "IF") (:import-from "USER" "IF"))
signals an error of type PACKAGE-ERROR. ANSI CL section DEFPACKAGE specifies:
"The collection of symbol-name arguments given to the options :shadow,
:intern, :import-from, and :shadowing-import-from must all be disjoint;
additionally, the symbol-name arguments given to :export and :intern must
be disjoint. Disjoint in this context is defined as no two of the
symbol-names being string= with each other. If either condition is violated,
an error of type PROGRAM-ERROR should be signaled."

(defpackage "FOO31" (:export "IF") (:intern "IF"))
signals an error of type PACKAGE-ERROR. ANSI CL section DEFPACKAGE specifies:
"The collection of symbol-name arguments given to the options :shadow,
:intern, :import-from, and :shadowing-import-from must all be disjoint;
additionally, the symbol-name arguments given to :export and :intern must
be disjoint. Disjoint in this context is defined as no two of the
symbol-names being string= with each other. If either condition is violated,
an error of type PROGRAM-ERROR should be signaled."

(delete-duplicates 'abba)
signals an error of type SIMPLE-ERROR. ANSI CL section DELETE-DUPLICATES
specifies that it "should signal an error of type TYPE-ERROR".

(disassemble #x123456)
signals an error of type SIMPLE-ERROR. ANSI CL section DISASSEMBLE specifies
that it "should signal an error of type TYPE-ERROR".

(elt 'x 0)
signals an error of type SIMPLE-ERROR. ANSI CL section ELT specifies
that it "should be prepared to signal an error of type TYPE-ERROR".

(elt '#(a b c) 4)
(elt (make-array 3 :fill-pointer 3 :adjustable t) 4)
signal an error of type SIMPLE-ERROR. ANSI CL section ELT specifies
that it "should signal an error of type TYPE-ERROR".

(endp 'x)
signals an error of type SIMPLE-ERROR. ANSI CL section ENDP specifies
that it "should signal an error of type TYPE-ERROR".

(every #'identity 'x)
signals an error of type SIMPLE-ERROR. ANSI CL section EVERY specifies
that it "should signal TYPE-ERROR".

(fdefinition '(psetf aref))
signals an error of type SIMPLE-ERROR. ANSI CL section FDEFINITION specifies
that it "should signal an error of type TYPE-ERROR".

(fdefinition '#:nonexistent)
signals an error of type SIMPLE-ERROR. ANSI CL section FDEFINITION specifies
that "an error of type UNDEFINED-FUNCTION is signaled".

(file-length *terminal-io*)
signals an error of type STREAM-ERROR. ANSI CL section FILE-LENGTH specifies
that it "should signal an error of type TYPE-ERROR".

(fill 'x #\x)
signals an error of type SIMPLE-ERROR. ANSI CL section FILL specifies
that it "should be prepared to signal an error of type TYPE-ERROR".

(fill (make-list 3) 'x :start nil)
signals an error of type SIMPLE-ERROR. ANSI CL section FILL specifies
that it "should signal an error of type TYPE-ERROR".

(fill (make-list 3) 'x :start -1)
signals an error of type SIMPLE-ERROR. ANSI CL section FILL specifies
that it "should signal an error of type TYPE-ERROR".

(fill (make-list 3) 'x :start 1 :end -1)
signals an error of type SIMPLE-ERROR. ANSI CL section FILL specifies
that it "should signal an error of type TYPE-ERROR".

(fill-pointer "abc")
signals an error of type SIMPLE-ERROR. ANSI CL section FILL-POINTER
specifies that it "should signal an error of type TYPE-ERROR".

(find #\x 'x)
signals an error of type SIMPLE-ERROR. ANSI CL section FIND specifies
that it "should be prepared to signal an error of type TYPE-ERROR".

(finish-output '*terminal-io*)
signals an error of type PROGRAM-ERROR. ANSI CL section FINISH-OUTPUT
specifies that it "should signal an error of type TYPE-ERROR".

(fmakunbound '(psetf aref))
signals an error of type SIMPLE-ERROR. ANSI CL section FMAKUNBOUND specifies
that it "should signal an error of type TYPE-ERROR".

(force-output '*terminal-io*)
signals an error of type PROGRAM-ERROR. ANSI CL section FORCE-OUTPUT
specifies that it "should signal an error of type TYPE-ERROR".

(funcall 'and)
signals an error of type PROGRAM-ERROR. ANSI CL section FUNCALL specifies
that "an error of type UNDEFINED-FUNCTION should be signaled".

(gentemp "X" 24)
signals an error of type PACKAGE-ERROR. ANSI CL section GENTEMP specifies
that it "should signal an error of type TYPE-ERROR".

(get "a" 'x)
signals an error of type SIMPLE-ERROR. ANSI CL section GET specifies that
it "should signal an error of type TYPE-ERROR".

(input-stream-p (pathname "abc"))
signals an error of type PROGRAM-ERROR. ANSI CL section INPUT-STREAM-P
specifies that it "should signal an error of type TYPE-ERROR".

(isqrt -1)
(isqrt #c(3 4))
signal an error of type SIMPLE-ERROR. ANSI CL section ISQRT specifies
that it "should signal TYPE-ERROR".

(length 'x)
signals an error of type SIMPLE-ERROR. ANSI CL section LENGTH specifies
that it "should signal TYPE-ERROR".

(list-length 'x)
(list-length '(x . y))
signal an error of type SIMPLE-ERROR. ANSI CL section LIST-LENGTH specifies
that it "should signal an error of type TYPE-ERROR".

(logbitp -1 5)
signal an error of type SIMPLE-ERROR. ANSI CL section LOGBITP specifies
that it "should signal an error of type TYPE-ERROR".

(make-list -1)
signals an error of type SIMPLE-ERROR. ANSI CL section MAKE-LIST specifies
that it "should signal an error of type TYPE-ERROR".

(make-random-state 'x)
signals an error of type SIMPLE-ERROR. ANSI CL section MAKE-RANDOM-STATE
specifies that it "should signal an error of type TYPE-ERROR".

(make-sequence 'x 5)
(make-sequence 'sequence 5)
signal an error of type SIMPLE-ERROR. ANSI CL section MAKE-SEQUENCE
specifies that "an error of type TYPE-ERROR must be signaled".

(map 'x #'identity "abc")
signal an error of type SIMPLE-ERROR. ANSI CL section MAP specifies that
"an error of type TYPE-ERROR must be signaled".

(nbutlast '#(a b c))
signals an error of type SIMPLE-ERROR (moreover, with a bogus error message).
ANSI CL section NBUTLAST specifies that it "should signal an error of type
TYPE-ERROR".

(notany #'identity 'x)
signals an error of type SIMPLE-ERROR. ANSI CL section NOTANY specifies
that it "should signal TYPE-ERROR".

(notevery #'identity 'x)
signals an error of type SIMPLE-ERROR. ANSI CL section NOTEVERY specifies
that it "should signal TYPE-ERROR".

(open-stream-p (pathname "foo45"))
signals an error of type PROGRAM-ERROR. ANSI CL section OPEN-STREAM-P
specifies that it "should signal an error of type TYPE-ERROR".

(output-stream-p (pathname "foo46"))
signals an error of type PROGRAM-ERROR. ANSI CL section OUTPUT-STREAM-P
specifies that it "should signal an error of type TYPE-ERROR".

(package-name 47)
signals an error of type PACKAGE-ERROR. ANSI CL section PACKAGE-NAME
specifies that it "should signal an error of type TYPE-ERROR".

(package-nicknames (pathname "foo47"))
signals an error of type PACKAGE-ERROR. ANSI CL section PACKAGE-NICKNAMES
specifies that it "should signal an error of type TYPE-ERROR".

(package-shadowing-symbols (vector 'a 'b 'c))
signals an error of type PACKAGE-ERROR. ANSI CL section
PACKAGE-SHADOWING-SYMBOLS specifies that it "should signal an error of type
TYPE-ERROR".

(package-use-list (list 'a 'b 'c))
signals an error of type PACKAGE-ERROR. ANSI CL section PACKAGE-USE-LIST
specifies that it "should signal an error of type TYPE-ERROR".

(package-used-by-list (list 'a 'b 'c))
signals an error of type PACKAGE-ERROR. ANSI CL section PACKAGE-USED-BY-LIST
specifies that it "should signal an error of type TYPE-ERROR".

(pprint-newline :fresh)
signals an error of type SIMPLE-ERROR. ANSI CL section PPRINT-NEWLINE
specifies that "an error of type TYPE-ERROR is signaled".

(random -2.3)
signals an error of type SIMPLE-ERROR. ANSI CL section RANDOM specifies
that it "should signal an error of type TYPE-ERROR".

(read-sequence (list 1 2 3) (make-string-input-stream "") :start nil)
signals an error of type SIMPLE-ERROR. ANSI CL section READ-SEQUENCE
specifies that it "should signal an error of type TYPE-ERROR".

(setf (readtable-case *readtable*) ':unknown)
signals an error of type SIMPLE-ERROR. ANSI CL section READTABLE-CASE
specifies that it "should signal an error of type TYPE-ERROR".

(remove #\x 'x)
signals an error of type SIMPLE-ERROR. ANSI CL section REMOVE specifies
that it "should be prepared to signal an error of type TYPE-ERROR".

(remove-duplicates 'abba)
signals an error of type SIMPLE-ERROR. ANSI CL section REMOVE-DUPLICATES
specifies that it "should signal an error of type TYPE-ERROR".

(remprop 55 'abc)
signals an error of type SIMPLE-ERROR. ANSI CL section REMPROP specifies
that it "should signal an error of type TYPE-ERROR".

(rplaca nil 5)
signals an error of type SIMPLE-ERROR. ANSI CL section RPLACA specifies
that it "should signal an error of type TYPE-ERROR".

(rplacd nil 5)
signals an error of type SIMPLE-ERROR. ANSI CL section RPLACD specifies
that it "should signal an error of type TYPE-ERROR".

(sleep -1)
signals an error of type SIMPLE-ERROR. ANSI CL section SLEEP specifies
that it "should signal an error of type TYPE-ERROR".

(some #'identity 'x)
signals an error of type SIMPLE-ERROR. ANSI CL section SOME specifies
that it "should signal TYPE-ERROR".

(stream-element-type '*terminal-io)
signals an error of type PROGRAM-ERROR. ANSI CL section STREAM-ELEMENT-TYPE
specifies that it "should signal an error of type TYPE-ERROR".

(symbol-function 33)
signals an error of type SIMPLE-ERROR. ANSI CL section SYMBOL-FUNCTION
specifies that it "should signal an error of type TYPE-ERROR".

(symbol-function ':compile)
signals an error of type SIMPLE-ERROR. ANSI CL section SYMBOL-FUNCTION
specifies that it "should signal UNDEFINED-FUNCTION".

(symbol-name '(setf foo59))
signals an error of type SIMPLE-ERROR. ANSI CL section SYMBOL-NAME
specifies that it "should signal an error of type TYPE-ERROR".

(symbol-package '(setf foo59))
signals an error of type SIMPLE-ERROR. ANSI CL section SYMBOL-PACKAGE
specifies that it "should signal an error of type TYPE-ERROR".

(symbol-plist '(setf foo59))
signals an error of type SIMPLE-ERROR. ANSI CL section SYMBOL-PLIST
specifies that it "should signal an error of type TYPE-ERROR".

(symbol-value '(setf foo59))
signals an error of type SIMPLE-ERROR. ANSI CL section SYMBOL-VALUE
specifies that it "should signal an error of type TYPE-ERROR".

(translate-logical-pathname (make-broadcast-stream))
signals an error of type STREAM-ERROR. ANSI CL section
TRANSLATE-LOGICAL-PATHNAME specifies that "an error of type TYPE-ERROR
is signaled".

(translate-logical-pathname (logical-pathname "foo61:"))
signals an error of type SIMPLE-ERROR. ANSI CL section
TRANSLATE-LOGICAL-PATHNAME specifies that "an error of type TYPE-ERROR
is signaled".

(values-list '(a b . c))
signals an error of type SIMPLE-ERROR, with a bogus error message. ANSI CL
section VALUES-LIST specifies that it "should signal TYPE-ERROR".

(vector-pop "foo67")
signals an error of type SIMPLE-ERROR. ANSI CL section VECTOR-POP specifies
that "an error of type TYPE-ERROR is signaled".

(write-sequence '(#\1 #\2 #\3) (make-string-output-stream) :start nil)
signals an error of type SIMPLE-ERROR. ANSI CL section WRITE-SEQUENCE
specifies that it "should signal an error of type TYPE-ERROR".

=============================================================================

From: Larry Hunter
Subject: Re: ANSI CL compliant or not?
Date: 
Message-ID: <rbiumkdiwy.fsf@work.nlm.nih.gov>
Bruno Haible says:

  Recently I condensed the "Exceptional Situations" specifications present
  in ANSI CL into a test suite. The test suite has 337 items.  Then I ran
  the testsuite in a widely available Common Lisp implementation ...  In
  this implementation, 155 tests failed, which is 46%.

Having run a bunch of the examples he provided in ACL 4.3 on SGI Irix 6.2
(with all current patches), almost all seem to cause the problem he found,
so I imagine he is talking about Franz ACL.   

Two questions:

 1.  Bruno, will you make this test suite available on some ftp site?  It
     seems like a useful community resource.

 2.  Does anyone have an ACL 5.0 beta that they would care to run the suite
     on?  Does anyone from Franz have any comments?

Thanks for doing this, Bruno.  I think it's very valuable.

Regards,

Larry 

-- 
Lawrence Hunter, PhD.
National Library of Medicine               phone: +1 (301) 496-9303
Bldg. 38A, 9th fl, MS-54                   fax:   +1 (301) 496-0673
Bethesda. MD 20894 USA                     email: ······@nlm.nih.gov
From: Bruno Haible
Subject: Re: ANSI CL compliant or not?
Date: 
Message-ID: <6l3ijf$13k@news.u-bordeaux.fr>
Larry Hunter <······@nlm.nih.gov> wrote:
>
> 1.  Bruno, will you make this test suite available on some ftp site?  It
>     seems like a useful community resource.

Good idea. The test suite is available at
http://clisp.cons.org/~haible/cltests/.

             Bruno