Skip to content

Commit b706cb0

Browse files
committed
Chunks: autogenerate unique ids for sections missing them.
This is needed for TOC generation to work properly. We can't create TOC links if there are no ids. This fixes some EPUB validation issues we've been getting since switching over to Chunks for chunking. Closes #9383.
1 parent 32b6db1 commit b706cb0

File tree

1 file changed

+20
-2
lines changed

1 file changed

+20
-2
lines changed

src/Text/Pandoc/Chunks.hs

+20-2
Original file line numberDiff line numberDiff line change
@@ -29,7 +29,7 @@ module Text.Pandoc.Chunks
2929

3030
import Text.Pandoc.Definition
3131
import Text.Pandoc.Shared (makeSections, stringify, inlineListToIdentifier,
32-
tshow)
32+
tshow, uniqueIdent)
3333
import Text.Pandoc.Walk (Walkable(..), query)
3434
import Data.Aeson (FromJSON, ToJSON)
3535
import Data.Text (Text)
@@ -43,6 +43,8 @@ import Text.HTML.TagSoup (Tag (TagOpen), fromAttrib, parseTags)
4343
import Data.Tree (Tree(..))
4444
import Data.Data (Data)
4545
import Data.Typeable (Typeable)
46+
import qualified Data.Set as Set
47+
import Control.Monad.State
4648

4749
-- | Split 'Pandoc' into 'Chunk's, e.g. for conversion into
4850
-- a set of HTML pages or EPUB chapters.
@@ -63,7 +65,23 @@ splitIntoChunks pathTemplate numberSections mbBaseLevel
6365
where
6466
tocTree = fixTOCTreePaths chunks $ toTOCTree sections
6567
chunks = makeChunks chunklev pathTemplate meta $ sections
66-
sections = makeSections numberSections mbBaseLevel $ blocks
68+
sections = ensureIds $ makeSections numberSections mbBaseLevel blocks
69+
70+
-- The TOC won't work if we don't have unique identifiers for all sections.
71+
ensureIds :: [Block] -> [Block]
72+
ensureIds bs = evalState (walkM go bs) mempty
73+
where
74+
go :: Block -> State (Set.Set Text) Block
75+
go b@(Div (ident,"section":cls,kvs) bs'@(Header _ _ ils : _))
76+
| T.null ident
77+
= do ids <- get
78+
let newid = uniqueIdent mempty ils ids
79+
modify $ Set.insert newid
80+
pure $ Div (newid,"section":cls,kvs) bs'
81+
| otherwise
82+
= do modify $ Set.insert ident
83+
pure b
84+
go b = pure b
6785

6886
-- | Add chunkNext, chunkPrev, chunkUp
6987
addNav :: ChunkedDoc -> ChunkedDoc

0 commit comments

Comments
 (0)