99{-# LANGUAGE TypeApplications #-}
1010{- |
1111 Module : Text.Pandoc.Writers.Docx
12- Copyright : Copyright (C) 2012-2024 John MacFarlane
12+ Copyright : Copyright (C) 2012-2025 John MacFarlane
1313 License : GNU GPL, version 2 or above
1414
1515 Maintainer : John MacFarlane <[email protected] > @@ -20,7 +20,7 @@ Conversion of 'Pandoc' documents to docx.
2020-}
2121module Text.Pandoc.Writers.Docx.OpenXML ( writeOpenXML , maxListLevel ) where
2222
23- import Control.Monad (when , unless )
23+ import Control.Monad ((>=>) , when , unless )
2424import Control.Applicative ((<|>) )
2525import Control.Monad.Except (catchError )
2626import Crypto.Hash (hashWith , SHA1 (SHA1 ))
@@ -220,6 +220,15 @@ makeLOT opts = do
220220 ]) -- w:sdtContent
221221 ]] -- w:sdt
222222
223+ -- | Separator element between sections
224+ sectionSeparator :: PandocMonad m => WS m (Maybe Content )
225+ sectionSeparator = do
226+ asks envSectPr >>= \ case
227+ Just sectPrElem -> pure $
228+ Just $ Elem (mknode " w:p" [] (mknode " w:pPr" [] [sectPrElem]))
229+ Nothing -> pure
230+ Nothing
231+
223232-- | Convert Pandoc document to rendered document contents plus two lists of
224233-- OpenXML elements (footnotes and comments).
225234writeOpenXML :: PandocMonad m
@@ -317,7 +326,17 @@ writeOpenXML opts (Pandoc meta blocks) = do
317326
318327-- | Convert a list of Pandoc blocks to OpenXML.
319328blocksToOpenXML :: (PandocMonad m ) => WriterOptions -> [Block ] -> WS m [Content ]
320- blocksToOpenXML opts = fmap concat . mapM (blockToOpenXML opts) . separateTables . filter (not . isForeignRawBlock)
329+ blocksToOpenXML opts =
330+ fmap concat . mapM (blockToOpenXML opts)
331+ . separateTables . filter (not . isForeignRawBlock)
332+ >=>
333+ \ case
334+ a@ (x: xs) -> do
335+ sep <- sectionSeparator
336+ if Just x == sep
337+ then pure xs
338+ else pure a
339+ [] -> pure []
321340
322341isForeignRawBlock :: Block -> Bool
323342isForeignRawBlock (RawBlock format _) = format /= " openxml"
@@ -395,13 +414,9 @@ blockToOpenXML' opts (Header lev (ident,_,kvs) lst) = do
395414 Nothing -> return []
396415 else return []
397416 contents <- (number ++ ) <$> inlinesToOpenXML opts lst
398- sectpr <- asks envSectPr
399- let addSectionBreak
400- | isSection
401- , Just sectPrElem <- sectpr
402- = (Elem (mknode " w:p" []
403- (mknode " w:pPr" [] [sectPrElem])) : )
404- | otherwise = id
417+ addSectionBreak <- sectionSeparator >>= \ case
418+ Just sep | isSection -> pure (sep: )
419+ _ -> pure id
405420 addSectionBreak <$>
406421 if T. null ident
407422 then return [Elem $ mknode " w:p" [] (map Elem paraProps ++ contents)]
0 commit comments