module Darcs.UI.Defaults ( applyDefaults ) where
import Prelude ()
import Darcs.Prelude
import Control.Monad.Writer
import Data.Char ( isSpace )
import Data.Functor.Compose ( Compose(..) )
import Data.List ( nub, intercalate )
import Data.Maybe ( catMaybes )
import qualified Data.Map as M
import System.Console.GetOpt
import Text.Regex.Applicative
( (<|>)
, match, many, some
, psym, anySym, string )
import Darcs.UI.Flags ( DarcsFlag )
import Darcs.UI.Options ( DarcsOptDescr )
import Darcs.UI.Commands
( DarcsCommand(..), commandAlloptions, extractAllCommands
, WrappedCommand(..)
)
import Darcs.UI.TheCommands ( commandControlList )
import Darcs.Util.Path ( AbsolutePath )
applyDefaults :: Maybe String
-> DarcsCommand pf
-> AbsolutePath
-> [String]
-> [String]
-> [DarcsFlag]
-> ([DarcsFlag], [String])
applyDefaults msuper cmd cwd user repo flags = runWriter $ do
cl_flags <- runChecks "Command line" check_opts flags
user_defs <- get_flags "User defaults" user
repo_defs <- get_flags "Repo defaults" repo
return $ cl_flags ++ repo_defs ++ user_defs ++ builtin_defs
where
cmd_name = mkCmdName msuper (commandName cmd)
builtin_defs = commandDefaults cmd
check_opts = commandCheckOptions cmd
opts = uncurry (++) $ commandAlloptions cmd
get_flags source = parseDefaults source cwd cmd_name opts check_opts
data CmdName = NormalCmd String | SuperCmd String String
mkCmdName :: Maybe String -> String -> CmdName
mkCmdName Nothing cmd = NormalCmd cmd
mkCmdName (Just super) sub = SuperCmd super sub
showCmdName :: CmdName -> String
showCmdName (SuperCmd super sub) = unwords [super,sub]
showCmdName (NormalCmd name) = name
runChecks :: String -> ([DarcsFlag] -> [String]) -> [DarcsFlag] -> Writer [String] [DarcsFlag]
runChecks source check fs = case check fs of
[] -> return fs
es -> do
tell [intercalate "\n" $ map ((source++": ")++) es]
return fs
parseDefaults :: String
-> AbsolutePath
-> CmdName
-> [DarcsOptDescr DarcsFlag]
-> ([DarcsFlag] -> [String])
-> [String]
-> Writer [String] [DarcsFlag]
parseDefaults source cwd cmd opts check_opts def_lines = do
cmd_flags <- flags_for (M.keys opt_map) cmd_defs >>=
runChecks (source++" for command '"++showCmdName cmd++"'") check_opts
all_flags <- flags_for allOptionSwitches all_defs >>=
runChecks (source++" for ALL commands") check_opts
return $ cmd_flags ++ all_flags
where
opt_map = optionMap opts
cmd_defs = parseDefaultsLines cmd def_lines
all_defs = parseDefaultsLines (NormalCmd "ALL") def_lines
to_flag all_switches (switch,arg) =
if switch `notElem` all_switches then do
tell [source++": command '"++showCmdName cmd
++"' has no option '"++switch++"'."]
return Nothing
else
mapErrors ((source++" for command '"++showCmdName cmd++"':"):)
$ defaultToFlag cwd opt_map (switch,arg)
flags_for all_switches = fmap catMaybes . mapM (to_flag all_switches)
mapErrors f = mapWriter (\(r, es) -> (r, if null es then [] else f es))
type Default = (String, String)
parseDefaultsLines :: CmdName -> [String] -> [Default]
parseDefaultsLines cmd = catMaybes . map matchLine
where
matchLine = match $ (,) <$> (match_cmd cmd *> spaces *> opt_dashes *> word) <*> rest
match_cmd (NormalCmd name) = string name
match_cmd (SuperCmd super sub) = string super *> spaces *> string sub
opt_dashes = string "--" <|> pure ""
word = some $ psym (not.isSpace)
spaces = some $ psym isSpace
rest = spaces *> many anySym <|> pure ""
defaultToFlag :: AbsolutePath
-> OptionMap
-> Default
-> Writer [String] (Maybe DarcsFlag)
defaultToFlag cwd opts (switch, arg) = case M.lookup switch opts of
Nothing -> return Nothing
Just opt -> flag_from $ getArgDescr $ getCompose opt
where
getArgDescr (Option _ _ a _) = a
flag_from (NoArg mkFlag) = do
if not (null arg) then do
tell ["'"++switch++"' takes no argument, but '"++arg++"' argument given."]
return Nothing
else
return $ Just $ mkFlag cwd
flag_from (OptArg mkFlag _) =
return $ Just $ mkFlag (if null arg then Nothing else Just arg) cwd
flag_from (ReqArg mkFlag _) = do
if null arg then do
tell ["'"++switch++"' requires an argument, but no "++"argument given."]
return Nothing
else
return $ Just $ mkFlag arg cwd
optionSwitches :: [DarcsOptDescr DarcsFlag] -> [String]
optionSwitches = concatMap sel where
sel (Compose (Option _ switches _ _)) = switches
type OptionMap = M.Map String (DarcsOptDescr DarcsFlag)
optionMap :: [DarcsOptDescr DarcsFlag] -> OptionMap
optionMap = M.fromList . concatMap sel where
add_option opt switch = (switch, opt)
sel o@(Compose (Option _ switches _ _)) = map (add_option o) switches
allOptionSwitches :: [String]
allOptionSwitches = nub $ optionSwitches $
concatMap (\(WrappedCommand c) -> uncurry (++) . commandAlloptions $ c) $
extractAllCommands commandControlList