Add restric to for the server

This commit is contained in:
Erèbe 2016-05-16 23:33:00 +02:00
parent 58a313f354
commit b40e0e677c
2 changed files with 29 additions and 12 deletions

View file

@ -5,8 +5,9 @@ module Main where
import Lib import Lib
import ClassyPrelude (readMay) import ClassyPrelude (guard, readMay)
import qualified Data.ByteString.Char8 as BC import qualified Data.ByteString.Char8 as BC
import Data.Maybe (fromMaybe)
import System.Console.CmdArgs import System.Console.CmdArgs
import System.Environment (getArgs, withArgs) import System.Environment (getArgs, withArgs)
@ -77,6 +78,17 @@ parseTunnelInfo str = mk $ BC.unpack <$> BC.split ':' (BC.pack str)
mk _ = error $ "Invalid tunneling information `" ++ str ++ "`, please use format [BIND:]PORT:HOST:PORT" mk _ = error $ "Invalid tunneling information `" ++ str ++ "`, please use format [BIND:]PORT:HOST:PORT"
parseRestrictTo :: String -> ((String, Int)-> Bool)
parseRestrictTo "" = const True
parseRestrictTo str = let (h, p) = fromMaybe (error "Invalid Parameter restart") parse
in (\(hst, port) -> hst == h && port == p)
where
parse = do
let ret = BC.unpack <$> BC.split ':' (BC.pack str)
guard (length ret == 2)
portNumber <- readMay $ ret !! 1 :: Maybe Int
return (head ret, portNumber)
main :: IO () main :: IO ()
main = do main = do
args <- getArgs args <- getArgs
@ -87,7 +99,7 @@ main = do
if serverMode cfg if serverMode cfg
then putStrLn ("Starting server with opts " ++ show serverInfo ) then putStrLn ("Starting server with opts " ++ show serverInfo )
>> runServer (host serverInfo, fromIntegral $ port serverInfo) >> runServer (host serverInfo, fromIntegral $ port serverInfo) (parseRestrictTo $ restrictTo cfg)
else if not $ null (localToRemote cfg) else if not $ null (localToRemote cfg)
then let (TunnelInfo lHost lPort rHost rPort) = parseTunnelInfo (localToRemote cfg) then let (TunnelInfo lHost lPort rHost rPort) = parseTunnelInfo (localToRemote cfg)
in runClient (useTls serverInfo) (if udpMode cfg then UDP else TCP) (lHost, (fromIntegral lPort)) in runClient (useTls serverInfo) (if udpMode cfg then UDP else TCP) (lHost, (fromIntegral lPort))

View file

@ -128,18 +128,22 @@ runTunnelingClient proto (wsHost, wsPort) (remoteHost, remotePort) app = do
putStrLn $ "CLOSE connection to " <> tshow remoteHost <> ":" <> tshow remotePort putStrLn $ "CLOSE connection to " <> tshow remoteHost <> ":" <> tshow remotePort
runTunnelingServer :: (HostName, PortNumber) -> IO () runTunnelingServer :: (HostName, PortNumber) -> ((ByteString, Int) -> Bool) -> IO ()
runTunnelingServer (host, port) = do runTunnelingServer (host, port) isAllowed = do
putStrLn $ "WAIT for connection on " <> tshow host <> ":" <> tshow port putStrLn $ "WAIT for connection on " <> tshow host <> ":" <> tshow port
WS.runServer host (fromIntegral port) $ \pendingConn -> do WS.runServer host (fromIntegral port) $ \pendingConn -> do
let path = parsePath . WS.requestPath $ WS.pendingRequest pendingConn let path = parsePath . WS.requestPath $ WS.pendingRequest pendingConn
case path of case path of
Nothing -> putStrLn "Rejecting connection" >> WS.rejectRequest pendingConn "Invalid tunneling information" Nothing -> putStrLn "Rejecting connection" >> WS.rejectRequest pendingConn "Invalid tunneling information"
Just (!proto, !rhost, !rport) -> do Just (!proto, !rhost, !rport) ->
conn <- WS.acceptRequest pendingConn if isAllowed (rhost, rport)
case proto of then do
UDP -> runUDPClient (BC.unpack rhost, fromIntegral rport) (propagateRW conn) conn <- WS.acceptRequest pendingConn
TCP -> runTCPClient (BC.unpack rhost, fromIntegral rport) (propagateRW conn) case proto of
UDP -> runUDPClient (BC.unpack rhost, fromIntegral rport) (propagateRW conn)
TCP -> runTCPClient (BC.unpack rhost, fromIntegral rport) (propagateRW conn)
else
putStrLn "Rejecting tunneling" >> WS.rejectRequest pendingConn "Restriction is on, You cannot request this tunneling"
putStrLn "CLOSE server" putStrLn "CLOSE server"
@ -176,8 +180,9 @@ runClient useTls proto local wsServer remote = do
TCP -> runTCPServer local (\hOther -> out (`propagateRW` hOther)) TCP -> runTCPServer local (\hOther -> out (`propagateRW` hOther))
runServer :: (HostName, PortNumber) -> IO () runServer :: (HostName, PortNumber) -> ((String, Int) -> Bool) -> IO ()
runServer = runTunnelingServer runServer wsInfo isAllowed = let isAllowed' (str, port) = isAllowed (BC.unpack str, fromIntegral port)
in runTunnelingServer wsInfo isAllowed'
runTlsTunnelingClient :: Proto -> (HostName, PortNumber) -> (HostName, PortNumber) -> (WS.Connection -> IO ()) -> IO () runTlsTunnelingClient :: Proto -> (HostName, PortNumber) -> (HostName, PortNumber) -> (WS.Connection -> IO ()) -> IO ()