15

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.

user27815
  • 4,767
  • 14
  • 28
  • If it's not the answer you want, then I'll try to write a longer one, but... I think you're trying to use Prolog for the wrong purposes. It's a logic engine, not an OOP language. The problem would be much more simply solved in an imperative/OOP language like Python or Java. – Tom Jan 26 '15 at 16:19
  • 1
    I'm just experimenting. This is just a trivial example, I have lots of prolog code and i'm wondering if using a combined oop and logic style will be a good way of doing things or not.. happy to hear your thoughts, i understand how to program in Java and python so I am familiar with standard oop but not oop in prolog. – user27815 Jan 26 '15 at 16:38
  • I think the important think to note is that OOP is a paradigm, and so is logical programming. In Prolog, I don't think that they mix particularly well. If you _need_ to combine the two disciplines, consider a package like this: https://code.google.com/p/pyswip/ – Tom Jan 26 '15 at 16:46
  • 1
    Thanks but I don't want to use python etc I want to stick to swi for learning purposes, they are two separate paradigms, but it is not that uncommon to combine them. for example SICStus https://sicstus.sics.se/sicstus/docs/3.7.1/html/sicstus_35.html – user27815 Jan 26 '15 at 16:50
  • It certainly _is_ uncommon, but, as you say, not unheard of. My advice is that this, while possible, is just not what Prolog is for. However, someone has just posted an answer that might be useful if you wish to continue :) – Tom Jan 26 '15 at 16:52
  • My feeling is it's better to combine the two paradigms by querying the logic-programming engine and producing objects from it... but for an OOP language, e.g. Java. A bit further afield, but Answer Set Programming has, in my opinion, a nice integration like this with DLV, you can see a code snippet here: http://www.dlvsystem.com/jdlv/ – Dr. Thomas C. King Jan 27 '15 at 07:15

7 Answers7

9

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.

Paulo Moura
  • 18,373
  • 3
  • 23
  • 33
  • why isn’t there a pure-Prolog version of Logtalk in the same spirit as the Prolog Objects in SICStus? – Erik Kaplun Jan 17 '22 at 15:22
  • @ErikKaplun No idea of what exactly you're asking. Logtalk is implemented in plain and portable Prolog code. What does "pure" means in the context of the OP question and answers? – Paulo Moura Jan 17 '22 at 18:56
  • no, I mean it would be nice to be able to “embed” Logtalk structures in plain .pl files and have these structures expanded. at least to the extent possible without full project compiles. – Erik Kaplun Jan 24 '22 at 12:00
  • 1
    @ErikKaplun Thanks for clarifying. Logtalk source files can contain both plain Prolog code and Logtalk code. Note that the only portable term-expansion mechanism is the one in Logtalk. There's no Prolog standard for it. Thus, those files (which can have a `.pl` extension) would still need to be compiled and loaded using the Logtalk `logtalk_load/1-2` predicates. – Paulo Moura Jan 24 '22 at 12:12
  • So I couldn’t first load the backend specific term-extension from Logtalk into Prolog and then write Logtalk constructs directly? Or that would require the avoiding of any and all already-active vanilla term-expansions in the loading code, to avoid two competing term-expansion mechanisms being active at the same time? – Erik Kaplun Jan 24 '22 at 14:59
  • @ErikKaplun The Logtalk compiler is not based on term-expansion. For some details, see https://logtalk.org/manuals/userman/programming.html#multi-pass-compiler Term- and goal-expansion may happen during the compilation of a source file but that's just a *hook* mechanism supported by the compiler. – Paulo Moura Jan 24 '22 at 16:28
  • Right. Ok, so in theory I could write pieces of Logtalk in my Prolog code and have a custom term expander send it to the Logtalk compiler and put the result back in my pure Prolog code. – Erik Kaplun Jan 25 '22 at 07:46
  • @ErikKaplun Given that the Logtalk compiler generates Prolog code and that both Logtalk itself and any Logtalk application can be embedded in a Prolog application, what would be the purpose of such a setup? – Paulo Moura Jan 25 '22 at 10:04
  • Just to be able to define Logtalk objects inline I guess. But I can also put `.lgt` files straight alongside the `.pl` files and load into pure Prolog from there directly, without having to do a separate `lgt` compilation step, right? – Erik Kaplun Jan 26 '22 at 12:32
  • @ErikKaplun You always need to compile the Logtalk source files using the Logtalk compiler. But you can also load the Prolog files from the same Logtalk loader file and using the Logtalk load predicates. – Paulo Moura Jan 26 '22 at 14:05
7

Prolog modules can be trivially interpreted as objects (specifically, as prototypes). Prolog modules can be dynamically created, have a name that can be regarded as their identity (as it must be unique in a running session as the module namespace is flat), and can have dynamic state (using dynamic predicates local to the module). In most systems, however, they provide weak encapsulation in the sense that you can usually call any module predicate using explicit qualification (that said, at least one system, ECLiPSe, allows you to lock a module to prevent breaking encapsulation this way). There's also no support for separating interface from implementation or having multiple implementations of the same interface (you can somehow hack it, depending on the Prolog module system, but it's not pretty).

Logtalk, as mentioned in other answers, is a highly portable object-oriented extension to Prolog supporting most systems, including SWI-Prolog. Logtalk objects subsume Prolog modules, both from a conceptual and a practical point-of-view. The Logtalk compiler supports a common core of module features. You can use it e.g. to write module code in Prolog implementations without a module system. Logtalk can compile modules as objects and supports bi-directional calls between objects and modules.

Note that objects in Logic Programming are best seen as a code encapsulation and code reuse mechanism. Just like modules. OO concepts can be (and have been) successfully applied in other programming paradigms, including functional and logic. But that doesn't mean necessarily bringing along imperative/procedural concepts. As an example, the relations between an instance and its class or between a prototype as its parent can be interpreted as specifying a pattern of code reuse instead of being seen from a dynamic/state point-of-view (in fact, in OOP languages derived from imperative/procedural languages, an instance is little more than a glorified dynamic data structure whose specification is distributed between its class and its class superclasses).

Considering your sample code, you can recode it easily in Logtalk close to your formulation but also in other ways, the most interesting of them making use of no dynamic features. Storing state (as in dynamic state) is sometimes necessary and may even be the best solution for particular problems (Prolog have dynamic predicates for a reason!) but should be used with care and only when truly necessary. Using Logtalk doesn't change (nor intends to change) that.

I suggest you look into the extensive Logtalk documentation and its numerous programming examples. There you will find how to e.g. cleanly separate interface from implementation, how to use composition, inheritance, specialize or override inherited predicates, etc.

Erik Kaplun
  • 37,128
  • 15
  • 99
  • 111
Paulo Moura
  • 18,373
  • 3
  • 23
  • 33
  • 2
    Some years ago I tried to bend the 'dynamic module' implementation into something of practical use, following [the documentation](http://www.swi-prolog.org/pldoc/man?section=dynamic-modules), but I had a bad experience, so I preferred not to advise the OP about that possibility. – CapelliC Jan 26 '15 at 21:58
3

Logtalk is effectively the prominent object oriented Prolog available today. Paulo made it available as a pack, so installing should be very easy.

Modules are not really appropriate for object orientation. They are more similar to namespaces, but without nesting. Also, the ISO standard it's a bit controversy.

SWI-Prolog v7 introduced dicts, an extension that at least handles an historical problem of the language, and make available 'fields' by name, and a syntax for 'methods'. But still, no inheritance...

edit

I've added here a small example of object orientation in SWI-Prolog. It's an evolution of my test application about creating genealogy trees.

Comparing the genealogy.pl sources, you can appreciate how the latest version uses the module specifier, instead of the directive :- multifile, and then can work with multiple trees.

You can see, the calling module is passed down the graph construction code, and have optional or mandatory predicates, that gets called by module qualification:

make_rank(M, RPs, Rp-P) :-
    findall(G, M:parent_child(P, G), Gs),
    maplist(generated(M, Rp, RPs), Gs).

optional predicates must be called like

...
catch(M:female(P),_,fail) -> C = red
...

Note that predicates are not exported by the applicative modules. Exporting them, AFAIK, breaks the object orientation.

==========

Another, maybe more trivial, example of of object orientation, it's the module pqGraphviz_emu, where I crafted a simple minded replacement of system level objects.

I explain: pqGraphviz it's a tiny layer - written in Qt - over Graphviz library. Graphviz - albeit in C - has an object oriented interface. Indeed, the API allows to create relevant objects (graphs, nodes, links) and then assign attributes to them. My layer attempts to keep the API most similar to the original. For instance, Graphviz creates a node with

Agnode_t* agnode(Agraph_t*,char*,int);

then I wrote with the C++ interface

PREDICATE(agnode, 4) {
    if (Agnode_t* N = agnode(graph(PL_A1), CP(PL_A2), PL_A3))
        return PL_A4 = N;
    return false;
}

We exchange pointers, and I have setup the Qt metatype facility to handle the typing... but since the interface is rather low level, I usually have a tiny middle layer that exposes a more applicative view, and it's this middle level interface that gets called from genealogy.pl:

make_node(G, Id, Np) :-
    make_node(G, Id, [], Np).
make_node(G, Id, As, Np) :-
    empty(node, N0),
    term_to_atom(Id, IdW),
    N = N0.put(id, IdW),
    alloc_new(N, Np),
    set_attrs(Np, As),
    dladd(G, nodes, Np).

In this snippet, you can see an example of the SWI-Prolog v7 dicts:

...
N = N0.put(id, IdW),
...

The memory allocation schema is handled in allocator.pl.

CapelliC
  • 59,646
  • 5
  • 47
  • 90
  • For beginners, installing Logtalk using the provided installers (they are available for most operating-systems) provides a better user experience. The pack makes the installation very easy but also kind of hides the installation directory where the docs, examples, tools, etc, are to be found (see the pack description). – Paulo Moura Jan 26 '15 at 21:20
2

Have a look at logtalk. It is kind of an object-oriented extension to Prolog.

http://logtalk.org/

schrobe
  • 767
  • 2
  • 8
  • 29
2

the PCE system in SWI-Prolog is also an option for OOP in Prolog. It's usually associated with xpce, the GUI system, but it's actually a general purpose class based OO system.

Anniepoo
  • 2,152
  • 17
  • 17
0

Nowadays, SWI prolog has dicts which interact with the modules in a nice way. See The SWI prolog manual page on dicts, especially section 5.4.1.1: User defined functions on dicts.

This allows you to define things that look exactly like methods, up to returning values (unusual but very useful in Prolog).

Unlike discussed in some of the other answers, I personally find the logic programming and OOP paradigms to be orthogonal to each other: it definitely doesn't hurt to be able to structure your logic code using the OOP modularity...

tjltjl
  • 1,479
  • 8
  • 18
0

There is something called context.pl implemented as part of another, unrelated project. Unlike Logtalk, it doesn't require compilation, but it definitely has only a fraction of Logtalk's features:

Context is an object-oriented programming paradigm for Prolog. It implements contexts (namespaces), classes and instances. It supports various inheritance mechanisms. Access to member predicates is regulated through public/protected & private meta-predicates. We enable declarative static typing of class data members.

/.../

CONTEXT implements a declarative contextual logic programming paradigm that aims to facilitate Prolog software engineering. Short description:

  1. We split up the global Prolog namespace into contexts, each having their own facts and rules.
  2. We create a meta-language allowing you to declare metadata about facts and rules in a context.
  3. We implement Classes and Instances, Public, Protected and Private meta-predicates. We implement (Multiple) inheritance and cloning. We implement operators enabling interaction with context.
Erik Kaplun
  • 37,128
  • 15
  • 99
  • 111