430ea339366649fbaa6b15f915199bccecec6010
[sbcl.git] / src / code / primordial-extensions.lisp
1 ;;;; various user-level definitions which need to be done particularly
2 ;;;; early
3
4 ;;;; This software is part of the SBCL system. See the README file for
5 ;;;; more information.
6 ;;;;
7 ;;;; This software is derived from the CMU CL system, which was
8 ;;;; written at Carnegie Mellon University and released into the
9 ;;;; public domain. The software is in the public domain and is
10 ;;;; provided with absolutely no warranty. See the COPYING and CREDITS
11 ;;;; files for more information.
12
13 (in-package "SB!INT")
14 \f
15 ;;;; DO-related stuff which needs to be visible on the cross-compilation host
16
17 (eval-when (:compile-toplevel :load-toplevel :execute)
18   (defun do-do-body (varlist endlist decls-and-code bind step name block)
19     (let* ((r-inits nil) ; accumulator for reversed list
20            (r-steps nil) ; accumulator for reversed list
21            (label-1 (gensym))
22            (label-2 (gensym)))
23       ;; Check for illegal old-style DO.
24       (when (or (not (listp varlist)) (atom endlist))
25         (error "Ill-formed ~S -- possibly illegal old style DO?" name))
26       ;; Parse VARLIST to get R-INITS and R-STEPS.
27       (dolist (v varlist)
28         (flet (;; (We avoid using CL:PUSH here so that CL:PUSH can be defined
29                ;; in terms of CL:SETF, and CL:SETF can be defined in terms of
30                ;; CL:DO, and CL:DO can be defined in terms of the current
31                ;; function.)
32                (push-on-r-inits (x)
33                  (setq r-inits (cons x r-inits)))
34                ;; common error-handling
35                (illegal-varlist ()
36                  (error "~S is an illegal form for a ~S varlist." v name)))
37           (cond ((symbolp v) (push-on-r-inits v))
38                 ((listp v)
39                  (unless (symbolp (first v))
40                    (error "~S step variable is not a symbol: ~S"
41                           name
42                           (first v)))
43                  (let ((lv (length v)))
44                    ;; (We avoid using CL:CASE here so that CL:CASE can be
45                    ;; defined in terms of CL:SETF, and CL:SETF can be defined
46                    ;; in terms of CL:DO, and CL:DO can be defined in terms of
47                    ;; the current function.)
48                    (cond ((= lv 1)
49                           (push-on-r-inits (first v)))
50                          ((= lv 2)
51                           (push-on-r-inits v))
52                          ((= lv 3)
53                           (push-on-r-inits (list (first v) (second v)))
54                           (setq r-steps (list* (third v) (first v) r-steps)))
55                          (t (illegal-varlist)))))
56                 (t (illegal-varlist)))))
57       ;; Construct the new form.
58       (multiple-value-bind (code decls) (parse-body decls-and-code nil)
59         `(block ,block
60            (,bind ,(nreverse r-inits)
61                   ,@decls
62                   (tagbody
63                    (go ,label-2)
64                    ,label-1
65                    ,@code
66                    (,step ,@(nreverse r-steps))
67                    ,label-2
68                    (unless ,(first endlist) (go ,label-1))
69                    (return-from ,block (progn ,@(rest endlist))))))))))
70
71 (defmacro do-anonymous (varlist endlist &rest body)
72   #!+sb-doc
73   "DO-ANONYMOUS ({(Var [Init] [Step])}*) (Test Exit-Form*) Declaration* Form*
74   Like DO, but has no implicit NIL block. Each Var is initialized in parallel
75   to the value of the specified Init form. On subsequent iterations, the Vars
76   are assigned the value of the Step form (if any) in parallel. The Test is
77   evaluated before each evaluation of the body Forms. When the Test is true,
78   the Exit-Forms are evaluated as a PROGN, with the result being the value
79   of the DO."
80   (do-do-body varlist endlist body 'let 'psetq 'do-anonymous (gensym)))
81 \f
82 ;;;; miscellany
83
84 ;;; Concatenate together the names of some strings and symbols,
85 ;;; producing a symbol in the current package.
86 (eval-when (:compile-toplevel :load-toplevel :execute)
87   (defun symbolicate (&rest things)
88     (values (intern (apply #'concatenate
89                            'string
90                            (mapcar #'string things))))))
91
92 ;;; like SYMBOLICATE, but producing keywords
93 (defun keywordicate (&rest things)
94   (let ((*package* *keyword-package*))
95     (apply #'symbolicate things)))
96
97 ;;; Access *PACKAGE* in a way which lets us recover if someone has
98 ;;; done something silly like (SETF *PACKAGE* :CL-USER). (Such an
99 ;;; assignment is undefined behavior, so it's sort of reasonable for it
100 ;;; to cause the system to go totally insane afterwards, but it's
101 ;;; a fairly easy mistake to make, so let's try to recover gracefully
102 ;;; instead.)
103 (defun sane-package ()
104   (let ((maybe-package *package*))
105     (cond ((and (packagep maybe-package)
106                 ;; For good measure, we also catch the problem of
107                 ;; *PACKAGE* being bound to a deleted package.
108                 ;; Technically, this is not undefined behavior in itself,
109                 ;; but it will immediately lead to undefined to behavior,
110                 ;; since almost any operation on a deleted package is
111                 ;; undefined.
112                 (package-name maybe-package))
113            maybe-package)
114           (t
115            ;; We're in the undefined behavior zone. First, munge the
116            ;; system back into a defined state.
117            (let ((really-package (find-package :cl-user)))
118              (setf *package* really-package)
119              ;; Then complain.
120              (error 'simple-type-error
121                     :datum maybe-package
122                     :expected-type 'package
123                     :format-control
124                     "~@<~S can't be a ~S: ~2I~_~S has been reset to ~S.~:>"
125                     :format-arguments (list '*package* (type-of maybe-package)
126                                             '*package* really-package)))))))
127
128 ;;; Give names to elements of a numeric sequence.
129 (defmacro defenum ((&key (prefix "") (suffix "") (start 0) (step 1))
130                    &rest identifiers)
131   (let ((results nil)
132         (index 0)
133         (start (eval start))
134         (step (eval step)))
135     (dolist (id identifiers)
136       (when id
137         (multiple-value-bind (root docs)
138             (if (consp id)
139                 (values (car id) (cdr id))
140                 (values id nil))
141           (push `(defconstant ,(symbolicate prefix root suffix)
142                    ,(+ start (* step index))
143                    ,@docs)
144                 results)))
145       (incf index))
146     `(progn
147        ,@(nreverse results))))
148
149 ;;; generalization of DEFCONSTANT to values which are the same not
150 ;;; under EQL but under e.g. EQUAL or EQUALP
151 ;;;
152 ;;; DEFCONSTANT-EQX is to be used instead of DEFCONSTANT for values
153 ;;; which are appropriately compared using the function given by the
154 ;;; EQX argument instead of EQL.
155 ;;;
156 ;;; Note: Be careful when using this macro, since it's easy to
157 ;;; unintentionally pessimize your code. A good time to use this macro
158 ;;; is when the values defined will be fed into optimization
159 ;;; transforms and never actually appear in the generated code; this
160 ;;; is especially common when defining BYTE expressions. Unintentional
161 ;;; pessimization can result when the values defined by this macro are
162 ;;; actually used in generated code: because of the way that the
163 ;;; dump/load system works, you'll typically get one copy of consed
164 ;;; structure for each object file which contains code referring to
165 ;;; the value, plus perhaps one more copy bound to the SYMBOL-VALUE of
166 ;;; the constant. If you don't want that to happen, you should
167 ;;; probably use DEFPARAMETER instead.
168 (defmacro defconstant-eqx (symbol expr eqx &optional doc)
169   (let ((expr-tmp (gensym "EXPR-TMP-")))
170     `(progn
171        ;; When we're building the cross-compiler, and in most
172        ;; situations even when we're running the cross-compiler,
173        ;; all we need is a nice portable definition in terms of the
174        ;; ANSI Common Lisp operations.
175        (eval-when (:compile-toplevel :load-toplevel :execute)
176          (let ((,expr-tmp ,expr))
177            (cond ((boundp ',symbol)
178                   (unless (and (constantp ',symbol)
179                                (funcall ,eqx
180                                         (symbol-value ',symbol)
181                                         ,expr-tmp))
182                     (error "already bound differently: ~S")))
183                  (t
184                   (defconstant ,symbol ,expr-tmp ,@(when doc `(,doc)))))))
185        ;; The #+SB-XC :COMPILE-TOPLEVEL situation is special, since we
186        ;; want to define the symbol not just in the cross-compilation
187        ;; host Lisp (which was handled above) but also in the
188        ;; cross-compiler (which we will handle now).
189        ;;
190        ;; KLUDGE: It would probably be possible to do this fairly
191        ;; cleanly, in a way parallel to the code above, if we had
192        ;; SB!XC:FOO versions of all the primitives CL:FOO used above
193        ;; (e.g. SB!XC:BOUNDP, SB!XC:SYMBOL-VALUE, and
194        ;; SB!XC:DEFCONSTANT), and took care to call them. But right
195        ;; now we just hack around in the guts of the cross-compiler
196        ;; instead. -- WHN 2000-11-03
197        #+sb-xc
198        (eval-when (:compile-toplevel)
199          (let ((,expr-tmp ,symbol))
200            (unless (and (eql (info :variable :kind ',symbol) :constant)
201                         (funcall ,eqx
202                                  (info :variable :constant-value ',symbol)
203                                  ,expr-tmp))
204              (sb!c::%defconstant ',symbol ,expr-tmp ,doc)))))))