
Of course, but something like take k . (!! m) will cut it down nicely.
On Sun, Apr 3, 2016 at 12:39 AM, Arseniy Alekseyev
Um, the result is exponential in size. A problem will emerge in any solution. :)
On 3 April 2016 at 05:38, David Feuer
wrote: Your lists are very short. Pump them up to thousands of elements each and you will see a problem emerge in the naive solution.
On Sun, Apr 3, 2016 at 12:16 AM, Arseniy Alekseyev
wrote: I measure the following naive solution of interleave2 beating yours in performance:
i2 [] ys = [ys] i2 xs [] = [xs] i2 (x : xs) (y : ys) = fmap (x :) (i2 xs (y : ys)) ++ fmap (y :) (i2 (x : xs) ys)
The program I'm benchmarking is:
main = print $ sum $ map sum $ interleavings [[1,2,3,4],[5,6,7,8],[9,10,11,12],[1,1,1]]
On 3 April 2016 at 04:05, David Feuer
wrote: I ran into a fun question today: http://stackoverflow.com/q/36342967/1477667
Specifically, it asks how to find all ways to interleave lists so that the order of elements within each list is preserved. The most efficient way I found is copied below. It's nicely lazy, and avoids left-nested appends. Unfortunately, it's pretty seriously ugly. Does anyone have any idea of a way to do this that's both efficient and elegant?
{-# LANGUAGE BangPatterns #-} import Data.Monoid import Data.Foldable (toList) import Data.Sequence (Seq, (|>))
-- Find all ways to interleave two lists interleave2 :: [a] -> [a] -> [[a]] interleave2 xs ys = interleave2' mempty xs ys []
-- Find all ways to interleave two lists, adding the -- given prefix to each result and continuing with -- a given list to append interleave2' :: Seq a -> [a] -> [a] -> [[a]] -> [[a]] interleave2' !prefix xs ys rest = (toList prefix ++ xs ++ ys) : interleave2'' prefix xs ys rest
-- Find all ways to interleave two lists except for -- the trivial case of just appending them. Glom -- the results onto the given list. interleave2'' :: Seq a -> [a] -> [a] -> [[a]] -> [[a]] interleave2'' !prefix [] _ = id interleave2'' !prefix _ [] = id interleave2'' !prefix xs@(x : xs') ys@(y : ys') = interleave2' (prefix |> y) xs ys' . interleave2'' (prefix |> x) xs' ys
-- What the question poser wanted; I don't *think* there's -- anything terribly interesting to do here. interleavings :: [[a]] -> [[a]] interleavings = foldr (concatMap . interleave2) [[]]
Thanks, David _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe