Skip to content

Commit

Permalink
Use integer ids for bookmarks.
Browse files Browse the repository at this point in the history
Closes jgm#626.
  • Loading branch information
jgm committed Oct 3, 2012
1 parent f9d76bd commit 02bb0f0
Showing 1 changed file with 8 additions and 6 deletions.
14 changes: 8 additions & 6 deletions src/Text/Pandoc/Writers/Docx.hs
Original file line number Diff line number Diff line change
Expand Up @@ -50,6 +50,7 @@ import Text.XML.Light
import Text.TeXMath
import Control.Monad.State
import Text.Highlighting.Kate
import Data.Unique (hashUnique, newUnique)

data WriterState = WriterState{
stTextProperties :: [Element]
Expand Down Expand Up @@ -333,11 +334,12 @@ blockToOpenXML opts (Header lev lst) = do
contents <- withParaProp (pStyle $ "Heading" ++ show lev) $
blockToOpenXML opts (Para lst)
usedIdents <- gets stSectionIds
let ident = uniqueIdent lst usedIdents
modify $ \s -> s{ stSectionIds = ident : stSectionIds s }
let bookmarkStart = mknode "w:bookmarkStart" [("w:id",ident)
,("w:name",ident)] ()
let bookmarkEnd = mknode "w:bookmarkEnd" [("w:id",ident)] ()
let bookmarkName = uniqueIdent lst usedIdents
modify $ \s -> s{ stSectionIds = bookmarkName : stSectionIds s }
id' <- liftIO $ hashUnique `fmap` newUnique
let bookmarkStart = mknode "w:bookmarkStart" [("w:id",show id')
,("w:name",bookmarkName)] ()
let bookmarkEnd = mknode "w:bookmarkEnd" [("w:id",show id')] ()
return $ [bookmarkStart] ++ contents ++ [bookmarkEnd]
blockToOpenXML opts (Plain lst) = blockToOpenXML opts (Para lst)
blockToOpenXML opts (Para x@[Image alt _]) = do
Expand Down Expand Up @@ -574,7 +576,7 @@ inlineToOpenXML _ (Code attrs str) =
, mknode "w:t" [("xml:space","preserve")] tok ]
inlineToOpenXML opts (Note bs) = do
notes <- gets stFootnotes
let notenum = length notes + 1
notenum <- liftIO $ hashUnique `fmap` newUnique
let notemarker = mknode "w:r" []
[ mknode "w:rPr" [] (rStyle "FootnoteReference")
, mknode "w:footnoteRef" [] () ]
Expand Down

0 comments on commit 02bb0f0

Please sign in to comment.