/* CSE 341 - brief tour of the finite domain and integer constraint solver. Finite domain constraints can be used to model and solve various combinatorial problems. */ :- use_module(library(clpfd)). /* A few sample goals: X#>3. X#>3, X#<10. X#>3, X#<10, Y#<10, Y#=X+5. Vs = [X,Y,Z], Vs ins 1..3, all_different(Vs), X = 1, Y #\= 2. We can use 'label' to systematically try out values for a list of finite domain variables until all of them are ground: X#>3, X#<10, Y#=X+5, label([Y]). */ puzzle([S,E,N,D] + [M,O,R,E] = [M,O,N,E,Y]) :- Vars = [S,E,N,D,M,O,R,Y], Vars ins 0..9, all_different(Vars), S*1000 + E*100 + N*10 + D + M*1000 + O*100 + R*10 + E #= M*10000 + O*1000 + N*100 + E*10 + Y, M #\= 0, S #\= 0. /* Sample queries for puzzle. This query won't solve for all the variables: ?- puzzle(As+Bs=Cs). Different version that uses individual variables: ?- puzzle([S,E,N,D] + [M,O,R,E] = [M,O,N,E,Y]). ?- puzzle(As+Bs=Cs), label(As). Or we can try just labelling one variable: ?- puzzle([S,E,N,D] + [M,O,R,E] = [M,O,N,E,Y]), label([N]). ?- puzzle([S,E,N,D] + [M,O,R,E] = [M,O,N,E,Y]), label([E]). ?- puzzle([S,E,N,D] + [M,O,R,E] = [M,O,N,E,Y]), label([Y]). In nearly all cases this gives a unique solution. */ /* We can also use this library to replace uses of 'is' for integer arithmetic in other queries, often resulting in more generality. For example, here is factorial. */ factorial(0, 1). factorial(N, F) :- N #> 0, N1 #= N - 1, factorial(N1, F1), F #= N * F1.