Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
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
Synopsis
- data Event
- = Added { }
- | Modified { }
- | ModifiedAttributes { }
- | Removed { }
- | WatchedDirectoryRemoved { }
- | CloseWrite { }
- | Unknown { }
- data EventIsDirectory
- type EventChannel = Chan Event
- 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
- confWatchMode :: WatchConfig -> WatchMode
- confThreadingMode :: WatchConfig -> ThreadingMode
- confOnHandlerException :: WatchConfig -> SomeException -> IO ()
- data WatchMode
- = WatchModePoll { }
- | WatchModeOS
- data ThreadingMode
- withManagerConf :: WatchConfig -> (WatchManager -> IO a) -> IO a
- startManagerConf :: WatchConfig -> IO WatchManager
- type StopListening = IO ()
- 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).
Added | |
Modified | |
ModifiedAttributes | |
Removed | |
WatchedDirectoryRemoved | Note: Linux-only |
CloseWrite | Note: Linux-only |
Unknown | Note: Linux-only |
data EventIsDirectory Source #
Instances
Show EventIsDirectory Source # | |
Defined in System.FSNotify.Types showsPrec :: Int -> EventIsDirectory -> ShowS # show :: EventIsDirectory -> String # showList :: [EventIsDirectory] -> ShowS # | |
Eq EventIsDirectory Source # | |
Defined in System.FSNotify.Types (==) :: EventIsDirectory -> EventIsDirectory -> Bool # (/=) :: EventIsDirectory -> EventIsDirectory -> Bool # |
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 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.
Configuration
defaultConfig :: WatchConfig Source #
Default configuration
- Uses OS watch mode and single thread.
data WatchConfig Source #
Watch configuration.
confWatchMode :: WatchConfig -> WatchMode Source #
Watch mode to use.
confThreadingMode :: WatchConfig -> ThreadingMode Source #
Threading mode to use.
confOnHandlerException :: WatchConfig -> SomeException -> IO () Source #
Called when a handler throws an exception.
Method of watching for changes.
WatchModePoll | Detect changes by polling the filesystem. Less efficient and may miss fast changes. Not recommended
unless you're experiencing problems with |
WatchModeOS | Use OS-specific mechanisms to be notified of changes (inotify on Linux, FSEvents on OSX, etc.). Not currently available on *BSD. |
data ThreadingMode Source #
SingleThread | Use a single thread for the entire |
ThreadPerWatch | Use a single thread for each watch (i.e. each call to |
ThreadPerEvent | Launch a separate thread for every event handler. |
Lower level
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.
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.
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.
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.