{-# LANGUAGE OverloadedStrings #-}
module Darcs.UI.Flags
( F.DarcsFlag
, remoteDarcs
, diffingOpts
, diffOpts
, scanKnown
, wantGuiPause
, isInteractive
, willRemoveLogFile
, includeBoring
, lookForAdds
, lookForMoves
, lookForReplaces
, setDefault
, allowConflicts
, hasXmlOutput
, hasLogfile
, quiet
, verbose
, enumeratePatches
, fixRemoteRepos
, fixUrl
, pathsFromArgs
, pathSetFromArgs
, getRepourl
, getAuthor
, promptAuthor
, getEasyAuthor
, getSendmailCmd
, fileHelpAuthor
, environmentHelpEmail
, getSubject
, getInReplyTo
, getCc
, environmentHelpSendmail
, getOutput
, getDate
, workRepo
, withNewRepo
, O.compress
, O.diffAlgorithm
, O.reorder
, O.minimize
, O.editDescription
, O.externalMerge
, O.maxCount
, O.matchAny
, O.withContext
, O.allowCaseDifferingFilenames
, O.allowWindowsReservedFilenames
, O.changesReverse
, O.usePacks
, O.onlyToFiles
, O.amendUnrecord
, O.verbosity
, O.useCache
, O.useIndex
, O.umask
, O.dryRun
, O.runTest
, O.testChanges
, O.setScriptsExecutable
, O.withWorkingDir
, O.leaveTestDir
, O.remoteRepos
, O.cloneKind
, O.patchIndexNo
, O.patchIndexYes
, O.xmlOutput
, O.selectDeps
, O.author
, O.patchFormat
, O.charset
, O.siblings
, O.applyAs
, O.enumPatches
) where
import Darcs.Prelude
import Data.List ( intercalate )
import Data.List.Ordered ( nubSort )
import Data.Maybe
( isJust
, maybeToList
, isNothing
, catMaybes
)
import Control.Monad ( unless )
import System.Directory ( doesDirectoryExist, createDirectory )
import System.FilePath.Posix ( (</>) )
import System.Environment ( lookupEnv )
import qualified Darcs.UI.Options.Flags as F ( DarcsFlag(RemoteRepo) )
import Darcs.UI.Options ( Config, (?), (^), oparse, parseFlags, unparseOpt )
import qualified Darcs.UI.Options.All as O
import Darcs.Util.Exception ( catchall )
import Darcs.Util.File ( withCurrentDirectory )
import Darcs.Util.Prompt
( askUser
, askUserListItem
)
import Darcs.Util.Lock ( writeTextFile )
import Darcs.Repository.Flags ( WorkRepo(..) )
import Darcs.Repository.Prefs
( getPreflist
, getGlobal
, globalPrefsDirDoc
, globalPrefsDir
, prefsDirPath
)
import Darcs.Util.IsoDate ( getIsoDateTime, cleanLocalDate )
import Darcs.Util.Path
( AbsolutePath
, AbsolutePathOrStd
, toFilePath
, makeSubPathOf
, ioAbsolute
, makeAbsoluteOrStd
, AnchoredPath
, floatSubPath
, inDarcsdir
)
import Darcs.Util.Printer ( pathlist, putDocLn, text, ($$), (<+>) )
import Darcs.Util.Printer.Color ( ePutDocLn )
import Darcs.Util.URL ( isValidLocalPath )
verbose :: Config -> Bool
verbose = (== O.Verbose) . parseFlags O.verbosity
quiet :: Config -> Bool
quiet = (== O.Quiet) . parseFlags O.verbosity
remoteDarcs :: Config -> O.RemoteDarcs
remoteDarcs = O.remoteDarcs . parseFlags O.network
enumeratePatches :: Config -> Bool
enumeratePatches = (== O.YesEnumPatches) . parseFlags O.enumPatches
diffOpts :: O.UseIndex -> O.LookForAdds -> O.IncludeBoring -> O.DiffAlgorithm -> (O.UseIndex, O.ScanKnown, O.DiffAlgorithm)
diffOpts use_index look_for_adds include_boring diff_alg =
(use_index, scanKnown look_for_adds include_boring, diff_alg)
scanKnown :: O.LookForAdds -> O.IncludeBoring -> O.ScanKnown
scanKnown O.NoLookForAdds _ = O.ScanKnown
scanKnown O.YesLookForAdds O.NoIncludeBoring = O.ScanAll
scanKnown O.YesLookForAdds O.YesIncludeBoring = O.ScanBoring
diffingOpts :: Config -> (O.UseIndex, O.ScanKnown, O.DiffAlgorithm)
diffingOpts flags = diffOpts (O.useIndex ? flags) (lookForAdds flags)
(parseFlags O.includeBoring flags) (O.diffAlgorithm ? flags)
wantGuiPause :: Config -> O.WantGuiPause
wantGuiPause fs = if (hasDiffCmd fs || hasExternalMerge fs) && hasPause fs then O.YesWantGuiPause else O.NoWantGuiPause
where
hasDiffCmd = isJust . O.diffCmd . parseFlags O.extDiff
hasExternalMerge = (/= O.NoExternalMerge) . parseFlags O.externalMerge
hasPause = (== O.YesWantGuiPause) . parseFlags O.pauseForGui
isInteractive :: Bool -> Config -> Bool
isInteractive def = oparse (O.dryRunXml ^ O.changesFormat ^ O.interactive) decide
where
decide :: O.DryRun -> O.XmlOutput -> Maybe O.ChangesFormat -> Maybe Bool -> Bool
decide _ _ _ (Just True) = True
decide _ _ _ (Just False) = False
decide _ _ (Just O.CountPatches) Nothing = False
decide _ O.YesXml _ Nothing = False
decide O.YesDryRun _ _ Nothing = False
decide _ _ _ Nothing = def
willRemoveLogFile :: Config -> Bool
willRemoveLogFile = O._rmlogfile . parseFlags O.logfile
includeBoring :: Config -> Bool
includeBoring cfg = case parseFlags O.includeBoring cfg of
O.NoIncludeBoring -> False
O.YesIncludeBoring -> True
lookForAdds :: Config -> O.LookForAdds
lookForAdds = O.adds . parseFlags O.lookfor
lookForReplaces :: Config -> O.LookForReplaces
lookForReplaces = O.replaces . parseFlags O.lookfor
lookForMoves :: Config -> O.LookForMoves
lookForMoves = O.moves . parseFlags O.lookfor
setDefault :: Bool -> Config -> O.SetDefault
setDefault defYes = maybe def noDef . parseFlags O.setDefault where
def = if defYes then O.YesSetDefault False else O.NoSetDefault False
noDef yes = if yes then O.YesSetDefault True else O.NoSetDefault True
allowConflicts :: Config -> O.AllowConflicts
allowConflicts = maybe O.NoAllowConflicts id . parseFlags O.conflictsNo
fixRemoteRepos :: AbsolutePath -> Config -> IO Config
fixRemoteRepos d = mapM fixRemoteRepo where
fixRemoteRepo (F.RemoteRepo p) = F.RemoteRepo `fmap` fixUrl d p
fixRemoteRepo f = return f
fixUrl :: AbsolutePath -> String -> IO String
fixUrl d f = if isValidLocalPath f
then toFilePath `fmap` withCurrentDirectory d (ioAbsolute f)
else return f
pathsFromArgs :: (AbsolutePath, AbsolutePath) -> [String] -> IO [AnchoredPath]
pathsFromArgs fps args = catMaybes <$> maybeFixSubPaths fps args
pathSetFromArgs :: (AbsolutePath, AbsolutePath)
-> [String]
-> IO (Maybe [AnchoredPath])
pathSetFromArgs _ [] = return Nothing
pathSetFromArgs fps args = do
pathSet <- nubSort . catMaybes <$> maybeFixSubPaths fps args
case pathSet of
[] -> fail "No valid arguments were given."
_ -> return $ Just pathSet
maybeFixSubPaths :: (AbsolutePath, AbsolutePath) -> [String] -> IO [Maybe AnchoredPath]
maybeFixSubPaths (r, o) fs = do
fixedFs <- mapM (fmap dropInDarcsdir . fixit) fs
let bads = snd . unzip . filter (isNothing . fst) $ zip fixedFs fs
unless (null bads) $
ePutDocLn $ text "Ignoring invalid repository paths:" <+> pathlist bads
return fixedFs
where
dropInDarcsdir (Just p) | inDarcsdir p = Nothing
dropInDarcsdir mp = mp
fixit "" = return Nothing
fixit p = do ap <- withCurrentDirectory o $ ioAbsolute p
case makeSubPathOf r ap of
Just sp -> return $ Just $ floatSubPath sp
Nothing -> do
absolutePathByRepodir <- withCurrentDirectory r $ ioAbsolute p
return $ floatSubPath <$> makeSubPathOf r absolutePathByRepodir
getRepourl :: Config -> Maybe String
getRepourl fs = case parseFlags O.possiblyRemoteRepo fs of
Nothing -> Nothing
Just d -> if not (isValidLocalPath d) then Just d else Nothing
fileHelpAuthor :: [String]
fileHelpAuthor = [
"Each patch is attributed to its author, usually by email address (for",
"example, `Fred Bloggs <fred@example.net>`). Darcs looks in several",
"places for this author string: the `--author` option, the files",
"`_darcs/prefs/author` (in the repository) and `" ++ globalPrefsDirDoc ++ "author` (in your",
"home directory), and the environment variables `$DARCS_EMAIL` and",
"`$EMAIL`. If none of those exist, Darcs will prompt you for an author",
"string and write it to `" ++ globalPrefsDirDoc ++ "author`. Note that if you have more",
"than one email address, you can put them all in `" ++ globalPrefsDirDoc ++ "author`,",
"one author per line. Darcs will still prompt you for an author, but it",
"allows you to select from the list, or to type in an alternative."
]
environmentHelpEmail :: ([String], [String])
environmentHelpEmail = (["DARCS_EMAIL","EMAIL"], fileHelpAuthor)
getAuthor :: Maybe String -> Bool -> IO String
getAuthor (Just author) _ = return author
getAuthor Nothing pipe = if pipe then askUser "Who is the author? " else promptAuthor True False
promptAuthor :: Bool
-> Bool
-> IO String
promptAuthor store alwaysAsk = do
as <- getEasyAuthor
case as of
[a] -> if alwaysAsk then
askForAuthor False (fancyPrompt as) (fancyPrompt as)
else return a
[] -> askForAuthor True shortPrompt longPrompt
_ -> askForAuthor False (fancyPrompt as) (fancyPrompt as)
where
shortPrompt = askUser "What is your email address? "
longPrompt = askUser "What is your email address (e.g. Fred Bloggs <fred@example.net>)? "
fancyPrompt xs =
do putDocLn $ text "" $$
text "You have saved the following email addresses to your global settings:"
str <- askUserListItem "Please select an email address for this repository: " (xs ++ ["Other"])
if str == "Other"
then longPrompt
else return str
askForAuthor storeGlobal askfn1 askfn2 = do
aminrepo <- doesDirectoryExist prefsDirPath
if aminrepo && store then do
prefsdir <- if storeGlobal
then tryGlobalPrefsDir
else return prefsDirPath
putDocLn $
text "Each patch is attributed to its author, usually by email address (for" $$
text "example, `Fred Bloggs <fred@example.net>'). Darcs could not determine" $$
text "your email address, so you will be prompted for it." $$
text "" $$
text ("Your address will be stored in " ++ prefsdir)
if prefsdir /= prefsDirPath then
putDocLn $
text "It will be used for all patches you record in ALL repositories." $$
text ("If you move that file to " ++ prefsDirPath </> "author" ++ ", it will") $$
text "be used for patches recorded in this repository only."
else
putDocLn $
text "It will be used for all patches you record in this repository only." $$
text ("If you move that file to " ++ globalPrefsDirDoc ++ "author, it will") $$
text "be used for all patches recorded in ALL repositories."
add <- askfn1
writeTextFile (prefsdir </> "author") $
unlines ["# " ++ line | line <- fileHelpAuthor] ++ "\n" ++ add
return add
else askfn2
tryGlobalPrefsDir = do
maybeprefsdir <- globalPrefsDir
case maybeprefsdir of
Nothing -> do
putStrLn "WARNING: Global preference directory could not be found."
return prefsDirPath
Just dir -> do exists <- doesDirectoryExist dir
unless exists $ createDirectory dir
return dir
getEasyAuthor :: IO [String]
getEasyAuthor =
firstNotNullIO [ (take 1 . nonblank) `fmap` getPreflist "author"
, nonblank `fmap` getGlobal "author"
, maybeToList `fmap` lookupEnv "DARCS_EMAIL"
, maybeToList `fmap` lookupEnv "EMAIL"
]
where
nonblank = filter (not . null)
firstNotNullIO [] = return []
firstNotNullIO (e:es) = do
v <- e `catchall` return []
if null v then firstNotNullIO es else return v
getDate :: Bool -> IO String
getDate hasPipe = if hasPipe then cleanLocalDate =<< askUser "What is the date? "
else getIsoDateTime
environmentHelpSendmail :: ([String], [String])
environmentHelpSendmail = (["SENDMAIL"], [
"On Unix, the `darcs send` command relies on sendmail(8). The",
"`--sendmail-command` or $SENDMAIL environment variable can be used to",
"provide an explicit path to this program; otherwise the standard",
"locations /usr/sbin/sendmail and /usr/lib/sendmail will be tried."])
getSendmailCmd :: Config -> IO String
getSendmailCmd fs = case parseFlags O.sendmailCmd fs of
Just cmd -> return cmd
Nothing -> fmap (maybe "" id) $ lookupEnv "SENDMAIL"
getOutput :: Config -> FilePath -> Maybe AbsolutePathOrStd
getOutput fs fp = fmap go (parseFlags O.output fs) where
go (O.Output ap) = ap
go (O.OutputAutoName ap) = makeAbsoluteOrStd ap fp
getSubject :: Config -> Maybe String
getSubject = O._subject . parseFlags O.headerFields
getCc :: Config -> String
getCc = intercalate " , " . O._cc . parseFlags O.headerFields
getInReplyTo :: Config -> Maybe String
getInReplyTo = O._inReplyTo . parseFlags O.headerFields
hasXmlOutput :: Config -> Bool
hasXmlOutput = (== O.YesXml) . parseFlags O.xmlOutput
hasLogfile :: Config -> Maybe AbsolutePath
hasLogfile = O._logfile . parseFlags O.logfile
workRepo :: Config -> WorkRepo
workRepo = oparse (O.repoDir ^ O.possiblyRemoteRepo) go
where
go (Just s) _ = WorkRepoDir s
go Nothing (Just s) = WorkRepoPossibleURL s
go Nothing Nothing = WorkRepoCurrentDir
withNewRepo :: String -> Config -> Config
withNewRepo dir = unparseOpt O.newRepo (Just dir)