Portability | portable |
---|---|
Maintainer | cabal-devel@haskell.org |
Safe Haskell | None |
This is a big module, but not very complicated. The code is very regular
and repetitive. It defines the command line interface for all the Cabal
commands. For each command (like configure
, build
etc) it defines a type
that holds all the flags, the default set of flags and a CommandUI
that
maps command line flags to and from the corresponding flags type.
All the flags types are instances of Monoid
, see
http://www.haskell.org/pipermail/cabal-devel/2007-December/001509.html
for an explanation.
The types defined here get used in the front end and especially in
cabal-install
which has to do quite a bit of manipulating sets of command
line flags.
This is actually relatively nice, it works quite well. The main change it needs is to unify it with the code for managing sets of fields that can be read and written from files. This would allow us to save configure flags in config files.
- data GlobalFlags = GlobalFlags {
- globalVersion :: Flag Bool
- globalNumericVersion :: Flag Bool
- emptyGlobalFlags :: GlobalFlags
- defaultGlobalFlags :: GlobalFlags
- globalCommand :: CommandUI GlobalFlags
- data ConfigFlags = ConfigFlags {
- configPrograms :: ProgramConfiguration
- configProgramPaths :: [(String, FilePath)]
- configProgramArgs :: [(String, [String])]
- configProgramPathExtra :: [FilePath]
- configHcFlavor :: Flag CompilerFlavor
- configHcPath :: Flag FilePath
- configHcPkg :: Flag FilePath
- configVanillaLib :: Flag Bool
- configProfLib :: Flag Bool
- configSharedLib :: Flag Bool
- configDynExe :: Flag Bool
- configProfExe :: Flag Bool
- configConfigureArgs :: [String]
- configOptimization :: Flag OptimisationLevel
- configProgPrefix :: Flag PathTemplate
- configProgSuffix :: Flag PathTemplate
- configInstallDirs :: InstallDirs (Flag PathTemplate)
- configScratchDir :: Flag FilePath
- configExtraLibDirs :: [FilePath]
- configExtraIncludeDirs :: [FilePath]
- configDistPref :: Flag FilePath
- configVerbosity :: Flag Verbosity
- configUserInstall :: Flag Bool
- configPackageDBs :: [Maybe PackageDB]
- configGHCiLib :: Flag Bool
- configSplitObjs :: Flag Bool
- configStripExes :: Flag Bool
- configConstraints :: [Dependency]
- configConfigurationsFlags :: FlagAssignment
- configTests :: Flag Bool
- configBenchmarks :: Flag Bool
- configLibCoverage :: Flag Bool
- emptyConfigFlags :: ConfigFlags
- defaultConfigFlags :: ProgramConfiguration -> ConfigFlags
- configureCommand :: ProgramConfiguration -> CommandUI ConfigFlags
- configAbsolutePaths :: ConfigFlags -> IO ConfigFlags
- data CopyFlags = CopyFlags {
- copyDest :: Flag CopyDest
- copyDistPref :: Flag FilePath
- copyVerbosity :: Flag Verbosity
- emptyCopyFlags :: CopyFlags
- defaultCopyFlags :: CopyFlags
- copyCommand :: CommandUI CopyFlags
- data InstallFlags = InstallFlags {
- installPackageDB :: Flag PackageDB
- installDistPref :: Flag FilePath
- installUseWrapper :: Flag Bool
- installInPlace :: Flag Bool
- installVerbosity :: Flag Verbosity
- emptyInstallFlags :: InstallFlags
- defaultInstallFlags :: InstallFlags
- installCommand :: CommandUI InstallFlags
- data HaddockFlags = HaddockFlags {
- haddockProgramPaths :: [(String, FilePath)]
- haddockProgramArgs :: [(String, [String])]
- haddockHoogle :: Flag Bool
- haddockHtml :: Flag Bool
- haddockHtmlLocation :: Flag String
- haddockExecutables :: Flag Bool
- haddockTestSuites :: Flag Bool
- haddockBenchmarks :: Flag Bool
- haddockInternal :: Flag Bool
- haddockCss :: Flag FilePath
- haddockHscolour :: Flag Bool
- haddockHscolourCss :: Flag FilePath
- haddockContents :: Flag PathTemplate
- haddockDistPref :: Flag FilePath
- haddockKeepTempFiles :: Flag Bool
- haddockVerbosity :: Flag Verbosity
- emptyHaddockFlags :: HaddockFlags
- defaultHaddockFlags :: HaddockFlags
- haddockCommand :: CommandUI HaddockFlags
- data HscolourFlags = HscolourFlags {
- hscolourCSS :: Flag FilePath
- hscolourExecutables :: Flag Bool
- hscolourTestSuites :: Flag Bool
- hscolourBenchmarks :: Flag Bool
- hscolourDistPref :: Flag FilePath
- hscolourVerbosity :: Flag Verbosity
- emptyHscolourFlags :: HscolourFlags
- defaultHscolourFlags :: HscolourFlags
- hscolourCommand :: CommandUI HscolourFlags
- data BuildFlags = BuildFlags {
- buildProgramPaths :: [(String, FilePath)]
- buildProgramArgs :: [(String, [String])]
- buildDistPref :: Flag FilePath
- buildVerbosity :: Flag Verbosity
- buildArgs :: [String]
- emptyBuildFlags :: BuildFlags
- defaultBuildFlags :: BuildFlags
- buildCommand :: ProgramConfiguration -> CommandUI BuildFlags
- buildVerbose :: BuildFlags -> Verbosity
- data ReplFlags = ReplFlags {
- replProgramPaths :: [(String, FilePath)]
- replProgramArgs :: [(String, [String])]
- replDistPref :: Flag FilePath
- replVerbosity :: Flag Verbosity
- replReload :: Flag Bool
- defaultReplFlags :: ReplFlags
- replCommand :: ProgramConfiguration -> CommandUI ReplFlags
- data CleanFlags = CleanFlags {
- cleanSaveConf :: Flag Bool
- cleanDistPref :: Flag FilePath
- cleanVerbosity :: Flag Verbosity
- emptyCleanFlags :: CleanFlags
- defaultCleanFlags :: CleanFlags
- cleanCommand :: CommandUI CleanFlags
- data RegisterFlags = RegisterFlags {
- regPackageDB :: Flag PackageDB
- regGenScript :: Flag Bool
- regGenPkgConf :: Flag (Maybe FilePath)
- regInPlace :: Flag Bool
- regDistPref :: Flag FilePath
- regVerbosity :: Flag Verbosity
- emptyRegisterFlags :: RegisterFlags
- defaultRegisterFlags :: RegisterFlags
- registerCommand :: CommandUI RegisterFlags
- unregisterCommand :: CommandUI RegisterFlags
- data SDistFlags = SDistFlags {
- sDistSnapshot :: Flag Bool
- sDistDirectory :: Flag FilePath
- sDistDistPref :: Flag FilePath
- sDistListSources :: Flag FilePath
- sDistVerbosity :: Flag Verbosity
- emptySDistFlags :: SDistFlags
- defaultSDistFlags :: SDistFlags
- sdistCommand :: CommandUI SDistFlags
- data TestFlags = TestFlags {
- testDistPref :: Flag FilePath
- testVerbosity :: Flag Verbosity
- testHumanLog :: Flag PathTemplate
- testMachineLog :: Flag PathTemplate
- testShowDetails :: Flag TestShowDetails
- testKeepTix :: Flag Bool
- testList :: Flag [String]
- testOptions :: [PathTemplate]
- emptyTestFlags :: TestFlags
- defaultTestFlags :: TestFlags
- testCommand :: CommandUI TestFlags
- data TestShowDetails
- data BenchmarkFlags = BenchmarkFlags {
- benchmarkDistPref :: Flag FilePath
- benchmarkVerbosity :: Flag Verbosity
- benchmarkOptions :: [PathTemplate]
- emptyBenchmarkFlags :: BenchmarkFlags
- defaultBenchmarkFlags :: BenchmarkFlags
- benchmarkCommand :: CommandUI BenchmarkFlags
- data CopyDest
- = NoCopyDest
- | CopyTo FilePath
- configureArgs :: Bool -> ConfigFlags -> [String]
- configureOptions :: ShowOrParseArgs -> [OptionField ConfigFlags]
- configureCCompiler :: Verbosity -> ProgramConfiguration -> IO (FilePath, [String])
- configureLinker :: Verbosity -> ProgramConfiguration -> IO (FilePath, [String])
- buildOptions :: ProgramConfiguration -> ShowOrParseArgs -> [OptionField BuildFlags]
- installDirsOptions :: [OptionField (InstallDirs (Flag PathTemplate))]
- programConfigurationOptions :: ProgramConfiguration -> ShowOrParseArgs -> (flags -> [(String, [String])]) -> ([(String, [String])] -> flags -> flags) -> [OptionField flags]
- programConfigurationPaths' :: (String -> String) -> ProgramConfiguration -> ShowOrParseArgs -> (flags -> [(String, FilePath)]) -> ([(String, FilePath)] -> flags -> flags) -> [OptionField flags]
- defaultDistPref :: FilePath
- data Flag a
- toFlag :: a -> Flag a
- fromFlag :: Flag a -> a
- fromFlagOrDefault :: a -> Flag a -> a
- flagToMaybe :: Flag a -> Maybe a
- flagToList :: Flag a -> [a]
- boolOpt :: SFlags -> SFlags -> MkOptDescr (a -> Flag Bool) (Flag Bool -> a -> a) a
- boolOpt' :: OptFlags -> OptFlags -> MkOptDescr (a -> Flag Bool) (Flag Bool -> a -> a) a
- trueArg :: SFlags -> LFlags -> Description -> (b -> Flag Bool) -> (Flag Bool -> b -> b) -> OptDescr b
- falseArg :: SFlags -> LFlags -> Description -> (b -> Flag Bool) -> (Flag Bool -> b -> b) -> OptDescr b
- optionVerbosity :: (flags -> Flag Verbosity) -> (Flag Verbosity -> flags -> flags) -> OptionField flags
Documentation
data GlobalFlags
Flags that apply at the top level, not to any sub-command.
GlobalFlags | |
|
Monoid GlobalFlags |
data ConfigFlags
Flags to configure
command
ConfigFlags | |
|
Read ConfigFlags | |
Show ConfigFlags | |
Monoid ConfigFlags |
configAbsolutePaths :: ConfigFlags -> IO ConfigFlags
data CopyFlags
Flags to copy
: (destdir, copy-prefix (backwards compat), verbosity)
CopyFlags | |
|
data InstallFlags
Flags to install
: (package db, verbosity)
InstallFlags | |
|
Show InstallFlags | |
Monoid InstallFlags |
data HaddockFlags
HaddockFlags | |
|
Show HaddockFlags | |
Monoid HaddockFlags |
data HscolourFlags
HscolourFlags | |
|
Show HscolourFlags | |
Monoid HscolourFlags |
data BuildFlags
BuildFlags | |
|
Show BuildFlags | |
Monoid BuildFlags |
buildVerbose :: BuildFlags -> Verbosity
Deprecated: Use buildVerbosity instead
data ReplFlags
ReplFlags | |
|
data CleanFlags
CleanFlags | |
|
Show CleanFlags | |
Monoid CleanFlags |
data RegisterFlags
Flags to register
and unregister
: (user package, gen-script,
in-place, verbosity)
RegisterFlags | |
|
Show RegisterFlags | |
Monoid RegisterFlags |
data SDistFlags
Flags to sdist
: (snapshot, verbosity)
SDistFlags | |
|
Show SDistFlags | |
Monoid SDistFlags |
data TestFlags
TestFlags | |
|
Monoid TestFlags |
data TestShowDetails
Bounded TestShowDetails | |
Enum TestShowDetails | |
Eq TestShowDetails | |
Ord TestShowDetails | |
Show TestShowDetails | |
Monoid TestShowDetails | |
Text TestShowDetails |
data BenchmarkFlags
BenchmarkFlags | |
|
Monoid BenchmarkFlags |
configureArgs :: Bool -> ConfigFlags -> [String]
Arguments to pass to a configure
script, e.g. generated by
autoconf
.
configureCCompiler :: Verbosity -> ProgramConfiguration -> IO (FilePath, [String])
configureLinker :: Verbosity -> ProgramConfiguration -> IO (FilePath, [String])
programConfigurationOptions :: ProgramConfiguration -> ShowOrParseArgs -> (flags -> [(String, [String])]) -> ([(String, [String])] -> flags -> flags) -> [OptionField flags]
For each known program PROG
in progConf
, produce a PROG-options
OptionField
.
programConfigurationPaths' :: (String -> String) -> ProgramConfiguration -> ShowOrParseArgs -> (flags -> [(String, FilePath)]) -> ([(String, FilePath)] -> flags -> flags) -> [OptionField flags]
Like programConfigurationPaths
, but allows to customise the option name.
defaultDistPref :: FilePath
data Flag a
All flags are monoids, they come in two flavours:
- list flags eg
--ghc-option=foo --ghc-option=bar
gives us all the values [foo, bar]
- singular value flags, eg:
--enable-foo --disable-foo
gives us Just False
So this Flag type is for the latter singular kind of flag.
Its monoid instance gives us the behaviour where it starts out as
NoFlag
and later flags override earlier ones.
fromFlagOrDefault :: a -> Flag a -> a
flagToMaybe :: Flag a -> Maybe a
flagToList :: Flag a -> [a]
trueArg :: SFlags -> LFlags -> Description -> (b -> Flag Bool) -> (Flag Bool -> b -> b) -> OptDescr b
falseArg :: SFlags -> LFlags -> Description -> (b -> Flag Bool) -> (Flag Bool -> b -> b) -> OptDescr b
optionVerbosity :: (flags -> Flag Verbosity) -> (Flag Verbosity -> flags -> flags) -> OptionField flags