Remove 8-bit hash codes in packages.
[sbcl.git] / src / code / cas.lisp
bloba4cef28cb03c3bef12f9d9d7e3021d085739c3b9
1 (in-package "SB!IMPL")
3 ;;;; COMPARE-AND-SWAP
4 ;;;;
5 ;;;; SB-EXT:COMPARE-AND-SWAP is the public API for now.
6 ;;;;
7 ;;;; Internally our interface has CAS, GET-CAS-EXPANSION, DEFINE-CAS-EXPANDER,
8 ;;;; DEFCAS, and #'(CAS ...) functions -- making things mostly isomorphic with
9 ;;;; SETF.
11 (eval-when (:compile-toplevel :load-toplevel :execute)
12 (defun expand-structure-slot-cas (info name place)
13 (let* ((dd (car info))
14 (structure (dd-name dd))
15 (slotd (cdr info))
16 (index (dsd-index slotd))
17 (type (dsd-type slotd))
18 (casser
19 (case (dsd-raw-type slotd)
20 ((t) '%instance-cas)
21 #!+(or x86 x86-64)
22 ((word) '%raw-instance-cas/word))))
23 (unless casser
24 (error "Cannot use COMPARE-AND-SWAP with structure accessor ~
25 for a typed slot: ~S"
26 place))
27 (when (dsd-read-only slotd)
28 (error "Cannot use COMPARE-AND-SWAP with structure accessor ~
29 for a read-only slot: ~S"
30 place))
31 (destructuring-bind (op arg) place
32 (aver (eq op name))
33 (with-unique-names (instance old new)
34 (values (list instance)
35 (list `(the ,structure ,arg))
36 old
37 new
38 `(truly-the (values ,type &optional)
39 (,casser ,instance ,index
40 (the ,type ,old)
41 (the ,type ,new)))
42 `(,op ,instance))))))
44 ;;; FIXME: the generated code for CAS on a defglobal contains a
45 ;;; use of UNBOUND-SYMBOL-ERROR. This is is not unique to CAS, viz.:
46 ;;; * (defglobal *ggg* 3)
47 ;;; * (disassemble '(lambda () (symbol-value '*ggg*)))
48 ;;; ...
49 ;;; ; 98: L0: CC0A BREAK 10 ; error trap
50 ;;; ; 9A: 06 BYTE #X06 ; UNBOUND-SYMBOL-ERROR
51 ;;; ; 9B: 00 BYTE #X00 ; RAX
52 ;;; whereas evaluating the atom *GGG* is perfectly fine.
53 ;;; In fact not only is the unbound check emitted, so is the TLS value check,
54 ;;; but there's no CAS expander for SYMBOL-GLOBAL-VALUE, so we can't
55 ;;; macroexpand ATOMIC-PUSH into (CAS (SYMBOL-GLOBAL-VALUE ...))
57 (defun get-cas-expansion (place &optional environment)
58 #!+sb-doc
59 "Analogous to GET-SETF-EXPANSION. Returns the following six values:
61 * list of temporary variables
63 * list of value-forms whose results those variable must be bound
65 * temporary variable for the old value of PLACE
67 * temporary variable for the new value of PLACE
69 * form using the aforementioned temporaries which performs the
70 compare-and-swap operation on PLACE
72 * form using the aforementioned temporaries with which to perform a volatile
73 read of PLACE
75 Example:
77 (get-cas-expansion '(car x))
78 ; => (#:CONS871), (X), #:OLD872, #:NEW873,
79 ; (SB-KERNEL:%COMPARE-AND-SWAP-CAR #:CONS871 #:OLD872 :NEW873).
80 ; (CAR #:CONS871)
82 (defmacro my-atomic-incf (place &optional (delta 1) &environment env)
83 (multiple-value-bind (vars vals old new cas-form read-form)
84 (get-cas-expansion place env)
85 (let ((delta-value (gensym \"DELTA\")))
86 `(let* (,@(mapcar 'list vars vals)
87 (,old ,read-form)
88 (,delta-value ,delta)
89 (,new (+ ,old ,delta-value)))
90 (loop until (eq ,old (setf ,old ,cas-form))
91 do (setf ,new (+ ,old ,delta-value)))
92 ,new))))
94 EXPERIMENTAL: Interface subject to change."
95 ;; FIXME: this seems wrong on two points:
96 ;; 1. if TRULY-THE had a CAS expander (which it doesn't) we'd want
97 ;; to use %MACROEXPAND[-1] so as not to lose the "truly-the"-ness
98 ;; 2. if both a CAS expander and a macro exist, the CAS expander
99 ;; should be preferred before macroexpanding (just like SETF does)
100 (let ((expanded (sb!xc:macroexpand place environment)))
101 (flet ((invalid-place ()
102 (error "Invalid place to CAS: ~S -> ~S" place expanded)))
103 (unless (consp expanded)
104 (cond ((and (symbolp expanded)
105 (member (info :variable :kind expanded)
106 '(:global :special)))
107 (setq expanded `(symbol-value ',expanded)))
109 (invalid-place))))
110 (let ((name (car expanded)))
111 (unless (symbolp name)
112 (invalid-place))
113 (acond
114 ((info :cas :expander name)
115 ;; CAS expander.
116 (funcall it expanded environment))
118 ;; Structure accessor
119 ((structure-instance-accessor-p name)
120 (expand-structure-slot-cas it name expanded))
122 ;; CAS function
124 (with-unique-names (old new)
125 (let ((vars nil)
126 (vals nil)
127 (args nil))
128 (dolist (x (reverse (cdr expanded)))
129 (cond ((sb!xc:constantp x environment)
130 (push x args))
132 (let ((tmp (gensymify x)))
133 (push tmp args)
134 (push tmp vars)
135 (push x vals)))))
136 (values vars vals old new
137 `(funcall #'(cas ,name) ,old ,new ,@args)
138 `(,name ,@args))))))))))
141 ;;; This is what it all comes down to.
142 (defmacro cas (place old new &environment env)
143 #!+sb-doc
144 "Synonym for COMPARE-AND-SWAP.
146 Additionally DEFUN, DEFGENERIC, DEFMETHOD, FLET, and LABELS can be also used to
147 define CAS-functions analogously to SETF-functions:
149 (defvar *foo* nil)
151 (defun (cas foo) (old new)
152 (cas (symbol-value '*foo*) old new))
154 First argument of a CAS function is the expected old value, and the second
155 argument of is the new value. Note that the system provides no automatic
156 atomicity for CAS functions, nor can it verify that they are atomic: it is up
157 to the implementor of a CAS function to ensure its atomicity.
159 EXPERIMENTAL: Interface subject to change."
160 (multiple-value-bind (temps place-args old-temp new-temp cas-form)
161 (get-cas-expansion place env)
162 `(let* (,@(mapcar #'list temps place-args)
163 (,old-temp ,old)
164 (,new-temp ,new))
165 ,cas-form)))
167 (defmacro define-cas-expander (accessor lambda-list &body body)
168 #!+sb-doc
169 "Analogous to DEFINE-SETF-EXPANDER. Defines a CAS-expansion for ACCESSOR.
170 BODY must return six values as specified in GET-CAS-EXPANSION.
172 Note that the system provides no automatic atomicity for CAS expansion, nor
173 can it verify that they are atomic: it is up to the implementor of a CAS
174 expansion to ensure its atomicity.
176 EXPERIMENTAL: Interface subject to change."
177 `(eval-when (:compile-toplevel :load-toplevel :execute)
178 (setf (info :cas :expander ',accessor)
179 ,(make-macro-lambda `(cas-expand ,accessor) lambda-list body
180 'define-cas-expander accessor))))
182 ;; FIXME: this interface is bogus - short-form DEFSETF/CAS does not
183 ;; want a lambda-list. You just blindly substitute
184 ;; (CAS (PLACE arg1 ... argN) old new) -> (F arg1 ... argN old new).
185 ;; What role can this lambda-list have when there is no user-provided
186 ;; code to read the variables?
187 ;; And as mentioned no sbcl-devel, &REST is beyond bogus, it's broken.
189 (defmacro defcas (accessor lambda-list function &optional docstring)
190 #!+sb-doc
191 "Analogous to short-form DEFSETF. Defines FUNCTION as responsible
192 for compare-and-swap on places accessed using ACCESSOR. LAMBDA-LIST
193 must correspond to the lambda-list of the accessor.
195 Note that the system provides no automatic atomicity for CAS expansions
196 resulting from DEFCAS, nor can it verify that they are atomic: it is up to the
197 user of DEFCAS to ensure that the function specified is atomic.
199 EXPERIMENTAL: Interface subject to change."
200 (multiple-value-bind (llks reqs opts rest)
201 (parse-lambda-list lambda-list
202 :accept (lambda-list-keyword-mask '(&optional &rest))
203 :context "a DEFCAS lambda-list")
204 (declare (ignore llks))
205 `(define-cas-expander ,accessor ,lambda-list
206 ,@(when docstring (list docstring))
207 ;; FIXME: if a &REST arg is present, this is really weird.
208 (let ((temps (mapcar #'gensymify ',(append reqs opts rest)))
209 (args (list ,@(append reqs opts rest)))
210 (old (gensym "OLD"))
211 (new (gensym "NEW")))
212 (values temps
213 args
216 `(,',function ,@temps ,old ,new)
217 `(,',accessor ,@temps))))))
219 (defmacro compare-and-swap (place old new)
220 #!+sb-doc
221 "Atomically stores NEW in PLACE if OLD matches the current value of PLACE.
222 Two values are considered to match if they are EQ. Returns the previous value
223 of PLACE: if the returned value is EQ to OLD, the swap was carried out.
225 PLACE must be an CAS-able place. Built-in CAS-able places are accessor forms
226 whose CAR is one of the following:
228 CAR, CDR, FIRST, REST, SVREF, SYMBOL-PLIST, SYMBOL-VALUE, SVREF, SLOT-VALUE
229 SB-MOP:STANDARD-INSTANCE-ACCESS, SB-MOP:FUNCALLABLE-STANDARD-INSTANCE-ACCESS,
231 or the name of a DEFSTRUCT created accessor for a slot whose declared type is
232 either FIXNUM or T. Results are unspecified if the slot has a declared type
233 other than FIXNUM or T.
235 In case of SLOT-VALUE, if the slot is unbound, SLOT-UNBOUND is called unless
236 OLD is EQ to SB-PCL:+SLOT-UNBOUND+ in which case SB-PCL:+SLOT-UNBOUND+ is
237 returned and NEW is assigned to the slot. Additionally, the results are
238 unspecified if there is an applicable method on either
239 SB-MOP:SLOT-VALUE-USING-CLASS, (SETF SB-MOP:SLOT-VALUE-USING-CLASS), or
240 SB-MOP:SLOT-BOUNDP-USING-CLASS.
242 Additionally, the PLACE can be a anything for which a CAS-expansion has been
243 specified using DEFCAS, DEFINE-CAS-EXPANDER, or for which a CAS-function has
244 been defined. (See SB-EXT:CAS for more information.)
246 `(cas ,place ,old ,new))
248 (define-cas-expander symbol-value (name &environment env)
249 (multiple-value-bind (tmp val cname)
250 (if (sb!xc:constantp name env)
251 (values nil nil (constant-form-value name env))
252 (values (gensymify name) name nil))
253 (let ((symbol (or tmp `',cname)))
254 (with-unique-names (old new)
255 (values (when tmp (list tmp))
256 (when val (list val))
259 (let ((slow
260 `(progn
261 (about-to-modify-symbol-value ,symbol 'compare-and-swap ,new)
262 (%compare-and-swap-symbol-value ,symbol ,old ,new))))
263 (if cname
264 (if (member (info :variable :kind cname) '(:special :global))
265 ;; We can generate the type-check reasonably.
266 `(%compare-and-swap-symbol-value
267 ',cname ,old (the ,(info :variable :type cname) ,new))
268 slow)
269 slow))
270 `(symbol-value ,symbol))))))
272 (define-cas-expander svref (vector index)
273 (with-unique-names (v i old new)
274 (values (list v i)
275 (list vector index)
278 `(locally (declare (simple-vector ,v))
279 (%compare-and-swap-svref ,v (check-bound ,v (length ,v) ,i) ,old ,new))
280 `(svref ,v ,i))))
282 ;;;; ATOMIC-INCF and ATOMIC-DECF
284 (eval-when (:compile-toplevel :load-toplevel :execute)
285 (defun expand-atomic-frob
286 (name specified-place diff env
287 &aux (place (sb!xc:macroexpand specified-place env)))
288 (declare (type (member atomic-incf atomic-decf) name))
289 (flet ((invalid-place ()
290 (error "Invalid first argument to ~S: ~S" name specified-place))
291 (compute-newval (old) ; used only if no atomic inc vop
292 `(logand (,(case name (atomic-incf '+) (atomic-decf '-)) ,old
293 (the sb!vm:signed-word ,diff)) sb!ext:most-positive-word))
294 (compute-delta () ; used only with atomic inc vop
295 `(logand ,(case name
296 (atomic-incf `(the sb!vm:signed-word ,diff))
297 (atomic-decf `(- (the sb!vm:signed-word ,diff))))
298 sb!ext:most-positive-word)))
299 (declare (ignorable #'compute-newval #'compute-delta))
300 (when (and (symbolp place)
301 (eq (info :variable :kind place) :global)
302 (type= (info :variable :type place) (specifier-type 'fixnum)))
303 ;; Global can't be lexically rebound.
304 (return-from expand-atomic-frob
305 `(truly-the fixnum (,(case name
306 (atomic-incf '%atomic-inc-symbol-global-value)
307 (atomic-decf '%atomic-dec-symbol-global-value))
308 ',place (the fixnum ,diff)))))
309 (unless (consp place) (invalid-place))
310 (destructuring-bind (op . args) place
311 ;; FIXME: The lexical environment should not be disregarded.
312 ;; CL builtins can't be lexically rebound, but structure accessors can.
313 (case op
314 (aref
315 (unless (singleton-p (cdr args))
316 (invalid-place))
317 (with-unique-names (array)
318 `(let ((,array (the (simple-array word (*)) ,(car args))))
319 #!+compare-and-swap-vops
320 (%array-atomic-incf/word
321 ,array
322 (check-bound ,array (array-dimension ,array 0) ,(cadr args))
323 ,(compute-delta))
324 #!-compare-and-swap-vops
325 ,(with-unique-names (index old-value)
326 `(without-interrupts
327 (let* ((,index ,(cadr args))
328 (,old-value (aref ,array ,index)))
329 (setf (aref ,array ,index) ,(compute-newval old-value))
330 ,old-value))))))
331 ((car cdr first rest)
332 (when (cdr args)
333 (invalid-place))
334 `(truly-the
335 fixnum
336 (,(case op
337 ((first car) (case name
338 (atomic-incf '%atomic-inc-car)
339 (atomic-decf '%atomic-dec-car)))
340 ((rest cdr) (case name
341 (atomic-incf '%atomic-inc-cdr)
342 (atomic-decf '%atomic-dec-cdr))))
343 ,(car args) (the fixnum ,diff))))
345 (when (or (cdr args)
346 ;; Because accessor info is identical for the writer and reader
347 ;; functions, without a SYMBOLP check this would erroneously allow
348 ;; (ATOMIC-INCF ((SETF STRUCT-SLOT) x))
349 (not (symbolp op))
350 (not (structure-instance-accessor-p op)))
351 (invalid-place))
352 (let* ((accessor-info (structure-instance-accessor-p op))
353 (slotd (cdr accessor-info))
354 (type (dsd-type slotd)))
355 (unless (and (eq 'sb!vm:word (dsd-raw-type slotd))
356 (type= (specifier-type type) (specifier-type 'sb!vm:word)))
357 (error "~S requires a slot of type (UNSIGNED-BYTE ~S), not ~S: ~S"
358 name sb!vm:n-word-bits type place))
359 (when (dsd-read-only slotd)
360 (error "Cannot use ~S with structure accessor for a read-only slot: ~S"
361 name place))
362 #!+compare-and-swap-vops
363 `(truly-the sb!vm:word
364 (%raw-instance-atomic-incf/word
365 (the ,(dd-name (car accessor-info)) ,@args)
366 ,(dsd-index slotd)
367 ,(compute-delta)))
368 #!-compare-and-swap-vops
369 (with-unique-names (structure old-value)
370 `(without-interrupts
371 (let* ((,structure ,@args)
372 (,old-value (,op ,structure)))
373 (setf (,op ,structure) ,(compute-newval old-value))
374 ,old-value))))))))))
376 (defmacro atomic-incf (&environment env place &optional (diff 1))
377 #!+sb-doc
378 #.(format nil
379 "Atomically increments PLACE by DIFF, and returns the value of PLACE before
380 the increment.
382 PLACE must access one of the following:
383 - a DEFSTRUCT slot with declared type (UNSIGNED-BYTE ~D~:*)
384 or AREF of a (SIMPLE-ARRAY (UNSIGNED-BYTE ~D~:*) (*))
385 The type SB-EXT:WORD can be used for these purposes.
386 - CAR or CDR (respectively FIRST or REST) of a CONS.
387 - a variable defined using DEFGLOBAL with a proclaimed type of FIXNUM.
388 Macroexpansion is performed on PLACE before expanding ATOMIC-INCF.
390 Incrementing is done using modular arithmetic,
391 which is well-defined over two different domains:
392 - For structures and arrays, the operation accepts and produces
393 an (UNSIGNED-BYTE ~D~:*), and DIFF must be of type (SIGNED-BYTE ~D).
394 ATOMIC-INCF of #x~x by one results in #x0 being stored in PLACE.
395 - For other places, the domain is FIXNUM, and DIFF must be a FIXNUM.
396 ATOMIC-INCF of #x~x by one results in #x~x
397 being stored in PLACE.
399 DIFF defaults to 1.
401 EXPERIMENTAL: Interface subject to change."
402 sb!vm:n-word-bits most-positive-word
403 sb!xc:most-positive-fixnum sb!xc:most-negative-fixnum)
404 (expand-atomic-frob 'atomic-incf place diff env))
406 (defmacro atomic-decf (&environment env place &optional (diff 1))
407 #!+sb-doc
408 #.(format nil
409 "Atomically decrements PLACE by DIFF, and returns the value of PLACE before
410 the decrement.
412 PLACE must access one of the following:
413 - a DEFSTRUCT slot with declared type (UNSIGNED-BYTE ~D~:*)
414 or AREF of a (SIMPLE-ARRAY (UNSIGNED-BYTE ~D~:*) (*))
415 The type SB-EXT:WORD can be used for these purposes.
416 - CAR or CDR (respectively FIRST or REST) of a CONS.
417 - a variable defined using DEFGLOBAL with a proclaimed type of FIXNUM.
418 Macroexpansion is performed on PLACE before expanding ATOMIC-DECF.
420 Decrementing is done using modular arithmetic,
421 which is well-defined over two different domains:
422 - For structures and arrays, the operation accepts and produces
423 an (UNSIGNED-BYTE ~D~:*), and DIFF must be of type (SIGNED-BYTE ~D).
424 ATOMIC-DECF of #x0 by one results in #x~x being stored in PLACE.
425 - For other places, the domain is FIXNUM, and DIFF must be a FIXNUM.
426 ATOMIC-DECF of #x~x by one results in #x~x
427 being stored in PLACE.
429 DIFF defaults to 1.
431 EXPERIMENTAL: Interface subject to change."
432 sb!vm:n-word-bits most-positive-word
433 sb!xc:most-negative-fixnum sb!xc:most-positive-fixnum)
434 (expand-atomic-frob 'atomic-decf place diff env))
436 ;; Interpreter stubs for ATOMIC-INCF.
437 #!+(and compare-and-swap-vops (host-feature sb-xc))
438 (progn
439 ;; argument types are declared in vm-fndb
440 (defun %array-atomic-incf/word (array index diff)
441 (%array-atomic-incf/word array index diff))
442 (defun %raw-instance-atomic-incf/word (instance index diff)
443 (%raw-instance-atomic-incf/word instance index diff)))