@@ -123,6 +123,7 @@ defaultWriterEnv = WriterEnv{ envTextProperties = []
123123
124124data WriterState = WriterState {
125125 stFootnotes :: [Element ]
126+ , stEndnotes :: [Element ]
126127 , stComments :: [([(String ,String )], [Inline ])]
127128 , stSectionIds :: Set. Set String
128129 , stExternalLinks :: M. Map String String
@@ -140,6 +141,7 @@ data WriterState = WriterState{
140141defaultWriterState :: WriterState
141142defaultWriterState = WriterState {
142143 stFootnotes = defaultFootnotes
144+ , stEndnotes = []
143145 , stComments = []
144146 , stSectionIds = Set. empty
145147 , stExternalLinks = M. empty
@@ -307,7 +309,7 @@ writeDocx opts doc@(Pandoc meta _) = do
307309 }
308310
309311
310- ((contents, footnotes, comments), st) <- runStateT
312+ ((contents, footnotes, endnotes, comments), st) <- runStateT
311313 (runReaderT
312314 (writeOpenXML opts{writerWrapText = WrapNone } doc')
313315 env)
@@ -376,6 +378,8 @@ writeDocx opts doc@(Pandoc meta _) = do
376378 " application/vnd.openxmlformats-officedocument.wordprocessingml.comments+xml" )
377379 ,(" /word/footnotes.xml" ,
378380 " application/vnd.openxmlformats-officedocument.wordprocessingml.footnotes+xml" )
381+ ,(" /word/endnotes.xml" ,
382+ " application/vnd.openxmlformats-officedocument.wordprocessingml.endnotes+xml" )
379383 ] ++
380384 map (\ x -> (maybe " " (" /word/" ++ ) $ extractTarget x,
381385 " application/vnd.openxmlformats-officedocument.wordprocessingml.header+xml" )) headers ++
@@ -420,8 +424,11 @@ writeDocx opts doc@(Pandoc meta _) = do
420424 ,(" http://schemas.openxmlformats.org/officeDocument/2006/relationships/footnotes" ,
421425 " rId7" ,
422426 " footnotes.xml" )
423- ,(" http://schemas.openxmlformats.org/officeDocument/2006/relationships/comments " ,
427+ ,(" http://schemas.openxmlformats.org/officeDocument/2006/relationships/endnotes " ,
424428 " rId8" ,
429+ " endnotes.xml" )
430+ ,(" http://schemas.openxmlformats.org/officeDocument/2006/relationships/comments" ,
431+ " rId9" ,
425432 " comments.xml" )
426433 ]
427434
@@ -460,14 +467,23 @@ writeDocx opts doc@(Pandoc meta _) = do
460467 $ renderXml docContents
461468
462469 -- footnotes
463- let notes = mknode " w:footnotes" stdAttributes footnotes
464- let footnotesEntry = toEntry " word/footnotes.xml" epochtime $ renderXml notes
470+ let footnotesNode = mknode " w:footnotes" stdAttributes footnotes
471+ let footnotesEntry = toEntry " word/footnotes.xml" epochtime $ renderXml footnotesNode
465472
466473 -- footnote rels
467474 let footnoteRelEntry = toEntry " word/_rels/footnotes.xml.rels" epochtime
468475 $ renderXml $ mknode " Relationships" [(" xmlns" ," http://schemas.openxmlformats.org/package/2006/relationships" )]
469476 linkrels
470477
478+ -- endnotes
479+ let endnotesNode = mknode " w:endnotes" stdAttributes endnotes
480+ let endnotesEntry = toEntry " word/endnotes.xml" epochtime $ renderXml endnotesNode
481+
482+ -- endnote rels
483+ let endnoteRelEntry = toEntry " word/_rels/endnotes.xml.rels" epochtime
484+ $ renderXml $ mknode " Relationships" [(" xmlns" ," http://schemas.openxmlformats.org/package/2006/relationships" )]
485+ linkrels
486+
471487 -- comments
472488 let commentsEntry = toEntry " word/comments.xml" epochtime
473489 $ renderXml $ mknode " w:comments" stdAttributes comments
@@ -568,15 +584,16 @@ writeDocx opts doc@(Pandoc meta _) = do
568584 , " word/_rels/" `isPrefixOf` (eRelativePath e)
569585 , " .xml.rels" `isSuffixOf` (eRelativePath e)
570586 , eRelativePath e /= " word/_rels/document.xml.rels"
571- , eRelativePath e /= " word/_rels/footnotes.xml.rels" ]
587+ , eRelativePath e /= " word/_rels/footnotes.xml.rels"
588+ , eRelativePath e /= " word/_rels/endnotes.xml.rels" ]
572589 let otherMediaEntries = [ e | e <- zEntries refArchive
573590 , " word/media/" `isPrefixOf` eRelativePath e ]
574591
575592 -- Create archive
576593 let archive = foldr addEntryToArchive emptyArchive $
577594 contentTypesEntry : relsEntry : contentEntry : relEntry :
578- footnoteRelEntry : numEntry : styleEntry : footnotesEntry :
579- commentsEntry :
595+ footnoteRelEntry : endnoteRelEntry : numEntry : styleEntry :
596+ footnotesEntry : endnotesEntry : commentsEntry :
580597 docPropsEntry : docPropsAppEntry : themeEntry :
581598 fontTableEntry : settingsEntry : webSettingsEntry :
582599 imageEntries ++ headerFooterEntries ++
@@ -775,7 +792,7 @@ makeTOC _ = return []
775792
776793-- | Convert Pandoc document to two lists of
777794-- OpenXML elements (the main document and footnotes).
778- writeOpenXML :: (PandocMonad m ) => WriterOptions -> Pandoc -> WS m ([Element ], [Element ],[Element ])
795+ writeOpenXML :: (PandocMonad m ) => WriterOptions -> Pandoc -> WS m ([Element ], [Element ], [ Element ], [Element ])
779796writeOpenXML opts (Pandoc meta blocks) = do
780797 let tit = docTitle meta ++ case lookupMeta " subtitle" meta of
781798 Just (MetaBlocks [Plain xs]) -> LineBreak : xs
@@ -804,7 +821,8 @@ writeOpenXML opts (Pandoc meta blocks) = do
804821 convertSpace xs = xs
805822 let blocks' = bottomUp convertSpace blocks
806823 doc' <- setFirstPara >> blocksToOpenXML opts blocks'
807- notes' <- reverse <$> gets stFootnotes
824+ footnotes' <- reverse <$> gets stFootnotes
825+ endnotes' <- reverse <$> gets stEndnotes
808826 comments <- reverse <$> gets stComments
809827 let toComment (kvs, ils) = do
810828 annotation <- inlinesToOpenXML opts ils
@@ -824,7 +842,7 @@ writeOpenXML opts (Pandoc meta blocks) = do
824842 comments' <- mapM toComment comments
825843 toc <- makeTOC opts
826844 let meta' = title ++ subtitle ++ authors ++ date ++ abstract ++ toc
827- return (meta' ++ doc', notes ', comments')
845+ return (meta' ++ doc', footnotes', endnotes ', comments')
828846
829847-- | Convert a list of Pandoc blocks to OpenXML.
830848blocksToOpenXML :: (PandocMonad m ) => WriterOptions -> [Block ] -> WS m [Element ]
@@ -1250,8 +1268,8 @@ inlineToOpenXML' opts (Code attrs str) = do
12501268 Left msg -> do
12511269 unless (null msg) $ report $ CouldNotHighlight msg
12521270 unhighlighted
1253- inlineToOpenXML' opts (Note _ bs) = do
1254- notes <- gets stFootnotes
1271+ inlineToOpenXML' opts (Note FootNote bs) = do
1272+ footnotes <- gets stFootnotes
12551273 notenum <- (lift . lift) getUniqueId
12561274 footnoteStyle <- rStyleM " Footnote Reference"
12571275 let notemarker = mknode " w:r" []
@@ -1268,10 +1286,32 @@ inlineToOpenXML' opts (Note _ bs) = do
12681286 (withParaPropM (pStyleM " Footnote Text" ) $ blocksToOpenXML opts
12691287 $ insertNoteRef bs)
12701288 let newnote = mknode " w:footnote" [(" w:id" , notenum)] contents
1271- modify $ \ s -> s{ stFootnotes = newnote : notes }
1289+ modify $ \ s -> s{ stFootnotes = newnote : footnotes }
12721290 return [ mknode " w:r" []
12731291 [ mknode " w:rPr" [] footnoteStyle
12741292 , mknode " w:footnoteReference" [(" w:id" , notenum)] () ] ]
1293+ inlineToOpenXML' opts (Note EndNote bs) = do
1294+ endnotes <- gets stEndnotes
1295+ notenum <- (lift . lift) getUniqueId
1296+ endnoteStyle <- rStyleM " Endnote Reference"
1297+ let notemarker = mknode " w:r" []
1298+ [ mknode " w:rPr" [] endnoteStyle
1299+ , mknode " w:endnoteRef" [] () ]
1300+ let notemarkerXml = RawInline (Format " openxml" ) $ ppElement notemarker
1301+ let insertNoteRef (Plain ils : xs) = Plain (notemarkerXml : Space : ils) : xs
1302+ insertNoteRef (Para ils : xs) = Para (notemarkerXml : Space : ils) : xs
1303+ insertNoteRef xs = Para [notemarkerXml] : xs
1304+
1305+ contents <- local (\ env -> env{ envListLevel = - 1
1306+ , envParaProperties = []
1307+ , envTextProperties = [] })
1308+ (withParaPropM (pStyleM " Endnote Text" ) $ blocksToOpenXML opts
1309+ $ insertNoteRef bs)
1310+ let newnote = mknode " w:endnote" [(" w:id" , notenum)] contents
1311+ modify $ \ s -> s{ stEndnotes = newnote : endnotes }
1312+ return [ mknode " w:r" []
1313+ [ mknode " w:rPr" [] endnoteStyle
1314+ , mknode " w:endnoteReference" [(" w:id" , notenum)] () ] ]
12751315-- internal link:
12761316inlineToOpenXML' opts (Link _ txt (' #' : xs,_)) = do
12771317 contents <- withTextPropM (rStyleM " Hyperlink" ) $ inlinesToOpenXML opts txt
0 commit comments