Skip to content

Commit

Permalink
implicit global scope of blank nodes
Browse files Browse the repository at this point in the history
  • Loading branch information
josd committed Oct 17, 2023
1 parent deea0e2 commit d27d281
Show file tree
Hide file tree
Showing 159 changed files with 53 additions and 67 deletions.
1 change: 1 addition & 0 deletions RELEASE
Original file line number Diff line number Diff line change
@@ -1,5 +1,6 @@
EYE release

v5.1.0 (2023-10-17) implicit global scope of blank nodes
v5.0.10 (2023-10-15) testing s(urface) equ(ivalent) ent(ailment)s
v5.0.9 (2023-10-15) Surface Equivalent Entailment - SEE
v5.0.8 (2023-10-15) checking surface equivalent entailment
Expand Down
2 changes: 1 addition & 1 deletion VERSION
Original file line number Diff line number Diff line change
@@ -1 +1 @@
5.0.10
5.1.0
41 changes: 15 additions & 26 deletions eye.pl
Original file line number Diff line number Diff line change
Expand Up @@ -21,7 +21,7 @@
:- use_module(library(pcre)).
:- catch(use_module(library(http/http_open)), _, true).

version_info('EYE v5.0.10 (2023-10-15)').
version_info('EYE v5.1.0 (2023-10-17)').

license_info('MIT License

Expand Down Expand Up @@ -963,8 +963,6 @@
% DEPRECATED
opts(['--blogic'|Argus], Args) :-
!,
retractall(flag(blogic)),
assertz(flag(blogic)),
opts(Argus, Args).
opts(['--csv-separator', Separator|Argus], Args) :-
!,
Expand Down Expand Up @@ -2002,6 +2000,12 @@
tr_tr(A, A) :-
number(A),
!.
tr_tr(triple(A, B, C), triple(D, E, F)) :-
G =.. [B, A, C],
\+sub_atom(B, 0, _, _, '_e_'),
!,
tr_tr(G, H),
H =.. [E, D, F].
tr_tr(A, B) :-
A =.. [C|D],
tr_tr(D, E),
Expand Down Expand Up @@ -2722,29 +2726,14 @@
}.
symbol(Name) -->
[bnode(Lbl)],
{ ( flag(blogic)
-> atom_codes(Lbl, LblCodes),
subst([[[0'-], [0'_, 0'M, 0'I, 0'N, 0'U, 0'S, 0'_]], [[0'.], [0'_, 0'D, 0'O, 0'T, 0'_]]], LblCodes, LblTidy),
atom_codes(Label, LblTidy),
( evar(Label, S, 0)
-> true
; atom_concat(Label, '_', M),
gensym(M, S),
assertz(evar(Label, S, 0))
)
; nb_getval(fdepth, D),
( D =:= 0
-> Label = Lbl
; atom_codes(Lbl, LblCodes),
subst([[[0'-], [0'_, 0'M, 0'I, 0'N, 0'U, 0'S, 0'_]], [[0'.], [0'_, 0'D, 0'O, 0'T, 0'_]]], LblCodes, LblTidy),
atom_codes(Label, LblTidy)
),
( evar(Label, S, D)
-> true
; atom_concat(Label, '_', M),
gensym(M, S),
assertz(evar(Label, S, D))
)
{ atom_codes(Lbl, LblCodes),
subst([[[0'-], [0'_, 0'M, 0'I, 0'N, 0'U, 0'S, 0'_]], [[0'.], [0'_, 0'D, 0'O, 0'T, 0'_]]], LblCodes, LblTidy),
atom_codes(Label, LblTidy),
( evar(Label, S, 0)
-> true
; atom_concat(Label, '_', M),
gensym(M, S),
assertz(evar(Label, S, 0))
),
( ( nb_getval(entail_mode, false),
nb_getval(fdepth, 0)
Expand Down
Binary file modified eye.zip
Binary file not shown.
20 changes: 10 additions & 10 deletions reasoning/bi/biA.n3
Original file line number Diff line number Diff line change
Expand Up @@ -492,12 +492,12 @@
{
{
<http://eyereasoner.github.io/eye/reasoning/bi/ab_c.n3> log:semantics {
:a :b _:e_c_14.
:a :b _:e_c_2.
}.
{
:a :b _:e_c_14.
:a :b _:e_c_2.
} log:equalTo {
:a :b _:e_c_14.
:a :b _:e_c_2.
}.
} => {
:loges3 :result true.
Expand Down Expand Up @@ -663,12 +663,12 @@
{
{
<http://eyereasoner.github.io/eye/reasoning/bi/ab_c.n3> log:semantics {
:a :b _:e_c_14.
:a :b _:e_c_2.
}.
{
:a :b _:e_c_14.
:a :b _:e_c_2.
} log:includes {
:a :b _:e_c_14.
:a :b _:e_c_2.
}.
} => {
:logis3 :result true.
Expand Down Expand Up @@ -791,10 +791,10 @@
{
{
<http://eyereasoner.github.io/eye/reasoning/bi/ab_c.n3> log:semantics {
:a :b _:e_c_14.
:a :b _:e_c_2.
}.
{
:a :b _:e_c_14.
:a :b _:e_c_2.
} log:notIncludes {
:a :b :c.
}.
Expand All @@ -805,13 +805,13 @@
{
{
<http://eyereasoner.github.io/eye/reasoning/bi/ab_c.n3> log:semantics {
:a :b _:e_c_14.
:a :b _:e_c_2.
}.
<http://eyereasoner.github.io/eye/reasoning/bi/abc.n3> log:semantics {
:a :b :c.
}.
{
:a :b _:e_c_14.
:a :b _:e_c_2.
} log:notIncludes {
:a :b :c.
}.
Expand Down
File renamed without changes.
File renamed without changes.
File renamed without changes.
File renamed without changes.
File renamed without changes.
File renamed without changes.
File renamed without changes.
File renamed without changes.
File renamed without changes.
File renamed without changes.
File renamed without changes.
File renamed without changes.
File renamed without changes.
File renamed without changes.
File renamed without changes.
File renamed without changes.
File renamed without changes.
File renamed without changes.
File renamed without changes.
File renamed without changes.
File renamed without changes.
File renamed without changes.
File renamed without changes.
File renamed without changes.
File renamed without changes.
File renamed without changes.
File renamed without changes.
File renamed without changes.
File renamed without changes.
File renamed without changes.
File renamed without changes.
File renamed without changes.
File renamed without changes.
File renamed without changes.
File renamed without changes.
File renamed without changes.
File renamed without changes.
File renamed without changes.
File renamed without changes.
File renamed without changes.
File renamed without changes.
File renamed without changes.
File renamed without changes.
File renamed without changes.
File renamed without changes.
File renamed without changes.
File renamed without changes.
File renamed without changes.
File renamed without changes.
File renamed without changes.
File renamed without changes.
File renamed without changes.
File renamed without changes.
File renamed without changes.
File renamed without changes.
File renamed without changes.
File renamed without changes.
File renamed without changes.
File renamed without changes.
File renamed without changes.
File renamed without changes.
File renamed without changes.
File renamed without changes.
File renamed without changes.
File renamed without changes.
File renamed without changes.
File renamed without changes.
File renamed without changes.
File renamed without changes.
File renamed without changes.
File renamed without changes.
File renamed without changes.
File renamed without changes.
File renamed without changes.
File renamed without changes.
File renamed without changes.
File renamed without changes.
File renamed without changes.
File renamed without changes.
File renamed without changes.
File renamed without changes.
File renamed without changes.
File renamed without changes.
File renamed without changes.
File renamed without changes.
File renamed without changes.
File renamed without changes.
File renamed without changes.
File renamed without changes.
File renamed without changes.
File renamed without changes.
File renamed without changes.
File renamed without changes.
File renamed without changes.
File renamed without changes.
File renamed without changes.
File renamed without changes.
File renamed without changes.
File renamed without changes.
File renamed without changes.
File renamed without changes.
File renamed without changes.
File renamed without changes.
File renamed without changes.
File renamed without changes.
File renamed without changes.
File renamed without changes.
File renamed without changes.
File renamed without changes.
File renamed without changes.
File renamed without changes.
File renamed without changes.
File renamed without changes.
File renamed without changes.
File renamed without changes.
File renamed without changes.
File renamed without changes.
File renamed without changes.
File renamed without changes.
File renamed without changes.
File renamed without changes.
File renamed without changes.
File renamed without changes.
File renamed without changes.
File renamed without changes.
File renamed without changes.
File renamed without changes.
File renamed without changes.
File renamed without changes.
File renamed without changes.
File renamed without changes.
File renamed without changes.
File renamed without changes.
File renamed without changes.
File renamed without changes.
File renamed without changes.
File renamed without changes.
File renamed without changes.
File renamed without changes.
File renamed without changes.
6 changes: 3 additions & 3 deletions reasoning/blogic/test
Original file line number Diff line number Diff line change
@@ -1,6 +1,6 @@
#!/bin/bash
for f in *.n3s
for f in *.n3
do
echo + eye --quiet --blogic --skolem-genid 8b98b360-9a70-4845-b52c-c675af60ad01 --nope $f --output $f.out
eye --quiet --blogic --skolem-genid 8b98b360-9a70-4845-b52c-c675af60ad01 --nope $f --output $f.out
echo + eye --quiet --skolem-genid 8b98b360-9a70-4845-b52c-c675af60ad01 --nope $f --output $f.out
eye --quiet --skolem-genid 8b98b360-9a70-4845-b52c-c675af60ad01 --nope $f --output $f.out
done
File renamed without changes.
File renamed without changes.
File renamed without changes.
18 changes: 8 additions & 10 deletions reasoning/blogic/unpack.n3s → reasoning/blogic/unpack.n3
Original file line number Diff line number Diff line change
Expand Up @@ -7,19 +7,19 @@
# sample data from RubenD
[] :data {
[] :package {
[] :content {
<<(_:c) log:onNeutralSurface {
:a :b _:c.
[] :package {
[] :content {
<<(_:c) log:onNeutralSurface {
:u :v _:c.
[] :package {
[] :content {
<<(_:c) log:onNeutralSurface {
:x :y _:c.
}; :usable_until :yesterday.
}>> :usable_until :yesterday.
}; :tag :invalid.
}; :usable_until :tomorrow; :p :o.
}>> :usable_until :tomorrow; :p :o.
}; :tag :valid.
}; :usable_until :next_week.
}>> :usable_until :next_week.
}; :tag :valid.
}.

Expand Down Expand Up @@ -50,8 +50,7 @@
_:b :package _:p.
} :unpack _:f>>.
_:p log:includes {
_:a :content _:c.
_:a :usable_until _:t.
<<_:a log:onNeutralSurface _:c>> :usable_until _:t.
}.
(:tomorrow :next_week) list:member _:t.
_:c graph:list _:l.
Expand All @@ -64,8 +63,7 @@
_:b :package _:p.
} :unpack true>>.
_:p log:includes {
_:a :content _:c.
_:a :usable_until _:t.
<<_:a log:onNeutralSurface _:c>> :usable_until _:t.
}.
(:yesterday :last_week) list:member _:t.
}.
Expand Down
Original file line number Diff line number Diff line change
@@ -1,4 +1,4 @@
@prefix : <http://example.org/ns#>.

:a :b _:e_c_1.
:u :v _:e_c_1.
:a :b _:e_c_1_5.
:u :v _:e_c_1_2_1.
File renamed without changes.
Original file line number Diff line number Diff line change
@@ -1,3 +1,3 @@
@prefix log: <http://www.w3.org/2000/10/swap/log#>.

() log:version "EYE v5.0.10 (2023-10-15)".
() log:version "EYE v5.1.0 (2023-10-17)".
File renamed without changes.
File renamed without changes.
4 changes: 2 additions & 2 deletions reasoning/iq/iqA.n3
Original file line number Diff line number Diff line change
@@ -1,7 +1,7 @@
@prefix : <http://example.org/test#>.

_:e_x_1 :says {
_:e_x_3 :knows :Albert.
_:e_x_1 :knows :Albert.
}.
:s :p :o.
:s :pp {
Expand All @@ -10,7 +10,7 @@ _:e_x_1 :says {
{
?U_0 :knows :Albert.
} => {
<http://eyereasoner.github.io/var#x_0> :knows :Kurt.
?U_0 :knows :Kurt.
}.
{
:e :p :a.
Expand Down
4 changes: 2 additions & 2 deletions reasoning/pack/out.n3
Original file line number Diff line number Diff line change
@@ -1,4 +1,4 @@
@prefix : <http://example.org/ns#>.

:a :b _:e_c_148.
:u :v _:e_c_164.
:a :b _:e_c_1_5.
:u :v _:e_c_1_2_1.
18 changes: 8 additions & 10 deletions reasoning/pack/unpack.n3
Original file line number Diff line number Diff line change
Expand Up @@ -7,19 +7,19 @@
# sample data from RubenD
[] :data {
[] :package {
[] :content {
<<(_:c) log:onNeutralSurface {
:a :b _:c.
[] :package {
[] :content {
<<(_:c) log:onNeutralSurface {
:u :v _:c.
[] :package {
[] :content {
<<(_:c) log:onNeutralSurface {
:x :y _:c.
}; :usable_until :yesterday.
}>> :usable_until :yesterday.
}; :tag :invalid.
}; :usable_until :tomorrow; :p :o.
}>> :usable_until :tomorrow; :p :o.
}; :tag :valid.
}; :usable_until :next_week.
}>> :usable_until :next_week.
}; :tag :valid.
}.

Expand Down Expand Up @@ -51,8 +51,7 @@
} :unpack ?f.
} <= {
?p log:includes {
?a :content ?c.
?a :usable_until ?t.
<<?a log:onNeutralSurface ?c>> :usable_until ?t.
}.
(:tomorrow :next_week) list:member ?t.
?c graph:list ?l.
Expand All @@ -66,8 +65,7 @@
} :unpack true.
} <= {
?p log:includes {
?a :content ?c.
?a :usable_until ?t.
<<?a log:onNeutralSurface ?c>> :usable_until ?t.
}.
(:yesterday :last_week) list:member ?t.
?c graph:list ?l.
Expand Down

0 comments on commit d27d281

Please sign in to comment.