summaryrefslogtreecommitdiff
path: root/src
diff options
context:
space:
mode:
authorSam Truzjan <pxqr.sta@gmail.com>2013-12-18 22:00:45 +0400
committerSam Truzjan <pxqr.sta@gmail.com>2013-12-18 22:00:45 +0400
commit4b5b7b56445fe2521e89146b2761de6b7534e59d (patch)
tree2cab54daaf84e87ba3c9e2db67309c560c6a6f76 /src
parent8bff89d4dd6354288c8b01395bcf6103c6edfe19 (diff)
Add the new purified routing table
Diffstat (limited to 'src')
-rw-r--r--src/Data/Kademlia/Routing/Table.hs182
-rw-r--r--src/Network/BitTorrent/Core.hs1
-rw-r--r--src/Network/BitTorrent/Core/Node.hs21
-rw-r--r--src/Network/BitTorrent/DHT/Routing.hs313
4 files changed, 330 insertions, 187 deletions
diff --git a/src/Data/Kademlia/Routing/Table.hs b/src/Data/Kademlia/Routing/Table.hs
deleted file mode 100644
index b3b2a655..00000000
--- a/src/Data/Kademlia/Routing/Table.hs
+++ /dev/null
@@ -1,182 +0,0 @@
1-- |
2-- Copyright : (c) Sam Truzjan 2013
3-- License : BSD3
4-- Maintainer : pxqr.sta@gmail.com
5-- Stability : experimental
6-- Portability : portable
7--
8{-# LANGUAGE RecordWildCards #-}
9module Data.Kademlia.Routing.Table
10 ( Table(nodeID)
11 ) where
12
13import Control.Applicative hiding (empty)
14import Data.Bits
15import Data.List as L hiding (insert)
16import Data.Maybe
17
18{-----------------------------------------------------------------------
19 Bucket
20-----------------------------------------------------------------------}
21
22type Size = Int
23
24-- | Bucket is kept sorted by time last seen — least-recently seen
25-- node at the head, most-recently seen at the tail. Reason: when we
26-- insert a node into the bucket we first filter nodes with smaller
27-- lifetime since they more likely leave network and we more likely
28-- don't reach list end. This should reduce list traversal, we don't
29-- need to reverse list in insertion routines.
30--
31-- Bucket is also limited in its length — thus it's called k-bucket.
32-- When bucket becomes full we should split it in two lists by
33-- current span bit. Span bit is defined by depth in the routing
34-- table tree. Size of the bucket should be choosen such that it's
35-- very unlikely that all nodes in bucket fail within an hour of
36-- each other.
37--
38data Bucket = Empty
39 | Cons {-# UNPACK #-} !NodeAddr {-# UNPACK #-} !TimeStamp !Bucket
40
41-- | Gives /current/ size of bucket.
42--
43-- forall bucket. size bucket <= maxSize bucket
44--
45size :: Bucket k v -> Size
46size = L.length . kvs
47
48isFull :: Bucket k v -> Bool
49isFull Bucket {..} = L.length kvs == maxSize
50
51member :: Eq k => k -> Bucket k v -> Bool
52member k = elem k . map fst . kvs
53
54empty :: Size -> Bucket k v
55empty s = Bucket (max 0 s) []
56
57singleton :: Size -> k -> v -> Bucket k v
58singleton s k v = Bucket (max 1 s) [(k, v)]
59
60
61-- | Increase size of a given bucket.
62enlarge :: Size -> Bucket k v -> Bucket k v
63enlarge additional b = b { maxSize = maxSize b + additional }
64
65split :: Bits k => Int -> Bucket k v -> (Bucket k v, Bucket k v)
66split index Bucket {..} =
67 let (far, near) = partition spanBit kvs
68 in (Bucket maxSize near, Bucket maxSize far)
69 where
70 spanBit = (`testBit` index) . fst
71
72
73-- move elem to the end in one traversal
74moveToEnd :: Eq k => (k, v) -> Bucket k v -> Bucket k v
75moveToEnd kv@(k, _) b = b { kvs = go (kvs b) }
76 where
77 go [] = []
78 go (x : xs)
79 | fst x == k = xs ++ [kv]
80 | otherwise = x : go xs
81
82insertToEnd :: (k, v) -> Bucket k v -> Bucket k v
83insertToEnd kv b = b { kvs = kvs b ++ [kv] }
84
85-- | * If the info already exists in bucket then move it to the end.
86--
87-- * If bucket is not full then insert the info to the end.
88--
89-- * If bucket is full then ping the least recently seen node.
90-- Here we have a choice:
91--
92-- If node respond then move it the end and discard node
93-- we want to insert.
94--
95-- If not remove it from the bucket and add the
96-- (we want to insert) node to the end.
97--
98insert :: Applicative f => Eq k
99 => (v -> f Bool) -- ^ Ping RPC
100 -> (k, v) -> Bucket k v -> f (Bucket k v)
101
102insert ping new bucket@(Bucket {..})
103 | fst new `member` bucket = pure (new `moveToEnd` bucket)
104 | size bucket < maxSize = pure (new `insertToEnd` bucket)
105 | least : rest <- kvs =
106 let select alive = if alive then least else new
107 mk most = Bucket maxSize (rest ++ [most])
108 in mk . select <$> ping (snd least)
109 where
110-- | otherwise = pure bucket
111 -- WARN: or maybe error "insertBucket: max size should not be 0" ?
112
113lookup :: k -> Bucket k v -> Maybe v
114lookup = undefined
115
116closest :: Int -> k -> Bucket k v -> [(k, v)]
117closest = undefined
118
119-- | Most clients use this value for maximum bucket size.
120defaultBucketSize :: Int
121defaultBucketSize = 20
122
123{-----------------------------------------------------------------------
124 Tree
125-----------------------------------------------------------------------}
126
127-- | Routing tree should contain key -> value pairs in this way:
128--
129-- * More keys that near to our node key, and less keys that far
130-- from our node key.
131--
132-- * Tree might be saturated. If this happen we can only update
133-- buckets, but we can't add new buckets.
134--
135-- Instead of using ordinary binary tree and keep track is it
136-- following restrictions above (that's somewhat non-trivial) we
137-- store distance -> value keys. This lead to simple data structure
138-- that actually isomorphic to non-empty list. So we first map our
139-- keys to distances using our node ID and store them in tree. When
140-- we need to extract a pair we map distances to keys back, again
141-- using our node ID. This normalization happen in routing table.
142--
143data Tree k v
144 = Tip (Bucket k v)
145 | Bin (Tree k v) (Bucket k v)
146
147empty :: Int -> Tree k v
148empty = Tip . Bucket.empty
149
150insert :: Applicative f => Bits k
151 => (v -> f Bool) -> (k, v) -> Tree k v -> f (Tree k v)
152insert ping (k, v) = go 0
153 where
154 go n (Tip bucket)
155 | isFull bucket, (near, far) <- split n bucket
156 = pure (Tip near `Bin` far)
157 | otherwise = Tip <$> Bucket.insert ping (k, v) bucket
158
159 go n (Bin near far)
160 | k `testBit` n = Bin <$> pure near <*> Bucket.insert ping (k, v) far
161 | otherwise = Bin <$> go (succ n) near <*> pure far
162
163{-----------------------------------------------------------------------
164 Table
165-----------------------------------------------------------------------}
166
167data Table k v = Table {
168 routeTree :: Tree k v
169
170 -- | Set degree of parallelism in node lookup calls.
171 , alpha :: Int
172 , nodeID :: k
173 }
174
175--insert :: NodeID -> Table -> Table
176--insert x t = undefined
177
178--closest :: InfoHash -> Table -> [NodeID]
179--closest = undefined
180
181-- TODO table serialization: usually we need to save table between
182-- target program executions for bootstrapping
diff --git a/src/Network/BitTorrent/Core.hs b/src/Network/BitTorrent/Core.hs
index 7b8ff07d..9cfb3dd7 100644
--- a/src/Network/BitTorrent/Core.hs
+++ b/src/Network/BitTorrent/Core.hs
@@ -19,5 +19,6 @@ module Network.BitTorrent.Core
19import Data.IP 19import Data.IP
20 20
21import Network.BitTorrent.Core.Fingerprint as Core 21import Network.BitTorrent.Core.Fingerprint as Core
22import Network.BitTorrent.Core.Node as Core
22import Network.BitTorrent.Core.PeerId as Core 23import Network.BitTorrent.Core.PeerId as Core
23import Network.BitTorrent.Core.PeerAddr as Core 24import Network.BitTorrent.Core.PeerAddr as Core
diff --git a/src/Network/BitTorrent/Core/Node.hs b/src/Network/BitTorrent/Core/Node.hs
index e93c3586..5098d260 100644
--- a/src/Network/BitTorrent/Core/Node.hs
+++ b/src/Network/BitTorrent/Core/Node.hs
@@ -4,6 +4,7 @@
4module Network.BitTorrent.Core.Node 4module Network.BitTorrent.Core.Node
5 ( -- * Node ID 5 ( -- * Node ID
6 NodeId 6 NodeId
7 , testIdBit
7 , genNodeId 8 , genNodeId
8 9
9 -- * Node address 10 -- * Node address
@@ -16,9 +17,11 @@ module Network.BitTorrent.Core.Node
16import Control.Applicative 17import Control.Applicative
17import Data.Aeson (ToJSON, FromJSON) 18import Data.Aeson (ToJSON, FromJSON)
18import Data.Aeson.TH 19import Data.Aeson.TH
20import Data.Bits
19import Data.ByteString as BS 21import Data.ByteString as BS
20import Data.BEncode as BE 22import Data.BEncode as BE
21import Data.Serialize as S 23import Data.Serialize as S
24import Data.Word
22import Network 25import Network
23import System.Entropy 26import System.Entropy
24 27
@@ -28,11 +31,12 @@ import Network.BitTorrent.Core.PeerAddr ()
28{----------------------------------------------------------------------- 31{-----------------------------------------------------------------------
29-- Node id 32-- Node id
30-----------------------------------------------------------------------} 33-----------------------------------------------------------------------}
34-- TODO more compact representation ('ShortByteString's?)
31 35
32-- | Normally, /this/ node id should we saved between invocations of 36-- | Normally, /this/ node id should we saved between invocations of
33-- the client software. 37-- the client software.
34newtype NodeId = NodeId ByteString 38newtype NodeId = NodeId ByteString
35 deriving (Show, Eq, FromJSON, ToJSON) 39 deriving (Show, Eq, Ord, FromJSON, ToJSON)
36 40
37nodeIdSize :: Int 41nodeIdSize :: Int
38nodeIdSize = 20 42nodeIdSize = 20
@@ -43,6 +47,15 @@ instance Serialize NodeId where
43 put (NodeId bs) = putByteString bs 47 put (NodeId bs) = putByteString bs
44 {-# INLINE put #-} 48 {-# INLINE put #-}
45 49
50-- | Test if the nth bit is set.
51testIdBit :: NodeId -> Word -> Bool
52testIdBit (NodeId bs) i
53 | fromIntegral i < nodeIdSize * 8
54 , (q, r) <- quotRem (fromIntegral i) 8
55 = testBit (BS.index bs q) r
56 | otherwise = False
57{-# INLINE testIdBit #-}
58
46-- TODO WARN is the 'system' random suitable for this? 59-- TODO WARN is the 'system' random suitable for this?
47-- | Generate random NodeID used for the entire session. 60-- | Generate random NodeID used for the entire session.
48-- Distribution of ID's should be as uniform as possible. 61-- Distribution of ID's should be as uniform as possible.
@@ -50,8 +63,6 @@ instance Serialize NodeId where
50genNodeId :: IO NodeId 63genNodeId :: IO NodeId
51genNodeId = NodeId <$> getEntropy nodeIdSize 64genNodeId = NodeId <$> getEntropy nodeIdSize
52 65
53type Distance = NodeId
54
55{----------------------------------------------------------------------- 66{-----------------------------------------------------------------------
56-- Node address 67-- Node address
57-----------------------------------------------------------------------} 68-----------------------------------------------------------------------}
@@ -59,7 +70,7 @@ type Distance = NodeId
59data NodeAddr a = NodeAddr 70data NodeAddr a = NodeAddr
60 { nodeHost :: !a 71 { nodeHost :: !a
61 , nodePort :: {-# UNPACK #-} !PortNumber 72 , nodePort :: {-# UNPACK #-} !PortNumber
62 } deriving (Show, Eq) 73 } deriving (Show, Eq, Ord)
63 74
64$(deriveJSON omitRecordPrefix ''NodeAddr) 75$(deriveJSON omitRecordPrefix ''NodeAddr)
65 76
@@ -82,7 +93,7 @@ instance BEncode a => BEncode (NodeAddr a) where
82data NodeInfo a = NodeInfo 93data NodeInfo a = NodeInfo
83 { nodeId :: !NodeId 94 { nodeId :: !NodeId
84 , nodeAddr :: !(NodeAddr a) 95 , nodeAddr :: !(NodeAddr a)
85 } deriving (Show, Eq) 96 } deriving (Show, Eq, Ord)
86 97
87$(deriveJSON omitRecordPrefix ''NodeInfo) 98$(deriveJSON omitRecordPrefix ''NodeInfo)
88 99
diff --git a/src/Network/BitTorrent/DHT/Routing.hs b/src/Network/BitTorrent/DHT/Routing.hs
new file mode 100644
index 00000000..5f00a924
--- /dev/null
+++ b/src/Network/BitTorrent/DHT/Routing.hs
@@ -0,0 +1,313 @@
1-- |
2-- Copyright : (c) Sam Truzjan 2013
3-- License : BSD3
4-- Maintainer : pxqr.sta@gmail.com
5-- Stability : experimental
6-- Portability : portable
7--
8{-# LANGUAGE RecordWildCards #-}
9{-# LANGUAGE TypeOperators #-}
10{-# LANGUAGE DeriveGeneric #-}
11module Network.BitTorrent.DHT.Routing
12 ( -- * Routing table
13 Table
14 , BucketCount
15
16 -- * Routing
17 , Routing
18 , runRouting
19
20 -- * Query
21 , thisId
22 , Network.BitTorrent.DHT.Routing.size
23 , Network.BitTorrent.DHT.Routing.depth
24 , K
25 , Network.BitTorrent.DHT.Routing.kclosest
26 , Network.BitTorrent.DHT.Routing.kclosestHash
27
28 -- * Construction
29 , Network.BitTorrent.DHT.Routing.nullTable
30 , Network.BitTorrent.DHT.Routing.insert
31 ) where
32
33import Control.Applicative hiding (empty)
34import Control.Arrow
35import Control.Monad
36import Data.List as L hiding (insert)
37import Data.Maybe
38import Data.Function
39import Data.PSQueue as PSQ
40import Data.Serialize as S hiding (Result, Done)
41import Data.Time
42import Data.Time.Clock.POSIX
43import Data.Word
44import GHC.Generics
45
46import Data.Torrent.InfoHash
47import Network.BitTorrent.Core
48
49{-
50-- | Routing tree should contain key -> value pairs in this way:
51--
52-- * More keys that near to our node key, and less keys that far
53-- from our node key.
54--
55-- * Tree might be saturated. If this happen we can only update
56-- buckets, but we can't add new buckets.
57--
58-- Instead of using ordinary binary tree and keep track is it
59-- following restrictions above (that's somewhat non-trivial) we
60-- store distance -> value keys. This lead to simple data structure
61-- that actually isomorphic to non-empty list. So we first map our
62-- keys to distances using our node ID and store them in tree. When
63-- we need to extract a pair we map distances to keys back, again
64-- using our node ID. This normalization happen in routing table.
65--
66data Tree k v
67 = Tip (Bucket k v)
68 | Bin (Tree k v) (Bucket k v)
69
70empty :: Int -> Tree k v
71empty = Tip . Bucket.empty
72
73insert :: Applicative f => Bits k
74 => (v -> f Bool) -> (k, v) -> Tree k v -> f (Tree k v)
75insert ping (k, v) = go 0
76 where
77 go n (Tip bucket)
78 | isFull bucket, (near, far) <- split n bucket
79 = pure (Tip near `Bin` far)
80 | otherwise = Tip <$> Bucket.insert ping (k, v) bucket
81
82 go n (Bin near far)
83 | k `testBit` n = Bin <$> pure near <*> Bucket.insert ping (k, v) far
84 | otherwise = Bin <$> go (succ n) near <*> pure far
85-}
86
87{-----------------------------------------------------------------------
88-- Insertion
89-----------------------------------------------------------------------}
90
91type Timestamp = POSIXTime
92type PingInterval = POSIXTime
93
94data Routing ip result
95 = Full result
96 | Done (Timestamp -> result)
97 | Refresh (NodeAddr ip) (([NodeInfo ip], Timestamp) -> Routing ip result)
98 | NeedPing (NodeAddr ip) (Maybe Timestamp -> Routing ip result)
99
100instance Functor (Routing ip) where
101 fmap f (Full r) = Full ( f r)
102 fmap f (Done r) = Done ( f . r)
103 fmap f (Refresh addr g) = Refresh addr (fmap f . g)
104 fmap f (NeedPing addr g) = NeedPing addr (fmap f . g)
105
106runRouting :: (Monad m, Eq ip)
107 => (NodeAddr ip -> m Bool) -- ^ ping_node
108 -> (NodeId -> m [NodeInfo ip]) -- ^ find_nodes
109 -> m Timestamp -- ^ timestamper
110 -> Routing ip f
111 -> m f -- ^ result
112runRouting ping_node find_nodes timestamp = go
113 where
114 go (Full r) = return r
115 go (Done f) = liftM f timestamp
116 go (NeedPing addr f) = do
117 pong <- ping_node addr
118 if pong
119 then do
120 time <- timestamp
121 go (f (Just time))
122 else go (f Nothing)
123
124 go (Refresh nodes f) = do
125 let nid = undefined
126 go (f undefined)
127
128{-----------------------------------------------------------------------
129 Bucket
130-----------------------------------------------------------------------}
131
132-- | Timestamp - last time this node is pinged.
133type NodeEntry ip = Binding (NodeInfo ip) Timestamp
134
135instance (Serialize k, Serialize v) => Serialize (Binding k v) where
136 get = (:->) <$> get <*> get
137 put (k :-> v) = put k >> put v
138
139-- TODO instance Pretty where
140
141-- | Most clients use this value for maximum bucket size.
142defaultBucketSize :: Int
143defaultBucketSize = 20
144
145-- | Bucket is also limited in its length — thus it's called k-bucket.
146-- When bucket becomes full we should split it in two lists by
147-- current span bit. Span bit is defined by depth in the routing
148-- table tree. Size of the bucket should be choosen such that it's
149-- very unlikely that all nodes in bucket fail within an hour of
150-- each other.
151--
152type Bucket ip = PSQ (NodeInfo ip) Timestamp
153
154instance (Serialize k, Serialize v, Ord k, Ord v)
155 => Serialize (PSQ k v) where
156 get = PSQ.fromList <$> get
157 put = put . PSQ.toList
158
159-- | Get the most recently changed node entry, if any.
160lastChanged :: Eq ip => Bucket ip -> Maybe (NodeEntry ip)
161lastChanged bucket
162 | L.null timestamps = Nothing
163 | otherwise = Just (L.maximumBy (compare `on` prio) timestamps)
164 where
165 timestamps = PSQ.toList bucket
166
167leastRecently :: Eq ip => Bucket ip -> Maybe (NodeEntry ip, Bucket ip)
168leastRecently = minView
169
170-- | Update interval, in seconds.
171delta :: NominalDiffTime
172delta = 15
173
174-- | Max bucket size, in nodes.
175type Alpha = Int
176
177defaultAlpha :: Int
178defaultAlpha = 8
179
180insertNode :: Eq ip => NodeInfo ip -> Bucket ip -> ip `Routing` Bucket ip
181insertNode info bucket
182 -- just update timestamp if a node is already in bucket
183 | Just _ <- PSQ.lookup info bucket
184 = Done $ \ t -> PSQ.insertWith max info t bucket
185
186 -- update the all bucket if it is too outdated
187 | Just (NodeInfo {..} :-> lastSeen) <- lastChanged bucket
188 , lastSeen > delta
189 = Refresh nodeAddr $ \ (infos, t) ->
190 insertNode info $
191 L.foldr (\ x -> PSQ.insertWith max x t) bucket infos
192
193 -- update questionable nodes, if any; then try to insert our new node
194 -- this case can remove bad nodes from bucket, so we can insert a new one
195 | Just ((old @ NodeInfo {..} :-> leastSeen), rest) <- leastRecently bucket
196 , leastSeen > delta
197 = NeedPing nodeAddr $ insertNode info . maybe rest
198 (\ pong_time -> PSQ.insert old pong_time bucket)
199
200 -- bucket is good, but not full => we can insert a new node
201 | PSQ.size bucket < defaultAlpha = Done (\ t -> PSQ.insert info t bucket)
202
203 -- bucket is full of good nodes => ignore new node
204 | otherwise = Full bucket
205
206type BitIx = Word
207
208split :: Eq ip => BitIx -> Bucket ip -> (Bucket ip, Bucket ip)
209split i = (PSQ.fromList *** PSQ.fromList) . partition spanBit . PSQ.toList
210 where
211 spanBit entry = testIdBit (nodeId (key entry)) i
212
213{-----------------------------------------------------------------------
214-- Table
215-----------------------------------------------------------------------}
216
217type BucketCount = Word
218
219defaultBucketCount :: BucketCount
220defaultBucketCount = 20
221
222data Table ip
223 = Tip NodeId BucketCount (Bucket ip)
224 | Zero (Table ip) (Bucket ip)
225 | One (Bucket ip) (Table ip)
226 deriving Generic
227
228instance Serialize NominalDiffTime where
229 put = putWord32be . fromIntegral . fromEnum
230 get = (toEnum . fromIntegral) <$> getWord32be
231
232-- | Normally, routing table should we saved between invocations of
233-- the client software. Note that you don't need store /this/ 'NodeId'
234-- since it is included in routing table.
235instance (Eq ip, Serialize ip) => Serialize (Table ip)
236
237nullTable :: Eq ip => NodeId -> Table ip
238nullTable nid = Tip nid defaultBucketCount PSQ.empty
239
240thisId :: Table ip -> NodeId
241thisId (Tip nid _ _) = nid
242thisId (Zero table _) = thisId table
243thisId (One _ table) = thisId table
244
245-- | Get number of nodes in the table.
246size :: Table ip -> Int
247size = go
248 where
249 go (Tip _ _ bucket) = PSQ.size bucket
250 go (Zero t bucket) = go t + PSQ.size bucket
251 go (One bucket t ) = PSQ.size bucket + go t
252
253-- | Get number of buckets in the table.
254depth :: Table ip -> BucketCount
255depth = go
256 where
257 go (Tip _ _ _) = 1
258 go (Zero t _) = succ (go t)
259 go (One _ t) = succ (go t)
260
261lookupBucket :: NodeId -> Table ip -> Maybe (Bucket ip)
262lookupBucket nid = go 0
263 where
264 go i (Zero table bucket)
265 | testIdBit nid i = pure bucket
266 | otherwise = go (succ i) table
267 go i (One bucket table)
268 | testIdBit nid i = go (succ i) table
269 | otherwise = pure bucket
270 go _ (Tip _ _ bucket) = pure bucket
271
272type K = Int
273
274-- | Used in 'find_node' queries.
275kclosest :: Eq ip => K -> NodeId -> Table ip -> [NodeInfo ip]
276kclosest k nid = L.map key . PSQ.toList . fromMaybe PSQ.empty
277 . lookupBucket nid
278
279coerseId :: (Serialize a, Serialize b) => a -> b
280coerseId = either (error msg) id . S.decode . S.encode
281 where
282 msg = "coerseId: impossible"
283
284-- | Used in 'get_peers' queries.
285kclosestHash :: Eq a => Alpha -> InfoHash -> Table a -> [NodeInfo a]
286kclosestHash k nid t = kclosest k (coerseId nid) t
287
288{-----------------------------------------------------------------------
289-- Routing
290-----------------------------------------------------------------------}
291
292splitTip :: Eq ip => NodeId -> BucketCount -> BitIx -> Bucket ip -> Table ip
293splitTip nid n i bucket
294 | testIdBit nid i = (One zeros (Tip nid (pred n) ones))
295 | otherwise = (Zero (Tip nid (pred n) zeros) ones)
296 where
297 (zeros, ones) = split i bucket
298
299-- | Used in each query.
300insert :: Eq ip => NodeInfo ip -> Table ip -> ip `Routing` Table ip
301insert info @ NodeInfo {..} = go (0 :: BitIx)
302 where
303 go i (Zero table bucket)
304 | testIdBit nodeId i = Zero table <$> insertNode info bucket
305 | otherwise = (`Zero` bucket) <$> go (succ i) table
306 go i (One bucket table )
307 | testIdBit nodeId i = One bucket <$> go (succ i) table
308 | otherwise = (`One` table) <$> insertNode info bucket
309 go i (Tip nid n bucket) = case insertNode info bucket of
310 Full kbucket
311 | n == 0 -> Tip nid n <$> Full kbucket
312 | otherwise -> go (succ i) (splitTip nid n i kbucket)
313 result -> Tip nid n <$> result