X-Git-Url: http://repo.macrolet.net/gitweb/?a=blobdiff_plain;f=src%2Fcode%2Fearly-extensions.lisp;h=b73ac29033f7c44aa273907cbd28a163c7728f1e;hb=83ff95b8a70b1dc7cfffdf0a6bb7f4500ebe1ca1;hp=833adb7169b430b882d4db8460851bc8e4349e73;hpb=b6aed043108ac99142b124306a346d18a99d21ef;p=sbcl.git diff --git a/src/code/early-extensions.lisp b/src/code/early-extensions.lisp index 833adb7..b73ac29 100644 --- a/src/code/early-extensions.lisp +++ b/src/code/early-extensions.lisp @@ -13,21 +13,40 @@ (in-package "SB!IMPL") +(defvar *core-pathname* nil + #!+sb-doc + "The absolute pathname of the running SBCL core.") + +(defvar *runtime-pathname* nil + #!+sb-doc + "The absolute pathname of the running SBCL runtime.") + ;;; something not EQ to anything we might legitimately READ (defparameter *eof-object* (make-symbol "EOF-OBJECT")) -;;; a type used for indexing into arrays, and for related quantities -;;; like lengths of lists +(eval-when (:compile-toplevel :load-toplevel :execute) + (defconstant max-hash sb!xc:most-positive-fixnum)) + +(def!type hash () + `(integer 0 ,max-hash)) + +;;; a type used for indexing into sequences, and for related +;;; quantities like lengths of lists and other sequences. ;;; -;;; It's intentionally limited to one less than the -;;; ARRAY-DIMENSION-LIMIT for efficiency reasons, because in SBCL -;;; ARRAY-DIMENSION-LIMIT is MOST-POSITIVE-FIXNUM, and staying below -;;; that lets the system know it can increment a value of this type -;;; without having to worry about using a bignum to represent the -;;; result. +;;; A more correct value for the exclusive upper bound for indexing +;;; would be (1- ARRAY-DIMENSION-LIMIT) since ARRAY-DIMENSION-LIMIT is +;;; the exclusive maximum *size* of one array dimension (As specified +;;; in CLHS entries for MAKE-ARRAY and "valid array dimensions"). The +;;; current value is maintained to avoid breaking existing code that +;;; also uses that type for upper bounds on indices (e.g. sequence +;;; length). ;;; -;;; (It should be safe to use ARRAY-DIMENSION-LIMIT as an exclusive -;;; bound because ANSI specifies it as an exclusive bound.) +;;; In SBCL, ARRAY-DIMENSION-LIMIT is arranged to be a little smaller +;;; than MOST-POSITIVE-FIXNUM, for implementation (see comment above +;;; ARRAY-DIMENSION-LIMIT) and efficiency reasons: staying below +;;; MOST-POSITIVE-FIXNUM lets the system know it can increment a value +;;; of type INDEX without having to worry about using a bignum to +;;; represent the result. (def!type index () `(integer 0 (,sb!xc:array-dimension-limit))) ;;; like INDEX, but only up to half the maximum. Used by hash-table @@ -102,7 +121,7 @@ ((or (atom result) (not (eq (car result) 'values))) `(values ,result &optional)) - ((intersection (cdr result) lambda-list-keywords) + ((intersection (cdr result) sb!xc:lambda-list-keywords) result) (t `(values ,@(cdr result) &optional))))) `(function ,args ,result))) @@ -377,8 +396,8 @@ ;;; not really an old-fashioned function, but what the calling ;;; convention should've been: like NTH, but with the same argument -;;; order as in all the other dereferencing functions, with the -;;; collection first and the index second +;;; order as in all the other indexed dereferencing functions, with +;;; the collection first and the index second (declaim (inline nth-but-with-sane-arg-order)) (declaim (ftype (function (list index) t) nth-but-with-sane-arg-order)) (defun nth-but-with-sane-arg-order (list index) @@ -395,11 +414,12 @@ ;;;; miscellaneous iteration extensions -;;; "the ultimate iteration macro" +;;; like Scheme's named LET ;;; -;;; note for Schemers: This seems to be identical to Scheme's "named LET". +;;; (CMU CL called this ITERATE, and commented it as "the ultimate +;;; iteration macro...". I (WHN) found the old name insufficiently +;;; specific to remind me what the macro means, so I renamed it.) (defmacro named-let (name binds &body body) - #!+sb-doc (dolist (x binds) (unless (proper-list-of-length-p x 2) (error "malformed NAMED-LET variable spec: ~S" x))) @@ -415,7 +435,6 @@ (eq (car clause) 'ignore)))) (cdr decl)))) decls)) - ;;; just like DOLIST, but with one-dimensional arrays (defmacro dovector ((elt vector &optional result) &body body) (multiple-value-bind (forms decls) (parse-body body :doc-string-allowed nil) @@ -433,17 +452,35 @@ (tagbody ,@forms))))))) -;;; Iterate over the entries in a HASH-TABLE. -(defmacro dohash ((key-var value-var table &optional result) &body body) +;;; Iterate over the entries in a HASH-TABLE, first obtaining the lock +;;; if the table is a synchronized table. +(defmacro dohash (((key-var value-var) table &key result locked) &body body) (multiple-value-bind (forms decls) (parse-body body :doc-string-allowed nil) - (let ((gen (gensym)) - (n-more (gensym))) - `(with-hash-table-iterator (,gen ,table) - (loop - (multiple-value-bind (,n-more ,key-var ,value-var) (,gen) - ,@decls - (unless ,n-more (return ,result)) - ,@forms)))))) + (with-unique-names (gen n-more n-table) + (let ((iter-form `(with-hash-table-iterator (,gen ,n-table) + (loop + (multiple-value-bind (,n-more ,key-var ,value-var) (,gen) + ,@decls + (unless ,n-more (return ,result)) + ,@forms))))) + `(let ((,n-table ,table)) + ,(if locked + `(with-locked-system-table (,n-table) + ,iter-form) + iter-form)))))) + +;;; Executes BODY for all entries of PLIST with KEY and VALUE bound to +;;; the respective keys and values. +(defmacro doplist ((key val) plist &body body) + (with-unique-names (tail) + `(let ((,tail ,plist) ,key ,val) + (loop (when (null ,tail) (return nil)) + (setq ,key (pop ,tail)) + (when (null ,tail) + (error "malformed plist, odd number of elements")) + (setq ,val (pop ,tail)) + (progn ,@body))))) + ;;;; hash cache utility @@ -500,20 +537,30 @@ ;;; the specified name. (:INIT-WRAPPER is set to COLD-INIT-FORMS ;;; in type system definitions so that caches will be created ;;; before top level forms run.) +(defvar *cache-vector-symbols* nil) + +(defun drop-all-hash-caches () + (dolist (name *cache-vector-symbols*) + (set name nil))) + (defmacro define-hash-cache (name args &key hash-function hash-bits default (init-wrapper 'progn) (values 1)) - (let* ((var-name (symbolicate "*" name "-CACHE-VECTOR*")) + (let* ((var-name (symbolicate "**" name "-CACHE-VECTOR**")) + (probes-name (when *profile-hash-cache* + (symbolicate "**" name "-CACHE-PROBES**"))) + (misses-name (when *profile-hash-cache* + (symbolicate "**" name "-CACHE-MISSES**"))) (nargs (length args)) (size (ash 1 hash-bits)) (default-values (if (and (consp default) (eq (car default) 'values)) (cdr default) (list default))) - (args-and-values (gensym)) + (args-and-values (sb!xc:gensym "ARGS-AND-VALUES")) (args-and-values-size (+ nargs values)) - (n-index (gensym)) - (n-cache (gensym))) - + (n-index (sb!xc:gensym "INDEX")) + (n-cache (sb!xc:gensym "CACHE"))) + (declare (ignorable probes-name misses-name)) (unless (= (length default-values) values) (error "The number of default values ~S differs from :VALUES ~W." default values)) @@ -527,7 +574,7 @@ (values-refs) (values-names)) (dotimes (i values) - (let ((name (gensym))) + (let ((name (sb!xc:gensym "VALUE"))) (values-names name) (values-refs `(svref ,args-and-values (+ ,nargs ,i))) (sets `(setf (svref ,args-and-values (+ ,nargs ,i)) ,name)))) @@ -543,37 +590,36 @@ (incf n))) (when *profile-hash-cache* - (let ((n-probe (symbolicate "*" name "-CACHE-PROBES*")) - (n-miss (symbolicate "*" name "-CACHE-MISSES*"))) - (inits `(setq ,n-probe 0)) - (inits `(setq ,n-miss 0)) - (forms `(defvar ,n-probe)) - (forms `(defvar ,n-miss)) - (forms `(declaim (fixnum ,n-miss ,n-probe))))) + (inits `(setq ,probes-name 0)) + (inits `(setq ,misses-name 0)) + (forms `(declaim (fixnum ,probes-name ,misses-name)))) (let ((fun-name (symbolicate name "-CACHE-LOOKUP"))) (inlines fun-name) (forms `(defun ,fun-name ,(arg-vars) ,@(when *profile-hash-cache* - `((incf ,(symbolicate "*" name "-CACHE-PROBES*")))) - (let* ((,n-index (,hash-function ,@(arg-vars))) - (,n-cache ,var-name) - (,args-and-values (svref ,n-cache ,n-index))) - (cond ((and ,args-and-values - ,@(tests)) - (values ,@(values-refs))) - (t + `((incf ,probes-name))) + (flet ((miss () ,@(when *profile-hash-cache* - `((incf ,(symbolicate "*" name "-CACHE-MISSES*")))) - ,default)))))) + `((incf ,misses-name))) + (return-from ,fun-name ,default))) + (let* ((,n-index (,hash-function ,@(arg-vars))) + (,n-cache (or ,var-name (miss))) + (,args-and-values (svref ,n-cache ,n-index))) + (cond ((and (not (eql 0 ,args-and-values)) + ,@(tests)) + (values ,@(values-refs))) + (t + (miss)))))))) (let ((fun-name (symbolicate name "-CACHE-ENTER"))) (inlines fun-name) (forms `(defun ,fun-name (,@(arg-vars) ,@(values-names)) (let ((,n-index (,hash-function ,@(arg-vars))) - (,n-cache ,var-name) + (,n-cache (or ,var-name + (setq ,var-name (make-array ,size :initial-element 0)))) (,args-and-values (make-array ,args-and-values-size))) ,@(sets) (setf (svref ,n-cache ,n-index) ,args-and-values)) @@ -582,16 +628,19 @@ (let ((fun-name (symbolicate name "-CACHE-CLEAR"))) (forms `(defun ,fun-name () - (fill ,var-name nil))) - (forms `(,fun-name))) + (setq ,var-name nil)))) - (inits `(unless (boundp ',var-name) - (setq ,var-name (make-array ,size :initial-element nil)))) + ;; Needed for cold init! + (inits `(setq ,var-name nil)) #!+sb-show (inits `(setq *hash-caches-initialized-p* t)) `(progn - (defvar ,var-name) - (declaim (type (simple-vector ,size) ,var-name)) + (pushnew ',var-name *cache-vector-symbols*) + (defglobal ,var-name nil) + ,@(when *profile-hash-cache* + `((defglobal ,probes-name 0) + (defglobal ,misses-name 0))) + (declaim (type (or null (simple-vector ,size)) ,var-name)) #!-sb-fluid (declaim (inline ,@(inlines))) (,init-wrapper ,@(inits)) ,@(forms) @@ -605,42 +654,40 @@ (let ((default-values (if (and (consp default) (eq (car default) 'values)) (cdr default) (list default))) - (arg-names (mapcar #'car args))) - (collect ((values-names)) - (dotimes (i values) - (values-names (gensym))) - (multiple-value-bind (body decls doc) (parse-body body-decls-doc) - `(progn - (define-hash-cache ,name ,args ,@options) - (defun ,name ,arg-names - ,@decls - ,doc - (cond #!+sb-show - ((not (boundp '*hash-caches-initialized-p*)) - ;; This shouldn't happen, but it did happen to me - ;; when revising the type system, and it's a lot - ;; easier to figure out what what's going on with - ;; that kind of problem if the system can be kept - ;; alive until cold boot is complete. The recovery - ;; mechanism should definitely be conditional on - ;; some debugging feature (e.g. SB-SHOW) because - ;; it's big, duplicating all the BODY code. -- WHN - (/show0 ,name " too early in cold init, uncached") - (/show0 ,(first arg-names) "=..") - (/hexstr ,(first arg-names)) - ,@body) - (t - (multiple-value-bind ,(values-names) - (,(symbolicate name "-CACHE-LOOKUP") ,@arg-names) - (if (and ,@(mapcar (lambda (val def) - `(eq ,val ,def)) - (values-names) default-values)) - (multiple-value-bind ,(values-names) - (progn ,@body) - (,(symbolicate name "-CACHE-ENTER") ,@arg-names - ,@(values-names)) - (values ,@(values-names))) - (values ,@(values-names)))))))))))) + (arg-names (mapcar #'car args)) + (values-names (make-gensym-list values))) + (multiple-value-bind (body decls doc) (parse-body body-decls-doc) + `(progn + (define-hash-cache ,name ,args ,@options) + (defun ,name ,arg-names + ,@decls + ,doc + (cond #!+sb-show + ((not (boundp '*hash-caches-initialized-p*)) + ;; This shouldn't happen, but it did happen to me + ;; when revising the type system, and it's a lot + ;; easier to figure out what what's going on with + ;; that kind of problem if the system can be kept + ;; alive until cold boot is complete. The recovery + ;; mechanism should definitely be conditional on some + ;; debugging feature (e.g. SB-SHOW) because it's big, + ;; duplicating all the BODY code. -- WHN + (/show0 ,name " too early in cold init, uncached") + (/show0 ,(first arg-names) "=..") + (/hexstr ,(first arg-names)) + ,@body) + (t + (multiple-value-bind ,values-names + (,(symbolicate name "-CACHE-LOOKUP") ,@arg-names) + (if (and ,@(mapcar (lambda (val def) + `(eq ,val ,def)) + values-names default-values)) + (multiple-value-bind ,values-names + (progn ,@body) + (,(symbolicate name "-CACHE-ENTER") ,@arg-names + ,@values-names) + (values ,@values-names)) + (values ,@values-names)))))))))) (defmacro define-cached-synonym (name &optional (original (symbolicate "%" name))) @@ -668,13 +715,13 @@ ;;; our equality tests, because MEMBER and friends refer to EQLity. ;;; So: (defun equal-but-no-car-recursion (x y) - (cond - ((eql x y) t) - ((consp x) - (and (consp y) - (eql (car x) (car y)) - (equal-but-no-car-recursion (cdr x) (cdr y)))) - (t nil))) + (do () (()) + (cond ((eql x y) (return t)) + ((and (consp x) + (consp y) + (eql (pop x) (pop y)))) + (t + (return))))) ;;;; package idioms @@ -747,38 +794,6 @@ (char= #\* (aref name 0)) (char= #\* (aref name (1- (length name)))))))) -;;; Some symbols are defined by ANSI to be self-evaluating. Return -;;; non-NIL for such symbols (and make the non-NIL value a traditional -;;; message, for use in contexts where the user asks us to change such -;;; a symbol). -(defun symbol-self-evaluating-p (symbol) - (declare (type symbol symbol)) - (cond ((eq symbol t) - "Veritas aeterna. (can't change T)") - ((eq symbol nil) - "Nihil ex nihil. (can't change NIL)") - ((keywordp symbol) - "Keyword values can't be changed.") - (t - nil))) - -;;; This function is to be called just before a change which would -;;; affect the symbol value. (We don't absolutely have to call this -;;; function before such changes, since such changes are given as -;;; undefined behavior. In particular, we don't if the runtime cost -;;; would be annoying. But otherwise it's nice to do so.) -(defun about-to-modify-symbol-value (symbol) - (declare (type symbol symbol)) - (let ((reason (symbol-self-evaluating-p symbol))) - (when reason - (error reason))) - ;; (Note: Just because a value is CONSTANTP is not a good enough - ;; reason to complain here, because we want DEFCONSTANT to be able - ;; to use this function, and it's legal to DEFCONSTANT a constant as - ;; long as the new value is EQL to the old value.) - (values)) - - ;;; If COLD-FSET occurs not at top level, just treat it as an ordinary ;;; assignment instead of doing cold static linking. That way things like ;;; (FLET ((FROB (X) ..)) @@ -826,9 +841,9 @@ (unless (proper-list-of-length-p spec 2) (error "malformed ONCE-ONLY binding spec: ~S" spec)) (let* ((name (first spec)) - (exp-temp (gensym (symbol-name name)))) + (exp-temp (gensym "ONCE-ONLY"))) `(let ((,exp-temp ,(second spec)) - (,name (gensym "ONCE-ONLY-"))) + (,name (sb!xc:gensym ,(symbol-name name)))) `(let ((,,name ,,exp-temp)) ,,(frob (rest specs) body)))))))) @@ -859,18 +874,18 @@ ;;; guts of complex systems anyway, I replaced it too.) (defmacro aver (expr) `(unless ,expr - (%failed-aver ,(format nil "~A" expr)))) + (%failed-aver ',expr))) -(defun %failed-aver (expr-as-string) +(defun %failed-aver (expr) ;; hackish way to tell we're in a cold sbcl and output the - ;; message before signallign error, as it may be this is too + ;; message before signalling error, as it may be this is too ;; early in the cold init. (when (find-package "SB!C") (fresh-line) (write-line "failed AVER:") - (write-line expr-as-string) + (write expr) (terpri)) - (bug "~@" expr-as-string)) + (bug "~@" expr)) (defun bug (format-control &rest format-arguments) (error 'bug @@ -920,20 +935,27 @@ (def-constantly-fun constantly-nil nil) (def-constantly-fun constantly-0 0)) -;;; If X is an atom, see whether it is present in *FEATURES*. Also +;;; If X is a symbol, see whether it is present in *FEATURES*. Also ;;; handle arbitrary combinations of atoms using NOT, AND, OR. (defun featurep (x) - (if (consp x) - (case (car x) - ((:not not) - (if (cddr x) - (error "too many subexpressions in feature expression: ~S" x) - (not (featurep (cadr x))))) - ((:and and) (every #'featurep (cdr x))) - ((:or or) (some #'featurep (cdr x))) - (t - (error "unknown operator in feature expression: ~S." x))) - (not (null (memq x *features*))))) + (typecase x + (cons + (case (car x) + ((:not not) + (cond + ((cddr x) + (error "too many subexpressions in feature expression: ~S" x)) + ((null (cdr x)) + (error "too few subexpressions in feature expression: ~S" x)) + (t (not (featurep (cadr x)))))) + ((:and and) (every #'featurep (cdr x))) + ((:or or) (some #'featurep (cdr x))) + (t + (error "unknown operator in feature expression: ~S." x)))) + (symbol (not (null (memq x *features*)))) + (t + (error "invalid feature expression: ~S" x)))) + ;;;; utilities for two-VALUES predicates @@ -1031,7 +1053,7 @@ (let ((first? t) maybe-print-space (reversed-prints nil) - (stream (gensym "STREAM"))) + (stream (sb!xc:gensym "STREAM"))) (flet ((sref (slot-name) `(,(symbolicate conc-name slot-name) structure))) (dolist (slot-desc slot-descs) @@ -1082,10 +1104,126 @@ (translate-logical-pathname possibly-logical-pathname) possibly-logical-pathname)) -(defun deprecation-warning (bad-name &optional good-name) - (warn "using deprecated ~S~@[, should use ~S instead~]" - bad-name - good-name)) +;;;; Deprecating stuff + +(defun normalize-deprecation-replacements (replacements) + (if (or (not (listp replacements)) + (eq 'setf (car replacements))) + (list replacements) + replacements)) + +(defun deprecation-error (since name replacements) + (error 'deprecation-error + :name name + :replacements (normalize-deprecation-replacements replacements) + :since since)) + +(defun deprecation-warning (state since name replacements + &key (runtime-error (neq :early state))) + (warn (ecase state + (:early 'early-deprecation-warning) + (:late 'late-deprecation-warning) + (:final 'final-deprecation-warning)) + :name name + :replacements (normalize-deprecation-replacements replacements) + :since since + :runtime-error runtime-error)) + +(defun deprecated-function (since name replacements) + (lambda (&rest deprecated-function-args) + (declare (ignore deprecated-function-args)) + (deprecation-error since name replacements))) + +(defun deprecation-compiler-macro (state since name replacements) + (lambda (form env) + (declare (ignore env)) + (deprecation-warning state since name replacements) + form)) + +;;; STATE is one of +;;; +;;; :EARLY, for a compile-time style-warning. +;;; :LATE, for a compile-time full warning. +;;; :FINAL, for a compile-time full warning and runtime error. +;;; +;;; Suggested duration of each stage is one year, but some things can move faster, +;;; and some widely used legacy APIs might need to move slower. Internals we don't +;;; usually add deprecation notes for, but sometimes an internal API actually has +;;; several external users, in which case we try to be nice about it. +;;; +;;; When you deprecate something, note it here till it is fully gone: makes it +;;; easier to keep things progressing orderly. Also add the relevant section +;;; (or update it when deprecation proceeds) in the manual, in +;;; deprecated.texinfo. +;;; +;;; EARLY: +;;; - SB-THREAD::GET-MUTEX, since 1.0.37.33 (04/2010) -> Late: 01/2013 +;;; ^- initially deprecated without compile-time warning, hence the schedule +;;; - SB-THREAD::SPINLOCK (type), since 1.0.53.11 (08/2011) -> Late: 08/2012 +;;; - SB-THREAD::MAKE-SPINLOCK, since 1.0.53.11 (08/2011) -> Late: 08/2012 +;;; - SB-THREAD::WITH-SPINLOCK, since 1.0.53.11 (08/2011) -> Late: 08/2012 +;;; - SB-THREAD::WITH-RECURSIVE-SPINLOCK, since 1.0.53.11 (08/2011) -> Late: 08/2012 +;;; - SB-THREAD::GET-SPINLOCK, since 1.0.53.11 (08/2011) -> Late: 08/2012 +;;; - SB-THREAD::RELEASE-SPINLOCK, since 1.0.53.11 (08/2011) -> Late: 08/2012 +;;; - SB-THREAD::SPINLOCK-VALUE, since 1.0.53.11 (08/2011) -> Late: 08/2012 +;;; - SB-THREAD::SPINLOCK-NAME, since 1.0.53.11 (08/2011) -> Late: 08/2012 +;;; - SETF SB-THREAD::SPINLOCK-NAME, since 1.0.53.11 (08/2011) -> Late: 08/2012 +;;; - SB-C::MERGE-TAIL-CALLS (policy), since 1.0.53.74 (11/2011) -> Late: 11/2012 +;;; - SB-EXT:QUIT, since 1.0.56.55 (05/2012) -> Late: 05/2013 +;;; - SB-UNIX:UNIX-EXIT, since 1.0.56.55 (05/2012) -> Late: 05/2013 +;;; - SB-DEBUG:*SHOW-ENTRY-POINT-DETAILS*, since 1.1.4.9 (02/2013) -> Late: 02/2014 +;;; +;;; LATE: +;;; - SB-SYS:OUTPUT-RAW-BYTES, since 1.0.8.16 (06/2007) -> Final: anytime +;;; Note: make sure CLX doesn't use it anymore! +;;; - SB-C::STACK-ALLOCATE-DYNAMIC-EXTENT (policy), since 1.0.19.7 -> Final: anytime +;;; - SB-C::STACK-ALLOCATE-VECTOR (policy), since 1.0.19.7 -> Final: anytime +;;; - SB-C::STACK-ALLOCATE-VALUE-CELLS (policy), since 1.0.19.7 -> Final: anytime +;;; - SB-INTROSPECT:FUNCTION-ARGLIST, since 1.0.24.5 (01/2009) -> Final: anytime +;;; - SB-THREAD:JOIN-THREAD-ERROR-THREAD, since 1.0.29.17 (06/2009) -> Final: 09/2012 +;;; - SB-THREAD:INTERRUPT-THREAD-ERROR-THREAD since 1.0.29.17 (06/2009) -> Final: 06/2012 + +(defmacro define-deprecated-function (state since name replacements lambda-list &body body) + (let* ((replacements (normalize-deprecation-replacements replacements)) + (doc + (let ((*package* (find-package :keyword)) + (*print-pretty* nil)) + (apply #'format nil + "~S has been deprecated as of SBCL ~A.~ + ~#[~;~2%Use ~S instead.~;~2%~ + Use ~S or ~S instead.~:;~2%~ + Use~@{~#[~; or~] ~S~^,~} instead.~]" + name since replacements)))) + `(progn + ,(ecase state + ((:early :late) + `(progn + (defun ,name ,lambda-list + ,doc + ,@body))) + ((:final) + `(progn + (declaim (ftype (function * nil) ,name)) + (setf (fdefinition ',name) + (deprecated-function ',name ',replacements ,since)) + (setf (documentation ',name 'function) ,doc)))) + (setf (compiler-macro-function ',name) + (deprecation-compiler-macro ,state ,since ',name ',replacements))))) + +(defun check-deprecated-variable (name) + (let ((info (info :variable :deprecated name))) + (when info + (deprecation-warning (car info) (cdr info) name nil)))) + +(defmacro define-deprecated-variable (state since name &key (value nil valuep) replacement) + `(progn + (setf (info :variable :deprecated ',name) (cons ,state ,since)) + ,@(when (member state '(:early :late)) + `((defvar ,name ,@(when valuep (list value)) + ,(let ((*package* (find-package :keyword))) + (format nil + "~@<~S has been deprecated as of SBCL ~A~@[, use ~S instead~].~:>" + name since replacement))))))) ;;; Anaphoric macros (defmacro awhen (test &body body) @@ -1193,6 +1331,20 @@ (*print-length* (or (true *print-length*) 12))) (funcall function)))) +;;; Returns a list of members of LIST. Useful for dealing with circular lists. +;;; For a dotted list returns a secondary value of T -- in which case the +;;; primary return value does not include the dotted tail. +;;; If the maximum length is reached, return a secondary value of :MAYBE. +(defun list-members (list &key max-length) + (when list + (do ((tail (cdr list) (cdr tail)) + (members (list (car list)) (cons (car tail) members)) + (count 0 (1+ count))) + ((or (not (consp tail)) (eq tail list) + (and max-length (>= count max-length))) + (values members (or (not (listp tail)) + (and (>= count max-length) :maybe))))))) + ;;; Default evaluator mode (interpeter / compiler) (declaim (type (member :compile #!+sb-eval :interpret) *evaluator-mode*)) @@ -1204,51 +1356,96 @@ to :INTERPRET, an interpreter will be used.") ;;; Helper for making the DX closure allocation in macros expanding ;;; to CALL-WITH-FOO less ugly. -;;; -;;; This expands to something like -;;; -;;; (flet ((foo (...) )) -;;; (declare (optimize stack-allocate-dynamic-extent)) -;;; (flet ((foo (...) -;;; (foo ...)) -;;; (declare (dynamic-extent #'foo)) -;;; ))) -;;; -;;; The outer FLETs are inlined into the inner ones, and the inner ones -;;; are DX-allocated. The double-fletting is done to keep the bodies of -;;; the functions in an environment with correct policy: we don't want -;;; to force DX allocation in their bodies, which would be bad eg. -;;; in safe code. (defmacro dx-flet (functions &body forms) - (let ((names (mapcar #'car functions))) - `(flet ,functions - #-sb-xc-host - (declare (optimize sb!c::stack-allocate-dynamic-extent)) - (flet ,(mapcar - (lambda (f) - (let ((args (cadr f)) - (name (car f))) - (when (intersection args lambda-list-keywords) - ;; No fundamental reason not to support them, but we - ;; don't currently need them here. - (error "Non-required arguments not implemented for DX-FLET.")) - `(,name ,args - (,name ,@args)))) - functions) - (declare (dynamic-extent ,@(mapcar (lambda (x) `(function ,x)) names))) - ,@forms)))) - -;;; Another similar one -- but actually touches the policy of the body, -;;; so take care with this one... + `(flet ,functions + (declare (#+sb-xc-host dynamic-extent #-sb-xc-host truly-dynamic-extent + ,@(mapcar (lambda (func) `(function ,(car func))) functions))) + ,@forms)) + +;;; Another similar one. (defmacro dx-let (bindings &body forms) - `(locally - #-sb-xc-host - (declare (optimize sb!c::stack-allocate-dynamic-extent)) - (let ,bindings - (declare (dynamic-extent ,@(mapcar (lambda (bind) - (if (consp bind) - (car bind) - bind)) - bindings))) - ,@forms))) + `(let ,bindings + (declare (#+sb-xc-host dynamic-extent #-sb-xc-host truly-dynamic-extent + ,@(mapcar (lambda (bind) (if (consp bind) (car bind) bind)) + bindings))) + ,@forms)) + +(in-package "SB!KERNEL") + +(defun fp-zero-p (x) + (typecase x + (single-float (zerop x)) + (double-float (zerop x)) + #!+long-float + (long-float (zerop x)) + (t nil))) +(defun neg-fp-zero (x) + (etypecase x + (single-float + (if (eql x 0.0f0) + (make-unportable-float :single-float-negative-zero) + 0.0f0)) + (double-float + (if (eql x 0.0d0) + (make-unportable-float :double-float-negative-zero) + 0.0d0)) + #!+long-float + (long-float + (if (eql x 0.0l0) + (make-unportable-float :long-float-negative-zero) + 0.0l0)))) + +;;; Signalling an error when trying to print an error condition is +;;; generally a PITA, so whatever the failure encountered when +;;; wondering about FILE-POSITION within a condition printer, 'tis +;;; better silently to give up than to try to complain. +(defun file-position-or-nil-for-error (stream &optional (pos nil posp)) + ;; Arguably FILE-POSITION shouldn't be signalling errors at all; but + ;; "NIL if this cannot be determined" in the ANSI spec doesn't seem + ;; absolutely unambiguously to prohibit errors when, e.g., STREAM + ;; has been closed so that FILE-POSITION is a nonsense question. So + ;; my (WHN) impression is that the conservative approach is to + ;; IGNORE-ERRORS. (I encountered this failure from within a homebrew + ;; defsystemish operation where the ERROR-STREAM had been CL:CLOSEd, + ;; I think by nonlocally exiting through a WITH-OPEN-FILE, by the + ;; time an error was reported.) + (if posp + (ignore-errors (file-position stream pos)) + (ignore-errors (file-position stream)))) + +(defun stream-error-position-info (stream &optional position) + (unless (interactive-stream-p stream) + (let ((now (file-position-or-nil-for-error stream)) + (pos position)) + (when (and (not pos) now (plusp now)) + ;; FILE-POSITION is the next character -- error is at the previous one. + (setf pos (1- now))) + (let (lineno colno) + (when (and pos + (< pos sb!xc:array-dimension-limit) + (file-position stream :start)) + (let ((string + (make-string pos :element-type (stream-element-type stream)))) + (when (= pos (read-sequence string stream)) + ;; Lines count from 1, columns from 0. It's stupid and traditional. + (setq lineno (1+ (count #\Newline string)) + colno (- pos (or (position #\Newline string :from-end t) 0))))) + (file-position-or-nil-for-error stream now)) + (remove-if-not #'second + (list (list :line lineno) + (list :column colno) + (list :file-position pos))))))) + +(declaim (inline schwartzian-stable-sort-list)) +(defun schwartzian-stable-sort-list (list comparator &key key) + (if (null key) + (stable-sort (copy-list list) comparator) + (let* ((key (if (functionp key) + key + (symbol-function key))) + (wrapped (mapcar (lambda (x) + (cons x (funcall key x))) + list)) + (sorted (stable-sort wrapped comparator :key #'cdr))) + (map-into sorted #'car sorted))))