2013-12-15 18:46:29 +00:00
|
|
|
{- git-annex command
|
|
|
|
-
|
2020-11-12 18:08:13 +00:00
|
|
|
- Copyright 2013-2020 Joey Hess <id@joeyh.name>
|
2013-12-15 18:46:29 +00:00
|
|
|
-
|
2019-03-13 19:48:14 +00:00
|
|
|
- Licensed under the GNU AGPL version 3 or higher.
|
2013-12-15 18:46:29 +00:00
|
|
|
-}
|
|
|
|
|
2023-04-11 18:57:09 +00:00
|
|
|
{-# LANGUAGE OverloadedStrings #-}
|
|
|
|
|
2013-12-15 18:46:29 +00:00
|
|
|
module Command.ExamineKey where
|
|
|
|
|
|
|
|
import Command
|
|
|
|
import qualified Utility.Format
|
2020-11-16 13:56:32 +00:00
|
|
|
import Command.Find (parseFormatOption, showFormatted, formatVars)
|
2020-11-12 17:02:31 +00:00
|
|
|
import Annex.Link
|
2020-11-12 18:08:13 +00:00
|
|
|
import Backend
|
|
|
|
import Types.Backend
|
|
|
|
import Types.Key
|
2023-04-12 17:48:21 +00:00
|
|
|
import Utility.Terminal
|
2020-11-12 18:08:13 +00:00
|
|
|
|
|
|
|
import Data.Char
|
|
|
|
import qualified Data.ByteString as B
|
2013-12-15 18:46:29 +00:00
|
|
|
|
2015-07-08 16:33:27 +00:00
|
|
|
cmd :: Command
|
2016-09-05 16:26:59 +00:00
|
|
|
cmd = noCommit $ noMessages $ dontCheck repoExists $
|
2022-06-29 17:28:08 +00:00
|
|
|
withAnnexOptions [jsonOptions] $
|
2016-09-05 16:26:59 +00:00
|
|
|
command "examinekey" SectionPlumbing
|
|
|
|
"prints information from a key"
|
|
|
|
(paramRepeating paramKey)
|
2020-11-12 18:08:13 +00:00
|
|
|
(batchable run optParser)
|
|
|
|
|
|
|
|
data ExamineOptions = ExamineOptions
|
|
|
|
{ format :: Maybe Utility.Format.Format
|
|
|
|
, migrateToBackend :: Maybe (DeferredParse Backend)
|
|
|
|
, associatedFile :: AssociatedFile
|
|
|
|
}
|
2013-12-15 18:46:29 +00:00
|
|
|
|
2020-11-12 18:08:13 +00:00
|
|
|
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
|
|
|
|
|
2020-11-12 17:02:31 +00:00
|
|
|
objectpath <- calcRepo $ gitAnnexLocation k
|
|
|
|
let objectpointer = formatPointer k
|
2023-04-11 18:57:09 +00:00
|
|
|
isterminal <- liftIO $ checkIsTerminal stdout
|
|
|
|
showFormatted isterminal (format o) (serializeKey' k) $
|
2020-11-12 17:02:31 +00:00
|
|
|
[ ("objectpath", fromRawFilePath objectpath)
|
|
|
|
, ("objectpointer", fromRawFilePath objectpointer)
|
2020-11-16 13:56:32 +00:00
|
|
|
] ++ formatVars k af
|
2015-07-12 00:43:45 +00:00
|
|
|
return True
|
2020-11-12 18:08:13 +00:00
|
|
|
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
|
2024-03-01 20:42:02 +00:00
|
|
|
Just fm -> fromMaybe ik <$> fm ik b af False
|
2020-11-12 18:08:13 +00:00
|
|
|
Nothing -> pure ik
|
|
|
|
Nothing -> pure ik
|