aboutsummaryrefslogtreecommitdiff
path: root/pandoc-lua-engine
diff options
context:
space:
mode:
authorAlbert Krewinkel <[email protected]>2022-10-07 21:16:45 +0200
committerJohn MacFarlane <[email protected]>2022-10-08 16:05:48 -0700
commita4218b9719c77978e1968065a3c2c4f25d3c4137 (patch)
tree2335115e82577031786f766a122ae400ac3dcc5a /pandoc-lua-engine
parente663bb0e1479dac2638a3e4f693e5eeac314e347 (diff)
[API Change] Add new module "Text.Pandoc.Format"
The module provides functions and types for format spec parsing and processing. The function `parseFormatSpec` was moved from Text.Pandoc.Extensions to the new module and renamed to `parseFlavoredFormat`. It now operates in a PandocMonad and is based on the updated types.
Diffstat (limited to 'pandoc-lua-engine')
-rw-r--r--pandoc-lua-engine/src/Text/Pandoc/Lua/Module/Pandoc.hs45
-rw-r--r--pandoc-lua-engine/test/lua/module/pandoc.lua4
2 files changed, 19 insertions, 30 deletions
diff --git a/pandoc-lua-engine/src/Text/Pandoc/Lua/Module/Pandoc.hs b/pandoc-lua-engine/src/Text/Pandoc/Lua/Module/Pandoc.hs
index ec77e2df6..1fdc6fd65 100644
--- a/pandoc-lua-engine/src/Text/Pandoc/Lua/Module/Pandoc.hs
+++ b/pandoc-lua-engine/src/Text/Pandoc/Lua/Module/Pandoc.hs
@@ -206,32 +206,21 @@ functions =
=?> "output string, or error triple"
, defun "read"
- ### (\content mformatspec mreaderOptions -> do
+ ### (\content mformatspec mreaderOptions -> unPandocLua $ do
+ let readerOpts = fromMaybe def mreaderOptions
let formatSpec = fromMaybe "markdown" mformatspec
- readerOpts = fromMaybe def mreaderOptions
- readAction = getReader formatSpec >>= \case
- (TextReader r, es) ->
- r readerOpts{readerExtensions = es}
- (case content of
- Left bs -> toSources $ UTF8.toText bs
- Right sources -> sources)
- (ByteStringReader r, es) ->
- case content of
- Left bs -> r readerOpts{readerExtensions = es}
- (BSL.fromStrict bs)
- Right _ -> liftPandocLua $ Lua.failLua
- "Cannot use bytestring reader with Sources"
- try (unPandocLua readAction) >>= \case
- Right pd ->
- -- success, got a Pandoc document
- return pd
- Left (PandocUnknownReaderError f) ->
- Lua.failLua . T.unpack $ "Unknown reader: " <> f
- Left (PandocUnsupportedExtensionError e f) ->
- Lua.failLua . T.unpack $
- "Extension " <> e <> " not supported for " <> f
- Left e ->
- throwM e)
+ getReader formatSpec >>= \case
+ (TextReader r, es) ->
+ r readerOpts{readerExtensions = es}
+ (case content of
+ Left bs -> toSources $ UTF8.toText bs
+ Right sources -> sources)
+ (ByteStringReader r, es) ->
+ case content of
+ Left bs -> r readerOpts{readerExtensions = es}
+ (BSL.fromStrict bs)
+ Right _ -> throwM $ PandocLuaError
+ "Cannot use bytestring reader with Sources")
<#> parameter (\idx -> (Left <$> peekByteString idx)
<|> (Right <$> peekSources idx))
"string|Sources" "content" "text to parse"
@@ -255,10 +244,10 @@ functions =
=#> functionResult pushInline "Inline" "modified Inline"
, defun "write"
- ### (\doc mformatspec mwriterOpts -> do
+ ### (\doc mformatspec mwriterOpts -> unPandocLua $ do
+ let writerOpts = fromMaybe def mwriterOpts
let formatSpec = fromMaybe "html" mformatspec
- writerOpts = fromMaybe def mwriterOpts
- unPandocLua $ getWriter formatSpec >>= \case
+ getWriter formatSpec >>= \case
(TextWriter w, es) -> Right <$>
w writerOpts{ writerExtensions = es } doc
(ByteStringWriter w, es) -> Left <$>
diff --git a/pandoc-lua-engine/test/lua/module/pandoc.lua b/pandoc-lua-engine/test/lua/module/pandoc.lua
index 397182438..d61bcf3b0 100644
--- a/pandoc-lua-engine/test/lua/module/pandoc.lua
+++ b/pandoc-lua-engine/test/lua/module/pandoc.lua
@@ -266,7 +266,7 @@ return {
test('unsupported extension', function ()
assert.error_matches(
function () pandoc.read('foo', 'gfm+empty_paragraphs') end,
- 'Extension empty_paragraphs not supported for gfm'
+ 'The extension empty_paragraphs is not supported for gfm'
)
end),
test('read with other indented code classes', function()
@@ -290,7 +290,7 @@ return {
test('failing read', function ()
assert.error_matches(
function () pandoc.read('foo', 'nosuchreader') end,
- 'Unknown reader: nosuchreader'
+ 'Unknown input format nosuchreader'
)
end)
},