summaryrefslogtreecommitdiff
path: root/src/Network/RPC.hs
diff options
context:
space:
mode:
Diffstat (limited to 'src/Network/RPC.hs')
-rw-r--r--src/Network/RPC.hs24
1 files changed, 23 insertions, 1 deletions
diff --git a/src/Network/RPC.hs b/src/Network/RPC.hs
index 727422fd..7fb0e571 100644
--- a/src/Network/RPC.hs
+++ b/src/Network/RPC.hs
@@ -1,16 +1,22 @@
1{-# LANGUAGE ConstraintKinds #-} 1{-# LANGUAGE ConstraintKinds #-}
2{-# LANGUAGE DeriveDataTypeable #-}
3{-# LANGUAGE FlexibleContexts #-}
2{-# LANGUAGE FunctionalDependencies #-} 4{-# LANGUAGE FunctionalDependencies #-}
3{-# LANGUAGE MultiParamTypeClasses #-} 5{-# LANGUAGE MultiParamTypeClasses #-}
4{-# LANGUAGE RankNTypes #-} 6{-# LANGUAGE RankNTypes #-}
5{-# LANGUAGE ScopedTypeVariables #-} 7{-# LANGUAGE ScopedTypeVariables #-}
6{-# LANGUAGE TypeFamilies #-} 8{-# LANGUAGE TypeFamilies #-}
7{-# LANGUAGE DeriveDataTypeable #-}
8module Network.RPC where 9module Network.RPC where
9 10
11import Data.Bits
10import Data.ByteString (ByteString) 12import Data.ByteString (ByteString)
11import Data.Kind (Constraint) 13import Data.Kind (Constraint)
12import Data.Data 14import Data.Data
13import Network.Socket 15import Network.Socket
16import Text.PrettyPrint.HughesPJClass hiding (($$), (<>))
17import Data.Serialize as S
18import qualified Data.ByteString.Char8 as Char8
19import Data.ByteString.Base16 as Base16
14 20
15data MessageClass = Error | Query | Response 21data MessageClass = Error | Query | Response
16 deriving (Eq,Ord,Enum,Bounded,Data,Show,Read) 22 deriving (Eq,Ord,Enum,Bounded,Data,Show,Read)
@@ -36,6 +42,22 @@ class Envelope envelope where
36 -- Returns: response message envelope 42 -- Returns: response message envelope
37 buildReply :: NodeId envelope -> SockAddr -> envelope a -> b -> envelope b 43 buildReply :: NodeId envelope -> SockAddr -> envelope a -> b -> envelope b
38 44
45-- | In Kademlia, the distance metric is XOR and the result is
46-- interpreted as an unsigned integer.
47newtype NodeDistance nodeid = NodeDistance nodeid
48 deriving (Eq, Ord)
49
50-- | distance(A,B) = |A xor B| Smaller values are closer.
51distance :: Bits nid => nid -> nid -> NodeDistance nid
52distance a b = NodeDistance $ xor a b
53
54instance Serialize nodeid => Show (NodeDistance nodeid) where
55 show (NodeDistance w) = Char8.unpack $ Base16.encode $ S.encode w
56
57instance Serialize nodeid => Pretty (NodeDistance nodeid) where
58 pPrint n = text $ show n
59
60
39class Envelope envelope => WireFormat raw envelope where 61class Envelope envelope => WireFormat raw envelope where
40 type SerializableTo raw :: * -> Constraint 62 type SerializableTo raw :: * -> Constraint
41 type CipherContext raw envelope 63 type CipherContext raw envelope