Colliding stellar objects via multimethods in OO Prolog?

237 Views Asked by At

I wonder how one would combine unification and OO in Prolog. I would like to implement a multimethod dispatch on term objects.

Without term objects and simple terms I would do the following and could profit from multi-argument indexing:

collide_with(asteroid(_), asteroid(_)) :- /* case 1 */
collide_with(asteroid(_), spaceship(_,_)) :- /* case 2 */
collide_with(spaceship(_,_), asteroid(_)) :- /* case 3 */
collide_with(spaceship(_,_), spaceship(_,_)) :- /* case 4 */

But the above only gives an exact type match.

What should I do if I want a sub class type match (there could be further spaceship subclasses such as excelsior, galaxy, etc.. that should also match in case 2,3 and 4).

Can I still use unification and indexing?

Bye

P.S.: The example is from here which doesn't have a Prolog solution:
https://en.wikipedia.org/wiki/Multiple_dispatch

3

There are 3 best solutions below

5
On

You're kind of all over the place with your question: term objects, multimethod dispatch, etc. Prolog doesn't have term objects or dispatch, really, but I think the spirit of the question is interesting.

Before we can have multimethods and multiple dispatch we will need, well, dispatch. I take it what you're worried about is that you want to be able to write a procedure that looks like this:

frob(spaceship(X, Y...)) :- % do something with spaceships
frob(asteroid(X, Y...))  :- % do something with asteroids

And then you want to be able to say, frob(excelsior(X, Y, ...)) and have it wind up in the first clause, somehow. This obviously isn't going to work out of the box, but that doesn't mean you can't make it work. Here are the approaches I would try:

Choose a simpler functor shape

Instead of trying to make it work with excelsior(...), change your representation to make it easier to introspect. An extremely general approach might look like this:

object(Type, Properties...)

This might work if you don't care about inheritance, but you do. Well, what if you made a slot for subtype information? Then you could match on that in the cases where you care and ignore it otherwise. Your structure would look like this:

type(SubtypeInfo, Properties...)

Then you could write frob like this:

frob(spaceship(_, X, Y)) :- % stuff

If you call it with Excelsior, it might look like this:

?- frob(spaceship(excelsior(SpecialProperties...), X, Y)).

In other words, make your term have the most general type at the outside, and wrap more specific information in inner stuff.

frob2(spaceship(excelsior(_, ...), X, Y)) :- % do something with excelsiors

Use a Metainterpreter

Writing your own dialect of Prolog is possible. If you add some facts to the database about what your types are subtypes of, your own metainterpreter can intercept the evaluation process and retry with parent types.

Unfortunately, I am not great at this and the following metainterpreter should be regarded as a buggy sketch/proof-of-concept, and not exactly a model to be followed.

:- op(500, xfx, is_kind_of).

excelsior is_kind_of spaceship.

frob(spaceship(X, Y)) :- !, write('I frobbed a spaceship'), nl.
frob(_) :- write('I frobbed something else'), nl.

execute(true).
execute((A,B)) :- execute(A), execute(B).
execute(A) :-
    predicate_property(A, built_in)
       -> call(A)
       ;  execute_goal(A).

execute_goal(Goal) :- clause(Goal, Body), call(Body).
execute_goal(Goal) :- supertype_goal(Goal, NewGoal), execute_goal(NewGoal).

supertype_goal(Goal, NewGoal) :-
    Goal =.. [Head, Term],
    Term =.. [Type|Args],
    Type is_kind_of Supertype,
    NewTerm =.. [Supertype|Args],
    NewGoal =.. [Head, NewTerm].

The idea here is to try and execute the goal as-is, and then re-execute the goal having rewritten part of it. The supertype_goal is not very general though, and the replacement routine is not comprehensive, but it can illustrate the intent:

?- execute(frob(excelsior(this,that))).
I frobbed something else
true ;
I frobbed a spaceship
true ;
I frobbed something else
true ;
false.

Yeah, so, not great, but a more skilled Prolog user than me could probably clean it up and make it work.

Discussion

There are really only two places data can go in Prolog: it can live on the call stack, or it can live in the database. The first method I show is really an example of the first: find a way to repackage "subtyping" for your purposes so that it can live in the call stack without interfering with (some) of the unification. If you structure the terms carefully (and code carefully) you can probably make this work, and it will not be hell to debug. But it may be a bit harder to read.

The second method uses a separate relationship in the database to reify the relationship between the different "subtypes." Once you have that, you need to modify the interpreter to make use of it. This is easier said than done and a bit tricky, but I don't think it's the worst idea in the world. Although, in thinking about it, the kind of unification you want to do has to be engineered by the metainterpreter.

You'll find that Logtalk also has a similar dichotomy between "parametric objects", whose identifiers are essentially full Prolog terms, and ordinary objects, that create a whole namespace that they encapsulate as if in a separate database. With non-parametric objects, unification does not happen on the structure of the object the way it does with a term.

Performance Concerns

Suppose I take two objects as parameters in some method. If I use the first method, I think I benefit from indexing if it's available and I'm not digging in too deep into the term—general programming should be better, I think. I don't know how Prolog systems respond to unifying deep into some structure; I would imagine they do well, but I don't know about argument indexing. Feels like it would be fraught.

The second approach doesn't hold up that well at all. If my hierarchy could be N classes deep, I might try N^2 different combinations. This sounds unproductive. Clearly Paulo has figured something out in Logtalk, which doesn't seem to have this performance issue.

Diversion on Double Dispatch

This was quite a revelation to me when I was learning Smalltalk, so forgive me if you already know it. You can get the type benefit of multiple dispatch in a single-dispatch language using "double dispatch." Basically, you have all your objects implement collide_with, taking an "other" object as a parameter, so you have Asteroid::collide_with(Other) and Ship::collide_with(Other) and Bullet::collide_with(Other). Then, each of these methods calls Other's collide_with_type, passing in self. You get a bunch of methods (and many you will delegate to the other side) but you can recreate all the missing type information safely at runtime.

I wrote a crappy Asteroids clone in Lua some time ago, in which you can see how it works:

-- double dispatch for post collision handling
function Asteroid:collideWith(other)
   return other:collideWithAsteroid(self)
end

function Asteroid:collideWithShot(s) 
   -- remove this asteroid from the map
   if index[self] then
      table.remove(asteroids, index[self])
      index[self] = nil
      s:remove()
   end
end

function Asteroid:collideWithPlayer(p) 
   p:collideWithAsteroid(self)
end

function Asteroid:collideWithAsteroid(ast) end

So you can see a little of everything there: Asteroid:collideWithShot removes the asteroid from play, but it delegates the Asteroid:collideWithPlayer(p) to Player:collideWithAsteroid(a), and two asteroids colliding doesn't do anything.

A basic sketch of how this might look in Logtalk would be:

:- protocol(physical).

  :- public(collides_with/1).

:- end_protocol.

:- object(asteroid, implements(physical)).

  collides_with(Other) :- self(Self), Other::collides_with_asteroid(Self).

  collides_with_asteroid(AnotherAsteroid).
  collides_with_ship(Ship) :- % do stuff with a ship

:- end_object.

Bear with me, I use Logtalk very rarely!

Update: sad to say, Jan Burse (author of Jekejeke Prolog) has pointed out that the cut operator will wreak havoc with double dispatch. This doesn't necessarily mean that multiple dispatch with subtyping is incompatible with unification, but it does mean that double dispatch as a workaround is incompatible with the cut, which will complicate nondeterminism and may ruin this approach. See the comments below for more discussion.

Conclusion

I don't think subtyping and unification are mutually exclusive, because Logtalk has them both. I don't think subtyping and multiple dispatch with argument indexing are mutually exclusive either, but Logtalk doesn't have multiple dispatch, so I can't be certain. I avoid subtyping even in Java, for the most part, so I'm probably biased. Multiple dispatch is kind of a $100 language feature though; I can't say many languages have it, but you can fake it quite effectively with double dispatch.

I would investigate Logtalk heavily if you are interested in this stuff though. The parametric example in particular is pretty compelling.

I have some doubt that this really answered your question or even landed in the same ballpark but I hope it helps!

0
On

Just had the following funky idea. Assume we have a predicate isinst/2, the mirror of instof/2. If we want to check that X is an asteroid resp. spaceship we would do:

 isinst(asteroid, X). /* checks whether X is an asteroid */
 isinst(spaceship, X). /* checks whether X is a spaceship */

So the Prolog code is straight forward:

 collide_with(X, Y) :- isinst(asteroid, X), isinst(asteroid, Y), /* case 1 */
 collide_with(X, Y) :- isinst(asteroid, X), isinst(spaceship, Y), /* case 2 */
 collide_with(X, Y) :- isinst(spaceship, X), isinst(asteroid, Y), /* case 3 */
 collide_with(X, Y) :- isinst(spaceship, X), isinst(spaceship, Y), /* case 4 */

Now assume our Prolog system offers attribute variables, and a readable notion for attribute variables such as X{...}. We could then go on, and define:

 collide_with(X{isinst(asteroid)}, Y{isinst(asteroid)}) :- /* case 1 */
 collide_with(X{isinst(asteroid)}, Y{isinst(spaceship)}) :- /* case 2 */
 collide_with(X{isinst(spaceship)}, Y{isinst(asteroid)}) :- /* case 3 */
 collide_with(X{isinst(spaceship)}, Y{isinst(spaceship)}) :- /* case 4 */

This could lead to slightly faster code, since the attribute variables would directly help the unification, and it is not that the body must something check.

Whether it also leads to better indexing is still unclear for me at the moment, problem is that inheritance hierarchie might change at runtime, and this could impact the index and require re-index. This also holds if we can guarantee that inheritance hierarchie is not open world, by for example marking classes as final. If the Prolog system is viewed as dynamic, also this can change.

Besides that there are some obvious ideas for indexing if the inheritance hierarchie is not open world, i.e. if the sub classes can be enumerated. The only problem here would be to efficiently share different heads, if this is possible, by the same body. Otherwise there could be quite an explosion in clauses.

Bye

P.S.: There is a slight semantic shift when going from the body checks to the attribute variables, since the attribute variables might defer the hook,

so we might get that collide_with(X,Y) fails when using the body checks, since X and Y are uninstantiated and on the other hand collide_with(X,Y) succeeds when using attribute variables.

But the outcome should be more or less the same when the arguments of collide_with/2 are instantiated.

3
On

In CLOS, the generic functions used for multiple dispatch are not encapsulated in classes but rather grouped by function name. Thus, the equivalent here would be plain Prolog rules. Moreover, assuming multiple argument indexing, the arguments in the rule heads must be sufficiently instantiated to the "types" over which we want to perform multiple dispatch so that the correct rule will be selected everytime with no spurious choice-points. As the OP exemplified:

collide_with(asteroid(_), asteroid(_)) :-
    ...
collide_with(asteroid(_), spaceship(_)) :-
    ...
collide_with(spaceship(_), asteroid(_)) :-
    ...
collide_with(spaceship(_), spaceship(_)) :-
    ...

Given how unification works in Prolog, if we want to have specializations of the basic asteroid and spaceship "types", and following Daniel's suggestion, we can use the compound terms asteroid/1 and spaceship/1 as wrappers for the actual objects defining the "types" and "sub-types". What is missing then is a way to use single dispatch, as found e.g. in Logtalk, to redirect to the correct rule. Daniel already described how to use double dispatch as a possible solution. An alternative could be to define a parametric object such as:

:- object(collide_with(_, _)).

    :- public(bump/0).
    bump :-
        % access the object parameters
        this(collide_with(Obj1, Obj2)),
        % wrap the object parameters
        wrap(Obj1, Wrapper1), wrap(Obj2, Wrapper2),
        % call the plain Prolog rules
        {collide_with(Wrapper1, Wrapper2)}. 

    wrap(Obj, Wrapper) :-
        wrap(Obj, Obj, Wrapper).

    wrap(Obj, Wrapper0, Wrapper) :-
        (   extends_object(Wrapper0, Parent) ->
            wrap(Obj, Parent, Wrapper)
        ;   Wrapper =.. [Wrapper0, Obj] 
        ).

:- end_object.

We would also have all the necessary objects to represent the hierarchies of asteroids and starships (here I'm using prototypes instead of classes/instances for simplicity). For example:

:- object(spaceship).
    ...
:- end_object.

:- object(galaxy, extends(spaceship)).
    ...
:- end_object.

:- object(asteroid).
    ...
:- end_object.

:- object(ceres, extends(asteroid)).
    ...
:- end_object.

Typical usage would then be:

?- collide_with(ceres, galaxy)::bump.
...

As the plain Prolog rules for the collide_with/2 predicate will receive the (wrapped) object identifiers, is trivial for them to send to those objects messages requesting any necessary information to implement whatever behavior we want when two objects bump.

The collide_with/2 parametric object abstracts the implementation details of this multiple dispatch solution. One advantage over the double dispatch solution described by Daniel is that we don't need to single out one of the objects for the collide message. One disadvantage is that we need an additional message, bump/0 in the code abode, to trigger the computation.