Meta-interpreter with modules and meta-predicates

Hello,
Did anyone write a meta-interpreter capable of interpreting swi-prolog code that use modules and meta-predicates ?

Here is test case that the meta-interpreter should be able to interpret:

% mylib.pl
:- module(mylib, [mypred/1]).

mypred(true) :-
    myprivatepred.

myprivatepred.
% main.pl
:- use_module(library(apply)).
:- use_module(mylib).

main :-
    maplist(mypred, [true, true]).
% meta interpreter mi/1 should succeed
?- mi(main).
true

Is there a meta-predicate involved? I don’t see a reference to meta_predicate/1 to define any.

yes, maplist/2 is a meta-predicate that should be interpreted.

See ‘$meta_call’/1 in boot/init.pl. This is used to deal with meta-calling in the system when inside a delimited continuation as we cannot use the normal mechanism in that case. It handles modules, control structures and cuts.

1 Like

Thank you for this interesting predicates.
I also tried to make my mi a meta_predicate and use the builtin module resolver but I couldn’t make it work reliably.

Here is my own attempt at this by explicitly reifying the context module in an argument of the meta interpreter, if anyone is interested in comments and remarks:

:- module(mi, [mi/1, mi/2]).

mi(Goal) :-
    mi(user, Goal).

mi(_, true) => true.
mi(Ctx, (A, B)) =>
    mi(Ctx, A),
    mi(Ctx, B).
mi(Ctx, Goal) =>
    qualify_meta_predicate(Ctx, Goal, NewGoal),
    meta_call(Ctx, NewGoal, Ctx1, Goal1),
    imported_from(Ctx1, Goal1, Ctx2, Goal2),
    @(clause(Goal2, Body), Ctx2),
    mi(Ctx2, Body).

Basically, to correctly interpret meta predicate, one has to:

  1. qualify goal arguments of meta predicates with the context module at the calling site
  2. unwrap call(mygoal, Arg) to mygoal(Arg)
  3. resolve the implementation module of imported predicate

Did I forget anything ?
This mi pass the test case I wrote above.

The @/2 predicate is a lifesaver in this case to manipulate the context module for helper predicates like clause, predicate_property or strip_module.

Here are the helper predicates used in the last clause of mi/2:

meta_call(Ctx, Goal, NewCtx, NewGoal),
        strip_module(Goal, _, Call), Call =.. [call, SubGoal | Args] =>
    add_args(SubGoal, Args, NewSubGoal),
    @(strip_module(NewSubGoal, NewCtx, NewGoal), Ctx).
meta_call(Ctx, Goal, NewCtx, NewGoal) =>
    NewCtx = Ctx, NewGoal = Goal.

imported_from(Ctx, Goal, NewCtx, NewGoal),
        @(predicate_property(Goal, imported_from(From)), Ctx) =>
    NewCtx = From,
    strip_module(Goal, _, NewGoal).
imported_from(Ctx, Goal, NewCtx, NewGoal) =>
    NewCtx = Ctx, NewGoal = Goal.

qualify_meta_predicate(Ctx, Goal, NewGoal),
        @(predicate_property(Goal, meta_predicate(Spec)), Ctx) =>
    Goal =.. [Name | GoalArgs],
    Spec =.. [Name | SpecArgs],
    maplist(qualify_arg(Ctx), GoalArgs, SpecArgs, NewArgs),
    NewGoal =.. [Name | NewArgs].
qualify_meta_predicate(_, Goal, NewGoal) =>
    NewGoal = Goal.

qualify_arg(_, Mod:Goal, Spec, R), number(Spec) =>
    R = Mod:Goal.
qualify_arg(Ctx, Goal, Spec, R), number(Spec) =>
    R = Ctx:Goal.
qualify_arg(_, Arg, _, R) => R = Arg.

add_args(Mod:Goal, AdditionalArgs, R) =>
    add_args(Goal, AdditionalArgs, NewGoal),
    R = Mod:NewGoal.
add_args(Goal, AdditionalArgs, NewGoal) =>
    Goal =.. [Name | Args],
    append(Args, AdditionalArgs, NewArgs),
    NewGoal =.. [Name | NewArgs].

Yeah. ‘$meta_call’/1 only deals with dealing with a body term and unwrapping the control structures. If you want the fill Monty you’ll need to deal meta predicates. It is rather complicated. library(prolog_codewalk) may be of some help, notably walk_meta_call/7.

I don’t know your ultimate aim. Sometimes there are easier ways then meta-interpreting.

So, my goal with this:

I suspect that the use of my new units library will incur quite a lot of runtime cost, since every qeval calls will have to parse the expression, resolve unit and quantity compatibility and finally do the arithmetic.
The original mp-units c++ library is actually a compile time library, and so I thought that I could do partial evaluation of prolog code in order to compile time evaluate all qeval calls.
This would resolve all units and quantities and inline resulting arithmetic expression.

  • The pros is that one can use the units library in a larger application, without incurring additional runtime cost
  • The cons is that meta interpreting is very complicated to do correctly…

Another slightly different way would be to unroll all qeval calls of the partially evaluated goal, but that would mean that the whole goal would run at compile time, which would limit its use.

If anyone has a better idea in how to do this, I would be very glad to hear it.

I believe that using the built-in term expansion would be of limited use, since every qeval calls would have to be fully annotated with units and quantities.

I do not connect these dots. I see the use of partial evaluation. Meta-interpreting is runtime, but then slower.

For partial evaluation you have goal_expansion/2, or if you need to get multiple calls involved, term_expansion/2. If you really want you can collect all clauses of a predicate/file and rewrite them as a whole. E.g., CHR does this.

A new option is to optimize a predicate by creating an optimized version (collect the clauses using clause/2 and rewrite) and use wrap_predicate/4 to make the original call your optimized version.

I’m probably missing something. If so, a little example may help :slight_smile:

Isn’t partial evaluation a form of meta-interpretation at compile-time ?

So, my very vague need is that I would like to make my units library a zero cost abstraction (like in c++).

Here is an example of what I would like to achieve.
Let’s say that the user wants to do some physics computation with a known set of units.
There is quite a lot of code and arithmetic to do, so using units will add a lot of safety to the code.
But making all those qeval calls at runtime slows the code too much (very vague, I know):

% code doing physics computation, should be able to use all prolog constructs:
% multiple predicates, modules, meta-predicates, disjunctions, recursion, etc
avg_speed(Distance, Time, Speed) :-
   qeval(Speed is Distance / Time as isq:speed).

% compile avg_speed/3 with a specific set of units
:- compile(avg_speed(_*m, _*s, _*inch/hour)).

% my guess of what avg_speed/3 should be compile to:
avg_speed(Distance, Time, Speed) :-
   Speed is Distance*3*12*60**2*10000/(Time*9144)

Unfortunately, this is not a complete example. I know I should be more precise, but I hope I clarified things a little.

Not in my vocabulary. They are in my view more the opposite. anyway, that is irrelevant.

Thanks for the example. That clarifies a little. But, how is avg_speed/3 called? Using numbers? Or using terms, i.e.,

 ?- avg_speed(10*m, 1*s, Avg*inch/hour).

If this is the case, you can redefine this as

avg_speed(Distance, Time, Speed) :-
     avg_speed_expression(Distance, Time, Speed, Expression),
     eval(Expression).

Where avg_speed_expression/3 produces an expression ready for clpBNR, native arithmetic, … Now, you can cache the heavy lifting in avg_speed_expression/4 and you’d get fair performance. I’m afraid the above outline is not very precise and I’d need more time to figure out the details, but I have good hope that you get the idea and either like it or dislike it with some good reason. This schema is slower than full compilation, but also much more flexible.

1 Like

Sorry for mixing up the vocabulary, I don’t have any formal education in this topic.


So basically, the idea would be to:

  1. write the code in unit agnostic manner
  2. then partial evaluate it with known units
  3. and then call the partially evaluated predicate with only numbers

Interestingly, this is already how qeval works. I first compile an overall arithmetic expression, then call it.
So, implementing your idea would not be very hard.
Maybe we could call it a kind of just in time compilation ?

The reason I don’t really like this approach is that:

  • the caching is going to incur some runtime cost
  • meta calling the arithmetic expression means no optimized arithmetic (swipl -O)
  • no propagation of units across different qeval calls: imagine that avg_speed is a complex predicate with recursion, meta-predicate calls, etc. Any way, this needs a more complete example, I’ll try to write one soon.