81d402216d
This will speed up the common case where a Key is deserialized from disk, but is then serialized to build eg, the path to the annex object. Previously attempted in4536c93bb2
and reverted in96aba8eff7
. The problems mentioned in the latter commit are addressed now: Read/Show of KeyData is backwards-compatible with Read/Show of Key from before this change, so Types.Distribution will keep working. The Eq instance is fixed. Also, Key has smart constructors, avoiding needing to remember to update the cached serialization. Used git-annex benchmark: find is 7% faster whereis is 3% faster get when all files are already present is 5% faster Generally, the benchmarks are running 0.1 seconds faster per 2000 files, on a ram disk in my laptop.
53 lines
1.3 KiB
Haskell
53 lines
1.3 KiB
Haskell
{- git-annex exports
|
|
-
|
|
- Copyright 2017 Joey Hess <id@joeyh.name>
|
|
-
|
|
- Licensed under the GNU AGPL version 3 or higher.
|
|
-}
|
|
|
|
module Annex.Export where
|
|
|
|
import Annex
|
|
import Annex.CatFile
|
|
import Types
|
|
import Types.Key
|
|
import qualified Git
|
|
import qualified Types.Remote as Remote
|
|
import Messages
|
|
import Utility.FileSystemEncoding
|
|
|
|
import Control.Applicative
|
|
import Data.Maybe
|
|
import Prelude
|
|
|
|
-- An export includes both annexed files and files stored in git.
|
|
-- For the latter, a SHA1 key is synthesized.
|
|
data ExportKey = AnnexKey Key | GitKey Key
|
|
deriving (Show, Eq, Ord)
|
|
|
|
asKey :: ExportKey -> Key
|
|
asKey (AnnexKey k) = k
|
|
asKey (GitKey k) = k
|
|
|
|
exportKey :: Git.Sha -> Annex ExportKey
|
|
exportKey sha = mk <$> catKey sha
|
|
where
|
|
mk (Just k) = AnnexKey k
|
|
mk Nothing = GitKey $ mkKey $ \k -> k
|
|
{ keyName = encodeBS $ Git.fromRef sha
|
|
, keyVariety = SHA1Key (HasExt False)
|
|
, keySize = Nothing
|
|
, keyMtime = Nothing
|
|
, keyChunkSize = Nothing
|
|
, keyChunkNum = Nothing
|
|
}
|
|
|
|
warnExportImportConflict :: Remote -> Annex ()
|
|
warnExportImportConflict r = do
|
|
ops <- Remote.isImportSupported r >>= return . \case
|
|
True -> "exported to and/or imported from"
|
|
False -> "exported to"
|
|
toplevelWarning True $
|
|
"Conflict detected. Different trees have been " ++ ops ++
|
|
Remote.name r ++
|
|
". Use git-annex export to resolve this conflict."
|