aboutsummaryrefslogtreecommitdiff
path: root/src/Text
diff options
context:
space:
mode:
authorJohn MacFarlane <fiddlosopher@gmail.com>2014-04-05 10:58:32 -0700
committerJohn MacFarlane <fiddlosopher@gmail.com>2014-04-05 10:58:32 -0700
commitc0309a60bc48e347e4b9d621ee38b84a98d0c187 (patch)
tree8ce40a62ce7c6802036897ce1fd7836588d24030 /src/Text
parentee2e769cd7ee075876c974f94817e6eee294bedd (diff)
downloadpandoc-c0309a60bc48e347e4b9d621ee38b84a98d0c187.tar.gz
Shared.openURL: Set proxy with value of http_proxy env variable.
Note: proxies with non-root paths are not supported, because of limitations in http-conduit. Closes #1211.
Diffstat (limited to 'src/Text')
-rw-r--r--src/Text/Pandoc/Shared.hs14
1 files changed, 11 insertions, 3 deletions
diff --git a/src/Text/Pandoc/Shared.hs b/src/Text/Pandoc/Shared.hs
index 714402e42..3835629db 100644
--- a/src/Text/Pandoc/Shared.hs
+++ b/src/Text/Pandoc/Shared.hs
@@ -1,5 +1,5 @@
{-# LANGUAGE DeriveDataTypeable, CPP, MultiParamTypeClasses,
- FlexibleContexts #-}
+ FlexibleContexts, ScopedTypeVariables #-}
{-
Copyright (C) 2006-2013 John MacFarlane <jgm@berkeley.edu>
@@ -120,7 +120,9 @@ import Paths_pandoc (getDataFileName)
#ifdef HTTP_CONDUIT
import Data.ByteString.Lazy (toChunks)
import Network.HTTP.Conduit (httpLbs, parseUrl, withManager,
- responseBody, responseHeaders)
+ responseBody, responseHeaders, addProxy,
+ Request(port,host))
+import System.Environment (getEnv)
import Network.HTTP.Types.Header ( hContentType)
import Network (withSocketsDo)
#else
@@ -648,7 +650,13 @@ openURL u
#ifdef HTTP_CONDUIT
| otherwise = withSocketsDo $ E.try $ do
req <- parseUrl u
- resp <- withManager $ httpLbs req
+ (proxy :: Either E.SomeException String) <- E.try $ getEnv "http_proxy"
+ let req' = case proxy of
+ Left _ -> req
+ Right pr -> case parseUrl pr of
+ Just r -> addProxy (host r) (port r) req
+ Nothing -> req
+ resp <- withManager $ httpLbs req'
return (BS.concat $ toChunks $ responseBody resp,
UTF8.toString `fmap` lookup hContentType (responseHeaders resp))
#else