Added Ext_fenced_code_attributes.
This commit is contained in:
parent
b985d33406
commit
dc6a133dbf
3 changed files with 12 additions and 6 deletions
|
@ -65,6 +65,7 @@ data Extension =
|
|||
| Ext_tex_math_double_backslash -- ^ TeX math btw \\(..\\) \\[..\\]
|
||||
| Ext_latex_macros -- ^ Parse LaTeX macro definitions (for math only)
|
||||
| Ext_fenced_code_blocks -- ^ Parse fenced code blocks
|
||||
| Ext_fenced_code_attributes -- ^ Allow attributes on fenced code blocks
|
||||
| Ext_inline_code_attributes -- ^ Allow attributes on inline code
|
||||
| Ext_markdown_in_html_blocks -- ^ Interpret as markdown inside HTML blocks
|
||||
| Ext_markdown_attribute -- ^ Interpret text inside HTML as markdown
|
||||
|
@ -105,6 +106,7 @@ pandocExtensions = Set.fromList
|
|||
, Ext_tex_math_dollars
|
||||
, Ext_latex_macros
|
||||
, Ext_fenced_code_blocks
|
||||
, Ext_fenced_code_attributes
|
||||
, Ext_inline_code_attributes
|
||||
, Ext_markdown_in_html_blocks
|
||||
, Ext_escaped_line_breaks
|
||||
|
|
|
@ -379,7 +379,7 @@ indentedLine = indentSpaces >> manyTill anyChar newline >>= return . (++ "\n")
|
|||
|
||||
blockDelimiter :: (Char -> Bool)
|
||||
-> Maybe Int
|
||||
-> Parser [Char] st (Int, (String, [String], [(String, String)]), Char)
|
||||
-> Parser [Char] ParserState (Int, (String, [String], [(String, String)]), Char)
|
||||
blockDelimiter f len = try $ do
|
||||
c <- lookAhead (satisfy f)
|
||||
size <- case len of
|
||||
|
@ -387,9 +387,11 @@ blockDelimiter f len = try $ do
|
|||
Nothing -> count 3 (char c) >> many (char c) >>=
|
||||
return . (+ 3) . length
|
||||
many spaceChar
|
||||
attr <- option ([],[],[])
|
||||
$ attributes -- ~~~ {.ruby}
|
||||
<|> (many1 alphaNum >>= \x -> return ([],[x],[])) -- github variant ```ruby
|
||||
attr <- option ([],[],[]) $ do
|
||||
guardEnabled Ext_fenced_code_attributes
|
||||
attributes -- ~~~ {.ruby}
|
||||
<|> (many1 alphaNum >>= \x ->
|
||||
return ([],[x],[])) -- github variant ```ruby
|
||||
blankline
|
||||
return (size, attr, c)
|
||||
|
||||
|
|
|
@ -297,8 +297,10 @@ blockToMarkdown opts (CodeBlock attribs str) = return $
|
|||
(tildes <> space <> attrs <> cr <> text str <>
|
||||
cr <> tildes) <> blankline
|
||||
else nest (writerTabStop opts) (text str) <> blankline
|
||||
where tildes = text "~~~~"
|
||||
attrs = attrsToMarkdown attribs
|
||||
where tildes = text "~~~~"
|
||||
attrs = if isEnabled Ext_fenced_code_attributes opts
|
||||
then attrsToMarkdown attribs
|
||||
else empty
|
||||
blockToMarkdown opts (BlockQuote blocks) = do
|
||||
st <- get
|
||||
-- if we're writing literate haskell, put a space before the bird tracks
|
||||
|
|
Loading…
Add table
Reference in a new issue