diff options
author | joe <joe@jerkface.net> | 2017-08-31 23:46:17 -0400 |
---|---|---|
committer | joe <joe@jerkface.net> | 2017-08-31 23:46:17 -0400 |
commit | a4038e485c5a303262ebcb8370f1eccb652ebab0 (patch) | |
tree | 9a9917a0ea94701cbee9ffe0447b6d5ea55b3e2c | |
parent | f198e2b07a53603fa854b3a74702948493525613 (diff) |
DHTTransport handlers.
-rw-r--r-- | DHTHandlers.hs | 182 |
1 files changed, 182 insertions, 0 deletions
diff --git a/DHTHandlers.hs b/DHTHandlers.hs new file mode 100644 index 00000000..d98a5e60 --- /dev/null +++ b/DHTHandlers.hs | |||
@@ -0,0 +1,182 @@ | |||
1 | {-# LANGUAGE PatternSynonyms #-} | ||
2 | module DHTHandlers where | ||
3 | |||
4 | import DHTTransport | ||
5 | import Network.QueryResponse as QR hiding (Client) | ||
6 | import qualified Network.QueryResponse as QR (Client) | ||
7 | import ToxCrypto | ||
8 | import ToxMessage as Tox (PacketKind(..), pattern PingType, pattern GetNodesType, pattern DHTRequestType) | ||
9 | |||
10 | import qualified Data.Wrapper.PSQInt as Int | ||
11 | import Kademlia | ||
12 | import Network.Address (WantIP (..), ipFamily, testIdBit) | ||
13 | import qualified Network.DHT.Routing as R | ||
14 | import TriadCommittee | ||
15 | |||
16 | import Control.Monad | ||
17 | import Control.Concurrent.STM | ||
18 | import Data.Time.Clock.POSIX (POSIXTime, getPOSIXTime) | ||
19 | import Network.Socket | ||
20 | import Data.IP | ||
21 | import Data.Maybe | ||
22 | import Data.Bits | ||
23 | |||
24 | data TransactionId = TransactionId | ||
25 | { transactionKey :: Nonce8 -- ^ Used to lookup pending query. | ||
26 | , cryptoNonce :: Nonce24 -- ^ Used during the encryption layer. | ||
27 | } | ||
28 | |||
29 | classify :: DHTMessage ((,) Nonce8) -> MessageClass String PacketKind TransactionId | ||
30 | classify msg = mapMessage (\nonce24 (nonce8,_) -> go msg (TransactionId nonce8 nonce24)) msg | ||
31 | where | ||
32 | go (DHTPing {}) = IsQuery PingType | ||
33 | go (DHTGetNodes {}) = IsQuery GetNodesType | ||
34 | go (DHTPong {}) = IsResponse | ||
35 | go (DHTSendNodes {}) = IsResponse | ||
36 | go (DHTCookieRequest {}) = IsQuery (PacketKind 0x18) | ||
37 | go (DHTCookie {}) = IsResponse | ||
38 | go (DHTDHTRequest {}) = IsQuery DHTRequestType | ||
39 | |||
40 | data Routing = Routing | ||
41 | { tentativeId :: NodeInfo | ||
42 | , sched4 :: !( TVar (Int.PSQ POSIXTime) ) | ||
43 | , routing4 :: !( TVar (R.BucketList NodeInfo) ) | ||
44 | , committee4 :: TriadCommittee NodeId SockAddr | ||
45 | , sched6 :: !( TVar (Int.PSQ POSIXTime) ) | ||
46 | , routing6 :: !( TVar (R.BucketList NodeInfo) ) | ||
47 | , committee6 :: TriadCommittee NodeId SockAddr | ||
48 | } | ||
49 | |||
50 | |||
51 | -- TODO: This should cover more cases | ||
52 | isLocal (IPv6 ip6) = (ip6 == toEnum 0) | ||
53 | isLocal (IPv4 ip4) = (ip4 == toEnum 0) | ||
54 | |||
55 | isGlobal = not . isLocal | ||
56 | |||
57 | prefer4or6 :: NodeInfo -> Maybe WantIP -> WantIP | ||
58 | prefer4or6 addr iptyp = fromMaybe (ipFamily $ nodeIP addr) iptyp | ||
59 | |||
60 | toxSpace :: R.KademliaSpace NodeId NodeInfo | ||
61 | toxSpace = R.KademliaSpace | ||
62 | { R.kademliaLocation = nodeId | ||
63 | , R.kademliaTestBit = testIdBit | ||
64 | , R.kademliaXor = xor | ||
65 | } | ||
66 | |||
67 | |||
68 | pingH :: NodeInfo -> Ping -> IO Pong | ||
69 | pingH _ Ping = return Pong | ||
70 | |||
71 | getNodesH :: Routing -> NodeInfo -> GetNodes -> IO SendNodes | ||
72 | getNodesH routing addr (GetNodes nid) = do | ||
73 | let preferred = prefer4or6 addr Nothing | ||
74 | |||
75 | (append4,append6) <- atomically $ do | ||
76 | ni4 <- R.thisNode <$> readTVar (routing4 routing) | ||
77 | ni6 <- R.thisNode <$> readTVar (routing6 routing) | ||
78 | return $ case ipFamily (nodeIP addr) of | ||
79 | Want_IP4 | isGlobal (nodeIP ni6) -> (id, (++ [ni6])) | ||
80 | Want_IP6 | isGlobal (nodeIP ni4) -> ((++ [ni4]), id) | ||
81 | _ -> (id, id) | ||
82 | ks <- go append4 $ routing4 routing | ||
83 | ks6 <- go append6 $ routing6 routing | ||
84 | let (ns1,ns2) = case preferred of Want_IP6 -> (ks6,ks) | ||
85 | Want_IP4 -> (ks,ks6) | ||
86 | return $ SendNodes | ||
87 | $ if null ns2 then ns1 | ||
88 | else take 4 (take 3 ns1 ++ ns2) | ||
89 | where | ||
90 | go f var = f . R.kclosest toxSpace k nid <$> atomically (readTVar var) | ||
91 | |||
92 | k = 4 | ||
93 | |||
94 | type Message = DHTMessage ((,) Nonce8) | ||
95 | |||
96 | type Client = QR.Client String PacketKind TransactionId NodeInfo Message | ||
97 | |||
98 | |||
99 | wrapAssym :: TransactionId -> NodeInfo -> NodeInfo -> dta -> Assym (Nonce8,dta) | ||
100 | wrapAssym (TransactionId n8 n24) src dst dta = Assym | ||
101 | { senderKey = let NodeId pubkey = nodeId src in pubkey | ||
102 | , assymNonce = n24 | ||
103 | , assymData = (n8, dta) | ||
104 | } | ||
105 | |||
106 | serializer :: PacketKind | ||
107 | -> (Assym (Nonce8,ping) -> Message) | ||
108 | -> (Message -> Maybe (Assym (Nonce8,pong))) | ||
109 | -> MethodSerializer TransactionId NodeInfo Message PacketKind ping (Maybe pong) | ||
110 | serializer pktkind mkping mkpong = MethodSerializer | ||
111 | { methodTimeout = 5 | ||
112 | , method = pktkind | ||
113 | -- wrapQuery :: tid -> addr -> addr -> qry -> x | ||
114 | , wrapQuery = \tid src dst ping -> mkping $ wrapAssym tid src dst ping | ||
115 | -- unwrapResponse :: x -> b | ||
116 | , unwrapResponse = fmap (snd . assymData) . mkpong | ||
117 | } | ||
118 | |||
119 | |||
120 | unpong :: Message -> Maybe (Assym (Nonce8,Pong)) | ||
121 | unpong (DHTPong assym) = Just assym | ||
122 | unpong _ = Nothing | ||
123 | |||
124 | ping :: Client -> NodeInfo -> IO Bool | ||
125 | ping client addr = do | ||
126 | reply <- QR.sendQuery client (serializer PingType DHTPing unpong) Ping addr | ||
127 | maybe (return False) (\Pong -> return True) $ join reply | ||
128 | |||
129 | unsendNodes :: Message -> Maybe (Assym (Nonce8,SendNodes)) | ||
130 | unsendNodes (DHTSendNodes assym) = Just assym | ||
131 | unsendNodes _ = Nothing | ||
132 | |||
133 | unwrapNodes :: SendNodes -> ( [NodeInfo], [NodeInfo], () ) | ||
134 | unwrapNodes (SendNodes ns) = (ns,ns,()) | ||
135 | |||
136 | getNodes :: Client -> NodeId -> NodeInfo -> IO (Maybe ([NodeInfo],[NodeInfo],())) | ||
137 | getNodes client nid addr = do | ||
138 | reply <- QR.sendQuery client (serializer GetNodesType DHTGetNodes unsendNodes) (GetNodes nid) addr | ||
139 | return $ fmap unwrapNodes $ join reply | ||
140 | |||
141 | updateRouting :: Client -> Routing -> NodeInfo -> Message -> IO () | ||
142 | updateRouting client routing naddr msg = do | ||
143 | -- hPutStrLn stderr $ "updateRouting "++show typ | ||
144 | -- TODO: check msg type | ||
145 | case prefer4or6 naddr Nothing of | ||
146 | Want_IP4 -> updateTable client naddr (routing4 routing) (committee4 routing) (sched4 routing) | ||
147 | Want_IP6 -> updateTable client naddr (routing6 routing) (committee6 routing) (sched6 routing) | ||
148 | |||
149 | updateTable :: Client -> NodeInfo -> TVar (R.BucketList NodeInfo) -> TriadCommittee NodeId SockAddr -> TVar (Int.PSQ POSIXTime) -> IO () | ||
150 | updateTable client naddr tbl committee sched = do | ||
151 | self <- atomically $ R.thisNode <$> readTVar tbl | ||
152 | when (nodeIP self /= nodeIP naddr) $ do | ||
153 | -- TODO: IP address vote? | ||
154 | insertNode (toxKademlia client committee tbl sched) naddr | ||
155 | |||
156 | toxKademlia :: Client -> TriadCommittee NodeId SockAddr -> TVar (R.BucketList NodeInfo) -> TVar (Int.PSQ POSIXTime) -> Kademlia NodeId NodeInfo | ||
157 | toxKademlia client committee var sched | ||
158 | = Kademlia quietInsertions | ||
159 | toxSpace | ||
160 | (vanillaIO var $ ping client) | ||
161 | { tblTransition = \tr -> do | ||
162 | io1 <- transitionCommittee committee tr | ||
163 | io2 <- touchBucket toxSpace (15*60) var sched tr | ||
164 | return $ do | ||
165 | io1 >> io2 | ||
166 | {- | ||
167 | hPutStrLn stderr $ unwords | ||
168 | [ show (transitionedTo tr) | ||
169 | , show (transitioningNode tr) | ||
170 | ] | ||
171 | -} | ||
172 | return () | ||
173 | } | ||
174 | |||
175 | transitionCommittee :: TriadCommittee NodeId SockAddr -> RoutingTransition NodeInfo -> STM (IO ()) | ||
176 | transitionCommittee committee (RoutingTransition ni Stranger) = do | ||
177 | delVote committee (nodeId ni) | ||
178 | return $ do | ||
179 | -- hPutStrLn stderr $ "delVote "++show (nodeId ni) | ||
180 | return () | ||
181 | transitionCommittee committee _ = return $ return () | ||
182 | |||