avoid borg list of archives that have been listed before

This makes sync a lot faster in the common case where there's no new
backup.

There's still room for it to be faster. Currently the old imported tree
has to be traversed, to generate the ImportableContents. Which then
gets turned around to generate the new imported tree, which is
identical. So, it would be possible to just return a "no new imports",
or an ImportableContents that has a way to graft in a tree. The latter
is probably too far to go to optimise this, unless other things need it.
The former might be worth it, but it's already pretty fast, since git
ls-tree is pretty fast.
This commit is contained in:
Joey Hess 2020-12-22 14:06:40 -04:00
parent 06ef1b7d68
commit 5d8e4a7c74
No known key found for this signature in database
GPG key ID: DB12DB0FF05F8F38
4 changed files with 98 additions and 29 deletions

View file

@ -1,17 +1,17 @@
{- git ls-tree interface
-
- Copyright 2011-2019 Joey Hess <id@joeyh.name>
- Copyright 2011-2020 Joey Hess <id@joeyh.name>
-
- Licensed under the GNU AGPL version 3 or higher.
-}
{-# LANGUAGE BangPatterns #-}
module Git.LsTree (
TreeItem(..),
LsTreeMode(..),
lsTree,
lsTree',
lsTreeStrict,
lsTreeStrict',
lsTreeParams,
lsTreeFiles,
parseLsTree,
@ -30,6 +30,7 @@ import Data.Either
import System.Posix.Types
import qualified Data.ByteString as S
import qualified Data.ByteString.Lazy as L
import qualified Data.Attoparsec.ByteString as AS
import qualified Data.Attoparsec.ByteString.Lazy as A
import qualified Data.Attoparsec.ByteString.Char8 as A8
@ -38,7 +39,7 @@ data TreeItem = TreeItem
, typeobj :: S.ByteString
, sha :: Ref
, file :: TopFilePath
} deriving Show
} deriving (Show)
data LsTreeMode = LsTreeRecursive | LsTreeNonRecursive
@ -51,6 +52,13 @@ lsTree' ps lsmode t repo = do
(l, cleanup) <- pipeNullSplit (lsTreeParams lsmode t ps) repo
return (rights (map parseLsTree l), cleanup)
lsTreeStrict :: LsTreeMode -> Ref -> Repo -> IO [TreeItem]
lsTreeStrict = lsTreeStrict' []
lsTreeStrict' :: [CommandParam] -> LsTreeMode -> Ref -> Repo -> IO [TreeItem]
lsTreeStrict' ps lsmode t repo = rights . map parseLsTreeStrict
<$> pipeNullSplitStrict (lsTreeParams lsmode t ps) repo
lsTreeParams :: LsTreeMode -> Ref -> [CommandParam] -> [CommandParam]
lsTreeParams lsmode r ps =
[ Param "ls-tree"
@ -83,6 +91,13 @@ parseLsTree b = case A.parse parserLsTree b of
A.Done _ r -> Right r
A.Fail _ _ err -> Left err
parseLsTreeStrict :: S.ByteString -> Either String TreeItem
parseLsTreeStrict b = go (AS.parse parserLsTree b)
where
go (AS.Done _ r) = Right r
go (AS.Fail _ _ err) = Left err
go (AS.Partial c) = go (c mempty)
{- Parses a line of ls-tree output, in format:
- mode SP type SP sha TAB file
-

View file

@ -135,7 +135,12 @@ fmtObjectType CommitObject = "commit"
fmtObjectType TreeObject = "tree"
{- Types of items in a tree. -}
data TreeItemType = TreeFile | TreeExecutable | TreeSymlink | TreeSubmodule
data TreeItemType
= TreeFile
| TreeExecutable
| TreeSymlink
| TreeSubmodule
| TreeSubtree
deriving (Eq, Show)
{- Git uses magic numbers to denote the type of a tree item. -}
@ -144,6 +149,7 @@ readTreeItemType "100644" = Just TreeFile
readTreeItemType "100755" = Just TreeExecutable
readTreeItemType "120000" = Just TreeSymlink
readTreeItemType "160000" = Just TreeSubmodule
readTreeItemType "040000" = Just TreeSubtree
readTreeItemType _ = Nothing
fmtTreeItemType :: TreeItemType -> S.ByteString
@ -151,12 +157,14 @@ fmtTreeItemType TreeFile = "100644"
fmtTreeItemType TreeExecutable = "100755"
fmtTreeItemType TreeSymlink = "120000"
fmtTreeItemType TreeSubmodule = "160000"
fmtTreeItemType TreeSubtree = "040000"
toTreeItemType :: FileMode -> Maybe TreeItemType
toTreeItemType 0o100644 = Just TreeFile
toTreeItemType 0o100755 = Just TreeExecutable
toTreeItemType 0o120000 = Just TreeSymlink
toTreeItemType 0o160000 = Just TreeSubmodule
toTreeItemType 0o040000 = Just TreeSubtree
toTreeItemType _ = Nothing
fromTreeItemType :: TreeItemType -> FileMode
@ -164,6 +172,7 @@ fromTreeItemType TreeFile = 0o100644
fromTreeItemType TreeExecutable = 0o100755
fromTreeItemType TreeSymlink = 0o120000
fromTreeItemType TreeSubmodule = 0o160000
fromTreeItemType TreeSubtree = 0o040000
data Commit = Commit
{ commitTree :: Sha