[Haskell-beginners] monads and mutants
Amy de Buitléir
amy at nualeargais.ie
Fri Aug 20 20:21:36 EDT 2010
I'm dipping a toe in the shallow end of the monad pool. I would
appreciate any feedback on the first function here, "mutateList". It
seems to be working fine, but I have this feeling that I'm doing some
unnecessary mucking about with state and I don't know how to fix it.
Since both randomListSelection and mutateGene update the state, it
seems unnecessary for mutateList to get and put the state as well.
What do ye think?
I have a list of 16-bit unsigned words.
I want to randomly select an element in the list.
In the selected element, I want to flip a bit at random.
---------- The code ----------
{-# LANGUAGE PackageImports #-}
import "mtl" Control.Monad.State
import System.Random
import Data.Word
import Data.Bits
-- | ***** LOOK HERE *****
-- | Flip a random bit in a random element in the list.
mutateList :: [Word16] -> State StdGen [Word16]
mutateList xs = do
g <- get
let ((i, x), g') = runState (randomListSelection xs) g
let (x', g'') = runState (mutateGene x) g'
put g''
return (replaceElement xs i x')
-- | ***** LOOK HERE *****
-- | Choose an element at random from a list and return the element
and its index
randomListSelection :: [a] -> State StdGen (Int, a)
randomListSelection xs = do
g <- get
let s = length xs
let (i, g') = randomR (0,s-1) g
put g'
return (i, xs !! i)
-- | Randomly flip a bit in this gene.
mutateGene :: Word16 -> State StdGen Word16
mutateGene x = do
g <- get
let (i, g') = randomR (0,16) g
put g'
return (x `complementBit` i)
-- | Replace an element in a list with a new element.
replaceElement
-- | The list
:: [a]
-- | Index of the element to replace.
-> Int
-- | The new element.
-> a
-- | The updated list.
-> [a]
replaceElement xs i x = fore ++ (x : aft)
where fore = take i xs
aft = drop (i+1) xs
More information about the Beginners
mailing list