Added optional section numbering in HTML output.
This involves a change to the Element data structure, including a section number as well as an id and title for each section. Section numbers are lists of integers; this should allow different numbering schemes to be used in the future. Currently [1,2,3] -> 1.2.3. Resolves Issue #150. git-svn-id: https://pandoc.googlecode.com/svn/trunk@1658 788f1e2b-df1e-0410-8736-df70ead52e1b
This commit is contained in:
parent
0543698895
commit
2ced785e95
7 changed files with 33 additions and 19 deletions
4
README
4
README
|
@ -363,8 +363,8 @@ For further documentation, see the `pandoc(1)` man page.
|
||||||
displayed all at once.
|
displayed all at once.
|
||||||
|
|
||||||
`-N` or `--number-sections`
|
`-N` or `--number-sections`
|
||||||
: causes sections to be numbered in LaTeX or ConTeXt output. By default,
|
: causes sections to be numbered in LaTeX, ConTeXt, or HTML output.
|
||||||
sections are not numbered.
|
By default, sections are not numbered.
|
||||||
|
|
||||||
`--no-wrap`
|
`--no-wrap`
|
||||||
: disables text-wrapping in output. By default, text is wrapped
|
: disables text-wrapping in output. By default, text is wrapped
|
||||||
|
|
|
@ -134,8 +134,8 @@ to Pandoc. Or use `html2markdown`(1), a wrapper around `pandoc`.
|
||||||
: Make list items in S5 display incrementally (one by one).
|
: Make list items in S5 display incrementally (one by one).
|
||||||
|
|
||||||
-N, \--number-sections
|
-N, \--number-sections
|
||||||
: Number section headings in LaTeX output. (Default is not to number
|
: Number section headings in LaTeX, ConTeXt, or HTML output.
|
||||||
them.)
|
(Default is not to number them.)
|
||||||
|
|
||||||
\--no-wrap
|
\--no-wrap
|
||||||
: Disable text wrapping in output. (Default is to wrap text.)
|
: Disable text wrapping in output. (Default is to wrap text.)
|
||||||
|
|
|
@ -882,8 +882,8 @@ isPara _ = False
|
||||||
|
|
||||||
-- | Data structure for defining hierarchical Pandoc documents
|
-- | Data structure for defining hierarchical Pandoc documents
|
||||||
data Element = Blk Block
|
data Element = Blk Block
|
||||||
| Sec Int String [Inline] [Element]
|
| Sec Int [Int] String [Inline] [Element]
|
||||||
-- lvl ident label contents
|
-- lvl num ident label contents
|
||||||
deriving (Eq, Read, Show, Typeable, Data)
|
deriving (Eq, Read, Show, Typeable, Data)
|
||||||
|
|
||||||
-- | Convert Pandoc inline list to plain text identifier.
|
-- | Convert Pandoc inline list to plain text identifier.
|
||||||
|
@ -921,18 +921,22 @@ inlineListToIdentifier' (x:xs) =
|
||||||
|
|
||||||
-- | Convert list of Pandoc blocks into (hierarchical) list of Elements
|
-- | Convert list of Pandoc blocks into (hierarchical) list of Elements
|
||||||
hierarchicalize :: [Block] -> [Element]
|
hierarchicalize :: [Block] -> [Element]
|
||||||
hierarchicalize blocks = S.evalState (hierarchicalizeWithIds blocks) []
|
hierarchicalize blocks = S.evalState (hierarchicalizeWithIds blocks) ([],[])
|
||||||
|
|
||||||
hierarchicalizeWithIds :: [Block] -> S.State [String] [Element]
|
hierarchicalizeWithIds :: [Block] -> S.State ([Int],[String]) [Element]
|
||||||
hierarchicalizeWithIds [] = return []
|
hierarchicalizeWithIds [] = return []
|
||||||
hierarchicalizeWithIds ((Header level title'):xs) = do
|
hierarchicalizeWithIds ((Header level title'):xs) = do
|
||||||
usedIdents <- S.get
|
(lastnum, usedIdents) <- S.get
|
||||||
let ident = uniqueIdent title' usedIdents
|
let ident = uniqueIdent title' usedIdents
|
||||||
S.modify (ident :)
|
let lastnum' = take level lastnum
|
||||||
|
let newnum = if length lastnum' >= level
|
||||||
|
then init lastnum' ++ [last lastnum' + 1]
|
||||||
|
else lastnum ++ replicate (level - length lastnum - 1) 0 ++ [1]
|
||||||
|
S.put (newnum, (ident : usedIdents))
|
||||||
let (sectionContents, rest) = break (headerLtEq level) xs
|
let (sectionContents, rest) = break (headerLtEq level) xs
|
||||||
sectionContents' <- hierarchicalizeWithIds sectionContents
|
sectionContents' <- hierarchicalizeWithIds sectionContents
|
||||||
rest' <- hierarchicalizeWithIds rest
|
rest' <- hierarchicalizeWithIds rest
|
||||||
return $ Sec level ident title' sectionContents' : rest'
|
return $ Sec level newnum ident title' sectionContents' : rest'
|
||||||
hierarchicalizeWithIds (x:rest) = do
|
hierarchicalizeWithIds (x:rest) = do
|
||||||
rest' <- hierarchicalizeWithIds rest
|
rest' <- hierarchicalizeWithIds rest
|
||||||
return $ (Blk x) : rest'
|
return $ (Blk x) : rest'
|
||||||
|
|
|
@ -82,7 +82,7 @@ writeDocbook opts (Pandoc (Meta title authors date) blocks) =
|
||||||
-- | Convert an Element to Docbook.
|
-- | Convert an Element to Docbook.
|
||||||
elementToDocbook :: WriterOptions -> Element -> Doc
|
elementToDocbook :: WriterOptions -> Element -> Doc
|
||||||
elementToDocbook opts (Blk block) = blockToDocbook opts block
|
elementToDocbook opts (Blk block) = blockToDocbook opts block
|
||||||
elementToDocbook opts (Sec _ id' title elements) =
|
elementToDocbook opts (Sec _ _num id' title elements) =
|
||||||
-- Docbook doesn't allow sections with no content, so insert some if needed
|
-- Docbook doesn't allow sections with no content, so insert some if needed
|
||||||
let elements' = if null elements
|
let elements' = if null elements
|
||||||
then [Blk (Para [])]
|
then [Blk (Para [])]
|
||||||
|
|
|
@ -38,7 +38,7 @@ import Text.Pandoc.Highlighting ( highlightHtml, defaultHighlightingCss )
|
||||||
import Text.Pandoc.XML (stripTags)
|
import Text.Pandoc.XML (stripTags)
|
||||||
import Numeric ( showHex )
|
import Numeric ( showHex )
|
||||||
import Data.Char ( ord, toLower )
|
import Data.Char ( ord, toLower )
|
||||||
import Data.List ( isPrefixOf )
|
import Data.List ( isPrefixOf, intersperse )
|
||||||
import Data.Maybe ( catMaybes )
|
import Data.Maybe ( catMaybes )
|
||||||
import qualified Data.Set as S
|
import qualified Data.Set as S
|
||||||
import Control.Monad.State
|
import Control.Monad.State
|
||||||
|
@ -156,12 +156,19 @@ tableOfContents opts sects = do
|
||||||
contents <- mapM (elementToListItem opts') sects
|
contents <- mapM (elementToListItem opts') sects
|
||||||
return $ thediv ! [prefixedId opts' "TOC"] $ unordList $ catMaybes contents
|
return $ thediv ! [prefixedId opts' "TOC"] $ unordList $ catMaybes contents
|
||||||
|
|
||||||
|
-- | Convert section number to inline
|
||||||
|
showSecNum :: [Int] -> Inline
|
||||||
|
showSecNum = Str . concat . intersperse "." . map show
|
||||||
|
|
||||||
-- | Converts an Element to a list item for a table of contents,
|
-- | Converts an Element to a list item for a table of contents,
|
||||||
-- retrieving the appropriate identifier from state.
|
-- retrieving the appropriate identifier from state.
|
||||||
elementToListItem :: WriterOptions -> Element -> State WriterState (Maybe Html)
|
elementToListItem :: WriterOptions -> Element -> State WriterState (Maybe Html)
|
||||||
elementToListItem _ (Blk _) = return Nothing
|
elementToListItem _ (Blk _) = return Nothing
|
||||||
elementToListItem opts (Sec _ id' headerText subsecs) = do
|
elementToListItem opts (Sec _ num id' headerText subsecs) = do
|
||||||
txt <- inlineListToHtml opts headerText
|
let headerText' = if writerNumberSections opts
|
||||||
|
then showSecNum num : Space : headerText
|
||||||
|
else headerText
|
||||||
|
txt <- inlineListToHtml opts headerText'
|
||||||
subHeads <- mapM (elementToListItem opts) subsecs >>= return . catMaybes
|
subHeads <- mapM (elementToListItem opts) subsecs >>= return . catMaybes
|
||||||
let subList = if null subHeads
|
let subList = if null subHeads
|
||||||
then noHtml
|
then noHtml
|
||||||
|
@ -171,9 +178,12 @@ elementToListItem opts (Sec _ id' headerText subsecs) = do
|
||||||
-- | Convert an Element to Html.
|
-- | Convert an Element to Html.
|
||||||
elementToHtml :: WriterOptions -> Element -> State WriterState Html
|
elementToHtml :: WriterOptions -> Element -> State WriterState Html
|
||||||
elementToHtml opts (Blk block) = blockToHtml opts block
|
elementToHtml opts (Blk block) = blockToHtml opts block
|
||||||
elementToHtml opts (Sec level id' title' elements) = do
|
elementToHtml opts (Sec level num id' title' elements) = do
|
||||||
innerContents <- mapM (elementToHtml opts) elements
|
innerContents <- mapM (elementToHtml opts) elements
|
||||||
header' <- blockToHtml opts (Header level title')
|
let title'' = if writerNumberSections opts
|
||||||
|
then showSecNum num : Space : title'
|
||||||
|
else title'
|
||||||
|
header' <- blockToHtml opts (Header level title'')
|
||||||
return $ if writerS5 opts || (writerStrictMarkdown opts && not (writerTableOfContents opts))
|
return $ if writerS5 opts || (writerStrictMarkdown opts && not (writerTableOfContents opts))
|
||||||
-- S5 gets confused by the extra divs around sections
|
-- S5 gets confused by the extra divs around sections
|
||||||
then toHtmlFromList (header' : innerContents)
|
then toHtmlFromList (header' : innerContents)
|
||||||
|
|
|
@ -138,7 +138,7 @@ tableOfContents opts headers =
|
||||||
-- | Converts an Element to a list item for a table of contents,
|
-- | Converts an Element to a list item for a table of contents,
|
||||||
elementToListItem :: Element -> [Block]
|
elementToListItem :: Element -> [Block]
|
||||||
elementToListItem (Blk _) = []
|
elementToListItem (Blk _) = []
|
||||||
elementToListItem (Sec _ _ headerText subsecs) = [Plain headerText] ++
|
elementToListItem (Sec _ _ _ headerText subsecs) = [Plain headerText] ++
|
||||||
if null subsecs
|
if null subsecs
|
||||||
then []
|
then []
|
||||||
else [BulletList $ map elementToListItem subsecs]
|
else [BulletList $ map elementToListItem subsecs]
|
||||||
|
|
|
@ -59,7 +59,7 @@ tableOfContents headers =
|
||||||
|
|
||||||
elementToListItem :: Element -> [Block]
|
elementToListItem :: Element -> [Block]
|
||||||
elementToListItem (Blk _) = []
|
elementToListItem (Blk _) = []
|
||||||
elementToListItem (Sec _ _ sectext subsecs) = [Plain sectext] ++
|
elementToListItem (Sec _ _ _ sectext subsecs) = [Plain sectext] ++
|
||||||
if null subsecs
|
if null subsecs
|
||||||
then []
|
then []
|
||||||
else [BulletList (map elementToListItem subsecs)]
|
else [BulletList (map elementToListItem subsecs)]
|
||||||
|
|
Loading…
Reference in a new issue