aboutsummaryrefslogtreecommitdiff
path: root/src/Text/Pandoc/Filter
diff options
context:
space:
mode:
Diffstat (limited to 'src/Text/Pandoc/Filter')
-rw-r--r--src/Text/Pandoc/Filter/JSON.hs20
-rw-r--r--src/Text/Pandoc/Filter/Lua.hs5
2 files changed, 15 insertions, 10 deletions
diff --git a/src/Text/Pandoc/Filter/JSON.hs b/src/Text/Pandoc/Filter/JSON.hs
index c1cbf91a9..e8e737499 100644
--- a/src/Text/Pandoc/Filter/JSON.hs
+++ b/src/Text/Pandoc/Filter/JSON.hs
@@ -1,4 +1,5 @@
{-# LANGUAGE NoImplicitPrelude #-}
+{-# LANGUAGE OverloadedStrings #-}
{- |
Module : Text.Pandoc.Filter
Copyright : Copyright (C) 2006-2019 John MacFarlane
@@ -18,6 +19,7 @@ import Control.Monad.Trans (MonadIO (liftIO))
import Data.Aeson (eitherDecode', encode)
import Data.Char (toLower)
import Data.Maybe (isNothing)
+import qualified Data.Text as T
import System.Directory (executable, doesFileExist, findExecutable,
getPermissions)
import System.Environment (getEnvironment)
@@ -28,7 +30,7 @@ import Text.Pandoc.Error (PandocError (PandocFilterError))
import Text.Pandoc.Definition (Pandoc)
import Text.Pandoc.Options (ReaderOptions)
import Text.Pandoc.Process (pipeProcess)
-import Text.Pandoc.Shared (pandocVersion)
+import Text.Pandoc.Shared (pandocVersion, tshow)
import qualified Control.Exception as E
import qualified Text.Pandoc.UTF8 as UTF8
@@ -61,18 +63,20 @@ externalFilter ropts f args' d = liftIO $ do
unless (exists && isExecutable) $ do
mbExe <- findExecutable f'
when (isNothing mbExe) $
- E.throwIO $ PandocFilterError f ("Could not find executable " ++ f')
+ E.throwIO $ PandocFilterError fText (T.pack $ "Could not find executable " <> f')
env <- getEnvironment
let env' = Just
- ( ("PANDOC_VERSION", pandocVersion)
+ ( ("PANDOC_VERSION", T.unpack pandocVersion)
: ("PANDOC_READER_OPTIONS", UTF8.toStringLazy (encode ropts))
: env )
(exitcode, outbs) <- E.handle filterException $
pipeProcess env' f' args'' $ encode d
case exitcode of
- ExitSuccess -> either (E.throwIO . PandocFilterError f)
+ ExitSuccess -> either (E.throwIO . PandocFilterError fText . T.pack)
return $ eitherDecode' outbs
- ExitFailure ec -> E.throwIO $ PandocFilterError f
- ("Filter returned error status " ++ show ec)
- where filterException :: E.SomeException -> IO a
- filterException e = E.throwIO $ PandocFilterError f (show e)
+ ExitFailure ec -> E.throwIO $ PandocFilterError fText
+ ("Filter returned error status " <> tshow ec)
+ where fText = T.pack f
+
+ filterException :: E.SomeException -> IO a
+ filterException e = E.throwIO $ PandocFilterError fText $ tshow e
diff --git a/src/Text/Pandoc/Filter/Lua.hs b/src/Text/Pandoc/Filter/Lua.hs
index afe525ab1..87c51ac42 100644
--- a/src/Text/Pandoc/Filter/Lua.hs
+++ b/src/Text/Pandoc/Filter/Lua.hs
@@ -15,6 +15,7 @@ module Text.Pandoc.Filter.Lua (apply) where
import Prelude
import Control.Exception (throw)
import Control.Monad ((>=>))
+import qualified Data.Text as T
import Text.Pandoc.Class (PandocIO)
import Text.Pandoc.Definition (Pandoc)
import Text.Pandoc.Error (PandocError (PandocFilterError))
@@ -35,7 +36,7 @@ apply ropts args fp doc = do
(x:_) -> x
_ -> error "Format not supplied for Lua filter"
runLua >=> forceResult fp $ do
- setGlobals [ FORMAT format
+ setGlobals [ FORMAT $ T.pack format
, PANDOC_READER_OPTIONS ropts
, PANDOC_SCRIPT_FILE fp
]
@@ -44,4 +45,4 @@ apply ropts args fp doc = do
forceResult :: FilePath -> Either LuaException Pandoc -> PandocIO Pandoc
forceResult fp eitherResult = case eitherResult of
Right x -> return x
- Left (LuaException s) -> throw (PandocFilterError fp s)
+ Left (LuaException s) -> throw (PandocFilterError (T.pack fp) s)