[Haskell-cafe] Combining RequiredTypeArguments and type class methods?
Viktor Dukhovni
ietf-dane at dukhovni.org
Sun Jul 13 06:03:08 UTC 2025
The user guide documentation of RequiredTypeArguments highlights a
hypothetical alternative to the interface of the `sizeOf` method of
the Storable class:
https://downloads.haskell.org/ghc/9.12.2/docs/users_guide/exts/required_type_arguments.html#relation-to-typeapplications
sizeOf :: forall a -> Storable a => Int
If sizeOf had this type, we could write sizeOf Bool without passing a
dummy value.
This is fine in isolation, but how would this actually work in a type
class method definition? The below naïve attempt does not work:
{-# LANGUAGE AllowAmbiguousTypes #-}
{-# LANGUAGE RequiredTypeArguments #-}
class MyStorable a where
sizeOf :: forall a -> MyStorable a => Int
instance MyStorable Bool where
sizeOf (type Bool) = 1
---
• Expected kind ‘k’, but ‘Bool’ has kind ‘*’
‘k’ is a rigid type variable bound by
the type signature for:
sizeOf :: forall {k}. forall (a1 :: k) -> MyStorable a1 => Int
at /tmp/foo.hs:8:5-10
• In the type ‘Bool’
In a type argument: Bool
In the pattern: type Bool
• Relevant bindings include
sizeOf :: forall (a :: k) -> MyStorable a => Int
(bound at /tmp/foo.hs:8:5)
|
8 | sizeOf (type Bool) = 1
| ^^^^
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?
{-# LANGUAGE RequiredTypeArguments #-}
class MyStorable a where
_sizeOf :: a -> Int
instance MyStorable Bool where
_sizeOf _ = 1
instance MyStorable Int where
_sizeOf _ = 8
sizeOf :: forall a -> MyStorable a => Int
sizeOf a = _sizeOf (undefined :: a)
Is it possible to avoid the (undefined :: a) term and somehow use
TypeApplications here, with an "ambiguous" `_sizeOf` method?
class MyStorable a where
_sizeOf :: Int
--
Viktor. 🇺🇦 Слава Україні!
More information about the Haskell-Cafe
mailing list