Skip to content

Commit

Permalink
using lingua variables in the var: namespace
Browse files Browse the repository at this point in the history
  • Loading branch information
josd committed Dec 12, 2023
1 parent afd9f8c commit 2a61255
Show file tree
Hide file tree
Showing 31 changed files with 536 additions and 1,224 deletions.
1 change: 1 addition & 0 deletions RELEASE
Original file line number Diff line number Diff line change
@@ -1,5 +1,6 @@
EYE release

v9.0.13 (2023-12-12) using lingua variables in the var: namespace
v9.0.12 (2023-12-12) reverting lingua
v9.0.11 (2023-12-11) for isomorphic rules use the rule with the least blank nodes
v9.0.10 (2023-12-11) using lingua:varCount to make rules safe
Expand Down
2 changes: 1 addition & 1 deletion VERSION
Original file line number Diff line number Diff line change
@@ -1 +1 @@
9.0.12
9.0.13
59 changes: 22 additions & 37 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 v9.0.12 (2023-12-12)').
version_info('EYE v9.0.13 (2023-12-12)').

license_info('MIT License

Expand Down Expand Up @@ -645,34 +645,23 @@
),
% forward rule
assertz(implies((
'<http://www.w3.org/1999/02/22-rdf-syntax-ns#type>'(R, '<http://www.w3.org/2000/10/swap/lingua#ForwardRule>'),
'<http://www.w3.org/2000/10/swap/lingua#vars>'(R, U),
getlist(U, V),
'<http://www.w3.org/2000/10/swap/lingua#premise>'(R, K),
'<http://www.w3.org/1999/02/22-rdf-syntax-ns#type>'(R, '<http://eyereasoner.github.io/lingua#ForwardRule>'),
'<http://eyereasoner.github.io/lingua#premise>'(R, K),
getconj(K, A),
'<http://www.w3.org/2000/10/swap/lingua#conclusion>'(R, H),
'<http://eyereasoner.github.io/lingua#conclusion>'(R, H),
getconj(H, B),
( flag(explain),
B \= false
-> conj_append(B, remember(answer('<http://www.w3.org/2000/10/swap/lingua#bindings>', R, U)), D)
; D = B
),
makevars([A, D], [Q, I], beta(V))
findvars([A, B], V, alpha),
makevars([A, B], [Q, I], beta(V))
), '<http://www.w3.org/2000/10/swap/log#implies>'(Q, I), '<>')),
% backward rule
assertz(implies((
'<http://www.w3.org/1999/02/22-rdf-syntax-ns#type>'(R, '<http://www.w3.org/2000/10/swap/lingua#BackwardRule>'),
'<http://www.w3.org/2000/10/swap/lingua#vars>'(R, U),
getlist(U, V),
'<http://www.w3.org/2000/10/swap/lingua#premise>'(R, K),
'<http://www.w3.org/1999/02/22-rdf-syntax-ns#type>'(R, '<http://eyereasoner.github.io/lingua#BackwardRule>'),
'<http://eyereasoner.github.io/lingua#premise>'(R, K),
getconj(K, A),
'<http://www.w3.org/2000/10/swap/lingua#conclusion>'(R, H),
'<http://eyereasoner.github.io/lingua#conclusion>'(R, H),
getconj(H, B),
( flag(explain)
-> conj_append(A, remember(answer('<http://www.w3.org/2000/10/swap/lingua#bindings>', R, U)), D)
; D = A
),
makevars(':-'(B, D), C, beta(V)),
findvars([A, B], V, alpha),
makevars(':-'(B, A), C, beta(V)),
copy_term_nat(C, CC),
labelvars(CC, 0, _, avar),
( \+cc(CC)
Expand All @@ -683,19 +672,14 @@
)), true, '<>')),
% query rule
assertz(implies((
'<http://www.w3.org/1999/02/22-rdf-syntax-ns#type>'(R, '<http://www.w3.org/2000/10/swap/lingua#QueryRule>'),
'<http://www.w3.org/2000/10/swap/lingua#vars>'(R, U),
getlist(U, V),
'<http://www.w3.org/2000/10/swap/lingua#premise>'(R, K),
'<http://www.w3.org/1999/02/22-rdf-syntax-ns#type>'(R, '<http://eyereasoner.github.io/lingua#QueryRule>'),
'<http://eyereasoner.github.io/lingua#premise>'(R, K),
getconj(K, A),
'<http://www.w3.org/2000/10/swap/lingua#conclusion>'(R, H),
'<http://eyereasoner.github.io/lingua#conclusion>'(R, H),
getconj(H, B),
djiti_answer(answer(B), J),
( flag(explain)
-> conj_append(A, remember(answer('<http://www.w3.org/2000/10/swap/lingua#bindings>', R, U)), D)
; D = A
),
makevars(implies(D, J, '<>'), C, beta(V)),
findvars([A, B], V, alpha),
makevars(implies(A, J, '<>'), C, beta(V)),
copy_term_nat(C, CC),
labelvars(CC, 0, _, avar),
( \+cc(CC)
Expand Down Expand Up @@ -1504,7 +1488,7 @@
ttl_n3p(O, Object),
Triple =.. [Predicate, Subject, Object],
djiti_assertz(Triple),
( Predicate = '<http://www.w3.org/2000/10/swap/lingua#premise>',
( Predicate = '<http://eyereasoner.github.io/lingua#premise>',
\+flag(lingua)
-> assertz(flag(lingua))
; true
Expand Down Expand Up @@ -1566,7 +1550,7 @@
-> nb_setval(current_scope, Scope)
; true
),
( Rt = '<http://www.w3.org/2000/10/swap/lingua#premise>'(_, _),
( Rt = '<http://eyereasoner.github.io/lingua#premise>'(_, _),
\+flag(lingua)
-> assertz(flag(lingua))
; true
Expand Down Expand Up @@ -2628,7 +2612,7 @@
verb(Item, Triples1),
{ prolog_verb(Item, Verb),
( atomic(Verb),
Verb = '\'<http://www.w3.org/2000/10/swap/lingua#premise>\'',
Verb = '\'<http://eyereasoner.github.io/lingua#premise>\'',
\+flag(lingua)
-> assertz(flag(lingua))
; true
Expand Down Expand Up @@ -11105,7 +11089,7 @@
recursion(B)
),
( flag(lingua)
-> A = '<http://www.w3.org/2000/10/swap/lingua#scope>'
-> A = '<http://eyereasoner.github.io/lingua#scope>'
; nb_getval(scope, A)
).

Expand Down Expand Up @@ -12076,7 +12060,8 @@
!,
distinct(C, D),
findvars(D, G, beta),
( D \= G
( flag(blogic),
D \= G
-> throw(invalid_graffiti(D, in(A)))
; true
),
Expand Down
Binary file modified eye.zip
Binary file not shown.
89 changes: 33 additions & 56 deletions reasoning/lingua/acp.ttl
Original file line number Diff line number Diff line change
@@ -1,7 +1,8 @@
@prefix rdf: <http://www.w3.org/1999/02/22-rdf-syntax-ns#>.
@prefix list: <http://www.w3.org/2000/10/swap/list#>.
@prefix log: <http://www.w3.org/2000/10/swap/log#>.
@prefix lingua: <http://www.w3.org/2000/10/swap/lingua#>.
@prefix lingua: <http://eyereasoner.github.io/lingua#>.
@prefix var: <http://eyereasoner.github.io/var#>.
@prefix : <http://example.org/ns#>.

:test1
Expand All @@ -15,89 +16,65 @@
:noneOf :D.

:acp_rule1 a lingua:BackwardRule;
lingua:vars (
_:Pol
_:Test
_:Field
_:X
);
lingua:conclusion (
_:Pol :pass :allOfTest
var:Pol :pass :allOfTest
);
lingua:premise (
_:Test :policy _:Pol
_:Pol rdf:type :Policy
var:Test :policy var:Pol
var:Pol rdf:type :Policy
(
(
_:Pol :allOf _:Field
var:Pol :allOf var:Field
)
(
_:Test :has _:Field
var:Test :has var:Field
)
) log:forAllIn _:X
) log:forAllIn var:X
).

:acp_rule2 a lingua:BackwardRule;
lingua:vars (
_:Pol
_:Test
_:Field
_:List
_:X
_:L
);lingua:conclusion (
_:Pol :pass :anyOfTest
lingua:conclusion (
var:Pol :pass :anyOfTest
);
lingua:premise (
_:Test :policy _:Pol
_:Pol rdf:type :Policy
var:Test :policy var:Pol
var:Pol rdf:type :Policy
(
_:Field
var:Field
(
_:Pol :anyOf _:Field
_:Test :has _:Field
var:Pol :anyOf var:Field
var:Test :has var:Field
)
_:List
) log:collectAllIn _:X
_:List list:length _:L
_:L log:notEqualTo 0
var:List
) log:collectAllIn var:X
var:List list:length var:L
var:L log:notEqualTo 0
).

:acp_rule3 a lingua:BackwardRule;
lingua:vars (
_:Pol
_:Test
_:Field
_:List
_:X
_:L
);
lingua:conclusion (
_:Pol :pass :noneOfTest
var:Pol :pass :noneOfTest
);
lingua:premise (
_:Test :policy _:Pol
_:Pol rdf:type :Policy
(_:Field (
_:Pol :noneOf _:Field
_:Test :has _:Field
) _:List) log:collectAllIn _:X
_:List list:length _:L
_:L log:equalTo 0
var:Test :policy var:Pol
var:Pol rdf:type :Policy
(var:Field (
var:Pol :noneOf var:Field
var:Test :has var:Field
) var:List) log:collectAllIn var:X
var:List list:length var:L
var:L log:equalTo 0
).

# query
:acp_query a lingua:QueryRule;
lingua:vars (
_:Pol
);
lingua:premise (
_:Pol rdf:type :Policy
_:Pol :pass :allOfTest
_:Pol :pass :anyOfTest
_:Pol :pass :noneOfTest
var:Pol rdf:type :Policy
var:Pol :pass :allOfTest
var:Pol :pass :anyOfTest
var:Pol :pass :noneOfTest
);
lingua:conclusion (
:test :for _:Pol
:test :for var:Pol
:test :is true
).
16 changes: 6 additions & 10 deletions reasoning/lingua/append.ttl
Original file line number Diff line number Diff line change
@@ -1,6 +1,7 @@
@prefix list: <http://www.w3.org/2000/10/swap/list#>.
@prefix log: <http://www.w3.org/2000/10/swap/log#>.
@prefix lingua: <http://www.w3.org/2000/10/swap/lingua#>.
@prefix lingua: <http://eyereasoner.github.io/lingua#>.
@prefix var: <http://eyereasoner.github.io/var#>.
@prefix : <http://example.org/ns#>.

:Let :param1 (
Expand All @@ -16,16 +17,11 @@

# query
:append_query a lingua:QueryRule;
lingua:vars (
_:X1
_:X2
_:Y
);
lingua:premise (
:Let :param1 _:X1
:Let :param2 _:X2
(_:X1 _:X2) list:append _:Y
:Let :param1 var:X1
:Let :param2 var:X2
(var:X1 var:X2) list:append var:Y
);
lingua:conclusion (
(_:X1 _:X2) :append _:Y
(var:X1 var:X2) :append var:Y
).
12 changes: 4 additions & 8 deletions reasoning/lingua/backward.ttl
Original file line number Diff line number Diff line change
@@ -1,24 +1,20 @@
@prefix math: <http://www.w3.org/2000/10/swap/math#>.
@prefix lingua: <http://www.w3.org/2000/10/swap/lingua#>.
@prefix lingua: <http://eyereasoner.github.io/lingua#>.
@prefix var: <http://eyereasoner.github.io/var#>.
@prefix : <http://example.org/ns#>.

# see https://www.w3.org/2000/10/swap/doc/tutorial-1.pdf page 17
# something is more interesting if it is greater
:backward_rule a lingua:BackwardRule;
lingua:vars (
_:X
_:Y
);
lingua:conclusion (
_:X :moreInterestingThan _:Y
var:X :moreInterestingThan var:Y
);
lingua:premise (
_:X math:greaterThan _:Y
var:X math:greaterThan var:Y
).

# query
:backward_query a lingua:QueryRule;
lingua:vars ();
lingua:premise (
5 :moreInterestingThan 3
);
Expand Down
Loading

0 comments on commit 2a61255

Please sign in to comment.