unionmount-0.1.0.0: Union mount filesystem paths into Haskell datastructures
Safe HaskellNone
LanguageHaskell2010

System.UnionMount

Synopsis

Documentation

mountOnLVar Source #

Arguments

:: forall model m b. (MonadIO m, MonadUnliftIO m, MonadLogger m, Show b, Ord b) 
=> FilePath

The directory to mount.

-> [(b, FilePattern)]

Only include these files (exclude everything else)

-> [FilePattern]

Ignore these patterns

-> LVar model

The LVar onto which to mount.

NOTE: It must not be set already. Otherwise, the value will be overriden with the initial value argument (next).

-> model

Initial value of model, onto which to apply updates.

-> (b -> FilePath -> FileAction () -> m (model -> model))

How to update the model given a file action.

b is the tag associated with the FilePattern that selected this FilePath. FileAction is the operation performed on this path. This should return a function (in monadic context) that will update the model, to reflect the given FileAction.

If the action throws an exception, it will be logged and ignored.

-> m (Maybe Cmd) 

Simplified variation of unionMountOnLVar with exactly one source.

unionMountOnLVar :: forall source tag model m. (MonadIO m, MonadUnliftIO m, MonadLogger m, Ord source, Ord tag) => Set (source, FilePath) -> [(tag, FilePattern)] -> [FilePattern] -> LVar model -> model -> (Change source tag -> m (model -> model)) -> m (Maybe Cmd) Source #

Like unionMount but updates a LVar as well handles exceptions (and unhandled events) by logging them.

data Evt source tag Source #

Constructors

Evt_Change (Change source tag) 
Evt_Unhandled 

Instances

Instances details
(Eq tag, Eq source) => Eq (Evt source tag) Source # 
Instance details

Defined in System.UnionMount

Methods

(==) :: Evt source tag -> Evt source tag -> Bool #

(/=) :: Evt source tag -> Evt source tag -> Bool #

(Show tag, Show source) => Show (Evt source tag) Source # 
Instance details

Defined in System.UnionMount

Methods

showsPrec :: Int -> Evt source tag -> ShowS #

show :: Evt source tag -> String #

showList :: [Evt source tag] -> ShowS #

data Cmd Source #

Constructors

Cmd_Remount 

Instances

Instances details
Eq Cmd Source # 
Instance details

Defined in System.UnionMount

Methods

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

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

Show Cmd Source # 
Instance details

Defined in System.UnionMount

Methods

showsPrec :: Int -> Cmd -> ShowS #

show :: Cmd -> String #

showList :: [Cmd] -> ShowS #

unionMount :: forall source tag m. (MonadIO m, MonadUnliftIO m, MonadLogger m, Ord source, Ord tag) => Set (source, FilePath) -> [(tag, FilePattern)] -> [FilePattern] -> (Change source tag -> m (Maybe Cmd)) -> m (Maybe Cmd) Source #

filesMatchingWithTag :: (MonadIO m, MonadLogger m, Ord b) => FilePath -> [(b, FilePattern)] -> [FilePattern] -> m [(b, [FilePath])] Source #

Like filesMatching but with a tag associated with a pattern so as to be able to tell which pattern a resulting filepath is associated with.

data RefreshAction Source #

Constructors

Existing

No recent change. Just notifying of file's existance

New

New file got created

Update

The already existing file was updated.

Instances

Instances details
Eq RefreshAction Source # 
Instance details

Defined in System.UnionMount

Show RefreshAction Source # 
Instance details

Defined in System.UnionMount

data FileAction a Source #

Constructors

Refresh RefreshAction a

A new file, or updated file, is available

Delete

The file just got deleted.

Instances

Instances details
Functor FileAction Source # 
Instance details

Defined in System.UnionMount

Methods

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

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

Eq a => Eq (FileAction a) Source # 
Instance details

Defined in System.UnionMount

Methods

(==) :: FileAction a -> FileAction a -> Bool #

(/=) :: FileAction a -> FileAction a -> Bool #

Show a => Show (FileAction a) Source # 
Instance details

Defined in System.UnionMount

newtype FolderAction a Source #

This is not an action on file, rather an action on a directory (which may contain files, which would be outside the scope of this fsnotify event, and so the user must manually deal with them.)

Constructors

FolderAction a 

Instances

Instances details
Functor FolderAction Source # 
Instance details

Defined in System.UnionMount

Methods

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

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

Eq a => Eq (FolderAction a) Source # 
Instance details

Defined in System.UnionMount

Show a => Show (FolderAction a) Source # 
Instance details

Defined in System.UnionMount

onChange Source #

Arguments

:: forall x m. (MonadIO m, MonadLogger m, MonadUnliftIO m) 
=> TBQueue (x, FilePath, Either (FolderAction ()) (FileAction ())) 
-> [(x, FilePath)] 
-> m ()

The filepath is relative to the folder being monitored, unless if its ancestor is a symlink.

log :: MonadLogger m => LogLevel -> Text -> m () Source #

newtype OverlayFs source Source #

Constructors

OverlayFs 

Fields

emptyOverlayFs :: Ord source => OverlayFs source Source #

overlayFsModify :: FilePath -> (Set src -> Set src) -> OverlayFs src -> OverlayFs src Source #

overlayFsAdd :: Ord src => FilePath -> src -> OverlayFs src -> OverlayFs src Source #

overlayFsRemove :: Ord src => FilePath -> src -> OverlayFs src -> OverlayFs src Source #

type Change source tag = Map tag (Map FilePath (FileAction (NonEmpty (source, FilePath)))) Source #

changeInsert :: (Ord source, Ord tag, MonadState (OverlayFs source) m) => source -> tag -> FilePath -> FileAction () -> Change source tag -> m (Change source tag) Source #

Report a change to overlay fs