rename getKey to genKey
for consistency with external backend protocol
This commit is contained in:
parent
d1300eca2e
commit
c4cc2cdf4c
8 changed files with 13 additions and 13 deletions
|
@ -551,7 +551,7 @@ gitAnnexAssistantDefaultDir = "annex"
|
||||||
{- Sanitizes a String that will be used as part of a Key's keyName,
|
{- Sanitizes a String that will be used as part of a Key's keyName,
|
||||||
- dealing with characters that cause problems.
|
- dealing with characters that cause problems.
|
||||||
-
|
-
|
||||||
- This is used when a new Key is initially being generated, eg by getKey.
|
- This is used when a new Key is initially being generated, eg by genKey.
|
||||||
- Unlike keyFile and fileKey, it does not need to be a reversable
|
- Unlike keyFile and fileKey, it does not need to be a reversable
|
||||||
- escaping. Also, it's ok to change this to add more problematic
|
- escaping. Also, it's ok to change this to add more problematic
|
||||||
- characters later. Unlike changing keyFile, which could result in the
|
- characters later. Unlike changing keyFile, which could result in the
|
||||||
|
|
|
@ -56,7 +56,7 @@ defaultBackend = maybe cache return =<< Annex.getState Annex.backend
|
||||||
genKey :: KeySource -> MeterUpdate -> Maybe Backend -> Annex (Key, Backend)
|
genKey :: KeySource -> MeterUpdate -> Maybe Backend -> Annex (Key, Backend)
|
||||||
genKey source meterupdate preferredbackend = do
|
genKey source meterupdate preferredbackend = do
|
||||||
b <- maybe defaultBackend return preferredbackend
|
b <- maybe defaultBackend return preferredbackend
|
||||||
case B.getKey b of
|
case B.genKey b of
|
||||||
Just a -> do
|
Just a -> do
|
||||||
k <- a source meterupdate
|
k <- a source meterupdate
|
||||||
return (makesane k, b)
|
return (makesane k, b)
|
||||||
|
|
|
@ -74,7 +74,7 @@ backends = concatMap (\h -> [genBackendE h, genBackend h]) hashes
|
||||||
genBackend :: Hash -> Backend
|
genBackend :: Hash -> Backend
|
||||||
genBackend hash = Backend
|
genBackend hash = Backend
|
||||||
{ backendVariety = hashKeyVariety hash (HasExt False)
|
{ backendVariety = hashKeyVariety hash (HasExt False)
|
||||||
, getKey = Just (keyValue hash)
|
, genKey = Just (keyValue hash)
|
||||||
, verifyKeyContent = Just $ checkKeyChecksum hash
|
, verifyKeyContent = Just $ checkKeyChecksum hash
|
||||||
, canUpgradeKey = Just needsUpgrade
|
, canUpgradeKey = Just needsUpgrade
|
||||||
, fastMigrate = Just trivialMigrate
|
, fastMigrate = Just trivialMigrate
|
||||||
|
@ -85,7 +85,7 @@ genBackend hash = Backend
|
||||||
genBackendE :: Hash -> Backend
|
genBackendE :: Hash -> Backend
|
||||||
genBackendE hash = (genBackend hash)
|
genBackendE hash = (genBackend hash)
|
||||||
{ backendVariety = hashKeyVariety hash (HasExt True)
|
{ backendVariety = hashKeyVariety hash (HasExt True)
|
||||||
, getKey = Just (keyValueE hash)
|
, genKey = Just (keyValueE hash)
|
||||||
}
|
}
|
||||||
|
|
||||||
hashKeyVariety :: Hash -> HasExt -> KeyVariety
|
hashKeyVariety :: Hash -> HasExt -> KeyVariety
|
||||||
|
@ -308,10 +308,10 @@ md5Hasher = show . md5
|
||||||
testKeyBackend :: Backend
|
testKeyBackend :: Backend
|
||||||
testKeyBackend =
|
testKeyBackend =
|
||||||
let b = genBackendE (SHA2Hash (HashSize 256))
|
let b = genBackendE (SHA2Hash (HashSize 256))
|
||||||
gk = case getKey b of
|
gk = case genKey b of
|
||||||
Nothing -> Nothing
|
Nothing -> Nothing
|
||||||
Just f -> Just (\ks p -> addE <$> f ks p)
|
Just f -> Just (\ks p -> addE <$> f ks p)
|
||||||
in b { getKey = gk }
|
in b { genKey = gk }
|
||||||
where
|
where
|
||||||
addE k = alterKey k $ \d -> d
|
addE k = alterKey k $ \d -> d
|
||||||
{ keyName = keyName d <> longext
|
{ keyName = keyName d <> longext
|
||||||
|
|
|
@ -21,7 +21,7 @@ backends = [backend]
|
||||||
backend :: Backend
|
backend :: Backend
|
||||||
backend = Backend
|
backend = Backend
|
||||||
{ backendVariety = URLKey
|
{ backendVariety = URLKey
|
||||||
, getKey = Nothing
|
, genKey = Nothing
|
||||||
, verifyKeyContent = Nothing
|
, verifyKeyContent = Nothing
|
||||||
, canUpgradeKey = Nothing
|
, canUpgradeKey = Nothing
|
||||||
, fastMigrate = Nothing
|
, fastMigrate = Nothing
|
||||||
|
|
|
@ -24,7 +24,7 @@ backends = [backend]
|
||||||
backend :: Backend
|
backend :: Backend
|
||||||
backend = Backend
|
backend = Backend
|
||||||
{ backendVariety = WORMKey
|
{ backendVariety = WORMKey
|
||||||
, getKey = Just keyValue
|
, genKey = Just keyValue
|
||||||
, verifyKeyContent = Nothing
|
, verifyKeyContent = Nothing
|
||||||
, canUpgradeKey = Just needsUpgrade
|
, canUpgradeKey = Just needsUpgrade
|
||||||
, fastMigrate = Just removeProblemChars
|
, fastMigrate = Just removeProblemChars
|
||||||
|
|
|
@ -13,7 +13,7 @@ import Command
|
||||||
import qualified Annex
|
import qualified Annex
|
||||||
import qualified Remote
|
import qualified Remote
|
||||||
import qualified Types.Remote as Remote
|
import qualified Types.Remote as Remote
|
||||||
import qualified Types.Backend as Backend
|
import qualified Types.Backend
|
||||||
import Types.KeySource
|
import Types.KeySource
|
||||||
import Annex.Content
|
import Annex.Content
|
||||||
import Annex.WorkTree
|
import Annex.WorkTree
|
||||||
|
@ -290,7 +290,7 @@ test runannex mkr mkk =
|
||||||
present r k b = (== Right b) <$> Remote.hasKey r k
|
present r k b = (== Right b) <$> Remote.hasKey r k
|
||||||
fsck _ k = case maybeLookupBackendVariety (fromKey keyVariety k) of
|
fsck _ k = case maybeLookupBackendVariety (fromKey keyVariety k) of
|
||||||
Nothing -> return True
|
Nothing -> return True
|
||||||
Just b -> case Backend.verifyKeyContent b of
|
Just b -> case Types.Backend.verifyKeyContent b of
|
||||||
Nothing -> return True
|
Nothing -> return True
|
||||||
Just verifier -> verifier k (serializeKey k)
|
Just verifier -> verifier k (serializeKey k)
|
||||||
get r k = getViaTmp (Remote.retrievalSecurityPolicy r) (RemoteVerify r) k $ \dest ->
|
get r k = getViaTmp (Remote.retrievalSecurityPolicy r) (RemoteVerify r) k $ \dest ->
|
||||||
|
@ -432,7 +432,7 @@ randKey sz = withTmpFile "randkey" $ \f h -> do
|
||||||
, contentLocation = toRawFilePath f
|
, contentLocation = toRawFilePath f
|
||||||
, inodeCache = Nothing
|
, inodeCache = Nothing
|
||||||
}
|
}
|
||||||
k <- case Backend.getKey Backend.Hash.testKeyBackend of
|
k <- case Types.Backend.genKey Backend.Hash.testKeyBackend of
|
||||||
Just a -> a ks nullMeterUpdate
|
Just a -> a ks nullMeterUpdate
|
||||||
Nothing -> giveup "failed to generate random key (backend problem)"
|
Nothing -> giveup "failed to generate random key (backend problem)"
|
||||||
_ <- moveAnnex k f
|
_ <- moveAnnex k f
|
||||||
|
|
|
@ -584,7 +584,7 @@ backend_ :: String -> Types.Backend
|
||||||
backend_ = Backend.lookupBackendVariety . Types.Key.parseKeyVariety . encodeBS
|
backend_ = Backend.lookupBackendVariety . Types.Key.parseKeyVariety . encodeBS
|
||||||
|
|
||||||
getKey :: Types.Backend -> FilePath -> IO Types.Key
|
getKey :: Types.Backend -> FilePath -> IO Types.Key
|
||||||
getKey b f = case Types.Backend.getKey b of
|
getKey b f = case Types.Backend.genKey b of
|
||||||
Just a -> annexeval $ a ks Utility.Metered.nullMeterUpdate
|
Just a -> annexeval $ a ks Utility.Metered.nullMeterUpdate
|
||||||
Nothing -> error "internal"
|
Nothing -> error "internal"
|
||||||
where
|
where
|
||||||
|
|
|
@ -17,7 +17,7 @@ import Utility.FileSystemEncoding
|
||||||
|
|
||||||
data BackendA a = Backend
|
data BackendA a = Backend
|
||||||
{ backendVariety :: KeyVariety
|
{ backendVariety :: KeyVariety
|
||||||
, getKey :: Maybe (KeySource -> MeterUpdate -> a Key)
|
, genKey :: Maybe (KeySource -> MeterUpdate -> a Key)
|
||||||
-- Verifies the content of a key using a hash. This does not need
|
-- Verifies the content of a key using a hash. This does not need
|
||||||
-- to be cryptographically secure.
|
-- to be cryptographically secure.
|
||||||
, verifyKeyContent :: Maybe (Key -> FilePath -> a Bool)
|
, verifyKeyContent :: Maybe (Key -> FilePath -> a Bool)
|
||||||
|
|
Loading…
Reference in a new issue