Cabal-1.6.0.1: A framework for packaging Haskell softwareContentsIndex
Distribution.Simple.Setup
Portabilityportable
Maintainercabal-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
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])]
configHcFlavor :: Flag CompilerFlavor
configHcPath :: Flag FilePath
configHcPkg :: Flag FilePath
configVanillaLib :: Flag Bool
configProfLib :: Flag Bool
configSharedLib :: 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
configPackageDB :: Flag PackageDB
configGHCiLib :: Flag Bool
configSplitObjs :: Flag Bool
configStripExes :: Flag Bool
configConstraints :: [Dependency]
configConfigurationsFlags :: FlagAssignment
}
emptyConfigFlags :: ConfigFlags
defaultConfigFlags :: ProgramConfiguration -> ConfigFlags
configureCommand :: ProgramConfiguration -> CommandUI ConfigFlags
data CopyFlags = CopyFlags {
copyDest :: Flag CopyDest
copyDistPref :: Flag FilePath
copyUseWrapper :: Flag Bool
copyInPlace :: Flag Bool
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
haddockHtmlLocation :: Flag String
haddockExecutables :: Flag Bool
haddockInternal :: Flag Bool
haddockCss :: Flag FilePath
haddockHscolour :: Flag Bool
haddockHscolourCss :: Flag FilePath
haddockDistPref :: Flag FilePath
haddockVerbosity :: Flag Verbosity
}
emptyHaddockFlags :: HaddockFlags
defaultHaddockFlags :: HaddockFlags
haddockCommand :: CommandUI HaddockFlags
data HscolourFlags = HscolourFlags {
hscolourCSS :: Flag FilePath
hscolourExecutables :: 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
}
emptyBuildFlags :: BuildFlags
defaultBuildFlags :: BuildFlags
buildCommand :: ProgramConfiguration -> CommandUI BuildFlags
buildVerbose :: BuildFlags -> Verbosity
data CleanFlags = CleanFlags {
cleanSaveConf :: Flag Bool
cleanDistPref :: Flag FilePath
cleanVerbosity :: Flag Verbosity
}
emptyCleanFlags :: CleanFlags
defaultCleanFlags :: CleanFlags
cleanCommand :: CommandUI CleanFlags
data MakefileFlags = MakefileFlags {
makefileFile :: Flag FilePath
makefileDistPref :: Flag FilePath
makefileVerbosity :: Flag Verbosity
}
emptyMakefileFlags :: MakefileFlags
defaultMakefileFlags :: MakefileFlags
makefileCommand :: CommandUI MakefileFlags
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
sDistDistPref :: Flag FilePath
sDistVerbosity :: Flag Verbosity
}
emptySDistFlags :: SDistFlags
defaultSDistFlags :: SDistFlags
sdistCommand :: CommandUI SDistFlags
data TestFlags = TestFlags {
testDistPref :: Flag FilePath
testVerbosity :: Flag Verbosity
}
emptyTestFlags :: TestFlags
defaultTestFlags :: TestFlags
testCommand :: CommandUI TestFlags
data CopyDest
= NoCopyDest
| CopyTo FilePath
| CopyPrefix FilePath
configureArgs :: Bool -> ConfigFlags -> [String]
configureOptions :: ShowOrParseArgs -> [OptionField ConfigFlags]
installDirsOptions :: [OptionField (InstallDirs (Flag PathTemplate))]
defaultDistPref :: FilePath
data Flag a
= Flag a
| NoFlag
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
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.
Constructors
GlobalFlags
globalVersion :: Flag Bool
globalNumericVersion :: Flag Bool
show/hide Instances
emptyGlobalFlags :: GlobalFlags
defaultGlobalFlags :: GlobalFlags
globalCommand :: CommandUI GlobalFlags
data ConfigFlags
Flags to configure command
Constructors
ConfigFlags
configPrograms :: ProgramConfigurationAll programs that cabal may run
configProgramPaths :: [(String, FilePath)]user specifed programs paths
configProgramArgs :: [(String, [String])]user specifed programs args
configHcFlavor :: Flag CompilerFlavorThe "flavor" of the compiler, sugh as GHC or Hugs.
configHcPath :: Flag FilePathgiven compiler location
configHcPkg :: Flag FilePathgiven hc-pkg location
configVanillaLib :: Flag BoolEnable vanilla library
configProfLib :: Flag BoolEnable profiling in the library
configSharedLib :: Flag BoolBuild shared library
configProfExe :: Flag BoolEnable profiling in the executables.
configConfigureArgs :: [String]Extra arguments to configure
configOptimization :: Flag OptimisationLevelEnable optimization.
configProgPrefix :: Flag PathTemplateInstalled executable prefix.
configProgSuffix :: Flag PathTemplateInstalled 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 FilePathdist prefix
configVerbosity :: Flag Verbosityverbosity level
configUserInstall :: Flag BoolThe --user/--global flag
configPackageDB :: Flag PackageDBWhich package DB to use
configGHCiLib :: Flag BoolEnable compiling library for GHCi
configSplitObjs :: Flag BoolEnable -split-objs with GHC
configStripExes :: Flag BoolEnable executable stripping
configConstraints :: [Dependency]Additional constraints for dependencies
configConfigurationsFlags :: FlagAssignment
show/hide Instances
emptyConfigFlags :: ConfigFlags
defaultConfigFlags :: ProgramConfiguration -> ConfigFlags
configureCommand :: ProgramConfiguration -> CommandUI ConfigFlags
data CopyFlags
Flags to copy: (destdir, copy-prefix (backwards compat), verbosity)
Constructors
CopyFlags
copyDest :: Flag CopyDest
copyDistPref :: Flag FilePath
copyUseWrapper :: Flag Bool
copyInPlace :: Flag Bool
copyVerbosity :: Flag Verbosity
show/hide Instances
emptyCopyFlags :: CopyFlags
defaultCopyFlags :: CopyFlags
copyCommand :: CommandUI CopyFlags
data InstallFlags
Flags to install: (package db, verbosity)
Constructors
InstallFlags
installPackageDB :: Flag PackageDB
installDistPref :: Flag FilePath
installUseWrapper :: Flag Bool
installInPlace :: Flag Bool
installVerbosity :: Flag Verbosity
show/hide Instances
emptyInstallFlags :: InstallFlags
defaultInstallFlags :: InstallFlags
installCommand :: CommandUI InstallFlags
data HaddockFlags
Constructors
HaddockFlags
haddockProgramPaths :: [(String, FilePath)]
haddockProgramArgs :: [(String, [String])]
haddockHoogle :: 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
show/hide Instances
emptyHaddockFlags :: HaddockFlags
defaultHaddockFlags :: HaddockFlags
haddockCommand :: CommandUI HaddockFlags
data HscolourFlags
Constructors
HscolourFlags
hscolourCSS :: Flag FilePath
hscolourExecutables :: Flag Bool
hscolourDistPref :: Flag FilePath
hscolourVerbosity :: Flag Verbosity
show/hide Instances
emptyHscolourFlags :: HscolourFlags
defaultHscolourFlags :: HscolourFlags
hscolourCommand :: CommandUI HscolourFlags
data BuildFlags
Constructors
BuildFlags
buildProgramPaths :: [(String, FilePath)]
buildProgramArgs :: [(String, [String])]
buildDistPref :: Flag FilePath
buildVerbosity :: Flag Verbosity
show/hide Instances
emptyBuildFlags :: BuildFlags
defaultBuildFlags :: BuildFlags
buildCommand :: ProgramConfiguration -> CommandUI BuildFlags
buildVerbose :: BuildFlags -> Verbosity
data CleanFlags
Constructors
CleanFlags
cleanSaveConf :: Flag Bool
cleanDistPref :: Flag FilePath
cleanVerbosity :: Flag Verbosity
show/hide Instances
emptyCleanFlags :: CleanFlags
defaultCleanFlags :: CleanFlags
cleanCommand :: CommandUI CleanFlags
data MakefileFlags
Constructors
MakefileFlags
makefileFile :: Flag FilePath
makefileDistPref :: Flag FilePath
makefileVerbosity :: Flag Verbosity
show/hide Instances
emptyMakefileFlags :: MakefileFlags
defaultMakefileFlags :: MakefileFlags
makefileCommand :: CommandUI MakefileFlags
data RegisterFlags
Flags to register and unregister: (user package, gen-script, in-place, verbosity)
Constructors
RegisterFlags
regPackageDB :: Flag PackageDB
regGenScript :: Flag Bool
regGenPkgConf :: Flag (Maybe FilePath)
regInPlace :: Flag Bool
regDistPref :: Flag FilePath
regVerbosity :: Flag Verbosity
show/hide Instances
emptyRegisterFlags :: RegisterFlags
defaultRegisterFlags :: RegisterFlags
registerCommand :: CommandUI RegisterFlags
unregisterCommand :: CommandUI RegisterFlags
data SDistFlags
Flags to sdist: (snapshot, verbosity)
Constructors
SDistFlags
sDistSnapshot :: Flag Bool
sDistDistPref :: Flag FilePath
sDistVerbosity :: Flag Verbosity
show/hide Instances
emptySDistFlags :: SDistFlags
defaultSDistFlags :: SDistFlags
sdistCommand :: CommandUI SDistFlags
data TestFlags
Constructors
TestFlags
testDistPref :: Flag FilePath
testVerbosity :: Flag Verbosity
show/hide Instances
emptyTestFlags :: TestFlags
defaultTestFlags :: TestFlags
testCommand :: CommandUI TestFlags
data CopyDest
The location prefix for the copy command.
Constructors
NoCopyDest
CopyTo FilePath
CopyPrefix FilePath
show/hide Instances
configureArgs :: Bool -> ConfigFlags -> [String]
Arguments to pass to a configure script, e.g. generated by autoconf.
configureOptions :: ShowOrParseArgs -> [OptionField ConfigFlags]
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
Flag a
NoFlag
show/hide Instances
Functor Flag
Bounded a => Bounded (Flag a)
Enum a => Enum (Flag a)
Eq a => Eq (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
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.3.0