[GHC] #14303: HasField ambiguity error

GHC ghc-devs at haskell.org
Sun Oct 1 22:22:03 UTC 2017


#14303: HasField ambiguity error
-------------------------------------+-------------------------------------
        Reporter:  cloudhead         |                Owner:  (none)
            Type:  bug               |               Status:  closed
        Priority:  normal            |            Milestone:
       Component:  Compiler          |              Version:  8.2.1
      Resolution:  invalid           |             Keywords:
Operating System:  Unknown/Multiple  |         Architecture:
                                     |  Unknown/Multiple
 Type of failure:  None/Unknown      |            Test Case:
      Blocked By:                    |             Blocking:
 Related Tickets:                    |  Differential Rev(s):
       Wiki Page:                    |
-------------------------------------+-------------------------------------
Changes (by RyanGlScott):

 * status:  new => closed
 * resolution:   => invalid


Comment:

 This is expected behavior. GHC reports that these constraints are
 ambiguous because it can't determine what `x` is from the types on the
 right-hand sides of each function. Notice that `m a` doesn't mention `x`,
 and `x` isn't determined by a functional dependency like the `r` in
 `MonadReader r m`.

 There is a way to make ambiguous type signatures like this compile,
 however, by using the aptly named extension `AllowAmbiguousTypes` (which
 is often needed in `TypeApplications`-heavy code like what you have here).
 With `AllowAmbiguousTypes`, `askField` compiles without any further
 changes:

 {{{#!hs
 {-# LANGUAGE AllowAmbiguousTypes #-}
 {-# 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)
 }}}

 Making `askField'` compile takes a little extra work, since GHC is unable
 to figure out that you meant to use `getField` at type `x`. To fix this,
 use another type application:

 {{{#!hs
 {-# LANGUAGE AllowAmbiguousTypes #-}
 {-# 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 (getFieldWithProxy (Proxy :: Proxy x))
   where
     getFieldWithProxy :: forall proxy. proxy x -> r -> a
     getFieldWithProxy = const (getField @x)
 }}}

 Which makes it compile as well.

-- 
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/14303#comment:1>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler


More information about the ghc-tickets mailing list