{-# LANGUAGE CPP #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE FlexibleContexts #-}
module Network.HTTP.Proxy( ProxyProtocol(..), EnvHelper(..),
systemProxyHelper, envHelper,
httpProtocol,
ProxySettings ) where
import qualified Control.Applicative as A
import Control.Arrow (first)
import Control.Monad (guard)
import qualified Data.ByteString.Char8 as S8
import Data.Char (toLower)
import qualified Data.Map as Map
import qualified Data.Text as T
import Data.Text.Read (decimal)
import Network.HTTP.Client.Request (applyBasicProxyAuth,
extractBasicAuthInfo)
import Network.HTTP.Client.Types (HttpExceptionContent (..),
Proxy (..), Request (..),
throwHttp)
import qualified Network.URI as U
import System.Environment (getEnvironment)
#if defined(mingw32_HOST_OS)
import Control.Exception (IOException, bracket, catch, try)
import Control.Monad (join, liftM, mplus, when)
import Data.List (isInfixOf, isPrefixOf)
import Foreign (Storable (peek, sizeOf), alloca,
castPtr, toBool)
import Network.URI (parseAbsoluteURI)
import Safe (readDef)
import System.IO
import System.Win32.Registry (hKEY_CURRENT_USER, rEG_DWORD,
regCloseKey, regOpenKey,
regQueryValue, regQueryValueEx)
import System.Win32.Types (DWORD, HKEY)
#endif
type EnvName = T.Text
type HostAddress = S8.ByteString
type UserName = S8.ByteString
type Password = S8.ByteString
data ProxyProtocol = HTTPProxy | HTTPSProxy
instance Show ProxyProtocol where
show HTTPProxy = "http"
show HTTPSProxy = "https"
data ProxySettings = ProxySettings { _proxyHost :: Proxy,
_proxyAuth :: Maybe (UserName, Password) }
deriving Show
httpProtocol :: Bool -> ProxyProtocol
httpProtocol True = HTTPSProxy
httpProtocol False = HTTPProxy
data EnvHelper = EHFromRequest
| EHNoProxy
| EHUseProxy Proxy
headJust :: [Maybe a] -> Maybe a
headJust [] = Nothing
headJust (Nothing:xs) = headJust xs
headJust ((y@(Just _)):_) = y
systemProxyHelper :: Maybe T.Text -> ProxyProtocol -> EnvHelper -> IO (Request -> Request)
systemProxyHelper envOveride prot eh = do
let envName' Nothing = envName prot
envName' (Just name) = name
modifier <- envHelper (envName' envOveride)
#if defined(mingw32_HOST_OS)
modifier' <- systemProxy prot
let modifiers = [modifier, modifier']
#else
let modifiers = [modifier]
#endif
let chooseMod :: Request -> Maybe ProxySettings
chooseMod req = headJust . map (\m -> m . host $ req) $ modifiers
noEnvProxy = case eh of
EHFromRequest -> id
EHNoProxy -> \req -> req { proxy = Nothing }
EHUseProxy p -> \req -> req { proxy = Just p }
let result req = toRequest . chooseMod $ req where
toRequest Nothing = noEnvProxy req
toRequest (Just (ProxySettings p muserpass)) = maybe id (uncurry applyBasicProxyAuth) muserpass
req { proxy = Just p }
return result
#if defined(mingw32_HOST_OS)
windowsProxyString :: ProxyProtocol -> IO (Maybe (String, String))
windowsProxyString proto = do
mProxy <- registryProxyString
return $ do
(proxies, exceptions) <- mProxy
protoProxy <- parseWindowsProxy proto proxies
return (protoProxy, exceptions)
registryProxyLoc :: (HKEY,String)
registryProxyLoc = (hive, path)
where
hive = hKEY_CURRENT_USER
path = "Software\\Microsoft\\Windows\\CurrentVersion\\Internet Settings"
registryProxyString :: IO (Maybe (String, String))
registryProxyString = catch
(bracket (uncurry regOpenKey registryProxyLoc) regCloseKey $ \hkey -> do
enable <- toBool . maybe 0 id A.<$> regQueryValueDWORD hkey "ProxyEnable"
if enable
then do
#if MIN_VERSION_Win32(2, 6, 0)
server <- regQueryValue hkey "ProxyServer"
exceptions <- try $ regQueryValue hkey "ProxyOverride" :: IO (Either IOException String)
#else
server <- regQueryValue hkey (Just "ProxyServer")
exceptions <- try $ regQueryValue hkey (Just "ProxyOverride") :: IO (Either IOException String)
#endif
return $ Just (server, either (const "") id exceptions)
else return Nothing)
hideError where
hideError :: IOException -> IO (Maybe (String, String))
hideError _ = return Nothing
parseWindowsProxy :: ProxyProtocol -> String -> Maybe String
parseWindowsProxy proto s =
case proxies of
x:_ -> Just x
_ -> Nothing
where
parts = split ';' s
pr x = case break (== '=') x of
(p, []) -> p
(p, u) -> p ++ "://" ++ drop 1 u
protoPrefix = (show proto) ++ "://"
proxies = filter (isPrefixOf protoPrefix) . map pr $ parts
split :: Eq a => a -> [a] -> [[a]]
split _ [] = []
split a xs = case break (a ==) xs of
(ys, []) -> [ys]
(ys, _:zs) -> ys:split a zs
systemProxy :: ProxyProtocol -> IO (HostAddress -> Maybe ProxySettings)
systemProxy proto = do
let isURLlocal "127.0.0.1" = True
isURLlocal "localhost" = True
isURLlocal _ = False
hasLocal exceptions = "<local>" `isInfixOf` exceptions
settings <- fetchProxy proto
return $ \url -> do
(proxy, exceptions) <- settings
if (isURLlocal url && hasLocal exceptions) || (url `S8.isInfixOf` (S8.pack exceptions)) then Nothing
else Just proxy
fetchProxy :: ProxyProtocol -> IO (Maybe (ProxySettings, String))
fetchProxy proto = do
mstr <- windowsProxyString proto
case mstr of
Nothing -> return Nothing
Just (proxy, except) -> case parseProxy proto proxy of
Just p -> return $ Just (p, except)
Nothing ->
throwHttp . InvalidProxySettings . T.pack . unlines $
[ "Invalid http proxy uri: " ++ show proxy
, "proxy uri must be http with a hostname"
, "ignoring http proxy, trying a direct connection"
]
parseProxy :: ProxyProtocol -> String -> Maybe ProxySettings
parseProxy proto str = join
. fmap (uri2proxy proto)
$ parseHttpURI str
`mplus` parseHttpURI (protoPrefix ++ str)
where
protoPrefix = (show proto) ++ "://"
parseHttpURI str' =
case parseAbsoluteURI str' of
Just uri@U.URI{U.uriAuthority = Just{}} -> Just (fixUserInfo uri)
_ -> Nothing
dropWhileTail :: (a -> Bool) -> [a] -> [a]
dropWhileTail f ls =
case foldr chop Nothing ls of { Just xs -> xs; Nothing -> [] }
where
chop x (Just xs) = Just (x:xs)
chop x _
| f x = Nothing
| otherwise = Just [x]
chopAtDelim :: Eq a => a -> [a] -> ([a],[a])
chopAtDelim elt xs =
case break (==elt) xs of
(_,[]) -> (xs,[])
(as,_:bs) -> (as,bs)
fixUserInfo :: U.URI -> U.URI
fixUserInfo uri = uri{ U.uriAuthority = f `fmap` U.uriAuthority uri }
where
f a@U.URIAuth{U.uriUserInfo=s} = a{U.uriUserInfo=dropWhileTail (=='@') s}
defaultHTTPport :: ProxyProtocol -> Int
defaultHTTPport HTTPProxy = 80
defaultHTTPport HTTPSProxy = 443
uri2proxy :: ProxyProtocol -> U.URI -> Maybe ProxySettings
uri2proxy proto uri@U.URI{ U.uriAuthority = Just (U.URIAuth auth' hst prt) } =
if (show proto ++ ":") == U.uriScheme uri then
Just (ProxySettings (Proxy (S8.pack hst) (port prt)) auth) else Nothing
where
port (':':xs) = readDef (defaultHTTPport proto) xs
port _ = (defaultHTTPport proto)
auth =
case auth' of
[] -> Nothing
as -> Just ((S8.pack . U.unEscapeString $ usr), (S8.pack . U.unEscapeString $ pwd))
where
(usr,pwd) = chopAtDelim ':' as
uri2proxy _ _ = Nothing
regQueryValueDWORD :: HKEY -> String -> IO (Maybe DWORD)
regQueryValueDWORD hkey name = alloca $ \ptr -> do
key <- regQueryValueEx hkey name (castPtr ptr) (sizeOf (undefined :: DWORD))
if key == rEG_DWORD then
Just A.<$> peek ptr
else return Nothing
#endif
envName :: ProxyProtocol -> EnvName
envName proto = T.pack $ show proto ++ "_proxy"
envHelper :: EnvName -> IO (HostAddress -> Maybe ProxySettings)
envHelper name = do
env <- getEnvironment
let lenv = Map.fromList $ map (first $ T.toLower . T.pack) env
lookupEnvVar n = lookup (T.unpack n) env A.<|> Map.lookup n lenv
noProxyDomains = domainSuffixes (lookupEnvVar "no_proxy")
case lookupEnvVar name of
Nothing -> return . const $ Nothing
Just "" -> return . const $ Nothing
Just str -> do
let invalid = throwHttp $ InvalidProxyEnvironmentVariable name (T.pack str)
(p, muserpass) <- maybe invalid return $ do
let allowedScheme x = x == "http:"
uri <- case U.parseURI str of
Just u | allowedScheme (U.uriScheme u) -> return u
_ -> U.parseURI $ "http://" ++ str
guard $ allowedScheme $ U.uriScheme uri
guard $ null (U.uriPath uri) || U.uriPath uri == "/"
guard $ null $ U.uriQuery uri
guard $ null $ U.uriFragment uri
auth <- U.uriAuthority uri
port' <-
case U.uriPort auth of
"" -> Just 80
':':rest ->
case decimal $ T.pack rest of
Right (p, "") -> Just p
_ -> Nothing
_ -> Nothing
Just (Proxy (S8.pack $ U.uriRegName auth) port', extractBasicAuthInfo uri)
return $ \hostRequest ->
if hostRequest `hasDomainSuffixIn` noProxyDomains
then Nothing
else Just $ ProxySettings p muserpass
where prefixed s | S8.head s == '.' = s
| otherwise = S8.cons '.' s
domainSuffixes Nothing = []
domainSuffixes (Just "") = []
domainSuffixes (Just no_proxy) = [prefixed $ S8.dropWhile (== ' ') suffix | suffix <- S8.split ',' (S8.pack (map toLower no_proxy)), not (S8.null suffix)]
hasDomainSuffixIn host' = any (`S8.isSuffixOf` prefixed (S8.map toLower host'))