Traversable can't be derived for datatypes with unboxed arguments
Unlike Functor
and Foldable
, Traversable
cannot be derived for datatypes that contain arguments with unboxed types. A simple example:
{-# LANGUAGE DeriveTraversable, MagicHash #-}
import GHC.Prim (Int#)
data IntHash a = IntHash Int# deriving (Functor, Foldable, Traversable)
The generated Traversable
instance reveals the issue:
instance Traversable IntHash where
traverse f (IntHash a1) = fmap IntHash (pure a1)
Couldn't match kind `*' with `#'
When matching types
a0 :: *
Int# :: #
Expected type: a0 -> IntHash b
Actual type: Int# -> IntHash b
In the first argument of `fmap', namely `IntHash'
In the expression: fmap IntHash (pure a1)
When typechecking the code for `traverse'
in a derived instance for `Traversable IntHash':
To see the code I am typechecking, use -ddump-deriv
We have to avoid calling pure
on a1
, since pure
expects an argument with a *
-kinded type, not a #
-kinded one.
One way to fix this would be restructuring the derived traverse
implementation such that arguments which do not mention the last type parameter are moved to the function initially lifted with pure
, and doing nothing with them later. To better articulate what I mean, envision something like this:
data IntHash2 a = IntHash2 Int# a (IntHash2 a) Int deriving (Functor, Foldable)
Then a derived Traversable
instance that would type-check (and kind-check) would be:
instance Traversable IntHash2 where
traverse f (IntHash2 a1 a2 a3 a4) =
pure (\x2 x3 -> IntHash2 a1 x2 x3 a4) <*> f a2 <*> traverse f a3
Conceptually, this doesn't sound hard to implement. The tricky part is figuring out how much of the existing Functor
/Foldable
/Traversable
deriving machinery would need to be tweaked to make this work.