[GHC] #12923: MultiParamTypeClasses + ExtendedDefaultRules
GHC
ghc-devs at haskell.org
Wed Feb 8 12:29:21 UTC 2017
#12923: MultiParamTypeClasses + ExtendedDefaultRules
-------------------------------------+-------------------------------------
Reporter: amindfv | Owner:
Type: feature request | Status: patch
Priority: normal | Milestone: 8.2.1
Component: Compiler | Version: 8.0.1
Resolution: | Keywords:
Operating System: Unknown/Multiple | Architecture:
| Unknown/Multiple
Type of failure: None/Unknown | Test Case:
Blocked By: | Blocking:
Related Tickets: | Differential Rev(s): Phab:D2822
Wiki Page: |
-------------------------------------+-------------------------------------
Comment (by simonpj):
On Phab you comment that this program is still rejected with ambiguous
variables.
{{{
{-# LANGUAGE ExtendedDefaultRules #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE KindSignatures #-}
module T12924 where
import GHC.TypeLits
data A (b :: [Symbol]) = A deriving Show
class Works a (b :: [Symbol]) where
works :: a -> A b
instance Works Integer a where
works _ = A
addA :: A a -> A a -> A a
addA A A = A
test2 :: A x
test2 = addA (works 5) (works 5)
}}}
The reason is described in `Note [ApproximateWC]` in `TcSimplify`, item
(2) in that note. It arose from Trac #8155. We have a constraint
{{{
forall x. () => Num alpha, Works alpha x
}}}
but because we carefully make the `Works alpha x` prevent the `Num alpha`
float out for defaulting, for reasons described in the Note.
The rule is un-documented and indeed hard to explain. I'm quite inclined
to back-pedal on the fix to #8155.
--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/12923#comment:15>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list