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

-----------------------------------------------------------------------------
-- |
-- Module      :  Distribution.Simple.Setup
-- Copyright   :  Isaac Jones 2003-2004
--                Duncan Coutts 2007
-- License     :  BSD3
--
-- Maintainer  :  cabal-devel@haskell.org
-- Portability :  portable
--
-- This is a big module, but not very complicated. The code is very regular
-- and repetitive. It defines the command line interface for all the Cabal
-- commands. For each command (like @configure@, @build@ etc) it defines a type
-- that holds all the flags, the default set of flags and a 'CommandUI' that
-- maps command line flags to and from the corresponding flags type.
--
-- All the flags types are instances of 'Monoid', see
-- <http://www.haskell.org/pipermail/cabal-devel/2007-December/001509.html>
-- for an explanation.
--
-- The types defined here get used in the front end and especially in
-- @cabal-install@ which has to do quite a bit of manipulating sets of command
-- line flags.
--
-- This is actually relatively nice, it works quite well. The main change it
-- needs is to unify it with the code for managing sets of fields that can be
-- read and written from files. This would allow us to save configure flags in
-- config files.

module Distribution.Simple.Setup (

  GlobalFlags(..),   emptyGlobalFlags,   defaultGlobalFlags,   globalCommand,
  ConfigFlags(..),   emptyConfigFlags,   defaultConfigFlags,   configureCommand,
  configPrograms,
  configAbsolutePaths, readPackageDbList, showPackageDbList,
  CopyFlags(..),     emptyCopyFlags,     defaultCopyFlags,     copyCommand,
  InstallFlags(..),  emptyInstallFlags,  defaultInstallFlags,  installCommand,
  DoctestFlags(..),  emptyDoctestFlags,  defaultDoctestFlags,  doctestCommand,
  HaddockTarget(..),
  HaddockFlags(..),  emptyHaddockFlags,  defaultHaddockFlags,  haddockCommand,
  HscolourFlags(..), emptyHscolourFlags, defaultHscolourFlags, hscolourCommand,
  BuildFlags(..),    emptyBuildFlags,    defaultBuildFlags,    buildCommand,
  ShowBuildInfoFlags(..),                defaultShowBuildFlags, showBuildInfoCommand,
  ReplFlags(..),                         defaultReplFlags,     replCommand,
  CleanFlags(..),    emptyCleanFlags,    defaultCleanFlags,    cleanCommand,
  RegisterFlags(..), emptyRegisterFlags, defaultRegisterFlags, registerCommand,
                                                               unregisterCommand,
  SDistFlags(..),    emptySDistFlags,    defaultSDistFlags,    sdistCommand,
  TestFlags(..),     emptyTestFlags,     defaultTestFlags,     testCommand,
  TestShowDetails(..),
  BenchmarkFlags(..), emptyBenchmarkFlags,
  defaultBenchmarkFlags, benchmarkCommand,
  CopyDest(..),
  configureArgs, configureOptions, configureCCompiler, configureLinker,
  buildOptions, haddockOptions, installDirsOptions,
  testOptions', benchmarkOptions',
  programDbOptions, programDbPaths',
  programFlagsDescription,
  replOptions,
  splitArgs,

  defaultDistPref, optionDistPref,

  Flag(..),
  toFlag,
  fromFlag,
  fromFlagOrDefault,
  flagToMaybe,
  flagToList,
  maybeToFlag,
  BooleanFlag(..),
  boolOpt, boolOpt', trueArg, falseArg,
  optionVerbosity, optionNumJobs) where

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

import Distribution.Compiler
import Distribution.ReadE
import Distribution.Parsec
import Distribution.Pretty
import qualified Distribution.Compat.CharParsing as P
import qualified Text.PrettyPrint as Disp
import Distribution.ModuleName
import Distribution.PackageDescription hiding (Flag)
import Distribution.Simple.Command hiding (boolOpt, boolOpt')
import qualified Distribution.Simple.Command as Command
import Distribution.Simple.Compiler hiding (Flag)
import Distribution.Simple.Flag
import Distribution.Simple.Utils
import Distribution.Simple.Program
import Distribution.Simple.InstallDirs
import Distribution.Verbosity
import Distribution.Utils.NubList
import Distribution.Types.Dependency
import Distribution.Types.ComponentId
import Distribution.Types.GivenComponent
import Distribution.Types.Module
import Distribution.Types.PackageName
import Distribution.Types.UnqualComponentName (unUnqualComponentName)

import Distribution.Compat.Stack
import Distribution.Compat.Semigroup (Last' (..), Option' (..))

import Data.Function (on)

-- FIXME Not sure where this should live
defaultDistPref :: FilePath
defaultDistPref :: FilePath
defaultDistPref = FilePath
"dist"

-- ------------------------------------------------------------
-- * Global flags
-- ------------------------------------------------------------

-- In fact since individual flags types are monoids and these are just sets of
-- flags then they are also monoids pointwise. This turns out to be really
-- useful. The mempty is the set of empty flags and mappend allows us to
-- override specific flags. For example we can start with default flags and
-- override with the ones we get from a file or the command line, or both.

-- | Flags that apply at the top level, not to any sub-command.
data GlobalFlags = GlobalFlags {
    GlobalFlags -> Flag Bool
globalVersion        :: Flag Bool,
    GlobalFlags -> Flag Bool
globalNumericVersion :: Flag Bool
  } deriving ((forall x. GlobalFlags -> Rep GlobalFlags x)
-> (forall x. Rep GlobalFlags x -> GlobalFlags)
-> Generic GlobalFlags
forall x. Rep GlobalFlags x -> GlobalFlags
forall x. GlobalFlags -> Rep GlobalFlags x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GlobalFlags x -> GlobalFlags
$cfrom :: forall x. GlobalFlags -> Rep GlobalFlags x
Generic, Typeable)

defaultGlobalFlags :: GlobalFlags
defaultGlobalFlags :: GlobalFlags
defaultGlobalFlags  = GlobalFlags :: Flag Bool -> Flag Bool -> GlobalFlags
GlobalFlags {
    globalVersion :: Flag Bool
globalVersion        = Bool -> Flag Bool
forall a. a -> Flag a
Flag Bool
False,
    globalNumericVersion :: Flag Bool
globalNumericVersion = Bool -> Flag Bool
forall a. a -> Flag a
Flag Bool
False
  }

globalCommand :: [Command action] -> CommandUI GlobalFlags
globalCommand :: [Command action] -> CommandUI GlobalFlags
globalCommand [Command action]
commands = CommandUI :: forall flags.
FilePath
-> FilePath
-> (FilePath -> FilePath)
-> Maybe (FilePath -> FilePath)
-> Maybe (FilePath -> FilePath)
-> flags
-> (ShowOrParseArgs -> [OptionField flags])
-> CommandUI flags
CommandUI
  { commandName :: FilePath
commandName         = FilePath
""
  , commandSynopsis :: FilePath
commandSynopsis     = FilePath
""
  , commandUsage :: FilePath -> FilePath
commandUsage        = \FilePath
pname ->
         FilePath
"This Setup program uses the Haskell Cabal Infrastructure.\n"
      FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
"See http://www.haskell.org/cabal/ for more information.\n"
      FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
"\n"
      FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
"Usage: " FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
pname FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
" [GLOBAL FLAGS] [COMMAND [FLAGS]]\n"
  , commandDescription :: Maybe (FilePath -> FilePath)
commandDescription = (FilePath -> FilePath) -> Maybe (FilePath -> FilePath)
forall a. a -> Maybe a
Just ((FilePath -> FilePath) -> Maybe (FilePath -> FilePath))
-> (FilePath -> FilePath) -> Maybe (FilePath -> FilePath)
forall a b. (a -> b) -> a -> b
$ \FilePath
pname ->
      let
        commands' :: [Command action]
commands' = [Command action]
commands [Command action] -> [Command action] -> [Command action]
forall a. [a] -> [a] -> [a]
++ [CommandUI () -> (() -> [FilePath] -> action) -> Command action
forall flags action.
CommandUI flags
-> (flags -> [FilePath] -> action) -> Command action
commandAddAction CommandUI ()
helpCommandUI () -> [FilePath] -> action
forall a. HasCallStack => a
undefined]
        cmdDescs :: [(FilePath, FilePath)]
cmdDescs = [Command action] -> [(FilePath, FilePath)]
forall action. [Command action] -> [(FilePath, FilePath)]
getNormalCommandDescriptions [Command action]
commands'
        maxlen :: Int
maxlen    = [Int] -> Int
forall (t :: * -> *) a. (Foldable t, Ord a) => t a -> a
maximum ([Int] -> Int) -> [Int] -> Int
forall a b. (a -> b) -> a -> b
$ [FilePath -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length FilePath
name | (FilePath
name, FilePath
_) <- [(FilePath, FilePath)]
cmdDescs]
        align :: FilePath -> FilePath
align FilePath
str = FilePath
str FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ Int -> Char -> FilePath
forall a. Int -> a -> [a]
replicate (Int
maxlen Int -> Int -> Int
forall a. Num a => a -> a -> a
- FilePath -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length FilePath
str) Char
' '
      in
         FilePath
"Commands:\n"
      FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ [FilePath] -> FilePath
unlines [ FilePath
"  " FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath -> FilePath
align FilePath
name FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
"    " FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
descr
                 | (FilePath
name, FilePath
descr) <- [(FilePath, FilePath)]
cmdDescs ]
      FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
"\n"
      FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
"For more information about a command use\n"
      FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
"  " FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
pname FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
" COMMAND --help\n\n"
      FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
"Typical steps for installing Cabal packages:\n"
      FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ [FilePath] -> FilePath
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat [ FilePath
"  " FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
pname FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
" " FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
x FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
"\n"
                | FilePath
x <- [FilePath
"configure", FilePath
"build", FilePath
"install"]]
  , commandNotes :: Maybe (FilePath -> FilePath)
commandNotes        = Maybe (FilePath -> FilePath)
forall a. Maybe a
Nothing
  , commandDefaultFlags :: GlobalFlags
commandDefaultFlags = GlobalFlags
defaultGlobalFlags
  , commandOptions :: ShowOrParseArgs -> [OptionField GlobalFlags]
commandOptions      = \ShowOrParseArgs
_ ->
      [FilePath
-> [FilePath]
-> FilePath
-> (GlobalFlags -> Flag Bool)
-> (Flag Bool -> GlobalFlags -> GlobalFlags)
-> MkOptDescr
     (GlobalFlags -> Flag Bool)
     (Flag Bool -> GlobalFlags -> GlobalFlags)
     GlobalFlags
-> OptionField GlobalFlags
forall get set a.
FilePath
-> [FilePath]
-> FilePath
-> get
-> set
-> MkOptDescr get set a
-> OptionField a
option [Char
'V'] [FilePath
"version"]
         FilePath
"Print version information"
         GlobalFlags -> Flag Bool
globalVersion (\Flag Bool
v GlobalFlags
flags -> GlobalFlags
flags { globalVersion :: Flag Bool
globalVersion = Flag Bool
v })
         MkOptDescr
  (GlobalFlags -> Flag Bool)
  (Flag Bool -> GlobalFlags -> GlobalFlags)
  GlobalFlags
forall a. MkOptDescr (a -> Flag Bool) (Flag Bool -> a -> a) a
trueArg
      ,FilePath
-> [FilePath]
-> FilePath
-> (GlobalFlags -> Flag Bool)
-> (Flag Bool -> GlobalFlags -> GlobalFlags)
-> MkOptDescr
     (GlobalFlags -> Flag Bool)
     (Flag Bool -> GlobalFlags -> GlobalFlags)
     GlobalFlags
-> OptionField GlobalFlags
forall get set a.
FilePath
-> [FilePath]
-> FilePath
-> get
-> set
-> MkOptDescr get set a
-> OptionField a
option [] [FilePath
"numeric-version"]
         FilePath
"Print just the version number"
         GlobalFlags -> Flag Bool
globalNumericVersion (\Flag Bool
v GlobalFlags
flags -> GlobalFlags
flags { globalNumericVersion :: Flag Bool
globalNumericVersion = Flag Bool
v })
         MkOptDescr
  (GlobalFlags -> Flag Bool)
  (Flag Bool -> GlobalFlags -> GlobalFlags)
  GlobalFlags
forall a. MkOptDescr (a -> Flag Bool) (Flag Bool -> a -> a) a
trueArg
      ]
  }

emptyGlobalFlags :: GlobalFlags
emptyGlobalFlags :: GlobalFlags
emptyGlobalFlags = GlobalFlags
forall a. Monoid a => a
mempty

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

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

-- ------------------------------------------------------------
-- * Config flags
-- ------------------------------------------------------------

-- | Flags to @configure@ command.
--
-- IMPORTANT: every time a new flag is added, 'D.C.Setup.filterConfigureFlags'
-- should be updated.
-- IMPORTANT: every time a new flag is added, it should be added to the Eq instance
data ConfigFlags = ConfigFlags {
    -- This is the same hack as in 'buildArgs' and 'copyArgs'.
    -- TODO: Stop using this eventually when 'UserHooks' gets changed
    ConfigFlags -> [FilePath]
configArgs :: [String],

    --FIXME: the configPrograms is only here to pass info through to configure
    -- because the type of configure is constrained by the UserHooks.
    -- when we change UserHooks next we should pass the initial
    -- ProgramDb directly and not via ConfigFlags
    ConfigFlags -> Option' (Last' ProgramDb)
configPrograms_     :: Option' (Last' ProgramDb), -- ^All programs that
                                                      -- @cabal@ may run

    ConfigFlags -> [(FilePath, FilePath)]
configProgramPaths  :: [(String, FilePath)], -- ^user specified programs paths
    ConfigFlags -> [(FilePath, [FilePath])]
configProgramArgs   :: [(String, [String])], -- ^user specified programs args
    ConfigFlags -> NubList FilePath
configProgramPathExtra :: NubList FilePath,  -- ^Extend the $PATH
    ConfigFlags -> Flag CompilerFlavor
configHcFlavor      :: Flag CompilerFlavor, -- ^The \"flavor\" of the
                                                -- compiler, e.g. GHC.
    ConfigFlags -> Flag FilePath
configHcPath        :: Flag FilePath, -- ^given compiler location
    ConfigFlags -> Flag FilePath
configHcPkg         :: Flag FilePath, -- ^given hc-pkg location
    ConfigFlags -> Flag Bool
configVanillaLib    :: Flag Bool,     -- ^Enable vanilla library
    ConfigFlags -> Flag Bool
configProfLib       :: Flag Bool,     -- ^Enable profiling in the library
    ConfigFlags -> Flag Bool
configSharedLib     :: Flag Bool,     -- ^Build shared library
    ConfigFlags -> Flag Bool
configStaticLib     :: Flag Bool,     -- ^Build static library
    ConfigFlags -> Flag Bool
configDynExe        :: Flag Bool,     -- ^Enable dynamic linking of the
                                          -- executables.
    ConfigFlags -> Flag Bool
configFullyStaticExe :: Flag Bool,     -- ^Enable fully static linking of the
                                          -- executables.
    ConfigFlags -> Flag Bool
configProfExe       :: Flag Bool,     -- ^Enable profiling in the
                                          -- executables.
    ConfigFlags -> Flag Bool
configProf          :: Flag Bool,     -- ^Enable profiling in the library
                                          -- and executables.
    ConfigFlags -> Flag ProfDetailLevel
configProfDetail    :: Flag ProfDetailLevel, -- ^Profiling detail level
                                          --  in the library and executables.
    ConfigFlags -> Flag ProfDetailLevel
configProfLibDetail :: Flag ProfDetailLevel, -- ^Profiling  detail level
                                                 -- in the library
    ConfigFlags -> [FilePath]
configConfigureArgs :: [String],      -- ^Extra arguments to @configure@
    ConfigFlags -> Flag OptimisationLevel
configOptimization  :: Flag OptimisationLevel,  -- ^Enable optimization.
    ConfigFlags -> Flag PathTemplate
configProgPrefix    :: Flag PathTemplate, -- ^Installed executable prefix.
    ConfigFlags -> Flag PathTemplate
configProgSuffix    :: Flag PathTemplate, -- ^Installed executable suffix.
    ConfigFlags -> InstallDirs (Flag PathTemplate)
configInstallDirs   :: InstallDirs (Flag PathTemplate), -- ^Installation
                                                            -- paths
    ConfigFlags -> Flag FilePath
configScratchDir    :: Flag FilePath,
    ConfigFlags -> [FilePath]
configExtraLibDirs  :: [FilePath],   -- ^ path to search for extra libraries
    ConfigFlags -> [FilePath]
configExtraFrameworkDirs :: [FilePath],   -- ^ path to search for extra
                                              -- frameworks (OS X only)
    ConfigFlags -> [FilePath]
configExtraIncludeDirs :: [FilePath],   -- ^ path to search for header files
    ConfigFlags -> Flag FilePath
configIPID          :: Flag String, -- ^ explicit IPID to be used
    ConfigFlags -> Flag ComponentId
configCID           :: Flag ComponentId, -- ^ explicit CID to be used
    ConfigFlags -> Flag Bool
configDeterministic :: Flag Bool, -- ^ be as deterministic as possible
                                      -- (e.g., invariant over GHC, database,
                                      -- etc).  Used by the test suite

    ConfigFlags -> Flag FilePath
configDistPref :: Flag FilePath, -- ^"dist" prefix
    ConfigFlags -> Flag FilePath
configCabalFilePath :: Flag FilePath, -- ^ Cabal file to use
    ConfigFlags -> Flag Verbosity
configVerbosity :: Flag Verbosity, -- ^verbosity level
    ConfigFlags -> Flag Bool
configUserInstall :: Flag Bool,    -- ^The --user\/--global flag
    ConfigFlags -> [Maybe PackageDB]
configPackageDBs :: [Maybe PackageDB], -- ^Which package DBs to use
    ConfigFlags -> Flag Bool
configGHCiLib   :: Flag Bool,      -- ^Enable compiling library for GHCi
    ConfigFlags -> Flag Bool
configSplitSections :: Flag Bool,      -- ^Enable -split-sections with GHC
    ConfigFlags -> Flag Bool
configSplitObjs :: Flag Bool,      -- ^Enable -split-objs with GHC
    ConfigFlags -> Flag Bool
configStripExes :: Flag Bool,      -- ^Enable executable stripping
    ConfigFlags -> Flag Bool
configStripLibs :: Flag Bool,      -- ^Enable library stripping
    ConfigFlags -> [Dependency]
configConstraints :: [Dependency], -- ^Additional constraints for
                                       -- dependencies.
    ConfigFlags -> [GivenComponent]
configDependencies :: [GivenComponent],
      -- ^The packages depended on.
    ConfigFlags -> [(ModuleName, Module)]
configInstantiateWith :: [(ModuleName, Module)],
      -- ^ The requested Backpack instantiation.  If empty, either this
      -- package does not use Backpack, or we just want to typecheck
      -- the indefinite package.
    ConfigFlags -> FlagAssignment
configConfigurationsFlags :: FlagAssignment,
    ConfigFlags -> Flag Bool
configTests               :: Flag Bool, -- ^Enable test suite compilation
    ConfigFlags -> Flag Bool
configBenchmarks          :: Flag Bool, -- ^Enable benchmark compilation
    ConfigFlags -> Flag Bool
configCoverage :: Flag Bool, -- ^Enable program coverage
    ConfigFlags -> Flag Bool
configLibCoverage :: Flag Bool, -- ^Enable program coverage (deprecated)
    ConfigFlags -> Flag Bool
configExactConfiguration  :: Flag Bool,
      -- ^All direct dependencies and flags are provided on the command line by
      -- the user via the '--dependency' and '--flags' options.
    ConfigFlags -> Flag FilePath
configFlagError :: Flag String,
      -- ^Halt and show an error message indicating an error in flag assignment
    ConfigFlags -> Flag Bool
configRelocatable :: Flag Bool, -- ^ Enable relocatable package built
    ConfigFlags -> Flag DebugInfoLevel
configDebugInfo :: Flag DebugInfoLevel,  -- ^ Emit debug info.
    ConfigFlags -> Flag Bool
configUseResponseFiles :: Flag Bool,
      -- ^ Whether to use response files at all. They're used for such tools
      -- as haddock, or or ld.
    ConfigFlags -> Flag Bool
configAllowDependingOnPrivateLibs :: Flag Bool
      -- ^ Allow depending on private sublibraries. This is used by external
      -- tools (like cabal-install) so they can add multiple-public-libraries
      -- compatibility to older ghcs by checking visibility externally.
  }
  deriving ((forall x. ConfigFlags -> Rep ConfigFlags x)
-> (forall x. Rep ConfigFlags x -> ConfigFlags)
-> Generic ConfigFlags
forall x. Rep ConfigFlags x -> ConfigFlags
forall x. ConfigFlags -> Rep ConfigFlags x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ConfigFlags x -> ConfigFlags
$cfrom :: forall x. ConfigFlags -> Rep ConfigFlags x
Generic, ReadPrec [ConfigFlags]
ReadPrec ConfigFlags
Int -> ReadS ConfigFlags
ReadS [ConfigFlags]
(Int -> ReadS ConfigFlags)
-> ReadS [ConfigFlags]
-> ReadPrec ConfigFlags
-> ReadPrec [ConfigFlags]
-> Read ConfigFlags
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ConfigFlags]
$creadListPrec :: ReadPrec [ConfigFlags]
readPrec :: ReadPrec ConfigFlags
$creadPrec :: ReadPrec ConfigFlags
readList :: ReadS [ConfigFlags]
$creadList :: ReadS [ConfigFlags]
readsPrec :: Int -> ReadS ConfigFlags
$creadsPrec :: Int -> ReadS ConfigFlags
Read, Int -> ConfigFlags -> FilePath -> FilePath
[ConfigFlags] -> FilePath -> FilePath
ConfigFlags -> FilePath
(Int -> ConfigFlags -> FilePath -> FilePath)
-> (ConfigFlags -> FilePath)
-> ([ConfigFlags] -> FilePath -> FilePath)
-> Show ConfigFlags
forall a.
(Int -> a -> FilePath -> FilePath)
-> (a -> FilePath) -> ([a] -> FilePath -> FilePath) -> Show a
showList :: [ConfigFlags] -> FilePath -> FilePath
$cshowList :: [ConfigFlags] -> FilePath -> FilePath
show :: ConfigFlags -> FilePath
$cshow :: ConfigFlags -> FilePath
showsPrec :: Int -> ConfigFlags -> FilePath -> FilePath
$cshowsPrec :: Int -> ConfigFlags -> FilePath -> FilePath
Show, Typeable)

instance Binary ConfigFlags
instance Structured ConfigFlags

-- | More convenient version of 'configPrograms'. Results in an
-- 'error' if internal invariant is violated.
configPrograms :: WithCallStack (ConfigFlags -> ProgramDb)
configPrograms :: ConfigFlags -> ProgramDb
configPrograms = ProgramDb -> Maybe ProgramDb -> ProgramDb
forall a. a -> Maybe a -> a
fromMaybe (FilePath -> ProgramDb
forall a. HasCallStack => FilePath -> a
error FilePath
"FIXME: remove configPrograms") (Maybe ProgramDb -> ProgramDb)
-> (ConfigFlags -> Maybe ProgramDb) -> ConfigFlags -> ProgramDb
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Last' ProgramDb -> ProgramDb)
-> Maybe (Last' ProgramDb) -> Maybe ProgramDb
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Last' ProgramDb -> ProgramDb
forall a. Last' a -> a
getLast'
               (Maybe (Last' ProgramDb) -> Maybe ProgramDb)
-> (ConfigFlags -> Maybe (Last' ProgramDb))
-> ConfigFlags
-> Maybe ProgramDb
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Option' (Last' ProgramDb) -> Maybe (Last' ProgramDb)
forall a. Option' a -> Maybe a
getOption' (Option' (Last' ProgramDb) -> Maybe (Last' ProgramDb))
-> (ConfigFlags -> Option' (Last' ProgramDb))
-> ConfigFlags
-> Maybe (Last' ProgramDb)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ConfigFlags -> Option' (Last' ProgramDb)
configPrograms_

instance Eq ConfigFlags where
  == :: ConfigFlags -> ConfigFlags -> Bool
(==) ConfigFlags
a ConfigFlags
b =
    -- configPrograms skipped: not user specified, has no Eq instance
    (ConfigFlags -> [(FilePath, FilePath)]) -> Bool
forall a. Eq a => (ConfigFlags -> a) -> Bool
equal ConfigFlags -> [(FilePath, FilePath)]
configProgramPaths
    Bool -> Bool -> Bool
&& (ConfigFlags -> [(FilePath, [FilePath])]) -> Bool
forall a. Eq a => (ConfigFlags -> a) -> Bool
equal ConfigFlags -> [(FilePath, [FilePath])]
configProgramArgs
    Bool -> Bool -> Bool
&& (ConfigFlags -> NubList FilePath) -> Bool
forall a. Eq a => (ConfigFlags -> a) -> Bool
equal ConfigFlags -> NubList FilePath
configProgramPathExtra
    Bool -> Bool -> Bool
&& (ConfigFlags -> Flag CompilerFlavor) -> Bool
forall a. Eq a => (ConfigFlags -> a) -> Bool
equal ConfigFlags -> Flag CompilerFlavor
configHcFlavor
    Bool -> Bool -> Bool
&& (ConfigFlags -> Flag FilePath) -> Bool
forall a. Eq a => (ConfigFlags -> a) -> Bool
equal ConfigFlags -> Flag FilePath
configHcPath
    Bool -> Bool -> Bool
&& (ConfigFlags -> Flag FilePath) -> Bool
forall a. Eq a => (ConfigFlags -> a) -> Bool
equal ConfigFlags -> Flag FilePath
configHcPkg
    Bool -> Bool -> Bool
&& (ConfigFlags -> Flag Bool) -> Bool
forall a. Eq a => (ConfigFlags -> a) -> Bool
equal ConfigFlags -> Flag Bool
configVanillaLib
    Bool -> Bool -> Bool
&& (ConfigFlags -> Flag Bool) -> Bool
forall a. Eq a => (ConfigFlags -> a) -> Bool
equal ConfigFlags -> Flag Bool
configProfLib
    Bool -> Bool -> Bool
&& (ConfigFlags -> Flag Bool) -> Bool
forall a. Eq a => (ConfigFlags -> a) -> Bool
equal ConfigFlags -> Flag Bool
configSharedLib
    Bool -> Bool -> Bool
&& (ConfigFlags -> Flag Bool) -> Bool
forall a. Eq a => (ConfigFlags -> a) -> Bool
equal ConfigFlags -> Flag Bool
configStaticLib
    Bool -> Bool -> Bool
&& (ConfigFlags -> Flag Bool) -> Bool
forall a. Eq a => (ConfigFlags -> a) -> Bool
equal ConfigFlags -> Flag Bool
configDynExe
    Bool -> Bool -> Bool
&& (ConfigFlags -> Flag Bool) -> Bool
forall a. Eq a => (ConfigFlags -> a) -> Bool
equal ConfigFlags -> Flag Bool
configFullyStaticExe
    Bool -> Bool -> Bool
&& (ConfigFlags -> Flag Bool) -> Bool
forall a. Eq a => (ConfigFlags -> a) -> Bool
equal ConfigFlags -> Flag Bool
configProfExe
    Bool -> Bool -> Bool
&& (ConfigFlags -> Flag Bool) -> Bool
forall a. Eq a => (ConfigFlags -> a) -> Bool
equal ConfigFlags -> Flag Bool
configProf
    Bool -> Bool -> Bool
&& (ConfigFlags -> Flag ProfDetailLevel) -> Bool
forall a. Eq a => (ConfigFlags -> a) -> Bool
equal ConfigFlags -> Flag ProfDetailLevel
configProfDetail
    Bool -> Bool -> Bool
&& (ConfigFlags -> Flag ProfDetailLevel) -> Bool
forall a. Eq a => (ConfigFlags -> a) -> Bool
equal ConfigFlags -> Flag ProfDetailLevel
configProfLibDetail
    Bool -> Bool -> Bool
&& (ConfigFlags -> [FilePath]) -> Bool
forall a. Eq a => (ConfigFlags -> a) -> Bool
equal ConfigFlags -> [FilePath]
configConfigureArgs
    Bool -> Bool -> Bool
&& (ConfigFlags -> Flag OptimisationLevel) -> Bool
forall a. Eq a => (ConfigFlags -> a) -> Bool
equal ConfigFlags -> Flag OptimisationLevel
configOptimization
    Bool -> Bool -> Bool
&& (ConfigFlags -> Flag PathTemplate) -> Bool
forall a. Eq a => (ConfigFlags -> a) -> Bool
equal ConfigFlags -> Flag PathTemplate
configProgPrefix
    Bool -> Bool -> Bool
&& (ConfigFlags -> Flag PathTemplate) -> Bool
forall a. Eq a => (ConfigFlags -> a) -> Bool
equal ConfigFlags -> Flag PathTemplate
configProgSuffix
    Bool -> Bool -> Bool
&& (ConfigFlags -> InstallDirs (Flag PathTemplate)) -> Bool
forall a. Eq a => (ConfigFlags -> a) -> Bool
equal ConfigFlags -> InstallDirs (Flag PathTemplate)
configInstallDirs
    Bool -> Bool -> Bool
&& (ConfigFlags -> Flag FilePath) -> Bool
forall a. Eq a => (ConfigFlags -> a) -> Bool
equal ConfigFlags -> Flag FilePath
configScratchDir
    Bool -> Bool -> Bool
&& (ConfigFlags -> [FilePath]) -> Bool
forall a. Eq a => (ConfigFlags -> a) -> Bool
equal ConfigFlags -> [FilePath]
configExtraLibDirs
    Bool -> Bool -> Bool
&& (ConfigFlags -> [FilePath]) -> Bool
forall a. Eq a => (ConfigFlags -> a) -> Bool
equal ConfigFlags -> [FilePath]
configExtraIncludeDirs
    Bool -> Bool -> Bool
&& (ConfigFlags -> Flag FilePath) -> Bool
forall a. Eq a => (ConfigFlags -> a) -> Bool
equal ConfigFlags -> Flag FilePath
configIPID
    Bool -> Bool -> Bool
&& (ConfigFlags -> Flag Bool) -> Bool
forall a. Eq a => (ConfigFlags -> a) -> Bool
equal ConfigFlags -> Flag Bool
configDeterministic
    Bool -> Bool -> Bool
&& (ConfigFlags -> Flag FilePath) -> Bool
forall a. Eq a => (ConfigFlags -> a) -> Bool
equal ConfigFlags -> Flag FilePath
configDistPref
    Bool -> Bool -> Bool
&& (ConfigFlags -> Flag Verbosity) -> Bool
forall a. Eq a => (ConfigFlags -> a) -> Bool
equal ConfigFlags -> Flag Verbosity
configVerbosity
    Bool -> Bool -> Bool
&& (ConfigFlags -> Flag Bool) -> Bool
forall a. Eq a => (ConfigFlags -> a) -> Bool
equal ConfigFlags -> Flag Bool
configUserInstall
    Bool -> Bool -> Bool
&& (ConfigFlags -> [Maybe PackageDB]) -> Bool
forall a. Eq a => (ConfigFlags -> a) -> Bool
equal ConfigFlags -> [Maybe PackageDB]
configPackageDBs
    Bool -> Bool -> Bool
&& (ConfigFlags -> Flag Bool) -> Bool
forall a. Eq a => (ConfigFlags -> a) -> Bool
equal ConfigFlags -> Flag Bool
configGHCiLib
    Bool -> Bool -> Bool
&& (ConfigFlags -> Flag Bool) -> Bool
forall a. Eq a => (ConfigFlags -> a) -> Bool
equal ConfigFlags -> Flag Bool
configSplitSections
    Bool -> Bool -> Bool
&& (ConfigFlags -> Flag Bool) -> Bool
forall a. Eq a => (ConfigFlags -> a) -> Bool
equal ConfigFlags -> Flag Bool
configSplitObjs
    Bool -> Bool -> Bool
&& (ConfigFlags -> Flag Bool) -> Bool
forall a. Eq a => (ConfigFlags -> a) -> Bool
equal ConfigFlags -> Flag Bool
configStripExes
    Bool -> Bool -> Bool
&& (ConfigFlags -> Flag Bool) -> Bool
forall a. Eq a => (ConfigFlags -> a) -> Bool
equal ConfigFlags -> Flag Bool
configStripLibs
    Bool -> Bool -> Bool
&& (ConfigFlags -> [Dependency]) -> Bool
forall a. Eq a => (ConfigFlags -> a) -> Bool
equal ConfigFlags -> [Dependency]
configConstraints
    Bool -> Bool -> Bool
&& (ConfigFlags -> [GivenComponent]) -> Bool
forall a. Eq a => (ConfigFlags -> a) -> Bool
equal ConfigFlags -> [GivenComponent]
configDependencies
    Bool -> Bool -> Bool
&& (ConfigFlags -> FlagAssignment) -> Bool
forall a. Eq a => (ConfigFlags -> a) -> Bool
equal ConfigFlags -> FlagAssignment
configConfigurationsFlags
    Bool -> Bool -> Bool
&& (ConfigFlags -> Flag Bool) -> Bool
forall a. Eq a => (ConfigFlags -> a) -> Bool
equal ConfigFlags -> Flag Bool
configTests
    Bool -> Bool -> Bool
&& (ConfigFlags -> Flag Bool) -> Bool
forall a. Eq a => (ConfigFlags -> a) -> Bool
equal ConfigFlags -> Flag Bool
configBenchmarks
    Bool -> Bool -> Bool
&& (ConfigFlags -> Flag Bool) -> Bool
forall a. Eq a => (ConfigFlags -> a) -> Bool
equal ConfigFlags -> Flag Bool
configCoverage
    Bool -> Bool -> Bool
&& (ConfigFlags -> Flag Bool) -> Bool
forall a. Eq a => (ConfigFlags -> a) -> Bool
equal ConfigFlags -> Flag Bool
configLibCoverage
    Bool -> Bool -> Bool
&& (ConfigFlags -> Flag Bool) -> Bool
forall a. Eq a => (ConfigFlags -> a) -> Bool
equal ConfigFlags -> Flag Bool
configExactConfiguration
    Bool -> Bool -> Bool
&& (ConfigFlags -> Flag FilePath) -> Bool
forall a. Eq a => (ConfigFlags -> a) -> Bool
equal ConfigFlags -> Flag FilePath
configFlagError
    Bool -> Bool -> Bool
&& (ConfigFlags -> Flag Bool) -> Bool
forall a. Eq a => (ConfigFlags -> a) -> Bool
equal ConfigFlags -> Flag Bool
configRelocatable
    Bool -> Bool -> Bool
&& (ConfigFlags -> Flag DebugInfoLevel) -> Bool
forall a. Eq a => (ConfigFlags -> a) -> Bool
equal ConfigFlags -> Flag DebugInfoLevel
configDebugInfo
    Bool -> Bool -> Bool
&& (ConfigFlags -> Flag Bool) -> Bool
forall a. Eq a => (ConfigFlags -> a) -> Bool
equal ConfigFlags -> Flag Bool
configUseResponseFiles
    where
      equal :: (ConfigFlags -> a) -> Bool
equal ConfigFlags -> a
f = (a -> a -> Bool)
-> (ConfigFlags -> a) -> ConfigFlags -> ConfigFlags -> Bool
forall b c a. (b -> b -> c) -> (a -> b) -> a -> a -> c
on a -> a -> Bool
forall a. Eq a => a -> a -> Bool
(==) ConfigFlags -> a
f ConfigFlags
a ConfigFlags
b

configAbsolutePaths :: ConfigFlags -> NoCallStackIO ConfigFlags
configAbsolutePaths :: ConfigFlags -> NoCallStackIO ConfigFlags
configAbsolutePaths ConfigFlags
f =
  (\[Maybe PackageDB]
v -> ConfigFlags
f { configPackageDBs :: [Maybe PackageDB]
configPackageDBs = [Maybe PackageDB]
v })
  ([Maybe PackageDB] -> ConfigFlags)
-> IO [Maybe PackageDB] -> NoCallStackIO ConfigFlags
forall (m :: * -> *) a1 r. Monad m => (a1 -> r) -> m a1 -> m r
`liftM` (Maybe PackageDB -> IO (Maybe PackageDB))
-> [Maybe PackageDB] -> IO [Maybe PackageDB]
forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
traverse (IO (Maybe PackageDB)
-> (PackageDB -> IO (Maybe PackageDB))
-> Maybe PackageDB
-> IO (Maybe PackageDB)
forall b a. b -> (a -> b) -> Maybe a -> b
maybe (Maybe PackageDB -> IO (Maybe PackageDB)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe PackageDB
forall a. Maybe a
Nothing) ((PackageDB -> Maybe PackageDB)
-> IO PackageDB -> IO (Maybe PackageDB)
forall (m :: * -> *) a1 r. Monad m => (a1 -> r) -> m a1 -> m r
liftM PackageDB -> Maybe PackageDB
forall a. a -> Maybe a
Just (IO PackageDB -> IO (Maybe PackageDB))
-> (PackageDB -> IO PackageDB) -> PackageDB -> IO (Maybe PackageDB)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. PackageDB -> IO PackageDB
absolutePackageDBPath))
  (ConfigFlags -> [Maybe PackageDB]
configPackageDBs ConfigFlags
f)

defaultConfigFlags :: ProgramDb -> ConfigFlags
defaultConfigFlags :: ProgramDb -> ConfigFlags
defaultConfigFlags ProgramDb
progDb = ConfigFlags
emptyConfigFlags {
    configArgs :: [FilePath]
configArgs         = [],
    configPrograms_ :: Option' (Last' ProgramDb)
configPrograms_    = Maybe (Last' ProgramDb) -> Option' (Last' ProgramDb)
forall a. Maybe a -> Option' a
Option' (Last' ProgramDb -> Maybe (Last' ProgramDb)
forall a. a -> Maybe a
Just (ProgramDb -> Last' ProgramDb
forall a. a -> Last' a
Last' ProgramDb
progDb)),
    configHcFlavor :: Flag CompilerFlavor
configHcFlavor     = Flag CompilerFlavor
-> (CompilerFlavor -> Flag CompilerFlavor)
-> Maybe CompilerFlavor
-> Flag CompilerFlavor
forall b a. b -> (a -> b) -> Maybe a -> b
maybe Flag CompilerFlavor
forall a. Flag a
NoFlag CompilerFlavor -> Flag CompilerFlavor
forall a. a -> Flag a
Flag Maybe CompilerFlavor
defaultCompilerFlavor,
    configVanillaLib :: Flag Bool
configVanillaLib   = Bool -> Flag Bool
forall a. a -> Flag a
Flag Bool
True,
    configProfLib :: Flag Bool
configProfLib      = Flag Bool
forall a. Flag a
NoFlag,
    configSharedLib :: Flag Bool
configSharedLib    = Flag Bool
forall a. Flag a
NoFlag,
    configStaticLib :: Flag Bool
configStaticLib    = Flag Bool
forall a. Flag a
NoFlag,
    configDynExe :: Flag Bool
configDynExe       = Bool -> Flag Bool
forall a. a -> Flag a
Flag Bool
False,
    configFullyStaticExe :: Flag Bool
configFullyStaticExe = Bool -> Flag Bool
forall a. a -> Flag a
Flag Bool
False,
    configProfExe :: Flag Bool
configProfExe      = Flag Bool
forall a. Flag a
NoFlag,
    configProf :: Flag Bool
configProf         = Flag Bool
forall a. Flag a
NoFlag,
    configProfDetail :: Flag ProfDetailLevel
configProfDetail   = Flag ProfDetailLevel
forall a. Flag a
NoFlag,
    configProfLibDetail :: Flag ProfDetailLevel
configProfLibDetail= Flag ProfDetailLevel
forall a. Flag a
NoFlag,
    configOptimization :: Flag OptimisationLevel
configOptimization = OptimisationLevel -> Flag OptimisationLevel
forall a. a -> Flag a
Flag OptimisationLevel
NormalOptimisation,
    configProgPrefix :: Flag PathTemplate
configProgPrefix   = PathTemplate -> Flag PathTemplate
forall a. a -> Flag a
Flag (FilePath -> PathTemplate
toPathTemplate FilePath
""),
    configProgSuffix :: Flag PathTemplate
configProgSuffix   = PathTemplate -> Flag PathTemplate
forall a. a -> Flag a
Flag (FilePath -> PathTemplate
toPathTemplate FilePath
""),
    configDistPref :: Flag FilePath
configDistPref     = Flag FilePath
forall a. Flag a
NoFlag,
    configCabalFilePath :: Flag FilePath
configCabalFilePath = Flag FilePath
forall a. Flag a
NoFlag,
    configVerbosity :: Flag Verbosity
configVerbosity    = Verbosity -> Flag Verbosity
forall a. a -> Flag a
Flag Verbosity
normal,
    configUserInstall :: Flag Bool
configUserInstall  = Bool -> Flag Bool
forall a. a -> Flag a
Flag Bool
False,           --TODO: reverse this
#if defined(mingw32_HOST_OS)
    -- See #1589.
    configGHCiLib      = Flag True,
#else
    configGHCiLib :: Flag Bool
configGHCiLib      = Flag Bool
forall a. Flag a
NoFlag,
#endif
    configSplitSections :: Flag Bool
configSplitSections = Bool -> Flag Bool
forall a. a -> Flag a
Flag Bool
False,
    configSplitObjs :: Flag Bool
configSplitObjs    = Bool -> Flag Bool
forall a. a -> Flag a
Flag Bool
False, -- takes longer, so turn off by default
    configStripExes :: Flag Bool
configStripExes    = Flag Bool
forall a. Flag a
NoFlag,
    configStripLibs :: Flag Bool
configStripLibs    = Flag Bool
forall a. Flag a
NoFlag,
    configTests :: Flag Bool
configTests        = Bool -> Flag Bool
forall a. a -> Flag a
Flag Bool
False,
    configBenchmarks :: Flag Bool
configBenchmarks   = Bool -> Flag Bool
forall a. a -> Flag a
Flag Bool
False,
    configCoverage :: Flag Bool
configCoverage     = Bool -> Flag Bool
forall a. a -> Flag a
Flag Bool
False,
    configLibCoverage :: Flag Bool
configLibCoverage  = Flag Bool
forall a. Flag a
NoFlag,
    configExactConfiguration :: Flag Bool
configExactConfiguration = Bool -> Flag Bool
forall a. a -> Flag a
Flag Bool
False,
    configFlagError :: Flag FilePath
configFlagError    = Flag FilePath
forall a. Flag a
NoFlag,
    configRelocatable :: Flag Bool
configRelocatable  = Bool -> Flag Bool
forall a. a -> Flag a
Flag Bool
False,
    configDebugInfo :: Flag DebugInfoLevel
configDebugInfo    = DebugInfoLevel -> Flag DebugInfoLevel
forall a. a -> Flag a
Flag DebugInfoLevel
NoDebugInfo,
    configUseResponseFiles :: Flag Bool
configUseResponseFiles = Flag Bool
forall a. Flag a
NoFlag
  }

configureCommand :: ProgramDb -> CommandUI ConfigFlags
configureCommand :: ProgramDb -> CommandUI ConfigFlags
configureCommand ProgramDb
progDb = CommandUI :: forall flags.
FilePath
-> FilePath
-> (FilePath -> FilePath)
-> Maybe (FilePath -> FilePath)
-> Maybe (FilePath -> FilePath)
-> flags
-> (ShowOrParseArgs -> [OptionField flags])
-> CommandUI flags
CommandUI
  { commandName :: FilePath
commandName         = FilePath
"configure"
  , commandSynopsis :: FilePath
commandSynopsis     = FilePath
"Prepare to build the package."
  , commandDescription :: Maybe (FilePath -> FilePath)
commandDescription  = (FilePath -> FilePath) -> Maybe (FilePath -> FilePath)
forall a. a -> Maybe a
Just ((FilePath -> FilePath) -> Maybe (FilePath -> FilePath))
-> (FilePath -> FilePath) -> Maybe (FilePath -> FilePath)
forall a b. (a -> b) -> a -> b
$ \FilePath
_ -> FilePath -> FilePath
wrapText (FilePath -> FilePath) -> FilePath -> FilePath
forall a b. (a -> b) -> a -> b
$
         FilePath
"Configure how the package is built by setting "
      FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
"package (and other) flags.\n"
      FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
"\n"
      FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
"The configuration affects several other commands, "
      FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
"including build, test, bench, run, repl.\n"
  , commandNotes :: Maybe (FilePath -> FilePath)
commandNotes        = (FilePath -> FilePath) -> Maybe (FilePath -> FilePath)
forall a. a -> Maybe a
Just ((FilePath -> FilePath) -> Maybe (FilePath -> FilePath))
-> (FilePath -> FilePath) -> Maybe (FilePath -> FilePath)
forall a b. (a -> b) -> a -> b
$ \FilePath
_pname -> ProgramDb -> FilePath
programFlagsDescription ProgramDb
progDb
  , commandUsage :: FilePath -> FilePath
commandUsage        = \FilePath
pname ->
      FilePath
"Usage: " FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
pname FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
" configure [FLAGS]\n"
  , commandDefaultFlags :: ConfigFlags
commandDefaultFlags = ProgramDb -> ConfigFlags
defaultConfigFlags ProgramDb
progDb
  , commandOptions :: ShowOrParseArgs -> [OptionField ConfigFlags]
commandOptions      = \ShowOrParseArgs
showOrParseArgs ->
         ShowOrParseArgs -> [OptionField ConfigFlags]
configureOptions ShowOrParseArgs
showOrParseArgs
      [OptionField ConfigFlags]
-> [OptionField ConfigFlags] -> [OptionField ConfigFlags]
forall a. [a] -> [a] -> [a]
++ ProgramDb
-> ShowOrParseArgs
-> (ConfigFlags -> [(FilePath, FilePath)])
-> ([(FilePath, FilePath)] -> ConfigFlags -> ConfigFlags)
-> [OptionField ConfigFlags]
forall flags.
ProgramDb
-> ShowOrParseArgs
-> (flags -> [(FilePath, FilePath)])
-> ([(FilePath, FilePath)] -> flags -> flags)
-> [OptionField flags]
programDbPaths   ProgramDb
progDb ShowOrParseArgs
showOrParseArgs
           ConfigFlags -> [(FilePath, FilePath)]
configProgramPaths (\[(FilePath, FilePath)]
v ConfigFlags
fs -> ConfigFlags
fs { configProgramPaths :: [(FilePath, FilePath)]
configProgramPaths = [(FilePath, FilePath)]
v })
      [OptionField ConfigFlags]
-> [OptionField ConfigFlags] -> [OptionField ConfigFlags]
forall a. [a] -> [a] -> [a]
++ ProgramDb
-> ShowOrParseArgs
-> (ConfigFlags -> [(FilePath, [FilePath])])
-> ([(FilePath, [FilePath])] -> ConfigFlags -> ConfigFlags)
-> [OptionField ConfigFlags]
forall flags.
ProgramDb
-> ShowOrParseArgs
-> (flags -> [(FilePath, [FilePath])])
-> ([(FilePath, [FilePath])] -> flags -> flags)
-> [OptionField flags]
programDbOption ProgramDb
progDb ShowOrParseArgs
showOrParseArgs
           ConfigFlags -> [(FilePath, [FilePath])]
configProgramArgs (\[(FilePath, [FilePath])]
v ConfigFlags
fs -> ConfigFlags
fs { configProgramArgs :: [(FilePath, [FilePath])]
configProgramArgs = [(FilePath, [FilePath])]
v })
      [OptionField ConfigFlags]
-> [OptionField ConfigFlags] -> [OptionField ConfigFlags]
forall a. [a] -> [a] -> [a]
++ ProgramDb
-> ShowOrParseArgs
-> (ConfigFlags -> [(FilePath, [FilePath])])
-> ([(FilePath, [FilePath])] -> ConfigFlags -> ConfigFlags)
-> [OptionField ConfigFlags]
forall flags.
ProgramDb
-> ShowOrParseArgs
-> (flags -> [(FilePath, [FilePath])])
-> ([(FilePath, [FilePath])] -> flags -> flags)
-> [OptionField flags]
programDbOptions ProgramDb
progDb ShowOrParseArgs
showOrParseArgs
           ConfigFlags -> [(FilePath, [FilePath])]
configProgramArgs (\[(FilePath, [FilePath])]
v ConfigFlags
fs -> ConfigFlags
fs { configProgramArgs :: [(FilePath, [FilePath])]
configProgramArgs = [(FilePath, [FilePath])]
v })
  }

-- | Inverse to 'dispModSubstEntry'.
parsecModSubstEntry :: ParsecParser (ModuleName, Module)
parsecModSubstEntry :: ParsecParser (ModuleName, Module)
parsecModSubstEntry = do
    ModuleName
k <- ParsecParser ModuleName
forall a (m :: * -> *). (Parsec a, CabalParsing m) => m a
parsec
    Char
_ <- Char -> ParsecParser Char
forall (m :: * -> *). CharParsing m => Char -> m Char
P.char Char
'='
    Module
v <- ParsecParser Module
forall a (m :: * -> *). (Parsec a, CabalParsing m) => m a
parsec
    (ModuleName, Module) -> ParsecParser (ModuleName, Module)
forall (m :: * -> *) a. Monad m => a -> m a
return (ModuleName
k, Module
v)

-- | Pretty-print a single entry of a module substitution.
dispModSubstEntry :: (ModuleName, Module) -> Disp.Doc
dispModSubstEntry :: (ModuleName, Module) -> Doc
dispModSubstEntry (ModuleName
k, Module
v) = ModuleName -> Doc
forall a. Pretty a => a -> Doc
pretty ModuleName
k Doc -> Doc -> Doc
<<>> Char -> Doc
Disp.char Char
'=' Doc -> Doc -> Doc
<<>> Module -> Doc
forall a. Pretty a => a -> Doc
pretty Module
v

configureOptions :: ShowOrParseArgs -> [OptionField ConfigFlags]
configureOptions :: ShowOrParseArgs -> [OptionField ConfigFlags]
configureOptions ShowOrParseArgs
showOrParseArgs =
      [(ConfigFlags -> Flag Verbosity)
-> (Flag Verbosity -> ConfigFlags -> ConfigFlags)
-> OptionField ConfigFlags
forall flags.
(flags -> Flag Verbosity)
-> (Flag Verbosity -> flags -> flags) -> OptionField flags
optionVerbosity ConfigFlags -> Flag Verbosity
configVerbosity
       (\Flag Verbosity
v ConfigFlags
flags -> ConfigFlags
flags { configVerbosity :: Flag Verbosity
configVerbosity = Flag Verbosity
v })
      ,(ConfigFlags -> Flag FilePath)
-> (Flag FilePath -> ConfigFlags -> ConfigFlags)
-> ShowOrParseArgs
-> OptionField ConfigFlags
forall flags.
(flags -> Flag FilePath)
-> (Flag FilePath -> flags -> flags)
-> ShowOrParseArgs
-> OptionField flags
optionDistPref
         ConfigFlags -> Flag FilePath
configDistPref (\Flag FilePath
d ConfigFlags
flags -> ConfigFlags
flags { configDistPref :: Flag FilePath
configDistPref = Flag FilePath
d })
         ShowOrParseArgs
showOrParseArgs

      ,FilePath
-> [FilePath]
-> FilePath
-> (ConfigFlags -> Flag CompilerFlavor)
-> (Flag CompilerFlavor -> ConfigFlags -> ConfigFlags)
-> MkOptDescr
     (ConfigFlags -> Flag CompilerFlavor)
     (Flag CompilerFlavor -> ConfigFlags -> ConfigFlags)
     ConfigFlags
-> OptionField ConfigFlags
forall get set a.
FilePath
-> [FilePath]
-> FilePath
-> get
-> set
-> MkOptDescr get set a
-> OptionField a
option [] [FilePath
"compiler"] FilePath
"compiler"
         ConfigFlags -> Flag CompilerFlavor
configHcFlavor (\Flag CompilerFlavor
v ConfigFlags
flags -> ConfigFlags
flags { configHcFlavor :: Flag CompilerFlavor
configHcFlavor = Flag CompilerFlavor
v })
         ([(Flag CompilerFlavor, (FilePath, [FilePath]), FilePath)]
-> MkOptDescr
     (ConfigFlags -> Flag CompilerFlavor)
     (Flag CompilerFlavor -> ConfigFlags -> ConfigFlags)
     ConfigFlags
forall b a.
Eq b =>
[(b, (FilePath, [FilePath]), FilePath)]
-> MkOptDescr (a -> b) (b -> a -> a) a
choiceOpt [ (CompilerFlavor -> Flag CompilerFlavor
forall a. a -> Flag a
Flag CompilerFlavor
GHC,   (FilePath
"g", [FilePath
"ghc"]),   FilePath
"compile with GHC")
                    , (CompilerFlavor -> Flag CompilerFlavor
forall a. a -> Flag a
Flag CompilerFlavor
GHCJS, ([] , [FilePath
"ghcjs"]), FilePath
"compile with GHCJS")
                    , (CompilerFlavor -> Flag CompilerFlavor
forall a. a -> Flag a
Flag CompilerFlavor
UHC,   ([] , [FilePath
"uhc"]),   FilePath
"compile with UHC")
                    -- "haskell-suite" compiler id string will be replaced
                    -- by a more specific one during the configure stage
                    , (CompilerFlavor -> Flag CompilerFlavor
forall a. a -> Flag a
Flag (FilePath -> CompilerFlavor
HaskellSuite FilePath
"haskell-suite"), ([] , [FilePath
"haskell-suite"]),
                        FilePath
"compile with a haskell-suite compiler")])

      ,FilePath
-> [FilePath]
-> FilePath
-> (ConfigFlags -> Flag FilePath)
-> (Flag FilePath -> ConfigFlags -> ConfigFlags)
-> MkOptDescr
     (ConfigFlags -> Flag FilePath)
     (Flag FilePath -> ConfigFlags -> ConfigFlags)
     ConfigFlags
-> OptionField ConfigFlags
forall get set a.
FilePath
-> [FilePath]
-> FilePath
-> get
-> set
-> MkOptDescr get set a
-> OptionField a
option FilePath
"" [FilePath
"cabal-file"]
         FilePath
"use this Cabal file"
         ConfigFlags -> Flag FilePath
configCabalFilePath (\Flag FilePath
v ConfigFlags
flags -> ConfigFlags
flags { configCabalFilePath :: Flag FilePath
configCabalFilePath = Flag FilePath
v })
         (FilePath
-> MkOptDescr
     (ConfigFlags -> Flag FilePath)
     (Flag FilePath -> ConfigFlags -> ConfigFlags)
     ConfigFlags
forall b.
FilePath
-> FilePath
-> [FilePath]
-> FilePath
-> (b -> Flag FilePath)
-> (Flag FilePath -> b -> b)
-> OptDescr b
reqArgFlag FilePath
"PATH")

      ,FilePath
-> [FilePath]
-> FilePath
-> (ConfigFlags -> Flag FilePath)
-> (Flag FilePath -> ConfigFlags -> ConfigFlags)
-> MkOptDescr
     (ConfigFlags -> Flag FilePath)
     (Flag FilePath -> ConfigFlags -> ConfigFlags)
     ConfigFlags
-> OptionField ConfigFlags
forall get set a.
FilePath
-> [FilePath]
-> FilePath
-> get
-> set
-> MkOptDescr get set a
-> OptionField a
option FilePath
"w" [FilePath
"with-compiler"]
         FilePath
"give the path to a particular compiler"
         ConfigFlags -> Flag FilePath
configHcPath (\Flag FilePath
v ConfigFlags
flags -> ConfigFlags
flags { configHcPath :: Flag FilePath
configHcPath = Flag FilePath
v })
         (FilePath
-> MkOptDescr
     (ConfigFlags -> Flag FilePath)
     (Flag FilePath -> ConfigFlags -> ConfigFlags)
     ConfigFlags
forall b.
FilePath
-> FilePath
-> [FilePath]
-> FilePath
-> (b -> Flag FilePath)
-> (Flag FilePath -> b -> b)
-> OptDescr b
reqArgFlag FilePath
"PATH")

      ,FilePath
-> [FilePath]
-> FilePath
-> (ConfigFlags -> Flag FilePath)
-> (Flag FilePath -> ConfigFlags -> ConfigFlags)
-> MkOptDescr
     (ConfigFlags -> Flag FilePath)
     (Flag FilePath -> ConfigFlags -> ConfigFlags)
     ConfigFlags
-> OptionField ConfigFlags
forall get set a.
FilePath
-> [FilePath]
-> FilePath
-> get
-> set
-> MkOptDescr get set a
-> OptionField a
option FilePath
"" [FilePath
"with-hc-pkg"]
         FilePath
"give the path to the package tool"
         ConfigFlags -> Flag FilePath
configHcPkg (\Flag FilePath
v ConfigFlags
flags -> ConfigFlags
flags { configHcPkg :: Flag FilePath
configHcPkg = Flag FilePath
v })
         (FilePath
-> MkOptDescr
     (ConfigFlags -> Flag FilePath)
     (Flag FilePath -> ConfigFlags -> ConfigFlags)
     ConfigFlags
forall b.
FilePath
-> FilePath
-> [FilePath]
-> FilePath
-> (b -> Flag FilePath)
-> (Flag FilePath -> b -> b)
-> OptDescr b
reqArgFlag FilePath
"PATH")
      ]
   [OptionField ConfigFlags]
-> [OptionField ConfigFlags] -> [OptionField ConfigFlags]
forall a. [a] -> [a] -> [a]
++ (OptionField (InstallDirs (Flag PathTemplate))
 -> OptionField ConfigFlags)
-> [OptionField (InstallDirs (Flag PathTemplate))]
-> [OptionField ConfigFlags]
forall a b. (a -> b) -> [a] -> [b]
map OptionField (InstallDirs (Flag PathTemplate))
-> OptionField ConfigFlags
liftInstallDirs [OptionField (InstallDirs (Flag PathTemplate))]
installDirsOptions
   [OptionField ConfigFlags]
-> [OptionField ConfigFlags] -> [OptionField ConfigFlags]
forall a. [a] -> [a] -> [a]
++ [FilePath
-> [FilePath]
-> FilePath
-> (ConfigFlags -> Flag PathTemplate)
-> (Flag PathTemplate -> ConfigFlags -> ConfigFlags)
-> MkOptDescr
     (ConfigFlags -> Flag PathTemplate)
     (Flag PathTemplate -> ConfigFlags -> ConfigFlags)
     ConfigFlags
-> OptionField ConfigFlags
forall get set a.
FilePath
-> [FilePath]
-> FilePath
-> get
-> set
-> MkOptDescr get set a
-> OptionField a
option FilePath
"" [FilePath
"program-prefix"]
          FilePath
"prefix to be applied to installed executables"
          ConfigFlags -> Flag PathTemplate
configProgPrefix
          (\Flag PathTemplate
v ConfigFlags
flags -> ConfigFlags
flags { configProgPrefix :: Flag PathTemplate
configProgPrefix = Flag PathTemplate
v })
          (FilePath
-> MkOptDescr
     (ConfigFlags -> Flag PathTemplate)
     (Flag PathTemplate -> ConfigFlags -> ConfigFlags)
     ConfigFlags
forall a.
FilePath
-> FilePath
-> [FilePath]
-> FilePath
-> (a -> Flag PathTemplate)
-> (Flag PathTemplate -> a -> a)
-> OptDescr a
reqPathTemplateArgFlag FilePath
"PREFIX")

      ,FilePath
-> [FilePath]
-> FilePath
-> (ConfigFlags -> Flag PathTemplate)
-> (Flag PathTemplate -> ConfigFlags -> ConfigFlags)
-> MkOptDescr
     (ConfigFlags -> Flag PathTemplate)
     (Flag PathTemplate -> ConfigFlags -> ConfigFlags)
     ConfigFlags
-> OptionField ConfigFlags
forall get set a.
FilePath
-> [FilePath]
-> FilePath
-> get
-> set
-> MkOptDescr get set a
-> OptionField a
option FilePath
"" [FilePath
"program-suffix"]
          FilePath
"suffix to be applied to installed executables"
          ConfigFlags -> Flag PathTemplate
configProgSuffix (\Flag PathTemplate
v ConfigFlags
flags -> ConfigFlags
flags { configProgSuffix :: Flag PathTemplate
configProgSuffix = Flag PathTemplate
v } )
          (FilePath
-> MkOptDescr
     (ConfigFlags -> Flag PathTemplate)
     (Flag PathTemplate -> ConfigFlags -> ConfigFlags)
     ConfigFlags
forall a.
FilePath
-> FilePath
-> [FilePath]
-> FilePath
-> (a -> Flag PathTemplate)
-> (Flag PathTemplate -> a -> a)
-> OptDescr a
reqPathTemplateArgFlag FilePath
"SUFFIX")

      ,FilePath
-> [FilePath]
-> FilePath
-> (ConfigFlags -> Flag Bool)
-> (Flag Bool -> ConfigFlags -> ConfigFlags)
-> MkOptDescr
     (ConfigFlags -> Flag Bool)
     (Flag Bool -> ConfigFlags -> ConfigFlags)
     ConfigFlags
-> OptionField ConfigFlags
forall get set a.
FilePath
-> [FilePath]
-> FilePath
-> get
-> set
-> MkOptDescr get set a
-> OptionField a
option FilePath
"" [FilePath
"library-vanilla"]
         FilePath
"Vanilla libraries"
         ConfigFlags -> Flag Bool
configVanillaLib (\Flag Bool
v ConfigFlags
flags -> ConfigFlags
flags { configVanillaLib :: Flag Bool
configVanillaLib = Flag Bool
v })
         (FilePath
-> FilePath
-> MkOptDescr
     (ConfigFlags -> Flag Bool)
     (Flag Bool -> ConfigFlags -> ConfigFlags)
     ConfigFlags
forall a.
FilePath
-> FilePath -> MkOptDescr (a -> Flag Bool) (Flag Bool -> a -> a) a
boolOpt [] [])

      ,FilePath
-> [FilePath]
-> FilePath
-> (ConfigFlags -> Flag Bool)
-> (Flag Bool -> ConfigFlags -> ConfigFlags)
-> MkOptDescr
     (ConfigFlags -> Flag Bool)
     (Flag Bool -> ConfigFlags -> ConfigFlags)
     ConfigFlags
-> OptionField ConfigFlags
forall get set a.
FilePath
-> [FilePath]
-> FilePath
-> get
-> set
-> MkOptDescr get set a
-> OptionField a
option FilePath
"p" [FilePath
"library-profiling"]
         FilePath
"Library profiling"
         ConfigFlags -> Flag Bool
configProfLib (\Flag Bool
v ConfigFlags
flags -> ConfigFlags
flags { configProfLib :: Flag Bool
configProfLib = Flag Bool
v })
         (FilePath
-> FilePath
-> MkOptDescr
     (ConfigFlags -> Flag Bool)
     (Flag Bool -> ConfigFlags -> ConfigFlags)
     ConfigFlags
forall a.
FilePath
-> FilePath -> MkOptDescr (a -> Flag Bool) (Flag Bool -> a -> a) a
boolOpt FilePath
"p" [])

      ,FilePath
-> [FilePath]
-> FilePath
-> (ConfigFlags -> Flag Bool)
-> (Flag Bool -> ConfigFlags -> ConfigFlags)
-> MkOptDescr
     (ConfigFlags -> Flag Bool)
     (Flag Bool -> ConfigFlags -> ConfigFlags)
     ConfigFlags
-> OptionField ConfigFlags
forall get set a.
FilePath
-> [FilePath]
-> FilePath
-> get
-> set
-> MkOptDescr get set a
-> OptionField a
option FilePath
"" [FilePath
"shared"]
         FilePath
"Shared library"
         ConfigFlags -> Flag Bool
configSharedLib (\Flag Bool
v ConfigFlags
flags -> ConfigFlags
flags { configSharedLib :: Flag Bool
configSharedLib = Flag Bool
v })
         (FilePath
-> FilePath
-> MkOptDescr
     (ConfigFlags -> Flag Bool)
     (Flag Bool -> ConfigFlags -> ConfigFlags)
     ConfigFlags
forall a.
FilePath
-> FilePath -> MkOptDescr (a -> Flag Bool) (Flag Bool -> a -> a) a
boolOpt [] [])

      ,FilePath
-> [FilePath]
-> FilePath
-> (ConfigFlags -> Flag Bool)
-> (Flag Bool -> ConfigFlags -> ConfigFlags)
-> MkOptDescr
     (ConfigFlags -> Flag Bool)
     (Flag Bool -> ConfigFlags -> ConfigFlags)
     ConfigFlags
-> OptionField ConfigFlags
forall get set a.
FilePath
-> [FilePath]
-> FilePath
-> get
-> set
-> MkOptDescr get set a
-> OptionField a
option FilePath
"" [FilePath
"static"]
         FilePath
"Static library"
         ConfigFlags -> Flag Bool
configStaticLib (\Flag Bool
v ConfigFlags
flags -> ConfigFlags
flags { configStaticLib :: Flag Bool
configStaticLib = Flag Bool
v })
         (FilePath
-> FilePath
-> MkOptDescr
     (ConfigFlags -> Flag Bool)
     (Flag Bool -> ConfigFlags -> ConfigFlags)
     ConfigFlags
forall a.
FilePath
-> FilePath -> MkOptDescr (a -> Flag Bool) (Flag Bool -> a -> a) a
boolOpt [] [])

      ,FilePath
-> [FilePath]
-> FilePath
-> (ConfigFlags -> Flag Bool)
-> (Flag Bool -> ConfigFlags -> ConfigFlags)
-> MkOptDescr
     (ConfigFlags -> Flag Bool)
     (Flag Bool -> ConfigFlags -> ConfigFlags)
     ConfigFlags
-> OptionField ConfigFlags
forall get set a.
FilePath
-> [FilePath]
-> FilePath
-> get
-> set
-> MkOptDescr get set a
-> OptionField a
option FilePath
"" [FilePath
"executable-dynamic"]
         FilePath
"Executable dynamic linking"
         ConfigFlags -> Flag Bool
configDynExe (\Flag Bool
v ConfigFlags
flags -> ConfigFlags
flags { configDynExe :: Flag Bool
configDynExe = Flag Bool
v })
         (FilePath
-> FilePath
-> MkOptDescr
     (ConfigFlags -> Flag Bool)
     (Flag Bool -> ConfigFlags -> ConfigFlags)
     ConfigFlags
forall a.
FilePath
-> FilePath -> MkOptDescr (a -> Flag Bool) (Flag Bool -> a -> a) a
boolOpt [] [])

      ,FilePath
-> [FilePath]
-> FilePath
-> (ConfigFlags -> Flag Bool)
-> (Flag Bool -> ConfigFlags -> ConfigFlags)
-> MkOptDescr
     (ConfigFlags -> Flag Bool)
     (Flag Bool -> ConfigFlags -> ConfigFlags)
     ConfigFlags
-> OptionField ConfigFlags
forall get set a.
FilePath
-> [FilePath]
-> FilePath
-> get
-> set
-> MkOptDescr get set a
-> OptionField a
option FilePath
"" [FilePath
"executable-static"]
         FilePath
"Executable fully static linking"
         ConfigFlags -> Flag Bool
configFullyStaticExe (\Flag Bool
v ConfigFlags
flags -> ConfigFlags
flags { configFullyStaticExe :: Flag Bool
configFullyStaticExe = Flag Bool
v })
         (FilePath
-> FilePath
-> MkOptDescr
     (ConfigFlags -> Flag Bool)
     (Flag Bool -> ConfigFlags -> ConfigFlags)
     ConfigFlags
forall a.
FilePath
-> FilePath -> MkOptDescr (a -> Flag Bool) (Flag Bool -> a -> a) a
boolOpt [] [])

      ,FilePath
-> [FilePath]
-> FilePath
-> (ConfigFlags -> Flag Bool)
-> (Flag Bool -> ConfigFlags -> ConfigFlags)
-> MkOptDescr
     (ConfigFlags -> Flag Bool)
     (Flag Bool -> ConfigFlags -> ConfigFlags)
     ConfigFlags
-> OptionField ConfigFlags
forall get set a.
FilePath
-> [FilePath]
-> FilePath
-> get
-> set
-> MkOptDescr get set a
-> OptionField a
option FilePath
"" [FilePath
"profiling"]
         FilePath
"Executable and library profiling"
         ConfigFlags -> Flag Bool
configProf (\Flag Bool
v ConfigFlags
flags -> ConfigFlags
flags { configProf :: Flag Bool
configProf = Flag Bool
v })
         (FilePath
-> FilePath
-> MkOptDescr
     (ConfigFlags -> Flag Bool)
     (Flag Bool -> ConfigFlags -> ConfigFlags)
     ConfigFlags
forall a.
FilePath
-> FilePath -> MkOptDescr (a -> Flag Bool) (Flag Bool -> a -> a) a
boolOpt [] [])

      ,FilePath
-> [FilePath]
-> FilePath
-> (ConfigFlags -> Flag Bool)
-> (Flag Bool -> ConfigFlags -> ConfigFlags)
-> MkOptDescr
     (ConfigFlags -> Flag Bool)
     (Flag Bool -> ConfigFlags -> ConfigFlags)
     ConfigFlags
-> OptionField ConfigFlags
forall get set a.
FilePath
-> [FilePath]
-> FilePath
-> get
-> set
-> MkOptDescr get set a
-> OptionField a
option FilePath
"" [FilePath
"executable-profiling"]
         FilePath
"Executable profiling (DEPRECATED)"
         ConfigFlags -> Flag Bool
configProfExe (\Flag Bool
v ConfigFlags
flags -> ConfigFlags
flags { configProfExe :: Flag Bool
configProfExe = Flag Bool
v })
         (FilePath
-> FilePath
-> MkOptDescr
     (ConfigFlags -> Flag Bool)
     (Flag Bool -> ConfigFlags -> ConfigFlags)
     ConfigFlags
forall a.
FilePath
-> FilePath -> MkOptDescr (a -> Flag Bool) (Flag Bool -> a -> a) a
boolOpt [] [])

      ,FilePath
-> [FilePath]
-> FilePath
-> (ConfigFlags -> Flag ProfDetailLevel)
-> (Flag ProfDetailLevel -> ConfigFlags -> ConfigFlags)
-> MkOptDescr
     (ConfigFlags -> Flag ProfDetailLevel)
     (Flag ProfDetailLevel -> ConfigFlags -> ConfigFlags)
     ConfigFlags
-> OptionField ConfigFlags
forall get set a.
FilePath
-> [FilePath]
-> FilePath
-> get
-> set
-> MkOptDescr get set a
-> OptionField a
option FilePath
"" [FilePath
"profiling-detail"]
         (FilePath
"Profiling detail level for executable and library (default, " FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++
          FilePath
"none, exported-functions, toplevel-functions,  all-functions).")
         ConfigFlags -> Flag ProfDetailLevel
configProfDetail (\Flag ProfDetailLevel
v ConfigFlags
flags -> ConfigFlags
flags { configProfDetail :: Flag ProfDetailLevel
configProfDetail = Flag ProfDetailLevel
v })
         (FilePath
-> (FilePath -> Flag ProfDetailLevel)
-> (Flag ProfDetailLevel -> [FilePath])
-> MkOptDescr
     (ConfigFlags -> Flag ProfDetailLevel)
     (Flag ProfDetailLevel -> ConfigFlags -> ConfigFlags)
     ConfigFlags
forall b a.
Monoid b =>
FilePath
-> (FilePath -> b)
-> (b -> [FilePath])
-> MkOptDescr (a -> b) (b -> a -> a) a
reqArg' FilePath
"level" (ProfDetailLevel -> Flag ProfDetailLevel
forall a. a -> Flag a
Flag (ProfDetailLevel -> Flag ProfDetailLevel)
-> (FilePath -> ProfDetailLevel)
-> FilePath
-> Flag ProfDetailLevel
forall b c a. (b -> c) -> (a -> b) -> a -> c
. FilePath -> ProfDetailLevel
flagToProfDetailLevel)
                          Flag ProfDetailLevel -> [FilePath]
showProfDetailLevelFlag)

      ,FilePath
-> [FilePath]
-> FilePath
-> (ConfigFlags -> Flag ProfDetailLevel)
-> (Flag ProfDetailLevel -> ConfigFlags -> ConfigFlags)
-> MkOptDescr
     (ConfigFlags -> Flag ProfDetailLevel)
     (Flag ProfDetailLevel -> ConfigFlags -> ConfigFlags)
     ConfigFlags
-> OptionField ConfigFlags
forall get set a.
FilePath
-> [FilePath]
-> FilePath
-> get
-> set
-> MkOptDescr get set a
-> OptionField a
option FilePath
"" [FilePath
"library-profiling-detail"]
         FilePath
"Profiling detail level for libraries only."
         ConfigFlags -> Flag ProfDetailLevel
configProfLibDetail (\Flag ProfDetailLevel
v ConfigFlags
flags -> ConfigFlags
flags { configProfLibDetail :: Flag ProfDetailLevel
configProfLibDetail = Flag ProfDetailLevel
v })
         (FilePath
-> (FilePath -> Flag ProfDetailLevel)
-> (Flag ProfDetailLevel -> [FilePath])
-> MkOptDescr
     (ConfigFlags -> Flag ProfDetailLevel)
     (Flag ProfDetailLevel -> ConfigFlags -> ConfigFlags)
     ConfigFlags
forall b a.
Monoid b =>
FilePath
-> (FilePath -> b)
-> (b -> [FilePath])
-> MkOptDescr (a -> b) (b -> a -> a) a
reqArg' FilePath
"level" (ProfDetailLevel -> Flag ProfDetailLevel
forall a. a -> Flag a
Flag (ProfDetailLevel -> Flag ProfDetailLevel)
-> (FilePath -> ProfDetailLevel)
-> FilePath
-> Flag ProfDetailLevel
forall b c a. (b -> c) -> (a -> b) -> a -> c
. FilePath -> ProfDetailLevel
flagToProfDetailLevel)
                          Flag ProfDetailLevel -> [FilePath]
showProfDetailLevelFlag)

      ,FilePath
-> (ConfigFlags -> Flag OptimisationLevel)
-> (Flag OptimisationLevel -> ConfigFlags -> ConfigFlags)
-> [(ConfigFlags -> Flag OptimisationLevel)
    -> (Flag OptimisationLevel -> ConfigFlags -> ConfigFlags)
    -> OptDescr ConfigFlags]
-> OptionField ConfigFlags
forall get set a.
FilePath
-> get -> set -> [get -> set -> OptDescr a] -> OptionField a
multiOption FilePath
"optimization"
         ConfigFlags -> Flag OptimisationLevel
configOptimization (\Flag OptimisationLevel
v ConfigFlags
flags -> ConfigFlags
flags { configOptimization :: Flag OptimisationLevel
configOptimization = Flag OptimisationLevel
v })
         [FilePath
-> (Maybe FilePath -> Flag OptimisationLevel)
-> (Flag OptimisationLevel -> [Maybe FilePath])
-> MkOptDescr
     (ConfigFlags -> Flag OptimisationLevel)
     (Flag OptimisationLevel -> ConfigFlags -> ConfigFlags)
     ConfigFlags
forall b a.
Monoid b =>
FilePath
-> (Maybe FilePath -> b)
-> (b -> [Maybe FilePath])
-> MkOptDescr (a -> b) (b -> a -> a) a
optArg' FilePath
"n" (OptimisationLevel -> Flag OptimisationLevel
forall a. a -> Flag a
Flag (OptimisationLevel -> Flag OptimisationLevel)
-> (Maybe FilePath -> OptimisationLevel)
-> Maybe FilePath
-> Flag OptimisationLevel
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Maybe FilePath -> OptimisationLevel
flagToOptimisationLevel)
                     (\Flag OptimisationLevel
f -> case Flag OptimisationLevel
f of
                              Flag OptimisationLevel
NoOptimisation      -> []
                              Flag OptimisationLevel
NormalOptimisation  -> [Maybe FilePath
forall a. Maybe a
Nothing]
                              Flag OptimisationLevel
MaximumOptimisation -> [FilePath -> Maybe FilePath
forall a. a -> Maybe a
Just FilePath
"2"]
                              Flag OptimisationLevel
_                        -> [])
                 FilePath
"O" [FilePath
"enable-optimization",FilePath
"enable-optimisation"]
                 FilePath
"Build with optimization (n is 0--2, default is 1)",
          Flag OptimisationLevel
-> MkOptDescr
     (ConfigFlags -> Flag OptimisationLevel)
     (Flag OptimisationLevel -> ConfigFlags -> ConfigFlags)
     ConfigFlags
forall b a. Eq b => b -> MkOptDescr (a -> b) (b -> a -> a) a
noArg (OptimisationLevel -> Flag OptimisationLevel
forall a. a -> Flag a
Flag OptimisationLevel
NoOptimisation) []
                [FilePath
"disable-optimization",FilePath
"disable-optimisation"]
                FilePath
"Build without optimization"
         ]

      ,FilePath
-> (ConfigFlags -> Flag DebugInfoLevel)
-> (Flag DebugInfoLevel -> ConfigFlags -> ConfigFlags)
-> [(ConfigFlags -> Flag DebugInfoLevel)
    -> (Flag DebugInfoLevel -> ConfigFlags -> ConfigFlags)
    -> OptDescr ConfigFlags]
-> OptionField ConfigFlags
forall get set a.
FilePath
-> get -> set -> [get -> set -> OptDescr a] -> OptionField a
multiOption FilePath
"debug-info"
         ConfigFlags -> Flag DebugInfoLevel
configDebugInfo (\Flag DebugInfoLevel
v ConfigFlags
flags -> ConfigFlags
flags { configDebugInfo :: Flag DebugInfoLevel
configDebugInfo = Flag DebugInfoLevel
v })
         [FilePath
-> (Maybe FilePath -> Flag DebugInfoLevel)
-> (Flag DebugInfoLevel -> [Maybe FilePath])
-> MkOptDescr
     (ConfigFlags -> Flag DebugInfoLevel)
     (Flag DebugInfoLevel -> ConfigFlags -> ConfigFlags)
     ConfigFlags
forall b a.
Monoid b =>
FilePath
-> (Maybe FilePath -> b)
-> (b -> [Maybe FilePath])
-> MkOptDescr (a -> b) (b -> a -> a) a
optArg' FilePath
"n" (DebugInfoLevel -> Flag DebugInfoLevel
forall a. a -> Flag a
Flag (DebugInfoLevel -> Flag DebugInfoLevel)
-> (Maybe FilePath -> DebugInfoLevel)
-> Maybe FilePath
-> Flag DebugInfoLevel
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Maybe FilePath -> DebugInfoLevel
flagToDebugInfoLevel)
                     (\Flag DebugInfoLevel
f -> case Flag DebugInfoLevel
f of
                              Flag DebugInfoLevel
NoDebugInfo      -> []
                              Flag DebugInfoLevel
MinimalDebugInfo -> [FilePath -> Maybe FilePath
forall a. a -> Maybe a
Just FilePath
"1"]
                              Flag DebugInfoLevel
NormalDebugInfo  -> [Maybe FilePath
forall a. Maybe a
Nothing]
                              Flag DebugInfoLevel
MaximalDebugInfo -> [FilePath -> Maybe FilePath
forall a. a -> Maybe a
Just FilePath
"3"]
                              Flag DebugInfoLevel
_                     -> [])
                 FilePath
"" [FilePath
"enable-debug-info"]
                 FilePath
"Emit debug info (n is 0--3, default is 0)",
          Flag DebugInfoLevel
-> MkOptDescr
     (ConfigFlags -> Flag DebugInfoLevel)
     (Flag DebugInfoLevel -> ConfigFlags -> ConfigFlags)
     ConfigFlags
forall b a. Eq b => b -> MkOptDescr (a -> b) (b -> a -> a) a
noArg (DebugInfoLevel -> Flag DebugInfoLevel
forall a. a -> Flag a
Flag DebugInfoLevel
NoDebugInfo) []
                [FilePath
"disable-debug-info"]
                FilePath
"Don't emit debug info"
         ]

      ,FilePath
-> [FilePath]
-> FilePath
-> (ConfigFlags -> Flag Bool)
-> (Flag Bool -> ConfigFlags -> ConfigFlags)
-> MkOptDescr
     (ConfigFlags -> Flag Bool)
     (Flag Bool -> ConfigFlags -> ConfigFlags)
     ConfigFlags
-> OptionField ConfigFlags
forall get set a.
FilePath
-> [FilePath]
-> FilePath
-> get
-> set
-> MkOptDescr get set a
-> OptionField a
option FilePath
"" [FilePath
"library-for-ghci"]
         FilePath
"compile library for use with GHCi"
         ConfigFlags -> Flag Bool
configGHCiLib (\Flag Bool
v ConfigFlags
flags -> ConfigFlags
flags { configGHCiLib :: Flag Bool
configGHCiLib = Flag Bool
v })
         (FilePath
-> FilePath
-> MkOptDescr
     (ConfigFlags -> Flag Bool)
     (Flag Bool -> ConfigFlags -> ConfigFlags)
     ConfigFlags
forall a.
FilePath
-> FilePath -> MkOptDescr (a -> Flag Bool) (Flag Bool -> a -> a) a
boolOpt [] [])

      ,FilePath
-> [FilePath]
-> FilePath
-> (ConfigFlags -> Flag Bool)
-> (Flag Bool -> ConfigFlags -> ConfigFlags)
-> MkOptDescr
     (ConfigFlags -> Flag Bool)
     (Flag Bool -> ConfigFlags -> ConfigFlags)
     ConfigFlags
-> OptionField ConfigFlags
forall get set a.
FilePath
-> [FilePath]
-> FilePath
-> get
-> set
-> MkOptDescr get set a
-> OptionField a
option FilePath
"" [FilePath
"split-sections"]
         FilePath
"compile library code such that unneeded definitions can be dropped from the final executable (GHC 7.8+)"
         ConfigFlags -> Flag Bool
configSplitSections (\Flag Bool
v ConfigFlags
flags -> ConfigFlags
flags { configSplitSections :: Flag Bool
configSplitSections = Flag Bool
v })
         (FilePath
-> FilePath
-> MkOptDescr
     (ConfigFlags -> Flag Bool)
     (Flag Bool -> ConfigFlags -> ConfigFlags)
     ConfigFlags
forall a.
FilePath
-> FilePath -> MkOptDescr (a -> Flag Bool) (Flag Bool -> a -> a) a
boolOpt [] [])

      ,FilePath
-> [FilePath]
-> FilePath
-> (ConfigFlags -> Flag Bool)
-> (Flag Bool -> ConfigFlags -> ConfigFlags)
-> MkOptDescr
     (ConfigFlags -> Flag Bool)
     (Flag Bool -> ConfigFlags -> ConfigFlags)
     ConfigFlags
-> OptionField ConfigFlags
forall get set a.
FilePath
-> [FilePath]
-> FilePath
-> get
-> set
-> MkOptDescr get set a
-> OptionField a
option FilePath
"" [FilePath
"split-objs"]
         FilePath
"split library into smaller objects to reduce binary sizes (GHC 6.6+)"
         ConfigFlags -> Flag Bool
configSplitObjs (\Flag Bool
v ConfigFlags
flags -> ConfigFlags
flags { configSplitObjs :: Flag Bool
configSplitObjs = Flag Bool
v })
         (FilePath
-> FilePath
-> MkOptDescr
     (ConfigFlags -> Flag Bool)
     (Flag Bool -> ConfigFlags -> ConfigFlags)
     ConfigFlags
forall a.
FilePath
-> FilePath -> MkOptDescr (a -> Flag Bool) (Flag Bool -> a -> a) a
boolOpt [] [])

      ,FilePath
-> [FilePath]
-> FilePath
-> (ConfigFlags -> Flag Bool)
-> (Flag Bool -> ConfigFlags -> ConfigFlags)
-> MkOptDescr
     (ConfigFlags -> Flag Bool)
     (Flag Bool -> ConfigFlags -> ConfigFlags)
     ConfigFlags
-> OptionField ConfigFlags
forall get set a.
FilePath
-> [FilePath]
-> FilePath
-> get
-> set
-> MkOptDescr get set a
-> OptionField a
option FilePath
"" [FilePath
"executable-stripping"]
         FilePath
"strip executables upon installation to reduce binary sizes"
         ConfigFlags -> Flag Bool
configStripExes (\Flag Bool
v ConfigFlags
flags -> ConfigFlags
flags { configStripExes :: Flag Bool
configStripExes = Flag Bool
v })
         (FilePath
-> FilePath
-> MkOptDescr
     (ConfigFlags -> Flag Bool)
     (Flag Bool -> ConfigFlags -> ConfigFlags)
     ConfigFlags
forall a.
FilePath
-> FilePath -> MkOptDescr (a -> Flag Bool) (Flag Bool -> a -> a) a
boolOpt [] [])

      ,FilePath
-> [FilePath]
-> FilePath
-> (ConfigFlags -> Flag Bool)
-> (Flag Bool -> ConfigFlags -> ConfigFlags)
-> MkOptDescr
     (ConfigFlags -> Flag Bool)
     (Flag Bool -> ConfigFlags -> ConfigFlags)
     ConfigFlags
-> OptionField ConfigFlags
forall get set a.
FilePath
-> [FilePath]
-> FilePath
-> get
-> set
-> MkOptDescr get set a
-> OptionField a
option FilePath
"" [FilePath
"library-stripping"]
         FilePath
"strip libraries upon installation to reduce binary sizes"
         ConfigFlags -> Flag Bool
configStripLibs (\Flag Bool
v ConfigFlags
flags -> ConfigFlags
flags { configStripLibs :: Flag Bool
configStripLibs = Flag Bool
v })
         (FilePath
-> FilePath
-> MkOptDescr
     (ConfigFlags -> Flag Bool)
     (Flag Bool -> ConfigFlags -> ConfigFlags)
     ConfigFlags
forall a.
FilePath
-> FilePath -> MkOptDescr (a -> Flag Bool) (Flag Bool -> a -> a) a
boolOpt [] [])

      ,FilePath
-> [FilePath]
-> FilePath
-> (ConfigFlags -> [FilePath])
-> ([FilePath] -> ConfigFlags -> ConfigFlags)
-> MkOptDescr
     (ConfigFlags -> [FilePath])
     ([FilePath] -> ConfigFlags -> ConfigFlags)
     ConfigFlags
-> OptionField ConfigFlags
forall get set a.
FilePath
-> [FilePath]
-> FilePath
-> get
-> set
-> MkOptDescr get set a
-> OptionField a
option FilePath
"" [FilePath
"configure-option"]
         FilePath
"Extra option for configure"
         ConfigFlags -> [FilePath]
configConfigureArgs (\[FilePath]
v ConfigFlags
flags -> ConfigFlags
flags { configConfigureArgs :: [FilePath]
configConfigureArgs = [FilePath]
v })
         (FilePath
-> (FilePath -> [FilePath])
-> ([FilePath] -> [FilePath])
-> MkOptDescr
     (ConfigFlags -> [FilePath])
     ([FilePath] -> ConfigFlags -> ConfigFlags)
     ConfigFlags
forall b a.
Monoid b =>
FilePath
-> (FilePath -> b)
-> (b -> [FilePath])
-> MkOptDescr (a -> b) (b -> a -> a) a
reqArg' FilePath
"OPT" (\FilePath
x -> [FilePath
x]) [FilePath] -> [FilePath]
forall a. a -> a
id)

      ,FilePath
-> [FilePath]
-> FilePath
-> (ConfigFlags -> Flag Bool)
-> (Flag Bool -> ConfigFlags -> ConfigFlags)
-> MkOptDescr
     (ConfigFlags -> Flag Bool)
     (Flag Bool -> ConfigFlags -> ConfigFlags)
     ConfigFlags
-> OptionField ConfigFlags
forall get set a.
FilePath
-> [FilePath]
-> FilePath
-> get
-> set
-> MkOptDescr get set a
-> OptionField a
option FilePath
"" [FilePath
"user-install"]
         FilePath
"doing a per-user installation"
         ConfigFlags -> Flag Bool
configUserInstall (\Flag Bool
v ConfigFlags
flags -> ConfigFlags
flags { configUserInstall :: Flag Bool
configUserInstall = Flag Bool
v })
         ((FilePath, [FilePath])
-> (FilePath, [FilePath])
-> MkOptDescr
     (ConfigFlags -> Flag Bool)
     (Flag Bool -> ConfigFlags -> ConfigFlags)
     ConfigFlags
forall a.
(FilePath, [FilePath])
-> (FilePath, [FilePath])
-> MkOptDescr (a -> Flag Bool) (Flag Bool -> a -> a) a
boolOpt' ([],[FilePath
"user"]) ([], [FilePath
"global"]))

      ,FilePath
-> [FilePath]
-> FilePath
-> (ConfigFlags -> [Maybe PackageDB])
-> ([Maybe PackageDB] -> ConfigFlags -> ConfigFlags)
-> MkOptDescr
     (ConfigFlags -> [Maybe PackageDB])
     ([Maybe PackageDB] -> ConfigFlags -> ConfigFlags)
     ConfigFlags
-> OptionField ConfigFlags
forall get set a.
FilePath
-> [FilePath]
-> FilePath
-> get
-> set
-> MkOptDescr get set a
-> OptionField a
option FilePath
"" [FilePath
"package-db"]
         (   FilePath
"Append the given package database to the list of package"
          FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
" databases used (to satisfy dependencies and register into)."
          FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
" May be a specific file, 'global' or 'user'. The initial list"
          FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
" is ['global'], ['global', 'user'], or ['global', $sandbox],"
          FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
" depending on context. Use 'clear' to reset the list to empty."
          FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
" See the user guide for details.")
         ConfigFlags -> [Maybe PackageDB]
configPackageDBs (\[Maybe PackageDB]
v ConfigFlags
flags -> ConfigFlags
flags { configPackageDBs :: [Maybe PackageDB]
configPackageDBs = [Maybe PackageDB]
v })
         (FilePath
-> (FilePath -> [Maybe PackageDB])
-> ([Maybe PackageDB] -> [FilePath])
-> MkOptDescr
     (ConfigFlags -> [Maybe PackageDB])
     ([Maybe PackageDB] -> ConfigFlags -> ConfigFlags)
     ConfigFlags
forall b a.
Monoid b =>
FilePath
-> (FilePath -> b)
-> (b -> [FilePath])
-> MkOptDescr (a -> b) (b -> a -> a) a
reqArg' FilePath
"DB" FilePath -> [Maybe PackageDB]
readPackageDbList [Maybe PackageDB] -> [FilePath]
showPackageDbList)

      ,FilePath
-> [FilePath]
-> FilePath
-> (ConfigFlags -> FlagAssignment)
-> (FlagAssignment -> ConfigFlags -> ConfigFlags)
-> MkOptDescr
     (ConfigFlags -> FlagAssignment)
     (FlagAssignment -> ConfigFlags -> ConfigFlags)
     ConfigFlags
-> OptionField ConfigFlags
forall get set a.
FilePath
-> [FilePath]
-> FilePath
-> get
-> set
-> MkOptDescr get set a
-> OptionField a
option FilePath
"f" [FilePath
"flags"]
         FilePath
"Force values for the given flags in Cabal conditionals in the .cabal file.  E.g., --flags=\"debug -usebytestrings\" forces the flag \"debug\" to true and \"usebytestrings\" to false."
         ConfigFlags -> FlagAssignment
configConfigurationsFlags (\FlagAssignment
v ConfigFlags
flags -> ConfigFlags
flags { configConfigurationsFlags :: FlagAssignment
configConfigurationsFlags = FlagAssignment
v })
         (FilePath
-> ReadE FlagAssignment
-> (FlagAssignment -> [FilePath])
-> MkOptDescr
     (ConfigFlags -> FlagAssignment)
     (FlagAssignment -> ConfigFlags -> ConfigFlags)
     ConfigFlags
forall b a.
Monoid b =>
FilePath
-> ReadE b
-> (b -> [FilePath])
-> MkOptDescr (a -> b) (b -> a -> a) a
reqArg FilePath
"FLAGS"
              ((FilePath -> FilePath)
-> ParsecParser FlagAssignment -> ReadE FlagAssignment
forall a. (FilePath -> FilePath) -> ParsecParser a -> ReadE a
parsecToReadE (\FilePath
err -> FilePath
"Invalid flag assignment: " FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
err) ParsecParser FlagAssignment
forall (m :: * -> *). CabalParsing m => m FlagAssignment
parsecFlagAssignment)
              FlagAssignment -> [FilePath]
showFlagAssignment)

      ,FilePath
-> [FilePath]
-> FilePath
-> (ConfigFlags -> [FilePath])
-> ([FilePath] -> ConfigFlags -> ConfigFlags)
-> MkOptDescr
     (ConfigFlags -> [FilePath])
     ([FilePath] -> ConfigFlags -> ConfigFlags)
     ConfigFlags
-> OptionField ConfigFlags
forall get set a.
FilePath
-> [FilePath]
-> FilePath
-> get
-> set
-> MkOptDescr get set a
-> OptionField a
option FilePath
"" [FilePath
"extra-include-dirs"]
         FilePath
"A list of directories to search for header files"
         ConfigFlags -> [FilePath]
configExtraIncludeDirs (\[FilePath]
v ConfigFlags
flags -> ConfigFlags
flags {configExtraIncludeDirs :: [FilePath]
configExtraIncludeDirs = [FilePath]
v})
         (FilePath
-> (FilePath -> [FilePath])
-> ([FilePath] -> [FilePath])
-> MkOptDescr
     (ConfigFlags -> [FilePath])
     ([FilePath] -> ConfigFlags -> ConfigFlags)
     ConfigFlags
forall b a.
Monoid b =>
FilePath
-> (FilePath -> b)
-> (b -> [FilePath])
-> MkOptDescr (a -> b) (b -> a -> a) a
reqArg' FilePath
"PATH" (\FilePath
x -> [FilePath
x]) [FilePath] -> [FilePath]
forall a. a -> a
id)

      ,FilePath
-> [FilePath]
-> FilePath
-> (ConfigFlags -> Flag Bool)
-> (Flag Bool -> ConfigFlags -> ConfigFlags)
-> MkOptDescr
     (ConfigFlags -> Flag Bool)
     (Flag Bool -> ConfigFlags -> ConfigFlags)
     ConfigFlags
-> OptionField ConfigFlags
forall get set a.
FilePath
-> [FilePath]
-> FilePath
-> get
-> set
-> MkOptDescr get set a
-> OptionField a
option FilePath
"" [FilePath
"deterministic"]
         FilePath
"Try to be as deterministic as possible (used by the test suite)"
         ConfigFlags -> Flag Bool
configDeterministic (\Flag Bool
v ConfigFlags
flags -> ConfigFlags
flags {configDeterministic :: Flag Bool
configDeterministic = Flag Bool
v})
         (FilePath
-> FilePath
-> MkOptDescr
     (ConfigFlags -> Flag Bool)
     (Flag Bool -> ConfigFlags -> ConfigFlags)
     ConfigFlags
forall a.
FilePath
-> FilePath -> MkOptDescr (a -> Flag Bool) (Flag Bool -> a -> a) a
boolOpt [] [])

      ,FilePath
-> [FilePath]
-> FilePath
-> (ConfigFlags -> Flag FilePath)
-> (Flag FilePath -> ConfigFlags -> ConfigFlags)
-> MkOptDescr
     (ConfigFlags -> Flag FilePath)
     (Flag FilePath -> ConfigFlags -> ConfigFlags)
     ConfigFlags
-> OptionField ConfigFlags
forall get set a.
FilePath
-> [FilePath]
-> FilePath
-> get
-> set
-> MkOptDescr get set a
-> OptionField a
option FilePath
"" [FilePath
"ipid"]
         FilePath
"Installed package ID to compile this package as"
         ConfigFlags -> Flag FilePath
configIPID (\Flag FilePath
v ConfigFlags
flags -> ConfigFlags
flags {configIPID :: Flag FilePath
configIPID = Flag FilePath
v})
         (FilePath
-> MkOptDescr
     (ConfigFlags -> Flag FilePath)
     (Flag FilePath -> ConfigFlags -> ConfigFlags)
     ConfigFlags
forall b.
FilePath
-> FilePath
-> [FilePath]
-> FilePath
-> (b -> Flag FilePath)
-> (Flag FilePath -> b -> b)
-> OptDescr b
reqArgFlag FilePath
"IPID")

      ,FilePath
-> [FilePath]
-> FilePath
-> (ConfigFlags -> Flag FilePath)
-> (Flag FilePath -> ConfigFlags -> ConfigFlags)
-> MkOptDescr
     (ConfigFlags -> Flag FilePath)
     (Flag FilePath -> ConfigFlags -> ConfigFlags)
     ConfigFlags
-> OptionField ConfigFlags
forall get set a.
FilePath
-> [FilePath]
-> FilePath
-> get
-> set
-> MkOptDescr get set a
-> OptionField a
option FilePath
"" [FilePath
"cid"]
         FilePath
"Installed component ID to compile this component as"
         ((ComponentId -> FilePath) -> Flag ComponentId -> Flag FilePath
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ComponentId -> FilePath
forall a. Pretty a => a -> FilePath
prettyShow (Flag ComponentId -> Flag FilePath)
-> (ConfigFlags -> Flag ComponentId)
-> ConfigFlags
-> Flag FilePath
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ConfigFlags -> Flag ComponentId
configCID) (\Flag FilePath
v ConfigFlags
flags -> ConfigFlags
flags {configCID :: Flag ComponentId
configCID = (FilePath -> ComponentId) -> Flag FilePath -> Flag ComponentId
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap FilePath -> ComponentId
mkComponentId Flag FilePath
v})
         (FilePath
-> MkOptDescr
     (ConfigFlags -> Flag FilePath)
     (Flag FilePath -> ConfigFlags -> ConfigFlags)
     ConfigFlags
forall b.
FilePath
-> FilePath
-> [FilePath]
-> FilePath
-> (b -> Flag FilePath)
-> (Flag FilePath -> b -> b)
-> OptDescr b
reqArgFlag FilePath
"CID")

      ,FilePath
-> [FilePath]
-> FilePath
-> (ConfigFlags -> [FilePath])
-> ([FilePath] -> ConfigFlags -> ConfigFlags)
-> MkOptDescr
     (ConfigFlags -> [FilePath])
     ([FilePath] -> ConfigFlags -> ConfigFlags)
     ConfigFlags
-> OptionField ConfigFlags
forall get set a.
FilePath
-> [FilePath]
-> FilePath
-> get
-> set
-> MkOptDescr get set a
-> OptionField a
option FilePath
"" [FilePath
"extra-lib-dirs"]
         FilePath
"A list of directories to search for external libraries"
         ConfigFlags -> [FilePath]
configExtraLibDirs (\[FilePath]
v ConfigFlags
flags -> ConfigFlags
flags {configExtraLibDirs :: [FilePath]
configExtraLibDirs = [FilePath]
v})
         (FilePath
-> (FilePath -> [FilePath])
-> ([FilePath] -> [FilePath])
-> MkOptDescr
     (ConfigFlags -> [FilePath])
     ([FilePath] -> ConfigFlags -> ConfigFlags)
     ConfigFlags
forall b a.
Monoid b =>
FilePath
-> (FilePath -> b)
-> (b -> [FilePath])
-> MkOptDescr (a -> b) (b -> a -> a) a
reqArg' FilePath
"PATH" (\FilePath
x -> [FilePath
x]) [FilePath] -> [FilePath]
forall a. a -> a
id)

      ,FilePath
-> [FilePath]
-> FilePath
-> (ConfigFlags -> [FilePath])
-> ([FilePath] -> ConfigFlags -> ConfigFlags)
-> MkOptDescr
     (ConfigFlags -> [FilePath])
     ([FilePath] -> ConfigFlags -> ConfigFlags)
     ConfigFlags
-> OptionField ConfigFlags
forall get set a.
FilePath
-> [FilePath]
-> FilePath
-> get
-> set
-> MkOptDescr get set a
-> OptionField a
option FilePath
"" [FilePath
"extra-framework-dirs"]
         FilePath
"A list of directories to search for external frameworks (OS X only)"
         ConfigFlags -> [FilePath]
configExtraFrameworkDirs
         (\[FilePath]
v ConfigFlags
flags -> ConfigFlags
flags {configExtraFrameworkDirs :: [FilePath]
configExtraFrameworkDirs = [FilePath]
v})
         (FilePath
-> (FilePath -> [FilePath])
-> ([FilePath] -> [FilePath])
-> MkOptDescr
     (ConfigFlags -> [FilePath])
     ([FilePath] -> ConfigFlags -> ConfigFlags)
     ConfigFlags
forall b a.
Monoid b =>
FilePath
-> (FilePath -> b)
-> (b -> [FilePath])
-> MkOptDescr (a -> b) (b -> a -> a) a
reqArg' FilePath
"PATH" (\FilePath
x -> [FilePath
x]) [FilePath] -> [FilePath]
forall a. a -> a
id)

      ,FilePath
-> [FilePath]
-> FilePath
-> (ConfigFlags -> NubList FilePath)
-> (NubList FilePath -> ConfigFlags -> ConfigFlags)
-> MkOptDescr
     (ConfigFlags -> NubList FilePath)
     (NubList FilePath -> ConfigFlags -> ConfigFlags)
     ConfigFlags
-> OptionField ConfigFlags
forall get set a.
FilePath
-> [FilePath]
-> FilePath
-> get
-> set
-> MkOptDescr get set a
-> OptionField a
option FilePath
"" [FilePath
"extra-prog-path"]
         FilePath
"A list of directories to search for required programs (in addition to the normal search locations)"
         ConfigFlags -> NubList FilePath
configProgramPathExtra (\NubList FilePath
v ConfigFlags
flags -> ConfigFlags
flags {configProgramPathExtra :: NubList FilePath
configProgramPathExtra = NubList FilePath
v})
         (FilePath
-> (FilePath -> NubList FilePath)
-> (NubList FilePath -> [FilePath])
-> MkOptDescr
     (ConfigFlags -> NubList FilePath)
     (NubList FilePath -> ConfigFlags -> ConfigFlags)
     ConfigFlags
forall b a.
Monoid b =>
FilePath
-> (FilePath -> b)
-> (b -> [FilePath])
-> MkOptDescr (a -> b) (b -> a -> a) a
reqArg' FilePath
"PATH" (\FilePath
x -> [FilePath] -> NubList FilePath
forall a. Ord a => [a] -> NubList a
toNubList [FilePath
x]) NubList FilePath -> [FilePath]
forall a. NubList a -> [a]
fromNubList)

      ,FilePath
-> [FilePath]
-> FilePath
-> (ConfigFlags -> [Dependency])
-> ([Dependency] -> ConfigFlags -> ConfigFlags)
-> MkOptDescr
     (ConfigFlags -> [Dependency])
     ([Dependency] -> ConfigFlags -> ConfigFlags)
     ConfigFlags
-> OptionField ConfigFlags
forall get set a.
FilePath
-> [FilePath]
-> FilePath
-> get
-> set
-> MkOptDescr get set a
-> OptionField a
option FilePath
"" [FilePath
"constraint"]
         FilePath
"A list of additional constraints on the dependencies."
         ConfigFlags -> [Dependency]
configConstraints (\[Dependency]
v ConfigFlags
flags -> ConfigFlags
flags { configConstraints :: [Dependency]
configConstraints = [Dependency]
v})
         (FilePath
-> ReadE [Dependency]
-> ([Dependency] -> [FilePath])
-> MkOptDescr
     (ConfigFlags -> [Dependency])
     ([Dependency] -> ConfigFlags -> ConfigFlags)
     ConfigFlags
forall b a.
Monoid b =>
FilePath
-> ReadE b
-> (b -> [FilePath])
-> MkOptDescr (a -> b) (b -> a -> a) a
reqArg FilePath
"DEPENDENCY"
                 ((FilePath -> FilePath)
-> ParsecParser [Dependency] -> ReadE [Dependency]
forall a. (FilePath -> FilePath) -> ParsecParser a -> ReadE a
parsecToReadE (FilePath -> FilePath -> FilePath
forall a b. a -> b -> a
const FilePath
"dependency expected") ((\Dependency
x -> [Dependency
x]) (Dependency -> [Dependency])
-> ParsecParser Dependency -> ParsecParser [Dependency]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
`fmap` ParsecParser Dependency
forall a (m :: * -> *). (Parsec a, CabalParsing m) => m a
parsec))
                 ((Dependency -> FilePath) -> [Dependency] -> [FilePath]
forall a b. (a -> b) -> [a] -> [b]
map Dependency -> FilePath
forall a. Pretty a => a -> FilePath
prettyShow))

      ,FilePath
-> [FilePath]
-> FilePath
-> (ConfigFlags -> [GivenComponent])
-> ([GivenComponent] -> ConfigFlags -> ConfigFlags)
-> MkOptDescr
     (ConfigFlags -> [GivenComponent])
     ([GivenComponent] -> ConfigFlags -> ConfigFlags)
     ConfigFlags
-> OptionField ConfigFlags
forall get set a.
FilePath
-> [FilePath]
-> FilePath
-> get
-> set
-> MkOptDescr get set a
-> OptionField a
option FilePath
"" [FilePath
"dependency"]
         FilePath
"A list of exact dependencies. E.g., --dependency=\"void=void-0.5.8-177d5cdf20962d0581fe2e4932a6c309\""
         ConfigFlags -> [GivenComponent]
configDependencies (\[GivenComponent]
v ConfigFlags
flags -> ConfigFlags
flags { configDependencies :: [GivenComponent]
configDependencies = [GivenComponent]
v})
         (FilePath
-> ReadE [GivenComponent]
-> ([GivenComponent] -> [FilePath])
-> MkOptDescr
     (ConfigFlags -> [GivenComponent])
     ([GivenComponent] -> ConfigFlags -> ConfigFlags)
     ConfigFlags
forall b a.
Monoid b =>
FilePath
-> ReadE b
-> (b -> [FilePath])
-> MkOptDescr (a -> b) (b -> a -> a) a
reqArg FilePath
"NAME[:COMPONENT_NAME]=CID"
                 ((FilePath -> FilePath)
-> ParsecParser [GivenComponent] -> ReadE [GivenComponent]
forall a. (FilePath -> FilePath) -> ParsecParser a -> ReadE a
parsecToReadE (FilePath -> FilePath -> FilePath
forall a b. a -> b -> a
const FilePath
"dependency expected") ((\GivenComponent
x -> [GivenComponent
x]) (GivenComponent -> [GivenComponent])
-> ParsecParser GivenComponent -> ParsecParser [GivenComponent]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
`fmap` ParsecParser GivenComponent
parsecGivenComponent))
                 ((GivenComponent -> FilePath) -> [GivenComponent] -> [FilePath]
forall a b. (a -> b) -> [a] -> [b]
map (\(GivenComponent PackageName
pn LibraryName
cn ComponentId
cid) ->
                     PackageName -> FilePath
forall a. Pretty a => a -> FilePath
prettyShow PackageName
pn
                     FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ case LibraryName
cn of LibraryName
LMainLibName -> FilePath
""
                                   LSubLibName UnqualComponentName
n -> FilePath
":" FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ UnqualComponentName -> FilePath
forall a. Pretty a => a -> FilePath
prettyShow UnqualComponentName
n
                     FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
"=" FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ ComponentId -> FilePath
forall a. Pretty a => a -> FilePath
prettyShow ComponentId
cid)))

      ,FilePath
-> [FilePath]
-> FilePath
-> (ConfigFlags -> [(ModuleName, Module)])
-> ([(ModuleName, Module)] -> ConfigFlags -> ConfigFlags)
-> MkOptDescr
     (ConfigFlags -> [(ModuleName, Module)])
     ([(ModuleName, Module)] -> ConfigFlags -> ConfigFlags)
     ConfigFlags
-> OptionField ConfigFlags
forall get set a.
FilePath
-> [FilePath]
-> FilePath
-> get
-> set
-> MkOptDescr get set a
-> OptionField a
option FilePath
"" [FilePath
"instantiate-with"]
        FilePath
"A mapping of signature names to concrete module instantiations."
        ConfigFlags -> [(ModuleName, Module)]
configInstantiateWith (\[(ModuleName, Module)]
v ConfigFlags
flags -> ConfigFlags
flags { configInstantiateWith :: [(ModuleName, Module)]
configInstantiateWith = [(ModuleName, Module)]
v  })
        (FilePath
-> ReadE [(ModuleName, Module)]
-> ([(ModuleName, Module)] -> [FilePath])
-> MkOptDescr
     (ConfigFlags -> [(ModuleName, Module)])
     ([(ModuleName, Module)] -> ConfigFlags -> ConfigFlags)
     ConfigFlags
forall b a.
Monoid b =>
FilePath
-> ReadE b
-> (b -> [FilePath])
-> MkOptDescr (a -> b) (b -> a -> a) a
reqArg FilePath
"NAME=MOD"
            ((FilePath -> FilePath)
-> ParsecParser [(ModuleName, Module)]
-> ReadE [(ModuleName, Module)]
forall a. (FilePath -> FilePath) -> ParsecParser a -> ReadE a
parsecToReadE (FilePath
"Cannot parse module substitution: " FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++) (((ModuleName, Module) -> [(ModuleName, Module)])
-> ParsecParser (ModuleName, Module)
-> ParsecParser [(ModuleName, Module)]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ((ModuleName, Module)
-> [(ModuleName, Module)] -> [(ModuleName, Module)]
forall a. a -> [a] -> [a]
:[]) ParsecParser (ModuleName, Module)
parsecModSubstEntry))
            (((ModuleName, Module) -> FilePath)
-> [(ModuleName, Module)] -> [FilePath]
forall a b. (a -> b) -> [a] -> [b]
map (Style -> Doc -> FilePath
Disp.renderStyle Style
defaultStyle (Doc -> FilePath)
-> ((ModuleName, Module) -> Doc)
-> (ModuleName, Module)
-> FilePath
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (ModuleName, Module) -> Doc
dispModSubstEntry)))

      ,FilePath
-> [FilePath]
-> FilePath
-> (ConfigFlags -> Flag Bool)
-> (Flag Bool -> ConfigFlags -> ConfigFlags)
-> MkOptDescr
     (ConfigFlags -> Flag Bool)
     (Flag Bool -> ConfigFlags -> ConfigFlags)
     ConfigFlags
-> OptionField ConfigFlags
forall get set a.
FilePath
-> [FilePath]
-> FilePath
-> get
-> set
-> MkOptDescr get set a
-> OptionField a
option FilePath
"" [FilePath
"tests"]
         FilePath
"dependency checking and compilation for test suites listed in the package description file."
         ConfigFlags -> Flag Bool
configTests (\Flag Bool
v ConfigFlags
flags -> ConfigFlags
flags { configTests :: Flag Bool
configTests = Flag Bool
v })
         (FilePath
-> FilePath
-> MkOptDescr
     (ConfigFlags -> Flag Bool)
     (Flag Bool -> ConfigFlags -> ConfigFlags)
     ConfigFlags
forall a.
FilePath
-> FilePath -> MkOptDescr (a -> Flag Bool) (Flag Bool -> a -> a) a
boolOpt [] [])

      ,FilePath
-> [FilePath]
-> FilePath
-> (ConfigFlags -> Flag Bool)
-> (Flag Bool -> ConfigFlags -> ConfigFlags)
-> MkOptDescr
     (ConfigFlags -> Flag Bool)
     (Flag Bool -> ConfigFlags -> ConfigFlags)
     ConfigFlags
-> OptionField ConfigFlags
forall get set a.
FilePath
-> [FilePath]
-> FilePath
-> get
-> set
-> MkOptDescr get set a
-> OptionField a
option FilePath
"" [FilePath
"coverage"]
         FilePath
"build package with Haskell Program Coverage. (GHC only)"
         ConfigFlags -> Flag Bool
configCoverage (\Flag Bool
v ConfigFlags
flags -> ConfigFlags
flags { configCoverage :: Flag Bool
configCoverage = Flag Bool
v })
         (FilePath
-> FilePath
-> MkOptDescr
     (ConfigFlags -> Flag Bool)
     (Flag Bool -> ConfigFlags -> ConfigFlags)
     ConfigFlags
forall a.
FilePath
-> FilePath -> MkOptDescr (a -> Flag Bool) (Flag Bool -> a -> a) a
boolOpt [] [])

      ,FilePath
-> [FilePath]
-> FilePath
-> (ConfigFlags -> Flag Bool)
-> (Flag Bool -> ConfigFlags -> ConfigFlags)
-> MkOptDescr
     (ConfigFlags -> Flag Bool)
     (Flag Bool -> ConfigFlags -> ConfigFlags)
     ConfigFlags
-> OptionField ConfigFlags
forall get set a.
FilePath
-> [FilePath]
-> FilePath
-> get
-> set
-> MkOptDescr get set a
-> OptionField a
option FilePath
"" [FilePath
"library-coverage"]
         FilePath
"build package with Haskell Program Coverage. (GHC only) (DEPRECATED)"
         ConfigFlags -> Flag Bool
configLibCoverage (\Flag Bool
v ConfigFlags
flags -> ConfigFlags
flags { configLibCoverage :: Flag Bool
configLibCoverage = Flag Bool
v })
         (FilePath
-> FilePath
-> MkOptDescr
     (ConfigFlags -> Flag Bool)
     (Flag Bool -> ConfigFlags -> ConfigFlags)
     ConfigFlags
forall a.
FilePath
-> FilePath -> MkOptDescr (a -> Flag Bool) (Flag Bool -> a -> a) a
boolOpt [] [])

      ,FilePath
-> [FilePath]
-> FilePath
-> (ConfigFlags -> Flag Bool)
-> (Flag Bool -> ConfigFlags -> ConfigFlags)
-> MkOptDescr
     (ConfigFlags -> Flag Bool)
     (Flag Bool -> ConfigFlags -> ConfigFlags)
     ConfigFlags
-> OptionField ConfigFlags
forall get set a.
FilePath
-> [FilePath]
-> FilePath
-> get
-> set
-> MkOptDescr get set a
-> OptionField a
option FilePath
"" [FilePath
"exact-configuration"]
         FilePath
"All direct dependencies and flags are provided on the command line."
         ConfigFlags -> Flag Bool
configExactConfiguration
         (\Flag Bool
v ConfigFlags
flags -> ConfigFlags
flags { configExactConfiguration :: Flag Bool
configExactConfiguration = Flag Bool
v })
         MkOptDescr
  (ConfigFlags -> Flag Bool)
  (Flag Bool -> ConfigFlags -> ConfigFlags)
  ConfigFlags
forall a. MkOptDescr (a -> Flag Bool) (Flag Bool -> a -> a) a
trueArg

      ,FilePath
-> [FilePath]
-> FilePath
-> (ConfigFlags -> Flag Bool)
-> (Flag Bool -> ConfigFlags -> ConfigFlags)
-> MkOptDescr
     (ConfigFlags -> Flag Bool)
     (Flag Bool -> ConfigFlags -> ConfigFlags)
     ConfigFlags
-> OptionField ConfigFlags
forall get set a.
FilePath
-> [FilePath]
-> FilePath
-> get
-> set
-> MkOptDescr get set a
-> OptionField a
option FilePath
"" [FilePath
"benchmarks"]
         FilePath
"dependency checking and compilation for benchmarks listed in the package description file."
         ConfigFlags -> Flag Bool
configBenchmarks (\Flag Bool
v ConfigFlags
flags -> ConfigFlags
flags { configBenchmarks :: Flag Bool
configBenchmarks = Flag Bool
v })
         (FilePath
-> FilePath
-> MkOptDescr
     (ConfigFlags -> Flag Bool)
     (Flag Bool -> ConfigFlags -> ConfigFlags)
     ConfigFlags
forall a.
FilePath
-> FilePath -> MkOptDescr (a -> Flag Bool) (Flag Bool -> a -> a) a
boolOpt [] [])

      ,FilePath
-> [FilePath]
-> FilePath
-> (ConfigFlags -> Flag Bool)
-> (Flag Bool -> ConfigFlags -> ConfigFlags)
-> MkOptDescr
     (ConfigFlags -> Flag Bool)
     (Flag Bool -> ConfigFlags -> ConfigFlags)
     ConfigFlags
-> OptionField ConfigFlags
forall get set a.
FilePath
-> [FilePath]
-> FilePath
-> get
-> set
-> MkOptDescr get set a
-> OptionField a
option FilePath
"" [FilePath
"relocatable"]
         FilePath
"building a package that is relocatable. (GHC only)"
         ConfigFlags -> Flag Bool
configRelocatable (\Flag Bool
v ConfigFlags
flags -> ConfigFlags
flags { configRelocatable :: Flag Bool
configRelocatable = Flag Bool
v})
         (FilePath
-> FilePath
-> MkOptDescr
     (ConfigFlags -> Flag Bool)
     (Flag Bool -> ConfigFlags -> ConfigFlags)
     ConfigFlags
forall a.
FilePath
-> FilePath -> MkOptDescr (a -> Flag Bool) (Flag Bool -> a -> a) a
boolOpt [] [])

      ,FilePath
-> [FilePath]
-> FilePath
-> (ConfigFlags -> Flag Bool)
-> (Flag Bool -> ConfigFlags -> ConfigFlags)
-> MkOptDescr
     (ConfigFlags -> Flag Bool)
     (Flag Bool -> ConfigFlags -> ConfigFlags)
     ConfigFlags
-> OptionField ConfigFlags
forall get set a.
FilePath
-> [FilePath]
-> FilePath
-> get
-> set
-> MkOptDescr get set a
-> OptionField a
option FilePath
"" [FilePath
"response-files"]
         FilePath
"enable workaround for old versions of programs like \"ar\" that do not support @file arguments"
         ConfigFlags -> Flag Bool
configUseResponseFiles
         (\Flag Bool
v ConfigFlags
flags -> ConfigFlags
flags { configUseResponseFiles :: Flag Bool
configUseResponseFiles = Flag Bool
v })
         ((FilePath, [FilePath])
-> (FilePath, [FilePath])
-> MkOptDescr
     (ConfigFlags -> Flag Bool)
     (Flag Bool -> ConfigFlags -> ConfigFlags)
     ConfigFlags
forall a.
(FilePath, [FilePath])
-> (FilePath, [FilePath])
-> MkOptDescr (a -> Flag Bool) (Flag Bool -> a -> a) a
boolOpt' ([], [FilePath
"disable-response-files"]) ([], []))

      ,FilePath
-> [FilePath]
-> FilePath
-> (ConfigFlags -> Flag Bool)
-> (Flag Bool -> ConfigFlags -> ConfigFlags)
-> MkOptDescr
     (ConfigFlags -> Flag Bool)
     (Flag Bool -> ConfigFlags -> ConfigFlags)
     ConfigFlags
-> OptionField ConfigFlags
forall get set a.
FilePath
-> [FilePath]
-> FilePath
-> get
-> set
-> MkOptDescr get set a
-> OptionField a
option FilePath
"" [FilePath
"allow-depending-on-private-libs"]
         (  FilePath
"Allow depending on private libraries. "
         FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
"If set, the library visibility check MUST be done externally." )
         ConfigFlags -> Flag Bool
configAllowDependingOnPrivateLibs
         (\Flag Bool
v ConfigFlags
flags -> ConfigFlags
flags { configAllowDependingOnPrivateLibs :: Flag Bool
configAllowDependingOnPrivateLibs = Flag Bool
v })
         MkOptDescr
  (ConfigFlags -> Flag Bool)
  (Flag Bool -> ConfigFlags -> ConfigFlags)
  ConfigFlags
forall a. MkOptDescr (a -> Flag Bool) (Flag Bool -> a -> a) a
trueArg
      ]
  where
    liftInstallDirs :: OptionField (InstallDirs (Flag PathTemplate))
-> OptionField ConfigFlags
liftInstallDirs =
      (ConfigFlags -> InstallDirs (Flag PathTemplate))
-> (InstallDirs (Flag PathTemplate) -> ConfigFlags -> ConfigFlags)
-> OptionField (InstallDirs (Flag PathTemplate))
-> OptionField ConfigFlags
forall b a.
(b -> a) -> (a -> b -> b) -> OptionField a -> OptionField b
liftOption ConfigFlags -> InstallDirs (Flag PathTemplate)
configInstallDirs (\InstallDirs (Flag PathTemplate)
v ConfigFlags
flags -> ConfigFlags
flags { configInstallDirs :: InstallDirs (Flag PathTemplate)
configInstallDirs = InstallDirs (Flag PathTemplate)
v })

    reqPathTemplateArgFlag :: FilePath
-> FilePath
-> [FilePath]
-> FilePath
-> (a -> Flag PathTemplate)
-> (Flag PathTemplate -> a -> a)
-> OptDescr a
reqPathTemplateArgFlag FilePath
title FilePath
_sf [FilePath]
_lf FilePath
d a -> Flag PathTemplate
get Flag PathTemplate -> a -> a
set =
      FilePath
-> FilePath
-> [FilePath]
-> FilePath
-> (a -> Flag FilePath)
-> (Flag FilePath -> a -> a)
-> OptDescr a
forall b.
FilePath
-> FilePath
-> [FilePath]
-> FilePath
-> (b -> Flag FilePath)
-> (Flag FilePath -> b -> b)
-> OptDescr b
reqArgFlag FilePath
title FilePath
_sf [FilePath]
_lf FilePath
d
        ((PathTemplate -> FilePath) -> Flag PathTemplate -> Flag FilePath
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap PathTemplate -> FilePath
fromPathTemplate (Flag PathTemplate -> Flag FilePath)
-> (a -> Flag PathTemplate) -> a -> Flag FilePath
forall b c a. (b -> c) -> (a -> b) -> a -> c
. a -> Flag PathTemplate
get) (Flag PathTemplate -> a -> a
set (Flag PathTemplate -> a -> a)
-> (Flag FilePath -> Flag PathTemplate) -> Flag FilePath -> a -> a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (FilePath -> PathTemplate) -> Flag FilePath -> Flag PathTemplate
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap FilePath -> PathTemplate
toPathTemplate)

showFlagAssignment :: FlagAssignment -> [String]
showFlagAssignment :: FlagAssignment -> [FilePath]
showFlagAssignment = ((FlagName, Bool) -> FilePath) -> [(FlagName, Bool)] -> [FilePath]
forall a b. (a -> b) -> [a] -> [b]
map (FlagName, Bool) -> FilePath
showFlagValue' ([(FlagName, Bool)] -> [FilePath])
-> (FlagAssignment -> [(FlagName, Bool)])
-> FlagAssignment
-> [FilePath]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. FlagAssignment -> [(FlagName, Bool)]
unFlagAssignment
  where
    -- We can't use 'showFlagValue' because legacy custom-setups don't
    -- support the '+' prefix in --flags; so we omit the (redundant) + prefix;
    -- NB: we assume that we never have to set/enable '-'-prefixed flags here.
    showFlagValue' :: (FlagName, Bool) -> String
    showFlagValue' :: (FlagName, Bool) -> FilePath
showFlagValue' (FlagName
f, Bool
True)   =       FlagName -> FilePath
unFlagName FlagName
f
    showFlagValue' (FlagName
f, Bool
False)  = Char
'-' Char -> FilePath -> FilePath
forall a. a -> [a] -> [a]
: FlagName -> FilePath
unFlagName FlagName
f

readPackageDbList :: String -> [Maybe PackageDB]
readPackageDbList :: FilePath -> [Maybe PackageDB]
readPackageDbList FilePath
"clear"  = [Maybe PackageDB
forall a. Maybe a
Nothing]
readPackageDbList FilePath
"global" = [PackageDB -> Maybe PackageDB
forall a. a -> Maybe a
Just PackageDB
GlobalPackageDB]
readPackageDbList FilePath
"user"   = [PackageDB -> Maybe PackageDB
forall a. a -> Maybe a
Just PackageDB
UserPackageDB]
readPackageDbList FilePath
other    = [PackageDB -> Maybe PackageDB
forall a. a -> Maybe a
Just (FilePath -> PackageDB
SpecificPackageDB FilePath
other)]

showPackageDbList :: [Maybe PackageDB] -> [String]
showPackageDbList :: [Maybe PackageDB] -> [FilePath]
showPackageDbList = (Maybe PackageDB -> FilePath) -> [Maybe PackageDB] -> [FilePath]
forall a b. (a -> b) -> [a] -> [b]
map Maybe PackageDB -> FilePath
showPackageDb
  where
    showPackageDb :: Maybe PackageDB -> FilePath
showPackageDb Maybe PackageDB
Nothing                       = FilePath
"clear"
    showPackageDb (Just PackageDB
GlobalPackageDB)        = FilePath
"global"
    showPackageDb (Just PackageDB
UserPackageDB)          = FilePath
"user"
    showPackageDb (Just (SpecificPackageDB FilePath
db)) = FilePath
db

showProfDetailLevelFlag :: Flag ProfDetailLevel -> [String]
showProfDetailLevelFlag :: Flag ProfDetailLevel -> [FilePath]
showProfDetailLevelFlag Flag ProfDetailLevel
NoFlag    = []
showProfDetailLevelFlag (Flag ProfDetailLevel
dl) = [ProfDetailLevel -> FilePath
showProfDetailLevel ProfDetailLevel
dl]

parsecGivenComponent :: ParsecParser GivenComponent
parsecGivenComponent :: ParsecParser GivenComponent
parsecGivenComponent = do
  PackageName
pn <- ParsecParser PackageName
forall a (m :: * -> *). (Parsec a, CabalParsing m) => m a
parsec
  LibraryName
ln <- LibraryName -> ParsecParser LibraryName -> ParsecParser LibraryName
forall (m :: * -> *) a. Alternative m => a -> m a -> m a
P.option LibraryName
LMainLibName (ParsecParser LibraryName -> ParsecParser LibraryName)
-> ParsecParser LibraryName -> ParsecParser LibraryName
forall a b. (a -> b) -> a -> b
$ do
    Char
_ <- Char -> ParsecParser Char
forall (m :: * -> *). CharParsing m => Char -> m Char
P.char Char
':'
    UnqualComponentName
ucn <- ParsecParser UnqualComponentName
forall a (m :: * -> *). (Parsec a, CabalParsing m) => m a
parsec
    LibraryName -> ParsecParser LibraryName
forall (m :: * -> *) a. Monad m => a -> m a
return (LibraryName -> ParsecParser LibraryName)
-> LibraryName -> ParsecParser LibraryName
forall a b. (a -> b) -> a -> b
$ if UnqualComponentName -> FilePath
unUnqualComponentName UnqualComponentName
ucn FilePath -> FilePath -> Bool
forall a. Eq a => a -> a -> Bool
== PackageName -> FilePath
unPackageName PackageName
pn
             then LibraryName
LMainLibName
             else UnqualComponentName -> LibraryName
LSubLibName UnqualComponentName
ucn
  Char
_ <- Char -> ParsecParser Char
forall (m :: * -> *). CharParsing m => Char -> m Char
P.char Char
'='
  ComponentId
cid <- ParsecParser ComponentId
forall a (m :: * -> *). (Parsec a, CabalParsing m) => m a
parsec
  GivenComponent -> ParsecParser GivenComponent
forall (m :: * -> *) a. Monad m => a -> m a
return (GivenComponent -> ParsecParser GivenComponent)
-> GivenComponent -> ParsecParser GivenComponent
forall a b. (a -> b) -> a -> b
$ PackageName -> LibraryName -> ComponentId -> GivenComponent
GivenComponent PackageName
pn LibraryName
ln ComponentId
cid

installDirsOptions :: [OptionField (InstallDirs (Flag PathTemplate))]
installDirsOptions :: [OptionField (InstallDirs (Flag PathTemplate))]
installDirsOptions =
  [ FilePath
-> [FilePath]
-> FilePath
-> (InstallDirs (Flag PathTemplate) -> Flag PathTemplate)
-> (Flag PathTemplate
    -> InstallDirs (Flag PathTemplate)
    -> InstallDirs (Flag PathTemplate))
-> MkOptDescr
     (InstallDirs (Flag PathTemplate) -> Flag PathTemplate)
     (Flag PathTemplate
      -> InstallDirs (Flag PathTemplate)
      -> InstallDirs (Flag PathTemplate))
     (InstallDirs (Flag PathTemplate))
-> OptionField (InstallDirs (Flag PathTemplate))
forall get set a.
FilePath
-> [FilePath]
-> FilePath
-> get
-> set
-> MkOptDescr get set a
-> OptionField a
option FilePath
"" [FilePath
"prefix"]
      FilePath
"bake this prefix in preparation of installation"
      InstallDirs (Flag PathTemplate) -> Flag PathTemplate
forall dir. InstallDirs dir -> dir
prefix (\Flag PathTemplate
v InstallDirs (Flag PathTemplate)
flags -> InstallDirs (Flag PathTemplate)
flags { prefix :: Flag PathTemplate
prefix = Flag PathTemplate
v })
      MkOptDescr
  (InstallDirs (Flag PathTemplate) -> Flag PathTemplate)
  (Flag PathTemplate
   -> InstallDirs (Flag PathTemplate)
   -> InstallDirs (Flag PathTemplate))
  (InstallDirs (Flag PathTemplate))
forall a.
FilePath
-> [FilePath]
-> FilePath
-> (a -> Flag PathTemplate)
-> (Flag PathTemplate -> a -> a)
-> OptDescr a
installDirArg

  , FilePath
-> [FilePath]
-> FilePath
-> (InstallDirs (Flag PathTemplate) -> Flag PathTemplate)
-> (Flag PathTemplate
    -> InstallDirs (Flag PathTemplate)
    -> InstallDirs (Flag PathTemplate))
-> MkOptDescr
     (InstallDirs (Flag PathTemplate) -> Flag PathTemplate)
     (Flag PathTemplate
      -> InstallDirs (Flag PathTemplate)
      -> InstallDirs (Flag PathTemplate))
     (InstallDirs (Flag PathTemplate))
-> OptionField (InstallDirs (Flag PathTemplate))
forall get set a.
FilePath
-> [FilePath]
-> FilePath
-> get
-> set
-> MkOptDescr get set a
-> OptionField a
option FilePath
"" [FilePath
"bindir"]
      FilePath
"installation directory for executables"
      InstallDirs (Flag PathTemplate) -> Flag PathTemplate
forall dir. InstallDirs dir -> dir
bindir (\Flag PathTemplate
v InstallDirs (Flag PathTemplate)
flags -> InstallDirs (Flag PathTemplate)
flags { bindir :: Flag PathTemplate
bindir = Flag PathTemplate
v })
      MkOptDescr
  (InstallDirs (Flag PathTemplate) -> Flag PathTemplate)
  (Flag PathTemplate
   -> InstallDirs (Flag PathTemplate)
   -> InstallDirs (Flag PathTemplate))
  (InstallDirs (Flag PathTemplate))
forall a.
FilePath
-> [FilePath]
-> FilePath
-> (a -> Flag PathTemplate)
-> (Flag PathTemplate -> a -> a)
-> OptDescr a
installDirArg

  , FilePath
-> [FilePath]
-> FilePath
-> (InstallDirs (Flag PathTemplate) -> Flag PathTemplate)
-> (Flag PathTemplate
    -> InstallDirs (Flag PathTemplate)
    -> InstallDirs (Flag PathTemplate))
-> MkOptDescr
     (InstallDirs (Flag PathTemplate) -> Flag PathTemplate)
     (Flag PathTemplate
      -> InstallDirs (Flag PathTemplate)
      -> InstallDirs (Flag PathTemplate))
     (InstallDirs (Flag PathTemplate))
-> OptionField (InstallDirs (Flag PathTemplate))
forall get set a.
FilePath
-> [FilePath]
-> FilePath
-> get
-> set
-> MkOptDescr get set a
-> OptionField a
option FilePath
"" [FilePath
"libdir"]
      FilePath
"installation directory for libraries"
      InstallDirs (Flag PathTemplate) -> Flag PathTemplate
forall dir. InstallDirs dir -> dir
libdir (\Flag PathTemplate
v InstallDirs (Flag PathTemplate)
flags -> InstallDirs (Flag PathTemplate)
flags { libdir :: Flag PathTemplate
libdir = Flag PathTemplate
v })
      MkOptDescr
  (InstallDirs (Flag PathTemplate) -> Flag PathTemplate)
  (Flag PathTemplate
   -> InstallDirs (Flag PathTemplate)
   -> InstallDirs (Flag PathTemplate))
  (InstallDirs (Flag PathTemplate))
forall a.
FilePath
-> [FilePath]
-> FilePath
-> (a -> Flag PathTemplate)
-> (Flag PathTemplate -> a -> a)
-> OptDescr a
installDirArg

  , FilePath
-> [FilePath]
-> FilePath
-> (InstallDirs (Flag PathTemplate) -> Flag PathTemplate)
-> (Flag PathTemplate
    -> InstallDirs (Flag PathTemplate)
    -> InstallDirs (Flag PathTemplate))
-> MkOptDescr
     (InstallDirs (Flag PathTemplate) -> Flag PathTemplate)
     (Flag PathTemplate
      -> InstallDirs (Flag PathTemplate)
      -> InstallDirs (Flag PathTemplate))
     (InstallDirs (Flag PathTemplate))
-> OptionField (InstallDirs (Flag PathTemplate))
forall get set a.
FilePath
-> [FilePath]
-> FilePath
-> get
-> set
-> MkOptDescr get set a
-> OptionField a
option FilePath
"" [FilePath
"libsubdir"]
      FilePath
"subdirectory of libdir in which libs are installed"
      InstallDirs (Flag PathTemplate) -> Flag PathTemplate
forall dir. InstallDirs dir -> dir
libsubdir (\Flag PathTemplate
v InstallDirs (Flag PathTemplate)
flags -> InstallDirs (Flag PathTemplate)
flags { libsubdir :: Flag PathTemplate
libsubdir = Flag PathTemplate
v })
      MkOptDescr
  (InstallDirs (Flag PathTemplate) -> Flag PathTemplate)
  (Flag PathTemplate
   -> InstallDirs (Flag PathTemplate)
   -> InstallDirs (Flag PathTemplate))
  (InstallDirs (Flag PathTemplate))
forall a.
FilePath
-> [FilePath]
-> FilePath
-> (a -> Flag PathTemplate)
-> (Flag PathTemplate -> a -> a)
-> OptDescr a
installDirArg

  , FilePath
-> [FilePath]
-> FilePath
-> (InstallDirs (Flag PathTemplate) -> Flag PathTemplate)
-> (Flag PathTemplate
    -> InstallDirs (Flag PathTemplate)
    -> InstallDirs (Flag PathTemplate))
-> MkOptDescr
     (InstallDirs (Flag PathTemplate) -> Flag PathTemplate)
     (Flag PathTemplate
      -> InstallDirs (Flag PathTemplate)
      -> InstallDirs (Flag PathTemplate))
     (InstallDirs (Flag PathTemplate))
-> OptionField (InstallDirs (Flag PathTemplate))
forall get set a.
FilePath
-> [FilePath]
-> FilePath
-> get
-> set
-> MkOptDescr get set a
-> OptionField a
option FilePath
"" [FilePath
"dynlibdir"]
      FilePath
"installation directory for dynamic libraries"
      InstallDirs (Flag PathTemplate) -> Flag PathTemplate
forall dir. InstallDirs dir -> dir
dynlibdir (\Flag PathTemplate
v InstallDirs (Flag PathTemplate)
flags -> InstallDirs (Flag PathTemplate)
flags { dynlibdir :: Flag PathTemplate
dynlibdir = Flag PathTemplate
v })
      MkOptDescr
  (InstallDirs (Flag PathTemplate) -> Flag PathTemplate)
  (Flag PathTemplate
   -> InstallDirs (Flag PathTemplate)
   -> InstallDirs (Flag PathTemplate))
  (InstallDirs (Flag PathTemplate))
forall a.
FilePath
-> [FilePath]
-> FilePath
-> (a -> Flag PathTemplate)
-> (Flag PathTemplate -> a -> a)
-> OptDescr a
installDirArg

  , FilePath
-> [FilePath]
-> FilePath
-> (InstallDirs (Flag PathTemplate) -> Flag PathTemplate)
-> (Flag PathTemplate
    -> InstallDirs (Flag PathTemplate)
    -> InstallDirs (Flag PathTemplate))
-> MkOptDescr
     (InstallDirs (Flag PathTemplate) -> Flag PathTemplate)
     (Flag PathTemplate
      -> InstallDirs (Flag PathTemplate)
      -> InstallDirs (Flag PathTemplate))
     (InstallDirs (Flag PathTemplate))
-> OptionField (InstallDirs (Flag PathTemplate))
forall get set a.
FilePath
-> [FilePath]
-> FilePath
-> get
-> set
-> MkOptDescr get set a
-> OptionField a
option FilePath
"" [FilePath
"libexecdir"]
      FilePath
"installation directory for program executables"
      InstallDirs (Flag PathTemplate) -> Flag PathTemplate
forall dir. InstallDirs dir -> dir
libexecdir (\Flag PathTemplate
v InstallDirs (Flag PathTemplate)
flags -> InstallDirs (Flag PathTemplate)
flags { libexecdir :: Flag PathTemplate
libexecdir = Flag PathTemplate
v })
      MkOptDescr
  (InstallDirs (Flag PathTemplate) -> Flag PathTemplate)
  (Flag PathTemplate
   -> InstallDirs (Flag PathTemplate)
   -> InstallDirs (Flag PathTemplate))
  (InstallDirs (Flag PathTemplate))
forall a.
FilePath
-> [FilePath]
-> FilePath
-> (a -> Flag PathTemplate)
-> (Flag PathTemplate -> a -> a)
-> OptDescr a
installDirArg

  , FilePath
-> [FilePath]
-> FilePath
-> (InstallDirs (Flag PathTemplate) -> Flag PathTemplate)
-> (Flag PathTemplate
    -> InstallDirs (Flag PathTemplate)
    -> InstallDirs (Flag PathTemplate))
-> MkOptDescr
     (InstallDirs (Flag PathTemplate) -> Flag PathTemplate)
     (Flag PathTemplate
      -> InstallDirs (Flag PathTemplate)
      -> InstallDirs (Flag PathTemplate))
     (InstallDirs (Flag PathTemplate))
-> OptionField (InstallDirs (Flag PathTemplate))
forall get set a.
FilePath
-> [FilePath]
-> FilePath
-> get
-> set
-> MkOptDescr get set a
-> OptionField a
option FilePath
"" [FilePath
"libexecsubdir"]
      FilePath
"subdirectory of libexecdir in which private executables are installed"
      InstallDirs (Flag PathTemplate) -> Flag PathTemplate
forall dir. InstallDirs dir -> dir
libexecsubdir (\Flag PathTemplate
v InstallDirs (Flag PathTemplate)
flags -> InstallDirs (Flag PathTemplate)
flags { libexecsubdir :: Flag PathTemplate
libexecsubdir = Flag PathTemplate
v })
      MkOptDescr
  (InstallDirs (Flag PathTemplate) -> Flag PathTemplate)
  (Flag PathTemplate
   -> InstallDirs (Flag PathTemplate)
   -> InstallDirs (Flag PathTemplate))
  (InstallDirs (Flag PathTemplate))
forall a.
FilePath
-> [FilePath]
-> FilePath
-> (a -> Flag PathTemplate)
-> (Flag PathTemplate -> a -> a)
-> OptDescr a
installDirArg

  , FilePath
-> [FilePath]
-> FilePath
-> (InstallDirs (Flag PathTemplate) -> Flag PathTemplate)
-> (Flag PathTemplate
    -> InstallDirs (Flag PathTemplate)
    -> InstallDirs (Flag PathTemplate))
-> MkOptDescr
     (InstallDirs (Flag PathTemplate) -> Flag PathTemplate)
     (Flag PathTemplate
      -> InstallDirs (Flag PathTemplate)
      -> InstallDirs (Flag PathTemplate))
     (InstallDirs (Flag PathTemplate))
-> OptionField (InstallDirs (Flag PathTemplate))
forall get set a.
FilePath
-> [FilePath]
-> FilePath
-> get
-> set
-> MkOptDescr get set a
-> OptionField a
option FilePath
"" [FilePath
"datadir"]
      FilePath
"installation directory for read-only data"
      InstallDirs (Flag PathTemplate) -> Flag PathTemplate
forall dir. InstallDirs dir -> dir
datadir (\Flag PathTemplate
v InstallDirs (Flag PathTemplate)
flags -> InstallDirs (Flag PathTemplate)
flags { datadir :: Flag PathTemplate
datadir = Flag PathTemplate
v })
      MkOptDescr
  (InstallDirs (Flag PathTemplate) -> Flag PathTemplate)
  (Flag PathTemplate
   -> InstallDirs (Flag PathTemplate)
   -> InstallDirs (Flag PathTemplate))
  (InstallDirs (Flag PathTemplate))
forall a.
FilePath
-> [FilePath]
-> FilePath
-> (a -> Flag PathTemplate)
-> (Flag PathTemplate -> a -> a)
-> OptDescr a
installDirArg

  , FilePath
-> [FilePath]
-> FilePath
-> (InstallDirs (Flag PathTemplate) -> Flag PathTemplate)
-> (Flag PathTemplate
    -> InstallDirs (Flag PathTemplate)
    -> InstallDirs (Flag PathTemplate))
-> MkOptDescr
     (InstallDirs (Flag PathTemplate) -> Flag PathTemplate)
     (Flag PathTemplate
      -> InstallDirs (Flag PathTemplate)
      -> InstallDirs (Flag PathTemplate))
     (InstallDirs (Flag PathTemplate))
-> OptionField (InstallDirs (Flag PathTemplate))
forall get set a.
FilePath
-> [FilePath]
-> FilePath
-> get
-> set
-> MkOptDescr get set a
-> OptionField a
option FilePath
"" [FilePath
"datasubdir"]
      FilePath
"subdirectory of datadir in which data files are installed"
      InstallDirs (Flag PathTemplate) -> Flag PathTemplate
forall dir. InstallDirs dir -> dir
datasubdir (\Flag PathTemplate
v InstallDirs (Flag PathTemplate)
flags -> InstallDirs (Flag PathTemplate)
flags { datasubdir :: Flag PathTemplate
datasubdir = Flag PathTemplate
v })
      MkOptDescr
  (InstallDirs (Flag PathTemplate) -> Flag PathTemplate)
  (Flag PathTemplate
   -> InstallDirs (Flag PathTemplate)
   -> InstallDirs (Flag PathTemplate))
  (InstallDirs (Flag PathTemplate))
forall a.
FilePath
-> [FilePath]
-> FilePath
-> (a -> Flag PathTemplate)
-> (Flag PathTemplate -> a -> a)
-> OptDescr a
installDirArg

  , FilePath
-> [FilePath]
-> FilePath
-> (InstallDirs (Flag PathTemplate) -> Flag PathTemplate)
-> (Flag PathTemplate
    -> InstallDirs (Flag PathTemplate)
    -> InstallDirs (Flag PathTemplate))
-> MkOptDescr
     (InstallDirs (Flag PathTemplate) -> Flag PathTemplate)
     (Flag PathTemplate
      -> InstallDirs (Flag PathTemplate)
      -> InstallDirs (Flag PathTemplate))
     (InstallDirs (Flag PathTemplate))
-> OptionField (InstallDirs (Flag PathTemplate))
forall get set a.
FilePath
-> [FilePath]
-> FilePath
-> get
-> set
-> MkOptDescr get set a
-> OptionField a
option FilePath
"" [FilePath
"docdir"]
      FilePath
"installation directory for documentation"
      InstallDirs (Flag PathTemplate) -> Flag PathTemplate
forall dir. InstallDirs dir -> dir
docdir (\Flag PathTemplate
v InstallDirs (Flag PathTemplate)
flags -> InstallDirs (Flag PathTemplate)
flags { docdir :: Flag PathTemplate
docdir = Flag PathTemplate
v })
      MkOptDescr
  (InstallDirs (Flag PathTemplate) -> Flag PathTemplate)
  (Flag PathTemplate
   -> InstallDirs (Flag PathTemplate)
   -> InstallDirs (Flag PathTemplate))
  (InstallDirs (Flag PathTemplate))
forall a.
FilePath
-> [FilePath]
-> FilePath
-> (a -> Flag PathTemplate)
-> (Flag PathTemplate -> a -> a)
-> OptDescr a
installDirArg

  , FilePath
-> [FilePath]
-> FilePath
-> (InstallDirs (Flag PathTemplate) -> Flag PathTemplate)
-> (Flag PathTemplate
    -> InstallDirs (Flag PathTemplate)
    -> InstallDirs (Flag PathTemplate))
-> MkOptDescr
     (InstallDirs (Flag PathTemplate) -> Flag PathTemplate)
     (Flag PathTemplate
      -> InstallDirs (Flag PathTemplate)
      -> InstallDirs (Flag PathTemplate))
     (InstallDirs (Flag PathTemplate))
-> OptionField (InstallDirs (Flag PathTemplate))
forall get set a.
FilePath
-> [FilePath]
-> FilePath
-> get
-> set
-> MkOptDescr get set a
-> OptionField a
option FilePath
"" [FilePath
"htmldir"]
      FilePath
"installation directory for HTML documentation"
      InstallDirs (Flag PathTemplate) -> Flag PathTemplate
forall dir. InstallDirs dir -> dir
htmldir (\Flag PathTemplate
v InstallDirs (Flag PathTemplate)
flags -> InstallDirs (Flag PathTemplate)
flags { htmldir :: Flag PathTemplate
htmldir = Flag PathTemplate
v })
      MkOptDescr
  (InstallDirs (Flag PathTemplate) -> Flag PathTemplate)
  (Flag PathTemplate
   -> InstallDirs (Flag PathTemplate)
   -> InstallDirs (Flag PathTemplate))
  (InstallDirs (Flag PathTemplate))
forall a.
FilePath
-> [FilePath]
-> FilePath
-> (a -> Flag PathTemplate)
-> (Flag PathTemplate -> a -> a)
-> OptDescr a
installDirArg

  , FilePath
-> [FilePath]
-> FilePath
-> (InstallDirs (Flag PathTemplate) -> Flag PathTemplate)
-> (Flag PathTemplate
    -> InstallDirs (Flag PathTemplate)
    -> InstallDirs (Flag PathTemplate))
-> MkOptDescr
     (InstallDirs (Flag PathTemplate) -> Flag PathTemplate)
     (Flag PathTemplate
      -> InstallDirs (Flag PathTemplate)
      -> InstallDirs (Flag PathTemplate))
     (InstallDirs (Flag PathTemplate))
-> OptionField (InstallDirs (Flag PathTemplate))
forall get set a.
FilePath
-> [FilePath]
-> FilePath
-> get
-> set
-> MkOptDescr get set a
-> OptionField a
option FilePath
"" [FilePath
"haddockdir"]
      FilePath
"installation directory for haddock interfaces"
      InstallDirs (Flag PathTemplate) -> Flag PathTemplate
forall dir. InstallDirs dir -> dir
haddockdir (\Flag PathTemplate
v InstallDirs (Flag PathTemplate)
flags -> InstallDirs (Flag PathTemplate)
flags { haddockdir :: Flag PathTemplate
haddockdir = Flag PathTemplate
v })
      MkOptDescr
  (InstallDirs (Flag PathTemplate) -> Flag PathTemplate)
  (Flag PathTemplate
   -> InstallDirs (Flag PathTemplate)
   -> InstallDirs (Flag PathTemplate))
  (InstallDirs (Flag PathTemplate))
forall a.
FilePath
-> [FilePath]
-> FilePath
-> (a -> Flag PathTemplate)
-> (Flag PathTemplate -> a -> a)
-> OptDescr a
installDirArg

  , FilePath
-> [FilePath]
-> FilePath
-> (InstallDirs (Flag PathTemplate) -> Flag PathTemplate)
-> (Flag PathTemplate
    -> InstallDirs (Flag PathTemplate)
    -> InstallDirs (Flag PathTemplate))
-> MkOptDescr
     (InstallDirs (Flag PathTemplate) -> Flag PathTemplate)
     (Flag PathTemplate
      -> InstallDirs (Flag PathTemplate)
      -> InstallDirs (Flag PathTemplate))
     (InstallDirs (Flag PathTemplate))
-> OptionField (InstallDirs (Flag PathTemplate))
forall get set a.
FilePath
-> [FilePath]
-> FilePath
-> get
-> set
-> MkOptDescr get set a
-> OptionField a
option FilePath
"" [FilePath
"sysconfdir"]
      FilePath
"installation directory for configuration files"
      InstallDirs (Flag PathTemplate) -> Flag PathTemplate
forall dir. InstallDirs dir -> dir
sysconfdir (\Flag PathTemplate
v InstallDirs (Flag PathTemplate)
flags -> InstallDirs (Flag PathTemplate)
flags { sysconfdir :: Flag PathTemplate
sysconfdir = Flag PathTemplate
v })
      MkOptDescr
  (InstallDirs (Flag PathTemplate) -> Flag PathTemplate)
  (Flag PathTemplate
   -> InstallDirs (Flag PathTemplate)
   -> InstallDirs (Flag PathTemplate))
  (InstallDirs (Flag PathTemplate))
forall a.
FilePath
-> [FilePath]
-> FilePath
-> (a -> Flag PathTemplate)
-> (Flag PathTemplate -> a -> a)
-> OptDescr a
installDirArg
  ]
  where
    installDirArg :: FilePath
-> [FilePath]
-> FilePath
-> (a -> Flag PathTemplate)
-> (Flag PathTemplate -> a -> a)
-> OptDescr a
installDirArg FilePath
_sf [FilePath]
_lf FilePath
d a -> Flag PathTemplate
get Flag PathTemplate -> a -> a
set =
      FilePath
-> FilePath
-> [FilePath]
-> FilePath
-> (a -> Flag FilePath)
-> (Flag FilePath -> a -> a)
-> OptDescr a
forall b.
FilePath
-> FilePath
-> [FilePath]
-> FilePath
-> (b -> Flag FilePath)
-> (Flag FilePath -> b -> b)
-> OptDescr b
reqArgFlag FilePath
"DIR" FilePath
_sf [FilePath]
_lf FilePath
d
        ((PathTemplate -> FilePath) -> Flag PathTemplate -> Flag FilePath
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap PathTemplate -> FilePath
fromPathTemplate (Flag PathTemplate -> Flag FilePath)
-> (a -> Flag PathTemplate) -> a -> Flag FilePath
forall b c a. (b -> c) -> (a -> b) -> a -> c
. a -> Flag PathTemplate
get) (Flag PathTemplate -> a -> a
set (Flag PathTemplate -> a -> a)
-> (Flag FilePath -> Flag PathTemplate) -> Flag FilePath -> a -> a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (FilePath -> PathTemplate) -> Flag FilePath -> Flag PathTemplate
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap FilePath -> PathTemplate
toPathTemplate)

emptyConfigFlags :: ConfigFlags
emptyConfigFlags :: ConfigFlags
emptyConfigFlags = ConfigFlags
forall a. Monoid a => a
mempty

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

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

-- ------------------------------------------------------------
-- * Copy flags
-- ------------------------------------------------------------

-- | Flags to @copy@: (destdir, copy-prefix (backwards compat), verbosity)
data CopyFlags = CopyFlags {
    CopyFlags -> Flag CopyDest
copyDest      :: Flag CopyDest,
    CopyFlags -> Flag FilePath
copyDistPref  :: Flag FilePath,
    CopyFlags -> Flag Verbosity
copyVerbosity :: Flag Verbosity,
    -- This is the same hack as in 'buildArgs'.  But I (ezyang) don't
    -- think it's a hack, it's the right way to make hooks more robust
    -- TODO: Stop using this eventually when 'UserHooks' gets changed
    CopyFlags -> [FilePath]
copyArgs :: [String],
    CopyFlags -> Flag FilePath
copyCabalFilePath :: Flag FilePath
  }
  deriving (Int -> CopyFlags -> FilePath -> FilePath
[CopyFlags] -> FilePath -> FilePath
CopyFlags -> FilePath
(Int -> CopyFlags -> FilePath -> FilePath)
-> (CopyFlags -> FilePath)
-> ([CopyFlags] -> FilePath -> FilePath)
-> Show CopyFlags
forall a.
(Int -> a -> FilePath -> FilePath)
-> (a -> FilePath) -> ([a] -> FilePath -> FilePath) -> Show a
showList :: [CopyFlags] -> FilePath -> FilePath
$cshowList :: [CopyFlags] -> FilePath -> FilePath
show :: CopyFlags -> FilePath
$cshow :: CopyFlags -> FilePath
showsPrec :: Int -> CopyFlags -> FilePath -> FilePath
$cshowsPrec :: Int -> CopyFlags -> FilePath -> FilePath
Show, (forall x. CopyFlags -> Rep CopyFlags x)
-> (forall x. Rep CopyFlags x -> CopyFlags) -> Generic CopyFlags
forall x. Rep CopyFlags x -> CopyFlags
forall x. CopyFlags -> Rep CopyFlags x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep CopyFlags x -> CopyFlags
$cfrom :: forall x. CopyFlags -> Rep CopyFlags x
Generic)

defaultCopyFlags :: CopyFlags
defaultCopyFlags :: CopyFlags
defaultCopyFlags  = CopyFlags :: Flag CopyDest
-> Flag FilePath
-> Flag Verbosity
-> [FilePath]
-> Flag FilePath
-> CopyFlags
CopyFlags {
    copyDest :: Flag CopyDest
copyDest      = CopyDest -> Flag CopyDest
forall a. a -> Flag a
Flag CopyDest
NoCopyDest,
    copyDistPref :: Flag FilePath
copyDistPref  = Flag FilePath
forall a. Flag a
NoFlag,
    copyVerbosity :: Flag Verbosity
copyVerbosity = Verbosity -> Flag Verbosity
forall a. a -> Flag a
Flag Verbosity
normal,
    copyArgs :: [FilePath]
copyArgs      = [],
    copyCabalFilePath :: Flag FilePath
copyCabalFilePath = Flag FilePath
forall a. Monoid a => a
mempty
  }

copyCommand :: CommandUI CopyFlags
copyCommand :: CommandUI CopyFlags
copyCommand = CommandUI :: forall flags.
FilePath
-> FilePath
-> (FilePath -> FilePath)
-> Maybe (FilePath -> FilePath)
-> Maybe (FilePath -> FilePath)
-> flags
-> (ShowOrParseArgs -> [OptionField flags])
-> CommandUI flags
CommandUI
  { commandName :: FilePath
commandName         = FilePath
"copy"
  , commandSynopsis :: FilePath
commandSynopsis     = FilePath
"Copy the files of all/specific components to install locations."
  , commandDescription :: Maybe (FilePath -> FilePath)
commandDescription  = (FilePath -> FilePath) -> Maybe (FilePath -> FilePath)
forall a. a -> Maybe a
Just ((FilePath -> FilePath) -> Maybe (FilePath -> FilePath))
-> (FilePath -> FilePath) -> Maybe (FilePath -> FilePath)
forall a b. (a -> b) -> a -> b
$ \FilePath
_ -> FilePath -> FilePath
wrapText (FilePath -> FilePath) -> FilePath -> FilePath
forall a b. (a -> b) -> a -> b
$
          FilePath
"Components encompass executables and libraries. "
       FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
"Does not call register, and allows a prefix at install time. "
       FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
"Without the --destdir flag, configure determines location.\n"
  , commandNotes :: Maybe (FilePath -> FilePath)
commandNotes        = (FilePath -> FilePath) -> Maybe (FilePath -> FilePath)
forall a. a -> Maybe a
Just ((FilePath -> FilePath) -> Maybe (FilePath -> FilePath))
-> (FilePath -> FilePath) -> Maybe (FilePath -> FilePath)
forall a b. (a -> b) -> a -> b
$ \FilePath
pname ->
       FilePath
"Examples:\n"
        FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
"  " FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
pname FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
" copy           "
        FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
"    All the components in the package\n"
        FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
"  " FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
pname FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
" copy foo       "
        FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
"    A component (i.e. lib, exe, test suite)"
  , commandUsage :: FilePath -> FilePath
commandUsage        = FilePath -> [FilePath] -> FilePath -> FilePath
usageAlternatives FilePath
"copy" ([FilePath] -> FilePath -> FilePath)
-> [FilePath] -> FilePath -> FilePath
forall a b. (a -> b) -> a -> b
$
      [ FilePath
"[FLAGS]"
      , FilePath
"COMPONENTS [FLAGS]"
      ]
  , commandDefaultFlags :: CopyFlags
commandDefaultFlags = CopyFlags
defaultCopyFlags
  , commandOptions :: ShowOrParseArgs -> [OptionField CopyFlags]
commandOptions      = \ShowOrParseArgs
showOrParseArgs -> case ShowOrParseArgs
showOrParseArgs of
      ShowOrParseArgs
ShowArgs -> (OptionField CopyFlags -> Bool)
-> [OptionField CopyFlags] -> [OptionField CopyFlags]
forall a. (a -> Bool) -> [a] -> [a]
filter ((FilePath -> [FilePath] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`notElem` [FilePath
"target-package-db"])
                          (FilePath -> Bool)
-> (OptionField CopyFlags -> FilePath)
-> OptionField CopyFlags
-> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. OptionField CopyFlags -> FilePath
forall a. OptionField a -> FilePath
optionName) ([OptionField CopyFlags] -> [OptionField CopyFlags])
-> [OptionField CopyFlags] -> [OptionField CopyFlags]
forall a b. (a -> b) -> a -> b
$ ShowOrParseArgs -> [OptionField CopyFlags]
copyOptions ShowOrParseArgs
ShowArgs
      ShowOrParseArgs
ParseArgs -> ShowOrParseArgs -> [OptionField CopyFlags]
copyOptions ShowOrParseArgs
ParseArgs
}

copyOptions ::  ShowOrParseArgs -> [OptionField CopyFlags]
copyOptions :: ShowOrParseArgs -> [OptionField CopyFlags]
copyOptions ShowOrParseArgs
showOrParseArgs =
  [(CopyFlags -> Flag Verbosity)
-> (Flag Verbosity -> CopyFlags -> CopyFlags)
-> OptionField CopyFlags
forall flags.
(flags -> Flag Verbosity)
-> (Flag Verbosity -> flags -> flags) -> OptionField flags
optionVerbosity CopyFlags -> Flag Verbosity
copyVerbosity (\Flag Verbosity
v CopyFlags
flags -> CopyFlags
flags { copyVerbosity :: Flag Verbosity
copyVerbosity = Flag Verbosity
v })

  ,(CopyFlags -> Flag FilePath)
-> (Flag FilePath -> CopyFlags -> CopyFlags)
-> ShowOrParseArgs
-> OptionField CopyFlags
forall flags.
(flags -> Flag FilePath)
-> (Flag FilePath -> flags -> flags)
-> ShowOrParseArgs
-> OptionField flags
optionDistPref
    CopyFlags -> Flag FilePath
copyDistPref (\Flag FilePath
d CopyFlags
flags -> CopyFlags
flags { copyDistPref :: Flag FilePath
copyDistPref = Flag FilePath
d })
    ShowOrParseArgs
showOrParseArgs

  ,FilePath
-> [FilePath]
-> FilePath
-> (CopyFlags -> Flag CopyDest)
-> (Flag CopyDest -> CopyFlags -> CopyFlags)
-> MkOptDescr
     (CopyFlags -> Flag CopyDest)
     (Flag CopyDest -> CopyFlags -> CopyFlags)
     CopyFlags
-> OptionField CopyFlags
forall get set a.
FilePath
-> [FilePath]
-> FilePath
-> get
-> set
-> MkOptDescr get set a
-> OptionField a
option FilePath
"" [FilePath
"destdir"]
    FilePath
"directory to copy files to, prepended to installation directories"
    CopyFlags -> Flag CopyDest
copyDest (\Flag CopyDest
v CopyFlags
flags -> case CopyFlags -> Flag CopyDest
copyDest CopyFlags
flags of
                 Flag (CopyToDb FilePath
_) -> FilePath -> CopyFlags
forall a. HasCallStack => FilePath -> a
error FilePath
"Use either 'destdir' or 'target-package-db'."
                 Flag CopyDest
_ -> CopyFlags
flags { copyDest :: Flag CopyDest
copyDest = Flag CopyDest
v })
    (FilePath
-> ReadE (Flag CopyDest)
-> (Flag CopyDest -> [FilePath])
-> MkOptDescr
     (CopyFlags -> Flag CopyDest)
     (Flag CopyDest -> CopyFlags -> CopyFlags)
     CopyFlags
forall b a.
Monoid b =>
FilePath
-> ReadE b
-> (b -> [FilePath])
-> MkOptDescr (a -> b) (b -> a -> a) a
reqArg FilePath
"DIR" ((FilePath -> Flag CopyDest) -> ReadE (Flag CopyDest)
forall a. (FilePath -> a) -> ReadE a
succeedReadE (CopyDest -> Flag CopyDest
forall a. a -> Flag a
Flag (CopyDest -> Flag CopyDest)
-> (FilePath -> CopyDest) -> FilePath -> Flag CopyDest
forall b c a. (b -> c) -> (a -> b) -> a -> c
. FilePath -> CopyDest
CopyTo))
      (\Flag CopyDest
f -> case Flag CopyDest
f of Flag (CopyTo FilePath
p) -> [FilePath
p]; Flag CopyDest
_ -> []))

  ,FilePath
-> [FilePath]
-> FilePath
-> (CopyFlags -> Flag CopyDest)
-> (Flag CopyDest -> CopyFlags -> CopyFlags)
-> MkOptDescr
     (CopyFlags -> Flag CopyDest)
     (Flag CopyDest -> CopyFlags -> CopyFlags)
     CopyFlags
-> OptionField CopyFlags
forall get set a.
FilePath
-> [FilePath]
-> FilePath
-> get
-> set
-> MkOptDescr get set a
-> OptionField a
option FilePath
"" [FilePath
"target-package-db"]
    FilePath
"package database to copy files into. Required when using ${pkgroot} prefix."
    CopyFlags -> Flag CopyDest
copyDest (\Flag CopyDest
v CopyFlags
flags -> case CopyFlags -> Flag CopyDest
copyDest CopyFlags
flags of
                 Flag CopyDest
NoFlag -> CopyFlags
flags { copyDest :: Flag CopyDest
copyDest = Flag CopyDest
v }
                 Flag CopyDest
NoCopyDest -> CopyFlags
flags { copyDest :: Flag CopyDest
copyDest = Flag CopyDest
v }
                 Flag CopyDest
_ -> FilePath -> CopyFlags
forall a. HasCallStack => FilePath -> a
error FilePath
"Use either 'destdir' or 'target-package-db'.")
    (FilePath
-> ReadE (Flag CopyDest)
-> (Flag CopyDest -> [FilePath])
-> MkOptDescr
     (CopyFlags -> Flag CopyDest)
     (Flag CopyDest -> CopyFlags -> CopyFlags)
     CopyFlags
forall b a.
Monoid b =>
FilePath
-> ReadE b
-> (b -> [FilePath])
-> MkOptDescr (a -> b) (b -> a -> a) a
reqArg FilePath
"DATABASE" ((FilePath -> Flag CopyDest) -> ReadE (Flag CopyDest)
forall a. (FilePath -> a) -> ReadE a
succeedReadE (CopyDest -> Flag CopyDest
forall a. a -> Flag a
Flag (CopyDest -> Flag CopyDest)
-> (FilePath -> CopyDest) -> FilePath -> Flag CopyDest
forall b c a. (b -> c) -> (a -> b) -> a -> c
. FilePath -> CopyDest
CopyToDb))
      (\Flag CopyDest
f -> case Flag CopyDest
f of Flag (CopyToDb FilePath
p) -> [FilePath
p]; Flag CopyDest
_ -> []))
  ]

emptyCopyFlags :: CopyFlags
emptyCopyFlags :: CopyFlags
emptyCopyFlags = CopyFlags
forall a. Monoid a => a
mempty

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

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

-- ------------------------------------------------------------
-- * Install flags
-- ------------------------------------------------------------

-- | Flags to @install@: (package db, verbosity)
data InstallFlags = InstallFlags {
    InstallFlags -> Flag PackageDB
installPackageDB :: Flag PackageDB,
    InstallFlags -> Flag CopyDest
installDest      :: Flag CopyDest,
    InstallFlags -> Flag FilePath
installDistPref  :: Flag FilePath,
    InstallFlags -> Flag Bool
installUseWrapper :: Flag Bool,
    InstallFlags -> Flag Bool
installInPlace    :: Flag Bool,
    InstallFlags -> Flag Verbosity
installVerbosity :: Flag Verbosity,
    -- this is only here, because we can not
    -- change the hooks API.
    InstallFlags -> Flag FilePath
installCabalFilePath :: Flag FilePath
  }
  deriving (Int -> InstallFlags -> FilePath -> FilePath
[InstallFlags] -> FilePath -> FilePath
InstallFlags -> FilePath
(Int -> InstallFlags -> FilePath -> FilePath)
-> (InstallFlags -> FilePath)
-> ([InstallFlags] -> FilePath -> FilePath)
-> Show InstallFlags
forall a.
(Int -> a -> FilePath -> FilePath)
-> (a -> FilePath) -> ([a] -> FilePath -> FilePath) -> Show a
showList :: [InstallFlags] -> FilePath -> FilePath
$cshowList :: [InstallFlags] -> FilePath -> FilePath
show :: InstallFlags -> FilePath
$cshow :: InstallFlags -> FilePath
showsPrec :: Int -> InstallFlags -> FilePath -> FilePath
$cshowsPrec :: Int -> InstallFlags -> FilePath -> FilePath
Show, (forall x. InstallFlags -> Rep InstallFlags x)
-> (forall x. Rep InstallFlags x -> InstallFlags)
-> Generic InstallFlags
forall x. Rep InstallFlags x -> InstallFlags
forall x. InstallFlags -> Rep InstallFlags x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep InstallFlags x -> InstallFlags
$cfrom :: forall x. InstallFlags -> Rep InstallFlags x
Generic)

defaultInstallFlags :: InstallFlags
defaultInstallFlags :: InstallFlags
defaultInstallFlags  = InstallFlags :: Flag PackageDB
-> Flag CopyDest
-> Flag FilePath
-> Flag Bool
-> Flag Bool
-> Flag Verbosity
-> Flag FilePath
-> InstallFlags
InstallFlags {
    installPackageDB :: Flag PackageDB
installPackageDB = Flag PackageDB
forall a. Flag a
NoFlag,
    installDest :: Flag CopyDest
installDest      = CopyDest -> Flag CopyDest
forall a. a -> Flag a
Flag CopyDest
NoCopyDest,
    installDistPref :: Flag FilePath
installDistPref  = Flag FilePath
forall a. Flag a
NoFlag,
    installUseWrapper :: Flag Bool
installUseWrapper = Bool -> Flag Bool
forall a. a -> Flag a
Flag Bool
False,
    installInPlace :: Flag Bool
installInPlace    = Bool -> Flag Bool
forall a. a -> Flag a
Flag Bool
False,
    installVerbosity :: Flag Verbosity
installVerbosity = Verbosity -> Flag Verbosity
forall a. a -> Flag a
Flag Verbosity
normal,
    installCabalFilePath :: Flag FilePath
installCabalFilePath = Flag FilePath
forall a. Monoid a => a
mempty
  }

installCommand :: CommandUI InstallFlags
installCommand :: CommandUI InstallFlags
installCommand = CommandUI :: forall flags.
FilePath
-> FilePath
-> (FilePath -> FilePath)
-> Maybe (FilePath -> FilePath)
-> Maybe (FilePath -> FilePath)
-> flags
-> (ShowOrParseArgs -> [OptionField flags])
-> CommandUI flags
CommandUI
  { commandName :: FilePath
commandName         = FilePath
"install"
  , commandSynopsis :: FilePath
commandSynopsis     =
      FilePath
"Copy the files into the install locations. Run register."
  , commandDescription :: Maybe (FilePath -> FilePath)
commandDescription  = (FilePath -> FilePath) -> Maybe (FilePath -> FilePath)
forall a. a -> Maybe a
Just ((FilePath -> FilePath) -> Maybe (FilePath -> FilePath))
-> (FilePath -> FilePath) -> Maybe (FilePath -> FilePath)
forall a b. (a -> b) -> a -> b
$ \FilePath
_ -> FilePath -> FilePath
wrapText (FilePath -> FilePath) -> FilePath -> FilePath
forall a b. (a -> b) -> a -> b
$
         FilePath
"Unlike the copy command, install calls the register command."
      FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
"If you want to install into a location that is not what was"
      FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
"specified in the configure step, use the copy command.\n"
  , commandNotes :: Maybe (FilePath -> FilePath)
commandNotes        = Maybe (FilePath -> FilePath)
forall a. Maybe a
Nothing
  , commandUsage :: FilePath -> FilePath
commandUsage        = \FilePath
pname ->
      FilePath
"Usage: " FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
pname FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
" install [FLAGS]\n"
  , commandDefaultFlags :: InstallFlags
commandDefaultFlags = InstallFlags
defaultInstallFlags
  , commandOptions :: ShowOrParseArgs -> [OptionField InstallFlags]
commandOptions      = \ShowOrParseArgs
showOrParseArgs -> case ShowOrParseArgs
showOrParseArgs of
      ShowOrParseArgs
ShowArgs -> (OptionField InstallFlags -> Bool)
-> [OptionField InstallFlags] -> [OptionField InstallFlags]
forall a. (a -> Bool) -> [a] -> [a]
filter ((FilePath -> [FilePath] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`notElem` [FilePath
"target-package-db"])
                          (FilePath -> Bool)
-> (OptionField InstallFlags -> FilePath)
-> OptionField InstallFlags
-> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. OptionField InstallFlags -> FilePath
forall a. OptionField a -> FilePath
optionName) ([OptionField InstallFlags] -> [OptionField InstallFlags])
-> [OptionField InstallFlags] -> [OptionField InstallFlags]
forall a b. (a -> b) -> a -> b
$ ShowOrParseArgs -> [OptionField InstallFlags]
installOptions ShowOrParseArgs
ShowArgs
      ShowOrParseArgs
ParseArgs -> ShowOrParseArgs -> [OptionField InstallFlags]
installOptions ShowOrParseArgs
ParseArgs
  }

installOptions ::  ShowOrParseArgs -> [OptionField InstallFlags]
installOptions :: ShowOrParseArgs -> [OptionField InstallFlags]
installOptions ShowOrParseArgs
showOrParseArgs =
  [(InstallFlags -> Flag Verbosity)
-> (Flag Verbosity -> InstallFlags -> InstallFlags)
-> OptionField InstallFlags
forall flags.
(flags -> Flag Verbosity)
-> (Flag Verbosity -> flags -> flags) -> OptionField flags
optionVerbosity InstallFlags -> Flag Verbosity
installVerbosity (\Flag Verbosity
v InstallFlags
flags -> InstallFlags
flags { installVerbosity :: Flag Verbosity
installVerbosity = Flag Verbosity
v })
  ,(InstallFlags -> Flag FilePath)
-> (Flag FilePath -> InstallFlags -> InstallFlags)
-> ShowOrParseArgs
-> OptionField InstallFlags
forall flags.
(flags -> Flag FilePath)
-> (Flag FilePath -> flags -> flags)
-> ShowOrParseArgs
-> OptionField flags
optionDistPref
    InstallFlags -> Flag FilePath
installDistPref (\Flag FilePath
d InstallFlags
flags -> InstallFlags
flags { installDistPref :: Flag FilePath
installDistPref = Flag FilePath
d })
    ShowOrParseArgs
showOrParseArgs

  ,FilePath
-> [FilePath]
-> FilePath
-> (InstallFlags -> Flag Bool)
-> (Flag Bool -> InstallFlags -> InstallFlags)
-> MkOptDescr
     (InstallFlags -> Flag Bool)
     (Flag Bool -> InstallFlags -> InstallFlags)
     InstallFlags
-> OptionField InstallFlags
forall get set a.
FilePath
-> [FilePath]
-> FilePath
-> get
-> set
-> MkOptDescr get set a
-> OptionField a
option FilePath
"" [FilePath
"inplace"]
    FilePath
"install the package in the install subdirectory of the dist prefix, so it can be used without being installed"
    InstallFlags -> Flag Bool
installInPlace (\Flag Bool
v InstallFlags
flags -> InstallFlags
flags { installInPlace :: Flag Bool
installInPlace = Flag Bool
v })
    MkOptDescr
  (InstallFlags -> Flag Bool)
  (Flag Bool -> InstallFlags -> InstallFlags)
  InstallFlags
forall a. MkOptDescr (a -> Flag Bool) (Flag Bool -> a -> a) a
trueArg

  ,FilePath
-> [FilePath]
-> FilePath
-> (InstallFlags -> Flag Bool)
-> (Flag Bool -> InstallFlags -> InstallFlags)
-> MkOptDescr
     (InstallFlags -> Flag Bool)
     (Flag Bool -> InstallFlags -> InstallFlags)
     InstallFlags
-> OptionField InstallFlags
forall get set a.
FilePath
-> [FilePath]
-> FilePath
-> get
-> set
-> MkOptDescr get set a
-> OptionField a
option FilePath
"" [FilePath
"shell-wrappers"]
    FilePath
"using shell script wrappers around executables"
    InstallFlags -> Flag Bool
installUseWrapper (\Flag Bool
v InstallFlags
flags -> InstallFlags
flags { installUseWrapper :: Flag Bool
installUseWrapper = Flag Bool
v })
    (FilePath
-> FilePath
-> MkOptDescr
     (InstallFlags -> Flag Bool)
     (Flag Bool -> InstallFlags -> InstallFlags)
     InstallFlags
forall a.
FilePath
-> FilePath -> MkOptDescr (a -> Flag Bool) (Flag Bool -> a -> a) a
boolOpt [] [])

  ,FilePath
-> [FilePath]
-> FilePath
-> (InstallFlags -> Flag PackageDB)
-> (Flag PackageDB -> InstallFlags -> InstallFlags)
-> MkOptDescr
     (InstallFlags -> Flag PackageDB)
     (Flag PackageDB -> InstallFlags -> InstallFlags)
     InstallFlags
-> OptionField InstallFlags
forall get set a.
FilePath
-> [FilePath]
-> FilePath
-> get
-> set
-> MkOptDescr get set a
-> OptionField a
option FilePath
"" [FilePath
"package-db"] FilePath
""
    InstallFlags -> Flag PackageDB
installPackageDB (\Flag PackageDB
v InstallFlags
flags -> InstallFlags
flags { installPackageDB :: Flag PackageDB
installPackageDB = Flag PackageDB
v })
    ([(Flag PackageDB, (FilePath, [FilePath]), FilePath)]
-> MkOptDescr
     (InstallFlags -> Flag PackageDB)
     (Flag PackageDB -> InstallFlags -> InstallFlags)
     InstallFlags
forall b a.
Eq b =>
[(b, (FilePath, [FilePath]), FilePath)]
-> MkOptDescr (a -> b) (b -> a -> a) a
choiceOpt [ (PackageDB -> Flag PackageDB
forall a. a -> Flag a
Flag PackageDB
UserPackageDB, ([],[FilePath
"user"]),
                   FilePath
"upon configuration register this package in the user's local package database")
               , (PackageDB -> Flag PackageDB
forall a. a -> Flag a
Flag PackageDB
GlobalPackageDB, ([],[FilePath
"global"]),
                   FilePath
"(default) upon configuration register this package in the system-wide package database")])
  ,FilePath
-> [FilePath]
-> FilePath
-> (InstallFlags -> Flag CopyDest)
-> (Flag CopyDest -> InstallFlags -> InstallFlags)
-> MkOptDescr
     (InstallFlags -> Flag CopyDest)
     (Flag CopyDest -> InstallFlags -> InstallFlags)
     InstallFlags
-> OptionField InstallFlags
forall get set a.
FilePath
-> [FilePath]
-> FilePath
-> get
-> set
-> MkOptDescr get set a
-> OptionField a
option FilePath
"" [FilePath
"target-package-db"]
    FilePath
"package database to install into. Required when using ${pkgroot} prefix."
    InstallFlags -> Flag CopyDest
installDest (\Flag CopyDest
v InstallFlags
flags -> InstallFlags
flags { installDest :: Flag CopyDest
installDest = Flag CopyDest
v })
    (FilePath
-> ReadE (Flag CopyDest)
-> (Flag CopyDest -> [FilePath])
-> MkOptDescr
     (InstallFlags -> Flag CopyDest)
     (Flag CopyDest -> InstallFlags -> InstallFlags)
     InstallFlags
forall b a.
Monoid b =>
FilePath
-> ReadE b
-> (b -> [FilePath])
-> MkOptDescr (a -> b) (b -> a -> a) a
reqArg FilePath
"DATABASE" ((FilePath -> Flag CopyDest) -> ReadE (Flag CopyDest)
forall a. (FilePath -> a) -> ReadE a
succeedReadE (CopyDest -> Flag CopyDest
forall a. a -> Flag a
Flag (CopyDest -> Flag CopyDest)
-> (FilePath -> CopyDest) -> FilePath -> Flag CopyDest
forall b c a. (b -> c) -> (a -> b) -> a -> c
. FilePath -> CopyDest
CopyToDb))
      (\Flag CopyDest
f -> case Flag CopyDest
f of Flag (CopyToDb FilePath
p) -> [FilePath
p]; Flag CopyDest
_ -> []))
  ]

emptyInstallFlags :: InstallFlags
emptyInstallFlags :: InstallFlags
emptyInstallFlags = InstallFlags
forall a. Monoid a => a
mempty

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

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

-- ------------------------------------------------------------
-- * SDist flags
-- ------------------------------------------------------------

-- | Flags to @sdist@: (snapshot, verbosity)
data SDistFlags = SDistFlags {
    SDistFlags -> Flag Bool
sDistSnapshot    :: Flag Bool,
    SDistFlags -> Flag FilePath
sDistDirectory   :: Flag FilePath,
    SDistFlags -> Flag FilePath
sDistDistPref    :: Flag FilePath,
    SDistFlags -> Flag FilePath
sDistListSources :: Flag FilePath,
    SDistFlags -> Flag Verbosity
sDistVerbosity   :: Flag Verbosity
  }
  deriving (Int -> SDistFlags -> FilePath -> FilePath
[SDistFlags] -> FilePath -> FilePath
SDistFlags -> FilePath
(Int -> SDistFlags -> FilePath -> FilePath)
-> (SDistFlags -> FilePath)
-> ([SDistFlags] -> FilePath -> FilePath)
-> Show SDistFlags
forall a.
(Int -> a -> FilePath -> FilePath)
-> (a -> FilePath) -> ([a] -> FilePath -> FilePath) -> Show a
showList :: [SDistFlags] -> FilePath -> FilePath
$cshowList :: [SDistFlags] -> FilePath -> FilePath
show :: SDistFlags -> FilePath
$cshow :: SDistFlags -> FilePath
showsPrec :: Int -> SDistFlags -> FilePath -> FilePath
$cshowsPrec :: Int -> SDistFlags -> FilePath -> FilePath
Show, (forall x. SDistFlags -> Rep SDistFlags x)
-> (forall x. Rep SDistFlags x -> SDistFlags) -> Generic SDistFlags
forall x. Rep SDistFlags x -> SDistFlags
forall x. SDistFlags -> Rep SDistFlags x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep SDistFlags x -> SDistFlags
$cfrom :: forall x. SDistFlags -> Rep SDistFlags x
Generic, Typeable)

defaultSDistFlags :: SDistFlags
defaultSDistFlags :: SDistFlags
defaultSDistFlags = SDistFlags :: Flag Bool
-> Flag FilePath
-> Flag FilePath
-> Flag FilePath
-> Flag Verbosity
-> SDistFlags
SDistFlags {
    sDistSnapshot :: Flag Bool
sDistSnapshot    = Bool -> Flag Bool
forall a. a -> Flag a
Flag Bool
False,
    sDistDirectory :: Flag FilePath
sDistDirectory   = Flag FilePath
forall a. Monoid a => a
mempty,
    sDistDistPref :: Flag FilePath
sDistDistPref    = Flag FilePath
forall a. Flag a
NoFlag,
    sDistListSources :: Flag FilePath
sDistListSources = Flag FilePath
forall a. Monoid a => a
mempty,
    sDistVerbosity :: Flag Verbosity
sDistVerbosity   = Verbosity -> Flag Verbosity
forall a. a -> Flag a
Flag Verbosity
normal
  }

sdistCommand :: CommandUI SDistFlags
sdistCommand :: CommandUI SDistFlags
sdistCommand = CommandUI :: forall flags.
FilePath
-> FilePath
-> (FilePath -> FilePath)
-> Maybe (FilePath -> FilePath)
-> Maybe (FilePath -> FilePath)
-> flags
-> (ShowOrParseArgs -> [OptionField flags])
-> CommandUI flags
CommandUI
  { commandName :: FilePath
commandName         = FilePath
"sdist"
  , commandSynopsis :: FilePath
commandSynopsis     =
      FilePath
"Generate a source distribution file (.tar.gz)."
  , commandDescription :: Maybe (FilePath -> FilePath)
commandDescription  = Maybe (FilePath -> FilePath)
forall a. Maybe a
Nothing
  , commandNotes :: Maybe (FilePath -> FilePath)
commandNotes        = Maybe (FilePath -> FilePath)
forall a. Maybe a
Nothing
  , commandUsage :: FilePath -> FilePath
commandUsage        = \FilePath
pname ->
      FilePath
"Usage: " FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
pname FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
" sdist [FLAGS]\n"
  , commandDefaultFlags :: SDistFlags
commandDefaultFlags = SDistFlags
defaultSDistFlags
  , commandOptions :: ShowOrParseArgs -> [OptionField SDistFlags]
commandOptions      = \ShowOrParseArgs
showOrParseArgs ->
      [(SDistFlags -> Flag Verbosity)
-> (Flag Verbosity -> SDistFlags -> SDistFlags)
-> OptionField SDistFlags
forall flags.
(flags -> Flag Verbosity)
-> (Flag Verbosity -> flags -> flags) -> OptionField flags
optionVerbosity SDistFlags -> Flag Verbosity
sDistVerbosity (\Flag Verbosity
v SDistFlags
flags -> SDistFlags
flags { sDistVerbosity :: Flag Verbosity
sDistVerbosity = Flag Verbosity
v })
      ,(SDistFlags -> Flag FilePath)
-> (Flag FilePath -> SDistFlags -> SDistFlags)
-> ShowOrParseArgs
-> OptionField SDistFlags
forall flags.
(flags -> Flag FilePath)
-> (Flag FilePath -> flags -> flags)
-> ShowOrParseArgs
-> OptionField flags
optionDistPref
         SDistFlags -> Flag FilePath
sDistDistPref (\Flag FilePath
d SDistFlags
flags -> SDistFlags
flags { sDistDistPref :: Flag FilePath
sDistDistPref = Flag FilePath
d })
         ShowOrParseArgs
showOrParseArgs

      ,FilePath
-> [FilePath]
-> FilePath
-> (SDistFlags -> Flag FilePath)
-> (Flag FilePath -> SDistFlags -> SDistFlags)
-> MkOptDescr
     (SDistFlags -> Flag FilePath)
     (Flag FilePath -> SDistFlags -> SDistFlags)
     SDistFlags
-> OptionField SDistFlags
forall get set a.
FilePath
-> [FilePath]
-> FilePath
-> get
-> set
-> MkOptDescr get set a
-> OptionField a
option FilePath
"" [FilePath
"list-sources"]
         FilePath
"Just write a list of the package's sources to a file"
         SDistFlags -> Flag FilePath
sDistListSources (\Flag FilePath
v SDistFlags
flags -> SDistFlags
flags { sDistListSources :: Flag FilePath
sDistListSources = Flag FilePath
v })
         (FilePath
-> MkOptDescr
     (SDistFlags -> Flag FilePath)
     (Flag FilePath -> SDistFlags -> SDistFlags)
     SDistFlags
forall b.
FilePath
-> FilePath
-> [FilePath]
-> FilePath
-> (b -> Flag FilePath)
-> (Flag FilePath -> b -> b)
-> OptDescr b
reqArgFlag FilePath
"FILE")

      ,FilePath
-> [FilePath]
-> FilePath
-> (SDistFlags -> Flag Bool)
-> (Flag Bool -> SDistFlags -> SDistFlags)
-> MkOptDescr
     (SDistFlags -> Flag Bool)
     (Flag Bool -> SDistFlags -> SDistFlags)
     SDistFlags
-> OptionField SDistFlags
forall get set a.
FilePath
-> [FilePath]
-> FilePath
-> get
-> set
-> MkOptDescr get set a
-> OptionField a
option FilePath
"" [FilePath
"snapshot"]
         FilePath
"Produce a snapshot source distribution"
         SDistFlags -> Flag Bool
sDistSnapshot (\Flag Bool
v SDistFlags
flags -> SDistFlags
flags { sDistSnapshot :: Flag Bool
sDistSnapshot = Flag Bool
v })
         MkOptDescr
  (SDistFlags -> Flag Bool)
  (Flag Bool -> SDistFlags -> SDistFlags)
  SDistFlags
forall a. MkOptDescr (a -> Flag Bool) (Flag Bool -> a -> a) a
trueArg

      ,FilePath
-> [FilePath]
-> FilePath
-> (SDistFlags -> Flag FilePath)
-> (Flag FilePath -> SDistFlags -> SDistFlags)
-> MkOptDescr
     (SDistFlags -> Flag FilePath)
     (Flag FilePath -> SDistFlags -> SDistFlags)
     SDistFlags
-> OptionField SDistFlags
forall get set a.
FilePath
-> [FilePath]
-> FilePath
-> get
-> set
-> MkOptDescr get set a
-> OptionField a
option FilePath
"" [FilePath
"output-directory"]
       (FilePath
"Generate a source distribution in the given directory, "
        FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
"without creating a tarball")
         SDistFlags -> Flag FilePath
sDistDirectory (\Flag FilePath
v SDistFlags
flags -> SDistFlags
flags { sDistDirectory :: Flag FilePath
sDistDirectory = Flag FilePath
v })
         (FilePath
-> MkOptDescr
     (SDistFlags -> Flag FilePath)
     (Flag FilePath -> SDistFlags -> SDistFlags)
     SDistFlags
forall b.
FilePath
-> FilePath
-> [FilePath]
-> FilePath
-> (b -> Flag FilePath)
-> (Flag FilePath -> b -> b)
-> OptDescr b
reqArgFlag FilePath
"DIR")
      ]
  }

emptySDistFlags :: SDistFlags
emptySDistFlags :: SDistFlags
emptySDistFlags = SDistFlags
forall a. Monoid a => a
mempty

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

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

-- ------------------------------------------------------------
-- * Register flags
-- ------------------------------------------------------------

-- | Flags to @register@ and @unregister@: (user package, gen-script,
-- in-place, verbosity)
data RegisterFlags = RegisterFlags {
    RegisterFlags -> Flag PackageDB
regPackageDB   :: Flag PackageDB,
    RegisterFlags -> Flag Bool
regGenScript   :: Flag Bool,
    RegisterFlags -> Flag (Maybe FilePath)
regGenPkgConf  :: Flag (Maybe FilePath),
    RegisterFlags -> Flag Bool
regInPlace     :: Flag Bool,
    RegisterFlags -> Flag FilePath
regDistPref    :: Flag FilePath,
    RegisterFlags -> Flag Bool
regPrintId     :: Flag Bool,
    RegisterFlags -> Flag Verbosity
regVerbosity   :: Flag Verbosity,
    -- Same as in 'buildArgs' and 'copyArgs'
    RegisterFlags -> [FilePath]
regArgs        :: [String],
    RegisterFlags -> Flag FilePath
regCabalFilePath :: Flag FilePath
  }
  deriving (Int -> RegisterFlags -> FilePath -> FilePath
[RegisterFlags] -> FilePath -> FilePath
RegisterFlags -> FilePath
(Int -> RegisterFlags -> FilePath -> FilePath)
-> (RegisterFlags -> FilePath)
-> ([RegisterFlags] -> FilePath -> FilePath)
-> Show RegisterFlags
forall a.
(Int -> a -> FilePath -> FilePath)
-> (a -> FilePath) -> ([a] -> FilePath -> FilePath) -> Show a
showList :: [RegisterFlags] -> FilePath -> FilePath
$cshowList :: [RegisterFlags] -> FilePath -> FilePath
show :: RegisterFlags -> FilePath
$cshow :: RegisterFlags -> FilePath
showsPrec :: Int -> RegisterFlags -> FilePath -> FilePath
$cshowsPrec :: Int -> RegisterFlags -> FilePath -> FilePath
Show, (forall x. RegisterFlags -> Rep RegisterFlags x)
-> (forall x. Rep RegisterFlags x -> RegisterFlags)
-> Generic RegisterFlags
forall x. Rep RegisterFlags x -> RegisterFlags
forall x. RegisterFlags -> Rep RegisterFlags x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep RegisterFlags x -> RegisterFlags
$cfrom :: forall x. RegisterFlags -> Rep RegisterFlags x
Generic, Typeable)

defaultRegisterFlags :: RegisterFlags
defaultRegisterFlags :: RegisterFlags
defaultRegisterFlags = RegisterFlags :: Flag PackageDB
-> Flag Bool
-> Flag (Maybe FilePath)
-> Flag Bool
-> Flag FilePath
-> Flag Bool
-> Flag Verbosity
-> [FilePath]
-> Flag FilePath
-> RegisterFlags
RegisterFlags {
    regPackageDB :: Flag PackageDB
regPackageDB   = Flag PackageDB
forall a. Flag a
NoFlag,
    regGenScript :: Flag Bool
regGenScript   = Bool -> Flag Bool
forall a. a -> Flag a
Flag Bool
False,
    regGenPkgConf :: Flag (Maybe FilePath)
regGenPkgConf  = Flag (Maybe FilePath)
forall a. Flag a
NoFlag,
    regInPlace :: Flag Bool
regInPlace     = Bool -> Flag Bool
forall a. a -> Flag a
Flag Bool
False,
    regDistPref :: Flag FilePath
regDistPref    = Flag FilePath
forall a. Flag a
NoFlag,
    regPrintId :: Flag Bool
regPrintId     = Bool -> Flag Bool
forall a. a -> Flag a
Flag Bool
False,
    regArgs :: [FilePath]
regArgs        = [],
    regCabalFilePath :: Flag FilePath
regCabalFilePath = Flag FilePath
forall a. Monoid a => a
mempty,
    regVerbosity :: Flag Verbosity
regVerbosity   = Verbosity -> Flag Verbosity
forall a. a -> Flag a
Flag Verbosity
normal
  }

registerCommand :: CommandUI RegisterFlags
registerCommand :: CommandUI RegisterFlags
registerCommand = CommandUI :: forall flags.
FilePath
-> FilePath
-> (FilePath -> FilePath)
-> Maybe (FilePath -> FilePath)
-> Maybe (FilePath -> FilePath)
-> flags
-> (ShowOrParseArgs -> [OptionField flags])
-> CommandUI flags
CommandUI
  { commandName :: FilePath
commandName         = FilePath
"register"
  , commandSynopsis :: FilePath
commandSynopsis     =
      FilePath
"Register this package with the compiler."
  , commandDescription :: Maybe (FilePath -> FilePath)
commandDescription  = Maybe (FilePath -> FilePath)
forall a. Maybe a
Nothing
  , commandNotes :: Maybe (FilePath -> FilePath)
commandNotes        = Maybe (FilePath -> FilePath)
forall a. Maybe a
Nothing
  , commandUsage :: FilePath -> FilePath
commandUsage        = \FilePath
pname ->
      FilePath
"Usage: " FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
pname FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
" register [FLAGS]\n"
  , commandDefaultFlags :: RegisterFlags
commandDefaultFlags = RegisterFlags
defaultRegisterFlags
  , commandOptions :: ShowOrParseArgs -> [OptionField RegisterFlags]
commandOptions      = \ShowOrParseArgs
showOrParseArgs ->
      [(RegisterFlags -> Flag Verbosity)
-> (Flag Verbosity -> RegisterFlags -> RegisterFlags)
-> OptionField RegisterFlags
forall flags.
(flags -> Flag Verbosity)
-> (Flag Verbosity -> flags -> flags) -> OptionField flags
optionVerbosity RegisterFlags -> Flag Verbosity
regVerbosity (\Flag Verbosity
v RegisterFlags
flags -> RegisterFlags
flags { regVerbosity :: Flag Verbosity
regVerbosity = Flag Verbosity
v })
      ,(RegisterFlags -> Flag FilePath)
-> (Flag FilePath -> RegisterFlags -> RegisterFlags)
-> ShowOrParseArgs
-> OptionField RegisterFlags
forall flags.
(flags -> Flag FilePath)
-> (Flag FilePath -> flags -> flags)
-> ShowOrParseArgs
-> OptionField flags
optionDistPref
         RegisterFlags -> Flag FilePath
regDistPref (\Flag FilePath
d RegisterFlags
flags -> RegisterFlags
flags { regDistPref :: Flag FilePath
regDistPref = Flag FilePath
d })
         ShowOrParseArgs
showOrParseArgs

      ,FilePath
-> [FilePath]
-> FilePath
-> (RegisterFlags -> Flag PackageDB)
-> (Flag PackageDB -> RegisterFlags -> RegisterFlags)
-> MkOptDescr
     (RegisterFlags -> Flag PackageDB)
     (Flag PackageDB -> RegisterFlags -> RegisterFlags)
     RegisterFlags
-> OptionField RegisterFlags
forall get set a.
FilePath
-> [FilePath]
-> FilePath
-> get
-> set
-> MkOptDescr get set a
-> OptionField a
option FilePath
"" [FilePath
"packageDB"] FilePath
""
         RegisterFlags -> Flag PackageDB
regPackageDB (\Flag PackageDB
v RegisterFlags
flags -> RegisterFlags
flags { regPackageDB :: Flag PackageDB
regPackageDB = Flag PackageDB
v })
         ([(Flag PackageDB, (FilePath, [FilePath]), FilePath)]
-> MkOptDescr
     (RegisterFlags -> Flag PackageDB)
     (Flag PackageDB -> RegisterFlags -> RegisterFlags)
     RegisterFlags
forall b a.
Eq b =>
[(b, (FilePath, [FilePath]), FilePath)]
-> MkOptDescr (a -> b) (b -> a -> a) a
choiceOpt [ (PackageDB -> Flag PackageDB
forall a. a -> Flag a
Flag PackageDB
UserPackageDB, ([],[FilePath
"user"]),
                                FilePath
"upon registration, register this package in the user's local package database")
                    , (PackageDB -> Flag PackageDB
forall a. a -> Flag a
Flag PackageDB
GlobalPackageDB, ([],[FilePath
"global"]),
                                FilePath
"(default)upon registration, register this package in the system-wide package database")])

      ,FilePath
-> [FilePath]
-> FilePath
-> (RegisterFlags -> Flag Bool)
-> (Flag Bool -> RegisterFlags -> RegisterFlags)
-> MkOptDescr
     (RegisterFlags -> Flag Bool)
     (Flag Bool -> RegisterFlags -> RegisterFlags)
     RegisterFlags
-> OptionField RegisterFlags
forall get set a.
FilePath
-> [FilePath]
-> FilePath
-> get
-> set
-> MkOptDescr get set a
-> OptionField a
option FilePath
"" [FilePath
"inplace"]
         FilePath
"register the package in the build location, so it can be used without being installed"
         RegisterFlags -> Flag Bool
regInPlace (\Flag Bool
v RegisterFlags
flags -> RegisterFlags
flags { regInPlace :: Flag Bool
regInPlace = Flag Bool
v })
         MkOptDescr
  (RegisterFlags -> Flag Bool)
  (Flag Bool -> RegisterFlags -> RegisterFlags)
  RegisterFlags
forall a. MkOptDescr (a -> Flag Bool) (Flag Bool -> a -> a) a
trueArg

      ,FilePath
-> [FilePath]
-> FilePath
-> (RegisterFlags -> Flag Bool)
-> (Flag Bool -> RegisterFlags -> RegisterFlags)
-> MkOptDescr
     (RegisterFlags -> Flag Bool)
     (Flag Bool -> RegisterFlags -> RegisterFlags)
     RegisterFlags
-> OptionField RegisterFlags
forall get set a.
FilePath
-> [FilePath]
-> FilePath
-> get
-> set
-> MkOptDescr get set a
-> OptionField a
option FilePath
"" [FilePath
"gen-script"]
         FilePath
"instead of registering, generate a script to register later"
         RegisterFlags -> Flag Bool
regGenScript (\Flag Bool
v RegisterFlags
flags -> RegisterFlags
flags { regGenScript :: Flag Bool
regGenScript = Flag Bool
v })
         MkOptDescr
  (RegisterFlags -> Flag Bool)
  (Flag Bool -> RegisterFlags -> RegisterFlags)
  RegisterFlags
forall a. MkOptDescr (a -> Flag Bool) (Flag Bool -> a -> a) a
trueArg

      ,FilePath
-> [FilePath]
-> FilePath
-> (RegisterFlags -> Flag (Maybe FilePath))
-> (Flag (Maybe FilePath) -> RegisterFlags -> RegisterFlags)
-> MkOptDescr
     (RegisterFlags -> Flag (Maybe FilePath))
     (Flag (Maybe FilePath) -> RegisterFlags -> RegisterFlags)
     RegisterFlags
-> OptionField RegisterFlags
forall get set a.
FilePath
-> [FilePath]
-> FilePath
-> get
-> set
-> MkOptDescr get set a
-> OptionField a
option FilePath
"" [FilePath
"gen-pkg-config"]
         FilePath
"instead of registering, generate a package registration file/directory"
         RegisterFlags -> Flag (Maybe FilePath)
regGenPkgConf (\Flag (Maybe FilePath)
v RegisterFlags
flags -> RegisterFlags
flags { regGenPkgConf :: Flag (Maybe FilePath)
regGenPkgConf  = Flag (Maybe FilePath)
v })
         (FilePath
-> (Maybe FilePath -> Flag (Maybe FilePath))
-> (Flag (Maybe FilePath) -> [Maybe FilePath])
-> MkOptDescr
     (RegisterFlags -> Flag (Maybe FilePath))
     (Flag (Maybe FilePath) -> RegisterFlags -> RegisterFlags)
     RegisterFlags
forall b a.
Monoid b =>
FilePath
-> (Maybe FilePath -> b)
-> (b -> [Maybe FilePath])
-> MkOptDescr (a -> b) (b -> a -> a) a
optArg' FilePath
"PKG" Maybe FilePath -> Flag (Maybe FilePath)
forall a. a -> Flag a
Flag Flag (Maybe FilePath) -> [Maybe FilePath]
forall a. Flag a -> [a]
flagToList)

      ,FilePath
-> [FilePath]
-> FilePath
-> (RegisterFlags -> Flag Bool)
-> (Flag Bool -> RegisterFlags -> RegisterFlags)
-> MkOptDescr
     (RegisterFlags -> Flag Bool)
     (Flag Bool -> RegisterFlags -> RegisterFlags)
     RegisterFlags
-> OptionField RegisterFlags
forall get set a.
FilePath
-> [FilePath]
-> FilePath
-> get
-> set
-> MkOptDescr get set a
-> OptionField a
option FilePath
"" [FilePath
"print-ipid"]
         FilePath
"print the installed package ID calculated for this package"
         RegisterFlags -> Flag Bool
regPrintId (\Flag Bool
v RegisterFlags
flags -> RegisterFlags
flags { regPrintId :: Flag Bool
regPrintId = Flag Bool
v })
         MkOptDescr
  (RegisterFlags -> Flag Bool)
  (Flag Bool -> RegisterFlags -> RegisterFlags)
  RegisterFlags
forall a. MkOptDescr (a -> Flag Bool) (Flag Bool -> a -> a) a
trueArg
      ]
  }

unregisterCommand :: CommandUI RegisterFlags
unregisterCommand :: CommandUI RegisterFlags
unregisterCommand = CommandUI :: forall flags.
FilePath
-> FilePath
-> (FilePath -> FilePath)
-> Maybe (FilePath -> FilePath)
-> Maybe (FilePath -> FilePath)
-> flags
-> (ShowOrParseArgs -> [OptionField flags])
-> CommandUI flags
CommandUI
  { commandName :: FilePath
commandName         = FilePath
"unregister"
  , commandSynopsis :: FilePath
commandSynopsis     =
      FilePath
"Unregister this package with the compiler."
  , commandDescription :: Maybe (FilePath -> FilePath)
commandDescription  = Maybe (FilePath -> FilePath)
forall a. Maybe a
Nothing
  , commandNotes :: Maybe (FilePath -> FilePath)
commandNotes        = Maybe (FilePath -> FilePath)
forall a. Maybe a
Nothing
  , commandUsage :: FilePath -> FilePath
commandUsage        = \FilePath
pname ->
      FilePath
"Usage: " FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
pname FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
" unregister [FLAGS]\n"
  , commandDefaultFlags :: RegisterFlags
commandDefaultFlags = RegisterFlags
defaultRegisterFlags
  , commandOptions :: ShowOrParseArgs -> [OptionField RegisterFlags]
commandOptions      = \ShowOrParseArgs
showOrParseArgs ->
      [(RegisterFlags -> Flag Verbosity)
-> (Flag Verbosity -> RegisterFlags -> RegisterFlags)
-> OptionField RegisterFlags
forall flags.
(flags -> Flag Verbosity)
-> (Flag Verbosity -> flags -> flags) -> OptionField flags
optionVerbosity RegisterFlags -> Flag Verbosity
regVerbosity (\Flag Verbosity
v RegisterFlags
flags -> RegisterFlags
flags { regVerbosity :: Flag Verbosity
regVerbosity = Flag Verbosity
v })
      ,(RegisterFlags -> Flag FilePath)
-> (Flag FilePath -> RegisterFlags -> RegisterFlags)
-> ShowOrParseArgs
-> OptionField RegisterFlags
forall flags.
(flags -> Flag FilePath)
-> (Flag FilePath -> flags -> flags)
-> ShowOrParseArgs
-> OptionField flags
optionDistPref
         RegisterFlags -> Flag FilePath
regDistPref (\Flag FilePath
d RegisterFlags
flags -> RegisterFlags
flags { regDistPref :: Flag FilePath
regDistPref = Flag FilePath
d })
          ShowOrParseArgs
showOrParseArgs

      ,FilePath
-> [FilePath]
-> FilePath
-> (RegisterFlags -> Flag PackageDB)
-> (Flag PackageDB -> RegisterFlags -> RegisterFlags)
-> MkOptDescr
     (RegisterFlags -> Flag PackageDB)
     (Flag PackageDB -> RegisterFlags -> RegisterFlags)
     RegisterFlags
-> OptionField RegisterFlags
forall get set a.
FilePath
-> [FilePath]
-> FilePath
-> get
-> set
-> MkOptDescr get set a
-> OptionField a
option FilePath
"" [FilePath
"user"] FilePath
""
         RegisterFlags -> Flag PackageDB
regPackageDB (\Flag PackageDB
v RegisterFlags
flags -> RegisterFlags
flags { regPackageDB :: Flag PackageDB
regPackageDB = Flag PackageDB
v })
         ([(Flag PackageDB, (FilePath, [FilePath]), FilePath)]
-> MkOptDescr
     (RegisterFlags -> Flag PackageDB)
     (Flag PackageDB -> RegisterFlags -> RegisterFlags)
     RegisterFlags
forall b a.
Eq b =>
[(b, (FilePath, [FilePath]), FilePath)]
-> MkOptDescr (a -> b) (b -> a -> a) a
choiceOpt [ (PackageDB -> Flag PackageDB
forall a. a -> Flag a
Flag PackageDB
UserPackageDB, ([],[FilePath
"user"]),
                              FilePath
"unregister this package in the user's local package database")
                    , (PackageDB -> Flag PackageDB
forall a. a -> Flag a
Flag PackageDB
GlobalPackageDB, ([],[FilePath
"global"]),
                              FilePath
"(default) unregister this package in the  system-wide package database")])

      ,FilePath
-> [FilePath]
-> FilePath
-> (RegisterFlags -> Flag Bool)
-> (Flag Bool -> RegisterFlags -> RegisterFlags)
-> MkOptDescr
     (RegisterFlags -> Flag Bool)
     (Flag Bool -> RegisterFlags -> RegisterFlags)
     RegisterFlags
-> OptionField RegisterFlags
forall get set a.
FilePath
-> [FilePath]
-> FilePath
-> get
-> set
-> MkOptDescr get set a
-> OptionField a
option FilePath
"" [FilePath
"gen-script"]
         FilePath
"Instead of performing the unregister command, generate a script to unregister later"
         RegisterFlags -> Flag Bool
regGenScript (\Flag Bool
v RegisterFlags
flags -> RegisterFlags
flags { regGenScript :: Flag Bool
regGenScript = Flag Bool
v })
         MkOptDescr
  (RegisterFlags -> Flag Bool)
  (Flag Bool -> RegisterFlags -> RegisterFlags)
  RegisterFlags
forall a. MkOptDescr (a -> Flag Bool) (Flag Bool -> a -> a) a
trueArg
      ]
  }

emptyRegisterFlags :: RegisterFlags
emptyRegisterFlags :: RegisterFlags
emptyRegisterFlags = RegisterFlags
forall a. Monoid a => a
mempty

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

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

-- ------------------------------------------------------------
-- * HsColour flags
-- ------------------------------------------------------------

data HscolourFlags = HscolourFlags {
    HscolourFlags -> Flag FilePath
hscolourCSS         :: Flag FilePath,
    HscolourFlags -> Flag Bool
hscolourExecutables :: Flag Bool,
    HscolourFlags -> Flag Bool
hscolourTestSuites  :: Flag Bool,
    HscolourFlags -> Flag Bool
hscolourBenchmarks  :: Flag Bool,
    HscolourFlags -> Flag Bool
hscolourForeignLibs :: Flag Bool,
    HscolourFlags -> Flag FilePath
hscolourDistPref    :: Flag FilePath,
    HscolourFlags -> Flag Verbosity
hscolourVerbosity   :: Flag Verbosity,
    HscolourFlags -> Flag FilePath
hscolourCabalFilePath :: Flag FilePath
    }
  deriving (Int -> HscolourFlags -> FilePath -> FilePath
[HscolourFlags] -> FilePath -> FilePath
HscolourFlags -> FilePath
(Int -> HscolourFlags -> FilePath -> FilePath)
-> (HscolourFlags -> FilePath)
-> ([HscolourFlags] -> FilePath -> FilePath)
-> Show HscolourFlags
forall a.
(Int -> a -> FilePath -> FilePath)
-> (a -> FilePath) -> ([a] -> FilePath -> FilePath) -> Show a
showList :: [HscolourFlags] -> FilePath -> FilePath
$cshowList :: [HscolourFlags] -> FilePath -> FilePath
show :: HscolourFlags -> FilePath
$cshow :: HscolourFlags -> FilePath
showsPrec :: Int -> HscolourFlags -> FilePath -> FilePath
$cshowsPrec :: Int -> HscolourFlags -> FilePath -> FilePath
Show, (forall x. HscolourFlags -> Rep HscolourFlags x)
-> (forall x. Rep HscolourFlags x -> HscolourFlags)
-> Generic HscolourFlags
forall x. Rep HscolourFlags x -> HscolourFlags
forall x. HscolourFlags -> Rep HscolourFlags x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep HscolourFlags x -> HscolourFlags
$cfrom :: forall x. HscolourFlags -> Rep HscolourFlags x
Generic, Typeable)

emptyHscolourFlags :: HscolourFlags
emptyHscolourFlags :: HscolourFlags
emptyHscolourFlags = HscolourFlags
forall a. Monoid a => a
mempty

defaultHscolourFlags :: HscolourFlags
defaultHscolourFlags :: HscolourFlags
defaultHscolourFlags = HscolourFlags :: Flag FilePath
-> Flag Bool
-> Flag Bool
-> Flag Bool
-> Flag Bool
-> Flag FilePath
-> Flag Verbosity
-> Flag FilePath
-> HscolourFlags
HscolourFlags {
    hscolourCSS :: Flag FilePath
hscolourCSS         = Flag FilePath
forall a. Flag a
NoFlag,
    hscolourExecutables :: Flag Bool
hscolourExecutables = Bool -> Flag Bool
forall a. a -> Flag a
Flag Bool
False,
    hscolourTestSuites :: Flag Bool
hscolourTestSuites  = Bool -> Flag Bool
forall a. a -> Flag a
Flag Bool
False,
    hscolourBenchmarks :: Flag Bool
hscolourBenchmarks  = Bool -> Flag Bool
forall a. a -> Flag a
Flag Bool
False,
    hscolourDistPref :: Flag FilePath
hscolourDistPref    = Flag FilePath
forall a. Flag a
NoFlag,
    hscolourForeignLibs :: Flag Bool
hscolourForeignLibs = Bool -> Flag Bool
forall a. a -> Flag a
Flag Bool
False,
    hscolourVerbosity :: Flag Verbosity
hscolourVerbosity   = Verbosity -> Flag Verbosity
forall a. a -> Flag a
Flag Verbosity
normal,
    hscolourCabalFilePath :: Flag FilePath
hscolourCabalFilePath = Flag FilePath
forall a. Monoid a => a
mempty
  }

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

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

hscolourCommand :: CommandUI HscolourFlags
hscolourCommand :: CommandUI HscolourFlags
hscolourCommand = CommandUI :: forall flags.
FilePath
-> FilePath
-> (FilePath -> FilePath)
-> Maybe (FilePath -> FilePath)
-> Maybe (FilePath -> FilePath)
-> flags
-> (ShowOrParseArgs -> [OptionField flags])
-> CommandUI flags
CommandUI
  { commandName :: FilePath
commandName         = FilePath
"hscolour"
  , commandSynopsis :: FilePath
commandSynopsis     =
      FilePath
"Generate HsColour colourised code, in HTML format."
  , commandDescription :: Maybe (FilePath -> FilePath)
commandDescription  = (FilePath -> FilePath) -> Maybe (FilePath -> FilePath)
forall a. a -> Maybe a
Just (\FilePath
_ -> FilePath
"Requires the hscolour program.\n")
  , commandNotes :: Maybe (FilePath -> FilePath)
commandNotes        = (FilePath -> FilePath) -> Maybe (FilePath -> FilePath)
forall a. a -> Maybe a
Just ((FilePath -> FilePath) -> Maybe (FilePath -> FilePath))
-> (FilePath -> FilePath) -> Maybe (FilePath -> FilePath)
forall a b. (a -> b) -> a -> b
$ \FilePath
_ ->
      FilePath
"Deprecated in favour of 'cabal haddock --hyperlink-source'."
  , commandUsage :: FilePath -> FilePath
commandUsage        = \FilePath
pname ->
      FilePath
"Usage: " FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
pname FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
" hscolour [FLAGS]\n"
  , commandDefaultFlags :: HscolourFlags
commandDefaultFlags = HscolourFlags
defaultHscolourFlags
  , commandOptions :: ShowOrParseArgs -> [OptionField HscolourFlags]
commandOptions      = \ShowOrParseArgs
showOrParseArgs ->
      [(HscolourFlags -> Flag Verbosity)
-> (Flag Verbosity -> HscolourFlags -> HscolourFlags)
-> OptionField HscolourFlags
forall flags.
(flags -> Flag Verbosity)
-> (Flag Verbosity -> flags -> flags) -> OptionField flags
optionVerbosity HscolourFlags -> Flag Verbosity
hscolourVerbosity
       (\Flag Verbosity
v HscolourFlags
flags -> HscolourFlags
flags { hscolourVerbosity :: Flag Verbosity
hscolourVerbosity = Flag Verbosity
v })
      ,(HscolourFlags -> Flag FilePath)
-> (Flag FilePath -> HscolourFlags -> HscolourFlags)
-> ShowOrParseArgs
-> OptionField HscolourFlags
forall flags.
(flags -> Flag FilePath)
-> (Flag FilePath -> flags -> flags)
-> ShowOrParseArgs
-> OptionField flags
optionDistPref
         HscolourFlags -> Flag FilePath
hscolourDistPref (\Flag FilePath
d HscolourFlags
flags -> HscolourFlags
flags { hscolourDistPref :: Flag FilePath
hscolourDistPref = Flag FilePath
d })
         ShowOrParseArgs
showOrParseArgs

      ,FilePath
-> [FilePath]
-> FilePath
-> (HscolourFlags -> Flag Bool)
-> (Flag Bool -> HscolourFlags -> HscolourFlags)
-> MkOptDescr
     (HscolourFlags -> Flag Bool)
     (Flag Bool -> HscolourFlags -> HscolourFlags)
     HscolourFlags
-> OptionField HscolourFlags
forall get set a.
FilePath
-> [FilePath]
-> FilePath
-> get
-> set
-> MkOptDescr get set a
-> OptionField a
option FilePath
"" [FilePath
"executables"]
         FilePath
"Run hscolour for Executables targets"
         HscolourFlags -> Flag Bool
hscolourExecutables (\Flag Bool
v HscolourFlags
flags -> HscolourFlags
flags { hscolourExecutables :: Flag Bool
hscolourExecutables = Flag Bool
v })
         MkOptDescr
  (HscolourFlags -> Flag Bool)
  (Flag Bool -> HscolourFlags -> HscolourFlags)
  HscolourFlags
forall a. MkOptDescr (a -> Flag Bool) (Flag Bool -> a -> a) a
trueArg

      ,FilePath
-> [FilePath]
-> FilePath
-> (HscolourFlags -> Flag Bool)
-> (Flag Bool -> HscolourFlags -> HscolourFlags)
-> MkOptDescr
     (HscolourFlags -> Flag Bool)
     (Flag Bool -> HscolourFlags -> HscolourFlags)
     HscolourFlags
-> OptionField HscolourFlags
forall get set a.
FilePath
-> [FilePath]
-> FilePath
-> get
-> set
-> MkOptDescr get set a
-> OptionField a
option FilePath
"" [FilePath
"tests"]
         FilePath
"Run hscolour for Test Suite targets"
         HscolourFlags -> Flag Bool
hscolourTestSuites (\Flag Bool
v HscolourFlags
flags -> HscolourFlags
flags { hscolourTestSuites :: Flag Bool
hscolourTestSuites = Flag Bool
v })
         MkOptDescr
  (HscolourFlags -> Flag Bool)
  (Flag Bool -> HscolourFlags -> HscolourFlags)
  HscolourFlags
forall a. MkOptDescr (a -> Flag Bool) (Flag Bool -> a -> a) a
trueArg

      ,FilePath
-> [FilePath]
-> FilePath
-> (HscolourFlags -> Flag Bool)
-> (Flag Bool -> HscolourFlags -> HscolourFlags)
-> MkOptDescr
     (HscolourFlags -> Flag Bool)
     (Flag Bool -> HscolourFlags -> HscolourFlags)
     HscolourFlags
-> OptionField HscolourFlags
forall get set a.
FilePath
-> [FilePath]
-> FilePath
-> get
-> set
-> MkOptDescr get set a
-> OptionField a
option FilePath
"" [FilePath
"benchmarks"]
         FilePath
"Run hscolour for Benchmark targets"
         HscolourFlags -> Flag Bool
hscolourBenchmarks (\Flag Bool
v HscolourFlags
flags -> HscolourFlags
flags { hscolourBenchmarks :: Flag Bool
hscolourBenchmarks = Flag Bool
v })
         MkOptDescr
  (HscolourFlags -> Flag Bool)
  (Flag Bool -> HscolourFlags -> HscolourFlags)
  HscolourFlags
forall a. MkOptDescr (a -> Flag Bool) (Flag Bool -> a -> a) a
trueArg

      ,FilePath
-> [FilePath]
-> FilePath
-> (HscolourFlags -> Flag Bool)
-> (Flag Bool -> HscolourFlags -> HscolourFlags)
-> MkOptDescr
     (HscolourFlags -> Flag Bool)
     (Flag Bool -> HscolourFlags -> HscolourFlags)
     HscolourFlags
-> OptionField HscolourFlags
forall get set a.
FilePath
-> [FilePath]
-> FilePath
-> get
-> set
-> MkOptDescr get set a
-> OptionField a
option FilePath
"" [FilePath
"foreign-libraries"]
         FilePath
"Run hscolour for Foreign Library targets"
         HscolourFlags -> Flag Bool
hscolourForeignLibs (\Flag Bool
v HscolourFlags
flags -> HscolourFlags
flags { hscolourForeignLibs :: Flag Bool
hscolourForeignLibs = Flag Bool
v })
         MkOptDescr
  (HscolourFlags -> Flag Bool)
  (Flag Bool -> HscolourFlags -> HscolourFlags)
  HscolourFlags
forall a. MkOptDescr (a -> Flag Bool) (Flag Bool -> a -> a) a
trueArg

      ,FilePath
-> [FilePath]
-> FilePath
-> (HscolourFlags -> Flag Bool)
-> (Flag Bool -> HscolourFlags -> HscolourFlags)
-> MkOptDescr
     (HscolourFlags -> Flag Bool)
     (Flag Bool -> HscolourFlags -> HscolourFlags)
     HscolourFlags
-> OptionField HscolourFlags
forall get set a.
FilePath
-> [FilePath]
-> FilePath
-> get
-> set
-> MkOptDescr get set a
-> OptionField a
option FilePath
"" [FilePath
"all"]
         FilePath
"Run hscolour for all targets"
         (\HscolourFlags
f -> [Flag Bool] -> Flag Bool
allFlags [ HscolourFlags -> Flag Bool
hscolourExecutables HscolourFlags
f
                         , HscolourFlags -> Flag Bool
hscolourTestSuites  HscolourFlags
f
                         , HscolourFlags -> Flag Bool
hscolourBenchmarks  HscolourFlags
f
                         , HscolourFlags -> Flag Bool
hscolourForeignLibs HscolourFlags
f
                         ])
         (\Flag Bool
v HscolourFlags
flags -> HscolourFlags
flags { hscolourExecutables :: Flag Bool
hscolourExecutables = Flag Bool
v
                            , hscolourTestSuites :: Flag Bool
hscolourTestSuites  = Flag Bool
v
                            , hscolourBenchmarks :: Flag Bool
hscolourBenchmarks  = Flag Bool
v
                            , hscolourForeignLibs :: Flag Bool
hscolourForeignLibs = Flag Bool
v
                            })
         MkOptDescr
  (HscolourFlags -> Flag Bool)
  (Flag Bool -> HscolourFlags -> HscolourFlags)
  HscolourFlags
forall a. MkOptDescr (a -> Flag Bool) (Flag Bool -> a -> a) a
trueArg

      ,FilePath
-> [FilePath]
-> FilePath
-> (HscolourFlags -> Flag FilePath)
-> (Flag FilePath -> HscolourFlags -> HscolourFlags)
-> MkOptDescr
     (HscolourFlags -> Flag FilePath)
     (Flag FilePath -> HscolourFlags -> HscolourFlags)
     HscolourFlags
-> OptionField HscolourFlags
forall get set a.
FilePath
-> [FilePath]
-> FilePath
-> get
-> set
-> MkOptDescr get set a
-> OptionField a
option FilePath
"" [FilePath
"css"]
         FilePath
"Use a cascading style sheet"
         HscolourFlags -> Flag FilePath
hscolourCSS (\Flag FilePath
v HscolourFlags
flags -> HscolourFlags
flags { hscolourCSS :: Flag FilePath
hscolourCSS = Flag FilePath
v })
         (FilePath
-> MkOptDescr
     (HscolourFlags -> Flag FilePath)
     (Flag FilePath -> HscolourFlags -> HscolourFlags)
     HscolourFlags
forall b.
FilePath
-> FilePath
-> [FilePath]
-> FilePath
-> (b -> Flag FilePath)
-> (Flag FilePath -> b -> b)
-> OptDescr b
reqArgFlag FilePath
"PATH")
      ]
  }

-- ------------------------------------------------------------
-- * Doctest flags
-- ------------------------------------------------------------

data DoctestFlags = DoctestFlags {
    DoctestFlags -> [(FilePath, FilePath)]
doctestProgramPaths :: [(String, FilePath)],
    DoctestFlags -> [(FilePath, [FilePath])]
doctestProgramArgs  :: [(String, [String])],
    DoctestFlags -> Flag FilePath
doctestDistPref     :: Flag FilePath,
    DoctestFlags -> Flag Verbosity
doctestVerbosity    :: Flag Verbosity
  }
   deriving (Int -> DoctestFlags -> FilePath -> FilePath
[DoctestFlags] -> FilePath -> FilePath
DoctestFlags -> FilePath
(Int -> DoctestFlags -> FilePath -> FilePath)
-> (DoctestFlags -> FilePath)
-> ([DoctestFlags] -> FilePath -> FilePath)
-> Show DoctestFlags
forall a.
(Int -> a -> FilePath -> FilePath)
-> (a -> FilePath) -> ([a] -> FilePath -> FilePath) -> Show a
showList :: [DoctestFlags] -> FilePath -> FilePath
$cshowList :: [DoctestFlags] -> FilePath -> FilePath
show :: DoctestFlags -> FilePath
$cshow :: DoctestFlags -> FilePath
showsPrec :: Int -> DoctestFlags -> FilePath -> FilePath
$cshowsPrec :: Int -> DoctestFlags -> FilePath -> FilePath
Show, (forall x. DoctestFlags -> Rep DoctestFlags x)
-> (forall x. Rep DoctestFlags x -> DoctestFlags)
-> Generic DoctestFlags
forall x. Rep DoctestFlags x -> DoctestFlags
forall x. DoctestFlags -> Rep DoctestFlags x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep DoctestFlags x -> DoctestFlags
$cfrom :: forall x. DoctestFlags -> Rep DoctestFlags x
Generic, Typeable)

defaultDoctestFlags :: DoctestFlags
defaultDoctestFlags :: DoctestFlags
defaultDoctestFlags = DoctestFlags :: [(FilePath, FilePath)]
-> [(FilePath, [FilePath])]
-> Flag FilePath
-> Flag Verbosity
-> DoctestFlags
DoctestFlags {
    doctestProgramPaths :: [(FilePath, FilePath)]
doctestProgramPaths = [(FilePath, FilePath)]
forall a. Monoid a => a
mempty,
    doctestProgramArgs :: [(FilePath, [FilePath])]
doctestProgramArgs  = [],
    doctestDistPref :: Flag FilePath
doctestDistPref     = Flag FilePath
forall a. Flag a
NoFlag,
    doctestVerbosity :: Flag Verbosity
doctestVerbosity    = Verbosity -> Flag Verbosity
forall a. a -> Flag a
Flag Verbosity
normal
  }

doctestCommand :: CommandUI DoctestFlags
doctestCommand :: CommandUI DoctestFlags
doctestCommand = CommandUI :: forall flags.
FilePath
-> FilePath
-> (FilePath -> FilePath)
-> Maybe (FilePath -> FilePath)
-> Maybe (FilePath -> FilePath)
-> flags
-> (ShowOrParseArgs -> [OptionField flags])
-> CommandUI flags
CommandUI
  { commandName :: FilePath
commandName         = FilePath
"doctest"
  , commandSynopsis :: FilePath
commandSynopsis     = FilePath
"Run doctest tests."
  , commandDescription :: Maybe (FilePath -> FilePath)
commandDescription  = (FilePath -> FilePath) -> Maybe (FilePath -> FilePath)
forall a. a -> Maybe a
Just ((FilePath -> FilePath) -> Maybe (FilePath -> FilePath))
-> (FilePath -> FilePath) -> Maybe (FilePath -> FilePath)
forall a b. (a -> b) -> a -> b
$ \FilePath
_ ->
      FilePath
"Requires the program doctest, version 0.12.\n"
  , commandNotes :: Maybe (FilePath -> FilePath)
commandNotes        = Maybe (FilePath -> FilePath)
forall a. Maybe a
Nothing
  , commandUsage :: FilePath -> FilePath
commandUsage        = \FilePath
pname ->
      FilePath
"Usage: " FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
pname FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
" doctest [FLAGS]\n"
  , commandDefaultFlags :: DoctestFlags
commandDefaultFlags = DoctestFlags
defaultDoctestFlags
  , commandOptions :: ShowOrParseArgs -> [OptionField DoctestFlags]
commandOptions      = \ShowOrParseArgs
showOrParseArgs ->
         ShowOrParseArgs -> [OptionField DoctestFlags]
doctestOptions ShowOrParseArgs
showOrParseArgs
      [OptionField DoctestFlags]
-> [OptionField DoctestFlags] -> [OptionField DoctestFlags]
forall a. [a] -> [a] -> [a]
++ ProgramDb
-> ShowOrParseArgs
-> (DoctestFlags -> [(FilePath, FilePath)])
-> ([(FilePath, FilePath)] -> DoctestFlags -> DoctestFlags)
-> [OptionField DoctestFlags]
forall flags.
ProgramDb
-> ShowOrParseArgs
-> (flags -> [(FilePath, FilePath)])
-> ([(FilePath, FilePath)] -> flags -> flags)
-> [OptionField flags]
programDbPaths   ProgramDb
progDb ShowOrParseArgs
ParseArgs
             DoctestFlags -> [(FilePath, FilePath)]
doctestProgramPaths (\[(FilePath, FilePath)]
v DoctestFlags
flags -> DoctestFlags
flags { doctestProgramPaths :: [(FilePath, FilePath)]
doctestProgramPaths = [(FilePath, FilePath)]
v })
      [OptionField DoctestFlags]
-> [OptionField DoctestFlags] -> [OptionField DoctestFlags]
forall a. [a] -> [a] -> [a]
++ ProgramDb
-> ShowOrParseArgs
-> (DoctestFlags -> [(FilePath, [FilePath])])
-> ([(FilePath, [FilePath])] -> DoctestFlags -> DoctestFlags)
-> [OptionField DoctestFlags]
forall flags.
ProgramDb
-> ShowOrParseArgs
-> (flags -> [(FilePath, [FilePath])])
-> ([(FilePath, [FilePath])] -> flags -> flags)
-> [OptionField flags]
programDbOption  ProgramDb
progDb ShowOrParseArgs
showOrParseArgs
             DoctestFlags -> [(FilePath, [FilePath])]
doctestProgramArgs (\[(FilePath, [FilePath])]
v DoctestFlags
fs -> DoctestFlags
fs { doctestProgramArgs :: [(FilePath, [FilePath])]
doctestProgramArgs = [(FilePath, [FilePath])]
v })
      [OptionField DoctestFlags]
-> [OptionField DoctestFlags] -> [OptionField DoctestFlags]
forall a. [a] -> [a] -> [a]
++ ProgramDb
-> ShowOrParseArgs
-> (DoctestFlags -> [(FilePath, [FilePath])])
-> ([(FilePath, [FilePath])] -> DoctestFlags -> DoctestFlags)
-> [OptionField DoctestFlags]
forall flags.
ProgramDb
-> ShowOrParseArgs
-> (flags -> [(FilePath, [FilePath])])
-> ([(FilePath, [FilePath])] -> flags -> flags)
-> [OptionField flags]
programDbOptions ProgramDb
progDb ShowOrParseArgs
ParseArgs
             DoctestFlags -> [(FilePath, [FilePath])]
doctestProgramArgs (\[(FilePath, [FilePath])]
v DoctestFlags
flags -> DoctestFlags
flags { doctestProgramArgs :: [(FilePath, [FilePath])]
doctestProgramArgs = [(FilePath, [FilePath])]
v })
  }
  where
    progDb :: ProgramDb
progDb = Program -> ProgramDb -> ProgramDb
addKnownProgram Program
doctestProgram
             ProgramDb
emptyProgramDb

doctestOptions :: ShowOrParseArgs -> [OptionField DoctestFlags]
doctestOptions :: ShowOrParseArgs -> [OptionField DoctestFlags]
doctestOptions ShowOrParseArgs
showOrParseArgs =
  [(DoctestFlags -> Flag Verbosity)
-> (Flag Verbosity -> DoctestFlags -> DoctestFlags)
-> OptionField DoctestFlags
forall flags.
(flags -> Flag Verbosity)
-> (Flag Verbosity -> flags -> flags) -> OptionField flags
optionVerbosity DoctestFlags -> Flag Verbosity
doctestVerbosity
   (\Flag Verbosity
v DoctestFlags
flags -> DoctestFlags
flags { doctestVerbosity :: Flag Verbosity
doctestVerbosity = Flag Verbosity
v })
  ,(DoctestFlags -> Flag FilePath)
-> (Flag FilePath -> DoctestFlags -> DoctestFlags)
-> ShowOrParseArgs
-> OptionField DoctestFlags
forall flags.
(flags -> Flag FilePath)
-> (Flag FilePath -> flags -> flags)
-> ShowOrParseArgs
-> OptionField flags
optionDistPref
   DoctestFlags -> Flag FilePath
doctestDistPref (\Flag FilePath
d DoctestFlags
flags -> DoctestFlags
flags { doctestDistPref :: Flag FilePath
doctestDistPref = Flag FilePath
d })
   ShowOrParseArgs
showOrParseArgs
  ]

emptyDoctestFlags :: DoctestFlags
emptyDoctestFlags :: DoctestFlags
emptyDoctestFlags = DoctestFlags
forall a. Monoid a => a
mempty

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

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

-- ------------------------------------------------------------
-- * Haddock flags
-- ------------------------------------------------------------


-- | When we build haddock documentation, there are two cases:
--
-- 1. We build haddocks only for the current development version,
--    intended for local use and not for distribution. In this case,
--    we store the generated documentation in @<dist>/doc/html/<package name>@.
--
-- 2. We build haddocks for intended for uploading them to hackage.
--    In this case, we need to follow the layout that hackage expects
--    from documentation tarballs, and we might also want to use different
--    flags than for development builds, so in this case we store the generated
--    documentation in @<dist>/doc/html/<package id>-docs@.
data HaddockTarget = ForHackage | ForDevelopment deriving (HaddockTarget -> HaddockTarget -> Bool
(HaddockTarget -> HaddockTarget -> Bool)
-> (HaddockTarget -> HaddockTarget -> Bool) -> Eq HaddockTarget
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: HaddockTarget -> HaddockTarget -> Bool
$c/= :: HaddockTarget -> HaddockTarget -> Bool
== :: HaddockTarget -> HaddockTarget -> Bool
$c== :: HaddockTarget -> HaddockTarget -> Bool
Eq, Int -> HaddockTarget -> FilePath -> FilePath
[HaddockTarget] -> FilePath -> FilePath
HaddockTarget -> FilePath
(Int -> HaddockTarget -> FilePath -> FilePath)
-> (HaddockTarget -> FilePath)
-> ([HaddockTarget] -> FilePath -> FilePath)
-> Show HaddockTarget
forall a.
(Int -> a -> FilePath -> FilePath)
-> (a -> FilePath) -> ([a] -> FilePath -> FilePath) -> Show a
showList :: [HaddockTarget] -> FilePath -> FilePath
$cshowList :: [HaddockTarget] -> FilePath -> FilePath
show :: HaddockTarget -> FilePath
$cshow :: HaddockTarget -> FilePath
showsPrec :: Int -> HaddockTarget -> FilePath -> FilePath
$cshowsPrec :: Int -> HaddockTarget -> FilePath -> FilePath
Show, (forall x. HaddockTarget -> Rep HaddockTarget x)
-> (forall x. Rep HaddockTarget x -> HaddockTarget)
-> Generic HaddockTarget
forall x. Rep HaddockTarget x -> HaddockTarget
forall x. HaddockTarget -> Rep HaddockTarget x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep HaddockTarget x -> HaddockTarget
$cfrom :: forall x. HaddockTarget -> Rep HaddockTarget x
Generic, Typeable)

instance Binary HaddockTarget
instance Structured HaddockTarget

instance Pretty HaddockTarget where
    pretty :: HaddockTarget -> Doc
pretty HaddockTarget
ForHackage     = FilePath -> Doc
Disp.text FilePath
"for-hackage"
    pretty HaddockTarget
ForDevelopment = FilePath -> Doc
Disp.text FilePath
"for-development"

instance Parsec HaddockTarget where
    parsec :: m HaddockTarget
parsec = [m HaddockTarget] -> m HaddockTarget
forall (m :: * -> *) a. Alternative m => [m a] -> m a
P.choice [ m HaddockTarget -> m HaddockTarget
forall (m :: * -> *) a. Parsing m => m a -> m a
P.try (m HaddockTarget -> m HaddockTarget)
-> m HaddockTarget -> m HaddockTarget
forall a b. (a -> b) -> a -> b
$ FilePath -> m FilePath
forall (m :: * -> *). CharParsing m => FilePath -> m FilePath
P.string FilePath
"for-hackage"     m FilePath -> m HaddockTarget -> m HaddockTarget
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> HaddockTarget -> m HaddockTarget
forall (m :: * -> *) a. Monad m => a -> m a
return HaddockTarget
ForHackage
                      , FilePath -> m FilePath
forall (m :: * -> *). CharParsing m => FilePath -> m FilePath
P.string FilePath
"for-development" m FilePath -> m HaddockTarget -> m HaddockTarget
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> HaddockTarget -> m HaddockTarget
forall (m :: * -> *) a. Monad m => a -> m a
return HaddockTarget
ForDevelopment]

data HaddockFlags = HaddockFlags {
    HaddockFlags -> [(FilePath, FilePath)]
haddockProgramPaths :: [(String, FilePath)],
    HaddockFlags -> [(FilePath, [FilePath])]
haddockProgramArgs  :: [(String, [String])],
    HaddockFlags -> Flag Bool
haddockHoogle       :: Flag Bool,
    HaddockFlags -> Flag Bool
haddockHtml         :: Flag Bool,
    HaddockFlags -> Flag FilePath
haddockHtmlLocation :: Flag String,
    HaddockFlags -> Flag HaddockTarget
haddockForHackage   :: Flag HaddockTarget,
    HaddockFlags -> Flag Bool
haddockExecutables  :: Flag Bool,
    HaddockFlags -> Flag Bool
haddockTestSuites   :: Flag Bool,
    HaddockFlags -> Flag Bool
haddockBenchmarks   :: Flag Bool,
    HaddockFlags -> Flag Bool
haddockForeignLibs  :: Flag Bool,
    HaddockFlags -> Flag Bool
haddockInternal     :: Flag Bool,
    HaddockFlags -> Flag FilePath
haddockCss          :: Flag FilePath,
    HaddockFlags -> Flag Bool
haddockLinkedSource :: Flag Bool,
    HaddockFlags -> Flag Bool
haddockQuickJump    :: Flag Bool,
    HaddockFlags -> Flag FilePath
haddockHscolourCss  :: Flag FilePath,
    HaddockFlags -> Flag PathTemplate
haddockContents     :: Flag PathTemplate,
    HaddockFlags -> Flag FilePath
haddockDistPref     :: Flag FilePath,
    HaddockFlags -> Flag Bool
haddockKeepTempFiles:: Flag Bool,
    HaddockFlags -> Flag Verbosity
haddockVerbosity    :: Flag Verbosity,
    HaddockFlags -> Flag FilePath
haddockCabalFilePath :: Flag FilePath,
    HaddockFlags -> [FilePath]
haddockArgs         :: [String]
  }
  deriving (Int -> HaddockFlags -> FilePath -> FilePath
[HaddockFlags] -> FilePath -> FilePath
HaddockFlags -> FilePath
(Int -> HaddockFlags -> FilePath -> FilePath)
-> (HaddockFlags -> FilePath)
-> ([HaddockFlags] -> FilePath -> FilePath)
-> Show HaddockFlags
forall a.
(Int -> a -> FilePath -> FilePath)
-> (a -> FilePath) -> ([a] -> FilePath -> FilePath) -> Show a
showList :: [HaddockFlags] -> FilePath -> FilePath
$cshowList :: [HaddockFlags] -> FilePath -> FilePath
show :: HaddockFlags -> FilePath
$cshow :: HaddockFlags -> FilePath
showsPrec :: Int -> HaddockFlags -> FilePath -> FilePath
$cshowsPrec :: Int -> HaddockFlags -> FilePath -> FilePath
Show, (forall x. HaddockFlags -> Rep HaddockFlags x)
-> (forall x. Rep HaddockFlags x -> HaddockFlags)
-> Generic HaddockFlags
forall x. Rep HaddockFlags x -> HaddockFlags
forall x. HaddockFlags -> Rep HaddockFlags x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep HaddockFlags x -> HaddockFlags
$cfrom :: forall x. HaddockFlags -> Rep HaddockFlags x
Generic, Typeable)

defaultHaddockFlags :: HaddockFlags
defaultHaddockFlags :: HaddockFlags
defaultHaddockFlags  = HaddockFlags :: [(FilePath, FilePath)]
-> [(FilePath, [FilePath])]
-> Flag Bool
-> Flag Bool
-> Flag FilePath
-> Flag HaddockTarget
-> Flag Bool
-> Flag Bool
-> Flag Bool
-> Flag Bool
-> Flag Bool
-> Flag FilePath
-> Flag Bool
-> Flag Bool
-> Flag FilePath
-> Flag PathTemplate
-> Flag FilePath
-> Flag Bool
-> Flag Verbosity
-> Flag FilePath
-> [FilePath]
-> HaddockFlags
HaddockFlags {
    haddockProgramPaths :: [(FilePath, FilePath)]
haddockProgramPaths = [(FilePath, FilePath)]
forall a. Monoid a => a
mempty,
    haddockProgramArgs :: [(FilePath, [FilePath])]
haddockProgramArgs  = [],
    haddockHoogle :: Flag Bool
haddockHoogle       = Bool -> Flag Bool
forall a. a -> Flag a
Flag Bool
False,
    haddockHtml :: Flag Bool
haddockHtml         = Bool -> Flag Bool
forall a. a -> Flag a
Flag Bool
False,
    haddockHtmlLocation :: Flag FilePath
haddockHtmlLocation = Flag FilePath
forall a. Flag a
NoFlag,
    haddockForHackage :: Flag HaddockTarget
haddockForHackage   = Flag HaddockTarget
forall a. Flag a
NoFlag,
    haddockExecutables :: Flag Bool
haddockExecutables  = Bool -> Flag Bool
forall a. a -> Flag a
Flag Bool
False,
    haddockTestSuites :: Flag Bool
haddockTestSuites   = Bool -> Flag Bool
forall a. a -> Flag a
Flag Bool
False,
    haddockBenchmarks :: Flag Bool
haddockBenchmarks   = Bool -> Flag Bool
forall a. a -> Flag a
Flag Bool
False,
    haddockForeignLibs :: Flag Bool
haddockForeignLibs  = Bool -> Flag Bool
forall a. a -> Flag a
Flag Bool
False,
    haddockInternal :: Flag Bool
haddockInternal     = Bool -> Flag Bool
forall a. a -> Flag a
Flag Bool
False,
    haddockCss :: Flag FilePath
haddockCss          = Flag FilePath
forall a. Flag a
NoFlag,
    haddockLinkedSource :: Flag Bool
haddockLinkedSource = Bool -> Flag Bool
forall a. a -> Flag a
Flag Bool
False,
    haddockQuickJump :: Flag Bool
haddockQuickJump    = Bool -> Flag Bool
forall a. a -> Flag a
Flag Bool
False,
    haddockHscolourCss :: Flag FilePath
haddockHscolourCss  = Flag FilePath
forall a. Flag a
NoFlag,
    haddockContents :: Flag PathTemplate
haddockContents     = Flag PathTemplate
forall a. Flag a
NoFlag,
    haddockDistPref :: Flag FilePath
haddockDistPref     = Flag FilePath
forall a. Flag a
NoFlag,
    haddockKeepTempFiles :: Flag Bool
haddockKeepTempFiles= Bool -> Flag Bool
forall a. a -> Flag a
Flag Bool
False,
    haddockVerbosity :: Flag Verbosity
haddockVerbosity    = Verbosity -> Flag Verbosity
forall a. a -> Flag a
Flag Verbosity
normal,
    haddockCabalFilePath :: Flag FilePath
haddockCabalFilePath = Flag FilePath
forall a. Monoid a => a
mempty,
    haddockArgs :: [FilePath]
haddockArgs         = [FilePath]
forall a. Monoid a => a
mempty
  }

haddockCommand :: CommandUI HaddockFlags
haddockCommand :: CommandUI HaddockFlags
haddockCommand = CommandUI :: forall flags.
FilePath
-> FilePath
-> (FilePath -> FilePath)
-> Maybe (FilePath -> FilePath)
-> Maybe (FilePath -> FilePath)
-> flags
-> (ShowOrParseArgs -> [OptionField flags])
-> CommandUI flags
CommandUI
  { commandName :: FilePath
commandName         = FilePath
"haddock"
  , commandSynopsis :: FilePath
commandSynopsis     = FilePath
"Generate Haddock HTML documentation."
  , commandDescription :: Maybe (FilePath -> FilePath)
commandDescription  = (FilePath -> FilePath) -> Maybe (FilePath -> FilePath)
forall a. a -> Maybe a
Just ((FilePath -> FilePath) -> Maybe (FilePath -> FilePath))
-> (FilePath -> FilePath) -> Maybe (FilePath -> FilePath)
forall a b. (a -> b) -> a -> b
$ \FilePath
_ ->
      FilePath
"Requires the program haddock, version 2.x.\n"
  , commandNotes :: Maybe (FilePath -> FilePath)
commandNotes        = Maybe (FilePath -> FilePath)
forall a. Maybe a
Nothing
  , commandUsage :: FilePath -> FilePath
commandUsage        = FilePath -> [FilePath] -> FilePath -> FilePath
usageAlternatives FilePath
"haddock" ([FilePath] -> FilePath -> FilePath)
-> [FilePath] -> FilePath -> FilePath
forall a b. (a -> b) -> a -> b
$
      [ FilePath
"[FLAGS]"
      , FilePath
"COMPONENTS [FLAGS]"
      ]
  , commandDefaultFlags :: HaddockFlags
commandDefaultFlags = HaddockFlags
defaultHaddockFlags
  , commandOptions :: ShowOrParseArgs -> [OptionField HaddockFlags]
commandOptions      = \ShowOrParseArgs
showOrParseArgs ->
         ShowOrParseArgs -> [OptionField HaddockFlags]
haddockOptions ShowOrParseArgs
showOrParseArgs
      [OptionField HaddockFlags]
-> [OptionField HaddockFlags] -> [OptionField HaddockFlags]
forall a. [a] -> [a] -> [a]
++ ProgramDb
-> ShowOrParseArgs
-> (HaddockFlags -> [(FilePath, FilePath)])
-> ([(FilePath, FilePath)] -> HaddockFlags -> HaddockFlags)
-> [OptionField HaddockFlags]
forall flags.
ProgramDb
-> ShowOrParseArgs
-> (flags -> [(FilePath, FilePath)])
-> ([(FilePath, FilePath)] -> flags -> flags)
-> [OptionField flags]
programDbPaths   ProgramDb
progDb ShowOrParseArgs
ParseArgs
             HaddockFlags -> [(FilePath, FilePath)]
haddockProgramPaths (\[(FilePath, FilePath)]
v HaddockFlags
flags -> HaddockFlags
flags { haddockProgramPaths :: [(FilePath, FilePath)]
haddockProgramPaths = [(FilePath, FilePath)]
v})
      [OptionField HaddockFlags]
-> [OptionField HaddockFlags] -> [OptionField HaddockFlags]
forall a. [a] -> [a] -> [a]
++ ProgramDb
-> ShowOrParseArgs
-> (HaddockFlags -> [(FilePath, [FilePath])])
-> ([(FilePath, [FilePath])] -> HaddockFlags -> HaddockFlags)
-> [OptionField HaddockFlags]
forall flags.
ProgramDb
-> ShowOrParseArgs
-> (flags -> [(FilePath, [FilePath])])
-> ([(FilePath, [FilePath])] -> flags -> flags)
-> [OptionField flags]
programDbOption  ProgramDb
progDb ShowOrParseArgs
showOrParseArgs
             HaddockFlags -> [(FilePath, [FilePath])]
haddockProgramArgs (\[(FilePath, [FilePath])]
v HaddockFlags
fs -> HaddockFlags
fs { haddockProgramArgs :: [(FilePath, [FilePath])]
haddockProgramArgs = [(FilePath, [FilePath])]
v })
      [OptionField HaddockFlags]
-> [OptionField HaddockFlags] -> [OptionField HaddockFlags]
forall a. [a] -> [a] -> [a]
++ ProgramDb
-> ShowOrParseArgs
-> (HaddockFlags -> [(FilePath, [FilePath])])
-> ([(FilePath, [FilePath])] -> HaddockFlags -> HaddockFlags)
-> [OptionField HaddockFlags]
forall flags.
ProgramDb
-> ShowOrParseArgs
-> (flags -> [(FilePath, [FilePath])])
-> ([(FilePath, [FilePath])] -> flags -> flags)
-> [OptionField flags]
programDbOptions ProgramDb
progDb ShowOrParseArgs
ParseArgs
             HaddockFlags -> [(FilePath, [FilePath])]
haddockProgramArgs  (\[(FilePath, [FilePath])]
v HaddockFlags
flags -> HaddockFlags
flags { haddockProgramArgs :: [(FilePath, [FilePath])]
haddockProgramArgs = [(FilePath, [FilePath])]
v})
  }
  where
    progDb :: ProgramDb
progDb = Program -> ProgramDb -> ProgramDb
addKnownProgram Program
haddockProgram
             (ProgramDb -> ProgramDb) -> ProgramDb -> ProgramDb
forall a b. (a -> b) -> a -> b
$ Program -> ProgramDb -> ProgramDb
addKnownProgram Program
ghcProgram
             (ProgramDb -> ProgramDb) -> ProgramDb -> ProgramDb
forall a b. (a -> b) -> a -> b
$ ProgramDb
emptyProgramDb

haddockOptions :: ShowOrParseArgs -> [OptionField HaddockFlags]
haddockOptions :: ShowOrParseArgs -> [OptionField HaddockFlags]
haddockOptions ShowOrParseArgs
showOrParseArgs =
  [(HaddockFlags -> Flag Verbosity)
-> (Flag Verbosity -> HaddockFlags -> HaddockFlags)
-> OptionField HaddockFlags
forall flags.
(flags -> Flag Verbosity)
-> (Flag Verbosity -> flags -> flags) -> OptionField flags
optionVerbosity HaddockFlags -> Flag Verbosity
haddockVerbosity
   (\Flag Verbosity
v HaddockFlags
flags -> HaddockFlags
flags { haddockVerbosity :: Flag Verbosity
haddockVerbosity = Flag Verbosity
v })
  ,(HaddockFlags -> Flag FilePath)
-> (Flag FilePath -> HaddockFlags -> HaddockFlags)
-> ShowOrParseArgs
-> OptionField HaddockFlags
forall flags.
(flags -> Flag FilePath)
-> (Flag FilePath -> flags -> flags)
-> ShowOrParseArgs
-> OptionField flags
optionDistPref
   HaddockFlags -> Flag FilePath
haddockDistPref (\Flag FilePath
d HaddockFlags
flags -> HaddockFlags
flags { haddockDistPref :: Flag FilePath
haddockDistPref = Flag FilePath
d })
   ShowOrParseArgs
showOrParseArgs

  ,FilePath
-> [FilePath]
-> FilePath
-> (HaddockFlags -> Flag Bool)
-> (Flag Bool -> HaddockFlags -> HaddockFlags)
-> MkOptDescr
     (HaddockFlags -> Flag Bool)
     (Flag Bool -> HaddockFlags -> HaddockFlags)
     HaddockFlags
-> OptionField HaddockFlags
forall get set a.
FilePath
-> [FilePath]
-> FilePath
-> get
-> set
-> MkOptDescr get set a
-> OptionField a
option FilePath
"" [FilePath
"keep-temp-files"]
   FilePath
"Keep temporary files"
   HaddockFlags -> Flag Bool
haddockKeepTempFiles (\Flag Bool
b HaddockFlags
flags -> HaddockFlags
flags { haddockKeepTempFiles :: Flag Bool
haddockKeepTempFiles = Flag Bool
b })
   MkOptDescr
  (HaddockFlags -> Flag Bool)
  (Flag Bool -> HaddockFlags -> HaddockFlags)
  HaddockFlags
forall a. MkOptDescr (a -> Flag Bool) (Flag Bool -> a -> a) a
trueArg

  ,FilePath
-> [FilePath]
-> FilePath
-> (HaddockFlags -> Flag Bool)
-> (Flag Bool -> HaddockFlags -> HaddockFlags)
-> MkOptDescr
     (HaddockFlags -> Flag Bool)
     (Flag Bool -> HaddockFlags -> HaddockFlags)
     HaddockFlags
-> OptionField HaddockFlags
forall get set a.
FilePath
-> [FilePath]
-> FilePath
-> get
-> set
-> MkOptDescr get set a
-> OptionField a
option FilePath
"" [FilePath
"hoogle"]
   FilePath
"Generate a hoogle database"
   HaddockFlags -> Flag Bool
haddockHoogle (\Flag Bool
v HaddockFlags
flags -> HaddockFlags
flags { haddockHoogle :: Flag Bool
haddockHoogle = Flag Bool
v })
   MkOptDescr
  (HaddockFlags -> Flag Bool)
  (Flag Bool -> HaddockFlags -> HaddockFlags)
  HaddockFlags
forall a. MkOptDescr (a -> Flag Bool) (Flag Bool -> a -> a) a
trueArg

  ,FilePath
-> [FilePath]
-> FilePath
-> (HaddockFlags -> Flag Bool)
-> (Flag Bool -> HaddockFlags -> HaddockFlags)
-> MkOptDescr
     (HaddockFlags -> Flag Bool)
     (Flag Bool -> HaddockFlags -> HaddockFlags)
     HaddockFlags
-> OptionField HaddockFlags
forall get set a.
FilePath
-> [FilePath]
-> FilePath
-> get
-> set
-> MkOptDescr get set a
-> OptionField a
option FilePath
"" [FilePath
"html"]
   FilePath
"Generate HTML documentation (the default)"
   HaddockFlags -> Flag Bool
haddockHtml (\Flag Bool
v HaddockFlags
flags -> HaddockFlags
flags { haddockHtml :: Flag Bool
haddockHtml = Flag Bool
v })
   MkOptDescr
  (HaddockFlags -> Flag Bool)
  (Flag Bool -> HaddockFlags -> HaddockFlags)
  HaddockFlags
forall a. MkOptDescr (a -> Flag Bool) (Flag Bool -> a -> a) a
trueArg

  ,FilePath
-> [FilePath]
-> FilePath
-> (HaddockFlags -> Flag FilePath)
-> (Flag FilePath -> HaddockFlags -> HaddockFlags)
-> MkOptDescr
     (HaddockFlags -> Flag FilePath)
     (Flag FilePath -> HaddockFlags -> HaddockFlags)
     HaddockFlags
-> OptionField HaddockFlags
forall get set a.
FilePath
-> [FilePath]
-> FilePath
-> get
-> set
-> MkOptDescr get set a
-> OptionField a
option FilePath
"" [FilePath
"html-location"]
   FilePath
"Location of HTML documentation for pre-requisite packages"
   HaddockFlags -> Flag FilePath
haddockHtmlLocation (\Flag FilePath
v HaddockFlags
flags -> HaddockFlags
flags { haddockHtmlLocation :: Flag FilePath
haddockHtmlLocation = Flag FilePath
v })
   (FilePath
-> MkOptDescr
     (HaddockFlags -> Flag FilePath)
     (Flag FilePath -> HaddockFlags -> HaddockFlags)
     HaddockFlags
forall b.
FilePath
-> FilePath
-> [FilePath]
-> FilePath
-> (b -> Flag FilePath)
-> (Flag FilePath -> b -> b)
-> OptDescr b
reqArgFlag FilePath
"URL")

  ,FilePath
-> [FilePath]
-> FilePath
-> (HaddockFlags -> Flag HaddockTarget)
-> (Flag HaddockTarget -> HaddockFlags -> HaddockFlags)
-> MkOptDescr
     (HaddockFlags -> Flag HaddockTarget)
     (Flag HaddockTarget -> HaddockFlags -> HaddockFlags)
     HaddockFlags
-> OptionField HaddockFlags
forall get set a.
FilePath
-> [FilePath]
-> FilePath
-> get
-> set
-> MkOptDescr get set a
-> OptionField a
option FilePath
"" [FilePath
"for-hackage"]
   FilePath
"Collection of flags to generate documentation suitable for upload to hackage"
   HaddockFlags -> Flag HaddockTarget
haddockForHackage (\Flag HaddockTarget
v HaddockFlags
flags -> HaddockFlags
flags { haddockForHackage :: Flag HaddockTarget
haddockForHackage = Flag HaddockTarget
v })
   (Flag HaddockTarget
-> MkOptDescr
     (HaddockFlags -> Flag HaddockTarget)
     (Flag HaddockTarget -> HaddockFlags -> HaddockFlags)
     HaddockFlags
forall b a. Eq b => b -> MkOptDescr (a -> b) (b -> a -> a) a
noArg (HaddockTarget -> Flag HaddockTarget
forall a. a -> Flag a
Flag HaddockTarget
ForHackage))

  ,FilePath
-> [FilePath]
-> FilePath
-> (HaddockFlags -> Flag Bool)
-> (Flag Bool -> HaddockFlags -> HaddockFlags)
-> MkOptDescr
     (HaddockFlags -> Flag Bool)
     (Flag Bool -> HaddockFlags -> HaddockFlags)
     HaddockFlags
-> OptionField HaddockFlags
forall get set a.
FilePath
-> [FilePath]
-> FilePath
-> get
-> set
-> MkOptDescr get set a
-> OptionField a
option FilePath
"" [FilePath
"executables"]
   FilePath
"Run haddock for Executables targets"
   HaddockFlags -> Flag Bool
haddockExecutables (\Flag Bool
v HaddockFlags
flags -> HaddockFlags
flags { haddockExecutables :: Flag Bool
haddockExecutables = Flag Bool
v })
   MkOptDescr
  (HaddockFlags -> Flag Bool)
  (Flag Bool -> HaddockFlags -> HaddockFlags)
  HaddockFlags
forall a. MkOptDescr (a -> Flag Bool) (Flag Bool -> a -> a) a
trueArg

  ,FilePath
-> [FilePath]
-> FilePath
-> (HaddockFlags -> Flag Bool)
-> (Flag Bool -> HaddockFlags -> HaddockFlags)
-> MkOptDescr
     (HaddockFlags -> Flag Bool)
     (Flag Bool -> HaddockFlags -> HaddockFlags)
     HaddockFlags
-> OptionField HaddockFlags
forall get set a.
FilePath
-> [FilePath]
-> FilePath
-> get
-> set
-> MkOptDescr get set a
-> OptionField a
option FilePath
"" [FilePath
"tests"]
   FilePath
"Run haddock for Test Suite targets"
   HaddockFlags -> Flag Bool
haddockTestSuites (\Flag Bool
v HaddockFlags
flags -> HaddockFlags
flags { haddockTestSuites :: Flag Bool
haddockTestSuites = Flag Bool
v })
   MkOptDescr
  (HaddockFlags -> Flag Bool)
  (Flag Bool -> HaddockFlags -> HaddockFlags)
  HaddockFlags
forall a. MkOptDescr (a -> Flag Bool) (Flag Bool -> a -> a) a
trueArg

  ,FilePath
-> [FilePath]
-> FilePath
-> (HaddockFlags -> Flag Bool)
-> (Flag Bool -> HaddockFlags -> HaddockFlags)
-> MkOptDescr
     (HaddockFlags -> Flag Bool)
     (Flag Bool -> HaddockFlags -> HaddockFlags)
     HaddockFlags
-> OptionField HaddockFlags
forall get set a.
FilePath
-> [FilePath]
-> FilePath
-> get
-> set
-> MkOptDescr get set a
-> OptionField a
option FilePath
"" [FilePath
"benchmarks"]
   FilePath
"Run haddock for Benchmark targets"
   HaddockFlags -> Flag Bool
haddockBenchmarks (\Flag Bool
v HaddockFlags
flags -> HaddockFlags
flags { haddockBenchmarks :: Flag Bool
haddockBenchmarks = Flag Bool
v })
   MkOptDescr
  (HaddockFlags -> Flag Bool)
  (Flag Bool -> HaddockFlags -> HaddockFlags)
  HaddockFlags
forall a. MkOptDescr (a -> Flag Bool) (Flag Bool -> a -> a) a
trueArg

  ,FilePath
-> [FilePath]
-> FilePath
-> (HaddockFlags -> Flag Bool)
-> (Flag Bool -> HaddockFlags -> HaddockFlags)
-> MkOptDescr
     (HaddockFlags -> Flag Bool)
     (Flag Bool -> HaddockFlags -> HaddockFlags)
     HaddockFlags
-> OptionField HaddockFlags
forall get set a.
FilePath
-> [FilePath]
-> FilePath
-> get
-> set
-> MkOptDescr get set a
-> OptionField a
option FilePath
"" [FilePath
"foreign-libraries"]
   FilePath
"Run haddock for Foreign Library targets"
   HaddockFlags -> Flag Bool
haddockForeignLibs (\Flag Bool
v HaddockFlags
flags -> HaddockFlags
flags { haddockForeignLibs :: Flag Bool
haddockForeignLibs = Flag Bool
v })
   MkOptDescr
  (HaddockFlags -> Flag Bool)
  (Flag Bool -> HaddockFlags -> HaddockFlags)
  HaddockFlags
forall a. MkOptDescr (a -> Flag Bool) (Flag Bool -> a -> a) a
trueArg

  ,FilePath
-> [FilePath]
-> FilePath
-> (HaddockFlags -> Flag Bool)
-> (Flag Bool -> HaddockFlags -> HaddockFlags)
-> MkOptDescr
     (HaddockFlags -> Flag Bool)
     (Flag Bool -> HaddockFlags -> HaddockFlags)
     HaddockFlags
-> OptionField HaddockFlags
forall get set a.
FilePath
-> [FilePath]
-> FilePath
-> get
-> set
-> MkOptDescr get set a
-> OptionField a
option FilePath
"" [FilePath
"all"]
   FilePath
"Run haddock for all targets"
   (\HaddockFlags
f -> [Flag Bool] -> Flag Bool
allFlags [ HaddockFlags -> Flag Bool
haddockExecutables HaddockFlags
f
                   , HaddockFlags -> Flag Bool
haddockTestSuites  HaddockFlags
f
                   , HaddockFlags -> Flag Bool
haddockBenchmarks  HaddockFlags
f
                   , HaddockFlags -> Flag Bool
haddockForeignLibs HaddockFlags
f
                   ])
         (\Flag Bool
v HaddockFlags
flags -> HaddockFlags
flags { haddockExecutables :: Flag Bool
haddockExecutables = Flag Bool
v
                            , haddockTestSuites :: Flag Bool
haddockTestSuites  = Flag Bool
v
                            , haddockBenchmarks :: Flag Bool
haddockBenchmarks  = Flag Bool
v
                            , haddockForeignLibs :: Flag Bool
haddockForeignLibs = Flag Bool
v
                            })
         MkOptDescr
  (HaddockFlags -> Flag Bool)
  (Flag Bool -> HaddockFlags -> HaddockFlags)
  HaddockFlags
forall a. MkOptDescr (a -> Flag Bool) (Flag Bool -> a -> a) a
trueArg

  ,FilePath
-> [FilePath]
-> FilePath
-> (HaddockFlags -> Flag Bool)
-> (Flag Bool -> HaddockFlags -> HaddockFlags)
-> MkOptDescr
     (HaddockFlags -> Flag Bool)
     (Flag Bool -> HaddockFlags -> HaddockFlags)
     HaddockFlags
-> OptionField HaddockFlags
forall get set a.
FilePath
-> [FilePath]
-> FilePath
-> get
-> set
-> MkOptDescr get set a
-> OptionField a
option FilePath
"" [FilePath
"internal"]
   FilePath
"Run haddock for internal modules and include all symbols"
   HaddockFlags -> Flag Bool
haddockInternal (\Flag Bool
v HaddockFlags
flags -> HaddockFlags
flags { haddockInternal :: Flag Bool
haddockInternal = Flag Bool
v })
   MkOptDescr
  (HaddockFlags -> Flag Bool)
  (Flag Bool -> HaddockFlags -> HaddockFlags)
  HaddockFlags
forall a. MkOptDescr (a -> Flag Bool) (Flag Bool -> a -> a) a
trueArg

  ,FilePath
-> [FilePath]
-> FilePath
-> (HaddockFlags -> Flag FilePath)
-> (Flag FilePath -> HaddockFlags -> HaddockFlags)
-> MkOptDescr
     (HaddockFlags -> Flag FilePath)
     (Flag FilePath -> HaddockFlags -> HaddockFlags)
     HaddockFlags
-> OptionField HaddockFlags
forall get set a.
FilePath
-> [FilePath]
-> FilePath
-> get
-> set
-> MkOptDescr get set a
-> OptionField a
option FilePath
"" [FilePath
"css"]
   FilePath
"Use PATH as the haddock stylesheet"
   HaddockFlags -> Flag FilePath
haddockCss (\Flag FilePath
v HaddockFlags
flags -> HaddockFlags
flags { haddockCss :: Flag FilePath
haddockCss = Flag FilePath
v })
   (FilePath
-> MkOptDescr
     (HaddockFlags -> Flag FilePath)
     (Flag FilePath -> HaddockFlags -> HaddockFlags)
     HaddockFlags
forall b.
FilePath
-> FilePath
-> [FilePath]
-> FilePath
-> (b -> Flag FilePath)
-> (Flag FilePath -> b -> b)
-> OptDescr b
reqArgFlag FilePath
"PATH")

  ,FilePath
-> [FilePath]
-> FilePath
-> (HaddockFlags -> Flag Bool)
-> (Flag Bool -> HaddockFlags -> HaddockFlags)
-> MkOptDescr
     (HaddockFlags -> Flag Bool)
     (Flag Bool -> HaddockFlags -> HaddockFlags)
     HaddockFlags
-> OptionField HaddockFlags
forall get set a.
FilePath
-> [FilePath]
-> FilePath
-> get
-> set
-> MkOptDescr get set a
-> OptionField a
option FilePath
"" [FilePath
"hyperlink-source",FilePath
"hyperlink-sources",FilePath
"hyperlinked-source"]
   FilePath
"Hyperlink the documentation to the source code"
   HaddockFlags -> Flag Bool
haddockLinkedSource (\Flag Bool
v HaddockFlags
flags -> HaddockFlags
flags { haddockLinkedSource :: Flag Bool
haddockLinkedSource = Flag Bool
v })
   MkOptDescr
  (HaddockFlags -> Flag Bool)
  (Flag Bool -> HaddockFlags -> HaddockFlags)
  HaddockFlags
forall a. MkOptDescr (a -> Flag Bool) (Flag Bool -> a -> a) a
trueArg

  ,FilePath
-> [FilePath]
-> FilePath
-> (HaddockFlags -> Flag Bool)
-> (Flag Bool -> HaddockFlags -> HaddockFlags)
-> MkOptDescr
     (HaddockFlags -> Flag Bool)
     (Flag Bool -> HaddockFlags -> HaddockFlags)
     HaddockFlags
-> OptionField HaddockFlags
forall get set a.
FilePath
-> [FilePath]
-> FilePath
-> get
-> set
-> MkOptDescr get set a
-> OptionField a
option FilePath
"" [FilePath
"quickjump"]
   FilePath
"Generate an index for interactive documentation navigation"
   HaddockFlags -> Flag Bool
haddockQuickJump (\Flag Bool
v HaddockFlags
flags -> HaddockFlags
flags { haddockQuickJump :: Flag Bool
haddockQuickJump = Flag Bool
v })
   MkOptDescr
  (HaddockFlags -> Flag Bool)
  (Flag Bool -> HaddockFlags -> HaddockFlags)
  HaddockFlags
forall a. MkOptDescr (a -> Flag Bool) (Flag Bool -> a -> a) a
trueArg

  ,FilePath
-> [FilePath]
-> FilePath
-> (HaddockFlags -> Flag FilePath)
-> (Flag FilePath -> HaddockFlags -> HaddockFlags)
-> MkOptDescr
     (HaddockFlags -> Flag FilePath)
     (Flag FilePath -> HaddockFlags -> HaddockFlags)
     HaddockFlags
-> OptionField HaddockFlags
forall get set a.
FilePath
-> [FilePath]
-> FilePath
-> get
-> set
-> MkOptDescr get set a
-> OptionField a
option FilePath
"" [FilePath
"hscolour-css"]
   FilePath
"Use PATH as the HsColour stylesheet"
   HaddockFlags -> Flag FilePath
haddockHscolourCss (\Flag FilePath
v HaddockFlags
flags -> HaddockFlags
flags { haddockHscolourCss :: Flag FilePath
haddockHscolourCss = Flag FilePath
v })
   (FilePath
-> MkOptDescr
     (HaddockFlags -> Flag FilePath)
     (Flag FilePath -> HaddockFlags -> HaddockFlags)
     HaddockFlags
forall b.
FilePath
-> FilePath
-> [FilePath]
-> FilePath
-> (b -> Flag FilePath)
-> (Flag FilePath -> b -> b)
-> OptDescr b
reqArgFlag FilePath
"PATH")

  ,FilePath
-> [FilePath]
-> FilePath
-> (HaddockFlags -> Flag PathTemplate)
-> (Flag PathTemplate -> HaddockFlags -> HaddockFlags)
-> MkOptDescr
     (HaddockFlags -> Flag PathTemplate)
     (Flag PathTemplate -> HaddockFlags -> HaddockFlags)
     HaddockFlags
-> OptionField HaddockFlags
forall get set a.
FilePath
-> [FilePath]
-> FilePath
-> get
-> set
-> MkOptDescr get set a
-> OptionField a
option FilePath
"" [FilePath
"contents-location"]
   FilePath
"Bake URL in as the location for the contents page"
   HaddockFlags -> Flag PathTemplate
haddockContents (\Flag PathTemplate
v HaddockFlags
flags -> HaddockFlags
flags { haddockContents :: Flag PathTemplate
haddockContents = Flag PathTemplate
v })
   (FilePath
-> (FilePath -> Flag PathTemplate)
-> (Flag PathTemplate -> [FilePath])
-> MkOptDescr
     (HaddockFlags -> Flag PathTemplate)
     (Flag PathTemplate -> HaddockFlags -> HaddockFlags)
     HaddockFlags
forall b a.
Monoid b =>
FilePath
-> (FilePath -> b)
-> (b -> [FilePath])
-> MkOptDescr (a -> b) (b -> a -> a) a
reqArg' FilePath
"URL"
    (PathTemplate -> Flag PathTemplate
forall a. a -> Flag a
toFlag (PathTemplate -> Flag PathTemplate)
-> (FilePath -> PathTemplate) -> FilePath -> Flag PathTemplate
forall b c a. (b -> c) -> (a -> b) -> a -> c
. FilePath -> PathTemplate
toPathTemplate)
    (Flag FilePath -> [FilePath]
forall a. Flag a -> [a]
flagToList (Flag FilePath -> [FilePath])
-> (Flag PathTemplate -> Flag FilePath)
-> Flag PathTemplate
-> [FilePath]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (PathTemplate -> FilePath) -> Flag PathTemplate -> Flag FilePath
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap PathTemplate -> FilePath
fromPathTemplate))
  ]

emptyHaddockFlags :: HaddockFlags
emptyHaddockFlags :: HaddockFlags
emptyHaddockFlags = HaddockFlags
forall a. Monoid a => a
mempty

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

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

-- ------------------------------------------------------------
-- * Clean flags
-- ------------------------------------------------------------

data CleanFlags = CleanFlags {
    CleanFlags -> Flag Bool
cleanSaveConf  :: Flag Bool,
    CleanFlags -> Flag FilePath
cleanDistPref  :: Flag FilePath,
    CleanFlags -> Flag Verbosity
cleanVerbosity :: Flag Verbosity,
    CleanFlags -> Flag FilePath
cleanCabalFilePath :: Flag FilePath
  }
  deriving (Int -> CleanFlags -> FilePath -> FilePath
[CleanFlags] -> FilePath -> FilePath
CleanFlags -> FilePath
(Int -> CleanFlags -> FilePath -> FilePath)
-> (CleanFlags -> FilePath)
-> ([CleanFlags] -> FilePath -> FilePath)
-> Show CleanFlags
forall a.
(Int -> a -> FilePath -> FilePath)
-> (a -> FilePath) -> ([a] -> FilePath -> FilePath) -> Show a
showList :: [CleanFlags] -> FilePath -> FilePath
$cshowList :: [CleanFlags] -> FilePath -> FilePath
show :: CleanFlags -> FilePath
$cshow :: CleanFlags -> FilePath
showsPrec :: Int -> CleanFlags -> FilePath -> FilePath
$cshowsPrec :: Int -> CleanFlags -> FilePath -> FilePath
Show, (forall x. CleanFlags -> Rep CleanFlags x)
-> (forall x. Rep CleanFlags x -> CleanFlags) -> Generic CleanFlags
forall x. Rep CleanFlags x -> CleanFlags
forall x. CleanFlags -> Rep CleanFlags x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep CleanFlags x -> CleanFlags
$cfrom :: forall x. CleanFlags -> Rep CleanFlags x
Generic, Typeable)

defaultCleanFlags :: CleanFlags
defaultCleanFlags :: CleanFlags
defaultCleanFlags  = CleanFlags :: Flag Bool
-> Flag FilePath -> Flag Verbosity -> Flag FilePath -> CleanFlags
CleanFlags {
    cleanSaveConf :: Flag Bool
cleanSaveConf  = Bool -> Flag Bool
forall a. a -> Flag a
Flag Bool
False,
    cleanDistPref :: Flag FilePath
cleanDistPref  = Flag FilePath
forall a. Flag a
NoFlag,
    cleanVerbosity :: Flag Verbosity
cleanVerbosity = Verbosity -> Flag Verbosity
forall a. a -> Flag a
Flag Verbosity
normal,
    cleanCabalFilePath :: Flag FilePath
cleanCabalFilePath = Flag FilePath
forall a. Monoid a => a
mempty
  }

cleanCommand :: CommandUI CleanFlags
cleanCommand :: CommandUI CleanFlags
cleanCommand = CommandUI :: forall flags.
FilePath
-> FilePath
-> (FilePath -> FilePath)
-> Maybe (FilePath -> FilePath)
-> Maybe (FilePath -> FilePath)
-> flags
-> (ShowOrParseArgs -> [OptionField flags])
-> CommandUI flags
CommandUI
  { commandName :: FilePath
commandName         = FilePath
"clean"
  , commandSynopsis :: FilePath
commandSynopsis     = FilePath
"Clean up after a build."
  , commandDescription :: Maybe (FilePath -> FilePath)
commandDescription  = (FilePath -> FilePath) -> Maybe (FilePath -> FilePath)
forall a. a -> Maybe a
Just ((FilePath -> FilePath) -> Maybe (FilePath -> FilePath))
-> (FilePath -> FilePath) -> Maybe (FilePath -> FilePath)
forall a b. (a -> b) -> a -> b
$ \FilePath
_ ->
      FilePath
"Removes .hi, .o, preprocessed sources, etc.\n"
  , commandNotes :: Maybe (FilePath -> FilePath)
commandNotes        = Maybe (FilePath -> FilePath)
forall a. Maybe a
Nothing
  , commandUsage :: FilePath -> FilePath
commandUsage        = \FilePath
pname ->
      FilePath
"Usage: " FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
pname FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
" clean [FLAGS]\n"
  , commandDefaultFlags :: CleanFlags
commandDefaultFlags = CleanFlags
defaultCleanFlags
  , commandOptions :: ShowOrParseArgs -> [OptionField CleanFlags]
commandOptions      = \ShowOrParseArgs
showOrParseArgs ->
      [(CleanFlags -> Flag Verbosity)
-> (Flag Verbosity -> CleanFlags -> CleanFlags)
-> OptionField CleanFlags
forall flags.
(flags -> Flag Verbosity)
-> (Flag Verbosity -> flags -> flags) -> OptionField flags
optionVerbosity CleanFlags -> Flag Verbosity
cleanVerbosity (\Flag Verbosity
v CleanFlags
flags -> CleanFlags
flags { cleanVerbosity :: Flag Verbosity
cleanVerbosity = Flag Verbosity
v })
      ,(CleanFlags -> Flag FilePath)
-> (Flag FilePath -> CleanFlags -> CleanFlags)
-> ShowOrParseArgs
-> OptionField CleanFlags
forall flags.
(flags -> Flag FilePath)
-> (Flag FilePath -> flags -> flags)
-> ShowOrParseArgs
-> OptionField flags
optionDistPref
         CleanFlags -> Flag FilePath
cleanDistPref (\Flag FilePath
d CleanFlags
flags -> CleanFlags
flags { cleanDistPref :: Flag FilePath
cleanDistPref = Flag FilePath
d })
         ShowOrParseArgs
showOrParseArgs

      ,FilePath
-> [FilePath]
-> FilePath
-> (CleanFlags -> Flag Bool)
-> (Flag Bool -> CleanFlags -> CleanFlags)
-> MkOptDescr
     (CleanFlags -> Flag Bool)
     (Flag Bool -> CleanFlags -> CleanFlags)
     CleanFlags
-> OptionField CleanFlags
forall get set a.
FilePath
-> [FilePath]
-> FilePath
-> get
-> set
-> MkOptDescr get set a
-> OptionField a
option FilePath
"s" [FilePath
"save-configure"]
         FilePath
"Do not remove the configuration file (dist/setup-config) during cleaning.  Saves need to reconfigure."
         CleanFlags -> Flag Bool
cleanSaveConf (\Flag Bool
v CleanFlags
flags -> CleanFlags
flags { cleanSaveConf :: Flag Bool
cleanSaveConf = Flag Bool
v })
         MkOptDescr
  (CleanFlags -> Flag Bool)
  (Flag Bool -> CleanFlags -> CleanFlags)
  CleanFlags
forall a. MkOptDescr (a -> Flag Bool) (Flag Bool -> a -> a) a
trueArg
      ]
  }

emptyCleanFlags :: CleanFlags
emptyCleanFlags :: CleanFlags
emptyCleanFlags = CleanFlags
forall a. Monoid a => a
mempty

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

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

-- ------------------------------------------------------------
-- * Build flags
-- ------------------------------------------------------------

data BuildFlags = BuildFlags {
    BuildFlags -> [(FilePath, FilePath)]
buildProgramPaths :: [(String, FilePath)],
    BuildFlags -> [(FilePath, [FilePath])]
buildProgramArgs :: [(String, [String])],
    BuildFlags -> Flag FilePath
buildDistPref    :: Flag FilePath,
    BuildFlags -> Flag Verbosity
buildVerbosity   :: Flag Verbosity,
    BuildFlags -> Flag (Maybe Int)
buildNumJobs     :: Flag (Maybe Int),
    -- TODO: this one should not be here, it's just that the silly
    -- UserHooks stop us from passing extra info in other ways
    BuildFlags -> [FilePath]
buildArgs :: [String],
    BuildFlags -> Flag FilePath
buildCabalFilePath :: Flag FilePath
  }
  deriving (ReadPrec [BuildFlags]
ReadPrec BuildFlags
Int -> ReadS BuildFlags
ReadS [BuildFlags]
(Int -> ReadS BuildFlags)
-> ReadS [BuildFlags]
-> ReadPrec BuildFlags
-> ReadPrec [BuildFlags]
-> Read BuildFlags
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [BuildFlags]
$creadListPrec :: ReadPrec [BuildFlags]
readPrec :: ReadPrec BuildFlags
$creadPrec :: ReadPrec BuildFlags
readList :: ReadS [BuildFlags]
$creadList :: ReadS [BuildFlags]
readsPrec :: Int -> ReadS BuildFlags
$creadsPrec :: Int -> ReadS BuildFlags
Read, Int -> BuildFlags -> FilePath -> FilePath
[BuildFlags] -> FilePath -> FilePath
BuildFlags -> FilePath
(Int -> BuildFlags -> FilePath -> FilePath)
-> (BuildFlags -> FilePath)
-> ([BuildFlags] -> FilePath -> FilePath)
-> Show BuildFlags
forall a.
(Int -> a -> FilePath -> FilePath)
-> (a -> FilePath) -> ([a] -> FilePath -> FilePath) -> Show a
showList :: [BuildFlags] -> FilePath -> FilePath
$cshowList :: [BuildFlags] -> FilePath -> FilePath
show :: BuildFlags -> FilePath
$cshow :: BuildFlags -> FilePath
showsPrec :: Int -> BuildFlags -> FilePath -> FilePath
$cshowsPrec :: Int -> BuildFlags -> FilePath -> FilePath
Show, (forall x. BuildFlags -> Rep BuildFlags x)
-> (forall x. Rep BuildFlags x -> BuildFlags) -> Generic BuildFlags
forall x. Rep BuildFlags x -> BuildFlags
forall x. BuildFlags -> Rep BuildFlags x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep BuildFlags x -> BuildFlags
$cfrom :: forall x. BuildFlags -> Rep BuildFlags x
Generic, Typeable)

defaultBuildFlags :: BuildFlags
defaultBuildFlags :: BuildFlags
defaultBuildFlags  = BuildFlags :: [(FilePath, FilePath)]
-> [(FilePath, [FilePath])]
-> Flag FilePath
-> Flag Verbosity
-> Flag (Maybe Int)
-> [FilePath]
-> Flag FilePath
-> BuildFlags
BuildFlags {
    buildProgramPaths :: [(FilePath, FilePath)]
buildProgramPaths = [(FilePath, FilePath)]
forall a. Monoid a => a
mempty,
    buildProgramArgs :: [(FilePath, [FilePath])]
buildProgramArgs = [],
    buildDistPref :: Flag FilePath
buildDistPref    = Flag FilePath
forall a. Monoid a => a
mempty,
    buildVerbosity :: Flag Verbosity
buildVerbosity   = Verbosity -> Flag Verbosity
forall a. a -> Flag a
Flag Verbosity
normal,
    buildNumJobs :: Flag (Maybe Int)
buildNumJobs     = Flag (Maybe Int)
forall a. Monoid a => a
mempty,
    buildArgs :: [FilePath]
buildArgs        = [],
    buildCabalFilePath :: Flag FilePath
buildCabalFilePath = Flag FilePath
forall a. Monoid a => a
mempty
  }

buildCommand :: ProgramDb -> CommandUI BuildFlags
buildCommand :: ProgramDb -> CommandUI BuildFlags
buildCommand ProgramDb
progDb = CommandUI :: forall flags.
FilePath
-> FilePath
-> (FilePath -> FilePath)
-> Maybe (FilePath -> FilePath)
-> Maybe (FilePath -> FilePath)
-> flags
-> (ShowOrParseArgs -> [OptionField flags])
-> CommandUI flags
CommandUI
  { commandName :: FilePath
commandName         = FilePath
"build"
  , commandSynopsis :: FilePath
commandSynopsis     = FilePath
"Compile all/specific components."
  , commandDescription :: Maybe (FilePath -> FilePath)
commandDescription  = (FilePath -> FilePath) -> Maybe (FilePath -> FilePath)
forall a. a -> Maybe a
Just ((FilePath -> FilePath) -> Maybe (FilePath -> FilePath))
-> (FilePath -> FilePath) -> Maybe (FilePath -> FilePath)
forall a b. (a -> b) -> a -> b
$ \FilePath
_ -> FilePath -> FilePath
wrapText (FilePath -> FilePath) -> FilePath -> FilePath
forall a b. (a -> b) -> a -> b
$
         FilePath
"Components encompass executables, tests, and benchmarks.\n"
      FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
"\n"
      FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
"Affected by configuration options, see `configure`.\n"
  , commandNotes :: Maybe (FilePath -> FilePath)
commandNotes        = (FilePath -> FilePath) -> Maybe (FilePath -> FilePath)
forall a. a -> Maybe a
Just ((FilePath -> FilePath) -> Maybe (FilePath -> FilePath))
-> (FilePath -> FilePath) -> Maybe (FilePath -> FilePath)
forall a b. (a -> b) -> a -> b
$ \FilePath
pname ->
       FilePath
"Examples:\n"
        FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
"  " FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
pname FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
" build           "
        FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
"    All the components in the package\n"
        FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
"  " FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
pname FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
" build foo       "
        FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
"    A component (i.e. lib, exe, test suite)\n\n"
        FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ ProgramDb -> FilePath
programFlagsDescription ProgramDb
progDb
--TODO: re-enable once we have support for module/file targets
--        ++ "  " ++ pname ++ " build Foo.Bar   "
--        ++ "    A module\n"
--        ++ "  " ++ pname ++ " build Foo/Bar.hs"
--        ++ "    A file\n\n"
--        ++ "If a target is ambiguous it can be qualified with the component "
--        ++ "name, e.g.\n"
--        ++ "  " ++ pname ++ " build foo:Foo.Bar\n"
--        ++ "  " ++ pname ++ " build testsuite1:Foo/Bar.hs\n"
  , commandUsage :: FilePath -> FilePath
commandUsage        = FilePath -> [FilePath] -> FilePath -> FilePath
usageAlternatives FilePath
"build" ([FilePath] -> FilePath -> FilePath)
-> [FilePath] -> FilePath -> FilePath
forall a b. (a -> b) -> a -> b
$
      [ FilePath
"[FLAGS]"
      , FilePath
"COMPONENTS [FLAGS]"
      ]
  , commandDefaultFlags :: BuildFlags
commandDefaultFlags = BuildFlags
defaultBuildFlags
  , commandOptions :: ShowOrParseArgs -> [OptionField BuildFlags]
commandOptions      = \ShowOrParseArgs
showOrParseArgs ->
      [ (BuildFlags -> Flag Verbosity)
-> (Flag Verbosity -> BuildFlags -> BuildFlags)
-> OptionField BuildFlags
forall flags.
(flags -> Flag Verbosity)
-> (Flag Verbosity -> flags -> flags) -> OptionField flags
optionVerbosity
        BuildFlags -> Flag Verbosity
buildVerbosity (\Flag Verbosity
v BuildFlags
flags -> BuildFlags
flags { buildVerbosity :: Flag Verbosity
buildVerbosity = Flag Verbosity
v })

      , (BuildFlags -> Flag FilePath)
-> (Flag FilePath -> BuildFlags -> BuildFlags)
-> ShowOrParseArgs
-> OptionField BuildFlags
forall flags.
(flags -> Flag FilePath)
-> (Flag FilePath -> flags -> flags)
-> ShowOrParseArgs
-> OptionField flags
optionDistPref
        BuildFlags -> Flag FilePath
buildDistPref (\Flag FilePath
d BuildFlags
flags -> BuildFlags
flags { buildDistPref :: Flag FilePath
buildDistPref = Flag FilePath
d }) ShowOrParseArgs
showOrParseArgs
      ]
      [OptionField BuildFlags]
-> [OptionField BuildFlags] -> [OptionField BuildFlags]
forall a. [a] -> [a] -> [a]
++ ProgramDb -> ShowOrParseArgs -> [OptionField BuildFlags]
buildOptions ProgramDb
progDb ShowOrParseArgs
showOrParseArgs
  }

buildOptions :: ProgramDb -> ShowOrParseArgs
                -> [OptionField BuildFlags]
buildOptions :: ProgramDb -> ShowOrParseArgs -> [OptionField BuildFlags]
buildOptions ProgramDb
progDb ShowOrParseArgs
showOrParseArgs =
  [ (BuildFlags -> Flag (Maybe Int))
-> (Flag (Maybe Int) -> BuildFlags -> BuildFlags)
-> OptionField BuildFlags
forall flags.
(flags -> Flag (Maybe Int))
-> (Flag (Maybe Int) -> flags -> flags) -> OptionField flags
optionNumJobs
      BuildFlags -> Flag (Maybe Int)
buildNumJobs (\Flag (Maybe Int)
v BuildFlags
flags -> BuildFlags
flags { buildNumJobs :: Flag (Maybe Int)
buildNumJobs = Flag (Maybe Int)
v })
  ]

  [OptionField BuildFlags]
-> [OptionField BuildFlags] -> [OptionField BuildFlags]
forall a. [a] -> [a] -> [a]
++ ProgramDb
-> ShowOrParseArgs
-> (BuildFlags -> [(FilePath, FilePath)])
-> ([(FilePath, FilePath)] -> BuildFlags -> BuildFlags)
-> [OptionField BuildFlags]
forall flags.
ProgramDb
-> ShowOrParseArgs
-> (flags -> [(FilePath, FilePath)])
-> ([(FilePath, FilePath)] -> flags -> flags)
-> [OptionField flags]
programDbPaths ProgramDb
progDb ShowOrParseArgs
showOrParseArgs
       BuildFlags -> [(FilePath, FilePath)]
buildProgramPaths (\[(FilePath, FilePath)]
v BuildFlags
flags -> BuildFlags
flags { buildProgramPaths :: [(FilePath, FilePath)]
buildProgramPaths = [(FilePath, FilePath)]
v})

  [OptionField BuildFlags]
-> [OptionField BuildFlags] -> [OptionField BuildFlags]
forall a. [a] -> [a] -> [a]
++ ProgramDb
-> ShowOrParseArgs
-> (BuildFlags -> [(FilePath, [FilePath])])
-> ([(FilePath, [FilePath])] -> BuildFlags -> BuildFlags)
-> [OptionField BuildFlags]
forall flags.
ProgramDb
-> ShowOrParseArgs
-> (flags -> [(FilePath, [FilePath])])
-> ([(FilePath, [FilePath])] -> flags -> flags)
-> [OptionField flags]
programDbOption ProgramDb
progDb ShowOrParseArgs
showOrParseArgs
       BuildFlags -> [(FilePath, [FilePath])]
buildProgramArgs (\[(FilePath, [FilePath])]
v BuildFlags
fs -> BuildFlags
fs { buildProgramArgs :: [(FilePath, [FilePath])]
buildProgramArgs = [(FilePath, [FilePath])]
v })

  [OptionField BuildFlags]
-> [OptionField BuildFlags] -> [OptionField BuildFlags]
forall a. [a] -> [a] -> [a]
++ ProgramDb
-> ShowOrParseArgs
-> (BuildFlags -> [(FilePath, [FilePath])])
-> ([(FilePath, [FilePath])] -> BuildFlags -> BuildFlags)
-> [OptionField BuildFlags]
forall flags.
ProgramDb
-> ShowOrParseArgs
-> (flags -> [(FilePath, [FilePath])])
-> ([(FilePath, [FilePath])] -> flags -> flags)
-> [OptionField flags]
programDbOptions ProgramDb
progDb ShowOrParseArgs
showOrParseArgs
       BuildFlags -> [(FilePath, [FilePath])]
buildProgramArgs (\[(FilePath, [FilePath])]
v BuildFlags
flags -> BuildFlags
flags { buildProgramArgs :: [(FilePath, [FilePath])]
buildProgramArgs = [(FilePath, [FilePath])]
v})

emptyBuildFlags :: BuildFlags
emptyBuildFlags :: BuildFlags
emptyBuildFlags = BuildFlags
forall a. Monoid a => a
mempty

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

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

-- ------------------------------------------------------------
-- * REPL Flags
-- ------------------------------------------------------------

data ReplFlags = ReplFlags {
    ReplFlags -> [(FilePath, FilePath)]
replProgramPaths :: [(String, FilePath)],
    ReplFlags -> [(FilePath, [FilePath])]
replProgramArgs :: [(String, [String])],
    ReplFlags -> Flag FilePath
replDistPref    :: Flag FilePath,
    ReplFlags -> Flag Verbosity
replVerbosity   :: Flag Verbosity,
    ReplFlags -> Flag Bool
replReload      :: Flag Bool,
    ReplFlags -> [FilePath]
replReplOptions :: [String]
  }
  deriving (Int -> ReplFlags -> FilePath -> FilePath
[ReplFlags] -> FilePath -> FilePath
ReplFlags -> FilePath
(Int -> ReplFlags -> FilePath -> FilePath)
-> (ReplFlags -> FilePath)
-> ([ReplFlags] -> FilePath -> FilePath)
-> Show ReplFlags
forall a.
(Int -> a -> FilePath -> FilePath)
-> (a -> FilePath) -> ([a] -> FilePath -> FilePath) -> Show a
showList :: [ReplFlags] -> FilePath -> FilePath
$cshowList :: [ReplFlags] -> FilePath -> FilePath
show :: ReplFlags -> FilePath
$cshow :: ReplFlags -> FilePath
showsPrec :: Int -> ReplFlags -> FilePath -> FilePath
$cshowsPrec :: Int -> ReplFlags -> FilePath -> FilePath
Show, (forall x. ReplFlags -> Rep ReplFlags x)
-> (forall x. Rep ReplFlags x -> ReplFlags) -> Generic ReplFlags
forall x. Rep ReplFlags x -> ReplFlags
forall x. ReplFlags -> Rep ReplFlags x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ReplFlags x -> ReplFlags
$cfrom :: forall x. ReplFlags -> Rep ReplFlags x
Generic, Typeable)

defaultReplFlags :: ReplFlags
defaultReplFlags :: ReplFlags
defaultReplFlags  = ReplFlags :: [(FilePath, FilePath)]
-> [(FilePath, [FilePath])]
-> Flag FilePath
-> Flag Verbosity
-> Flag Bool
-> [FilePath]
-> ReplFlags
ReplFlags {
    replProgramPaths :: [(FilePath, FilePath)]
replProgramPaths = [(FilePath, FilePath)]
forall a. Monoid a => a
mempty,
    replProgramArgs :: [(FilePath, [FilePath])]
replProgramArgs = [],
    replDistPref :: Flag FilePath
replDistPref    = Flag FilePath
forall a. Flag a
NoFlag,
    replVerbosity :: Flag Verbosity
replVerbosity   = Verbosity -> Flag Verbosity
forall a. a -> Flag a
Flag Verbosity
normal,
    replReload :: Flag Bool
replReload      = Bool -> Flag Bool
forall a. a -> Flag a
Flag Bool
False,
    replReplOptions :: [FilePath]
replReplOptions = []
  }

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

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

replCommand :: ProgramDb -> CommandUI ReplFlags
replCommand :: ProgramDb -> CommandUI ReplFlags
replCommand ProgramDb
progDb = CommandUI :: forall flags.
FilePath
-> FilePath
-> (FilePath -> FilePath)
-> Maybe (FilePath -> FilePath)
-> Maybe (FilePath -> FilePath)
-> flags
-> (ShowOrParseArgs -> [OptionField flags])
-> CommandUI flags
CommandUI
  { commandName :: FilePath
commandName         = FilePath
"repl"
  , commandSynopsis :: FilePath
commandSynopsis     =
      FilePath
"Open an interpreter session for the given component."
  , commandDescription :: Maybe (FilePath -> FilePath)
commandDescription  = (FilePath -> FilePath) -> Maybe (FilePath -> FilePath)
forall a. a -> Maybe a
Just ((FilePath -> FilePath) -> Maybe (FilePath -> FilePath))
-> (FilePath -> FilePath) -> Maybe (FilePath -> FilePath)
forall a b. (a -> b) -> a -> b
$ \FilePath
pname -> FilePath -> FilePath
wrapText (FilePath -> FilePath) -> FilePath -> FilePath
forall a b. (a -> b) -> a -> b
$
         FilePath
"If the current directory contains no package, ignores COMPONENT "
      FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
"parameters and opens an interactive interpreter session; if a "
      FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
"sandbox is present, its package database will be used.\n"
      FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
"\n"
      FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
"Otherwise, (re)configures with the given or default flags, and "
      FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
"loads the interpreter with the relevant modules. For executables, "
      FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
"tests and benchmarks, loads the main module (and its "
      FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
"dependencies); for libraries all exposed/other modules.\n"
      FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
"\n"
      FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
"The default component is the library itself, or the executable "
      FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
"if that is the only component.\n"
      FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
"\n"
      FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
"Support for loading specific modules is planned but not "
      FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
"implemented yet. For certain scenarios, `" FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
pname
      FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
" exec -- ghci :l Foo` may be used instead. Note that `exec` will "
      FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
"not (re)configure and you will have to specify the location of "
      FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
"other modules, if required.\n"

  , commandNotes :: Maybe (FilePath -> FilePath)
commandNotes        = (FilePath -> FilePath) -> Maybe (FilePath -> FilePath)
forall a. a -> Maybe a
Just ((FilePath -> FilePath) -> Maybe (FilePath -> FilePath))
-> (FilePath -> FilePath) -> Maybe (FilePath -> FilePath)
forall a b. (a -> b) -> a -> b
$ \FilePath
pname ->
         FilePath
"Examples:\n"
      FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
"  " FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
pname FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
" repl           "
      FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
"    The first component in the package\n"
      FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
"  " FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
pname FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
" repl foo       "
      FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
"    A named component (i.e. lib, exe, test suite)\n"
      FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
"  " FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
pname FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
" repl --repl-options=\"-lstdc++\""
      FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
"  Specifying flags for interpreter\n"
--TODO: re-enable once we have support for module/file targets
--        ++ "  " ++ pname ++ " repl Foo.Bar   "
--        ++ "    A module\n"
--        ++ "  " ++ pname ++ " repl Foo/Bar.hs"
--        ++ "    A file\n\n"
--        ++ "If a target is ambiguous it can be qualified with the component "
--        ++ "name, e.g.\n"
--        ++ "  " ++ pname ++ " repl foo:Foo.Bar\n"
--        ++ "  " ++ pname ++ " repl testsuite1:Foo/Bar.hs\n"
  , commandUsage :: FilePath -> FilePath
commandUsage =  \FilePath
pname -> FilePath
"Usage: " FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
pname FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
" repl [COMPONENT] [FLAGS]\n"
  , commandDefaultFlags :: ReplFlags
commandDefaultFlags = ReplFlags
defaultReplFlags
  , commandOptions :: ShowOrParseArgs -> [OptionField ReplFlags]
commandOptions = \ShowOrParseArgs
showOrParseArgs ->
      (ReplFlags -> Flag Verbosity)
-> (Flag Verbosity -> ReplFlags -> ReplFlags)
-> OptionField ReplFlags
forall flags.
(flags -> Flag Verbosity)
-> (Flag Verbosity -> flags -> flags) -> OptionField flags
optionVerbosity ReplFlags -> Flag Verbosity
replVerbosity (\Flag Verbosity
v ReplFlags
flags -> ReplFlags
flags { replVerbosity :: Flag Verbosity
replVerbosity = Flag Verbosity
v })
      OptionField ReplFlags
-> [OptionField ReplFlags] -> [OptionField ReplFlags]
forall a. a -> [a] -> [a]
: (ReplFlags -> Flag FilePath)
-> (Flag FilePath -> ReplFlags -> ReplFlags)
-> ShowOrParseArgs
-> OptionField ReplFlags
forall flags.
(flags -> Flag FilePath)
-> (Flag FilePath -> flags -> flags)
-> ShowOrParseArgs
-> OptionField flags
optionDistPref
          ReplFlags -> Flag FilePath
replDistPref (\Flag FilePath
d ReplFlags
flags -> ReplFlags
flags { replDistPref :: Flag FilePath
replDistPref = Flag FilePath
d })
          ShowOrParseArgs
showOrParseArgs

      OptionField ReplFlags
-> [OptionField ReplFlags] -> [OptionField ReplFlags]
forall a. a -> [a] -> [a]
: ProgramDb
-> ShowOrParseArgs
-> (ReplFlags -> [(FilePath, FilePath)])
-> ([(FilePath, FilePath)] -> ReplFlags -> ReplFlags)
-> [OptionField ReplFlags]
forall flags.
ProgramDb
-> ShowOrParseArgs
-> (flags -> [(FilePath, FilePath)])
-> ([(FilePath, FilePath)] -> flags -> flags)
-> [OptionField flags]
programDbPaths   ProgramDb
progDb ShowOrParseArgs
showOrParseArgs
          ReplFlags -> [(FilePath, FilePath)]
replProgramPaths (\[(FilePath, FilePath)]
v ReplFlags
flags -> ReplFlags
flags { replProgramPaths :: [(FilePath, FilePath)]
replProgramPaths = [(FilePath, FilePath)]
v})

     [OptionField ReplFlags]
-> [OptionField ReplFlags] -> [OptionField ReplFlags]
forall a. [a] -> [a] -> [a]
++ ProgramDb
-> ShowOrParseArgs
-> (ReplFlags -> [(FilePath, [FilePath])])
-> ([(FilePath, [FilePath])] -> ReplFlags -> ReplFlags)
-> [OptionField ReplFlags]
forall flags.
ProgramDb
-> ShowOrParseArgs
-> (flags -> [(FilePath, [FilePath])])
-> ([(FilePath, [FilePath])] -> flags -> flags)
-> [OptionField flags]
programDbOption ProgramDb
progDb ShowOrParseArgs
showOrParseArgs
          ReplFlags -> [(FilePath, [FilePath])]
replProgramArgs (\[(FilePath, [FilePath])]
v ReplFlags
flags -> ReplFlags
flags { replProgramArgs :: [(FilePath, [FilePath])]
replProgramArgs = [(FilePath, [FilePath])]
v})

     [OptionField ReplFlags]
-> [OptionField ReplFlags] -> [OptionField ReplFlags]
forall a. [a] -> [a] -> [a]
++ ProgramDb
-> ShowOrParseArgs
-> (ReplFlags -> [(FilePath, [FilePath])])
-> ([(FilePath, [FilePath])] -> ReplFlags -> ReplFlags)
-> [OptionField ReplFlags]
forall flags.
ProgramDb
-> ShowOrParseArgs
-> (flags -> [(FilePath, [FilePath])])
-> ([(FilePath, [FilePath])] -> flags -> flags)
-> [OptionField flags]
programDbOptions ProgramDb
progDb ShowOrParseArgs
showOrParseArgs
          ReplFlags -> [(FilePath, [FilePath])]
replProgramArgs (\[(FilePath, [FilePath])]
v ReplFlags
flags -> ReplFlags
flags { replProgramArgs :: [(FilePath, [FilePath])]
replProgramArgs = [(FilePath, [FilePath])]
v})

     [OptionField ReplFlags]
-> [OptionField ReplFlags] -> [OptionField ReplFlags]
forall a. [a] -> [a] -> [a]
++ case ShowOrParseArgs
showOrParseArgs of
          ShowOrParseArgs
ParseArgs ->
            [ FilePath
-> [FilePath]
-> FilePath
-> (ReplFlags -> Flag Bool)
-> (Flag Bool -> ReplFlags -> ReplFlags)
-> MkOptDescr
     (ReplFlags -> Flag Bool)
     (Flag Bool -> ReplFlags -> ReplFlags)
     ReplFlags
-> OptionField ReplFlags
forall get set a.
FilePath
-> [FilePath]
-> FilePath
-> get
-> set
-> MkOptDescr get set a
-> OptionField a
option FilePath
"" [FilePath
"reload"]
              FilePath
"Used from within an interpreter to update files."
              ReplFlags -> Flag Bool
replReload (\Flag Bool
v ReplFlags
flags -> ReplFlags
flags { replReload :: Flag Bool
replReload = Flag Bool
v })
              MkOptDescr
  (ReplFlags -> Flag Bool)
  (Flag Bool -> ReplFlags -> ReplFlags)
  ReplFlags
forall a. MkOptDescr (a -> Flag Bool) (Flag Bool -> a -> a) a
trueArg
            ]
          ShowOrParseArgs
_ -> []
     [OptionField ReplFlags]
-> [OptionField ReplFlags] -> [OptionField ReplFlags]
forall a. [a] -> [a] -> [a]
++ (OptionField [FilePath] -> OptionField ReplFlags)
-> [OptionField [FilePath]] -> [OptionField ReplFlags]
forall a b. (a -> b) -> [a] -> [b]
map OptionField [FilePath] -> OptionField ReplFlags
liftReplOption (ShowOrParseArgs -> [OptionField [FilePath]]
replOptions ShowOrParseArgs
showOrParseArgs)
  }
  where
    liftReplOption :: OptionField [FilePath] -> OptionField ReplFlags
liftReplOption = (ReplFlags -> [FilePath])
-> ([FilePath] -> ReplFlags -> ReplFlags)
-> OptionField [FilePath]
-> OptionField ReplFlags
forall b a.
(b -> a) -> (a -> b -> b) -> OptionField a -> OptionField b
liftOption ReplFlags -> [FilePath]
replReplOptions (\[FilePath]
v ReplFlags
flags -> ReplFlags
flags { replReplOptions :: [FilePath]
replReplOptions = [FilePath]
v })

replOptions :: ShowOrParseArgs -> [OptionField [String]]
replOptions :: ShowOrParseArgs -> [OptionField [FilePath]]
replOptions ShowOrParseArgs
_ = [ FilePath
-> [FilePath]
-> FilePath
-> ([FilePath] -> [FilePath])
-> ([FilePath] -> [FilePath] -> [FilePath])
-> MkOptDescr
     ([FilePath] -> [FilePath])
     ([FilePath] -> [FilePath] -> [FilePath])
     [FilePath]
-> OptionField [FilePath]
forall get set a.
FilePath
-> [FilePath]
-> FilePath
-> get
-> set
-> MkOptDescr get set a
-> OptionField a
option [] [FilePath
"repl-options"] FilePath
"use this option for the repl" [FilePath] -> [FilePath]
forall a. a -> a
id
              [FilePath] -> [FilePath] -> [FilePath]
forall a b. a -> b -> a
const (FilePath
-> ReadE [FilePath]
-> ([FilePath] -> [FilePath])
-> MkOptDescr
     ([FilePath] -> [FilePath])
     ([FilePath] -> [FilePath] -> [FilePath])
     [FilePath]
forall b a.
Monoid b =>
FilePath
-> ReadE b
-> (b -> [FilePath])
-> MkOptDescr (a -> b) (b -> a -> a) a
reqArg FilePath
"FLAG" ((FilePath -> [FilePath]) -> ReadE [FilePath]
forall a. (FilePath -> a) -> ReadE a
succeedReadE (FilePath -> [FilePath] -> [FilePath]
forall a. a -> [a] -> [a]
:[])) [FilePath] -> [FilePath]
forall a. a -> a
id) ]

-- ------------------------------------------------------------
-- * Test flags
-- ------------------------------------------------------------

data TestShowDetails = Never | Failures | Always | Streaming | Direct
    deriving (TestShowDetails -> TestShowDetails -> Bool
(TestShowDetails -> TestShowDetails -> Bool)
-> (TestShowDetails -> TestShowDetails -> Bool)
-> Eq TestShowDetails
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: TestShowDetails -> TestShowDetails -> Bool
$c/= :: TestShowDetails -> TestShowDetails -> Bool
== :: TestShowDetails -> TestShowDetails -> Bool
$c== :: TestShowDetails -> TestShowDetails -> Bool
Eq, Eq TestShowDetails
Eq TestShowDetails
-> (TestShowDetails -> TestShowDetails -> Ordering)
-> (TestShowDetails -> TestShowDetails -> Bool)
-> (TestShowDetails -> TestShowDetails -> Bool)
-> (TestShowDetails -> TestShowDetails -> Bool)
-> (TestShowDetails -> TestShowDetails -> Bool)
-> (TestShowDetails -> TestShowDetails -> TestShowDetails)
-> (TestShowDetails -> TestShowDetails -> TestShowDetails)
-> Ord TestShowDetails
TestShowDetails -> TestShowDetails -> Bool
TestShowDetails -> TestShowDetails -> Ordering
TestShowDetails -> TestShowDetails -> TestShowDetails
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: TestShowDetails -> TestShowDetails -> TestShowDetails
$cmin :: TestShowDetails -> TestShowDetails -> TestShowDetails
max :: TestShowDetails -> TestShowDetails -> TestShowDetails
$cmax :: TestShowDetails -> TestShowDetails -> TestShowDetails
>= :: TestShowDetails -> TestShowDetails -> Bool
$c>= :: TestShowDetails -> TestShowDetails -> Bool
> :: TestShowDetails -> TestShowDetails -> Bool
$c> :: TestShowDetails -> TestShowDetails -> Bool
<= :: TestShowDetails -> TestShowDetails -> Bool
$c<= :: TestShowDetails -> TestShowDetails -> Bool
< :: TestShowDetails -> TestShowDetails -> Bool
$c< :: TestShowDetails -> TestShowDetails -> Bool
compare :: TestShowDetails -> TestShowDetails -> Ordering
$ccompare :: TestShowDetails -> TestShowDetails -> Ordering
$cp1Ord :: Eq TestShowDetails
Ord, Int -> TestShowDetails
TestShowDetails -> Int
TestShowDetails -> [TestShowDetails]
TestShowDetails -> TestShowDetails
TestShowDetails -> TestShowDetails -> [TestShowDetails]
TestShowDetails
-> TestShowDetails -> TestShowDetails -> [TestShowDetails]
(TestShowDetails -> TestShowDetails)
-> (TestShowDetails -> TestShowDetails)
-> (Int -> TestShowDetails)
-> (TestShowDetails -> Int)
-> (TestShowDetails -> [TestShowDetails])
-> (TestShowDetails -> TestShowDetails -> [TestShowDetails])
-> (TestShowDetails -> TestShowDetails -> [TestShowDetails])
-> (TestShowDetails
    -> TestShowDetails -> TestShowDetails -> [TestShowDetails])
-> Enum TestShowDetails
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
enumFromThenTo :: TestShowDetails
-> TestShowDetails -> TestShowDetails -> [TestShowDetails]
$cenumFromThenTo :: TestShowDetails
-> TestShowDetails -> TestShowDetails -> [TestShowDetails]
enumFromTo :: TestShowDetails -> TestShowDetails -> [TestShowDetails]
$cenumFromTo :: TestShowDetails -> TestShowDetails -> [TestShowDetails]
enumFromThen :: TestShowDetails -> TestShowDetails -> [TestShowDetails]
$cenumFromThen :: TestShowDetails -> TestShowDetails -> [TestShowDetails]
enumFrom :: TestShowDetails -> [TestShowDetails]
$cenumFrom :: TestShowDetails -> [TestShowDetails]
fromEnum :: TestShowDetails -> Int
$cfromEnum :: TestShowDetails -> Int
toEnum :: Int -> TestShowDetails
$ctoEnum :: Int -> TestShowDetails
pred :: TestShowDetails -> TestShowDetails
$cpred :: TestShowDetails -> TestShowDetails
succ :: TestShowDetails -> TestShowDetails
$csucc :: TestShowDetails -> TestShowDetails
Enum, TestShowDetails
TestShowDetails -> TestShowDetails -> Bounded TestShowDetails
forall a. a -> a -> Bounded a
maxBound :: TestShowDetails
$cmaxBound :: TestShowDetails
minBound :: TestShowDetails
$cminBound :: TestShowDetails
Bounded, (forall x. TestShowDetails -> Rep TestShowDetails x)
-> (forall x. Rep TestShowDetails x -> TestShowDetails)
-> Generic TestShowDetails
forall x. Rep TestShowDetails x -> TestShowDetails
forall x. TestShowDetails -> Rep TestShowDetails x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep TestShowDetails x -> TestShowDetails
$cfrom :: forall x. TestShowDetails -> Rep TestShowDetails x
Generic, Int -> TestShowDetails -> FilePath -> FilePath
[TestShowDetails] -> FilePath -> FilePath
TestShowDetails -> FilePath
(Int -> TestShowDetails -> FilePath -> FilePath)
-> (TestShowDetails -> FilePath)
-> ([TestShowDetails] -> FilePath -> FilePath)
-> Show TestShowDetails
forall a.
(Int -> a -> FilePath -> FilePath)
-> (a -> FilePath) -> ([a] -> FilePath -> FilePath) -> Show a
showList :: [TestShowDetails] -> FilePath -> FilePath
$cshowList :: [TestShowDetails] -> FilePath -> FilePath
show :: TestShowDetails -> FilePath
$cshow :: TestShowDetails -> FilePath
showsPrec :: Int -> TestShowDetails -> FilePath -> FilePath
$cshowsPrec :: Int -> TestShowDetails -> FilePath -> FilePath
Show, Typeable)

instance Binary TestShowDetails
instance Structured TestShowDetails

knownTestShowDetails :: [TestShowDetails]
knownTestShowDetails :: [TestShowDetails]
knownTestShowDetails = [TestShowDetails
forall a. Bounded a => a
minBound..TestShowDetails
forall a. Bounded a => a
maxBound]

instance Pretty TestShowDetails where
    pretty :: TestShowDetails -> Doc
pretty  = FilePath -> Doc
Disp.text (FilePath -> Doc)
-> (TestShowDetails -> FilePath) -> TestShowDetails -> Doc
forall b c a. (b -> c) -> (a -> b) -> a -> c
. FilePath -> FilePath
lowercase (FilePath -> FilePath)
-> (TestShowDetails -> FilePath) -> TestShowDetails -> FilePath
forall b c a. (b -> c) -> (a -> b) -> a -> c
. TestShowDetails -> FilePath
forall a. Show a => a -> FilePath
show

instance Parsec TestShowDetails where
    parsec :: m TestShowDetails
parsec = m TestShowDetails
-> (TestShowDetails -> m TestShowDetails)
-> Maybe TestShowDetails
-> m TestShowDetails
forall b a. b -> (a -> b) -> Maybe a -> b
maybe (FilePath -> m TestShowDetails
forall (m :: * -> *) a. MonadFail m => FilePath -> m a
fail FilePath
"invalid TestShowDetails") TestShowDetails -> m TestShowDetails
forall (m :: * -> *) a. Monad m => a -> m a
return (Maybe TestShowDetails -> m TestShowDetails)
-> (FilePath -> Maybe TestShowDetails)
-> FilePath
-> m TestShowDetails
forall b c a. (b -> c) -> (a -> b) -> a -> c
. FilePath -> Maybe TestShowDetails
classify (FilePath -> m TestShowDetails) -> m FilePath -> m TestShowDetails
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< m FilePath
ident
      where
        ident :: m FilePath
ident        = (Char -> Bool) -> m FilePath
forall (m :: * -> *). CharParsing m => (Char -> Bool) -> m FilePath
P.munch1 (\Char
c -> Char -> Bool
isAlpha Char
c Bool -> Bool -> Bool
|| Char
c Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
'_' Bool -> Bool -> Bool
|| Char
c Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
'-')
        classify :: FilePath -> Maybe TestShowDetails
classify FilePath
str = FilePath -> [(FilePath, TestShowDetails)] -> Maybe TestShowDetails
forall a b. Eq a => a -> [(a, b)] -> Maybe b
lookup (FilePath -> FilePath
lowercase FilePath
str) [(FilePath, TestShowDetails)]
enumMap
        enumMap     :: [(String, TestShowDetails)]
        enumMap :: [(FilePath, TestShowDetails)]
enumMap      = [ (TestShowDetails -> FilePath
forall a. Pretty a => a -> FilePath
prettyShow TestShowDetails
x, TestShowDetails
x)
                       | TestShowDetails
x <- [TestShowDetails]
knownTestShowDetails ]

--TODO: do we need this instance?
instance Monoid TestShowDetails where
    mempty :: TestShowDetails
mempty = TestShowDetails
Never
    mappend :: TestShowDetails -> TestShowDetails -> TestShowDetails
mappend = TestShowDetails -> TestShowDetails -> TestShowDetails
forall a. Semigroup a => a -> a -> a
(<>)

instance Semigroup TestShowDetails where
    TestShowDetails
a <> :: TestShowDetails -> TestShowDetails -> TestShowDetails
<> TestShowDetails
b = if TestShowDetails
a TestShowDetails -> TestShowDetails -> Bool
forall a. Ord a => a -> a -> Bool
< TestShowDetails
b then TestShowDetails
b else TestShowDetails
a

data TestFlags = TestFlags {
    TestFlags -> Flag FilePath
testDistPref    :: Flag FilePath,
    TestFlags -> Flag Verbosity
testVerbosity   :: Flag Verbosity,
    TestFlags -> Flag PathTemplate
testHumanLog    :: Flag PathTemplate,
    TestFlags -> Flag PathTemplate
testMachineLog  :: Flag PathTemplate,
    TestFlags -> Flag TestShowDetails
testShowDetails :: Flag TestShowDetails,
    TestFlags -> Flag Bool
testKeepTix     :: Flag Bool,
    TestFlags -> Flag FilePath
testWrapper     :: Flag FilePath,
    TestFlags -> Flag Bool
testFailWhenNoTestSuites :: Flag Bool,
    -- TODO: think about if/how options are passed to test exes
    TestFlags -> [PathTemplate]
testOptions     :: [PathTemplate]
  } deriving ((forall x. TestFlags -> Rep TestFlags x)
-> (forall x. Rep TestFlags x -> TestFlags) -> Generic TestFlags
forall x. Rep TestFlags x -> TestFlags
forall x. TestFlags -> Rep TestFlags x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep TestFlags x -> TestFlags
$cfrom :: forall x. TestFlags -> Rep TestFlags x
Generic, Typeable)

defaultTestFlags :: TestFlags
defaultTestFlags :: TestFlags
defaultTestFlags  = TestFlags :: Flag FilePath
-> Flag Verbosity
-> Flag PathTemplate
-> Flag PathTemplate
-> Flag TestShowDetails
-> Flag Bool
-> Flag FilePath
-> Flag Bool
-> [PathTemplate]
-> TestFlags
TestFlags {
    testDistPref :: Flag FilePath
testDistPref    = Flag FilePath
forall a. Flag a
NoFlag,
    testVerbosity :: Flag Verbosity
testVerbosity   = Verbosity -> Flag Verbosity
forall a. a -> Flag a
Flag Verbosity
normal,
    testHumanLog :: Flag PathTemplate
testHumanLog    = PathTemplate -> Flag PathTemplate
forall a. a -> Flag a
toFlag (PathTemplate -> Flag PathTemplate)
-> PathTemplate -> Flag PathTemplate
forall a b. (a -> b) -> a -> b
$ FilePath -> PathTemplate
toPathTemplate (FilePath -> PathTemplate) -> FilePath -> PathTemplate
forall a b. (a -> b) -> a -> b
$ FilePath
"$pkgid-$test-suite.log",
    testMachineLog :: Flag PathTemplate
testMachineLog  = PathTemplate -> Flag PathTemplate
forall a. a -> Flag a
toFlag (PathTemplate -> Flag PathTemplate)
-> PathTemplate -> Flag PathTemplate
forall a b. (a -> b) -> a -> b
$ FilePath -> PathTemplate
toPathTemplate (FilePath -> PathTemplate) -> FilePath -> PathTemplate
forall a b. (a -> b) -> a -> b
$ FilePath
"$pkgid.log",
    testShowDetails :: Flag TestShowDetails
testShowDetails = TestShowDetails -> Flag TestShowDetails
forall a. a -> Flag a
toFlag TestShowDetails
Failures,
    testKeepTix :: Flag Bool
testKeepTix     = Bool -> Flag Bool
forall a. a -> Flag a
toFlag Bool
False,
    testWrapper :: Flag FilePath
testWrapper     = Flag FilePath
forall a. Flag a
NoFlag,
    testFailWhenNoTestSuites :: Flag Bool
testFailWhenNoTestSuites = Bool -> Flag Bool
forall a. a -> Flag a
toFlag Bool
False,
    testOptions :: [PathTemplate]
testOptions     = []
  }

testCommand :: CommandUI TestFlags
testCommand :: CommandUI TestFlags
testCommand = CommandUI :: forall flags.
FilePath
-> FilePath
-> (FilePath -> FilePath)
-> Maybe (FilePath -> FilePath)
-> Maybe (FilePath -> FilePath)
-> flags
-> (ShowOrParseArgs -> [OptionField flags])
-> CommandUI flags
CommandUI
  { commandName :: FilePath
commandName         = FilePath
"test"
  , commandSynopsis :: FilePath
commandSynopsis     =
      FilePath
"Run all/specific tests in the test suite."
  , commandDescription :: Maybe (FilePath -> FilePath)
commandDescription  = (FilePath -> FilePath) -> Maybe (FilePath -> FilePath)
forall a. a -> Maybe a
Just ((FilePath -> FilePath) -> Maybe (FilePath -> FilePath))
-> (FilePath -> FilePath) -> Maybe (FilePath -> FilePath)
forall a b. (a -> b) -> a -> b
$ \FilePath
pname -> FilePath -> FilePath
wrapText (FilePath -> FilePath) -> FilePath -> FilePath
forall a b. (a -> b) -> a -> b
$
         FilePath
"If necessary (re)configures with `--enable-tests` flag and builds"
      FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
" the test suite.\n"
      FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
"\n"
      FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
"Remember that the tests' dependencies must be installed if there"
      FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
" are additional ones; e.g. with `" FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
pname
      FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
" install --only-dependencies --enable-tests`.\n"
      FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
"\n"
      FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
"By defining UserHooks in a custom Setup.hs, the package can"
      FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
" define actions to be executed before and after running tests.\n"
  , commandNotes :: Maybe (FilePath -> FilePath)
commandNotes        = Maybe (FilePath -> FilePath)
forall a. Maybe a
Nothing
  , commandUsage :: FilePath -> FilePath
commandUsage        = FilePath -> [FilePath] -> FilePath -> FilePath
usageAlternatives FilePath
"test"
      [ FilePath
"[FLAGS]"
      , FilePath
"TESTCOMPONENTS [FLAGS]"
      ]
  , commandDefaultFlags :: TestFlags
commandDefaultFlags = TestFlags
defaultTestFlags
  , commandOptions :: ShowOrParseArgs -> [OptionField TestFlags]
commandOptions = ShowOrParseArgs -> [OptionField TestFlags]
testOptions'
  }

testOptions' ::  ShowOrParseArgs -> [OptionField TestFlags]
testOptions' :: ShowOrParseArgs -> [OptionField TestFlags]
testOptions' ShowOrParseArgs
showOrParseArgs =
  [ (TestFlags -> Flag Verbosity)
-> (Flag Verbosity -> TestFlags -> TestFlags)
-> OptionField TestFlags
forall flags.
(flags -> Flag Verbosity)
-> (Flag Verbosity -> flags -> flags) -> OptionField flags
optionVerbosity TestFlags -> Flag Verbosity
testVerbosity (\Flag Verbosity
v TestFlags
flags -> TestFlags
flags { testVerbosity :: Flag Verbosity
testVerbosity = Flag Verbosity
v })
  , (TestFlags -> Flag FilePath)
-> (Flag FilePath -> TestFlags -> TestFlags)
-> ShowOrParseArgs
-> OptionField TestFlags
forall flags.
(flags -> Flag FilePath)
-> (Flag FilePath -> flags -> flags)
-> ShowOrParseArgs
-> OptionField flags
optionDistPref
        TestFlags -> Flag FilePath
testDistPref (\Flag FilePath
d TestFlags
flags -> TestFlags
flags { testDistPref :: Flag FilePath
testDistPref = Flag FilePath
d })
        ShowOrParseArgs
showOrParseArgs
  , FilePath
-> [FilePath]
-> FilePath
-> (TestFlags -> Flag PathTemplate)
-> (Flag PathTemplate -> TestFlags -> TestFlags)
-> MkOptDescr
     (TestFlags -> Flag PathTemplate)
     (Flag PathTemplate -> TestFlags -> TestFlags)
     TestFlags
-> OptionField TestFlags
forall get set a.
FilePath
-> [FilePath]
-> FilePath
-> get
-> set
-> MkOptDescr get set a
-> OptionField a
option [] [FilePath
"log"]
        (FilePath
"Log all test suite results to file (name template can use "
        FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
"$pkgid, $compiler, $os, $arch, $test-suite, $result)")
        TestFlags -> Flag PathTemplate
testHumanLog (\Flag PathTemplate
v TestFlags
flags -> TestFlags
flags { testHumanLog :: Flag PathTemplate
testHumanLog = Flag PathTemplate
v })
        (FilePath
-> (FilePath -> Flag PathTemplate)
-> (Flag PathTemplate -> [FilePath])
-> MkOptDescr
     (TestFlags -> Flag PathTemplate)
     (Flag PathTemplate -> TestFlags -> TestFlags)
     TestFlags
forall b a.
Monoid b =>
FilePath
-> (FilePath -> b)
-> (b -> [FilePath])
-> MkOptDescr (a -> b) (b -> a -> a) a
reqArg' FilePath
"TEMPLATE"
            (PathTemplate -> Flag PathTemplate
forall a. a -> Flag a
toFlag (PathTemplate -> Flag PathTemplate)
-> (FilePath -> PathTemplate) -> FilePath -> Flag PathTemplate
forall b c a. (b -> c) -> (a -> b) -> a -> c
. FilePath -> PathTemplate
toPathTemplate)
            (Flag FilePath -> [FilePath]
forall a. Flag a -> [a]
flagToList (Flag FilePath -> [FilePath])
-> (Flag PathTemplate -> Flag FilePath)
-> Flag PathTemplate
-> [FilePath]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (PathTemplate -> FilePath) -> Flag PathTemplate -> Flag FilePath
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap PathTemplate -> FilePath
fromPathTemplate))
  , FilePath
-> [FilePath]
-> FilePath
-> (TestFlags -> Flag PathTemplate)
-> (Flag PathTemplate -> TestFlags -> TestFlags)
-> MkOptDescr
     (TestFlags -> Flag PathTemplate)
     (Flag PathTemplate -> TestFlags -> TestFlags)
     TestFlags
-> OptionField TestFlags
forall get set a.
FilePath
-> [FilePath]
-> FilePath
-> get
-> set
-> MkOptDescr get set a
-> OptionField a
option [] [FilePath
"machine-log"]
        (FilePath
"Produce a machine-readable log file (name template can use "
        FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
"$pkgid, $compiler, $os, $arch, $result)")
        TestFlags -> Flag PathTemplate
testMachineLog (\Flag PathTemplate
v TestFlags
flags -> TestFlags
flags { testMachineLog :: Flag PathTemplate
testMachineLog = Flag PathTemplate
v })
        (FilePath
-> (FilePath -> Flag PathTemplate)
-> (Flag PathTemplate -> [FilePath])
-> MkOptDescr
     (TestFlags -> Flag PathTemplate)
     (Flag PathTemplate -> TestFlags -> TestFlags)
     TestFlags
forall b a.
Monoid b =>
FilePath
-> (FilePath -> b)
-> (b -> [FilePath])
-> MkOptDescr (a -> b) (b -> a -> a) a
reqArg' FilePath
"TEMPLATE"
            (PathTemplate -> Flag PathTemplate
forall a. a -> Flag a
toFlag (PathTemplate -> Flag PathTemplate)
-> (FilePath -> PathTemplate) -> FilePath -> Flag PathTemplate
forall b c a. (b -> c) -> (a -> b) -> a -> c
. FilePath -> PathTemplate
toPathTemplate)
            (Flag FilePath -> [FilePath]
forall a. Flag a -> [a]
flagToList (Flag FilePath -> [FilePath])
-> (Flag PathTemplate -> Flag FilePath)
-> Flag PathTemplate
-> [FilePath]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (PathTemplate -> FilePath) -> Flag PathTemplate -> Flag FilePath
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap PathTemplate -> FilePath
fromPathTemplate))
  , FilePath
-> [FilePath]
-> FilePath
-> (TestFlags -> Flag TestShowDetails)
-> (Flag TestShowDetails -> TestFlags -> TestFlags)
-> MkOptDescr
     (TestFlags -> Flag TestShowDetails)
     (Flag TestShowDetails -> TestFlags -> TestFlags)
     TestFlags
-> OptionField TestFlags
forall get set a.
FilePath
-> [FilePath]
-> FilePath
-> get
-> set
-> MkOptDescr get set a
-> OptionField a
option [] [FilePath
"show-details"]
        (FilePath
"'always': always show results of individual test cases. "
         FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
"'never': never show results of individual test cases. "
         FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
"'failures': show results of failing test cases. "
         FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
"'streaming': show results of test cases in real time."
         FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
"'direct': send results of test cases in real time; no log file.")
        TestFlags -> Flag TestShowDetails
testShowDetails (\Flag TestShowDetails
v TestFlags
flags -> TestFlags
flags { testShowDetails :: Flag TestShowDetails
testShowDetails = Flag TestShowDetails
v })
        (FilePath
-> ReadE (Flag TestShowDetails)
-> (Flag TestShowDetails -> [FilePath])
-> MkOptDescr
     (TestFlags -> Flag TestShowDetails)
     (Flag TestShowDetails -> TestFlags -> TestFlags)
     TestFlags
forall b a.
Monoid b =>
FilePath
-> ReadE b
-> (b -> [FilePath])
-> MkOptDescr (a -> b) (b -> a -> a) a
reqArg FilePath
"FILTER"
            ((FilePath -> FilePath)
-> ParsecParser (Flag TestShowDetails)
-> ReadE (Flag TestShowDetails)
forall a. (FilePath -> FilePath) -> ParsecParser a -> ReadE a
parsecToReadE (\FilePath
_ -> FilePath
"--show-details flag expects one of "
                          FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath -> [FilePath] -> FilePath
forall a. [a] -> [[a]] -> [a]
intercalate FilePath
", "
                               ((TestShowDetails -> FilePath) -> [TestShowDetails] -> [FilePath]
forall a b. (a -> b) -> [a] -> [b]
map TestShowDetails -> FilePath
forall a. Pretty a => a -> FilePath
prettyShow [TestShowDetails]
knownTestShowDetails))
                        ((TestShowDetails -> Flag TestShowDetails)
-> ParsecParser TestShowDetails
-> ParsecParser (Flag TestShowDetails)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap TestShowDetails -> Flag TestShowDetails
forall a. a -> Flag a
toFlag ParsecParser TestShowDetails
forall a (m :: * -> *). (Parsec a, CabalParsing m) => m a
parsec))
            (Flag FilePath -> [FilePath]
forall a. Flag a -> [a]
flagToList (Flag FilePath -> [FilePath])
-> (Flag TestShowDetails -> Flag FilePath)
-> Flag TestShowDetails
-> [FilePath]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (TestShowDetails -> FilePath)
-> Flag TestShowDetails -> Flag FilePath
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap TestShowDetails -> FilePath
forall a. Pretty a => a -> FilePath
prettyShow))
  , FilePath
-> [FilePath]
-> FilePath
-> (TestFlags -> Flag Bool)
-> (Flag Bool -> TestFlags -> TestFlags)
-> MkOptDescr
     (TestFlags -> Flag Bool)
     (Flag Bool -> TestFlags -> TestFlags)
     TestFlags
-> OptionField TestFlags
forall get set a.
FilePath
-> [FilePath]
-> FilePath
-> get
-> set
-> MkOptDescr get set a
-> OptionField a
option [] [FilePath
"keep-tix-files"]
        FilePath
"keep .tix files for HPC between test runs"
        TestFlags -> Flag Bool
testKeepTix (\Flag Bool
v TestFlags
flags -> TestFlags
flags { testKeepTix :: Flag Bool
testKeepTix = Flag Bool
v})
        MkOptDescr
  (TestFlags -> Flag Bool)
  (Flag Bool -> TestFlags -> TestFlags)
  TestFlags
forall a. MkOptDescr (a -> Flag Bool) (Flag Bool -> a -> a) a
trueArg
  , FilePath
-> [FilePath]
-> FilePath
-> (TestFlags -> Flag FilePath)
-> (Flag FilePath -> TestFlags -> TestFlags)
-> MkOptDescr
     (TestFlags -> Flag FilePath)
     (Flag FilePath -> TestFlags -> TestFlags)
     TestFlags
-> OptionField TestFlags
forall get set a.
FilePath
-> [FilePath]
-> FilePath
-> get
-> set
-> MkOptDescr get set a
-> OptionField a
option [] [FilePath
"test-wrapper"]
        FilePath
"Run test through a wrapper."
        TestFlags -> Flag FilePath
testWrapper (\Flag FilePath
v TestFlags
flags -> TestFlags
flags { testWrapper :: Flag FilePath
testWrapper = Flag FilePath
v })
        (FilePath
-> (FilePath -> Flag FilePath)
-> (Flag FilePath -> [FilePath])
-> MkOptDescr
     (TestFlags -> Flag FilePath)
     (Flag FilePath -> TestFlags -> TestFlags)
     TestFlags
forall b a.
Monoid b =>
FilePath
-> (FilePath -> b)
-> (b -> [FilePath])
-> MkOptDescr (a -> b) (b -> a -> a) a
reqArg' FilePath
"FILE" (FilePath -> Flag FilePath
forall a. a -> Flag a
toFlag :: FilePath -> Flag FilePath)
            (Flag FilePath -> [FilePath]
forall a. Flag a -> [a]
flagToList :: Flag FilePath -> [FilePath]))
  , FilePath
-> [FilePath]
-> FilePath
-> (TestFlags -> Flag Bool)
-> (Flag Bool -> TestFlags -> TestFlags)
-> MkOptDescr
     (TestFlags -> Flag Bool)
     (Flag Bool -> TestFlags -> TestFlags)
     TestFlags
-> OptionField TestFlags
forall get set a.
FilePath
-> [FilePath]
-> FilePath
-> get
-> set
-> MkOptDescr get set a
-> OptionField a
option [] [FilePath
"fail-when-no-test-suites"]
        (FilePath
"Exit with failure when no test suites are found.")
        TestFlags -> Flag Bool
testFailWhenNoTestSuites (\Flag Bool
v TestFlags
flags -> TestFlags
flags { testFailWhenNoTestSuites :: Flag Bool
testFailWhenNoTestSuites = Flag Bool
v})
        MkOptDescr
  (TestFlags -> Flag Bool)
  (Flag Bool -> TestFlags -> TestFlags)
  TestFlags
forall a. MkOptDescr (a -> Flag Bool) (Flag Bool -> a -> a) a
trueArg
  , FilePath
-> [FilePath]
-> FilePath
-> (TestFlags -> [PathTemplate])
-> ([PathTemplate] -> TestFlags -> TestFlags)
-> MkOptDescr
     (TestFlags -> [PathTemplate])
     ([PathTemplate] -> TestFlags -> TestFlags)
     TestFlags
-> OptionField TestFlags
forall get set a.
FilePath
-> [FilePath]
-> FilePath
-> get
-> set
-> MkOptDescr get set a
-> OptionField a
option [] [FilePath
"test-options"]
        (FilePath
"give extra options to test executables "
         FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
"(name templates can use $pkgid, $compiler, "
         FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
"$os, $arch, $test-suite)")
        TestFlags -> [PathTemplate]
testOptions (\[PathTemplate]
v TestFlags
flags -> TestFlags
flags { testOptions :: [PathTemplate]
testOptions = [PathTemplate]
v })
        (FilePath
-> (FilePath -> [PathTemplate])
-> ([PathTemplate] -> [FilePath])
-> MkOptDescr
     (TestFlags -> [PathTemplate])
     ([PathTemplate] -> TestFlags -> TestFlags)
     TestFlags
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
-> (TestFlags -> [PathTemplate])
-> ([PathTemplate] -> TestFlags -> TestFlags)
-> MkOptDescr
     (TestFlags -> [PathTemplate])
     ([PathTemplate] -> TestFlags -> TestFlags)
     TestFlags
-> OptionField TestFlags
forall get set a.
FilePath
-> [FilePath]
-> FilePath
-> get
-> set
-> MkOptDescr get set a
-> OptionField a
option [] [FilePath
"test-option"]
        (FilePath
"give extra option to test executables "
         FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
"(no need to quote options containing spaces, "
         FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
"name template can use $pkgid, $compiler, "
         FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
"$os, $arch, $test-suite)")
        TestFlags -> [PathTemplate]
testOptions (\[PathTemplate]
v TestFlags
flags -> TestFlags
flags { testOptions :: [PathTemplate]
testOptions = [PathTemplate]
v })
        (FilePath
-> (FilePath -> [PathTemplate])
-> ([PathTemplate] -> [FilePath])
-> MkOptDescr
     (TestFlags -> [PathTemplate])
     ([PathTemplate] -> TestFlags -> TestFlags)
     TestFlags
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))
  ]

emptyTestFlags :: TestFlags
emptyTestFlags :: TestFlags
emptyTestFlags  = TestFlags
forall a. Monoid a => a
mempty

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

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

-- ------------------------------------------------------------
-- * Benchmark flags
-- ------------------------------------------------------------

data BenchmarkFlags = BenchmarkFlags {
    BenchmarkFlags -> Flag FilePath
benchmarkDistPref  :: Flag FilePath,
    BenchmarkFlags -> Flag Verbosity
benchmarkVerbosity :: Flag Verbosity,
    BenchmarkFlags -> [PathTemplate]
benchmarkOptions   :: [PathTemplate]
  } deriving ((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
$cto :: forall x. Rep BenchmarkFlags x -> BenchmarkFlags
$cfrom :: forall x. BenchmarkFlags -> Rep BenchmarkFlags x
Generic, Typeable)

defaultBenchmarkFlags :: BenchmarkFlags
defaultBenchmarkFlags :: BenchmarkFlags
defaultBenchmarkFlags  = BenchmarkFlags :: Flag FilePath -> Flag Verbosity -> [PathTemplate] -> BenchmarkFlags
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 :: forall flags.
FilePath
-> FilePath
-> (FilePath -> FilePath)
-> Maybe (FilePath -> FilePath)
-> Maybe (FilePath -> FilePath)
-> flags
-> (ShowOrParseArgs -> [OptionField flags])
-> CommandUI flags
CommandUI
  { commandName :: FilePath
commandName         = FilePath
"bench"
  , commandSynopsis :: FilePath
commandSynopsis     =
      FilePath
"Run all/specific benchmarks."
  , commandDescription :: Maybe (FilePath -> FilePath)
commandDescription  = (FilePath -> FilePath) -> Maybe (FilePath -> FilePath)
forall a. a -> Maybe a
Just ((FilePath -> FilePath) -> Maybe (FilePath -> FilePath))
-> (FilePath -> FilePath) -> Maybe (FilePath -> FilePath)
forall a b. (a -> b) -> a -> b
$ \FilePath
pname -> FilePath -> FilePath
wrapText (FilePath -> FilePath) -> FilePath -> FilePath
forall a b. (a -> b) -> a -> b
$
         FilePath
"If necessary (re)configures with `--enable-benchmarks` flag and"
      FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
" builds the benchmarks.\n"
      FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
"\n"
      FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
"Remember that the benchmarks' dependencies must be installed if"
      FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
" there are additional ones; e.g. with `" FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
pname
      FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
" install --only-dependencies --enable-benchmarks`.\n"
      FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
"\n"
      FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
"By defining UserHooks in a custom Setup.hs, the package can"
      FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
" define actions to be executed before and after running"
      FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
" benchmarks.\n"
  , commandNotes :: Maybe (FilePath -> FilePath)
commandNotes        = Maybe (FilePath -> FilePath)
forall a. Maybe a
Nothing
  , commandUsage :: FilePath -> FilePath
commandUsage        = FilePath -> [FilePath] -> FilePath -> FilePath
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 :: Flag Verbosity
benchmarkVerbosity = Flag Verbosity
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 :: Flag FilePath
benchmarkDistPref = Flag FilePath
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 -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
"(name templates can use $pkgid, $compiler, "
         FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
"$os, $arch, $benchmark)")
        BenchmarkFlags -> [PathTemplate]
benchmarkOptions (\[PathTemplate]
v BenchmarkFlags
flags -> BenchmarkFlags
flags { benchmarkOptions :: [PathTemplate]
benchmarkOptions = [PathTemplate]
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 -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
"(no need to quote options containing spaces, "
         FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
"name template can use $pkgid, $compiler, "
         FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
"$os, $arch, $benchmark)")
        BenchmarkFlags -> [PathTemplate]
benchmarkOptions (\[PathTemplate]
v BenchmarkFlags
flags -> BenchmarkFlags
flags { benchmarkOptions :: [PathTemplate]
benchmarkOptions = [PathTemplate]
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

-- ------------------------------------------------------------
-- * Shared options utils
-- ------------------------------------------------------------

programFlagsDescription :: ProgramDb -> String
programFlagsDescription :: ProgramDb -> FilePath
programFlagsDescription ProgramDb
progDb =
     FilePath
"The flags --with-PROG and --PROG-option(s) can be used with"
  FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
" the following programs:"
  FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ (([FilePath] -> FilePath) -> [[FilePath]] -> FilePath
forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap (\[FilePath]
line -> FilePath
"\n  " FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ [FilePath] -> FilePath
unwords [FilePath]
line) ([[FilePath]] -> FilePath)
-> ([FilePath] -> [[FilePath]]) -> [FilePath] -> FilePath
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> [FilePath] -> [[FilePath]]
wrapLine Int
77 ([FilePath] -> [[FilePath]])
-> ([FilePath] -> [FilePath]) -> [FilePath] -> [[FilePath]]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [FilePath] -> [FilePath]
forall a. Ord a => [a] -> [a]
sort)
     [ Program -> FilePath
programName Program
prog | (Program
prog, Maybe ConfiguredProgram
_) <- ProgramDb -> [(Program, Maybe ConfiguredProgram)]
knownPrograms ProgramDb
progDb ]
  FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
"\n"

-- | For each known program @PROG@ in 'progDb', produce a @with-PROG@
-- 'OptionField'.
programDbPaths
  :: ProgramDb
  -> ShowOrParseArgs
  -> (flags -> [(String, FilePath)])
  -> ([(String, FilePath)] -> (flags -> flags))
  -> [OptionField flags]
programDbPaths :: ProgramDb
-> ShowOrParseArgs
-> (flags -> [(FilePath, FilePath)])
-> ([(FilePath, FilePath)] -> flags -> flags)
-> [OptionField flags]
programDbPaths ProgramDb
progDb ShowOrParseArgs
showOrParseArgs flags -> [(FilePath, FilePath)]
get [(FilePath, FilePath)] -> flags -> flags
set =
  (FilePath -> FilePath)
-> ProgramDb
-> ShowOrParseArgs
-> (flags -> [(FilePath, FilePath)])
-> ([(FilePath, FilePath)] -> flags -> flags)
-> [OptionField flags]
forall flags.
(FilePath -> FilePath)
-> ProgramDb
-> ShowOrParseArgs
-> (flags -> [(FilePath, FilePath)])
-> ([(FilePath, FilePath)] -> flags -> flags)
-> [OptionField flags]
programDbPaths' (FilePath
"with-" FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++) ProgramDb
progDb ShowOrParseArgs
showOrParseArgs flags -> [(FilePath, FilePath)]
get [(FilePath, FilePath)] -> flags -> flags
set

-- | Like 'programDbPaths', but allows to customise the option name.
programDbPaths'
  :: (String -> String)
  -> ProgramDb
  -> ShowOrParseArgs
  -> (flags -> [(String, FilePath)])
  -> ([(String, FilePath)] -> (flags -> flags))
  -> [OptionField flags]
programDbPaths' :: (FilePath -> FilePath)
-> ProgramDb
-> ShowOrParseArgs
-> (flags -> [(FilePath, FilePath)])
-> ([(FilePath, FilePath)] -> flags -> flags)
-> [OptionField flags]
programDbPaths' FilePath -> FilePath
mkName ProgramDb
progDb ShowOrParseArgs
showOrParseArgs flags -> [(FilePath, FilePath)]
get [(FilePath, FilePath)] -> flags -> flags
set =
  case ShowOrParseArgs
showOrParseArgs of
    -- we don't want a verbose help text list so we just show a generic one:
    ShowOrParseArgs
ShowArgs  -> [FilePath -> OptionField flags
withProgramPath FilePath
"PROG"]
    ShowOrParseArgs
ParseArgs -> ((Program, Maybe ConfiguredProgram) -> OptionField flags)
-> [(Program, Maybe ConfiguredProgram)] -> [OptionField flags]
forall a b. (a -> b) -> [a] -> [b]
map (FilePath -> OptionField flags
withProgramPath (FilePath -> OptionField flags)
-> ((Program, Maybe ConfiguredProgram) -> FilePath)
-> (Program, Maybe ConfiguredProgram)
-> OptionField flags
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Program -> FilePath
programName (Program -> FilePath)
-> ((Program, Maybe ConfiguredProgram) -> Program)
-> (Program, Maybe ConfiguredProgram)
-> FilePath
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Program, Maybe ConfiguredProgram) -> Program
forall a b. (a, b) -> a
fst)
                 (ProgramDb -> [(Program, Maybe ConfiguredProgram)]
knownPrograms ProgramDb
progDb)
  where
    withProgramPath :: FilePath -> OptionField flags
withProgramPath FilePath
prog =
      FilePath
-> [FilePath]
-> FilePath
-> (flags -> [(FilePath, FilePath)])
-> ([(FilePath, FilePath)] -> flags -> flags)
-> MkOptDescr
     (flags -> [(FilePath, FilePath)])
     ([(FilePath, FilePath)] -> flags -> flags)
     flags
-> OptionField flags
forall get set a.
FilePath
-> [FilePath]
-> FilePath
-> get
-> set
-> MkOptDescr get set a
-> OptionField a
option FilePath
"" [FilePath -> FilePath
mkName FilePath
prog]
        (FilePath
"give the path to " FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
prog)
        flags -> [(FilePath, FilePath)]
get [(FilePath, FilePath)] -> flags -> flags
set
        (FilePath
-> (FilePath -> [(FilePath, FilePath)])
-> ([(FilePath, FilePath)] -> [FilePath])
-> MkOptDescr
     (flags -> [(FilePath, FilePath)])
     ([(FilePath, FilePath)] -> flags -> flags)
     flags
forall b a.
Monoid b =>
FilePath
-> (FilePath -> b)
-> (b -> [FilePath])
-> MkOptDescr (a -> b) (b -> a -> a) a
reqArg' FilePath
"PATH" (\FilePath
path -> [(FilePath
prog, FilePath
path)])
          (\[(FilePath, FilePath)]
progPaths -> [ FilePath
path | (FilePath
prog', FilePath
path) <- [(FilePath, FilePath)]
progPaths, FilePath
progFilePath -> FilePath -> Bool
forall a. Eq a => a -> a -> Bool
==FilePath
prog' ]))

-- | For each known program @PROG@ in 'progDb', produce a @PROG-option@
-- 'OptionField'.
programDbOption
  :: ProgramDb
  -> ShowOrParseArgs
  -> (flags -> [(String, [String])])
  -> ([(String, [String])] -> (flags -> flags))
  -> [OptionField flags]
programDbOption :: ProgramDb
-> ShowOrParseArgs
-> (flags -> [(FilePath, [FilePath])])
-> ([(FilePath, [FilePath])] -> flags -> flags)
-> [OptionField flags]
programDbOption ProgramDb
progDb ShowOrParseArgs
showOrParseArgs flags -> [(FilePath, [FilePath])]
get [(FilePath, [FilePath])] -> flags -> flags
set =
  case ShowOrParseArgs
showOrParseArgs of
    -- we don't want a verbose help text list so we just show a generic one:
    ShowOrParseArgs
ShowArgs  -> [FilePath -> OptionField flags
programOption FilePath
"PROG"]
    ShowOrParseArgs
ParseArgs -> ((Program, Maybe ConfiguredProgram) -> OptionField flags)
-> [(Program, Maybe ConfiguredProgram)] -> [OptionField flags]
forall a b. (a -> b) -> [a] -> [b]
map (FilePath -> OptionField flags
programOption  (FilePath -> OptionField flags)
-> ((Program, Maybe ConfiguredProgram) -> FilePath)
-> (Program, Maybe ConfiguredProgram)
-> OptionField flags
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Program -> FilePath
programName (Program -> FilePath)
-> ((Program, Maybe ConfiguredProgram) -> Program)
-> (Program, Maybe ConfiguredProgram)
-> FilePath
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Program, Maybe ConfiguredProgram) -> Program
forall a b. (a, b) -> a
fst)
                 (ProgramDb -> [(Program, Maybe ConfiguredProgram)]
knownPrograms ProgramDb
progDb)
  where
    programOption :: FilePath -> OptionField flags
programOption FilePath
prog =
      FilePath
-> [FilePath]
-> FilePath
-> (flags -> [(FilePath, [FilePath])])
-> ([(FilePath, [FilePath])] -> flags -> flags)
-> MkOptDescr
     (flags -> [(FilePath, [FilePath])])
     ([(FilePath, [FilePath])] -> flags -> flags)
     flags
-> OptionField flags
forall get set a.
FilePath
-> [FilePath]
-> FilePath
-> get
-> set
-> MkOptDescr get set a
-> OptionField a
option FilePath
"" [FilePath
prog FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
"-option"]
        (FilePath
"give an extra option to " FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
prog FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++
         FilePath
" (no need to quote options containing spaces)")
        flags -> [(FilePath, [FilePath])]
get [(FilePath, [FilePath])] -> flags -> flags
set
        (FilePath
-> (FilePath -> [(FilePath, [FilePath])])
-> ([(FilePath, [FilePath])] -> [FilePath])
-> MkOptDescr
     (flags -> [(FilePath, [FilePath])])
     ([(FilePath, [FilePath])] -> flags -> flags)
     flags
forall b a.
Monoid b =>
FilePath
-> (FilePath -> b)
-> (b -> [FilePath])
-> MkOptDescr (a -> b) (b -> a -> a) a
reqArg' FilePath
"OPT" (\FilePath
arg -> [(FilePath
prog, [FilePath
arg])])
           (\[(FilePath, [FilePath])]
progArgs -> [[FilePath]] -> [FilePath]
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat [ [FilePath]
args
                                | (FilePath
prog', [FilePath]
args) <- [(FilePath, [FilePath])]
progArgs, FilePath
progFilePath -> FilePath -> Bool
forall a. Eq a => a -> a -> Bool
==FilePath
prog' ]))


-- | For each known program @PROG@ in 'progDb', produce a @PROG-options@
-- 'OptionField'.
programDbOptions
  :: ProgramDb
  -> ShowOrParseArgs
  -> (flags -> [(String, [String])])
  -> ([(String, [String])] -> (flags -> flags))
  -> [OptionField flags]
programDbOptions :: ProgramDb
-> ShowOrParseArgs
-> (flags -> [(FilePath, [FilePath])])
-> ([(FilePath, [FilePath])] -> flags -> flags)
-> [OptionField flags]
programDbOptions ProgramDb
progDb ShowOrParseArgs
showOrParseArgs flags -> [(FilePath, [FilePath])]
get [(FilePath, [FilePath])] -> flags -> flags
set =
  case ShowOrParseArgs
showOrParseArgs of
    -- we don't want a verbose help text list so we just show a generic one:
    ShowOrParseArgs
ShowArgs  -> [FilePath -> OptionField flags
programOptions  FilePath
"PROG"]
    ShowOrParseArgs
ParseArgs -> ((Program, Maybe ConfiguredProgram) -> OptionField flags)
-> [(Program, Maybe ConfiguredProgram)] -> [OptionField flags]
forall a b. (a -> b) -> [a] -> [b]
map (FilePath -> OptionField flags
programOptions (FilePath -> OptionField flags)
-> ((Program, Maybe ConfiguredProgram) -> FilePath)
-> (Program, Maybe ConfiguredProgram)
-> OptionField flags
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Program -> FilePath
programName (Program -> FilePath)
-> ((Program, Maybe ConfiguredProgram) -> Program)
-> (Program, Maybe ConfiguredProgram)
-> FilePath
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Program, Maybe ConfiguredProgram) -> Program
forall a b. (a, b) -> a
fst)
                 (ProgramDb -> [(Program, Maybe ConfiguredProgram)]
knownPrograms ProgramDb
progDb)
  where
    programOptions :: FilePath -> OptionField flags
programOptions FilePath
prog =
      FilePath
-> [FilePath]
-> FilePath
-> (flags -> [(FilePath, [FilePath])])
-> ([(FilePath, [FilePath])] -> flags -> flags)
-> MkOptDescr
     (flags -> [(FilePath, [FilePath])])
     ([(FilePath, [FilePath])] -> flags -> flags)
     flags
-> OptionField flags
forall get set a.
FilePath
-> [FilePath]
-> FilePath
-> get
-> set
-> MkOptDescr get set a
-> OptionField a
option FilePath
"" [FilePath
prog FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
"-options"]
        (FilePath
"give extra options to " FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
prog)
        flags -> [(FilePath, [FilePath])]
get [(FilePath, [FilePath])] -> flags -> flags
set
        (FilePath
-> (FilePath -> [(FilePath, [FilePath])])
-> ([(FilePath, [FilePath])] -> [FilePath])
-> MkOptDescr
     (flags -> [(FilePath, [FilePath])])
     ([(FilePath, [FilePath])] -> flags -> flags)
     flags
forall b a.
Monoid b =>
FilePath
-> (FilePath -> b)
-> (b -> [FilePath])
-> MkOptDescr (a -> b) (b -> a -> a) a
reqArg' FilePath
"OPTS" (\FilePath
args -> [(FilePath
prog, FilePath -> [FilePath]
splitArgs FilePath
args)]) ([FilePath] -> [(FilePath, [FilePath])] -> [FilePath]
forall a b. a -> b -> a
const []))

-- ------------------------------------------------------------
-- * GetOpt Utils
-- ------------------------------------------------------------

boolOpt :: SFlags -> SFlags
           -> MkOptDescr (a -> Flag Bool) (Flag Bool -> a -> a) a
boolOpt :: FilePath
-> FilePath -> MkOptDescr (a -> Flag Bool) (Flag Bool -> a -> a) a
boolOpt  = (Flag Bool -> Maybe Bool)
-> (Bool -> Flag Bool)
-> FilePath
-> FilePath
-> MkOptDescr (a -> Flag Bool) (Flag Bool -> a -> a) a
forall b a.
(b -> Maybe Bool)
-> (Bool -> b)
-> FilePath
-> FilePath
-> MkOptDescr (a -> b) (b -> a -> a) a
Command.boolOpt  Flag Bool -> Maybe Bool
forall a. Flag a -> Maybe a
flagToMaybe Bool -> Flag Bool
forall a. a -> Flag a
Flag

boolOpt' :: OptFlags -> OptFlags
            -> MkOptDescr (a -> Flag Bool) (Flag Bool -> a -> a) a
boolOpt' :: (FilePath, [FilePath])
-> (FilePath, [FilePath])
-> MkOptDescr (a -> Flag Bool) (Flag Bool -> a -> a) a
boolOpt' = (Flag Bool -> Maybe Bool)
-> (Bool -> Flag Bool)
-> (FilePath, [FilePath])
-> (FilePath, [FilePath])
-> MkOptDescr (a -> Flag Bool) (Flag Bool -> a -> a) a
forall b a.
(b -> Maybe Bool)
-> (Bool -> b)
-> (FilePath, [FilePath])
-> (FilePath, [FilePath])
-> MkOptDescr (a -> b) (b -> a -> a) a
Command.boolOpt' Flag Bool -> Maybe Bool
forall a. Flag a -> Maybe a
flagToMaybe Bool -> Flag Bool
forall a. a -> Flag a
Flag

trueArg, falseArg :: MkOptDescr (a -> Flag Bool) (Flag Bool -> a -> a) a
trueArg :: MkOptDescr (a -> Flag Bool) (Flag Bool -> a -> a) a
trueArg  FilePath
sfT [FilePath]
lfT = (FilePath, [FilePath])
-> (FilePath, [FilePath])
-> MkOptDescr (a -> Flag Bool) (Flag Bool -> a -> a) a
forall a.
(FilePath, [FilePath])
-> (FilePath, [FilePath])
-> MkOptDescr (a -> Flag Bool) (Flag Bool -> a -> a) a
boolOpt' (FilePath
sfT, [FilePath]
lfT) ([], [])   FilePath
sfT [FilePath]
lfT
falseArg :: MkOptDescr (a -> Flag Bool) (Flag Bool -> a -> a) a
falseArg FilePath
sfF [FilePath]
lfF = (FilePath, [FilePath])
-> (FilePath, [FilePath])
-> MkOptDescr (a -> Flag Bool) (Flag Bool -> a -> a) a
forall a.
(FilePath, [FilePath])
-> (FilePath, [FilePath])
-> MkOptDescr (a -> Flag Bool) (Flag Bool -> a -> a) a
boolOpt' ([],  [])  (FilePath
sfF, [FilePath]
lfF) FilePath
sfF [FilePath]
lfF

reqArgFlag :: ArgPlaceHolder -> SFlags -> LFlags -> Description ->
              (b -> Flag String) -> (Flag String -> b -> b) -> OptDescr b
reqArgFlag :: FilePath
-> FilePath
-> [FilePath]
-> FilePath
-> (b -> Flag FilePath)
-> (Flag FilePath -> b -> b)
-> OptDescr b
reqArgFlag FilePath
ad = FilePath
-> ReadE (Flag FilePath)
-> (Flag FilePath -> [FilePath])
-> FilePath
-> [FilePath]
-> FilePath
-> (b -> Flag FilePath)
-> (Flag FilePath -> b -> b)
-> OptDescr b
forall b a.
Monoid b =>
FilePath
-> ReadE b
-> (b -> [FilePath])
-> MkOptDescr (a -> b) (b -> a -> a) a
reqArg FilePath
ad ((FilePath -> Flag FilePath) -> ReadE (Flag FilePath)
forall a. (FilePath -> a) -> ReadE a
succeedReadE FilePath -> Flag FilePath
forall a. a -> Flag a
Flag) Flag FilePath -> [FilePath]
forall a. Flag a -> [a]
flagToList

optionDistPref :: (flags -> Flag FilePath)
               -> (Flag FilePath -> flags -> flags)
               -> ShowOrParseArgs
               -> OptionField flags
optionDistPref :: (flags -> Flag FilePath)
-> (Flag FilePath -> flags -> flags)
-> ShowOrParseArgs
-> OptionField flags
optionDistPref flags -> Flag FilePath
get Flag FilePath -> flags -> flags
set = \ShowOrParseArgs
showOrParseArgs ->
  FilePath
-> [FilePath]
-> FilePath
-> (flags -> Flag FilePath)
-> (Flag FilePath -> flags -> flags)
-> MkOptDescr
     (flags -> Flag FilePath) (Flag FilePath -> flags -> flags) flags
-> OptionField flags
forall get set a.
FilePath
-> [FilePath]
-> FilePath
-> get
-> set
-> MkOptDescr get set a
-> OptionField a
option FilePath
"" (ShowOrParseArgs -> [FilePath]
distPrefFlagName ShowOrParseArgs
showOrParseArgs)
    (   FilePath
"The directory where Cabal puts generated build files "
     FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
"(default " FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
defaultDistPref FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
")")
    flags -> Flag FilePath
get Flag FilePath -> flags -> flags
set
    (FilePath
-> MkOptDescr
     (flags -> Flag FilePath) (Flag FilePath -> flags -> flags) flags
forall b.
FilePath
-> FilePath
-> [FilePath]
-> FilePath
-> (b -> Flag FilePath)
-> (Flag FilePath -> b -> b)
-> OptDescr b
reqArgFlag FilePath
"DIR")
  where
    distPrefFlagName :: ShowOrParseArgs -> [FilePath]
distPrefFlagName ShowOrParseArgs
ShowArgs  = [FilePath
"builddir"]
    distPrefFlagName ShowOrParseArgs
ParseArgs = [FilePath
"builddir", FilePath
"distdir", FilePath
"distpref"]

optionVerbosity :: (flags -> Flag Verbosity)
                -> (Flag Verbosity -> flags -> flags)
                -> OptionField flags
optionVerbosity :: (flags -> Flag Verbosity)
-> (Flag Verbosity -> flags -> flags) -> OptionField flags
optionVerbosity flags -> Flag Verbosity
get Flag Verbosity -> flags -> flags
set =
  FilePath
-> [FilePath]
-> FilePath
-> (flags -> Flag Verbosity)
-> (Flag Verbosity -> flags -> flags)
-> MkOptDescr
     (flags -> Flag Verbosity) (Flag Verbosity -> flags -> flags) flags
-> OptionField flags
forall get set a.
FilePath
-> [FilePath]
-> FilePath
-> get
-> set
-> MkOptDescr get set a
-> OptionField a
option FilePath
"v" [FilePath
"verbose"]
    FilePath
"Control verbosity (n is 0--3, default verbosity level is 1)"
    flags -> Flag Verbosity
get Flag Verbosity -> flags -> flags
set
    (FilePath
-> ReadE (Flag Verbosity)
-> Flag Verbosity
-> (Flag Verbosity -> [Maybe FilePath])
-> MkOptDescr
     (flags -> Flag Verbosity) (Flag Verbosity -> flags -> flags) flags
forall b a.
Monoid b =>
FilePath
-> ReadE b
-> b
-> (b -> [Maybe FilePath])
-> MkOptDescr (a -> b) (b -> a -> a) a
optArg FilePath
"n" ((Verbosity -> Flag Verbosity)
-> ReadE Verbosity -> ReadE (Flag Verbosity)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Verbosity -> Flag Verbosity
forall a. a -> Flag a
Flag ReadE Verbosity
flagToVerbosity)
                (Verbosity -> Flag Verbosity
forall a. a -> Flag a
Flag Verbosity
verbose) -- default Value if no n is given
                ((Verbosity -> Maybe FilePath) -> [Verbosity] -> [Maybe FilePath]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (FilePath -> Maybe FilePath
forall a. a -> Maybe a
Just (FilePath -> Maybe FilePath)
-> (Verbosity -> FilePath) -> Verbosity -> Maybe FilePath
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Verbosity -> FilePath
showForCabal) ([Verbosity] -> [Maybe FilePath])
-> (Flag Verbosity -> [Verbosity])
-> Flag Verbosity
-> [Maybe FilePath]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Flag Verbosity -> [Verbosity]
forall a. Flag a -> [a]
flagToList))

optionNumJobs :: (flags -> Flag (Maybe Int))
              -> (Flag (Maybe Int) -> flags -> flags)
              -> OptionField flags
optionNumJobs :: (flags -> Flag (Maybe Int))
-> (Flag (Maybe Int) -> flags -> flags) -> OptionField flags
optionNumJobs flags -> Flag (Maybe Int)
get Flag (Maybe Int) -> flags -> flags
set =
  FilePath
-> [FilePath]
-> FilePath
-> (flags -> Flag (Maybe Int))
-> (Flag (Maybe Int) -> flags -> flags)
-> MkOptDescr
     (flags -> Flag (Maybe Int))
     (Flag (Maybe Int) -> flags -> flags)
     flags
-> OptionField flags
forall get set a.
FilePath
-> [FilePath]
-> FilePath
-> get
-> set
-> MkOptDescr get set a
-> OptionField a
option FilePath
"j" [FilePath
"jobs"]
    FilePath
"Run NUM jobs simultaneously (or '$ncpus' if no NUM is given)."
    flags -> Flag (Maybe Int)
get Flag (Maybe Int) -> flags -> flags
set
    (FilePath
-> ReadE (Flag (Maybe Int))
-> Flag (Maybe Int)
-> (Flag (Maybe Int) -> [Maybe FilePath])
-> MkOptDescr
     (flags -> Flag (Maybe Int))
     (Flag (Maybe Int) -> flags -> flags)
     flags
forall b a.
Monoid b =>
FilePath
-> ReadE b
-> b
-> (b -> [Maybe FilePath])
-> MkOptDescr (a -> b) (b -> a -> a) a
optArg FilePath
"NUM" ((Maybe Int -> Flag (Maybe Int))
-> ReadE (Maybe Int) -> ReadE (Flag (Maybe Int))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Maybe Int -> Flag (Maybe Int)
forall a. a -> Flag a
Flag ReadE (Maybe Int)
numJobsParser)
                  (Maybe Int -> Flag (Maybe Int)
forall a. a -> Flag a
Flag Maybe Int
forall a. Maybe a
Nothing)
                  ((Maybe Int -> Maybe FilePath) -> [Maybe Int] -> [Maybe FilePath]
forall a b. (a -> b) -> [a] -> [b]
map (FilePath -> Maybe FilePath
forall a. a -> Maybe a
Just (FilePath -> Maybe FilePath)
-> (Maybe Int -> FilePath) -> Maybe Int -> Maybe FilePath
forall b c a. (b -> c) -> (a -> b) -> a -> c
. FilePath -> (Int -> FilePath) -> Maybe Int -> FilePath
forall b a. b -> (a -> b) -> Maybe a -> b
maybe FilePath
"$ncpus" Int -> FilePath
forall a. Show a => a -> FilePath
show) ([Maybe Int] -> [Maybe FilePath])
-> (Flag (Maybe Int) -> [Maybe Int])
-> Flag (Maybe Int)
-> [Maybe FilePath]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Flag (Maybe Int) -> [Maybe Int]
forall a. Flag a -> [a]
flagToList))
  where
    numJobsParser :: ReadE (Maybe Int)
    numJobsParser :: ReadE (Maybe Int)
numJobsParser = (FilePath -> Either FilePath (Maybe Int)) -> ReadE (Maybe Int)
forall a. (FilePath -> Either FilePath a) -> ReadE a
ReadE ((FilePath -> Either FilePath (Maybe Int)) -> ReadE (Maybe Int))
-> (FilePath -> Either FilePath (Maybe Int)) -> ReadE (Maybe Int)
forall a b. (a -> b) -> a -> b
$ \FilePath
s ->
      case FilePath
s of
        FilePath
"$ncpus" -> Maybe Int -> Either FilePath (Maybe Int)
forall a b. b -> Either a b
Right Maybe Int
forall a. Maybe a
Nothing
        FilePath
_        -> case ReadS Int
forall a. Read a => ReadS a
reads FilePath
s of
          [(Int
n, FilePath
"")]
            | Int
n Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
< Int
1     -> FilePath -> Either FilePath (Maybe Int)
forall a b. a -> Either a b
Left FilePath
"The number of jobs should be 1 or more."
            | Bool
otherwise -> Maybe Int -> Either FilePath (Maybe Int)
forall a b. b -> Either a b
Right (Int -> Maybe Int
forall a. a -> Maybe a
Just Int
n)
          [(Int, FilePath)]
_             -> FilePath -> Either FilePath (Maybe Int)
forall a b. a -> Either a b
Left FilePath
"The jobs value should be a number or '$ncpus'"


-- ------------------------------------------------------------
-- * show-build-info command flags
-- ------------------------------------------------------------

data ShowBuildInfoFlags = ShowBuildInfoFlags
  { ShowBuildInfoFlags -> BuildFlags
buildInfoBuildFlags :: BuildFlags
  , ShowBuildInfoFlags -> Maybe FilePath
buildInfoOutputFile :: Maybe FilePath
  } deriving (Int -> ShowBuildInfoFlags -> FilePath -> FilePath
[ShowBuildInfoFlags] -> FilePath -> FilePath
ShowBuildInfoFlags -> FilePath
(Int -> ShowBuildInfoFlags -> FilePath -> FilePath)
-> (ShowBuildInfoFlags -> FilePath)
-> ([ShowBuildInfoFlags] -> FilePath -> FilePath)
-> Show ShowBuildInfoFlags
forall a.
(Int -> a -> FilePath -> FilePath)
-> (a -> FilePath) -> ([a] -> FilePath -> FilePath) -> Show a
showList :: [ShowBuildInfoFlags] -> FilePath -> FilePath
$cshowList :: [ShowBuildInfoFlags] -> FilePath -> FilePath
show :: ShowBuildInfoFlags -> FilePath
$cshow :: ShowBuildInfoFlags -> FilePath
showsPrec :: Int -> ShowBuildInfoFlags -> FilePath -> FilePath
$cshowsPrec :: Int -> ShowBuildInfoFlags -> FilePath -> FilePath
Show, Typeable)

defaultShowBuildFlags  :: ShowBuildInfoFlags
defaultShowBuildFlags :: ShowBuildInfoFlags
defaultShowBuildFlags =
    ShowBuildInfoFlags :: BuildFlags -> Maybe FilePath -> ShowBuildInfoFlags
ShowBuildInfoFlags
      { buildInfoBuildFlags :: BuildFlags
buildInfoBuildFlags = BuildFlags
defaultBuildFlags
      , buildInfoOutputFile :: Maybe FilePath
buildInfoOutputFile = Maybe FilePath
forall a. Maybe a
Nothing
      }

showBuildInfoCommand :: ProgramDb -> CommandUI ShowBuildInfoFlags
showBuildInfoCommand :: ProgramDb -> CommandUI ShowBuildInfoFlags
showBuildInfoCommand ProgramDb
progDb = CommandUI :: forall flags.
FilePath
-> FilePath
-> (FilePath -> FilePath)
-> Maybe (FilePath -> FilePath)
-> Maybe (FilePath -> FilePath)
-> flags
-> (ShowOrParseArgs -> [OptionField flags])
-> CommandUI flags
CommandUI
  { commandName :: FilePath
commandName         = FilePath
"show-build-info"
  , commandSynopsis :: FilePath
commandSynopsis     = FilePath
"Emit details about how a package would be built."
  , commandDescription :: Maybe (FilePath -> FilePath)
commandDescription  = (FilePath -> FilePath) -> Maybe (FilePath -> FilePath)
forall a. a -> Maybe a
Just ((FilePath -> FilePath) -> Maybe (FilePath -> FilePath))
-> (FilePath -> FilePath) -> Maybe (FilePath -> FilePath)
forall a b. (a -> b) -> a -> b
$ \FilePath
_ -> FilePath -> FilePath
wrapText (FilePath -> FilePath) -> FilePath -> FilePath
forall a b. (a -> b) -> a -> b
$
         FilePath
"Components encompass executables, tests, and benchmarks.\n"
      FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
"\n"
      FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
"Affected by configuration options, see `configure`.\n"
  , commandNotes :: Maybe (FilePath -> FilePath)
commandNotes        = (FilePath -> FilePath) -> Maybe (FilePath -> FilePath)
forall a. a -> Maybe a
Just ((FilePath -> FilePath) -> Maybe (FilePath -> FilePath))
-> (FilePath -> FilePath) -> Maybe (FilePath -> FilePath)
forall a b. (a -> b) -> a -> b
$ \FilePath
pname ->
       FilePath
"Examples:\n"
        FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
"  " FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
pname FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
" show-build-info      "
        FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
"    All the components in the package\n"
        FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
"  " FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
pname FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
" show-build-info foo       "
        FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
"    A component (i.e. lib, exe, test suite)\n\n"
        FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ ProgramDb -> FilePath
programFlagsDescription ProgramDb
progDb
--TODO: re-enable once we have support for module/file targets
--        ++ "  " ++ pname ++ " show-build-info Foo.Bar   "
--        ++ "    A module\n"
--        ++ "  " ++ pname ++ " show-build-info Foo/Bar.hs"
--        ++ "    A file\n\n"
--        ++ "If a target is ambiguous it can be qualified with the component "
--        ++ "name, e.g.\n"
--        ++ "  " ++ pname ++ " show-build-info foo:Foo.Bar\n"
--        ++ "  " ++ pname ++ " show-build-info testsuite1:Foo/Bar.hs\n"
  , commandUsage :: FilePath -> FilePath
commandUsage        = FilePath -> [FilePath] -> FilePath -> FilePath
usageAlternatives FilePath
"show-build-info" ([FilePath] -> FilePath -> FilePath)
-> [FilePath] -> FilePath -> FilePath
forall a b. (a -> b) -> a -> b
$
      [ FilePath
"[FLAGS]"
      , FilePath
"COMPONENTS [FLAGS]"
      ]
  , commandDefaultFlags :: ShowBuildInfoFlags
commandDefaultFlags = ShowBuildInfoFlags
defaultShowBuildFlags
  , commandOptions :: ShowOrParseArgs -> [OptionField ShowBuildInfoFlags]
commandOptions      = \ShowOrParseArgs
showOrParseArgs ->
      ShowOrParseArgs -> ProgramDb -> [OptionField ShowBuildInfoFlags]
parseBuildFlagsForShowBuildInfoFlags ShowOrParseArgs
showOrParseArgs ProgramDb
progDb
      [OptionField ShowBuildInfoFlags]
-> [OptionField ShowBuildInfoFlags]
-> [OptionField ShowBuildInfoFlags]
forall a. [a] -> [a] -> [a]
++
      [ FilePath
-> [FilePath]
-> FilePath
-> (ShowBuildInfoFlags -> Maybe FilePath)
-> (Maybe FilePath -> ShowBuildInfoFlags -> ShowBuildInfoFlags)
-> MkOptDescr
     (ShowBuildInfoFlags -> Maybe FilePath)
     (Maybe FilePath -> ShowBuildInfoFlags -> ShowBuildInfoFlags)
     ShowBuildInfoFlags
-> OptionField ShowBuildInfoFlags
forall get set a.
FilePath
-> [FilePath]
-> FilePath
-> get
-> set
-> MkOptDescr get set a
-> OptionField a
option [] [FilePath
"buildinfo-json-output"]
                FilePath
"Write the result to the given file instead of stdout"
                ShowBuildInfoFlags -> Maybe FilePath
buildInfoOutputFile (\Maybe FilePath
pf ShowBuildInfoFlags
flags -> ShowBuildInfoFlags
flags { buildInfoOutputFile :: Maybe FilePath
buildInfoOutputFile = Maybe FilePath
pf })
                (FilePath
-> (FilePath -> Maybe FilePath)
-> (Maybe FilePath -> [FilePath])
-> MkOptDescr
     (ShowBuildInfoFlags -> Maybe FilePath)
     (Maybe FilePath -> ShowBuildInfoFlags -> ShowBuildInfoFlags)
     ShowBuildInfoFlags
forall b a.
Monoid b =>
FilePath
-> (FilePath -> b)
-> (b -> [FilePath])
-> MkOptDescr (a -> b) (b -> a -> a) a
reqArg' FilePath
"FILE" FilePath -> Maybe FilePath
forall a. a -> Maybe a
Just ([FilePath]
-> (FilePath -> [FilePath]) -> Maybe FilePath -> [FilePath]
forall b a. b -> (a -> b) -> Maybe a -> b
maybe [] FilePath -> [FilePath]
forall (f :: * -> *) a. Applicative f => a -> f a
pure))
      ]

  }

parseBuildFlagsForShowBuildInfoFlags :: ShowOrParseArgs -> ProgramDb -> [OptionField ShowBuildInfoFlags]
parseBuildFlagsForShowBuildInfoFlags :: ShowOrParseArgs -> ProgramDb -> [OptionField ShowBuildInfoFlags]
parseBuildFlagsForShowBuildInfoFlags ShowOrParseArgs
showOrParseArgs ProgramDb
progDb =
  (OptionField BuildFlags -> OptionField ShowBuildInfoFlags)
-> [OptionField BuildFlags] -> [OptionField ShowBuildInfoFlags]
forall a b. (a -> b) -> [a] -> [b]
map
      ((ShowBuildInfoFlags -> BuildFlags)
-> (BuildFlags -> ShowBuildInfoFlags -> ShowBuildInfoFlags)
-> OptionField BuildFlags
-> OptionField ShowBuildInfoFlags
forall b a.
(b -> a) -> (a -> b -> b) -> OptionField a -> OptionField b
liftOption
        ShowBuildInfoFlags -> BuildFlags
buildInfoBuildFlags
          (\BuildFlags
bf ShowBuildInfoFlags
flags -> ShowBuildInfoFlags
flags { buildInfoBuildFlags :: BuildFlags
buildInfoBuildFlags = BuildFlags
bf } )
      )
      [OptionField BuildFlags]
buildFlags
  where
    buildFlags :: [OptionField BuildFlags]
buildFlags = ProgramDb -> ShowOrParseArgs -> [OptionField BuildFlags]
buildOptions ProgramDb
progDb ShowOrParseArgs
showOrParseArgs
      [OptionField BuildFlags]
-> [OptionField BuildFlags] -> [OptionField BuildFlags]
forall a. [a] -> [a] -> [a]
++
      [ (BuildFlags -> Flag Verbosity)
-> (Flag Verbosity -> BuildFlags -> BuildFlags)
-> OptionField BuildFlags
forall flags.
(flags -> Flag Verbosity)
-> (Flag Verbosity -> flags -> flags) -> OptionField flags
optionVerbosity
        BuildFlags -> Flag Verbosity
buildVerbosity (\Flag Verbosity
v BuildFlags
flags -> BuildFlags
flags { buildVerbosity :: Flag Verbosity
buildVerbosity = Flag Verbosity
v })

      , (BuildFlags -> Flag FilePath)
-> (Flag FilePath -> BuildFlags -> BuildFlags)
-> ShowOrParseArgs
-> OptionField BuildFlags
forall flags.
(flags -> Flag FilePath)
-> (Flag FilePath -> flags -> flags)
-> ShowOrParseArgs
-> OptionField flags
optionDistPref
        BuildFlags -> Flag FilePath
buildDistPref (\Flag FilePath
d BuildFlags
flags -> BuildFlags
flags { buildDistPref :: Flag FilePath
buildDistPref = Flag FilePath
d }) ShowOrParseArgs
showOrParseArgs
      ]

-- ------------------------------------------------------------
-- * Other Utils
-- ------------------------------------------------------------

-- | Arguments to pass to a @configure@ script, e.g. generated by
-- @autoconf@.
configureArgs :: Bool -> ConfigFlags -> [String]
configureArgs :: Bool -> ConfigFlags -> [FilePath]
configureArgs Bool
bcHack ConfigFlags
flags
  = [FilePath]
hc_flag
 [FilePath] -> [FilePath] -> [FilePath]
forall a. [a] -> [a] -> [a]
++ FilePath -> (ConfigFlags -> Flag FilePath) -> [FilePath]
optFlag  FilePath
"with-hc-pkg" ConfigFlags -> Flag FilePath
configHcPkg
 [FilePath] -> [FilePath] -> [FilePath]
forall a. [a] -> [a] -> [a]
++ FilePath
-> (InstallDirs (Flag PathTemplate) -> Flag PathTemplate)
-> [FilePath]
optFlag' FilePath
"prefix"      InstallDirs (Flag PathTemplate) -> Flag PathTemplate
forall dir. InstallDirs dir -> dir
prefix
 [FilePath] -> [FilePath] -> [FilePath]
forall a. [a] -> [a] -> [a]
++ FilePath
-> (InstallDirs (Flag PathTemplate) -> Flag PathTemplate)
-> [FilePath]
optFlag' FilePath
"bindir"      InstallDirs (Flag PathTemplate) -> Flag PathTemplate
forall dir. InstallDirs dir -> dir
bindir
 [FilePath] -> [FilePath] -> [FilePath]
forall a. [a] -> [a] -> [a]
++ FilePath
-> (InstallDirs (Flag PathTemplate) -> Flag PathTemplate)
-> [FilePath]
optFlag' FilePath
"libdir"      InstallDirs (Flag PathTemplate) -> Flag PathTemplate
forall dir. InstallDirs dir -> dir
libdir
 [FilePath] -> [FilePath] -> [FilePath]
forall a. [a] -> [a] -> [a]
++ FilePath
-> (InstallDirs (Flag PathTemplate) -> Flag PathTemplate)
-> [FilePath]
optFlag' FilePath
"libexecdir"  InstallDirs (Flag PathTemplate) -> Flag PathTemplate
forall dir. InstallDirs dir -> dir
libexecdir
 [FilePath] -> [FilePath] -> [FilePath]
forall a. [a] -> [a] -> [a]
++ FilePath
-> (InstallDirs (Flag PathTemplate) -> Flag PathTemplate)
-> [FilePath]
optFlag' FilePath
"datadir"     InstallDirs (Flag PathTemplate) -> Flag PathTemplate
forall dir. InstallDirs dir -> dir
datadir
 [FilePath] -> [FilePath] -> [FilePath]
forall a. [a] -> [a] -> [a]
++ FilePath
-> (InstallDirs (Flag PathTemplate) -> Flag PathTemplate)
-> [FilePath]
optFlag' FilePath
"sysconfdir"  InstallDirs (Flag PathTemplate) -> Flag PathTemplate
forall dir. InstallDirs dir -> dir
sysconfdir
 [FilePath] -> [FilePath] -> [FilePath]
forall a. [a] -> [a] -> [a]
++ ConfigFlags -> [FilePath]
configConfigureArgs ConfigFlags
flags
  where
        hc_flag :: [FilePath]
hc_flag = case (ConfigFlags -> Flag CompilerFlavor
configHcFlavor ConfigFlags
flags, ConfigFlags -> Flag FilePath
configHcPath ConfigFlags
flags) of
                        (Flag CompilerFlavor
_, Flag FilePath
hc_path) -> [FilePath
hc_flag_name FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
hc_path]
                        (Flag CompilerFlavor
hc, Flag FilePath
NoFlag) -> [FilePath
hc_flag_name FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ CompilerFlavor -> FilePath
forall a. Pretty a => a -> FilePath
prettyShow CompilerFlavor
hc]
                        (Flag CompilerFlavor
NoFlag,Flag FilePath
NoFlag)   -> []
        hc_flag_name :: FilePath
hc_flag_name
            --TODO kill off thic bc hack when defaultUserHooks is removed.
            | Bool
bcHack    = FilePath
"--with-hc="
            | Bool
otherwise = FilePath
"--with-compiler="
        optFlag :: FilePath -> (ConfigFlags -> Flag FilePath) -> [FilePath]
optFlag FilePath
name ConfigFlags -> Flag FilePath
config_field = case ConfigFlags -> Flag FilePath
config_field ConfigFlags
flags of
                        Flag FilePath
p -> [FilePath
"--" FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
name FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
"=" FilePath -> FilePath -> FilePath
forall a. [a] -> [a] -> [a]
++ FilePath
p]
                        Flag FilePath
NoFlag -> []
        optFlag' :: FilePath
-> (InstallDirs (Flag PathTemplate) -> Flag PathTemplate)
-> [FilePath]
optFlag' FilePath
name InstallDirs (Flag PathTemplate) -> Flag PathTemplate
config_field = FilePath -> (ConfigFlags -> Flag FilePath) -> [FilePath]
optFlag FilePath
name ((PathTemplate -> FilePath) -> Flag PathTemplate -> Flag FilePath
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap PathTemplate -> FilePath
fromPathTemplate
                                                 (Flag PathTemplate -> Flag FilePath)
-> (ConfigFlags -> Flag PathTemplate)
-> ConfigFlags
-> Flag FilePath
forall b c a. (b -> c) -> (a -> b) -> a -> c
. InstallDirs (Flag PathTemplate) -> Flag PathTemplate
config_field
                                                 (InstallDirs (Flag PathTemplate) -> Flag PathTemplate)
-> (ConfigFlags -> InstallDirs (Flag PathTemplate))
-> ConfigFlags
-> Flag PathTemplate
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ConfigFlags -> InstallDirs (Flag PathTemplate)
configInstallDirs)

configureCCompiler :: Verbosity -> ProgramDb
                      -> IO (FilePath, [String])
configureCCompiler :: Verbosity -> ProgramDb -> IO (FilePath, [FilePath])
configureCCompiler Verbosity
verbosity ProgramDb
progdb = Verbosity -> ProgramDb -> Program -> IO (FilePath, [FilePath])
configureProg Verbosity
verbosity ProgramDb
progdb Program
gccProgram

configureLinker :: Verbosity -> ProgramDb -> IO (FilePath, [String])
configureLinker :: Verbosity -> ProgramDb -> IO (FilePath, [FilePath])
configureLinker Verbosity
verbosity ProgramDb
progdb = Verbosity -> ProgramDb -> Program -> IO (FilePath, [FilePath])
configureProg Verbosity
verbosity ProgramDb
progdb Program
ldProgram

configureProg :: Verbosity -> ProgramDb -> Program
                 -> IO (FilePath, [String])
configureProg :: Verbosity -> ProgramDb -> Program -> IO (FilePath, [FilePath])
configureProg Verbosity
verbosity ProgramDb
programDb Program
prog = do
    (ConfiguredProgram
p, ProgramDb
_) <- Verbosity
-> Program -> ProgramDb -> IO (ConfiguredProgram, ProgramDb)
requireProgram Verbosity
verbosity Program
prog ProgramDb
programDb
    let pInv :: ProgramInvocation
pInv = ConfiguredProgram -> [FilePath] -> ProgramInvocation
programInvocation ConfiguredProgram
p []
    (FilePath, [FilePath]) -> IO (FilePath, [FilePath])
forall (m :: * -> *) a. Monad m => a -> m a
return (ProgramInvocation -> FilePath
progInvokePath ProgramInvocation
pInv, ProgramInvocation -> [FilePath]
progInvokeArgs ProgramInvocation
pInv)

-- | Helper function to split a string into a list of arguments.
-- It's supposed to handle quoted things sensibly, eg:
--
-- > splitArgs "--foo=\"C:/Program Files/Bar/" --baz"
-- >   = ["--foo=C:/Program Files/Bar", "--baz"]
--
-- > splitArgs "\"-DMSGSTR=\\\"foo bar\\\"\" --baz"
-- >   = ["-DMSGSTR=\"foo bar\"","--baz"]
--
splitArgs :: String -> [String]
splitArgs :: FilePath -> [FilePath]
splitArgs  = FilePath -> FilePath -> [FilePath]
space []
  where
    space :: String -> String -> [String]
    space :: FilePath -> FilePath -> [FilePath]
space FilePath
w []      = FilePath -> [FilePath] -> [FilePath]
forall a. [a] -> [[a]] -> [[a]]
word FilePath
w []
    space FilePath
w ( Char
c :FilePath
s)
        | Char -> Bool
isSpace Char
c = FilePath -> [FilePath] -> [FilePath]
forall a. [a] -> [[a]] -> [[a]]
word FilePath
w (FilePath -> FilePath -> [FilePath]
space [] FilePath
s)
    space FilePath
w (Char
'"':FilePath
s) = FilePath -> FilePath -> [FilePath]
string FilePath
w FilePath
s
    space FilePath
w FilePath
s       = FilePath -> FilePath -> [FilePath]
nonstring FilePath
w FilePath
s

    string :: String -> String -> [String]
    string :: FilePath -> FilePath -> [FilePath]
string FilePath
w []      = FilePath -> [FilePath] -> [FilePath]
forall a. [a] -> [[a]] -> [[a]]
word FilePath
w []
    string FilePath
w (Char
'"':FilePath
s) = FilePath -> FilePath -> [FilePath]
space FilePath
w FilePath
s
    string FilePath
w (Char
'\\':Char
'"':FilePath
s) = FilePath -> FilePath -> [FilePath]
string (Char
'"'Char -> FilePath -> FilePath
forall a. a -> [a] -> [a]
:FilePath
w) FilePath
s
    string FilePath
w ( Char
c :FilePath
s) = FilePath -> FilePath -> [FilePath]
string (Char
cChar -> FilePath -> FilePath
forall a. a -> [a] -> [a]
:FilePath
w) FilePath
s

    nonstring :: String -> String -> [String]
    nonstring :: FilePath -> FilePath -> [FilePath]
nonstring FilePath
w  []      = FilePath -> [FilePath] -> [FilePath]
forall a. [a] -> [[a]] -> [[a]]
word FilePath
w []
    nonstring FilePath
w  (Char
'"':FilePath
s) = FilePath -> FilePath -> [FilePath]
string FilePath
w FilePath
s
    nonstring FilePath
w  ( Char
c :FilePath
s) = FilePath -> FilePath -> [FilePath]
space (Char
cChar -> FilePath -> FilePath
forall a. a -> [a] -> [a]
:FilePath
w) FilePath
s

    word :: [a] -> [[a]] -> [[a]]
word [] [[a]]
s = [[a]]
s
    word [a]
w  [[a]]
s = [a] -> [a]
forall a. [a] -> [a]
reverse [a]
w [a] -> [[a]] -> [[a]]
forall a. a -> [a] -> [a]
: [[a]]
s

-- The test cases kinda have to be rewritten from the ground up... :/
--hunitTests :: [Test]
--hunitTests =
--    let m = [("ghc", GHC), ("nhc98", NHC), ("hugs", Hugs)]
--        (flags, commands', unkFlags, ers)
--               = getOpt Permute options ["configure", "foobar", "--prefix=/foo", "--ghc", "--nhc98", "--hugs", "--with-compiler=/comp", "--unknown1", "--unknown2", "--install-prefix=/foo", "--user", "--global"]
--       in  [TestLabel "very basic option parsing" $ TestList [
--                 "getOpt flags" ~: "failed" ~:
--                 [Prefix "/foo", GhcFlag, NhcFlag, HugsFlag,
--                  WithCompiler "/comp", InstPrefix "/foo", UserFlag, GlobalFlag]
--                 ~=? flags,
--                 "getOpt commands" ~: "failed" ~: ["configure", "foobar"] ~=? commands',
--                 "getOpt unknown opts" ~: "failed" ~:
--                      ["--unknown1", "--unknown2"] ~=? unkFlags,
--                 "getOpt errors" ~: "failed" ~: [] ~=? ers],
--
--               TestLabel "test location of various compilers" $ TestList
--               ["configure parsing for prefix and compiler flag" ~: "failed" ~:
--                    (Right (ConfigCmd (Just comp, Nothing, Just "/usr/local"), []))
--                   ~=? (parseArgs ["--prefix=/usr/local", "--"++name, "configure"])
--                   | (name, comp) <- m],
--
--               TestLabel "find the package tool" $ TestList
--               ["configure parsing for prefix comp flag, withcompiler" ~: "failed" ~:
--                    (Right (ConfigCmd (Just comp, Just "/foo/comp", Just "/usr/local"), []))
--                   ~=? (parseArgs ["--prefix=/usr/local", "--"++name,
--                                   "--with-compiler=/foo/comp", "configure"])
--                   | (name, comp) <- m],
--
--               TestLabel "simpler commands" $ TestList
--               [flag ~: "failed" ~: (Right (flagCmd, [])) ~=? (parseArgs [flag])
--                   | (flag, flagCmd) <- [("build", BuildCmd),
--                                         ("install", InstallCmd Nothing False),
--                                         ("sdist", SDistCmd),
--                                         ("register", RegisterCmd False)]
--                  ]
--               ]

{- Testing ideas:
   * IO to look for hugs and hugs-pkg (which hugs, etc)
   * quickCheck to test permutations of arguments
   * what other options can we over-ride with a command-line flag?
-}