commit 6adc4e376fee9e49756302ee27695ee43f20b10d
Author: Jared Tobin <jared@jtobin.ca>
Date: Fri, 30 Nov 2012 10:00:24 +1300
Initial commit.
Diffstat:
12 files changed, 693 insertions(+), 0 deletions(-)
diff --git a/20090724_monty/altmonty.hs b/20090724_monty/altmonty.hs
@@ -0,0 +1,22 @@
+import System.Random.MWC
+import Control.Monad
+
+data Choice = Switch | Stay deriving Eq
+
+montyRandSwitch g = do
+ z0 <- uniformR (0, 2) g :: IO Int
+ switch <- uniformR (False, True) g :: IO Bool
+ return $ if switch
+ then (z0 /= 2, Switch)
+ else (z0 == 2, Stay)
+
+runAltSimulation n g = do
+ ws <- liftM (filter fst) (replicateM n (montyRandSwitch g))
+ let winBySwitch = length . filter ((== Switch) . snd) $ ws
+ winByStay = length . filter ((== Stay) . snd) $ ws
+ return (winBySwitch, winByStay)
+
+main = do
+ g <- create
+ replicateM 10 (runAltSimulation 10000 g)
+
diff --git a/20090724_monty/monty.c b/20090724_monty/monty.c
@@ -0,0 +1,66 @@
+#include <stdio.h>
+#include <stdlib.h>
+#include <time.h>
+
+int *simulation(int n)
+{
+ int win_with_switch_cup = 0;
+ int win_with_stay = 0;
+
+ srand(time(NULL));
+
+ int i = 0;
+ for (i = 0; i < n; i++) {
+ int cash = 0;
+ int choice = 0;
+ cash = rand()%3;
+ choice = rand()%3;
+
+ int flipped_over = 0;
+
+ int a = 0;
+ for (a = 0; a < 3; a++) {
+ if ((a != cash) && (a != choice)) {
+ flipped_over = a;
+ }
+ }
+
+ int switch_cup = 0;
+ switch_cup = rand()%(2);
+ if (switch_cup) {
+ for (a = 0; a < 3; a++) {
+ if (a != choice && a != flipped_over) {
+ choice = a;
+ break;
+ }
+ }
+ }
+
+
+ if (choice == cash) {
+ if (switch_cup) {
+ win_with_switch_cup++;
+ } else {
+ win_with_stay++;
+ }
+ }
+ }
+
+ int *wins = malloc(2 * sizeof(int));
+ wins[0] = win_with_switch_cup;
+ wins[1] = win_with_stay;
+
+ return wins;
+}
+
+int main(void){
+ int n = 10000;
+
+ int *w = simulation(n);
+
+ printf("(%d, %d)\n", w[0], w[1]);
+
+ free(w);
+ return 0;
+}
+
diff --git a/20090724_monty/monty.hs b/20090724_monty/monty.hs
@@ -0,0 +1,30 @@
+import System.Random.MWC
+import Control.Monad
+
+data Choice = Switch | Stay deriving Eq
+
+monty switch g = do
+ z0 <- uniformR (0, 2) g :: IO Int
+ return $ if switch then z0 /= 2 else z0 == 2
+
+montyRandSwitch g = do
+ z0 <- uniformR (0, 2) g :: IO Int
+ zc <- uniformR (0, 1) g :: IO Double
+ let switch = zc < 0.5
+ return $ if switch then (z0 /= 2, Switch) else (z0 == 2, Stay)
+
+runAltSimulation n g = do
+ rs <- liftM (filter fst) (replicateM n (montyRandSwitch g))
+ let winBySwitch = length . filter ((== Switch) . snd) $ rs
+ winByStay = length . filter ((== Stay) . snd) $ rs
+ return (winBySwitch, winByStay)
+
+runSimulation n g = do
+ [n0, n1] <- mapM runMontyOnSwitch [True, False]
+ putStrLn $ "proportion of wins, switching: " ++ show (n0 / fromIntegral n)
+ putStrLn $ "proportion of wins, staying: " ++ show (n1 / fromIntegral n)
+ where runMontyOnSwitch b = liftM (sum . map (\a -> if a then 1 else 0))
+ (replicateM n (monty b g))
+
+main = create >>= runSimulation 10000
+
diff --git a/20090724_monty/monty.r b/20090724_monty/monty.r
@@ -0,0 +1,11 @@
+#!/usr/bin/Rscript
+monty = function(n, switch) {
+ z = rmultinom(n, 3, replicate(3, 1/3))
+ zs = apply(z, MARGIN = 1, sum)
+ if (switch) { wins = sum(zs[1:2]) } else { wins = zs[3] }
+ print(wins / sum(zs))
+}
+
+whenSwitching = monty(10000, T)
+whenStaying = monty(10000, F)
+
diff --git a/20120727_minstack/minstack.hs b/20120727_minstack/minstack.hs
@@ -0,0 +1,48 @@
+import Test.QuickCheck
+import Control.Monad
+
+data MinStack a = Bottom | Stack a a (MinStack a)
+ deriving (Eq, Read)
+
+instance Show a => Show (MinStack a) where
+ show Bottom = "|"
+ show (Stack m x s) = "<" ++ show x ++ show s
+
+push x s@(Stack m _ _) = if x < m then Stack x x s else Stack m x s
+push x Bottom = Stack x x Bottom
+
+pop Bottom = error "nothing there"
+pop (Stack _ x s) = (x, s)
+
+smin Bottom = error "nothing there"
+smin (Stack m _ _) = m
+
+-- Testing
+
+fromList :: Ord a => [a] -> MinStack a
+fromList = foldr push Bottom
+
+toList :: MinStack a -> [a]
+toList Bottom = []
+toList (Stack _ x s) = x : toList s
+
+instance (Ord a, Arbitrary a) => Arbitrary (MinStack a) where
+ arbitrary = liftM fromList (arbitrary :: Arbitrary a => Gen [a])
+
+newtype NonEmptyMinStack a = NonEmptyMinStack {getValue :: MinStack a}
+ deriving (Eq, Show, Read)
+
+instance (Ord a, Arbitrary a) => Arbitrary (NonEmptyMinStack a) where
+ arbitrary = liftM NonEmptyMinStack (arbitrary `suchThat` (/= Bottom))
+
+sminReturnsMinimum (NonEmptyMinStack ms) = smin ms == minimum (toList ms)
+
+newtype LargeMinStack a = LargeMinStack {getValueOfLargeMinStack :: MinStack a}
+ deriving (Eq, Show, Read)
+
+instance (Ord a, Arbitrary a) => Arbitrary (LargeMinStack a) where
+ arbitrary = liftM LargeMinStack (arbitrary `suchThat` ((> 1) . length . toList))
+
+sminUnaffectedByPopping (LargeMinStack ms) = let (x, s) = pop ms in
+ if smin ms /= smin s then x == smin ms else True
+
diff --git a/20121012_bdayParadox/paradox.hs b/20121012_bdayParadox/paradox.hs
@@ -0,0 +1,69 @@
+{-# LANGUAGE BangPatterns, TemplateHaskell #-}
+
+import System.Random.MWC
+import Control.Arrow
+import Control.Monad
+import Data.List
+import System.Exit
+-- Testing
+import System.Environment
+import Test.QuickCheck
+import Test.QuickCheck.All
+
+simulate :: Int -> Int -> IO Double
+simulate ne np = do
+ zs <- withSystemRandom . asGenIO $ \g0 -> replicateM ne
+ . fmap duplicatesPresent $ replicateM np (uniformR (1 :: Int, 365) g0)
+ return . average $ map (\x -> if x then 1 else 0) zs
+
+main :: IO ()
+main = do
+ args <- getArgs
+ when (args == []) $ putStrLn "(Birthday Paradox Simulator) usage: ./simulate <runTests=True|False>" >> exitSuccess
+ let run = read $ head args :: Bool
+ when run (void runTests)
+ unless run $ do let psim n ne np = do putStrLn $ "run " ++ show n ++ " (" ++ show np ++ " people, " ++ show ne ++ " simulations)"
+ sresult <- simulate ne np
+ putStrLn $ " frequency of " ++ show sresult
+ psim 0 10000 12
+ psim 1 10000 23
+ psim 2 10000 57
+ psim 3 10000 100
+
+-- Utilities
+
+average :: Fractional a => [a] -> a
+average [] = error "average: empty list"
+average xs = go 0 0 xs
+ where go !s !n [] = s / fromIntegral n
+ go !s !n (x:xs) = go (s + x) (n + 1) xs
+{-# INLINE average #-}
+
+duplicatesPresent :: (Eq a, Ord a) => [a] -> Bool
+duplicatesPresent [] = False
+duplicatesPresent xs = go h0 t0
+ where go h [] = False
+ go h (t:ts) = h == t || go t ts
+ (h0, t0) = (head &&& tail) (sort xs)
+{-# INLINE duplicatesPresent #-}
+
+-- Testing
+
+prop_averageEqualsNaiveMean :: NonEmptyList Double -> Bool
+prop_averageEqualsNaiveMean (NonEmpty xs) =
+ average xs == (sum xs / fromIntegral (length xs))
+
+prop_averageLiesBetweenExtrema :: NonEmptyList Double -> Bool
+prop_averageLiesBetweenExtrema (NonEmpty xs) =
+ (minimum xs <= average xs) && (maximum xs >= average xs)
+
+prop_duplicatesPresentDetectsDuplicates :: [Int] -> Bool
+prop_duplicatesPresentDetectsDuplicates xs =
+ duplicatesPresent xs == (any (> 1) . map length . group . sort) xs
+
+qcOptions :: Args
+qcOptions = stdArgs { maxSuccess = 1000 }
+
+runTests :: IO Bool
+runTests = $forAllProperties (quickCheckWithResult qcOptions)
+
diff --git a/20121030_pandigital/pandigital.hs b/20121030_pandigital/pandigital.hs
@@ -0,0 +1,18 @@
+-- Spec: a 3-digit number is added to another 3-digit number, and the result is
+-- a 4-digit number. If the ten digits involved are all different (0 thru 9)
+-- then what is the smallest possible value for any of the three numbers?
+
+import Data.List
+
+-- nums = [(x, y, x + y) | x <-
+
+pandigitals = [(x, y, x + y) | x <- shared, y <- shared, x < y, x + y > 999, unique [x, y, x + y]]
+ where shared = filter (unique . return) [100..999]
+ unique = (\x -> x == nub x) . (show =<<)
+
+unique :: Show a => [a] -> Bool
+unique = (\x -> x == nub x) . (show =<<)
+
+-- stringize :: Show a => [a] -> String
+-- stringize = (show =<<)
+
diff --git a/20121109_taxicab/.exrc b/20121109_taxicab/.exrc
@@ -0,0 +1,46 @@
+if &cp | set nocp | endif
+let s:cpo_save=&cpo
+set cpo&vim
+inoremap <silent> <Plug>(neocomplcache_start_omni_complete) =neocomplcache#popup_post()
+inoremap <silent> <Plug>(neocomplcache_start_auto_complete) =neocomplcache#popup_post()
+inoremap <silent> <expr> <Plug>(neocomplcache_start_unite_snippet) unite#sources#snippet#start_complete()
+inoremap <silent> <expr> <Plug>(neocomplcache_start_unite_quick_match) unite#sources#neocomplcache#start_quick_match()
+inoremap <silent> <expr> <Plug>(neocomplcache_start_unite_complete) unite#sources#neocomplcache#start_complete()
+map _lang :emenu ]LANGUAGES_GHC.
+map _opt :emenu ]OPTIONS_GHC.
+map _ie :call GHC_MkImportsExplicit()
+map _ct :call GHC_CreateTagfile()
+map _si :call GHC_ShowInfo()
+map _t :call GHC_ShowType(0)
+map _T :call GHC_ShowType(1)
+map _iqm :call Import(1,1)
+map _iq :call Import(0,1)
+map _im :call Import(1,0)
+map _i :call Import(0,0)
+map _. :call Qualify()
+map _?2 :call HaskellSearchEngine('hayoo!')
+map _?1 :call HaskellSearchEngine('hoogle')
+map _?? :let es=g:haskell_search_engines |echo "g:haskell_search_engines" |for e in keys(es) |echo e.' : '.es[e] |endfor
+map _? :call Haddock()
+nmap gx <Plug>NetrwBrowseX
+nnoremap <silent> <Plug>NetrwBrowseX :call netrw#NetrwBrowseX(expand("<cWORD>"),0)
+let &cpo=s:cpo_save
+unlet s:cpo_save
+set background=dark
+set backspace=2
+set cmdheight=3
+set completefunc=neocomplcache#manual_complete
+set completeopt=preview,menuone
+set expandtab
+set fileencodings=ucs-bom,utf-8,default,latin1
+set helplang=en
+set laststatus=2
+set modelines=0
+set omnifunc=GHC_CompleteImports
+set runtimepath=~/.vim,~/.vim/bundle/ghcmod-vim,~/.vim/bundle/neco-ghc,~/.vim/bundle/neocomplcache,~/.vim/bundle/syntastic,~/.vim/bundle/vimproc,/usr/share/vim/vimfiles,/usr/share/vim/vim73,/usr/share/vim/vimfiles/after,~/.vim/bundle/ghcmod-vim/after,~/.vim/after
+set shellpipe=2>
+set shiftwidth=2
+set tabstop=4
+set tags=tags
+set window=0
+" vim: set ft=vim :
diff --git a/20121109_taxicab/taxicab.hs b/20121109_taxicab/taxicab.hs
@@ -0,0 +1,29 @@
+-- Spec: write a function that returns all of the ways a number can be written
+-- as the sum of two non-negative cubes.
+
+{-# OPTIONS_GHC -Wall -Werror #-}
+
+import Control.Arrow
+import Test.QuickCheck
+
+cubeDecomposition :: Int -> [(Int, Int)]
+cubeDecomposition n =
+ [(x, y) | x <- [1..m], y <- [x..m], x^(3 :: Int) + y^(3 :: Int) == n]
+ where m = truncate $ fromIntegral n ** (1/3 :: Double)
+
+main :: IO ()
+main = do
+ let highConfidence = stdArgs {maxSuccess = 10000}
+ putStrLn "running tests.."
+ quickCheckWith highConfidence (forAll smallInts cubedElementsSumToN)
+
+-- Tests -----------------------------------------------------------------------
+
+smallInts :: Gen Int
+smallInts = choose (-100000000, 100000000)
+
+cubedElementsSumToN :: Int -> Bool
+cubedElementsSumToN n = all (== n) d
+ where d = map (uncurry (+) . ((^(3 :: Int)) *** (^(3 :: Int))))
+ (cubeDecomposition n)
+
diff --git a/20121126_unionintersection/ui.hs b/20121126_unionintersection/ui.hs
@@ -0,0 +1,132 @@
+{-# OPTIONS_GHC -Wall #-}
+{-# LANGUAGE TemplateHaskell #-}
+
+import Data.List
+import Data.Hashable (Hashable)
+import Data.HashMap.Strict hiding (filter)
+import Control.Monad
+import Test.QuickCheck
+import Test.QuickCheck.All
+import Criterion.Main
+import Criterion.Config
+import System.Random.MWC
+
+-- O(n^2) ----------------------------------------------------------------------
+
+-- nub, loop + elem are O(n^2)
+i0 :: Eq a => [a] -> [a] -> [a]
+i0 _ [] = []
+i0 [] _ = []
+i0 (x:xs) ys = nub $ if x `elem` ys then x : i0 xs ys else i0 xs ys
+
+-- nub is O(n^2), otherwise linear
+u0 :: Eq a => [a] -> [a] -> [a]
+u0 xs ys = nub $ xs ++ go xs ys
+ where go as [] = as
+ go [] bs = bs
+ go as (b:bs) = if b `notElem` as then b : go as bs else go as bs
+
+-- O(n log n) ------------------------------------------------------------------
+
+-- sort (mergesort) is O(n log n), otherwise linear
+i1 :: Ord a => [a] -> [a] -> [a]
+i1 xs ys = go (sort xs) (sort ys) []
+ where go [] _ cs = cs
+ go _ [] cs = cs
+ go al@(a:as) bl@(b:bs) cs = case compare a b of
+ LT -> go as bl cs
+ GT -> go al bs cs
+ EQ -> go as bs (b:cs)
+
+-- sort (mergesort) is O(n log n), otherwise linear
+u1 :: Ord a => [a] -> [a] -> [a]
+u1 xs ys = go (sort xs) (sort ys) []
+ where go [] bs cs = bs ++ cs
+ go as [] cs = as ++ cs
+ go al@(a:as) bl@(b:bs) cs = case compare a b of
+ LT -> go as bl (a:cs)
+ GT -> go al bs (b:cs)
+ EQ -> go as bs (a:cs)
+
+-- O(n) ------------------------------------------------------------------------
+
+-- filter, fromList, zip are O(n), otherwise constant
+i2 :: (Enum a, Eq a, Hashable a) => [a] -> [a] -> [a]
+i2 xs = filter (\y -> member y . fromList $ zip xs ([1..] :: [Int]))
+
+-- filter, fromList, zip are O(n), otherwise constant
+u2 :: (Eq k, Hashable k) => [k] -> [k] -> [k]
+u2 xs ys = xs ++
+ filter (\y -> not . member y . fromList $ zip xs ([1..] :: [Int])) ys
+
+-- Tests -----------------------------------------------------------------------
+
+prop_i0ResultElementsAreInBoth :: Eq a => [a] -> [a] -> Bool
+prop_i0ResultElementsAreInBoth xs ys = all (`elem` xs) zs && all (`elem` ys) zs
+ where zs = i0 xs ys
+
+prop_i1ResultElementsAreInBoth :: Ord a => [a] -> [a] -> Bool
+prop_i1ResultElementsAreInBoth xs ys = all (`elem` xs) zs && all (`elem` ys) zs
+ where zs = i1 xs ys
+
+prop_i2ResultElementsAreInBoth :: (Enum a, Eq a, Num a, Hashable a)
+ => [a] -> [a] -> Bool
+prop_i2ResultElementsAreInBoth xs ys = all (`elem` xs) zs && all (`elem` ys) zs
+ where zs = i2 xs ys
+
+prop_u0ResultElementsInAtLeastOne :: Eq a => [a] -> [a] -> Bool
+prop_u0ResultElementsInAtLeastOne xs ys = all (`elem` (xs ++ ys)) zs
+ where zs = u0 xs ys
+
+prop_u1ResultElementsInAtLeastOne :: Ord a => [a] -> [a] -> Bool
+prop_u1ResultElementsInAtLeastOne xs ys = all (`elem` (xs ++ ys)) zs
+ where zs = u1 xs ys
+
+prop_u2ResultElementsInAtLeastOne :: (Eq a, Hashable a) => [a] -> [a] -> Bool
+prop_u2ResultElementsInAtLeastOne xs ys = all (`elem` (xs ++ ys)) zs
+ where zs = u2 xs ys
+
+runTestSuite :: IO Bool
+runTestSuite = $forAllProperties
+ (quickCheckWithResult (stdArgs {maxSuccess = 1000}))
+
+-- Benchmarks ------------------------------------------------------------------
+
+myConfig :: Config
+myConfig = defaultConfig { cfgPerformGC = ljust True }
+
+main :: IO ()
+main = do
+ prng <- create
+ [l0s, l1s] <- replicateM 2 $ replicateM 75 (uniformR (1 :: Int, 100) prng)
+ [l0m, l1m] <- replicateM 2 $ replicateM 125 (uniformR (1 :: Int, 100) prng)
+ [l0l, l1l] <- replicateM 2 $ replicateM 250 (uniformR (1 :: Int, 100) prng)
+
+ void runTestSuite
+
+ defaultMain [
+ bgroup "intersection - i0 " [ bench "i0s" $ nf (i0 l0s) l1s
+ , bench "i0m" $ nf (i0 l0m) l1m
+ , bench "i0l" $ nf (i0 l0l) l1l ]
+
+ , bgroup "intersection - i1 " [ bench "i1s" $ nf (i1 l0s) l1s
+ , bench "i1m" $ nf (i1 l0m) l1m
+ , bench "i1l" $ nf (i1 l0l) l1l ]
+
+ , bgroup "intersection - i2 " [ bench "i2s" $ nf (i2 l0s) l1s
+ , bench "i2m" $ nf (i2 l0m) l1m
+ , bench "i2l" $ nf (i2 l0l) l1l ]
+
+ , bgroup "union - u0 " [ bench "u0s" $ nf (u0 l0s) l1s
+ , bench "u0m" $ nf (u0 l0m) l1m
+ , bench "u0l" $ nf (u0 l0l) l1l ]
+
+ , bgroup "union - u1 " [ bench "u1s" $ nf (u1 l0s) l1s
+ , bench "u1m" $ nf (u1 l0m) l1m
+ , bench "u1l" $ nf (u1 l0l) l1l ]
+
+ , bgroup "union - u2 " [ bench "u2s" $ nf (u2 l0s) l1s
+ , bench "u2m" $ nf (u2 l0m) l1m
+ , bench "u2l" $ nf (u2 l0l) l1l ]
+ ]
+
diff --git a/20121126_unionintersection/ui.out b/20121126_unionintersection/ui.out
@@ -0,0 +1,180 @@
+=== prop_i0ResultElementsAreInBoth from ui.hs:64 ===
++++ OK, passed 1000 tests.
+
+=== prop_i1ResultElementsAreInBoth from ui.hs:68 ===
++++ OK, passed 1000 tests.
+
+=== prop_i2ResultElementsAreInBoth from ui.hs:72 ===
++++ OK, passed 1000 tests.
+
+=== prop_u0ResultElementsInAtLeastOne from ui.hs:77 ===
++++ OK, passed 1000 tests.
+
+=== prop_u1ResultElementsInAtLeastOne from ui.hs:81 ===
++++ OK, passed 1000 tests.
+
+=== prop_u2ResultElementsInAtLeastOne from ui.hs:85 ===
++++ OK, passed 1000 tests.
+
+warming up
+estimating clock resolution...
+mean is 1.653605 us (320001 iterations)
+found 2070 outliers among 319999 samples (0.6%)
+ 1657 (0.5%) high severe
+estimating cost of a clock call...
+mean is 65.59666 ns (17 iterations)
+found 2 outliers among 17 samples (11.8%)
+ 2 (11.8%) high severe
+
+benchmarking intersection - i0 /i0s
+mean: 241.8527 us, lb 240.9886 us, ub 243.1653 us, ci 0.950
+std dev: 5.370071 us, lb 3.981611 us, ub 8.452537 us, ci 0.950
+found 7 outliers among 100 samples (7.0%)
+ 4 (4.0%) high mild
+ 3 (3.0%) high severe
+variance introduced by outliers: 15.189%
+variance is moderately inflated by outliers
+
+benchmarking intersection - i0 /i0m
+mean: 1.349664 ms, lb 1.343737 ms, ub 1.356489 ms, ci 0.950
+std dev: 32.54633 us, lb 27.51927 us, ub 39.69676 us, ci 0.950
+found 4 outliers among 100 samples (4.0%)
+ 4 (4.0%) high mild
+variance introduced by outliers: 18.030%
+variance is moderately inflated by outliers
+
+benchmarking intersection - i0 /i0l
+mean: 10.43376 ms, lb 10.26692 ms, ub 10.68256 ms, ci 0.950
+std dev: 1.030502 ms, lb 766.8110 us, ub 1.357862 ms, ci 0.950
+found 11 outliers among 100 samples (11.0%)
+ 10 (10.0%) high severe
+variance introduced by outliers: 78.975%
+variance is severely inflated by outliers
+
+benchmarking intersection - i1 /i1s
+mean: 37.62627 us, lb 36.20585 us, ub 39.56645 us, ci 0.950
+std dev: 8.452334 us, lb 6.684560 us, ub 12.01732 us, ci 0.950
+found 3 outliers among 100 samples (3.0%)
+ 2 (2.0%) high mild
+ 1 (1.0%) high severe
+variance introduced by outliers: 95.715%
+variance is severely inflated by outliers
+
+benchmarking intersection - i1 /i1m
+mean: 60.59575 us, lb 60.08477 us, ub 61.36355 us, ci 0.950
+std dev: 3.184276 us, lb 2.424147 us, ub 4.954732 us, ci 0.950
+found 9 outliers among 100 samples (9.0%)
+ 7 (7.0%) high mild
+ 2 (2.0%) high severe
+variance introduced by outliers: 50.470%
+variance is severely inflated by outliers
+
+benchmarking intersection - i1 /i1l
+mean: 149.5444 us, lb 148.7898 us, ub 150.9952 us, ci 0.950
+std dev: 5.176023 us, lb 3.219088 us, ub 9.524480 us, ci 0.950
+found 5 outliers among 100 samples (5.0%)
+ 4 (4.0%) high severe
+variance introduced by outliers: 30.664%
+variance is moderately inflated by outliers
+
+benchmarking intersection - i2 /i2s
+mean: 9.463958 us, lb 9.407915 us, ub 9.542428 us, ci 0.950
+std dev: 336.3714 ns, lb 257.5346 ns, ub 423.1264 ns, ci 0.950
+found 10 outliers among 100 samples (10.0%)
+ 3 (3.0%) high mild
+ 7 (7.0%) high severe
+variance introduced by outliers: 31.653%
+variance is moderately inflated by outliers
+
+benchmarking intersection - i2 /i2m
+mean: 15.80304 us, lb 15.75625 us, ub 15.86975 us, ci 0.950
+std dev: 283.1245 ns, lb 217.4457 ns, ub 380.9612 ns, ci 0.950
+found 5 outliers among 100 samples (5.0%)
+ 3 (3.0%) high mild
+ 2 (2.0%) high severe
+variance introduced by outliers: 10.411%
+variance is moderately inflated by outliers
+
+benchmarking intersection - i2 /i2l
+mean: 30.04472 us, lb 29.94999 us, ub 30.17653 us, ci 0.950
+std dev: 569.5918 ns, lb 435.6022 ns, ub 743.6671 ns, ci 0.950
+found 6 outliers among 100 samples (6.0%)
+ 3 (3.0%) high mild
+ 3 (3.0%) high severe
+variance introduced by outliers: 11.374%
+variance is moderately inflated by outliers
+
+benchmarking union - u0 /u0s
+mean: 237.2854 us, lb 231.8887 us, ub 243.8647 us, ci 0.950
+std dev: 30.44916 us, lb 24.46645 us, ub 42.27376 us, ci 0.950
+found 2 outliers among 100 samples (2.0%)
+ 1 (1.0%) high severe
+variance introduced by outliers: 86.282%
+variance is severely inflated by outliers
+
+benchmarking union - u0 /u0m
+mean: 424.4515 us, lb 415.2468 us, ub 440.1109 us, ci 0.950
+std dev: 60.34614 us, lb 41.67318 us, ub 109.6783 us, ci 0.950
+found 1 outliers among 100 samples (1.0%)
+ 1 (1.0%) high severe
+variance introduced by outliers: 88.388%
+variance is severely inflated by outliers
+
+benchmarking union - u0 /u0l
+mean: 845.0848 us, lb 827.2701 us, ub 865.6639 us, ci 0.950
+std dev: 97.83496 us, lb 86.25617 us, ub 112.0636 us, ci 0.950
+found 1 outliers among 100 samples (1.0%)
+variance introduced by outliers: 84.158%
+variance is severely inflated by outliers
+
+benchmarking union - u1 /u1s
+mean: 32.13088 us, lb 31.85796 us, ub 32.63588 us, ci 0.950
+std dev: 1.838367 us, lb 1.202909 us, ub 3.379434 us, ci 0.950
+found 12 outliers among 100 samples (12.0%)
+ 11 (11.0%) high mild
+ 1 (1.0%) high severe
+variance introduced by outliers: 55.449%
+variance is severely inflated by outliers
+
+benchmarking union - u1 /u1m
+mean: 65.00069 us, lb 64.02871 us, ub 66.24941 us, ci 0.950
+std dev: 5.635944 us, lb 4.652454 us, ub 7.169802 us, ci 0.950
+found 5 outliers among 100 samples (5.0%)
+ 4 (4.0%) high mild
+ 1 (1.0%) high severe
+variance introduced by outliers: 73.831%
+variance is severely inflated by outliers
+
+benchmarking union - u1 /u1l
+mean: 159.6619 us, lb 157.4585 us, ub 163.0561 us, ci 0.950
+std dev: 13.78931 us, lb 10.02459 us, ub 21.04754 us, ci 0.950
+found 8 outliers among 100 samples (8.0%)
+ 5 (5.0%) high mild
+ 3 (3.0%) high severe
+variance introduced by outliers: 73.822%
+variance is severely inflated by outliers
+
+benchmarking union - u2 /u2s
+mean: 10.83968 us, lb 10.78467 us, ub 10.92027 us, ci 0.950
+std dev: 336.8579 ns, lb 251.8153 ns, ub 441.4622 ns, ci 0.950
+found 9 outliers among 100 samples (9.0%)
+ 3 (3.0%) high mild
+ 6 (6.0%) high severe
+variance introduced by outliers: 25.821%
+variance is moderately inflated by outliers
+
+benchmarking union - u2 /u2m
+mean: 17.35428 us, lb 17.27169 us, ub 17.47427 us, ci 0.950
+std dev: 503.9214 ns, lb 373.6216 ns, ub 660.5846 ns, ci 0.950
+found 7 outliers among 100 samples (7.0%)
+ 6 (6.0%) high severe
+variance introduced by outliers: 23.842%
+variance is moderately inflated by outliers
+
+benchmarking union - u2 /u2l
+mean: 31.64824 us, lb 31.48891 us, ub 31.94573 us, ci 0.950
+std dev: 1.078435 us, lb 668.9161 ns, ub 1.644798 us, ci 0.950
+found 4 outliers among 100 samples (4.0%)
+ 4 (4.0%) high severe
+variance introduced by outliers: 29.707%
+variance is moderately inflated by outliers
diff --git a/20121127_amazon/amazon.hs b/20121127_amazon/amazon.hs
@@ -0,0 +1,42 @@
+import Control.Monad
+import System.Random.MWC
+import Test.QuickCheck
+
+import Data.Map.Strict (empty, insert, deleteMax, findMax, size, toList)
+
+distanceToNull :: Num a => (a, a) -> a
+distanceToNull (x, y) = x^2 + y^2
+
+smallestHundred :: (Num a, Ord a) => [(a, a)] -> [(a, a)]
+smallestHundred xs = findSmallest xs empty where
+ findSmallest [] m = map fst . toList $ m
+ findSmallest (x:xs) m = case compare (size m) 100 of
+ GT -> error "you done fucked up"
+ LT -> findSmallest xs (insert x (distanceToNull x) m)
+ EQ -> if distanceToNull x >= snd (findMax m)
+ then findSmallest xs m
+ else findSmallest xs (insert x (distanceToNull x) $ deleteMax m)
+
+-- Tests -----------------------------------------------------------------------
+
+prop_smallestHundredAreSmallest :: [(Double, Double)] -> Bool
+prop_smallestHundredAreSmallest xs =
+ all (\x -> if x `notElem` sh then all (<= x) sh else True) xs
+ where sh = smallestHundred xs
+
+prop_smallestHundredAreMaxHundred :: [(Double, Double)] -> Bool
+prop_smallestHundredAreMaxHundred xs = length sh <= 100
+ where sh = smallestHundred xs
+
+main = do
+ -- QuickCheck stuff
+ quickCheck prop_smallestHundredAreMaxHundred
+ quickCheck prop_smallestHundredAreSmallest
+
+ -- Unit test
+ g <- create
+ z0s <- replicateM 1000000 (uniformR (-1000, 1000) g) :: IO [Int]
+ z1s <- replicateM 1000000 (uniformR (-1000, 1000) g) :: IO [Int]
+
+ print $ smallestHundred (zip z0s z1s)
+