 
            Ryan If you compile newtype Compose f g a = Compose (f (g a)) deriving( Generic1 ) and do –show-iface on the resulting hi file, you’ll see $fGeneric1Compose :: forall (f :: * -> *) k (g :: k -> *). Functor f => Generic1 (Compose f g) I was expecting to see $fGeneric1Compose :: forall (f :: k1 -> *) k (g :: k -> k1). (..something..) => Generic1 (Compose f g) Otherwise the Generic1 instance only works if its first argument has kind (* -> *). Is that the intention? Maybe so… Simon
 
            This is a consequence of the way GHC generics represents datatypes
that compose functor-like types in this fashion. If you compile that
code with -ddump-deriv, you'll see that the Rep1 for Compose is (in
abbreviated form):
    type Rep1 (Compose f g) = ... (f :.: Rec1 g)
where (:.:) is defined as [1]:
    newtype (:.:) (f :: k2 -> *) (g :: k1 -> k2) (p :: k1) = Comp1 (f (g p))
In other words, we must kind-check the type (f (Rec1 g p)). But Rec1
is a datatype, so it must have result kind *. Therefore, the kind of f
is forced to be (* -> *). I describe this in a Note here [2].
This feels like a somewhat fundamental consequence of using datatypes
to abstract over a datatype's structure, so I'm not aware of a way
around this. Luckily, the kind of g is still (k -> *), which was the
main goal of Trac #10604 [3].
Ryan S.
-----
[1] http://git.haskell.org/ghc.git/blob/0676e68cf5fe8696f1f760fef0f35dba14db1104...
[2] http://git.haskell.org/ghc.git/blob/0676e68cf5fe8696f1f760fef0f35dba14db1104...
[3] https://ghc.haskell.org/trac/ghc/ticket/10604
On Wed, Jun 1, 2016 at 10:55 AM, Simon Peyton Jones
Ryan
If you compile
newtype Compose f g a = Compose (f (g a)) deriving( Generic1 )
and do –show-iface on the resulting hi file, you’ll see
$fGeneric1Compose ::
forall (f :: * -> *) k (g :: k -> *).
Functor f =>
Generic1 (Compose f g)
I was expecting to see
$fGeneric1Compose ::
forall (f :: k1 -> *) k (g :: k -> k1).
(..something..) =>
Generic1 (Compose f g)
Otherwise the Generic1 instance only works if its first argument has kind (* -> *).
Is that the intention? Maybe so…
Simon
participants (2)
- 
                 Ryan Scott Ryan Scott
- 
                 Simon Peyton Jones Simon Peyton Jones