3

I want to implement SKI combinators in Prolog.

There are just 3 simple rules:

  1. (I x) = x
  2. ((K x) y) = x
  3. (S x y z) = (x z (y z))

I came up with the following code by using epilog:

term(s)
term(k)
term(i)
term(app(X,Y)) :- term(X) & term(Y)

proc(s, s)
proc(k, k)
proc(i, i)

proc(app(i,Y), Y1) :- proc(Y,Y1)
proc(app(app(k,Y),Z), Y1) :- proc(Y,Y1)
proc(app(app(app(s,P1),P2),P3), Y1) :- proc(app( app(P1,P3), app(P2, P3) ), Y1)

proc(app(X, Y), app(X1, Y1)) :- proc(X, X1) & proc(Y, Y1)
proc(X,X)

It works for some cases but has 2 issues:

  1. It takes too much time to execute simple queries:

    term(X) & proc(app(app(k, X), s), app(s,k)) 
    

    100004 unification(s)

  2. It requires multiple queries to process some terms. For example:

    ((((S(K(SI)))K)S)K) -> (KS)

    requires 2 runs:

    proc(app(app(app(app(s,app(k,app(s,i))),k),s),k),   X)    ==>
    proc(app(app(app(app(s,app(k,app(s,i))),k),s),k),   app(app(app(s,i),app(k,s)),k))
    
    proc(app(app(app(s,i),app(k,s)),k),    X)                 ==>
    proc(app(app(app(s,i),app(k,s)),k),    app(k,s))
    

Can you please suggest how to optimize my implementation and make it work on complex combinators?

edit: The goal is to reduce combinators. I want to enumerate them (without duplicates) where the last one is in normal form (if it exists of course).

Will Ness
  • 70,110
  • 9
  • 98
  • 181
Oleg Dats
  • 3,933
  • 9
  • 38
  • 61
  • what is your goal here? is it to reduce the combinators? (seems like it). there's usually multiple results, do you want to enumerate them all? in some order (like from shortest t longest)? *without duplicates*? – Will Ness Sep 28 '22 at 12:49
  • The goal is to reduce combinators. I want to enumerate them (without duplicates) where the last one is in normal form (if it exists of course). – Oleg Dats Sep 28 '22 at 13:15
  • For example: ((S K K) S) = (S K K S) = (K S (K S)) = S – Oleg Dats Sep 28 '22 at 13:17
  • aha, now it is clearer. – Will Ness Sep 28 '22 at 13:49

3 Answers3

3

It can be implemented with iterative deepening like this:

term(s) --> "S".
term(k) --> "K".
term(i) --> "I".
term(a(E0,E)) --> "(", term(E0), term(E), ")".

reduce_(s, s).
reduce_(k, k).
reduce_(i, i).
% Level 1.
reduce_(a(s,A0), a(s,A)) :-
    reduce_(A0, A).
reduce_(a(k,A0), a(k,A)) :-
    reduce_(A0, A).
reduce_(a(i,A), A).
% level 2.
reduce_(a(a(s,E0),A0), a(a(s,E),A)) :-
    reduce_(E0, E),
    if_(E0 = E, reduce_(A0, A), A0 = A).
    % reduce_(A0, A). % Without `reif`.
reduce_(a(a(k,E),_), E).
reduce_(a(a(i,E),A), a(E,A)).
% level 3.
reduce_(a(a(a(s,E),F),A), a(a(E,A),a(F,A))).
reduce_(a(a(a(k,E),_),A), a(E,A)).
reduce_(a(a(a(i,E),F),A), a(a(E,F),A)).
% Recursion.
reduce_(a(a(a(a(E0,E1),E2),E3),A0), a(E,A)) :-
    reduce_(a(a(a(E0,E1),E2),E3), E),
    if_(a(a(a(E0,E1),E2),E3) = E, reduce_(A0, A), A0 = A).
    % reduce_(A0, A). % Without `reif`.

step(E, E0, E) :-
    reduce_(E0, E).

reduce_(N, E0, E, [E0|Es]) :-
    length(Es, N),
    foldl(step, Es, E0, E).

reduce(N, E0, E) :-
    reduce_(N, E0, E, _),
    reduce_(E, E), % Fix point.
    !. % Commit.

The term can be inputted and outputted as a list of characters with term//1. The grammar rule term//1 can also generate unique terms.

?- length(Cs, M), M mod 3 =:= 1, phrase(term(E0), Cs).

The goal is to be as lazy as possible when reducing a term thus dif/2 and the library reif is used in reduce_/2. The predicate reduce_/2 does a single reduction. If any of the argument of reduce_/2 is ground then termination is guarantee (checked with cTI).

To reduce a term, reduce_/4 can be used. The first argument specifies the depth, the last argument holds the list of terms. The predicate reduce_/4 is pure and does not terminate.

?- Cs = "(((SK)K)S)", phrase(term(E0), Cs), reduce_(N, E0, E, Es).

The predicate reduce/3 succeeds if there is a normal form. It is recommended to provide a maximum depth (e.g. Cs = "(((SI)I)((SI)(SI)))"):

?- length(Cs, M), M mod 3 =:= 1, phrase(term(E0), Cs), \+ reduce(16, E0, _).

Test with ((((S(K(SI)))K)S)K):

?- Cs0 = "((((S(K(SI)))K)S)K)", phrase(term(E0), Cs0), 
   reduce(N, E0, E), phrase(term(E), Cs).

   Cs0="((((S(K(SI)))K)S)K)", E0=a(a(a(a(s,a(k,a(s,i))),k),s),k), N=5, E=a(k,s), Cs="(KS)"
Will Ness
  • 70,110
  • 9
  • 98
  • 181
notoria
  • 2,053
  • 1
  • 4
  • 15
  • without looking into code, is it working by iterative deepening? Could you perhaps add a few words of explanation in general? – Will Ness Sep 28 '22 at 16:49
  • 1
    Yes, it is iterative deepening with `reduce_/4`. – notoria Sep 28 '22 at 16:54
  • @notoria I try to run $ Cs = "(((SK)K)S)", phrase(term(E0), Cs), reduce_(N, E0, E, Es). $ in https://swish.swi-prolog.org and it produces False. I have changed only if(..) to (p1 -> p2 ; p3). Can you please suggest how to fix it? – Oleg Dats Sep 30 '22 at 08:32
  • 1
    Don't change `if_/3` with `(->)/2` and `(;)/2`. If `reif` isn't available then comment the `if_/3` lines and uncomment the ones following `if_/3`. And `:- set_prolog_flag(double_quotes, chars)` for SWI-Prolog. – notoria Sep 30 '22 at 09:38
  • what version of Prolog do you use? – Oleg Dats Sep 30 '22 at 11:11
  • I mainly use Scryer Prolog. I tested this solution with Scryer and SWI. – notoria Sep 30 '22 at 11:17
  • It works for reductions. I can not make it work for searching terms, for example: $N=10, reduce(N, a(a(a(a(s, X ),k),s),k), a(k,s)).$ runs forever, even the answer is simple: X=a(k,a(s,i)). Ideally, I want to get an answer for: reduce(N, a(a(X,s),k), a(k,s)). (find a term that swaps 2 terms) – Oleg Dats Sep 30 '22 at 13:36
  • 1
    When you run the query `?- reduce_(E0, a(k,s)).` there are multiple results (more than 2), you will be searching in a space that increases exponentially on depth. You need to guide the search like `?- N = 4, length(Cs, M), M mod 3 =:= 1, phrase(term(X), Cs), reduce(N, a(a(a(a(s, X ),k),s),k), a(k,s)).`. – notoria Sep 30 '22 at 14:19
  • Just a last question, why does `?- N = 4, length(Cs, M), phrase(term(X), Cs), reduce(N, a(a(X,s),k), a(k,s)).` works (even without specifying M) but when `length(Cs, M)` is removed it runs forever? And another one: why this query produces stack limit error: `?- N = 4, length(Cs12, M1), length(Cs1, M2), length(Cs2, M3), M1=3, M2=2, M3=2, phrase(term(F), Cs12), phrase(term(X1), Cs1), phrase(term(X2), Cs2), reduce(N, a(F, X1), X2), reduce(N, a(F, X2), X1).` – Oleg Dats Sep 30 '22 at 16:16
  • 1
    That because of unfair enumeration (try `?- phrase(term(X), Cs).`). The stack error is because of `length/2` (simpler: `?- length(Cs, N), N=1.`). – notoria Sep 30 '22 at 16:44
2

Translating your code trivially to Prolog, using the built-in left-associating infix operator - for app, to improve readability,

term(s).
term(k).
term(i).
term( X-Y ) :- term(X) , term(Y).

/* proc(s, s).      %%% not really needed.
proc(k, k).
proc(i, i). */

proc( i-Y, Y1) :- proc( Y,Y1).
proc( k-Y-Z, Y1) :- proc( Y,Y1).
proc( s-X-Y-Z, Y1) :- proc( X-Z-(Y-Z), Y1).

proc( X-Y, X1-Y1 ) :- proc( X, X1) , proc( Y, Y1).
proc( X, X).

executing in SWI Prolog,

26 ?- time( (term(X), proc( k-X-s, s-k)) ).
% 20 inferences, 0.000 CPU in 0.001 seconds (0% CPU, Infinite Lips)
X = s-k ;
% 1 inferences, 0.000 CPU in 0.000 seconds (?% CPU, Infinite Lips)
X = s-k ;
Action (h for help) ? abort
% 952,783 inferences, 88.359 CPU in 90.112 seconds (98% CPU, 10783 Lips)
% Execution Aborted
27 ?- 

the first result is produced in 20 inferences.


Furthermore, indeed

32 ?- time( proc( s-(k-(s-i))-k-s-k, X) ).
% 10 inferences, 0.000 CPU in 0.000 seconds (?% CPU, Infinite Lips)
X = s-i- (k-s)-k ;
% 2 inferences, 0.000 CPU in 0.001 seconds (0% CPU, Infinite Lips)
X = s-i- (k-s)-k ;
% 5 inferences, 0.000 CPU in 0.000 seconds (?% CPU, Infinite Lips)
X = s-i- (k-s)-k ;
% 2 inferences, 0.000 CPU in 0.000 seconds (?% CPU, Infinite Lips)
X = s-i- (k-s)-k ;
% 11 inferences, 0.000 CPU in 0.001 seconds (0% CPU, Infinite Lips)
X = k- (s-i)-s- (k-s)-k ;
% 2 inferences, 0.000 CPU in 0.000 seconds (?% CPU, Infinite Lips)
X = k- (s-i)-s- (k-s)-k . % stopped manually

and then

33 ?- time( proc( s-i- (k-s)-k, X) ).
% 5 inferences, 0.000 CPU in 0.000 seconds (?% CPU, Infinite Lips)
X = k-s ;
% 5 inferences, 0.000 CPU in 0.000 seconds (?% CPU, Infinite Lips)
X = k- (k-s-k) ;
% 2 inferences, 0.000 CPU in 0.000 seconds (?% CPU, Infinite Lips)
X = k- (k-s-k) ;
% 1 inferences, 0.000 CPU in 0.000 seconds (?% CPU, Infinite Lips)
X = k- (k-s-k) ;
% 5 inferences, 0.000 CPU in 0.000 seconds (?% CPU, Infinite Lips)
X = i-k-s ;
% 5 inferences, 0.000 CPU in 0.000 seconds (?% CPU, Infinite Lips)
X = i-k- (k-s-k) ;
% 2 inferences, 0.000 CPU in 0.000 seconds (?% CPU, Infinite Lips)
X = i-k- (k-s-k) ;
% 1 inferences, 0.000 CPU in 0.000 seconds (?% CPU, Infinite Lips)
X = i-k- (k-s-k) ;
% 3 inferences, 0.000 CPU in 0.000 seconds (?% CPU, Infinite Lips)
X = i-k-s ;
% 5 inferences, 0.000 CPU in 0.000 seconds (?% CPU, Infinite Lips)
X = i-k- (k-s-k) . % stopped manually

but probably the result you wanted will still get generated directly, just after some more time.

Will Ness
  • 70,110
  • 9
  • 98
  • 181
  • BTW your [haskell question](https://stackoverflow.com/questions/73878832/how-to-implement-the-next-type-inference-in-haskell) is really unclear. – Will Ness Sep 28 '22 at 12:24
  • but I invite you to browse through [my answers on the matter](https://stackoverflow.com/search?q=user%3A849891+%5Btype-inference%5D), esp. [this one](https://stackoverflow.com/questions/14335704/how-to-infer-the-type-of-an-expression-manually/14558244#14558244) with a rudimentary Prolog program for very simplified type inference. – Will Ness Sep 28 '22 at 12:55
  • I tried this code (SWI-Prolog online) and have 2 issues: "proc( k-Y-Z, Y1) :- proc( Y,Y1). Singleton variables: [Z]", "time( (term(X), proc( s-s-s, X)) )." produces infinite run – Oleg Dats Sep 28 '22 at 13:21
  • $time( (term(X), proc( X-k-s, s-k)) ).$ runs forever. – Oleg Dats Sep 28 '22 at 13:28
  • yes, I just translated your code, for now. :) – Will Ness Sep 28 '22 at 13:48
0

Based on Will Ness answer here is my solution:

term(s).
term(k).
term(i).
term(app(X,Y)) :- term(X), term(Y).

eq(s,s).
eq(k,k).
eq(i,i).
eq(app(X,Y),app(X,Y)).

proc(s, s).
proc(k, k).
proc(i, i).

proc(app(i,Y), Y1) :- proc(Y,Y1).
proc(app(app(k,Y),Z), Y1) :- proc(Y,Y1).
proc(app(app(app(s,P1),P2),P3), Y1) :- proc(app( app(P1,P3), app(P2, P3) ), Y1).

proc(app(X, Y), Z) :- proc(X, X1), proc(Y, Y1), eq(X, X1), eq(X, X1), eq(app(X, Y), Z).
proc(app(X, Y), Z) :- proc(X, X1), proc(Y, Y1), not(eq(X, X1)), proc(app(X1, Y1), Z).
proc(app(X, Y), Z) :- proc(X, X1), proc(Y, Y1), not(eq(Y, Y1)), proc(app(X1, Y1), Z).
  1. Move code to swish prolog. It works much faster

time((term(X), proc(app(app(k, X), s), app(s,k)))). 
% 356 inferences, 0.000 CPU in 0.000 seconds (94% CPU, 3768472 Lips)
X = app(s,k)
  1. Implemented complete reduction procedure:

proc(app(app(app(app(s,app(k,app(s,i))),k),s),k), X) 
answer contains: X = app(k,s)

There are still issues that I can not resolve

  1. time((term(X), proc(app(app(X, k), s), app(s,k)))). runs forever
  2. Answers are not ordered by reductions.
Oleg Dats
  • 3,933
  • 9
  • 38
  • 61