Cabal-1.24.2.0: A framework for packaging Haskell software

CopyrightIsaac Jones 2003-2004
Duncan Coutts 2007
LicenseBSD3
Maintainercabal-devel@haskell.org
Portabilityportable
Safe HaskellNone
LanguageHaskell98

Distribution.Simple.Setup

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 Source #

Flags that apply at the top level, not to any sub-command.

data ConfigFlags Source #

Flags to configure command.

IMPORTANT: every time a new flag is added, filterConfigureFlags should be updated.

Constructors

ConfigFlags 

Fields

Instances

Read ConfigFlags Source # 
Show ConfigFlags Source # 
Generic ConfigFlags Source # 

Associated Types

type Rep ConfigFlags :: * -> * #

Semigroup ConfigFlags Source # 
Monoid ConfigFlags Source # 
Binary ConfigFlags Source # 
type Rep ConfigFlags Source # 
type Rep ConfigFlags = D1 (MetaData "ConfigFlags" "Distribution.Simple.Setup" "Cabal-1.24.2.0-DZNolZ9MBQLKV7GSAwAGX6" False) (C1 (MetaCons "ConfigFlags" PrefixI True) ((:*:) ((:*:) ((:*:) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "configPrograms_") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Last' ProgramConfiguration))) (S1 (MetaSel (Just Symbol "configProgramPaths") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [(String, FilePath)]))) ((:*:) (S1 (MetaSel (Just Symbol "configProgramArgs") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [(String, [String])])) ((:*:) (S1 (MetaSel (Just Symbol "configProgramPathExtra") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (NubList FilePath))) (S1 (MetaSel (Just Symbol "configHcFlavor") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Flag CompilerFlavor)))))) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "configHcPath") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Flag FilePath))) ((:*:) (S1 (MetaSel (Just Symbol "configHcPkg") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Flag FilePath))) (S1 (MetaSel (Just Symbol "configVanillaLib") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Flag Bool))))) ((:*:) (S1 (MetaSel (Just Symbol "configProfLib") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Flag Bool))) ((:*:) (S1 (MetaSel (Just Symbol "configSharedLib") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Flag Bool))) (S1 (MetaSel (Just Symbol "configDynExe") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Flag Bool))))))) ((:*:) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "configProfExe") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Flag Bool))) (S1 (MetaSel (Just Symbol "configProf") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Flag Bool)))) ((:*:) (S1 (MetaSel (Just Symbol "configProfDetail") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Flag ProfDetailLevel))) ((:*:) (S1 (MetaSel (Just Symbol "configProfLibDetail") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Flag ProfDetailLevel))) (S1 (MetaSel (Just Symbol "configConfigureArgs") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [String]))))) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "configOptimization") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Flag OptimisationLevel))) ((:*:) (S1 (MetaSel (Just Symbol "configProgPrefix") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Flag PathTemplate))) (S1 (MetaSel (Just Symbol "configProgSuffix") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Flag PathTemplate))))) ((:*:) (S1 (MetaSel (Just Symbol "configInstallDirs") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (InstallDirs (Flag PathTemplate)))) ((:*:) (S1 (MetaSel (Just Symbol "configScratchDir") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Flag FilePath))) (S1 (MetaSel (Just Symbol "configExtraLibDirs") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [FilePath]))))))) ((:*:) ((:*:) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "configExtraFrameworkDirs") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [FilePath])) (S1 (MetaSel (Just Symbol "configExtraIncludeDirs") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [FilePath]))) ((:*:) (S1 (MetaSel (Just Symbol "configIPID") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Flag String))) ((:*:) (S1 (MetaSel (Just Symbol "configDistPref") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Flag FilePath))) (S1 (MetaSel (Just Symbol "configVerbosity") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Flag Verbosity)))))) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "configUserInstall") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Flag Bool))) ((:*:) (S1 (MetaSel (Just Symbol "configPackageDBs") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Maybe PackageDB])) (S1 (MetaSel (Just Symbol "configGHCiLib") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Flag Bool))))) ((:*:) (S1 (MetaSel (Just Symbol "configSplitObjs") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Flag Bool))) ((:*:) (S1 (MetaSel (Just Symbol "configStripExes") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Flag Bool))) (S1 (MetaSel (Just Symbol "configStripLibs") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Flag Bool))))))) ((:*:) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "configConstraints") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Dependency])) ((:*:) (S1 (MetaSel (Just Symbol "configDependencies") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [(PackageName, UnitId)])) (S1 (MetaSel (Just Symbol "configConfigurationsFlags") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 FlagAssignment)))) ((:*:) (S1 (MetaSel (Just Symbol "configTests") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Flag Bool))) ((:*:) (S1 (MetaSel (Just Symbol "configBenchmarks") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Flag Bool))) (S1 (MetaSel (Just Symbol "configCoverage") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Flag Bool)))))) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "configLibCoverage") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Flag Bool))) ((:*:) (S1 (MetaSel (Just Symbol "configExactConfiguration") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Flag Bool))) (S1 (MetaSel (Just Symbol "configFlagError") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Flag String))))) ((:*:) (S1 (MetaSel (Just Symbol "configRelocatable") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Flag Bool))) ((:*:) (S1 (MetaSel (Just Symbol "configDebugInfo") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Flag DebugInfoLevel))) (S1 (MetaSel (Just Symbol "configAllowNewer") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe AllowNewer))))))))))

configPrograms :: ConfigFlags -> ProgramConfiguration Source #

More convenient version of configPrograms. Results in an error if internal invariant is violated.

data AllowNewer Source #

Policy for relaxing upper bounds in dependencies. For example, given 'build-depends: array >= 0.3 && < 0.5', are we allowed to relax the upper bound and choose a version of array that is greater or equal to 0.5? By default the upper bounds are always strictly honored.

Constructors

AllowNewerNone

Default: honor the upper bounds in all dependencies, never choose versions newer than allowed.

AllowNewerSome [AllowNewerDep]

Ignore upper bounds in dependencies on the given packages.

AllowNewerAll

Ignore upper bounds in dependencies on all packages.

data AllowNewerDep Source #

Dependencies can be relaxed either for all packages in the install plan, or only for some packages.

isAllowNewer :: AllowNewer -> Bool Source #

Convert AllowNewer to a boolean.

data CopyFlags Source #

Flags to copy: (destdir, copy-prefix (backwards compat), verbosity)

data InstallFlags Source #

Flags to install: (package db, verbosity)

Instances

Show InstallFlags Source # 
Generic InstallFlags Source # 

Associated Types

type Rep InstallFlags :: * -> * #

Semigroup InstallFlags Source # 
Monoid InstallFlags Source # 
type Rep InstallFlags Source # 
type Rep InstallFlags = D1 (MetaData "InstallFlags" "Distribution.Simple.Setup" "Cabal-1.24.2.0-DZNolZ9MBQLKV7GSAwAGX6" False) (C1 (MetaCons "InstallFlags" PrefixI True) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "installPackageDB") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Flag PackageDB))) (S1 (MetaSel (Just Symbol "installDistPref") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Flag FilePath)))) ((:*:) (S1 (MetaSel (Just Symbol "installUseWrapper") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Flag Bool))) ((:*:) (S1 (MetaSel (Just Symbol "installInPlace") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Flag Bool))) (S1 (MetaSel (Just Symbol "installVerbosity") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Flag Verbosity)))))))

data HaddockTarget Source #

When we build haddock documentation, there are two cases:

  1. We build haddocks only for the current development version, intended for local use and not for distribution. In this case, we store the generated documentation in distdochtml/name.
  2. We build haddocks for intended for uploading them to hackage. In this case, we need to follow the layout that hackage expects from documentation tarballs, and we might also want to use different flags than for development builds, so in this case we store the generated documentation in distdochtml/id-docs.

Constructors

ForHackage 
ForDevelopment 

Instances

Eq HaddockTarget Source # 
Show HaddockTarget Source # 
Generic HaddockTarget Source # 

Associated Types

type Rep HaddockTarget :: * -> * #

type Rep HaddockTarget Source # 
type Rep HaddockTarget = D1 (MetaData "HaddockTarget" "Distribution.Simple.Setup" "Cabal-1.24.2.0-DZNolZ9MBQLKV7GSAwAGX6" False) ((:+:) (C1 (MetaCons "ForHackage" PrefixI False) U1) (C1 (MetaCons "ForDevelopment" PrefixI False) U1))

data HaddockFlags Source #

Instances

Show HaddockFlags Source # 
Generic HaddockFlags Source # 

Associated Types

type Rep HaddockFlags :: * -> * #

Semigroup HaddockFlags Source # 
Monoid HaddockFlags Source # 
type Rep HaddockFlags Source # 
type Rep HaddockFlags = D1 (MetaData "HaddockFlags" "Distribution.Simple.Setup" "Cabal-1.24.2.0-DZNolZ9MBQLKV7GSAwAGX6" False) (C1 (MetaCons "HaddockFlags" PrefixI True) ((:*:) ((:*:) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "haddockProgramPaths") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [(String, FilePath)])) (S1 (MetaSel (Just Symbol "haddockProgramArgs") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [(String, [String])]))) ((:*:) (S1 (MetaSel (Just Symbol "haddockHoogle") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Flag Bool))) (S1 (MetaSel (Just Symbol "haddockHtml") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Flag Bool))))) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "haddockHtmlLocation") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Flag String))) (S1 (MetaSel (Just Symbol "haddockForHackage") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Flag Bool)))) ((:*:) (S1 (MetaSel (Just Symbol "haddockExecutables") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Flag Bool))) (S1 (MetaSel (Just Symbol "haddockTestSuites") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Flag Bool)))))) ((:*:) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "haddockBenchmarks") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Flag Bool))) (S1 (MetaSel (Just Symbol "haddockInternal") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Flag Bool)))) ((:*:) (S1 (MetaSel (Just Symbol "haddockCss") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Flag FilePath))) (S1 (MetaSel (Just Symbol "haddockHscolour") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Flag Bool))))) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "haddockHscolourCss") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Flag FilePath))) (S1 (MetaSel (Just Symbol "haddockContents") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Flag PathTemplate)))) ((:*:) (S1 (MetaSel (Just Symbol "haddockDistPref") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Flag FilePath))) ((:*:) (S1 (MetaSel (Just Symbol "haddockKeepTempFiles") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Flag Bool))) (S1 (MetaSel (Just Symbol "haddockVerbosity") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Flag Verbosity)))))))))

data HscolourFlags Source #

Instances

Show HscolourFlags Source # 
Generic HscolourFlags Source # 

Associated Types

type Rep HscolourFlags :: * -> * #

Semigroup HscolourFlags Source # 
Monoid HscolourFlags Source # 
type Rep HscolourFlags Source # 

data BuildFlags Source #

Instances

Show BuildFlags Source # 
Generic BuildFlags Source # 

Associated Types

type Rep BuildFlags :: * -> * #

Semigroup BuildFlags Source # 
Monoid BuildFlags Source # 
type Rep BuildFlags Source # 

buildVerbose :: BuildFlags -> Verbosity Source #

Deprecated: Use buildVerbosity instead

data ReplFlags Source #

data RegisterFlags Source #

Flags to register and unregister: (user package, gen-script, in-place, verbosity)

Instances

Show RegisterFlags Source # 
Generic RegisterFlags Source # 

Associated Types

type Rep RegisterFlags :: * -> * #

Semigroup RegisterFlags Source # 
Monoid RegisterFlags Source # 
type Rep RegisterFlags Source # 

data SDistFlags Source #

Flags to sdist: (snapshot, verbosity)

data TestFlags Source #

Instances

Generic TestFlags Source # 

Associated Types

type Rep TestFlags :: * -> * #

Semigroup TestFlags Source # 
Monoid TestFlags Source # 
type Rep TestFlags Source # 

data TestShowDetails Source #

Instances

Bounded TestShowDetails Source # 
Enum TestShowDetails Source # 
Eq TestShowDetails Source # 
Ord TestShowDetails Source # 
Show TestShowDetails Source # 
Semigroup TestShowDetails Source # 
Monoid TestShowDetails Source # 
Text TestShowDetails Source # 

data CopyDest Source #

The location prefix for the copy command.

Constructors

NoCopyDest 
CopyTo FilePath 

configureArgs :: Bool -> ConfigFlags -> [String] Source #

Arguments to pass to a configure script, e.g. generated by autoconf.

programConfigurationOptions :: ProgramConfiguration -> ShowOrParseArgs -> (flags -> [(String, [String])]) -> ([(String, [String])] -> flags -> flags) -> [OptionField flags] Source #

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] Source #

Like programConfigurationPaths, but allows to customise the option name.

splitArgs :: String -> [String] Source #

Helper function to split a string into a list of arguments. It's supposed to handle quoted things sensibly, eg:

splitArgs "--foo=\"C:\Program Files\Bar\" --baz"
  = ["--foo=C:\Program Files\Bar", "--baz"]

optionDistPref :: (flags -> Flag FilePath) -> (Flag FilePath -> flags -> flags) -> ShowOrParseArgs -> OptionField flags Source #

data Flag a Source #

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"]

  1. 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 

Instances

Functor Flag Source # 

Methods

fmap :: (a -> b) -> Flag a -> Flag b #

(<$) :: a -> Flag b -> Flag a #

Bounded a => Bounded (Flag a) Source # 

Methods

minBound :: Flag a #

maxBound :: Flag a #

Enum a => Enum (Flag a) Source # 

Methods

succ :: Flag a -> Flag a #

pred :: Flag a -> Flag a #

toEnum :: Int -> Flag a #

fromEnum :: Flag a -> Int #

enumFrom :: Flag a -> [Flag a] #

enumFromThen :: Flag a -> Flag a -> [Flag a] #

enumFromTo :: Flag a -> Flag a -> [Flag a] #

enumFromThenTo :: Flag a -> Flag a -> Flag a -> [Flag a] #

Eq a => Eq (Flag a) Source # 

Methods

(==) :: Flag a -> Flag a -> Bool #

(/=) :: Flag a -> Flag a -> Bool #

Read a => Read (Flag a) Source # 
Show a => Show (Flag a) Source # 

Methods

showsPrec :: Int -> Flag a -> ShowS #

show :: Flag a -> String #

showList :: [Flag a] -> ShowS #

Generic (Flag a) Source # 

Associated Types

type Rep (Flag a) :: * -> * #

Methods

from :: Flag a -> Rep (Flag a) x #

to :: Rep (Flag a) x -> Flag a #

Semigroup (Flag a) Source # 

Methods

(<>) :: Flag a -> Flag a -> Flag a #

sconcat :: NonEmpty (Flag a) -> Flag a #

stimes :: Integral b => b -> Flag a -> Flag a #

Monoid (Flag a) Source # 

Methods

mempty :: Flag a #

mappend :: Flag a -> Flag a -> Flag a #

mconcat :: [Flag a] -> Flag a #

Binary a => Binary (Flag a) Source # 

Methods

put :: Flag a -> Put #

get :: Get (Flag a) #

putList :: [Flag a] -> Put #

type Rep (Flag a) Source # 
type Rep (Flag a) = D1 (MetaData "Flag" "Distribution.Simple.Setup" "Cabal-1.24.2.0-DZNolZ9MBQLKV7GSAwAGX6" False) ((:+:) (C1 (MetaCons "Flag" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a))) (C1 (MetaCons "NoFlag" PrefixI False) U1))

toFlag :: a -> Flag a Source #

fromFlag :: Flag a -> a Source #

flagToList :: Flag a -> [a] Source #

boolOpt :: SFlags -> SFlags -> MkOptDescr (a -> Flag Bool) (Flag Bool -> a -> a) a Source #

boolOpt' :: OptFlags -> OptFlags -> MkOptDescr (a -> Flag Bool) (Flag Bool -> a -> a) a Source #

trueArg :: MkOptDescr (a -> Flag Bool) (Flag Bool -> a -> a) a Source #

falseArg :: MkOptDescr (a -> Flag Bool) (Flag Bool -> a -> a) a Source #

optionVerbosity :: (flags -> Flag Verbosity) -> (Flag Verbosity -> flags -> flags) -> OptionField flags Source #

optionNumJobs :: (flags -> Flag (Maybe Int)) -> (Flag (Maybe Int) -> flags -> flags) -> OptionField flags Source #