This is a topic to discuss the Wiki
Stated Wiki: Meta Interpreter
because it is one of the essential skills all Prolog programmers should posses.
As a community we can share what we know to help all of us acquire this essential skill.
A useful place to start learning about them is A Couple of Meta-interpreters in Prolog by Markus Triska
Personal Notes
Be aware of library(apply_macros) (ref)
static void
registerControlFunctors()
{ static functor_t control[] =
{ FUNCTOR_comma2,
FUNCTOR_semicolon2,
FUNCTOR_bar2,
FUNCTOR_ifthen2,
FUNCTOR_softcut2,
FUNCTOR_not_provable1,
FUNCTOR_colon2, /* Module:Goal */
#ifdef O_CALL_AT_MODULE
FUNCTOR_xpceref2, /* Goal@Module */
#endif
(functor_t) 0
};
functor_t *f;
for(f = control; *f; f++)
{ valueFunctor(*f)->flags |= CONTROL_F;
}
}
(ref)
callable/1 exist but don’t know how it relates to the criteria as noted by Jan W. in this post.
callable/1 is often seen as a guard, e.g.
predicate_xyz(_:Head) :-
callable(Head),
!
...
example in syspred.pl
and with a conditional ->/2 e.g.
( callable(Head)
-> ...
; ...
).
example in autoload.pl
callable/1 is also used as part of the type checking from library(error), e.g. has_type(callable,X)
NB Do not call has_type/2 but use the other wrapper predicates as demonstrated in the following.
must_be(callable,Predicate)
must_be/2 throws instantiation_error if Term is insufficiently instantiated and type_error(Type, Term)
if Term is not of Type.
example in sandbox.pl
must_be(list(callable), List)
example in thread.pl
has_type/2
has_type(callable,Predicate)
fails silently
In searching the SWI-Prolog source code for callable
found interesting code. Still don’t know what it means or how to use it but they make good food for thought.
prolog_codewalk.pl
prolog_colour.pl
syspred.pl
test_util_iso.pl
yall.pl
For examples of predicate_property/2 and module_property/2 see Using listing/N and suc
Are these 5 classes of predicates suppose to be independent or will some predicates fall into more than one class?
There are roughly 5 classes of predicates relevant to meta-interpretation:
With predicate property
foreign
. These are written in C (or have a C wrapper to Java/Python/…). You cannot do clause/2 and thus you cannot meta-interpret them.Stuff handled by the compiler that has a clause that is exactly the same. Below is an example. You can get a clause, but this is the same as the original clause and thus you make no progress You find the full set in
boot/init.pl
, currently from line 318.(G1, G2) :- call((G1, G2)).
Normal Prolog code that is part of the core system. They are reported as
built_in
.Normal Prolog code from the libraries. The way to find them is using the
imported_from(Module)
property and module_property/2, checking forclass(library)
User code. This may be local to the module (or not in a module) or imported user code.
The first two cannot be meta-interpreted. The rest is a choice up to the user.
e.g.
fail/0 is both foreign
(class 1) and built_in
(class 3). Many predicates are in both class 1 and 3.
For others on this same path here is some code that might be of benefit.
meta_interpreter_class(Head,1) :-
predicate_property(Head,foreign).
meta_interpreter_class((M0:_If ; M0:_Then),2).
meta_interpreter_class((_G1 ,_G2),2).
meta_interpreter_class((_If -> _Then),2).
meta_interpreter_class((_If *-> _Then),2).
meta_interpreter_class(@(_Goal,_Module),2).
meta_interpreter_class(Head,3) :-
predicate_property(Head,built_in).
meta_interpreter_class(Head,4) :-
predicate_property(Head,imported_from(Module)),
module_property(Module,class(library)).
meta_interpreter_class(Head,5) :-
predicate_property(Head,imported_from(user)).
meta_interpreter_number_class(1,foreign).
meta_interpreter_number_class(2,control_structure).
meta_interpreter_number_class(3,built_in).
meta_interpreter_number_class(4,library).
meta_interpreter_number_class(5,user).
pred_meta_class :-
current_predicate(Name/Arity),
compound_name_arity(Predicate,Name,Arity),
pred_meta_class(Predicate,Class_ids),
% Class_ids = [5],
maplist(meta_interpreter_number_class,Class_ids,Class_names),
format('~w/~w - ~w~n',[Name,Arity,Class_names]),
fail.
pred_meta_class.
pred_meta_class(Predicate,Classes) :-
setof(Class,meta_interpreter_class(Predicate,Class),Classes).
:- begin_tests(meta_interpreter).
test(predicate_property_foreign_success) :-
predicate_property(=(_,_),foreign).
test(predicate_property_foreign_success,[set(P = [built_in,defined,foreign,iso,nodebug,static,visible,imported_from(system),size(144)])]) :-
predicate_property(=(_,_),P).
test(meta_interpreter_class_1_success,[nondet]) :-
meta_interpreter_class(=(_,_),1).
test(meta_interpreter_class_2_success,[nondet]) :-
meta_interpreter_class((user:1;user:2),2).
test(meta_interpreter_class_2_success,[nondet]) :-
meta_interpreter_class((true,false),2).
test(meta_interpreter_class_2_success,[nondet]) :-
meta_interpreter_class((true -> 1),2).
test(meta_interpreter_class_2_success,[nondet]) :-
meta_interpreter_class((true *-> 1),2).
test(meta_interpreter_class_2_success,[nondet]) :-
meta_interpreter_class(@(true,user),2).
test(predicate_property_built_in_success) :-
predicate_property(assert(_),built_in).
test(predicate_property_built_in_success,[set(P = [built_in,defined,foreign,nodebug,static,transparent,visible,imported_from(system),(meta_predicate assert(:)),size(144)])]) :-
predicate_property(assert(_),P).
test(meta_interpreter_class_3_success,[nondet]) :-
meta_interpreter_class(assert(_),3).
test(predicate_property_imported_from_success) :-
predicate_property(append(_,_,_),imported_from(lists)).
test(predicate_property_imported_from_success,[set(P = [defined,interpreted,nodebug,static,visible,file('c:/program files/swipl/library/lists.pl'),imported_from(lists),last_modified_generation(6476),line_count(123),number_of_clauses(2),number_of_rules(1),size(504)])]) :-
predicate_property(append(_,_,_),P).
test(meta_interpreter_class_4_success,[nondet]) :-
meta_interpreter_class(append(_,_,_),4).
:- end_tests(meta_interpreter).
Still working on meta_interpreter_class(Head,5)
.
EDIT
Since @JCR was kind enough to give this post a like here is an update of the code in this post.
% Collects all current predicates into a list of pred_1(Name,Arity).
current_predicates_set_1(Predicates) :-
setof(pred_1(Name,Arity),current_predicate(Name/Arity),Predicates).
% To be used with maplist/3
predicate_name_arity_to_compound(pred_1(Name,Arity),pred_2(Predicate,Name,Arity)) :-
compound_name_arity(Predicate,Name,Arity).
map_name_arity_to_compound(Predicates0,Predicates) :-
maplist(predicate_name_arity_to_compound,Predicates0,Predicates), !.
% Collects all current predicates into a list of pred_2(Predicate,Name,Arity).
current_predicates_set_2(Predicates) :-
current_predicates_set_1(Predicates0),
map_name_arity_to_compound(Predicates0,Predicates).
meta_interpreter_class(Head,1) :-
predicate_property(Head,foreign).
meta_interpreter_class((M0:_If ; M0:_Then),2).
meta_interpreter_class((_G1 ,_G2),2).
meta_interpreter_class((_If -> _Then),2).
meta_interpreter_class((_If *-> _Then),2).
meta_interpreter_class(@(_Goal,_Module),2).
meta_interpreter_class(Head,3) :-
predicate_property(Head,built_in).
meta_interpreter_class(Head,4) :-
predicate_property(Head,imported_from(Module)),
module_property(Module,class(library)).
meta_interpreter_class(Head,5) :-
predicate_property(Head,imported_from(user)).
meta_interpreter_class(Head,6) :-
predicate_property(Head,imported_from(system)).
meta_interpreter_class(Head,7) :-
predicate_property(Head,(dynamic)).
meta_interpreter_class(Head,8) :-
predicate_property(Head,interpreted).
meta_interpreter_class(Head,9) :-
predicate_property(Head,visible).
% To be used with maplist/3
predicate_to_class_ids(pred_2(Predicate,Name,Arity),pred_3(Predicate,Name,Arity,Class_ids)) :-
(
setof(Class,meta_interpreter_class(Predicate,Class),Class_ids) ,!
;
(
format('Unknown class: ~w~n',[Predicate]),
Class_ids = [20]
)
).
map_predicate_to_class_ids(Predicates0,Predicates) :-
maplist(predicate_to_class_ids,Predicates0,Predicates), !.
% Collects all current predicates into a list of pred_3(Predicate,Name,Arity,Class_ids).
current_predicates_set_3(Predicates) :-
current_predicates_set_1(Predicates0),
map_name_arity_to_compound(Predicates0,Predicates1),
map_predicate_to_class_ids(Predicates1,Predicates).
meta_interpreter_number_class(1,foreign).
meta_interpreter_number_class(2,control_structure).
meta_interpreter_number_class(3,built_in).
meta_interpreter_number_class(4,library).
meta_interpreter_number_class(5,user).
meta_interpreter_number_class(6,system).
meta_interpreter_number_class(7,dynamic).
meta_interpreter_number_class(8,interpreted).
meta_interpreter_number_class(9,visible).
meta_interpreter_number_class(20,unknown).
% To be used with maplist/3
map_class_id_to_name(pred_3(Predicate,Name,Arity,Class_ids),pred_4(Predicate,Name,Arity,Class_ids,Class_names)) :-
maplist(meta_interpreter_number_class,Class_ids,Class_names).
map_class_ids_to_names(Predicates0,Predicates) :-
maplist(map_class_id_to_name,Predicates0,Predicates).
% Collects all current predicates into a list of pred_4(Predicate,Name,Arity,Class_ids,Class_names).
current_predicates_set_4(Predicates) :-
current_predicates_set_1(Predicates0),
map_name_arity_to_compound(Predicates0,Predicates1),
map_predicate_to_class_ids(Predicates1,Predicates2),
map_class_ids_to_names(Predicates2,Predicates).
% Displays all current predicates sorted by class ids as row(Class_ids,Class_names,Predicate,Name,Arity).
current_predicates_set_5(row(Class_ids,Class_names,Predicate,Name,Arity)) :-
current_predicates_set_1(Predicates0),
map_name_arity_to_compound(Predicates0,Predicates1),
map_predicate_to_class_ids(Predicates1,Predicates2),
map_class_ids_to_names(Predicates2,Predicates3),
order_by([asc(Class_ids)], member(pred_4(Predicate,Name,Arity,Class_ids,Class_names),Predicates3) ).
To use
?- current_predicates_set_5(R).
R = row([1, 3, 6, 9], [foreign, built_in, system, visible], !(), !, 0) ;
R = row([1, 3, 6, 9], [foreign, built_in, system, visible], '$absolute_file_name'(_52, _54), '$absolute_file_name', 2) ;
R = row([1, 3, 6, 9], [foreign, built_in, system, visible], '$add_directive_wic'(_64), '$add_directive_wic', 1) ;
...
The code is still not done but it makes it easier to reason about the classes for predicates as used for interpretation. I plan to count the group_by sections instead of displaying each predicate in a group and add predicates to look for class ids that might be subset of others.
The main requirement missing is a predicate to determine if a predicate can be used in an interpreter. I was hoping callable/1 would do that but sadly it is not that smart.
EDIT
Added count the group_by sections instead of displaying each predicate in a group
% Displays all current predicates grouped by class ids with a count as (Class_ids,Class_names)-Count.
current_predicates_set_6((Class_ids,Class_names)-Count) :-
current_predicates_set_1(Predicates0),
map_name_arity_to_compound(Predicates0,Predicates1),
map_predicate_to_class_ids(Predicates1,Predicates2),
map_class_ids_to_names(Predicates2,Predicates3),
group_by(Class_ids, row(Predicate), member(pred_4(Predicate,_Name,_Arity,Class_ids,Class_names),Predicates3), Bag),
length(Bag,Count),
maplist(meta_interpreter_number_class,Class_ids,Class_names).
Example run
?- current_predicates_set_6(R).
R = ([1, 3, 6, 9], [foreign, built_in, system, visible])-692 ;
R = ([2, 3, 6, 8, 9], [control_structure, built_in, system, interpreted, visible])-4 ;
R = ([3, 6, 7, 8, 9], [built_in, system, dynamic, interpreted, visible])-11 ;
R = ([3, 6, 8, 9], [built_in, system, interpreted, visible])-312 ;
R = ([3, 8, 9], [built_in, interpreted, visible])-169 ;
R = ([4, 8, 9], [library, interpreted, visible])-17 ;
R = ([6, 7, 8, 9], [system, dynamic, interpreted, visible])-8 ;
R = ([6, 8, 9], [system, interpreted, visible])-8 ;
R = ([7, 8, 9], [dynamic, interpreted, visible])-19 ;
R = ([8, 9], [interpreted, visible])-21.
EDIT
Here is that start of the the predicate to check if an SWI-Prolog predicate can be used in Prolog meta-interpreter.
meta_call_check(Goal) :-
(
predicate_property(Goal,foreign)
->
(
(
Goal = true
;
Goal = false
)
->
true
;
fail
)
;
catch(
call(Goal),
Catcher,
(
% format('My message: ~w~n',[Catcher]),
Catcher == error(existence_error(_,_)),
fail
)
)
).
Here is the start of some test cases.
:- begin_tests(meta_call_check).
meta_call_check_test_case(success,true ).
meta_call_check_test_case(fail ,a() ).
test(meta_call_check,[forall(meta_call_check_test_case(success,Predicate))]) :-
meta_call_check(Predicate).
test(meta_call_check,[fail,forall(meta_call_check_test_case(fail,Predicate))]) :-
meta_call_check(Predicate).
:- end_tests(meta_call_check).
Example run
?- run_tests(meta_call_check).
% PL-Unit: meta_call_check .. done
% All 2 tests passed
true.
I don’t know if I can make it work as needed but won’t know if I don’t try. Also this is going to become one large predicate with lots of conditionals (-> ; ) until I get it all sorted out.
At this point I am afraid to ask, but I will face my fears. This is an honest question.
For what is a meta-interpreter used?
From my very limited understanding, they are good for fixing a perceived deficiency of the Prolog implementation that is being used. Is that correct? (This assumes that the meta-interpreted Prolog is more “powerful” than the underlying implementation?)
Could someone share an interesting use case for a meta-interpreter?
callable/1 seems to just check for a pattern and not if the predicate exist, e.g.
?- callable(a()).
true.
?- a().
ERROR: Unknown procedure: a/0 (DWIM could not correct goal)
?- call(a()).
ERROR: Unknown procedure: a/0
ERROR: In:
ERROR: [11] a
ERROR: [10] call(user:a()) at c:/program files/swipl/boot/init.pl:418
ERROR: [9] <user>
I think it’s more about easy enriching the language, specially if the Prolog engine doesn’t offer term/goal rewriting. Prolog and Natural-Language Analysis, by Pereira,Shieber, has the last chapter devoted to illustrate some applications of meta interpreters, like Compiling by Partial Execution, or Tabular Parsing.
Also Datalog, being a syntactical subset of Prolog, could be a natural target for meta interpreting.
What’s of utmost importance, is how much of the language extension (or restriction) makes use of the unique features of Prolog. Logical variables, unification, searching are all features that could be absorbed into the target language.
How is this definition different (better?) than the current DCG (compile-time expansion?) of SWI-Prolog?
So maybe I didn’t ask the correct question. I am not asking how to implement a meta-interpreter (this is explained in every textbook I have seen). I wanted to know why to implement a meta-interpreter.
Thank you Carlo! I will try to rephrase your answer and you can correct me, so you are saying that a meta-interpreter is useful for defining a different language that has as much (or as little) of the underlying Prolog as it needs.
It can do more than add or subtract to a language, in a simple word, syntax, it can also modify the current semantics, e.g. In the following link scroll down to the section title Changing the search strategy .
Thank you @EricGT! I have read this textbook in full (time I will never get back ). Those examples are all good but a bit forced, in the sense that I didn’t understand why doing it in such a difficult way was strictly necessary…
But those unnecessary opinions aside, it is basically about defining a different language, I think I get it now.
That is typically how it is taught and used with examples but they can be wielded to do even more. Don’t ask me what as I have not reached that level.
You might be interested in reading or re-reading Use of Prolog for developing a new programming language
Thank you @j4n_bur53 . This actually makes a lot of sense. So again, rephrasing so that you can correct me, it is a useful step for learning purposes. In particular, it is useful as an intermediate step, on the way to going from run-time (“interpreting”) to compile-time (“transpiling” or just “compiling”, where the target is usually a VM).
I have to figure out what exactly “partial evaluation” means in this context. Could you tell me if this page is a good starting point for reading:
Disclaimer, I don’t have hands on, but this is an older reference, its
from Sterlings book from The Practice of Prolog from 1990:
ProMiX is a partial evaluation system for “full” Prolog. It is decomposed into three main modules: kernel, driver, and knowledge base. The kernel provides the partial evaluation engine. The other two modules “drive” and “control” this engine. The paper discusses the problems associated with each module and presents the solutions adopted in the system. The driver module and control knowledge are designed for using ProMiX as a compiler by specializing interpreters.
Thank you. This is sadly behind a paywall for me. It seems to be a chapter from “The Practice of Prolog”, I guess I might try to find the book in a library or maybe get it through my university.
I seem to see this style more and more. What is wrong with the code below as what I’ve always learned to be the way to write this (or two clauses with a !/0 in the first). I wonder about the origin and why it seems to be getting more popular … In the old days it surely was a bad idea as the interaction between !/0 and ;/2 was not well defined. I think part of ISO is now solid, so yes, it will work. For SWI, and I think many systems, the below solution is generally because (if->then;else) using a simple condition (built-in known to create no choicepoint and not instantiating anything) is translated into a simple conditional branch rather than doing all the stuff with creating and destroying choicepoints.
callable(X) :-
( atom(X)
-> true
; compound(X)
).
Usually, yes, but as I said
This does not apply to prolog_current_choice/1 as it instantiates a variable, but notably for the primitive type tests (atom/1, integer/1, etc), comparison (==/2
, @>/2
, >/2
, etc.) Used as condition in (if->then;else) this translates basically to if(!cond) goto else