module System.FSNotify.Devel
( treeExtAny, treeExtExists,
doAllEvents,
allEvents, existsEvents
) where
import Data.Text
import Prelude hiding (FilePath)
import System.FSNotify
import System.FSNotify.Path (hasThisExtension)
import System.FilePath
treeExtExists :: WatchManager
-> FilePath
-> Text
-> (FilePath -> IO ())
-> IO StopListening
treeExtExists man dir ext action =
watchTree man dir (existsEvents $ flip hasThisExtension ext) (doAllEvents action)
treeExtAny :: WatchManager
-> FilePath
-> Text
-> (FilePath -> IO ())
-> IO StopListening
treeExtAny man dir ext action =
watchTree man dir (allEvents $ flip hasThisExtension ext) (doAllEvents action)
doAllEvents :: Monad m => (FilePath -> m ()) -> Event -> m ()
doAllEvents action event =
case event of
Added f _ _ -> action f
Modified f _ _ -> action f
Removed f _ _ -> action f
Unknown f _ _ -> action f
existsEvents :: (FilePath -> Bool) -> (Event -> Bool)
existsEvents filt event =
case event of
Added f _ _ -> filt f
Modified f _ _ -> filt f
Removed _ _ _ -> False
Unknown _ _ _ -> False
allEvents :: (FilePath -> Bool) -> (Event -> Bool)
allEvents filt event =
case event of
Added f _ _ -> filt f
Modified f _ _ -> filt f
Removed f _ _ -> filt f
Unknown f _ _ -> filt f