diff options
author | joe <joe@jerkface.net> | 2017-06-08 13:37:22 -0400 |
---|---|---|
committer | joe <joe@jerkface.net> | 2017-06-08 13:37:22 -0400 |
commit | ce4ff7cfdc77629b347d325fca62250d5e59794e (patch) | |
tree | 7f369611cf214ce9c53621db150bc87c6c0c9033 /src/Network/DatagramServer | |
parent | 3202734fa9a0bd72c8c91279c83a4674432c4f11 (diff) |
Renamed Network.RPC -> Network.DatagramServer.Types
Diffstat (limited to 'src/Network/DatagramServer')
-rw-r--r-- | src/Network/DatagramServer/Types.hs | 301 |
1 files changed, 301 insertions, 0 deletions
diff --git a/src/Network/DatagramServer/Types.hs b/src/Network/DatagramServer/Types.hs new file mode 100644 index 00000000..ac18e6ce --- /dev/null +++ b/src/Network/DatagramServer/Types.hs | |||
@@ -0,0 +1,301 @@ | |||
1 | {-# LANGUAGE ConstraintKinds #-} | ||
2 | {-# LANGUAGE DeriveDataTypeable #-} | ||
3 | {-# LANGUAGE DeriveFunctor #-} | ||
4 | {-# LANGUAGE DeriveFoldable #-} | ||
5 | {-# LANGUAGE DeriveTraversable #-} | ||
6 | {-# LANGUAGE FlexibleInstances #-} | ||
7 | {-# LANGUAGE FlexibleContexts #-} | ||
8 | {-# LANGUAGE FunctionalDependencies #-} | ||
9 | {-# LANGUAGE MultiParamTypeClasses #-} | ||
10 | {-# LANGUAGE RankNTypes #-} | ||
11 | {-# LANGUAGE ScopedTypeVariables #-} | ||
12 | {-# LANGUAGE TypeFamilies #-} | ||
13 | {-# LANGUAGE StandaloneDeriving #-} | ||
14 | module Network.DatagramServer.Types where | ||
15 | |||
16 | import Control.Applicative | ||
17 | import qualified Text.ParserCombinators.ReadP as RP | ||
18 | import Data.Digest.CRC32C | ||
19 | import Data.Word | ||
20 | import Data.Monoid | ||
21 | import Data.Hashable | ||
22 | import Data.String | ||
23 | import Data.Bits | ||
24 | import Data.ByteString (ByteString) | ||
25 | import Data.Kind (Constraint) | ||
26 | import Data.Data | ||
27 | import Data.Default | ||
28 | import Data.List.Split | ||
29 | import Data.Ord | ||
30 | import Data.IP | ||
31 | import Network.Socket | ||
32 | import Text.PrettyPrint as PP hiding ((<>)) | ||
33 | import Text.PrettyPrint.HughesPJClass hiding (($$), (<>)) | ||
34 | import Text.Read (readMaybe) | ||
35 | import Data.Serialize as S | ||
36 | import qualified Data.ByteString.Char8 as Char8 | ||
37 | import qualified Data.ByteString as BS | ||
38 | import Data.ByteString.Base16 as Base16 | ||
39 | import System.Entropy | ||
40 | |||
41 | class (Eq a, Serialize a, Typeable a, Hashable a, Pretty a) | ||
42 | => Address a where | ||
43 | toSockAddr :: a -> SockAddr | ||
44 | fromSockAddr :: SockAddr -> Maybe a | ||
45 | |||
46 | fromAddr :: (Address a, Address b) => a -> Maybe b | ||
47 | fromAddr = fromSockAddr . toSockAddr | ||
48 | |||
49 | -- | Note that port is zeroed. | ||
50 | instance Address IPv4 where | ||
51 | toSockAddr = SockAddrInet 0 . toHostAddress | ||
52 | fromSockAddr (SockAddrInet _ h) = Just (fromHostAddress h) | ||
53 | fromSockAddr _ = Nothing | ||
54 | |||
55 | -- | Note that port is zeroed. | ||
56 | instance Address IPv6 where | ||
57 | toSockAddr h = SockAddrInet6 0 0 (toHostAddress6 h) 0 | ||
58 | fromSockAddr (SockAddrInet6 _ _ h _) = Just (fromHostAddress6 h) | ||
59 | fromSockAddr _ = Nothing | ||
60 | |||
61 | -- | Note that port is zeroed. | ||
62 | instance Address IP where | ||
63 | toSockAddr (IPv4 h) = toSockAddr h | ||
64 | toSockAddr (IPv6 h) = toSockAddr h | ||
65 | fromSockAddr sa = | ||
66 | IPv4 <$> fromSockAddr sa | ||
67 | <|> IPv6 <$> fromSockAddr sa | ||
68 | |||
69 | |||
70 | |||
71 | |||
72 | data MessageClass = Error | Query | Response | ||
73 | deriving (Eq,Ord,Enum,Bounded,Data,Show,Read) | ||
74 | |||
75 | class Envelope envelope where | ||
76 | type TransactionID envelope | ||
77 | data NodeId envelope | ||
78 | |||
79 | envelopePayload :: envelope a -> a | ||
80 | envelopeTransaction :: envelope a -> TransactionID envelope | ||
81 | envelopeClass :: envelope a -> MessageClass | ||
82 | |||
83 | -- | > buildReply self addr qry response | ||
84 | -- | ||
85 | -- [ self ] this node's id. | ||
86 | -- | ||
87 | -- [ addr ] SockAddr of query origin. | ||
88 | -- | ||
89 | -- [ qry ] received query message. | ||
90 | -- | ||
91 | -- [ response ] response payload. | ||
92 | -- | ||
93 | -- Returns: response message envelope | ||
94 | buildReply :: NodeId envelope -> SockAddr -> envelope a -> b -> envelope b | ||
95 | |||
96 | -- | In Kademlia, the distance metric is XOR and the result is | ||
97 | -- interpreted as an unsigned integer. | ||
98 | newtype NodeDistance nodeid = NodeDistance nodeid | ||
99 | deriving (Eq, Ord) | ||
100 | |||
101 | -- | distance(A,B) = |A xor B| Smaller values are closer. | ||
102 | distance :: Bits nid => nid -> nid -> NodeDistance nid | ||
103 | distance a b = NodeDistance $ xor a b | ||
104 | |||
105 | instance Serialize nodeid => Show (NodeDistance nodeid) where | ||
106 | show (NodeDistance w) = Char8.unpack $ Base16.encode $ S.encode w | ||
107 | |||
108 | instance Serialize nodeid => Pretty (NodeDistance nodeid) where | ||
109 | pPrint n = text $ show n | ||
110 | |||
111 | |||
112 | -- | When 'get'ing an IP it must be 'isolate'd to the appropriate | ||
113 | -- number of bytes since we have no other way of telling which | ||
114 | -- address type we are trying to parse | ||
115 | instance Serialize IP where | ||
116 | put (IPv4 ip) = put ip | ||
117 | put (IPv6 ip) = put ip | ||
118 | |||
119 | get = do | ||
120 | n <- remaining | ||
121 | case n of | ||
122 | 4 -> IPv4 <$> get | ||
123 | 16 -> IPv6 <$> get | ||
124 | _ -> fail (show n ++ " is the wrong number of remaining bytes to parse IP") | ||
125 | |||
126 | instance Serialize IPv4 where | ||
127 | put = putWord32host . toHostAddress | ||
128 | get = fromHostAddress <$> getWord32host | ||
129 | |||
130 | instance Serialize IPv6 where | ||
131 | put ip = put $ toHostAddress6 ip | ||
132 | get = fromHostAddress6 <$> get | ||
133 | |||
134 | instance Pretty IPv4 where | ||
135 | pPrint = PP.text . show | ||
136 | {-# INLINE pPrint #-} | ||
137 | |||
138 | instance Pretty IPv6 where | ||
139 | pPrint = PP.text . show | ||
140 | {-# INLINE pPrint #-} | ||
141 | |||
142 | instance Pretty IP where | ||
143 | pPrint = PP.text . show | ||
144 | {-# INLINE pPrint #-} | ||
145 | |||
146 | instance Hashable IPv4 where | ||
147 | hashWithSalt = hashUsing toHostAddress | ||
148 | {-# INLINE hashWithSalt #-} | ||
149 | |||
150 | instance Hashable IPv6 where | ||
151 | hashWithSalt s a = hashWithSalt s (toHostAddress6 a) | ||
152 | |||
153 | instance Hashable IP where | ||
154 | hashWithSalt s (IPv4 h) = hashWithSalt s h | ||
155 | hashWithSalt s (IPv6 h) = hashWithSalt s h | ||
156 | |||
157 | |||
158 | |||
159 | |||
160 | |||
161 | data NodeAddr a = NodeAddr | ||
162 | { nodeHost :: !a | ||
163 | , nodePort :: {-# UNPACK #-} !PortNumber | ||
164 | } deriving (Eq, Ord, Typeable, Functor, Foldable, Traversable) | ||
165 | |||
166 | instance Show a => Show (NodeAddr a) where | ||
167 | showsPrec i NodeAddr {..} | ||
168 | = showsPrec i nodeHost <> showString ":" <> showsPrec i nodePort | ||
169 | |||
170 | instance Read (NodeAddr IPv4) where | ||
171 | readsPrec i = RP.readP_to_S $ do | ||
172 | ipv4 <- RP.readS_to_P (readsPrec i) | ||
173 | _ <- RP.char ':' | ||
174 | port <- toEnum <$> RP.readS_to_P (readsPrec i) | ||
175 | return $ NodeAddr ipv4 port | ||
176 | |||
177 | -- | @127.0.0.1:6882@ | ||
178 | instance Default (NodeAddr IPv4) where | ||
179 | def = "127.0.0.1:6882" | ||
180 | |||
181 | -- | KRPC compatible encoding. | ||
182 | instance Serialize a => Serialize (NodeAddr a) where | ||
183 | get = NodeAddr <$> get <*> get | ||
184 | {-# INLINE get #-} | ||
185 | put NodeAddr {..} = put nodeHost >> put nodePort | ||
186 | {-# INLINE put #-} | ||
187 | |||
188 | -- | Example: | ||
189 | -- | ||
190 | -- @nodePort \"127.0.0.1:6881\" == 6881@ | ||
191 | -- | ||
192 | instance IsString (NodeAddr IPv4) where | ||
193 | fromString str | ||
194 | | [hostAddrStr, portStr] <- splitWhen (== ':') str | ||
195 | , Just hostAddr <- readMaybe hostAddrStr | ||
196 | , Just portNum <- toEnum <$> readMaybe portStr | ||
197 | = NodeAddr hostAddr portNum | ||
198 | | otherwise = error $ "fromString: unable to parse (NodeAddr IPv4): " ++ str | ||
199 | |||
200 | instance Hashable PortNumber where | ||
201 | hashWithSalt s = hashWithSalt s . fromEnum | ||
202 | {-# INLINE hashWithSalt #-} | ||
203 | |||
204 | instance Pretty PortNumber where | ||
205 | pPrint = PP.int . fromEnum | ||
206 | {-# INLINE pPrint #-} | ||
207 | |||
208 | |||
209 | instance Hashable a => Hashable (NodeAddr a) where | ||
210 | hashWithSalt s NodeAddr {..} = hashWithSalt s (nodeHost, nodePort) | ||
211 | {-# INLINE hashWithSalt #-} | ||
212 | |||
213 | instance Pretty ip => Pretty (NodeAddr ip) where | ||
214 | pPrint NodeAddr {..} = pPrint nodeHost <> ":" <> pPrint nodePort | ||
215 | |||
216 | |||
217 | instance Serialize PortNumber where | ||
218 | get = fromIntegral <$> getWord16be | ||
219 | {-# INLINE get #-} | ||
220 | put = putWord16be . fromIntegral | ||
221 | {-# INLINE put #-} | ||
222 | |||
223 | |||
224 | |||
225 | |||
226 | data NodeInfo dht addr u = NodeInfo | ||
227 | { nodeId :: !(NodeId dht) | ||
228 | , nodeAddr :: !(NodeAddr addr) | ||
229 | , nodeAnnotation :: u | ||
230 | } deriving (Functor, Foldable, Traversable) | ||
231 | |||
232 | deriving instance ( Show (NodeId dht) | ||
233 | , Show addr | ||
234 | , Show u ) => Show (NodeInfo dht addr u) | ||
235 | |||
236 | mapAddress :: (addr -> b) -> NodeInfo dht addr u -> NodeInfo dht b u | ||
237 | mapAddress f ni = ni { nodeAddr = fmap f (nodeAddr ni) } | ||
238 | |||
239 | traverseAddress :: Applicative f => (addr -> f b) -> NodeInfo dht addr u -> f (NodeInfo dht b u) | ||
240 | traverseAddress f ni = fmap (\addr -> ni { nodeAddr = addr }) $ traverse f (nodeAddr ni) | ||
241 | |||
242 | -- Warning: Eq and Ord only look at the nodeId field. | ||
243 | instance Eq (NodeId dht) => Eq (NodeInfo dht a u) where | ||
244 | a == b = (nodeId a == nodeId b) | ||
245 | |||
246 | instance Ord (NodeId dht) => Ord (NodeInfo dht a u) where | ||
247 | compare = comparing nodeId | ||
248 | |||
249 | |||
250 | -- TODO WARN is the 'system' random suitable for this? | ||
251 | -- | Generate random NodeID used for the entire session. | ||
252 | -- Distribution of ID's should be as uniform as possible. | ||
253 | -- | ||
254 | genNodeId :: forall dht. | ||
255 | ( Serialize (NodeId dht) | ||
256 | , FiniteBits (NodeId dht) | ||
257 | ) => IO (NodeId dht) | ||
258 | genNodeId = either error id . S.decode <$> getEntropy nodeIdSize | ||
259 | where | ||
260 | nodeIdSize = finiteBitSize (undefined :: NodeId dht) `div` 8 | ||
261 | |||
262 | -- | Generate a random 'NodeId' within a range suitable for a bucket. To | ||
263 | -- obtain a sample for bucket number /index/ where /is_last/ indicates if this | ||
264 | -- is for the current deepest bucket in our routing table: | ||
265 | -- | ||
266 | -- > sample <- genBucketSample nid (bucketRange index is_last) | ||
267 | genBucketSample :: ( FiniteBits (NodeId dht) | ||
268 | , Serialize (NodeId dht) | ||
269 | ) => NodeId dht -> (Int,Word8,Word8) -> IO (NodeId dht) | ||
270 | genBucketSample n qmb = genBucketSample' getEntropy n qmb | ||
271 | |||
272 | -- | Generalizion of 'genBucketSample' that accepts a byte generator | ||
273 | -- function to use instead of the system entropy. | ||
274 | genBucketSample' :: forall m dht. | ||
275 | ( Applicative m | ||
276 | , FiniteBits (NodeId dht) | ||
277 | , Serialize (NodeId dht) | ||
278 | ) => | ||
279 | (Int -> m ByteString) -> NodeId dht -> (Int,Word8,Word8) -> m (NodeId dht) | ||
280 | genBucketSample' gen self (q,m,b) | ||
281 | | q <= 0 = either error id . S.decode <$> gen nodeIdSize | ||
282 | | q >= nodeIdSize = pure self | ||
283 | | otherwise = either error id . S.decode . build <$> gen (nodeIdSize - q + 1) | ||
284 | where | ||
285 | nodeIdSize = finiteBitSize (undefined :: NodeId dht) `div` 8 | ||
286 | build tl = BS.init hd <> BS.cons (h .|. t) (BS.tail tl) | ||
287 | where | ||
288 | hd = BS.take q $ S.encode self | ||
289 | h = xor b (complement m .&. BS.last hd) | ||
290 | t = m .&. BS.head tl | ||
291 | |||
292 | |||
293 | class Envelope envelope => WireFormat raw envelope where | ||
294 | type SerializableTo raw :: * -> Constraint | ||
295 | type CipherContext raw envelope | ||
296 | |||
297 | decodeHeaders :: CipherContext raw envelope -> ByteString -> Either String (envelope raw) | ||
298 | decodePayload :: SerializableTo raw a => envelope raw -> Either String (envelope a) | ||
299 | |||
300 | encodeHeaders :: CipherContext raw envelope -> envelope raw -> ByteString | ||
301 | encodePayload :: SerializableTo raw a => envelope a -> envelope raw | ||