aboutsummaryrefslogtreecommitdiff
path: root/src/Text/Pandoc/Shared.hs
diff options
context:
space:
mode:
authorfiddlosopher <fiddlosopher@788f1e2b-df1e-0410-8736-df70ead52e1b>2009-12-08 02:36:16 +0000
committerfiddlosopher <fiddlosopher@788f1e2b-df1e-0410-8736-df70ead52e1b>2009-12-08 02:36:16 +0000
commit2ced785e95e0799f3c8a705e828e6522e11a8a98 (patch)
tree5023d6cf6debc6971549a389ef98a12fd8a3955a /src/Text/Pandoc/Shared.hs
parent05436988950d271f8a55ee48b4d7794da9b40172 (diff)
downloadpandoc-2ced785e95e0799f3c8a705e828e6522e11a8a98.tar.gz
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
Diffstat (limited to 'src/Text/Pandoc/Shared.hs')
-rw-r--r--src/Text/Pandoc/Shared.hs18
1 files changed, 11 insertions, 7 deletions
diff --git a/src/Text/Pandoc/Shared.hs b/src/Text/Pandoc/Shared.hs
index 6f11d0200..c99fa3e9e 100644
--- a/src/Text/Pandoc/Shared.hs
+++ b/src/Text/Pandoc/Shared.hs
@@ -882,8 +882,8 @@ isPara _ = False
-- | Data structure for defining hierarchical Pandoc documents
data Element = Blk Block
- | Sec Int String [Inline] [Element]
- -- lvl ident label contents
+ | Sec Int [Int] String [Inline] [Element]
+ -- lvl num ident label contents
deriving (Eq, Read, Show, Typeable, Data)
-- | 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
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 ((Header level title'):xs) = do
- usedIdents <- S.get
+ (lastnum, usedIdents) <- S.get
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
sectionContents' <- hierarchicalizeWithIds sectionContents
rest' <- hierarchicalizeWithIds rest
- return $ Sec level ident title' sectionContents' : rest'
+ return $ Sec level newnum ident title' sectionContents' : rest'
hierarchicalizeWithIds (x:rest) = do
rest' <- hierarchicalizeWithIds rest
return $ (Blk x) : rest'