
I need to generate distinct arbitrary values for my quickcheck tests and they don't have to be arbitrary (although that doesn't matter). No problem I thought, I'll create my own random number generator (which will not be random at all) and use
choose :: forall a. (Random a) => (a, a) -> Gen a
Here's my code:
import Test.QuickCheck import System.Random
data MyGen = MyGen Int deriving (Eq, Show)
myNext :: MyGen -> (Int, MyGen) myNext (MyGen s1) = (s1, MyGen (s1 + 1))
-- Assume we will never need this mySplit :: MyGen -> (MyGen, MyGen) mySplit = error "No split for predictable random generator"
myGenRange :: MyGen -> (Int, Int) myGenRange (MyGen s1) = (s1, s1)
instance RandomGen MyGen where next = myNext split = mySplit genRange = myGenRange
data Foo = Foo Int deriving (Eq, Show)
myRandomR :: (Foo, Foo) -> MyGen -> (Foo, MyGen) myRandomR (Foo lo, Foo hi) g = let (n, g') = next g in (Foo n, g')
instance Random Foo where randomR = myRandomR random = undefined
But I get
Supply.hs:33:13: Couldn't match expected type `g' against inferred type `MyGen' `g' is a rigid type variable bound by the type signature for `randomR' at <no location info> Expected type: (Foo, Foo) -> g -> (Foo, g) Inferred type: (Foo, Foo) -> MyGen -> (Foo, MyGen) In the expression: myRandomR In the definition of `randomR': randomR = myRandomR Failed, modules loaded: none.
I have two questions: 1. Why can't I instantiate a type class with any function I like provided it fits the type signature? 2. Is this the right approach to generating predictable arbitrary values? Are there others? Thanks, Dominic.

Hi Dominic,
On Dec 15, 2007 10:38 AM, Dominic Steinitz
Supply.hs:33:13: Couldn't match expected type `g' against inferred type `MyGen' `g' is a rigid type variable bound by the type signature for `randomR' at <no location info> Expected type: (Foo, Foo) -> g -> (Foo, g) Inferred type: (Foo, Foo) -> MyGen -> (Foo, MyGen) In the expression: myRandomR In the definition of `randomR': randomR = myRandomR Failed, modules loaded: none.
I have two questions:
1. Why can't I instantiate a type class with any function I like provided it fits the type signature?
The problem here is that myRandomR does not match the type signature in the class. You have myRandomR :: (Foo, Foo) -> MyGen -> (Foo, MyGen) but you need randomR :: RandomGen g => (Foo, Foo) -> g -> (Foo, g) i.e., the function is required to be more generic than the one you provide. The good news is that you don't need to declare Foo at all. You only need to declare an instance of Random if you want to generate random *values* of some new type. If you just want numbers, remove all the stuff about Foo and call (for example) randomR (0,5) $ MyGen 18 and it'll give you a number and a new MyGen.
2. Is this the right approach to generating predictable arbitrary values? Are there others?
Seems entirely fine to me. Hope this helps, - Benja

Benja Fallenstein wrote:
Hi Dominic,
myRandomR :: (Foo, Foo) -> MyGen -> (Foo, MyGen)
but you need
randomR :: RandomGen g => (Foo, Foo) -> g -> (Foo, g)
i.e., the function is required to be more generic than the one you provide.
Thank you - obvious in hindsight.
The good news is that you don't need to declare Foo at all. You only need to declare an instance of Random if you want to generate random *values* of some new type. If you just want numbers, remove all the stuff about Foo and call (for example)
randomR (0,5) $ MyGen 18
and it'll give you a number and a new MyGen.
But don't I need something in class Random so that I can use choose?
choose :: forall a. (Random a) => (a, a) -> Gen a
Actually, looking in QuickCheck, I can see this approach is not going to work as QuickCheck always picks the StdGen instance of RandomGen :-(
choose :: Random a => (a, a) -> Gen a choose bounds = (fst . randomR bounds) `fmap` rand
rand :: Gen StdGen rand = Gen (\n r -> r)
Does anyone have any ideas on a way to force QuickCheck to use a different generator of random values? Thanks, Dominic.

What do you need, i.e., what meaning do you attribute to the words "predictable" and "arbitrary"?
Apologies - I didn't explain my problem clearly. I want to say something like: instance Arbitrary Foo where arbitrary = choose (Foo 1, Foo 5) but the "random" values are generated by my own random number generator not the standard one. Does that make sense? The reason I'm trying to do this is I am generating random test data but some of it needs to be predictable.

Dominic Steinitz wrote:
I want to say something like:
instance Arbitrary Foo where arbitrary = choose (Foo 1, Foo 5)
but the "random" values are generated by my own random number generator not the standard one.
Does that make sense? The reason I'm trying to do this is I am generating random test data but some of it needs to be predictable It makes sense, but its not possible. The "generate" function has the type:
*generate* :: Int http://www.haskell.org/ghc/docs/latest/html/libraries/base/Data-Int.html#t%3... -> StdGen http://www.haskell.org/ghc/docs/latest/html/libraries/random/System-Random.h... -> Gen http://www.haskell.org/ghc/docs/latest/html/libraries/QuickCheck/Test-QuickC... a -> a Unfortunately for your purpose you would need: *generate* :: (RandomGen g) => Int http://www.haskell.org/ghc/docs/latest/html/libraries/base/Data-Int.html#t%3... -> g -> Gen http://www.haskell.org/ghc/docs/latest/html/libraries/QuickCheck/Test-QuickC... a -> a Take a look at SmallCheck. It might be more suited to your requirement anyway. Paul.

Paul Johnson wrote:
Dominic Steinitz wrote:
Unfortunately for your purpose you would need:
*generate* :: (RandomGen g) => Int http://www.haskell.org/ghc/docs/latest/html/libraries/base/Data-Int.html#t%3... -> g -> Gen http://www.haskell.org/ghc/docs/latest/html/libraries/QuickCheck/Test-QuickC... a -> a
Thanks - rather what I thought. This seems to do the trick using a state monad but it doesn't look pretty. import Test.QuickCheck import Control.Monad.State data Baz = Baz String Int deriving (Eq, Show) g :: MonadState Int m => m (Gen Int) g = do x <- get put (x + 1) return (return x) f :: MonadState Int m => Int -> m (Gen [Baz]) f 0 = return (return []) f n = do x <- g xs <- f (n - 1) let z = do u <- x us <- xs v <- arbitrary return ((Baz ("t" ++ (show u)) v):us) return z *Main> let (q,p) = runState (f 10) 1 in sample q [Baz "t1" (-1),Baz "t2" 0,Baz "t3" 0,Baz "t4" (-1),Baz "t5" 1,Baz "t6" 1,Baz "t7" 1,Baz "t8" 1,Baz "t9" 1,Baz "t10" 1] [Baz "t1" 0,Baz "t2" 2,Baz "t3" (-2),Baz "t4" (-2),Baz "t5" (-1),Baz "t6" 0,Baz "t7" 1,Baz "t8" 2,Baz "t9" (-2),Baz "t10" (-2)] This gives me what I wanted: distinct (and in this case predictable) names and random values.
Take a look at SmallCheck. It might be more suited to your requirement anyway.
I will do so now. Thanks, Dominic.

Dominic Steinitz schrieb:
What do you need, i.e., what meaning do you attribute to the words "predictable" and "arbitrary"?
Apologies - I didn't explain my problem clearly.
I want to say something like:
instance Arbitrary Foo where arbitrary = choose (Foo 1, Foo 5)
but the "random" values are generated by my own random number generator not the standard one.
Does that make sense? The reason I'm trying to do this is I am generating random test data but some of it needs to be predictable.
When I work with QuickCheck, it often finds some interesting corner cases. I prefer to solve this one problem before further testing, so I use a little wrapper around QuickCheck to be able to reproduce a specific test: <code> import Test.QuickCheck hiding (test) import qualified Test.QuickCheck as QC (test) test prop = do getStdGen >>= print QC.test prop -- for repeatable tests testRnd prop r1 r2 = do setStdGen . read $ show r1 ++ " " ++ show r2 QC.test prop </code> 'test' simply dumps the current generator (show as two numbers) and one can use these two numbers with 'testRnd' to repeat the test with exactly the same data. Perhaps this technique is useful for your problem. Cheers, Harald

Dominic Steinitz writes:
I need to generate distinct arbitrary values...
... I'll create my own random number generator (which will not be random at all) ...
myNext (MyGen s1) = (s1, MyGen (s1 + 1))
2. Is this the right approach to generating predictable arbitrary values? Are there others?
The "really random" congruential generators: x -> A*x + C (mod M) are fully predictable in the sense that there is no indeterminacy involved, no? What do you need, i.e., what meaning do you attribute to the words "predictable" and "arbitrary"? BTW. people often think that a "pure function" cannot generatate pseudo- random numbers, that a generator *must* thread the updated seed. But there are hashing functions, which for n=0,1,2,3,4,... generate a complete mess, numbers which look random and uncorrelated. For example, if you do that (a pseudocode, [actually, this code works in Clean, which discards overflows in Int arith.] not Haskell): n = (n<<13) `bitxor` n return toReal(n*(n*n*599479+649657)+1376312589)/2147483648.0 provided your favourite language is able to discard all overflows tacitly, you will get "arbitrary" values, for sequential arguments. Of course, predictable in the well understood sense, practically not easy to predict. Jerzy Karczmarczuk
participants (5)
-
Benja Fallenstein
-
Dominic Steinitz
-
Harald Holtmann
-
jerzy.karczmarczuk@info.unicaen.fr
-
Paul Johnson