module Network.Wai.Handler.Warp.Timeout (
  
    Manager
  , TimeoutAction
  , Handle
  
  , initialize
  , stopManager
  , withManager
  
  , register
  , registerKillThread
  
  , tickle
  , cancel
  , pause
  , resume
  
  , TimeoutThread (..)
  ) where
#ifndef MIN_VERSION_base
#define MIN_VERSION_base(x,y,z) 1
#endif
#if MIN_VERSION_base(4,6,0)
import Control.Concurrent (mkWeakThreadId, ThreadId)
#else
import GHC.Conc (ThreadId(..))
import GHC.Exts (mkWeak#)
import GHC.IO (IO (IO))
#endif
import Control.Concurrent (myThreadId)
import qualified Control.Exception as E
import GHC.Weak (Weak (..))
import Network.Wai.Handler.Warp.IORef (IORef)
import qualified Network.Wai.Handler.Warp.IORef as I
import System.Mem.Weak (deRefWeak)
import Data.Typeable (Typeable)
import Control.Reaper
type Manager = Reaper [Handle] Handle
type TimeoutAction = IO ()
data Handle = Handle 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 onTimeout iactive) = do
        state <- I.atomicModifyIORef' iactive (\x -> (inactivate x, x))
        case state of
            Inactive -> do
                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 onTimeout _) = onTimeout `E.catch` ignoreAll
ignoreAll :: E.SomeException -> IO ()
ignoreAll _ = return ()
register :: Manager -> TimeoutAction -> IO Handle
register mgr onTimeout = do
    iactive <- I.newIORef Active
    let h = Handle onTimeout iactive
    reaperAdd mgr h
    return h
registerKillThread :: Manager -> IO Handle
registerKillThread m = do
    wtid <- myThreadId >>= mkWeakThreadId
    register m $ killIfExist wtid
killIfExist :: Weak ThreadId -> TimeoutAction
killIfExist wtid = deRefWeak wtid >>= maybe (return ()) (`E.throwTo` TimeoutThread)
data TimeoutThread = TimeoutThread
    deriving Typeable
instance E.Exception TimeoutThread
instance Show TimeoutThread where
    show TimeoutThread = "Thread killed by Warp's timeout reaper"
#if !MIN_VERSION_base(4,6,0)
mkWeakThreadId :: ThreadId -> IO (Weak ThreadId)
mkWeakThreadId t@(ThreadId t#) = IO $ \s ->
   case mkWeak# t# t Nothing s of
      (# s1, w #) -> (# s1, Weak w #)
#endif
tickle :: Handle -> IO ()
tickle (Handle _ iactive) = I.writeIORef iactive Active
cancel :: Handle -> IO ()
cancel (Handle _ iactive) = I.writeIORef iactive Canceled
pause :: Handle -> IO ()
pause (Handle _ iactive) = I.writeIORef iactive Paused
resume :: Handle -> IO ()
resume = tickle
withManager :: Int 
            -> (Manager -> IO a)
            -> IO a
withManager timeout f = do
    
    man <- initialize timeout
    f man