[Haskell-cafe] Generating random enums
Thomas Hartman
tphyahoo at gmail.com
Fri May 1 14:08:26 EDT 2009
So... I must say I am rather pleased with the following code.
It allows you to use any value of type Bounded and Enum as a member of
Random, or Arbitrary, which means you can quickCheck properties on it
as well.
For quickchecking, the code below "cheats" by not defining the
coarbitrary funciton, which I confess I don't really understand and
never use.
Even so, I can see myself using this in a number of places... Does it
seem reasonable to add a ticket to get this added to
http://hackage.haskell.org/packages/archive/QuickCheck/2.1.0.1/doc/html/Test-QuickCheck-Arbitrary.html
perhaps modulo the definition of an appropriate coarbitrary function?
thomas.
thartman at patchwiki:~/haskell-learning/testing>cat BoundedEnum.hs
{-# LANGUAGE FlexibleInstances, UndecidableInstances,
ScopedTypeVariables, OverlappingInstances #-}
module Main where
import Test.QuickCheck
import System.Random
class (Bounded a, Enum a) => BoundedEnum a
instance (Bounded a, Enum a) => BoundedEnum a
instance BoundedEnum a => Random a
where random g =
let min = fromEnum (minBound :: a)
max = fromEnum (maxBound :: a)
(i,g') = randomR (min,max) $ g
in (toEnum i,g')
randomR (low,high) g =
let min = fromEnum low
max = fromEnum high
(i,g') = randomR (min,max) $ g
in (toEnum i,g')
instance BoundedEnum a => Arbitrary a
where arbitrary = do
let min = fromEnum (minBound :: a)
max = fromEnum (maxBound :: a)
i <- arbitrary
return . toEnum $ min + (i `mod` (max-min))
coarbitrary = undefined
data DayOfWeek
= Monday
| Tuesday
| Wednesday
| Thursday
| Friday
| Saturday
| Sunday
deriving (Show, Read, Eq, Enum, Ord, Bounded)
t :: IO DayOfWeek
t = randomIO
t2 :: IO Int
t2 = randomIO
pDayEqualsItself :: DayOfWeek -> Bool
pDayEqualsItself day = day == day -- a trivial property, just so we can show
t3 = quickCheck pDayEqualsItself
-- show what days are being tested
t4 = verboseCheck pDayEqualsItself
2009/5/1 michael rice <nowgate at yahoo.com>:
> I'm using the code below to generate random days of the week
> [Monday..Sunday].
>
> Is there a better/shorter way to do this?
>
> Michael
>
> ==============
>
> [michael at localhost ~]$ ghci dow
> GHCi, version 6.10.1: http://www.haskell.org/ghc/ :? for help
> Loading package ghc-prim ... linking ... done.
> Loading package integer ... linking ... done.
> Loading package base ... linking ... done.
> [1 of 1] Compiling Main ( dow.hs, interpreted )
> Ok, modules loaded: Main.
> *Main> random (mkStdGen 100) :: (DayOfWeek, StdGen)
> Loading package old-locale-1.0.0.1 ... linking ... done.
> Loading package old-time-1.0.0.1 ... linking ... done.
> Loading package random-1.0.0.1 ... linking ... done.
> (Friday,4041414 40692)
> *Main> random (mkStdGen 123) :: (DayOfWeek, StdGen)
> (Tuesday,4961736 40692)
> *Main>
>
> ==============
>
> import System.Random
>
> data DayOfWeek
> = Monday
> | Tuesday
> | Wednesday
> | Thursday
> | Friday
> | Saturday
> | Sunday
> deriving (Show, Read, Eq, Enum, Ord, Bounded)
>
> instance Random DayOfWeek where
> randomR (a,b) g =
> case (randomIvalInteger (toInteger (dow2Int a), toInteger (dow2Int b))
> g) of
> (x, g) -> (int2Dow x, g)
> where
> dow2Int Monday = 0
> dow2Int Tuesday = 1
> dow2Int Wednesday = 2
> dow2Int Thursday = 3
> dow2Int Friday = 4
> dow2Int Saturday = 5
> dow2Int Sunday = 6
>
> int2Dow 0 = Monday
> int2Dow 1 = Tuesday
> int2Dow 2 = Wednesday
> int2Dow 3 = Thursday
> int2Dow 4 = Friday
> int2Dow 5 = Saturday
> int2Dow 6 = Sunday
>
> random g = randomR (minBound,maxBound) g
>
> randomIvalInteger :: (RandomGen g, Num a) => (Integer, Integer) -> g -> (a,
> g)
> randomIvalInteger (l,h) rng
> | l > h = randomIvalInteger (h,l) rng
> | otherwise = case (f n 1 rng) of (v, rng') -> (fromInteger (l + v `mod`
> k), rng')
> where
> k = h - l + 1
> b = 2147483561
> n = iLogBase b k
>
> f 0 acc g = (acc, g)
> f n acc g =
> let
> (x,g') = next g
> in
> f (n-1) (fromIntegral x + acc * b) g'
>
> iLogBase :: Integer -> Integer -> Integer
> iLogBase b i = if i < b then 1 else 1 + iLogBase b (i `div` b)
>
>
>
>
>
>
>
> _______________________________________________
> Haskell-Cafe mailing list
> Haskell-Cafe at haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>
>
More information about the Haskell-Cafe
mailing list