Metaobjects in PROLOG

I wrote a basic implementation for metaobjects in PROLOG, due to the fact that I am always writing PROLOG in an open-polymorphic, example-driven manner, and have to write something of the form fn(ID, Attr) constantly and I just wanted a faster way to do this, especially in live systems, without a bunch of repeating boilerplate.

There is nothing fancy like bitemporality, but perhaps someone might also find this useful. I am very interested in ‘declarative object’ systems.

:- use_module(library(clpfd)).

:- dynamic(slot/3).

call_slot(SlotHead) :-
    SlotHead =.. [_, ID|_],
    call_slot(ID, SlotHead).
    
call_slot(CallerID, SlotHead) :-
    (slot(CallerID, SlotHead, Body)
    -> Body
    ; (slot(CallerID, inherits(CallerID, InheritsID), Body),
       Body,
       call_slot(InheritsID, SlotHead))).

%% slot(0, card_name(ID, ren), true).
%% slot(1, inherits(ID, 0), true).


% ?- call_slot(card_name(1, X)).

slot(0, make_obj(Self, Slots, ID),
     (gensym(obj_, ID),
      call_slot(make_slots(Self, ID, Slots)))).

slot(0, make_slots(_Self, _, []), true).
slot(0, make_slots(Self, ID, [(SlotHead, SlotBody)|Slots]),
     (asserta(slot(ID, SlotHead, SlotBody)),
      call_slot(make_slots(Self, ID, Slots)))).

% ?- trace(call_slot/1).
% ?- trace(call_slot/2).
% ?- trace(slot/3).

% ?- slot(0, make_slots(0, obj_1, [(card_name(_23816), true)]), Body).

% ?- call_slot(make_obj(0, [(card_name(Self), true)], ID)).
%@ ID = obj_1.

% ?- slot(obj_1, Head, Body).
%@ Head = card_name(_),
%@ Body = true.

I do not use logtalk because I usually make extensive use of qsave and logtalk doesn’t support qsave very well. Last time I checked you have to define a special top-level REPL and then mess w a script for the compiler.

Any feedback welcome.

Proof that this is a ‘proper’ MOP-- here’s a simple metaobject that increases a counter whenever it creates an object.


:- module(simple_metaobject_example, []).

:- use_module("../core/core.pl", [call_slot/1, slot/3]).

simple_metaobject_init(MetaObjectID, Slots) :-
    call_slot(make_obj(root,
                       [(make_obj(Self, Slots, ObjID),
                         (call_slot(make_obj(root,
                                             Slots,
                                             ObjID)),
                          call_slot(counter(Self, N)),
                          N1 is N + 1,
                          call_slot(make_slots(Self,
                                               Self,
                                               [(counter(_S, N1), true)])))),
                        (inherits(Self, root), true),
                        (counter(Self, 0), true)],
                       MetaObjectID)),
    findall(Head-Body, slot(MetaObjectID, Head, Body), Slots).

simple_metaobject_make_object(MetaObjectID, NewObj, OldCounter, NewCounter) :-
    call_slot(counter(MetaObjectID, OldCounter)),
    call_slot(make_obj(MetaObjectID, [], NewObj)),
    call_slot(counter(MetaObjectID, NewCounter)).

% ?- simple_metaobject_init(MetaID, Slots), simple_metaobject_make_object(MetaID, NewObj, OldCounter, NewCounter).
%@ Correct to: "simple_metaobject_example:simple_metaobject_init(MetaID,Slots)"? yes
%@ Correct to: "simple_metaobject_example:simple_metaobject_make_object(MetaID,NewObj,OldCounter,NewCounter)"? yes
%@ MetaID = obj_1,
%@ Slots = [counter(_, 0)-true, inherits(_, root)-true, make_obj(_A, _B, _C)-(call_slot(make_obj(root, _B, _C)), call_slot(counter(_A, _D)), _E is _D+1, call_slot(make_slots(_A, _A, [...])))],
%@ NewObj = obj_2,
%@ OldCounter = 0,
%@ NewCounter = 1 ;
%@ false.

:- module(delegation_example, []).

:- use_module("../core/core.pl", [call_slot/1, slot/3]).

dog_init(DogID) :-
    call_slot(make_obj(root,
                       [(woof(Self), (print(Self), nl, print("woof!")))],
                       DogID)).

fido_init(DogID, FidoID) :-
    call_slot(make_obj(root,
                       [(inherits(_Self, DogID), true)],
                      FidoID)).


% ?- dog_init(DogID), fido_init(DogID, FidoID), call_slot(woof(FidoID)).
%@ Correct to: "delegation_example:dog_init(DogID)"? yes
%@ Correct to: "delegation_example:fido_init(DogID,FidoID)"? yes
%@ Correct to: "core:call_slot(woof(FidoID))"? yes
%@ obj_2
%@ "woof!"
%@ DogID = obj_1,
%@ FidoID = obj_2.

Like this. As you can see woof is delegated to dog, but self now references Fido, this is because we pass down the original caller via the predicate within call_slot, but we’re following the inheritance chain for which slot is being called.

One thing I wanna work on later (not right now because it sounds like a rabbit hole) is abstracting hooks around call_slot further and thereby allowing the user to do things like having metaobjects that dictate the execution model – you could do things like have a BFS metaobject! I’ve already experimented w some other things like genserver

server_object_init(ServerID, Slots) :-
    call_slot(make_obj(root,
                       [(state(Self, 0), true),

                        (start(Self, Queue),
                         (message_queue_create(Queue),
                          thread_create(call_slot(server_loop(Self, Queue)), _, [detached]))),

                        (server_loop(Self, Queue),
                         (thread_get_message(Queue, Msg),
                          call_slot(state(Self, State0)),
                          call_slot(handle_message(Self, Msg, State0, State1)),
                          call_slot(make_slots(root, Self, [(state(_, State1), true)])),
                          call_slot(server_loop(Self, Queue)))),

                        (handle_message(Self, inc, N0, N1),
                         N1 is N0 + 1),

                        (handle_message(Self, print, N0, N0),
                         print(N0),
                         nl)],
                       ServerID)),
    findall(Head-Body, slot(ServerID, Head, Body), Slots).

server_object_test(ServerID) :-
    call_slot(start(ServerID, Queue)),
    thread_send_message(Queue, print),
    thread_send_message(Queue, inc),
    thread_send_message(Queue, print).


% ?- server_object_init(ServerID, Slots), server_object_test(ServerID).
%@ Correct to: "server_example:server_object_init(ServerID,Slots)"? yes
%@ Correct to: "server_example:server_object_test(ServerID)"? yes
%@ 0
%@ 1

I feel lost. What do you gain by using this?

Suppose I’m writing a dynamic flashcard system. I want users to be able to add flashcards dynamically to the system. They might also want specific kinds of flashcards to have specific functionality.
Normally I’d do smt like

flashcard_name(ID, name).
flashcard_english(ID, blah).
flashcard_mandarin(ID, char, pinyin).
It makes more sense to have a helper for this. But my helper would only apply to a certain kind of flashcard with certain interfaces. What I really need is a concept of objects. The natural culmination of a relational system is an object system. You’re just reinventing objects in PROLOG at this point.

Logtalk exists to help with this, but its live system capabilities suck.

Wouldn’t this be better:

flashcard(ID, name).
flashcard_lang(ID, english, blah).
flashcard_lang(ID, mandarin, char, pinyin).

i.e. think of what would sensibly be used in a relational database.

That’s a bold claim. How exactly did you mean this?

1 Like

Counter claim: A relational system establishes relations between elements of objects. The typical object system tries to hide elements, making it hard to establish relations. These are not compatible directions.

A relational model establishes relationships between entities: not per chance the relevant notation is the entity-relationship diagram.

The relational model and the object model are indeed incomparable, which in the literature is called the object–relational impedance mismatch (see e.g. the article on Wikipedia – as a starting point only, it is not a great article), and is the reason why O/RM (Object-Relational Mappers) also exist.

All that said, it is indeed dubious that there is anything OO in what the OP is trying to do: related data and maybe rules, that’s the relational model, and it’s indeed the most natural in Prolog…

1 Like

Have you read the third relational manifesto? I can’t really agree that the object model and relational model are in any way incomparable, unless you mean java-style objects with encapsulation and whatnot, and not at all message-passing. Logtalk exists for this reason: it is quite natural.

Nope.

Seems to refer to http://www.thethirdmanifesto.com/ - the paper is https://www.dcs.warwick.ac.uk/~hugh/TTM/DTATRM.pdf , discussed at Databases, Types, and the Relational Model: The Third Manifesto [pdf] | Hacker News

An old version of the paper is available at https://dl.acm.org/doi/pdf/10.1145/202660.202667