#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            |    Milestone:              
   Component:  Compiler          |      Version:  6.12.3      
    Keywords:                    |     Testcase:              
   Blockedby:                    |   Difficulty:              
          Os:  Unknown/Multiple  |     Blocking:              
Architecture:  Unknown/Multiple  |      Failure:  None/Unknown
---------------------------------+------------------------------------------
Description changed by igloo:

Old description:

> So, here's a test case
>
> -- 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
>
> -- 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
>
> ---------
>
> $ cabal build && ./dist/build/bug/bug
> Preprocessing executables for bug-0.1...
> Building bug-0.1...
> [1 of 1] Compiling Main             ( Bug.hs, dist/build/bug/bug-
> tmp/Main.o )
> Linking dist/build/bug/bug ...
> Cases: 1  Tried: 0  Errors: 0  Failures: 0bug: internal error: PAP object
> entered!
>     (GHC version 6.12.3 for x86_64_unknown_linux)
>     Please report this as a GHC bug:
> http://www.haskell.org/ghc/reportabug
> Aborted
>

>
> I couldn't figure out how to get the error to happen with HUnit or a
> monad transformer.  But here are some additional notes:
>
> Compiling with -O0 fixes it.
>
> Using mtl instead of monads-fd doesn't change anything.
>
> Changing the ("" == "") to True results in not getting a GHC internal
> error, but the test run reports 0 failures, which is incorrect.  Changing
> the import of Control.Monad.State.Strict to Control.Monad.State also
> results in no crash, but 0 failures reported.
>
> None of these issues occurs in GHC 6.10.4.  I haven't tested on versions
> other than 6.10.4 and 6.12.3.

New description:

 So, here's a test case
 {{{
 -- 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
 }}}

 {{{
 -- 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
 }}}

 ---------

 {{{
 $ cabal build && ./dist/build/bug/bug
 Preprocessing executables for bug-0.1...
 Building bug-0.1...
 [1 of 1] Compiling Main             ( Bug.hs, dist/build/bug/bug-
 tmp/Main.o )
 Linking dist/build/bug/bug ...
 Cases: 1  Tried: 0  Errors: 0  Failures: 0bug: internal error: PAP object
 entered!
     (GHC version 6.12.3 for x86_64_unknown_linux)
     Please report this as a GHC bug:
 http://www.haskell.org/ghc/reportabug
 Aborted
 }}}

 I couldn't figure out how to get the error to happen with HUnit or a monad
 transformer.  But here are some additional notes:

 Compiling with -O0 fixes it.

 Using mtl instead of monads-fd doesn't change anything.

 Changing the ("" == "") to True results in not getting a GHC internal
 error, but the test run reports 0 failures, which is incorrect.  Changing
 the import of Control.Monad.State.Strict to Control.Monad.State also
 results in no crash, but 0 failures reported.

 None of these issues occurs in GHC 6.10.4.  I haven't tested on versions
 other than 6.10.4 and 6.12.3.

--

-- 
Ticket URL: <http://hackage.haskell.org/trac/ghc/ticket/4229#comment:2>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
_______________________________________________
Glasgow-haskell-bugs mailing list
Glasgow-haskell-bugs@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs

Reply via email to