Re: [Haskell-cafe] QuickCheck Generators

2012-11-22 Thread Anton Kholomiov
An idea. You can make a type:

data TestContains = TestContains Tweet TweetSet

and the make an Arbitrary instance for it. When you do
a recursove call you have three different tweets one new tweet
and two from the sub-calls. Then you can place one of them in the
result. In the end you will have a random TweetSet with some value from it.

Here is a scratch of the implementation:

instance Arbitrary TestContains where
   arbitrary = sized set'
   where set' 0 = mkSingleTweet <$> (arbitrary :: Tweet)
 set' n = do
  t0 <- arbitrary :: Tweet
  TestContains t1 ts1 <- subTweets
  TestContains t2 ts2 <- subTweets
  t <- oneof [t0, t1, t2]
  return $ TestContains t $ TweetSet t0 ts1 ts2

 subTweets = set' (n `div` 2)


2012/11/21 

> I have
>
> data Tweet = Tweet {
> user :: String,
> text :: String,
> retweets :: Double
> } deriving (Show)
>
> data TweetSet = NoTweets | SomeTweets Tweet TweetSet TweetSet
>
> and trying to create some generators for testing, with
>
> instance Arbitrary Tweet where
>   arbitrary = liftM3 Tweet arbitrary arbitrary arbitrary
>
> instance Arbitrary TweetSet where
>   arbitrary = sized set'
> where set' 0 = return NoTweets
>   set' n | n>0 = oneof[return NoTweets, liftM3 SomeTweets
>   arbitrary subTweets subTweets]
> where subTweets = set' (n `div` 2)
>
> but wondering how I would go about generating a random TweetSet that
> contains a known random Tweet I later have reference to and I would also
> assume the known Tweet to be placed randomly.
>
> Then I could test a contains function.
>
> Thanks
>
> ___
> Haskell-Cafe mailing list
> Haskell-Cafe@haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] QuickCheck Generators

2012-11-20 Thread graham
I have 

data Tweet = Tweet {
user :: String,
text :: String,
retweets :: Double
} deriving (Show)

data TweetSet = NoTweets | SomeTweets Tweet TweetSet TweetSet

and trying to create some generators for testing, with

instance Arbitrary Tweet where
  arbitrary = liftM3 Tweet arbitrary arbitrary arbitrary 
  
instance Arbitrary TweetSet where
  arbitrary = sized set'
where set' 0 = return NoTweets
  set' n | n>0 = oneof[return NoTweets, liftM3 SomeTweets
  arbitrary subTweets subTweets]
where subTweets = set' (n `div` 2) 

but wondering how I would go about generating a random TweetSet that
contains a known random Tweet I later have reference to and I would also
assume the known Tweet to be placed randomly.

Then I could test a contains function.

Thanks

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe