how can I select all the 3-element-combination out of a list efficiently

hi dear haskell lover ;) what I want to do is simply this: select3 :: [a] -> [(a, a, a)] and how can it be done efficiently? thanks in advance! -- View this message in context: http://www.nabble.com/how-can-I-select-all-the-3-element-combination-out-of-... Sent from the Haskell - Haskell-Cafe mailing list archive at Nabble.com.

geniusfat wrote:
hi dear haskell lover ;) what I want to do is simply this: select3 :: [a] -> [(a, a, a)] and how can it be done efficiently? thanks in advance!
What, as in select3 [1..10] -> [(1,2,3),(2,3,4),(3,4,5),(4,5,6),(5,6,7),(6,7,8),(7,8,9),(8,9,10)] ? How about like this: select3 = map (\[x,y,z] -> (x,y,z)) . filter ((2 <) . length) . take 3 . tails

geniusfat wrote:
hi dear haskell lover ;) what I want to do is simply this: select3 :: [a] -> [(a, a, a)] and how can it be done efficiently? thanks in advance!
If, given [1,2,3,4,5,6,7,8,9,10,11,12] you want [(1,2,3),(4,5,6),(7,8,9)....] then: map (take 3) . iterate (drop 3) is very nearly what you need. Two problems: (a) it gives you [[1,2,3],[4,5,6]..] instead (b) it carries on with an infinite number of [] empty lists you can fix both of these: map (\[a,b,c]->(a,b,c)) . takeWhile (not.null) . map (take 3) . iterate (drop 3) Prelude> map (\[a,b,c] -> (a,b,c)) . takeWhile (not.null) . map (take 3) . iterate (drop 3) $ [1..12] [(1,2,3),(4,5,6),(7,8,9),(10,11,12)] Hope that helps. Jules

geniusfat wrote:
hi dear haskell lover ;) what I want to do is simply this: select3 :: [a] -> [(a, a, a)] and how can it be done efficiently? thanks in advance!
Oh, hang on. I just read your subject line. Do you really mean all the 3-elem combinations? that's much easier: Prelude> let l = [1,5,9,15] in [(a,b,c) | a <- l, b <- l, c <- l] [(1,1,1),(1,1,5),(1,1,9),(1,1,15),(1,5,1),(1,5,5),(1,5,9),(1,5,15),(1,9,1),(1,9,5),(1,9,9),(1,9,15),(1,15,1),(1,15,5),(1,15,9),(1,15,15),(5,1,1),(5,1,5),(5,1,9),(5,1,15),(5,5,1),(5,5,5),(5,5,9),(5,5,15),(5,9,1),(5,9,5),(5,9,9),(5,9,15),(5,15,1),(5,15,5),(5,15,9),(5,15,15),(9,1,1),(9,1,5),(9,1,9),(9,1,15),(9,5,1),(9,5,5),(9,5,9),(9,5,15),(9,9,1),(9,9,5),(9,9,9),(9,9,15),(9,15,1),(9,15,5),(9,15,9),(9,15,15),(15,1,1),(15,1,5),(15,1,9),(15,1,15),(15,5,1),(15,5,5),(15,5,9),(15,5,15),(15,9,1),(15,9,5),(15,9,9),(15,9,15),(15,15,1),(15,15,5),(15,15,9),(15,15,15)] Jules

Oh, hang on. I just read your subject line. Do you really mean all the 3-elem combinations?
Ah, Haskell... So many ways to do the same thing, so many possible meanings to every apparently innocuous statement. ;-)

with which model in Combinatorics in mind do you want that function? with or without repetition? http://en.wikipedia.org/wiki/Combinatorics#Permutation_with_repetition the order matters and each object can be chosen more than once http://en.wikipedia.org/wiki/Combinatorics#Permutation_without_repetition the order matters and each object can be chosen only once http://en.wikipedia.org/wiki/Combinatorics#Combination_without_repetition the order does not matter and each object can be chosen only once http://en.wikipedia.org/wiki/Combinatorics#Combination_with_repetition the order does not matter and each object can be chosen more than once -------------------------------------------------- import Data.List perm3_with_rep,perm3_without_rep,comb3_with_rep,comb3_without_rep :: [a] -> [(a, a, a)] perm3_with_rep es = [(x,y,z)|x<-es,y<-es,z<-es] perm3_without_rep es = [(x,y,z)|let it s=zip s $ zipWith (++) (inits s) (tail $ tails s),(x,xr)<-it es,(y,yr)<-it xr,z<-yr] comb3_with_rep es = [(x,y,z)|let it=init.tails,xs@(x:_)<-it es,ys@(y:_)<-it xs,z<-ys] comb3_without_rep es = [(x,y,z)|let it=init.tails,(x:xr)<-it es,(y:yr)<-it xr,z<-yr] comb3_to_perm3 :: [(a, a, a)] -> [(a, a, a)] comb3_to_perm3 xyz = concat[perm_without_rep [x,y,z]|(x,y,z)<-xyz] -------------------------------------------------- - marc

What I meant is this: http://en.wikipedia.org/wiki/Combinatorics#Combination_without_repetition the order does not matter and each object can be chosen only once. But thank all those who have offered help, it helps a lot ;) -- View this message in context: http://www.nabble.com/how-can-I-select-all-the-3-element-combination-out-of-... Sent from the Haskell - Haskell-Cafe mailing list archive at Nabble.com.

geniusfat wrote:
What I meant is this: http://en.wikipedia.org/wiki/Combinatorics#Combination_without_repetition the order does not matter and each object can be chosen only once. But thank all those who have offered help, it helps a lot ;)
Then you want "triples1" from the code below. The idea for triples1, triples2, and triples3 is that each pickOne returns a list of pairs. The first element of each pair is the chosen element and the second element of each pair is the list of choices for the next element (given the current choice). import Data.List -- Order does not matter, no repetition -- preserves sorting triples1 xs = do (x,ys) <- pickOne xs (y,zs) <- pickOne ys z <- zs return (x,y,z) where pickOne [] = [] pickOne (x:xs) = (x,xs) : pickOne xs -- Alternative -- pickOne xs = map helper . init . tails $ xs -- helper (x:xs) = (x,xs) -- Order does matter, no repetition -- does not preserve sorting triples2 xs = do (x,ys) <- pickOne xs (y,zs) <- pickOne ys z <- zs return (x,y,z) where pickOne xs = helper [] xs helper bs [] = [] helper bs (x:xs) = (x,bs++xs) : helper (x:bs) xs -- Alternative (produces results in different order -- and preserves sorting) -- pickOne xs = zipWith helper (inits xs) (init (tails xs)) -- helper pre (x:post) = (x,pre++post) -- Order does not matter, repetition allowed -- preserves sorting triples3 xs = do (x,ys) <- pickOne xs (y,zs) <- pickOne ys z <- zs return (x,y,z) where pickOne [] = [] pickOne a@(x:xs) = (x,a) : pickOne xs -- Alternative -- pickOne xs = map helper . init . tails $ xs -- helper xs@(x:_) = (x,xs) -- Order does matter, repetition allowed -- preserves sorting triples4 xs = do x <- xs y <- xs z <- xs return (x,y,z) temp = map ($ [1..4]) $ [triples1,triples2,triples3,triples4] preservesSorting = map (\xs -> xs == sort xs) temp test1 = putStr . unlines . map show $ temp test2 = putStr . unlines . map show . map length $ temp

haskell@list.mightyreason.com wrote:
Then you want "triples1" from the code below.
The idea for triples1, triples2, and triples3 is that each pickOne returns a list of pairs. The first element of each pair is the chosen element and the second element of each pair is the list of choices for the next element (given the current choice).
In the spirit of multiple implementations; another approach is to note that you're really asking for all 3-element sublists: power [] = [[]] power (x:xs) = power xs ++ map (x:) (power xs) triples1' l = [ t | t <- power l, length t == 3] (this implementation also preserves sorting) Jules

Jules Bean wrote:
In the spirit of multiple implementations; another approach is to note that you're really asking for all 3-element sublists:
power [] = [[]] power (x:xs) = power xs ++ map (x:) (power xs)
triples1' l = [ t | t <- power l, length t == 3]
(this implementation also preserves sorting)
...but is exponentially slower than necessary, and fails on infinite lists. Try this one: sublistsN 0 _ = [[]] sublistsN n (x:xs) = map (x:) (sublistsN (n-1) xs) ++ sublistsN n xs sublistsN _ _ = [] triples = sublistsN 3 BR, -- -- Mirko Rahn -- Tel +49-721 608 7504 -- --- http://liinwww.ira.uka.de/~rahn/ ---

geniusfat
the order does not matter and each object can be chosen only once. (snip)
In that case, with the help of Data.List.tails, one can do: threeOf :: [a] -> [(a,a,a)] threeOf xs = [ (p,q,r) | (p:ps) <- tails xs, (q:qs) <- tails ps, r <- qs ] (the r <- qs is a simpler version of (r:rs) <- tails qs) or maybe, nOf :: Int -> [a] -> [[a]] nOf _ [] = [] nOf 1 xs = map return xs nOf n (x:xs) = map (x:) (nOf (n-1) xs) ++ nOf n xs (These are fairly naive versions that just took me a few minutes, but perhaps they'll do.) -- Mark

Mark T.B. Carroll wrote:
nOf _ [] = [] nOf 1 xs = map return xs nOf n (x:xs) = map (x:) (nOf (n-1) xs) ++ nOf n xs
No! With this implementation we have nOf 0 _ == [] but it should be nOf 0 _ == [[]]: The list of all sublists of length 0 is not empty, it contains the empty list! Correct (and more natural): nOf 0 _ = [[]] nOf n (x:xs) = map (x:) (nOf (n-1) xs) ++ nOf n xs nOf _ [] = [] BR, -- -- Mirko Rahn -- Tel +49-721 608 7504 -- --- http://liinwww.ira.uka.de/~rahn/ ---

Mirko Rahn
Correct (and more natural):
nOf 0 _ = [[]] nOf n (x:xs) = map (x:) (nOf (n-1) xs) ++ nOf n xs nOf _ [] = []
Thanks very much - in both claims you're indeed correct. -- Mark
participants (7)
-
Andrew Coppin
-
geniusfat
-
haskell@list.mightyreason.com
-
Jules Bean
-
Marc A. Ziegert
-
mark@ixod.org
-
Mirko Rahn