| Cabal-1.10.2.0: A framework for packaging Haskell software | Contents | Index |
|
Distribution.Simple.Setup | Portability | portable | Maintainer | cabal-devel@haskell.org |
|
|
|
Description |
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.
|
|
Synopsis |
|
|
|
Documentation |
|
data GlobalFlags |
Flags that apply at the top level, not to any sub-command.
| Constructors | GlobalFlags | | globalVersion :: Flag Bool | | globalNumericVersion :: Flag Bool | |
|
| Instances | |
|
|
emptyGlobalFlags :: GlobalFlags |
|
defaultGlobalFlags :: GlobalFlags |
|
globalCommand :: CommandUI GlobalFlags |
|
data ConfigFlags |
Flags to configure command
| Constructors | ConfigFlags | | configPrograms :: ProgramConfiguration | All programs that cabal may run
| configProgramPaths :: [(String, FilePath)] | user specifed programs paths
| configProgramArgs :: [(String, [String])] | user specifed programs args
| configHcFlavor :: Flag CompilerFlavor | The "flavor" of the compiler, sugh as GHC or Hugs.
| configHcPath :: Flag FilePath | given compiler location
| configHcPkg :: Flag FilePath | given hc-pkg location
| configVanillaLib :: Flag Bool | Enable vanilla library
| configProfLib :: Flag Bool | Enable profiling in the library
| configSharedLib :: Flag Bool | Build shared library
| configProfExe :: Flag Bool | Enable profiling in the executables.
| configConfigureArgs :: [String] | Extra arguments to configure
| configOptimization :: Flag OptimisationLevel | Enable optimization.
| configProgPrefix :: Flag PathTemplate | Installed executable prefix.
| configProgSuffix :: Flag PathTemplate | Installed executable suffix.
| configInstallDirs :: InstallDirs (Flag PathTemplate) | Installation paths
| configScratchDir :: Flag FilePath | | configExtraLibDirs :: [FilePath] | path to search for extra libraries
| configExtraIncludeDirs :: [FilePath] | path to search for header files
| configDistPref :: Flag FilePath | dist prefix
| configVerbosity :: Flag Verbosity | verbosity level
| configUserInstall :: Flag Bool | The --user/--global flag
| configPackageDB :: Flag PackageDB | Which package DB to use
| configGHCiLib :: Flag Bool | Enable compiling library for GHCi
| configSplitObjs :: Flag Bool | Enable -split-objs with GHC
| configStripExes :: Flag Bool | Enable executable stripping
| configConstraints :: [Dependency] | Additional constraints for
dependencies
| configConfigurationsFlags :: FlagAssignment | | configTests :: Flag Bool | Enable test suite compilation
|
|
| Instances | |
|
|
emptyConfigFlags :: ConfigFlags |
|
defaultConfigFlags :: ProgramConfiguration -> ConfigFlags |
|
configureCommand :: ProgramConfiguration -> CommandUI ConfigFlags |
|
data CopyFlags |
Flags to copy: (destdir, copy-prefix (backwards compat), verbosity)
| Constructors | | Instances | |
|
|
emptyCopyFlags :: CopyFlags |
|
defaultCopyFlags :: CopyFlags |
|
copyCommand :: CommandUI CopyFlags |
|
data InstallFlags |
Flags to install: (package db, verbosity)
| Constructors | | Instances | |
|
|
emptyInstallFlags :: InstallFlags |
|
defaultInstallFlags :: InstallFlags |
|
installCommand :: CommandUI InstallFlags |
|
data HaddockFlags |
Constructors | HaddockFlags | | haddockProgramPaths :: [(String, FilePath)] | | haddockProgramArgs :: [(String, [String])] | | haddockHoogle :: Flag Bool | | haddockHtml :: Flag Bool | | haddockHtmlLocation :: Flag String | | haddockExecutables :: Flag Bool | | haddockInternal :: Flag Bool | | haddockCss :: Flag FilePath | | haddockHscolour :: Flag Bool | | haddockHscolourCss :: Flag FilePath | | haddockDistPref :: Flag FilePath | | haddockVerbosity :: Flag Verbosity | |
|
| Instances | |
|
|
emptyHaddockFlags :: HaddockFlags |
|
defaultHaddockFlags :: HaddockFlags |
|
haddockCommand :: CommandUI HaddockFlags |
|
data HscolourFlags |
Constructors | HscolourFlags | | hscolourCSS :: Flag FilePath | | hscolourExecutables :: Flag Bool | | hscolourDistPref :: Flag FilePath | | hscolourVerbosity :: Flag Verbosity | |
|
| Instances | |
|
|
emptyHscolourFlags :: HscolourFlags |
|
defaultHscolourFlags :: HscolourFlags |
|
hscolourCommand :: CommandUI HscolourFlags |
|
data BuildFlags |
Constructors | BuildFlags | | buildProgramPaths :: [(String, FilePath)] | | buildProgramArgs :: [(String, [String])] | | buildDistPref :: Flag FilePath | | buildVerbosity :: Flag Verbosity | |
|
| Instances | |
|
|
emptyBuildFlags :: BuildFlags |
|
defaultBuildFlags :: BuildFlags |
|
buildCommand :: ProgramConfiguration -> CommandUI BuildFlags |
|
buildVerbose :: BuildFlags -> Verbosity |
|
data CleanFlags |
Constructors | | Instances | |
|
|
emptyCleanFlags :: CleanFlags |
|
defaultCleanFlags :: CleanFlags |
|
cleanCommand :: CommandUI CleanFlags |
|
data RegisterFlags |
Flags to register and unregister: (user package, gen-script,
in-place, verbosity)
| Constructors | | Instances | |
|
|
emptyRegisterFlags :: RegisterFlags |
|
defaultRegisterFlags :: RegisterFlags |
|
registerCommand :: CommandUI RegisterFlags |
|
unregisterCommand :: CommandUI RegisterFlags |
|
data SDistFlags |
Flags to sdist: (snapshot, verbosity)
| Constructors | | Instances | |
|
|
emptySDistFlags :: SDistFlags |
|
defaultSDistFlags :: SDistFlags |
|
sdistCommand :: CommandUI SDistFlags |
|
data TestFlags |
Constructors | | Instances | |
|
|
emptyTestFlags :: TestFlags |
|
defaultTestFlags :: TestFlags |
|
testCommand :: CommandUI TestFlags |
|
data TestShowDetails |
Constructors | | Instances | |
|
|
data CopyDest |
The location prefix for the copy command.
| Constructors | NoCopyDest | | CopyTo FilePath | |
| Instances | |
|
|
configureArgs :: Bool -> ConfigFlags -> [String] |
Arguments to pass to a configure script, e.g. generated by
autoconf.
|
|
configureOptions :: ShowOrParseArgs -> [OptionField ConfigFlags] |
|
configureCCompiler :: Verbosity -> ProgramConfiguration -> IO (FilePath, [String]) |
|
configureLinker :: Verbosity -> ProgramConfiguration -> IO (FilePath, [String]) |
|
installDirsOptions :: [OptionField (InstallDirs (Flag PathTemplate))] |
|
defaultDistPref :: FilePath |
|
data Flag a |
All flags are monoids, they come in two flavours:
1. list flags eg
--ghc-option=foo --ghc-option=bar
gives us all the values [foo, bar]
2. 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.
| Constructors | | Instances | Functor Flag | Bounded a => Bounded (Flag a) | Enum a => Enum (Flag a) | Eq a => Eq (Flag a) | Read a => Read (Flag a) | Show a => Show (Flag a) | Monoid (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 |
|
Produced by Haddock version 2.6.1 |