[GHC] #11577: GHCi accepts invalid programs when recompiling
GHC
ghc-devs at haskell.org
Sun Feb 14 18:06:46 UTC 2016
#11577: GHCi accepts invalid programs when recompiling
-------------------------------------+-------------------------------------
Reporter: crockeea | Owner:
Type: bug | Status: new
Priority: normal | Milestone:
Component: GHCi | Version: 7.10.2-rc2
Keywords: | Operating System: Unknown/Multiple
Architecture: | Type of failure: GHC accepts
Unknown/Multiple | invalid program
Test Case: | Blocked By:
Blocking: | Related Tickets:
Differential Rev(s): | Wiki Page:
-------------------------------------+-------------------------------------
This ticket may or may not be a duplicate of #9729, but I ran into it
again in a different context, so I'm reporting it. My GHC version is
7.10.2.20151030. The example is as minimal as I could make it.
File Bar.hs
{{{
{-# LANGUAGE FlexibleInstances, MultiParamTypeClasses #-}
module Bar where
class Bar a b where
(*^) :: a -> b -> b
}}}
File Foo.hs
{{{
{-# LANGUAGE MultiParamTypeClasses #-}
module Foo where
import Bar
import GHC.Prim
newtype Foo fp = Foo [fp]
instance {-# OVERLAPS #-}
Bar (Foo fp) [fp]
}}}
File Main.hs
{{{
{-# LANGUAGE MultiParamTypeClasses #-}
import Foo
import Bar
newtype LW a = LW [a]
instance Bar (Foo fp) (LW fp) where
r *^ (LW xs) = LW $ r *^ xs
}}}
If I start GHCi with `ghci Main`, everything compiles as it should. Then I
remove the `{-# OVERLAPS #-}` pragma in Foo.hs, which should break
Main.hs. But GHCi happily recompiles with `:r`.
A couple of notes: *with* the pragma, `:i Bar` gives the instances
{{{
instance Bar (Foo fp) (LW fp) -- Defined at Main.hs:8:10
instance Bar a b => Bar a [b] -- Defined at Bar.hs:8:10
instance [overlap ok] Bar (Foo fp) [fp] -- Defined at Foo.hs:22:3
}}}
while after (successfully, but incorrectly) recompiling without the
pragma, I get the instances
{{{
instance Bar (Foo fp) (LW fp) -- Defined at Main.hs:8:10
instance Bar a b => Bar a [b] -- Defined at Bar.hs:8:10
instance Bar (Foo fp) [fp] -- Defined at Foo.hs:22:3
}}}
(i.e., without the `[overlap ok]`).
Another strange thing is that the bug is only triggered if I import
specific (superfluous) modules in Foo.hs. For example, if I replace
GHC.Prim with Control.Monad or Data.Maybe, the bug is not triggered (i.e.,
GHCi correctly detects when I remove the pragma).
--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/11577>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list