Skip to content

Commit

Permalink
Improve and fix benchmarking suite
Browse files Browse the repository at this point in the history
  • Loading branch information
alt-romes committed Jul 5, 2023
1 parent 2385570 commit 8f645e5
Show file tree
Hide file tree
Showing 5 changed files with 57 additions and 10 deletions.
9 changes: 9 additions & 0 deletions BENCHMARKING.md
Original file line number Diff line number Diff line change
@@ -0,0 +1,9 @@
### Comparing benchmarks against baselines
```
cabal bench --benchmark-options="+RTS -T -RTS --baseline baseline.csv"
```

### Saving new baselines
```
cabal bench --benchmark-options="+RTS -T -RTS --csv baseline.csv"
```
7 changes: 7 additions & 0 deletions baseline.csv
Original file line number Diff line number Diff line change
@@ -0,0 +1,7 @@
Name,Mean (ps),2*Stdev (ps),Allocated,Copied,Peak Memory
All.Tests.Symbolic bench.i1,30148987500,1892104820,108977098,5670033,42991616
All.Tests.Symbolic bench.i2,32330562500,2040971046,111012444,5925886,42991616
All.Tests.Symbolic bench.i3,55056050000,4438483130,199744799,17062413,50331648
All.Tests.Symbolic bench.i4,37195237500,2147631488,133168692,9604120,50331648
All.Tests.Symbolic bench.i5,28361087500,1849731332,104740735,5986935,50331648
All.Tests.Symbolic bench.i6,28716525000,2002342972,102315060,5563405,50331648
7 changes: 5 additions & 2 deletions hegg.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -129,8 +129,11 @@ benchmark hegg-bench
tasty,
tasty-hunit,
tasty-quickcheck,
tasty-bench >= 0.2 && < 0.4
ghc-options: -with-rtsopts=-A32m -threaded
tasty-bench >= 0.2,
deepseq
ghc-options: -with-rtsopts=-A32m
if impl(ghc >= 8.6)
ghc-options: -fproc-alignment=64

Flag vizdot
Description: Compile 'Data.Equality.Graph.Dot' module to visualize e-graphs
Expand Down
37 changes: 31 additions & 6 deletions test/Bench.hs
Original file line number Diff line number Diff line change
@@ -1,18 +1,43 @@
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE StandaloneDeriving, FlexibleInstances, DeriveAnyClass, RankNTypes, QuantifiedConstraints, UndecidableInstances, DeriveGeneric #-}
import Test.Tasty.Bench

import GHC.Generics
import Control.DeepSeq

import Data.Equality.Utils
import Invariants
import Sym
import Lambda
import SimpleSym

-- Instances for benchmarking. It's amazing this works!
deriving instance (forall a. Generic a => Generic (f a)) => Generic (Fix f)
deriving instance NFData UOp
deriving instance NFData BOp
deriving instance NFData a => NFData (Expr a)
deriving instance (forall a. NFData a => NFData (f a), forall a. Generic a => Generic (f a)) => NFData (Fix f)

tests :: [Benchmark]
tests = [ bgroup "Tests"
[ symTests
, lambdaTests
, simpleSymTests
, invariants
[ bgroup "Symbolic bench"
[ bench "i1" $
nf rewrite (Fix $ BinOp Integral 1 "x")

, bench "i2" $
nf rewrite (Fix $ BinOp Integral (Fix $ UnOp Cos "x") "x")

, bench "i3" $
nf rewrite (Fix $ BinOp Integral (Fix $ BinOp Pow "x" 1) "x")

, bench "i4" $
nf rewrite (_i ((*) "x" (_cos "x")) "x")

, bench "i5" $
nf rewrite (_i ((*) (_cos "x") "x") "x")

, bench "i6" $
nf rewrite (_i (_ln "x") "x")
]
-- , invariants
] ]

main :: IO ()
Expand Down
7 changes: 5 additions & 2 deletions test/Sym.hs
Original file line number Diff line number Diff line change
Expand Up @@ -6,8 +6,10 @@
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE DeriveGeneric #-}
module Sym where

import GHC.Generics
import Test.Tasty
import Test.Tasty.HUnit

Expand Down Expand Up @@ -35,6 +37,7 @@ data Expr a = Sym !String
| BinOp !BOp !a !a
deriving ( Eq, Ord, Show
, Functor, Foldable, Traversable
, Generic
)
data BOp = Add
| Sub
Expand All @@ -43,13 +46,13 @@ data BOp = Add
| Pow
| Diff
| Integral
deriving (Eq, Ord, Show)
deriving (Eq, Ord, Show, Generic)

data UOp = Sin
| Cos
| Sqrt
| Ln
deriving (Eq, Ord, Show)
deriving (Eq, Ord, Show, Generic)

instance IsString (Fix Expr) where
fromString = Fix . Sym
Expand Down

0 comments on commit 8f645e5

Please sign in to comment.