Implemented fenced Divs.

+ Added Ext_fenced_divs to Extensions (default for pandoc Markdown).
+ Document fenced_divs extension in manual.
+ Implemented fenced code divs in Markdown reader.
+ Added test.

Closes #168.
This commit is contained in:
John MacFarlane 2017-10-23 21:40:45 -07:00
parent 896803b0d5
commit fda0c0119f
5 changed files with 93 additions and 0 deletions

View file

@ -3073,6 +3073,37 @@ For the most part this should give the same output as `raw_html`,
but it makes it easier to write pandoc filters to manipulate groups but it makes it easier to write pandoc filters to manipulate groups
of inlines. of inlines.
#### Extension: `fenced_divs` ####
Allow special fenced syntax for native `Div` blocks. A Div
starts with a fence containing at least three consecutive
colons plus some attributes. The attributes may optionally
be followed by another string of consecutive colons.
The attribute syntax is exactly as in fenced code blocks (see
[Extension-fenced_code_attributes], above). The Div ends with
another line containing a string of at least three consecutive
colons. The fenced Div should be separated by blank lines from
preceding and following blocks.
Example:
::::: {#special .sidebar}
Here is a paragraph.
And another.
:::::
Fenced divs can be nested. Opening fences are distinguished
because they *must* have attributes:
::: Warning
This is a warning.
::: Danger
This is a warning within a warning.
:::
:::
#### Extension: `raw_tex` #### #### Extension: `raw_tex` ####
In addition to raw HTML, pandoc allows raw LaTeX, TeX, and ConTeXt to be In addition to raw HTML, pandoc allows raw LaTeX, TeX, and ConTeXt to be

View file

@ -107,6 +107,7 @@ data Extension =
| Ext_raw_attribute -- ^ Allow explicit raw blocks/inlines | Ext_raw_attribute -- ^ Allow explicit raw blocks/inlines
| Ext_markdown_in_html_blocks -- ^ Interpret as markdown inside HTML blocks | Ext_markdown_in_html_blocks -- ^ Interpret as markdown inside HTML blocks
| Ext_native_divs -- ^ Use Div blocks for contents of <div> tags | Ext_native_divs -- ^ Use Div blocks for contents of <div> tags
| Ext_fenced_divs -- ^ Allow fenced div syntax :::
| Ext_native_spans -- ^ Use Span inlines for contents of <span> | Ext_native_spans -- ^ Use Span inlines for contents of <span>
| Ext_bracketed_spans -- ^ Bracketed spans with attributes | Ext_bracketed_spans -- ^ Bracketed spans with attributes
| Ext_markdown_attribute -- ^ Interpret text inside HTML as markdown | Ext_markdown_attribute -- ^ Interpret text inside HTML as markdown
@ -183,6 +184,7 @@ pandocExtensions = extensionsFromList
, Ext_raw_attribute , Ext_raw_attribute
, Ext_markdown_in_html_blocks , Ext_markdown_in_html_blocks
, Ext_native_divs , Ext_native_divs
, Ext_fenced_divs
, Ext_native_spans , Ext_native_spans
, Ext_bracketed_spans , Ext_bracketed_spans
, Ext_escaped_line_breaks , Ext_escaped_line_breaks

View file

@ -1069,6 +1069,7 @@ data ParserState = ParserState
-- roles), 3) Additional classes (rest of Attr is unused)). -- roles), 3) Additional classes (rest of Attr is unused)).
stateCaption :: Maybe Inlines, -- ^ Caption in current environment stateCaption :: Maybe Inlines, -- ^ Caption in current environment
stateInHtmlBlock :: Maybe String, -- ^ Tag type of HTML block being parsed stateInHtmlBlock :: Maybe String, -- ^ Tag type of HTML block being parsed
stateFencedDivLevel :: Int, -- ^ Depth of fenced div
stateContainers :: [String], -- ^ parent include files stateContainers :: [String], -- ^ parent include files
stateLogMessages :: [LogMessage], -- ^ log messages stateLogMessages :: [LogMessage], -- ^ log messages
stateMarkdownAttribute :: Bool -- ^ True if in markdown=1 context stateMarkdownAttribute :: Bool -- ^ True if in markdown=1 context
@ -1185,6 +1186,7 @@ defaultParserState =
stateRstCustomRoles = M.empty, stateRstCustomRoles = M.empty,
stateCaption = Nothing, stateCaption = Nothing,
stateInHtmlBlock = Nothing, stateInHtmlBlock = Nothing,
stateFencedDivLevel = 0,
stateContainers = [], stateContainers = [],
stateLogMessages = [], stateLogMessages = [],
stateMarkdownAttribute = False stateMarkdownAttribute = False

View file

@ -499,6 +499,7 @@ block = do
, header , header
, lhsCodeBlock , lhsCodeBlock
, divHtml , divHtml
, divFenced
, htmlBlock , htmlBlock
, table , table
, codeBlockIndented , codeBlockIndented
@ -1686,6 +1687,9 @@ endline = try $ do
guardEnabled Ext_blank_before_header <|> (notFollowedBy . char =<< atxChar) -- atx header guardEnabled Ext_blank_before_header <|> (notFollowedBy . char =<< atxChar) -- atx header
guardDisabled Ext_backtick_code_blocks <|> guardDisabled Ext_backtick_code_blocks <|>
notFollowedBy (() <$ (lookAhead (char '`') >> codeBlockFenced)) notFollowedBy (() <$ (lookAhead (char '`') >> codeBlockFenced))
guardDisabled Ext_fenced_divs <|>
do divLevel <- stateFencedDivLevel <$> getState
guard (divLevel < 1) <|> notFollowedBy fenceEnd
notFollowedByHtmlCloser notFollowedByHtmlCloser
(eof >> return mempty) (eof >> return mempty)
<|> (guardEnabled Ext_hard_line_breaks >> return (return B.linebreak)) <|> (guardEnabled Ext_hard_line_breaks >> return (return B.linebreak))
@ -1930,6 +1934,30 @@ divHtml = try $ do
else -- avoid backtracing else -- avoid backtracing
return $ return (B.rawBlock "html" (rawtag <> bls)) <> contents return $ return (B.rawBlock "html" (rawtag <> bls)) <> contents
divFenced :: PandocMonad m => MarkdownParser m (F Blocks)
divFenced = try $ do
guardEnabled Ext_fenced_divs
nonindentSpaces
string ":::"
skipMany (char ':')
skipMany spaceChar
attribs <- attributes <|> ((\x -> ("",[x],[])) <$> many1 nonspaceChar)
skipMany spaceChar
skipMany (char ':')
blankline
updateState $ \st -> st{ stateFencedDivLevel = stateFencedDivLevel st + 1 }
bs <- mconcat <$> manyTill block fenceEnd
updateState $ \st -> st{ stateFencedDivLevel = stateFencedDivLevel st - 1 }
return $ B.divWith attribs <$> bs
fenceEnd :: PandocMonad m => MarkdownParser m ()
fenceEnd = try $ do
nonindentSpaces
string ":::"
skipMany (char ':')
blanklines
return ()
rawHtmlInline :: PandocMonad m => MarkdownParser m (F Inlines) rawHtmlInline :: PandocMonad m => MarkdownParser m (F Inlines)
rawHtmlInline = do rawHtmlInline = do
guardEnabled Ext_raw_html guardEnabled Ext_raw_html

30
test/command/168.md Normal file
View file

@ -0,0 +1,30 @@
```
% pandoc -t native
:::::::::: warning ::::::::::::
This is the warning!
1. list
2. another
::: {#myid .class key=val}
nested div
:::
:::::::::::::::::::::::::::::::
^D
[Div ("",["warning"],[])
[Para [Str "This",Space,Str "is",Space,Str "the",Space,Str "warning!"]
,OrderedList (1,Decimal,Period)
[[Plain [Str "list"]]
,[Plain [Str "another"]]]
,Div ("myid",["class"],[("key","val")])
[Plain [Str "nested",Space,Str "div"]]]]
```
```
% pandoc -t native
foo
:::
bar
^D
[Para [Str "foo",SoftBreak,Str ":::",SoftBreak,Str "bar"]]
```