{-# LANGUAGE CPP #-}
{-# LANGUAGE DeriveDataTypeable #-}
module Network.Wai.Handler.Warp.Timeout (
Manager
, TimeoutAction
, Handle
, initialize
, stopManager
, killManager
, withManager
, register
, registerKillThread
, tickle
, cancel
, pause
, resume
, TimeoutThread (..)
) where
import Control.Concurrent (myThreadId)
import qualified Control.Exception as E
import Control.Reaper
import Data.Typeable (Typeable)
import Data.IORef (IORef)
import qualified Data.IORef as I
type Manager = Reaper [Handle] Handle
type TimeoutAction = IO ()
data Handle = Handle !(IORef TimeoutAction) !(IORef State)
data State = Active
| Inactive
| Paused
| Canceled
initialize :: Int -> IO Manager
initialize timeout = mkReaper defaultReaperSettings
{ reaperAction = mkListAction prune
, reaperDelay = timeout
}
where
prune m@(Handle actionRef stateRef) = do
state <- I.atomicModifyIORef' stateRef (\x -> (inactivate x, x))
case state of
Inactive -> do
onTimeout <- I.readIORef actionRef
onTimeout `E.catch` ignoreAll
return Nothing
Canceled -> return Nothing
_ -> return $ Just m
inactivate Active = Inactive
inactivate x = x
stopManager :: Manager -> IO ()
stopManager mgr = E.mask_ (reaperStop mgr >>= mapM_ fire)
where
fire (Handle actionRef _) = do
onTimeout <- I.readIORef actionRef
onTimeout `E.catch` ignoreAll
ignoreAll :: E.SomeException -> IO ()
ignoreAll _ = return ()
killManager :: Manager -> IO ()
killManager = reaperKill
register :: Manager -> TimeoutAction -> IO Handle
register mgr onTimeout = do
actionRef <- I.newIORef onTimeout
stateRef <- I.newIORef Active
let h = Handle actionRef stateRef
reaperAdd mgr h
return h
registerKillThread :: Manager -> TimeoutAction -> IO Handle
registerKillThread m onTimeout = do
tid <- myThreadId
register m $ onTimeout `E.finally` E.throwTo tid TimeoutThread
data TimeoutThread = TimeoutThread
deriving Typeable
instance E.Exception TimeoutThread where
toException = E.asyncExceptionToException
fromException = E.asyncExceptionFromException
instance Show TimeoutThread where
show TimeoutThread = "Thread killed by Warp's timeout reaper"
tickle :: Handle -> IO ()
tickle (Handle _ stateRef) = I.writeIORef stateRef Active
cancel :: Handle -> IO ()
cancel (Handle actionRef stateRef) = do
I.writeIORef actionRef (return ())
I.writeIORef stateRef Canceled
pause :: Handle -> IO ()
pause (Handle _ stateRef) = I.writeIORef stateRef Paused
resume :: Handle -> IO ()
resume = tickle
withManager :: Int
-> (Manager -> IO a)
-> IO a
withManager timeout f = do
man <- initialize timeout
f man