Using Proxy in a TypeClass
Using Proxy in a TypeClass
I'm trying to do something similar to this question.
I'd like to define a typeclass
class Wrapper f where
wrap :: a -> f a
unwrap :: f a -> a
name :: Proxy (f a) -> String
and then define
instance (IsString a, FromJSON a, Wrapper f) => FromJSON (f a) where
parseJSON (String s) = wrap <$> pure (fromString $ unpack s)
parseJSON invalid = typeMismatch (name (Proxy :: Proxy (f a))) invalid
But I'm getting an error saying that
Could not deduce (Wrapper f0) arising from a use of ‘name’
from the context: (IsString a, FromJSON a, Wrapper f)
bound by the instance declaration at src/Model/Wrapper.hs:29:10-62
The type variable ‘f0’ is ambiguous
It's not really clear to me why this doesn't work and if it possible to fix it somehow
1 Answer
1
First a couple of remarks:
f a
f
Wrapper
FromJSON (Vector a)
Vector
Wrapper
I would advice against using Proxy
in new code. I always considered Proxy
an ugly hack, barely less ugly than the undefined :: T
arguments that were commonly used for this in old Haskell code. In new GHC, the problem was fixed properly by -XAllowAmbiguousTypes
with -XTypeApplications
; these allow you to simply make the signature
Proxy
Proxy
undefined :: T
-XAllowAmbiguousTypes
-XTypeApplications
{-# LANGUAGE AllowAmbiguousTypes #-}
class Wrapper f where
...
name :: String
and then instead of name (Proxy :: Proxy (f a))
write only name @f
.
name (Proxy :: Proxy (f a))
name @f
Now to the actual problem: your code doesn't work because type variables in standard Haskell always only belong to a single type signature / class context, but aren't usable in the code that defines it. IOW, type variables don't use the same name scopes as value-variables, that's why when you mention Proxy (f a)
the compiler “disambiguates” the type variables to f0
and a0
. This is a bit of a silly shortcoming of Haskell98, and is adressed by the -XScopedTypeVariables
extension (together with the ∀
aka forall
keyword). The following would compile, by itself:
Proxy (f a)
f0
a0
-XScopedTypeVariables
∀
forall
{-# LANGUAGE ScopedTypeVariables, UnicodeSyntax #-}
instance ∀ f a . (IsString a, FromJSON a, Wrapper f) => FromJSON (f a) where
parseJSON (String s) = wrap <$> pure (fromString $ unpack s)
parseJSON invalid = typeMismatch (name (Proxy :: Proxy (f a))) invalid
Just, as I said, such an instance shouldn't be defined. I think what you actually want is something like
{-# LANGUAGE DataKinds, KindSignatures, TypeApplications #-}
import GHC.TypeLits (Symbol, KnownSymbol, symbolVal)
data Wrapper (n :: String) (a :: *)
= Wrapper a
| TypeMismatch String
instance ∀ a s . (IsString a, FromJSON a, KnownSymbol s)
=> FromJSON (Wrapper s a) where
parseJSON (String s) = Wrapper <$> pure (fromString $ unpack s)
parseJSON invalid = TypeMismatch $ symbolVal @s Proxy
No classes needed.
By clicking "Post Your Answer", you acknowledge that you have read our updated terms of service, privacy policy and cookie policy, and that your continued use of the website is subject to these policies.
thanks @leftaroundabout, very clear and informative!
– marcosh
Jun 29 at 14:07