
On Sun, Jul 13, 2025 at 11:47:36AM +0100, Tom Ellis wrote:
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
That's clever, thanks! I may at times have use for this. Example: {-# LANGUAGE AllowAmbiguousTypes #-} {-# LANGUAGE RequiredTypeArguments #-} {-# LANGUAGE ScopedTypeVariables #-} {-# LANGUAGE TypeApplications #-} import Data.Kind (Type) class MyStorable a where sizeOf :: forall b -> b ~ a => MyStorable a => Int instance MyStorable Bool where sizeOf Bool = 1 instance MyStorable Int where sizeOf Int = 8 testMe :: forall a. MyStorable a => a -> Int testMe _ = sizeOf a testMe2 :: forall a. MyStorable a => Int testMe2 = sizeOf a main :: IO () main = do print $ testMe True print $ testMe (1 :: Int) print $ testMe2 @Bool print $ testMe2 @Int Nice to see that it is also possible to write a wrapper in the other direction, to indirectly call the visible-dependent-qualified function via a term of the appropriate type or via type application. It might be useful to document this bit of "lore" in the use guide, since it was not exactly obvious how to do this.
(But I prefer your solution: the wrapper.)
Sure, the wrapper approach I found may also have its uses. -- Viktor. 🇺🇦 Слава Україні!