[Haskell-cafe] Combining RequiredTypeArguments and type class methods?
Tom Ellis
tom-lists-haskell-cafe-2023 at jaguarpaw.co.uk
Sun Jul 13 10:47:36 UTC 2025
On Sun, Jul 13, 2025 at 04:03:08PM +1000, Viktor Dukhovni wrote:
> The user guide documentation of RequiredTypeArguments highlights a
> hypothetical alternative to the interface of the `sizeOf` method of
> the Storable class:
>
> sizeOf :: forall a -> Storable a => Int
>
> This is fine in isolation, but how would this actually work in a type
> class method definition?
>
> Is the hypothetical `sizeOf` actually realisable as a type class method?
> Or can it only be a module-level wrapper? Something like the below,
> which does work?
Yeah, there's definitely something that doesn't quite work with
RequiredTypeArguments and type class methods. After all, the type of a
type class `C` is implicitly prefixed with `forall a. C a =>`, so you
can't add your own `forall a ->`. It would shadow.
There is, however, a known trick. This works:
{-# LANGUAGE AllowAmbiguousTypes #-}
{-# LANGUAGE RequiredTypeArguments #-}
class MyStorable a where
sizeOf :: forall b -> b ~ a => (MyStorable a) => Int
instance MyStorable Bool where
sizeOf (type Bool) = 1
(But I prefer your solution: the wrapper.)
Tom
More information about the Haskell-Cafe
mailing list