aboutsummaryrefslogtreecommitdiff
path: root/pandoc-lua-engine
diff options
context:
space:
mode:
authorAlbert Krewinkel <[email protected]>2022-10-05 12:37:30 +0200
committerJohn MacFarlane <[email protected]>2022-12-16 10:43:01 -0800
commita36f12119fe1a0b70a1a3ff65264e94373a490ce (patch)
tree224f9932bf6e1c120db568a6a111f69a9146317a /pandoc-lua-engine
parentdb0232fc545913a9ea6e81d84fc5ee4d9cc8a185 (diff)
Lua: allow table structure as format spec.
This allows to pass structured values as format specifiers to `pandoc.write` and `pandoc.read`.
Diffstat (limited to 'pandoc-lua-engine')
-rw-r--r--pandoc-lua-engine/src/Text/Pandoc/Lua/Marshal/Format.hs80
-rw-r--r--pandoc-lua-engine/src/Text/Pandoc/Lua/Module/Pandoc.hs15
-rw-r--r--pandoc-lua-engine/test/lua/module/pandoc.lua69
3 files changed, 151 insertions, 13 deletions
diff --git a/pandoc-lua-engine/src/Text/Pandoc/Lua/Marshal/Format.hs b/pandoc-lua-engine/src/Text/Pandoc/Lua/Marshal/Format.hs
index 39b1b98a0..f6d6b67ba 100644
--- a/pandoc-lua-engine/src/Text/Pandoc/Lua/Marshal/Format.hs
+++ b/pandoc-lua-engine/src/Text/Pandoc/Lua/Marshal/Format.hs
@@ -1,3 +1,5 @@
+{-# LANGUAGE LambdaCase #-}
+{-# LANGUAGE OverloadedStrings #-}
{-# OPTIONS_GHC -fno-warn-orphans #-}
{- |
Module : Text.Pandoc.Lua.Marshaling.Format
@@ -12,11 +14,21 @@ module Text.Pandoc.Lua.Marshal.Format
( peekExtensions
, pushExtensions
, peekExtensionsConfig
+ , peekFlavoredFormat
) where
+import Control.Applicative ((<|>))
+import Control.Monad ((<$!>))
+import Data.Maybe (fromMaybe)
import HsLua
-import Text.Pandoc.Extensions (Extension, Extensions, extensionsFromList, readExtension)
-import Text.Pandoc.Format (ExtensionsConfig (..))
+import Text.Pandoc.Error (PandocError (..))
+import Text.Pandoc.Extensions
+ ( Extension, Extensions, extensionsFromList
+ , getDefaultExtensions, readExtension )
+import Text.Pandoc.Format
+ ( ExtensionsConfig (..), ExtensionsDiff (..), FlavoredFormat (..)
+ , diffExtensions, parseFlavoredFormat)
+import Text.Pandoc.Lua.PandocLua (PandocLua (unPandocLua))
-- | Retrieves an 'Extensions' set from the Lua stack.
peekExtension :: LuaError e => Peeker e Extension
@@ -27,7 +39,7 @@ peekExtension idx = do
-- | Retrieves an 'Extensions' set from the Lua stack.
peekExtensions :: LuaError e => Peeker e Extensions
-peekExtensions = peekViaJSON
+peekExtensions = fmap extensionsFromList . peekList peekExtension
{-# INLINE peekExtensions #-}
-- | Pushes a set of 'Extensions' to the top of the Lua stack.
@@ -44,8 +56,64 @@ instance Pushable Extensions where
-- | Retrieves an 'ExtensionsConfig' value from the Lua stack.
peekExtensionsConfig :: LuaError e => Peeker e ExtensionsConfig
peekExtensionsConfig idx = do
- exts <- peekKeyValuePairs peekExtension peekBool idx
+ diff <- peekExtensionsDiff idx
return $ ExtensionsConfig
- { extsDefault = extensionsFromList . map fst $ filter snd exts
- , extsSupported = extensionsFromList . map fst $ exts
+ { extsDefault = extsToEnable diff
+ , extsSupported = extsToEnable diff <> extsToDisable diff
}
+
+instance Peekable ExtensionsConfig where
+ safepeek = peekExtensionsConfig
+
+peekExtensionsDiff :: LuaError e => Peeker e ExtensionsDiff
+peekExtensionsDiff = typeChecked "table" istable $ \idx ->
+ (do
+ en <- peekFieldRaw (emptyOr (fmap Just . peekExtensions)) "enable" idx
+ di <- peekFieldRaw (emptyOr (fmap Just . peekExtensions)) "disable" idx
+ if (en, di) == (Nothing, Nothing)
+ then failPeek "At least on of 'enable' and 'disable' must be set"
+ else return $
+ ExtensionsDiff (fromMaybe mempty en) (fromMaybe mempty di))
+ <|> -- two lists of extensions; the first is list assumed to contain those
+ -- extensions to be enabled
+ (uncurry ExtensionsDiff <$!> peekPair peekExtensions peekExtensions idx)
+ <|> (do
+ let
+ exts <- peekKeyValuePairs peekExtension peekEnabled idx
+ let enabled = extensionsFromList . map fst $ filter snd exts
+ let disabled = extensionsFromList . map fst $ filter (not . snd) exts
+ return $ ExtensionsDiff enabled disabled)
+
+-- | Retrieves the activation status of an extension. True or the string
+-- @'enable'@ for activated, False or 'disable' for disabled.
+peekEnabled :: LuaError e => Peeker e Bool
+peekEnabled idx' = liftLua (ltype idx') >>= \case
+ TypeBoolean -> peekBool idx'
+ TypeString -> peekText idx' >>= \case
+ "disable" -> pure False
+ "enable" -> pure True
+ _ -> failPeek "expected 'disable' or 'enable'"
+ _ -> failPeek "expected boolean or string"
+
+-- | Retrieves a flavored format from the Lua stack.
+peekFlavoredFormat :: Peeker PandocError FlavoredFormat
+peekFlavoredFormat idx = retrieving "flavored format" $
+ liftLua (ltype idx) >>= \case
+ TypeString -> peekText idx >>= liftLua . unPandocLua . parseFlavoredFormat
+ TypeTable -> do
+ let diffFor format idx' = peekExtensionsDiff idx' <|>
+ (getDefaultExtensions format `diffExtensions`) <$>
+ (typeChecked "table" istable peekExtensions idx')
+ format <- peekFieldRaw peekText "format" idx
+ extsDiff <- peekFieldRaw (emptyOr (diffFor format)) "extensions" idx
+ return (FlavoredFormat format extsDiff)
+ _ -> failPeek =<< typeMismatchMessage "string or table" idx
+
+-- | Returns 'mempty' if the given stack index is @nil@, and the result
+-- of the peeker otherwise.
+emptyOr :: Monoid a => Peeker e a -> Peeker e a
+emptyOr p idx = do
+ nil <- liftLua (isnil idx)
+ if nil
+ then pure mempty
+ else p idx
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 aaca86b02..9d74f363c 100644
--- a/pandoc-lua-engine/src/Text/Pandoc/Lua/Module/Pandoc.hs
+++ b/pandoc-lua-engine/src/Text/Pandoc/Lua/Module/Pandoc.hs
@@ -32,6 +32,7 @@ import Text.Pandoc.Error (PandocError (..))
import Text.Pandoc.Format (parseFlavoredFormat)
import Text.Pandoc.Lua.Orphans ()
import Text.Pandoc.Lua.Marshal.AST
+import Text.Pandoc.Lua.Marshal.Format (peekFlavoredFormat)
import Text.Pandoc.Lua.Marshal.Filter (peekFilter)
import Text.Pandoc.Lua.Marshal.ReaderOptions ( peekReaderOptions
, pushReaderOptions)
@@ -200,9 +201,9 @@ functions =
, defun "read"
### (\content mformatspec mreaderOptions -> unPandocLua $ do
+ flvrd <- maybe (parseFlavoredFormat "markdown") pure mformatspec
let readerOpts = fromMaybe def mreaderOptions
- formatSpec <- parseFlavoredFormat $ fromMaybe "markdown" mformatspec
- getReader formatSpec >>= \case
+ getReader flvrd >>= \case
(TextReader r, es) ->
r readerOpts{readerExtensions = es}
(case content of
@@ -217,7 +218,8 @@ functions =
<#> parameter (\idx -> (Left <$> peekByteString idx)
<|> (Right <$> peekSources idx))
"string|Sources" "content" "text to parse"
- <#> opt (textParam "formatspec" "format and extensions")
+ <#> opt (parameter peekFlavoredFormat "string|table"
+ "formatspec" "format and extensions")
<#> opt (parameter peekReaderOptions "ReaderOptions" "reader_options"
"reader options")
=#> functionResult pushPandoc "Pandoc" "result document"
@@ -238,15 +240,16 @@ functions =
, defun "write"
### (\doc mformatspec mwriterOpts -> unPandocLua $ do
+ flvrd <- maybe (parseFlavoredFormat "markdown") pure mformatspec
let writerOpts = fromMaybe def mwriterOpts
- formatSpec <- parseFlavoredFormat $ fromMaybe "html" mformatspec
- getWriter formatSpec >>= \case
+ getWriter flvrd >>= \case
(TextWriter w, es) -> Right <$>
w writerOpts{ writerExtensions = es } doc
(ByteStringWriter w, es) -> Left <$>
w writerOpts{ writerExtensions = es } doc)
<#> parameter peekPandoc "Pandoc" "doc" "document to convert"
- <#> opt (textParam "formatspec" "format and extensions")
+ <#> opt (parameter peekFlavoredFormat "string|table"
+ "formatspec" "format and extensions")
<#> opt (parameter peekWriterOptions "WriterOptions" "writer_options"
"writer options")
=#> functionResult (either pushLazyByteString pushText) "string"
diff --git a/pandoc-lua-engine/test/lua/module/pandoc.lua b/pandoc-lua-engine/test/lua/module/pandoc.lua
index d61bcf3b0..bb02f172b 100644
--- a/pandoc-lua-engine/test/lua/module/pandoc.lua
+++ b/pandoc-lua-engine/test/lua/module/pandoc.lua
@@ -292,7 +292,33 @@ return {
function () pandoc.read('foo', 'nosuchreader') end,
'Unknown input format nosuchreader'
)
- end)
+ end),
+ group 'extensions' {
+ test('string spec', function ()
+ local doc = pandoc.read('"vice versa"', 'markdown-smart')
+ assert.are_equal(doc, pandoc.Pandoc{pandoc.Para '"vice versa"'})
+ end),
+ test('unsupported extension', function ()
+ assert.error_matches(
+ function () pandoc.read('foo', 'gfm+empty_paragraphs') end,
+ 'The extension empty_paragraphs is not supported for gfm'
+ )
+ end),
+ test('unknown extension', function ()
+ local format_spec = { format = 'markdown', extensions = {'nope'}}
+ assert.error_matches(
+ function () pandoc.read('x', format_spec) end,
+ 'The extension nope is not supported for markdown'
+ )
+ end),
+ test('fails on invalid extension', function ()
+ local format_spec = { format = 'markdown', extensions = {'nope'}}
+ assert.error_matches(
+ function () pandoc.read('nu-uh', format_spec) end,
+ 'The extension nope is not supported for markdown'
+ )
+ end),
+ },
},
group 'walk_block' {
@@ -333,6 +359,47 @@ return {
end)
},
+ group 'write' {
+ test('string spec', function ()
+ local doc = pandoc.Pandoc{pandoc.Quoted('DoubleQuote', 'vice versa')}
+ local plain = pandoc.write(doc, 'plain+smart')
+ assert.are_equal(plain, '"vice versa"\n')
+ end),
+ test('table format spec with extensions list', function ()
+ local doc = pandoc.Pandoc{pandoc.Quoted('DoubleQuote', 'vice versa')}
+ local format_spec = { format = 'plain', extensions = {'smart'}}
+ local plain = pandoc.write(doc, format_spec)
+ assert.are_equal(plain, '"vice versa"\n')
+ end),
+ test('table format spec with `enable`/`disable` diff', function ()
+ local diff = {
+ enable = {'smart'}
+ }
+ local doc = pandoc.Pandoc{pandoc.Quoted('DoubleQuote', 'vice versa')}
+ local format_spec = { format = 'plain', extensions = diff}
+ local plain = pandoc.write(doc, format_spec)
+ assert.are_equal(plain, '"vice versa"\n')
+ end),
+ test('table format spec with set-like diff', function ()
+ local diff = {
+ smart = true,
+ auto_identifiers = false
+ }
+ local doc = pandoc.Pandoc{pandoc.Quoted('DoubleQuote', 'vice versa')}
+ local format_spec = { format = 'plain', extensions = diff}
+ local plain = pandoc.write(doc, format_spec)
+ assert.are_equal(plain, '"vice versa"\n')
+ end),
+ test('fails on invalid extension', function ()
+ local doc = pandoc.Pandoc{'nope'}
+ local format_spec = { format = 'plain', extensions = {'nope'}}
+ assert.error_matches(
+ function () pandoc.write(doc, format_spec) end,
+ 'The extension nope is not supported for plain'
+ )
+ end),
+ },
+
group 'Marshal' {
group 'Inlines' {
test('Strings are broken into words', function ()