gitrev-1.1.0: Compile git revision info into Haskell projects

Copyright(c) 2015 Adam C. Foltzer
LicenseBSD3
Maintaineracfoltzer@galois.com
Stabilityprovisional
Portabilityportable
Safe HaskellNone
LanguageHaskell2010

Development.GitRev

Description

Some handy Template Haskell splices for including the current git hash and branch in the code of your project. Useful for including in panic messages, --version output, or diagnostic info for more informative bug reports.

{-# LANGUAGE TemplateHaskell #-}
import Development.GitRev

panic :: String -> a
panic msg = error panicMsg
  where panicMsg =
          concat [ "[panic ", $(gitBranch), "@", $(gitHash)
                 , " (", $(gitCommitCount), " commits in HEAD)"
                 , dirty, "] ", msg ]
        dirty | $(gitDirty) = " (uncommitted files present)"
              | otherwise   = ""

main = panic "oh no!"
% cabal exec runhaskell Example.hs
Example.hs: [panic master@2702e69355c978805064543489c351b61ac6760b (6 commits in HEAD) (uncommitted files present)] oh no!

Synopsis

Documentation

gitHash :: ExpQ Source

Return the hash of the current git commit, or UNKNOWN if not in a git repository

gitBranch :: ExpQ Source

Return the branch (or tag) name of the current git commit, or UNKNOWN if not in a git repository. For detached heads, this will just be HEAD

gitDirty :: ExpQ Source

Return True if there are non-committed files present in the repository

gitCommitCount :: ExpQ Source

Return the number of commits in the current head