
The Trac page for 'Generalised deriving for newtype' remarks that it is 'difficult to specify without saying "the same representation"'. I assume that no one has tried yet, so I'll take a shot at it. Say we have a declaration of the form:
class C a where x :: T a -- any type that can contain a ..
-- instance declaration, can also be more general instance Ctx p => C (OldT p) where x = .. ..
newtype NewT p = Constr (OldT p) deriving C
Where p can be any number of type variables and Ctx is a context depending on them. The instance for C NewT can be derived with the following algorithm. The new instance declaration will be:
instance Ctx b => C (NewT b) where x = wrap_T (x :: T a) ..
Now the details of the wrap function depend on the type T. There are four cases: 1. If T is a type not containg a, i.e. > type T a = T' then define: > wrap_T x = x > unwrap_T x = x 2. If T is exactly the type a, possible applied to arguments: > type T a = a or > type T a = a b .. then define: > wrap_T x = Constr x > unwrap_T x = case x of (Constr x') -> x' 3. If T is a function type: > type T a = T1 a -> T2 a then define > wrap_T f = \arg -> wrap_T2 (f (unwrap_T1 arg)) > unwrap_T f = \arg -> unwrap_T2 (f (wrap_T1 arg)) 4. If T is an abstract data type: > data T a = C1 (T1 a) .. > | .. then define: > wrap_T x = case x of > (C1 x1 ..) -> C1 (wrap_T1 x1) .. > .. > unwrap_T x = case x of > (C1 x1 ..) -> C1 (unwrap_T1 x1) .. > .. With an alternative for each constructor of T. All these wrap/unwrap functions are specific for the type NewT and the definition x. The T in wrap_T should be read as a subscript where T is the actual type, and not as a value named "wrap_T". '..' stands for a repetition of the same principle. Here is also an example from the wiki page:
-- | Unique integer generator monad transformer. newtype UniqT m a = UniqT (StateT Int m a) deriving Monad
The class is:
class Monad m where (>>=) :: m a -> (a -> m b) -> m b ..
There is an instance:
instance Monad m => Monad (StateT s m)
Now the newtype declaration desugars to (using wr_T for wrap_T and un_T for unwrap_T):
newtype UniqT m a = UniqT (StateT Int m a)
instance Monad m => Monad (UniqT m a) where (>>=) = w (>>= :: StateT Int m a) where wr_T f = \arg -> wr_T2 (f (un_T1 arg)) -- m a -> (a -> m b) -> m b un_T1 x = case x of (UniqT x') -> x' -- m a wr_T2 f = \arg -> wr_T4 (f (un_T3 arg)) -- (a -> m b) -> m b un_T3 f = \arg -> un_T6 (f (wr_T5 arg)) -- a -> m b wr_T4 x = UniqT x -- m b wr_T5 x = x -- a un_T6 x = case x of (UniqT x') -> x' -- m b
Cleaning up leads to:
instance Monad m => Monad (UniqT m a) where wr_T = \(UniqT a0) a2 -> UniqT (a0 >>= ( \a3 -> case (a2 a3) of (UniqT x') -> x' ))
Which is essentially the same as what the programmer would have written himself. Twan