[GHC] #9432: IncoherentInstances are too restricted
GHC
ghc-devs at haskell.org
Mon Aug 11 10:54:49 UTC 2014
#9432: IncoherentInstances are too restricted
-------------------------------------+-------------------------------------
Reporter: danilo2 | Owner:
Type: feature | Status: new
request | Milestone:
Priority: high | Version: 7.8.2
Component: Compiler | Keywords:
(Type checker) | Architecture: Unknown/Multiple
Resolution: | Difficulty: Unknown
Operating System: | Blocked By:
Unknown/Multiple | Related Tickets:
Type of failure: |
None/Unknown |
Test Case: |
Blocking: |
Differential Revisions: |
-------------------------------------+-------------------------------------
Comment (by danilo2):
Maybe we should treat it as a bug? I've got here a small example showing
that it really breaks how `OverlappingInstances` are working:
{{{#!haskell
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE FunctionalDependencies #-}
{-# LANGUAGE UndecidableInstances #-}
{-# LANGUAGE OverlappingInstances #-}
{-# LANGUAGE IncoherentInstances #-} -- the flag is niot needed by the
example
module Main where
import Data.Typeable
class CTest a b | a -> b where
cTest :: a -> b
cTest = undefined
-- this example is choosen even if more specific is available!
instance out~a => CTest a out where
cTest = id
instance CTest Int String where
cTest _ = "test"
main = do
print $ typeOf $ cTest (5::Int)
}}}
The instance `CTest a out` even if more specific (`CTest Int String`) is
in scope, which just breaks how `OverlappingInstances` work. If we disable
the `IncoherentInstances` flag, the right one is selected.
--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/9432#comment:1>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list