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.

Looks like delegation without a behalf, i.e. a SELF:

How would you do delegation on behalf? Like:

dog::bark :- write(SELF), write(': woof), nl.

fido::inherits(dog).

?- fido::bark.

Expected output:

fido: woof

Interestingly there are like a dozen schools how to do it…

1 Like
:- 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

How difficult would it be to marry the SWI-Prolog dicts
school with the JavaScript prototype school?

Inheritance and the prototype
https://developer.mozilla.org/en-US/docs/Web/JavaScript/Guide/Inheritance_and_the_prototype_chain

In your take things are fact based. But how about storing
all information more dynamically in SWI-Prolog dicts terms?
Here is an idea for a method handle, without yet using inheritance,

but illustrating another idea, i.e. methods as fixpoints via
cyclic terms. First without using a “method handle” in the dict:

?- DogWithoutMethod = #{name:'Fido'}.
DogWithoutMethod = #{name:'Fido'}.

Second with using a “method handle” in the dict:

method(Self) :- write(Self.name), nl.

?- DogWithMethod = #{name:'Fido', bark:method(DogWithMethod)}, 
   call(DogWithMethod.bark).
Fido
DogWithMethod = #{bark:method(DogWithMethod), name:'Fido'}.

Edit 26.05.2025
Or with a syntactic extension in SWI-Prolog, that does not
yet work but could work. Note the () after field accessor .bark:

?- DogWithMethod = #{age:123,name:'Fido',
   bark:method(DogWithMethod)}, DogWithMethod.bark().
ERROR: Unknown procedure: ('.')/2

The above is already syntactically accepted in SWI-Prolog.
But doesn’t work yet semantically. So methods stored directly
or indirectly via prototype chain does not yet work. It only works

again with facts as in 5.4.1.1 User defined functions on dicts.

1 Like