aboutsummaryrefslogtreecommitdiff
path: root/src/Text/Pandoc/Writers/ICML.hs
diff options
context:
space:
mode:
authorJohn MacFarlane <jgm@berkeley.edu>2016-12-12 13:51:20 +0100
committerJohn MacFarlane <jgm@berkeley.edu>2017-01-25 17:07:42 +0100
commit6aff97e4e16b3829151a5e84b63a0aee26ea8511 (patch)
treebdab822f07f9d868ab8714dc8a392f48278b8d6e /src/Text/Pandoc/Writers/ICML.hs
parent4cb124d147790814cf2055afdfd17e500cece559 (diff)
downloadpandoc-6aff97e4e16b3829151a5e84b63a0aee26ea8511.tar.gz
Text.Pandoc.Shared: Removed fetchItem, fetchItem'.
Made changes where these are used, so that the version of fetchItem from PandocMonad can be used instead.
Diffstat (limited to 'src/Text/Pandoc/Writers/ICML.hs')
-rw-r--r--src/Text/Pandoc/Writers/ICML.hs8
1 files changed, 5 insertions, 3 deletions
diff --git a/src/Text/Pandoc/Writers/ICML.hs b/src/Text/Pandoc/Writers/ICML.hs
index 6bc7436d8..b68b9067a 100644
--- a/src/Text/Pandoc/Writers/ICML.hs
+++ b/src/Text/Pandoc/Writers/ICML.hs
@@ -1,4 +1,4 @@
-{-# LANGUAGE OverloadedStrings, FlexibleContexts #-}
+{-# LANGUAGE OverloadedStrings, FlexibleContexts, ScopedTypeVariables #-}
{- |
Module : Text.Pandoc.Writers.ICML
@@ -15,6 +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.XML
import Text.Pandoc.Writers.Math (texMathToInlines)
import Text.Pandoc.Writers.Shared
@@ -26,6 +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 Network.URI (isURI)
import qualified Data.Set as Set
import Text.Pandoc.Class (PandocMonad)
@@ -534,9 +536,9 @@ styleToStrAttr style =
-- | Assemble an ICML Image.
imageICML :: PandocMonad m => WriterOptions -> Style -> Attr -> Target -> WS m Doc
imageICML opts style attr (src, _) = do
- res <- lift $ P.fetchItem (writerSourceURL opts) src
+ res <- runExceptT $ lift $ P.fetchItem (writerSourceURL opts) src
imgS <- case res of
- Left (_) -> do
+ Left (_ :: PandocError) -> do
lift $ P.warning $ "Could not find image `" ++ src ++ "', skipping..."
return def
Right (img, _) -> do