module Development.GitRev (gitHash, gitBranch, gitDirty, gitCommitCount, gitCommitDate) where
import Control.Exception
import Control.Monad
import Data.Maybe
import Language.Haskell.TH
import Language.Haskell.TH.Syntax
import System.Directory
import System.Exit
import System.FilePath
import System.Process
import Prelude ()
import Prelude.Compat
runGit :: [String] -> String -> IndexUsed -> Q String
runGit args def useIdx = do
let oops :: SomeException -> IO (ExitCode, String, String)
oops _e = return (ExitFailure 1, def, "")
gitFound <- runIO $ isJust <$> findExecutable "git"
if gitFound
then do
pwd <- runIO getGitDirectory
let hd = pwd </> ".git" </> "HEAD"
index = pwd </> ".git" </> "index"
packedRefs = pwd </> ".git" </> "packed-refs"
hdExists <- runIO $ doesFileExist hd
when hdExists $ do
splitAt 5 `fmap` runIO (readFile hd) >>= \case
("ref: ", relRef) -> do
let ref = pwd </> ".git" </> relRef
refExists <- runIO $ doesFileExist ref
when refExists $ addDependentFile ref
_hash -> addDependentFile hd
indexExists <- runIO $ doesFileExist index
when (indexExists && useIdx == IdxUsed) $ addDependentFile index
packedExists <- runIO $ doesFileExist packedRefs
when packedExists $ addDependentFile packedRefs
runIO $ do
(code, out, _err) <- readProcessWithExitCode "git" args "" `catch` oops
case code of
ExitSuccess -> return (takeWhile (/= '\n') out)
ExitFailure _ -> return def
else return def
getGitDirectory :: IO FilePath
getGitDirectory = do
pwd <- getCurrentDirectory
let dotGit = pwd </> ".git"
oops = return dotGit
isDir <- doesDirectoryExist dotGit
isFile <- doesFileExist dotGit
if | isDir -> return dotGit
| not isFile -> oops
| isFile ->
splitAt 8 `fmap` readFile dotGit >>= \case
("gitdir: ", relDir) -> do
isRelDir <- doesDirectoryExist relDir
if isRelDir
then return relDir
else oops
_ -> oops
data IndexUsed = IdxUsed
| IdxNotUsed
deriving (Eq)
gitHash :: ExpQ
gitHash =
stringE =<< runGit ["rev-parse", "HEAD"] "UNKNOWN" IdxNotUsed
gitBranch :: ExpQ
gitBranch =
stringE =<< runGit ["rev-parse", "--abbrev-ref", "HEAD"] "UNKNOWN" IdxNotUsed
gitDirty :: ExpQ
gitDirty = do
output <- runGit ["status", "--porcelain"] "" IdxUsed
case output of
"" -> conE falseName
_ -> conE trueName
gitCommitCount :: ExpQ
gitCommitCount =
stringE =<< runGit ["rev-list", "HEAD", "--count"] "UNKNOWN" IdxNotUsed
gitCommitDate :: ExpQ
gitCommitDate =
stringE =<< runGit ["log", "HEAD", "-1", "--format=%cd"] "UNKNOWN" IdxNotUsed