<p dir="ltr">I choose the `force (map head)` attack.</p>
<div class="gmail_quote">On Apr 3, 2016 1:04 AM, "Arseniy Alekseyev" <<a href="mailto:arseniy.alekseyev@gmail.com">arseniy.alekseyev@gmail.com</a>> wrote:<br type="attribution"><blockquote class="gmail_quote" style="margin:0 0 0 .8ex;border-left:1px #ccc solid;padding-left:1ex"><div dir="ltr">I see! At this point I'd say that you probably have the wrong type: there are ways to produce n'th interleaving much faster, but let's continue optimizing for the hell of it!<br><div><br><span style="font-family:monospace,monospace">i2 :: ([a] -> [b]) -> [a] -> [a] -> [[b]] -> [[b]]<br>i2 f [] ys = (f ys :)<br>i2 f xs [] = (f xs :)<br>i2 f (x : xs) (y : ys) =<br>  i2 (f . (x :)) xs (y : ys) . i2 (f . (y :)) (x : xs) ys<br><br>interleave2 xs ys = i2 id xs ys []</span><br><br></div><div>Seems faster than your original solution on examples I tried it on and it has fewer characters. :)<br></div></div><div class="gmail_extra"><br><div class="gmail_quote">On 3 April 2016 at 05:41, David Feuer <span dir="ltr"><<a href="mailto:david.feuer@gmail.com" target="_blank">david.feuer@gmail.com</a>></span> wrote:<br><blockquote class="gmail_quote" style="margin:0 0 0 .8ex;border-left:1px #ccc solid;padding-left:1ex">Of course, but something like take k . (!! m)   will cut it down nicely.<br>
<br>
On Sun, Apr 3, 2016 at 12:39 AM, Arseniy Alekseyev<br>
<div><div><<a href="mailto:arseniy.alekseyev@gmail.com" target="_blank">arseniy.alekseyev@gmail.com</a>> wrote:<br>
> Um, the result is exponential in size. A problem will emerge in any<br>
> solution. :)<br>
><br>
> On 3 April 2016 at 05:38, David Feuer <<a href="mailto:david.feuer@gmail.com" target="_blank">david.feuer@gmail.com</a>> wrote:<br>
>><br>
>> Your lists are very short. Pump them up to thousands of elements each<br>
>> and you will see a problem emerge in the naive solution.<br>
>><br>
>> On Sun, Apr 3, 2016 at 12:16 AM, Arseniy Alekseyev<br>
>> <<a href="mailto:arseniy.alekseyev@gmail.com" target="_blank">arseniy.alekseyev@gmail.com</a>> wrote:<br>
>> > I measure the following naive solution of interleave2 beating yours in<br>
>> > performance:<br>
>> ><br>
>> > i2 [] ys = [ys]<br>
>> > i2 xs [] = [xs]<br>
>> > i2 (x : xs) (y : ys) =<br>
>> >   fmap (x :) (i2 xs (y : ys)) ++ fmap (y :) (i2 (x : xs) ys)<br>
>> ><br>
>> > The program I'm benchmarking is:<br>
>> ><br>
>> > main = print $ sum $ map sum $ interleavings<br>
>> > [[1,2,3,4],[5,6,7,8],[9,10,11,12],[1,1,1]]<br>
>> ><br>
>> ><br>
>> ><br>
>> > On 3 April 2016 at 04:05, David Feuer <<a href="mailto:david.feuer@gmail.com" target="_blank">david.feuer@gmail.com</a>> wrote:<br>
>> >><br>
>> >> I ran into a fun question today:<br>
>> >> <a href="http://stackoverflow.com/q/36342967/1477667" rel="noreferrer" target="_blank">http://stackoverflow.com/q/36342967/1477667</a><br>
>> >><br>
>> >> Specifically, it asks how to find all ways to interleave lists so that<br>
>> >> the order of elements within each list is preserved. The most<br>
>> >> efficient way I found is copied below. It's nicely lazy, and avoids<br>
>> >> left-nested appends. Unfortunately, it's pretty seriously ugly. Does<br>
>> >> anyone have any idea of a way to do this that's both efficient and<br>
>> >> elegant?<br>
>> >><br>
>> >> {-# LANGUAGE BangPatterns #-}<br>
>> >> import Data.Monoid<br>
>> >> import Data.Foldable (toList)<br>
>> >> import Data.Sequence (Seq, (|>))<br>
>> >><br>
>> >> -- Find all ways to interleave two lists<br>
>> >> interleave2 :: [a] -> [a] -> [[a]]<br>
>> >> interleave2 xs ys = interleave2' mempty xs ys []<br>
>> >><br>
>> >> -- Find all ways to interleave two lists, adding the<br>
>> >> -- given prefix to each result and continuing with<br>
>> >> -- a given list to append<br>
>> >> interleave2' :: Seq a -> [a] -> [a] -> [[a]] -> [[a]]<br>
>> >> interleave2' !prefix xs ys rest =<br>
>> >>   (toList prefix ++ xs ++ ys)<br>
>> >>      : interleave2'' prefix xs ys rest<br>
>> >><br>
>> >> -- Find all ways to interleave two lists except for<br>
>> >> -- the trivial case of just appending them. Glom<br>
>> >> -- the results onto the given list.<br>
>> >> interleave2'' :: Seq a -> [a] -> [a] -> [[a]] -> [[a]]<br>
>> >> interleave2'' !prefix [] _ = id<br>
>> >> interleave2'' !prefix _ [] = id<br>
>> >> interleave2'' !prefix xs@(x : xs') ys@(y : ys') =<br>
>> >>   interleave2' (prefix |> y) xs ys' .<br>
>> >>       interleave2'' (prefix |> x) xs' ys<br>
>> >><br>
>> >> -- What the question poser wanted; I don't *think* there's<br>
>> >> -- anything terribly interesting to do here.<br>
>> >> interleavings :: [[a]] -> [[a]]<br>
>> >> interleavings = foldr (concatMap . interleave2) [[]]<br>
>> >><br>
>> >><br>
>> >> Thanks,<br>
>> >> David<br>
>> >> _______________________________________________<br>
>> >> Haskell-Cafe mailing list<br>
>> >> <a href="mailto:Haskell-Cafe@haskell.org" target="_blank">Haskell-Cafe@haskell.org</a><br>
>> >> <a href="http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe" rel="noreferrer" target="_blank">http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe</a><br>
>> ><br>
>> ><br>
><br>
><br>
</div></div></blockquote></div><br></div>
</blockquote></div>