git-annex/Command/ExamineKey.hs
Joey Hess e7652b0997
implement URL to VURL migration
This needs the content to be present in order to hash it. But it's not
possible for a module used by Backend.URL to call inAnnex because that
would entail a dependency loop. So instead, rely on the fact that
Command.Migrate calls inAnnex before performing a migration.

But, Command.ExamineKey calls fastMigrate and the key may or may not
exist, and it's not wanting to actually perform a migration in any case.
To handle that, had to add an additional value to fastMigrate to
indicate whether the content is inAnnex.

Factored generateEquivilantKey out of Remote.Web.

Note that migrateFromURLToVURL hardcodes use of the SHA256E backend.
It would have been difficult not to, given all the dependency loop
issues. But --backend and annex.backend are used to tell git-annex
migrate to use VURL in any case, so there's no config knob that
the user could expect to configure that.

Sponsored-by: Brock Spratlen on Patreon
2024-03-01 16:42:02 -04:00

83 lines
2.4 KiB
Haskell

{- git-annex command
-
- Copyright 2013-2020 Joey Hess <id@joeyh.name>
-
- Licensed under the GNU AGPL version 3 or higher.
-}
{-# LANGUAGE OverloadedStrings #-}
module Command.ExamineKey where
import Command
import qualified Utility.Format
import Command.Find (parseFormatOption, showFormatted, formatVars)
import Annex.Link
import Backend
import Types.Backend
import Types.Key
import Utility.Terminal
import Data.Char
import qualified Data.ByteString as B
cmd :: Command
cmd = noCommit $ noMessages $ dontCheck repoExists $
withAnnexOptions [jsonOptions] $
command "examinekey" SectionPlumbing
"prints information from a key"
(paramRepeating paramKey)
(batchable run optParser)
data ExamineOptions = ExamineOptions
{ format :: Maybe Utility.Format.Format
, migrateToBackend :: Maybe (DeferredParse Backend)
, associatedFile :: AssociatedFile
}
optParser :: Parser ExamineOptions
optParser = ExamineOptions
<$> optional parseFormatOption
<*> (fmap (DeferredParse . tobackend) <$> migrateopt)
<*> (AssociatedFile <$> fileopt)
where
fileopt = optional $ strOption
( long "filename" <> metavar paramFile
<> help "file associated with the key"
)
migrateopt = optional $ strOption
( long "migrate-to-backend" <> metavar paramName
<> help "migrate key to other backend when possible"
)
tobackend = lookupBackendVariety . parseKeyVariety . encodeBS
run :: ExamineOptions -> SeekInput -> String -> Annex Bool
run o _ input = do
k <- getkey
objectpath <- calcRepo $ gitAnnexLocation k
let objectpointer = formatPointer k
isterminal <- liftIO $ checkIsTerminal stdout
showFormatted isterminal (format o) (serializeKey' k) $
[ ("objectpath", fromRawFilePath objectpath)
, ("objectpointer", fromRawFilePath objectpointer)
] ++ formatVars k af
return True
where
-- Parse the input, which is either a key, or in batch mode
-- can be "key filename"
(ikb, ifb) = B.break (== (fromIntegral (ord ' '))) (toRawFilePath input)
ifb' = B.drop 1 ifb
ik = fromMaybe (giveup "bad key") (deserializeKey' ikb)
af = if B.null ifb'
then associatedFile o
else AssociatedFile (Just ifb')
getkey = case migrateToBackend o of
Nothing -> pure ik
Just v -> getParsed v >>= \b ->
maybeLookupBackendVariety (fromKey keyVariety ik) >>= \case
Just ib -> case fastMigrate ib of
Just fm -> fromMaybe ik <$> fm ik b af False
Nothing -> pure ik
Nothing -> pure ik