[Haskell-cafe] Funny type signature question

Michael Snoyman michael at snoyman.com
Thu Apr 2 14:03:14 EDT 2009


I've butted into this problem multiple times, so I thought it's finally time
to get a good solution. I don't even have the terminology to describe the
issue, so I'll just post the code I'm annoyed with and hope someone
understands what I mean.

import Control.Monad.Random
import System.Random

data Marital = Single | Married | Divorced
    deriving (Enum, Bounded, Show)

randomEnum :: (Enum a, Bounded a, RandomGen g) => Rand g a
randomEnum = do
    let minb = minBound
        maxb = maxBound
    randVal <- getRandomR (fromEnum minb, fromEnum maxb)
    return $ head [toEnum randVal, minb, maxb] -- if I do the obvious thing
(return $ toEnum randVal) I get funny errors

main = do
    stdGen <- newStdGen
    let marital = evalRand randomEnum stdGen :: Marital
    putStrLn $ "Random marital status: " ++ show marital

Any help is appreciated. Thanks!
Michael
-------------- next part --------------
An HTML attachment was scrubbed...
URL: http://www.haskell.org/pipermail/haskell-cafe/attachments/20090402/7960bb43/attachment.htm


More information about the Haskell-Cafe mailing list