#4229: relatively simple test case for "internal error: PAP object entered!" on
GHC 6.12.3
---------------------------------+------------------------------------------
Reporter: carlhowells | Owner:
Type: bug | Status: new
Priority: normal | Component: Compiler
Version: 6.12.3 | Keywords:
Os: Unknown/Multiple | Testcase:
Architecture: Unknown/Multiple | Failure: None/Unknown
---------------------------------+------------------------------------------
Comment(by carlhowells):
Whoops, let me format that code properly.
{{{
-- Bug.hs
module Main where
import Control.Monad.Trans
import Control.Monad.State.Strict
import Test.HUnit
runMyTest :: StateT () IO a -> IO a
runMyTest x = evalStateT x ()
explode :: StateT () IO ()
explode = when ("" == "") . liftIO . assertFailure $ "X"
main :: IO Counts
main = runTestTT . TestCase . runMyTest $ explode
-- bug.cabal
Name: bug
Version: 0.1
Build-type: Simple
Cabal-version: >=1.2
Executable bug
Main-is: Bug.hs
Build-depends:
base > 4 && < 5,
HUnit >= 1.2.2.1 && < 1.3,
monads-fd >= 0.1 && < 0.2
}}}
--
Ticket URL: <http://hackage.haskell.org/trac/ghc/ticket/4229#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