Skip to content

Instantly share code, notes, and snippets.

@tibbe
Created October 29, 2015 09:51
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 tibbe/4933970caa9b374f5262 to your computer and use it in GitHub Desktop.
Save tibbe/4933970caa9b374f5262 to your computer and use it in GitHub Desktop.
Benchmarks from the Haskell eXchange talk on High performance programming in Haskell
{-# LANGUAGE BangPatterns #-}
{-# LANGUAGE DeriveGeneric, DeriveAnyClass #-}
module Main (main) where
import Control.DeepSeq
import Criterion.Main
import GHC.Generics (Generic)
import Prelude hiding (replicate, sum)
data List = Cons Int List | Nil
deriving (Generic, NFData)
sum :: List -> Int
sum = go 0
where go !n Nil = n
go n (Cons x xs) = go (x+n) xs
replicate :: Int -> List
replicate 0 = Nil
replicate n = Cons n (replicate (n-1))
------------------------------------------------------------------------
data UList = UCons !Int UList | UNil
deriving (Generic, NFData)
sumU :: UList -> Int
sumU = go 0
where go !n UNil = n
go n (UCons x xs) = go (x+n) xs
replicateU :: Int -> UList
replicateU 0 = UNil
replicateU n = UCons n (replicateU (n-1))
------------------------------------------------------------------------
n :: Int
n = 2^20
setup = return (replicate n)
setupU = return (replicateU n)
main = defaultMain [
bgroup "streaming" [
bench "sumU" $ whnf sumU (replicateU n)
, bench "sum" $ whnf sum (replicate n)
]
, bgroup "non-streaming" [
env setupU $ \ ~ xs -> bench "sumU" $ whnf sumU xs
, env setup $ \ ~ xs -> bench "sum" $ whnf sum xs
]
]
Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment