When you define an abstract type using newtype, you may want
the new type to inherit some instances from its representation. In
Haskell 98, you can inherit instances of Eq, Ord,
Enum and Bounded by deriving them, but for any
other classes you have to write an explicit instance declaration. For
example, if you define
newtype Dollars = Dollars Int |
and you want to use arithmetic on
Dollars, you have to
explicitly define an instance of
Num:
instance Num Dollars where
Dollars a + Dollars b = Dollars (a+b)
... |
All the instance does is apply and remove the
newtype
constructor. It is particularly galling that, since the constructor
doesn't appear at run-time, this instance declaration defines a
dictionary which is
wholly equivalent to the
Int
dictionary, only slower!
GHC now permits such instances to be derived instead, so one can write
newtype Dollars = Dollars Int deriving (Eq,Show,Num) |
and the implementation uses the
same Num dictionary
for
Dollars as for
Int. Notionally, the compiler
derives an instance declaration of the form
instance Num Int => Num Dollars |
which just adds or removes the
newtype constructor according to the type.
We can also derive instances of constructor classes in a similar
way. For example, suppose we have implemented state and failure monad
transformers, such that
instance Monad m => Monad (State s m)
instance Monad m => Monad (Failure m) |
In Haskell 98, we can define a parsing monad by
type Parser tok m a = State [tok] (Failure m) a |
which is automatically a monad thanks to the instance declarations
above. With the extension, we can make the parser type abstract,
without needing to write an instance of class
Monad, via
newtype Parser tok m a = Parser (State [tok] (Failure m) a)
deriving Monad |
In this case the derived instance declaration is of the form
instance Monad (State [tok] (Failure m)) => Monad (Parser tok m) |
Notice that, since
Monad is a constructor class, the
instance is a
partial application of the new type, not the
entire left hand side. We can imagine that the type declaration is
``eta-converted'' to generate the context of the instance
declaration.
We can even derive instances of multi-parameter classes, provided the
newtype is the last class parameter. In this case, a ``partial
application'' of the class appears in the deriving
clause. For example, given the class
class StateMonad s m | m -> s where ...
instance Monad m => StateMonad s (State s m) where ... |
then we can derive an instance of
StateMonad for
Parsers by
newtype Parser tok m a = Parser (State [tok] (Failure m) a)
deriving (Monad, StateMonad [tok]) |
The derived instance is obtained by completing the application of the
class to the new type:
instance StateMonad [tok] (State [tok] (Failure m)) =>
StateMonad [tok] (Parser tok m) |
As a result of this extension, all derived instances in newtype
declarations are treated uniformly (and implemented just by reusing
the dictionary for the representation type), except
Show and Read, which really behave differently for
the newtype and its representation.
Derived instance declarations are constructed as follows. Consider the
declaration (after expansion of any type synonyms)
newtype T v1...vn = T' (S t1...tk vk+1...vn) deriving (c1...cm) |
where
S is a type constructor,
t1...tk are
types,
vk+1...vn are type variables which do not occur in any of
the
ti, and the
ci are partial applications of
classes of the form
C t1'...tj'. The derived instance
declarations are, for each
ci,
instance ci (S t1...tk vk+1...v) => ci (T v1...vp) |
where
p is chosen so that
T v1...vp is of the
right
kind for the last parameter of class
Ci.
As an example which does not work, consider
newtype NonMonad m s = NonMonad (State s m s) deriving Monad |
Here we cannot derive the instance
instance Monad (State s m) => Monad (NonMonad m) |
because the type variable
s occurs in
State s m,
and so cannot be "eta-converted" away. It is a good thing that this
deriving clause is rejected, because
NonMonad m is
not, in fact, a monad --- for the same reason. Try defining
>>= with the correct type: you won't be able to.
Notice also that the order of class parameters becomes
important, since we can only derive instances for the last one. If the
StateMonad class above were instead defined as
class StateMonad m s | m -> s where ... |
then we would not have been able to derive an instance for the
Parser type above. We hypothesise that multi-parameter
classes usually have one "main" parameter for which deriving new
instances is most interesting.