hierarchicalize: Do not number section with class "unnumbered".
Unnumbered sections get [] for their section number. So far only the HTML writer has been adjusted to be sensitive to this. If we keep this change, all the writers will need to be changed either (a) to directly check for the "unnumbered" class, if they do section numbering themselves, or (b) to check for a null section number, if they use hierarchicalize.
This commit is contained in:
parent
1a22709ff9
commit
cdee226586
2 changed files with 14 additions and 12 deletions
|
@ -92,7 +92,7 @@ import Text.Pandoc.MIME (getMimeType)
|
||||||
import System.FilePath ( (</>), takeExtension, dropExtension )
|
import System.FilePath ( (</>), takeExtension, dropExtension )
|
||||||
import Data.Generics (Typeable, Data)
|
import Data.Generics (Typeable, Data)
|
||||||
import qualified Control.Monad.State as S
|
import qualified Control.Monad.State as S
|
||||||
import Control.Monad (msum)
|
import Control.Monad (msum, unless)
|
||||||
import Text.Pandoc.Pretty (charWidth)
|
import Text.Pandoc.Pretty (charWidth)
|
||||||
import System.Locale (defaultTimeLocale)
|
import System.Locale (defaultTimeLocale)
|
||||||
import Data.Time
|
import Data.Time
|
||||||
|
@ -435,13 +435,15 @@ hierarchicalize blocks = S.evalState (hierarchicalizeWithIds blocks) []
|
||||||
|
|
||||||
hierarchicalizeWithIds :: [Block] -> S.State [Int] [Element]
|
hierarchicalizeWithIds :: [Block] -> S.State [Int] [Element]
|
||||||
hierarchicalizeWithIds [] = return []
|
hierarchicalizeWithIds [] = return []
|
||||||
hierarchicalizeWithIds ((Header level attr title'):xs) = do
|
hierarchicalizeWithIds ((Header level attr@(_,classes,_) title'):xs) = do
|
||||||
lastnum <- S.get
|
lastnum <- S.get
|
||||||
let lastnum' = take level lastnum
|
let lastnum' = take level lastnum
|
||||||
let newnum = if length lastnum' >= level
|
let newnum = case length lastnum' of
|
||||||
then init lastnum' ++ [last lastnum' + 1]
|
x | "unnumbered" `elem` classes -> []
|
||||||
else lastnum ++ replicate (level - length lastnum - 1) 0 ++ [1]
|
| x >= level -> init lastnum' ++ [last lastnum' + 1]
|
||||||
S.put newnum
|
| otherwise -> lastnum ++
|
||||||
|
replicate (level - length lastnum - 1) 0 ++ [1]
|
||||||
|
unless (null newnum) $ S.put newnum
|
||||||
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
|
||||||
|
|
|
@ -252,9 +252,9 @@ showSecNum = concat . intersperse "." . map show
|
||||||
elementToListItem :: WriterOptions -> Element -> State WriterState (Maybe Html)
|
elementToListItem :: WriterOptions -> Element -> State WriterState (Maybe Html)
|
||||||
elementToListItem opts (Sec lev num (id',classes,keyvals) headerText subsecs)
|
elementToListItem opts (Sec lev num (id',classes,keyvals) headerText subsecs)
|
||||||
| lev <= writerTOCDepth opts = do
|
| lev <= writerTOCDepth opts = do
|
||||||
let sectnum = if writerNumberSections opts
|
let sectnum = if writerNumberSections opts && not (null num)
|
||||||
then (H.span ! A.class_ "toc-section-number" $ toHtml $ showSecNum num) >>
|
then (H.span ! A.class_ "toc-section-number"
|
||||||
preEscapedString " "
|
$ toHtml $ showSecNum num) >> preEscapedString " "
|
||||||
else mempty
|
else mempty
|
||||||
txt <- liftM (sectnum >>) $ inlineListToHtml opts headerText
|
txt <- liftM (sectnum >>) $ inlineListToHtml opts headerText
|
||||||
subHeads <- mapM (elementToListItem opts) subsecs >>= return . catMaybes
|
subHeads <- mapM (elementToListItem opts) subsecs >>= return . catMaybes
|
||||||
|
@ -453,9 +453,9 @@ blockToHtml opts (BlockQuote blocks) =
|
||||||
blockToHtml opts (Header level (ident,_,_) lst) = do
|
blockToHtml opts (Header level (ident,_,_) lst) = do
|
||||||
contents <- inlineListToHtml opts lst
|
contents <- inlineListToHtml opts lst
|
||||||
secnum <- liftM stSecNum get
|
secnum <- liftM stSecNum get
|
||||||
let contents' = if writerNumberSections opts
|
let contents' = if writerNumberSections opts && not (null secnum)
|
||||||
then (H.span ! A.class_ "header-section-number" $ toHtml $ showSecNum secnum) >>
|
then (H.span ! A.class_ "header-section-number" $ toHtml
|
||||||
strToHtml " " >> contents
|
$ showSecNum secnum) >> strToHtml " " >> contents
|
||||||
else contents
|
else contents
|
||||||
let contents'' = if writerTableOfContents opts && not (null ident)
|
let contents'' = if writerTableOfContents opts && not (null ident)
|
||||||
then H.a ! A.href (toValue $
|
then H.a ! A.href (toValue $
|
||||||
|
|
Loading…
Reference in a new issue