HTML writer: Don't include TOC div if table of contents is empty.
git-svn-id: https://pandoc.googlecode.com/svn/trunk@1922 788f1e2b-df1e-0410-8736-df70ead52e1b
This commit is contained in:
parent
bdd5ec37ae
commit
1547728d7e
1 changed files with 11 additions and 10 deletions
|
@ -88,7 +88,7 @@ writeHtml opts d =
|
||||||
-- result is (title, authors, date, toc, body, new variables)
|
-- result is (title, authors, date, toc, body, new variables)
|
||||||
pandocToHtml :: WriterOptions
|
pandocToHtml :: WriterOptions
|
||||||
-> Pandoc
|
-> Pandoc
|
||||||
-> State WriterState (Html, [Html], Html, Html, Html, [(String,String)])
|
-> State WriterState (Html, [Html], Html, Maybe Html, Html, [(String,String)])
|
||||||
pandocToHtml opts (Pandoc (Meta title' authors' date') blocks) = do
|
pandocToHtml opts (Pandoc (Meta title' authors' date') blocks) = do
|
||||||
let standalone = writerStandalone opts
|
let standalone = writerStandalone opts
|
||||||
tit <- if standalone
|
tit <- if standalone
|
||||||
|
@ -103,7 +103,7 @@ pandocToHtml opts (Pandoc (Meta title' authors' date') blocks) = do
|
||||||
let sects = hierarchicalize blocks
|
let sects = hierarchicalize blocks
|
||||||
toc <- if writerTableOfContents opts
|
toc <- if writerTableOfContents opts
|
||||||
then tableOfContents opts sects
|
then tableOfContents opts sects
|
||||||
else return noHtml
|
else return Nothing
|
||||||
blocks' <- liftM toHtmlFromList $ mapM (elementToHtml opts) sects
|
blocks' <- liftM toHtmlFromList $ mapM (elementToHtml opts) sects
|
||||||
st <- get
|
st <- get
|
||||||
let notes = reverse (stNotes st)
|
let notes = reverse (stNotes st)
|
||||||
|
@ -134,7 +134,7 @@ inTemplate :: TemplateTarget a
|
||||||
-> Html
|
-> Html
|
||||||
-> [Html]
|
-> [Html]
|
||||||
-> Html
|
-> Html
|
||||||
-> Html
|
-> Maybe Html
|
||||||
-> Html
|
-> Html
|
||||||
-> [(String,String)]
|
-> [(String,String)]
|
||||||
-> a
|
-> a
|
||||||
|
@ -147,9 +147,11 @@ inTemplate opts tit auths date toc body' newvars =
|
||||||
context = variables ++
|
context = variables ++
|
||||||
[ ("body", renderHtmlFragment body')
|
[ ("body", renderHtmlFragment body')
|
||||||
, ("pagetitle", topTitle')
|
, ("pagetitle", topTitle')
|
||||||
, ("toc", renderHtmlFragment toc)
|
|
||||||
, ("title", renderHtmlFragment tit)
|
, ("title", renderHtmlFragment tit)
|
||||||
, ("date", date') ] ++
|
, ("date", date') ] ++
|
||||||
|
(case toc of
|
||||||
|
Just t -> [ ("toc", renderHtmlFragment t)]
|
||||||
|
Nothing -> []) ++
|
||||||
[ ("author", a) | a <- authors ]
|
[ ("author", a) | a <- authors ]
|
||||||
in renderTemplate context $ writerTemplate opts
|
in renderTemplate context $ writerTemplate opts
|
||||||
|
|
||||||
|
@ -158,16 +160,15 @@ prefixedId :: WriterOptions -> String -> HtmlAttr
|
||||||
prefixedId opts s = identifier $ writerIdentifierPrefix opts ++ s
|
prefixedId opts s = identifier $ writerIdentifierPrefix opts ++ s
|
||||||
|
|
||||||
-- | Construct table of contents from list of elements.
|
-- | Construct table of contents from list of elements.
|
||||||
tableOfContents :: WriterOptions -> [Element] -> State WriterState Html
|
tableOfContents :: WriterOptions -> [Element] -> State WriterState (Maybe Html)
|
||||||
tableOfContents _ [] = return noHtml
|
tableOfContents _ [] = return Nothing
|
||||||
tableOfContents opts sects = do
|
tableOfContents opts sects = do
|
||||||
let opts' = opts { writerIgnoreNotes = True }
|
let opts' = opts { writerIgnoreNotes = True }
|
||||||
contents <- mapM (elementToListItem opts') sects
|
contents <- mapM (elementToListItem opts') sects
|
||||||
let tocList = catMaybes contents
|
let tocList = catMaybes contents
|
||||||
return $ thediv ! [prefixedId opts' "TOC"] $
|
return $ if null tocList
|
||||||
if null tocList
|
then Nothing
|
||||||
then noHtml
|
else Just $ thediv ! [prefixedId opts' "TOC"] $ unordList tocList
|
||||||
else unordList tocList
|
|
||||||
|
|
||||||
-- | Convert section number to string
|
-- | Convert section number to string
|
||||||
showSecNum :: [Int] -> String
|
showSecNum :: [Int] -> String
|
||||||
|
|
Loading…
Reference in a new issue