module Streamly.FSNotify (
FSEntryType(..), Event(..), StopWatching,
eventPath, eventTime, eventFSEntry,
EventPredicate(..),
isDirectory, hasExtension, isCreation, isModification, isDeletion, isBasic, invert, conj, disj,
watchDirectory, watchDirectoryWith, watchTree, watchTreeWith,
) where
import Control.Arrow ((>>>))
import Control.Concurrent.Chan (newChan, readChan)
import Control.Monad.IO.Class (MonadIO(..))
import Data.Bool (bool)
import Data.Semiring (Semiring(..))
import Data.Text (Text, pack)
import Data.Time.Clock (UTCTime)
import Streamly (IsStream, MonadAsync)
import System.Path (Path, FsPath(..), FileExt, Absolute, isExtensionOf, toFilePath, makeAbsolute, fromAbsoluteFilePath)
import qualified Streamly.Prelude as SP
import qualified System.FSNotify as FSN
data FSEntryType = Dir | NotDir
deriving (Eq, Show, Read, Bounded, Enum)
data Event
= Added (Path Absolute) UTCTime FSEntryType
| Modified (Path Absolute) UTCTime FSEntryType
| Removed (Path Absolute) UTCTime FSEntryType
| Other (Path Absolute) UTCTime Text
deriving (Eq, Show)
type StopWatching m = m ()
eventPath :: Event -> FsPath
eventPath = \case
Added p _ _ -> FsPath p
Modified p _ _ -> FsPath p
Removed p _ _ -> FsPath p
Other p _ _ -> FsPath p
eventTime :: Event -> UTCTime
eventTime = \case
Added _ t _ -> t
Modified _ t _ -> t
Removed _ t _ -> t
Other _ t _ -> t
eventFSEntry :: Event -> Maybe FSEntryType
eventFSEntry = \case
Added _ _ e -> Just e
Modified _ _ e -> Just e
Removed _ _ e -> Just e
Other{} -> Nothing
newtype EventPredicate = EventPredicate { runPredicate :: Event -> Bool }
instance Semiring EventPredicate where
(EventPredicate f) `plus` (EventPredicate g) = EventPredicate $ (||) <$> f <*> g
zero = nothing
(EventPredicate f) `times` (EventPredicate g) = EventPredicate $ (&&) <$> f <*> g
one = everything
conj :: EventPredicate -> EventPredicate -> EventPredicate
conj = times
disj :: EventPredicate -> EventPredicate -> EventPredicate
disj = plus
everything :: EventPredicate
everything = EventPredicate . const $ True
nothing :: EventPredicate
nothing = EventPredicate . const $ False
isDirectory :: EventPredicate
isDirectory = EventPredicate $ eventFSEntry >>> \case
Nothing -> False
Just Dir -> True
Just NotDir -> False
hasExtension :: FileExt -> EventPredicate
hasExtension fe = EventPredicate $ isExtensionOf fe . \case
Added p _ _ -> p
Modified p _ _ -> p
Removed p _ _ -> p
Other p _ _ -> p
isCreation :: EventPredicate
isCreation = EventPredicate $ \case
Added{} -> True
_ -> False
isModification :: EventPredicate
isModification = EventPredicate $ \case
Modified{} -> True
_ -> False
isDeletion :: EventPredicate
isDeletion = EventPredicate $ \case
Removed{} -> True
_ -> False
isBasic :: EventPredicate
isBasic = EventPredicate $ \case
Other{} -> False
_ -> True
invert :: EventPredicate -> EventPredicate
invert (EventPredicate f) = EventPredicate $ not . f
watchDirectory :: (IsStream t, MonadAsync m) => FsPath -> EventPredicate -> m (StopWatching m, t m Event)
watchDirectory = watch FSN.watchDirChan FSN.defaultConfig
watchDirectoryWith :: (IsStream t, MonadAsync m) =>
FSN.WatchConfig -> FsPath -> EventPredicate -> m (StopWatching m, t m Event)
watchDirectoryWith = watch FSN.watchDirChan
watchTree :: (IsStream t, MonadAsync m) => FsPath -> EventPredicate -> m (StopWatching m, t m Event)
watchTree = watch FSN.watchTreeChan FSN.defaultConfig
watchTreeWith :: (IsStream t, MonadAsync m) => FSN.WatchConfig -> FsPath -> EventPredicate -> m (StopWatching m, t m Event)
watchTreeWith = watch FSN.watchTreeChan
watch :: (IsStream t, MonadAsync m) =>
(FSN.WatchManager -> FilePath -> FSN.ActionPredicate -> FSN.EventChannel -> IO FSN.StopListening) ->
FSN.WatchConfig -> FsPath -> EventPredicate -> m (StopWatching m, t m Event)
watch f conf p predicate = do
manager <- liftIO . FSN.startManagerConf $ conf
fp <- toFilePath <$> liftIO (makeAbsolute p)
let pred' = runPredicate predicate . mungeEvent
chan <- liftIO newChan
stop <- liftIO $ f manager fp pred' chan
let reallyStop = liftIO stop >> liftIO (FSN.stopManager manager)
pure (reallyStop, SP.repeatM . liftIO . fmap mungeEvent $ readChan chan)
mungeEvent :: FSN.Event -> Event
mungeEvent = \case
FSN.Added p t b-> Added (fromAbsoluteFilePath p) t (isDir b)
FSN.Modified p t b-> Modified (fromAbsoluteFilePath p) t (isDir b)
FSN.Removed p t b-> Modified (fromAbsoluteFilePath p) t (isDir b)
FSN.Unknown p t s-> Other (fromAbsoluteFilePath p) t (pack s)
isDir :: Bool -> FSEntryType
isDir = bool NotDir Dir