summaryrefslogtreecommitdiff
path: root/src/Network/Tox
diff options
context:
space:
mode:
authorjoe <joe@jerkface.net>2017-09-15 03:53:43 -0400
committerjoe <joe@jerkface.net>2017-09-15 03:53:43 -0400
commit93e62f0563c69ec206eea01cabaa23e5784bcc82 (patch)
tree45128737e2acf4029252ddcb70a2aab6b4bd6a21 /src/Network/Tox
parent7acfd91d1390d2137994366cbdfdfc6b9a2885fd (diff)
Moved ToxAddress to hierarchical location.
Diffstat (limited to 'src/Network/Tox')
-rw-r--r--src/Network/Tox/Address.hs456
1 files changed, 456 insertions, 0 deletions
diff --git a/src/Network/Tox/Address.hs b/src/Network/Tox/Address.hs
new file mode 100644
index 00000000..0d853bcb
--- /dev/null
+++ b/src/Network/Tox/Address.hs
@@ -0,0 +1,456 @@
1{-# LANGUAGE ApplicativeDo #-}
2{-# LANGUAGE BangPatterns #-}
3{-# LANGUAGE CPP #-}
4{-# LANGUAGE DataKinds #-}
5{-# LANGUAGE DeriveDataTypeable #-}
6{-# LANGUAGE DeriveFunctor #-}
7{-# LANGUAGE DeriveTraversable #-}
8{-# LANGUAGE ExistentialQuantification #-}
9{-# LANGUAGE FlexibleInstances #-}
10{-# LANGUAGE GADTs #-}
11{-# LANGUAGE GeneralizedNewtypeDeriving #-}
12{-# LANGUAGE KindSignatures #-}
13{-# LANGUAGE PatternSynonyms #-}
14{-# LANGUAGE ScopedTypeVariables #-}
15{-# LANGUAGE TupleSections #-}
16{-# LANGUAGE TypeApplications #-}
17module Network.Tox.Address
18 ( NodeInfo(..)
19 , NodeId
20 , nodeInfo
21 , nodeAddr
22 , zeroID
23 , key2id
24 , id2key
25 , getIP
26 , xorNodeId
27 , testNodeIdBit
28 , sampleNodeId) where
29
30import Control.Applicative
31import Control.Monad
32import Crypto.Error.Types (CryptoFailable (..),
33 throwCryptoError)
34import Crypto.PubKey.Curve25519
35import qualified Data.Aeson as JSON
36 ;import Data.Aeson (FromJSON, ToJSON, (.=))
37import Data.Bits.ByteString ()
38import qualified Data.ByteArray as BA
39 ;import Data.ByteArray as BA (ByteArrayAccess)
40import qualified Data.ByteString as B
41 ;import Data.ByteString (ByteString)
42import qualified Data.ByteString.Base16 as Base16
43import qualified Data.ByteString.Char8 as C8
44import Data.Char
45import Data.Data
46import Data.Hashable
47import Data.IP
48import Data.Serialize as S
49import Data.Word
50import Foreign.Storable
51import GHC.TypeLits
52import Network.Address hiding (nodePort)
53import System.IO.Unsafe (unsafeDupablePerformIO)
54import qualified Text.ParserCombinators.ReadP as RP
55import Text.Read
56import Data.Bits
57import Crypto.Tox
58import Foreign.Ptr
59import Data.Function
60import System.Endian
61
62-- | perform io for hashes that do allocation and ffi.
63-- unsafeDupablePerformIO is used when possible as the
64-- computation is pure and the output is directly linked
65-- to the input. we also do not modify anything after it has
66-- been returned to the user.
67unsafeDoIO :: IO a -> a
68#if __GLASGOW_HASKELL__ > 704
69unsafeDoIO = unsafeDupablePerformIO
70#else
71unsafeDoIO = unsafePerformIO
72#endif
73
74unpackPublicKey :: ByteArrayAccess bs => bs -> [Word64]
75unpackPublicKey bs = loop 0
76 where loop i
77 | i == (BA.length bs `div` 8) = []
78 | otherwise =
79 let !v = unsafeDoIO $ BA.withByteArray bs (\p -> fromBE64 <$> peekElemOff p i)
80 in v : loop (i+1)
81
82packPublicKey :: BA.ByteArray bs => [Word64] -> bs
83packPublicKey ws = BA.allocAndFreeze (8 * length ws) $
84 flip fix ws $ \loop ys ptr -> case ys of
85 [] -> return ()
86 x:xs -> do poke ptr (toBE64 x)
87 loop xs (plusPtr ptr 8)
88
89newtype NodeId = NodeId [Word64]
90 deriving (Eq,Ord) -- ByteArrayAccess) -- (Eq,Ord,ByteArrayAccess, Bits, Hashable)
91
92
93key2id :: PublicKey -> NodeId
94key2id = NodeId . unpackPublicKey
95
96bs2id :: ByteString -> NodeId
97bs2id bs = NodeId . unpackPublicKey $ throwCryptoError . publicKey $ bs
98
99id2key :: NodeId -> PublicKey
100id2key (NodeId key) = throwCryptoError . publicKey $ (packPublicKey key :: BA.Bytes)
101
102
103{-
104id2key :: NodeId -> PublicKey
105id2key recipient = case publicKey recipient of
106 CryptoPassed key -> key
107 -- This should never happen because a NodeId is 32 bytes.
108 CryptoFailed e -> error ("Unexpected pattern fail: "++show e)
109
110key2id :: PublicKey -> NodeId
111key2id pk = case S.decode (BA.convert pk) of
112 Left _ -> error "key2id"
113 Right nid -> nid
114
115-}
116
117{-
118instance Ord NodeId where
119 compare (NodeId a) (NodeId b) = compare (unpackPublicKey a) (unpackPublicKey b)
120-}
121
122zeroID :: NodeId
123zeroID = NodeId $ replicate 4 0 -- throwCryptoError $ publicKey $ B.replicate 32 0
124
125instance Read NodeId where
126 readsPrec _ str
127 | (bs, xs) <- Base16.decode $ C8.pack str
128 , CryptoPassed pub <- publicKey bs -- B.length bs == 32
129 = [ (key2id pub, drop 64 str) ]
130 | otherwise = []
131
132instance Show NodeId where
133 show nid = C8.unpack $ Base16.encode $ BA.convert $ id2key nid
134
135instance S.Serialize NodeId where
136 get = key2id <$> getPublicKey
137 put nid = putPublicKey $ id2key nid
138
139instance Hashable NodeId where
140 hashWithSalt salt (NodeId key) = salt `xor` fromIntegral (byteSwap64 $ head key)
141
142-- instance FiniteBits NodeId where finiteBitSize _ = 256
143
144testNodeIdBit :: NodeId -> Word -> Bool
145testNodeIdBit (NodeId ws) i
146 | fromIntegral i < 256 -- 256 bits
147 , (q, r) <- quotRem (fromIntegral i) 64
148 = testBit (ws !! q) (63 - r)
149 | otherwise = False
150
151xorNodeId :: NodeId -> NodeId -> NodeId
152xorNodeId (NodeId xs) (NodeId ys) = NodeId $ zipWith xor xs ys
153
154sampleNodeId :: Applicative m => (Int -> m ByteString) -> NodeId -> (Int,Word8,Word8) -> m NodeId
155sampleNodeId gen (NodeId self) (q,m,b)
156 | q <= 0 = bs2id <$> gen 32
157 | q >= 32 = pure (NodeId self)
158 | let (qw,r) = (q+7) `divMod` 8 -- How many Word64 to prepend?
159 bw = shiftL (fromIntegral b) (8*(7-r))
160 mw = bw - 1 :: Word64
161 (hd, t0 : _) = splitAt (qw-1) self
162 h = xor bw (complement mw .&. t0)
163 = flip fmap (gen $ 8 * (4 - (qw-1)) ) $ \bs ->
164 let (w:ws) = unpackPublicKey bs
165 in NodeId $ hd ++ (h .|. (w .&. mw)) : ws
166
167data NodeInfo = NodeInfo
168 { nodeId :: NodeId
169 , nodeIP :: IP
170 , nodePort :: PortNumber
171 }
172 deriving (Eq,Ord)
173
174nodeInfo :: NodeId -> SockAddr -> Either String NodeInfo
175nodeInfo nid saddr
176 | Just ip <- fromSockAddr saddr
177 , Just port <- sockAddrPort saddr = Right $ NodeInfo nid ip port
178 | otherwise = Left "Address family not supported."
179
180
181instance ToJSON NodeInfo where
182 toJSON (NodeInfo nid (IPv4 ip) port)
183 = JSON.object [ "public_key" .= show nid
184 , "ipv4" .= show ip
185 , "port" .= (fromIntegral port :: Int)
186 ]
187 toJSON (NodeInfo nid (IPv6 ip6) port)
188 | Just ip <- un4map ip6
189 = JSON.object [ "public_key" .= show nid
190 , "ipv4" .= show ip
191 , "port" .= (fromIntegral port :: Int)
192 ]
193 | otherwise
194 = JSON.object [ "public_key" .= show nid
195 , "ipv6" .= show ip6
196 , "port" .= (fromIntegral port :: Int)
197 ]
198instance FromJSON NodeInfo where
199 parseJSON (JSON.Object v) = do
200 nidstr <- v JSON..: "public_key"
201 ip6str <- v JSON..:? "ipv6"
202 ip4str <- v JSON..:? "ipv4"
203 portnum <- v JSON..: "port"
204 ip <- maybe empty (return . IPv6) (ip6str >>= readMaybe)
205 <|> maybe empty (return . IPv4) (ip4str >>= readMaybe)
206 let (bs,_) = Base16.decode (C8.pack nidstr)
207 guard (B.length bs == 32)
208 return $ NodeInfo (bs2id bs) ip (fromIntegral (portnum :: Word16))
209
210getIP :: Word8 -> S.Get IP
211getIP 0x02 = IPv4 <$> S.get
212getIP 0x0a = IPv6 <$> S.get
213getIP 0x82 = IPv4 <$> S.get -- TODO: TCP
214getIP 0x8a = IPv6 <$> S.get -- TODO: TCP
215getIP x = fail ("unsupported address family ("++show x++")")
216
217instance Sized NodeInfo where
218 size = VarSize $ \(NodeInfo nid ip port) ->
219 case ip of
220 IPv4 _ -> 39 -- 35 + 4 = 1 + 4 + 2 + 32
221 IPv6 _ -> 51 -- 35 + 16 = 1 + 16 + 2 + 32
222
223instance S.Serialize NodeInfo where
224 get = do
225 addrfam <- S.get :: S.Get Word8
226 ip <- getIP addrfam
227 port <- S.get :: S.Get PortNumber
228 nid <- S.get
229 return $ NodeInfo nid ip port
230
231 put (NodeInfo nid ip port) = do
232 case ip of
233 IPv4 ip4 -> S.put (2 :: Word8) >> S.put ip4
234 IPv6 ip6 -> S.put (10 :: Word8) >> S.put ip6
235 S.put port
236 S.put nid
237
238hexdigit :: Char -> Bool
239hexdigit c = ('0' <= c && c <= '9') || ( 'a' <= c && c <= 'f') || ( 'A' <= c && c <= 'F')
240
241instance Read NodeInfo where
242 readsPrec i = RP.readP_to_S $ do
243 RP.skipSpaces
244 let n = 64 -- characters in node id.
245 parseAddr = RP.between (RP.char '(') (RP.char ')') (RP.munch (/=')'))
246 RP.+++ RP.munch (not . isSpace)
247 nodeidAt = do hexhash <- sequence $ replicate n (RP.satisfy hexdigit)
248 RP.char '@' RP.+++ RP.satisfy isSpace
249 addrstr <- parseAddr
250 nid <- case Base16.decode $ C8.pack hexhash of
251 (bs,_) | B.length bs==32 -> return (bs2id bs)
252 _ -> fail "Bad node id."
253 return (nid,addrstr)
254 (nid,addrstr) <- ( nodeidAt RP.+++ ( (zeroID,) <$> parseAddr) )
255 let raddr = do
256 ip <- RP.between (RP.char '[') (RP.char ']')
257 (IPv6 <$> RP.readS_to_P (readsPrec i))
258 RP.+++ (IPv4 <$> RP.readS_to_P (readsPrec i))
259 _ <- RP.char ':'
260 port <- toEnum <$> RP.readS_to_P (readsPrec i)
261 return (ip, port)
262
263 (ip,port) <- case RP.readP_to_S raddr addrstr of
264 [] -> fail "Bad address."
265 ((ip,port),_):_ -> return (ip,port)
266 return $ NodeInfo nid ip port
267
268-- The Hashable instance depends only on the IP address and port number.
269instance Hashable NodeInfo where
270 hashWithSalt s ni = hashWithSalt s (nodeIP ni , nodePort ni)
271 {-# INLINE hashWithSalt #-}
272
273
274instance Show NodeInfo where
275 showsPrec _ (NodeInfo nid ip port) =
276 shows nid . ('@' :) . showsip . (':' :) . shows port
277 where
278 showsip
279 | IPv4 ip4 <- ip = shows ip4
280 | IPv6 ip6 <- ip , Just ip4 <- un4map ip6 = shows ip4
281 | otherwise = ('[' :) . shows ip . (']' :)
282
283
284
285
286{-
287type NodeId = PubKey
288
289pattern NodeId bs = PubKey bs
290
291-- TODO: This should probably be represented by Curve25519.PublicKey, but
292-- ByteString has more instances...
293newtype PubKey = PubKey ByteString
294 deriving (Eq,Ord,Data, ByteArrayAccess, Bits, Hashable)
295
296instance Serialize PubKey where
297 get = PubKey <$> getBytes 32
298 put (PubKey bs) = putByteString bs
299
300instance Show PubKey where
301 show (PubKey bs) = C8.unpack $ Base16.encode bs
302
303instance FiniteBits PubKey where
304 finiteBitSize _ = 256
305
306instance Read PubKey where
307 readsPrec _ str
308 | (bs, xs) <- Base16.decode $ C8.pack str
309 , B.length bs == 32
310 = [ (PubKey bs, drop 64 str) ]
311 | otherwise = []
312
313
314
315
316data NodeInfo = NodeInfo
317 { nodeId :: NodeId
318 , nodeIP :: IP
319 , nodePort :: PortNumber
320 }
321 deriving (Eq,Ord,Data)
322
323instance Data PortNumber where
324 dataTypeOf _ = mkNoRepType "PortNumber"
325 toConstr _ = error "PortNumber.toConstr"
326 gunfold _ _ = error "PortNumber.gunfold"
327
328instance ToJSON NodeInfo where
329 toJSON (NodeInfo nid (IPv4 ip) port)
330 = JSON.object [ "public_key" .= show nid
331 , "ipv4" .= show ip
332 , "port" .= (fromIntegral port :: Int)
333 ]
334 toJSON (NodeInfo nid (IPv6 ip6) port)
335 | Just ip <- un4map ip6
336 = JSON.object [ "public_key" .= show nid
337 , "ipv4" .= show ip
338 , "port" .= (fromIntegral port :: Int)
339 ]
340 | otherwise
341 = JSON.object [ "public_key" .= show nid
342 , "ipv6" .= show ip6
343 , "port" .= (fromIntegral port :: Int)
344 ]
345instance FromJSON NodeInfo where
346 parseJSON (JSON.Object v) = do
347 nidstr <- v JSON..: "public_key"
348 ip6str <- v JSON..:? "ipv6"
349 ip4str <- v JSON..:? "ipv4"
350 portnum <- v JSON..: "port"
351 ip <- maybe empty (return . IPv6) (ip6str >>= readMaybe)
352 <|> maybe empty (return . IPv4) (ip4str >>= readMaybe)
353 let (bs,_) = Base16.decode (C8.pack nidstr)
354 guard (B.length bs == 32)
355 return $ NodeInfo (NodeId bs) ip (fromIntegral (portnum :: Word16))
356
357getIP :: Word8 -> S.Get IP
358getIP 0x02 = IPv4 <$> S.get
359getIP 0x0a = IPv6 <$> S.get
360getIP 0x82 = IPv4 <$> S.get -- TODO: TCP
361getIP 0x8a = IPv6 <$> S.get -- TODO: TCP
362getIP x = fail ("unsupported address family ("++show x++")")
363
364instance S.Serialize NodeInfo where
365 get = do
366 addrfam <- S.get :: S.Get Word8
367 ip <- getIP addrfam
368 port <- S.get :: S.Get PortNumber
369 nid <- S.get
370 return $ NodeInfo nid ip port
371
372 put (NodeInfo nid ip port) = do
373 case ip of
374 IPv4 ip4 -> S.put (2 :: Word8) >> S.put ip4
375 IPv6 ip6 -> S.put (10 :: Word8) >> S.put ip6
376 S.put port
377 S.put nid
378
379-- node format:
380-- [uint8_t family (2 == IPv4, 10 == IPv6, 130 == TCP IPv4, 138 == TCP IPv6)]
381-- [ip (in network byte order), length=4 bytes if ipv4, 16 bytes if ipv6]
382-- [port (in network byte order), length=2 bytes]
383-- [char array (node_id), length=32 bytes]
384--
385
386
387hexdigit :: Char -> Bool
388hexdigit c = ('0' <= c && c <= '9') || ( 'a' <= c && c <= 'f') || ( 'A' <= c && c <= 'F')
389
390instance Read NodeInfo where
391 readsPrec i = RP.readP_to_S $ do
392 RP.skipSpaces
393 let n = 64 -- characters in node id.
394 parseAddr = RP.between (RP.char '(') (RP.char ')') (RP.munch (/=')'))
395 RP.+++ RP.munch (not . isSpace)
396 nodeidAt = do hexhash <- sequence $ replicate n (RP.satisfy hexdigit)
397 RP.char '@' RP.+++ RP.satisfy isSpace
398 addrstr <- parseAddr
399 nid <- case Base16.decode $ C8.pack hexhash of
400 (bs,_) | B.length bs==32 -> return (PubKey bs)
401 _ -> fail "Bad node id."
402 return (nid,addrstr)
403 (nid,addrstr) <- ( nodeidAt RP.+++ ( (zeroID,) <$> parseAddr) )
404 let raddr = do
405 ip <- RP.between (RP.char '[') (RP.char ']')
406 (IPv6 <$> RP.readS_to_P (readsPrec i))
407 RP.+++ (IPv4 <$> RP.readS_to_P (readsPrec i))
408 _ <- RP.char ':'
409 port <- toEnum <$> RP.readS_to_P (readsPrec i)
410 return (ip, port)
411
412 (ip,port) <- case RP.readP_to_S raddr addrstr of
413 [] -> fail "Bad address."
414 ((ip,port),_):_ -> return (ip,port)
415 return $ NodeInfo nid ip port
416
417
418-- The Hashable instance depends only on the IP address and port number.
419instance Hashable NodeInfo where
420 hashWithSalt s ni = hashWithSalt s (nodeIP ni , nodePort ni)
421 {-# INLINE hashWithSalt #-}
422
423
424instance Show NodeInfo where
425 showsPrec _ (NodeInfo nid ip port) =
426 shows nid . ('@' :) . showsip . (':' :) . shows port
427 where
428 showsip
429 | IPv4 ip4 <- ip = shows ip4
430 | IPv6 ip6 <- ip , Just ip4 <- un4map ip6 = shows ip4
431 | otherwise = ('[' :) . shows ip . (']' :)
432
433nodeInfo :: NodeId -> SockAddr -> Either String NodeInfo
434nodeInfo nid saddr
435 | Just ip <- fromSockAddr saddr
436 , Just port <- sockAddrPort saddr = Right $ NodeInfo nid ip port
437 | otherwise = Left "Address family not supported."
438
439zeroID :: NodeId
440zeroID = PubKey $ B.replicate 32 0
441
442-}
443
444nodeAddr :: NodeInfo -> SockAddr
445nodeAddr (NodeInfo _ ip port) = setPort port $ toSockAddr ip
446
447
448newtype ForwardPath (n::Nat) = ForwardPath ByteString
449 deriving (Eq, Ord,Data)
450
451{-
452class KnownNat n => OnionPacket n where
453 mkOnion :: ReturnPath n -> Packet -> Packet
454instance OnionPacket 0 where mkOnion _ = id
455instance OnionPacket 3 where mkOnion = OnionResponse3
456-}