module Network.HTTP.Proxy
( Port
, Request (..)
, Settings (..)
, UpstreamProxy (..)
, httpProxyApp
, warpSettings
, runProxy
, runProxySettings
, runProxySettingsSocket
, defaultProxySettings
)
where
import Blaze.ByteString.Builder (fromByteString)
import Control.Concurrent.Async (race_)
import Control.Exception
import Data.ByteString.Char8 (ByteString)
import Data.Conduit (Flush (..), Sink, Source, ($$), mapOutput, yield)
import Data.Conduit.Network
import Data.Monoid
import Network.Socket
import Network.Wai.Conduit hiding (Request, requestMethod)
import qualified Data.ByteString.Char8 as BS
import qualified Data.ByteString.Lazy.Char8 as LBS
import qualified Data.CaseInsensitive as CI
import qualified Data.Conduit.Network as NC
import qualified Network.HTTP.Client as HC
import qualified Network.HTTP.Conduit as HC
import qualified Network.HTTP.Client.Conduit as HCC
import qualified Network.HTTP.Types as HT
import qualified Network.Wai as Wai
import qualified Network.Wai.Handler.Warp as Warp
import Network.HTTP.Proxy.Request
#if 0
import Data.Version (showVersion)
import qualified Paths_httpProxy
httpProxyVersion :: String
httpProxyVersion = showVersion Paths_warp.version
#endif
runProxy :: Port -> IO ()
runProxy port = runProxySettings $ defaultProxySettings { proxyPort = port }
runProxySettings :: Settings -> IO ()
runProxySettings set = do
mgr <- HC.newManager HC.tlsManagerSettings
Warp.runSettings (warpSettings set) $ httpProxyApp set mgr
runProxySettingsSocket :: Settings -> Socket -> IO ()
runProxySettingsSocket set sock = do
port <- socketPort sock
mgr <- HC.newManager HC.tlsManagerSettings
Warp.runSettingsSocket (warpSettings set) sock
$ httpProxyApp set { proxyPort = fromIntegral port } mgr
data Settings = Settings
{ proxyPort :: Int
, proxyHost :: HostPreference
, proxyOnException :: SomeException -> Wai.Response
, proxyTimeout :: Int
, proxyRequestModifier :: Request -> IO (Either Response Request)
, proxyLogger :: ByteString -> IO ()
, proxyUpstream :: Maybe UpstreamProxy
}
data UpstreamProxy = UpstreamProxy
{ upstreamHost :: ByteString
, upstreamPort :: Int
, upstreamAuth :: Maybe (ByteString, ByteString)
}
warpSettings :: Settings -> Warp.Settings
warpSettings pset = Warp.setPort (proxyPort pset)
. Warp.setHost (proxyHost pset)
. Warp.setTimeout (proxyTimeout pset)
. Warp.setOnException (\ _ _ -> return ())
. Warp.setOnExceptionResponse defaultExceptionResponse
$ Warp.setNoParsePath True Warp.defaultSettings
defaultProxySettings :: Settings
defaultProxySettings = Settings
{ proxyPort = 3100
, proxyHost = "*"
, proxyOnException = defaultExceptionResponse
, proxyTimeout = 30
, proxyRequestModifier = return . Right
, proxyLogger = const $ return ()
, proxyUpstream = Nothing
}
defaultExceptionResponse :: SomeException -> Wai.Response
defaultExceptionResponse e =
Wai.responseLBS HT.internalServerError500
[ (HT.hContentType, "text/plain; charset=utf-8") ]
$ LBS.fromChunks [BS.pack $ show e]
httpProxyApp :: Settings -> HC.Manager -> Application
httpProxyApp settings mgr wreq respond = do
mwreq <- proxyRequestModifier settings $ proxyRequest wreq
either respond (doUpstreamRequest settings mgr respond . waiRequest wreq) mwreq
doUpstreamRequest :: Settings -> HC.Manager -> (Wai.Response -> IO Wai.ResponseReceived) -> Wai.Request -> IO Wai.ResponseReceived
doUpstreamRequest settings mgr respond mwreq
| Wai.requestMethod mwreq == "CONNECT" =
respond $ responseRawSource (handleConnect mwreq)
(Wai.responseLBS HT.status500 [("Content-Type", "text/plain")] "No support for responseRaw")
| otherwise = do
hreq0 <- HC.parseRequest $ BS.unpack (Wai.rawPathInfo mwreq <> Wai.rawQueryString mwreq)
let hreq = hreq0
{ HC.method = Wai.requestMethod mwreq
, HC.requestHeaders = filter dropRequestHeader $ Wai.requestHeaders mwreq
, HC.redirectCount = 0
, HC.requestBody =
case Wai.requestBodyLength mwreq of
Wai.ChunkedBody ->
HC.requestBodySourceChunkedIO (sourceRequestBody mwreq)
Wai.KnownLength l ->
HC.requestBodySourceIO (fromIntegral l) (sourceRequestBody mwreq)
, HC.decompress = const False
}
handle (respond . errorResponse) $
HC.withResponse hreq mgr $ \res -> do
let body = mapOutput (Chunk . fromByteString) . HCC.bodyReaderSource $ HC.responseBody res
headers = (CI.mk "X-Via-Proxy", "yes") : filter dropResponseHeader (HC.responseHeaders res)
respond $ responseSource (HC.responseStatus res) headers body
where
dropRequestHeader (k, _) = k `notElem`
[ "content-encoding"
, "content-length"
]
dropResponseHeader (k, _) = k `notElem` []
errorResponse :: SomeException -> Wai.Response
errorResponse = proxyOnException settings . toException
handleConnect :: Wai.Request -> Source IO BS.ByteString -> Sink BS.ByteString IO () -> IO ()
handleConnect wreq fromClient toClient = do
let (host, port) =
case BS.break (== ':') $ Wai.rawPathInfo wreq of
(x, "") -> (x, 80)
(x, y) ->
case BS.readInt $ BS.drop 1 y of
Just (port', _) -> (x, port')
Nothing -> (x, 80)
settings = clientSettings port host
runTCPClient settings $ \ad -> do
yield "HTTP/1.1 200 OK\r\n\r\n" $$ toClient
race_
(fromClient $$ NC.appSink ad)
(NC.appSource ad $$ toClient)