Safe Haskell | None |
---|---|
Language | Haskell98 |
NOTE: This library does not currently report changes made to directories, only files within watched directories.
Minimal example:
{-# LANGUAGE OverloadedStrings #-} -- for FilePath literals import System.FSNotify import Control.Concurrent (threadDelay) import Control.Monad (forever) main = withManager $ \mgr -> do -- start a watching job (in the background) watchDir mgr -- manager "." -- directory to watch (const True) -- predicate print -- action -- sleep forever (until interrupted) forever $ threadDelay 1000000
- data Event
- type EventChannel = Chan Event
- eventTime :: Event -> UTCTime
- eventPath :: Event -> FilePath
- type Action = Event -> IO ()
- type ActionPredicate = Event -> Bool
- data WatchManager
- withManager :: (WatchManager -> IO a) -> IO a
- startManager :: IO WatchManager
- stopManager :: WatchManager -> IO ()
- defaultConfig :: WatchConfig
- data WatchConfig = WatchConfig {}
- data Debounce
- withManagerConf :: WatchConfig -> (WatchManager -> IO a) -> IO a
- startManagerConf :: WatchConfig -> IO WatchManager
- type StopListening = IO ()
- isPollingManager :: WatchManager -> Bool
- watchDir :: WatchManager -> FilePath -> ActionPredicate -> Action -> IO StopListening
- watchDirChan :: WatchManager -> FilePath -> ActionPredicate -> EventChannel -> IO StopListening
- watchTree :: WatchManager -> FilePath -> ActionPredicate -> Action -> IO StopListening
- watchTreeChan :: WatchManager -> FilePath -> ActionPredicate -> EventChannel -> IO StopListening
Events
A file event reported by a file watcher. Each event contains the canonical path for the file and a timestamp guaranteed to be after the event occurred (timestamps represent current time when FSEvents receives it from the OS and/or platform-specific Haskell modules).
type EventChannel = Chan Event Source
type ActionPredicate = Event -> Bool Source
A predicate used to determine whether to act on an event.
Starting/Stopping
data WatchManager Source
Watch manager. You need one in order to create watching jobs.
withManager :: (WatchManager -> IO a) -> IO a Source
Perform an IO action with a WatchManager in place. Tear down the WatchManager after the action is complete.
startManager :: IO WatchManager Source
Start a file watch manager.
Directories can only be watched when they are managed by a started watch
watch manager.
When finished watching. you must release resources via stopManager
.
It is preferrable if possible to use withManager
to handle this
automatically.
stopManager :: WatchManager -> IO () Source
Stop a file watch manager. Stopping a watch manager will immediately stop watching for files and free resources.
defaultConfig :: WatchConfig Source
Default configuration
- Debouncing is enabled with a time interval of 1 millisecond
- Polling is disabled
- The polling interval defaults to 1 second
data WatchConfig Source
Watch configuration
WatchConfig | |
|
This specifies whether multiple events from the same file should be collapsed together, and how close is close enough.
This is performed by ignoring any event that occurs to the same file until the specified time interval has elapsed.
Note that the current debouncing logic may fail to report certain changes to a file, potentially leaving your program in a state that is not consistent with the filesystem.
Make sure that if you are using this feature, all changes you make as a
result of an Event
notification are both non-essential and idempotent.
DebounceDefault | perform debouncing based on the default time interval of 1 millisecond |
Debounce NominalDiffTime | perform debouncing based on the specified time interval |
NoDebounce | do not perform debouncing |
withManagerConf :: WatchConfig -> (WatchManager -> IO a) -> IO a Source
Like withManager
, but configurable
startManagerConf :: WatchConfig -> IO WatchManager Source
Like startManager
, but configurable
type StopListening = IO () Source
An action that cancels a watching/listening job
isPollingManager :: WatchManager -> Bool Source
Does this manager use polling?
Watching
watchDir :: WatchManager -> FilePath -> ActionPredicate -> Action -> IO StopListening Source
Watch the immediate contents of a directory by committing an Action for each event. Watching the immediate contents of a directory will only report events associated with files within the specified directory, and not files within its subdirectories. No two events pertaining to the same FilePath will be executed concurrently.
watchDirChan :: WatchManager -> FilePath -> ActionPredicate -> EventChannel -> IO StopListening Source
Watch the immediate contents of a directory by streaming events to a Chan. Watching the immediate contents of a directory will only report events associated with files within the specified directory, and not files within its subdirectories.
watchTree :: WatchManager -> FilePath -> ActionPredicate -> Action -> IO StopListening Source
Watch all the contents of a directory by committing an Action for each event. Watching all the contents of a directory will report events associated with files within the specified directory and its subdirectories. No two events pertaining to the same FilePath will be executed concurrently.
watchTreeChan :: WatchManager -> FilePath -> ActionPredicate -> EventChannel -> IO StopListening Source
Watch all the contents of a directory by streaming events to a Chan. Watching all the contents of a directory will report events associated with files within the specified directory and its subdirectories.