Cabal-1.3.12: A framework for packaging Haskell softwareContentsIndex
Distribution.Simple.Setup
Portabilityportable
Stabilityalpha
MaintainerIsaac Jones <ijones@syntaxpolice.org>
Description
Explanation: Data types and parser for the standard command-line setup. Will also return commands it doesn't know about.
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)
configVerbose :: Verbosity
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 :: CopyDest
copyDest' :: (Flag CopyDest)
copyDistPref :: (Flag FilePath)
copyVerbose :: Verbosity
copyVerbosity :: (Flag Verbosity)
}
emptyCopyFlags :: CopyFlags
defaultCopyFlags :: CopyFlags
copyCommand :: CommandUI CopyFlags
data InstallFlags = InstallFlags {
installPackageDB :: (Flag PackageDB)
installDistPref :: (Flag FilePath)
installVerbose :: Verbosity
installVerbosity :: (Flag Verbosity)
}
emptyInstallFlags :: InstallFlags
defaultInstallFlags :: InstallFlags
installCommand :: CommandUI InstallFlags
data HaddockFlags = HaddockFlags {
haddockHoogle :: (Flag Bool)
haddockHtmlLocation :: (Flag String)
haddockExecutables :: (Flag Bool)
haddockInternal :: (Flag Bool)
haddockCss :: (Flag FilePath)
haddockHscolour :: (Flag Bool)
haddockHscolourCss :: (Flag FilePath)
haddockDistPref :: (Flag FilePath)
haddockVerbose :: Verbosity
haddockVerbosity :: (Flag Verbosity)
}
emptyHaddockFlags :: HaddockFlags
defaultHaddockFlags :: HaddockFlags
haddockCommand :: CommandUI HaddockFlags
data HscolourFlags = HscolourFlags {
hscolourCSS :: (Flag FilePath)
hscolourExecutables :: (Flag Bool)
hscolourDistPref :: (Flag FilePath)
hscolourVerbose :: Verbosity
hscolourVerbosity :: (Flag Verbosity)
}
emptyHscolourFlags :: HscolourFlags
defaultHscolourFlags :: HscolourFlags
hscolourCommand :: CommandUI HscolourFlags
data BuildFlags = BuildFlags {
buildProgramArgs :: [(String, [String])]
buildDistPref :: (Flag FilePath)
buildVerbose :: Verbosity
buildVerbosity :: (Flag Verbosity)
}
emptyBuildFlags :: BuildFlags
defaultBuildFlags :: BuildFlags
buildCommand :: ProgramConfiguration -> CommandUI BuildFlags
data CleanFlags = CleanFlags {
cleanSaveConf :: (Flag Bool)
cleanDistPref :: (Flag FilePath)
cleanVerbose :: Verbosity
cleanVerbosity :: (Flag Verbosity)
}
emptyCleanFlags :: CleanFlags
defaultCleanFlags :: CleanFlags
cleanCommand :: CommandUI CleanFlags
data MakefileFlags = MakefileFlags {
makefileFile :: (Flag FilePath)
makefileDistPref :: (Flag FilePath)
makefileVerbose :: Verbosity
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)
regVerbose :: Verbosity
regVerbosity :: (Flag Verbosity)
}
emptyRegisterFlags :: RegisterFlags
defaultRegisterFlags :: RegisterFlags
registerCommand :: CommandUI RegisterFlags
unregisterCommand :: CommandUI RegisterFlags
data SDistFlags = SDistFlags {
sDistSnapshot :: (Flag Bool)
sDistDistPref :: (Flag FilePath)
sDistVerbose :: Verbosity
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]
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
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.
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 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
configVerbose :: Verbosityverbosity level (deprecated)
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
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 :: CopyDest
copyDest' :: (Flag CopyDest)
copyDistPref :: (Flag FilePath)
copyVerbose :: Verbosity
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)
installVerbose :: Verbosity
installVerbosity :: (Flag Verbosity)
show/hide Instances
emptyInstallFlags :: InstallFlags
defaultInstallFlags :: InstallFlags
installCommand :: CommandUI InstallFlags
data HaddockFlags
Constructors
HaddockFlags
haddockHoogle :: (Flag Bool)
haddockHtmlLocation :: (Flag String)
haddockExecutables :: (Flag Bool)
haddockInternal :: (Flag Bool)
haddockCss :: (Flag FilePath)
haddockHscolour :: (Flag Bool)
haddockHscolourCss :: (Flag FilePath)
haddockDistPref :: (Flag FilePath)
haddockVerbose :: Verbosity
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)
hscolourVerbose :: Verbosity
hscolourVerbosity :: (Flag Verbosity)
show/hide Instances
emptyHscolourFlags :: HscolourFlags
defaultHscolourFlags :: HscolourFlags
hscolourCommand :: CommandUI HscolourFlags
data BuildFlags
Constructors
BuildFlags
buildProgramArgs :: [(String, [String])]
buildDistPref :: (Flag FilePath)
buildVerbose :: Verbosity
buildVerbosity :: (Flag Verbosity)
show/hide Instances
emptyBuildFlags :: BuildFlags
defaultBuildFlags :: BuildFlags
buildCommand :: ProgramConfiguration -> CommandUI BuildFlags
data CleanFlags
Constructors
CleanFlags
cleanSaveConf :: (Flag Bool)
cleanDistPref :: (Flag FilePath)
cleanVerbose :: Verbosity
cleanVerbosity :: (Flag Verbosity)
show/hide Instances
emptyCleanFlags :: CleanFlags
defaultCleanFlags :: CleanFlags
cleanCommand :: CommandUI CleanFlags
data MakefileFlags
Constructors
MakefileFlags
makefileFile :: (Flag FilePath)
makefileDistPref :: (Flag FilePath)
makefileVerbose :: Verbosity
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)
regVerbose :: Verbosity
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)
sDistVerbose :: Verbosity
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]
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)
Monoid (Flag a)
Show a => Show (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 0.9