#5441: unsafeCoerce'ing function to GHC.Prim.Any causes segfault
---------------------------------+------------------------------------------
Reporter: ulfn | Owner:
Type: bug | Status: new
Priority: normal | Component: Compiler
Version: 7.2.1 | Keywords:
Testcase: | Blockedby:
Os: Unknown/Multiple | Blocking:
Architecture: x86 | Failure: None/Unknown
---------------------------------+------------------------------------------
The following module is the smallest one I've been able to find exhibiting
the bug. Any simplification (that I've tried) results in the problem going
away.
module Any where
import Unsafe.Coerce (unsafeCoerce)
import GHC.Prim (Any)
listmap :: (a -> b) -> [a] -> [b]
listmap f [] = []
listmap f (x : xs) = f x : listmap f xs
data Nat = Z | S Nat
{-# NOINLINE inject #-}
inject :: Nat -> Nat -> Nat
inject m i = i
{-# NOINLINE look #-}
look :: Nat -> String -> Char
look Z _ = '0'
showDigit :: Nat -> () -> Nat -> Char
showDigit base prf d = look (inject base d) ""
toDigits :: Nat -> Nat -> [Nat]
toDigits Z Z = [Z]
coe1 :: (Nat -> String) -> Any
coe1 = unsafeCoerce
coe2 :: Any -> (Nat -> String)
coe2 = unsafeCoerce
showInBase :: Nat -> Any
showInBase base
= coe1 (\n -> listmap
(showDigit base ())
(toDigits base n))
showNat :: Nat -> String
showNat = coe2 (showInBase Z)
Now given this main module (it needs to be a different module)
import Any
main = putStrLn (showNat Z)
Compiling with optimisations:
$ ghc -O --make Main.hs
...
$ ./Main
Bus error: 10
Without optimizations it prints 0 as expected.
This has been reproduced on 7.0.3 (Mac OS X) and 7.2.1 (some Linux).
--
Ticket URL: <http://hackage.haskell.org/trac/ghc/ticket/5441>
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