{-# LANGUAGE CPP #-}
{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE RankNTypes #-}

-----------------------------------------------------------------------------

-- |
-- Module      :  Distribution.Simple.Benchmark
-- Copyright   :  Isaac Jones 2003-2004
--                Duncan Coutts 2007
-- License     :  BSD3
--
-- Maintainer  :  cabal-devel@haskell.org
-- Portability :  portable
--
-- Definition of the benchmarking command-line options.
-- See: @Distribution.Simple.Setup@
module Distribution.Simple.Setup.Benchmark
  ( BenchmarkFlags (..)
  , emptyBenchmarkFlags
  , defaultBenchmarkFlags
  , benchmarkCommand
  , benchmarkOptions'
  ) where

import Distribution.Compat.Prelude hiding (get)
import Prelude ()

import Distribution.Simple.Command hiding (boolOpt, boolOpt')
import Distribution.Simple.Flag
import Distribution.Simple.InstallDirs
import Distribution.Simple.Utils
import Distribution.Verbosity

import Distribution.Simple.Setup.Common

-- ------------------------------------------------------------

-- * Benchmark flags

-- ------------------------------------------------------------

data BenchmarkFlags = BenchmarkFlags
  { BenchmarkFlags -> Flag FilePath
benchmarkDistPref :: Flag FilePath
  , BenchmarkFlags -> Flag Verbosity
benchmarkVerbosity :: Flag Verbosity
  , BenchmarkFlags -> [PathTemplate]
benchmarkOptions :: [PathTemplate]
  }
  deriving (Int -> BenchmarkFlags -> ShowS
[BenchmarkFlags] -> ShowS
BenchmarkFlags -> FilePath
(Int -> BenchmarkFlags -> ShowS)
-> (BenchmarkFlags -> FilePath)
-> ([BenchmarkFlags] -> ShowS)
-> Show BenchmarkFlags
forall a.
(Int -> a -> ShowS) -> (a -> FilePath) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> BenchmarkFlags -> ShowS
showsPrec :: Int -> BenchmarkFlags -> ShowS
$cshow :: BenchmarkFlags -> FilePath
show :: BenchmarkFlags -> FilePath
$cshowList :: [BenchmarkFlags] -> ShowS
showList :: [BenchmarkFlags] -> ShowS
Show, (forall x. BenchmarkFlags -> Rep BenchmarkFlags x)
-> (forall x. Rep BenchmarkFlags x -> BenchmarkFlags)
-> Generic BenchmarkFlags
forall x. Rep BenchmarkFlags x -> BenchmarkFlags
forall x. BenchmarkFlags -> Rep BenchmarkFlags x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. BenchmarkFlags -> Rep BenchmarkFlags x
from :: forall x. BenchmarkFlags -> Rep BenchmarkFlags x
$cto :: forall x. Rep BenchmarkFlags x -> BenchmarkFlags
to :: forall x. Rep BenchmarkFlags x -> BenchmarkFlags
Generic, Typeable)

instance Binary BenchmarkFlags
instance Structured BenchmarkFlags

defaultBenchmarkFlags :: BenchmarkFlags
defaultBenchmarkFlags :: BenchmarkFlags
defaultBenchmarkFlags =
  BenchmarkFlags
    { benchmarkDistPref :: Flag FilePath
benchmarkDistPref = Flag FilePath
forall a. Flag a
NoFlag
    , benchmarkVerbosity :: Flag Verbosity
benchmarkVerbosity = Verbosity -> Flag Verbosity
forall a. a -> Flag a
Flag Verbosity
normal
    , benchmarkOptions :: [PathTemplate]
benchmarkOptions = []
    }

benchmarkCommand :: CommandUI BenchmarkFlags
benchmarkCommand :: CommandUI BenchmarkFlags
benchmarkCommand =
  CommandUI
    { commandName :: FilePath
commandName = FilePath
"bench"
    , commandSynopsis :: FilePath
commandSynopsis =
        FilePath
"Run all/specific benchmarks."
    , commandDescription :: Maybe ShowS
commandDescription = ShowS -> Maybe ShowS
forall a. a -> Maybe a
Just (ShowS -> Maybe ShowS) -> ShowS -> Maybe ShowS
forall a b. (a -> b) -> a -> b
$ \FilePath
_pname ->
        ShowS
wrapText ShowS -> ShowS
forall a b. (a -> b) -> a -> b
$
          ShowS
testOrBenchmarkHelpText FilePath
"benchmark"
    , commandNotes :: Maybe ShowS
commandNotes = Maybe ShowS
forall a. Maybe a
Nothing
    , commandUsage :: ShowS
commandUsage =
        FilePath -> [FilePath] -> ShowS
usageAlternatives
          FilePath
"bench"
          [ FilePath
"[FLAGS]"
          , FilePath
"BENCHCOMPONENTS [FLAGS]"
          ]
    , commandDefaultFlags :: BenchmarkFlags
commandDefaultFlags = BenchmarkFlags
defaultBenchmarkFlags
    , commandOptions :: ShowOrParseArgs -> [OptionField BenchmarkFlags]
commandOptions = ShowOrParseArgs -> [OptionField BenchmarkFlags]
benchmarkOptions'
    }

benchmarkOptions' :: ShowOrParseArgs -> [OptionField BenchmarkFlags]
benchmarkOptions' :: ShowOrParseArgs -> [OptionField BenchmarkFlags]
benchmarkOptions' ShowOrParseArgs
showOrParseArgs =
  [ (BenchmarkFlags -> Flag Verbosity)
-> (Flag Verbosity -> BenchmarkFlags -> BenchmarkFlags)
-> OptionField BenchmarkFlags
forall flags.
(flags -> Flag Verbosity)
-> (Flag Verbosity -> flags -> flags) -> OptionField flags
optionVerbosity
      BenchmarkFlags -> Flag Verbosity
benchmarkVerbosity
      (\Flag Verbosity
v BenchmarkFlags
flags -> BenchmarkFlags
flags{benchmarkVerbosity = v})
  , (BenchmarkFlags -> Flag FilePath)
-> (Flag FilePath -> BenchmarkFlags -> BenchmarkFlags)
-> ShowOrParseArgs
-> OptionField BenchmarkFlags
forall flags.
(flags -> Flag FilePath)
-> (Flag FilePath -> flags -> flags)
-> ShowOrParseArgs
-> OptionField flags
optionDistPref
      BenchmarkFlags -> Flag FilePath
benchmarkDistPref
      (\Flag FilePath
d BenchmarkFlags
flags -> BenchmarkFlags
flags{benchmarkDistPref = d})
      ShowOrParseArgs
showOrParseArgs
  , FilePath
-> [FilePath]
-> FilePath
-> (BenchmarkFlags -> [PathTemplate])
-> ([PathTemplate] -> BenchmarkFlags -> BenchmarkFlags)
-> MkOptDescr
     (BenchmarkFlags -> [PathTemplate])
     ([PathTemplate] -> BenchmarkFlags -> BenchmarkFlags)
     BenchmarkFlags
-> OptionField BenchmarkFlags
forall get set a.
FilePath
-> [FilePath]
-> FilePath
-> get
-> set
-> MkOptDescr get set a
-> OptionField a
option
      []
      [FilePath
"benchmark-options"]
      ( FilePath
"give extra options to benchmark executables "
          FilePath -> ShowS
forall a. [a] -> [a] -> [a]
++ FilePath
"(name templates can use $pkgid, $compiler, "
          FilePath -> ShowS
forall a. [a] -> [a] -> [a]
++ FilePath
"$os, $arch, $benchmark)"
      )
      BenchmarkFlags -> [PathTemplate]
benchmarkOptions
      (\[PathTemplate]
v BenchmarkFlags
flags -> BenchmarkFlags
flags{benchmarkOptions = v})
      ( FilePath
-> (FilePath -> [PathTemplate])
-> ([PathTemplate] -> [FilePath])
-> MkOptDescr
     (BenchmarkFlags -> [PathTemplate])
     ([PathTemplate] -> BenchmarkFlags -> BenchmarkFlags)
     BenchmarkFlags
forall b a.
Monoid b =>
FilePath
-> (FilePath -> b)
-> (b -> [FilePath])
-> MkOptDescr (a -> b) (b -> a -> a) a
reqArg'
          FilePath
"TEMPLATES"
          ((FilePath -> PathTemplate) -> [FilePath] -> [PathTemplate]
forall a b. (a -> b) -> [a] -> [b]
map FilePath -> PathTemplate
toPathTemplate ([FilePath] -> [PathTemplate])
-> (FilePath -> [FilePath]) -> FilePath -> [PathTemplate]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. FilePath -> [FilePath]
splitArgs)
          ([FilePath] -> [PathTemplate] -> [FilePath]
forall a b. a -> b -> a
const [])
      )
  , FilePath
-> [FilePath]
-> FilePath
-> (BenchmarkFlags -> [PathTemplate])
-> ([PathTemplate] -> BenchmarkFlags -> BenchmarkFlags)
-> MkOptDescr
     (BenchmarkFlags -> [PathTemplate])
     ([PathTemplate] -> BenchmarkFlags -> BenchmarkFlags)
     BenchmarkFlags
-> OptionField BenchmarkFlags
forall get set a.
FilePath
-> [FilePath]
-> FilePath
-> get
-> set
-> MkOptDescr get set a
-> OptionField a
option
      []
      [FilePath
"benchmark-option"]
      ( FilePath
"give extra option to benchmark executables "
          FilePath -> ShowS
forall a. [a] -> [a] -> [a]
++ FilePath
"(no need to quote options containing spaces, "
          FilePath -> ShowS
forall a. [a] -> [a] -> [a]
++ FilePath
"name template can use $pkgid, $compiler, "
          FilePath -> ShowS
forall a. [a] -> [a] -> [a]
++ FilePath
"$os, $arch, $benchmark)"
      )
      BenchmarkFlags -> [PathTemplate]
benchmarkOptions
      (\[PathTemplate]
v BenchmarkFlags
flags -> BenchmarkFlags
flags{benchmarkOptions = v})
      ( FilePath
-> (FilePath -> [PathTemplate])
-> ([PathTemplate] -> [FilePath])
-> MkOptDescr
     (BenchmarkFlags -> [PathTemplate])
     ([PathTemplate] -> BenchmarkFlags -> BenchmarkFlags)
     BenchmarkFlags
forall b a.
Monoid b =>
FilePath
-> (FilePath -> b)
-> (b -> [FilePath])
-> MkOptDescr (a -> b) (b -> a -> a) a
reqArg'
          FilePath
"TEMPLATE"
          (\FilePath
x -> [FilePath -> PathTemplate
toPathTemplate FilePath
x])
          ((PathTemplate -> FilePath) -> [PathTemplate] -> [FilePath]
forall a b. (a -> b) -> [a] -> [b]
map PathTemplate -> FilePath
fromPathTemplate)
      )
  ]

emptyBenchmarkFlags :: BenchmarkFlags
emptyBenchmarkFlags :: BenchmarkFlags
emptyBenchmarkFlags = BenchmarkFlags
forall a. Monoid a => a
mempty

instance Monoid BenchmarkFlags where
  mempty :: BenchmarkFlags
mempty = BenchmarkFlags
forall a. (Generic a, GMonoid (Rep a)) => a
gmempty
  mappend :: BenchmarkFlags -> BenchmarkFlags -> BenchmarkFlags
mappend = BenchmarkFlags -> BenchmarkFlags -> BenchmarkFlags
forall a. Semigroup a => a -> a -> a
(<>)

instance Semigroup BenchmarkFlags where
  <> :: BenchmarkFlags -> BenchmarkFlags -> BenchmarkFlags
(<>) = BenchmarkFlags -> BenchmarkFlags -> BenchmarkFlags
forall a. (Generic a, GSemigroup (Rep a)) => a -> a -> a
gmappend