aboutsummaryrefslogtreecommitdiff
path: root/src/Text/Pandoc/Shared.hs
diff options
context:
space:
mode:
authorJohn MacFarlane <jgm@berkeley.edu>2017-02-23 16:21:03 +0100
committerJohn MacFarlane <jgm@berkeley.edu>2017-02-23 16:21:03 +0100
commit4a9069130f8d53a1b417fc3e0fcf7da6d7d2c5dd (patch)
tree54ca7c35fdc4e505a2237b39f6456a94554db7d8 /src/Text/Pandoc/Shared.hs
parent2d964dd4eec295085234f1505523af6b3d6d72cd (diff)
downloadpandoc-4a9069130f8d53a1b417fc3e0fcf7da6d7d2c5dd.tar.gz
Shared.openURL: Changed type from an Either.
Now it will just raise an exception to be trapped later.
Diffstat (limited to 'src/Text/Pandoc/Shared.hs')
-rw-r--r--src/Text/Pandoc/Shared.hs15
1 files changed, 9 insertions, 6 deletions
diff --git a/src/Text/Pandoc/Shared.hs b/src/Text/Pandoc/Shared.hs
index 268a5052e..dbe00d231 100644
--- a/src/Text/Pandoc/Shared.hs
+++ b/src/Text/Pandoc/Shared.hs
@@ -124,6 +124,7 @@ import Text.Pandoc.Pretty (charWidth)
import Text.Pandoc.Compat.Time
import Data.Time.Clock.POSIX
import System.IO (stderr)
+import System.IO.Error
import System.IO.Temp
import Text.HTML.TagSoup (renderTagsOptions, RenderOptions(..), Tag(..),
renderOptions)
@@ -730,17 +731,19 @@ readDataFileUTF8 userDir fname =
UTF8.toString `fmap` readDataFile userDir fname
-- | Read from a URL and return raw data and maybe mime type.
-openURL :: String -> IO (Either E.SomeException (BS.ByteString, Maybe MimeType))
+openURL :: String -> IO (BS.ByteString, Maybe MimeType)
openURL u
| Just u'' <- stripPrefix "data:" u =
let mime = takeWhile (/=',') u''
contents = B8.pack $ unEscapeString $ drop 1 $ dropWhile (/=',') u''
- in return $ Right (decodeLenient contents, Just mime)
+ in return (decodeLenient contents, Just mime)
#ifdef HTTP_CLIENT
- | otherwise = withSocketsDo $ E.try $ do
+ | otherwise = withSocketsDo $ do
let parseReq = parseRequest
- (proxy :: Either E.SomeException String) <- E.try $ getEnv "http_proxy"
- (useragent :: Either E.SomeException String) <- E.try $ getEnv "USER_AGENT"
+ (proxy :: Either IOError String) <-
+ tryIOError $ getEnv "http_proxy"
+ (useragent :: Either IOError String) <-
+ tryIOError $ getEnv "USER_AGENT"
req <- parseReq u
req' <- case proxy of
Left _ -> return req
@@ -758,7 +761,7 @@ openURL u
return (BS.concat $ toChunks $ responseBody resp,
UTF8.toString `fmap` lookup hContentType (responseHeaders resp))
#else
- | otherwise = E.try $ getBodyAndMimeType `fmap` browse
+ | otherwise = getBodyAndMimeType `fmap` browse
(do liftIO $ UTF8.hPutStrLn stderr $ "Fetching " ++ u ++ "..."
setOutHandler $ const (return ())
setAllowRedirects True