Skip to content

Instantly share code, notes, and snippets.

@jewel12
Last active March 13, 2016 13:41
Show Gist options
  • Star 0 You must be signed in to star a gist
  • Fork 0 You must be signed in to fork a gist
  • Save jewel12/f8d2d81ebb9ccd48e2d0 to your computer and use it in GitHub Desktop.
Save jewel12/f8d2d81ebb9ccd48e2d0 to your computer and use it in GitHub Desktop.
ConsistentHashing
module ConsistentHash where
import Data.Map as M
import Data.List as L
import Data.ByteString.Lazy.Char8
import Data.Digest.Pure.MD5 hiding (hash)
type Key = String
type Node = Key
type Nodes = [Node]
type CH = (Map Key Node, Node)
create :: Nodes -> CH
create nodes = (circle, (L.head nodes))
where circle = M.fromList $ L.map (\n -> (hash n, n)) nodes
hash :: Key -> String
hash key = show $ md5 $ pack key
get :: CH -> Key -> Node
get (circle, firstNode) key = case M.lookupGE (hash key) circle of
Just (k, n) -> n
Nothing -> firstNode
{-# LANGUAGE OverloadedStrings #-}
import ConsistentHash
import Data.List as L
import Data.Map as M
main = do
let nodes = ["n1", "n2", "n3", "n4", "n5", "n6"]
let ds = ['a'..'z']
let emptyStat = M.fromList $ L.map (\n -> (n, [])) nodes
let ch = create nodes
let foundNodes = L.map (\d -> (d, ((get ch).show) d)) ds
print $ L.foldl (\st (d, n) -> M.adjust (++[d]) n st) emptyStat foundNodes
Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment