#5095: Incoherent instance for Prelude type class accepted without incoherent
instances option
-------------------------------+--------------------------------------------
Reporter: brunosoliveira | Owner:
Type: bug | Status: new
Priority: normal | Milestone:
Component: Compiler | Version: 7.0.1
Keywords: | Testcase:
Blockedby: | Difficulty:
Os: MacOS X | Blocking:
Architecture: x86 | Failure: GHC accepts invalid program
-------------------------------+--------------------------------------------
Description changed by igloo:
Old description:
> If we create a new module allowing overlapping instances, flexible
> instances and undecidable instances we can define a function that selects
> an incoherent instance for a type class defined in the Prelude. Example:
>
> > {-# OPTIONS -XFlexibleInstances -XOverlappingInstances
> -XUndecidableInstances #-}
>
> > module Test where
>
> > instance Show a => Eq a where
> > x == y = length (show x) == length (show y)
> >
> > f :: Show a => a -> a -> Bool
> > f x y = x == y
> >
> > p = f (3 :: Int) 4
>
> The instance selected here (tested with GHC 7.0 and 6.12) is the one in
> this module, even if the instance Eq Int from the Prelude is more
> specific. If we try to reproduce a similar example using a module other
> than the Prelude, an incoherent instances error is reported. I believe
> that, for consistency the same should happen here.
New description:
If we create a new module allowing overlapping instances, flexible
instances and undecidable instances we can define a function that selects
an incoherent instance for a type class defined in the Prelude. Example:
{{{
> {-# OPTIONS -XFlexibleInstances -XOverlappingInstances
-XUndecidableInstances #-}
> module Test where
> instance Show a => Eq a where
> x == y = length (show x) == length (show y)
>
> f :: Show a => a -> a -> Bool
> f x y = x == y
>
> p = f (3 :: Int) 4
}}}
The instance selected here (tested with GHC 7.0 and 6.12) is the one in
this module, even if the instance Eq Int from the Prelude is more
specific. If we try to reproduce a similar example using a module other
than the Prelude, an incoherent instances error is reported. I believe
that, for consistency the same should happen here.
--
--
Ticket URL: <http://hackage.haskell.org/trac/ghc/ticket/5095#comment:1>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
_______________________________________________
Glasgow-haskell-bugs mailing list
[email protected]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs