3 ;;; Aggregating method combinations
5 ;;; (c) 2015 Straylight/Edgeware
8 ;;;----- Licensing notice ---------------------------------------------------
10 ;;; This file is part of the Sensble Object Design, an object system for C.
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.
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.
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.
28 ;;;--------------------------------------------------------------------------
29 ;;; Classes and protocol.
31 (export 'aggregating-message)
32 (defclass aggregating-message (simple-message)
33 ((combination :initarg :combination :type keyword
34 :reader message-combination)
35 (kernel-function :type function :reader message-kernel-function))
37 "Message class for aggregating method combinations.
39 An aggregating method combination invokes the primary methods in order,
40 most-specific first, collecting their return values, and combining them
41 together in some way to produce a result for the effective method as a
44 Mostly, this is done by initializing an accumulator to some appropriate
45 value, updating it with the result of each primary method in turn, and
46 finally returning some appropriate output function of it. The order is
47 determined by the `:most-specific' property, which may have the value
50 The `progn' method combination is implemented as a slightly weird special
51 case of an aggregating method combination with a trivial state. More
52 typical combinations are `:sum', `:product', `:min', `:max', `:and', and
53 `:or'. Finally, there's a `custom' combination which uses user-supplied
54 code fragments to stitch everything together."))
56 (export 'aggregating-message-properties)
57 (defgeneric aggregating-message-properties (message combination)
59 "Return a description of the properties needed by the method COMBINATION.
61 The description should be a plist of alternating property name and type
62 keywords. The named properties will be looked up in the pset supplied at
63 initialization time, and supplied to `compute-aggregating-message-kernel'
64 as keyword arguments. Defaults can be supplied in method BVLs.
66 The default is not to capture any property values.
68 The reason for this is as not to retain the pset beyond message object
70 (:method (message combination) nil))
72 (export 'compute-aggregating-message-kernel)
73 (defgeneric compute-aggregating-message-kernel
74 (message combination codegen target methods arg-names &key)
76 "Determine how to aggregate the direct methods for an aggregating message.
78 The return value is a function taking arguments (CODEGEN TARGET ARG-NAMES
79 METHODS): it should emit, to CODEGEN, an appropriate effective-method
80 kernel which invokes the listed direct METHODS, in the appropriate order,
81 collects and aggregates their values, and delivers to TARGET the final
82 result of the method kernel.
84 The easy way to implement this method is to use the macro
85 `define-aggregating-method-combination'."))
87 (export 'check-aggregating-message-type)
88 (defgeneric check-aggregating-message-type (message combination type)
90 "Check that TYPE is an acceptable function TYPE for the COMBINATION.
92 For example, `progn' messages must return `void', while `and' and `or'
93 messages must return `int'.")
94 (:method (message combination type)
97 (export 'standard-effective-method)
98 (defclass aggregating-effective-method (simple-effective-method) ()
99 (:documentation "Effective method counterpart to `aggregating-message'."))
101 ;;;--------------------------------------------------------------------------
104 (defmethod check-message-type ((message aggregating-message) type)
105 (with-slots (combination) message
106 (check-aggregating-message-type message combination type)))
108 (defmethod message-effective-method-class ((message aggregating-message))
109 'aggregating-effective-method)
111 (defmethod simple-method-body
112 ((method aggregating-effective-method) codegen target)
113 (let ((argument-names (effective-method-basic-argument-names method))
114 (primary-methods (effective-method-primary-methods method)))
115 (funcall (message-kernel-function (effective-method-message method))
116 codegen target argument-names primary-methods)))
118 (defmethod shared-initialize :before
119 ((message aggregating-message) slot-names &key pset)
120 (declare (ignore slot-names))
121 (with-slots (combination kernel-function) message
122 (let ((most-specific (get-property pset :most-specific :keyword :first))
123 (comb (get-property pset :combination :keyword)))
125 ;; Check that we've been given a method combination and make sure it
128 (error "The `combination' property is required."))
129 (unless (some (lambda (method)
130 (let* ((specs (method-specializers method))
131 (message-spec (car specs))
132 (combination-spec (cadr specs)))
133 (and (typep message-spec 'class)
134 (typep message message-spec)
135 (typep combination-spec 'eql-specializer)
136 (eq (eql-specializer-object combination-spec)
138 (generic-function-methods
139 #'compute-aggregating-message-kernel))
140 (error "Unknown method combination `~(~A~)'." comb))
141 (setf combination comb)
143 ;; Make sure the ordering is actually valid.
144 (unless (member most-specific '(:first :last))
145 (error "The `most_specific' property must be `first' or `last'."))
147 ;; Set up the function which will compute the kernel.
148 (let ((magic (cons nil nil))
151 ;; Collect the property values wanted by the method combination.
152 (do ((want (aggregating-message-properties message comb)
155 (let* ((name (car want))
157 (prop (get-property pset name type magic)))
158 (unless (eq prop magic)
159 (setf keys (list* name prop keys)))))
161 ;; Set the kernel function for later.
162 (setf kernel-function
163 (lambda (codegen target arg-names methods)
164 (apply #'compute-aggregating-message-kernel
169 (:last (setf methods (reverse methods))))
173 ;;;--------------------------------------------------------------------------
176 (export 'define-aggregating-method-combination)
177 (defmacro define-aggregating-method-combination
180 &key (codegen (gensym "CODEGEN-"))
181 (methods (gensym "METHODS-")))
183 ((:around around-func) '#'funcall)
184 ((:first-method first-method-func) nil firstp)
185 ((:methods methods-func) '#'funcall))
186 "Utility macro for definining aggregating method combinations.
188 The VARS are a list of variable names to be bound to temporary variable
189 objects of the method's return type. Additional keyword arguments define
190 variables names to be bound to other possibly interesting values:
192 * CODEGEN is the `codegen' object passed at effective-method computation
195 * METHODS is the list of primary methods, in the order in which they
196 should be invoked. Note that this list must be non-empty, since
197 otherwise the method on `compute-effective-method-body' specialized to
198 `simple-effective-method' will suppress the method entirely.
200 The PROPERTIES, if specified, are a list of properties to be collected
201 during message-object initialization; items in the list have the form
203 (([KEYWORD] NAME) TYPE [DEFAULT] [SUPPLIEDP])
205 similar to a `&key' BVL entry, except for the additional TYPE entry. In
206 particular, a symbolic NAME may be written in place of a singleton list.
207 The KEYWORD names the property as it should be looked up in the pset,
208 while the NAME names a variable to which the property value or default is
211 All of these variables, and the VARS, are available in the functions
214 The AROUND, FIRST-METHOD, and METHODS are function designators (probably
215 `lambda' forms) providing pieces of the aggregating behaviour.
217 The AROUND function is called first, with a single argument BODY, though
218 the variables above are also in scope. It is expected to emit code to
219 CODEGEN which invokes the METHODS in the appropriate order, and arranges
220 to store the aggregated return value in the first of the VARS.
222 It may call BODY as a function in order to assist with this; let ARGS be
223 the list of arguments supplied to it. The default behaviour is to call
224 BODY with no arguments. The BODY function first calls FIRST-METHOD,
225 passing it as arguments a function INVOKE and the ARGS which were passed
226 to BODY, and then calls METHODS once for each remaining method, again
227 passing an INVOKE function and the ARGS. If FIRST-METHOD is not
228 specified, then the METHODS function is used for all of the methods. If
229 METHODS is not specified, then the behaviour is simply to call INVOKE
230 immediately. (See the definition of the `:progn' method combination.)
232 Calling (funcall INVOKE [TARGET]) emits instructions to CODEGEN to call
233 the appropriate direct method and deliver its return value to TARGET,
234 which defaults to `:void'."
236 (with-gensyms (type msg combvar target arg-names args
237 meth targ func call-methfunc
238 aroundfunc fmethfunc methfunc)
241 ;; If properties are listed, arrange for them to be collected.
243 `((defmethod aggregating-message-properties
244 ((,msg aggregating-message) (,combvar (eql ',comb)))
245 ',(mapcan (lambda (prop)
246 (list (let* ((name (car prop))
247 (names (if (listp name) name
249 (if (cddr names) (car names)
250 (intern (car names) :keyword)))
254 ;; Define the main kernel-compuation method.
255 (defmethod compute-aggregating-message-kernel
256 ((,msg aggregating-message) (,combvar (eql ',comb))
257 ,codegen ,target ,methods ,arg-names
258 &key ,@(mapcar (lambda (prop) (cons (car prop) (cddr prop)))
260 (declare (ignore ,combvar))
262 ;; Declare the necessary variables and give names to the functions
263 ;; supplied by the caller.
265 `((,type (c-type-subtype (sod-message-type ,msg)))))
266 ,@(mapcar (lambda (var)
267 (list var `(temporary-var ,codegen ,type)))
269 (,aroundfunc ,around-func)
270 (,methfunc ,methods-func)
271 (,fmethfunc ,(if firstp first-method-func methfunc)))
273 ;; Arrange to release the temporaries when we're finished with
278 ;; Wrap the AROUND function around most of the work.
280 (lambda (&rest ,args)
281 (flet ((,call-methfunc (,func ,meth)
282 ;; Call FUNC, passing it an INVOKE
283 ;; function which will generate a call
287 (&optional (,targ :void))
288 (invoke-method ,codegen
294 ;; The first method might need special
296 (,call-methfunc ,fmethfunc (car ,methods))
298 ;; Call the remaining methods in the right
300 (dolist (,meth (cdr ,methods))
301 (,call-methfunc ,methfunc ,meth)))))
303 ;; Outside the AROUND function now, deliver the final
304 ;; result to the right place.
305 (deliver-expr ,codegen ,target ,(car vars)))
307 ;; Finally, release the temporary variables.
308 ,@(mapcar (lambda (var) `(setf (var-in-use-p ,var) nil))
313 ;;;--------------------------------------------------------------------------
314 ;;; Fixed aggregating method combinations.
316 (flet ((check (comb want type)
317 (unless (eq (c-type-subtype type) want)
318 (error "Messages with `~A' combination must return `~A'."
319 (string-downcase comb) want))))
320 (defmethod check-aggregating-message-type
321 ((message aggregating-message)
322 (combination (eql :progn))
323 (type c-function-type))
324 (check combination c-type-void type)
326 (defmethod check-aggregating-message-type
327 ((message aggregating-message)
328 (combination (eql :and))
329 (type c-function-type))
330 (check combination c-type-int type)
332 (defmethod check-aggregating-message-type
333 ((message aggregating-message)
334 (combination (eql :or))
335 (type c-function-type))
336 (check combination c-type-int type)
339 (define-aggregating-method-combination :progn (nil))
341 (define-aggregating-method-combination :sum ((acc val) :codegen codegen)
342 :first-method (lambda (invoke)
344 (emit-inst codegen (make-set-inst acc val)))
345 :methods (lambda (invoke)
347 (emit-inst codegen (make-update-inst acc #\+ val))))
349 (define-aggregating-method-combination :product ((acc val) :codegen codegen)
350 :first-method (lambda (invoke)
352 (emit-inst codegen (make-set-inst acc val)))
353 :methods (lambda (invoke)
355 (emit-inst codegen (make-update-inst acc #\* val))))
357 (define-aggregating-method-combination :min ((acc val) :codegen codegen)
358 :first-method (lambda (invoke)
360 (emit-inst codegen (make-set-inst acc val)))
361 :methods (lambda (invoke)
363 (emit-inst codegen (make-if-inst (format nil "~A > ~A" acc val)
364 (make-set-inst acc val) nil))))
366 (define-aggregating-method-combination :max ((acc val) :codegen codegen)
367 :first-method (lambda (invoke)
369 (emit-inst codegen (make-set-inst acc val)))
370 :methods (lambda (invoke)
372 (emit-inst codegen (make-if-inst (format nil "~A < ~A" acc val)
373 (make-set-inst acc val) nil))))
375 (define-aggregating-method-combination :and ((ret val) :codegen codegen)
376 :around (lambda (body)
377 (codegen-push codegen)
378 (deliver-expr codegen ret 0)
380 (deliver-expr codegen ret 1)
382 (make-do-while-inst (codegen-pop-block codegen) 0)))
383 :methods (lambda (invoke)
385 (emit-inst codegen (make-if-inst (format nil "!~A" val)
386 (make-break-inst) nil))))
388 (define-aggregating-method-combination :or ((ret val) :codegen codegen)
389 :around (lambda (body)
390 (codegen-push codegen)
391 (deliver-expr codegen ret 1)
393 (deliver-expr codegen ret 0)
395 (make-do-while-inst (codegen-pop-block codegen) 0)))
396 :methods (lambda (invoke)
398 (emit-inst codegen (make-if-inst val (make-break-inst) nil))))
400 ;;;--------------------------------------------------------------------------
401 ;;; A customizable aggregating method combination.
403 (defmethod aggregating-message-properties
404 ((message aggregating-message) (combination (eql :custom)))
413 (defmethod compute-aggregating-message-kernel
414 ((message aggregating-message) (combination (eql :custom))
415 codegen target methods arg-names
416 &key (retvar "sod_ret") (valvar "sod_val")
417 decls before each (first each) after)
418 (let* ((type (c-type-subtype (sod-message-type message)))
419 (not-void-p (not (eq type c-type-void))))
421 (ensure-var codegen retvar type)
422 (ensure-var codegen valvar type))
424 (emit-decl codegen decls))
425 (labels ((maybe-emit (fragment)
426 (when fragment (emit-inst codegen fragment)))
427 (invoke (method fragment)
428 (invoke-method codegen (if not-void-p valvar :void)
430 (maybe-emit fragment)))
432 (invoke (car methods) first)
433 (dolist (method (cdr methods)) (invoke method each))
435 (deliver-expr codegen target retvar))))
437 ;;;----- That's all, folks --------------------------------------------------