Copyright | (C) Koz Ross 2019 |
---|---|
License | GPL version 3.0 or later |
Maintainer | koz.ross@retro-freedom.nz |
Stability | Experimental |
Portability | GHC only |
Safe Haskell | Trustworthy |
Language | Haskell2010 |
Introduction
This provides file watching as a Streamly stream. You can either watch recursively (namely, a directory's contents and all its subdirectories as well), or not. You can also filter out file system events you are not interested in. Lastly, we provide a compositional scheme for constructing filters for file system events.
Example
This example program watches /home/koz/c-project
(and any of its
subdirectories) for added or modified
files with a .c
extension, and emits the change to the terminal, along with a
timestamp of when it happened, forever:
{-# LANGUAGE LambdaCase #-} import Streamly.FSNotify (EventPredicate, hasExtension, isDirectory, invert, isDeletion, conj, watchTree) import System.Path (FsPath, FileExt, fromFilePath) import qualified Streamly.Prelude as SP -- conj -> both must be true -- invert -> true when the argument would be false and vice versa isCSourceFile :: EventPredicate isCSourceFile = hasExtension (FileExt "c") `conj` (invert isDirectory) notDeletion :: EventPredicate notDeletion = invert isDeletion srcPath :: FsPath srcPath = fromFilePath "/home/koz/c-project" -- first value given by watchTree stops the watcher -- we don't use it here, but if you want to, just call it main :: IO () main = do (_, stream) <- watchTree srcPath (isCSourceFile `conj` notDeletion) SP.drain . SP.mapM go $ stream where go = \case (Added p t _) -> putStrLn ("Created: " ++ show p ++ " at " ++ show t) (Modified p t _) -> putStrLn ("Modified: " ++ show p ++ " at " ++ show t) _ -> pure ()
Synopsis
- data FSEntryType
- data Event
- type StopWatching m = m ()
- eventPath :: Event -> FsPath
- eventTime :: Event -> UTCTime
- eventFSEntry :: Event -> Maybe FSEntryType
- newtype EventPredicate = EventPredicate {
- runPredicate :: Event -> Bool
- isDirectory :: EventPredicate
- hasExtension :: FileExt -> EventPredicate
- isCreation :: EventPredicate
- isModification :: EventPredicate
- isDeletion :: EventPredicate
- isBasic :: EventPredicate
- invert :: EventPredicate -> EventPredicate
- conj :: EventPredicate -> EventPredicate -> EventPredicate
- disj :: EventPredicate -> EventPredicate -> EventPredicate
- watchDirectory :: (IsStream t, MonadAsync m) => FsPath -> EventPredicate -> m (StopWatching m, t m Event)
- watchDirectoryWith :: (IsStream t, MonadAsync m) => WatchConfig -> FsPath -> EventPredicate -> m (StopWatching m, t m Event)
- watchTree :: (IsStream t, MonadAsync m) => FsPath -> EventPredicate -> m (StopWatching m, t m Event)
- watchTreeWith :: (IsStream t, MonadAsync m) => WatchConfig -> FsPath -> EventPredicate -> m (StopWatching m, t m Event)
Basic types
data FSEntryType Source #
Allows us to designate Event
s as being fired by a directory or a
non-directory entry.
Instances
A file system notification.
type StopWatching m = m () Source #
A function, which, when executed, stops a file system watch.
eventFSEntry :: Event -> Maybe FSEntryType Source #
Helper to retrieve whether the event stems from a directory or not.
Returns Nothing
if the event is not 'basic' (that is, not a creation,
modification or deletion).
Events and predicates
newtype EventPredicate Source #
A 'test' for whether we want to 'notice' an event. Should return True
for events we care about.
EventPredicate | |
|
Instances
Semiring EventPredicate Source # |
Both of these can be made into a If you want an instance of |
Defined in Streamly.FSNotify plus :: EventPredicate -> EventPredicate -> EventPredicate # zero :: EventPredicate # times :: EventPredicate -> EventPredicate -> EventPredicate # one :: EventPredicate # fromNatural :: Natural -> EventPredicate # |
isDirectory :: EventPredicate Source #
Allows through events that are caused by directories. Note that this will assume that non-'basic' events (that is, not creations, modifications or deletions) do not stem from directories; use with care.
hasExtension :: FileExt -> EventPredicate Source #
Allows through events triggered by file system entries with a specific extension.
isCreation :: EventPredicate Source #
Allows through only creation events.
isModification :: EventPredicate Source #
Allows through only modification events.
isDeletion :: EventPredicate Source #
Allows through only deletion events.
isBasic :: EventPredicate Source #
Allows through only 'basic' events (namely creation, modification and deletion).
invert :: EventPredicate -> EventPredicate Source #
'Flips' the predicate - what it used to allow through is now blocked, and vice versa.
conj :: EventPredicate -> EventPredicate -> EventPredicate Source #
Predicate conjunction (meaning that both have to be true for the result
to be true). Synonym for times
.
disj :: EventPredicate -> EventPredicate -> EventPredicate Source #
Predicate disjunction (meaning that either has to be true for the result
to be true). Synonym for plus
.
Watchers
watchDirectory :: (IsStream t, MonadAsync m) => FsPath -> EventPredicate -> m (StopWatching m, t m Event) Source #
Watch a given directory, but only at one level (thus, subdirectories will not be watched recursively).
watchDirectoryWith :: (IsStream t, MonadAsync m) => WatchConfig -> FsPath -> EventPredicate -> m (StopWatching m, t m Event) Source #
As watchDirectory
, but with a specified set of watch options.
watchTree :: (IsStream t, MonadAsync m) => FsPath -> EventPredicate -> m (StopWatching m, t m Event) Source #
Watch a given directory recursively (thus, subdirectories will also have their contents watched).
watchTreeWith :: (IsStream t, MonadAsync m) => WatchConfig -> FsPath -> EventPredicate -> m (StopWatching m, t m Event) Source #
As watchTree
, but with a specified set of watch options.