|
2 | 2 | :- use_module(library(dcgs)).
|
3 | 3 | :- use_module(library(format)).
|
4 | 4 | :- use_module(library(reif)).
|
| 5 | +:- use_module(library(debug)). |
5 | 6 |
|
6 | 7 | tt :-
|
7 | 8 | tt(Clause),
|
8 | 9 | nl, portray_clause(Clause), nl.
|
9 | 10 | 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), |
12 | 13 | append(Removed, [V is Repl], X),
|
13 | 14 | list_sequence(X, Sequence).
|
14 | 15 |
|
|
18 | 19 | length(Es, L),
|
19 | 20 | repeat,
|
20 | 21 | 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]), |
22 | 23 | nth0(I, Es, R).
|
23 | 24 |
|
24 | 25 | %% Proof-of-concept arithmetic expression expander
|
25 | 26 | %
|
26 | 27 | % TODO: Don't use DCG's, because they aren't available in loader.pl
|
27 |
| -% TODO: Don't hardcode invalid expression |
28 | 28 | test :- test(Clause), nl, portray_clause(Clause), nl.
|
29 | 29 | test((f(V is Expr) :- Sequence)) :-
|
30 | 30 | length(Removed, _),
|
31 | 31 | phrase(ae(Expr,Repl), Removed),
|
32 | 32 | append(Removed, [V is Repl], X),
|
33 | 33 | list_sequence(X, Sequence).
|
34 | 34 |
|
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). |
37 | 35 | 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]. |
38 | 40 |
|
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. |
44 | 44 |
|
45 | 45 | ey(-A ,A, AR,-AR) --> t.
|
| 46 | +ey(+A ,A, AR,+AR) --> t. |
| 47 | +ey(\A ,A, AR,\AR) --> t. |
46 | 48 | ey(sqrt(A),A, AR,sqrt(AR)) --> t.
|
47 | 49 | 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. |
48 | 66 |
|
49 | 67 | ez(A+B,A,B, AR,BR,AR+BR) --> t.
|
50 | 68 | ez(A-B,A,B, AR,BR,AR-BR) --> t.
|
51 | 69 | ez(A*B,A,B, AR,BR,AR*BR) --> t.
|
52 | 70 | ez(A/B,A,B, AR,BR,AR/BR) --> t.
|
53 | 71 | 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. |
54 | 87 |
|
55 | 88 | t --> [].
|
56 | 89 |
|
| 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 | + |
57 | 138 | %% list_sequence(List, Sequence).
|
58 | 139 | %
|
59 | 140 | list_sequence([H|T], S) :- ls_aux(T, H, S).
|
|
0 commit comments