Lua filter: allow shorthand functions for math and quoted

Allow to use functions named `SingleQuoted`, `DoubleQuoted`,
`DisplayMath`, and `InlineMath` in filters.
This commit is contained in:
Albert Krewinkel 2017-04-14 23:24:52 +02:00
parent eb8de6514b
commit 3aeed816e1
No known key found for this signature in database
GPG key ID: 388DC0B21F631124
4 changed files with 52 additions and 21 deletions

View file

@ -247,10 +247,7 @@ Extra-Source-Files:
test/odt/odt/*.odt test/odt/odt/*.odt
test/odt/markdown/*.md test/odt/markdown/*.md
test/odt/native/*.native test/odt/native/*.native
test/lua/hello-world-doc.lua test/lua/*.lua
test/lua/markdown-reader.lua
test/lua/plain-to-para.lua
test/lua/strmacro.lua
Source-repository head Source-repository head
type: git type: git
location: git://github.com/jgm/pandoc.git location: git://github.com/jgm/pandoc.git

View file

@ -34,7 +34,7 @@ import Control.Monad ( (>=>), when )
import Control.Monad.Trans ( MonadIO(..) ) import Control.Monad.Trans ( MonadIO(..) )
import Data.Map ( Map ) import Data.Map ( Map )
import Scripting.Lua ( LuaState, StackValue(..) ) import Scripting.Lua ( LuaState, StackValue(..) )
import Text.Pandoc.Definition ( Block(..), Inline(..), Pandoc(..) ) import Text.Pandoc.Definition
import Text.Pandoc.Lua.PandocModule ( pushPandocModule ) import Text.Pandoc.Lua.PandocModule ( pushPandocModule )
import Text.Pandoc.Lua.StackInstances () import Text.Pandoc.Lua.StackInstances ()
import Text.Pandoc.Walk import Text.Pandoc.Walk
@ -135,6 +135,12 @@ execInlineLuaFilter lua fnMap x = do
case Map.lookup fnName fnMap of case Map.lookup fnName fnMap of
Nothing -> return x Nothing -> return x
Just fn -> callFilterFn fn Just fn -> callFilterFn fn
let tryFilterAlternatives :: [(String, LuaFilterFunction Inline -> IO Inline)] -> IO Inline
tryFilterAlternatives [] = return x
tryFilterAlternatives ((fnName, callFilterFn) : alternatives) =
case Map.lookup fnName fnMap of
Nothing -> tryFilterAlternatives alternatives
Just fn -> callFilterFn fn
case x of case x of
LineBreak -> tryFilter "LineBreak" runFn LineBreak -> tryFilter "LineBreak" runFn
SoftBreak -> tryFilter "SoftBreak" runFn SoftBreak -> tryFilter "SoftBreak" runFn
@ -142,9 +148,7 @@ execInlineLuaFilter lua fnMap x = do
Cite cs lst -> tryFilter "Cite" $ \fn -> runFn fn lst cs Cite cs lst -> tryFilter "Cite" $ \fn -> runFn fn lst cs
Code attr str -> tryFilter "Code" $ \fn -> runFn fn str attr Code attr str -> tryFilter "Code" $ \fn -> runFn fn str attr
Emph lst -> tryFilter "Emph" $ \fn -> runFn fn lst Emph lst -> tryFilter "Emph" $ \fn -> runFn fn lst
Math mt lst -> tryFilter "Math" $ \fn -> runFn fn lst mt
Note blks -> tryFilter "Note" $ \fn -> runFn fn blks Note blks -> tryFilter "Note" $ \fn -> runFn fn blks
Quoted qt lst -> tryFilter "Quoted" $ \fn -> runFn fn qt lst
RawInline f str -> tryFilter "RawInline" $ \fn -> runFn fn f str RawInline f str -> tryFilter "RawInline" $ \fn -> runFn fn f str
SmallCaps lst -> tryFilter "SmallCaps" $ \fn -> runFn fn lst SmallCaps lst -> tryFilter "SmallCaps" $ \fn -> runFn fn lst
Span attr lst -> tryFilter "Span" $ \fn -> runFn fn lst attr Span attr lst -> tryFilter "Span" $ \fn -> runFn fn lst attr
@ -153,6 +157,22 @@ execInlineLuaFilter lua fnMap x = do
Strong lst -> tryFilter "Strong" $ \fn -> runFn fn lst Strong lst -> tryFilter "Strong" $ \fn -> runFn fn lst
Subscript lst -> tryFilter "Subscript" $ \fn -> runFn fn lst Subscript lst -> tryFilter "Subscript" $ \fn -> runFn fn lst
Superscript lst -> tryFilter "Superscript" $ \fn -> runFn fn lst Superscript lst -> tryFilter "Superscript" $ \fn -> runFn fn lst
Math DisplayMath lst -> tryFilterAlternatives
[ ("DisplayMath", \fn -> runFn fn lst)
, ("Math", \fn -> runFn fn DisplayMath lst)
]
Math InlineMath lst -> tryFilterAlternatives
[ ("InlineMath", \fn -> runFn fn lst)
, ("Math", \fn -> runFn fn InlineMath lst)
]
Quoted SingleQuote lst -> tryFilterAlternatives
[ ("SingleQuoted", \fn -> runFn fn lst)
, ("Quoted", \fn -> runFn fn SingleQuote lst)
]
Quoted DoubleQuote lst -> tryFilterAlternatives
[ ("DoubleQuoted", \fn -> runFn fn lst)
, ("Quoted", \fn -> runFn fn DoubleQuote lst)
]
Link attr txt (src, tit) -> tryFilter "Link" $ Link attr txt (src, tit) -> tryFilter "Link" $
\fn -> runFn fn txt src tit attr \fn -> runFn fn txt src tit attr
Image attr alt (src, tit) -> tryFilter "Image" $ Image attr alt (src, tit) -> tryFilter "Image" $

View file

@ -8,15 +8,28 @@ import Test.Tasty.HUnit (Assertion, assertEqual, testCase)
import Test.Tasty.QuickCheck (ioProperty, testProperty) import Test.Tasty.QuickCheck (ioProperty, testProperty)
import Text.Pandoc.Arbitrary () import Text.Pandoc.Arbitrary ()
import Text.Pandoc.Definition (Block, Inline, Meta, Pandoc) import Text.Pandoc.Definition (Block, Inline, Meta, Pandoc)
import Text.Pandoc.Builder ( (<>), bulletList, doc, emph, linebreak, rawBlock import Text.Pandoc.Builder ( (<>), bulletList, doc, doubleQuoted, emph
, para, plain, space, str, strong) , linebreak, rawBlock, singleQuoted, para, plain
, space, str, strong)
import Text.Pandoc.Lua import Text.Pandoc.Lua
import qualified Scripting.Lua as Lua import qualified Scripting.Lua as Lua
tests :: [TestTree] tests :: [TestTree]
tests = tests =
[ testCase "macro expansion via filter" $ [ testProperty "inline elements can be round-tripped through the lua stack" $
\x -> ioProperty (roundtripEqual (x::Inline))
, testProperty "block elements can be round-tripped through the lua stack" $
\x -> ioProperty (roundtripEqual (x::Block))
, testProperty "meta blocks can be round-tripped through the lua stack" $
\x -> ioProperty (roundtripEqual (x::Meta))
, testProperty "documents can be round-tripped through the lua stack" $
\x -> ioProperty (roundtripEqual (x::Pandoc))
, testCase "macro expansion via filter" $
assertFilterConversion "a '{{helloworld}}' string is expanded" assertFilterConversion "a '{{helloworld}}' string is expanded"
"strmacro.lua" "strmacro.lua"
(doc . para $ str "{{helloworld}}") (doc . para $ str "{{helloworld}}")
@ -40,17 +53,11 @@ tests =
(doc $ rawBlock "markdown" "*charly* **delta**") (doc $ rawBlock "markdown" "*charly* **delta**")
(doc . para $ emph "charly" <> space <> strong "delta") (doc . para $ emph "charly" <> space <> strong "delta")
, testProperty "inline elements can be round-tripped through the lua stack" $ , testCase "allow shorthand functions for quote types" $
\x -> ioProperty (roundtripEqual (x::Inline)) assertFilterConversion "single quoted becomes double quoted string"
"single-to-double-quoted.lua"
, testProperty "block elements can be round-tripped through the lua stack" $ (doc . para . singleQuoted $ str "simple")
\x -> ioProperty (roundtripEqual (x::Block)) (doc . para . doubleQuoted $ str "simple")
, testProperty "meta blocks can be round-tripped through the lua stack" $
\x -> ioProperty (roundtripEqual (x::Meta))
, testProperty "documents can be round-tripped through the lua stack" $
\x -> ioProperty (roundtripEqual (x::Pandoc))
] ]
assertFilterConversion :: String -> FilePath -> Pandoc -> Pandoc -> Assertion assertFilterConversion :: String -> FilePath -> Pandoc -> Pandoc -> Assertion

View file

@ -0,0 +1,7 @@
return {
{
SingleQuoted = function (content)
return pandoc.Quoted("DoubleQuote", content)
end,
}
}