[version 0.11.0 ediware**20070309060017] { hunk ./CHANGELOG 1 +Version 0.11.0 +2007-03-09 +Re-factoring of how encoding errors are handled (patch by Anton Vodonosov) + hunk ./CHANGELOG 16 -Fixed the last changed (thanks to Red Daly) +Fixed the last change (thanks to Red Daly) hunk ./doc/index.html 59 +
*use-replacement-char*
hunk ./doc/index.html 89
- *provide-use-value-restart*
hunk ./doc/index.html 223
-current version is 0.10.3.
+current version is 0.11.0.
hunk ./doc/index.html 247
+
+Luís Oliveira maintains a darcs
+repository of FLEXI-STREAMS
+at http://common-lisp.net/~loliveira/ediware/.
+
+
+
+
*PROVIDE-USE-VALUE-RESTART*
and *USE-REPLACEMENT-CHAR*
.
+
+
+The code now behaves as if
+*PROVIDE-USE-VALUE-RESTART*
is always T
.
+Instead of *USE-REPLACEMENT-CHAR*
, you can use
+*SUBSTITUTION-CHAR*
or
+invoke
+a USE-VALUE
+restart
+when a FLEXI-STREAM-ENCODING-ERROR
+is signaled.
hunk ./doc/index.html 714
-
-
-
[Special variable]
-
*use-replacement-char*
-
-
- -
-If this value is true (the default isNIL
) and an unknown octet is encountered while reading with an 8-bit encoding, the replacement character (65533) is returned instead of signalling an error. hunk ./doc/index.html 723 -This substitution will only happen if*PROVIDE-USE-VALUE-RESTART*
is true, though. hunk ./doc/index.html 731 - -CL-USER 2 > (setq*provide-use-value-restart*
t) -T hunk ./doc/index.html 732 -CL-USER 3 > (foo) +CL-USER 2 > (foo) hunk ./doc/index.html 741 -CL-USER 4 : 1 > :c +CL-USER 3 : 1 > :c hunk ./doc/index.html 751 -CL-USER 5 : 1 > :c +CL-USER 4 : 1 > :c hunk ./doc/index.html 756 -CL-USER 6 > (handler-bind ((flexi-stream-encoding-error (lambda (condition) +CL-USER 5 > (handler-bind ((flexi-stream-encoding-error (lambda (condition) hunk ./doc/index.html 762 -CL-USER 7 > (let ((*substitution-char* #\?)) +CL-USER 6 > (let ((*substitution-char* #\?)) hunk ./doc/index.html 767 -
[Special variable]
-
*provide-use-value-restart*
-
-
-WhetherREAD-CHAR
-for flexi streams should provide a -USE-VALUE
-restart in case an encoding error is encountered. This is not -done by default because it entails a performance penalty. hunk ./doc/index.html 787 -All errors related to encoding problems with flexi streams are of this type. (This includes situation where an end of file is encountered in the middle of a multi-octet character.) This is a subtype ofFLEXI-STREAM-ERROR
. +All errors related to encoding problems with flexi streams are of this type. (This includes situation where an end of file is encountered in the middle of a multi-octet character.) When this condition is signaled during reading,USE-VALUE
+restart is provided. See also*SUBSTITUTION-CHAR*
and example for it.FLEXI-STREAM-ENCODING-ERROR
is a subtype ofFLEXI-STREAM-ERROR
. hunk ./doc/index.html 1018 -Thanks to David Lichteblau for numerous portability patches. Thanks to Igor Plekhov for the KOI8-R code. +Thanks to David Lichteblau for numerous portability patches. Thanks +to Igor Plekhov for the KOI8-R code. Thanks to Anton Vodonosov for +numerous patches and additions. hunk ./doc/index.html 1023 -$Header: /usr/local/cvsrep/flexi-streams/doc/index.html,v 1.86 2007/02/19 07:48:02 edi Exp $ +$Header: /usr/local/cvsrep/flexi-streams/doc/index.html,v 1.89 2007/03/09 01:16:58 edi Exp $ hunk ./flexi-streams.asd 2 -;;; $Header: /usr/local/cvsrep/flexi-streams/flexi-streams.asd,v 1.51 2007/02/19 07:48:00 edi Exp $ +;;; $Header: /usr/local/cvsrep/flexi-streams/flexi-streams.asd,v 1.52 2007/03/09 01:14:27 edi Exp $ hunk ./flexi-streams.asd 38 - :version "0.10.3" + :version "0.11.0" hunk ./input.lisp 2 -;;; $Header: /usr/local/cvsrep/flexi-streams/input.lisp,v 1.45 2007/01/01 23:46:49 edi Exp $ +;;; $Header: /usr/local/cvsrep/flexi-streams/input.lisp,v 1.46 2007/03/09 01:14:27 edi Exp $ hunk ./input.lisp 138 - "Helper macro to define methods for STREAM-READ-CHAR. Defines -a method for the class STREAM-CLASS using the variable STREAM-VAR -and the code body BODY wrapped with some standard code common to -all methods defined here." - (with-unique-names (char char-code line body-fn) + "Helper macro to define methods for STREAM-READ-CHAR. Defines a +method for the class STREAM-CLASS using the variable STREAM-VAR and +the code body BODY wrapped with some standard code common to all +methods defined here. The return value of BODY is a character code. +Note: In case of encoding problems, BODY must return the value +returned by \(RECOVER-FROM-ENCODING-ERROR ...)." + (with-unique-names (char-code body-fn) hunk ./input.lisp 160 - (cond (*provide-use-value-restart* - (restart-case - (handler-bind ((flexi-stream-encoding-error - (lambda (condition) - (declare (ignore condition)) - (when *substitution-char* - (use-value *substitution-char*))))) - (,body-fn)) - (use-value (,char) - :report "Specify a character to be used instead." - :interactive (lambda () - (loop - (format *query-io* "Type a character: ") - (let ((,line (read-line *query-io*))) - (when (= 1 (length ,line)) - (return (list (char ,line 0))))))) - (char-code ,char)))) - (t (,body-fn)))))) - (when (eq ,char-code :eof) - (return-from stream-read-char :eof)) + (,body-fn)))) hunk ./input.lisp 166 +(defun recover-from-encoding-error (flexi-stream format-control &rest format-args) + "Helper function used by the STREAM-READ-CHAR methods below to deal +with encoding errors. Checks if *SUBSTITUTION-CHAR* is not NIL and +returns its character code in this case. Otherwise signals a +FLEXI-STREAM-ENCODING-ERROR as determined by the arguments to this +function and provides a corresponding USE-VALUE restart." + (when *substitution-char* + (return-from recover-from-encoding-error (char-code *substitution-char*))) + (restart-case + (apply #'signal-encoding-error flexi-stream format-control format-args) + (use-value (char) + :report "Specify a character to be used instead." + :interactive (lambda () + (loop + (format *query-io* "Type a character: ") + (let ((line (read-line *query-io*))) + (when (= 1 (length line)) + (return (list (char line 0))))))) + (char-code char)))) + hunk ./input.lisp 194 - (when (> octet 127) - (signal-encoding-error stream "No character which corresponds to octet #x~X." octet)) - octet)) + (if (> octet 127) + (recover-from-encoding-error stream "No character which corresponds to octet #x~X." octet) + octet))) hunk ./input.lisp 205 - (when (or (null char-code) - (and (= char-code 65533) - (not *use-replacement-char*))) - (signal-encoding-error stream "No character which corresponds to octet #x~X." octet)) - char-code))) + (if (or (null char-code) + (= char-code 65533)) + (recover-from-encoding-error stream "No character which corresponds to octet #x~X." octet) + char-code)))) hunk ./input.lisp 211 - (let (first-octet-seen) - (flet ((read-next-byte () - (prog1 - (or (read-byte* stream) - (cond (first-octet-seen - (signal-encoding-error stream "End of file while in UTF-8 sequence.")) - (t (return-from stream-read-char :eof)))) - (setq first-octet-seen t)))) - (declare (inline read-next-byte) (dynamic-extent (function read-next-byte))) - (let ((octet (read-next-byte))) - (declare (type octet octet)) - (multiple-value-bind (start count) - (cond ((zerop (logand octet #b10000000)) - (values octet 0)) - ((= #b11000000 (logand octet #b11100000)) - (values (logand octet #b00011111) 1)) - ((= #b11100000 (logand octet #b11110000)) - (values (logand octet #b00001111) 2)) - ((= #b11110000 (logand octet #b11111000)) - (values (logand octet #b00000111) 3)) - ((= #b11111000 (logand octet #b11111100)) - (values (logand octet #b00000011) 4)) - ((= #b11111100 (logand octet #b11111110)) - (values (logand octet #b00000001) 5)) - (t (signal-encoding-error stream "Unexpected value #x~X at start of UTF-8 sequence." - octet))) - ;; note that we currently don't check for "overlong" - ;; sequences or other illegal values - (loop for result of-type (unsigned-byte 32) + (block body + (let (first-octet-seen) + (flet ((read-next-byte () + (prog1 + (or (read-byte* stream) + (cond (first-octet-seen + (return-from body + (recover-from-encoding-error stream + "End of file while in UTF-8 sequence."))) + (t (return-from stream-read-char :eof)))) + (setq first-octet-seen t)))) + (declare (inline read-next-byte) (dynamic-extent (function read-next-byte))) + (let ((octet (read-next-byte))) + (declare (type octet octet)) + (multiple-value-bind (start count) + (cond ((zerop (logand octet #b10000000)) + (values octet 0)) + ((= #b11000000 (logand octet #b11100000)) + (values (logand octet #b00011111) 1)) + ((= #b11100000 (logand octet #b11110000)) + (values (logand octet #b00001111) 2)) + ((= #b11110000 (logand octet #b11111000)) + (values (logand octet #b00000111) 3)) + ((= #b11111000 (logand octet #b11111100)) + (values (logand octet #b00000011) 4)) + ((= #b11111100 (logand octet #b11111110)) + (values (logand octet #b00000001) 5)) + (t (return-from body + (recover-from-encoding-error stream + "Unexpected value #x~X at start of UTF-8 sequence." + octet)))) + ;; note that we currently don't check for "overlong" + ;; sequences or other illegal values + (loop for result of-type (unsigned-byte 32) hunk ./input.lisp 247 - repeat count - for octet of-type octet = (read-next-byte) - unless (= #b10000000 (logand octet #b11000000)) - do (signal-encoding-error stream "Unexpected value #x~X in UTF-8 sequence." octet) - finally (return result))))))) + repeat count + for octet of-type octet = (read-next-byte) + unless (= #b10000000 (logand octet #b11000000)) + do (return-from body + (recover-from-encoding-error stream + "Unexpected value #x~X in UTF-8 sequence." octet)) + finally (return result)))))))) hunk ./input.lisp 256 - (let (first-octet-seen) - (labels ((read-next-byte () + (block body + (let (first-octet-seen) + (labels ((read-next-byte () + (prog1 + (or (read-byte* stream) + (cond (first-octet-seen + (return-from body + (recover-from-encoding-error stream + "End of file while in UTF-16 sequence."))) + (t (return-from stream-read-char :eof)))) + (setq first-octet-seen t))) + (read-next-word () + (+ (the octet (read-next-byte)) + (ash (the octet (read-next-byte)) 8)))) + (declare (inline read-next-byte read-next-word) + (dynamic-extent (function read-next-byte) (function read-next-word))) + (let ((word (read-next-word))) + (cond ((<= #xd800 word #xdfff) + (let ((next-word (read-next-word))) + (unless (<= #xdc00 next-word #xdfff) + (return-from body + (recover-from-encoding-error stream "Unexpected UTF-16 word #x~X following #x~X." + next-word word))) + (+ (ash (logand #b1111111111 word) 10) + (logand #b1111111111 next-word) + #x10000))) + (t word))))))) + +(define-char-reader (stream flexi-utf-16-be-input-stream) + (block body + (let (first-octet-seen) + (labels ((read-next-byte () + (prog1 + (or (read-byte* stream) + (cond (first-octet-seen + (return-from body + (recover-from-encoding-error stream + "End of file while in UTF-16 sequence."))) + (t (return-from stream-read-char :eof)))) + (setq first-octet-seen t))) + (read-next-word () + (+ (ash (the octet (read-next-byte)) 8) + (the octet (read-next-byte))))) + (let ((word (read-next-word))) + (cond ((<= #xd800 word #xdfff) + (let ((next-word (read-next-word))) + (unless (<= #xdc00 next-word #xdfff) + (return-from body + (recover-from-encoding-error stream "Unexpected UTF-16 word #x~X following #x~X." + next-word word))) + (+ (ash (logand #b1111111111 word) 10) + (logand #b1111111111 next-word) + #x10000))) + (t word))))))) + +(define-char-reader (stream flexi-utf-32-le-input-stream) + (block body + (let (first-octet-seen) + (flet ((read-next-byte () hunk ./input.lisp 318 - (signal-encoding-error stream "End of file while in UTF-16 sequence.")) + (return-from body + (recover-from-encoding-error stream + "End of file while in UTF-32 sequence."))) hunk ./input.lisp 322 - (setq first-octet-seen t))) - (read-next-word () - (+ (the octet (read-next-byte)) - (ash (the octet (read-next-byte)) 8)))) - (declare (inline read-next-byte read-next-word) - (dynamic-extent (function read-next-byte) (function read-next-word))) - (let ((word (read-next-word))) - (cond ((<= #xd800 word #xdfff) - (let ((next-word (read-next-word))) - (unless (<= #xdc00 next-word #xdfff) - (signal-encoding-error stream "Unexpected UTF-16 word #x~X following #x~S." - next-word word)) - (+ (ash (logand #b1111111111 word) 10) - (logand #b1111111111 next-word) - #x10000))) - (t word)))))) + (setq first-octet-seen t)))) + (declare (inline read-next-byte) (dynamic-extent (function read-next-byte))) + (loop for count from 0 to 24 by 8 + for octet of-type octet = (read-next-byte) + sum (ash octet count)))))) hunk ./input.lisp 328 -(define-char-reader (stream flexi-utf-16-be-input-stream) - (let (first-octet-seen) - (labels ((read-next-byte () +(define-char-reader (stream flexi-utf-32-be-input-stream) + (block body + (let (first-octet-seen) + (flet ((read-next-byte () hunk ./input.lisp 335 - (signal-encoding-error stream "End of file while in UTF-16 sequence.")) + (return-from body + (recover-from-encoding-error stream + "End of file while in UTF-32 sequence."))) hunk ./input.lisp 339 - (setq first-octet-seen t))) - (read-next-word () - (+ (ash (the octet (read-next-byte)) 8) - (the octet (read-next-byte))))) - (let ((word (read-next-word))) - (cond ((<= #xd800 word #xdfff) - (let ((next-word (read-next-word))) - (unless (<= #xdc00 next-word #xdfff) - (signal-encoding-error stream "Unexpected UTF-16 word #x~X following #x~S." - next-word word)) - (+ (ash (logand #b1111111111 word) 10) - (logand #b1111111111 next-word) - #x10000))) - (t word)))))) - -(define-char-reader (stream flexi-utf-32-le-input-stream) - (let (first-octet-seen) - (flet ((read-next-byte () - (prog1 - (or (read-byte* stream) - (cond (first-octet-seen - (signal-encoding-error stream "End of file while in UTF-32 sequence.")) - (t (return-from stream-read-char :eof)))) - (setq first-octet-seen t)))) - (declare (inline read-next-byte) (dynamic-extent (function read-next-byte))) - (loop for count from 0 to 24 by 8 - for octet of-type octet = (read-next-byte) - sum (ash octet count))))) - -(define-char-reader (stream flexi-utf-32-be-input-stream) - (let (first-octet-seen) - (flet ((read-next-byte () - (prog1 - (or (read-byte* stream) - (cond (first-octet-seen - (signal-encoding-error stream "End of file while in UTF-32 sequence.")) - (t (return-from stream-read-char :eof)))) - (setq first-octet-seen t)))) - (declare (inline read-next-byte) (dynamic-extent (function read-next-byte))) - (loop for count from 24 downto 0 by 8 - for octet of-type octet = (read-next-byte) - sum (ash octet count))))) + (setq first-octet-seen t)))) + (declare (inline read-next-byte) (dynamic-extent (function read-next-byte))) + (loop for count from 24 downto 0 by 8 + for octet of-type octet = (read-next-byte) + sum (ash octet count)))))) hunk ./packages.lisp 2 -;;; $Header: /usr/local/cvsrep/flexi-streams/packages.lisp,v 1.26 2007/01/01 23:46:49 edi Exp $ +;;; $Header: /usr/local/cvsrep/flexi-streams/packages.lisp,v 1.27 2007/03/09 01:14:27 edi Exp $ hunk ./packages.lisp 42 - :*provide-use-value-restart* - :*use-replacement-char* hunk ./specials.lisp 2 -;;; $Header: /usr/local/cvsrep/flexi-streams/specials.lisp,v 1.21 2007/01/01 23:46:49 edi Exp $ +;;; $Header: /usr/local/cvsrep/flexi-streams/specials.lisp,v 1.22 2007/03/09 01:14:27 edi Exp $ hunk ./specials.lisp 127 -(defvar *use-replacement-char* nil - "Whether reading an unknown octet for an 8-bit encoding should -return the replacement character (65533) instead of signalling an -error.") - hunk ./specials.lisp 128 - "If this value is not NIL, it should be a character which is -used \(as if by a USE-VALUE restart) whenever during reading an -error of type FLEXI-STREAM-ENCODING-ERROR would have been -signaled otherwise. This substitution will only happen if -*PROVIDE-USE-VALUE-RESTART* is true, though.") - -(defvar *provide-use-value-restart* nil - "Whether READ-CHAR for flexi streams should provide a USE-VALUE -restart in case an encoding error is encountered. This is not done by -default because it entails a performance penalty.") + "If this value is not NIL, it should be a character which is used +\(as if by a USE-VALUE restart) whenever during reading an error of +type FLEXI-STREAM-ENCODING-ERROR would have been signaled otherwise.") hunk ./test/test.lisp 2 -;;; $Header: /usr/local/cvsrep/flexi-streams/test/test.lisp,v 1.11 2007/01/01 23:47:17 edi Exp $ +;;; $Header: /usr/local/cvsrep/flexi-streams/test/test.lisp,v 1.12 2007/03/09 01:14:30 edi Exp $ hunk ./test/test.lisp 57 -(defvar *test-counter* 0 +(defvar *test-success-counter* 0 hunk ./test/test.lisp 176 - (incf *test-counter*)) + (incf *test-success-counter*)) hunk ./test/test.lisp 189 - (incf *test-counter*)) + (incf *test-success-counter*)) hunk ./test/test.lisp 193 +(defmacro with-test ((test-description) &body body) + "Defines a test. Two utilities are available inside of the body of +the maco: The function FAIL, and the macro CHECK. FAIL, the lowest +level utility, marks the test defined by WITH-TEST as faided. CHECK +checks whether its argument is true, otherwise it calls FAIL. If +during evaluation of the specified expression any condition is +signaled, this is also considered a failure. + +WITH-TEST prints reports while the tests run. It also increments +*TEST-SUCCESS-COUNT* if a test completes successfully." + (flex::with-unique-names (successp) + `(let ((,successp t)) + (flet ((fail (format-str &rest format-args) + (setf ,successp nil) + (apply #'format *error-output* format-str format-args))) + (macrolet ((check (expression) + `(handler-case + (unless ,expression + (fail "Expression ~S failed.~%" ',expression)) + (condition (c) + (fail "Expression ~S failed signaling condition of type ~A: ~A.~%" + ',expression (type-of c) c))))) + (format *error-output* "Test ~S~%" ,test-description) + ,@body + (if ,successp + (incf *test-success-counter*) + (format *error-output* " Test failed!!!~%")) + (terpri *error-output*) + (terpri *error-output*)) + ,successp)))) + +(defmacro using-values ((&rest values) &body body) + "Executes BODY and feeds an element from VALUES to the USE-VALUE +restart each time a FLEXI-STREAM-ENCODING-ERROR is signaled. Signals +an error when there are more or less FLEXI-STREAM-ENCODING-ERRORs than +there are elements in VALUES." + (flex::with-unique-names (value-stack condition-counter) + `(let ((,value-stack ',values) + (,condition-counter 0)) + (handler-bind ((flexi-stream-encoding-error + #'(lambda (c) + (declare (ignore c)) + (unless ,value-stack + (error "Too many FLEXI-STREAM-ENCODING-ERRORs signaled, expected only ~A." + ,(length values))) + (incf ,condition-counter) + (use-value (pop ,value-stack))))) + (prog1 (progn ,@body) + (when ,value-stack + (error "~A FLEXI-STREAM-ENCODING-ERRORs signaled, but ~A were expected." + ,condition-counter ,(length values)))))))) + +(defun read-flexi-line (sequence external-format) + "Creates and returns a string from the octet sequence SEQUENCE using +the external format EXTERNAL-FORMAT." + (with-input-from-sequence (in sequence) + (setq in (make-flexi-stream in :external-format external-format)) + (read-line in))) + +(defun encoding-error-handling-test() + (with-test ("Handling of encoding errors") + (let ((*substitution-char* #\?)) + ;; :ASCII doesn't have characters with char codes > 127 + (check (string= "a??" (read-flexi-line `(,(char-code #\a) 128 200) :ascii))) + ;; :WINDOWS-1253 doesn't have a characters with codes 170 and 210 + (check (string= "a??" (read-flexi-line `(,(char-code #\a) 170 210) :windows-1253))) + ;; not a valid UTF-8 sequence + (check (string= "??" (read-flexi-line `(#xe4 #xf6 #xfc) :utf8))) + ;; UTF-8 can't start neither with #b11111110 nor with #b11111111 + (check (string= "??" (read-flexi-line `(#b11111110 #b11111111) :utf8)))) + (let ((*substitution-char* nil)) + ;; :ASCII doesn't have characters with char codes > 127 + (check (string= "abc" (using-values (#\b #\c) + (read-flexi-line `(,(char-code #\a) 128 200) :ascii)))) + ;; :WINDOWS-1253 encoding doesn't have a characters with codes 170 and 210 + (check (string= "axy" (using-values (#\x #\y) + (read-flexi-line `(,(char-code #\a) 170 210) :windows-1253)))) + ;; not a valid UTF-8 sequence + (check (string= "QW" (using-values (#\Q #\W) (read-flexi-line `(#xe4 #xf6 #xfc) :utf8)))) + ;; UTF-8 can't start neither with #b11111110 nor with #b11111111 + (check (string= "QW" (using-values (#\Q #\W) (read-flexi-line `(#b11111110 #b11111111) :utf8)))) + ;; only one byte + (check (string= "E" (using-values (#\E) (read-flexi-line `(#x01) :utf-16le)))) + ;; two bytes, but value of resulting word suggests that another word follows + (check (string= "R" (using-values (#\R) (read-flexi-line `(#x01 #xd8) :utf-16le)))) + ;; the second word must fit into the [#xdc00; #xdfff] interval, but it is #xdbff + (check (string= "T" (using-values (#\T) (read-flexi-line `(#x01 #xd8 #xff #xdb) :utf-16le)))) + ;; the same as for little endian above, but using inverse order of bytes in words + (check (string= "E" (using-values (#\E) (read-flexi-line `(#x01) :utf-16be)))) + (check (string= "R" (using-values (#\R) (read-flexi-line `(#xd8 #x01) :utf-16be)))) + (check (string= "T" (using-values (#\T) (read-flexi-line `(#xd8 #x01 #xdb #xff) :utf-16be)))) + ;; the only case when error is signaled for UTF-32 is at end of file + ;; in the middle of 4-byte sequence, both for big and little endian + (check (string= "Y" (using-values (#\Y) (read-flexi-line `(#x01) :utf-32le)))) + (check (string= "Y" (using-values (#\Y) (read-flexi-line `(#x01 #x01) :utf-32le)))) + (check (string= "Y" (using-values (#\Y) (read-flexi-line `(#x01 #x01 #x01) :utf-32le)))) + (check (string= "aY" (using-values (#\Y) + (read-flexi-line `(,(char-code #\a) #x00 #x00 #x00 #x01) :utf-32le)))) + (check (string= "Y" (using-values (#\Y) (read-flexi-line `(#x01) :utf-32be)))) + (check (string= "Y" (using-values (#\Y) (read-flexi-line `(#x01 #x01) :utf-32be)))) + (check (string= "Y" (using-values (#\Y) (read-flexi-line `(#x01 #x01 #x01) :utf-32be)))) + (check (string= "aY" (using-values (#\Y) + (read-flexi-line `(#x00 #x00 #x00 ,(char-code #\a) #x01) :utf-32be))))))) + hunk ./test/test.lisp 299 -CREATE-TEST-COMBINATIONS and shows simple statistics at the end." - (let* ((*test-counter* 0) +CREATE-TEST-COMBINATIONS, runs test for handling of encoding errors, +and shows simple statistics at the end." + (let* ((*test-success-counter* 0) hunk ./test/test.lisp 309 + (incf no-tests) + (encoding-error-handling-test) hunk ./test/test.lisp 312 - (= no-tests *test-counter*) (- no-tests *test-counter*) no-tests))) + (= no-tests *test-success-counter*) (- no-tests *test-success-counter*) no-tests))) }