renaming
This commit is contained in:
parent
4c9ad1de46
commit
7a42a47902
17 changed files with 31 additions and 34 deletions
|
@ -351,7 +351,7 @@ applyView' mkviewedfile getfilemetadata view = do
|
|||
withUpdateIndex viewg $ \uh -> do
|
||||
forM_ l $ \(f, sha, mode) -> do
|
||||
topf <- inRepo (toTopFilePath f)
|
||||
go uh topf sha (toTreeItemType mode) =<< lookupFile f
|
||||
go uh topf sha (toTreeItemType mode) =<< lookupKey f
|
||||
liftIO $ void clean
|
||||
genViewBranch view
|
||||
where
|
||||
|
|
|
@ -35,8 +35,8 @@ import Control.Concurrent
|
|||
- When in an adjusted branch that may have hidden the file, looks for a
|
||||
- pointer to a key in the original branch.
|
||||
-}
|
||||
lookupFile :: RawFilePath -> Annex (Maybe Key)
|
||||
lookupFile = lookupFile' catkeyfile
|
||||
lookupKey :: RawFilePath -> Annex (Maybe Key)
|
||||
lookupKey = lookupKey' catkeyfile
|
||||
where
|
||||
catkeyfile file =
|
||||
ifM (liftIO $ doesFileExist $ fromRawFilePath file)
|
||||
|
@ -44,8 +44,8 @@ lookupFile = lookupFile' catkeyfile
|
|||
, catKeyFileHidden file =<< getCurrentBranch
|
||||
)
|
||||
|
||||
lookupFileNotHidden :: RawFilePath -> Annex (Maybe Key)
|
||||
lookupFileNotHidden = lookupFile' catkeyfile
|
||||
lookupKeyNotHidden :: RawFilePath -> Annex (Maybe Key)
|
||||
lookupKeyNotHidden = lookupKey' catkeyfile
|
||||
where
|
||||
catkeyfile file =
|
||||
ifM (liftIO $ doesFileExist $ fromRawFilePath file)
|
||||
|
@ -53,8 +53,8 @@ lookupFileNotHidden = lookupFile' catkeyfile
|
|||
, return Nothing
|
||||
)
|
||||
|
||||
lookupFile' :: (RawFilePath -> Annex (Maybe Key)) -> RawFilePath -> Annex (Maybe Key)
|
||||
lookupFile' catkeyfile file = isAnnexLink file >>= \case
|
||||
lookupKey' :: (RawFilePath -> Annex (Maybe Key)) -> RawFilePath -> Annex (Maybe Key)
|
||||
lookupKey' catkeyfile file = isAnnexLink file >>= \case
|
||||
Just key -> return (Just key)
|
||||
Nothing -> catkeyfile file
|
||||
|
||||
|
@ -64,7 +64,7 @@ whenAnnexed :: (RawFilePath -> Key -> Annex (Maybe a)) -> RawFilePath -> Annex (
|
|||
whenAnnexed a file = ifAnnexed file (a file) (return Nothing)
|
||||
|
||||
ifAnnexed :: RawFilePath -> (Key -> Annex a) -> Annex a -> Annex a
|
||||
ifAnnexed file yes no = maybe no yes =<< lookupFile file
|
||||
ifAnnexed file yes no = maybe no yes =<< lookupKey file
|
||||
|
||||
{- Find all unlocked files and update the keys database for them.
|
||||
-
|
||||
|
|
|
@ -145,7 +145,7 @@ expensiveScan urlrenderer rs = batch <~> do
|
|||
(unwanted', ts) <- maybe
|
||||
(return (unwanted, []))
|
||||
(findtransfers f unwanted)
|
||||
=<< liftAnnex (lookupFile f)
|
||||
=<< liftAnnex (lookupKey f)
|
||||
mapM_ (enqueue f) ts
|
||||
|
||||
{- Delay for a short time to avoid using too much CPU. -}
|
||||
|
|
|
@ -289,7 +289,7 @@ onAddUnlocked' contentchanged addassociatedfile addlink samefilestatus symlinkss
|
|||
onAddSymlink :: Handler
|
||||
onAddSymlink file filestatus = unlessIgnored file $ do
|
||||
linktarget <- liftIO (catchMaybeIO $ readSymbolicLink file)
|
||||
kv <- liftAnnex (lookupFile (toRawFilePath file))
|
||||
kv <- liftAnnex (lookupKey (toRawFilePath file))
|
||||
onAddSymlink' linktarget kv file filestatus
|
||||
|
||||
onAddSymlink' :: Maybe String -> Maybe Key -> Handler
|
||||
|
|
|
@ -128,7 +128,7 @@ makeinfos updated version = do
|
|||
now <- liftIO getCurrentTime
|
||||
liftIO $ putStrLn $ "building info files"
|
||||
forM_ updated $ \(f, bv) -> do
|
||||
v <- lookupFile (toRawFilePath f)
|
||||
v <- lookupKey (toRawFilePath f)
|
||||
case v of
|
||||
Nothing -> noop
|
||||
Just k -> whenM (inAnnex k) $ do
|
||||
|
|
|
@ -49,7 +49,7 @@ withFilesInGit ww a l = seekFiltered a $
|
|||
seekHelper id ww LsFiles.inRepo l
|
||||
|
||||
withFilesInGitAnnex :: WarnUnmatchWhen -> (RawFilePath -> Key -> CommandSeek) -> [WorkTreeItem] -> CommandSeek
|
||||
withFilesInGitAnnex ww a l = seekFiltered' a $
|
||||
withFilesInGitAnnex ww a l = seekFilteredKeys a $
|
||||
seekHelper fst3 ww LsFiles.inRepoDetails l
|
||||
|
||||
withFilesInGitNonRecursive :: WarnUnmatchWhen -> String -> (RawFilePath -> CommandSeek) -> [WorkTreeItem] -> CommandSeek
|
||||
|
@ -120,10 +120,6 @@ withFilesToBeCommitted :: (RawFilePath -> CommandSeek) -> [WorkTreeItem] -> Comm
|
|||
withFilesToBeCommitted a l = seekFiltered a $
|
||||
seekHelper id WarnUnmatchWorkTreeItems (const LsFiles.stagedNotDeleted) l
|
||||
|
||||
isOldUnlocked :: RawFilePath -> Annex Bool
|
||||
isOldUnlocked f = liftIO (notSymlink f) <&&>
|
||||
(isJust <$> catKeyFile f <||> isJust <$> catKeyFileHEAD f)
|
||||
|
||||
{- unlocked pointer files that are staged, and whose content has not been
|
||||
- modified-}
|
||||
withUnmodifiedUnlockedPointers :: WarnUnmatchWhen -> (RawFilePath -> CommandSeek) -> [WorkTreeItem] -> CommandSeek
|
||||
|
@ -268,8 +264,9 @@ seekFiltered a fs = do
|
|||
process matcher f =
|
||||
whenM (matcher $ MatchingFile $ FileInfo f f) $ a f
|
||||
|
||||
seekFiltered' :: (RawFilePath -> Key -> CommandSeek) -> Annex [(RawFilePath, Git.Sha, FileMode)] -> Annex ()
|
||||
seekFiltered' a fs = do
|
||||
-- This is siginificantly faster than using lookupKey after seekFiltered.
|
||||
seekFilteredKeys :: (RawFilePath -> Key -> CommandSeek) -> Annex [(RawFilePath, Git.Sha, FileMode)] -> Annex ()
|
||||
seekFilteredKeys a fs = do
|
||||
g <- Annex.gitRepo
|
||||
catObjectStream' g $ \feeder closer reader -> do
|
||||
tid <- liftIO . async =<< forkState (gofeed feeder closer)
|
||||
|
|
|
@ -84,7 +84,7 @@ keyOpt s = case parseURI s of
|
|||
Nothing -> giveup $ "bad key/url " ++ s
|
||||
|
||||
perform :: Key -> FilePath -> CommandPerform
|
||||
perform key file = lookupFileNotHidden (toRawFilePath file) >>= \case
|
||||
perform key file = lookupKeyNotHidden (toRawFilePath file) >>= \case
|
||||
Nothing -> ifM (liftIO $ doesFileExist file)
|
||||
( hasothercontent
|
||||
, do
|
||||
|
|
|
@ -168,7 +168,7 @@ parseJSONInput i = case eitherDecode (BU.fromString i) of
|
|||
startBatch :: (Either RawFilePath Key, MetaData) -> CommandStart
|
||||
startBatch (i, (MetaData m)) = case i of
|
||||
Left f -> do
|
||||
mk <- lookupFile f
|
||||
mk <- lookupKey f
|
||||
case mk of
|
||||
Just k -> go k (mkActionItem (k, AssociatedFile (Just f)))
|
||||
Nothing -> giveup $ "not an annexed file: " ++ fromRawFilePath f
|
||||
|
|
|
@ -136,7 +136,7 @@ send ups fs = do
|
|||
let addlist f o = whenM (matcher $ MatchingFile $ FileInfo f f) $
|
||||
liftIO $ hPutStrLn h o
|
||||
forM_ fs' $ \f -> do
|
||||
mk <- lookupFile f
|
||||
mk <- lookupKey f
|
||||
case mk of
|
||||
Nothing -> noop
|
||||
Just k -> withObjectLoc k $
|
||||
|
|
|
@ -439,7 +439,7 @@ randKey sz = withTmpFile "randkey" $ \f h -> do
|
|||
return k
|
||||
|
||||
getReadonlyKey :: Remote -> FilePath -> Annex Key
|
||||
getReadonlyKey r f = lookupFile (toRawFilePath f) >>= \case
|
||||
getReadonlyKey r f = lookupKey (toRawFilePath f) >>= \case
|
||||
Nothing -> giveup $ f ++ " is not an annexed file"
|
||||
Just k -> do
|
||||
unlessM (inAnnex k) $
|
||||
|
|
|
@ -215,7 +215,7 @@ withKeysReferenced' mdir initial a = do
|
|||
Just dir -> inRepo $ LsFiles.inRepo [] [toRawFilePath dir]
|
||||
go v [] = return v
|
||||
go v (f:fs) = do
|
||||
mk <- lookupFile f
|
||||
mk <- lookupKey f
|
||||
case mk of
|
||||
Nothing -> go v fs
|
||||
Just k -> do
|
||||
|
|
2
Limit.hs
2
Limit.hs
|
@ -372,7 +372,7 @@ addAccessedWithin duration = do
|
|||
secs = fromIntegral (durationSeconds duration)
|
||||
|
||||
lookupFileKey :: FileInfo -> Annex (Maybe Key)
|
||||
lookupFileKey = lookupFile . currFile
|
||||
lookupFileKey = lookupKey . currFile
|
||||
|
||||
checkKey :: (Key -> Annex Bool) -> MatchInfo -> Annex Bool
|
||||
checkKey a (MatchingFile fi) = lookupFileKey fi >>= maybe (return False) a
|
||||
|
|
4
Test.hs
4
Test.hs
|
@ -704,7 +704,7 @@ test_lock_force = intmpclonerepo $ do
|
|||
git_annex "get" [annexedfile] @? "get of file failed"
|
||||
git_annex "unlock" [annexedfile] @? "unlock failed"
|
||||
annexeval $ do
|
||||
Just k <- Annex.WorkTree.lookupFile (toRawFilePath annexedfile)
|
||||
Just k <- Annex.WorkTree.lookupKey (toRawFilePath annexedfile)
|
||||
Database.Keys.removeInodeCaches k
|
||||
Database.Keys.closeDb
|
||||
liftIO . nukeFile =<< Annex.fromRepo Annex.Locations.gitAnnexKeysDbIndexCache
|
||||
|
@ -1680,7 +1680,7 @@ test_crypto = do
|
|||
(c,k) <- annexeval $ do
|
||||
uuid <- Remote.nameToUUID "foo"
|
||||
rs <- Logs.Remote.readRemoteLog
|
||||
Just k <- Annex.WorkTree.lookupFile (toRawFilePath annexedfile)
|
||||
Just k <- Annex.WorkTree.lookupKey (toRawFilePath annexedfile)
|
||||
return (fromJust $ M.lookup uuid rs, k)
|
||||
let key = if scheme `elem` ["hybrid","pubkey"]
|
||||
then Just $ Utility.Gpg.KeyIds [Utility.Gpg.testKeyId]
|
||||
|
|
|
@ -316,7 +316,7 @@ checkdangling f = ifM (annexeval Config.crippledFileSystem)
|
|||
checklocationlog :: FilePath -> Bool -> Assertion
|
||||
checklocationlog f expected = do
|
||||
thisuuid <- annexeval Annex.UUID.getUUID
|
||||
r <- annexeval $ Annex.WorkTree.lookupFile (toRawFilePath f)
|
||||
r <- annexeval $ Annex.WorkTree.lookupKey (toRawFilePath f)
|
||||
case r of
|
||||
Just k -> do
|
||||
uuids <- annexeval $ Remote.keyLocations k
|
||||
|
@ -327,7 +327,7 @@ checklocationlog f expected = do
|
|||
checkbackend :: FilePath -> Types.Backend -> Assertion
|
||||
checkbackend file expected = do
|
||||
b <- annexeval $ maybe (return Nothing) (Backend.getBackend file)
|
||||
=<< Annex.WorkTree.lookupFile (toRawFilePath file)
|
||||
=<< Annex.WorkTree.lookupKey (toRawFilePath file)
|
||||
assertEqual ("backend for " ++ file) (Just expected) b
|
||||
|
||||
checkispointerfile :: FilePath -> Assertion
|
||||
|
|
|
@ -31,8 +31,8 @@ keyFile0 :: Key -> FilePath
|
|||
keyFile0 = Upgrade.V1.keyFile1
|
||||
fileKey0 :: FilePath -> Key
|
||||
fileKey0 = Upgrade.V1.fileKey1
|
||||
lookupFile0 :: FilePath -> Annex (Maybe (Key, Backend))
|
||||
lookupFile0 = Upgrade.V1.lookupFile1
|
||||
lookupKey0 :: FilePath -> Annex (Maybe (Key, Backend))
|
||||
lookupKey0 = Upgrade.V1.lookupKey1
|
||||
|
||||
getKeysPresent0 :: FilePath -> Annex [Key]
|
||||
getKeysPresent0 dir = ifM (liftIO $ doesDirectoryExist dir)
|
||||
|
|
|
@ -90,7 +90,7 @@ updateSymlinks = do
|
|||
void $ liftIO cleanup
|
||||
where
|
||||
fixlink f = do
|
||||
r <- lookupFile1 f
|
||||
r <- lookupKey1 f
|
||||
case r of
|
||||
Nothing -> noop
|
||||
Just (k, _) -> do
|
||||
|
@ -191,8 +191,8 @@ readLog1 :: FilePath -> IO [LogLine]
|
|||
readLog1 file = catchDefaultIO [] $
|
||||
parseLog . encodeBL <$> readFileStrict file
|
||||
|
||||
lookupFile1 :: FilePath -> Annex (Maybe (Key, Backend))
|
||||
lookupFile1 file = do
|
||||
lookupKey1 :: FilePath -> Annex (Maybe (Key, Backend))
|
||||
lookupKey1 file = do
|
||||
tl <- liftIO $ tryIO getsymlink
|
||||
case tl of
|
||||
Left _ -> return Nothing
|
||||
|
|
|
@ -115,7 +115,7 @@ upgradeDirectWorkTree = do
|
|||
void $ liftIO clean
|
||||
where
|
||||
go (f, _sha, mode) | isSymLink mode = do
|
||||
-- Cannot use lookupFile here, as we're in between direct
|
||||
-- Cannot use lookupKey here, as we're in between direct
|
||||
-- mode and v6.
|
||||
mk <- catKeyFile f
|
||||
case mk of
|
||||
|
|
Loading…
Add table
Reference in a new issue