How to use predicate sharing the same name from several modules in Prolog
Asked Answered
C

2

8

I am new to Prolog and I'm struggling with the following problem using SWI-Prolog. I have several files dataBase1.pl, dataBase2.pl, ... with the same structure (based on this thread)

:- module(dataBase1,[]).

:- use_module(library(persistency)).

:- persistent 
       predicate1(A:any, B:any),
       predicate2(A:any, B:any).

:- initialization(init).

init :-
        absolute_file_name('dataBase1.db', File, [access(write)]),
        db_attach(File, []).

predicate1/2, predicate2/2 are common to all the database files.

Then, I defined in a third file predicates.pl several clauses which make use of clauses in the previous databases such as testPredicate(A,B) :- predicate1(A,B), predicate2(A,B).

My problem is that I would like above clause to use predicate1/2, predicate2/2 from all the modules corresponding to database files. In the current state, I need to precise the context module in order to use predicate1/2, predicate2/2 (ie dataBase1:predicate1/2, dataBase2:predicate1/2,....)

I can't use use_module/1 as I will add/remove database file dynamically.

Thanks in advance for any advice !

Edit : Following the discussion in the comments, how can I define query-able predicate of the form head(X,Y) :- body() as persistent dynamic predicate ?

Claudette answered 10/1, 2018 at 16:27 Comment(7)
So these predicates are different? I'm sure it makes sense in your head but this is really not good design in Prolog. What can make sense is to have one predicate spread out over several files, and that should work without any problems.Aerie
Thanks for your answer. If I was using only one database file or several files without module, there would be no problem as you said. The problem is that to be able to choose in which database file I want to "assert" my new facts, I had to put each database in separated modules. Using the persistency library, I have to define which predicates would be dynamically added (through the persistent/1) and here comes the trouble.Claudette
If you must call your predicates that are in different modules separately, maybe they shouldn't have the same name? Maybe they should be called db1_predicate1, etc. Or the database name is an argument to the predicate and the predicates do have the same name. Hard to tell here since your use case isn't clear in detail.Roadster
I must call my predicates from different modules because of how works the persistency library, not because of my own need. It would be one possibility to change the predicate name in each module, but then I would have to reflect it in my third file 'predicates.pl'. As I would dynamically create new databases, I would have to also make the 'predicates.pl' persistent and update it accordingly. I checked the documentation, but persistency seems to only apply to facts and not to predicate definition. (But I may be wrong)Claudette
I'm not sure if I am following what you are meaning by "persistency" if you're thinking it's different for facts versus predicates. In Prolog, a predicate is just a term in the database just like fact is. It just so happens that it is a fact of a certain, query-able form: :-( head, body ).Roadster
Predicates can be dynamic as well. E.g., assertz(':-'(foo(X,Y), (...)))..Roadster
Thank you ! During my search, I only saw example of persistency with facts and not with query-able form. So whenever I would create a new database dataBaseN.pl, I will also dynamically create the corresponding predicate version in predicates.pl : testPredicate(A,B) :- dataBaseN:predicate1(A,B), dataBaseN:predicate2(A,B). It seems rather verbose but at least It should work.Claudette
F
1

iirc, you should call predicates using module name as a prefix separated by colon.

http://www.swi-prolog.org/pldoc/man?section=overrule

Ferrochromium answered 21/1, 2019 at 3:49 Comment(0)
B
0

Prolog modules don't provide a sensible solution for the design pattern you're trying to implement. This design pattern is sometimes referred as the "many worlds" pattern. But you can do it easily using in alternative Logtalk objects (you can run Logtalk with most Prolog compilers including SWI-Prolog).

First, define a root object declaring your database predicates:

:- object(database).

    :- public([predicate1/2, predicate2/2]).
    :- dynamic([predicate1/2, predicate2/2]).

:- end_object.

You can have any number of database objects extending this object. To associate a file with each individual database/object, you can simple use an include/1 directive to load the contents of the files into the respective objects when these are loaded. For example:

:- object(db1, extends(database)).

    :- include('db1.db').

:- end_object.


:- object(db2, extends(database)).

    :- include('db2.db').

:- end_object.

You can also easily create dynamic databases:

...,
% ensure the corresponding file exists
open(write, 'db42.db', Stream),
close(Stream),
% create the dynamic database object    
create_object(db42, [extends(database)] [include('db42.db')], []),
...

You also want to be able to make inferences using the different databases:

Then, I defined in a third file predicates.pl several clauses which make use of clauses in the previous databases such as testPredicate(A,B) :- predicate1(A,B), predicate2(A,B).

You can do it easily by defining the testPredicate/2 predicate in the root object, which becomes:

:- object(database).

    :- public([predicate1/2, predicate2/2]).

    :- public(testPredicate/2).
    testPredicate(A,B) :-
        ::predicate1(A,B),
        ::predicate2(A,B).

:- end_object.

The ::/1 is Logtalk's message to self control construct. This means that in a goal such as:

?- db1::testPredicate(A,B).

the predicate1/2 and predicate2/2 will be called in db1 while in the goal:

?- db2::testPredicate(A,B).

the predicate1/2 and predicate2/2 will be called in db2. To modify a database dynamic predicates, simply use the assert and retract messages to the database objects. For example:

?- db42::assertz(predicate1(foo,bar)).
...

Finally, you want to persist the database dynamic predicates. We can e.g add a predicate to the root object that saves all databases to the respective files. For example (assuming the database predicate clauses are facts):

    :- public(save/0).
    save :-
        this(This),
        forall(
            extends_object(Database, This),
            save(This)
        ).

    save(Database) :-
        atom_concat(Database, '.db', File),
        open(File, write, Stream),
        save_predicates(Database, Stream),
        close(Stream).

    save_predicates(Database, Stream) :-
        current_predicate(Functor/Arity),
        functor(Template, Functor, Arity),
        predicate_property(Template, (dynamic)),
        write_canonical(Stream, (:- dynamic(Functor/Arity))), write('.\n),
        Database::clause(Template, true),
        write_canonical(Stream, Template), write('.\n),
        fail.
    save_predicates(_, _).

To save all databases, you simply call the goal database::save. Note that the sketched solution is fully portable. you can use with any of the Logtalk supported Prolog compilers.

Balliett answered 21/1, 2019 at 10:20 Comment(0)

© 2022 - 2024 — McMap. All rights reserved.