gitrev-typed: Compile git revision info into Haskell projects

This is a package candidate release! Here you can preview how this package release will appear once published to the main package index (which can be accomplished via the 'maintain' link below). Please note that once a package has been published to the main package index it cannot be undone! Please consult the package uploading documentation for more information.

[maintain] [Publish]

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.


[Skip to Readme]

Properties

Versions 0.1
Change log CHANGELOG.md
Dependencies base (>=4.15.0.0 && <4.22), directory (>=1.3.8.0 && <1.4), file-io (>=0.1.1 && <0.2), filepath (>=1.5.2.0 && <1.6), os-string (>=2.0.0 && <2.1), process (>=1.6.13.2 && <1.7), template-haskell (>=2.17.0.0 && <2.24), text (>=2.0.1 && <2.2) [details]
License BSD-3-Clause
Author Adam C. Foltzer
Maintainer tbidne@protonmail.com
Category Development
Home page https://github.com/tbidne/gitrev
Source repo head: git clone https://github.com/tbidne/gitrev.git
Uploaded by tbidne at 2025-04-18T21:34:13Z

Modules

[Index] [Quick Jump]

Downloads

Maintainer's Corner

Package maintainers

For package maintainers and hackage trustees


Readme for gitrev-typed-0.1

[back to package description]

Gitrev-typed

Embedding git metadata in haskell projects

Hackage haskell ci BSD-3-Clause


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.

There are two main interfaces:

1. Development.GitRev

This module provides untyped splices e.g.

-- Definition in Development.GitRev
gitHash :: ExpQ
{-# LANGUAGE TemplateHaskell #-}

import Development.GitRev qualified as GR

-- Returns a hash like "e67e943dd03744d3f93c21f84e127744e6a04543" or
-- "UNKNOWN", if something goes wrong.
myHash :: String
myHash = $(GR.gitHash)

2. Development.GitRev.Typed

This module -- on the other hand -- provides typed splices e.g.

-- Definition in Development.GitRev.Typed
gitHash :: Code Q String
{-# LANGUAGE TemplateHaskell #-}

import Development.GitRev.Typed qualified as GRT

-- Returns a hash like "e67e943dd03744d3f93c21f84e127744e6a04543" or
-- "UNKNOWN", if something goes wrong.
myHash :: String
myHash = $$(GRT.gitHash)

We also provide combinators for defining custom behavior. For instance, we can instead define a variant that fails at compile-time instead of returning the string UNKNOWN.

-- gitHashQ :: Q (Either GitError String)
-- projectError :: Q (Either GitError String) -> Q String
-- qToCode :: Q a -> Code Q a
myHashOrDie :: String
myHashOrDie = $$(GRT.qToCode $ GRT.projectError GRT.gitHashQ)

Out-of-tree builds

Furthermore, we have workarounds for "out-of-tree" builds:

myHashEnv :: Code Q String
myHashEnv = toCode gitHash
  where
    toCode :: Q (Either (Exceptions GitOrLookupEnvError) String) -> Code Q String
    toCode = GRT.qToCode . GRT.projectError

    gitHash :: Q (Either (Exceptions GitOrLookupEnvError) String)
    gitHash =
      -- Tries, in order:
      --
      -- 1. Retrieving the git hash, as normal.
      -- 2. Looking up environment variable EXAMPLE_HASH, returning the
      --    value if it exists.
      -- 3. Running the git action under the directory pointed to by the
      --    environment variable EXAMPLE_HOME, if it exists.
      GRT.firstSuccessQ
        (GRT.embedGitError GRT.gitHashQ)
        [ GRT.embedLookupEnvError $ GRT.envValQ "EXAMPLE_HASH",
          GRT.runGitInEnvDirQ "EXAMPLE_HOME" GRT.gitHashQ
        ]

For example, myHashEnv will work for cabal install if we include the environment variable:

$ export EXAMPLE_HOME=$(pwd); cabal install example

This function will also work with nix flakes:

# flake.nix
let
  compiler = pkgs.haskell.packages."ghc9101";
in
{
  # Using nixpkgs haskell infra i.e. developPackage.
  packages.default = compiler.developPackage {
    name = "example";
    root = ./.;
    returnShellEnv = false;
    modifier =
      drv:
      let
        drv' = pkgs.haskell.lib.addBuildTools drv [
          compiler.cabal-install
          compiler.ghc
          pkgs.git
          pkgs.zlib
        ];
      in
      drv'.overrideAttrs (oldAttrs: {
        EXAMPLE_HASH = "${self.rev or self.dirtyRev}";
      });
  };
};

See example in the flake.nix for a full nix example, and Development.GitRev.Typed for full documentation.

Addendum

Most of the complication is due to the various places the current git hash might be stored:

  1. Detached HEAD: the hash is in .git/HEAD
  2. On a branch or tag: the hash is in a file pointed to by .git/HEAD in a location like .git/refs/heads
  3. On a branch or tag but in a repository with packed refs: the hash is in .git/packed-refs
  4. In any of the above situations, if the current repo is checked out as a submodule, follow the reference to its .git directory first

These files are added as dependencies to modules that use GitRev, and so the module should be rebuilt automatically whenever these files change.

If you run into further scenarios that cause problems, let me know!