| Safe Haskell | None |
|---|
Data.Thorn
Contents
Description
Thorn, Datatype Manipulation with Template Haskell.
- autofmap :: TypeQ -> ExpQ
- data Variance
- autovariance :: TypeQ -> ExpQ
- autofunctorize :: TypeQ -> DecsQ
- unfixdata :: TypeQ -> DecsQ
- unfixdataEx :: (String, String) -> (String, String) -> (String, String) -> (String, String) -> TypeQ -> DecsQ
- autoin :: TypeQ -> TypeQ -> ExpQ
- autoout :: TypeQ -> TypeQ -> ExpQ
- autohylo :: TypeQ -> ExpQ
- autofold :: TypeQ -> TypeQ -> ExpQ
- autounfold :: TypeQ -> TypeQ -> ExpQ
- data T0
- data T1
- data T2
- data T3
- data T4
- data T5
- data T6
- data T7
- data T8
- data T9
Functor
Thorn generates functors from various kinds of data types.
Quite surprisingly, it still works for any arities, co/contra/free/fixed-variances, partially applied types, type synonyms, and mutual recursions.
For more information, see Functor Example.
Variance is a variance of a parameter of a functor.
autovariance :: TypeQ -> ExpQSource
autovariance t provides the variances of the type t.
autofunctorize :: TypeQ -> DecsQSource
autofunctorize t provides instance delcarations of the type t, for the suitable functor classes : Funtor, Contravariant, Bifunctor, or Profunctor.
Folding and Unfolding
For more information, see Folding and Unfolding Example.
unfixdata :: TypeQ -> DecsQSource
unfixdata t provides a declaration of a data whose fixpoint is the recursive type t.
Arguments
| :: (String, String) | prefix and suffix of type constructor |
| -> (String, String) | prefix and suffix of data constructor |
| -> (String, String) | prefix and suffix of infix type constructor |
| -> (String, String) | prefix and suffix of infix data constructor |
| -> TypeQ | data type |
| -> DecsQ | declaration of data |
Special version of unfixdata. Note that
unfixdata = unfixdataEx ("Uf","") ("Uf","") ("&","") ("&","")
Arguments
| :: TypeQ |
|
| -> TypeQ |
|
| -> ExpQ | function with a type |
autofold u t provides a folding function for a recursive type t.
Arguments
| :: TypeQ |
|
| -> TypeQ |
|
| -> ExpQ | function with a type |
autounfold t provides an unfolding function for the recursive type t.
Type Variants
These types are used for representing type variants. For more information, see Functor Example.
Example
Functor Example
import Data.Thorn import Data.Char import Data.Functor.Contravariant import Data.Bifunctor import Data.Profunctor type a :<- b = b -> a nuf :: Char nuf = $(autofmap [t|(:<-)|]) chr ord (+1) 'a' -- 'b' varnuf :: [Variance] varnuf = $(autovariance [t|(:<-)|]) -- [Co,Contra] data Cntr a = Cntr (a -> Int) autofunctorize [t|Cntr|] -- instance Contravariant Cntr where ... tuple :: (Int,Int,Int) tuple = $(autofmap $[t|(,,) Int|]) (+1) (+2) (0,0,0) -- (0,1,2) vartuple :: [Variance] vartuple = $(autovariance [t|(,,) Int|]) -- [Co,Co] data FunFun a b = FunFun ((b -> a) -> b) varfunfun :: [Variance] varfunfun = $(autovariance [t|FunFun|]) -- [Contra,Co] autofunctorize [t|FunFun|] -- instance Profunctor FunFun where ... data What a b c = What1 c (a -> c) | What2 a varwhat :: [Variance] varwhat = $(autovariance [t|What|]) -- [Fixed,Free,Co] autofunctorize [t|What T0|] -- instance Bifunctor (What a) where ... and -- instance Profunctor (What a) where ... data List a = Nil | a :* (List a) deriving Show fromNormalList :: [a] -> List a fromNormalList [] = Nil fromNormalList (a : as) = a :* fromNormalList as toNormalList :: List a -> [a] toNormalList Nil = [] toNormalList (a :* as) = a : toNormalList as list :: [Int] list = toNormalList $ $(autofmap [t|List|]) (+10) (fromNormalList [1..5]) -- [11..15] varlist :: [Variance] varlist = $(autovariance [t|List|]) -- [Co] autofunctorize [t|List|] -- instance Functor List where ... data Rose a = Rose a (Forest a) deriving Show data Forest a = Forest [Rose a] deriving Show gorose n = Rose n (Forest (replicate n (gorose (n-1)))) rose = $(autofmap [t|Rose|]) (+1) (gorose 2) varrose, varforest :: [Variance] varrose = $(autovariance [t|Rose|]) -- [Co] varforest = $(autovariance [t|Forest|]) -- [Co] autofunctorize [t|Rose|] -- instance Functor Rose where ... autofunctorize [t|Forest|] -- instance Functor Forest where ...