wstunnel/src/Types.hs
Gabriel Ebner 748b329514 Support network >= 3.1.2 (#107)
* Bump to stackage LTS 19.2 for network >= 3.1.2

* Support network >= 3.1.2

* Disable docker login on forked repositories.

* Update dockerfile.

Former-commit-id: 34645524c3221a596fb59e8dbad4381f10f93933
Former-commit-id: bcc40487b5cc36af72bcccfabb77fc2fe3933377 [formerly 36e5a23cc5f50719fbc334741e41101527e44a32] [formerly 35b7f5ad0096ba3e1ba2b3946e9eb46d17b477c5 [formerly c1e83ef29175f48c1bc199405670ac70a85d7bfa [formerly c3d180e0a066c83db261f296055e0fc6485f85cd] [formerly 29ca68bf69f44df5770d665f1997fce6afe8c6a9] [formerly 29ca68bf69f44df5770d665f1997fce6afe8c6a9 [formerly 29ca68bf69f44df5770d665f1997fce6afe8c6a9 [formerly dd31ffea070f0cccf6fb8064ea6f445a2d8b3d7c]]]]]
Former-commit-id: d9e2f84d44728723b9ddcbad5ae1d088fdf574b2 [formerly ccdba4b1ec6a29b032c7696f8d6893940f44c25c]
Former-commit-id: 10137d6047496f188dc4d29f31ab21452aedb7ad
Former-commit-id: 0549973a0980949a8743f6cac6ea5f265ccdd583
Former-commit-id: 061811becd00ed2022ed1c6c35c7aee484dccdf6
Former-commit-id: 20ac5d98e082c67e650a6bcf63d380ba08973ade [formerly 2ce99e6abc267a2f1db82ee0ed3f5ce762ecabb2]
Former-commit-id: b1be9c6813f3c3f1a9ffa8cd3915954cbc902723
2022-04-16 11:23:52 +02:00

150 lines
5.5 KiB
Haskell

{-# LANGUAGE DeriveAnyClass #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE StandaloneDeriving #-}
{-# LANGUAGE StrictData #-}
module Types where
import ClassyPrelude
import Data.Maybe
import System.IO (stdin, stdout)
import Data.ByteString (hGetSome, hPutStr)
import Data.CaseInsensitive ( CI )
import qualified Data.Streaming.Network as N
import qualified Network.Connection as NC
import Network.Socket (HostName, 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)
instance Hashable PortNumber where
hashWithSalt s p = hashWithSalt s (fromEnum p)
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)
sO_MARK :: N.SocketOption
sO_MARK = N.SockOpt 1 36 -- https://elixir.bootlin.com/linux/latest/source/arch/alpha/include/uapi/asm/socket.h#L64
{-# NOINLINE sO_MARK_Value #-}
sO_MARK_Value :: IORef Int
sO_MARK_Value = unsafeDupablePerformIO $ (newIORef 0)
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
, upgradeCredentials
:: ByteString
, tlsSNI :: ByteString
, hostHeader :: ByteString
, udpTimeout :: Int
, websocketPingFrequencySec :: Int
, customHeaders :: [(CI ByteString, ByteString)]
}
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)