mutagen-0.1.0.0: Property-based testing framework for Haskell using type-preserving mutations.
Safe HaskellNone
LanguageHaskell2010

Test.Mutagen.TH

Description

Entry point for Template Haskell based derivations of Mutagen type classes.

Currently, this supports deriving instances for the Arbitrary, Mutable, Lazy, and Fragmentable type classes.

   {-# LANGUAGE TemplateHaskell #-}
   import qualified Test.Mutagen.TH as TH

   data MyType = Foo | Bar | Baz Int | Qux String
     deriving (Show, Eq, Ord)

   -- Derive all supported instances
   TH.deriveAll ''MyType

   -- Or, alternatively, derive individual instances
   TH.deriveInstance ''MyType ''Arbitrary
   TH.deriveInstance ''MyType ''Fragmentable

   -- While optionally setting custom derivation options
   TH.deriveInstanceWithOptions
     TH.defaultTHOptions
       { TH.optIgnore = ['Qux] -- ignore the Qux constructor
       , TH.optDef = Just 'Bar -- derive def = Bar
       }
     ''MyType
     ''Mutable
Synopsis

Derivation options

data THOptions Source #

Options for deriving instances using Template Haskell.

Constructors

THOptions 

Fields

defaultTHOptions :: THOptions Source #

Default derivation options.

Derivation dispatchers

deriveAll :: Name -> Q [Dec] Source #

Derive all supported type class instances for a given data type.

deriveInstance :: Name -> Name -> Q [Dec] Source #

Derive a single instance for a given data type and type class.

deriveInstanceWithOptions :: THOptions -> Name -> Name -> Q [Dec] Source #

Derive a single custom instance for a given data type and type class.