[GHC] #14303: HasField ambiguity error
GHC
ghc-devs at haskell.org
Sun Oct 1 20:39:39 UTC 2017
#14303: HasField ambiguity error
-------------------------------------+-------------------------------------
Reporter: cloudhead | Owner: (none)
Type: bug | Status: new
Priority: normal | Milestone:
Component: Compiler | Version: 8.2.1
Keywords: | Operating System: Unknown/Multiple
Architecture: | Type of failure: None/Unknown
Unknown/Multiple |
Test Case: | Blocked By:
Blocking: | Related Tickets:
Differential Rev(s): | Wiki Page:
-------------------------------------+-------------------------------------
Both of these functions fail to compile with the error below:
{{{#!haskell
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeApplications #-}
import Control.Monad.Reader
import GHC.Records
import Data.Proxy
askField :: forall x a m r. (HasField x r a, MonadReader r m) => m a
askField =
asks (getField @x)
askField' :: forall x a m r. (HasField x r a, MonadReader r m) => m a
askField' =
asks (getFieldWithProxy (Proxy :: Proxy x))
where
getFieldWithProxy :: forall proxy. proxy x -> r -> a
getFieldWithProxy = const getField
}}}
{{{
Test.hs:12:14: error:
• Could not deduce (HasField x0 r a)
from the context: (HasField x r a, MonadReader r m)
bound by the type signature for:
askField' :: forall x a (m :: * -> *) r.
(HasField x r a, MonadReader r m) =>
m a
at Test.hs:12:14-69
The type variable ‘x0’ is ambiguous
• In the ambiguity check for ‘askField'’
To defer the ambiguity check to use sites, enable
AllowAmbiguousTypes
In the type signature:
askField' :: forall x a m r.
(HasField x r a, MonadReader r m) => m a
|
12 | askField' :: forall x a m r. (HasField x r a, MonadReader r m) => m a
| ^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^
}}}
I hope I'm not missing something, but one of these should compile.
--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/14303>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list