aboutsummaryrefslogtreecommitdiff
path: root/src/Text/Pandoc/Writers
diff options
context:
space:
mode:
Diffstat (limited to 'src/Text/Pandoc/Writers')
-rw-r--r--src/Text/Pandoc/Writers/Docbook.hs8
-rw-r--r--src/Text/Pandoc/Writers/EPUB.hs82
-rw-r--r--src/Text/Pandoc/Writers/HTML.hs6
-rw-r--r--src/Text/Pandoc/Writers/LaTeX.hs5
4 files changed, 61 insertions, 40 deletions
diff --git a/src/Text/Pandoc/Writers/Docbook.hs b/src/Text/Pandoc/Writers/Docbook.hs
index 08a83c85e..f3b99e141 100644
--- a/src/Text/Pandoc/Writers/Docbook.hs
+++ b/src/Text/Pandoc/Writers/Docbook.hs
@@ -154,6 +154,14 @@ listItemToDocbook opts item =
-- | Convert a Pandoc block element to Docbook.
blockToDocbook :: WriterOptions -> Block -> Doc
blockToDocbook _ Null = empty
+-- Add ids to paragraphs in divs with ids - this is needed for
+-- pandoc-citeproc to get link anchors in bibliographies:
+blockToDocbook opts (Div (ident,_,_) [Para lst]) =
+ let attribs = [("id", ident) | not (null ident)] in
+ if hasLineBreaks lst
+ then flush $ nowrap $ inTags False "literallayout" attribs
+ $ inlinesToDocbook opts lst
+ else inTags True "para" attribs $ inlinesToDocbook opts lst
blockToDocbook opts (Div _ bs) = blocksToDocbook opts $ map plainToPara bs
blockToDocbook _ (Header _ _ _) = empty -- should not occur after hierarchicalize
blockToDocbook opts (Plain lst) = inlinesToDocbook opts lst
diff --git a/src/Text/Pandoc/Writers/EPUB.hs b/src/Text/Pandoc/Writers/EPUB.hs
index 37c285dc2..4ce7857ac 100644
--- a/src/Text/Pandoc/Writers/EPUB.hs
+++ b/src/Text/Pandoc/Writers/EPUB.hs
@@ -31,7 +31,7 @@ Conversion of 'Pandoc' documents to EPUB.
module Text.Pandoc.Writers.EPUB ( writeEPUB ) where
import Data.IORef ( IORef, newIORef, readIORef, modifyIORef )
import qualified Data.Map as M
-import Data.Maybe ( fromMaybe )
+import Data.Maybe ( fromMaybe, catMaybes )
import Data.List ( isPrefixOf, isInfixOf, intercalate )
import System.Environment ( getEnv )
import Text.Printf (printf)
@@ -60,14 +60,14 @@ import Text.Pandoc.Walk (walk, walkM)
import Data.Default
import Text.Pandoc.Writers.Markdown (writePlain)
import Control.Monad.State (modify, get, execState, State, put, evalState)
-import Control.Monad (foldM, mplus, liftM, when)
+import Control.Monad (mplus, liftM, when)
import Text.XML.Light ( unode, Element(..), unqual, Attr(..), add_attrs
, strContent, lookupAttr, Node(..), QName(..), parseXML
, onlyElems, node, ppElement)
import Text.Pandoc.UUID (getRandomUUID)
import Text.Pandoc.Writers.HTML (writeHtmlString, writeHtml)
import Data.Char ( toLower, isDigit, isAlphaNum )
-import Text.Pandoc.MIME (MimeType, getMimeType)
+import Text.Pandoc.MIME (MimeType, getMimeType, extensionFromMimeType)
import qualified Control.Exception as E
import Text.Blaze.Html.Renderer.Utf8 (renderHtml)
import Text.HTML.TagSoup (Tag(TagOpen), fromAttrib, parseTags)
@@ -378,17 +378,7 @@ writeEPUB opts doc@(Pandoc meta _) = do
mediaRef <- newIORef []
Pandoc _ blocks <- walkM (transformInline opts' mediaRef) doc >>=
walkM (transformBlock opts' mediaRef)
- pics <- readIORef mediaRef
- let readPicEntry entries (oldsrc, newsrc) = do
- res <- fetchItem' (writerMediaBag opts')
- (writerSourceURL opts') oldsrc
- case res of
- Left _ -> do
- warn $ "Could not find media `" ++ oldsrc ++ "', skipping..."
- return entries
- Right (img,_) -> return $
- (toEntry newsrc epochtime $ B.fromChunks . (:[]) $ img) : entries
- picEntries <- foldM readPicEntry [] pics
+ picEntries <- (catMaybes . map (snd . snd)) <$> readIORef mediaRef
-- handle fonts
let matchingGlob f = do
@@ -425,10 +415,14 @@ writeEPUB opts doc@(Pandoc meta _) = do
let blocks'' = replaceRefs reftable blocks'
let isChapterHeader (Header n _ _) = n <= chapterHeaderLevel
+ isChapterHeader (Div ("",["references"],[]) (Header n _ _:_)) =
+ n <= chapterHeaderLevel
isChapterHeader _ = False
let toChapters :: [Block] -> State [Int] [Chapter]
toChapters [] = return []
+ toChapters (Div ("",["references"],[]) bs@(Header 1 _ _:_) : rest) =
+ toChapters (bs ++ rest)
toChapters (Header n attr@(_,classes,_) ils : bs) = do
nums <- get
mbnum <- if "unnumbered" `elem` classes
@@ -794,59 +788,75 @@ metadataElement version md currentTime =
showDateTimeISO8601 :: UTCTime -> String
showDateTimeISO8601 = formatTime defaultTimeLocale "%FT%TZ"
-transformTag :: IORef [(FilePath, FilePath)] -- ^ (oldpath, newpath) media
+transformTag :: WriterOptions
+ -> IORef [(FilePath, (FilePath, Maybe Entry))] -- ^ (oldpath, newpath, entry) media
-> Tag String
-> IO (Tag String)
-transformTag mediaRef tag@(TagOpen name attr)
+transformTag opts mediaRef tag@(TagOpen name attr)
| name `elem` ["video", "source", "img", "audio"] = do
let src = fromAttrib "src" tag
let poster = fromAttrib "poster" tag
- newsrc <- modifyMediaRef mediaRef src
- newposter <- modifyMediaRef mediaRef poster
+ newsrc <- modifyMediaRef opts mediaRef src
+ newposter <- modifyMediaRef opts mediaRef poster
let attr' = filter (\(x,_) -> x /= "src" && x /= "poster") attr ++
[("src", newsrc) | not (null newsrc)] ++
[("poster", newposter) | not (null newposter)]
return $ TagOpen name attr'
-transformTag _ tag = return tag
-
-modifyMediaRef :: IORef [(FilePath, FilePath)] -> FilePath -> IO FilePath
-modifyMediaRef _ "" = return ""
-modifyMediaRef mediaRef oldsrc = do
+transformTag _ _ tag = return tag
+
+modifyMediaRef :: WriterOptions
+ -> IORef [(FilePath, (FilePath, Maybe Entry))]
+ -> FilePath
+ -> IO FilePath
+modifyMediaRef _ _ "" = return ""
+modifyMediaRef opts mediaRef oldsrc = do
media <- readIORef mediaRef
case lookup oldsrc media of
- Just n -> return n
- Nothing -> do
- let new = "media/file" ++ show (length media) ++
- takeExtension (takeWhile (/='?') oldsrc) -- remove query
- modifyIORef mediaRef ( (oldsrc, new): )
+ Just (n,_) -> return n
+ Nothing -> do
+ res <- fetchItem' (writerMediaBag opts)
+ (writerSourceURL opts) oldsrc
+ (new, mbEntry) <-
+ case res of
+ Left _ -> do
+ warn $ "Could not find media `" ++ oldsrc ++ "', skipping..."
+ return (oldsrc, Nothing)
+ Right (img,mbMime) -> do
+ let new = "media/file" ++ show (length media) ++
+ fromMaybe (takeExtension (takeWhile (/='?') oldsrc))
+ (('.':) <$> (mbMime >>= extensionFromMimeType))
+ epochtime <- floor `fmap` getPOSIXTime
+ let entry = toEntry new epochtime $ B.fromChunks . (:[]) $ img
+ return (new, Just entry)
+ modifyIORef mediaRef ( (oldsrc, (new, mbEntry)): )
return new
transformBlock :: WriterOptions
- -> IORef [(FilePath, FilePath)] -- ^ (oldpath, newpath) media
+ -> IORef [(FilePath, (FilePath, Maybe Entry))] -- ^ (oldpath, newpath, entry) media
-> Block
-> IO Block
-transformBlock _ mediaRef (RawBlock fmt raw)
+transformBlock opts mediaRef (RawBlock fmt raw)
| fmt == Format "html" = do
let tags = parseTags raw
- tags' <- mapM (transformTag mediaRef) tags
+ tags' <- mapM (transformTag opts mediaRef) tags
return $ RawBlock fmt (renderTags' tags')
transformBlock _ _ b = return b
transformInline :: WriterOptions
- -> IORef [(FilePath, FilePath)] -- ^ (oldpath, newpath) media
+ -> IORef [(FilePath, (FilePath, Maybe Entry))] -- ^ (oldpath, newpath) media
-> Inline
-> IO Inline
-transformInline _ mediaRef (Image lab (src,tit)) = do
- newsrc <- modifyMediaRef mediaRef src
+transformInline opts mediaRef (Image lab (src,tit)) = do
+ newsrc <- modifyMediaRef opts mediaRef src
return $ Image lab (newsrc, tit)
transformInline opts _ (x@(Math _ _))
| WebTeX _ <- writerHTMLMathMethod opts = do
raw <- makeSelfContained opts $ writeHtmlInline opts x
return $ RawInline (Format "html") raw
-transformInline _ mediaRef (RawInline fmt raw)
+transformInline opts mediaRef (RawInline fmt raw)
| fmt == Format "html" = do
let tags = parseTags raw
- tags' <- mapM (transformTag mediaRef) tags
+ tags' <- mapM (transformTag opts mediaRef) tags
return $ RawInline fmt (renderTags' tags')
transformInline _ _ x = return x
diff --git a/src/Text/Pandoc/Writers/HTML.hs b/src/Text/Pandoc/Writers/HTML.hs
index 3a89b226b..022a0e17f 100644
--- a/src/Text/Pandoc/Writers/HTML.hs
+++ b/src/Text/Pandoc/Writers/HTML.hs
@@ -46,7 +46,7 @@ import Numeric ( showHex )
import Data.Char ( ord, toLower )
import Data.List ( isPrefixOf, intersperse )
import Data.String ( fromString )
-import Data.Maybe ( catMaybes, fromMaybe )
+import Data.Maybe ( catMaybes, fromMaybe, isJust )
import Control.Monad.State
import Text.Blaze.Html hiding(contents)
#if MIN_VERSION_blaze_markup(0,6,3)
@@ -825,7 +825,9 @@ inlineToHtml opts inline =
writerIdentifierPrefix opts ++ "fn" ++ ref)
! A.class_ "footnoteRef"
! prefixedId opts ("fnref" ++ ref)
- $ H.sup
+ $ (if isJust (writerEpubVersion opts)
+ then id
+ else H.sup)
$ toHtml ref
return $ case writerEpubVersion opts of
Just EPUB3 -> link ! customAttribute "epub:type" "noteref"
diff --git a/src/Text/Pandoc/Writers/LaTeX.hs b/src/Text/Pandoc/Writers/LaTeX.hs
index 70280aaec..a785e1edc 100644
--- a/src/Text/Pandoc/Writers/LaTeX.hs
+++ b/src/Text/Pandoc/Writers/LaTeX.hs
@@ -274,10 +274,11 @@ elementToBeamer slideLevel (Sec lvl _num (ident,classes,kvs) tit elts)
let hasCode (Code _ _) = [True]
hasCode _ = []
opts <- gets stOptions
- let fragile = not $ null $ query hasCodeBlock elts ++
+ let fragile = "fragile" `elem` classes ||
+ not (null $ query hasCodeBlock elts ++
if writerListings opts
then query hasCode elts
- else []
+ else [])
let allowframebreaks = "allowframebreaks" `elem` classes
let optionslist = ["fragile" | fragile] ++
["allowframebreaks" | allowframebreaks]