[Haskell-cafe] how can I select all the 3-element-combination out of a list efficiently

haskell at list.mightyreason.com haskell at list.mightyreason.com
Mon May 21 07:39:53 EDT 2007


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


More information about the Haskell-Cafe mailing list