Following example causes 'Segentation fault' under
Linux (Mandrake). Under Windows it works well.

---------------------------------------------------
module Main where

import Control.Concurrent.MVar
import System.IO.Unsafe

main = cfun >> main

foreign export ccall hfun :: IO ()
foreign import ccall cfun :: IO ()

{-# NOINCLUDE counter #-}
counter :: MVar Int
counter = unsafePerformIO (newMVar 0)

hfun = do
        n <- takeMVar counter
        print n
        putMVar counter (n+1)
------------------------------------------------------

#include "Main_stub.h"

void cfun ()
{
        hfun();
}


Krasimir

__________________________________________________
Do You Yahoo!?
Yahoo! Finance - Get real-time stock quotes
http://finance.yahoo.com
_______________________________________________
Glasgow-haskell-bugs mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs

Reply via email to