aboutsummaryrefslogtreecommitdiff
path: root/src
diff options
context:
space:
mode:
Diffstat (limited to 'src')
-rw-r--r--src/Text/Pandoc/Readers/Muse.hs62
-rw-r--r--src/Text/Pandoc/Writers/LaTeX.hs6
-rw-r--r--src/Text/Pandoc/Writers/RTF.hs6
3 files changed, 38 insertions, 36 deletions
diff --git a/src/Text/Pandoc/Readers/Muse.hs b/src/Text/Pandoc/Readers/Muse.hs
index e8e309115..6475669ce 100644
--- a/src/Text/Pandoc/Readers/Muse.hs
+++ b/src/Text/Pandoc/Readers/Muse.hs
@@ -225,7 +225,7 @@ parseEmacsDirective :: PandocMonad m => MuseParser m (String, F Inlines)
parseEmacsDirective = (,)
<$> parseDirectiveKey
<* spaceChar
- <*> (trimInlinesF . mconcat <$> manyTill (choice inlineList) eol)
+ <*> (trimInlinesF . mconcat <$> manyTill inline' eol)
parseAmuseDirective :: PandocMonad m => MuseParser m (String, F Inlines)
parseAmuseDirective = (,)
@@ -455,7 +455,7 @@ playTag = do
verseLine :: PandocMonad m => MuseParser m (F Inlines)
verseLine = do
indent <- (B.str <$> many1 ('\160' <$ char ' ')) <|> pure mempty
- rest <- manyTill (choice inlineList) newline
+ rest <- manyTill inline' newline
return $ trimInlinesF $ mconcat (pure indent : rest)
-- | Parse @\<verse>@ tag.
@@ -546,7 +546,7 @@ lineVerseLine = try $ do
string "> "
indent <- many ('\160' <$ char ' ')
let indentEl = if null indent then mempty else B.str indent
- rest <- manyTill (choice inlineList) eol
+ rest <- manyTill inline' eol
return $ trimInlinesF $ mconcat (pure indentEl : rest)
blanklineVerseLine :: PandocMonad m => MuseParser m (F Inlines)
@@ -648,7 +648,7 @@ definitionListItemsUntil indent end =
where
continuation = try $ do
pos <- getPosition
- term <- trimInlinesF . mconcat <$> manyTill (choice inlineList) (try $ string "::")
+ term <- trimInlinesF . mconcat <$> manyTill inline' (try $ string "::")
(x, (xs, e)) <- descriptionsUntil (sourceColumn pos) (try (optional blankline *> indentWith indent *> continuation) <|> (([],) <$> end))
let xx = (,) <$> term <*> sequence x
return (xx:xs, e)
@@ -753,33 +753,33 @@ tableParseCaption = try $ fmap MuseCaption . trimInlinesF . mconcat
-- ** Inline parsers
-inlineList :: PandocMonad m => [MuseParser m (F Inlines)]
-inlineList = [ whitespace
- , br
- , anchor
- , footnote
- , strong
- , strongTag
- , emph
- , emphTag
- , underlined
- , superscriptTag
- , subscriptTag
- , strikeoutTag
- , verbatimTag
- , classTag
- , nbsp
- , linkOrImage
- , code
- , codeTag
- , mathTag
- , inlineLiteralTag
- , str
- , symbol
- ]
+inline' :: PandocMonad m => MuseParser m (F Inlines)
+inline' = whitespace
+ <|> br
+ <|> anchor
+ <|> footnote
+ <|> strong
+ <|> strongTag
+ <|> emph
+ <|> emphTag
+ <|> underlined
+ <|> superscriptTag
+ <|> subscriptTag
+ <|> strikeoutTag
+ <|> verbatimTag
+ <|> classTag
+ <|> nbsp
+ <|> linkOrImage
+ <|> code
+ <|> codeTag
+ <|> mathTag
+ <|> inlineLiteralTag
+ <|> str
+ <|> symbol
+ <?> "inline"
inline :: PandocMonad m => MuseParser m (F Inlines)
-inline = endline <|> choice inlineList <?> "inline"
+inline = endline <|> inline'
-- | Parse a soft break.
endline :: PandocMonad m => MuseParser m (F Inlines)
@@ -963,7 +963,7 @@ image :: PandocMonad m => MuseParser m (F Inlines)
image = try $ do
string "[["
(url, (ext, width, align)) <- manyUntil (noneOf "]") (imageExtensionAndOptions <* char ']')
- content <- optionMaybe linkContent
+ content <- option mempty linkContent
char ']'
let widthAttr = case align of
Just 'f' -> [("width", fromMaybe "100" width ++ "%"), ("height", "75%")]
@@ -973,7 +973,7 @@ image = try $ do
Just 'l' -> ["align-left"]
Just 'f' -> []
_ -> []
- return $ B.imageWith ("", alignClass, widthAttr) (url ++ ext) mempty <$> fromMaybe (return mempty) content
+ return $ B.imageWith ("", alignClass, widthAttr) (url ++ ext) mempty <$> content
where -- Taken from muse-image-regexp defined in Emacs Muse file lisp/muse-regexps.el
imageExtensions = [".eps", ".gif", ".jpg", ".jpeg", ".pbm", ".png", ".tiff", ".xbm", ".xpm"]
imageExtension = choice (try . string <$> imageExtensions)
diff --git a/src/Text/Pandoc/Writers/LaTeX.hs b/src/Text/Pandoc/Writers/LaTeX.hs
index 3db643503..6042f2765 100644
--- a/src/Text/Pandoc/Writers/LaTeX.hs
+++ b/src/Text/Pandoc/Writers/LaTeX.hs
@@ -176,9 +176,9 @@ pandocToLaTeX options (Pandoc meta blocks) = do
modify $ \s -> s{stCsquotes = True}
let (blocks'', lastHeader) = if writerCiteMethod options == Citeproc then
(blocks', [])
- else case last blocks' of
- Header 1 _ il -> (init blocks', il)
- _ -> (blocks', [])
+ else case reverse blocks' of
+ Header 1 _ il : _ -> (init blocks', il)
+ _ -> (blocks', [])
beamer <- gets stBeamer
blocks''' <- if beamer
then toSlides blocks''
diff --git a/src/Text/Pandoc/Writers/RTF.hs b/src/Text/Pandoc/Writers/RTF.hs
index 3045c1c10..ed8dc9ae4 100644
--- a/src/Text/Pandoc/Writers/RTF.hs
+++ b/src/Text/Pandoc/Writers/RTF.hs
@@ -341,8 +341,10 @@ listItemToRTF :: PandocMonad m
listItemToRTF alignment indent marker [] = return $
rtfCompact (indent + listIncrement) (negate listIncrement) alignment
(marker ++ "\\tx" ++ show listIncrement ++ "\\tab ")
-listItemToRTF alignment indent marker list = do
- (first:rest) <- mapM (blockToRTF (indent + listIncrement) alignment) list
+listItemToRTF alignment indent marker (listFirst:listRest) = do
+ let f = blockToRTF (indent + listIncrement) alignment
+ first <- f listFirst
+ rest <- mapM f listRest
let listMarker = "\\fi" ++ show (negate listIncrement) ++ " " ++ marker ++
"\\tx" ++ show listIncrement ++ "\\tab"
let insertListMarker ('\\':'f':'i':'-':d:xs) | isDigit d =