[Haskell-cafe] ghc -O2 and HUnit weirdness

Jürgen Doser jurgen.doser at gmail.com
Fri Jan 7 00:18:09 CET 2011


El jue, 06-01-2011 a las 16:41 -0400, Joey Hess escribió:
> So, the problem seems to be that ghc -O2 somehow optimises the static
> assertBool _ True away, in what seems to be a bad way. Remove the -O2 and
> the test fails as expected. Presumably, although I have not verified,
> less static boolean values would not trigger the optimisation.
> Is this a ghc or HUnit bug? 
> 
> (Versions: 6.12.1, 1.2.2.1)

Looks like a GHC bug. The following code mimics what HUnit does:

--
import Control.Exception as E
import Data.Typeable

data Fail = Fail deriving (Show)
instance Typeable Fail where typeOf _ = mkTyConApp (mkTyCon "Fail") []
instance Exception Fail

t = (E.throw Fail >> return Nothing) `E.catch` (\Fail -> return $ Just Fail)

main = do a <- t
          print a
--

it runs fine with -O0, but produces an internal error when compiled with -O1 or -O2:

$ ghc --make  -O2 t.hs
[1 of 1] Compiling Main             ( t.hs, t.o )
Linking t ...
$ ./t
t: internal error: PAP object entered!
    (GHC version 6.12.1 for i386_unknown_linux)
    Please report this as a GHC bug:  http://www.haskell.org/ghc/reportabug

It looks like the following bug:
http://hackage.haskell.org/trac/ghc/ticket/3959

I don't have a newer GHC version installed, though, so I can't test if it works in a newer GHC. 

	Jürgen





More information about the Haskell-Cafe mailing list