3

I have the following code which works fine without a meta_predicate declaration. I have defined a predicate rec/3 as follows:

:- use_module(library(lambda)).

 rec(F,1,F).
 rec(F,N,\A^B^(call(F,A,H),call(G,H,B))) :- 
      N>1, M is N-1, rec(F,M,G).

The predicate rec/3 basically implements the following higherorder recursion equation:

 F^1 = F
 F^N = F*F^(N-1)      for N>1

Where * is the composition of two relations. It can for example be used to define addition in terms of successor. Successor would be the following relation:

 ?- F = \A^B^(B is A+1), call(F, 2, R).
 R = 3        /* 3 = 2+1 */

Addition can then be done as follows (SWI-Prolog):

 ?- F = \A^B^(B is A+1), rec(F, 8, G), call(G, 3, R).
 R = 11       /* 11 = 3+8 */

Now if a I add a meta_predicate declaration as follows, before the clauses of rec/3:

 :- meta_predicate rec(2,?,2).
 rec(F,1,F).
 rec(F,N,\A^B^(call(F,A,H),call(G,H,B))) :- 
      N>1, M is N-1, rec(F,M,G).

Things don't work anymore (SWI-Prolog):

  ?- F = \A^B^(B is A+1), rec(F, 8, G), call(G, 3, R).
  false

How can I fix the clauses for rec/3 and the query so that they work in the presence of meta_predicate?

Bye

3 Answers3

1

No problem with a Logtalk version of your code:

:- object(rec).

    :- public(rec/3).
    :- meta_predicate(rec(2,*,*)).
    rec(F, 1, F).
    rec(F, N, [A,B]>>(call(F,A,H),call(G,H,B))) :- 
        N > 1, M is N - 1,
        rec(F, M, G).

    :- public(local/2).
    local(A, B) :-
        B is A + 1.

:- end_object.

I get:

$ swilgt
...
?- {rec}.
% [ /Users/pmoura/Desktop/lgtemp/stackoverflow/rec.lgt loaded ]
% (0 warnings)
true.

?- F = [A,B]>>(B is A+1), rec::rec(F, 8, G), logtalk<<call(G, 3, R).
F = [A, B]>> (B is A+1),
G = [_G88, _G91]>> (call([A, B]>> (B is A+1), _G88, _G99), call([_G108, _G111]>> (call([A, B]>> (B is A+1), _G108, _G119), call([_G128, _G131]>> (call(... >> ..., _G128, _G139), call(... >> ..., _G139, _G131)), _G119, _G111)), _G99, _G91)),
R = 11 ;
false.

?- F = [A,B]>>(rec::local(A,B)), rec::rec(F, 8, G), logtalk<<call(G, 3, R).
F = [A, B]>> (rec<<local(A, B)),
G = [_G2655, _G2658]>> (call([A, B]>> (rec<<local(A, B)), _G2655, _G2666), call([_G2675, _G2678]>> (call([A, B]>> (rec<<local(A, B)), _G2675, _G2686), call([_G2695, _G2698]>> (call(... >> ..., _G2695, _G2706), call(... >> ..., _G2706, _G2698)), _G2686, _G2678)), _G2666, _G2658)),
R = 11 ;
false.

Note the "fix" for the meta_predicate/1 directive. The code for the rec/3 predicate is the same except for the conversion of the lambda expression syntax to the Logtalk syntax. However, in the case of Logtalk, the meta_predicate/1 directive is not required for this example (as all that the rec/3 predicate does is converting a term to a new term) and only serves documentation purposes. You can comment it out and still use the rec::rec/3 predicate, calling it from either user (i.e. from the top-level interpreter) or from a client object.

The call/3 call is made in the context of the logtalk built-in object just to get the Logtalk lambda expression interpreted (Logtalk doesn't make, on purpose, its native lambda expression support available at the Prolog top-level interpreter).

Paulo Moura
  • 18,373
  • 3
  • 23
  • 33
  • This same "fix" is possible in SWI or any other system with meta_predicate directives, too... It does not work should the argument refer to a definition local to rec ; while it will be called in another module later on. – false Jun 25 '14 at 13:28
  • @false I edited my answer to also illustrate an argument refereeing to a definition local to the `rec` object. Not sure it answers your observation. Let us know. – Paulo Moura Jun 25 '14 at 13:44
  • So you can refer from **outside** to the very local `local/2` definition? That clearly breaks module boundaries. You needed to export `rec/3` to call it. But now `local/2` can be called directly?? – false Jun 25 '14 at 13:48
  • 1
    BTW: I didn't downvote, I still think Logtalk an interesting experiment. –  Jun 25 '14 at 13:49
  • There's nothing wrong with either the `rec/3` predicate or the query. It's the `meta_predicate/1` directive that's wrong. The third argument is never called (by the `rec/3` predicate itself). Thus, the third argument, should not be `2` but `*` (i.e. it's not a meta-argument). – Paulo Moura Jun 25 '14 at 13:49
  • @false The `<2` is a debugging control construct that allows you to switch the calling context. But you can also instead "export" the `local/2` definition. It will work the same. I'll edit my reply to show exactly that. – Paulo Moura Jun 25 '14 at 13:52
  • If the meta argument specifier 0 corresponds to the type o (proposition) and the meta argument specifier 1 corresponds to the type i->o (and individual argument to a proposition) and meta argument specifier 2 corresponds to the type i->i->o etc.., then a meta_predicate directive would be just a type judgement, and wouldn't care about input/output flow. –  Jun 25 '14 at 13:53
  • My reservation is this: If you would include `local/2` somehow in the 3rd argument, then it would be OK to call it from outside. But if someone refers to `local/2` from outside, then he should not be able to reach the local definition (except maybe by some overriding qualification, like the `:`). – false Jun 25 '14 at 13:55
  • My interpretation of integer meta-argument specifiers is different: 0 means that the meta-argument, a goal, will be called by the meta-predicate; N>0 means that the meta-argument, a closure, will be converted to a goal by appending N arguments and calling the resulting goal. – Paulo Moura Jun 25 '14 at 13:57
  • @PauloMoura: By consequence, every meta-argument that is an uninstantiated variable at call time should produce an instantiation error. Yes? – false Jun 25 '14 at 14:11
  • @false "(except maybe by some overriding qualification, like the :)" was exactly what I illustrated when using the `<2` context-switch debugging control construct (which, btw, can be disabled per object or globally to prevent abuse). – Paulo Moura Jun 25 '14 at 14:16
  • @PauloMoura: Imagine `rec(_,-1,local).` in the (module free) definition. A corresponding definition should be possible with modules such that one can call from outside `rec(=,-1,C_2), call(C_2,1,X).` directly. – false Jun 25 '14 at 14:24
  • @false The predicate `rec/3` fails when called with a `-1` second argument. A typo or do you have a different definition for the predicate in mind? – Paulo Moura Jun 25 '14 at 14:44
  • @PauloMoura: Concerning interpretation of meta-argument specifiers: Your interpretation is only right, if we can demonstrate that it is impossible to use meta-arguments as output. For twice / 1 this has already been disproved, for example the twice head rewriting works also with a meta_predicate directive. I guess such a rewriting also exists for rec / 3. –  Jun 25 '14 at 14:44
  • IIRC that discussion (link?), the use of meta-arguments as output was not a question of being possible but of being unsafe. If that, by itself, is a problem likely depends on the usage context. – Paulo Moura Jun 25 '14 at 14:50
  • @PauloMore: I said: "Imagine `rec(_,-1,local)`. in the (module free) definition". That is: Assume this fact as part of the definition. – false Jun 25 '14 at 14:52
  • @PauloMoura: What kind of safety are you refering to? First of all meta-arguments are already output. Take for example the meta-predicate ','(0,0), both arguments of it are output. If I call p(X), q(X,Y), then most likely X and Y will be instantiated, even the output X in p will be input X in q. But X and Y are usually on the term level, question is why does meta_predicate forbid sometimes output on the goal level, is this intentional and unbreakable or is there a simple workaround. For twice/1 there is already a workaround. What about rec/3. –  Jun 25 '14 at 14:59
  • The corresponding mode template for the `(,)/2` control construct is `(+,+)`, i.e. both argument must be instantiated at the time of the call. Note that `+` mode doesn't preclude further instantiation of the argument by the call. Saying that "(...) ','(0,0), both arguments of it are output." is not correct. Safety here means that the meta-predicate must not be allowed to temper with the meta-arguments by modifying them to something else than the caller intended. Allowing instantiated meta-arguments in meta-predicate clause heads opens the door to such trickery. – Paulo Moura Jun 27 '14 at 11:15
1

The SWI meta-predicate declarations and modules are similar to those in Quintus, SICStus, and YAP. The fundamental assumption in those systems is that all information is passed through the declared meta-argument using (:)/2. There is no hidden state or context. For the common cases (simple instantiated arguments), the meta-predicate declarations are sufficient to relieve the burden of explicit qualification from the programmer.

However, in more complex situations as the present one, you have to ensure that explicit qualification will be added. Further, you need to ensure to "dereference" the (:)/2 prefixes accordingly. In SWI, there is strip_module/3:

?- strip_module(a:b:c:X,M,G).
X = G,
M = c.

Assume the definition:

rec(_, -1, local).
rec(_,  0, =).
rec(F, 1, F).

local(S0,S) :-
   S is S0+1.

Which now has to be written like so:

:- meta_predicate goal_qualified(:,-).
goal_qualified(G,G).

:- meta_predicate rec(2,+,2).
rec(_, -1, G) :-
    strip_module(G,_,VG),
    goal_qualified(local,VG).
rec(_, 0, G) :-
    strip_module(G,_,VG),
    goal_qualified(=,VG).
rec(F, 1, G) :-
    strip_module(G,_,F).

Many prefer to add module prefixes manually:

:- meta_predicate rec(2,+,2).
rec(_, -1, G) :-
    strip_module(G,_,mymodule:local).
...

And if we restrict ourselves to SWI only, thereby sacrificing compatibility to SICStus or YAP:

:- meta_predicate rec(2,+,2).
rec(_, -1, _:mymodule:local).
rec(_, 0, _:(=)).
rec(F, 1, _:F).

The rule in your question

rec(F,N,\A^B^(call(F,A,H),call(G,H,B))) :- 
      N>1, M is N-1, rec(F,M,G).

is thus translated as:

rec(F, N, MG) :-
   N > 1, M is N - 1,
   strip_module(MG,_,VG),
   goal_qualified(\A^B^(call(F,A,H),call(G,H,B)),VG),
   rec(F, M, G).

Assuming that library(lambda) is imported everywhere this can again be simplified in SWI to:

rec(F, N, _:(\A^B^(call(F,A,H),call(G,H,B)) )) :-
   N > 1, M is N -1,
   rec(F, M, G).

My conclusion

1mo: Systems should produce a warning for always failing clauses, like in:

| ?- [user].
% compiling user...
| :- meta_predicate p(0).
| p(1).
% compiled user in module user, 0 msec 2080 bytes
yes
| ?- p(X).
no

2do: Maybe it would be best to use the following auxiliary predicate:

:- meta_predicate cont_to(:,:).
cont_to(MGoal, MVar) :-
   strip_module(MVar, _, Var),
   (  nonvar(Var)
   -> throw(error(uninstantiation_error(Var),_))
   ;  true
   ),
   (  strip_module(MGoal,_,Goal),
      var(Goal)
   -> throw(error(instantiation_error,_))
   ;  true
   ),
   Var = MGoal.

Usage.

rec(_, -1, MV) :-
   cont_to(local, MV).

Or rather: one version for each number of auxiliary arguments, thus

:- meta_predicate cont0_to(0,0).
:- meta_predicate cont1_to(1,1).
:- meta_predicate cont2_to(2,2).
...

The name could be better, an operator would not do, though.

false
  • 10,264
  • 13
  • 101
  • 209
  • @CookieMonster: `strip_module/3` is only necessary as a layer of compatibility to SICStus. Neither compatibility nor conformity are priorities in SWI. – false Jun 26 '14 at 08:38
  • Yep, Compound -> _:Compound head rewriting does the job, also for the second clause of rec/3. At least when working from the module user. Have to check how to do it from within a different module. –  Jun 26 '14 at 12:20
  • 1
    Regarding your conclusion, Logtalk already throws a compilation error for the `p(1)` clause and an instantiation error for the `p(0)` query. No need for a `cont_to/2` (or equivalent) auxiliary predicate. – Paulo Moura Jun 27 '14 at 11:05
  • Very good for p(1)! But for the other issue: inevitably, this will hamper cross referencing. (The solution is to add cont0_to cont1_to ...cont7_to, then, cross referencing is possible, too. – false Jun 27 '14 at 11:12
  • It doesn't hamper cross-referencing in the case of Logtalk as it doesn't use a (predicate) prefixing mechanism (the `::/2` operator is a message sending operator, not a syntactic variant of the `:/2` operator). Incidentally, that's also why the meta-predicate directive is optional in the Logtalk solution to this question. – Paulo Moura Jun 27 '14 at 15:29
  • @PauloMoura: (corrected version) How can you then signal a warning that - say `local/2` (as above) is not defined (with the definition for local absent, indeed)? – false Jun 27 '14 at 16:03
  • In order to be able to give the user a **compile** time warning that the closure corresponds to a unknown predicate, you'll need of course the meta-predicate directive but it isn't required for compiling and running the solution (try it). – Paulo Moura Jun 27 '14 at 16:33
  • @PauloMoura: As you say, it is not required to declare a term as being of a certain callable form. But exactly this leads to unchecked code. With `cont_n/2`, also this code could be checked - which is also what `0`, `1`, ... is about - in contrast to the underlying `:`. – false Jun 27 '14 at 16:38
1

The following straigh-forward solution (only tested on SWI-Prolog but in any case far from the wide portability of the Logtalk-based solution):

:- module(m, [rec/3]).

:- use_module(library(lambda)). 

:- meta_predicate(rec(:,?,-)). 

rec(F, 1, F). 
rec(F, N, \A^B^(call(F,A,H),call(G,H,B))) :- 
    N > 1, M is N -1, 
    rec(F, M, G). 

gives:

?- [mrec].
true.

?- use_module(library(lambda)).
true.

?- F = \A^B^(B is A+1), rec(F,10,G), call(G,0,R).
F = \A^B^ (B is A+1),
G = \_G56^_G59^ (call(user: \A^B^ (...is...), _G56, _G67), call(\_G75^_G78^ (call(..., ..., ...), call(..., ..., ...)), _G67, _G59)),
R = 10 .

without requiring low level hacks (one of the motivations of the meta_predicate/1 directive is to avoid the need of using explicit qualification) or requiring a misleading a meta_predicate/1 directive. After re-reading the post and the comments, I still wonder why you want forcibly to write:

:- meta_predicate(rec(2,?,2)).

The first argument of rec/2 is not going to be used as a closure to which the meta-predicate will append two arguments to construct a goal in order to call it. The third argument is an output argument. In the first argument, "2" means input but for the third argument it means instead output! In neither case the meta-predicate is making any meta-calls! The end result of this breakage of the meaning of long established meta-argument indicators in meta-predicate directives is that a user will no longer know how to interpret a meta-predicate template without looking at the actual code of the meta-predicate.

Paulo Moura
  • 18,373
  • 3
  • 23
  • 33
  • 1
    In the comp.lang.prolog thread, one can already find an argument why output arguments that produce closures could profit from some typing. The example I gave there is ?- clause(H,B), foo(B). The SWI-Prolog type inference could profit if clause had a 0 meta-argument specifier in the second argument. –  Jun 26 '14 at 21:12
  • 1
    A possible extension would be to allow out(0) and in(0), or since the (+)/1 and (-)/1 syntax operators exist in Prolog, -0 could be read as out(o) and +0 as in(0) being synonymous to 0. The 0 or +0 and -0 would be a totally conservative solution, that doesn't break anything old, only adds something new. –  Jun 26 '14 at 21:15
  • 1
    But before providing an extension, lets maybe first seriously check whether an extension is needed or not. For example Ulrich Neumerkel doesn't seem to be afraid to use 0 as -0, with the help of strip module or whatever. This discussion is important. –  Jun 26 '14 at 21:17
  • This solution just does not use the module mechanism at all. You can always do that but it leads to lots of *ad hoc* manual additions of module prefixes - making cross referencing (or any other statement about program properties) next to impossible. – false Jun 26 '14 at 21:41
  • If you want to reserve `0`, `1`, `2`, ... to only instantiated arguments, you should really produce an instantiation error otherwise. However, I doubt that this would work out. – false Jun 26 '14 at 21:49
  • Using `-2` in the 3rd would resolve the ambiguity while providing useful information. Is an option whose viability is worth exploring. Voted up. The `2` in the 1st could be regarded as misleading (as there's no derived call made by the meta-predicate). But, in the other hand, provides useful information was it informs a client that when calling the library `rec/3` predicate it should use in the first argument a callable term that when added two arguments should correspond to one if its predicates. This still requires broadening the interpretation of N>=0 meta-argument indicators, however. – Paulo Moura Jun 26 '14 at 22:59