[Haskell-cafe] Re: Haskell Propeganda

Don Stewart dons at galois.com
Sun Aug 24 23:59:21 EDT 2008


ashley:
> Thomas Davie wrote:
> >I'd be interested to see your other examples -- because that error is 
> >not happening in Haskell!  You can't argue that Haskell doesn't give you 
> >no segfaults, because you can embed a C segfault within Haskell.
> 
> This segfaults on my x86_64 Linux box:
> 
>   module Main where
>   import Data.Typeable
>   import Data.IORef
>   data T = T
>   instance Typeable T where
>     typeOf _ = typeOf (undefined :: IORef ())
>   main :: IO ()
>   main = writeIORef (maybe undefined id (cast T)) ()
> 
> You'll note nothing marked "Foreign" or "unsafe", and only the base 
> library used. Does the segfault "happen in Haskell" or not?

You just wrote unsafeCoere# a different way:

        typeOf T = typeOf (undefined :: IORef ())

Manual Typeable deriving should probably be disabled :-)

-- Don


More information about the Haskell-Cafe mailing list