aboutsummaryrefslogtreecommitdiff
path: root/src/Text
diff options
context:
space:
mode:
Diffstat (limited to 'src/Text')
-rw-r--r--src/Text/Pandoc/Readers/Textile.hs24
-rw-r--r--src/Text/Pandoc/Writers/Markdown.hs26
2 files changed, 32 insertions, 18 deletions
diff --git a/src/Text/Pandoc/Readers/Textile.hs b/src/Text/Pandoc/Readers/Textile.hs
index 6d839ec1d..cd34da942 100644
--- a/src/Text/Pandoc/Readers/Textile.hs
+++ b/src/Text/Pandoc/Readers/Textile.hs
@@ -265,8 +265,20 @@ definitionList :: Parser [Char] ParserState Blocks
definitionList = try $ B.definitionList <$> many1 definitionListItem
-- | List start character.
-listStart :: Parser [Char] st Char
-listStart = oneOf "*#-"
+listStart :: Parser [Char] ParserState ()
+listStart = genericListStart '*'
+ <|> () <$ genericListStart '#'
+ <|> () <$ definitionListStart
+
+genericListStart :: Char -> Parser [Char] st ()
+genericListStart c = () <$ try (many1 (char c) >> whitespace)
+
+definitionListStart :: Parser [Char] ParserState Inlines
+definitionListStart = try $ do
+ char '-'
+ whitespace
+ trimInlines . mconcat <$>
+ many1Till inline (try (string ":=")) <* optional whitespace
listInline :: Parser [Char] ParserState Inlines
listInline = try (notFollowedBy newline >> inline)
@@ -278,8 +290,7 @@ listInline = try (notFollowedBy newline >> inline)
-- break.
definitionListItem :: Parser [Char] ParserState (Inlines, [Blocks])
definitionListItem = try $ do
- string "- "
- term <- mconcat <$> many1Till inline (try (whitespace >> string ":="))
+ term <- definitionListStart
def' <- multilineDef <|> inlineDef
return (term, def')
where inlineDef :: Parser [Char] ParserState [Blocks]
@@ -488,7 +499,7 @@ str = do
return $ B.str fullStr
-- | Some number of space chars
-whitespace :: Parser [Char] ParserState Inlines
+whitespace :: Parser [Char] st Inlines
whitespace = many1 spaceChar >> return B.space <?> "whitespace"
-- | In Textile, an isolated endline character is a line break
@@ -616,7 +627,8 @@ simpleInline border construct = try $ do
attr <- attributes
body <- trimInlines . mconcat <$>
withQuoteContext InSingleQuote
- (manyTill inline (try border <* notFollowedBy alphaNum))
+ (manyTill (notFollowedBy newline >> inline)
+ (try border <* notFollowedBy alphaNum))
return $ construct $
if attr == nullAttr
then body
diff --git a/src/Text/Pandoc/Writers/Markdown.hs b/src/Text/Pandoc/Writers/Markdown.hs
index 211d793dd..5c0476b7d 100644
--- a/src/Text/Pandoc/Writers/Markdown.hs
+++ b/src/Text/Pandoc/Writers/Markdown.hs
@@ -80,6 +80,8 @@ writePlain opts document =
writerExtensions = Set.delete Ext_escaped_line_breaks $
Set.delete Ext_pipe_tables $
Set.delete Ext_raw_html $
+ Set.delete Ext_markdown_in_html_blocks $
+ Set.delete Ext_raw_tex $
Set.delete Ext_footnotes $
Set.delete Ext_tex_math_dollars $
Set.delete Ext_citations $
@@ -296,12 +298,12 @@ blockToMarkdown :: WriterOptions -- ^ Options
-> State WriterState Doc
blockToMarkdown _ Null = return empty
blockToMarkdown opts (Div attrs ils) = do
- plain <- gets stPlain
contents <- blockListToMarkdown opts ils
- return $ if plain || not (isEnabled Ext_markdown_in_html_blocks opts)
- then contents <> blankline
- else tagWithAttrs "div" attrs <> blankline <>
+ return $ if isEnabled Ext_raw_html opts &&
+ isEnabled Ext_markdown_in_html_blocks opts
+ then tagWithAttrs "div" attrs <> blankline <>
contents <> blankline <> "</div>" <> blankline
+ else contents <> blankline
blockToMarkdown opts (Plain inlines) = do
contents <- inlineListToMarkdown opts inlines
-- escape if para starts with ordered list marker
@@ -676,11 +678,10 @@ escapeSpaces x = x
-- | Convert Pandoc inline element to markdown.
inlineToMarkdown :: WriterOptions -> Inline -> State WriterState Doc
inlineToMarkdown opts (Span attrs ils) = do
- plain <- gets stPlain
contents <- inlineListToMarkdown opts ils
- return $ if plain
- then contents
- else tagWithAttrs "span" attrs <> contents <> text "</span>"
+ return $ if isEnabled Ext_raw_html opts
+ then tagWithAttrs "span" attrs <> contents <> text "</span>"
+ else contents
inlineToMarkdown opts (Emph lst) = do
plain <- gets stPlain
contents <- inlineListToMarkdown opts lst
@@ -696,8 +697,7 @@ inlineToMarkdown opts (Strong lst) = do
return $ "**" <> contents <> "**"
inlineToMarkdown opts (Strikeout lst) = do
contents <- inlineListToMarkdown opts lst
- plain <- gets stPlain
- return $ if plain || isEnabled Ext_strikeout opts
+ return $ if isEnabled Ext_strikeout opts
then "~~" <> contents <> "~~"
else "<s>" <> contents <> "</s>"
inlineToMarkdown opts (Superscript lst) = do
@@ -767,8 +767,10 @@ inlineToMarkdown opts (Math DisplayMath str)
inlineListToMarkdown opts (texMathToInlines DisplayMath str)
inlineToMarkdown opts (RawInline f str) = do
plain <- gets stPlain
- if not plain && f == "html" || f == "markdown" ||
- (isEnabled Ext_raw_tex opts && (f == "latex" || f == "tex"))
+ if not plain &&
+ ( f == "markdown" ||
+ (isEnabled Ext_raw_tex opts && (f == "latex" || f == "tex")) ||
+ (isEnabled Ext_raw_html opts && f == "html") )
then return $ text str
else return empty
inlineToMarkdown opts (LineBreak) = do