aboutsummaryrefslogtreecommitdiff
path: root/src/Text/Pandoc/Writers
diff options
context:
space:
mode:
authorJohn MacFarlane <fiddlosopher@gmail.com>2012-10-29 22:45:52 -0700
committerJohn MacFarlane <fiddlosopher@gmail.com>2013-01-09 09:30:05 -0800
commitd599c4cdabd0d71fd9d27161c949b5e1e692436d (patch)
tree96b6130be929282f85d0261bbb0e0ef37e4e43ff /src/Text/Pandoc/Writers
parent7a40fa8c08996cb94e7ff3cfafd8ede84972ce70 (diff)
downloadpandoc-d599c4cdabd0d71fd9d27161c949b5e1e692436d.tar.gz
Added Attr field to Header.
Previously header ids were autogenerated by the writers. Now they are generated (unless supplied explicitly) in the markdown parser, if the `header_identifiers` extension is selected. In addition, the textile reader now supports id attributes on headers.
Diffstat (limited to 'src/Text/Pandoc/Writers')
-rw-r--r--src/Text/Pandoc/Writers/AsciiDoc.hs4
-rw-r--r--src/Text/Pandoc/Writers/ConTeXt.hs2
-rw-r--r--src/Text/Pandoc/Writers/Docbook.hs2
-rw-r--r--src/Text/Pandoc/Writers/Docx.hs6
-rw-r--r--src/Text/Pandoc/Writers/EPUB.hs13
-rw-r--r--src/Text/Pandoc/Writers/FB2.hs12
-rw-r--r--src/Text/Pandoc/Writers/HTML.hs22
-rw-r--r--src/Text/Pandoc/Writers/LaTeX.hs10
-rw-r--r--src/Text/Pandoc/Writers/Man.hs2
-rw-r--r--src/Text/Pandoc/Writers/Markdown.hs2
-rw-r--r--src/Text/Pandoc/Writers/MediaWiki.hs2
-rw-r--r--src/Text/Pandoc/Writers/OpenDocument.hs2
-rw-r--r--src/Text/Pandoc/Writers/Org.hs2
-rw-r--r--src/Text/Pandoc/Writers/RST.hs2
-rw-r--r--src/Text/Pandoc/Writers/RTF.hs6
-rw-r--r--src/Text/Pandoc/Writers/Texinfo.hs16
-rw-r--r--src/Text/Pandoc/Writers/Textile.hs5
17 files changed, 59 insertions, 51 deletions
diff --git a/src/Text/Pandoc/Writers/AsciiDoc.hs b/src/Text/Pandoc/Writers/AsciiDoc.hs
index b03bc77a8..30da6ac1a 100644
--- a/src/Text/Pandoc/Writers/AsciiDoc.hs
+++ b/src/Text/Pandoc/Writers/AsciiDoc.hs
@@ -126,10 +126,10 @@ blockToAsciiDoc opts (Para inlines) = do
blockToAsciiDoc _ (RawBlock _ _) = return empty
blockToAsciiDoc _ HorizontalRule =
return $ blankline <> text "'''''" <> blankline
-blockToAsciiDoc opts (Header level inlines) = do
+blockToAsciiDoc opts (Header level (ident,_,_) inlines) = do
contents <- inlineListToAsciiDoc opts inlines
let len = offset contents
- return $ contents <> cr <>
+ return $ ("[[" <> text ident <> "]]") $$ contents $$
(case level of
1 -> text $ replicate len '-'
2 -> text $ replicate len '~'
diff --git a/src/Text/Pandoc/Writers/ConTeXt.hs b/src/Text/Pandoc/Writers/ConTeXt.hs
index 0663d537c..b9dcf0c71 100644
--- a/src/Text/Pandoc/Writers/ConTeXt.hs
+++ b/src/Text/Pandoc/Writers/ConTeXt.hs
@@ -190,7 +190,7 @@ blockToConTeXt (DefinitionList lst) =
liftM vcat $ mapM defListItemToConTeXt lst
blockToConTeXt HorizontalRule = return $ "\\thinrule" <> blankline
-- If this is ever executed, provide a default for the reference identifier.
-blockToConTeXt (Header level lst) = sectionHeader "" level lst
+blockToConTeXt (Header level (ident,_,_) lst) = sectionHeader ident level lst
blockToConTeXt (Table caption aligns widths heads rows) = do
let colDescriptor colWidth alignment = (case alignment of
AlignLeft -> 'l'
diff --git a/src/Text/Pandoc/Writers/Docbook.hs b/src/Text/Pandoc/Writers/Docbook.hs
index fe768efc5..890feacbf 100644
--- a/src/Text/Pandoc/Writers/Docbook.hs
+++ b/src/Text/Pandoc/Writers/Docbook.hs
@@ -142,7 +142,7 @@ listItemToDocbook opts item =
-- | Convert a Pandoc block element to Docbook.
blockToDocbook :: WriterOptions -> Block -> Doc
blockToDocbook _ Null = empty
-blockToDocbook _ (Header _ _) = empty -- should not occur after hierarchicalize
+blockToDocbook _ (Header _ _ _) = empty -- should not occur after hierarchicalize
blockToDocbook opts (Plain lst) = inlinesToDocbook opts lst
blockToDocbook opts (Para [Image txt (src,_)]) =
let alt = inlinesToDocbook opts txt
diff --git a/src/Text/Pandoc/Writers/Docx.hs b/src/Text/Pandoc/Writers/Docx.hs
index 069a5f6eb..839bb16d4 100644
--- a/src/Text/Pandoc/Writers/Docx.hs
+++ b/src/Text/Pandoc/Writers/Docx.hs
@@ -337,11 +337,13 @@ getUniqueId = liftIO $ (show . (+ 20) . hashUnique) `fmap` newUnique
-- | Convert a Pandoc block element to OpenXML.
blockToOpenXML :: WriterOptions -> Block -> WS [Element]
blockToOpenXML _ Null = return []
-blockToOpenXML opts (Header lev lst) = do
+blockToOpenXML opts (Header lev (ident,_,_) lst) = do
contents <- withParaProp (pStyle $ "Heading" ++ show lev) $
blockToOpenXML opts (Para lst)
usedIdents <- gets stSectionIds
- let bookmarkName = uniqueIdent lst usedIdents
+ let bookmarkName = if null ident
+ then uniqueIdent lst usedIdents
+ else ident
modify $ \s -> s{ stSectionIds = bookmarkName : stSectionIds s }
id' <- getUniqueId
let bookmarkStart = mknode "w:bookmarkStart" [("w:id", id')
diff --git a/src/Text/Pandoc/Writers/EPUB.hs b/src/Text/Pandoc/Writers/EPUB.hs
index b8a4bf1c6..493b762ac 100644
--- a/src/Text/Pandoc/Writers/EPUB.hs
+++ b/src/Text/Pandoc/Writers/EPUB.hs
@@ -119,18 +119,17 @@ writeEPUB opts doc@(Pandoc meta _) = do
-- add level 1 header to beginning if none there
let blocks' = case blocks of
- (Header 1 _ : _) -> blocks
- _ -> Header 1 (docTitle meta) : blocks
+ (Header 1 _ _ : _) -> blocks
+ _ -> Header 1 ("",[],[]) (docTitle meta) : blocks
let chapterHeaderLevel = writerEpubChapterLevel opts
-
-- internal reference IDs change when we chunk the file,
-- so that '#my-header-1' might turn into 'chap004.xhtml#my-header'.
-- the next two lines fix that:
let reftable = correlateRefs chapterHeaderLevel blocks'
let blocks'' = replaceRefs reftable blocks'
- let isChapterHeader (Header n _) = n <= chapterHeaderLevel
+ let isChapterHeader (Header n _ _) = n <= chapterHeaderLevel
isChapterHeader _ = False
let toChunks :: [Block] -> [[Block]]
@@ -145,8 +144,8 @@ writeEPUB opts doc@(Pandoc meta _) = do
$ renderHtml
$ writeHtml opts'
$ case bs of
- (Header _ xs : _) -> Pandoc (Meta xs [] []) bs
- _ -> Pandoc (Meta [] [] []) bs
+ (Header _ _ xs : _) -> Pandoc (Meta xs [] []) bs
+ _ -> Pandoc (Meta [] [] []) bs
let chapterEntries = zipWith chapToEntry [1..] chunks
@@ -444,7 +443,7 @@ correlateRefs chapterHeaderLevel bs =
, chapterIdents = []
, identTable = [] }
where go :: Block -> State IdentState ()
- go (Header n ils) = do
+ go (Header n _ ils) = do
when (n <= chapterHeaderLevel) $
modify $ \s -> s{ chapterNumber = chapterNumber s + 1
, chapterIdents = [] }
diff --git a/src/Text/Pandoc/Writers/FB2.hs b/src/Text/Pandoc/Writers/FB2.hs
index 301d80c54..eeb4616b4 100644
--- a/src/Text/Pandoc/Writers/FB2.hs
+++ b/src/Text/Pandoc/Writers/FB2.hs
@@ -158,7 +158,7 @@ renderSection level (ttl, body) = do
return $ el "section" (title ++ content)
where
hasSubsections = any isHeader
- isHeader (Header _ _) = True
+ isHeader (Header _ _ _) = True
isHeader _ = False
-- | Only <p> and <empty-line> are allowed within <title> in FB2.
@@ -186,13 +186,13 @@ splitSections level blocks = reverse $ revSplit (reverse blocks)
let (lastsec, before) = break sameLevel rblocks
(header, prevblocks) =
case before of
- ((Header n title):prevblocks') ->
+ ((Header n _ title):prevblocks') ->
if n == level
then (title, prevblocks')
else ([], before)
_ -> ([], before)
in (header, reverse lastsec) : revSplit prevblocks
- sameLevel (Header n _) = n == level
+ sameLevel (Header n _ _) = n == level
sameLevel _ = False
-- | Make another FictionBook body with footnotes.
@@ -361,7 +361,7 @@ blockToXml (DefinitionList defs) =
needsBreak (Para _) = False
needsBreak (Plain ins) = LineBreak `notElem` ins
needsBreak _ = True
-blockToXml (Header _ _) = -- should never happen, see renderSections
+blockToXml (Header _ _ _) = -- should never happen, see renderSections
error "unexpected header in section text"
blockToXml HorizontalRule = return
[ el "empty-line" ()
@@ -413,7 +413,7 @@ indent = indentBlock
let s' = unlines . map (spacer++) . lines $ s
in CodeBlock a s'
indentBlock (BlockQuote bs) = BlockQuote (map indent bs)
- indentBlock (Header l ins) = Header l (indentLines ins)
+ indentBlock (Header l attr' ins) = Header l attr' (indentLines ins)
indentBlock everythingElse = everythingElse
-- indent every (explicit) line
indentLines :: [Inline] -> [Inline]
@@ -613,4 +613,4 @@ cMap = concatMap
-- | Monadic equivalent of 'concatMap'.
cMapM :: (Monad m) => (a -> m [b]) -> [a] -> m [b]
-cMapM f xs = concat `liftM` mapM f xs \ No newline at end of file
+cMapM f xs = concat `liftM` mapM f xs
diff --git a/src/Text/Pandoc/Writers/HTML.hs b/src/Text/Pandoc/Writers/HTML.hs
index 68a8a1e09..2d42dd24e 100644
--- a/src/Text/Pandoc/Writers/HTML.hs
+++ b/src/Text/Pandoc/Writers/HTML.hs
@@ -219,7 +219,10 @@ inTemplate opts tit auths authsMeta date toc body' newvars =
-- | Like Text.XHtml's identifier, but adds the writerIdentifierPrefix
prefixedId :: WriterOptions -> String -> Attribute
-prefixedId opts s = A.id $ toValue $ writerIdentifierPrefix opts ++ s
+prefixedId opts s =
+ case s of
+ "" -> mempty
+ _ -> A.id $ toValue $ writerIdentifierPrefix opts ++ s
-- | Replacement for Text.XHtml's unordList.
unordList :: WriterOptions -> ([Html] -> Html)
@@ -258,7 +261,10 @@ elementToListItem opts (Sec lev num id' headerText subsecs)
let subList = if null subHeads
then mempty
else unordList opts subHeads
- return $ Just $ (H.a ! A.href (toValue $ "#" ++ writerIdentifierPrefix opts ++ id')
+ return $ Just
+ $ if null id'
+ then (H.a $ toHtml txt) >> subList
+ else (H.a ! A.href (toValue $ "#" ++ writerIdentifierPrefix opts ++ id')
$ toHtml txt) >> subList
elementToListItem _ _ = return Nothing
@@ -273,7 +279,7 @@ elementToHtml slideLevel opts (Sec level num id' title' elements) = do
let titleSlide = slide && level < slideLevel
header' <- if title' == [Str "\0"] -- marker for hrule
then return mempty
- else blockToHtml opts (Header level' title')
+ else blockToHtml opts (Header level' (id',[],[]) title')
let isSec (Sec _ _ _ _ _) = True
isSec (Blk _) = False
innerContents <- mapM (elementToHtml slideLevel opts)
@@ -283,8 +289,7 @@ elementToHtml slideLevel opts (Sec level num id' title' elements) = do
else elements
let header'' = if (writerSectionDivs opts ||
writerSlideVariant opts == S5Slides ||
- slide ||
- not (isEnabled Ext_header_identifiers opts))
+ slide)
then header'
else header' ! prefixedId opts id'
let inNl x = mconcat $ nl opts : intersperse (nl opts) x ++ [nl opts]
@@ -442,15 +447,16 @@ blockToHtml opts (BlockQuote blocks) =
else do
contents <- blockListToHtml opts blocks
return $ H.blockquote $ nl opts >> contents >> nl opts
-blockToHtml opts (Header level lst) = do
+blockToHtml opts (Header level (ident,_,_) lst) = do
contents <- inlineListToHtml opts lst
secnum <- liftM stSecNum get
let contents' = if writerNumberSections opts
then (H.span ! A.class_ "header-section-number" $ toHtml $ showSecNum secnum) >>
strToHtml " " >> contents
else contents
- let contents'' = if writerTableOfContents opts
- then H.a ! A.href (toValue $ "#" ++ writerIdentifierPrefix opts ++ "TOC") $ contents'
+ let contents'' = if writerTableOfContents opts && not (null ident)
+ then H.a ! A.href (toValue $
+ '#' : writerIdentifierPrefix opts ++ ident) $ contents'
else contents'
return $ (case level of
1 -> H.h1 contents''
diff --git a/src/Text/Pandoc/Writers/LaTeX.hs b/src/Text/Pandoc/Writers/LaTeX.hs
index f86eb079a..f01ddac78 100644
--- a/src/Text/Pandoc/Writers/LaTeX.hs
+++ b/src/Text/Pandoc/Writers/LaTeX.hs
@@ -109,8 +109,8 @@ pandocToLaTeX options (Pandoc (Meta title authors date) blocks) = do
let (blocks', lastHeader) = if writerCiteMethod options == Citeproc then
(blocks, [])
else case last blocks of
- Header 1 il -> (init blocks, il)
- _ -> (blocks, [])
+ Header 1 _ il -> (init blocks, il)
+ _ -> (blocks, [])
blocks'' <- if writerBeamer options
then toSlides blocks'
else return blocks'
@@ -227,7 +227,7 @@ toSlides bs = do
elementToBeamer :: Int -> Element -> State WriterState [Block]
elementToBeamer _slideLevel (Blk b) = return [b]
-elementToBeamer slideLevel (Sec lvl _num _ident tit elts)
+elementToBeamer slideLevel (Sec lvl _num ident tit elts)
| lvl > slideLevel = do
bs <- concat `fmap` mapM (elementToBeamer slideLevel) elts
return $ Para ( RawInline "latex" "\\begin{block}{"
@@ -235,7 +235,7 @@ elementToBeamer slideLevel (Sec lvl _num _ident tit elts)
: bs ++ [RawBlock "latex" "\\end{block}"]
| lvl < slideLevel = do
bs <- concat `fmap` mapM (elementToBeamer slideLevel) elts
- return $ (Header lvl tit) : bs
+ return $ (Header lvl (ident,[],[]) tit) : bs
| otherwise = do -- lvl == slideLevel
-- note: [fragile] is required or verbatim breaks
let hasCodeBlock (CodeBlock _ _) = [True]
@@ -404,7 +404,7 @@ blockToLaTeX (DefinitionList lst) = do
"\\end{description}"
blockToLaTeX HorizontalRule = return $
"\\begin{center}\\rule{3in}{0.4pt}\\end{center}"
-blockToLaTeX (Header level lst) = sectionHeader "" level lst
+blockToLaTeX (Header level (id',_,_) lst) = sectionHeader id' level lst
blockToLaTeX (Table caption aligns widths heads rows) = do
modify $ \s -> s{ stInTable = True, stTableNotes = [] }
headers <- if all null heads
diff --git a/src/Text/Pandoc/Writers/Man.hs b/src/Text/Pandoc/Writers/Man.hs
index 10ca961f8..d5e44e71a 100644
--- a/src/Text/Pandoc/Writers/Man.hs
+++ b/src/Text/Pandoc/Writers/Man.hs
@@ -161,7 +161,7 @@ blockToMan opts (Para inlines) = do
blockToMan _ (RawBlock "man" str) = return $ text str
blockToMan _ (RawBlock _ _) = return empty
blockToMan _ HorizontalRule = return $ text ".PP" $$ text " * * * * *"
-blockToMan opts (Header level inlines) = do
+blockToMan opts (Header level _ inlines) = do
contents <- inlineListToMan opts inlines
let heading = case level of
1 -> ".SH "
diff --git a/src/Text/Pandoc/Writers/Markdown.hs b/src/Text/Pandoc/Writers/Markdown.hs
index 384851c91..adefbb2b5 100644
--- a/src/Text/Pandoc/Writers/Markdown.hs
+++ b/src/Text/Pandoc/Writers/Markdown.hs
@@ -274,7 +274,7 @@ blockToMarkdown opts (RawBlock f str)
blockToMarkdown _ (RawBlock _ _) = return empty
blockToMarkdown _ HorizontalRule =
return $ blankline <> text "* * * * *" <> blankline
-blockToMarkdown opts (Header level inlines) = do
+blockToMarkdown opts (Header level attr inlines) = do
contents <- inlineListToMarkdown opts inlines
st <- get
let setext = writerSetextHeaders opts
diff --git a/src/Text/Pandoc/Writers/MediaWiki.hs b/src/Text/Pandoc/Writers/MediaWiki.hs
index 01fc49a10..a71d7ee7e 100644
--- a/src/Text/Pandoc/Writers/MediaWiki.hs
+++ b/src/Text/Pandoc/Writers/MediaWiki.hs
@@ -104,7 +104,7 @@ blockToMediaWiki _ (RawBlock _ _) = return ""
blockToMediaWiki _ HorizontalRule = return "\n-----\n"
-blockToMediaWiki opts (Header level inlines) = do
+blockToMediaWiki opts (Header level _ inlines) = do
contents <- inlineListToMediaWiki opts inlines
let eqs = replicate level '='
return $ eqs ++ " " ++ contents ++ " " ++ eqs ++ "\n"
diff --git a/src/Text/Pandoc/Writers/OpenDocument.hs b/src/Text/Pandoc/Writers/OpenDocument.hs
index 027ddfda1..b59e096c9 100644
--- a/src/Text/Pandoc/Writers/OpenDocument.hs
+++ b/src/Text/Pandoc/Writers/OpenDocument.hs
@@ -287,7 +287,7 @@ blockToOpenDocument :: WriterOptions -> Block -> State WriterState Doc
blockToOpenDocument o bs
| Plain b <- bs = inParagraphTags =<< inlinesToOpenDocument o b
| Para b <- bs = inParagraphTags =<< inlinesToOpenDocument o b
- | Header i b <- bs = setFirstPara >>
+ | Header i _ b <- bs = setFirstPara >>
(inHeaderTags i =<< inlinesToOpenDocument o b)
| BlockQuote b <- bs = setFirstPara >> mkBlockQuote b
| DefinitionList b <- bs = setFirstPara >> defList b
diff --git a/src/Text/Pandoc/Writers/Org.hs b/src/Text/Pandoc/Writers/Org.hs
index 86b570c30..894d4afa0 100644
--- a/src/Text/Pandoc/Writers/Org.hs
+++ b/src/Text/Pandoc/Writers/Org.hs
@@ -131,7 +131,7 @@ blockToOrg (RawBlock f str) | f == "org" || f == "latex" || f == "tex" =
return $ text str
blockToOrg (RawBlock _ _) = return empty
blockToOrg HorizontalRule = return $ blankline $$ "--------------" $$ blankline
-blockToOrg (Header level inlines) = do
+blockToOrg (Header level _ inlines) = do
contents <- inlineListToOrg inlines
let headerStr = text $ if level > 999 then " " else replicate level '*'
return $ headerStr <> " " <> contents <> blankline
diff --git a/src/Text/Pandoc/Writers/RST.hs b/src/Text/Pandoc/Writers/RST.hs
index 40939c6b7..85ca98f5a 100644
--- a/src/Text/Pandoc/Writers/RST.hs
+++ b/src/Text/Pandoc/Writers/RST.hs
@@ -161,7 +161,7 @@ blockToRST (RawBlock f str) =
(nest 3 $ text str) $$ blankline
blockToRST HorizontalRule =
return $ blankline $$ "--------------" $$ blankline
-blockToRST (Header level inlines) = do
+blockToRST (Header level _ inlines) = do
contents <- inlineListToRST inlines
let headerChar = if level > 5 then ' ' else "=-~^'" !! (level - 1)
let border = text $ replicate (offset contents) headerChar
diff --git a/src/Text/Pandoc/Writers/RTF.hs b/src/Text/Pandoc/Writers/RTF.hs
index 619e7086f..f2a271c1d 100644
--- a/src/Text/Pandoc/Writers/RTF.hs
+++ b/src/Text/Pandoc/Writers/RTF.hs
@@ -72,7 +72,7 @@ writeRTF options (Pandoc (Meta title authors date) blocks) =
datetext = inlineListToRTF date
spacer = not $ all null $ titletext : datetext : authorstext
body = concatMap (blockToRTF 0 AlignDefault) blocks
- isTOCHeader (Header lev _) = lev <= writerTOCDepth options
+ isTOCHeader (Header lev _ _) = lev <= writerTOCDepth options
isTOCHeader _ = False
context = writerVariables options ++
[ ("body", body)
@@ -91,7 +91,7 @@ tableOfContents :: [Block] -> String
tableOfContents headers =
let contentsTree = hierarchicalize headers
in concatMap (blockToRTF 0 AlignDefault) $
- [Header 1 [Str "Contents"],
+ [Header 1 nullAttr [Str "Contents"],
BulletList (map elementToListItem contentsTree)]
elementToListItem :: Element -> [Block]
@@ -208,7 +208,7 @@ blockToRTF indent alignment (DefinitionList lst) = spaceAtEnd $
concatMap (definitionListItemToRTF alignment indent) lst
blockToRTF indent _ HorizontalRule =
rtfPar indent 0 AlignCenter "\\emdash\\emdash\\emdash\\emdash\\emdash"
-blockToRTF indent alignment (Header level lst) = rtfPar indent 0 alignment $
+blockToRTF indent alignment (Header level _ lst) = rtfPar indent 0 alignment $
"\\b \\fs" ++ (show (40 - (level * 4))) ++ " " ++ inlineListToRTF lst
blockToRTF indent alignment (Table caption aligns sizes headers rows) =
(if all null headers
diff --git a/src/Text/Pandoc/Writers/Texinfo.hs b/src/Text/Pandoc/Writers/Texinfo.hs
index 4c29b410d..03e08c463 100644
--- a/src/Text/Pandoc/Writers/Texinfo.hs
+++ b/src/Text/Pandoc/Writers/Texinfo.hs
@@ -64,7 +64,7 @@ writeTexinfo options document =
-- | Add a "Top" node around the document, needed by Texinfo.
wrapTop :: Pandoc -> Pandoc
wrapTop (Pandoc (Meta title authors date) blocks) =
- Pandoc (Meta title authors date) (Header 0 title : blocks)
+ Pandoc (Meta title authors date) (Header 0 nullAttr title : blocks)
pandocToTexinfo :: WriterOptions -> Pandoc -> State WriterState String
pandocToTexinfo options (Pandoc (Meta title authors date) blocks) = do
@@ -195,14 +195,14 @@ blockToTexinfo HorizontalRule =
text (take 72 $ repeat '-') $$
text "@end ifnottex"
-blockToTexinfo (Header 0 lst) = do
+blockToTexinfo (Header 0 _ lst) = do
txt <- if null lst
then return $ text "Top"
else inlineListToTexinfo lst
return $ text "@node Top" $$
text "@top " <> txt <> blankline
-blockToTexinfo (Header level lst) = do
+blockToTexinfo (Header level _ lst) = do
node <- inlineListForNode lst
txt <- inlineListToTexinfo lst
idsUsed <- gets stIdentifiers
@@ -286,7 +286,7 @@ blockListToTexinfo [] = return empty
blockListToTexinfo (x:xs) = do
x' <- blockToTexinfo x
case x of
- Header level _ -> do
+ Header level _ _ -> do
-- We need need to insert a menu for this node.
let (before, after) = break isHeader xs
before' <- blockListToTexinfo before
@@ -311,14 +311,14 @@ blockListToTexinfo (x:xs) = do
return $ x' $$ xs'
isHeader :: Block -> Bool
-isHeader (Header _ _) = True
-isHeader _ = False
+isHeader (Header _ _ _) = True
+isHeader _ = False
collectNodes :: Int -> [Block] -> [Block]
collectNodes _ [] = []
collectNodes level (x:xs) =
case x of
- (Header hl _) ->
+ (Header hl _ _) ->
if hl < level
then []
else if hl == level
@@ -329,7 +329,7 @@ collectNodes level (x:xs) =
makeMenuLine :: Block
-> State WriterState Doc
-makeMenuLine (Header _ lst) = do
+makeMenuLine (Header _ _ lst) = do
txt <- inlineListForNode lst
return $ text "* " <> txt <> text "::"
makeMenuLine _ = error "makeMenuLine called with non-Header block"
diff --git a/src/Text/Pandoc/Writers/Textile.hs b/src/Text/Pandoc/Writers/Textile.hs
index 44fdc7efb..1f5d3e79d 100644
--- a/src/Text/Pandoc/Writers/Textile.hs
+++ b/src/Text/Pandoc/Writers/Textile.hs
@@ -121,9 +121,10 @@ blockToTextile _ (RawBlock f str) =
blockToTextile _ HorizontalRule = return "<hr />\n"
-blockToTextile opts (Header level inlines) = do
+blockToTextile opts (Header level (ident,_,_) inlines) = do
contents <- inlineListToTextile opts inlines
- let prefix = 'h' : (show level ++ ". ")
+ let attribs = if null ident then "" else "(#" ++ ident ++ ")"
+ let prefix = 'h' : show level ++ attribs ++ ". "
return $ prefix ++ contents ++ "\n"
blockToTextile _ (CodeBlock (_,classes,_) str) | any (all isSpace) (lines str) =