Christophe Weblog Wiki Code Publications Music
figures
[paper-els-specializers.git] / els-specializers.org
index a5534c4121d183f34388560331d00f85e0ed072f..74b26499fd74b009089f55494e846e088aef30f5 100644 (file)
@@ -32,6 +32,8 @@
   \\affaddr{Vilhonkatu 5 A}\\\\
   \\affaddr{FI-00100 Helsinki}\\\\
   \\email{david@lichteblau.com}
+}
+\\maketitle")
 #+end_src
 
 #+begin_abstract
@@ -53,7 +55,7 @@ efficient.
 
 #+begin_LaTeX
 \category{D.1}{Software}{Programming Techniques}[Object-oriented Programming]
-\category{D.3.3}{Programming Languages}{Language Constructs and Features} 
+\category{D.3.3}{Programming Languages}{Language Constructs and Features}
 \terms{Languages, Design}
 \keywords{generic functions, specialization-oriented programming, method selection, method combination}
 #+end_LaTeX
@@ -79,6 +81,11 @@ efficient.
   incorporating substantial fractions of the Metaobject Protocol as
   described.
 
+  #+CAPTION:    MOP Design Space
+  #+LABEL:      fig:mopdesign
+  #+ATTR_LATEX: width=\linewidth float
+  [[file:figures/mop-design-space.pdf]]
+
   Although it has stood the test of time, the CLOS MOP is neither
   without issues (e.g. semantic problems with =make-method-lambda=
   \cite{Costanza.Herzeel:2008}; useful functions such as
@@ -87,22 +94,24 @@ efficient.
   implement all conceivable variations of object-oriented behaviour.
   While metaprogramming offers some possibilities for customization of
   the object system behaviour, those possibilities cannot extend
-  arbitrarily in all directions.  There is still an expectation that
-  functionality is implemented with methods on generic functions,
-  acting on objects with slots.  Nevertheless, the MOP is flexible,
-  and is used for a number of things, including: documentation
-  generation (where introspective functionality in the MOP is used to
-  extract information from a running system); object-relational
-  mapping and other approaches to object persistence; alternative
-  backing stores for slots (hash-tables or symbols); and programmatic
-  construction of metaobjects, for example for IDL compilers and model
-  transformations.
-
-  [ XXX: A picture on MOP flexibility here would be good; I have in my mind
-  one where an object system is a point and the MOP opens up a blob
-  around that point, and I'm sure I've seen it somewhere but I can't
-  remember where.  Alternatively, there's Kiczales et al "MOPs: why we
-  want them and what else they can do", fig. 2 ]
+  arbitrarily in all directions (conceptually, if a given object
+  system is a point in design space, then a MOP for that object system
+  allows exploration of a region of design space around that point;
+  see figure \ref{fig:mopdesign}).  In the case of the CLOS MOP, there is
+  still an expectation that functionality is implemented with methods
+  on generic functions, acting on objects with slots; it is not
+  possible, for example, to transparently implement support for
+  “message not understood” as in the message-passing paradigm, because
+  the analogue of messages (generic functions) need to be defined
+  before they are used.
+
+  Nevertheless, the MOP is flexible, and is used for a number of
+  things, including: documentation generation (where introspection in
+  the MOP is used to extract information from a running system);
+  object-relational mapping and other approaches to object
+  persistence; alternative backing stores for slots (hash-tables or
+  symbols); and programmatic construction of metaobjects, for example
+  for IDL compilers and model transformations.
 
   One area of functionality where there is scope for customization by
   the metaprogrammer is in the mechanics and semantics of method
@@ -121,10 +130,10 @@ efficient.
   there are no restrictions on the metaprogrammer constructing
   additional subclasses.  Previous work \cite{Newton.Rhodes:2008} has
   explored the potential for customizing generic function dispatch
-  using extended specializers, but as of that work the metaprogrammer
-  must override the entirety of the generic function invocation
-  protocol (from =compute-discriminating-function= on down), leading
-  to toy implementations and duplicated effort.
+  using extended specializers, but there the metaprogrammer must
+  override the entirety of the generic function invocation protocol
+  (from =compute-discriminating-function= on down), leading to toy
+  implementations and duplicated effort.
 
   This paper introduces a protocol for efficient and controlled
   handling of new subclasses of =specializer=.  In particular, it
@@ -136,8 +145,8 @@ efficient.
 
   #+CAPTION:    Dispatch Comparison
   #+LABEL:      fig:dispatch
-  #+ATTR_LATEX: width=0.9\linewidth float
-  [[file:figures/dispatch-comparison.pdf]]
+  #+ATTR_LATEX: width=\linewidth float
+  [[file:figures/dispatch-relationships.pdf]]
 
   The remaining sections in this paper can be read in any order.  We
   give some motivating examples in section [[#Examples]], including
@@ -159,9 +168,10 @@ efficient.
   implemented using our protocol, which we describe in section
   [[#Protocol]].  For reasons of space, the metaprogram code examples in
   this section do not include some of the necessary support code to
-  run; complete implementations of each of these cases are included in
-  an appendix / in the accompanying repository snapshot / at this
-  location.
+  run; complete implementations of each of these cases, along with the
+  integration of this protocol into the SBCL implementation
+  \cite{Rhodes:2008} of Common Lisp, are included in an appendix / in
+  the accompanying repository snapshot / at this location.
 
   A note on terminology: we will attempt to distinguish between the
   user of an individual case of generalized dispatch (the
@@ -173,28 +183,31 @@ efficient.
    :PROPERTIES:
    :CUSTOM_ID: Cons
    :END:
-   We start by presenting our original use case, performing
-   dispatching on the first element of lists.  Semantically, we allow
-   the programmer to specialize any argument of methods with a new
-   kind of specializer, =cons-specializer=, which is applicable if and
-   only if the corresponding object is a =cons= whose =car= is =eql=
-   to the symbol associated with the =cons-specializer=; these
-   specializers are more specific than the =cons= class, but less
-   specific than an =eql-specializer= on any given =cons=.
-
-   One motivation for the use of this specializer is in an extensible
-   code walker: a new special form can be handled simply by writing an
-   additional method on the walking generic function, seamlessly
-   interoperating with all existing methods.
+   One motivation for the use of generalized dispatch is in an
+   extensible code walker: a new special form can be handled simply by
+   writing an additional method on the walking generic function,
+   seamlessly interoperating with all existing methods. In this
+   use-case, dispatch is performed on the first element of lists.
+   Semantically, we allow the programmer to specialize any argument of
+   methods with a new kind of specializer, =cons-specializer=, which
+   is applicable if and only if the corresponding object is a =cons=
+   whose =car= is =eql= to the symbol associated with the
+   =cons-specializer=; these specializers are more specific than the
+   =cons= class, but less specific than an =eql-specializer= on any
+   given =cons=.
+
    The programmer code using these specializers is unchanged from
    \cite{Newton.Rhodes:2008}; the benefits of the protocol described
-   here are centered on performance and generality: in an application
-   such as walking source code, we would expect to encounter special
-   forms (distinguished by particular atoms in the =car= position)
-   multiple times, and hence to dispatch to the same effective method
-   repeatedly.  We discuss this in more detail in section [[#Memoization]];
-   we present the metaprogrammer code below.
+   here are: that the separation of concerns is complete – method
+   selection is independent of method combination – and that the
+   protocol allows for efficient implementation where possible, even
+   when method selection is customized.  In an application such as
+   walking source code, we would expect to encounter special forms
+   (distinguished by particular atoms in the =car= position) multiple
+   times, and hence to dispatch to the same effective method
+   repeatedly.  We discuss the efficiency aspects of the protocol in
+   more detail in section [[#Memoization]]; we present the metaprogrammer
+   code to implement the =cons-specializer= below.
 
 #+begin_src lisp
 (defclass cons-specializer (specializer)
@@ -224,57 +237,62 @@ efficient.
   (and (consp o) (eql (car o) (%car s))))
 #+end_src
 
-The code above shows the core of the use of our protocol.  We have
-elided some support code for parsing and unparsing specializers, and
-for handling introspective functions such as finding generic functions
-for a given specializer.  We have also elided methods on the protocol
-function =specializer<=; for =cons-specializers= here, specializer
-ordering is trivial, as only one =cons-specializer= can ever be
-applicable to any given argument.  See section [[#Accept]] for a case
-where specializer ordering is substantially different.
-
-As in \cite{Newton.Rhodes:2008}, we can use these specializers to
-implement a modular code walker, where we define one method per
-special operator.  We show two of those methods below, in the context
-of a walker which checks for unused bindings and uses of unbound
-variables.
+The code above shows a minimal use of our protocol.  We have elided
+some support code for parsing and unparsing specializers, and for
+handling introspective functions such as finding generic functions for
+a given specializer.  We have also elided methods on the protocol
+functions =specializer<= and =same-specializer-p=; for
+=cons-specializer= objects, specializer ordering is trivial, as only
+one =cons-specializer= (up to equality) can ever be applicable to any
+given argument.  See section [[#Accept]] for a case where specializer
+ordering is non-trivial.
+
+As in \cite{Newton.Rhodes:2008}, the programmer can use these
+specializers to implement a modular code walker, where they define one
+method per special operator.  We show two of those methods below, in
+the context of a walker which checks for unused bindings and uses of
+unbound variables.
 
 #+begin_src
 (defgeneric walk (form env stack)
   (:generic-function-class cons-generic-function))
-(defmethod walk ((expr (cons lambda)) env call-stack)
+(defmethod walk
+    ((expr (cons lambda)) env call-stack)
   (let ((lambda-list (cadr expr))
         (body (cddr expr)))
     (with-checked-bindings
-        ((bindings-from-ll lambda-list) env call-stack)
+        ((bindings-from-ll lambda-list)
+         env call-stack)
       (dolist (form body)
         (walk form env (cons form call-stack))))))
-(defmethod walk ((expr (cons let)) env call-stack)
+(defmethod walk
+    ((expr (cons let)) env call-stack)
   (flet ((let-binding (x)
-           (walk (cadr x) env (cons (cadr x) call-stack))
-           (cons (car x) (make-instance 'binding))))
+           (walk (cadr x) env
+                 (cons (cadr x) call-stack))
+           (cons (car x)
+                 (make-instance 'binding))))
     (with-checked-bindings
-        ((mapcar #'let-binding (cadr expr)) env call-stack)
+        ((mapcar #'let-binding (cadr expr))
+          env call-stack)
       (dolist (form (cddr expr))
         (walk form env (cons form call-stack))))))
 #+end_src
 
    Note that in this example there is no strict need for
-   =cons-specializer= and =cons-generalizer= to be distinct classes –
-   just as in the normal protocol involving
-   =compute-applicable-methods= and
-   =compute-applicable-methods-using-classes=, the specializer object
-   for mediating dispatch contains the same information as the object
-   representing the equivalence class of objects to which that
-   specializer is applicable: here it is the =car= of the =cons=
-   (which we wrap in a distinct object); in the standard dispatch it
-   is the =class= of the object.  This feature also characterizes
-   those use cases where the metaprogrammer could straightforwardly
-   use filtered dispatch \cite{Costanza.etal:2008} to implement their
-   dispatch semantics.  We will see in section [[#Accept]] an example
-   of a case where filtered dispatch is incapable of straightforwardly
-   expressing the dispatch, but first we present our implementation of
-   the motivating case from \cite{Costanza.etal:2008}.
+   =cons-specializer= and =cons-generalizer= to be distinct classes.
+   In standard generic function dispatch, the =class= functions both
+   as the specializer for methods and as the generalizer for generic
+   function arguments; we can think of the dispatch implemented by
+   =cons-specializer= objects as providing for subclasses of the
+   =cons= class distinguished by the =car= of the =cons=.  This
+   analogy also characterizes those use cases where the metaprogrammer
+   could straightforwardly use filtered dispatch
+   \cite{Costanza.etal:2008} to implement their dispatch semantics.
+   We will see in section [[#Accept]] an example of a case where filtered
+   dispatch is incapable of straightforwardly expressing the dispatch,
+   but first we present our implementation of the motivating case from
+   \cite{Costanza.etal:2008}.
 ** SIGNUM specializers
    :PROPERTIES:
    :CUSTOM_ID: Signum
@@ -282,52 +300,52 @@ variables.
    Our second example of the implementation and use of generalized
    specializers is a reimplementation of one of the examples in
    \cite{Costanza.etal:2008}: specifically, the factorial function.
-   Here, we will perform dispatch based on the =signum= of the
+   Here, dispatch will be performed based on the =signum= of the
    argument, and again, at most one method with a =signum= specializer
-   will be appliable to any given argument, which makes the structure
+   will be applicable to any given argument, which makes the structure
    of the specializer implementation very similar to the =cons=
    specializers in the previous section.
 
-   We have chosen to compare signum values using \texttt{=}, which
-   means that a method with specializer =(signum 1)= will be
-   applicable to positive floating-point arguments (see the first
-   method on =specializer-accepts-generalizer-p= and the method on
-   =specializer=accepts-p= below).  This leads to one subtle
+   The metaprogrammer has chosen in the example below to compare
+   signum values using \texttt{=}, which means that a method with
+   specializer =(signum 1)= will be applicable to positive
+   floating-point arguments (see the first method on
+   =specializer-accepts-generalizer-p= and the method on
+   =specializer-accepts-p= below).  This leads to one subtle
    difference in behaviour compared to that of the =cons=
    specializers: in the case of =signum= specializers, the /next/
    method after any =signum= specializer can be different, depending
    on the class of the argument.  This aspect of the dispatch is
    handled by the second method on =specializer-accepts-generalizer-p=
    below.
+
 #+begin_src lisp
 (defclass signum-specializer (specializer)
   ((%signum :reader %signum :initarg :signum)))
 (defclass signum-generalizer (generalizer)
   ((%signum :reader %signum :initarg :signum)))
 (defmethod generalizer-of-using-class
-    ((gf signum-generic-function) arg)
-  (typecase arg
-    (real (make-instance 'signum-generalizer
-                         :signum (signum arg)))
-    (t (call-next-method))))
+    ((gf signum-generic-function) (arg real))
+  (make-instance 'signum-generalizer
+                 :signum (signum arg)))
 (defmethod generalizer-equal-hash-key
     ((gf signum-generic-function)
-     (g signum-specializer))
+     (g signum-generalizer))
   (%signum g))
 (defmethod specializer-accepts-generalizer-p
     ((gf signum-generic-function)
      (s signum-specializer)
      (g signum-generalizer))
-  (if (= (%signum s) (%signum g)) ; or EQL?
+  (if (= (%signum s) (%signum g))
       (values t t)
       (values nil t)))
 
 (defmethod specializer-accepts-generalizer-p
     ((gf signum-generic-function)
-     (specializer sb-mop:specializer)
-     (thing signum-specializer))
+     (s specializer)
+     (g signum-generalizer))
   (specializer-accepts-generalizer-p
-   gf specializer (class-of (%signum thing))))
+   gf s (class-of (%signum g))))
 
 (defmethod specializer-accepts-p
     ((s signum-specializer) o)
@@ -335,8 +353,8 @@ variables.
 #+end_src
 
    Given these definitions, and once again some more straightforward
-   ones elided for reasons of space, we can implement the factorial
-   function as follows:
+   ones elided for reasons of space, the programmer can implement the
+   factorial function as follows:
 
 #+begin_src lisp
 (defgeneric fact (n)
@@ -345,9 +363,9 @@ variables.
 (defmethod fact ((n (signum 1))) (* n (fact (1- n))))
 #+end_src
 
-   We do not need to include a method on =(signum -1)=, as the
-   standard =no-applicable-method= protocol will automatically apply to
-   negative real or non-real arguments.
+   The programmer does not need to include a method on =(signum -1)=,
+   as the standard =no-applicable-method= protocol will automatically
+   apply to negative real or non-real arguments.
 ** Accept HTTP header specializers
    :PROPERTIES:
    :CUSTOM_ID: Accept
@@ -366,15 +384,14 @@ variables.
    it has available to satisfy this request, and sends the best
    matching resource in its response.
 
-   For example, a graphical web browser might by default send an
-   =Accept= header such as
-   =text/html,application/xml;q=0.9,*/*;q=0.8=.  This should be
-   interpreted by a web server as meaning that if for a given resource
-   the server can provide content of type =text/html= (i.e. HTML),
-   then it should do so.  Otherwise, if it can provide
-   =application/xml= content (i.e. XML of any schema), then that
-   should be provided; failing that, any other content type is
-   acceptable.
+   For example, a graphical web browser might send an =Accept= header
+   of =text/html,application/xml;q=0.9,*/*;q=0.8= for a request of a
+   resource typed in to the URL bar.  This should be interpreted as
+   meaning that: if the server can provide content of type =text/html=
+   (i.e. HTML) for that resource, then it should do so.  Otherwise, if
+   it can provide =application/xml= content (i.e. XML of any schema),
+   then that should be provided; failing that, any other content type
+   is acceptable.
 
    In the case where there are static files on the filesystem, and the
    web server must merely select between them, there is not much more
@@ -388,7 +405,7 @@ variables.
    generic function must then perform method selection against the
    request's =Accept= header to compute the appropriate response.
 
-   The =accept-specializer= below implements the dispatch.  It depends
+   The =accept-specializer= below implements this dispatch.  It depends
    on a lazily-computed =tree= slot to represent the information in
    the accept header (generated by =parse-accept-string=), and a
    function =q= to compute the (defaulted) preference level for a
@@ -411,23 +428,23 @@ variables.
 (defmethod specializer-accepts-generalizer-p
     ((gf accept-generic-function)
      (s accept-specializer)
-     (generalizer accept-generalizer))
-  (values (q (media-type s) (tree generalizer)) t))
+     (g accept-generalizer))
+  (values (q (media-type s) (tree g)) t))
 (defmethod specializer-accepts-generalizer-p
     ((gf accept-generic-function)
      (s specializer)
-     (generalizer accept-generalizer))
+     (g accept-generalizer))
   (specializer-accepts-generalizer-p
-   gf s (next generalizer)))
+   gf s (next g)))
 
 (defmethod specializer<
     ((gf accept-generic-function)
      (s1 accept-specializer)
      (s2 accept-specializer)
-     (generalizer accept-generalizer))
+     (g accept-generalizer))
   (let ((m1 (media-type s1))
         (m2 (media-type s2))
-        (tree (tree generalizer)))
+        (tree (tree g)))
     (cond
       ((string= m1 m2) '=)
       (t (let ((q1 (q m1 tree)))
@@ -438,15 +455,15 @@ variables.
              (t '<))))))
 #+end_src
 
-   The metaprogrammer can then support dispatching in this way for
-   suitable objects, such as the =request= object representing a
-   client request in the Hunchentoot web server.  The code below
-   implements this, by defining the computation of a suitable
-   =generalizer= object for a given request, and specifying how to
-   compute whether the specializer accepts the given request object
-   (=q= returns a number between 0 and 1 if any pattern in the =tree=
-   matches the media type, and =nil= if the media type cannot be
-   matched at all).
+   The metaprogrammer can then add support for objects representing
+   client requests, such as instances of the =request= class in the
+   Hunchentoot web server, by translating these into
+   =accept-generalizer= instances.  The code below implements this, by
+   defining the computation of a =generalizer= object for a given
+   request, and specifying how to compute whether the specializer
+   accepts the given request object (=q= returns a number between 0
+   and 1 if any pattern in the =tree= matches the media type, and
+   =nil= if the media type cannot be matched at all).
 
 #+begin_src
 (defmethod generalizer-of-using-class
@@ -454,13 +471,13 @@ variables.
      (arg tbnl:request))
   (make-instance 'accept-generalizer
                  :header (tbnl:header-in :accept arg)
-                 :next (class-of arg)))
+                 :next (call-next-method)))
 (defmethod specializer-accepts-p
-    ((specializer accept-specializer)
-     (obj tbnl:request))
-  (let* ((accept (tbnl:header-in :accept obj))
+    ((s accept-specializer)
+     (o tbnl:request))
+  (let* ((accept (tbnl:header-in :accept o))
          (tree (parse-accept-string accept))
-         (q (q (media-type specializer) tree)))
+         (q (q (media-type s) tree)))
     (and q (> q 0))))
 #+end_src
 
@@ -471,7 +488,7 @@ variables.
 (ensure-class nil :direct-superclasses
  '(text/html image/webp ...))
 #+end_src
-   and dispatch the operates using those anonymous classes.  While
+   and dispatch would operate using those anonymous classes.  While
    this is possible to do, it is awkward to express content-type
    negotiation in this way, as it means that the dispatcher must know
    about the universe of mime-types that clients might declare that
@@ -481,8 +498,8 @@ variables.
    filtering paradigm.
 
    Note that in this example, the method on =specializer<= involves a
-   nontrivial ordering of methods based on the =q= values specified in
-   the accept header (whereas in sections [[#Cons]] and [[#Signum]] only a
+   non-trivial ordering of methods based on the =q= values specified
+   in the accept header (whereas in sections [[#Cons]] and [[#Signum]] only a
    single extended specializer could be applicable to any given
    argument).
 
@@ -502,13 +519,24 @@ variables.
      (s string))
   (make-instance 'accept-generalizer
                  :header s
-                 :next (class-of s)))
+                 :next (call-next-method)))
 (defmethod specializer-accepts-p
-    ((s accept-specializer) (string string))
-  (let* ((tree (parse-accept-string string))
+    ((s accept-specializer) (o string))
+  (let* ((tree (parse-accept-string o))
          (q (q (media-type s) tree)))
     (and q (> q 0))))
 #+end_src
+
+   The =next= slot in the =accept-generalizer= is used to deal with
+   the case of methods specialized on the classes of objects as well
+   as on the acceptable media types; there is a method on
+   =specializer-accepts-generalizer-p= for specializers that are not
+   of type =accept-specializer= which calls the generic function again
+   with the next generalizer, so that methods specialized on the
+   classes =tbnl:request= and =string= are treated as applicable to
+   corresponding objects, though less specific than methods with
+   =accept-specializer= specializations.
+
 ** COMMENT Pattern / xpattern / regex / optima
    Here's the /really/ interesting bit, but on the other hand we're
    probably going to run out of space, and the full description of
@@ -520,19 +548,19 @@ variables.
   :END:
 
   In section [[#Examples]], we have seen a number of code fragments as
-  partial implementations of particular non-standard method dispatch,
-  using =generalizer= metaobjects to mediate between the methods of
-  the generic function and the actual arguments passed to it.  In
-  section [[#Generalizer metaobjects]], we go into more detail regarding
-  these =generalizer= metaobjects, describing the generic function
-  invocation protocol in full, and showing how this protocol allows a
-  similar form of effective method cacheing as the standard one does.
-  In section [[#Generalizer performance]], we show the results of some
-  simple performance measurements on our implementation of this
-  protocol in the SBCL implementation \cite{Rhodes:2008} of Common
-  Lisp to highlight the improvement that this protocol can bring over
-  a naïve implementation of generalized dispatch, as well as
-  to make the potential for further improvement clear.
+  partial implementations of particular non-standard method dispatch
+  strategies, using =generalizer= metaobjects to mediate between the
+  methods of the generic function and the actual arguments passed to
+  it.  In section [[#Generalizer metaobjects]], we go into more detail
+  regarding these =generalizer= metaobjects, describing the generic
+  function invocation protocol in full, and showing how this protocol
+  allows a similar form of effective method cacheing as the standard
+  one does.  In section [[#Generalizer performance]], we show the results
+  of some simple performance measurements on our implementation of
+  this protocol in the SBCL implementation \cite{Rhodes:2008} of
+  Common Lisp to highlight the improvement that this protocol can
+  bring over a naïve implementation of generalized dispatch, as well
+  as to make the potential for further improvement clear.
 
 ** Generalizer metaobjects
    :PROPERTIES:
@@ -562,12 +590,12 @@ variables.
     applicability of a particular specializer against a given argument
     using =specializer-accepts-p=, a new protocol function with
     default implementations on =class= and =eql-specializer= to
-    implement the expected behaviour.  In order to order the methods,
-    as required by the protocol, we define a pairwise comparison
-    operator =specializer<= which defines an ordering between
-    specializers for a given generalizer argument (remembering that
-    even in standard CLOS the ordering between =class= specializers
-    can change depending on the actual class of the argument).
+    implement the expected behaviour.  To order the methods, as
+    required by the protocol, we define a pairwise comparison operator
+    =specializer<= which defines an ordering between specializers for
+    a given generalizer argument (remembering that even in standard
+    CLOS the ordering between =class= specializers can change
+    depending on the actual class of the argument).
 
     The new =compute-applicable-methods-using-generalizers= is the
     analogue of the MOP's =compute-applicable-methods-using-classes=.
@@ -625,8 +653,10 @@ variables.
     required arguments in a list to use as a key in an =equal=
     hash-table.
 
-    [XXX could we actually compute a suitable hash key using the
+#+begin_comment
+    [could we actually compute a suitable hash key using the
     generalizer's class name and initargs?]
+#+end_comment
 
 *** COMMENT
     - [X] =generalizer-of-using-class= (NB class of gf not class of object)
@@ -689,7 +719,7 @@ variables.
    answer fits in SBCL's 63-bit fixnums – in an attempt to measure the
    worst case for generic dispatch, where the work done within the
    methods is as small as possible without being meaningless, and in
-   particular does not cause allocation or garbage collection to
+   particular does not cause heap allocation or garbage collection to
    obscure the picture.
 
 #+begin_src lisp :exports none
@@ -783,7 +813,7 @@ variables.
   cater for filtered dispatch, but they would have to explicitly
   modify their method combinations.  The Clojure programming language
   supports multimethods[fn:5] with a variant of filtered dispatch as
-  well as hierachical and identity-based method selectors.
+  well as hierarchical and identity-based method selectors.
 
   In context-oriented programming
   \cite{Hirschfeld.etal:2008,Vallejos.etal:2010}, context dispatch
@@ -820,9 +850,10 @@ variables.
   context of partial evaluation; for example, \cite{Ruf:1993}
   considers generalization in online partial evaluation, where sets of
   possible values are represented by a type system construct
-  representing an upper bound.  The relationship between generalizer
-  metaobjects and approximation in type systems could be further
-  explored.
+  representing an upper bound.  Exploring the relationship between
+  generalizer metaobjects and approximation in type systems might
+  yield strategies for automatically computing suitable generalizers
+  and cache functions for a variety of forms of generalized dispatch.
 * Conclusions
   :PROPERTIES:
   :CUSTOM_ID: Conclusions
@@ -847,7 +878,7 @@ variables.
   amortized (though there remains a substantial overhead compared with
   standard generic-function or regular function calls).  We discuss
   how the efficiency could be improved below.
-** Future Work
+** Future work
    :PROPERTIES:
    :CUSTOM_ID: Future Work
    :END:
@@ -922,5 +953,3 @@ variables.
 [fn:4] https://github.com/m2ym/optima
 
 [fn:5] http://clojure.org/multimethods
-
-