summaryrefslogtreecommitdiff
diff options
context:
space:
mode:
-rw-r--r--src/Data/Tox.hs81
-rw-r--r--src/Network/BitTorrent/DHT/Query.hs2
-rw-r--r--src/Network/DHT/Mainline.hs48
-rw-r--r--src/Network/KRPC/Manager.hs27
-rw-r--r--src/Network/RPC.hs52
5 files changed, 169 insertions, 41 deletions
diff --git a/src/Data/Tox.hs b/src/Data/Tox.hs
index 448b39eb..4449ce65 100644
--- a/src/Data/Tox.hs
+++ b/src/Data/Tox.hs
@@ -1,5 +1,7 @@
1{-# LANGUAGE DeriveDataTypeable #-} 1{-# LANGUAGE DeriveDataTypeable #-}
2{-# LANGUAGE DeriveGeneric #-} 2{-# LANGUAGE DeriveGeneric #-}
3{-# LANGUAGE DeriveTraversable #-}
4{-# LANGUAGE DeriveFunctor #-}
3{-# LANGUAGE PatternSynonyms #-} 5{-# LANGUAGE PatternSynonyms #-}
4{-# LANGUAGE RecordWildCards #-} 6{-# LANGUAGE RecordWildCards #-}
5{-# LANGUAGE TupleSections #-} 7{-# LANGUAGE TupleSections #-}
@@ -15,6 +17,9 @@ import Data.Serialize
15import Network.BitTorrent.Address () -- Serialize IP 17import Network.BitTorrent.Address () -- Serialize IP
16import GHC.Generics (Generic) 18import GHC.Generics (Generic)
17import Network.Socket 19import Network.Socket
20import Network.RPC hiding (NodeId)
21import qualified Network.RPC as Envelope (NodeId)
22import Crypto.PubKey.ECC.Types
18 23
19type Key32 = Word256 -- 32 byte key 24type Key32 = Word256 -- 32 byte key
20type Nonce8 = Word64 -- 8 bytes 25type Nonce8 = Word64 -- 8 bytes
@@ -88,7 +93,7 @@ data Message a = Message
88 , msgNonce :: Nonce24 93 , msgNonce :: Nonce24
89 , msgPayload :: a 94 , msgPayload :: a
90 } 95 }
91 deriving (Show, Generic) 96 deriving (Show, Generic, Functor, Foldable, Traversable)
92 97
93isQuery :: Message a -> Bool 98isQuery :: Message a -> Bool
94isQuery (Message { msgType = SendNodes }) = False 99isQuery (Message { msgType = SendNodes }) = False
@@ -101,8 +106,6 @@ isResponse m = not (isQuery m)
101isError :: Message a -> Bool 106isError :: Message a -> Bool
102isError _ = False 107isError _ = False
103 108
104instance Serialize a => Serialize (Message a) where -- TODO TOX
105
106data PingPayload = PingPayload 109data PingPayload = PingPayload
107 { isPong :: Bool 110 { isPong :: Bool
108 , pingId :: Nonce8 111 , pingId :: Nonce8
@@ -194,3 +197,75 @@ instance Serialize NodeFormat where
194-- [Sendback data, length=8 bytes] 197-- [Sendback data, length=8 bytes]
195-- ] 198-- ]
196 199
200data ToxCipherContext = ToxCipherContext -- TODO
201
202newtype Ciphered = Ciphered { cipheredBytes :: ByteString }
203
204getMessage :: Get (Message Ciphered)
205getMessage = do
206 typ <- get
207 nid <- get
208 tid <- get
209 cnt <- remaining
210 bs <- getBytes cnt
211 return Message { msgType = typ
212 , msgClient = nid
213 , msgNonce = tid
214 , msgPayload = Ciphered bs }
215
216putMessage :: Message Ciphered -> Put
217putMessage (Message {..}) = do
218 put msgType
219 put msgClient
220 put msgNonce
221 let Ciphered bs = msgPayload
222 putByteString bs
223
224decipher :: ToxCipherContext -> Message Ciphered -> Either String (Message ByteString)
225decipher = error "TODO TOX: decipher"
226
227encipher :: ToxCipherContext -> Message ByteString -> Message Ciphered
228encipher = error "TODO TOX: encipher"
229
230-- see rfc7748
231curve25519 :: Curve
232curve25519 = CurveFP (CurvePrime prime curvecommon)
233 where
234 prime = 2^255 - 19 -- (≅ 1 modulo 4)
235
236 -- 1 * v^2 = u^3 + 486662*u^2 + u
237
238 curvecommon = CurveCommon
239 { ecc_a = 486662
240 , ecc_b = 1
241 , ecc_g = Point 9 14781619447589544791020593568409986887264606134616475288964881837755586237401 -- base point
242 , ecc_n = 2^252 + 0x14def9dea2f79cd65812631a5cf5d3ed -- order
243 , ecc_h = 8 -- cofactor
244 }
245
246
247
248instance Envelope Message where
249 type TransactionID Message = Nonce24
250 type NodeId Message = NodeId
251
252 envelopePayload = msgPayload
253
254 envelopeTransaction = msgNonce
255
256 envelopeClass Message { msgType = Ping } = Query
257 envelopeClass Message { msgType = Pong } = Response
258 envelopeClass Message { msgType = GetNodes } = Query
259 envelopeClass Message { msgType = SendNodes } = Response
260
261 buildReply self addr qry payload = (fmap (const payload) qry) { msgClient = self }
262
263instance WireFormat ByteString Message where
264 type SerializableTo ByteString = Serialize
265 type CipherContext ByteString Message = ToxCipherContext
266
267 decodePayload = mapM decode
268 encodePayload = fmap encode
269
270 decodeHeaders ctx bs = runGet getMessage bs >>= decipher ctx
271 encodeHeaders ctx msg = runPut $ putMessage $ encipher ctx msg
diff --git a/src/Network/BitTorrent/DHT/Query.hs b/src/Network/BitTorrent/DHT/Query.hs
index e1104cb9..820db8ba 100644
--- a/src/Network/BitTorrent/DHT/Query.hs
+++ b/src/Network/BitTorrent/DHT/Query.hs
@@ -112,7 +112,7 @@ nodeHandler :: ( Address ip
112#endif 112#endif
113 => (NodeAddr ip -> a -> DHT ip b) -> NodeHandler ip 113 => (NodeAddr ip -> a -> DHT ip b) -> NodeHandler ip
114#ifdef VERSION_bencoding 114#ifdef VERSION_bencoding
115nodeHandler action = handler mainline $ \ sockAddr qry -> do 115nodeHandler action = handler $ \ sockAddr qry -> do
116 let remoteId = queringNodeId qry 116 let remoteId = queringNodeId qry
117 read_only = queryIsReadOnly qry 117 read_only = queryIsReadOnly qry
118 q = queryParams qry 118 q = queryParams qry
diff --git a/src/Network/DHT/Mainline.hs b/src/Network/DHT/Mainline.hs
index 7cd33c0d..540b74f9 100644
--- a/src/Network/DHT/Mainline.hs
+++ b/src/Network/DHT/Mainline.hs
@@ -1,22 +1,40 @@
1{-# LANGUAGE LambdaCase #-} 1{-# LANGUAGE LambdaCase #-}
2{-# LANGUAGE MultiParamTypeClasses #-}
3{-# LANGUAGE TypeFamilies #-}
2module Network.DHT.Mainline where 4module Network.DHT.Mainline where
3 5
6import Network.Socket
4import Network.RPC 7import Network.RPC
5import Network.KRPC.Message 8import Network.KRPC.Message as KRPC
6import Data.BEncode as BE 9import Data.BEncode as BE
7import qualified Data.ByteString.Lazy as L 10import qualified Data.ByteString.Lazy as L
11import Network.BitTorrent.Address as BT (NodeId)
8 12
9mainline :: Messaging KMessageOf TransactionId BValue 13instance Envelope KMessageOf where
10mainline = Messaging 14 type TransactionID KMessageOf = KRPC.TransactionId
11 { messageClass = \case Q _ -> Query 15 type NodeId KMessageOf = BT.NodeId
12 R _ -> Response 16
13 E _ -> Error 17 envelopePayload (Q q) = queryArgs q
14 , messageTransaction = \case Q q -> queryId q 18 envelopePayload (R r) = respVals r
15 R r -> respId r 19 envelopePayload (E _) = error "TODO: messagePayload for KError"
16 E e -> errorId e 20
17 , messagePayload = \case Q q -> queryArgs q 21 envelopeTransaction (Q q) = queryId q
18 R r -> respVals r 22 envelopeTransaction (R r) = respId r
19 E e -> error "TODO: messagePayload for KError" 23 envelopeTransaction (E e) = errorId e
20 , encodePayload = fmap (L.toStrict . BE.encode) 24
21 , decodePayload = sequence . fmap BE.decode 25 envelopeClass (Q _) = Query
22 } 26 envelopeClass (R _) = Response
27 envelopeClass (E _) = Error
28
29 buildReply self addr qry response =
30 (R (KResponse response (envelopeTransaction qry) (Just $ ReflectedIP addr)))
31
32instance WireFormat BValue KMessageOf where
33 type SerializableTo BValue = BEncode
34 type CipherContext BValue KMessageOf = ()
35
36 decodeHeaders _ bs = BE.decode bs >>= BE.fromBEncode
37 decodePayload kmsg = mapM BE.fromBEncode kmsg
38
39 encodeHeaders _ kmsg = L.toStrict $ BE.encode kmsg
40 encodePayload msg = fmap BE.toBEncode msg
diff --git a/src/Network/KRPC/Manager.hs b/src/Network/KRPC/Manager.hs
index 58ac7674..f31a3cd6 100644
--- a/src/Network/KRPC/Manager.hs
+++ b/src/Network/KRPC/Manager.hs
@@ -78,11 +78,13 @@ import Data.Tuple
78import Data.Typeable 78import Data.Typeable
79import Network.RPC 79import Network.RPC
80import Network.KRPC.Message 80import Network.KRPC.Message
81import Network.KRPC.Method 81import Network.KRPC.Method hiding (Envelope)
82import qualified Network.KRPC.Method as KRPC (Envelope)
82import Network.Socket hiding (listen) 83import Network.Socket hiding (listen)
83import Network.Socket.ByteString as BS 84import Network.Socket.ByteString as BS
84import System.IO.Error 85import System.IO.Error
85import System.Timeout 86import System.Timeout
87import Network.DHT.Mainline
86 88
87 89
88{----------------------------------------------------------------------- 90{-----------------------------------------------------------------------
@@ -130,14 +132,14 @@ validateOptions Options {..}
130-- Options 132-- Options
131-----------------------------------------------------------------------} 133-----------------------------------------------------------------------}
132 134
133type KResult = Either KError KResponse 135type KResult = Either KError KMessage -- Response
134 136
135type TransactionCounter = IORef Int 137type TransactionCounter = IORef Int
136type CallId = (TransactionId, SockAddr) 138type CallId = (TransactionId, SockAddr)
137type CallRes = MVar (KQueryArgs, KResult) -- (raw response, decoded response) 139type CallRes = MVar (KQueryArgs, KResult) -- (raw response, decoded response)
138type PendingCalls = IORef (Map CallId CallRes) 140type PendingCalls = IORef (Map CallId CallRes)
139 141
140type HandlerBody h msg v = SockAddr -> msg v -> h (Either String v) 142type HandlerBody h msg v = SockAddr -> msg v -> h (Either String (msg v))
141 143
142-- | Handler is a function which will be invoked then some /remote/ 144-- | Handler is a function which will be invoked then some /remote/
143-- node querying /this/ node. 145-- node querying /this/ node.
@@ -362,7 +364,7 @@ queryK addr params kont = do
362 case res of 364 case res of
363#ifdef VERSION_bencoding 365#ifdef VERSION_bencoding
364 Left (KError c m _) -> throwIO $ QueryFailed c (T.decodeUtf8 m) 366 Left (KError c m _) -> throwIO $ QueryFailed c (T.decodeUtf8 m)
365 Right (KResponse {..}) -> 367 Right (R (KResponse {..})) ->
366 case fromBEncode respVals of 368 case fromBEncode respVals of
367 Right r -> pure $ kont raw r respIP 369 Right r -> pure $ kont raw r respIP
368#else 370#else
@@ -421,15 +423,16 @@ prettyQF e = T.encodeUtf8 $ "handler fail while performing query: "
421-- If the handler make some 'query' normally it /should/ handle 423-- If the handler make some 'query' normally it /should/ handle
422-- corresponding 'QueryFailure's. 424-- corresponding 'QueryFailure's.
423-- 425--
424handler :: forall h a b msg. (KRPC a b, Applicative h, Functor msg) 426handler :: forall h a b msg raw. (KRPC a b, Applicative h, Functor msg, WireFormat raw msg, SerializableTo raw a, SerializableTo raw b)
425 => Messaging msg TransactionId (Envelope a b) -> (SockAddr -> a -> h b) -> Handler h msg (Envelope a b) 427 => (SockAddr -> a -> h b) -> Handler h msg raw
426handler msging body = (name, wrapper) 428handler body = (name, wrapper)
427 where 429 where
428 Method name = method :: Method a b 430 Method name = method :: Method a b
431 wrapper :: SockAddr -> msg raw -> h (Either String (msg raw))
429 wrapper addr args = 432 wrapper addr args =
430 case unseal $ messagePayload msging args of 433 case decodePayload args of
431 Left e -> pure $ Left e 434 Left e -> pure $ Left e
432 Right a -> Right . seal <$> body addr a 435 Right a -> Right . encodePayload . buildReply (error "self node-id") addr args <$> body addr (envelopePayload a)
433 436
434runHandler :: MonadKRPC h m 437runHandler :: MonadKRPC h m
435#ifdef VERSION_bencoding 438#ifdef VERSION_bencoding
@@ -461,7 +464,7 @@ runHandler h addr m = Lifted.catches wrapper failbacks
461 Right a -> do -- KQueryArgs 464 Right a -> do -- KQueryArgs
462 $(logDebugS) "handler.success" signature 465 $(logDebugS) "handler.success" signature
463#ifdef VERSION_bencoding 466#ifdef VERSION_bencoding
464 return $ Right $ KResponse a (queryId m) (Just $ ReflectedIP addr) 467 return $ Right a
465#else 468#else
466 let cli = error "TODO TOX client node id" 469 let cli = error "TODO TOX client node id"
467 messageid = error "TODO TOX message response id" 470 messageid = error "TODO TOX message response id"
@@ -542,7 +545,7 @@ handleResponse raw result addr = do
542 Manager {..} <- getManager 545 Manager {..} <- getManager
543 liftIO $ do 546 liftIO $ do
544#ifdef VERSION_bencoding 547#ifdef VERSION_bencoding
545 let resultId = either errorId respId result 548 let resultId = either errorId envelopeTransaction result
546#else 549#else
547 let resultId = either Tox.msgNonce Tox.msgNonce result 550 let resultId = either Tox.msgNonce Tox.msgNonce result
548#endif 551#endif
@@ -554,7 +557,7 @@ handleResponse raw result addr = do
554#ifdef VERSION_bencoding 557#ifdef VERSION_bencoding
555handleMessage :: MonadKRPC h m => KQueryArgs -> KMessage -> SockAddr -> m () 558handleMessage :: MonadKRPC h m => KQueryArgs -> KMessage -> SockAddr -> m ()
556handleMessage raw (Q q) = handleQuery raw q 559handleMessage raw (Q q) = handleQuery raw q
557handleMessage raw (R r) = handleResponse raw (Right r) 560handleMessage raw (R r) = handleResponse raw (Right (R r))
558handleMessage raw (E e) = handleResponse raw (Left e) 561handleMessage raw (E e) = handleResponse raw (Left e)
559#else 562#else
560handleMessage :: MonadKRPC h m => KQueryArgs -> Tox.Message BC.ByteString -> SockAddr -> m () 563handleMessage :: MonadKRPC h m => KQueryArgs -> Tox.Message BC.ByteString -> SockAddr -> m ()
diff --git a/src/Network/RPC.hs b/src/Network/RPC.hs
index 2e9356e8..727422fd 100644
--- a/src/Network/RPC.hs
+++ b/src/Network/RPC.hs
@@ -1,15 +1,47 @@
1{-# LANGUAGE RankNTypes #-} 1{-# LANGUAGE ConstraintKinds #-}
2{-# LANGUAGE FunctionalDependencies #-}
3{-# LANGUAGE MultiParamTypeClasses #-}
4{-# LANGUAGE RankNTypes #-}
5{-# LANGUAGE ScopedTypeVariables #-}
6{-# LANGUAGE TypeFamilies #-}
7{-# LANGUAGE DeriveDataTypeable #-}
2module Network.RPC where 8module Network.RPC where
3 9
4import Data.ByteString (ByteString) 10import Data.ByteString (ByteString)
11import Data.Kind (Constraint)
12import Data.Data
13import Network.Socket
5 14
6data MessageClass = Error | Query | Response 15data MessageClass = Error | Query | Response
7 deriving (Eq,Ord,Enum,Bounded,Show,Read) 16 deriving (Eq,Ord,Enum,Bounded,Data,Show,Read)
8 17
9data Messaging msg tid payload = Messaging 18class Envelope envelope where
10 { messageClass :: forall a. msg a -> MessageClass 19 type TransactionID envelope
11 , messageTransaction :: forall a. msg a -> tid 20 type NodeId envelope
12 , messagePayload :: forall a. msg a -> a 21
13 , encodePayload :: msg payload -> msg ByteString 22 envelopePayload :: envelope a -> a
14 , decodePayload :: msg ByteString -> Either String (msg payload) 23 envelopeTransaction :: envelope a -> TransactionID envelope
15 } 24 envelopeClass :: envelope a -> MessageClass
25
26 -- | > buildReply self addr qry response
27 --
28 -- [ self ] this node's id.
29 --
30 -- [ addr ] SockAddr of query origin.
31 --
32 -- [ qry ] received query message.
33 --
34 -- [ response ] response payload.
35 --
36 -- Returns: response message envelope
37 buildReply :: NodeId envelope -> SockAddr -> envelope a -> b -> envelope b
38
39class Envelope envelope => WireFormat raw envelope where
40 type SerializableTo raw :: * -> Constraint
41 type CipherContext raw envelope
42
43 decodeHeaders :: CipherContext raw envelope -> ByteString -> Either String (envelope raw)
44 decodePayload :: SerializableTo raw a => envelope raw -> Either String (envelope a)
45
46 encodeHeaders :: CipherContext raw envelope -> envelope raw -> ByteString
47 encodePayload :: SerializableTo raw a => envelope a -> envelope raw