module SimpleCmd.Git (
git,
git_,
gitBranch,
gitDiffQuiet,
grepGitConfig,
isGitDir,
rwGitDir) where
import Data.List (isPrefixOf)
import System.Directory (doesDirectoryExist)
import System.FilePath ((</>))
import SimpleCmd (cmd, cmd_, cmdBool, cmdLines, egrep_, removePrefix)
#if (defined(MIN_VERSION_base) && MIN_VERSION_base(4,8,0))
#else
import Control.Applicative ((<$>))
#endif
git :: String
-> [String]
-> IO String
git c args =
cmd "git" (c:args)
git_ :: String -> [String] -> IO ()
git_ c args =
cmd_ "git" (c:args)
isGitDir :: FilePath -> IO Bool
isGitDir dir = doesDirectoryExist (dir </> ".git")
gitBranch :: IO String
gitBranch =
removePrefix "* " . head . filter (isPrefixOf "* ") <$> cmdLines "git" ["branch"]
rwGitDir :: IO Bool
rwGitDir =
grepGitConfig "url = \\(ssh://\\|git@\\)"
grepGitConfig :: String -> IO Bool
grepGitConfig key = do
gitdir <- isGitDir "."
if gitdir
then egrep_ key ".git/config"
else return False
gitDiffQuiet :: [String] -> IO Bool
gitDiffQuiet args = cmdBool "git" $ ["diff", "--quiet"] ++ args