Crash.hs:
------------------------------------------------------------------------
import FFI
import Monad

stringToInteger:: Addr -> IO (StablePtr Integer)
stringToInteger a = addrToString a >>= makeStablePtr . read

integerToString:: StablePtr Integer -> IO Addr
integerToString sp = deRefStablePtr sp >>= stringToAddr . show

addrToString:: Addr -> IO String
addrToString a = do
    c <- peek a
    if c == '\0'
        then return []
        else liftM (c:) $ addrToString (a `plusAddr` 1)

stringToAddr:: String -> IO Addr
stringToAddr s = do
    let s' = s++"\0"
    a <- malloc (length s')
    zipWithM (pokeElemOff a) [0..] s'
    return a

mul:: StablePtr Integer -> StablePtr Integer -> IO (StablePtr Integer)
mul a b = do
    a' <- deRefStablePtr a
    b' <- deRefStablePtr b
    makeStablePtr (a' * b')

foreign import "test" main     :: IO ()
foreign export stringToInteger :: Addr -> IO (StablePtr Integer)
foreign export integerToString :: StablePtr Integer -> IO Addr
foreign export mul             :: StablePtr Integer
                               -> StablePtr Integer
                               -> IO (StablePtr Integer)
------------------------------------------------------------------------

crash.c:
------------------------------------------------------------------------
#include <Rts.h>
#include "Crash_stub.h"

void test (void)
{
    StgStablePtr a = stringToInteger ("1000000000000000000000000000001");
    StgStablePtr b = stringToInteger ("1000000000000000000000000000002");
    StgStablePtr c = mul (a, b);
    printf ("%s\n", integerToString (c));
    a = stringToInteger ("1000000000000000000000000000003");
    b = stringToInteger ("1000000000000000000000000000004");
    c = mul (a, b);
    printf ("%s\n", integerToString (c));
}
------------------------------------------------------------------------

$ ghc -fglasgow-exts -c Crash.hs
$ ghc -c crash.c
$ ghc -fglasgow-exts Crash.o Crash_stub.o crash.o -o crash
$ ./crash
1000000000000000000000000000003000000000000000000000000000002
zsh: segmentation fault  ./crash
$ ghc --version
The Glorious Glasgow Haskell Compilation System, version 4.06

With related examples I also get "ARR_WORDS object entered!".
Change two definitions:
stringToInteger a  = do s <- addrToString   a;  makeStablePtr (read s)
integerToString sp = do i <- deRefStablePtr sp; stringToAddr  (show i)

-- 
 __("<    Marcin Kowalczyk * [EMAIL PROTECTED] http://qrczak.ids.net.pl/
 \__/              GCS/M d- s+:-- a22 C+++$ UL++>++++$ P+++ L++>++++$ E-
  ^^                  W++ N+++ o? K? w(---) O? M- V? PS-- PE++ Y? PGP+ t
QRCZAK                  5? X- R tv-- b+>++ DI D- G+ e>++++ h! r--%>++ y-

Reply via email to