CREDITS SINCE THE RELEASE OF SBCL
+(Some more details are available in the NEWS file and in the
+project's CVS change logs.)
+
Martin Atzmueller:
- He reported many bugs in SBCL, helped clean up various stale
- bug data in SBCL, and ported many patches from CMU CL.
+ He reported many bugs, fixed many bugs, ported various fixes
+ from CMU CL, and helped clean up various stale bug data.
Daniel Barlow:
He contributed sblisp.lisp, a set of patches to make SBCL
problems, has been invaluable to the CMU CL project and, by
porting, invaluable to the SBCL project as well.
+William Newman:
+ He continued to work on the project after the fork, increasing
+ ANSI compliance, fixing bugs, regularizing the internals of the
+ system, deleting unused extensions, improving performance in
+ some areas (especially sequence functions and non-simple vectors),
+ and updating documentation.
+
Peter Van Eynde:
He wrestled the CLISP test suite into a portable test suite which
can be used on SBCL, and submitted many other bug reports as well.
array)
(optimize (speed 3) (safety 0))
(ext:optimize-interface (safety 3)))
- ;; with-array-data will get us to the actual data. However, because
+ ;; WITH-ARRAY-DATA will get us to the actual data. However, because
;; the array could have been displaced, we need to know where the
;; data starts.
(lisp::with-array-data ((data array)
;; FIXME: It seems to me that this could go away, with its contents moved
;; into SB!KERNEL, like the implementation of the rest of the class system.
- #s(sb-cold:package-data
- :name "SB!CONDITIONS"
- :doc "private: the implementation of the condition system"
- :use ("CL" "SB!EXT" "SB!INT" "SB!KERNEL"))
+;; #s(sb-cold:package-data
+;; :name "SB!CONDITIONS"
+;; :doc "private: the implementation of the condition system"
+;; :use ("CL" "SB!EXT" "SB!INT" "SB!KERNEL"))
#s(sb-cold:package-data
:name "SB!DEBUG"
"SIMPLE-CONTROL-ERROR" "SIMPLE-FILE-ERROR"
"SIMPLE-PROGRAM-ERROR" "SIMPLE-STYLE-WARNING" "STYLE-WARN"
+ ;; newly exported from former SB!CONDITIONS
+ "*HANDLER-CLUSTERS*" "*RESTART-CLUSTERS*"
+ "SHOW-CONDITION" "CASE-FAILURE"
+ "NAMESTRING-PARSE-ERROR"
+ "DESCRIBE-CONDITION"
+
"!COLD-INIT"
"!GLOBALDB-COLD-INIT" "!FDEFN-COLD-INIT"
"!TYPE-CLASS-COLD-INIT" "!TYPEDEFS-COLD-INIT"
;;;; provided with absolutely no warranty. See the COPYING and CREDITS
;;;; files for more information.
-(in-package "SB!CONDITIONS")
+(in-package "SB!KERNEL")
(defvar *break-on-signals* nil
#!+sb-doc
(setf *gc-notify-stream* nil)
(setf *before-gc-hooks* nil)
(setf *after-gc-hooks* nil)
- #!+gengc (setf sb!conditions::*handler-clusters* nil)
+ #!+gengc (setf *handler-clusters* nil)
#!-gengc (setf *already-maybe-gcing* t
*gc-inhibit* t
*need-to-collect-garbage* nil
;; and when people redirect *ERROR-OUTPUT*, they could
;; reasonably expect to see error messages logged there,
;; regardless of what the debugger does afterwards.
- #!+sb-show (sb!conditions::show-condition *debug-condition*
+ #!+sb-show (sb!kernel:show-condition *debug-condition*
*error-output*)
(format *error-output*
"~2&debugger invoked on condition of type ~S:~% "
;;; This calls DEBUG-LOOP, performing some simple initializations
;;; before doing so. INVOKE-DEBUGGER calls this to actually get into
-;;; the debugger. SB!CONDITIONS::ERROR-ERROR calls this in emergencies
+;;; the debugger. SB!KERNEL::ERROR-ERROR calls this in emergencies
;;; to get into a debug prompt as quickly as possible with as little
;;; risk as possible for stepping on whatever is causing recursive
;;; errors.
(format s "~:_(~@<~S ~:_~S~:>)" k v)))))
(defmethod describe-object ((condition condition) s)
- (sb-conditions::describe-condition condition s))
+ (sb-kernel:describe-condition condition s))
\f
;;;; DESCRIBE-OBJECT methods for symbols and functions, including all
;;;; sorts of messy stuff about documentation, type information,
;;;; provided with absolutely no warranty. See the COPYING and CREDITS
;;;; files for more information.
-(in-package "SB!CONDITIONS")
+(in-package "SB!KERNEL")
\f
;;;; restarts
(defun assert-error (assertion places datum &rest arguments)
(let ((cond (if datum
- (sb!conditions::coerce-to-condition datum
+ (coerce-to-condition datum
arguments
'simple-error
'error)
(defun case-body-error (name keyform keyform-value expected-type keys)
(restart-case
- (error 'sb!conditions::case-failure
+ (error 'case-failure
:name name
:datum keyform-value
:expected-type expected-type
;;;; provided with absolutely no warranty. See the COPYING and CREDITS
;;;; files for more information.
-(in-package "SB!CONDITIONS")
+(in-package "SB!KERNEL")
(define-condition simple-style-warning (simple-condition style-warning) ())
*standard-readtable*
sb!debug:*in-the-debugger*
sb!debug:*stack-top-hint*
- sb!conditions::*handler-clusters*
- sb!conditions::*restart-clusters*
+ *handler-clusters*
+ *restart-clusters*
*gc-inhibit* *need-to-collect-garbage*
*software-interrupt-vector* *load-verbose*
*load-print-stuff* *in-compilation-unit*
;;;; provided with absolutely no warranty. See the COPYING and CREDITS
;;;; files for more information.
-(in-package "SB!CONDITIONS")
+(in-package "SB!KERNEL")
\f
;;;; the CONDITION class
(cond
,@(nreverse clauses)
,@(if errorp
- `((t (error 'sb!conditions::case-failure
+ `((t (error 'case-failure
:name ',name
:datum ,keyform-value
:expected-type ',expected-type
;;; This checks to see whether the array is simple and the start and
;;; end are in bounds. If so, it proceeds with those values.
-;;; Otherwise, it calls %WITH-ARRAY-DATA. Note that there is a
-;;; DERIVE-TYPE method for %WITH-ARRAY-DATA.
+;;; Otherwise, it calls %WITH-ARRAY-DATA. Note that %WITH-ARRAY-DATA
+;;; may be further optimized.
+;;;
+;;; Given any ARRAY, bind DATA-VAR to the array's data vector and
+;;; START-VAR and END-VAR to the start and end of the designated
+;;; portion of the data vector. SVALUE and EVALUE are any start and
+;;; end specified to the original operation, and are factored into the
+;;; bindings of START-VAR and END-VAR. OFFSET-VAR is the cumulative
+;;; offset of all displacements encountered, and does not include
+;;; SVALUE.
(defmacro with-array-data (((data-var array &key (offset-var (gensym)))
(start-var &optional (svalue 0))
(end-var &optional (evalue nil)))
&body forms)
- #!+sb-doc
- "Given any Array, binds Data-Var to the array's data vector and Start-Var and
- End-Var to the start and end of the designated portion of the data vector.
- Svalue and Evalue are any start and end specified to the original operation,
- and are factored into the bindings of Start-Var and End-Var. Offset-Var is
- the cumulative offset of all displacements encountered, and does not
- include Svalue."
(once-only ((n-array array)
(n-svalue `(the index ,svalue))
(n-evalue `(the (or index null) ,evalue)))
(defoptimizer (hairy-data-vector-set derive-type) ((array index new-value))
(assert-new-value-type new-value array))
-;;; Figure out the type of the data vector if we know the argument element
-;;; type.
+;;; Figure out the type of the data vector if we know the argument
+;;; element type.
(defoptimizer (%with-array-data derive-type) ((array start end))
(let ((atype (continuation-type array)))
(when (array-type-p atype)
(values (vars) keyp allowp (aux-vars) (aux-vals))))))
-;;; Similar to IR1-Convert-Progn-Body except that we sequentially bind each
-;;; Aux-Var to the corresponding Aux-Val before converting the body. If there
-;;; are no bindings, just convert the body, otherwise do one binding and
-;;; recurse on the rest.
+;;; This is similar to IR1-CONVERT-PROGN-BODY except that we
+;;; sequentially bind each AUX-VAR to the corresponding AUX-VAL before
+;;; converting the body. If there are no bindings, just convert the
+;;; body, otherwise do one binding and recurse on the rest.
;;;
-;;; If Interface is true, then we convert bindings with the interface
-;;; policy. For real &aux bindings, and implicit aux bindings introduced by
-;;; keyword bindings, this is always true. It is only false when LET* directly
-;;; calls this function.
+;;; If INTERFACE is true, then we convert bindings with the interface
+;;; policy. For real &AUX bindings, and implicit aux bindings
+;;; introduced by keyword bindings, this is always true. It is only
+;;; false when LET* directly calls this function.
(defun ir1-convert-aux-bindings (start cont body aux-vars aux-vals interface)
(declare (type continuation start cont) (list body aux-vars aux-vals))
(if (null aux-vars)
(list (first aux-vals))))))
(values))
-;;; Similar to IR1-Convert-Progn-Body except that code to bind the Specvar
-;;; for each Svar to the value of the variable is wrapped around the body. If
-;;; there are no special bindings, we just convert the body, otherwise we do
-;;; one special binding and recurse on the rest.
+;;; This is similar to IR1-CONVERT-PROGN-BODY except that code to bind
+;;; the SPECVAR for each SVAR to the value of the variable is wrapped
+;;; around the body. If there are no special bindings, we just convert
+;;; the body, otherwise we do one special binding and recurse on the
+;;; rest.
;;;
-;;; We make a cleanup and introduce it into the lexical environment. If
-;;; there are multiple special bindings, the cleanup for the blocks will end up
-;;; being the innermost one. We force Cont to start a block outside of this
-;;; cleanup, causing cleanup code to be emitted when the scope is exited.
+;;; We make a cleanup and introduce it into the lexical environment.
+;;; If there are multiple special bindings, the cleanup for the blocks
+;;; will end up being the innermost one. We force CONT to start a
+;;; block outside of this cleanup, causing cleanup code to be emitted
+;;; when the scope is exited.
(defun ir1-convert-special-bindings (start cont body aux-vars aux-vals
interface svars)
(declare (type continuation start cont)
lambda))
;;; Create the actual entry-point function for an optional entry
-;;; point. The lambda binds copies of each of the Vars, then calls Fun
-;;; with the argument Vals and the Defaults. Presumably the Vals refer
-;;; to the Vars by name. The Vals are passed in in reverse order.
+;;; point. The lambda binds copies of each of the VARS, then calls FUN
+;;; with the argument VALS and the DEFAULTS. Presumably the VALS refer
+;;; to the VARS by name. The VALS are passed in in reverse order.
;;;
;;; If any of the copies of the vars are referenced more than once,
-;;; then we mark the corresponding var as Ever-Used to inhibit
+;;; then we mark the corresponding var as EVER-USED to inhibit
;;; "defined but not read" warnings for arguments that are only used
;;; by default forms.
;;;
;;; This function deals with supplied-p vars in optional arguments. If
;;; the there is no supplied-p arg, then we just call
-;;; IR1-Convert-Hairy-Args on the remaining arguments, and generate a
+;;; IR1-CONVERT-HAIRY-ARGS on the remaining arguments, and generate a
;;; optional entry that calls the result. If there is a supplied-p
;;; var, then we add it into the default vars and throw a T into the
;;; entry values. The resulting entry point function is returned.
(declare (list path) (inline member))
(cadr (member 'original-source-start path :test #'eq)))
-;;; Return a list of all the enclosing forms not in the original source that
-;;; converted to get to this form, with the immediate source for node at the
-;;; start of the list.
+;;; Return a list of all the enclosing forms not in the original
+;;; source that converted to get to this form, with the immediate
+;;; source for node at the start of the list.
(defun source-path-forms (path)
(subseq path 0 (position 'original-source-start path)))
(first forms)
(values (find-original-source path)))))
-;;; Return NODE-SOURCE-FORM, T if continuation has a single use, otherwise
-;;; NIL, NIL.
+;;; Return NODE-SOURCE-FORM, T if continuation has a single use,
+;;; otherwise NIL, NIL.
(defun continuation-source (cont)
(let ((use (continuation-use cont)))
(if use
(values (node-source-form use) t)
(values nil nil))))
\f
-;;; Return a new LEXENV just like Default except for the specified slot
-;;; values. Values for the alist slots are NCONC'ed to the beginning of the
-;;; current value, rather than replacing it entirely.
+;;; Return a new LEXENV just like DEFAULT except for the specified
+;;; slot values. Values for the alist slots are NCONCed to the
+;;; beginning of the current value, rather than replacing it entirely.
(defun make-lexenv (&key (default *lexenv*)
functions variables blocks tags type-restrictions
options
lambda cleanup cookie interface-cookie
(frob options lexenv-options))))
-;;; Return a cookie that defaults any unsupplied optimize qualities in the
-;;; Interface-Cookie with the corresponding ones from the Cookie.
+;;; Return a cookie that defaults any unsupplied optimize qualities in
+;;; the Interface-Cookie with the corresponding ones from the Cookie.
(defun make-interface-cookie (lexenv)
(declare (type lexenv lexenv))
(let ((icookie (lexenv-interface-cookie lexenv))
;; a list (MACRO . <function>) (a local macro, with the specifier
;; expander.) Note that Name may be a (SETF <name>) function.
(functions nil :type list)
- ;; An alist translating variable names to Leaf structures. A special binding
- ;; is indicated by a :Special Global-Var leaf. Each special binding within
- ;; the code gets a distinct leaf structure, as does the current "global"
- ;; value on entry to the code compiled. (locally (special ...)) is handled
- ;; by adding the most recent special binding to the front of the list.
+ ;; an alist translating variable names to LEAF structures. A special
+ ;; binding is indicated by a :SPECIAL GLOBAL-VAR leaf. Each special
+ ;; binding within the code gets a distinct leaf structure, as does
+ ;; the current "global" value on entry to the code compiled.
+ ;; (locally (special ...)) is handled by adding the most recent
+ ;; special binding to the front of the list.
;;
- ;; If the CDR is (MACRO . <exp>), then <exp> is the expansion of a symbol
- ;; macro.
+ ;; If the CDR is (MACRO . <exp>), then <exp> is the expansion of a
+ ;; symbol macro.
(variables nil :type list)
- ;; Blocks and Tags are alists from block and go-tag names to 2-lists of the
- ;; form (<entry> <continuation>), where <continuation> is the continuation to
- ;; exit to, and <entry> is the corresponding Entry node.
+ ;; BLOCKS and TAGS are alists from block and go-tag names to 2-lists
+ ;; of the form (<entry> <continuation>), where <continuation> is the
+ ;; continuation to exit to, and <entry> is the corresponding ENTRY node.
(blocks nil :type list)
(tags nil :type list)
- ;; An alist (Thing . CType) which is used to keep track of "pervasive" type
- ;; declarations. When Thing is a leaf, this is for type declarations that
- ;; pertain to the type in a syntactic extent which does not correspond to a
- ;; binding of the affected name. When Thing is a continuation, this is used
- ;; to track the innermost THE type declaration.
+ ;; an alist (THING . CTYPE) which is used to keep track of
+ ;; "pervasive" type declarations. When THING is a leaf, this is for
+ ;; type declarations that pertain to the type in a syntactic extent
+ ;; which does not correspond to a binding of the affected name. When
+ ;; Thing is a continuation, this is used to track the innermost THE
+ ;; type declaration.
(type-restrictions nil :type list)
- ;; The lexically enclosing lambda, if any.
+ ;; the lexically enclosing lambda, if any
;;
;; FIXME: This should be :TYPE (OR CLAMBDA NULL), but it was too hard
;; to get CLAMBDA defined in time for the cross-compiler.
(lambda nil)
- ;; The lexically enclosing cleanup, or NIL if none enclosing within Lambda.
+ ;; the lexically enclosing cleanup, or NIL if none enclosing within Lambda
;;
;; FIXME: This should be :TYPE (OR CLEANUP NULL), but it was too hard
;; to get CLEANUP defined in time for the cross-compiler.
(cleanup nil)
;; The representation of the current OPTIMIZE policy.
(cookie *default-cookie* :type cookie)
- ;; The policy that takes effect in XEPs and related syntax parsing functions.
- ;; Slots in this cookie may be null to indicate that the normal value in
- ;; effect.
+ ;; the policy that takes effect in XEPs and related syntax parsing
+ ;; functions. Slots in this cookie may be null to indicate that the
+ ;; normal value in effect.
(interface-cookie *default-interface-cookie* :type cookie)
- ;; an alist of miscellaneous options that are associated with the lexical
- ;; environment
+ ;; an alist of miscellaneous options that are associated with the
+ ;; lexical environment
(options nil :type list))
(t
(%argument-count-error ,n-supplied)))))))))
-;;; Make an external entry point (XEP) for Fun and return it. We
-;;; convert the result of Make-XEP-Lambda in the correct environment,
-;;; then associate this lambda with Fun as its XEP. After the
+;;; Make an external entry point (XEP) for FUN and return it. We
+;;; convert the result of MAKE-XEP-LAMBDA in the correct environment,
+;;; then associate this lambda with FUN as its XEP. After the
;;; conversion, we iterate over the function's associated lambdas,
;;; redoing local call analysis so that the XEP calls will get
;;; converted. We also bind *LEXENV* to change the compilation policy
;;; over to the interface policy.
;;;
-;;; We set Reanalyze and Reoptimize in the component, just in case we
+;;; We set REANALYZE and REOPTIMIZE in the component, just in case we
;;; discover an XEP after the initial local call analyze pass.
(defun make-external-entry-point (fun)
(declare (type functional fun))
(res (find-used-parameters arg))))))
) ; EVAL-WHEN
-;;; This macro provides some syntactic sugar for querying the settings of
-;;; the compiler policy parameters.
+;;; This macro provides some syntactic sugar for querying the settings
+;;; of the compiler policy parameters.
+;;;
+;;; Test whether some conditions apply to the current compiler policy
+;;; for Node. Each condition is a predicate form which accesses the
+;;; policy values by referring to them as the variables SPEED, SPACE,
+;;; SAFETY, CSPEED, BREVITY and DEBUG. The results of all the
+;;; conditions are combined with AND and returned as the result.
+;;;
+;;; NODE is a form which is evaluated to obtain the node which the
+;;; policy is for. If NODE is NIL, then we use the current policy as
+;;; defined by *DEFAULT-COOKIE* and *CURRENT-COOKIE*. This option is
+;;; only well defined during IR1 conversion.
(defmacro policy (node &rest conditions)
- #!+sb-doc
- "Policy Node Condition*
- Test whether some conditions apply to the current compiler policy for Node.
- Each condition is a predicate form which accesses the policy values by
- referring to them as the variables SPEED, SPACE, SAFETY, CSPEED, BREVITY and
- DEBUG. The results of all the conditions are combined with AND and returned
- as the result.
-
- Node is a form which is evaluated to obtain the node which the policy is for.
- If Node is NIL, then we use the current policy as defined by *DEFAULT-COOKIE*
- and *CURRENT-COOKIE*. This option is only well defined during IR1
- conversion."
(let* ((form `(and ,@conditions))
(n-cookie (gensym))
(binds (mapcar
\f
;;;; source-hacking defining forms
-;;; Passed to PARSE-DEFMACRO when we want compiler errors instead of real
-;;; errors.
+;;; to be passed to PARSE-DEFMACRO when we want compiler errors
+;;; instead of real errors
#!-sb-fluid (declaim (inline convert-condition-into-compiler-error))
(defun convert-condition-into-compiler-error (datum &rest stuff)
(if (stringp datum)
(apply #'make-condition datum stuff)
datum))))
-;;; Parse DEFMACRO-style lambda-list, setting things up so that a
+;;; Parse a DEFMACRO-style lambda-list, setting things up so that a
;;; compiler error happens if the syntax is invalid.
+;;;
+;;; Define a function that converts a special form or other magical
+;;; thing into IR1. LAMBDA-LIST is a defmacro style lambda list.
+;;; START-VAR and CONT-VAR are bound to the start and result
+;;; continuations for the resulting IR1. KIND is the function kind to
+;;; associate with NAME.
(defmacro def-ir1-translator (name (lambda-list start-var cont-var
&key (kind :special-form))
&body body)
- #!+sb-doc
- "Def-IR1-Translator Name (Lambda-List Start-Var Cont-Var {Key Value}*)
- [Doc-String] Form*
- Define a function that converts a Special-Form or other magical thing into
- IR1. Lambda-List is a defmacro style lambda list. Start-Var and Cont-Var
- are bound to the start and result continuations for the resulting IR1.
- This keyword is defined:
- Kind
- The function kind to associate with Name (default :special-form)."
(let ((fn-name (symbolicate "IR1-CONVERT-" name))
(n-form (gensym))
(n-env (gensym)))
(error "can't FUNCALL the SYMBOL-FUNCTION of ~
special forms")))))))))
-;;; Similar to DEF-IR1-TRANSLATOR, except that we pass if the syntax is
-;;; invalid.
+;;; (This is similar to DEF-IR1-TRANSLATOR, except that we pass if the
+;;; syntax is invalid.)
+;;;
+;;; Define a macro-like source-to-source transformation for the
+;;; function NAME. A source transform may "pass" by returning a
+;;; non-nil second value. If the transform passes, then the form is
+;;; converted as a normal function call. If the supplied arguments are
+;;; not compatible with the specified LAMBDA-LIST, then the transform
+;;; automatically passes.
+;;;
+;;; Source transforms may only be defined for functions. Source
+;;; transformation is not attempted if the function is declared
+;;; NOTINLINE. Source transforms should not examine their arguments.
+;;; If it matters how the function is used, then DEFTRANSFORM should
+;;; be used to define an IR1 transformation.
+;;;
+;;; If the desirability of the transformation depends on the current
+;;; OPTIMIZE parameters, then the POLICY macro should be used to
+;;; determine when to pass.
(defmacro def-source-transform (name lambda-list &body body)
- #!+sb-doc
- "Def-Source-Transform Name Lambda-List Form*
- Define a macro-like source-to-source transformation for the function Name.
- A source transform may \"pass\" by returning a non-nil second value. If the
- transform passes, then the form is converted as a normal function call. If
- the supplied arguments are not compatible with the specified lambda-list,
- then the transform automatically passes.
-
- Source-Transforms may only be defined for functions. Source transformation
- is not attempted if the function is declared Notinline. Source transforms
- should not examine their arguments. If it matters how the function is used,
- then Deftransform should be used to define an IR1 transformation.
-
- If the desirability of the transformation depends on the current Optimize
- parameters, then the Policy macro should be used to determine when to pass."
(let ((fn-name
(if (listp name)
(collect ((pieces))
,body))
(setf (info :function :source-transform ',name) #',fn-name)))))
+;;; Define a function that converts a use of (%PRIMITIVE NAME ..)
+;;; into Lisp code. LAMBDA-LIST is a DEFMACRO-style lambda list.
(defmacro def-primitive-translator (name lambda-list &body body)
- #!+sb-doc
- "DEF-PRIMITIVE-TRANSLATOR Name Lambda-List Form*
- Define a function that converts a use of (%PRIMITIVE Name ...) into Lisp
- code. Lambda-List is a DEFMACRO-style lambda list."
(let ((fn-name (symbolicate "PRIMITIVE-TRANSLATE-" name))
(n-form (gensym))
(n-env (gensym)))
'(cerror "Skip this form."
"compile-time read error"))))
-;;; If Stream is present, return it, otherwise open a stream to the
+;;; If STREAM is present, return it, otherwise open a stream to the
;;; current file. There must be a current file. When we open a new
;;; file, we also reset *PACKAGE* and policy. This gives the effect of
;;; rebinding around each file.
;;; *DEFAULT-COOKIE* as the policy. The need for this hack is due to
;;; the quirk that there is no way to represent in a cookie that an
;;; optimize quality came from the default.
+;;; FIXME: Ideally, something should be done so that DECLAIM inside LOCALLY
+;;; works OK. Failing that, at least we could issue a warning instead
+;;; of silently screwing up.
(defun process-top-level-locally (form path)
(declare (list path))
(multiple-value-bind (forms decls) (sb!sys:parse-body (cdr form) nil)
(format stream
"obsolete structure error in ~S:~@
for a structure of type: ~S"
- (sb-conditions::condition-function-name condition)
+ (sb-kernel::condition-function-name condition)
(type-of (obsolete-structure-datum condition))))))
(defun obsolete-instance-trap (owrapper nwrapper instance)
;;; versions, and a string like "0.6.5.12" is used for versions which
;;; aren't released but correspond only to CVS tags or snapshots.
-"0.6.9.5"
+"0.6.9.6"