[Haskell-cafe] derive + quickCheck

bob zhang bobzhang1988 at gmail.com
Mon Jul 18 01:42:50 CEST 2011


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)





More information about the Haskell-Cafe mailing list