Maj sock5 proxy

This commit is contained in:
Erèbe 2016-06-20 17:10:48 +02:00
parent e6950ea526
commit a2eac5a595
2 changed files with 80 additions and 19 deletions

View file

@ -1,3 +1,4 @@
{-# LANGUAGE DeriveAnyClass #-}
{-# LANGUAGE DuplicateRecordFields #-} {-# LANGUAGE DuplicateRecordFields #-}
{-# LANGUAGE NoImplicitPrelude #-} {-# LANGUAGE NoImplicitPrelude #-}
{-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE OverloadedStrings #-}
@ -11,7 +12,14 @@ module Socks5 where
import ClassyPrelude import ClassyPrelude
import Data.Binary import Data.Binary
import Data.Binary.Get import Data.Binary.Get
import Data.Binary.Put
import qualified Data.ByteString as BC
import qualified Data.ByteString.Char8 as BC8
import Data.Either
import qualified Data.Text as T
import qualified Data.Text.Encoding as E
import Network.Socket (HostName, PortNumber) import Network.Socket (HostName, PortNumber)
import Numeric (showHex)
data AuthMethod = NoAuth data AuthMethod = NoAuth
| GSSAPI | GSSAPI
@ -48,18 +56,18 @@ instance Binary RequestAuth where
putWord8 (fromIntegral version) putWord8 (fromIntegral version)
putWord8 (fromIntegral $ length methods) putWord8 (fromIntegral $ length methods)
sequence_ (put <$> methods) sequence_ (put <$> methods)
-- Check length <= 255
get = do get = do
version <- fromIntegral <$> getWord8 version <- fromIntegral <$> getWord8
guard (version == 0x05) guard (version == 0x05)
nbMethods <- fromIntegral <$> getWord8 nbMethods <- fromIntegral <$> getWord8
guard (version <= 0xFF) guard (nbMethods > 0 && nbMethods <= 0xFF)
methods <- replicateM nbMethods get methods <- replicateM nbMethods get
return $ RequestAuth version methods return $ RequestAuth version methods
data Request = Request data Request = Request
{ version :: Int { version :: Int
, command :: Command , command :: Command
@ -70,9 +78,59 @@ data Request = Request
data Command = Connect data Command = Connect
| Bind | Bind
| UdpAssociate | UdpAssociate
deriving (Show, Eq) deriving (Show, Eq, Enum, Bounded)
instance Binary Command where
put = putWord8 . (+1) . fromIntegral . fromEnum
get = do
cmd <- (\val -> fromIntegral val - 1) <$> getWord8
guard $ cmd >= fromEnum (minBound :: Command) && cmd <= fromEnum (maxBound :: Command)
return .toEnum $ cmd
instance Binary Request where
put Request{..} = do
putWord8 (fromIntegral version)
put command
putWord8 0x00 -- RESERVED
putWord8 0x03 -- DOMAINNAME
let host = BC8.pack addr
putWord8 (fromIntegral . length $ host)
traverse_ put host
putWord16be (fromIntegral port)
get = do
version <- fromIntegral <$> getWord8
guard (version == 5)
cmd <- get :: Get Command
_ <- getWord8 -- RESERVED
opCode <- fromIntegral <$> getWord8 -- DOMAINNAME
guard (opCode == 0x03)
length <- fromIntegral <$> getWord8
host <- either (const T.empty) id . E.decodeUtf8' <$> replicateM length getWord8
guard (not $ null host)
port <- fromIntegral <$> getWord16be
return Request
{ version = version
, command = cmd
, addr = unpack host
, port = port
}
toHex :: LByteString -> String
toHex = foldr showHex "" . unpack
data Response = Response data Response = Response
{ version :: Int { version :: Int
, returnCode :: RetCode , returnCode :: RetCode

View file

@ -16,20 +16,21 @@ cabal-version: >=1.10
library library
hs-source-dirs: src hs-source-dirs: src
exposed-modules: Tunnel, Protocols, Utils exposed-modules: Tunnel, Protocols, Utils
build-depends: base build-depends: async
, classy-prelude , base
, bytestring
, async
, unordered-containers
, network
, streaming-commons
, websockets
, network-conduit-tls
, connection
, hslogger
, base64-bytestring >= 1.0 , base64-bytestring >= 1.0
, binary >= 0.7 , binary >= 0.7
, bytestring
, classy-prelude
, connection
, hslogger
, mtl , mtl
, network
, network-conduit-tls
, streaming-commons
, text >= 1.2.2.1
, unordered-containers
, websockets
default-language: Haskell2010 default-language: Haskell2010
@ -38,11 +39,12 @@ executable wstunnel
main-is: Main.hs main-is: Main.hs
ghc-options: -threaded -rtsopts -with-rtsopts=-N ghc-options: -threaded -rtsopts -with-rtsopts=-N
build-depends: base build-depends: base
, wstunnel
, cmdargs
, classy-prelude
, bytestring , bytestring
, classy-prelude
, cmdargs
, hslogger , hslogger
, text >= 1.2.2.1
, wstunnel
default-language: Haskell2010 default-language: Haskell2010
@ -51,6 +53,7 @@ test-suite wstunnel-test
hs-source-dirs: test hs-source-dirs: test
main-is: Spec.hs main-is: Spec.hs
build-depends: base build-depends: base
, text >= 1.2.2.1
, wstunnel , wstunnel
ghc-options: -threaded -rtsopts -with-rtsopts=-N ghc-options: -threaded -rtsopts -with-rtsopts=-N
default-language: Haskell2010 default-language: Haskell2010