Data.List permutations

Krasimir Angelov kr.angelov at gmail.com
Tue Aug 4 13:53:53 EDT 2009


Your function is not equivalent:

perm _|_ = _|_

permutations _|_ = _|_ : _|_


On 8/4/09, Slavomir Kaslev <slavomir.kaslev at gmail.com> wrote:
> 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)
>
> I would like to suggest to change the current implementation in Data.List with
> the simpler one. Also, it would be nice to add variations and combinations in
> the Data.List module.
>
> Cheers.
>
> --
> Slavomir Kaslev
> _______________________________________________
> Glasgow-haskell-users mailing list
> Glasgow-haskell-users at haskell.org
> http://www.haskell.org/mailman/listinfo/glasgow-haskell-users
>


More information about the Glasgow-haskell-users mailing list