wstunnel/src/HttpProxy.hs
Σrebe - Romain GERARD d0868f6630 fix linter warnings
Former-commit-id: ceecd6cd0b6e75f81d85901bd7ad1890e838e8eb [formerly e274544a535fa2e171063a043b2189dc4cb15268] [formerly b0649ee32ec63fa8c766878ca498d985ea04251c [formerly bd3f6d274fe0be3a8e54ad3f162dcde17e5691a4 [formerly bd3f6d274fe0be3a8e54ad3f162dcde17e5691a4 [formerly bd3f6d274fe0be3a8e54ad3f162dcde17e5691a4 [formerly 41664826ae67c0a742c71613a10af7014176cac1]]]]]
Former-commit-id: fc0f22afe3e2a3ce4caab6e509c0f6167ab1bd68 [formerly 0ef98eae2265b9afad17f19fb7e2bf8411050934]
Former-commit-id: 74eccd0fac7d327fdd391f0a2b7dc7c8ee4c71e0
Former-commit-id: 768b8e64c5cc5df505195ab0b43452073a0be2ec
Former-commit-id: 17e03e49916bcf718585aba21c58b1ee1aa2d054
Former-commit-id: d7f69f46257675857526004dca3f525189612ba0 [formerly f7c06993bd3718de1e080d73116f3dfc78ba05fd]
Former-commit-id: eaec27d94ca6e9c005298207930d6c0a16a1fb76
2023-07-29 12:28:41 +02:00

76 lines
3.1 KiB
Haskell

{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE StrictData #-}
{-# LANGUAGE ViewPatterns #-}
module HttpProxy () where
import ClassyPrelude
import qualified Data.ByteString.Char8 as BC
import Control.Monad.Except
import qualified Data.Streaming.Network as N
import qualified Data.ByteString.Base64 as B64
import Network.Socket (HostName, PortNumber)
import Logger
import Types
data HttpProxySettings = HttpProxySettings
{ proxyHost :: HostName
, proxyPort :: PortNumber
, credentials :: Maybe (ByteString, ByteString)
} deriving (Show)
httpProxyConnection :: MonadError Error m => HttpProxySettings -> (HostName, PortNumber) -> (Connection -> IO (m a)) -> IO (m a)
httpProxyConnection HttpProxySettings{..} (host, port) app = onError $ do
debug $ "Opening tcp connection to proxy " <> show proxyHost <> ":" <> show proxyPort
ret <- N.runTCPClient (N.clientSettingsTCP (fromIntegral proxyPort) (fromString proxyHost)) $ \conn' -> do
let conn = toConnection conn'
_ <- sendConnectRequest conn
-- wait 10sec for a reply before giving up
let _10sec = 1000000 * 10
responseM <- timeout _10sec $ readConnectResponse mempty conn
case responseM of
Just (isAuthorized -> True) -> app conn
Just response -> return . throwError $ ProxyForwardError (BC.unpack response)
Nothing -> return . throwError $ ProxyForwardError ("No response from the proxy after "
<> show (_10sec `div` 1000000) <> "sec" )
debug $ "Closing tcp connection to proxy " <> show proxyHost <> ":" <> show proxyPort
return ret
where
credentialsToHeader :: (ByteString, ByteString) -> ByteString
credentialsToHeader (user, password) = "Proxy-Authorization: Basic " <> B64.encode (user <> ":" <> password) <> "\r\n"
sendConnectRequest :: Connection -> IO ()
sendConnectRequest h = write h $ "CONNECT " <> fromString host <> ":" <> fromString (show port) <> " HTTP/1.0\r\n"
<> "Host: " <> fromString host <> ":" <> fromString (show port) <> "\r\n"
<> maybe mempty credentialsToHeader credentials
<> "\r\n"
readConnectResponse :: ByteString -> Connection -> IO ByteString
readConnectResponse buff conn = do
responseM <- read conn
case responseM of
Nothing -> return buff
Just response -> if "\r\n\r\n" `isInfixOf` response
then return $ buff <> response
else readConnectResponse (buff <> response) conn
isAuthorized :: ByteString -> Bool
isAuthorized response = " 200 " `isInfixOf` response
onError f = catch f $ \(e :: SomeException) -> return $
if take 10 (show e) == "user error"
then throwError $ ProxyConnectionError (show e)
else throwError $ ProxyConnectionError ("Unknown Error :: " <> show e)