Question about forkIO

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

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
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

Quoth C K Kashyap
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?
Once control returns to f's caller, outside of the Haskell runtime, then there isn't any way to dispatch IO threads - that's done by the runtime, so it can happen only while executing in the runtime. I am not a forkIO expert, that's just how it appears to me from my limited understanding of how they work. For extra credit - do the old IO threads resume if you call 'f' again, so you'd have more each time? (I don't know!) Donn

Hey Donn ...... thanks, it turns out that threads do resume!!! This is how
I got my gmail stuff working.
I only have a doubt if the TCP "keep/alive" stuff continues to happen or
not....
Regards,
Kashyap
On Thu, Feb 28, 2013 at 9:07 PM, Donn Cave
Quoth C K Kashyap
, ... 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?
Once control returns to f's caller, outside of the Haskell runtime, then there isn't any way to dispatch IO threads - that's done by the runtime, so it can happen only while executing in the runtime. I am not a forkIO expert, that's just how it appears to me from my limited understanding of how they work.
For extra credit - do the old IO threads resume if you call 'f' again, so you'd have more each time? (I don't know!)
Donn
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

On Thu, Feb 28, 2013 at 6:09 AM, C K Kashyap
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?
While you're off in C the I/O manager and garbage collector are suspended. Many C programs are not prepared to deal with the side effects of their operation, such as being interrupted by timer signals; moreover, it is not possible to have multiple handlers at the OS level for a signal, and C programs may want to use the signal handlers themselves. -- brandon s allbery kf8nh sine nomine associates allbery.b@gmail.com ballbery@sinenomine.net unix, openafs, kerberos, infrastructure, xmonad http://sinenomine.net
participants (3)
-
Brandon Allbery
-
C K Kashyap
-
Donn Cave