Jonas,

You can also derive (Co)Arbitrary instances automatically using the 
regular-extras package based on the Regular generic programming library.

The advantage of using a library like Regular is that you do not have to write 
any Template Haskell code. The library generates a nice algebraic generic view 
on your datatype that you can use to write your generic functions. The Regular 
library itself of course uses TH internally, but this is done once and all 
datatype generic functions can piggy bag on the same TH derivation. For 
example, look at Generics.Regular.Functions.Arbitrary, this module is really 
concise.

Nice work though!

Gr,
Sebastiaan

On Apr 18, 2010, at 1:43 AM, Jonas Almström Duregård wrote:
> I'm pleased to announce Agata (Agata Generates Algebraic Types Automatically)!
> 
> Avoiding excessive details, usage is best described by a small example:
> 
> {-#LANGUAGE TemplateHaskell #-}
> import Test.QuickCheck
> import Test.AgataTH
> 
> data X a b = X [Either a b] deriving Show
> data Y = Y deriving Show
> data Z = Z deriving Show
> 
> $(agatath $ deriveall [''X,''Y,''Z])
> 
> main = sample (arbitrary :: Gen (X Y Z))
> 
> This code derives instances of Test.QuickCheck.Arbitrary for the data
> types X, Y and Z.
> 
> http://hackage.haskell.org/package/Agata
> 
> Regards Jonas

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

Reply via email to