On 17 February 2011 20:34, Bas van Dijk <v.dijk....@gmail.com> wrote:
> Speaking of Uniques: what is the best way to create them?
> I see 3 options:

There may be a 4th option but it requires changing the
System.Event.Manager.registerTimeout function from:

registerTimeout :: EventManager
                -> Int
                -> TimeoutCallback
                -> IO TimeoutKey

to:

registerTimeout :: EventManager
                -> Int
                -> (TimeoutKey -> TimeoutCallback)
                -> IO TimeoutKey

Then we can use the TimeoutKey as our Unique (Note that a TimeoutKey
is actually a newtype for a Unique):

newtype Timeout = Timeout TimeoutKey deriving Eq

instance Exception Timeout

timeout :: Int -> IO a -> IO (Maybe a)
timeout usecs f
    | usecs <  0 = fmap Just f
    | usecs == 0 = return Nothing
    | otherwise  = do
        myTid <- myThreadId
        Just mgr <- readIORef eventManager
        mask $ \restore -> do
          reg <- registerTimeout mgr usecs $ \reg -> throwTo myTid $ Timeout reg
          let unregTimeout = M.unregisterTimeout mgr reg
          (restore (fmap Just f) >>= \mb -> unregTimeout >> return mb)
            `catch` \e ->
                case fromException e of
                  Just (Timeout reg') | reg' == reg -> return Nothing
                  _ -> unregTimeout >> throwIO e

Bas

_______________________________________________
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe

Reply via email to