0.6.11.28:
[sbcl.git] / src / code / early-extensions.lisp
index 0288453..0d40d30 100644 (file)
 ;;;; provided with absolutely no warranty. See the COPYING and CREDITS
 ;;;; files for more information.
 
-(in-package "SB!EXT")
+(in-package "SB!IMPL")
+
+;;; 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
 (defconstant escape-char-code 27)
 (defconstant rubout-char-code 127)
 \f
-;;; Concatenate together the names of some strings and symbols,
-;;; producing a symbol in the current package.
-(eval-when (:compile-toplevel :load-toplevel :execute)
-  (declaim (ftype (function (&rest (or string symbol)) symbol) symbolicate))
-  (defun symbolicate (&rest things)
-    (values (intern (apply #'concatenate
-                          'string
-                          (mapcar #'string things))))))
-
-;;; like SYMBOLICATE, but producing keywords
-(defun keywordicate (&rest things)
-  (let ((*package* *keyword-package*))
-    (apply #'symbolicate things)))
-\f
 ;;;; miscellaneous iteration extensions
 
 (defmacro dovector ((elt vector &optional result) &rest forms)
 (eval-when (:compile-toplevel :load-toplevel :execute)
   (defvar *profile-hash-cache* nil))
 
-;;; :INIT-WRAPPER is set to COLD-INIT-FORMS in type system definitions
-;;; so that caches will be created before top-level forms run.
+;;; a flag for whether it's too early in cold init to use caches so
+;;; that we have a better chance of recovering so that we have a
+;;; better chance of getting the system running so that we have a
+;;; better chance of diagnosing the problem which caused us to use the
+;;; caches too early
+#!+sb-show
+(defvar *hash-caches-initialized-p*)
+
+;;; Define a hash cache that associates some number of argument values
+;;; with a result value. The TEST-FUNCTION paired with each ARG-NAME
+;;; is used to compare the value for that arg in a cache entry with a
+;;; supplied arg. The TEST-FUNCTION must not error when passed NIL as
+;;; its first arg, but need not return any particular value.
+;;; TEST-FUNCTION may be any thing that can be placed in CAR position.
+;;;
+;;; NAME is used to define these functions:
+;;; <name>-CACHE-LOOKUP Arg*
+;;;   See whether there is an entry for the specified ARGs in the
+;;;   cache. If not present, the :DEFAULT keyword (default NIL)
+;;;   determines the result(s).
+;;; <name>-CACHE-ENTER Arg* Value*
+;;;   Encache the association of the specified args with VALUE.
+;;; <name>-CACHE-CLEAR
+;;;   Reinitialize the cache, invalidating all entries and allowing
+;;;   the arguments and result values to be GC'd.
+;;;
+;;; These other keywords are defined:
+;;; :HASH-BITS <n>
+;;;   The size of the cache as a power of 2.
+;;; :HASH-FUNCTION function
+;;;   Some thing that can be placed in CAR position which will compute
+;;;   a value between 0 and (1- (expt 2 <hash-bits>)).
+;;; :VALUES <n>
+;;;   the number of return values cached for each function call
+;;; :INIT-WRAPPER <name>
+;;;   The code for initializing the cache is wrapped in a form with
+;;;   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.)
 (defmacro define-hash-cache (name args &key hash-function hash-bits default
                                  (init-wrapper 'progn)
                                  (values 1))
-  #!+sb-doc
-  "DEFINE-HASH-CACHE Name ({(Arg-Name Test-Function)}*) {Key Value}*
-  Define a hash cache that associates some number of argument values to a
-  result value. The Test-Function paired with each Arg-Name is used to compare
-  the value for that arg in a cache entry with a supplied arg. The
-  Test-Function must not error when passed NIL as its first arg, but need not
-  return any particular value. Test-Function may be any thing that can be
-  placed in CAR position.
-
-  Name is used to define these functions:
-
-  <name>-CACHE-LOOKUP Arg*
-      See whether there is an entry for the specified Args in the cache. If
-      not present, the :DEFAULT keyword (default NIL) determines the result(s).
-
-  <name>-CACHE-ENTER Arg* Value*
-      Encache the association of the specified args with Value.
-
-  <name>-CACHE-CLEAR
-      Reinitialize the cache, invalidating all entries and allowing the
-      arguments and result values to be GC'd.
-
-  These other keywords are defined:
-
-  :HASH-BITS <n>
-      The size of the cache as a power of 2.
-
-  :HASH-FUNCTION function
-      Some thing that can be placed in CAR position which will compute a value
-      between 0 and (1- (expt 2 <hash-bits>)).
-
-  :VALUES <n>
-      The number of values cached.
-
-  :INIT-WRAPPER <name>
-      The code for initializing the cache is wrapped in a form with the
-      specified name. Default PROGN."
-
   (let* ((var-name (symbolicate "*" name "-CACHE-VECTOR*"))
         (nargs (length args))
         (entry-size (+ nargs values))
       (let ((n 0))
         (dolist (arg args)
           (unless (= (length arg) 2)
-            (error "bad arg spec: ~S" arg))
+            (error "bad argument spec: ~S" arg))
           (let ((arg-name (first arg))
                 (test (second arg)))
             (arg-vars arg-name)
 
       (inits `(unless (boundp ',var-name)
                (setq ,var-name (make-array ,total-size))))
+      #!+sb-show (inits `(setq *hash-caches-initialized-p* t))
 
       `(progn
         (defvar ,var-name)
         ,@(forms)
         ',name))))
 
+;;; some syntactic sugar for defining a function whose values are
+;;; cached by DEFINE-HASH-CACHE
 (defmacro defun-cached ((name &rest options &key (values 1) default
                              &allow-other-keys)
                        args &body body-decls-doc)
-  #!+sb-doc
-  "DEFUN-CACHED (Name {Key Value}*) ({(Arg-Name Test-Function)}*) Form*
-  Some syntactic sugar for defining a function whose values are cached by
-  DEFINE-HASH-CACHE."
   (let ((default-values (if (and (consp default) (eq (car default) 'values))
                            (cdr default)
                            (list default)))
           (defun ,name ,arg-names
             ,@decls
             ,doc
-            (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))))))))))
+            (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))))))))))))
 \f
 ;;;; package idioms
 
 \f
 ;;;; miscellany
 
-;;; FIXME: What is this used for that SYMBOLICATE couldn't be used for instead?
-;;; If nothing, replace it.
-(eval-when (:compile-toplevel :load-toplevel :execute)
-  (defun concat-pnames (name1 name2)
-    (declare (symbol name1 name2))
-    (if name1
-       (intern (concatenate 'simple-string
-                            (symbol-name name1)
-                            (symbol-name name2)))
-       name2)))
-
 ;;; Is NAME a legal function name?
 (defun legal-function-name-p (name)
   (or (symbolp name)
            (symbolp (cadr name))
            (null (cddr name)))))
 
-;;; Given a function name, return the name for the BLOCK which encloses its
-;;; body (e.g. in DEFUN, DEFINE-COMPILER-MACRO, or FLET).
+;;; Given a function name, return the name for the BLOCK which
+;;; encloses its body (e.g. in DEFUN, DEFINE-COMPILER-MACRO, or FLET).
 (declaim (ftype (function ((or symbol cons)) symbol) function-name-block-name))
 (defun function-name-block-name (function-name)
   (cond ((symbolp function-name)
 (declaim (ftype (function (index) list) make-gensym-list))
 (defun make-gensym-list (n)
   (loop repeat n collect (gensym)))
+
+;;; ANSI guarantees that some symbols are self-evaluating. This
+;;; function is to be called just before a change which would affect
+;;; that. (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)
+  (declare (type symbol symbol))
+  (cond ((eq symbol t)
+        (error "Veritas aeterna. (can't change T)"))
+       ((eq symbol nil)
+        (error "Nihil ex nihil. (can't change NIL)"))
+       ((keywordp symbol)
+        (error "Keyword values can't be changed."))
+       ;; (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.)
+       ))
+
+;;; Return a function like FUN, but expecting its (two) arguments in
+;;; the opposite order that FUN does.
+(declaim (inline swapped-args-fun))
+(defun swapped-args-fun (fun)
+  (declare (type function fun))
+  (lambda (x y)
+    (funcall fun y x)))
+
+;;; like CL:ASSERT, but lighter-weight
+;;;
+;;; (As of sbcl-0.6.11.20, we were using some 400 calls to CL:ASSERT
+;;; in SBCL. The CL:ASSERT restarts and whatnot expand into a
+;;; significant amount of code when you multiply them by 400, so
+;;; replacing them with this should reduce the size of the system
+;;; by enough to be worthwhile.)
+(defmacro aver (expr)
+  `(unless ,expr
+     (%failed-aver ,(let ((*package* (find-package :keyword)))
+                     (format nil "~S" expr)))))
+(defun %failed-aver (expr-as-string)
+  (error "~@<failed AVER: ~2I~_~S~:>" expr-as-string))
+
+;;; Return the numeric value of a type bound, i.e. an interval bound
+;;; more or less in the format of bounds in ANSI's type specifiers,
+;;; where a bare numeric value is a closed bound and a list of a
+;;; single numeric value is an open bound.
+;;;
+;;; The "more or less" bit is that the no-bound-at-all case is
+;;; represented by NIL (not by * as in ANSI type specifiers); and in
+;;; this case we return NIL.
+(defun type-bound-number (x)
+  (if (consp x)
+      (destructuring-bind (result) x result)
+      x))
+
+;;; some commonly-occuring CONSTANTLY forms
+(macrolet ((def-constantly-fun (name constant-expr)
+            `(setf (symbol-function ',name)
+                   (constantly ,constant-expr))))
+  (def-constantly-fun constantly-t t)
+  (def-constantly-fun constantly-nil nil)
+  (def-constantly-fun constantly-0 0))
+\f
+;;;; utilities for two-VALUES predicates
+
+;;; sort of like ANY and EVERY, except:
+;;;   * We handle two-VALUES predicate functions, as SUBTYPEP does.
+;;;     (And if the result is uncertain, then we return (VALUES NIL NIL),
+;;;     as SUBTYPEP does.)
+;;;   * THING is just an atom, and we apply OP (an arity-2 function)
+;;;     successively to THING and each element of LIST.
+(defun any/type (op thing list)
+  (declare (type function op))
+  (let ((certain? t))
+    (dolist (i list (values nil certain?))
+      (multiple-value-bind (sub-value sub-certain?) (funcall op thing i)
+       (if sub-certain?
+           (when sub-value (return (values t t)))
+           (setf certain? nil))))))
+(defun every/type (op thing list)
+  (declare (type function op))
+  (let ((certain? t))
+    (dolist (i list (if certain? (values t t) (values nil nil)))
+      (multiple-value-bind (sub-value sub-certain?) (funcall op thing i)
+       (if sub-certain?
+           (unless sub-value (return (values nil t)))
+           (setf certain? nil))))))
+\f
+;;;; DEFPRINTER
+
+;;; These functions are called by the expansion of the DEFPRINTER
+;;; macro to do the actual printing.
+(declaim (ftype (function (symbol t stream &optional t) (values))
+               defprinter-prin1 defprinter-princ))
+(defun defprinter-prin1 (name value stream &optional indent)
+  (declare (ignore indent))
+  (defprinter-prinx #'prin1 name value stream))
+(defun defprinter-princ (name value stream &optional indent)
+  (declare (ignore indent))
+  (defprinter-prinx #'princ name value stream))
+(defun defprinter-prinx (prinx name value stream)
+  (declare (type function prinx))
+  (when *print-pretty*
+    (pprint-newline :linear stream))
+  (format stream ":~A " name)
+  (funcall prinx value stream)
+  (values))
+(defun defprinter-print-space (stream)
+  (write-char #\space stream))
+
+;;; Define some kind of reasonable PRINT-OBJECT method for a
+;;; STRUCTURE-OBJECT class.
+;;;
+;;; NAME is the name of the structure class, and CONC-NAME is the same
+;;; as in DEFSTRUCT.
+;;;
+;;; The SLOT-DESCS describe how each slot should be printed. Each
+;;; SLOT-DESC can be a slot name, indicating that the slot should
+;;; simply be printed. A SLOT-DESC may also be a list of a slot name
+;;; and other stuff. The other stuff is composed of keywords followed
+;;; by expressions. The expressions are evaluated with the variable
+;;; which is the slot name bound to the value of the slot. These
+;;; keywords are defined:
+;;;
+;;; :PRIN1    Print the value of the expression instead of the slot value.
+;;; :PRINC    Like :PRIN1, only PRINC the value
+;;; :TEST     Only print something if the test is true.
+;;;
+;;; If no printing thing is specified then the slot value is printed
+;;; as if by PRIN1.
+;;;
+;;; The structure being printed is bound to STRUCTURE and the stream
+;;; is bound to STREAM.
+(defmacro defprinter ((name &key (conc-name (concatenate 'simple-string
+                                                        (symbol-name name)
+                                                        "-")))
+                     &rest slot-descs)
+  (let ((first? t)
+       maybe-print-space
+       (reversed-prints nil)
+       (stream (gensym "STREAM")))
+    (flet ((sref (slot-name)
+            `(,(symbolicate conc-name slot-name) structure)))
+      (dolist (slot-desc slot-descs)
+       (if first?
+           (setf maybe-print-space nil
+                 first? nil)
+           (setf maybe-print-space `(defprinter-print-space ,stream)))
+       (cond ((atom slot-desc)
+              (push maybe-print-space reversed-prints)
+              (push `(defprinter-prin1 ',slot-desc ,(sref slot-desc) ,stream)
+                    reversed-prints))
+             (t
+              (let ((sname (first slot-desc))
+                    (test t))
+                (collect ((stuff))
+                  (do ((option (rest slot-desc) (cddr option)))
+                      ((null option)
+                       (push `(let ((,sname ,(sref sname)))
+                                (when ,test
+                                  ,maybe-print-space
+                                  ,@(or (stuff)
+                                        `((defprinter-prin1
+                                            ',sname ,sname ,stream)))))
+                             reversed-prints))
+                    (case (first option)
+                      (:prin1
+                       (stuff `(defprinter-prin1
+                                 ',sname ,(second option) ,stream)))
+                      (:princ
+                       (stuff `(defprinter-princ
+                                 ',sname ,(second option) ,stream)))
+                      (:test (setq test (second option)))
+                      (t
+                       (error "bad option: ~S" (first option)))))))))))
+    `(def!method print-object ((structure ,name) ,stream)
+       ;; FIXME: should probably be byte-compiled
+       (pprint-logical-block (,stream nil)
+        (print-unreadable-object (structure ,stream :type t)
+          (when *print-pretty*
+            (pprint-indent :block 2 ,stream))
+          ,@(nreverse reversed-prints))))))
 \f
 #|
 ;;; REMOVEME when done testing byte cross-compiler
   (if x
       x
       (cons y y)))
-|#
\ No newline at end of file
+|#