diff options
-rw-r--r-- | examples/toxrelay.hs | 61 |
1 files changed, 61 insertions, 0 deletions
diff --git a/examples/toxrelay.hs b/examples/toxrelay.hs new file mode 100644 index 00000000..60c2a44b --- /dev/null +++ b/examples/toxrelay.hs | |||
@@ -0,0 +1,61 @@ | |||
1 | {-# LANGUAGE ScopedTypeVariables #-} | ||
2 | |||
3 | import Control.Exception | ||
4 | import Control.Monad | ||
5 | import Control.Concurrent.STM | ||
6 | import qualified Data.ByteString as B | ||
7 | import Data.Function | ||
8 | import qualified Data.IntMap as IntMap | ||
9 | ;import Data.IntMap (IntMap) | ||
10 | import Data.Serialize | ||
11 | import System.IO | ||
12 | import Data.Functor.Identity | ||
13 | |||
14 | import Crypto.Tox | ||
15 | import Data.Tox.Relay | ||
16 | import Network.StreamServer | ||
17 | import Network.Address (getBindAddress) | ||
18 | |||
19 | |||
20 | |||
21 | hGetPrefixed :: Serialize a => Handle -> IO (Either String a) | ||
22 | hGetPrefixed h = do | ||
23 | mlen <- runGet getWord16be <$> B.hGet h 2 | ||
24 | fmap join $ forM mlen $ \len -> runGet get <$> B.hGet h (fromIntegral len) | ||
25 | |||
26 | hGetSized :: forall x. (Sized x, Serialize x) => Handle -> IO (Either String x) | ||
27 | hGetSized h = runGet get <$> B.hGet h len | ||
28 | where | ||
29 | ConstSize len = size :: Size x | ||
30 | |||
31 | relaySession :: TVar (IntMap Handle) -> (RelayPacket -> IO ()) -> sock -> Int -> Handle -> IO () | ||
32 | relaySession cons dispatch _ conid h = do | ||
33 | atomically $ modifyTVar' cons $ IntMap.insert conid h | ||
34 | mhello <- fmap (>>= decryptPayload _todo) $ hGetSized h | ||
35 | B.hPut h $ encode $ encryptPayload _todo $ Welcome _todo _todo | ||
36 | forM_ mhello $ \hello -> do | ||
37 | let _ = hello :: Hello Identity | ||
38 | fix $ \loop -> do | ||
39 | m <- (>>= decrypt _todo >=> decodePlain) <$> hGetPrefixed h | ||
40 | forM_ m $ \p -> do | ||
41 | dispatch p | ||
42 | loop | ||
43 | `finally` | ||
44 | atomically (modifyTVar' cons $ IntMap.delete conid) | ||
45 | |||
46 | |||
47 | |||
48 | main :: IO () | ||
49 | main = do | ||
50 | cons <- newTVarIO IntMap.empty | ||
51 | a <- getBindAddress "33445" True | ||
52 | h <- streamServer ServerConfig | ||
53 | { serverWarn = hPutStrLn stderr | ||
54 | , serverSession = relaySession cons print | ||
55 | } | ||
56 | a | ||
57 | |||
58 | putStrLn $ "ENTER to quit..." | ||
59 | s <- getLine | ||
60 | |||
61 | quitListening h | ||