#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:  Runtime crash
---------------------------------+------------------------------------------
Changes (by ulfn):

  * failure:  None/Unknown => Runtime crash


Comment:

 Wiki-fu fail. New attempt with proper code block (can I edit the
 original?)

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

 {{{
 -- Main.hs
 import Any
 main = putStrLn (showNat Z)
 }}}

 {{{
 $ ghc -O --make Main.hs
 $ ./Main
 Bus error: 10
 }}}

-- 
Ticket URL: <http://hackage.haskell.org/trac/ghc/ticket/5441#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

Reply via email to