From 743419af5c0872d8e4b5fdf53d47080e8648b4a7 Mon Sep 17 00:00:00 2001
From: John MacFarlane <jgm@berkeley.edu>
Date: Sat, 24 Jun 2017 13:47:10 +0200
Subject: [PATCH] Readers.getReader, Writers.getWriter API change.

Now these functions return a pair of a reader/writer and an
Extensions, instead of building the extensions into the
reader/writer.  The calling code must explicitly set
readerExtensions or writerExtensions using the Extensions
returned.

The point of the change is to make it possible for the
calling code to determine what extensions are being used.

See #3659.
---
 src/Text/Pandoc/App.hs              | 14 +++++++++-----
 src/Text/Pandoc/Lua/PandocModule.hs |  5 +++--
 src/Text/Pandoc/Readers.hs          | 12 ++++--------
 src/Text/Pandoc/Writers.hs          | 11 ++++-------
 trypandoc/trypandoc.hs              | 10 ++++++----
 5 files changed, 26 insertions(+), 26 deletions(-)

diff --git a/src/Text/Pandoc/App.hs b/src/Text/Pandoc/App.hs
index 3c259fce7..ee74d39c0 100644
--- a/src/Text/Pandoc/App.hs
+++ b/src/Text/Pandoc/App.hs
@@ -182,11 +182,12 @@ convertWithOpts opts = do
   let msOutput = format == "ms"
 
   -- disabling the custom writer for now
-  writer <- if ".lua" `isSuffixOf` format
+  (writer, writerExts) <-
+            if ".lua" `isSuffixOf` format
                -- note:  use non-lowercased version writerName
                then return (TextWriter
                        (\o d -> liftIO $ writeCustom writerName o d)
-                               :: Writer PandocIO)
+                               :: Writer PandocIO, mempty)
                else case getWriter writerName of
                          Left e  -> E.throwIO $ PandocAppError $
                            if format == "pdf"
@@ -196,12 +197,13 @@ convertWithOpts opts = do
                                "\nand specify an output file with " ++
                                ".pdf extension (-o filename.pdf)."
                               else e
-                         Right w -> return (w :: Writer PandocIO)
+                         Right (w, es) -> return (w :: Writer PandocIO, es)
 
   -- TODO: we have to get the input and the output into the state for
   -- the sake of the text2tags reader.
-  reader <-  case getReader readerName of
-                Right r  -> return (r :: Reader PandocIO)
+  (reader, readerExts) <-
+           case getReader readerName of
+                Right (r, es) -> return (r :: Reader PandocIO, es)
                 Left e   -> E.throwIO $ PandocAppError e'
                   where e' = case readerName of
                                   "pdf" -> e ++
@@ -310,6 +312,7 @@ convertWithOpts opts = do
                          optDefaultImageExtension opts
                       , readerTrackChanges = optTrackChanges opts
                       , readerAbbreviations = abbrevs
+                      , readerExtensions = readerExts
                       }
 
   highlightStyle <- lookupHighlightStyle $ optHighlightStyle opts
@@ -340,6 +343,7 @@ convertWithOpts opts = do
                             writerNumberSections   = optNumberSections opts,
                             writerNumberOffset     = optNumberOffset opts,
                             writerSectionDivs      = optSectionDivs opts,
+                            writerExtensions       = writerExts,
                             writerReferenceLinks   = optReferenceLinks opts,
                             writerReferenceLocation = optReferenceLocation opts,
                             writerDpi              = optDpi opts,
diff --git a/src/Text/Pandoc/Lua/PandocModule.hs b/src/Text/Pandoc/Lua/PandocModule.hs
index 27c19d4f0..fccfbebf3 100644
--- a/src/Text/Pandoc/Lua/PandocModule.hs
+++ b/src/Text/Pandoc/Lua/PandocModule.hs
@@ -34,6 +34,7 @@ import Data.Text (pack)
 import Scripting.Lua (LuaState, call, push, pushhsfunction, rawset)
 import Text.Pandoc.Class hiding (readDataFile)
 import Text.Pandoc.Definition (Pandoc)
+import Text.Pandoc.Options (ReaderOptions(readerExtensions))
 import Text.Pandoc.Lua.Compat (loadstring)
 import Text.Pandoc.Lua.StackInstances ()
 import Text.Pandoc.Readers (Reader (..), getReader)
@@ -57,10 +58,10 @@ read_doc :: String -> String -> IO (Either String Pandoc)
 read_doc formatSpec content = do
   case getReader formatSpec of
     Left  s      -> return $ Left s
-    Right reader ->
+    Right (reader, es) ->
       case reader of
         TextReader r -> do
-          res <- runIO $ r def (pack content)
+          res <- runIO $ r def{ readerExtensions = es } (pack content)
           case res of
             Left s   -> return . Left $ show s
             Right pd -> return $ Right pd
diff --git a/src/Text/Pandoc/Readers.hs b/src/Text/Pandoc/Readers.hs
index 20e503a7e..0374d27d5 100644
--- a/src/Text/Pandoc/Readers.hs
+++ b/src/Text/Pandoc/Readers.hs
@@ -133,20 +133,16 @@ readers = [ ("native"       , TextReader readNative)
            ,("muse"         , TextReader readMuse)
            ]
 
--- | Retrieve reader based on formatSpec (format+extensions).
-getReader :: PandocMonad m => String -> Either String (Reader m)
+-- | Retrieve reader, extensions based on formatSpec (format+extensions).
+getReader :: PandocMonad m => String -> Either String (Reader m, Extensions)
 getReader s =
   case parseFormatSpec s of
        Left e  -> Left $ intercalate "\n" [m | Message m <- errorMessages e]
        Right (readerName, setExts) ->
            case lookup readerName readers of
                    Nothing  -> Left $ "Unknown reader: " ++ readerName
-                   Just  (TextReader r)  -> Right $ TextReader $ \o ->
-                                  r o{ readerExtensions = setExts $
-                                            getDefaultExtensions readerName }
-                   Just (ByteStringReader r) -> Right $ ByteStringReader $ \o ->
-                                  r o{ readerExtensions = setExts $
-                                            getDefaultExtensions readerName }
+                   Just  r  -> Right (r, setExts $
+                                        getDefaultExtensions readerName)
 
 -- | Read pandoc document from JSON format.
 readJSON :: ReaderOptions -> Text -> Either PandocError Pandoc
diff --git a/src/Text/Pandoc/Writers.hs b/src/Text/Pandoc/Writers.hs
index dbe55449f..6dfc1a7b3 100644
--- a/src/Text/Pandoc/Writers.hs
+++ b/src/Text/Pandoc/Writers.hs
@@ -176,19 +176,16 @@ writers = [
   ,("muse"         , TextWriter writeMuse)
   ]
 
-getWriter :: PandocMonad m => String -> Either String (Writer m)
+-- | Retrieve writer, extensions based on formatSpec (format+extensions).
+getWriter :: PandocMonad m => String -> Either String (Writer m, Extensions)
 getWriter s
   = case parseFormatSpec s of
          Left e  -> Left $ intercalate "\n" [m | Message m <- errorMessages e]
          Right (writerName, setExts) ->
              case lookup writerName writers of
                      Nothing -> Left $ "Unknown writer: " ++ writerName
-                     Just (TextWriter r) -> Right $ TextWriter $
-                             \o -> r o{ writerExtensions = setExts $
-                                              getDefaultExtensions writerName }
-                     Just (ByteStringWriter r) -> Right $ ByteStringWriter $
-                             \o -> r o{ writerExtensions = setExts $
-                                              getDefaultExtensions writerName }
+                     Just r -> Right (r, setExts $
+                                  getDefaultExtensions writerName)
 
 writeJSON :: WriterOptions -> Pandoc -> Text
 writeJSON _ = UTF8.toText . BL.toStrict . encode
diff --git a/trypandoc/trypandoc.hs b/trypandoc/trypandoc.hs
index b8b821883..5a4828877 100644
--- a/trypandoc/trypandoc.hs
+++ b/trypandoc/trypandoc.hs
@@ -3,15 +3,15 @@ module Main where
 import Network.Wai.Handler.CGI
 import Network.Wai
 import Control.Applicative ((<$>))
-import Data.Maybe (mapMaybe, fromMaybe)
+import Data.Maybe (fromMaybe)
 import Network.HTTP.Types.Status (status200)
 import Network.HTTP.Types.Header (hContentType)
 import Network.HTTP.Types.URI (queryToQueryText)
 import Text.Pandoc
+import Text.Pandoc.Writers.Math (defaultMathJaxURL)
 import Text.Pandoc.Highlighting (pygments)
 import Text.Pandoc.Readers (getReader, Reader(..))
 import Text.Pandoc.Writers (getWriter, Writer(..))
-import Text.Pandoc.Error (PandocError)
 import Text.Pandoc.Shared (tabFilter)
 import Data.Aeson
 import qualified Data.Text as T
@@ -29,11 +29,13 @@ app req respond = do
   fromFormat <- fromMaybe "" <$> getParam "from"
   toFormat <- fromMaybe "" <$> getParam "to"
   let reader = case getReader (T.unpack fromFormat) of
-                    Right (TextReader r) -> r readerOpts
+                    Right (TextReader r, es) -> r readerOpts{
+                       readerExtensions = es }
                     _ -> error $ "could not find reader for "
                                   ++ T.unpack fromFormat
   let writer = case getWriter (T.unpack toFormat) of
-                    Right (TextWriter w) -> w writerOpts
+                    Right (TextWriter w, es) -> w writerOpts{
+                       writerExtensions = es }
                     _ -> error $ "could not find writer for " ++
                            T.unpack toFormat
   let result = case runPure $ reader (tabFilter 4 text) >>= writer of