aboutsummaryrefslogtreecommitdiff
path: root/src/Text/Pandoc/Writers
diff options
context:
space:
mode:
Diffstat (limited to 'src/Text/Pandoc/Writers')
-rw-r--r--src/Text/Pandoc/Writers/Docx.hs2
-rw-r--r--src/Text/Pandoc/Writers/Markdown.hs7
-rw-r--r--src/Text/Pandoc/Writers/RST.hs8
3 files changed, 13 insertions, 4 deletions
diff --git a/src/Text/Pandoc/Writers/Docx.hs b/src/Text/Pandoc/Writers/Docx.hs
index 0cb313e7b..5870844a4 100644
--- a/src/Text/Pandoc/Writers/Docx.hs
+++ b/src/Text/Pandoc/Writers/Docx.hs
@@ -211,7 +211,7 @@ writeDocx opts doc@(Pandoc meta _) = do
let doc' = walk fixDisplayMath $ doc
username <- lookup "USERNAME" <$> getEnvironment
utctime <- getCurrentTime
- distArchive <- getDefaultReferenceDocx Nothing
+ distArchive <- getDefaultReferenceDocx datadir
refArchive <- case writerReferenceDocx opts of
Just f -> liftM (toArchive . toLazy) $ B.readFile f
Nothing -> getDefaultReferenceDocx datadir
diff --git a/src/Text/Pandoc/Writers/Markdown.hs b/src/Text/Pandoc/Writers/Markdown.hs
index 804f4101d..5e7748efb 100644
--- a/src/Text/Pandoc/Writers/Markdown.hs
+++ b/src/Text/Pandoc/Writers/Markdown.hs
@@ -258,10 +258,13 @@ tableOfContents opts headers =
-- | Converts an Element to a list item for a table of contents,
elementToListItem :: WriterOptions -> Element -> [Block]
-elementToListItem opts (Sec lev _ _ headerText subsecs)
- = Plain headerText :
+elementToListItem opts (Sec lev _nums (ident,_,_) headerText subsecs)
+ = Plain headerLink :
[ BulletList (map (elementToListItem opts) subsecs) |
not (null subsecs) && lev < writerTOCDepth opts ]
+ where headerLink = if null ident
+ then headerText
+ else [Link headerText ('#':ident, "")]
elementToListItem _ (Blk _) = []
attrsToMarkdown :: Attr -> Doc
diff --git a/src/Text/Pandoc/Writers/RST.hs b/src/Text/Pandoc/Writers/RST.hs
index fae908f30..754aee29c 100644
--- a/src/Text/Pandoc/Writers/RST.hs
+++ b/src/Text/Pandoc/Writers/RST.hs
@@ -81,7 +81,8 @@ pandocToRST (Pandoc meta blocks) = do
(fmap (render colwidth) . blockListToRST)
(fmap (trimr . render colwidth) . inlineListToRST)
$ deleteMeta "title" $ deleteMeta "subtitle" meta
- body <- blockListToRST' True $ normalizeHeadings 1 blocks
+ let minLev = findMinHeadingLevel Nothing blocks
+ body <- blockListToRST' True $ normalizeHeadings minLev blocks
notes <- liftM (reverse . stNotes) get >>= notesToRST
-- note that the notes may contain refs, so we do them first
refs <- liftM (reverse . stLinks) get >>= refsToRST
@@ -107,6 +108,11 @@ pandocToRST (Pandoc meta blocks) = do
headerLtEq _ _ = False
normalizeHeadings lev (b:bs) = b:normalizeHeadings lev bs
normalizeHeadings _ [] = []
+ findMinHeadingLevel Nothing (Header l _a _i:bs) = findMinHeadingLevel (Just l) bs
+ findMinHeadingLevel (Just ol) (Header l _a _i:bs) =
+ findMinHeadingLevel (Just $ if ol>l then l else ol) bs
+ findMinHeadingLevel l (_:bs) = findMinHeadingLevel l bs
+ findMinHeadingLevel l [] = fromMaybe 1 l
-- | Return RST representation of reference key table.
refsToRST :: Refs -> State WriterState Doc