git-annex/Command/Wanted.hs
Joey Hess 4781ca297b
showStart variant for when there's no worktree file
Clean up some uses of showStart with "" for the file,
or in some cases, a non-filename description string. That would
generate bad json, although none of the commands doing that
supported --json.

Using "" for the file resulted in output like "foo  rest";
now the extra space is eliminated.

This commit was sponsored by Fernando Jimenez on Patreon.
2017-11-28 15:14:16 -04:00

57 lines
1.5 KiB
Haskell

{- git-annex command
-
- Copyright 2013-2015 Joey Hess <id@joeyh.name>
-
- Licensed under the GNU GPL version 3 or higher.
-}
module Command.Wanted where
import Command
import qualified Remote
import Logs.PreferredContent
import Types.StandardGroups
import qualified Data.Map as M
cmd :: Command
cmd = cmd' "wanted" "get or set preferred content expression"
preferredContentMapRaw
preferredContentSet
cmd'
:: String
-> String
-> Annex (M.Map UUID PreferredContentExpression)
-> (UUID -> PreferredContentExpression -> Annex ())
-> Command
cmd' name desc getter setter = noMessages $
command name SectionSetup desc pdesc (withParams seek)
where
pdesc = paramPair paramRemote (paramOptional paramExpression)
seek = withWords start
start (rname:[]) = go rname (performGet getter)
start (rname:expr:[]) = go rname $ \uuid -> do
allowMessages
showStart' name (Just rname)
performSet setter expr uuid
start _ = giveup "Specify a repository."
go rname a = do
u <- Remote.nameToUUID rname
next $ a u
performGet :: Ord a => Annex (M.Map a PreferredContentExpression) -> a -> CommandPerform
performGet getter a = do
m <- getter
liftIO $ putStrLn $ fromMaybe "" $ M.lookup a m
next $ return True
performSet :: (a -> PreferredContentExpression -> Annex ()) -> String -> a -> CommandPerform
performSet setter expr a = case checkPreferredContentExpression expr of
Just e -> giveup $ "Parse error: " ++ e
Nothing -> do
setter a expr
next $ return True