Incoherent instance solving is over-eager
danilo2 writes (originally in #9432 #13284)
{-# 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
-- this instance 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.
Trac metadata
Trac field | Value |
---|---|
Version | 8.0.1 |
Type | Bug |
TypeOfFailure | OtherFailure |
Priority | normal |
Resolution | Unresolved |
Component | Compiler |
Test case | |
Differential revisions | |
BlockedBy | |
Related | |
Blocking | |
CC | |
Operating system | |
Architecture |