kqueue: properly call delHook for file deletion, not delDirHook
This commit is contained in:
parent
d53f70e203
commit
32ac773934
1 changed files with 37 additions and 23 deletions
|
@ -14,8 +14,6 @@ module Utility.Kqueue (
|
||||||
waitChange,
|
waitChange,
|
||||||
Change(..),
|
Change(..),
|
||||||
changedFile,
|
changedFile,
|
||||||
isAdd,
|
|
||||||
isDelete,
|
|
||||||
runHooks,
|
runHooks,
|
||||||
) where
|
) where
|
||||||
|
|
||||||
|
@ -34,15 +32,14 @@ import Control.Concurrent
|
||||||
|
|
||||||
data Change
|
data Change
|
||||||
= Deleted FilePath
|
= Deleted FilePath
|
||||||
|
| DeletedDir FilePath
|
||||||
| Added FilePath
|
| Added FilePath
|
||||||
deriving (Show)
|
deriving (Show)
|
||||||
|
|
||||||
isAdd :: Change -> Bool
|
isAdd :: Change -> Bool
|
||||||
isAdd (Added _) = True
|
isAdd (Added _) = True
|
||||||
isAdd (Deleted _) = False
|
isAdd (Deleted _) = False
|
||||||
|
isAdd (DeletedDir _) = False
|
||||||
isDelete :: Change -> Bool
|
|
||||||
isDelete = not . isAdd
|
|
||||||
|
|
||||||
changedFile :: Change -> FilePath
|
changedFile :: Change -> FilePath
|
||||||
changedFile (Added f) = f
|
changedFile (Added f) = f
|
||||||
|
@ -59,31 +56,43 @@ type Pruner = FilePath -> Bool
|
||||||
|
|
||||||
type DirMap = M.Map Fd DirInfo
|
type DirMap = M.Map Fd DirInfo
|
||||||
|
|
||||||
{- A directory, and its last known contents (with filenames relative to it) -}
|
{- Enough information to uniquely identify a file in a directory,
|
||||||
|
- but not too much. -}
|
||||||
|
data DirEnt = DirEnt
|
||||||
|
{ dirEnt :: FilePath -- relative to the parent directory
|
||||||
|
, _dirInode :: FileID -- included to notice file replacements
|
||||||
|
, isSubDir :: Bool
|
||||||
|
}
|
||||||
|
deriving (Eq, Ord, Show)
|
||||||
|
|
||||||
|
{- A directory, and its last known contents. -}
|
||||||
data DirInfo = DirInfo
|
data DirInfo = DirInfo
|
||||||
{ dirName :: FilePath
|
{ dirName :: FilePath
|
||||||
, dirCache :: S.Set (FilePath, FileID)
|
, dirCache :: S.Set DirEnt
|
||||||
}
|
}
|
||||||
deriving (Show)
|
deriving (Show)
|
||||||
|
|
||||||
getDirInfo :: FilePath -> IO DirInfo
|
getDirInfo :: FilePath -> IO DirInfo
|
||||||
getDirInfo dir = do
|
getDirInfo dir = do
|
||||||
l <- filter (not . dirCruft) <$> getDirectoryContents dir
|
l <- filter (not . dirCruft) <$> getDirectoryContents dir
|
||||||
contents <- S.fromList . catMaybes <$> mapM addinode l
|
contents <- S.fromList . catMaybes <$> mapM getDirEnt l
|
||||||
return $ DirInfo dir contents
|
return $ DirInfo dir contents
|
||||||
where
|
where
|
||||||
addinode f = catchMaybeIO $ do
|
getDirEnt f = catchMaybeIO $ do
|
||||||
inode <- fileID <$> getFileStatus (dir </> f)
|
s <- getFileStatus (dir </> f)
|
||||||
return (f, inode)
|
return $ DirEnt f (fileID s) (isDirectory s)
|
||||||
|
|
||||||
{- Difference between the dirCaches of two DirInfos. -}
|
{- Difference between the dirCaches of two DirInfos. -}
|
||||||
(//) :: DirInfo -> DirInfo -> [Change]
|
(//) :: DirInfo -> DirInfo -> [Change]
|
||||||
oldc // newc = deleted ++ added
|
oldc // newc = deleted ++ added
|
||||||
where
|
where
|
||||||
deleted = calc Deleted oldc newc
|
deleted = calc gendel oldc newc
|
||||||
added = calc Added newc oldc
|
added = calc genadd newc oldc
|
||||||
calc a x y = map a . map (dirName x </>) . map fst $
|
gendel x = (if isSubDir x then DeletedDir else Deleted) $
|
||||||
S.toList $ S.difference (dirCache x) (dirCache y)
|
dirName oldc </> dirEnt x
|
||||||
|
genadd x = Added $ dirName newc </> dirEnt x
|
||||||
|
calc a x y = map a $ S.toList $
|
||||||
|
S.difference (dirCache x) (dirCache y)
|
||||||
|
|
||||||
{- Builds a map of directories in a tree, possibly pruning some.
|
{- Builds a map of directories in a tree, possibly pruning some.
|
||||||
- Opens each directory in the tree, and records its current contents. -}
|
- Opens each directory in the tree, and records its current contents. -}
|
||||||
|
@ -103,7 +112,7 @@ scanRecursive topdir prune = M.fromList <$> walk [] [topdir]
|
||||||
case mfd of
|
case mfd of
|
||||||
Nothing -> walk c rest
|
Nothing -> walk c rest
|
||||||
Just fd -> do
|
Just fd -> do
|
||||||
let subdirs = map (dir </>) . map fst $
|
let subdirs = map (dir </>) . map dirEnt $
|
||||||
S.toList $ dirCache info
|
S.toList $ dirCache info
|
||||||
walk ((fd, info):c) (subdirs ++ rest)
|
walk ((fd, info):c) (subdirs ++ rest)
|
||||||
|
|
||||||
|
@ -128,7 +137,7 @@ findDirContents :: DirMap -> FilePath -> [FilePath]
|
||||||
findDirContents dirmap dir = concatMap absolutecontents $ search
|
findDirContents dirmap dir = concatMap absolutecontents $ search
|
||||||
where
|
where
|
||||||
absolutecontents i = map (dirName i </>)
|
absolutecontents i = map (dirName i </>)
|
||||||
(map fst $ S.toList $ dirCache i)
|
(map dirEnt $ S.toList $ dirCache i)
|
||||||
search = map snd $ M.toList $
|
search = map snd $ M.toList $
|
||||||
M.filter (\i -> dirName i == dir) dirmap
|
M.filter (\i -> dirName i == dir) dirmap
|
||||||
|
|
||||||
|
@ -229,12 +238,14 @@ runHooks kq hooks = do
|
||||||
(q', changes) <- waitChange q
|
(q', changes) <- waitChange q
|
||||||
forM_ changes $ dispatch (kqueueMap q')
|
forM_ changes $ dispatch (kqueueMap q')
|
||||||
loop q'
|
loop q'
|
||||||
-- Kqueue returns changes for both whole directories
|
|
||||||
-- being added and deleted, and individual files being
|
dispatch dirmap change@(Deleted _) =
|
||||||
-- added and deleted.
|
callhook delHook Nothing change
|
||||||
dispatch dirmap change
|
dispatch dirmap change@(DeletedDir _) =
|
||||||
| isAdd change = withstatus change $ dispatchadd dirmap
|
callhook delDirHook Nothing change
|
||||||
| otherwise = callhook delDirHook Nothing change
|
dispatch dirmap change@(Added _) =
|
||||||
|
withstatus change $ dispatchadd dirmap
|
||||||
|
|
||||||
dispatchadd dirmap change s
|
dispatchadd dirmap change s
|
||||||
| Files.isSymbolicLink s =
|
| Files.isSymbolicLink s =
|
||||||
callhook addSymlinkHook (Just s) change
|
callhook addSymlinkHook (Just s) change
|
||||||
|
@ -242,12 +253,15 @@ runHooks kq hooks = do
|
||||||
| Files.isRegularFile s =
|
| Files.isRegularFile s =
|
||||||
callhook addHook (Just s) change
|
callhook addHook (Just s) change
|
||||||
| otherwise = noop
|
| otherwise = noop
|
||||||
|
|
||||||
recursiveadd dirmap change = do
|
recursiveadd dirmap change = do
|
||||||
let contents = findDirContents dirmap $ changedFile change
|
let contents = findDirContents dirmap $ changedFile change
|
||||||
forM_ contents $ \f ->
|
forM_ contents $ \f ->
|
||||||
withstatus (Added f) $ dispatchadd dirmap
|
withstatus (Added f) $ dispatchadd dirmap
|
||||||
|
|
||||||
callhook h s change = case h hooks of
|
callhook h s change = case h hooks of
|
||||||
Nothing -> noop
|
Nothing -> noop
|
||||||
Just a -> a (changedFile change) s
|
Just a -> a (changedFile change) s
|
||||||
|
|
||||||
withstatus change a = maybe noop (a change) =<<
|
withstatus change a = maybe noop (a change) =<<
|
||||||
(catchMaybeIO (getSymbolicLinkStatus (changedFile change)))
|
(catchMaybeIO (getSymbolicLinkStatus (changedFile change)))
|
||||||
|
|
Loading…
Add table
Add a link
Reference in a new issue