Is there a meta_predicate tutorial?

In short if I were asked to explain why is meta_predicate/1 needed, how does it solve the problem, what are it’s short comings, how does it modify the code, how to show a visual representation of the changes, how can the changes to the source code be seen, etc., I would not be able to answer any of these with certainty.

I have found a few pages that give some clues, and some example code but there is not enough evidence to seal the case.

While I don’t expect to find the perfect tutorial for meta_predicate/1 (prefer it be specific to SWI-Prolog), I am all ears if you know a good tutorial or just references that added to your understanding of meta_predicate/1. :slightly_smiling_face:

Here are some of my better references
  • SWI-Prolog Documentation

SWI-Prolog Predicate meta_predicate/1
SWI-Prolog Predicate @/2
SWI-Prolog Section 6.5 Defining a meta-predicate
SWI-Prolog Section 2.12 Environment Control (Prolog flags) - colon_sets_calling_context/2
SWI-Prolog Section 4.25 Operators - Seems operators were left out when meta_predicate/1 was designed.

  • SWI-Prolog source code implementation in C

pl-proc.c
pl-incl.h

  • Other Prolog Documentation

LogTalk meta_predicate/1
Quintus Prolog User’s Manual - Section 8.13.17 The meta_predicate Declaration

SICStus Prolog manual - Section 5.5 Module Name Expansion

Goals appearing in queries and meta-calls are expanded prior to execution while goals in the bodies of clauses and directives are expanded at compile time.

Need to see if this holds true for SWI-Prolog.

  • Forums

Google Groups for SWI-Prolog - DCG meta-predicate error
SWI-Prolog Discourse topic: Mode declarations vs meta_predicate/1
SWI-Prolog Discourse topic: Context module and module prefix attached to arguments [Q]
SWI-Prolog Discourse topic: How to get multifile to work with dynamic predicates
SWI-Prolog Discourse topic: Modules design for multi-agent modeling
SWI-Prolog Discourse topic: How can the module for a term be identified?
SWI-Prolog Discourse topic: Module finding calling program DCG predicates

StackOverflow - Custom DCG Operators
StackOverflow - Definition of a path/trail/walk
StackOverflow - Definition of Reflexive Transitive Closure
StackOverflow - How do I code rec/3 in the presence of a meta_predicate declaration?
StackOverflow - What kind of meta argument is the first argument of predicate_property/2?

  • Slides

Using Modules - These have nice definitions and examples of words like Context Module
Name-based versus Predicate-based Modules
Meta-Predicates in Modules

Modules in SWI Prolog - This is source code with annotations that give meaning to a picture is worth a thousand words.

  • Prolog Source Code using meta_predicate/1

SWI-Prolog pack -strand
GitHub - mndrix/dcg_util.pl

  • Papers

SWI-Prolog Section 7.2.1 Meta-predicate handling
A New Module System for Prolog
Functions in Full Prolog
An Elementary Prolog Library Section 2.2 meta_predicate - This starts to talk about the history of meta_predicate.
Section 4.0 Compatibility of the Module System
Global Analysis of Standard Prolog Programs
Implementing a Module System for SICStus Prolog - Has a few nice images.
Meta-Predicate Semantics

Towards a Study of Meta-Predicate Semantics

The :/2 operator both calls a predicate in another module and changes the calling context of the predicate to that module.
The idea of the meta_predicate/1 directive is to avoid the need for explicit qualifications in the first place.

  • Books

“The Craft of Prolog” Section 6.13 Meta-programs and Object-Oriented Programming
“The Art of Prolog” Section 10.5 Background - Notes when some the problems first asked.

  • Standards

ISO/IEC 13211-2:2000. Part 2: Modules. Published 2000-06-01. Also available much cheaper as INCITS/ISO/IEC 13211-2:2000 (R 2006) due to INCITS.

Personal Notes

After years of trying to understand these this statement by Annie hits the nail on the head.

The fix there is the meta_predicate/1 declaration, which marks which arguments are module sensitive . (ref)

Anyone using The Prolog Development Tool - A Prolog IDE for Eclipse?
prolog_xref has predicate meta_xref/2,3 (ref).

If the code uses library(option) and there are options that are module-sensitive, then use meta_options/3 (ref)

meta_predicate/1 works with more than just predicates, e.g. operators (ref) and facts ??? (need ref).

Is it incorrect to add a module variable (e.g. M) for a meta-predicate since the meta_predicate/1 will set the module based on context_module/1 (ref), e.g.

:- meta_predicate foo(:).
foo(M:Goal) :-
   true,
   Goal,
   true.

Is // the same as 2 (ref), e.g.

dcg_call(//, ?, ?),
dcg_call(3, ?, ?, ?),
dcg_call(4, ?, ?, ?, ?),
dcg_call(5, ?, ?, ?, ?, ?),
dcg_call(6, ?, ?, ?, ?, ?, ?),
dcg_call(7, ?, ?, ?, ?, ?, ?, ?),

In SWI-Prolog sometimes for meta-predicates the code uses strip_module/3 and sometimes it does not. Is this because the strip_module/3 was used before meta_predicate/1 was created/used here, then when strip_module/3 was deprecated and meta_predicate/1 was used, the way of adding the module to the meta-predicates had to change?

Message Passing:
Wikipedia
PROGRAMMING WORD OF THE DAY
wiki.c2.com

Unexpected predicate_property/2 size changing without editing predicate in this post in the personal notes references SWI-Prolog C source code where the the C level structures are modified when MA_NEEDS_TRANSPARENT is used.


Related to the definition of closure

SWI Prolog documentation mentions “closures” - but these are not the “closures” you are looking for

pl-wrap.h

typedef struct closure
{ struct definition def;
} closure;

GLOBAL PL_blob_t _PL_closure_blob;
COMMON(void)	  resetWrappedSupervisor(Definition def);
COMMON(int)	  get_closure_predicate__LD(term_t t, Definition *def ARG_LD);

#define get_closure_predicate(t, def) get_closure_predicate__LD(t, def PASS_LD)

SWI-Prolog source code implementation in C

Since SWI-Prolog is implemented using Virtual Machine Instructions (VMI) and the instructions are defined in pl-vmi.c this is the lowest level to start the understanding the source code.

A Portable Prolog Compiler by D.L. Bowen, L.H. Byrd and W.F. Clocksin (pdf)

I_CONTEXT

I_CONTEXT is used by non-meta predicates that are compiled into a different module using : :- . The I_CONTEXT instruction immediately follows the I_ENTER. The argument is the module.

I_LCALL

Actual tail call. The arguments for the new predicate have been set by now. The number of arguments may be both more and less than for the running frame. As we may need to perform callbacks this is a bit of a problem.

  • If we perform the callbacks giving the current GC context we go wrong if the new predicate has more arguments than the current clause has prolog_vars.
  • If we first change the context to the new predicate we can perform the callbacks, but we still need to fix the calling context.

S_MQUAL

Meta-predicate argument qualification. S_MQUAL qualifies the Nth argument. S_LMQUAL does the same and resets the context module of the frame to be definition module of the predicate, such that unqualified calls refer again to the definition module. This sequence must be processed as part of the supervisor, notably before creating the first choicepoint.

I_CALLATM

I_CALLATM: procedure-module, context-module, procedure The procedure-module is provided to support the decompiler.

I_CALLATMV

This instruction deals with @(Callable, Module), where Module is a variable. The module argument can be NULL.

I_CALLM

I_CALLM deals with qualified calls. The unfortunate task is to sort out the context module for calling a transparent procedure. This job is the same as the end of I_USERCALL.

I_USERCALL0

I_USERCALL0 is generated by the compiler if a variable is encountered as a subclause. Note that the compount statement opened here is encloses also I_CALL. This allows us to use local register variables, but still jump to the `normal_call’ label to do the common part of all these three virtual machine instructions.

I_USERCALL0 has the task of analysing the goal: it should fill the ->procedure slot of the new frame and save the current program counter. It also is responsible of filling the argument part of the environment frame with the arguments of the term.

I_USERCALLN

I_USERCALLN: translation of call(Goal, Arg1, …)

typedef struct module *		Module;		/* predicate modules */

(ref)

#define P_TRANSPARENT		(0x00040000) /* Inherit calling module */

(ref)

#define P_MFCONTEXT		(0x00100000) /* Used for Goal@Module */

(ref)

#define CL_BODY_CONTEXT		(0x0080) /* Module context of body is different */
					 /* from predicate */

(ref)

struct localFrame
{ Code		programPointer;		/* pointer into program */
  LocalFrame	parent;			/* parent local frame */
  ClauseRef	clause;			/* Current clause of frame */
  Definition	predicate;		/* Predicate we are running */
  Module	context;		/* context module of frame */
#ifdef O_PROFILE
  struct call_node *prof_node;		/* Profiling node */
#endif
#ifdef O_LOGICAL_UPDATE
  lgen_t	generation;		/* generation of the database */
#endif
  unsigned int	level;			/* recursion level */
  unsigned int	flags;			/* packed long holding: */
};

(ref)

struct module
{ atom_t	name;		/* name of module */
  atom_t	class;		/* class of the module */
  SourceFile	file;		/* file from which module is loaded */
  Table		procedures;	/* predicates associated with module */
  Table		public;		/* public predicates associated */
  Table		operators;	/* local operator declarations */
  ListCell	supers;		/* Import predicates from here */
  ListCell	lingering;	/* Lingering definitions */
  size_t	code_size;	/* #Bytes used for its procedures */
  size_t	code_limit;	/* Limit for code_size */
#ifdef O_PLMT
  counting_mutex *mutex;	/* Mutex to guard module modifications */
  struct thread_wait_area *wait;/* Manage waiting threads */
#endif
#ifdef O_PROLOG_HOOK
  Procedure	hook;		/* Hooked module */
#endif
  int		level;		/* Distance to root (root=0) */
  unsigned int	line_no;	/* Source line-number */
  unsigned int  flags;		/* booleans: */
  int		references;	/* see acquireModule() */
  gen_t		last_modified;	/* Generation I was last modified */
};

(ref)

COMMON(Module)      contextModule(LocalFrame fr);
COMMON(void)        setContextModule(LocalFrame fr, Module context);
COMMON(Module)      lookupModule__LD(atom_t name ARG_LD);
COMMON(Module)      isCurrentModule__LD(atom_t name ARG_LD);
COMMON(Module)      acquireModule__LD(atom_t name ARG_LD);
COMMON(void)        releaseModule(Module m);
COMMON(int)         addModuleSourceFile(SourceFile sf, Module m);
COMMON(int)         setSuperModule(Module m, Module s);
COMMON(int)         setSuperModule(Module m, Module s);
COMMON(int)         isSuperModule(Module s, Module m);
COMMON(int)         isSuperModule(Module s, Module m);
COMMON(void)        clearSupersModule(Module m);
COMMON(int)         addSuperModule(Module m, Module s, int where);
COMMON(int)         addSuperModule(Module m, Module s, int where);
COMMON(int)         getUnknownModule(Module m);
COMMON(Word)        stripModule(Word term, Module *module, int flags ARG_LD);
COMMON(bool)        isPublicModule(Module module, Procedure proc);
COMMON(int)         exportProcedure(Module module, Procedure proc);
COMMON(Module)      advanceModuleEnum(ModuleEnum en);
COMMON(int)         currentOperator(Module m, atom_t name, int kind,
COMMON(int)         priorityOperator(Module m, atom_t atom);
COMMON(int)         callProlog(Module module, term_t goal, int flags, term_t *ex);
COMMON(Procedure)   lookupProcedure(functor_t f, Module m) WUNUSED;
COMMON(Procedure)   isCurrentProcedure__LD(functor_t f, Module m ARG_LD);
COMMON(int)         importDefinitionModule(Module m,
COMMON(Procedure)   lookupProcedureToDefine(functor_t def, Module m);
COMMON(int)         get_functor(term_t descr, functor_t *fdef, Module *m, term_t h, int how);
COMMON(int)         overruleImportedProcedure(Procedure proc, Module target);
COMMON(bool)        abolishProcedure(Procedure proc, Module module);
COMMON(Procedure)   resolveProcedure__LD(functor_t f, Module module ARG_LD);
COMMON(Definition)  autoImport(functor_t f, Module m);
COMMON(void)        unlinkSourceFileModule(SourceFile sf, Module m);
COMMON(int)         exportProcedureSource(SourceFile sf, Module module,
COMMON(void)        registerReloadModule(SourceFile sf, Module module);

(ref)

Many of the c functions related to using Prolog modules are in pl-modul.c

CODE GENERATION
int compileClause(Clause *cp, Word head, Word body, Procedure proc, Module module, term_t warnings ARG_LD)

Context Module
Module contextModule(LocalFrame fr)
void setContextModule(LocalFrame fr, Module context)

MA_NEEDS_TRANSPARENT 1

FR_CONTEXT

O_CALL_AT_MODULE @

multifile

strip_module PL_strip_module_ex
lookupModule

target_module
getTargetModule
pushTargetModule

definition->module


One link that is missing from your list, somehow, is the section on defining a meta-predicate. It gives a pretty good overview it seems.

1 Like

When I use a reference in the SWI-Prolog documentation I will typically click in the left menu the section name for a specific predicate. Doing so for meta_predicate/1 is the same as the link you provided.

While that section is technically correct, can you use it to answer my questions? I could not. :frowning_face:

Don’t take that to mean I dislike the documentation, it just lacks enough information for me to feel confident in understanding and using meta_predicate/1.

I added it to the list. :slightly_smiling_face:

Not sure. The questions are not too specific on first sight. They are answered, in a fashion, in the intro there. I would guess that this is the gist of it:

The meta_predicate/1 directive tells the compiler that certain arguments are terms that will be used to look up a predicate and thus need to be wrapped (qualified) with <module>:<term>, unless they are already wrapped.

I strongly suspect that I am missing something from your questions; please forgive me for that.

1 Like

Or it could be that I am missing something simple.

One of the problems I am having with Prolog is that sometimes a call needs to be made from one predicate in one module to a predicate in another module. From what I am gathering is that if sometimes the call can not be made is because Prolog does not know which module to use for the predicate. The better way to resolve this seems to be using meta_predicate/1. See: Using prolog_walk_code/1 to identify meta predicate calls?. In that the call is added at the binary level, but if you list out the source using listing/1 you might expect to see the added meta-predicate, but I don’t. The references talk about other ways to deal with the problem but some are clearly seen as being very wrong, i.e. hardcoding the module with the predicate.

Also if you read some of the references there is a big difference between a Goal and closure, still don’t get that one. Also there are more than one way to solve this problem as noted in “The Craft of Prolog” by Richard O’Keefe Section 6.13 Meta-programs and Object-Oriented Programming.

In trying to understand this, it makes one really have to understand the deeper happenings of the code with regards to calls between modules and history of what it has done to Prolog. It seems in the land of Prolog there was happiness, then modules where added and the world or Prolog shattered like broken glass. :frowning_face:

I have been purposefully avoiding mentioning my specific problem because I don’t want the discussion to focus on that particular problem and then still leave me with a large gap in my knowledge. Until today I would not have guessed that cut (!/0) and once/1 would be of consideration with these problems.

I don’t know about that. My understanding so far is that “knowledge” is just the titbits that each of us has gathered along the way and has at their disposal. I am not sure there is a shortcut to knowledge, in the sense that some deep revelation would somehow allow me to be more knowledgeable with less effort.

I guess the module tutorial is probably one of the best places to start.

Roughly though, the problem is not that hard. We have predicates that live in modules, so the full specification of a predicate is module:name/arity (as a predicate indicator) or module:name(arg1, ....) as a goal. Now the whole module thing is rather pointless if we have to specify each goal or predicate indicator in its full form, so a simple name/arity or name(arg1, …) needs to refer to the proper module. Using normal code in modules this is rather easy: any such reference in a module refers by default to the module it appears in. This can call/refer to either a locally defined predicate or an imported predicate.

So far, so good. If there were no meta predicates this would be the end of the story. But, we have things that (notably) take closures as an argument and are defined in some other module. If we call maplist(p, List), maplist/2 calls call(p,Element), but we want this called in the module calling the maplist goal, not the module in which maplist/2 is defined. That is where meta-arguments come in. If an argument is defined as a meta-argument, as the first argument of maplist/2, the caller adds its module to the argument if this is not already there. So, p becomes m:p, where m is the module making the call to maplist/2.

The machinery only distinguishes meta arguments and normal arguments. The first are qualified, the latter left untouched. Next, meta_predicate/1 adds some additional machinery to support code analysis. : simply means this is a meta argument without being more specific. 0 means the argument is a goal that will be called. 1 means the argument is a term that will be called using call(Term, Arg), etc.

That is (technically) 99% of the story (there are some more meta-predicate indicators and we have multi-file predicates related to modules as we have seen recently).

1 Like

My overly simplistic view of modules: a meta-predicate can expect the : (and 0, 1, etc.) arguments to be of the form Module:Term – and if the caller doesn’t specify the module, it’ll get filled in.

EDIT: I originally typed ? instead of :, which is, of course, nonsensical. So, if you read @jan’s reply, bear in mind that he was responding to my incorrect ?.

1 Like

Mostly. ? not though. We have the meta arguments (those that do qualify): :,//,^,0..9 and the mode arguments (those that do not qualify): *, ?, -, +. The mode arguments are documentation only: no part of the system does anything with them. The meta arguments are all the same when it comes to runtime, but they do affect code analysis (cross-referencing) and expand_goal/2, used to do macro rewriting on goals. So, goal expansion applies to e.g., the 2nd argument of findall/3.

Here, : merely qualifies, not affecting anything else. That is used if you write a predicate that needs to do something in the module it is called from. 0..9 stands for call/1…10, // for DCG expansion (1st arg of phrase/2) and ^ for existential binding as in setof/3.

This was mostly invented by Quintus. I don’t know who introduced * (Paulo?). I have added // and ^.

1 Like

For those who want to delve much deeper into the subject of meta predicates, Paulo Moura has written a whole paper about it.

1 Like

Oops … I meant : and typed ?.

As to who invented this flavour of modules – I vaguely remember some discussion about it at Quintus around 1991 … I’m pretty sure it’s quite a bit older than 1991 and that Richard O’Keefe was involved, but not sure whose original idea it was. If you wish, I can ask some ex-Quintus people …

Thanks, but no.

I really just want my code to work without the hacks and understand why the fix worked. Currently the hacks are duplicating code into other modules.

From a theoretical point of view, there is a big difference, but from a practical point of view, not so much. You can print out closures to understand what’s going on – they’re just terms.

Note that you can put “module:” in front of a compound goal, e.g. some_module:(goal1(X), goal2(X,Y)).

Maybe your problem is in understanding how use_module/1 (and similar) modify the namespace in the current module?
TL;DR: all the imported names get added to the current module’s namespace. E.g., if you import foo:bar/1 into module qqsv (by :-use_module(foo,[bar/1])), then qqsv:bar(X) is the same as foo:bar(X) and if in module qqsv you don’t specify the module, qqsv is implicitly used – that is, bar(X) is the same as qqsv:bar(X) and for a call to a meta_predicate, qqsv: will be added if no module is explicitly given (for args specified by :, 0, etc.).

1 Like

Thanks for the response Peter.


In further searching found

Towards a Study of Meta-Predicate Semantics by Paulo Moura

for which footnote 1 reads

In Prolog and Logtalk, a closure is defined as a callable term used to construct a
goal by appending one or more additional arguments.

So for now will take that to mean that Goals can not use a number for the meta argument specifier but that Closures will require a number for the meta argument specifier.

First off, I don’t think that the concept of “closure” is very meaningful in Prolog. In the cases of languages like Python or Lisp, a closure can capture “hidden” local variables; in Prolog, everything is visible and captured in the term. (Python also has tricky semantics of one of the local variables in the closure is a global value that is modified; this isn’t a problem in Prolog because it doesn’t have mutable variables.)

A meta-predicate specifier of 0 merely means that the goal is used as-is, and isn’t called with additional arguments. For example (note that 0 is used in the meta_predicate declaration but : in the mode comment:

:- meta_predicate must_once(0).

%! must_once(:Goal) is det.
must_once(Goal) :-
    (   call(Goal)
    ->  true
    ;   throw(error(must_once_failed(Goal), _))
    ).

However, it’s probably most common to append arguments, such as in maplist/2 (the library definition is a bit more complex, for efficiency):

:- meta_predicate maplist(1, ?).

%! maplist(:Pred, ?List) is det.
maplist(_Pred, []).
maplist(Pred, [Elem|Tail]) :-
    call(Pred, Elem),
    maplist(Pred, Tail).

And it could be used like this: maplist(positive_integer, [1,2,3,4]) or maplist(must_be(between(0,10)), [1,2,3,4]).

As @jan mentioned, 0, 1, etc. in meta-predicate declarations are treated like : when there’s a call; they’re used by things like list_undefined/0, to check for calls that appear in meta-predicates.

4 Likes