{-# LANGUAGE RecordWildCards #-}

-- | cabal-install CLI command: bench
--
module Distribution.Client.CmdBench (
    -- * The @bench@ CLI and action
    benchCommand,
    benchAction,

    -- * Internals exposed for testing
    componentNotBenchmarkProblem,
    isSubComponentProblem,
    noBenchmarksProblem,
    selectPackageTargets,
    selectComponentTarget
  ) where

import Distribution.Client.Compat.Prelude
import Prelude ()

import Distribution.Client.ProjectOrchestration
import Distribution.Client.CmdErrorMessages
         ( renderTargetSelector, showTargetSelector, renderTargetProblem,
           renderTargetProblemNoTargets, plural, targetSelectorPluralPkgs,
           targetSelectorFilter )
import Distribution.Client.TargetProblem
         ( TargetProblem (..) )
import Distribution.Client.NixStyleOptions
         ( NixStyleFlags (..), nixStyleOptions, defaultNixStyleFlags )
import Distribution.Client.Setup
         ( GlobalFlags, ConfigFlags(..) )
import Distribution.Simple.Flag
         ( fromFlagOrDefault )
import Distribution.Simple.Command
         ( CommandUI(..), usageAlternatives )
import Distribution.Verbosity
         ( normal )
import Distribution.Simple.Utils
         ( wrapText, die' )

benchCommand :: CommandUI (NixStyleFlags ())
benchCommand :: CommandUI (NixStyleFlags ())
benchCommand = CommandUI {
  commandName :: String
commandName         = String
"v2-bench",
  commandSynopsis :: String
commandSynopsis     = String
"Run benchmarks.",
  commandUsage :: String -> String
commandUsage        = String -> [String] -> String -> String
usageAlternatives String
"v2-bench" [ String
"[TARGETS] [FLAGS]" ],
  commandDescription :: Maybe (String -> String)
commandDescription  = forall a. a -> Maybe a
Just forall a b. (a -> b) -> a -> b
$ \String
_ -> String -> String
wrapText forall a b. (a -> b) -> a -> b
$
        String
"Runs the specified benchmarks, first ensuring they are up to "
     forall a. [a] -> [a] -> [a]
++ String
"date.\n\n"

     forall a. [a] -> [a] -> [a]
++ String
"Any benchmark in any package in the project can be specified. "
     forall a. [a] -> [a] -> [a]
++ String
"A package can be specified in which case all the benchmarks in the "
     forall a. [a] -> [a] -> [a]
++ String
"package are run. The default is to run all the benchmarks in the "
     forall a. [a] -> [a] -> [a]
++ String
"package in the current directory.\n\n"

     forall a. [a] -> [a] -> [a]
++ String
"Dependencies are built or rebuilt as necessary. Additional "
     forall a. [a] -> [a] -> [a]
++ String
"configuration flags can be specified on the command line and these "
     forall a. [a] -> [a] -> [a]
++ String
"extend the project configuration from the 'cabal.project', "
     forall a. [a] -> [a] -> [a]
++ String
"'cabal.project.local' and other files.",
  commandNotes :: Maybe (String -> String)
commandNotes        = forall a. a -> Maybe a
Just forall a b. (a -> b) -> a -> b
$ \String
pname ->
        String
"Examples:\n"
     forall a. [a] -> [a] -> [a]
++ String
"  " forall a. [a] -> [a] -> [a]
++ String
pname forall a. [a] -> [a] -> [a]
++ String
" v2-bench\n"
     forall a. [a] -> [a] -> [a]
++ String
"    Run all the benchmarks in the package in the current directory\n"
     forall a. [a] -> [a] -> [a]
++ String
"  " forall a. [a] -> [a] -> [a]
++ String
pname forall a. [a] -> [a] -> [a]
++ String
" v2-bench pkgname\n"
     forall a. [a] -> [a] -> [a]
++ String
"    Run all the benchmarks in the package named pkgname\n"
     forall a. [a] -> [a] -> [a]
++ String
"  " forall a. [a] -> [a] -> [a]
++ String
pname forall a. [a] -> [a] -> [a]
++ String
" v2-bench cname\n"
     forall a. [a] -> [a] -> [a]
++ String
"    Run the benchmark named cname\n"
     forall a. [a] -> [a] -> [a]
++ String
"  " forall a. [a] -> [a] -> [a]
++ String
pname forall a. [a] -> [a] -> [a]
++ String
" v2-bench cname -O2\n"
     forall a. [a] -> [a] -> [a]
++ String
"    Run the benchmark built with '-O2' (including local libs used)\n"

   , commandDefaultFlags :: NixStyleFlags ()
commandDefaultFlags = forall a. a -> NixStyleFlags a
defaultNixStyleFlags ()
   , commandOptions :: ShowOrParseArgs -> [OptionField (NixStyleFlags ())]
commandOptions      = forall a.
(ShowOrParseArgs -> [OptionField a])
-> ShowOrParseArgs -> [OptionField (NixStyleFlags a)]
nixStyleOptions (forall a b. a -> b -> a
const [])
   }


-- | The @build@ command does a lot. It brings the install plan up to date,
-- selects that part of the plan needed by the given or implicit targets and
-- then executes the plan.
--
-- For more details on how this works, see the module
-- "Distribution.Client.ProjectOrchestration"
--
benchAction :: NixStyleFlags () -> [String] -> GlobalFlags -> IO ()
benchAction :: NixStyleFlags () -> [String] -> GlobalFlags -> IO ()
benchAction flags :: NixStyleFlags ()
flags@NixStyleFlags {()
ConfigFlags
HaddockFlags
TestFlags
BenchmarkFlags
ProjectFlags
InstallFlags
ConfigExFlags
extraFlags :: forall a. NixStyleFlags a -> a
projectFlags :: forall a. NixStyleFlags a -> ProjectFlags
benchmarkFlags :: forall a. NixStyleFlags a -> BenchmarkFlags
testFlags :: forall a. NixStyleFlags a -> TestFlags
haddockFlags :: forall a. NixStyleFlags a -> HaddockFlags
installFlags :: forall a. NixStyleFlags a -> InstallFlags
configExFlags :: forall a. NixStyleFlags a -> ConfigExFlags
configFlags :: forall a. NixStyleFlags a -> ConfigFlags
extraFlags :: ()
projectFlags :: ProjectFlags
benchmarkFlags :: BenchmarkFlags
testFlags :: TestFlags
haddockFlags :: HaddockFlags
installFlags :: InstallFlags
configExFlags :: ConfigExFlags
configFlags :: ConfigFlags
..} [String]
targetStrings GlobalFlags
globalFlags = do

    ProjectBaseContext
baseCtx <- Verbosity
-> ProjectConfig -> CurrentCommand -> IO ProjectBaseContext
establishProjectBaseContext Verbosity
verbosity ProjectConfig
cliConfig CurrentCommand
OtherCommand

    [TargetSelector]
targetSelectors <- forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either (forall a. Verbosity -> [TargetSelectorProblem] -> IO a
reportTargetSelectorProblems Verbosity
verbosity) forall (m :: * -> *) a. Monad m => a -> m a
return
                   forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< forall a.
[PackageSpecifier (SourcePackage (PackageLocation a))]
-> Maybe ComponentKindFilter
-> [String]
-> IO (Either [TargetSelectorProblem] [TargetSelector])
readTargetSelectors (ProjectBaseContext -> [PackageSpecifier UnresolvedSourcePackage]
localPackages ProjectBaseContext
baseCtx) (forall a. a -> Maybe a
Just ComponentKindFilter
BenchKind) [String]
targetStrings

    ProjectBuildContext
buildCtx <-
      Verbosity
-> ProjectBaseContext
-> (ElaboratedInstallPlan
    -> IO (ElaboratedInstallPlan, TargetsMap))
-> IO ProjectBuildContext
runProjectPreBuildPhase Verbosity
verbosity ProjectBaseContext
baseCtx forall a b. (a -> b) -> a -> b
$ \ElaboratedInstallPlan
elaboratedPlan -> do

            forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (BuildTimeSettings -> Bool
buildSettingOnlyDeps (ProjectBaseContext -> BuildTimeSettings
buildSettings ProjectBaseContext
baseCtx)) forall a b. (a -> b) -> a -> b
$
              forall a. Verbosity -> String -> IO a
die' Verbosity
verbosity forall a b. (a -> b) -> a -> b
$
                  String
"The bench command does not support '--only-dependencies'. "
               forall a. [a] -> [a] -> [a]
++ String
"You may wish to use 'build --only-dependencies' and then "
               forall a. [a] -> [a] -> [a]
++ String
"use 'bench'."

            -- Interpret the targets on the command line as bench targets
            -- (as opposed to say build or haddock targets).
            TargetsMap
targets <- forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either (forall a. Verbosity -> [BenchTargetProblem] -> IO a
reportTargetProblems Verbosity
verbosity) forall (m :: * -> *) a. Monad m => a -> m a
return
                     forall a b. (a -> b) -> a -> b
$ forall err.
(forall k.
 TargetSelector
 -> [AvailableTarget k] -> Either (TargetProblem err) [k])
-> (forall k.
    SubComponentTarget
    -> AvailableTarget k -> Either (TargetProblem err) k)
-> ElaboratedInstallPlan
-> Maybe SourcePackageDb
-> [TargetSelector]
-> Either [TargetProblem err] TargetsMap
resolveTargets
                         forall k.
TargetSelector
-> [AvailableTarget k] -> Either BenchTargetProblem [k]
selectPackageTargets
                         forall k.
SubComponentTarget
-> AvailableTarget k -> Either BenchTargetProblem k
selectComponentTarget
                         ElaboratedInstallPlan
elaboratedPlan
                         forall a. Maybe a
Nothing
                         [TargetSelector]
targetSelectors

            let elaboratedPlan' :: ElaboratedInstallPlan
elaboratedPlan' = TargetAction
-> TargetsMap -> ElaboratedInstallPlan -> ElaboratedInstallPlan
pruneInstallPlanToTargets
                                    TargetAction
TargetActionBench
                                    TargetsMap
targets
                                    ElaboratedInstallPlan
elaboratedPlan
            forall (m :: * -> *) a. Monad m => a -> m a
return (ElaboratedInstallPlan
elaboratedPlan', TargetsMap
targets)

    Verbosity -> ProjectBaseContext -> ProjectBuildContext -> IO ()
printPlan Verbosity
verbosity ProjectBaseContext
baseCtx ProjectBuildContext
buildCtx

    BuildOutcomes
buildOutcomes <- Verbosity
-> ProjectBaseContext -> ProjectBuildContext -> IO BuildOutcomes
runProjectBuildPhase Verbosity
verbosity ProjectBaseContext
baseCtx ProjectBuildContext
buildCtx
    Verbosity
-> ProjectBaseContext
-> ProjectBuildContext
-> BuildOutcomes
-> IO ()
runProjectPostBuildPhase Verbosity
verbosity ProjectBaseContext
baseCtx ProjectBuildContext
buildCtx BuildOutcomes
buildOutcomes
  where
    verbosity :: Verbosity
verbosity = forall a. a -> Flag a -> a
fromFlagOrDefault Verbosity
normal (ConfigFlags -> Flag Verbosity
configVerbosity ConfigFlags
configFlags)
    cliConfig :: ProjectConfig
cliConfig = forall a.
GlobalFlags
-> NixStyleFlags a -> ClientInstallFlags -> ProjectConfig
commandLineFlagsToProjectConfig GlobalFlags
globalFlags NixStyleFlags ()
flags
                  forall a. Monoid a => a
mempty -- ClientInstallFlags, not needed here

-- | This defines what a 'TargetSelector' means for the @bench@ command.
-- It selects the 'AvailableTarget's that the 'TargetSelector' refers to,
-- or otherwise classifies the problem.
--
-- For the @bench@ command we select all buildable benchmarks,
-- or fail if there are no benchmarks or no buildable benchmarks.
--
selectPackageTargets :: TargetSelector
                     -> [AvailableTarget k] -> Either BenchTargetProblem [k]
selectPackageTargets :: forall k.
TargetSelector
-> [AvailableTarget k] -> Either BenchTargetProblem [k]
selectPackageTargets TargetSelector
targetSelector [AvailableTarget k]
targets

    -- If there are any buildable benchmark targets then we select those
  | Bool -> Bool
not (forall (t :: * -> *) a. Foldable t => t a -> Bool
null [k]
targetsBenchBuildable)
  = forall a b. b -> Either a b
Right [k]
targetsBenchBuildable

    -- If there are benchmarks but none are buildable then we report those
  | Bool -> Bool
not (forall (t :: * -> *) a. Foldable t => t a -> Bool
null [AvailableTarget ()]
targetsBench)
  = forall a b. a -> Either a b
Left (forall a. TargetSelector -> [AvailableTarget ()] -> TargetProblem a
TargetProblemNoneEnabled TargetSelector
targetSelector [AvailableTarget ()]
targetsBench)

    -- If there are no benchmarks but some other targets then we report that
  | Bool -> Bool
not (forall (t :: * -> *) a. Foldable t => t a -> Bool
null [AvailableTarget k]
targets)
  = forall a b. a -> Either a b
Left (TargetSelector -> BenchTargetProblem
noBenchmarksProblem TargetSelector
targetSelector)

    -- If there are no targets at all then we report that
  | Bool
otherwise
  = forall a b. a -> Either a b
Left (forall a. TargetSelector -> TargetProblem a
TargetProblemNoTargets TargetSelector
targetSelector)
  where
    targetsBenchBuildable :: [k]
targetsBenchBuildable = forall k. [AvailableTarget k] -> [k]
selectBuildableTargets
                          forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall k.
ComponentKindFilter -> [AvailableTarget k] -> [AvailableTarget k]
filterTargetsKind ComponentKindFilter
BenchKind
                          forall a b. (a -> b) -> a -> b
$ [AvailableTarget k]
targets

    targetsBench :: [AvailableTarget ()]
targetsBench          = forall k. [AvailableTarget k] -> [AvailableTarget ()]
forgetTargetsDetail
                          forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall k.
ComponentKindFilter -> [AvailableTarget k] -> [AvailableTarget k]
filterTargetsKind ComponentKindFilter
BenchKind
                          forall a b. (a -> b) -> a -> b
$ [AvailableTarget k]
targets


-- | For a 'TargetComponent' 'TargetSelector', check if the component can be
-- selected.
--
-- For the @bench@ command we just need to check it is a benchmark, in addition
-- to the basic checks on being buildable etc.
--
selectComponentTarget :: SubComponentTarget
                      -> AvailableTarget k -> Either BenchTargetProblem k
selectComponentTarget :: forall k.
SubComponentTarget
-> AvailableTarget k -> Either BenchTargetProblem k
selectComponentTarget subtarget :: SubComponentTarget
subtarget@SubComponentTarget
WholeComponent AvailableTarget k
t
  | CBenchName UnqualComponentName
_ <- forall k. AvailableTarget k -> ComponentName
availableTargetComponentName AvailableTarget k
t
  = forall k a.
SubComponentTarget
-> AvailableTarget k -> Either (TargetProblem a) k
selectComponentTargetBasic SubComponentTarget
subtarget AvailableTarget k
t
  | Bool
otherwise
  = forall a b. a -> Either a b
Left (PackageId -> ComponentName -> BenchTargetProblem
componentNotBenchmarkProblem
           (forall k. AvailableTarget k -> PackageId
availableTargetPackageId AvailableTarget k
t)
           (forall k. AvailableTarget k -> ComponentName
availableTargetComponentName AvailableTarget k
t))

selectComponentTarget SubComponentTarget
subtarget AvailableTarget k
t
  = forall a b. a -> Either a b
Left (PackageId
-> ComponentName -> SubComponentTarget -> BenchTargetProblem
isSubComponentProblem
           (forall k. AvailableTarget k -> PackageId
availableTargetPackageId AvailableTarget k
t)
           (forall k. AvailableTarget k -> ComponentName
availableTargetComponentName AvailableTarget k
t)
           SubComponentTarget
subtarget)

-- | The various error conditions that can occur when matching a
-- 'TargetSelector' against 'AvailableTarget's for the @bench@ command.
--
data BenchProblem =
     -- | The 'TargetSelector' matches targets but no benchmarks
     TargetProblemNoBenchmarks TargetSelector

     -- | The 'TargetSelector' refers to a component that is not a benchmark
   | TargetProblemComponentNotBenchmark PackageId ComponentName

     -- | Asking to benchmark an individual file or module is not supported
   | TargetProblemIsSubComponent   PackageId ComponentName SubComponentTarget
  deriving (BenchProblem -> BenchProblem -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: BenchProblem -> BenchProblem -> Bool
$c/= :: BenchProblem -> BenchProblem -> Bool
== :: BenchProblem -> BenchProblem -> Bool
$c== :: BenchProblem -> BenchProblem -> Bool
Eq, Int -> BenchProblem -> String -> String
[BenchProblem] -> String -> String
BenchProblem -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [BenchProblem] -> String -> String
$cshowList :: [BenchProblem] -> String -> String
show :: BenchProblem -> String
$cshow :: BenchProblem -> String
showsPrec :: Int -> BenchProblem -> String -> String
$cshowsPrec :: Int -> BenchProblem -> String -> String
Show)


type BenchTargetProblem = TargetProblem BenchProblem

noBenchmarksProblem :: TargetSelector -> TargetProblem BenchProblem
noBenchmarksProblem :: TargetSelector -> BenchTargetProblem
noBenchmarksProblem = forall a. a -> TargetProblem a
CustomTargetProblem forall b c a. (b -> c) -> (a -> b) -> a -> c
. TargetSelector -> BenchProblem
TargetProblemNoBenchmarks

componentNotBenchmarkProblem :: PackageId -> ComponentName -> TargetProblem BenchProblem
componentNotBenchmarkProblem :: PackageId -> ComponentName -> BenchTargetProblem
componentNotBenchmarkProblem PackageId
pkgid ComponentName
name = forall a. a -> TargetProblem a
CustomTargetProblem forall a b. (a -> b) -> a -> b
$
  PackageId -> ComponentName -> BenchProblem
TargetProblemComponentNotBenchmark PackageId
pkgid ComponentName
name

isSubComponentProblem
  :: PackageId
  -> ComponentName
  -> SubComponentTarget
  -> TargetProblem BenchProblem
isSubComponentProblem :: PackageId
-> ComponentName -> SubComponentTarget -> BenchTargetProblem
isSubComponentProblem PackageId
pkgid ComponentName
name SubComponentTarget
subcomponent = forall a. a -> TargetProblem a
CustomTargetProblem forall a b. (a -> b) -> a -> b
$
    PackageId -> ComponentName -> SubComponentTarget -> BenchProblem
TargetProblemIsSubComponent PackageId
pkgid ComponentName
name SubComponentTarget
subcomponent

reportTargetProblems :: Verbosity -> [BenchTargetProblem] -> IO a
reportTargetProblems :: forall a. Verbosity -> [BenchTargetProblem] -> IO a
reportTargetProblems Verbosity
verbosity =
    forall a. Verbosity -> String -> IO a
die' Verbosity
verbosity forall b c a. (b -> c) -> (a -> b) -> a -> c
. [String] -> String
unlines forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. (a -> b) -> [a] -> [b]
map BenchTargetProblem -> String
renderBenchTargetProblem

renderBenchTargetProblem :: BenchTargetProblem -> String
renderBenchTargetProblem :: BenchTargetProblem -> String
renderBenchTargetProblem (TargetProblemNoTargets TargetSelector
targetSelector) =
    case TargetSelector -> Maybe ComponentKindFilter
targetSelectorFilter TargetSelector
targetSelector of
      Just ComponentKindFilter
kind | ComponentKindFilter
kind forall a. Eq a => a -> a -> Bool
/= ComponentKindFilter
BenchKind
        -> String
"The bench command is for running benchmarks, but the target '"
           forall a. [a] -> [a] -> [a]
++ TargetSelector -> String
showTargetSelector TargetSelector
targetSelector forall a. [a] -> [a] -> [a]
++ String
"' refers to "
           forall a. [a] -> [a] -> [a]
++ TargetSelector -> String
renderTargetSelector TargetSelector
targetSelector forall a. [a] -> [a] -> [a]
++ String
"."

      Maybe ComponentKindFilter
_ -> String -> TargetSelector -> String
renderTargetProblemNoTargets String
"benchmark" TargetSelector
targetSelector
renderBenchTargetProblem BenchTargetProblem
problem =
    forall a. String -> (a -> String) -> TargetProblem a -> String
renderTargetProblem String
"benchmark" BenchProblem -> String
renderBenchProblem BenchTargetProblem
problem

renderBenchProblem :: BenchProblem -> String
renderBenchProblem :: BenchProblem -> String
renderBenchProblem (TargetProblemNoBenchmarks TargetSelector
targetSelector) =
    String
"Cannot run benchmarks for the target '" forall a. [a] -> [a] -> [a]
++ TargetSelector -> String
showTargetSelector TargetSelector
targetSelector
 forall a. [a] -> [a] -> [a]
++ String
"' which refers to " forall a. [a] -> [a] -> [a]
++ TargetSelector -> String
renderTargetSelector TargetSelector
targetSelector
 forall a. [a] -> [a] -> [a]
++ String
" because "
 forall a. [a] -> [a] -> [a]
++ forall a. Plural -> a -> a -> a
plural (TargetSelector -> Plural
targetSelectorPluralPkgs TargetSelector
targetSelector) String
"it does" String
"they do"
 forall a. [a] -> [a] -> [a]
++ String
" not contain any benchmarks."

renderBenchProblem (TargetProblemComponentNotBenchmark PackageId
pkgid ComponentName
cname) =
    String
"The bench command is for running benchmarks, but the target '"
 forall a. [a] -> [a] -> [a]
++ TargetSelector -> String
showTargetSelector TargetSelector
targetSelector forall a. [a] -> [a] -> [a]
++ String
"' refers to "
 forall a. [a] -> [a] -> [a]
++ TargetSelector -> String
renderTargetSelector TargetSelector
targetSelector forall a. [a] -> [a] -> [a]
++ String
" from the package "
 forall a. [a] -> [a] -> [a]
++ forall a. Pretty a => a -> String
prettyShow PackageId
pkgid forall a. [a] -> [a] -> [a]
++ String
"."
  where
    targetSelector :: TargetSelector
targetSelector = PackageId -> ComponentName -> SubComponentTarget -> TargetSelector
TargetComponent PackageId
pkgid ComponentName
cname SubComponentTarget
WholeComponent

renderBenchProblem (TargetProblemIsSubComponent PackageId
pkgid ComponentName
cname SubComponentTarget
subtarget) =
    String
"The bench command can only run benchmarks as a whole, "
 forall a. [a] -> [a] -> [a]
++ String
"not files or modules within them, but the target '"
 forall a. [a] -> [a] -> [a]
++ TargetSelector -> String
showTargetSelector TargetSelector
targetSelector forall a. [a] -> [a] -> [a]
++ String
"' refers to "
 forall a. [a] -> [a] -> [a]
++ TargetSelector -> String
renderTargetSelector TargetSelector
targetSelector forall a. [a] -> [a] -> [a]
++ String
"."
  where
    targetSelector :: TargetSelector
targetSelector = PackageId -> ComponentName -> SubComponentTarget -> TargetSelector
TargetComponent PackageId
pkgid ComponentName
cname SubComponentTarget
subtarget