diff options
Diffstat (limited to 'src/Text/Pandoc')
-rw-r--r-- | src/Text/Pandoc/Writers/ICML.hs | 20 | ||||
-rw-r--r-- | src/Text/Pandoc/Writers/ODT.hs | 22 | ||||
-rw-r--r-- | src/Text/Pandoc/Writers/RTF.hs | 83 |
3 files changed, 68 insertions, 57 deletions
diff --git a/src/Text/Pandoc/Writers/ICML.hs b/src/Text/Pandoc/Writers/ICML.hs index 3b7d3c4da..59f9db26a 100644 --- a/src/Text/Pandoc/Writers/ICML.hs +++ b/src/Text/Pandoc/Writers/ICML.hs @@ -15,7 +15,7 @@ into InDesign with File -> Place. -} module Text.Pandoc.Writers.ICML (writeICML) where import Text.Pandoc.Definition -import Text.Pandoc.Error (PandocError) +import Text.Pandoc.Error (PandocError(..)) import Text.Pandoc.XML import Text.Pandoc.Writers.Math (texMathToInlines) import Text.Pandoc.Writers.Shared @@ -27,7 +27,7 @@ import Text.Pandoc.ImageSize import Data.List (isPrefixOf, isInfixOf, stripPrefix, intersperse) import Data.Text as Text (breakOnAll, pack) import Control.Monad.State -import Control.Monad.Except (runExceptT) +import Control.Monad.Except (catchError) import Network.URI (isURI) import qualified Data.Set as Set import Text.Pandoc.Class (PandocMonad, report) @@ -540,17 +540,19 @@ styleToStrAttr style = -- | Assemble an ICML Image. imageICML :: PandocMonad m => WriterOptions -> Style -> Attr -> Target -> WS m Doc imageICML opts style attr (src, _) = do - res <- runExceptT $ lift $ P.fetchItem (writerSourceURL opts) src - imgS <- case res of - Left (_ :: PandocError) -> do - report $ CouldNotFetchResource src "" - return def - Right (img, _) -> do + imgS <- catchError + (do (img, _) <- P.fetchItem (writerSourceURL opts) src case imageSize opts img of Right size -> return size Left msg -> do report $ CouldNotDetermineImageSize src msg - return def + return def) + (\e -> do + case e of + PandocIOError _ e' -> + report $ CouldNotFetchResource src (show e') + e' -> report $ CouldNotFetchResource src (show e') + return def) let (ow, oh) = sizeInPoints imgS (imgWidth, imgHeight) = desiredSizeInPoints opts attr imgS hw = showFl $ ow / 2 diff --git a/src/Text/Pandoc/Writers/ODT.hs b/src/Text/Pandoc/Writers/ODT.hs index 61bb63d9b..3fa1626d2 100644 --- a/src/Text/Pandoc/Writers/ODT.hs +++ b/src/Text/Pandoc/Writers/ODT.hs @@ -45,8 +45,8 @@ import Text.Pandoc.Walk import Text.Pandoc.Writers.Shared ( fixDisplayMath ) import Text.Pandoc.Writers.OpenDocument ( writeOpenDocument ) import Control.Monad.State -import Control.Monad.Except (runExceptT) -import Text.Pandoc.Error (PandocError) +import Control.Monad.Except (catchError) +import Text.Pandoc.Error (PandocError(..)) import Text.Pandoc.XML import Text.Pandoc.Pretty import System.FilePath ( takeExtension, takeDirectory, (<.>)) @@ -146,13 +146,8 @@ pandocToODT opts doc@(Pandoc meta _) = do -- | transform both Image and Math elements transformPicMath :: PandocMonad m => WriterOptions ->Inline -> O m Inline -transformPicMath opts (Image attr@(id', cls, _) lab (src,t)) = do - res <- runExceptT $ lift $ P.fetchItem (writerSourceURL opts) src - case res of - Left (_ :: PandocError) -> do - report $ CouldNotFetchResource src "" - return $ Emph lab - Right (img, mbMimeType) -> do +transformPicMath opts (Image attr@(id', cls, _) lab (src,t)) = catchError + (do (img, mbMimeType) <- P.fetchItem (writerSourceURL opts) src (ptX, ptY) <- case imageSize opts img of Right s -> return $ sizeInPoints s Left msg -> do @@ -181,7 +176,14 @@ transformPicMath opts (Image attr@(id', cls, _) lab (src,t)) = do epochtime <- floor `fmap` (lift P.getPOSIXTime) let entry = toEntry newsrc epochtime $ toLazy img modify $ \st -> st{ stEntries = entry : entries } - return $ Image newattr lab (newsrc, t) + return $ Image newattr lab (newsrc, t)) + (\e -> do + case e of + PandocIOError _ e' -> + report $ CouldNotFetchResource src (show e') + e' -> report $ CouldNotFetchResource src (show e') + return $ Emph lab) + transformPicMath _ (Math t math) = do entries <- gets stEntries let dt = if t == InlineMath then DisplayInline else DisplayBlock diff --git a/src/Text/Pandoc/Writers/RTF.hs b/src/Text/Pandoc/Writers/RTF.hs index 5172a0ddd..56d72afcb 100644 --- a/src/Text/Pandoc/Writers/RTF.hs +++ b/src/Text/Pandoc/Writers/RTF.hs @@ -44,7 +44,7 @@ import qualified Data.ByteString as B import qualified Data.Map as M import Text.Printf ( printf ) import Text.Pandoc.ImageSize -import Control.Monad.Except (throwError, runExceptT, lift) +import Control.Monad.Except (throwError, catchError) import Text.Pandoc.Error import Text.Pandoc.Class (PandocMonad, report) import qualified Text.Pandoc.Class as P @@ -53,43 +53,50 @@ import qualified Text.Pandoc.Class as P -- or a MediaBag, or the internet. -- If file not found or filetype not jpeg or png, leave the inline unchanged. rtfEmbedImage :: PandocMonad m => WriterOptions -> Inline -> m Inline -rtfEmbedImage opts x@(Image attr _ (src,_)) = do - result <- runExceptT $ lift $ P.fetchItem (writerSourceURL opts) src - case result of - Right (imgdata, Just mime) - | mime == "image/jpeg" || mime == "image/png" -> do - let bytes = map (printf "%02x") $ B.unpack imgdata - filetype <- case mime of - "image/jpeg" -> return "\\jpegblip" - "image/png" -> return "\\pngblip" - _ -> throwError $ PandocSomeError "Unknown file type" - sizeSpec <- case imageSize opts imgdata of - Left msg -> do - report $ CouldNotDetermineImageSize src msg - return "" - Right sz -> return $ "\\picw" ++ show xpx ++ - "\\pich" ++ show ypx ++ - "\\picwgoal" ++ show (floor (xpt * 20) :: Integer) - ++ "\\pichgoal" ++ show (floor (ypt * 20) :: Integer) - -- twip = 1/1440in = 1/20pt - where (xpx, ypx) = sizeInPixels sz - (xpt, ypt) = desiredSizeInPoints opts attr sz - let raw = "{\\pict" ++ filetype ++ sizeSpec ++ "\\bin " ++ - concat bytes ++ "}" - if B.null imgdata - then do - report $ CouldNotFetchResource src "image contained no data" - return x - else return $ RawInline (Format "rtf") raw - | otherwise -> do - report $ CouldNotFetchResource src "image is not a jpeg or png" - return x - Right (_, Nothing) -> do - report $ CouldNotDetermineMimeType src - return x - Left ( e :: PandocError ) -> do - report $ CouldNotFetchResource src (show e) - return x +rtfEmbedImage opts x@(Image attr _ (src,_)) = catchError + (do result <- P.fetchItem (writerSourceURL opts) src + case result of + (imgdata, Just mime) + | mime == "image/jpeg" || mime == "image/png" -> do + let bytes = map (printf "%02x") $ B.unpack imgdata + filetype <- + case mime of + "image/jpeg" -> return "\\jpegblip" + "image/png" -> return "\\pngblip" + _ -> throwError $ + PandocShouldNeverHappenError $ + "Unknown file type " ++ mime + sizeSpec <- + case imageSize opts imgdata of + Left msg -> do + report $ CouldNotDetermineImageSize src msg + return "" + Right sz -> return $ "\\picw" ++ show xpx ++ + "\\pich" ++ show ypx ++ + "\\picwgoal" ++ show (floor (xpt * 20) :: Integer) + ++ "\\pichgoal" ++ show (floor (ypt * 20) :: Integer) + -- twip = 1/1440in = 1/20pt + where (xpx, ypx) = sizeInPixels sz + (xpt, ypt) = desiredSizeInPoints opts attr sz + let raw = "{\\pict" ++ filetype ++ sizeSpec ++ "\\bin " ++ + concat bytes ++ "}" + if B.null imgdata + then do + report $ CouldNotFetchResource src "image contained no data" + return x + else return $ RawInline (Format "rtf") raw + | otherwise -> do + report $ CouldNotFetchResource src "image is not a jpeg or png" + return x + (_, Nothing) -> do + report $ CouldNotDetermineMimeType src + return x) + (\e -> do + case e of + PandocIOError _ e' -> + report $ CouldNotFetchResource src (show e') + e' -> report $ CouldNotFetchResource src (show e') + return x) rtfEmbedImage _ x = return x -- | Convert Pandoc to a string in rich text format. |