
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@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)

When you derive Enum, you get fromEnum and toEnum for free. You don't need
your dow2Int stuff or int2Dow. Replace those with fromEnum and toEnum
respectively.
/jve
On Fri, May 1, 2009 at 12:26 PM, michael rice
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@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@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
-- /jve

see
http://www.mail-archive.com/haskell-cafe@haskell.org/msg38528.html
for some ideas, particularly antoine latter's answer.
2009/5/1 michael rice
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@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@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

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...
perhaps modulo the definition of an appropriate coarbitrary function?
thomas.
thartman@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
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@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@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

On Fri, May 01, 2009 at 01:08:26PM -0500, Thomas Hartman wrote:
For quickchecking, the code below "cheats" by not defining the coarbitrary funciton, which I confess I don't really understand and never use.
FWIW, QuickCheck 2 separates 'coarbitrary' in a different class. -- Felipe.

On Fri, May 1, 2009 at 11:08 AM, Thomas Hartman
For quickchecking, the code below "cheats" by not defining the coarbitrary funciton, which I confess I don't really understand and never use.
coarbitrary is simple; it's used for generating arbitrary functions. If you don't know how to define it for your type, "coarbitrary _ = id" is a reasonable definition. But it's usually easy to define, and I'll show you how! But first, the motivation for its existence. You have an instance of arbitrary "X", and an instance of arbitrary "Y", and some transformations:
transformX :: X -> X transformY :: Y -> Y
prop_natural_transform :: (X -> Y) -> X -> Bool prop_natural_transform f x = f (transformX x) == transformY (f x)
This says, for all f, (f . transformX) = (transformY . f). A real example of a property similar to this is for "map" and "reverse":
prop_map_reverse :: Eq b => (a -> b) -> [a] -> Bool prop_map_reverse f xs = map f (reverse xs) == reverse (map f xs)
Now, how can QuickCheck generate functions to pass to these properties? The function f is *pure*; it can't use a random generator to determine what Y to output. What QuickCheck *can* do, however, is "split" the random generator at the point where it needs to create "f", then uses "coarbitrary" to adjust the state of the generator based on the argument passed in:
mkArbFunction :: forall a b. (Arbitrary a, Arbitrary b) => Gen (a -> b) mkArbFunction = sized $ \size -> do randomSource <- rand let f :: a -> b f x = generate size randomSource (coarbitrary x arbitrary) return f
Inside of "f", we have a single generator that is fixed; without coarbitrary, we would only be able to generate a single object of type "b", the one that is a result of running "arbitrary" with that fixed generator. But with coarbitrary, the argument can affect the response! The simplest thing to do is to extract some random values from the generator before using it to generate the result:
-- only works for non-negative values twist :: Int -> Gen a -> Gen a twist 0 g = g twist n g = do () <- elements [(), ()] -- just make the random generator do some work coarbitrary (n-1) g
It's really easy to implement coarbitrary for many types in terms of "twist":
data Color = Red | Green | Blue instance Arbitrary Color where arbitrary = elements [Red, Green, Blue] coarbitrary Red = twist 0 coarbitrary Green = twist 1 coarbitrary Blue = twist 2
instance Arbitrary a => Arbitrary (Maybe a) where arbitrary = oneOf [return Nothing, liftM Just arbitrary] coarbitrary Nothing = twist 0 coarbitrary (Just x) = twist 1 . coarbitrary x
A better version of "twist" is in Test.QuickCheck with the name "variant". In fact, for Bounded/Enum types like your code uses, it's easy to define coarbitrary from variant:
coarbEnum :: (Bounded a, Enum a) => a -> Gen b -> Gen b coarbEnum a = variant (fromEnum a - fromEnum (minBound `asTypeOf` a))
-- ryan
participants (5)
-
Felipe Lessa
-
John Van Enk
-
michael rice
-
Ryan Ingram
-
Thomas Hartman