aboutsummaryrefslogtreecommitdiff
path: root/src
diff options
context:
space:
mode:
Diffstat (limited to 'src')
-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
5 files changed, 78 insertions, 42 deletions
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