| Copyright | (c) Brent Yorgey 2010 |
|---|---|
| License | BSD-style (see LICENSE) |
| Maintainer | byorgey@cis.upenn.edu |
| Stability | experimental |
| Safe Haskell | None |
| Language | Haskell2010 |
Math.Combinatorics.Species.TH
Description
Use Template Haskell to automatically derive species instances for user-defined data types.
- deriveDefaultSpecies :: Name -> Q [Dec]
- deriveSpecies :: Name -> SpeciesAST -> Q [Dec]
Documentation
deriveDefaultSpecies :: Name -> Q [Dec] Source
Generate default species declarations for the given user-defined data type. To use it:
{-# LANGUAGE TemplateHaskell,
TypeFamilies,
DeriveDataTypeable,
FlexibleInstances,
UndecidableInstances #-}
data MyType = ...
$(deriveDefaultSpecies ''MyType)Yes, you really do need all those extensions. And don't panic
about the UndecidableInstances; the instances generated
actually are decidable, but GHC just can't tell.
This is what you get:
- An
Enumerableinstance forMyType(and various other supporting things like a code and anASTFunctorinstance if your data type is recursive) - A declaration of
myType :: Species s => s(the same name as the type constructor but with the first letter lowercased)
You can then use myType in any species expression, or as input
to any function expecting a species. For example, to count your
data type's distinct shapes, you can do
take 10 . unlabeled $ myType
deriveSpecies :: Name -> SpeciesAST -> Q [Dec] Source
Like deriveDefaultSpecies, except that you specify the species
expression that your data type should be isomorphic to. Note: this
is currently experimental (read: bug-ridden).