
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