[Haskell-cafe] Re: syscall, sigpause and EINTR on Mac OSX

Joel Reymont joelr1 at gmail.com
Sun Dec 11 14:09:20 EST 2005


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)

--
http://wagerlabs.com/







More information about the Haskell-Cafe mailing list