Skip to content

Commit

Permalink
running with rdf12 reifier
Browse files Browse the repository at this point in the history
  • Loading branch information
josd committed Sep 24, 2024
1 parent d0fc894 commit 79dec9e
Show file tree
Hide file tree
Showing 6 changed files with 28 additions and 36 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.23.4 (2024-09-25) running with rdf12 reifier
v10.23.3 (2024-09-23) fixing makevars zeta
v10.23.2 (2024-09-22) fixing log:copy
v10.23.1 (2024-09-22) running reasoning/lingua/lingua.n3
Expand Down
2 changes: 1 addition & 1 deletion VERSION
Original file line number Diff line number Diff line change
@@ -1 +1 @@
10.23.3
10.23.4
25 changes: 14 additions & 11 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.23.3 (2024-09-23)').
version_info('EYE v10.23.4 (2024-09-25)').

license_info('MIT License

Expand Down Expand Up @@ -1914,8 +1914,8 @@
[].

edgename(N) -->
['~'],
expression(N, []),
['|'],
!.
edgename(N) -->
{ gensym('bne_', B),
Expand Down Expand Up @@ -2139,13 +2139,15 @@
verb(P, []),
object(O, []),
[rp_gt_gt].
pathitem(edge(N, triple(S, P, O)), []) -->
pathitem(edge(N, triple(S, P, O)), T) -->
[lt_lt],
!,
subject(S, Ts),
verb(P, Tp),
object(O, To),
{ append([Ts, Tp, To], T)
},
edgename(N),
subject(S, []),
verb(P, []),
object(O, []),
[gt_gt].
pathitem(Node, []) -->
['{'],
Expand Down Expand Up @@ -3408,6 +3410,7 @@
punctuation(0'>, '>').
punctuation(0'$, '$').
punctuation(0'|, '|').
punctuation(0'~, '~').

skip_line(-1, _, -1) :-
!.
Expand Down Expand Up @@ -4391,16 +4394,16 @@
wt2(edge(N, triple(S, P, O))) :-
!,
write('<< '),
( findvar(N, beta)
-> true
; wg(N),
write(' | ')
),
wg(S),
write(' '),
wp(P),
write(' '),
wg(O),
( findvar(N, beta)
-> true
; write(' ~ '),
wg(N)
),
write(' >>').
wt2(is(O, T)) :-
!,
Expand Down
Binary file modified eye.zip
Binary file not shown.
17 changes: 7 additions & 10 deletions reasoning/temp/edge-output.ttl
Original file line number Diff line number Diff line change
Expand Up @@ -3,22 +3,19 @@

:s :p <<( :a :b :c )>>.
:s :p << :d :e :f >>.
:s :p << :x | :g :h :i >>.
:s :p << :g :h :i ~ :x >>.
:s :p :o.
<< :s :p :o >> :j :k.
<< :y | :s :p :o >> :j :k.
<< :y | :s :p :o >> :l :m.
<< :y | :s :p :o >> :l :n.
:r rdf:reifies <<( :u :v :w )>>.
_:e_s_1 rdf:reifies <<( :u :v :w )>>.
_:e_t_1 rdf:reifies <<( :u :v :w )>>.
:r :y :z.
_:e_s_1 :y :z.
_:e_t_1 :y :z.
:liz :marriedTo :richard.
<< :m1 | :liz :marriedTo :richard >> :from 1964 .
<< :m2 | :liz :marriedTo :richard >> :from 1980 .
<< :m1 | :liz :marriedTo :richard >> :to 1975 .
<< :m2 | :liz :marriedTo :richard >> :to 2001 .
<< :r | :a :b _:e_x_1 >> :c :d.
<< :r | :a :b _:e_y_1 >> :c :d.
<< :liz :marriedTo :richard >> :from 1964 .
<< :liz :marriedTo :richard >> :from 1980 .
<< :liz :marriedTo :richard >> :to 1975 .
<< :liz :marriedTo :richard >> :to 2001 .
<< :a :b _:e_x_1 ~ :r >> :c :d.
<< :a :b _:e_y_1 ~ :r >> :c :d.
19 changes: 5 additions & 14 deletions reasoning/temp/edge.ttl
Original file line number Diff line number Diff line change
@@ -1,28 +1,19 @@
@base <http://example.org/> .

@prefix rdf: <http://www.w3.org/1999/02/22-rdf-syntax-ns#>.
@prefix : <http://example.org/#> .

:s :p <<( :a :b :c )>> .
:s :p << :d :e :f >> .
:s :p << :x | :g :h :i >> .
# :s :p << :x | :g2 :h2 :i2 >> . # throws a malformed_edge_extra_reifies/3 exception
:s :p << :g :h :i ~ :x >> .

:s :p :o {| :j :k |} .
:s :p :o {| :y | :j :k |} .
:s :p :o {| :y | :j :k; :l :m |} .
:s :p :o {| :y | :j :k; :l :m, :n |} .

:r rdf:reifies <<( :u :v :w )>>; :y :z .
# :r rdf:reifies <<( :u2 :v2 :w2 )>>; :y :z . # throws a malformed_edge_extra_reifies/3 exception
_:s rdf:reifies <<( :u :v :w )>>; :y :z .
_:t rdf:reifies <<( :u :v :w )>>; :y :z .

# from https://lists.w3.org/Archives/Public/public-rdf-star-wg/2024Apr/0137.html
:liz :marriedTo :richard
{| <#m1> | :from 1964; :to 1975 |}
{| <#m2> | :from 1980; :to 2001 |} .
{| :from 1964; :to 1975 |}
{| :from 1980; :to 2001 |} .

# from https://lists.w3.org/Archives/Public/public-rdf-star-wg/2024Apr/0147.html
<< :r | :a :b _:x >> :c :d .
<< :r | :a :b _:y >> :c :d .
<< :a :b _:x ~ :r >> :c :d .
<< :a :b _:y ~ :r >> :c :d .

0 comments on commit 79dec9e

Please sign in to comment.