diff options
Diffstat (limited to 'src/Text/Pandoc/Writers/Docx/OpenXML.hs')
| -rw-r--r-- | src/Text/Pandoc/Writers/Docx/OpenXML.hs | 35 |
1 files changed, 25 insertions, 10 deletions
diff --git a/src/Text/Pandoc/Writers/Docx/OpenXML.hs b/src/Text/Pandoc/Writers/Docx/OpenXML.hs index 0b76153f4..e061b19f1 100644 --- a/src/Text/Pandoc/Writers/Docx/OpenXML.hs +++ b/src/Text/Pandoc/Writers/Docx/OpenXML.hs @@ -9,7 +9,7 @@ {-# LANGUAGE TypeApplications #-} {- | Module : Text.Pandoc.Writers.Docx - Copyright : Copyright (C) 2012-2024 John MacFarlane + Copyright : Copyright (C) 2012-2025 John MacFarlane License : GNU GPL, version 2 or above Maintainer : John MacFarlane <[email protected]> @@ -20,7 +20,7 @@ Conversion of 'Pandoc' documents to docx. -} module Text.Pandoc.Writers.Docx.OpenXML ( writeOpenXML, maxListLevel ) where -import Control.Monad (when, unless) +import Control.Monad ((>=>), when, unless) import Control.Applicative ((<|>)) import Control.Monad.Except (catchError) import Crypto.Hash (hashWith, SHA1(SHA1)) @@ -220,6 +220,15 @@ makeLOT opts = do ]) -- w:sdtContent ]] -- w:sdt +-- | Separator element between sections +sectionSeparator :: PandocMonad m => WS m (Maybe Content) +sectionSeparator = do + asks envSectPr >>= \case + Just sectPrElem -> pure $ + Just $ Elem (mknode "w:p" [] (mknode "w:pPr" [] [sectPrElem])) + Nothing -> pure + Nothing + -- | Convert Pandoc document to rendered document contents plus two lists of -- OpenXML elements (footnotes and comments). writeOpenXML :: PandocMonad m @@ -317,7 +326,17 @@ writeOpenXML opts (Pandoc meta blocks) = do -- | Convert a list of Pandoc blocks to OpenXML. blocksToOpenXML :: (PandocMonad m) => WriterOptions -> [Block] -> WS m [Content] -blocksToOpenXML opts = fmap concat . mapM (blockToOpenXML opts) . separateTables . filter (not . isForeignRawBlock) +blocksToOpenXML opts = + fmap concat . mapM (blockToOpenXML opts) + . separateTables . filter (not . isForeignRawBlock) + >=> + \case + a@(x:xs) -> do + sep <- sectionSeparator + if Just x == sep + then pure xs + else pure a + [] -> pure [] isForeignRawBlock :: Block -> Bool isForeignRawBlock (RawBlock format _) = format /= "openxml" @@ -395,13 +414,9 @@ blockToOpenXML' opts (Header lev (ident,_,kvs) lst) = do Nothing -> return [] else return [] contents <- (number ++) <$> inlinesToOpenXML opts lst - sectpr <- asks envSectPr - let addSectionBreak - | isSection - , Just sectPrElem <- sectpr - = (Elem (mknode "w:p" [] - (mknode "w:pPr" [] [sectPrElem])) :) - | otherwise = id + addSectionBreak <- sectionSeparator >>= \case + Just sep | isSection -> pure (sep:) + _ -> pure id addSectionBreak <$> if T.null ident then return [Elem $ mknode "w:p" [] (map Elem paraProps ++ contents)] |
