Hi everyone,
I’m reading the GHC Manual on RequiredTypeArguments and it illustrates the implementation of the proposal with the following:
One advantage of required type arguments is that they are never ambiguous. Consider the type of Foreign.Storable.sizeOf:
sizeOf :: forall a. Storable a => a -> Int
The value parameter is not actually used, its only purpose is to drive type inference. At call sites, one might write sizeOf (undefined :: Bool) or sizeOf @Bool undefined. Either way, the undefined is entirely superfluous and exists only to avoid an ambiguous type variable.
If sizeOf had this type, we could write sizeOf Bool without passing a dummy value.
Which sounds great. So I have tried to replicate it:
{-# LANGUAGE RequiredTypeArguments #-}
module Main where
import Data.Kind (Type)
class Storable (a :: Type) where
sizeOf :: forall a -> Int
instance Storable Int where
sizeOf _ = 8
Unfortunately I get all manners of type errors:
Main.hs:8:3: error: [GHC-39999]
• Could not deduce ‘Storable a0’
from the context: Storable a
bound by the type signature for:
sizeOf :: forall a {k}. Storable a => forall (a1 :: k) -> Int
at Main.hs:8:3-27
The type variable ‘a0’ is ambiguous
• In the ambiguity check for ‘sizeOf’
To defer the ambiguity check to use sites, enable AllowAmbiguousTypes
When checking the class method:
sizeOf :: forall a {k}. Storable a => forall (a1 :: k) -> Int
In the class declaration for ‘Storable’
|
8 | sizeOf :: forall a -> Int
| ^^^^^^^^^^^^^^^^^^^^^^^^^
Am I missing something? Is there a complementary extension to enable?
The recommended way, currently, is just to use a separate function:
{-# LANGUAGE RequiredTypeArguments, AllowAmbiguousTypes #-}
import Data.Kind (Type)
class Storable (a :: Type) where
_sizeOf :: Int
instance Storable Int where
_sizeOf = 8
sizeOf :: forall a -> Storable a => Int
sizeOf a = _sizeOf @a
You can write an explicit quantifier on an instance definition (and I do!) like instance forall a b. (Semigroup a, Semigroup b) => Semigroup (a, b). So I feel like it should also work to write one on a class, in which case you could spell out which quantifier you want.
class forall (a :: Type). Storable a where sizeOf :: Int
sizeOf :: forall a. Storable a => Int
instance Storable Int where sizeOf = 8
class forall (a :: Type) -> Storable a where sizeOf :: Int
sizeOf :: forall a -> Storable a => Int
instance Storable Int where sizeOf Int = 8 (or sizeOf _ = 8)
For consistency it would then also be possible to write instance forall a -> …, which is a little weird, but I don’t think it causes any actual problems for instance resolution.
I asked an essentially identical question on the haskell-cafe list, and got an answer identical to @TeofilC’s approach. Works for me, and I would strongly support some text in the guide that covers this topic. Anyone care to propose an MR?
It is also I think worth pointing out that it is possible to write wrappers in the opposite direction, i.e. calling the function with visible type arguments from a context where a term of the type is available.