aboutsummaryrefslogtreecommitdiff
path: root/src/Text/Pandoc/Writers/EPUB.hs
diff options
context:
space:
mode:
authorJesse Rosenthal <jrosenthal@jhu.edu>2016-11-26 08:46:28 -0500
committerJohn MacFarlane <jgm@berkeley.edu>2017-01-25 17:07:39 +0100
commit04487779b26458597fb751325b24c576b5088662 (patch)
tree0ee34da90dcfaee63b821ac68f8e0a40267d616a /src/Text/Pandoc/Writers/EPUB.hs
parentb19f79f672c49322328584fa339215e4234d98af (diff)
downloadpandoc-04487779b26458597fb751325b24c576b5088662.tar.gz
Convert all writers to use PandocMonad.
Since PandocMonad is an instance of MonadError, this will allow us, in a future commit, to change all invocations of `error` to `throwError`, which will be preferable for the pure versions. At the moment, we're disabling the lua custom writers (this is temporary). This requires changing the type of the Writer in Text.Pandoc. Right now, we run `runIOorExplode` in pandoc.hs, to make the conversion easier. We can switch it to the safer `runIO` in the future. Note that this required a change to Text.Pandoc.PDF as well. Since running an external program is necessarily IO, we can be clearer about using PandocIO.
Diffstat (limited to 'src/Text/Pandoc/Writers/EPUB.hs')
-rw-r--r--src/Text/Pandoc/Writers/EPUB.hs44
1 files changed, 22 insertions, 22 deletions
diff --git a/src/Text/Pandoc/Writers/EPUB.hs b/src/Text/Pandoc/Writers/EPUB.hs
index 397aa5847..298561db6 100644
--- a/src/Text/Pandoc/Writers/EPUB.hs
+++ b/src/Text/Pandoc/Writers/EPUB.hs
@@ -55,7 +55,7 @@ import Text.Pandoc.Definition
import Text.Pandoc.Walk (walk, walkM, query)
import Text.Pandoc.UUID (getUUID)
import Control.Monad.State (modify, get, gets, State, StateT, put, evalState, evalStateT, lift)
-import Control.Monad (mplus, when)
+import Control.Monad (mplus, when, zipWithM)
import Text.XML.Light ( unode, Element(..), unqual, Attr(..), add_attrs
, strContent, lookupAttr, Node(..), QName(..), parseXML
, onlyElems, node, ppElement)
@@ -374,17 +374,17 @@ pandocToEPUB opts doc@(Pandoc meta _) = do
Nothing -> return ([],[])
Just img -> do
let coverImage = "media/" ++ takeFileName img
- let cpContent = renderHtml $ writeHtml
+ cpContent <- renderHtml <$> (lift $ writeHtml
opts'{ writerVariables = ("coverpage","true"):vars }
- (Pandoc meta [RawBlock (Format "html") $ "<div id=\"cover-image\">\n<img src=\"" ++ coverImage ++ "\" alt=\"cover image\" />\n</div>"])
+ (Pandoc meta [RawBlock (Format "html") $ "<div id=\"cover-image\">\n<img src=\"" ++ coverImage ++ "\" alt=\"cover image\" />\n</div>"]))
imgContent <- lift $ P.readFileLazy img
return ( [mkEntry "cover.xhtml" cpContent]
, [mkEntry coverImage imgContent] )
-- title page
- let tpContent = renderHtml $ writeHtml opts'{
- writerVariables = ("titlepage","true"):vars }
- (Pandoc meta [])
+ tpContent <- renderHtml <$> (lift $ writeHtml opts'{
+ writerVariables = ("titlepage","true"):vars }
+ (Pandoc meta []))
let tpEntry = mkEntry "title_page.xhtml" tpContent
-- handle pictures
@@ -482,20 +482,20 @@ pandocToEPUB opts doc@(Pandoc meta _) = do
Chapter mbnum $ walk fixInternalReferences bs)
chapters'
- let chapToEntry :: Int -> Chapter -> Entry
- chapToEntry num (Chapter mbnum bs) = mkEntry (showChapter num)
- $ renderHtml
- $ writeHtml opts'{ writerNumberOffset =
- fromMaybe [] mbnum }
- $ case bs of
- (Header _ _ xs : _) ->
- -- remove notes or we get doubled footnotes
- Pandoc (setMeta "title" (walk removeNote $ fromList xs)
- nullMeta) bs
- _ ->
- Pandoc nullMeta bs
-
- let chapterEntries = zipWith chapToEntry [1..] chapters
+ let chapToEntry :: PandocMonad m => Int -> Chapter -> m Entry
+ chapToEntry num (Chapter mbnum bs) =
+ (mkEntry (showChapter num) . renderHtml) <$>
+ (writeHtml opts'{ writerNumberOffset =
+ fromMaybe [] mbnum }
+ $ case bs of
+ (Header _ _ xs : _) ->
+ -- remove notes or we get doubled footnotes
+ Pandoc (setMeta "title" (walk removeNote $ fromList xs)
+ nullMeta) bs
+ _ ->
+ Pandoc nullMeta bs)
+
+ chapterEntries <- lift $ zipWithM chapToEntry [1..] chapters
-- incredibly inefficient (TODO):
let containsMathML ent = epub3 &&
@@ -679,11 +679,11 @@ pandocToEPUB opts doc@(Pandoc meta _) = do
]
]
else []
- let navData = renderHtml $ writeHtml
+ navData <- renderHtml <$> (lift $ writeHtml
opts'{ writerVariables = ("navpage","true"):vars }
(Pandoc (setMeta "title"
(walk removeNote $ fromList $ docTitle' meta) nullMeta)
- (navBlocks ++ landmarks))
+ (navBlocks ++ landmarks)))
let navEntry = mkEntry "nav.xhtml" navData
-- mimetype