I recently discovered -XTypeApplications
, which allows me to write abbreviate my code. Consider the following:
{-# LANGUAGE AllowAmbiguousTypes, DataKinds, KindSignatures, RankNTypes,
ScopedTypeVariables, TypeApplications #-}
import Data.Tagged
import Data.Proxy
class Foo (a :: Bool) where
foo :: Tagged a Int
instance Foo 'True where
foo = 3
instance Foo 'False where
foo = 4
instead of writing proxy foo (Proxy::Proxy 'True)
, I can now write untag $ foo @'True
, which saves me a lot of Proxy
boilerplate. That's okay, but we can do better with ambiguous types:
foo' :: forall (a :: Bool) . (Foo a) => Int
foo' = untag $ foo @a
Now I can write foo' @'True
! Note that although the type was ambiguous prior to -XTypeApplications
, it is no longer since I can specify the type a
. I think this is pretty great, but others might not. So I was hoping to introduce a wrapper
wrapAmbiguous :: forall (a :: Bool) b . (Foo a) => (forall (t :: Bool) . (Foo t) => b) -> Tagged a b
wrapAmbiguous f = Tagged $ f @a
(even more general in my actual use case, but this gets the point across), so that users don't need -XTypeApplications
. However, when I try to use wrapAmbiguous
like proxy (wrapAmbiguous foo') (Proxy::Proxy 'True)
, I get the error
• Could not deduce (Foo a0) arising from a use of ‘foo'’
from the context: Foo t
bound by a type expected by the context:
Foo t => Int
at Foo.hs:26:18-35
The type variable ‘a0’ is ambiguous
These potential instances exist:
instance Foo 'False -- Defined at Foo.hs:12:10
instance Foo 'True -- Defined at Foo.hs:9:10
• In the first argument of ‘wrapAmbiguous’, namely ‘foo'’
In the first argument of ‘proxy’, namely ‘(wrapAmbiguous foo')’
In the second argument of ‘($)’, namely
‘proxy (wrapAmbiguous foo') (Proxy :: Proxy True)’
It seems to me that this should be legal, but GHC apparently can't unify the type of foo'
with forall (t :: Bool) (Foo t) => b
. Is there some way to make my wrapper work?