#include "config.h"
#if HAVE_DECL_IN_EXCL_UNLINK
module Streamly.Internal.FileSystem.Event.Linux
(
Config (..)
, defaultConfig
, setRecursiveMode
, setFollowSymLinks
, setUnwatchMoved
, setOneShot
, setOnlyDir
, WhenExists (..)
, setWhenExists
, setRootDeleted
, setRootMoved
, setRootPathEvents
, setAttrsModified
, setAccessed
, setOpened
, setWriteClosed
, setNonWriteClosed
, setCreated
, setDeleted
, setMovedFrom
, setMovedTo
, setModified
, setAllEvents
, watch
, watchRecursive
, watchWith
, addToWatch
, removeFromWatch
, Event(..)
, getRoot
, getRelPath
, getAbsPath
, getCookie
, isRootPathEvent
, isRootUnwatched
, isRootDeleted
, isRootMoved
, isRootUnmounted
, isAttrsModified
, isAccessed
, isOpened
, isWriteClosed
, isNonWriteClosed
, isCreated
, isDeleted
, isMovedFrom
, isMovedTo
, isMoved
, isModified
, isDir
, isEventsLost
, showEvent
)
where
import Control.Monad (void, when)
import Control.Monad.IO.Class (MonadIO)
import Data.Bits ((.|.), (.&.), complement)
import Data.Char (ord)
import Data.Foldable (foldlM)
import Data.Functor.Identity (runIdentity)
import Data.IntMap.Lazy (IntMap)
import Data.IORef (IORef, newIORef, readIORef, writeIORef, modifyIORef)
import Data.List.NonEmpty (NonEmpty)
#if !(MIN_VERSION_base(4,13,0))
import Data.Semigroup (Semigroup(..))
#endif
import Data.Word (Word8, Word32)
import Foreign.C.Error (throwErrnoIfMinus1)
import Foreign.C.String (CString)
import Foreign.C.Types (CInt(..), CUInt(..))
import Foreign.Ptr (Ptr)
import Foreign.Storable (peek, peekByteOff, sizeOf)
import GHC.IO.Device (IODeviceType(Stream))
import GHC.IO.FD (fdFD, mkFD)
import GHC.IO.Handle.FD (mkHandleFromFD)
import Streamly.Data.Stream (Stream)
import Streamly.Data.Parser (Parser)
import System.Directory (doesDirectoryExist)
import System.IO (Handle, hClose, IOMode(ReadMode))
import GHC.IO.Handle.FD (handleToFd)
import Streamly.Internal.Data.Array (Array(..), byteLength)
import qualified Data.IntMap.Lazy as Map
import qualified Data.List.NonEmpty as NonEmpty
import qualified Streamly.Data.Fold as FL
import qualified Streamly.Data.Array as A (fromList, writeN, getIndex)
import qualified Streamly.Data.Stream as S
import qualified Streamly.FileSystem.Handle as FH
import qualified Streamly.Unicode.Stream as U
import qualified Streamly.Internal.Data.Array as A
( fromStream, asCStringUnsafe, unsafePinnedAsPtr
, getSliceUnsafe, read
)
import qualified Streamly.Internal.FileSystem.Dir as Dir (readDirs)
import qualified Streamly.Internal.Data.Parser as PR
(takeEQ, fromEffect, fromFold)
data Config = Config
{ Config -> Bool
watchRec :: Bool
, Config -> Word32
createFlags :: Word32
}
setFlag :: Word32 -> Bool -> Config -> Config
setFlag :: Word32 -> Bool -> Config -> Config
setFlag Word32
mask Bool
status cfg :: Config
cfg@Config{Bool
Word32
createFlags :: Word32
watchRec :: Bool
createFlags :: Config -> Word32
watchRec :: Config -> Bool
..} =
let flags :: Word32
flags =
if Bool
status
then Word32
createFlags Word32 -> Word32 -> Word32
forall a. Bits a => a -> a -> a
.|. Word32
mask
else Word32
createFlags Word32 -> Word32 -> Word32
forall a. Bits a => a -> a -> a
.&. Word32 -> Word32
forall a. Bits a => a -> a
complement Word32
mask
in Config
cfg {createFlags :: Word32
createFlags = Word32
flags}
setRecursiveMode :: Bool -> Config -> Config
setRecursiveMode :: Bool -> Config -> Config
setRecursiveMode Bool
recursive cfg :: Config
cfg@Config{} = Config
cfg {watchRec :: Bool
watchRec = Bool
recursive}
foreign import capi
"sys/inotify.h value IN_DONT_FOLLOW" iN_DONT_FOLLOW :: Word32
setFollowSymLinks :: Bool -> Config -> Config
setFollowSymLinks :: Bool -> Config -> Config
setFollowSymLinks Bool
s = Word32 -> Bool -> Config -> Config
setFlag Word32
iN_DONT_FOLLOW (Bool -> Bool
not Bool
s)
foreign import capi
"sys/inotify.h value IN_EXCL_UNLINK" iN_EXCL_UNLINK :: Word32
setUnwatchMoved :: Bool -> Config -> Config
setUnwatchMoved :: Bool -> Config -> Config
setUnwatchMoved = Word32 -> Bool -> Config -> Config
setFlag Word32
iN_EXCL_UNLINK
#if HAVE_DECL_IN_MASK_CREATE
foreign import capi
"sys/inotify.h value IN_MASK_CREATE" iN_MASK_CREATE :: Word32
#endif
foreign import capi
"sys/inotify.h value IN_MASK_ADD" iN_MASK_ADD :: Word32
data WhenExists =
AddIfExists
| ReplaceIfExists
#if HAVE_DECL_IN_MASK_CREATE
| FailIfExists
#endif
setWhenExists :: WhenExists -> Config -> Config
setWhenExists :: WhenExists -> Config -> Config
setWhenExists WhenExists
val Config
cfg =
case WhenExists
val of
WhenExists
AddIfExists -> Word32 -> Bool -> Config -> Config
setFlag Word32
iN_MASK_ADD Bool
True Config
cfg
WhenExists
ReplaceIfExists -> Word32 -> Bool -> Config -> Config
setFlag Word32
iN_MASK_ADD Bool
False Config
cfg
#if HAVE_DECL_IN_MASK_CREATE
WhenExists
FailIfExists -> Word32 -> Bool -> Config -> Config
setFlag Word32
iN_MASK_CREATE Bool
True Config
cfg
#endif
foreign import capi
"sys/inotify.h value IN_ONESHOT" iN_ONESHOT :: Word32
setOneShot :: Bool -> Config -> Config
setOneShot :: Bool -> Config -> Config
setOneShot = Word32 -> Bool -> Config -> Config
setFlag Word32
iN_ONESHOT
foreign import capi
"sys/inotify.h value IN_ONLYDIR" iN_ONLYDIR :: Word32
setOnlyDir :: Bool -> Config -> Config
setOnlyDir :: Bool -> Config -> Config
setOnlyDir = Word32 -> Bool -> Config -> Config
setFlag Word32
iN_ONLYDIR
foreign import capi
"sys/inotify.h value IN_DELETE_SELF" iN_DELETE_SELF :: Word32
setRootDeleted :: Bool -> Config -> Config
setRootDeleted :: Bool -> Config -> Config
setRootDeleted = Word32 -> Bool -> Config -> Config
setFlag Word32
iN_DELETE_SELF
foreign import capi
"sys/inotify.h value IN_MOVE_SELF" iN_MOVE_SELF :: Word32
setRootMoved :: Bool -> Config -> Config
setRootMoved :: Bool -> Config -> Config
setRootMoved = Word32 -> Bool -> Config -> Config
setFlag Word32
iN_MOVE_SELF
setRootPathEvents :: Bool -> Config -> Config
setRootPathEvents :: Bool -> Config -> Config
setRootPathEvents = Word32 -> Bool -> Config -> Config
setFlag (Word32
iN_DELETE_SELF Word32 -> Word32 -> Word32
forall a. Bits a => a -> a -> a
.|. Word32
iN_MOVE_SELF)
foreign import capi
"sys/inotify.h value IN_ATTRIB" iN_ATTRIB :: Word32
setAttrsModified :: Bool -> Config -> Config
setAttrsModified :: Bool -> Config -> Config
setAttrsModified = Word32 -> Bool -> Config -> Config
setFlag Word32
iN_ATTRIB
foreign import capi
"sys/inotify.h value IN_ACCESS" iN_ACCESS :: Word32
setAccessed :: Bool -> Config -> Config
setAccessed :: Bool -> Config -> Config
setAccessed = Word32 -> Bool -> Config -> Config
setFlag Word32
iN_ACCESS
foreign import capi
"sys/inotify.h value IN_OPEN" iN_OPEN :: Word32
setOpened :: Bool -> Config -> Config
setOpened :: Bool -> Config -> Config
setOpened = Word32 -> Bool -> Config -> Config
setFlag Word32
iN_OPEN
foreign import capi
"sys/inotify.h value IN_CLOSE_WRITE" iN_CLOSE_WRITE :: Word32
setWriteClosed :: Bool -> Config -> Config
setWriteClosed :: Bool -> Config -> Config
setWriteClosed = Word32 -> Bool -> Config -> Config
setFlag Word32
iN_CLOSE_WRITE
foreign import capi
"sys/inotify.h value IN_CLOSE_NOWRITE" iN_CLOSE_NOWRITE :: Word32
setNonWriteClosed :: Bool -> Config -> Config
setNonWriteClosed :: Bool -> Config -> Config
setNonWriteClosed = Word32 -> Bool -> Config -> Config
setFlag Word32
iN_CLOSE_NOWRITE
foreign import capi
"sys/inotify.h value IN_CREATE" iN_CREATE :: Word32
setCreated :: Bool -> Config -> Config
setCreated :: Bool -> Config -> Config
setCreated = Word32 -> Bool -> Config -> Config
setFlag Word32
iN_CREATE
foreign import capi
"sys/inotify.h value IN_DELETE" iN_DELETE :: Word32
setDeleted :: Bool -> Config -> Config
setDeleted :: Bool -> Config -> Config
setDeleted = Word32 -> Bool -> Config -> Config
setFlag Word32
iN_DELETE
foreign import capi
"sys/inotify.h value IN_MOVED_FROM" iN_MOVED_FROM :: Word32
setMovedFrom :: Bool -> Config -> Config
setMovedFrom :: Bool -> Config -> Config
setMovedFrom = Word32 -> Bool -> Config -> Config
setFlag Word32
iN_MOVED_FROM
foreign import capi
"sys/inotify.h value IN_MOVED_TO" iN_MOVED_TO :: Word32
setMovedTo :: Bool -> Config -> Config
setMovedTo :: Bool -> Config -> Config
setMovedTo = Word32 -> Bool -> Config -> Config
setFlag Word32
iN_MOVED_TO
foreign import capi
"sys/inotify.h value IN_MODIFY" iN_MODIFY :: Word32
setModified :: Bool -> Config -> Config
setModified :: Bool -> Config -> Config
setModified = Word32 -> Bool -> Config -> Config
setFlag Word32
iN_MODIFY
setAllEvents :: Bool -> Config -> Config
setAllEvents :: Bool -> Config -> Config
setAllEvents Bool
s =
Bool -> Config -> Config
setRootDeleted Bool
s
(Config -> Config) -> (Config -> Config) -> Config -> Config
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Bool -> Config -> Config
setRootMoved Bool
s
(Config -> Config) -> (Config -> Config) -> Config -> Config
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Bool -> Config -> Config
setAttrsModified Bool
s
(Config -> Config) -> (Config -> Config) -> Config -> Config
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Bool -> Config -> Config
setAccessed Bool
s
(Config -> Config) -> (Config -> Config) -> Config -> Config
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Bool -> Config -> Config
setOpened Bool
s
(Config -> Config) -> (Config -> Config) -> Config -> Config
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Bool -> Config -> Config
setWriteClosed Bool
s
(Config -> Config) -> (Config -> Config) -> Config -> Config
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Bool -> Config -> Config
setNonWriteClosed Bool
s
(Config -> Config) -> (Config -> Config) -> Config -> Config
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Bool -> Config -> Config
setCreated Bool
s
(Config -> Config) -> (Config -> Config) -> Config -> Config
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Bool -> Config -> Config
setDeleted Bool
s
(Config -> Config) -> (Config -> Config) -> Config -> Config
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Bool -> Config -> Config
setMovedFrom Bool
s
(Config -> Config) -> (Config -> Config) -> Config -> Config
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Bool -> Config -> Config
setMovedTo Bool
s
(Config -> Config) -> (Config -> Config) -> Config -> Config
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Bool -> Config -> Config
setModified Bool
s
defaultConfig :: Config
defaultConfig :: Config
defaultConfig =
WhenExists -> Config -> Config
setWhenExists WhenExists
AddIfExists
(Config -> Config) -> Config -> Config
forall a b. (a -> b) -> a -> b
$ Bool -> Config -> Config
setCreated Bool
True
(Config -> Config) -> Config -> Config
forall a b. (a -> b) -> a -> b
$ Bool -> Config -> Config
setDeleted Bool
True
(Config -> Config) -> Config -> Config
forall a b. (a -> b) -> a -> b
$ Bool -> Config -> Config
setMovedFrom Bool
True
(Config -> Config) -> Config -> Config
forall a b. (a -> b) -> a -> b
$ Bool -> Config -> Config
setMovedTo Bool
True
(Config -> Config) -> Config -> Config
forall a b. (a -> b) -> a -> b
$ Bool -> Config -> Config
setModified Bool
True
(Config -> Config) -> Config -> Config
forall a b. (a -> b) -> a -> b
$ Config :: Bool -> Word32 -> Config
Config
{ watchRec :: Bool
watchRec = Bool
False
, createFlags :: Word32
createFlags = Word32
0
}
data Watch =
Watch
Handle
(IORef
(IntMap
( Array Word8
, Array Word8
)
)
)
newtype WD = WD CInt deriving Key -> WD -> ShowS
[WD] -> ShowS
WD -> String
(Key -> WD -> ShowS)
-> (WD -> String) -> ([WD] -> ShowS) -> Show WD
forall a.
(Key -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [WD] -> ShowS
$cshowList :: [WD] -> ShowS
show :: WD -> String
$cshow :: WD -> String
showsPrec :: Key -> WD -> ShowS
$cshowsPrec :: Key -> WD -> ShowS
Show
foreign import ccall unsafe
"sys/inotify.h inotify_init" c_inotify_init :: IO CInt
createWatch :: IO Watch
createWatch :: IO Watch
createWatch = do
CInt
rawfd <- String -> IO CInt -> IO CInt
forall a. (Eq a, Num a) => String -> IO a -> IO a
throwErrnoIfMinus1 String
"createWatch" IO CInt
c_inotify_init
(FD
fd, IODeviceType
fdType) <-
CInt
-> IOMode
-> Maybe (IODeviceType, CDev, CIno)
-> Bool
-> Bool
-> IO (FD, IODeviceType)
mkFD
CInt
rawfd
IOMode
ReadMode
((IODeviceType, CDev, CIno) -> Maybe (IODeviceType, CDev, CIno)
forall a. a -> Maybe a
Just (IODeviceType
Stream, CDev
0, CIno
0))
Bool
False
Bool
False
let fdString :: String
fdString = String
"<createWatch file descriptor: " String -> ShowS
forall a. [a] -> [a] -> [a]
++ FD -> String
forall a. Show a => a -> String
show FD
fd String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
">"
Handle
h <-
FD
-> IODeviceType
-> String
-> IOMode
-> Bool
-> Maybe TextEncoding
-> IO Handle
mkHandleFromFD
FD
fd
IODeviceType
fdType
String
fdString
IOMode
ReadMode
Bool
True
Maybe TextEncoding
forall a. Maybe a
Nothing
IORef (IntMap (Array Word8, Array Word8))
emptyMapRef <- IntMap (Array Word8, Array Word8)
-> IO (IORef (IntMap (Array Word8, Array Word8)))
forall a. a -> IO (IORef a)
newIORef IntMap (Array Word8, Array Word8)
forall a. IntMap a
Map.empty
Watch -> IO Watch
forall (m :: * -> *) a. Monad m => a -> m a
return (Watch -> IO Watch) -> Watch -> IO Watch
forall a b. (a -> b) -> a -> b
$ Handle -> IORef (IntMap (Array Word8, Array Word8)) -> Watch
Watch Handle
h IORef (IntMap (Array Word8, Array Word8))
emptyMapRef
foreign import ccall unsafe
"sys/inotify.h inotify_add_watch" c_inotify_add_watch
:: CInt -> CString -> CUInt -> IO CInt
toUtf8 :: MonadIO m => String -> m (Array Word8)
toUtf8 :: forall (m :: * -> *). MonadIO m => String -> m (Array Word8)
toUtf8 = Stream m Word8 -> m (Array Word8)
forall (m :: * -> *) a.
(MonadIO m, Unbox a) =>
Stream m a -> m (Array a)
A.fromStream (Stream m Word8 -> m (Array Word8))
-> (String -> Stream m Word8) -> String -> m (Array Word8)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Stream m Char -> Stream m Word8
forall (m :: * -> *). Monad m => Stream m Char -> Stream m Word8
U.encodeUtf8 (Stream m Char -> Stream m Word8)
-> (String -> Stream m Char) -> String -> Stream m Word8
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> Stream m Char
forall (m :: * -> *) a. Applicative m => [a] -> Stream m a
S.fromList
utf8ToString :: Array Word8 -> String
utf8ToString :: Array Word8 -> String
utf8ToString = Identity String -> String
forall a. Identity a -> a
runIdentity (Identity String -> String)
-> (Array Word8 -> Identity String) -> Array Word8 -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Fold Identity Char String
-> Stream Identity Char -> Identity String
forall (m :: * -> *) a b.
Monad m =>
Fold m a b -> Stream m a -> m b
S.fold Fold Identity Char String
forall (m :: * -> *) a. Monad m => Fold m a [a]
FL.toList (Stream Identity Char -> Identity String)
-> (Array Word8 -> Stream Identity Char)
-> Array Word8
-> Identity String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Stream Identity Word8 -> Stream Identity Char
forall (m :: * -> *). Monad m => Stream m Word8 -> Stream m Char
U.decodeUtf8' (Stream Identity Word8 -> Stream Identity Char)
-> (Array Word8 -> Stream Identity Word8)
-> Array Word8
-> Stream Identity Char
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Array Word8 -> Stream Identity Word8
forall (m :: * -> *) a. (Monad m, Unbox a) => Array a -> Stream m a
A.read
ensureTrailingSlash :: Array Word8 -> Array Word8
ensureTrailingSlash :: Array Word8 -> Array Word8
ensureTrailingSlash Array Word8
path =
if Array Word8 -> Key
forall a. Array a -> Key
byteLength Array Word8
path Key -> Key -> Bool
forall a. Eq a => a -> a -> Bool
/= Key
0
then
let mx :: Maybe Word8
mx = Key -> Array Word8 -> Maybe Word8
forall a. Unbox a => Key -> Array a -> Maybe a
A.getIndex (Array Word8 -> Key
forall a. Array a -> Key
byteLength Array Word8
path Key -> Key -> Key
forall a. Num a => a -> a -> a
- Key
1) Array Word8
path
in case Maybe Word8
mx of
Maybe Word8
Nothing -> String -> Array Word8
forall a. HasCallStack => String -> a
error String
"ensureTrailingSlash: Bug: Invalid index"
Just Word8
x ->
if Word8
x Word8 -> Word8 -> Bool
forall a. Eq a => a -> a -> Bool
/= Word8
forwardSlashByte
then Array Word8
path Array Word8 -> Array Word8 -> Array Word8
forall a. Semigroup a => a -> a -> a
<> Array Word8
forwardSlash
else Array Word8
path
else Array Word8
path
where forwardSlash :: Array Word8
forwardSlash = [Word8] -> Array Word8
forall a. Unbox a => [a] -> Array a
A.fromList [ Word8
forwardSlashByte ]
forwardSlashByte :: Word8
forwardSlashByte = Key -> Word8
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Char -> Key
ord Char
'/')
removeTrailingSlash :: Array Word8 -> Array Word8
removeTrailingSlash :: Array Word8 -> Array Word8
removeTrailingSlash Array Word8
path =
if Array Word8 -> Key
forall a. Array a -> Key
byteLength Array Word8
path Key -> Key -> Bool
forall a. Eq a => a -> a -> Bool
/= Key
0
then
let n :: Key
n = Array Word8 -> Key
forall a. Array a -> Key
byteLength Array Word8
path Key -> Key -> Key
forall a. Num a => a -> a -> a
- Key
1
mx :: Maybe Word8
mx = Key -> Array Word8 -> Maybe Word8
forall a. Unbox a => Key -> Array a -> Maybe a
A.getIndex Key
n Array Word8
path
in case Maybe Word8
mx of
Maybe Word8
Nothing -> String -> Array Word8
forall a. HasCallStack => String -> a
error String
"removeTrailingSlash: Bug: Invalid index"
Just Word8
x ->
if Word8
x Word8 -> Word8 -> Bool
forall a. Eq a => a -> a -> Bool
== Key -> Word8
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Char -> Key
ord Char
'/')
then Key -> Key -> Array Word8 -> Array Word8
forall a. Unbox a => Key -> Key -> Array a -> Array a
A.getSliceUnsafe Key
0 Key
n Array Word8
path
else Array Word8
path
else Array Word8
path
appendPaths :: Array Word8 -> Array Word8 -> Array Word8
appendPaths :: Array Word8 -> Array Word8 -> Array Word8
appendPaths Array Word8
a Array Word8
b
| Array Word8 -> Key
forall a. Array a -> Key
byteLength Array Word8
a Key -> Key -> Bool
forall a. Eq a => a -> a -> Bool
== Key
0 = Array Word8
b
| Array Word8 -> Key
forall a. Array a -> Key
byteLength Array Word8
b Key -> Key -> Bool
forall a. Eq a => a -> a -> Bool
== Key
0 = Array Word8
a
| Bool
otherwise = Array Word8 -> Array Word8
ensureTrailingSlash Array Word8
a Array Word8 -> Array Word8 -> Array Word8
forall a. Semigroup a => a -> a -> a
<> Array Word8
b
addToWatch :: Config -> Watch -> Array Word8 -> Array Word8 -> IO ()
addToWatch :: Config -> Watch -> Array Word8 -> Array Word8 -> IO ()
addToWatch cfg :: Config
cfg@Config{Bool
Word32
createFlags :: Word32
watchRec :: Bool
createFlags :: Config -> Word32
watchRec :: Config -> Bool
..} watch0 :: Watch
watch0@(Watch Handle
handle IORef (IntMap (Array Word8, Array Word8))
wdMap) Array Word8
root0 Array Word8
path0 = do
let root :: Array Word8
root = Array Word8 -> Array Word8
removeTrailingSlash Array Word8
root0
path :: Array Word8
path = Array Word8 -> Array Word8
removeTrailingSlash Array Word8
path0
absPath :: Array Word8
absPath = Array Word8 -> Array Word8 -> Array Word8
appendPaths Array Word8
root Array Word8
path
String -> IO ()
putStrLn (String -> IO ()) -> String -> IO ()
forall a b. (a -> b) -> a -> b
$ String
"root = " String -> ShowS
forall a. [a] -> [a] -> [a]
++ Array Word8 -> String
utf8ToString Array Word8
root String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
" path = " String -> ShowS
forall a. [a] -> [a] -> [a]
++ Array Word8 -> String
utf8ToString Array Word8
path String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
" absPath = " String -> ShowS
forall a. [a] -> [a] -> [a]
++ Array Word8 -> String
utf8ToString Array Word8
absPath
FD
fd <- Handle -> IO FD
handleToFd Handle
handle
CInt
wd <- Array Word8 -> (CString -> IO CInt) -> IO CInt
forall a b. Array a -> (CString -> IO b) -> IO b
A.asCStringUnsafe Array Word8
absPath ((CString -> IO CInt) -> IO CInt)
-> (CString -> IO CInt) -> IO CInt
forall a b. (a -> b) -> a -> b
$ \CString
pathPtr ->
String -> IO CInt -> IO CInt
forall a. (Eq a, Num a) => String -> IO a -> IO a
throwErrnoIfMinus1 (String
"addToWatch: " String -> ShowS
forall a. [a] -> [a] -> [a]
++ Array Word8 -> String
utf8ToString Array Word8
absPath) (IO CInt -> IO CInt) -> IO CInt -> IO CInt
forall a b. (a -> b) -> a -> b
$
CInt -> CString -> CUInt -> IO CInt
c_inotify_add_watch (FD -> CInt
fdFD FD
fd) CString
pathPtr (Word32 -> CUInt
CUInt Word32
createFlags)
IORef (IntMap (Array Word8, Array Word8))
-> (IntMap (Array Word8, Array Word8)
-> IntMap (Array Word8, Array Word8))
-> IO ()
forall a. IORef a -> (a -> a) -> IO ()
modifyIORef IORef (IntMap (Array Word8, Array Word8))
wdMap (Key
-> (Array Word8, Array Word8)
-> IntMap (Array Word8, Array Word8)
-> IntMap (Array Word8, Array Word8)
forall a. Key -> a -> IntMap a -> IntMap a
Map.insert (CInt -> Key
forall a b. (Integral a, Num b) => a -> b
fromIntegral CInt
wd) (Array Word8
root, Array Word8
path))
Bool
pathIsDir <- String -> IO Bool
doesDirectoryExist (String -> IO Bool) -> String -> IO Bool
forall a b. (a -> b) -> a -> b
$ Array Word8 -> String
utf8ToString Array Word8
absPath
Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Bool
watchRec Bool -> Bool -> Bool
&& Bool
pathIsDir) (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$ do
let f :: Array Word8 -> IO ()
f = Config -> Watch -> Array Word8 -> Array Word8 -> IO ()
addToWatch Config
cfg Watch
watch0 Array Word8
root (Array Word8 -> IO ())
-> (Array Word8 -> Array Word8) -> Array Word8 -> IO ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Array Word8 -> Array Word8 -> Array Word8
appendPaths Array Word8
path
in Fold IO (Array Word8) () -> Stream IO (Array Word8) -> IO ()
forall (m :: * -> *) a b.
Monad m =>
Fold m a b -> Stream m a -> m b
S.fold ((Array Word8 -> IO ()) -> Fold IO (Array Word8) ()
forall (m :: * -> *) a b. Monad m => (a -> m b) -> Fold m a ()
FL.drainMapM Array Word8 -> IO ()
f)
(Stream IO (Array Word8) -> IO ())
-> Stream IO (Array Word8) -> IO ()
forall a b. (a -> b) -> a -> b
$ (String -> IO (Array Word8))
-> Stream IO String -> Stream IO (Array Word8)
forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> Stream m a -> Stream m b
S.mapM String -> IO (Array Word8)
forall (m :: * -> *). MonadIO m => String -> m (Array Word8)
toUtf8
(Stream IO String -> Stream IO (Array Word8))
-> Stream IO String -> Stream IO (Array Word8)
forall a b. (a -> b) -> a -> b
$ String -> Stream IO String
forall (m :: * -> *).
(MonadIO m, MonadCatch m) =>
String -> Stream m String
Dir.readDirs (String -> Stream IO String) -> String -> Stream IO String
forall a b. (a -> b) -> a -> b
$ Array Word8 -> String
utf8ToString Array Word8
absPath
foreign import ccall unsafe
"sys/inotify.h inotify_rm_watch" c_inotify_rm_watch
:: CInt -> CInt -> IO CInt
removeFromWatch :: Watch -> Array Word8 -> IO ()
removeFromWatch :: Watch -> Array Word8 -> IO ()
removeFromWatch (Watch Handle
handle IORef (IntMap (Array Word8, Array Word8))
wdMap) Array Word8
path = do
FD
fd <- Handle -> IO FD
handleToFd Handle
handle
IntMap (Array Word8, Array Word8)
km <- IORef (IntMap (Array Word8, Array Word8))
-> IO (IntMap (Array Word8, Array Word8))
forall a. IORef a -> IO a
readIORef IORef (IntMap (Array Word8, Array Word8))
wdMap
IntMap (Array Word8, Array Word8)
wdMap1 <- (IntMap (Array Word8, Array Word8)
-> (Key, (Array Word8, Array Word8))
-> IO (IntMap (Array Word8, Array Word8)))
-> IntMap (Array Word8, Array Word8)
-> [(Key, (Array Word8, Array Word8))]
-> IO (IntMap (Array Word8, Array Word8))
forall (t :: * -> *) (m :: * -> *) b a.
(Foldable t, Monad m) =>
(b -> a -> m b) -> b -> t a -> m b
foldlM (FD
-> IntMap (Array Word8, Array Word8)
-> (Key, (Array Word8, Array Word8))
-> IO (IntMap (Array Word8, Array Word8))
forall {b}.
FD
-> IntMap (Array Word8, b)
-> (Key, (Array Word8, b))
-> IO (IntMap (Array Word8, b))
step FD
fd) IntMap (Array Word8, Array Word8)
forall a. IntMap a
Map.empty (IntMap (Array Word8, Array Word8)
-> [(Key, (Array Word8, Array Word8))]
forall a. IntMap a -> [(Key, a)]
Map.toList IntMap (Array Word8, Array Word8)
km)
IORef (IntMap (Array Word8, Array Word8))
-> IntMap (Array Word8, Array Word8) -> IO ()
forall a. IORef a -> a -> IO ()
writeIORef IORef (IntMap (Array Word8, Array Word8))
wdMap IntMap (Array Word8, Array Word8)
wdMap1
where
step :: FD
-> IntMap (Array Word8, b)
-> (Key, (Array Word8, b))
-> IO (IntMap (Array Word8, b))
step FD
fd IntMap (Array Word8, b)
newMap (Key
wd, (Array Word8, b)
v) = do
if (Array Word8, b) -> Array Word8
forall a b. (a, b) -> a
fst (Array Word8, b)
v Array Word8 -> Array Word8 -> Bool
forall a. Eq a => a -> a -> Bool
== Array Word8
path
then do
let err :: String
err = String
"removeFromWatch: " String -> ShowS
forall a. [a] -> [a] -> [a]
++ ShowS
forall a. Show a => a -> String
show (Array Word8 -> String
utf8ToString Array Word8
path)
rm :: IO CInt
rm = CInt -> CInt -> IO CInt
c_inotify_rm_watch (FD -> CInt
fdFD FD
fd) (Key -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral Key
wd)
IO CInt -> IO ()
forall (f :: * -> *) a. Functor f => f a -> f ()
void (IO CInt -> IO ()) -> IO CInt -> IO ()
forall a b. (a -> b) -> a -> b
$ String -> IO CInt -> IO CInt
forall a. (Eq a, Num a) => String -> IO a -> IO a
throwErrnoIfMinus1 String
err IO CInt
rm
IntMap (Array Word8, b) -> IO (IntMap (Array Word8, b))
forall (m :: * -> *) a. Monad m => a -> m a
return IntMap (Array Word8, b)
newMap
else IntMap (Array Word8, b) -> IO (IntMap (Array Word8, b))
forall (m :: * -> *) a. Monad m => a -> m a
return (IntMap (Array Word8, b) -> IO (IntMap (Array Word8, b)))
-> IntMap (Array Word8, b) -> IO (IntMap (Array Word8, b))
forall a b. (a -> b) -> a -> b
$ Key
-> (Array Word8, b)
-> IntMap (Array Word8, b)
-> IntMap (Array Word8, b)
forall a. Key -> a -> IntMap a -> IntMap a
Map.insert Key
wd (Array Word8, b)
v IntMap (Array Word8, b)
newMap
openWatch :: Config -> NonEmpty (Array Word8) -> IO Watch
openWatch :: Config -> NonEmpty (Array Word8) -> IO Watch
openWatch Config
cfg NonEmpty (Array Word8)
paths = do
Watch
w <- IO Watch
createWatch
(Array Word8 -> IO ()) -> [Array Word8] -> IO ()
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
(a -> m b) -> t a -> m ()
mapM_
(\Array Word8
root -> Config -> Watch -> Array Word8 -> Array Word8 -> IO ()
addToWatch Config
cfg Watch
w Array Word8
root ([Word8] -> Array Word8
forall a. Unbox a => [a] -> Array a
A.fromList []))
([Array Word8] -> IO ()) -> [Array Word8] -> IO ()
forall a b. (a -> b) -> a -> b
$ NonEmpty (Array Word8) -> [Array Word8]
forall a. NonEmpty a -> [a]
NonEmpty.toList NonEmpty (Array Word8)
paths
Watch -> IO Watch
forall (m :: * -> *) a. Monad m => a -> m a
return Watch
w
closeWatch :: Watch -> IO ()
closeWatch :: Watch -> IO ()
closeWatch (Watch Handle
h IORef (IntMap (Array Word8, Array Word8))
_) = Handle -> IO ()
hClose Handle
h
newtype Cookie = Cookie Word32 deriving (Key -> Cookie -> ShowS
[Cookie] -> ShowS
Cookie -> String
(Key -> Cookie -> ShowS)
-> (Cookie -> String) -> ([Cookie] -> ShowS) -> Show Cookie
forall a.
(Key -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Cookie] -> ShowS
$cshowList :: [Cookie] -> ShowS
show :: Cookie -> String
$cshow :: Cookie -> String
showsPrec :: Key -> Cookie -> ShowS
$cshowsPrec :: Key -> Cookie -> ShowS
Show, Cookie -> Cookie -> Bool
(Cookie -> Cookie -> Bool)
-> (Cookie -> Cookie -> Bool) -> Eq Cookie
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Cookie -> Cookie -> Bool
$c/= :: Cookie -> Cookie -> Bool
== :: Cookie -> Cookie -> Bool
$c== :: Cookie -> Cookie -> Bool
Eq)
data Event = Event
{ Event -> CInt
eventWd :: CInt
, Event -> Word32
eventFlags :: Word32
, Event -> Word32
eventCookie :: Word32
, Event -> Array Word8
eventRelPath :: Array Word8
, Event -> IntMap (Array Word8, Array Word8)
eventMap :: IntMap (Array Word8, Array Word8)
} deriving (Key -> Event -> ShowS
[Event] -> ShowS
Event -> String
(Key -> Event -> ShowS)
-> (Event -> String) -> ([Event] -> ShowS) -> Show Event
forall a.
(Key -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Event] -> ShowS
$cshowList :: [Event] -> ShowS
show :: Event -> String
$cshow :: Event -> String
showsPrec :: Key -> Event -> ShowS
$cshowsPrec :: Key -> Event -> ShowS
Show, Eq Event
Eq Event
-> (Event -> Event -> Ordering)
-> (Event -> Event -> Bool)
-> (Event -> Event -> Bool)
-> (Event -> Event -> Bool)
-> (Event -> Event -> Bool)
-> (Event -> Event -> Event)
-> (Event -> Event -> Event)
-> Ord Event
Event -> Event -> Bool
Event -> Event -> Ordering
Event -> Event -> Event
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: Event -> Event -> Event
$cmin :: Event -> Event -> Event
max :: Event -> Event -> Event
$cmax :: Event -> Event -> Event
>= :: Event -> Event -> Bool
$c>= :: Event -> Event -> Bool
> :: Event -> Event -> Bool
$c> :: Event -> Event -> Bool
<= :: Event -> Event -> Bool
$c<= :: Event -> Event -> Bool
< :: Event -> Event -> Bool
$c< :: Event -> Event -> Bool
compare :: Event -> Event -> Ordering
$ccompare :: Event -> Event -> Ordering
Ord, Event -> Event -> Bool
(Event -> Event -> Bool) -> (Event -> Event -> Bool) -> Eq Event
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Event -> Event -> Bool
$c/= :: Event -> Event -> Bool
== :: Event -> Event -> Bool
$c== :: Event -> Event -> Bool
Eq)
readOneEvent :: Config -> Watch -> Parser Word8 IO Event
readOneEvent :: Config -> Watch -> Parser Word8 IO Event
readOneEvent Config
cfg wt :: Watch
wt@(Watch Handle
_ IORef (IntMap (Array Word8, Array Word8))
wdMap) = do
let headerLen :: Key
headerLen = CInt -> Key
forall a. Storable a => a -> Key
sizeOf (CInt
forall a. HasCallStack => a
undefined :: CInt) Key -> Key -> Key
forall a. Num a => a -> a -> a
+ Key
12
Array Word8
arr <- Key -> Fold IO Word8 (Array Word8) -> Parser Word8 IO (Array Word8)
forall (m :: * -> *) a b.
Monad m =>
Key -> Fold m a b -> Parser a m b
PR.takeEQ Key
headerLen (Key -> Fold IO Word8 (Array Word8)
forall (m :: * -> *) a.
(MonadIO m, Unbox a) =>
Key -> Fold m a (Array a)
A.writeN Key
headerLen)
(Word8
ewd, Word32
eflags, Word32
cookie, Key
pathLen) <- IO (Word8, Word32, Word32, Key)
-> Parser Word8 IO (Word8, Word32, Word32, Key)
forall (m :: * -> *) b a. Monad m => m b -> Parser a m b
PR.fromEffect (IO (Word8, Word32, Word32, Key)
-> Parser Word8 IO (Word8, Word32, Word32, Key))
-> IO (Word8, Word32, Word32, Key)
-> Parser Word8 IO (Word8, Word32, Word32, Key)
forall a b. (a -> b) -> a -> b
$ Array Word8
-> (Ptr Word8 -> IO (Word8, Word32, Word32, Key))
-> IO (Word8, Word32, Word32, Key)
forall (m :: * -> *) a b.
MonadIO m =>
Array a -> (Ptr a -> m b) -> m b
A.unsafePinnedAsPtr Array Word8
arr Ptr Word8 -> IO (Word8, Word32, Word32, Key)
forall {b} {c} {d}.
(Storable b, Storable c, Num d) =>
Ptr Word8 -> IO (Word8, b, c, d)
readHeader
Array Word8
path <-
if Key
pathLen Key -> Key -> Bool
forall a. Eq a => a -> a -> Bool
/= Key
0
then do
Array Word8
pth <-
Fold IO Word8 (Array Word8) -> Parser Word8 IO (Array Word8)
forall (m :: * -> *) a b. Monad m => Fold m a b -> Parser a m b
PR.fromFold
(Fold IO Word8 (Array Word8) -> Parser Word8 IO (Array Word8))
-> Fold IO Word8 (Array Word8) -> Parser Word8 IO (Array Word8)
forall a b. (a -> b) -> a -> b
$ (Word8 -> Bool)
-> Fold IO Word8 (Array Word8) -> Fold IO Word8 (Array Word8)
forall (m :: * -> *) a b.
Monad m =>
(a -> Bool) -> Fold m a b -> Fold m a b
FL.takeEndBy_ (Word8 -> Word8 -> Bool
forall a. Eq a => a -> a -> Bool
== Word8
0)
(Fold IO Word8 (Array Word8) -> Fold IO Word8 (Array Word8))
-> Fold IO Word8 (Array Word8) -> Fold IO Word8 (Array Word8)
forall a b. (a -> b) -> a -> b
$ Key -> Fold IO Word8 (Array Word8) -> Fold IO Word8 (Array Word8)
forall (m :: * -> *) a b.
Monad m =>
Key -> Fold m a b -> Fold m a b
FL.take Key
pathLen (Key -> Fold IO Word8 (Array Word8)
forall (m :: * -> *) a.
(MonadIO m, Unbox a) =>
Key -> Fold m a (Array a)
A.writeN Key
pathLen)
let remaining :: Key
remaining = Key
pathLen Key -> Key -> Key
forall a. Num a => a -> a -> a
- Array Word8 -> Key
forall a. Array a -> Key
byteLength Array Word8
pth Key -> Key -> Key
forall a. Num a => a -> a -> a
- Key
1
Bool -> Parser Word8 IO () -> Parser Word8 IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Key
remaining Key -> Key -> Bool
forall a. Eq a => a -> a -> Bool
/= Key
0) (Parser Word8 IO () -> Parser Word8 IO ())
-> Parser Word8 IO () -> Parser Word8 IO ()
forall a b. (a -> b) -> a -> b
$ Key -> Fold IO Word8 () -> Parser Word8 IO ()
forall (m :: * -> *) a b.
Monad m =>
Key -> Fold m a b -> Parser a m b
PR.takeEQ Key
remaining Fold IO Word8 ()
forall (m :: * -> *) a. Monad m => Fold m a ()
FL.drain
Array Word8 -> Parser Word8 IO (Array Word8)
forall (m :: * -> *) a. Monad m => a -> m a
return Array Word8
pth
else Array Word8 -> Parser Word8 IO (Array Word8)
forall (m :: * -> *) a. Monad m => a -> m a
return (Array Word8 -> Parser Word8 IO (Array Word8))
-> Array Word8 -> Parser Word8 IO (Array Word8)
forall a b. (a -> b) -> a -> b
$ [Word8] -> Array Word8
forall a. Unbox a => [a] -> Array a
A.fromList []
IntMap (Array Word8, Array Word8)
wdm <- IO (IntMap (Array Word8, Array Word8))
-> Parser Word8 IO (IntMap (Array Word8, Array Word8))
forall (m :: * -> *) b a. Monad m => m b -> Parser a m b
PR.fromEffect (IO (IntMap (Array Word8, Array Word8))
-> Parser Word8 IO (IntMap (Array Word8, Array Word8)))
-> IO (IntMap (Array Word8, Array Word8))
-> Parser Word8 IO (IntMap (Array Word8, Array Word8))
forall a b. (a -> b) -> a -> b
$ IORef (IntMap (Array Word8, Array Word8))
-> IO (IntMap (Array Word8, Array Word8))
forall a. IORef a -> IO a
readIORef IORef (IntMap (Array Word8, Array Word8))
wdMap
let (Array Word8
root, Array Word8
sub) =
case Key
-> IntMap (Array Word8, Array Word8)
-> Maybe (Array Word8, Array Word8)
forall a. Key -> IntMap a -> Maybe a
Map.lookup (Word8 -> Key
forall a b. (Integral a, Num b) => a -> b
fromIntegral Word8
ewd) IntMap (Array Word8, Array Word8)
wdm of
Just (Array Word8, Array Word8)
pair -> (Array Word8, Array Word8)
pair
Maybe (Array Word8, Array Word8)
Nothing ->
String -> (Array Word8, Array Word8)
forall a. HasCallStack => String -> a
error (String -> (Array Word8, Array Word8))
-> String -> (Array Word8, Array Word8)
forall a b. (a -> b) -> a -> b
$ String
"readOneEvent: "
String -> ShowS
forall a. Semigroup a => a -> a -> a
<> String
"Unknown watch descriptor: "
String -> ShowS
forall a. Semigroup a => a -> a -> a
<> Word8 -> String
forall a. Show a => a -> String
show Word8
ewd
let sub1 :: Array Word8
sub1 = Array Word8 -> Array Word8 -> Array Word8
appendPaths Array Word8
sub Array Word8
path
isDirCreate :: Bool
isDirCreate = Word32
eflags Word32 -> Word32 -> Word32
forall a. Bits a => a -> a -> a
.&. Word32
iN_ISDIR Word32 -> Word32 -> Bool
forall a. Eq a => a -> a -> Bool
/= Word32
0 Bool -> Bool -> Bool
&& Word32
eflags Word32 -> Word32 -> Word32
forall a. Bits a => a -> a -> a
.&. Word32
iN_CREATE Word32 -> Word32 -> Bool
forall a. Eq a => a -> a -> Bool
/= Word32
0
Bool -> Parser Word8 IO () -> Parser Word8 IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Config -> Bool
watchRec Config
cfg Bool -> Bool -> Bool
&& Bool
isDirCreate)
(Parser Word8 IO () -> Parser Word8 IO ())
-> Parser Word8 IO () -> Parser Word8 IO ()
forall a b. (a -> b) -> a -> b
$ IO () -> Parser Word8 IO ()
forall (m :: * -> *) b a. Monad m => m b -> Parser a m b
PR.fromEffect (IO () -> Parser Word8 IO ()) -> IO () -> Parser Word8 IO ()
forall a b. (a -> b) -> a -> b
$ Config -> Watch -> Array Word8 -> Array Word8 -> IO ()
addToWatch Config
cfg Watch
wt Array Word8
root Array Word8
sub1
Event -> Parser Word8 IO Event
forall (m :: * -> *) a. Monad m => a -> m a
return (Event -> Parser Word8 IO Event) -> Event -> Parser Word8 IO Event
forall a b. (a -> b) -> a -> b
$ Event :: CInt
-> Word32
-> Word32
-> Array Word8
-> IntMap (Array Word8, Array Word8)
-> Event
Event
{ eventWd :: CInt
eventWd = Word8 -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral Word8
ewd
, eventFlags :: Word32
eventFlags = Word32
eflags
, eventCookie :: Word32
eventCookie = Word32
cookie
, eventRelPath :: Array Word8
eventRelPath = Array Word8
sub1
, eventMap :: IntMap (Array Word8, Array Word8)
eventMap = IntMap (Array Word8, Array Word8)
wdm
}
where
readHeader :: Ptr Word8 -> IO (Word8, b, c, d)
readHeader (Ptr Word8
ptr :: Ptr Word8) = do
let len :: Key
len = CInt -> Key
forall a. Storable a => a -> Key
sizeOf (CInt
forall a. HasCallStack => a
undefined :: CInt)
Word8
ewd <- Ptr Word8 -> IO Word8
forall a. Storable a => Ptr a -> IO a
peek Ptr Word8
ptr
b
eflags <- Ptr Word8 -> Key -> IO b
forall a b. Storable a => Ptr b -> Key -> IO a
peekByteOff Ptr Word8
ptr Key
len
c
cookie <- Ptr Word8 -> Key -> IO c
forall a b. Storable a => Ptr b -> Key -> IO a
peekByteOff Ptr Word8
ptr (Key
len Key -> Key -> Key
forall a. Num a => a -> a -> a
+ Key
4)
Word32
pathLen :: Word32 <- Ptr Word8 -> Key -> IO Word32
forall a b. Storable a => Ptr b -> Key -> IO a
peekByteOff Ptr Word8
ptr (Key
len Key -> Key -> Key
forall a. Num a => a -> a -> a
+ Key
8)
(Word8, b, c, d) -> IO (Word8, b, c, d)
forall (m :: * -> *) a. Monad m => a -> m a
return (Word8
ewd, b
eflags, c
cookie, Word32 -> d
forall a b. (Integral a, Num b) => a -> b
fromIntegral Word32
pathLen)
watchToStream :: Config -> Watch -> Stream IO Event
watchToStream :: Config -> Watch -> Stream IO Event
watchToStream Config
cfg wt :: Watch
wt@(Watch Handle
handle IORef (IntMap (Array Word8, Array Word8))
_) = do
Stream IO (Either ParseError Event) -> Stream IO Event
forall (m :: * -> *) a b.
Monad m =>
Stream m (Either a b) -> Stream m b
S.catRights (Stream IO (Either ParseError Event) -> Stream IO Event)
-> Stream IO (Either ParseError Event) -> Stream IO Event
forall a b. (a -> b) -> a -> b
$ Parser Word8 IO Event
-> Stream IO Word8 -> Stream IO (Either ParseError Event)
forall (m :: * -> *) a b.
Monad m =>
Parser a m b -> Stream m a -> Stream m (Either ParseError b)
S.parseMany (Config -> Watch -> Parser Word8 IO Event
readOneEvent Config
cfg Watch
wt) (Stream IO Word8 -> Stream IO (Either ParseError Event))
-> Stream IO Word8 -> Stream IO (Either ParseError Event)
forall a b. (a -> b) -> a -> b
$ Unfold IO Handle Word8 -> Handle -> Stream IO Word8
forall (m :: * -> *) a b.
Applicative m =>
Unfold m a b -> a -> Stream m b
S.unfold Unfold IO Handle Word8
forall (m :: * -> *). MonadIO m => Unfold m Handle Word8
FH.reader Handle
handle
watchWith :: (Config -> Config) -> NonEmpty (Array Word8) -> Stream IO Event
watchWith :: (Config -> Config) -> NonEmpty (Array Word8) -> Stream IO Event
watchWith Config -> Config
f NonEmpty (Array Word8)
paths = IO Watch
-> (Watch -> IO ())
-> (Watch -> Stream IO Event)
-> Stream IO Event
forall (m :: * -> *) b c a.
(MonadIO m, MonadCatch m) =>
IO b -> (b -> IO c) -> (b -> Stream m a) -> Stream m a
S.bracketIO IO Watch
before Watch -> IO ()
after (Config -> Watch -> Stream IO Event
watchToStream Config
cfg)
where
cfg :: Config
cfg = Config -> Config
f Config
defaultConfig
before :: IO Watch
before = Config -> NonEmpty (Array Word8) -> IO Watch
openWatch Config
cfg NonEmpty (Array Word8)
paths
after :: Watch -> IO ()
after = Watch -> IO ()
closeWatch
watchRecursive :: NonEmpty (Array Word8) -> Stream IO Event
watchRecursive :: NonEmpty (Array Word8) -> Stream IO Event
watchRecursive = (Config -> Config) -> NonEmpty (Array Word8) -> Stream IO Event
watchWith (Bool -> Config -> Config
setRecursiveMode Bool
True)
watch :: NonEmpty (Array Word8) -> Stream IO Event
watch :: NonEmpty (Array Word8) -> Stream IO Event
watch = (Config -> Config) -> NonEmpty (Array Word8) -> Stream IO Event
watchWith Config -> Config
forall a. a -> a
id
getRoot :: Event -> Array Word8
getRoot :: Event -> Array Word8
getRoot Event{Word32
CInt
IntMap (Array Word8, Array Word8)
Array Word8
eventMap :: IntMap (Array Word8, Array Word8)
eventRelPath :: Array Word8
eventCookie :: Word32
eventFlags :: Word32
eventWd :: CInt
eventMap :: Event -> IntMap (Array Word8, Array Word8)
eventRelPath :: Event -> Array Word8
eventCookie :: Event -> Word32
eventFlags :: Event -> Word32
eventWd :: Event -> CInt
..} =
if CInt
eventWd CInt -> CInt -> Bool
forall a. Ord a => a -> a -> Bool
>= CInt
1
then
case Key
-> IntMap (Array Word8, Array Word8)
-> Maybe (Array Word8, Array Word8)
forall a. Key -> IntMap a -> Maybe a
Map.lookup (CInt -> Key
forall a b. (Integral a, Num b) => a -> b
fromIntegral CInt
eventWd) IntMap (Array Word8, Array Word8)
eventMap of
Just (Array Word8, Array Word8)
path -> (Array Word8, Array Word8) -> Array Word8
forall a b. (a, b) -> a
fst (Array Word8, Array Word8)
path
Maybe (Array Word8, Array Word8)
Nothing ->
String -> Array Word8
forall a. HasCallStack => String -> a
error (String -> Array Word8) -> String -> Array Word8
forall a b. (a -> b) -> a -> b
$ String
"Bug: getRoot: No path found corresponding to the "
String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
"watch descriptor " String -> ShowS
forall a. [a] -> [a] -> [a]
++ CInt -> String
forall a. Show a => a -> String
show CInt
eventWd
else [Word8] -> Array Word8
forall a. Unbox a => [a] -> Array a
A.fromList []
getRelPath :: Event -> Array Word8
getRelPath :: Event -> Array Word8
getRelPath Event{Word32
CInt
IntMap (Array Word8, Array Word8)
Array Word8
eventMap :: IntMap (Array Word8, Array Word8)
eventRelPath :: Array Word8
eventCookie :: Word32
eventFlags :: Word32
eventWd :: CInt
eventMap :: Event -> IntMap (Array Word8, Array Word8)
eventRelPath :: Event -> Array Word8
eventCookie :: Event -> Word32
eventFlags :: Event -> Word32
eventWd :: Event -> CInt
..} = Array Word8
eventRelPath
getAbsPath :: Event -> Array Word8
getAbsPath :: Event -> Array Word8
getAbsPath Event
ev =
let relpath :: Array Word8
relpath = Event -> Array Word8
getRelPath Event
ev
root :: Array Word8
root = Event -> Array Word8
getRoot Event
ev
in if Array Word8 -> Key
forall a. Array a -> Key
byteLength Array Word8
relpath Key -> Key -> Bool
forall a. Eq a => a -> a -> Bool
/= Key
0
then Array Word8 -> Array Word8
ensureTrailingSlash Array Word8
root Array Word8 -> Array Word8 -> Array Word8
forall a. Semigroup a => a -> a -> a
<> Array Word8
relpath
else Array Word8 -> Array Word8
removeTrailingSlash Array Word8
root
getCookie :: Event -> Cookie
getCookie :: Event -> Cookie
getCookie Event{Word32
CInt
IntMap (Array Word8, Array Word8)
Array Word8
eventMap :: IntMap (Array Word8, Array Word8)
eventRelPath :: Array Word8
eventCookie :: Word32
eventFlags :: Word32
eventWd :: CInt
eventMap :: Event -> IntMap (Array Word8, Array Word8)
eventRelPath :: Event -> Array Word8
eventCookie :: Event -> Word32
eventFlags :: Event -> Word32
eventWd :: Event -> CInt
..} = Word32 -> Cookie
Cookie Word32
eventCookie
getFlag :: Word32 -> Event -> Bool
getFlag :: Word32 -> Event -> Bool
getFlag Word32
mask Event{Word32
CInt
IntMap (Array Word8, Array Word8)
Array Word8
eventMap :: IntMap (Array Word8, Array Word8)
eventRelPath :: Array Word8
eventCookie :: Word32
eventFlags :: Word32
eventWd :: CInt
eventMap :: Event -> IntMap (Array Word8, Array Word8)
eventRelPath :: Event -> Array Word8
eventCookie :: Event -> Word32
eventFlags :: Event -> Word32
eventWd :: Event -> CInt
..} = Word32
eventFlags Word32 -> Word32 -> Word32
forall a. Bits a => a -> a -> a
.&. Word32
mask Word32 -> Word32 -> Bool
forall a. Eq a => a -> a -> Bool
/= Word32
0
foreign import capi
"sys/inotify.h value IN_Q_OVERFLOW" iN_Q_OVERFLOW :: Word32
isEventsLost :: Event -> Bool
isEventsLost :: Event -> Bool
isEventsLost = Word32 -> Event -> Bool
getFlag Word32
iN_Q_OVERFLOW
foreign import capi
"sys/inotify.h value IN_IGNORED" iN_IGNORED :: Word32
isRootUnwatched :: Event -> Bool
isRootUnwatched :: Event -> Bool
isRootUnwatched = Word32 -> Event -> Bool
getFlag Word32
iN_IGNORED
isRootDeleted :: Event -> Bool
isRootDeleted :: Event -> Bool
isRootDeleted = Word32 -> Event -> Bool
getFlag Word32
iN_DELETE_SELF
isRootMoved :: Event -> Bool
isRootMoved :: Event -> Bool
isRootMoved = Word32 -> Event -> Bool
getFlag Word32
iN_MOVE_SELF
foreign import capi
"sys/inotify.h value IN_UNMOUNT" iN_UNMOUNT :: Word32
isRootUnmounted :: Event -> Bool
isRootUnmounted :: Event -> Bool
isRootUnmounted = Word32 -> Event -> Bool
getFlag Word32
iN_UNMOUNT
isRootPathEvent :: Event -> Bool
isRootPathEvent :: Event -> Bool
isRootPathEvent = Word32 -> Event -> Bool
getFlag (Word32
iN_DELETE_SELF Word32 -> Word32 -> Word32
forall a. Bits a => a -> a -> a
.|. Word32
iN_MOVE_SELF Word32 -> Word32 -> Word32
forall a. Bits a => a -> a -> a
.|. Word32
iN_UNMOUNT)
isAttrsModified :: Event -> Bool
isAttrsModified :: Event -> Bool
isAttrsModified = Word32 -> Event -> Bool
getFlag Word32
iN_ATTRIB
isAccessed :: Event -> Bool
isAccessed :: Event -> Bool
isAccessed = Word32 -> Event -> Bool
getFlag Word32
iN_ACCESS
isOpened :: Event -> Bool
isOpened :: Event -> Bool
isOpened = Word32 -> Event -> Bool
getFlag Word32
iN_OPEN
isWriteClosed :: Event -> Bool
isWriteClosed :: Event -> Bool
isWriteClosed = Word32 -> Event -> Bool
getFlag Word32
iN_CLOSE_WRITE
isNonWriteClosed :: Event -> Bool
isNonWriteClosed :: Event -> Bool
isNonWriteClosed = Word32 -> Event -> Bool
getFlag Word32
iN_CLOSE_NOWRITE
isCreated :: Event -> Bool
isCreated :: Event -> Bool
isCreated = Word32 -> Event -> Bool
getFlag Word32
iN_CREATE
isDeleted :: Event -> Bool
isDeleted :: Event -> Bool
isDeleted = Word32 -> Event -> Bool
getFlag Word32
iN_DELETE
isMovedFrom :: Event -> Bool
isMovedFrom :: Event -> Bool
isMovedFrom = Word32 -> Event -> Bool
getFlag Word32
iN_MOVED_FROM
isMovedTo :: Event -> Bool
isMovedTo :: Event -> Bool
isMovedTo = Word32 -> Event -> Bool
getFlag Word32
iN_MOVED_TO
isMoved :: Event -> Bool
isMoved :: Event -> Bool
isMoved Event
ev = Event -> Bool
isMovedFrom Event
ev Bool -> Bool -> Bool
|| Event -> Bool
isMovedTo Event
ev
isModified :: Event -> Bool
isModified :: Event -> Bool
isModified = Word32 -> Event -> Bool
getFlag Word32
iN_MODIFY
foreign import capi
"sys/inotify.h value IN_ISDIR" iN_ISDIR :: Word32
isDir :: Event -> Bool
isDir :: Event -> Bool
isDir = Word32 -> Event -> Bool
getFlag Word32
iN_ISDIR
showEvent :: Event -> String
showEvent :: Event -> String
showEvent ev :: Event
ev@Event{Word32
CInt
IntMap (Array Word8, Array Word8)
Array Word8
eventMap :: IntMap (Array Word8, Array Word8)
eventRelPath :: Array Word8
eventCookie :: Word32
eventFlags :: Word32
eventWd :: CInt
eventMap :: Event -> IntMap (Array Word8, Array Word8)
eventRelPath :: Event -> Array Word8
eventCookie :: Event -> Word32
eventFlags :: Event -> Word32
eventWd :: Event -> CInt
..} =
String
"--------------------------"
String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
"\nWd = " String -> ShowS
forall a. [a] -> [a] -> [a]
++ CInt -> String
forall a. Show a => a -> String
show CInt
eventWd
String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
"\nRoot = " String -> ShowS
forall a. [a] -> [a] -> [a]
++ ShowS
forall a. Show a => a -> String
show (Array Word8 -> String
utf8ToString (Array Word8 -> String) -> Array Word8 -> String
forall a b. (a -> b) -> a -> b
$ Event -> Array Word8
getRoot Event
ev)
String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
"\nPath = " String -> ShowS
forall a. [a] -> [a] -> [a]
++ ShowS
forall a. Show a => a -> String
show (Array Word8 -> String
utf8ToString (Array Word8 -> String) -> Array Word8 -> String
forall a b. (a -> b) -> a -> b
$ Event -> Array Word8
getRelPath Event
ev)
String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
"\nCookie = " String -> ShowS
forall a. [a] -> [a] -> [a]
++ Cookie -> String
forall a. Show a => a -> String
show (Event -> Cookie
getCookie Event
ev)
String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
"\nFlags " String -> ShowS
forall a. [a] -> [a] -> [a]
++ Word32 -> String
forall a. Show a => a -> String
show Word32
eventFlags
String -> ShowS
forall a. [a] -> [a] -> [a]
++ (Event -> Bool) -> ShowS
showev Event -> Bool
isEventsLost String
"Overflow"
String -> ShowS
forall a. [a] -> [a] -> [a]
++ (Event -> Bool) -> ShowS
showev Event -> Bool
isRootUnwatched String
"RootUnwatched"
String -> ShowS
forall a. [a] -> [a] -> [a]
++ (Event -> Bool) -> ShowS
showev Event -> Bool
isRootDeleted String
"RootDeleted"
String -> ShowS
forall a. [a] -> [a] -> [a]
++ (Event -> Bool) -> ShowS
showev Event -> Bool
isRootMoved String
"RootMoved"
String -> ShowS
forall a. [a] -> [a] -> [a]
++ (Event -> Bool) -> ShowS
showev Event -> Bool
isRootUnmounted String
"RootUnmounted"
String -> ShowS
forall a. [a] -> [a] -> [a]
++ (Event -> Bool) -> ShowS
showev Event -> Bool
isAttrsModified String
"AttrsModified"
String -> ShowS
forall a. [a] -> [a] -> [a]
++ (Event -> Bool) -> ShowS
showev Event -> Bool
isAccessed String
"Accessed"
String -> ShowS
forall a. [a] -> [a] -> [a]
++ (Event -> Bool) -> ShowS
showev Event -> Bool
isOpened String
"Opened"
String -> ShowS
forall a. [a] -> [a] -> [a]
++ (Event -> Bool) -> ShowS
showev Event -> Bool
isWriteClosed String
"WriteClosed"
String -> ShowS
forall a. [a] -> [a] -> [a]
++ (Event -> Bool) -> ShowS
showev Event -> Bool
isNonWriteClosed String
"NonWriteClosed"
String -> ShowS
forall a. [a] -> [a] -> [a]
++ (Event -> Bool) -> ShowS
showev Event -> Bool
isCreated String
"Created"
String -> ShowS
forall a. [a] -> [a] -> [a]
++ (Event -> Bool) -> ShowS
showev Event -> Bool
isDeleted String
"Deleted"
String -> ShowS
forall a. [a] -> [a] -> [a]
++ (Event -> Bool) -> ShowS
showev Event -> Bool
isModified String
"Modified"
String -> ShowS
forall a. [a] -> [a] -> [a]
++ (Event -> Bool) -> ShowS
showev Event -> Bool
isMovedFrom String
"MovedFrom"
String -> ShowS
forall a. [a] -> [a] -> [a]
++ (Event -> Bool) -> ShowS
showev Event -> Bool
isMovedTo String
"MovedTo"
String -> ShowS
forall a. [a] -> [a] -> [a]
++ (Event -> Bool) -> ShowS
showev Event -> Bool
isDir String
"Dir"
String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
"\n"
where showev :: (Event -> Bool) -> ShowS
showev Event -> Bool
f String
str = if Event -> Bool
f Event
ev then String
"\n" String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
str else String
""
#else
#warning "Disabling module Streamly.Internal.FileSystem.Event.Linux. Does not support kernels older than 2.6.36."
module Streamly.Internal.FileSystem.Event.Linux () where
#endif