Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- inotifyEventsSource :: (MonadResource m, Monad m) => INotify -> NonEmpty EventVariety -> FilePath -> STM (ConduitT () Event m (), STM ())
- sourceHandleEof :: MonadIO m => Handle -> ConduitT () (Maybe ByteString) m ()
- sourceFileFollowModify :: (MonadResource m, MonadIO m) => INotify -> FilePath -> STM (ConduitT () (Maybe ByteString) m (), STM ())
- sourceFileFollowModify' :: (MonadResource m, MonadIO m) => INotify -> FilePath -> STM (ConduitT () ByteString m (), STM ())
- replacableBracketP :: MonadResource m => IO a -> (a -> IO ()) -> ((m a, m ()) -> ConduitT i o m ()) -> ConduitT i o m ()
- inotifyEventsSourceRotate :: MonadResource m => INotify -> NonEmpty EventVariety -> FilePath -> STM (ConduitT () Event m (), STM ())
- inotifyEventsSourceRotateMultiple :: MonadResource m => INotify -> [(NonEmpty EventVariety, FilePath)] -> STM (ConduitT () (Event, FilePath) m (), STM ())
- data FollowFileEvent
- sourceFileFollowModifyRotateWithSeek :: (MonadResource m, MonadIO m) => INotify -> FilePath -> FilePath -> STM (ConduitT () (Maybe ByteString) m (), STM ())
- sourceFileFollowModifyRotateWithSeek' :: (MonadResource m, MonadIO m) => INotify -> FilePath -> FilePath -> STM (ConduitT () ByteString m (), STM ())
- sourceFileFollowModifyRotateWithSeekIO :: (MonadResource m, MonadIO m) => INotify -> FilePath -> IO (ConduitT () (Maybe ByteString) m (), STM ())
- sourceFileFollowModifyRotateWithSeekIO' :: (MonadResource m, MonadIO m) => INotify -> FilePath -> IO (ConduitT () ByteString m (), STM ())
Documentation
:: (MonadResource m, Monad m) | |
=> INotify | INotify |
-> NonEmpty EventVariety | events to watch for |
-> FilePath | path to file to be watched |
-> STM (ConduitT () Event m (), STM ()) | returns (source, handle to terminate the watch) |
Watch INotify events for given file Does not support file rotation. Once the watched file is removed, it will not emit any additional events and needs to be terminated via handle.
sourceHandleEof :: MonadIO m => Handle -> ConduitT () (Maybe ByteString) m () Source #
Stream contents of a Handle
as binary data and yield Nothing after EOF is reached
sourceFileFollowModify Source #
:: (MonadResource m, MonadIO m) | |
=> INotify | INotify |
-> FilePath | path to file to be followed |
-> STM (ConduitT () (Maybe ByteString) m (), STM ()) | returns (source of binary data from file, handle to terminate the follow) |
Stream contents of a file as binary data. Once EOF is reached it waits for file modifications and streams data as they are appended to the file. Once the watch is terminated, it will read the file until EOF is reached.
Source emits Nothing
when EOF is reached. For version emitting just data see 'sourceFileFollowModify''
Does not support file rotations. For version supporing rotations see sourceFileFollowModifyRotateWithSeek
sourceFileFollowModify' :: (MonadResource m, MonadIO m) => INotify -> FilePath -> STM (ConduitT () ByteString m (), STM ()) Source #
Version of sourceFileFollowModify
not notifying about EOF
:: MonadResource m | |
=> IO a | acquire resource computation |
-> (a -> IO ()) | release resource computation |
-> ((m a, m ()) -> ConduitT i o m ()) | computation to run in-between. | first: acquires the resource if not available, otherwise just gets it | second: releases the resource |
-> ConduitT i o m () |
Like bracketP
, but resource can be released within 'in-between' computation.
Resource is recreated after release if needed
inotifyEventsSourceRotate :: MonadResource m => INotify -> NonEmpty EventVariety -> FilePath -> STM (ConduitT () Event m (), STM ()) Source #
Watch INotify events for given file. Interprets file removal as file rotation and tries to recreate the watch again.
inotifyEventsSourceRotateMultiple :: MonadResource m => INotify -> [(NonEmpty EventVariety, FilePath)] -> STM (ConduitT () (Event, FilePath) m (), STM ()) Source #
data FollowFileEvent Source #
Instances
Eq FollowFileEvent Source # | |
Defined in Data.Conduit.INotify (==) :: FollowFileEvent -> FollowFileEvent -> Bool # (/=) :: FollowFileEvent -> FollowFileEvent -> Bool # | |
Show FollowFileEvent Source # | |
Defined in Data.Conduit.INotify showsPrec :: Int -> FollowFileEvent -> ShowS # show :: FollowFileEvent -> String # showList :: [FollowFileEvent] -> ShowS # |
sourceFileFollowModifyRotateWithSeek Source #
:: (MonadResource m, MonadIO m) | |
=> INotify | INotify |
-> FilePath | path to parent directory |
-> FilePath | file name relative to parent directory |
-> STM (ConduitT () (Maybe ByteString) m (), STM ()) | (source, handle to terminate the watch) |
Stream contents of a file as binary data. Once EOF is reached it waits for file modifications and streams data as they are appended to the file. Once the watch is terminated, it will read the file until EOF is reached.
Interprets file removal as file rotation and tries to recreate the watch and continue to follow the file from last position (expects just rotation that resembles append to file).
Source emits Nothing
when EOF is reached. For version emitting just data see 'sourceFileFollowModifyRotateWithSeek''
Since the handle prevents the file from deleting, it is watching a parent directory for MoveIn
events and interprets them as rotations
sourceFileFollowModifyRotateWithSeek' Source #
:: (MonadResource m, MonadIO m) | |
=> INotify | INotify |
-> FilePath | path to parent directory |
-> FilePath | file name relative to parent directory |
-> STM (ConduitT () ByteString m (), STM ()) | (source, handle to terminate the watch) |
Version of sourceFileFollowModifyRotateWithSeek
not notifying about EOF
sourceFileFollowModifyRotateWithSeekIO Source #
:: (MonadResource m, MonadIO m) | |
=> INotify | INotify |
-> FilePath | file name |
-> IO (ConduitT () (Maybe ByteString) m (), STM ()) | (source, handle to terminate the watch) |
Version of sourceFileFollowModifyRotateWithSeek
that determines parent directory
sourceFileFollowModifyRotateWithSeekIO' Source #
:: (MonadResource m, MonadIO m) | |
=> INotify | INotify |
-> FilePath | file name |
-> IO (ConduitT () ByteString m (), STM ()) | (source, handle to terminate the watch) |
Version of 'sourceFileFollowModifyRotateWithSeek'' that determines parent directory