aboutsummaryrefslogtreecommitdiff
diff options
context:
space:
mode:
authorMichael Hoffmann <brennan.brisad@gmail.com>2020-10-02 18:30:05 +0200
committerGitHub <noreply@github.com>2020-10-02 09:30:05 -0700
commit74bd5a4f4758d06be43bc807f6f9b82a20970a0b (patch)
treee9acbfe9f104079b90c2787d2a157419312bb120
parent27b4c21f727ca02228a1fae8f3cdbba74641ede8 (diff)
downloadpandoc-74bd5a4f4758d06be43bc807f6f9b82a20970a0b.tar.gz
Docx writer: better handle list items whose contents are lists (#6522)
If the first element of a bulleted or ordered list is another list, then that first item will disappear if the target format is docx. This changes the docx writer so that it prepends an empty string for those cases. With this, no items will disappear. Closes #5948.
-rw-r--r--src/Text/Pandoc/Writers/Docx.hs16
-rw-r--r--test/Tests/Writers/Docx.hs5
-rw-r--r--test/docx/golden/lists_multiple_initial.docxbin0 -> 10208 bytes
-rw-r--r--test/docx/lists_multiple_initial.native8
4 files changed, 26 insertions, 3 deletions
diff --git a/src/Text/Pandoc/Writers/Docx.hs b/src/Text/Pandoc/Writers/Docx.hs
index 89a50125b..a7720eb53 100644
--- a/src/Text/Pandoc/Writers/Docx.hs
+++ b/src/Text/Pandoc/Writers/Docx.hs
@@ -3,6 +3,7 @@
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE ViewPatterns #-}
{-# LANGUAGE FlexibleContexts #-}
+{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE OverloadedStrings #-}
{- |
Module : Text.Pandoc.Writers.Docx
@@ -1087,11 +1088,20 @@ listItemToOpenXML _ _ [] = return []
listItemToOpenXML opts numid (first:rest) = do
oldInList <- gets stInList
modify $ \st -> st{ stInList = True }
- first' <- withNumId numid $ blockToOpenXML opts first
+ let isListBlock = \case
+ BulletList{} -> True
+ OrderedList{} -> True
+ _ -> False
+ -- Prepend an empty string if the first entry is another
+ -- list. Otherwise the outer bullet will disappear.
+ let (first', rest') = if isListBlock first
+ then (Plain [Str ""] , first:rest)
+ else (first, rest)
+ first'' <- withNumId numid $ blockToOpenXML opts first'
-- baseListId is the code for no list marker:
- rest' <- withNumId baseListId $ blocksToOpenXML opts rest
+ rest'' <- withNumId baseListId $ blocksToOpenXML opts rest'
modify $ \st -> st{ stInList = oldInList }
- return $ first' ++ rest'
+ return $ first'' ++ rest''
alignmentToString :: Alignment -> [Char]
alignmentToString alignment = case alignment of
diff --git a/test/Tests/Writers/Docx.hs b/test/Tests/Writers/Docx.hs
index 9e1414c40..ccd31642a 100644
--- a/test/Tests/Writers/Docx.hs
+++ b/test/Tests/Writers/Docx.hs
@@ -84,6 +84,11 @@ tests = [ testGroup "inlines"
"docx/lists_restarting.native"
"docx/golden/lists_restarting.docx"
, docxTest
+ "lists with multiple initial list levels"
+ def
+ "docx/lists_multiple_initial.native"
+ "docx/golden/lists_multiple_initial.docx"
+ , docxTest
"definition lists"
def
"docx/definition_list.native"
diff --git a/test/docx/golden/lists_multiple_initial.docx b/test/docx/golden/lists_multiple_initial.docx
new file mode 100644
index 000000000..3e632517f
--- /dev/null
+++ b/test/docx/golden/lists_multiple_initial.docx
Binary files differ
diff --git a/test/docx/lists_multiple_initial.native b/test/docx/lists_multiple_initial.native
new file mode 100644
index 000000000..91efdfd17
--- /dev/null
+++ b/test/docx/lists_multiple_initial.native
@@ -0,0 +1,8 @@
+[OrderedList (1,Decimal,Period)
+ [[OrderedList (1,LowerAlpha,TwoParens)
+ [[Para [Str "foo"]]
+ ,[Para [Str "bar"]]]]]
+,BulletList
+ [[BulletList
+ [[Para [Str "foo"]]
+ ,[Para [Str "bar"]]]]]]