Skip to content

Commit

Permalink
using lists as compounds and adding experimental --prolog to use prol…
Browse files Browse the repository at this point in the history
…og code
  • Loading branch information
josd committed Nov 7, 2024
1 parent aa109d6 commit 43ef7f5
Show file tree
Hide file tree
Showing 15 changed files with 693 additions and 685 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.30.0 (2024-11-07) using lists as compounds and adding experimental --prolog to use prolog code
v10.29.1 (2024-11-06) adding list:compound built-in to convert list tofro compound term
v10.29.0 (2024-11-05) introducing ^(functor args) compound terms
v10.28.9 (2024-11-04) using RDF Proofs
Expand Down
2 changes: 1 addition & 1 deletion VERSION
Original file line number Diff line number Diff line change
@@ -1 +1 @@
10.29.1
10.30.0
90 changes: 52 additions & 38 deletions eye.pl
Original file line number Diff line number Diff line change
Expand Up @@ -22,7 +22,7 @@
:- catch(use_module(library(process)), _, true).
:- catch(use_module(library(http/http_open)), _, true).

version_info('EYE v10.29.1 (2024-11-06)').
version_info('EYE v10.30.0 (2024-11-07)').

license_info('MIT License

Expand Down Expand Up @@ -92,6 +92,7 @@
<data>
[--n3] <uri> N3 triples and rules
--n3p <uri> N3P intermediate
--prolog <uri> Prolog code
--proof <uri> N3 proof lemmas
--trig <uri> TriG data
--turtle <uri> Turtle triples
Expand Down Expand Up @@ -345,7 +346,7 @@
argv([Arg|Argvs], [U, V|Argus]) :-
sub_atom(Arg, B, 1, E, '='),
sub_atom(Arg, 0, B, _, U),
memberchk(U, ['--csv-separator', '--hmac-key', '--image', '--max-inferences', '--n3', '--n3p', '--proof', '--quantify', '--query', '--output', '--skolem-genid', '--tactic', '--trig', '--turtle']),
memberchk(U, ['--csv-separator', '--hmac-key', '--image', '--max-inferences', '--n3', '--n3p', '--prolog', '--proof', '--quantify', '--query', '--output', '--skolem-genid', '--tactic', '--trig', '--turtle']),
!,
sub_atom(Arg, _, E, 0, V),
argv(Argvs, Argus).
Expand Down Expand Up @@ -511,14 +512,23 @@
( flag(profile)
-> asserta(pce_profile:pce_show_profile :- fail),
profile(eam(0))
; catch(eam(0), Exc3,
( ( Exc3 = halt(0)
-> true
; format(user_error, '** ERROR ** eam ** ~w~n', [Exc3]),
flush_output(user_error),
( Exc3 = inference_fuse(_)
-> nb_setval(exit_code, 2)
; nb_setval(exit_code, 3)
; ( member('--prolog', Args)
-> ( query(Q),
Q,
write_term(Q, [numbervars(true), quoted(true), double_quotes(true)]),
write('.\n'),
fail
; true
)
; catch(eam(0), Exc3,
( ( Exc3 = halt(0)
-> true
; format(user_error, '** ERROR ** eam ** ~w~n', [Exc3]),
flush_output(user_error),
( Exc3 = inference_fuse(_)
-> nb_setval(exit_code, 2)
; nb_setval(exit_code, 3)
)
)
)
)
Expand Down Expand Up @@ -855,7 +865,7 @@
assertz(wcache(Arg, File)),
opts(Argus, Args).
opts([Arg|_], _) :-
\+memberchk(Arg, ['--entail', '--help', '--n3', '--n3p', '--not-entail', '--pass', '--pass-all', '--proof', '--query', '--trig', '--turtle']),
\+memberchk(Arg, ['--entail', '--help', '--n3', '--n3p', '--not-entail', '--pass', '--pass-all', '--prolog', '--proof', '--query', '--trig', '--turtle']),
sub_atom(Arg, 0, 2, _, '--'),
!,
throw(not_supported_option(Arg)).
Expand Down Expand Up @@ -990,6 +1000,37 @@
; true
),
args(Args).
args(['--prolog', Argument|Args]) :-
!,
absolute_uri(Argument, Arg),
( wcacher(Arg, File)
-> ( flag(quiet)
-> true
; format(user_error, 'GET ~w FROM ~w ', [Arg, File]),
flush_output(user_error)
)
; ( flag(quiet)
-> true
; format(user_error, 'GET ~w ', [Arg]),
flush_output(user_error)
),
( ( sub_atom(Arg, 0, 5, _, 'http:')
-> true
; sub_atom(Arg, 0, 6, _, 'https:')
)
-> http_open(Arg, In, []),
set_stream(In, encoding(utf8))
; ( sub_atom(Arg, 0, 5, _, 'file:')
-> ( parse_url(Arg, Parts)
-> memberchk(path(File), Parts)
; sub_atom(Arg, 7, _, 0, File)
)
; File = Arg
)
)
),
consult(File),
args(Args).
args(['--proof', Arg|Args]) :-
!,
absolute_uri(Arg, A),
Expand Down Expand Up @@ -2148,11 +2189,6 @@
{ sort(List, Distinct)
},
['$', ')'].
pathitem(compound_term(List), Triples) -->
[caret_lb],
!,
pathlist(List, Triples),
[')'].
pathitem(List, Triples) -->
['('],
!,
Expand Down Expand Up @@ -2829,11 +2865,6 @@
!,
get_code(In, _),
get_code(In, C).
token(0'^, In, C, caret_lb) :-
peek_code(In, 0'(),
!,
get_code(In, _),
get_code(In, C).
token(C0, In, C, Token) :-
name(C0, In, C1, Name),
!,
Expand Down Expand Up @@ -4179,12 +4210,6 @@
write('($'),
wl(X),
write(' $)').
wt1(compound_term([X|Y])) :-
!,
write('^('),
wt(X),
wl(Y),
write(')').
wt1('$VAR'(X)) :-
!,
write('?V'),
Expand Down Expand Up @@ -6902,15 +6927,6 @@
)
).

'<http://www.w3.org/2000/10/swap/list#compound>'(A, B) :-
when(
( nonvar(A)
; nonvar(B)
),
( B = compound_term(A)
)
).

'<http://www.w3.org/2000/10/swap/list#first>'(A, B) :-
when(
( nonvar(A)
Expand Down Expand Up @@ -12701,8 +12717,6 @@
!.
raw_type(set(_), '<http://www.w3.org/2000/10/swap/log#Set>') :-
!.
raw_type(compound_term(_), '<http://www.w3.org/2000/10/swap/log#Compound>') :-
!.
raw_type(A, '<http://www.w3.org/2000/10/swap/log#Formula>') :-
functor(A, B, C),
B \= ':',
Expand Down
Binary file modified eye.zip
Binary file not shown.
4 changes: 2 additions & 2 deletions reasoning/good-cobbler/cobbler.n3
Original file line number Diff line number Diff line change
Expand Up @@ -6,11 +6,11 @@
@prefix : <urn:example:>.

# some x is a good cobbler
_:x a ^(:good :Cobbler).
_:x a (:good :Cobbler).

# is there some x which is good at some y
{
?x a ^(:good ?y).
?x a (:good ?y).
} =^ {
:test :is true.
}.
2 changes: 1 addition & 1 deletion reasoning/n3plus1/README
Original file line number Diff line number Diff line change
Expand Up @@ -2,4 +2,4 @@
N3 plus 1
---------

N3 plus increments like RDF 1.1, RDF 1.2, sets, compounds, ...
N3 plus increments like RDF 1.1, RDF 1.2, ...
20 changes: 0 additions & 20 deletions reasoning/n3plus1/in.n3
Original file line number Diff line number Diff line change
Expand Up @@ -49,26 +49,6 @@ _:i {
{| :from 1964; :to 1975 |}
{| :from 1980; :to 2001 |} .

# sets
:g :h ($ :s :m :l $).

{
:g :h ?I.
?I log:equalTo ($ :l :s :m :l :s $).
} => {
?I :v :w.
}.

# compounds
:i :j ^(:f :a :b :c).

{
(:g :d :e) list:compound ?C.
?E list:compound ?C.
} => {
?E :k ?C.
}.

# queries
{
?S ?P ?O.
Expand Down
4 changes: 0 additions & 4 deletions reasoning/n3plus1/out.n3
Original file line number Diff line number Diff line change
Expand Up @@ -2,7 +2,6 @@
@prefix rdf: <http://www.w3.org/1999/02/22-rdf-syntax-ns#>.

_:e_g_1 :h _:e_i_1.
:g :h ($ :l :m :s $).
:s :p << :d :e :f ~ _:bne_21 >>.
:s :p << :g :h :i ~ :x >>.
:s :p :o.
Expand All @@ -16,14 +15,11 @@ _:bne_21 rdf:reifies <<( :d :e :f )>>.
_:bn_1 :q1 "A".
_:bn_1 :q2 "B".
<< :s :p :o ~ _:bne_28 >> :j :k.
:i :j ^(:f :a :b :c).
:liz :marriedTo :richard.
<< :liz :marriedTo :richard ~ _:bne_31 >> :from 1964 .
<< :liz :marriedTo :richard ~ _:bne_34 >> :from 1980 .
<< :liz :marriedTo :richard ~ _:bne_31 >> :to 1975 .
<< :liz :marriedTo :richard ~ _:bne_34 >> :to 2001 .
($ :l :m :s $) :v :w.
(:g :d :e) :k ^(:g :d :e).

_:e_g_1 {
:s :p _:e_x_1.
Expand Down
2 changes: 1 addition & 1 deletion reasoning/peano/peano-answer.n3
Original file line number Diff line number Diff line change
@@ -1,3 +1,3 @@
@prefix : <http://example.org/#>.

^(:s ^(:s ^(:s ^(:s ^(:s 0))))) :factorial ^(:s ^(:s ^(:s ^(:s ^(:s ^(:s ^(:s ^(:s ^(:s ^(:s ^(:s ^(:s ^(:s ^(:s ^(:s ^(:s ^(:s ^(:s ^(:s ^(:s ^(:s ^(:s ^(:s ^(:s ^(:s ^(:s ^(:s ^(:s ^(:s ^(:s ^(:s ^(:s ^(:s ^(:s ^(:s ^(:s ^(:s ^(:s ^(:s ^(:s ^(:s ^(:s ^(:s ^(:s ^(:s ^(:s ^(:s ^(:s ^(:s ^(:s ^(:s ^(:s ^(:s ^(:s ^(:s ^(:s ^(:s ^(:s ^(:s ^(:s ^(:s ^(:s ^(:s ^(:s ^(:s ^(:s ^(:s ^(:s ^(:s ^(:s ^(:s ^(:s ^(:s ^(:s ^(:s ^(:s ^(:s ^(:s ^(:s ^(:s ^(:s ^(:s ^(:s ^(:s ^(:s ^(:s ^(:s ^(:s ^(:s ^(:s ^(:s ^(:s ^(:s ^(:s ^(:s ^(:s ^(:s ^(:s ^(:s ^(:s ^(:s ^(:s ^(:s ^(:s ^(:s ^(:s ^(:s ^(:s ^(:s ^(:s ^(:s ^(:s ^(:s ^(:s ^(:s ^(:s ^(:s ^(:s ^(:s ^(:s 0)))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))).
(:s (:s (:s (:s (:s 0))))) :factorial (:s (:s (:s (:s (:s (:s (:s (:s (:s (:s (:s (:s (:s (:s (:s (:s (:s (:s (:s (:s (:s (:s (:s (:s (:s (:s (:s (:s (:s (:s (:s (:s (:s (:s (:s (:s (:s (:s (:s (:s (:s (:s (:s (:s (:s (:s (:s (:s (:s (:s (:s (:s (:s (:s (:s (:s (:s (:s (:s (:s (:s (:s (:s (:s (:s (:s (:s (:s (:s (:s (:s (:s (:s (:s (:s (:s (:s (:s (:s (:s (:s (:s (:s (:s (:s (:s (:s (:s (:s (:s (:s (:s (:s (:s (:s (:s (:s (:s (:s (:s (:s (:s (:s (:s (:s (:s (:s (:s (:s (:s (:s (:s (:s (:s (:s (:s (:s (:s (:s (:s 0)))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))).
Loading

0 comments on commit 43ef7f5

Please sign in to comment.