Add 'subsequences' and 'permutations' to Data.List (ticket #1990)

Twan van Laarhoven twanvl at gmail.com
Thu Dec 20 23:28:37 EST 2007


Yitzchak Gale wrote:
> Twan, I think you are working a little too hard to satisfy
> the consistency property. You only need to satisfy it for
> permutations where the first n elements of the permutation
> are the same as the first n elements of the original list.
> Other than that, you can just use the faster function that you
> defined earlier.
> 
> Here is a quick effort that beats permutations5 by using your
> previous permutations3:
> 
> permutations7 xs = xs : (concat $ zipWith newPerms (init $ tail $ tails xs)
>                                                    (init $ tail $ inits xs))
>   where
>     newPerms (t:ts) = map (++ts) . concatMap (interleave t) . permutations3
>     interleave t [y]        = [[t, y]]
>     interleave t ys@(y:ys') = (t:ys) : map (y:) (interleave t ys')

That looks quite nice. Unfortunatly your function is too strict with the 
normal inits and tails. After replacing those with these lazier versions 
(which should be in Data.List) it works much better.

    inits' xxs = [] : case xxs of
                        []     -> []
                        (x:xs) -> map (x:) (inits' xs)

    tails' xxs = xxs : case xxs of
                        []     -> []
                        (_:xs) -> tails' xs

There is also a problem with "permutations7 []". The problem is 'tail', it 
is not needed. Replacing the first two lines with:

   permutations7' xs = xs : (concat $ init $ zipWith newPerms
                                             (tails' xs) (inits' xs))

solves that problem, and it is also shorter.

It is also possible to get rid of inits and tails entirely:

  permutations8 xs = xs : newPerms xs []
    where
     newPerms []     is =  []
     newPerms (t:ts) is =  concatMap interleave (permutations8 is)
                        ++ newPerms ts (t:is)
       where interleave []     = []
             interleave (y:ys) = (t:y:ys++ts) : map (y:) (interleave ys)

A foldr version is of course also possible

   permutations8b xs = xs : newPerms xs []
     where
      newPerms []     is = []
      newPerms (t:ts) is = foldr (interleave id) (newPerms ts (t:is))
                                 (permutations8b is)
       where interleave f []         r = r
             interleave f yys@(y:ys) r = f (t:yys++ts)
                                        : interleave (f . (y:)) ys r

Some run times:

  permutations7':                        4.750 sec
  permutations7', using 3 for recursion: 4.250 sec
  permutations8:                         3.984 sec
  permutations8b:                        2.250 sec
  permutations8b, using 3 for recursion: 1.984 sec

My current preference is 8 or 8b, using a different function in the 
recursion is going to far for my taste.

Twan


More information about the Libraries mailing list