Search code examples
oopobjectmoduleprologswi-prolog

Objected Oriented Programming in SWI-Prolog


I read somewhere that you can think of modules as objects in Prolog. I am trying to get my head around this, and if it a good way to code.

If I have two files, one defining a class dog and then another one that uses this class to make two dog objects.

:- module(dog,
      [ create_dog/4,bark/1 ]).

create_dog(Name,Age,Type,Dog):-
   Dog = dog(name(Name),age(Age),type(Type)).

bark(Dog):-
   Dog = dog(name(_Name),age(_Age),type(Type)),
   Type = bassethound,
   woof.
bark(Dog):-
   Dog = dog(name(_Name),age(_Age),type(Type)),
   Type \= bassethound,
   ruff.

woof:-format("woof~n").

ruff:-format("ruff~n").

second file

use_module(library(dog)).

run:-
   dog:create_dog('fred',5,bassethound,Dog),
   forall(between(1,5,_X),
       dog:bark(Dog)
      ),
   dog:create_dog('fido',6,bloodhound,Dog2),
   dog:bark(Dog2).

This makes a dog object Dog which is a basset hound and makes it bark 5 times, I then make another dog object Dog2 which is a bloodhound and make this also bark. I understand that in oop you have objects that have behaviours and state. So I now have two objects with different behaviours based on their own states but at the moment I am storing the state of the objects in the Dog variables where they can be seen by the code in the main program. Is there a way to hide the state of the objects i.e to have private variables? For example I might want to have a way of storing the state has_barked for each dog object, which would be true if it has barked earlier in the program and false otherwise, then change the behaviour of bark/1 based on this.

Also how would you handle inheritance and overriding methods etc? Any pointer to readings welcomed. Thank you.


Solution

  • Just an example of one of the possible reimplementations of your sample code in Logtalk. It uses prototypes for simplicity but it still illustrates some key concepts including inheritance, default predicate definitions, static and dynamic objects, and parametric objects.

    % a generic dog
    :- object(dog).
    
        :- public([
            create_dog/3, bark/0, name/1, age/1
        ]).
    
        create_dog(Name, Age, Dog) :-
            self(Type),
            create_object(Dog, [extends(Type)], [], [name(Name),age(Age)]).
    
        % default definition for all dogs
        bark :-
            write(ruff), nl.
    
    :- end_object.
    
    
    :- object(bassethound,
        extends(dog)).
    
        % bark different
        bark :-
            write(woof), nl.
    
    :- end_object.
    
    
    :- object(bloodhound,
        extends(dog)).
    
    :- end_object.
    
    
    % support representing dogs as plain database facts using a parametric object
    :- object(dog(_Name,_Age,_Type),
        extends(dog)).
    
        name(Name) :-
            parameter(1, Name).
    
        age(Age) :-
            parameter(2, Age).
    
        bark :-
            parameter(3, Type),
            [Type::bark].
    
    :- end_object.
    
    
    % a couple of (static) dogs as parametric object proxies
    dog(fred, 5, bassethound).
    dog(fido, 6, bloodhound).
    
    
    % another static object
    :- object(frisbee,
        extends(bloodhound)).
    
        name(frisbee).
        age(1).
    
    :- end_object.
    

    Some sample queries:

    $ swilgt
    ...
    ?- {dogs}.
    % [ /Users/foo/dogs.lgt loaded ]
    % (0 warnings)
    true.
    
    ?- bassethound::bark.
    woof
    true.
    
    ?- bloodhound::bark.
    ruff
    true.
    
    ?- bassethound::create_dog(boss, 2, Dog).
    Dog = o1.
    
    ?- o1::bark.
    woof
    true.
    
    ?- {dog(Name, Age, Type)}::bark.
    woof
    Name = fred,
    Age = 5,
    Type = bassethound ;
    ruff
    Name = fido,
    Age = 6,
    Type = bloodhound.
    
    ?- dog(ghost, 78, bloodhound)::(bark, age(Age)).
    ruff
    Age = 78.
    
    ?- forall(between(1,5,_X), {dog(fred,_,_)}::bark).
    woof
    woof
    woof
    woof
    woof
    true.
    

    Some notes. ::/2 is the message sending control construct. The goal {Object}::Message simply proves Object using the plain Prolog database and then sends the message Message to the result. The goal [Object::Message] delegates a message to an object while keeping the original sender.