aboutsummaryrefslogtreecommitdiff
diff options
context:
space:
mode:
-rw-r--r--MANUAL.txt16
-rw-r--r--doc/lua-filters.md37
-rw-r--r--src/Text/Pandoc/Lua/Module/Utils.hs41
-rw-r--r--src/Text/Pandoc/Lua/Util.hs16
-rw-r--r--src/Text/Pandoc/Readers/LaTeX.hs40
-rw-r--r--src/Text/Pandoc/Readers/Markdown.hs21
-rw-r--r--src/Text/Pandoc/Writers/RST.hs2
-rw-r--r--test/Tests/Lua.hs1
-rw-r--r--test/command/3937.md2
-rw-r--r--test/command/4159.md3
-rw-r--r--test/command/hspace.md2
-rw-r--r--test/command/macros.md34
-rw-r--r--test/lua/test-pandoc-utils.lua19
-rw-r--r--test/markdown-reader-more.native5
14 files changed, 169 insertions, 70 deletions
diff --git a/MANUAL.txt b/MANUAL.txt
index 19e1764a1..78bd057ed 100644
--- a/MANUAL.txt
+++ b/MANUAL.txt
@@ -3195,18 +3195,22 @@ LaTeX macros
#### Extension: `latex_macros` ####
-For output formats other than LaTeX, pandoc will parse LaTeX `\newcommand` and
-`\renewcommand` definitions and apply the resulting macros to all LaTeX
-math. So, for example, the following will work in all output formats,
-not just LaTeX:
+For output formats other than LaTeX, pandoc will parse LaTeX
+macro definitions and apply the resulting macros to all LaTeX
+math and raw LaTeX. So, for example, the following will work in
+all output formats, not just LaTeX:
\newcommand{\tuple}[1]{\langle #1 \rangle}
$\tuple{a, b, c}$
-In LaTeX output, the `\newcommand` definition will simply be passed
-unchanged to the output.
+In LaTeX output, the macro definitions will not be passed
+through as raw LaTeX.
+When `latex_macros` is disabled, the macro definitions will
+be passed through as raw LaTeX, and the raw LaTeX and math will
+not have macros applied. This is usually a better approach when
+you are targeting LaTeX or PDF.
Links
-----
diff --git a/doc/lua-filters.md b/doc/lua-filters.md
index a109871f6..52d745ce8 100644
--- a/doc/lua-filters.md
+++ b/doc/lua-filters.md
@@ -166,15 +166,17 @@ those elements accessible through the filter function parameter.
Some pandoc functions have been made available in lua:
-- `walk_block` and `walk_inline` allow filters to be applied
- inside specific block or inline elements.
-- `read` allows filters to parse strings into pandoc documents
-- `pipe` runs an external command with input from and output to
- strings
-- `sha1` generates a SHA1 hash
-- The `mediabag` module allows access to the "mediabag,"
- which stores binary content such as images that may be
- included in the final document.
+- [`walk_block`](#walk_block) and [`walk_inline`](#walk_inline)
+ allow filters to be applied inside specific block or inline
+ elements;
+- [`read`](#read) allows filters to parse strings into pandoc
+ documents;
+- [`pipe`](#pipe) runs an external command with input from and
+ output to strings;
+- [`sha1`](#utils-sha1) generates a SHA1 hash;
+- the [`pandoc.mediabag`](#module-pandoc.mediabag) module allows
+ access to the "mediabag," which stores binary content such as
+ images that may be included in the final document.
# Lua interpreter initialization
@@ -1405,7 +1407,7 @@ Lua functions for pandoc scripts.
-- the above is equivallent to
-- return {{Str = Str}}
-[`pipe (command, args, input)`]{#mediabag-sha1}
+[`pipe (command, args, input)`]{#pipe}
: Runs command with arguments, passing it some input,
and returns the output.
@@ -1442,6 +1444,21 @@ functions.
local fp = pandoc.utils.sha1("foobar")
+[`stringify (element)`]{#utils-stringify}
+
+: Converts the given element (Pandoc, Meta, Block, or Inline)
+ into a string with all formatting removed.
+
+ Returns:
+
+ - A plain string representation of the given element.
+
+ Usage:
+
+ local inline = pandoc.Emph{pandoc.Str 'Moin'}
+ -- outputs "Moin"
+ print(pandoc.utils.stringify(inline))
+
# Module pandoc.mediabag
diff --git a/src/Text/Pandoc/Lua/Module/Utils.hs b/src/Text/Pandoc/Lua/Module/Utils.hs
index 496fdbc0a..3a3727355 100644
--- a/src/Text/Pandoc/Lua/Module/Utils.hs
+++ b/src/Text/Pandoc/Lua/Module/Utils.hs
@@ -29,22 +29,51 @@ module Text.Pandoc.Lua.Module.Utils
( pushModule
) where
-import Data.Digest.Pure.SHA (sha1, showDigest)
-import Foreign.Lua (Lua, NumResults)
+import Control.Applicative ((<|>))
+import Foreign.Lua (FromLuaStack, Lua, NumResults)
+import Text.Pandoc.Definition (Pandoc, Meta, Block, Inline)
import Text.Pandoc.Lua.StackInstances ()
import Text.Pandoc.Lua.Util (addFunction)
+import qualified Data.Digest.Pure.SHA as SHA
import qualified Data.ByteString.Lazy as BSL
import qualified Foreign.Lua as Lua
+import qualified Text.Pandoc.Shared as Shared
-- | Push the "pandoc.utils" module to the lua stack.
pushModule :: Lua NumResults
pushModule = do
Lua.newtable
- addFunction "sha1" sha1HashFn
+ addFunction "sha1" sha1
+ addFunction "stringify" stringify
return 1
-- | Calculate the hash of the given contents.
-sha1HashFn :: BSL.ByteString
- -> Lua String
-sha1HashFn = return . showDigest . sha1
+sha1 :: BSL.ByteString
+ -> Lua String
+sha1 = return . SHA.showDigest . SHA.sha1
+
+stringify :: AstElement -> Lua String
+stringify el = return $ case el of
+ PandocElement pd -> Shared.stringify pd
+ InlineElement i -> Shared.stringify i
+ BlockElement b -> Shared.stringify b
+ MetaElement m -> Shared.stringify m
+
+data AstElement
+ = PandocElement Pandoc
+ | MetaElement Meta
+ | BlockElement Block
+ | InlineElement Inline
+ deriving (Show)
+
+instance FromLuaStack AstElement where
+ peek idx = do
+ res <- Lua.tryLua $ (PandocElement <$> Lua.peek idx)
+ <|> (InlineElement <$> Lua.peek idx)
+ <|> (BlockElement <$> Lua.peek idx)
+ <|> (MetaElement <$> Lua.peek idx)
+ case res of
+ Right x -> return x
+ Left _ -> Lua.throwLuaError
+ "Expected an AST element, but could not parse value as such."
diff --git a/src/Text/Pandoc/Lua/Util.hs b/src/Text/Pandoc/Lua/Util.hs
index e688ad255..28d09d339 100644
--- a/src/Text/Pandoc/Lua/Util.hs
+++ b/src/Text/Pandoc/Lua/Util.hs
@@ -67,7 +67,7 @@ getTable :: (ToLuaStack a, FromLuaStack b) => StackIndex -> a -> Lua b
getTable idx key = do
push key
rawget (idx `adjustIndexBy` 1)
- peek (-1) <* pop 1
+ popValue
-- | Add a key-value pair to the table at the top of the stack.
addValue :: (ToLuaStack a, ToLuaStack b) => a -> b -> Lua ()
@@ -86,10 +86,9 @@ addFunction name fn = do
-- | Get value behind key from table at given index.
getRawInt :: FromLuaStack a => StackIndex -> Int -> Lua a
-getRawInt idx key =
+getRawInt idx key = do
rawgeti idx key
- *> peek (-1)
- <* pop 1
+ popValue
-- | Set numeric key/value in table at the given index
setRawInt :: ToLuaStack a => StackIndex -> Int -> a -> Lua ()
@@ -106,6 +105,15 @@ raiseError e = do
Lua.push e
fromIntegral <$> Lua.lerror
+-- | Get, then pop the value at the top of the stack.
+popValue :: FromLuaStack a => Lua a
+popValue = do
+ resOrError <- Lua.peekEither (-1)
+ pop 1
+ case resOrError of
+ Left err -> Lua.throwLuaError err
+ Right x -> return x
+
-- | Newtype wrapper intended to be used for optional Lua values. Nesting this
-- type is strongly discouraged and will likely lead to a wrong result.
newtype OrNil a = OrNil { toMaybe :: Maybe a }
diff --git a/src/Text/Pandoc/Readers/LaTeX.hs b/src/Text/Pandoc/Readers/LaTeX.hs
index e6ae4c11b..f7e45e01a 100644
--- a/src/Text/Pandoc/Readers/LaTeX.hs
+++ b/src/Text/Pandoc/Readers/LaTeX.hs
@@ -237,19 +237,21 @@ withVerbatimMode parser = do
return result
rawLaTeXParser :: (PandocMonad m, HasMacros s, HasReaderOptions s)
- => LP m a -> ParserT String s m String
+ => LP m a -> ParserT String s m (a, String)
rawLaTeXParser parser = do
inp <- getInput
let toks = tokenize "source" $ T.pack inp
pstate <- getState
- let lstate = def{ sOptions = extractReaderOptions pstate }
- res <- lift $ runParserT ((,) <$> try (snd <$> withRaw parser) <*> getState)
- lstate "source" toks
+ let lstate = def{ sOptions = extractReaderOptions pstate
+ , sMacros = extractMacros pstate }
+ let rawparser = (,) <$> withRaw parser <*> getState
+ res <- lift $ runParserT rawparser lstate "chunk" toks
case res of
Left _ -> mzero
- Right (raw, st) -> do
+ Right ((val, raw), st) -> do
updateState (updateMacros (sMacros st <>))
- takeP (T.length (untokenize raw))
+ rawstring <- takeP (T.length (untokenize raw))
+ return (val, rawstring)
applyMacros :: (PandocMonad m, HasMacros s, HasReaderOptions s)
=> String -> ParserT String s m String
@@ -268,33 +270,23 @@ rawLaTeXBlock :: (PandocMonad m, HasMacros s, HasReaderOptions s)
=> ParserT String s m String
rawLaTeXBlock = do
lookAhead (try (char '\\' >> letter))
- rawLaTeXParser (environment <|> macroDef <|> blockCommand)
+ -- we don't want to apply newly defined latex macros to their own
+ -- definitions:
+ (do (_, raw) <- rawLaTeXParser macroDef
+ (guardDisabled Ext_latex_macros >> return raw) <|> return "")
+ <|> (do (_, raw) <- rawLaTeXParser (environment <|> blockCommand)
+ applyMacros raw)
rawLaTeXInline :: (PandocMonad m, HasMacros s, HasReaderOptions s)
=> ParserT String s m String
rawLaTeXInline = do
lookAhead (try (char '\\' >> letter) <|> char '$')
- rawLaTeXParser (inlineEnvironment <|> inlineCommand')
+ rawLaTeXParser (inlineEnvironment <|> inlineCommand') >>= applyMacros . snd
inlineCommand :: PandocMonad m => ParserT String ParserState m Inlines
inlineCommand = do
lookAhead (try (char '\\' >> letter) <|> char '$')
- inp <- getInput
- let toks = tokenize "chunk" $ T.pack inp
- let rawinline = do
- (il, raw) <- try $ withRaw (inlineEnvironment <|> inlineCommand')
- st <- getState
- return (il, raw, st)
- pstate <- getState
- let lstate = def{ sOptions = extractReaderOptions pstate
- , sMacros = extractMacros pstate }
- res <- runParserT rawinline lstate "source" toks
- case res of
- Left _ -> mzero
- Right (il, raw, s) -> do
- updateState $ updateMacros (const $ sMacros s)
- takeP (T.length (untokenize raw))
- return il
+ fst <$> rawLaTeXParser (inlineEnvironment <|> inlineCommand')
tokenize :: SourceName -> Text -> [Tok]
tokenize sourcename = totoks (initialPos sourcename)
diff --git a/src/Text/Pandoc/Readers/Markdown.hs b/src/Text/Pandoc/Readers/Markdown.hs
index 9ffdbf00d..e7ad9d8ba 100644
--- a/src/Text/Pandoc/Readers/Markdown.hs
+++ b/src/Text/Pandoc/Readers/Markdown.hs
@@ -1120,13 +1120,20 @@ rawVerbatimBlock = htmlInBalanced isVerbTag
rawTeXBlock :: PandocMonad m => MarkdownParser m (F Blocks)
rawTeXBlock = do
guardEnabled Ext_raw_tex
- result <- (B.rawBlock "context" . concat <$>
- rawConTeXtEnvironment `sepEndBy1` blankline)
- <|> (B.rawBlock "latex" . concat <$>
- rawLaTeXBlock `sepEndBy1` blankline)
-
- optional blanklines
- return $ return result
+ result <- (B.rawBlock "context" . trim . concat <$>
+ many1 ((++) <$> (rawConTeXtEnvironment <|> conTeXtCommand)
+ <*> (blanklines <|> many spaceChar)))
+ <|> (B.rawBlock "latex" . trim . concat <$>
+ many1 ((++) <$> rawLaTeXBlock
+ <*> (blanklines <|> many spaceChar)))
+ return $ case B.toList result of
+ [RawBlock _ cs]
+ | all (`elem` [' ','\t','\n']) cs -> return mempty
+ -- don't create a raw block for suppressed macro defs
+ _ -> return result
+
+conTeXtCommand :: PandocMonad m => MarkdownParser m String
+conTeXtCommand = oneOfStrings ["\\placeformula"]
rawHtmlBlocks :: PandocMonad m => MarkdownParser m (F Blocks)
rawHtmlBlocks = do
diff --git a/src/Text/Pandoc/Writers/RST.hs b/src/Text/Pandoc/Writers/RST.hs
index 42d4d0040..515276985 100644
--- a/src/Text/Pandoc/Writers/RST.hs
+++ b/src/Text/Pandoc/Writers/RST.hs
@@ -250,7 +250,7 @@ blockToRST (Header level (name,classes,_) inlines) = do
let headerChar = if level > 5 then ' ' else "=-~^'" !! (level - 1)
let border = text $ replicate (offset contents) headerChar
let anchor | null name || name == autoId = empty
- | otherwise = ".. " <> text name <> ":" $$ blankline
+ | otherwise = ".. _" <> text name <> ":" $$ blankline
return $ nowrap $ anchor $$ contents $$ border $$ blankline
else do
let rub = "rubric:: " <> contents
diff --git a/test/Tests/Lua.hs b/test/Tests/Lua.hs
index 0e76249fe..57e7c5f0c 100644
--- a/test/Tests/Lua.hs
+++ b/test/Tests/Lua.hs
@@ -101,6 +101,7 @@ tests = map (localOption (QuickCheckTests 20))
, plain (str "failing pipe: OK")
, plain (str "read: OK")
, plain (str "failing read: OK")
+ , plain (str "stringify: OK")
])
]
diff --git a/test/command/3937.md b/test/command/3937.md
index 1d5e4238a..2f32cd172 100644
--- a/test/command/3937.md
+++ b/test/command/3937.md
@@ -3,7 +3,7 @@
# My Great Section {#mysection}
# Other section
^D
-.. mysection:
+.. _mysection:
My Great Section
================
diff --git a/test/command/4159.md b/test/command/4159.md
index 4881edcc5..81deba53a 100644
--- a/test/command/4159.md
+++ b/test/command/4159.md
@@ -3,6 +3,5 @@
\newcommand{\gen}{a\ Gen\ b}
abc
^D
-[RawBlock (Format "latex") "\\newcommand{\\gen}{a\\ Gen\\ b}"
-,Para [Str "abc"]]
+[Para [Str "abc"]]
```
diff --git a/test/command/hspace.md b/test/command/hspace.md
index 5d5c7171b..ec1669ca5 100644
--- a/test/command/hspace.md
+++ b/test/command/hspace.md
@@ -32,7 +32,7 @@ F & T &\\
F & F &\\
\end{tabular}
^D
-[RawBlock (Format "latex") "\\begin{tabular}[t]{cc|c}\n\\(P\\) & \\(Q\\) & \\(P\\wedge Q\\)\\\\\n\\hline\nT & T &\\\\\nT & F &\\\\\nF & T &\\\\\nF & F &\\\\\n\\end{tabular}\\hspace{1em}\\begin{tabular}[t]{cc|c}\n\\(P\\) & \\(Q\\) & \\(P\\vee Q\\)\\\\\n\\hline\nT & T &\\\\\nT & F &\\\\\nF & T &\\\\\nF & F &\\\\\n\\end{tabular}"]
+[RawBlock (Format "latex") "\\begin{tabular}[t]{cc|c}\n\\(P\\) & \\(Q\\) & \\(P\\wedge Q\\)\\\\\n\\hline\nT & T &\\\\\nT & F &\\\\\nF & T &\\\\\nF & F &\\\\\n\\end{tabular}\n\\hspace{1em}\n\\begin{tabular}[t]{cc|c}\n\\(P\\) & \\(Q\\) & \\(P\\vee Q\\)\\\\\n\\hline\nT & T &\\\\\nT & F &\\\\\nF & T &\\\\\nF & F &\\\\\n\\end{tabular}"]
```
```
diff --git a/test/command/macros.md b/test/command/macros.md
index 46179e3c7..4bd2eb00a 100644
--- a/test/command/macros.md
+++ b/test/command/macros.md
@@ -3,7 +3,6 @@
\newcommand{\my}{\phi}
$\my+\my$
^D
-\newcommand{\my}{\phi}
$\phi+\phi$
```
@@ -66,3 +65,36 @@ x &= y\\\end{aligned}\]
\emph{hi--ok}
```
+
+```
+% pandoc -f markdown+latex_macros -t markdown
+\newcommand{\my}{\phi}
+\begin{equation}
+\my+\my
+\end{equation}
+^D
+\begin{equation}
+\phi+\phi
+\end{equation}
+```
+
+```
+% pandoc -f markdown-latex_macros -t markdown
+\newcommand{\my}{\phi}
+\begin{equation}
+\my+\my
+\end{equation}
+^D
+\newcommand{\my}{\phi}
+\begin{equation}
+\my+\my
+\end{equation}
+```
+
+```
+% pandoc -f markdown+latex_macros -t markdown
+\newcommand{\my}{\emph{a}}
+\my
+^D
+\emph{a}
+```
diff --git a/test/lua/test-pandoc-utils.lua b/test/lua/test-pandoc-utils.lua
index 7354496f9..ce3456d5d 100644
--- a/test/lua/test-pandoc-utils.lua
+++ b/test/lua/test-pandoc-utils.lua
@@ -1,4 +1,4 @@
-utils = require 'pandoc'
+utils = require 'pandoc.utils'
-- SHA1
------------------------------------------------------------------------
@@ -22,7 +22,7 @@ function test_pipe ()
warn 'Did not find /bin/sed, skipping test'
return true
end
- local pipe_result = utils.pipe('/bin/sed', {'-e', 's/a/b/'}, 'abc')
+ local pipe_result = pandoc.pipe('/bin/sed', {'-e', 's/a/b/'}, 'abc')
return pipe_result == 'bbc'
end
@@ -31,7 +31,7 @@ function test_failing_pipe ()
warn 'Did not find /bin/false, skipping test'
return true
end
- local res, err = pcall(utils.pipe, '/bin/false', {}, 'abc')
+ local res, err = pcall(pandoc.pipe, '/bin/false', {}, 'abc')
return not res and
err.command == '/bin/false' and
err.error_code == 1 and
@@ -51,6 +51,18 @@ function test_failing_read ()
return not res and err:match 'Unknown reader: nosuchreader'
end
+-- Stringify
+------------------------------------------------------------------------
+function test_stringify ()
+ local inline = pandoc.Emph{
+ pandoc.Str 'Cogito',
+ pandoc.Space(),
+ pandoc.Str 'ergo',
+ pandoc.Space(),
+ pandoc.Str 'sum.',
+ }
+ return utils.stringify(inline) == 'Cogito ergo sum.'
+end
-- Return result
------------------------------------------------------------------------
@@ -65,5 +77,6 @@ function Para (el)
pandoc.Plain{pandoc.Str("failing pipe: " .. run(test_failing_pipe))},
pandoc.Plain{pandoc.Str("read: " .. run(test_read))},
pandoc.Plain{pandoc.Str("failing read: " .. run(test_failing_read))},
+ pandoc.Plain{pandoc.Str("stringify: " .. run(test_stringify))},
}
end
diff --git a/test/markdown-reader-more.native b/test/markdown-reader-more.native
index 2e55dbb18..742b6187c 100644
--- a/test/markdown-reader-more.native
+++ b/test/markdown-reader-more.native
@@ -3,9 +3,7 @@ Pandoc (Meta {unMeta = fromList [("author",MetaList [MetaInlines [Str "Author",S
,Header 2 ("blank-line-before-url-in-link-reference",[],[]) [Str "Blank",Space,Str "line",Space,Str "before",Space,Str "URL",Space,Str "in",Space,Str "link",Space,Str "reference"]
,Para [Link ("",[],[]) [Str "foo"] ("/url",""),Space,Str "and",Space,Link ("",[],[]) [Str "bar"] ("/url","title")]
,Header 2 ("raw-context-environments",[],[]) [Str "Raw",Space,Str "ConTeXt",Space,Str "environments"]
-,RawBlock (Format "latex") "\\placeformula "
-,RawBlock (Format "context") "\\startformula\n L_{1} = L_{2}\n \\stopformula"
-,RawBlock (Format "context") "\\start[a2]\n\\start[a2]\n\\stop[a2]\n\\stop[a2]"
+,RawBlock (Format "context") "\\placeformula \\startformula\n L_{1} = L_{2}\n \\stopformula\n\n\\start[a2]\n\\start[a2]\n\\stop[a2]\n\\stop[a2]"
,Header 2 ("raw-latex-environments",[],[]) [Str "Raw",Space,Str "LaTeX",Space,Str "environments"]
,RawBlock (Format "latex") "\\begin{center}\n\\begin{tikzpicture}[baseline={([yshift=+-.5ex]current bounding box.center)}, level distance=24pt]\n\\Tree [.{S} [.NP John\\index{i} ] [.VP [.V likes ] [.NP himself\\index{i,*j} ]]]\n\\end{tikzpicture}\n\\end{center}"
,Header 2 ("urls-with-spaces-and-punctuation",[],[]) [Str "URLs",Space,Str "with",Space,Str "spaces",Space,Str "and",Space,Str "punctuation"]
@@ -56,7 +54,6 @@ Pandoc (Meta {unMeta = fromList [("author",MetaList [MetaInlines [Str "Author",S
,OrderedList (3,Example,TwoParens)
[[Plain [Str "Third",Space,Str "example."]]]
,Header 2 ("macros",[],[]) [Str "Macros"]
-,RawBlock (Format "latex") "\\newcommand{\\tuple}[1]{\\langle #1 \\rangle}"
,Para [Math InlineMath "\\langle x,y \\rangle"]
,Header 2 ("case-insensitive-references",[],[]) [Str "Case-insensitive",Space,Str "references"]
,Para [Link ("",[],[]) [Str "Fum"] ("/fum","")]