| Copyright | (c) 2018 Michael Snoyman 2015 Adam C. Foltzer |
|---|---|
| License | BSD3 |
| Maintainer | michael@snoyman.com |
| Stability | provisional |
| Portability | portable |
| Safe Haskell | Safe |
| Language | Haskell2010 |
GitHash
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 GitHash
panic :: String -> a
panic msg = error panicMsg
where panicMsg =
concat [ "[panic ", giBranch gi, "@", giHash gi
, " (", giCommitDate gi, ")"
, " (", show (giCommitCount gi), " commits in HEAD)"
, dirty, "] ", msg ]
dirty | giDirty gi = " (uncommitted files present)"
| otherwise = ""
gi = $$tGitInfoCwd
main = panic "oh no!"% stack runghc Example.hs Example.hs: [panic master@2ae047ba5e4a6f0f3e705a43615363ac006099c1 (Mon Jan 11 11:50:59 2016 -0800) (14 commits in HEAD) (uncommitted files present)] oh no!
WARNING: None of this will work in a git repository without any commits.
Since: 0.1.0.0
Synopsis
- data GitInfo
- data GitHashException
- giHash :: GitInfo -> String
- giBranch :: GitInfo -> String
- giDirty :: GitInfo -> Bool
- giCommitDate :: GitInfo -> String
- giCommitCount :: GitInfo -> Int
- giCommitMessage :: GitInfo -> String
- giDescribe :: GitInfo -> String
- getGitInfo :: FilePath -> IO (Either GitHashException GitInfo)
- getGitRoot :: FilePath -> IO (Either GitHashException FilePath)
- tGitInfo :: FilePath -> Q (TExp GitInfo)
- tGitInfoCwd :: Q (TExp GitInfo)
- tGitInfoTry :: FilePath -> Q (TExp (Either String GitInfo))
- tGitInfoCwdTry :: Q (TExp (Either String GitInfo))
Types
Various pieces of information about a Git repository.
Since: 0.1.0.0
data GitHashException Source #
Exceptions which can occur when using this library's functions.
Since: 0.1.0.0
Constructors
Instances
| Eq GitHashException Source # | |
Defined in GitHash Methods (==) :: GitHashException -> GitHashException -> Bool # (/=) :: GitHashException -> GitHashException -> Bool # | |
| Show GitHashException Source # | |
Defined in GitHash Methods showsPrec :: Int -> GitHashException -> ShowS # show :: GitHashException -> String # showList :: [GitHashException] -> ShowS # | |
| Exception GitHashException Source # | |
Defined in GitHash Methods toException :: GitHashException -> SomeException # | |
Getters
giCommitDate :: GitInfo -> String Source #
giCommitCount :: GitInfo -> Int Source #
giCommitMessage :: GitInfo -> String Source #
The message of the most recent commit.
Since: 0.1.1.0
giDescribe :: GitInfo -> String Source #
The output of git describe --always for the most recent commit.
Since: 0.1.4.0
Creators
getGitInfo :: FilePath -> IO (Either GitHashException GitInfo) Source #
Get the GitInfo for the given root directory. Root directory
should be the directory containing the .git directory.
Since: 0.1.0.0
getGitRoot :: FilePath -> IO (Either GitHashException FilePath) Source #
Get the root directory of the Git repo containing the given file path.
Since: 0.1.0.0
Template Haskell
tGitInfo :: FilePath -> Q (TExp GitInfo) Source #
Load up the GitInfo value at compile time for the given
directory. Compilation fails if no info is available.
Since: 0.1.0.0
tGitInfoCwd :: Q (TExp GitInfo) Source #
Load up the GitInfo value at compile time for the current
working directory.
Since: 0.1.0.0