Getting errors when using meta interpreter with clpr. UPDATE: Now works in Terminal but not in Swish

Hi!

I am trying to get a meta interpreter (thanks Daniel) to work with some code that has clpr. With main1 i get the error No permission to access private_procedure 'var/1' (even when i comment our the line in prove/2 that uses call/1). It works with main2 though. Could anyone point me in the correct direction?

Kind regards, JC

CODE:

:-use_module(library(clpr)).

main1:- prove(path(x(2), Z), Proof), maplist(writeln, [Z, Proof]).
main2:- clause(path(x(2), Z), Body), maplist(writeln, [Z, Body]).

link(x(X), y(Y)):- {Y = 2 * X}.
link(y(Y), z(Z)):- {Z = 2 * Y}.
path(X, Y):-link(X, Y).
path(X, Z):- link(X, Y), path(Y, Z).

prove(true, true):-!.
prove((G1, G2), (P1, P2)) :- 
   !,
   prove(G1, P1), 
   prove(G2, P2).
prove((G1;_), P1) :- prove(G1, P1).
prove((_;G2), P2) :- prove(G2, P2).
prove(H, subproof(H, Subproof)) :- clause(H, Body), prove(Body, Subproof).
prove(H, builtin(H)) :- call(H).

ERROR:

ERROR: No permission to access private_procedure `var/1'
ERROR: In:
ERROR:   [14] clause(var(_10414= ...),_10406)
ERROR:   [13] prove(var(_10450= ...),subproof(var(...),_10458)) at /Users/x/x/x/x/testbed.pl:18
ERROR:   [12] prove((var(...),!,...),(subproof(...,_10516),_10510)) at /Users/x/x/x/x/testbed.pl:14
ERROR:   [11] prove({_10550= ...},subproof({...},(...,_10568))) at /Users/x/x/x/x/testbed.pl:18
ERROR:    [9] prove(path(x(2),y(_10608)),subproof(path(...,...),subproof(...,...))) at/Users/x/x/x/x/testbed.pl:18
ERROR:    [8] main1 at /Users/x/x/x/x/testbed.pl:3
ERROR:    [7] <user>
ERROR: 
ERROR: Note: some frames are missing due to last-call optimization.
ERROR: Re-run your program in debug mode (:- debug.) to get more detail.

You can use predicate_property/2 to test for built-in predicates:

prove(G, builtin(G)) :- predicate_property(G, built_in), !, call(G).

Insert this clause after the one that deals with disjunction and delete the last one.

Thank you Paulo!

I tried your suggestion but now i get the error ERROR: Unhandled exception: type_error({_7454=2*2},1,'a constraint',_7454

My updated code is:

:-use_module(library(clpr)).

main1:- prove(path(x(2), Z), Proof), maplist(writeln, [Z, Proof]).
main2:- clause(path(x(2), Z), Body), maplist(writeln, [Z, Body]).

link(x(X), y(Y)):- {Y = 2 * X}.
link(y(Y), z(Z)):- {Z = 2 * Y}.
path(X, Y):-link(X, Y).
path(X, Z):- link(X, Y), path(Y, Z).

prove(true, true):-!.
prove((G1, G2), (P1, P2)) :- 
!,
   prove(G1, P1), 
   prove(G2, P2).
prove((G1;_), P1) :- prove(G1, P1).
prove((_;G2), P2) :- prove(G2, P2).
prove(G, builtin(G)) :- predicate_property(G, built_in), !, call(G).
prove(H, subproof(H, Subproof)) :- clause(H, Body), prove(Body, Subproof).

Got it to work by replacing
prove(G, builtin(G)) :- predicate_property(G, built_in), !, call(G).
with
prove(G, G) :- G = {_}, !, call(G).

So now ?-main1. returns

z(8.0)
subproof(path(x(2),z(8.0)),(subproof(link(x(2),y(4.0)),
{4.0=2*2}),subproof(path(y(4.0),z(8.0)),subproof(link(y(4.0),z(8.0)),{8.0=2*4.0}))))

However this only works from my Terminal but not in Swish, which complains:

Sandbox restriction!
Could not derive which predicate may be called from
	  call(C)
	  prove(A,B)
	  prove(path(x(2),A),B)
	  main

Anyway around this in Swish?