
Former-commit-id: 5adb049b14d9380e46c4f80c10a1d8062fe83904 [formerly b10cc7b46bda496234557f7b61ad7aa3ca988527] [formerly 557a8511fa2d9470bbd1a544d8b7e509103314d5 [formerly e1d1f02a69b56adf64d3aa0fef35f5e47e08039f [formerly e1d1f02a69b56adf64d3aa0fef35f5e47e08039f [formerly e1d1f02a69b56adf64d3aa0fef35f5e47e08039f [formerly 0fc191817c92b9b62300bec0acd8fb64c148cbc7]]]]] Former-commit-id: da13228c115750898b6cfbd4c4c91ce63b08b509 [formerly 4feac2317e1efbf60134e585c96cdaa6ee3b18ff] Former-commit-id: 5bf83c3e60bcdffc02c05f5fc826659b607188dc Former-commit-id: b38569743f40ab3dc1c7a8792fafaa143b5d39b8 Former-commit-id: de5fd5b6a52f8c5d8fdc224dcfde2f7b35cf9c4f Former-commit-id: a14726dacbedeab41fdde692399a282d1f784dfe [formerly 2ac7520615a3a508c4c1905433d7e2b5887c1a59] Former-commit-id: 7996f71d276326ea9e698d5ae63f465070e73b50
303 lines
13 KiB
Haskell
303 lines
13 KiB
Haskell
{-# LANGUAGE FlexibleContexts #-}
|
|
{-# LANGUAGE OverloadedStrings #-}
|
|
|
|
|
|
module Tunnel
|
|
( runClient
|
|
, runServer
|
|
, rrunTCPClient
|
|
) where
|
|
|
|
import ClassyPrelude
|
|
import Data.Maybe (fromJust)
|
|
|
|
import qualified Data.ByteString.Char8 as BC
|
|
|
|
import qualified Data.Conduit.Network.TLS as N
|
|
import qualified Data.Streaming.Network as N
|
|
|
|
import Network.Socket (HostName, PortNumber)
|
|
import qualified Network.Socket as N
|
|
import qualified Network.Socket.ByteString as N
|
|
import qualified Network.Socket.ByteString.Lazy as NL
|
|
|
|
import qualified Network.WebSockets as WS
|
|
import qualified Network.WebSockets.Connection as WS
|
|
import qualified Network.WebSockets.Stream as WS
|
|
|
|
import Control.Monad.Except
|
|
import qualified Network.Connection as NC
|
|
|
|
import qualified Data.ByteString.Base64 as B64
|
|
|
|
import Types
|
|
import Protocols
|
|
import qualified Socks5
|
|
import Logger
|
|
|
|
|
|
|
|
rrunTCPClient :: MonadError Error m => N.ClientSettings -> (Connection -> IO (m a)) -> IO (m a)
|
|
rrunTCPClient cfg app = onError $ bracket
|
|
(do
|
|
let _10sec = 1000000 * 10
|
|
ret <- timeout _10sec $ N.getSocketFamilyTCP (N.getHost cfg) (N.getPort cfg) (N.getAddrFamily cfg)
|
|
(s, addr) <- pure $ case ret of
|
|
Just (s, addr) -> (s, addr)
|
|
Nothing -> error $ "Cannot open tcp socket within 10 sec to " <> show (N.getHost cfg) <> ":" <> show (N.getPort cfg)
|
|
|
|
so_mark_val <- readIORef sO_MARK_Value
|
|
when (so_mark_val /= 0 && N.isSupportedSocketOption sO_MARK) (N.setSocketOption s sO_MARK so_mark_val)
|
|
return (s,addr)
|
|
)
|
|
(\r -> catch (N.close $ fst r) (\(_ :: SomeException) -> return ()))
|
|
(\(s, _) -> app Connection
|
|
{ read = Just <$> N.safeRecv s defaultRecvBufferSize
|
|
, write = N.sendAll s
|
|
, close = N.close s
|
|
, rawConnection = Just s
|
|
})
|
|
where
|
|
onError = flip catch (\(e :: SomeException) -> return . throwError . TunnelError $ show e)
|
|
|
|
--
|
|
-- Pipes
|
|
--
|
|
tunnelingClientP :: MonadError Error m => TunnelSettings -> (Connection -> IO (m ())) -> (Connection -> IO (m ()))
|
|
tunnelingClientP cfg@TunnelSettings{..} app conn = onError $ do
|
|
debug "Opening Websocket stream"
|
|
|
|
stream <- connectionToStream conn
|
|
let authorization = ([("Authorization", "Basic " <> B64.encode upgradeCredentials) | not (null upgradeCredentials)])
|
|
let headers = authorization <> customHeaders
|
|
let hostname = if not (null hostHeader) then BC.unpack hostHeader else serverHost
|
|
|
|
ret <- WS.runClientWithStream stream hostname (toPath cfg) WS.defaultConnectionOptions headers run
|
|
|
|
debug "Closing Websocket stream"
|
|
return ret
|
|
|
|
where
|
|
connectionToStream Connection{..} = WS.makeStream read (write . toStrict . fromJust)
|
|
onError = flip catch (\(e :: SomeException) -> return . throwError . WebsocketError $ show e)
|
|
run cnx = WS.withPingThread cnx websocketPingFrequencySec mempty (app (toConnection cnx))
|
|
|
|
|
|
tlsClientP :: MonadError Error m => TunnelSettings -> (Connection -> IO (m ())) -> (Connection -> IO (m ()))
|
|
tlsClientP TunnelSettings{..} app conn = onError $ do
|
|
debug "Doing tls Handshake"
|
|
|
|
context <- NC.initConnectionContext
|
|
let socket = fromJust $ rawConnection conn
|
|
h <- N.socketToHandle socket ReadWriteMode
|
|
|
|
connection <- NC.connectFromHandle context h connectionParams
|
|
ret <- app (toConnection connection) `finally` hClose h
|
|
|
|
debug "Closing TLS"
|
|
return ret
|
|
|
|
where
|
|
onError = flip catch (\(e :: SomeException) -> return . throwError . TlsError $ show e)
|
|
tlsSettings = NC.TLSSettingsSimple { NC.settingDisableCertificateValidation = not tlsVerifyCertificate
|
|
, NC.settingDisableSession = False
|
|
, NC.settingUseServerName = False
|
|
}
|
|
connectionParams = NC.ConnectionParams { NC.connectionHostname = if tlsSNI == mempty then serverHost else BC.unpack tlsSNI
|
|
, NC.connectionPort = serverPort
|
|
, NC.connectionUseSecure = Just tlsSettings
|
|
, NC.connectionUseSocks = Nothing
|
|
}
|
|
|
|
|
|
--
|
|
-- Connectors
|
|
--
|
|
tcpConnection :: MonadError Error m => TunnelSettings -> (Connection -> IO (m ())) -> IO (m ())
|
|
tcpConnection TunnelSettings{..} app = onError $ do
|
|
debug $ "Opening tcp connection to " <> fromString serverHost <> ":" <> show (fromIntegral serverPort :: Int)
|
|
|
|
ret <- rrunTCPClient (N.clientSettingsTCP (fromIntegral serverPort) (fromString serverHost)) app
|
|
|
|
debug $ "Closing tcp connection to " <> fromString serverHost <> ":" <> show (fromIntegral serverPort :: Int)
|
|
return ret
|
|
|
|
where
|
|
onError = flip catch (\(e :: SomeException) -> return $ (throwError $ TunnelError $ show e))
|
|
|
|
|
|
|
|
httpProxyConnection :: MonadError Error m => TunnelSettings -> (Connection -> IO (m ())) -> IO (m ())
|
|
httpProxyConnection TunnelSettings{..} app = onError $ do
|
|
let settings = fromJust proxySetting
|
|
debug $ "Opening tcp connection to proxy " <> show settings
|
|
|
|
ret <- rrunTCPClient (N.clientSettingsTCP (fromIntegral (port settings)) (BC.pack $ host settings)) $ \conn -> do
|
|
_ <- sendConnectRequest settings conn
|
|
responseM <- timeout (1000000 * 10) $ readConnectResponse mempty conn
|
|
let response = fromMaybe "No response of the proxy after 10s" responseM
|
|
|
|
if isAuthorized response
|
|
then app conn
|
|
else return . throwError . ProxyForwardError $ BC.unpack response
|
|
|
|
debug $ "Closing tcp connection to proxy " <> show settings
|
|
return ret
|
|
|
|
where
|
|
credentialsToHeader (user, password) = "Proxy-Authorization: Basic " <> B64.encode (user <> ":" <> password) <> "\r\n"
|
|
sendConnectRequest settings h = write h $ "CONNECT " <> fromString serverHost <> ":" <> fromString (show serverPort) <> " HTTP/1.0\r\n"
|
|
<> "Host: " <> fromString serverHost <> ":" <> fromString (show serverPort) <> "\r\n"
|
|
<> maybe mempty credentialsToHeader (credentials settings)
|
|
<> "\r\n"
|
|
|
|
readConnectResponse buff conn = do
|
|
response <- fromJust <$> read conn
|
|
if "\r\n\r\n" `BC.isInfixOf` response
|
|
then return $ buff <> response
|
|
else readConnectResponse (buff <> response) conn
|
|
|
|
isAuthorized response = " 200 " `BC.isInfixOf` response
|
|
|
|
onError = flip catch (\(e :: SomeException) -> return $ when (take 10 (show e) == "user error") (throwError $ ProxyConnectionError $ show e))
|
|
|
|
--
|
|
-- Client
|
|
--
|
|
runClient :: TunnelSettings -> IO ()
|
|
runClient cfg@TunnelSettings{..} = do
|
|
let withEndPoint = if isJust proxySetting then httpProxyConnection cfg else tcpConnection cfg
|
|
let doTlsIf tlsNeeded app = if tlsNeeded then tlsClientP cfg app else app
|
|
let withTunnel cfg' app = withEndPoint (doTlsIf useTls . tunnelingClientP cfg' $ app)
|
|
|
|
let app cfg' localH = do
|
|
ret <- withTunnel cfg' $ \remoteH -> do
|
|
ret <- remoteH <==> toConnection localH
|
|
info $ "CLOSE tunnel :: " <> show cfg'
|
|
return ret
|
|
|
|
handleError ret
|
|
|
|
case protocol of
|
|
UDP -> runUDPServer (localBind, localPort) udpTimeout (app cfg)
|
|
TCP -> runTCPServer (localBind, localPort) (app cfg)
|
|
STDIO -> runSTDIOServer (app cfg)
|
|
SOCKS5 -> runSocks5Server (Socks5.ServerSettings localPort localBind) cfg app
|
|
|
|
|
|
|
|
|
|
--
|
|
-- Server
|
|
--
|
|
runTlsTunnelingServer :: (ByteString, ByteString) -> (HostName, PortNumber) -> ((ByteString, Int) -> Bool) -> IO ()
|
|
runTlsTunnelingServer (tlsCert, tlsKey) endPoint@(bindTo, portNumber) isAllowed = do
|
|
info $ "WAIT for TLS connection on " <> toStr endPoint
|
|
|
|
N.runTCPServerTLS (N.tlsConfigBS (fromString bindTo) (fromIntegral portNumber) tlsCert tlsKey) $ \sClient ->
|
|
runApp sClient WS.defaultConnectionOptions (serverEventLoop (N.appSockAddr sClient) isAllowed)
|
|
|
|
info "SHUTDOWN server"
|
|
|
|
where
|
|
runApp :: N.AppData -> WS.ConnectionOptions -> WS.ServerApp -> IO ()
|
|
runApp appData opts app = do
|
|
stream <- WS.makeStream (N.appRead appData <&> \payload -> if payload == mempty then Nothing else Just payload) (N.appWrite appData . toStrict . fromJust)
|
|
--let socket = fromJust $ N.appRawSocket appData
|
|
--stream <- WS.makeStream (N.recv socket defaultRecvBufferSize <&> \payload -> if payload == mempty then Nothing else Just payload) (NL.sendAll socket . fromJust)
|
|
bracket (WS.makePendingConnectionFromStream stream opts)
|
|
(\conn -> catch (WS.close $ WS.pendingStream conn) (\(_ :: SomeException) -> return ()))
|
|
app
|
|
|
|
runTunnelingServer :: (HostName, PortNumber) -> ((ByteString, Int) -> Bool) -> IO ()
|
|
runTunnelingServer endPoint@(host, port) isAllowed = do
|
|
info $ "WAIT for connection on " <> toStr endPoint
|
|
|
|
let srvSet = N.setReadBufferSize defaultRecvBufferSize $ N.serverSettingsTCP (fromIntegral port) (fromString host)
|
|
void $ N.runTCPServer srvSet $ \sClient -> do
|
|
let socket = fromJust $ N.appRawSocket sClient
|
|
stream <- WS.makeStream (N.recv socket defaultRecvBufferSize <&> \payload -> if payload == mempty then Nothing else Just payload) (NL.sendAll socket . fromJust)
|
|
runApp stream WS.defaultConnectionOptions (serverEventLoop (N.appSockAddr sClient) isAllowed)
|
|
|
|
info "CLOSE server"
|
|
|
|
where
|
|
runApp :: WS.Stream -> WS.ConnectionOptions -> WS.ServerApp -> IO ()
|
|
runApp socket opts = bracket (WS.makePendingConnectionFromStream socket opts)
|
|
(\conn -> catch (WS.close $ WS.pendingStream conn) (\(_ :: SomeException) -> return ()))
|
|
|
|
serverEventLoop :: N.SockAddr -> ((ByteString, Int) -> Bool) -> WS.PendingConnection -> IO ()
|
|
serverEventLoop sClient isAllowed pendingConn = do
|
|
let path = fromPath . WS.requestPath $ WS.pendingRequest pendingConn
|
|
let forwardedFor = filter (\(header, _) -> header == "x-forwarded-for") $ WS.requestHeaders $ WS.pendingRequest pendingConn
|
|
info $ "NEW incoming connection from " <> show sClient <> " " <> show forwardedFor
|
|
case path of
|
|
Nothing -> info "Rejecting connection" >> WS.rejectRequest pendingConn "Invalid tunneling information"
|
|
Just (!proto, !rhost, !rport) ->
|
|
if not $ isAllowed (rhost, rport)
|
|
then do
|
|
info "Rejecting tunneling"
|
|
WS.rejectRequest pendingConn "Restriction is on, You cannot request this tunneling"
|
|
else do
|
|
conn <- WS.acceptRequest pendingConn
|
|
case proto of
|
|
UDP -> runUDPClient (BC.unpack rhost, fromIntegral rport) (\cnx -> void $ toConnection conn <==> toConnection cnx)
|
|
TCP -> runTCPClient (BC.unpack rhost, fromIntegral rport) (\cnx -> void $ toConnection conn <==> toConnection cnx)
|
|
STDIO -> mempty
|
|
SOCKS5 -> mempty
|
|
|
|
|
|
runServer :: Maybe (ByteString, ByteString) -> (HostName, PortNumber) -> ((ByteString, Int) -> Bool) -> IO ()
|
|
runServer Nothing = runTunnelingServer
|
|
runServer (Just (tlsCert, tlsKey)) = runTlsTunnelingServer (tlsCert, tlsKey)
|
|
|
|
|
|
|
|
|
|
--
|
|
-- Commons
|
|
--
|
|
toPath :: TunnelSettings -> String
|
|
toPath TunnelSettings{..} = "/" <> upgradePrefix <> "/"
|
|
<> toLower (show $ if protocol == UDP then UDP else TCP)
|
|
<> "/" <> destHost <> "/" <> show destPort
|
|
|
|
fromPath :: ByteString -> Maybe (Protocol, ByteString, Int)
|
|
fromPath path = let rets = BC.split '/' . BC.drop 1 $ path
|
|
in do
|
|
guard (length rets == 4)
|
|
let [_, protocol, h, prt] = rets
|
|
prt' <- readMay . BC.unpack $ prt :: Maybe Int
|
|
proto <- readMay . toUpper . BC.unpack $ protocol :: Maybe Protocol
|
|
return (proto, h, prt')
|
|
|
|
handleError :: Either Error () -> IO ()
|
|
handleError (Right ()) = return ()
|
|
handleError (Left errMsg) =
|
|
case errMsg of
|
|
ProxyConnectionError msg -> err "Cannot connect to the proxy" >> debugPP msg
|
|
ProxyForwardError msg -> err "Connection not allowed by the proxy" >> debugPP msg
|
|
TunnelError msg -> err "Cannot establish the connection to the server" >> debugPP msg
|
|
LocalServerError msg -> err "Cannot create the localServer, port already binded ?" >> debugPP msg
|
|
WebsocketError msg -> err "Cannot establish websocket connection with the server" >> debugPP msg
|
|
TlsError msg -> err "Cannot do tls handshake with the server" >> debugPP msg
|
|
Other msg -> debugPP msg
|
|
|
|
where
|
|
debugPP msg = debug $ "====\n" <> msg <> "\n===="
|
|
|
|
myTry :: MonadError Error m => IO a -> IO (m ())
|
|
myTry f = either (\(e :: SomeException) -> throwError . Other $ show e) (const $ return ()) <$> try f
|
|
|
|
(<==>) :: Connection -> Connection -> IO (Either Error ())
|
|
(<==>) hTunnel hOther =
|
|
myTry $ race_ (propagateReads hTunnel hOther) (propagateWrites hTunnel hOther)
|
|
|
|
propagateReads :: Connection -> Connection -> IO ()
|
|
propagateReads hTunnel hOther = forever $ read hTunnel >>= write hOther . fromJust
|
|
|
|
|
|
propagateWrites :: Connection -> Connection -> IO ()
|
|
propagateWrites hTunnel hOther = do
|
|
payload <- fromJust <$> read hOther
|
|
unless (null payload) (write hTunnel payload >> propagateWrites hTunnel hOther)
|