Skip to content

Commit

Permalink
using log:program instead of log:core
Browse files Browse the repository at this point in the history
  • Loading branch information
josd committed Mar 1, 2025
1 parent c8417b4 commit c339e1a
Show file tree
Hide file tree
Showing 56 changed files with 726 additions and 725 deletions.
1 change: 1 addition & 0 deletions RELEASE
Original file line number Diff line number Diff line change
@@ -1,5 +1,6 @@
EYE release

v11.9.11 (2025-03-02) using log:program instead of log:core
v11.9.10 (2025-02-27) using log:core instead of log:herbrand
v11.9.9 (2025-02-26) using log:term instead of log:getTerm
v11.9.8 (2025-02-26) using log:getTerm instead of log:herbrandTerm together with log:herbrand
Expand Down
2 changes: 1 addition & 1 deletion VERSION
Original file line number Diff line number Diff line change
@@ -1 +1 @@
11.9.10
11.9.11
2 changes: 1 addition & 1 deletion eye-builtins.n3
Original file line number Diff line number Diff line change
Expand Up @@ -149,7 +149,6 @@ log:conclusion a e:Builtin.
log:conjunction a e:Builtin.
log:content a e:Builtin.
log:copy a e:Builtin.
log:core a e:Builtin.
log:dtlit a e:Builtin.
log:equalTo a e:Builtin.
log:forAllIn a e:Builtin.
Expand All @@ -175,6 +174,7 @@ log:outputString a e:Builtin.
log:parsedAsN3 a e:Builtin.
log:phrase a e:Builtin.
log:prefix a e:Builtin.
log:program a e:Builtin.
log:query a e:Builtin.
log:racine a e:Builtin.
log:rawType a e:Builtin.
Expand Down
28 changes: 14 additions & 14 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 v11.9.10 (2025-02-27)').
version_info('EYE v11.9.11 (2025-03-02)').

license_info('MIT License

Expand Down Expand Up @@ -4016,7 +4016,7 @@
wt0(fail) :-
!,
write('("fail") '),
wp('<http://www.w3.org/2000/10/swap/log#core>'),
wp('<http://www.w3.org/2000/10/swap/log#program>'),
write(' true').
wt0([]) :-
!,
Expand Down Expand Up @@ -7515,15 +7515,6 @@
'<http://www.w3.org/2000/10/swap/log#copy>'(A, B) :-
copy_term_nat(A, B).

'<http://www.w3.org/2000/10/swap/log#core>'(A, B) :-
\+flag(restricted),
atomify(A, C),
D =.. C,
( B = true
-> catch(call(D), _, fail)
; \+catch(call(D), _, fail)
).

'<http://www.w3.org/2000/10/swap/log#dtlit>'([A, B], C) :-
when(
( ground(A)
Expand Down Expand Up @@ -7895,6 +7886,15 @@
)
).

'<http://www.w3.org/2000/10/swap/log#program>'(A, B) :-
\+flag(restricted),
atomify(A, C),
D =.. C,
( B = true
-> catch(call(D), _, fail)
; \+catch(call(D), _, fail)
).

'<http://www.w3.org/2000/10/swap/log#racine>'(A, B) :-
when(
( nonvar(A)
Expand Down Expand Up @@ -12609,13 +12609,13 @@
'<http://eulersharp.sourceforge.net/2003/03swap/log-rules#derive>'([literal(A, type('<http://www.w3.org/2001/XMLSchema#string>'))|B], true), C], true), when(D, C)) :-
!,
D =.. [A|B].
conjify('<http://www.w3.org/2000/10/swap/log#core>'([literal(when, type('<http://www.w3.org/2001/XMLSchema#string>')),
'<http://www.w3.org/2000/10/swap/log#core>'([literal(A, type('<http://www.w3.org/2001/XMLSchema#string>'))|B], true), C], true), when(D, C)) :-
conjify('<http://www.w3.org/2000/10/swap/log#program'([literal(when, type('<http://www.w3.org/2001/XMLSchema#string>')),
'<http://www.w3.org/2000/10/swap/log#program>'([literal(A, type('<http://www.w3.org/2001/XMLSchema#string>'))|B], true), C], true), when(D, C)) :-
!,
D =.. [A|B].
conjify('<http://eulersharp.sourceforge.net/2003/03swap/log-rules#derive>'([literal(!, type('<http://www.w3.org/2001/XMLSchema#string>'))], true), !) :-
!.
conjify('<http://www.w3.org/2000/10/swap/log#core>'([literal(!, type('<http://www.w3.org/2001/XMLSchema#string>'))], true), !) :-
conjify('<http://www.w3.org/2000/10/swap/log#program>'([literal(!, type('<http://www.w3.org/2001/XMLSchema#string>'))], true), !) :-
!.
conjify('<http://eulersharp.sourceforge.net/2003/03swap/prolog#cut>'([], true), !) :-
!.
Expand Down
Binary file modified eye.zip
Binary file not shown.
4 changes: 2 additions & 2 deletions reasoning/bi/biA.n3
Original file line number Diff line number Diff line change
Expand Up @@ -495,15 +495,15 @@
} a :PASS.
{
{
("atom_codes" "HOME" (72 79 77 69)) log:core true.
("atom_codes" "HOME" (72 79 77 69)) log:program true.
} => {
:loghac1 :result true.
}.
} a :PASS.
{
{
("date(1970, 1, 1, 0, 0, 0.0, 0, 'UTC', -)") log:term "date(1970,1,1,0,0,0.0,0,'UTC',-)".
("date_time_stamp" "date(1970,1,1,0,0,0.0,0,'UTC',-)" 0.0) log:core true.
("date_time_stamp" "date(1970,1,1,0,0,0.0,0,'UTC',-)" 0.0) log:program true.
0.0 math:equalTo 0.0.
} => {
:loghdts1 :result true.
Expand Down
4 changes: 2 additions & 2 deletions reasoning/bi/biP.n3
Original file line number Diff line number Diff line change
Expand Up @@ -74,8 +74,8 @@
{<abc.n3> log:semantics ?X. ?X log:equalTo {:a :b :c}} => {:loges0 :result true}.
{<ab_c.n3> log:semantics ?X. ?X log:equalTo {:a :b ?c}} => {:loges3 :result true}.
{($ "a" "b" "c" "c" "a" $) log:equalTo ($ "c" "b" "b" "a" "c" $)} => {:loget1 :result true}.
{("atom_codes" "HOME" (72 79 77 69)) log:core true} => {:loghac1 :result true}.
{("date_time_stamp" ("date(1970, 1, 1, 0, 0, 0.0, 0, 'UTC', -)")!log:term ?R) log:core true. ?R math:equalTo 0.0} => {:loghdts1 :result true}.
{("atom_codes" "HOME" (72 79 77 69)) log:program true} => {:loghac1 :result true}.
{("date_time_stamp" ("date(1970, 1, 1, 0, 0, 0.0, 0, 'UTC', -)")!log:term ?R) log:program true. ?R math:equalTo 0.0} => {:loghdts1 :result true}.
{{:b :a :c. :e :d :f. :h :g :i. :k :j :l} log:includes {:k :j :l. ?X :d ?Z}} => {:logi1 :result true}.
{<medic.n3> log:semantics ?F. ?F log:includes {med:aspirinHighDose med:excludedFor med:AllergyForAspirin}} => {:logi3 :result true}.
{{:a :b :c} log:includes {:a :b :c}} => {:logid0 :result true}.
Expand Down
2 changes: 1 addition & 1 deletion reasoning/collatz/collatz-query.n3
Original file line number Diff line number Diff line change
Expand Up @@ -3,7 +3,7 @@
@prefix : <https://eyereasoner.github.io/ns#>.

{
("consult" "./collatz.pl") log:core true.
("consult" "./collatz.pl") log:program true.
10000 log:repeat ?N0.
(?N0 1) math:sum ?N.
?N :collatz ?M.
Expand Down
26 changes: 13 additions & 13 deletions reasoning/d3-group/d3-group-proof.n3
Original file line number Diff line number Diff line change
Expand Up @@ -38,7 +38,7 @@ skolem:lemma1 a r:Inference;
("identity" "rotation_120" "rotation_240" "reflection_a" "reflection_b" "reflection_c") :validGroup true.
};
r:evidence (
[ a r:Fact; r:gives {("consult" "./d3-group.pl") log:core true}]
[ a r:Fact; r:gives {("consult" "./d3-group.pl") log:program true}]
[ a r:Fact; r:gives {("identity" "rotation_120" "rotation_240" "reflection_a" "reflection_b" "reflection_c") :validGroup true}]
);
r:binding [ r:variable [ n3:uri "http://www.w3.org/2000/10/swap/var#x_0"]; r:boundTo ("identity" "rotation_120" "rotation_240" "reflection_a" "reflection_b" "reflection_c")];
Expand All @@ -49,7 +49,7 @@ skolem:lemma2 a r:Inference;
("identity" "rotation_120" "rotation_240" "reflection_a" "reflection_b") :validGroup true.
};
r:evidence (
[ a r:Fact; r:gives {("consult" "./d3-group.pl") log:core true}]
[ a r:Fact; r:gives {("consult" "./d3-group.pl") log:program true}]
[ a r:Fact; r:gives {("identity" "rotation_120" "rotation_240" "reflection_a" "reflection_b") :validGroup true}]
);
r:binding [ r:variable [ n3:uri "http://www.w3.org/2000/10/swap/var#x_0"]; r:boundTo ("identity" "rotation_120" "rotation_240" "reflection_a" "reflection_b")];
Expand All @@ -60,7 +60,7 @@ skolem:lemma3 a r:Inference;
("identity" "rotation_120" "rotation_240" "reflection_a" "reflection_c") :validGroup true.
};
r:evidence (
[ a r:Fact; r:gives {("consult" "./d3-group.pl") log:core true}]
[ a r:Fact; r:gives {("consult" "./d3-group.pl") log:program true}]
[ a r:Fact; r:gives {("identity" "rotation_120" "rotation_240" "reflection_a" "reflection_c") :validGroup true}]
);
r:binding [ r:variable [ n3:uri "http://www.w3.org/2000/10/swap/var#x_0"]; r:boundTo ("identity" "rotation_120" "rotation_240" "reflection_a" "reflection_c")];
Expand All @@ -71,7 +71,7 @@ skolem:lemma4 a r:Inference;
("identity" "rotation_120" "rotation_240" "reflection_a") :validGroup true.
};
r:evidence (
[ a r:Fact; r:gives {("consult" "./d3-group.pl") log:core true}]
[ a r:Fact; r:gives {("consult" "./d3-group.pl") log:program true}]
[ a r:Fact; r:gives {("identity" "rotation_120" "rotation_240" "reflection_a") :validGroup true}]
);
r:binding [ r:variable [ n3:uri "http://www.w3.org/2000/10/swap/var#x_0"]; r:boundTo ("identity" "rotation_120" "rotation_240" "reflection_a")];
Expand All @@ -82,7 +82,7 @@ skolem:lemma5 a r:Inference;
("identity" "rotation_120" "rotation_240" "reflection_b" "reflection_c") :validGroup true.
};
r:evidence (
[ a r:Fact; r:gives {("consult" "./d3-group.pl") log:core true}]
[ a r:Fact; r:gives {("consult" "./d3-group.pl") log:program true}]
[ a r:Fact; r:gives {("identity" "rotation_120" "rotation_240" "reflection_b" "reflection_c") :validGroup true}]
);
r:binding [ r:variable [ n3:uri "http://www.w3.org/2000/10/swap/var#x_0"]; r:boundTo ("identity" "rotation_120" "rotation_240" "reflection_b" "reflection_c")];
Expand All @@ -93,7 +93,7 @@ skolem:lemma6 a r:Inference;
("identity" "rotation_120" "rotation_240" "reflection_b") :validGroup true.
};
r:evidence (
[ a r:Fact; r:gives {("consult" "./d3-group.pl") log:core true}]
[ a r:Fact; r:gives {("consult" "./d3-group.pl") log:program true}]
[ a r:Fact; r:gives {("identity" "rotation_120" "rotation_240" "reflection_b") :validGroup true}]
);
r:binding [ r:variable [ n3:uri "http://www.w3.org/2000/10/swap/var#x_0"]; r:boundTo ("identity" "rotation_120" "rotation_240" "reflection_b")];
Expand All @@ -104,7 +104,7 @@ skolem:lemma7 a r:Inference;
("identity" "rotation_120" "rotation_240" "reflection_c") :validGroup true.
};
r:evidence (
[ a r:Fact; r:gives {("consult" "./d3-group.pl") log:core true}]
[ a r:Fact; r:gives {("consult" "./d3-group.pl") log:program true}]
[ a r:Fact; r:gives {("identity" "rotation_120" "rotation_240" "reflection_c") :validGroup true}]
);
r:binding [ r:variable [ n3:uri "http://www.w3.org/2000/10/swap/var#x_0"]; r:boundTo ("identity" "rotation_120" "rotation_240" "reflection_c")];
Expand All @@ -115,7 +115,7 @@ skolem:lemma8 a r:Inference;
("identity" "rotation_120" "rotation_240") :validGroup true.
};
r:evidence (
[ a r:Fact; r:gives {("consult" "./d3-group.pl") log:core true}]
[ a r:Fact; r:gives {("consult" "./d3-group.pl") log:program true}]
[ a r:Fact; r:gives {("identity" "rotation_120" "rotation_240") :validGroup true}]
);
r:binding [ r:variable [ n3:uri "http://www.w3.org/2000/10/swap/var#x_0"]; r:boundTo ("identity" "rotation_120" "rotation_240")];
Expand All @@ -126,7 +126,7 @@ skolem:lemma9 a r:Inference;
("identity" "reflection_a") :validGroup true.
};
r:evidence (
[ a r:Fact; r:gives {("consult" "./d3-group.pl") log:core true}]
[ a r:Fact; r:gives {("consult" "./d3-group.pl") log:program true}]
[ a r:Fact; r:gives {("identity" "reflection_a") :validGroup true}]
);
r:binding [ r:variable [ n3:uri "http://www.w3.org/2000/10/swap/var#x_0"]; r:boundTo ("identity" "reflection_a")];
Expand All @@ -137,7 +137,7 @@ skolem:lemma10 a r:Inference;
("identity" "reflection_b") :validGroup true.
};
r:evidence (
[ a r:Fact; r:gives {("consult" "./d3-group.pl") log:core true}]
[ a r:Fact; r:gives {("consult" "./d3-group.pl") log:program true}]
[ a r:Fact; r:gives {("identity" "reflection_b") :validGroup true}]
);
r:binding [ r:variable [ n3:uri "http://www.w3.org/2000/10/swap/var#x_0"]; r:boundTo ("identity" "reflection_b")];
Expand All @@ -148,7 +148,7 @@ skolem:lemma11 a r:Inference;
("identity" "reflection_c") :validGroup true.
};
r:evidence (
[ a r:Fact; r:gives {("consult" "./d3-group.pl") log:core true}]
[ a r:Fact; r:gives {("consult" "./d3-group.pl") log:program true}]
[ a r:Fact; r:gives {("identity" "reflection_c") :validGroup true}]
);
r:binding [ r:variable [ n3:uri "http://www.w3.org/2000/10/swap/var#x_0"]; r:boundTo ("identity" "reflection_c")];
Expand All @@ -159,7 +159,7 @@ skolem:lemma12 a r:Inference;
("identity") :validGroup true.
};
r:evidence (
[ a r:Fact; r:gives {("consult" "./d3-group.pl") log:core true}]
[ a r:Fact; r:gives {("consult" "./d3-group.pl") log:program true}]
[ a r:Fact; r:gives {("identity") :validGroup true}]
);
r:binding [ r:variable [ n3:uri "http://www.w3.org/2000/10/swap/var#x_0"]; r:boundTo ("identity")];
Expand All @@ -168,7 +168,7 @@ skolem:lemma12 a r:Inference;
skolem:lemma13 a r:Extraction;
r:gives {
@forAll var:x_0. {
("consult" "./d3-group.pl") log:core true.
("consult" "./d3-group.pl") log:program true.
var:x_0 :validGroup true.
} => {
var:x_0 :validGroup true.
Expand Down
2 changes: 1 addition & 1 deletion reasoning/d3-group/d3-group-query.n3
Original file line number Diff line number Diff line change
Expand Up @@ -2,7 +2,7 @@
@prefix : <https://eyereasoner.github.io/ns#>.

{
("consult" "./d3-group.pl") log:core true.
("consult" "./d3-group.pl") log:program true.
?Group :validGroup true.
} => {
?Group :validGroup true.
Expand Down
36 changes: 18 additions & 18 deletions reasoning/dining-philosophers/dp.n3
Original file line number Diff line number Diff line change
Expand Up @@ -9,36 +9,36 @@

{?P :pickup true} <= {
?P :chopstick (?L ?R).
("mutex_lock" ?L) log:core true.
("mutex_lock" ?R) log:core true.
("mutex_lock" ?L) log:program true.
("mutex_lock" ?R) log:program true.
}.

{?P :putdown true} <= {
?P :chopstick (?L ?R).
("mutex_unlock" ?R) log:core true.
("mutex_unlock" ?L) log:core true.
("mutex_unlock" ?R) log:program true.
("mutex_unlock" ?L) log:program true.
}.

{?P :run (?T ?S)} <= {
("sleep" ?T) log:core true.
#("format" "# ~w thinking for ~w seconds~n" (?P ?T)) log:core true.
("sleep" ?T) log:program true.
#("format" "# ~w thinking for ~w seconds~n" (?P ?T)) log:program true.
?P :pickup true.
("sleep" ?S) log:core true.
#("format" "# ~w eating for ~w seconds~n" (?P ?S)) log:core true.
("sleep" ?S) log:program true.
#("format" "# ~w eating for ~w seconds~n" (?P ?S)) log:program true.
?P :putdown true.
}.

{
("thread_create" {:person1 :run (0.100 0.100)} ?A ()) log:core true.
("thread_create" {:person2 :run (0.200 0.200)} ?B ()) log:core true.
("thread_create" {:person3 :run (0.300 0.300)} ?C ()) log:core true.
("thread_create" {:person4 :run (0.250 0.200)} ?D ()) log:core true.
("thread_create" {:person5 :run (0.025 0.100)} ?E ()) log:core true.
("thread_join" ?A ?F) log:core true.
("thread_join" ?B ?G) log:core true.
("thread_join" ?C ?H) log:core true.
("thread_join" ?D ?I) log:core true.
("thread_join" ?E ?J) log:core true.
("thread_create" {:person1 :run (0.100 0.100)} ?A ()) log:program true.
("thread_create" {:person2 :run (0.200 0.200)} ?B ()) log:program true.
("thread_create" {:person3 :run (0.300 0.300)} ?C ()) log:program true.
("thread_create" {:person4 :run (0.250 0.200)} ?D ()) log:program true.
("thread_create" {:person5 :run (0.025 0.100)} ?E ()) log:program true.
("thread_join" ?A ?F) log:program true.
("thread_join" ?B ?G) log:program true.
("thread_join" ?C ?H) log:program true.
("thread_join" ?D ?I) log:program true.
("thread_join" ?E ?J) log:program true.
} => {
:all :got :dinner.
}.
40 changes: 20 additions & 20 deletions reasoning/dining-philosophers/dpE.n3
Original file line number Diff line number Diff line change
Expand Up @@ -27,24 +27,24 @@ skolem:lemma2 a r:Inference;
r:evidence (
[ a r:Fact; r:gives {("thread_create" {
:person1 :run (0.1 0.1).
} skolem:t_0 ()) log:core true}]
} skolem:t_0 ()) log:program true}]
[ a r:Fact; r:gives {("thread_create" {
:person2 :run (0.2 0.2).
} skolem:t_1 ()) log:core true}]
} skolem:t_1 ()) log:program true}]
[ a r:Fact; r:gives {("thread_create" {
:person3 :run (0.3 0.3).
} skolem:t_2 ()) log:core true}]
} skolem:t_2 ()) log:program true}]
[ a r:Fact; r:gives {("thread_create" {
:person4 :run (0.25 0.2).
} skolem:t_3 ()) log:core true}]
} skolem:t_3 ()) log:program true}]
[ a r:Fact; r:gives {("thread_create" {
:person5 :run (0.025 0.1).
} skolem:t_4 ()) log:core true}]
[ a r:Fact; r:gives {("thread_join" skolem:t_0 true) log:core true}]
[ a r:Fact; r:gives {("thread_join" skolem:t_1 true) log:core true}]
[ a r:Fact; r:gives {("thread_join" skolem:t_2 true) log:core true}]
[ a r:Fact; r:gives {("thread_join" skolem:t_3 true) log:core true}]
[ a r:Fact; r:gives {("thread_join" skolem:t_4 true) log:core true}]
} skolem:t_4 ()) log:program true}]
[ a r:Fact; r:gives {("thread_join" skolem:t_0 true) log:program true}]
[ a r:Fact; r:gives {("thread_join" skolem:t_1 true) log:program true}]
[ a r:Fact; r:gives {("thread_join" skolem:t_2 true) log:program true}]
[ a r:Fact; r:gives {("thread_join" skolem:t_3 true) log:program true}]
[ a r:Fact; r:gives {("thread_join" skolem:t_4 true) log:program true}]
);
r:binding [ r:variable [ n3:uri "http://www.w3.org/2000/10/swap/var#x_0"]; r:boundTo skolem:t_0];
r:binding [ r:variable [ n3:uri "http://www.w3.org/2000/10/swap/var#x_1"]; r:boundTo skolem:t_1];
Expand Down Expand Up @@ -73,24 +73,24 @@ skolem:lemma4 a r:Extraction;
@forAll var:x_0, var:x_1, var:x_2, var:x_3, var:x_4, var:x_5, var:x_6, var:x_7, var:x_8, var:x_9. {
("thread_create" {
:person1 :run (0.1 0.1).
} var:x_0 ()) log:core true.
} var:x_0 ()) log:program true.
("thread_create" {
:person2 :run (0.2 0.2).
} var:x_1 ()) log:core true.
} var:x_1 ()) log:program true.
("thread_create" {
:person3 :run (0.3 0.3).
} var:x_2 ()) log:core true.
} var:x_2 ()) log:program true.
("thread_create" {
:person4 :run (0.25 0.2).
} var:x_3 ()) log:core true.
} var:x_3 ()) log:program true.
("thread_create" {
:person5 :run (0.025 0.1).
} var:x_4 ()) log:core true.
("thread_join" var:x_0 var:x_5) log:core true.
("thread_join" var:x_1 var:x_6) log:core true.
("thread_join" var:x_2 var:x_7) log:core true.
("thread_join" var:x_3 var:x_8) log:core true.
("thread_join" var:x_4 var:x_9) log:core true.
} var:x_4 ()) log:program true.
("thread_join" var:x_0 var:x_5) log:program true.
("thread_join" var:x_1 var:x_6) log:program true.
("thread_join" var:x_2 var:x_7) log:program true.
("thread_join" var:x_3 var:x_8) log:program true.
("thread_join" var:x_4 var:x_9) log:program true.
} => {
:all :got :dinner.
}.
Expand Down
Loading

0 comments on commit c339e1a

Please sign in to comment.