
Hi, all, I found derive + quickCheck very useful but I came across some problems. I used derive to derive instance of Arbitrary immeditaely, but sometimes the sample is non-terminating, which I mean the result is very very big. I used samples <- take 10 <$> sample' in ghci to test the result, it's non-terminating.. another problem is that $(derive makeArbitrary ''JValue) uses reify, so I can not see the generated code, any better way to have a look at the generated code in ghci? my sample code {-# LANGUAGE FlexibleInstances ,MultiParamTypeClasses ,GeneralizedNewtypeDeriving ,FunctionalDependencies ,TypeSynonymInstances ,TemplateHaskell #-} module JsonParse where import Text.ParserCombinators.Parsec import Text.Parsec.String() import Control.Applicative hiding ( (<|>) , many, optional ) import Control.Monad import Test.QuickCheck -- unGen, sample -- import Language import Data.DeriveTH import Data.Binary import Data.Derive.Arbitrary import Language.Haskell.TH import Language.Haskell.TH.Syntax data JValue = JString String | JNumber Double | JBool Bool | JNull | JObject [(String, JValue)] -- | JArray [JValue] -- deriving (Eq,Ord,Show) $(derive makeArbitrary ''JValue)

On 17 July 2011 23:42, bob zhang
Hi, all, I found derive + quickCheck very useful but I came across some problems. I used derive to derive instance of Arbitrary immeditaely, but sometimes the sample is non-terminating, which I mean the result is very very big.
[snip]
data JValue = JString String | JNumber Double | JBool Bool | JNull | JObject [(String, JValue)] -- | JArray [JValue] -- deriving (Eq,Ord,Show) $(derive makeArbitrary ''JValue)
Your JValue type is recursive; as such I highly suggest you manually create the Arbitrary instances for it (e.g. a helper function with a Bool parameter to indicate whether or not to create recursive calls; see how I do it in http://code.haskell.org/graphviz/Data/GraphViz/Testing/Instances/Canonical.h... where the DotStatements type can have DotSubGraph values, which in turn have DotStatements). -- Ivan Lazar Miljenovic Ivan.Miljenovic@gmail.com IvanMiljenovic.wordpress.com

Hi, thank you . I read your souce, I found the depth is only 2, right? like data A = [A]|String, any easy way to control the maximum_depth of generated data? Regards,bob 于 11-7-17 下午8:13, Ivan Lazar Miljenovic 写道:
On 17 July 2011 23:42, bob zhang
wrote: Hi, all, I found derive + quickCheck very useful but I came across some problems. I used derive to derive instance of Arbitrary immeditaely, but sometimes the sample is non-terminating, which I mean the result is very very big.
[snip]
data JValue = JString String | JNumber Double | JBool Bool | JNull | JObject [(String, JValue)] -- | JArray [JValue] -- deriving (Eq,Ord,Show) $(derive makeArbitrary ''JValue) Your JValue type is recursive; as such I highly suggest you manually create the Arbitrary instances for it (e.g. a helper function with a Bool parameter to indicate whether or not to create recursive calls; see how I do it in http://code.haskell.org/graphviz/Data/GraphViz/Testing/Instances/Canonical.h... where the DotStatements type can have DotSubGraph values, which in turn have DotStatements).

On 19 July 2011 21:23, bob zhang
Hi, thank you . I read your souce, I found the depth is only 2, right? like data A = [A]|String, any easy way to control the maximum_depth of generated data?
You could always use an Int parameter instead of a Bool and have it count down to 0, in which case you stop generating recursive structures.
Regards,bob 于 11-7-17 下午8:13, Ivan Lazar Miljenovic 写道:
On 17 July 2011 23:42, bob zhang
wrote: Hi, all, I found derive + quickCheck very useful but I came across some problems. I used derive to derive instance of Arbitrary immeditaely, but sometimes the sample is non-terminating, which I mean the result is very very big.
[snip]
data JValue = JString String | JNumber Double | JBool Bool | JNull | JObject [(String, JValue)] -- | JArray [JValue] -- deriving (Eq,Ord,Show) $(derive makeArbitrary ''JValue)
Your JValue type is recursive; as such I highly suggest you manually create the Arbitrary instances for it (e.g. a helper function with a Bool parameter to indicate whether or not to create recursive calls; see how I do it in
http://code.haskell.org/graphviz/Data/GraphViz/Testing/Instances/Canonical.h... where the DotStatements type can have DotSubGraph values, which in turn have DotStatements).
-- Ivan Lazar Miljenovic Ivan.Miljenovic@gmail.com IvanMiljenovic.wordpress.com
participants (2)
-
bob zhang
-
Ivan Lazar Miljenovic