streamly-fsnotify-2.1.0.2: Folder watching as a Streamly stream.
Safe HaskellSafe-Inferred
LanguageGHC2021

Streamly.FSNotify

Description

Example

Here is a program which watches /home/georgefst/c-project and any of its subdirectories for added or modified C source files (which we take to be anything with a .c extension). This program then writes that the event occurred, to what file, and when, forever.

{\-# LANGUAGE GHC2021, BlockArguments, LambdaCase #-\}

import Streamly.Data.Fold qualified as SF
import Streamly.Data.Stream.Prelude qualified as SP
import System.FilePath (isExtensionOf, (</>))

import Streamly.FSNotify

isCSourceFile :: Event -> Bool
isCSourceFile e =
    "c" `isExtensionOf` eventPath e && eventIsDirectory e == IsFile

srcPath :: FilePath
srcPath = "/" </> "home" </> "georgefst" </> "c-project"

main :: IO ()
main = SP.fold (SF.drainMapM go) $ watchTree srcPath
  where
    go = \case
        e | not (isCSourceFile e) -> pure ()
        Added p t _ -> putStrLn $ "Created: " ++ show p ++ " at " ++ show t
        Modified p t _ -> putStrLn $ "Modified: " ++ show p ++ " at " ++ show t
        _ -> pure ()
Synopsis

Documentation

data Event #

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 
Instance details

Defined in System.FSNotify.Types

Methods

showsPrec :: Int -> Event -> ShowS #

show :: Event -> String #

showList :: [Event] -> ShowS #

Eq Event 
Instance details

Defined in System.FSNotify.Types

Methods

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

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

watchDir :: (MonadAsync m, MonadCatch m) => FilePath -> Stream m Event Source #

Watch a given directory, but only at one level (thus, subdirectories will not be watched recursively).

watchTree :: (MonadAsync m, MonadCatch m) => FilePath -> Stream m Event Source #

Watch a given directory recursively (thus, subdirectories will also have their contents watched).