Data.List permutations

Slavomir Kaslev slavomir.kaslev at gmail.com
Tue Aug 4 14:30:58 EDT 2009


On Tue, Aug 4, 2009 at 9:23 PM, Daniel Fischer<daniel.is.fischer at web.de> wrote:
> Am Dienstag 04 August 2009 19:48:25 schrieb Slavomir Kaslev:
>> A friend mine, new to functional programming, was entertaining himself by
>> writing different combinatorial algorithms in Haskell. He asked me for some
>> help so I sent him my quick and dirty solutions for generating variations
>> and
>>
>> permutations:
>> > inter x [] = [[x]]
>> > inter x yys@(y:ys) = [x:yys] ++ map (y:) (inter x ys)
>> >
>> > perm [] = [[]]
>> > perm (x:xs) = concatMap (inter x) (perm xs)
>> >
>> > vari 0 _ = [[]]
>> > vari _ [] = []
>> > vari k (x:xs) = concatMap (inter x) (vari (k-1) xs) ++ vari k xs
>>
>> After that I found out that nowadays there is a permutation function in the
>>
>> Data.List module:
>> > permutations            :: [a] -> [[a]]
>> > permutations xs0        =  xs0 : perms xs0 []
>> >   where
>> >     perms []     _  = []
>> >     perms (t:ts) is = foldr interleave (perms ts (t:is)) (permutations
>> > is) where interleave    xs     r = let (_,zs) = interleave' id xs r in zs
>> > interleave' _ []     r = (ts, r)
>> >             interleave' f (y:ys) r = let (us,zs) = interleave' (f . (y:))
>> > ys r in  (y:us, f (t:y:us) : zs)
>>
>> I was surprised to find that not only my version is much simpler from the
>> one in Data.List but it also performs better. Here are some numbers from my
>> rather old ghc 6.8.1 running ubuntu on my box:
>>
>> *Main> length $ permutations [1..10]
>> 3628800
>> (10.80 secs, 2391647384 bytes)
>> *Main> length $ perm [1..10]
>> 3628800
>> (8.58 secs, 3156902672 bytes)
>
> But you compare *interpreted* code here, that's not what counts.
>
> Prelude Perms> length $ perm [1 .. 10]
> 3628800
> (1.20 secs, 1259105892 bytes)
> Prelude Perms> length $ permutations [1 .. 10]
> 3628800
> (0.56 secs, 551532668 bytes)
> Prelude Perms> length $ perm [1 .. 11]
> 39916800
> (13.18 secs, 14651808004 bytes)
> Prelude Perms> length $ permutations [1 .. 11]
> 39916800
> (4.30 secs, 5953485728 bytes)

Which version of ghc are you testing on? I guess, it's more recent than mine.

> Apparently the library code is more amenable to the optimiser (note that the actual
> library is faster still:
>
> Prelude Data.List> length $ permutations [1 .. 10]
> 3628800
> (0.49 secs, 551532812 bytes)
> Prelude Data.List> length $ permutations [1 .. 11]
> 39916800
> (3.73 secs, 5953485816 bytes)
>
> I have no idea why).

Probably because it's compiled (and not interpreted) in this case.

-- 
Slavomir Kaslev


More information about the Glasgow-haskell-users mailing list