Merge pull request #4018 from swilde/creole-fixes

Creole Reader: fix lists with triling white space
This commit is contained in:
John MacFarlane 2017-11-01 00:04:36 -04:00 committed by GitHub
commit fd7e3cb18f
No known key found for this signature in database
GPG key ID: 4AEE18F83AFDEB23
2 changed files with 21 additions and 6 deletions

View file

@ -27,7 +27,7 @@ Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA 02111-1307 USA
License : GNU GPL, version 2 or above
Maintainer : Sascha Wilde <wilde@sha-bang.de>
Stability : WIP
Stability : alpha
Portability : portable
Conversion of creole text to 'Pandoc' document.
@ -64,7 +64,7 @@ readCreole opts s = do
type CRLParser = ParserT [Char] ParserState
--
-- Utility funcitons
-- Utility functions
--
(<+>) :: (Monad m, Monoid a) => m a -> m a -> m a
@ -111,7 +111,8 @@ block = do
return res
nowiki :: PandocMonad m => CRLParser m B.Blocks
nowiki = try $ fmap (B.codeBlock . mconcat) (nowikiStart >> manyTill content nowikiEnd)
nowiki = try $ fmap (B.codeBlock . mconcat) (nowikiStart
>> manyTill content nowikiEnd)
where
content = brackets <|> line
brackets = try $ option "" ((:[]) <$> newline)
@ -154,7 +155,8 @@ listItem :: PandocMonad m => Char -> Int -> CRLParser m B.Blocks
listItem c n =
fmap (B.plain . B.trimInlines .mconcat) (listStart >> many1Till inline itemEnd)
where
listStart = try $ optional newline >> skipSpaces >> count n (char c)
listStart = try $ skipSpaces >> optional newline >> skipSpaces
>> count n (char c)
>> lookAhead (noneOf [c]) >> skipSpaces
itemEnd = endOfParaElement <|> nextItem n
<|> if n < 3 then nextItem (n+1)
@ -193,7 +195,7 @@ endOfParaElement = lookAhead $ endOfInput <|> endOfPara
startOf :: PandocMonad m => CRLParser m a -> CRLParser m ()
startOf p = try $ blankline >> p >> return mempty
startOfList = startOf $ anyList 1
startOfTable =startOf table
startOfTable = startOf table
startOfHeader = startOf header
startOfNowiki = startOf nowiki
hr = startOf horizontalRule

View file

@ -127,6 +127,11 @@ tests = [
=?> bulletList [ plain "foo"
<> bulletList [ plain "bar", plain "baz" ]
, plain "blubb" ]
, "nested unordered list, one separating space, trailing space" =:
"* foo \n** bar \n** baz \n* blubb "
=?> bulletList [ plain "foo"
<> bulletList [ plain "bar", plain "baz" ]
, plain "blubb" ]
, "ordered list, two entries, one separating space" =:
"# foo\n# bar"
=?> orderedList [ plain "foo", plain "bar" ]
@ -141,6 +146,11 @@ tests = [
=?> orderedList [ plain "foo"
<> orderedList [ plain "bar", plain "baz" ]
, plain "blubb" ]
, "nested ordered list, one separating space, trailing space" =:
"# foo \n## bar \n## baz \n# blubb "
=?> orderedList [ plain "foo"
<> orderedList [ plain "bar", plain "baz" ]
, plain "blubb" ]
, "nested many ordered lists, one separating space" =:
("# foo\n## bar\n### third\n### third two\n## baz\n### third again\n"
<> "#### fourth\n##### fith\n# blubb")
@ -193,7 +203,10 @@ tests = [
, "forced line breaks" =:
"{{{no break!\\\\here}}} but a break\\\\here!"
=?> para (code "no break!\\\\here" <> " but a break"
<> linebreak <> "here!")
<> linebreak <> "here!"),
"quoted block, after trailing white space" =:
"this is a paragraph \n{{{\nfoo bar\n //baz//\n}}}"
=?> para "this is a paragraph" <> codeBlock "foo bar\n //baz//"
]
, testGroup "Images and Links" [
"image simple" =: