git-annex/Command/Vicfg.hs

298 lines
9.4 KiB
Haskell
Raw Normal View History

{- git-annex command
-
- Copyright 2012-2014 Joey Hess <id@joeyh.name>
-
- Licensed under the GNU GPL version 3 or higher.
-}
{-# LANGUAGE RankNTypes #-}
module Command.Vicfg where
import qualified Data.Map as M
import qualified Data.Set as S
import System.Environment (getEnv)
import Data.Tuple (swap)
2012-10-03 23:13:21 +00:00
import Data.Char (isSpace)
import Data.Default
import Command
import Annex.Perms
import Types.TrustLevel
import Types.Group
import Logs.Trust
import Logs.Group
import Logs.PreferredContent
2013-10-07 21:11:13 +00:00
import Logs.Schedule
2013-05-23 18:54:59 +00:00
import Types.StandardGroups
2013-10-07 21:11:13 +00:00
import Types.ScheduledActivity
import Remote
cmd :: Command
cmd = command "vicfg" SectionSetup "edit git-annex's configuration"
paramNothing (withParams seek)
seek :: CmdParams -> CommandSeek
seek = withNothing start
start :: CommandStart
start = do
f <- fromRepo gitAnnexTmpCfgFile
createAnnexDirectory $ parentDir f
2012-10-03 23:13:21 +00:00
cfg <- getCfg
descs <- uuidDescriptions
liftIO $ writeFileAnyEncoding f $ genCfg cfg descs
2012-10-03 23:13:21 +00:00
vicfg cfg f
stop
2012-10-03 23:13:21 +00:00
vicfg :: Cfg -> FilePath -> Annex ()
vicfg curcfg f = do
vi <- liftIO $ catchDefaultIO "vi" $ getEnv "EDITOR"
-- Allow EDITOR to be processed by the shell, so it can contain options.
2012-12-18 16:19:24 +00:00
unlessM (liftIO $ boolSystem "sh" [Param "-c", Param $ unwords [vi, shellEscape f]]) $
error $ vi ++ " exited nonzero; aborting"
r <- parseCfg (defCfg curcfg) <$> liftIO (readFileStrictAnyEncoding f)
liftIO $ nukeFile f
case r of
Left s -> do
liftIO $ writeFileAnyEncoding f s
2012-10-03 23:13:21 +00:00
vicfg curcfg f
Right newcfg -> setCfg curcfg newcfg
data Cfg = Cfg
{ cfgTrustMap :: TrustMap
, cfgGroupMap :: M.Map UUID (S.Set Group)
, cfgPreferredContentMap :: M.Map UUID PreferredContentExpression
, cfgRequiredContentMap :: M.Map UUID PreferredContentExpression
, cfgGroupPreferredContentMap :: M.Map Group PreferredContentExpression
2013-10-07 21:11:13 +00:00
, cfgScheduleMap :: M.Map UUID [ScheduledActivity]
}
getCfg :: Annex Cfg
getCfg = Cfg
<$> trustMapRaw -- without local trust overrides
<*> (groupsByUUID <$> groupMap)
<*> preferredContentMapRaw
<*> requiredContentMapRaw
<*> groupPreferredContentMapRaw
2013-10-07 21:11:13 +00:00
<*> scheduleMap
setCfg :: Cfg -> Cfg -> Annex ()
setCfg curcfg newcfg = do
let diff = diffCfg curcfg newcfg
mapM_ (uncurry trustSet) $ M.toList $ cfgTrustMap diff
mapM_ (uncurry groupSet) $ M.toList $ cfgGroupMap diff
mapM_ (uncurry preferredContentSet) $ M.toList $ cfgPreferredContentMap diff
mapM_ (uncurry requiredContentSet) $ M.toList $ cfgRequiredContentMap diff
mapM_ (uncurry groupPreferredContentSet) $ M.toList $ cfgGroupPreferredContentMap diff
mapM_ (uncurry scheduleSet) $ M.toList $ cfgScheduleMap diff
{- Default config has all the keys from the input config, but with their
- default values. -}
defCfg :: Cfg -> Cfg
defCfg curcfg = Cfg
{ cfgTrustMap = mapdef $ cfgTrustMap curcfg
, cfgGroupMap = mapdef $ cfgGroupMap curcfg
, cfgPreferredContentMap = mapdef $ cfgPreferredContentMap curcfg
, cfgRequiredContentMap = mapdef $ cfgRequiredContentMap curcfg
, cfgGroupPreferredContentMap = mapdef $ cfgGroupPreferredContentMap curcfg
, cfgScheduleMap = mapdef $ cfgScheduleMap curcfg
}
where
mapdef :: forall k v. Default v => M.Map k v -> M.Map k v
mapdef = M.map (const def)
diffCfg :: Cfg -> Cfg -> Cfg
diffCfg curcfg newcfg = Cfg
{ cfgTrustMap = diff cfgTrustMap
, cfgGroupMap = diff cfgGroupMap
, cfgPreferredContentMap = diff cfgPreferredContentMap
, cfgRequiredContentMap = diff cfgRequiredContentMap
, cfgGroupPreferredContentMap = diff cfgGroupPreferredContentMap
, cfgScheduleMap = diff cfgScheduleMap
}
2012-11-12 05:05:04 +00:00
where
diff f = M.differenceWith (\x y -> if x == y then Nothing else Just x)
(f newcfg) (f curcfg)
genCfg :: Cfg -> M.Map UUID String -> String
genCfg cfg descs = unlines $ intercalate [""]
[ intro
, trust
, groups
, preferredcontent
, grouppreferredcontent
, standardgroups
, requiredcontent
, schedule
]
2012-11-12 05:05:04 +00:00
where
intro =
[ com "git-annex configuration"
, com ""
, com "Changes saved to this file will be recorded in the git-annex branch."
, com ""
, com "Lines in this file have the format:"
, com " setting field = value"
2012-11-12 05:05:04 +00:00
]
trust = settings cfg descs cfgTrustMap
[ com "Repository trust configuration"
2013-05-23 18:54:59 +00:00
, com "(Valid trust levels: " ++ trustlevels ++ ")"
2012-11-12 05:05:04 +00:00
]
(\(t, u) -> line "trust" u $ showTrustLevel t)
(\u -> lcom $ line "trust" u $ showTrustLevel def)
2013-05-23 18:54:59 +00:00
where
trustlevels = unwords $ map showTrustLevel [Trusted .. DeadTrusted]
2012-11-12 05:05:04 +00:00
groups = settings cfg descs cfgGroupMap
[ com "Repository groups"
2013-05-23 18:54:59 +00:00
, com $ "(Standard groups: " ++ grouplist ++ ")"
2012-11-12 05:05:04 +00:00
, com "(Separate group names with spaces)"
]
(\(s, u) -> line "group" u $ unwords $ S.toList s)
(\u -> lcom $ line "group" u "")
2013-05-23 18:54:59 +00:00
where
grouplist = unwords $ map fromStandardGroup [minBound..]
2012-11-12 05:05:04 +00:00
preferredcontent = settings cfg descs cfgPreferredContentMap
[ com "Repository preferred contents"
, com "(Set to \"standard\" to use a repository's group's preferred contents)"
]
(\(s, u) -> line "wanted" u s)
(\u -> line "wanted" u "")
requiredcontent = settings cfg descs cfgRequiredContentMap
[ com "Repository required contents" ]
(\(s, u) -> line "required" u s)
(\u -> line "required" u "")
grouppreferredcontent = settings' cfg allgroups cfgGroupPreferredContentMap
[ com "Group preferred contents"
, com "(Used by repositories with \"groupwanted\" in their preferred contents)"
2012-11-12 05:05:04 +00:00
]
(\(s, g) -> gline g s)
(\g -> gline g "")
where
2015-07-11 00:40:30 +00:00
gline g val = [ unwords ["groupwanted", g, "=", val] ]
allgroups = S.unions $ stdgroups : M.elems (cfgGroupMap cfg)
stdgroups = S.fromList $ map fromStandardGroup [minBound..maxBound]
2012-11-12 05:05:04 +00:00
standardgroups =
[ com "Standard preferred contents"
, com "(Used by wanted or groupwanted expressions containing \"standard\")"
, com "(For reference only; built-in and cannot be changed!)"
]
++ map gline [minBound..maxBound]
where
gline g = com $ unwords
[ "standard"
2014-03-15 21:08:55 +00:00
, fromStandardGroup g, "=", standardPreferredContent g
]
schedule = settings cfg descs cfgScheduleMap
[ com "Scheduled activities"
2013-10-07 21:11:13 +00:00
, com "(Separate multiple activities with \"; \")"
]
(\(l, u) -> line "schedule" u $ fromScheduledActivities l)
2013-10-07 21:11:13 +00:00
(\u -> line "schedule" u "")
2015-07-11 00:40:30 +00:00
line setting u val =
2013-09-25 07:09:06 +00:00
[ com $ "(for " ++ fromMaybe "" (M.lookup u descs) ++ ")"
2015-07-11 00:40:30 +00:00
, unwords [setting, fromUUID u, "=", val]
2012-11-12 05:05:04 +00:00
]
settings :: Ord v => Cfg -> M.Map UUID String -> (Cfg -> M.Map UUID v) -> [String] -> ((v, UUID) -> [String]) -> (UUID -> [String]) -> [String]
settings cfg descs = settings' cfg (M.keysSet descs)
settings' :: (Ord v, Ord f) => Cfg -> S.Set f -> (Cfg -> M.Map f v) -> [String] -> ((v, f) -> [String]) -> (f -> [String]) -> [String]
settings' cfg s field desc showvals showdefaults = concat
[ desc
, concatMap showvals $ sort $ map swap $ M.toList $ field cfg
, concatMap (lcom . showdefaults) missing
]
where
missing = S.toList $ s `S.difference` M.keysSet (field cfg)
lcom :: [String] -> [String]
lcom = map (\l -> if "#" `isPrefixOf` l then l else '#' : l)
{- If there's a parse error, returns a new version of the file,
- with the problem lines noted. -}
2012-10-03 23:13:21 +00:00
parseCfg :: Cfg -> String -> Either String Cfg
parseCfg defcfg = go [] defcfg . lines
2012-11-12 05:05:04 +00:00
where
go c cfg []
2013-09-25 07:09:06 +00:00
| null (mapMaybe fst c) = Right cfg
2012-11-12 05:05:04 +00:00
| otherwise = Left $ unlines $
badheader ++ concatMap showerr (reverse c)
go c cfg (l:ls) = case parse (dropWhile isSpace l) cfg of
Left msg -> go ((Just msg, l):c) cfg ls
Right cfg' -> go ((Nothing, l):c) cfg' ls
parse l cfg
| null l = Right cfg
| "#" `isPrefixOf` l = Right cfg
| null setting || null f = Left "missing field"
2015-07-11 00:40:30 +00:00
| otherwise = parsed cfg f setting val'
2012-11-12 05:05:04 +00:00
where
(setting, rest) = separate isSpace l
2015-07-11 00:40:30 +00:00
(r, val) = separate (== '=') rest
val' = trimspace val
f = reverse $ trimspace $ reverse $ trimspace r
2012-11-12 05:05:04 +00:00
trimspace = dropWhile isSpace
2015-07-11 00:40:30 +00:00
parsed cfg f setting val
| setting == "trust" = case readTrustLevel val of
Nothing -> badval "trust value" val
2012-11-12 05:05:04 +00:00
Just t ->
let m = M.insert u t (cfgTrustMap cfg)
in Right $ cfg { cfgTrustMap = m }
| setting == "group" =
2015-07-11 00:40:30 +00:00
let m = M.insert u (S.fromList $ words val) (cfgGroupMap cfg)
2012-11-12 05:05:04 +00:00
in Right $ cfg { cfgGroupMap = m }
| setting == "wanted" =
2015-07-11 00:40:30 +00:00
case checkPreferredContentExpression val of
2012-11-12 05:05:04 +00:00
Just e -> Left e
Nothing ->
2015-07-11 00:40:30 +00:00
let m = M.insert u val (cfgPreferredContentMap cfg)
2012-11-12 05:05:04 +00:00
in Right $ cfg { cfgPreferredContentMap = m }
| setting == "required" =
2015-07-11 00:40:30 +00:00
case checkPreferredContentExpression val of
Just e -> Left e
Nothing ->
2015-07-11 00:40:30 +00:00
let m = M.insert u val (cfgRequiredContentMap cfg)
in Right $ cfg { cfgRequiredContentMap = m }
| setting == "groupwanted" =
2015-07-11 00:40:30 +00:00
case checkPreferredContentExpression val of
Just e -> Left e
Nothing ->
2015-07-11 00:40:30 +00:00
let m = M.insert f val (cfgGroupPreferredContentMap cfg)
in Right $ cfg { cfgGroupPreferredContentMap = m }
2015-07-11 00:40:30 +00:00
| setting == "schedule" = case parseScheduledActivities val of
Left e -> Left e
Right l ->
let m = M.insert u l (cfgScheduleMap cfg)
in Right $ cfg { cfgScheduleMap = m }
2012-11-12 05:05:04 +00:00
| otherwise = badval "setting" setting
where
u = toUUID f
2012-11-12 05:05:04 +00:00
showerr (Just msg, l) = [parseerr ++ msg, l]
showerr (Nothing, l)
-- filter out the header and parse error lines
-- from any previous parse failure
| any (`isPrefixOf` l) (parseerr:badheader) = []
| otherwise = [l]
badval desc val = Left $ "unknown " ++ desc ++ " \"" ++ val ++ "\""
badheader =
[ com "** There was a problem parsing your input!"
, com "** Search for \"Parse error\" to find the bad lines."
, com "** Either fix the bad lines, or delete them (to discard your changes)."
2012-11-12 05:05:04 +00:00
]
parseerr = com "** Parse error in next line: "
2012-10-03 23:13:21 +00:00
com :: String -> String
com s = "# " ++ s