
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

Wow, very cool! This is so helpful I'm surprised it isn't part of QuickCheck. Why isn't it? Regards, Duane Johnson On Apr 17, 2010, at 6:43 PM, Jonas Almström Duregård wrote:
{-#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))

Wow, very cool! Thank you :)
This is so helpful I'm surprised it isn't part of QuickCheck. Why isn't it? Maybe it will be eventually. It would introduce some package dependencies though, and as the version number hints it's not exactly mature code.
2010/4/18 Duane Johnson
Wow, very cool! This is so helpful I'm surprised it isn't part of QuickCheck. Why isn't it? Regards, Duane Johnson On Apr 17, 2010, at 6:43 PM, Jonas Almström Duregård wrote:
{-#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))

If this is to be used with QuickCheck maybe it should be named that way. eg quickcheck-agatath ? This way its found faster. Marc Weber

If this is to be used with QuickCheck maybe it should be named that way. Certainly worth considering. There seems to be no convenient way of renaming packages on Hackage though, is there?
I suppose it would be wrong/impossible to create an alias package
(quickcheck-agata) with no modules, just a dependency on the primary
package (Agata)?
/Jonas
2010/4/18 Marc Weber
If this is to be used with QuickCheck maybe it should be named that way. eg quickcheck-agatath ?
This way its found faster.
Marc Weber

2010/4/19 Jonas Almström Duregård
If this is to be used with QuickCheck maybe it should be named that way. Certainly worth considering. There seems to be no convenient way of renaming packages on Hackage though, is there?
AFAIK hackage has support for deprecating packages in favor of others. This functionality is not exposed to regular users but you could mail one of the maintainers (Ross Paterson) to rename your package. Bas

Hi,
Have you seen the derive package? It also generates QuickCheck
instances in virtually the same way - plus it can generate source code
and do lots of other types of instances.
http://community.haskell.org/~ndm/derive/
Thanks, Neil
2010/4/20 Bas van Dijk
2010/4/19 Jonas Almström Duregård
: If this is to be used with QuickCheck maybe it should be named that way. Certainly worth considering. There seems to be no convenient way of renaming packages on Hackage though, is there?
AFAIK hackage has support for deprecating packages in favor of others. This functionality is not exposed to regular users but you could mail one of the maintainers (Ross Paterson) to rename your package.
Bas _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

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

Hi Neil and Sebastiaan, Thanks for the constructive criticism ;). As far as i can tell, derive only works for regular and linear recursive types and Regular uses frequencies to regulate size. (Also Regular doesn't seem to work for QuickCheck-2). I think I may have used a too simple example in my original post. Here is a more complicated one:
data TrinaryTree a = Branch a (TrinaryTree a) (TrinaryTree a) (TrinaryTree a) | Empty deriving Show
$(agatath $ derive ''TrinaryTree)
With the derive tool, generated values would typically be infinite.
With Regular, the user would need to specify frequencies, and even
then the generator would be useless because of the low frequency
required for "Branch" to ensure termination (most generated trees
would be empty, and almost none would contain several branches).
Most of the work i have done on Agata is to make a class that
resembles arbitrary (i.e. can be used to construct generators) but
where the instances can be defined mechanically from the definition of
instantiated types. The reason i didn't use Generics for defining the
instances is that I was unsure if/how it distinguishes mutually
recursive fields.
Another feature of Agata generators is improved scalability compared
to other QuickCheck generators, especially for nested collection data
types (analog to [[[[a]]]] and such). The details of how this works in
Agata will one day be explained in the documentation, but the
principle is explained in my masters thesis[1].
Regards,
Jonas
[1] http://gupea.ub.gu.se/bitstream/2077/22087/1/gupea_2077_22087_1.pdf
2010/4/20 Sebastiaan Visser
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

Hi Jonas,
As far as i can tell, derive only works for regular and linear recursive types and Regular uses frequencies to regulate size. (Also Regular doesn't seem to work for QuickCheck-2).
Derive will generate instances for all types, but uses a fairly standard formulation (pick between each constructor equally), meaning that in some cases the generators won't be that good, and will tend to generate infinite branches.
Another feature of Agata generators is improved scalability compared to other QuickCheck generators, especially for nested collection data types (analog to [[[[a]]]] and such). The details of how this works in Agata will one day be explained in the documentation, but the principle is explained in my masters thesis[1].
Very neat :-) I'd welcome an instance generator based on your ideas as a patch to Derive. Derive provides 3 things: * Infrastructure - given a definition, it provides tests, ability to run as template haskell, ability to write to files, auto-generated documentation etc. I hope to add more infrastructure, such as the ability to run derivations via a website, so the user need not even install derive. * Derivation inference - a method infer derivations given a single example (explained in this paper: http://community.haskell.org/~ndm/downloads/paper-deriving_a_relationship_fr...) * Lots of instances, about 34 different ones. I/you/we could replace the Arbitrary instance with one based on your implementation. You don't have to use the derivation inference (and it probably wouldn't be suitable), but you do get to benefit from the rest of the infrastructure. People can then run your program via the command line, integrate easily with preprocessors etc - and still do the Template Haskell bit too.
[1] http://gupea.ub.gu.se/bitstream/2077/22087/1/gupea_2077_22087_1.pdf
Nice, I'll have a read (if it's in English) Thanks, Neil
participants (6)
-
Bas van Dijk
-
Duane Johnson
-
Jonas Almström Duregård
-
Marc Weber
-
Neil Mitchell
-
Sebastiaan Visser