Scraping boilerplate deriving?

I have a set of wrapper newtypes that are always of the same format: newtype MyType = MyType Obj deriving (A,B,C,D) where Obj, A, B, C, and D are always the same. Only MyType varies. A, B, C, and D are automagically derived by GHC using the {-# LANGUAGE GeneralizedNewtypeDeriving #-} feature. I would like to use some macro system (perhaps Template Haskell?) to reduce this to something like defObj MyType I've read through some Template Haskell documentation and examples, but I find it intimidatingly hard to follow. Does anyone has some code suggestions or pointers to something similar? Alternatively, is there any way in standard Haskell to define some kind of union class: U = (A, B, C, D) and then using newtype MyType = MyType Obj deriving U which would at least be shorter?

class (A x, B x, C x, D x) => U x ? 14.09.2010 12:24, Kevin Jardine пишет:
I have a set of wrapper newtypes that are always of the same format:
newtype MyType = MyType Obj deriving (A,B,C,D)
where Obj, A, B, C, and D are always the same. Only MyType varies.
A, B, C, and D are automagically derived by GHC using the
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
feature.
I would like to use some macro system (perhaps Template Haskell?) to reduce this to something like
defObj MyType
I've read through some Template Haskell documentation and examples, but I find it intimidatingly hard to follow. Does anyone has some code suggestions or pointers to something similar?
Alternatively, is there any way in standard Haskell to define some kind of union class:
U = (A, B, C, D)
and then using
newtype MyType = MyType Obj deriving U
which would at least be shorter? _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Sorry, got stupid today. Won't help. 14.09.2010 12:29, Miguel Mitrofanov пишет:
class (A x, B x, C x, D x) => U x
?
14.09.2010 12:24, Kevin Jardine пишет:
I have a set of wrapper newtypes that are always of the same format:
newtype MyType = MyType Obj deriving (A,B,C,D)
where Obj, A, B, C, and D are always the same. Only MyType varies.
A, B, C, and D are automagically derived by GHC using the
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
feature.
I would like to use some macro system (perhaps Template Haskell?) to reduce this to something like
defObj MyType
I've read through some Template Haskell documentation and examples, but I find it intimidatingly hard to follow. Does anyone has some code suggestions or pointers to something similar?
Alternatively, is there any way in standard Haskell to define some kind of union class:
U = (A, B, C, D)
and then using
newtype MyType = MyType Obj deriving U
which would at least be shorter? _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

I supposed the simple solution might be CPP:
#define defObj(NAME) newtype NAME = NAME Obj deriving (A,B,C,D)
and then use
defObj (MyType)
I have heard some people, however, say that CPP macros are horrible in
Haskell, so is there a better solution?
Kevin
On Sep 14, 10:34 am, Miguel Mitrofanov
Sorry, got stupid today. Won't help.
14.09.2010 12:29, Miguel Mitrofanov пишет:
class (A x, B x, C x, D x) => U x
?
14.09.2010 12:24, Kevin Jardine пишет:
I have a set of wrapper newtypes that are always of the same format:
newtype MyType = MyType Obj deriving (A,B,C,D)
where Obj, A, B, C, and D are always the same. Only MyType varies.
A, B, C, and D are automagically derived by GHC using the
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
feature.
I would like to use some macro system (perhaps Template Haskell?) to reduce this to something like
defObj MyType
I've read through some Template Haskell documentation and examples, but I find it intimidatingly hard to follow. Does anyone has some code suggestions or pointers to something similar?
Alternatively, is there any way in standard Haskell to define some kind of union class:
U = (A, B, C, D)
and then using
newtype MyType = MyType Obj deriving U
which would at least be shorter? _______________________________________________ Haskell-Cafe mailing list Haskell-C...@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
Haskell-Cafe mailing list Haskell-C...@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
_______________________________________________ Haskell-Cafe mailing list Haskell-C...@haskell.orghttp://www.haskell.org/mailman/listinfo/haskell-cafe

On Tue, Sep 14, 2010 at 10:24, Kevin Jardine wrote:
I have a set of wrapper newtypes that are always of the same format:
newtype MyType = MyType Obj deriving (A,B,C,D)
where Obj, A, B, C, and D are always the same. Only MyType varies.
A, B, C, and D are automagically derived by GHC using the
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
feature.
I would like to use some macro system (perhaps Template Haskell?) to reduce this to something like
defObj MyType
I've read through some Template Haskell documentation and examples, but I find it intimidatingly hard to follow. Does anyone has some code suggestions or pointers to something similar?
This works in TH:
[d|newtype Blah = Blah Int deriving (Num,Show,Eq)|]
But the parameterized variations on this theme do not:
derive1 name = [d|newtype $name = Blah Int deriving (Num,Show,Eq)|] Malformed head of type or class declaration
derive2 name = [d|newtype Blah = $name Int deriving (Num,Show,Eq)|] parse error in data/newtype declaration
I think it has something to do with the type of the splice. Perhaps you can look into further: http://www.haskell.org/ghc/docs/6.12.2/html/users_guide/template-haskell.htm... Sean

2010/9/14 Kevin Jardine
I would like to use some macro system (perhaps Template Haskell?) to reduce this to something like
defObj MyType
I've read through some Template Haskell documentation and examples, but I find it intimidatingly hard to follow. Does anyone has some code suggestions or pointers to something similar?
The solutions first: ------------------------------------------------- {-# LANGUAGE TemplateHaskell #-} module T(mkNewType) where import Language.Haskell.TH decls = [d|newtype TempDecl = TempDecl Int deriving (Eq,Ord,Show)|] decl = do [d] <- decls runIO $ print d -- just to show inetrnals return d mkNewType :: String -> Q [Dec] mkNewType n = do d <- decl let name = mkName n return $ (\x -> [x]) $ case d of (NewtypeD cxt _ argvars (NormalC _ args) derivings) -> NewtypeD cxt name argvars (NormalC name args) derivings -------------------------------------- I took perfectly valid declaration, dissected it using case analysis and changed relevant parts. And an example client: ------------------------------------- {-# LANGUAGE TemplateHaskell #-} import T $(mkNewType "A") ------------------------------------- It all work together. I studied how to use Template Haskell that way: I obtained declarations of what I need, printed them and looked through documentation for relevant data types and constructors. It's not harder that any other library in Haskell, actually.

Thanks Serguey!
The library code compiles, but when I try to use it in client code:
a. I get:
Not in scope: type constructor or class 'A'
and even stranger,
b. GHC cannot find any of my code after the
$(mkNewType "A")
and claims that all the functions I defined there are also not in
scope.
Any ideas?
The CPP solution works but Template Haskell is definitely cooler, so
it would be great to get this to work!
Kevin
On Sep 14, 2:29 pm, Zefirov
2010/9/14 Kevin Jardine
: I would like to use some macro system (perhaps Template Haskell?) to reduce this to something like
defObj MyType
I've read through some Template Haskell documentation and examples, but I find it intimidatingly hard to follow. Does anyone has some code suggestions or pointers to something similar?
The solutions first: ------------------------------------------------- {-# LANGUAGE TemplateHaskell #-}
module T(mkNewType) where
import Language.Haskell.TH
decls = [d|newtype TempDecl = TempDecl Int deriving (Eq,Ord,Show)|] decl = do [d] <- decls runIO $ print d -- just to show inetrnals return d
mkNewType :: String -> Q [Dec] mkNewType n = do d <- decl let name = mkName n return $ (\x -> [x]) $ case d of (NewtypeD cxt _ argvars (NormalC _ args) derivings) -> NewtypeD cxt name argvars (NormalC name args) derivings -------------------------------------- I took perfectly valid declaration, dissected it using case analysis and changed relevant parts.
And an example client: ------------------------------------- {-# LANGUAGE TemplateHaskell #-}
import T
$(mkNewType "A") ------------------------------------- It all work together.
I studied how to use Template Haskell that way: I obtained declarations of what I need, printed them and looked through documentation for relevant data types and constructors. It's not harder that any other library in Haskell, actually. _______________________________________________ Haskell-Cafe mailing list Haskell-C...@haskell.orghttp://www.haskell.org/mailman/listinfo/haskell-cafe

Hmm - It seems to work if the code is defined before my main function
and not after it.
Does this have to do with TH being part of the compile process and so
the order matters?
Kevin
On Sep 14, 6:03 pm, Kevin Jardine
Thanks Serguey!
The library code compiles, but when I try to use it in client code:
a. I get:
Not in scope: type constructor or class 'A'
and even stranger,
b. GHC cannot find any of my code after the
$(mkNewType "A")
and claims that all the functions I defined there are also not in scope.
Any ideas?
The CPP solution works but Template Haskell is definitely cooler, so it would be great to get this to work!
Kevin
On Sep 14, 2:29 pm, Zefirov
wrote: 2010/9/14 Kevin Jardine
: I would like to use some macro system (perhaps Template Haskell?) to reduce this to something like
defObj MyType
I've read through some Template Haskell documentation and examples, but I find it intimidatingly hard to follow. Does anyone has some code suggestions or pointers to something similar?
The solutions first: ------------------------------------------------- {-# LANGUAGE TemplateHaskell #-}
module T(mkNewType) where
import Language.Haskell.TH
decls = [d|newtype TempDecl = TempDecl Int deriving (Eq,Ord,Show)|] decl = do [d] <- decls runIO $ print d -- just to show inetrnals return d
mkNewType :: String -> Q [Dec] mkNewType n = do d <- decl let name = mkName n return $ (\x -> [x]) $ case d of (NewtypeD cxt _ argvars (NormalC _ args) derivings) -> NewtypeD cxt name argvars (NormalC name args) derivings -------------------------------------- I took perfectly valid declaration, dissected it using case analysis and changed relevant parts.
And an example client: ------------------------------------- {-# LANGUAGE TemplateHaskell #-}
import T
$(mkNewType "A") ------------------------------------- It all work together.
I studied how to use Template Haskell that way: I obtained declarations of what I need, printed them and looked through documentation for relevant data types and constructors. It's not harder that any other library in Haskell, actually. _______________________________________________ Haskell-Cafe mailing list Haskell-C...@haskell.orghttp://www.haskell.org/mailman/listinfo/haskell-cafe
_______________________________________________ Haskell-Cafe mailing list Haskell-C...@haskell.orghttp://www.haskell.org/mailman/listinfo/haskell-cafe

Yes, if you use template haskell, all top level functions and values
have to be defined before you use them.
Erik
On Tue, Sep 14, 2010 at 18:11, Kevin Jardine
Hmm - It seems to work if the code is defined before my main function and not after it.
Does this have to do with TH being part of the compile process and so the order matters?
Kevin
On Sep 14, 6:03 pm, Kevin Jardine
wrote: Thanks Serguey!
The library code compiles, but when I try to use it in client code:
a. I get:
Not in scope: type constructor or class 'A'
and even stranger,
b. GHC cannot find any of my code after the
$(mkNewType "A")
and claims that all the functions I defined there are also not in scope.
Any ideas?
The CPP solution works but Template Haskell is definitely cooler, so it would be great to get this to work!
Kevin
On Sep 14, 2:29 pm, Zefirov
wrote: 2010/9/14 Kevin Jardine
: I would like to use some macro system (perhaps Template Haskell?) to reduce this to something like
defObj MyType
I've read through some Template Haskell documentation and examples, but I find it intimidatingly hard to follow. Does anyone has some code suggestions or pointers to something similar?
The solutions first: ------------------------------------------------- {-# LANGUAGE TemplateHaskell #-}
module T(mkNewType) where
import Language.Haskell.TH
decls = [d|newtype TempDecl = TempDecl Int deriving (Eq,Ord,Show)|] decl = do [d] <- decls runIO $ print d -- just to show inetrnals return d
mkNewType :: String -> Q [Dec] mkNewType n = do d <- decl let name = mkName n return $ (\x -> [x]) $ case d of (NewtypeD cxt _ argvars (NormalC _ args) derivings) -> NewtypeD cxt name argvars (NormalC name args) derivings -------------------------------------- I took perfectly valid declaration, dissected it using case analysis and changed relevant parts.
And an example client: ------------------------------------- {-# LANGUAGE TemplateHaskell #-}
import T
$(mkNewType "A") ------------------------------------- It all work together.
I studied how to use Template Haskell that way: I obtained declarations of what I need, printed them and looked through documentation for relevant data types and constructors. It's not harder that any other library in Haskell, actually. _______________________________________________ Haskell-Cafe mailing list Haskell-C...@haskell.orghttp://www.haskell.org/mailman/listinfo/haskell-cafe
_______________________________________________ Haskell-Cafe mailing list Haskell-C...@haskell.orghttp://www.haskell.org/mailman/listinfo/haskell-cafe
Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

OK, thanks for everyone's help!
Serguey's code works very well now.
Kevin
On Sep 14, 6:14 pm, Erik Hesselink
Yes, if you use template haskell, all top level functions and values have to be defined before you use them.
Erik
On Tue, Sep 14, 2010 at 18:11, Kevin Jardine
wrote: Hmm - It seems to work if the code is defined before my main function and not after it.
Does this have to do with TH being part of the compile process and so the order matters?
Kevin
On Sep 14, 6:03 pm, Kevin Jardine
wrote: Thanks Serguey!
The library code compiles, but when I try to use it in client code:
a. I get:
Not in scope: type constructor or class 'A'
and even stranger,
b. GHC cannot find any of my code after the
$(mkNewType "A")
and claims that all the functions I defined there are also not in scope.
Any ideas?
The CPP solution works but Template Haskell is definitely cooler, so it would be great to get this to work!
Kevin
On Sep 14, 2:29 pm, Zefirov
wrote: 2010/9/14 Kevin Jardine
: I would like to use some macro system (perhaps Template Haskell?) to reduce this to something like
defObj MyType
I've read through some Template Haskell documentation and examples, but I find it intimidatingly hard to follow. Does anyone has some code suggestions or pointers to something similar?
The solutions first: ------------------------------------------------- {-# LANGUAGE TemplateHaskell #-}
module T(mkNewType) where
import Language.Haskell.TH
decls = [d|newtype TempDecl = TempDecl Int deriving (Eq,Ord,Show)|] decl = do [d] <- decls runIO $ print d -- just to show inetrnals return d
mkNewType :: String -> Q [Dec] mkNewType n = do d <- decl let name = mkName n return $ (\x -> [x]) $ case d of (NewtypeD cxt _ argvars (NormalC _ args) derivings) -> NewtypeD cxt name argvars (NormalC name args) derivings -------------------------------------- I took perfectly valid declaration, dissected it using case analysis and changed relevant parts.
And an example client: ------------------------------------- {-# LANGUAGE TemplateHaskell #-}
import T
$(mkNewType "A") ------------------------------------- It all work together.
I studied how to use Template Haskell that way: I obtained declarations of what I need, printed them and looked through documentation for relevant data types and constructors. It's not harder that any other library in Haskell, actually. _______________________________________________ Haskell-Cafe mailing list Haskell-C...@haskell.orghttp://www.haskell.org/mailman/listinfo/haskell-cafe
_______________________________________________ Haskell-Cafe mailing list Haskell-C...@haskell.orghttp://www.haskell.org/mailman/listinfo/haskell-cafe
Haskell-Cafe mailing list Haskell-C...@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
_______________________________________________ Haskell-Cafe mailing list Haskell-C...@haskell.orghttp://www.haskell.org/mailman/listinfo/haskell-cafe

On Tue, Sep 14, 2010 at 01:24:16AM -0700, Kevin Jardine wrote:
I have a set of wrapper newtypes that are always of the same format:
newtype MyType = MyType Obj deriving (A,B,C,D)
where Obj, A, B, C, and D are always the same. Only MyType varies.
A, B, C, and D are automagically derived by GHC using the
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
feature.
I would like to use some macro system (perhaps Template Haskell?) to reduce this to something like
defObj MyType
How about the straightforward?
{-# LANGUAGE CPP #-} #define defObj(t) newtype t = t Obj deriving (A,B,C,D)
defObj(Foo) defObj(Bar) ....
It has the advantage of being (de facto) portable. John -- John Meacham - ⑆repetae.net⑆john⑈ - http://notanumber.net/

Hi John,
That's what I had originally. However, some people have made critical
comments about CPP macros on this list and I thought that TH was
considered the better option.
What do other people think?
Serguey's code is great in any case as it gives me a clearer
understanding on how TH works.
Kevin
On Sep 14, 11:01 pm, John Meacham
On Tue, Sep 14, 2010 at 01:24:16AM -0700, Kevin Jardine wrote:
I have a set of wrapper newtypes that are always of the same format:
newtype MyType = MyType Obj deriving (A,B,C,D)
where Obj, A, B, C, and D are always the same. Only MyType varies.
A, B, C, and D are automagically derived by GHC using the
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
feature.
I would like to use some macro system (perhaps Template Haskell?) to reduce this to something like
defObj MyType
How about the straightforward?
{-# LANGUAGE CPP #-} #define defObj(t) newtype t = t Obj deriving (A,B,C,D)
defObj(Foo) defObj(Bar) ....
It has the advantage of being (de facto) portable.
John
-- John Meacham - ⑆repetae.net⑆john⑈ -http://notanumber.net/ _______________________________________________ Haskell-Cafe mailing list Haskell-C...@haskell.orghttp://www.haskell.org/mailman/listinfo/haskell-cafe

That's what I had originally. However, some people have made critical comments about CPP macros on this list and I thought that TH was considered the better option.
I was one of those people advising against the use of CPP macros. However, Template Haskell is ghc-only, and is unlikely ever to be implemented by any other Haskell compiler. Thus CPP, for all its faults, may be the better solution here, simply because it is portable. (I also note in passing that ghc's core libraries themselves use exactly this kind of CPP macro to generate lots of tedious boilerplate.) Regards, Malcolm

Hi Malcolm,
In this case, I am counting on GHC's
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
feature to derive the instances for the classes I am including in the
deriving clause.
So perhaps portability is not a big issue here in any case.
I do think that
defObj(MyType)
looks a bit cleaner than
$(defObj "MyType")
so I am starting to lean back towards the CPP solution after all.
CPP is not always the best option, but perhaps it is in this case.
Kevin
On Sep 15, 10:31 am, Malcolm Wallace
That's what I had originally. However, some people have made critical comments about CPP macros on this list and I thought that TH was considered the better option.
I was one of those people advising against the use of CPP macros. However, Template Haskell is ghc-only, and is unlikely ever to be implemented by any other Haskell compiler. Thus CPP, for all its faults, may be the better solution here, simply because it is portable.
(I also note in passing that ghc's core libraries themselves use exactly this kind of CPP macro to generate lots of tedious boilerplate.)
Regards, Malcolm
_______________________________________________ Haskell-Cafe mailing list Haskell-C...@haskell.orghttp://www.haskell.org/mailman/listinfo/haskell-cafe

Hi Ben,
Good point! I can confirm that it does compile under GHC 6.12.
So really the same number of characters either way.
Kevin
On Sep 15, 4:49 pm, Ben Millwood
On Wed, Sep 15, 2010 at 2:11 PM, Kevin Jardine
wrote: I do think that
defObj(MyType)
looks a bit cleaner than
$(defObj "MyType")
I believe as of GHC 6.12 you no longer need the $() around top-level splices. So that would just be:
defObj "MyType" _______________________________________________ Haskell-Cafe mailing list Haskell-C...@haskell.orghttp://www.haskell.org/mailman/listinfo/haskell-cafe

On 9/15/10 9:11 AM, Kevin Jardine wrote:
Hi Malcolm,
In this case, I am counting on GHC's
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
feature to derive the instances for the classes I am including in the deriving clause.
So perhaps portability is not a big issue here in any case.
Yes, but GND is a feature that would not be terribly difficult to add to another compiler. That it is GHC-only today is only because other compilers have bigger fish to fry. Implementing TH, on the other hand, is a major undertaking and doesn't look like it will be reimplemented anytime soon. -- Live well, ~wren

It has been - there is a package called 'zeroth' on hackage.
It only works for top-level splices, the last I looked.
On Sep 15, 2010 11:20 AM, "Gregory Crosswhite"
On 9/15/10 1:31 AM, Malcolm Wallace wrote:
[...] However, Template Haskell is ghc-only, and is unlikely ever to be implemented by any other Haskell compiler. [...]
Could it be implemented as a separate preprocessor?
Cheers, Greg
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

#define defObj(t) newtype t = t Obj deriving (A,B,C,D)
Blasphemy! :)
On 14 September 2010 23:01, John Meacham
On Tue, Sep 14, 2010 at 01:24:16AM -0700, Kevin Jardine wrote:
I have a set of wrapper newtypes that are always of the same format:
newtype MyType = MyType Obj deriving (A,B,C,D)
where Obj, A, B, C, and D are always the same. Only MyType varies.
A, B, C, and D are automagically derived by GHC using the
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
feature.
I would like to use some macro system (perhaps Template Haskell?) to reduce this to something like
defObj MyType
How about the straightforward?
{-# LANGUAGE CPP #-} #define defObj(t) newtype t = t Obj deriving (A,B,C,D)
defObj(Foo) defObj(Bar) ....
It has the advantage of being (de facto) portable.
John
-- John Meacham - ⑆repetae.net⑆john⑈ - http://notanumber.net/ _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
participants (12)
-
Antoine Latter
-
Ben Millwood
-
Erik Hesselink
-
Gregory Crosswhite
-
John Meacham
-
Jonas Almström Duregård
-
Kevin Jardine
-
Malcolm Wallace
-
Miguel Mitrofanov
-
Sean Leather
-
Serguey Zefirov
-
wren ng thornton