Stack smashing when using FunPtr wrappers on ARM

Stephen Paul Weber singpolyma at singpolyma.net
Thu Jan 24 15:44:56 CET 2013


I just got my unregistered LLVM-based ARM cross-compiler to a working place, 
which means I can produce any binaries which do no crash.  Yay!

However, <http://hackage.haskell.org/trac/ghc/ticket/7621> when I try to use 
FunPtr wrappers, something smashes the stack.

Would others working on ARM cross-compilers be willing to try this test and 
see if it works for you:

{-# LANGUAGE ForeignFunctionInterface #-}
module Main (main) where

import Foreign.Ptr

foreign import ccall "wrapper" wrap_refresh :: ( IO ()) -> IO (FunPtr ( IO ()))

main :: IO ()
main = do
	wrap_refresh (return ())
	return ()

-- 
Stephen Paul Weber, @singpolyma
See <http://singpolyma.net> for how I prefer to be contacted
edition right joseph



More information about the ghc-devs mailing list