{-# LANGUAGE CPP #-}
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE ScopedTypeVariables #-}
module Data.CAS.ContentStore.Notify.Linux
( Notifier
, initNotifier
, killNotifier
, Watch
, addDirWatch
, removeDirWatch
) where
import Control.Exception.Safe (catch)
#if MIN_VERSION_hinotify(0,3,10)
import qualified Data.ByteString.Char8 as BS
#endif
import System.INotify
type Notifier = INotify
initNotifier :: IO Notifier
initNotifier = initINotify
killNotifier :: Notifier -> IO ()
killNotifier = killINotify
type Watch = WatchDescriptor
addDirWatch :: Notifier -> FilePath -> IO () -> IO Watch
addDirWatch inotify dir f = addWatch inotify mask dir' $ \case
Attributes True Nothing -> f
MovedSelf True -> f
DeletedSelf -> f
_ -> return ()
where
mask = [Attrib, MoveSelf, DeleteSelf, OnlyDir]
#if MIN_VERSION_hinotify(0,3,10)
dir' = BS.pack dir
#else
dir' = dir
#endif
removeDirWatch :: Watch -> IO ()
removeDirWatch w =
removeWatch w
`catch` \(_::IOError) -> return ()