Skip to content

Commit

Permalink
using linear lists for lingua
Browse files Browse the repository at this point in the history
  • Loading branch information
josd committed Dec 6, 2023
1 parent 957c1fe commit b65c1ec
Show file tree
Hide file tree
Showing 35 changed files with 645 additions and 708 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.7 (2023-12-06) using linear lists for lingua
v9.0.6 (2023-12-03) detecting malformed rdf lists and dropping --rdf-list-input option
v9.0.5 (2023-12-02) doing lingua without lingua:graph functor and backward rules were the culprit
v9.0.4 (2023-12-02) using lingua:graph in the lingua output
Expand Down
2 changes: 1 addition & 1 deletion VERSION
Original file line number Diff line number Diff line change
@@ -1 +1 @@
9.0.6
9.0.7
120 changes: 46 additions & 74 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.6 (2023-12-03)').
version_info('EYE v9.0.7 (2023-12-06)').

license_info('MIT License

Expand Down Expand Up @@ -3840,10 +3840,7 @@
; wt(C)
),
ws(C),
( flag(lingua)
-> true
; write('.')
),
write('.'),
nl,
cnt(output_statements),
fail
Expand Down Expand Up @@ -4364,7 +4361,8 @@
write(' true')
; wt(X),
ws(X),
( flag(lingua)
( flag(lingua),
\+nb_getval(indentation, 0)
-> true
; write('.')
),
Expand Down Expand Up @@ -4398,26 +4396,10 @@
indentation(-4),
indent,
write(']')
; ( flag(lingua),
is_lott([X|Y])
-> write('('),
indentation(4),
forall(
member(Z, [X|Y]),
( nl,
indent,
wt(Z)
)
),
indentation(-4),
nl,
indent,
write(')')
; write('('),
wg(X),
wl(Y),
write(')')
)
; write('('),
wg(X),
wl(Y),
write(')')
).
wt2(literal(X, lang(Y))) :-
!,
Expand Down Expand Up @@ -4675,47 +4657,23 @@
-> write('"'),
writeq(X),
write('"')
; ( flag(lingua),
\+nb_getval(indentation, 0)
-> write('(')
; true
),
wg(S),
; wg(S),
write(' '),
wp(P),
write(' '),
wg(O),
( flag(lingua)
-> ( \+nb_getval(indentation, 0)
-> write(')')
; write('.')
)
; true
)
wg(O)
).

wtn(exopred(P, S, O)) :-
!,
( atom(P)
-> X =.. [P, S, O],
wt2(X)
; ( flag(lingua),
\+nb_getval(indentation, 0)
-> write('(')
; true
),
wg(S),
; wg(S),
write(' '),
wg(P),
write(' '),
wg(O),
( flag(lingua)
-> ( \+nb_getval(indentation, 0)
-> write(')')
; write('.')
)
; true
)
wg(O)
).
wtn(triple(S, P, O)) :-
!,
Expand Down Expand Up @@ -5434,11 +5392,11 @@
!,
djiti_conc(answer(B, void, void), D).
djiti_conc(answer(A, void, void), answer(B, void, void)) :-
is_lott(A),
list_lott(A, _),
!,
getconj(A, B).
djiti_conc(A, B) :-
is_lott(A),
list_lott(A, _),
!,
getconj(A, B).
djiti_conc(A, A).
Expand Down Expand Up @@ -6541,7 +6499,19 @@
),
( getconj(A, Ag),
conj_list(Ag, C),
member(B, C)
getconj(B, Bg),
member(Bg, C)
)
).

'<http://www.w3.org/2000/10/swap/graph#notMember>'(A, B) :-
when(
( nonvar(A)
),
( getconj(A, Ag),
conj_list(Ag, C),
getconj(B, Bg),
\+member(Bg, C)
)
).

Expand Down Expand Up @@ -6593,6 +6563,9 @@

'<http://www.w3.org/2000/10/swap/list#firstRest>'([A|B], [A, B]).

'<http://www.w3.org/2000/10/swap/list#lott>'(A, B) :-
list_lott(A, B).

'<http://www.w3.org/2000/10/swap/list#in>'(A, B) :-
when(
( nonvar(B)
Expand Down Expand Up @@ -11195,10 +11168,10 @@
is_graph(A) :-
is_gl(A).

is_lott([]).
is_lott([[_, P, _]|A]) :-
\+is_list(P),
is_lott(A).
list_lott([], []).
list_lott([A, B, C|D], [[A, B, C]|E]) :-
\+is_list(B),
list_lott(D, E).

unify(A, B) :-
nonvar(A),
Expand Down Expand Up @@ -12372,35 +12345,34 @@
var(A),
!.
getterm(A, B) :-
is_lott(A),
list_lott(A, C),
!,
findall(_,
( member([D, E, F], A),
( member([D, E, F], C),
memberchk(E, ['<http://www.w3.org/1999/02/22-rdf-syntax-ns#first>', '<http://www.w3.org/1999/02/22-rdf-syntax-ns#rest>']),
Z =.. [E, D, F],
assertz(Z)
),
_
),
findall([D, E, F],
( member([G, E, H], A),
findall([G, E, H],
( member([D, E, F], C),
E \= '<http://www.w3.org/1999/02/22-rdf-syntax-ns#first>',
E \= '<http://www.w3.org/1999/02/22-rdf-syntax-ns#rest>',
getterm(G, D),
getterm(H, F)
getterm(D, G),
getterm(F, H)
),
B
I
),
findall(_,
( member([D, E, F], A),
( member([D, E, F], C),
memberchk(E, ['<http://www.w3.org/1999/02/22-rdf-syntax-ns#first>', '<http://www.w3.org/1999/02/22-rdf-syntax-ns#rest>']),
Z =.. [E, D, F],
retract(Z)
),
_
).
getterm([], []) :-
!.
),
list_lott(B, I).
getterm('<http://www.w3.org/1999/02/22-rdf-syntax-ns#nil>', []) :-
!.
getterm([A|B], [C|D]) :-
Expand Down Expand Up @@ -12440,10 +12412,10 @@
!.
getconj([], true) :-
!.
getconj([[S, P, O]], A) :-
getconj([S, P, O], A) :-
!,
A =.. [P, S, O].
getconj([[S, P, O]|A], (B, C)) :-
getconj([S, P, O|A], (B, C)) :-
!,
B =.. [P, S, O],
getconj(A, C).
Expand Down
Binary file modified eye.zip
Binary file not shown.
38 changes: 24 additions & 14 deletions lingua/4color/4color.ttl
Original file line number Diff line number Diff line change
Expand Up @@ -38,7 +38,7 @@
:places_rule1 a lingua:BackwardRule;
lingua:vars ();
lingua:conclusion (
(() :places true)
() :places true
);
lingua:premise ().

Expand All @@ -53,17 +53,21 @@
_:SCOPE
);
lingua:conclusion (
(_:PLACES :places true)
_:PLACES :places true
);
lingua:premise (
(_:PLACES list:firstRest ((_:PLACE _:COLOR) _:TAIL))
(_:TAIL :places true)
(_:PLACE :neighbours _:NEIGHBOURS)
((:red :green :blue :yellow) list:member _:COLOR)
((1 (
(_:TAIL list:member (_:NEIGHBOUR _:COLOR))
(_:NEIGHBOURS list:member _:NEIGHBOUR)
) ()) log:collectAllIn _:SCOPE)
_:PLACES list:firstRest ((_:PLACE _:COLOR) _:TAIL)
_:TAIL :places true
_:PLACE :neighbours _:NEIGHBOURS
(:red :green :blue :yellow) list:member _:COLOR
(
1
(
_:TAIL list:member (_:NEIGHBOUR _:COLOR)
_:NEIGHBOURS list:member _:NEIGHBOUR
)
()
) log:collectAllIn _:SCOPE
).

# query
Expand All @@ -77,10 +81,16 @@
_:PLACES
);
lingua:premise (
(((_:PLACE _:COLOR) ((_:PLACE :neighbours _:NEIGHBOURS)) _:LIST) log:collectAllIn _:SCOPE)
((_:LIST) func:reverse _:PLACES)
(_:PLACES :places true)
(
(_:PLACE _:COLOR)
(
_:PLACE :neighbours _:NEIGHBOURS
)
_:LIST
) log:collectAllIn _:SCOPE
(_:LIST) func:reverse _:PLACES
_:PLACES :places true
);
lingua:conclusion (
(_:PLACES :coloring true)
_:PLACES :coloring true
).
61 changes: 39 additions & 22 deletions lingua/acp/acp.ttl
Original file line number Diff line number Diff line change
Expand Up @@ -22,12 +22,19 @@
_:X
);
lingua:conclusion (
(_:Pol :pass :allOfTest)
_:Pol :pass :allOfTest
);
lingua:premise (
(_:Test :policy _:Pol)
(_:Pol rdf:type :Policy)
((((_:Pol :allOf _:Field)) ((_:Test :has _:Field))) log:forAllIn _:X)
_:Test :policy _:Pol
_:Pol rdf:type :Policy
(
(
_:Pol :allOf _:Field
)
(
_:Test :has _:Field
)
) log:forAllIn _:X
).

:acp_rule2 a lingua:BackwardRule;
Expand All @@ -39,14 +46,21 @@
_:X
_:L
);lingua:conclusion (
(_:Pol :pass :anyOfTest)
_:Pol :pass :anyOfTest
);
lingua:premise (
(_:Test :policy _:Pol)
(_:Pol rdf:type :Policy)
((_:Field ((_:Pol :anyOf _:Field) (_:Test :has _:Field)) _:List) log:collectAllIn _:X)
(_:List list:length _:L)
(_:L log:notEqualTo 0)
_:Test :policy _:Pol
_:Pol rdf:type :Policy
(
_:Field
(
_:Pol :anyOf _:Field
_:Test :has _:Field
)
_:List
) log:collectAllIn _:X
_:List list:length _:L
_:L log:notEqualTo 0
).

:acp_rule3 a lingua:BackwardRule;
Expand All @@ -59,14 +73,17 @@
_:L
);
lingua:conclusion (
(_:Pol :pass :noneOfTest)
_: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)
_: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
).

# query
Expand All @@ -75,12 +92,12 @@
_:Pol
);
lingua:premise (
(_:Pol rdf:type :Policy)
(_:Pol :pass :allOfTest)
(_:Pol :pass :anyOfTest)
(_:Pol :pass :noneOfTest)
_:Pol rdf:type :Policy
_:Pol :pass :allOfTest
_:Pol :pass :anyOfTest
_:Pol :pass :noneOfTest
);
lingua:conclusion (
(:test :for _:Pol)
(:test :is true)
:test :for _:Pol
:test :is true
).
Loading

0 comments on commit b65c1ec

Please sign in to comment.