Generalised deriving for newtype
Brief Explanation
The deriving
clause on a newtype
can list any class. For any class except Read
, Show
, Typeable
or Data
, the instance is "the same" as for the wrapped type.
There are restrictions on the syntactic form of the newtype
, and this mechanism also cannot be used with recursive newtypes.
Examples
one area where this is particularly useful is when dealing with monad transformers. for example the jhc typechecking monad is declared as follows
data TcEnv = TcEnv { ... }
newtype TI a = TI (ReaderT TcEnv IO a)
deriving(Monad,MonadFix,MonadIO,MonadReader TcEnv,Functor)
and we end up with a complete monad with every interesting instance defined for free.
It is also good for selectively hiding properties of monad transformers
-- | Unique integer generator monad transformer.
newtype UniqT m a = UniqT (StateT Int m a)
deriving(Monad,MonadTrans, Functor, MonadFix, MonadPlus)
notice that while it uses a state transformer internally, the MonadState? class is intentionally left out of the deriving clause. this means that calls to the state monad will pass through the UniqT making stacking monads signifigantly easier.
A quick survey shows 34 different special purpose monads created in this fashion in jhc. This technique would not be possible without newtype deriving.
References
- Generalised derived instances for newtypes in the GHC User's Guide
Tickets
#22 | create DerivedInstances proposal |
---|---|
#52 | Generalised deriving for newtype |
Pros
- saves on repetitious boilerplate, significantly lowering the cost of
newtype
Cons
- difficult to specify without saying "the same representation" ( first attempt)
- difficult interactions with Type Families and GADTs, see http://hackage.haskell.org/trac/ghc/ticket/1496
Other Issues
- interaction with FlexibleInstances: whether we have FlexibleInstances or not affects which newtype derivings are possible.
Comment
This proposal would make newtypes a bit more like type synonyms since they can be made to inherit properties of the underlying type, albeit (usefully) selectively. Having both type synonyms and newtype is a bit confusing, and the more alike they are, the more confusing it is. I guess looking for a single replacement is not an option for Haskell', but at least we should consider if automatic derivation for newtypes does not supersede TypeSynonymInstances as it would make it significantly less tiresome to introduce a newtype for purposes of abbreviation.
Deriving Instances for Multi-Parameter Classes
The current implementation (GHC 6.8.2) of newtype
deriving supports multi-parameter classes but only as long as the newly defined type is the last parameter to the class. It would be nice to lift this restriction. Here is an example:
class C a b where ...
instance C Int Char where ...
newtype T1 = T1 Char deriving (C Int) -- OK
newtype T2 = T2 Int deriving (C _ Char) -- not OK
It would be nice if both of these worked. The expectation is that the compiler will generate instances like the following:
instance C Int T1 where ... reuse C Int Char ...
instance C T2 Char where ... reuse C Int Char ...
The main new bit is the _
in the deriving clause. It marks the position of the (possibly applied) newly defined type in the dervied instance. If an underscore is not present, then it is assumed to be at the end of the parameter list for the predicate. This makes this extension backward compatible.