问题
There is a generic method, say incx.  There are two versions of incx.  One specialized on type a,  and one specialized on type b.  Type b is a subclass of a.  You are given an object of type b, the derived type - but you want to call the method that is specialized on type a.   You could do this easily if there wasn't already a method of the same name specialized on type b, but alas, there is such a method.  
So how do you call the method specialized on type a in such a situation?
(defclass a () ((x :accessor x :initform 0)))
(defclass b (a) ((y :accessor y :initform 0)))
(defgeneric inc (i))
(defmethod inc ((i a)) (incf (x i)))
(defmethod inc ((i b)) (incf (y i)))
(defvar r (make-instance 'b))
As promised by CLOS, this calls the most specialized method:
* (inc r) 
* (describe r)
    ..
  Slots with :INSTANCE allocation:
    X  = 0
    Y  = 1
But this in this particular case, (not in general) what I want is to access the less specialized version. Say something like:
(inc (r a)) ; crashes and burns of course, no function r or variable a
(inc a::r)  ; of course there is no such scoping operator in CL
I see the call-next-method function can be used from within a specialized method to get the next less specialized method, but that isn't what is wanted here. 
In the code this was cut out of, I do need something similar to call-next-method, but for calling a complementary method.  Rather than calling a method of the same name in the next less specialized class, we need to call its complementary method,  which has a different name.  The complementary method is also specialized, but calling this specialized version doesn't work - for much the same reasons that call-next-method was probably included for.  It isn't always the case that the required method specialized on the super class has the same name.
(call-next-method my-complement)  ; doesn't work, thinks my-complement is an arg
Here is another example.
There is a base class describing electron properties and a derived class describing the properties of a "strange-electron". Methods specialized on the strange electron desire to call methods specialized on the electron. Why? because these methods do the normal electron part of the work for the program. The non-electron part of the strange electron is almost trivial, or rather it would be if it didn't duplicate the electron code:
(defgeneric apply-velocity (particle velocity))
(defgeneric flip-spin (particle))
;;;; SIMPLE ELECTRONS
(defclass electron ()
  ((mass
      :initform 9.11e-31
      :accessor mass)
   (spin
      :initform -1
      :accessor spin)))
(defmacro sq (x) `(* ,x ,x))
(defmethod apply-velocity ((particle electron) v)
  ;; stands in for a long formula/program we don't want to type again:
  (setf (mass particle) 
        (* (mass particle) (sqrt (- 1 (sq (/ v 3e8)))))))
(defmethod flip-spin ((particle electron))
  (setf (spin particle) (- (spin particle))))
;;;; STRANGE ELECTRONS
(defclass strange-electron (electron)
  ((hidden-state
      :initform 1
      :accessor hidden-state)))
(defmethod flip-spin ((particle strange-electron))
  (cond
    ((= (hidden-state particle) 1)
     (call-next-method)
     ;; CALL ELECTRON'S APPLY-VELOCITY HERE to update
     ;; the electron. But how???
     )
    (t nil)))
;; changing the velocity of strange electrons has linear affect!
;; it also flips the spin without reguard to the hidden state!
(defmethod apply-velocity ((particle strange-electron) v)
  (setf (mass particle) (* (/ 8 10) (mass particle)))
  ;; CALL ELECTRON'S SPIN FLIP HERE - must be good performance,
  ;; as this occurs in critical loop code, i.e compiler needs to remove
  ;; fluff, not search inheritance lists at run time
  )
It all reduces to a simple question:
How to call the less specialized method if a more specialized one has been defined?
回答1:
I'd prefer the explicit approach here:
(defun actually-inc-a (value) (incf (x value)))
(defun actually-inc-b (value) (incf (y value)))
(defmethod inc ((object a)) (actually-inc-a object))
(defmethod inc ((object b)) (actually-inc-b object))
i.e., place the part of the implementation you want to share into a separate function.
(defun apply-velocity-for-simple-electron (particle v)
  (setf (mass particle) (* (mass particle) (sqrt (- 1 (sq (/ v 3e8)))))))
(defun flip-spin-for-simple-electron (particle)
  (setf (spin particle) (- (spin particle))))
(defmethod apply-velocity ((particle electron) v)
  (apply-velocity-for-simple-electron particle v))
(defmethod flip-spin ((particle electron))
  (flip-spin-for-simple-electron particle))
(defmethod apply-velocity ((particle strange-electron) v)
  (setf (mass particle) (* (/ 8 10) (mass particle)))
  (flip-spin-for-simple-electron particle))
(defmethod flip-spin ((particle strange-electron))
  (when (= (hidden-state particle) 1)
    (call-next-method)
    (apply-velocity-for-simple-electron particle #| Hu? What's the V here? |#)))
Given, that I don't know anything about electrons, whether plain or strange, spinning or not, I couldn't really think of a meaningful name for those base helper functions. But apart from that...
回答2:
Your question contains two questions:
- How to call a specific effective method?
- How to avoid copy-pasting in the case of the electron simulation?
This answer is a merge of my other answer and is inspired partially by Dirk's good answer for the concrete example. I'll cover first the question as asked (calling a specific method) and explain why you should instead try another approach, notably for your example.
Calling an effective method
Yes, you can call the function associated with a method instead of the generic function. For a portable approach, first load closer-mop:
(ql:quickload :closer-mop)
Define some classes and a simple generic function:
(defclass a () ())
(defclass b (a) ())
(defclass c (b) ())
(defgeneric foo (x)
  (:method ((x a)) 0)
  (:method ((x b)) (+ (call-next-method) 1))
  (:method ((x c)) (* (call-next-method) 2)))
We have a class hierarchy (a < b < c) and a generic function dispatching on the first argument only.
Now, we compute the applicable methods for class b and use the resulting list to define a function which calls the effective method of foo specialized on b.
(destructuring-bind (method . next)
    (closer-mop:compute-applicable-methods-using-classes
     #'foo
     (list (find-class 'b)))
  (let ((fn (closer-mop:method-function method)))
    (defun %foo-as-b (&rest args)
      (funcall fn args next))))
And here you have the two different behaviors:
(let ((object (make-instance 'c)))
  (list
    (%foo-as-b object)
    (foo object))
=> (1 2)
This is however not recommended. CLOS provides a way to combine effective methods and you should try to use it as intended instead of hijacking it. Indeed, suppose that I evaluate the following:
(defmethod foo :before ((i a)) (print "Before A"))
The foo generic function, called on an instance c of c, will print the string. But when using %foo-as-b on c, no string is printed, even though we are calling the function as-if c was instead an instance of  b and the method is specialized on a.
This is of course because compute-applicable-methods-using-classes depends on the set of methods known when called. In that case function %foo-as-b is still using an outdated list of methods. The effect is amplified if you define several such functions or specialize over multiple classes. If you want to always keep %foo-as-b synchronized with your environment, you somehow need to recompute the list at each invocation of this function (instead of having a let-over-lambda, you'd recompute the value inside the lambda).
Another possibility is to introduce hooks into CLOS to recompute the function when required, but this is madness.
Do not overuse inheritance for sharing code
Consider the Liskov substitution principle. The overuse of inheritance for sharing code (i.e. implementation details) instead of polymorphism is what springs advices like "Favor Composition over Inheritance". See Where does this concept of “favor composition over inheritance” come from? and Code Smell: Inheritance Abuse for more details on this.
Use functions
In C++, where base::method() can be found, you are just calling a different function with a similar name: there is no dynamic dispatch when you tell your compiler which method you want to call, so this is in fact as-if you called a regular function.
With your requirements, I would write what follows. It is based on Dirk's version and makes use of auxiliary inlined local functions, which are perfectly adequate when you want to avoid repetition:
(defclass electron ()
  ((mass :initform 9.11e-31 :accessor mass)
   (spin :initform -1 :accessor spin)))
(defclass strange-electron (electron)
  ((hidden-state :initform 1 :accessor hidden-state)))
(let ((light-speed 3e8)
      (mysterious-velocity 0d0))
  (flet ((%flip (p)
           (setf (spin p) (- (spin p))))
         (%velocity (p v)
           (setf (mass p)
                 (* (mass p)
                    (sqrt
                     (- 1 (expt (/ v light-speed) 2)))))))
    (declare (inline %flip %velocity))
    (defgeneric flip-spin (particle)
      (:method ((p electron))
        (%flip p))
      (:method ((p strange-electron))
        (when (= (hidden-state p) 1)
          (call-next-method)
          (%velocity p mysterious-velocity))))
    (defgeneric apply-velocity (particle velocity)
      (:method ((p electron) v)
        (%velocity p v))
      (:method ((p strange-electron) v)
        (setf (mass p)
              (* (/ 8 10) (mass p)))
        (%flip p)))))
The problem is solved and is hopefully quite readable: there is no need to hack something else in CLOS. Auxiliary functions that are shared by different methods are easily identified and if you need to recompile any of them, you'll have to recompile the whole form, which ensures the existing coupling between classes is taken into account in all methods.
Use composition
What happens if we apply the above recommendation and use composition instead?
Let's change your strange-electron so that it contains a simple-electron. That may sound weird with respect to actual electrons, but it makes sense if we consider the objects used to simulate; also, note that in your question you actually wrote about an "electron part" and the "non-electron part of the strange electron". First, the main classes:
;; Common base class
(defclass electron () ())
;; Actual data for mass and spin
(defclass simple-electron (electron)
  ((mass :initform 9.11e-31 :accessor mass)
   (spin :initform -1 :accessor spin)))
;; A strange electron with a hidden state
(defclass strange-electron (electron)
  ((simple-electron :accessor simple-electron :initarg :electron)
   (hidden-state :initform 1 :accessor hidden-state)))
Notice how the strange-electron does not inherit anymore from simple-electron (we don't need to store a separate mass and spin) but contains an instance of simple-electron.
Note also that we added a common electron base class, which is not strictly necessary in that case.
I'll skip the part where we define generic functions and just describe methods.
In order to get/set the mass and spin of those strange electrons, we have to delegate to the inner object:
(macrolet ((delegate (fn &rest args)
             `(defmethod ,fn (,@args (e strange-electron))
                (funcall #',fn ,@args (simple-electron e)))))
  (delegate mass)
  (delegate spin)
  (delegate (setf mass) new-value)
  (delegate (setf spin) new-value))
Before we continue, what does the above code do? If we expand the last form inside the macrolet, namely the one with (setf spin), we obtain a method which sets the slot of the inner particle:
(defmethod (setf spin) (new-value (e strange-electron))
  (funcall #'(setf spin) new-value (simple-electron e)))
That's great. Now, we can define flip-spin and apply-velocity quite simply. 
The basic behavior is tied to the simple-electron class:
(defmethod flip-spin ((e simple-electron))
  (setf (spin e) (- (spin e))))
(defmethod apply-velocity ((e simple-electron) velocity)
  (setf (mass e)
        (* (mass e)
           (sqrt
            (- 1 (expt (/ velocity +light-speed+) 2))))))
This is the same equation as in your original question, but specialized on simple-electron. For strange electrons, you rely on the internal object:
(defmethod flip-spin ((e strange-electron))
  (when (= (hidden-state e) 1)
    (flip-spin (simple-electron e))
    (apply-velocity (simple-electron e) 0d0)))
(defmethod apply-velocity ((e strange-electron) velocity)
  (setf (mass e) (* (/ 8 10) (mass e)))
  (flip-spin (simple-electron e)))
One of your objective is to have a CLOS interface and not a "static interface", and this is exactly the case here.
Conclusion
Calling a less specific method explicitely is a code smell. I don't exclude the possibility that it might be a sensible approach in some cases, but I'd suggest to consider alternative designs first.
Common code can be shared through regular functions, like it was always done (for a convenient definition of always). Alternatively, prefer composition.
回答3:
It may be possible using MOP (MetaObect Protocol). It seems as if compute-applicable-methods might be exactly what you want.
It might also be possible to play rather horrible tricks using change-class.
Just a note, the methods in CLOS are not "methods on classes", they're "methods on generic functions". So you can't really call "a method of a different name, in the parent class", you can only call a different generic function.
回答4:
PS: I know this answer is late, but I still find it a strong option not yet regarded in other answers.
Note: For methods specialized on a single parameter, it may make sense to say that the next method is a method specialized on a superclass of the argument provided for the specialized parameter.
However, this doesn't hold in general, for instance, with a method specializes on one parameter and another method on another parameter, or with methods specialized on more than one parameter.
Nonetheless, for the practical problem you have at hand, you may use another approach, which is to use a special variable to tell your own methods to simply call-next-method:
(defvar *strange-electron-bypass* nil)
(defmethod flip-spin ((particle strange-electron))
  (let ((bypass *strange-electron-bypass*)
        (*strange-electron-bypass* nil))
    (cond (bypass
           (call-next-method))
          ((= (hidden-state particle) 1)
           (call-next-method)
           (let ((*strange-electron-bypass* t))
             ;; where does v come from?
             (apply-velocity particle v)))
          (t
           nil))))
(defmethod apply-velocity ((particle strange-electron) v)
  (let ((bypass *strange-electron-bypass*)
        (*strange-electron-bypass* nil))
    (cond (bypass
           (call-next-method))
          (t
           (setf (mass particle)
                 (* (/ 8 10) (mass particle)))
           (let ((*strange-electron-bypass* t))
             (flip-spin particle))))))
The performance of the call to flip-spin (strange-electron) inside apply-velocity (strange-elector t) will not get hurt much if you only ever specialize on classes.  In most (if not all) CLOS implementations, the applicable methods will be memoized (cached) based on the argument's classes in this case, so only the first call on an instance of strange-electron itself will pay the price for computing the applicable methods.
This approach has the advantage that it is generalizable, as it will call whatever is the next most specific method, and it doesn't require messing with CLOS, which usually would mean losing optimizations performed by the Common Lisp implementation.
EDIT: As you can see, the variable *strange-electron-bypass* is rebound to nil on method entry to support recursion, mutual or otherwise.  In this case, there's no recursion, but if you want to generalize this solution to other situations where there might be recursion (i.e. the same method is applicable twice in the call stack), especially in a composition case, the methods will be reentrant.
回答5:
Dirk's answer has a couple of problems which can be fixed, as shown here.
Firstly, it does not generalize without becoming a new static object system. When attempting generalization, one quickly runs into the fact that all methods belonging to the same generic definition have the same name. In order to fix this problem one is left to give the functions munged names reflecting their type signature (as per Stroustrup's famous macro processor).
Secondly, when generalized it becomes a separate static object oriented system. As a static system it does not play well with CLOS. It becomes a case of mixed paradigms.
However, Dirks approach of avoiding code duplication can be kept local without exporting the auxiliary routines to the interface. This can be accomplished by wrapping them in CLOS methods. These CLOS methods then become branches in the specialization tree, one's that can be specialized separately from other branches. The name change then represents a branch rather than a type signature (more manageable).
So here is the encapsulated auxiliary function approach applied to the inc example. Note that inc-a becomes a less specialized function that can be called by others, including methods specialized on the inherited b class, as no methods in the b class specialize it further (unlike for inc).
(defclass a () ((x :accessor x :initform 0)))
(defclass b (a) ((y :accessor y :initform 0)))
(defgeneric inc (i))
(defgeneric inc-a (i)) ; same as inc, but won't be further specialized
(defmacro inc-a-stuff (i) ; this is not exported! not an interface
  `(incf (x ,i))
  )
(defmethod inc ((i a)) (inc-a-stuff i))
(defmethod inc ((i b)) (incf (y i)))
;; provides a method to generalize back to class a
;; this method does not get further specialization by b, thus
;; remains a window into the "a part"
(defmethod inc-a ((i a)) (inc-a-stuff i))
(defvar r (make-instance 'b))
(inc r) ; all good, increments y
;;(inc (r a)) ; ah how do you get this?
;;
(inc-a r) ; 
(describe r)
#|
Slots with :INSTANCE allocation:
  X  = 1
  Y  = 1
|#
This solution is hazard free for dynamic changes to the object schema. I.e. it works within CLOS.
来源:https://stackoverflow.com/questions/35171694/clos-how-to-call-a-less-specific-method