Org reader: support counter cookies in lists

This adds support for counter cookies in org lists. Such cookies are
used to override the item counter in ordered lists. In org it is
possible to set the counter at any list item, but since Pandoc AST does
not support this, we restrict the usage to setting an offset for the
entire ordered list, by using the cookie in the first list item.

Note that even though unordered lists do not have counters, Org Mode
still parses such cookies in unordered lists and suppresses them in the
output, so we do the same.

Also, even though org-list-allow-alphabetical is disabled in Emacs by
default, for some reason alphabetical cookies are always parsed and used
in Org Mode regardlessly of whether this option is enabled or the list
style is decimal, so we do the same.

E.g.
 2. test
 3. test
Is parsed as an ordered list starting at 1, as before. This also
conforms to Org Mode behaviour.

 1. [@2] test
 2. test
Is now parsed as an ordered list starting at 2, so that it conforms to
Org Mode behaviour.

Note that when parsing
 1. [@2] test
 2. [@9] test
the second cookie is silenced and the entire list starts at 2. This is
because the current Pandoc AST does not support expressing a change in
the counter at a specific item.
This commit is contained in:
Lucas Viana 2022-01-05 19:02:47 -03:00 committed by Albert Krewinkel
parent ea74582288
commit 4be41e3bb5
3 changed files with 83 additions and 17 deletions

View file

@ -25,8 +25,10 @@ module Text.Pandoc.Readers.Org.BlockStarts
import Control.Monad (void)
import Data.Text (Text)
import qualified Data.Text as T
import Text.Pandoc.Readers.Org.Parsing
import Text.Pandoc.Definition as Pandoc
import Text.Pandoc.Shared (safeRead)
import Data.Char (toLower)
-- | Horizontal Line (five -- dashes or more)
hline :: Monad m => OrgParser m ()
@ -60,30 +62,38 @@ latexEnvStart = try $
latexEnvName :: Monad m => OrgParser m Text
latexEnvName = try $ mappend <$> many1Char alphaNum <*> option "" (textStr "*")
listCounterCookie :: Monad m => OrgParser m Int
listCounterCookie = try $
string "[@"
*> ((many1Char digit >>= safeRead) <|> numFromAlph <$> oneOf asciiAlph)
<* char ']'
<* (skipSpaces <|> lookAhead eol)
where
asciiAlph = ['a'..'z'] ++ ['A'..'Z']
-- The number makes sense because char is always in asciiAlph
numFromAlph c = fromEnum (toLower c) - fromEnum 'a' + 1
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 Text
-> OrgParser m Int
genericListStart listMarker = try $ do
ind <- length <$> many spaceChar
void listMarker
skipSpaces1 <|> lookAhead eol
optionMaybe listCounterCookie
return (ind + 1)
eol :: Monad m => OrgParser m ()
eol = void (char '\n')
orderedListStart :: Monad m => OrgParser m Int
orderedListStart = genericListStart orderedListMarker
orderedListStart :: Monad m => OrgParser m (Int, ListAttributes)
orderedListStart = try $ do
ind <- length <$> many spaceChar
orderedListMarker
skipSpaces1 <|> lookAhead eol
start <- option 1 listCounterCookie
return (ind + 1, (start, DefaultStyle, DefaultDelim))
-- Ordered list markers allowed in org-mode
where orderedListMarker = T.snoc <$> many1Char digit <*> oneOf ".)"
where orderedListMarker = many1Char digit *> oneOf ".)"
drawerStart :: Monad m => OrgParser m Text
drawerStart = try $ skipSpaces *> drawerName <* skipSpaces <* newline

View file

@ -802,7 +802,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 *> (void orderedListStart <|> void bulletListStart))
$> (B.para <$> ils))
<|> return (B.plain <$> ils)
@ -834,9 +834,9 @@ indented indentedMarker minIndent = try $ do
orderedList :: PandocMonad m => OrgParser m (F Blocks)
orderedList = try $ do
indent <- lookAhead orderedListStart
fmap (B.orderedList . compactify) . sequence
<$> many1 (listItem (orderedListStart `indented` indent))
(indent, attr) <- lookAhead orderedListStart
fmap (B.orderedListWith attr . compactify) . sequence
<$> many1 (listItem ((fst <$> orderedListStart) `indented` indent))
definitionListItem :: PandocMonad m
=> OrgParser m Int

View file

@ -27,6 +27,13 @@ tests =
, plain "Item2"
]
, "Simple Bullet List with Ignored Counter Cookie" =:
("- [@4] Item1\n" <>
"- Item2\n") =?>
bulletList [ plain "Item1"
, plain "Item2"
]
, "Indented Bullet Lists" =:
(" - Item1\n" <>
" - Item2\n") =?>
@ -131,6 +138,21 @@ tests =
]
]
, "Task List with Counter Cookies" =:
T.unlines [ "- [ ] nope"
, "- [@9] [X] yup"
, "- [@a][-] started"
, " 1. [@3][X] sure"
, " 2. [@b] [ ] nuh-uh"
] =?>
bulletList [ plain "☐ nope", plain "☒ yup"
, mconcat [ plain "☐ started"
, orderedListWith
(3, DefaultStyle, DefaultDelim)
[plain "☒ sure", plain "☐ nuh-uh"]
]
]
, "Simple Ordered List" =:
("1. Item1\n" <>
"2. Item2\n") =?>
@ -140,6 +162,33 @@ tests =
]
in orderedListWith listStyle listStructure
, "Simple Ordered List with Counter Cookie" =:
("1. [@1234] Item1\n" <>
"2. Item2\n") =?>
let listStyle = (1234, DefaultStyle, DefaultDelim)
listStructure = [ plain "Item1"
, plain "Item2"
]
in orderedListWith listStyle listStructure
, "Simple Ordered List with Alphabetical Counter Cookie" =:
("1. [@c] Item1\n" <>
"2. Item2\n") =?>
let listStyle = (3, DefaultStyle, DefaultDelim)
listStructure = [ plain "Item1"
, plain "Item2"
]
in orderedListWith listStyle listStructure
, "Simple Ordered List with Ignored Counter Cookie" =:
("1. Item1\n" <>
"2. [@4] Item2\n") =?>
let listStyle = (1, DefaultStyle, DefaultDelim)
listStructure = [ plain "Item1"
, plain "Item2"
]
in orderedListWith listStyle listStructure
, "Simple Ordered List with Parens" =:
("1) Item1\n" <>
"2) Item2\n") =?>
@ -164,6 +213,13 @@ tests =
] =?>
orderedList [ plain "", plain "" ]
, "Empty ordered list item with counter cookie" =:
T.unlines [ "1. [@5]"
, "3. [@e] "
] =?>
let listStyle = (5, DefaultStyle, DefaultDelim)
in orderedListWith listStyle [ plain "", plain "" ]
, "Nested Ordered Lists" =:
("1. One\n" <>
" 1. One-One\n" <>