parent
75e2a1104c
commit
cd85c73ded
3 changed files with 54 additions and 45 deletions
|
@ -75,21 +75,25 @@ latexEnvStart = try $
|
||||||
latexEnvName :: Monad m => OrgParser m String
|
latexEnvName :: Monad m => OrgParser m String
|
||||||
latexEnvName = try $ mappend <$> many1 alphaNum <*> option "" (string "*")
|
latexEnvName = try $ mappend <$> many1 alphaNum <*> option "" (string "*")
|
||||||
|
|
||||||
|
bulletListStart :: Monad m => OrgParser m Int
|
||||||
-- | Parses bullet list marker.
|
bulletListStart = try $ do
|
||||||
bulletListStart :: Monad m => OrgParser m ()
|
ind <- length <$> many spaceChar
|
||||||
bulletListStart = try $
|
-- Unindented lists cannot use '*' bullets.
|
||||||
choice
|
oneOf (if ind == 0 then "+-" else "*+-")
|
||||||
[ () <$ skipSpaces <* oneOf "+-" <* skipSpaces1
|
skipSpaces1 <|> lookAhead eol
|
||||||
, () <$ skipSpaces1 <* char '*' <* skipSpaces1
|
return (ind + 1)
|
||||||
]
|
|
||||||
|
|
||||||
genericListStart :: Monad m
|
genericListStart :: Monad m
|
||||||
=> OrgParser m String
|
=> OrgParser m String
|
||||||
-> OrgParser m Int
|
-> OrgParser m Int
|
||||||
genericListStart listMarker = try $
|
genericListStart listMarker = try $ do
|
||||||
(+) <$> (length <$> many spaceChar)
|
ind <- length <$> many spaceChar
|
||||||
<*> (length <$> listMarker <* many1 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 :: Monad m => OrgParser m Int
|
||||||
orderedListStart = genericListStart orderedListMarker
|
orderedListStart = genericListStart orderedListMarker
|
||||||
|
|
|
@ -744,7 +744,7 @@ paraOrPlain = try $ do
|
||||||
-- is directly followed by a list item, in which case the block is read as
|
-- is directly followed by a list item, in which case the block is read as
|
||||||
-- plain text.
|
-- plain text.
|
||||||
try (guard nl
|
try (guard nl
|
||||||
*> notFollowedBy (inList *> (() <$ orderedListStart <|> bulletListStart))
|
*> notFollowedBy (inList *> (orderedListStart <|> bulletListStart))
|
||||||
*> return (B.para <$> ils))
|
*> return (B.para <$> ils))
|
||||||
<|> return (B.plain <$> ils)
|
<|> return (B.plain <$> ils)
|
||||||
|
|
||||||
|
@ -757,40 +757,34 @@ list :: PandocMonad m => OrgParser m (F Blocks)
|
||||||
list = choice [ definitionList, bulletList, orderedList ] <?> "list"
|
list = choice [ definitionList, bulletList, orderedList ] <?> "list"
|
||||||
|
|
||||||
definitionList :: PandocMonad m => OrgParser m (F Blocks)
|
definitionList :: PandocMonad m => OrgParser m (F Blocks)
|
||||||
definitionList = try $ do n <- lookAhead (bulletListStart' Nothing)
|
definitionList = try $ do
|
||||||
fmap (B.definitionList . compactifyDL) . sequence
|
indent <- lookAhead bulletListStart
|
||||||
<$> many1 (definitionListItem $ bulletListStart' (Just n))
|
fmap (B.definitionList . compactifyDL) . sequence
|
||||||
|
<$> many1 (definitionListItem (bulletListStart `indented` indent))
|
||||||
|
|
||||||
bulletList :: PandocMonad m => OrgParser m (F Blocks)
|
bulletList :: PandocMonad m => OrgParser m (F Blocks)
|
||||||
bulletList = try $ do n <- lookAhead (bulletListStart' Nothing)
|
bulletList = try $ do
|
||||||
fmap (B.bulletList . compactify) . sequence
|
indent <- lookAhead bulletListStart
|
||||||
<$> many1 (listItem (bulletListStart' $ Just n))
|
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 :: PandocMonad m => OrgParser m (F Blocks)
|
||||||
orderedList = fmap (B.orderedList . compactify) . sequence
|
orderedList = try $ do
|
||||||
<$> many1 (listItem orderedListStart)
|
indent <- lookAhead orderedListStart
|
||||||
|
fmap (B.orderedList . compactify) . sequence
|
||||||
bulletListStart' :: Monad m => Maybe Int -> OrgParser m Int
|
<$> many1 (listItem (orderedListStart `indented` indent))
|
||||||
-- 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 "*+-"
|
|
||||||
|
|
||||||
definitionListItem :: PandocMonad m
|
definitionListItem :: PandocMonad m
|
||||||
=> OrgParser m Int
|
=> OrgParser m Int
|
||||||
-> OrgParser m (F (Inlines, [Blocks]))
|
-> OrgParser m (F (Inlines, [Blocks]))
|
||||||
definitionListItem parseMarkerGetLength = try $ do
|
definitionListItem parseIndentedMarker = try $ do
|
||||||
markerLength <- parseMarkerGetLength
|
markerLength <- parseIndentedMarker
|
||||||
term <- manyTill (noneOf "\n\r") (try definitionMarker)
|
term <- manyTill (noneOf "\n\r") (try definitionMarker)
|
||||||
line1 <- anyLineNewline
|
line1 <- anyLineNewline
|
||||||
blank <- option "" ("\n" <$ blankline)
|
blank <- option "" ("\n" <$ blankline)
|
||||||
|
@ -802,13 +796,12 @@ definitionListItem parseMarkerGetLength = try $ do
|
||||||
definitionMarker =
|
definitionMarker =
|
||||||
spaceChar *> string "::" <* (spaceChar <|> lookAhead newline)
|
spaceChar *> string "::" <* (spaceChar <|> lookAhead newline)
|
||||||
|
|
||||||
|
-- | parse raw text for one list item
|
||||||
-- parse raw text for one list item, excluding start marker and continuations
|
|
||||||
listItem :: PandocMonad m
|
listItem :: PandocMonad m
|
||||||
=> OrgParser m Int
|
=> OrgParser m Int
|
||||||
-> OrgParser m (F Blocks)
|
-> OrgParser m (F Blocks)
|
||||||
listItem start = try . withContext ListItemState $ do
|
listItem parseIndentedMarker = try . withContext ListItemState $ do
|
||||||
markerLength <- try start
|
markerLength <- try parseIndentedMarker
|
||||||
firstLine <- anyLineNewline
|
firstLine <- anyLineNewline
|
||||||
blank <- option "" ("\n" <$ blankline)
|
blank <- option "" ("\n" <$ blankline)
|
||||||
rest <- concat <$> many (listContinuation markerLength)
|
rest <- concat <$> many (listContinuation markerLength)
|
||||||
|
@ -818,9 +811,9 @@ listItem start = try . withContext ListItemState $ do
|
||||||
-- Note: nested lists are parsed as continuations.
|
-- Note: nested lists are parsed as continuations.
|
||||||
listContinuation :: Monad m => Int
|
listContinuation :: Monad m => Int
|
||||||
-> OrgParser m String
|
-> OrgParser m String
|
||||||
listContinuation markerLength = try $
|
listContinuation markerLength = try $ do
|
||||||
notFollowedBy' blankline
|
notFollowedBy' blankline
|
||||||
*> (mappend <$> (concat <$> many1 listLine)
|
mappend <$> (concat <$> many1 listLine)
|
||||||
<*> many blankline)
|
<*> many blankline
|
||||||
where
|
where
|
||||||
listLine = try $ indentWith markerLength *> anyLineNewline
|
listLine = try $ indentWith markerLength *> anyLineNewline
|
||||||
|
|
|
@ -1262,6 +1262,12 @@ tests =
|
||||||
, headerWith ("notvalidlistitem", [], []) 1 "NotValidListItem"
|
, headerWith ("notvalidlistitem", [], []) 1 "NotValidListItem"
|
||||||
]
|
]
|
||||||
|
|
||||||
|
, "Empty bullet points" =:
|
||||||
|
T.unlines [ "-"
|
||||||
|
, "- "
|
||||||
|
] =?>
|
||||||
|
bulletList [ plain "", plain "" ]
|
||||||
|
|
||||||
, "Simple Ordered List" =:
|
, "Simple Ordered List" =:
|
||||||
("1. Item1\n" <>
|
("1. Item1\n" <>
|
||||||
"2. Item2\n") =?>
|
"2. Item2\n") =?>
|
||||||
|
@ -1289,6 +1295,12 @@ tests =
|
||||||
]
|
]
|
||||||
in orderedListWith listStyle listStructure
|
in orderedListWith listStyle listStructure
|
||||||
|
|
||||||
|
, "Empty ordered list item" =:
|
||||||
|
T.unlines [ "1."
|
||||||
|
, "3. "
|
||||||
|
] =?>
|
||||||
|
orderedList [ plain "", plain "" ]
|
||||||
|
|
||||||
, "Nested Ordered Lists" =:
|
, "Nested Ordered Lists" =:
|
||||||
("1. One\n" <>
|
("1. One\n" <>
|
||||||
" 1. One-One\n" <>
|
" 1. One-One\n" <>
|
||||||
|
|
Loading…
Add table
Reference in a new issue