2012-03-15 16:00:19 +00:00
|
|
|
{- git-annex-shell main program
|
|
|
|
-
|
2018-03-07 19:15:23 +00:00
|
|
|
- Copyright 2010-2018 Joey Hess <id@joeyh.name>
|
2012-03-15 16:00:19 +00:00
|
|
|
-
|
2019-03-13 19:48:14 +00:00
|
|
|
- Licensed under the GNU AGPL version 3 or higher.
|
2012-03-15 16:00:19 +00:00
|
|
|
-}
|
|
|
|
|
2014-01-26 20:25:55 +00:00
|
|
|
module CmdLine.GitAnnexShell where
|
2012-03-15 16:00:19 +00:00
|
|
|
|
2016-01-20 20:36:33 +00:00
|
|
|
import Annex.Common
|
2012-03-15 16:00:19 +00:00
|
|
|
import qualified Git.Construct
|
2015-03-06 01:45:42 +00:00
|
|
|
import qualified Git.Config
|
2012-03-15 16:00:19 +00:00
|
|
|
import CmdLine
|
2015-07-10 06:18:08 +00:00
|
|
|
import CmdLine.GlobalSetter
|
2012-03-15 16:00:19 +00:00
|
|
|
import Command
|
|
|
|
import Annex.UUID
|
2015-08-05 18:09:25 +00:00
|
|
|
import CmdLine.GitAnnexShell.Checks
|
2014-01-26 20:32:55 +00:00
|
|
|
import CmdLine.GitAnnexShell.Fields
|
2013-09-24 21:25:47 +00:00
|
|
|
import Remote.GCrypt (getGCryptUUID)
|
2018-05-25 17:17:56 +00:00
|
|
|
import P2P.Protocol (ServerMode(..))
|
2012-03-15 16:00:19 +00:00
|
|
|
|
|
|
|
import qualified Command.ConfigList
|
|
|
|
import qualified Command.InAnnex
|
2015-10-08 18:47:46 +00:00
|
|
|
import qualified Command.LockContent
|
2012-03-15 16:00:19 +00:00
|
|
|
import qualified Command.DropKey
|
|
|
|
import qualified Command.RecvKey
|
|
|
|
import qualified Command.SendKey
|
2012-09-21 20:23:25 +00:00
|
|
|
import qualified Command.TransferInfo
|
2012-03-15 16:00:19 +00:00
|
|
|
import qualified Command.Commit
|
2014-04-05 20:04:37 +00:00
|
|
|
import qualified Command.NotifyChanges
|
2013-10-01 21:20:51 +00:00
|
|
|
import qualified Command.GCryptSetup
|
2018-03-07 19:15:23 +00:00
|
|
|
import qualified Command.P2PStdIO
|
2012-03-15 16:00:19 +00:00
|
|
|
|
2018-05-25 17:17:56 +00:00
|
|
|
import qualified Data.Map as M
|
2012-03-15 16:00:19 +00:00
|
|
|
|
2018-05-25 17:17:56 +00:00
|
|
|
cmdsMap :: M.Map ServerMode [Command]
|
|
|
|
cmdsMap = M.fromList $ map mk
|
|
|
|
[ (ServeReadOnly, readonlycmds)
|
|
|
|
, (ServeAppendOnly, appendcmds)
|
|
|
|
, (ServeReadWrite, allcmds)
|
2018-03-07 19:15:23 +00:00
|
|
|
]
|
2012-11-11 04:51:07 +00:00
|
|
|
where
|
2021-02-02 19:55:45 +00:00
|
|
|
readonlycmds = map addGlobalOptions
|
2018-05-25 17:17:56 +00:00
|
|
|
[ Command.ConfigList.cmd
|
|
|
|
, gitAnnexShellCheck Command.InAnnex.cmd
|
|
|
|
, gitAnnexShellCheck Command.LockContent.cmd
|
|
|
|
, gitAnnexShellCheck Command.SendKey.cmd
|
|
|
|
, gitAnnexShellCheck Command.TransferInfo.cmd
|
|
|
|
, gitAnnexShellCheck Command.NotifyChanges.cmd
|
|
|
|
-- p2pstdio checks the enviroment variables to
|
|
|
|
-- determine the security policy to use
|
|
|
|
, gitAnnexShellCheck Command.P2PStdIO.cmd
|
|
|
|
]
|
2021-02-02 19:55:45 +00:00
|
|
|
appendcmds = readonlycmds ++ map addGlobalOptions
|
2018-05-25 17:17:56 +00:00
|
|
|
[ gitAnnexShellCheck Command.RecvKey.cmd
|
|
|
|
, gitAnnexShellCheck Command.Commit.cmd
|
|
|
|
]
|
2021-02-02 19:55:45 +00:00
|
|
|
allcmds = map addGlobalOptions
|
2018-05-25 17:17:56 +00:00
|
|
|
[ gitAnnexShellCheck Command.DropKey.cmd
|
|
|
|
, Command.GCryptSetup.cmd
|
|
|
|
]
|
|
|
|
|
|
|
|
mk (s, l) = (s, map (adddirparam . noMessages) l)
|
2012-11-11 04:51:07 +00:00
|
|
|
adddirparam c = c { cmdparamdesc = "DIRECTORY " ++ cmdparamdesc c }
|
2012-03-15 16:00:19 +00:00
|
|
|
|
2018-05-25 17:17:56 +00:00
|
|
|
cmdsFor :: ServerMode -> [Command]
|
|
|
|
cmdsFor = fromMaybe [] . flip M.lookup cmdsMap
|
|
|
|
|
|
|
|
cmdsList :: [Command]
|
|
|
|
cmdsList = concat $ M.elems cmdsMap
|
|
|
|
|
2021-02-02 19:55:45 +00:00
|
|
|
addGlobalOptions :: Command -> Command
|
|
|
|
addGlobalOptions c = c { cmdglobaloptions = globalOptions ++ cmdglobaloptions c }
|
|
|
|
|
2015-07-10 17:18:46 +00:00
|
|
|
globalOptions :: [GlobalOption]
|
2015-07-10 06:03:03 +00:00
|
|
|
globalOptions =
|
2021-04-06 19:14:00 +00:00
|
|
|
globalOption (setAnnexState . checkUUID) (strOption
|
2015-07-10 04:55:53 +00:00
|
|
|
( long "uuid" <> metavar paramUUID
|
|
|
|
<> help "local repository uuid"
|
2015-07-10 06:03:03 +00:00
|
|
|
))
|
|
|
|
: commonGlobalOptions
|
2012-11-11 04:51:07 +00:00
|
|
|
where
|
2013-09-24 21:25:47 +00:00
|
|
|
checkUUID expected = getUUID >>= check
|
2012-11-11 04:51:07 +00:00
|
|
|
where
|
|
|
|
check u | u == toUUID expected = noop
|
2013-09-24 21:25:47 +00:00
|
|
|
check NoUUID = checkGCryptUUID expected
|
|
|
|
check u = unexpectedUUID expected u
|
2013-09-27 20:21:56 +00:00
|
|
|
checkGCryptUUID expected = check =<< getGCryptUUID True =<< gitRepo
|
2013-09-24 21:25:47 +00:00
|
|
|
where
|
2014-10-09 18:53:13 +00:00
|
|
|
check (Just u) | u == toUUID expected = noop
|
2013-09-24 21:25:47 +00:00
|
|
|
check Nothing = unexpected expected "uninitialized repository"
|
|
|
|
check (Just u) = unexpectedUUID expected u
|
|
|
|
unexpectedUUID expected u = unexpected expected $ "UUID " ++ fromUUID u
|
2016-11-16 01:29:54 +00:00
|
|
|
unexpected expected s = giveup $
|
2013-09-24 21:25:47 +00:00
|
|
|
"expected repository UUID " ++ expected ++ " but found " ++ s
|
2012-03-15 16:00:19 +00:00
|
|
|
|
|
|
|
run :: [String] -> IO ()
|
|
|
|
run [] = failure
|
|
|
|
-- skip leading -c options, passed by eg, ssh
|
|
|
|
run ("-c":p) = run p
|
|
|
|
-- a command can be either a builtin or something to pass to git-shell
|
|
|
|
run c@(cmd:dir:params)
|
|
|
|
| cmd `elem` builtins = builtin cmd dir params
|
|
|
|
| otherwise = external c
|
|
|
|
run c@(cmd:_)
|
|
|
|
-- Handle the case of being the user's login shell. It will be passed
|
|
|
|
-- a single string containing all the real parameters.
|
|
|
|
| "git-annex-shell " `isPrefixOf` cmd = run $ drop 1 $ shellUnEscape cmd
|
|
|
|
| cmd `elem` builtins = failure
|
|
|
|
| otherwise = external c
|
|
|
|
|
|
|
|
builtins :: [String]
|
2018-05-25 17:17:56 +00:00
|
|
|
builtins = map cmdname cmdsList
|
2012-03-15 16:00:19 +00:00
|
|
|
|
|
|
|
builtin :: String -> String -> [String] -> IO ()
|
|
|
|
builtin cmd dir params = do
|
2018-05-25 17:17:56 +00:00
|
|
|
unless (cmd `elem` map cmdname (cmdsFor ServeReadOnly))
|
2015-08-05 18:09:25 +00:00
|
|
|
checkNotReadOnly
|
2018-05-25 17:17:56 +00:00
|
|
|
unless (cmd `elem` map cmdname (cmdsFor ServeAppendOnly))
|
|
|
|
checkNotAppendOnly
|
2012-11-05 15:29:12 +00:00
|
|
|
checkDirectory $ Just dir
|
2013-03-29 00:34:07 +00:00
|
|
|
let (params', fieldparams, opts) = partitionParams params
|
2015-07-08 16:33:27 +00:00
|
|
|
rsyncopts = ("RsyncOptions", unwords opts)
|
|
|
|
fields = rsyncopts : filter checkField (parseFields fieldparams)
|
addon commands
Seems only fair, that, like git runs git-annex, git-annex runs
git-annex-foo.
Implementation relies on O.forwardOptions, so that any options are passed
through to the addon program. Note that this includes options before the
subcommand, eg: git-annex -cx=y foo
Unfortunately, git-annex eats the --help/-h options.
This is because it uses O.hsubparser, which injects that option into each
subcommand. Seems like this should be possible to avoid somehow, to let
commands display their own --help, instead of the dummy one git-annex
displays.
The two step searching mirrors how git works, it makes finding
git-annex-foo fast when "git annex foo" is run, but will also support fuzzy
matching, once findAllAddonCommands gets implemented.
This commit was sponsored by Dr. Land Raider on Patreon.
2021-02-02 20:32:25 +00:00
|
|
|
dispatch False False (cmd : params') cmdsList fields mkrepo
|
2015-07-09 15:49:52 +00:00
|
|
|
"git-annex-shell"
|
|
|
|
"Restricted login shell for git-annex only SSH access"
|
2013-03-29 00:34:07 +00:00
|
|
|
where
|
2015-03-06 01:45:42 +00:00
|
|
|
mkrepo = do
|
2020-11-04 18:20:37 +00:00
|
|
|
r <- Git.Construct.repoAbsPath (toRawFilePath dir)
|
|
|
|
>>= Git.Construct.fromAbsPath
|
2015-03-06 01:45:42 +00:00
|
|
|
Git.Config.read r
|
|
|
|
`catchIO` \_ -> do
|
|
|
|
hn <- fromMaybe "unknown" <$> getHostname
|
2016-11-16 01:29:54 +00:00
|
|
|
giveup $ "failed to read git config of git repository in " ++ hn ++ " on " ++ dir ++ "; perhaps this repository is not set up correctly or has moved"
|
2012-03-15 16:00:19 +00:00
|
|
|
|
|
|
|
external :: [String] -> IO ()
|
|
|
|
external params = do
|
2012-11-05 15:29:12 +00:00
|
|
|
{- Normal git-shell commands all have the directory as their last
|
|
|
|
- parameter. -}
|
2012-11-06 00:15:36 +00:00
|
|
|
let lastparam = lastMaybe =<< shellUnEscape <$> lastMaybe params
|
2013-03-29 00:34:07 +00:00
|
|
|
(params', _, _) = partitionParams params
|
2012-11-06 00:15:36 +00:00
|
|
|
checkDirectory lastparam
|
2012-03-15 16:00:19 +00:00
|
|
|
checkNotLimited
|
2013-03-29 00:34:07 +00:00
|
|
|
unlessM (boolSystem "git-shell" $ map Param $ "-c":params') $
|
2016-11-16 01:29:54 +00:00
|
|
|
giveup "git-shell failed"
|
2012-03-15 16:00:19 +00:00
|
|
|
|
2013-03-29 00:34:07 +00:00
|
|
|
{- Split the input list into 3 groups separated with a double dash --.
|
|
|
|
- Parameters between two -- markers are field settings, in the form:
|
2012-07-02 04:53:00 +00:00
|
|
|
- field=value field=value
|
|
|
|
-
|
2013-03-29 00:34:07 +00:00
|
|
|
- Parameters after the last -- are the command itself and its arguments e.g.,
|
|
|
|
- rsync --bandwidth=100.
|
2012-07-02 04:53:00 +00:00
|
|
|
-}
|
2013-03-29 00:34:07 +00:00
|
|
|
partitionParams :: [String] -> ([String], [String], [String])
|
2012-10-16 05:22:09 +00:00
|
|
|
partitionParams ps = case segment (== "--") ps of
|
2013-03-29 00:34:07 +00:00
|
|
|
params:fieldparams:rest -> ( params, fieldparams, intercalate ["--"] rest )
|
|
|
|
[params] -> (params, [], [])
|
|
|
|
_ -> ([], [], [])
|
2012-07-02 04:53:00 +00:00
|
|
|
|
|
|
|
parseFields :: [String] -> [(String, String)]
|
|
|
|
parseFields = map (separate (== '='))
|
2012-03-15 16:00:19 +00:00
|
|
|
|
2012-07-02 05:31:10 +00:00
|
|
|
{- Only allow known fields to be set, ignore others.
|
|
|
|
- Make sure that field values make sense. -}
|
2012-07-02 15:08:50 +00:00
|
|
|
checkField :: (String, String) -> Bool
|
2015-07-09 23:03:21 +00:00
|
|
|
checkField (field, val)
|
|
|
|
| field == fieldName remoteUUID = fieldCheck remoteUUID val
|
|
|
|
| field == fieldName associatedFile = fieldCheck associatedFile val
|
2015-12-26 17:59:27 +00:00
|
|
|
| field == fieldName unlocked = fieldCheck unlocked val
|
2015-07-09 23:03:21 +00:00
|
|
|
| field == fieldName direct = fieldCheck direct val
|
2015-08-05 17:49:54 +00:00
|
|
|
| field == fieldName autoInit = fieldCheck autoInit val
|
2012-07-02 15:08:50 +00:00
|
|
|
| otherwise = False
|
2012-07-02 05:31:10 +00:00
|
|
|
|
2012-03-15 16:00:19 +00:00
|
|
|
failure :: IO ()
|
2018-05-25 17:17:56 +00:00
|
|
|
failure = giveup $ "bad parameters\n\n" ++ usage h cmdsList
|
2015-07-09 23:03:21 +00:00
|
|
|
where
|
|
|
|
h = "git-annex-shell [-c] command [parameters ...] [option ...]"
|