Skip to content

Commit

Permalink
treating graffiti as scratches
Browse files Browse the repository at this point in the history
  • Loading branch information
josd committed Apr 22, 2023
1 parent 67626ad commit 3809f9f
Show file tree
Hide file tree
Showing 4 changed files with 28 additions and 7 deletions.
1 change: 1 addition & 0 deletions RELEASE
Original file line number Diff line number Diff line change
@@ -1,5 +1,6 @@
EYE release

v3.21.0 (2023-04-22) treating graffiti as scratches
v3.20.10 (2023-04-20) fixing --pass-only-new (obs from William Van Woensel)
v3.20.9 (2023-04-20) fixing issue with blogic create contrapositive
v3.20.8 (2023-04-18) moving the graffiti in erase at even level
Expand Down
2 changes: 1 addition & 1 deletion VERSION
Original file line number Diff line number Diff line change
@@ -1 +1 @@
3.20.10
3.21.0
32 changes: 26 additions & 6 deletions eye.pl
Original file line number Diff line number Diff line change
Expand Up @@ -21,7 +21,7 @@
:- catch(use_module(library(pcre)), _, true).
:- catch(use_module(library(http/http_open)), _, true).

version_info('EYE v3.20.10 (2023-04-20)').
version_info('EYE v3.21.0 (2023-04-22)').

license_info('MIT License

Expand Down Expand Up @@ -735,12 +735,14 @@
assertz(implies('<http://www.w3.org/2000/10/swap/log#onPositiveSurface>'(_, G), G, '<>')),
% blow inference fuse
assertz(implies(('<http://www.w3.org/2000/10/swap/log#onNegativeSurface>'(V, G),
is_list(V),
makevars(G, H, beta(V)),
catch(call(H), _, false),
'<http://www.w3.org/2000/10/swap/log#onNegativeSurface>'(_, H)
), false, '<>')),
% simplify positive surface
assertz(implies(('<http://www.w3.org/2000/10/swap/log#onNegativeSurface>'(V, G),
is_list(V),
conj_list(G, L),
select('<http://www.w3.org/2000/10/swap/log#onPositiveSurface>'([], H), L, K),
conj_list(H, D),
Expand All @@ -749,6 +751,7 @@
), '<http://www.w3.org/2000/10/swap/log#onNegativeSurface>'(V, F), '<>')),
% simplify graffiti
assertz(implies(('<http://www.w3.org/2000/10/swap/log#onNegativeSurface>'(V, G),
is_list(V),
findvars(G, U, beta),
findall(M,
( member(M, V),
Expand All @@ -760,10 +763,12 @@
), '<http://www.w3.org/2000/10/swap/log#onNegativeSurface>'(W, G), '<>')),
% simplify nested negative surfaces
assertz(implies(('<http://www.w3.org/2000/10/swap/log#onNegativeSurface>'(V, G),
is_list(V),
conj_list(G, L),
select('<http://www.w3.org/2000/10/swap/log#onNegativeSurface>'([], H), L, K),
conj_list(H, M),
select('<http://www.w3.org/2000/10/swap/log#onNegativeSurface>'(W, O), M, N),
is_list(W),
( conj_list(O, D),
append(K, D, E),
conj_list(C, E)
Expand All @@ -776,6 +781,7 @@
), '<http://www.w3.org/2000/10/swap/log#onNegativeSurface>'(U, C), '<>')),
% resolve two negative surfaces
assertz(implies(('<http://www.w3.org/2000/10/swap/log#onNegativeSurface>'(V, G),
is_list(V),
conj_list(G, L),
\+member('<http://www.w3.org/2000/10/swap/log#onQuerySurface>'(_, _), L),
findall(1,
Expand All @@ -786,13 +792,16 @@
length(O, E),
memberchk(E, [0, 2, 3]),
'<http://www.w3.org/2000/10/swap/log#onNegativeSurface>'(W, F),
is_list(W),
conj_list(F, K),
\+member('<http://www.w3.org/2000/10/swap/log#onQuerySurface>'(_, _), K),
length(K, 2),
\+ (member('<http://www.w3.org/2000/10/swap/log#onNegativeSurface>'(_, I), K), atomic(I)),
makevars(K, J, beta(W)),
select('<http://www.w3.org/2000/10/swap/log#onNegativeSurface>'(U, C), J, [P]),
( select('<http://www.w3.org/2000/10/swap/log#onNegativeSurface>'(_, Q), L, A),
is_list(U),
( select('<http://www.w3.org/2000/10/swap/log#onNegativeSurface>'(Z, Q), L, A),
is_list(Z),
M = ['<http://www.w3.org/2000/10/swap/log#onNegativeSurface>'(U, C)|A],
conj_list(Q, R),
memberchk(P, R)
Expand All @@ -807,8 +816,10 @@
), '<http://www.w3.org/2000/10/swap/log#onNegativeSurface>'(V, H), '<>')),
% create forward rule
assertz(implies(('<http://www.w3.org/2000/10/swap/log#onNegativeSurface>'(V, G),
is_list(V),
conj_list(G, L),
select('<http://www.w3.org/2000/10/swap/log#onNegativeSurface>'(_, H), L, K),
select('<http://www.w3.org/2000/10/swap/log#onNegativeSurface>'(Z, H), L, K),
is_list(Z),
conj_list(R, K),
domain(V, R, P),
find_graffiti(K, D),
Expand All @@ -819,6 +830,7 @@
), '<http://www.w3.org/2000/10/swap/log#implies>'(Q, I), '<>')),
% create contrapositive rule
assertz(implies(('<http://www.w3.org/2000/10/swap/log#onNegativeSurface>'(V, G),
is_list(V),
conj_list(G, L),
\+member('<http://www.w3.org/2000/10/swap/log#onPositiveSurface>'(_, _), L),
\+member('<http://www.w3.org/2000/10/swap/log#onNegativeSurface>'(_, _), L),
Expand All @@ -842,8 +854,10 @@
), '<http://www.w3.org/2000/10/swap/log#implies>'(Q, I), '<>')),
% create backward rule
assertz(implies(('<http://www.w3.org/2000/10/swap/log#onNegativeSurface>'(V, G),
is_list(V),
conj_list(G, L),
select('<http://www.w3.org/2000/10/swap/log#onQuerySurface>'(_, H), L, K),
select('<http://www.w3.org/2000/10/swap/log#onQuerySurface>'(Z, H), L, K),
is_list(Z),
conj_list(H, [T]),
conj_list(R, K),
conjify(R, S),
Expand All @@ -853,8 +867,10 @@
), C, '<>')),
% create query
assertz(implies(('<http://www.w3.org/2000/10/swap/log#onQuerySurface>'(V, G),
is_list(V),
conj_list(G, L),
( select('<http://www.w3.org/2000/10/swap/log#onQuerySurface>'(_, H), L, K)
( select('<http://www.w3.org/2000/10/swap/log#onQuerySurface>'(Z, H), L, K),
is_list(Z)
-> conj_list(I, K),
find_graffiti(K, D),
append(V, D, U),
Expand Down Expand Up @@ -4758,7 +4774,11 @@
)
-> ( flag(blogic)
-> conj_list(Prem, Lst),
Lst = [_|Lst1],
Lst = [_|Lst0],
( select(is_list(_), Lst0, Lst1)
-> true
; Lst1 = Lst0
),
( select(makevars(_, _, _), Lst1, Lst2)
-> true
; Lst2 = Lst
Expand Down
Binary file modified eye.zip
Binary file not shown.

0 comments on commit 3809f9f

Please sign in to comment.