{-# LANGUAGE CPP, ScopedTypeVariables, ExistentialQuantification, RankNTypes #-}
module System.FSNotify
(
Event(..)
, EventChannel
, eventIsDirectory
, eventTime
, eventPath
, Action
, ActionPredicate
, WatchManager
, withManager
, startManager
, stopManager
, defaultConfig
, WatchConfig(..)
, Debounce(..)
, withManagerConf
, startManagerConf
, StopListening
, isPollingManager
, watchDir
, watchDirChan
, watchTree
, watchTreeChan
) where
import Prelude hiding (FilePath)
import Control.Concurrent
import Control.Concurrent.Async
import Control.Exception
import Control.Monad
import Data.Maybe
import System.FSNotify.Polling
import System.FSNotify.Types
import System.FilePath
import System.FSNotify.Listener (StopListening)
#ifdef OS_Linux
import System.FSNotify.Linux
#else
# ifdef OS_Win32
import System.FSNotify.Win32
# else
# ifdef OS_Mac
import System.FSNotify.OSX
# else
type NativeManager = PollManager
# endif
# endif
#endif
data WatchManager
= forall manager . FileListener manager
=> WatchManager
WatchConfig
manager
(MVar (Maybe (IO ())))
defaultConfig :: WatchConfig
defaultConfig =
WatchConfig
{ confDebounce = DebounceDefault
, confPollInterval = 10^(6 :: Int)
, confUsePolling = False
}
withManager :: (WatchManager -> IO a) -> IO a
withManager = withManagerConf defaultConfig
startManager :: IO WatchManager
startManager = startManagerConf defaultConfig
stopManager :: WatchManager -> IO ()
stopManager (WatchManager _ wm cleanupVar) = do
mbCleanup <- swapMVar cleanupVar Nothing
fromMaybe (return ()) mbCleanup
killSession wm
withManagerConf :: WatchConfig -> (WatchManager -> IO a) -> IO a
withManagerConf conf = bracket (startManagerConf conf) stopManager
startManagerConf :: WatchConfig -> IO WatchManager
startManagerConf conf
| confUsePolling conf = pollingManager
| otherwise = initSession >>= createManager
where
createManager :: Maybe NativeManager -> IO WatchManager
createManager (Just nativeManager) =
WatchManager conf nativeManager <$> cleanupVar
createManager Nothing = pollingManager
pollingManager =
WatchManager conf <$> createPollManager <*> cleanupVar
cleanupVar = newMVar (Just (return ()))
isPollingManager :: WatchManager -> Bool
isPollingManager (WatchManager _ wm _) = usesPolling wm
watchDirChan :: WatchManager -> FilePath -> ActionPredicate -> EventChannel -> IO StopListening
watchDirChan (WatchManager db wm _) = listen db wm
watchTreeChan :: WatchManager -> FilePath -> ActionPredicate -> EventChannel -> IO StopListening
watchTreeChan (WatchManager db wm _) = listenRecursive db wm
watchDir :: WatchManager -> FilePath -> ActionPredicate -> Action -> IO StopListening
watchDir wm = threadChan listen wm
watchTree :: WatchManager -> FilePath -> ActionPredicate -> Action -> IO StopListening
watchTree wm = threadChan listenRecursive wm
threadChan
:: (forall sessionType . FileListener sessionType =>
WatchConfig -> sessionType -> FilePath -> ActionPredicate -> EventChannel -> IO StopListening)
-> WatchManager -> FilePath -> ActionPredicate -> Action -> IO StopListening
threadChan listenFn (WatchManager db listener cleanupVar) path actPred action =
modifyMVar cleanupVar $ \mbCleanup -> case mbCleanup of
Nothing -> return (Nothing, return ())
Just cleanup -> do
chan <- newChan
asy <- async $ readEvents chan action
stopListener <- listenFn db listener path actPred chan
let cleanThisUp = cancel asy
return
( Just $ cleanup >> cleanThisUp
, stopListener >> cleanThisUp
)
readEvents :: EventChannel -> Action -> IO ()
readEvents chan action = forever $ do
event <- readChan chan
us <- myThreadId
forkFinally (action event) $ either (throwTo us) (const $ return ())
#if !MIN_VERSION_base(4,6,0)
forkFinally :: IO a -> (Either SomeException a -> IO ()) -> IO ThreadId
forkFinally action and_then =
mask $ \restore ->
forkIO $ try (restore action) >>= and_then
#endif