git-annex/Command/Init.hs
Joey Hess f09a248fe2
init: Support --json and --json-error-messages
Dunno how useful this will be, since about all that's accessible from
the json is whether it succeeded or failed, and the error messages
which were already on stderr.

Note that, when autoenabling a special remote, it would be possible for
one to stop and prompt or output not using Messages and so not output as
part of the json. I don't think that happens, but I'm not 100% sure
something doesn't manage to break it. Of course, the same could be the
case for commands that transfer objects. Using Annex.Init.autoEnableSpecialRemotes
in --json mode would avoid the problem, but I've chosen to wait until I
know it's needed to use it.

Sponsored-By: the NIH-funded NICEMAN (ReproNim TR&D3) project
2023-05-08 14:58:08 -04:00

90 lines
2.5 KiB
Haskell

{- git-annex command
-
- Copyright 2010-2020 Joey Hess <id@joeyh.name>
-
- Licensed under the GNU AGPL version 3 or higher.
-}
{-# LANGUAGE OverloadedStrings #-}
module Command.Init where
import Command
import Annex.Init
import Annex.Version
import Types.RepoVersion
import qualified Annex.SpecialRemote
import Control.Monad.Fail as Fail (MonadFail(..))
import qualified Data.Map as M
cmd :: Command
cmd = dontCheck repoExists $ withAnnexOptions [jsonOptions] $
command "init" SectionSetup "initialize git-annex"
paramDesc (seek <$$> optParser)
data InitOptions = InitOptions
{ initDesc :: String
, initVersion :: Maybe RepoVersion
, autoEnableOnly :: Bool
, noAutoEnable :: Bool
}
optParser :: CmdParamsDesc -> Parser InitOptions
optParser desc = InitOptions
<$> (unwords <$> cmdParams desc)
<*> optional (option (str >>= parseRepoVersion)
( long "version" <> metavar paramValue
<> help "Override default annex.version"
))
<*> switch
( long "autoenable"
<> help "only enable special remotes configured with autoenable=true"
)
<*> switch
( long "no-autoenable"
<> help "do not enable special remotes configured with autoenable=true"
)
parseRepoVersion :: MonadFail m => String -> m RepoVersion
parseRepoVersion s = case RepoVersion <$> readish s of
Nothing -> Fail.fail $ "version parse error"
Just v
| v `elem` supportedVersions -> return v
| otherwise -> case M.lookup v autoUpgradeableVersions of
Just v' -> return v'
Nothing -> Fail.fail $ s ++ " is not a currently supported repository version"
seek :: InitOptions -> CommandSeek
seek = commandAction . start
start :: InitOptions -> CommandStart
start os
| autoEnableOnly os =
starting "init" (ActionItemOther (Just "autoenable")) si $
performAutoEnableOnly
| otherwise =
starting "init" (ActionItemOther (Just $ UnquotedString $ initDesc os)) si $
perform os
where
si = SeekInput []
perform :: InitOptions -> CommandPerform
perform os = do
case initVersion os of
Nothing -> noop
Just wantversion -> getVersion >>= \case
Just v | v /= wantversion ->
giveup $ "This repository is already a initialized with version " ++ show (fromRepoVersion v) ++ ", not changing to requested version."
_ -> noop
initialize
(if null (initDesc os) then Nothing else Just (initDesc os))
(initVersion os)
unless (noAutoEnable os)
Annex.SpecialRemote.autoEnable
next $ return True
performAutoEnableOnly :: CommandPerform
performAutoEnableOnly = do
Annex.SpecialRemote.autoEnable
next $ return True