Markdown reader: Support RST-style line blocks.

This depends on the new Ext_line_blocks extension.
This commit is contained in:
John MacFarlane 2013-01-13 12:34:18 -08:00
parent 0598cf0fee
commit 6b5302e063
2 changed files with 15 additions and 1 deletions

View file

@ -95,6 +95,7 @@ data Extension =
| Ext_auto_identifiers -- ^ Automatic identifiers for headers
| Ext_header_attributes -- ^ Explicit header attributes {#id .class k=v}
| Ext_implicit_header_references -- ^ Implicit reference links for headers
| Ext_line_blocks -- ^ RST style line blocks
deriving (Show, Read, Enum, Eq, Ord, Bounded)
pandocExtensions :: Set Extension
@ -134,6 +135,7 @@ pandocExtensions = Set.fromList
, Ext_auto_identifiers
, Ext_header_attributes
, Ext_implicit_header_references
, Ext_line_blocks
]
phpMarkdownExtraExtensions :: Set Extension

View file

@ -31,7 +31,7 @@ Conversion of markdown-formatted plain text to 'Pandoc' document.
module Text.Pandoc.Readers.Markdown ( readMarkdown,
readMarkdownWithWarnings ) where
import Data.List ( transpose, sortBy, findIndex, intercalate )
import Data.List ( transpose, sortBy, findIndex, intersperse, intercalate )
import qualified Data.Map as M
import Data.Ord ( comparing )
import Data.Char ( isAlphaNum, toLower )
@ -350,6 +350,7 @@ block = choice [ codeBlockFenced
, header
, rawTeXBlock
, htmlBlock
, lineBlock
, table
, codeBlockIndented
, lhsCodeBlock
@ -868,6 +869,17 @@ stripMarkdownAttribute s = renderTags' $ map filterAttrib $ parseTags s
[(k,v) | (k,v) <- as, k /= "markdown"]
filterAttrib x = x
--
-- line block
--
lineBlock :: MarkdownParser (F Blocks)
lineBlock = try $ do
guardEnabled Ext_line_blocks
lines' <- lineBlockLines >>=
mapM (parseFromString (trimInlinesF . mconcat <$> many inline))
return $ B.para <$> (mconcat $ intersperse (return B.linebreak) lines')
--
-- Tables
--