Skip to content

Instantly share code, notes, and snippets.

@mbrcknl
Created September 15, 2014 23:42
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 mbrcknl/3532be49d945dff15b8d to your computer and use it in GitHub Desktop.
Save mbrcknl/3532be49d945dff15b8d to your computer and use it in GitHub Desktop.
import Criterion.Main (Benchmark, bench, bgroup, defaultMain, env, whnf)
import Data.Foldable (Foldable(..),toList)
import Data.Maybe (Maybe(..))
import Data.Monoid (Monoid(..), (<>))
import Data.Set (Set,fromList)
import Prelude (Eq(..),Ord(..),Show(..),Int,(.),($),($!),Num(..),const,take,iterate,map,return,IO)
last :: Foldable t => t a -> Maybe a
last = foldl (const Just) Nothing
data Snoc a = Nil | Snoc (Snoc a) a
deriving (Eq,Ord,Show)
instance Foldable Snoc where
foldMap _ Nil = mempty
foldMap f (Snoc xs x) = foldMap f xs <> f x
inf :: Snoc Int
inf = go 0
where
go n = Snoc (go $! n+1) n
-- immediately returns (Just 0)
lastInf :: Maybe Int
lastInf = last inf
-- loops forever
lastInfToList :: Maybe Int
lastInfToList = last (toList inf)
-- O(log n)
lastSet :: Set a -> Maybe a
lastSet = last
-- O(n)
lastSetToList :: Set a -> Maybe a
lastSetToList = last . toList
sizes :: [Int]
sizes = take 10 $ iterate (*2) 512
inputSet :: Int -> IO (Set Int)
inputSet n = return $ fromList [1..n]
benchSet :: (Set Int -> Maybe Int) -> Int -> Benchmark
benchSet f n = env (inputSet n) $ bench (show n) . whnf f
main :: IO ()
main = defaultMain
[ bgroup "noList" $ map (benchSet lastSet) sizes
, bgroup "toList" $ map (benchSet lastSetToList) sizes
]
Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment