aboutsummaryrefslogtreecommitdiff
path: root/src/Text/Pandoc/Writers
diff options
context:
space:
mode:
authorJohn MacFarlane <jgm@berkeley.edu>2015-01-17 11:27:49 -0800
committerJohn MacFarlane <jgm@berkeley.edu>2015-01-17 11:27:49 -0800
commit25e12ca7b20bc48fc5ff866a8427b08df7c1c71a (patch)
tree890aacb1e83dac7638d4ad3907970e2067764e34 /src/Text/Pandoc/Writers
parentc63020d5f2969b3c4a74b812097335de036a2b6c (diff)
downloadpandoc-25e12ca7b20bc48fc5ff866a8427b08df7c1c71a.tar.gz
EPUB writer: properly handle internal links to IDs in spans, divs.
Closes #1884.
Diffstat (limited to 'src/Text/Pandoc/Writers')
-rw-r--r--src/Text/Pandoc/Writers/EPUB.hs29
1 files changed, 18 insertions, 11 deletions
diff --git a/src/Text/Pandoc/Writers/EPUB.hs b/src/Text/Pandoc/Writers/EPUB.hs
index 212206ac6..cebbaa835 100644
--- a/src/Text/Pandoc/Writers/EPUB.hs
+++ b/src/Text/Pandoc/Writers/EPUB.hs
@@ -41,7 +41,7 @@ import qualified Data.ByteString.Lazy.Char8 as B8
import qualified Text.Pandoc.UTF8 as UTF8
import Text.Pandoc.SelfContained ( makeSelfContained )
import Codec.Archive.Zip ( emptyArchive, addEntryToArchive, eRelativePath, fromEntry , Entry, toEntry, fromArchive)
-import Control.Applicative ((<$>))
+import Control.Applicative ((<$>), (<$))
import Data.Time.Clock.POSIX ( getPOSIXTime )
import Data.Time (getCurrentTime,UTCTime, formatTime)
import Text.Pandoc.Compat.Locale ( defaultTimeLocale )
@@ -57,7 +57,7 @@ import Text.Pandoc.Options ( WriterOptions(..)
import Text.Pandoc.Definition
import Text.Pandoc.Walk (walk, walkM)
import Control.Monad.State (modify, get, execState, State, put, evalState)
-import Control.Monad (foldM, when, mplus, liftM)
+import Control.Monad (foldM, mplus, liftM)
import Text.XML.Light ( unode, Element(..), unqual, Attr(..), add_attrs
, strContent, lookupAttr, Node(..), QName(..), parseXML
, onlyElems, node, ppElement)
@@ -894,20 +894,27 @@ addIdentifiers bs = evalState (mapM go bs) []
-- was "header-1" might turn into "ch006.xhtml#header".
correlateRefs :: Int -> [Block] -> [(String,String)]
correlateRefs chapterHeaderLevel bs =
- identTable $ execState (mapM_ go bs)
+ identTable $ execState (walkM goBlock bs >>= walkM goInline)
IdentState{ chapterNumber = 0
, identTable = [] }
- where go :: Block -> State IdentState ()
- go (Header n (ident,_,_) _) = do
- when (n <= chapterHeaderLevel) $
- modify $ \s -> s{ chapterNumber = chapterNumber s + 1 }
+ where goBlock :: Block -> State IdentState Block
+ goBlock x@(Header n (ident,_,_) _) = x <$ addIdentifier (Just n) ident
+ goBlock x@(Div (ident,_,_) _) = x <$ addIdentifier Nothing ident
+ goBlock x = return x
+ goInline :: Inline -> State IdentState Inline
+ goInline x@(Span (ident,_,_) _) = x <$ addIdentifier Nothing ident
+ goInline x = return x
+ addIdentifier mbHeaderLevel ident = do
+ case mbHeaderLevel of
+ Just n | n <= chapterHeaderLevel ->
+ modify $ \s -> s{ chapterNumber = chapterNumber s + 1 }
+ _ -> return ()
st <- get
let chapterid = showChapter (chapterNumber st) ++
- if n <= chapterHeaderLevel
- then ""
- else '#' : ident
+ case mbHeaderLevel of
+ Just n | n <= chapterHeaderLevel -> ""
+ _ -> '#' : ident
modify $ \s -> s{ identTable = (ident, chapterid) : identTable st }
- go _ = return ()
-- Replace internal link references using the table produced
-- by correlateRefs.