summaryrefslogtreecommitdiff
path: root/Utility/Kqueue.hs
diff options
context:
space:
mode:
authorGravatar Joey Hess <joey@kitenet.net>2012-06-18 13:01:58 -0400
committerGravatar Joey Hess <joey@kitenet.net>2012-06-18 13:01:58 -0400
commita39b73d118c18707e6549d57a902fca9966119f8 (patch)
tree8778c4a6bb3d6bb73f4be34668aae0f864c8e725 /Utility/Kqueue.hs
parentdc3d9d1e982f7342dd3e2b3fc14fbbe85e7acd3e (diff)
recurse dirTree and open the directories for kqueue to watch
Diffstat (limited to 'Utility/Kqueue.hs')
-rw-r--r--Utility/Kqueue.hs23
1 files changed, 18 insertions, 5 deletions
diff --git a/Utility/Kqueue.hs b/Utility/Kqueue.hs
index bfc6ee9fc..aabea7d03 100644
--- a/Utility/Kqueue.hs
+++ b/Utility/Kqueue.hs
@@ -7,7 +7,10 @@
{-# LANGUAGE ForeignFunctionInterface #-}
-module Utility.Kqueue ( waitChange ) where
+module Utility.Kqueue (
+ waitChange,
+ scanRecursive
+) where
import Common
@@ -16,16 +19,26 @@ import Foreign.C.Types
import Foreign.C.Error
import Foreign.Ptr
import Foreign.Marshal
+import qualified Data.Map as M
+
+type DirMap = M.Map Fd FilePath
foreign import ccall unsafe "libkqueue.h waitchange" c_waitchange
:: Ptr Fd -> IO Fd
-waitChange :: [Fd] -> IO (Maybe Fd)
-waitChange fds = withArray fds $ \c_fds -> do
- ret <- c_waitchange c_fds
+waitChange :: DirMap -> IO (Maybe FilePath)
+waitChange dirmap = withArray (M.keys dirmap) $ \c_fds -> do
+ changed <- c_waitchange c_fds
ifM (safeErrno <$> getErrno)
- ( return $ Just ret
+ ( return $ M.lookup changed dirmap
, return Nothing
)
where
safeErrno (Errno v) = v == 0
+
+scanRecursive :: FilePath -> (FilePath -> Bool) -> IO DirMap
+scanRecursive dir prune = M.fromList <$> (mapM opendir =<< dirTree dir prune)
+ where
+ opendir d = (,)
+ <$> openFd d ReadOnly Nothing defaultFileFlags
+ <*> pure d