{-|
Some wrappers for git commands.
-}

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 c args@ runs git command and return output
git :: String -- ^ git command
    -> [String] -- ^ arguments
    -> IO String -- ^ output
git :: String -> [String] -> IO String
git String
c [String]
args =
  String -> [String] -> IO String
cmd String
"git" (String
cString -> [String] -> [String]
forall a. a -> [a] -> [a]
:[String]
args)

-- | @git_ c args@ run git command with output to stdout and stderr
git_ :: String -> [String] -> IO ()
git_ :: String -> [String] -> IO ()
git_ String
c [String]
args =
  String -> [String] -> IO ()
cmd_ String
"git" (String
cString -> [String] -> [String]
forall a. a -> [a] -> [a]
:[String]
args)

-- | @gitBool c args@ runs git command and return result
--
-- @since 0.2.2
gitBool :: String -- ^ git command
        -> [String] -- ^ arguments
        -> IO Bool -- ^ result
gitBool :: String -> [String] -> IO Bool
gitBool String
c [String]
args =
  String -> [String] -> IO Bool
cmdBool String
"git" (String
cString -> [String] -> [String]
forall a. a -> [a] -> [a]
:[String]
args)

-- | @isGitDir dir@ checks if directory has a .git/ subdir
isGitDir :: FilePath -> IO Bool
isGitDir :: String -> IO Bool
isGitDir String
dir = String -> IO Bool
doesDirectoryExist (String
dir String -> String -> String
</> String
".git")

-- | @gitBranch@ returns the git branch of the current directory
gitBranch :: IO String
gitBranch :: IO String
gitBranch =
  String -> [String] -> IO String
git String
"rev-parse" [String
"--abbrev-ref", String
"HEAD"]

-- | @rwGitDir@ checks if a git repo is under ssh
rwGitDir :: IO Bool
rwGitDir :: IO Bool
rwGitDir =
  String -> IO Bool
grepGitConfig String
"url = \\(ssh://\\|git@\\)"

-- | @grepGitConfig pat@ greps ".git/config" for extended regexp
--
-- @since 0.1.1
grepGitConfig :: String -> IO Bool
grepGitConfig :: String -> IO Bool
grepGitConfig String
key = do
  Bool
gitdir <- String -> IO Bool
isGitDir String
"."
  if Bool
gitdir
    then String -> String -> IO Bool
egrep_ String
key String
".git/config"
    else Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
False

-- | @gitDiffQuiet@ checks if unchanged
--
-- @since 0.1.3
gitDiffQuiet :: [String] -> IO Bool
gitDiffQuiet :: [String] -> IO Bool
gitDiffQuiet [String]
args = String -> [String] -> IO Bool
cmdBool String
"git" ([String] -> IO Bool) -> [String] -> IO Bool
forall a b. (a -> b) -> a -> b
$ [String
"diff", String
"--quiet"] [String] -> [String] -> [String]
forall a. [a] -> [a] -> [a]
++ [String]
args