Maj sock5
This commit is contained in:
parent
05fd439946
commit
d2bd237bdd
3 changed files with 44 additions and 14 deletions
|
@ -7,6 +7,7 @@
|
||||||
{-# LANGUAGE RecordWildCards #-}
|
{-# LANGUAGE RecordWildCards #-}
|
||||||
{-# LANGUAGE ScopedTypeVariables #-}
|
{-# LANGUAGE ScopedTypeVariables #-}
|
||||||
{-# LANGUAGE StrictData #-}
|
{-# LANGUAGE StrictData #-}
|
||||||
|
{-# LANGUAGE ExistentialQuantification #-}
|
||||||
|
|
||||||
module Socks5 where
|
module Socks5 where
|
||||||
|
|
||||||
|
@ -212,19 +213,6 @@ data ServerSettings m = ServerSettings
|
||||||
}
|
}
|
||||||
|
|
||||||
|
|
||||||
runSocks5Server :: IO ()
|
|
||||||
runSocks5Server = do
|
|
||||||
|
|
||||||
N.runTCPServer (N.serverSettingsTCP 8888 (fromString"127.0.0.1" )) $ \cnx -> do
|
|
||||||
request <- decode .fromStrict <$> N.appRead cnx :: IO RequestAuth
|
|
||||||
traceShowM request
|
|
||||||
N.appWrite cnx (toStrict . encode $ ResponseAuth (fromIntegral socksVersion) NoAuth)
|
|
||||||
request <- decode .fromStrict <$> N.appRead cnx :: IO Request
|
|
||||||
traceShowM request
|
|
||||||
|
|
||||||
return ()
|
|
||||||
|
|
||||||
return ()
|
|
||||||
|
|
||||||
|
|
||||||
|
|
|
@ -41,6 +41,8 @@ import System.Timeout
|
||||||
import qualified Data.ByteString.Base64 as B64
|
import qualified Data.ByteString.Base64 as B64
|
||||||
|
|
||||||
import Utils
|
import Utils
|
||||||
|
import qualified Socks5
|
||||||
|
import Data.Binary (encode, decode)
|
||||||
|
|
||||||
data ProxySettings = ProxySettings
|
data ProxySettings = ProxySettings
|
||||||
{ host :: HostName
|
{ host :: HostName
|
||||||
|
@ -389,3 +391,43 @@ fromPath path = let rets = BC.split '/' . BC.drop 1 $ path
|
||||||
prt' <- readMay . BC.unpack $ prt :: Maybe Int
|
prt' <- readMay . BC.unpack $ prt :: Maybe Int
|
||||||
proto <- readMay . toUpper . BC.unpack $ protocol :: Maybe Protocol
|
proto <- readMay . toUpper . BC.unpack $ protocol :: Maybe Protocol
|
||||||
return (proto, h, prt')
|
return (proto, h, prt')
|
||||||
|
|
||||||
|
|
||||||
|
runSocks5Server :: Socks5.ServerSettings IO -> (N.AppData -> IO()) -> IO ()
|
||||||
|
runSocks5Server Socks5.ServerSettings{..} inner = do
|
||||||
|
N.runTCPServer (N.serverSettingsTCP (fromIntegral listenOn) (fromString bindOn)) $ \cnx -> do
|
||||||
|
responseAuth <- join $ onAuthentification . decode . fromStrict <$> N.appRead cnx :: IO Socks5.ResponseAuth
|
||||||
|
N.appWrite cnx (toStrict $ encode responseAuth)
|
||||||
|
request <- decode .fromStrict <$> N.appRead cnx :: IO Socks5.Request
|
||||||
|
traceShowM request
|
||||||
|
ret <- onRequest request
|
||||||
|
N.appWrite cnx (toStrict . encode $ ret)
|
||||||
|
inner cnx
|
||||||
|
|
||||||
|
|
||||||
|
|
||||||
|
return ()
|
||||||
|
|
||||||
|
return ()
|
||||||
|
|
||||||
|
|
||||||
|
|
||||||
|
main :: IO ()
|
||||||
|
main = do
|
||||||
|
|
||||||
|
runSocks5Server (Socks5.ServerSettings 8888 "127.0.0.1" auth req) $ \cnx -> do
|
||||||
|
putStrLn "tota"
|
||||||
|
da <- N.appRead cnx
|
||||||
|
putStrLn "toot"
|
||||||
|
print da
|
||||||
|
return ()
|
||||||
|
|
||||||
|
return ()
|
||||||
|
|
||||||
|
where
|
||||||
|
auth authReq = do
|
||||||
|
traceShowM authReq
|
||||||
|
return $ Socks5.ResponseAuth (fromIntegral Socks5.socksVersion) Socks5.NoAuth
|
||||||
|
req request= do
|
||||||
|
traceShowM request
|
||||||
|
return $ Socks5.Response (fromIntegral Socks5.socksVersion) Socks5.SUCCEEDED 0x00000000 0x0000
|
||||||
|
|
|
@ -15,7 +15,7 @@ cabal-version: >=1.10
|
||||||
|
|
||||||
library
|
library
|
||||||
hs-source-dirs: src
|
hs-source-dirs: src
|
||||||
exposed-modules: Tunnel, Protocols, Utils
|
exposed-modules: Tunnel, Protocols, Utils, Socks5
|
||||||
build-depends: async
|
build-depends: async
|
||||||
, base
|
, base
|
||||||
, base64-bytestring >= 1.0
|
, base64-bytestring >= 1.0
|
||||||
|
|
Loading…
Reference in a new issue