X-Git-Url: http://repo.macrolet.net/gitweb/?a=blobdiff_plain;f=BUGS;h=3389897784e44b1348a66768b8b1286f7a3f3ff7;hb=73d8c340050371085f25cb87d0c676ce7c7928f9;hp=c3ad6f924f7da9850c4f7b3480642c5e33d8cb3d;hpb=c7dc5b2a1f56ed0583a0b3ea61b6ceb540c6f89e;p=sbcl.git diff --git a/BUGS b/BUGS index c3ad6f9..3389897 100644 --- a/BUGS +++ b/BUGS @@ -42,7 +42,8 @@ KNOWN BUGS OF NO SPECIAL CLASS: program, even if you know or guess enough about the internals of SBCL to wager that this (undefined in ANSI) operation would be safe. -3: +3: "type checking of structure slots" + a: ANSI specifies that a type mismatch in a structure slot initialization value should not cause a warning. WORKAROUND: @@ -78,19 +79,27 @@ WORKAROUND: Such code should compile without complaint and work correctly either on SBCL or on any other completely compliant Common Lisp system. -6: - bogus warnings about undefined functions for magic functions like - SB!C::%%DEFUN and SB!C::%DEFCONSTANT when cross-compiling files - like src/code/float.lisp. Fixing this will probably require - straightening out enough bootstrap consistency issues that - the cross-compiler can run with *TYPE-SYSTEM-INITIALIZED*. - Instead, the cross-compiler runs in a slightly flaky state - which is sane enough to compile SBCL itself, but which is - also unstable in several ways, including its inability - to really grok function declarations. - - As of sbcl-0.7.5, sbcl's cross-compiler does run with - *TYPE-SYSTEM-INITIALIZED*; however, this bug remains. + b: &AUX argument in a boa-constructor without a default value means + "do not initilize this slot" and does not cause type error. But + an error may be signalled at read time and it would be good if + SBCL did it. + + c: Reading of not initialized slot sometimes causes SEGV. + + d: + (declaim (optimize (safety 3) (speed 1) (space 1))) + (defstruct foo + x y) + (defstruct (stringwise-foo (:include foo + (x "x" :type simple-string) + (y "y" :type simple-string)))) + (defparameter *stringwise-foo* + (make-stringwise-foo)) + (setf (foo-x *stringwise-foo*) 0) + (defun frob-stringwise-foo (sf) + (aref (stringwise-foo-x sf) 0)) + (frob-stringwise-foo *stringwise-foo*) + SEGV. 7: The "compiling top-level form:" output ought to be condensed. @@ -135,16 +144,6 @@ WORKAROUND: (FORMAT NIL "~,1G" 1.4) => "1. " (FORMAT NIL "~3,1G" 1.4) => "1. " -20: - from Marco Antoniotti on cmucl-imp mailing list 1 Mar 2000: - (defclass ccc () ()) - (setf (find-class 'ccc1) (find-class 'ccc)) - (defmethod zut ((c ccc1)) 123) - In sbcl-0.7.1.13, this gives an error, - There is no class named CCC1. - DTC's recommended workaround from the mailing list 3 Mar 2000: - (setf (pcl::find-class 'ccc1) (pcl::find-class 'ccc)) - 27: Sometimes (SB-EXT:QUIT) fails with Argh! maximum interrupt nesting depth (4096) exceeded, exiting @@ -229,8 +228,8 @@ WORKAROUND: 45: a slew of floating-point-related errors reported by Peter Van Eynde on July 25, 2000: - b: SBCL's value for LEAST-POSITIVE-SHORT-FLOAT is bogus, and - should probably be 1.4012985e-45. In SBCL, + b: SBCL's value for LEAST-POSITIVE-SHORT-FLOAT on the x86 is + bogus, and should probably be 1.4012985e-45. In SBCL, (/ LEAST-POSITIVE-SHORT-FLOAT 2) returns a number smaller than LEAST-POSITIVE-SHORT-FLOAT. Similar problems exist for LEAST-NEGATIVE-SHORT-FLOAT, LEAST-POSITIVE-LONG-FLOAT, @@ -277,16 +276,6 @@ WORKAROUND: (ADD-METHOD (FUNCTION FOO03) M))) should give an error, but SBCL allows it. -52: - It has been reported (e.g. by Peter Van Eynde) that there are - several metaobject protocol "errors". (In order to fix them, we might - need to document exactly what metaobject protocol specification - we're following -- the current code is just inherited from PCL.) - -54: - The implementation of #'+ returns its single argument without - type checking, e.g. (+ "illegal") => "illegal". - 60: The debugger LIST-LOCATIONS command doesn't work properly. @@ -297,40 +286,6 @@ WORKAROUND: then requesting a BACKTRACE at the debugger prompt gives no information about where in the user program the problem occurred. -62: - The compiler is supposed to do type inference well enough that - the declaration in - (TYPECASE X - ((SIMPLE-ARRAY SINGLE-FLOAT) - (LOCALLY - (DECLARE (TYPE (SIMPLE-ARRAY SINGLE-FLOAT) X)) - ..)) - ..) - is redundant. However, as reported by Juan Jose Garcia Ripoll for - CMU CL, it sometimes doesn't. Adding declarations is a pretty good - workaround for the problem for now, but can't be done by the TYPECASE - macros themselves, since it's too hard for the macro to detect - assignments to the variable within the clause. - Note: The compiler *is* smart enough to do the type inference in - many cases. This case, derived from a couple of MACROEXPAND-1 - calls on Ripoll's original test case, - (DEFUN NEGMAT (A) - (DECLARE (OPTIMIZE SPEED (SAFETY 0))) - (COND ((TYPEP A '(SIMPLE-ARRAY SINGLE-FLOAT)) NIL - (LET ((LENGTH (ARRAY-TOTAL-SIZE A))) - (LET ((I 0) (G2554 LENGTH)) - (DECLARE (TYPE REAL G2554) (TYPE REAL I)) - (TAGBODY - SB-LOOP::NEXT-LOOP - (WHEN (>= I G2554) (GO SB-LOOP::END-LOOP)) - (SETF (ROW-MAJOR-AREF A I) (- (ROW-MAJOR-AREF A I))) - (GO SB-LOOP::NEXT-LOOP) - SB-LOOP::END-LOOP)))))) - demonstrates the problem; but the problem goes away if the TAGBODY - and GO forms are removed (leaving the SETF in ordinary, non-looping - code), or if the TAGBODY and GO forms are retained, but the - assigned value becomes 0.0 instead of (- (ROW-MAJOR-AREF A I)). - 63: Paul Werkowski wrote on cmucl-imp@cons.org 2000-11-15 I am looking into this problem that showed up on the cmucl-help @@ -385,18 +340,6 @@ WORKAROUND: (partially alleviated in sbcl-0.7.9.32 by a fix by Matthew Danish to make the temporary filename less easily guessable) -82: - Functions are assigned names based on the context in which they're - defined. This is less than ideal for the functions which are - used to implement CLOS methods. E.g. the output of - (DESCRIBE 'PRINT-OBJECT) lists functions like - # - and - # - It would be better if these functions' names always identified - them as methods, and identified their generic functions and - specializers. - 83: RANDOM-INTEGER-EXTRA-BITS=10 may not be large enough for the RANDOM RNG to be high quality near RANDOM-FIXNUM-MAX; it looks as though @@ -506,56 +449,6 @@ WORKAROUND: time trying to GC afterwards. Surely there's some more economical way to implement (ROOM T). -115: - reported by Martin Atzmueller 2001-06-25; originally from CMU CL bugs - collection: - (in-package :cl-user) - ;;; The following invokes a compiler error. - (declaim (optimize (speed 2) (debug 3))) - (defun tst () - (flet ((m1 () - (unwind-protect nil))) - (if (catch nil) - (m1) - (m1)))) - The error message in sbcl-0.6.12.42 is - internal error, failed AVER: - "(COMMON-LISP:EQ (SB!C::TN-ENVIRONMENT SB!C:TN) SB!C::TN-ENV)" - - This examples better illustrates the problem: - - (defun tst () - (declare (optimize (speed 2) (debug 3))) - (flet ((m1 () - (bar (if (foo) 1 2)) - (let ((x (foo))) - (bar x (list x))))) - (if (catch nil) - (m1) - (m1)))) - - (X is allocated in the physical environment of M1; X is :WRITE in - the call of LET [convert-to-global]; IF makes sure that a block - exists in M1 before this call.) - - Because X is :DEBUG-ENVIRONMENT, it is :LIVE by default in all - blocks in the environment, particularly it is :LIVE in the start of - M1 (where it is not yet :WRITE) [setup-environment-tn-conflicts]. - - Then :LIVE is propagated backwards, i.e. into the caller of M1 - where X does not exist [lifetime-flow-analysis]. - - (CATCH NIL) causes all TNs to be saved; Python fails on saving - non-existent variable; if it is replaced with (FOO), the problem - appears when debugging TST: LIST-LOCALS says - - debugger invoked on condition of type SB-DI:UNKNOWN-DEBUG-VAR: - - # is not in #. - - (in those old versions, in which debugger worked :-(). - 117: When the compiler inline expands functions, it may be that different kinds of return values are generated from different code branches. @@ -670,12 +563,6 @@ WORKAROUND: Evidently Python thinks of the lambda as a code transformation so much that it forgets that it's also an object. -127: - The DEFSTRUCT section of the ANSI spec, in the :CONC-NAME section, - specifies a precedence rule for name collisions between slot accessors of - structure classes related by inheritance. As of 0.7.0, SBCL still - doesn't follow it. - 135: Ideally, uninterning a symbol would allow it, and its associated FDEFINITION and PROCLAIM data, to be reclaimed by the GC. However, @@ -686,13 +573,16 @@ WORKAROUND: forever, even when it is uninterned and all other references to it are lost. -141: - Pretty-printing nested backquotes doesn't work right, as - reported by Alexey Dejneka sbcl-devel 2002-01-13: - * '``(FOO ,@',@S) - ``(FOO SB-IMPL::BACKQ-COMMA-AT S) - * (lisp-implementation-version) - "0.pre7.129" +141: "pretty printing and backquote" + a. + * '``(FOO ,@',@S) + ``(FOO SB-IMPL::BACKQ-COMMA-AT S) + + b. + * (write '`(, .ala.) :readably t :pretty t) + `(,.ALA.) + + (note the space between the comma and the point) 143: (reported by Jesse Bouwman 2001-10-24 through the unfortunately @@ -784,10 +674,8 @@ WORKAROUND: expansion, leaving garbage consisting of infinished blocks of the partially converted function.) -157: - Functions SUBTYPEP, TYPEP, UPGRADED-ARRAY-ELEMENT-TYPE, and - UPGRADED-COMPLEX-PART-TYPE should have an optional environment argument. - (reported by Alexey Dejneka sbcl-devel 2002-04-12) + (due to reordering of the compiler this example is compiled + successfully by 0.7.14, but the bug probably remains) 162: (reported by Robert E. Brown 2002-04-16) @@ -838,19 +726,6 @@ WORKAROUND: code. Since then the warning has been downgraded to STYLE-WARNING, so it's still a bug but at least it's a little less annoying. -178: "AVER failure compiling confused THEs in FUNCALL" - In sbcl-0.7.4.24, compiling - (defun bug178 (x) - (funcall (the function (the standard-object x)))) - gives - failed AVER: - "(AND (EQ (IR2-CONTINUATION-PRIMITIVE-TYPE 2CONT) FUNCTION-PTYPE) (EQ CHECK T))" - This variant compiles OK, though: - (defun bug178alternative (x) - (funcall (the nil x))) - - (since 0.7.8.9 it does not signal an error; see also bug 199) - 183: "IEEE floating point issues" Even where floating point handling is being dealt with relatively well (as of sbcl-0.7.5, on sparc/sunos and alpha; see bug #146), the @@ -970,6 +845,28 @@ WORKAROUND: (INTEGER 1296 1296) ...)>)[:EXTERNAL] + In recent SBCL the following example also illustrates this bug: + + (time (compile + nil + '(lambda () + (declare (optimize (safety 3))) + (declare (optimize (compilation-speed 2))) + (declare (optimize (speed 1) (debug 1) (space 1))) + (let ((start 4)) + (declare (type (integer 0) start)) + (print (incf start 22)) + (print (incf start 26)) + (print (incf start 28))) + (let ((start 6)) + (declare (type (integer 0) start)) + (print (incf start 22)) + (print (incf start 26))) + (let ((start 10)) + (declare (type (integer 0) start)) + (print (incf start 22)) + (print (incf start 26)))))) + 190: "PPC/Linux pipe? buffer? bug" In sbcl-0.7.6, the run-program.test.sh test script sometimes hangs on the PPC/Linux platform, waiting for a zombie env process. This @@ -1013,6 +910,11 @@ WORKAROUND: (see bug 203) + c. (defun foo (x y) + (locally (declare (type fixnum x y)) + (+ x (* 2 y)))) + (foo 1.1 2) => 5.1 + 194: "no error from (THE REAL '(1 2 3)) in some cases" fixed parts: a. In sbcl-0.7.7.9, @@ -1049,27 +951,9 @@ WORKAROUND: inaccurate transformations. * Alexey Dejneka pointed out that (IGNORE-ERRORS (IDENTITY (THE REAL '(1 2 3)))) - works as it should. Also + and (IGNORE-ERRORS (VALUES (THE REAL '(1 2 3)))) - works as it should. Perhaps this is another case of VALUES type - intersections behaving in non-useful ways? - -199: "hairy FUNCTION types confuse the compiler" - (reported by APD sbcl-devel 2002-09-15) - (DEFUN MUR (F) - (EQ NIL (FUNCALL F))) - - (DEFUN FOO (F X) - (DECLARE (TYPE (AND FUNCTION (SATISFIES MUR)) F)) - (FUNCALL F X)) - - fails to compile, printing - failed AVER: - "(AND (EQ (IR2-CONTINUATION-PRIMITIVE-TYPE 2CONT) FUNCTION-PTYPE) (EQ CHECK T))" - - APD further reports that this bug is not present in CMUCL. - - (this case was fixed in 0.7.8.9; see also bug 178) + work as they should. 201: "Incautious type inference from compound CONS types" (reported by APD sbcl-devel 2002-09-17) @@ -1091,7 +975,7 @@ WORKAROUND: (progn (the real (list 1)) t) This situation may appear during optimizing away degenerate cases of - certain functions: see bugs 54, 192b. + certain functions: see bug 192b. 205: "environment issues in cross compiler" (These bugs have no impact on user code, but should be fixed or @@ -1100,6 +984,8 @@ WORKAROUND: lexical environment. b. The body of (EVAL-WHEN (:COMPILE-TOPLEVEL) ...) is evaluated in the null lexical environment. + c. The cross-compiler cannot inline functions defined in a non-null + lexical environment. 206: ":SB-FLUID feature broken" (reported by Antonio Martinez-Shotton sbcl-devel 2002-10-07) @@ -1249,23 +1135,6 @@ WORKAROUND: (defun test (x y) (the (values integer) (truncate x y))) (test 10 4) => 2 -219: "DEFINE-COMPILER-MACRO in non-toplevel contexts evaluated at compile-time" - In sbcl-0.7.9: - - * (defun foo (x) - (when x - (define-compiler-macro bar (&whole whole) - (declare (ignore whole)) - (print "expanding compiler macro") - 1))) - FOO - * (defun baz (x) (bar)) - [ ... ] - "expanding compiler macro" - BAZ - * (baz t) - 1 - 220: Sbcl 0.7.9 fails to compile @@ -1273,80 +1142,178 @@ WORKAROUND: (the integer (helper)) nil) - Type check for INTEGER is inserted, the result of which serves as - the first argument of M-V-C, is inserted after evaluation of NIL. So - arguments of M-V-C are pushed in the wrong order. As a temporary - workaround type checking was disabled for M-V-Cs in 0.7.9.13. A - better solution would be to put a check between evaluation of - arguments, but it could be tricky to check result types of PROG1, IF - etc. - -222: "environment problems in PCL" - Evaluating - - (symbol-macrolet ((x 1)) - (defmethod foo (z) - (macrolet ((ml (form) `(progn ,form ,x))) - (ml (print x))))) - - causes - - debugger invoked on condition of type UNBOUND-VARIABLE: - The variable X is unbound. - -223: "(SETF FDEFINITION) and #' semantics broken for wrappers" - Although this - (defun foo (x) - (print x)) - (defun traced (fn) - (lambda (&rest rest) - (format t "~&about to call ~S on ~S~%" fn rest) - (apply fn rest) - (format t "~&returned from ~S~%" fn))) - (setf (fdefinition 'foo) - (traced #'foo)) - (foo 11) - does what one would expect, this - (defun bar (x) - (print x)) - (let ((bar0 #'bar)) - (setf (fdefinition 'bar) - (lambda (&rest rest) - (format t "~&about to enter BAR ~S~%" rest) - (apply bar0 rest) - (format t "~&back from BAR~%")))) - (bar 12) - recurses endlessly in sbcl-0.7.9.32. (Or it works if #' and - FDEFINITION are replaced by SYMBOL-FUNCTION.) - -224: - SBCL 0.7.8 fails to compile - - (localy (declare (optimize (safety 3))) - (ignore-errors (progn (values-list (car (list '(1 . 2)))) t))) - -225: - (fixed in 0.7.9.42) - -226: "AVER failure in COMPILE-FILE of clocc-ansi-test/tests.lisp" - sbcl-0.7.9.43 dies with failed AVER "(EQ (TN-PHYSENV TN) TN-ENV)" when - trying to compile clocc-ansi-test/tests.lisp. sbcl-0.7.9.31 was able to - to compile it. A smaller test case exhibiting the same problem is - (declaim (optimize (speed 0) (safety 3) (debug 3))) - (defun c-a-p () - (flet ((safe-format (stream string &rest r) - (unless (ignore-errors (progn - (apply #'format stream string r) - t)) - (format stream "~&foo ~S" string)))) - (cond - ((eq my-result :ERROR) - (cond - ((ignore-errors (typep condition result)) - (safe-format t "~&bar ~S" result)) - (t - (safe-format t "~&baz ~S (~A) ~S" condition condition result))))))) - + Type check for INTEGER, the result of which serves as the first + argument of M-V-C, is inserted after evaluation of NIL. So arguments + of M-V-C are pushed in the wrong order. As a temporary workaround + type checking was disabled for M-V-Cs in 0.7.9.13. A better solution + would be to put the check between evaluation of arguments, but it + could be tricky to check result types of PROG1, IF etc. + +229: + (subtypep 'function '(function)) => nil, t. + +233: bugs in constraint propagation + a. + (defun foo (x) + (declare (optimize (speed 2) (safety 3))) + (let ((y 0d0)) + (values + (the double-float x) + (setq y (+ x 1d0)) + (setq x 3d0) + (quux y (+ y 2d0) (* y 3d0))))) + (foo 4) => segmentation violation + + (see usage of CONTINUATION-ASSERTED-TYPE in USE-RESULT-CONSTRAINTS) + (see also bug 236) + + b. + (declaim (optimize (speed 2) (safety 3))) + (defun foo (x y) + (if (typep (prog1 x (setq x y)) 'double-float) + (+ x 1d0) + (+ x 2))) + (foo 1d0 5) => segmentation violation + +235: "type system and inline expansion" + a. + (declaim (ftype (function (cons) number) acc)) + (declaim (inline acc)) + (defun acc (c) + (the number (car c))) + + (defun foo (x y) + (values (locally (declare (optimize (safety 0))) + (acc x)) + (locally (declare (optimize (safety 3))) + (acc y)))) + + (foo '(nil) '(t)) => NIL, T. + + b. (reported by brown on #lisp 2003-01-21) + + (defun find-it (x) + (declare (optimize (speed 3) (safety 0))) + (declare (notinline mapcar)) + (let ((z (mapcar #'car x))) + (find 'foobar z))) + + Without (DECLARE (NOTINLINE MAPCAR)), Python cannot derive that Z is + LIST. + +236: "THE semantics is broken" + + (defun foo (a f) + (declare (optimize (speed 2) (safety 0))) + (+ 1d0 + (the double-float + (multiple-value-prog1 + (svref a 0) + (unless f (return-from foo 0)))))) + + (foo #(4) nil) => SEGV + + VOP selection thinks that in unsafe code result type assertions + should be valid immediately. (See also bug 233a.) + + The similar problem exists for TRULY-THE. + +237: "Environment arguments to type functions" + a. Functions SUBTYPEP, TYPEP, UPGRADED-ARRAY-ELEMENT-TYPE, and + UPGRADED-COMPLEX-PART-TYPE now have an optional environment + argument, but they ignore it completely. This is almost + certainly not correct. + b. Also, the compiler's optimizers for TYPEP have not been informed + about the new argument; consequently, they will not transform + calls of the form (TYPEP 1 'INTEGER NIL), even though this is + just as optimizeable as (TYPEP 1 'INTEGER). + +238: "REPL compiler overenthusiasm for CLOS code" + From the REPL, + * (defclass foo () ()) + * (defmethod bar ((x foo) (foo foo)) (call-next-method)) + causes approximately 100 lines of code deletion notes. Some + discussion on this issue happened under the title 'Three "interesting" + bugs in PCL', resulting in a fix for this oververbosity from the + compiler proper; however, the problem persists in the interactor + because the notion of original source is not preserved: for the + compiler, the original source of the above expression is (DEFMETHOD + BAR ((X FOO) (FOO FOO)) (CALL-NEXT-METHOD)), while by the time the + compiler gets its hands on the code needing compilation from the REPL, + it has been macroexpanded several times. + + A symptom of the same underlying problem, reported by Tony Martinez: + * (handler-case + (with-input-from-string (*query-io* " no") + (yes-or-no-p)) + (simple-type-error () 'error)) + ; in: LAMBDA NIL + ; (SB-KERNEL:FLOAT-WAIT) + ; + ; note: deleting unreachable code + ; compilation unit finished + ; printed 1 note + +241: "DEFCLASS mysteriously remembers uninterned accessor names." + (from tonyms on #lisp IRC 2003-02-25) + In sbcl-0.7.12.55, typing + (defclass foo () ((bar :accessor foo-bar))) + (profile foo-bar) + (unintern 'foo-bar) + (defclass foo () ((bar :accessor foo-bar))) + gives the error message + "#:FOO-BAR already names an ordinary function or a macro." + So it's somehow checking the uninterned old accessor name instead + of the new requested accessor name, which seems broken to me (WHN). + +242: "WRITE-SEQUENCE suboptimality" + (observed from clx performance) + In sbcl-0.7.13, WRITE-SEQUENCE of a sequence of type + (SIMPLE-ARRAY (UNSIGNED-BYTE 8) (*)) on a stream with element-type + (UNSIGNED-BYTE 8) will write to the stream one byte at a time, + rather than writing the sequence in one go, leading to severe + performance degradation. + +243: "STYLE-WARNING overenthusiasm for unused variables" + (observed from clx compilation) + In sbcl-0.7.14, in the presence of the macros + (DEFMACRO FOO (X) `(BAR ,X)) + (DEFMACRO BAR (X) (DECLARE (IGNORABLE X)) 'NIL) + somewhat surprising style warnings are emitted for + (COMPILE NIL '(LAMBDA (Y) (FOO Y))): + ; in: LAMBDA (Y) + ; (LAMBDA (Y) (FOO Y)) + ; + ; caught STYLE-WARNING: + ; The variable Y is defined but never used. + +244: "optimizing away tests for &KEY args of type declared in DEFKNOWN" + (caught by clocc-ansi-test :EXCEPSIT-LEGACY-1050) + In sbcl-0.pre8.44, (OPEN "foo" :DIRECTION :INPUT :EXTERNAL-FORMAT 'FOO) + succeeds with no error (ignoring the bogus :EXTERNAL-FORMAT argument) + apparently because the test is optimized away. The problem doesn't + exist in sbcl-0.pre8.19. Deleting the (MEMBER :DEFAULT) declaration + for :EXTERNAL-FORMAT in DEFKNOWN OPEN (and LOAD) is a workaround for + the problem (and should be removed when the problem is fixed). + +245: bugs in disassembler + a. On X86 an immediate operand for IMUL is printed incorrectly. + b. On X86 operand size prefix is not recognized. + +246: "NTH-VALUE scaling problem" + NTH-VALUE's current implementation for constant integers scales in + compile-time as O(n^4), as indeed must the optional dispatch + mechanism on which it is implemented. While it is unlikely to + matter in real user code, it's still unpleasant to observe that + (NTH-VALUE 1000 (VALUES-LIST (MAKE-LIST 1001))) takes several hours + to compile. + +247: "incomplete conversion of stack parameters in #-SB-THREAD code" + In 0.pre8.67/x86/nothreads, executing (ROOM) causes an error to + be signalled: + The variable SB-VM:CONTROL-STACK-END is unbound. + (When this is fixed, the ROOM entries in tests/smoke.impure.lisp + should be uncommented.) DEFUNCT CATEGORIES OF BUGS IR1-#: