[Haskell-cafe] Some useful TH templates

Yair Chuchem yairchu at gmail.com
Thu Nov 19 09:17:41 EST 2009


Hi,

I wrote some Template Haskell templates that I think may be of use to others.

The first generates "in" and "with" functions for newtypes.

For example, using it one can replace this code (from TypeCompose):

> inFlip :: ((a~>b) -> (a' ~~> b')) -> (Flip (~>) b a -> Flip (~~>) b' a')
> inFlip = (Flip .).(. unFlip)
>
> inFlip2 :: ((a~>b) -> (a' ~~> b') -> (a'' ~~~> b''))
>        -> (Flip (~>) b a -> Flip (~~>) b' a' -> Flip (~~~>) b'' a'')
> inFlip2 f (Flip ar) = inFlip (f ar)
>
> inFlip3 :: ((a~>b) -> (a' ~~> b') -> (a'' ~~~> b'') -> (a''' ~~~~> b'''))
>         -> (Flip (~>) b a -> Flip (~~>) b' a' -> Flip (~~~>) b'' a'' -> Flip (~~~~>) b''' a''')
> inFlip3 f (Flip ar) = inFlip2 (f ar)

with this code:

> {-# LANGUAGE TemplateHaskell #-}
> import Data.Newtype
> $(mkInNewtypeFuncs [1..3] ''Flip)

The second template is for accessing ADTs in the Maybe monad. For example:

> {-# LANGUAGE TemplateHaskell #-}
> import Data.ADT.Getters
> data Blah a = NoBlah | YesBlah a | ManyBlah a Int
> $(mkADTGetters ''Blah)

Generates:

> gNoBlah :: Blah a -> Maybe ()
> gYesBlah :: Blah a -> Maybe a
> gManyBlah :: Blah a -> Maybe (a, Int)

I'm more than willing to upload these templates to hackage (or rather,
split them out of an unrelated package),
but all I need is a suggestion for a package name :)

For now you can find these here:
http://hackage.haskell.org/package/peakachu

Hoping someone else will find it useful,
cheers,
Yair


More information about the Haskell-Cafe mailing list