
Am Freitag, 13. Februar 2009 10:23 schrieb Jan Snajder:
Brent Yorgey wrote:
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>
Thanks Brant, I forgot to mention explicitly that I need a random permutation.
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 #-}
I guess by 'sneaky' you mean this solution is GHC-specific?
It can be made a little less sneaky, you don't need FlexibleContexts, because the type signature permute :: forall a. [a] -> IO [a] works, too (code otherwise unchanged). But that still doesn't work with hugs :( However, if you bring the array-creation to top level, it doesn't need any module-specific language extensions: module Perms where import Data.Array.MArray import Data.Array.IO import Control.Monad import System.Random -- call with toArray (length xs - 1) xs toArray :: Int -> [a] -> IO (IOArray Int a) toArray n xs = newListArray (0,n) xs permute :: [a] -> IO [a] permute xs = do let n = length xs - 1 arr0 <- toArray n xs arr <- foldM swap arr0 [n, n-1 .. 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 and it works in hugs, too (needs the -98 flag, because one of the imports needs ST.hs, which has foralled type signatures). Cheers, Daniel