Skip to content

Instantly share code, notes, and snippets.

@timjb
Created January 18, 2018 17:12
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 timjb/c4599882800a46ab7d7b17f849e15735 to your computer and use it in GitHub Desktop.
Save timjb/c4599882800a46ab7d7b17f849e15735 to your computer and use it in GitHub Desktop.
module Main where
import Data.List (intercalate)
import Control.Monad (forM_)
type Nat = Int
type Prime = Nat
type HashFunction = Int -> Int
type HashFunctionFamily = Nat -> HashFunction
h :: Nat -> Prime -> HashFunctionFamily
h s p a x = ((a*x) `mod` p) `mod` s
collisionsFor :: Nat -> Prime -> Int -> Int -> [Nat]
collisionsFor s p x y = [a | a <- [1..(p-1)], h s p a x == h s p a y]
listAllCollisions :: Nat -> Prime -> [(Int,Int,[Nat])]
listAllCollisions s p = [(x,y,collisionsFor s p x y) | x <- [0..(p-1)], y <- [(x+1)..(p-1)]]
test :: Nat -> Prime -> IO ()
test s p = do
putStrLn ("Testing with s=" ++ show s ++ " and p=" ++ show p)
putStrLn ("Since class is 2-universal, we must have <= 2*|H|/s = 2*(p-1)/s = " ++ show (2*(fromIntegral (p-1))/(fromIntegral s)) ++ " collisions for each pair (x,y) with x != y")
forM_ (listAllCollisions s p) $ \(x,y,collisions) ->
putStrLn (" For x=" ++ show x ++ " and y=" ++ show y ++ " we have h_a(x) = h_a(y) for a=" ++ intercalate "," (map show collisions))
main :: IO ()
main = do
test 2 5
test 2 7
test 2 11
test 2 13
test 5 13
test 13 61
Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment