twitch-0.1.3.0: A high level file watcher DSL

Safe HaskellNone
LanguageHaskell2010

Twitch

Contents

Description

Twitch is a monadic DSL and library for file watching. It conveniently utilizes 'do' notation in the style of Shake and clay to expose the functionality of the fsnotify cross-platform file system watcher.

Here is an example that converts Markdown files to HTML and reloads Safari whenever the input files change.

{-# LANGUAGE OverloadedStrings #-}
import Twitch 
import Filesystem.Path.CurrentOS

main = defaultMain $ do
  "*.md"   |> \filePath -> system $ "pandoc -t html " ++ encodeString filePath 
  "*.html" |> \_ -> system $ "osascript refreshSafari.AppleScript"

Rules are specified in the Dep (for Dependency) monad. The library takes advantage of the OverloadedStrings extension to create a Dep value from a glob pattern.

After creating a Dep value using a glob, event callbacks are added using prefix or infix API.

There are three types of events: 'add', 'modify' and 'delete'. In many cases, the 'add' and 'modify' responses are the same, so an 'add and modify' API is provided

In the example above, an 'add and modify' callback was added to both the "*.md" and "*.html" globs using the |> operator.

Although this is the common case, differing callbacks can be added with |+ (or add) and |% (or modify) functions. Finally, delete callbacks are added with |- (of delete).

Here is a more complex usage example, handling all three events separately.

handleHaskellFiles :: Dep 
handleHaskellFiles = "src/**/*.hs" |+ addToCabalFile |% reloadFile |- removeFromCabalFile

The glob above is also more complicated and incorporates a recursive wildcard. For complete documentation on the glob syntax, consult the Glob library's documentation.

Since a command pattern is calling system commands with a file path, a useful addition to twitch is the file-command-qq quasiquoter.

Here is a slightly more complicated version the example from earlier, using the FileCommand quasiquoter.

{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE QuasiQuotes #-}
import Twitch 
import FileCommand

main = defaultMain $ do
  "*.md"    |> [s|pandoc -t html -o$directory$basename-test.html $path|]
  "*.html"  |> [s|osascript refreshSafari.AppleScript|]

Synopsis

Documentation

type Dep = DepM () Source

This is the key type of the package, it is where rules are accumulated.

defaultMain :: Dep -> IO () Source

Simplest way to create a file watcher app. Set your main equal to defaultMain and you are good to go. See the module documentation for examples.

Infix API

(|+) :: Dep -> (FilePath -> IO a) -> Dep infixl 8 Source

Add a 'add' callback ex.

"*.png" |+ addToManifest

(|%) :: Dep -> (FilePath -> IO a) -> Dep infixl 8 Source

Add a 'modify' callback ex.

"*.c" |% [s|gcc -o$directory$basename.o $path|]

(|-) :: Dep -> (FilePath -> IO a) -> Dep infixl 8 Source

Add a 'delete' callback ex.

"*.c" |- [s|gcc -o$directory$basename.o $path|]

(|>) :: Dep -> (FilePath -> IO a) -> Dep infixl 8 Source

Add the same callback for the 'add' and the 'modify' events. ex.

"*.md" |> [s|pandoc -t html $path|]

Defined as: x |> f = x |+ f |% f

(|#) :: Dep -> Text -> Dep infixl 8 Source

Set the name of a rule. Useful for debugging when logging is enabled. Rules names default to the glob pattern. ex.

"*.md" |> [s|pandoc -t html $path|] |# "markdown to html"

Prefix API

add :: (FilePath -> IO a) -> Dep -> Dep Source

Add a 'add' callback ex.

add addToManifest "*.png"

modify :: (FilePath -> IO a) -> Dep -> Dep Source

Add a 'modify' callback ex.

mod [s|gcc -o$directory$basename.o $path|] "*.c"

delete :: (FilePath -> IO a) -> Dep -> Dep Source

Add a 'delete' callback ex.

delete [s|gcc -o$directory$basename.o $path|] "*.c"

addModify :: (FilePath -> IO a) -> Dep -> Dep Source

Add the same callback for the 'add' and the 'modify' events. ex.

addModify [s|pandoc -t html $path|] "*.md" 

name :: Text -> Dep -> Dep Source

Set the name of a rule. Useful for debugging when logging is enabled. Rules names default to the glob pattern. ex.

name "markdown to html" $ addModify [s|pandoc -t html $path|] "*.md"

Advanced Main

data Options Source

Constructors

Options 

Fields

log :: LoggerType
 
logFile :: Maybe FilePath

A logger for the issues

dirsToWatch :: [FilePath]

The directories to watch

recurseThroughDirectories :: Bool
 
debounce :: DebounceType
 
debounceAmount :: Double

Debounce configuration

pollInterval :: Int

poll interval

usePolling :: Bool

config for the file watch

currentDir :: Maybe FilePath
 

Instances

defaultMainWithOptions :: Options -> Dep -> IO () Source

A main file that uses manually supplied options instead of parsing the passed in arguments.

Running as a library

data Config Source

Configuration to run the file watcher

Constructors

Config 

Fields

logger :: Issue -> IO ()

A logger for the issues

dirs :: [FilePath]

The directories to watch

watchConfig :: WatchConfig

config for the file watcher

Extra

data DepM a Source

A polymorphic Dep. Exported for completeness, ignore.