aboutsummaryrefslogtreecommitdiff
diff options
context:
space:
mode:
-rw-r--r--MANUAL.txt31
-rw-r--r--src/Text/Pandoc/Extensions.hs2
-rw-r--r--src/Text/Pandoc/Parsing.hs2
-rw-r--r--src/Text/Pandoc/Readers/Markdown.hs28
-rw-r--r--test/command/168.md30
5 files changed, 93 insertions, 0 deletions
diff --git a/MANUAL.txt b/MANUAL.txt
index eacd11275..b52e900c3 100644
--- a/MANUAL.txt
+++ b/MANUAL.txt
@@ -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
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` ####
In addition to raw HTML, pandoc allows raw LaTeX, TeX, and ConTeXt to be
diff --git a/src/Text/Pandoc/Extensions.hs b/src/Text/Pandoc/Extensions.hs
index 5d3a4cb29..8c8b405be 100644
--- a/src/Text/Pandoc/Extensions.hs
+++ b/src/Text/Pandoc/Extensions.hs
@@ -107,6 +107,7 @@ data Extension =
| Ext_raw_attribute -- ^ Allow explicit raw blocks/inlines
| Ext_markdown_in_html_blocks -- ^ Interpret as markdown inside HTML blocks
| 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_bracketed_spans -- ^ Bracketed spans with attributes
| Ext_markdown_attribute -- ^ Interpret text inside HTML as markdown
@@ -183,6 +184,7 @@ pandocExtensions = extensionsFromList
, Ext_raw_attribute
, Ext_markdown_in_html_blocks
, Ext_native_divs
+ , Ext_fenced_divs
, Ext_native_spans
, Ext_bracketed_spans
, Ext_escaped_line_breaks
diff --git a/src/Text/Pandoc/Parsing.hs b/src/Text/Pandoc/Parsing.hs
index 2543f11f0..73498788d 100644
--- a/src/Text/Pandoc/Parsing.hs
+++ b/src/Text/Pandoc/Parsing.hs
@@ -1069,6 +1069,7 @@ data ParserState = ParserState
-- roles), 3) Additional classes (rest of Attr is unused)).
stateCaption :: Maybe Inlines, -- ^ Caption in current environment
stateInHtmlBlock :: Maybe String, -- ^ Tag type of HTML block being parsed
+ stateFencedDivLevel :: Int, -- ^ Depth of fenced div
stateContainers :: [String], -- ^ parent include files
stateLogMessages :: [LogMessage], -- ^ log messages
stateMarkdownAttribute :: Bool -- ^ True if in markdown=1 context
@@ -1185,6 +1186,7 @@ defaultParserState =
stateRstCustomRoles = M.empty,
stateCaption = Nothing,
stateInHtmlBlock = Nothing,
+ stateFencedDivLevel = 0,
stateContainers = [],
stateLogMessages = [],
stateMarkdownAttribute = False
diff --git a/src/Text/Pandoc/Readers/Markdown.hs b/src/Text/Pandoc/Readers/Markdown.hs
index 61c07ed12..221c834e8 100644
--- a/src/Text/Pandoc/Readers/Markdown.hs
+++ b/src/Text/Pandoc/Readers/Markdown.hs
@@ -499,6 +499,7 @@ block = do
, header
, lhsCodeBlock
, divHtml
+ , divFenced
, htmlBlock
, table
, codeBlockIndented
@@ -1686,6 +1687,9 @@ endline = try $ do
guardEnabled Ext_blank_before_header <|> (notFollowedBy . char =<< atxChar) -- atx header
guardDisabled Ext_backtick_code_blocks <|>
notFollowedBy (() <$ (lookAhead (char '`') >> codeBlockFenced))
+ guardDisabled Ext_fenced_divs <|>
+ do divLevel <- stateFencedDivLevel <$> getState
+ guard (divLevel < 1) <|> notFollowedBy fenceEnd
notFollowedByHtmlCloser
(eof >> return mempty)
<|> (guardEnabled Ext_hard_line_breaks >> return (return B.linebreak))
@@ -1930,6 +1934,30 @@ divHtml = try $ do
else -- avoid backtracing
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 = do
guardEnabled Ext_raw_html
diff --git a/test/command/168.md b/test/command/168.md
new file mode 100644
index 000000000..0d6183a78
--- /dev/null
+++ b/test/command/168.md
@@ -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"]]
+```