Code generated by GND/DerivingVia should use InstanceSigs
If you compile this code:
{-# LANGUAGE DerivingStrategies #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# OPTIONS_GHC -ddump-deriv #-}
module Foo where
newtype T f a = MkT (f a) deriving newtype Functor
You'll get this:
$ /opt/ghc/8.8.3/bin/ghci Foo.hs
GHCi, version 8.8.3: https://www.haskell.org/ghc/ :? for help
Loaded GHCi configuration from /home/rgscott/.ghci
[1 of 1] Compiling Foo ( Foo.hs, interpreted )
==================== Derived instances ====================
Derived class instances:
instance GHC.Base.Functor f => GHC.Base.Functor (Foo.T f) where
GHC.Base.fmap
= GHC.Prim.coerce
@((a -> b) -> f a -> f b)
@((a -> b) -> Foo.T f a -> Foo.T f b)
(GHC.Base.fmap @f) ::
forall (a :: TYPE GHC.Types.LiftedRep)
(b :: TYPE GHC.Types.LiftedRep).
(a -> b) -> Foo.T f a -> Foo.T f b
(GHC.Base.<$)
= GHC.Prim.coerce
@(a -> f b -> f a)
@(a -> Foo.T f b -> Foo.T f a)
((GHC.Base.<$) @f) ::
forall (a :: TYPE GHC.Types.LiftedRep)
(b :: TYPE GHC.Types.LiftedRep).
a -> Foo.T f b -> Foo.T f a
Derived type family instances:
This works, but it's a bit difficult to read due to the expression signatures
cluttering up the code on the right-hand sides of each equation. Why not
generate code with InstanceSigs
instead?
instance GHC.Base.Functor f => GHC.Base.Functor (Foo.T f) where
GHC.Base.fmap ::
forall (a :: TYPE GHC.Types.LiftedRep)
(b :: TYPE GHC.Types.LiftedRep).
(a -> b) -> Foo.T f a -> Foo.T f b
GHC.Base.fmap
= GHC.Prim.coerce
@((a -> b) -> f a -> f b)
@((a -> b) -> Foo.T f a -> Foo.T f b)
(GHC.Base.fmap @f)
(GHC.Base.<$) ::
forall (a :: TYPE GHC.Types.LiftedRep)
(b :: TYPE GHC.Types.LiftedRep).
a -> Foo.T f b -> Foo.T f a
(GHC.Base.<$)
= GHC.Prim.coerce
@(a -> f b -> f a)
@(a -> Foo.T f b -> Foo.T f a)
((GHC.Base.<$) @f)
This is certainly much nicer to read. But besides making the output of
-ddump-deriv
look prettier, there is a user-facing benefit to
this idea: it will improve the quality of certain error messages. Consider
GHC's T15073
test case, which requires two files:
{-# LANGUAGE UnboxedTuples #-}
module T15073a where
class P a where
p :: a -> (# a #)
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE DataKinds, PolyKinds #-}
module T15073 where
import T15073a
newtype Foo a = MkFoo a
deriving P
Compiling T15073
with GHC 8.8.3 will give a rather long-winded error message:
$ /opt/ghc/8.8.3/bin/ghc T15073.hs
[1 of 2] Compiling T15073a ( T15073a.hs, T15073a.o )
[2 of 2] Compiling T15073 ( T15073.hs, T15073.o )
T15073.hs:8:12: error:
• Illegal unboxed tuple type as function argument: (# Foo a #)
Perhaps you intended to use UnboxedTuples
• In an expression type signature:
Foo a -> Unit# @GHC.Types.LiftedRep (Foo a)
In the expression:
GHC.Prim.coerce
@(a -> Unit# @GHC.Types.LiftedRep a)
@(Foo a -> Unit# @GHC.Types.LiftedRep (Foo a))
(p @a) ::
Foo a -> Unit# @GHC.Types.LiftedRep (Foo a)
In an equation for ‘p’:
p = GHC.Prim.coerce
@(a -> Unit# @GHC.Types.LiftedRep a)
@(Foo a -> Unit# @GHC.Types.LiftedRep (Foo a))
(p @a) ::
Foo a -> Unit# @GHC.Types.LiftedRep (Foo a)
When typechecking the code for ‘p’
in a derived instance for ‘P (Foo a)’:
To see the code I am typechecking, use -ddump-deriv
|
8 | deriving P
| ^
This is because the offending type ((# Foo a #)
) is nested deep within an expression signature. On the other hand, if we made GeneralizedNewtypeDeriving
generate an instance signature for the derived p
implementation, then the error message is much more direct:
$ /opt/ghc/8.8.3/bin/ghc T15073.hs
[1 of 2] Compiling T15073a ( T15073a.hs, T15073a.o )
[2 of 2] Compiling T15073 ( T15073.hs, T15073.o )
T15073.hs:8:12: error:
• Illegal unboxed tuple type as function argument: (# Foo a #)
Perhaps you intended to use UnboxedTuples
• In the type signature:
p :: Foo a -> Unit# @GHC.Types.LiftedRep (Foo a)
When typechecking the code for ‘p’
in a derived instance for ‘P (Foo a)’:
To see the code I am typechecking, use -ddump-deriv
In the instance declaration for ‘P (Foo a)’
|
8 | deriving P
| ^
Now the error message is localized entirely to p
's instance signature, side-stepping the need to mention p = coerce ...
entirely.
I originally pondered implementing this idea back in #15290 (comment 155370), but I never figured out how to insert InstanceSigs
using the GHC API. I've finally got it working at
https://gitlab.haskell.org/RyanGlScott/ghc/tree/wip/instance-sigs-gnd, thankfully, so I can prepare a patch if this sounds agreeable.