7.5. Extensions to the "deriving" mechanism

7.5.1. Inferred context for deriving clauses

The Haskell Report is vague about exactly when a deriving clause is legal. For example:

  data T0 f a = MkT0 a         deriving( Eq )
  data T1 f a = MkT1 (f a)     deriving( Eq )
  data T2 f a = MkT2 (f (f a)) deriving( Eq )

The natural generated Eq code would result in these instance declarations:

  instance Eq a         => Eq (T0 f a) where ...
  instance Eq (f a)     => Eq (T1 f a) where ...
  instance Eq (f (f a)) => Eq (T2 f a) where ...

The first of these is obviously fine. The second is still fine, although less obviously. The third is not Haskell 98, and risks losing termination of instances.

GHC takes a conservative position: it accepts the first two, but not the third. The rule is this: each constraint in the inferred instance context must consist only of type variables, with no repetitions.

This rule is applied regardless of flags. If you want a more exotic context, you can write it yourself, using the standalone deriving mechanism.

7.5.2. Stand-alone deriving declarations

GHC now allows stand-alone deriving declarations, enabled by -XStandaloneDeriving:

  data Foo a = Bar a | Baz String

  deriving instance Eq a => Eq (Foo a)

The syntax is identical to that of an ordinary instance declaration apart from (a) the keyword deriving, and (b) the absence of the where part.

However, standalone deriving differs from a deriving clause in a number of important ways:

  • The standalone deriving declaration does not need to be in the same module as the data type declaration. (But be aware of the dangers of orphan instances (Section 4.7.13, “Orphan modules and instance declarations”).

  • You must supply an explicit context (in the example the context is (Eq a)), exactly as you would in an ordinary instance declaration. (In contrast, in a deriving clause attached to a data type declaration, the context is inferred.)

  • Unlike a deriving declaration attached to a data declaration, the instance can be more specific than the data type (assuming you also use -XFlexibleInstances, Section 7.6.3.3, “Relaxed rules for instance contexts”). Consider for example

      data Foo a = Bar a | Baz String
    
      deriving instance Eq a => Eq (Foo [a])
      deriving instance Eq a => Eq (Foo (Maybe a))
    

    This will generate a derived instance for (Foo [a]) and (Foo (Maybe a)), but other types such as (Foo (Int,Bool)) will not be an instance of Eq.

  • Unlike a deriving declaration attached to a data declaration, GHC does not restrict the form of the data type. Instead, GHC simply generates the appropriate boilerplate code for the specified class, and typechecks it. If there is a type error, it is your problem. (GHC will show you the offending code if it has a type error.)

    The merit of this is that you can derive instances for GADTs and other exotic data types, providing only that the boilerplate code does indeed typecheck. For example:

      data T a where
         T1 :: T Int
         T2 :: T Bool
    
      deriving instance Show (T a)
    

    In this example, you cannot say ... deriving( Show ) on the data type declaration for T, because T is a GADT, but you can generate the instance declaration using stand-alone deriving.

    The down-side is that, if the boilerplate code fails to typecheck, you will get an error message about that code, which you did not write. Whereas, with a deriving clause the side-conditions are necessarily more conservative, but any error message may be more comprehensible.

In other ways, however, a standalone deriving obeys the same rules as ordinary deriving:

  • A deriving instance declaration must obey the same rules concerning form and termination as ordinary instance declarations, controlled by the same flags; see Section 7.6.3, “Instance declarations”.

  • The stand-alone syntax is generalised for newtypes in exactly the same way that ordinary deriving clauses are generalised (Section 7.5.5, “Generalised derived instances for newtypes”). For example:

      newtype Foo a = MkFoo (State Int a)
    
      deriving instance MonadState Int Foo
    

    GHC always treats the last parameter of the instance (Foo in this example) as the type whose instance is being derived.

7.5.3. Deriving instances of extra classes (Data, etc)

Haskell 98 allows the programmer to add "deriving( Eq, Ord )" to a data type declaration, to generate a standard instance declaration for classes specified in the deriving clause. In Haskell 98, the only classes that may appear in the deriving clause are the standard classes Eq, Ord, Enum, Ix, Bounded, Read, and Show.

GHC extends this list with several more classes that may be automatically derived:

  • With -XDeriveGeneric, you can derive instances of the classes Generic and Generic1, defined in GHC.Generics. You can use these to define generic functions, as described in Section 7.26, “Generic programming”.

  • With -XDeriveFunctor, you can derive instances of the class Functor, defined in GHC.Base.

  • With -XDeriveDataTypeable, you can derive instances of the class Data, defined in Data.Data. See Section 7.5.4, “Deriving Typeable instances” for deriving Typeable.

  • With -XDeriveFoldable, you can derive instances of the class Foldable, defined in Data.Foldable.

  • With -XDeriveTraversable, you can derive instances of the class Traversable, defined in Data.Traversable. Since the Traversable instance dictates the instances of Functor and Foldable, you'll probably want to derive them too, so -XDeriveTraversable implies -XDeriveFunctor and -XDeriveFoldable.

You can also use a standalone deriving declaration instead (see Section 7.5.2, “Stand-alone deriving declarations”).

In each case the appropriate class must be in scope before it can be mentioned in the deriving clause.

7.5.4. Deriving Typeable instances

The class Typeable is very special:

  • Typeable is kind-polymorphic (see Section 7.8, “Kind polymorphism”).

  • GHC has a custom solver for discharging constraints that involve class Typeable, and handwritten instances are forbidden. This ensures that the programmer cannot subert the type system by writing bogus instances.

  • Derived instances of Typeable are ignored, and may be reported as an error in a later version of the compiler.

  • The rules for solving `Typeable` constraints are as follows:

    • A concrete type constructor applied to some types.

      instance (Typeable t1, .., Typeable t_n) =>
        Typeable (T t1 .. t_n)
      

      This rule works for any concrete type constructor, including type constructors with polymorhic kinds. The only restriction is that if the type constructor has a polymorhic kind, then it has to be applied to all of its kinds parameters, and these kinds need to be concrete (i.e., they cannot mention kind variables).

    • A type variable applied to some types.
      instance (Typeable f, Typeable t1, .., Typeable t_n) =>
        Typeable (f t1 .. t_n)
      

    • A concrete type literal.
      instance Typeable 0       -- Type natural literals
      instance Typeable "Hello" -- Type-level symbols
      

7.5.5. Generalised derived instances for newtypes

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!

7.5.5.1.  Generalising the deriving clause

GHC now permits such instances to be derived instead, using the flag -XGeneralizedNewtypeDeriving, 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.

7.5.5.2.  A more precise specification

A derived instance is derived only for declarations of these forms (after expansion of any type synonyms)

  newtype T v1..vn                   = MkT (t vk+1..vn) deriving (C t1..tj)
  newtype instance T s1..sk vk+1..vn = MkT (t vk+1..vn) deriving (C t1..tj)

where

  • v1..vn are type variables, and t, s1..sk, t1..tj are types.

  • The (C t1..tj) is a partial applications of the class C, where the arity of C is exactly j+1. That is, C lacks exactly one type argument.

  • k is chosen so that C t1..tj (T v1...vk) is well-kinded. (Or, in the case of a data instance, so that C t1..tj (T s1..sk) is well kinded.)

  • The type t is an arbitrary type.

  • The type variables vk+1...vn do not occur in the types t, s1..sk, or t1..tj.

  • C is not Read, Show, Typeable, or Data. These classes should not "look through" the type or its constructor. You can still derive these classes for a newtype, but it happens in the usual way, not via this new mechanism.

  • It is safe to coerce each of the methods of C. That is, the missing last argument to C is not used at a nominal role in any of the C's methods. (See Section 7.27, “Roles ”.)

Then the derived instance is of form declaration is:

  instance C t1..tj t => C t1..tj (T v1...vk)

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.

Lastly, all of this applies only for classes other than Read, Show, Typeable, and Data, for which the built-in derivation applies (section 4.3.3. of the Haskell Report). (For the standard classes Eq, Ord, Ix, and Bounded it is immaterial whether the standard method is used or the one described here.)

7.5.6. Deriving any other class

With -XDeriveAnyClass you can derive any other class. The compiler will simply generate an empty instance. The instance context will be generated according to the same rules used when deriving Eq. This is mostly useful in classes whose minimal set is empty, and especially when writing generic functions. In case you try to derive some class on a newtype, and -XGeneralizedNewtypeDeriving is also on, -XDeriveAnyClass takes precedence.