aboutsummaryrefslogtreecommitdiff
path: root/src/Text/Pandoc
diff options
context:
space:
mode:
Diffstat (limited to 'src/Text/Pandoc')
-rw-r--r--src/Text/Pandoc/Writers/Docx.hs16
1 files changed, 13 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