diff options
| -rw-r--r-- | src/Text/Pandoc/Class/IO.hs | 6 | ||||
| -rw-r--r-- | src/Text/Pandoc/Class/PandocMonad.hs | 2 | ||||
| -rw-r--r-- | src/Text/Pandoc/Error.hs | 6 | ||||
| -rw-r--r-- | src/Text/Pandoc/SelfContained.hs | 2 |
4 files changed, 8 insertions, 8 deletions
diff --git a/src/Text/Pandoc/Class/IO.hs b/src/Text/Pandoc/Class/IO.hs index 49de2c436..1a9dc2eae 100644 --- a/src/Text/Pandoc/Class/IO.hs +++ b/src/Text/Pandoc/Class/IO.hs @@ -1,4 +1,5 @@ {-# LANGUAGE CPP #-} +{-# LANGUAGE ScopedTypeVariables #-} {-# LANGUAGE OverloadedStrings #-} {- | Module : Text.Pandoc.Class.IO @@ -46,7 +47,7 @@ import qualified Network.TLS as TLS import qualified Network.TLS.Extra as TLS import Network.HTTP.Client (httpLbs, Manager, responseBody, responseHeaders, - Request(port, host, requestHeaders), parseUrlThrow, newManager) + Request(port, host, requestHeaders), parseUrlThrow, newManager, HttpException) import Network.HTTP.Client.Internal (addProxy) import Network.HTTP.Client.TLS (mkManagerSettings) import Network.HTTP.Types.Header ( hContentType ) @@ -178,7 +179,8 @@ openURL u case res of Right r -> return r - Left e -> throwError $ PandocHttpError u e + Left (e :: HttpException) + -> throwError $ PandocHttpError u (T.pack (show e)) -- | Read the lazy ByteString contents from a file path, raising an error on -- failure. diff --git a/src/Text/Pandoc/Class/PandocMonad.hs b/src/Text/Pandoc/Class/PandocMonad.hs index 618b27c79..5614b5aea 100644 --- a/src/Text/Pandoc/Class/PandocMonad.hs +++ b/src/Text/Pandoc/Class/PandocMonad.hs @@ -534,7 +534,7 @@ fillMediaBag d = walkM handleImage d return $ replacementSpan attr src tit lab PandocHttpError u er -> do report $ CouldNotFetchResource u - (T.pack $ show er ++ "\rReplacing image with description.") + (er <> "\nReplacing image with description.") -- emit alt text return $ replacementSpan attr src tit lab _ -> throwError e) diff --git a/src/Text/Pandoc/Error.hs b/src/Text/Pandoc/Error.hs index e782df735..15dab4b09 100644 --- a/src/Text/Pandoc/Error.hs +++ b/src/Text/Pandoc/Error.hs @@ -25,7 +25,6 @@ import Data.Word (Word8) import Data.Text (Text) import qualified Data.Text as T import GHC.Generics (Generic) -import Network.HTTP.Client (HttpException) import System.Exit (ExitCode (..), exitWith) import System.IO (stderr) import qualified Text.Pandoc.UTF8 as UTF8 @@ -34,7 +33,7 @@ import Text.Pandoc.Shared (tshow) import Citeproc (CiteprocError, prettyCiteprocError) data PandocError = PandocIOError Text IOError - | PandocHttpError Text HttpException + | PandocHttpError Text Text | PandocShouldNeverHappenError Text | PandocSomeError Text | PandocParseError Text @@ -74,8 +73,7 @@ renderError :: PandocError -> Text renderError e = case e of PandocIOError _ err' -> T.pack $ displayException err' - PandocHttpError u err' -> - "Could not fetch " <> u <> "\n" <> tshow err' + PandocHttpError u err' -> "Could not fetch " <> u <> "\n" <> err' PandocShouldNeverHappenError s -> "Something we thought was impossible happened!\n" <> "Please report this to pandoc's developers: " <> s diff --git a/src/Text/Pandoc/SelfContained.hs b/src/Text/Pandoc/SelfContained.hs index 330dddff2..4ae01ad88 100644 --- a/src/Text/Pandoc/SelfContained.hs +++ b/src/Text/Pandoc/SelfContained.hs @@ -431,7 +431,7 @@ getData mimetype src report $ CouldNotFetchResource r "" return $ CouldNotFetch e PandocHttpError u er -> do - report $ CouldNotFetchResource u (tshow er) + report $ CouldNotFetchResource u er return $ CouldNotFetch e _ -> throwError e removeQueryAndFragment = T.takeWhile (\c -> c /= '#' && c /= '?') |
