[Haskell-beginners] permuting a list

Daniel Fischer daniel.is.fischer at web.de
Thu Feb 12 14:46:22 EST 2009


Am Donnerstag, 12. Februar 2009 20:19 schrieb Thomas Davie:
> On 12 Feb 2009, at 19:33, Brent Yorgey wrote:
> > On Thu, Feb 12, 2009 at 11:58:21AM -0500, Andrew Wagner wrote:
> >>> <rant>
> >>> It seems everyone has just been reading the first few words of Jan's
> >>> email and not the actual content.  Jan is clearly trying to write a
> >>> *random list shuffling* function, not a function to generate
> >>> permutations.  Let's try to be helpful, people...
> >>> </rant>
> >>
> >> Agreed, I've been quite confused by this thread. In the spirit of
> >> laziness,
> >> though, wouldn't it seem like the "right" method is to generate all
> >> the
> >> permutations lazily, and then choose a random element of that list?
> >
> > Well, it sounds nice, but it's pretty inefficient.  And by "pretty
> > inefficient" I mean "horrendously, terribly inefficient" -- there are
> > n! permutations of a list of length n, so this would take time O(n!)
> > as opposed to O(n); O(n!) is even worse than O(2^n).
>
> Would it?  We're talking about lazyness here... it's not gonna compute
> one it doesn't need, and if you're somewhat cleverer with your permute
> function than I was, I'm sure you can do as little computation as the
> imperative version.
>
> Bob

But to find the k-th permutation, it would have to traverse k cons cells 
containing thunks, wouldn't it?

Well, the following is O(n^2), not quite O(n), but at least it's not 
"horrendously, terribly inefficient".

module Permutations where

import Data.List (sortBy, genericSplitAt, genericLength)
import Data.Ord (comparing)

factorialDigits :: Integer -> [Integer]
factorialDigits k = go k 2
      where
        go 0 _ = []
        go m d = case m `divMod` d of
                    (q,r) -> r:go q (d+1)

permIndices :: Integer -> [Integer]
permIndices k = go [0] 1 fds
      where
        fds = factorialDigits k
        go acc d [] = acc ++ [d .. ]
        go acc d (p:ps) =
            case genericSplitAt (d-p) acc of
                (front,back) -> go (front ++ d:back) (d+1) ps

kthPerm :: Integer -> [a] -> [a]
kthPerm k = map snd . sortBy (comparing fst) . zip (permIndices k)




More information about the Beginners mailing list