#4809: MonoLocalBinds and type classes cause infinite loop
---------------------------------+------------------------------------------
Reporter: JeremyShaw | Owner:
Type: bug | Status: new
Priority: normal | Component: Compiler
Version: 7.0.1 | Keywords:
Testcase: | Blockedby:
Os: Unknown/Multiple | Blocking:
Architecture: Unknown/Multiple | Failure: Incorrect result at runtime
---------------------------------+------------------------------------------
The following program gets stuck in a loop and prints no output when run:
{{{
{-# LANGUAGE MonoLocalBinds #-}
module Main where
import IdentityT (IdentityT(..), XML, runIdentityT)
import XMLGenerator (XMLGenT(..), XMLGen(genElement), Child,
EmbedAsChild(..), unXMLGenT)
import System.IO (BufferMode(..), hSetBuffering, stdout)
page :: XMLGenT (IdentityT IO) XML
page = genElement (Nothing, "ul") [] [ asChild (asChild "foo")]
where
-- item :: XMLGenT (IdentityT IO) [Child (IdentityT IO)]
item = (asChild $ asChild (return "bar" :: XMLGenT (IdentityT IO)
String))
main :: IO ()
main =
do hSetBuffering stdout LineBuffering
r <- runIdentityT (unXMLGenT page)
print r
}}}
I believe this is due to a compiler bug. There are five things you can do
to make it run successfully (i.e., not loop) -- none of which ought to
have an effect. Doing any one of the five works though.
Note that 'item' in the 'page' where clause is not actually used anywhere,
but three of the five things involve changes to that clause.
1. remove the 'where' clause in 'page' entirely. After all it is not
needed.
2. uncomment the type signature for 'item'
3. remove one of the calls to 'asChild' in item.
4. remove one of the calls to 'asChild' in page.
5. remove the MonoLocalBinds pragma.
I considered the possibility that the loop might be cause by asChild calls
forming a loop depending on how the types are inferred. However, each call
to asChild does a putStrLn. Since there is no output when the loop occurs,
I believe that the execution is not even getting that far.
Doing --dump-ds, does show the loop. But I could figure out anything
useful from seeing the loop in the desugared code.
The looping seems to occur whether compiled or using GHCi and at all
optimization levels.
This bug prevents HSP, and therefore Happstack and SeeReason from moving
to GHC 7.
I have attached 3 files. The above file, IdentityT.hs and XMLGenerator.hs.
The latter two come from HSP/Happstack, but have been stripped down to the
bare essentials.
--
Ticket URL: <http://hackage.haskell.org/trac/ghc/ticket/4809>
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