From 9d7c01e4a412d488ca958df2d74a6231f24483c8 Mon Sep 17 00:00:00 2001
From: John MacFarlane <jgm@berkeley.edu>
Date: Mon, 11 Apr 2022 09:33:41 -0700
Subject: [PATCH] Add info about git commit and date to `--version` info.

See #8016.
---
 pandoc.cabal                              | 3 ++-
 src/Text/Pandoc/App/CommandLineOptions.hs | 9 ++++++++-
 2 files changed, 10 insertions(+), 2 deletions(-)

diff --git a/pandoc.cabal b/pandoc.cabal
index 6b4c0b8ad..5cd2fa334 100644
--- a/pandoc.cabal
+++ b/pandoc.cabal
@@ -528,7 +528,8 @@ library
                  xml-types             >= 0.3      && < 0.4,
                  yaml                  >= 0.11     && < 0.12,
                  zip-archive           >= 0.2.3.4  && < 0.5,
-                 zlib                  >= 0.5      && < 0.7
+                 zlib                  >= 0.5      && < 0.7,
+                 githash               >= 0.1.6.2  && < 0.2
   if !os(windows)
     build-depends:  unix >= 2.4 && < 2.8
   if flag(lua53)
diff --git a/src/Text/Pandoc/App/CommandLineOptions.hs b/src/Text/Pandoc/App/CommandLineOptions.hs
index ffb7c5eb8..9328fff1f 100644
--- a/src/Text/Pandoc/App/CommandLineOptions.hs
+++ b/src/Text/Pandoc/App/CommandLineOptions.hs
@@ -5,6 +5,7 @@
 {-# LANGUAGE OverloadedStrings   #-}
 {-# LANGUAGE FlexibleContexts    #-}
 {-# LANGUAGE TypeApplications    #-}
+{-# LANGUAGE TemplateHaskell     #-}
 {- |
    Module      : Text.Pandoc.App.CommandLineOptions
    Copyright   : Copyright (C) 2006-2022 John MacFarlane
@@ -70,6 +71,7 @@ import qualified Data.ByteString.Lazy as B
 import qualified Data.Map as M
 import qualified Data.Text as T
 import qualified Text.Pandoc.UTF8 as UTF8
+import GitHash
 
 parseOptions :: [OptDescr (Opt -> IO Opt)] -> Opt -> IO Opt
 parseOptions options' defaults = do
@@ -952,9 +954,14 @@ options =
                        openlibs
                        getglobal "_VERSION"
                        peek top
+                     let buildInfo = either
+                             (\_ -> mempty)
+                             (\gi -> "\nBuilt from commit " ++ giDescribe gi ++
+                                     " on " ++ giCommitDate gi)
+                             $$tGitInfoCwdTry
                      UTF8.hPutStrLn stdout
                       $ T.pack
-                      $ prg ++ " " ++ T.unpack pandocVersion ++
+                      $ prg ++ " " ++ T.unpack pandocVersion ++ buildInfo ++
                         compileInfo ++ "\nScripting engine: " ++ luaVersion ++
                         "\nUser data directory: " ++ defaultDatadir ++
                         ('\n':copyrightMessage)