Skip to content

Commit

Permalink
further support for reasoning/n3plus1 (N3 plus increments like RDF 1.…
Browse files Browse the repository at this point in the history
…1, RDF 1.2, functional terms, ...)
  • Loading branch information
josd committed Oct 18, 2024
1 parent a5800bc commit fdb8863
Show file tree
Hide file tree
Showing 8 changed files with 72 additions and 30 deletions.
1 change: 1 addition & 0 deletions RELEASE
Original file line number Diff line number Diff line change
@@ -1,5 +1,6 @@
EYE release

v10.26.3 (2024-10-18) further support for reasoning/n3plus1 (N3 plus increments like RDF 1.1, RDF 1.2, functional terms, ...)
v10.26.2 (2024-10-18) testing reasoning/n3+1
v10.26.1 (2024-10-18) introducing (~ functor args) functional terms
v10.26.0 (2024-10-18) using RDF star to describe logic rules and queries
Expand Down
2 changes: 1 addition & 1 deletion VERSION
Original file line number Diff line number Diff line change
@@ -1 +1 @@
10.26.2
10.26.3
43 changes: 28 additions & 15 deletions eye.pl
Original file line number Diff line number Diff line change
Expand Up @@ -22,7 +22,7 @@
:- catch(use_module(library(process)), _, true).
:- catch(use_module(library(http/http_open)), _, true).

version_info('EYE v10.26.2 (2024-10-18)').
version_info('EYE v10.26.3 (2024-10-18)').

license_info('MIT License

Expand Down Expand Up @@ -78,6 +78,7 @@
--quiet quiet mode
--random-seed create random seed for e:random built-in
--rdf-list-output output lists as RDF lists
--rdf-star-output output as RDF star data
--restricted restricting to core built-ins
--rule-histogram output rule histogram info on stderr
--skolem-genid <genid> use <genid> in Skolem IRIs
Expand All @@ -86,7 +87,6 @@
--strings output log:outputString objects on stdout
--tactic limited-answer <nr> give only a limited number of answers
--tactic linear-select select each rule only once
--trig-output output as TriG data
--version show version info
--warn output warning info on stderr
--wcache <uri> <file> to tell that <uri> is cached as <file>
Expand Down Expand Up @@ -838,10 +838,10 @@
opts(['--tactic', Tactic|_], _) :-
!,
throw(not_supported_tactic(Tactic)).
opts(['--trig-output'|Argus], Args) :-
opts(['--rdf-star-output'|Argus], Args) :-
!,
retractall(flag('trig-output')),
assertz(flag('trig-output')),
retractall(flag('rdf-star-output')),
assertz(flag('rdf-star-output')),
opts(Argus, Args).
opts(['--version'|_], _) :-
!,
Expand Down Expand Up @@ -2161,7 +2161,7 @@
verb(P, Tp),
object(O, To),
reifiedtriplename(N),
{ ( flag('trig-output')
{ ( flag('rdf-star-output')
-> append([['\'<http://www.w3.org/1999/02/22-rdf-syntax-ns#reifies>\''(N, triple(S, P, O))], Ts, Tp, To], T)
; append([Ts, Tp, To], T)
)
Expand Down Expand Up @@ -4297,7 +4297,10 @@
wt(X),
write('}').
wt2('<http://www.w3.org/2000/10/swap/log#implies>'(X, Y)) :-
\+flag('trig-output'),
( retract(flag('rdf-star-output'))
-> assertz(flag('no-rdf-star-output'))
; true
),
( flag(nope)
-> U = X
; ( X = when(A, B)
Expand Down Expand Up @@ -4378,6 +4381,10 @@
-> retract(rule_uvar(_))
; true
),
( retract(flag('no-rdf-star-output'))
-> assertz(flag('rdf-star-output'))
; true
),
!.
wt2(':-'(X, Y)) :-
( rule_uvar(R)
Expand Down Expand Up @@ -4406,7 +4413,10 @@
),
!.
wt2('<http://www.w3.org/2000/10/swap/log#query>'(X, Y)) :-
\+flag('trig-output'),
( retract(flag('rdf-star-output'))
-> assertz(flag('no-rdf-star-output'))
; true
),
( rule_uvar(R)
-> true
; R = [],
Expand All @@ -4431,6 +4441,11 @@
-> retract(ncllit)
; true
),
!,
( retract(flag('no-rdf-star-output'))
-> assertz(flag('rdf-star-output'))
; true
),
!.
wt2(quad(triple(S, P, O), G)) :-
!,
Expand Down Expand Up @@ -4522,7 +4537,8 @@
wp(P),
write(' '),
wg(O),
( findvar(N, beta)
( \+flag('rdf-star-output'),
findvar(N, beta)
-> true
; write(' ~ '),
wg(N)
Expand Down Expand Up @@ -4568,7 +4584,7 @@
; F = ':-'
)
)
-> ( flag('trig-output'),
-> ( flag('rdf-star-output'),
nb_getval(keep_ng, true)
-> ( graph(N, X)
-> true
Expand All @@ -4582,7 +4598,7 @@
; true
),
wt(N)
; ( flag('trig-output')
; ( flag('rdf-star-output')
-> nb_setval(keep_ng, true)
; true
),
Expand Down Expand Up @@ -4622,17 +4638,14 @@
write('a').
wp('<http://www.w3.org/2000/10/swap/log#implies>') :-
\+flag('no-qnames'),
\+flag('trig-output'),
!,
write('=>').
wp(':-') :-
\+flag('no-qnames'),
\+flag('trig-output'),
!,
write('<=').
wp('<http://www.w3.org/2000/10/swap/log#query>') :-
\+flag('no-qnames'),
\+flag('trig-output'),
!,
write('=^').
wp(X) :-
Expand All @@ -4659,7 +4672,7 @@
wl(Y).

wm(A) :-
( flag('trig-output'),
( flag('rdf-star-output'),
raw_type(A, '<http://www.w3.org/2000/10/swap/log#Literal>')
-> write('[] '),
wp('<http://www.w3.org/1999/02/22-rdf-syntax-ns#value>'),
Expand Down
Binary file modified eye.zip
Binary file not shown.
2 changes: 1 addition & 1 deletion reasoning/n3plus1/README
Original file line number Diff line number Diff line change
Expand Up @@ -2,4 +2,4 @@
N3 plus 1
---------

Testing RDF 1.x and functional terms in N3
N3 plus increments like RDF 1.1, RDF 1.2, functional terms, ...
15 changes: 10 additions & 5 deletions reasoning/n3plus1/in.n3
Original file line number Diff line number Diff line change
Expand Up @@ -3,18 +3,21 @@
@prefix log: <http://www.w3.org/2000/10/swap/log#>.
@prefix : <http://example.org/#>.

# triple with blank node graphs
_:g :h _:i.

# blank node graphs
_:bng_1 {
_:g {
:s :p _:x.
}

_:bng_2 {
_:i {
:a :b :c.
:d :e _:x.
}

# additional quad
:s :p :o _:bng_1.
:s :p :o _:g.

# derive trig graph
{
Expand Down Expand Up @@ -45,9 +48,11 @@ _:bng_2 {
{| :from 1964; :to 1975 |}
{| :from 1980; :to 2001 |} .

# functional term
:ann a (~ :good :Poet).
# functional terms
(~ :s (~ :s 0)) a :PeanoNumber.
:tom a (~ :good :Pilot).

# query
{ ?S ?P ?O } =^ { ?S ?P ?O }.
{ ?S graph:statement ?O } =^ { ?S graph:statement ?O }.
{ ?S => ?O } =^ { ?S => ?O }.
37 changes: 30 additions & 7 deletions reasoning/n3plus1/out.n3
Original file line number Diff line number Diff line change
@@ -1,21 +1,29 @@
@prefix : <http://example.org/#>.
@prefix rdf: <http://www.w3.org/1999/02/22-rdf-syntax-ns#>.
@prefix graph: <http://www.w3.org/2000/10/swap/graph#>.
@prefix var: <http://www.w3.org/2000/10/swap/var#>.

:s :p << :d :e :f >>.
_:e_g_1 :h _:e_i_1.
:s :p << :d :e :f ~ _:bne_21 >>.
:s :p << :g :h :i ~ :x >>.
:s :p :o.
_:bne_21 rdf:reifies <<( :d :e :f )>>.
:x rdf:reifies <<( :g :h :i )>>.
:r rdf:reifies <<( :a :b _:e_x_1 )>>.
:r rdf:reifies <<( :a :b _:e_y_1 )>>.
:x rdf:reifies <<( :s :p _:bn_1 )>>.
<< :a :b _:e_x_1 ~ :r >> :c :d.
<< :a :b _:e_y_1 ~ :r >> :c :d.
_:bn_1 :q1 "A".
_:bn_1 :q2 "B".
<< :s :p :o >> :j :k.
<< :s :p :o ~ _:bne_28 >> :j :k.
:liz :marriedTo :richard.
<< :liz :marriedTo :richard >> :from 1964 .
<< :liz :marriedTo :richard >> :from 1980 .
<< :liz :marriedTo :richard >> :to 1975 .
<< :liz :marriedTo :richard >> :to 2001 .
:ann a (~ :good :Poet).
<< :liz :marriedTo :richard ~ _:bne_31 >> :from 1964 .
<< :liz :marriedTo :richard ~ _:bne_34 >> :from 1980 .
<< :liz :marriedTo :richard ~ _:bne_31 >> :to 1975 .
<< :liz :marriedTo :richard ~ _:bne_34 >> :to 2001 .
(~ :s (~ :s 0)) a :PeanoNumber.
:tom a (~ :good :Pilot).
{
?U_1 graph:statement ?U_2.
?U_2 graph:member {
Expand All @@ -27,3 +35,18 @@ _:bn_1 :q2 "B".
:x :y :z.
}.
}.

_:e_g_1 {
:s :p _:e_x_1.
:s :p :o.
}

_:e_i_1 {
:a :b :c.
:d :e _:e_x_1.
}

_:sk_0 {
:u :v :w.
:x :y :z.
}
2 changes: 1 addition & 1 deletion reasoning/n3plus1/test
Original file line number Diff line number Diff line change
@@ -1,2 +1,2 @@
#!/bin/bash
eye --quiet --skolem-genid 8b98b360-9a70-4845-b52c-c675af60ad01 --wcache https://eyereasoner.github.io/eye/reasoning .. --nope https://eyereasoner.github.io/eye/reasoning/n3plus1/in.n3 --output out.n3
eye --quiet --skolem-genid 8b98b360-9a70-4845-b52c-c675af60ad01 --wcache https://eyereasoner.github.io/eye/reasoning .. --nope --rdf-star-output https://eyereasoner.github.io/eye/reasoning/n3plus1/in.n3 --output out.n3

0 comments on commit fdb8863

Please sign in to comment.