
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

Hi Yair,
I wrote some Template Haskell templates that I think may be of use to others.
The first generates "in" and "with" functions for newtypes.
This looks very nice. Have you thought about putting this code in to the Derive package? (http://community.haskell.org/~ndm/derive, and also on Hackage). It provides a set of derivations, which can be called from Template Haskell, and a command line program for applying them. By putting them inside Derive you'll get lots of nice things for free, and it will be easier for people to use your code. Thanks, Neil

On Mon, Nov 23, 2009 at 11:50 AM, Neil Mitchell
This looks very nice. Have you thought about putting this code in to the Derive package? (http://community.haskell.org/~ndm/derive, and also on Hackage).
Hi Neil, If you think this would belong in Derive, then, cool, let's do it :) I'll take a deeper look on derive soon when I find some time. Cheers, Yair
participants (2)
-
Neil Mitchell
-
Yair Chuchem