syscall, sigpause and EINTR on Mac OSX

Folks, I'm kind of stuck on this and can't figure it out... Take a look at the trace below, this is Mac OSX Tiger. (gdb) where #0 0x90006068 in syscall () #1 0x9004420c in sigpause () #2 0x001791b8 in awaitUserSignals () at Signals.c:256 #3 0x0012e1a8 in schedule (mainThread=0x1300360, initialCapability=0x0) at Schedule.c:518 #4 0x0012f340 in waitThread_ (m=0x1300360, initialCapability=0x0) at Schedule.c:2156 #5 0x0012f224 in scheduleWaitThread (tso=0x15c0000, ret=0x0, initialCapability=0x0) at Schedule.c:2050 #6 0x0012ba18 in rts_evalLazyIO (p=0x215254, ret=0x0) at RtsAPI.c:459 #7 0x0001ea7c in main (argc=4, argv=0x0) at Main.c:104 (gdb) p16 $r22 0x40: Cannot access memory at address 0x40 My program is currently stuck here. The man pages say that sigpause will only terminate by being interrupted and EINTR will be the errno. EINTR is signal 2, the same one that I'm trapping and the one sent when ^C is pressed. This probably explains why my signal handler is getting hit from time to time without any input from me. My program then exits and leaves me very puzzled as the whole thing looks like someone sneaked up to my keyboard and hit ^C to interrupt the program. I'm not making any sense of this. Why would someone be calling sigpause and making it interrupt my program? How can I work around this? I guess I'll poke around the ghc internals a bit and see what's cooking. Thanks, Joel -- http://wagerlabs.com/

I looked at the scheduler source code and it appears that GHC goes to wait for signals when a deadlock is detected and there's nothing else to do. It still does not explain where the signal comes from when I'm away from the keyboard. On Dec 11, 2005, at 4:10 PM, Joel Reymont wrote:
(gdb) where #0 0x90006068 in syscall () #1 0x9004420c in sigpause () #2 0x001791b8 in awaitUserSignals () at Signals.c:256 #3 0x0012e1a8 in schedule (mainThread=0x1300360, initialCapability=0x0) at Schedule.c:518 [...] My program is currently stuck here. The man pages say that sigpause will only terminate by being interrupted and EINTR will be the errno. EINTR is signal 2, the same one that I'm trapping and the one sent when ^C is pressed.

From: Joel Reymont
To: Haskell Cafe Subject: [Haskell-cafe] Re: syscall, sigpause and EINTR on Mac OSX Date: Sun, 11 Dec 2005 16:33:36 +0000 I looked at the scheduler source code and it appears that GHC goes to wait for signals when a deadlock is detected and there's nothing else to do.
It still does not explain where the signal comes from when I'm away from the keyboard.
This is not signal, it is result from call to pause() . #if !defined(RTS_SUPPORTS_THREADS) void awaitUserSignals(void) { while (!signals_pending() && !interrupted) { pause(); <<<<<<<<<< this is where it stops and waits for signals } } #endif you have to look elsewhere as this is normal behavior. Strange is that you are using threaded run time (I guess ) but this function is defined only for single threaded variant. This I implied from #if !defined(RTS_SUPPORTS_THREADS) Greetings, Bane.
On Dec 11, 2005, at 4:10 PM, Joel Reymont wrote:
(gdb) where #0 0x90006068 in syscall () #1 0x9004420c in sigpause () #2 0x001791b8 in awaitUserSignals () at Signals.c:256 #3 0x0012e1a8 in schedule (mainThread=0x1300360, initialCapability=0x0) at Schedule.c:518 [...] My program is currently stuck here. The man pages say that sigpause will only terminate by being interrupted and EINTR will be the errno. EINTR is signal 2, the same one that I'm trapping and the one sent when ^C is pressed.
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
_________________________________________________________________ Express yourself instantly with MSN Messenger! Download today it's FREE! http://messenger.msn.click-url.com/go/onm00200471ave/direct/01/

On Dec 11, 2005, at 4:50 PM, Branimir Maksimovic wrote:
This is not signal, it is result from call to pause() . [...] you have to look elsewhere as this is normal behavior.
You are saying that triggering my ^C handler randomly is normal behavior? I understand why it goes to wait for signals but it still does not explain where the signal itself is coming from.
Strange is that you are using threaded run time (I guess ) but this function is defined only for single threaded variant. This I implied from #if !defined(RTS_SUPPORTS_THREADS)
I'm not using a threaded runtime in this case. It appears that -debug and -threaded are incompatible as I get an error about a mixed debug/ threaded runtime library not being available. I compile with -debug so that I can run +RTS -Ds to check for deadlocks. Thanks, Joel -- http://wagerlabs.com/

From: Joel Reymont
To: Branimir Maksimovic CC: haskell-cafe@haskell.org Subject: Re: [Haskell-cafe] Re: syscall, sigpause and EINTR on Mac OSX Date: Sun, 11 Dec 2005 16:56:23 +0000 On Dec 11, 2005, at 4:50 PM, Branimir Maksimovic wrote:
This is not signal, it is result from call to pause() . [...] you have to look elsewhere as this is normal behavior.
You are saying that triggering my ^C handler randomly is normal behavior? I understand why it goes to wait for signals but it still does not explain where the signal itself is coming from.
I'm saying that neither is this result of signal, nor stack trace shows that any signal handler is called. It just shows call to await.... and await calls pause. That's all Greetings, Bane.
Strange is that you are using threaded run time (I guess ) but this function is defined only for single threaded variant. This I implied from #if !defined(RTS_SUPPORTS_THREADS)
I'm not using a threaded runtime in this case. It appears that -debug and -threaded are incompatible as I get an error about a mixed debug/ threaded runtime library not being available. I compile with -debug so that I can run +RTS -Ds to check for deadlocks.
Thanks, Joel
_________________________________________________________________ FREE pop-up blocking with the new MSN Toolbar - get it now! http://toolbar.msn.click-url.com/go/onm00200415ave/direct/01/

Though I frorgot to add that deadlock can be caused by signal somewhere else (eg other thread) if signal handler eg locks mutex internally or calls some other non asynchronous safe functions like locking functions. This is likely scenario, if you doubt at signal handlers but I don;t know the details . Deadlocks can be caused by other things, not neccessarily signals. Greetings, Bane.
From: "Branimir Maksimovic"
To: joelr1@gmail.com CC: haskell-cafe@haskell.org Subject: Re: [Haskell-cafe] Re: syscall, sigpause and EINTR on Mac OSX Date: Sun, 11 Dec 2005 17:28:54 +0000 From: Joel Reymont
To: Branimir Maksimovic CC: haskell-cafe@haskell.org Subject: Re: [Haskell-cafe] Re: syscall, sigpause and EINTR on Mac OSX Date: Sun, 11 Dec 2005 16:56:23 +0000 On Dec 11, 2005, at 4:50 PM, Branimir Maksimovic wrote:
This is not signal, it is result from call to pause() . [...] you have to look elsewhere as this is normal behavior.
You are saying that triggering my ^C handler randomly is normal behavior? I understand why it goes to wait for signals but it still does not explain where the signal itself is coming from.
I'm saying that neither is this result of signal, nor stack trace shows that any signal handler is called. It just shows call to await.... and await calls pause. That's all
Greetings, Bane.
Strange is that you are using threaded run time (I guess ) but this function is defined only for single threaded variant. This I implied from #if !defined(RTS_SUPPORTS_THREADS)
I'm not using a threaded runtime in this case. It appears that -debug and -threaded are incompatible as I get an error about a mixed debug/ threaded runtime library not being available. I compile with -debug so that I can run +RTS -Ds to check for deadlocks.
Thanks, Joel
_________________________________________________________________ FREE pop-up blocking with the new MSN Toolbar - get it now! http://toolbar.msn.click-url.com/go/onm00200415ave/direct/01/
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
_________________________________________________________________ Don't just search. Find. Check out the new MSN Search! http://search.msn.com/

Understood. But I'm printing things in the signal handler to show that it was triggered. And I trigger it when ^C is pressed (well, one more signal): initSnippets :: IO () initSnippets = do initSSL installHandler sigPIPE Ignore Nothing flip mapM_ [sigTERM, sigINT] $ \sig -> do installHandler sig (handler sig) Nothing where handler sig = Catch $ do trace_ $ "Signal " ++ show sig + + " caught." trace_ "Broadcasting Quit..." broadcast (ForcedQuit :: Event ()) This way I know what the signal was that triggered the handler and I can tell that it was triggered. The deadlock is somewhere else because the handler is not being tripped. The issue of the signal handler being tripped by a phantom ^C (signal 2) is another issue entirely. On Dec 11, 2005, at 6:10 PM, Branimir Maksimovic wrote:
Though I frorgot to add that deadlock can be caused by signal somewhere else (eg other thread) if signal handler eg locks mutex internally or calls some other non asynchronous safe functions like locking functions. This is likely scenario, if you doubt at signal handlers but I don;t know the details . Deadlocks can be caused by other things, not neccessarily signals.

From: Joel Reymont
To: "Branimir Maksimovic" CC: haskell-cafe@haskell.org Subject: Re: [Haskell-cafe] Re: syscall, sigpause and EINTR on Mac OSX Date: Sun, 11 Dec 2005 18:25:47 +0000 Understood. But I'm printing things in the signal handler to show that it was triggered. And I trigger it when ^C is pressed (well, one more signal):
initSnippets :: IO () initSnippets = do initSSL installHandler sigPIPE Ignore Nothing flip mapM_ [sigTERM, sigINT] $ \sig -> do installHandler sig (handler sig) Nothing where handler sig = Catch $ do trace_ $ "Signal " ++ show sig + + " caught." trace_ "Broadcasting Quit..." broadcast (ForcedQuit :: Event ())
This way I know what the signal was that triggered the handler and I can tell that it was triggered. The deadlock is somewhere else because the handler is not being tripped.
After seeing this only I can tell that for example in C++ one can't cout clog cerr or post some event via synchronized event queue or condition variable from signal handler. All of that would result in ghosts and goblins in program. Actually one can't do much at all in signal handlers in multithreaded environment, cause they don;t like each other. If you wan;t to trap ^C then I advise that you give up signal handlers and dedicate one thread to read keyboard events then post those keyboard events like you do from signal handler. That is ignore all signals, but fatal ones in which case you will just abort program (perhaps try some cleanup, if at all possible from signal handler) Hope this helps. Greetings, Bane.
The issue of the signal handler being tripped by a phantom ^C (signal 2) is another issue entirely.
On Dec 11, 2005, at 6:10 PM, Branimir Maksimovic wrote:
Though I frorgot to add that deadlock can be caused by signal somewhere else (eg other thread) if signal handler eg locks mutex internally or calls some other non asynchronous safe functions like locking functions. This is likely scenario, if you doubt at signal handlers but I don;t know the details . Deadlocks can be caused by other things, not neccessarily signals.
_________________________________________________________________ Express yourself instantly with MSN Messenger! Download today it's FREE! http://messenger.msn.click-url.com/go/onm00200471ave/direct/01/

What I do works so I don't see any reason to do it otherwise. Now, it might work by luck and chance, by some ghc magic or otherwise, but it does work and causes me no problems. Not when I press ^C and everything shuts down cleanly. My issues are 1) A phantom sigINT that gets sent to me out of nowhere and 2) A deadlock somewhere in my program that I'm trying to troubleshoot The code: type Child a = (MVar (), TMVar (ClockTime, (Event a)), MVar ThreadId) {-# NOINLINE children #-} children :: MVar [Child a] children = unsafePerformIO $ newMVar [] broadcast :: Show a => Event a -> IO () broadcast event = withMVar children $ \cs -> mapM_ (post event) cs where post event (_, mbx, tmv) = do tid <- readMVar tmv trace_ $ "broadcast: Sending " ++ show event ++ " to " ++ show tid time <- getClockTime atomically $ putTMVar mbx (time, event) return () and data Tracer = Tracer !(MVar Trace) !(MVar Trace) {-# NOINLINE tracer #-} tracer :: Tracer tracer = unsafePerformIO $ startTracer trace_ :: String -> IO () trace_ a = do tid <- myThreadId time <- getClockTime time' <- toCalendarTime time let stamp = formatCalendarTime defaultTimeLocale "%H:%M:%S" time' msg = stamp ++ ": " ++ (show tid) ++ ": " ++ a case tracer of (Tracer inbox _) -> putMVar inbox $! Trace msg On Dec 11, 2005, at 6:43 PM, Branimir Maksimovic wrote:
After seeing this only I can tell that for example in C++ one can't cout clog cerr or post some event via synchronized event queue or condition variable from signal handler. All of that would result in ghosts and goblins in program. Actually one can't do much at all in signal handlers in multithreaded environment, cause they don;t like each other. If you wan;t to trap ^C then I advise that you give up signal handlers and dedicate one thread to read keyboard events then post those keyboard events like you do from signal handler. That is ignore all signals, but fatal ones in which case you will just abort program (perhaps try some cleanup, if at all possible from signal handler)

On Sun, Dec 11, 2005 at 07:09:20PM +0000, Joel Reymont wrote:
{-# NOINLINE children #-} children :: MVar [Child a] children = unsafePerformIO $ newMVar []
This is asking for disaster. children shouldn't have a polymorphic type! Best regards Tomasz -- I am searching for a programmer who is good at least in some of [Haskell, ML, C++, Linux, FreeBSD, math] for work in Warsaw, Poland

Would you care to elaborate? This has not caused any problems for me so far but this is probably due to my usage. On Dec 11, 2005, at 8:09 PM, Tomasz Zielonka wrote:
On Sun, Dec 11, 2005 at 07:09:20PM +0000, Joel Reymont wrote:
{-# NOINLINE children #-} children :: MVar [Child a] children = unsafePerformIO $ newMVar []
This is asking for disaster. children shouldn't have a polymorphic type!

On Sun, Dec 11, 2005 at 08:37:06PM +0000, Joel Reymont wrote:
Would you care to elaborate? This has not caused any problems for me so far but this is probably due to my usage.
This is a know danger of using unsafePerformIO and one reason for "unsafe" in its name.
From http://www.cse.unsw.edu.au/~chak/haskell/ffi/ffi/ffise5.html: Great care should be exercised in the use of this primitive. Not only because of the danger of introducing side effects, but also because unsafePerformIO may compromise typing; to avoid this, the programmer should ensure that the result of unsafePerformIO has a monomorphic type.
If you wonder why, analyze this code and see what happens when you run it. import Control.Concurrent import System.IO.Unsafe {-# NOINLINE children #-} children :: MVar [a] children = unsafePerformIO $ newEmptyMVar main = do putMVar children (["foo", "bar", "baz"]) l <- takeMVar children print (l :: [Integer]) It would be nice if GHC could warn about such situations, at least in the most simple, recognizable cases. Seems like a good task for a new GHC developer. Best regards Tomasz -- I am searching for a programmer who is good at least in some of [Haskell, ML, C++, Linux, FreeBSD, math] for work in Warsaw, Poland

Oh, right. It does not apply in my case, though, so I thought it was safe. I'm not sure what the proper Haskell wording is to explain but it seems like the type system catches if a user of the library tries to use two different a's (Child a) and complains. Exactly what I need as access to children is hidden within my code. On Dec 11, 2005, at 9:10 PM, Tomasz Zielonka wrote:
main = do putMVar children (["foo", "bar", "baz"]) l <- takeMVar children print (l :: [Integer])
It would be nice if GHC could warn about such situations, at least in the most simple, recognizable cases. Seems like a good task for a new GHC developer.

On Sun, Dec 11, 2005 at 10:37:12PM +0000, Joel Reymont wrote:
Oh, right. It does not apply in my case, though, so I thought it was safe.
I'm not sure what the proper Haskell wording is to explain but it seems like the type system catches if a user of the library tries to use two different a's (Child a) and complains. Exactly what I need as access to children is hidden within my code.
If you always use "children" with the same type, then make it the type of "children". On the other hand, if you use "children" in a scoped, local manner, then it's better to move the variable to these local scopes, getting rid of unsafePerformIO. What you did here is a major Haskell sin. I am not going to invest my time searching for bugs in your code until you fix this one ;-) As a fast and dirty solution, I propose using MVar [Dynamic]. Best regards Tomasz -- I am searching for a programmer who is good at least in some of [Haskell, ML, C++, Linux, FreeBSD, math] for work in Warsaw, Poland

No way. Thanks for the suggestion, though ;-). On Dec 12, 2005, at 7:48 AM, Tomasz Zielonka wrote:
As a fast and dirty solution, I propose using MVar [Dynamic].

Hello Joel, this code really looks strange: you asks to create global veriable, but don't say its type :) polymorhism is for functions definitions, any concrete data in Haskell have concrete type Sunday, December 11, 2005, 11:37:06 PM, you wrote: JR> Would you care to elaborate? This has not caused any problems for me JR> so far but this is probably due to my usage. JR> On Dec 11, 2005, at 8:09 PM, Tomasz Zielonka wrote:
On Sun, Dec 11, 2005 at 07:09:20PM +0000, Joel Reymont wrote:
{-# NOINLINE children #-} children :: MVar [Child a] children = unsafePerformIO $ newMVar []
This is asking for disaster. children shouldn't have a polymorphic type!
JR> -- JR> http://wagerlabs.com/ JR> _______________________________________________ JR> Haskell-Cafe mailing list JR> Haskell-Cafe@haskell.org JR> http://www.haskell.org/mailman/listinfo/haskell-cafe -- Best regards, Bulat mailto:bulatz@HotPOP.com

On Dec 12, 2005, at 11:31 AM, Bulat Ziganshin wrote:
Hello Joel,
this code really looks strange: you asks to create global veriable, but don't say its type :) polymorhism is for functions definitions, any concrete data in Haskell have concrete type
It's a long story but I'll try to explain. I would also emphasize that the code works and the type checker complains if I try to use, say, Event String once Event Int has been used. So this is how I do it... This chunk lives in my internal libraries that I deliver to the client. I have some pre-defined events and let the user of the library come up with custom ones. data Event a = Go | Quit | ForcedQuit | NetworkError Exception | Timeout String | Cmd Command | Custom a deriving Show Yes, this looks bad but keep reading! The 'a' is the same throughout. type Child a = (MVar (), TMVar (ClockTime, (Event a)), MVar ThreadId) {-# NOINLINE children #-} children :: MVar [Child a] children = unsafePerformIO $ newMVar [] forkChild :: Show a => (TMVar (ClockTime, (Event a)) -> IO ()) -> IO ThreadId forkChild io = do mvar <- newEmptyMVar mbx <- atomically $ newEmptyTMVar childs <- takeMVar children thread <- newEmptyMVar putMVar children ((mvar, mbx, thread):childs) tid <- forkIO (io mbx `finally` putMVar mvar ()) putMVar thread tid return tid This is the poker bot state. I use the 'b' for the user data type. data World a b = World { ... dispatchers :: ![(String, Dispatcher a b)], trace_filter:: Event a -> Bool, ... user_data :: !(Maybe b) } The monad... type ScriptState a b = ErrorT String (StateT (World a b) IO) type ScriptResult a b = IO (Either String (), World a b) This is the type signature for the bot fun... type Dispatcher a b = Event a -> ((ScriptState a b) (Status a)) data Status a = Start | Eat (Maybe (Event a)) | Skip deriving Show What each bot should return. Eat means do not process any further dispatchers in the list of dispatchers kept in the bot state (World above). Skip will continue processing by calling dispatchers upstream with the same event. Dispatchers can fail thus they are in the ScriptState monad. This bit is actually exported getdata :: Show b => (ScriptState a b) b getdata = do w <- get return $ fromJust $ user_data w setdata :: b -> (ScriptState a b) () setdata b = do w <- get put_ $ w { user_data = Just $ b } launch :: (Show a, Show b) => HostInfo -> Dispatcher a b -> IO () launch hi script = do forkChild $ run hi script liftIO $ sleep_ 10 return () This is what a user "script" looks like. We are almost there, I promise! data CustomEvent = Tables [TableInfo] | LoggedIn | JoinedTable Word32 | SeatTaken Word8 | SeatNotTaken Word8 | DealerChip | Quorum deriving Show main = do initSnippets launch host script sleep_ 2000 -- 2 seconds waitToFinish Notice the call to setdata (). The type of 'b' will not be known without it and ghc will not compile the program. script Go = do startScript setdata () trace 10 "Kicking off" push "goToLobby" $ goToLobby [28] return $ Eat $ Just Go script (Custom (JoinedTable 0)) = do trace 10 "We are in the lobby" return $ Eat $ Just Quit script (Timeout _) = fail $ "Script: Timeout received" script event = do fail $ "script: event: " ++ show event return Skip Now, as soom as I use my custom event in the script, 'a' in the dispatcher signature and everywhere else will be "bound" to CustomEvent and thus the chunk of code below will be resolved. {-# NOINLINE children #-} children :: MVar [Child a] children = unsafePerformIO $ newMVar [] As soon as you try to post a different event somewhere in the script ghc will complain of a type mismatch and suggest that you use CustomEvent instead. Problem solved, everything works. Did I explain this to everyone's satisfaction? Have I supplied enough context? Is my code beautiful and efficient? Finally, does anyone have _constructive_ criticism to offer? :D Thanks, Joel -- http://wagerlabs.com/

From: Joel Reymont
To: "Branimir Maksimovic" CC: haskell-cafe@haskell.org Subject: Re: [Haskell-cafe] Re: syscall, sigpause and EINTR on Mac OSX Date: Sun, 11 Dec 2005 19:09:20 +0000 What I do works so I don't see any reason to do it otherwise.
Oh, I 've seen to many programs with undefined behavior floating around that appears to work.:0) Problem with mt programs is that they just appear to work but in havy load situation those errors show once a while. You have only two choices. Either to clean up code or to live with it. You didn;t properly initialize SSL as per documention and you have problem with signal handlers. Both things will work 99% of the time with spurious crashes on occasion.
Now, it might work by luck and chance, by some ghc magic or otherwise, but it does work and causes me no problems. Not when I press ^C and everything shuts down cleanly.
My issues are
1) A phantom sigINT that gets sent to me out of nowhere and
This should be enough reason to scan for keyboard events instead. There is no guarantee that SIGINT would be sent only by keyboard.
2) A deadlock somewhere in my program that I'm trying to troubleshoot
The code:
type Child a = (MVar (), TMVar (ClockTime, (Event a)), MVar ThreadId)
{-# NOINLINE children #-} children :: MVar [Child a] children = unsafePerformIO $ newMVar []
Just to comment about memory allocation and signals. Suppose your malloc locks internally. Let's say thread in the background performs malloc, malloc grabs the lock. Signal is raised , your handler is called , which calls malloc and boom deadlock. If malloc does implement lock free algorithm internaly you don't have a problem, but that's unlikely.
broadcast :: Show a => Event a -> IO () broadcast event = withMVar children $ \cs -> mapM_ (post event) cs where post event (_, mbx, tmv) = do tid <- readMVar tmv trace_ $ "broadcast: Sending " ++ show event ++ " to " ++ show tid time <- getClockTime atomically $ putTMVar mbx (time, event)
this is lock? same situation as with malloc. thread locks, then signal arrives , then handler, then deadlock. Greetings, Bane. _________________________________________________________________ Express yourself instantly with MSN Messenger! Download today it's FREE! http://messenger.msn.click-url.com/go/onm00200471ave/direct/01/

Allright, I _am_ convinced. How do I ready ^C from the keyboard??? On Dec 11, 2005, at 10:02 PM, Branimir Maksimovic wrote:
This should be enough reason to scan for keyboard events instead. There is no guarantee that SIGINT would be sent only by keyboard.

^C seems to be '\ETX' so ignoring SIGINT and using getChar should probably do it. On Dec 11, 2005, at 11:31 PM, Joel Reymont wrote:
Allright, I _am_ convinced. How do I ready ^C from the keyboard???
On Dec 11, 2005, at 10:02 PM, Branimir Maksimovic wrote:
This should be enough reason to scan for keyboard events instead. There is no guarantee that SIGINT would be sent only by keyboard.

From: Joel Reymont
To: Branimir Maksimovic CC: haskell-cafe@haskell.org Subject: Re: [Haskell-cafe] Re: syscall, sigpause and EINTR on Mac OSX Date: Sun, 11 Dec 2005 23:31:44 +0000 Allright, I _am_ convinced. How do I ready ^C from the keyboard???
If this is some daemon program you can't. Perhaps that should be a daemon. Just make console client that will read commands from keyboard and send to your program. In single threaded client you can handle ^C if you like in signal handler without problem. That can be gui program if you like , but console one should be enough. You can implement eg: status, start, pause, quit and so. For now quit will be just fine, later you can add more commands. Make one listener thread in your program for such connections and that's it. Or just use telnet (this isn't safe though), but you can restrict connections. And don't forget to mask SIGINT :) Greetings, Bane.
On Dec 11, 2005, at 10:02 PM, Branimir Maksimovic wrote:
This should be enough reason to scan for keyboard events instead. There is no guarantee that SIGINT would be sent only by keyboard.
_________________________________________________________________ Express yourself instantly with MSN Messenger! Download today it's FREE! http://messenger.msn.click-url.com/go/onm00200471ave/direct/01/

My client _is_ single-threaded, I do not use bound (OS) threads at all. Does this shed any light on why my OpenSSL stuff is working as well as my signal handler? ;-) On Dec 12, 2005, at 12:21 AM, Branimir Maksimovic wrote:
In single threaded client you can handle ^C if you like in signal handler without problem. That can be gui program if you like , but console one should be enough. You can implement eg: status, start, pause, quit and so. For now quit will be just fine, later you can add more commands. Make one listener thread in your program for such connections and that's it.

From: Joel Reymont
To: "Branimir Maksimovic" CC: haskell-cafe@haskell.org Subject: Re: [Haskell-cafe] Re: syscall, sigpause and EINTR on Mac OSX Date: Mon, 12 Dec 2005 02:28:54 +0000 My client _is_ single-threaded, I do not use bound (OS) threads at all. Does this shed any light on why my OpenSSL stuff is working as well as my signal handler? ;-)
If your app is single threaded you should be ok. But then nothing is executed concurrently? why locking at all then? You wouldn;t have problems with deadlocks and signals if single threaded without locking. Now, I m really puzzled. Greetings, Bane.
On Dec 12, 2005, at 12:21 AM, Branimir Maksimovic wrote:
In single threaded client you can handle ^C if you like in signal handler without problem. That can be gui program if you like , but console one should be enough. You can implement eg: status, start, pause, quit and so. For now quit will be just fine, later you can add more commands. Make one listener thread in your program for such connections and that's it.
_________________________________________________________________ Don't just search. Find. Check out the new MSN Search! http://search.msn.click-url.com/go/onm00200636ave/direct/01/

The app is multi-threaded but uses lightweight threads (unbound). On Dec 12, 2005, at 4:24 AM, Branimir Maksimovic wrote:
If your app is single threaded you should be ok. But then nothing is executed concurrently? why locking at all then? You wouldn;t have problems with deadlocks and signals if single threaded without locking. Now, I m really puzzled.

From: Joel Reymont
To: Branimir Maksimovic CC: haskell-cafe@haskell.org Subject: Re: [Haskell-cafe] Re: syscall, sigpause and EINTR on Mac OSX Date: Mon, 12 Dec 2005 09:00:18 +0000 The app is multi-threaded but uses lightweight threads (unbound).
So that means user space threads, in comparison to kernel space threads? If this is so then all of what I said still stands, because userspace threads are executed concurrently too, just that more user threads share same lwp's on Solaris for example, if I understand correctly, taht is user space thread is not bound to single lwp. On linux all threads are kernel space threads. Not sure about windows though. If GHC implements user space threads that would be great, but that does not helps with your problems. Greetings, Bane.
On Dec 12, 2005, at 4:24 AM, Branimir Maksimovic wrote:
If your app is single threaded you should be ok. But then nothing is executed concurrently? why locking at all then? You wouldn;t have problems with deadlocks and signals if single threaded without locking. Now, I m really puzzled.
_________________________________________________________________ Express yourself instantly with MSN Messenger! Download today it's FREE! http://messenger.msn.click-url.com/go/onm00200471ave/direct/01/

Hello Branimir, Monday, December 12, 2005, 2:52:47 PM, you wrote: BM> If GHC implements user space threads that would be great, BM> but that does not helps with your problems. ghc (and any other haskell implememtations which implements Concurrent Haskell extensions) implement IT'S OWN threads. switching occurcs just inside RTS. this is how we can manage thousands of threads with acceptable speed. see "Writing High-Performance Server Applications in Haskell, Case Study: A Haskell Web Server" (http://www.haskell.org/~simonmar/papers/web-server.ps.gz) -- Best regards, Bulat mailto:bulatz@HotPOP.com

On Dec 11, 2005, at 10:02 PM, Branimir Maksimovic wrote:
Problem with mt programs is that they just appear to work but in havy load situation those errors show once a while.
My loads are pretty heavy. Did not see any problems with SSL yet.
This should be enough reason to scan for keyboard events instead. There is no guarantee that SIGINT would be sent only by keyboard.
import System.Posix.Signals main = do installHandler sigINT Ignore Nothing x <- getChar if x == '\ETX' then do print "Gotcha!" else do print "Try again!" main This does not work for ^C. Can it actually be done? Of course I can just read "q" but that would be too simple :-). Thanks, Joel -- http://wagerlabs.com/

From: Joel Reymont
To: Branimir Maksimovic CC: haskell-cafe@haskell.org Subject: Re: [Haskell-cafe] Re: syscall, sigpause and EINTR on Mac OSX Date: Sun, 11 Dec 2005 23:52:19 +0000 On Dec 11, 2005, at 10:02 PM, Branimir Maksimovic wrote:
This does not work for ^C. Can it actually be done? Of course I can just read "q" but that would be too simple :-).
Perhaps you can implement this in Haskell? dedicate single thread to just handle ^C signal? this is how you should do it properly, but I would go with console client anyway: http://www.scit.wlv.ac.uk/cgi-bin/mansec?3T+thr_sigsetmask Greetings, Bane.
Thanks, Joel
_________________________________________________________________ Express yourself instantly with MSN Messenger! Download today it's FREE! http://messenger.msn.click-url.com/go/onm00200471ave/direct/01/

Hello Branimir, Monday, December 12, 2005, 3:47:12 AM, you wrote: BM> Perhaps you can implement this in Haskell? dedicate single thread to BM> just handle ^C signal? this is how you should do it properly, BM> but I would go with console client anyway: moreover, that must be the MAIN THREAD, as i sayed in previous msg. smth like this: main = do id <- forkIO real_main installInterruptsHandler (killThread id) wait forever... i will try it in my windows prog -- Best regards, Bulat mailto:bulatz@HotPOP.com

Joel Reymont wrote:
This should be enough reason to scan for keyboard events instead. There is no guarantee that SIGINT would be sent only by keyboard.
import System.Posix.Signals
main = do installHandler sigINT Ignore Nothing x <- getChar if x == '\ETX' then do print "Gotcha!" else do print "Try again!" main
This does not work for ^C. Can it actually be done? Of course I can just read "q" but that would be too simple :-).
You have to put the terminal into "raw" mode to be able to read any
character which is normally processed by the TTY driver, e.g.:
import System.Posix.Terminal
atts <- getTerminalAttributes (handleToFd stdin)
let atts' = withoutMode atts ProcessInput
setTerminalAttributes (handleToFd stdin) atts' Immediately
This disables all input processing, e.g. line-editing and CR->LF
translation (i.e. pressing the Enter/Return key will result in CR, not
LF).
Remember to set it back before exiting.
--
Glynn Clements

Hello Branimir, Sunday, December 11, 2005, 9:43:08 PM, you wrote: BM> After seeing this only I can tell that for example in C++ one can't cout BM> clog cerr BM> or post some event via synchronized event queue or condition variable BM> from signal handler. BM> All of that would result in ghosts and goblins in program. it is not the case for Haskell. at least, the following handler works very well in GHC 6.4/windows: handleCtrlBreak handler action = do myThread <- myThreadId let onBreak event = do putStr " ^Break!" programTerminated =: True handler killThread myThread bracket (installHandler$ Catch onBreak) (installHandler) $ \oldHandler -> do action
This way I know what the signal was that triggered the handler and I can tell that it was triggered. The deadlock is somewhere else because the handler is not being tripped.
but in 6.4.1 (ATTENTION, JOEL!) this code was breaked. i does an investigation and found that in 6.4.1 with -threaded ^Break hadnling works only in main program thread! i complained several days ago in ghc-bugs list. you, Joel, can get example i posted there, replace windows-specific ^Break handling with Unix one and test it -- Best regards, Bulat mailto:bulatz@HotPOP.com

I'm positively not catching the ^C in the main thread. I just went ahead and disabled ^C handling alltogether. On Dec 12, 2005, at 10:50 AM, Bulat Ziganshin wrote:
but in 6.4.1 (ATTENTION, JOEL!) this code was breaked. i does an investigation and found that in 6.4.1 with -threaded ^Break hadnling works only in main program thread! i complained several days ago in ghc-bugs list. you, Joel, can get example i posted there, replace windows-specific ^Break handling with Unix one and test it

Linking ... /usr/bin/ld: can't locate file for: -lHSrts_thr_debug collect2: ld returned 1 exit status How do I get a threaded+debug runtime? On Dec 11, 2005, at 4:50 PM, Branimir Maksimovic wrote:
Strange is that you are using threaded run time (I guess ) but this function is defined only for single threaded variant. This I implied from #if !defined(RTS_SUPPORTS_THREADS)

Would there be any advantage in doing this? There's no deadlock info produced for a debug threaded runtime, for example. Not according to ghc/rts/Schedule.c. Of course I could print the capabilities of the main thread (TSO structure) and see what it's blocked on, etc. but I could do that just as well without using -threaded. My issue seems to be that of a deadlock. Strangely enough, building with -debug and running with +RTS -Ds seems to go through all the way. I think I'm not completely reproducing the previous deadlock situation, though, so I'm working on that. On Dec 11, 2005, at 5:12 PM, Peter Simons wrote:
Joel Reymont writes:
How do I get a threaded+debug runtime?
You have to build GHC from source code for that. When you do, make sure your ${srcdir}/ghc/mk/build.mk file contains:
GhcRTSWays += thr_debug

I've got two versions: HSrts_thr and HSrts_thr_p I don't know what's second for? but there is only one with debug in it's name. So I'm not much of a help here. Greetings, Bane.
From: Joel Reymont
To: Branimir Maksimovic CC: haskell-cafe@haskell.org Subject: Re: [Haskell-cafe] Re: syscall, sigpause and EINTR on Mac OSX Date: Sun, 11 Dec 2005 17:00:50 +0000 Linking ... /usr/bin/ld: can't locate file for: -lHSrts_thr_debug collect2: ld returned 1 exit status
How do I get a threaded+debug runtime?
On Dec 11, 2005, at 4:50 PM, Branimir Maksimovic wrote:
Strange is that you are using threaded run time (I guess ) but this function is defined only for single threaded variant. This I implied from #if !defined(RTS_SUPPORTS_THREADS)
_________________________________________________________________ Express yourself instantly with MSN Messenger! Download today it's FREE! http://messenger.msn.click-url.com/go/onm00200471ave/direct/01/

The second one is the threaded and profiled runtime. On Dec 11, 2005, at 5:14 PM, Branimir Maksimovic wrote:
I've got two versions: HSrts_thr and HSrts_thr_p I don't know what's second for? but there is only one with debug in it's name. So I'm not much of a help here.

Nothing like answering your own questions... There's no deadlock information for the threaded version of the runtime so I would not have deadlock information if I were to compile with -threaded. On Dec 11, 2005, at 5:00 PM, Joel Reymont wrote:
Linking ... /usr/bin/ld: can't locate file for: -lHSrts_thr_debug collect2: ld returned 1 exit status
How do I get a threaded+debug runtime?
On Dec 11, 2005, at 4:50 PM, Branimir Maksimovic wrote:
Strange is that you are using threaded run time (I guess ) but this function is defined only for single threaded variant. This I implied from #if !defined(RTS_SUPPORTS_THREADS)
participants (6)
-
Branimir Maksimovic
-
Bulat Ziganshin
-
Glynn Clements
-
Joel Reymont
-
Peter Simons
-
Tomasz Zielonka