hgrev: Compile Mercurial (hg) version info into Haskell code
- Overview
 
hgrev provides two modules:
Development.HgRev- Mercurial (hg) Haskell APIDevelopment.HgRev.TH- Template Haskell splice to compile version info into Haskell code
Use $(hgRevStateTH defFormat) with Template Haskell enabled to insert the
formatted version string.
- Requirements
 
hgrev requires the hg binary version 3.2 or greater is installed and available on the system.
Development.HgRev.HgRev and Development.HgRev.HgState are obtained via two
separate calls to hg because working directory state isn't available programmatically.
- Usage Example
 
module Example where
import           Data.Monoid          ((<>))
import           Data.Text            (Text, pack)
import           Development.HgRev.TH (defFormat, hgRevStateTH, jsonFormat)
import           Options.Applicative  (Parser, ParserInfo, execParser, fullDesc,
                                       help, helper, info, infoOption, long,
                                       progDesc, short)
main :: IO ()
main = execParser parserInfo >> return ()
verSwitch :: Parser (a -> a)
verSwitch =
    infoOption ("HG rev: " <> $(hgRevStateTH defFormat))
    $  long "version"
    <> short 'v'
    <> help "Display version information"
jsonSwitch :: Parser (a -> a)
jsonSwitch =
    infoOption $(hgRevStateTH jsonFormat)
    $  long "json"
    <> short 'J'
    <> help "Display JSON version information"
parserInfo :: ParserInfo (a -> a)
parserInfo = info (helper <*> verSwitch <* jsonSwitch) fullDesc
Check out the gitrev package for similar git functionality.
[Skip to Readme]
Downloads
- hgrev-0.2.6.tar.gz [browse] (Cabal source package)
 - Package description (as included in the package)
 
Maintainer's Corner
For package maintainers and hackage trustees
Candidates
| Versions [RSS] | 0.1.0.0, 0.1.1, 0.1.2, 0.1.3, 0.1.4, 0.1.5, 0.2.0, 0.2.1, 0.2.2, 0.2.3, 0.2.4, 0.2.5, 0.2.6 | 
|---|---|
| Dependencies | aeson (>=0.8 && <1.6), base (>=4.7 && <4.15), bytestring (>=0.10 && <0.11), directory (>=1.2 && <1.4), filepath (>=1.4 && <1.5), process (>=1.2 && <1.7), template-haskell (>=2.10 && <2.17) [details] | 
| License | BSD-3-Clause | 
| Copyright | Bitnomial, Inc. (c) 2016 | 
| Author | Luke Hoersten | 
| Maintainer | luke@bitnomial.com | 
| Category | Development | 
| Home page | https://github.com/bitnomial/hgrev | 
| Bug tracker | https://github.com/bitnomial/hgrev/issues | 
| Source repo | head: git clone git://github.com/bitnomial/hgrev.git | 
| Uploaded | by wraithm at 2020-08-02T00:11:18Z | 
| Distributions | |
| Reverse Dependencies | 1 direct, 0 indirect [details] | 
| Downloads | 8540 total (24 in the last 30 days) | 
| Rating | 2.0 (votes: 1) [estimated by Bayesian average] | 
| Your Rating | |
| Status | Docs available [build log] Last success reported on 2020-08-02 [all 1 reports]  |