[Haskell-cafe] Generating random enums

Ross Mellgren rmm-haskell at z.odi.ac
Fri Oct 16 15:40:42 EDT 2009


I didn't try to compile this:

import Control.Arrow (first)
import System.Random (Random(..))

instance Random Dir where
     randomR (lo, hi) gen = first fromEnum (randomR (toEnum lo)  
(toEnum hi) gen)
     random gen = randomR (minBound, maxBound)

But something along those lines should help you I think.


-Ross

On Oct 16, 2009, at 3:36 PM, michael rice wrote:

> What is the minimum I need to do to get this function to generate a  
> three direction tuple?
>
> Michael
>
>
> =====================
>
> import System.Random
> import Data.Ord
>
> data Dir
>     = North
>     | South
>     | East
>     | West
>     deriving (Show, Read, Eq, Enum, Ord, Bounded)
>
> threeDirs :: StdGen -> (Dir,Dir,Dir)
> threeDirs gen =
>   let (firstDir, newGen) = random gen
>       (secondDir, newGen') = random newGen
>       (thirdDir, newGen'') = random newGen'
>   in (firstDir, secondDir, thirdDir)
>
>
>
> =====================
>
> GHCi, version 6.10.3: http://www.haskell.org/ghc/  :? for help
> Loading package ghc-prim ... linking ... done.
> Loading package integer ... linking ... done.
> Loading package base ... linking ... done.
> Prelude> :l dir.hs
> [1 of 1] Compiling Main             ( dir.hs, interpreted )
>
> dir.hs:15:29:
>     No instance for (Random Dir)
>       arising from a use of `random' at dir.hs:15:29-42
>     Possible fix: add an instance declaration for (Random Dir)
>     In the expression: random newGen'
>     In a pattern binding: (thirdDir, newGen'') = random newGen'
>     In the expression:
>         let
>           (firstDir, newGen) = random gen
>           (secondDir, newGen') = random newGen
>           (thirdDir, newGen'') = random newGen'
>         in (firstDir, secondDir, thirdDir)
> Failed, modules loaded: none.
> Prelude>
>
>
>
> _______________________________________________
> Haskell-Cafe mailing list
> Haskell-Cafe at haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe

-------------- next part --------------
An HTML attachment was scrubbed...
URL: http://www.haskell.org/pipermail/haskell-cafe/attachments/20091016/618c41b9/attachment.html


More information about the Haskell-Cafe mailing list