Find all possible pairs - list

Im working on some erlang code and want to create a recursive function for extracting all possible pairs from a list. The list could have zero elements, but it could have up to 70 elements. Writing cases for all of these occurrences is bad practice and I would like your help.
pair(List) ->
case List of
[] -> [];
[A] -> [{A}];
[A, B] -> [{A, B}, {B, A}];
[A, B, C] -> [{A, B}, {A, C}, {B, A}, {B, C}, {C, A}, {C, B}];
end.
I found a function written to create a list of all possible combinations (not only all pairs), but I don't understand how to change it.
combos(1, L) -> [[X] || X <-L];
combos(K, L) when K == length(L) -> [L];
combos(K, [H|T]) ->
[[H | Subcombos] || Subcombos <- combos(K-1, T)]
++(combos(K, T)).
combos(L) ->
lists:foldl(
fun(K, Acc) -> Acc++(combos(K, L)) end,
[[]], lists:seq(1, length(L))).

You can use a list comprehension and reference the same list twice as an input:
1> L = [a,b,c,d].
[a,b,c,d]
2> [{X, Y} || X <- L, Y <- L].
[{a,a},
{a,b},
{a,c},
{a,d},
{b,a},
{b,b},
{b,c},
{b,d},
{c,a},
{c,b},
{c,c},
{c,d},
{d,a},
{d,b},
{d,c},
{d,d}]
I'd be surprised if there was any clearer or more efficient way to do this.
EDIT
In the event you don't want identical pairs ({a,a} and so on) you can add a guard to ensure inequality:
5> [{X, Y} || X <- L1, Y <- L1, X /= Y].
[{a,b},
{a,c},
{a,d},
{b,a},
{b,c},
{b,d},
{c,a},
{c,b},
{c,d},
{d,a},
{d,b},
{d,c}]

Related

Reverse list of tuples of nodes and edges (Haskell)

I have a list of nodes and edges, represented as tuples where the first element is a node, and the second element is a list of all nodes it has an edge to. I am trying to reverse the list like so:
ghci> snuN [("a",["b"]),("b",["c"]),("c",["a","d"]),("e",["d"])]
ghci> [("a",["c"]),("b",["a"]),("c",["b"]),("d",["c","e"]),("e",[])]
So far, I've written this code:
snuH :: Eq t => [(t,[t])] -> [(t,[t])]
snuH [] = []
snuH ps#((x, xs):rest) =
if (length xs <= 1) && not (x `isInSublist` ps)
then [(y,[x])| y <- xs] ++ snuH rest ++ [(x, [])]
else [(y,[x])| y <- xs] ++ snuH rest
isInSublist :: Eq t => t -> [(t,[t])] -> Bool
isInSublist _ [] = False
isInSublist x ((y, ys):rest) = (x `elem` ys) || isInSublist x rest
combine :: Eq t => [(t,[t])] -> [(t,[t])]
combine ps#((x, xs):(y, ys):rest) = if x == y then (x, xs++ys):rest else (x, xs):combine((y, ys):rest)
snuN :: Eq t => [(t, [t])] -> [(t, [t])]
snuN ls = combine $ snuH ls
The first function gives me this output:
ghci> snuH [("a",["b"]),("b",["c"]),("c",["a","d"]),("e",["d"])]
ghci> [("b",["a"]),("c",["b"]),("a",["c"]),("d",["c"]),("d",["e"]),("e",[]),("b",[])]
Which is not quite the result I wanted, because it creates two tuples with the same first element (("d",["c"]),("d",["e"])), and it has the extra ("b",[]) as an element when it shouldn't. I wrote the combine helper-function to fix the problem, which gives me this output:
ghci> snuN [("a",["b"]),("b",["c"]),("c",["a","d"]),("e",["d"])]
ghci> [("b",["a"]),("c",["b"]),("a",["c"]),("d",["c","e"]),("e",[]),("b",[])]
Which fixes the problem with the two tuples with the same first element, but I still have the extra ("b",[]) which I can't figure out how to fix, I assume there's something wrong with my snuH but I can't see where the problem is.
Can you tell me what im doing wrong here? I don't understan why I get the extra ("b",[]). All help is appreciated!
I'd argue that the following list comprehension gives you what you need:
type Graph node = [(node, [node])]
converse :: Eq node => Graph node -> Graph node
converse g = [(v, [e | (e, es) <- g, v `elem` es]) | (v, _) <- g]
However, if you try it out, you'll get:
> converse [("a",["b"]),("b",["c"]),("c",["a","d"]),("e",["d"])]
[("a",["c"]),("b",["a"]),("c",["b"]),("e",[])]
Compared to the example you gave, the entry for "d" is missing from the output. That's because the input did not mention an explicit entry ("d", []).
To compensate for this, we could put a bit more logic in retrieving the complete list of nodes from the graph, also accounting for the "implied" ones:
nodes :: Eq node => Graph node -> [node]
nodes g = nub $ concat [v : es | (v, es) <- g]
Note: this requires importing nub from Data.List.
Then, we can write:
converse' :: Eq node => Graph node -> Graph node
converse' g = [(v, [e | (e, es) <- g, v `elem` es]) | v <- nodes g]
And, indeed, we yield:
> converse' [("a",["b"]),("b",["c"]),("c",["a","d"]),("e",["d"])]
[("a",["c"]),("b",["a"]),("c",["b"]),("d",["c","e"]),("e",[])]
You have [(a, [a])], which maps nodes to the nodes they have an edge to. One approach to "reversing" this is to first convert it to a list of all the edges. We can actually generalize the type a bit here, to distinguish from and to nodes.
allEdges :: [(a, [b])] -> [(a, b)]
allEdges g = [(a, b) | (a, bs) <- g, b <- bs]
Now it's just a matter of gathering up the nodes with an edge to each particular node:
import Data.Map.Strict (Map)
import qualified Data.Map.Strict as M
gather :: Ord b => [(a,b)] -> Map b [a]
gather edges = M.fromListWith (++) [(b, [a]) | (a, b) <- edges]
Now we can just use M.assocs to convert that map to a list!
The above code will leave out nodes that have no edges going to them. We can patch that up with a bit of extra work.
reverseGraph :: Ord a => [(a, [a])] -> [(a, [a])]
reverseGraph = M.assocs . M.fromListWith (++) . gunk
where
gunk g = [q | (a, bs) <- g, q <- (a, []) : [(b, [a]) | b <- bs]]
The idea here is that when we see (a, bs), we insert the empty edge set (a, []) along with the nonempty ones (b, [a] for each b in bs.

How split list of tuples to tuple of lists?

I'm asked to split list of tuples to tuple that has 2 list, in the following way:
splitter ([{1,2},{3,4},{5,6}]). = {[1,3,5],[2,4,6]}
I've tried to write the following code:
splitter([]) -> {[],[]};
splitter(L) ->(map (fun ({A, _}) -> A end, L))|(map (fun ({_, B}) -> B end, L)).
And it does not compile, the error I am getting is: syntax error before: '|'
where is the problem?:
You are missing the outer curly braces. Also, replace the | by , as that's what's used to separate tuple members.
splitter([]) -> {[],[]};
splitter(L) -> {(map (fun ({A, _}) -> A end, L)),
(map (fun ({_, B}) -> B end, L))
}.
Empty list clause is unnecessary. You can use list comprehensions as well.
splitter(L) -> {[ X || {X, _} <- L], [X || {_, X} <- L]}.
You can make universal one as well
splitter_n(L) ->
list_to_tuple(transpose([tuple_to_list(X) || X <- L])).
transpose([]) -> [];
transpose([[]|_]) -> [];
transpose(L) ->
[[hd(X) || X <- L] | transpose([tl(X) || X <- L])].
In work
1> c(splitter).
{ok,splitter}
2> splitter:splitter_n([{1,2},{3,4},{5,6}]).
{[1,3,5],[2,4,6]}
3> splitter:splitter_n([{1,2,3},{4,5,6},{7,8,9}]).
{[1,4,7],[2,5,8],[3,6,9]}

How can I sum the middle elements of an expanding list in Haskell?

So far I know how to expand a list from its ends, but they end up getting doubled because of the first condition, which is to double a singleton. Would it make sense for the code to be like this:
sumExpand :: [Integer] -> [Integer]
sumExpand l = expand l []
where
expand [] a = a
expand (x:[]) a = x: expand [] (x:a)
expand (x:xs) a = expand (x:a) (expand xs a)
And for me to work on its output:
[1,1,2,2,3,3] from [1,2,3]
instead of [1,3,5,3]
The latter being my desire? Here's how I got to a temporary solution for a list of two elements:
expand (x:xs) a = x: tail (expand (map (x+) xs) (last xs:a))
Output:
*Main> sumExpand [1,2]
[1,3,2]
*Main> sumExpand [1,2,3]
[1,7,4,3]
EDIT: basically, I want the algorithm to work like this: [a, b, c] => [a, a+b, b+c, c]
Basically, all you want to compute component-wise sums between your input list and a shifted version of it:
a b c d e
a b c d e
---------------------------
a a+b b+c c+d d+e e
Fill each empty slot with a 0 (0:x and x++[0]), and you just need zipWith
> (\x -> zipWith (+) (0:x) (x++[0])) [1,2,3]
[1,3,5,3]

All combinations of a list without doubles in Prolog

Is there a simple way of getting all the combinations of a list without doubles. Without doubles I mean also no permutations of each other. So no [a,b,c] and [c,a,b] or [c,b,a].
So for the input [a,b,c] the output would be:
[a]
[b]
[c]
[a,b]
[a,c]
[b,c]
[a,b,c]
I can only find solutions WITH the doubles (permutations)
The solution to this problem is rather simple: there is evidently only one combination out of the empty set: the empty set:
combs([],[]).
Furthermore for each element, you can decide whether you add it or not:
combs([H|T],[H|T2]) :-
combs(T,T2).
combs([_|T],T2) :-
combs(T,T2).
Since you pick (or drop) in the order of the list, this guarantees you that you later will not redecide to pick a. If you feed it [a,b,c], it will never generate something like [b,a,c], because once it has decided to pick/drop a, it cannot add b and re-decide on a.
Running this gives:
?- combs([a,b,c],L).
L = [a, b, c] ;
L = [a, b] ;
L = [a, c] ;
L = [a] ;
L = [b, c] ;
L = [b] ;
L = [c] ;
L = [].
In case you want to generate it the opposite way (have more of a test to first drop elements, instead of adding them, you can simply swap the recursive statements):
combs([],[]).
combs([_|T],T2) :-
combs(T,T2).
combs([H|T],[H|T2]) :-
combs(T,T2).
In that case the result will be:
?- combs([a,b,c],L).
L = [] ;
L = [c] ;
L = [b] ;
L = [b, c] ;
L = [a] ;
L = [a, c] ;
L = [a, b] ;
L = [a, b, c].
EDIT
Given you want to exclude the empty list, either you can do it simply by adding another check in your call:
?- combs([a,b,c],L),L \= [].
You can define this in a function like:
combs_without_empty1(LA,LB) :-
combs_without_empty1(LA,LB),
LB \= [].
Or by rewriting the comb/2 function. In that case you better use an accumulator that counts the current amount of selected elements:
combs_without_empty(L,C) :-
combs_without_empty(L,0,C).
The combs_without_empty/3 is a bit more complicated. In case the list contains only one element, one should check if N is greater than zero. If that is the case, we can choose whether to add the element or not. If N is zero, we have to include it. So:
combs_without_empty([A],_,[A]).
combs_without_empty([_],N,[]) :-
N > 0.
We also have to implement a recursive part that will increment N given we select an element:
combs_without_empty([_|T],N,T2) :-
combs_without_empty(T,N,T2).
combs_without_empty([H|T],N,[H|T2]) :-
N1 is N+1,
combs_without_empty(T,N1,T2).
Putting it all together gives:
combs_without_empty(L,C) :-
combs_without_empty(L,0,C).
combs_without_empty([A],_,[A]).
combs_without_empty([_],N,[]) :-
N > 0.
combs_without_empty([_|T],N,T2) :-
combs_without_empty(T,N,T2).
combs_without_empty([H|T],N,[H|T2]) :-
N1 is N+1,
combs_without_empty(T,N1,T2).
Which produces:
?- combs_without_empty([a,b,c],L).
L = [c] ;
L = [b, c] ;
L = [b] ;
L = [a, c] ;
L = [a] ;
L = [a, b, c] ;
L = [a, b] ;
false.
A clean solution without ancillary checks for empty list would be simply to exclude empty lists from the rules. The base case should be a single element combination:
comb_without_empty([H|_], [H]). % Simple case of one element comb
comb_without_empty([_|T], C) :- % Combinations of the tail w/o head
comb_without_empty(T, C).
comb_without_empty([H|T], [H|C]) :- % Combinations of the tail including head
comb_without_empty(T, C).
| ?- comb_without_empty([a,b,c], L).
L = [a] ? a
L = [b]
L = [c]
L = [b,c]
L = [a,b]
L = [a,c]
L = [a,b,c]
(1 ms) no
| ?-

How to predicate all pairs in a given list in Prolog?

When given a list I would like to compute all the possible combinations of pairs in the list.
e.g 2) input is a list (a,b,c) I would like to obtain pairs (a,b) (a,c) (b,c)
e.g 1) input is a list (a,b,c,d) I would like to obtain pairs (a,b) (a,c) (a,d) (b,c) (b,d) and (c,d)
Using select/3 twice (or select/3 once and member/2 once) will allow you to achieve what you want here. I'll let you work out the details and ask for help if it's still troublesome.
BTW, Prolog syntax for list isn't (a, b, c) but [a, b, c] (well, it's syntactic sugar but I'll leave it at that).
edit: as #WillNess pointed out, you're not looking for any pair (X, Y) but only for pairs where X is before Y in the list.
DCGs are a really good fit: as #false described, they can produce a graphically appealing solution:
... --> [] | [_], ... .
pair(L, X-Y) :-
phrase((..., [X], ..., [Y], ...), L).
Alternatively, if you use SWI-Prolog, a call to append/2 does the trick too, in a similar manner, but is less efficient than DCGs:
pair2(L, X-Y) :-
append([_, [X], _, [Y], _], L).
You can do it with a basic recursion, as #WillNess suggested in his comment. I'll leave this part for him to detail if needed!
OK, so to translate the Haskell definition
pairs (x:xs) = [ (x,y) | y <- xs ]
++ pairs xs
pairs [] = []
(which means, pairs in the list with head x and tail xs are all the pairs (x,y) where y is in xs, and also the pairs in xs; and there's no pairs in an empty list)
as a backtracking Prolog predicate, producing the pairs one by one on each redo, it's a straightforward one-to-one re-write of the above,
pair( [X|XS], X-Y) :- member( ... , XS) % fill in
; pair( XS, ... ). % the blanks
%% pair( [], _) :- false.
To get all the possible pairs, use findall:
pairs( L, PS) :- findall( P, pair( L, P), PS).
Consider using bagof if your lists can contain logical variables in them. Controlling bagof's backtracking could be an intricate issue though.
pairs can also be written as a (nearly) deterministic, non-backtracking, recursive definition, constructing its output list through an accumulator parameter as a functional programming language would do -- here in the top-down manner, which is what Prolog so excels in:
pairs( [X|T], PS) :- T = [_|_], pairs( X, T, T, PS, []).
pairs( [_], []).
pairs( [], []).
pairs( _, [], [], Z, Z).
pairs( _, [], [X|T], PS, Z) :- pairs( X, T, T, PS, Z).
pairs( X, [Y|T], R, [X-Y|PS], Z) :- pairs( X, T, R, PS, Z).
Here is a possible way of solving this.
The following predicate combine/3 is true
if the third argument corresponds to a list
contains pairs, where the first element of each pair
is equal to the first argument of combine/3.
The second element of each pair will correspond to an item
of the list in the second argument of the predicate combine/3.
Some examples how combine/3 should work:
?- combine(a,[b],X).
X = [pair(a,b)]
?- combine(a,[b,c,d],X).
X = [pair(a,b), pair(a,c), pair(a,d)]
Possible way of defining combine/3:
combine(A,[B],[pair(A,B)]) :- !.
combine(A,[B|T],C) :-
combine(A,T,C2), % Create pairs for remaining elements in T.
append([pair(A,B)],C2,C). % Append current pair and remaining pairs C2.
% The result of append is C.
Now combine/3 can be used to define pair/2:
pairs([],[]). % Empty list will correspond to empty list of pairs.
pairs([H|T],P) :- % In case there is at least one element.
nonvar([H|T]), % In this case it expected that [H|T] is instantiated.
pairs(H,T,P).
pairs(A,[B],[pair(A,B)]) % If remaining list contains exactly one element,
:- !. % then there will be only one pair(A,B).
pairs(A,[B|T],P) :- % In case there are at least two elements.
combine(A,[B|T],P2), % For each element in [B|T] compute pairs
% where first element of each pair will be A.
pairs(B,T,P3), % Compute all pairs without A recursively.
append(P2,P3,P). % Append results P2 and P3 together.
Sample usage:
?- pairs([a,b,c],X).
X = [pair(a, b), pair(a, c), pair(b, c)].
?- pairs([a,b,c,d],X).
X = [pair(a, b), pair(a, c), pair(a, d), pair(b, c), pair(b, d), pair(c, d)].
You can use append/ to iterate through the list:
?- append(_,[X|R],[a,b,c,d]).
X = a,
R = [b, c, d] ;
X = b,
R = [c, d] ;
X = c,
R = [d] ;
X = d,
R = [] ;
false.
Next, use member/2 to form a pair X-Y, for each Y in R:
?- append(_,[X|R],[a,b,c,d]), member(Y,R), Pair=(X-Y).
X = a,
R = [b, c, d],
Y = b,
Pair = a-b ;
X = a,
R = [b, c, d],
Y = c,
Pair = a-c ;
X = a,
R = [b, c, d],
Y = d,
Pair = a-d ;
X = b,
R = [c, d],
Y = c,
Pair = b-c ;
X = b,
R = [c, d],
Y = d,
Pair = b-d ;
X = c,
R = [d],
Y = d,
Pair = c-d ;
false.
Then, use findall/3 to collect all pairs in a list:
?- findall(X-Y, (append(_,[X|R],[a,b,c,d]), member(Y,R)), Pairs).
Pairs = [a-b, a-c, a-d, b-c, b-d, c-d].
Thus, your final solution can be expressed as:
pairs(List, Pairs) :-
findall(X-Y, (append(_,[X|R],List), member(Y,R)), Pairs).
An example of use is:
?- pairs([a,b,c,d], Pairs).
Pairs = [a-b, a-c, a-d, b-c, b-d, c-d].