{-# 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, readPackageDb, readPackageDbList, showPackageDb, showPackageDbList,
  CopyFlags(..),     emptyCopyFlags,     defaultCopyFlags,     copyCommand,
  InstallFlags(..),  emptyInstallFlags,  defaultInstallFlags,  installCommand,
  HaddockTarget(..),
  HaddockFlags(..),  emptyHaddockFlags,  defaultHaddockFlags,  haddockCommand,
  Visibility(..),
  HaddockProjectFlags(..), emptyHaddockProjectFlags, defaultHaddockProjectFlags, haddockProjectCommand,
  HscolourFlags(..), emptyHscolourFlags, defaultHscolourFlags, hscolourCommand,
  BuildFlags(..),    emptyBuildFlags,    defaultBuildFlags,    buildCommand,
  DumpBuildInfo(..),
  ReplFlags(..),                         defaultReplFlags,     replCommand,
  ReplOptions(..),
  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, haddockProjectOptions, 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
import Distribution.Simple.Command hiding (boolOpt, boolOpt')
import qualified Distribution.Simple.Command as Command
import Distribution.Simple.Compiler
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.ComponentId
import Distribution.Types.DumpBuildInfo
import Distribution.Types.GivenComponent
import Distribution.Types.Module
import Distribution.Types.PackageVersionConstraint

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

-- FIXME Not sure where this should live
defaultDistPref :: FilePath
defaultDistPref :: String
defaultDistPref = String
"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. 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 {
    globalVersion :: Flag Bool
globalVersion        = forall a. a -> Flag a
Flag Bool
False,
    globalNumericVersion :: Flag Bool
globalNumericVersion = forall a. a -> Flag a
Flag Bool
False
  }

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

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

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

instance Semigroup GlobalFlags where
  <> :: 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 -> [String]
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 -> [(String, String)]
configProgramPaths  :: [(String, FilePath)], -- ^user specified programs paths
    ConfigFlags -> [(String, [String])]
configProgramArgs   :: [(String, [String])], -- ^user specified programs args
    ConfigFlags -> NubList String
configProgramPathExtra :: NubList FilePath,  -- ^Extend the $PATH
    ConfigFlags -> Flag CompilerFlavor
configHcFlavor      :: Flag CompilerFlavor, -- ^The \"flavor\" of the
                                                -- compiler, e.g. GHC.
    ConfigFlags -> Flag String
configHcPath        :: Flag FilePath, -- ^given compiler location
    ConfigFlags -> Flag String
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 -> [String]
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 String
configScratchDir    :: Flag FilePath,
    ConfigFlags -> [String]
configExtraLibDirs  :: [FilePath],   -- ^ path to search for extra libraries
    ConfigFlags -> [String]
configExtraLibDirsStatic :: [FilePath],   -- ^ path to search for extra
                                              --   libraries when linking
                                              --   fully static executables
    ConfigFlags -> [String]
configExtraFrameworkDirs :: [FilePath],   -- ^ path to search for extra
                                              -- frameworks (OS X only)
    ConfigFlags -> [String]
configExtraIncludeDirs :: [FilePath],   -- ^ path to search for header files
    ConfigFlags -> Flag String
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 String
configDistPref :: Flag FilePath, -- ^"dist" prefix
    ConfigFlags -> Flag String
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 -> [PackageVersionConstraint]
configConstraints :: [PackageVersionConstraint], -- ^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 String
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 DumpBuildInfo
configDumpBuildInfo :: Flag DumpBuildInfo,
      -- ^ Should we dump available build information on build?
      -- Dump build information to disk before attempting to build,
      -- tooling can parse these files and use them to compile the
      -- source files themselves.
    ConfigFlags -> Flag Bool
configUseResponseFiles :: Flag Bool,
      -- ^ Whether to use response files at all. They're used for such tools
      -- as haddock, 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. 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]
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 -> String -> String
[ConfigFlags] -> String -> String
ConfigFlags -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [ConfigFlags] -> String -> String
$cshowList :: [ConfigFlags] -> String -> String
show :: ConfigFlags -> String
$cshow :: ConfigFlags -> String
showsPrec :: Int -> ConfigFlags -> String -> String
$cshowsPrec :: Int -> ConfigFlags -> String -> String
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 :: WithCallStack (ConfigFlags -> ProgramDb)
configPrograms = forall a. a -> Maybe a -> a
fromMaybe (forall a. HasCallStack => String -> a
error String
"FIXME: remove configPrograms") forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap forall a. Last' a -> a
getLast'
               forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Option' a -> Maybe a
getOption' 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
    forall {b}. Eq b => (ConfigFlags -> b) -> Bool
equal ConfigFlags -> [(String, String)]
configProgramPaths
    Bool -> Bool -> Bool
&& forall {b}. Eq b => (ConfigFlags -> b) -> Bool
equal ConfigFlags -> [(String, [String])]
configProgramArgs
    Bool -> Bool -> Bool
&& forall {b}. Eq b => (ConfigFlags -> b) -> Bool
equal ConfigFlags -> NubList String
configProgramPathExtra
    Bool -> Bool -> Bool
&& forall {b}. Eq b => (ConfigFlags -> b) -> Bool
equal ConfigFlags -> Flag CompilerFlavor
configHcFlavor
    Bool -> Bool -> Bool
&& forall {b}. Eq b => (ConfigFlags -> b) -> Bool
equal ConfigFlags -> Flag String
configHcPath
    Bool -> Bool -> Bool
&& forall {b}. Eq b => (ConfigFlags -> b) -> Bool
equal ConfigFlags -> Flag String
configHcPkg
    Bool -> Bool -> Bool
&& forall {b}. Eq b => (ConfigFlags -> b) -> Bool
equal ConfigFlags -> Flag Bool
configVanillaLib
    Bool -> Bool -> Bool
&& forall {b}. Eq b => (ConfigFlags -> b) -> Bool
equal ConfigFlags -> Flag Bool
configProfLib
    Bool -> Bool -> Bool
&& forall {b}. Eq b => (ConfigFlags -> b) -> Bool
equal ConfigFlags -> Flag Bool
configSharedLib
    Bool -> Bool -> Bool
&& forall {b}. Eq b => (ConfigFlags -> b) -> Bool
equal ConfigFlags -> Flag Bool
configStaticLib
    Bool -> Bool -> Bool
&& forall {b}. Eq b => (ConfigFlags -> b) -> Bool
equal ConfigFlags -> Flag Bool
configDynExe
    Bool -> Bool -> Bool
&& forall {b}. Eq b => (ConfigFlags -> b) -> Bool
equal ConfigFlags -> Flag Bool
configFullyStaticExe
    Bool -> Bool -> Bool
&& forall {b}. Eq b => (ConfigFlags -> b) -> Bool
equal ConfigFlags -> Flag Bool
configProfExe
    Bool -> Bool -> Bool
&& forall {b}. Eq b => (ConfigFlags -> b) -> Bool
equal ConfigFlags -> Flag Bool
configProf
    Bool -> Bool -> Bool
&& forall {b}. Eq b => (ConfigFlags -> b) -> Bool
equal ConfigFlags -> Flag ProfDetailLevel
configProfDetail
    Bool -> Bool -> Bool
&& forall {b}. Eq b => (ConfigFlags -> b) -> Bool
equal ConfigFlags -> Flag ProfDetailLevel
configProfLibDetail
    Bool -> Bool -> Bool
&& forall {b}. Eq b => (ConfigFlags -> b) -> Bool
equal ConfigFlags -> [String]
configConfigureArgs
    Bool -> Bool -> Bool
&& forall {b}. Eq b => (ConfigFlags -> b) -> Bool
equal ConfigFlags -> Flag OptimisationLevel
configOptimization
    Bool -> Bool -> Bool
&& forall {b}. Eq b => (ConfigFlags -> b) -> Bool
equal ConfigFlags -> Flag PathTemplate
configProgPrefix
    Bool -> Bool -> Bool
&& forall {b}. Eq b => (ConfigFlags -> b) -> Bool
equal ConfigFlags -> Flag PathTemplate
configProgSuffix
    Bool -> Bool -> Bool
&& forall {b}. Eq b => (ConfigFlags -> b) -> Bool
equal ConfigFlags -> InstallDirs (Flag PathTemplate)
configInstallDirs
    Bool -> Bool -> Bool
&& forall {b}. Eq b => (ConfigFlags -> b) -> Bool
equal ConfigFlags -> Flag String
configScratchDir
    Bool -> Bool -> Bool
&& forall {b}. Eq b => (ConfigFlags -> b) -> Bool
equal ConfigFlags -> [String]
configExtraLibDirs
    Bool -> Bool -> Bool
&& forall {b}. Eq b => (ConfigFlags -> b) -> Bool
equal ConfigFlags -> [String]
configExtraLibDirsStatic
    Bool -> Bool -> Bool
&& forall {b}. Eq b => (ConfigFlags -> b) -> Bool
equal ConfigFlags -> [String]
configExtraIncludeDirs
    Bool -> Bool -> Bool
&& forall {b}. Eq b => (ConfigFlags -> b) -> Bool
equal ConfigFlags -> Flag String
configIPID
    Bool -> Bool -> Bool
&& forall {b}. Eq b => (ConfigFlags -> b) -> Bool
equal ConfigFlags -> Flag Bool
configDeterministic
    Bool -> Bool -> Bool
&& forall {b}. Eq b => (ConfigFlags -> b) -> Bool
equal ConfigFlags -> Flag String
configDistPref
    Bool -> Bool -> Bool
&& forall {b}. Eq b => (ConfigFlags -> b) -> Bool
equal ConfigFlags -> Flag Verbosity
configVerbosity
    Bool -> Bool -> Bool
&& forall {b}. Eq b => (ConfigFlags -> b) -> Bool
equal ConfigFlags -> Flag Bool
configUserInstall
    Bool -> Bool -> Bool
&& forall {b}. Eq b => (ConfigFlags -> b) -> Bool
equal ConfigFlags -> [Maybe PackageDB]
configPackageDBs
    Bool -> Bool -> Bool
&& forall {b}. Eq b => (ConfigFlags -> b) -> Bool
equal ConfigFlags -> Flag Bool
configGHCiLib
    Bool -> Bool -> Bool
&& forall {b}. Eq b => (ConfigFlags -> b) -> Bool
equal ConfigFlags -> Flag Bool
configSplitSections
    Bool -> Bool -> Bool
&& forall {b}. Eq b => (ConfigFlags -> b) -> Bool
equal ConfigFlags -> Flag Bool
configSplitObjs
    Bool -> Bool -> Bool
&& forall {b}. Eq b => (ConfigFlags -> b) -> Bool
equal ConfigFlags -> Flag Bool
configStripExes
    Bool -> Bool -> Bool
&& forall {b}. Eq b => (ConfigFlags -> b) -> Bool
equal ConfigFlags -> Flag Bool
configStripLibs
    Bool -> Bool -> Bool
&& forall {b}. Eq b => (ConfigFlags -> b) -> Bool
equal ConfigFlags -> [PackageVersionConstraint]
configConstraints
    Bool -> Bool -> Bool
&& forall {b}. Eq b => (ConfigFlags -> b) -> Bool
equal ConfigFlags -> [GivenComponent]
configDependencies
    Bool -> Bool -> Bool
&& forall {b}. Eq b => (ConfigFlags -> b) -> Bool
equal ConfigFlags -> FlagAssignment
configConfigurationsFlags
    Bool -> Bool -> Bool
&& forall {b}. Eq b => (ConfigFlags -> b) -> Bool
equal ConfigFlags -> Flag Bool
configTests
    Bool -> Bool -> Bool
&& forall {b}. Eq b => (ConfigFlags -> b) -> Bool
equal ConfigFlags -> Flag Bool
configBenchmarks
    Bool -> Bool -> Bool
&& forall {b}. Eq b => (ConfigFlags -> b) -> Bool
equal ConfigFlags -> Flag Bool
configCoverage
    Bool -> Bool -> Bool
&& forall {b}. Eq b => (ConfigFlags -> b) -> Bool
equal ConfigFlags -> Flag Bool
configLibCoverage
    Bool -> Bool -> Bool
&& forall {b}. Eq b => (ConfigFlags -> b) -> Bool
equal ConfigFlags -> Flag Bool
configExactConfiguration
    Bool -> Bool -> Bool
&& forall {b}. Eq b => (ConfigFlags -> b) -> Bool
equal ConfigFlags -> Flag String
configFlagError
    Bool -> Bool -> Bool
&& forall {b}. Eq b => (ConfigFlags -> b) -> Bool
equal ConfigFlags -> Flag Bool
configRelocatable
    Bool -> Bool -> Bool
&& forall {b}. Eq b => (ConfigFlags -> b) -> Bool
equal ConfigFlags -> Flag DebugInfoLevel
configDebugInfo
    Bool -> Bool -> Bool
&& forall {b}. Eq b => (ConfigFlags -> b) -> Bool
equal ConfigFlags -> Flag DumpBuildInfo
configDumpBuildInfo
    Bool -> Bool -> Bool
&& forall {b}. Eq b => (ConfigFlags -> b) -> Bool
equal ConfigFlags -> Flag Bool
configUseResponseFiles
    where
      equal :: (ConfigFlags -> b) -> Bool
equal ConfigFlags -> b
f = forall b c a. (b -> b -> c) -> (a -> b) -> a -> a -> c
on forall a. Eq a => a -> a -> Bool
(==) ConfigFlags -> b
f ConfigFlags
a ConfigFlags
b

configAbsolutePaths :: ConfigFlags -> IO ConfigFlags
configAbsolutePaths :: ConfigFlags -> IO ConfigFlags
configAbsolutePaths ConfigFlags
f =
  (\[Maybe PackageDB]
v -> ConfigFlags
f { configPackageDBs :: [Maybe PackageDB]
configPackageDBs = [Maybe PackageDB]
v })
  forall (m :: * -> *) a1 r. Monad m => (a1 -> r) -> m a1 -> m r
`liftM` forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
traverse (forall b a. b -> (a -> b) -> Maybe a -> b
maybe (forall (m :: * -> *) a. Monad m => a -> m a
return forall a. Maybe a
Nothing) (forall (m :: * -> *) a1 r. Monad m => (a1 -> r) -> m a1 -> m r
liftM forall a. a -> Maybe a
Just 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 :: [String]
configArgs         = [],
    configPrograms_ :: Option' (Last' ProgramDb)
configPrograms_    = forall a. Maybe a -> Option' a
Option' (forall a. a -> Maybe a
Just (forall a. a -> Last' a
Last' ProgramDb
progDb)),
    configHcFlavor :: Flag CompilerFlavor
configHcFlavor     = forall b a. b -> (a -> b) -> Maybe a -> b
maybe forall a. Flag a
NoFlag forall a. a -> Flag a
Flag Maybe CompilerFlavor
defaultCompilerFlavor,
    configVanillaLib :: Flag Bool
configVanillaLib   = forall a. a -> Flag a
Flag Bool
True,
    configProfLib :: Flag Bool
configProfLib      = forall a. Flag a
NoFlag,
    configSharedLib :: Flag Bool
configSharedLib    = forall a. Flag a
NoFlag,
    configStaticLib :: Flag Bool
configStaticLib    = forall a. Flag a
NoFlag,
    configDynExe :: Flag Bool
configDynExe       = forall a. a -> Flag a
Flag Bool
False,
    configFullyStaticExe :: Flag Bool
configFullyStaticExe = forall a. a -> Flag a
Flag Bool
False,
    configProfExe :: Flag Bool
configProfExe      = forall a. Flag a
NoFlag,
    configProf :: Flag Bool
configProf         = forall a. Flag a
NoFlag,
    configProfDetail :: Flag ProfDetailLevel
configProfDetail   = forall a. Flag a
NoFlag,
    configProfLibDetail :: Flag ProfDetailLevel
configProfLibDetail= forall a. Flag a
NoFlag,
    configOptimization :: Flag OptimisationLevel
configOptimization = forall a. a -> Flag a
Flag OptimisationLevel
NormalOptimisation,
    configProgPrefix :: Flag PathTemplate
configProgPrefix   = forall a. a -> Flag a
Flag (String -> PathTemplate
toPathTemplate String
""),
    configProgSuffix :: Flag PathTemplate
configProgSuffix   = forall a. a -> Flag a
Flag (String -> PathTemplate
toPathTemplate String
""),
    configDistPref :: Flag String
configDistPref     = forall a. Flag a
NoFlag,
    configCabalFilePath :: Flag String
configCabalFilePath = forall a. Flag a
NoFlag,
    configVerbosity :: Flag Verbosity
configVerbosity    = forall a. a -> Flag a
Flag Verbosity
normal,
    configUserInstall :: Flag Bool
configUserInstall  = forall a. a -> Flag a
Flag Bool
False,           --TODO: reverse this
#if defined(mingw32_HOST_OS)
    -- See #8062 and GHC #21019.
    configGHCiLib      = Flag False,
#else
    configGHCiLib :: Flag Bool
configGHCiLib      = forall a. Flag a
NoFlag,
#endif
    configSplitSections :: Flag Bool
configSplitSections = forall a. a -> Flag a
Flag Bool
False,
    configSplitObjs :: Flag Bool
configSplitObjs    = forall a. a -> Flag a
Flag Bool
False, -- takes longer, so turn off by default
    configStripExes :: Flag Bool
configStripExes    = forall a. Flag a
NoFlag,
    configStripLibs :: Flag Bool
configStripLibs    = forall a. Flag a
NoFlag,
    configTests :: Flag Bool
configTests        = forall a. a -> Flag a
Flag Bool
False,
    configBenchmarks :: Flag Bool
configBenchmarks   = forall a. a -> Flag a
Flag Bool
False,
    configCoverage :: Flag Bool
configCoverage     = forall a. a -> Flag a
Flag Bool
False,
    configLibCoverage :: Flag Bool
configLibCoverage  = forall a. Flag a
NoFlag,
    configExactConfiguration :: Flag Bool
configExactConfiguration = forall a. a -> Flag a
Flag Bool
False,
    configFlagError :: Flag String
configFlagError    = forall a. Flag a
NoFlag,
    configRelocatable :: Flag Bool
configRelocatable  = forall a. a -> Flag a
Flag Bool
False,
    configDebugInfo :: Flag DebugInfoLevel
configDebugInfo    = forall a. a -> Flag a
Flag DebugInfoLevel
NoDebugInfo,
    configDumpBuildInfo :: Flag DumpBuildInfo
configDumpBuildInfo = forall a. Flag a
NoFlag,
    configUseResponseFiles :: Flag Bool
configUseResponseFiles = forall a. Flag a
NoFlag
  }

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

-- | Inverse to 'dispModSubstEntry'.
parsecModSubstEntry :: ParsecParser (ModuleName, Module)
parsecModSubstEntry :: ParsecParser (ModuleName, Module)
parsecModSubstEntry = do
    ModuleName
k <- forall a (m :: * -> *). (Parsec a, CabalParsing m) => m a
parsec
    Char
_ <- forall (m :: * -> *). CharParsing m => Char -> m Char
P.char Char
'='
    Module
v <- forall a (m :: * -> *). (Parsec a, CabalParsing m) => m a
parsec
    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) = forall a. Pretty a => a -> Doc
pretty ModuleName
k Doc -> Doc -> Doc
<<>> Char -> Doc
Disp.char Char
'=' Doc -> Doc -> Doc
<<>> forall a. Pretty a => a -> Doc
pretty Module
v

configureOptions :: ShowOrParseArgs -> [OptionField ConfigFlags]
configureOptions :: ShowOrParseArgs -> [OptionField ConfigFlags]
configureOptions ShowOrParseArgs
showOrParseArgs =
      [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 })
      ,forall flags.
(flags -> Flag String)
-> (Flag String -> flags -> flags)
-> ShowOrParseArgs
-> OptionField flags
optionDistPref
         ConfigFlags -> Flag String
configDistPref (\Flag String
d ConfigFlags
flags -> ConfigFlags
flags { configDistPref :: Flag String
configDistPref = Flag String
d })
         ShowOrParseArgs
showOrParseArgs

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

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

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

      ,forall get set a.
String
-> [String]
-> String
-> get
-> set
-> MkOptDescr get set a
-> OptionField a
option String
"" [String
"with-hc-pkg"]
         String
"give the path to the package tool"
         ConfigFlags -> Flag String
configHcPkg (\Flag String
v ConfigFlags
flags -> ConfigFlags
flags { configHcPkg :: Flag String
configHcPkg = Flag String
v })
         (forall b.
String
-> String
-> [String]
-> String
-> (b -> Flag String)
-> (Flag String -> b -> b)
-> OptDescr b
reqArgFlag String
"PATH")
      ]
   forall a. [a] -> [a] -> [a]
++ forall a b. (a -> b) -> [a] -> [b]
map OptionField (InstallDirs (Flag PathTemplate))
-> OptionField ConfigFlags
liftInstallDirs [OptionField (InstallDirs (Flag PathTemplate))]
installDirsOptions
   forall a. [a] -> [a] -> [a]
++ [forall get set a.
String
-> [String]
-> String
-> get
-> set
-> MkOptDescr get set a
-> OptionField a
option String
"" [String
"program-prefix"]
          String
"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 })
          (forall {b}.
String
-> String
-> [String]
-> String
-> (b -> Flag PathTemplate)
-> (Flag PathTemplate -> b -> b)
-> OptDescr b
reqPathTemplateArgFlag String
"PREFIX")

      ,forall get set a.
String
-> [String]
-> String
-> get
-> set
-> MkOptDescr get set a
-> OptionField a
option String
"" [String
"program-suffix"]
          String
"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 } )
          (forall {b}.
String
-> String
-> [String]
-> String
-> (b -> Flag PathTemplate)
-> (Flag PathTemplate -> b -> b)
-> OptDescr b
reqPathTemplateArgFlag String
"SUFFIX")

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

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

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

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

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

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

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

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

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

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

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

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

      , forall get set a.
String -> get -> set -> [get -> set -> OptDescr a] -> OptionField a
multiOption String
"build-info"
         ConfigFlags -> Flag DumpBuildInfo
configDumpBuildInfo
         (\Flag DumpBuildInfo
v ConfigFlags
flags -> ConfigFlags
flags { configDumpBuildInfo :: Flag DumpBuildInfo
configDumpBuildInfo = Flag DumpBuildInfo
v })
         [forall b a. Eq b => b -> MkOptDescr (a -> b) (b -> a -> a) a
noArg (forall a. a -> Flag a
Flag DumpBuildInfo
DumpBuildInfo) []
                [String
"enable-build-info"]
                String
"Enable build information generation during project building",
          forall b a. Eq b => b -> MkOptDescr (a -> b) (b -> a -> a) a
noArg (forall a. a -> Flag a
Flag DumpBuildInfo
NoDumpBuildInfo) []
                [String
"disable-build-info"]
                String
"Disable build information generation during project building"
         ]

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

      ,forall get set a.
String
-> [String]
-> String
-> get
-> set
-> MkOptDescr get set a
-> OptionField a
option String
"" [String
"split-sections"]
         String
"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 })
         (forall a.
String
-> String -> MkOptDescr (a -> Flag Bool) (Flag Bool -> a -> a) a
boolOpt [] [])

      ,forall get set a.
String
-> [String]
-> String
-> get
-> set
-> MkOptDescr get set a
-> OptionField a
option String
"" [String
"split-objs"]
         String
"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 })
         (forall a.
String
-> String -> MkOptDescr (a -> Flag Bool) (Flag Bool -> a -> a) a
boolOpt [] [])

      ,forall get set a.
String
-> [String]
-> String
-> get
-> set
-> MkOptDescr get set a
-> OptionField a
option String
"" [String
"executable-stripping"]
         String
"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 })
         (forall a.
String
-> String -> MkOptDescr (a -> Flag Bool) (Flag Bool -> a -> a) a
boolOpt [] [])

      ,forall get set a.
String
-> [String]
-> String
-> get
-> set
-> MkOptDescr get set a
-> OptionField a
option String
"" [String
"library-stripping"]
         String
"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 })
         (forall a.
String
-> String -> MkOptDescr (a -> Flag Bool) (Flag Bool -> a -> a) a
boolOpt [] [])

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

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

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

      ,forall get set a.
String
-> [String]
-> String
-> get
-> set
-> MkOptDescr get set a
-> OptionField a
option String
"f" [String
"flags"]
         String
"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 })
         (forall b a.
Monoid b =>
String
-> ReadE b
-> (b -> [String])
-> MkOptDescr (a -> b) (b -> a -> a) a
reqArg String
"FLAGS"
              (forall a. (String -> String) -> ParsecParser a -> ReadE a
parsecToReadE (\String
err -> String
"Invalid flag assignment: " forall a. [a] -> [a] -> [a]
++ String
err) forall (m :: * -> *). CabalParsing m => m FlagAssignment
legacyParsecFlagAssignment)
              FlagAssignment -> [String]
legacyShowFlagAssignment')

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

      ,forall get set a.
String
-> [String]
-> String
-> get
-> set
-> MkOptDescr get set a
-> OptionField a
option String
"" [String
"deterministic"]
         String
"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})
         (forall a.
String
-> String -> MkOptDescr (a -> Flag Bool) (Flag Bool -> a -> a) a
boolOpt [] [])

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

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

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

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

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

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

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

      ,forall get set a.
String
-> [String]
-> String
-> get
-> set
-> MkOptDescr get set a
-> OptionField a
option String
"" [String
"dependency"]
         String
"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})
         (forall b a.
Monoid b =>
String
-> ReadE b
-> (b -> [String])
-> MkOptDescr (a -> b) (b -> a -> a) a
reqArg String
"NAME[:COMPONENT_NAME]=CID"
                 (forall a. (String -> String) -> ParsecParser a -> ReadE a
parsecToReadE (forall a b. a -> b -> a
const String
"dependency expected") ((\GivenComponent
x -> [GivenComponent
x]) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
`fmap` ParsecParser GivenComponent
parsecGivenComponent))
                 (forall a b. (a -> b) -> [a] -> [b]
map (\(GivenComponent PackageName
pn LibraryName
cn ComponentId
cid) ->
                     forall a. Pretty a => a -> String
prettyShow PackageName
pn
                     forall a. [a] -> [a] -> [a]
++ case LibraryName
cn of LibraryName
LMainLibName -> String
""
                                   LSubLibName UnqualComponentName
n -> String
":" forall a. [a] -> [a] -> [a]
++ forall a. Pretty a => a -> String
prettyShow UnqualComponentName
n
                     forall a. [a] -> [a] -> [a]
++ String
"=" forall a. [a] -> [a] -> [a]
++ forall a. Pretty a => a -> String
prettyShow ComponentId
cid)))

      ,forall get set a.
String
-> [String]
-> String
-> get
-> set
-> MkOptDescr get set a
-> OptionField a
option String
"" [String
"instantiate-with"]
        String
"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  })
        (forall b a.
Monoid b =>
String
-> ReadE b
-> (b -> [String])
-> MkOptDescr (a -> b) (b -> a -> a) a
reqArg String
"NAME=MOD"
            (forall a. (String -> String) -> ParsecParser a -> ReadE a
parsecToReadE (String
"Cannot parse module substitution: " forall a. [a] -> [a] -> [a]
++) (forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (forall a. a -> [a] -> [a]
:[]) ParsecParser (ModuleName, Module)
parsecModSubstEntry))
            (forall a b. (a -> b) -> [a] -> [b]
map (Style -> Doc -> String
Disp.renderStyle Style
defaultStyle forall b c a. (b -> c) -> (a -> b) -> a -> c
. (ModuleName, Module) -> Doc
dispModSubstEntry)))

      ,forall get set a.
String
-> [String]
-> String
-> get
-> set
-> MkOptDescr get set a
-> OptionField a
option String
"" [String
"tests"]
         String
"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 })
         (forall a.
String
-> String -> MkOptDescr (a -> Flag Bool) (Flag Bool -> a -> a) a
boolOpt [] [])

      ,forall get set a.
String
-> [String]
-> String
-> get
-> set
-> MkOptDescr get set a
-> OptionField a
option String
"" [String
"coverage"]
         String
"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 })
         (forall a.
String
-> String -> MkOptDescr (a -> Flag Bool) (Flag Bool -> a -> a) a
boolOpt [] [])

      ,forall get set a.
String
-> [String]
-> String
-> get
-> set
-> MkOptDescr get set a
-> OptionField a
option String
"" [String
"library-coverage"]
         String
"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 })
         (forall a.
String
-> String -> MkOptDescr (a -> Flag Bool) (Flag Bool -> a -> a) a
boolOpt [] [])

      ,forall get set a.
String
-> [String]
-> String
-> get
-> set
-> MkOptDescr get set a
-> OptionField a
option String
"" [String
"exact-configuration"]
         String
"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 })
         forall a. MkOptDescr (a -> Flag Bool) (Flag Bool -> a -> a) a
trueArg

      ,forall get set a.
String
-> [String]
-> String
-> get
-> set
-> MkOptDescr get set a
-> OptionField a
option String
"" [String
"benchmarks"]
         String
"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 })
         (forall a.
String
-> String -> MkOptDescr (a -> Flag Bool) (Flag Bool -> a -> a) a
boolOpt [] [])

      ,forall get set a.
String
-> [String]
-> String
-> get
-> set
-> MkOptDescr get set a
-> OptionField a
option String
"" [String
"relocatable"]
         String
"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})
         (forall a.
String
-> String -> MkOptDescr (a -> Flag Bool) (Flag Bool -> a -> a) a
boolOpt [] [])

      ,forall get set a.
String
-> [String]
-> String
-> get
-> set
-> MkOptDescr get set a
-> OptionField a
option String
"" [String
"response-files"]
         String
"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 })
         (forall a.
(String, [String])
-> (String, [String])
-> MkOptDescr (a -> Flag Bool) (Flag Bool -> a -> a) a
boolOpt' ([], [String
"disable-response-files"]) ([], []))

      ,forall get set a.
String
-> [String]
-> String
-> get
-> set
-> MkOptDescr get set a
-> OptionField a
option String
"" [String
"allow-depending-on-private-libs"]
         (  String
"Allow depending on private libraries. "
         forall a. [a] -> [a] -> [a]
++ String
"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 })
         forall a. MkOptDescr (a -> Flag Bool) (Flag Bool -> a -> a) a
trueArg
      ]
  where
    liftInstallDirs :: OptionField (InstallDirs (Flag PathTemplate))
-> OptionField ConfigFlags
liftInstallDirs =
      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 :: String
-> String
-> [String]
-> String
-> (b -> Flag PathTemplate)
-> (Flag PathTemplate -> b -> b)
-> OptDescr b
reqPathTemplateArgFlag String
title String
_sf [String]
_lf String
d b -> Flag PathTemplate
get Flag PathTemplate -> b -> b
set =
      forall b.
String
-> String
-> [String]
-> String
-> (b -> Flag String)
-> (Flag String -> b -> b)
-> OptDescr b
reqArgFlag String
title String
_sf [String]
_lf String
d
        (forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap PathTemplate -> String
fromPathTemplate forall b c a. (b -> c) -> (a -> b) -> a -> c
. b -> Flag PathTemplate
get) (Flag PathTemplate -> b -> b
set forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap String -> PathTemplate
toPathTemplate)

readPackageDbList :: String -> [Maybe PackageDB]
readPackageDbList :: String -> [Maybe PackageDB]
readPackageDbList String
str = [String -> Maybe PackageDB
readPackageDb String
str]

-- | Parse a PackageDB stack entry
--
-- @since 3.7.0.0
readPackageDb :: String -> Maybe PackageDB
readPackageDb :: String -> Maybe PackageDB
readPackageDb String
"clear"  = forall a. Maybe a
Nothing
readPackageDb String
"global" = forall a. a -> Maybe a
Just PackageDB
GlobalPackageDB
readPackageDb String
"user"   = forall a. a -> Maybe a
Just PackageDB
UserPackageDB
readPackageDb String
other    = forall a. a -> Maybe a
Just (String -> PackageDB
SpecificPackageDB String
other)

showPackageDbList :: [Maybe PackageDB] -> [String]
showPackageDbList :: [Maybe PackageDB] -> [String]
showPackageDbList = forall a b. (a -> b) -> [a] -> [b]
map Maybe PackageDB -> String
showPackageDb

-- | Show a PackageDB stack entry
--
-- @since 3.7.0.0
showPackageDb :: Maybe PackageDB -> String
showPackageDb :: Maybe PackageDB -> String
showPackageDb Maybe PackageDB
Nothing                       = String
"clear"
showPackageDb (Just PackageDB
GlobalPackageDB)        = String
"global"
showPackageDb (Just PackageDB
UserPackageDB)          = String
"user"
showPackageDb (Just (SpecificPackageDB String
db)) = String
db

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

parsecGivenComponent :: ParsecParser GivenComponent
parsecGivenComponent :: ParsecParser GivenComponent
parsecGivenComponent = do
  PackageName
pn <- forall a (m :: * -> *). (Parsec a, CabalParsing m) => m a
parsec
  LibraryName
ln <- forall (m :: * -> *) a. Alternative m => a -> m a -> m a
P.option LibraryName
LMainLibName forall a b. (a -> b) -> a -> b
$ do
    Char
_ <- forall (m :: * -> *). CharParsing m => Char -> m Char
P.char Char
':'
    UnqualComponentName
ucn <- forall a (m :: * -> *). (Parsec a, CabalParsing m) => m a
parsec
    forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ if UnqualComponentName -> String
unUnqualComponentName UnqualComponentName
ucn forall a. Eq a => a -> a -> Bool
== PackageName -> String
unPackageName PackageName
pn
             then LibraryName
LMainLibName
             else UnqualComponentName -> LibraryName
LSubLibName UnqualComponentName
ucn
  Char
_ <- forall (m :: * -> *). CharParsing m => Char -> m Char
P.char Char
'='
  ComponentId
cid <- forall a (m :: * -> *). (Parsec a, CabalParsing m) => m a
parsec
  forall (m :: * -> *) a. Monad m => a -> m a
return 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 =
  [ forall get set a.
String
-> [String]
-> String
-> get
-> set
-> MkOptDescr get set a
-> OptionField a
option String
"" [String
"prefix"]
      String
"bake this prefix in preparation of installation"
      forall dir. InstallDirs dir -> dir
prefix (\Flag PathTemplate
v InstallDirs (Flag PathTemplate)
flags -> InstallDirs (Flag PathTemplate)
flags { prefix :: Flag PathTemplate
prefix = Flag PathTemplate
v })
      forall {b}.
String
-> [String]
-> String
-> (b -> Flag PathTemplate)
-> (Flag PathTemplate -> b -> b)
-> OptDescr b
installDirArg

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

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

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

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

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

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

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

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

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

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

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

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

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

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

instance Semigroup ConfigFlags where
  <> :: 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 String
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 -> [String]
copyArgs :: [String],
    CopyFlags -> Flag String
copyCabalFilePath :: Flag FilePath
  }
  deriving (Int -> CopyFlags -> String -> String
[CopyFlags] -> String -> String
CopyFlags -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [CopyFlags] -> String -> String
$cshowList :: [CopyFlags] -> String -> String
show :: CopyFlags -> String
$cshow :: CopyFlags -> String
showsPrec :: Int -> CopyFlags -> String -> String
$cshowsPrec :: Int -> CopyFlags -> String -> String
Show, 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 {
    copyDest :: Flag CopyDest
copyDest      = forall a. a -> Flag a
Flag CopyDest
NoCopyDest,
    copyDistPref :: Flag String
copyDistPref  = forall a. Flag a
NoFlag,
    copyVerbosity :: Flag Verbosity
copyVerbosity = forall a. a -> Flag a
Flag Verbosity
normal,
    copyArgs :: [String]
copyArgs      = [],
    copyCabalFilePath :: Flag String
copyCabalFilePath = forall a. Monoid a => a
mempty
  }

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

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

  ,forall get set a.
String
-> [String]
-> String
-> get
-> set
-> MkOptDescr get set a
-> OptionField a
option String
"" [String
"destdir"]
    String
"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 String
_) -> forall a. HasCallStack => String -> a
error String
"Use either 'destdir' or 'target-package-db'."
                 Flag CopyDest
_ -> CopyFlags
flags { copyDest :: Flag CopyDest
copyDest = Flag CopyDest
v })
    (forall b a.
Monoid b =>
String
-> ReadE b
-> (b -> [String])
-> MkOptDescr (a -> b) (b -> a -> a) a
reqArg String
"DIR" (forall a. (String -> a) -> ReadE a
succeedReadE (forall a. a -> Flag a
Flag forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> CopyDest
CopyTo))
      (\Flag CopyDest
f -> case Flag CopyDest
f of Flag (CopyTo String
p) -> [String
p]; Flag CopyDest
_ -> []))

  ,forall get set a.
String
-> [String]
-> String
-> get
-> set
-> MkOptDescr get set a
-> OptionField a
option String
"" [String
"target-package-db"]
    String
"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
_ -> forall a. HasCallStack => String -> a
error String
"Use either 'destdir' or 'target-package-db'.")
    (forall b a.
Monoid b =>
String
-> ReadE b
-> (b -> [String])
-> MkOptDescr (a -> b) (b -> a -> a) a
reqArg String
"DATABASE" (forall a. (String -> a) -> ReadE a
succeedReadE (forall a. a -> Flag a
Flag forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> CopyDest
CopyToDb))
      (\Flag CopyDest
f -> case Flag CopyDest
f of Flag (CopyToDb String
p) -> [String
p]; Flag CopyDest
_ -> []))
  ]

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

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

instance Semigroup CopyFlags where
  <> :: 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 String
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 String
installCabalFilePath :: Flag FilePath
  }
  deriving (Int -> InstallFlags -> String -> String
[InstallFlags] -> String -> String
InstallFlags -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [InstallFlags] -> String -> String
$cshowList :: [InstallFlags] -> String -> String
show :: InstallFlags -> String
$cshow :: InstallFlags -> String
showsPrec :: Int -> InstallFlags -> String -> String
$cshowsPrec :: Int -> InstallFlags -> String -> String
Show, 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 {
    installPackageDB :: Flag PackageDB
installPackageDB = forall a. Flag a
NoFlag,
    installDest :: Flag CopyDest
installDest      = forall a. a -> Flag a
Flag CopyDest
NoCopyDest,
    installDistPref :: Flag String
installDistPref  = forall a. Flag a
NoFlag,
    installUseWrapper :: Flag Bool
installUseWrapper = forall a. a -> Flag a
Flag Bool
False,
    installInPlace :: Flag Bool
installInPlace    = forall a. a -> Flag a
Flag Bool
False,
    installVerbosity :: Flag Verbosity
installVerbosity = forall a. a -> Flag a
Flag Verbosity
normal,
    installCabalFilePath :: Flag String
installCabalFilePath = forall a. Monoid a => a
mempty
  }

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

  ,forall get set a.
String
-> [String]
-> String
-> get
-> set
-> MkOptDescr get set a
-> OptionField a
option String
"" [String
"inplace"]
    String
"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 })
    forall a. MkOptDescr (a -> Flag Bool) (Flag Bool -> a -> a) a
trueArg

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

  ,forall get set a.
String
-> [String]
-> String
-> get
-> set
-> MkOptDescr get set a
-> OptionField a
option String
"" [String
"package-db"] String
""
    InstallFlags -> Flag PackageDB
installPackageDB (\Flag PackageDB
v InstallFlags
flags -> InstallFlags
flags { installPackageDB :: Flag PackageDB
installPackageDB = Flag PackageDB
v })
    (forall b a.
Eq b =>
[(b, (String, [String]), String)]
-> MkOptDescr (a -> b) (b -> a -> a) a
choiceOpt [ (forall a. a -> Flag a
Flag PackageDB
UserPackageDB, ([],[String
"user"]),
                   String
"upon configuration register this package in the user's local package database")
               , (forall a. a -> Flag a
Flag PackageDB
GlobalPackageDB, ([],[String
"global"]),
                   String
"(default) upon configuration register this package in the system-wide package database")])
  ,forall get set a.
String
-> [String]
-> String
-> get
-> set
-> MkOptDescr get set a
-> OptionField a
option String
"" [String
"target-package-db"]
    String
"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 })
    (forall b a.
Monoid b =>
String
-> ReadE b
-> (b -> [String])
-> MkOptDescr (a -> b) (b -> a -> a) a
reqArg String
"DATABASE" (forall a. (String -> a) -> ReadE a
succeedReadE (forall a. a -> Flag a
Flag forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> CopyDest
CopyToDb))
      (\Flag CopyDest
f -> case Flag CopyDest
f of Flag (CopyToDb String
p) -> [String
p]; Flag CopyDest
_ -> []))
  ]

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

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

instance Semigroup InstallFlags where
  <> :: 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 String
sDistDirectory   :: Flag FilePath,
    SDistFlags -> Flag String
sDistDistPref    :: Flag FilePath,
    SDistFlags -> Flag String
sDistListSources :: Flag FilePath,
    SDistFlags -> Flag Verbosity
sDistVerbosity   :: Flag Verbosity
  }
  deriving (Int -> SDistFlags -> String -> String
[SDistFlags] -> String -> String
SDistFlags -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [SDistFlags] -> String -> String
$cshowList :: [SDistFlags] -> String -> String
show :: SDistFlags -> String
$cshow :: SDistFlags -> String
showsPrec :: Int -> SDistFlags -> String -> String
$cshowsPrec :: Int -> SDistFlags -> String -> String
Show, 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 {
    sDistSnapshot :: Flag Bool
sDistSnapshot    = forall a. a -> Flag a
Flag Bool
False,
    sDistDirectory :: Flag String
sDistDirectory   = forall a. Monoid a => a
mempty,
    sDistDistPref :: Flag String
sDistDistPref    = forall a. Flag a
NoFlag,
    sDistListSources :: Flag String
sDistListSources = forall a. Monoid a => a
mempty,
    sDistVerbosity :: Flag Verbosity
sDistVerbosity   = forall a. a -> Flag a
Flag Verbosity
normal
  }

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

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

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

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

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

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

instance Semigroup SDistFlags where
  <> :: 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 String)
regGenPkgConf  :: Flag (Maybe FilePath),
    RegisterFlags -> Flag Bool
regInPlace     :: Flag Bool,
    RegisterFlags -> Flag String
regDistPref    :: Flag FilePath,
    RegisterFlags -> Flag Bool
regPrintId     :: Flag Bool,
    RegisterFlags -> Flag Verbosity
regVerbosity   :: Flag Verbosity,
    -- Same as in 'buildArgs' and 'copyArgs'
    RegisterFlags -> [String]
regArgs        :: [String],
    RegisterFlags -> Flag String
regCabalFilePath :: Flag FilePath
  }
  deriving (Int -> RegisterFlags -> String -> String
[RegisterFlags] -> String -> String
RegisterFlags -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [RegisterFlags] -> String -> String
$cshowList :: [RegisterFlags] -> String -> String
show :: RegisterFlags -> String
$cshow :: RegisterFlags -> String
showsPrec :: Int -> RegisterFlags -> String -> String
$cshowsPrec :: Int -> RegisterFlags -> String -> String
Show, 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 {
    regPackageDB :: Flag PackageDB
regPackageDB   = forall a. Flag a
NoFlag,
    regGenScript :: Flag Bool
regGenScript   = forall a. a -> Flag a
Flag Bool
False,
    regGenPkgConf :: Flag (Maybe String)
regGenPkgConf  = forall a. Flag a
NoFlag,
    regInPlace :: Flag Bool
regInPlace     = forall a. a -> Flag a
Flag Bool
False,
    regDistPref :: Flag String
regDistPref    = forall a. Flag a
NoFlag,
    regPrintId :: Flag Bool
regPrintId     = forall a. a -> Flag a
Flag Bool
False,
    regArgs :: [String]
regArgs        = [],
    regCabalFilePath :: Flag String
regCabalFilePath = forall a. Monoid a => a
mempty,
    regVerbosity :: Flag Verbosity
regVerbosity   = forall a. a -> Flag a
Flag Verbosity
normal
  }

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

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

      ,forall get set a.
String
-> [String]
-> String
-> get
-> set
-> MkOptDescr get set a
-> OptionField a
option String
"" [String
"inplace"]
         String
"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 })
         forall a. MkOptDescr (a -> Flag Bool) (Flag Bool -> a -> a) a
trueArg

      ,forall get set a.
String
-> [String]
-> String
-> get
-> set
-> MkOptDescr get set a
-> OptionField a
option String
"" [String
"gen-script"]
         String
"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 })
         forall a. MkOptDescr (a -> Flag Bool) (Flag Bool -> a -> a) a
trueArg

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

      ,forall get set a.
String
-> [String]
-> String
-> get
-> set
-> MkOptDescr get set a
-> OptionField a
option String
"" [String
"print-ipid"]
         String
"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 })
         forall a. MkOptDescr (a -> Flag Bool) (Flag Bool -> a -> a) a
trueArg
      ]
  }

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

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

      ,forall get set a.
String
-> [String]
-> String
-> get
-> set
-> MkOptDescr get set a
-> OptionField a
option String
"" [String
"gen-script"]
         String
"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 })
         forall a. MkOptDescr (a -> Flag Bool) (Flag Bool -> a -> a) a
trueArg
      ]
  }

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

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

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

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

data HscolourFlags = HscolourFlags {
    HscolourFlags -> Flag String
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 String
hscolourDistPref    :: Flag FilePath,
    HscolourFlags -> Flag Verbosity
hscolourVerbosity   :: Flag Verbosity,
    HscolourFlags -> Flag String
hscolourCabalFilePath :: Flag FilePath
    }
  deriving (Int -> HscolourFlags -> String -> String
[HscolourFlags] -> String -> String
HscolourFlags -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [HscolourFlags] -> String -> String
$cshowList :: [HscolourFlags] -> String -> String
show :: HscolourFlags -> String
$cshow :: HscolourFlags -> String
showsPrec :: Int -> HscolourFlags -> String -> String
$cshowsPrec :: Int -> HscolourFlags -> String -> String
Show, 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 = forall a. Monoid a => a
mempty

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

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

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

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

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

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

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

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

      ,forall get set a.
String
-> [String]
-> String
-> get
-> set
-> MkOptDescr get set a
-> OptionField a
option String
"" [String
"all"]
         String
"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
                            })
         forall a. MkOptDescr (a -> Flag Bool) (Flag Bool -> a -> a) a
trueArg

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

-- ------------------------------------------------------------
-- * 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
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 -> String -> String
[HaddockTarget] -> String -> String
HaddockTarget -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [HaddockTarget] -> String -> String
$cshowList :: [HaddockTarget] -> String -> String
show :: HaddockTarget -> String
$cshow :: HaddockTarget -> String
showsPrec :: Int -> HaddockTarget -> String -> String
$cshowsPrec :: Int -> HaddockTarget -> String -> String
Show, 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     = String -> Doc
Disp.text String
"for-hackage"
    pretty HaddockTarget
ForDevelopment = String -> Doc
Disp.text String
"for-development"

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

data HaddockFlags = HaddockFlags {
    HaddockFlags -> [(String, String)]
haddockProgramPaths :: [(String, FilePath)],
    HaddockFlags -> [(String, [String])]
haddockProgramArgs  :: [(String, [String])],
    HaddockFlags -> Flag Bool
haddockHoogle       :: Flag Bool,
    HaddockFlags -> Flag Bool
haddockHtml         :: Flag Bool,
    HaddockFlags -> Flag String
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 String
haddockCss          :: Flag FilePath,
    HaddockFlags -> Flag Bool
haddockLinkedSource :: Flag Bool,
    HaddockFlags -> Flag Bool
haddockQuickJump    :: Flag Bool,
    HaddockFlags -> Flag String
haddockHscolourCss  :: Flag FilePath,
    HaddockFlags -> Flag PathTemplate
haddockContents     :: Flag PathTemplate,
    HaddockFlags -> Flag PathTemplate
haddockIndex        :: Flag PathTemplate,
    HaddockFlags -> Flag String
haddockDistPref     :: Flag FilePath,
    HaddockFlags -> Flag Bool
haddockKeepTempFiles:: Flag Bool,
    HaddockFlags -> Flag Verbosity
haddockVerbosity    :: Flag Verbosity,
    HaddockFlags -> Flag String
haddockCabalFilePath :: Flag FilePath,
    HaddockFlags -> Flag String
haddockBaseUrl      :: Flag String,
    HaddockFlags -> Flag String
haddockLib          :: Flag String,
    HaddockFlags -> [String]
haddockArgs         :: [String]
  }
  deriving (Int -> HaddockFlags -> String -> String
[HaddockFlags] -> String -> String
HaddockFlags -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [HaddockFlags] -> String -> String
$cshowList :: [HaddockFlags] -> String -> String
show :: HaddockFlags -> String
$cshow :: HaddockFlags -> String
showsPrec :: Int -> HaddockFlags -> String -> String
$cshowsPrec :: Int -> HaddockFlags -> String -> String
Show, 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 {
    haddockProgramPaths :: [(String, String)]
haddockProgramPaths = forall a. Monoid a => a
mempty,
    haddockProgramArgs :: [(String, [String])]
haddockProgramArgs  = [],
    haddockHoogle :: Flag Bool
haddockHoogle       = forall a. a -> Flag a
Flag Bool
False,
    haddockHtml :: Flag Bool
haddockHtml         = forall a. a -> Flag a
Flag Bool
False,
    haddockHtmlLocation :: Flag String
haddockHtmlLocation = forall a. Flag a
NoFlag,
    haddockForHackage :: Flag HaddockTarget
haddockForHackage   = forall a. Flag a
NoFlag,
    haddockExecutables :: Flag Bool
haddockExecutables  = forall a. a -> Flag a
Flag Bool
False,
    haddockTestSuites :: Flag Bool
haddockTestSuites   = forall a. a -> Flag a
Flag Bool
False,
    haddockBenchmarks :: Flag Bool
haddockBenchmarks   = forall a. a -> Flag a
Flag Bool
False,
    haddockForeignLibs :: Flag Bool
haddockForeignLibs  = forall a. a -> Flag a
Flag Bool
False,
    haddockInternal :: Flag Bool
haddockInternal     = forall a. a -> Flag a
Flag Bool
False,
    haddockCss :: Flag String
haddockCss          = forall a. Flag a
NoFlag,
    haddockLinkedSource :: Flag Bool
haddockLinkedSource = forall a. a -> Flag a
Flag Bool
False,
    haddockQuickJump :: Flag Bool
haddockQuickJump    = forall a. a -> Flag a
Flag Bool
False,
    haddockHscolourCss :: Flag String
haddockHscolourCss  = forall a. Flag a
NoFlag,
    haddockContents :: Flag PathTemplate
haddockContents     = forall a. Flag a
NoFlag,
    haddockDistPref :: Flag String
haddockDistPref     = forall a. Flag a
NoFlag,
    haddockKeepTempFiles :: Flag Bool
haddockKeepTempFiles= forall a. a -> Flag a
Flag Bool
False,
    haddockVerbosity :: Flag Verbosity
haddockVerbosity    = forall a. a -> Flag a
Flag Verbosity
normal,
    haddockCabalFilePath :: Flag String
haddockCabalFilePath = forall a. Monoid a => a
mempty,
    haddockIndex :: Flag PathTemplate
haddockIndex        = forall a. Flag a
NoFlag,
    haddockBaseUrl :: Flag String
haddockBaseUrl      = forall a. Flag a
NoFlag,
    haddockLib :: Flag String
haddockLib          = forall a. Flag a
NoFlag,
    haddockArgs :: [String]
haddockArgs         = forall a. Monoid a => a
mempty
  }

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

haddockOptions :: ShowOrParseArgs -> [OptionField HaddockFlags]
haddockOptions :: ShowOrParseArgs -> [OptionField HaddockFlags]
haddockOptions ShowOrParseArgs
showOrParseArgs =
  [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 })
  ,forall flags.
(flags -> Flag String)
-> (Flag String -> flags -> flags)
-> ShowOrParseArgs
-> OptionField flags
optionDistPref
   HaddockFlags -> Flag String
haddockDistPref (\Flag String
d HaddockFlags
flags -> HaddockFlags
flags { haddockDistPref :: Flag String
haddockDistPref = Flag String
d })
   ShowOrParseArgs
showOrParseArgs

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

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

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

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

  ,forall get set a.
String
-> [String]
-> String
-> get
-> set
-> MkOptDescr get set a
-> OptionField a
option String
"" [String
"for-hackage"]
   String
"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 })
   (forall b a. Eq b => b -> MkOptDescr (a -> b) (b -> a -> a) a
noArg (forall a. a -> Flag a
Flag HaddockTarget
ForHackage))

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

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

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

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

  ,forall get set a.
String
-> [String]
-> String
-> get
-> set
-> MkOptDescr get set a
-> OptionField a
option String
"" [String
"all"]
   String
"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
                            })
         forall a. MkOptDescr (a -> Flag Bool) (Flag Bool -> a -> a) a
trueArg

  ,forall get set a.
String
-> [String]
-> String
-> get
-> set
-> MkOptDescr get set a
-> OptionField a
option String
"" [String
"internal"]
   String
"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 })
   forall a. MkOptDescr (a -> Flag Bool) (Flag Bool -> a -> a) a
trueArg

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

  ,forall get set a.
String
-> [String]
-> String
-> get
-> set
-> MkOptDescr get set a
-> OptionField a
option String
"" [String
"hyperlink-source",String
"hyperlink-sources",String
"hyperlinked-source"]
   String
"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 })
   forall a. MkOptDescr (a -> Flag Bool) (Flag Bool -> a -> a) a
trueArg

  ,forall get set a.
String
-> [String]
-> String
-> get
-> set
-> MkOptDescr get set a
-> OptionField a
option String
"" [String
"quickjump"]
   String
"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 })
   forall a. MkOptDescr (a -> Flag Bool) (Flag Bool -> a -> a) a
trueArg

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

  ,forall get set a.
String
-> [String]
-> String
-> get
-> set
-> MkOptDescr get set a
-> OptionField a
option String
"" [String
"contents-location"]
   String
"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 })
   (forall b a.
Monoid b =>
String
-> (String -> b)
-> (b -> [String])
-> MkOptDescr (a -> b) (b -> a -> a) a
reqArg' String
"URL"
    (forall a. a -> Flag a
toFlag forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> PathTemplate
toPathTemplate)
    (forall a. Flag a -> [a]
flagToList forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap PathTemplate -> String
fromPathTemplate))

  ,forall get set a.
String
-> [String]
-> String
-> get
-> set
-> MkOptDescr get set a
-> OptionField a
option String
"" [String
"index-location"]
   String
"Use a separately-generated HTML index"
   HaddockFlags -> Flag PathTemplate
haddockIndex (\Flag PathTemplate
v HaddockFlags
flags -> HaddockFlags
flags { haddockIndex :: Flag PathTemplate
haddockIndex = Flag PathTemplate
v})
   (forall b a.
Monoid b =>
String
-> (String -> b)
-> (b -> [String])
-> MkOptDescr (a -> b) (b -> a -> a) a
reqArg' String
"URL"
    (forall a. a -> Flag a
toFlag forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> PathTemplate
toPathTemplate)
    (forall a. Flag a -> [a]
flagToList forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap PathTemplate -> String
fromPathTemplate))

  ,forall get set a.
String
-> [String]
-> String
-> get
-> set
-> MkOptDescr get set a
-> OptionField a
option String
"" [String
"base-url"]
   String
"Base URL for static files."
   HaddockFlags -> Flag String
haddockBaseUrl (\Flag String
v HaddockFlags
flags -> HaddockFlags
flags { haddockBaseUrl :: Flag String
haddockBaseUrl = Flag String
v})
   (forall b.
String
-> String
-> [String]
-> String
-> (b -> Flag String)
-> (Flag String -> b -> b)
-> OptDescr b
reqArgFlag String
"URL")

  ,forall get set a.
String
-> [String]
-> String
-> get
-> set
-> MkOptDescr get set a
-> OptionField a
option String
"" [String
"lib"]
   String
"location of Haddocks static / auxiliary files"
   HaddockFlags -> Flag String
haddockLib (\Flag String
v HaddockFlags
flags -> HaddockFlags
flags { haddockLib :: Flag String
haddockLib = Flag String
v})
   (forall b.
String
-> String
-> [String]
-> String
-> (b -> Flag String)
-> (Flag String -> b -> b)
-> OptDescr b
reqArgFlag String
"DIR")
  ]

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

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

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

-- ------------------------------------------------------------
-- * HaddocksFlags flags
-- ------------------------------------------------------------

-- | Governs whether modules from a given interface should be visible or
-- hidden in the Haddock generated content page.  We don't expose this
-- functionality to the user, but simply use 'Visible' for only local packages.
-- Visibility of modules is available since @haddock-2.26.1@.
--
data Visibility = Visible | Hidden
  deriving (Visibility -> Visibility -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Visibility -> Visibility -> Bool
$c/= :: Visibility -> Visibility -> Bool
== :: Visibility -> Visibility -> Bool
$c== :: Visibility -> Visibility -> Bool
Eq, Int -> Visibility -> String -> String
[Visibility] -> String -> String
Visibility -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [Visibility] -> String -> String
$cshowList :: [Visibility] -> String -> String
show :: Visibility -> String
$cshow :: Visibility -> String
showsPrec :: Int -> Visibility -> String -> String
$cshowsPrec :: Int -> Visibility -> String -> String
Show)

data HaddockProjectFlags = HaddockProjectFlags {
    HaddockProjectFlags -> Flag Bool
haddockProjectHackage      :: Flag Bool,
    -- ^ a shortcut option which builds documentation linked to hackage.  It implies:
    -- * `--html-location='https://hackage.haskell.org/package/$prg-$version/docs'
    -- * `--quickjump`
    -- * `--gen-index`
    -- * `--gen-contents`
    -- * `--hyperlinked-source`
    HaddockProjectFlags -> Flag Bool
haddockProjectLocal        :: Flag Bool,
    -- ^ a shortcut option which builds self contained directory which contains
    -- all the documentation, it implies:
    -- * `--quickjump`
    -- * `--gen-index`
    -- * `--gen-contents`
    -- * `--hyperlinked-source`
    --
    -- And it will also pass `--base-url` option to `haddock`.

    -- options passed to @haddock@ via 'createHaddockIndex'
    HaddockProjectFlags -> Flag String
haddockProjectDir          :: Flag String,
    -- ^ output directory of combined haddocks, the default is './haddocks'
    HaddockProjectFlags -> Flag String
haddockProjectPrologue     :: Flag String,
    HaddockProjectFlags -> Flag Bool
haddockProjectGenIndex     :: Flag Bool,
    HaddockProjectFlags -> Flag Bool
haddockProjectGenContents  :: Flag Bool,
    HaddockProjectFlags
-> Flag [(String, Maybe String, Maybe String, Visibility)]
haddockProjectInterfaces   :: Flag [(FilePath, Maybe FilePath, Maybe FilePath, Visibility)],
    -- ^ 'haddocksInterfaces' is inferred by the 'haddocksAction'; currently not
    -- exposed to the user.

    -- options passed to @haddock@ via 'HaddockFlags' when building
    -- documentation

    HaddockProjectFlags -> [(String, String)]
haddockProjectProgramPaths :: [(String, FilePath)],
    HaddockProjectFlags -> [(String, [String])]
haddockProjectProgramArgs  :: [(String, [String])],
    HaddockProjectFlags -> Flag Bool
haddockProjectHoogle       :: Flag Bool,
    -- haddockHtml is not supported
    HaddockProjectFlags -> Flag String
haddockProjectHtmlLocation :: Flag String,
    -- haddockForHackage is not supported
    HaddockProjectFlags -> Flag Bool
haddockProjectExecutables  :: Flag Bool,
    HaddockProjectFlags -> Flag Bool
haddockProjectTestSuites   :: Flag Bool,
    HaddockProjectFlags -> Flag Bool
haddockProjectBenchmarks   :: Flag Bool,
    HaddockProjectFlags -> Flag Bool
haddockProjectForeignLibs  :: Flag Bool,
    HaddockProjectFlags -> Flag Bool
haddockProjectInternal     :: Flag Bool,
    HaddockProjectFlags -> Flag String
haddockProjectCss          :: Flag FilePath,
    HaddockProjectFlags -> Flag Bool
haddockProjectLinkedSource :: Flag Bool,
    HaddockProjectFlags -> Flag Bool
haddockProjectQuickJump    :: Flag Bool,
    HaddockProjectFlags -> Flag String
haddockProjectHscolourCss  :: Flag FilePath,
    -- haddockContent is not supported, a fixed value is provided
    -- haddockIndex is not supported, a fixed value is provided
    -- haddockDistPerf is not supported, note: it changes location of the haddocks
    HaddockProjectFlags -> Flag Bool
haddockProjectKeepTempFiles:: Flag Bool,
    HaddockProjectFlags -> Flag Verbosity
haddockProjectVerbosity    :: Flag Verbosity,
    -- haddockBaseUrl is not supported, a fixed value is provided
    HaddockProjectFlags -> Flag String
haddockProjectLib          :: Flag String
  }
  deriving (Int -> HaddockProjectFlags -> String -> String
[HaddockProjectFlags] -> String -> String
HaddockProjectFlags -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [HaddockProjectFlags] -> String -> String
$cshowList :: [HaddockProjectFlags] -> String -> String
show :: HaddockProjectFlags -> String
$cshow :: HaddockProjectFlags -> String
showsPrec :: Int -> HaddockProjectFlags -> String -> String
$cshowsPrec :: Int -> HaddockProjectFlags -> String -> String
Show, forall x. Rep HaddockProjectFlags x -> HaddockProjectFlags
forall x. HaddockProjectFlags -> Rep HaddockProjectFlags x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep HaddockProjectFlags x -> HaddockProjectFlags
$cfrom :: forall x. HaddockProjectFlags -> Rep HaddockProjectFlags x
Generic, Typeable)

defaultHaddockProjectFlags :: HaddockProjectFlags
defaultHaddockProjectFlags :: HaddockProjectFlags
defaultHaddockProjectFlags = HaddockProjectFlags {
    haddockProjectHackage :: Flag Bool
haddockProjectHackage      = forall a. a -> Flag a
Flag Bool
False,
    haddockProjectLocal :: Flag Bool
haddockProjectLocal        = forall a. a -> Flag a
Flag Bool
False,
    haddockProjectDir :: Flag String
haddockProjectDir          = forall a. a -> Flag a
Flag String
"./haddocks",
    haddockProjectPrologue :: Flag String
haddockProjectPrologue     = forall a. Flag a
NoFlag,
    haddockProjectGenIndex :: Flag Bool
haddockProjectGenIndex     = forall a. a -> Flag a
Flag Bool
False,
    haddockProjectGenContents :: Flag Bool
haddockProjectGenContents  = forall a. a -> Flag a
Flag Bool
False,
    haddockProjectTestSuites :: Flag Bool
haddockProjectTestSuites   = forall a. a -> Flag a
Flag Bool
False,
    haddockProjectProgramPaths :: [(String, String)]
haddockProjectProgramPaths = forall a. Monoid a => a
mempty,
    haddockProjectProgramArgs :: [(String, [String])]
haddockProjectProgramArgs  = forall a. Monoid a => a
mempty,
    haddockProjectHoogle :: Flag Bool
haddockProjectHoogle       = forall a. a -> Flag a
Flag Bool
False,
    haddockProjectHtmlLocation :: Flag String
haddockProjectHtmlLocation = forall a. Flag a
NoFlag,
    haddockProjectExecutables :: Flag Bool
haddockProjectExecutables  = forall a. a -> Flag a
Flag Bool
False,
    haddockProjectBenchmarks :: Flag Bool
haddockProjectBenchmarks   = forall a. a -> Flag a
Flag Bool
False,
    haddockProjectForeignLibs :: Flag Bool
haddockProjectForeignLibs  = forall a. a -> Flag a
Flag Bool
False,
    haddockProjectInternal :: Flag Bool
haddockProjectInternal     = forall a. a -> Flag a
Flag Bool
False,
    haddockProjectCss :: Flag String
haddockProjectCss          = forall a. Flag a
NoFlag,
    haddockProjectLinkedSource :: Flag Bool
haddockProjectLinkedSource = forall a. a -> Flag a
Flag Bool
False,
    haddockProjectQuickJump :: Flag Bool
haddockProjectQuickJump    = forall a. a -> Flag a
Flag Bool
False,
    haddockProjectHscolourCss :: Flag String
haddockProjectHscolourCss  = forall a. Flag a
NoFlag,
    haddockProjectKeepTempFiles :: Flag Bool
haddockProjectKeepTempFiles= forall a. a -> Flag a
Flag Bool
False,
    haddockProjectVerbosity :: Flag Verbosity
haddockProjectVerbosity    = forall a. a -> Flag a
Flag Verbosity
normal,
    haddockProjectLib :: Flag String
haddockProjectLib          = forall a. Flag a
NoFlag,
    haddockProjectInterfaces :: Flag [(String, Maybe String, Maybe String, Visibility)]
haddockProjectInterfaces   = forall a. Flag a
NoFlag
  }

haddockProjectCommand :: CommandUI HaddockProjectFlags
haddockProjectCommand :: CommandUI HaddockProjectFlags
haddockProjectCommand = CommandUI
  { commandName :: String
commandName        = String
"v2-haddock-project"
  , commandSynopsis :: String
commandSynopsis    = String
"Generate Haddocks HTML documentation for the cabal project."
  , commandDescription :: Maybe (String -> String)
commandDescription = forall a. a -> Maybe a
Just forall a b. (a -> b) -> a -> b
$ \String
_ ->
      String
"Require the programm haddock, version 2.26.\n"
  , commandNotes :: Maybe (String -> String)
commandNotes       = forall a. Maybe a
Nothing
  , commandUsage :: String -> String
commandUsage       = String -> [String] -> String -> String
usageAlternatives String
"haddocks" forall a b. (a -> b) -> a -> b
$
      [ String
"[FLAGS]"
      , String
"COMPONENTS [FLAGS]"
      ]
  , commandDefaultFlags :: HaddockProjectFlags
commandDefaultFlags = HaddockProjectFlags
defaultHaddockProjectFlags
  , commandOptions :: ShowOrParseArgs -> [OptionField HaddockProjectFlags]
commandOptions      = \ShowOrParseArgs
showOrParseArgs ->
         ShowOrParseArgs -> [OptionField HaddockProjectFlags]
haddockProjectOptions ShowOrParseArgs
showOrParseArgs
      forall a. [a] -> [a] -> [a]
++ forall flags.
ProgramDb
-> ShowOrParseArgs
-> (flags -> [(String, String)])
-> ([(String, String)] -> flags -> flags)
-> [OptionField flags]
programDbPaths   ProgramDb
progDb ShowOrParseArgs
ParseArgs
             HaddockProjectFlags -> [(String, String)]
haddockProjectProgramPaths (\[(String, String)]
v HaddockProjectFlags
flags -> HaddockProjectFlags
flags { haddockProjectProgramPaths :: [(String, String)]
haddockProjectProgramPaths = [(String, String)]
v})
      forall a. [a] -> [a] -> [a]
++ forall flags.
ProgramDb
-> ShowOrParseArgs
-> (flags -> [(String, [String])])
-> ([(String, [String])] -> flags -> flags)
-> [OptionField flags]
programDbOption  ProgramDb
progDb ShowOrParseArgs
showOrParseArgs
             HaddockProjectFlags -> [(String, [String])]
haddockProjectProgramArgs (\[(String, [String])]
v HaddockProjectFlags
fs -> HaddockProjectFlags
fs { haddockProjectProgramArgs :: [(String, [String])]
haddockProjectProgramArgs = [(String, [String])]
v })
      forall a. [a] -> [a] -> [a]
++ forall flags.
ProgramDb
-> ShowOrParseArgs
-> (flags -> [(String, [String])])
-> ([(String, [String])] -> flags -> flags)
-> [OptionField flags]
programDbOptions ProgramDb
progDb ShowOrParseArgs
ParseArgs
             HaddockProjectFlags -> [(String, [String])]
haddockProjectProgramArgs  (\[(String, [String])]
v HaddockProjectFlags
flags -> HaddockProjectFlags
flags { haddockProjectProgramArgs :: [(String, [String])]
haddockProjectProgramArgs = [(String, [String])]
v})
  }
  where
    progDb :: ProgramDb
progDb = Program -> ProgramDb -> ProgramDb
addKnownProgram Program
haddockProgram
             forall a b. (a -> b) -> a -> b
$ Program -> ProgramDb -> ProgramDb
addKnownProgram Program
ghcProgram
             forall a b. (a -> b) -> a -> b
$ ProgramDb
emptyProgramDb

haddockProjectOptions :: ShowOrParseArgs -> [OptionField HaddockProjectFlags]
haddockProjectOptions :: ShowOrParseArgs -> [OptionField HaddockProjectFlags]
haddockProjectOptions ShowOrParseArgs
_showOrParseArgs =
    [forall get set a.
String
-> [String]
-> String
-> get
-> set
-> MkOptDescr get set a
-> OptionField a
option String
"" [String
"hackage"]
     (forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat [String
"A short-cut option to build documentation linked to hackage; "
             ,String
"it implies --quickjump, --gen-index, --gen-contents, "
             ,String
"--hyperlinked-source and --html-location"
             ])
     HaddockProjectFlags -> Flag Bool
haddockProjectHackage (\Flag Bool
v HaddockProjectFlags
flags -> HaddockProjectFlags
flags { haddockProjectHackage :: Flag Bool
haddockProjectHackage = Flag Bool
v })
     forall a. MkOptDescr (a -> Flag Bool) (Flag Bool -> a -> a) a
trueArg

    ,forall get set a.
String
-> [String]
-> String
-> get
-> set
-> MkOptDescr get set a
-> OptionField a
option String
"" [String
"local"]
     (forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat [String
"A short-cut option to build self contained documentation; "
             ,String
"it implies  --quickjump, --gen-index, --gen-contents "
             ,String
"and --hyperlinked-source."
             ])
     HaddockProjectFlags -> Flag Bool
haddockProjectLocal (\Flag Bool
v HaddockProjectFlags
flags -> HaddockProjectFlags
flags { haddockProjectLocal :: Flag Bool
haddockProjectLocal = Flag Bool
v })
     forall a. MkOptDescr (a -> Flag Bool) (Flag Bool -> a -> a) a
trueArg

    ,forall get set a.
String
-> [String]
-> String
-> get
-> set
-> MkOptDescr get set a
-> OptionField a
option String
"" [String
"output"]
      String
"Output directory"
      HaddockProjectFlags -> Flag String
haddockProjectDir (\Flag String
v HaddockProjectFlags
flags -> HaddockProjectFlags
flags { haddockProjectDir :: Flag String
haddockProjectDir = Flag String
v })
      (forall b a.
Monoid b =>
String
-> (Maybe String -> b)
-> (b -> [Maybe String])
-> MkOptDescr (a -> b) (b -> a -> a) a
optArg' String
"DIRECTORY" forall a. Maybe a -> Flag a
maybeToFlag (forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap forall a. a -> Maybe a
Just forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Flag a -> [a]
flagToList))

    ,forall get set a.
String
-> [String]
-> String
-> get
-> set
-> MkOptDescr get set a
-> OptionField a
option String
"" [String
"prologue"]
     String
"File path to a prologue file in haddock format"
     HaddockProjectFlags -> Flag String
haddockProjectPrologue (\Flag String
v HaddockProjectFlags
flags -> HaddockProjectFlags
flags { haddockProjectPrologue :: Flag String
haddockProjectPrologue = Flag String
v})
     (forall b a.
Monoid b =>
String
-> (Maybe String -> b)
-> (b -> [Maybe String])
-> MkOptDescr (a -> b) (b -> a -> a) a
optArg' String
"PATH" forall a. Maybe a -> Flag a
maybeToFlag (forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap forall a. a -> Maybe a
Just forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Flag a -> [a]
flagToList))

    ,forall get set a.
String
-> [String]
-> String
-> get
-> set
-> MkOptDescr get set a
-> OptionField a
option String
"" [String
"gen-index"]
     String
"Generate index"
     HaddockProjectFlags -> Flag Bool
haddockProjectGenIndex (\Flag Bool
v HaddockProjectFlags
flags -> HaddockProjectFlags
flags { haddockProjectGenIndex :: Flag Bool
haddockProjectGenIndex = Flag Bool
v})
     forall a. MkOptDescr (a -> Flag Bool) (Flag Bool -> a -> a) a
trueArg

    ,forall get set a.
String
-> [String]
-> String
-> get
-> set
-> MkOptDescr get set a
-> OptionField a
option String
"" [String
"gen-contents"]
     String
"Generate contents"
     HaddockProjectFlags -> Flag Bool
haddockProjectGenContents (\Flag Bool
v HaddockProjectFlags
flags -> HaddockProjectFlags
flags { haddockProjectGenContents :: Flag Bool
haddockProjectGenContents = Flag Bool
v})
     forall a. MkOptDescr (a -> Flag Bool) (Flag Bool -> a -> a) a
trueArg

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

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

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

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

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

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

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

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

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

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

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

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

    ,forall flags.
(flags -> Flag Verbosity)
-> (Flag Verbosity -> flags -> flags) -> OptionField flags
optionVerbosity HaddockProjectFlags -> Flag Verbosity
haddockProjectVerbosity
     (\Flag Verbosity
v HaddockProjectFlags
flags -> HaddockProjectFlags
flags { haddockProjectVerbosity :: Flag Verbosity
haddockProjectVerbosity = Flag Verbosity
v })

    ,forall get set a.
String
-> [String]
-> String
-> get
-> set
-> MkOptDescr get set a
-> OptionField a
option String
"" [String
"lib"]
     String
"location of Haddocks static / auxiliary files"
     HaddockProjectFlags -> Flag String
haddockProjectLib (\Flag String
v HaddockProjectFlags
flags -> HaddockProjectFlags
flags { haddockProjectLib :: Flag String
haddockProjectLib = Flag String
v})
     (forall b.
String
-> String
-> [String]
-> String
-> (b -> Flag String)
-> (Flag String -> b -> b)
-> OptDescr b
reqArgFlag String
"DIR")
    ]


emptyHaddockProjectFlags :: HaddockProjectFlags
emptyHaddockProjectFlags :: HaddockProjectFlags
emptyHaddockProjectFlags = forall a. Monoid a => a
mempty

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

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

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

data CleanFlags = CleanFlags {
    CleanFlags -> Flag Bool
cleanSaveConf  :: Flag Bool,
    CleanFlags -> Flag String
cleanDistPref  :: Flag FilePath,
    CleanFlags -> Flag Verbosity
cleanVerbosity :: Flag Verbosity,
    CleanFlags -> Flag String
cleanCabalFilePath :: Flag FilePath
  }
  deriving (Int -> CleanFlags -> String -> String
[CleanFlags] -> String -> String
CleanFlags -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [CleanFlags] -> String -> String
$cshowList :: [CleanFlags] -> String -> String
show :: CleanFlags -> String
$cshow :: CleanFlags -> String
showsPrec :: Int -> CleanFlags -> String -> String
$cshowsPrec :: Int -> CleanFlags -> String -> String
Show, 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 {
    cleanSaveConf :: Flag Bool
cleanSaveConf  = forall a. a -> Flag a
Flag Bool
False,
    cleanDistPref :: Flag String
cleanDistPref  = forall a. Flag a
NoFlag,
    cleanVerbosity :: Flag Verbosity
cleanVerbosity = forall a. a -> Flag a
Flag Verbosity
normal,
    cleanCabalFilePath :: Flag String
cleanCabalFilePath = forall a. Monoid a => a
mempty
  }

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

      ,forall get set a.
String
-> [String]
-> String
-> get
-> set
-> MkOptDescr get set a
-> OptionField a
option String
"s" [String
"save-configure"]
         String
"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 })
         forall a. MkOptDescr (a -> Flag Bool) (Flag Bool -> a -> a) a
trueArg
      ]
  }

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

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

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

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

data BuildFlags = BuildFlags {
    BuildFlags -> [(String, String)]
buildProgramPaths :: [(String, FilePath)],
    BuildFlags -> [(String, [String])]
buildProgramArgs :: [(String, [String])],
    BuildFlags -> Flag String
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 -> [String]
buildArgs :: [String],
    BuildFlags -> Flag String
buildCabalFilePath :: Flag FilePath
  }
  deriving (ReadPrec [BuildFlags]
ReadPrec BuildFlags
Int -> ReadS BuildFlags
ReadS [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 -> String -> String
[BuildFlags] -> String -> String
BuildFlags -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [BuildFlags] -> String -> String
$cshowList :: [BuildFlags] -> String -> String
show :: BuildFlags -> String
$cshow :: BuildFlags -> String
showsPrec :: Int -> BuildFlags -> String -> String
$cshowsPrec :: Int -> BuildFlags -> String -> String
Show, 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 {
    buildProgramPaths :: [(String, String)]
buildProgramPaths = forall a. Monoid a => a
mempty,
    buildProgramArgs :: [(String, [String])]
buildProgramArgs = [],
    buildDistPref :: Flag String
buildDistPref    = forall a. Monoid a => a
mempty,
    buildVerbosity :: Flag Verbosity
buildVerbosity   = forall a. a -> Flag a
Flag Verbosity
normal,
    buildNumJobs :: Flag (Maybe Int)
buildNumJobs     = forall a. Monoid a => a
mempty,
    buildArgs :: [String]
buildArgs        = [],
    buildCabalFilePath :: Flag String
buildCabalFilePath = forall a. Monoid a => a
mempty
  }

buildCommand :: ProgramDb -> CommandUI BuildFlags
buildCommand :: ProgramDb -> CommandUI BuildFlags
buildCommand ProgramDb
progDb = CommandUI
  { commandName :: String
commandName         = String
"build"
  , commandSynopsis :: String
commandSynopsis     = String
"Compile all/specific components."
  , commandDescription :: Maybe (String -> String)
commandDescription  = forall a. a -> Maybe a
Just forall a b. (a -> b) -> a -> b
$ \String
_ -> String -> String
wrapText forall a b. (a -> b) -> a -> b
$
         String
"Components encompass executables, tests, and benchmarks.\n"
      forall a. [a] -> [a] -> [a]
++ String
"\n"
      forall a. [a] -> [a] -> [a]
++ String
"Affected by configuration options, see `configure`.\n"
  , commandNotes :: Maybe (String -> String)
commandNotes        = forall a. a -> Maybe a
Just forall a b. (a -> b) -> a -> b
$ \String
pname ->
       String
"Examples:\n"
        forall a. [a] -> [a] -> [a]
++ String
"  " forall a. [a] -> [a] -> [a]
++ String
pname forall a. [a] -> [a] -> [a]
++ String
" build           "
        forall a. [a] -> [a] -> [a]
++ String
"    All the components in the package\n"
        forall a. [a] -> [a] -> [a]
++ String
"  " forall a. [a] -> [a] -> [a]
++ String
pname forall a. [a] -> [a] -> [a]
++ String
" build foo       "
        forall a. [a] -> [a] -> [a]
++ String
"    A component (i.e. lib, exe, test suite)\n\n"
        forall a. [a] -> [a] -> [a]
++ ProgramDb -> String
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 :: String -> String
commandUsage        = String -> [String] -> String -> String
usageAlternatives String
"build" forall a b. (a -> b) -> a -> b
$
      [ String
"[FLAGS]"
      , String
"COMPONENTS [FLAGS]"
      ]
  , commandDefaultFlags :: BuildFlags
commandDefaultFlags = BuildFlags
defaultBuildFlags
  , commandOptions :: ShowOrParseArgs -> [OptionField BuildFlags]
commandOptions      = \ShowOrParseArgs
showOrParseArgs ->
      [ 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 })

      , forall flags.
(flags -> Flag String)
-> (Flag String -> flags -> flags)
-> ShowOrParseArgs
-> OptionField flags
optionDistPref
        BuildFlags -> Flag String
buildDistPref (\Flag String
d BuildFlags
flags -> BuildFlags
flags { buildDistPref :: Flag String
buildDistPref = Flag String
d }) ShowOrParseArgs
showOrParseArgs
      ]
      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 =
  [ 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 })
  ]

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

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

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

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

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

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

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

data ReplOptions = ReplOptions {
    ReplOptions -> [String]
replOptionsFlags :: [String],
    ReplOptions -> Flag Bool
replOptionsNoLoad :: Flag Bool
  }
  deriving (Int -> ReplOptions -> String -> String
[ReplOptions] -> String -> String
ReplOptions -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [ReplOptions] -> String -> String
$cshowList :: [ReplOptions] -> String -> String
show :: ReplOptions -> String
$cshow :: ReplOptions -> String
showsPrec :: Int -> ReplOptions -> String -> String
$cshowsPrec :: Int -> ReplOptions -> String -> String
Show, forall x. Rep ReplOptions x -> ReplOptions
forall x. ReplOptions -> Rep ReplOptions x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ReplOptions x -> ReplOptions
$cfrom :: forall x. ReplOptions -> Rep ReplOptions x
Generic, Typeable)

instance Binary ReplOptions
instance Structured ReplOptions


instance Monoid ReplOptions where
  mempty :: ReplOptions
mempty = [String] -> Flag Bool -> ReplOptions
ReplOptions forall a. Monoid a => a
mempty (forall a. a -> Flag a
Flag Bool
False)
  mappend :: ReplOptions -> ReplOptions -> ReplOptions
mappend = forall a. Semigroup a => a -> a -> a
(<>)

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

data ReplFlags = ReplFlags {
    ReplFlags -> [(String, String)]
replProgramPaths :: [(String, FilePath)],
    ReplFlags -> [(String, [String])]
replProgramArgs :: [(String, [String])],
    ReplFlags -> Flag String
replDistPref    :: Flag FilePath,
    ReplFlags -> Flag Verbosity
replVerbosity   :: Flag Verbosity,
    ReplFlags -> Flag Bool
replReload      :: Flag Bool,
    ReplFlags -> ReplOptions
replReplOptions :: ReplOptions
  }
  deriving (Int -> ReplFlags -> String -> String
[ReplFlags] -> String -> String
ReplFlags -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [ReplFlags] -> String -> String
$cshowList :: [ReplFlags] -> String -> String
show :: ReplFlags -> String
$cshow :: ReplFlags -> String
showsPrec :: Int -> ReplFlags -> String -> String
$cshowsPrec :: Int -> ReplFlags -> String -> String
Show, 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 {
    replProgramPaths :: [(String, String)]
replProgramPaths = forall a. Monoid a => a
mempty,
    replProgramArgs :: [(String, [String])]
replProgramArgs = [],
    replDistPref :: Flag String
replDistPref    = forall a. Flag a
NoFlag,
    replVerbosity :: Flag Verbosity
replVerbosity   = forall a. a -> Flag a
Flag Verbosity
normal,
    replReload :: Flag Bool
replReload      = forall a. a -> Flag a
Flag Bool
False,
    replReplOptions :: ReplOptions
replReplOptions = forall a. Monoid a => a
mempty
  }

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

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

  , commandNotes :: Maybe (String -> String)
commandNotes        = forall a. a -> Maybe a
Just forall a b. (a -> b) -> a -> b
$ \String
pname ->
         String
"Examples:\n"
      forall a. [a] -> [a] -> [a]
++ String
"  " forall a. [a] -> [a] -> [a]
++ String
pname forall a. [a] -> [a] -> [a]
++ String
" repl           "
      forall a. [a] -> [a] -> [a]
++ String
"    The first component in the package\n"
      forall a. [a] -> [a] -> [a]
++ String
"  " forall a. [a] -> [a] -> [a]
++ String
pname forall a. [a] -> [a] -> [a]
++ String
" repl foo       "
      forall a. [a] -> [a] -> [a]
++ String
"    A named component (i.e. lib, exe, test suite)\n"
      forall a. [a] -> [a] -> [a]
++ String
"  " forall a. [a] -> [a] -> [a]
++ String
pname forall a. [a] -> [a] -> [a]
++ String
" repl --repl-options=\"-lstdc++\""
      forall a. [a] -> [a] -> [a]
++ String
"  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 :: String -> String
commandUsage =  \String
pname -> String
"Usage: " forall a. [a] -> [a] -> [a]
++ String
pname forall a. [a] -> [a] -> [a]
++ String
" repl [COMPONENT] [FLAGS]\n"
  , commandDefaultFlags :: ReplFlags
commandDefaultFlags = ReplFlags
defaultReplFlags
  , commandOptions :: ShowOrParseArgs -> [OptionField ReplFlags]
commandOptions = \ShowOrParseArgs
showOrParseArgs ->
      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 })
      forall a. a -> [a] -> [a]
: forall flags.
(flags -> Flag String)
-> (Flag String -> flags -> flags)
-> ShowOrParseArgs
-> OptionField flags
optionDistPref
          ReplFlags -> Flag String
replDistPref (\Flag String
d ReplFlags
flags -> ReplFlags
flags { replDistPref :: Flag String
replDistPref = Flag String
d })
          ShowOrParseArgs
showOrParseArgs

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

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

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

     forall a. [a] -> [a] -> [a]
++ case ShowOrParseArgs
showOrParseArgs of
          ShowOrParseArgs
ParseArgs ->
            [ forall get set a.
String
-> [String]
-> String
-> get
-> set
-> MkOptDescr get set a
-> OptionField a
option String
"" [String
"reload"]
              String
"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 })
              forall a. MkOptDescr (a -> Flag Bool) (Flag Bool -> a -> a) a
trueArg
            ]
          ShowOrParseArgs
_ -> []
     forall a. [a] -> [a] -> [a]
++ forall a b. (a -> b) -> [a] -> [b]
map OptionField ReplOptions -> OptionField ReplFlags
liftReplOption (ShowOrParseArgs -> [OptionField ReplOptions]
replOptions ShowOrParseArgs
showOrParseArgs)
  }
  where
    liftReplOption :: OptionField ReplOptions -> OptionField ReplFlags
liftReplOption = forall b a.
(b -> a) -> (a -> b -> b) -> OptionField a -> OptionField b
liftOption ReplFlags -> ReplOptions
replReplOptions (\ReplOptions
v ReplFlags
flags -> ReplFlags
flags { replReplOptions :: ReplOptions
replReplOptions = ReplOptions
v })

replOptions :: ShowOrParseArgs -> [OptionField ReplOptions]
replOptions :: ShowOrParseArgs -> [OptionField ReplOptions]
replOptions ShowOrParseArgs
_ =
  [ forall get set a.
String
-> [String]
-> String
-> get
-> set
-> MkOptDescr get set a
-> OptionField a
option [] [String
"repl-no-load"]
    String
"Disable loading of project modules at REPL startup."
    ReplOptions -> Flag Bool
replOptionsNoLoad (\Flag Bool
p ReplOptions
flags -> ReplOptions
flags { replOptionsNoLoad :: Flag Bool
replOptionsNoLoad = Flag Bool
p })
    forall a. MkOptDescr (a -> Flag Bool) (Flag Bool -> a -> a) a
trueArg
  , forall get set a.
String
-> [String]
-> String
-> get
-> set
-> MkOptDescr get set a
-> OptionField a
option [] [String
"repl-options"]
    String
"Use the option(s) for the repl"
    ReplOptions -> [String]
replOptionsFlags (\[String]
p ReplOptions
flags -> ReplOptions
flags { replOptionsFlags :: [String]
replOptionsFlags = [String]
p })
    (forall b a.
Monoid b =>
String
-> ReadE b
-> (b -> [String])
-> MkOptDescr (a -> b) (b -> a -> a) a
reqArg String
"FLAG" (forall a. (String -> a) -> ReadE a
succeedReadE String -> [String]
words) forall a. a -> a
id)
  ]

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

data TestShowDetails = Never | Failures | Always | Streaming | Direct
    deriving (TestShowDetails -> TestShowDetails -> Bool
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
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
Ord, Int -> TestShowDetails
TestShowDetails -> Int
TestShowDetails -> [TestShowDetails]
TestShowDetails -> TestShowDetails
TestShowDetails -> TestShowDetails -> [TestShowDetails]
TestShowDetails
-> TestShowDetails -> TestShowDetails -> [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
forall a. a -> a -> Bounded a
maxBound :: TestShowDetails
$cmaxBound :: TestShowDetails
minBound :: TestShowDetails
$cminBound :: TestShowDetails
Bounded, 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 -> String -> String
[TestShowDetails] -> String -> String
TestShowDetails -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [TestShowDetails] -> String -> String
$cshowList :: [TestShowDetails] -> String -> String
show :: TestShowDetails -> String
$cshow :: TestShowDetails -> String
showsPrec :: Int -> TestShowDetails -> String -> String
$cshowsPrec :: Int -> TestShowDetails -> String -> String
Show, Typeable)

instance Binary TestShowDetails
instance Structured TestShowDetails

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

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

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

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

data TestFlags = TestFlags {
    TestFlags -> Flag String
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 String
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 (Int -> TestFlags -> String -> String
[TestFlags] -> String -> String
TestFlags -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [TestFlags] -> String -> String
$cshowList :: [TestFlags] -> String -> String
show :: TestFlags -> String
$cshow :: TestFlags -> String
showsPrec :: Int -> TestFlags -> String -> String
$cshowsPrec :: Int -> TestFlags -> String -> String
Show, 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 {
    testDistPref :: Flag String
testDistPref    = forall a. Flag a
NoFlag,
    testVerbosity :: Flag Verbosity
testVerbosity   = forall a. a -> Flag a
Flag Verbosity
normal,
    testHumanLog :: Flag PathTemplate
testHumanLog    = forall a. a -> Flag a
toFlag forall a b. (a -> b) -> a -> b
$ String -> PathTemplate
toPathTemplate forall a b. (a -> b) -> a -> b
$ String
"$pkgid-$test-suite.log",
    testMachineLog :: Flag PathTemplate
testMachineLog  = forall a. a -> Flag a
toFlag forall a b. (a -> b) -> a -> b
$ String -> PathTemplate
toPathTemplate forall a b. (a -> b) -> a -> b
$ String
"$pkgid.log",
    testShowDetails :: Flag TestShowDetails
testShowDetails = forall a. a -> Flag a
toFlag TestShowDetails
Failures,
    testKeepTix :: Flag Bool
testKeepTix     = forall a. a -> Flag a
toFlag Bool
False,
    testWrapper :: Flag String
testWrapper     = forall a. Flag a
NoFlag,
    testFailWhenNoTestSuites :: Flag Bool
testFailWhenNoTestSuites = forall a. a -> Flag a
toFlag Bool
False,
    testOptions :: [PathTemplate]
testOptions     = []
  }

testCommand :: CommandUI TestFlags
testCommand :: CommandUI TestFlags
testCommand = CommandUI
  { commandName :: String
commandName         = String
"test"
  , commandSynopsis :: String
commandSynopsis     =
      String
"Run all/specific tests in the test suite."
  , commandDescription :: Maybe (String -> String)
commandDescription  = forall a. a -> Maybe a
Just forall a b. (a -> b) -> a -> b
$ \ String
_pname -> String -> String
wrapText forall a b. (a -> b) -> a -> b
$
      String -> String
testOrBenchmarkHelpText String
"test"
  , commandNotes :: Maybe (String -> String)
commandNotes        = forall a. Maybe a
Nothing
  , commandUsage :: String -> String
commandUsage        = String -> [String] -> String -> String
usageAlternatives String
"test"
      [ String
"[FLAGS]"
      , String
"TESTCOMPONENTS [FLAGS]"
      ]
  , commandDefaultFlags :: TestFlags
commandDefaultFlags = TestFlags
defaultTestFlags
  , commandOptions :: ShowOrParseArgs -> [OptionField TestFlags]
commandOptions = ShowOrParseArgs -> [OptionField TestFlags]
testOptions'
  }

-- | Help text for @test@ and @bench@ commands.
testOrBenchmarkHelpText
  :: String   -- ^ Either @"test"@ or @"benchmark"@.
  -> String   -- ^ Help text.
testOrBenchmarkHelpText :: String -> String
testOrBenchmarkHelpText String
s = [String] -> String
unlines forall a b. (a -> b) -> a -> b
$ forall a b. (a -> b) -> [a] -> [b]
map [String] -> String
unwords
  [ [ String
"The package must have been build with configuration"
    , forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat [ String
"flag `--enable-", String
s, String
"s`." ]
    ]
  , []  -- blank line
  , [ forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat [ String
"Note that additional dependencies of the ", String
s, String
"s" ]
    , String
"must have already been installed."
    ]
  , []
  , [ String
"By defining UserHooks in a custom Setup.hs, the package can define"
    , forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat [ String
"actions to be executed before and after running ", String
s, String
"s." ]
    ]
  ]

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

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

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

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

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

data BenchmarkFlags = BenchmarkFlags {
    BenchmarkFlags -> Flag String
benchmarkDistPref  :: Flag FilePath,
    BenchmarkFlags -> Flag Verbosity
benchmarkVerbosity :: Flag Verbosity,
    BenchmarkFlags -> [PathTemplate]
benchmarkOptions   :: [PathTemplate]
  } deriving (Int -> BenchmarkFlags -> String -> String
[BenchmarkFlags] -> String -> String
BenchmarkFlags -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [BenchmarkFlags] -> String -> String
$cshowList :: [BenchmarkFlags] -> String -> String
show :: BenchmarkFlags -> String
$cshow :: BenchmarkFlags -> String
showsPrec :: Int -> BenchmarkFlags -> String -> String
$cshowsPrec :: Int -> BenchmarkFlags -> String -> String
Show, 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 {
    benchmarkDistPref :: Flag String
benchmarkDistPref  = forall a. Flag a
NoFlag,
    benchmarkVerbosity :: Flag Verbosity
benchmarkVerbosity = forall a. a -> Flag a
Flag Verbosity
normal,
    benchmarkOptions :: [PathTemplate]
benchmarkOptions   = []
  }

benchmarkCommand :: CommandUI BenchmarkFlags
benchmarkCommand :: CommandUI BenchmarkFlags
benchmarkCommand = CommandUI
  { commandName :: String
commandName         = String
"bench"
  , commandSynopsis :: String
commandSynopsis     =
      String
"Run all/specific benchmarks."
  , commandDescription :: Maybe (String -> String)
commandDescription  = forall a. a -> Maybe a
Just forall a b. (a -> b) -> a -> b
$ \ String
_pname -> String -> String
wrapText forall a b. (a -> b) -> a -> b
$
      String -> String
testOrBenchmarkHelpText String
"benchmark"
  , commandNotes :: Maybe (String -> String)
commandNotes        = forall a. Maybe a
Nothing
  , commandUsage :: String -> String
commandUsage        = String -> [String] -> String -> String
usageAlternatives String
"bench"
      [ String
"[FLAGS]"
      , String
"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 =
  [ 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 })
  , forall flags.
(flags -> Flag String)
-> (Flag String -> flags -> flags)
-> ShowOrParseArgs
-> OptionField flags
optionDistPref
        BenchmarkFlags -> Flag String
benchmarkDistPref (\Flag String
d BenchmarkFlags
flags -> BenchmarkFlags
flags { benchmarkDistPref :: Flag String
benchmarkDistPref = Flag String
d })
        ShowOrParseArgs
showOrParseArgs
  , forall get set a.
String
-> [String]
-> String
-> get
-> set
-> MkOptDescr get set a
-> OptionField a
option [] [String
"benchmark-options"]
        (String
"give extra options to benchmark executables "
         forall a. [a] -> [a] -> [a]
++ String
"(name templates can use $pkgid, $compiler, "
         forall a. [a] -> [a] -> [a]
++ String
"$os, $arch, $benchmark)")
        BenchmarkFlags -> [PathTemplate]
benchmarkOptions (\[PathTemplate]
v BenchmarkFlags
flags -> BenchmarkFlags
flags { benchmarkOptions :: [PathTemplate]
benchmarkOptions = [PathTemplate]
v })
        (forall b a.
Monoid b =>
String
-> (String -> b)
-> (b -> [String])
-> MkOptDescr (a -> b) (b -> a -> a) a
reqArg' String
"TEMPLATES" (forall a b. (a -> b) -> [a] -> [b]
map String -> PathTemplate
toPathTemplate forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> [String]
splitArgs)
            (forall a b. a -> b -> a
const []))
  , forall get set a.
String
-> [String]
-> String
-> get
-> set
-> MkOptDescr get set a
-> OptionField a
option [] [String
"benchmark-option"]
        (String
"give extra option to benchmark executables "
         forall a. [a] -> [a] -> [a]
++ String
"(no need to quote options containing spaces, "
         forall a. [a] -> [a] -> [a]
++ String
"name template can use $pkgid, $compiler, "
         forall a. [a] -> [a] -> [a]
++ String
"$os, $arch, $benchmark)")
        BenchmarkFlags -> [PathTemplate]
benchmarkOptions (\[PathTemplate]
v BenchmarkFlags
flags -> BenchmarkFlags
flags { benchmarkOptions :: [PathTemplate]
benchmarkOptions = [PathTemplate]
v })
        (forall b a.
Monoid b =>
String
-> (String -> b)
-> (b -> [String])
-> MkOptDescr (a -> b) (b -> a -> a) a
reqArg' String
"TEMPLATE" (\String
x -> [String -> PathTemplate
toPathTemplate String
x])
            (forall a b. (a -> b) -> [a] -> [b]
map PathTemplate -> String
fromPathTemplate))
  ]

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

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

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

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

programFlagsDescription :: ProgramDb -> String
programFlagsDescription :: ProgramDb -> String
programFlagsDescription ProgramDb
progDb =
     String
"The flags --with-PROG and --PROG-option(s) can be used with"
  forall a. [a] -> [a] -> [a]
++ String
" the following programs:"
  forall a. [a] -> [a] -> [a]
++ (forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap (\[String]
line -> String
"\n  " forall a. [a] -> [a] -> [a]
++ [String] -> String
unwords [String]
line) forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> [String] -> [[String]]
wrapLine Int
77 forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Ord a => [a] -> [a]
sort)
     [ Program -> String
programName Program
prog | (Program
prog, Maybe ConfiguredProgram
_) <- ProgramDb -> [(Program, Maybe ConfiguredProgram)]
knownPrograms ProgramDb
progDb ]
  forall a. [a] -> [a] -> [a]
++ String
"\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 :: forall flags.
ProgramDb
-> ShowOrParseArgs
-> (flags -> [(String, String)])
-> ([(String, String)] -> flags -> flags)
-> [OptionField flags]
programDbPaths ProgramDb
progDb ShowOrParseArgs
showOrParseArgs flags -> [(String, String)]
get [(String, String)] -> flags -> flags
set =
  forall flags.
(String -> String)
-> ProgramDb
-> ShowOrParseArgs
-> (flags -> [(String, String)])
-> ([(String, String)] -> flags -> flags)
-> [OptionField flags]
programDbPaths' (String
"with-" forall a. [a] -> [a] -> [a]
++) ProgramDb
progDb ShowOrParseArgs
showOrParseArgs flags -> [(String, String)]
get [(String, String)] -> 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' :: forall flags.
(String -> String)
-> ProgramDb
-> ShowOrParseArgs
-> (flags -> [(String, String)])
-> ([(String, String)] -> flags -> flags)
-> [OptionField flags]
programDbPaths' String -> String
mkName ProgramDb
progDb ShowOrParseArgs
showOrParseArgs flags -> [(String, String)]
get [(String, String)] -> 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  -> [String -> OptionField flags
withProgramPath String
"PROG"]
    ShowOrParseArgs
ParseArgs -> forall a b. (a -> b) -> [a] -> [b]
map (String -> OptionField flags
withProgramPath forall b c a. (b -> c) -> (a -> b) -> a -> c
. Program -> String
programName forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. (a, b) -> a
fst)
                 (ProgramDb -> [(Program, Maybe ConfiguredProgram)]
knownPrograms ProgramDb
progDb)
  where
    withProgramPath :: String -> OptionField flags
withProgramPath String
prog =
      forall get set a.
String
-> [String]
-> String
-> get
-> set
-> MkOptDescr get set a
-> OptionField a
option String
"" [String -> String
mkName String
prog]
        (String
"give the path to " forall a. [a] -> [a] -> [a]
++ String
prog)
        flags -> [(String, String)]
get [(String, String)] -> flags -> flags
set
        (forall b a.
Monoid b =>
String
-> (String -> b)
-> (b -> [String])
-> MkOptDescr (a -> b) (b -> a -> a) a
reqArg' String
"PATH" (\String
path -> [(String
prog, String
path)])
          (\[(String, String)]
progPaths -> [ String
path | (String
prog', String
path) <- [(String, String)]
progPaths, String
progforall a. Eq a => a -> a -> Bool
==String
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 :: forall flags.
ProgramDb
-> ShowOrParseArgs
-> (flags -> [(String, [String])])
-> ([(String, [String])] -> flags -> flags)
-> [OptionField flags]
programDbOption ProgramDb
progDb ShowOrParseArgs
showOrParseArgs flags -> [(String, [String])]
get [(String, [String])] -> 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  -> [String -> OptionField flags
programOption String
"PROG"]
    ShowOrParseArgs
ParseArgs -> forall a b. (a -> b) -> [a] -> [b]
map (String -> OptionField flags
programOption  forall b c a. (b -> c) -> (a -> b) -> a -> c
. Program -> String
programName forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. (a, b) -> a
fst)
                 (ProgramDb -> [(Program, Maybe ConfiguredProgram)]
knownPrograms ProgramDb
progDb)
  where
    programOption :: String -> OptionField flags
programOption String
prog =
      forall get set a.
String
-> [String]
-> String
-> get
-> set
-> MkOptDescr get set a
-> OptionField a
option String
"" [String
prog forall a. [a] -> [a] -> [a]
++ String
"-option"]
        (String
"give an extra option to " forall a. [a] -> [a] -> [a]
++ String
prog forall a. [a] -> [a] -> [a]
++
         String
" (no need to quote options containing spaces)")
        flags -> [(String, [String])]
get [(String, [String])] -> flags -> flags
set
        (forall b a.
Monoid b =>
String
-> (String -> b)
-> (b -> [String])
-> MkOptDescr (a -> b) (b -> a -> a) a
reqArg' String
"OPT" (\String
arg -> [(String
prog, [String
arg])])
           (\[(String, [String])]
progArgs -> forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat [ [String]
args
                                | (String
prog', [String]
args) <- [(String, [String])]
progArgs, String
progforall a. Eq a => a -> a -> Bool
==String
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 :: forall flags.
ProgramDb
-> ShowOrParseArgs
-> (flags -> [(String, [String])])
-> ([(String, [String])] -> flags -> flags)
-> [OptionField flags]
programDbOptions ProgramDb
progDb ShowOrParseArgs
showOrParseArgs flags -> [(String, [String])]
get [(String, [String])] -> 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  -> [String -> OptionField flags
programOptions  String
"PROG"]
    ShowOrParseArgs
ParseArgs -> forall a b. (a -> b) -> [a] -> [b]
map (String -> OptionField flags
programOptions forall b c a. (b -> c) -> (a -> b) -> a -> c
. Program -> String
programName forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. (a, b) -> a
fst)
                 (ProgramDb -> [(Program, Maybe ConfiguredProgram)]
knownPrograms ProgramDb
progDb)
  where
    programOptions :: String -> OptionField flags
programOptions String
prog =
      forall get set a.
String
-> [String]
-> String
-> get
-> set
-> MkOptDescr get set a
-> OptionField a
option String
"" [String
prog forall a. [a] -> [a] -> [a]
++ String
"-options"]
        (String
"give extra options to " forall a. [a] -> [a] -> [a]
++ String
prog)
        flags -> [(String, [String])]
get [(String, [String])] -> flags -> flags
set
        (forall b a.
Monoid b =>
String
-> (String -> b)
-> (b -> [String])
-> MkOptDescr (a -> b) (b -> a -> a) a
reqArg' String
"OPTS" (\String
args -> [(String
prog, String -> [String]
splitArgs String
args)]) (forall a b. a -> b -> a
const []))

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

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

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

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

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

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

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

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

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

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

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

configureProg :: Verbosity -> ProgramDb -> Program
                 -> IO (FilePath, [String])
configureProg :: Verbosity -> ProgramDb -> Program -> IO (String, [String])
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 -> [String] -> ProgramInvocation
programInvocation ConfiguredProgram
p []
    forall (m :: * -> *) a. Monad m => a -> m a
return (ProgramInvocation -> String
progInvokePath ProgramInvocation
pInv, ProgramInvocation -> [String]
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 :: String -> [String]
splitArgs  = String -> String -> [String]
space []
  where
    space :: String -> String -> [String]
    space :: String -> String -> [String]
space String
w []      = forall {a}. [a] -> [[a]] -> [[a]]
word String
w []
    space String
w ( Char
c :String
s)
        | Char -> Bool
isSpace Char
c = forall {a}. [a] -> [[a]] -> [[a]]
word String
w (String -> String -> [String]
space [] String
s)
    space String
w (Char
'"':String
s) = String -> String -> [String]
string String
w String
s
    space String
w String
s       = String -> String -> [String]
nonstring String
w String
s

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

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

    word :: [a] -> [[a]] -> [[a]]
word [] [[a]]
s = [[a]]
s
    word [a]
w  [[a]]
s = forall a. [a] -> [a]
reverse [a]
w 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?
-}