Created
October 12, 2011 15:36
-
-
Save Tarrasch/1281545 to your computer and use it in GitHub Desktop.
Calculating average listheights for a skiplist of given height
This file contains hidden or bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
{-#LANGUAGE GeneralizedNewtypeDeriving #-} | |
module SkipList where | |
import System.Random | |
import Control.Monad.State | |
newtype KeyHeight = KH { height :: Int } | |
deriving (Num, Eq, Show, Integral, Real, Enum, Ord) | |
instance Random KeyHeight where | |
random = randKH | |
randomR = undefined | |
randKH g0 | continue = let (res, g2) = random g1 | |
in (KH 1 + res, g2) | |
| otherwise = (KH 0, g1) | |
where (continue, g1) = random g0 | |
type MyMonad a = State StdGen a | |
newRandValue :: Random a => MyMonad a | |
newRandValue = do g0 <- get | |
let (a, g1) = random g0 | |
put g1 | |
return a | |
expectedHeight :: Int -> MyMonad Double | |
expectedHeight i = do list <- mmlist | |
return $ fromIntegral (sum list) / fromIntegral nLoops | |
where n = 2^i | |
nLoops = 10000 | |
mmlist = sequence $ replicate nLoops (tryGetMax n) | |
tryGetMax :: Int -> MyMonad KeyHeight | |
tryGetMax 0 = return 0 | |
tryGetMax n = do x <- newRandValue | |
y <- tryGetMax (n-1) | |
return $ max x y | |
allTests :: MyMonad [Double] | |
allTests = sequence [expectedHeight i | i <- [1 .. 7]] | |
test n = do g0 <- newStdGen | |
let res = runState (expectedHeight n) g0 | |
return res | |
main = do g0 <- newStdGen | |
let xs = fst $ runState allTests g0 | |
mapM_ (putStrLn . show) xs | |
Sign up for free
to join this conversation on GitHub.
Already have an account?
Sign in to comment