[GHC] #12046: AllowAmbiguousTypes doesn't work with UndecidableSuperClasses
GHC
ghc-devs at haskell.org
Thu May 12 05:13:32 UTC 2016
#12046: AllowAmbiguousTypes doesn't work with UndecidableSuperClasses
-------------------------------------+-------------------------------------
Reporter: MikeIzbicki | Owner:
Type: bug | Status: new
Priority: normal | Milestone:
Component: Compiler | Version: 8.0.1-rc3
(Type checker) |
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:
-------------------------------------+-------------------------------------
Given the code below, `test1` and `test2` are the same except the former
has an ambiguous type and the latter does not. The compiler rejects the
former and accepts the latter.
{{{
{-# LANGUAGE UndecidableSuperClasses #-}
{-# LANGUAGE AllowAmbiguousTypes #-}
{-# LANGUAGE TypeFamilies #-}
class A (T a) => A a where
type T a
test1 :: forall a. A a => ()
test1 = ()
test2 :: A a => proxy a -> ()
test2 _ = ()
}}}
--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/12046>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list