From 0ddddf2f37e97ae9ef67150f934eff9ea4700a95 Mon Sep 17 00:00:00 2001
From: John MacFarlane <jgm@berkeley.edu>
Date: Mon, 11 Apr 2022 13:14:38 -0700
Subject: [PATCH] Revert "Add info about git commit and date to `--version`
 info."

This reverts commit 9d7c01e4a412d488ca958df2d74a6231f24483c8.
---
 pandoc.cabal                              | 3 +--
 src/Text/Pandoc/App/CommandLineOptions.hs | 9 +--------
 2 files changed, 2 insertions(+), 10 deletions(-)

diff --git a/pandoc.cabal b/pandoc.cabal
index 5cd2fa334..6b4c0b8ad 100644
--- a/pandoc.cabal
+++ b/pandoc.cabal
@@ -528,8 +528,7 @@ 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,
-                 githash               >= 0.1.6.2  && < 0.2
+                 zlib                  >= 0.5      && < 0.7
   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 9328fff1f..ffb7c5eb8 100644
--- a/src/Text/Pandoc/App/CommandLineOptions.hs
+++ b/src/Text/Pandoc/App/CommandLineOptions.hs
@@ -5,7 +5,6 @@
 {-# LANGUAGE OverloadedStrings   #-}
 {-# LANGUAGE FlexibleContexts    #-}
 {-# LANGUAGE TypeApplications    #-}
-{-# LANGUAGE TemplateHaskell     #-}
 {- |
    Module      : Text.Pandoc.App.CommandLineOptions
    Copyright   : Copyright (C) 2006-2022 John MacFarlane
@@ -71,7 +70,6 @@ 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
@@ -954,14 +952,9 @@ 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 ++ buildInfo ++
+                      $ prg ++ " " ++ T.unpack pandocVersion ++
                         compileInfo ++ "\nScripting engine: " ++ luaVersion ++
                         "\nUser data directory: " ++ defaultDatadir ++
                         ('\n':copyrightMessage)