diff options
author | John MacFarlane <jgm@berkeley.edu> | 2010-07-04 18:40:51 -0700 |
---|---|---|
committer | John MacFarlane <jgm@berkeley.edu> | 2010-07-05 00:06:27 -0700 |
commit | 6a7b16eb4d94683d1e3844b6296e5743e72deccc (patch) | |
tree | 6c5ccdbfc938e966a3dec52736253939a0795bd0 | |
parent | f895ee2e48d06c498e8f309ce6be0aeb72352baa (diff) | |
download | pandoc-6a7b16eb4d94683d1e3844b6296e5743e72deccc.tar.gz |
Removed links (internal and external).
-rw-r--r-- | src/Text/Pandoc/Writers/EPUB.hs | 32 |
1 files changed, 17 insertions, 15 deletions
diff --git a/src/Text/Pandoc/Writers/EPUB.hs b/src/Text/Pandoc/Writers/EPUB.hs index 4f8bd36f3..2e8f37091 100644 --- a/src/Text/Pandoc/Writers/EPUB.hs +++ b/src/Text/Pandoc/Writers/EPUB.hs @@ -79,7 +79,7 @@ writeEPUB sourceDir stylesheet opts doc = do -- handle pictures picEntriesRef <- newIORef ([] :: [Entry]) Pandoc meta blocks <- liftM (processWith transformBlock) $ - processWithM (transformInline (writerHTMLMathMethod opts) + processWithM (transformInlines (writerHTMLMathMethod opts) sourceDir picEntriesRef) doc picEntries <- readIORef picEntriesRef -- body pages @@ -186,21 +186,21 @@ metadataElement metadataXML uuid lang title authors = [ unode "dc:creator" ! [("opf:role","aut")] $ a | a <- authors ] in elt{ elContent = elContent elt ++ map Elem newNodes } -transformInline :: HTMLMathMethod - -> FilePath - -> IORef [Entry] - -> Inline - -> IO Inline -transformInline _ _ _ (Image lab (src,_)) | isNothing (imageTypeOf src) = - return (Emph lab) -transformInline _ sourceDir picsRef (Image lab (src,tit)) = do +transformInlines :: HTMLMathMethod + -> FilePath + -> IORef [Entry] + -> [Inline] + -> IO [Inline] +transformInlines _ _ _ (Image lab (src,_) : xs) | isNothing (imageTypeOf src) = + return $ Emph lab : xs +transformInlines _ sourceDir picsRef (Image lab (src,tit) : xs) = do entries <- readIORef picsRef let newsrc = "images/img" ++ show (length entries) ++ takeExtension src catch (readEntry [] (sourceDir </> src) >>= \entry -> modifyIORef picsRef (entry{ eRelativePath = newsrc } :) >> - return (Image lab (newsrc, tit))) - (\_ -> return (Emph lab)) -transformInline (MathML _) _ _ x@(Math _ _) = do + return (Image lab (newsrc, tit) : xs)) + (\_ -> return (Emph lab : xs)) +transformInlines (MathML _) _ _ (x@(Math _ _) : xs) = do let writeHtmlInline opts z = removeTrailingSpace $ writeHtmlString opts $ Pandoc (Meta [] [] []) [Plain [z]] mathml = writeHtmlInline defaultWriterOptions{ @@ -211,9 +211,11 @@ transformInline (MathML _) _ _ x@(Math _ _) = do "<ops:case required-namespace=\"http://www.w3.org/1998/Math/MathML\">" ++ mathml ++ "</ops:case><ops:default>" ++ fallback ++ "</ops:default>" ++ "</ops:switch>" - return $ HtmlInline $ if "<math" `isPrefixOf` mathml then inOps else mathml -transformInline _ _ _ (HtmlInline _) = return $ Str "" -transformInline _ _ _ x = return x + result = if "<math" `isPrefixOf` mathml then inOps else mathml + return $ HtmlInline result : xs +transformInlines _ _ _ (HtmlInline _ : xs) = return $ Str "" : xs +transformInlines _ _ _ (Link lab (_,_) : xs) = return $ lab ++ xs +transformInlines mathmethod sourceDir picsRef xs = return xs transformBlock :: Block -> Block transformBlock (RawHtml _) = Null |