Skip to content

Commit

Permalink
Store "unnumbered" class in DocBook role attribute (jgm#8481)
Browse files Browse the repository at this point in the history
Markdown allows marking a heading as unnumbered, which is stored
as a class token internally. This change will recognize this
particular class token and append it to the role attribute, or
create a role attribute with it if needed. This does not imply
any processing in DocBook but is intended to let customized
stylesheets identify these sections and act accordingly.

Closes jgm#1402
  • Loading branch information
lifeunleaded authored and liruqi committed Mar 3, 2023
1 parent 59290a8 commit cbb8f9b
Show file tree
Hide file tree
Showing 2 changed files with 29 additions and 9 deletions.
15 changes: 12 additions & 3 deletions src/Text/Pandoc/Writers/DocBook.hs
Original file line number Diff line number Diff line change
Expand Up @@ -14,7 +14,7 @@ Conversion of 'Pandoc' documents to DocBook XML.
module Text.Pandoc.Writers.DocBook ( writeDocBook4, writeDocBook5 ) where
import Control.Monad.Reader
import Data.Generics (everywhere, mkT)
import Data.Maybe (isNothing)
import Data.Maybe (isNothing, maybeToList)
import Data.Monoid (Any (..))
import Data.Text (Text)
import qualified Data.Text as T
Expand Down Expand Up @@ -169,7 +169,7 @@ blockToDocBook :: PandocMonad m => WriterOptions -> Block -> DB m (Doc Text)
blockToDocBook _ Null = return empty
-- Add ids to paragraphs in divs with ids - this is needed for
-- pandoc-citeproc to get link anchors in bibliographies:
blockToDocBook opts (Div (id',"section":_,_) (Header lvl (_,_,attrs) ils : xs)) = do
blockToDocBook opts (Div (id',"section":_,_) (Header lvl (_,classes,attrs) ils : xs)) = do
version <- ask
-- DocBook doesn't allow sections with no content, so insert some if needed
let bs = if null xs
Expand All @@ -191,7 +191,8 @@ blockToDocBook opts (Div (id',"section":_,_) (Header lvl (_,_,attrs) ils : xs))
else []

-- Populate miscAttr with Header.Attr.attributes, filtering out non-valid DocBook section attributes, id, and xml:id
miscAttr = filter (isSectionAttr version) attrs
-- Also enrich the role attribute with certain class tokens
miscAttr = enrichRole (filter (isSectionAttr version) attrs) classes
attribs = nsAttr <> idAttr <> miscAttr
title' <- inlinesToDocBook opts ils
contents <- blocksToDocBook opts bs
Expand Down Expand Up @@ -464,6 +465,14 @@ idAndRole (id',cls,_) = ident <> role
ident = [("id", id') | not (T.null id')]
role = [("role", T.unwords cls) | not (null cls)]

-- Used in blockToDocBook for Header (section) to create or extend
-- the role attribute with candidate class tokens
enrichRole :: [(Text, Text)] -> [Text] -> [(Text, Text)]
enrichRole mattrs cls = [("role",rolevals) | rolevals /= ""]<>(filter (\x -> (fst x) /= "role") mattrs)
where
rolevals = T.unwords((filter (`elem` cand) cls)<>(maybeToList(lookup "role" mattrs)))
cand = ["unnumbered"]

isSectionAttr :: DocBookVersion -> (Text, Text) -> Bool
isSectionAttr _ ("label",_) = True
isSectionAttr _ ("status",_) = True
Expand Down
23 changes: 17 additions & 6 deletions test/Tests/Writers/DocBook.hs
Original file line number Diff line number Diff line change
Expand Up @@ -387,34 +387,45 @@ tests = [ testGroup "inline elements"
]
, testGroup "section attributes" $
let
headers = headerWith ("myid1",[],[("role","internal"),("xml:id","anotherid"),("dir","rtl")]) 1 "header1"
<> headerWith ("myid2",[],[("invalidname","value"),("arch","linux"),("dir","invaliddir")]) 1 "header2"
headers = headerWith ("myid1",["unnumbered","ignored"],[("role","internal"),("xml:id","anotherid"),("dir","rtl")]) 1 "header1"
<> headerWith ("myid2",["unnumbered"],[("invalidname","value"),("arch","linux"),("dir","invaliddir")]) 1 "header2"
<> headerWith ("myid3",["ignored"],[]) 1 "header3"
in
[ test docbook5 "sections with attributes (db5)" $
headers =?>
unlines [ "<section xmlns=\"http://docbook.org/ns/docbook\" xmlns:xlink=\"http://www.w3.org/1999/xlink\" xml:id=\"myid1\" role=\"internal\" dir=\"rtl\">"
unlines [ "<section xmlns=\"http://docbook.org/ns/docbook\" xmlns:xlink=\"http://www.w3.org/1999/xlink\" xml:id=\"myid1\" role=\"unnumbered internal\" dir=\"rtl\">"
, " <title>header1</title>"
, " <para>"
, " </para>"
, "</section>"
, "<section xmlns=\"http://docbook.org/ns/docbook\" xmlns:xlink=\"http://www.w3.org/1999/xlink\" xml:id=\"myid2\">"
, "<section xmlns=\"http://docbook.org/ns/docbook\" xmlns:xlink=\"http://www.w3.org/1999/xlink\" xml:id=\"myid2\" role=\"unnumbered\">"
, " <title>header2</title>"
, " <para>"
, " </para>"
, "</section>"
, "<section xmlns=\"http://docbook.org/ns/docbook\" xmlns:xlink=\"http://www.w3.org/1999/xlink\" xml:id=\"myid3\">"
, " <title>header3</title>"
, " <para>"
, " </para>"
, "</section>"
]
, test docbook "sections with attributes (db4)" $
headers =?>
unlines [ "<sect1 id=\"myid1\" role=\"internal\">"
unlines [ "<sect1 id=\"myid1\" role=\"unnumbered internal\">"
, " <title>header1</title>"
, " <para>"
, " </para>"
, "</sect1>"
, "<sect1 id=\"myid2\" arch=\"linux\">"
, "<sect1 id=\"myid2\" role=\"unnumbered\" arch=\"linux\">"
, " <title>header2</title>"
, " <para>"
, " </para>"
, "</sect1>"
, "<sect1 id=\"myid3\">"
, " <title>header3</title>"
, " <para>"
, " </para>"
, "</sect1>"
]
]
]

0 comments on commit cbb8f9b

Please sign in to comment.