thorn-0.2: Datatype Manipulation with Template Haskell

Safe HaskellNone

Data.Thorn.Functor

Contents

Description

The module Data.Thorn.Functor.

Synopsis

Functors

Thorn generates functors from various kinds of datatypes.

Quite surprisingly, it still works for any arities, co/contra/free/fixed-variances, partially applied types, type synonyms, and mutual recursions.

autofmap :: TypeQ -> ExpQSource

autofmap t generates an fmap of the type t.

autofmaptype :: TypeQ -> TypeQSource

autofmaptype t provides the type of $(autofmap t).

autofmapdec :: String -> TypeQ -> DecsQSource

autofmapdec s t provides a declaration of an fmap for the type t with the name s, with a type signature.

autofunctorize :: TypeQ -> DecsQSource

autofunctorize t provides instance delcarations of the type t, for the suitable functor classes : Functor, Contravariant, Bifunctor, or Profunctor. Multiple classes can be suitable for t, when one of the variances of t is Free.

Variance

data Variance Source

Variance is a variance of a parameter of a functor.

Constructors

Co

Covariance, one of a normal functor.

Contra

Contravariance, the dual of covariance.

Free

Free-variance, or invariance, being supposed to satisfy either covariance or contravariance.

Fixed

Fixed-variance, or nonvariance, being supposed to satisfy both covariance and contravariance.

Instances

Read Variance 
Show Variance 
Monoid Variance

v1 mappend v2 means to be supposed to satisfy both v1 and v2.

autovariance :: TypeQ -> ExpQSource

autovariance t provides the variances of the type t.

Examples

Basic

It's a piece of cake.

 testtuple :: (Int,String)
 testtuple = $(autofmap [t|(,)|]) (+1) ('h':) (100,"ello") -- (101,"hello")
 
 testeither :: Either Int String
 testeither = $(autofmap [t|Either|]) (+1) ('a':) (Left 100) -- Left 101
 
 testfunction :: String
 testfunction = $(autofmap [t|(->)|]) ('h':) (++"!") (++", world") "ello" -- "hello, world!"
 
 testlist :: [Int]
 testlist = $(autofmap [t|[]|]) (+10) [1..5] -- [11..15]

Functions

You can nest functions.

 data FunFun a b = FunFun ((b -> a) -> b)
 
 varfunfun :: [Variance]
 varfunfun = $(autovariance [t|FunFun|]) -- [Contra,Co]
 
 autofunctorize [t|FunFun|]
 -- instance Profunctor FunFun where
 --     dimap = ...

Partial Application

It works for partially applied types.

 testpartial :: (Int,Int,Int)
 testpartial = $(autofmap $[t|(,,) Int|]) (+10) (+20) (1,1,1) -- (1,11,21)

You can use type variants T0, T1, ..., T9 to represent any type.

 testpartial' :: (String,Int,Int)
 testpartial' = $(autofmap $[t|(,,) T0|]) (+10) (+20) ("hello",1,1) -- ("hello",11,21)

Type Synonyms

Interestingly, it works for type synonyms.

 type a :<- b = b -> a
 varnuf :: [Variance]
 varnuf = $(autovariance [t|(:<-)|]) -- [Co,Contra]
 $(autofmapdec "fmapnuf" [t|(:<-)|])

Variances

It works for free-variance and fixed-variance. See how autofunctorize works for free-variance.

 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
 --     bimap = ...
 -- instance Profunctor (What a) where
 --     dimap = ...

Recursive Types

It works for recursive datatypes.

 data List a = Nil | a :* (List a) deriving Show
 
 autofunctorize [t|List|]
 -- instance Functor List where
 --     fmap = ...
 
 fromNormalList :: [a] -> List a
 fromNormalList [] = Nil
 fromNormalList (a : as) = a :* fromNormalList as
 toNormalList :: List a -> [a]
 toNormalList Nil = []
 toNormalList (a :* as) = a : toNormalList as
 
 testlist :: [Int]
 testlist = toNormalList $ fmap (+10) (fromNormalList [1..5]) -- [11..15]

It also works for mutually recursive datatypes.

 data Rose a = Rose a (Forest a) deriving Show
 data Forest a = Forest [Rose a] deriving Show
 
 autofunctorize [t|Rose|]
 -- instance Functor Rose where
 --     fmap = ...
 
 gorose :: Int -> Rose Int
 gorose 0 = Rose 0 (Forest [])
 gorose n = Rose n (Forest (replicate 2 (gorose (n-1))))
 testrose :: Rose Int
 testrose = fmap (+10) (gorose 2)
 -- Rose 12 (Forest [Rose 11 (Forest [Rose 10 (Forest []),Rose 10 (Forest [])]),Rose 11 (Forest [Rose 10 (Forest []),Rose 10 (Forest [])])])