module SimpleCmd.Git (
git,
git_,
gitBool,
gitBranch,
gitDiffQuiet,
grepGitConfig,
isGitDir,
rwGitDir) where
import System.Directory (doesDirectoryExist)
import System.FilePath ((</>))
import SimpleCmd (cmd, cmd_, cmdBool, egrep_)
#if (defined(MIN_VERSION_base) && MIN_VERSION_base(4,8,0))
#else
import Control.Applicative ((<$>))
#endif
git :: String
-> [String]
-> IO String
git :: String -> [String] -> IO String
git c :: String
c args :: [String]
args =
String -> [String] -> IO String
cmd "git" (String
cString -> [String] -> [String]
forall a. a -> [a] -> [a]
:[String]
args)
git_ :: String -> [String] -> IO ()
git_ :: String -> [String] -> IO ()
git_ c :: String
c args :: [String]
args =
String -> [String] -> IO ()
cmd_ "git" (String
cString -> [String] -> [String]
forall a. a -> [a] -> [a]
:[String]
args)
gitBool :: String
-> [String]
-> IO Bool
gitBool :: String -> [String] -> IO Bool
gitBool c :: String
c args :: [String]
args =
String -> [String] -> IO Bool
cmdBool "git" (String
cString -> [String] -> [String]
forall a. a -> [a] -> [a]
:[String]
args)
isGitDir :: FilePath -> IO Bool
isGitDir :: String -> IO Bool
isGitDir dir :: String
dir = String -> IO Bool
doesDirectoryExist (String
dir String -> String -> String
</> ".git")
gitBranch :: IO String
gitBranch :: IO String
gitBranch =
String -> [String] -> IO String
git "rev-parse" ["--abbrev-ref", "HEAD"]
rwGitDir :: IO Bool
rwGitDir :: IO Bool
rwGitDir =
String -> IO Bool
grepGitConfig "url = \\(ssh://\\|git@\\)"
grepGitConfig :: String -> IO Bool
grepGitConfig :: String -> IO Bool
grepGitConfig key :: String
key = do
Bool
gitdir <- String -> IO Bool
isGitDir "."
if Bool
gitdir
then String -> String -> IO Bool
egrep_ String
key ".git/config"
else Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
False
gitDiffQuiet :: [String] -> IO Bool
gitDiffQuiet :: [String] -> IO Bool
gitDiffQuiet args :: [String]
args = String -> [String] -> IO Bool
cmdBool "git" ([String] -> IO Bool) -> [String] -> IO Bool
forall a b. (a -> b) -> a -> b
$ ["diff", "--quiet"] [String] -> [String] -> [String]
forall a. [a] -> [a] -> [a]
++ [String]
args