Sum up a list using Prolog - list

I want to sum all list elements greater than some given number. Here's the description:
sumup(L, N, GREATN, GEN) sums up the members of list L which are greater than GREATN to a variable N and puts these members into the list GEN.
Sample query:
?- sumup([8, 6, 10, 3, 9, 12], N, 7, GEN).
GEN = [8, 10, 9, 12], % expected answer
N = 39. % 8+10+9+12 = 39
Following is my code:
sum_list([], 0).
sum_list([H|T], Sum) :-
H > 3,
sum_list(T, Rest),
Sum is H + Rest.
sum_list([H|T], Sum) :-
H < 3,
write('').
I've tried the recursive way but I failed. How can I fix it?

Looking at your question and your code, I noticed a few things:
While you speak of "numbers" several times, your samples are integer-only. May we neglect non-integer numbers (float, rational) and handle integers only? I guess so.
There is an auto-loaded SWI-Prolog library(lists) predicate sum_list/2.
Calling your predicate sum_list/2 is an unfortunate choice.
Let's pick another name!
Your definition of sum_list/2 comprises three clauses:
sum_list([], 0).
Okay!
sum_list([H|T], Sum) :- H > 3, sum_list(T, Rest), Sum is H + Rest.
Notice H > 3? Why hardcode the constant integer 3?
sum_list([H|T], Sum) :- H < 3, write('').
That clause is not recursive. We need to see all list elements to calculate the sum, not stop at the first list element H that fulfills H < 3!
What's the use of write('')? I don't see any.
What good is the goal H < 3? Like above, why hardcode the integer 3?
Clause #2 covers H > 3. Clause #3 covers H < 3. What about H = 3?
In this answer we use clpfd, which is present in swi-prolog.
Here's a straight-forward definition of sumup/4 based on clpfd. While it could be improved in several ways (better determinism, accumulator-style, possibly some clever redundant constraints could also help), but for the time being it's a nice first shot:
:- use_module(library(clpfd)).
sumup([], 0, _, []).
sumup([Z|Zs], S0, P, [Z|Xs]) :-
Z #> P,
S0 #= S+Z,
sumup(Zs, S, P, Xs).
sumup([Z|Zs], S, P, Xs) :-
Z #=< P,
sumup(Zs, S, P, Xs).
Sample query as given by the OP:
?- sumup([8,6,10,3,9,12], N, 7, GEN).
N = 39, GEN = [8,10,9,12] % expected answer
; false. % leftover useless choicepoint

No need to write recursive code! Just use tfilter/3, (#<)/3, and clpfd:sum/3 like this:
:- use_module(library(clpfd)).
sumup(Zs, S, P, Xs) :-
tfilter(#<(P), Zs, Xs),
sum(Xs, #=, S).
Sample query:
?- sumup([8,6,10,3,9,12], S, 7, Xs).
S = 39, Xs = [8,10,9,12]. % expected result
Note that above query succeeds deterministically—a clear improvement over this previous answer!
Bonus! As the implementation of sumup/4 is monotonic, we know that the solution of above query is also part of the solution set of every generalization of the query. Look for yourself!
?- sumup([8,6,10,3,9,12], S, E, Xs).
S = 48, E in inf..2 , Xs = [8,6,10,3,9,12]
; S = 45, E in 3..5 , Xs = [8,6,10, 9,12]
; S = 39, E in 6..7 , Xs = [8, 10, 9,12] % <==== solution of above query
; S = 31, E in 8..8 , Xs = [10, 9,12]
; S = 22, E in 9..9 , Xs = [10, 12]
; S = 12, E in 10..11 , Xs = [12]
; S = 0, E in 12..sup, Xs = []
; false.

In SWI-Prolog you can use a fold and simply query:
L=[8, 6, 10, 3, 9, 12], include(<(7),L,Gen), foldl(plus,Gen,0,N).
so that sumup would be written as
sumup(L,N,GreatN,Gen) :-
include(<(GreatN),L,Gen),
foldl(plus,Gen,0,N).
plus/3 is an arithmetic predicate that works well in our case.

Related

How to perform arithmetic operations on a list of lists in prolog

I'm writing a function that takes in a list of lists and takes the head element in the list and compares it to every other element in the list of lists. I know using recursion is how to perform most actions on a list but I've been coming across some difficulties trying to translate this onto a list of lists. This is what I've come up with so far:
compareElements([H|T]) :-
compareHeadList(H,T).
compareHeadList([H|T],RestOfList) :-
compare(T,H,GreaterList,LesserList),
compareRestList(RestOfList,H).
compareRestList(X,[HA|TA]) :-
compare(HA,X,GreaterList,LesserList),
compareRestList(X,TA).
compare([HA|TA],X,GreaterList,LesserList) :-
X #> HA -> GreaterList = [HA|GreaterTail],
compare(TA,X,GreaterTail,LesserList);
LesserList = [HA|LesserTail],
compare(TA,X,GreaterList,LesserTail).
compare([_|TA],X,GreaterList,LesserList) :-
compare(TA,X,GreaterList,LesserList).
For Example:
compareElements(LoL).
Where Lol = [[6,4,8],[7,9,2],[1,3,0]]
My Goal is to compare 6 with every other element in the Lol,
so that GreaterList = [8,7,9], and LesserList = [4,2,1,3,0]
My idea of how the code should run is compareElements() takes in a list of lists, then calls compareHeadList() to compare the head of the first list with the rest of the elements in that list. Finally, compareRestList() is supposed to take in the Head element to be compared and the rest of the list of lists, call the compare function, and return true.
My problem is when I writeLn() the lists to check the elements it's outputting sequences like "9c78" which seems like a memory address. I'm wondering if I'm comparing the elements properly and pushing them onto the list correctly or if there is another piece causing this to happen.
head_head([[X|_]|_], X).
split_list(_, [], [], []).
split_list(K, [H|T], G, S) :- H = K, split_list(K, T, G, S).
split_list(K, [H|T], [H|G], S) :- H > K, split_list(K, T, G, S).
split_list(K, [H|T], G, [H|S]) :- H < K, split_list(K, T, G, S).
split_lol(X, G, S) :- head_head(X, K), append(X, L), split_list(K, L, G, S).
Test:
?- split_lol([[6,4,8],[7,9,2],[1,3,0]], G, S).
G = [8, 7, 9],
S = [4, 2, 1, 3, 0] .
?-
Some kewl "backwards" functionality Prolog gives you:
?- split_lol([[6,X,Y], [A, B]], [7, 8], [2, 1]).
X = 7,
Y = 8,
A = 2,
B = 1 ;
X = 7,
Y = 2,
A = 8,
B = 1 ;
X = 7,
Y = 2,
A = 1,
B = 8 ;
X = 2,
Y = 7,
A = 8,
B = 1 ;
X = 2,
Y = 7,
A = 1,
B = 8 ;
X = 2,
Y = 1,
A = 7,
B = 8 ;
false.
?-
Your approach can be made to work. For a hint on what is missing, see these warnings emitted by Prolog:
Warning: /home/isabelle/lol.pl:4:
Singleton variables: [GreaterList,LesserList]
Warning: /home/isabelle/lol.pl:8:
Singleton variables: [GreaterList,LesserList]
Singleton variable warnings are serious. They tell you that you have made the kind of typo that typically makes a program meaningless, or (as in this case) that you have not yet connected some parts of the computation with others. In your program, even when you compute the greater/lesser lists for one of the nested lists, you never relate this to the greater/lesser lists for the other nested lists -- so you can never get a complete answer.
If the greater list for one of the lists is [8], and for another list it's [7, 9], then we somehow want to construct the total greater list of [8, 7, 9]. A common way in Prolog is to actually only compute partial lists: Lists where the tail is not [] but a variable. In the example, if we compute the partial list [8 | Tail], and then ask for the next computation to be unified with Tail, we get a combined partial list of [8, 7, 9 | Tail2]. Unifying Tail2 with [] will then close the list in the end.
Here is your code adapted to this approach, and using somewhat more explicit names:
list_element_greater_smaller([], _Y, GreaterTail, GreaterTail, SmallerTail, SmallerTail).
list_element_greater_smaller([X | Xs], Y, Greater, GreaterTail, Smaller, SmallerTail) :-
( X > Y
-> Greater = [X | Greater1],
list_element_greater_smaller(Xs, Y, Greater1, GreaterTail, Smaller, SmallerTail)
; Smaller = [X | Smaller1],
list_element_greater_smaller(Xs, Y, Greater, GreaterTail, Smaller1, SmallerTail) ).
lists_element_greater_smaller([], _Y, GreaterTail, GreaterTail, SmallerTail, SmallerTail).
lists_element_greater_smaller([Xs | Xss], Y, Greater, GreaterTail, Smaller, SmallerTail) :-
list_element_greater_smaller(Xs, Y, Greater, GreaterTail1, Smaller, SmallerTail1),
lists_element_greater_smaller(Xss, Y, GreaterTail1, GreaterTail, SmallerTail1, SmallerTail).
lists_greater_smaller([[Y | Xs] | Xss], Greater, Smaller) :-
lists_element_greater_smaller([Xs | Xss], Y, Greater, [], Smaller, []).
Take the time to understand how the Tail variables are threaded through all the computations and then closed off with [].
This behaves as follows:
?- lists_greater_smaller([[6,4,8],[7,9,2],[1,3,0]], Greater, Smaller).
Greater = [8, 7, 9],
Smaller = [4, 2, 1, 3, 0].
As long as the nesting depth of the lists is fixed, there is also a simpler way to write all this: You can write a single recursive predicate over nested lists very similarly to how you do a recursion over a "flat" list. You will have three cases to distinguish:
the overall outer list is empty
the first nested list is empty
the first nested list has some head and tail
This approach can look like this:
lists_greater_smaller2([[Y | Xs] | Xss], Greater, Smaller) :-
lists_element_greater_smaller2([Xs | Xss], Y, Greater, Smaller).
lists_element_greater_smaller2([], _Y, [], []).
lists_element_greater_smaller2([[] | Xss], Y, Greater, Smaller) :-
lists_element_greater_smaller2(Xss, Y, Greater, Smaller).
lists_element_greater_smaller2([[X | Xs] | Xss], Y, Greater, Smaller) :-
( X > Y
-> Greater = [X | Greater1],
lists_element_greater_smaller2([Xs | Xss], Y, Greater1, Smaller)
; Smaller = [X | Smaller1],
lists_element_greater_smaller2([Xs | Xss], Y, Greater, Smaller1) ).
And again:
?- lists_greater_smaller2([[6,4,8],[7,9,2],[1,3,0]], Greater, Smaller).
Greater = [8, 7, 9],
Smaller = [4, 2, 1, 3, 0] ;
false.

Prolog With Lists

I received this problem and I can't get it done, I don't know what I've done wrong, can someone help me ?
Write a predicate to add a value v after 1-st, 2-nd, 4-th, 8-th, … element in a list.
% add(L:list, E:Number, P:Number, C:number, H:List)
% add(i,i,i,i,o)
add([],_,_,_,[]).
add([_|T],E,P,C,[HR|TR]) :-
P =:= C,
HR is E,
C is C+1,
P is P*2,
add(T,E,P,C,TR).
add([H|T],E,P,C,[H|TR]) :-
P =\= C,
C is C+1,
add(T,E,P,C,TR).
Here's another possibility to define such a predicate. Whenever you are describing lists it is worthwhile to consider using DCGs since they yield easily readable code. First let's observe that there's only need for three arguments, namely the list, the element to be inserted and the list with the element already inserted at the desired positions. The arguments P and C are only needed for bookkeeping purposes so it's opportune to hide them inside the predicate. And since we're already about to redesign the predicates interface let's also give it a more descriptive name that reflects its relational nature, say list_e_inserted/3:
list_e_inserted(L,E,I) :-
phrase(inserted(L,E,1,1),I). % the DCG inserted//4 describes the list I
inserted([],_E,_P,_C) --> % if the list L is empty
[]. % the list I is empty as well
inserted([H|T],E,P,P) --> % if P and C are equal
{P1 is P*2, C1 is P+1}, % P is doubled and C is increased
[H,E], % H is in the list I, followed by E
inserted(T,E,P1,C1). % the same holds for T,E,P1,C1
inserted([H|T],E,P,C) --> % if P and C are
{dif(P,C), C1 is C+1}, % different C is increased
[H], % H is in the list I
inserted(T,E,P,C1). % the same holds for T,E,P,C1
Now let's see the predicate at work:
?- list_e_inserted([],10,I).
I = [].
?- list_e_inserted([1],10,I).
I = [1, 10] ;
false.
?- list_e_inserted([1,2],10,I).
I = [1, 10, 2, 10] ;
false.
?- list_e_inserted([1,2,3],10,I).
I = [1, 10, 2, 10, 3] ;
false.
?- list_e_inserted([1,2,3,4],10,I).
I = [1, 10, 2, 10, 3, 4, 10] ;
false.
The predicate also works in the other direction:
?- list_e_inserted(L,E,[1,10,2,10,3,4,10,5]).
L = [1, 2, 3, 4, 5],
E = 10 ;
false.
And the most general query also yields the desired solutions:
?- list_e_inserted(L,E,I).
L = I, I = [] ;
L = [_G23],
I = [_G23, E] ;
L = [_G23, _G35],
I = [_G23, E, _G35, E] ;
L = [_G23, _G35, _G47],
I = [_G23, E, _G35, E, _G47] ;
L = [_G23, _G35, _G47, _G53],
I = [_G23, E, _G35, E, _G47, _G53, E] ;
.
.
.
The main problem is that when a variable in Prolog gets instantiated you can't change the value e.g increase the value so you need to use a new variable:
add([],_,_,_,[]).
add([H|T],E,P,C,[H,E|TR]) :-
P =:= C,
C1 is C+1,
P1 is P*2,
add(T,E,P1,C1,TR).
add([H|T],E,P,C,[H|TR]) :-
P =\= C,
C1 is C+1,
add(T,E,P,C1,TR).
Example:
?- add([1,2,3,4],10,1,1,L).
L = [1, 10, 2, 10, 3, 4, 10] ;
false.

Improving list generation over a range in Prolog

I'm fairly new to Prolog, and falling in love with it more and more. I'm wondering if this implementation can be further generalized or improved upon, and whether it is idiomatic Prolog code?
%% range/2
range(End, List) :-
End > 0, !,
range_ascend(0, End, 1, List).
range(End, List) :-
End < 0,
range_descend(0, End, 1, List).
%% range/3
range(Start, End, List) :-
((Start =< End) ->
(range_ascend(Start, End, 1, List))
;
(range_descend(Start, End, 1, List))).
%% range/4 (+Start, +End, +Step, -List)
range(Start, End, Step, List) :-
((Start =< End) ->
(range_ascend(Start, End, Step, List))
;
(range_descend(Start, End, Step, List))).
range_descend(Start, End, _, []) :-
End >= Start, !.
range_descend(Start, End, Step, [Start|Rest]) :-
Next is Start - Step,
range_descend(Next, End, Step, Rest).
range_ascend(Start, End, _, []) :-
Start >= End, !.
range_ascend(Start, End, Step, [Start|Rest]) :-
Next is Start + Step,
range_ascend(Next, End, Step, Rest).
One of the main problems of your implementation is that it only works "one way", that is that your code works well when End is set to a certain value, but does not work when it is a variable:
?- range(X,[0,1,2,3]).
ERROR: >/2: Arguments are not sufficiently instantiated
Maybe you do not need such behavior to work but in Prolog it is usually both desirable and elegant that your predicate acts as a true relation, that works in multiple different ways.
However, implementing predicates as such is often more difficult than implementing them to work in a functional way, especially if you're a beginner to Prolog.
I am not going to go into details as to how to improve your code specifically (I think this is more of a question for the Code Review SE site). I am however presenting below a range predicate with better behavior than yours:
range(I, S, [I|R]) :-
I #=< S,
if_(I = S,
R = [],
( J #= I + 1,
range(J, S, R)
)
).
This predicate requires if_/3 and (=)/3 from library(reif), as well as library(clpfd) (which you can include in your program with :- use_module(library(clpfd)).).
As you can see it is much shorter than your implementation, but also works well in multiple different scenarios:
?- range(0,5,L). % Same behavior as your predicate
L = [0, 1, 2, 3, 4, 5].
?- range(-5,0,L). % Different behavior from your predicate, but logically sounder
L = [-5, -4, -3, -2, -1, 0]
?- range(1,S,[1,2,3,4,5]). % Finding the max of the range
S = 5 ;
false.
?- range(I,S,[1,2,3,4,5]). % Finding both the min and max of the range
I = 1,
S = 5 ;
false.
?- range(I,S,[1,2,X,Y,5]). % With variables in the range
I = 1,
S = 5,
X = 3,
Y = 4 ;
false.
?- range(1,S,L). % Generating ranges
S = 1,
L = [1] ;
S = 2,
L = [1, 2] ;
S = 3,
L = [1, 2, 3] ;
S = 4,
L = [1, 2, 3, 4] ;
…
?- range(I,1,L). % Generating ranges
I = 1,
L = [1] ;
I = 0,
L = [0, 1] ;
I = -1,
L = [-1, 0, 1] ;
I = -2,
L = [-2, -1, 0, 1] ;
…
?- range(I,S,L). % Generating all possible ranges
I = S,
L = [S],
S in inf..sup ;
L = [I, S],
I+1#=S,
S#>=I,
dif(I, S) ;
L = [I, _G6396, S],
I+1#=_G6396,
S#>=I,
dif(I, S),
_G6396+1#=S,
S#>=_G6396,
dif(_G6396, S) ;
…
I think you can see how many behaviors are displayed here, and how useful it can be to have access to all of them with only one predicate.
This predicate uses Constraint Logic Programming (the clpfd library). CLP allows to write relations between integers (which are the #=< and #= that you see in the code, as opposed to the classic =< and is that you use in low-level arithmetic). This is what does most of the heavy-lifting for us and allows to write short, declarative code about integers (which you cannot do easily with is).
I recommend you to read The Power of Prolog's arithmetic chapter by Markus Triska to learn about CLP arithmetic in Prolog, which is definitely a subject you need to learn if you intend to use Prolog seriously (as I hope I have illustrated in this answer).

Create list of pair of values 0 to n-1 in lexicographical order

I'm doing a program with Result is a pair of values [X,Y] between 0 and N-1 in lexicographic order
I have this right now:
pairs(N,R) :-
pairsHelp(N,R,0,0).
pairsHelp(N,[],N,N) :- !.
pairsHelp(N,[],N,0) :- !.
pairsHelp(N,[[X,Y]|List],X,Y) :-
Y is N-1,
X < N,
X1 is X + 1,
pairsHelp(N,List,X1,0).
pairsHelp(N,[[X,Y]|List],X,Y) :-
Y < N,
Y1 is Y + 1,
pairsHelp(N,List,X,Y1).
I'm getting what I want the first iteration but Prolog keeps going and then gives me a second answer.
?-pairs(2,R).
R = [[0,0],[0,1],[1,0],[1,1]] ;
false.
I don't want the second answer (false), just the first. I want it to stop after it finds the answer. Any ideas?
Keep in mind that there is a much easier way to get what you are after. If indeed both X and Y are supposed to be integers, use between/3 to enumerate integers ("lexicographical" here is the same as the order of natural numbers: 0, 1, 2, .... This is the order in which between/3 will enumerate possible solutions if the third argument is a variable):
pairs(N, R) :-
succ(N0, N),
bagof(P, pair(N0, P), R).
pair(N0, X-Y) :-
between(0, N0, X),
between(0, N0, Y).
And then:
?- pairs(2, R).
R = [0-0, 0-1, 1-0, 1-1].
?- pairs(3, R).
R = [0-0, 0-1, 0-2, 1-0, 1-1, 1-2, 2-0, 2-1, ... - ...].
I am using the conventional Prolog way of representing a pair, X-Y (in canonical form: -(X, Y)) instead of [X,Y] (canonical form: .(X, .(Y, []))).
The good thing about this program is that you can easily re-write it to work with another "alphabet" of your choosing.
?- between(0, Upper, X).
is semantically equivalent to:
x(0).
x(1).
% ...
x(Upper).
?- x(X).
For example, if we had an alphabet that consists of b, a, and c (in that order!):
foo(b).
foo(a).
foo(c).
foo_pairs(Ps) :-
bagof(X-Y, ( foo(X), foo(Y) ), Ps).
and then:
?- foo_pairs(R).
R = [b-b, b-a, b-c, a-b, a-a, a-c, c-b, c-a, ... - ...].
The order of the clauses of foo/1 defines the order of your alphabet. The conjunction foo(X), foo(Y) together with the order of X-Y in the pair defines the order of pairs in the list. Try writing for example bagof(X-Y, ( foo(Y), foo(X) ), Ps) to see what will be the order of pairs in Ps.
Use dcg in combination with lambda!
?- use_module(library(lambda)).
In combination with meta-predicate init0/3 and
xproduct//2 ("cross product") simply write:
?- init0(=,3,Xs), phrase(xproduct(\X^Y^phrase([X-Y]),Xs),Pss).
Xs = [0,1,2], Pss = [0-0,0-1,0-2,1-0,1-1,1-2,2-0,2-1,2-2].
How about something a little more general? What about other values of N?
?- init0(=,N,Xs), phrase(xproduct(\X^Y^phrase([X-Y]),Xs),Pss).
N = 0, Xs = [], Pss = []
; N = 1, Xs = [0], Pss = [0-0]
; N = 2, Xs = [0,1], Pss = [0-0,0-1,
1-0,1-1]
; N = 3, Xs = [0,1,2], Pss = [0-0,0-1,0-2,
1-0,1-1,1-2,
2-0,2-1,2-2]
; N = 4, Xs = [0,1,2,3], Pss = [0-0,0-1,0-2,0-3,
1-0,1-1,1-2,1-3,
2-0,2-1,2-2,2-3,
3-0,3-1,3-2,3-3]
; N = 5, Xs = [0,1,2,3,4], Pss = [0-0,0-1,0-2,0-3,0-4,
1-0,1-1,1-2,1-3,1-4,
2-0,2-1,2-2,2-3,2-4,
3-0,3-1,3-2,3-3,3-4,
4-0,4-1,4-2,4-3,4-4]
...
Does it work for other terms, too? What about order? Consider a case #Boris used in his answer:
?- phrase(xproduct(\X^Y^phrase([X-Y]),[b,a,c]),Pss).
Pss = [b-b,b-a,b-c,a-b,a-a,a-c,c-b,c-a,c-c]. % succeeds deterministically

How can I delete every occurrence of a sublist from a list in prolog?

This is the code for deleting or removing an element from a given list:
remove_elem(X,[],[]).
remove_elem(X,L1,L2) :-
L1 = [H|T],
X == H,
remove_elem(X,T,Temp),
L2 = Temp.
remove_elem(X,L1,L2) :-
L1 = [H|T],
X \== H,
remove_elem(X,T,Temp),
L2 = [H|Temp].
How can I modify it, so that I can delete every occurrence of a sub list from a list?
When I tried to put a list in an element, it only deletes the element and only once.
It should be this:
?- remove([1,2],[1,2,3,4,1,2,5,6,1,2,1],L).
L = [3,4,5,6,1]. % expected result
Inspired by #CapelliC's implementation I wrote the following code based on
and_t/3:
append_t([] ,Ys,Ys, true).
append_t([X|Xs],Ys,Zs,Truth) :-
append_aux_t(Zs,Ys,Xs,X,Truth).
append_aux_t([] ,_ ,_ ,_,false). % aux pred for using 1st argument indexing
append_aux_t([Z|Zs],Ys,Xs,X,Truth) :-
and_t(X=Z, append_t(Xs,Ys,Zs), Truth).
One append_t/4 goal can replace two prefix_of_t/3 and append/3 goals.
Because of that, the implementation of list_sublist_removed/3 gets a bit simpler than before:
list_sublist_removed([] ,[_|_] ,[]).
list_sublist_removed([X|Xs],[L|Ls],Zs) :-
if_(append_t([L|Ls],Xs0,[X|Xs]),
(Zs = Zs0 , Xs1 = Xs0),
(Zs = [X|Zs0], Xs1 = Xs)),
list_sublist_removed(Xs1,[L|Ls],Zs0).
Still deterministic?
?- list_sublist_removed([1,2,3,4,1,2,5,6,1,2,1],[1,2],L).
L = [3,4,5,6,1].
Yes! What about the following?
?- list_sublist_removed([1,2,3,4,1,2,5,6,1,2,1],X,[3,4,5,6,1]).
X = [1,2] ; % succeeds with useless choice-point
false.
Nope. So there is still room for potential improvement...
This logically pure implementation is based on the predicates if_/3 and (=)/3.
First, we build a reified version of prefix_of/2:
prefix_of_t([],_,true).
prefix_of_t([X|Xs],Zs,T) :-
prefix_of_t__aux(Zs,X,Xs,T).
prefix_of_t__aux([],_,_,false).
prefix_of_t__aux([Z|Zs],X,Xs,T) :-
if_(X=Z, prefix_of_t(Xs,Zs,T), T=false).
Then, on to the main predicate list_sublist_removed/3:
list_sublist_removed([],[_|_],[]).
list_sublist_removed([X|Xs],[L|Ls],Zs) :-
if_(prefix_of_t([L|Ls],[X|Xs]), % test
(Zs = Zs0, append([L|Ls],Xs0,[X|Xs])), % case 1
(Zs = [X|Zs0], Xs0 = Xs)), % case 2
list_sublist_removed(Xs0,[L|Ls],Zs0).
A few operational notes on the recursive clause of list_sublist_removed/3:
First (test), we check if [L|Ls] is a prefix of [X|Xs].
If it is present (case 1), we strip it off [X|Xs] yielding Xs0 and add nothing to Zs.
If it is absent (case 2), we strip X off [X|Xs] and add X to Zs.
We recurse on the rest of [X|Xs] until no more items are left to process.
Onwards to some queries!
The use case you gave in your question:
?- list_sublist_removed([1,2,3,4,1,2,5,6,1,2,1],[1,2],L).
L = [3,4,5,6,1]. % succeeds deterministically
Two queries that try to find the sublist that was removed:
?- list_sublist_removed([1,2,3,4,1,2,5,6,1,2,1],Sub,[ 3,4,5,6,1]).
Sub = [1,2] ? ;
no
?- list_sublist_removed([1,2,3,4,1,2,5,6,1,2,1],Sub,[1,3,4,5,6,1]).
no
Next, let's find a suitable Ls in this query:
?- list_sublist_removed(Ls,[1,2],[3,4,5,6,1]).
% a lot of time passes ... and nothing happens!
Non-termination! This is unfortunate, but within expectations, as the solution set is infinite. However, by a-priori constraining the length of Ls, we can get all expected results:
?- length(Ls,_), list_sublist_removed(Ls,[1,2],[3,4,5,6,1]).
Ls = [ 3,4,5,6,1] ?
; Ls = [1,2, 3,4,5,6,1] ?
; Ls = [3, 1,2, 4,5,6,1] ?
; Ls = [3,4, 1,2, 5,6,1] ?
; Ls = [3,4,5, 1,2, 6,1] ?
; Ls = [3,4,5,6, 1,2, 1] ?
; Ls = [3,4,5,6,1, 1,2 ] ?
; Ls = [1,2, 1,2, 3,4,5,6,1] ? ...
<rant>
So many years I study Prolog, still it deserves some surprises... your problem it's quite simple to solve, when you know the list library, and you have a specific mode (like the one you posted as example). But can also be also quite complex to generalize, and it's unclear to me if the approach proposed by #repeat, based on #false suggestion (if_/3 and friends) can be 'ported' to plain, old Prolog (a-la Clocksin-Mellish, just to say).
</rant>
A solution, that has been not so easy to find, based on old-school Prolog
list_sublist_removed(L, S, R) :-
append([A, S, B], L),
S \= [],
list_sublist_removed(B, S, T),
append(A, T, R),
!
; L = R.
some test:
?- list_sublist_removed([1,2,3,4,1,2,5,6,1,2,1],[1,2],L).
L = [3, 4, 5, 6, 1].
?- list_sublist_removed([1,2,3,4,1,2,5,6,1,2,1],X,[3, 4, 5, 6, 1]).
X = [1, 2].
?- length(X,_), list_sublist_removed(X,[1,2],[3, 4, 5, 6, 1]).
X = [3, 4, 5, 6, 1] ;
X = [3, 4, 5, 6, 1, 2, 1] ...