s(CASP) and RDF, knowledge graphs and the Semantic Web

RDF is very good at stating facts, and we have great online databases where we can get facts.
s(CASP) is very good at human-like reasoning, especially with negation.

In trying to put those two together I made this little test:

% Test reasoning from rdf facts using scasp


:- use_module(library(scasp)).
:- use_module(library(semweb/rdf11)).

:- style_check(-discontiguous).
:- rdf_register_prefix(ex,'https://www.example.com/').
:- rdf_register_prefix(swi,'https://www.swi-prolog.org/rdf/entity').


% Scasp code
thinks(X) :- human(X).
human(X) :- programmer(X).

programmer(X) :- rdf(X,rdf:type,ex:programmer).


% prolog
test :-
   Jan = swi:'Jan',
   rdf_assert(swi:'Jan',rdf:type,ex:programmer),
   scasp(thinks(Jan)).

But I get this error:

1 ?- test.
ERROR: No permission to scasp procedure `rdf_db:rdf/3'
ERROR: In:
ERROR:   [37] throw(error(permission_error(scasp,procedure,...),_1512))
ERROR:   [33] scasp_dyncall:body_calls((rdf_db: ...,post_object(_1570,_1572)),rdf11,_1554) at /home/u/.local/share/swi-prolog/pack/scasp/prolog/scasp/dyncall.pl:256
ERROR:   [31] scasp_dyncall:predicate_calls(rdf11:rdf(_1614,_1616,_1618),_1604) at /home/u/.local/share/swi-prolog/pack/scasp/prolog/scasp/dyncall.pl:252
[...]

The reason is because rdf/3 can not be converted into an scasp goal.

I think a sensible solution is my old proposal of allowing {} to annotate goals that should be run in prolog only, and considered to be true scasp facts if they succeed. This would be in addition to the nice dyncall facility already there.

Somethinmg like:

programmer(X) :-  { rdf(X,rdf:type,ex:programmer) }.

much like we do with DCGs.

any comments?

It is not that easy :frowning: The problem is that we need the dual rules that implement the constructive negation of a goal. The dual rule shall create a constraint on X that is true for any X for which rdf(X,rdf:type,ex:programmer) is false. In its current approach these are disequality constraints that state “X is not in List” and thus we must construct a list with all non-programmers. Constructing the dual is not that easy for the general case.

Alternatively we could have the user defining a new constraint that expresses negated RDF rules. Now we need to deal with the interaction of this constraint and the built-in disequality constraint. Unfortunately properly implementing constraint reasoners requires a lot of competences …

The alternative we are looking into is to to use Prolog to assemble an as small as possible set of rules and facts and use scasp_assert/1 to build the scasp program.

At least, this is my current understanding of the state of affairs.

P.s. Note that you could also simply state programmer(X) as a fact. The s(CASP) solver may now come up with solutions with some constraints on X. Now go to the RDF and find data that satisfy the constraints. Just popped up in my head, so could be nonsense :slight_smile:

3 Likes

It would be nice if you could have an s(CASP) module, then do something like

assert_in_scasp_module(module_name,programmer(X)) :- rdf(...).
scasp(module_name,thinks(Jan)).

I think I did not explain myself well, I didn’t mean for prolog to have to implement the dual rule. Please see below for what I meant.

This is more along the lines of what I was thinking, the simple thought I had in my head was this:

handle_prolog_call(Goal) :-
   call(Goal)
   -> scasp_assert(Goal)
   ;   scasp_assert(-Goal).

The generation of duals, etc would be handled by sCASP, and the limitation is that
within {} you can only have a head (not conjunctions, negations, etc). I think this limitation is okay.

Am I missing something?
EDIT: this also implies that goal runs as once(Goal), which I also think is okay as a limitation.

EDIT2: In essence, the {} is just generating sCASP code on the fly.

EDIT3: Also, the prolog code is not allowed to bind new values into sCASP logical variables, only sCASP is allowed to bind variables. I also think this limitation is okay.

2 Likes

Jason,
I think scasp_assert already does something like this, but I have not played with it yet.

This could be one way. There are more possible interpretations though. We could also interpred {Goal} to find, at compile time, all solutions of Goal and handle this as an anonymous predicate with the answers as clauses. So,

 { rdf(X, rdf:type, ex:programmer) }

Is than interpreted as findall(anon1(X), rdf(X, rdf:type, ex:programmer), Clauses) where we replace the {…} by anon1(X) and assert the and assert the clauses, leaving the rest to s(CASP).

Yet another way is to do this at runtime, where we may know X or have constraints on X and we do the above just-in-time. The disadvantage is that we may get different calls to the {…} and we may have to produce multiple dynamic rule sets.

I think that is rather dubious. The Prolog failure is NAF.

Yes. You can already do

forall(rdf(X, rdf:type, ex:programmer),
       scasp_assert(programmer(X)).

Technically that is the same as the first proposal above. Note however that s(CASP) scales poorly for predicates with a lot of facts because the dual rules explode :frowning:

2 Likes

Yes, I think this are all good options worth considering.

Yes, my idea here was to reinterpret, semantically, and only within sCASP, the prolog NAF as a classical definite negation. There is of course the option to translate it into a NAF also within sCASP and that may be okay also; perhaps a per-code-chunk option on how to treat a prolog failure within sCASP would be the best way, like we do with regular expressions, {...}/c classical negation, {...}/f for negation as failure.

yes, don’t know what to do about this…did you run some benchmarks to see when the number of facts becomes unbearable?

1 Like