Merge pull request #1645 from neongreen/issue1636
Fix 'Ext_lists_without_preceding_blankline' bug.
This commit is contained in:
commit
43c1978fae
2 changed files with 21 additions and 2 deletions
|
@ -117,6 +117,12 @@ isBlank _ = False
|
|||
-- auxiliary functions
|
||||
--
|
||||
|
||||
-- | Succeeds when we're in list context.
|
||||
inList :: MarkdownParser ()
|
||||
inList = do
|
||||
ctx <- stateParserContext <$> getState
|
||||
guard (ctx == ListItemState)
|
||||
|
||||
isNull :: F Inlines -> Bool
|
||||
isNull ils = B.isNull $ runF ils def
|
||||
|
||||
|
@ -926,6 +932,8 @@ para = try $ do
|
|||
<|> (guardEnabled Ext_backtick_code_blocks >> () <$ lookAhead codeBlockFenced)
|
||||
<|> (guardDisabled Ext_blank_before_header >> () <$ lookAhead header)
|
||||
<|> (guardEnabled Ext_lists_without_preceding_blankline >>
|
||||
-- Avoid creating a paragraph in a nested list.
|
||||
notFollowedBy' inList >>
|
||||
() <$ lookAhead listStart)
|
||||
<|> do guardEnabled Ext_native_divs
|
||||
inHtmlBlock <- stateInHtmlBlock <$> getState
|
||||
|
@ -1610,8 +1618,7 @@ endline = try $ do
|
|||
newline
|
||||
notFollowedBy blankline
|
||||
-- parse potential list-starts differently if in a list:
|
||||
st <- getState
|
||||
when (stateParserContext st == ListItemState) $ notFollowedBy listStart
|
||||
notFollowedBy (inList >> listStart)
|
||||
guardDisabled Ext_lists_without_preceding_blankline <|> notFollowedBy listStart
|
||||
guardEnabled Ext_blank_before_blockquote <|> notFollowedBy emailBlockQuoteStart
|
||||
guardEnabled Ext_blank_before_header <|> notFollowedBy (char '#') -- atx header
|
||||
|
|
|
@ -20,6 +20,9 @@ markdownCDL :: String -> Pandoc
|
|||
markdownCDL = readMarkdown def { readerExtensions = Set.insert
|
||||
Ext_compact_definition_lists $ readerExtensions def }
|
||||
|
||||
markdownGH :: String -> Pandoc
|
||||
markdownGH = readMarkdown def { readerExtensions = githubMarkdownExtensions }
|
||||
|
||||
infix 4 =:
|
||||
(=:) :: ToString c
|
||||
=> String -> (String, c) -> Test
|
||||
|
@ -271,5 +274,14 @@ tests = [ testGroup "inline code"
|
|||
plain (text "if this button exists") <>
|
||||
rawBlock "html" "</button>" <>
|
||||
divWith nullAttr (para $ text "with this div too.")]
|
||||
, test markdownGH "issue #1636" $
|
||||
unlines [ "* a"
|
||||
, "* b"
|
||||
, "* c"
|
||||
, " * d" ]
|
||||
=?>
|
||||
bulletList [ plain "a"
|
||||
, plain "b"
|
||||
, plain "c" <> bulletList [plain "d"] ]
|
||||
]
|
||||
]
|
||||
|
|
Loading…
Add table
Reference in a new issue