[Haskell-cafe] Question about forkIO

C K Kashyap ckkashyap at gmail.com
Thu Feb 28 15:36:53 CET 2013


Just to clarify, here is the sample haskell code that I am using -
{-# LANGUAGE ForeignFunctionInterface #-}
module Glue where
import Foreign.C.String
import qualified Control.Concurrent as CC

funHaskell :: CString -> IO Int
funHaskell cstr = do
     putStrLn "Haskell function called"
     str <- peekCString cstr
     CC.forkIO $ doForever str
     CC.threadDelay 2000000
     return 0

doForever str = do
          putStrLn "Hello World forever"
          CC.threadDelay 1000000
          doForever str

foreign export stdcall funHaskell :: CString -> IO Int


When I call "funHaskell" from my C program, "Hello World forever" gets
printed about twice - I think its because funHaskell waits for about 2
seconds before returning. However, once back in C land, the doForever
function stops to execute. I was wondering if there is some setting that
would allow the threads sparked to continue execute.

Regards,
Kashyap


On Thu, Feb 28, 2013 at 4:39 PM, C K Kashyap <ckkashyap at gmail.com> wrote:

> Hi All,
>
> Say I have a haskell function 'f' that does a forkIO and starts an action
> "a".  I create a DLL of this haskell code and inovke "f" from C. Can I
> expect the "a" to continue to run once "f" has returned to C?
>
> Regards,
> Kashyap
>
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://www.haskell.org/pipermail/haskell-cafe/attachments/20130228/b2d492ab/attachment.htm>


More information about the Haskell-Cafe mailing list