Skip to content

Commit

Permalink
fixing lingua output
Browse files Browse the repository at this point in the history
  • Loading branch information
josd committed Apr 6, 2024
1 parent 1005a77 commit 80c6230
Show file tree
Hide file tree
Showing 10 changed files with 145 additions and 70 deletions.
1 change: 1 addition & 0 deletions RELEASE
Original file line number Diff line number Diff line change
@@ -1,5 +1,6 @@
EYE release

v10.1.1 (2024-04-06) fixing lingua output
v10.1.0 (2024-04-06) adding lingua support in the eye reasoner
v10.0.5 (2024-03-30) rdfsurfaces query is a log:nand containing a log:nans
v10.0.4 (2024-03-29) fixing positive surfaces
Expand Down
2 changes: 1 addition & 1 deletion VERSION
Original file line number Diff line number Diff line change
@@ -1 +1 @@
10.1.0
10.1.1
125 changes: 96 additions & 29 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 v10.1.0 (2024-04-06)').
version_info('EYE v10.1.1 (2024-04-06)').

license_info('MIT License

Expand Down Expand Up @@ -136,6 +136,7 @@
:- dynamic(implies/3). % implies(Premise, Conclusion, Source)
:- dynamic(input_statements/1).
:- dynamic(intern/1).
:- dynamic(keep_ng/1).
:- dynamic(keep_skolem/1).
:- dynamic(lemma/6). % lemma(Count, Source, Premise, Conclusion, Premise-Conclusion_index, Rule)
:- dynamic(mtime/2).
Expand Down Expand Up @@ -4097,7 +4098,8 @@

wt0(!) :-
!,
write('true '),
wm(true),
write(' '),
wp('<http://www.w3.org/2000/10/swap/log#callWithCut>'),
write(' true').
wt0(:-) :-
Expand Down Expand Up @@ -4558,6 +4560,13 @@
wg(O),
write(' '),
wg(G).
wt2(graph(X, Y)) :-
!,
wp(X),
write(' '),
nb_setval(keep_ng, false),
retractall(keep_ng(graph(X, Y))),
wg(Y).
wt2(is(O, T)) :-
!,
( number(T),
Expand Down Expand Up @@ -4597,7 +4606,7 @@
-> write('"'),
writeq(X),
write('"')
; wg(S),
; wm(S),
write(' '),
wp(P),
write(' '),
Expand All @@ -4609,7 +4618,7 @@
( atom(P)
-> X =.. [P, S, O],
wt2(X)
; wg(S),
; wm(S),
write(' '),
wg(P),
write(' '),
Expand Down Expand Up @@ -4664,32 +4673,51 @@
; F = ':-'
)
)
-> write('{'),
indentation(4),
( flag(strings)
-> true
; ( flag('no-beautified-output')
-> ( flag(lingua),
nb_getval(keep_ng, true)
-> ( graph(N, X)
-> true
; nl,
indent
)
),
nb_getval(fdepth, D),
E is D+1,
nb_setval(fdepth, E),
wt(X),
nb_setval(fdepth, D),
indentation(-4),
( flag(strings)
-> true
; ( flag('no-beautified-output')
; gensym('bng_', Y),
nb_getval(var_ns, Sns),
atomic_list_concat(['<', Sns, Y, '>'], N),
assertz(graph(N, X))
),
( \+keep_ng(graph(N, X))
-> assertz(keep_ng(graph(N, X)))
; true
),
wt(N)
; ( flag(lingua)
-> nb_setval(keep_ng, true)
; true
),
write('{'),
indentation(4),
( flag(strings)
-> true
; write('.'),
nl,
indent
)
),
write('}')
; ( flag('no-beautified-output')
-> true
; nl,
indent
)
),
nb_getval(fdepth, D),
E is D+1,
nb_setval(fdepth, E),
wt(X),
nb_setval(fdepth, D),
indentation(-4),
( flag(strings)
-> true
; ( flag('no-beautified-output')
-> true
; write('.'),
nl,
indent
)
),
write('}')
)
; wt(X)
).

Expand Down Expand Up @@ -4728,6 +4756,17 @@
wg(X),
wl(Y).

wm(A) :-
( flag(lingua),
raw_type(A, '<http://www.w3.org/2000/10/swap/log#Literal>')
-> write('[] '),
wp('<http://www.w3.org/1999/02/22-rdf-syntax-ns#value>'),
write(' '),
wt(A),
write(';')
; wg(A)
).

wq([], _) :-
!.
wq([X|Y], allv) :-
Expand Down Expand Up @@ -5148,6 +5187,20 @@
tell(Ws),
nb_getval(wn, Wn),
w3,
forall(
retract(keep_ng(NG)),
( nl,
wt(NG),
nl
)
),
forall(
retract(keep_ng(NG)),
( nl,
wt(NG),
nl
)
),
retractall(pfx(_, _)),
retractall(wpfx(_)),
nb_setval(wn, Wn),
Expand All @@ -5162,7 +5215,21 @@
-> tell(Output)
; true
),
w3
w3,
forall(
retract(keep_ng(NG)),
( nl,
wt(NG),
nl
)
),
forall(
retract(keep_ng(NG)),
( nl,
wt(NG),
nl
)
)
)
)
; true
Expand Down
Binary file modified eye.zip
Binary file not shown.
3 changes: 2 additions & 1 deletion reasoning/lingua/output/backward.trig
Original file line number Diff line number Diff line change
@@ -1,3 +1,4 @@
@prefix rdf: <http://www.w3.org/1999/02/22-rdf-syntax-ns#>.
@prefix : <file:///home/jdroo/github.com/eyereasoner/eye/reasoning/lingua/backward.trig#>.

5 :moreInterestingThan 3 .
[] rdf:value 5; :moreInterestingThan 3 .
8 changes: 5 additions & 3 deletions reasoning/lingua/output/complement.trig
Original file line number Diff line number Diff line change
@@ -1,9 +1,11 @@
@prefix lingua: <http://www.w3.org/2000/10/swap/lingua#>.
@prefix var: <http://www.w3.org/2000/10/swap/var#>.
@prefix log: <http://www.w3.org/2000/10/swap/log#>.
@prefix lingua: <http://www.w3.org/2000/10/swap/lingua#>.

{
_:bng_1 lingua:implication false.

_:bng_1 {
var:P log:complement var:C.
var:S var:P var:O.
var:S var:C var:O.
} lingua:implication false.
}
55 changes: 28 additions & 27 deletions reasoning/lingua/output/easter.trig
Original file line number Diff line number Diff line change
@@ -1,29 +1,30 @@
@prefix rdf: <http://www.w3.org/1999/02/22-rdf-syntax-ns#>.
@prefix : <file:///home/jdroo/github.com/eyereasoner/eye/reasoning/lingua/easter.trig#>.

2024 :easter (31 3).
2025 :easter (20 4).
2026 :easter (5 4).
2027 :easter (28 3).
2028 :easter (16 4).
2029 :easter (1 4).
2030 :easter (21 4).
2031 :easter (13 4).
2032 :easter (28 3).
2033 :easter (17 4).
2034 :easter (9 4).
2035 :easter (25 3).
2036 :easter (13 4).
2037 :easter (5 4).
2038 :easter (25 4).
2039 :easter (10 4).
2040 :easter (1 4).
2041 :easter (21 4).
2042 :easter (6 4).
2043 :easter (29 3).
2044 :easter (17 4).
2045 :easter (9 4).
2046 :easter (25 3).
2047 :easter (14 4).
2048 :easter (5 4).
2049 :easter (18 4).
2050 :easter (10 4).
[] rdf:value 2024; :easter (31 3).
[] rdf:value 2025; :easter (20 4).
[] rdf:value 2026; :easter (5 4).
[] rdf:value 2027; :easter (28 3).
[] rdf:value 2028; :easter (16 4).
[] rdf:value 2029; :easter (1 4).
[] rdf:value 2030; :easter (21 4).
[] rdf:value 2031; :easter (13 4).
[] rdf:value 2032; :easter (28 3).
[] rdf:value 2033; :easter (17 4).
[] rdf:value 2034; :easter (9 4).
[] rdf:value 2035; :easter (25 3).
[] rdf:value 2036; :easter (13 4).
[] rdf:value 2037; :easter (5 4).
[] rdf:value 2038; :easter (25 4).
[] rdf:value 2039; :easter (10 4).
[] rdf:value 2040; :easter (1 4).
[] rdf:value 2041; :easter (21 4).
[] rdf:value 2042; :easter (6 4).
[] rdf:value 2043; :easter (29 3).
[] rdf:value 2044; :easter (17 4).
[] rdf:value 2045; :easter (9 4).
[] rdf:value 2046; :easter (25 3).
[] rdf:value 2047; :easter (14 4).
[] rdf:value 2048; :easter (5 4).
[] rdf:value 2049; :easter (18 4).
[] rdf:value 2050; :easter (10 4).
13 changes: 7 additions & 6 deletions reasoning/lingua/output/fibonacci.trig
Original file line number Diff line number Diff line change
@@ -1,8 +1,9 @@
@prefix rdf: <http://www.w3.org/1999/02/22-rdf-syntax-ns#>.
@prefix : <file:///home/jdroo/github.com/eyereasoner/eye/reasoning/lingua/fibonacci.trig#>.

0 :fibonacci 0 .
1 :fibonacci 1 .
6 :fibonacci 8 .
91 :fibonacci 4660046610375530309 .
283 :fibonacci 62232491515607091882574410635924603070626544377175485625797 .
3674 :fibonacci 295872959797101479478634366815157108100573212705250690577871041398423606408217262643449728342664061812585639168722421830407677671667740585806703531229882783069925750619720511808616484846128237251921414441458265138672827487722512845223115526738192067144721087756159352711138340620702266509343657403678256247195010013499661223527119909308682062873140767135468966093474944529418214755911968500799987099146489838560114063096775586903976827512299123202488315139397181279903459556726060805948910609527571241968534269554079076649680403030083743420820438603816095671532163428933363322524736324029745871445486444623006627119156710782085648303485296149604974010598940800770684835758031137479033374229914629583184427269638360355586190323578625395157899987377625662075558684705457 .
[] rdf:value 0; :fibonacci 0 .
[] rdf:value 1; :fibonacci 1 .
[] rdf:value 6; :fibonacci 8 .
[] rdf:value 91; :fibonacci 4660046610375530309 .
[] rdf:value 283; :fibonacci 62232491515607091882574410635924603070626544377175485625797 .
[] rdf:value 3674; :fibonacci 295872959797101479478634366815157108100573212705250690577871041398423606408217262643449728342664061812585639168722421830407677671667740585806703531229882783069925750619720511808616484846128237251921414441458265138672827487722512845223115526738192067144721087756159352711138340620702266509343657403678256247195010013499661223527119909308682062873140767135468966093474944529418214755911968500799987099146489838560114063096775586903976827512299123202488315139397181279903459556726060805948910609527571241968534269554079076649680403030083743420820438603816095671532163428933363322524736324029745871445486444623006627119156710782085648303485296149604974010598940800770684835758031137479033374229914629583184427269638360355586190323578625395157899987377625662075558684705457 .
2 changes: 1 addition & 1 deletion reasoning/lingua/output/sha512.trig
Original file line number Diff line number Diff line change
@@ -1,3 +1,3 @@
@prefix : <file:///home/jdroo/github.com/eyereasoner/eye/reasoning/lingua/sha512.trig#>.

"hello world" :sha512 "309ecc489c12d6eb4cc40f50c902f2b4d0ed77ee511a7c7a9bcd3ca86d4cd86f989dd35bc5ff499670da34255b45b0cfd830e81f605dcf7dc5542e93ae9cd76f".
[] <http://www.w3.org/1999/02/22-rdf-syntax-ns#value> "hello world"; :sha512 "309ecc489c12d6eb4cc40f50c902f2b4d0ed77ee511a7c7a9bcd3ca86d4cd86f989dd35bc5ff499670da34255b45b0cfd830e81f605dcf7dc5542e93ae9cd76f".
6 changes: 4 additions & 2 deletions reasoning/lingua/output/union.trig
Original file line number Diff line number Diff line change
@@ -1,8 +1,10 @@
@prefix : <file:///home/jdroo/github.com/eyereasoner/eye/reasoning/lingua/union.trig#>.

:result :is {
:result :is _:bng_1.

_:bng_1 {
:A :B :C.
:A :X :C.
:D :E :F.
:A :Y :C.
}.
}

0 comments on commit 80c6230

Please sign in to comment.