module Network.HTTP.Proxy
( Proxy(..)
, noProxy
, fetchProxy
, parseProxy
) where
import Control.Monad ( when, mplus, join, liftM2)
import Network.HTTP.Utils ( dropWhileTail, chopAtDelim )
import Network.HTTP.Auth
import Network.URI
( URI(..), URIAuth(..), parseAbsoluteURI )
import System.IO ( hPutStrLn, stderr )
import System.Environment
#if defined(WIN32)
import System.Win32.Types ( DWORD, HKEY )
import System.Win32.Registry( hKEY_CURRENT_USER, regOpenKey, regCloseKey, regQueryValue, regQueryValueEx )
import Control.Exception ( bracket )
import Foreign ( toBool, Storable(peek, sizeOf), castPtr, alloca )
#endif
data Proxy
= NoProxy
| Proxy String
(Maybe Authority)
noProxy :: Proxy
noProxy = NoProxy
envProxyString :: IO (Maybe String)
envProxyString = do
env <- getEnvironment
return (lookup "http_proxy" env `mplus` lookup "HTTP_PROXY" env)
proxyString :: IO (Maybe String)
proxyString = liftM2 mplus envProxyString registryProxyString
registryProxyString :: IO (Maybe String)
#if !defined(WIN32)
registryProxyString = return Nothing
#else
registryProxyLoc :: (HKEY,String)
registryProxyLoc = (hive, path)
where
hive = hKEY_CURRENT_USER
path = "Software\\Microsoft\\Windows\\CurrentVersion\\Internet Settings"
registryProxyString = Prelude.catch
(bracket (uncurry regOpenKey registryProxyLoc) regCloseKey $ \hkey -> do
enable <- fmap toBool $ regQueryValueDWORD hkey "ProxyEnable"
if enable
then fmap Just $ regQueryValue hkey (Just "ProxyServer")
else return Nothing)
(\_ -> return Nothing)
#endif
fetchProxy :: Bool -> IO Proxy
fetchProxy warnIfIllformed = do
mstr <- proxyString
case mstr of
Nothing -> return NoProxy
Just str -> case parseProxy str of
Just p -> return p
Nothing -> do
when warnIfIllformed $ System.IO.hPutStrLn System.IO.stderr $ unlines
[ "invalid http proxy uri: " ++ show str
, "proxy uri must be http with a hostname"
, "ignoring http proxy, trying a direct connection"
]
return NoProxy
parseProxy :: String -> Maybe Proxy
parseProxy str = join
. fmap uri2proxy
$ parseHttpURI str
`mplus` parseHttpURI ("http://" ++ str)
where
parseHttpURI str' =
case parseAbsoluteURI str' of
Just uri@URI{uriAuthority = Just{}} -> Just (fixUserInfo uri)
_ -> Nothing
fixUserInfo :: URI -> URI
fixUserInfo uri = uri{ uriAuthority = f `fmap` uriAuthority uri }
where
f a@URIAuth{uriUserInfo=s} = a{uriUserInfo=dropWhileTail (=='@') s}
uri2proxy :: URI -> Maybe Proxy
uri2proxy uri@URI{ uriScheme = "http:"
, uriAuthority = Just (URIAuth auth' hst prt)
} =
Just (Proxy (hst ++ prt) auth)
where
auth =
case auth' of
[] -> Nothing
as -> Just (AuthBasic "" usr pwd uri)
where
(usr,pwd) = chopAtDelim ':' as
uri2proxy _ = Nothing
#if defined(WIN32)
regQueryValueDWORD :: HKEY -> String -> IO DWORD
regQueryValueDWORD hkey name = alloca $ \ptr -> do
regQueryValueEx hkey name (castPtr ptr) (sizeOf (undefined :: DWORD))
peek ptr
#endif