Skip to content

Commit

Permalink
Refactored findNode to use nodeBools function
Browse files Browse the repository at this point in the history
  • Loading branch information
aninhumer committed Aug 4, 2011
1 parent ca1aaa5 commit 495bc24
Show file tree
Hide file tree
Showing 2 changed files with 13 additions and 7 deletions.
12 changes: 7 additions & 5 deletions Bucket.hs
Expand Up @@ -7,8 +7,9 @@ import Data.Ord (comparing)
import Data.Bits
import Data.LargeWord (Word160)

-- Returns the left to right index of the first high bit in the input
firstHighBit :: Word160 -> Int
firstHighBit n = case findIndex (`testBit` 159) . take 160 $ iterate (*2) n of
firstHighBit n = case findIndex id $ nodeBools n of
Just i -> i
Nothing -> 160

Expand All @@ -32,10 +33,11 @@ addNode new (BucketTable local bucket) = let
findNode :: (NodeID a) => a -> BucketTable -> Maybe Node
findNode target (BucketTable local buckets) =
find (nodeEq target) bucket
where bucket = case drop index buckets of
(b:_) -> b
[] -> last buckets
index = firstHighBit $ nodeDist target local
where
bucket = case filter fst $ zip bools buckets of
((_,b):_) -> b
[] -> last buckets
bools = nodeBools $ nodeDist local target

getNear :: (NodeID a) => a -> BucketTable -> [Node]
getNear target (BucketTable _ bs) =
Expand Down
8 changes: 6 additions & 2 deletions Node.hs
@@ -1,8 +1,10 @@

{-# LANGUAGE TypeSynonymInstances #-}

module Data.DHT.Node
(Node, NodeID, nodeID, isGood, lastSeen, nodeEq, nodeBit, nodeDist) where
module Data.DHT.Node (
NodeID, nodeID,
Node, isGood, lastSeen,
nodeBools, nodeEq, nodeBit, nodeDist) where

import Data.Bits
import Data.LargeWord (Word160)
Expand Down Expand Up @@ -31,4 +33,6 @@ nodeBit i = (`testBit` i) . nodeID
nodeDist :: (NodeID a, NodeID b) => a -> b -> Word160
nodeDist local target = nodeID local `xor` nodeID target

nodeBools :: (NodeID a) => a -> [Bool]
nodeBools node = map (`nodeBit` node) $ reverse [0..159]

0 comments on commit 495bc24

Please sign in to comment.