From d7cfa0ef4c926d6bb91d0a870edeea8911d81c3a Mon Sep 17 00:00:00 2001
From: John MacFarlane <jgm@berkeley.edu>
Date: Mon, 22 Feb 2021 22:10:20 -0800
Subject: [PATCH] Remove weigh-pandoc.

It's not really useful any more, now that our regular
benchmarks include data on allocation.
---
 benchmark/weigh-pandoc.hs | 48 ---------------------------------------
 pandoc.cabal              |  8 -------
 2 files changed, 56 deletions(-)
 delete mode 100644 benchmark/weigh-pandoc.hs

diff --git a/benchmark/weigh-pandoc.hs b/benchmark/weigh-pandoc.hs
deleted file mode 100644
index b77fa9ee9..000000000
--- a/benchmark/weigh-pandoc.hs
+++ /dev/null
@@ -1,48 +0,0 @@
-{-# LANGUAGE OverloadedStrings #-}
-{- |
-   Module      : Main
-   Copyright   : © 2016-2021 John MacFarlane <jgm@berkeley.edu>
-   License     : GNU GPL, version 2 or above
-
-   Maintainer  : John MacFarlane <jgm@berkeley.edu>
-   Stability   : alpha
-   Portability : portable
-
-Benchmarks to determine resource use of readers and writers.
--}
-import Weigh
-import Text.Pandoc
-import Data.Text (Text, unpack)
-
-main :: IO ()
-main = do
-  doc <- read <$> readFile "test/testsuite.native"
-  mainWith $ do
-    func "Pandoc document" id doc
-    mapM_
-      (\(n,r) -> weighReader doc n (either (error . show) id . runPure . r def{readerExtensions = pandocExtensions}))
-      [("markdown", readMarkdown)
-      ,("html", readHtml)
-      ,("docbook", readDocBook)
-      ,("latex", readLaTeX)
-      ,("commonmark", readCommonMark)
-      ]
-    mapM_
-      (\(n,w) -> weighWriter doc n (either (error . show) id . runPure . w def))
-      [("markdown", writeMarkdown)
-      ,("html", writeHtml5String)
-      ,("docbook", writeDocbook5)
-      ,("latex", writeLaTeX)
-      ,("commonmark", writeCommonMark)
-      ]
-
-weighWriter :: Pandoc -> String -> (Pandoc -> Text) -> Weigh ()
-weighWriter doc name writer = func (name ++ " writer") writer doc
-
-weighReader :: Pandoc -> Text -> (Text -> Pandoc) -> Weigh ()
-weighReader doc name reader =
-  case lookup name writers of
-       Just (TextWriter writer) ->
-         let inp = either (error . show) id $ runPure $ writer def{ writerWrapText = WrapAuto} doc
-         in func (unpack $ name <> " reader") reader inp
-       _ -> return () -- no writer for reader
diff --git a/pandoc.cabal b/pandoc.cabal
index 30226f445..e4001abb8 100644
--- a/pandoc.cabal
+++ b/pandoc.cabal
@@ -725,14 +725,6 @@ executable trypandoc
   else
     buildable:     False
 
-benchmark weigh-pandoc
-  import:          common-executable
-  type:            exitcode-stdio-1.0
-  main-is:         weigh-pandoc.hs
-  hs-source-dirs:  benchmark
-  build-depends:   mtl     >= 2.2 && < 2.3,
-                   weigh   >= 0.0 && < 0.1,
-
 test-suite test-pandoc
   import:         common-executable
   type:           exitcode-stdio-1.0