
I am running ghc 6.4.2 on a Win32 machine. I'm using hs-plugins in one thread and a simple getLine loop in another. It appears that getLine blocks the hs-plugins thread on Win32 (this has been verified to work fine on freeBSD). I've tried various combinations of -threaded flag and forkIO/forkOS and always get the undesireable result. Below is the minimal test case. module Main where import Control.Concurrent import System.Plugins import System.IO -- Main loop main = do hSetBuffering stdout NoBuffering forkIO blah test <- getLine putStrLn test blah = do contents <- loadPlugin "Hello" putStrLn contents loadPlugin path = do status <- pdynload (path ++ ".o") [] [] "Prelude.String" "myTestSym" case status of (LoadSuccess _ res) -> return res (LoadFailure errors) -> return $ concat errors --------------------- Hello.hs -------------------- module Hello where myTestSym :: String myTestSym = "Hello 2!" Thanks!

Hello Vyacheslav, Saturday, October 21, 2006, 7:37:19 AM, you wrote:
I am running ghc 6.4.2 on a Win32 machine. I'm using hs-plugins in one thread and a simple getLine loop in another. It appears that getLine blocks the hs-plugins thread on Win32 (this has been verified to work fine on freeBSD). I've tried various combinations of -threaded flag and forkIO/forkOS and always get the undesireable result.
_may be_ it is one more consequence of lack of IO manager in windows/threaded RTS ( http://hackage.haskell.org/trac/ghc/ticket/637 ) try _without_ -threaded. if it don't work, you can try my I/O library: http://haskell.org/haskellwiki/Library/Streams use 'vGetLine fdStdIn' in order to read lines. you should strip chr(13) at line-end by yourself because my lib don't implements CR+LF->LF conversion feel free to ask me more, i'm speaking russian ;) -- Best regards, Bulat mailto:Bulat.Ziganshin@gmail.com

Hello Bulat, Saturday, October 21, 2006, 12:56:48 PM, you wrote:
use 'vGetLine fdStdIn' in order to read lines. you should strip
sorry, use do h <- bufferBlockStream fdStdIn vGetLine h vGetLine h ... -- Best regards, Bulat mailto:Bulat.Ziganshin@gmail.com

bulat.ziganshin:
Hello Vyacheslav,
Saturday, October 21, 2006, 7:37:19 AM, you wrote:
I am running ghc 6.4.2 on a Win32 machine. I'm using hs-plugins in one thread and a simple getLine loop in another. It appears that getLine blocks the hs-plugins thread on Win32 (this has been verified to work fine on freeBSD). I've tried various combinations of -threaded flag and forkIO/forkOS and always get the undesireable result.
_may be_ it is one more consequence of lack of IO manager in windows/threaded RTS ( http://hackage.haskell.org/trac/ghc/ticket/637 )
Oh, that's almost certainly it. Bulat++ It's blocking on the foreign call (into the linker), since there's no IO manager thread, I think.
try _without_ -threaded. if it don't work, you can try my I/O library: http://haskell.org/haskellwiki/Library/Streams
use 'vGetLine fdStdIn' in order to read lines. you should strip chr(13) at line-end by yourself because my lib don't implements CR+LF->LF conversion
feel free to ask me more, i'm speaking russian ;)
-- Don

Hello Donald, Saturday, October 21, 2006, 1:03:34 PM, you wrote:
I am running ghc 6.4.2 on a Win32 machine. I'm using hs-plugins in one
Oh, that's almost certainly it. Bulat++ It's blocking on the foreign call (into the linker), since there's no IO manager thread, I think.
can't you define this call as 'safe'? -- Best regards, Bulat mailto:Bulat.Ziganshin@gmail.com

bulat.ziganshin:
Hello Donald,
Saturday, October 21, 2006, 1:03:34 PM, you wrote:
I am running ghc 6.4.2 on a Win32 machine. I'm using hs-plugins in one
Oh, that's almost certainly it. Bulat++ It's blocking on the foreign call (into the linker), since there's no IO manager thread, I think.
can't you define this call as 'safe'?
But is it safe. Hmm.... I get kind of queasy when mucking about in the rts. foreign import ccall unsafe "lookupSymbol" c_lookupSymbol :: CString -> IO (Ptr a) foreign import ccall unsafe "loadObj" c_loadObj :: CString -> IO Bool foreign import ccall unsafe "unloadObj" c_unloadObj :: CString -> IO Bool foreign import ccall unsafe "resolveObjs" c_resolveObjs :: IO Bool foreign import ccall unsafe "addDLL" c_addDLL :: CString -> IO CString foreign import ccall unsafe "initLinker" initLinker :: IO () -- Don

Hello Donald, Sunday, October 22, 2006, 9:04:02 AM, you wrote:
can't you define this call as 'safe'?
But is it safe. Hmm.... I get kind of queasy when mucking about in the rts.
i don't understand you (because of my weak English). 'safe' specifier is just says that function should be called in _safe_ way that will allow to continue execute other Haskell threads. for functions declared as 'unsafe' GHC uses simplified call method that freezes execution of all Haskell threads until called function will return look for details in http://www.haskell.org/~simonmar/papers/conc-ffi.pdf
foreign import ccall unsafe "lookupSymbol" c_lookupSymbol :: CString -> IO (Ptr a)
-- Best regards, Bulat mailto:Bulat.Ziganshin@gmail.com

bulat.ziganshin:
Hello Donald,
Sunday, October 22, 2006, 9:04:02 AM, you wrote:
can't you define this call as 'safe'?
But is it safe. Hmm.... I get kind of queasy when mucking about in the rts.
i don't understand you (because of my weak English).
'safe' specifier is just says that function should be called in _safe_ way that will allow to continue execute other Haskell threads. for functions declared as 'unsafe' GHC uses simplified call method that freezes execution of all Haskell threads until called function will return
look for details in http://www.haskell.org/~simonmar/papers/conc-ffi.pdf
Yes, I understand this. I just don't know how safe it is to have other threads continue executing while I'm swapping code in and out of the system...
foreign import ccall unsafe "lookupSymbol" c_lookupSymbol :: CString -> IO (Ptr a)
This could be safe, then, for other threads to continue. Yes. -- Don

Bulat: I didn't get the chance to use the streams library yet, but
could you explain how it would solve my locking problem? The core
problem that the runtime under Win32 doesn't have an IO manager still
remains, correct?
Is anyone looking to fix this issue? If not, how hard would it be for
me to fix it? I'd like to get my hands dirty with GHC but I don't
think I'll be able to do it without a lot of direction.
Thanks,
- Slava.
On 10/22/06, Donald Bruce Stewart
bulat.ziganshin:
Hello Donald,
Sunday, October 22, 2006, 9:04:02 AM, you wrote:
can't you define this call as 'safe'?
But is it safe. Hmm.... I get kind of queasy when mucking about in the rts.
i don't understand you (because of my weak English).
'safe' specifier is just says that function should be called in _safe_ way that will allow to continue execute other Haskell threads. for functions declared as 'unsafe' GHC uses simplified call method that freezes execution of all Haskell threads until called function will return
look for details in http://www.haskell.org/~simonmar/papers/conc-ffi.pdf
Yes, I understand this. I just don't know how safe it is to have other threads continue executing while I'm swapping code in and out of the system...
foreign import ccall unsafe "lookupSymbol" c_lookupSymbol :: CString -> IO (Ptr a)
This could be safe, then, for other threads to continue. Yes.
-- Don

Also, what would it take for me to fix the GHCi crash on Win32 when a plugin is being loaded? I figured I'll ask before blindly jumping into the code :)

coffeemug:
Also, what would it take for me to fix the GHCi crash on Win32 when a plugin is being loaded? I figured I'll ask before blindly jumping into the code :)
You need to find the win32 equivalent of the ELF-specific code that ignores requests to load a module multipe times, rather than dying with an error. -- Don

Hello Vyacheslav, Monday, October 23, 2006, 7:20:47 AM, you wrote:
Bulat: I didn't get the chance to use the streams library yet, but could you explain how it would solve my locking problem? The core problem that the runtime under Win32 doesn't have an IO manager still remains, correct?
i will say instead "ghc I/O library on windows doesn't include IO manager". there are 3 possible ways to implement I/O: 1) use read() calls marked as unsafe. it will block all haskell threads while one thread do I/O 2) use calls marked as safe. your I/O becomes fine 3) implement I/O manager which will make special asyncRead() calls and then wake up just the Haskell thread that completed its i/o. in terms of functionality, it's the same as 2), but a MUCH faster when you have a lot of I/O (imagine web server with thousands of threads running simultaneously) GHC i/o lib implements 3) on unixes but only 1) on windows. my Streams lib implement 1) on any system. BUT... all that you need to switch my lib to 2) is to edit System.FD module and mark imports as 'safe'. with GHC I/O lib it will be a hard task, believe me :)
Is anyone looking to fix this issue? If not, how hard would it be for me to fix it? I'd like to get my hands dirty with GHC but I don't think I'll be able to do it without a lot of direction.
wait a moment. GHC headquarter don't work at weekends ;) -- Best regards, Bulat mailto:Bulat.Ziganshin@gmail.com

Bulat Ziganshin wrote:
Hello Vyacheslav,
Monday, October 23, 2006, 7:20:47 AM, you wrote:
Bulat: I didn't get the chance to use the streams library yet, but could you explain how it would solve my locking problem? The core problem that the runtime under Win32 doesn't have an IO manager still remains, correct?
i will say instead "ghc I/O library on windows doesn't include IO manager".
there are 3 possible ways to implement I/O:
1) use read() calls marked as unsafe. it will block all haskell threads while one thread do I/O
2) use calls marked as safe. your I/O becomes fine
3) implement I/O manager which will make special asyncRead() calls and then wake up just the Haskell thread that completed its i/o. in terms of functionality, it's the same as 2), but a MUCH faster when you have a lot of I/O (imagine web server with thousands of threads running simultaneously)
GHC i/o lib implements 3) on unixes but only 1) on windows. my Streams lib implement 1) on any system. BUT...
I beg to differ ;-) On Windows: without -threaded * reads are implemented by the RTS which provides non-blocking I/O using OS threads. (see win32/IOManager.c etc.) with -threaded * reads are implemented with safe foreign calls, with no special support from the RTS. So you get non-blocking I/O in both cases on Windows. The lack of an I/O manager thread doesn't affect the non-blockiness of I/O on Windows. It does affect the efficiency: each blocked I/O request on Windows has an associated OS thread, which gets quite expensive when you have a few of them. It also affects signal handling (console events), which is what #637 is about. http://hackage.haskell.org/trac/ghc/ticket/637 Cheers, Simon

Simon Marlow wrote:
Bulat Ziganshin wrote:
Hello Vyacheslav,
Monday, October 23, 2006, 7:20:47 AM, you wrote:
Bulat: I didn't get the chance to use the streams library yet, but could you explain how it would solve my locking problem? The core problem that the runtime under Win32 doesn't have an IO manager still remains, correct?
i will say instead "ghc I/O library on windows doesn't include IO manager".
there are 3 possible ways to implement I/O:
1) use read() calls marked as unsafe. it will block all haskell threads while one thread do I/O
2) use calls marked as safe. your I/O becomes fine
3) implement I/O manager which will make special asyncRead() calls and then wake up just the Haskell thread that completed its i/o. in terms of functionality, it's the same as 2), but a MUCH faster when you have a lot of I/O (imagine web server with thousands of threads running simultaneously)
GHC i/o lib implements 3) on unixes but only 1) on windows. my Streams lib implement 1) on any system. BUT...
I beg to differ ;-) On Windows:
without -threaded * reads are implemented by the RTS which provides non-blocking I/O using OS threads. (see win32/IOManager.c etc.)
with -threaded * reads are implemented with safe foreign calls, with no special support from the RTS.
So you get non-blocking I/O in both cases on Windows. The lack of an I/O manager thread doesn't affect the non-blockiness of I/O on Windows. It does affect the efficiency: each blocked I/O request on Windows has an associated OS thread, which gets quite expensive when you have a few of them. It also affects signal handling (console events), which is what #637 is about.
Oh, I forgot to mention. Perhaps your bug is that you're using hGetBufNonBlocking, which isn't on Windows? Cheers, Simon

Hello Simon, Monday, October 23, 2006, 5:05:56 PM, you wrote:
Perhaps your bug is that you're using hGetBufNonBlocking, which isn't on Windows?
_whose_ bug? you write to Simon Marlow :) and what is you explanation why Vyacheslav's programs using getLine does block? -- Best regards, Bulat mailto:Bulat.Ziganshin@gmail.com

Bulat Ziganshin wrote:
Hello Simon,
Monday, October 23, 2006, 5:05:56 PM, you wrote:
Perhaps your bug is that you're using hGetBufNonBlocking, which isn't on Windows?
_whose_ bug? you write to Simon Marlow :)
Sorry - let me rephrase that: perhaps the problem is that hs-plugins uses hGetBufNonBlocking, which isn't non-blocking on Windows?
and what is you explanation why Vyacheslav's programs using getLine does block?
I really don't know. Could hs-plugins be trying to access stdin? stdin would be locked by the thread trying to read from it with getLine. Cheers, Simon

Donald Bruce Stewart wrote:
bulat.ziganshin:
Hello Donald,
Sunday, October 22, 2006, 9:04:02 AM, you wrote:
can't you define this call as 'safe'?
But is it safe. Hmm.... I get kind of queasy when mucking about in the rts.
i don't understand you (because of my weak English).
'safe' specifier is just says that function should be called in _safe_ way that will allow to continue execute other Haskell threads. for functions declared as 'unsafe' GHC uses simplified call method that freezes execution of all Haskell threads until called function will return
look for details in http://www.haskell.org/~simonmar/papers/conc-ffi.pdf
Yes, I understand this. I just don't know how safe it is to have other threads continue executing while I'm swapping code in and out of the system...
Does indeed sound dodgy. The only way to prevent other threads from running altogether is to compile *without* -threaded and make an unsafe foreign call. Cheers, Simon
participants (4)
-
Bulat Ziganshin
-
dons@cse.unsw.edu.au
-
Simon Marlow
-
Vyacheslav Akhmechet