Support building with hinotify-0.3.10.

Kept backwards compat with old versions via a shim.

This commit was sponsored by mo on Patreon.
This commit is contained in:
Joey Hess 2018-05-08 14:26:57 -04:00
parent 2948f6d916
commit 7dc28dc705
No known key found for this signature in database
GPG key ID: DB12DB0FF05F8F38
3 changed files with 61 additions and 12 deletions

View file

@ -1,14 +1,15 @@
git-annex (6.20180428) UNRELEASED; urgency=medium git-annex (6.20180428) UNRELEASED; urgency=medium
* Fix bug in last release that crashes when using
--all or running git-annex in a bare repository. May have also
affected git-annex unused and git-annex info.
* runshell: Use proot when running on Android, to work around * runshell: Use proot when running on Android, to work around
Android 8's ill-advised seccomp filtering of system calls, Android 8's ill-advised seccomp filtering of system calls,
including ones crucial for reliable thread locking. including ones crucial for reliable thread locking.
(This will only work with termux's version of proot.) (This will only work with termux's version of proot.)
* Fix bug in last release that crashes when using
--all or running git-annex in a bare repository. May have also
affected git-annex unused and git-annex info.
* Fix bug in last release that prevented the webapp opening on * Fix bug in last release that prevented the webapp opening on
non-Linux systems. non-Linux systems.
* Support building with hinotify-0.3.10.
-- Joey Hess <id@joeyh.name> Tue, 08 May 2018 13:51:37 -0400 -- Joey Hess <id@joeyh.name> Tue, 08 May 2018 13:51:37 -0400

View file

@ -1,3 +1,5 @@
{-# LANGUAGE CPP #-}
{- higher-level inotify interface {- higher-level inotify interface
- -
- Copyright 2012 Joey Hess <id@joeyh.name> - Copyright 2012 Joey Hess <id@joeyh.name>
@ -10,6 +12,9 @@ module Utility.DirWatcher.INotify where
import Common hiding (isDirectory) import Common hiding (isDirectory)
import Utility.ThreadLock import Utility.ThreadLock
import Utility.DirWatcher.Types import Utility.DirWatcher.Types
#if MIN_VERSION_hinotify(0,3,10)
import Utility.FileSystemEncoding
#endif
import System.INotify import System.INotify
import qualified System.Posix.Files as Files import qualified System.Posix.Files as Files
@ -55,7 +60,7 @@ watchDir i dir ignored scanevents hooks
lock <- newLock lock <- newLock
let handler event = withLock lock (void $ go event) let handler event = withLock lock (void $ go event)
flip catchNonAsync failedwatch $ do flip catchNonAsync failedwatch $ do
void (addWatch i watchevents dir handler) void (addWatch i watchevents (toInternalFilePath dir) handler)
`catchIO` failedaddwatch `catchIO` failedaddwatch
withLock lock $ withLock lock $
mapM_ scan =<< filter (not . dirCruft) <$> mapM_ scan =<< filter (not . dirCruft) <$>
@ -93,7 +98,7 @@ watchDir i dir ignored scanevents hooks
| otherwise -> | otherwise ->
noop noop
go (Created { isDirectory = isd, filePath = f }) go (Created { isDirectory = isd, filePath = fi })
| isd = recurse $ indir f | isd = recurse $ indir f
| otherwise = do | otherwise = do
ms <- getstatus f ms <- getstatus f
@ -106,28 +111,39 @@ watchDir i dir ignored scanevents hooks
when (hashook addHook) $ when (hashook addHook) $
runhook addHook f ms runhook addHook f ms
_ -> noop _ -> noop
where
f = fromInternalFilePath fi
-- Closing a file is assumed to mean it's done being written, -- Closing a file is assumed to mean it's done being written,
-- so a new add event is sent. -- so a new add event is sent.
go (Closed { isDirectory = False, maybeFilePath = Just f }) = go (Closed { isDirectory = False, maybeFilePath = Just fi }) =
checkfiletype Files.isRegularFile addHook f checkfiletype Files.isRegularFile addHook $
fromInternalFilePath fi
-- When a file or directory is moved in, scan it to add new -- When a file or directory is moved in, scan it to add new
-- stuff. -- stuff.
go (MovedIn { filePath = f }) = scan f go (MovedIn { filePath = fi }) = scan $ fromInternalFilePath fi
go (MovedOut { isDirectory = isd, filePath = f }) go (MovedOut { isDirectory = isd, filePath = fi })
| isd = runhook delDirHook f Nothing | isd = runhook delDirHook f Nothing
| otherwise = runhook delHook f Nothing | otherwise = runhook delHook f Nothing
where
f = fromInternalFilePath fi
-- Verify that the deleted item really doesn't exist, -- Verify that the deleted item really doesn't exist,
-- since there can be spurious deletion events for items -- since there can be spurious deletion events for items
-- in a directory that has been moved out, but is still -- in a directory that has been moved out, but is still
-- being watched. -- being watched.
go (Deleted { isDirectory = isd, filePath = f }) go (Deleted { isDirectory = isd, filePath = fi })
| isd = guarded $ runhook delDirHook f Nothing | isd = guarded $ runhook delDirHook f Nothing
| otherwise = guarded $ runhook delHook f Nothing | otherwise = guarded $ runhook delHook f Nothing
where where
guarded = unlessM (filetype (const True) f) guarded = unlessM (filetype (const True) f)
go (Modified { isDirectory = isd, maybeFilePath = Just f }) f = fromInternalFilePath fi
go (Modified { isDirectory = isd, maybeFilePath = Just fi })
| isd = noop | isd = noop
| otherwise = runhook modifyHook f Nothing | otherwise = runhook modifyHook (fromInternalFilePath fi) Nothing
go _ = noop go _ = noop
hashook h = isJust $ h hooks hashook h = isJust $ h hooks
@ -185,3 +201,15 @@ querySysctl ps = getM go ["sysctl", "/sbin/sysctl", "/usr/sbin/sysctl"]
Nothing -> return Nothing Nothing -> return Nothing
Just s -> return $ parsesysctl s Just s -> return $ parsesysctl s
parsesysctl s = readish =<< lastMaybe (words s) parsesysctl s = readish =<< lastMaybe (words s)
#if MIN_VERSION_hinotify(0,3,10)
toInternalFilePath :: FilePath -> RawFilePath
toInternalFilePath = toRawFilePath
fromInternalFilePath :: RawFilePath -> FilePath
fromInternalFilePath = fromRawFilePath
#else
toInternalFilePath :: FilePath -> FilePath
toInternalFilePath = id
fromInternalFilePath :: FilePath -> FilePath
fromInternalFilePath = id
#endif

View file

@ -12,6 +12,9 @@ module Utility.FileSystemEncoding (
useFileSystemEncoding, useFileSystemEncoding,
fileEncoding, fileEncoding,
withFilePath, withFilePath,
RawFilePath,
fromRawFilePath,
toRawFilePath,
decodeBS, decodeBS,
encodeBS, encodeBS,
decodeW8, decodeW8,
@ -32,6 +35,7 @@ import System.IO
import System.IO.Unsafe import System.IO.Unsafe
import Data.Word import Data.Word
import Data.List import Data.List
import qualified Data.ByteString as S
import qualified Data.ByteString.Lazy as L import qualified Data.ByteString.Lazy as L
#ifdef mingw32_HOST_OS #ifdef mingw32_HOST_OS
import qualified Data.ByteString.Lazy.UTF8 as L8 import qualified Data.ByteString.Lazy.UTF8 as L8
@ -120,6 +124,22 @@ encodeBS = L.pack . decodeW8NUL
encodeBS = L8.fromString encodeBS = L8.fromString
#endif #endif
{- Recent versions of the unix package have this alias; defined here
- for backwards compatibility. -}
type RawFilePath = S.ByteString
{- Note that the RawFilePath is assumed to never contain NUL,
- since filename's don't. This should only be used with actual
- RawFilePaths not arbitrary ByteString that may contain NUL. -}
fromRawFilePath :: RawFilePath -> FilePath
fromRawFilePath = encodeW8 . S.unpack
{- Note that the FilePath is assumed to never contain NUL,
- since filename's don't. This should only be used with actual FilePaths
- not arbitrary String that may contain NUL. -}
toRawFilePath :: FilePath -> RawFilePath
toRawFilePath = S.pack . decodeW8
{- Converts a [Word8] to a FilePath, encoding using the filesystem encoding. {- Converts a [Word8] to a FilePath, encoding using the filesystem encoding.
- -
- w82c produces a String, which may contain Chars that are invalid - w82c produces a String, which may contain Chars that are invalid