Removed links (internal and external).

This commit is contained in:
John MacFarlane 2010-07-04 18:40:51 -07:00
parent f895ee2e48
commit 6a7b16eb4d

View file

@ -79,7 +79,7 @@ writeEPUB sourceDir stylesheet opts doc = do
-- handle pictures -- handle pictures
picEntriesRef <- newIORef ([] :: [Entry]) picEntriesRef <- newIORef ([] :: [Entry])
Pandoc meta blocks <- liftM (processWith transformBlock) $ Pandoc meta blocks <- liftM (processWith transformBlock) $
processWithM (transformInline (writerHTMLMathMethod opts) processWithM (transformInlines (writerHTMLMathMethod opts)
sourceDir picEntriesRef) doc sourceDir picEntriesRef) doc
picEntries <- readIORef picEntriesRef picEntries <- readIORef picEntriesRef
-- body pages -- body pages
@ -186,21 +186,21 @@ metadataElement metadataXML uuid lang title authors =
[ unode "dc:creator" ! [("opf:role","aut")] $ a | a <- authors ] [ unode "dc:creator" ! [("opf:role","aut")] $ a | a <- authors ]
in elt{ elContent = elContent elt ++ map Elem newNodes } in elt{ elContent = elContent elt ++ map Elem newNodes }
transformInline :: HTMLMathMethod transformInlines :: HTMLMathMethod
-> FilePath -> FilePath
-> IORef [Entry] -> IORef [Entry]
-> Inline -> [Inline]
-> IO Inline -> IO [Inline]
transformInline _ _ _ (Image lab (src,_)) | isNothing (imageTypeOf src) = transformInlines _ _ _ (Image lab (src,_) : xs) | isNothing (imageTypeOf src) =
return (Emph lab) return $ Emph lab : xs
transformInline _ sourceDir picsRef (Image lab (src,tit)) = do transformInlines _ sourceDir picsRef (Image lab (src,tit) : xs) = do
entries <- readIORef picsRef entries <- readIORef picsRef
let newsrc = "images/img" ++ show (length entries) ++ takeExtension src let newsrc = "images/img" ++ show (length entries) ++ takeExtension src
catch (readEntry [] (sourceDir </> src) >>= \entry -> catch (readEntry [] (sourceDir </> src) >>= \entry ->
modifyIORef picsRef (entry{ eRelativePath = newsrc } :) >> modifyIORef picsRef (entry{ eRelativePath = newsrc } :) >>
return (Image lab (newsrc, tit))) return (Image lab (newsrc, tit) : xs))
(\_ -> return (Emph lab)) (\_ -> return (Emph lab : xs))
transformInline (MathML _) _ _ x@(Math _ _) = do transformInlines (MathML _) _ _ (x@(Math _ _) : xs) = do
let writeHtmlInline opts z = removeTrailingSpace $ let writeHtmlInline opts z = removeTrailingSpace $
writeHtmlString opts $ Pandoc (Meta [] [] []) [Plain [z]] writeHtmlString opts $ Pandoc (Meta [] [] []) [Plain [z]]
mathml = writeHtmlInline defaultWriterOptions{ mathml = writeHtmlInline defaultWriterOptions{
@ -211,9 +211,11 @@ transformInline (MathML _) _ _ x@(Math _ _) = do
"<ops:case required-namespace=\"http://www.w3.org/1998/Math/MathML\">" ++ "<ops:case required-namespace=\"http://www.w3.org/1998/Math/MathML\">" ++
mathml ++ "</ops:case><ops:default>" ++ fallback ++ "</ops:default>" ++ mathml ++ "</ops:case><ops:default>" ++ fallback ++ "</ops:default>" ++
"</ops:switch>" "</ops:switch>"
return $ HtmlInline $ if "<math" `isPrefixOf` mathml then inOps else mathml result = if "<math" `isPrefixOf` mathml then inOps else mathml
transformInline _ _ _ (HtmlInline _) = return $ Str "" return $ HtmlInline result : xs
transformInline _ _ _ x = return x transformInlines _ _ _ (HtmlInline _ : xs) = return $ Str "" : xs
transformInlines _ _ _ (Link lab (_,_) : xs) = return $ lab ++ xs
transformInlines mathmethod sourceDir picsRef xs = return xs
transformBlock :: Block -> Block transformBlock :: Block -> Block
transformBlock (RawHtml _) = Null transformBlock (RawHtml _) = Null