Skip to content

Commit bbb5d5b

Browse files
committed
Add more tests + handle more cases
1 parent 298805f commit bbb5d5b

File tree

2 files changed

+95
-14
lines changed

2 files changed

+95
-14
lines changed

tests/scryer/cli/issues/incorrect_arithmetics.in/hoist-expr.pl

Lines changed: 92 additions & 11 deletions
Original file line numberDiff line numberDiff line change
@@ -2,13 +2,14 @@
22
:- use_module(library(dcgs)).
33
:- use_module(library(format)).
44
:- use_module(library(reif)).
5+
:- use_module(library(debug)).
56

67
tt :-
78
tt(Clause),
89
nl, portray_clause(Clause), nl.
910
tt((f(V is Expr) :- Sequence)) :-
10-
sample("ttttffft", _ is Expr),
11-
once(phrase(ae(Expr,Repl), Removed)),
11+
sample("tttffft", _ is Expr),
12+
phrase(ae(Expr,Repl), Removed),
1213
append(Removed, [V is Repl], X),
1314
list_sequence(X, Sequence).
1415

@@ -18,42 +19,122 @@
1819
length(Es, L),
1920
repeat,
2021
random_integer(0, L, I),
21-
format("~n% Info: Selected ~dth out of ~d found aritmetic relations that satisfy ~s template:~n\t", [I,L,Template]),
22+
format("~n% Info: Selected ~dth out of ~d found aritmetic relations that satisfy ~s template:~n", [I,L,Template]),
2223
nth0(I, Es, R).
2324

2425
%% Proof-of-concept arithmetic expression expander
2526
%
2627
% TODO: Don't use DCG's, because they aren't available in loader.pl
27-
% TODO: Don't hardcode invalid expression
2828
test :- test(Clause), nl, portray_clause(Clause), nl.
2929
test((f(V is Expr) :- Sequence)) :-
3030
length(Removed, _),
3131
phrase(ae(Expr,Repl), Removed),
3232
append(Removed, [V is Repl], X),
3333
list_sequence(X, Sequence).
3434

35-
ae(F, FR) --> ez(F, A, B, AR, BR, FR), ae(A, AR), ae(B, BR).
36-
ae(F, FR) --> ey(F, A, R, FR), ae(A, R).
3735
ae(A, R) --> ex(A, R).
36+
ae(F, FR) --> ey(F, A, R, FR), ae(A, R).
37+
ae(F, FR) --> ez(F, A, B, AR, BR, FR), ae(A, AR), ae(B, BR).
38+
39+
ex(A, R) --> {ok_var(A,R)} -> proceed(A,R); [R=A].
3840

39-
ex(A , R ) --> [R = A], { nonvar(A), \+number(A), A \= e, A \= pi}.
40-
ex(A , A ) --> t, { var(A) }.
41-
ex(A , A ) --> t, { number(A) }.
42-
ex(e , e ) --> t.
43-
ex(pi , pi ) --> t.
41+
proceed(e,e) --> t.
42+
proceed(pi,pi) --> t.
43+
proceed(epsilon,epsilon) --> t.
4444

4545
ey(-A ,A, AR,-AR) --> t.
46+
ey(+A ,A, AR,+AR) --> t.
47+
ey(\A ,A, AR,\AR) --> t.
4648
ey(sqrt(A),A, AR,sqrt(AR)) --> t.
4749
ey(log(A) ,A, AR,log(AR)) --> t.
50+
ey(abs(A) ,A, AR,abs(AR)) --> t.
51+
ey(cos(A) ,A, AR,cos(AR)) --> t.
52+
ey(sin(A) ,A, AR,sin(AR)) --> t.
53+
ey(tan(A) ,A, AR,tan(AR)) --> t.
54+
ey(exp(A) ,A, AR,exp(AR)) --> t.
55+
ey(acos(A) ,A, AR,acos(AR)) --> t.
56+
ey(asin(A) ,A, AR,asin(AR)) --> t.
57+
ey(atan(A) ,A, AR,atan(AR)) --> t.
58+
ey(float(A) ,A, AR,float(AR)) --> t.
59+
ey(truncate(A) ,A, AR,truncate(AR)) --> t.
60+
ey(round(A) ,A, AR,round(AR)) --> t.
61+
ey(ceiling(A) ,A, AR,ceiling(AR)) --> t.
62+
ey(floor(A) ,A, AR,floor(AR)) --> t.
63+
ey(float_integer_part(A) ,A, AR,float_integer_part(AR)) --> t.
64+
ey(float_fractional_part(A) ,A, AR,float_fractional_part(AR)) --> t.
65+
ey(sign(A) ,A, AR,sign(AR)) --> t.
4866

4967
ez(A+B,A,B, AR,BR,AR+BR) --> t.
5068
ez(A-B,A,B, AR,BR,AR-BR) --> t.
5169
ez(A*B,A,B, AR,BR,AR*BR) --> t.
5270
ez(A/B,A,B, AR,BR,AR/BR) --> t.
5371
ez(A^B,A,B, AR,BR,AR^BR) --> t.
72+
ez(A**B,A,B, AR,BR,AR**BR) --> t.
73+
ez(A/\B,A,B, AR,BR,AR/\BR) --> t.
74+
ez(A\/B,A,B, AR,BR,AR\/BR) --> t.
75+
ez(A xor B,A,B, AR,BR,AR xor BR) --> t.
76+
ez(A div B,A,B, AR,BR,AR div BR) --> t.
77+
ez(A // B,A,B, AR,BR,AR // BR) --> t.
78+
ez(A rdiv B,A,B, AR,BR,AR rdiv BR) --> t.
79+
ez(A << B,A,B, AR,BR,AR << BR) --> t.
80+
ez(A >> B,A,B, AR,BR,AR >> BR) --> t.
81+
ez(A mod B,A,B, AR,BR,AR mod BR) --> t.
82+
ez(A rem B,A,B, AR,BR,AR rem BR) --> t.
83+
ez(max(A,B),A,B, AR,BR,max(AR,BR)) --> t.
84+
ez(min(A,B),A,B, AR,BR,min(AR,BR)) --> t.
85+
ez(gcd(A,B),A,B, AR,BR,gcd(AR,BR)) --> t.
86+
ez(atan2(A,B),A,B, AR,BR,atan2(AR,BR)) --> t.
5487

5588
t --> [].
5689

90+
ok_var(A, A) :-
91+
var(A); number(A); (nonvar(A), arithmetic_term(A)).
92+
93+
arithmetic_term(e).
94+
arithmetic_term(pi).
95+
arithmetic_term(epsilon).
96+
arithmetic_term(-_).
97+
arithmetic_term(+_).
98+
arithmetic_term(\_).
99+
arithmetic_term(sqrt(_)).
100+
arithmetic_term(log(_)).
101+
arithmetic_term(abs(_)).
102+
arithmetic_term(cos(_)).
103+
arithmetic_term(sin(_)).
104+
arithmetic_term(tan(_)).
105+
arithmetic_term(exp(_)).
106+
arithmetic_term(acos(_)).
107+
arithmetic_term(asin(_)).
108+
arithmetic_term(atan(_)).
109+
arithmetic_term(float(_)).
110+
arithmetic_term(truncate(_)).
111+
arithmetic_term(round(_)).
112+
arithmetic_term(ceiling(_)).
113+
arithmetic_term(floor(_)).
114+
arithmetic_term(float_integer_part(_)).
115+
arithmetic_term(float_fractional_part(_)).
116+
arithmetic_term(sign(_)).
117+
arithmetic_term(_+_).
118+
arithmetic_term(_-_).
119+
arithmetic_term(_*_).
120+
arithmetic_term(_/_).
121+
arithmetic_term(_^_).
122+
arithmetic_term(_**_).
123+
arithmetic_term(_/\_).
124+
arithmetic_term(_\/_).
125+
arithmetic_term(_ xor _).
126+
arithmetic_term(_ div _).
127+
arithmetic_term(_ // _).
128+
arithmetic_term(_ rdiv _).
129+
arithmetic_term(_ << _).
130+
arithmetic_term(_ >> _).
131+
arithmetic_term(_ mod _).
132+
arithmetic_term(_ rem _).
133+
arithmetic_term(max(_,_)).
134+
arithmetic_term(min(_,_)).
135+
arithmetic_term(gcd(_,_)).
136+
arithmetic_term(atan2(_,_)).
137+
57138
%% list_sequence(List, Sequence).
58139
%
59140
list_sequence([H|T], S) :- ls_aux(T, H, S).

tests/scryer/cli/issues/incorrect_arithmetics.in/incorrect_arithmetics.pl

Lines changed: 3 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -57,13 +57,13 @@
5757
func(Expr) --> {fn(T, Expr)}, [T].
5858
rel(Expr) --> {rl(T, Expr)}, [T].
5959

60-
rl(t, expr(F,A,B)) :- member(F, [A<B,A=:=B]).
60+
%rl(t, expr(F,A,B)) :- member(F, [A<B,A=:=B]).
6161
rl(t, expr(F,A)) :- member(F, [_ is A]).
6262

6363
fn(t, expr(A)) :- rnd(A).
6464
fn(t, expr(A)) :- member(A, [e,pi]).
65-
fn(t, expr(F,A)) :- member(F, [-(A),sqrt(A),log(A)]).
66-
fn(t, expr(F,A,B)) :- member(F, [A+B,A-B,A*B,A/B,A^B]).
65+
fn(t, expr(F,A)) :- member(F, [-A,sqrt(A),log(A),tan(A),\A,+A]).
66+
fn(t, expr(F,A,B)) :- member(F, [A+B,A-B,A*B,A/B,A^B,max(A,B)]).
6767
fn(f, expr(F)) :- member(F, [[],phi,[_|_]]).
6868
fn(f, expr(F,A)) :- member(F, [zeta(A)]).
6969
fn(f, expr(F,A,B)) :- member(F, [[A,B]]).

0 commit comments

Comments
 (0)