5903743a831ac5febec5a81807af348f53f83bde
[lisp] / dep.lisp
1 ;;; -*-lisp-*-
2 ;;;
3 ;;; Maintenance and recalculation of dependent values
4 ;;;
5 ;;; (c) 2008 Mark Wooding
6 ;;;
7
8 ;;;----- Licensing notice ---------------------------------------------------
9 ;;;
10 ;;; This program is free software; you can redistribute it and/or modify
11 ;;; it under the terms of the GNU General Public License as published by
12 ;;; the Free Software Foundation; either version 2 of the License, or
13 ;;; (at your option) any later version.
14 ;;;
15 ;;; This program is distributed in the hope that it will be useful,
16 ;;; but WITHOUT ANY WARRANTY; without even the implied warranty of
17 ;;; MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
18 ;;; GNU General Public License for more details.
19 ;;;
20 ;;; You should have received a copy of the GNU General Public License
21 ;;; along with this program; if not, write to the Free Software Foundation,
22 ;;; Inc., 59 Temple Place - Suite 330, Boston, MA 02111-1307, USA.
23
24 (defpackage #:dep
25 (:use #:common-lisp #:queue)
26 (:export #:dep #:depp #:make-dep #:dep-goodp
27 :delay-recomputing-deps
28 #:install-dep-syntax
29 #:dep-value #:dep-make-bad #:dep-bad #:dep-try
30 #:dep-add-listener))
31 (in-package #:dep)
32
33 ;;;--------------------------------------------------------------------------
34 ;;; Dependencies.
35
36 (defstruct (dep (:predicate depp)
37 (:constructor %make-dep))
38 "There are two kinds of `dep', though we use the same object type for both.
39 A leaf dep has no dependencies, and its value is set explicitly by the
40 programmer. A non-leaf dep has a value /function/, which computes the
41 dep's value as a function of other deps' values. The dependencies don't
42 need to be declared in advance, or remain constant over time.
43
44 When not during a recomputation phase (i.e., when `stable'), a dep is
45 either `good' (i.e., it has a value) or `bad'. An attempt to read the
46 value of a bad dep results in a throw of `bad-dep'. Badness propagates
47 automatically during recomputation phases."
48 (%value nil :type t)
49 (value-func nil :type (or function null))
50 (value-predicate #'eql :type function)
51 (goodp nil :type boolean)
52 (state :pending :type (member :stable :pending :recomputing))
53 (listeners nil :type list)
54 (dependents nil :type list))
55
56 (defvar *evaluating-dep* nil
57 "The dep currently being evaluated. This is bound only during the call of
58 a value-func, and is used to track the dependencies implied during the
59 function's evaluation.")
60
61 (defvar *pending-deps* nil
62 "A queue of deps pending recomputation. This is bound to a queue during
63 recomputation and restored afterwards, so it can also be used as a flag to
64 detect whether recomputation is happening.")
65
66 (defun kick-dep (dep)
67 "Call when DEP's value (or good/bad state) has changed. Marks the
68 dependents of DEP as :pending, if they're currently :stable, and then
69 clears the dependent list. Also invokes DEP's listener functions."
70 (dolist (d (dep-dependents dep))
71 (when (eq (dep-state d) :stable)
72 (enqueue d *pending-deps*)
73 (setf (dep-state d) :pending)))
74 (setf (dep-dependents dep) nil)
75 (dolist (l (dep-listeners dep))
76 (funcall l)))
77
78 (defun update-dep (dep value &optional (goodp t))
79 "Modify the value of DEP. If GOODP is t, then mark it as good and store
80 VALUE is its new value; otherwise mark it bad. If DEP's value is now
81 different (according to its value-predicate) then return true; otherwise
82 return false."
83 (setf (dep-state dep) :stable)
84 (cond ((not goodp)
85 (if (dep-goodp dep)
86 (progn (setf (dep-goodp dep) nil) t)
87 nil))
88 ((and (dep-goodp dep)
89 (funcall (dep-value-predicate dep) value (dep-%value dep)))
90 nil)
91 (t
92 (setf (dep-goodp dep) t
93 (dep-%value dep) value)
94 t)))
95
96 (defun recompute-dep (dep)
97 "Recompute the value of DEP. This function is careful to trap nonlocal
98 transfers from the value-func."
99 (let ((winning nil))
100 (unwind-protect
101 (catch 'dep-bad
102 (setf (dep-state dep) :recomputing)
103 (when (update-dep dep (let ((*evaluating-dep* dep))
104 (funcall (dep-value-func dep))))
105 (kick-dep dep))
106 (setf winning t))
107 (unless winning
108 (when (update-dep dep nil nil)
109 (kick-dep dep))))))
110
111 (defun recompute-deps ()
112 "Recompute all the pending deps, and any others that depend on them."
113 (unwind-protect
114 (loop (when (queue-emptyp *pending-deps*)
115 (return))
116 (let ((dep (dequeue *pending-deps*)))
117 (when (eq (dep-state dep) :pending)
118 (recompute-dep dep))))
119 (loop (when (queue-emptyp *pending-deps*)
120 (return))
121 (let ((d (dequeue *pending-deps*)))
122 (setf (dep-state d) :stable
123 (dep-goodp d) nil)))))
124
125 (defun ensure-dep-has-value (dep)
126 "Ensure that DEP has a stable value. If DEP is currently computing,
127 signals an error."
128 (ecase (dep-state dep)
129 (:stable)
130 (:pending
131 (recompute-dep dep))
132 (:recomputing
133 (error "Ouch! Cyclic dependency."))))
134
135 (defun pulse-dep (dep)
136 "Notifies DEP of a change in its value. If a recomputation phase is
137 currently under way, queue the dependents and leave fixing things up to
138 the outer loop; otherwise start up a recomputation phase."
139 (if *pending-deps*
140 (kick-dep dep)
141 (let ((*pending-deps* (make-queue)))
142 (kick-dep dep)
143 (recompute-deps))))
144
145 (defun (setf dep-value) (value dep)
146 "Set DEP's value to be VALUE (and mark it as being good)."
147 (when (dep-value-func dep)
148 (error "Not a leaf dep."))
149 (when (update-dep dep value)
150 (pulse-dep dep))
151 value)
152
153 (defun dep-make-bad (dep)
154 "Mark DEP as being bad."
155 (when (dep-value-func dep)
156 (error "Not a leaf dep."))
157 (when (update-dep dep nil nil)
158 (pulse-dep dep)))
159
160 (defun dep-add-listener (dep func)
161 "Add a listener function FUNC to the DEP. The FUNC is called each time the
162 DEP's value (or good/bad state) changes. It is called with no arguments,
163 and its return value is ignored."
164 (push func (dep-listeners dep)))
165
166 (defun dep-value (dep)
167 "Retrieve the current value from DEP."
168 (when *evaluating-dep*
169 (pushnew *evaluating-dep* (dep-dependents dep)))
170 (ensure-dep-has-value dep)
171 (if (dep-goodp dep) (dep-%value dep) (throw 'dep-bad nil)))
172
173 (defun make-dep (&rest args)
174 "Create a new DEP object. There are two basic argument forms:
175
176 (:leaf &optional OBJECT)
177 Return a leaf dep, whose value is OBJECT; if no OBJECT is given, the
178 dep is initially bad.
179
180 (:function FUNCTION)
181 Return a non-leaf dep whose value is computed by FUNCTION.
182
183 Additionally, if the first argument is something other than :leaf or
184 :function (ideally not a keyword, for forward compatibility), then the
185 first argument is inspected: if it's a function, then a function dep is
186 retuerned (as if you'd specified :function); otherwise a leaf dep is
187 returned.
188
189 If no arguments are given, a bad leaf dep is returned."
190
191 (flet ((arg (&optional (default nil defaultp))
192 (cond (args (pop args))
193 (defaultp default)
194 (t (error "Not enough arguments to MAKE-DEP.")))))
195
196 ;; Sort out the arguments.
197 (multiple-value-bind (type value goodp)
198 (if (null args)
199 (values :leaf nil nil)
200 (let ((indicator (pop args)))
201 (cond ((eq indicator :leaf)
202 (if args
203 (values :leaf (pop args) t)
204 (values :leaf nil nil)))
205 ((eq indicator :function)
206 (values :function (arg) nil))
207 ((functionp indicator)
208 (values :function indicator nil))
209 (t
210 (values :leaf indicator t)))))
211 (unless (endp args)
212 (error "Excess arguments to MAKE-DEP."))
213
214 ;; Create the object appropriately.
215 (case type
216 (:function
217 (let ((dep (%make-dep :value-func value :state :pending)))
218 (if *pending-deps*
219 (enqueue dep *pending-deps*)
220 (let ((*pending-deps* (make-queue)))
221 (enqueue dep *pending-deps*)
222 (recompute-deps)))
223 dep))
224 (:leaf
225 (%make-dep :%value value :goodp goodp :state :stable))))))
226
227 (defmacro dep-try (expr &body body)
228 "Evaluate EXPR. If it throws dep-bad then evaluate BODY instead."
229 (let ((block-name (gensym "TRY")))
230 `(block ,block-name
231 (catch 'dep-bad
232 (return-from ,block-name ,expr))
233 ,@body)))
234
235 (defun dep-bad ()
236 "Call from a value-func: indicates that the dep should marked as bad."
237 (throw 'dep-bad nil))
238
239 (defun delay-recomputing-deps* (thunk)
240 "The guts of the DELAY-RECOMPUTATING-DEPS macro. Evaluate THUNK without
241 immediately updating dependencies until THUNK finishes. Returns the
242 value(s) of THUNK."
243 (if *pending-deps*
244 (funcall thunk)
245 (let ((*pending-deps* (make-queue)))
246 (multiple-value-prog1
247 (funcall thunk)
248 (recompute-deps)))))
249
250 (defmacro delay-recomputing-deps (&body body)
251 "Evaluate BODY, but delay recomputing any deps until the BODY completes
252 execution.
253
254 Note that deps can report incorrect values while delayed recomputation is
255 in effect. In the current implementation, the direct dependents of a leaf
256 dep whose value has changed will be correctly marked as pending (and
257 recomputed as necessary); higher-level dependents won't be noticed until
258 the direct dependents are recomputed.
259
260 This form is intended to be used for bulk update to leaves, for which
261 purpose it is fairly safe."
262 `(delay-recomputating-deps* #'(lambda () ,@body)))
263
264 (defun install-dep-syntax (&optional (readtable *readtable*))
265 "Installs into the given READTABLE some syntactic shortcuts:
266
267 ?FORM -> (dep-value FORM)
268 Extract (or modify, for a leaf dep) the value of the dep indicated by
269 FORM.
270
271 #[FORM ...] -> (make-dep :funcion (lambda () FORM ...))
272 Return a derived dep whose value function computes the given FORMs
273 (as an implicit PROGN)
274
275 Returns the READTABLE."
276 (set-macro-character #\?
277 (lambda (stream char)
278 (declare (ignore char))
279 (list 'dep-value (read stream t nil t)))
280 readtable)
281 (set-syntax-from-char #\] #\) readtable readtable)
282 (set-dispatch-macro-character #\# #\[
283 (lambda (stream arg char)
284 (declare (ignore arg char))
285 `(make-dep :function
286 (lambda ()
287 ,@(read-delimited-list #\]
288 stream
289 t))))
290 readtable)
291 readtable)
292
293 (defmethod print-object ((dep dep) stream)
294 (print-unreadable-object (dep stream :type t :identity t)
295 (cond ((not (eq (dep-state dep) :stable))
296 (format stream "~S" (dep-state dep)))
297 ((dep-goodp dep)
298 (format stream "~S ~W" :good (dep-%value dep)))
299 (t
300 (format stream "~S" :bad)))))
301
302 #+ test
303 (progn
304 (defparameter x (make-leaf-dep 1))
305 (defparameter y (make-leaf-dep 2))
306 (defparameter z (make-dep (lambda () (+ (dep-value x) (dep-value y)))))
307 (defparameter w (make-dep (lambda () (* (dep-value x) (dep-value z)))))
308 (dep-add-listener x (lambda () (format t "x now ~A~%" x)))
309 (dep-add-listener z (lambda () (format t "z now ~A~%" z)))
310 (dep-add-listener w (lambda () (format t "w now ~A~%" w))))
311
312 ;;;----- That's all, folks --------------------------------------------------