[GHC] #14266: AllowAmbiguousTypes doesn't play well with default class methods

GHC ghc-devs at haskell.org
Thu Sep 21 23:53:27 UTC 2017


#14266: AllowAmbiguousTypes doesn't play well with default class methods
-------------------------------------+-------------------------------------
        Reporter:  chris-martin      |                Owner:  (none)
            Type:  bug               |               Status:  new
        Priority:  normal            |            Milestone:
       Component:  Compiler          |              Version:  8.0.2
      Resolution:                    |             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):

 * cc: RyanGlScott (added)


Comment:

 I can at least explain why you're seeing that error. GHC doesn't typecheck
 default methods by inlining their bodies like you suggest. Instead, it
 defines an auxiliary method and defines default `f` implementations in
 terms of that, like so:

 {{{#!hs
 {-# LANGUAGE AllowAmbiguousTypes #-}
 {-# LANGUAGE ExplicitForAll #-}
 {-# LANGUAGE TypeApplications #-}

 class A t where
   f :: forall x m. Monoid x => t m -> m

 instance A [] where
   f = df @[]

 df :: forall t. A t => forall x m. Monoid x => t m -> m
 df = undefined
 }}}

 You'll get the same sort of error from this code as well:

 {{{
 GHCi, version 8.2.1: http://www.haskell.org/ghc/  :? for help
 Loaded GHCi configuration from /home/rgscott/.ghci
 [1 of 1] Compiling Main             ( Bug.hs, interpreted )

 Bug.hs:9:7: error:
     • Could not deduce (Monoid x0) arising from a use of ‘df’
       from the context: Monoid x
         bound by the type signature for:
                    f :: forall x m. Monoid x => [m] -> m
         at Bug.hs:9:3
       The type variable ‘x0’ is ambiguous
       These potential instances exist:
         instance Monoid a => Monoid (IO a) -- Defined in ‘GHC.Base’
         instance Monoid Ordering -- Defined in ‘GHC.Base’
         instance Monoid a => Monoid (Maybe a) -- Defined in ‘GHC.Base’
         ...plus 7 others
         (use -fprint-potential-instances to see them all)
     • In the expression: df @[]
       In an equation for ‘f’: f = df @[]
       In the instance declaration for ‘A []’
   |
 9 |   f = df @[]
   |       ^^^^^^
 }}}

 As for how one would change this code to make this typecheck, I'm not
 sure. At first, I thought one could solve this by simply applying more
 arguments via `TypeApplications`, like so:

 {{{#!hs
 {-# LANGUAGE AllowAmbiguousTypes #-}
 {-# LANGUAGE InstanceSigs #-}
 {-# LANGUAGE ScopedTypeVariables #-}
 {-# LANGUAGE TypeApplications #-}

 class A t where
   f :: forall x m. Monoid x => t m -> m

 instance A [] where
   f :: forall x m. Monoid x => [m] -> m
   f = df @[] @x @m

 df :: forall t. A t => forall x m. Monoid x => t m -> m
 df = undefined
 }}}

 But this just shifts the location of the error around:

 {{{
 GHCi, version 8.2.1: http://www.haskell.org/ghc/  :? for help
 Loaded GHCi configuration from /home/rgscott/.ghci
 [1 of 1] Compiling Main             ( Bug.hs, interpreted )

 Bug.hs:10:8: error:
     • Could not deduce (Monoid x0)
       from the context: Monoid x
         bound by the type signature for:
                    f :: forall x m. Monoid x => [m] -> m
         at Bug.hs:10:8-39
       The type variable ‘x0’ is ambiguous
     • When checking that instance signature for ‘f’
         is more general than its signature in the class
         Instance sig: forall x m. Monoid x => [m] -> m
            Class sig: forall x m. Monoid x => [m] -> m
       In the instance declaration for ‘A []’
    |
 10 |   f :: forall x m. Monoid x => [m] -> m
    |        ^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^
 }}}

 This is all despite the fact that you can redefine `f` as a top-level
 function, and it works!

 {{{#!hs
 {-# LANGUAGE AllowAmbiguousTypes #-}
 {-# LANGUAGE ScopedTypeVariables #-}
 {-# LANGUAGE TypeApplications #-}

 class A t where
   f :: forall x m. Monoid x => t m -> m

 instance A [] where
   f = undefined

 f' :: forall x m. Monoid x => [m] -> m
 f' = df @[] @x @m

 df :: forall t. A t => forall x m. Monoid x => t m -> m
 df = undefined
 }}}

 It's all quite confusing. I find myself very unclear of when exactly
 `AllowAmbiguousTypes` is supposed to kick in and save me from ambiguity
 errors (because in the case of class methods, it's clearly not).

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


More information about the ghc-tickets mailing list