Skip to content

Commit 6672b70

Browse files
committed
refactor: restructure paragraph attribute handling across all writers
- Replace monolithic test file with format-specific test suite (32 new test files) - Standardize paragraph attribute processing in 31 writer modules - Add paragraph_attributes extension to control attribute preservation behavior - Update shared writer utilities for consistent attribute handling - Modify HTML tests to reflect new attribute processing logic Fixes #10768
1 parent 9e65e19 commit 6672b70

Some content is hidden

Large Commits have some content hidden by default. Use the searchbox below for content that may be hidden.

67 files changed

+3505
-350
lines changed

src/Text/Pandoc/Extensions.hs

Lines changed: 2 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -109,6 +109,7 @@ data Extension =
109109
| Ext_ntb -- ^ ConTeXt Natural Tables
110110
| Ext_old_dashes -- ^ -- = em, - before number = en
111111
| Ext_pandoc_title_block -- ^ Pandoc title block
112+
| Ext_paragraph_attributes -- ^ Allow paragraph attributes in HTML
112113
| Ext_pipe_tables -- ^ Pipe tables (as in PHP markdown extra)
113114
| Ext_raw_attribute -- ^ Allow explicit raw blocks/inlines
114115
| Ext_raw_html -- ^ Allow raw HTML
@@ -598,6 +599,7 @@ getAllExtensions f = universalExtensions <> getAll f
598599
, Ext_literate_haskell
599600
, Ext_epub_html_exts
600601
, Ext_smart
602+
, Ext_paragraph_attributes
601603
]
602604
getAll "html4" = getAll "html"
603605
getAll "html5" = getAll "html"

src/Text/Pandoc/Writers/AsciiDoc.hs

Lines changed: 32 additions & 28 deletions
Original file line numberDiff line numberDiff line change
@@ -377,34 +377,38 @@ blockToAsciiDoc opts (DefinitionList items) = do
377377
return $ mconcat contents <> blankline
378378

379379
-- convert admonition and sidebar divs to asicidoc
380-
blockToAsciiDoc opts (Div (ident,classes,_) bs) = do
381-
let identifier = if T.null ident then empty else "[[" <> literal ident <> "]]"
382-
let admonition_classes = ["attention","caution","danger","error","hint",
383-
"important","note","tip","warning"]
384-
let sidebar_class = "sidebar"
385-
386-
contents <-
387-
case classes of
388-
(l:_) | l `elem` admonition_classes || T.toLower l == sidebar_class -> do
389-
let (titleBs, bodyBs) =
390-
case bs of
391-
(Div (_,["title"],_) ts : rest) -> (ts, rest)
392-
_ -> ([], bs)
393-
let fence = if l == "sidebar" then "****" else "===="
394-
elemTitle <- if null titleBs ||
395-
-- If title matches class, omit
396-
(T.toLower (T.strip (stringify titleBs))) == l
397-
then return mempty
398-
else ("." <>) <$>
399-
blockListToAsciiDoc opts titleBs
400-
elemBody <- blockListToAsciiDoc opts bodyBs
401-
return $ "[" <> literal (T.toUpper l) <> "]" $$
402-
chomp elemTitle $$
403-
fence $$
404-
chomp elemBody $$
405-
fence
406-
_ -> blockListToAsciiDoc opts bs
407-
return $ identifier $$ contents $$ blankline
380+
blockToAsciiDoc opts divBlock@(Div (ident,classes,_) bs) = do
381+
-- First try to unwrap wrapper divs
382+
case unwrapWrapperDiv divBlock of
383+
Para inlines -> blockToAsciiDoc opts (Para inlines)
384+
_ -> do
385+
let identifier = if T.null ident then empty else "[[" <> literal ident <> "]]"
386+
let admonition_classes = ["attention","caution","danger","error","hint",
387+
"important","note","tip","warning"]
388+
let sidebar_class = "sidebar"
389+
390+
contents <-
391+
case classes of
392+
(l:_) | l `elem` admonition_classes || T.toLower l == sidebar_class -> do
393+
let (titleBs, bodyBs) =
394+
case bs of
395+
(Div (_,["title"],_) ts : rest) -> (ts, rest)
396+
_ -> ([], bs)
397+
let fence = if l == "sidebar" then "****" else "===="
398+
elemTitle <- if null titleBs ||
399+
-- If title matches class, omit
400+
(T.toLower (T.strip (stringify titleBs))) == l
401+
then return mempty
402+
else ("." <>) <$>
403+
blockListToAsciiDoc opts titleBs
404+
elemBody <- blockListToAsciiDoc opts bodyBs
405+
return $ "[" <> literal (T.toUpper l) <> "]" $$
406+
chomp elemTitle $$
407+
fence $$
408+
chomp elemBody $$
409+
fence
410+
_ -> blockListToAsciiDoc opts bs
411+
return $ identifier $$ contents $$ blankline
408412

409413
-- | Convert bullet list item (list of blocks) to asciidoc.
410414
bulletListItemToAsciiDoc :: PandocMonad m

src/Text/Pandoc/Writers/ConTeXt.hs

Lines changed: 20 additions & 17 deletions
Original file line numberDiff line numberDiff line change
@@ -38,7 +38,7 @@ import Text.Pandoc.Shared
3838
import Text.Pandoc.URI (isURI)
3939
import Text.Pandoc.Templates (renderTemplate)
4040
import Text.Pandoc.Walk (query)
41-
import Text.Pandoc.Writers.Shared
41+
import Text.Pandoc.Writers.Shared (unwrapWrapperDiv, defField, getField, resetField, lookupMetaString, metaToContext, getLang)
4242
import Text.Printf (printf)
4343

4444
import qualified Data.List.NonEmpty as NonEmpty
@@ -187,37 +187,40 @@ toLabel z = T.concatMap go z
187187

188188
-- | Convert Pandoc block element to ConTeXt.
189189
blockToConTeXt :: PandocMonad m => Block -> WM m (Doc Text)
190-
blockToConTeXt (Div attr@(_,"section":_,_)
190+
blockToConTeXt block = blockToConTeXt' (unwrapWrapperDiv block)
191+
192+
blockToConTeXt' :: PandocMonad m => Block -> WM m (Doc Text)
193+
blockToConTeXt' (Div attr@(_,"section":_,_)
191194
(Header level _ title' : xs)) = do
192195
header' <- sectionHeader attr level title' SectionHeading
193196
footer' <- sectionFooter attr level
194197
innerContents <- blockListToConTeXt xs
195198
return $ header' $$ innerContents $$ footer'
196-
blockToConTeXt (Plain lst) = do
199+
blockToConTeXt' (Plain lst) = do
197200
opts <- gets stOptions
198201
contents <- inlineListToConTeXt lst
199202
return $
200203
if isEnabled Ext_tagging opts
201204
then "\\bpar{}" <> contents <> "\\epar{}"
202205
else contents
203-
blockToConTeXt (Para lst) = do
206+
blockToConTeXt' (Para lst) = do
204207
opts <- gets stOptions
205208
contents <- inlineListToConTeXt lst
206209
return $
207210
if isEnabled Ext_tagging opts
208211
then "\\bpar" $$ contents $$ "\\epar" <> blankline
209212
else contents <> blankline
210-
blockToConTeXt (LineBlock lns) = do
213+
blockToConTeXt' (LineBlock lns) = do
211214
let emptyToBlankline doc = if isEmpty doc
212215
then blankline
213216
else doc
214217
doclines <- mapM inlineListToConTeXt lns
215218
let contextLines = vcat . map emptyToBlankline $ doclines
216219
return $ "\\startlines" $$ contextLines $$ "\\stoplines" <> blankline
217-
blockToConTeXt (BlockQuote lst) = do
220+
blockToConTeXt' (BlockQuote lst) = do
218221
contents <- blockListToConTeXt lst
219222
return $ "\\startblockquote" $$ nest 0 contents $$ "\\stopblockquote" <> blankline
220-
blockToConTeXt (CodeBlock (_ident, classes, kv) str) = do
223+
blockToConTeXt' (CodeBlock (_ident, classes, kv) str) = do
221224
opts <- gets stOptions
222225
let syntaxMap = writerSyntaxMap opts
223226
let attr' = ("", classes, kv)
@@ -236,15 +239,15 @@ blockToConTeXt (CodeBlock (_ident, classes, kv) str) = do
236239
if null classes || isNothing (writerHighlightStyle opts)
237240
then pure unhighlighted
238241
else highlighted
239-
blockToConTeXt b@(RawBlock f str)
242+
blockToConTeXt' b@(RawBlock f str)
240243
| f == Format "context" || f == Format "tex" = return $ literal str <> blankline
241244
| otherwise = empty <$ report (BlockNotRendered b)
242-
blockToConTeXt (Div ("refs",classes,_) bs) = do
245+
blockToConTeXt' (Div ("refs",classes,_) bs) = do
243246
modify $ \st -> st{ stHasCslRefs = True
244247
, stCslHangingIndent = "hanging-indent" `elem` classes }
245248
inner <- blockListToConTeXt bs
246249
return $ "\\startcslreferences" $$ inner $$ "\\stopcslreferences"
247-
blockToConTeXt (Div (ident,_,kvs) bs) = do
250+
blockToConTeXt' (Div (ident,_,kvs) bs) = do
248251
let align dir txt = "\\startalignment[" <> dir <> "]" $$ txt $$ "\\stopalignment"
249252
mblang <- fromBCP47 (lookup "lang" kvs)
250253
let wrapRef txt = if T.null ident
@@ -261,13 +264,13 @@ blockToConTeXt (Div (ident,_,kvs) bs) = do
261264
Nothing -> txt
262265
wrapBlank txt = blankline <> txt <> blankline
263266
wrapBlank . wrapLang . wrapDir . wrapRef <$> blockListToConTeXt bs
264-
blockToConTeXt (BulletList lst) = do
267+
blockToConTeXt' (BulletList lst) = do
265268
contents <- mapM listItemToConTeXt lst
266269
return $ ("\\startitemize" <> if isTightList lst
267270
then brackets "packed"
268271
else empty) $$
269272
vcat contents $$ literal "\\stopitemize" <> blankline
270-
blockToConTeXt (OrderedList (start, style', delim) lst) = do
273+
blockToConTeXt' (OrderedList (start, style', delim) lst) = do
271274
st <- get
272275
let level = stOrderedListLevel st
273276
put st {stOrderedListLevel = level + 1}
@@ -295,15 +298,15 @@ blockToConTeXt (OrderedList (start, style', delim) lst) = do
295298
let specs = T.pack style'' <> specs2
296299
return $ "\\startenumerate" <> literal specs $$ vcat contents $$
297300
"\\stopenumerate" <> blankline
298-
blockToConTeXt (DefinitionList lst) =
301+
blockToConTeXt' (DefinitionList lst) =
299302
liftM vcat $ mapM defListItemToConTeXt lst
300-
blockToConTeXt HorizontalRule = return $ "\\thinrule" <> blankline
303+
blockToConTeXt' HorizontalRule = return $ "\\thinrule" <> blankline
301304
-- If this is ever executed, provide a default for the reference identifier.
302-
blockToConTeXt (Header level attr lst) =
305+
blockToConTeXt' (Header level attr lst) =
303306
sectionHeader attr level lst NonSectionHeading
304-
blockToConTeXt (Table attr caption colspecs thead tbody tfoot) =
307+
blockToConTeXt' (Table attr caption colspecs thead tbody tfoot) =
305308
tableToConTeXt (Ann.toTable attr caption colspecs thead tbody tfoot)
306-
blockToConTeXt (Figure (ident, _, _) (Caption cshort clong) body) = do
309+
blockToConTeXt' (Figure (ident, _, _) (Caption cshort clong) body) = do
307310
title <- inlineListToConTeXt (blocksToInlines clong)
308311
list <- maybe (pure empty) inlineListToConTeXt cshort
309312
content <- blockListToConTeXt body

src/Text/Pandoc/Writers/DocBook.hs

Lines changed: 5 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -204,10 +204,11 @@ blockToDocBook opts (Div (id',"section":_classes,divattrs)
204204
title' <- inlinesToDocBook opts ils
205205
contents <- blocksToDocBook opts bs
206206
return $ inTags True tag attribs $ inTagsSimple "title" title' $$ contents
207-
blockToDocBook opts (Div (ident,classes,_) bs) = do
207+
blockToDocBook opts (Div (ident,classes,_kvs) bs) = do
208208
version <- ask
209209
let identAttribs = [(idName version, ident) | not (T.null ident)]
210210
admonitions = ["caution","danger","important","note","tip","warning"]
211+
211212
case classes of
212213
(l:_) | l `elem` admonitions -> do
213214
let (mTitleBs, bodyBs) =
@@ -219,13 +220,15 @@ blockToDocBook opts (Div (ident,classes,_) bs) = do
219220
_ -> (Nothing, bs)
220221
admonitionTitle <- case mTitleBs of
221222
Nothing -> return mempty
222-
-- id will be attached to the admonition so lets pass empty identAttrs.
223+
-- id will be attached to the admonition so let's pass empty identAttrs.
223224
Just titleBs -> inTagsSimple "title" <$> titleBs
224225
admonitionBody <- handleDivBody [] bodyBs
225226
return (inTags True l identAttribs (admonitionTitle $$ admonitionBody))
226227
_ -> handleDivBody identAttribs bs
227228
where
228229
handleDivBody identAttribs [Para lst] =
230+
-- For wrapper divs with single Para, apply attributes to para
231+
-- For normal divs with single Para, also apply attributes to para (original behavior)
229232
if hasLineBreaks lst
230233
then flush . nowrap . inTags False "literallayout" identAttribs
231234
<$> inlinesToDocBook opts lst

src/Text/Pandoc/Writers/Docx/OpenXML.hs

Lines changed: 3 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -227,6 +227,8 @@ writeOpenXML :: PandocMonad m
227227
-> WS m (Text, [Element], [Element])
228228
writeOpenXML opts (Pandoc meta blocks) = do
229229
setupTranslations meta
230+
-- Apply unwrapWrapperDiv to all blocks
231+
let blocks' = walk unwrapWrapperDiv blocks
230232
let includeTOC = writerTableOfContents opts || lookupMetaBool "toc" meta
231233
let includeLOF = writerListOfFigures opts || lookupMetaBool "lof" meta
232234
let includeLOT = writerListOfTables opts || lookupMetaBool "lot" meta
@@ -252,7 +254,7 @@ writeOpenXML opts (Pandoc meta blocks) = do
252254
(fmap (hcat . map (literal . showContent)) . inlinesToOpenXML opts)
253255
(docAuthors meta)
254256

255-
doc' <- setFirstPara >> blocksToOpenXML opts blocks
257+
doc' <- setFirstPara >> blocksToOpenXML opts blocks'
256258
let body = vcat $ map (literal . showContent) doc'
257259
notes' <- gets (reverse . stFootnotes)
258260
comments <- gets (reverse . stComments)

src/Text/Pandoc/Writers/DokuWiki.hs

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -41,7 +41,7 @@ import Text.Pandoc.Shared (figureDiv, linesToPara, removeFormatting, trimr)
4141
import Text.Pandoc.URI (escapeURI, isURI)
4242
import Text.Pandoc.Templates (renderTemplate)
4343
import Text.DocLayout (render, literal)
44-
import Text.Pandoc.Writers.Shared (defField, metaToContext, toLegacyTable)
44+
import Text.Pandoc.Writers.Shared (defField, metaToContext, toLegacyTable, unwrapWrapperDiv)
4545
import Data.Maybe (fromMaybe)
4646
import qualified Data.Map as M
4747

@@ -101,7 +101,7 @@ blockToDokuWiki :: PandocMonad m
101101
-> DokuWiki m Text
102102

103103
blockToDokuWiki opts (Div _attrs bs) = do
104-
contents <- blockListToDokuWiki opts bs
104+
contents <- blockListToDokuWiki opts (map unwrapWrapperDiv bs)
105105
indent <- asks stIndent
106106
return $ contents <> if T.null indent then "\n" else ""
107107

src/Text/Pandoc/Writers/EPUB.hs

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -35,7 +35,7 @@ import qualified Data.Text.Lazy as TL
3535
import System.FilePath (takeExtension, takeFileName, makeRelative)
3636
import Text.HTML.TagSoup (Tag (TagOpen), fromAttrib, parseTags)
3737
import Text.Pandoc.Builder (fromList, setMeta)
38-
import Text.Pandoc.Writers.Shared (ensureValidXmlIdentifiers)
38+
import Text.Pandoc.Writers.Shared (ensureValidXmlIdentifiers, unwrapWrapperDiv)
3939
import Data.Tree (Tree(..))
4040
import Text.Pandoc.Class (PandocMonad, report)
4141
import qualified Text.Pandoc.Class.PandocPure as P
@@ -1211,7 +1211,7 @@ transformBlock (RawBlock fmt raw)
12111211
let tags = parseTags raw
12121212
tags' <- mapM transformTag tags
12131213
return $ RawBlock fmt (renderTags' tags')
1214-
transformBlock b = return b
1214+
transformBlock b = return $ unwrapWrapperDiv b
12151215

12161216
transformInline :: PandocMonad m
12171217
=> WriterOptions

src/Text/Pandoc/Writers/FB2.hs

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -41,7 +41,7 @@ import Text.Pandoc.Shared (blocksToInlines, capitalize, orderedListMarkers,
4141
makeSections, tshow, stringify)
4242
import Text.Pandoc.Walk (walk)
4343
import Text.Pandoc.Writers.Shared (lookupMetaString, toLegacyTable,
44-
ensureValidXmlIdentifiers)
44+
ensureValidXmlIdentifiers, unwrapWrapperDiv)
4545
import Data.Generics (everywhere, mkT)
4646

4747
-- | Data to be written at the end of the document:
@@ -315,7 +315,7 @@ blockToXml (RawBlock f str) =
315315
Left msg -> throwError $ PandocXMLError "" msg
316316
Right nds -> return nds
317317
else return []
318-
blockToXml (Div _ bs) = cMapM blockToXml bs
318+
blockToXml (Div _ bs) = cMapM blockToXml (map unwrapWrapperDiv bs)
319319
blockToXml (BlockQuote bs) = list . el "cite" <$> cMapM blockToXml bs
320320
blockToXml (LineBlock lns) =
321321
list . el "poem" <$> mapM stanza (split null lns)

src/Text/Pandoc/Writers/HTML.hs

Lines changed: 10 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -752,11 +752,17 @@ blockToHtmlInner opts (LineBlock lns) = do
752752
return $ H.div ! A.class_ "line-block" $ htmlLines
753753
blockToHtmlInner opts (Div (ident, classes, kvs) [Para pans]) | Just "1" <- lookup "wrapper" kvs = do
754754
-- This is a paragraph that was wrapped in a Div by the reader
755-
-- Unwrap it back to a <p> tag, transferring attributes from the Div
756-
let pKVs = filter (\(k,_) -> k /= "wrapper") kvs
757-
let pAttr = (ident, classes, pKVs)
755+
-- Unwrap it back to a <p> tag, with extension-controlled attribute handling
758756
inner <- inlineListToHtml opts pans
759-
addAttrs opts pAttr (H.p inner)
757+
if isEnabled Ext_paragraph_attributes opts
758+
then do
759+
-- Extension enabled: preserve all attributes except wrapper
760+
let pKVs = filter (\(k,_) -> k /= "wrapper") kvs
761+
let pAttr = (ident, classes, pKVs)
762+
addAttrs opts pAttr (H.p inner)
763+
else
764+
-- Extension disabled: remove all attributes
765+
return (H.p inner)
760766
blockToHtmlInner opts (Div (ident, "section":dclasses, dkvs)
761767
(Header level
762768
hattr@(hident,hclasses,hkvs) ils : xs)) = do

0 commit comments

Comments
 (0)