AsciiDoc writer: improve ordered lists.
Use `.`+ as list markers to support nested ordered lists. Closes #5087. Support list number styles. Closes #5089.
This commit is contained in:
parent
c0d8b0abcb
commit
a5910c0a31
2 changed files with 83 additions and 71 deletions
|
@ -40,7 +40,7 @@ AsciiDoc: <http://www.methods.co.nz/asciidoc/>
|
||||||
module Text.Pandoc.Writers.AsciiDoc (writeAsciiDoc) where
|
module Text.Pandoc.Writers.AsciiDoc (writeAsciiDoc) where
|
||||||
import Prelude
|
import Prelude
|
||||||
import Control.Monad.State.Strict
|
import Control.Monad.State.Strict
|
||||||
import Data.Char (isPunctuation, isSpace)
|
import Data.Char (isPunctuation, isSpace, toLower)
|
||||||
import Data.List (intercalate, intersperse, stripPrefix)
|
import Data.List (intercalate, intersperse, stripPrefix)
|
||||||
import Data.Maybe (fromMaybe, isJust, listToMaybe)
|
import Data.Maybe (fromMaybe, isJust, listToMaybe)
|
||||||
import qualified Data.Set as Set
|
import qualified Data.Set as Set
|
||||||
|
@ -258,17 +258,18 @@ blockToAsciiDoc opts (Table caption aligns widths headers rows) = do
|
||||||
blockToAsciiDoc opts (BulletList items) = do
|
blockToAsciiDoc opts (BulletList items) = do
|
||||||
contents <- mapM (bulletListItemToAsciiDoc opts) items
|
contents <- mapM (bulletListItemToAsciiDoc opts) items
|
||||||
return $ cat contents <> blankline
|
return $ cat contents <> blankline
|
||||||
blockToAsciiDoc opts (OrderedList (_start, sty, _delim) items) = do
|
blockToAsciiDoc opts (OrderedList (start, sty, _delim) items) = do
|
||||||
let sty' = case sty of
|
let listStyle = case sty of
|
||||||
UpperRoman -> UpperAlpha
|
DefaultStyle -> []
|
||||||
LowerRoman -> LowerAlpha
|
Decimal -> ["arabic"]
|
||||||
x -> x
|
Example -> []
|
||||||
let markers = orderedListMarkers (1, sty', Period) -- start num not used
|
_ -> [map toLower (show sty)]
|
||||||
let markers' = map (\m -> if length m < 3
|
let listStart = if start == 1 then [] else ["start=" ++ show start]
|
||||||
then m ++ replicate (3 - length m) ' '
|
let listoptions = case intercalate ", " (listStyle ++ listStart) of
|
||||||
else m) markers
|
[] -> empty
|
||||||
contents <- zipWithM (orderedListItemToAsciiDoc opts) markers' items
|
x -> brackets (text x)
|
||||||
return $ cat contents <> blankline
|
contents <- mapM (orderedListItemToAsciiDoc opts) items
|
||||||
|
return $ listoptions $$ cat contents <> blankline
|
||||||
blockToAsciiDoc opts (DefinitionList items) = do
|
blockToAsciiDoc opts (DefinitionList items) = do
|
||||||
contents <- mapM (definitionListItemToAsciiDoc opts) items
|
contents <- mapM (definitionListItemToAsciiDoc opts) items
|
||||||
return $ cat contents <> blankline
|
return $ cat contents <> blankline
|
||||||
|
@ -281,40 +282,34 @@ blockToAsciiDoc opts (Div (ident,_,_) bs) = do
|
||||||
bulletListItemToAsciiDoc :: PandocMonad m
|
bulletListItemToAsciiDoc :: PandocMonad m
|
||||||
=> WriterOptions -> [Block] -> ADW m Doc
|
=> WriterOptions -> [Block] -> ADW m Doc
|
||||||
bulletListItemToAsciiDoc opts blocks = do
|
bulletListItemToAsciiDoc opts blocks = do
|
||||||
let addBlock :: PandocMonad m => Doc -> Block -> ADW m Doc
|
|
||||||
addBlock d b | isEmpty d = chomp `fmap` blockToAsciiDoc opts b
|
|
||||||
addBlock d b@(BulletList _) = do x <- blockToAsciiDoc opts b
|
|
||||||
return $ d <> cr <> chomp x
|
|
||||||
addBlock d b@(OrderedList _ _) = do x <- blockToAsciiDoc opts b
|
|
||||||
return $ d <> cr <> chomp x
|
|
||||||
addBlock d b = do x <- blockToAsciiDoc opts b
|
|
||||||
return $ d <> cr <> text "+" <> cr <> chomp x
|
|
||||||
lev <- gets bulletListLevel
|
lev <- gets bulletListLevel
|
||||||
modify $ \s -> s{ bulletListLevel = lev + 1 }
|
modify $ \s -> s{ bulletListLevel = lev + 1 }
|
||||||
contents <- foldM addBlock empty blocks
|
contents <- foldM (addBlock opts) empty blocks
|
||||||
modify $ \s -> s{ bulletListLevel = lev }
|
modify $ \s -> s{ bulletListLevel = lev }
|
||||||
let marker = text (replicate lev '*')
|
let marker = text (replicate lev '*')
|
||||||
return $ marker <> text " " <> contents <> cr
|
return $ marker <> text " " <> contents <> cr
|
||||||
|
|
||||||
|
addBlock :: PandocMonad m => WriterOptions -> Doc -> Block -> ADW m Doc
|
||||||
|
addBlock opts d b | isEmpty d = chomp `fmap` blockToAsciiDoc opts b
|
||||||
|
addBlock opts d b@(BulletList _) = do x <- blockToAsciiDoc opts b
|
||||||
|
return $ d <> cr <> chomp x
|
||||||
|
addBlock opts d b@(OrderedList _ _) = do x <- blockToAsciiDoc opts b
|
||||||
|
return $ d <> cr <> chomp x
|
||||||
|
addBlock opts d b = do x <- blockToAsciiDoc opts b
|
||||||
|
return $ d <> cr <> text "+" <> cr <> chomp x
|
||||||
|
|
||||||
-- | Convert ordered list item (a list of blocks) to asciidoc.
|
-- | Convert ordered list item (a list of blocks) to asciidoc.
|
||||||
orderedListItemToAsciiDoc :: PandocMonad m
|
orderedListItemToAsciiDoc :: PandocMonad m
|
||||||
=> WriterOptions -- ^ options
|
=> WriterOptions -- ^ options
|
||||||
-> String -- ^ list item marker
|
|
||||||
-> [Block] -- ^ list item (list of blocks)
|
-> [Block] -- ^ list item (list of blocks)
|
||||||
-> ADW m Doc
|
-> ADW m Doc
|
||||||
orderedListItemToAsciiDoc opts marker blocks = do
|
orderedListItemToAsciiDoc opts blocks = do
|
||||||
let addBlock d b | isEmpty d = chomp `fmap` blockToAsciiDoc opts b
|
|
||||||
addBlock d b@(BulletList _) = do x <- blockToAsciiDoc opts b
|
|
||||||
return $ d <> cr <> chomp x
|
|
||||||
addBlock d b@(OrderedList _ _) = do x <- blockToAsciiDoc opts b
|
|
||||||
return $ d <> cr <> chomp x
|
|
||||||
addBlock d b = do x <- blockToAsciiDoc opts b
|
|
||||||
return $ d <> cr <> text "+" <> cr <> chomp x
|
|
||||||
lev <- gets orderedListLevel
|
lev <- gets orderedListLevel
|
||||||
modify $ \s -> s{ orderedListLevel = lev + 1 }
|
modify $ \s -> s{ orderedListLevel = lev + 1 }
|
||||||
contents <- foldM addBlock empty blocks
|
contents <- foldM (addBlock opts) empty blocks
|
||||||
modify $ \s -> s{ orderedListLevel = lev }
|
modify $ \s -> s{ orderedListLevel = lev }
|
||||||
return $ text marker <> text " " <> contents <> cr
|
let marker = text (replicate lev '.')
|
||||||
|
return $ marker <> text " " <> contents <> cr
|
||||||
|
|
||||||
-- | Convert definition list item (label, list of blocks) to asciidoc.
|
-- | Convert definition list item (label, list of blocks) to asciidoc.
|
||||||
definitionListItemToAsciiDoc :: PandocMonad m
|
definitionListItemToAsciiDoc :: PandocMonad m
|
||||||
|
|
|
@ -66,8 +66,9 @@ sub status {
|
||||||
|
|
||||||
A list:
|
A list:
|
||||||
|
|
||||||
1. item one
|
[arabic]
|
||||||
2. item two
|
. item one
|
||||||
|
. item two
|
||||||
|
|
||||||
Nested block quotes:
|
Nested block quotes:
|
||||||
|
|
||||||
|
@ -156,35 +157,40 @@ Minuses loose:
|
||||||
|
|
||||||
Tight:
|
Tight:
|
||||||
|
|
||||||
1. First
|
[arabic]
|
||||||
2. Second
|
. First
|
||||||
3. Third
|
. Second
|
||||||
|
. Third
|
||||||
|
|
||||||
and:
|
and:
|
||||||
|
|
||||||
1. One
|
[arabic]
|
||||||
2. Two
|
. One
|
||||||
3. Three
|
. Two
|
||||||
|
. Three
|
||||||
|
|
||||||
Loose using tabs:
|
Loose using tabs:
|
||||||
|
|
||||||
1. First
|
[arabic]
|
||||||
2. Second
|
. First
|
||||||
3. Third
|
. Second
|
||||||
|
. Third
|
||||||
|
|
||||||
and using spaces:
|
and using spaces:
|
||||||
|
|
||||||
1. One
|
[arabic]
|
||||||
2. Two
|
. One
|
||||||
3. Three
|
. Two
|
||||||
|
. Three
|
||||||
|
|
||||||
Multiple paragraphs:
|
Multiple paragraphs:
|
||||||
|
|
||||||
1. Item 1, graf one.
|
[arabic]
|
||||||
|
. Item 1, graf one.
|
||||||
+
|
+
|
||||||
Item 1. graf two. The quick brown fox jumped over the lazy dog’s back.
|
Item 1. graf two. The quick brown fox jumped over the lazy dog’s back.
|
||||||
2. Item 2.
|
. Item 2.
|
||||||
3. Item 3.
|
. Item 3.
|
||||||
|
|
||||||
=== Nested
|
=== Nested
|
||||||
|
|
||||||
|
@ -194,21 +200,23 @@ Item 1. graf two. The quick brown fox jumped over the lazy dog’s back.
|
||||||
|
|
||||||
Here’s another:
|
Here’s another:
|
||||||
|
|
||||||
1. First
|
[arabic]
|
||||||
2. Second:
|
. First
|
||||||
|
. Second:
|
||||||
* Fee
|
* Fee
|
||||||
* Fie
|
* Fie
|
||||||
* Foe
|
* Foe
|
||||||
3. Third
|
. Third
|
||||||
|
|
||||||
Same thing but with paragraphs:
|
Same thing but with paragraphs:
|
||||||
|
|
||||||
1. First
|
[arabic]
|
||||||
2. Second:
|
. First
|
||||||
|
. Second:
|
||||||
* Fee
|
* Fee
|
||||||
* Fie
|
* Fie
|
||||||
* Foe
|
* Foe
|
||||||
3. Third
|
. Third
|
||||||
|
|
||||||
=== Tabs and spaces
|
=== Tabs and spaces
|
||||||
|
|
||||||
|
@ -219,27 +227,34 @@ Same thing but with paragraphs:
|
||||||
|
|
||||||
=== Fancy list markers
|
=== Fancy list markers
|
||||||
|
|
||||||
1. begins with 2
|
[arabic, start=2]
|
||||||
2. and now 3
|
. begins with 2
|
||||||
|
. and now 3
|
||||||
+
|
+
|
||||||
with a continuation
|
with a continuation
|
||||||
a. sublist with roman numerals, starting with 4
|
[lowerroman, start=4]
|
||||||
b. more items
|
.. sublist with roman numerals, starting with 4
|
||||||
A. a subsublist
|
.. more items
|
||||||
B. a subsublist
|
[upperalpha]
|
||||||
|
... a subsublist
|
||||||
|
... a subsublist
|
||||||
|
|
||||||
Nesting:
|
Nesting:
|
||||||
|
|
||||||
A. Upper Alpha
|
[upperalpha]
|
||||||
A. Upper Roman.
|
. Upper Alpha
|
||||||
1. Decimal start with 6
|
[upperroman]
|
||||||
a. Lower alpha with paren
|
.. Upper Roman.
|
||||||
|
[arabic, start=6]
|
||||||
|
... Decimal start with 6
|
||||||
|
[loweralpha, start=3]
|
||||||
|
.... Lower alpha with paren
|
||||||
|
|
||||||
Autonumbering:
|
Autonumbering:
|
||||||
|
|
||||||
1. Autonumber.
|
. Autonumber.
|
||||||
2. More.
|
. More.
|
||||||
1. Nested.
|
.. Nested.
|
||||||
|
|
||||||
Should not be a list item:
|
Should not be a list item:
|
||||||
|
|
||||||
|
@ -326,8 +341,9 @@ apple::
|
||||||
orange::
|
orange::
|
||||||
orange fruit
|
orange fruit
|
||||||
+
|
+
|
||||||
1. sublist
|
[arabic]
|
||||||
2. sublist
|
. sublist
|
||||||
|
. sublist
|
||||||
|
|
||||||
== HTML Blocks
|
== HTML Blocks
|
||||||
|
|
||||||
|
@ -622,6 +638,7 @@ ___________________________________________
|
||||||
Notes can go in quotes.footnote:[In quote.]
|
Notes can go in quotes.footnote:[In quote.]
|
||||||
___________________________________________
|
___________________________________________
|
||||||
|
|
||||||
1. And in list items.footnote:[In list.]
|
[arabic]
|
||||||
|
. And in list items.footnote:[In list.]
|
||||||
|
|
||||||
This paragraph should not be part of the note, as it is not indented.
|
This paragraph should not be part of the note, as it is not indented.
|
||||||
|
|
Loading…
Reference in a new issue