fsnotify-0.4.1.0: Cross platform library for file change notification.
Safe HaskellSafe-Inferred
LanguageHaskell2010

System.FSNotify

Description

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

Events

data Event Source #

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).

Instances

Instances details
Show Event Source # 
Instance details

Defined in System.FSNotify.Types

Methods

showsPrec :: Int -> Event -> ShowS #

show :: Event -> String #

showList :: [Event] -> ShowS #

Eq Event Source # 
Instance details

Defined in System.FSNotify.Types

Methods

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

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

type Action = Event -> IO () Source #

An action to be performed in response to an event.

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.

data WatchMode Source #

Method of watching for changes.

Constructors

WatchModePoll

Detect changes by polling the filesystem. Less efficient and may miss fast changes. Not recommended unless you're experiencing problems with WatchModeOS (or WatchModeOS is not supported on your platform).

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 #

Constructors

SingleThread

Use a single thread for the entire Manager. Event handler callbacks will run sequentially.

ThreadPerWatch

Use a single thread for each watch (i.e. each call to watchDir, watchTree, etc.). Callbacks within a watch will run sequentially but callbacks from different watches may be interleaved.

ThreadPerEvent

Launch a separate thread for every event handler.

Lower level

withManagerConf :: WatchConfig -> (WatchManager -> IO a) -> IO a Source #

Like withManager, 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.