diff options
author | John MacFarlane <jgm@berkeley.edu> | 2011-07-16 14:04:19 -0700 |
---|---|---|
committer | John MacFarlane <jgm@berkeley.edu> | 2011-07-16 14:19:45 -0700 |
commit | b5da7adfb8ba38ac662695989b81b6e0875ac2fe (patch) | |
tree | bd5b2ff17de707aeab074fba299280aa2cc1d27f /src | |
parent | fd46f610e3d127b27701795930b1e7f1a8b896fb (diff) | |
download | pandoc-b5da7adfb8ba38ac662695989b81b6e0875ac2fe.tar.gz |
Un-URI-escape image filenames in LaTeX, ConTeXt, RTF, Texinfo.
Also do this when copying image files into EPUBs and ODTs.
Closes #263.
Diffstat (limited to 'src')
-rw-r--r-- | src/Text/Pandoc/Writers/ConTeXt.hs | 6 | ||||
-rw-r--r-- | src/Text/Pandoc/Writers/EPUB.hs | 6 | ||||
-rw-r--r-- | src/Text/Pandoc/Writers/LaTeX.hs | 6 | ||||
-rw-r--r-- | src/Text/Pandoc/Writers/ODT.hs | 6 | ||||
-rw-r--r-- | src/Text/Pandoc/Writers/OpenDocument.hs | 2 | ||||
-rw-r--r-- | src/Text/Pandoc/Writers/RTF.hs | 31 | ||||
-rw-r--r-- | src/Text/Pandoc/Writers/Texinfo.hs | 12 |
7 files changed, 44 insertions, 25 deletions
diff --git a/src/Text/Pandoc/Writers/ConTeXt.hs b/src/Text/Pandoc/Writers/ConTeXt.hs index 0f6e00a3b..378c4ce96 100644 --- a/src/Text/Pandoc/Writers/ConTeXt.hs +++ b/src/Text/Pandoc/Writers/ConTeXt.hs @@ -36,6 +36,7 @@ import Data.List ( intercalate ) import Control.Monad.State import Text.Pandoc.Pretty import Text.Pandoc.Templates ( renderTemplate ) +import Network.URI ( isAbsoluteURI, unEscapeString ) data WriterState = WriterState { stNextRef :: Int -- number of next URL reference @@ -282,7 +283,10 @@ inlineToConTeXt (Link txt (src, _)) = do brackets empty <> brackets label <> "\\from" <> brackets (text ref) inlineToConTeXt (Image _ (src, _)) = do - return $ braces $ "\\externalfigure" <> brackets (text src) + let src' = if isAbsoluteURI src + then src + else unEscapeString src + return $ braces $ "\\externalfigure" <> brackets (text src') inlineToConTeXt (Note contents) = do contents' <- blockListToConTeXt contents return $ text "\\footnote{" <> diff --git a/src/Text/Pandoc/Writers/EPUB.hs b/src/Text/Pandoc/Writers/EPUB.hs index 00e95470a..9fc393fed 100644 --- a/src/Text/Pandoc/Writers/EPUB.hs +++ b/src/Text/Pandoc/Writers/EPUB.hs @@ -47,6 +47,7 @@ import Text.Pandoc.Writers.HTML import Text.Pandoc.Writers.Markdown ( writePlain ) import Data.Char ( toLower ) import System.Directory ( copyFile ) +import Network.URI ( unEscapeString ) -- | Produce an EPUB file from a Pandoc document. writeEPUB :: Maybe String -- ^ EPUB stylesheet specified at command line @@ -238,9 +239,10 @@ transformInlines :: HTMLMathMethod transformInlines _ _ _ (Image lab (src,_) : xs) | isNothing (imageTypeOf src) = return $ Emph lab : xs transformInlines _ sourceDir picsRef (Image lab (src,tit) : xs) = do + let src' = unEscapeString src pics <- readIORef picsRef - let oldsrc = sourceDir </> src - let ext = takeExtension src + let oldsrc = sourceDir </> src' + let ext = takeExtension src' newsrc <- case lookup oldsrc pics of Just n -> return n Nothing -> do diff --git a/src/Text/Pandoc/Writers/LaTeX.hs b/src/Text/Pandoc/Writers/LaTeX.hs index cf008bf6a..f3d7af7e5 100644 --- a/src/Text/Pandoc/Writers/LaTeX.hs +++ b/src/Text/Pandoc/Writers/LaTeX.hs @@ -34,6 +34,7 @@ import Text.Pandoc.Generic import Text.Pandoc.Shared import Text.Pandoc.Templates import Text.Printf ( printf ) +import Network.URI ( isAbsoluteURI, unEscapeString ) import Data.List ( (\\), isSuffixOf, isPrefixOf, intercalate, intersperse ) import Data.Char ( toLower, isPunctuation ) import Control.Monad.State @@ -425,7 +426,10 @@ inlineToLaTeX (Link txt (src, _)) = contents <> char '}' inlineToLaTeX (Image _ (source, _)) = do modify $ \s -> s{ stGraphics = True } - return $ "\\includegraphics" <> braces (text source) + let source' = if isAbsoluteURI source + then source + else unEscapeString source + return $ "\\includegraphics" <> braces (text source') inlineToLaTeX (Note contents) = do modify (\s -> s{stInNote = True}) contents' <- blockListToLaTeX contents diff --git a/src/Text/Pandoc/Writers/ODT.hs b/src/Text/Pandoc/Writers/ODT.hs index cf1be8755..908df1163 100644 --- a/src/Text/Pandoc/Writers/ODT.hs +++ b/src/Text/Pandoc/Writers/ODT.hs @@ -41,6 +41,7 @@ import Text.Pandoc.Generic import Text.Pandoc.Writers.OpenDocument ( writeOpenDocument ) import System.Directory import Control.Monad (liftM) +import Network.URI ( unEscapeString ) -- | Produce an ODT file from a Pandoc document. writeODT :: Maybe FilePath -- ^ Path specified by --reference-odt @@ -74,9 +75,10 @@ writeODT mbRefOdt opts doc = do transformPic :: FilePath -> IORef [Entry] -> Inline -> IO Inline transformPic sourceDir entriesRef (Image lab (src,tit)) = do + let src' = unEscapeString src entries <- readIORef entriesRef - let newsrc = "Pictures/" ++ show (length entries) ++ takeExtension src - catch (readEntry [] (sourceDir </> src) >>= \entry -> + let newsrc = "Pictures/" ++ show (length entries) ++ takeExtension src' + catch (readEntry [] (sourceDir </> src') >>= \entry -> modifyIORef entriesRef (entry{ eRelativePath = newsrc } :) >> return (Image lab (newsrc, tit))) (\_ -> return (Emph lab)) diff --git a/src/Text/Pandoc/Writers/OpenDocument.hs b/src/Text/Pandoc/Writers/OpenDocument.hs index e51ae92d4..e675f4e65 100644 --- a/src/Text/Pandoc/Writers/OpenDocument.hs +++ b/src/Text/Pandoc/Writers/OpenDocument.hs @@ -394,7 +394,7 @@ inlineToOpenDocument o ils mkImg s = inTags False "draw:frame" [] $ selfClosingTag "draw:image" [ ("xlink:href" , s ) , ("xlink:type" , "simple") - , (" xlink:show" , "embed" ) + , ("xlink:show" , "embed" ) , ("xlink:actuate", "onLoad")] mkNote l = do n <- length <$> gets stNotes diff --git a/src/Text/Pandoc/Writers/RTF.hs b/src/Text/Pandoc/Writers/RTF.hs index 605e4162b..eb36c1ca6 100644 --- a/src/Text/Pandoc/Writers/RTF.hs +++ b/src/Text/Pandoc/Writers/RTF.hs @@ -37,23 +37,28 @@ import Data.Char ( ord, isDigit, toLower ) import System.FilePath ( takeExtension ) import qualified Data.ByteString as B import Text.Printf ( printf ) +import Network.URI ( isAbsoluteURI, unEscapeString ) -- | Convert Image inlines into a raw RTF embedded image, read from a file. -- If file not found or filetype not jpeg or png, leave the inline unchanged. rtfEmbedImage :: Inline -> IO Inline -rtfEmbedImage x@(Image _ (src,_)) - | map toLower (takeExtension src) `elem` [".jpg",".jpeg",".png"] = do - imgdata <- catch (B.readFile src) (\_ -> return B.empty) - let bytes = map (printf "%02x") $ B.unpack imgdata - let filetype = case map toLower (takeExtension src) of - ".jpg" -> "\\jpegblip" - ".jpeg" -> "\\jpegblip" - ".png" -> "\\pngblip" - _ -> error "Unknown file type" - let raw = "{\\pict" ++ filetype ++ " " ++ concat bytes ++ "}" - return $ if B.null imgdata - then x - else RawInline "rtf" raw +rtfEmbedImage x@(Image _ (src,_)) = do + let ext = map toLower (takeExtension src) + if ext `elem` [".jpg",".jpeg",".png"] && not (isAbsoluteURI src) + then do + let src' = unEscapeString src + imgdata <- catch (B.readFile src') (\_ -> return B.empty) + let bytes = map (printf "%02x") $ B.unpack imgdata + let filetype = case ext of + ".jpg" -> "\\jpegblip" + ".jpeg" -> "\\jpegblip" + ".png" -> "\\pngblip" + _ -> error "Unknown file type" + let raw = "{\\pict" ++ filetype ++ " " ++ concat bytes ++ "}" + return $ if B.null imgdata + then x + else RawInline "rtf" raw + else return x rtfEmbedImage x = return x -- | Convert Pandoc to a string in rich text format. diff --git a/src/Text/Pandoc/Writers/Texinfo.hs b/src/Text/Pandoc/Writers/Texinfo.hs index c8638cdd7..4f6645cd5 100644 --- a/src/Text/Pandoc/Writers/Texinfo.hs +++ b/src/Text/Pandoc/Writers/Texinfo.hs @@ -37,6 +37,8 @@ import Data.Ord ( comparing ) import Data.Char ( chr, ord ) import Control.Monad.State import Text.Pandoc.Pretty +import Network.URI ( isAbsoluteURI, unEscapeString ) +import System.FilePath data WriterState = WriterState { stStrikeout :: Bool -- document contains strikeout @@ -412,11 +414,11 @@ inlineToTexinfo (Image alternate (source, _)) = do return $ text ("@image{" ++ base ++ ",,,") <> content <> text "," <> text (ext ++ "}") where - (revext, revbase) = break (=='.') (reverse source) - ext = reverse revext - base = case revbase of - ('.' : rest) -> reverse rest - _ -> reverse revbase + ext = drop 1 $ takeExtension source' + base = takeBaseName source' + source' = if isAbsoluteURI source + then source + else unEscapeString source inlineToTexinfo (Note contents) = do contents' <- blockListToTexinfo contents |