wstunnel/src/Types.hs
Romain GERARD 8ca1ed9fb3 Perf improvements: Use default os setting for socket recv buffer size
+ This commit 8e38589efb (diff-8c54fc2d40ad45803c6889efbb0192bbR278) introduce a default fixed size read buffer which is too low for most modern system. Thus it induce a lot of unecessary syscall and cpu usage.
  Use the default OS settings in order to let the user control it with
  ie: /proc/sys/net/ipv4/tcp_rmem


Former-commit-id: 1fc22266bf6cda96ec8c43b52cc6da527db35173
Former-commit-id: f9cbaa2ce612df6cbfc88963a32b0a0e38c1e13e [formerly 18c0558ec79d6a82ef242b114a63738a81329ec5] [formerly 5aa78fa4a16ac891f169a02275d147ec12fc336f [formerly 32204a8d46a8f4d06e40c15380e68afa4dd1f294 [formerly 32204a8d46a8f4d06e40c15380e68afa4dd1f294 [formerly 32204a8d46a8f4d06e40c15380e68afa4dd1f294 [formerly 11e560d1fae42a64cd645e79343209e6559473d9]]]]]
Former-commit-id: 8e4ccba7062154cdaba142c6110b32b05ca08e37 [formerly a7d2f3299f4c67ea0ec9d20cbf2780382258e143]
Former-commit-id: c9ebc4a70b48e7433d65af79ef161d2b0d510f61
Former-commit-id: b5056ca3dda1f23f3bc5d8e093772874b5666fbb
Former-commit-id: 7a25a6703c1c0396425d40f4080162b43179b96d
Former-commit-id: c6d4da14dfcbb373dcb3341f246bd6675f44e4e7 [formerly 5f081b250a55f9fa091a8f13927e4c2d7980ef2a]
Former-commit-id: 886b1fa73005e8167949ede1391086d3f6ed3e00
2020-01-04 15:43:05 +01:00

136 lines
5.1 KiB
Haskell

{-# LANGUAGE DeriveAnyClass #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE StandaloneDeriving #-}
module Types where
import ClassyPrelude
import Data.Maybe
import System.IO (stdin, stdout)
import Data.ByteString (hGetSome, hPutStr)
import qualified Data.Streaming.Network as N
import qualified Network.Connection as NC
import Network.Socket (HostName, PortNumber(..))
import Network.Socket.Internal (PortNumber(..))
import qualified Network.Socket as N hiding (recv, recvFrom,
send, sendTo)
import qualified Network.Socket.ByteString as N
import qualified Network.WebSockets.Connection as WS
import System.IO.Unsafe (unsafeDupablePerformIO)
deriving instance Generic PortNumber
deriving instance Hashable PortNumber
deriving instance Generic N.SockAddr
deriving instance Hashable N.SockAddr
{-# NOINLINE defaultRecvBufferSize #-}
defaultRecvBufferSize :: Int
defaultRecvBufferSize = unsafeDupablePerformIO $
bracket (N.socket N.AF_INET N.Stream 0) N.close (\sock -> N.getSocketOption sock N.RecvBuffer)
defaultSendBufferSize :: Int
defaultSendBufferSize = defaultRecvBufferSize
data Protocol = UDP | TCP | STDIO | SOCKS5 deriving (Show, Read, Eq)
data StdioAppData = StdioAppData
data UdpAppData = UdpAppData
{ appAddr :: N.SockAddr
, appSem :: MVar ByteString
, appRead :: IO ByteString
, appWrite :: ByteString -> IO ()
}
instance N.HasReadWrite UdpAppData where
readLens f appData = fmap (\getData -> appData { appRead = getData}) (f $ appRead appData)
writeLens f appData = fmap (\writeData -> appData { appWrite = writeData}) (f $ appWrite appData)
data ProxySettings = ProxySettings
{ host :: HostName
, port :: PortNumber
, credentials :: Maybe (ByteString, ByteString)
} deriving (Show)
data TunnelSettings = TunnelSettings
{ proxySetting :: Maybe ProxySettings
, localBind :: HostName
, localPort :: PortNumber
, serverHost :: HostName
, serverPort :: PortNumber
, destHost :: HostName
, destPort :: PortNumber
, protocol :: Protocol
, useTls :: Bool
, useSocks :: Bool
, upgradePrefix :: String
, udpTimeout :: Int
}
instance Show TunnelSettings where
show TunnelSettings{..} = localBind <> ":" <> show localPort
<> (if isNothing proxySetting
then mempty
else " <==PROXY==> " <> host (fromJust proxySetting) <> ":" <> (show . port $ fromJust proxySetting)
)
<> " <==" <> (if useTls then "WSS" else "WS") <> "==> "
<> serverHost <> ":" <> show serverPort
<> " <==" <> show (if protocol == SOCKS5 then TCP else protocol) <> "==> " <> destHost <> ":" <> show destPort
data Connection = Connection
{ read :: IO (Maybe ByteString)
, write :: ByteString -> IO ()
, close :: IO ()
, rawConnection :: Maybe N.Socket
}
class ToConnection a where
toConnection :: a -> Connection
instance ToConnection StdioAppData where
toConnection conn = Connection { read = Just <$> hGetSome stdin 512
, write = hPutStr stdout
, close = return ()
, rawConnection = Nothing
}
instance ToConnection WS.Connection where
toConnection conn = Connection { read = Just <$> WS.receiveData conn
, write = WS.sendBinaryData conn
, close = WS.sendClose conn (mempty :: LByteString)
, rawConnection = Nothing
}
instance ToConnection N.AppData where
toConnection conn = Connection { read = Just <$> N.appRead conn
, write = N.appWrite conn
, close = N.appCloseConnection conn
, rawConnection = Nothing
}
instance ToConnection UdpAppData where
toConnection conn = Connection { read = Just <$> appRead conn
, write = appWrite conn
, close = return ()
, rawConnection = Nothing
}
instance ToConnection NC.Connection where
toConnection conn = Connection { read = Just <$> NC.connectionGetChunk conn
, write = NC.connectionPut conn
, close = NC.connectionClose conn
, rawConnection = Nothing
}
data Error = ProxyConnectionError String
| ProxyForwardError String
| LocalServerError String
| TunnelError String
| WebsocketError String
| TlsError String
| Other String
deriving (Show)