{-# LANGUAGE CPP #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE PatternSynonyms #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE ViewPatterns #-}
module Distribution.Simple.Setup.Config
( ConfigFlags
( ConfigCommonFlags
, configVerbosity
, configDistPref
, configCabalFilePath
, configWorkingDir
, configTargets
, ..
)
, emptyConfigFlags
, defaultConfigFlags
, configureCommand
, configPrograms
, readPackageDb
, readPackageDbList
, showPackageDb
, showPackageDbList
, configureArgs
, configureOptions
, installDirsOptions
) where
import Distribution.Compat.Prelude hiding (get)
import Prelude ()
import qualified Distribution.Compat.CharParsing as P
import Distribution.Compat.Semigroup (Last' (..), Option' (..))
import Distribution.Compat.Stack
import Distribution.Compiler
import Distribution.ModuleName
import Distribution.PackageDescription
import Distribution.Parsec
import Distribution.Pretty
import Distribution.ReadE
import Distribution.Simple.Command hiding (boolOpt, boolOpt')
import Distribution.Simple.Compiler
import Distribution.Simple.Flag
import Distribution.Simple.InstallDirs
import Distribution.Simple.Program
import Distribution.Simple.Setup.Common
import Distribution.Simple.Utils
import Distribution.Types.ComponentId
import Distribution.Types.DumpBuildInfo
import Distribution.Types.GivenComponent
import Distribution.Types.Module
import Distribution.Types.PackageVersionConstraint
import Distribution.Types.UnitId
import Distribution.Utils.NubList
import Distribution.Utils.Path
import Distribution.Verbosity
import qualified Text.PrettyPrint as Disp
data ConfigFlags = ConfigFlags
{ ConfigFlags -> CommonSetupFlags
configCommonFlags :: !CommonSetupFlags
,
ConfigFlags -> Option' (Last' ProgramDb)
configPrograms_ :: Option' (Last' ProgramDb)
, ConfigFlags -> [(String, String)]
configProgramPaths :: [(String, FilePath)]
, ConfigFlags -> [(String, [String])]
configProgramArgs :: [(String, [String])]
, :: NubList FilePath
, ConfigFlags -> Flag CompilerFlavor
configHcFlavor :: Flag CompilerFlavor
, ConfigFlags -> Flag String
configHcPath :: Flag FilePath
, ConfigFlags -> Flag String
configHcPkg :: Flag FilePath
, ConfigFlags -> Flag Bool
configVanillaLib :: Flag Bool
, ConfigFlags -> Flag Bool
configProfLib :: Flag Bool
, ConfigFlags -> Flag Bool
configSharedLib :: Flag Bool
, ConfigFlags -> Flag Bool
configStaticLib :: Flag Bool
, ConfigFlags -> Flag Bool
configDynExe :: Flag Bool
, ConfigFlags -> Flag Bool
configFullyStaticExe :: Flag Bool
, ConfigFlags -> Flag Bool
configProfExe :: Flag Bool
, ConfigFlags -> Flag Bool
configProf :: Flag Bool
, ConfigFlags -> Flag Bool
configProfShared :: Flag Bool
, ConfigFlags -> Flag ProfDetailLevel
configProfDetail :: Flag ProfDetailLevel
, ConfigFlags -> Flag ProfDetailLevel
configProfLibDetail :: Flag ProfDetailLevel
, ConfigFlags -> [String]
configConfigureArgs :: [String]
, ConfigFlags -> Flag OptimisationLevel
configOptimization :: Flag OptimisationLevel
, ConfigFlags -> Flag PathTemplate
configProgPrefix :: Flag PathTemplate
, ConfigFlags -> Flag PathTemplate
configProgSuffix :: Flag PathTemplate
, ConfigFlags -> InstallDirs (Flag PathTemplate)
configInstallDirs :: InstallDirs (Flag PathTemplate)
, ConfigFlags -> Flag String
configScratchDir :: Flag FilePath
, :: [SymbolicPath Pkg (Dir Lib)]
, :: [SymbolicPath Pkg (Dir Lib)]
, :: [SymbolicPath Pkg (Dir Framework)]
, :: [SymbolicPath Pkg (Dir Include)]
, ConfigFlags -> Flag String
configIPID :: Flag String
, ConfigFlags -> Flag ComponentId
configCID :: Flag ComponentId
, ConfigFlags -> Flag Bool
configDeterministic :: Flag Bool
, ConfigFlags -> Flag Bool
configUserInstall :: Flag Bool
, ConfigFlags -> [Maybe PackageDB]
configPackageDBs :: [Maybe PackageDB]
, ConfigFlags -> Flag Bool
configGHCiLib :: Flag Bool
, ConfigFlags -> Flag Bool
configSplitSections :: Flag Bool
, ConfigFlags -> Flag Bool
configSplitObjs :: Flag Bool
, ConfigFlags -> Flag Bool
configStripExes :: Flag Bool
, ConfigFlags -> Flag Bool
configStripLibs :: Flag Bool
, ConfigFlags -> [PackageVersionConstraint]
configConstraints :: [PackageVersionConstraint]
, ConfigFlags -> [GivenComponent]
configDependencies :: [GivenComponent]
, ConfigFlags -> [PromisedComponent]
configPromisedDependencies :: [PromisedComponent]
, ConfigFlags -> [(ModuleName, Module)]
configInstantiateWith :: [(ModuleName, Module)]
, ConfigFlags -> FlagAssignment
configConfigurationsFlags :: FlagAssignment
, ConfigFlags -> Flag Bool
configTests :: Flag Bool
, ConfigFlags -> Flag Bool
configBenchmarks :: Flag Bool
, ConfigFlags -> Flag Bool
configCoverage :: Flag Bool
, ConfigFlags -> Flag Bool
configLibCoverage :: Flag Bool
, ConfigFlags -> Flag Bool
configExactConfiguration :: Flag Bool
, ConfigFlags -> Flag String
configFlagError :: Flag String
, ConfigFlags -> Flag Bool
configRelocatable :: Flag Bool
, ConfigFlags -> Flag DebugInfoLevel
configDebugInfo :: Flag DebugInfoLevel
, ConfigFlags -> Flag DumpBuildInfo
configDumpBuildInfo :: Flag DumpBuildInfo
, ConfigFlags -> Flag Bool
configUseResponseFiles :: Flag Bool
, ConfigFlags -> Flag Bool
configAllowDependingOnPrivateLibs :: Flag Bool
, ConfigFlags -> Flag [UnitId]
configCoverageFor :: Flag [UnitId]
, ConfigFlags -> Flag Bool
configIgnoreBuildTools :: Flag Bool
}
deriving ((forall x. ConfigFlags -> Rep ConfigFlags x)
-> (forall x. Rep ConfigFlags x -> ConfigFlags)
-> Generic ConfigFlags
forall x. Rep ConfigFlags x -> ConfigFlags
forall x. ConfigFlags -> Rep ConfigFlags x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. ConfigFlags -> Rep ConfigFlags x
from :: forall x. ConfigFlags -> Rep ConfigFlags x
$cto :: forall x. Rep ConfigFlags x -> ConfigFlags
to :: forall x. Rep ConfigFlags x -> ConfigFlags
Generic, ReadPrec [ConfigFlags]
ReadPrec ConfigFlags
Int -> ReadS ConfigFlags
ReadS [ConfigFlags]
(Int -> ReadS ConfigFlags)
-> ReadS [ConfigFlags]
-> ReadPrec ConfigFlags
-> ReadPrec [ConfigFlags]
-> Read ConfigFlags
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS ConfigFlags
readsPrec :: Int -> ReadS ConfigFlags
$creadList :: ReadS [ConfigFlags]
readList :: ReadS [ConfigFlags]
$creadPrec :: ReadPrec ConfigFlags
readPrec :: ReadPrec ConfigFlags
$creadListPrec :: ReadPrec [ConfigFlags]
readListPrec :: ReadPrec [ConfigFlags]
Read, Int -> ConfigFlags -> ShowS
[ConfigFlags] -> ShowS
ConfigFlags -> String
(Int -> ConfigFlags -> ShowS)
-> (ConfigFlags -> String)
-> ([ConfigFlags] -> ShowS)
-> Show ConfigFlags
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ConfigFlags -> ShowS
showsPrec :: Int -> ConfigFlags -> ShowS
$cshow :: ConfigFlags -> String
show :: ConfigFlags -> String
$cshowList :: [ConfigFlags] -> ShowS
showList :: [ConfigFlags] -> ShowS
Show, Typeable)
pattern ConfigCommonFlags
:: Flag Verbosity
-> Flag (SymbolicPath Pkg (Dir Dist))
-> Flag (SymbolicPath CWD (Dir Pkg))
-> Flag (SymbolicPath Pkg File)
-> [String]
-> ConfigFlags
pattern $mConfigCommonFlags :: forall {r}.
ConfigFlags
-> (Flag Verbosity
-> Flag (SymbolicPath Pkg ('Dir Dist))
-> Flag (SymbolicPath CWD ('Dir Pkg))
-> Flag (SymbolicPath Pkg 'File)
-> [String]
-> r)
-> ((# #) -> r)
-> r
ConfigCommonFlags
{ ConfigFlags -> Flag Verbosity
configVerbosity
, ConfigFlags -> Flag (SymbolicPath Pkg ('Dir Dist))
configDistPref
, ConfigFlags -> Flag (SymbolicPath CWD ('Dir Pkg))
configWorkingDir
, ConfigFlags -> Flag (SymbolicPath Pkg 'File)
configCabalFilePath
, ConfigFlags -> [String]
configTargets
} <-
( configCommonFlags ->
CommonSetupFlags
{ setupVerbosity = configVerbosity
, setupDistPref = configDistPref
, setupWorkingDir = configWorkingDir
, setupCabalFilePath = configCabalFilePath
, setupTargets = configTargets
}
)
instance Binary ConfigFlags
instance Structured ConfigFlags
configPrograms :: WithCallStack (ConfigFlags -> ProgramDb)
configPrograms :: WithCallStack (ConfigFlags -> ProgramDb)
configPrograms =
ProgramDb -> Maybe ProgramDb -> ProgramDb
forall a. a -> Maybe a -> a
fromMaybe (String -> ProgramDb
forall a. HasCallStack => String -> a
error String
"FIXME: remove configPrograms")
(Maybe ProgramDb -> ProgramDb)
-> (ConfigFlags -> Maybe ProgramDb) -> ConfigFlags -> ProgramDb
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Last' ProgramDb -> ProgramDb)
-> Maybe (Last' ProgramDb) -> Maybe ProgramDb
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Last' ProgramDb -> ProgramDb
forall a. Last' a -> a
getLast'
(Maybe (Last' ProgramDb) -> Maybe ProgramDb)
-> (ConfigFlags -> Maybe (Last' ProgramDb))
-> ConfigFlags
-> Maybe ProgramDb
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Option' (Last' ProgramDb) -> Maybe (Last' ProgramDb)
forall a. Option' a -> Maybe a
getOption'
(Option' (Last' ProgramDb) -> Maybe (Last' ProgramDb))
-> (ConfigFlags -> Option' (Last' ProgramDb))
-> ConfigFlags
-> Maybe (Last' ProgramDb)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ConfigFlags -> Option' (Last' ProgramDb)
configPrograms_
instance Eq ConfigFlags where
== :: ConfigFlags -> ConfigFlags -> Bool
(==) ConfigFlags
a ConfigFlags
b =
(ConfigFlags -> CommonSetupFlags) -> Bool
forall {b}. Eq b => (ConfigFlags -> b) -> Bool
equal ConfigFlags -> CommonSetupFlags
configCommonFlags
Bool -> Bool -> Bool
&& (ConfigFlags -> [(String, String)]) -> Bool
forall {b}. Eq b => (ConfigFlags -> b) -> Bool
equal ConfigFlags -> [(String, String)]
configProgramPaths
Bool -> Bool -> Bool
&& (ConfigFlags -> [(String, [String])]) -> Bool
forall {b}. Eq b => (ConfigFlags -> b) -> Bool
equal ConfigFlags -> [(String, [String])]
configProgramArgs
Bool -> Bool -> Bool
&& (ConfigFlags -> NubList String) -> Bool
forall {b}. Eq b => (ConfigFlags -> b) -> Bool
equal ConfigFlags -> NubList String
configProgramPathExtra
Bool -> Bool -> Bool
&& (ConfigFlags -> Flag CompilerFlavor) -> Bool
forall {b}. Eq b => (ConfigFlags -> b) -> Bool
equal ConfigFlags -> Flag CompilerFlavor
configHcFlavor
Bool -> Bool -> Bool
&& (ConfigFlags -> Flag String) -> Bool
forall {b}. Eq b => (ConfigFlags -> b) -> Bool
equal ConfigFlags -> Flag String
configHcPath
Bool -> Bool -> Bool
&& (ConfigFlags -> Flag String) -> Bool
forall {b}. Eq b => (ConfigFlags -> b) -> Bool
equal ConfigFlags -> Flag String
configHcPkg
Bool -> Bool -> Bool
&& (ConfigFlags -> Flag Bool) -> Bool
forall {b}. Eq b => (ConfigFlags -> b) -> Bool
equal ConfigFlags -> Flag Bool
configVanillaLib
Bool -> Bool -> Bool
&& (ConfigFlags -> Flag Bool) -> Bool
forall {b}. Eq b => (ConfigFlags -> b) -> Bool
equal ConfigFlags -> Flag Bool
configProfLib
Bool -> Bool -> Bool
&& (ConfigFlags -> Flag Bool) -> Bool
forall {b}. Eq b => (ConfigFlags -> b) -> Bool
equal ConfigFlags -> Flag Bool
configSharedLib
Bool -> Bool -> Bool
&& (ConfigFlags -> Flag Bool) -> Bool
forall {b}. Eq b => (ConfigFlags -> b) -> Bool
equal ConfigFlags -> Flag Bool
configStaticLib
Bool -> Bool -> Bool
&& (ConfigFlags -> Flag Bool) -> Bool
forall {b}. Eq b => (ConfigFlags -> b) -> Bool
equal ConfigFlags -> Flag Bool
configDynExe
Bool -> Bool -> Bool
&& (ConfigFlags -> Flag Bool) -> Bool
forall {b}. Eq b => (ConfigFlags -> b) -> Bool
equal ConfigFlags -> Flag Bool
configFullyStaticExe
Bool -> Bool -> Bool
&& (ConfigFlags -> Flag Bool) -> Bool
forall {b}. Eq b => (ConfigFlags -> b) -> Bool
equal ConfigFlags -> Flag Bool
configProfExe
Bool -> Bool -> Bool
&& (ConfigFlags -> Flag Bool) -> Bool
forall {b}. Eq b => (ConfigFlags -> b) -> Bool
equal ConfigFlags -> Flag Bool
configProf
Bool -> Bool -> Bool
&& (ConfigFlags -> Flag ProfDetailLevel) -> Bool
forall {b}. Eq b => (ConfigFlags -> b) -> Bool
equal ConfigFlags -> Flag ProfDetailLevel
configProfDetail
Bool -> Bool -> Bool
&& (ConfigFlags -> Flag Bool) -> Bool
forall {b}. Eq b => (ConfigFlags -> b) -> Bool
equal ConfigFlags -> Flag Bool
configProfShared
Bool -> Bool -> Bool
&& (ConfigFlags -> Flag ProfDetailLevel) -> Bool
forall {b}. Eq b => (ConfigFlags -> b) -> Bool
equal ConfigFlags -> Flag ProfDetailLevel
configProfLibDetail
Bool -> Bool -> Bool
&& (ConfigFlags -> [String]) -> Bool
forall {b}. Eq b => (ConfigFlags -> b) -> Bool
equal ConfigFlags -> [String]
configConfigureArgs
Bool -> Bool -> Bool
&& (ConfigFlags -> Flag OptimisationLevel) -> Bool
forall {b}. Eq b => (ConfigFlags -> b) -> Bool
equal ConfigFlags -> Flag OptimisationLevel
configOptimization
Bool -> Bool -> Bool
&& (ConfigFlags -> Flag PathTemplate) -> Bool
forall {b}. Eq b => (ConfigFlags -> b) -> Bool
equal ConfigFlags -> Flag PathTemplate
configProgPrefix
Bool -> Bool -> Bool
&& (ConfigFlags -> Flag PathTemplate) -> Bool
forall {b}. Eq b => (ConfigFlags -> b) -> Bool
equal ConfigFlags -> Flag PathTemplate
configProgSuffix
Bool -> Bool -> Bool
&& (ConfigFlags -> InstallDirs (Flag PathTemplate)) -> Bool
forall {b}. Eq b => (ConfigFlags -> b) -> Bool
equal ConfigFlags -> InstallDirs (Flag PathTemplate)
configInstallDirs
Bool -> Bool -> Bool
&& (ConfigFlags -> Flag String) -> Bool
forall {b}. Eq b => (ConfigFlags -> b) -> Bool
equal ConfigFlags -> Flag String
configScratchDir
Bool -> Bool -> Bool
&& (ConfigFlags -> [SymbolicPath Pkg ('Dir Lib)]) -> Bool
forall {b}. Eq b => (ConfigFlags -> b) -> Bool
equal ConfigFlags -> [SymbolicPath Pkg ('Dir Lib)]
configExtraLibDirs
Bool -> Bool -> Bool
&& (ConfigFlags -> [SymbolicPath Pkg ('Dir Lib)]) -> Bool
forall {b}. Eq b => (ConfigFlags -> b) -> Bool
equal ConfigFlags -> [SymbolicPath Pkg ('Dir Lib)]
configExtraLibDirsStatic
Bool -> Bool -> Bool
&& (ConfigFlags -> [SymbolicPath Pkg ('Dir Include)]) -> Bool
forall {b}. Eq b => (ConfigFlags -> b) -> Bool
equal ConfigFlags -> [SymbolicPath Pkg ('Dir Include)]
configExtraIncludeDirs
Bool -> Bool -> Bool
&& (ConfigFlags -> Flag String) -> Bool
forall {b}. Eq b => (ConfigFlags -> b) -> Bool
equal ConfigFlags -> Flag String
configIPID
Bool -> Bool -> Bool
&& (ConfigFlags -> Flag Bool) -> Bool
forall {b}. Eq b => (ConfigFlags -> b) -> Bool
equal ConfigFlags -> Flag Bool
configDeterministic
Bool -> Bool -> Bool
&& (ConfigFlags -> Flag Bool) -> Bool
forall {b}. Eq b => (ConfigFlags -> b) -> Bool
equal ConfigFlags -> Flag Bool
configUserInstall
Bool -> Bool -> Bool
&& (ConfigFlags -> [Maybe PackageDB]) -> Bool
forall {b}. Eq b => (ConfigFlags -> b) -> Bool
equal ConfigFlags -> [Maybe PackageDB]
configPackageDBs
Bool -> Bool -> Bool
&& (ConfigFlags -> Flag Bool) -> Bool
forall {b}. Eq b => (ConfigFlags -> b) -> Bool
equal ConfigFlags -> Flag Bool
configGHCiLib
Bool -> Bool -> Bool
&& (ConfigFlags -> Flag Bool) -> Bool
forall {b}. Eq b => (ConfigFlags -> b) -> Bool
equal ConfigFlags -> Flag Bool
configSplitSections
Bool -> Bool -> Bool
&& (ConfigFlags -> Flag Bool) -> Bool
forall {b}. Eq b => (ConfigFlags -> b) -> Bool
equal ConfigFlags -> Flag Bool
configSplitObjs
Bool -> Bool -> Bool
&& (ConfigFlags -> Flag Bool) -> Bool
forall {b}. Eq b => (ConfigFlags -> b) -> Bool
equal ConfigFlags -> Flag Bool
configStripExes
Bool -> Bool -> Bool
&& (ConfigFlags -> Flag Bool) -> Bool
forall {b}. Eq b => (ConfigFlags -> b) -> Bool
equal ConfigFlags -> Flag Bool
configStripLibs
Bool -> Bool -> Bool
&& (ConfigFlags -> [PackageVersionConstraint]) -> Bool
forall {b}. Eq b => (ConfigFlags -> b) -> Bool
equal ConfigFlags -> [PackageVersionConstraint]
configConstraints
Bool -> Bool -> Bool
&& (ConfigFlags -> [GivenComponent]) -> Bool
forall {b}. Eq b => (ConfigFlags -> b) -> Bool
equal ConfigFlags -> [GivenComponent]
configDependencies
Bool -> Bool -> Bool
&& (ConfigFlags -> [PromisedComponent]) -> Bool
forall {b}. Eq b => (ConfigFlags -> b) -> Bool
equal ConfigFlags -> [PromisedComponent]
configPromisedDependencies
Bool -> Bool -> Bool
&& (ConfigFlags -> FlagAssignment) -> Bool
forall {b}. Eq b => (ConfigFlags -> b) -> Bool
equal ConfigFlags -> FlagAssignment
configConfigurationsFlags
Bool -> Bool -> Bool
&& (ConfigFlags -> Flag Bool) -> Bool
forall {b}. Eq b => (ConfigFlags -> b) -> Bool
equal ConfigFlags -> Flag Bool
configTests
Bool -> Bool -> Bool
&& (ConfigFlags -> Flag Bool) -> Bool
forall {b}. Eq b => (ConfigFlags -> b) -> Bool
equal ConfigFlags -> Flag Bool
configBenchmarks
Bool -> Bool -> Bool
&& (ConfigFlags -> Flag Bool) -> Bool
forall {b}. Eq b => (ConfigFlags -> b) -> Bool
equal ConfigFlags -> Flag Bool
configCoverage
Bool -> Bool -> Bool
&& (ConfigFlags -> Flag Bool) -> Bool
forall {b}. Eq b => (ConfigFlags -> b) -> Bool
equal ConfigFlags -> Flag Bool
configLibCoverage
Bool -> Bool -> Bool
&& (ConfigFlags -> Flag Bool) -> Bool
forall {b}. Eq b => (ConfigFlags -> b) -> Bool
equal ConfigFlags -> Flag Bool
configExactConfiguration
Bool -> Bool -> Bool
&& (ConfigFlags -> Flag String) -> Bool
forall {b}. Eq b => (ConfigFlags -> b) -> Bool
equal ConfigFlags -> Flag String
configFlagError
Bool -> Bool -> Bool
&& (ConfigFlags -> Flag Bool) -> Bool
forall {b}. Eq b => (ConfigFlags -> b) -> Bool
equal ConfigFlags -> Flag Bool
configRelocatable
Bool -> Bool -> Bool
&& (ConfigFlags -> Flag DebugInfoLevel) -> Bool
forall {b}. Eq b => (ConfigFlags -> b) -> Bool
equal ConfigFlags -> Flag DebugInfoLevel
configDebugInfo
Bool -> Bool -> Bool
&& (ConfigFlags -> Flag DumpBuildInfo) -> Bool
forall {b}. Eq b => (ConfigFlags -> b) -> Bool
equal ConfigFlags -> Flag DumpBuildInfo
configDumpBuildInfo
Bool -> Bool -> Bool
&& (ConfigFlags -> Flag Bool) -> Bool
forall {b}. Eq b => (ConfigFlags -> b) -> Bool
equal ConfigFlags -> Flag Bool
configUseResponseFiles
Bool -> Bool -> Bool
&& (ConfigFlags -> Flag Bool) -> Bool
forall {b}. Eq b => (ConfigFlags -> b) -> Bool
equal ConfigFlags -> Flag Bool
configAllowDependingOnPrivateLibs
Bool -> Bool -> Bool
&& (ConfigFlags -> Flag [UnitId]) -> Bool
forall {b}. Eq b => (ConfigFlags -> b) -> Bool
equal ConfigFlags -> Flag [UnitId]
configCoverageFor
Bool -> Bool -> Bool
&& (ConfigFlags -> Flag Bool) -> Bool
forall {b}. Eq b => (ConfigFlags -> b) -> Bool
equal ConfigFlags -> Flag Bool
configIgnoreBuildTools
where
equal :: (ConfigFlags -> b) -> Bool
equal ConfigFlags -> b
f = (b -> b -> Bool)
-> (ConfigFlags -> b) -> ConfigFlags -> ConfigFlags -> Bool
forall b c a. (b -> b -> c) -> (a -> b) -> a -> a -> c
on b -> b -> Bool
forall a. Eq a => a -> a -> Bool
(==) ConfigFlags -> b
f ConfigFlags
a ConfigFlags
b
defaultConfigFlags :: ProgramDb -> ConfigFlags
defaultConfigFlags :: ProgramDb -> ConfigFlags
defaultConfigFlags ProgramDb
progDb =
ConfigFlags
emptyConfigFlags
{ configCommonFlags = defaultCommonSetupFlags
, configPrograms_ = Option' (Just (Last' progDb))
, configHcFlavor = maybe NoFlag Flag defaultCompilerFlavor
, configVanillaLib = Flag True
, configProfLib = NoFlag
, configSharedLib = NoFlag
, configStaticLib = NoFlag
, configDynExe = Flag False
, configFullyStaticExe = Flag False
, configProfExe = NoFlag
, configProf = NoFlag
, configProfDetail = NoFlag
, configProfLibDetail = NoFlag
, configOptimization = Flag NormalOptimisation
, configProgPrefix = Flag (toPathTemplate "")
, configProgSuffix = Flag (toPathTemplate "")
, configUserInstall = Flag False
#if defined(mingw32_HOST_OS)
, configGHCiLib = Flag False
#else
, configGHCiLib = NoFlag
#endif
, configSplitSections = Flag False
, configSplitObjs = Flag False
, configStripExes = NoFlag
, configStripLibs = NoFlag
, configTests = Flag False
, configBenchmarks = Flag False
, configCoverage = Flag False
, configLibCoverage = NoFlag
, configExactConfiguration = Flag False
, configFlagError = NoFlag
, configRelocatable = Flag False
, configDebugInfo = Flag NoDebugInfo
, configDumpBuildInfo = NoFlag
, configUseResponseFiles = 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 ShowS
commandDescription = ShowS -> Maybe ShowS
forall a. a -> Maybe a
Just (ShowS -> Maybe ShowS) -> ShowS -> Maybe ShowS
forall a b. (a -> b) -> a -> b
$ \String
_ ->
ShowS
wrapText ShowS -> ShowS
forall a b. (a -> b) -> a -> b
$
String
"Configure how the package is built by setting "
String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
"package (and other) flags.\n"
String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
"\n"
String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
"The configuration affects several other commands, "
String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
"including build, test, bench, run, repl.\n"
, commandNotes :: Maybe ShowS
commandNotes = ShowS -> Maybe ShowS
forall a. a -> Maybe a
Just (ShowS -> Maybe ShowS) -> ShowS -> Maybe ShowS
forall a b. (a -> b) -> a -> b
$ \String
_pname -> ProgramDb -> String
programFlagsDescription ProgramDb
progDb
, commandUsage :: ShowS
commandUsage = \String
pname ->
String
"Usage: " String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
pname String -> ShowS
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
[OptionField ConfigFlags]
-> [OptionField ConfigFlags] -> [OptionField ConfigFlags]
forall a. [a] -> [a] -> [a]
++ ProgramDb
-> ShowOrParseArgs
-> (ConfigFlags -> [(String, String)])
-> ([(String, String)] -> ConfigFlags -> ConfigFlags)
-> [OptionField ConfigFlags]
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 = v})
[OptionField ConfigFlags]
-> [OptionField ConfigFlags] -> [OptionField ConfigFlags]
forall a. [a] -> [a] -> [a]
++ ProgramDb
-> ShowOrParseArgs
-> (ConfigFlags -> [(String, [String])])
-> ([(String, [String])] -> ConfigFlags -> ConfigFlags)
-> [OptionField ConfigFlags]
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 = v})
[OptionField ConfigFlags]
-> [OptionField ConfigFlags] -> [OptionField ConfigFlags]
forall a. [a] -> [a] -> [a]
++ ProgramDb
-> ShowOrParseArgs
-> (ConfigFlags -> [(String, [String])])
-> ([(String, [String])] -> ConfigFlags -> ConfigFlags)
-> [OptionField ConfigFlags]
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 = v})
}
parsecModSubstEntry :: ParsecParser (ModuleName, Module)
parsecModSubstEntry :: ParsecParser (ModuleName, Module)
parsecModSubstEntry = do
k <- ParsecParser ModuleName
forall a (m :: * -> *). (Parsec a, CabalParsing m) => m a
forall (m :: * -> *). CabalParsing m => m ModuleName
parsec
_ <- P.char '='
v <- parsec
return (k, v)
dispModSubstEntry :: (ModuleName, Module) -> Disp.Doc
dispModSubstEntry :: (ModuleName, Module) -> Doc
dispModSubstEntry (ModuleName
k, Module
v) = ModuleName -> Doc
forall a. Pretty a => a -> Doc
pretty ModuleName
k Doc -> Doc -> Doc
<<>> Char -> Doc
Disp.char Char
'=' Doc -> Doc -> Doc
<<>> Module -> Doc
forall a. Pretty a => a -> Doc
pretty Module
v
configureOptions :: ShowOrParseArgs -> [OptionField ConfigFlags]
configureOptions :: ShowOrParseArgs -> [OptionField ConfigFlags]
configureOptions ShowOrParseArgs
showOrParseArgs =
(ConfigFlags -> CommonSetupFlags)
-> (CommonSetupFlags -> ConfigFlags -> ConfigFlags)
-> ShowOrParseArgs
-> [OptionField ConfigFlags]
-> [OptionField ConfigFlags]
forall flags.
(flags -> CommonSetupFlags)
-> (CommonSetupFlags -> flags -> flags)
-> ShowOrParseArgs
-> [OptionField flags]
-> [OptionField flags]
withCommonSetupOptions
ConfigFlags -> CommonSetupFlags
configCommonFlags
(\CommonSetupFlags
c ConfigFlags
f -> ConfigFlags
f{configCommonFlags = c})
ShowOrParseArgs
showOrParseArgs
[ String
-> [String]
-> String
-> (ConfigFlags -> Flag CompilerFlavor)
-> (Flag CompilerFlavor -> ConfigFlags -> ConfigFlags)
-> MkOptDescr
(ConfigFlags -> Flag CompilerFlavor)
(Flag CompilerFlavor -> ConfigFlags -> ConfigFlags)
ConfigFlags
-> OptionField ConfigFlags
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 = v})
( [(Flag CompilerFlavor, (String, [String]), String)]
-> MkOptDescr
(ConfigFlags -> Flag CompilerFlavor)
(Flag CompilerFlavor -> ConfigFlags -> ConfigFlags)
ConfigFlags
forall b a.
Eq b =>
[(b, (String, [String]), String)]
-> MkOptDescr (a -> b) (b -> a -> a) a
choiceOpt
[ (CompilerFlavor -> Flag CompilerFlavor
forall a. a -> Flag a
Flag CompilerFlavor
GHC, (String
"g", [String
"ghc"]), String
"compile with GHC")
, (CompilerFlavor -> Flag CompilerFlavor
forall a. a -> Flag a
Flag CompilerFlavor
GHCJS, ([], [String
"ghcjs"]), String
"compile with GHCJS")
, (CompilerFlavor -> Flag CompilerFlavor
forall a. a -> Flag a
Flag CompilerFlavor
UHC, ([], [String
"uhc"]), String
"compile with UHC")
,
( CompilerFlavor -> Flag CompilerFlavor
forall a. a -> Flag a
Flag (String -> CompilerFlavor
HaskellSuite String
"haskell-suite")
, ([], [String
"haskell-suite"])
, String
"compile with a haskell-suite compiler"
)
]
)
, String
-> [String]
-> String
-> (ConfigFlags -> Flag String)
-> (Flag String -> ConfigFlags -> ConfigFlags)
-> MkOptDescr
(ConfigFlags -> Flag String)
(Flag String -> ConfigFlags -> ConfigFlags)
ConfigFlags
-> OptionField ConfigFlags
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 = v})
(String
-> MkOptDescr
(ConfigFlags -> Flag String)
(Flag String -> ConfigFlags -> ConfigFlags)
ConfigFlags
forall b.
String
-> String
-> [String]
-> String
-> (b -> Flag String)
-> (Flag String -> b -> b)
-> OptDescr b
reqArgFlag String
"PATH")
, String
-> [String]
-> String
-> (ConfigFlags -> Flag String)
-> (Flag String -> ConfigFlags -> ConfigFlags)
-> MkOptDescr
(ConfigFlags -> Flag String)
(Flag String -> ConfigFlags -> ConfigFlags)
ConfigFlags
-> OptionField ConfigFlags
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 = v})
(String
-> MkOptDescr
(ConfigFlags -> Flag String)
(Flag String -> ConfigFlags -> ConfigFlags)
ConfigFlags
forall b.
String
-> String
-> [String]
-> String
-> (b -> Flag String)
-> (Flag String -> b -> b)
-> OptDescr b
reqArgFlag String
"PATH")
]
[OptionField ConfigFlags]
-> [OptionField ConfigFlags] -> [OptionField ConfigFlags]
forall a. [a] -> [a] -> [a]
++ (OptionField (InstallDirs (Flag PathTemplate))
-> OptionField ConfigFlags)
-> [OptionField (InstallDirs (Flag PathTemplate))]
-> [OptionField ConfigFlags]
forall a b. (a -> b) -> [a] -> [b]
map OptionField (InstallDirs (Flag PathTemplate))
-> OptionField ConfigFlags
liftInstallDirs [OptionField (InstallDirs (Flag PathTemplate))]
installDirsOptions
[OptionField ConfigFlags]
-> [OptionField ConfigFlags] -> [OptionField ConfigFlags]
forall a. [a] -> [a] -> [a]
++ [ String
-> [String]
-> String
-> (ConfigFlags -> Flag PathTemplate)
-> (Flag PathTemplate -> ConfigFlags -> ConfigFlags)
-> MkOptDescr
(ConfigFlags -> Flag PathTemplate)
(Flag PathTemplate -> ConfigFlags -> ConfigFlags)
ConfigFlags
-> OptionField ConfigFlags
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 = v})
(String
-> MkOptDescr
(ConfigFlags -> Flag PathTemplate)
(Flag PathTemplate -> ConfigFlags -> ConfigFlags)
ConfigFlags
forall {b}.
String
-> String
-> [String]
-> String
-> (b -> Flag PathTemplate)
-> (Flag PathTemplate -> b -> b)
-> OptDescr b
reqPathTemplateArgFlag String
"PREFIX")
, String
-> [String]
-> String
-> (ConfigFlags -> Flag PathTemplate)
-> (Flag PathTemplate -> ConfigFlags -> ConfigFlags)
-> MkOptDescr
(ConfigFlags -> Flag PathTemplate)
(Flag PathTemplate -> ConfigFlags -> ConfigFlags)
ConfigFlags
-> OptionField ConfigFlags
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 = v})
(String
-> MkOptDescr
(ConfigFlags -> Flag PathTemplate)
(Flag PathTemplate -> ConfigFlags -> ConfigFlags)
ConfigFlags
forall {b}.
String
-> String
-> [String]
-> String
-> (b -> Flag PathTemplate)
-> (Flag PathTemplate -> b -> b)
-> OptDescr b
reqPathTemplateArgFlag String
"SUFFIX")
, String
-> [String]
-> String
-> (ConfigFlags -> Flag Bool)
-> (Flag Bool -> ConfigFlags -> ConfigFlags)
-> MkOptDescr
(ConfigFlags -> Flag Bool)
(Flag Bool -> ConfigFlags -> ConfigFlags)
ConfigFlags
-> OptionField ConfigFlags
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 = v})
(String
-> String
-> MkOptDescr
(ConfigFlags -> Flag Bool)
(Flag Bool -> ConfigFlags -> ConfigFlags)
ConfigFlags
forall a.
String
-> String -> MkOptDescr (a -> Flag Bool) (Flag Bool -> a -> a) a
boolOpt [] [])
, String
-> [String]
-> String
-> (ConfigFlags -> Flag Bool)
-> (Flag Bool -> ConfigFlags -> ConfigFlags)
-> MkOptDescr
(ConfigFlags -> Flag Bool)
(Flag Bool -> ConfigFlags -> ConfigFlags)
ConfigFlags
-> OptionField ConfigFlags
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 = v})
(String
-> String
-> MkOptDescr
(ConfigFlags -> Flag Bool)
(Flag Bool -> ConfigFlags -> ConfigFlags)
ConfigFlags
forall a.
String
-> String -> MkOptDescr (a -> Flag Bool) (Flag Bool -> a -> a) a
boolOpt String
"p" [])
, String
-> [String]
-> String
-> (ConfigFlags -> Flag Bool)
-> (Flag Bool -> ConfigFlags -> ConfigFlags)
-> MkOptDescr
(ConfigFlags -> Flag Bool)
(Flag Bool -> ConfigFlags -> ConfigFlags)
ConfigFlags
-> OptionField ConfigFlags
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 = v})
(String
-> String
-> MkOptDescr
(ConfigFlags -> Flag Bool)
(Flag Bool -> ConfigFlags -> ConfigFlags)
ConfigFlags
forall a.
String
-> String -> MkOptDescr (a -> Flag Bool) (Flag Bool -> a -> a) a
boolOpt [] [])
, String
-> [String]
-> String
-> (ConfigFlags -> Flag Bool)
-> (Flag Bool -> ConfigFlags -> ConfigFlags)
-> MkOptDescr
(ConfigFlags -> Flag Bool)
(Flag Bool -> ConfigFlags -> ConfigFlags)
ConfigFlags
-> OptionField ConfigFlags
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 = v})
(String
-> String
-> MkOptDescr
(ConfigFlags -> Flag Bool)
(Flag Bool -> ConfigFlags -> ConfigFlags)
ConfigFlags
forall a.
String
-> String -> MkOptDescr (a -> Flag Bool) (Flag Bool -> a -> a) a
boolOpt [] [])
, String
-> [String]
-> String
-> (ConfigFlags -> Flag Bool)
-> (Flag Bool -> ConfigFlags -> ConfigFlags)
-> MkOptDescr
(ConfigFlags -> Flag Bool)
(Flag Bool -> ConfigFlags -> ConfigFlags)
ConfigFlags
-> OptionField ConfigFlags
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 = v})
(String
-> String
-> MkOptDescr
(ConfigFlags -> Flag Bool)
(Flag Bool -> ConfigFlags -> ConfigFlags)
ConfigFlags
forall a.
String
-> String -> MkOptDescr (a -> Flag Bool) (Flag Bool -> a -> a) a
boolOpt [] [])
, String
-> [String]
-> String
-> (ConfigFlags -> Flag Bool)
-> (Flag Bool -> ConfigFlags -> ConfigFlags)
-> MkOptDescr
(ConfigFlags -> Flag Bool)
(Flag Bool -> ConfigFlags -> ConfigFlags)
ConfigFlags
-> OptionField ConfigFlags
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 = v})
(String
-> String
-> MkOptDescr
(ConfigFlags -> Flag Bool)
(Flag Bool -> ConfigFlags -> ConfigFlags)
ConfigFlags
forall a.
String
-> String -> MkOptDescr (a -> Flag Bool) (Flag Bool -> a -> a) a
boolOpt [] [])
, String
-> [String]
-> String
-> (ConfigFlags -> Flag Bool)
-> (Flag Bool -> ConfigFlags -> ConfigFlags)
-> MkOptDescr
(ConfigFlags -> Flag Bool)
(Flag Bool -> ConfigFlags -> ConfigFlags)
ConfigFlags
-> OptionField ConfigFlags
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 = v})
(String
-> String
-> MkOptDescr
(ConfigFlags -> Flag Bool)
(Flag Bool -> ConfigFlags -> ConfigFlags)
ConfigFlags
forall a.
String
-> String -> MkOptDescr (a -> Flag Bool) (Flag Bool -> a -> a) a
boolOpt [] [])
, String
-> [String]
-> String
-> (ConfigFlags -> Flag Bool)
-> (Flag Bool -> ConfigFlags -> ConfigFlags)
-> MkOptDescr
(ConfigFlags -> Flag Bool)
(Flag Bool -> ConfigFlags -> ConfigFlags)
ConfigFlags
-> OptionField ConfigFlags
forall get set a.
String
-> [String]
-> String
-> get
-> set
-> MkOptDescr get set a
-> OptionField a
option
String
""
[String
"profiling-shared"]
String
"Build profiling shared libraries"
ConfigFlags -> Flag Bool
configProfShared
(\Flag Bool
v ConfigFlags
flags -> ConfigFlags
flags{configProfShared = v})
(String
-> String
-> MkOptDescr
(ConfigFlags -> Flag Bool)
(Flag Bool -> ConfigFlags -> ConfigFlags)
ConfigFlags
forall a.
String
-> String -> MkOptDescr (a -> Flag Bool) (Flag Bool -> a -> a) a
boolOpt [] [])
, String
-> [String]
-> String
-> (ConfigFlags -> Flag Bool)
-> (Flag Bool -> ConfigFlags -> ConfigFlags)
-> MkOptDescr
(ConfigFlags -> Flag Bool)
(Flag Bool -> ConfigFlags -> ConfigFlags)
ConfigFlags
-> OptionField ConfigFlags
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 = v})
(String
-> String
-> MkOptDescr
(ConfigFlags -> Flag Bool)
(Flag Bool -> ConfigFlags -> ConfigFlags)
ConfigFlags
forall a.
String
-> String -> MkOptDescr (a -> Flag Bool) (Flag Bool -> a -> a) a
boolOpt [] [])
, String
-> [String]
-> String
-> (ConfigFlags -> Flag ProfDetailLevel)
-> (Flag ProfDetailLevel -> ConfigFlags -> ConfigFlags)
-> MkOptDescr
(ConfigFlags -> Flag ProfDetailLevel)
(Flag ProfDetailLevel -> ConfigFlags -> ConfigFlags)
ConfigFlags
-> OptionField ConfigFlags
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, "
String -> ShowS
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 = v})
( String
-> (String -> Flag ProfDetailLevel)
-> (Flag ProfDetailLevel -> [String])
-> MkOptDescr
(ConfigFlags -> Flag ProfDetailLevel)
(Flag ProfDetailLevel -> ConfigFlags -> ConfigFlags)
ConfigFlags
forall b a.
Monoid b =>
String
-> (String -> b)
-> (b -> [String])
-> MkOptDescr (a -> b) (b -> a -> a) a
reqArg'
String
"level"
(ProfDetailLevel -> Flag ProfDetailLevel
forall a. a -> Flag a
Flag (ProfDetailLevel -> Flag ProfDetailLevel)
-> (String -> ProfDetailLevel) -> String -> Flag ProfDetailLevel
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> ProfDetailLevel
flagToProfDetailLevel)
Flag ProfDetailLevel -> [String]
showProfDetailLevelFlag
)
, String
-> [String]
-> String
-> (ConfigFlags -> Flag ProfDetailLevel)
-> (Flag ProfDetailLevel -> ConfigFlags -> ConfigFlags)
-> MkOptDescr
(ConfigFlags -> Flag ProfDetailLevel)
(Flag ProfDetailLevel -> ConfigFlags -> ConfigFlags)
ConfigFlags
-> OptionField ConfigFlags
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 = v})
( String
-> (String -> Flag ProfDetailLevel)
-> (Flag ProfDetailLevel -> [String])
-> MkOptDescr
(ConfigFlags -> Flag ProfDetailLevel)
(Flag ProfDetailLevel -> ConfigFlags -> ConfigFlags)
ConfigFlags
forall b a.
Monoid b =>
String
-> (String -> b)
-> (b -> [String])
-> MkOptDescr (a -> b) (b -> a -> a) a
reqArg'
String
"level"
(ProfDetailLevel -> Flag ProfDetailLevel
forall a. a -> Flag a
Flag (ProfDetailLevel -> Flag ProfDetailLevel)
-> (String -> ProfDetailLevel) -> String -> Flag ProfDetailLevel
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> ProfDetailLevel
flagToProfDetailLevel)
Flag ProfDetailLevel -> [String]
showProfDetailLevelFlag
)
, String
-> (ConfigFlags -> Flag OptimisationLevel)
-> (Flag OptimisationLevel -> ConfigFlags -> ConfigFlags)
-> [(ConfigFlags -> Flag OptimisationLevel)
-> (Flag OptimisationLevel -> ConfigFlags -> ConfigFlags)
-> OptDescr ConfigFlags]
-> OptionField ConfigFlags
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 = v})
[ String
-> (String, Maybe String -> Flag OptimisationLevel)
-> (Flag OptimisationLevel -> [Maybe String])
-> MkOptDescr
(ConfigFlags -> Flag OptimisationLevel)
(Flag OptimisationLevel -> ConfigFlags -> ConfigFlags)
ConfigFlags
forall b a.
Monoid b =>
String
-> (String, Maybe String -> b)
-> (b -> [Maybe String])
-> MkOptDescr (a -> b) (b -> a -> a) a
optArgDef'
String
"n"
(OptimisationLevel -> String
forall a. Show a => a -> String
show OptimisationLevel
NoOptimisation, OptimisationLevel -> Flag OptimisationLevel
forall a. a -> Flag a
Flag (OptimisationLevel -> Flag OptimisationLevel)
-> (Maybe String -> OptimisationLevel)
-> Maybe String
-> Flag OptimisationLevel
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 -> [Maybe String
forall a. Maybe a
Nothing]
Flag OptimisationLevel
MaximumOptimisation -> [String -> Maybe String
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)"
, Flag OptimisationLevel
-> MkOptDescr
(ConfigFlags -> Flag OptimisationLevel)
(Flag OptimisationLevel -> ConfigFlags -> ConfigFlags)
ConfigFlags
forall b a. Eq b => b -> MkOptDescr (a -> b) (b -> a -> a) a
noArg
(OptimisationLevel -> Flag OptimisationLevel
forall a. a -> Flag a
Flag OptimisationLevel
NoOptimisation)
[]
[String
"disable-optimization", String
"disable-optimisation"]
String
"Build without optimization"
]
, String
-> (ConfigFlags -> Flag DebugInfoLevel)
-> (Flag DebugInfoLevel -> ConfigFlags -> ConfigFlags)
-> [(ConfigFlags -> Flag DebugInfoLevel)
-> (Flag DebugInfoLevel -> ConfigFlags -> ConfigFlags)
-> OptDescr ConfigFlags]
-> OptionField ConfigFlags
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 = v})
[ String
-> (Maybe String -> Flag DebugInfoLevel)
-> (Flag DebugInfoLevel -> [Maybe String])
-> MkOptDescr
(ConfigFlags -> Flag DebugInfoLevel)
(Flag DebugInfoLevel -> ConfigFlags -> ConfigFlags)
ConfigFlags
forall b a.
Monoid b =>
String
-> (Maybe String -> b)
-> (b -> [Maybe String])
-> MkOptDescr (a -> b) (b -> a -> a) a
optArg'
String
"n"
(DebugInfoLevel -> Flag DebugInfoLevel
forall a. a -> Flag a
Flag (DebugInfoLevel -> Flag DebugInfoLevel)
-> (Maybe String -> DebugInfoLevel)
-> Maybe String
-> Flag DebugInfoLevel
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 -> [String -> Maybe String
forall a. a -> Maybe a
Just String
"1"]
Flag DebugInfoLevel
NormalDebugInfo -> [Maybe String
forall a. Maybe a
Nothing]
Flag DebugInfoLevel
MaximalDebugInfo -> [String -> Maybe String
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)"
, Flag DebugInfoLevel
-> MkOptDescr
(ConfigFlags -> Flag DebugInfoLevel)
(Flag DebugInfoLevel -> ConfigFlags -> ConfigFlags)
ConfigFlags
forall b a. Eq b => b -> MkOptDescr (a -> b) (b -> a -> a) a
noArg
(DebugInfoLevel -> Flag DebugInfoLevel
forall a. a -> Flag a
Flag DebugInfoLevel
NoDebugInfo)
[]
[String
"disable-debug-info"]
String
"Don't emit debug info"
]
, String
-> (ConfigFlags -> Flag DumpBuildInfo)
-> (Flag DumpBuildInfo -> ConfigFlags -> ConfigFlags)
-> [(ConfigFlags -> Flag DumpBuildInfo)
-> (Flag DumpBuildInfo -> ConfigFlags -> ConfigFlags)
-> OptDescr ConfigFlags]
-> OptionField ConfigFlags
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 = v})
[ Flag DumpBuildInfo
-> MkOptDescr
(ConfigFlags -> Flag DumpBuildInfo)
(Flag DumpBuildInfo -> ConfigFlags -> ConfigFlags)
ConfigFlags
forall b a. Eq b => b -> MkOptDescr (a -> b) (b -> a -> a) a
noArg
(DumpBuildInfo -> Flag DumpBuildInfo
forall a. a -> Flag a
Flag DumpBuildInfo
DumpBuildInfo)
[]
[String
"enable-build-info"]
String
"Enable build information generation during project building"
, Flag DumpBuildInfo
-> MkOptDescr
(ConfigFlags -> Flag DumpBuildInfo)
(Flag DumpBuildInfo -> ConfigFlags -> ConfigFlags)
ConfigFlags
forall b a. Eq b => b -> MkOptDescr (a -> b) (b -> a -> a) a
noArg
(DumpBuildInfo -> Flag DumpBuildInfo
forall a. a -> Flag a
Flag DumpBuildInfo
NoDumpBuildInfo)
[]
[String
"disable-build-info"]
String
"Disable build information generation during project building"
]
, String
-> [String]
-> String
-> (ConfigFlags -> Flag Bool)
-> (Flag Bool -> ConfigFlags -> ConfigFlags)
-> MkOptDescr
(ConfigFlags -> Flag Bool)
(Flag Bool -> ConfigFlags -> ConfigFlags)
ConfigFlags
-> OptionField ConfigFlags
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 = v})
(String
-> String
-> MkOptDescr
(ConfigFlags -> Flag Bool)
(Flag Bool -> ConfigFlags -> ConfigFlags)
ConfigFlags
forall a.
String
-> String -> MkOptDescr (a -> Flag Bool) (Flag Bool -> a -> a) a
boolOpt [] [])
, String
-> [String]
-> String
-> (ConfigFlags -> Flag Bool)
-> (Flag Bool -> ConfigFlags -> ConfigFlags)
-> MkOptDescr
(ConfigFlags -> Flag Bool)
(Flag Bool -> ConfigFlags -> ConfigFlags)
ConfigFlags
-> OptionField ConfigFlags
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 = v})
(String
-> String
-> MkOptDescr
(ConfigFlags -> Flag Bool)
(Flag Bool -> ConfigFlags -> ConfigFlags)
ConfigFlags
forall a.
String
-> String -> MkOptDescr (a -> Flag Bool) (Flag Bool -> a -> a) a
boolOpt [] [])
, String
-> [String]
-> String
-> (ConfigFlags -> Flag Bool)
-> (Flag Bool -> ConfigFlags -> ConfigFlags)
-> MkOptDescr
(ConfigFlags -> Flag Bool)
(Flag Bool -> ConfigFlags -> ConfigFlags)
ConfigFlags
-> OptionField ConfigFlags
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 = v})
(String
-> String
-> MkOptDescr
(ConfigFlags -> Flag Bool)
(Flag Bool -> ConfigFlags -> ConfigFlags)
ConfigFlags
forall a.
String
-> String -> MkOptDescr (a -> Flag Bool) (Flag Bool -> a -> a) a
boolOpt [] [])
, String
-> [String]
-> String
-> (ConfigFlags -> Flag Bool)
-> (Flag Bool -> ConfigFlags -> ConfigFlags)
-> MkOptDescr
(ConfigFlags -> Flag Bool)
(Flag Bool -> ConfigFlags -> ConfigFlags)
ConfigFlags
-> OptionField ConfigFlags
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 = v})
(String
-> String
-> MkOptDescr
(ConfigFlags -> Flag Bool)
(Flag Bool -> ConfigFlags -> ConfigFlags)
ConfigFlags
forall a.
String
-> String -> MkOptDescr (a -> Flag Bool) (Flag Bool -> a -> a) a
boolOpt [] [])
, String
-> [String]
-> String
-> (ConfigFlags -> Flag Bool)
-> (Flag Bool -> ConfigFlags -> ConfigFlags)
-> MkOptDescr
(ConfigFlags -> Flag Bool)
(Flag Bool -> ConfigFlags -> ConfigFlags)
ConfigFlags
-> OptionField ConfigFlags
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 = v})
(String
-> String
-> MkOptDescr
(ConfigFlags -> Flag Bool)
(Flag Bool -> ConfigFlags -> ConfigFlags)
ConfigFlags
forall a.
String
-> String -> MkOptDescr (a -> Flag Bool) (Flag Bool -> a -> a) a
boolOpt [] [])
, String
-> [String]
-> String
-> (ConfigFlags -> [String])
-> ([String] -> ConfigFlags -> ConfigFlags)
-> MkOptDescr
(ConfigFlags -> [String])
([String] -> ConfigFlags -> ConfigFlags)
ConfigFlags
-> OptionField ConfigFlags
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 = v})
(String
-> (String -> [String])
-> ([String] -> [String])
-> MkOptDescr
(ConfigFlags -> [String])
([String] -> ConfigFlags -> ConfigFlags)
ConfigFlags
forall b a.
Monoid b =>
String
-> (String -> b)
-> (b -> [String])
-> MkOptDescr (a -> b) (b -> a -> a) a
reqArg' String
"OPT" (\String
x -> [String
x]) [String] -> [String]
forall a. a -> a
id)
, String
-> [String]
-> String
-> (ConfigFlags -> Flag Bool)
-> (Flag Bool -> ConfigFlags -> ConfigFlags)
-> MkOptDescr
(ConfigFlags -> Flag Bool)
(Flag Bool -> ConfigFlags -> ConfigFlags)
ConfigFlags
-> OptionField ConfigFlags
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 = v})
((String, [String])
-> (String, [String])
-> MkOptDescr
(ConfigFlags -> Flag Bool)
(Flag Bool -> ConfigFlags -> ConfigFlags)
ConfigFlags
forall a.
(String, [String])
-> (String, [String])
-> MkOptDescr (a -> Flag Bool) (Flag Bool -> a -> a) a
boolOpt' ([], [String
"user"]) ([], [String
"global"]))
, String
-> [String]
-> String
-> (ConfigFlags -> [Maybe PackageDB])
-> ([Maybe PackageDB] -> ConfigFlags -> ConfigFlags)
-> MkOptDescr
(ConfigFlags -> [Maybe PackageDB])
([Maybe PackageDB] -> ConfigFlags -> ConfigFlags)
ConfigFlags
-> OptionField ConfigFlags
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"
String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
" databases used (to satisfy dependencies and register into)."
String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
" May be a specific file, 'global' or 'user'. The initial list"
String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
" is ['global'], ['global', 'user'], or ['global', $sandbox],"
String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
" depending on context. Use 'clear' to reset the list to empty."
String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
" See the user guide for details."
)
ConfigFlags -> [Maybe PackageDB]
configPackageDBs
(\[Maybe PackageDB]
v ConfigFlags
flags -> ConfigFlags
flags{configPackageDBs = v})
(String
-> (String -> [Maybe PackageDB])
-> ([Maybe PackageDB] -> [String])
-> MkOptDescr
(ConfigFlags -> [Maybe PackageDB])
([Maybe PackageDB] -> ConfigFlags -> ConfigFlags)
ConfigFlags
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)
, String
-> [String]
-> String
-> (ConfigFlags -> FlagAssignment)
-> (FlagAssignment -> ConfigFlags -> ConfigFlags)
-> MkOptDescr
(ConfigFlags -> FlagAssignment)
(FlagAssignment -> ConfigFlags -> ConfigFlags)
ConfigFlags
-> OptionField ConfigFlags
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 = v})
( String
-> ReadE FlagAssignment
-> (FlagAssignment -> [String])
-> MkOptDescr
(ConfigFlags -> FlagAssignment)
(FlagAssignment -> ConfigFlags -> ConfigFlags)
ConfigFlags
forall b a.
Monoid b =>
String
-> ReadE b
-> (b -> [String])
-> MkOptDescr (a -> b) (b -> a -> a) a
reqArg
String
"FLAGS"
(ShowS -> ParsecParser FlagAssignment -> ReadE FlagAssignment
forall a. ShowS -> ParsecParser a -> ReadE a
parsecToReadE (\String
err -> String
"Invalid flag assignment: " String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
err) ParsecParser FlagAssignment
forall (m :: * -> *). CabalParsing m => m FlagAssignment
legacyParsecFlagAssignment)
FlagAssignment -> [String]
legacyShowFlagAssignment'
)
, String
-> [String]
-> String
-> (ConfigFlags -> [SymbolicPath Pkg ('Dir Include)])
-> ([SymbolicPath Pkg ('Dir Include)]
-> ConfigFlags -> ConfigFlags)
-> MkOptDescr
(ConfigFlags -> [SymbolicPath Pkg ('Dir Include)])
([SymbolicPath Pkg ('Dir Include)] -> ConfigFlags -> ConfigFlags)
ConfigFlags
-> OptionField ConfigFlags
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 -> [SymbolicPath Pkg ('Dir Include)]
configExtraIncludeDirs
(\[SymbolicPath Pkg ('Dir Include)]
v ConfigFlags
flags -> ConfigFlags
flags{configExtraIncludeDirs = v})
(String
-> (String -> [SymbolicPath Pkg ('Dir Include)])
-> ([SymbolicPath Pkg ('Dir Include)] -> [String])
-> MkOptDescr
(ConfigFlags -> [SymbolicPath Pkg ('Dir Include)])
([SymbolicPath Pkg ('Dir Include)] -> ConfigFlags -> ConfigFlags)
ConfigFlags
forall b a.
Monoid b =>
String
-> (String -> b)
-> (b -> [String])
-> MkOptDescr (a -> b) (b -> a -> a) a
reqArg' String
"PATH" (\String
x -> [String -> SymbolicPath Pkg ('Dir Include)
forall from (to :: FileOrDir). String -> SymbolicPath from to
makeSymbolicPath String
x]) ((SymbolicPath Pkg ('Dir Include) -> String)
-> [SymbolicPath Pkg ('Dir Include)] -> [String]
forall a b. (a -> b) -> [a] -> [b]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap SymbolicPath Pkg ('Dir Include) -> String
forall (allowAbsolute :: AllowAbsolute) from (to :: FileOrDir).
SymbolicPathX allowAbsolute from to -> String
getSymbolicPath))
, String
-> [String]
-> String
-> (ConfigFlags -> Flag Bool)
-> (Flag Bool -> ConfigFlags -> ConfigFlags)
-> MkOptDescr
(ConfigFlags -> Flag Bool)
(Flag Bool -> ConfigFlags -> ConfigFlags)
ConfigFlags
-> OptionField ConfigFlags
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 = v})
(String
-> String
-> MkOptDescr
(ConfigFlags -> Flag Bool)
(Flag Bool -> ConfigFlags -> ConfigFlags)
ConfigFlags
forall a.
String
-> String -> MkOptDescr (a -> Flag Bool) (Flag Bool -> a -> a) a
boolOpt [] [])
, String
-> [String]
-> String
-> (ConfigFlags -> Flag String)
-> (Flag String -> ConfigFlags -> ConfigFlags)
-> MkOptDescr
(ConfigFlags -> Flag String)
(Flag String -> ConfigFlags -> ConfigFlags)
ConfigFlags
-> OptionField ConfigFlags
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 = v})
(String
-> MkOptDescr
(ConfigFlags -> Flag String)
(Flag String -> ConfigFlags -> ConfigFlags)
ConfigFlags
forall b.
String
-> String
-> [String]
-> String
-> (b -> Flag String)
-> (Flag String -> b -> b)
-> OptDescr b
reqArgFlag String
"IPID")
, String
-> [String]
-> String
-> (ConfigFlags -> Flag String)
-> (Flag String -> ConfigFlags -> ConfigFlags)
-> MkOptDescr
(ConfigFlags -> Flag String)
(Flag String -> ConfigFlags -> ConfigFlags)
ConfigFlags
-> OptionField ConfigFlags
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"
((ComponentId -> String) -> Flag ComponentId -> Flag String
forall a b. (a -> b) -> Flag a -> Flag b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ComponentId -> String
forall a. Pretty a => a -> String
prettyShow (Flag ComponentId -> Flag String)
-> (ConfigFlags -> Flag ComponentId) -> ConfigFlags -> Flag String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ConfigFlags -> Flag ComponentId
configCID)
(\Flag String
v ConfigFlags
flags -> ConfigFlags
flags{configCID = fmap mkComponentId v})
(String
-> MkOptDescr
(ConfigFlags -> Flag String)
(Flag String -> ConfigFlags -> ConfigFlags)
ConfigFlags
forall b.
String
-> String
-> [String]
-> String
-> (b -> Flag String)
-> (Flag String -> b -> b)
-> OptDescr b
reqArgFlag String
"CID")
, String
-> [String]
-> String
-> (ConfigFlags -> [SymbolicPath Pkg ('Dir Lib)])
-> ([SymbolicPath Pkg ('Dir Lib)] -> ConfigFlags -> ConfigFlags)
-> MkOptDescr
(ConfigFlags -> [SymbolicPath Pkg ('Dir Lib)])
([SymbolicPath Pkg ('Dir Lib)] -> ConfigFlags -> ConfigFlags)
ConfigFlags
-> OptionField ConfigFlags
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 -> [SymbolicPath Pkg ('Dir Lib)]
configExtraLibDirs
(\[SymbolicPath Pkg ('Dir Lib)]
v ConfigFlags
flags -> ConfigFlags
flags{configExtraLibDirs = v})
(String
-> (String -> [SymbolicPath Pkg ('Dir Lib)])
-> ([SymbolicPath Pkg ('Dir Lib)] -> [String])
-> MkOptDescr
(ConfigFlags -> [SymbolicPath Pkg ('Dir Lib)])
([SymbolicPath Pkg ('Dir Lib)] -> ConfigFlags -> ConfigFlags)
ConfigFlags
forall b a.
Monoid b =>
String
-> (String -> b)
-> (b -> [String])
-> MkOptDescr (a -> b) (b -> a -> a) a
reqArg' String
"PATH" (\String
x -> [String -> SymbolicPath Pkg ('Dir Lib)
forall from (to :: FileOrDir). String -> SymbolicPath from to
makeSymbolicPath String
x]) ((SymbolicPath Pkg ('Dir Lib) -> String)
-> [SymbolicPath Pkg ('Dir Lib)] -> [String]
forall a b. (a -> b) -> [a] -> [b]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap SymbolicPath Pkg ('Dir Lib) -> String
forall (allowAbsolute :: AllowAbsolute) from (to :: FileOrDir).
SymbolicPathX allowAbsolute from to -> String
getSymbolicPath))
, String
-> [String]
-> String
-> (ConfigFlags -> [SymbolicPath Pkg ('Dir Lib)])
-> ([SymbolicPath Pkg ('Dir Lib)] -> ConfigFlags -> ConfigFlags)
-> MkOptDescr
(ConfigFlags -> [SymbolicPath Pkg ('Dir Lib)])
([SymbolicPath Pkg ('Dir Lib)] -> ConfigFlags -> ConfigFlags)
ConfigFlags
-> OptionField ConfigFlags
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 -> [SymbolicPath Pkg ('Dir Lib)]
configExtraLibDirsStatic
(\[SymbolicPath Pkg ('Dir Lib)]
v ConfigFlags
flags -> ConfigFlags
flags{configExtraLibDirsStatic = v})
(String
-> (String -> [SymbolicPath Pkg ('Dir Lib)])
-> ([SymbolicPath Pkg ('Dir Lib)] -> [String])
-> MkOptDescr
(ConfigFlags -> [SymbolicPath Pkg ('Dir Lib)])
([SymbolicPath Pkg ('Dir Lib)] -> ConfigFlags -> ConfigFlags)
ConfigFlags
forall b a.
Monoid b =>
String
-> (String -> b)
-> (b -> [String])
-> MkOptDescr (a -> b) (b -> a -> a) a
reqArg' String
"PATH" (\String
x -> [String -> SymbolicPath Pkg ('Dir Lib)
forall from (to :: FileOrDir). String -> SymbolicPath from to
makeSymbolicPath String
x]) ((SymbolicPath Pkg ('Dir Lib) -> String)
-> [SymbolicPath Pkg ('Dir Lib)] -> [String]
forall a b. (a -> b) -> [a] -> [b]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap SymbolicPath Pkg ('Dir Lib) -> String
forall (allowAbsolute :: AllowAbsolute) from (to :: FileOrDir).
SymbolicPathX allowAbsolute from to -> String
getSymbolicPath))
, String
-> [String]
-> String
-> (ConfigFlags -> [SymbolicPath Pkg ('Dir Framework)])
-> ([SymbolicPath Pkg ('Dir Framework)]
-> ConfigFlags -> ConfigFlags)
-> MkOptDescr
(ConfigFlags -> [SymbolicPath Pkg ('Dir Framework)])
([SymbolicPath Pkg ('Dir Framework)] -> ConfigFlags -> ConfigFlags)
ConfigFlags
-> OptionField ConfigFlags
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 -> [SymbolicPath Pkg ('Dir Framework)]
configExtraFrameworkDirs
(\[SymbolicPath Pkg ('Dir Framework)]
v ConfigFlags
flags -> ConfigFlags
flags{configExtraFrameworkDirs = v})
(String
-> (String -> [SymbolicPath Pkg ('Dir Framework)])
-> ([SymbolicPath Pkg ('Dir Framework)] -> [String])
-> MkOptDescr
(ConfigFlags -> [SymbolicPath Pkg ('Dir Framework)])
([SymbolicPath Pkg ('Dir Framework)] -> ConfigFlags -> ConfigFlags)
ConfigFlags
forall b a.
Monoid b =>
String
-> (String -> b)
-> (b -> [String])
-> MkOptDescr (a -> b) (b -> a -> a) a
reqArg' String
"PATH" (\String
x -> [String -> SymbolicPath Pkg ('Dir Framework)
forall from (to :: FileOrDir). String -> SymbolicPath from to
makeSymbolicPath String
x]) ((SymbolicPath Pkg ('Dir Framework) -> String)
-> [SymbolicPath Pkg ('Dir Framework)] -> [String]
forall a b. (a -> b) -> [a] -> [b]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap SymbolicPath Pkg ('Dir Framework) -> String
forall (allowAbsolute :: AllowAbsolute) from (to :: FileOrDir).
SymbolicPathX allowAbsolute from to -> String
getSymbolicPath))
, String
-> [String]
-> String
-> (ConfigFlags -> NubList String)
-> (NubList String -> ConfigFlags -> ConfigFlags)
-> MkOptDescr
(ConfigFlags -> NubList String)
(NubList String -> ConfigFlags -> ConfigFlags)
ConfigFlags
-> OptionField ConfigFlags
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 = v})
(String
-> (String -> NubList String)
-> (NubList String -> [String])
-> MkOptDescr
(ConfigFlags -> NubList String)
(NubList String -> ConfigFlags -> ConfigFlags)
ConfigFlags
forall b a.
Monoid b =>
String
-> (String -> b)
-> (b -> [String])
-> MkOptDescr (a -> b) (b -> a -> a) a
reqArg' String
"PATH" (\String
x -> [String] -> NubList String
forall a. Ord a => [a] -> NubList a
toNubList [String
x]) NubList String -> [String]
forall a. NubList a -> [a]
fromNubList)
, String
-> [String]
-> String
-> (ConfigFlags -> [PackageVersionConstraint])
-> ([PackageVersionConstraint] -> ConfigFlags -> ConfigFlags)
-> MkOptDescr
(ConfigFlags -> [PackageVersionConstraint])
([PackageVersionConstraint] -> ConfigFlags -> ConfigFlags)
ConfigFlags
-> OptionField ConfigFlags
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 = v})
( String
-> ReadE [PackageVersionConstraint]
-> ([PackageVersionConstraint] -> [String])
-> MkOptDescr
(ConfigFlags -> [PackageVersionConstraint])
([PackageVersionConstraint] -> ConfigFlags -> ConfigFlags)
ConfigFlags
forall b a.
Monoid b =>
String
-> ReadE b
-> (b -> [String])
-> MkOptDescr (a -> b) (b -> a -> a) a
reqArg
String
"DEPENDENCY"
(ShowS
-> ParsecParser [PackageVersionConstraint]
-> ReadE [PackageVersionConstraint]
forall a. ShowS -> ParsecParser a -> ReadE a
parsecToReadE (String -> ShowS
forall a b. a -> b -> a
const String
"dependency expected") ((\PackageVersionConstraint
x -> [PackageVersionConstraint
x]) (PackageVersionConstraint -> [PackageVersionConstraint])
-> ParsecParser PackageVersionConstraint
-> ParsecParser [PackageVersionConstraint]
forall a b. (a -> b) -> ParsecParser a -> ParsecParser b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
`fmap` ParsecParser PackageVersionConstraint
forall a (m :: * -> *). (Parsec a, CabalParsing m) => m a
forall (m :: * -> *). CabalParsing m => m PackageVersionConstraint
parsec))
((PackageVersionConstraint -> String)
-> [PackageVersionConstraint] -> [String]
forall a b. (a -> b) -> [a] -> [b]
map PackageVersionConstraint -> String
forall a. Pretty a => a -> String
prettyShow)
)
, String
-> [String]
-> String
-> (ConfigFlags -> [GivenComponent])
-> ([GivenComponent] -> ConfigFlags -> ConfigFlags)
-> MkOptDescr
(ConfigFlags -> [GivenComponent])
([GivenComponent] -> ConfigFlags -> ConfigFlags)
ConfigFlags
-> OptionField ConfigFlags
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 = v})
( String
-> ReadE [GivenComponent]
-> ([GivenComponent] -> [String])
-> MkOptDescr
(ConfigFlags -> [GivenComponent])
([GivenComponent] -> ConfigFlags -> ConfigFlags)
ConfigFlags
forall b a.
Monoid b =>
String
-> ReadE b
-> (b -> [String])
-> MkOptDescr (a -> b) (b -> a -> a) a
reqArg
String
"NAME[:COMPONENT_NAME]=CID"
(ShowS -> ParsecParser [GivenComponent] -> ReadE [GivenComponent]
forall a. ShowS -> ParsecParser a -> ReadE a
parsecToReadE (String -> ShowS
forall a b. a -> b -> a
const String
"dependency expected") ((\GivenComponent
x -> [GivenComponent
x]) (GivenComponent -> [GivenComponent])
-> ParsecParser GivenComponent -> ParsecParser [GivenComponent]
forall a b. (a -> b) -> ParsecParser a -> ParsecParser b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
`fmap` ParsecParser GivenComponent
parsecGivenComponent))
((GivenComponent -> String) -> [GivenComponent] -> [String]
forall a b. (a -> b) -> [a] -> [b]
map GivenComponent -> String
prettyGivenComponent)
)
, String
-> [String]
-> String
-> (ConfigFlags -> [PromisedComponent])
-> ([PromisedComponent] -> ConfigFlags -> ConfigFlags)
-> MkOptDescr
(ConfigFlags -> [PromisedComponent])
([PromisedComponent] -> ConfigFlags -> ConfigFlags)
ConfigFlags
-> OptionField ConfigFlags
forall get set a.
String
-> [String]
-> String
-> get
-> set
-> MkOptDescr get set a
-> OptionField a
option
String
""
[String
"promised-dependency"]
String
"A list of promised dependencies. E.g., --promised-dependency=\"void-0.5.8=void-0.5.8-177d5cdf20962d0581fe2e4932a6c309\""
ConfigFlags -> [PromisedComponent]
configPromisedDependencies
(\[PromisedComponent]
v ConfigFlags
flags -> ConfigFlags
flags{configPromisedDependencies = v})
( String
-> ReadE [PromisedComponent]
-> ([PromisedComponent] -> [String])
-> MkOptDescr
(ConfigFlags -> [PromisedComponent])
([PromisedComponent] -> ConfigFlags -> ConfigFlags)
ConfigFlags
forall b a.
Monoid b =>
String
-> ReadE b
-> (b -> [String])
-> MkOptDescr (a -> b) (b -> a -> a) a
reqArg
String
"NAME-VER[:COMPONENT_NAME]=CID"
(ShowS
-> ParsecParser [PromisedComponent] -> ReadE [PromisedComponent]
forall a. ShowS -> ParsecParser a -> ReadE a
parsecToReadE (String -> ShowS
forall a b. a -> b -> a
const String
"dependency expected") ((\PromisedComponent
x -> [PromisedComponent
x]) (PromisedComponent -> [PromisedComponent])
-> ParsecParser PromisedComponent
-> ParsecParser [PromisedComponent]
forall a b. (a -> b) -> ParsecParser a -> ParsecParser b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
`fmap` ParsecParser PromisedComponent
parsecPromisedComponent))
((PromisedComponent -> String) -> [PromisedComponent] -> [String]
forall a b. (a -> b) -> [a] -> [b]
map PromisedComponent -> String
prettyPromisedComponent)
)
, String
-> [String]
-> String
-> (ConfigFlags -> [(ModuleName, Module)])
-> ([(ModuleName, Module)] -> ConfigFlags -> ConfigFlags)
-> MkOptDescr
(ConfigFlags -> [(ModuleName, Module)])
([(ModuleName, Module)] -> ConfigFlags -> ConfigFlags)
ConfigFlags
-> OptionField ConfigFlags
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 = v})
( String
-> ReadE [(ModuleName, Module)]
-> ([(ModuleName, Module)] -> [String])
-> MkOptDescr
(ConfigFlags -> [(ModuleName, Module)])
([(ModuleName, Module)] -> ConfigFlags -> ConfigFlags)
ConfigFlags
forall b a.
Monoid b =>
String
-> ReadE b
-> (b -> [String])
-> MkOptDescr (a -> b) (b -> a -> a) a
reqArg
String
"NAME=MOD"
(ShowS
-> ParsecParser [(ModuleName, Module)]
-> ReadE [(ModuleName, Module)]
forall a. ShowS -> ParsecParser a -> ReadE a
parsecToReadE (String
"Cannot parse module substitution: " String -> ShowS
forall a. [a] -> [a] -> [a]
++) (((ModuleName, Module) -> [(ModuleName, Module)])
-> ParsecParser (ModuleName, Module)
-> ParsecParser [(ModuleName, Module)]
forall a b. (a -> b) -> ParsecParser a -> ParsecParser b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ((ModuleName, Module)
-> [(ModuleName, Module)] -> [(ModuleName, Module)]
forall a. a -> [a] -> [a]
: []) ParsecParser (ModuleName, Module)
parsecModSubstEntry))
(((ModuleName, Module) -> String)
-> [(ModuleName, Module)] -> [String]
forall a b. (a -> b) -> [a] -> [b]
map (Style -> Doc -> String
Disp.renderStyle Style
defaultStyle (Doc -> String)
-> ((ModuleName, Module) -> Doc) -> (ModuleName, Module) -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (ModuleName, Module) -> Doc
dispModSubstEntry))
)
, String
-> [String]
-> String
-> (ConfigFlags -> Flag Bool)
-> (Flag Bool -> ConfigFlags -> ConfigFlags)
-> MkOptDescr
(ConfigFlags -> Flag Bool)
(Flag Bool -> ConfigFlags -> ConfigFlags)
ConfigFlags
-> OptionField ConfigFlags
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 = v})
(String
-> String
-> MkOptDescr
(ConfigFlags -> Flag Bool)
(Flag Bool -> ConfigFlags -> ConfigFlags)
ConfigFlags
forall a.
String
-> String -> MkOptDescr (a -> Flag Bool) (Flag Bool -> a -> a) a
boolOpt [] [])
, String
-> [String]
-> String
-> (ConfigFlags -> Flag Bool)
-> (Flag Bool -> ConfigFlags -> ConfigFlags)
-> MkOptDescr
(ConfigFlags -> Flag Bool)
(Flag Bool -> ConfigFlags -> ConfigFlags)
ConfigFlags
-> OptionField ConfigFlags
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 = v})
(String
-> String
-> MkOptDescr
(ConfigFlags -> Flag Bool)
(Flag Bool -> ConfigFlags -> ConfigFlags)
ConfigFlags
forall a.
String
-> String -> MkOptDescr (a -> Flag Bool) (Flag Bool -> a -> a) a
boolOpt [] [])
, String
-> [String]
-> String
-> (ConfigFlags -> Flag Bool)
-> (Flag Bool -> ConfigFlags -> ConfigFlags)
-> MkOptDescr
(ConfigFlags -> Flag Bool)
(Flag Bool -> ConfigFlags -> ConfigFlags)
ConfigFlags
-> OptionField ConfigFlags
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 = v})
(String
-> String
-> MkOptDescr
(ConfigFlags -> Flag Bool)
(Flag Bool -> ConfigFlags -> ConfigFlags)
ConfigFlags
forall a.
String
-> String -> MkOptDescr (a -> Flag Bool) (Flag Bool -> a -> a) a
boolOpt [] [])
, String
-> [String]
-> String
-> (ConfigFlags -> Flag Bool)
-> (Flag Bool -> ConfigFlags -> ConfigFlags)
-> MkOptDescr
(ConfigFlags -> Flag Bool)
(Flag Bool -> ConfigFlags -> ConfigFlags)
ConfigFlags
-> OptionField ConfigFlags
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 = v})
MkOptDescr
(ConfigFlags -> Flag Bool)
(Flag Bool -> ConfigFlags -> ConfigFlags)
ConfigFlags
forall a. MkOptDescr (a -> Flag Bool) (Flag Bool -> a -> a) a
trueArg
, String
-> [String]
-> String
-> (ConfigFlags -> Flag Bool)
-> (Flag Bool -> ConfigFlags -> ConfigFlags)
-> MkOptDescr
(ConfigFlags -> Flag Bool)
(Flag Bool -> ConfigFlags -> ConfigFlags)
ConfigFlags
-> OptionField ConfigFlags
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 = v})
(String
-> String
-> MkOptDescr
(ConfigFlags -> Flag Bool)
(Flag Bool -> ConfigFlags -> ConfigFlags)
ConfigFlags
forall a.
String
-> String -> MkOptDescr (a -> Flag Bool) (Flag Bool -> a -> a) a
boolOpt [] [])
, String
-> [String]
-> String
-> (ConfigFlags -> Flag Bool)
-> (Flag Bool -> ConfigFlags -> ConfigFlags)
-> MkOptDescr
(ConfigFlags -> Flag Bool)
(Flag Bool -> ConfigFlags -> ConfigFlags)
ConfigFlags
-> OptionField ConfigFlags
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 = v})
(String
-> String
-> MkOptDescr
(ConfigFlags -> Flag Bool)
(Flag Bool -> ConfigFlags -> ConfigFlags)
ConfigFlags
forall a.
String
-> String -> MkOptDescr (a -> Flag Bool) (Flag Bool -> a -> a) a
boolOpt [] [])
, String
-> [String]
-> String
-> (ConfigFlags -> Flag Bool)
-> (Flag Bool -> ConfigFlags -> ConfigFlags)
-> MkOptDescr
(ConfigFlags -> Flag Bool)
(Flag Bool -> ConfigFlags -> ConfigFlags)
ConfigFlags
-> OptionField ConfigFlags
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 = v})
((String, [String])
-> (String, [String])
-> MkOptDescr
(ConfigFlags -> Flag Bool)
(Flag Bool -> ConfigFlags -> ConfigFlags)
ConfigFlags
forall a.
(String, [String])
-> (String, [String])
-> MkOptDescr (a -> Flag Bool) (Flag Bool -> a -> a) a
boolOpt' ([], [String
"disable-response-files"]) ([], []))
, String
-> [String]
-> String
-> (ConfigFlags -> Flag Bool)
-> (Flag Bool -> ConfigFlags -> ConfigFlags)
-> MkOptDescr
(ConfigFlags -> Flag Bool)
(Flag Bool -> ConfigFlags -> ConfigFlags)
ConfigFlags
-> OptionField ConfigFlags
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. "
String -> ShowS
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 = v})
MkOptDescr
(ConfigFlags -> Flag Bool)
(Flag Bool -> ConfigFlags -> ConfigFlags)
ConfigFlags
forall a. MkOptDescr (a -> Flag Bool) (Flag Bool -> a -> a) a
trueArg
, String
-> [String]
-> String
-> (ConfigFlags -> Flag [UnitId])
-> (Flag [UnitId] -> ConfigFlags -> ConfigFlags)
-> MkOptDescr
(ConfigFlags -> Flag [UnitId])
(Flag [UnitId] -> ConfigFlags -> ConfigFlags)
ConfigFlags
-> OptionField ConfigFlags
forall get set a.
String
-> [String]
-> String
-> get
-> set
-> MkOptDescr get set a
-> OptionField a
option
String
""
[String
"coverage-for"]
String
"A list of unit-ids of libraries to include in the Haskell Program Coverage report."
ConfigFlags -> Flag [UnitId]
configCoverageFor
( \Flag [UnitId]
v ConfigFlags
flags ->
ConfigFlags
flags
{ configCoverageFor =
mergeListFlag (configCoverageFor flags) v
}
)
( String
-> (String -> Flag [UnitId])
-> (Flag [UnitId] -> [String])
-> MkOptDescr
(ConfigFlags -> Flag [UnitId])
(Flag [UnitId] -> ConfigFlags -> ConfigFlags)
ConfigFlags
forall b a.
Monoid b =>
String
-> (String -> b)
-> (b -> [String])
-> MkOptDescr (a -> b) (b -> a -> a) a
reqArg'
String
"UNITID"
([UnitId] -> Flag [UnitId]
forall a. a -> Flag a
Flag ([UnitId] -> Flag [UnitId])
-> (String -> [UnitId]) -> String -> Flag [UnitId]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (UnitId -> [UnitId] -> [UnitId]
forall a. a -> [a] -> [a]
: []) (UnitId -> [UnitId]) -> (String -> UnitId) -> String -> [UnitId]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> UnitId
forall a. IsString a => String -> a
fromString)
((UnitId -> String) -> [UnitId] -> [String]
forall a b. (a -> b) -> [a] -> [b]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap UnitId -> String
forall a. Pretty a => a -> String
prettyShow ([UnitId] -> [String])
-> (Flag [UnitId] -> [UnitId]) -> Flag [UnitId] -> [String]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [UnitId] -> Flag [UnitId] -> [UnitId]
forall a. a -> Flag a -> a
fromFlagOrDefault [])
)
, String
-> [String]
-> String
-> (ConfigFlags -> Flag Bool)
-> (Flag Bool -> ConfigFlags -> ConfigFlags)
-> MkOptDescr
(ConfigFlags -> Flag Bool)
(Flag Bool -> ConfigFlags -> ConfigFlags)
ConfigFlags
-> OptionField ConfigFlags
forall get set a.
String
-> [String]
-> String
-> get
-> set
-> MkOptDescr get set a
-> OptionField a
option
String
""
[String
"ignore-build-tools"]
( String
"Ignore build tool dependencies. "
String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
"If set, declared build tools needn't be found for compilation to proceed."
)
ConfigFlags -> Flag Bool
configIgnoreBuildTools
(\Flag Bool
v ConfigFlags
flags -> ConfigFlags
flags{configIgnoreBuildTools = v})
MkOptDescr
(ConfigFlags -> Flag Bool)
(Flag Bool -> ConfigFlags -> ConfigFlags)
ConfigFlags
forall a. MkOptDescr (a -> Flag Bool) (Flag Bool -> a -> a) a
trueArg
]
where
liftInstallDirs :: OptionField (InstallDirs (Flag PathTemplate))
-> OptionField ConfigFlags
liftInstallDirs =
(ConfigFlags -> InstallDirs (Flag PathTemplate))
-> (InstallDirs (Flag PathTemplate) -> ConfigFlags -> ConfigFlags)
-> OptionField (InstallDirs (Flag PathTemplate))
-> OptionField ConfigFlags
forall b a.
(b -> a) -> (a -> b -> b) -> OptionField a -> OptionField b
liftOption ConfigFlags -> InstallDirs (Flag PathTemplate)
configInstallDirs (\InstallDirs (Flag PathTemplate)
v ConfigFlags
flags -> ConfigFlags
flags{configInstallDirs = 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 =
String
-> String
-> [String]
-> String
-> (b -> Flag String)
-> (Flag String -> b -> b)
-> OptDescr b
forall b.
String
-> String
-> [String]
-> String
-> (b -> Flag String)
-> (Flag String -> b -> b)
-> OptDescr b
reqArgFlag
String
title
String
_sf
[String]
_lf
String
d
((PathTemplate -> String) -> Flag PathTemplate -> Flag String
forall a b. (a -> b) -> Flag a -> Flag b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap PathTemplate -> String
fromPathTemplate (Flag PathTemplate -> Flag String)
-> (b -> Flag PathTemplate) -> b -> Flag String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. b -> Flag PathTemplate
get)
(Flag PathTemplate -> b -> b
set (Flag PathTemplate -> b -> b)
-> (Flag String -> Flag PathTemplate) -> Flag String -> b -> b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (String -> PathTemplate) -> Flag String -> Flag PathTemplate
forall a b. (a -> b) -> Flag a -> Flag b
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]
readPackageDb :: String -> Maybe PackageDB
readPackageDb :: String -> Maybe PackageDB
readPackageDb String
"clear" = Maybe PackageDB
forall a. Maybe a
Nothing
readPackageDb String
"global" = PackageDB -> Maybe PackageDB
forall a. a -> Maybe a
Just PackageDB
forall fp. PackageDBX fp
GlobalPackageDB
readPackageDb String
"user" = PackageDB -> Maybe PackageDB
forall a. a -> Maybe a
Just PackageDB
forall fp. PackageDBX fp
UserPackageDB
readPackageDb String
other = PackageDB -> Maybe PackageDB
forall a. a -> Maybe a
Just (SymbolicPathX 'AllowAbsolute Pkg ('Dir PkgDB) -> PackageDB
forall fp. fp -> PackageDBX fp
SpecificPackageDB (String -> SymbolicPathX 'AllowAbsolute Pkg ('Dir PkgDB)
forall from (to :: FileOrDir). String -> SymbolicPath from to
makeSymbolicPath String
other))
showPackageDbList :: [Maybe PackageDB] -> [String]
showPackageDbList :: [Maybe PackageDB] -> [String]
showPackageDbList = (Maybe PackageDB -> String) -> [Maybe PackageDB] -> [String]
forall a b. (a -> b) -> [a] -> [b]
map Maybe PackageDB -> String
showPackageDb
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 SymbolicPathX 'AllowAbsolute Pkg ('Dir PkgDB)
db)) = SymbolicPathX 'AllowAbsolute Pkg ('Dir PkgDB) -> String
forall (allowAbsolute :: AllowAbsolute) from (to :: FileOrDir).
SymbolicPathX allowAbsolute from to -> String
getSymbolicPath SymbolicPathX 'AllowAbsolute Pkg ('Dir PkgDB)
db
showProfDetailLevelFlag :: Flag ProfDetailLevel -> [String]
showProfDetailLevelFlag :: Flag ProfDetailLevel -> [String]
showProfDetailLevelFlag Flag ProfDetailLevel
NoFlag = []
showProfDetailLevelFlag (Flag ProfDetailLevel
dl) = [ProfDetailLevel -> String
showProfDetailLevel ProfDetailLevel
dl]
parsecPromisedComponent :: ParsecParser PromisedComponent
parsecPromisedComponent :: ParsecParser PromisedComponent
parsecPromisedComponent = do
pn <- ParsecParser PackageId
forall a (m :: * -> *). (Parsec a, CabalParsing m) => m a
forall (m :: * -> *). CabalParsing m => m PackageId
parsec
ln <- P.option LMainLibName $ do
_ <- P.char ':'
ucn <- parsec
return $
if unUnqualComponentName ucn == unPackageName (pkgName pn)
then LMainLibName
else LSubLibName ucn
_ <- P.char '='
cid <- parsec
return $ PromisedComponent pn ln cid
prettyPromisedComponent :: PromisedComponent -> String
prettyPromisedComponent :: PromisedComponent -> String
prettyPromisedComponent (PromisedComponent PackageId
pn LibraryName
cn ComponentId
cid) =
PackageId -> String
forall a. Pretty a => a -> String
prettyShow PackageId
pn
String -> ShowS
forall a. [a] -> [a] -> [a]
++ case LibraryName
cn of
LibraryName
LMainLibName -> String
""
LSubLibName UnqualComponentName
n -> String
":" String -> ShowS
forall a. [a] -> [a] -> [a]
++ UnqualComponentName -> String
forall a. Pretty a => a -> String
prettyShow UnqualComponentName
n
String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
"="
String -> ShowS
forall a. [a] -> [a] -> [a]
++ ComponentId -> String
forall a. Pretty a => a -> String
prettyShow ComponentId
cid
parsecGivenComponent :: ParsecParser GivenComponent
parsecGivenComponent :: ParsecParser GivenComponent
parsecGivenComponent = do
pn <- ParsecParser PackageName
forall a (m :: * -> *). (Parsec a, CabalParsing m) => m a
forall (m :: * -> *). CabalParsing m => m PackageName
parsec
ln <- P.option LMainLibName $ do
_ <- P.char ':'
ucn <- parsec
return $
if unUnqualComponentName ucn == unPackageName pn
then LMainLibName
else LSubLibName ucn
_ <- P.char '='
cid <- parsec
return $ GivenComponent pn ln cid
prettyGivenComponent :: GivenComponent -> String
prettyGivenComponent :: GivenComponent -> String
prettyGivenComponent (GivenComponent PackageName
pn LibraryName
cn ComponentId
cid) =
PackageName -> String
forall a. Pretty a => a -> String
prettyShow PackageName
pn
String -> ShowS
forall a. [a] -> [a] -> [a]
++ case LibraryName
cn of
LibraryName
LMainLibName -> String
""
LSubLibName UnqualComponentName
n -> String
":" String -> ShowS
forall a. [a] -> [a] -> [a]
++ UnqualComponentName -> String
forall a. Pretty a => a -> String
prettyShow UnqualComponentName
n
String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
"="
String -> ShowS
forall a. [a] -> [a] -> [a]
++ ComponentId -> String
forall a. Pretty a => a -> String
prettyShow ComponentId
cid
installDirsOptions :: [OptionField (InstallDirs (Flag PathTemplate))]
installDirsOptions :: [OptionField (InstallDirs (Flag PathTemplate))]
installDirsOptions =
[ String
-> [String]
-> String
-> (InstallDirs (Flag PathTemplate) -> Flag PathTemplate)
-> (Flag PathTemplate
-> InstallDirs (Flag PathTemplate)
-> InstallDirs (Flag PathTemplate))
-> MkOptDescr
(InstallDirs (Flag PathTemplate) -> Flag PathTemplate)
(Flag PathTemplate
-> InstallDirs (Flag PathTemplate)
-> InstallDirs (Flag PathTemplate))
(InstallDirs (Flag PathTemplate))
-> OptionField (InstallDirs (Flag PathTemplate))
forall get set a.
String
-> [String]
-> String
-> get
-> set
-> MkOptDescr get set a
-> OptionField a
option
String
""
[String
"prefix"]
String
"bake this prefix in preparation of installation"
InstallDirs (Flag PathTemplate) -> Flag PathTemplate
forall dir. InstallDirs dir -> dir
prefix
(\Flag PathTemplate
v InstallDirs (Flag PathTemplate)
flags -> InstallDirs (Flag PathTemplate)
flags{prefix = v})
MkOptDescr
(InstallDirs (Flag PathTemplate) -> Flag PathTemplate)
(Flag PathTemplate
-> InstallDirs (Flag PathTemplate)
-> InstallDirs (Flag PathTemplate))
(InstallDirs (Flag PathTemplate))
forall {b}.
String
-> [String]
-> String
-> (b -> Flag PathTemplate)
-> (Flag PathTemplate -> b -> b)
-> OptDescr b
installDirArg
, String
-> [String]
-> String
-> (InstallDirs (Flag PathTemplate) -> Flag PathTemplate)
-> (Flag PathTemplate
-> InstallDirs (Flag PathTemplate)
-> InstallDirs (Flag PathTemplate))
-> MkOptDescr
(InstallDirs (Flag PathTemplate) -> Flag PathTemplate)
(Flag PathTemplate
-> InstallDirs (Flag PathTemplate)
-> InstallDirs (Flag PathTemplate))
(InstallDirs (Flag PathTemplate))
-> OptionField (InstallDirs (Flag PathTemplate))
forall get set a.
String
-> [String]
-> String
-> get
-> set
-> MkOptDescr get set a
-> OptionField a
option
String
""
[String
"bindir"]
String
"installation directory for executables"
InstallDirs (Flag PathTemplate) -> Flag PathTemplate
forall dir. InstallDirs dir -> dir
bindir
(\Flag PathTemplate
v InstallDirs (Flag PathTemplate)
flags -> InstallDirs (Flag PathTemplate)
flags{bindir = v})
MkOptDescr
(InstallDirs (Flag PathTemplate) -> Flag PathTemplate)
(Flag PathTemplate
-> InstallDirs (Flag PathTemplate)
-> InstallDirs (Flag PathTemplate))
(InstallDirs (Flag PathTemplate))
forall {b}.
String
-> [String]
-> String
-> (b -> Flag PathTemplate)
-> (Flag PathTemplate -> b -> b)
-> OptDescr b
installDirArg
, String
-> [String]
-> String
-> (InstallDirs (Flag PathTemplate) -> Flag PathTemplate)
-> (Flag PathTemplate
-> InstallDirs (Flag PathTemplate)
-> InstallDirs (Flag PathTemplate))
-> MkOptDescr
(InstallDirs (Flag PathTemplate) -> Flag PathTemplate)
(Flag PathTemplate
-> InstallDirs (Flag PathTemplate)
-> InstallDirs (Flag PathTemplate))
(InstallDirs (Flag PathTemplate))
-> OptionField (InstallDirs (Flag PathTemplate))
forall get set a.
String
-> [String]
-> String
-> get
-> set
-> MkOptDescr get set a
-> OptionField a
option
String
""
[String
"libdir"]
String
"installation directory for libraries"
InstallDirs (Flag PathTemplate) -> Flag PathTemplate
forall dir. InstallDirs dir -> dir
libdir
(\Flag PathTemplate
v InstallDirs (Flag PathTemplate)
flags -> InstallDirs (Flag PathTemplate)
flags{libdir = v})
MkOptDescr
(InstallDirs (Flag PathTemplate) -> Flag PathTemplate)
(Flag PathTemplate
-> InstallDirs (Flag PathTemplate)
-> InstallDirs (Flag PathTemplate))
(InstallDirs (Flag PathTemplate))
forall {b}.
String
-> [String]
-> String
-> (b -> Flag PathTemplate)
-> (Flag PathTemplate -> b -> b)
-> OptDescr b
installDirArg
, String
-> [String]
-> String
-> (InstallDirs (Flag PathTemplate) -> Flag PathTemplate)
-> (Flag PathTemplate
-> InstallDirs (Flag PathTemplate)
-> InstallDirs (Flag PathTemplate))
-> MkOptDescr
(InstallDirs (Flag PathTemplate) -> Flag PathTemplate)
(Flag PathTemplate
-> InstallDirs (Flag PathTemplate)
-> InstallDirs (Flag PathTemplate))
(InstallDirs (Flag PathTemplate))
-> OptionField (InstallDirs (Flag PathTemplate))
forall get set a.
String
-> [String]
-> String
-> get
-> set
-> MkOptDescr get set a
-> OptionField a
option
String
""
[String
"libsubdir"]
String
"subdirectory of libdir in which libs are installed"
InstallDirs (Flag PathTemplate) -> Flag PathTemplate
forall dir. InstallDirs dir -> dir
libsubdir
(\Flag PathTemplate
v InstallDirs (Flag PathTemplate)
flags -> InstallDirs (Flag PathTemplate)
flags{libsubdir = v})
MkOptDescr
(InstallDirs (Flag PathTemplate) -> Flag PathTemplate)
(Flag PathTemplate
-> InstallDirs (Flag PathTemplate)
-> InstallDirs (Flag PathTemplate))
(InstallDirs (Flag PathTemplate))
forall {b}.
String
-> [String]
-> String
-> (b -> Flag PathTemplate)
-> (Flag PathTemplate -> b -> b)
-> OptDescr b
installDirArg
, String
-> [String]
-> String
-> (InstallDirs (Flag PathTemplate) -> Flag PathTemplate)
-> (Flag PathTemplate
-> InstallDirs (Flag PathTemplate)
-> InstallDirs (Flag PathTemplate))
-> MkOptDescr
(InstallDirs (Flag PathTemplate) -> Flag PathTemplate)
(Flag PathTemplate
-> InstallDirs (Flag PathTemplate)
-> InstallDirs (Flag PathTemplate))
(InstallDirs (Flag PathTemplate))
-> OptionField (InstallDirs (Flag PathTemplate))
forall get set a.
String
-> [String]
-> String
-> get
-> set
-> MkOptDescr get set a
-> OptionField a
option
String
""
[String
"dynlibdir"]
String
"installation directory for dynamic libraries"
InstallDirs (Flag PathTemplate) -> Flag PathTemplate
forall dir. InstallDirs dir -> dir
dynlibdir
(\Flag PathTemplate
v InstallDirs (Flag PathTemplate)
flags -> InstallDirs (Flag PathTemplate)
flags{dynlibdir = v})
MkOptDescr
(InstallDirs (Flag PathTemplate) -> Flag PathTemplate)
(Flag PathTemplate
-> InstallDirs (Flag PathTemplate)
-> InstallDirs (Flag PathTemplate))
(InstallDirs (Flag PathTemplate))
forall {b}.
String
-> [String]
-> String
-> (b -> Flag PathTemplate)
-> (Flag PathTemplate -> b -> b)
-> OptDescr b
installDirArg
, String
-> [String]
-> String
-> (InstallDirs (Flag PathTemplate) -> Flag PathTemplate)
-> (Flag PathTemplate
-> InstallDirs (Flag PathTemplate)
-> InstallDirs (Flag PathTemplate))
-> MkOptDescr
(InstallDirs (Flag PathTemplate) -> Flag PathTemplate)
(Flag PathTemplate
-> InstallDirs (Flag PathTemplate)
-> InstallDirs (Flag PathTemplate))
(InstallDirs (Flag PathTemplate))
-> OptionField (InstallDirs (Flag PathTemplate))
forall get set a.
String
-> [String]
-> String
-> get
-> set
-> MkOptDescr get set a
-> OptionField a
option
String
""
[String
"libexecdir"]
String
"installation directory for program executables"
InstallDirs (Flag PathTemplate) -> Flag PathTemplate
forall dir. InstallDirs dir -> dir
libexecdir
(\Flag PathTemplate
v InstallDirs (Flag PathTemplate)
flags -> InstallDirs (Flag PathTemplate)
flags{libexecdir = v})
MkOptDescr
(InstallDirs (Flag PathTemplate) -> Flag PathTemplate)
(Flag PathTemplate
-> InstallDirs (Flag PathTemplate)
-> InstallDirs (Flag PathTemplate))
(InstallDirs (Flag PathTemplate))
forall {b}.
String
-> [String]
-> String
-> (b -> Flag PathTemplate)
-> (Flag PathTemplate -> b -> b)
-> OptDescr b
installDirArg
, String
-> [String]
-> String
-> (InstallDirs (Flag PathTemplate) -> Flag PathTemplate)
-> (Flag PathTemplate
-> InstallDirs (Flag PathTemplate)
-> InstallDirs (Flag PathTemplate))
-> MkOptDescr
(InstallDirs (Flag PathTemplate) -> Flag PathTemplate)
(Flag PathTemplate
-> InstallDirs (Flag PathTemplate)
-> InstallDirs (Flag PathTemplate))
(InstallDirs (Flag PathTemplate))
-> OptionField (InstallDirs (Flag PathTemplate))
forall get set a.
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"
InstallDirs (Flag PathTemplate) -> Flag PathTemplate
forall dir. InstallDirs dir -> dir
libexecsubdir
(\Flag PathTemplate
v InstallDirs (Flag PathTemplate)
flags -> InstallDirs (Flag PathTemplate)
flags{libexecsubdir = v})
MkOptDescr
(InstallDirs (Flag PathTemplate) -> Flag PathTemplate)
(Flag PathTemplate
-> InstallDirs (Flag PathTemplate)
-> InstallDirs (Flag PathTemplate))
(InstallDirs (Flag PathTemplate))
forall {b}.
String
-> [String]
-> String
-> (b -> Flag PathTemplate)
-> (Flag PathTemplate -> b -> b)
-> OptDescr b
installDirArg
, String
-> [String]
-> String
-> (InstallDirs (Flag PathTemplate) -> Flag PathTemplate)
-> (Flag PathTemplate
-> InstallDirs (Flag PathTemplate)
-> InstallDirs (Flag PathTemplate))
-> MkOptDescr
(InstallDirs (Flag PathTemplate) -> Flag PathTemplate)
(Flag PathTemplate
-> InstallDirs (Flag PathTemplate)
-> InstallDirs (Flag PathTemplate))
(InstallDirs (Flag PathTemplate))
-> OptionField (InstallDirs (Flag PathTemplate))
forall get set a.
String
-> [String]
-> String
-> get
-> set
-> MkOptDescr get set a
-> OptionField a
option
String
""
[String
"datadir"]
String
"installation directory for read-only data"
InstallDirs (Flag PathTemplate) -> Flag PathTemplate
forall dir. InstallDirs dir -> dir
datadir
(\Flag PathTemplate
v InstallDirs (Flag PathTemplate)
flags -> InstallDirs (Flag PathTemplate)
flags{datadir = v})
MkOptDescr
(InstallDirs (Flag PathTemplate) -> Flag PathTemplate)
(Flag PathTemplate
-> InstallDirs (Flag PathTemplate)
-> InstallDirs (Flag PathTemplate))
(InstallDirs (Flag PathTemplate))
forall {b}.
String
-> [String]
-> String
-> (b -> Flag PathTemplate)
-> (Flag PathTemplate -> b -> b)
-> OptDescr b
installDirArg
, String
-> [String]
-> String
-> (InstallDirs (Flag PathTemplate) -> Flag PathTemplate)
-> (Flag PathTemplate
-> InstallDirs (Flag PathTemplate)
-> InstallDirs (Flag PathTemplate))
-> MkOptDescr
(InstallDirs (Flag PathTemplate) -> Flag PathTemplate)
(Flag PathTemplate
-> InstallDirs (Flag PathTemplate)
-> InstallDirs (Flag PathTemplate))
(InstallDirs (Flag PathTemplate))
-> OptionField (InstallDirs (Flag PathTemplate))
forall get set a.
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"
InstallDirs (Flag PathTemplate) -> Flag PathTemplate
forall dir. InstallDirs dir -> dir
datasubdir
(\Flag PathTemplate
v InstallDirs (Flag PathTemplate)
flags -> InstallDirs (Flag PathTemplate)
flags{datasubdir = v})
MkOptDescr
(InstallDirs (Flag PathTemplate) -> Flag PathTemplate)
(Flag PathTemplate
-> InstallDirs (Flag PathTemplate)
-> InstallDirs (Flag PathTemplate))
(InstallDirs (Flag PathTemplate))
forall {b}.
String
-> [String]
-> String
-> (b -> Flag PathTemplate)
-> (Flag PathTemplate -> b -> b)
-> OptDescr b
installDirArg
, String
-> [String]
-> String
-> (InstallDirs (Flag PathTemplate) -> Flag PathTemplate)
-> (Flag PathTemplate
-> InstallDirs (Flag PathTemplate)
-> InstallDirs (Flag PathTemplate))
-> MkOptDescr
(InstallDirs (Flag PathTemplate) -> Flag PathTemplate)
(Flag PathTemplate
-> InstallDirs (Flag PathTemplate)
-> InstallDirs (Flag PathTemplate))
(InstallDirs (Flag PathTemplate))
-> OptionField (InstallDirs (Flag PathTemplate))
forall get set a.
String
-> [String]
-> String
-> get
-> set
-> MkOptDescr get set a
-> OptionField a
option
String
""
[String
"docdir"]
String
"installation directory for documentation"
InstallDirs (Flag PathTemplate) -> Flag PathTemplate
forall dir. InstallDirs dir -> dir
docdir
(\Flag PathTemplate
v InstallDirs (Flag PathTemplate)
flags -> InstallDirs (Flag PathTemplate)
flags{docdir = v})
MkOptDescr
(InstallDirs (Flag PathTemplate) -> Flag PathTemplate)
(Flag PathTemplate
-> InstallDirs (Flag PathTemplate)
-> InstallDirs (Flag PathTemplate))
(InstallDirs (Flag PathTemplate))
forall {b}.
String
-> [String]
-> String
-> (b -> Flag PathTemplate)
-> (Flag PathTemplate -> b -> b)
-> OptDescr b
installDirArg
, String
-> [String]
-> String
-> (InstallDirs (Flag PathTemplate) -> Flag PathTemplate)
-> (Flag PathTemplate
-> InstallDirs (Flag PathTemplate)
-> InstallDirs (Flag PathTemplate))
-> MkOptDescr
(InstallDirs (Flag PathTemplate) -> Flag PathTemplate)
(Flag PathTemplate
-> InstallDirs (Flag PathTemplate)
-> InstallDirs (Flag PathTemplate))
(InstallDirs (Flag PathTemplate))
-> OptionField (InstallDirs (Flag PathTemplate))
forall get set a.
String
-> [String]
-> String
-> get
-> set
-> MkOptDescr get set a
-> OptionField a
option
String
""
[String
"htmldir"]
String
"installation directory for HTML documentation"
InstallDirs (Flag PathTemplate) -> Flag PathTemplate
forall dir. InstallDirs dir -> dir
htmldir
(\Flag PathTemplate
v InstallDirs (Flag PathTemplate)
flags -> InstallDirs (Flag PathTemplate)
flags{htmldir = v})
MkOptDescr
(InstallDirs (Flag PathTemplate) -> Flag PathTemplate)
(Flag PathTemplate
-> InstallDirs (Flag PathTemplate)
-> InstallDirs (Flag PathTemplate))
(InstallDirs (Flag PathTemplate))
forall {b}.
String
-> [String]
-> String
-> (b -> Flag PathTemplate)
-> (Flag PathTemplate -> b -> b)
-> OptDescr b
installDirArg
, String
-> [String]
-> String
-> (InstallDirs (Flag PathTemplate) -> Flag PathTemplate)
-> (Flag PathTemplate
-> InstallDirs (Flag PathTemplate)
-> InstallDirs (Flag PathTemplate))
-> MkOptDescr
(InstallDirs (Flag PathTemplate) -> Flag PathTemplate)
(Flag PathTemplate
-> InstallDirs (Flag PathTemplate)
-> InstallDirs (Flag PathTemplate))
(InstallDirs (Flag PathTemplate))
-> OptionField (InstallDirs (Flag PathTemplate))
forall get set a.
String
-> [String]
-> String
-> get
-> set
-> MkOptDescr get set a
-> OptionField a
option
String
""
[String
"haddockdir"]
String
"installation directory for haddock interfaces"
InstallDirs (Flag PathTemplate) -> Flag PathTemplate
forall dir. InstallDirs dir -> dir
haddockdir
(\Flag PathTemplate
v InstallDirs (Flag PathTemplate)
flags -> InstallDirs (Flag PathTemplate)
flags{haddockdir = v})
MkOptDescr
(InstallDirs (Flag PathTemplate) -> Flag PathTemplate)
(Flag PathTemplate
-> InstallDirs (Flag PathTemplate)
-> InstallDirs (Flag PathTemplate))
(InstallDirs (Flag PathTemplate))
forall {b}.
String
-> [String]
-> String
-> (b -> Flag PathTemplate)
-> (Flag PathTemplate -> b -> b)
-> OptDescr b
installDirArg
, String
-> [String]
-> String
-> (InstallDirs (Flag PathTemplate) -> Flag PathTemplate)
-> (Flag PathTemplate
-> InstallDirs (Flag PathTemplate)
-> InstallDirs (Flag PathTemplate))
-> MkOptDescr
(InstallDirs (Flag PathTemplate) -> Flag PathTemplate)
(Flag PathTemplate
-> InstallDirs (Flag PathTemplate)
-> InstallDirs (Flag PathTemplate))
(InstallDirs (Flag PathTemplate))
-> OptionField (InstallDirs (Flag PathTemplate))
forall get set a.
String
-> [String]
-> String
-> get
-> set
-> MkOptDescr get set a
-> OptionField a
option
String
""
[String
"sysconfdir"]
String
"installation directory for configuration files"
InstallDirs (Flag PathTemplate) -> Flag PathTemplate
forall dir. InstallDirs dir -> dir
sysconfdir
(\Flag PathTemplate
v InstallDirs (Flag PathTemplate)
flags -> InstallDirs (Flag PathTemplate)
flags{sysconfdir = v})
MkOptDescr
(InstallDirs (Flag PathTemplate) -> Flag PathTemplate)
(Flag PathTemplate
-> InstallDirs (Flag PathTemplate)
-> InstallDirs (Flag PathTemplate))
(InstallDirs (Flag PathTemplate))
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 =
String
-> String
-> [String]
-> String
-> (b -> Flag String)
-> (Flag String -> b -> b)
-> OptDescr b
forall b.
String
-> String
-> [String]
-> String
-> (b -> Flag String)
-> (Flag String -> b -> b)
-> OptDescr b
reqArgFlag
String
"DIR"
String
_sf
[String]
_lf
String
d
((PathTemplate -> String) -> Flag PathTemplate -> Flag String
forall a b. (a -> b) -> Flag a -> Flag b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap PathTemplate -> String
fromPathTemplate (Flag PathTemplate -> Flag String)
-> (b -> Flag PathTemplate) -> b -> Flag String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. b -> Flag PathTemplate
get)
(Flag PathTemplate -> b -> b
set (Flag PathTemplate -> b -> b)
-> (Flag String -> Flag PathTemplate) -> Flag String -> b -> b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (String -> PathTemplate) -> Flag String -> Flag PathTemplate
forall a b. (a -> b) -> Flag a -> Flag b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap String -> PathTemplate
toPathTemplate)
emptyConfigFlags :: ConfigFlags
emptyConfigFlags :: ConfigFlags
emptyConfigFlags = ConfigFlags
forall a. Monoid a => a
mempty
instance Monoid ConfigFlags where
mempty :: ConfigFlags
mempty = ConfigFlags
forall a. (Generic a, GMonoid (Rep a)) => a
gmempty
mappend :: ConfigFlags -> ConfigFlags -> ConfigFlags
mappend = ConfigFlags -> ConfigFlags -> ConfigFlags
forall a. Semigroup a => a -> a -> a
(<>)
instance Semigroup ConfigFlags where
<> :: ConfigFlags -> ConfigFlags -> ConfigFlags
(<>) = ConfigFlags -> ConfigFlags -> ConfigFlags
forall a. (Generic a, GSemigroup (Rep a)) => a -> a -> a
gmappend
configureArgs :: Bool -> ConfigFlags -> [String]
configureArgs :: Bool -> ConfigFlags -> [String]
configureArgs Bool
bcHack ConfigFlags
flags =
[String]
hc_flag
[String] -> [String] -> [String]
forall a. [a] -> [a] -> [a]
++ String -> (ConfigFlags -> Flag String) -> [String]
optFlag String
"with-hc-pkg" ConfigFlags -> Flag String
configHcPkg
[String] -> [String] -> [String]
forall a. [a] -> [a] -> [a]
++ String
-> (InstallDirs (Flag PathTemplate) -> Flag PathTemplate)
-> [String]
optFlag' String
"prefix" InstallDirs (Flag PathTemplate) -> Flag PathTemplate
forall dir. InstallDirs dir -> dir
prefix
[String] -> [String] -> [String]
forall a. [a] -> [a] -> [a]
++ String
-> (InstallDirs (Flag PathTemplate) -> Flag PathTemplate)
-> [String]
optFlag' String
"bindir" InstallDirs (Flag PathTemplate) -> Flag PathTemplate
forall dir. InstallDirs dir -> dir
bindir
[String] -> [String] -> [String]
forall a. [a] -> [a] -> [a]
++ String
-> (InstallDirs (Flag PathTemplate) -> Flag PathTemplate)
-> [String]
optFlag' String
"libdir" InstallDirs (Flag PathTemplate) -> Flag PathTemplate
forall dir. InstallDirs dir -> dir
libdir
[String] -> [String] -> [String]
forall a. [a] -> [a] -> [a]
++ String
-> (InstallDirs (Flag PathTemplate) -> Flag PathTemplate)
-> [String]
optFlag' String
"libexecdir" InstallDirs (Flag PathTemplate) -> Flag PathTemplate
forall dir. InstallDirs dir -> dir
libexecdir
[String] -> [String] -> [String]
forall a. [a] -> [a] -> [a]
++ String
-> (InstallDirs (Flag PathTemplate) -> Flag PathTemplate)
-> [String]
optFlag' String
"datadir" InstallDirs (Flag PathTemplate) -> Flag PathTemplate
forall dir. InstallDirs dir -> dir
datadir
[String] -> [String] -> [String]
forall a. [a] -> [a] -> [a]
++ String
-> (InstallDirs (Flag PathTemplate) -> Flag PathTemplate)
-> [String]
optFlag' String
"sysconfdir" InstallDirs (Flag PathTemplate) -> Flag PathTemplate
forall dir. InstallDirs dir -> dir
sysconfdir
[String] -> [String] -> [String]
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 String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
hc_path]
(Flag CompilerFlavor
hc, Flag String
NoFlag) -> [String
hc_flag_name String -> ShowS
forall a. [a] -> [a] -> [a]
++ CompilerFlavor -> String
forall a. Pretty a => a -> String
prettyShow CompilerFlavor
hc]
(Flag CompilerFlavor
NoFlag, Flag String
NoFlag) -> []
hc_flag_name :: String
hc_flag_name
| 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
"--" String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
name String -> ShowS
forall a. [a] -> [a] -> [a]
++ String
"=" String -> ShowS
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
( (PathTemplate -> String) -> Flag PathTemplate -> Flag String
forall a b. (a -> b) -> Flag a -> Flag b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap PathTemplate -> String
fromPathTemplate
(Flag PathTemplate -> Flag String)
-> (ConfigFlags -> Flag PathTemplate) -> ConfigFlags -> Flag String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. InstallDirs (Flag PathTemplate) -> Flag PathTemplate
config_field
(InstallDirs (Flag PathTemplate) -> Flag PathTemplate)
-> (ConfigFlags -> InstallDirs (Flag PathTemplate))
-> ConfigFlags
-> Flag PathTemplate
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ConfigFlags -> InstallDirs (Flag PathTemplate)
configInstallDirs
)