avoid confusing git with a modified ctime in clean filter
Linking the file to the tmp dir was not necessary in the clean filter, and it caused the ctime to change, which caused git to think the file was changed. This caused git status to get slow as it kept re-cleaning unchanged files.
This commit is contained in:
parent
b1a1b40a15
commit
4b819bee2b
4 changed files with 47 additions and 27 deletions
|
@ -9,6 +9,7 @@
|
||||||
|
|
||||||
module Annex.Ingest (
|
module Annex.Ingest (
|
||||||
LockedDown(..),
|
LockedDown(..),
|
||||||
|
LockDownConfig(..),
|
||||||
lockDown,
|
lockDown,
|
||||||
ingest,
|
ingest,
|
||||||
finishIngestDirect,
|
finishIngestDirect,
|
||||||
|
@ -48,11 +49,17 @@ import Utility.Touch
|
||||||
import Control.Exception (IOException)
|
import Control.Exception (IOException)
|
||||||
|
|
||||||
data LockedDown = LockedDown
|
data LockedDown = LockedDown
|
||||||
{ lockingFile :: Bool
|
{ lockDownConfig :: LockDownConfig
|
||||||
, keySource :: KeySource
|
, keySource :: KeySource
|
||||||
}
|
}
|
||||||
deriving (Show)
|
deriving (Show)
|
||||||
|
|
||||||
|
data LockDownConfig = LockDownConfig
|
||||||
|
{ lockingFile :: Bool -- ^ write bit removed during lock down
|
||||||
|
, hardlinkFileTmp :: Bool -- ^ hard link to temp directory
|
||||||
|
}
|
||||||
|
deriving (Show)
|
||||||
|
|
||||||
{- The file that's being ingested is locked down before a key is generated,
|
{- The file that's being ingested is locked down before a key is generated,
|
||||||
- to prevent it from being modified in between. This lock down is not
|
- to prevent it from being modified in between. This lock down is not
|
||||||
- perfect at best (and pretty weak at worst). For example, it does not
|
- perfect at best (and pretty weak at worst). For example, it does not
|
||||||
|
@ -64,24 +71,21 @@ data LockedDown = LockedDown
|
||||||
- against some changes, like deletion or overwrite of the file, and
|
- against some changes, like deletion or overwrite of the file, and
|
||||||
- allows lsof checks to be done more efficiently when adding a lot of files.
|
- allows lsof checks to be done more efficiently when adding a lot of files.
|
||||||
-
|
-
|
||||||
- If lockingfile is True, the file is going to be added in locked mode.
|
|
||||||
- So, its write bit is removed as part of the lock down.
|
|
||||||
-
|
|
||||||
- Lockdown can fail if a file gets deleted, and Nothing will be returned.
|
- Lockdown can fail if a file gets deleted, and Nothing will be returned.
|
||||||
-}
|
-}
|
||||||
lockDown :: Bool -> FilePath -> Annex (Maybe LockedDown)
|
lockDown :: LockDownConfig -> FilePath -> Annex (Maybe LockedDown)
|
||||||
lockDown lockingfile file = either
|
lockDown cfg file = either
|
||||||
(\e -> warning (show e) >> return Nothing)
|
(\e -> warning (show e) >> return Nothing)
|
||||||
(return . Just)
|
(return . Just)
|
||||||
=<< lockDown' lockingfile file
|
=<< lockDown' cfg file
|
||||||
|
|
||||||
lockDown' :: Bool -> FilePath -> Annex (Either IOException LockedDown)
|
lockDown' :: LockDownConfig -> FilePath -> Annex (Either IOException LockedDown)
|
||||||
lockDown' lockingfile file = ifM crippledFileSystem
|
lockDown' cfg file = ifM (pure (not (hardlinkFileTmp cfg)) <||> crippledFileSystem)
|
||||||
( withTSDelta $ liftIO . tryIO . nohardlink
|
( withTSDelta $ liftIO . tryIO . nohardlink
|
||||||
, tryIO $ do
|
, tryIO $ do
|
||||||
tmp <- fromRepo gitAnnexTmpMiscDir
|
tmp <- fromRepo gitAnnexTmpMiscDir
|
||||||
createAnnexDirectory tmp
|
createAnnexDirectory tmp
|
||||||
when lockingfile $
|
when (lockingFile cfg) $
|
||||||
freezeContent file
|
freezeContent file
|
||||||
withTSDelta $ \delta -> liftIO $ do
|
withTSDelta $ \delta -> liftIO $ do
|
||||||
(tmpfile, h) <- openTempFile tmp $
|
(tmpfile, h) <- openTempFile tmp $
|
||||||
|
@ -93,7 +97,7 @@ lockDown' lockingfile file = ifM crippledFileSystem
|
||||||
where
|
where
|
||||||
nohardlink delta = do
|
nohardlink delta = do
|
||||||
cache <- genInodeCache file delta
|
cache <- genInodeCache file delta
|
||||||
return $ LockedDown lockingfile $ KeySource
|
return $ LockedDown cfg $ KeySource
|
||||||
{ keyFilename = file
|
{ keyFilename = file
|
||||||
, contentLocation = file
|
, contentLocation = file
|
||||||
, inodeCache = cache
|
, inodeCache = cache
|
||||||
|
@ -101,7 +105,7 @@ lockDown' lockingfile file = ifM crippledFileSystem
|
||||||
withhardlink delta tmpfile = do
|
withhardlink delta tmpfile = do
|
||||||
createLink file tmpfile
|
createLink file tmpfile
|
||||||
cache <- genInodeCache tmpfile delta
|
cache <- genInodeCache tmpfile delta
|
||||||
return $ LockedDown lockingfile $ KeySource
|
return $ LockedDown cfg $ KeySource
|
||||||
{ keyFilename = file
|
{ keyFilename = file
|
||||||
, contentLocation = tmpfile
|
, contentLocation = tmpfile
|
||||||
, inodeCache = cache
|
, inodeCache = cache
|
||||||
|
@ -115,7 +119,7 @@ lockDown' lockingfile file = ifM crippledFileSystem
|
||||||
-}
|
-}
|
||||||
ingest :: Maybe LockedDown -> Annex (Maybe Key, Maybe InodeCache)
|
ingest :: Maybe LockedDown -> Annex (Maybe Key, Maybe InodeCache)
|
||||||
ingest Nothing = return (Nothing, Nothing)
|
ingest Nothing = return (Nothing, Nothing)
|
||||||
ingest (Just (LockedDown lockingfile source)) = withTSDelta $ \delta -> do
|
ingest (Just (LockedDown cfg source)) = withTSDelta $ \delta -> do
|
||||||
backend <- chooseBackend $ keyFilename source
|
backend <- chooseBackend $ keyFilename source
|
||||||
k <- genKey source backend
|
k <- genKey source backend
|
||||||
let src = contentLocation source
|
let src = contentLocation source
|
||||||
|
@ -127,7 +131,7 @@ ingest (Just (LockedDown lockingfile source)) = withTSDelta $ \delta -> do
|
||||||
_ -> failure "changed while it was being added"
|
_ -> failure "changed while it was being added"
|
||||||
where
|
where
|
||||||
go (Just (key, _)) mcache (Just s)
|
go (Just (key, _)) mcache (Just s)
|
||||||
| lockingfile = golocked key mcache s
|
| lockingFile cfg = golocked key mcache s
|
||||||
| otherwise = ifM isDirect
|
| otherwise = ifM isDirect
|
||||||
( godirect key mcache s
|
( godirect key mcache s
|
||||||
, gounlocked key mcache s
|
, gounlocked key mcache s
|
||||||
|
|
|
@ -268,11 +268,15 @@ handleAdds havelsof delayadd cs = returnWhen (null incomplete) $ do
|
||||||
direct <- liftAnnex isDirect
|
direct <- liftAnnex isDirect
|
||||||
unlocked <- liftAnnex versionSupportsUnlockedPointers
|
unlocked <- liftAnnex versionSupportsUnlockedPointers
|
||||||
let lockingfiles = not (unlocked || direct)
|
let lockingfiles = not (unlocked || direct)
|
||||||
|
let lockdownconfig = LockDownConfig
|
||||||
|
{ lockingFile = lockingfiles
|
||||||
|
, hardlinkFileTmp = True
|
||||||
|
}
|
||||||
(pending', cleanup) <- if unlocked || direct
|
(pending', cleanup) <- if unlocked || direct
|
||||||
then return (pending, noop)
|
then return (pending, noop)
|
||||||
else findnew pending
|
else findnew pending
|
||||||
(postponed, toadd) <- partitionEithers
|
(postponed, toadd) <- partitionEithers
|
||||||
<$> safeToAdd lockingfiles havelsof delayadd pending' inprocess
|
<$> safeToAdd lockdownconfig havelsof delayadd pending' inprocess
|
||||||
cleanup
|
cleanup
|
||||||
|
|
||||||
unless (null postponed) $
|
unless (null postponed) $
|
||||||
|
@ -283,7 +287,7 @@ handleAdds havelsof delayadd cs = returnWhen (null incomplete) $ do
|
||||||
catMaybes <$>
|
catMaybes <$>
|
||||||
if not lockingfiles
|
if not lockingfiles
|
||||||
then addunlocked direct toadd
|
then addunlocked direct toadd
|
||||||
else forM toadd (add lockingfiles)
|
else forM toadd (add lockdownconfig)
|
||||||
if DirWatcher.eventsCoalesce || null added || unlocked || direct
|
if DirWatcher.eventsCoalesce || null added || unlocked || direct
|
||||||
then return $ added ++ otherchanges
|
then return $ added ++ otherchanges
|
||||||
else do
|
else do
|
||||||
|
@ -310,15 +314,15 @@ handleAdds havelsof delayadd cs = returnWhen (null incomplete) $ do
|
||||||
| c = return otherchanges
|
| c = return otherchanges
|
||||||
| otherwise = a
|
| otherwise = a
|
||||||
|
|
||||||
add :: Bool -> Change -> Assistant (Maybe Change)
|
add :: LockDownConfig -> Change -> Assistant (Maybe Change)
|
||||||
add lockingfile change@(InProcessAddChange { lockedDown = ld }) =
|
add lockdownconfig change@(InProcessAddChange { lockedDown = ld }) =
|
||||||
catchDefaultIO Nothing <~> doadd
|
catchDefaultIO Nothing <~> doadd
|
||||||
where
|
where
|
||||||
ks = keySource ld
|
ks = keySource ld
|
||||||
doadd = sanitycheck ks $ do
|
doadd = sanitycheck ks $ do
|
||||||
(mkey, mcache) <- liftAnnex $ do
|
(mkey, mcache) <- liftAnnex $ do
|
||||||
showStart "add" $ keyFilename ks
|
showStart "add" $ keyFilename ks
|
||||||
ingest $ Just $ LockedDown lockingfile ks
|
ingest $ Just $ LockedDown lockdownconfig ks
|
||||||
maybe (failedingest change) (done change mcache $ keyFilename ks) mkey
|
maybe (failedingest change) (done change mcache $ keyFilename ks) mkey
|
||||||
add _ _ = return Nothing
|
add _ _ = return Nothing
|
||||||
|
|
||||||
|
@ -332,15 +336,19 @@ handleAdds havelsof delayadd cs = returnWhen (null incomplete) $ do
|
||||||
ct <- liftAnnex compareInodeCachesWith
|
ct <- liftAnnex compareInodeCachesWith
|
||||||
m <- liftAnnex $ removedKeysMap isdirect ct cs
|
m <- liftAnnex $ removedKeysMap isdirect ct cs
|
||||||
delta <- liftAnnex getTSDelta
|
delta <- liftAnnex getTSDelta
|
||||||
|
let cfg = LockDownConfig
|
||||||
|
{ lockingFile = False
|
||||||
|
, hardlinkFileTmp = True
|
||||||
|
}
|
||||||
if M.null m
|
if M.null m
|
||||||
then forM toadd (add False)
|
then forM toadd (add cfg)
|
||||||
else forM toadd $ \c -> do
|
else forM toadd $ \c -> do
|
||||||
mcache <- liftIO $ genInodeCache (changeFile c) delta
|
mcache <- liftIO $ genInodeCache (changeFile c) delta
|
||||||
case mcache of
|
case mcache of
|
||||||
Nothing -> add False c
|
Nothing -> add cfg c
|
||||||
Just cache ->
|
Just cache ->
|
||||||
case M.lookup (inodeCacheToKey ct cache) m of
|
case M.lookup (inodeCacheToKey ct cache) m of
|
||||||
Nothing -> add False c
|
Nothing -> add cfg c
|
||||||
Just k -> fastadd isdirect c k
|
Just k -> fastadd isdirect c k
|
||||||
|
|
||||||
fastadd :: Bool -> Change -> Key -> Assistant (Maybe Change)
|
fastadd :: Bool -> Change -> Key -> Assistant (Maybe Change)
|
||||||
|
@ -416,12 +424,12 @@ handleAdds havelsof delayadd cs = returnWhen (null incomplete) $ do
|
||||||
-
|
-
|
||||||
- Check by running lsof on the repository.
|
- Check by running lsof on the repository.
|
||||||
-}
|
-}
|
||||||
safeToAdd :: Bool -> Bool -> Maybe Seconds -> [Change] -> [Change] -> Assistant [Either Change Change]
|
safeToAdd :: LockDownConfig -> Bool -> Maybe Seconds -> [Change] -> [Change] -> Assistant [Either Change Change]
|
||||||
safeToAdd _ _ _ [] [] = return []
|
safeToAdd _ _ _ [] [] = return []
|
||||||
safeToAdd lockingfiles havelsof delayadd pending inprocess = do
|
safeToAdd lockdownconfig havelsof delayadd pending inprocess = do
|
||||||
maybe noop (liftIO . threadDelaySeconds) delayadd
|
maybe noop (liftIO . threadDelaySeconds) delayadd
|
||||||
liftAnnex $ do
|
liftAnnex $ do
|
||||||
lockeddown <- forM pending $ lockDown lockingfiles . changeFile
|
lockeddown <- forM pending $ lockDown lockdownconfig . changeFile
|
||||||
let inprocess' = inprocess ++ mapMaybe mkinprocess (zip pending lockeddown)
|
let inprocess' = inprocess ++ mapMaybe mkinprocess (zip pending lockeddown)
|
||||||
openfiles <- if havelsof
|
openfiles <- if havelsof
|
||||||
then S.fromList . map fst3 . filter openwrite <$>
|
then S.fromList . map fst3 . filter openwrite <$>
|
||||||
|
|
|
@ -115,7 +115,11 @@ start file = ifAnnexed file addpresent add
|
||||||
perform :: FilePath -> CommandPerform
|
perform :: FilePath -> CommandPerform
|
||||||
perform file = do
|
perform file = do
|
||||||
lockingfile <- not <$> isDirect
|
lockingfile <- not <$> isDirect
|
||||||
lockDown lockingfile file >>= ingest >>= go
|
let cfg = LockDownConfig
|
||||||
|
{ lockingFile = lockingfile
|
||||||
|
, hardlinkFileTmp = True
|
||||||
|
}
|
||||||
|
lockDown cfg file >>= ingest >>= go
|
||||||
where
|
where
|
||||||
go (Just key, cache) = next $ cleanup file key cache True
|
go (Just key, cache) = next $ cleanup file key cache True
|
||||||
go (Nothing, _) = stop
|
go (Nothing, _) = stop
|
||||||
|
|
|
@ -72,7 +72,7 @@ clean file = do
|
||||||
then liftIO $ B.hPut stdout b
|
then liftIO $ B.hPut stdout b
|
||||||
else ifM (shouldAnnex file)
|
else ifM (shouldAnnex file)
|
||||||
( liftIO . emitPointer
|
( liftIO . emitPointer
|
||||||
=<< go =<< ingest =<< lockDown False file
|
=<< go =<< ingest =<< lockDown cfg file
|
||||||
, liftIO $ B.hPut stdout b
|
, liftIO $ B.hPut stdout b
|
||||||
)
|
)
|
||||||
stop
|
stop
|
||||||
|
@ -81,6 +81,10 @@ clean file = do
|
||||||
logStatus k InfoPresent
|
logStatus k InfoPresent
|
||||||
return k
|
return k
|
||||||
go _ = error "could not add file to the annex"
|
go _ = error "could not add file to the annex"
|
||||||
|
cfg = LockDownConfig
|
||||||
|
{ lockingFile = False
|
||||||
|
, hardlinkFileTmp = False
|
||||||
|
}
|
||||||
|
|
||||||
shouldAnnex :: FilePath -> Annex Bool
|
shouldAnnex :: FilePath -> Annex Bool
|
||||||
shouldAnnex file = do
|
shouldAnnex file = do
|
||||||
|
|
Loading…
Reference in a new issue