Skip to content

Commit

Permalink
Beginnings of a benchmark suite.
Browse files Browse the repository at this point in the history
  • Loading branch information
bos committed Dec 13, 2011
1 parent 5726d7a commit dec333a
Show file tree
Hide file tree
Showing 4 changed files with 71 additions and 0 deletions.
1 change: 1 addition & 0 deletions .hgignore
Expand Up @@ -2,6 +2,7 @@
\.(?:aux|eventlog|h[ip]|hs.html|log|[mt]ix|[oa]|orig|prof|ps|rej|swp)$
~$
benchmarks/Arse
benchmarks/dist
benchmarks/med.txt
benchmarks/tiny
hpc.*\.html$
Expand Down
2 changes: 2 additions & 0 deletions attoparsec.cabal
Expand Up @@ -18,8 +18,10 @@ description:
file formats.
extra-source-files:
README.markdown
benchmarks/Benchmarks.hs
benchmarks/Makefile
benchmarks/Tiny.hs
benchmarks/attoparsec-benchmarks.cabal
benchmarks/med.txt.bz2
tests/Makefile
tests/QC.hs
Expand Down
50 changes: 50 additions & 0 deletions benchmarks/Benchmarks.hs
@@ -0,0 +1,50 @@
{-# LANGUAGE BangPatterns #-}

import Control.Applicative
import Criterion.Main (bench, bgroup, defaultMain, nf, whnf)
import Data.Char
import qualified Data.Attoparsec.ByteString as AB
import qualified Data.Attoparsec.ByteString.Char8 as AC
import qualified Data.Attoparsec.Text as AT
import qualified Data.ByteString as B
import qualified Data.ByteString.Char8 as BC
import qualified Data.Text as T
import qualified Text.Parsec as P
import qualified Text.Parsec.Text as P
import Control.DeepSeq (NFData(rnf))
import Data.ByteString.Internal (ByteString(..))

instance NFData ByteString where
rnf (PS _ _ _) = ()

instance NFData P.ParseError where
rnf = rnf . show

main = do
let s = ['a'..'z'] ++ ['A'..'Z'] ++ ['0'..'9']
!b = BC.pack s
!t = T.pack s
defaultMain [
bgroup "comparison" [
bgroup "parsec-vs-atto" [
bench "attoparsec B" $ whnf (AB.parse (many (AC.satisfy AC.isAlpha_ascii))) b
, bench "attoparsec T" $ whnf (AT.parse (many (AT.satisfy AC.isAlpha_ascii))) t
, bench "parsec B" $ whnf (P.parse (many (P.satisfy AC.isAlpha_ascii)) "") b
, bench "parsec S" $ whnf (P.parse (many (P.satisfy AC.isAlpha_ascii)) "") s
, bench "parsec T" $ whnf (P.parse (many (P.satisfy AC.isAlpha_ascii)) "") t
]
, bgroup "many-vs-takeWhile" [
bench "many" $ whnf (AB.parse (many (AC.satisfy AC.isAlpha_ascii))) b
, bench "takeWhile" $ whnf (AB.parse (AC.takeWhile AC.isAlpha_ascii)) b
]
, bgroup "letter-vs-many" [
bench "letter" $ whnf (AB.parse (many AC.letter_ascii)) b
, bench "many" $ whnf (AB.parse (many (AC.satisfy AC.isAlpha_ascii))) b
]
]
, bgroup "takeWhile" [
bench "isAlpha" $ whnf (AB.parse (AC.takeWhile isAlpha)) b
, bench "isAlpha_ascii" $ whnf (AB.parse (AC.takeWhile AC.isAlpha_ascii)) b
, bench "isAlpha_iso8859_15" $ whnf (AB.parse (AC.takeWhile AC.isAlpha_iso8859_15)) b
]
]
18 changes: 18 additions & 0 deletions benchmarks/attoparsec-benchmarks.cabal
@@ -0,0 +1,18 @@
-- These benchmarks are not intended to be installed.
-- So don't install 'em.

name: attoparsec-benchmarks
version: 0
cabal-version: >=1.2
build-type: Simple

executable attoparsec-benchmarks
main-is: Benchmarks.hs
build-depends:
attoparsec,
base,
bytestring,
criterion >= 0.5,
deepseq == 1.1.*,
parsec >= 3.1.2,
text

0 comments on commit dec333a

Please sign in to comment.