chiark / gitweb /
src/method-aggregate.lisp: Store keyword list as a plist on the message.
[sod] / src / method-aggregate.lisp
CommitLineData
e75eb63d
MW
1;;; -*-lisp-*-
2;;;
3;;; Aggregating method combinations
4;;;
5;;; (c) 2015 Straylight/Edgeware
6;;;
7
8;;;----- Licensing notice ---------------------------------------------------
9;;;
e0808c47 10;;; This file is part of the Sensible Object Design, an object system for C.
e75eb63d
MW
11;;;
12;;; SOD is free software; you can redistribute it and/or modify
13;;; it under the terms of the GNU General Public License as published by
14;;; the Free Software Foundation; either version 2 of the License, or
15;;; (at your option) any later version.
16;;;
17;;; SOD is distributed in the hope that it will be useful,
18;;; but WITHOUT ANY WARRANTY; without even the implied warranty of
19;;; MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
20;;; GNU General Public License for more details.
21;;;
22;;; You should have received a copy of the GNU General Public License
23;;; along with SOD; if not, write to the Free Software Foundation,
24;;; Inc., 59 Temple Place - Suite 330, Boston, MA 02111-1307, USA.
25
26(cl:in-package #:sod)
27
28;;;--------------------------------------------------------------------------
29;;; Classes and protocol.
30
7f2917d2
MW
31(export '(aggregating-message
32 sod-message-combination sod-message-kernel-function))
e75eb63d
MW
33(defclass aggregating-message (simple-message)
34 ((combination :initarg :combination :type keyword
7f2917d2 35 :reader sod-message-combination)
88e0b18b 36 (plist :type list :accessor sod-message-plist)
7f2917d2 37 (kernel-function :type function :reader sod-message-kernel-function))
e75eb63d
MW
38 (:documentation
39 "Message class for aggregating method combinations.
40
41 An aggregating method combination invokes the primary methods in order,
42 most-specific first, collecting their return values, and combining them
43 together in some way to produce a result for the effective method as a
44 whole.
45
46 Mostly, this is done by initializing an accumulator to some appropriate
47 value, updating it with the result of each primary method in turn, and
48 finally returning some appropriate output function of it. The order is
49 determined by the `:most-specific' property, which may have the value
50 `:first' or `:last'.
51
52 The `progn' method combination is implemented as a slightly weird special
53 case of an aggregating method combination with a trivial state. More
54 typical combinations are `:sum', `:product', `:min', `:max', `:and', and
55 `:or'. Finally, there's a `custom' combination which uses user-supplied
56 code fragments to stitch everything together."))
57
58(export 'aggregating-message-properties)
59(defgeneric aggregating-message-properties (message combination)
60 (:documentation
61 "Return a description of the properties needed by the method COMBINATION.
62
63 The description should be a plist of alternating property name and type
64 keywords. The named properties will be looked up in the pset supplied at
65 initialization time, and supplied to `compute-aggregating-message-kernel'
66 as keyword arguments. Defaults can be supplied in method BVLs.
67
68 The default is not to capture any property values.
69
70 The reason for this is as not to retain the pset beyond message object
71 initialization.")
72 (:method (message combination) nil))
73
74(export 'compute-aggregating-message-kernel)
75(defgeneric compute-aggregating-message-kernel
76 (message combination codegen target methods arg-names &key)
77 (:documentation
78 "Determine how to aggregate the direct methods for an aggregating message.
79
80 The return value is a function taking arguments (CODEGEN TARGET ARG-NAMES
81 METHODS): it should emit, to CODEGEN, an appropriate effective-method
82 kernel which invokes the listed direct METHODS, in the appropriate order,
83 collects and aggregates their values, and delivers to TARGET the final
84 result of the method kernel.
85
86 The easy way to implement this method is to use the macro
87 `define-aggregating-method-combination'."))
88
89(export 'check-aggregating-message-type)
90(defgeneric check-aggregating-message-type (message combination type)
91 (:documentation
92 "Check that TYPE is an acceptable function TYPE for the COMBINATION.
93
94 For example, `progn' messages must return `void', while `and' and `or'
95 messages must return `int'.")
96 (:method (message combination type)
97 t))
98
d7887906 99(export 'aggregating-effective-method)
e75eb63d
MW
100(defclass aggregating-effective-method (simple-effective-method) ()
101 (:documentation "Effective method counterpart to `aggregating-message'."))
102
103;;;--------------------------------------------------------------------------
104;;; Implementation.
105
106(defmethod check-message-type ((message aggregating-message) type)
107 (with-slots (combination) message
108 (check-aggregating-message-type message combination type)))
109
7f2917d2 110(defmethod sod-message-effective-method-class ((message aggregating-message))
e75eb63d
MW
111 'aggregating-effective-method)
112
113(defmethod simple-method-body
114 ((method aggregating-effective-method) codegen target)
115 (let ((argument-names (effective-method-basic-argument-names method))
116 (primary-methods (effective-method-primary-methods method)))
7f2917d2 117 (funcall (sod-message-kernel-function (effective-method-message method))
e75eb63d
MW
118 codegen target argument-names primary-methods)))
119
120(defmethod shared-initialize :before
121 ((message aggregating-message) slot-names &key pset)
122 (declare (ignore slot-names))
88e0b18b 123 (with-slots (combination plist kernel-function) message
e75eb63d
MW
124 (let ((most-specific (get-property pset :most-specific :keyword :first))
125 (comb (get-property pset :combination :keyword)))
126
127 ;; Check that we've been given a method combination and make sure it
128 ;; actually exists.
129 (unless comb
130 (error "The `combination' property is required."))
131 (unless (some (lambda (method)
132 (let* ((specs (method-specializers method))
133 (message-spec (car specs))
134 (combination-spec (cadr specs)))
135 (and (typep message-spec 'class)
136 (typep message message-spec)
137 (typep combination-spec 'eql-specializer)
138 (eq (eql-specializer-object combination-spec)
139 comb))))
140 (generic-function-methods
141 #'compute-aggregating-message-kernel))
142 (error "Unknown method combination `~(~A~)'." comb))
143 (setf combination comb)
144
145 ;; Make sure the ordering is actually valid.
146 (unless (member most-specific '(:first :last))
147 (error "The `most_specific' property must be `first' or `last'."))
148
149 ;; Set up the function which will compute the kernel.
150 (let ((magic (cons nil nil))
151 (keys nil))
152
153 ;; Collect the property values wanted by the method combination.
154 (do ((want (aggregating-message-properties message comb)
155 (cddr want)))
156 ((endp want))
157 (let* ((name (car want))
158 (type (cadr want))
159 (prop (get-property pset name type magic)))
160 (unless (eq prop magic)
161 (setf keys (list* name prop keys)))))
88e0b18b 162 (setf plist keys)
e75eb63d
MW
163
164 ;; Set the kernel function for later.
165 (setf kernel-function
166 (lambda (codegen target arg-names methods)
167 (apply #'compute-aggregating-message-kernel
168 message comb
169 codegen target
170 (ecase most-specific
171 (:first methods)
172 (:last (setf methods (reverse methods))))
173 arg-names
88e0b18b 174 plist)))))))
e75eb63d
MW
175
176;;;--------------------------------------------------------------------------
177;;; Utilities.
178
179(export 'define-aggregating-method-combination)
180(defmacro define-aggregating-method-combination
181 (comb
182 (vars
183 &key (codegen (gensym "CODEGEN-"))
184 (methods (gensym "METHODS-")))
7b78999c 185 &key properties return-type
e75eb63d
MW
186 ((:around around-func) '#'funcall)
187 ((:first-method first-method-func) nil firstp)
188 ((:methods methods-func) '#'funcall))
189 "Utility macro for definining aggregating method combinations.
190
191 The VARS are a list of variable names to be bound to temporary variable
192 objects of the method's return type. Additional keyword arguments define
193 variables names to be bound to other possibly interesting values:
194
195 * CODEGEN is the `codegen' object passed at effective-method computation
196 time; and
197
198 * METHODS is the list of primary methods, in the order in which they
199 should be invoked. Note that this list must be non-empty, since
200 otherwise the method on `compute-effective-method-body' specialized to
201 `simple-effective-method' will suppress the method entirely.
202
203 The PROPERTIES, if specified, are a list of properties to be collected
204 during message-object initialization; items in the list have the form
205
206 (([KEYWORD] NAME) TYPE [DEFAULT] [SUPPLIEDP])
207
208 similar to a `&key' BVL entry, except for the additional TYPE entry. In
209 particular, a symbolic NAME may be written in place of a singleton list.
210 The KEYWORD names the property as it should be looked up in the pset,
211 while the NAME names a variable to which the property value or default is
212 bound.
213
214 All of these variables, and the VARS, are available in the functions
215 described below.
216
7b78999c
MW
217 If a RETURN-TYPE is given, it's a C-type S-expression: a method is defined
218 on `check-aggregating-message-type' to check the that the message's return
219 type matches RETURN-TYPE.
220
e75eb63d
MW
221 The AROUND, FIRST-METHOD, and METHODS are function designators (probably
222 `lambda' forms) providing pieces of the aggregating behaviour.
223
224 The AROUND function is called first, with a single argument BODY, though
225 the variables above are also in scope. It is expected to emit code to
226 CODEGEN which invokes the METHODS in the appropriate order, and arranges
227 to store the aggregated return value in the first of the VARS.
228
229 It may call BODY as a function in order to assist with this; let ARGS be
230 the list of arguments supplied to it. The default behaviour is to call
231 BODY with no arguments. The BODY function first calls FIRST-METHOD,
232 passing it as arguments a function INVOKE and the ARGS which were passed
233 to BODY, and then calls METHODS once for each remaining method, again
234 passing an INVOKE function and the ARGS. If FIRST-METHOD is not
235 specified, then the METHODS function is used for all of the methods. If
236 METHODS is not specified, then the behaviour is simply to call INVOKE
237 immediately. (See the definition of the `:progn' method combination.)
238
239 Calling (funcall INVOKE [TARGET]) emits instructions to CODEGEN to call
240 the appropriate direct method and deliver its return value to TARGET,
241 which defaults to `:void'."
242
7b78999c 243 (with-gensyms (type msg combvar target arg-names args want-type
e75eb63d
MW
244 meth targ func call-methfunc
245 aroundfunc fmethfunc methfunc)
246 `(progn
247
248 ;; If properties are listed, arrange for them to be collected.
249 ,@(and properties
250 `((defmethod aggregating-message-properties
251 ((,msg aggregating-message) (,combvar (eql ',comb)))
252 ',(mapcan (lambda (prop)
253 (list (let* ((name (car prop))
254 (names (if (listp name) name
255 (list name))))
256 (if (cddr names) (car names)
257 (intern (car names) :keyword)))
258 (cadr prop)))
259 properties))))
260
7b78999c
MW
261 ;; If a particular return type is wanted, check that.
262 ,@(and return-type
263 `((defmethod check-aggregating-message-type
264 ((,msg aggregating-message)
265 (,combvar (eql ',comb))
266 (,type c-function-type))
267 (let ((,want-type (c-type ,return-type)))
268 (unless (c-type-equal-p (c-type-subtype ,type)
269 ,want-type)
270 (error "Messages with `~(~A~)' combination ~
271 must return `~A'."
272 ,combvar ,want-type)))
273 (call-next-method))))
274
e75eb63d
MW
275 ;; Define the main kernel-compuation method.
276 (defmethod compute-aggregating-message-kernel
277 ((,msg aggregating-message) (,combvar (eql ',comb))
278 ,codegen ,target ,methods ,arg-names
279 &key ,@(mapcar (lambda (prop) (cons (car prop) (cddr prop)))
280 properties))
281 (declare (ignore ,combvar))
282
283 ;; Declare the necessary variables and give names to the functions
284 ;; supplied by the caller.
285 (let* (,@(and vars
286 `((,type (c-type-subtype (sod-message-type ,msg)))))
287 ,@(mapcar (lambda (var)
288 (list var `(temporary-var ,codegen ,type)))
289 vars)
290 (,aroundfunc ,around-func)
291 (,methfunc ,methods-func)
292 (,fmethfunc ,(if firstp first-method-func methfunc)))
293
294 ;; Arrange to release the temporaries when we're finished with
295 ;; them.
296 (unwind-protect
297 (progn
298
299 ;; Wrap the AROUND function around most of the work.
300 (funcall ,aroundfunc
301 (lambda (&rest ,args)
302 (flet ((,call-methfunc (,func ,meth)
303 ;; Call FUNC, passing it an INVOKE
304 ;; function which will generate a call
305 ;; to METH.
306 (apply ,func
307 (lambda
308 (&optional (,targ :void))
309 (invoke-method ,codegen
310 ,targ
311 ,arg-names
312 ,meth))
313 ,args)))
314
315 ;; The first method might need special
316 ;; handling.
317 (,call-methfunc ,fmethfunc (car ,methods))
318
319 ;; Call the remaining methods in the right
320 ;; order.
321 (dolist (,meth (cdr ,methods))
322 (,call-methfunc ,methfunc ,meth)))))
323
324 ;; Outside the AROUND function now, deliver the final
325 ;; result to the right place.
326 (deliver-expr ,codegen ,target ,(car vars)))
327
328 ;; Finally, release the temporary variables.
329 ,@(mapcar (lambda (var) `(setf (var-in-use-p ,var) nil))
330 vars))))
331
332 ',comb)))
333
334;;;--------------------------------------------------------------------------
335;;; Fixed aggregating method combinations.
336
7b78999c
MW
337(define-aggregating-method-combination :progn (nil)
338 :return-type void)
e75eb63d
MW
339
340(define-aggregating-method-combination :sum ((acc val) :codegen codegen)
341 :first-method (lambda (invoke)
342 (funcall invoke val)
343 (emit-inst codegen (make-set-inst acc val)))
344 :methods (lambda (invoke)
345 (funcall invoke val)
346 (emit-inst codegen (make-update-inst acc #\+ val))))
347
348(define-aggregating-method-combination :product ((acc val) :codegen codegen)
349 :first-method (lambda (invoke)
350 (funcall invoke val)
351 (emit-inst codegen (make-set-inst acc val)))
352 :methods (lambda (invoke)
353 (funcall invoke val)
354 (emit-inst codegen (make-update-inst acc #\* val))))
355
356(define-aggregating-method-combination :min ((acc val) :codegen codegen)
357 :first-method (lambda (invoke)
358 (funcall invoke val)
359 (emit-inst codegen (make-set-inst acc val)))
360 :methods (lambda (invoke)
361 (funcall invoke val)
362 (emit-inst codegen (make-if-inst (format nil "~A > ~A" acc val)
363 (make-set-inst acc val) nil))))
364
365(define-aggregating-method-combination :max ((acc val) :codegen codegen)
366 :first-method (lambda (invoke)
367 (funcall invoke val)
368 (emit-inst codegen (make-set-inst acc val)))
369 :methods (lambda (invoke)
370 (funcall invoke val)
371 (emit-inst codegen (make-if-inst (format nil "~A < ~A" acc val)
372 (make-set-inst acc val) nil))))
373
374(define-aggregating-method-combination :and ((ret val) :codegen codegen)
7b78999c 375 :return-type int
e75eb63d
MW
376 :around (lambda (body)
377 (codegen-push codegen)
378 (deliver-expr codegen ret 0)
379 (funcall body)
380 (deliver-expr codegen ret 1)
381 (emit-inst codegen
382 (make-do-while-inst (codegen-pop-block codegen) 0)))
383 :methods (lambda (invoke)
384 (funcall invoke val)
385 (emit-inst codegen (make-if-inst (format nil "!~A" val)
386 (make-break-inst) nil))))
387
388(define-aggregating-method-combination :or ((ret val) :codegen codegen)
7b78999c 389 :return-type int
e75eb63d
MW
390 :around (lambda (body)
391 (codegen-push codegen)
392 (deliver-expr codegen ret 1)
393 (funcall body)
394 (deliver-expr codegen ret 0)
395 (emit-inst codegen
396 (make-do-while-inst (codegen-pop-block codegen) 0)))
397 :methods (lambda (invoke)
398 (funcall invoke val)
399 (emit-inst codegen (make-if-inst val (make-break-inst) nil))))
400
401;;;--------------------------------------------------------------------------
402;;; A customizable aggregating method combination.
403
404(defmethod aggregating-message-properties
405 ((message aggregating-message) (combination (eql :custom)))
406 '(:retvar :id
407 :valvar :id
408 :decls :fragment
409 :before :fragment
410 :first :fragment
411 :each :fragment
05170d7a
MW
412 :after :fragment
413 :count :id))
e75eb63d
MW
414
415(defmethod compute-aggregating-message-kernel
416 ((message aggregating-message) (combination (eql :custom))
417 codegen target methods arg-names
418 &key (retvar "sod_ret") (valvar "sod_val")
05170d7a 419 decls before each (first each) after count)
e75eb63d
MW
420 (let* ((type (c-type-subtype (sod-message-type message)))
421 (not-void-p (not (eq type c-type-void))))
422 (when not-void-p
423 (ensure-var codegen retvar type)
424 (ensure-var codegen valvar type))
05170d7a 425 (when count
d84f7ee7 426 (ensure-var codegen count c-type-size-t (length methods)))
e75eb63d
MW
427 (when decls
428 (emit-decl codegen decls))
429 (labels ((maybe-emit (fragment)
430 (when fragment (emit-inst codegen fragment)))
431 (invoke (method fragment)
432 (invoke-method codegen (if not-void-p valvar :void)
433 arg-names method)
434 (maybe-emit fragment)))
435 (maybe-emit before)
436 (invoke (car methods) first)
437 (dolist (method (cdr methods)) (invoke method each))
438 (maybe-emit after)
439 (deliver-expr codegen target retvar))))
440
441;;;----- That's all, folks --------------------------------------------------