-- |
-- Module      : Streamly.Internal.FileSystem.Event.Linux
-- Copyright   : (c) 2020 Composewell Technologies
-- License     : BSD-3-Clause
-- Maintainer  : streamly@composewell.com
-- Stability   : experimental
-- Portability : GHC
--
-- =Overview
--
-- Use 'watchPaths' with a list of file system paths you want to watch as
-- argument. It returns a stream of 'Event' representing the file system events
-- occurring under the watched paths.
--
-- @
-- Stream.mapM_ (putStrLn . 'showEvent') $ 'watchPaths' [Array.fromList "dir"]
-- @
--
-- 'Event' is an opaque type. Accessor functions (e.g. 'showEvent' above)
-- provided in this module are used to determine the attributes of the event.
--
-- Identical successive events may be coalesced into a single event.
--
-- =Design notes
--
-- For reference documentation see:
--
-- * <https://man7.org/linux/man-pages/man7/inotify.7.html inotify man page>
--
-- We try to keep the macOS\/Linux/Windows event handling APIs and defaults
-- semantically and syntactically as close as possible.
--
-- =BUGs
--
-- When testing on Linux Kernel version @5.3.0-53-generic #47-Ubuntu@, the last
-- event for the root path seems to be delayed until one more event occurs.
--
-- = Differences between macOS and Linux APIs:
--
-- 1. macOS watch is based on the path provided to it, if the path is
-- deleted and recreated it will still be watched, if the path moves to another
-- path it won't be watched anymore. Whereas Linux watch is based on a handle
-- to the path, if the path is deleted and recreated it won't be watched, if
-- the path moves to another it can still be watched (though this is
-- configurable).
--
-- 2. macOS watches the directory hierarchy recursively, Linux watches only one
-- level of dir, recursive watch has to be built in user space by watching for
-- create events and adding the new directories to the watch. Not sure how this
-- will scale for too many paths.
--
-- 3. In macOS the path of the subject of the event is absolute, in Linux the
-- path is the name of the object inside the dir being watched.
--
-- 4. On Linux 'watchPaths' fails if a path does not exist, on macOS it does
-- not fail.

#include "config.h"

#if HAVE_DECL_IN_EXCL_UNLINK
module Streamly.Internal.FileSystem.Event.Linux
    (
    -- * Subscribing to events

    -- ** Default configuration
      Config (..)
    , defaultConfig

    -- ** Watch Behavior
    , setRecursiveMode
    , setFollowSymLinks
    , setUnwatchMoved
    , setOneShot
    , setOnlyDir
    , WhenExists (..)
    , setWhenExists

    -- ** Events of Interest
    -- *** Root Path Events
    , setRootDeleted
    , setRootMoved
    , setRootPathEvents

    -- *** Item Level Metadata change
    , setAttrsModified

    -- *** Item Level Access
    , setAccessed
    , setOpened
    , setWriteClosed
    , setNonWriteClosed

    -- *** Item CRUD events
    , setCreated
    , setDeleted
    , setMovedFrom
    , setMovedTo
    , setModified

    , setAllEvents

    -- ** Watch APIs
    , watch
    , watchRecursive
    , watchWith

    -- Low level watch APIs
    , addToWatch
    , removeFromWatch

    -- * Handling Events
    , Event(..)
    , getRoot
    , getRelPath
    , getAbsPath
    , getCookie

    -- ** Root Level Events
    , isRootPathEvent
    , isRootUnwatched
    , isRootDeleted
    , isRootMoved
    , isRootUnmounted

    -- ** Item Level Metadata change
    , isAttrsModified

    -- ** Item Level Access
    , isAccessed
    , isOpened
    , isWriteClosed
    , isNonWriteClosed

    -- ** Item Level CRUD events
    , isCreated
    , isDeleted
    , isMovedFrom
    , isMovedTo
    , isMoved
    , isModified

    -- ** Item Path info
    , isDir

    -- ** Exception Conditions
    , isEventsLost

    -- * Debugging
    , 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.Internal.Data.Stream.StreamD (Stream)
import Streamly.Internal.Data.Parser (Parser)
import Streamly.Internal.Data.Array.Type (Array(..), byteLength)
import System.Directory (doesDirectoryExist)
import System.IO (Handle, hClose, IOMode(ReadMode))
import GHC.IO.Handle.FD (handleToFd)

import qualified Data.IntMap.Lazy as Map
import qualified Data.List.NonEmpty as NonEmpty
import qualified Streamly.Internal.Data.Array as A
import qualified Streamly.Data.Fold as FL
import qualified Streamly.Internal.Data.Parser as PR
    (takeEQ, fromEffect, fromFold)
import qualified Streamly.Internal.Data.Stream.StreamD as S
import qualified Streamly.Internal.FileSystem.Dir as Dir
import qualified Streamly.Internal.FileSystem.Handle as FH
import qualified Streamly.Internal.Unicode.Stream as U

-------------------------------------------------------------------------------
-- Subscription to events
-------------------------------------------------------------------------------

-- | Watch configuration, used to specify the events of interest and the
-- behavior of the watch.
--
-- /Pre-release/
--
data Config = Config
    { Config -> Bool
watchRec :: Bool
    , Config -> Word32
createFlags :: Word32
    }

-------------------------------------------------------------------------------
-- Boolean settings
-------------------------------------------------------------------------------

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 forall a. Bits a => a -> a -> a
.|. Word32
mask
            else Word32
createFlags forall a. Bits a => a -> a -> a
.&. forall a. Bits a => a -> a
complement Word32
mask
    in Config
cfg {createFlags :: Word32
createFlags = Word32
flags}

-------------------------------------------------------------------------------
-- Settings
-------------------------------------------------------------------------------

-- | Watch the whole directory tree recursively instead of watching just one
-- level of directory.
--
-- /default: False/
--
-- /Pre-release/
--
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

-- | If the pathname to be watched is a symbolic link then watch the target of
-- the symbolic link instead of the symbolic link itself.
--
-- Note that the path location in the events is through the original symbolic
-- link path rather than the resolved path.
--
-- /default: True/
--
-- /Pre-release/
--
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

-- | If an object moves out of the directory being watched then stop watching
-- it.
--
-- /default: True/
--
-- /Pre-release/
--
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

-- | What to do if a watch already exists when 'openWatch' or 'addToWatch' is
-- called for a path.
--
-- /Pre-release/
--
data WhenExists =
      AddIfExists -- ^ Do not set an existing setting to 'False' only set to 'True'
    | ReplaceIfExists -- ^ Replace the existing settings with new settings
#if HAVE_DECL_IN_MASK_CREATE
    | FailIfExists -- ^ Fail the API
#endif

-- | When adding a new path to the watch, specify what to do if a watch already
-- exists on that path.
--
-- /default: FailIfExists/
--
-- /Pre-release/
--
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

-- | Watch the object only for one event and then remove it from the watch.
--
-- /default: False/
--
-- /Pre-release/
--
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

-- | Watch the object only if it is a directory. This provides a race-free way
-- to ensure that the watched object is a directory.
--
-- /default: False/
--
-- /Pre-release/
--
setOnlyDir :: Bool -> Config -> Config
setOnlyDir :: Bool -> Config -> Config
setOnlyDir = Word32 -> Bool -> Config -> Config
setFlag Word32
iN_ONLYDIR

-------------------------------------------------------------------------------
-- Event types that can occur
-------------------------------------------------------------------------------

foreign import capi
    "sys/inotify.h value IN_DELETE_SELF" iN_DELETE_SELF :: Word32

-- | Report when the watched path itself gets deleted.
--
-- /default: True/
--
-- /Pre-release/
--
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

-- | Report when the watched root path itself gets renamed.
--
-- /default: True/
--
-- /Pre-release/
--
setRootMoved :: Bool -> Config -> Config
setRootMoved :: Bool -> Config -> Config
setRootMoved = Word32 -> Bool -> Config -> Config
setFlag Word32
iN_MOVE_SELF

-- | Report when the watched root path itself gets deleted or renamed.
--
-- /default: True/
--
-- /Pre-release/
--
setRootPathEvents :: Bool -> Config -> Config
setRootPathEvents :: Bool -> Config -> Config
setRootPathEvents = Word32 -> Bool -> Config -> Config
setFlag (Word32
iN_DELETE_SELF forall a. Bits a => a -> a -> a
.|. Word32
iN_MOVE_SELF)

foreign import capi
    "sys/inotify.h value IN_ATTRIB" iN_ATTRIB :: Word32

-- | Report when the metadata e.g. owner, permission modes, modifications times
-- of an object changes.
--
-- /default: True/
--
-- /Pre-release/
--
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

-- | Report when a file is accessed.
--
-- /default: True/
--
-- /Pre-release/
--
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

-- | Report when a file is opened.
--
-- /default: True/
--
-- /Pre-release/
--
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

-- | Report when a file that was opened for writes is closed.
--
-- /default: True/
--
-- /Pre-release/
--
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

-- | Report when a file that was opened for not writing is closed.
--
-- /default: True/
--
-- /Pre-release/
--
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

-- | Report when a file is created.
--
-- /default: True/
--
-- /Pre-release/
--
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

-- | Report when a file is deleted.
--
-- /default: True/
--
-- /Pre-release/
--
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

-- | Report the source of a move.
--
-- /default: True/
--
-- /Pre-release/
--
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

-- | Report the target of a move.
--
-- /default: True/
--
-- /Pre-release/
--
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

-- | Report when a file is modified.
--
-- /default: True/
--
-- /Pre-release/
--
setModified :: Bool -> Config -> Config
setModified :: Bool -> Config -> Config
setModified = Word32 -> Bool -> Config -> Config
setFlag Word32
iN_MODIFY

-- | Set all tunable events 'True' or 'False'. Equivalent to setting:
--
-- * setRootDeleted
-- * setRootMoved
-- * setAttrsModified
-- * setAccessed
-- * setOpened
-- * setWriteClosed
-- * setNonWriteClosed
-- * setCreated
-- * setDeleted
-- * setMovedFrom
-- * setMovedTo
-- * setModified
--
-- /Pre-release/
--
setAllEvents :: Bool -> Config -> Config
setAllEvents :: Bool -> Config -> Config
setAllEvents Bool
s =
      Bool -> Config -> Config
setRootDeleted Bool
s
    forall b c a. (b -> c) -> (a -> b) -> a -> c
. Bool -> Config -> Config
setRootMoved Bool
s
    forall b c a. (b -> c) -> (a -> b) -> a -> c
. Bool -> Config -> Config
setAttrsModified Bool
s
    forall b c a. (b -> c) -> (a -> b) -> a -> c
. Bool -> Config -> Config
setAccessed Bool
s
    forall b c a. (b -> c) -> (a -> b) -> a -> c
. Bool -> Config -> Config
setOpened Bool
s
    forall b c a. (b -> c) -> (a -> b) -> a -> c
. Bool -> Config -> Config
setWriteClosed Bool
s
    forall b c a. (b -> c) -> (a -> b) -> a -> c
. Bool -> Config -> Config
setNonWriteClosed Bool
s
    forall b c a. (b -> c) -> (a -> b) -> a -> c
. Bool -> Config -> Config
setCreated Bool
s
    forall b c a. (b -> c) -> (a -> b) -> a -> c
. Bool -> Config -> Config
setDeleted Bool
s
    forall b c a. (b -> c) -> (a -> b) -> a -> c
. Bool -> Config -> Config
setMovedFrom Bool
s
    forall b c a. (b -> c) -> (a -> b) -> a -> c
. Bool -> Config -> Config
setMovedTo Bool
s
    forall b c a. (b -> c) -> (a -> b) -> a -> c
. Bool -> Config -> Config
setModified Bool
s

-------------------------------------------------------------------------------
-- Default config
-------------------------------------------------------------------------------

-- The defaults are set in such a way that the behavior on macOS and Linux is
-- as much compatible as possible.
--
-- | The default configuration settings are:
--
-- * 'setFollowSymLinks' 'True'
-- * 'setUnwatchMoved' 'True'
-- * 'setOneShot' 'False'
-- * 'setOnlyDir' 'False'
-- * 'setWhenExists' 'AddIfExists'
--
-- The tunable events enabled by default are:
--
-- * setCreated True
-- * setDeleted True
-- * setMovedFrom True
-- * setMovedTo True
-- * setModified True
--
-- /Pre-release/
--
defaultConfig :: Config
defaultConfig :: Config
defaultConfig =
      WhenExists -> Config -> Config
setWhenExists WhenExists
AddIfExists
    forall a b. (a -> b) -> a -> b
$ Bool -> Config -> Config
setCreated Bool
True
    forall a b. (a -> b) -> a -> b
$ Bool -> Config -> Config
setDeleted Bool
True
    forall a b. (a -> b) -> a -> b
$ Bool -> Config -> Config
setMovedFrom Bool
True
    forall a b. (a -> b) -> a -> b
$ Bool -> Config -> Config
setMovedTo Bool
True
    forall a b. (a -> b) -> a -> b
$ Bool -> Config -> Config
setModified Bool
True
    forall a b. (a -> b) -> a -> b
$ Config
        { watchRec :: Bool
watchRec = Bool
False
        , createFlags :: Word32
createFlags = Word32
0
        }

-------------------------------------------------------------------------------
-- Open an event stream
-------------------------------------------------------------------------------

-- | A handle for a watch.
data Watch =
    Watch
        Handle                  -- File handle for the watch
        (IORef
            (IntMap             -- Key is the watch descriptor
                ( Array Word8   -- Absolute path of the watch root
                , Array Word8   -- Path of subdir relative to watch root
                )
            )
        )

-- Instead of using the watch descriptor we can provide APIs that use the path
-- itself to identify the watch. That will require us to maintain a map from wd
-- to path in the Watch handle.

newtype WD = WD CInt deriving Key -> WD -> ShowS
[WD] -> ShowS
WD -> String
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

-- | Create a 'Watch' handle. 'addToWatch' can be used to add paths being
-- monitored by this watch.
--
-- /Pre-release/
--
createWatch :: IO Watch
createWatch :: IO Watch
createWatch = do
    CInt
rawfd <- forall a. (Eq a, Num a) => String -> IO a -> IO a
throwErrnoIfMinus1 String
"createWatch" IO CInt
c_inotify_init
    -- we could use fdToHandle but it cannot determine the fd type
    -- automatically for the inotify fd
    (FD
fd, IODeviceType
fdType) <-
        CInt
-> IOMode
-> Maybe (IODeviceType, CDev, CIno)
-> Bool
-> Bool
-> IO (FD, IODeviceType)
mkFD
            CInt
rawfd
            IOMode
ReadMode
            (forall a. a -> Maybe a
Just (IODeviceType
Stream, CDev
0, CIno
0))  -- (IODeviceType, CDev, CIno)
            Bool
False                  -- not a socket
            Bool
False                  -- non-blocking is false
    let fdString :: String
fdString = String
"<createWatch file descriptor: " forall a. [a] -> [a] -> [a]
++ forall a. Show a => a -> String
show FD
fd 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    -- use non-blocking IO
           forall a. Maybe a
Nothing -- TextEncoding (binary)
    IORef (IntMap (Array Word8, Array Word8))
emptyMapRef <- forall a. a -> IO (IORef a)
newIORef forall a. IntMap a
Map.empty
    forall (m :: * -> *) a. Monad m => a -> m a
return 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

-- XXX we really do not know the path encoding, all we know is that it is "/"
-- separated bytes. So these may fail or convert the path in an unexpected
-- manner. We should ultimately remove all usage of these.

toUtf8 :: MonadIO m => String -> m (Array Word8)
toUtf8 :: forall (m :: * -> *). MonadIO m => String -> m (Array Word8)
toUtf8 = forall (m :: * -> *) a.
(MonadIO m, Unbox a) =>
Stream m a -> m (Array a)
A.fromStream forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (m :: * -> *). Monad m => Stream m Char -> Stream m Word8
U.encodeUtf8 forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (m :: * -> *) a. Applicative m => [a] -> Stream m a
S.fromList

utf8ToString :: Array Word8 -> String
utf8ToString :: Array Word8 -> String
utf8ToString = forall a. Identity a -> a
runIdentity forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (m :: * -> *) a b.
Monad m =>
Fold m a b -> Stream m a -> m b
S.fold forall (m :: * -> *) a. Monad m => Fold m a [a]
FL.toList forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (m :: * -> *). Monad m => Stream m Word8 -> Stream m Char
U.decodeUtf8' forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (m :: * -> *) a. (Monad m, Unbox a) => Array a -> Stream m a
A.read

-- | Add a trailing "/" at the end of the path if there is none. Do not add a
-- "/" if the path is empty.
--
ensureTrailingSlash :: Array Word8 -> Array Word8
ensureTrailingSlash :: Array Word8 -> Array Word8
ensureTrailingSlash Array Word8
path =
    if forall a. Array a -> Key
byteLength Array Word8
path forall a. Eq a => a -> a -> Bool
/= Key
0
    then
        let mx :: Maybe Word8
mx = forall a. Unbox a => Key -> Array a -> Maybe a
A.getIndex (forall a. Array a -> Key
byteLength Array Word8
path forall a. Num a => a -> a -> a
- Key
1) Array Word8
path
         in case Maybe Word8
mx of
            Maybe Word8
Nothing -> forall a. HasCallStack => String -> a
error String
"ensureTrailingSlash: Bug: Invalid index"
            Just Word8
x ->
                if Word8
x forall a. Eq a => a -> a -> Bool
/= Word8
forwardSlashByte
                then Array Word8
path forall a. Semigroup a => a -> a -> a
<> Array Word8
forwardSlash
                else Array Word8
path
    else Array Word8
path
    where forwardSlash :: Array Word8
forwardSlash = forall a. Unbox a => [a] -> Array a
A.fromList [ Word8
forwardSlashByte ]
          forwardSlashByte :: Word8
forwardSlashByte = 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 forall a. Array a -> Key
byteLength Array Word8
path forall a. Eq a => a -> a -> Bool
/= Key
0
    then
        let n :: Key
n = forall a. Array a -> Key
byteLength Array Word8
path forall a. Num a => a -> a -> a
- Key
1
            mx :: Maybe Word8
mx = 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 -> forall a. HasCallStack => String -> a
error String
"removeTrailingSlash: Bug: Invalid index"
            Just Word8
x ->
                if Word8
x forall a. Eq a => a -> a -> Bool
== forall a b. (Integral a, Num b) => a -> b
fromIntegral (Char -> Key
ord Char
'/')
                then 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
  | forall a. Array a -> Key
byteLength Array Word8
a forall a. Eq a => a -> a -> Bool
== Key
0 = Array Word8
b
  | forall a. Array a -> Key
byteLength Array Word8
b forall a. Eq a => a -> a -> Bool
== Key
0 = Array Word8
a
  | Bool
otherwise = Array Word8 -> Array Word8
ensureTrailingSlash Array Word8
a forall a. Semigroup a => a -> a -> a
<> Array Word8
b

-- | @addToWatch cfg watch root subpath@ adds @subpath@ to the list of paths
-- being monitored under @root@ via the watch handle @watch@.  @root@ must be
-- an absolute path and @subpath@ must be relative to @root@.
--
-- /Pre-release/
--
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
    -- XXX do not add if the path is already added
    -- XXX if the watch is added by the scan and not via an event we can
    -- generate a create event assuming that the create may have been lost. We
    -- can also mark in the map that this entry was added by the scan. So if an
    -- actual create event later comes and tries to add this again then we can
    -- ignore that and drop the create event to avoid duplicate create, because
    -- we have already emitted it.
    --
    -- When a directory is added by the scan we should also emit create events
    -- for files that may have got added to the dir. However, such create
    -- events may get duplicated because of a race between the scan generated
    -- versus real events.
    --
    -- Or we may distinguish between scan generated events and real events so
    -- that the application can assume that other events may been lost and
    -- handle it. For example, if it is a dir create the application can read
    -- the dir to scan the files in it.
    --
    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 forall a b. (a -> b) -> a -> b
$ String
"root = " forall a. [a] -> [a] -> [a]
++ Array Word8 -> String
utf8ToString Array Word8
root forall a. [a] -> [a] -> [a]
++ String
" path = " forall a. [a] -> [a] -> [a]
++ Array Word8 -> String
utf8ToString Array Word8
path forall a. [a] -> [a] -> [a]
++ String
" absPath = " forall a. [a] -> [a] -> [a]
++ Array Word8 -> String
utf8ToString Array Word8
absPath

    FD
fd <- Handle -> IO FD
handleToFd Handle
handle

    -- XXX we need to tolerate an error where we are adding a watch for a
    -- non-existing file because the file may have got deleted by the time we
    -- added the watch. Perhaps we can have a flag in config for this and keep
    -- the default value to tolerate the error.
    --
    -- XXX The file may have even got deleted and then recreated which we will
    -- never get to know, document this.
    CInt
wd <- forall a b. Array a -> (CString -> IO b) -> IO b
A.asCStringUnsafe Array Word8
absPath forall a b. (a -> b) -> a -> b
$ \CString
pathPtr ->
            forall a. (Eq a, Num a) => String -> IO a -> IO a
throwErrnoIfMinus1 (String
"addToWatch: " forall a. [a] -> [a] -> [a]
++ Array Word8 -> String
utf8ToString Array Word8
absPath) 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)

    -- We add the parent first so that we start getting events for any new
    -- creates and add the new subdirectories on creates while we are adding
    -- the children.
    forall a. IORef a -> (a -> a) -> IO ()
modifyIORef IORef (IntMap (Array Word8, Array Word8))
wdMap (forall a. Key -> a -> IntMap a -> IntMap a
Map.insert (forall a b. (Integral a, Num b) => a -> b
fromIntegral CInt
wd) (Array Word8
root, Array Word8
path))

    -- Now add the children. If we missed any creates while we were adding the
    -- parent, this will make sure they are added too.
    --
    -- XXX Ensure that we generate events that we may have missed while we were
    -- adding the dirs. That may generate spurious events though.
    --
    -- XXX readDirs currently uses paths as String, we need to convert it
    -- to "/" separated by byte arrays.
    Bool
pathIsDir <- String -> IO Bool
doesDirectoryExist forall a b. (a -> b) -> a -> b
$ Array Word8 -> String
utf8ToString Array Word8
absPath
    forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Bool
watchRec Bool -> Bool -> Bool
&& Bool
pathIsDir) 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 forall b c a. (b -> c) -> (a -> b) -> a -> c
. Array Word8 -> Array Word8 -> Array Word8
appendPaths Array Word8
path
            in forall (m :: * -> *) a b.
Monad m =>
Fold m a b -> Stream m a -> m b
S.fold (forall (m :: * -> *) a b. Monad m => (a -> m b) -> Fold m a ()
FL.drainMapM Array Word8 -> IO ()
f)
                forall a b. (a -> b) -> a -> b
$ forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> Stream m a -> Stream m b
S.mapM forall (m :: * -> *). MonadIO m => String -> m (Array Word8)
toUtf8
                forall a b. (a -> b) -> a -> b
$ forall (m :: * -> *). MonadIO m => String -> Stream m String
Dir.readDirs 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

-- | Remove an absolute root path from a 'Watch', if a path was moved after
-- adding you need to provide the original path which was used to add the
-- Watch.
--
-- /Pre-release/
--
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 <- forall a. IORef a -> IO a
readIORef IORef (IntMap (Array Word8, Array Word8))
wdMap
    IntMap (Array Word8, Array Word8)
wdMap1 <- forall (t :: * -> *) (m :: * -> *) b a.
(Foldable t, Monad m) =>
(b -> a -> m b) -> b -> t a -> m b
foldlM (forall {b}.
FD
-> IntMap (Array Word8, b)
-> (Key, (Array Word8, b))
-> IO (IntMap (Array Word8, b))
step FD
fd) forall a. IntMap a
Map.empty (forall a. IntMap a -> [(Key, a)]
Map.toList IntMap (Array Word8, Array Word8)
km)
    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 forall a b. (a, b) -> a
fst (Array Word8, b)
v forall a. Eq a => a -> a -> Bool
== Array Word8
path
        then do
            let err :: String
err = String
"removeFromWatch: " forall a. [a] -> [a] -> [a]
++ 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) (forall a b. (Integral a, Num b) => a -> b
fromIntegral Key
wd)
            forall (f :: * -> *) a. Functor f => f a -> f ()
void forall a b. (a -> b) -> a -> b
$ forall a. (Eq a, Num a) => String -> IO a -> IO a
throwErrnoIfMinus1 String
err IO CInt
rm
            forall (m :: * -> *) a. Monad m => a -> m a
return IntMap (Array Word8, b)
newMap
        else forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall a. Key -> a -> IntMap a -> IntMap a
Map.insert Key
wd (Array Word8, b)
v IntMap (Array Word8, b)
newMap

-- | Given a 'Config' and list of @paths@ ("/" separated byte arrays) start
-- monitoring the paths for file system events. Returns a 'Watch' handle which
-- can then be used to read the event stream or to close the watch.
--
-- /Pre-release/
--
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
    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 (forall a. Unbox a => [a] -> Array a
A.fromList []))
        forall a b. (a -> b) -> a -> b
$ forall a. NonEmpty a -> [a]
NonEmpty.toList NonEmpty (Array Word8)
paths
    forall (m :: * -> *) a. Monad m => a -> m a
return Watch
w

-- | Close a 'Watch' handle.
--
-- /Pre-release/
--
closeWatch :: Watch -> IO ()
closeWatch :: Watch -> IO ()
closeWatch (Watch Handle
h IORef (IntMap (Array Word8, Array Word8))
_) = Handle -> IO ()
hClose Handle
h

-------------------------------------------------------------------------------
-- Raw events read from the watch file handle
-------------------------------------------------------------------------------

newtype Cookie = Cookie Word32 deriving (Key -> Cookie -> ShowS
[Cookie] -> ShowS
Cookie -> String
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
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)

-- | An Event generated by the file system. Use the accessor functions to
-- examine the event.
--
-- /Pre-release/
--
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
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
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
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)

-- The inotify event struct from the man page/header file:
--
--            struct inotify_event {
--                int      wd;       /* Watch descriptor */
--                uint32_t mask;     /* Mask describing event */
--                uint32_t cookie;   /* Unique cookie associating related
--                                      events (for rename(2)) */
--                uint32_t len;      /* Size of name field */
--                char     name[];   /* Optional null-terminated name */
--            };
--
-- XXX We can perhaps use parseD monad instance for fusing with parseMany? Need
-- to measure the perf.
--
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 = forall a. Storable a => a -> Key
sizeOf (forall a. HasCallStack => a
undefined :: CInt) forall a. Num a => a -> a -> a
+ Key
12
    Array Word8
arr <- forall (m :: * -> *) a b.
Monad m =>
Key -> Fold m a b -> Parser a m b
PR.takeEQ Key
headerLen (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) <- forall (m :: * -> *) b a. Monad m => m b -> Parser a m b
PR.fromEffect forall a b. (a -> b) -> a -> b
$ forall (m :: * -> *) a b.
MonadIO m =>
Array a -> (Ptr a -> m b) -> m b
A.asPtrUnsafe Array Word8
arr forall {b} {c} {d}.
(Storable b, Storable c, Num d) =>
Ptr Word8 -> IO (Word8, b, c, d)
readHeader
    -- XXX need the "initial" in parsers to return a step type so that "take 0"
    -- can return without an input. otherwise if pathLen is 0 we will keep
    -- waiting to read one more char before we return this event.
    Array Word8
path <-
        if Key
pathLen forall a. Eq a => a -> a -> Bool
/= Key
0
        then do
            -- XXX takeEndBy_ drops the separator so assumes a null
            -- terminated path, we should use a takeWhile nested inside a
            -- takeP
            Array Word8
pth <-
                forall (m :: * -> *) a b. Monad m => Fold m a b -> Parser a m b
PR.fromFold
                    forall a b. (a -> b) -> a -> b
$ forall (m :: * -> *) a b.
Monad m =>
(a -> Bool) -> Fold m a b -> Fold m a b
FL.takeEndBy_ (forall a. Eq a => a -> a -> Bool
== Word8
0)
                    forall a b. (a -> b) -> a -> b
$ forall (m :: * -> *) a b.
Monad m =>
Key -> Fold m a b -> Fold m a b
FL.take Key
pathLen (forall (m :: * -> *) a.
(MonadIO m, Unbox a) =>
Key -> Fold m a (Array a)
A.writeN Key
pathLen)
            let remaining :: Key
remaining = Key
pathLen forall a. Num a => a -> a -> a
- forall a. Array a -> Key
byteLength Array Word8
pth forall a. Num a => a -> a -> a
- Key
1
            forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Key
remaining forall a. Eq a => a -> a -> Bool
/= Key
0) forall a b. (a -> b) -> a -> b
$ forall (m :: * -> *) a b.
Monad m =>
Key -> Fold m a b -> Parser a m b
PR.takeEQ Key
remaining forall (m :: * -> *) a. Monad m => Fold m a ()
FL.drain
            forall (m :: * -> *) a. Monad m => a -> m a
return Array Word8
pth
        else forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ forall a. Unbox a => [a] -> Array a
A.fromList []
    IntMap (Array Word8, Array Word8)
wdm <- forall (m :: * -> *) b a. Monad m => m b -> Parser a m b
PR.fromEffect forall a b. (a -> b) -> a -> b
$ forall a. IORef a -> IO a
readIORef IORef (IntMap (Array Word8, Array Word8))
wdMap
    let (Array Word8
root, Array Word8
sub) =
            case forall a. Key -> IntMap a -> Maybe a
Map.lookup (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 ->
                        forall a. HasCallStack => String -> a
error forall a b. (a -> b) -> a -> b
$ String
"readOneEvent: "
                                  forall a. Semigroup a => a -> a -> a
<> String
"Unknown watch descriptor: "
                                  forall a. Semigroup a => a -> a -> a
<> 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
        -- Check for "ISDIR" first because it is less likely
        isDirCreate :: Bool
isDirCreate = Word32
eflags forall a. Bits a => a -> a -> a
.&. Word32
iN_ISDIR forall a. Eq a => a -> a -> Bool
/= Word32
0 Bool -> Bool -> Bool
&& Word32
eflags forall a. Bits a => a -> a -> a
.&. Word32
iN_CREATE forall a. Eq a => a -> a -> Bool
/= Word32
0
    forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Config -> Bool
watchRec Config
cfg Bool -> Bool -> Bool
&& Bool
isDirCreate)
        forall a b. (a -> b) -> a -> b
$ forall (m :: * -> *) b a. Monad m => m b -> Parser a m b
PR.fromEffect 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
    -- XXX Handle IN_DELETE, IN_DELETE_SELF, IN_MOVE_SELF, IN_MOVED_FROM,
    -- IN_MOVED_TO
    -- What if a large dir tree gets moved in to our hierarchy? Do we get a
    -- single event for the top level dir in this case?
    forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ Event
        { eventWd :: CInt
eventWd = 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 = forall a. Storable a => a -> Key
sizeOf (forall a. HasCallStack => a
undefined :: CInt)
        Word8
ewd <- forall a. Storable a => Ptr a -> IO a
peek Ptr Word8
ptr
        b
eflags <- forall a b. Storable a => Ptr b -> Key -> IO a
peekByteOff Ptr Word8
ptr Key
len
        c
cookie <- forall a b. Storable a => Ptr b -> Key -> IO a
peekByteOff Ptr Word8
ptr (Key
len forall a. Num a => a -> a -> a
+ Key
4)
        Word32
pathLen :: Word32 <- forall a b. Storable a => Ptr b -> Key -> IO a
peekByteOff Ptr Word8
ptr (Key
len forall a. Num a => a -> a -> a
+ Key
8)
        forall (m :: * -> *) a. Monad m => a -> m a
return (Word8
ewd, b
eflags, c
cookie, 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
    -- Do not use too small a buffer. As per inotify man page:
    --
    -- The behavior when the buffer given to read(2) is too small to return
    -- information about the next event depends on the kernel version: in
    -- kernels before 2.6.21, read(2) returns 0; since kernel 2.6.21, read(2)
    -- fails with the error EINVAL.  Specifying a buffer of size
    --
    --          sizeof(struct inotify_event) + NAME_MAX + 1
    --
    -- will be sufficient to read at least one event.
    forall (m :: * -> *) a b.
Monad m =>
Stream m (Either a b) -> Stream m b
S.catRights forall a b. (a -> b) -> a -> b
$ 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) forall a b. (a -> b) -> a -> b
$ forall (m :: * -> *) a b.
Applicative m =>
Unfold m a b -> a -> Stream m b
S.unfold forall (m :: * -> *). MonadIO m => Unfold m Handle Word8
FH.reader Handle
handle

-- XXX We should not go across the mount points of network file systems or file
-- systems that are known to not generate any events.
--
-- | Start monitoring a list of file system paths for file system events with
-- the supplied configuration operation over the 'defaultConfig'. The
-- paths could be files or directories.  When recursive mode is set and the
-- path is a directory, the whole directory tree under it is watched
-- recursively. Monitoring starts from the current time onwards.  The paths are
-- specified as UTF-8 encoded 'Array' of 'Word8'.
--
-- /Non-existing Paths:/ the API fails if a watch is started on a non-exsting
-- path.
--
-- /Performance:/ Note that recursive watch on a large directory tree could be
-- expensive. When starting a watch, the whole tree must be read and watches
-- are started on each directory in the tree. The initial time to start the
-- watch as well as the memory required is proportional to the number of
-- directories in the tree.
--
-- /Bugs:/ When new directories are created under the tree they are added to
-- the watch on receiving the directory create event. However, the creation of
-- a dir and adding a watch for it is not atomic.  The implementation takes
-- care of this and makes sure that watches are added for all directories.
-- However, In the mean time, the directory may have received more events which
-- may get lost.  Handling of any such lost events is yet to be implemented.
--
-- See the Linux __inotify__ man page for more details.
--
-- @
-- watchwith
--      ('setFollowSymLinks' True . 'setUnwatchMoved' False)
--      [Array.fromList "dir"]
-- @
--
-- /Pre-release/
--
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 = 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

-- | Same as 'watchWith' using 'defaultConfig' and recursive mode.
--
-- >>> watchRecursive = watchWith (setRecursiveMode True)
--
-- See 'watchWith' for pitfalls and bugs when using recursive watch on Linux.
--
-- /Pre-release/
--
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)

-- | Same as 'watchWith' using defaultConfig and non-recursive mode.
--
-- >>> watch = watchWith id
--
-- /Pre-release/
--
watch :: NonEmpty (Array Word8) -> Stream IO Event
watch :: NonEmpty (Array Word8) -> Stream IO Event
watch = (Config -> Config) -> NonEmpty (Array Word8) -> Stream IO Event
watchWith forall a. a -> a
id

-------------------------------------------------------------------------------
-- Examine event stream
-------------------------------------------------------------------------------

-- | Get the watch root corresponding to the 'Event'.
--
-- Note that if a path was moved after adding to the watch, this will give the
-- original path and not the new path after moving.
--
-- TBD: we can possibly update the watch root on a move self event.
--
-- /Pre-release/
--
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 forall a. Ord a => a -> a -> Bool
>= CInt
1
    then
        case forall a. Key -> IntMap a -> Maybe a
Map.lookup (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 -> forall a b. (a, b) -> a
fst (Array Word8, Array Word8)
path
            Maybe (Array Word8, Array Word8)
Nothing ->
                forall a. HasCallStack => String -> a
error forall a b. (a -> b) -> a -> b
$ String
"Bug: getRoot: No path found corresponding to the "
                    forall a. [a] -> [a] -> [a]
++ String
"watch descriptor " forall a. [a] -> [a] -> [a]
++ forall a. Show a => a -> String
show CInt
eventWd
    else forall a. Unbox a => [a] -> Array a
A.fromList []

-- XXX should we use a Maybe here?
-- | Get the file system object path for which the event is generated, relative
-- to the watched root. The path is a "/" separated array of bytes.
--
-- /Pre-release/
--
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

-- | Get the absolute file system object path for which the event is generated.
--
-- When the watch root is a symlink, the absolute path returned is via the
-- original symlink and not through the resolved path.
--
-- /Pre-release/
--
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 forall a. Array a -> Key
byteLength Array Word8
relpath forall a. Eq a => a -> a -> Bool
/= Key
0
        then Array Word8 -> Array Word8
ensureTrailingSlash Array Word8
root forall a. Semigroup a => a -> a -> a
<> Array Word8
relpath
        else Array Word8 -> Array Word8
removeTrailingSlash Array Word8
root

-- XXX should we use a Maybe?
-- | Cookie is set when a rename occurs. The cookie value can be used to
-- connect the 'isMovedFrom' and 'isMovedTo' events, if both the events belong
-- to the same move operation then they will have the same cookie value.
--
-- /Pre-release/
--
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

-------------------------------------------------------------------------------
-- Event types
-------------------------------------------------------------------------------

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 forall a. Bits a => a -> a -> a
.&. Word32
mask forall a. Eq a => a -> a -> Bool
/= Word32
0

-------------------------------------------------------------------------------
-- Error events
-------------------------------------------------------------------------------

foreign import capi
    "sys/inotify.h value IN_Q_OVERFLOW" iN_Q_OVERFLOW :: Word32

-- XXX rename to isQOverflowed or hasOverflowed?
--
-- macOS overflow API is more specific, it tells which paths have lost the
-- events due to overflow.
--
-- | Event queue overflowed (WD is invalid for this event) and we may have lost
-- some events..  The user application must scan everything under the watched
-- paths to know the current state.
--
-- /Pre-release/
--
isEventsLost :: Event -> Bool
isEventsLost :: Event -> Bool
isEventsLost = Word32 -> Event -> Bool
getFlag Word32
iN_Q_OVERFLOW

-------------------------------------------------------------------------------
-- Events affecting the watched path only
-------------------------------------------------------------------------------

foreign import capi
    "sys/inotify.h value IN_IGNORED" iN_IGNORED :: Word32

-- Compare with isRootChanged on macOS. isRootChanged includes all these cases.
--
-- | A path was removed from the watch explicitly using 'removeFromWatch' or
-- automatically (file was deleted, or filesystem was unmounted).
--
-- Note that in recursive watch mode all the subdirectories are watch roots,
-- therefore, they will all generate this event.
--
-- /Occurs only for a watched path/
--
-- /Pre-release/
--
isRootUnwatched :: Event -> Bool
isRootUnwatched :: Event -> Bool
isRootUnwatched = Word32 -> Event -> Bool
getFlag Word32
iN_IGNORED

-- | Watched file/directory was itself deleted.  (This event also occurs if an
-- object is moved to another filesystem, since mv(1) in effect copies the file
-- to the other filesystem and then deletes it from the original filesystem.)
-- In addition, an 'isRootUnwatched' event will subsequently be generated
-- for the watch descriptor.
--
-- Note that in recursive watch mode all the subdirectories are watch roots,
-- therefore, they will all generate this event.
--
-- /Occurs only for a watched path/
--
-- /Pre-release/
--
isRootDeleted :: Event -> Bool
isRootDeleted :: Event -> Bool
isRootDeleted = Word32 -> Event -> Bool
getFlag Word32
iN_DELETE_SELF

-- | Watched file/directory was itself moved within the file system.
--
-- Note that in recursive watch mode all the subdirectories are watch roots,
-- therefore, they will all generate this event.
--
-- /Occurs only for a watched path/
--
-- /Pre-release/
--
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

-- | Filesystem containing watched object was unmounted.  In addition, an
-- 'isRootUnwatched' event will subsequently be generated for the watch
-- descriptor.
--
-- /Occurs only for a watched path/
--
-- /Pre-release/
--
isRootUnmounted :: Event -> Bool
isRootUnmounted :: Event -> Bool
isRootUnmounted = Word32 -> Event -> Bool
getFlag Word32
iN_UNMOUNT

-- | Determine whether the event indicates a change of path of the monitored
-- object itself. Note that the object may become unreachable or deleted after
-- a change of path.
--
-- /Occurs only for a watched path/
--
-- /Pre-release/
--
isRootPathEvent :: Event -> Bool
isRootPathEvent :: Event -> Bool
isRootPathEvent = Word32 -> Event -> Bool
getFlag (Word32
iN_DELETE_SELF forall a. Bits a => a -> a -> a
.|. Word32
iN_MOVE_SELF forall a. Bits a => a -> a -> a
.|. Word32
iN_UNMOUNT)

-------------------------------------------------------------------------------
-- Metadata change Events
-------------------------------------------------------------------------------

-- macOS has multiple APIs for metadata change for different metadata.
--
-- | Determine whether the event indicates inode metadata change for an object
-- contained within the monitored path.
--
-- Metadata change may include, permissions (e.g., chmod(2)), timestamps
-- (e.g., utimensat(2)), extended attributes (setxattr(2)), link count (since
-- Linux 2.6.25; e.g., for the target of link(2) and for unlink(2)), and
-- user/group ID (e.g., chown(2)).
--
-- /Can occur for watched path or a file inside it/
--
-- /Pre-release/
--
isAttrsModified :: Event -> Bool
isAttrsModified :: Event -> Bool
isAttrsModified = Word32 -> Event -> Bool
getFlag Word32
iN_ATTRIB

-------------------------------------------------------------------------------
-- Access
-------------------------------------------------------------------------------

-- | File was accessed (e.g. read, execve).
--
-- /Occurs only for a file inside the watched directory/
--
-- /Pre-release/
--
isAccessed :: Event -> Bool
isAccessed :: Event -> Bool
isAccessed = Word32 -> Event -> Bool
getFlag Word32
iN_ACCESS

-- | File or directory was opened.
--
-- /Occurs only for a file inside the watched directory/
--
-- /Pre-release/
--
isOpened :: Event -> Bool
isOpened :: Event -> Bool
isOpened = Word32 -> Event -> Bool
getFlag Word32
iN_OPEN

-- | File opened for writing was closed.
--
-- /Occurs only for a file inside the watched directory/
--
-- /Pre-release/
--
isWriteClosed :: Event -> Bool
isWriteClosed :: Event -> Bool
isWriteClosed = Word32 -> Event -> Bool
getFlag Word32
iN_CLOSE_WRITE

-- XXX what if it was opened for append? Does NOWRITE mean all cases where the
-- mode was not write? A dir open comes in this category?
--
-- | File or directory opened for read but not write was closed.
--
-- /Can occur for watched path or a file inside it/
--
-- /Pre-release/
--
isNonWriteClosed :: Event -> Bool
isNonWriteClosed :: Event -> Bool
isNonWriteClosed = Word32 -> Event -> Bool
getFlag Word32
iN_CLOSE_NOWRITE

-------------------------------------------------------------------------------
-- CRUD Events
-------------------------------------------------------------------------------

-- On macOS this is not generated on hard linking but on Linux it is.
--
-- | File/directory created in watched directory (e.g., open(2) O_CREAT,
-- mkdir(2), link(2), symlink(2), bind(2) on a UNIX domain socket).
--
-- /Occurs only for an object inside the watched directory/
--
-- /Pre-release/
--
isCreated :: Event -> Bool
isCreated :: Event -> Bool
isCreated = Word32 -> Event -> Bool
getFlag Word32
iN_CREATE

-- | File/directory deleted from watched directory.
--
-- /Occurs only for an object inside the watched directory/
--
-- /Pre-release/
--
isDeleted :: Event -> Bool
isDeleted :: Event -> Bool
isDeleted = Word32 -> Event -> Bool
getFlag Word32
iN_DELETE

-- XXX what if an object is moved in from outside or moved out of the monitored
-- dir?
--
-- | Generated for the original path when an object is moved from under a
-- monitored directory.
--
-- /Occurs only for an object inside the watched directory/
--
-- /Pre-release/
--
isMovedFrom :: Event -> Bool
isMovedFrom :: Event -> Bool
isMovedFrom = Word32 -> Event -> Bool
getFlag Word32
iN_MOVED_FROM

-- | Generated for the new path when an object is moved under a monitored
-- directory.
--
-- /Occurs only for an object inside the watched directory/
--
-- /Pre-release/
--
isMovedTo :: Event -> Bool
isMovedTo :: Event -> Bool
isMovedTo = Word32 -> Event -> Bool
getFlag Word32
iN_MOVED_TO

-- | Generated for a path that is moved from or moved to the monitored
-- directory.
--
-- >>> isMoved ev = isMovedFrom ev || isMovedTo ev
--
-- /Occurs only for an object inside the watched directory/
--
-- /Pre-release/
--
isMoved :: Event -> Bool
isMoved :: Event -> Bool
isMoved Event
ev = Event -> Bool
isMovedFrom Event
ev Bool -> Bool -> Bool
|| Event -> Bool
isMovedTo Event
ev

-- | Determine whether the event indicates modification of an object within the
-- monitored path. This event is generated only for files and not directories.
--
-- /Occurs only for an object inside the watched directory/
--
-- /Pre-release/
--
isModified :: Event -> Bool
isModified :: Event -> Bool
isModified = Word32 -> Event -> Bool
getFlag Word32
iN_MODIFY

-------------------------------------------------------------------------------
-- Information about path type (applicable only when 'setFileEvents' is 'True')
-------------------------------------------------------------------------------

foreign import capi
    "sys/inotify.h value IN_ISDIR" iN_ISDIR :: Word32

-- | Determine whether the event is for a directory path.
--
-- /Pre-release/
--
isDir :: Event -> Bool
isDir :: Event -> Bool
isDir = Word32 -> Event -> Bool
getFlag Word32
iN_ISDIR

-------------------------------------------------------------------------------
-- Debugging
-------------------------------------------------------------------------------

-- | Convert an 'Event' record to a String representation.
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
"--------------------------"
    forall a. [a] -> [a] -> [a]
++ String
"\nWd = " forall a. [a] -> [a] -> [a]
++ forall a. Show a => a -> String
show CInt
eventWd
    forall a. [a] -> [a] -> [a]
++ String
"\nRoot = " forall a. [a] -> [a] -> [a]
++ forall a. Show a => a -> String
show (Array Word8 -> String
utf8ToString forall a b. (a -> b) -> a -> b
$ Event -> Array Word8
getRoot Event
ev)
    forall a. [a] -> [a] -> [a]
++ String
"\nPath = " forall a. [a] -> [a] -> [a]
++ forall a. Show a => a -> String
show (Array Word8 -> String
utf8ToString forall a b. (a -> b) -> a -> b
$ Event -> Array Word8
getRelPath Event
ev)
    forall a. [a] -> [a] -> [a]
++ String
"\nCookie = " forall a. [a] -> [a] -> [a]
++ forall a. Show a => a -> String
show (Event -> Cookie
getCookie Event
ev)
    forall a. [a] -> [a] -> [a]
++ String
"\nFlags " forall a. [a] -> [a] -> [a]
++ forall a. Show a => a -> String
show Word32
eventFlags

    forall a. [a] -> [a] -> [a]
++ (Event -> Bool) -> ShowS
showev Event -> Bool
isEventsLost String
"Overflow"

    forall a. [a] -> [a] -> [a]
++ (Event -> Bool) -> ShowS
showev Event -> Bool
isRootUnwatched String
"RootUnwatched"
    forall a. [a] -> [a] -> [a]
++ (Event -> Bool) -> ShowS
showev Event -> Bool
isRootDeleted String
"RootDeleted"
    forall a. [a] -> [a] -> [a]
++ (Event -> Bool) -> ShowS
showev Event -> Bool
isRootMoved String
"RootMoved"
    forall a. [a] -> [a] -> [a]
++ (Event -> Bool) -> ShowS
showev Event -> Bool
isRootUnmounted String
"RootUnmounted"

    forall a. [a] -> [a] -> [a]
++ (Event -> Bool) -> ShowS
showev Event -> Bool
isAttrsModified String
"AttrsModified"

    forall a. [a] -> [a] -> [a]
++ (Event -> Bool) -> ShowS
showev Event -> Bool
isAccessed String
"Accessed"
    forall a. [a] -> [a] -> [a]
++ (Event -> Bool) -> ShowS
showev Event -> Bool
isOpened String
"Opened"
    forall a. [a] -> [a] -> [a]
++ (Event -> Bool) -> ShowS
showev Event -> Bool
isWriteClosed String
"WriteClosed"
    forall a. [a] -> [a] -> [a]
++ (Event -> Bool) -> ShowS
showev Event -> Bool
isNonWriteClosed String
"NonWriteClosed"

    forall a. [a] -> [a] -> [a]
++ (Event -> Bool) -> ShowS
showev Event -> Bool
isCreated String
"Created"
    forall a. [a] -> [a] -> [a]
++ (Event -> Bool) -> ShowS
showev Event -> Bool
isDeleted String
"Deleted"
    forall a. [a] -> [a] -> [a]
++ (Event -> Bool) -> ShowS
showev Event -> Bool
isModified String
"Modified"
    forall a. [a] -> [a] -> [a]
++ (Event -> Bool) -> ShowS
showev Event -> Bool
isMovedFrom String
"MovedFrom"
    forall a. [a] -> [a] -> [a]
++ (Event -> Bool) -> ShowS
showev Event -> Bool
isMovedTo String
"MovedTo"

    forall a. [a] -> [a] -> [a]
++ (Event -> Bool) -> ShowS
showev Event -> Bool
isDir String
"Dir"
    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" 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