From 3d87e2080a27618e70edd1ff2d4160ff959732a6 Mon Sep 17 00:00:00 2001
From: Albert Krewinkel <albert@zeitkraut.de>
Date: Sun, 13 Aug 2017 17:48:43 +0200
Subject: [PATCH] Delete Text.Pandoc.Lua.SharedInstances

Stack instances for common data types are now provides by hslua. The
instance for Either was useful only for a very specific case; the
function that was using the `ToLuaStack Either` instance was rewritten
to work without it.

Closes: #3805
---
 pandoc.cabal                           |  1 -
 src/Text/Pandoc/Lua.hs                 |  1 -
 src/Text/Pandoc/Lua/PandocModule.hs    | 22 ++++++-------
 src/Text/Pandoc/Lua/SharedInstances.hs | 44 --------------------------
 src/Text/Pandoc/Lua/StackInstances.hs  |  1 -
 src/Text/Pandoc/Writers/Custom.hs      |  1 -
 6 files changed, 11 insertions(+), 59 deletions(-)
 delete mode 100644 src/Text/Pandoc/Lua/SharedInstances.hs

diff --git a/pandoc.cabal b/pandoc.cabal
index 988f253cd..52aad4892 100644
--- a/pandoc.cabal
+++ b/pandoc.cabal
@@ -465,7 +465,6 @@ Library
                    Text.Pandoc.Readers.Org.Parsing,
                    Text.Pandoc.Readers.Org.Shared,
                    Text.Pandoc.Lua.PandocModule,
-                   Text.Pandoc.Lua.SharedInstances,
                    Text.Pandoc.Lua.StackInstances,
                    Text.Pandoc.Lua.Util,
                    Text.Pandoc.CSS,
diff --git a/src/Text/Pandoc/Lua.hs b/src/Text/Pandoc/Lua.hs
index 264364006..6190a5fcf 100644
--- a/src/Text/Pandoc/Lua.hs
+++ b/src/Text/Pandoc/Lua.hs
@@ -44,7 +44,6 @@ import Foreign.Lua (Lua, FromLuaStack (peek), LuaException (..), StackIndex,
                     registryindex, runLua, setglobal, throwLuaError)
 import Text.Pandoc.Definition
 import Text.Pandoc.Lua.PandocModule (pushPandocModule)
-import Text.Pandoc.Lua.StackInstances ()
 import Text.Pandoc.Walk (Walkable (walkM))
 
 import qualified Data.Map as Map
diff --git a/src/Text/Pandoc/Lua/PandocModule.hs b/src/Text/Pandoc/Lua/PandocModule.hs
index c8eaf3da0..afb9aeca6 100644
--- a/src/Text/Pandoc/Lua/PandocModule.hs
+++ b/src/Text/Pandoc/Lua/PandocModule.hs
@@ -31,10 +31,9 @@ import Control.Monad (unless)
 import Data.ByteString.Char8 (unpack)
 import Data.Default (Default (..))
 import Data.Text (pack)
-import Foreign.Lua (Lua, Status (OK), liftIO, push, pushHaskellFunction)
-import Foreign.Lua.Api (call, loadstring, rawset)
-import Text.Pandoc.Class
-import Text.Pandoc.Definition (Pandoc)
+import Foreign.Lua (Lua, Status (OK), NumResults, call, loadstring, liftIO,
+                    push, pushHaskellFunction, rawset)
+import Text.Pandoc.Class (readDataFile, runIO, runIOorExplode, setUserDataDir)
 import Text.Pandoc.Options (ReaderOptions(readerExtensions))
 import Text.Pandoc.Lua.StackInstances ()
 import Text.Pandoc.Readers (Reader (..), getReader)
@@ -54,16 +53,17 @@ pandocModuleScript :: Maybe FilePath -> IO String
 pandocModuleScript datadir = unpack <$>
   runIOorExplode (setUserDataDir datadir >> readDataFile "pandoc.lua")
 
-readDoc :: String -> String -> Lua (Either String Pandoc)
-readDoc formatSpec content = liftIO $ do
+readDoc :: String -> String -> Lua NumResults
+readDoc formatSpec content = do
   case getReader formatSpec of
-    Left  s      -> return $ Left s
+    Left  s      -> push s -- Unknown reader
     Right (reader, es) ->
       case reader of
         TextReader r -> do
-          res <- runIO $ r def{ readerExtensions = es } (pack content)
+          res <- liftIO $ runIO $ r def{ readerExtensions = es } (pack content)
           case res of
-            Left s   -> return . Left $ show s
-            Right pd -> return $ Right pd
-        _  -> return $ Left "Only string formats are supported at the moment."
+            Left s   -> push $ show s -- error while reading
+            Right pd -> push pd       -- success, push Pandoc
+        _  -> push "Only string formats are supported at the moment."
+  return 1
 
diff --git a/src/Text/Pandoc/Lua/SharedInstances.hs b/src/Text/Pandoc/Lua/SharedInstances.hs
deleted file mode 100644
index e9e72c219..000000000
--- a/src/Text/Pandoc/Lua/SharedInstances.hs
+++ /dev/null
@@ -1,44 +0,0 @@
-{-
-Copyright © 2012-2017 John MacFarlane <jgm@berkeley.edu>
-            2017 Albert Krewinkel <tarleb+pandoc@moltkeplatz.de>
-
-This program is free software; you can redistribute it and/or modify
-it under the terms of the GNU General Public License as published by
-the Free Software Foundation; either version 2 of the License, or
-(at your option) any later version.
-
-This program is distributed in the hope that it will be useful,
-but WITHOUT ANY WARRANTY; without even the implied warranty of
-MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
-GNU General Public License for more details.
-
-You should have received a copy of the GNU General Public License
-along with this program; if not, write to the Free Software
-Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA  02111-1307  USA
--}
-{-# LANGUAGE CPP                  #-}
-{-# LANGUAGE FlexibleInstances    #-}
-{-# LANGUAGE LambdaCase           #-}
-#if !MIN_VERSION_base(4,8,0)
-{-# LANGUAGE OverlappingInstances #-}
-#endif
-{-# OPTIONS_GHC -fno-warn-orphans #-}
-{- |
-   Module      : Text.Pandoc.Lua.SharedInstances
-   Copyright   : © 2012–2016 John MacFarlane,
-                 © 2017 Albert Krewinkel
-   License     : GNU GPL, version 2 or above
-
-   Maintainer  : Albert Krewinkel <tarleb+pandoc@moltkeplatz.de>
-   Stability   : alpha
-
-Shared StackValue instances for pandoc and generic types.
--}
-module Text.Pandoc.Lua.SharedInstances () where
-
-import Foreign.Lua (ToLuaStack (push))
-
-instance (ToLuaStack a, ToLuaStack b) => ToLuaStack (Either a b) where
-  push = \case
-    Left x -> push x
-    Right x -> push x
diff --git a/src/Text/Pandoc/Lua/StackInstances.hs b/src/Text/Pandoc/Lua/StackInstances.hs
index 7d451a16a..da9c33183 100644
--- a/src/Text/Pandoc/Lua/StackInstances.hs
+++ b/src/Text/Pandoc/Lua/StackInstances.hs
@@ -37,7 +37,6 @@ import Foreign.Lua (Lua, Type (..), FromLuaStack (peek), ToLuaStack (push),
                     StackIndex, throwLuaError, tryLua)
 import Foreign.Lua.Api (getmetatable, ltype, newtable, pop, rawget, rawlen)
 import Text.Pandoc.Definition
-import Text.Pandoc.Lua.SharedInstances ()
 import Text.Pandoc.Lua.Util (addValue, adjustIndexBy, getTable, pushViaConstructor)
 import Text.Pandoc.Shared (safeRead)
 
diff --git a/src/Text/Pandoc/Writers/Custom.hs b/src/Text/Pandoc/Writers/Custom.hs
index 485394187..63725bb60 100644
--- a/src/Text/Pandoc/Writers/Custom.hs
+++ b/src/Text/Pandoc/Writers/Custom.hs
@@ -48,7 +48,6 @@ import Foreign.Lua (Lua, ToLuaStack (..), callFunc, runLua)
 import Foreign.Lua.Api
 import Text.Pandoc.Error
 import Text.Pandoc.Lua.Util ( addValue )
-import Text.Pandoc.Lua.SharedInstances ()
 import Text.Pandoc.Definition
 import Text.Pandoc.Options
 import Text.Pandoc.Templates