generics-sop-0.2.2.0: Generic Programming using True Sums of Products

Safe HaskellNone
LanguageHaskell2010

Generics.SOP.TH

Description

Generate generics-sop boilerplate instances using Template Haskell.

Synopsis

Documentation

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

Generate generics-sop boilerplate for the given datatype.

This function takes the name of a datatype and generates:

Note that the generated code will require the TypeFamilies and DataKinds extensions to be enabled for the module.

Example: If you have the datatype

data Tree = Leaf Int | Node Tree Tree

and say

deriveGeneric ''Tree

then you get code that is equivalent to:

instance Generic Tree where

  type Code Tree = '[ '[Int], '[Tree, Tree] ]

  from (Leaf x)   = SOP (   Z (I x :* Nil))
  from (Node l r) = SOP (S (Z (I l :* I r :* Nil)))

  to (SOP    (Z (I x :* Nil)))         = Leaf x
  to (SOP (S (Z (I l :* I r :* Nil)))) = Node l r
  to _ = error "unreachable" -- to avoid GHC warnings

instance HasDatatypeInfo Tree where
  datatypeInfo _ = ADT "Main" "Tree"
    (Constructor "Leaf" :* Constructor "Node" :* Nil)

Limitations: Generation does not work for GADTs, for datatypes that involve existential quantification, for datatypes with unboxed fields.

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

Like deriveGeneric, but omit the HasDatatypeInfo instance.

deriveGenericFunctions :: Name -> String -> String -> String -> Q [Dec] Source #

Like deriveGenericOnly, but don't derive class instance, only functions.

Example: If you say

deriveGenericFunctions ''Tree "TreeCode" "fromTree" "toTree"

then you get code that is equivalent to:

type TreeCode = '[ '[Int], '[Tree, Tree] ]

fromTree :: Tree -> SOP I TreeCode
fromTree (Leaf x)   = SOP (   Z (I x :* Nil))
fromTree (Node l r) = SOP (S (Z (I l :* I r :* Nil)))

toTree :: SOP I TreeCode -> Tree
toTree (SOP    (Z (I x :* Nil)))         = Leaf x
toTree (SOP (S (Z (I l :* I r :* Nil)))) = Node l r
toTree _ = error "unreachable" -- to avoid GHC warnings

Since: 0.2

deriveMetadataValue :: Name -> String -> String -> Q [Dec] Source #

Derive DatatypeInfo value for the type.

Example: If you say

deriveMetadataValue ''Tree "TreeCode" "treeDatatypeInfo"

then you get code that is equivalent to:

treeDatatypeInfo :: DatatypeInfo TreeCode
treeDatatypeInfo = ADT "Main" "Tree"
    (Constructor "Leaf" :* Constructor "Node" :* Nil)

Note: CodeType need to be derived with deriveGenericFunctions.

Since: 0.2