Skip to content
This repository has been archived by the owner on Sep 20, 2023. It is now read-only.

Commit

Permalink
Cleanup the interfaces of Main.hs and Benchmark.hs
Browse files Browse the repository at this point in the history
The exported interfaces were duplicated and some of the interfaces were not
consumable by users. Now all the exported interfaces are good for users and
Gauge.hs simply exports everything except analysis for easy import.

This is mostly refactoring change but some minor functionality changes also
happened e.g. the benchmark' and benchmarWith' now have a different return
type. The earlier implementation of these was incorrect.

The effect of the change can viewed using haddock generated html.
  • Loading branch information
harendra-kumar committed Nov 11, 2017
1 parent e0fd468 commit 65be220
Show file tree
Hide file tree
Showing 8 changed files with 241 additions and 307 deletions.
37 changes: 6 additions & 31 deletions Gauge.hs
Original file line number Diff line number Diff line change
@@ -1,5 +1,4 @@
{-# LANGUAGE CPP #-}
{-# LANGUAGE RecordWildCards #-}
-- |
-- Module : Gauge
-- Copyright : (c) 2009-2014 Bryan O'Sullivan
Expand All @@ -9,38 +8,14 @@
-- Stability : experimental
-- Portability : GHC
--
-- Core benchmarking code.
-- Fast and reliable micro benchmarking.

module Gauge
(
-- * Benchmarkable code
Benchmarkable
-- * Creating a benchmark suite
, Benchmark
, env
, envWithCleanup
, perBatchEnv
, perBatchEnvWithCleanup
, perRunEnv
, perRunEnvWithCleanup
, toBenchmarkable
, bench
, bgroup
-- ** Running a benchmark
, nf
, whnf
, nfIO
, whnfIO
-- * For interactive use
, benchmark
, benchmarkWith
#ifdef HAVE_ANALYSIS
, benchmark'
, benchmarkWith'
#endif
( module Gauge.Benchmark
, module Gauge.Main
, module Gauge.Main.Options
) where

#ifdef HAVE_ANALYSIS
import Gauge.Analysis (benchmark', benchmarkWith')
#endif
import Gauge.Benchmark
import Gauge.Main
import Gauge.Main.Options
26 changes: 16 additions & 10 deletions Gauge/Analysis.hs
Original file line number Diff line number Diff line change
Expand Up @@ -43,13 +43,13 @@ import Data.Monoid
import Control.Arrow (second)
import Control.DeepSeq (NFData(rnf))
import Control.Monad (forM_, when)
import Gauge.Benchmark (Benchmarkable, runWithAnalysisInteractive)
import Gauge.Benchmark (Benchmark (..), Benchmarkable, runBenchmarkWith)
import Gauge.IO.Printf (note, printError, prolix, rewindClearLine)
import Gauge.Main.Options (defaultConfig, Config(..), Verbosity (..),
DisplayMode (..))
import Gauge.Measurement (Measured(measTime), secs, rescale, measureKeys,
measureAccessors_, validateAccessors, renderNames)
import Gauge.Monad (Gauge, askConfig, gaugeIO, Crit(..), askCrit)
import Gauge.Monad (Gauge, askConfig, gaugeIO, Crit(..), askCrit, withConfig)
import Data.Data (Data, Typeable)
import Data.Int (Int64)
import Data.IORef (IORef, readIORef, writeIORef)
Expand Down Expand Up @@ -470,12 +470,18 @@ printOverallEffect Slight = "slightly inflated"
printOverallEffect Moderate = "moderately inflated"
printOverallEffect Severe = "severely inflated"

-- | Run a benchmark interactively, analyse its performance, and
-- return the analysis.
benchmark' :: Benchmarkable -> IO Report
benchmark' = benchmarkWith' defaultConfig
-- XXX The original type of these types returned 'Report' type. But the
-- implementation was wrong as it was not running any environment settings on
-- the way to the benchmark. Now, we have used the correct function to do that
-- but unfortunately that function returns void. That can be fixed though if it
-- is important.

-- | Run a benchmark interactively and analyse its performance.
benchmarkWith' :: Config -> Benchmarkable -> IO ()
benchmarkWith' cfg bm =
withConfig cfg $
runBenchmarkWith analyseBenchmark (const True) (Benchmark "function" bm)

-- | Run a benchmark interactively, analyse its performance, and
-- return the analysis.
benchmarkWith' :: Config -> Benchmarkable -> IO Report
benchmarkWith' = runWithAnalysisInteractive analyseBenchmark
-- | Run a benchmark interactively and analyse its performanc.
benchmark' :: Benchmarkable -> IO ()
benchmark' = benchmarkWith' defaultConfig
Loading

0 comments on commit 65be220

Please sign in to comment.