twitch-0.1.7.2: 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

Here is another complex example, using the named addModify and delete callbacks to the same function, which build a pdf and a Word document using pandoc, and refreshes a mupdf window.

```haskell buildPDFandWordandRefreshWindow _ = do pdfLatexCode <- system "pdflatex --interaction errorstopmode -file-line-error -halt-on-error document.tex" (pandocCode,pandocOut,pandocErr) <- readProcessWithExitCode "pandoc" [ "--from=latex" , "--to=docx" , "document.tex" , "-o" , "document.docx" ] "" (xwininfoCode,xwininfoOut,xwininfoErr) <- readProcessWithExitCode "xwininfo" ["-root", "-int", "-all"] "" let windowId = head . words . head . filter (isInfixOf "document") $ lines xwininfoOut (xDoToolCode,xDoToolOut,xDoToolErr) <- readProcessWithExitCode "xdotool" ["key", "--window", windowId, "r"] "" return ()

main :: IO () main = defaultMain $ do addModify buildPDFandWordandRefreshWindow "src***.tex" delete buildPDFandWordandRefreshWindow "src***.tex" ```

The globs in the above two examples are also more complicated and incorporate recursive wildcards. 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.

The command line is parsed to make Options value. For more information on the arguments that can be passed see the doc for Options and the run the executable made with defaultMain with the --help argument.

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 -> String -> 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 :: String -> 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

    The logger type. This corresponds to the --log or -l argument. The valid options are LogToStdout, LogToFile, and NoLogger If LogToFile a file can provide with the logFile field.

  • logFile :: Maybe FilePath

    The file to log to. This is only used if the log field is set to LogToFile. This corresponds to the --log-file or -f argument.

  • root :: Maybe FilePath

    The root directory to watch. This corresponds to the --root and -r argument. By default this is empty and the current directory is used.

  • recurseThroughDirectories :: Bool

    If true, main will recurse through all subdirectories of the dirsToWatch field. Otherwise the dirsToWatch will be used literally. By default this is true, and disabled with the --no-recurse-flag .

  • debounce :: DebounceType

    This corresponds to the debounce type used in the fsnotify library The argument for default main is --debounce or -b . Valid options are DebounceDefault, Debounce, NoDebounce. If Debounce is used, then a debounce amount must be specified with the debounceAmount.

  • debounceAmount :: Double

    The amount to debounce. This is only meaningful when debounce is set to Debounce. It corresponds to the --debounce-amount or -a argument.

  • pollInterval :: Int

    poll interval if polling is used. This corresponds to the --poll-interval or -i argument.

  • usePolling :: Bool

    Sets polling to true if used. This corresponds to the --should-poll or -p flag.

Instances
Default Options Source # 
Instance details

Defined in Twitch.Main

Methods

def :: Options #

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 Issue Source #

A sum type for the various issues that can be logged

Constructors

IEvent Event

logged every time an event is fired

IRuleFired Event InternalRule

logged every time an rule is fired

Instances
Show Issue Source # 
Instance details

Defined in Twitch.InternalRule

Methods

showsPrec :: Int -> Issue -> ShowS #

show :: Issue -> String #

showList :: [Issue] -> ShowS #

data InternalRule Source #

Instances
Show InternalRule Source # 
Instance details

Defined in Twitch.InternalRule

Default InternalRule Source # 
Instance details

Defined in Twitch.InternalRule

Methods

def :: InternalRule #

data Rule Source #

The pattern entity holds a name and pattern that is compiled when the rules are evaluated

Instances
IsString Rule Source # 
Instance details

Defined in Twitch.Rule

Methods

fromString :: String -> Rule #

Default Rule Source # 
Instance details

Defined in Twitch.Rule

Methods

def :: Rule #

data RuleIssue Source #

Instances
Eq RuleIssue Source # 
Instance details

Defined in Twitch.Rule

Show RuleIssue Source # 
Instance details

Defined in Twitch.Rule

data Config Source #

Configuration to run the file watcher

Constructors

Config 

Fields

Instances
Show Config Source # 
Instance details

Defined in Twitch.InternalRule

Default Config Source # 
Instance details

Defined in Twitch.InternalRule

Methods

def :: Config #

Extra

data DepM a Source #

A polymorphic Dep. Exported for completeness, ignore.

Instances
Monad DepM Source # 
Instance details

Defined in Twitch.Internal

Methods

(>>=) :: DepM a -> (a -> DepM b) -> DepM b #

(>>) :: DepM a -> DepM b -> DepM b #

return :: a -> DepM a #

fail :: String -> DepM a #

Functor DepM Source # 
Instance details

Defined in Twitch.Internal

Methods

fmap :: (a -> b) -> DepM a -> DepM b #

(<$) :: a -> DepM b -> DepM a #

IsString Dep Source # 
Instance details

Defined in Twitch.Internal

Methods

fromString :: String -> Dep #

Applicative DepM Source # 
Instance details

Defined in Twitch.Internal

Methods

pure :: a -> DepM a #

(<*>) :: DepM (a -> b) -> DepM a -> DepM b #

liftA2 :: (a -> b -> c) -> DepM a -> DepM b -> DepM c #

(*>) :: DepM a -> DepM b -> DepM b #

(<*) :: DepM a -> DepM b -> DepM a #

Semigroup (DepM a) Source # 
Instance details

Defined in Twitch.Internal

Methods

(<>) :: DepM a -> DepM a -> DepM a #

sconcat :: NonEmpty (DepM a) -> DepM a #

stimes :: Integral b => b -> DepM a -> DepM a #

Monoid a => Monoid (DepM a) Source # 
Instance details

Defined in Twitch.Internal

Methods

mempty :: DepM a #

mappend :: DepM a -> DepM a -> DepM a #

mconcat :: [DepM a] -> DepM a #