1
1
mirror of https://github.com/github/semantic.git synced 2024-11-28 01:47:01 +03:00
semantic/bench/Main.hs

42 lines
1.4 KiB
Haskell
Raw Normal View History

{-# LANGUAGE DeriveAnyClass, FlexibleInstances, StandaloneDeriving #-}
{-# OPTIONS_GHC -fno-warn-orphans #-}
2016-05-31 16:23:43 +03:00
module Main where
2016-05-31 16:27:00 +03:00
2016-05-31 17:53:23 +03:00
import Alignment
2016-05-31 16:27:00 +03:00
import Criterion.Main
import Data.Bifunctor.Join
import Data.String
import Data.These
2016-05-31 16:27:00 +03:00
import Prologue
import Test.QuickCheck
2016-05-31 16:27:00 +03:00
main :: IO ()
2016-05-31 17:53:23 +03:00
main = do
benchmarks <- sequenceA [ generativeBenchmark "numberedRows" length (nf (numberedRows :: [Join These ()] -> [Join These (Int, ())])) ]
defaultMain benchmarks
2016-05-31 17:40:25 +03:00
generativeBenchmark :: (Arbitrary a, Show m) => String -> (a -> m) -> (a -> Benchmarkable) -> IO Benchmark
generativeBenchmark name metric benchmark = do
benchmarks <- traverse measure [0..100]
pure $! bgroup name benchmarks
where measure n = do
input <- generate (resize n arbitrary)
let measurement = metric input
2016-05-31 17:40:25 +03:00
pure $! bench (show measurement) (benchmark input)
-- Instances
deriving instance (NFData a, NFData b) => NFData (These a b)
deriving instance NFData a => NFData (Join These a)
instance (Arbitrary a, Arbitrary b) => Arbitrary (These a b) where
arbitrary = oneof [ This <$> arbitrary
, That <$> arbitrary
, These <$> arbitrary <*> arbitrary ]
shrink = these (fmap This . shrink) (fmap That . shrink) (\ a b -> (This <$> shrink a) ++ (That <$> shrink b) ++ (These <$> shrink a <*> shrink b))
instance Arbitrary a => Arbitrary (Join These a) where
arbitrary = Join <$> arbitrary
shrink (Join a) = Join <$> shrink a