Skip to content

Commit

Permalink
using lingua:varCount to make rules safe
Browse files Browse the repository at this point in the history
  • Loading branch information
josd committed Dec 11, 2023
1 parent 077e06e commit 0ddbe5b
Show file tree
Hide file tree
Showing 29 changed files with 255 additions and 840 deletions.
2 changes: 2 additions & 0 deletions RELEASE
Original file line number Diff line number Diff line change
@@ -1,5 +1,7 @@
EYE release

v9.0.10 (2023-12-11) using lingua:varCount to make rules safe
v9.0.10 (2023-12-11) using lingua:varCount to make rules safe
v9.0.9 (2023-12-08) adding experimental log:callNotBind built-in
v9.0.8 (2023-12-06) using linear lists for surfaces
v9.0.7 (2023-12-06) using linear lists for lingua
Expand Down
2 changes: 1 addition & 1 deletion VERSION
Original file line number Diff line number Diff line change
@@ -1 +1 @@
9.0.9
9.0.10
39 changes: 16 additions & 23 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.9 (2023-12-08)').
version_info('EYE v9.0.10 (2023-12-11)').

license_info('MIT License

Expand Down Expand Up @@ -646,33 +646,28 @@
% 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),
getconj(K, A),
'<http://www.w3.org/2000/10/swap/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))
'<http://www.w3.org/2000/10/swap/lingua#varCount>'(R, N),
findvars([A, B], U, beta),
distinct(U, V),
length(V, N),
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),
getconj(K, A),
'<http://www.w3.org/2000/10/swap/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)),
'<http://www.w3.org/2000/10/swap/lingua#varCount>'(R, N),
findvars([A, B], U, beta),
distinct(U, V),
length(V, N),
makevars(':-'(B, A), C, beta(V)),
copy_term_nat(C, CC),
labelvars(CC, 0, _, avar),
( \+cc(CC)
Expand All @@ -684,18 +679,16 @@
% 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),
getconj(K, A),
'<http://www.w3.org/2000/10/swap/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)),
'<http://www.w3.org/2000/10/swap/lingua#varCount>'(R, N),
findvars([A, B], U, beta),
distinct(U, V),
length(V, N),
makevars(implies(A, J, '<>'), C, beta(V)),
copy_term_nat(C, CC),
labelvars(CC, 0, _, avar),
( \+cc(CC)
Expand Down
Binary file modified eye.zip
Binary file not shown.
38 changes: 9 additions & 29 deletions reasoning/lingua/acp.ttl
Original file line number Diff line number Diff line change
Expand Up @@ -15,12 +15,6 @@
:noneOf :D.

:acp_rule1 a lingua:BackwardRule;
lingua:vars (
_:Pol
_:Test
_:Field
_:X
);
lingua:conclusion (
_:Pol :pass :allOfTest
);
Expand All @@ -35,17 +29,11 @@
_:Test :has _:Field
)
) log:forAllIn _:X
).
);
lingua:varCount 4.

:acp_rule2 a lingua:BackwardRule;
lingua:vars (
_:Pol
_:Test
_:Field
_:List
_:X
_:L
);lingua:conclusion (
lingua:conclusion (
_:Pol :pass :anyOfTest
);
lingua:premise (
Expand All @@ -61,17 +49,10 @@
) log:collectAllIn _:X
_:List list:length _:L
_:L log:notEqualTo 0
).
);
lingua:varCount 6.

:acp_rule3 a lingua:BackwardRule;
lingua:vars (
_:Pol
_:Test
_:Field
_:List
_:X
_:L
);
lingua:conclusion (
_:Pol :pass :noneOfTest
);
Expand All @@ -84,13 +65,11 @@
) _:List) log:collectAllIn _:X
_:List list:length _:L
_:L log:equalTo 0
).
);
lingua:varCount 6.

# query
:acp_query a lingua:QueryRule;
lingua:vars (
_:Pol
);
lingua:premise (
_:Pol rdf:type :Policy
_:Pol :pass :allOfTest
Expand All @@ -100,4 +79,5 @@
lingua:conclusion (
:test :for _:Pol
:test :is true
).
);
lingua:varCount 1.
8 changes: 2 additions & 6 deletions reasoning/lingua/append.ttl
Original file line number Diff line number Diff line change
Expand Up @@ -16,16 +16,12 @@

# query
:append_query a lingua:QueryRule;
lingua:vars (
_:X1
_:X2
_:Y
);
lingua:premise (
:Let :param1 _:X1
:Let :param2 _:X2
(_:X1 _:X2) list:append _:Y
);
lingua:conclusion (
(_:X1 _:X2) :append _:Y
).
);
lingua:varCount 3.
11 changes: 4 additions & 7 deletions reasoning/lingua/backward.ttl
Original file line number Diff line number Diff line change
Expand Up @@ -5,23 +5,20 @@
# 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
);
lingua:premise (
_:X math:greaterThan _:Y
).
);
lingua:varCount 2.

# query
:backward_query a lingua:QueryRule;
lingua:vars ();
lingua:premise (
5 :moreInterestingThan 3
);
lingua:conclusion (
:result :is (5 :moreInterestingThan 3)
).
);
lingua:varCount 0.
Loading

0 comments on commit 0ddbe5b

Please sign in to comment.