aboutsummaryrefslogtreecommitdiff
path: root/src/Text/Pandoc/App.hs
diff options
context:
space:
mode:
Diffstat (limited to 'src/Text/Pandoc/App.hs')
-rw-r--r--src/Text/Pandoc/App.hs23
1 files changed, 15 insertions, 8 deletions
diff --git a/src/Text/Pandoc/App.hs b/src/Text/Pandoc/App.hs
index df4bdc151..50464830b 100644
--- a/src/Text/Pandoc/App.hs
+++ b/src/Text/Pandoc/App.hs
@@ -58,6 +58,9 @@ import Data.Monoid
import qualified Data.Set as Set
import Data.Text (Text)
import qualified Data.Text as T
+import qualified Data.Text.Lazy as TL
+import qualified Data.Text.Lazy.Encoding as TE
+import qualified Data.Text.Encoding.Error as TE
import Data.Yaml (decode)
import qualified Data.Yaml as Yaml
import GHC.Generics
@@ -143,7 +146,7 @@ pdfWriterAndProg :: Maybe String -- ^ user-specified writer name
-> IO (String, Maybe String) -- ^ IO (writerName, maybePdfEngineProg)
pdfWriterAndProg mWriter mEngine = do
let panErr msg = liftIO $ E.throwIO $ PandocAppError msg
- case go (baseWriterName <$> mWriter) mEngine of
+ case go mWriter mEngine of
Right (writ, prog) -> return (writ, Just prog)
Left err -> panErr err
where
@@ -151,7 +154,7 @@ pdfWriterAndProg mWriter mEngine = do
go (Just writer) Nothing = (writer,) <$> engineForWriter writer
go Nothing (Just engine) = (,engine) <$> writerForEngine engine
go (Just writer) (Just engine) =
- case find (== (writer, engine)) engines of
+ case find (== (baseWriterName writer, engine)) engines of
Just _ -> Right (writer, engine)
Nothing -> Left $ "pdf-engine " ++ engine ++
" is not compatible with output format " ++ writer
@@ -161,7 +164,7 @@ pdfWriterAndProg mWriter mEngine = do
[] -> Left $
"pdf-engine " ++ eng ++ " not known"
- engineForWriter w = case [e | (f,e) <- engines, f == w] of
+ engineForWriter w = case [e | (f,e) <- engines, f == baseWriterName w] of
eng : _ -> Right eng
[] -> Left $
"cannot produce pdf output from " ++ w
@@ -513,7 +516,9 @@ convertWithOpts opts = do
case res of
Right pdf -> writeFnBinary outputFile pdf
Left err' -> liftIO $
- E.throwIO $ PandocPDFError (UTF8.toStringLazy err')
+ E.throwIO $ PandocPDFError $
+ TL.unpack (TE.decodeUtf8With TE.lenientDecode err')
+
Nothing -> do
let htmlFormat = format `elem`
["html","html4","html5","s5","slidy",
@@ -1584,15 +1589,17 @@ options =
""
, Option "" ["list-extensions"]
- (NoArg
- (\_ -> do
+ (OptArg
+ (\arg _ -> do
+ let exts = getDefaultExtensions (fromMaybe "markdown" arg)
let showExt x = drop 4 (show x) ++
- if extensionEnabled x pandocExtensions
+ if extensionEnabled x exts
then " +"
else " -"
mapM_ (UTF8.hPutStrLn stdout . showExt)
([minBound..maxBound] :: [Extension])
- exitSuccess ))
+ exitSuccess )
+ "FORMAT")
""
, Option "" ["list-highlight-languages"]