From cd85c73ded2b100d33d3c1d36eac182bdd593b2f Mon Sep 17 00:00:00 2001
From: Albert Krewinkel <albert@zeitkraut.de>
Date: Wed, 22 Nov 2017 22:17:45 +0100
Subject: Org reader: allow empty list items

Fixes: #4090
---
 src/Text/Pandoc/Readers/Org/BlockStarts.hs | 26 +++++++------
 src/Text/Pandoc/Readers/Org/Blocks.hs      | 61 +++++++++++++-----------------
 2 files changed, 42 insertions(+), 45 deletions(-)

(limited to 'src/Text/Pandoc/Readers/Org')

diff --git a/src/Text/Pandoc/Readers/Org/BlockStarts.hs b/src/Text/Pandoc/Readers/Org/BlockStarts.hs
index 9c6614c99..7937c0ef7 100644
--- a/src/Text/Pandoc/Readers/Org/BlockStarts.hs
+++ b/src/Text/Pandoc/Readers/Org/BlockStarts.hs
@@ -75,21 +75,25 @@ latexEnvStart = try $
    latexEnvName :: Monad m => OrgParser m String
    latexEnvName = try $ mappend <$> many1 alphaNum <*> option "" (string "*")
 
-
--- | Parses bullet list marker.
-bulletListStart :: Monad m => OrgParser m ()
-bulletListStart = try $
-  choice
-  [ () <$ skipSpaces  <* oneOf "+-" <* skipSpaces1
-  , () <$ skipSpaces1 <* char '*'   <* skipSpaces1
-  ]
+bulletListStart :: Monad m => OrgParser m Int
+bulletListStart = try $ do
+  ind <- length <$> many spaceChar
+   -- Unindented lists cannot use '*' bullets.
+  oneOf (if ind == 0 then "+-" else "*+-")
+  skipSpaces1 <|> lookAhead eol
+  return (ind + 1)
 
 genericListStart :: Monad m
                  => OrgParser m String
                  -> OrgParser m Int
-genericListStart listMarker = try $
-  (+) <$> (length <$> many spaceChar)
-      <*> (length <$> listMarker <* many1 spaceChar)
+genericListStart listMarker = try $ do
+  ind <- length <$> many spaceChar
+  void listMarker
+  skipSpaces1 <|> lookAhead eol
+  return (ind + 1)
+
+eol :: Monad m => OrgParser m ()
+eol = void (char '\n')
 
 orderedListStart :: Monad m => OrgParser m Int
 orderedListStart = genericListStart orderedListMarker
diff --git a/src/Text/Pandoc/Readers/Org/Blocks.hs b/src/Text/Pandoc/Readers/Org/Blocks.hs
index 7f10195fe..04a0efc15 100644
--- a/src/Text/Pandoc/Readers/Org/Blocks.hs
+++ b/src/Text/Pandoc/Readers/Org/Blocks.hs
@@ -744,7 +744,7 @@ paraOrPlain = try $ do
   -- is directly followed by a list item, in which case the block is read as
   -- plain text.
   try (guard nl
-       *> notFollowedBy (inList *> (() <$ orderedListStart <|> bulletListStart))
+       *> notFollowedBy (inList *> (orderedListStart <|> bulletListStart))
        *> return (B.para <$> ils))
     <|>  return (B.plain <$> ils)
 
@@ -757,40 +757,34 @@ list :: PandocMonad m => OrgParser m (F Blocks)
 list = choice [ definitionList, bulletList, orderedList ] <?> "list"
 
 definitionList :: PandocMonad m => OrgParser m (F Blocks)
-definitionList = try $ do n <- lookAhead (bulletListStart' Nothing)
-                          fmap (B.definitionList . compactifyDL) . sequence
-                            <$> many1 (definitionListItem $ bulletListStart' (Just n))
+definitionList = try $ do
+  indent <- lookAhead bulletListStart
+  fmap (B.definitionList . compactifyDL) . sequence
+    <$> many1 (definitionListItem (bulletListStart `indented` indent))
 
 bulletList :: PandocMonad m => OrgParser m (F Blocks)
-bulletList = try $ do n <- lookAhead (bulletListStart' Nothing)
-                      fmap (B.bulletList . compactify) . sequence
-                        <$> many1 (listItem (bulletListStart' $ Just n))
+bulletList = try $ do
+  indent <- lookAhead bulletListStart
+  fmap (B.bulletList . compactify) . sequence
+    <$> many1 (listItem (bulletListStart `indented` indent))
+
+indented :: Monad m => OrgParser m Int -> Int -> OrgParser m Int
+indented indentedMarker minIndent = try $ do
+  n <- indentedMarker
+  guard (minIndent <= n)
+  return n
 
 orderedList :: PandocMonad m => OrgParser m (F Blocks)
-orderedList = fmap (B.orderedList . compactify) . sequence
-              <$> many1 (listItem orderedListStart)
-
-bulletListStart' :: Monad m => Maybe Int -> OrgParser m Int
--- returns length of bulletList prefix, inclusive of marker
-bulletListStart' Nothing  = do ind <- length <$> many spaceChar
-                               oneOf (bullets $ ind == 0)
-                               skipSpaces1
-                               return (ind + 1)
-bulletListStart' (Just n) = do count (n-1) spaceChar
-                               oneOf (bullets $ n == 1)
-                               many1 spaceChar
-                               return n
-
--- Unindented lists are legal, but they can't use '*' bullets.
--- We return n to maintain compatibility with the generic listItem.
-bullets :: Bool -> String
-bullets unindented = if unindented then "+-" else "*+-"
+orderedList = try $ do
+  indent <- lookAhead orderedListStart
+  fmap (B.orderedList . compactify) . sequence
+    <$> many1 (listItem (orderedListStart `indented` indent))
 
 definitionListItem :: PandocMonad m
                    => OrgParser m Int
                    -> OrgParser m (F (Inlines, [Blocks]))
-definitionListItem parseMarkerGetLength = try $ do
-  markerLength <- parseMarkerGetLength
+definitionListItem parseIndentedMarker = try $ do
+  markerLength <- parseIndentedMarker
   term <- manyTill (noneOf "\n\r") (try definitionMarker)
   line1 <- anyLineNewline
   blank <- option "" ("\n" <$ blankline)
@@ -802,13 +796,12 @@ definitionListItem parseMarkerGetLength = try $ do
    definitionMarker =
      spaceChar *> string "::" <* (spaceChar <|> lookAhead newline)
 
-
--- parse raw text for one list item, excluding start marker and continuations
+-- | parse raw text for one list item
 listItem :: PandocMonad m
          => OrgParser m Int
          -> OrgParser m (F Blocks)
-listItem start = try . withContext ListItemState $ do
-  markerLength <- try start
+listItem parseIndentedMarker = try . withContext ListItemState $ do
+  markerLength <- try parseIndentedMarker
   firstLine <- anyLineNewline
   blank <- option "" ("\n" <$ blankline)
   rest <- concat <$> many (listContinuation markerLength)
@@ -818,9 +811,9 @@ listItem start = try . withContext ListItemState $ do
 -- Note: nested lists are parsed as continuations.
 listContinuation :: Monad m => Int
                  -> OrgParser m String
-listContinuation markerLength = try $
+listContinuation markerLength = try $ do
   notFollowedBy' blankline
-  *> (mappend <$> (concat <$> many1 listLine)
-              <*> many blankline)
+  mappend <$> (concat <$> many1 listLine)
+          <*> many blankline
  where
    listLine = try $ indentWith markerLength *> anyLineNewline
-- 
cgit v1.2.3