5

To elaborate on a discussion in the comments below my last question: I am looking for suggestions on techniques or best practices for structuring SWI-Prolog code in order to be able to use and test alternative, interchangeable implementations of algorithms and their supporting modules.

The current situation can be illustrated using the following small, ficticous example: The user provides some input data (file data.pl) and loads a module with an algorithm to be applied (file graph.pl). The algorithm module itself uses helper predicates from another module (file path.pl) which in turn requires access to the user-provided data:

File 'data.pl' (input data set):

:- use_module(graph).

edge(a,b).
edge(b,c).
edge(c,d).

File 'graph.pl' (algorithm):

:- module(graph, [reachable/2]).
:- use_module(path).

reachable(X,Y) :-
    path(X,Y), !.
reachable(X,Y) :-
    path(Y,X), !.

File 'path.pl' (module with helper predicates, notice it accessing the data in user):

:- module(path, [path/2]).

path(X,X).
path(X,Y) :-
    user:edge(X,Z),
    path(Z,Y).

For the use case of applying the algorithm to a single input data set and the single implementation of the algorithm, this is perfectly fine:

?- [data].
true.

?- reachable(a,a).
true.

?- reachable(a,d).
true.

?- reachable(d,a).
true.

Now suppose that I have a larger number of data sets, and multiple alternative implementations of the graph and path modules (with the same interface, i.e., exported predicates). For the sake of the (small) example, let us assume we files data files data1.pl, data2.pl, helper predicate modules path1.pl, path2.pl, and algorithm modules graph1, graph2.pl.

I want to automate testing these using SWI-Prolog unit tests, and preferably be able to write a test suite that supports both the differing data sets and the different module implementations, without the need to restart Prolog in between. That is to say I want to be able test all combinations in the Cartesian product

{data1.pl, data2.pl} x {path1.pl, path2.pl} x {graph1.pl, graph2.pl}

without copy-pasting/duplicating code.

My question is: How would I go about this in SWI-Prolog? Are there best practices, design patterns or the like on how to structure code into modules for this purpose? Should I perhaps make use of dynamic importing for switching between alternative algorithm modules, and simply use setup and cleanup in unit tests for the data?

Jens Classen
  • 176
  • 10
  • I am not sure about using the `user` module like this. Altogether, why are you not using `use_module` instead of "consulting" with `[ ]`? I think the manual should explain the differences. – User9213 Aug 04 '19 at 06:42
  • Yes, the explicit reference to `user` is definitely not ideal. I guess the reasoning behind this was that the user would define their data in user space, may import different modules with algorithms all of which can then work on this data. – Jens Classen Aug 05 '19 at 21:35
  • Not sure if this could be useful at all, but https://www.swi-prolog.org/pldoc/man?predicate=include/1 – Erik Kaplun Jan 30 '21 at 11:39
  • @ErikKaplun No, that's not useful at all, that's just a link to the documentation of the include/1 predicate. – Jens Classen Jan 30 '21 at 20:13

3 Answers3

2

First, you have meta-predicates. Those should allow you to pass as arguments both the data and the building blocks of your algorithms. Take a look at this example. I wouldn't try anything more complicated until absolutely certain that this approach is not good enough.

Then, have you looked carefully at dynamic modules and the export/import interface?

Finally, you can always fall back to manually managing the database with assert, retract, abolish and so on. If you do that you could avoid the module system altogether.

But try doing it with meta-predicates first. Those are the obvious mechanism for "generic algorithms" in Prolog.


Some code. First, what can you do with unit test boxes? Well, you can do the following. Here are three modules:

$ cat foo.pl
:- module(foo, [x/1]).

x(foo).
$ cat bar.pl
:- module(bar, [x/1]).

x(bar).
$ cat baz.pl
:- module(baz, []).

:- begin_tests(foo).
:- use_module(foo).

test(x) :- x(foo).

:- end_tests(foo).

:- begin_tests(bar).
:- use_module(bar).

test(x) :- x(bar).

:- end_tests(bar).

The last module, baz, doesn't yet export anything, but it does have two separate unit test boxes. Loading the module and running the tests:

$ swipl
Welcome to SWI-Prolog (threaded, 64 bits, version 8.1.10-59-g09a7d554d-DIRTY)
SWI-Prolog comes with ABSOLUTELY NO WARRANTY. This is free software.
Please run ?- license. for legal details.

For online help and background, visit http://www.swi-prolog.org
For built-in help, use ?- help(Topic). or ?- apropos(Word).

?- use_module(baz).
true.

?- run_tests.
% PL-Unit: foo . done
% PL-Unit: bar . done
% All 2 tests passed
true.

So apparently unit text boxes do let you have scopes.

To clarify, the point is that you can have client code without meta-calls (so no additional arguments) that assumes an interface (in the example, the call to x/1). Then, you can test different implementations of the same interface by importing the two competing modules in two separate unit test boxes within the same file.

All of that seems to be doable with Logtalk in a cleaner way anyway.

User9213
  • 1,316
  • 6
  • 12
  • Thanks for the pointers. I guess dynamic modules are more suitable where one wants to generate modules "on the fly", but in this case, we want to simply be able to take user data files, each of which represents a known problem instance along with the expected solution/output, and check whether our algorithms' implementation(s) indeed yield the desired result. For this reason, assert/retract/abolish should be avoided as well in my opinion. – Jens Classen Aug 05 '19 at 22:02
  • At the moment, I also don't see how exactly dynamic modules would help (to be honest I have a bit of a hard time understanding the documentation, and it seems [I am not the only one](http://yfl.bahmanm.com/Members/ttmrichter/yfl-blog/meta-predicates-in-swi-prolog)). – Jens Classen Aug 05 '19 at 22:03
  • 1
    @JensClassen And yet: did you understand the meta-predicate approach? This is also what the answer by PauloMoura seems to suggest before going into another direction. I did not take the time to show how exactly to code it; I could do (add a bit of code to the answer) it if you think you did not quite understand it. – User9213 Aug 06 '19 at 04:29
  • @User9213 A meta-predicate would indeed allow to pass at runtime the data or algorithm locations (and also their functors). But this approach is cumbersome when you want to pass **both** locations. A unit test can easily call `call/N` with a closure for the algorithm location **but** then another closure argument is required to also pass the data location to a modified `reachable` predicate that would in turn pass it to a modified `path` predicate that's the one that actually calls the data predicates. This solution doesn't scale. But do expand your answer with code so that we can compare. – Paulo Moura Aug 06 '19 at 11:37
  • @User9213 I noticed two of your comments vanishing but assumed you deleted them after updating your answer. No idea of what's happening. Sorry to see you go and thanks for your contributions. – Paulo Moura Aug 07 '19 at 09:21
  • @User9213 The code you posted doesn't mention any meta-predicates, so I don't see what your point is? It also does not reflect the situation I described in my question: Multiple different implementations of an algorithm, each in its own module, multiple different helper predicates for the algorithm, each in its own separate module, and multiple different data sets, (currently) in `user` space, that the aforementioned modules need to access. If all you have is separate modules with no connection between them whatsoever, there is of course no problem devising unit tests for them... – Jens Classen Aug 12 '19 at 21:12
  • @User9213 Perhaps you could illustrate your solution idea using the concrete, minimal example that I provided in my question? – Jens Classen Aug 12 '19 at 21:16
  • 1
    @JensClassen I was about to, but my answers attract negative attention and my comments mysteriously disappear, which is bad, since there is sometimes relevant information there that didn't fit in the Q/A format of Stackoverflow. I tried to explain this in a comment and it disappeared :-( but to cut a long story short, I don't feel like pouring time into this any more. I would highly suggest you come with such questions to the SWI-Prolog mailing list, now on discourse: https://swi-prolog.discourse.group/ which is at least not that heavily censored. – User9213 Aug 13 '19 at 06:55
  • 1
    @JensClassen the code that is currently in the answer shows that you can have modules with identical interfaces (exports); then you can import them into different test unit boxes within the same file, to test the different implementations. Sorry if this was unclear. Altogether, such somewhat open-end questions are not easy to answer on Stackoverflow which has very strict guidelines about what constitutes a good question and a good answer. The [prolog] tag has been relatively relaxed about it but apparently not any longer. I still wonder who disliked Paulo's answer, and why. – User9213 Aug 13 '19 at 07:00
  • 1
    @User9213 The disappearing comments and down voting is indeed strange. I for one certainly am grateful for all of the answers and appreciate the effort you and the others put into them. – Jens Classen Aug 15 '19 at 17:32
  • @User9213 And just to clarify: What distinguishes the foo/bar example you posted from the minimal example in my original question is that in the former, there are no dependencies between the different modules, and so writing separate unit tests for them is more or less straightforward. I edited my question to emphasize that it is about the different parts depending on one another, and I want to be able to test different combinations of module implementations and data sets. – Jens Classen Aug 15 '19 at 17:57
2

In order to apply the same set of tests to different implementations of the same predicates, or, more generically, to different implementations of the same interface/protocol, the tests must take the implementation as a dynamic parameter. Ideally, we should also be able to test the different algorithm implementations with different datasets.

A separate concern is how to organize the data and the algorithms that we want to run on the data. There are two sensible approaches. The first option is to view the data as importing or inheriting the algorithm implementations. In this case, the queries (e.g. reachable/2) would be sent to the data. A downside of this solution is that we may need to update the datasets everytime we want to apply a different set of algorithms (e.g. by importing a different module).

The second option is to view the data as a parameter of the algorithms. An easy implementation of this solution would be to add an extra argument to the predicates (e.g. the path and reachable predicates) that would be used to pass a reference to the data (e.g. user in the simple case mentioned in the question). A downside of this solution is that all algorithm related predicates would need the extra parameter (e.g. reachable/2 only calls path/2 and is only this predicate that actually calls edge/2).

All the above questions and corresponding alternative solutions can be easily and cleanly expressed using Logtalk parametric objects instead of Prolog modules and using Logtalk unit test framework, lgtunit, which supports parameterized tests out-of-the-box. Follows an example solution (which is portable and can be used with most Prolog systems).

First, let's make data only about the data. We start by defining a protocol/interface for all data objects:

:- protocol(graph_protocol).

    :- public(edge/2).
    ...

:- end_protocol.

All data objects would implement this protocol. For example:

:- object(graph1,
    implements(graph_protocol)).

    edge(a,b).
    edge(b,c).
    edge(c,d).

:- end_object.

Next, let's define parametric objects holding the algorithms with the single parameter being to pass the dataset object. These objects would likely also implement defined protocols specifying the predicates for which we want to provide alternative implementations. These protocols are omitted here for brevity.

:- object(path(_Data_)).

    :- uses(_Data_, [edge/2]).

    :- public(path/2).
    path(X,X).
    path(X,Y) :-
        edge(X,Z),
        path(Z,Y).

:- end_object.


:- object(reachable(_Data_)).

    :- uses(path(_Data_), [path/2]).

    :- public(reachable/2).
    reachable(X,Y) :-
        path(X,Y), !.
    reachable(X,Y) :-
        path(Y,X), !.

:- end_object.

Note that these objects use your predicate definitions as-is (the uses/2 directive in the reachable/1 object requires Logtalk 3.28.0 or later version).

The default case where the dataset is loaded into user can be simplified by defining:

:- object(reachable ,
    extends(reachable(user))).

:- end_object.

A typical query would be:

?- reachable(graph1)::reachable(a,d).
...

So far, we're only parameterizing the datasets, not the algorithms. We will get there. The tests could be defined also as a parametric object. For example:

:- object(tests(_Data_),
    extends(lgtunit)).

    :- uses(reachable(_Data_), [reachable/2]).

    test(r1) :-
        reachable(a,a).

    test(r2) :-
        reachable(a,d).

    test(r3) :-
        reachable(d,a).

:- end_object.

Testing over multiple datasets would use a goal such as:

lgtunit::run_test_sets([
    tests(graph1),
    tests(graph2),
    tests(graph3)
])

The original question focused on test alternative, interchangeable implementations of algorithms. But the solution is the same. We just need to modify the parametric tests object to take instead the object implementing the algorithm being tested as a parameter:

:- object(tests(_Algorithm_),
    extends(lgtunit)).

    :- uses(_Algorithm_, [reachable/2]).

    cover(reachable(_)).
    cover(path(_)).

    test(r1) :-
        reachable(a,a).

    test(r2) :-
        reachable(a,d).

    test(r3) :-
        reachable(d,a).

:- end_object.

And then, on the query that runs the tests, use whatever combination we want of datasets and algorithms. For example:

lgtunit::run_test_sets([
    tests(reachable1(graph1)), tests(reachable2(graph1)), 
    tests(reachable1(graph2)), tests(reachable2(graph2)),
    ...
])

The list argument of the lgtunit::run_test_sets/1 predicate can also be dynamically created. For example, assuming that all alternative implementations of the reachable/2 predicate implement a reachable_protocol protocol, the test goal could be:

datasets(Datasets),
findall(
    tests(Algorithm),
    (   implements_protocol(Algorithm, reachable_protocol),
        member(Dataset, Datasets),
        arg(1, Algorithm, Dataset)
    ),
    TestObjects
),
lgtunit::run_test_sets(TestObjects)

One noteworthy aspect of running these tests using lgtunit is that, besides, reporting the passed and failed tests, it's also trivial to report full predicate code coverage at the predicate clause level. This means that we not only test the algorithms but also check that all clauses used to implement the algorithms are being used. For this example, using only the graph1 dataset, the test output at the top-level interpreter is:

?- {tester}.
% 
% tests started at 2019/8/5, 7:17:46
% 
% running tests from object tests(graph1)
% file: /Users/pmoura/Desktop/plu/tests.lgt
% 
% g1: success
% g2: success
% g3: success
% 
% 3 tests: 0 skipped, 3 passed, 0 failed
% completed tests from object tests(graph1)
% 
% 
% clause coverage ratio and covered clauses per entity predicate
% 
% path(A): path/2 - 2/2 - (all)
% path(A): 2 out of 2 clauses covered, 100.000000% coverage
% 
% reachable(A): reachable/2 - 2/2 - (all)
% reachable(A): 2 out of 2 clauses covered, 100.000000% coverage
% 
% 2 entities declared as covered containing 4 clauses
% 2 out of 2 entities covered, 100.000000% entity coverage
% 4 out of 4 clauses covered, 100.000000% clause coverage
% 
% tests ended at 2019/8/5, 7:17:46
% 
true.

If you're automating tests (e.g. using a CI server), you can use instead the logtalk_tester script.

What if we want to keep using modules for datasets and/or the algorithms? For the tests object, it's just a question of writing instead:

:- object(tests(_Algorithm_),
    extends(lgtunit)).

    :- use_module(_Algorithm_, [reachable/2]).
    ...

:- end_object.

Logtalk's lgtunit supports testing plain Prolog code and Prolog modules code, besides Logtalk code (indeed, the Logtalk distribution includes a Prolog standards conformance test suite). For a tool overview, see e.g.

https://logtalk.org/tools.html#testing

At the above URL, we'll also find a code coverage report example. For full code example of using the solution sketched above see e.g.

https://github.com/LogtalkDotOrg/logtalk3/tree/master/library/dictionaries

This library provides three alternative implementations of a dictionary API and a single set of tests (using a parametric object) to test all of them.

Last, but not the least, you can use this testing solution with not only SWI-Prolog but also +10 other Prolog systems.

Paulo Moura
  • 18,373
  • 3
  • 23
  • 33
  • Thanks for this very elaborate answer. It seems Logtalk does everything I need, and when one knows a bit or two about object orientation, the learning curve shouldn't be too steep. I'm a little worried though that this nonetheless would constitute some significant overhead in effort, and that it introduces yet another dependency into the code, but that may be price worth paying to keep things manageable in the future. – Jens Classen Aug 05 '19 at 21:32
  • You welcome. There are several learning resources in and linked from the Logtalk website, including a short tutorial. While Logtalk adds another dependency, it may also give your application (depending on its details) a degree of portability that would allow you to try it with multiple Prolog systems (there are a few, besides SWI-Prolog, that are also quite good). – Paulo Moura Aug 05 '19 at 21:58
0

For Unit Tests, absolutely use setup/1 and cleanup/1, you want your test cases with your tests.

For your own exploration and for flexibility, re-jig your dependency tree, you don't want to be calling predicates with the user namespace as it won't work when your imports get more complex or shifted around. The algorithm relies on the utility predicates, which then requires the data that it operates on.

File 'data.pl' (input data set):

:- module(data, [edge/2]).

edge(a,b).
edge(b,c).
edge(c,d).

File 'graph.pl' (algorithm):

:- module(graph, [reachable/2]).
:- use_module(path).

reachable(X,Y) :-
    path(X,Y), !.
reachable(X,Y) :-
    path(Y,X), !.

File 'path.pl' (module with helper predicates, notice it accessing the data in the used module):

:- module(path, [path/2]).
:- use_module(data).

path(X,X).
path(X,Y) :-
    edge(X,Z),
    path(Z,Y).

Now you can swipl -g "reachable(a, d)" -s graph.pl. This'll let you easily change the data module used in path.pl. If you wished, you could dynamically load the module here with a predicate, but better to make use of setup/cleanup in unit tests:

:- dynamic path:edge/2.

/* Testing Graph
a→b→c→d 
*/
setup :-
    asserta(path:edge(a,b)),
    asserta(path:edge(b,c)),
    asserta(path:edge(c,d)).
cleanup :-
    retractall(path:edge(_, _)).

test(reach_same,
    [ true(A, a)
    , setup(setup)
    , cleanup(cleanup)
    , nondet
    ]
 ) :-
     reachable(a, A).
Paul Brown
  • 2,235
  • 12
  • 18
  • The `dynamic(path:edge/2)` directive is a terrible hack. It would be bad enough if `edge/2` was a predicate exported by the `path` module. But it's worse: `edge/2` is a predicate used implicitly by the `path` module from another module. To be clear, changing the directive to `dynamic(data:edge/2)` is still a terrible hack as you would still be changing the property of an exported predicate from outside the module that exports it. – Paulo Moura Aug 04 '19 at 06:18
  • Yes, but just for the unit tests, so module path can be tested distinctly from it's dependencies. – Paul Brown Aug 04 '19 at 08:40
  • Thanks for the suggestion. Indeed we should make use of the setup and cleanup procedures, and the explicit reference to `user` should be avoided. However, I have to agree with Paulo that asserting the user data as a dynamic predicate does not seem like a good idea, for at least two reasons: It will in reality be more data than just 3 facts (think more like 100), and also it appears to be a case of (undesirable) duplicate code when we have to assert the same facts again that are already defined in the user data module. – Jens Classen Aug 05 '19 at 20:52
  • Then wrap the data source into a predicate in path: `mount_data(Source) :- use_module(Source).` Then in module `graph` or in unit tests: `:- mount_data(data).` – Paul Brown Aug 05 '19 at 20:55
  • Interesting suggestion (although most systems don't allow using directives as predicates). But you can only use it once: as soon as you load a data source in a given context, you will not be able to load another data source in the same context without restarting (you will get a permission error stating that the predicates are already imported from another module). Thus, testing alternative algorithm implementations and/or alternative datasets seems to imply restarting for each combo (not necessarily a bad thing but not required in the presented Logtalk-based solution). – Paulo Moura Aug 06 '19 at 06:47
  • `library(persistency)` supports mounting and unmounting data. They do so through assert/retract. So for large test data I'd still opt for the dirty hack in vanilla Prolog, use setup to consult the test data and cleanup to retract it. The duplication of data is like mocking your data so you can test the algorithms independent of it: in units. Testing with the actual data is an integration test, and can be done with plunit too. Of course, Logtalk always provides a correct solution whenever module problems arise and for that reason alone it's worth using. – Paul Brown Aug 06 '19 at 09:52
  • @PaulBrown What is striking is that both here in your comments, in your answer, and also linked from user9213 answer, you only show how to test with different datasets while the question (quoting with emphasis mine) is about **be able to use and test alternative, interchangeable implementations of algorithms**. – Paulo Moura Aug 06 '19 at 11:03
  • I ignored the algorithm changing as that'll be for exploration rather than unit testing. But, just like with user9213's answer, the same principle applies. You'd either pass the algorithm predicate into a meta-predicate, but change your code for testing, or assert/retract in your testing environment. You're not wrong though, using Logtalk is the best solution. – Paul Brown Aug 06 '19 at 11:18
  • @PaulBrown If you have a library of alternative algorithm (or data structures) implementations, you need to be able to fully test all of them. Only then you can with confidence explore, experiment, and chose the best one one for a particular application. – Paulo Moura Aug 06 '19 at 11:48