git-annex/Command/Group.hs
Joey Hess 2ba1559a8e
git style quoting for ActionItemOther
Added StringContainingQuotedPath, which is used for ActionItemOther.

In the process, checked every ActionItemOther for those containing
filenames, and made them use quoting.

Sponsored-by: Graham Spencer on Patreon
2023-04-08 16:30:01 -04:00

45 lines
1.1 KiB
Haskell

{- git-annex command
-
- Copyright 2012 Joey Hess <id@joeyh.name>
-
- Licensed under the GNU AGPL version 3 or higher.
-}
module Command.Group where
import Command
import qualified Remote
import Logs.Group
import Types.Group
import qualified Data.Set as S
cmd :: Command
cmd = noMessages $ command "group" SectionSetup "add a repository to a group"
(paramPair paramRemote paramDesc) (withParams seek)
seek :: CmdParams -> CommandSeek
seek = withWords (commandAction . start)
start :: [String] -> CommandStart
start ps@(name:g:[]) = do
u <- Remote.nameToUUID name
startingUsualMessages "group" ai si $
setGroup u (toGroup g)
where
ai = ActionItemOther (Just (UnquotedString name))
si = SeekInput ps
start (name:[]) = do
u <- Remote.nameToUUID name
startingCustomOutput (ActionItemOther Nothing) $ do
liftIO . putStrLn . unwords . map fmt . S.toList
=<< lookupGroups u
next $ return True
where
fmt (Group g) = decodeBS g
start _ = giveup "Specify a repository and a group."
setGroup :: UUID -> Group -> CommandPerform
setGroup uuid g = do
groupChange uuid (S.insert g)
next $ return True