streamly-fsnotify-1.0.1.0: Folder watching as a Streamly stream.

Safe HaskellNone
LanguageHaskell2010

Streamly.FSNotify

Contents

Description

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:


import Streamly.FSNotify (EventPredicate, hasExtension, isDirectory, invert, isDeletion, conj, watchTree)
import System.Path (FsPath, FileExt(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

Basic types

data Event Source #

A file system notification.

Constructors

Added (Path Absolute) UTCTime FSEntryType

Creation event

Modified (Path Absolute) UTCTime FSEntryType

Modification event

Removed (Path Absolute) UTCTime FSEntryType

Deletion event

Other (Path Absolute) UTCTime Text

Some other kind of event

Instances
Eq Event Source # 
Instance details

Defined in Streamly.FSNotify

Methods

(==) :: Event -> Event -> Bool #

(/=) :: Event -> Event -> Bool #

Show Event Source # 
Instance details

Defined in Streamly.FSNotify

Methods

showsPrec :: Int -> Event -> ShowS #

show :: Event -> String #

showList :: [Event] -> ShowS #

type StopWatching m = m () Source #

A function, which, when executed, stops a file system watch.

eventPath :: Event -> FsPath Source #

Helper to retrieve the file path associated with an event.

eventTime :: Event -> UTCTime Source #

Helper to retrieve an event's timestamp.

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.

Constructors

EventPredicate 

Fields

Instances
Semiring EventPredicate Source #

EventPredicate can be a Semigroup in two ways:

  • Under logical conjunction (both of the conditions must be met); and
  • Under logical disjunction (either of the conditions must be met).

Both of these can be made into a Monoid by using the trivial predicate (always true) for the first case, and the null predicate (always false) for the second. This makes it a valid candidate to be a semiring, which allows our users to compose EventPredicates using both of these methods, as they see fit.

If you want an instance of Semigroup and Monoid with one of these behaviours, you can use Add (for the logical disjunction behaviour) or Mul (for the logical conjunction behaviour).

Instance details

Defined in Streamly.FSNotify

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.