#5751: code works in 7.0 but hangs in 7.2/7.4 due to changes in type checker
(most
likely)
-------------------------------+--------------------------------------------
Reporter: JeremyShaw | Owner:
Type: bug | Status: new
Priority: normal | Milestone:
Component: Compiler | Version: 7.2.1
Keywords: | Os: Linux
Architecture: x86_64 (amd64) | Failure: Incorrect result at runtime
Difficulty: Unknown | Testcase:
Blockedby: | Blocking:
Related: |
-------------------------------+--------------------------------------------
Comment(by dimitris):
Hi, we investigated a bit with Simon, here is a small variation we have
isolated and which shows the problem as well (apologies for the
technicalities, I am also using this to record very low-level information
about our constraint solver):
{{{
> module Main where
> class XMLGenerator m where
> genElement :: m ()
>
> newtype IdentityT m a = IdentityT { runIdentityT :: m a }
> instance XMLGenerator (IdentityT IO) where
> genElement = IdentityT $
> return ()
>
> main :: IO ()
> main =
> do runIdentityT web -- [Wanted] Widgets (IdentityT IO)
> putStrLn "done."
>
> class (Widgets x) => MonadRender x where
> mr :: x ()
>
> class (XMLGenerator m) => Widgets m where
> wd :: m ()
>
> instance MonadRender m => Widgets m
> instance MonadRender (IdentityT IO)
>
> web :: Widgets m => m ()
> web = genElement
}}}
This is a bug in the way GHC (7.4) tries to satisfy superclass constraints
in instance declarations. Observe the evidence generated for the
particular program is:
{{{
main = ... (web dWidgets_adR)
web dw = genElement (sc dwidg) -- 'sc' is for superclass selector
dWidgets_adR :: Widgets (IdentityT IO) -- The wanted constraint
dWidgets_adR = fdWidgetsm fMonadRenderIdentityT
-- Instance for Widgets
fdWidgetsm :: MonadRender m -> Widgets m
fdWidgetsm x = Widget (sc (sc x))
-- Instance for MonadRender
fMonadRenderIdentityT :: MonadRender (IdentityT IO)
fMonadRenderIdentityT = MonadRender dWidgets_adR
}}}
Notice that the `MonadRender` instance accepts the very constraint which
is the original wanted constraint, resulting in a loop.
The problem here is that the bad recursion is hidden under the abstraction
of the `fWidgetsm` function which peels two constructors off its argument.
We have encountered this problem in the past, which is the reason previous
versions of
GHC introduced superclass 'silent parameters' but at some point we got
convinced (erroneously) that they were not needed any longer (sth related
to Derived constraints). The 'silent parameter' solution simply introduces
extra parameters in dictionary functions which directly discharge the
superclass requirements in instance declarations w/o any constraint
solving. In the above example we would have:
{{{
-- Instance for Widgets
fdWidgetsm :: XMLGenerator m -> -- Silent parameter
MonadRender m -> Widgets m
fdWidgetsm slnt x = Widget slnt
-- Instance for MonadRender
fMonadRenderIdentityT :: Widget (IdentityT IO) -- Silent parameter
-> MonadRender (IdentityT IO)
fMonadRenderIdentityT slnt = MonadRender slnt
}}}
This in turn means that at the call site there is no indirection, we have
all the knowledge about which constraints are needed and we can solve:
{{{
main = ... (web dWidgets_adR)
web dw = genElement (sc dwidg) -- 'sc' is for superclass selector
dWidgets_adR :: Widgets (IdentityT IO) -- The wanted constraint
dWidgets_adR = fdWidgetsm slnt1 (fMonadRenderIdentityT slnt2)
slnt1 = just the xmlgenerator instance !!!!
slnt2 = dWidgets_adR
}}}
And now, though there is recursion going on, there is no loop.
Hence the only solution that we know about this is to reintroduce the
silent parameters.
Unfortunately due to the way that caching of constraints works currently
in GHC, introducing a "manual" silent parameter like:
{{{
instance (XMLGenerator m, MonadRender m) => Widgets m
}}}
does not work because the superclass of the superclass of the first given
is added
later in our worklist and overrides the second given. A short term fix
that will
enable at the very least to introduce 'manual' silent parameters would be
to stop overriding givens in the evidence variable cache that we use
internally (see custom case of `newEvVar` in `TcSMonad`). Of course the
real fix is to introduce properly silent parameters (sigh ...)
Jeremy, how urgent is this -- is this stopping you? Do you have a viable
workaround?
--
Ticket URL: <http://hackage.haskell.org/trac/ghc/ticket/5751#comment:6>
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