rt TurtleWare: Dynamic Vars - A New Hope By turtleware.eu Published On :: Tue, 22 Oct 2024 00:00:00 GMT Table of Contents Dynamic Bindings The problem The solution Dynamic slots The context Summary Dynamic Bindings Common Lisp has an important language feature called dynamic binding. It is possible to rebind a dynamic variable somewhere on the call stack and downstream functions will see that new value, and when the stack is unwound, the old value is brought back. While Common Lisp does not specify multi-threading, it seems to be a consensus among various implementations that dynamic bindings are thread-local, allowing for controlling the computing context in a safe way. Before we start experiments, let's define a package to isolate our namespace: (defpackage "EU.TURTLEWARE.BLOG/DLET" (:local-nicknames ("MOP" #+closer-mop "C2MOP" #+(and (not closer-mop) ecl) "MOP" #+(and (not closer-mop) ccl) "CCL" #+(and (not closer-mop) sbcl) "SB-MOP")) (:use "CL")) (in-package "EU.TURTLEWARE.BLOG/DLET") Dynamic binding of variables is transparent to the programmer, because the operator LET is used for both lexical and dynamic bindings. For example: (defvar *dynamic-variable* 42) (defun test () (let ((*dynamic-variable* 15) (lexical-variable 12)) (lambda () (print (cons *dynamic-variable* lexical-variable))))) (funcall (test)) ;;; (42 . 12) (let ((*dynamic-variable* 'xx)) (funcall (test))) ;;; (xx . 12) Additionally the language specifies a special operator PROGV that gives the programmer a control over the dynamic binding mechanism, by allowing passing the dynamic variable by value instead of its name. Dynamic variables are represented by symbols: (progv (list '*dynamic-variable*) (list 'zz) (funcall (test))) ;;; (zz . 12) The problem Nowadays it is common to encapsulate the state in the instance of a class. Sometimes that state is dynamic. It would be nice if we could use dynamic binding to control it. That said slots are not variables, and if there are many objects of the same class with different states, then using dynamic variables defined with DEFVAR is not feasible. Consider the following classes which we want to be thread-safe: (defgeneric call-with-ink (cont window ink)) (defclass window-1 () ((ink :initform 'red :accessor ink))) (defmethod call-with-ink (cont (win window-1) ink) (let ((old-ink (ink win))) (setf (ink win) ink) (unwind-protect (funcall cont) (setf (ink win) old-ink)))) (defclass window-2 () ()) (defvar *ink* 'blue) (defmethod ink ((window window-2)) *ink*) (defmethod call-with-ink (cont (win window-2) ink) (let ((*ink* ink)) (funcall cont))) The first example is clearly not thread safe. If we access the WINDOW-1 instance from multiple threads, then they will overwrite a value of the slot INK. The second example is not good either, because when we have many instances of WINDOW-2 then they share the binding. Nesting CALL-WITH-INK will overwrite the binding of another window. The solution The solution is to use PROGV: (defclass window-3 () ((ink :initform (gensym)))) (defmethod initialize-instance :after ((win window-3) &key) (setf (symbol-value (slot-value win 'ink)) 'red)) (defmethod call-with-ink (cont (win window-3) ink) (progv (list (slot-value win 'ink)) (list ink) (funcall cont))) This way each instance has its own dynamic variable that may be rebound with a designated operator CALL-WITH-INK. It is thread-safe and private. We may add some syntactic sugar so it is more similar to let: (defmacro dlet (bindings &body body) (loop for (var val) in bindings collect var into vars collect val into vals finally (return `(progv (list ,@vars) (list ,@vals) ,@body)))) (defmacro dset (&rest pairs) `(setf ,@(loop for (var val) on pairs by #'cddr collect `(symbol-value ,var) collect val))) (defmacro dref (variable) `(symbol-value ,variable)) Dynamic slots While meta-classes are not easily composable, it is worth noting that we can mold it better into the language by specifying that slot itself has a dynamic value. This way CLOS aficionados will have a new tool in their arsenal. The approach we'll take is that a fresh symbol is stored as the value of each instance-allocated slot, and then accessors for the slot value will use these symbols as a dynamic variable. Here are low-level accessors: ;;; Accessing and binding symbols behind the slot. We don't use SLOT-VALUE, ;;; because it will return the _value_ of the dynamic variable, and not the ;;; variable itself. (defun slot-dvar (object slotd) (mop:standard-instance-access object (mop:slot-definition-location slotd))) (defun slot-dvar* (object slot-name) (let* ((class (class-of object)) (slotd (find slot-name (mop:class-slots class) :key #'mop:slot-definition-name))) (slot-dvar object slotd))) (defmacro slot-dlet (bindings &body body) `(dlet ,(loop for ((object slot-name) val) in bindings collect `((slot-dvar* ,object ,slot-name) ,val)) ,@body)) Now we'll define the meta-class. We need that to specialize functions responsible for processing slot definitions and the instance allocation. Notice, that we make use of a kludge to communicate between COMPUTE-EFFECTIVE-SLOT-DEFINITION and EFFECTIVE-SLOT-DEFINITION-CLASS – this is because the latter has no access to the direct slot definitions. ;;; The metaclass CLASS-WITH-DYNAMIC-SLOTS specifies alternative effective slot ;;; definitions for slots with an initarg :dynamic. (defclass class-with-dynamic-slots (standard-class) ()) ;;; Class with dynamic slots may be subclasses of the standard class. (defmethod mop:validate-superclass ((class class-with-dynamic-slots) (super standard-class)) t) ;;; When allocating the instance we initialize all slots to a fresh symbol that ;;; represents the dynamic variable. (defmethod allocate-instance ((class class-with-dynamic-slots) &rest initargs) (declare (ignore initargs)) (let ((object (call-next-method))) (loop for slotd in (mop:class-slots class) when (typep slotd 'dynamic-effective-slot) do (setf (mop:standard-instance-access object (mop:slot-definition-location slotd)) (gensym (string (mop:slot-definition-name slotd))))) object)) ;;; To improve potential composability of CLASS-WITH-DYNAMIC-SLOTS with other ;;; metaclasses we treat specially only slots that has :DYNAMIC in initargs, ;;; otherwise we call the next method. (defmethod mop:direct-slot-definition-class ((class class-with-dynamic-slots) &rest initargs) (loop for (key val) on initargs by #'cddr when (eq key :dynamic) do (return-from mop:direct-slot-definition-class (find-class 'dynamic-direct-slot))) (call-next-method)) ;;; The metaobject protocol did not specify an elegant way to communicate ;;; between the direct slot definition and the effective slot definition. ;;; Luckily we have dynamic bindings! :-) (defvar *kludge/mop-deficiency/dynamic-slot-p* nil) (defmethod mop:compute-effective-slot-definition ((class class-with-dynamic-slots) name direct-slotds) (if (typep (first direct-slotds) 'dynamic-direct-slot) (let* ((*kludge/mop-deficiency/dynamic-slot-p* t)) (call-next-method)) (call-next-method))) (defmethod mop:effective-slot-definition-class ((class class-with-dynamic-slots) &rest initargs) (declare (ignore initargs)) (if *kludge/mop-deficiency/dynamic-slot-p* (find-class 'dynamic-effective-slot) (call-next-method))) Finally we define a direct and an effective slot classes, and specialize slot accessors that are invoked by the instance accessors. ;;; There is a considerable boilerplate involving customizing slots. ;;; ;;; - direct slot definition: local to a single defclass form ;;; ;;; - effective slot definition: combination of all direct slots with the same ;;; name in the class and its superclasses ;;; (defclass dynamic-direct-slot (mop:standard-direct-slot-definition) ((dynamic :initform nil :initarg :dynamic :reader dynamic-slot-p))) ;;; DYNAMIC-EFFECTIVE-SLOT is implemented to return as slot-value values of the ;;; dynamic variable that is stored with the instance. ;;; ;;; It would be nice if we could specify :ALLOCATION :DYNAMIC for the slot, but ;;; then STANDARD-INSTANCE-ACCESS would go belly up. We could make a clever ;;; workaround, but who cares? (defclass dynamic-effective-slot (mop:standard-effective-slot-definition) ()) (defmethod mop:slot-value-using-class ((class class-with-dynamic-slots) object (slotd dynamic-effective-slot)) (dref (slot-dvar object slotd))) (defmethod (setf mop:slot-value-using-class) (new-value (class class-with-dynamic-slots) object (slotd dynamic-effective-slot)) (dset (slot-dvar object slotd) new-value)) (defmethod mop:slot-boundp-using-class ((class class-with-dynamic-slots) object (slotd dynamic-effective-slot)) (boundp (slot-dvar object slotd))) (defmethod mop:slot-makunbound-using-class ((class class-with-dynamic-slots) object (slotd dynamic-effective-slot)) (makunbound (slot-dvar object slotd))) With this, we can finally define a class with slots that have dynamic values. What's more, we may bind them like dynamic variables. ;;; Let there be light. (defclass window-4 () ((ink :initform 'red :dynamic t :accessor ink) (normal :initform 'normal :accessor normal)) (:metaclass class-with-dynamic-slots)) (let ((object (make-instance 'window-4))) (slot-dlet (((object 'ink) 15)) (print (ink object))) (print (ink object))) ContextL provides a similar solution with dynamic slots, although it provides much more, like layered classes. This example is much more self-contained. The context Lately I'm working on the repaint queue for McCLIM. While doing so I've decided to make stream operations thread-safe, so it is possible to draw on the stream and write to it from arbitrary thread asynchronously. The access to the output record history needs to be clearly locked, so that may be solved by the mutex. Graphics state is another story, consider the following functions running from separate threads: (defun team-red () (with-drawing-options (stream :ink +dark-red+) (loop for i from 0 below 50000 do (write-string (format nil "XXX: ~5d~%" i) stream)))) (defun team-blue () (with-drawing-options (stream :ink +dark-blue+) (loop for i from 0 below 50000 do (write-string (format nil "YYY: ~5d~%" i) stream)))) (defun team-pink () (with-drawing-options (stream :ink +deep-pink+) (loop for i from 0 below 25000 do (case (random 2) (0 (draw-rectangle* stream 200 (* i 100) 250 (+ (* i 100) 50))) (1 (draw-circle* stream 225 (+ (* i 100) 25) 25)))))) (defun gonow (stream) (window-clear stream) (time (let ((a (clim-sys:make-process #'team-red)) (b (clim-sys:make-process #'team-blue)) (c (clim-sys:make-process #'team-grue))) (bt:join-thread a) (bt:join-thread b) (bt:join-thread c) (format stream "done!~%"))) ) Operations like WRITE-STRING and DRAW-RECTANGLE can be implemented by holding a lock over the shared resource without much disruption. The drawing color on the other hand is set outside of the loop, so if we had locked the graphics state with a lock, then these functions would be serialized despite being called from different processes. The solution to this problem is to make graphics context a dynamic slot that is accessed with WITH-DRAWING-OPTIONS. Summary I hope that I've convinced you that dynamic variables are cool (I'm sure that majority of readers here are already convinced), and that dynamic slots are even cooler :-). Watch forward to the upcoming McCLIM release! If you like technical writeups like this, please consider supporting me on Patreon. Full Article
rt TurtleWare: Dynamic Vars - The Empire Strikes Back By turtleware.eu Published On :: Mon, 28 Oct 2024 00:00:00 GMT Table of Contents Thread Local storage exhausted The layer of indirection I can fix her Let's write some tests! Summary Thread Local storage exhausted In the last post I've described a technique to use dynamic variables by value instead of the name by utilizing the operator PROGV. Apparently it works fine on all Common Lisp implementations I've tried except from SBCL, where the number of thread local variables is by default limited to something below 4000. To add salt to the injury, these variables are not garbage collected. Try the following code to crash into LDB: (defun foo () (loop for i from 0 below 4096 do (when (zerop (mod i 100)) (print i)) (progv (list (gensym)) (list 42) (values)))) (foo) This renders our new technique not very practical given SBCL popularity. We need to either abandon the idea or come up with a workaround. The layer of indirection Luckily for us we've already introduced a layer of indirection. Operators to access dynamic variables are called DLET, DSET and DREF. This means, that it is enough to provide a kludge implementation for SBCL with minimal changes to the remaining code. The old code works the same as previously except that instead of SYMBOL-VALUE we use the accessor DYNAMIC-VARIABLE-VALUE, and the old call to PROGV is now DYNAMIC-VARIABLE-PROGV. Moreover DYNAMIC-EFFECTIVE-SLOT used functions BOUNDP and MAKUNBOUND, so we replace these with DYNAMIC-VARIABLE-BOUND-P and DYNAMIC-VARIABLE-MAKUNBOUND. To abstract away things further we also introduce the constructor MAKE-DYNAMIC-VARIABLE (defpackage "EU.TURTLEWARE.BLOG/DLET" (:local-nicknames ("MOP" #+closer-mop "C2MOP" #+(and (not closer-mop) ecl) "MOP" #+(and (not closer-mop) ccl) "CCL" #+(and (not closer-mop) sbcl) "SB-MOP")) (:use "CL")) (in-package "EU.TURTLEWARE.BLOG/DLET") (eval-when (:compile-toplevel :execute :load-toplevel) (unless (member :bordeaux-threads *features*) (error "Please load BORDEAUX-THREADS.")) (when (member :sbcl *features*) (unless (member :fake-progv-kludge *features*) (format t "~&;; Using FAKE-PROGV-KLUDGE for SBCL.~%") (push :fake-progv-kludge *features*)))) (defmacro dlet (bindings &body body) (flet ((pred (binding) (and (listp binding) (= 2 (length binding))))) (unless (every #'pred bindings) (error "DLET: bindings must be lists of two values.~%~ Invalid bindings:~%~{ ~s~%~}" (remove-if #'pred bindings)))) (loop for (var val) in bindings collect var into vars collect val into vals finally (return `(dynamic-variable-progv (list ,@vars) (list ,@vals) ,@body)))) (defmacro dset (&rest pairs) `(setf ,@(loop for (var val) on pairs by #'cddr collect `(dref ,var) collect val))) (defmacro dref (variable) `(dynamic-variable-value ,variable)) ;;; ... (defmethod mop:slot-boundp-using-class ((class standard-class) object (slotd dynamic-effective-slot)) (dynamic-variable-bound-p (slot-dvar object slotd))) (defmethod mop:slot-makunbound-using-class ((class standard-class) object (slotd dynamic-effective-slot)) (dynamic-variable-makunbound (slot-dvar object slotd))) With these in place we can change the portable implementation to conform. #-fake-progv-kludge (progn (defun make-dynamic-variable () (gensym)) (defun dynamic-variable-value (variable) (symbol-value variable)) (defun (setf dynamic-variable-value) (value variable) (setf (symbol-value variable) value)) (defun dynamic-variable-bound-p (variable) (boundp variable)) (defun dynamic-variable-makunbound (variable) (makunbound variable)) (defmacro dynamic-variable-progv (vars vals &body body) `(progv ,vars ,vals ,@body))) I can fix her The implementation for SBCL will mediate access to the dynamic variable value with a synchronized hash table with weak keys. The current process is the key of the hash table and the list of bindings is the value of the hash table. For compatibility between implementations the top level value of the symbol will be shared. The variable +FAKE-UNBOUND+ is the marker that signifies, that the variable has no value. When the list of bindings is EQ to +CELL-UNBOUND+, then it means that we should use the global value. We add new bindings by pushing to it. #+fake-progv-kludge (progn (defvar +fake-unbound+ 'unbound) (defvar +cell-unbound+ '(no-binding)) (defclass dynamic-variable () ((tls-table :initform (make-hash-table :synchronized t :weakness :key) :reader dynamic-variable-tls-table) (top-value :initform +fake-unbound+ :accessor dynamic-variable-top-value))) (defun make-dynamic-variable () (make-instance 'dynamic-variable)) (defun dynamic-variable-bindings (dvar) (let ((process (bt:current-thread)) (tls-table (dynamic-variable-tls-table dvar))) (gethash process tls-table +cell-unbound+))) (defun (setf dynamic-variable-bindings) (value dvar) (let ((process (bt:current-thread)) (tls-table (dynamic-variable-tls-table dvar))) (setf (gethash process tls-table +cell-unbound+) value)))) We define two readers for the variable value - one that simply reads the value, and the other that signals an error if the variable is unbound. Writer for its value either replaces the current binding, or if the value cell is unbound, then we modify the top-level symbol value. We use the value +FAKE-UNBOUND+ to check whether the variable is bound and to make it unbound. #+fake-progv-kludge (progn (defun %dynamic-variable-value (dvar) (let ((tls-binds (dynamic-variable-bindings dvar))) (if (eq tls-binds +cell-unbound+) (dynamic-variable-top-value dvar) (car tls-binds)))) (defun dynamic-variable-value (dvar) (let ((tls-value (%dynamic-variable-value dvar))) (when (eq tls-value +fake-unbound+) (error 'unbound-variable :name "(unnamed)")) tls-value)) (defun (setf dynamic-variable-value) (value dvar) (let ((tls-binds (dynamic-variable-bindings dvar))) (if (eq tls-binds +cell-unbound+) (setf (dynamic-variable-top-value dvar) value) (setf (car tls-binds) value)))) (defun dynamic-variable-bound-p (dvar) (not (eq +fake-unbound+ (%dynamic-variable-value dvar)))) (defun dynamic-variable-makunbound (dvar) (setf (dynamic-variable-value dvar) +fake-unbound+))) Finally we define the operator to dynamically bind variables that behaves similar to PROGV. Note that we PUSH and POP from the thread-local hash table DYNAMIC-VARIABLE-BINDINGS, so no synchronization is necessary. #+fake-progv-kludge (defmacro dynamic-variable-progv (vars vals &body body) (let ((svars (gensym)) (svals (gensym)) (var (gensym)) (val (gensym))) `(let ((,svars ,vars)) (loop for ,svals = ,vals then (rest ,svals) for ,var in ,svars for ,val = (if ,svals (car ,svals) +fake-unbound+) do (push ,val (dynamic-variable-bindings ,var))) (unwind-protect (progn ,@body) (loop for ,var in ,svars do (pop (dynamic-variable-bindings ,var))))))) Let's write some tests! But of course, we are going to also write a test framework. It's short, I promise. As a bonus point the API is compatibile with fiveam, so it is possible to drop tests as is in the appropriate test suite. (defvar *all-tests* '()) (defun run-tests () (dolist (test (reverse *all-tests*)) (format *debug-io* "Test ~a... " test) (handler-case (funcall test) (serious-condition (c) (format *debug-io* "Failed: ~a~%" c)) (:no-error (&rest args) (declare (ignore args)) (format *debug-io* "Passed.~%"))))) (defmacro test (name &body body) `(progn (pushnew ',name *all-tests*) (defun ,name () ,@body))) (defmacro is (form) `(assert ,form)) (defmacro pass ()) (defmacro signals (condition form) `(is (block nil (handler-case ,form (,condition () (return t))) nil))) (defmacro finishes (form) `(is (handler-case ,form (serious-condition (c) (declare (ignore c)) nil) (:no-error (&rest args) (declare (ignore args)) t)))) Now let's get to tests. First we'll test our metaclass: (defclass dynamic-let.test-class () ((slot1 :initarg :slot1 :dynamic nil :accessor slot1) (slot2 :initarg :slot2 :dynamic t :accessor slot2) (slot3 :initarg :slot3 :accessor slot3)) (:metaclass class-with-dynamic-slots)) (defparameter *dynamic-let.test-instance-1* (make-instance 'dynamic-let.test-class :slot1 :a :slot2 :b :slot3 :c)) (defparameter *dynamic-let.test-instance-2* (make-instance 'dynamic-let.test-class :slot1 :x :slot2 :y :slot3 :z)) (test dynamic-let.1 (let ((o1 *dynamic-let.test-instance-1*) (o2 *dynamic-let.test-instance-2*)) (with-slots (slot1 slot2 slot3) o1 (is (eq :a slot1)) (is (eq :b slot2)) (is (eq :c slot3))) (with-slots (slot1 slot2 slot3) o2 (is (eq :x slot1)) (is (eq :y slot2)) (is (eq :z slot3))))) (test dynamic-let.2 (let ((o1 *dynamic-let.test-instance-1*) (o2 *dynamic-let.test-instance-2*)) (signals error (slot-dlet (((o1 'slot1) 1)) nil)) (slot-dlet (((o1 'slot2) :k)) (is (eq :k (slot-value o1 'slot2))) (is (eq :y (slot-value o2 'slot2)))))) (test dynamic-let.3 (let ((o1 *dynamic-let.test-instance-1*) (exit nil) (fail nil)) (flet ((make-runner (values) (lambda () (slot-dlet (((o1 'slot2) :start)) (let ((value (slot2 o1))) (unless (eq value :start) (setf fail value))) (loop until (eq exit t) do (setf (slot2 o1) (elt values (random (length values)))) (let ((value (slot2 o1))) (unless (member value values) (setf fail value) (setf exit t)))))))) (let ((r1 (bt:make-thread (make-runner '(:k1 :k2)))) (r2 (bt:make-thread (make-runner '(:k3 :k4)))) (r3 (bt:make-thread (make-runner '(:k5 :k6))))) (sleep .1) (setf exit t) (map nil #'bt:join-thread (list r1 r2 r3)) (is (eq (slot2 o1) :b)) (is (null fail)))))) Then let's test the dynamic variable itself: (test dynamic-let.4 "Test basic dvar operators." (let ((dvar (make-dynamic-variable))) (is (eql 42 (dset dvar 42))) (is (eql 42 (dref dvar))) (ignore-errors (dlet ((dvar :x)) (is (eql :x (dref dvar))) (error "foo"))) (is (eql 42 (dref dvar))))) (test dynamic-let.5 "Test bound-p operator." (let ((dvar (make-dynamic-variable))) (is (not (dynamic-variable-bound-p dvar))) (dset dvar 15) (is (dynamic-variable-bound-p dvar)) (dynamic-variable-makunbound dvar) (is (not (dynamic-variable-bound-p dvar))))) (test dynamic-let.6 "Test makunbound operator." (let ((dvar (make-dynamic-variable))) (dset dvar t) (is (dynamic-variable-bound-p dvar)) (finishes (dynamic-variable-makunbound dvar)) (is (not (dynamic-variable-bound-p dvar))))) (test dynamic-let.7 "Test locally bound-p operator." (let ((dvar (make-dynamic-variable))) (is (not (dynamic-variable-bound-p dvar))) (dlet ((dvar 15)) (is (dynamic-variable-bound-p dvar))) (is (not (dynamic-variable-bound-p dvar))))) (test dynamic-let.8 "Test locally unbound-p operator." (let ((dvar (make-dynamic-variable))) (dset dvar t) (is (dynamic-variable-bound-p dvar)) (dlet ((dvar nil)) (is (dynamic-variable-bound-p dvar)) (finishes (dynamic-variable-makunbound dvar)) (is (not (dynamic-variable-bound-p dvar)))) (is (dynamic-variable-bound-p dvar)))) (test dynamic-let.9 "Stress test the implementation (see :FAKE-PROGV-KLUDGE)." (finishes ; at the same time (let ((dvars (loop repeat 4096 collect (make-dynamic-variable)))) ;; ensure tls variable (loop for v in dvars do (dlet ((v 1)))) (loop for i from 0 below 4096 for r = (random 4096) for v1 in dvars for v2 = (elt dvars r) do (when (zerop (mod i 64)) (pass)) (dlet ((v1 42) (v2 43)) (values)))))) (test dynamic-let.0 "Stress test the implementation (see :FAKE-PROGV-KLUDGE)." (finishes ; can be gc-ed (loop for i from 0 below 4096 do (when (zerop (mod i 64)) (pass)) (dlet (((make-dynamic-variable) 42)) (values))))) All that is left is to test both dynamic variable implementations: BLOG/DLET> (lisp-implementation-type) "ECL" BLOG/DLET> (run-tests) Test DYNAMIC-LET.1... Passed. Test DYNAMIC-LET.2... Passed. Test DYNAMIC-LET.3... Passed. Test DYNAMIC-LET.4... Passed. Test DYNAMIC-LET.5... Passed. Test DYNAMIC-LET.6... Passed. Test DYNAMIC-LET.7... Passed. Test DYNAMIC-LET.8... Passed. Test DYNAMIC-LET.9... Passed. Test DYNAMIC-LET.0... Passed. NIL And with the kludge: BLOG/DLET> (lisp-implementation-type) "SBCL" BLOG/DLET> (run-tests) Test DYNAMIC-LET.1... Passed. Test DYNAMIC-LET.2... Passed. Test DYNAMIC-LET.3... Passed. Test DYNAMIC-LET.4... Passed. Test DYNAMIC-LET.5... Passed. Test DYNAMIC-LET.6... Passed. Test DYNAMIC-LET.7... Passed. Test DYNAMIC-LET.8... Passed. Test DYNAMIC-LET.9... Passed. Test DYNAMIC-LET.0... Passed. NIL Summary In this post we've made our implementation to work on SBCL even when there are more than a few thousand dynamic variables. We've also added a simple test suite that checks the basic behavior. As it often happens, after achieving some goal we get greedy and achieve more. That's the case here as well. In the next (and the last) post in this series I'll explore the idea of adding truly thread-local variables without a shared global value. This will be useful for lazily creating context on threads that are outside of our control. We'll also generalize the implementation so it is possible to subclass and implement ones own flavor of a dynamic variable. Full Article
rt TurtleWare: Dynamic Vars - Return of the Jedi By turtleware.eu Published On :: Mon, 04 Nov 2024 00:00:00 GMT Table of Contents The protocol Control operators Synchronized hash tables with weakness First-class dynamic variables STANDARD-DYNAMIC-VARIABLE SURROGATE-DYNAMIC-VARIABLE Thread-local variables The protocol The implementation Thread-local slots What can we use it for? In the previous two posts I've presented an implementation of first-class dynamic variables using PROGV and a surrogate implementation for SBCL. Now we will double down on this idea and make the protocol extensible. Finally we'll implement a specialized version of dynamic variables where even the top level value of the variable is thread-local. The protocol Previously we've defined operators as either macros or functions. Different implementations were protected by the feature flag and symbols collided. Now we will introduce the protocol composed of a common superclass and functions that are specialized by particular implementations. Most notably we will introduce a new operator CALL-WITH-DYNAMIC-VARIABLE that is responsible for establishing a single binding. Thanks to that it will be possible to mix dynamic variables of different types within a single DLET statement. (defclass dynamic-variable () ()) (defgeneric dynamic-variable-bindings (dvar)) (defgeneric dynamic-variable-value (dvar)) (defgeneric (setf dynamic-variable-value) (value dvar)) (defgeneric dynamic-variable-bound-p (dvar)) (defgeneric dynamic-variable-makunbound (dvar)) (defgeneric call-with-dynamic-variable (cont dvar &optional value)) Moreover we'll define a constructor that is specializable by a key. This design will allow us to refer to the dynamic variable class by using a shorter name. We will also define the standard class to be used and an matching constructor. (defparameter *default-dynamic-variable-class* #-fake-progv-kludge 'standard-dynamic-variable #+fake-progv-kludge 'surrogate-dynamic-variable) (defgeneric make-dynamic-variable-using-key (key &rest initargs) (:method (class &rest initargs) (apply #'make-instance class initargs)) (:method ((class (eql t)) &rest initargs) (apply #'make-instance *default-dynamic-variable-class* initargs)) (:method ((class null) &rest initargs) (declare (ignore class initargs)) (error "Making a dynamic variable that is not, huh?"))) (defun make-dynamic-variable (&rest initargs) (apply #'make-dynamic-variable-using-key t initargs)) Control operators Control operators are the same as previously, that is a set of four macros that consume the protocol specified above. Note that DYNAMIC-VARIABLE-PROGV expands to a recursive call where each binding is processed separately. (defmacro dlet (bindings &body body) (flet ((pred (binding) (and (listp binding) (= 2 (length binding))))) (unless (every #'pred bindings) (error "DLET: bindings must be lists of two values.~%~ Invalid bindings:~%~{ ~s~%~}" (remove-if #'pred bindings)))) (loop for (var val) in bindings collect var into vars collect val into vals finally (return `(dynamic-variable-progv (list ,@vars) (list ,@vals) ,@body)))) (defmacro dset (&rest pairs) `(setf ,@(loop for (var val) on pairs by #'cddr collect `(dref ,var) collect val))) (defmacro dref (variable) `(dynamic-variable-value ,variable)) (defun call-with-dynamic-variable-progv (cont vars vals) (flet ((thunk () (if vals (call-with-dynamic-variable cont (car vars) (car vals)) (call-with-dynamic-variable cont (car vars))))) (if vars (call-with-dynamic-variable-progv #'thunk (cdr vars) (cdr vals)) (funcall cont)))) (defmacro dynamic-variable-progv (vars vals &body body) (let ((cont (gensym))) `(flet ((,cont () ,@body)) (call-with-dynamic-variable-progv (function ,cont) ,vars ,vals)))) Synchronized hash tables with weakness Previously we've used SBCL-specific options to define a synchronized hash table with weak keys. This won't do anymore, because we will need a similar object to implement the thread-local storage for top level values. trivial-garbage is a portability layer that allows to define hash tables with a specified weakness, but it does not provide an argument that would abstract away synchronization. We will ensure thread-safety with locks instead. (defclass tls-table () ((table :initform (trivial-garbage:make-weak-hash-table :test #'eq :weakness :key)) (lock :initform (bt:make-lock)))) (defun make-tls-table () (make-instance 'tls-table)) (defmacro with-tls-table ((var self) &body body) (let ((obj (gensym))) `(let* ((,obj ,self) (,var (slot-value ,obj 'table))) (bt:with-lock-held ((slot-value ,obj 'lock)) ,@body)))) First-class dynamic variables STANDARD-DYNAMIC-VARIABLE Previously in the default implementation we've represented dynamic variables with a symbol. The new implementation is similar except that the symbol is read from a STANDARD-OBJECT that represents the variable. This also enables us to specialize the function CALL-WITH-DYNAMIC-VARIABLE: (defclass standard-dynamic-variable (dynamic-variable) ((symbol :initform (gensym) :accessor dynamic-variable-bindings))) (defmethod dynamic-variable-value ((dvar standard-dynamic-variable)) (symbol-value (dynamic-variable-bindings dvar))) (defmethod (setf dynamic-variable-value) (value (dvar standard-dynamic-variable)) (setf (symbol-value (dynamic-variable-bindings dvar)) value)) (defmethod dynamic-variable-bound-p ((dvar standard-dynamic-variable)) (boundp (dynamic-variable-bindings dvar))) (defmethod dynamic-variable-makunbound ((dvar standard-dynamic-variable)) (makunbound (dynamic-variable-bindings dvar))) (defmethod call-with-dynamic-variable (cont (dvar standard-dynamic-variable) &optional (val nil val-p)) (progv (list (dynamic-variable-bindings dvar)) (if val-p (list val) ()) (funcall cont))) SURROGATE-DYNAMIC-VARIABLE The implementation of the SURROGATE-DYNAMIC-VARIABLE is almost the same as previously. The only difference is that we use the previously defined indirection to safely work with hash tables. Also note, that we are not add the feature condition - both classes is always created. (defvar +fake-unbound+ 'unbound) (defvar +cell-unbound+ '(no-binding)) (defclass surrogate-dynamic-variable (dynamic-variable) ((tls-table :initform (make-tls-table) :reader dynamic-variable-tls-table) (top-value :initform +fake-unbound+ :accessor dynamic-variable-top-value))) (defmethod dynamic-variable-bindings ((dvar surrogate-dynamic-variable)) (let ((process (bt:current-thread))) (with-tls-table (tls-table (dynamic-variable-tls-table dvar)) (gethash process tls-table +cell-unbound+)))) (defmethod (setf dynamic-variable-bindings) (value (dvar surrogate-dynamic-variable)) (let ((process (bt:current-thread))) (with-tls-table (tls-table (dynamic-variable-tls-table dvar)) (setf (gethash process tls-table) value)))) (defun %dynamic-variable-value (dvar) (let ((tls-binds (dynamic-variable-bindings dvar))) (if (eq tls-binds +cell-unbound+) (dynamic-variable-top-value dvar) (car tls-binds)))) (defmethod dynamic-variable-value ((dvar surrogate-dynamic-variable)) (let ((tls-value (%dynamic-variable-value dvar))) (when (eq tls-value +fake-unbound+) (error 'unbound-variable :name "(unnamed)")) tls-value)) (defmethod (setf dynamic-variable-value) (value (dvar surrogate-dynamic-variable)) (let ((tls-binds (dynamic-variable-bindings dvar))) (if (eq tls-binds +cell-unbound+) (setf (dynamic-variable-top-value dvar) value) (setf (car tls-binds) value)))) (defmethod dynamic-variable-bound-p ((dvar surrogate-dynamic-variable)) (not (eq +fake-unbound+ (%dynamic-variable-value dvar)))) (defmethod dynamic-variable-makunbound ((dvar surrogate-dynamic-variable)) (setf (dynamic-variable-value dvar) +fake-unbound+)) ;;; Apparently CCL likes to drop^Helide some writes and that corrupts bindings ;;; table. Let's ensure that the value is volatile. #+ccl (defvar *ccl-ensure-volatile* nil) (defmethod call-with-dynamic-variable (cont (dvar surrogate-dynamic-variable) &optional (val +fake-unbound+)) (push val (dynamic-variable-bindings dvar)) (let (#+ccl (*ccl-ensure-volatile* (dynamic-variable-bindings dvar))) (unwind-protect (funcall cont) (pop (dynamic-variable-bindings dvar))))) Thread-local variables We've refactored the previous code to be extensible. Now we can use metaobjects from the previous post without change. We can also test both implementations in the same process interchangeably by customizing the default class parameter. It is the time now to have some fun and extend dynamic variables into variables with top value not shared between different threads. This will enable ultimate thread safety. With our new protocol the implementation is trivial! The protocol First we will define the protocol class. THREAD-LOCAL-VARIABLE is a variant of a DYNAMIC-VARIABLE with thread-local top values. We specify initialization arguments :INITVAL and :INITFUN that will be used to assign the top value of a binding. The difference is that INITVAL specifies a single value, while INITFUN can produce an unique object on each invocation. INITARG takes a precedence over INTIFUN, and if neither is supplied, then a variable is unbound. We include the constructor that builds on MAKE-DYNAMIC-VARIABLE-USING-KEY, and macros corresponding to DEFVAR and DEFPARAMETER. Note that they expand to :INITFUN - this assures that the initialization form is re-evaluated for each new thread where the variable is used. (defclass thread-local-variable (dynamic-variable) ()) (defmethod initialize-instance :after ((self thread-local-variable) &key initfun initval) (declare (ignore self initfun initval))) (defparameter *default-thread-local-variable-class* #-fake-progv-kludge 'standard-thread-local-variable #+fake-progv-kludge 'surrogate-thread-local-variable) (defun make-thread-local-variable (&rest initargs) (apply #'make-dynamic-variable-using-key *default-thread-local-variable-class* initargs)) (defmacro create-tls-variable (&optional (form nil fp) &rest initargs) `(make-thread-local-variable ,@(when fp `(:initfun (lambda () ,form))) ,@initargs)) (defmacro define-tls-variable (name &rest initform-and-initargs) `(defvar ,name (create-tls-variable ,@initform-and-initargs))) (defmacro define-tls-parameter (name &rest initform-and-initargs) `(defparameter ,name (create-tls-variable ,@initform-and-initargs))) Perhaps it is a good time to introduce a new convention for tls variable names. I think that surrounding names with the minus sign is a nice idea, because it signifies, that it is something less than a global value. For example: DYNAMIC-VARS> (define-tls-variable -context- (progn (print "Initializing context!") (list :context))) -CONTEXT- DYNAMIC-VARS> -context- #<a EU.TURTLEWARE.DYNAMIC-VARS::STANDARD-THREAD-LOCAL-VARIABLE 0x7f7636c08640> DYNAMIC-VARS> (dref -context-) "Initializing context!" (:CONTEXT) DYNAMIC-VARS> (dref -context-) (:CONTEXT) DYNAMIC-VARS> (dset -context- :the-new-value) :THE-NEW-VALUE DYNAMIC-VARS> (dref -context-) :THE-NEW-VALUE DYNAMIC-VARS> (bt:make-thread (lambda () (print "Let's read it!") (print (dref -context-)))) #<process "Anonymous thread" 0x7f7637a26cc0> "Let's read it!" "Initializing context!" (:CONTEXT) DYNAMIC-VARS> (dref -context-) :THE-NEW-VALUE The implementation You might have noticed the inconspicuous operator DYNAMIC-VARIABLE-BINDINGS that is part of the protocol. It returns an opaque object that represents values of the dynamic variable in the current context: for STANDARD-DYNAMIC-VARIABLE it is a symbol for SURROGATE-DYNAMIC-VARIABLE it is a thread-local list of bindings In any case all other operators first take this object and then use it to read, write or bind the value. The gist of the tls variables implementation is to always return an object that is local to the thread. To store these objects we will use the tls-table we've defined earlier. (defclass thread-local-variable-mixin (dynamic-variable) ((tls-table :initform (make-tls-table) :reader dynamic-variable-tls-table) (tls-initfun :initarg :initfun :initform nil :accessor thread-local-variable-initfun) (tls-initval :initarg :initval :initform +fake-unbound+ :accessor thread-local-variable-initval))) For the class STANDARD-THREAD-LOCAL-VARIABLE we will simply return a different symbol depending on the thread: (defclass standard-thread-local-variable (thread-local-variable-mixin thread-local-variable standard-dynamic-variable) ()) (defmethod dynamic-variable-bindings ((tvar standard-thread-local-variable)) (flet ((make-new-tls-bindings () (let ((symbol (gensym)) (initval (thread-local-variable-initval tvar)) (initfun (thread-local-variable-initfun tvar))) (cond ((not (eq +fake-unbound+ initval)) (setf (symbol-value symbol) initval)) ((not (null initfun)) (setf (symbol-value symbol) (funcall initfun)))) symbol))) (let ((key (bt:current-thread))) (with-tls-table (tls-table (dynamic-variable-tls-table tvar)) (or (gethash key tls-table) (setf (gethash key tls-table) (make-new-tls-bindings))))))) And for the class SURROGATE-THREAD-LOCAL-VARIABLE the only difference from the SURROGATE-DYNAMIC-VARIABLE implementation is to cons a new list as the initial value (even when it is unbound) to ensure it is not EQ to +CELL-UNBOUND+. (defclass surrogate-thread-local-variable (thread-local-variable-mixin thread-local-variable surrogate-dynamic-variable) ()) (defmethod dynamic-variable-bindings ((tvar surrogate-thread-local-variable)) (flet ((make-new-tls-bindings () (let ((initval (thread-local-variable-initval tvar)) (initfun (thread-local-variable-initfun tvar))) (cond ((not (eq +fake-unbound+ initval)) (list initval)) ((not (null initfun)) (list (funcall initfun))) (t (list +fake-unbound+)))))) (let ((key (bt:current-thread))) (with-tls-table (tls-table (dynamic-variable-tls-table tvar)) (or (gethash key tls-table) (setf (gethash key tls-table) (make-new-tls-bindings))))))) That's all, now we have two implementations of thread-local variables. Ramifications are similar as with "ordinary" dynamic variables - the standard implementation is not advised for SBCL, because it will crash in LDB. Thread-local slots First we are going to allow to defined dynamic variable types with an abbreviated names. This will enable us to specify in the slot definition that type, for example (MY-SLOT :DYNAMIC :TLS :INITFORM 34) ;;; Examples how to add shorthand type names for the dynamic slots: (defmethod make-dynamic-variable-using-key ((key (eql :tls)) &rest initargs) (apply #'make-dynamic-variable-using-key *default-thread-local-variable-class* initargs)) (defmethod make-dynamic-variable-using-key ((key (eql :normal-tls)) &rest initargs) (apply #'make-dynamic-variable-using-key 'standard-thread-local-variable initargs)) (defmethod make-dynamic-variable-using-key ((key (eql :kludge-tls)) &rest initargs) (apply #'make-dynamic-variable-using-key 'surrogate-thread-local-variable initargs)) ;;; For *DEFAULT-DYNAMIC-VARIABLE* specify :DYNAMIC T. (defmethod make-dynamic-variable-using-key ((key (eql :normal-dyn)) &rest initargs) (apply #'make-dynamic-variable-using-key 'standard-dynamic-variable initargs)) (defmethod make-dynamic-variable-using-key ((key (eql :kludge-dyn)) &rest initargs) (apply #'make-dynamic-variable-using-key 'surrogate-dynamic-variable initargs)) In order to do that, we need to remember he value of the argument :DYNAMIC. We will read it with DYNAMIC-VARIABLE-TYPE and that value will be available in both direct and the effective slot: ;;; Slot definitions ;;; There is a considerable boilerplate involving customizing slots. ;;; ;;; - direct slot definition: local to a single defclass form ;;; ;;; - effective slot definition: combination of all direct slots with the same ;;; name in the class and its superclasses ;;; (defclass dynamic-direct-slot (mop:standard-direct-slot-definition) ((dynamic :initform nil :initarg :dynamic :reader dynamic-variable-type))) ;;; The metaobject protocol did not specify an elegant way to communicate ;;; between the direct slot definition and the effective slot definition. ;;; Luckily we have dynamic bindings! :-) (defvar *kludge/mop-deficiency/dynamic-variable-type* nil) ;;; DYNAMIC-EFFECTIVE-SLOT is implemented to return as slot-value values of the ;;; dynamic variable that is stored with the instance. ;;; ;;; It would be nice if we could specify :ALLOCATION :DYNAMIC for the slot, but ;;; then STANDARD-INSTANCE-ACCESS would go belly up. We could make a clever ;;; workaround, but who cares? (defclass dynamic-effective-slot (mop:standard-effective-slot-definition) ((dynamic :initform *kludge/mop-deficiency/dynamic-variable-type* :reader dynamic-variable-type))) Moreover we specialize the function MAKE-DYNAMIC-VARIABLE-USING-KEY to the effective slot class. The initargs in this method are meant for the instance. When the dynamic variable is created, we check whether it is a thread-local variable and initialize its INITVAL and INITFUN to values derived from INITARGS, MOP:SLOT-DEFINITION-INITARGS and MOP:SLOT-DEFINITION-INITFUN: (defmethod make-dynamic-variable-using-key ((key dynamic-effective-slot) &rest initargs) (let* ((dvar-type (dynamic-variable-type key)) (dvar (make-dynamic-variable-using-key dvar-type))) (when (typep dvar 'thread-local-variable) (loop with slot-initargs = (mop:slot-definition-initargs key) for (key val) on initargs by #'cddr when (member key slot-initargs) do (setf (thread-local-variable-initval dvar) val)) (setf (thread-local-variable-initfun dvar) (mop:slot-definition-initfunction key))) dvar)) The rest of the implementation of DYNAMIC-EFFECTIVE-SLOT is unchanged: (defmethod mop:slot-value-using-class ((class standard-class) object (slotd dynamic-effective-slot)) (dref (slot-dvar object slotd))) (defmethod (setf mop:slot-value-using-class) (new-value (class standard-class) object (slotd dynamic-effective-slot)) (dset (slot-dvar object slotd) new-value)) (defmethod mop:slot-boundp-using-class ((class standard-class) object (slotd dynamic-effective-slot)) (dynamic-variable-bound-p (slot-dvar object slotd))) (defmethod mop:slot-makunbound-using-class ((class standard-class) object (slotd dynamic-effective-slot)) (dynamic-variable-makunbound (slot-dvar object slotd))) The implementation of CLASS-WITH-DYNAMIC-SLOTS is also very similar. The first difference in that ALLOCATE-INSTANCE calls MAKE-DYNAMIC-VARIABLE-USING-KEY instead of MAKE-DYNAMIC-VARIABLE and supplies the effective slot definition as the key, and the instance initargs as the remaining arguments. Note that at this point initargs are already validated by MAKE-INSTANCE. The second difference is that MOP:COMPUTE-EFFECTIVE-SLOT-DEFINITION binds the flag *KLUDGE/MOP-DEFICIENCY/DYNAMIC-VARIABLE-TYPE* to DYNAMIC-VARIABLE-TYPE. ;;; This is a metaclass that allows defining dynamic slots that are bound with ;;; the operator SLOT-DLET, and, depending on the type, may have thread-local ;;; top value. ;;; ;;; The metaclass CLASS-WITH-DYNAMIC-SLOTS specifies alternative effective slot ;;; definitions for slots with an initarg :dynamic. (defclass class-with-dynamic-slots (standard-class) ()) ;;; Class with dynamic slots may be subclasses of the standard class. (defmethod mop:validate-superclass ((class class-with-dynamic-slots) (super standard-class)) t) ;;; When allocating the instance we initialize all slots to a fresh symbol that ;;; represents the dynamic variable. (defmethod allocate-instance ((class class-with-dynamic-slots) &rest initargs) (let ((object (call-next-method))) (loop for slotd in (mop:class-slots class) when (typep slotd 'dynamic-effective-slot) do (setf (mop:standard-instance-access object (mop:slot-definition-location slotd)) (apply #'make-dynamic-variable-using-key slotd initargs))) object)) ;;; To improve potential composability of CLASS-WITH-DYNAMIC-SLOTS with other ;;; metaclasses we treat specially only slots that has :DYNAMIC in initargs, ;;; otherwise we call the next method. (defmethod mop:direct-slot-definition-class ((class class-with-dynamic-slots) &rest initargs) (loop for (key) on initargs by #'cddr when (eq key :dynamic) do (return-from mop:direct-slot-definition-class (find-class 'dynamic-direct-slot))) (call-next-method)) (defmethod mop:compute-effective-slot-definition ((class class-with-dynamic-slots) name direct-slotds) (declare (ignore name)) (let ((latest-slotd (first direct-slotds))) (if (typep latest-slotd 'dynamic-direct-slot) (let ((*kludge/mop-deficiency/dynamic-variable-type* (dynamic-variable-type latest-slotd))) (call-next-method)) (call-next-method)))) (defmethod mop:effective-slot-definition-class ((class class-with-dynamic-slots) &rest initargs) (declare (ignore initargs)) (if *kludge/mop-deficiency/dynamic-variable-type* (find-class 'dynamic-effective-slot) (call-next-method))) Finally the implementation of SLOT-DLET does not change: ;;; Accessing and binding symbols behind the slot. We don't use SLOT-VALUE, ;;; because it will return the _value_ of the dynamic variable, and not the ;;; variable itself. (defun slot-dvar (object slotd) (check-type slotd dynamic-effective-slot) (mop:standard-instance-access object (mop:slot-definition-location slotd))) (defun slot-dvar* (object slot-name) (let* ((class (class-of object)) (slotd (find slot-name (mop:class-slots class) :key #'mop:slot-definition-name))) (slot-dvar object slotd))) (defmacro slot-dlet (bindings &body body) `(dlet ,(loop for ((object slot-name) val) in bindings collect `((slot-dvar* ,object ,slot-name) ,val)) ,@body)) Finally we can define a class with slots that do not share the top value: DYNAMIC-VARS> (defclass c1 () ((slot1 :initarg :slot1 :dynamic nil :accessor slot1) (slot2 :initarg :slot2 :dynamic t :accessor slot2) (slot3 :initarg :slot3 :dynamic :tls :accessor slot3)) (:metaclass class-with-dynamic-slots)) #<The EU.TURTLEWARE.DYNAMIC-VARS::CLASS-WITH-DYNAMIC-SLOTS EU.TURTLEWARE.DYNAMIC-VARS::C1> DYNAMIC-VARS> (with-slots (slot1 slot2 slot3) *object* (setf slot1 :x slot2 :y slot3 :z) (list slot1 slot2 slot3)) (:X :Y :Z) DYNAMIC-VARS> (bt:make-thread (lambda () (with-slots (slot1 slot2 slot3) *object* (setf slot1 :i slot2 :j slot3 :k) (print (list slot1 slot2 slot3))))) #<process "Anonymous thread" 0x7f76424c0240> (:I :J :K) DYNAMIC-VARS> (with-slots (slot1 slot2 slot3) *object* (list slot1 slot2 slot3)) (:I :J :Z) What can we use it for? Now that we know how to define thread-local variables, we are left with a question what can we use it for. Consider having a line-buffering stream. One possible implementation could be sketched as: (defclass line-buffering-stream (fancy-stream) ((current-line :initform (make-adjustable-string) :accessor current-line) (current-ink :initform +black+ :accessor current-ink))) (defmethod stream-write-char ((stream line-buffering-stream) char) (if (char= char # ewline) (terpri stream) (vector-push-extend char (current-line stream)))) (defmethod stream-terpri ((stream line-buffering-stream)) (%put-line-on-screen (current-line stream) (current-ink stream)) (setf (fill-pointer (current-line stream)) 0)) If this stream is shared between multiple threads, then even if individual operations and %PUT-LINE-ON-SCREEN are thread-safe , we have a problem. For example FORMAT writes are not usually atomic and individual lines are easily corrupted. If we use custom colors, these are also a subject of race conditions. The solution is as easy as making both slots thread-local. In that case the buffered line is private to each thread and it is put on the screen atomically: (defclass line-buffering-stream (fancy-stream) ((current-line :initform (make-adjustable-string) :accessor current-line :dynamic :tls) (current-ink :initform +black+ :accessor current-ink :dynamic :tls)) (:metaclass class-with-dynamic-slots)) Technique is not limited to streams. It may benefit thread-safe drawing, request processing, resource management and more. By subclassing DYNAMIC-VARIABLE we could create also variables that are local to different objects than processes. I hope that you've enjoyed reading this post as much as I had writing it. If you are interested in a full standalone implementation, with tests and system definitions, you may get it here. Cheers! Full Article
rt All Souls Night (Part 15 of 31) By floggingbabel.blogspot.com Published On :: Tue, 15 Oct 2024 07:30:00 +0000 . CONTINUED TOMORROW. Above: Every Autumn, I write a Halloween story, write it out on leaves (one word per leaf), photograph the leaves, and then leave them where.I found them. The story is then serialized, starting on October 1 and concluding on the 31st--All Souls Day. * Full Article
rt All Souls Night (Part 16 of 31) By floggingbabel.blogspot.com Published On :: Wed, 16 Oct 2024 07:30:00 +0000 . CONTINUED TOMORROW. Above: Every Autumn, I write a Halloween story, write it out on leaves (one word per leaf), photograph the leaves, and then leave them where.I found them. The story is then serialized, starting on October 1 and concluding on the 31st--All Souls Day. * Full Article
rt All Souls Night (Part 17 of 31) By floggingbabel.blogspot.com Published On :: Thu, 17 Oct 2024 07:30:00 +0000 . CONTINUED TOMORROW. Above: Every Autumn, I write a Halloween story, write it out on leaves (one word per leaf), photograph the leaves, and then leave them where.I found them. The story is then serialized, starting on October 1 and concluding on the 31st--All Souls Day. * Full Article
rt All Souls Night (Part 18 of 31) By floggingbabel.blogspot.com Published On :: Fri, 18 Oct 2024 07:30:00 +0000 . CONTINUED TOMORROW. Above: Every Autumn, I write a Halloween story, write it out on leaves (one word per leaf), photograph the leaves, and then leave them where. I found them. The story is then serialized, starting on October 1 and concluding on the 31st--All Souls Day. * Full Article
rt All Souls Night (Part 19 of 31) By floggingbabel.blogspot.com Published On :: Sat, 19 Oct 2024 07:30:00 +0000 . CONTINUED TOMORROW. Above: Every Autumn, I write a Halloween story, write it out on leaves (one word per leaf), photograph the leaves, and then leave them where.I found them. The story is then serialized, starting on October 1 and concluding on the 31st--All Souls Day. * Full Article
rt All Souls Night (Part 20 of 31) By floggingbabel.blogspot.com Published On :: Sun, 20 Oct 2024 07:30:00 +0000 . CONTINUED TOMORROW. Above: Every Autumn, I write a Halloween story, write it out on leaves (one word per leaf), photograph the leaves, and then leave them where.I found them. The story is then serialized, starting on October 1 and concluding on the 31st--All Souls Day. * Full Article
rt All Souls Night (Part 21 of 31) By floggingbabel.blogspot.com Published On :: Mon, 21 Oct 2024 07:30:00 +0000 . CONTINUED TOMORROW. Above: Every Autumn, I write a Halloween story, write it out on leaves (one word per leaf), photograph the leaves, and then leave them where.I found them. The story is then serialized, starting on October 1 and concluding on the 31st--All Souls Day. * Full Article
rt All Souls Night (Part 22 of 31) By floggingbabel.blogspot.com Published On :: Tue, 22 Oct 2024 07:30:00 +0000 . CONTINUED TOMORROW. Above: Every Autumn, I write a Halloween story, write it out on leaves (one word per leaf), photograph the leaves, and then leave them where.I found them. The story is then serialized, starting on October 1 and concluding on the 31st--All Souls Day. * Full Article
rt All Souls Night (Part 23 of 31) By floggingbabel.blogspot.com Published On :: Wed, 23 Oct 2024 07:30:00 +0000 . CONTINUED TOMORROW. (For those who came in late: The first sentence was posted here on October 1 and a new sentence was posted every day thereafter.) Above: Every Autumn, I write a Halloween story, write it out on leaves (one word per leaf), photograph the leaves, and then leave them where.I found them. The story is then serialized, starting on October 1 and concluding on the 31st--All Souls Day. * Full Article
rt All Souls Night (Part 24 of 31) By floggingbabel.blogspot.com Published On :: Thu, 24 Oct 2024 07:30:00 +0000 . CONTINUED TOMORROW. (For those who came in late: The first sentence was posted here on October 1 and a new sentence was posted every day thereafter.) Above: Every Autumn, I write a Halloween story, write it out on leaves (one word per leaf), photograph the leaves, and then leave them where.I found them. The story is then serialized, starting on October 1 and concluding on the 31st--All Souls Day. * Full Article
rt All Souls Night (Part 25 of 31) By floggingbabel.blogspot.com Published On :: Fri, 25 Oct 2024 07:30:00 +0000 . CONTINUED TOMORROW. (For those who came in late: The first sentence was posted here on October 1 and a new sentence was posted every day thereafter.) Above: Every Autumn, I write a Halloween story, write it out on leaves (one word per leaf), photograph the leaves, and then leave them where.I found them. The story is then serialized, starting on October 1 and concluding on the 31st--All Souls Day. * Full Article
rt All Souls Night (Part 26 of 31) By floggingbabel.blogspot.com Published On :: Sat, 26 Oct 2024 07:30:00 +0000 . CONTINUED TOMORROW. (For those who came in late: The first sentence was posted here on October 1 and a new sentence was posted every day thereafter.) Above: Every Autumn, I write a Halloween story, write it out on leaves (one word per leaf), photograph the leaves, and then leave them where.I found them. The story is then serialized, starting on October 1 and concluding on the 31st--All Souls Day. * Full Article
rt All Souls Night (Part 27 of 31) By floggingbabel.blogspot.com Published On :: Sun, 27 Oct 2024 07:30:00 +0000 . CONTINUED TOMORROW. (For those who came in late: The first sentence was posted here on October 1 and a new sentence was posted every day thereafter.) Above: Every Autumn, I write a Halloween story, write it out on leaves (one word per leaf), photograph the leaves, and then leave them where.I found them. The story is then serialized, starting on October 1 and concluding on the 31st--All Souls Day. * Full Article
rt All Souls Night (Part 28 of 31) By floggingbabel.blogspot.com Published On :: Mon, 28 Oct 2024 07:30:00 +0000 . CONTINUED TOMORROW. (For those who came in late: The first sentence was posted here on October 1 and a new sentence was posted every day thereafter.) Above: Every Autumn, I write a Halloween story, write it out on leaves (one word per leaf), photograph the leaves, and then leave them where.I found them. The story is then serialized, starting on October 1 and concluding on the 31st--All Souls Day. * Full Article
rt All Souls Night (Part 29 of 31) By floggingbabel.blogspot.com Published On :: Tue, 29 Oct 2024 07:30:00 +0000 . CONTINUED TOMORROW. (For those who came in late: The first sentence was posted here on October 1 and a new sentence was posted every day thereafter.) Above: Every Autumn, I write a Halloween story, write it out on leaves (one word per leaf), photograph the leaves, and then leave them where.I found them. The story is then serialized, starting on October 1 and concluding on the 31st--All Souls Day. * Full Article
rt All Souls Night (Part 30 of 31) By floggingbabel.blogspot.com Published On :: Wed, 30 Oct 2024 07:30:00 +0000 . CONTINUED TOMORROW. (For those who came in late: The first sentence was posted here on October 1 and a new sentence was posted every day thereafter, to make a complete story.) Above: Every Autumn, I write a Halloween story, write it out on leaves (one word per leaf), photograph the leaves, and then leave them where.I found them. The story is then serialized, starting on October 1 and concluding on the 31st--All Souls Day. * Full Article
rt Why Virat Kohli, Jasprit Bumrah were missing from Perth nets; India ramp up privacy amid Manchester United-like security - Hindustan Times By news.google.com Published On :: Wed, 13 Nov 2024 04:53:31 GMT Why Virat Kohli, Jasprit Bumrah were missing from Perth nets; India ramp up privacy amid Manchester United-like security Hindustan TimesVirat Kohli in focus: Intense net session begins for upcoming Test series against Australia The Times of IndiaVirat Kohli in Australia for BGT: A timeline India TodayBlack veil of secrecy: India begin training in privacy in Perth ESPNcricinfoIndia to play intra-squad warm-up match at WACA on Friday ahead of Australia Tests but BCCI denies public viewing Hindustan Times Full Article
rt my hands hurt By www.marriedtothesea.com Published On :: Thu, 29 Sep 2022 04:00:00 EDT Today on Married To The Sea: my hands hurtThis RSS feed is brought to you by Drew and Natalie's podcast Garbage Brain University. Our new series Everything Is Real explores the world of cryptids, aliens, quantum physics, the occult, and more. If you use this RSS feed, please consider supporting us by becoming a patron. Patronage includes membership to our private Discord server and other bonus material non-patrons never see! Full Article autogen_comic
rt w0w b1g f0rtune By www.marriedtothesea.com Published On :: Wed, 07 Jun 2023 04:00:00 EDT Today on Married To The Sea: w0w b1g f0rtuneThis RSS feed is brought to you by Drew and Natalie's podcast Garbage Brain University. Our new series Everything Is Real explores the world of cryptids, aliens, quantum physics, the occult, and more. If you use this RSS feed, please consider supporting us by becoming a patron. Patronage includes membership to our private Discord server and other bonus material non-patrons never see! Full Article autogen_comic
rt go forth strong man By www.marriedtothesea.com Published On :: Wed, 26 Jul 2023 04:00:00 EDT Today on Married To The Sea: go forth strong manThis RSS feed is brought to you by Drew and Natalie's podcast Garbage Brain University. Our new series Everything Is Real explores the world of cryptids, aliens, quantum physics, the occult, and more. If you use this RSS feed, please consider supporting us by becoming a patron. Patronage includes membership to our private Discord server and other bonus material non-patrons never see! Full Article autogen_comic
rt were supposed to use the earth By www.marriedtothesea.com Published On :: Wed, 03 Apr 2024 04:00:00 EDT Today on Married To The Sea: were supposed to use the earthThis RSS feed is brought to you by Drew and Natalie's podcast Garbage Brain University. Our new series Everything Is Real explores the world of cryptids, aliens, quantum physics, the occult, and more. If you use this RSS feed, please consider supporting us by becoming a patron. Patronage includes membership to our private Discord server and other bonus material non-patrons never see! Full Article autogen_comic
rt rich people are smarter By www.marriedtothesea.com Published On :: Wed, 08 May 2024 04:00:00 EDT Today on Married To The Sea: rich people are smarterThis RSS feed is brought to you by Drew and Natalie's podcast Garbage Brain University. Our new series Everything Is Real explores the world of cryptids, aliens, quantum physics, the occult, and more. If you use this RSS feed, please consider supporting us by becoming a patron. Patronage includes membership to our private Discord server and other bonus material non-patrons never see! Full Article autogen_comic
rt martin luther By www.marriedtothesea.com Published On :: Wed, 10 Jul 2024 04:00:00 EDT Today on Married To The Sea: martin lutherThis RSS feed is brought to you by Drew and Natalie's podcast Garbage Brain University. Our new series Everything Is Real explores the world of cryptids, aliens, quantum physics, the occult, and more. If you use this RSS feed, please consider supporting us by becoming a patron. Patronage includes membership to our private Discord server and other bonus material non-patrons never see! Full Article autogen_comic
rt Hallo kroket! Mike De Decker vermorzelt Michael Smith en treft Luke Littler in Grand Slam of Darts - Gazet van Antwerpen By news.google.com Published On :: Wed, 13 Nov 2024 05:28:38 GMT Hallo kroket! Mike De Decker vermorzelt Michael Smith en treft Luke Littler in Grand Slam of Darts Gazet van AntwerpenSterke Van den Bergh en De Decker stoten door in Grand Slam of Darts, onverwachte exit Van Gerwen sporza.beVIDEO. Hallo kroket! Mike De Decker vermorzelt Michael Smith en treft Luke Littler in 1/8ste finale Grand Slam of Darts Het NieuwsbladVIDEO. Dimitri Van den Bergh flitst naar 1/8ste finales Grand Slam of Darts, met dank aan een muntje: “Ik ga iets uit mijn achterzak pakken...” Gazet van AntwerpenMike De Decker bij laatste 16 op Grand Slam of Darts RTV Full Article
rt Gladiator 2: De langstverwachte film van het jaar is een mission impossible - VRT.be By news.google.com Published On :: Wed, 13 Nov 2024 04:30:06 GMT Gladiator 2: De langstverwachte film van het jaar is een mission impossible VRT.beHele verhaal bekijken via Google Nieuws Full Article
rt “‘Dr. Vogel’ was geen dokter”: expert over zin en onzin van homeopathie en kruidengeneeskunde - Het Laatste Nieuws By news.google.com Published On :: Tue, 12 Nov 2024 16:00:00 GMT “‘Dr. Vogel’ was geen dokter”: expert over zin en onzin van homeopathie en kruidengeneeskunde Het Laatste Nieuws Full Article
rt “Absurde toestanden” bij verplichting zonnepanelen voor grote verbruikers: “Zelfs bedrijf dat niets meer produceert, moet er leggen” - Het Laatste Nieuws By news.google.com Published On :: Wed, 13 Nov 2024 05:00:00 GMT “Absurde toestanden” bij verplichting zonnepanelen voor grote verbruikers: “Zelfs bedrijf dat niets meer produceert, moet er leggen” Het Laatste Nieuws Full Article
rt Diepenbeek start onderzoek naar fraude door adjunct-financieel directeur: geld van lokaal bestuur verduisterd - Het Nieuwsblad By news.google.com Published On :: Wed, 13 Nov 2024 06:32:27 GMT Diepenbeek start onderzoek naar fraude door adjunct-financieel directeur: geld van lokaal bestuur verduisterd Het Nieuwsblad Full Article
rt Prijsstijging energie-eiland voor kust kan huishoudens jaarlijks "20 euro" extra kosten - VRT.be By news.google.com Published On :: Tue, 12 Nov 2024 16:50:46 GMT Prijsstijging energie-eiland voor kust kan huishoudens jaarlijks "20 euro" extra kosten VRT.beKosten energie-eiland in Noordzee lopen op tot 630 miljoen euro per jaar De TijdKamerleden willen uitstel van miljardencontract voor energie-eiland De StandaardKamerleden willen uitstel voor toewijzing duur contract energie-eiland Knack.beVan der Straeten: “Voorbarig om stekker uit energie-eiland te trekken” Het Belang van Limburg Full Article
rt Man die slapende dakloze in Rotterdam ernstig verwondde met steen mogelijk aangehouden in Franse stad Toulon - VRT.be By news.google.com Published On :: Wed, 13 Nov 2024 05:25:27 GMT Man die slapende dakloze in Rotterdam ernstig verwondde met steen mogelijk aangehouden in Franse stad Toulon VRT.beMan die zware tegel op hoofd van slapende dakloze gooide mogelijk gearresteerd in Frankrijk Het Laatste NieuwsVerdachte (32) van aanval met betonblok op slapende dakloze in Rotterdam opgepakt in Franse stad Toulon Het NieuwsbladPoging moord op slapende, dakloze man Opsporing VerzochtArrestatie in Frankrijk na dood dakloze, link met Rotterdamse zaak onderzocht NOS Full Article
rt Keuze voor hondstrouwe hardliners illustreert welke koers Trump wil varen - De Tijd By news.google.com Published On :: Tue, 12 Nov 2024 18:28:42 GMT Keuze voor hondstrouwe hardliners illustreert welke koers Trump wil varen De TijdTrumps buitenlandteam zoekt snelle deal in Oekraïne en wil druk op Iran verhogen De StandaardWie zit (voorlopig) op welke stoel in het team van verkozen VS-president Donald Trump? VRT.beMarco Rubio genoemd als nieuwe minister van Buitenlandse Zaken van de VS Het NieuwsbladElon Musk wordt ‘minister van Overheidsefficiëntie’: Trumps ‘dreamteam’ begint snel vorm te krijgen AD Full Article
rt Overleden vrouw aangetroffen op oprit van woning in Zwijndrecht, parket opent onderzoek - VRT.be By news.google.com Published On :: Wed, 13 Nov 2024 08:02:08 GMT Overleden vrouw aangetroffen op oprit van woning in Zwijndrecht, parket opent onderzoek VRT.beVrouw vermoord op oprit van woning in Zwijndrecht bij Antwerpen: schedel van slachtoffer werd ingeslagen Het Laatste NieuwsVrouw dood aangetroffen op oprit van een woning in Zwijndrecht, parket start onderzoek naar gewelddadig overlijden Het NieuwsbladVermoorde vrouw aangetroffen voor woning in Zwijndrecht: parket start onderzoek Gazet van AntwerpenLevenloos lichaam van vrouw gevonden op oprit van woning in Zwijndrecht: schedel van slachtoffer werd ingeslagen Het Laatste Nieuws Full Article
rt Petra De Sutter is geen kandidaat-voorzitter Groen: "Partij heeft nu iemand nodig die tanden laat zien" - VRT.be By news.google.com Published On :: Wed, 13 Nov 2024 04:25:41 GMT Petra De Sutter is geen kandidaat-voorzitter Groen: "Partij heeft nu iemand nodig die tanden laat zien" VRT.bePetra De Sutter geen kandidaat-voorzitter voor Groen - Musk gaat onder Trump ministerie voor ‘overheidsefficiëntie’ leiden De Standaard“Andere partijen zijn geoliede machines, wij vergaderen ons dood”: Groen snakt naar nieuwe voorzitter en heeft topfavoriet, maar wil Petra De Sutter ook? Het NieuwsbladNeen, Petra De Sutter wordt geen voorzitter van Groen. In dit interview legt ze uit waarom De Morgen Full Article
rt Nu Bart De Wever (N-VA) aan zet blijft als formateur: krijgt hij in 2 weken rond wat al 5 maanden niet lukt? - VRT.be By news.google.com Published On :: Tue, 12 Nov 2024 17:14:50 GMT Nu Bart De Wever (N-VA) aan zet blijft als formateur: krijgt hij in 2 weken rond wat al 5 maanden niet lukt? VRT.be“De Wever wil Open Vld én Vooruit in federale regering” Het Laatste NieuwsDe Wever wil Arizona nog eens reanimeren met ‘trucje’, maar of Vooruit deze keer hapt? Het Laatste NieuwsDe Wever grijpt naar beproefd recept om Vooruit snel weer aan tafel te krijgen: het ‘saucissoneren’ De MorgenFormatie: ‘Bart De Wever voert een toneeltje op’ Knack.be Full Article
rt Convert Old Junk Bikes Into Race-Ready Fixed Gear Bikes in No Time! By cheezburger.com Published On :: Thu, 04 Oct 2012 08:00:00 -0700 EIGHTINCH shows us how to fix up old bikes using a fairly basic conversion kit. You'll need: Amelia wheels with tires & tubes 16t cog lockring Courier cranks A bottom bracket A KMC chain More videos for both seasoned and amateur bike enthusiasts here! Full Article bicycle bikes How To Video
rt The Hardest Part About Moving into 2014 By cheezburger.com Published On :: Tue, 31 Dec 2013 10:00:00 -0800 Prepare to make this fix a lot. Full Article spelling g rated
rt Lint Trap Fixed, Fire Averted By cheezburger.com Published On :: Fri, 09 Aug 2013 05:00:00 -0700 Full Article funny there I fixed it
rt Opportunity knocks for USMNT's Ricardo Pepi: 'I'm feeling ready to be the man' By www.foxsports.com Published On :: Tue, 12 Nov 2024 18:29:11 -0500 With several U.S. men's national team strikers out with injuries, 21-year-old Ricardo Pepi has a golden opportunity to prove why he deserves to be Mauricio Pochettino top choice up top. Full Article soccer
rt Matthew Nicholson throws down a two-handed slam to help Northwestern lead over UIC going into the half By www.foxsports.com Published On :: Wed, 13 Nov 2024 01:03:13 +0000 Matthew Nicholson threw down a two-handed slam to help the Northwestern Wildcats lead over the the UIC Flames going into the half. Full Article college-basketball
rt Now That's Tasty Comfort By cheezburger.com Published On :: Wed, 21 Aug 2013 07:00:00 -0700 Full Article wtf slippers bread funny
rt This Bizarre Instagram Account Inserts Donald Trump Into Your Favorite Movies By cheezburger.com Published On :: Wed, 28 Aug 2019 07:00:00 -0700 Trump In Cinema is dedicated to displaying some of movie history's best moments with Donald Trump at the center of them. Some of these photoshops are too perfect. Others as just... troubling. Full Article donald trump movies photoshop
rt The Internet Took the Opportunity to Photoshop Donald Trump With a Blank Sign and Ran With It By cheezburger.com Published On :: Wed, 28 Aug 2019 19:00:00 -0700 Has Trump seen people holding signs on the internet before? It never turns out well. Full Article twitter trolling signs donald trump photoshop Memes
rt The Untouched Picture of Kim Jong-Un Started a Supreme Photoshop Battle By cheezburger.com Published On :: Sat, 31 Aug 2019 07:00:00 -0700 North Korea released a smiling picture of Kim Jong-Un and were VERY specific about pointing out the fact that the image was untouched. Obviously the first thing the internet did when they got a hold of the image was to touch it up a bit. The results were glorious. Full Article list photoshop image photoshop battle
rt Nancy Pelosi Pointing At Trump Is An Assertive Dank Meme By cheezburger.com Published On :: Sun, 20 Oct 2019 19:00:00 -0700 During a meeting to discuss Syria, Speaker of the House Nancy Pelosi was photographed assertively pointing a finger at Donald Trump. Trump later tweeted the photo with the caption, "Nervous Nancy's unhinged meltdown!" the photo has inspired a whole host of memes from every political angle. Whether you're a Trump supporter or a Pelosi fan, we think you'll find these trending memes amusing. Or maybe you hate both of them equally! That's certainly an option too! Full Article Republicans donald trump funny memes Nancy Pelosi trending memes Democrat trump memes politics White house
rt Fourteen Joe Biden Memes For The Political Satirists By cheezburger.com Published On :: Fri, 06 Dec 2019 19:00:00 -0800 Look, we definitely don't want to hate on any particular candidate or take sides in this presidential election cycle, but Joe Biden has just been so meme-able this election season that we really had to take advantage of the material handed to us. We think that Biden supporters and haters alike will be able to laugh at these. Full Article 2020 president Democrat presidential election barack obama election joe biden politics
rt Bernie Still Needs Your Financial Support In These Fresh Dank Memes By cheezburger.com Published On :: Fri, 31 Jan 2020 19:00:00 -0800 We've been seeing these Bernie Sanders memes practically everywhere on the internet lately, and they don't appear to be stopping any time soon! Here's our last gallery in case you missed 'em. We sincerely hope you're not sick of political memes yet, because we've still got far to go before the 2020 presidential elections, so buckle up! Full Article bernie sanders funny memes political memes dank memes trending election socialist money politics socialism