module Git.Embed
( embedGitRevision
, embedGitShortRevision
, embedGitBranch
, embedGitDescribe
, embedGit )
where
import Data.Char (isSpace)
import Data.List (dropWhileEnd)
import Language.Haskell.TH.Syntax
( Exp (LitE)
, Lit (StringL)
, Q
, Quasi(qAddDependentFile)
, runIO )
import System.Directory (getDirectoryContents, doesDirectoryExist)
import System.Environment (lookupEnv)
import System.FilePath (combine)
import System.Process (readProcess)
embedGitRevision :: Q Exp
embedGitRevision = embedGit ["rev-parse", "HEAD"]
embedGitShortRevision :: Q Exp
embedGitShortRevision = embedGit ["rev-parse", "--short", "HEAD"]
embedGitBranch :: Q Exp
embedGitBranch = embedGit ["rev-parse", "--abbrev-ref", "HEAD"]
embedGitDescribe :: [String]
-> Q Exp
embedGitDescribe args = embedGit ("describe" : args)
embedGit :: [String]
-> Q Exp
embedGit args = do
addRefDependentFiles
gitOut <- runIO (readProcess "git" args "")
return $! LitE (StringL (dropWhileEnd isSpace gitOut))
addRefDependentFiles :: Q ()
addRefDependentFiles = do
gitDir <- runIO findGitDir
qAddDependentFile (combine gitDir "HEAD")
addDirDeps (combine gitDir "refs")
where
findGitDir = do
maybeGitDir <- lookupEnv "GIT_DIR"
case maybeGitDir of
Just dir -> return dir
Nothing -> fmap (\x -> combine (dropWhileEnd isSpace x) ".git")
(readProcess "git" ["rev-parse", "--show-cdup"] "")
addDirDeps dir = do
subPaths <- runIO (fmap (map (combine dir) . filter notHidden)
(getDirectoryContents dir))
mapM_ recursePath subPaths
recursePath path = do
isDir <- runIO (doesDirectoryExist path)
if isDir
then addDirDeps path
else qAddDependentFile path
notHidden ('.':_) = False
notHidden _ = True