uninit: Support --json and --json-error-messages

Had to convert uninit to do everything that can error out inside a
CommandStart. This was harder than feels nice.

(Also, in passing, converted CommandCheck to use a data type, not a
weird number that it was not clear how it managed to be unique.)

Sponsored-By: the NIH-funded NICEMAN (ReproNim TR&D3) project
This commit is contained in:
Joey Hess 2023-05-11 13:36:59 -04:00
parent 1904cebbb3
commit 271f3b1ab4
No known key found for this signature in database
GPG key ID: DB12DB0FF05F8F38
7 changed files with 128 additions and 77 deletions

View file

@ -41,7 +41,7 @@ git-annex (10.20230408) UNRELEASED; urgency=medium
(addunused, configremote, dead, describe, dropunused, enableremote, (addunused, configremote, dead, describe, dropunused, enableremote,
expire, fix, importfeed, init, initremote, log, merge, migrate, reinit, expire, fix, importfeed, init, initremote, log, merge, migrate, reinit,
reinject, rekey, renameremote, rmurl, semitrust, setpresentkey, trust, reinject, rekey, renameremote, rmurl, semitrust, setpresentkey, trust,
unannex, undo, untrust, unused, upgrade) unannex, undo, uninit, untrust, unused, upgrade)
* log: When --raw-date is used, display only seconds from the epoch, as * log: When --raw-date is used, display only seconds from the epoch, as
documented, omitting a trailing "s" that was included in the output documented, omitting a trailing "s" that was included in the output
before. before.

View file

@ -78,7 +78,7 @@ checkDirectory mdir = do
{- Modifies a Command to check that it is run in either a git-annex {- Modifies a Command to check that it is run in either a git-annex
- repository, or a repository with a gcrypt-id set. -} - repository, or a repository with a gcrypt-id set. -}
gitAnnexShellCheck :: Command -> Command gitAnnexShellCheck :: Command -> Command
gitAnnexShellCheck = addCheck okforshell . dontCheck repoExists gitAnnexShellCheck = addCheck GitAnnexShellOk okforshell . dontCheck repoExists
where where
okforshell = unlessM (isInitialized <||> isJust . gcryptId <$> Annex.getGitConfig) $ okforshell = unlessM (isInitialized <||> isJust . gcryptId <$> Annex.getGitConfig) $
giveup "Not a git-annex or gcrypt repository." giveup "Not a git-annex or gcrypt repository."

View file

@ -125,17 +125,17 @@ commonChecks :: [CommandCheck]
commonChecks = [repoExists] commonChecks = [repoExists]
repoExists :: CommandCheck repoExists :: CommandCheck
repoExists = CommandCheck 0 (ensureInitialized remoteList) repoExists = CommandCheck RepoExists (ensureInitialized remoteList)
notBareRepo :: Command -> Command notBareRepo :: Command -> Command
notBareRepo = addCheck checkNotBareRepo notBareRepo = addCheck CheckNotBareRepo checkNotBareRepo
checkNotBareRepo :: Annex () checkNotBareRepo :: Annex ()
checkNotBareRepo = whenM (fromRepo Git.repoIsLocalBare) $ checkNotBareRepo = whenM (fromRepo Git.repoIsLocalBare) $
giveup "You cannot run this command in a bare repository." giveup "You cannot run this command in a bare repository."
noDaemonRunning :: Command -> Command noDaemonRunning :: Command -> Command
noDaemonRunning = addCheck $ whenM (isJust <$> daemonpid) $ noDaemonRunning = addCheck NoDaemonRunning $ whenM (isJust <$> daemonpid) $
giveup "You cannot run this command while git-annex watch or git-annex assistant is running." giveup "You cannot run this command while git-annex watch or git-annex assistant is running."
where where
daemonpid = liftIO . checkDaemon . fromRawFilePath daemonpid = liftIO . checkDaemon . fromRawFilePath
@ -144,9 +144,9 @@ noDaemonRunning = addCheck $ whenM (isJust <$> daemonpid) $
dontCheck :: CommandCheck -> Command -> Command dontCheck :: CommandCheck -> Command -> Command
dontCheck check cmd = mutateCheck cmd $ \c -> filter (/= check) c dontCheck check cmd = mutateCheck cmd $ \c -> filter (/= check) c
addCheck :: Annex () -> Command -> Command addCheck :: CommandCheckId -> Annex () -> Command -> Command
addCheck check cmd = mutateCheck cmd $ \c -> addCheck cid check cmd = mutateCheck cmd $ \c ->
CommandCheck (length c + 100) check : c CommandCheck cid check : c
mutateCheck :: Command -> ([CommandCheck] -> [CommandCheck]) -> Command mutateCheck :: Command -> ([CommandCheck] -> [CommandCheck]) -> Command
mutateCheck cmd@(Command { cmdcheck = c }) a = cmd { cmdcheck = a c } mutateCheck cmd@(Command { cmdcheck = c }) a = cmd { cmdcheck = a c }

View file

@ -1,6 +1,6 @@
{- git-annex command {- git-annex command
- -
- Copyright 2010-2021 Joey Hess <id@joeyh.name> - Copyright 2010-2023 Joey Hess <id@joeyh.name>
- -
- Licensed under the GNU AGPL version 3 or higher. - Licensed under the GNU AGPL version 3 or higher.
-} -}
@ -11,6 +11,7 @@ import Command
import qualified Git import qualified Git
import qualified Git.Command import qualified Git.Command
import qualified Git.Ref import qualified Git.Ref
import qualified Git.Branch
import qualified Command.Unannex import qualified Command.Unannex
import qualified Annex.Branch import qualified Annex.Branch
import qualified Annex.Queue import qualified Annex.Queue
@ -23,23 +24,60 @@ import Utility.FileMode
import qualified Utility.RawFilePath as R import qualified Utility.RawFilePath as R
import System.PosixCompat.Files (linkCount) import System.PosixCompat.Files (linkCount)
import Control.Concurrent.STM
cmd :: Command cmd :: Command
cmd = addCheck check $ cmd = withAnnexOptions [jsonOptions] $
command "uninit" SectionUtility command "uninit" SectionUtility
"de-initialize git-annex and clean out repository" "de-initialize git-annex and clean out repository"
paramNothing (withParams seek) paramNothing (withParams seek)
check :: Annex () seek :: CmdParams -> CommandSeek
check = do seek = withNothing $ do
b <- current_branch ok <- liftIO $ newTVarIO False
when (b == Just Annex.Branch.name) $ giveup $ let checkok v a = do
"cannot uninit when the " ++ Git.fromRef Annex.Branch.name ++ " branch is checked out" liftIO $ atomically $ writeTVar ok v
top <- fromRepo Git.repoPath () <- a
currdir <- liftIO R.getCurrentDirectory liftIO $ atomically $ readTVar ok
whenM ((/=) <$> liftIO (absPath top) <*> liftIO (absPath currdir)) $ let recordok = do
giveup "can only run uninit from the top of the git repository" liftIO $ atomically $ writeTVar ok True
return True
let recordnotok = liftIO $ atomically $ writeTVar ok False
whenM (checkok False $ commandAction $ checkCanUninit recordok) $ do
let symlinksok = checkok True $ withFilesNotInGit
(CheckGitIgnore False)
(WarnUnmatchWorkTreeItems "uninit")
(checksymlinks recordnotok)
=<< workTreeItems ww []
whenM symlinksok $ do
withFilesInGitAnnex ww (Command.Unannex.seeker True)
=<< workTreeItems ww []
whenM (checkok False $ commandAction $ removeAnnexDir recordok) $
whenM (checkok False $ commandAction $ completeUnitialize recordok) $
liftIO exitSuccess
where where
ww = WarnUnmatchLsFiles "uninit"
checksymlinks recordnotok (_, f) =
commandAction $ lookupKey f >>= \case
Nothing -> stop
Just k -> startCheckIncomplete recordnotok f k
checkCanUninit :: CommandCleanup -> CommandStart
checkCanUninit recordok =
starting "uninit check" (ActionItemOther Nothing) (SeekInput []) $ do
runchecks
next recordok
where
runchecks = do
b <- current_branch
when (b == Just Annex.Branch.name) $ giveup $
"cannot uninit when the " ++ Git.fromRef Annex.Branch.name ++ " branch is checked out"
top <- fromRepo Git.repoPath
currdir <- liftIO R.getCurrentDirectory
whenM ((/=) <$> liftIO (absPath top) <*> liftIO (absPath currdir)) $
giveup "can only run uninit from the top of the git repository"
current_branch = current_branch =
ifM (inRepo Git.Ref.headExists) ifM (inRepo Git.Ref.headExists)
( Just . Git.Ref . encodeBS . Prelude.head . lines . decodeBS <$> revhead ( Just . Git.Ref . encodeBS . Prelude.head . lines . decodeBS <$> revhead
@ -48,65 +86,49 @@ check = do
revhead = inRepo $ Git.Command.pipeReadStrict revhead = inRepo $ Git.Command.pipeReadStrict
[Param "rev-parse", Param "--abbrev-ref", Param "HEAD"] [Param "rev-parse", Param "--abbrev-ref", Param "HEAD"]
seek :: CmdParams -> CommandSeek
seek = withNothing $ do
withFilesNotInGit
(CheckGitIgnore False)
(WarnUnmatchWorkTreeItems "uninit")
checksymlinks
=<< workTreeItems ww []
withFilesInGitAnnex ww (Command.Unannex.seeker True)
=<< workTreeItems ww []
finish
where
ww = WarnUnmatchLsFiles "uninit"
checksymlinks (_, f) =
commandAction $ lookupKey f >>= \case
Nothing -> stop
Just k -> startCheckIncomplete (fromRawFilePath f) k
{- git annex symlinks that are not checked into git could be left by an {- git annex symlinks that are not checked into git could be left by an
- interrupted add. -} - interrupted add. -}
startCheckIncomplete :: FilePath -> Key -> CommandStart startCheckIncomplete :: Annex () -> RawFilePath -> Key -> CommandStart
startCheckIncomplete file _ = giveup $ unlines startCheckIncomplete recordnotok file key =
[ file ++ " points to annexed content, but is not checked into git." starting "uninit check" (mkActionItem (file, key)) (SeekInput []) $ do
, "Perhaps this was left behind by an interrupted git annex add?" recordnotok
, "Not continuing with uninit; either delete or git annex add the file and retry." giveup $ unlines err
] where
err =
[ fromRawFilePath file ++ " points to annexed content, but is not checked into git."
, "Perhaps this was left behind by an interrupted git annex add?"
, "Not continuing with uninit; either delete or git annex add the file and retry."
]
finish :: Annex () removeAnnexDir :: CommandCleanup -> CommandStart
finish = do removeAnnexDir recordok = do
Annex.Queue.flush Annex.Queue.flush
annexdir <- fromRawFilePath <$> fromRepo gitAnnexDir annexdir <- fromRawFilePath <$> fromRepo gitAnnexDir
annexobjectdir <- fromRepo gitAnnexObjectDir annexobjectdir <- fromRepo gitAnnexObjectDir
leftovers <- removeUnannexed =<< listKeys InAnnex starting ("uninit objects") (ActionItemOther (Just (QuotedPath annexobjectdir))) (SeekInput []) $ do
prepareRemoveAnnexDir annexdir leftovers <- removeUnannexed =<< listKeys InAnnex
if null leftovers prepareRemoveAnnexDir annexdir
then liftIO $ removeDirectoryRecursive annexdir if null leftovers
else giveup $ unlines then do
[ "Not fully uninitialized" liftIO $ removeDirectoryRecursive annexdir
, "Some annexed data is still left in " ++ fromRawFilePath annexobjectdir next recordok
, "This may include deleted files, or old versions of modified files." else giveup $ unlines
, "" [ "Not fully uninitialized"
, "If you don't care about preserving the data, just delete the" , "Some annexed data is still left in " ++ fromRawFilePath annexobjectdir
, "directory." , "This may include deleted files, or old versions of modified files."
, "" , ""
, "Or, you can move it to another location, in case it turns out" , "If you don't care about preserving the data, just delete the"
, "something in there is important." , "directory."
, "" , ""
, "Or, you can run `git annex unused` followed by `git annex dropunused`" , "Or, you can move it to another location, in case it turns out"
, "to remove data that is not used by any tag or branch, which might" , "something in there is important."
, "take care of all the data." , ""
, "" , "Or, you can run `git annex unused` followed by `git annex dropunused`"
, "Then run `git annex uninit` again to finish." , "to remove data that is not used by any tag or branch, which might"
] , "take care of all the data."
uninitialize , ""
-- avoid normal shutdown , "Then run `git annex uninit` again to finish."
saveState False ]
whenM (inRepo $ Git.Ref.exists Annex.Branch.fullname) $
inRepo $ Git.Command.run
[Param "branch", Param "-D", Param $ Git.fromRef Annex.Branch.name]
liftIO exitSuccess
{- Turn on write bits in all remaining files in the annex directory, in {- Turn on write bits in all remaining files in the annex directory, in
- preparation for removal. - preparation for removal.
@ -140,3 +162,17 @@ removeUnannexed = go []
enoughlinks f = catchBoolIO $ do enoughlinks f = catchBoolIO $ do
s <- R.getFileStatus f s <- R.getFileStatus f
return $ linkCount s > 1 return $ linkCount s > 1
completeUnitialize :: CommandCleanup -> CommandStart
completeUnitialize recordok =
starting ("uninit finish") (ActionItemOther Nothing) (SeekInput []) $ do
uninitialize
removeAnnexBranch
next recordok
removeAnnexBranch :: Annex ()
removeAnnexBranch = do
-- avoid normal shutdown commit to the branch
saveState False
whenM (inRepo $ Git.Ref.exists Annex.Branch.fullname) $
inRepo $ Git.Branch.delete Annex.Branch.name

View file

@ -24,7 +24,7 @@ import Types.ActionItem
type CommandParser = Parser CommandSeek type CommandParser = Parser CommandSeek
{- b. The check stage runs checks, that error out if {- b. The check stage runs checks, that error out if
- anything prevents the command from running. -} - anything prevents the command from running. -}
data CommandCheck = CommandCheck { idCheck :: Int, runCheck :: Annex () } data CommandCheck = CommandCheck { idCheck :: CommandCheckId, runCheck :: Annex () }
{- c. The seek stage is passed input from the parser, looks through {- c. The seek stage is passed input from the parser, looks through
- the repo to find things to act on (ie, new files to add), and - the repo to find things to act on (ie, new files to add), and
- runs commandAction to handle all necessary actions. -} - runs commandAction to handle all necessary actions. -}
@ -136,3 +136,10 @@ descSection SectionAddOn = "Addon commands"
newtype DryRun = DryRun Bool newtype DryRun = DryRun Bool
deriving (Show) deriving (Show)
data CommandCheckId
= CheckNotBareRepo
| RepoExists
| NoDaemonRunning
| GitAnnexShellOk
deriving (Show, Ord, Eq)

View file

@ -14,7 +14,17 @@ git repository plus the previously annexed files.
# OPTIONS # OPTIONS
* The [[git-annex-common-options]](1) can be used. * `--json`
Enable JSON output. This is intended to be parsed by programs that use
git-annex. Each line of output is a JSON object.
* `--json-error-messages`
Messages that would normally be output to standard error are included in
the JSON instead.
* Also the [[git-annex-common-options]](1) can be used.
# SEE ALSO # SEE ALSO

View file

@ -42,12 +42,10 @@ These commands have been updated to support --json:
* git-annex-initremote * git-annex-initremote
* git-annex-enableremote * git-annex-enableremote
* git-annex-configremote * git-annex-configremote
* git-annex-uninit
These commands could support json, but I punted: These commands could support json, but I punted:
* git-annex-uninit (hard to support --json-error-messages because it does
pre-check and post-unannex things that are not usual actions and so would
not show as json objects without more work)
* git-annex-version (--raw already exists, and the output is fairly machine * git-annex-version (--raw already exists, and the output is fairly machine
parseable already. It would be possible to jsonize the output to make it parseable already. It would be possible to jsonize the output to make it
possibly more machine parseable. But I'm doubtful that would be useful. possibly more machine parseable. But I'm doubtful that would be useful.