#5002: 7.0.2 ignores a context which 7.0.1 picks up
--------------------------------+-------------------------------------------
Reporter: patrick_premont | Owner:
Type: bug | Status: new
Priority: normal | Component: Compiler
Version: 7.0.2 | Keywords:
Testcase: | Blockedby:
Os: Windows | Blocking:
Architecture: x86 | Failure: GHC rejects valid program
--------------------------------+-------------------------------------------
GHC 7.0.2 rejects programs which 7.0.1 accepts.
A passed context is not used, and the compiler (expectedly) fails to
deduce an instance. Patching the code so that it works again is not
difficult. Some type annotations can do the trick. So this is not a
critical issue but it is a bit surprising.
I have simplified my code as much as possible so that it still shows
the error in 7.0.2 (okIn701). I have included two further
simplifications which produce no error : okInBoth and okInBoth'. I see
why okInBoth is more simple (it side steps a type function), but I do
not see why okInBoth' would avoid the problem.
The code also compiles if we remove the instance
declaration for class B. In that case the type of a in okIn701 can be
infered, and the context for that type is provided.
I have seen the following comment by dimitris in ticket #4981, which
seems related. "I know why GHC is not picking the given up: it has to
do with the fact that we have not saturated all possible equalities
before we look for instances, but luckily this is something Simon and
I are planning to fix pretty soon." Ticket #4981 seems to be an issue
with 7.0.1. Here we see an apparent regression with 7.0.2, so I
thought I would bring it up in case it is an unexpected change in
behavior.
The diagnosis of ticket #3018 may be applicable to the code here: we
may be asking too much of the compiler. As an additional
simplification attempt, I have added function fromTicket3018, but it
compiles fine with 7.0.1 and 7.0.2.
Also if the instance for 'B' is restricted to '[a]' (we can then
remove the UndecidableInstances extension), and the type 'a' is
replaced by '[a]' in 'okIn701', then it compiles fine. Are instances
that match everything applied more eagerly ? If so then this
compilatin problem should be quite rare.
{{{
> {-# LANGUAGE TypeFamilies, FlexibleInstances, UndecidableInstances,
FlexibleContexts #-}
> class A a
> class B a where b :: a -> ()
> instance A a => B [a] where b = undefined
> newtype Y a = Y (a -> ())
> okIn701 :: B [a] => Y [a]
> okIn701 = wrap $ const () . b
> okInBoth' :: B a => Y a
> okInBoth' = wrap $ b
> okInBoth :: B a => Y a
> okInBoth = Y $ const () . b
> class Wrapper a where
> type Wrapped a
> wrap :: Wrapped a -> a
> instance Wrapper (Y a) where
> type Wrapped (Y a) = a -> ()
> wrap = Y
> fromTicket3018 :: Eq [a] => a -> ()
> fromTicket3018 x = let {g :: Int -> Int; g = [x]==[x] `seq` id} in ()
> main = undefined
}}}
--
Ticket URL: <http://hackage.haskell.org/trac/ghc/ticket/5002>
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