
Hi! I'm trying to write a list permutation function, and there is in fact a nice explanation of how to do it here: http://sneakymustard.com/2008/12/23/shuffling-in-haskell But for the start I wanted to keep things simple and avoid monad transformers (since I'm not into this yet). Instead, I'd like to write a function of type:
permute :: [a] -> IO [a]
and so this is what I did:
permute xs = do let n = length xs - 1 arr0 <- newListArray (0, n) xs arr <- foldM swap arr0 [n..1] getElems arr where swap arr n = do x <- readArray arr n r <- randomRIO (0, n) y <- readArray arr r writeArray arr n y writeArray arr r x return arr
Unfortunately, what I get is:
permute :: (MArray a1 a IO) => [a] -> IO [a]
and so when I try to apply this function:
permute [1,2,3]
this is what I get: <interactive>:1:0: No instance for (MArray a1 t IO) arising from a use of `permute' at <interactive>:1:0-14 Possible fix: add an instance declaration for (MArray a1 t IO) In the expression: permute [1, 2, 3] In the definition of `it': it = permute [1, 2, 3] How can I fix this? Thanx, jan

On 12 Feb 2009, at 10:20, Jan Snajder wrote:
Hi!
I'm trying to write a list permutation function, and there is in fact a nice explanation of how to do it here: http://sneakymustard.com/2008/12/23/shuffling-in-haskell
But for the start I wanted to keep things simple and avoid monad transformers (since I'm not into this yet). Instead, I'd like to write a function of type:
permute :: [a] -> IO [a]
o.O Why not keep things simple and just write a pure function? permute :: [a] -> [[a]] permute xs = [s:ps | (s,ss) <- select xs, ps <- permute ss] select :: [a] -> [(a,[a])] select [] = [] select (x:xs) = (x,xs) : [(s,x:ss) | (s,ss) <- select xs] Bob

Hi,
Why not keep things simple and just write a pure function?
permute :: [a] -> [[a]] permute xs = [s:ps | (s,ss) <- select xs, ps <- permute ss]
select :: [a] -> [(a,[a])] select [] = [] select (x:xs) = (x,xs) : [(s,x:ss) | (s,ss) <- select xs]
When I run this in ghci I always get an empty list: [patrickl@fc9i386 haskell]$ ghci permute.hs GHCi, version 6.8.2: http://www.haskell.org/ghc/ :? for help Loading package base ... linking ... done. [1 of 1] Compiling Main ( permute.hs, interpreted ) Ok, modules loaded: Main. *Main> permute [1,2,3] [] Am i missing something? Patrick
Bob _______________________________________________ Beginners mailing list Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners
-- ===================== Patrick LeBoutillier Rosemère, Québec, Canada

Patrick LeBoutillier wrote:
permute :: [a] -> [[a]] permute xs = [s:ps | (s,ss) <- select xs, ps <- permute ss]
select :: [a] -> [(a,[a])] select [] = [] select (x:xs) = (x,xs) : [(s,x:ss) | (s,ss) <- select xs]
When I run this in ghci I always get an empty list:
[patrickl@fc9i386 haskell]$ ghci permute.hs GHCi, version 6.8.2: http://www.haskell.org/ghc/ :? for help Loading package base ... linking ... done. [1 of 1] Compiling Main ( permute.hs, interpreted ) Ok, modules loaded: Main. *Main> permute [1,2,3] []
Am i missing something?
No. The base case permute [] = [[]] was missing. Regards, apfelmus -- http://apfelmus.nfshost.com

On Thu, Feb 12, 2009 at 1:20 AM, Jan Snajder
Hi!
I'm trying to write a list permutation function, and there is in fact a nice explanation of how to do it here: http://sneakymustard.com/2008/12/23/shuffling-in-haskell
But for the start I wanted to keep things simple and avoid monad transformers (since I'm not into this yet). Instead, I'd like to write a function of type:
permute :: [a] -> IO [a]
and so this is what I did:
permute xs = do let n = length xs - 1 arr0 <- newListArray (0, n) xs arr <- foldM swap arr0 [n..1] getElems arr where swap arr n = do x <- readArray arr n r <- randomRIO (0, n) y <- readArray arr r writeArray arr n y writeArray arr r x return arr
Unfortunately, what I get is:
permute :: (MArray a1 a IO) => [a] -> IO [a]
and so when I try to apply this function:
permute [1,2,3]
this is what I get:
<interactive>:1:0: No instance for (MArray a1 t IO) arising from a use of `permute' at <interactive>:1:0-14 Possible fix: add an instance declaration for (MArray a1 t IO) In the expression: permute [1, 2, 3] In the definition of `it': it = permute [1, 2, 3]
How can I fix this?
Thanx, jan
_______________________________________________ Beginners mailing list Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners
The simplest way to do this is to use base v4, which I believe contains a "permutations" function in Data.List. Alex

On Thu, Feb 12, 2009 at 10:20:32AM +0100, Jan Snajder wrote:
this is what I get:
<interactive>:1:0: No instance for (MArray a1 t IO) arising from a use of `permute' at <interactive>:1:0-14 Possible fix: add an instance declaration for (MArray a1 t IO) In the expression: permute [1, 2, 3] In the definition of `it': it = permute [1, 2, 3]
How can I fix this?
<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> Jan, this is tricky. The type of permute is indeed (MArray a1 a IO) => [a] -> IO [a], but this is fine, it just means that there has to be some sort of mutable array which can store the things you are trying to shuffle. This is not the problem. The problem seems to be that Haskell has no way to know what sort of array you want to use. I was able to get the code to work, but it's sort of sneaky:
{-# LANGUAGE FlexibleContexts, ScopedTypeVariables #-}
import Data.Array.MArray import Data.Array.IO import Control.Monad import System.Random
permute :: forall a. (MArray IOArray a IO) => [a] -> IO [a] permute xs = do let n = length xs - 1 arr0 <- (newListArray (0, n) xs :: IO (IOArray Int a)) arr <- foldM swap arr0 [n..1] getElems arr where swap arr n = do x <- readArray arr n r <- randomRIO (0, n) y <- readArray arr r writeArray arr n y writeArray arr r x return arr
We have to give an explicit type annotation on the newListArray, to tell Haskell what kind of array we want to use. But then we also need to use the ScopedTypeVariables extension, so that the 'a' in the type signature for permute scopes over the definition, so that Haskell knows we want the 'a' in the IOArray Int a to be the same type as the 'a' in the type signature. Otherwise it doesn't know they are the same and complains. Also, when I try running permute, it seems to be the identity function, but I guess that's a separate issue! -Brent

<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?

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). -Brent

Hrmm, I suppose you're right. I was thinking that we could magically write
permute so that it wound up with n! thunks in an array, and then grab the
nth element in constant time. I guess that's not very correct. And by "not
very" I mean "not even close to".
On Thu, Feb 12, 2009 at 1:33 PM, Brent Yorgey
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).
-Brent _______________________________________________ Beginners mailing list Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners

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

On Thu, Feb 12, 2009 at 08:19:46PM +0100, Thomas Davie wrote:
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.
Indexing into a list is still O(n) in the index, whether you actually compute the elements or not. That is, if you're actually building a list of permutations, then even if you don't compute anything about the permutations you don't need, just traversing through the spine of the list to get the one you want will take a very long time---O(n!)---for reasonably large n. However, you can actually write a pure function with type Int -> [a] -> [a] which just computes which permutation "would be" at the given index, without ever actually constructing a list of them. I'll leave this as an interesting exercise (hint: convert the input number to "base factorial"...), although I still think it's not going to be quite as fast as the imperative version (at least O(n lg n)). -Brent

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)

Daniel Fischer wrote:
Thomas Davie wrote:
Brent Yorgey wrote:
Andrew Wagner wrote:
Brent Yorgey 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.
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".
That of course begs the question whether there is a faster but purely functional algorithm for generating random permutations without indexes and arrays? The answer is a resounding "yes" and the main idea is that shuffling a list is *essentially the same* as sorting a list; the minor difference being that the former chooses a permutation at random while the latter chooses a very particular permutation, namely the one that sorts the input. For the full exposition, see http://apfelmus.nfshost.com/random-permutations.html Regards, apfelmus -- http://apfelmus.nfshost.com

Am Samstag, 14. Februar 2009 16:37 schrieb Heinrich Apfelmus:
That of course begs the question whether there is a faster but purely
No, it didn't beg any question. (Sorry for being a humourless pedant here)
functional algorithm for generating random permutations without indexes and arrays?
The answer is a resounding "yes" and the main idea is that shuffling a list is *essentially the same* as sorting a list; the minor difference being that the former chooses a permutation at random while the latter chooses a very particular permutation, namely the one that sorts the input.
For the full exposition, see
Excellent work, thanks.
Regards, apfelmus
Cheers, Daniel

On Sat, 14 Feb 2009, Daniel Fischer wrote:
Am Samstag, 14. Februar 2009 16:37 schrieb Heinrich Apfelmus:
For the full exposition, see
Excellent work, thanks.
Interesting read. Btw. a further development of the PFP library is also on Hackage: http://hackage.haskell.org/cgi-bin/hackage-scripts/package/probability

Heinrich Apfelmus
The answer is a resounding "yes" and the main idea is that shuffling a list is *essentially the same* as sorting a list; the minor difference being that the former chooses a permutation at random while the latter chooses a very particular permutation, namely the one that sorts the input.
For the full exposition, see
I haven't been following the thread, but my initial reaction would have been something like use System.Random.randoms to get a list rs and then do (roughly) randomPerm = map snd . sortBy (compare `on` fst) . zip rs How bad is that? I mean, how unfair does it get? -- Jón Fairbairn Jon.Fairbairn@cl.cam.ac.uk http://www.chaos.org.uk/~jf/Stuff-I-dont-want.html (updated 2009-01-31)

Am Donnerstag, 12. Februar 2009 17:53 schrieb Brent Yorgey:
On Thu, Feb 12, 2009 at 10:20:32AM +0100, Jan Snajder wrote:
this is what I get:
<interactive>:1:0: No instance for (MArray a1 t IO) arising from a use of `permute' at <interactive>:1:0-14 Possible fix: add an instance declaration for (MArray a1 t IO) In the expression: permute [1, 2, 3] In the definition of `it': it = permute [1, 2, 3]
How can I fix this?
<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>
Jan, this is tricky. The type of permute is indeed (MArray a1 a IO) => [a] -> IO [a], but this is fine, it just means that there has to be some sort of mutable array which can store the things you are trying to shuffle. This is not the problem. The problem seems to be that Haskell has no way to know what sort of array you want to use. I was
able to get the code to work, but it's sort of sneaky:
{-# LANGUAGE FlexibleContexts, ScopedTypeVariables #-}
import Data.Array.MArray import Data.Array.IO import Control.Monad import System.Random
permute :: forall a. (MArray IOArray a IO) => [a] -> IO [a] permute xs = do let n = length xs - 1 arr0 <- (newListArray (0, n) xs :: IO (IOArray Int a)) arr <- foldM swap arr0 [n..1] getElems arr where swap arr n = do x <- readArray arr n r <- randomRIO (0, n) y <- readArray arr r writeArray arr n y writeArray arr r x return arr
We have to give an explicit type annotation on the newListArray, to tell Haskell what kind of array we want to use. But then we also need to use the ScopedTypeVariables extension, so that the 'a' in the type signature for permute scopes over the definition, so that Haskell knows we want the 'a' in the IOArray Int a to be the same type as the 'a' in the type signature. Otherwise it doesn't know they are the same and complains.
Also, when I try running permute, it seems to be the identity function, but I guess that's a separate issue!
That's because [n .. 1] is almost always an empty list. That code changes only lists of length 2. Make it foldM swap arr0 [n, n-1 .. 1] and it works. *Main> permute [1 .. 5] [3,2,1,5,4]
-Brent
participants (10)
-
Alexander Dunlap
-
Andrew Wagner
-
Brent Yorgey
-
Daniel Fischer
-
Heinrich Apfelmus
-
Henning Thielemann
-
Jan Snajder
-
Jon Fairbairn
-
Patrick LeBoutillier
-
Thomas Davie